Changeset 3706 for LMDZ6/branches
- Timestamp:
- Jun 11, 2020, 11:09:38 AM (4 years ago)
- Location:
- LMDZ6/branches/Optimisation_LMDZ
- Files:
-
- 1 added
- 3 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/branches/Optimisation_LMDZ/bld.cfg
r3441 r3706 99 99 bld::excl_dep use::ifile_attr 100 100 bld::excl_dep use::ixml_tree 101 bld::excl_dep use::omp_lib 101 102 102 103 # Don't generate interface files -
LMDZ6/branches/Optimisation_LMDZ/libf/phy_common/mod_phys_lmdz_mpi_transfert.F90
r3465 r3706 46 46 reduce_min_mpi_r,reduce_min_mpi_r1,reduce_min_mpi_r2,reduce_min_mpi_r3,reduce_min_mpi_r4 47 47 END INTERFACE 48 49 INTERFACE reduce_max_mpi 50 MODULE PROCEDURE reduce_max_mpi_r 51 END INTERFACE 48 52 49 53 INTERFACE grid1dTo2d_mpi … … 1115 1119 END SUBROUTINE reduce_min_mpi_r4 1116 1120 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 1118 1135 1119 1136 … … 1805 1822 1806 1823 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 1807 1850 1808 1851 -
LMDZ6/branches/Optimisation_LMDZ/libf/phylmd/physiq_mod.F90
r3632 r3706 15 15 flxmass_w, & 16 16 d_u, d_v, d_t, d_qx, d_ps) 17 17 USE profiling_physic_mod, only : enter_profile, exit_profile, print_profile 18 18 USE assert_m, only: assert 19 19 USE ioipsl, only: histbeg, histvert, histdef, histend, histsync, & … … 1182 1182 REAL pi 1183 1183 1184 integer, save :: itau_profiling_physiq ! Print frequency for physiq profiling 1185 1184 1186 pi = 4. * ATAN(1.) 1185 1187 … … 1226 1228 CALL assert(paprs(:, nbp_lev + 1) < paprs(:, nbp_lev), & 1227 1229 "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 1230 1236 CALL init_etat0_limit_unstruct 1231 1237 IF (.NOT. create_etat0_limit) CALL init_limit_read(days_elapsed) … … 1284 1290 first=.FALSE. 1285 1291 1292 call exit_profile("phy_init") 1286 1293 ENDIF ! first 1294 1295 call enter_profile("physiq") 1287 1296 1288 1297 !ym => necessaire pour iflag_con != 2 … … 1304 1313 1305 1314 IF (debut) THEN 1315 call enter_profile("phy_init") 1316 1306 1317 CALL suphel ! initialiser constantes et parametres phys. 1307 1318 ! tau_gl : constante de rappel de la temperature a la surface de la glace - en … … 1368 1379 WRITE(lunout,*) 'Call to infocfields from physiq' 1369 1380 CALL infocfields_init 1370 1371 1381 ENDIF 1372 1382 … … 2022 2032 sollwdown(:)= sollwdown(:) + betalwoff *(-1.*ZFLDN0(:,1) - & 2023 2033 sollwdown(:)) 2024 2025 2026 ENDIF 2034 call exit_profile("phy_init") 2035 ENDIF 2027 2036 ! 2028 2037 ! **************** Fin de IF ( debut ) *************** … … 2445 2454 2446 2455 IF (iflag_pbl/=0) THEN 2456 2457 call enter_profile("phy_pbl") 2447 2458 2448 2459 !jyg+nrlmd< … … 2623 2634 t_seri(:,1),q_seri(:,1),u_seri(:,1),v_seri(:,1),evap_pot) 2624 2635 2636 call exit_profile("phy_pbl") 2625 2637 ENDIF 2626 2638 ! =================================================================== c … … 2697 2709 !! itapcv, cvpas, itap-1, cvpas_0 2698 2710 IF (MOD(itapcv,cvpas).EQ.0 .OR. MOD(itap-1,cvpas_0).EQ.0) THEN 2711 2712 call enter_profile("phy_convection") 2699 2713 2700 2714 ! … … 3018 3032 proba_notrig(:) = 1. 3019 3033 itapcv = 0 3034 3035 call exit_profile("phy_convection") 3020 3036 ENDIF ! (MOD(itapcv,cvpas).EQ.0 .OR. MOD(itapcv,cvpas_0).EQ.0) 3021 3037 ! … … 3108 3124 ! 3109 3125 IF (MOD(itapwk,wkpas).EQ.0) THEN 3110 ! 3126 call enter_profile("phy_wake") 3127 3111 3128 DO k=1,klev 3112 3129 DO i=1,klon … … 3166 3183 !jyg Reinitialize itapwk when wakes have been called 3167 3184 itapwk = 0 3185 call exit_profile("phy_wake") 3168 3186 ENDIF ! (MOD(itapwk,wkpas).EQ.0) 3169 3187 ! … … 3233 3251 3234 3252 ELSE 3235 3253 call enter_profile("phy_thermique") 3236 3254 ! Thermiques 3237 3255 ! ========== … … 3402 3420 ENDIF 3403 3421 3422 call exit_profile("phy_thermique") 3404 3423 ENDIF 3405 3424 ! … … 3423 3442 print *,'itap, ->fisrtilp ',itap 3424 3443 ENDIF 3425 ! 3444 call enter_profile("phy_ls_condens") 3445 3426 3446 CALL fisrtilp(phys_tstep,paprs,pplay, & 3427 3447 t_seri, q_seri,ptconv,ratqs, & … … 3436 3456 WHERE (rain_lsc < 0) rain_lsc = 0. 3437 3457 WHERE (snow_lsc < 0) snow_lsc = 0. 3458 3459 call exit_profile("phy_ls_condens") 3438 3460 3439 3461 !+JLD … … 3699 3721 3700 3722 IF (type_trac == 'inca') THEN 3723 call enter_profile("phy_inca") 3701 3724 #ifdef INCA 3702 3725 CALL VTe(VTphysiq) … … 3753 3776 CALL VTb(VTphysiq) 3754 3777 #endif 3778 call exit_profile("phy_inca") 3755 3779 ENDIF !type_trac = inca 3756 3780 … … 3760 3784 ! 3761 3785 IF (MOD(itaprad,radpas).EQ.0) THEN 3762 3786 call enter_profile("phy_rayonnement") 3763 3787 ! 3764 3788 !jq - introduce the aerosol direct and first indirect radiative forcings 3765 3789 !jq - Johannes Quaas, 27/11/2003 (quaas@lmd.jussieu.fr) 3766 3790 IF (flag_aerosol .GT. 0) THEN 3791 call enter_profile("read_aerosol") 3767 3792 IF (iflag_rrtm .EQ. 0) THEN !--old radiation 3768 3793 IF (.NOT. aerosol_couple) THEN … … 3842 3867 ENDIF 3843 3868 ENDIF 3869 call exit_profile("read_aerosol") 3844 3870 ELSE !--flag_aerosol = 0 3845 3871 tausum_aero(:,:,:) = 0. … … 3865 3891 !--updates tausum_aero,tau_aero,piz_aero,cg_aero 3866 3892 IF (flag_aerosol_strat.GT.0) THEN 3893 call enter_profile("read_aerosol") 3867 3894 IF (prt_level .GE.10) THEN 3868 3895 PRINT *,'appel a readaerosolstrat', mth_cur … … 3895 3922 #endif 3896 3923 ENDIF 3924 call exit_profile("read_aerosol") 3897 3925 ELSE 3898 3926 tausum_aero(:,:,id_STRAT_phy) = 0. … … 4220 4248 zxtsol(:) = zsav_tsol (:) 4221 4249 ENDIF 4250 call exit_profile("phy_rayonnement") 4222 4251 ENDIF ! MOD(itaprad,radpas) 4223 4252 itaprad = itaprad + 1 … … 4502 4531 ! Inititialization 4503 4532 !------------------ 4504 4533 call enter_profile("phy_init") 4505 4534 addtkeoro=0 4506 4535 CALL getin_p('addtkeoro',addtkeoro) … … 4514 4543 4515 4544 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") 4517 4547 4518 4548 … … 4605 4635 4606 4636 IF (ok_cosp) THEN 4637 call enter_profile("phy_cosp") 4607 4638 ! adeclarer 4608 4639 #ifdef CPP_COSP … … 4684 4715 ENDIF 4685 4716 #endif 4686 4717 call exit_profile("phy_cosp") 4687 4718 ENDIF !ok_cosp 4688 4719 … … 4726 4757 4727 4758 IF (iflag_phytrac == 1 ) THEN 4728 4759 call enter_profile("phy_phytrac") 4729 4760 #ifdef CPP_Dust 4730 4761 CALL phytracr_spl ( debut,lafin , jD_cur,jH_cur,iflag_con, & ! I … … 4770 4801 tr_seri, init_source) 4771 4802 #endif 4803 call exit_profile("phy_phytrac") 4772 4804 ENDIF ! (iflag_phytrac=1) 4773 4805 … … 5027 5059 ! Ecriture des sorties 5028 5060 !============================================================= 5061 call enter_profile("phy_output") 5062 5063 if( itau_profiling_physiq>0 .and. 0 == mod( itap, itau_profiling_physiq ) ) call print_profile() 5064 5029 5065 #ifdef CPP_IOIPSL 5030 5066 … … 5091 5127 ! On remet des variables a .false. apres un premier appel 5092 5128 IF (debut) THEN 5129 call enter_profile("phy_init") 5093 5130 #ifdef CPP_XIOS 5094 5131 swaero_diag=.FALSE. … … 5137 5174 ! write (lunout,*)'ok_4xCO2atm= ',swaero_diag, swaerofree_diag, dryaod_diag, ok_4xCO2atm 5138 5175 #endif 5139 ENDIF 5176 call exit_profile("phy_init") 5177 ENDIF 5140 5178 5141 5179 !==================================================================== … … 5177 5215 WRITE(lunout,*) ' physiq fin, nombre de steps ou cvpas = 1 : ', Ncvpaseq1 5178 5216 ENDIF 5179 5217 5218 call exit_profile("phy_output") 5219 call exit_profile("physiq") 5180 5220 ! first=.false. 5181 5221
Note: See TracChangeset
for help on using the changeset viewer.