tem_timer_dumplabeled Subroutine

public subroutine tem_timer_dumplabeled(me, comm, myrank, nProcs)

Arguments

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

timer object

integer, intent(in) :: comm

communicator handle

integer, intent(in) :: myrank

MPI rank of the calling process.

integer, intent(in) :: nProcs

Number of processes in the communicator.


Calls

proc~~tem_timer_dumplabeled~~CallsGraph proc~tem_timer_dumplabeled tem_timer_dumplabeled interface~positionofval~5 positionofval proc~tem_timer_dumplabeled->interface~positionofval~5 mpi_gather mpi_gather proc~tem_timer_dumplabeled->mpi_gather proc~tem_getmaxtimerval tem_getMaxTimerVal proc~tem_timer_dumplabeled->proc~tem_getmaxtimerval proc~tem_getmintimerval tem_getMinTimerVal proc~tem_timer_dumplabeled->proc~tem_getmintimerval proc~tem_getsumtimerval tem_getSumTimerVal proc~tem_timer_dumplabeled->proc~tem_getsumtimerval proc~tem_open tem_open proc~tem_timer_dumplabeled->proc~tem_open proc~upper_to_lower upper_to_lower proc~tem_timer_dumplabeled->proc~upper_to_lower proc~posofval_label posofval_label interface~positionofval~5->proc~posofval_label mpi_allreduce mpi_allreduce proc~tem_getmaxtimerval->mpi_allreduce proc~tem_gettimerval tem_getTimerVal proc~tem_getmaxtimerval->proc~tem_gettimerval proc~tem_getmintimerval->mpi_allreduce proc~tem_getmintimerval->proc~tem_gettimerval proc~tem_getsumtimerval->mpi_allreduce proc~tem_getsumtimerval->proc~tem_gettimerval proc~tem_open->proc~upper_to_lower proc~newunit newunit proc~tem_open->proc~newunit proc~tem_abort tem_abort proc~tem_open->proc~tem_abort interface~sortedposofval~5 sortedposofval proc~posofval_label->interface~sortedposofval~5 mpi_abort mpi_abort proc~tem_abort->mpi_abort proc~tem_stoptimer tem_stopTimer proc~tem_gettimerval->proc~tem_stoptimer proc~sortposofval_label sortposofval_label interface~sortedposofval~5->proc~sortposofval_label mpi_wtime mpi_wtime proc~tem_stoptimer->mpi_wtime

Called by

proc~~tem_timer_dumplabeled~~CalledByGraph proc~tem_timer_dumplabeled tem_timer_dumplabeled proc~tem_timer_dump_glob tem_timer_dump_glob proc~tem_timer_dump_glob->proc~tem_timer_dumplabeled proc~tem_finalize tem_finalize proc~tem_finalize->proc~tem_timer_dump_glob

Source Code

  subroutine tem_timer_dumplabeled(me, comm, myrank, nProcs)
    ! -------------------------------------------------------------------- !
    !> timer object
    type(tem_labeledtimer_type), intent(inout) :: me
    !> communicator handle
    integer, intent(in) :: comm
    !> MPI rank of the calling process.
    integer, intent(in) :: myrank
    !> Number of processes in the communicator.
    integer, intent(in) :: nProcs
    ! -------------------------------------------------------------------- !
    character(len=labelLen) :: timerlabel
    character(len=pathLen) :: detail_file
    integer :: iProc
    integer :: funit
    integer :: dunit
    integer :: timerpos
    integer :: itimer
    integer :: verbosity
    integer :: iError
    logical :: unmatched(me%config%label%nVals)
    real(kind=rk) :: mintime, maxtime, sumtime
    real(kind=rk), allocatable :: proctimer(:)
    ! -------------------------------------------------------------------- !

    unmatched = .true.

    if (me%config%filename /= '') then

      if (myrank == 0) then
        call tem_open( file    = trim(me%config%filename), &
          &            newunit = funit,                    &
          &            action  = 'write',                  &
          &            status  = 'replace',                &
          &            form    = 'formatted'               )
        write(funit,*) 'Timings for a run on ', nProcs, 'processes'
        write(funit,'(a24,3(1x,a16))') 'timer', 'min', 'max', 'sum'
        allocate(proctimer(nProcs))
      else
        allocate(proctimer(0))
      end if
      do itimer=1,me%label%nVals
        verbosity = tem_timer_summary
        timerlabel = upper_to_lower(me%label%val(itimer))
        timerpos = PositionOfVal( me  = me%config%label, &
          &                       val = trim(timerlabel) )
        if (timerpos > 0) then
          verbosity = me%config%verbosity%val(timerpos)
          unmatched(timerpos) = .false.
        end if

        select case(verbosity)
        case (tem_timer_summary)
          mintime = tem_getMinTimerVal(me%timedat, itimer, comm)
          maxtime = tem_getMaxTimerVal(me%timedat, itimer, comm)
          sumtime = tem_getSumTimerVal(me%timedat, itimer, comm)
          if (myrank == 0) then
            write(funit,'(a24,3(1x,en16.6))') trim(me%label%val(itimer)), &
              &                               mintime, maxtime, sumtime
          end if

        case (tem_timer_details)
          call MPI_Gather( me%timedat%duration%val(iTimer), 1, rk_mpi, &
            &              proctimer, 1, rk_mpi, 0, comm, iError       )
          if (myrank == 0) then
            detail_file = trim(me%config%filename) // '_' &
              &           // trim(me%label%val(itimer)) // '.details'
            write(funit,'(a1,a22,a1,1x,a)') 'D', trim(me%label%val(itimer)), &
              &                             ':', trim(detail_file)
            call tem_open( file    = trim(detail_file), &
              &            newunit = dunit,             &
              &            action  = 'write',           &
              &            status  = 'replace',         &
              &            form    = 'formatted'        )
            write(dunit, '(a)') 'Detailed timings for ' &
              &                 // trim(me%label%val(itimer))
            write(dunit, '(a8,1x,en16.6)') 'min:', minval(proctimer)
            write(dunit, '(a8,1x,en16.6)') 'max:', maxval(proctimer)
            write(dunit, '(a8,1x,en16.6)') 'sum:', sum(proctimer)
            write(dunit, *) ''
            do iProc=1,nProcs
              write(dunit, '(i7,a1,en16.6)') iProc, ':', proctimer(iProc)
            end do
            close(dunit)
          end if

        end select

      end do

      deallocate(proctimer)

      ! Write any user-defined, but unknown timers...
      if (myrank == 0) then
        do itimer=1,me%config%label%nVals
          if ( unmatched(iTimer)                       &
            &  .and. ( me%config%verbosity%val(iTimer) &
            &          /= tem_timer_ignored )          ) then
            write(funit,'(a1,a23,1x,a)') 'U',                               &
              &                          trim(me%config%label%val(itimer)), &
              &                          '    .:!UNKNOWN!:.'
          end if
        end do

        close(funit)
      end if

    end if

  end subroutine tem_timer_dumplabeled