Changeset 3666
- Timestamp:
- Apr 20, 2020, 12:13:34 PM (5 years ago)
- Location:
- LMDZ6/trunk/libf
- Files:
-
- 12 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/trunk/libf/dyn3d_common/infotrac.F90
r3362 r3666 422 422 IF (type_trac == 'repr') THEN 423 423 #ifdef REPROBUS 424 CALL Init_chem_rep_trac(nbtr )424 CALL Init_chem_rep_trac(nbtr,nqo,tnom_0) 425 425 #endif 426 426 END IF -
LMDZ6/trunk/libf/dyn3dmem/leapfrog_loc.F
r3583 r3666 1543 1543 endif 1544 1544 #endif 1545 #ifdef REPROBUS 1546 if (type_trac == 'repr') then 1547 call finalize_reprobus 1548 endif 1549 #endif 1545 1550 1546 1551 c$OMP MASTER … … 1593 1598 endif 1594 1599 #endif 1600 #ifdef REPROBUS 1601 if (type_trac == 'repr') then 1602 call finalize_reprobus 1603 endif 1604 #endif 1595 1605 1596 1606 c$OMP MASTER … … 1742 1752 if (type_trac == 'inca') then 1743 1753 call finalize_inca 1754 endif 1755 #endif 1756 #ifdef REPROBUS 1757 if (type_trac == 'repr') then 1758 call finalize_reprobus 1744 1759 endif 1745 1760 #endif … … 1834 1849 endif 1835 1850 #endif 1851 #ifdef REPROBUS 1852 if (type_trac == 'repr') then 1853 call finalize_reprobus 1854 endif 1855 #endif 1836 1856 1837 1857 c$OMP MASTER -
LMDZ6/trunk/libf/dynphy_lonlat/phylmd/iniphysiq_mod.F90
r3579 r3666 27 27 #ifdef REPROBUS 28 28 USE CHEM_REP, ONLY : Init_chem_rep_phys 29 #ifdef CPP_PARA 30 USE parallel_lmdz, ONLY : mpi_size, mpi_rank 31 USE bands, ONLY : distrib_phys 32 #endif 33 USE mod_phys_lmdz_omp_data, ONLY: klon_omp 29 34 #endif 30 35 USE control_mod, ONLY: dayref,anneeref,day_step,nday,offline, iphysiq, config_inca … … 46 51 USE ioipsl_getin_p_mod, ONLY: getin_p 47 52 USE slab_heat_transp_mod, ONLY: ini_slab_transp_geom 48 #ifdef REPROBUS49 USE CHEM_REP, ONLY : Init_chem_rep_phys50 #endif51 53 IMPLICIT NONE 52 54 … … 152 154 IF (type_trac == 'repr') THEN 153 155 #ifdef REPROBUS 154 CALL Init_chem_rep_phys(klon_omp,nlayer) 156 call Init_chem_rep_phys(klon_omp,nlayer) 157 call init_reprobus_para( & 158 nbp_lon,nbp_lat,nbp_lev,klon_glo,mpi_size, & 159 distrib_phys,communicator) 155 160 #endif 156 161 ENDIF … … 168 173 #endif 169 174 END IF 175 IF (type_trac == 'repr') THEN 176 #ifdef REPROBUS 177 call init_reprobus_para( & 178 nbp_lon,nbp_lat,nbp_lev,klon_glo,mpi_size, & 179 distrib_phys,communicator) 180 #endif 181 ENDIF 170 182 171 183 !!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/) -
LMDZ6/trunk/libf/phylmd/phys_output_ctrlout_mod.F90
r3622 r3666 1776 1776 TYPE(ctrl_out), SAVE, ALLOCATABLE :: o_trac(:) 1777 1777 TYPE(ctrl_out), SAVE, ALLOCATABLE :: o_trac_cum(:) 1778 #ifdef REPROBUS1779 TYPE(ctrl_out), SAVE, ALLOCATABLE :: o_nas(:)1780 #endif1781 1778 TYPE(ctrl_out), SAVE, ALLOCATABLE :: o_dtr_vdf(:) 1782 1779 TYPE(ctrl_out), SAVE, ALLOCATABLE :: o_dtr_the(:) -
LMDZ6/trunk/libf/phylmd/phys_output_mod.F90
r3630 r3666 46 46 USE vertical_layers_mod, ONLY: ap,bp,preff,presnivs, aps, bps, pseudoalt 47 47 USE time_phylmdz_mod, ONLY: day_ini, itau_phy, start_time, annee_ref, day_ref 48 #ifdef REPROBUS49 USE chem_rep, ONLY: nbnas, tnamenas, ttextnas50 #endif51 48 #ifdef CPP_XIOS 52 49 ! ug Pour les sorties XIOS … … 160 157 IF (.NOT. ALLOCATED(o_trac)) ALLOCATE(o_trac(nqtot)) 161 158 IF (.NOT. ALLOCATED(o_trac_cum)) ALLOCATE(o_trac_cum(nqtot)) 162 #ifdef REPROBUS163 IF (.NOT. ALLOCATED(o_nas)) ALLOCATE(o_nas(nbnas))164 #endif165 159 ALLOCATE(o_dtr_the(nqtot),o_dtr_con(nqtot),o_dtr_lessi_impa(nqtot)) 166 160 ALLOCATE(o_dtr_lessi_nucl(nqtot),o_dtr_insc(nqtot),o_dtr_bcscav(nqtot)) … … 581 575 ENDDO 582 576 ENDIF 583 IF (type_trac=='repr') THEN584 #ifdef REPROBUS585 DO iiq=1,nbnas586 o_nas(iiq) = ctrl_out((/ 4, 5, 5, 5, 10, 10, 11, 11, 11, 11 /), &587 tnamenas(iiq),ttextnas(iiq), "-", &588 (/ '', '', '', '', '', '', '', '', '', '' /))589 ENDDO590 #endif591 ENDIF592 577 593 578 ENDDO ! iff -
LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90
r3630 r3666 172 172 o_uxv, o_vxq, o_vxT, o_wxq, o_vxphi, & 173 173 o_wxT, o_uxu, o_vxv, o_TxT, o_trac, & 174 #ifdef REPROBUS175 o_nas, &176 #endif177 174 o_dtr_vdf, o_dtr_the, o_dtr_con, & 178 175 o_dtr_lessi_impa, o_dtr_lessi_nucl, & … … 331 328 surf_PM25_sulf, tau_strat_550, tausum_strat, & 332 329 vsed_aer, tau_strat_1020, f_r_wet 333 #endif334 335 #ifdef REPROBUS336 USE CHEM_REP, ONLY : nas, nbnas, tnamenas, ttextnas337 330 #endif 338 331 … … 2267 2260 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 2268 2261 IF (iflag_phytrac == 1 ) then 2269 IF (type_trac == 'lmdz' .OR. type_trac == ' repr' .OR. type_trac == 'coag') THEN2262 IF (type_trac == 'lmdz' .OR. type_trac == 'coag') THEN 2270 2263 DO iq=nqo+1, nqtot 2271 2264 !--3D fields … … 2292 2285 ENDDO 2293 2286 ENDIF 2294 #ifndef REPROBUS2295 2287 CALL histwrite_phy(o_trac_cum(iq-nqo), zx_tmp_fi2d) 2296 #endif2297 2288 ENDDO !--iq 2298 2289 ENDIF !--type_trac … … 2322 2313 ENDIF !--type_trac co2i 2323 2314 2324 IF (type_trac == 'repr') THEN2325 #ifdef REPROBUS2326 DO iq=1,nbnas2327 CALL histwrite_phy(o_nas(iq), nas(:,:,iq))2328 ENDDO2329 #endif2330 ENDIF2331 2332 2315 ENDIF !(iflag_phytrac==1) 2333 2316 -
LMDZ6/trunk/libf/phylmd/physiq_mod.F90
r3632 r3666 246 246 #endif 247 247 #ifdef REPROBUS 248 USE CHEM_REP, ONLY : Init_chem_rep_xjour 248 USE CHEM_REP, ONLY : Init_chem_rep_xjour, & 249 d_q_rep,d_ql_rep,d_qi_rep,ptrop,ttrop, & 250 ztrop, gravit,itroprep, Z1,Z2,fac,B 249 251 #endif 250 252 USE indice_sol_mod … … 1950 1952 #endif 1951 1953 ENDIF 1954 IF (type_trac == 'repr') THEN 1955 #ifdef REPROBUS 1956 CALL chemini_rep( & 1957 presnivs, & 1958 pdtphys, & 1959 annee_ref, & 1960 day_ref, & 1961 day_ini, & 1962 start_time, & 1963 itau_phy, & 1964 io_lon, & 1965 io_lat) 1966 #endif 1967 ENDIF 1952 1968 1953 1969 !$omp single … … 2286 2302 2287 2303 wo(:,:,1)=ozonecm(latitude_deg, paprs,read_climoz,rjour=zzz) 2304 #ifdef REPROBUS 2305 ptrop=dyn_tropopause(t_seri, ztsol, paprs, pplay, rot)/100. 2306 DO i = 1, klon 2307 Z1=t_seri(i,itroprep(i)+1) 2308 Z2=t_seri(i,itroprep(i)) 2309 fac=(Z1-Z2)/alog(pplay(i,itroprep(i)+1)/pplay(i,itroprep(i))) 2310 B=Z2-fac*alog(pplay(i,itroprep(i))) 2311 ttrop(i)= fac*alog(ptrop(i))+B 2312 ! 2313 Z1= 1.e-3 * ( pphi(i,itroprep(i)+1)+pphis(i) ) / gravit 2314 Z2= 1.e-3 * ( pphi(i,itroprep(i)) +pphis(i) ) / gravit 2315 fac=(Z1-Z2)/alog(pplay(i,itroprep(i)+1)/pplay(i,itroprep(i))) 2316 B=Z2-fac*alog(pplay(i,itroprep(i))) 2317 ztrop(i)=fac*alog(ptrop(i))+B 2318 ENDDO 2319 #endif 2288 2320 ELSE 2289 2321 !--- ro3i = elapsed days number since current year 1st january, 0h … … 3754 3786 #endif 3755 3787 ENDIF !type_trac = inca 3756 3788 IF (type_trac == 'repr') THEN 3789 #ifdef REPROBUS 3790 !CALL chemtime_rep(itap+itau_phy-1, date0, dtime, itap) 3791 CALL chemtime_rep(itap+itau_phy-1, date0, phys_tstep, itap) 3792 #endif 3793 ENDIF 3757 3794 3758 3795 ! … … 4719 4756 4720 4757 IF (type_trac=='repr') THEN 4758 !MM pas d'impact, car on recupere q_seri,tr_seri,t_seri via phys_local_var_mod 4759 !MM dans Reprobus 4721 4760 sh_in(:,:) = q_seri(:,:) 4761 #ifdef REPROBUS 4762 d_q_rep(:,:) = 0. 4763 d_ql_rep(:,:) = 0. 4764 d_qi_rep(:,:) = 0. 4765 #endif 4722 4766 ELSE 4723 4767 sh_in(:,:) = qx(:,:,ivap) … … 4769 4813 d_tr_dyn, & !<<RomP 4770 4814 tr_seri, init_source) 4815 #ifdef REPROBUS 4816 4817 4818 print*,'avt add phys rep',abortphy 4819 4820 CALL add_phys_tend & 4821 (du0,dv0,dt0,d_q_rep,d_ql_rep,d_qi_rep,paprs,& 4822 'rep',abortphy,flag_inhib_tend,itap,0) 4823 IF (abortphy==1) Print*,'ERROR ABORT REP' 4824 4825 print*,'apr add phys rep',abortphy 4826 4827 #endif 4828 4771 4829 #endif 4772 4830 ENDIF ! (iflag_phytrac=1) -
LMDZ6/trunk/libf/phylmd/radiation_AR4.F90
r2346 r3666 482 482 #ifdef REPROBUS 483 483 USE chem_rep, ONLY: rsuntime, ok_suntime 484 USE print_control_mod, ONLY: lunout 484 485 #endif 485 486 -
LMDZ6/trunk/libf/phylmd/radlwsw_m.F90
r3630 r3666 453 453 IF (type_trac == 'repr') THEN 454 454 #ifdef REPROBUS 455 if(ok_SUNTIME) PSCT = solaireTIME/zdist/zdist 456 print*,'Constante solaire: ',PSCT*zdist*zdist 455 IF (iflag_rrtm==0) THEN 456 if(ok_SUNTIME) PSCT = solaireTIME/zdist/zdist 457 print*,'Constante solaire: ',PSCT*zdist*zdist 458 END IF 457 459 #endif 458 460 END IF -
LMDZ6/trunk/libf/phylmd/rrtm/lwu.F90
r2027 r3666 74 74 !USE YOERDI , ONLY : RCH4 ,RN2O ,RCFC11 ,RCFC12 75 75 USE YOERDU , ONLY : R10E ,REPSCO ,REPSCQ 76 #ifdef REPROBUS 77 USE chem_rep, ONLY: rch42d, rn2o2d, rcfc112d, rcfc122d, ok_rtime2d 78 USE infotrac_phy, ONLY : type_trac 79 #endif 76 80 77 81 … … 316 320 PABCU(JL,17,IC)=PABCU(JL,17,ICP1)+ ZUAER(JL,4) *ZDUC(JL,IC)*ZDIFF 317 321 PABCU(JL,18,IC)=PABCU(JL,18,ICP1)+ ZUAER(JL,5) *ZDUC(JL,IC)*ZDIFF 322 #ifdef REPROBUS 323 IF (type_trac=='repr'.and. ok_rtime2d) THEN 324 !- CH4 325 PABCU(JL,19,IC)=PABCU(JL,19,ICP1)& 326 & + ZABLY(JL,2,IC)*RCH42D(JL, IC)/PCCO2*ZPHM6(JL)*ZDIFF 327 PABCU(JL,20,IC)=PABCU(JL,20,ICP1)& 328 & + ZABLY(JL,3,IC)*RCH42D(JL, IC)/PCCO2*ZPSM6(JL)*ZDIFF 329 !- N2O 330 PABCU(JL,21,IC)=PABCU(JL,21,ICP1)& 331 & + ZABLY(JL,2,IC)*RN2O2D(JL, IC)/PCCO2*ZPHN6(JL)*ZDIFF 332 PABCU(JL,22,IC)=PABCU(JL,22,ICP1)& 333 & + ZABLY(JL,3,IC)*RN2O2D(JL, IC)/PCCO2*ZPSN6(JL)*ZDIFF 334 !- CFC11 335 PABCU(JL,23,IC)=PABCU(JL,23,ICP1)& 336 & + ZABLY(JL,2,IC)*RCFC112D(JL, IC)/PCCO2 *ZDIFF 337 !- CFC12 338 PABCU(JL,24,IC)=PABCU(JL,24,ICP1)& 339 & + ZABLY(JL,2,IC)*RCFC122D(JL, IC)/PCCO2 *ZDIFF 340 341 ELSE 342 #endif 318 343 !- CH4 319 344 PABCU(JL,19,IC)=PABCU(JL,19,ICP1)& … … 332 357 PABCU(JL,24,IC)=PABCU(JL,24,ICP1)& 333 358 & + ZABLY(JL,2,IC)*RCFC12/PCCO2 *ZDIFF 359 #ifdef REPROBUS 360 END IF 361 #endif 334 362 ENDDO 335 363 ENDDO -
LMDZ6/trunk/libf/phylmd/tracreprobus_mod.F90
r3125 r3666 16 16 USE CHEM_REP, ONLY : pdt_rep, & ! pas de temps reprobus 17 17 daynum, iter, & ! jourjulien, iteration chimie 18 pdel 18 pdel,& 19 d_q_rep,d_ql_rep,d_qi_rep 19 20 #endif 20 21 IMPLICIT NONE … … 46 47 ! Local variables 47 48 !---------------- 48 INTEGER :: it, k 49 INTEGER :: it, k, niter 49 50 50 51 #ifdef REPROBUS 51 52 ! -- CHIMIE REPROBUS -- 52 pdt_rep=pdtphys/2. 53 ! pdt_rep=pdtphys/2. 54 niter=pdtphys/pdt_rep 55 write(*,*)'nb d appel de REPROBUS',niter 53 56 54 57 DO k = 1, klev … … 60 63 tr_seri(:,:,11)=tr_seri(:,:,8) 61 64 END IF 65 66 d_q_rep(:,:) =0. 67 d_ql_rep(:,:) =0. 68 d_qi_rep(:,:) =0. 62 69 63 DO iter = 1, 270 DO iter = 1,niter 64 71 daynum = FLOAT(julien) + gmtime + (iter-1)*pdt_rep/86400. 65 72 66 DO it=1, nbtr73 ! DO it=1, nbtr 67 74 ! WRITE(lunout,*)it,' ',minval(tr_seri(:,:,it)),maxval(tr_seri(:,:,it)) 68 75 ! seulement pour les especes chimiques (pas l'age de l'air) … … 70 77 ! correction: a 1.e-30 quand =0 ou negatif et 71 78 ! call abort si >ou= 1.e10 72 WRITE(*,*)it,'nqtot',nqtot,'nbtr',nbtr73 IF (it < nqtot) THEN74 WRITE(*,*)'iciav',it,nqtot75 #ifdef REPROBUS76 CALL minmaxqfi_chimie(it,tr_seri(1,1,it),0.,1.e10,'avant chimie ')77 #endif78 WRITE(*,*)iter,'avpres'79 ENDIF80 ENDDO79 ! WRITE(*,*)it,'nqtot',nqtot,'nbtr',nbtr 80 ! IF (it < nqtot) THEN 81 ! WRITE(*,*)'iciav',it,nqtot 82 !#ifdef REPROBUS 83 ! CALL minmaxqfi_chimie(it,tr_seri(1,1,it),0.,1.e10,'avant chimie ') 84 !#endif 85 ! WRITE(*,*)iter,'avpres' 86 ! ENDIF 87 ! ENDDO 81 88 82 89 #ifdef REPROBUS … … 95 102 ! et transporte par CHEM_REP 96 103 97 DO it=1, nbtr104 ! DO it=1, nbtr 98 105 ! WRITE(lunout,*)it,' ',minval(tr_seri(:,:,it)),maxval(tr_seri(:,:,it)) 99 106 ! seulement pour les especes chimiques (pas l'age de l'air) … … 101 108 ! correction: a 1.e-30 quand =0 ou negatif et 102 109 ! call abort si >ou= 1.e10 103 WRITE(*,*)it,'nqtot',nqtot,'nbtr',nbtr104 IF (it < nqtot) THEN105 WRITE(*,*)'iciap',it,nqtot106 CALL minmaxqfi_chimie(it,tr_seri(1,1,it),0.,1.e10,'apres chemmain')107 WRITE(*,*)iter,'appres'108 ENDIF109 ENDDO110 ! WRITE(*,*)it,'nqtot',nqtot,'nbtr',nbtr 111 ! IF (it < nqtot) THEN 112 ! WRITE(*,*)'iciap',it,nqtot 113 ! CALL minmaxqfi_chimie(it,tr_seri(1,1,it),0.,1.e10,'apres chemmain') 114 ! WRITE(*,*)iter,'appres' 115 ! ENDIF 116 ! ENDDO 110 117 111 118 #endif -
LMDZ6/trunk/libf/phylmd/tropopause_m.F90
r3141 r3666 17 17 USE geometry_mod, ONLY: latitude_deg, longitude_deg 18 18 USE vertical_layers_mod, ONLY: aps, bps, preff 19 #ifdef REPROBUS 20 USE chem_rep, ONLY: itroprep 21 #endif 19 22 20 23 !------------------------------------------------------------------------------- … … 108 111 DO kt=1,klev-1; IF(pplay(i,kt+1)>dyn_tropopause(i)) EXIT; END DO; kp=kt 109 112 END IF 113 #ifdef REPROBUS 114 itroprep(i)=MAX(kt,kp) 115 #endif 110 116 !--- LAST TROPOSPHERIC LAYER INDEX NEEDED 111 117 IF(PRESENT(itrop)) itrop(i)=MAX(kt,kp)
Note: See TracChangeset
for help on using the changeset viewer.