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 10172 for NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/OCE/LBC – NEMO

Ignore:
Timestamp:
2018-10-04T17:32:54+02:00 (6 years ago)
Author:
smasson
Message:

dev_r10164_HPC09_ESIWACE_PREP_MERGE: action 2b: improve of timing, add computing and waiting time, see #2133

Location:
NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/OCE/LBC
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/OCE/LBC/lib_mpp.F90

    r10170 r10172  
    170170   INTEGER, PUBLIC                               ::   n_sequence = 0               !: # of communicated arrays 
    171171   LOGICAL                                       ::   l_comm_report_done = .false. !: print report only once 
    172  
     172    
     173   ! timing summary report 
     174   REAL(wp), PUBLIC ::  waiting_time = 0._wp, compute_time = 0._wp, elapsed_time = 0._wp 
     175    
    173176   REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::   tampon   ! buffer in case of bsend 
    174177 
     
    16091612      ! 
    16101613   END SUBROUTINE mpp_lnk_2d_icb 
     1614 
     1615    
     1616   SUBROUTINE tic_tac (l_tic) 
     1617 
     1618    LOGICAL, INTENT(IN) :: l_tic 
     1619    REAL(wp), SAVE :: tic_wt, tic_ct = 0._wp 
     1620 
     1621    IF( ncom_stp <= nit000 ) RETURN 
     1622    IF( ncom_stp == nitend ) RETURN 
     1623     
     1624#if defined key_mpp_mpi 
     1625    IF ( l_tic ) THEN 
     1626       tic_wt = MPI_Wtime()                                                        ! start count tic->tac (waiting time) 
     1627       IF ( tic_ct > 0.0_wp ) compute_time = compute_time + MPI_Wtime() - tic_ct   ! cumulate count tac->tic 
     1628    ELSE 
     1629       waiting_time = waiting_time + MPI_Wtime() - tic_wt                          ! cumulate count tic->tac 
     1630       tic_ct = MPI_Wtime()                                                        ! start count tac->tic (waiting time) 
     1631    ENDIF 
     1632#endif 
     1633     
     1634   END SUBROUTINE tic_tac 
     1635 
    16111636    
    16121637#else 
  • NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/OCE/LBC/mpp_lnk_generic.h90

    r10170 r10172  
    205205      ENDIF 
    206206      ! 
     207      IF( ln_timing ) CALL tic_tac(.TRUE.) 
     208      ! 
    207209      SELECT CASE ( nbondi ) 
    208210      CASE ( -1 ) 
     
    223225      END SELECT 
    224226      ! 
     227      IF( ln_timing ) CALL tic_tac(.FALSE.) 
     228      ! 
     229      ! 
    225230      !                           ! Write Dirichlet lateral conditions 
    226231      iihom = nlci-nn_hls 
     
    281286      imigr = nn_hls * jpi * ipk * ipl * ipf 
    282287      ! 
     288      IF( ln_timing ) CALL tic_tac(.TRUE.) 
     289      !  
    283290      SELECT CASE ( nbondj ) 
    284291      CASE ( -1 ) 
     
    299306      END SELECT 
    300307      ! 
     308      IF( ln_timing ) CALL tic_tac(.FALSE.) 
    301309      !                           ! Write Dirichlet lateral conditions 
    302310      ijhom = nlcj-nn_hls 
  • NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/OCE/LBC/mpp_nfd_generic.h90

    r10068 r10172  
    116116            END DO 
    117117         END DO 
     118         ! 
     119         IF( ln_timing ) CALL tic_tac(.TRUE.) 
    118120         ! 
    119121         DO jr = 1, nsndto 
     
    167169            END DO 
    168170         ENDIF 
     171         ! 
     172         IF( ln_timing ) CALL tic_tac(.FALSE.) 
     173         ! 
    169174         DO jf = 1, ipf 
    170175            CALL lbc_nfd_nogather( ztabl(:,:,:,:,jf), ztabr(:,:,:,:,jf), cd_nat LBC_ARG, psgn LBC_ARG )   ! North fold boundary condition 
     
    195200         IF ( jpni*jpnj /= jpnij ) ztab(:,:,:,:,:)=0._wp 
    196201         ! 
     202         IF( ln_timing ) CALL tic_tac(.TRUE.) 
     203         ! 
    197204         CALL MPI_ALLGATHER( znorthloc  , itaille, MPI_DOUBLE_PRECISION,                & 
    198205            &                znorthgloio, itaille, MPI_DOUBLE_PRECISION, ncomm_north, ierr ) 
     206         ! 
     207         IF( ln_timing ) CALL tic_tac(.FALSE.) 
    199208         ! 
    200209         DO jr = 1, ndim_rank_north         ! recover the global north array 
Note: See TracChangeset for help on using the changeset viewer.