Changeset 3706


Ignore:
Timestamp:
Jun 11, 2020, 11:09:38 AM (4 years ago)
Author:
adurocher
Message:

Added timers for physiq and display physic profiling

Location:
LMDZ6/branches/Optimisation_LMDZ
Files:
1 added
3 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Optimisation_LMDZ/bld.cfg

    r3441 r3706  
    9999bld::excl_dep        use::ifile_attr
    100100bld::excl_dep        use::ixml_tree
     101bld::excl_dep        use::omp_lib
    101102
    102103# Don't generate interface files
  • LMDZ6/branches/Optimisation_LMDZ/libf/phy_common/mod_phys_lmdz_mpi_transfert.F90

    r3465 r3706  
    4646                     reduce_min_mpi_r,reduce_min_mpi_r1,reduce_min_mpi_r2,reduce_min_mpi_r3,reduce_min_mpi_r4
    4747  END INTERFACE
     48 
     49  INTERFACE reduce_max_mpi
     50    MODULE PROCEDURE reduce_max_mpi_r
     51  END INTERFACE
    4852
    4953 INTERFACE grid1dTo2d_mpi
     
    11151119  END SUBROUTINE reduce_min_mpi_r4
    11161120
    1117 
     1121  SUBROUTINE reduce_max_mpi_r(VarIn, VarOut)
     1122    USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
     1123    IMPLICIT NONE
     1124 
     1125    REAL,INTENT(IN)  :: VarIn
     1126    REAL,INTENT(OUT) :: VarOut
     1127    REAL             :: VarIn_tmp(1)
     1128    REAL             :: VarOut_tmp(1)
     1129   
     1130    VarIn_tmp(1)=VarIn   
     1131    CALL reduce_max_mpi_rgen(VarIn_tmp,Varout_tmp,1)
     1132    VarOut=VarOut_tmp(1)
     1133 
     1134  END SUBROUTINE reduce_max_mpi_r
    11181135
    11191136
     
    18051822       
    18061823  END SUBROUTINE reduce_sum_mpi_rgen
     1824 
     1825  SUBROUTINE reduce_max_mpi_rgen(VarIn,VarOut,nb)
     1826    USE mod_phys_lmdz_mpi_data
     1827    USE mod_grid_phy_lmdz
     1828
     1829    IMPLICIT NONE
     1830
     1831#ifdef CPP_MPI
     1832    INCLUDE 'mpif.h'
     1833#endif
     1834   
     1835    INTEGER,INTENT(IN) :: nb
     1836    REAL,DIMENSION(nb),INTENT(IN) :: VarIn
     1837    REAL,DIMENSION(nb),INTENT(OUT) :: VarOut   
     1838    INTEGER :: ierr
     1839 
     1840    IF (.not.is_using_mpi) THEN
     1841      VarOut(:)=VarIn(:)
     1842      RETURN
     1843    ENDIF
     1844   
     1845#ifdef CPP_MPI
     1846    CALL MPI_REDUCE(VarIn,VarOut,nb,MPI_REAL_LMDZ,MPI_MAX,mpi_master,COMM_LMDZ_PHY,ierr)
     1847#endif
     1848       
     1849  END SUBROUTINE reduce_max_mpi_rgen
    18071850
    18081851
  • LMDZ6/branches/Optimisation_LMDZ/libf/phylmd/physiq_mod.F90

    r3632 r3706  
    1515       flxmass_w, &
    1616       d_u, d_v, d_t, d_qx, d_ps)
    17 
     17    USE profiling_physic_mod, only : enter_profile, exit_profile, print_profile
    1818    USE assert_m, only: assert
    1919    USE ioipsl, only: histbeg, histvert, histdef, histend, histsync, &
     
    11821182    REAL pi
    11831183
     1184    integer, save :: itau_profiling_physiq ! Print frequency for physiq profiling
     1185
    11841186    pi = 4. * ATAN(1.)
    11851187
     
    12261228    CALL assert(paprs(:, nbp_lev + 1) < paprs(:, nbp_lev), &
    12271229            "physiq_mod paprs bad order")
    1228 
    1229     IF (first) THEN
     1230    IF (first) THEN     
     1231       call enter_profile("phy_init")
     1232
     1233       itau_profiling_physiq=-1 ! Default is -1 : never
     1234       CALL getin_p('itau_profiling_physiq', itau_profiling_physiq )
     1235
    12301236       CALL init_etat0_limit_unstruct
    12311237       IF (.NOT. create_etat0_limit) CALL init_limit_read(days_elapsed)
     
    12841290       first=.FALSE.
    12851291
     1292       call exit_profile("phy_init")
    12861293    ENDIF  ! first
     1294   
     1295    call enter_profile("physiq")
    12871296
    12881297    !ym => necessaire pour iflag_con != 2   
     
    13041313
    13051314    IF (debut) THEN
     1315       call enter_profile("phy_init")
     1316
    13061317       CALL suphel ! initialiser constantes et parametres phys.
    13071318! tau_gl : constante de rappel de la temperature a la surface de la glace - en
     
    13681379       WRITE(lunout,*) 'Call to infocfields from physiq'
    13691380       CALL infocfields_init
    1370 
    13711381    ENDIF
    13721382
     
    20222032      sollwdown(:)= sollwdown(:) + betalwoff *(-1.*ZFLDN0(:,1) - &
    20232033                    sollwdown(:))
    2024 
    2025 
    2026     ENDIF
     2034      call exit_profile("phy_init")
     2035   ENDIF
    20272036    !
    20282037    !   ****************     Fin  de   IF ( debut  )   ***************
     
    24452454
    24462455    IF (iflag_pbl/=0) THEN
     2456     
     2457       call enter_profile("phy_pbl")
    24472458
    24482459       !jyg+nrlmd<
     
    26232634            t_seri(:,1),q_seri(:,1),u_seri(:,1),v_seri(:,1),evap_pot)
    26242635
     2636      call exit_profile("phy_pbl")
    26252637    ENDIF
    26262638    ! =================================================================== c
     
    26972709!!                       itapcv, cvpas, itap-1, cvpas_0
    26982710    IF (MOD(itapcv,cvpas).EQ.0 .OR. MOD(itap-1,cvpas_0).EQ.0) THEN
     2711     
     2712      call enter_profile("phy_convection")
    26992713
    27002714    !
     
    30183032    proba_notrig(:) = 1.
    30193033    itapcv = 0
     3034   
     3035    call exit_profile("phy_convection")
    30203036    ENDIF !  (MOD(itapcv,cvpas).EQ.0 .OR. MOD(itapcv,cvpas_0).EQ.0)
    30213037!
     
    31083124       !
    31093125       IF (MOD(itapwk,wkpas).EQ.0) THEN
    3110           !
     3126          call enter_profile("phy_wake")
     3127         
    31113128          DO k=1,klev
    31123129             DO i=1,klon
     
    31663183          !jyg    Reinitialize itapwk when wakes have been called
    31673184          itapwk = 0
     3185          call exit_profile("phy_wake")
    31683186       ENDIF !  (MOD(itapwk,wkpas).EQ.0)
    31693187       !
     
    32333251
    32343252    ELSE
    3235 
     3253       call enter_profile("phy_thermique")
    32363254       !  Thermiques
    32373255       !  ==========
     
    34023420       ENDIF
    34033421
     3422       call exit_profile("phy_thermique")
    34043423    ENDIF
    34053424    !
     
    34233442       print *,'itap, ->fisrtilp ',itap
    34243443    ENDIF
    3425     !
     3444    call enter_profile("phy_ls_condens")
     3445   
    34263446    CALL fisrtilp(phys_tstep,paprs,pplay, &
    34273447         t_seri, q_seri,ptconv,ratqs, &
     
    34363456    WHERE (rain_lsc < 0) rain_lsc = 0.
    34373457    WHERE (snow_lsc < 0) snow_lsc = 0.
     3458   
     3459    call exit_profile("phy_ls_condens")
    34383460
    34393461!+JLD
     
    36993721
    37003722    IF (type_trac == 'inca') THEN
     3723       call enter_profile("phy_inca")
    37013724#ifdef INCA
    37023725       CALL VTe(VTphysiq)
     
    37533776       CALL VTb(VTphysiq)
    37543777#endif
     3778       call exit_profile("phy_inca")
    37553779    ENDIF !type_trac = inca
    37563780
     
    37603784    !
    37613785    IF (MOD(itaprad,radpas).EQ.0) THEN
    3762 
     3786       call enter_profile("phy_rayonnement")
    37633787       !
    37643788       !jq - introduce the aerosol direct and first indirect radiative forcings
    37653789       !jq - Johannes Quaas, 27/11/2003 (quaas@lmd.jussieu.fr)
    37663790       IF (flag_aerosol .GT. 0) THEN
     3791          call enter_profile("read_aerosol")
    37673792          IF (iflag_rrtm .EQ. 0) THEN !--old radiation
    37683793             IF (.NOT. aerosol_couple) THEN
     
    38423867             ENDIF
    38433868          ENDIF
     3869          call exit_profile("read_aerosol")
    38443870       ELSE   !--flag_aerosol = 0
    38453871          tausum_aero(:,:,:) = 0.
     
    38653891       !--updates tausum_aero,tau_aero,piz_aero,cg_aero
    38663892       IF (flag_aerosol_strat.GT.0) THEN
     3893          call enter_profile("read_aerosol")
    38673894          IF (prt_level .GE.10) THEN
    38683895             PRINT *,'appel a readaerosolstrat', mth_cur
     
    38953922#endif
    38963923          ENDIF
     3924          call exit_profile("read_aerosol")
    38973925       ELSE
    38983926          tausum_aero(:,:,id_STRAT_phy) = 0.
     
    42204248          zxtsol(:) = zsav_tsol (:)
    42214249       ENDIF
     4250       call exit_profile("phy_rayonnement")
    42224251    ENDIF ! MOD(itaprad,radpas)
    42234252    itaprad = itaprad + 1
     
    45024531! Inititialization
    45034532!------------------
    4504 
     4533       call enter_profile("phy_init")
    45054534       addtkeoro=0   
    45064535       CALL getin_p('addtkeoro',addtkeoro)
     
    45144543
    45154544       smallscales_tkeoro=.FALSE.   
    4516        CALL getin_p('smallscales_tkeoro',smallscales_tkeoro)
     4545       CALL getin_p('smallscales_tkeoro',smallscales_tkeoro)
     4546       call exit_profile("phy_init")
    45174547
    45184548
     
    46054635
    46064636    IF (ok_cosp) THEN
     4637       call enter_profile("phy_cosp")
    46074638       ! adeclarer
    46084639#ifdef CPP_COSP
     
    46844715       ENDIF
    46854716#endif
    4686 
     4717       call exit_profile("phy_cosp")
    46874718    ENDIF  !ok_cosp
    46884719
     
    47264757
    47274758    IF (iflag_phytrac == 1 ) THEN
    4728 
     4759      call enter_profile("phy_phytrac")
    47294760#ifdef CPP_Dust
    47304761      CALL       phytracr_spl ( debut,lafin , jD_cur,jH_cur,iflag_con,       &  ! I
     
    47704801         tr_seri, init_source)
    47714802#endif
     4803      call exit_profile("phy_phytrac")
    47724804    ENDIF    ! (iflag_phytrac=1)
    47734805
     
    50275059    !   Ecriture des sorties
    50285060    !=============================================================
     5061    call enter_profile("phy_output")
     5062
     5063    if( itau_profiling_physiq>0 .and. 0 == mod( itap, itau_profiling_physiq ) ) call print_profile()
     5064
    50295065#ifdef CPP_IOIPSL
    50305066
     
    50915127! On remet des variables a .false. apres un premier appel
    50925128    IF (debut) THEN
     5129      call enter_profile("phy_init")
    50935130#ifdef CPP_XIOS
    50945131      swaero_diag=.FALSE.
     
    51375174!      write (lunout,*)'ok_4xCO2atm= ',swaero_diag, swaerofree_diag, dryaod_diag, ok_4xCO2atm
    51385175#endif
    5139     ENDIF
     5176      call exit_profile("phy_init")
     5177   ENDIF
    51405178
    51415179    !====================================================================
     
    51775215       WRITE(lunout,*) ' physiq fin, nombre de steps ou cvpas = 1 : ', Ncvpaseq1
    51785216    ENDIF
    5179 
     5217   
     5218    call exit_profile("phy_output")
     5219    call exit_profile("physiq")
    51805220    !      first=.false.
    51815221
Note: See TracChangeset for help on using the changeset viewer.