Changeset 2945 for trunk/LMDZ.COMMON/libf/evolution
- Timestamp:
- Apr 18, 2023, 3:16:47 PM (20 months ago)
- Location:
- trunk/LMDZ.COMMON/libf/evolution
- Files:
-
- 5 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.COMMON/libf/evolution/comsoil_h_PEM.F90
r2895 r2945 3 3 implicit none 4 4 integer, parameter :: nsoilmx_PEM = 27 ! number of layers in the PEM 5 integer, parameter :: n_1km = 23 ! index at which we have overcome 1km6 7 5 real,save,allocatable,dimension(:) :: layer_PEM ! soil layer depths [m] 8 6 real,save,allocatable,dimension(:) :: mlayer_PEM ! soil mid-layer depths [m] 9 7 real,save,allocatable,dimension(:,:,:) :: TI_PEM ! soil thermal inertia [SI] 10 8 real,save,allocatable,dimension(:,:) :: inertiedat_PEM ! soil thermal inertia saved as reference for current climate [SI] 11 9 ! variables (FC: built in firstcall in soil.F) 12 10 REAL,SAVE,ALLOCATABLE :: tsoil_PEM(:,:,:) ! sub-surface temperatures [K] -
trunk/LMDZ.COMMON/libf/evolution/constants_marspem_mod.F90
r2944 r2945 3 3 4 4 IMPLICIT NONE 5 5 ! Duration of a year and day 6 INTEGER,PARAMETER :: sols_per_my =669 ! Number of Sols per year 7 REAL, PARAMETER :: sec_per_sol=88775. ! Duration of a sol, in seconds 6 8 7 9 ! Molecular masses for CO2,H2O and non condensible gaz, following Franz et al. 2017 8 9 10 10 REAL,PARAMETER :: m_co2 = 44.01E-3 ! CO2 molecular mass (kg/mol) 11 REAL,PARAMETER :: m_noco2 = 33.37E-3 ! Non condensible mol mass (kg/mol) 12 REAL,PARAMETER :: m_h2o = 18.01528E-3 ! Molecular weight of h2o (kg/mol) 11 13 12 14 ! Coefficient for Clapeyron law for CO2 condensation temperature (Tco2 = beta/(alpha-log(vmr)),following James et al. 1992 -
trunk/LMDZ.COMMON/libf/evolution/pemetat0.F90
r2944 r2945 5 5 6 6 use iostart_PEM, only: open_startphy, close_startphy, get_field, get_var 7 use comsoil_h_PEM, only: soil_pem,layer_PEM, mlayer_PEM, n_1km,fluxgeo,inertiedat_PEM,water_reservoir_nom,depth_breccia,depth_bedrock,index_breccia,index_bedrock7 use comsoil_h_PEM, only: soil_pem,layer_PEM, mlayer_PEM,fluxgeo,inertiedat_PEM,water_reservoir_nom,depth_breccia,depth_bedrock,index_breccia,index_bedrock 8 8 use comsoil_h, only: volcapa,inertiedat 9 9 use adsorption_mod, only : regolith_adsorption,adsorption_pem -
trunk/LMDZ.COMMON/libf/evolution/recomp_tend_co2_slope.F90
r2944 r2945 2 2 ! $Id $ 3 3 ! 4 SUBROUTINE recomp_tend_co2_slope(tendencies_co2_ice_phys,tendencies_co2_ice_phys_ini,co2ice_slope,vmr_co2_gcm,vmr_co2_pem,ps_GCM_2,global_ave_press_GCM,global_ave_press_new,timelen,ngrid,nslope) 4 SUBROUTINE recomp_tend_co2_slope(ngrid,nslope,timelen,tendencies_co2_ice_phys,tendencies_co2_ice_phys_ini,co2ice_slope, emissivity_slope, & 5 vmr_co2_gcm,vmr_co2_pem,ps_GCM_2,global_ave_press_GCM,global_ave_press_new) 5 6 6 use constants_marspem_mod, only : alpha_clap_co2, beta_clap_co2, sigmaB,Lco2 7 use constants_marspem_mod, only : alpha_clap_co2, beta_clap_co2, sigmaB,Lco2, sols_per_my, sec_per_sol 7 8 8 9 IMPLICIT NONE … … 21 22 REAL, INTENT(in) :: vmr_co2_gcm(ngrid,timelen) ! physical point field : Volume mixing ratio of co2 in the first layer 22 23 REAL, INTENT(in) :: vmr_co2_pem(ngrid,timelen) ! physical point field : Volume mixing ratio of co2 in the first layer 23 REAL, intent(in) :: ps_GCM_2(ngrid,timelen) ! physical point field : Surface pressure in the GCM24 REAL, intent(in) :: global_ave_press_GCM 25 REAL, intent(in) :: global_ave_press_new 24 REAL, intent(in) :: ps_GCM_2(ngrid,timelen) ! physical point field : Surface pressure in the GCM 25 REAL, intent(in) :: global_ave_press_GCM ! global averaged pressure at previous timestep 26 REAL, intent(in) :: global_ave_press_new ! global averaged pressure at current timestep 26 27 REAL, intent(in) :: tendencies_co2_ice_phys_ini(ngrid,nslope) ! physical point field : Evolution of perenial ice over one year 27 REAL, intent(in) :: co2ice_slope(ngrid,nslope) 28 REAL, intent(in) :: co2ice_slope(ngrid,nslope) ! CO2 ice per mesh and sub-grid slope(kg/m^2) 29 REAL, intent(in) :: emissivity_slope(ngrid,nslope) ! Emissivity per mesh and sub-grid slope(1) 28 30 29 31 ! OUTPUT … … 34 36 35 37 INTEGER :: i,t,islope 36 REAL :: eps, coef, ave 37 38 eps=0.95 39 coef=669*88875*eps*sigmaB/Lco2 38 REAL :: coef, ave 40 39 41 40 ! Evolution of the water ice for each physical point 42 41 do i=1,ngrid 43 42 do islope=1,nslope 43 coef=sols_per_my*sec_per_sol*emissivity_slope(i,islope)*sigmaB/Lco2 44 44 ave=0. 45 45 ! if(abs(tendencies_co2_ice_phys(i,islope)).gt.1e-4) then -
trunk/LMDZ.COMMON/libf/evolution/update_soil.F90
r2944 r2945 2 2 #ifndef CPP_STD 3 3 USE comsoil_h, only: inertiedat, volcapa 4 USE comsoil_h_PEM, only: layer_PEM, n_1km,inertiedat_PEM,depth_breccia,depth_bedrock,index_breccia,index_bedrock,reg_thprop_dependp4 USE comsoil_h_PEM, only: layer_PEM,inertiedat_PEM,depth_breccia,depth_bedrock,index_breccia,index_bedrock,reg_thprop_dependp 5 5 USE vertical_layers_mod, ONLY: ap,bp 6 USE comsoil_h_PEM, only: n_1km7 6 USE constants_marspem_mod,only: TI_breccia,TI_bedrock, TI_regolith_avg 8 7 implicit none
Note: See TracChangeset
for help on using the changeset viewer.