MAPL_GenericRecord Subroutine

public recursive subroutine MAPL_GenericRecord(GC, IMPORT, EXPORT, CLOCK, RC)

Arguments

Type IntentOptional Attributes Name
type(ESMF_GridComp), intent(inout) :: GC
type(ESMF_State), intent(inout) :: IMPORT
type(ESMF_State), intent(inout) :: EXPORT
type(ESMF_Clock), intent(inout) :: CLOCK
integer, intent(out), optional :: RC

Calls

MAPL_GenericRecordwArrDescrCreateReaderComm
w
wArrDescrCreateWriterComm
w
wArrDescrSet
w
wCompositeComponent%get_num_children
w
wDistributedProfiler%start
w
wESMF_AlarmIsRinging
w
wESMF_AttributeGet
w
wESMF_ClockGet
w
wESMF_GridCompGet
w
wESMF_GridCompWriteRestart
w
wESMF_GridGet
w
wesmf_stateget
w
wESMF_TimeGet
w
wESMF_UtilStringLowerCase
w
wFREE_FILE
w
wget_global_time_profiler
w
wGETFILE
w
wLogger%warning
w
wMAPL_Am_I_Root
w
wMAPL_Assert
w
wMAPL_DateStampGet
w
wMAPL_GetLogger
w
wMAPL_GetResource
w
wMAPL_GridGet
w
wMAPL_InternalStateRetrieve
w
wMAPL_LocStreamGet
w
wMAPL_LocStreamIsAssociated
w
wMAPL_MetaComp%get_child_export_state
w
wMAPL_MetaComp%get_child_gridcomp
w
wMAPL_MetaComp%get_child_import_state
w
wMAPL_Return
w
wMAPL_TimerOff
w
wMAPL_TimerOn
w
wMAPL_VarWrite
w
wMAPL_VarWriteNCPar
w
wMAPL_Verify
w
wMaplGenericComponent%get_internal_state
w
wmpi_barrier
w
wmpi_comm_rank
w
wmpi_file_close
w
wmpi_file_open
w
wmpi_info_create
w
wmpi_info_free
w
wmpi_info_set
w
wWRITE_PARALLEL
w

