tem_load_restart Subroutine

public subroutine tem_load_restart(me, conf, tree, timing, globProc, parent_table, key)

Read all necessary information for the restart from the lua config file.

Include this routine into your general configuration load routine. The configuration looks as follows

 restart = { read = 'restart/lastHeader.lua', -- Which file to restart from,
                                              -- if any
             write = 'restart/', -- Where to write the restart files to,
                                 -- if any
             time = { min = 0, max = 10, interval = 10} -- when to output
             }

Here, the restart is loaded from restart/lastHeader.lua and reads in the related data and configuration. Restart files are written out in restart/ folder

Arguments

Type IntentOptional Attributes Name
type(tem_restart_type), intent(inout) :: me

restart type to be filled

type(flu_State) :: conf

lua configuration file

type(treelmesh_type), intent(inout) :: tree

mesh, provided in treelm format

type(tem_time_type), intent(inout) :: timing

the timing for re-setting the times

type(tem_comm_env_type), intent(in) :: globProc

Global process communicator env

integer, intent(in), optional :: parent_table

optional parent handle

character(len=*), intent(in), optional :: key

optional key for table


Calls

proc~~tem_load_restart~~CallsGraph proc~tem_load_restart tem_load_restart aot_get_val aot_get_val proc~tem_load_restart->aot_get_val aot_table_close aot_table_close proc~tem_load_restart->aot_table_close aot_table_open aot_table_open proc~tem_load_restart->aot_table_open mpi_bcast mpi_bcast proc~tem_load_restart->mpi_bcast proc~tem_abort tem_abort proc~tem_load_restart->proc~tem_abort proc~tem_horizontalspacer tem_horizontalSpacer proc~tem_load_restart->proc~tem_horizontalspacer proc~tem_restart_readheader tem_restart_readHeader proc~tem_load_restart->proc~tem_restart_readheader proc~tem_time_reset tem_time_reset proc~tem_load_restart->proc~tem_time_reset proc~tem_time_set_clock tem_time_set_clock proc~tem_load_restart->proc~tem_time_set_clock proc~tem_timecontrol_align_trigger tem_timeControl_align_trigger proc~tem_load_restart->proc~tem_timecontrol_align_trigger proc~tem_timecontrol_dump tem_timeControl_dump proc~tem_load_restart->proc~tem_timecontrol_dump proc~tem_timecontrol_load tem_timeControl_load proc~tem_load_restart->proc~tem_timecontrol_load mpi_abort mpi_abort proc~tem_abort->mpi_abort proc~tem_restart_readheader->aot_get_val proc~tem_restart_readheader->aot_table_close proc~tem_restart_readheader->aot_table_open close_config close_config proc~tem_restart_readheader->close_config interface~tem_varsys_dump tem_varSys_dump proc~tem_restart_readheader->interface~tem_varsys_dump interface~tem_varsys_load tem_varSys_load proc~tem_restart_readheader->interface~tem_varsys_load proc~load_tem load_tem proc~tem_restart_readheader->proc~load_tem proc~tem_open_distconf tem_open_distconf proc~tem_restart_readheader->proc~tem_open_distconf proc~tem_time_dump tem_time_dump proc~tem_restart_readheader->proc~tem_time_dump proc~tem_time_load tem_time_load proc~tem_restart_readheader->proc~tem_time_load proc~tem_time_sim_stamp tem_time_sim_stamp proc~tem_restart_readheader->proc~tem_time_sim_stamp mpi_wtime mpi_wtime proc~tem_time_reset->mpi_wtime proc~tem_time_set_clock->mpi_wtime proc~tem_timecontrol_align_trigger->aot_table_open proc~load_alignmask load_alignmask proc~tem_timecontrol_align_trigger->proc~load_alignmask proc~tem_time_ge_trigger tem_time_ge_trigger proc~tem_timecontrol_align_trigger->proc~tem_time_ge_trigger proc~tem_time_last_interval tem_time_last_interval proc~tem_timecontrol_align_trigger->proc~tem_time_last_interval proc~tem_timecontrol_dump->proc~tem_time_dump proc~tem_timecontrol_load->aot_get_val proc~tem_timecontrol_load->aot_table_close proc~tem_timecontrol_load->aot_table_open proc~tem_time_default_zero tem_time_default_zero proc~tem_timecontrol_load->proc~tem_time_default_zero proc~tem_timecontrol_load->proc~tem_time_load proc~tem_time_needs_reduce tem_time_needs_reduce proc~tem_timecontrol_load->proc~tem_time_needs_reduce proc~tem_time_never tem_time_never proc~tem_timecontrol_load->proc~tem_time_never

