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_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC – NEMO

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/timing.F90 @ 3837

Last change on this file since 3837 was 3837, checked in by trackstand2, 11 years ago

Merge of finiss

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