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.
timing.F90 in branches/2011/dev_NEMO_MERGE_2011/NEMOGCM/NEMO/OPA_SRC – NEMO

source: branches/2011/dev_NEMO_MERGE_2011/NEMOGCM/NEMO/OPA_SRC/timing.F90 @ 3222

Last change on this file since 3222 was 3222, checked in by rblod, 12 years ago

Correct a bug in timing with more than 2 levels of imbrication

  • Property svn:executable set to *
  • Property svn:keywords set to Id
File size: 30.8 KB
Line 
1MODULE timing
2   !!========================================================================
3   !!                     ***  MODULE  timing  ***
4   !!========================================================================
5   !! History : 4.0  ! 2001-05  (R. Benshila)   
6   !!------------------------------------------------------------------------
7
8   !!------------------------------------------------------------------------
9   !!   timming_init    : initialize timing process
10   !!   timing_start    : start Timer
11   !!   timing_stop     : stop  Timer
12   !!   timing_reset    : end timing variable creation
13   !!   timing_finalize : compute stats and write output in calling w*_info
14   !!   timing_ini_var  : create timing variables
15   !!   timing_listing  : print instumented subroutines in ocean.output
16   !!   wcurrent_info   : compute and print detailed stats on the current CPU
17   !!   wave_info       : compute and print averaged statson all processors
18   !!   wmpi_info       : compute and write global stats 
19   !!   supress         : suppress an element of the timing linked list 
20   !!   insert          : insert an element of the timing linked list 
21   !!------------------------------------------------------------------------
22   USE in_out_manager  ! I/O manager
23   USE dom_oce         ! ocean domain
24   USE lib_mpp         
25   
26   IMPLICIT NONE
27   PRIVATE
28
29   PUBLIC   timing_init, timing_finalize   ! called in nemogcm module
30   PUBLIC   timing_reset                   ! called in step module
31   PUBLIC   timing_start, timing_stop      ! called in each routine to time
32   
33#if defined key_mpp_mpi
34   INCLUDE 'mpif.h'
35#endif
36
37   ! Variables for fine grain timing
38   TYPE timer
39      CHARACTER(LEN=20)  :: cname
40        REAL(wp)  :: t_cpu, t_clock, tsum_cpu, tsum_clock, tmax_cpu, tmax_clock, tmin_cpu, tmin_clock, tsub_cpu, tsub_clock
41      INTEGER :: ncount, ncount_max, ncount_rate 
42      INTEGER :: niter
43      LOGICAL :: l_tdone
44      TYPE(timer), POINTER :: next => NULL()
45      TYPE(timer), POINTER :: prev => NULL()
46      TYPE(timer), POINTER :: parent_section => NULL()
47   END TYPE timer
48   
49   TYPE alltimer
50      CHARACTER(LEN=20), DIMENSION(:), POINTER :: cname => NULL()
51        REAL(wp), DIMENSION(:), POINTER :: tsum_cpu   => NULL()
52        REAL(wp), DIMENSION(:), POINTER :: tsum_clock => NULL()
53        INTEGER, DIMENSION(:), POINTER :: niter => NULL()
54      TYPE(alltimer), POINTER :: next => NULL()
55      TYPE(alltimer), POINTER :: prev => NULL()
56   END TYPE alltimer 
57 
58   TYPE(timer), POINTER :: s_timer_root => NULL()
59   TYPE(timer), POINTER :: s_timer      => NULL()
60   TYPE(timer), POINTER :: s_wrk        => NULL()
61   REAL(wp) :: t_overclock, t_overcpu
62   LOGICAL :: l_initdone = .FALSE.
63   INTEGER :: nsize
64   
65   ! Variables for coarse grain timing
66   REAL(wp) :: tot_etime, tot_ctime
67   REAL(kind=wp), DIMENSION(2)     :: t_elaps, t_cpu
68   REAL(wp), ALLOCATABLE, DIMENSION(:) :: all_etime, all_ctime
69   INTEGER :: nfinal_count, ncount, ncount_rate, ncount_max
70   INTEGER, DIMENSION(8)           :: nvalues
71   CHARACTER(LEN=8), DIMENSION(2)  :: cdate
72   CHARACTER(LEN=10), DIMENSION(2) :: ctime
73   CHARACTER(LEN=5)                :: czone
74   
75   ! From of ouput file (1/proc or one global)   !RB to put in nammpp or namctl
76   LOGICAL :: ln_onefile = .TRUE. 
77   LOGICAL :: lwriter
78
79   !!----------------------------------------------------------------------
80   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
81   !! $Id$
82   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
83   !!----------------------------------------------------------------------
84CONTAINS
85
86   SUBROUTINE timing_start(cdinfo)
87      !!----------------------------------------------------------------------
88      !!               ***  ROUTINE timing_start  ***
89      !! ** Purpose :   collect execution time
90      !!----------------------------------------------------------------------
91      CHARACTER(len=*), INTENT(in) :: cdinfo
92      !
93       
94      ! Create timing structure at first call
95      IF( .NOT. l_initdone ) THEN
96         CALL timing_ini_var(cdinfo)
97      ELSE
98         s_timer => s_timer_root
99         DO WHILE( TRIM(s_timer%cname) /= TRIM(cdinfo) ) 
100            IF( ASSOCIATED(s_timer%next) ) s_timer => s_timer%next
101         END DO
102      ENDIF         
103      s_timer%l_tdone = .FALSE.
104      s_timer%niter = s_timer%niter + 1
105      s_timer%t_cpu = 0.
106      s_timer%t_clock = 0.
107                 
108      ! CPU time collection
109      CALL CPU_TIME( s_timer%t_cpu  )
110      ! clock time collection
111#if defined key_mpp_mpi
112      s_timer%t_clock= MPI_Wtime()
113#else
114      CALL SYSTEM_CLOCK(COUNT_RATE=s_timer%ncount_rate, COUNT_MAX=s_timer%ncount_max)
115      CALL SYSTEM_CLOCK(COUNT = s_timer%ncount)
116#endif
117      !
118   END SUBROUTINE timing_start
119
120
121   SUBROUTINE timing_stop(cdinfo, csection)
122      !!----------------------------------------------------------------------
123      !!               ***  ROUTINE timing_stop  ***
124      !! ** Purpose :   finalize timing and output
125      !!----------------------------------------------------------------------
126      CHARACTER(len=*), INTENT(in) :: cdinfo
127      CHARACTER(len=*), INTENT(in), OPTIONAL :: csection
128      !
129      INTEGER  :: ifinal_count, iperiods   
130      REAL(wp) :: zcpu_end, zmpitime
131      !
132      s_wrk => NULL()
133
134      ! clock time collection
135#if defined key_mpp_mpi
136      zmpitime = MPI_Wtime()
137#else
138      CALL SYSTEM_CLOCK(COUNT = ifinal_count)
139#endif
140      ! CPU time collection
141      CALL CPU_TIME( zcpu_end )
142
143      s_timer => s_timer_root
144      DO WHILE( TRIM(s_timer%cname) /= TRIM(cdinfo) ) 
145         IF( ASSOCIATED(s_timer%next) ) s_timer => s_timer%next
146      END DO
147 
148      ! CPU time correction
149      s_timer%t_cpu  = zcpu_end - s_timer%t_cpu - t_overcpu - s_timer%tsub_cpu
150 
151      ! clock time correction
152#if defined key_mpp_mpi
153      s_timer%t_clock = zmpitime - s_timer%t_clock - t_overclock - s_timer%tsub_clock
154#else
155      iperiods = ifinal_count - s_timer%ncount
156      IF( ifinal_count < s_timer%ncount )  &
157          iperiods = iperiods + s_timer%ncount_max 
158      s_timer%t_clock  = REAL(iperiods) / s_timer%ncount_rate - t_overclock - s_timer%tsub_clock
159#endif
160     
161      ! Correction of parent section
162      IF( .NOT. PRESENT(csection) ) THEN
163         s_wrk => s_timer
164         DO WHILE ( ASSOCIATED(s_wrk%parent_section ) )
165            s_wrk => s_wrk%parent_section
166            s_wrk%tsub_cpu   = s_wrk%tsub_cpu   + s_timer%t_cpu 
167            s_wrk%tsub_clock = s_wrk%tsub_clock + s_timer%t_clock             
168         END DO
169      ENDIF
170           
171      ! time diagnostics
172      s_timer%tsum_clock = s_timer%tsum_clock + s_timer%t_clock 
173      s_timer%tsum_cpu   = s_timer%tsum_cpu   + s_timer%t_cpu
174!RB to use to get min/max during a time integration
175!      IF( .NOT. l_initdone ) THEN
176!         s_timer%tmin_clock = s_timer%t_clock
177!         s_timer%tmin_cpu   = s_timer%t_cpu
178!      ELSE
179!         s_timer%tmin_clock = MIN( s_timer%tmin_clock, s_timer%t_clock )
180!         s_timer%tmin_cpu   = MIN( s_timer%tmin_cpu  , s_timer%t_cpu   )
181!      ENDIF   
182!      s_timer%tmax_clock = MAX( s_timer%tmax_clock, s_timer%t_clock )
183!      s_timer%tmax_cpu   = MAX( s_timer%tmax_cpu  , s_timer%t_cpu   ) 
184      !
185      s_timer%tsub_clock = 0.
186      s_timer%tsub_cpu = 0.
187      s_timer%l_tdone = .TRUE.
188      !
189   END SUBROUTINE timing_stop
190 
191 
192   SUBROUTINE timing_init
193      !!----------------------------------------------------------------------
194      !!               ***  ROUTINE timing_init  ***
195      !! ** Purpose :   open timing output file
196      !!----------------------------------------------------------------------
197      INTEGER :: iperiods, istart_count, ifinal_count
198      REAL(wp) :: zdum
199      LOGICAL :: ll_f
200             
201      IF( ln_onefile ) THEN
202         IF( lwp) CALL ctl_opn( numtime, 'timing.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout,.TRUE., narea )
203         lwriter = lwp
204      ELSE
205         CALL ctl_opn( numtime, 'timing.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout,.FALSE., narea )
206         lwriter = .TRUE.
207      ENDIF
208     
209      IF( lwriter) THEN     
210         WRITE(numtime,*)
211         WRITE(numtime,*) '      CNRS - NERC - Met OFFICE - MERCATOR-ocean - CMCC - INGV'
212         WRITE(numtime,*) '                             NEMO team'
213         WRITE(numtime,*) '                  Ocean General Circulation Model'
214         WRITE(numtime,*) '                        version 3.3  (2010) '
215         WRITE(numtime,*)
216         WRITE(numtime,*) '                        Timing Informations '
217         WRITE(numtime,*)
218         WRITE(numtime,*)
219      ENDIF   
220     
221      ! Compute clock function overhead
222#if defined key_mpp_mpi       
223      t_overclock = MPI_WTIME()
224      t_overclock = MPI_WTIME() - t_overclock
225#else       
226      CALL SYSTEM_CLOCK(COUNT_RATE=ncount_rate, COUNT_MAX=ncount_max)
227      CALL SYSTEM_CLOCK(COUNT = istart_count)
228      CALL SYSTEM_CLOCK(COUNT = ifinal_count)
229      iperiods = ifinal_count - istart_count
230      IF( ifinal_count < istart_count )  &
231          iperiods = iperiods + ncount_max 
232      t_overclock = REAL(iperiods) / ncount_rate
233#endif
234
235      ! Compute cpu_time function overhead
236      CALL CPU_TIME(zdum)
237      CALL CPU_TIME(t_overcpu)
238     
239      ! End overhead omputation 
240      t_overcpu = t_overcpu - zdum       
241      t_overclock = t_overcpu + t_overclock       
242
243      ! Timing on date and time
244      CALL DATE_AND_TIME(cdate(1),ctime(1),czone,nvalues)
245   
246      CALL CPU_TIME(t_cpu(1))     
247#if defined key_mpp_mpi       
248      ! Start elapsed and CPU time counters
249      t_elaps(1) = MPI_WTIME()
250#else
251      CALL SYSTEM_CLOCK(COUNT_RATE=ncount_rate, COUNT_MAX=ncount_max)
252      CALL SYSTEM_CLOCK(COUNT = ncount)
253#endif                 
254      !
255   END SUBROUTINE timing_init
256
257
258   SUBROUTINE timing_finalize
259      !!----------------------------------------------------------------------
260      !!               ***  ROUTINE timing_finalize ***
261      !! ** Purpose :  compute average time
262      !!               write timing output file
263      !!----------------------------------------------------------------------
264      TYPE(timer), POINTER :: s_temp
265      INTEGER :: idum, iperiods, icode
266      LOGICAL :: ll_ord, ll_averep
267      CHARACTER(len=120) :: clfmt           
268     
269      ll_averep = .TRUE.
270   
271      ! total CPU and elapse
272      CALL CPU_TIME(t_cpu(2))
273      t_cpu(2)   = t_cpu(2)    - t_cpu(1)   - t_overcpu
274#if defined key_mpp_mpi
275      t_elaps(2) = MPI_WTIME() - t_elaps(1) - t_overclock
276#else
277      CALL SYSTEM_CLOCK(COUNT = nfinal_count)
278      iperiods = nfinal_count - ncount
279      IF( nfinal_count < ncount )  &
280          iperiods = iperiods + ncount_max 
281      t_elaps(2) = REAL(iperiods) / ncount_rate - t_overclock
282#endif     
283
284      ! End of timings on date & time
285      CALL DATE_AND_TIME(cdate(2),ctime(2),czone,nvalues)
286       
287      ! Compute the numer of routines
288      nsize = 0 
289      s_timer => s_timer_root
290      DO WHILE( ASSOCIATED(s_timer) )
291         nsize = nsize + 1
292         s_timer => s_timer%next
293      END DO
294      idum = nsize
295      IF(lk_mpp) CALL mpp_sum(idum)
296      IF( idum/jpnij /= nsize ) THEN
297         IF( lwriter ) WRITE(numtime,*) '        ===> W A R N I N G: '
298         IF( lwriter ) WRITE(numtime,*) ' Some CPU have different number of routines instrumented for timing'
299         IF( lwriter ) WRITE(numtime,*) ' No detailed report on averaged timing can be provided'
300         IF( lwriter ) WRITE(numtime,*) ' The following detailed report only deals with the current processor'
301         IF( lwriter ) WRITE(numtime,*)
302         ll_averep = .FALSE.
303      ENDIF   
304
305#if defined key_mpp_mpi     
306      ! in MPI gather some info
307      ALLOCATE( all_etime(jpnij), all_ctime(jpnij) )
308      CALL MPI_ALLGATHER(t_elaps(2), 1, MPI_DOUBLE_PRECISION,   &
309                         all_etime , 1, MPI_DOUBLE_PRECISION,   &
310                         MPI_COMM_OPA, icode)
311      CALL MPI_ALLGATHER(t_cpu(2) , 1, MPI_DOUBLE_PRECISION,   &
312                         all_ctime, 1, MPI_DOUBLE_PRECISION,   &
313                         MPI_COMM_OPA, icode)
314      tot_etime = SUM(all_etime(:))
315      tot_ctime = SUM(all_ctime(:))
316#else
317      tot_etime = t_elaps(2)
318      tot_ctime = t_cpu  (2)           
319#endif
320
321      ! write output file
322      IF( lwriter ) WRITE(numtime,*) 'Total timing (sum) :'
323      IF( lwriter ) WRITE(numtime,*) '--------------------'
324      IF( lwriter ) WRITE(numtime,*) 'Elapsed Time (s)  ','CPU Time (s)'
325      IF( lwriter ) WRITE(numtime,'(5x,f12.3,2x,f12.3)')  tot_etime, tot_ctime
326      IF( lwriter ) WRITE(numtime,*) 
327#if defined key_mpp_mpi
328      IF( ll_averep ) CALL waver_info
329      CALL wmpi_info
330#endif     
331      IF( lwriter ) CALL wcurrent_info
332     
333      clfmt='(1X,"Timing started on ",2(A2,"/"),A4," at ",2(A2,":"),A2," MET ",A3,":",A2," from GMT")'
334      IF( lwriter ) WRITE(numtime, TRIM(clfmt)) &           
335      &       cdate(1)(7:8), cdate(1)(5:6), cdate(1)(1:4),   &
336      &       ctime(1)(1:2), ctime(1)(3:4), ctime(1)(5:6),   &
337      &       czone(1:3),    czone(4:5)                     
338      clfmt='(1X,  "Timing   ended on ",2(A2,"/"),A4," at ",2(A2,":"),A2," MET ",A3,":",A2," from GMT")'
339      IF( lwriter ) WRITE(numtime, TRIM(clfmt)) &           
340      &       cdate(2)(7:8), cdate(2)(5:6), cdate(2)(1:4),   &
341      &       ctime(2)(1:2), ctime(2)(3:4), ctime(2)(5:6),   &
342      &       czone(1:3),    czone(4:5)
343
344      IF( lwriter ) CLOSE(numtime) 
345      !
346   END SUBROUTINE timing_finalize
347   
348
349   SUBROUTINE wcurrent_info
350      !!----------------------------------------------------------------------
351      !!               ***  ROUTINE wcurrent_info ***
352      !! ** Purpose :  compute and write timing output file
353      !!----------------------------------------------------------------------
354      LOGICAL :: ll_ord
355      CHARACTER(len=2048) :: clfmt           
356   
357      ! reorder the current list by elapse time     
358      s_wrk => NULL()
359      s_timer => s_timer_root
360      DO
361         ll_ord = .TRUE.
362         s_timer => s_timer_root
363         DO WHILE ( ASSOCIATED( s_timer%next ) )
364         IF (.NOT. ASSOCIATED(s_timer%next)) EXIT
365            IF ( s_timer%tsum_clock < s_timer%next%tsum_clock ) THEN
366               ALLOCATE(s_wrk)
367               s_wrk = s_timer%next
368               CALL insert  (s_timer, s_timer_root, s_wrk)
369               CALL suppress(s_timer%next)           
370               ll_ord = .FALSE.
371               CYCLE           
372            ENDIF           
373         IF( ASSOCIATED(s_timer%next) ) s_timer => s_timer%next
374         END DO         
375         IF( ll_ord ) EXIT
376      END DO
377           
378      ! write current info
379      WRITE(numtime,*) 'Detailed timing for proc :', narea-1
380      WRITE(numtime,*) '--------------------------'
381      WRITE(numtime,*) 'Section             ',            &
382      &   'Elapsed Time (s)  ','Elapsed Time (%)  ',   &
383      &   'CPU Time(s)  ','CPU Time (%)  ','CPU/Elapsed  ','Frequency' 
384      s_timer => s_timer_root 
385      clfmt = '(1x,a,4x,f12.3,6x,f12.3,x,f12.3,2x,f12.3,6x,f7.3,2x,i9)'
386      DO WHILE ( ASSOCIATED(s_timer) )
387         WRITE(numtime,TRIM(clfmt))   s_timer%cname,   &
388         &   s_timer%tsum_clock,s_timer%tsum_clock*100./t_elaps(2),            &
389         &   s_timer%tsum_cpu  ,s_timer%tsum_cpu*100./t_cpu(2)    ,            &
390         &   s_timer%tsum_cpu/s_timer%tsum_clock, s_timer%niter
391         s_timer => s_timer%next
392      END DO
393      WRITE(numtime,*)
394      !                 
395   END SUBROUTINE wcurrent_info
396
397#if defined key_mpp_mpi     
398   SUBROUTINE waver_info
399      !!----------------------------------------------------------------------
400      !!               ***  ROUTINE wcurrent_info ***
401      !! ** Purpose :  compute and write averaged timing informations
402      !!----------------------------------------------------------------------
403      TYPE(alltimer), POINTER :: sl_timer_glob_root => NULL()
404      TYPE(alltimer), POINTER :: sl_timer_glob      => NULL()
405      TYPE(timer), POINTER :: sl_timer_ave_root => NULL()
406      TYPE(timer), POINTER :: sl_timer_ave      => NULL()
407      INTEGER :: icode
408      LOGICAL :: ll_ord           
409      CHARACTER(len=200) :: clfmt             
410                 
411      ! Initialised the global strucutre   
412      ALLOCATE(sl_timer_glob_root)
413      ALLOCATE(sl_timer_glob_root%cname     (jpnij))
414      ALLOCATE(sl_timer_glob_root%tsum_cpu  (jpnij))
415      ALLOCATE(sl_timer_glob_root%tsum_clock(jpnij))
416      ALLOCATE(sl_timer_glob_root%niter     (jpnij))
417      sl_timer_glob_root%cname(:)       = ''
418      sl_timer_glob_root%tsum_cpu(:)   = 0._wp
419      sl_timer_glob_root%tsum_clock(:) = 0._wp
420      sl_timer_glob_root%niter(:)      = 0
421      sl_timer_glob_root%next => NULL()
422      sl_timer_glob_root%prev => NULL()
423      ALLOCATE(sl_timer_glob)
424      ALLOCATE(sl_timer_glob%cname     (jpnij))
425      ALLOCATE(sl_timer_glob%tsum_cpu  (jpnij))
426      ALLOCATE(sl_timer_glob%tsum_clock(jpnij))
427      ALLOCATE(sl_timer_glob%niter     (jpnij))
428      sl_timer_glob => sl_timer_glob_root
429      !
430      IF( narea .EQ. 1 ) THEN
431         ALLOCATE(sl_timer_ave_root)
432         sl_timer_ave_root%cname       = ''
433         sl_timer_ave_root%t_cpu      = 0._wp
434         sl_timer_ave_root%t_clock    = 0._wp
435         sl_timer_ave_root%tsum_cpu   = 0._wp
436         sl_timer_ave_root%tsum_clock = 0._wp
437         sl_timer_ave_root%tmax_cpu   = 0._wp
438         sl_timer_ave_root%tmax_clock = 0._wp
439         sl_timer_ave_root%tmin_cpu   = 0._wp
440         sl_timer_ave_root%tmin_clock = 0._wp
441         sl_timer_ave_root%tsub_cpu   = 0._wp
442         sl_timer_ave_root%tsub_clock = 0._wp
443         sl_timer_ave_root%ncount      = 0
444         sl_timer_ave_root%ncount_rate = 0
445         sl_timer_ave_root%ncount_max  = 0
446         sl_timer_ave_root%niter       = 0
447         sl_timer_ave_root%l_tdone  = .FALSE.
448         sl_timer_ave_root%next => NULL()
449         sl_timer_ave_root%prev => NULL()
450         ALLOCATE(sl_timer_ave)
451         sl_timer_ave => sl_timer_ave_root           
452      ENDIF 
453     
454      ! Gather info from all processors
455      s_timer => s_timer_root
456      DO WHILE ( ASSOCIATED(s_timer) )
457         CALL MPI_GATHER(s_timer%cname     , 20, MPI_CHARACTER,   &
458                         sl_timer_glob%cname, 20, MPI_CHARACTER,   &
459                         0, MPI_COMM_OPA, icode)
460         CALL MPI_GATHER(s_timer%tsum_clock     , 1, MPI_DOUBLE_PRECISION,   &
461                         sl_timer_glob%tsum_clock, 1, MPI_DOUBLE_PRECISION,   &
462                         0, MPI_COMM_OPA, icode)
463         CALL MPI_GATHER(s_timer%tsum_cpu     , 1, MPI_DOUBLE_PRECISION,   &
464                         sl_timer_glob%tsum_cpu, 1, MPI_DOUBLE_PRECISION,   &
465                         0, MPI_COMM_OPA, icode)
466         CALL MPI_GATHER(s_timer%niter     , 1, MPI_INTEGER,   &
467                         sl_timer_glob%niter, 1, MPI_INTEGER,   &
468                         0, MPI_COMM_OPA, icode)
469         IF( narea == 1 .AND. ASSOCIATED(s_timer%next) ) THEN
470            ALLOCATE(sl_timer_glob%next)
471            ALLOCATE(sl_timer_glob%next%cname     (jpnij))
472            ALLOCATE(sl_timer_glob%next%tsum_cpu  (jpnij))
473            ALLOCATE(sl_timer_glob%next%tsum_clock(jpnij))
474            ALLOCATE(sl_timer_glob%next%niter     (jpnij))
475            sl_timer_glob%next%prev => sl_timer_glob
476            sl_timer_glob%next%next => NULL()
477            sl_timer_glob           => sl_timer_glob%next
478         ENDIF             
479         s_timer => s_timer%next
480      END DO     
481     
482      IF( narea == 1 ) THEN   
483         ! Compute some stats
484         sl_timer_glob => sl_timer_glob_root
485         DO WHILE( ASSOCIATED(sl_timer_glob) )
486            sl_timer_ave%cname  = sl_timer_glob%cname(1)
487            sl_timer_ave%tsum_cpu   = SUM   (sl_timer_glob%tsum_cpu  (:)) / jpnij
488            sl_timer_ave%tsum_clock = SUM   (sl_timer_glob%tsum_clock(:)) / jpnij
489            sl_timer_ave%tmax_cpu   = MAXVAL(sl_timer_glob%tsum_cpu  (:))
490            sl_timer_ave%tmax_clock = MAXVAL(sl_timer_glob%tsum_clock(:))
491            sl_timer_ave%tmin_cpu   = MINVAL(sl_timer_glob%tsum_cpu  (:))
492            sl_timer_ave%tmin_clock = MINVAL(sl_timer_glob%tsum_clock(:))
493            sl_timer_ave%niter      = SUM   (sl_timer_glob%niter     (:))
494            !
495            IF( ASSOCIATED(sl_timer_glob%next) ) THEN
496               ALLOCATE(sl_timer_ave%next)         
497               sl_timer_ave%next%prev => sl_timer_ave
498               sl_timer_ave%next%next => NULL()           
499               sl_timer_ave           => sl_timer_ave%next
500            ENDIF
501            sl_timer_glob => sl_timer_glob%next                               
502         END DO         
503     
504         ! reorder the avearged list by CPU time     
505         s_wrk => NULL()
506         sl_timer_ave => sl_timer_ave_root
507         DO
508            ll_ord = .TRUE.
509            sl_timer_ave => sl_timer_ave_root
510            DO WHILE( ASSOCIATED( sl_timer_ave%next ) )
511            IF( .NOT. ASSOCIATED(sl_timer_ave%next) ) EXIT
512               IF ( sl_timer_ave%tsum_clock < sl_timer_ave%next%tsum_clock ) THEN
513                  ALLOCATE(s_wrk)
514                  s_wrk = sl_timer_ave%next
515                  CALL insert  (sl_timer_ave, sl_timer_ave_root, s_wrk)
516                  CALL suppress(sl_timer_ave%next)           
517                  ll_ord = .FALSE.
518                  CYCLE           
519               ENDIF           
520            IF( ASSOCIATED(sl_timer_ave%next) ) sl_timer_ave => sl_timer_ave%next
521            END DO         
522           IF( ll_ord ) EXIT
523         END DO
524
525         ! write averaged info
526         WRITE(numtime,*) 'Averaged timing on all processors :'
527         WRITE(numtime,*) '-----------------------------------'
528         WRITE(numtime,*) 'Section             ',                &
529         &   'Elapsed Time (s)  ','Elapsed Time (%)  ',          &
530         &   'CPU Time(s)  ','CPU Time (%)  ','CPU/Elapsed  ',   &
531         &   'Max Elapsed (%)  ','Min elapsed (%)  ',            &           
532         &   'Frequency' 
533         sl_timer_ave => sl_timer_ave_root 
534         clfmt = '(1x,a,4x,f12.3,6x,f12.3,x,f12.3,2x,f12.3,6x,f7.3,5x,f12.3,5x,f12.3,2x,f9.2)'
535         DO WHILE ( ASSOCIATED(sl_timer_ave) )
536            WRITE(numtime,TRIM(clfmt))   sl_timer_ave%cname,                            &
537            &   sl_timer_ave%tsum_clock,sl_timer_ave%tsum_clock*100.*jpnij/tot_etime,   &
538            &   sl_timer_ave%tsum_cpu  ,sl_timer_ave%tsum_cpu*100.*jpnij/tot_ctime  ,   &
539            &   sl_timer_ave%tsum_cpu/sl_timer_ave%tsum_clock,                          &
540            &   sl_timer_ave%tmax_clock*100.*jpnij/tot_etime,                           &
541            &   sl_timer_ave%tmin_clock*100.*jpnij/tot_etime,                           &                                               
542            &   sl_timer_ave%niter/REAL(jpnij)
543            sl_timer_ave => sl_timer_ave%next
544         END DO
545         WRITE(numtime,*)
546         !
547         DEALLOCATE(sl_timer_ave_root)
548      ENDIF
549      !
550      DEALLOCATE(sl_timer_glob_root)
551      !                 
552   END SUBROUTINE waver_info
553 
554 
555   SUBROUTINE wmpi_info
556      !!----------------------------------------------------------------------
557      !!               ***  ROUTINE wmpi_time  ***
558      !! ** Purpose :   compute and write a summary of MPI infos
559      !!----------------------------------------------------------------------   
560      !   
561      INTEGER                            :: idum, icode
562      INTEGER, ALLOCATABLE, DIMENSION(:) :: iall_rank
563      REAL(wp) :: ztot_ratio
564      REAL(wp) :: zmax_etime, zmax_ctime, zmax_ratio, zmin_etime, zmin_ctime, zmin_ratio
565      REAL(wp) :: zavg_etime, zavg_ctime, zavg_ratio
566      REAL(wp), ALLOCATABLE, DIMENSION(:) :: zall_ratio
567      CHARACTER(LEN=128), dimension(8) :: cllignes
568      CHARACTER(LEN=128)               :: clhline, clstart_date, clfinal_date
569      CHARACTER(LEN=2048)              :: clfmt   
570   
571      ! Gather all times
572      ALLOCATE( zall_ratio(jpnij), iall_rank(jpnij) )
573      IF( narea == 1 ) THEN
574         iall_rank(:) = (/ (idum,idum=0,jpnij-1) /)
575   
576         ! Compute elapse user time
577         zavg_etime = tot_etime/REAL(jpnij,wp)
578         zmax_etime = MAXVAL(all_etime(:))
579         zmin_etime = MINVAL(all_etime(:))
580
581         ! Compute CPU user time
582         zavg_ctime = tot_ctime/REAL(jpnij,wp)
583         zmax_ctime = MAXVAL(all_ctime(:))
584         zmin_ctime = MINVAL(all_ctime(:))
585   
586         ! Compute cpu/elapsed ratio
587         zall_ratio(:) = all_ctime(:) / all_etime(:)
588         ztot_ratio    = SUM(zall_ratio(:))
589         zavg_ratio    = ztot_ratio/REAL(jpnij,wp)
590         zmax_ratio    = MAXVAL(zall_ratio(:))
591         zmin_ratio    = MINVAL(zall_ratio(:))   
592   
593         ! Output Format
594         clhline    ='1x,13("-"),"|",18("-"),"|",14("-"),"|",18("-"),/,'
595         cllignes(1)='(1x,"MPI summary report :",/,'
596         cllignes(2)='1x,"--------------------",//,'
597         cllignes(3)='1x,"Process Rank |"," Elapsed Time (s) |"," CPU Time (s) |"," Ratio CPU/Elapsed",/,'
598         cllignes(4)='    (1x,i4,9x,"|",f12.3,6x,"|",f12.3,2x,"|",4x,f7.3,/),'
599         WRITE(cllignes(4)(1:4),'(I4)') jpnij
600         cllignes(5)='1x,"Total        |",f12.3,6x,"|",F12.3,2x,"|",4x,f7.3,/,'
601         cllignes(6)='1x,"Minimum      |",f12.3,6x,"|",F12.3,2x,"|",4x,f7.3,/,'
602         cllignes(7)='1x,"Maximum      |",f12.3,6x,"|",F12.3,2x,"|",4x,f7.3,/,'
603         cllignes(8)='1x,"Average      |",f12.3,6x,"|",F12.3,2x,"|",4x,f7.3)'
604         clfmt=TRIM(cllignes(1))// TRIM(cllignes(2))//TRIM(cllignes(3))//          &
605           & TRIM(clhline)//TRIM(cllignes(4))//TRIM(clhline)//TRIM(cllignes(5))//  &
606           & TRIM(clhline)//TRIM(cllignes(6))//TRIM(clhline)//TRIM(cllignes(7))//  &
607           & TRIM(clhline)//TRIM(cllignes(8))
608         WRITE(numtime, TRIM(clfmt)) &
609             (iall_rank(idum),all_etime(idum),all_ctime(idum),zall_ratio(idum),idum=1, jpnij), &
610             tot_etime,     tot_ctime,     ztot_ratio,   &
611             zmin_etime,    zmin_ctime,    zmin_ratio,   &
612             zmax_etime,    zmax_ctime,    zmax_ratio,   &
613             zavg_etime,    zavg_ctime,    zavg_ratio
614         WRITE(numtime,*)   
615      END IF
616      !
617      DEALLOCATE(zall_ratio, iall_rank)
618      !
619   END SUBROUTINE wmpi_info
620#endif   
621
622
623   SUBROUTINE timing_ini_var(cdinfo)
624      !!----------------------------------------------------------------------
625      !!               ***  ROUTINE timing_ini_var  ***
626      !! ** Purpose :   create timing structure
627      !!----------------------------------------------------------------------
628      CHARACTER(len=*), INTENT(in) :: cdinfo
629      LOGICAL :: ll_section
630       
631      !
632      IF( .NOT. ASSOCIATED(s_timer_root) ) THEN
633         ALLOCATE(s_timer_root)
634         s_timer_root%cname       = cdinfo
635         s_timer_root%t_cpu      = 0._wp
636         s_timer_root%t_clock    = 0._wp
637         s_timer_root%tsum_cpu   = 0._wp
638         s_timer_root%tsum_clock = 0._wp
639         s_timer_root%tmax_cpu   = 0._wp
640         s_timer_root%tmax_clock = 0._wp
641         s_timer_root%tmin_cpu   = 0._wp
642         s_timer_root%tmin_clock = 0._wp
643         s_timer_root%tsub_cpu   = 0._wp
644         s_timer_root%tsub_clock = 0._wp
645         s_timer_root%ncount      = 0
646         s_timer_root%ncount_rate = 0
647         s_timer_root%ncount_max  = 0
648         s_timer_root%niter       = 0
649         s_timer_root%l_tdone  = .FALSE.
650         s_timer_root%next => NULL()
651         s_timer_root%prev => NULL()
652         s_timer => s_timer_root
653         !
654         ALLOCATE(s_wrk)
655         s_wrk => NULL()
656         
657      ELSE
658         s_timer => s_timer_root
659         ! case of already existing area (typically inside a loop)
660         DO WHILE( ASSOCIATED(s_timer) ) 
661            IF( TRIM(s_timer%cname) .EQ. TRIM(cdinfo) ) RETURN
662            s_timer => s_timer%next
663         END DO
664         
665         ! end of the chain
666         s_timer => s_timer_root
667         DO WHILE( ASSOCIATED(s_timer%next) )
668            s_timer => s_timer%next
669         END DO
670         
671         ALLOCATE(s_timer%next)     
672         s_timer%next%cname       = cdinfo
673         s_timer%next%t_cpu      = 0._wp
674         s_timer%next%t_clock    = 0._wp
675         s_timer%next%tsum_cpu   = 0._wp
676         s_timer%next%tsum_clock = 0._wp 
677         s_timer%next%tmax_cpu   = 0._wp
678         s_timer%next%tmax_clock = 0._wp
679         s_timer%next%tmin_cpu   = 0._wp
680         s_timer%next%tmin_clock = 0._wp
681         s_timer%next%tsub_cpu   = 0._wp
682         s_timer%next%tsub_clock = 0._wp
683         s_timer%next%ncount      = 0
684         s_timer%next%ncount_rate = 0
685         s_timer%next%ncount_max  = 0
686         s_timer%next%niter       = 0
687         s_timer%next%l_tdone  = .FALSE.
688         s_timer%next%parent_section => NULL()
689         s_timer%next%prev => s_timer
690         s_timer%next%next => NULL()
691         s_timer => s_timer%next
692
693         ! are we inside a section
694         s_wrk => s_timer%prev
695         ll_section = .FALSE.
696         DO WHILE( ASSOCIATED(s_wrk) .AND. .NOT. ll_section )
697            IF( .NOT. s_wrk%l_tdone ) THEN
698               ll_section = .TRUE.
699               s_timer%parent_section => s_wrk 
700            ENDIF
701            s_wrk => s_wrk%prev
702         END DO
703      ENDIF         
704      !
705   END SUBROUTINE timing_ini_var
706
707
708   SUBROUTINE timing_reset
709      !!----------------------------------------------------------------------
710      !!               ***  ROUTINE timing_reset  ***
711      !! ** Purpose :   go to root of timing tree
712      !!----------------------------------------------------------------------
713      l_initdone = .TRUE. 
714      IF(lwp) WRITE(numout,*)
715      IF(lwp) WRITE(numout,*) 'timing_reset : instrumented routines for timing'
716      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
717      CALL timing_list(s_timer_root)
718      WRITE(numout,*)
719      !
720   END SUBROUTINE timing_reset
721
722
723   RECURSIVE SUBROUTINE timing_list(ptr)
724   
725      TYPE(timer), POINTER, INTENT(inout) :: ptr
726      !
727      IF( ASSOCIATED(ptr%next) ) CALL timing_list(ptr%next)
728      IF(lwp) WRITE(numout,*)'   ', ptr%cname   
729      !
730   END SUBROUTINE timing_list
731
732
733   SUBROUTINE insert(sd_current, sd_root ,sd_ptr)
734      !!----------------------------------------------------------------------
735      !!               ***  ROUTINE insert  ***
736      !! ** Purpose :   insert an element in  imer structure
737      !!----------------------------------------------------------------------
738      TYPE(timer), POINTER, INTENT(inout) :: sd_current, sd_root, sd_ptr
739      !
740     
741      IF( ASSOCIATED( sd_current, sd_root ) ) THEN
742         sd_root => sd_ptr
743      ELSE
744         sd_current%prev%next => sd_ptr
745      END IF
746      sd_ptr%next     => sd_current
747      sd_ptr%prev     => sd_current%prev
748      sd_current%prev => sd_ptr
749      !   
750   END SUBROUTINE insert
751 
752 
753   SUBROUTINE suppress(sd_ptr)
754      !!----------------------------------------------------------------------
755      !!               ***  ROUTINE suppress  ***
756      !! ** Purpose :   supress an element in timer structure
757      !!----------------------------------------------------------------------
758      TYPE(timer), POINTER, INTENT(inout) :: sd_ptr
759      !
760      TYPE(timer), POINTER :: sl_temp
761   
762      sl_temp => sd_ptr
763      sd_ptr => sd_ptr%next   
764      IF ( ASSOCIATED(sl_temp%next) ) sl_temp%next%prev => sl_temp%prev
765      DEALLOCATE(sl_temp)
766      !
767    END SUBROUTINE suppress
768
769   !!=====================================================================
770END MODULE timing
Note: See TracBrowser for help on using the repository browser.