Changeset 3865 for LMDZ6/trunk/libf/phylmd
- Timestamp:
- Mar 23, 2021, 4:14:07 PM (4 years ago)
- Location:
- LMDZ6/trunk/libf/phylmd
- Files:
-
- 6 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/trunk/libf/phylmd/carbon_cycle_mod.F90
r3857 r3865 45 45 LOGICAL, PUBLIC :: read_fco2_ocean_cor ! flag to read corrective oceanic CO2 flux 46 46 !$OMP THREADPRIVATE(read_fco2_ocean_cor) 47 REAL, PUBLIC :: var_fco2_ocean_cor ! corrective oceanic CO2 flux47 REAL, SAVE, PUBLIC :: var_fco2_ocean_cor ! corrective oceanic CO2 flux 48 48 !$OMP THREADPRIVATE(var_fco2_ocean_cor) 49 REAL, PUBLIC :: ocean_area_tot ! total oceanic area to convert flux49 REAL, SAVE, PUBLIC :: ocean_area_tot ! total oceanic area to convert flux 50 50 !$OMP THREADPRIVATE(ocean_area_tot) 51 51 LOGICAL, PUBLIC :: read_fco2_land_cor ! flag to read corrective land CO2 flux 52 52 !$OMP THREADPRIVATE(read_fco2_land_cor) 53 REAL, PUBLIC :: var_fco2_land_cor ! corrective land CO2 flux53 REAL, SAVE, PUBLIC :: var_fco2_land_cor ! corrective land CO2 flux 54 54 !$OMP THREADPRIVATE(var_fco2_land_cor) 55 REAL, PUBLIC :: land_area_tot ! total land area to convert flux55 REAL, SAVE, PUBLIC :: land_area_tot ! total land area to convert flux 56 56 !$OMP THREADPRIVATE(land_area_tot) 57 57 … … 108 108 REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fco2_ocean ! Net flux from ocean [kgCO2/m2/s] 109 109 !$OMP THREADPRIVATE(fco2_ocean) 110 REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fco2_ocean_cor ! Net corrective flux from ocean [kgCO2/m2/s]110 REAL, DIMENSION(:), ALLOCATABLE, SAVE, PUBLIC :: fco2_ocean_cor ! Net corrective flux from ocean [kgCO2/m2/s] 111 111 !$OMP THREADPRIVATE(fco2_ocean_cor) 112 REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fco2_land_cor ! Net corrective flux from land [kgCO2/m2/s]112 REAL, DIMENSION(:), ALLOCATABLE, SAVE, PUBLIC :: fco2_land_cor ! Net corrective flux from land [kgCO2/m2/s] 113 113 !$OMP THREADPRIVATE(fco2_land_cor) 114 114 … … 123 123 124 124 ! Calculated co2 field to be send to the ocean via the coupler and to ORCHIDEE 125 REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: co2_send ! Field allocated in phyetat0125 REAL, DIMENSION(:), ALLOCATABLE, SAVE, PUBLIC :: co2_send ! Field allocated in phyetat0 126 126 !$OMP THREADPRIVATE(co2_send) 127 127 -
LMDZ6/trunk/libf/phylmd/infotrac_phy.F90
r3677 r3865 20 20 INTEGER, SAVE :: nbtr 21 21 !$OMP THREADPRIVATE(nbtr) 22 23 ! ThL : number of tracers specific to INCA 24 INTEGER, SAVE :: nqINCA 25 !$OMP THREADPRIVATE(nqINCA) 22 26 23 27 #ifdef CPP_StratAer … … 33 37 INTEGER, SAVE :: nqperes 34 38 !$OMP THREADPRIVATE(nqperes) 39 40 ! ThL : nb de traceurs dans le traceur.def 41 INTEGER, SAVE :: nqexcl 42 !$OMP THREADPRIVATE(nqexcl) 35 43 36 44 ! Name variables … … 96 104 CONTAINS 97 105 98 SUBROUTINE init_infotrac_phy(nqtot_,nqo_,nbtr_, tname_,ttext_,type_trac_,&106 SUBROUTINE init_infotrac_phy(nqtot_,nqo_,nbtr_,nqINCA_,tname_,ttext_,type_trac_,& 99 107 niadv_,conv_flg_,pbl_flg_,solsym_,& 100 108 nqfils_,nqdesc_,nqdesc_tot_,iqfils_,iqpere_,& … … 118 126 INTEGER,INTENT(IN) :: nqo_ 119 127 INTEGER,INTENT(IN) :: nbtr_ 128 INTEGER,INTENT(IN) :: nqINCA_ 120 129 #ifdef CPP_StratAer 121 130 INTEGER,INTENT(IN) :: nbtr_bin_ … … 130 139 CHARACTER(len=4),INTENT(IN) :: type_trac_ 131 140 INTEGER,INTENT(IN) :: niadv_ (nqtot_) ! equivalent dyn / physique 132 INTEGER,INTENT(IN) :: conv_flg_(n btr_)133 INTEGER,INTENT(IN) :: pbl_flg_(n btr_)134 CHARACTER(len=8),INTENT(IN) :: solsym_(n btr_)141 INTEGER,INTENT(IN) :: conv_flg_(nqINCA_) 142 INTEGER,INTENT(IN) :: pbl_flg_(nqINCA_) 143 CHARACTER(len=8),INTENT(IN) :: solsym_(nqINCA_) 135 144 ! Isotopes: 136 145 INTEGER,INTENT(IN) :: nqfils_(nqtot_) … … 163 172 nqo=nqo_ 164 173 nbtr=nbtr_ 174 nqINCA=nqINCA_ 165 175 #ifdef CPP_StratAer 166 176 nbtr_bin=nbtr_bin_ … … 179 189 niadv(:)=niadv_(:) 180 190 ALLOCATE(conv_flg(nbtr)) 181 conv_flg(:)=conv_flg_(:) 191 IF (type_trac == 'inco') THEN 192 conv_flg(1)=1 193 conv_flg(2:nbtr)=conv_flg_(:) 194 ELSE 195 conv_flg(:)=conv_flg_(:) 196 ENDIF 182 197 ALLOCATE(pbl_flg(nbtr)) 183 pbl_flg(:)=pbl_flg_(:) 198 IF (type_trac == 'inco') THEN 199 pbl_flg(1)=1 200 pbl_flg(2:nbtr)=pbl_flg_(:) 201 ELSE 202 pbl_flg(:)=pbl_flg_(:) 203 ENDIF 184 204 ALLOCATE(solsym(nbtr)) 185 solsym(:)=solsym_(:) 186 205 IF (type_trac == 'inco') THEN 206 solsym(1)='CO2' 207 solsym(2:nbtr)=solsym_(:) 208 ELSE 209 solsym(:)=solsym_(:) 210 ENDIF 211 187 212 IF(prt_level.ge.1) THEN 188 write(lunout,*) TRIM(modname)//": nqtot,nqo,nbtr ",nqtot,nqo,nbtr213 write(lunout,*) TRIM(modname)//": nqtot,nqo,nbtr,nqINCA",nqtot,nqo,nbtr,nqINCA 189 214 ENDIF 190 215 -
LMDZ6/trunk/libf/phylmd/phyetat0.F90
r3862 r3865 452 452 ENDIF 453 453 454 !--OB now this is for co2i 455 IF (type_trac == 'co2i' ) THEN454 !--OB now this is for co2i - ThL: and therefore also for inco 455 IF (type_trac == 'co2i' .OR. type_trac == 'inco') THEN 456 456 IF (carbon_cycle_cpl) THEN 457 457 ALLOCATE(co2_send(klon), stat=ierr) -
LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90
r3857 r3865 453 453 REAL,DIMENSION(klon) :: zrho, zt 454 454 455 INTEGER :: nqup 456 455 457 ! On calcul le nouveau tau: 456 458 itau_w = itau_phy + itap … … 2436 2438 ENDIF !--type_trac co2i 2437 2439 2440 IF (type_trac == 'inco') THEN 2441 nqup = nqo+1 2442 DO iq=nqo+1, nqup 2443 !--3D fields 2444 CALL histwrite_phy(o_trac(iq-nqo), tr_seri(:,:,iq-nqo)) 2445 CALL histwrite_phy(o_dtr_vdf(iq-nqo),d_tr_cl(:,:,iq-nqo)) 2446 CALL histwrite_phy(o_dtr_the(iq-nqo),d_tr_th(:,:,iq-nqo)) 2447 CALL histwrite_phy(o_dtr_con(iq-nqo),d_tr_cv(:,:,iq-nqo)) 2448 !--2D fields 2449 !--CO2 burden 2450 zx_tmp_fi2d=0. 2451 IF (vars_defined) THEN 2452 DO k=1,klev 2453 zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+zmasse(:,k)*tr_seri(:,k,iq-nqo) 2454 ENDDO 2455 ENDIF 2456 CALL histwrite_phy(o_trac_cum(iq-nqo), zx_tmp_fi2d) 2457 ENDDO !--iq 2458 !--CO2 net fluxes 2459 CALL histwrite_phy(o_flx_co2_land, fco2_land) 2460 CALL histwrite_phy(o_flx_co2_ocean, fco2_ocean) 2461 CALL histwrite_phy(o_flx_co2_ocean_cor, fco2_ocean_cor) 2462 CALL histwrite_phy(o_flx_co2_land_cor, fco2_land_cor) 2463 CALL histwrite_phy(o_flx_co2_ff, fco2_ff) 2464 CALL histwrite_phy(o_flx_co2_bb, fco2_bb) 2465 ENDIF !--type_trac inco 2466 2438 2467 ENDIF !(iflag_phytrac==1) 2439 2468 -
LMDZ6/trunk/libf/phylmd/physiq_mod.F90
r3861 r3865 39 39 USE ioipsl_getin_p_mod, ONLY : getin_p 40 40 USE indice_sol_mod 41 USE infotrac_phy, ONLY: nqtot, nbtr, nqo, type_trac 41 USE infotrac_phy, ONLY: nqtot, nbtr, nqo, type_trac, nqINCA 42 42 USE iophy 43 43 USE limit_read_mod, ONLY : init_limit_read … … 1412 1412 tau_overturning_th(:)=0. 1413 1413 1414 IF (type_trac == 'inca' ) THEN1414 IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN 1415 1415 ! jg : initialisation jusqu'au ces variables sont dans restart 1416 1416 ccm(:,:,:) = 0. … … 1968 1968 cg_aero(:,:,:,:) = init_cginca 1969 1969 ! 1970 1971 1972 CALL VTe(VTinca) 1973 CALL VTb(VTphysiq) 1974 #endif 1975 ELSEIF (type_trac == 'inco') THEN 1976 #ifdef INCA 1977 CALL VTe(VTphysiq) 1978 CALL VTb(VTinca) 1979 calday = REAL(days_elapsed) + jH_cur 1980 WRITE(lunout,*) 'initial time chemini', days_elapsed, calday 1981 1982 CALL chemini( & 1983 rg, & 1984 ra, & 1985 cell_area, & 1986 latitude_deg, & 1987 longitude_deg, & 1988 presnivs, & 1989 calday, & 1990 klon, & 1991 nqtot, & 1992 nqo+1, & ! Note ThL: diff is here with case 'inca' 1993 pdtphys, & 1994 annee_ref, & 1995 year_cur, & 1996 day_ref, & 1997 day_ini, & 1998 start_time, & 1999 itau_phy, & 2000 date0, & 2001 io_lon, & 2002 io_lat, & 2003 chemistry_couple, & 2004 init_source, & 2005 init_tauinca, & 2006 init_pizinca, & 2007 init_cginca, & 2008 init_ccminca) 2009 2010 2011 ! initialisation des variables depuis le restart de inca 2012 ccm(:,:,:) = init_ccminca 2013 tau_aero(:,:,:,:) = init_tauinca 2014 piz_aero(:,:,:,:) = init_pizinca 2015 cg_aero(:,:,:,:) = init_cginca 2016 ! 1970 2017 1971 2018 … … 3792 3839 CALL VTe(VTinca) 3793 3840 CALL VTb(VTphysiq) 3794 #endif 3795 ENDIF !type_trac = inca 3841 #endif 3842 ELSEIF (type_trac == 'inco') THEN 3843 #ifdef INCA 3844 CALL VTe(VTphysiq) 3845 CALL VTb(VTinca) 3846 calday = REAL(days_elapsed + 1) + jH_cur 3847 3848 CALL chemtime(itap+itau_phy-1, date0, phys_tstep, itap) 3849 CALL AEROSOL_METEO_CALC( & 3850 calday,pdtphys,pplay,paprs,t,pmflxr,pmflxs, & 3851 prfl,psfl,pctsrf,cell_area, & 3852 latitude_deg,longitude_deg,u10m,v10m) 3853 3854 zxsnow_dummy(:) = 0.0 3855 3856 CALL chemhook_begin (calday, & 3857 days_elapsed+1, & 3858 jH_cur, & 3859 pctsrf(1,1), & 3860 latitude_deg, & 3861 longitude_deg, & 3862 cell_area, & 3863 paprs, & 3864 pplay, & 3865 coefh(1:klon,1:klev,is_ave), & 3866 pphi, & 3867 t_seri, & 3868 u, & 3869 v, & 3870 rot, & 3871 wo(:, :, 1), & 3872 q_seri, & 3873 zxtsol, & 3874 zt2m, & 3875 zxsnow_dummy, & 3876 solsw, & 3877 albsol1, & 3878 rain_fall, & 3879 snow_fall, & 3880 itop_con, & 3881 ibas_con, & 3882 cldfra, & 3883 nbp_lon, & 3884 nbp_lat-1, & 3885 tr_seri(:,:,2:nbtr), & ! Note ThL: diff is here with case 'inca' 3886 ftsol, & 3887 paprs, & 3888 cdragh, & 3889 cdragm, & 3890 pctsrf, & 3891 pdtphys, & 3892 itap) 3893 3894 CALL VTe(VTinca) 3895 CALL VTb(VTphysiq) 3896 #endif 3897 ENDIF !type_trac = inca or inco 3796 3898 IF (type_trac == 'repr') THEN 3797 3899 #ifdef REPROBUS … … 4945 5047 CALL VTb(VTphysiq) 4946 5048 #endif 5049 ELSEIF (type_trac == 'inco') THEN 5050 #ifdef INCA 5051 CALL VTe(VTphysiq) 5052 CALL VTb(VTinca) 5053 5054 CALL chemhook_end ( & 5055 phys_tstep, & 5056 pplay, & 5057 t_seri, & 5058 tr_seri(:,:,2:nbtr), & ! Note ThL: diff is here with case 'inca' 5059 nbtr, & 5060 paprs, & 5061 q_seri, & 5062 cell_area, & 5063 pphi, & 5064 pphis, & 5065 zx_rh, & 5066 aps, bps, ap, bp) 5067 5068 CALL VTe(VTinca) 5069 CALL VTb(VTphysiq) 5070 #endif 4947 5071 ENDIF 4948 5072 -
LMDZ6/trunk/libf/phylmd/phytrac_mod.F90
r3861 r3865 56 56 SUBROUTINE phytrac_init() 57 57 USE dimphy 58 USE infotrac_phy, ONLY: nbtr, type_trac58 USE infotrac_phy, ONLY: nbtr, nqINCA, type_trac 59 59 USE tracco2i_mod, ONLY: tracco2i_init 60 60 IMPLICIT NONE … … 81 81 CASE('co2i') 82 82 ! -- CO2 interactif -- 83 CALL tracco2i_init() 84 CASE('inco') 83 85 CALL tracco2i_init() 84 86 END SELECT … … 122 124 USE phys_cal_mod, only : hour 123 125 USE dimphy 124 USE infotrac_phy, ONLY: nbtr, type_trac, conv_flg, solsym, pbl_flg126 USE infotrac_phy, ONLY: nbtr, nqINCA, type_trac, conv_flg, solsym, pbl_flg 125 127 USE mod_grid_phy_lmdz 126 128 USE mod_phys_lmdz_para … … 505 507 iflag_vdf_trac= 1 506 508 iflag_con_trac= 1 509 CASE('inco') 510 source(:,1) = 0. ! from CO2i 511 source(:,2:nbtr)=init_source(:,:) ! from INCA 512 aerosol(1) = .FALSE. ! from CO2i 513 CALL tracinca_init(aerosol(2:nbtr),lessivage) ! from INCA 514 pbl_flg(1) = 1 ! From CO2i 515 iflag_the_trac= 1 ! From CO2i 516 iflag_vdf_trac= 1 ! From CO2i 517 iflag_con_trac= 1 ! From CO2i 507 518 #ifdef CPP_StratAer 508 519 CASE('coag') … … 571 582 !--co2 tracers are not scavenged 572 583 flag_cvltr(it)=.FALSE. 573 584 CASE('inco') ! Add ThL 585 flag_cvltr(it)=.FALSE. 574 586 #ifdef CPP_StratAer 575 587 CASE('coag') … … 614 626 write(lunout,*) 'flag_cvltr = ', flag_cvltr 615 627 616 IF (lessivage .AND. type_trac .EQ. 'inca') THEN628 IF (lessivage .AND. (type_trac .EQ. 'inca' .OR. type_trac .EQ. 'inco')) THEN ! Mod ThL 617 629 CALL abort_physic('phytrac', 'lessivage=T config_inca=inca impossible',1) 618 630 ! STOP … … 666 678 ! -- sign convention : positive into the atmosphere 667 679 680 CALL tracco2i(pdtphys, debutphy, & 681 xlat, xlon, pphis, pphi, & 682 t_seri, pplay, paprs, tr_seri, source) 683 CASE('inco') ! Add ThL 668 684 CALL tracco2i(pdtphys, debutphy, & 669 685 xlat, xlon, pphis, pphi, & … … 1104 1120 tau_aero, piz_aero, cg_aero, ccm, & 1105 1121 rfname, & 1106 tr_seri, source) 1107 1108 1122 tr_seri, source) 1123 ELSEIF (type_trac == 'inco') THEN ! Add ThL 1124 CALL tracinca(& 1125 nstep, julien, gmtime, lafin, & 1126 pdtphys, t_seri, paprs, pplay, & 1127 pmfu, upwd, ftsol, pctsrf, pphis, & 1128 pphi, albsol, sh, ch, rh, & 1129 cldfra, rneb, diafra, cldliq, & 1130 itop_con, ibas_con, pmflxr, pmflxs, & 1131 prfl, psfl, aerosol_couple, flxmass_w, & 1132 tau_aero, piz_aero, cg_aero, ccm, & 1133 rfname, & 1134 tr_seri(:,:,2:nbtr), source(:,2:nbtr)) ! Difference with case 'inca' 1109 1135 ENDIF 1110 1136 !=============================================================
Note: See TracChangeset
for help on using the changeset viewer.