New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
timers.f90 in branches/UKMO/dev_r5785_SSS_obsoper/NEMOGCM/TOOLS/WEIGHTS/src – NEMO

source: branches/UKMO/dev_r5785_SSS_obsoper/NEMOGCM/TOOLS/WEIGHTS/src/timers.f90 @ 7740

Last change on this file since 7740 was 7740, checked in by mattmartin, 7 years ago

Removed svn keywords.

File size: 10.5 KB
Line 
1!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2!
3!     This module uses F90 cpu time routines to allowing setting of
4!     multiple CPU timers.
5!
6!-----------------------------------------------------------------------
7!
8!     CVS:$Id$
9!
10!     Copyright (c) 1997, 1998 the Regents of the University of
11!       California.
12!
13!     This software and ancillary information (herein called software)
14!     called SCRIP is made available under the terms described here. 
15!     The software has been approved for release with associated
16!     LA-CC Number 98-45.
17!
18!     Unless otherwise indicated, this software has been authored
19!     by an employee or employees of the University of California,
20!     operator of the Los Alamos National Laboratory under Contract
21!     No. W-7405-ENG-36 with the U.S. Department of Energy.  The U.S.
22!     Government has rights to use, reproduce, and distribute this
23!     software.  The public may copy and use this software without
24!     charge, provided that this Notice and any statement of authorship
25!     are reproduced on all copies.  Neither the Government nor the
26!     University makes any warranty, express or implied, or assumes
27!     any liability or responsibility for the use of this software.
28!
29!     If software is modified to produce derivative works, such modified
30!     software should be clearly marked, so as not to confuse it with
31!     the version available from Los Alamos National Laboratory.
32!
33!***********************************************************************
34
35      module timers
36
37!-----------------------------------------------------------------------
38
39      use kinds_mod
40
41      implicit none
42
43      integer (kind=int_kind), parameter ::   &
44           max_timers = 99  ! max number of timers allowed
45
46      integer (kind=int_kind), save ::  &
47           cycles_max       ! max value of clock allowed by system
48
49      integer (kind=int_kind), dimension(max_timers), save ::  &
50           cycles1,          & ! cycle number at start for each timer
51           cycles2          ! cycle number at stop  for each timer
52
53      real (kind=real_kind), save ::   &
54           clock_rate       ! clock_rate in seconds for each cycle
55
56      real (kind=real_kind), dimension(max_timers), save ::   &
57           cputime          ! accumulated cpu time in each timer
58
59      character (len=8), dimension(max_timers), save ::   &
60           status           ! timer status string
61
62!***********************************************************************
63
64      contains
65
66!***********************************************************************
67
68      subroutine timer_check(timer)
69
70!-----------------------------------------------------------------------
71!
72!     This routine checks a given timer.  This is primarily used to
73!     periodically accumulate time in the timer to prevent timer cycles
74!     from wrapping around max_cycles.
75!
76!-----------------------------------------------------------------------
77
78!-----------------------------------------------------------------------
79!
80!     Input Variables:
81!
82!-----------------------------------------------------------------------
83
84      integer (kind=int_kind), intent(in) ::   &
85          timer            ! timer number
86
87!-----------------------------------------------------------------------
88
89      if (status(timer) .eq. 'running') then
90        call timer_stop (timer)
91        call timer_start(timer)
92      endif
93
94!-----------------------------------------------------------------------
95
96      end subroutine timer_check
97
98!***********************************************************************
99
100      subroutine timer_clear(timer)
101
102!-----------------------------------------------------------------------
103!
104!     This routine resets a given timer.
105!
106!-----------------------------------------------------------------------
107
108!-----------------------------------------------------------------------
109!
110!     Input Variables:
111!
112!-----------------------------------------------------------------------
113
114      integer (kind=int_kind), intent(in) ::   &
115          timer            ! timer number
116
117!-----------------------------------------------------------------------
118
119      cputime(timer) = 0.0_real_kind  ! clear the timer
120
121!-----------------------------------------------------------------------
122
123      end subroutine timer_clear
124
125!***********************************************************************
126
127      function timer_get(timer)
128
129!-----------------------------------------------------------------------
130!
131!     This routine returns the result of a given timer.  This can be
132!     called instead of timer_print so that the calling routine can
133!     print it in desired format.
134!
135!-----------------------------------------------------------------------
136
137!-----------------------------------------------------------------------
138!
139!     Input Variables:
140!
141!-----------------------------------------------------------------------
142
143      integer (kind=int_kind), intent(in) ::   &
144          timer            ! timer number
145
146!-----------------------------------------------------------------------
147!
148!     Output Variables:
149!
150!-----------------------------------------------------------------------
151
152      real (kind=real_kind) ::   &
153           timer_get   ! accumulated cputime in given timer
154
155!-----------------------------------------------------------------------
156
157      if (status(timer) .eq. 'stopped') then
158        timer_get = cputime(timer)
159      else
160        call timer_stop(timer)
161        timer_get = cputime(timer)
162        call timer_start(timer)
163      endif
164
165!-----------------------------------------------------------------------
166
167      end function timer_get
168
169!***********************************************************************
170
171      subroutine timer_print(timer)
172
173!-----------------------------------------------------------------------
174!
175!     This routine prints the accumulated cpu time in given timer.
176!
177!-----------------------------------------------------------------------
178
179!-----------------------------------------------------------------------
180!
181!     Input Variables:
182!
183!-----------------------------------------------------------------------
184
185      integer (kind=int_kind), intent(in) ::   &
186          timer            ! timer number
187
188!-----------------------------------------------------------------------
189
190      !---
191      !--- print the cputime accumulated for timer
192      !--- make sure timer is stopped
193      !---
194
195      if (status(timer) .eq. 'stopped') then
196        write(*,"(' CPU time for timer',i3,':',1p,e16.8)")   &
197             timer,cputime(timer)
198      else
199        call timer_stop(timer)
200        write(*,"(' CPU time for timer',i3,':',1p,e16.8)")   &
201             timer,cputime(timer)
202        call timer_start(timer)
203      endif
204
205!-----------------------------------------------------------------------
206
207      end subroutine timer_print
208
209!***********************************************************************
210
211      subroutine timer_start(timer)
212
213!-----------------------------------------------------------------------
214!
215!     This routine starts a given timer.
216!
217!-----------------------------------------------------------------------
218
219!-----------------------------------------------------------------------
220!
221!     Input Variables:
222!
223!-----------------------------------------------------------------------
224
225      integer (kind=int_kind), intent(in) ::   &
226          timer            ! timer number
227
228!-----------------------------------------------------------------------
229
230      !---
231      !--- Start the timer and change timer status.
232      !---
233
234      if (status(timer) .eq. 'stopped') then
235        call system_clock(count=cycles1(timer))
236        status(timer) = 'running'
237      endif
238
239!-----------------------------------------------------------------------
240
241      end subroutine timer_start
242
243!***********************************************************************
244
245      subroutine timer_stop(timer)
246
247!-----------------------------------------------------------------------
248!
249!     This routine stops a given timer.
250!
251!-----------------------------------------------------------------------
252
253!-----------------------------------------------------------------------
254!
255!     Input Variables:
256!
257!-----------------------------------------------------------------------
258
259      integer (kind=int_kind), intent(in) ::   &
260          timer            ! timer number
261
262!-----------------------------------------------------------------------
263
264      if (status(timer) .eq. 'running') then
265
266        !---
267        !--- Stop the desired timer.
268        !---
269
270        call system_clock(count=cycles2(timer))
271
272        !---
273        !--- check and correct for cycle wrapping
274        !---
275
276        if (cycles2(timer) .ge. cycles1(timer)) then
277          cputime(timer) = cputime(timer) + clock_rate*   &
278                           (cycles2(timer) - cycles1(timer))
279        else
280          cputime(timer) = cputime(timer) + clock_rate*   &
281                      (cycles2(timer) - cycles1(timer) + cycles_max)
282        endif
283
284        !---
285        !--- Change timer status.
286        !---
287
288        status(timer)='stopped'
289
290      endif
291
292!-----------------------------------------------------------------------
293
294      end subroutine timer_stop
295
296!***********************************************************************
297
298      subroutine timers_init
299
300!-----------------------------------------------------------------------
301!
302!     This routine initializes some machine parameters necessary for
303!     computing cpu time from F90 intrinsics.
304!
305!-----------------------------------------------------------------------
306
307      integer (kind=int_kind) :: cycles ! count rate return by sys_clock
308
309!-----------------------------------------------------------------------
310
311      !---
312      !--- Initialize timer arrays and clock_rate.
313      !---
314
315      clock_rate = 0.0_real_kind
316      cycles1    = 0
317      cycles2    = 0
318      cputime    = 0.0_real_kind
319      status     = 'stopped'
320
321      !---
322      !--- Call F90 intrinsic system_clock to determine clock rate
323      !--- and maximum cycles.  If no clock available, print message.
324      !---
325
326      call system_clock(count_rate=cycles, count_max=cycles_max)
327
328      if (cycles /= 0) then
329        clock_rate = 1.0_real_kind/real(cycles)
330      else
331        clock_rate = 0.0_real_kind
332        print *, '--- No system clock available ---'
333      endif
334
335!-----------------------------------------------------------------------
336
337      end subroutine timers_init
338
339!***********************************************************************
340
341      end module timers
342
343!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
Note: See TracBrowser for help on using the repository browser.