F.1.13 Timer Class Unit Test Program

This lightly commented program performs a unit test on the Timer Class.

module Unit_Test_Module
  use Caesar_Intrinsics_Module
  use Caesar_Timer_Class
  use Caesar_Communication_Class
  implicit none

contains

  subroutine Red (R)
    type(real) :: R
    type(integer) :: i
    do i = 1, 100
      R = 2+R**.781828
    end do
    return
  end subroutine Red

  subroutine Julian_Day_Output (year, month, day)
    type(integer), intent(in) :: day, month, year
    type(integer) :: julian, gregorian

    julian = Julian_Day(year,month,day,'Julian')
    gregorian = Julian_Day(year,month,day,'Gregorian')

    if (this_is_IO_PE) then
      write (6,100) 'Date: ', year, month, day, &
                    '  Julian Day:', julian, gregorian
100   format (a, i6, '/', i2, '/', i2, a, i10, i10)
    end if
    return
  end subroutine Julian_Day_Output

  subroutine Check_Interval (Hostname, Value, Min, Max)
    type(character,*) :: Hostname
    type(real) :: Value, Min, Max

    if (Value .NotInInterval. (/ Min, Max /) ) then
      if (this_is_IO_PE) then
        write (6,*) 'Hostname: ', Hostname
        write (6,*) '  **Timer not in interval**'
        write (6,*) '  Value    =  ', Value
        write (6,*) '  Interval = (', Min, ',', Max, ')'
      end if
    end if

    return
  end subroutine Check_Interval

end module Unit_Test_Module

