Changeset 3554
- Timestamp:
- Dec 16, 2024, 5:57:50 PM (6 days ago)
- Location:
- trunk/LMDZ.COMMON/libf/evolution
- Files:
-
- 5 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.COMMON/libf/evolution/adsorption_mod.F90
r3498 r3554 4 4 5 5 logical :: adsorption_pem ! True by default, to compute adsorption/desorption. Read in pem.def 6 real, save, allocatable, dimension(:,:,:) :: co2_adsorb ded_phys ! co2 that is in the regolith [kg/m^2]7 real, save, allocatable, dimension(:,:,:) :: h2o_adsorb ded_phys ! h2o that is in the regolith [kg/m^2]6 real, save, allocatable, dimension(:,:,:) :: co2_adsorbed_phys ! co2 that is in the regolith [kg/m^2] 7 real, save, allocatable, dimension(:,:,:) :: h2o_adsorbed_phys ! h2o that is in the regolith [kg/m^2] 8 8 9 9 !======================================================================= … … 26 26 integer, intent(in) :: nsoilmx_PEM ! number of soil layer in the PEM 27 27 28 allocate(co2_adsorb ded_phys(ngrid,nsoilmx_PEM,nslope))29 allocate(h2o_adsorb ded_phys(ngrid,nsoilmx_PEM,nslope))28 allocate(co2_adsorbed_phys(ngrid,nsoilmx_PEM,nslope)) 29 allocate(h2o_adsorbed_phys(ngrid,nsoilmx_PEM,nslope)) 30 30 31 31 END SUBROUTINE ini_adsorption_h_PEM … … 34 34 SUBROUTINE end_adsorption_h_PEM 35 35 36 if (allocated(co2_adsorb ded_phys)) deallocate(co2_adsorbded_phys)37 if (allocated(h2o_adsorb ded_phys)) deallocate(h2o_adsorbded_phys)36 if (allocated(co2_adsorbed_phys)) deallocate(co2_adsorbed_phys) 37 if (allocated(h2o_adsorbed_phys)) deallocate(h2o_adsorbed_phys) 38 38 39 39 END SUBROUTINE end_adsorption_h_PEM … … 63 63 64 64 ! Local variables 65 real, dimension(ngrid,nsoil_PEM,nslope) :: theta_h2o_adsorb ded ! Fraction of the pores occupied by H2O molecules65 real, dimension(ngrid,nsoil_PEM,nslope) :: theta_h2o_adsorbed ! Fraction of the pores occupied by H2O molecules 66 66 ! ------------- 67 67 ! Compute H2O adsorption, then CO2 adsorption 68 68 call regolith_h2oadsorption(ngrid,nslope,nsoil_PEM,timelen,d_h2oglaciers,d_co2glaciers,waterice,co2ice,ps,q_co2,q_h2o,tsoil_PEM,TI_PEM, & 69 theta_h2o_adsorb ded,m_h2o_completesoil,delta_mh2oreg)69 theta_h2o_adsorbed,m_h2o_completesoil,delta_mh2oreg) 70 70 call regolith_co2adsorption(ngrid,nslope,nsoil_PEM,timelen,d_h2oglaciers,d_co2glaciers,waterice,co2ice,ps,q_co2,q_h2o, & 71 71 tsoil_PEM,TI_PEM,m_co2_completesoil,delta_mco2reg) … … 75 75 !======================================================================= 76 76 SUBROUTINE regolith_h2oadsorption(ngrid,nslope,nsoil_PEM,timelen,d_h2oglaciers,d_co2glaciers,waterice,co2ice,ps,q_co2,q_h2o,tsoil_PEM,TI_PEM, & 77 theta_h2o_adsorb ded,m_h2o_completesoil,delta_mreg)77 theta_h2o_adsorbed,m_h2o_completesoil,delta_mreg) 78 78 79 79 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! … … 111 111 ! Outputs 112 112 real, dimension(ngrid,nsoil_PEM,nslope), intent(inout) :: m_h2o_completesoil ! Density of h2o adsorbed (kg/m^3)(ngrid,nsoil_PEM,nslope) 113 real, dimension(ngrid,nsoil_PEM,nslope), intent(out) :: theta_h2o_adsorb ded ! Fraction of the pores occupied by H2O molecules113 real, dimension(ngrid,nsoil_PEM,nslope), intent(out) :: theta_h2o_adsorbed ! Fraction of the pores occupied by H2O molecules 114 114 real, dimension(ngrid), intent(out) :: delta_mreg ! Difference density of h2o adsorbed (kg/m^3) 115 115 … … 142 142 A = 1./m_co2 - 1./m_noco2 143 143 B = 1./m_noco2 144 theta_h2o_adsorb ded = 0.144 theta_h2o_adsorbed = 0. 145 145 dm_h2o_regolith_slope = 0. 146 146 ispermanent_h2oglaciers = .false. … … 182 182 K = Ko*exp(e/tsoil_PEM(ig,iloop,islope)) 183 183 if (TI_PEM(ig,iloop,islope) < inertie_thresold) then 184 theta_h2o_adsorb ded(ig,iloop,islope) = (K*pvapor_avg(ig)/(1. + K*pvapor_avg(ig)))**mu184 theta_h2o_adsorbed(ig,iloop,islope) = (K*pvapor_avg(ig)/(1. + K*pvapor_avg(ig)))**mu 185 185 else 186 186 p_sat = exp(beta_clap_h2o/tsoil_PEM(ig,iloop,islope) + alpha_clap_h2o) ! we assume fixed temperature in the ice ... not really good but ... 187 theta_h2o_adsorb ded(ig,iloop,islope) = (K*p_sat/(1. + K*p_sat))**mu187 theta_h2o_adsorbed(ig,iloop,islope) = (K*p_sat/(1. + K*p_sat))**mu 188 188 endif 189 dm_h2o_regolith_slope(ig,iloop,islope) = as*theta_h2o_adsorb ded(ig,iloop,islope)*m_theta*rho_regolith189 dm_h2o_regolith_slope(ig,iloop,islope) = as*theta_h2o_adsorbed(ig,iloop,islope)*m_theta*rho_regolith 190 190 enddo 191 191 enddo -
trunk/LMDZ.COMMON/libf/evolution/evol_ice_mod.F90
r3553 r3554 49 49 !======================================================================= 50 50 51 SUBROUTINE evol_h2o_ice(ngrid,nslope,cell_area,delta_h2o_adsorb ded,delta_h2o_icetablesublim,h2o_ice,d_h2oice,zshift_surf,stopPEM)51 SUBROUTINE evol_h2o_ice(ngrid,nslope,cell_area,delta_h2o_adsorbed,delta_h2o_icetablesublim,h2o_ice,d_h2oice,zshift_surf,stopPEM) 52 52 53 53 use time_evol_mod, only: dt … … 73 73 integer, intent(in) :: ngrid, nslope ! # of grid points, # of subslopes 74 74 real, dimension(ngrid), intent(in) :: cell_area ! Area of each mesh grid (m^2) 75 real, dimension(ngrid), intent(in) :: delta_h2o_adsorb ded ! Mass of H2O adsorbded/desorbded in the soil (kg/m^2)75 real, dimension(ngrid), intent(in) :: delta_h2o_adsorbed ! Mass of H2O adsorbed/desorbded in the soil (kg/m^2) 76 76 real, dimension(ngrid), intent(in) :: delta_h2o_icetablesublim ! Mass of H2O that have condensed/sublimated at the ice table (kg/m^2) 77 77 … … 93 93 neg_tend = 0. 94 94 do i = 1,ngrid 95 if (delta_h2o_adsorb ded(i) > 0.) then96 pos_tend = pos_tend + delta_h2o_adsorb ded(i)*cell_area(i)95 if (delta_h2o_adsorbed(i) > 0.) then 96 pos_tend = pos_tend + delta_h2o_adsorbed(i)*cell_area(i) 97 97 else 98 neg_tend = neg_tend + delta_h2o_adsorb ded(i)*cell_area(i)98 neg_tend = neg_tend + delta_h2o_adsorbed(i)*cell_area(i) 99 99 endif 100 100 if (delta_h2o_icetablesublim(i) > 0.) then -
trunk/LMDZ.COMMON/libf/evolution/pem.F90
r3553 r3554 217 217 real, dimension(:,:,:), allocatable :: watersoil_density_PEM_avg ! Physic x Soil x Slopes, water soil density, yearly averaged [kg/m^3] 218 218 real, dimension(:,:), allocatable :: Tsurfavg_before_saved ! Surface temperature saved from previous time step [K] 219 real, dimension(:), allocatable :: delta_co2_adsorbed ! Physics: quantity of CO2 that is exchanged because of adsorption / desorption [kg/m^2]220 real, dimension(:), allocatable :: delta_h2o_adsorbed ! Physics: quantity of H2O that is exchanged because of adsorption / desorption [kg/m^2]221 real :: totmassco2_adsorbed ! Total mass of CO2 that is exchanged because of adsorption / desoprtion over the planets [kg]222 real :: totmassh2o_adsorbed ! Total mass of H2O that is exchanged because of adsorption / desoprtion over the planets [kg]219 real, dimension(:), allocatable :: delta_co2_adsorbed ! Physics: quantity of CO2 that is exchanged because of adsorption / desorption [kg/m^2] 220 real, dimension(:), allocatable :: delta_h2o_adsorbed ! Physics: quantity of H2O that is exchanged because of adsorption / desorption [kg/m^2] 221 real :: totmassco2_adsorbed ! Total mass of CO2 that is exchanged because of adsorption / desoprtion over the planets [kg] 222 real :: totmassh2o_adsorbed ! Total mass of H2O that is exchanged because of adsorption / desoprtion over the planets [kg] 223 223 logical :: bool_sublim ! logical to check if there is sublimation or not 224 224 logical, dimension(:,:), allocatable :: co2ice_disappeared ! logical to check if a co2 ice reservoir already disappeared at a previous timestep -
trunk/LMDZ.COMMON/libf/evolution/pemredem.F90
r3537 r3554 119 119 call put_field("tsoil_PEM_slope"//num,"Soil temperature by slope type",tsoil_slope_PEM(:,:,islope),Year) 120 120 call put_field("TI_PEM_slope"//num,"Soil Thermal Inertia by slope type",inertiesoil_slope_PEM(:,:,islope),Year) 121 call put_field("mco2_reg_ads_slope"//num, "Mass of co2 adsorb ded in the regolith",m_co2_regolith(:,:,islope),Year)122 call put_field("mh2o_reg_ads_slope"//num, "Mass of h2o adsorb ded in the regolith",m_h2o_regolith(:,:,islope),Year)121 call put_field("mco2_reg_ads_slope"//num, "Mass of co2 adsorbed in the regolith",m_co2_regolith(:,:,islope),Year) 122 call put_field("mh2o_reg_ads_slope"//num, "Mass of h2o adsorbed in the regolith",m_h2o_regolith(:,:,islope),Year) 123 123 enddo 124 124 call put_field("icetable_depth","Depth of ice table",icetable_depth,Year) -
trunk/LMDZ.COMMON/libf/evolution/recomp_tend_co2_slope_mod.F90
r3553 r3554 59 59 60 60 END SUBROUTINE recomp_tend_co2 61 !=======================================================================62 63 SUBROUTINE recomp_tend_h2o(ngrid,nslope,timelen,d_h2oice,PCM_temp,PEM_temp)64 65 implicit none66 67 !=======================================================================68 !69 ! Routine that compute the evolution of the tendencie for h2o ice70 !71 !=======================================================================72 73 ! arguments:74 ! ----------75 ! INPUT76 integer, intent(in) :: timelen, ngrid, nslope77 real, dimension(:), intent(in) :: PCM_temp, PEM_temp78 79 ! OUTPUT80 real, dimension(ngrid,nslope), intent(inout) :: d_h2oice ! physical point field: Evolution of perennial ice over one year81 82 ! local:83 ! ------84 real :: coef, ave, Rz_old, Rz_new, R_dec, soil_psv_old, soil_psv_new, hum_dec, h2oice_depth_new, h2oice_depth_old85 86 write(*,*) "Update of the H2O tendency due to lag layer"87 88 ! Flux correction due to lag layer89 !~ Rz_old = h2oice_depth_old*0.0325/4.e-4 ! resistance from PCM90 !~ Rz_new = h2oice_depth_new*0.0325/4.e-4 ! new resistance based on new depth91 !~ R_dec = (1./Rz_old)/(1./Rz_new) ! decrease because of resistance92 !~ soil_psv_old = psv(max(PCM_temp(h2oice_depth_old))) ! the maxmimum annual mean saturation vapor pressure at the temperature of the GCM run temperature at the old ice location93 !~ soil_psv_new = psv(max(PEM_temp(h2oice_depth_new))) ! the maxmimum annual mean saturation vapor pressure at the temperature of the PEM run temperature at the new ice location94 !~ hum_dec = soil_psv_old/soil_psv_new ! decrease because of lower water vapor pressure at the new depth95 !~ d_h2oice = d_h2oice*R_dec*hum_dec ! decrease of flux96 97 END SUBROUTINE recomp_tend_h2o98 61 99 62 END MODULE recomp_tend_co2_slope_mod
Note: See TracChangeset
for help on using the changeset viewer.