Three of the best process timing routines available are listed below.
I think that HIGH_RES_CLOCK@ is based on cpu_clock@. The documentation for HIGH_RES_CLOCK@ indicates it can have problems in some cases, especially when timing to very short tick intervals.
SUBROUTINE use_GetProcessTimes (time)
!
! 'All times are expressed using FILETIME data structures. Such a structure
! contains two 32-bit values that combine to form a 64-bit count of
! 100-nanosecond time units.'
!
real*8, dimension (4), intent (out) :: time
!
STDCALL GETPROCESSTIMES 'GetProcessTimes' (VAL,REF,REF,REF,REF):LOGICAL*4
STDCALL GETCURRENTPROCESS 'GetCurrentProcess':INTEGER*4
!
integer*8 :: CreationTime, ExitTime, KernelTime, UserTime
integer*8, save :: CreationInit, ExitInit, KernelInit, UserInit
integer*4 :: CurrentProcess = 0
integer*4 :: lute
logical*4 :: first = .true.
!
if (first) then
CurrentProcess = GetCurrentProcess()
call GetProcessTimes (CurrentProcess, CreationInit, ExitInit, KernelInit, UserInit)
call get_echo_unit (lute)
write (lute,9001) 'CurrentProcess ', CurrentProcess
write (lute,9001) 'CreationTime ', CreationInit
write (lute,9001) 'ExitTime ', ExitInit
write (lute,9001) 'KernelTime # ', KernelInit
write (lute,9001) 'UserTime # ', UserInit
first = .false.
end if
!
call GetProcessTimes (CurrentProcess, CreationTime, ExitTime, KernelTime, UserTime)
!
time(1) = dble (CreationTime-CreationInit) * 1.0d-07
time(2) = dble (ExitTime -ExitInit ) * 1.0d-07
time(3) = dble (KernelTime -KernelInit ) * 1.0d-07
time(4) = dble (UserTime -UserInit ) * 1.0d-07
!
return
9001 format (a,i0)
end
subroutine use_cpu_clock (time)
!
! subroutine to use cpu_clock@ by first estimating the cpu mhz
! dclock@ is used to calibrate the processor
!
real*10, intent (out) :: time
!
real*10 cpu_clock@
intrinsic cpu_clock@
!
time = cpu_clock@ ()
return
end
SUBROUTINE use_QueryPerform (elapse)
!
! Returns the total elapsed time in seconds
! based on QueryPerformanceCounter
! This is the fastest and most accurate timing routine
!
real*8, intent (out) :: elapse
!
STDCALL QUERYPERFORMANCECOUNTER 'QueryPerformanceCounter' (REF):LOGICAL*4
STDCALL QUERYPERFORMANCEFREQUENCY 'QueryPerformanceFrequency' (REF):LOGICAL*4
!
real*8 :: freq = 1
logical*4 :: first = .true.
integer*8 :: start = 0
integer*8 :: num
logical*4 :: ll
!
! Calibrate this time using QueryPerformanceFrequency
if (first) then
num = 0
ll = QueryPerformanceFrequency (num)
freq = 1.0d0 / dble (num)
start = 0
ll = QueryPerformanceCounter (start)
first = .false.
end if
!
num = 0
ll = QueryPerformanceCounter (num)
elapse = dble (num-start) * freq
return
end
High clock rate processors above 2ghz can cause problems.