Silverfrost Forums

Welcome to our forums

HIGH_RES_CLOCK@

9 Sep 2011 11:50 #8932

We are using the HIGH_RES_CLOCK@ function to synchronize our process with the cpu real time clock.

This works really good on most machines. But on some machines our process becomes asynchronous behaviour.

Has anyone experiences with this function and / or an explanation for this behaviour?

The windows OS is the same on these machines. Maybe it is depending on the hardware.

Detlef Pannhorst

10 Sep 2011 2:25 #8950

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.

11 Sep 2011 7:44 #8952

Thanks for your proposals. I will check them.

Detlef

12 Sep 2011 1:14 #8953

When calling a timing routine, there are a number of factors to consider, including:

  1. how long the call takes
  2. if it reports processor time or elapsed time
  3. how often the timing routine 'ticks', ie accuracy.

The following are summary statistics from a number of timing alternatives available with Salford and WinAPI. The concept of a tick is important and a number of routines are accurate to .0156 seconds or about 64 ticks per second. Some of the results for intrinsics differ with other compilers. ! Results of timing call tests using c:\gen\audit\timing.f95 ! ! ELAPSED TIME CALLS ! fastest gettickcount winapi ! accurate QueryPerform winapi !
! CPU TIME CALLS ! fastest cpu_clock@ salford ! accurate cpu_clock@ salford !
! P4 2553 mhz using ftn95 ver 4.50 ! Run on Tuesday, 24 August 2004 at 09:50:06 ! cpu_clock : MHz = 2.535E+09 ( 1118676 cycles) ! Run on Tuesday, 24 August 2004 at 09:50:35 !
! # indicates routine time: only call time is uniformly timed !
! Call Description Total time call time unique min dif max dif accuracy ! # seconds mu.sec number # mu.sec # mu.sec # mu.sec ! Intrinsics Routines ! call system_clock 28.371 3.176 6332 100.00 600.00 100.38 f95 a real-time clock ! call cpu_time 28.297 0.909 11 15625.00 15625.00 15625.00 f95 To get the processor time. ! date_and_time 28.360 1.738 22 15000.00 16000.00 15636.36 f95 real-time date and clock time ! ! Salford routines ! call dclock@ 28.360 0.482 6 15000.00 16000.00 15666.67 sal elapsed time ! seconds_since_1980@ 29.000 0.476 1 1000000.00 1000000.00 1000000.00 sal ! cpu_clock@ () 28.355 0.096 199999 0.09 203.05 0.10 sal not reliable on NT + ?? ! high_res_clock@ 28.371 2.948 199999 2.79 383.01 2.95 sal CPU time accurate to 1 microsecond ! ! WINAPI Routines ! call gettickcount 28.360 0.142 2 16000.00 16000.00 16000.00 api GetTickCount WINAPI ! call getlocaltime 28.360 0.527 7 15000.00 16000.00 15714.29 api GetLocalTime WINAPI ! call QueryPerform 28.371 1.593 199999 1.40 411.23 1.59 api is the fastest and most accurate ! GetProcessTimes 28.297 0.762 10 15625.00 15625.00 15625.00 api GetProcessTimes WINAPI !
! Total time the time obtained from this routine for the full test run using timing.f95 ! call time the estimate for the time of each call ( using cpu_clock@ ) ! number unique the number of calls that returned a different time out of 100,000 calls ! min dif the smallest difference in the time estimate from sucessive call, ignoring same ! max dif the maximum difference in the call value ! accuracy the average of the different calls

From memory, these results are taken from 200,000 successive calls to each routine, identifying the number of different results and the average time taken. For CPU, 'GetProcessTimes' should be the best, but suffers from a poor system tick update. I'm not sure what WINAPI interface CPU_CLOCK@ uses. For elapsed time, QUERYPERFORMANCECOUNTER and QUERYPERFORMANCEFREQUENCY appear to be the best system interface returning integer*8 counts.

system_clock was based on high_res_clock@ and both of these can fail if the clock rate of the processor is > 2ghz. This bug may have been removed.

cpu_clock@ is by far the best, but it needs to be calibrated. Typically it cycles at the processor clock rate.

John

Paul, what winapi call does cpu_clock@ use ?

Please login to reply.