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.
Changeset 14072 for NEMO/trunk/src/OCE/timing.F90 – NEMO

Ignore:
Timestamp:
2020-12-04T08:48:38+01:00 (3 years ago)
Author:
laurent
Message:

Merging branch "2020/dev_r13648_ASINTER-04_laurent_bulk_ice", ticket #2369

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/OCE/timing.F90

    r13982 r14072  
    33   !!                     ***  MODULE  timing  *** 
    44   !!======================================================================== 
    5    !! History : 4.0  ! 2001-05  (R. Benshila)    
     5   !! History : 4.0  ! 2001-05  (R. Benshila) 
    66   !!------------------------------------------------------------------------ 
    77 
    88   !!------------------------------------------------------------------------ 
    9    !!   timming_init    : initialize timing process  
     9   !!   timming_init    : initialize timing process 
    1010   !!   timing_start    : start Timer 
    1111   !!   timing_stop     : stop  Timer 
    1212   !!   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  
     13   !!   timing_finalize : compute stats and write output in calling w*_info 
     14   !!   timing_ini_var  : create timing variables 
    1515   !!   timing_listing  : print instumented subroutines in ocean.output 
    1616   !!   wcurrent_info   : compute and print detailed stats on the current CPU 
    1717   !!   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   
     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 
    2121   !!------------------------------------------------------------------------ 
    22    USE in_out_manager  ! I/O manager  
     22   USE in_out_manager  ! I/O manager 
    2323   USE dom_oce         ! ocean domain 
    24    USE lib_mpp           
    25     
     24   USE lib_mpp 
     25 
    2626   IMPLICIT NONE 
    2727   PRIVATE 
    2828 
    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     
     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 
    3333#if defined key_mpp_mpi 
    3434   INCLUDE 'mpif.h' 
     
    4141      INTEGER :: rank 
    4242      REAL(wp)  :: t_cpu, t_clock, tsum_cpu, tsum_clock, tmax_cpu, tmax_clock, tmin_cpu, tmin_clock, tsub_cpu, tsub_clock 
    43       INTEGER :: ncount, ncount_max, ncount_rate   
     43      INTEGER :: ncount, ncount_max, ncount_rate 
    4444      INTEGER :: niter 
    4545      LOGICAL :: l_tdone 
     
    4848      TYPE(timer), POINTER :: parent_section => NULL() 
    4949   END TYPE timer 
    50      
     50 
    5151   TYPE alltimer 
    5252      CHARACTER(LEN=20), DIMENSION(:), POINTER :: cname => NULL() 
     
    5656      TYPE(alltimer), POINTER :: next => NULL() 
    5757      TYPE(alltimer), POINTER :: prev => NULL() 
    58    END TYPE alltimer  
    59   
     58   END TYPE alltimer 
     59 
    6060   TYPE(timer), POINTER :: s_timer_root => NULL() 
    6161   TYPE(timer), POINTER :: s_timer      => NULL() 
     
    6666   LOGICAL :: l_initdone = .FALSE. 
    6767   INTEGER :: nsize 
    68     
     68 
    6969   ! Variables for coarse grain timing 
    7070   REAL(wp) :: tot_etime, tot_ctime 
     
    7676   CHARACTER(LEN=10), DIMENSION(2) :: ctime 
    7777   CHARACTER(LEN=5)                :: czone 
    78      
     78 
    7979   ! From of ouput file (1/proc or one global)   !RB to put in nammpp or namctl 
    80    LOGICAL :: ln_onefile = .TRUE.  
     80   LOGICAL :: ln_onefile = .TRUE. 
    8181   LOGICAL :: lwriter 
    8282   !!---------------------------------------------------------------------- 
     
    9696       IF(ASSOCIATED(s_timer) ) s_timer_old => s_timer 
    9797       ! 
    98       ! Create timing structure at first call of the routine  
     98      ! Create timing structure at first call of the routine 
    9999       CALL timing_ini_var(cdinfo) 
    100100   !   write(*,*) 'after inivar ', s_timer%cname 
     
    102102      ! ici timing_ini_var a soit retrouve s_timer et fait return soit ajoute un maillon 
    103103      ! maintenant on regarde si le call d'avant corrsspond a un parent ou si il est ferme 
    104       IF( .NOT. s_timer_old%l_tdone ) THEN       
     104      IF( .NOT. s_timer_old%l_tdone ) THEN 
    105105         s_timer%parent_section => s_timer_old 
    106106      ELSE 
    107107         s_timer%parent_section => NULL() 
    108       ENDIF     
     108      ENDIF 
    109109 
    110110      s_timer%l_tdone = .FALSE. 
     
    112112      s_timer%t_cpu = 0. 
    113113      s_timer%t_clock = 0. 
    114                    
     114 
    115115      ! CPU time collection 
    116116      CALL CPU_TIME( s_timer%t_cpu  ) 
     
    136136      CHARACTER(len=*), INTENT(in), OPTIONAL :: csection 
    137137      ! 
    138       INTEGER  :: ifinal_count, iperiods     
     138      INTEGER  :: ifinal_count, iperiods 
    139139      REAL(wp) :: zcpu_end, zmpitime,zcpu_raw,zclock_raw 
    140140      ! 
     
    152152!!$      IF(associated(s_timer%parent_section))then 
    153153!!$        write(*,*) s_timer%cname,' <-- ', s_timer%parent_section%cname 
    154 !!$      ENDIF   
     154!!$      ENDIF 
    155155 
    156156 !     No need to search ... : s_timer has the last value defined in start 
    157157 !     s_timer => s_timer_root 
    158  !     DO WHILE( TRIM(s_timer%cname) /= TRIM(cdinfo) )  
     158 !     DO WHILE( TRIM(s_timer%cname) /= TRIM(cdinfo) ) 
    159159 !        IF( ASSOCIATED(s_timer%next) ) s_timer => s_timer%next 
    160160 !     END DO 
    161   
     161 
    162162      ! CPU time correction 
    163163      zcpu_raw = zcpu_end - s_timer%t_cpu - t_overcpu ! total time including child 
     
    172172      iperiods = ifinal_count - s_timer%ncount 
    173173      IF( ifinal_count < s_timer%ncount )  & 
    174          iperiods = iperiods + s_timer%ncount_max  
    175          zclock_raw = REAL(iperiods) / s_timer%ncount_rate !- t_overclock    
     174         iperiods = iperiods + s_timer%ncount_max 
     175         zclock_raw = REAL(iperiods) / s_timer%ncount_rate !- t_overclock 
    176176         s_timer%t_clock  = zclock_raw - s_timer%tsub_clock 
    177177#endif 
    178178 !     IF(s_timer%cname==trim('lbc_lnk_2d')) write(*,*) zclock_raw , s_timer%tsub_clock 
    179        
     179 
    180180      ! Correction of parent section 
    181181      IF( .NOT. PRESENT(csection) ) THEN 
    182182         IF ( ASSOCIATED(s_timer%parent_section ) ) THEN 
    183             s_timer%parent_section%tsub_cpu   = zcpu_raw   + s_timer%parent_section%tsub_cpu  
    184             s_timer%parent_section%tsub_clock = zclock_raw + s_timer%parent_section%tsub_clock              
     183            s_timer%parent_section%tsub_cpu   = zcpu_raw   + s_timer%parent_section%tsub_cpu 
     184            s_timer%parent_section%tsub_clock = zclock_raw + s_timer%parent_section%tsub_clock 
    185185         ENDIF 
    186186      ENDIF 
    187              
    188       ! time diagnostics  
    189       s_timer%tsum_clock = s_timer%tsum_clock + s_timer%t_clock  
     187 
     188      ! time diagnostics 
     189      s_timer%tsum_clock = s_timer%tsum_clock + s_timer%t_clock 
    190190      s_timer%tsum_cpu   = s_timer%tsum_cpu   + s_timer%t_cpu 
    191191!RB to use to get min/max during a time integration 
    192192!      IF( .NOT. l_initdone ) THEN 
    193 !         s_timer%tmin_clock = s_timer%t_clock  
    194 !         s_timer%tmin_cpu   = s_timer%t_cpu  
     193!         s_timer%tmin_clock = s_timer%t_clock 
     194!         s_timer%tmin_cpu   = s_timer%t_cpu 
    195195!      ELSE 
    196 !         s_timer%tmin_clock = MIN( s_timer%tmin_clock, s_timer%t_clock )  
    197 !         s_timer%tmin_cpu   = MIN( s_timer%tmin_cpu  , s_timer%t_cpu   )  
    198 !      ENDIF    
    199 !      s_timer%tmax_clock = MAX( s_timer%tmax_clock, s_timer%t_clock )  
    200 !      s_timer%tmax_cpu   = MAX( s_timer%tmax_cpu  , s_timer%t_cpu   )   
     196!         s_timer%tmin_clock = MIN( s_timer%tmin_clock, s_timer%t_clock ) 
     197!         s_timer%tmin_cpu   = MIN( s_timer%tmin_cpu  , s_timer%t_cpu   ) 
     198!      ENDIF 
     199!      s_timer%tmax_clock = MAX( s_timer%tmax_clock, s_timer%t_clock ) 
     200!      s_timer%tmax_cpu   = MAX( s_timer%tmax_cpu  , s_timer%t_cpu   ) 
    201201      ! 
    202202      s_timer%tsub_clock = 0. 
     
    207207      ! we come back 
    208208      IF ( ASSOCIATED(s_timer%parent_section ) ) s_timer => s_timer%parent_section 
    209       
     209 
    210210!      write(*,*) 'end of stop ', s_timer%cname 
    211211 
    212212   END SUBROUTINE timing_stop 
    213   
    214   
     213 
     214 
    215215   SUBROUTINE timing_init( clname ) 
    216216      !!---------------------------------------------------------------------- 
     
    235235         lwriter = .TRUE. 
    236236      ENDIF 
    237        
    238       IF( lwriter) THEN       
     237 
     238      IF( lwriter) THEN 
    239239         WRITE(numtime,*) 
    240240         WRITE(numtime,*) '      CNRS - NERC - Met OFFICE - MERCATOR-ocean - CMCC - INGV' 
     
    246246         WRITE(numtime,*) 
    247247         WRITE(numtime,*) 
    248       ENDIF    
    249        
     248      ENDIF 
     249 
    250250      ! Compute clock function overhead 
    251 #if defined key_mpp_mpi         
     251#if defined key_mpp_mpi 
    252252      t_overclock = MPI_WTIME() 
    253253      t_overclock = MPI_WTIME() - t_overclock 
    254 #else         
     254#else 
    255255      CALL SYSTEM_CLOCK(COUNT_RATE=ncount_rate, COUNT_MAX=ncount_max) 
    256256      CALL SYSTEM_CLOCK(COUNT = istart_count) 
     
    258258      iperiods = ifinal_count - istart_count 
    259259      IF( ifinal_count < istart_count )  & 
    260           iperiods = iperiods + ncount_max  
     260          iperiods = iperiods + ncount_max 
    261261      t_overclock = REAL(iperiods) / ncount_rate 
    262262#endif 
     
    265265      CALL CPU_TIME(zdum) 
    266266      CALL CPU_TIME(t_overcpu) 
    267        
    268       ! End overhead omputation   
    269       t_overcpu = t_overcpu - zdum         
    270       t_overclock = t_overcpu + t_overclock         
     267 
     268      ! End overhead omputation 
     269      t_overcpu = t_overcpu - zdum 
     270      t_overclock = t_overcpu + t_overclock 
    271271 
    272272      ! Timing on date and time 
    273273      CALL DATE_AND_TIME(cdate(1),ctime(1),czone,nvalues) 
    274      
    275       CALL CPU_TIME(t_cpu(1))       
    276 #if defined key_mpp_mpi         
     274 
     275      CALL CPU_TIME(t_cpu(1)) 
     276#if defined key_mpp_mpi 
    277277      ! Start elapsed and CPU time counters 
    278278      t_elaps(1) = MPI_WTIME() 
     
    280280      CALL SYSTEM_CLOCK(COUNT_RATE=ncount_rate, COUNT_MAX=ncount_max) 
    281281      CALL SYSTEM_CLOCK(COUNT = ncount) 
    282 #endif                  
     282#endif 
    283283      ! 
    284284   END SUBROUTINE timing_init 
     
    288288      !!---------------------------------------------------------------------- 
    289289      !!               ***  ROUTINE timing_finalize *** 
    290       !! ** Purpose :  compute average time  
     290      !! ** Purpose :  compute average time 
    291291      !!               write timing output file 
    292292      !!---------------------------------------------------------------------- 
     
    295295      INTEGER :: ji 
    296296      LOGICAL :: ll_ord, ll_averep 
    297       CHARACTER(len=120) :: clfmt             
     297      CHARACTER(len=120) :: clfmt 
    298298      REAL(wp), DIMENSION(:), ALLOCATABLE ::   timing_glob 
    299299      REAL(wp) ::   zsypd   ! simulated years per day (Balaji 2017) 
     
    301301 
    302302      ll_averep = .TRUE. 
    303      
     303 
    304304      ! total CPU and elapse 
    305305      CALL CPU_TIME(t_cpu(2)) 
     
    311311      iperiods = nfinal_count - ncount 
    312312      IF( nfinal_count < ncount )  & 
    313           iperiods = iperiods + ncount_max  
     313          iperiods = iperiods + ncount_max 
    314314      t_elaps(2) = REAL(iperiods) / ncount_rate - t_overclock 
    315 #endif       
     315#endif 
    316316 
    317317      ! End of timings on date & time 
    318318      CALL DATE_AND_TIME(cdate(2),ctime(2),czone,nvalues) 
    319         
     319 
    320320      ! Compute the numer of routines 
    321       nsize = 0  
     321      nsize = 0 
    322322      s_timer => s_timer_root 
    323323      DO WHILE( ASSOCIATED(s_timer) ) 
     
    334334         IF( lwriter ) WRITE(numtime,*) 
    335335         ll_averep = .FALSE. 
    336       ENDIF    
    337  
    338 #if defined key_mpp_mpi       
     336      ENDIF 
     337 
     338#if defined key_mpp_mpi 
    339339      ! in MPI gather some info 
    340340      ALLOCATE( all_etime(jpnij), all_ctime(jpnij) ) 
     
    349349#else 
    350350      tot_etime = t_elaps(2) 
    351       tot_ctime = t_cpu  (2)            
     351      tot_ctime = t_cpu  (2) 
    352352#endif 
    353353 
    354354      ! write output file 
    355       IF( lwriter ) WRITE(numtime,*)  
    356       IF( lwriter ) WRITE(numtime,*)  
     355      IF( lwriter ) WRITE(numtime,*) 
     356      IF( lwriter ) WRITE(numtime,*) 
    357357      IF( lwriter ) WRITE(numtime,*) 'Total timing (sum) :' 
    358358      IF( lwriter ) WRITE(numtime,*) '--------------------' 
    359359      IF( lwriter ) WRITE(numtime,"('Elapsed Time (s)  CPU Time (s)')") 
    360360      IF( lwriter ) WRITE(numtime,'(5x,f12.3,1x,f12.3)')  tot_etime, tot_ctime 
    361       IF( lwriter ) WRITE(numtime,*)  
     361      IF( lwriter ) WRITE(numtime,*) 
    362362#if defined key_mpp_mpi 
    363363      IF( ll_averep ) CALL waver_info 
    364364      CALL wmpi_info 
    365 #endif       
     365#endif 
    366366      IF( lwriter ) CALL wcurrent_info 
    367        
     367 
    368368      clfmt='(1X,"Timing started on ",2(A2,"/"),A4," at ",2(A2,":"),A2," MET ",A3,":",A2," from GMT")' 
    369       IF( lwriter ) WRITE(numtime, TRIM(clfmt)) &            
     369      IF( lwriter ) WRITE(numtime, TRIM(clfmt)) & 
    370370      &       cdate(1)(7:8), cdate(1)(5:6), cdate(1)(1:4),   & 
    371371      &       ctime(1)(1:2), ctime(1)(3:4), ctime(1)(5:6),   & 
    372       &       czone(1:3),    czone(4:5)                      
     372      &       czone(1:3),    czone(4:5) 
    373373      clfmt='(1X,  "Timing   ended on ",2(A2,"/"),A4," at ",2(A2,":"),A2," MET ",A3,":",A2," from GMT")' 
    374       IF( lwriter ) WRITE(numtime, TRIM(clfmt)) &            
     374      IF( lwriter ) WRITE(numtime, TRIM(clfmt)) & 
    375375      &       cdate(2)(7:8), cdate(2)(5:6), cdate(2)(1:4),   & 
    376376      &       ctime(2)(1:2), ctime(2)(3:4), ctime(2)(5:6),   & 
     
    402402      ENDIF 
    403403      DEALLOCATE(timing_glob) 
    404 #endif       
    405  
    406       IF( lwriter ) CLOSE(numtime)  
     404#endif 
     405 
     406      IF( lwriter ) CLOSE(numtime) 
    407407      ! 
    408408   END SUBROUTINE timing_finalize 
    409     
     409 
    410410 
    411411   SUBROUTINE wcurrent_info 
     
    415415      !!---------------------------------------------------------------------- 
    416416      LOGICAL :: ll_ord 
    417       CHARACTER(len=2048) :: clfmt             
    418     
    419       ! reorder the current list by elapse time       
     417      CHARACTER(len=2048) :: clfmt 
     418 
     419      ! reorder the current list by elapse time 
    420420      s_wrk => NULL() 
    421421      s_timer => s_timer_root 
     
    425425         DO WHILE ( ASSOCIATED( s_timer%next ) ) 
    426426            IF (.NOT. ASSOCIATED(s_timer%next)) EXIT 
    427             IF ( s_timer%tsum_clock < s_timer%next%tsum_clock ) THEN  
     427            IF ( s_timer%tsum_clock < s_timer%next%tsum_clock ) THEN 
    428428               ALLOCATE(s_wrk) 
    429429               s_wrk = s_timer%next 
    430430               CALL insert  (s_timer, s_timer_root, s_wrk) 
    431                CALL suppress(s_timer%next)             
     431               CALL suppress(s_timer%next) 
    432432               ll_ord = .FALSE. 
    433                CYCLE             
     433               CYCLE 
    434434            ENDIF 
    435435            IF( ASSOCIATED(s_timer%next) ) s_timer => s_timer%next 
     
    437437         IF( ll_ord ) EXIT 
    438438      END DO 
    439              
     439 
    440440      ! write current info 
    441441      WRITE(numtime,*) 'Detailed timing for proc :', narea-1 
     
    443443      WRITE(numtime,*) 'Section             ',            & 
    444444      &   'Elapsed Time (s)  ','Elapsed Time (%)  ',   & 
    445       &   'CPU Time(s)  ','CPU Time (%)  ','CPU/Elapsed  ','Frequency'  
    446       s_timer => s_timer_root   
     445      &   'CPU Time(s)  ','CPU Time (%)  ','CPU/Elapsed  ','Frequency' 
     446      s_timer => s_timer_root 
    447447      clfmt = '(1x,a,4x,f12.3,6x,f12.3,x,f12.3,2x,f12.3,6x,f7.3,2x,i9)' 
    448448      DO WHILE ( ASSOCIATED(s_timer) ) 
     
    455455      END DO 
    456456      WRITE(numtime,*) 
    457       !                   
     457      ! 
    458458   END SUBROUTINE wcurrent_info 
    459459 
    460 #if defined key_mpp_mpi      
     460#if defined key_mpp_mpi 
    461461   SUBROUTINE waver_info 
    462462      !!---------------------------------------------------------------------- 
     
    470470      INTEGER :: icode 
    471471      INTEGER :: ierr 
    472       LOGICAL :: ll_ord            
    473       CHARACTER(len=200) :: clfmt               
    474                   
    475       ! Initialised the global strucutre    
     472      LOGICAL :: ll_ord 
     473      CHARACTER(len=200) :: clfmt 
     474 
     475      ! Initialised the global strucutre 
    476476      ALLOCATE(sl_timer_glob_root, Stat=ierr) 
    477477      IF(ierr /= 0)THEN 
     
    524524         sl_timer_ave_root%prev => NULL() 
    525525         ALLOCATE(sl_timer_ave) 
    526          sl_timer_ave => sl_timer_ave_root             
    527       ENDIF  
     526         sl_timer_ave => sl_timer_ave_root 
     527      ENDIF 
    528528 
    529529      ! Gather info from all processors 
     
    552552            sl_timer_glob%next%next => NULL() 
    553553            sl_timer_glob           => sl_timer_glob%next 
    554          ENDIF               
     554         ENDIF 
    555555         s_timer => s_timer%next 
    556       END DO       
    557        
    558       IF( narea == 1 ) THEN     
     556      END DO 
     557 
     558      IF( narea == 1 ) THEN 
    559559         ! Compute some stats 
    560560         sl_timer_glob => sl_timer_glob_root 
     
    570570            ! 
    571571            IF( ASSOCIATED(sl_timer_glob%next) ) THEN 
    572                ALLOCATE(sl_timer_ave%next)           
     572               ALLOCATE(sl_timer_ave%next) 
    573573               sl_timer_ave%next%prev => sl_timer_ave 
    574                sl_timer_ave%next%next => NULL()            
     574               sl_timer_ave%next%next => NULL() 
    575575               sl_timer_ave           => sl_timer_ave%next 
    576576            ENDIF 
    577             sl_timer_glob => sl_timer_glob%next                                 
     577            sl_timer_glob => sl_timer_glob%next 
    578578         END DO 
    579        
    580          ! reorder the averaged list by CPU time       
     579 
     580         ! reorder the averaged list by CPU time 
    581581         s_wrk => NULL() 
    582582         sl_timer_ave => sl_timer_ave_root 
     
    588588               IF( .NOT. ASSOCIATED(sl_timer_ave%next) ) EXIT 
    589589 
    590                IF ( sl_timer_ave%tsum_clock < sl_timer_ave%next%tsum_clock ) THEN  
     590               IF ( sl_timer_ave%tsum_clock < sl_timer_ave%next%tsum_clock ) THEN 
    591591                  ALLOCATE(s_wrk) 
    592592                  ! Copy data into the new object pointed to by s_wrk 
     
    595595                  CALL insert  (sl_timer_ave, sl_timer_ave_root, s_wrk) 
    596596                  ! Remove the old object from the list 
    597                   CALL suppress(sl_timer_ave%next)             
     597                  CALL suppress(sl_timer_ave%next) 
    598598                  ll_ord = .FALSE. 
    599                   CYCLE             
    600                ENDIF            
     599                  CYCLE 
     600               ENDIF 
    601601               IF( ASSOCIATED(sl_timer_ave%next) ) sl_timer_ave => sl_timer_ave%next 
    602             END DO          
     602            END DO 
    603603            IF( ll_ord ) EXIT 
    604604         END DO 
     
    609609         WRITE(numtime,"('Section',13x,'Elap. Time(s)',2x,'Elap. Time(%)',2x, & 
    610610         &   'CPU Time(s)',2x,'CPU Time(%)',2x,'CPU/Elap',1x,   & 
    611          &   'Max elap(%)',2x,'Min elap(%)',2x,            &            
     611         &   'Max elap(%)',2x,'Min elap(%)',2x,            & 
    612612         &   'Freq')") 
    613          sl_timer_ave => sl_timer_ave_root   
     613         sl_timer_ave => sl_timer_ave_root 
    614614         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)' 
    615615         DO WHILE ( ASSOCIATED(sl_timer_ave) ) 
    616             IF( sl_timer_ave%tsum_clock > 0. )                                             &  
     616            IF( sl_timer_ave%tsum_clock > 0. )                                             & 
    617617               WRITE(numtime,TRIM(clfmt))   sl_timer_ave%cname(1:18),                      & 
    618618               &   sl_timer_ave%tsum_clock,sl_timer_ave%tsum_clock*100.*jpnij/tot_etime,   & 
     
    630630      ! 
    631631      DEALLOCATE(sl_timer_glob_root) 
    632       !                   
     632      ! 
    633633   END SUBROUTINE waver_info 
    634    
    635    
     634 
     635 
    636636   SUBROUTINE wmpi_info 
    637637      !!---------------------------------------------------------------------- 
    638638      !!               ***  ROUTINE wmpi_time  *** 
    639       !! ** Purpose :   compute and write a summary of MPI infos  
    640       !!----------------------------------------------------------------------    
    641       !    
     639      !! ** Purpose :   compute and write a summary of MPI infos 
     640      !!---------------------------------------------------------------------- 
     641      ! 
    642642      INTEGER                            :: idum, icode 
    643643      INTEGER, ALLOCATABLE, DIMENSION(:) :: iall_rank 
     
    648648      CHARACTER(LEN=128), dimension(8) :: cllignes 
    649649      CHARACTER(LEN=128)               :: clhline, clstart_date, clfinal_date 
    650       CHARACTER(LEN=2048)              :: clfmt     
    651     
     650      CHARACTER(LEN=2048)              :: clfmt 
     651 
    652652      ! Gather all times 
    653653      ALLOCATE( zall_ratio(jpnij), iall_rank(jpnij) ) 
    654654      IF( narea == 1 ) THEN 
    655655         iall_rank(:) = (/ (idum,idum=0,jpnij-1) /) 
    656     
     656 
    657657         ! Compute elapse user time 
    658658         zavg_etime = tot_etime/REAL(jpnij,wp) 
     
    664664         zmax_ctime = MAXVAL(all_ctime(:)) 
    665665         zmin_ctime = MINVAL(all_ctime(:)) 
    666     
     666 
    667667         ! Compute cpu/elapsed ratio 
    668668         zall_ratio(:) = all_ctime(:) / all_etime(:) 
     
    670670         zavg_ratio    = SUM(zall_ratio(:))/REAL(jpnij,wp) 
    671671         zmax_ratio    = MAXVAL(zall_ratio(:)) 
    672          zmin_ratio    = MINVAL(zall_ratio(:))    
    673     
     672         zmin_ratio    = MINVAL(zall_ratio(:)) 
     673 
    674674         ! Output Format 
    675675         clhline    ='1x,13("-"),"|",18("-"),"|",14("-"),"|",18("-"),/,' 
     
    693693             zmax_etime,    zmax_ctime,    zmax_ratio,   & 
    694694             zavg_etime,    zavg_ctime,    zavg_ratio 
    695          WRITE(numtime,*)     
     695         WRITE(numtime,*) 
    696696      END IF 
    697697      ! 
     
    699699      ! 
    700700   END SUBROUTINE wmpi_info 
    701 #endif    
     701#endif 
    702702 
    703703 
     
    705705      !!---------------------------------------------------------------------- 
    706706      !!               ***  ROUTINE timing_ini_var  *** 
    707       !! ** Purpose :   create timing structure  
     707      !! ** Purpose :   create timing structure 
    708708      !!---------------------------------------------------------------------- 
    709709      CHARACTER(len=*), INTENT(in) :: cdinfo 
    710710      LOGICAL :: ll_section 
    711         
     711 
    712712      ! 
    713713      IF( .NOT. ASSOCIATED(s_timer_root) ) THEN 
     
    760760         ! case of already existing area (typically inside a loop) 
    761761   !         write(*,*) 'in ini_var for routine : ', cdinfo 
    762          DO WHILE( ASSOCIATED(s_timer) )  
     762         DO WHILE( ASSOCIATED(s_timer) ) 
    763763            IF( TRIM(s_timer%cname) .EQ. TRIM(cdinfo) ) THEN 
    764  !             write(*,*) 'in ini_var for routine : ', cdinfo,' we return'            
     764 !             write(*,*) 'in ini_var for routine : ', cdinfo,' we return' 
    765765               RETURN ! cdinfo is already in the chain 
    766766            ENDIF 
     
    775775 
    776776    !     write(*,*) 'after search', s_timer%cname 
    777          ! cdinfo is not part of the chain so we add it with initialisation           
     777         ! cdinfo is not part of the chain so we add it with initialisation 
    778778          ALLOCATE(s_timer%next) 
    779779    !     write(*,*) 'after allocation of next' 
    780    
     780 
    781781         s_timer%next%cname       = cdinfo 
    782782         s_timer%next%t_cpu      = 0._wp 
    783783         s_timer%next%t_clock    = 0._wp 
    784784         s_timer%next%tsum_cpu   = 0._wp 
    785          s_timer%next%tsum_clock = 0._wp   
     785         s_timer%next%tsum_clock = 0._wp 
    786786         s_timer%next%tmax_cpu   = 0._wp 
    787787         s_timer%next%tmax_clock = 0._wp 
     
    799799         s_timer%next%next => NULL() 
    800800         s_timer => s_timer%next 
    801       ENDIF  
     801      ENDIF 
    802802      !    write(*,*) 'after allocation' 
    803803     ! 
     
    808808      !!---------------------------------------------------------------------- 
    809809      !!               ***  ROUTINE timing_reset  *** 
    810       !! ** Purpose :   go to root of timing tree  
    811       !!---------------------------------------------------------------------- 
    812       l_initdone = .TRUE.  
     810      !! ** Purpose :   go to root of timing tree 
     811      !!---------------------------------------------------------------------- 
     812      l_initdone = .TRUE. 
    813813!      IF(lwp) WRITE(numout,*) 
    814814!      IF(lwp) WRITE(numout,*) 'timing_reset : instrumented routines for timing' 
     
    821821 
    822822   RECURSIVE SUBROUTINE timing_list(ptr) 
    823     
     823 
    824824      TYPE(timer), POINTER, INTENT(inout) :: ptr 
    825825      ! 
    826826      IF( ASSOCIATED(ptr%next) ) CALL timing_list(ptr%next) 
    827       IF(lwp) WRITE(numout,*)'   ', ptr%cname    
     827      IF(lwp) WRITE(numout,*)'   ', ptr%cname 
    828828      ! 
    829829   END SUBROUTINE timing_list 
     
    837837      TYPE(timer), POINTER, INTENT(inout) :: sd_current, sd_root, sd_ptr 
    838838      ! 
    839       
     839 
    840840      IF( ASSOCIATED( sd_current, sd_root ) ) THEN 
    841841         ! If our current element is the root element then 
     
    852852      ! to ALLOCATE memory to this pointer will fail. 
    853853      sd_ptr => NULL() 
    854       !     
     854      ! 
    855855   END SUBROUTINE insert 
    856    
    857    
     856 
     857 
    858858   SUBROUTINE suppress(sd_ptr) 
    859859      !!---------------------------------------------------------------------- 
     
    864864      ! 
    865865      TYPE(timer), POINTER :: sl_temp 
    866      
     866 
    867867      sl_temp => sd_ptr 
    868       sd_ptr => sd_ptr%next     
     868      sd_ptr => sd_ptr%next 
    869869      IF ( ASSOCIATED(sl_temp%next) ) sl_temp%next%prev => sl_temp%prev 
    870870      DEALLOCATE(sl_temp) 
Note: See TracChangeset for help on using the changeset viewer.