Source Code

  subroutine tem_load_restart( me, conf, tree, timing, globProc, parent_table, &
    &                          key )
    ! -------------------------------------------------------------------- !
    !> restart type to be filled
    type(tem_restart_type), intent(inout)  :: me
    !> lua configuration file
    type(flu_state)                        :: conf
    !> mesh, provided in treelm format
    type(treelmesh_type), intent(inout)    :: tree
    !> the timing for re-setting the times
    type(tem_time_type), intent(inout)     :: timing
    !> Global process communicator env
    type( tem_comm_env_type ), intent(in)  :: globProc
    !> optional parent handle
    integer, optional, intent(in)          :: parent_table
    !> optional key for table
    character(len=*), optional, intent(in) :: key
    ! -------------------------------------------------------------------- !
    character(len=32) :: localKey
    logical :: readexists
    integer :: restart_table
    integer :: iError
    ! -------------------------------------------------------------------- !

    if (present(key)) then
      ! The table to look for is not named restart, look for this different
      ! key.
      localKey = key
    else
      ! Use the default name restart for the table.
      localKey = 'restart'
      ! Set current folder as default prefix for writing
      me%controller%writePrefix = '.'//pathSep
    end if

    me%controller%readRestart  = .false.
    me%controller%writeRestart = .false.

    ! Attempt to open the restart table (within another table, if a parent is
    ! given).
    call aot_table_open( L       = conf,          &
      &                  thandle = restart_table, &
      &                  parent  = parent_table,  &
      &                  key     = trim(localKey) )

    ! Initialize the last written time to 0.
    call tem_time_reset(me%lastWritten)
    me%lastWritten%iter = -1

    ! If the restart table is present, the parameters are loaded.
    ! In case of dynamic load balancing, parameters are loaded
    ! in a different manner i.e. timings etc. are read from balance table
    if (restart_table .ne. 0 ) then
      call tem_horizontalSpacer(fUnit = logUnit(1))
      write(logUnit(1),*) 'Loading restart ...'
      ! Successfully opened the table.

      ! First we get all the informations of the read table.
      ! Reading the filename to read the restart data from.
      call aot_get_val( L       = conf,                       &
        &               thandle = restart_table,              &
        &               key     = 'read',                     &
        &               val     = me%controller%readFileName, &
        &               ErrCode = iError                      )

      if (iError == 0) then
        call aot_get_val( L       = conf,                          &
          &               thandle = restart_table,                 &
          &               key     = 'init_on_missing',             &
          &               val     = me%controller%init_on_missing, &
          &               default = .false.,                       &
          &               ErrCode = iError                         )

        ! Successfully obtained a filename to restart from, now go on and read
        ! the data from its header if it exists.
        write(logUnit(1),*) "*****************************"
        write(logUnit(1),*) "Restart read parameters: "
        write(logUnit(1),*) "  filename : "//trim(me%controller%readFileName)

        if (globProc%rank == 0) then
          inquire(file = trim(me%controller%readFileName), exist = readexists)
        end if
        call MPI_Bcast(readexists, 1, MPI_LOGICAL, 0, globProc%comm, iError)

        ! Set the restart flag if the restart file exists
        me%controller%readRestart = readexists

        if (readexists) then
          call tem_restart_readHeader( me          = me,       &
            &                          timing      = timing,   &
            &                          globProc    = globProc, &
            &                          tree        = tree      )

          if ( tree%global%nElems /= me%header%nElems ) then
            write(logUnit(0),*) 'Number of elements in restart header different ' &
              &                 // 'from mesh'
            write(logUnit(0),*) 'Stopping...'
            call tem_abort()
          end if

          call tem_time_set_clock(me = timing)
          me%lastWritten = timing

        else
          write(logUnit(1),*) ''
          write(logUnit(1),*) '!File to restart from does NOT exist!'
          write(logUnit(1),*) ''
          if (me%controller%init_on_missing) then
            write(logUnit(1),*) 'NOTE: performing initialization without'
            write(logUnit(1),*) '      reading data from restart as requested'
            write(logUnit(1),*) '      via the init_on_missing flag.'
            write(logUnit(1),*) ''
          else
            write(logUnit(1),*) '  Do not know how proceed, aborting now...'
            write(logUnit(1),*) '  If you want to perform the initialization'
            write(logUnit(1),*) '  when the restart file is missing, set'
            write(logUnit(1),*) '  the init_on_missing option in the restart'
            write(logUnit(1),*) '  table to true.'
            call tem_abort()
          end if
        end if
        write(logUnit(1),*) "*****************************"
        write(logUnit(1),*) ''
      end if ! If reading restart

      ! Now we get all the information about writing restart data.
      call aot_get_val( L       = conf,                      &
        &               thandle = restart_table,             &
        &               key     = 'write',                   &
        &               val     = me%controller%writePrefix, &
        &               ErrCode = iError                     )
      me%controller%writeRestart = (iError == 0)

      if (me%controller%writeRestart) then
        ! Read the time intervals for restart output from the Lua config.
        call tem_timeControl_load( me     = me%controller%timeControl, &
          &                        conf   = conf,                      &
          &                        parent = restart_table              )
        if (me%controller%readRestart) then
          call tem_timeControl_align_trigger(        &
            &    me     = me%controller%timeControl, &
            &    conf   = conf,                      &
            &    now    = timing,                    &
            &    parent = restart_table              )
        end if
        write(logUnit(1),*) "*****************************"
        write(logUnit(1),*) "Restart write parameters: "
        write(logUnit(1),*) "  prefix   : "//trim(me%controller%writePrefix)
        call tem_timeControl_dump(me%controller%timeControl, logUnit(2))
        write(logUnit(1),*) "*****************************"
        write(logUnit(1),*) ''
      end if

      call tem_horizontalSpacer(fUnit = logUnit(1))
    end if ! If restart table present

    call aot_table_close( L=conf, thandle=restart_table )

  end subroutine tem_load_restart