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 10727 for utils/tools_AGRIF_CMEMS_2020/DOMAINcfg/src/timing.F90 – NEMO

Ignore:
Timestamp:
2019-02-27T17:02:02+01:00 (5 years ago)
Author:
rblod
Message:

new nesting tools (attempt) and brutal cleaning of DOMAINcfg, see ticket #2129

File:
1 moved

Legend:

Unmodified
Added
Removed
  • utils/tools_AGRIF_CMEMS_2020/DOMAINcfg/src/timing.F90

    r10725 r10727  
    3131   PUBLIC   timing_start, timing_stop      ! called in each routine to time  
    3232    
    33  
     33#if defined key_mpp_mpi 
    3434   INCLUDE 'mpif.h' 
    35  
     35#endif 
    3636 
    3737   ! Variables for fine grain timing 
    3838   TYPE timer 
    3939      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 
     40      CHARACTER(LEN=20)  :: surname 
     41      INTEGER :: rank 
     42      REAL(wp)  :: t_cpu, t_clock, tsum_cpu, tsum_clock, tmax_cpu, tmax_clock, tmin_cpu, tmin_clock, tsub_cpu, tsub_clock 
    4143      INTEGER :: ncount, ncount_max, ncount_rate   
    4244      INTEGER :: niter 
     
    4951   TYPE alltimer 
    5052      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() 
     53      REAL(wp), DIMENSION(:), POINTER :: tsum_cpu   => NULL() 
     54      REAL(wp), DIMENSION(:), POINTER :: tsum_clock => NULL() 
     55      INTEGER, DIMENSION(:), POINTER :: niter => NULL() 
    5456      TYPE(alltimer), POINTER :: next => NULL() 
    5557      TYPE(alltimer), POINTER :: prev => NULL() 
     
    5860   TYPE(timer), POINTER :: s_timer_root => NULL() 
    5961   TYPE(timer), POINTER :: s_timer      => NULL() 
     62   TYPE(timer), POINTER :: s_timer_old      => NULL() 
     63 
    6064   TYPE(timer), POINTER :: s_wrk        => NULL() 
    6165   REAL(wp) :: t_overclock, t_overcpu 
     
    7781   LOGICAL :: lwriter 
    7882   !!---------------------------------------------------------------------- 
    79    !! NEMO/OPA 4.0 , NEMO Consortium (2011) 
    80    !! $Id: timing.F90 5120 2015-03-03 16:11:55Z acc $ 
    81    !! Software governed by the CeCILL licence     (./LICENSE) 
     83   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     84   !! $Id: timing.F90 10510 2019-01-14 16:13:17Z clem $ 
     85   !! Software governed by the CeCILL license (see ./LICENSE) 
    8286   !!---------------------------------------------------------------------- 
    8387CONTAINS 
     
    9094      CHARACTER(len=*), INTENT(in) :: cdinfo 
    9195      ! 
    92         
    93       ! Create timing structure at first call 
    94       IF( .NOT. l_initdone ) THEN 
    95          CALL timing_ini_var(cdinfo) 
     96       IF(ASSOCIATED(s_timer) ) s_timer_old => s_timer 
     97       ! 
     98      ! Create timing structure at first call of the routine  
     99       CALL timing_ini_var(cdinfo) 
     100   !   write(*,*) 'after inivar ', s_timer%cname 
     101 
     102      ! ici timing_ini_var a soit retrouve s_timer et fait return soit ajoute un maillon 
     103      ! 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       
     105         s_timer%parent_section => s_timer_old 
    96106      ELSE 
    97          s_timer => s_timer_root 
    98          DO WHILE( TRIM(s_timer%cname) /= TRIM(cdinfo) )  
    99             IF( ASSOCIATED(s_timer%next) ) s_timer => s_timer%next 
    100          END DO 
    101       ENDIF          
     107         s_timer%parent_section => NULL() 
     108      ENDIF     
     109 
    102110      s_timer%l_tdone = .FALSE. 
    103111      s_timer%niter = s_timer%niter + 1 
     
    108116      CALL CPU_TIME( s_timer%t_cpu  ) 
    109117      ! clock time collection 
    110  
     118#if defined key_mpp_mpi 
    111119      s_timer%t_clock= MPI_Wtime() 
    112  
    113  
    114  
     120#else 
     121      CALL SYSTEM_CLOCK(COUNT_RATE=s_timer%ncount_rate, COUNT_MAX=s_timer%ncount_max) 
     122      CALL SYSTEM_CLOCK(COUNT = s_timer%ncount) 
     123#endif 
     124!      write(*,*) 'end of start ', s_timer%cname 
    115125 
    116126      ! 
     
    127137      ! 
    128138      INTEGER  :: ifinal_count, iperiods     
    129       REAL(wp) :: zcpu_end, zmpitime 
     139      REAL(wp) :: zcpu_end, zmpitime,zcpu_raw,zclock_raw 
    130140      ! 
    131141      s_wrk => NULL() 
    132142 
    133143      ! clock time collection 
    134  
     144#if defined key_mpp_mpi 
    135145      zmpitime = MPI_Wtime() 
    136  
    137  
    138  
     146#else 
     147      CALL SYSTEM_CLOCK(COUNT = ifinal_count) 
     148#endif 
    139149      ! CPU time collection 
    140150      CALL CPU_TIME( zcpu_end ) 
    141151 
    142       s_timer => s_timer_root 
    143       DO WHILE( TRIM(s_timer%cname) /= TRIM(cdinfo) )  
    144          IF( ASSOCIATED(s_timer%next) ) s_timer => s_timer%next 
    145       END DO 
     152!!$      IF(associated(s_timer%parent_section))then 
     153!!$        write(*,*) s_timer%cname,' <-- ', s_timer%parent_section%cname 
     154!!$      ENDIF   
     155 
     156 !     No need to search ... : s_timer has the last value defined in start 
     157 !     s_timer => s_timer_root 
     158 !     DO WHILE( TRIM(s_timer%cname) /= TRIM(cdinfo) )  
     159 !        IF( ASSOCIATED(s_timer%next) ) s_timer => s_timer%next 
     160 !     END DO 
    146161  
    147162      ! CPU time correction 
    148       s_timer%t_cpu  = zcpu_end - s_timer%t_cpu - t_overcpu - s_timer%tsub_cpu 
    149    
     163      zcpu_raw = zcpu_end - s_timer%t_cpu - t_overcpu ! total time including child 
     164      s_timer%t_cpu  = zcpu_raw - s_timer%tsub_cpu 
     165  !    IF(s_timer%cname==trim('lbc_lnk_2d'))  write(*,*) s_timer%tsub_cpu,zcpu_end 
     166 
    150167      ! clock time correction 
    151  
    152       s_timer%t_clock = zmpitime - s_timer%t_clock - t_overclock - s_timer%tsub_clock 
    153  
    154  
    155  
    156  
    157  
    158  
     168#if defined key_mpp_mpi 
     169      zclock_raw = zmpitime - s_timer%t_clock - t_overclock ! total time including child 
     170      s_timer%t_clock = zclock_raw - t_overclock - s_timer%tsub_clock 
     171#else 
     172      iperiods = ifinal_count - s_timer%ncount 
     173      IF( ifinal_count < s_timer%ncount )  & 
     174         iperiods = iperiods + s_timer%ncount_max  
     175         zclock_raw = REAL(iperiods) / s_timer%ncount_rate !- t_overclock    
     176         s_timer%t_clock  = zclock_raw - s_timer%tsub_clock 
     177#endif 
     178 !     IF(s_timer%cname==trim('lbc_lnk_2d')) write(*,*) zclock_raw , s_timer%tsub_clock 
    159179       
    160180      ! Correction of parent section 
    161181      IF( .NOT. PRESENT(csection) ) THEN 
    162          s_wrk => s_timer 
    163          DO WHILE ( ASSOCIATED(s_wrk%parent_section ) ) 
    164             s_wrk => s_wrk%parent_section 
    165             s_wrk%tsub_cpu   = s_wrk%tsub_cpu   + s_timer%t_cpu  
    166             s_wrk%tsub_clock = s_wrk%tsub_clock + s_timer%t_clock               
    167          END DO 
     182         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              
     185         ENDIF 
    168186      ENDIF 
    169187             
     
    186204      s_timer%l_tdone = .TRUE. 
    187205      ! 
     206      ! 
     207      ! we come back 
     208      IF ( ASSOCIATED(s_timer%parent_section ) ) s_timer => s_timer%parent_section 
     209      
     210!      write(*,*) 'end of stop ', s_timer%cname 
     211 
    188212   END SUBROUTINE timing_stop 
    189213  
     
    211235         WRITE(numtime,*) '                             NEMO team' 
    212236         WRITE(numtime,*) '                  Ocean General Circulation Model' 
    213          WRITE(numtime,*) '                        version 3.6  (2015) ' 
     237         WRITE(numtime,*) '                        version 4.0  (2019) ' 
    214238         WRITE(numtime,*) 
    215239         WRITE(numtime,*) '                        Timing Informations ' 
     
    219243       
    220244      ! Compute clock function overhead 
    221  
     245#if defined key_mpp_mpi         
    222246      t_overclock = MPI_WTIME() 
    223247      t_overclock = MPI_WTIME() - t_overclock 
     248#else         
     249      CALL SYSTEM_CLOCK(COUNT_RATE=ncount_rate, COUNT_MAX=ncount_max) 
     250      CALL SYSTEM_CLOCK(COUNT = istart_count) 
     251      CALL SYSTEM_CLOCK(COUNT = ifinal_count) 
     252      iperiods = ifinal_count - istart_count 
     253      IF( ifinal_count < istart_count )  & 
     254          iperiods = iperiods + ncount_max  
     255      t_overclock = REAL(iperiods) / ncount_rate 
     256#endif 
    224257 
    225258      ! Compute cpu_time function overhead 
     
    235268     
    236269      CALL CPU_TIME(t_cpu(1))       
     270#if defined key_mpp_mpi         
    237271      ! Start elapsed and CPU time counters 
    238272      t_elaps(1) = MPI_WTIME() 
     273#else 
     274      CALL SYSTEM_CLOCK(COUNT_RATE=ncount_rate, COUNT_MAX=ncount_max) 
     275      CALL SYSTEM_CLOCK(COUNT = ncount) 
     276#endif                  
    239277      ! 
    240278   END SUBROUTINE timing_init 
     
    249287      TYPE(timer), POINTER :: s_temp 
    250288      INTEGER :: idum, iperiods, icode 
     289      INTEGER :: ji 
    251290      LOGICAL :: ll_ord, ll_averep 
    252291      CHARACTER(len=120) :: clfmt             
    253        
     292      REAL(wp), DIMENSION(:), ALLOCATABLE ::   timing_glob 
     293      REAL(wp) ::   zsypd   ! simulated years per day (Balaji 2017) 
     294      REAL(wp) ::   zperc, ztot 
     295 
    254296      ll_averep = .TRUE. 
    255297     
     
    257299      CALL CPU_TIME(t_cpu(2)) 
    258300      t_cpu(2)   = t_cpu(2)    - t_cpu(1)   - t_overcpu 
     301#if defined key_mpp_mpi 
    259302      t_elaps(2) = MPI_WTIME() - t_elaps(1) - t_overclock 
     303#else 
     304      CALL SYSTEM_CLOCK(COUNT = nfinal_count) 
     305      iperiods = nfinal_count - ncount 
     306      IF( nfinal_count < ncount )  & 
     307          iperiods = iperiods + ncount_max  
     308      t_elaps(2) = REAL(iperiods) / ncount_rate - t_overclock 
     309#endif       
    260310 
    261311      ! End of timings on date & time 
     
    270320      END DO 
    271321      idum = nsize 
    272       IF(lk_mpp) CALL mpp_sum(idum) 
     322      CALL mpp_sum('timing', idum) 
    273323      IF( idum/jpnij /= nsize ) THEN 
    274324         IF( lwriter ) WRITE(numtime,*) '        ===> W A R N I N G: ' 
     
    280330      ENDIF    
    281331 
     332#if defined key_mpp_mpi       
    282333      ! in MPI gather some info 
    283334      ALLOCATE( all_etime(jpnij), all_ctime(jpnij) ) 
    284335      CALL MPI_ALLGATHER(t_elaps(2), 1, MPI_DOUBLE_PRECISION,   & 
    285336                         all_etime , 1, MPI_DOUBLE_PRECISION,   & 
    286                          MPI_COMM_OPA, icode) 
     337                         MPI_COMM_OCE, icode) 
    287338      CALL MPI_ALLGATHER(t_cpu(2) , 1, MPI_DOUBLE_PRECISION,   & 
    288339                         all_ctime, 1, MPI_DOUBLE_PRECISION,   & 
    289                          MPI_COMM_OPA, icode) 
     340                         MPI_COMM_OCE, icode) 
    290341      tot_etime = SUM(all_etime(:)) 
    291342      tot_ctime = SUM(all_ctime(:)) 
     343#else 
     344      tot_etime = t_elaps(2) 
     345      tot_ctime = t_cpu  (2)            
     346#endif 
    292347 
    293348      ! write output file 
     
    297352      IF( lwriter ) WRITE(numtime,'(5x,f12.3,1x,f12.3)')  tot_etime, tot_ctime 
    298353      IF( lwriter ) WRITE(numtime,*)  
     354#if defined key_mpp_mpi 
    299355      IF( ll_averep ) CALL waver_info 
    300356      CALL wmpi_info 
     357#endif       
    301358      IF( lwriter ) CALL wcurrent_info 
    302359       
     
    311368      &       ctime(2)(1:2), ctime(2)(3:4), ctime(2)(5:6),   & 
    312369      &       czone(1:3),    czone(4:5) 
     370 
     371#if defined key_mpp_mpi 
     372      ALLOCATE(timing_glob(4*jpnij), stat=icode) 
     373      CALL MPI_GATHER( (/compute_time, waiting_time(1), waiting_time(2), elapsed_time/),   & 
     374         &             4, MPI_DOUBLE_PRECISION, timing_glob, 4, MPI_DOUBLE_PRECISION, 0, MPI_COMM_OCE, icode) 
     375      IF( narea == 1 ) THEN 
     376         WRITE(numtime,*) ' ' 
     377         WRITE(numtime,*) ' Report on time spent on waiting MPI messages ' 
     378         WRITE(numtime,*) '    total timing measured between nit000+1 and nitend-1 ' 
     379         WRITE(numtime,*) '    warning: includes restarts writing time if output before nitend... ' 
     380         WRITE(numtime,*) ' ' 
     381         DO ji = 1, jpnij 
     382            ztot = SUM( timing_glob(4*ji-3:4*ji-1) ) 
     383            WRITE(numtime,'(A28,F11.6,            A34,I8)') 'Computing       time : ',timing_glob(4*ji-3), ' on MPI rank : ', ji 
     384            IF ( ztot /= 0. ) zperc = timing_glob(4*ji-2) / ztot * 100. 
     385            WRITE(numtime,'(A28,F11.6,A2, F4.1,A3,A25,I8)') 'Waiting lbc_lnk time : ',timing_glob(4*ji-2)   & 
     386               &                                                         , ' (',      zperc,' %)',   ' on MPI rank : ', ji 
     387            IF ( ztot /= 0. ) zperc = timing_glob(4*ji-1) / ztot * 100. 
     388            WRITE(numtime,'(A28,F11.6,A2, F4.1,A3,A25,I8)') 'Waiting  global time : ',timing_glob(4*ji-1)   & 
     389               &                                                         , ' (',      zperc,' %)',   ' on MPI rank : ', ji 
     390            zsypd = rn_rdt * REAL(nitend-nit000-1, wp) / (timing_glob(4*ji) * 365.) 
     391            WRITE(numtime,'(A28,F11.6,A7,F10.3,A2,A15,I8)') 'Total           time : ',timing_glob(4*ji  )   & 
     392               &                                                         , ' (SYPD: ', zsypd, ')',   ' on MPI rank : ', ji 
     393         END DO 
     394      ENDIF 
     395      DEALLOCATE(timing_glob) 
     396#endif       
    313397 
    314398      IF( lwriter ) CLOSE(numtime)  
     
    365449   END SUBROUTINE wcurrent_info 
    366450 
     451#if defined key_mpp_mpi      
    367452   SUBROUTINE waver_info 
    368453      !!---------------------------------------------------------------------- 
     
    438523         CALL MPI_GATHER(s_timer%cname     , 20, MPI_CHARACTER,   & 
    439524                         sl_timer_glob%cname, 20, MPI_CHARACTER,   & 
    440                          0, MPI_COMM_OPA, icode) 
     525                         0, MPI_COMM_OCE, icode) 
    441526         CALL MPI_GATHER(s_timer%tsum_clock     , 1, MPI_DOUBLE_PRECISION,   & 
    442527                         sl_timer_glob%tsum_clock, 1, MPI_DOUBLE_PRECISION,   & 
    443                          0, MPI_COMM_OPA, icode) 
     528                         0, MPI_COMM_OCE, icode) 
    444529         CALL MPI_GATHER(s_timer%tsum_cpu     , 1, MPI_DOUBLE_PRECISION,   & 
    445530                         sl_timer_glob%tsum_cpu, 1, MPI_DOUBLE_PRECISION,   & 
    446                          0, MPI_COMM_OPA, icode) 
     531                         0, MPI_COMM_OCE, icode) 
    447532         CALL MPI_GATHER(s_timer%niter     , 1, MPI_INTEGER,   & 
    448533                         sl_timer_glob%niter, 1, MPI_INTEGER,   & 
    449                          0, MPI_COMM_OPA, icode) 
     534                         0, MPI_COMM_OCE, icode) 
    450535 
    451536         IF( narea == 1 .AND. ASSOCIATED(s_timer%next) ) THEN 
     
    461546         s_timer => s_timer%next 
    462547      END DO       
    463  
    464          WRITE(*,*) 'ARPDBG: timing: done gathers' 
    465548       
    466549      IF( narea == 1 ) THEN     
     
    485568            sl_timer_glob => sl_timer_glob%next                                 
    486569         END DO 
    487  
    488          WRITE(*,*) 'ARPDBG: timing: done computing stats' 
    489570       
    490571         ! reorder the averaged list by CPU time       
     
    608689      ! 
    609690   END SUBROUTINE wmpi_info 
     691#endif    
    610692 
    611693 
     
    643725         ALLOCATE(s_wrk) 
    644726         s_wrk => NULL() 
    645           
     727         ! 
     728         ALLOCATE(s_timer_old) 
     729         s_timer_old%cname       = cdinfo 
     730         s_timer_old%t_cpu      = 0._wp 
     731         s_timer_old%t_clock    = 0._wp 
     732         s_timer_old%tsum_cpu   = 0._wp 
     733         s_timer_old%tsum_clock = 0._wp 
     734         s_timer_old%tmax_cpu   = 0._wp 
     735         s_timer_old%tmax_clock = 0._wp 
     736         s_timer_old%tmin_cpu   = 0._wp 
     737         s_timer_old%tmin_clock = 0._wp 
     738         s_timer_old%tsub_cpu   = 0._wp 
     739         s_timer_old%tsub_clock = 0._wp 
     740         s_timer_old%ncount      = 0 
     741         s_timer_old%ncount_rate = 0 
     742         s_timer_old%ncount_max  = 0 
     743         s_timer_old%niter       = 0 
     744         s_timer_old%l_tdone  = .TRUE. 
     745         s_timer_old%next => NULL() 
     746         s_timer_old%prev => NULL() 
     747 
    646748      ELSE 
    647749         s_timer => s_timer_root 
    648750         ! case of already existing area (typically inside a loop) 
     751   !         write(*,*) 'in ini_var for routine : ', cdinfo 
    649752         DO WHILE( ASSOCIATED(s_timer) )  
    650             IF( TRIM(s_timer%cname) .EQ. TRIM(cdinfo) ) RETURN 
     753            IF( TRIM(s_timer%cname) .EQ. TRIM(cdinfo) ) THEN 
     754 !             write(*,*) 'in ini_var for routine : ', cdinfo,' we return'            
     755               RETURN ! cdinfo is already in the chain 
     756            ENDIF 
    651757            s_timer => s_timer%next 
    652758         END DO 
    653           
     759 
    654760         ! end of the chain 
    655761         s_timer => s_timer_root 
     
    657763            s_timer => s_timer%next 
    658764         END DO 
    659            
    660          ALLOCATE(s_timer%next)       
     765 
     766    !     write(*,*) 'after search', s_timer%cname 
     767         ! cdinfo is not part of the chain so we add it with initialisation           
     768          ALLOCATE(s_timer%next) 
     769    !     write(*,*) 'after allocation of next' 
     770   
    661771         s_timer%next%cname       = cdinfo 
    662772         s_timer%next%t_cpu      = 0._wp 
     
    679789         s_timer%next%next => NULL() 
    680790         s_timer => s_timer%next 
    681  
    682          ! are we inside a section 
    683          s_wrk => s_timer%prev 
    684          ll_section = .FALSE. 
    685          DO WHILE( ASSOCIATED(s_wrk) .AND. .NOT. ll_section ) 
    686             IF( .NOT. s_wrk%l_tdone ) THEN 
    687                ll_section = .TRUE. 
    688                s_timer%parent_section => s_wrk  
    689             ENDIF 
    690             s_wrk => s_wrk%prev 
    691          END DO  
    692       ENDIF          
    693       ! 
     791      ENDIF  
     792      !    write(*,*) 'after allocation' 
     793     ! 
    694794   END SUBROUTINE timing_ini_var 
    695795 
     
    704804!      IF(lwp) WRITE(numout,*) 'timing_reset : instrumented routines for timing' 
    705805!      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~' 
    706 !      CALL timing_list(s_timer_root) 
     806      CALL timing_list(s_timer_root) 
    707807!      WRITE(numout,*) 
    708808      ! 
Note: See TracChangeset for help on using the changeset viewer.