Changeset 3230 for trunk/LMDZ.MARS
- Timestamp:
- Feb 20, 2024, 10:14:22 PM (9 months ago)
- Location:
- trunk/LMDZ.MARS
- Files:
-
- 1 added
- 1 deleted
- 8 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.MARS/changelog.txt
r3225 r3230 4511 4511 Remove interactive checking with XIOS whether a field should be sent to it; 4512 4512 some yet unresolved issues arise when using this in mixed MPI-OpenMP mode... 4513 4514 == 20/02/2024 == LL 4515 * Move soil_tifeedback into a module waterice_tifeedback_mod.F90 4516 * The flag to call tifeedback has been changed from "tifeedback" to surfaceice_tifeedback for clarity 4517 * Add the possibility to change the thermal inertia while pore ices is forming in the soil: to do so, use the flag poreice_tifeedback. The computation is done i 4518 n waterice_tifeedback_mod.F90. 4519 For now, surfaceice_tifeedback and poreice_tifeedback can not be called together 4520 , we might think about how to merge later. -
trunk/LMDZ.MARS/libf/phymars/callkeys.h
r3167 r3230 12 12 & ,callg2d,linear,rayleigh & 13 13 & ,scavenging,sedimentation & 14 & ,activice,water, tifeedback,microphys,supersat,caps,photochem&14 & ,activice,water,microphys,supersat,caps,photochem & 15 15 & ,calltherm,callrichsl,callslope,tituscap,callyamada4,co2clouds & 16 16 & ,co2useh2o,meteo_flux,activeco2ice,CLFvaryingCO2,spantCO2 & … … 18 18 & ,latentheat_surfwater,gwd_convective_source,startphy_file & 19 19 & ,hdo,hdofrac,cst_cap_albedo,temp_dependent_m,refill_watercap & 20 & ,cloud_adapt_ts, callatke 20 & ,cloud_adapt_ts,callatke,surfaceice_tifeedback & 21 & , poreice_tifeedback 21 22 !$OMP THREADPRIVATE(/callkeys_l/) 22 23 … … 79 80 logical cloud_adapt_ts ! adaptative timestep for cloud microphysics 80 81 logical sedimentation 81 logical activice,tifeedback,supersat,caps 82 logical activice,surfaceice_tifeedback,supersat,caps 83 logical poreice_tifeedback 82 84 logical co2clouds,co2useh2o,meteo_flux,CLFvaryingCO2,satindexco2 83 85 logical activeco2ice -
trunk/LMDZ.MARS/libf/phymars/comsoil_h.F90
r3183 r3230 30 30 31 31 ! Subsurface tracers: 32 logical, save :: adsorption_soil ! boolean to call adosrption (or not)33 real, save :: choice_ads ! Choice for adsorption isotherm (3 means no adsorption, see soilwater.F90)34 real, save, allocatable, dimension(:,:,:,:) :: qsoil ! subsurface tracers (kg/m^3 of regol)35 integer, parameter :: nqsoil = 3 ! number of subsurface tracers, only three when working with water32 logical, save :: adsorption_soil ! boolean to call adosrption (or not) 33 real, save :: choice_ads ! Choice for adsorption isotherm (3 means no adsorption, see soilwater.F90) 34 real, save, allocatable, dimension(:,:,:,:) :: qsoil ! subsurface tracers (kg/m^3 of regol) 35 integer, parameter :: nqsoil = 3 ! number of subsurface tracers, only three when working with water 36 36 integer, parameter :: igcm_h2o_vap_soil = 1 37 37 integer, parameter :: igcm_h2o_ice_soil = 2 38 38 integer, parameter :: igcm_h2o_vap_ads = 3 39 39 REAL, parameter :: porosity_reg = 0.45 40 40 !$OMP THREADPRIVATE(adsorption_soil,qsoil,choice_ads) 41 41 -
trunk/LMDZ.MARS/libf/phymars/conf_phys.F
r3167 r3230 683 683 ! thermal inertia feedback 684 684 write(*,*) "Activate the thermal inertia feedback ?" 685 tifeedback=.false. ! default value686 call getin_p(" tifeedback",tifeedback)687 write(*,*) " tifeedback = ",tifeedback685 surfaceice_tifeedback=.false. ! default value 686 call getin_p("surfaceice_tifeedback",surfaceice_tifeedback) 687 write(*,*) " surfaceice_tifeedback = ",surfaceice_tifeedback 688 688 689 689 ! Test of incompatibility: 690 690 691 if ( tifeedback.and..not.water) then692 print*,'if tifeedback is used,'691 if (surfaceice_tifeedback.and..not.water) then 692 print*,'if surfaceice_tifeedback is used,' 693 693 print*,'water should be used too' 694 694 call abort_physic(modname, 695 & " tifeedback requires water",1)696 endif 697 698 if ( tifeedback.and..not.callsoil) then699 print*,'if tifeedback is used,'695 & "surfaceice_tifeedback requires water",1) 696 endif 697 698 if (surfaceice_tifeedback.and..not.callsoil) then 699 print*,'if surfaceice_tifeedback is used,' 700 700 print*,'callsoil should be used too' 701 701 call abort_physic(modname, 702 & " tifeedback requires callsoil",1)702 & "surfaceice_tifeedback requires callsoil",1) 703 703 endif 704 704 … … 1041 1041 if (adsorption_soil) choice_ads = 1 1042 1042 call getin_p("choice_ads",choice_ads) 1043 1043 1044 poreice_tifeedback = .false. 1045 call getin_p("poreice_tifeedback",poreice_tifeedback) 1046 write(*,*) 'poreice_tifeedback=',poreice_tifeedback 1047 if (poreice_tifeedback .and. (.not. adsorption_soil)) then 1048 write(*,*)"Pore ice TI feedback can be run only if 1049 & adsorption_soil = True" 1050 call abort_physic(modname, 1051 & "Pore ice TI feedback be used with adsorption_soil 1052 & = true",1) 1053 endif 1044 1054 c ---------------------------------------------------------- 1045 1055 -
trunk/LMDZ.MARS/libf/phymars/physiq_mod.F
r3219 r3230 123 123 use pbl_parameters_mod, only: pbl_parameters 124 124 use lmdz_atke_turbulence_ini, only : atke_ini 125 use waterice_tifeedback_mod, only : waterice_tifeedback 125 126 IMPLICIT NONE 126 127 c======================================================================= … … 282 283 REAL inertiesoil_tifeedback(ngrid,nsoilmx,nslope) ! Time varying subsurface 283 284 ! thermal inertia (J.s-1/2.m-2.K-1) 284 ! (used only when tifeedback =.true.)285 ! (used only when tifeedback surface or pore =.true.) 285 286 c Variables used by the CO2 clouds microphysical scheme: 286 287 DOUBLE PRECISION riceco2(ngrid,nlayer) ! co2 ice geometric mean radius (m) … … 540 541 541 542 ! Variable for ice table 542 REAL :: rhowater_surf(ngrid,nslope) ! Water density at the surface [kg/m^3]543 REAL :: rhowater_surf_sat(ngrid,nslope) ! Water density at the surface at saturation [kg/m^3]544 REAL :: rhowater_soil(ngrid,nsoilmx,nslope) ! Water density in soil layers [kg/m^3]545 REAL,PARAMETER :: alpha_clap_h2o = 28.9074 ! Coeff for Clapeyron law [/]546 REAL,PARAMETER :: beta_clap_h2o = -6143.7 ! Coeff for Clapeyron law [K]547 REAL :: pvap_surf(ngrid) ! Water vapor partial pressure in first layer [Pa]548 REAL,PARAMETER :: m_co2 = 44.01E-3 ! CO2 molecular mass [kg/mol]549 REAL,PARAMETER :: m_noco2 = 33.37E-3 ! Non condensible mol mass [kg/mol]550 REAL :: ztmp1,ztmp2 ! intermediate variables to compute the mean molar mass of the layer551 543 REAL :: rhowater_surf(ngrid,nslope) ! Water density at the surface [kg/m^3] 544 REAL :: rhowater_surf_sat(ngrid,nslope) ! Water density at the surface at saturation [kg/m^3] 545 REAL :: rhowater_soil(ngrid,nsoilmx,nslope) ! Water density in soil layers [kg/m^3] 546 REAL,PARAMETER :: alpha_clap_h2o = 28.9074 ! Coeff for Clapeyron law [/] 547 REAL,PARAMETER :: beta_clap_h2o = -6143.7 ! Coeff for Clapeyron law [K] 548 REAL :: pvap_surf(ngrid) ! Water vapor partial pressure in first layer [Pa] 549 REAL,PARAMETER :: m_co2 = 44.01E-3 ! CO2 molecular mass [kg/mol] 550 REAL,PARAMETER :: m_noco2 = 33.37E-3 ! Non condensible mol mass [kg/mol] 551 REAL :: ztmp1,ztmp2 ! intermediate variables to compute the mean molar mass of the layer 552 REAL :: pore_icefraction(ngrid,nsoilmx,nslope) ! ice filling fraction in the pores 552 553 ! Variable for the computation of the TKE with parameterization from ATKE working group 553 554 REAL :: viscom ! kinematic molecular viscosity for momentum … … 694 695 IF (callsoil) THEN 695 696 c Thermal inertia feedback: 696 IF ( tifeedback) THEN697 IF (surfaceice_tifeedback.or.poreice_tifeedback) THEN 697 698 DO islope = 1,nslope 698 CALL soil_tifeedback(ngrid,nsoilmx,699 s qsurf(:, :,islope),700 s inertiesoil_tifeedback (:,:,islope))699 CALL waterice_tifeedback(ngrid,nsoilmx,nslope, 700 s qsurf(:,igcm_h2o_ice,:),pore_icefraction, 701 s inertiesoil_tifeedback) 701 702 ENDDO 702 703 CALL soil(ngrid,nsoilmx,firstcall, … … 1498 1499 c Calling vdif (Martian version WITH CO2 condensation) 1499 1500 dwatercap_dif(:,:) = 0. 1500 1501 1501 CALL vdifc(ngrid,nlayer,nsoilmx,nq,nqsoil,zpopsk, 1502 1502 $ ptimestep,capcal,lwrite, 1503 1503 $ zplay,zplev,zzlay,zzlev,z0, 1504 $ pu,pv,zh,pq,tsurf,tsoil,emis,qsurf,qsoil, 1504 $ pu,pv,zh,pq,tsurf,tsoil,emis,qsurf, 1505 $ qsoil,pore_icefraction, 1505 1506 $ zdum1,zdum2,zdh,pdq,zflubid, 1506 1507 $ zdudif,zdvdif,zdhdif,zdtsdif,q2, … … 2385 2386 IF (callsoil) THEN 2386 2387 c Thermal inertia feedback 2387 IF ( tifeedback) THEN2388 DO islope = 1,nslope2389 CALL soil_tifeedback(ngrid,nsoilmx,2390 s qsurf(:, :,islope),2391 s inertiesoil_tifeedback(:,:, islope))2392 ENDDO2388 IF (surfaceice_tifeedback.or.poreice_tifeedback) THEN 2389 2390 CALL waterice_tifeedback(ngrid,nsoilmx,nslope, 2391 s qsurf(:,igcm_h2o_ice,:),pore_icefraction, 2392 s inertiesoil_tifeedback(:,:,:)) 2393 2393 2394 CALL soil(ngrid,nsoilmx,.false.,inertiesoil_tifeedback, 2394 2395 s ptimestep,tsurf,tsoil,capcal,fluxgrd) … … 3551 3552 & '',albedo(:,1,islope)) 3552 3553 ENDDO 3553 if ( tifeedback) then3554 if (surfaceice_tifeedback.or.poreice_tifeedback) then 3554 3555 call write_output("soiltemp", 3555 3556 & "Soil temperature","K", … … 3558 3559 & 'Soil Thermal Inertia', 3559 3560 & 'J.s-1/2.m-2.K-1',inertiesoil_tifeedback(:,:,iflat)) 3561 3560 3562 do islope=1,nslope 3561 3563 write(str2(1:2),'(i2.2)') islope -
trunk/LMDZ.MARS/libf/phymars/soil.F
r2919 r3230 41 41 42 42 ! 0. Initialisations and preprocessing step 43 if (firstcall.or.tifeedback) then43 if(firstcall.or.surfaceice_tifeedback.or.poreice_tifeedback) then 44 44 ! note: firstcall is set to .true. or .false. by the caller 45 45 ! and not changed by soil.F -
trunk/LMDZ.MARS/libf/phymars/soilwater.F90
r3223 r3230 1 1 subroutine soilwater(ngrid, nlayer, nq, nsoil, nqsoil, ptsrf, ptsoil, ptimestep, & 2 2 exchange, qsat_surf, pq, pa, pb, pc, pd, pdqsdifpot, pqsurf, & 3 pqsoil, pplev, rhoatmo, writeoutput, zdqsdifrego, zq1temp2 )4 5 6 use comsoil_h, only: igcm_h2o_vap_soil, igcm_h2o_ice_soil, igcm_h2o_vap_ads, layer, mlayer, choice_ads 3 pqsoil, pplev, rhoatmo, writeoutput, zdqsdifrego, zq1temp2, saturation_water_ice) 4 5 6 use comsoil_h, only: igcm_h2o_vap_soil, igcm_h2o_ice_soil, igcm_h2o_vap_ads, layer, mlayer, choice_ads, porosity_reg 7 7 use comcstfi_h 8 8 use tracer_mod … … 92 92 ! Outputs : 93 93 ! ---------------------------------------------------------------------- 94 real, intent(out) :: zdqsdifrego(ngrid) ! Flux from subsurface (positive pointing outwards) 95 real, intent(out) :: zq1temp2(ngrid) ! Temporary atmospheric mixing ratio after exchange with subsurface (kg / kg) 94 real, intent(out) :: zdqsdifrego(ngrid) ! Flux from subsurface (positive pointing outwards) 95 real, intent(out) :: zq1temp2(ngrid) ! Temporary atmospheric mixing ratio after exchange with subsurface (kg / kg) 96 real*8, intent(out) :: saturation_water_ice(ngrid, nsoil) ! Water pore ice saturation level (formerly Sw) 96 97 97 98 ! Outputs for the output files … … 162 163 real*8, allocatable, save :: tortuosity(:, :) ! Tortuosity factor (formerly tortuo) 163 164 164 real*8 :: saturation_water_ice(ngrid, nsoil) ! Water pore ice saturation level (formerly Sw)165 165 real*8 :: saturation_water_ice_inter(ngrid, nsoil) ! Water pore ice saturation level at the interlayer 166 166 … … 346 346 347 347 ! These properties are defined here in order to enable custom profiles 348 porosity_ice_free(ig, ik) = 0.45D0348 porosity_ice_free(ig, ik) = porosity_reg 349 349 tortuosity(ig, ik) = 1.5D0 350 350 rho_soil(ig, ik) = 1.3D3 ! in kg/m3 of regolith (incl. porosity) -
trunk/LMDZ.MARS/libf/phymars/vdifc_mod.F
r3203 r3230 9 9 $ pplay,pplev,pzlay,pzlev,pz0, 10 10 $ pu,pv,ph,pq,ptsrf,ptsoil,pemis,pqsurf,qsoil, 11 $ pdufi,pdvfi,pdhfi,pdqfi,pfluxsrf, 11 $ pore_icefraction,pdufi,pdvfi,pdhfi, 12 $ pdqfi,pfluxsrf, 12 13 $ pdudif,pdvdif,pdhdif,pdtsrf,pq2, 13 14 $ pdqdif,pdqsdif,wstar, … … 239 240 REAL zdqsdif_tot(ngrid) ! subtimestep pdqsdif for water ice 240 241 LOGICAL :: writeoutput ! boolean to say to soilexchange.F if we are at the last iteration and thus if he can write in the diagsoil 241 242 REAL, INTENT(out) :: pore_icefraction(ngrid,nsoil,nslope) ! ice filling fraction in the pores 242 243 !! Water buyoncy 243 244 LOGICAL :: virtual … … 307 308 h2o_ice_depth(1:ngrid,1:nslope)=1 308 309 virtual = .false. 309 310 pore_icefraction(:,:,:) = 0. 310 311 c ** calcul de rho*dz et dt*rho/dz=dt*rho**2 g/dp 311 312 c avec rho=p/RT=p/ (R Theta) (p/ps)**kappa … … 1084 1085 & qsoil(ig,:,:,islope), pplev(ig,1), rho(ig), 1085 1086 & writeoutput,zdqsdif_regolith(ig,islope), 1086 & zq1temp_regolith(ig)) 1087 & zq1temp_regolith(ig), 1088 & pore_icefraction(ig,:,islope)) 1087 1089 1088 1090
Note: See TracChangeset
for help on using the changeset viewer.