program Unit_Test

  use Unit_Test_Module
  use Caesar_Intrinsics_Module
  use Caesar_Data_Structures_Module
  use Caesar_Timer_Class
  use Caesar_Numbers_Module, only: zero, one 
  implicit none

  type(real) :: R, Timer_CPU_Mean, Timer_Wall_Clock_Max
  type(real) :: JD_avg, JD_min, JD_max, CPU_speed
  type(integer) :: day, i, Julian_Day_Number, month, month_end, year, &
                   year_end, year_start
  type(integer), dimension(12) :: days_in_month
  type(logical) :: Debug, Show_Timer_Output
  type(Timer_type) :: Blue_Loop_Timer, Julian_Day_Timer, Red_Subroutine_Timer
  type(Communication_type) :: Comm
  !--------
  ! Uncomment here and two places below to compare
  ! Wall Clock time with MPI_Wtime (parallel only).
  !type(real) :: Time_MPI, MPI_WTime
  !--------

  ! Initialize communications.

  call Initialize (Comm)
  call Output (Comm)
  if (this_is_IO_PE) write (6,*)

  ! Timer output toggle. Turn off for unit tests.

  Show_Timer_Output = .false.

  ! Initialize Timers.

  call Initialize (Blue_Loop_Timer, "Blue Loop")
  call Initialize (Red_Subroutine_Timer, "Red Subroutine")
  call Initialize (Julian_Day_Timer, "Julian Day")

  ! Time some loops and subroutines.

  call Start (Blue_Loop_Timer)
  !--------
  ! Uncomment here; in declarations; and below to compare
  ! Wall Clock time with MPI_Wtime (parallel only).
  !Time_MPI = MPI_WTime()
  !--------
  R = 0
  do i = 1, 10000/NPEs
    call Start (Red_Subroutine_Timer)
    call Red (R)
    call Stop (Red_Subroutine_Timer)
  end do
  call Stop (Blue_Loop_Timer)
  if (Show_Timer_Output) then
    call Output (Blue_Loop_Timer, Verbose=.true., Global=.false.)
    if (this_is_IO_PE) write (6,*) ' '
    call Output (Blue_Loop_Timer, Verbose=.true., Global=.true.)
    !--------
    ! Uncomment here; in declarations; and above to compare
    ! Wall Clock time with MPI_Wtime (parallel only).
    !if (this_is_IO_PE) write (6,*) 'MPI_WTime = ', MPI_WTime() - Time_MPI
    !--------
    if (this_is_IO_PE) write (6,*) ' '
    call Output (Red_Subroutine_Timer, Verbose=.true., Global=.false.)
    if (this_is_IO_PE) write (6,*) ' '
    call Output (Red_Subroutine_Timer, Verbose=.true., Global=.true.)
  end if

  ! Tests on the Julian_Day procedure.

  ! Output some representative dates. These have all been checked.

  call Start (Julian_Day_Timer)
  if (this_is_IO_PE) then 
    write (6,*)
    write (6,100) 'Significant dates                 Julian    Gregorian'
    write (6,100) '                                  Calendar  Calendar'
  end if
  call Julian_Day_Output (-4713,  1,  1)
  call Julian_Day_Output ( -753,  4, 21)
  call Julian_Day_Output (   -2, 10, 30)
  call Julian_Day_Output (   -1,  1,  1)
  call Julian_Day_Output (    1,  1,  1)
  call Julian_Day_Output (  200,  2, 28)
  call Julian_Day_Output (  200,  2, 29)
  call Julian_Day_Output (  200,  3,  1)
  call Julian_Day_Output (  300,  2, 28)
  call Julian_Day_Output (  300,  2, 29)
  call Julian_Day_Output (  300,  3,  1)
  call Julian_Day_Output ( 1582, 10,  4)
  call Julian_Day_Output ( 1582, 10, 14)
  call Julian_Day_Output ( 1752,  9,  2)
  call Julian_Day_Output ( 1752,  9, 13)
  call Julian_Day_Output ( 1858, 11, 16)
  call Julian_Day_Output ( 1968,  5, 23)
  call Julian_Day_Output ( 1995, 10,  9)
  call Julian_Day_Output ( 2000,  1,  1)
  call Julian_Day_Output ( 2132,  8, 31)
  if (this_is_IO_PE) write (6,*) ' '

  ! Turn off verifications inside the Julian_Day procedure for parallel 
  ! versions of the thousands of calls in the next few tests.

  if (parallel) Debug = .false.

  ! Julian = Gregorian Test:
  ! 
  ! Julian Day numbers for Julian calendar and Gregorian calendar dates will
  ! generally be different. They are only the same for dates from March 1st,
  ! 200, to February 28, 300. Here we check to make sure they are the same
  ! for those dates.

  days_in_month = (/ 31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31 /)

  if (this_is_IO_PE) write (6,100) 'Julian = Gregorian test starting...'
  do year = 200, 300
    do month = 1, 12
      if ((year /= 200 .or. month >= 3) .and. &
          (year /= 300 .or. month <= 2)) then 
        month_end = days_in_month(month)
        if (MOD(year,4) == 0 .and. month == 2) then
          month_end = month_end + 1
        end if
        do day = 1, month_end
          if (Julian_Day(year, month, day, 'Gregorian', Debug) /= &
              Julian_Day(year, month, day, 'Julian', Debug) .and. &
              this_is_IO_PE) then
            write (6,*) '*******************************************'
            write (6,*) 'Error -- Julian Day number not the same for'
            write (6,*) 'Gregorian and Julian calendars on: '
            write (6,*) ' '
            write (6,*) '  Date = ', year, month, day
            write (6,*) ' '
            write (6,*) 'and it should be.'
            write (6,*) '*******************************************'
          end if
        end do
      end if
    end do
  end do
  if (this_is_IO_PE) then
    write (6,100) 'Julian = Gregorian test finished.'
    write (6,*)
  end if
  call Stop (Julian_Day_Timer)

  ! Julian Calendar Sequential Test.
  !
  ! Check to see if all Julian Days are sequential for the Julian calendar.

  call Start (Julian_Day_Timer)
  if (this_is_IO_PE) &
    write (6,100) 'Julian Calendar Sequential test starting...'
  year_start = -4713
  year_end = 2100
  Julian_Day_Number = Julian_Day(year_start, 1, 1, 'Julian')
  do year = year_start, year_end
    if (year /= 0) then
      do month = 1, 12
        month_end = days_in_month(month)
        if (year > 0) then
          if (MOD(year,4) == 0 .and. month == 2) then
            month_end = month_end + 1
          end if
        else
          if (MOD(year,4) == -1 .and. month == 2) then
            month_end = month_end + 1
          end if
        end if
        do day = 1, month_end
          if (Julian_Day(year, month, day, 'Julian', Debug) /= &
              Julian_Day_Number .and. this_is_IO_PE) then
            write (6,*) '**********************************************'
            write (6,*) 'Error -- Julian Day number not sequential for:'
            write (6,*) ' '
            write (6,*) '  Date = ', year, month, day
            write (6,*) ' '
            write (6,*) 'and it should be.'
            write (6,*) '**********************************************'
          end if
          Julian_Day_Number = Julian_Day_Number + 1
        end do
      end do
    end if
  end do
  if (this_is_IO_PE) then
    write (6,100) 'Julian Calendar Sequential test finished.'
    write (6,*)
  end if
  call Stop (Julian_Day_Timer)

  ! Gregorian Calendar Sequential Test.
  !
  ! Check to see if all Julian Days are sequential for the Gregorian calendar.

  call Start (Julian_Day_Timer)
  if (this_is_IO_PE) &
    write (6,100) 'Gregorian Calendar Sequential test starting...'
  year_start = -4713
  year_end = 2100
  Julian_Day_Number = Julian_Day(year_start, 1, 1, 'Gregorian')
  do year = year_start, year_end
    if (year /= 0) then
      do month = 1, 12
        month_end = days_in_month(month)
        if (year > 0) then
          if (MOD(year,4) == 0 .and. month == 2) then
            month_end = month_end + 1
          end if
          if (MOD(year,100) == 0 .and. MOD(year,400) /= 0 .and. &
              month == 2) then
            month_end = month_end - 1
          end if
        else
          if (MOD(year,4) == -1 .and. month == 2) then
            month_end = month_end + 1
          end if
          if (MOD(year,100) == -1 .and. MOD(year,400) /= -1 .and. &
              month == 2) then
            month_end = month_end - 1
          end if
        end if
        do day = 1, month_end
          if (Julian_Day(year, month, day, 'Gregorian', Debug) /= &
              Julian_Day_Number .and. this_is_IO_PE) then
            write (6,*) '**********************************************'
            write (6,*) 'Error -- Julian Day number not sequential for:'
            write (6,*) ' '
            write (6,*) '  Date = ', year, month, day
            write (6,*) ' '
            write (6,*) 'and it should be.'
            write (6,*) '**********************************************'
          end if
          Julian_Day_Number = Julian_Day_Number + 1
        end do
      end do
    end if
  end do
  if (this_is_IO_PE) then
    write (6,100) 'Gregorian Calendar Sequential test finished.'
    write (6,*)
  end if
  call Stop (Julian_Day_Timer)
  if (Show_Timer_Output) then
    call Output (Julian_Day_Timer, Verbose=.true., Global=.false.)
    if (this_is_IO_PE) write (6,*)
    call Output (Julian_Day_Timer, Verbose=.true., Global=.true.)
  end if

  ! Check timings for various systems.

  Timer_CPU_Mean = &
    Mean(Julian_Day_Timer, 'CPU', Global=.true., Split=.false.)
  Timer_Wall_Clock_Max = &
    Maximum(Julian_Day_Timer, 'Wall_Clock', Global=.true., Split=.false.)

  ! Turn this on for new systems to see the timings.

  if (.false.) then
    if (this_is_IO_PE) then
      write (6,*) ' Timer_CPU_Mean       = ', Timer_CPU_Mean
      write (6,*) ' Timer_Wall_Clock_Max = ', Timer_Wall_Clock_Max
    end if
  end if

  ! Galt: Xeon_Intel_Linux-2.4.2_Absoft-8.2
  !       Xeon_Intel_Linux-2.4.2_Lahey-L6.00c
  ! NPES: 2
  ! uname -a: Linux galt 2.4.2-2smp #1 SMP \
  !           Sun Apr 8 20:21:34 EDT 2001 i686 unknown
  ! f90 -V f.f90: Copyright Absoft Corporation 1994-2003; \
  !               Absoft Pro FORTRAN Version 8.2
  ! lf95 --version: Lahey/Fujitsu Fortran 95 Express Release L6.00c
  !
  !                    Lahey                 Absoft
  ! Run times:      CPU    Wall Clock    CPU    Wall Clock
  !   serial        1.32    1.32         1.47    1.47
  !   1-parallel    1.32    1.32         1.45    1.45
  !   2-parallel    1.22    1.24          .75    1.46
  !   4-parallel    1.25    2.54          .40    1.56
  !   8-parallel    1.27    5.1           .24    1.78
  !  16-parallel    1.30   10.6           .16    2.53
  !  32-parallel    1.36   22.4           .13    4.52
  !
  ! Comment: After scrutiny, I determined that the Absoft compiler is
  ! optimizing out the work on the PEs that don't need to communicate
  ! back! This is with no optimization on! Full output shows that,
  ! for example, the 32-PE CPU time is 1.46 on the IO_PE and an
  ! average of 0.08 on the other 31 PEs, resulting in an overall average 
  ! of 0.13.
 
  if ('HOSTNAME' == 'galt') then
    if ('COMPILER' == 'Lahey') then
      if (parallel) then
        call Check_Interval ('Galt', Timer_CPU_Mean, 1.20d0, 1.50d0)
        JD_avg = 1.25 + MAX(0, NPEs-2)*0.63
        JD_min = 0.9 * JD_avg
        JD_max = 1.2 * JD_avg
        call Check_Interval ('Galt', Timer_Wall_Clock_Max, JD_min, JD_max)
      else
        call Check_Interval ('Galt', Timer_CPU_Mean, 1.25d0, 1.50d0)
        call Check_Interval ('Galt', Timer_Wall_Clock_Max, 1.25d0, 1.50d0)
      end if
    else if ('COMPILER' == 'Absoft') then
      if (parallel) then
        JD_avg = 1.2298 * NPEs**(-0.70916)
        JD_min = 0.8 * JD_avg
        JD_max = 1.2 * JD_avg
        call Check_Interval ('Galt', Timer_CPU_Mean, JD_min, JD_max)
        JD_avg = 1.3586 * EXP( 0.037611 * NPEs )
        JD_min = 0.9 * JD_avg
        JD_max = 1.3 * JD_avg
        call Check_Interval ('Galt', Timer_Wall_Clock_Max, JD_min, JD_max)
      else
        call Check_Interval ('Galt', Timer_CPU_Mean, 1.30d0, 1.60d0)
        call Check_Interval ('Galt', Timer_Wall_Clock_Max, 1.30d0, 1.60d0)
      end if
    end if

  ! Dagny: PentiumIII_Intel_Linux-2.4.20_Absoft-8.2
  ! uname -a: Linux dagny 2.4.20-emp_2420p6a0328 #1 \
  !           Tue Apr 1 19:52:06 EST 2003 i686 i686 i386 GNU/Linux
  ! f90 -V f.f90: Copyright Absoft Corporation 1994-2003; \
  !               Absoft Pro FORTRAN Version 8.2
  ! 
  ! Run times:     CPU    Wall Clock
  !   serial       2.33    2.33
  !   1-parallel   2.33    2.33
  !   2-parallel   1.20    2.41
  !   4-parallel    .64    2.64
  !   8-parallel    .37    3.40
  !  16-parallel    .25    4.81
  !  32-parallel    .19    9.16
  !
  ! See comments on Absoft compiler under Galt above.

  else if ('HOSTNAME' == 'dagny') then
    if ('COMPILER' == 'Absoft') then
      if (parallel) then
        JD_avg = 2.0016 * NPEs**(-0.73317)
        JD_min = 0.8 * JD_avg
        JD_max = 1.3 * JD_avg
        call Check_Interval ('Dagny', Timer_CPU_Mean, JD_min, JD_max)
        JD_avg = 2.1876 + 0.11487 * NPEs + 0.0032143 * NPEs**2
        JD_min = 0.9 * JD_avg
        JD_max = 1.2 * JD_avg
        call Check_Interval ('Dagny', Timer_Wall_Clock_Max, JD_min, JD_max)
      else
        call Check_Interval ('Dagny', Timer_CPU_Mean, 2.20d0, 2.50d0)
        call Check_Interval ('Dagny', Timer_Wall_Clock_Max, 2.20d0, 2.50d0)
      end if
    end if

  ! Kira: PentiumM_Intel_Linux-2.4.23_Absoft-8.2
  ! uname -a: Linux kira 2.4.23-emp_2423sw #1 \
  !           Mon Dec 8 20:12:14 EST 2003 i686 i686 i386 GNU/Linux
  ! f90 -V f.f90: Copyright Absoft Corporation 1994-2003; \
  !               Absoft Pro FORTRAN Version 8.2
  !
  ! The PentiumM chip in kira varies its processor speed from time to time.
  ! Two times are given below:
  !
  !                   600 MHz                 1600 MHz 
  ! Run times:     CPU    Wall Clock      CPU    Wall Clock
  !   serial       3.19    3.20           1.2       1.2
  !   1-parallel   3.21    3.20           1.2       1.2
  !   2-parallel   1.66    3.51           0.62      1.25
  !   4-parallel    .90    3.82           0.33      1.37
  !   8-parallel    .52    4.62           0.195     1.64
  !  16-parallel    .32    6.24           0.122     2.27
  !  32-parallel    .24   10.22           0.090     3.98
  !
  ! The current CPU_speed variable can be seen via "gmake environment".
  ! The current speed can then be set below to allow correct timing
  ! results.
  !
  ! See comments on Absoft compiler under Galt above.

  else if ('HOSTNAME' == 'kira') then
    CPU_speed = 1600.d0
    if ('COMPILER' == 'Absoft') then
      if (parallel) then
        JD_avg = 1702.14 * NPEs**(-0.76068) / CPU_speed
        JD_min = 0.8 * JD_avg
        JD_max = 1.2 * JD_avg
        call Check_Interval ('Kira', Timer_CPU_Mean, JD_min, JD_max)
        JD_avg = (1767.78 + 133.542 * NPEs) / CPU_speed
        JD_min = 0.9 * JD_avg
        JD_max = 1.3 * JD_avg
        call Check_Interval ('Kira', Timer_Wall_Clock_Max, JD_min, JD_max)
      else
        JD_avg = 1920.0 / CPU_speed
        JD_min = JD_avg - 0.1
        JD_max = JD_avg + 0.1
        call Check_Interval ('Kira', Timer_CPU_Mean, JD_min, JD_max)
        JD_avg = 1950.0 / CPU_speed
        JD_min = JD_avg - 0.1
        JD_max = JD_avg + 0.1
        call Check_Interval ('Kira', Timer_Wall_Clock_Max, JD_min, JD_max)
      end if
    end if

  ! Caesar:   UltraSPARC-IIi_Sun_Solaris-5.6_Native-6.2
  ! uname -a: SunOS caesar 5.6 Generic_105181-03 sun4u sparc SUNW,Ultra-5_10
  ! f90 -V:   Sun WorkShop 6 update 2 Fortran 95 6.2 2001/05/15
  !
  ! Note that CPU Time scales with the number of PEs! This must
  ! mean that Suns return the CPU Time of the parent process. Also,
  ! some runs have given results that lead me to suspect that Suns
  ! return Wall Clock Time from the CPU_TIME call -- not sure about 
  ! this.
  ! 
  ! Run times:     Both CPU and       Both CPU and 
  !                 Wall Clock     Wall Clock (optimized)
  !   serial            7.2              4.7
  !   1-parallel        7.06             4.4
  !   2-parallel       14.35             9.9
  !   4-parallel       29.8             19.1
  !   8-parallel       58.1             41.4
  !  16-parallel      123.8             99.1
  !  32-parallel      281.3            191.0

  else if ('HOSTNAME' == 'caesar') then
    if (parallel) then
      JD_avg = 1.631 + 3.261 * NPEs + 0.2697 * NPEs**2 - 0.005832 * NPEs**3
      ! Non-optimized version:
      !JD_avg = 1.011 + 6.626 * NPEs + 0.06659 * NPEs**2
      JD_min = 0.8 * JD_avg
      JD_max = 1.1 * JD_avg
      call Check_Interval ('Caesar', Timer_CPU_Mean, JD_min, JD_max)
      call Check_Interval ('Caesar', Timer_Wall_Clock_Max, JD_min, JD_max)
    else
      JD_min = 4.4d0  
      JD_max = 5.0d0
      ! Non-optimized version:
      ! JD_min = 6.9d0  
      ! JD_max = 7.5d0
      call Check_Interval ('Caesar', Timer_CPU_Mean, JD_min, JD_max)
      call Check_Interval ('Caesar', Timer_Wall_Clock_Max, JD_min, JD_max)
    end if
  end if

  ! Check state of Timer.

  VERIFY(Valid_State(Blue_Loop_Timer),0)
  VERIFY(Valid_State(Red_Subroutine_Timer),0)
  VERIFY(Valid_State(Julian_Day_Timer),0)

  ! Finalize Timers.

  call Finalize (Blue_Loop_Timer)
  call Finalize (Red_Subroutine_Timer)
  call Finalize (Julian_Day_Timer)

  ! Finalize communications.

  call Finalize (Comm)

  ! Format statements.

100 format (a)

end



Michael L. Hall