My Project
mod_clock.f90
Go to the documentation of this file.
1 
2 
3 
4 
5 
6 
7 
8 
9 
10 
11 
12 !/===========================================================================/
13 ! Copyright (c) 2007, The University of Massachusetts Dartmouth
14 ! Produced at the School of Marine Science & Technology
15 ! Marine Ecosystem Dynamics Modeling group
16 ! All rights reserved.
17 !
18 ! FVCOM has been developed by the joint UMASSD-WHOI research team. For
19 ! details of authorship and attribution of credit please see the FVCOM
20 ! technical manual or contact the MEDM group.
21 !
22 !
23 ! This file is part of FVCOM. For details, see http://fvcom.smast.umassd.edu
24 ! The full copyright notice is contained in the file COPYRIGHT located in the
25 ! root directory of the FVCOM code. This original header must be maintained
26 ! in all distributed versions.
27 !
28 ! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS"
29 ! AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO,
30 ! THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
31 ! PURPOSE ARE DISCLAIMED.
32 !
33 !/---------------------------------------------------------------------------/
34 ! CVS VERSION INFORMATION
35 ! $Id$
36 ! $Name$
37 ! $Revision$
38 !/===========================================================================/
39 
40 MODULE mod_clock
41  USE mod_prec
42  USE mod_time
44  USE mod_utils
45  IMPLICIT NONE
46 
47 ! SUBROUTINES IN MOD_CLOCK:
48 ! TIMER ROUTINES
49 ! WATCH_INIT(TYPE::WATCH)
50 ! WATCH_TIME(TYPE::WATCH) RETURN(REAL(DP))
51 ! WATCH_RESET(TYPE::WATCH)
52 ! WATCH_LAP(TYPE::WATCH)
53 ! WATCH_LAP(TYPE::WATCH,INTEGER::UNIT#,CHARACTER(LEN*)::MESSAGE)
54 ! WATCH_REPORT(TYPE::WATCH,INTEGER,CHARACTER(LEN*))
55 !
56 ! TIME STRING FORMATTING
57 ! GETTIME(CHARACTER(LEN=13),INTEGER)
58 ! GET_TIMESTAMP(CHARACTER(LEN=*))
59 !
60 ! REPORT_TIME(INTEGER(ITIME),INTEGER(ITIME),INTEGER(ITIME),TYPE::TIME)
61 
62 
63 
64  TYPE watch
65  INTEGER :: count_rate,count_max
66  INTEGER :: count_0
67  INTEGER :: count_current, count_last
68  INTEGER :: lap_count
69  END TYPE watch
70 
72 
73  INTERFACE watch_lap
74  MODULE PROCEDURE watch_lap_noprint
75  MODULE PROCEDURE watch_lap_print
76  END INTERFACE
77 
78 !!$EXAMPLE OF TIMER USE:
79 !!$
80 !!$! Declare a watch type
81 !!$TYPE(WATCH):: atimer
82 !!$real(sp) :: atime
83 !!$
84 !!$! Initialize the Timer
85 !!$CALL WATCH_INIT(atimer)
86 !!$
87 !!$
88 !!$Do J = 1:KB
89 !!$
90 !!$ Do I = 1:NT
91 !!$ ! DO SOMETHING
92 !!$
93 !!$ END Do
94 !!$ ! Prints the time take for each internal do-loop
95 !!$ call Watch_lap(atimer) ! JUST COUNT FOR LATER
96 !!$ OR
97 !!$ call Watch_lap(atimer,ipt,"what am I counting!") ! PRINTS TO SCREEN
98 !!$END Do
99 !!$
100 !!$ ! Prints the average time taken for all laps
101 !!$ call Watch_report(atimer)
102 !!$
103 !!$ ! Return time since watch started
104 !!$ atime = Watch_time(atimer)
105 !!$
106 !!$ ! RESET THE WATCH
107 !!$ CALL WATCH_RESET(atimer)
108 
109 
110  CONTAINS
111 
112 !==============================================================================!
113 ! Initialize STOPWATCH !
114 !==============================================================================!
115 SUBROUTINE watch_init(MYWATCH)
116  IMPLICIT NONE
117  TYPE(watch) :: MYWATCH
118 
119  mywatch%COUNT_RATE = 0
120  mywatch%COUNT_MAX = 0
121  mywatch%COUNT_CURRENT = 0
122  mywatch%COUNT_LAST = 0
123  mywatch%COUNT_0 = 0
124  mywatch%Lap_Count = 0
125 
126  CALL system_clock (mywatch%COUNT_CURRENT, mywatch%COUNT_RATE, mywatch%COUNT_MAX)
127 
128  mywatch%COUNT_0 = mywatch%COUNT_CURRENT
129  mywatch%COUNT_LAST = mywatch%COUNT_CURRENT
130 
131  IF(mywatch%COUNT_MAX == 0) CALL fatal_error &
132  & ("MOD_CLOCK: FORTRAN DOES NOT RECOGNIZE YOUR SYSTEM CLOCK!",&
133  & "INTIRINISIC, SYSTEM_CLOCK returned COUNT_MAX==0")
134 
135  IF(mywatch%COUNT_RATE .LE. 0) CALL fatal_error &
136  & ("MOD_CLOCK: FORTRAN DOES NOT RECOGNIZE YOUR SYSTEM CLOCK!",&
137  & .LE."INTIRINISIC, SYSTEM_CLOCK returned COUNT_RATE 0")
138 
139  IF(mywatch%COUNT_0 .LT. 0) CALL fatal_error &
140  & ("MOD_CLOCK: FORTRAN DOES NOT RECOGNIZE YOUR SYSTEM CLOCK!",&
141  & .LT."INTIRINISIC, SYSTEM_CLOCK returned COUNT 0")
142 
143 END SUBROUTINE watch_init
144 !==============================================================================!
145 ! Retrieve Stopwatch time !
146 ! Return a double # of seconds since watch_initialize
147 !==============================================================================!
148  FUNCTION watch_time(MYWATCH)
149  IMPLICIT NONE
150  TYPE(watch) :: mywatch
151  REAL(dp) :: watch_time
152  INTEGER(ITIME) :: big_count
153  INTEGER :: my_count
154 
155  CALL system_clock(count=my_count)
156  big_count = my_count - mywatch%COUNT_0
157  IF (big_count < 0) big_count = big_count + mywatch%COUNT_MAX
158 
159  watch_time = dble(big_count) / dble(mywatch%COUNT_RATE)
160 
161  END FUNCTION watch_time
162 
163 !==============================================================================!
164 ! Start Watch lapstart !
165 !==============================================================================!
166  SUBROUTINE watch_reset(MYWATCH)
167  IMPLICIT NONE
168  TYPE(watch) :: MYWATCH
169 
170  CALL system_clock(mywatch%COUNT_CURRENT)
171  mywatch%LAP_Count = 0
172  mywatch%Count_LAST = mywatch%COUNT_CURRENT
173  mywatch%Count_0 = mywatch%COUNT_CURRENT
174 
175  END SUBROUTINE watch_reset
176 
177 !==============================================================================!
178 ! Watch lap !
179 !==============================================================================!
180  SUBROUTINE watch_lap_noprint(MYWATCH)
181  IMPLICIT NONE
182  TYPE(watch) :: MYWATCH
183 
184  mywatch%COUNT_LAST = mywatch%COUNT_CURRENT
185  CALL system_clock(mywatch%COUNT_CURRENT)
186  mywatch%LAP_Count = mywatch%LAP_Count + 1
187 
188  END SUBROUTINE watch_lap_noprint
189 
190 !==============================================================================!
191 ! Watch Start lap !
192 !==============================================================================!
193  SUBROUTINE watch_start_lap(MYWATCH)
194  IMPLICIT NONE
195  TYPE(watch) :: MYWATCH
196 
197  CALL system_clock(mywatch%COUNT_CURRENT)
198  !IGNORE TIME SINCE LAST STOP
199  mywatch%Count_0 =mywatch%Count_0 + (mywatch%COUNT_CURRENT - mywatch%COUNT_LAST)
200 
201  END SUBROUTINE watch_start_lap
202 
203 !==============================================================================!
204 ! Watch Stop lap !
205 !==============================================================================!
206  SUBROUTINE watch_stop_lap(MYWATCH)
207  IMPLICIT NONE
208  TYPE(watch) :: MYWATCH
209 
210  CALL system_clock(mywatch%COUNT_CURRENT)
211  mywatch%COUNT_LAST = mywatch%COUNT_CURRENT
212  mywatch%LAP_Count = mywatch%LAP_Count + 1
213 
214  END SUBROUTINE watch_stop_lap
215 !==============================================================================!
216 ! Print Watch Report !
217 !==============================================================================!
218  SUBROUTINE watch_report(MYWATCH,UNIT,MSG)
219  IMPLICIT NONE
220 
221 
222  TYPE(watch) :: MYWATCH
223  integer, intent(in) :: unit
224  Character(len=*), intent(in) :: MSG
225  INTEGER(ITIME) :: BIG_COUNT
226  Character(len=16) :: lcnt,ltime
227  REAL(DP) :: AVG_TIME
228 
229  write(lcnt,'(I8.8)')mywatch%LAP_COUNT
230 
231  big_count = mywatch%COUNT_CURRENT - mywatch%COUNT_0
232  IF (big_count < 0) big_count = big_count + mywatch%COUNT_MAX
233 
234  avg_time = dble(big_count) / dble(mywatch%COUNT_RATE * mywatch%LAP_COUNT)
235 
236  write(ltime,'(F16.6)') avg_time
237 
238  write(unit,*) "! === "//trim(msg)//" ==="
239  write(unit,*) "! Average Lap Time(seconds):"//trim(adjustl(ltime))//"; &
240  &Lap Count:"//trim(adjustl(lcnt))
241  write(unit,*) "! ==============================="
242 
243 
244  END SUBROUTINE watch_report
245 !==============================================================================!
246 ! Print Watch Print !
247 !==============================================================================!
248  SUBROUTINE watch_lap_print(MYWATCH,UNIT,MSG)
249  IMPLICIT NONE
250 
251 
252  TYPE(watch) :: MYWATCH
253  integer, intent(in) :: unit
254  Character(len=*), intent(in) :: MSG
255  INTEGER(ITIME) :: BIG_COUNT
256  REAL(DP) :: LAP_TIME
257  Character(len=16) :: ltime
258 
259 
260  CALL watch_lap_noprint(mywatch)
261  big_count = mywatch%COUNT_CURRENT - mywatch%COUNT_LAST
262  IF (big_count < 0) big_count = big_count + mywatch%COUNT_MAX
263 
264  lap_time = dble(big_count) / dble(mywatch%COUNT_RATE)
265 
266  write(ltime,'(F16.6)') lap_time
267 
268  write(unit,*) "! === "//trim(msg)//" ==="
269  write(unit,*) "! Last Lap Time(seconds):"//trim(adjustl(ltime))
270  write(unit,*) "! ==============================="
271 
272  END SUBROUTINE watch_lap_print
273 
274 !==============================================================================!
275 ! Return a Time String Days:Hours:Minutes:Seconds from Number of Seconds !
276 !==============================================================================!
277 
278  SUBROUTINE gettime(INSTRING,INSECS)
280  IMPLICIT NONE
281  INTEGER, INTENT(IN) :: INSECS
282  CHARACTER(LEN=13), INTENT(INOUT) :: INSTRING
283  CHARACTER(LEN=4) :: S0
284  CHARACTER(LEN=2) :: S1,S2,S3
285  INTEGER :: DTCP,HTCP,MTCP,STCP
286 
287  dtcp = insecs/(3600*24)
288  htcp = mod(insecs,(3600*24))/3600
289  mtcp = mod(insecs,(3600))/60
290  stcp = insecs - (dtcp*3600*24 + htcp*3600 + mtcp*60)
291 
292  IF(dtcp >= 10000 ) then
293 
294  instring = "> 10000 DAYS"
295  return
296 
297  else if (dtcp < 0) THEN
298 
299  instring = " < 0 DAYS?"
300  return
301 
302  else
303 
304  WRITE(s0,"(I4.4)")int(dtcp)
305 
306  END IF
307 
308  WRITE(s1,"(I2.2)")int(htcp)
309 
310  WRITE(s2,"(I2.2)")int(mtcp)
311 
312  WRITE(s3,"(I2.2)")int(stcp)
313 
314 
315  instring = s0//":"//s1//":"//s2//":"//s3
316 
317  END SUBROUTINE gettime
318 !==============================================================================!
319 ! Get Current Time As Sting !
320 !==============================================================================!
321 SUBROUTINE get_timestamp(TS)
322  CHARACTER(LEN=*) TS
323  CHARACTER(LEN=8) D
324  CHARACTER(LEN=10) T
325 
326  CALL date_and_time ( date=d,time=t )
327  ts = d(7:8)//'/'//d(5:6)//'/'//d(1:4)//' '//t(1:2)//':'//t(3:4)
328 END SUBROUTINE get_timestamp
329 !==============================================================================!
330 ! Report Calculation Speed and Time to Complete !
331 !==============================================================================!
332 
333  SUBROUTINE report_time(IINT,ISTART,IEND,STIME)
335  IMPLICIT NONE
336  INTEGER(itime), INTENT(IN) :: IINT,ISTART,IEND
337  Type(time),INTENT(IN) :: STIME
338  REAL(SP) :: TTCP,TAVE
339  CHARACTER(LEN=80) :: SIMTIME,FINTIME
340  CHARACTER(LEN=22) :: PCOMP
341  INTEGER :: I,ICMP,ICMP2
342  INTEGER(ITIME) :: BIG_COUNT
343  LOGICAL, SAVE :: INITIALIZED
344 
345  real(DP):: tmp, seconds
346  integer :: hours, minutes
347  Character(len=2) :: h, m
348  Character(Len=9) :: s
349  Character(Len=6) :: d
350 
351  IF(.not. initialized) THEN
353 
354  tave = -1.0_sp
355  fintime = " UNKNOWN"
356  initialized = .true.
357 
358  ELSE
359  !
360  ! CALCULATE CURRENT TIME
361  !
362  CALL watch_lap(report_watch)
363 
364  !
365  ! CALCULATE AVERAGE TIME/ITERATION
366  !
367  big_count = report_watch%COUNT_CURRENT - report_watch%COUNT_0
368  IF (big_count < 0) big_count = big_count + report_watch%COUNT_MAX
369 
370  tave = dble(big_count) / dble(report_watch%COUNT_RATE * report_watch%LAP_COUNT)
371 
372  IF(tave < 0) tave = 0.0_sp
373 
374  !
375  ! CALCULATE TIME TO COMPLETION
376  !
377  ttcp = tave*(iend-iint)
378 
379  CALL gettime(fintime,int(ttcp))
380 
381  END IF
382 
383 !
384 ! CALCULATE COMPLETION PERCENTAGE GRAPHIC
385 !
386 ! IF(MOD(IINT,1) /= 0) RETURN
387  icmp = int( 100.*float(iint-istart+1)/float(iend-istart+1))
388  icmp2 = icmp/5
389  pcomp = " "
390  pcomp(1:1) = "|"
391  pcomp(22:22) = "|"
392 
393  DO i=2,icmp2+1
394  pcomp(i:i) = "="
395  END DO
396 
397  if (use_real_world_time) then
398  ! Get the date and time of the current iterationr
399  simtime = write_datetime(stime,6,"UTC")
400 
401 
402  !
403  ! REPORT
404  !
405  IF(mod(iint-1,10_dp) ==0) THEN
406  WRITE(ipt,102)
407  END IF
408  WRITE(ipt,101)iint,simtime,fintime,tave,pcomp
409 
410  else
411 
412  tmp = real(stime%MuSOD,dp) / real(million,dp)
413 
414  hours = tmp/3600
415  minutes = (tmp-hours*3600)/60
416  seconds = mod(tmp,60.0_dp)
417 
418  write(d,'(i6.6)') stime%mjd
419  write(h,'(i2.2)') hours
420  write(m,'(i2.2)') minutes
421  write(s,'(F9.6)') seconds
422 
423  simtime = "D"//d//"T"//h//":"//m//":"//s
424  IF(mod(iint-1,10_dp) ==0) THEN
425  WRITE(ipt,103)
426  END IF
427 
428  WRITE(ipt,101)iint,simtime,fintime,tave,pcomp
429  end if
430 
431  return
432 101 FORMAT(1x,"!",i7,3x,a26,3x,a13,3x,f8.4,2x,a22)
433 102 FORMAT(1x,"! IINT ",6x," SIMTIME(UTC) ",9x," FINISH IN ",5x," SECS/IT ",1x," PERCENT COMPLETE ")
434 103 FORMAT(1x,"! IINT ",6x," SIMTIME ",14x," FINISH IN ",5x," SECS/IT ",1x," PERCENT COMPLETE ")
435 
436  END SUBROUTINE report_time
437 
438 
439 END MODULE mod_clock
subroutine get_timestamp(TS)
Definition: mod_clock.f90:322
subroutine watch_init(MYWATCH)
Definition: mod_clock.f90:116
subroutine report_time(IINT, ISTART, IEND, STIME)
Definition: mod_clock.f90:334
real(dp) function watch_time(MYWATCH)
Definition: mod_clock.f90:149
subroutine watch_lap_noprint(MYWATCH)
Definition: mod_clock.f90:181
subroutine watch_reset(MYWATCH)
Definition: mod_clock.f90:167
type(watch) report_watch
Definition: mod_clock.f90:71
subroutine watch_report(MYWATCH, UNIT, MSG)
Definition: mod_clock.f90:219
logical use_real_world_time
Definition: mod_main.f90:131
integer, parameter dp
Definition: mod_prec.f90:52
subroutine fatal_error(ER1, ER2, ER3, ER4)
Definition: mod_utils.f90:230
subroutine watch_start_lap(MYWATCH)
Definition: mod_clock.f90:194
subroutine gettime(INSTRING, INSECS)
Definition: mod_clock.f90:279
subroutine watch_lap_print(MYWATCH, UNIT, MSG)
Definition: mod_clock.f90:249
integer ipt
Definition: mod_main.f90:922
integer(itime), parameter million
Definition: mod_time.f90:160
subroutine watch_stop_lap(MYWATCH)
Definition: mod_clock.f90:207
character(len=80) function write_datetime(mjdin, prec, TZONE)
Definition: mod_time.f90:682