To time a function/part of my program, I usually use the pattern below:
program main
implicit none
integer :: t0, t1, count_max, count_rate
call system_clock(t0, count_rate, count_max)
! do a heavy computation ...
call system_clock(t1)
print *, 'Elapsed Time :', real(t1 - t0) / count_rate
end program main
That works fine, but I have to define 4 more variables every time I want to time some code and I have to use these variables to explicitely calculate and print the elapsed time. What I want is something like the following to do the same as above:
program main
use time
implicit none
call tic()
! do a heavy computation ...
call toc()
end program main
The respective subroutines were defined as follows in a module time:
Which also works fine, but still, I have to define one variable t0 for this to work. My question is how can I remove this variable and be able to call tic() and call toc()?
You can use module variables to store times and access them to compute elapsed times.
In the thread Module to time code a few modules to time codes were presented or cited.
You can make t0,count_rate and count_max private variables in the module, with t0 at least saved,
and you donât even need () in tic and toc. My test example with very few changes from the original:
Just as a footnote, as that works just fine for a lot of cases, you want to look at the packages referenced above instead of using a single SAVEd variable if your code is parallel, recursive, or elemental. Also note calling a routine that produces I/O limits you in some circumstances in creating PURE routines. All that said, the above is fine; just wanted to mention it is not OK for some circumstances.
I like to mention not to overlook profiling tools too, as supplied by almost all vendors. the GNU or BSD gprof(1) command is supported by several programming environments.
A couple of additional considerations to build on the useful suggestions you have received upthread:
with SYSTEM_CLOCK and timing determinations, use an integer kind of higher range and a real kind of greater precision. Assuming you are on the widely used processors these days with binary arithmetic, this can mean a range of 10 for your integer (aka 64-bit integer) and a decimal precision of at least 12 (usually a 64-bit binary floating-point kind).
based on what you state as your desired use scenarios, you may want to look into an object-oriented type for your timer. But here you would need to declare and define an object in your code instrumentation that is such a type, but the usage patterns might then be clearer for you.
Click to see an example
module kinds_m
use, intrinsic :: iso_fortran_env, only : I8 => int64
integer, parameter :: P12 = selected_real_kind( p=12 )
end module
module timer_m
use kinds_m, only : I8, WP => P12
private
real(WP), parameter :: ZERO = 0.0_wp
type, public :: timer_t
private
real(WP) :: start_time = ZERO
real(WP) :: end_time = ZERO
contains
private
procedure, pass(this) :: start => start_time
procedure, pass(this) :: stop => end_time
procedure, pass(this) :: t => get_time
end type
contains
impure elemental subroutine start_time( this )
class(timer_t), intent(inout) :: this
call my_cpu_time( this%start_time )
end subroutine
impure elemental subroutine end_time( this )
class(timer_t), intent(inout) :: this
call my_cpu_time( this%end_time )
end subroutine
elemental function get_time( this ) result(time)
class(timer_t), intent(in) :: this
real(WP) :: time
time = this%end_time - this%start_time
end function
impure elemental subroutine my_cpu_time( time )
! Argument list
real(WP), intent(inout) :: time
! Local variables
integer(I8) :: tick
integer(I8) :: rate
call system_clock (tick, rate)
time = real(tick, kind=kind(time) ) / real(rate, kind=kind(time) )
return
end subroutine my_cpu_time
end module
use timer_m, only : timer_t
type(timer_t) :: timer
..
call timer%start()
.. do some work
call timer%stop()
.. fetch the elapsed time
print *, timer%t()
I agree with you on the integer 64bit part, but why do you believe the OO approach is superior than a straightforward module-subroutine/function model? One of the reasons I dislike C++ is its strong usage of the OO paradigm, which makes algorithms needlessly complex/unreadable in many circumstances. Also, unless Iâm missing something obvious, the 32-bit real is sufficiently large for the 18-digits of integer 64 division?
Note I prefaced my suggestion with âbased on what you state as your desired use scenarios.â Under the circumstances, the module-based model you intend to use per the other suggestion upthread involves âglobalâ data with the SAVE attribute. This wonât scale all that well for any needs (now or in the future) with concurrent execution. The OO approach I show decouples the state from the data and enables the code to freely consume the âclassâ; it can be instantiated as many times as needed and consumed across sequential or concurrent/parallel modes. The users of C++ may abuse the OO paradigm but that does not signal the rest to throw the baby out with the bathwater.
Well, it may not be that obvious but some processors scale up the count rate in the SYSTEM_CLOCK arbitrarily with integers of higher range. Given this, you can run into loss of precision with your timing studies, particularly if you are working with microbenchmarks. Thus the safer option is a decimal precision of 12 or greater for better portability of code.