The following code can identify the difference between the precision suggested by “clock_rate” and the actual precision available. This varies greatly with Kind and operating system. Windows and Kind=4 is the worst !
! test the clock rate and precision for various compilets
!
integer, parameter :: ip = selected_int_kind ( 10 ) ! try 6 10 or possibly 18
integer(ip) :: clock_tick, last_tick, clock_rate
integer*8 :: elapse_ticks(0:10), num_ticks(0:10), calls, ticks
integer :: k, i
real*8 :: sec
call system_clock ( last_tick, clock_rate )
elapse_ticks(0) = last_tick
do k = 0,10
do i = 1,9999999
call system_clock ( clock_tick )
if ( clock_tick == last_tick ) cycle
elapse_ticks(k) = clock_tick
num_ticks(k) = i
last_tick = clock_tick
exit
end do
end do
sec = dble ( elapse_ticks(10)-elapse_ticks(0) ) / dble(clock_rate) / sum(num_ticks)
write (*,*) 'Integer KIND =',ip
write (*,*) 'clock_rate =',clock_rate,' ticks/sec reporting precision'
write (*,*) 'system_clock call time =',sec,' seconds / call'
write (*,fmt='(/a)') ' Step Calls Change Seconds'
do k = 1,10
calls = num_ticks(k)
ticks = elapse_ticks(k)-elapse_ticks(k-1)
sec = dble ( ticks ) / dble(clock_rate)
write (*,fmt='(i5,i10,i10, es12.3 )') k, calls, ticks, sec
end do
write (*,fmt='(/a)') 'NOTE :'
write (*,*) ' Calls is the number of repeated calls before "clock_tick" changes value'
write (*,*) ' Change is the minimum change to clock_tick that can be reported'
write (*,*) ' Seconds is the true accuracy available'
end
Typically when 4-byte integers are used, the actual precision can be as little as 64 changes per second, while when 8-byte integers are used, a much better precision is available.
The Windows version of Gfortran I have shows this effect, so kind=8 should always be used.
I have not tested Ifort lately, but previously it provided a clock_tick value that changed only 64 times per second, much less than is required.
When an 8-byte integer is used, it should be possible to get values of clock_tick, based on the processor clock, which can be 5 GHz. I am sure if Fortran compiler developers used Fortran timers, this would have been available many years ago.
Typically CPU_TIME also suffers from this poor precision, due to the frequency at which the CPU time accumulator is updated. There is no “KIND” fix I am aware of, as usnig REAL(4) or REAL(8) has the same result.