-
Notifications
You must be signed in to change notification settings - Fork 5
/
clocks.f90
188 lines (134 loc) · 5.69 KB
/
clocks.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
!>
!! \short This module contains variables and routines for dealing with
!! cpu and wall clocks
!!
!! This module uses calls to the Fortran 2003 internal routines cpu_time
!! and system_clock. To get the time passed between two events, one has
!! to call these twice, once at the start and once at the end.
!! To avoid overflowing the variable (which can happen for codes that run
!! for many hours or days), this module provides "update" routines that
!! update hour and minute counters. These should be called at regular
!! intervals. The module also comes with its own reporting routines.
!!
!! General module
!!
!! Dependencies:
!! - file_admin module (for the unit of the log file where to write the report)
!! - my_mpi (for the value of rank, the MPI id of the current processor, reporting is only done for the rank 0 processor)
!!
!! Author: Garrelt Mellema
!!
!! Date: 2010-03-08
!!
!! Version: 1.0
!!
!<
module clocks
use file_admin, only: logf, timefile, results_dir
use my_mpi, only: rank
implicit none
! Time limit for production of iterdump files (see evolve)
real,parameter,public :: iterdump_minutes=15.0
! Start and end time for CPU report
real :: cputime1 !< Start time for call to CPU routine
real :: cputime2 !< End time for call to CPU routine
integer :: cpu_hours=0 !< accumulates the CPU hours
integer :: cpu_minutes=0 !< accumulates the CPU minutes
real :: cpu_seconds=0.0 !< accumulates the CPU seconds
! Wall clock time variables
! (use 8 byte integers to avoid the clock reset)
integer(kind=8) :: cntr1 !< Start time for call to wall clock routine
integer(kind=8) :: cntr2 !< End time for call to wall clock routine
integer(kind=8) :: absolute_cntr1 !< Asbolute start time wall clock
integer(kind=8) :: countspersec !< counts per second (for wall clock time)
integer :: clock_hours=0 !< accumulates the wall clock hours
integer :: clock_minutes=0 !< accumulates the wall clock minutes
real :: clock_seconds=0.0 !< accumulates the wall clock seconds
contains
!=======================================================================
!> Sets up all the clocks (initialization routine)
subroutine setup_clocks
character(len=512) :: filename ! name of the time file
call setup_cpuclock()
call setup_wallclock()
if (rank == 0) then
filename=trim(adjustl(trim(adjustl(results_dir))//"Timings.log"))
open(unit=timefile,file=filename,status="unknown",action="write",&
position="append")
write(unit=timefile,fmt="(A)") "Timings file for C2-Ray run"
endif
end subroutine setup_clocks
!=======================================================================
!> Sets up cpu clock (initialization routine)
subroutine setup_cpuclock
! Initialize cpu timer
call cpu_time(cputime1)
end subroutine setup_cpuclock
!=======================================================================
!> Sets up wall clock (initialization routine)
subroutine setup_wallclock
! Initialize wall cock timer
call system_clock(cntr1)
! Save initial value
absolute_cntr1=cntr1
end subroutine setup_wallclock
!=======================================================================
!> Updates all the clocks
subroutine update_clocks
call update_cpuclock
call update_wallclock
end subroutine update_clocks
!=======================================================================
!> Updates CPU clock
subroutine update_cpuclock
! Find out intermediate CPU time (to avoid overflowing the counter)
call cpu_time(cputime2)
cpu_seconds=cpu_seconds+real(cputime2-cputime1)
cputime1=cputime2
cpu_minutes = cpu_minutes + int(cpu_seconds) / 60
cpu_seconds = MOD ( cpu_seconds , 60.0 )
cpu_hours = cpu_hours + cpu_minutes / 60
cpu_minutes = MOD ( cpu_minutes , 60 )
end subroutine update_cpuclock
!=======================================================================
!> Updates wall clock
subroutine update_wallclock
call system_clock(cntr2,countspersec)
clock_seconds=clock_seconds+real(cntr2-cntr1)/real(countspersec)
cntr1=cntr2
clock_minutes = clock_minutes + int(clock_seconds) / 60
clock_seconds = MOD ( clock_seconds , 60.0 )
clock_hours = clock_hours + clock_minutes / 60
clock_minutes = MOD ( clock_minutes , 60 )
end subroutine update_wallclock
!=======================================================================
!> Return number of seconds wall clock since start of program
real function timestamp_wallclock ()
call system_clock(cntr2,countspersec)
timestamp_wallclock=real(cntr2-absolute_cntr1)/real(countspersec)
end function timestamp_wallclock
!=======================================================================
!> Reports all the clocks
subroutine report_clocks
call report_cpuclock
call report_wallclock
end subroutine report_clocks
!=======================================================================
!> Reports CPU clock to log file (unit logf)
subroutine report_cpuclock
call update_cpuclock ()
if (rank == 0) then
write(logf,*) "CPU time: ",cpu_hours,' hours',cpu_minutes,' minutes', &
cpu_seconds,' seconds.'
endif
end subroutine report_cpuclock
!=======================================================================
!> Reports wall clock to log file (unit logf)
subroutine report_wallclock
call update_wallclock ()
if (rank == 0) then
write(logf,*) "Wall clock time: ",clock_hours,' hours', &
clock_minutes,' minutes',clock_seconds,' seconds.'
endif
end subroutine report_wallclock
end module clocks