Source Code

   recursive subroutine MAPL_GenericRecord ( GC, IMPORT, EXPORT, CLOCK, RC )

      ! !ARGUMENTS:

      type(ESMF_GridComp), intent(inout) :: GC     ! composite gridded component
      type(ESMF_State),    intent(inout) :: IMPORT ! import state
      type(ESMF_State),    intent(inout) :: EXPORT ! export state
      type(ESMF_Clock),    intent(inout) :: CLOCK  ! the clock
      integer, optional,   intent(  out) :: RC     ! Error code:
      ! = 0 all is well
      ! otherwise, error
      !EOPI

      ! LOCAL VARIABLES

      character(len=ESMF_MAXSTR)                  :: IAm
      character(len=ESMF_MAXSTR)                  :: comp_name
      character(len=ESMF_MAXSTR)                  :: CHILD_NAME
      character(len=14)                           :: datestamp ! YYYYMMDD_HHMMz
      integer                                     :: status
      integer                                     :: userRC
      integer                                     :: I
      type (MAPL_MetaComp), pointer               :: STATE

      integer                                     :: filetype
      character(len=1)                            :: separator

      character(len=ESMF_MAXSTR)                  :: filetypechar
      character(len=4)                            :: extension
      integer                                     :: hdr

      integer                                     :: K
      logical                                     :: ftype(0:1)
      class(BaseProfiler), pointer                :: t_p
      type(ESMF_GridComp), pointer :: gridcomp
      type(ESMF_State), pointer :: child_import_state
      type(ESMF_State), pointer :: child_export_state
      !=============================================================================

      !  Begin...

      Iam = "MAPL_GenericRecord"
      call ESMF_GridCompGet(GC, name=comp_name, RC=status )
      _VERIFY(status)
      Iam = trim(comp_name) // Iam

      ! Retrieve the pointer to the state
      !----------------------------------

      call MAPL_InternalStateRetrieve(GC, STATE, RC=status)
      _VERIFY(status)

      t_p => get_global_time_profiler()
      call state%t_profiler%start(_RC)
      call state%t_profiler%start('Record',_RC)


      ! Record the children
      ! ---------------------
      do I = 1, STATE%get_num_children()
         call ESMF_GridCompGet( STATE%GET_CHILD_GRIDCOMP(I), NAME=CHILD_NAME, RC=status )
         _VERIFY(status)
         call MAPL_TimerOn (STATE,trim(CHILD_NAME))
         gridcomp => STATE%GET_CHILD_GRIDCOMP(I)
         child_import_state => STATE%get_child_import_state(i)
         child_export_state => STATE%get_child_export_state(i)
         call ESMF_GridCompWriteRestart (gridcomp, &
              importState=child_import_state, &
              exportState=child_export_state, &
              clock=CLOCK, userRC=userRC, _RC ) ! number of phases is currently limited to 1
         _VERIFY(userRC)
         call MAPL_TimerOff(STATE,trim(CHILD_NAME))
      enddo

      ! Do my "own" record
      ! ------------------
      call MAPL_TimerOn(STATE,"generic")

      if (associated(STATE%RECORD)) then

         FILETYPE = MAPL_Write2Disk
         ftype = .false.
         DO I = 1, size(STATE%RECORD%ALARM)
            if ( ESMF_AlarmIsRinging(STATE%RECORD%ALARM(I), RC=status) ) then
               _VERIFY(status)
               filetype = STATE%RECORD%FILETYPE(I)

               if (.not. ftype(filetype)) then
                  !ALT: we do this only ONCE per given filetype (RAM or Disk)
                  ftype(filetype) = .true.
                  ! add timestamp to filename
                  call MAPL_DateStampGet(clock, datestamp, rc=status)
                  _VERIFY(status)

                  if (FILETYPE /= MAPL_Write2Disk) then
                     separator = '*'
                  else
                     separator = '.'
                  end if

                  K=STATE%RECORD%IMP_LEN
                  if (K > 0) then
                     call    MAPL_GetResource( STATE, filetypechar, LABEL="IMPORT_CHECKPOINT_TYPE:",                  RC=status )
                     if ( status/=ESMF_SUCCESS  .or.  filetypechar == "default" ) then
                        call MAPL_GetResource( STATE, filetypechar, LABEL="DEFAULT_CHECKPOINT_TYPE:", default='pnc4', RC=status )
                        _VERIFY(status)
                     end if
                     filetypechar = ESMF_UtilStringLowerCase(filetypechar,rc=status)
                     _VERIFY(status)
                     if (filetypechar == 'pnc4') then
                        extension = '.nc4'
                     else
                        extension = '.bin'
                     end if
                     STATE%RECORD%IMP_FNAME(K+1:) = separator // DATESTAMP // extension
                  end if

                  K=STATE%RECORD%INT_LEN
                  if (K > 0) then
                     call    MAPL_GetResource( STATE, hdr,      LABEL="INTERNAL_HEADER:",         default=0,      RC=status )
                     _VERIFY(status)
                     call    MAPL_GetResource( STATE, filetypechar, LABEL="INTERNAL_CHECKPOINT_TYPE:",                RC=status )
                     if ( status/=ESMF_SUCCESS  .or.  filetypechar == "default" ) then
                        call MAPL_GetResource( STATE, filetypechar, LABEL="DEFAULT_CHECKPOINT_TYPE:", default='pnc4', RC=status )
                        _VERIFY(status)
                     end if
                     filetypechar = ESMF_UtilStringLowerCase(filetypechar,rc=status)
                     _VERIFY(status)
                     if (filetypechar == 'pnc4') then
                        extension = '.nc4'
                     else
                        extension = '.bin'
                     end if
                     STATE%RECORD%INT_FNAME(K+1:) = separator // DATESTAMP // extension
                  end if

                  ! call the actual record method
                  call MAPL_StateRecord (GC, IMPORT, EXPORT, CLOCK, RC=status )
                  _VERIFY(status)
               endif
            end if
         END DO
      endif
      call MAPL_TimerOff(STATE,"generic",_RC)

      call state%t_profiler%stop('Record',_RC)
      call state%t_profiler%stop(_RC)

      _RETURN(ESMF_SUCCESS)
   end subroutine MAPL_GenericRecord