To time sections N sections of a code, one may declare real :: times(:N+1)
and insert
call cpu_time(times(i))
in the right places. It’s simple but tedious, and if you want to add a new check point between two check points, you need to renumber times(:)
. At the end of the program you need to label and print the elapsed times. I wrote a simple module to streamline this, printing both CPU and wall times given check points. A main program could be
program xwatch
! 11/20/2021 08:15 PM driver for watch and print_elapsed_times
use kind_mod , only: dp
use watch_mod, only: watch,print_elapsed_times
implicit none
integer , parameter :: n = 10**7, iunit = 20
character (len=*), parameter :: xfile = "temp.bin"
real(kind=dp) :: x(n),xchk(n)
call random_seed()
call watch("init")
call random_number(x)
call watch("random_number()")
print*,"sum(x) =",sum(x)
call watch("sum(x)")
print*,"sum(sin(x)) =",sum(sin(x))
call watch("sum(sin(x))")
open (unit=iunit,file=xfile,action="write",status="replace",form="unformatted")
write (iunit) x
close (iunit)
call watch("wrote x")
open (unit=iunit,file=xfile,action="read",status="old",form="unformatted")
read (iunit) xchk
call watch("read x")
print*,"max_diff =",maxval(abs(x-xchk))
call watch("check")
call print_elapsed_times()
end program xwatch
for the modules
module kind_mod
implicit none
integer, public, parameter :: dp = kind(1.0d0)
end module kind_mod
!
module watch_mod
use kind_mod, only: dp
implicit none
private
public :: watch,print_elapsed_times
integer, parameter :: max_times = 1000
real(kind=dp) :: cpu_times(max_times)
integer :: wall_times(max_times)
integer, save :: ntimes = 0
character (len=100) :: time_labels(max_times)
contains
!
subroutine watch(label)
character (len=*), intent(in), optional :: label
ntimes = ntimes + 1
if (ntimes <= max_times) then
call cpu_time(cpu_times(ntimes))
call system_clock(wall_times(ntimes))
if (present(label)) then
time_labels(ntimes) = label
else
time_labels(ntimes) = ""
end if
end if
end subroutine watch
!
subroutine print_elapsed_times()
integer :: i, itick
call system_clock(count_rate = itick)
write (*,"(/,a20,2a12)") "task","cpu_time","wall_time"
do i=2,ntimes
write (*,"(a20,2f12.6)") trim(time_labels(i)),cpu_times(i)-cpu_times(i-1), &
(wall_times(i)-wall_times(i-1))/real(itick,kind=dp)
if (i == ntimes) write (*,"(a20,2f12.6)") "TOTAL",cpu_times(i)-cpu_times(1), &
(wall_times(i)-wall_times(1))/real(itick,kind=dp)
end do
end subroutine print_elapsed_times
end module watch_mod
Sample output is
sum(x) = 4999193.4915036112
sum(sin(x)) = 4596353.7277946780
max_diff = 0.0000000000000000
task cpu_time wall_time
random_number() 0.078125 0.078000
sum(x) 0.000000 0.000000
sum(sin(x)) 0.375000 0.375000
wrote x 0.093750 0.313000
read x 0.031250 0.047000
check 0.031250 0.031000
TOTAL 0.609375 0.844000
Wall and CPU times tend to be very close except for I/O. I could add an option to print the elapsed times in descending order to clarify where a program spends more time.