Line data Source code
1 : !|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
2 :
3 : module ice_timers
4 :
5 : ! This module contains routine for supporting multiple CPU timers
6 : ! and accumulates time for each individual block and node (task).
7 : !
8 : ! 2005: Adapted from POP by William Lipscomb
9 : ! Replaced 'stdout' by 'nu_diag'
10 : ! 2006 ECH: Replaced 'system_clock' timing mechanism by 'MPI_WTIME'
11 : ! for MPI runs. Single-processor runs still use system_clock.
12 :
13 : use ice_kinds_mod
14 : use ice_constants, only: c0, c1
15 : use ice_domain, only: nblocks, distrb_info
16 : use ice_global_reductions, only: global_minval, global_maxval, global_sum
17 : use ice_exit, only: abort_ice
18 : use ice_fileunits, only: nu_diag
19 : use ice_communicate, only: my_task, master_task
20 : use icepack_intfc, only: icepack_query_parameters
21 : use icepack_intfc, only: icepack_warnings_flush, icepack_warnings_aborted
22 :
23 : implicit none
24 : private
25 :
26 : public :: init_ice_timers, &
27 : get_ice_timer, & ! LCOV_EXCL_LINE
28 : ice_timer_clear, & ! LCOV_EXCL_LINE
29 : ice_timer_start, & ! LCOV_EXCL_LINE
30 : ice_timer_stop, & ! LCOV_EXCL_LINE
31 : ice_timer_print, & ! LCOV_EXCL_LINE
32 : ice_timer_print_all, & ! LCOV_EXCL_LINE
33 : ice_timer_check
34 :
35 : logical(log_kind), public :: &
36 : timer_stats ! controls printing of timer statistics
37 :
38 : !-----------------------------------------------------------------------
39 : ! public timers
40 : !-----------------------------------------------------------------------
41 :
42 : integer (int_kind), public :: &
43 : timer_total, &! total time ! LCOV_EXCL_LINE
44 : timer_step, &! time stepping ! LCOV_EXCL_LINE
45 : timer_dynamics, &! dynamics ! LCOV_EXCL_LINE
46 : timer_advect, &! horizontal advection ! LCOV_EXCL_LINE
47 : timer_column, &! column ! LCOV_EXCL_LINE
48 : timer_thermo, &! thermodynamics ! LCOV_EXCL_LINE
49 : timer_sw, &! radiative transfer ! LCOV_EXCL_LINE
50 : timer_ponds, &! melt ponds ! LCOV_EXCL_LINE
51 : timer_ridge, &! ridging ! LCOV_EXCL_LINE
52 : timer_catconv, &! category conversions ! LCOV_EXCL_LINE
53 : timer_fsd, &! floe size distribution ! LCOV_EXCL_LINE
54 : timer_couple, &! coupling ! LCOV_EXCL_LINE
55 : timer_readwrite, &! read/write ! LCOV_EXCL_LINE
56 : timer_diags, &! diagnostics/history ! LCOV_EXCL_LINE
57 : timer_hist, &! diagnostics/history ! LCOV_EXCL_LINE
58 : #if (defined CESMCOUPLED)
59 : timer_cplrecv, &! receive from coupler
60 : timer_rcvsnd, &! time between receive to send ! LCOV_EXCL_LINE
61 : timer_cplsend, &! send to coupled ! LCOV_EXCL_LINE
62 : timer_sndrcv, &! time between send to receive ! LCOV_EXCL_LINE
63 : #endif
64 : timer_bound, &! boundary updates
65 : timer_bundbound, &! boundary updates bundling ! LCOV_EXCL_LINE
66 : timer_bgc, &! biogeochemistry ! LCOV_EXCL_LINE
67 : timer_forcing, &! forcing ! LCOV_EXCL_LINE
68 : timer_evp_1d, &! timer only loop ! LCOV_EXCL_LINE
69 : timer_evp_2d, &! timer including conversion 1d/2d ! LCOV_EXCL_LINE
70 : timer_updstate ! update state
71 : ! timer_updstate, &! update state
72 : ! timer_tmp1, &! for temporary timings ! LCOV_EXCL_LINE
73 : ! timer_tmp2, &! for temporary timings ! LCOV_EXCL_LINE
74 : ! timer_tmp3, &! for temporary timings ! LCOV_EXCL_LINE
75 : ! timer_tmp4, &! for temporary timings ! LCOV_EXCL_LINE
76 : ! timer_tmp5, &! for temporary timings ! LCOV_EXCL_LINE
77 : ! timer_tmp6, &! for temporary timings ! LCOV_EXCL_LINE
78 : ! timer_tmp7, &! for temporary timings ! LCOV_EXCL_LINE
79 : ! timer_tmp8, &! for temporary timings ! LCOV_EXCL_LINE
80 : ! timer_tmp9 ! for temporary timings
81 :
82 : !-----------------------------------------------------------------------
83 : !
84 : ! module variables
85 : !
86 : !-----------------------------------------------------------------------
87 :
88 : integer (int_kind), parameter :: &
89 : max_timers = 50 ! max number of timers
90 :
91 : type timer_data
92 : character (char_len) :: &
93 : name ! timer name
94 :
95 : logical (log_kind) :: &
96 : in_use, &! true if timer initialized ! LCOV_EXCL_LINE
97 : node_started ! true if any thread has started timer
98 :
99 : integer (int_kind) :: &
100 : num_blocks, &! number of blocks using this timer ! LCOV_EXCL_LINE
101 : num_nodes, &! number of nodes using this timer ! LCOV_EXCL_LINE
102 : num_starts, &! number of start requests ! LCOV_EXCL_LINE
103 : num_stops ! number of stop requests
104 :
105 : real (dbl_kind) :: &
106 : node_cycles1, &! cycle number at start for node timer ! LCOV_EXCL_LINE
107 : node_cycles2 ! cycle number at stop for node timer
108 :
109 : real (dbl_kind) :: &
110 : node_accum_time ! accumulated time for node timer
111 :
112 : logical (log_kind), dimension(:), pointer :: &
113 : block_started ! true if block timer started
114 :
115 : real (dbl_kind), dimension(:), pointer :: &
116 : block_cycles1, &! cycle number at start for block timers ! LCOV_EXCL_LINE
117 : block_cycles2 ! cycle number at stop for block timers
118 :
119 : real (dbl_kind), dimension(:), pointer :: &
120 : block_accum_time ! accumulated time for block timers
121 :
122 : end type
123 :
124 : type (timer_data), dimension(max_timers) :: &
125 : all_timers ! timer data for all timers
126 :
127 : real (dbl_kind) :: &
128 : clock_rate ! clock rate in seconds for each cycle
129 :
130 : !***********************************************************************
131 :
132 : contains
133 :
134 : !***********************************************************************
135 :
136 36 : subroutine init_ice_timers
137 :
138 : ! This routine initializes machine parameters and timer structures
139 : ! for computing cpu time from F90 intrinsic timer functions.
140 :
141 : !-----------------------------------------------------------------------
142 : !
143 : ! local variables
144 : !
145 : !-----------------------------------------------------------------------
146 :
147 : integer (int_kind) :: n ! dummy loop index
148 :
149 : character(len=*), parameter :: subname = '(init_ice_timers)'
150 :
151 : !-----------------------------------------------------------------------
152 : !
153 : ! initialize timer structures
154 : !
155 : !-----------------------------------------------------------------------
156 :
157 36 : clock_rate = c1
158 :
159 1836 : do n=1,max_timers
160 1800 : all_timers(n)%name = 'unknown_timer_name'
161 :
162 1800 : all_timers(n)%in_use = .false.
163 1800 : all_timers(n)%node_started = .false.
164 :
165 1800 : all_timers(n)%num_blocks = 0
166 1800 : all_timers(n)%num_nodes = 0
167 1800 : all_timers(n)%num_starts = 0
168 1800 : all_timers(n)%num_stops = 0
169 1800 : all_timers(n)%node_cycles1 = c0
170 1800 : all_timers(n)%node_cycles2 = c0
171 :
172 1800 : all_timers(n)%node_accum_time = c0
173 :
174 1800 : nullify(all_timers(n)%block_started)
175 1800 : nullify(all_timers(n)%block_cycles1)
176 1800 : nullify(all_timers(n)%block_cycles2)
177 1836 : nullify(all_timers(n)%block_accum_time)
178 : end do
179 :
180 36 : call get_ice_timer(timer_total, 'Total', nblocks,distrb_info%nprocs)
181 36 : call get_ice_timer(timer_step, 'TimeLoop', nblocks,distrb_info%nprocs)
182 36 : call get_ice_timer(timer_dynamics, 'Dynamics', nblocks,distrb_info%nprocs)
183 36 : call get_ice_timer(timer_advect, 'Advection',nblocks,distrb_info%nprocs)
184 36 : call get_ice_timer(timer_column, 'Column', nblocks,distrb_info%nprocs)
185 36 : call get_ice_timer(timer_thermo, 'Thermo', nblocks,distrb_info%nprocs)
186 36 : call get_ice_timer(timer_sw, 'Shortwave',nblocks,distrb_info%nprocs)
187 : ! call get_ice_timer(timer_ponds, 'Meltponds',nblocks,distrb_info%nprocs)
188 36 : call get_ice_timer(timer_ridge, 'Ridging', nblocks,distrb_info%nprocs)
189 : ! call get_ice_timer(timer_catconv, 'Cat Conv', nblocks,distrb_info%nprocs)
190 36 : call get_ice_timer(timer_fsd, 'FloeSize', nblocks,distrb_info%nprocs)
191 36 : call get_ice_timer(timer_couple, 'Coupling', nblocks,distrb_info%nprocs)
192 36 : call get_ice_timer(timer_readwrite,'ReadWrite',nblocks,distrb_info%nprocs)
193 36 : call get_ice_timer(timer_diags, 'Diags ',nblocks,distrb_info%nprocs)
194 36 : call get_ice_timer(timer_hist, 'History ',nblocks,distrb_info%nprocs)
195 36 : call get_ice_timer(timer_bound, 'Bound', nblocks,distrb_info%nprocs)
196 36 : call get_ice_timer(timer_bundbound,'Bundbound',nblocks,distrb_info%nprocs)
197 36 : call get_ice_timer(timer_bgc, 'BGC', nblocks,distrb_info%nprocs)
198 36 : call get_ice_timer(timer_forcing, 'Forcing', nblocks,distrb_info%nprocs)
199 : #if (defined CESMCOUPLED)
200 : call get_ice_timer(timer_cplrecv, 'Cpl-recv', nblocks,distrb_info%nprocs)
201 : call get_ice_timer(timer_rcvsnd, 'Rcv->Snd', nblocks,distrb_info%nprocs)
202 : call get_ice_timer(timer_cplsend, 'Cpl-Send', nblocks,distrb_info%nprocs)
203 : call get_ice_timer(timer_sndrcv, 'Snd->Rcv', nblocks,distrb_info%nprocs)
204 : #endif
205 36 : call get_ice_timer(timer_evp_1d, '1d-evp', nblocks,distrb_info%nprocs)
206 36 : call get_ice_timer(timer_evp_2d, '2d-evp', nblocks,distrb_info%nprocs)
207 36 : call get_ice_timer(timer_updstate, 'UpdState', nblocks,distrb_info%nprocs)
208 : ! call get_ice_timer(timer_tmp1, 'tmp1', nblocks,distrb_info%nprocs)
209 : ! call get_ice_timer(timer_tmp2, 'tmp2', nblocks,distrb_info%nprocs)
210 : ! call get_ice_timer(timer_tmp3, 'tmp3', nblocks,distrb_info%nprocs)
211 : ! call get_ice_timer(timer_tmp4, 'tmp4', nblocks,distrb_info%nprocs)
212 : ! call get_ice_timer(timer_tmp5, 'tmp5', nblocks,distrb_info%nprocs)
213 : ! call get_ice_timer(timer_tmp6, 'tmp6', nblocks,distrb_info%nprocs)
214 : ! call get_ice_timer(timer_tmp7, 'tmp7', nblocks,distrb_info%nprocs)
215 : ! call get_ice_timer(timer_tmp8, 'tmp8', nblocks,distrb_info%nprocs)
216 : ! call get_ice_timer(timer_tmp9, 'tmp9', nblocks,distrb_info%nprocs)
217 :
218 : !-----------------------------------------------------------------------
219 :
220 36 : end subroutine init_ice_timers
221 :
222 : !***********************************************************************
223 :
224 720 : subroutine get_ice_timer(timer_id, name_choice, num_blocks, num_nodes)
225 :
226 : ! This routine initializes a timer with a given name and returns a
227 : ! timer id.
228 :
229 : character (*), intent(in) :: &
230 : name_choice ! input name for this timer
231 :
232 : integer (int_kind), intent(in) :: &
233 : num_nodes, &! number of nodes(tasks) using this timer ! LCOV_EXCL_LINE
234 : num_blocks ! number of blocks using this timer
235 : ! (can be =1 if timer called outside
236 : ! threaded region)
237 :
238 : integer (int_kind), intent(out) :: &
239 : timer_id ! timer number assigned to this timer
240 :
241 : !-----------------------------------------------------------------------
242 : !
243 : ! local variables
244 : !
245 : !-----------------------------------------------------------------------
246 :
247 : integer (int_kind) :: &
248 : n, &! dummy loop index ! LCOV_EXCL_LINE
249 : srch_error ! error flag for search
250 :
251 : character(len=*), parameter :: subname = '(get_ice_timer)'
252 :
253 : !-----------------------------------------------------------------------
254 : !
255 : ! search for next free timer
256 : !
257 : !-----------------------------------------------------------------------
258 :
259 720 : srch_error = 1
260 :
261 7560 : srch_loop: do n=1,max_timers
262 7560 : if (.not. all_timers(n)%in_use) then
263 720 : srch_error = 0
264 720 : timer_id = n
265 :
266 720 : all_timers(n)%name = ' '
267 720 : all_timers(n)%name = name_choice
268 720 : all_timers(n)%in_use = .true.
269 720 : all_timers(n)%num_blocks = num_blocks
270 720 : all_timers(n)%num_nodes = num_nodes
271 :
272 160 : allocate(all_timers(n)%block_started (num_blocks), &
273 : all_timers(n)%block_cycles1 (num_blocks), & ! LCOV_EXCL_LINE
274 : all_timers(n)%block_cycles2 (num_blocks), & ! LCOV_EXCL_LINE
275 1040 : all_timers(n)%block_accum_time(num_blocks))
276 :
277 3900 : all_timers(n)%block_started = .false.
278 3900 : all_timers(n)%block_cycles1 = c0
279 3900 : all_timers(n)%block_cycles2 = c0
280 3900 : all_timers(n)%block_accum_time = c0
281 :
282 720 : exit srch_loop
283 : endif
284 : end do srch_loop
285 :
286 720 : if (srch_error /= 0) &
287 0 : call abort_ice(subname//'ERROR: Exceeded maximum number of timers')
288 :
289 :
290 : !-----------------------------------------------------------------------
291 :
292 720 : end subroutine get_ice_timer
293 :
294 : !***********************************************************************
295 :
296 0 : subroutine ice_timer_clear(timer_id)
297 :
298 : ! This routine resets the time for a timer which has already been
299 : ! defined. NOTE: This routine must be called from outside a threaded
300 : ! region to ensure correct reset of block timers.
301 :
302 : integer (int_kind), intent(in) :: &
303 : timer_id ! timer number
304 :
305 : character(len=*), parameter :: subname = '(ice_timer_clear)'
306 :
307 : !-----------------------------------------------------------------------
308 : !
309 : ! if the timer has been defined, reset all times to 0
310 : ! otherwise exit with an error
311 : !
312 : !-----------------------------------------------------------------------
313 :
314 0 : if (all_timers(timer_id)%in_use) then
315 0 : all_timers(timer_id)%node_started = .false.
316 0 : all_timers(timer_id)%num_starts = 0
317 0 : all_timers(timer_id)%num_stops = 0
318 0 : all_timers(timer_id)%node_cycles1 = c0
319 0 : all_timers(timer_id)%node_cycles2 = c0
320 :
321 0 : all_timers(timer_id)%node_accum_time = c0
322 :
323 0 : all_timers(timer_id)%block_started(:) = .false.
324 0 : all_timers(timer_id)%block_cycles1(:) = c0
325 0 : all_timers(timer_id)%block_cycles2(:) = c0
326 0 : all_timers(timer_id)%block_accum_time(:) = c0
327 : else
328 0 : call abort_ice(subname//'ERROR: attempt to reset undefined timer')
329 :
330 : endif
331 :
332 : !-----------------------------------------------------------------------
333 :
334 0 : end subroutine ice_timer_clear
335 :
336 : !***********************************************************************
337 :
338 2130948 : subroutine ice_timer_start(timer_id, block_id)
339 :
340 : ! This routine starts a given node timer if it has not already
341 : ! been started by another thread. If block information is available,
342 : ! the appropriate block timer is also started.
343 :
344 : integer (int_kind), intent(in) :: &
345 : timer_id ! timer number
346 :
347 : integer (int_kind), intent(in), optional :: &
348 : block_id ! optional block id for this block
349 : ! this must be the actual local address
350 : ! of the block in the distribution
351 : ! from which it is called
352 : ! (if timer called outside of block
353 : ! region, no block info required)
354 :
355 : double precision MPI_WTIME
356 : external MPI_WTIME
357 :
358 : character(len=*), parameter :: subname = '(ice_timer_start)'
359 :
360 : ! if (my_task == master_task) write(nu_diag,*) subname,trim(all_timers(timer_id)%name)
361 : !-----------------------------------------------------------------------
362 : !
363 : ! if timer is defined, start it up
364 : !
365 : !-----------------------------------------------------------------------
366 :
367 2130948 : if (all_timers(timer_id)%in_use) then
368 :
369 : !***
370 : !*** if called from within a block loop, start block timers
371 : !***
372 :
373 2130948 : if (present(block_id)) then
374 :
375 : !*** if block timer already started, stop it first
376 :
377 114600 : if (all_timers(timer_id)%block_started(block_id)) &
378 0 : call ice_timer_stop(timer_id, block_id)
379 :
380 : !*** start block timer
381 :
382 114600 : all_timers(timer_id)%block_started(block_id) = .true.
383 114600 : all_timers(timer_id)%block_cycles1(block_id) = MPI_WTIME()
384 :
385 : !*** start node timer if not already started by
386 : !*** another thread. if already started, keep track
387 : !*** of number of start requests in order to match
388 : !*** start and stop requests
389 :
390 85800 : !$OMP CRITICAL
391 :
392 114600 : if (.not. all_timers(timer_id)%node_started) then
393 76486 : all_timers(timer_id)%node_started = .true.
394 76486 : all_timers(timer_id)%num_starts = 1
395 76486 : all_timers(timer_id)%num_stops = 0
396 76486 : all_timers(timer_id)%node_cycles1 = MPI_WTIME()
397 : else
398 14448 : all_timers(timer_id)%num_starts = &
399 52562 : all_timers(timer_id)%num_starts + 1
400 : endif
401 :
402 : !$OMP END CRITICAL
403 :
404 : !***
405 : !*** if called from outside a block loop, start node timer
406 : !***
407 :
408 : else
409 :
410 : !*** stop timer if already started
411 2016348 : if (all_timers(timer_id)%node_started) &
412 0 : call ice_timer_stop(timer_id)
413 :
414 : !*** start node timer
415 :
416 2016348 : all_timers(timer_id)%node_started = .true.
417 2016348 : all_timers(timer_id)%node_cycles1 = MPI_WTIME()
418 :
419 : endif
420 : else
421 0 : call abort_ice(subname//'ERROR: attempt to start undefined timer')
422 :
423 : endif
424 :
425 : !-----------------------------------------------------------------------
426 :
427 2130948 : end subroutine ice_timer_start
428 :
429 : !***********************************************************************
430 :
431 2130948 : subroutine ice_timer_stop(timer_id, block_id)
432 :
433 : ! This routine stops a given node timer if appropriate. If block
434 : ! information is available the appropriate block timer is also stopped.
435 :
436 : integer (int_kind), intent(in) :: &
437 : timer_id ! timer number
438 :
439 : integer (int_kind), intent(in), optional :: &
440 : block_id ! optional block id for this block
441 : ! this must be the actual local address
442 : ! of the block in the distribution
443 : ! from which it is called
444 : ! (if timer called outside of block
445 : ! region, no block info required)
446 :
447 : double precision MPI_WTIME
448 : external MPI_WTIME
449 :
450 : !-----------------------------------------------------------------------
451 : !
452 : ! local variables
453 : !
454 : !-----------------------------------------------------------------------
455 :
456 : real (dbl_kind) :: &
457 417664 : cycles1, cycles2 ! temps to hold cycle info before correction
458 :
459 : character(len=*), parameter :: subname = '(ice_timer_stop)'
460 :
461 : ! if (my_task == master_task) write(nu_diag,*) subname,trim(all_timers(timer_id)%name)
462 : !-----------------------------------------------------------------------
463 : !
464 : ! get end cycles
465 : !
466 : !-----------------------------------------------------------------------
467 :
468 2130948 : cycles2 = MPI_WTIME()
469 :
470 : !-----------------------------------------------------------------------
471 : !
472 : ! if timer is defined, stop it
473 : !
474 : !-----------------------------------------------------------------------
475 :
476 2130948 : if (all_timers(timer_id)%in_use) then
477 :
478 : !***
479 : !*** if called from within a block loop, stop block timer
480 : !***
481 :
482 2130948 : if (present(block_id)) then
483 :
484 114600 : all_timers(timer_id)%block_started(block_id) = .false.
485 :
486 114600 : cycles1 = all_timers(timer_id)%block_cycles1(block_id)
487 28800 : all_timers(timer_id)%block_accum_time(block_id) = &
488 : all_timers(timer_id)%block_accum_time(block_id) + & ! LCOV_EXCL_LINE
489 172200 : clock_rate*(cycles2 - cycles1)
490 :
491 : !*** stop node timer if number of requested stops
492 : !*** matches the number of starts (to avoid stopping
493 : !*** a node timer started by multiple threads)
494 :
495 114600 : cycles1 = all_timers(timer_id)%node_cycles1
496 :
497 85800 : !$OMP CRITICAL
498 :
499 28800 : all_timers(timer_id)%num_stops = &
500 143400 : all_timers(timer_id)%num_stops + 1
501 :
502 114600 : if (all_timers(timer_id)%num_starts == &
503 : all_timers(timer_id)%num_stops) then
504 :
505 76486 : all_timers(timer_id)%node_started = .false.
506 14352 : all_timers(timer_id)%node_accum_time = &
507 : all_timers(timer_id)%node_accum_time + & ! LCOV_EXCL_LINE
508 90838 : clock_rate*(cycles2 - cycles1)
509 :
510 76486 : all_timers(timer_id)%num_starts = 0
511 76486 : all_timers(timer_id)%num_stops = 0
512 :
513 : endif
514 :
515 : !$OMP END CRITICAL
516 :
517 : !***
518 : !*** if called from outside a block loop, stop node timer
519 : !***
520 :
521 : else
522 :
523 2016348 : all_timers(timer_id)%node_started = .false.
524 2016348 : cycles1 = all_timers(timer_id)%node_cycles1
525 :
526 388864 : all_timers(timer_id)%node_accum_time = &
527 : all_timers(timer_id)%node_accum_time + & ! LCOV_EXCL_LINE
528 2794076 : clock_rate*(cycles2 - cycles1)
529 :
530 : endif
531 : else
532 0 : call abort_ice(subname//'ERROR: attempt to stop undefined timer')
533 :
534 : endif
535 :
536 : !-----------------------------------------------------------------------
537 :
538 2130948 : end subroutine ice_timer_stop
539 :
540 : !***********************************************************************
541 :
542 720 : subroutine ice_timer_print(timer_id,stats)
543 :
544 : ! Prints the accumulated time for a given timer and optional
545 : ! statistics for that timer. It is assumed that this routine
546 : ! is called outside of a block loop.
547 :
548 : integer (int_kind), intent(in) :: &
549 : timer_id ! timer number
550 :
551 : logical (log_kind), intent(in), optional :: &
552 : stats ! if true, print statistics for node
553 : ! and block times for this timer
554 :
555 : !-----------------------------------------------------------------------
556 : !
557 : ! local variables
558 : !
559 : !-----------------------------------------------------------------------
560 :
561 : integer (int_kind) :: &
562 : n,icount, & ! dummy loop index and counter ! LCOV_EXCL_LINE
563 : nBlocks
564 :
565 : logical (log_kind) :: &
566 : lrestart_timer ! flag to restart timer if timer is running
567 : ! when this routine is called
568 :
569 : real (dbl_kind) :: &
570 : bignum, &! big num ! LCOV_EXCL_LINE
571 : local_time, &! temp space for holding local timer results ! LCOV_EXCL_LINE
572 : min_time, &! minimum accumulated time ! LCOV_EXCL_LINE
573 : max_time, &! maximum accumulated time ! LCOV_EXCL_LINE
574 160 : mean_time ! mean accumulated time
575 :
576 : character (41), parameter :: &
577 : timer_format = "('Timer ',i3,': ',a9,f11.2,' seconds')"
578 :
579 : character (49), parameter :: &
580 : stats_fmt1 = "(' Timer stats (node): min = ',f11.2,' seconds')",& ! LCOV_EXCL_LINE
581 : stats_fmt2 = "(' max = ',f11.2,' seconds')",& ! LCOV_EXCL_LINE
582 : stats_fmt3 = "(' mean= ',f11.2,' seconds')",& ! LCOV_EXCL_LINE
583 : stats_fmt4 = "(' Timer stats(block): min = ',f11.2,' seconds')"
584 :
585 : character(len=*), parameter :: subname = '(ice_timer_print)'
586 :
587 : !-----------------------------------------------------------------------
588 : !
589 : ! if timer has been defined, check to see whether it is currently
590 : ! running. If it is, stop the timer and print the info.
591 : !
592 : !-----------------------------------------------------------------------
593 :
594 720 : call icepack_query_parameters(bignum_out=bignum)
595 720 : call icepack_warnings_flush(nu_diag)
596 720 : if (icepack_warnings_aborted()) call abort_ice(error_message=subname, &
597 0 : file=__FILE__, line=__LINE__)
598 :
599 720 : if (all_timers(timer_id)%in_use) then
600 720 : if (all_timers(timer_id)%node_started) then
601 0 : call ice_timer_stop(timer_id)
602 0 : lrestart_timer = .true.
603 : else
604 720 : lrestart_timer = .false.
605 : endif
606 :
607 : !*** Find max node time and print that time as default timer
608 : !*** result
609 :
610 720 : if (my_task < all_timers(timer_id)%num_nodes) then
611 720 : local_time = all_timers(timer_id)%node_accum_time
612 : else
613 0 : local_time = c0
614 : endif
615 720 : max_time = global_maxval(local_time,distrb_info)
616 :
617 720 : if (my_task == master_task) then
618 120 : write (nu_diag,timer_format) timer_id, &
619 240 : trim(all_timers(timer_id)%name),max_time
620 : endif
621 :
622 720 : if (present(stats)) then
623 720 : if (stats) then
624 :
625 : !*** compute and print statistics for node timer
626 :
627 0 : min_time = global_minval(local_time,distrb_info)
628 : mean_time = global_sum(local_time,distrb_info)/ &
629 0 : real(all_timers(timer_id)%num_nodes,kind=dbl_kind)
630 0 : if (my_task == master_task) then
631 0 : write (nu_diag,stats_fmt1) min_time
632 0 : write (nu_diag,stats_fmt2) max_time
633 0 : write (nu_diag,stats_fmt3) mean_time
634 : endif
635 :
636 : !*** compute and print statistics for block timers
637 : !*** min block time
638 :
639 0 : local_time = bignum
640 0 : do n=1,all_timers(timer_id)%num_blocks
641 : local_time = min(local_time, &
642 0 : all_timers(timer_id)%block_accum_time(n))
643 : end do
644 0 : min_time = global_minval(local_time,distrb_info)
645 0 : if (min_time == bignum) min_time = c0
646 :
647 : !*** max block time
648 :
649 0 : local_time = -bignum
650 0 : do n=1,all_timers(timer_id)%num_blocks
651 : local_time = max(local_time, &
652 0 : all_timers(timer_id)%block_accum_time(n))
653 : end do
654 0 : max_time = global_maxval(local_time,distrb_info)
655 0 : if (max_time == -bignum) min_time = c0
656 :
657 : !*** mean block time
658 :
659 0 : local_time = c0
660 0 : nBlocks = all_timers(timer_id)%num_blocks
661 0 : do n=1,nBlocks
662 : local_time = local_time + &
663 0 : all_timers(timer_id)%block_accum_time(n)
664 : end do
665 0 : icount = global_sum(nBlocks, distrb_info)
666 0 : if (icount > 0) mean_time=global_sum(local_time,distrb_info)&
667 0 : /real(icount,kind=dbl_kind)
668 :
669 0 : if (my_task == master_task) then
670 0 : write (nu_diag,stats_fmt4) min_time
671 0 : write (nu_diag,stats_fmt2) max_time
672 0 : write (nu_diag,stats_fmt3) mean_time
673 : endif
674 :
675 : endif
676 : endif
677 :
678 720 : if (lrestart_timer) call ice_timer_start(timer_id)
679 : else
680 0 : call abort_ice(subname//'ERROR: attempt to print undefined timer')
681 : endif
682 :
683 : !-----------------------------------------------------------------------
684 :
685 720 : end subroutine ice_timer_print
686 :
687 : !***********************************************************************
688 :
689 36 : subroutine ice_timer_print_all(stats)
690 :
691 : ! Prints the accumulated time for a all timers and optional
692 : ! statistics for that timer. It is assumed that this routine
693 : ! is called outside of a block loop.
694 :
695 : logical (log_kind), intent(in), optional :: &
696 : stats ! if true, print statistics for node
697 : ! and block times for this timer
698 :
699 : !-----------------------------------------------------------------------
700 : !
701 : ! local variables
702 : !
703 : !-----------------------------------------------------------------------
704 :
705 : integer (int_kind) :: n ! dummy loop index
706 :
707 : character(len=*), parameter :: subname = '(ice_timer_print_all)'
708 :
709 : !-----------------------------------------------------------------------
710 : !
711 : ! loop through timers anc call timer_print for each defined timer
712 : !
713 : !-----------------------------------------------------------------------
714 :
715 36 : if (my_task == master_task) then
716 6 : write(nu_diag,'(/,a19,/)') 'Timing information:'
717 : endif
718 :
719 1836 : do n=1,max_timers
720 1836 : if (all_timers(n)%in_use) then
721 720 : if (present(stats)) then
722 720 : call ice_timer_print(n,stats)
723 : else
724 0 : call ice_timer_print(n)
725 : endif
726 : endif
727 : end do
728 :
729 : !-----------------------------------------------------------------------
730 :
731 36 : end subroutine ice_timer_print_all
732 :
733 : !***********************************************************************
734 :
735 0 : subroutine ice_timer_check(timer_id,block_id)
736 :
737 : ! This routine checks a given timer by stopping and restarting the
738 : ! timer. This is primarily used to periodically accumulate time in
739 : ! the timer to prevent timer cycles from wrapping around max_cycles.
740 :
741 : integer (int_kind), intent(in) :: &
742 : timer_id ! timer number
743 :
744 : integer (int_kind), intent(in), optional :: &
745 : block_id ! optional block id for this block
746 : ! this must be the actual local address
747 : ! of the block in the distribution
748 : ! from which it is called
749 : ! (if timer called outside of block
750 : ! region, no block info required)
751 :
752 : character(len=*), parameter :: subname = '(ice_timer_check)'
753 :
754 : !-----------------------------------------------------------------------
755 : !
756 : ! stop and restart the requested timer
757 : !
758 : !-----------------------------------------------------------------------
759 :
760 0 : if (present(block_id)) then
761 0 : call ice_timer_stop (timer_id,block_id)
762 0 : call ice_timer_start(timer_id,block_id)
763 : else
764 0 : call ice_timer_stop (timer_id)
765 0 : call ice_timer_start(timer_id)
766 : endif
767 :
768 : !-----------------------------------------------------------------------
769 :
770 0 : end subroutine ice_timer_check
771 :
772 : !***********************************************************************
773 :
774 0 : end module ice_timers
775 :
776 : !|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
|