tem_simControl_syncUpdate Subroutine

public subroutine tem_simControl_syncUpdate(me, proc, dt, d_iter, outUnit)

Synchronize the status bits across all processes and update the time.

Arguments

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

Simulation control information.

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

Communicator to use for the communication of status flags.

real(kind=rk), intent(in), optional :: dt

Time step to use for updating the simulation time.

If this is not given, no advance of the time will be done.

integer, intent(in), optional :: d_iter

Number of iterations to add to the current number of iterations. (Default: 1)

integer, intent(in), optional :: outUnit

Unit to write messages to.

If this argument is present, the current time will be printed whenever the interval of the simControl is triggered.


Calls

proc~~tem_simcontrol_syncupdate~~CallsGraph proc~tem_simcontrol_syncupdate tem_simControl_syncUpdate proc~tem_starttimer tem_startTimer proc~tem_simcontrol_syncupdate->proc~tem_starttimer proc~tem_stop_file_exists tem_stop_file_exists proc~tem_simcontrol_syncupdate->proc~tem_stop_file_exists proc~tem_timecontrol_update tem_timeControl_update proc~tem_simcontrol_syncupdate->proc~tem_timecontrol_update proc~tem_timecontrol_reached_max tem_timeControl_reached_max proc~tem_simcontrol_syncupdate->proc~tem_timecontrol_reached_max proc~tem_timecontrol_triggered tem_timeControl_triggered proc~tem_simcontrol_syncupdate->proc~tem_timecontrol_triggered proc~tem_time_advance tem_time_advance proc~tem_simcontrol_syncupdate->proc~tem_time_advance proc~tem_status_communicate_delayed tem_status_communicate_delayed proc~tem_simcontrol_syncupdate->proc~tem_status_communicate_delayed proc~tem_status_communicate tem_status_communicate proc~tem_simcontrol_syncupdate->proc~tem_status_communicate proc~tem_time_set_clock tem_time_set_clock proc~tem_simcontrol_syncupdate->proc~tem_time_set_clock proc~tem_time_dump tem_time_dump proc~tem_simcontrol_syncupdate->proc~tem_time_dump proc~tem_stoptimer tem_stopTimer proc~tem_simcontrol_syncupdate->proc~tem_stoptimer mpi_wtime mpi_wtime proc~tem_starttimer->mpi_wtime proc~newunit newunit proc~tem_stop_file_exists->proc~newunit proc~tem_timecontrol_update->proc~tem_timecontrol_triggered proc~tem_time_ge_each tem_time_ge_each proc~tem_timecontrol_reached_max->proc~tem_time_ge_each proc~tem_time_gt_trigger tem_time_gt_trigger proc~tem_timecontrol_triggered->proc~tem_time_gt_trigger proc~tem_time_never tem_time_never proc~tem_timecontrol_triggered->proc~tem_time_never proc~tem_time_ge_trigger tem_time_ge_trigger proc~tem_timecontrol_triggered->proc~tem_time_ge_trigger proc~tem_time_advance->mpi_wtime mpi_wait mpi_wait proc~tem_status_communicate_delayed->mpi_wait mpi_iallreduce mpi_iallreduce proc~tem_status_communicate_delayed->mpi_iallreduce mpi_allreduce mpi_allreduce proc~tem_status_communicate->mpi_allreduce proc~tem_time_set_clock->mpi_wtime proc~tem_stoptimer->mpi_wtime

Contents


Source Code

  subroutine tem_simControl_syncUpdate(me, proc, dt, d_iter, outUnit)
    ! -------------------------------------------------------------------- !
    !> Simulation control information.
    type(tem_simControl_type), intent(inout) :: me

    !> Unit to write messages to.
    !!
    !! If this argument is present, the current time will be printed whenever
    !! the interval of the simControl is triggered.
    integer, intent(in), optional :: outUnit

    !> Communicator to use for the communication of status flags.
    type(tem_comm_env_type), intent(in) :: proc

    !> Time step to use for updating the simulation time.
    !!
    !! If this is not given, no advance of the time will be done.
    real(kind=rk), intent(in), optional :: dt

    !> Number of iterations to add to the current number of iterations.
    !! (Default: 1)
    integer, intent(in), optional :: d_iter
    ! -------------------------------------------------------------------- !
    logical :: max_reached(tem_time_n_ids)
    logical :: stat_interval
    logical :: out_interval
    ! -------------------------------------------------------------------- !

    call tem_startTimer(timerHandle = me%syncUpdate_timer)

    if (present(dt)) then
      call tem_time_advance( me     = me%now, &
        &                    sim_dt = dt,     &
        &                    iter   = d_iter  )
    end if

    max_reached = tem_timeControl_reached_max(me%timeControl, me%now)

    me%status%bits(tem_stat_max_sim)   = max_reached(tem_time_sim_id)
    me%status%bits(tem_stat_max_iter)  = max_reached(tem_time_iter_id)
    if (mod(me%now%iter, me%timeControl%check_iter) == 0) then
      me%status%bits(tem_stat_max_clock) = max_reached(tem_time_clock_id)

      me%status%bits(tem_stat_interval) = tem_timeControl_triggered( &
        &                                   me  = me%timeControl,    &
        &                                   now = me%now             )

      me%status%bits(tem_stat_stop_file) &
        &  = tem_stop_file_exists( abortCriteria = me%abortCriteria, &
        &                          rank          = proc%rank         )

      stat_interval = me%status%bits(tem_stat_interval)

      if (me%delay_check) then
        call tem_status_communicate_delayed(me = me%status, comm = proc%comm)
        me%status%bits(tem_stat_max_sim)  = max_reached(tem_time_sim_id)
        me%status%bits(tem_stat_max_iter) = max_reached(tem_time_iter_id)
        out_interval = stat_interval
      else
        call tem_status_communicate(me = me%status, comm = proc%comm)
        out_interval = me%status%bits(tem_stat_interval)
      end if

      if (present(outUnit) .and. out_interval) then
        call tem_time_set_clock(me%now)
        call tem_time_dump(me%now, outUnit)
      end if

      call tem_timeControl_update( me             = me%timeControl, &
        &                          now            = me%now,         &
        &                          hasTriggered   = out_interval,   &
        &                          localTriggered = stat_interval   )

    end if

    call tem_stopTimer(timerHandle = me%syncUpdate_timer)

  end subroutine tem_simControl_syncUpdate