Changeset 3149 for trunk/LMDZ.COMMON
- Timestamp:
- Dec 6, 2023, 4:02:06 PM (12 months ago)
- Location:
- trunk/LMDZ.COMMON/libf/evolution
- Files:
-
- 1 added
- 2 deleted
- 18 edited
- 3 moved
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.COMMON/libf/evolution/changelog.txt
r3145 r3149 154 154 - Addition of a script in LMDZ.MARS/deftank/pem/ to launch a chained simulation of 1D PCM runs which follow, year by year, the orbital parameters (obliquity, eccentricity, Ls perihelion) given in a specified file. 155 155 - Small changes to other files of the deftank directory (check and cosmetic). 156 157 == 06/12/2023 == JBC 158 - Simplification of the algorithm managing the stopping criteria; 159 - Complete rework of the ice management in the PEM (H2O & CO2); 160 > Subroutines to evolve the H2O and CO2 ice are now in the same module "evol_ice_mod.F90". 161 > Tendencies are computed from the variation of "ice + frost" between the 2 PCM runs. 162 > Evolving ice in the PEM is now called 'h2o_ice' or 'co2_ice' (not anymore in 'qsurf' and free of 'water_reservoir'). 163 > Default value 'ini_h2o_bigreservoir' (= 10 m) initializes the H2O ice of the first PEM run where there is 'watercap'. For the next PEM runs, initialization is done with the value kept in "startpem.nc". CO2 ice is taken from 'perennial_co2ice' of the PCM (paleoclimate flag must be true). 164 > Simplification of the condition to compute the surface ice cover needed for the stopping criteria. 165 > Frost ('qsurf') is not evolved by the PEM and given back to the PCM. 166 > New default threshold value 'inf_h2oice_threshold' (= 2 m) to decide at the end of the PEM run if the H2O ice should be 'watercap' or not for the next PCM runs. If H2O ice cannot be 'watercap', then the remaining H2O ice is transferred to the frost ('qsurf'). 167 - Renaming of variables/subroutines for clarity; 168 - Some cleanings throughout the code; 169 - Small updates in files of the deftank. -
trunk/LMDZ.COMMON/libf/evolution/compute_tend_mod.F90
r3148 r3149 1 MODULE compute_tend encies_slope_mod1 MODULE compute_tend_mod 2 2 3 3 implicit none … … 7 7 !======================================================================= 8 8 9 SUBROUTINE compute_tend encies_slope(ngrid,nslope,min_ice_Y1,min_ice_Y2,tendencies_ice)9 SUBROUTINE compute_tend(ngrid,nslope,min_ice,tendencies_ice) 10 10 11 11 implicit none … … 13 13 !======================================================================= 14 14 ! 15 ! 15 ! Compute the tendencies of the evolution of water ice over the years 16 16 ! 17 17 !======================================================================= … … 20 20 ! ---------- 21 21 ! INPUT 22 integer, intent(in) :: ngrid, nslope ! # of grid points along longitude/latitude/ total23 real, dimension(ngrid,nslope), intent(in) :: min_ice_Y1 ! LON x LAT field : minimum of water ice at each point for the first year 24 real, dimension(ngrid,nslope ), intent(in) :: min_ice_Y2 ! LON x LAT field : minimum of water ice at each point for the second year22 integer, intent(in) :: ngrid ! # of grid points 23 integer, intent(in) :: nslope ! # of subslopes 24 real, dimension(ngrid,nslope,2), intent(in) :: min_ice ! Minima of ice at each point for the PCM years 25 25 26 26 ! OUTPUT 27 real, dimension(ngrid,nslope), intent(out) :: tendencies_ice ! physical point field : difference between the minima = evolution of perennial ice27 real, dimension(ngrid,nslope), intent(out) :: tendencies_ice ! Difference between the minima = evolution of perennial ice 28 28 !======================================================================= 29 ! We compute the difference 30 tendencies_ice = min_ice(:,:,2) - min_ice(:,:,1) 29 31 30 ! We compute the difference 31 tendencies_ice = min_ice_Y2 - min_ice_Y1 32 33 ! If the difference is too small; there is no evolution 32 ! If the difference is too small, then there is no evolution 34 33 where (abs(tendencies_ice) < 1.e-10) tendencies_ice = 0. 35 34 36 END SUBROUTINE compute_tend encies_slope35 END SUBROUTINE compute_tend 37 36 38 END MODULE compute_tendencies_slope_mod 39 37 END MODULE compute_tend_mod -
trunk/LMDZ.COMMON/libf/evolution/comsoil_h_PEM.F90
r3143 r3149 3 3 implicit none 4 4 5 integer, parameter :: nsoilmx_PEM = 68 ! number of layers in the PEM6 real, allocatable, dimension(:), save :: layer_PEM ! soil layer depths [m]7 real, allocatable, dimension(:), save :: mlayer_PEM ! soil mid-layer depths [m]8 real, allocatable, dimension(:,:,:), save :: TI_PEM ! soil thermal inertia [SI]9 real, allocatable, dimension(:,:), save :: inertiedat_PEM ! soil thermal inertia saved as reference for current climate [SI]5 integer, parameter :: nsoilmx_PEM = 68 ! number of layers in the PEM 6 real, allocatable, dimension(:), save :: layer_PEM ! soil layer depths [m] 7 real, allocatable, dimension(:), save :: mlayer_PEM ! soil mid-layer depths [m] 8 real, allocatable, dimension(:,:,:), save :: TI_PEM ! soil thermal inertia [SI] 9 real, allocatable, dimension(:,:), save :: inertiedat_PEM ! soil thermal inertia saved as reference for current climate [SI] 10 10 ! Variables (FC: built in firstcall in soil.F) 11 real, allocatable, dimension(:,:,:), save :: tsoil_PEM ! sub-surface temperatures [K] 12 real, allocatable, dimension(:,:), save :: mthermdiff_PEM ! (FC) mid-layer thermal diffusivity [SI] 13 real, allocatable, dimension(:,:), save :: thermdiff_PEM ! (FC) inter-layer thermal diffusivity [SI] 14 real, allocatable, dimension(:), save :: coefq_PEM ! (FC) q_{k+1/2} coefficients [SI] 15 real, allocatable, dimension(:,:), save :: coefd_PEM ! (FC) d_k coefficients [SI] 16 real, allocatable, dimension(:,:), save :: alph_PEM ! (FC) alpha_k coefficients [SI] 17 real, allocatable, dimension(:,:), save :: beta_PEM ! beta_k coefficients [SI] 18 real, save :: mu_PEM ! mu coefficient [SI] 19 real, save :: fluxgeo ! Geothermal flux [W/m^2] 20 real, save :: depth_breccia ! Depth at which we have breccia [m] 21 real, save :: depth_bedrock ! Depth at which we have bedrock [m] 22 integer, save :: index_breccia ! last index of the depth grid before having breccia 23 integer, save :: index_bedrock ! last index of the depth grid before having bedrock 24 logical :: soil_pem ! True by default, to run with the subsurface physic. Read in pem.def 25 real, allocatable, dimension(:), save :: water_reservoir ! Large reserve of water [kg/m^2] 26 real, save :: water_reservoir_nom ! Nominal value for the large reserve of water [kg/m^2] 27 logical, save :: reg_thprop_dependp ! thermal properites of the regolith vary with the surface pressure 11 real, allocatable, dimension(:,:,:), save :: tsoil_PEM ! sub-surface temperatures [K] 12 real, allocatable, dimension(:,:), save :: mthermdiff_PEM ! (FC) mid-layer thermal diffusivity [SI] 13 real, allocatable, dimension(:,:), save :: thermdiff_PEM ! (FC) inter-layer thermal diffusivity [SI] 14 real, allocatable, dimension(:), save :: coefq_PEM ! (FC) q_{k+1/2} coefficients [SI] 15 real, allocatable, dimension(:,:), save :: coefd_PEM ! (FC) d_k coefficients [SI] 16 real, allocatable, dimension(:,:), save :: alph_PEM ! (FC) alpha_k coefficients [SI] 17 real, allocatable, dimension(:,:), save :: beta_PEM ! beta_k coefficients [SI] 18 real, save :: mu_PEM ! mu coefficient [SI] 19 real, save :: fluxgeo ! Geothermal flux [W/m^2] 20 real, save :: depth_breccia ! Depth at which we have breccia [m] 21 real, save :: depth_bedrock ! Depth at which we have bedrock [m] 22 integer, save :: index_breccia ! last index of the depth grid before having breccia 23 integer, save :: index_bedrock ! last index of the depth grid before having bedrock 24 logical :: soil_pem ! True by default, to run with the subsurface physic. Read in pem.def 25 real, save :: ini_h2o_bigreservoir ! Initial value for the large reservoir of water [kg/m^2] 26 logical, save :: reg_thprop_dependp ! thermal properites of the regolith vary with the surface pressure 28 27 29 28 !======================================================================= … … 39 38 40 39 allocate(layer_PEM(nsoilmx_PEM)) 41 allocate(mlayer_PEM(0:nsoilmx_PEM -1))40 allocate(mlayer_PEM(0:nsoilmx_PEM - 1)) 42 41 allocate(TI_PEM(ngrid,nsoilmx_PEM,nslope)) 43 42 allocate(tsoil_PEM(ngrid,nsoilmx_PEM,nslope)) 44 allocate(mthermdiff_PEM(ngrid,0:nsoilmx_PEM -1))45 allocate(thermdiff_PEM(ngrid,nsoilmx_PEM -1))46 allocate(coefq_PEM(0:nsoilmx_PEM -1))47 allocate(coefd_PEM(ngrid,nsoilmx_PEM -1))48 allocate(alph_PEM(ngrid,nsoilmx_PEM -1))49 allocate(beta_PEM(ngrid,nsoilmx_PEM -1))43 allocate(mthermdiff_PEM(ngrid,0:nsoilmx_PEM - 1)) 44 allocate(thermdiff_PEM(ngrid,nsoilmx_PEM - 1)) 45 allocate(coefq_PEM(0:nsoilmx_PEM - 1)) 46 allocate(coefd_PEM(ngrid,nsoilmx_PEM - 1)) 47 allocate(alph_PEM(ngrid,nsoilmx_PEM - 1)) 48 allocate(beta_PEM(ngrid,nsoilmx_PEM - 1)) 50 49 allocate(inertiedat_PEM(ngrid,nsoilmx_PEM)) 51 allocate(water_reservoir(ngrid))52 50 53 51 END SUBROUTINE ini_comsoil_h_PEM … … 70 68 if (allocated(beta_PEM)) deallocate(beta_PEM) 71 69 if (allocated(inertiedat_PEM)) deallocate(inertiedat_PEM) 72 if (allocated(water_reservoir)) deallocate(water_reservoir)73 70 74 71 END SUBROUTINE end_comsoil_h_PEM -
trunk/LMDZ.COMMON/libf/evolution/conf_pem.F90
r3096 r3149 25 25 use time_evol_mod, only: year_bp_ini, dt_pem, water_ice_criterion, co2_ice_criterion, ps_criterion, Max_iter_pem, & 26 26 evol_orbit_pem, var_obl, var_ecc, var_lsp, convert_years 27 use comsoil_h_pem, only: soil_pem, fluxgeo, water_reservoir_nom, depth_breccia, depth_bedrock, reg_thprop_dependp27 use comsoil_h_pem, only: soil_pem, fluxgeo, ini_h2o_bigreservoir, depth_breccia, depth_bedrock, reg_thprop_dependp 28 28 use adsorption_mod, only: adsorption_pem 29 use glaciers_mod, only: co2 glaciersflow, h2oglaciersflow29 use glaciers_mod, only: co2_ice_flow, h2o_ice_flow 30 30 use ice_table_mod, only: icetable_equilibrium, icetable_dynamic 31 31 use time_phylmdz_mod, only: ecritphy … … 71 71 var_ecc = .true. 72 72 call getin('var_ecc',var_ecc) 73 write(*,*) 'Does e xcentricity vary ?',var_ecc73 write(*,*) 'Does eccentricity vary ?',var_ecc 74 74 75 75 var_lsp = .true. … … 100 100 call getin('adsorption_pem',adsorption_pem) 101 101 102 co2 glaciersflow = .true.103 call getin('co2 glaciersflow',co2glaciersflow)102 co2_ice_flow = .true. 103 call getin('co2_ice_flow',co2_ice_flow) 104 104 105 h2o glaciersflow = .true.106 call getin('h2o glaciersflow',h2oglaciersflow)105 h2o_ice_flow = .true. 106 call getin('h2o_ice_flow',h2o_ice_flow) 107 107 108 108 reg_thprop_dependp = .false. … … 156 156 endif 157 157 158 water_reservoir_nom= 1.e4159 call getin(' water_reservoir_nom',water_reservoir_nom)158 ini_h2o_bigreservoir = 1.e4 159 call getin('ini_h2o_bigreservoir',ini_h2o_bigreservoir) 160 160 161 161 END SUBROUTINE conf_pem -
trunk/LMDZ.COMMON/libf/evolution/constants_marspem_mod.F90
r3143 r3149 12 12 real, parameter :: m_h2o = 18.01528e-3 ! Molecular weight of h2o (kg/mol) 13 13 14 ! 14 ! Coefficient for Clapeyron law for CO2 condensation temperature (Tco2 = beta/(alpha-log(vmr)),following James et al. 1992 15 15 real, parameter :: alpha_clap_co2 = 23.3494 ! Uniteless, James et al. 1992 16 16 real, parameter :: beta_clap_co2 = 3182.48 ! Kelvin, James et al. 1992 17 17 18 ! 18 ! Coefficient for Clapeyron law for psat (psat = exp(beta/Th2o+alpha)),following Murphy and Koop 2005 19 19 real, parameter :: alpha_clap_h2o = 28.9074 ! Uniteless, Murphy and Koop 2005 20 20 real, parameter :: beta_clap_h2o = -6143.7 ! Kelvin, Murphy and Koop 2005 21 21 22 ! 22 ! Density of the regolith (Zent et al., 1995, Buhler and Piqueux 2021) 23 23 real, parameter :: rho_regolith = 2000. ! kg/m^3 24 24 25 ! Average Thermal inertia of the surface, breccia, bedrock, following Mellon et al., 2000., Wood et al., 200825 ! Average thermal inertia of the surface, breccia, bedrock, following Mellon et al., 2000., Wood et al., 2008 26 26 real, parameter :: TI_regolith_avg = 250. ! Averaged of the observed thermal inertia for regolith following Mellon et al., 2000[SI] 27 27 real, parameter :: TI_breccia = 750. ! Thermal inertia of Breccia following Wood 2009 [SI] 28 28 real, parameter :: TI_bedrock = 2300. ! Thermal inertia of Bedrock following Wood 2009 [SI] 29 29 30 ! 30 ! Porosity of the soil 31 31 real, parameter :: porosity = 0.4 ! porosity of the martian soil, correspond to the value for a random loose packing of monodiperse sphere (Scott, 1960) 32 32 33 ! 33 ! Stefan Boltzmann constant 34 34 real, parameter :: sigmaB = 5.678e-8 35 35 36 ! 36 ! Latent heat of CO2 37 37 real, parameter :: Lco2 = 5.71e5 ! Pilorget and Forget 2016 38 38 39 ! Conversion H2O/CO2 frost to perennial frost and vice versa 40 real, parameter :: threshold_h2o_frost2perennial = 1000. !~ 1 m 41 real, parameter :: threshold_co2_frost2perennial = 16000. !~ 10 m 39 ! Threshold to consider the amount of H2O ice as an infinite reservoir 40 real, parameter :: inf_h2oice_threshold = 2000. !~ 1 m 42 41 43 42 END MODULE constants_marspem_mod -
trunk/LMDZ.COMMON/libf/evolution/glaciers_mod.F90
r3082 r3149 1 module glaciers_mod 2 3 implicit none 4 LOGICAL co2glaciersflow ! True by default, to compute co2 ice flow. Read in pem.def 5 LOGICAL h2oglaciersflow ! True by default, to compute co2 ice flow. Read in pem.def 6 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 7 !!! 8 !!! Purpose: Compute CO2 glacier flows 9 !!! 10 !!! Author: LL 11 !!! 12 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 13 1 MODULE glaciers_mod 2 3 implicit none 4 5 logical :: co2_ice_flow ! True by default, to compute co2 ice flow. Read in run_PEM.def 6 logical :: h2o_ice_flow ! True by default, to compute h2o ice flow. Read in run_PEM.def 7 8 !======================================================================= 14 9 contains 15 16 subroutine co2glaciers_evol(timelen,ngrid,nslope,iflat,subslope_dist,def_slope_mean,vmr_co2_PEM,ps_GCM,global_ave_ps_GCM,global_ave_ps_PEM,co2ice,flag_co2flow,flag_co2flow_mesh) 10 !======================================================================= 11 12 SUBROUTINE flow_co2glaciers(timelen,ngrid,nslope,iflat,subslope_dist,def_slope_mean,vmr_co2_PEM,ps_PCM,global_avg_ps_PCM,global_avg_ps_PEM,co2ice,flag_co2flow,flag_co2flow_mesh) 17 13 18 14 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! … … 26 22 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 27 23 28 IMPLICIT NONE 24 implicit none 29 25 30 26 ! arguments … … 32 28 33 29 ! Inputs: 34 INTEGER,INTENT(IN) :: timelen,ngrid,nslope,iflat ! number of time sample, physical points, subslopes, index of the flat subslope 35 REAL,INTENT(IN) :: subslope_dist(ngrid,nslope), def_slope_mean(ngrid) ! Physical points x Slopes : Distribution of the subgrid slopes; Slopes: values of the sub grid slope angles 36 REAL,INTENT(IN) :: vmr_co2_PEM(ngrid,timelen) ! Physical x Time field : VMR of co2 in the first layer [mol/mol] 37 REAL,INTENT(IN) :: ps_GCM(ngrid,timelen) ! Physical x Time field: surface pressure given by the GCM [Pa] 38 REAL,INTENT(IN) :: global_ave_ps_GCM ! Global averaged surface pressure from the GCM [Pa] 39 REAL,INTENT(IN) :: global_ave_ps_PEM ! global averaged surface pressure during the PEM iteration [Pa] 30 integer, intent(in) :: timelen, ngrid, nslope, iflat ! number of time sample, physical points, subslopes, index of the flat subslope 31 real, dimension(ngrid,nslope), intent(in) :: subslope_dist ! Physical points x Slopes: Distribution of the subgrid slopes 32 real, dimension(ngrid), intent(in) :: def_slope_mean ! Physical points: values of the sub grid slope angles 33 real, dimension(ngrid,timelen), intent(in) :: vmr_co2_PEM ! Physical x Time field : VMR of co2 in the first layer [mol/mol] 34 real, dimension(ngrid,timelen), intent(in) :: ps_PCM ! Physical x Time field: surface pressure given by the PCM [Pa] 35 real, intent(in) :: global_avg_ps_PCM ! Global averaged surface pressure from the PCM [Pa] 36 real, intent(in) :: global_avg_ps_PEM ! global averaged surface pressure during the PEM iteration [Pa] 40 37 41 38 ! Ouputs: 42 REAL,INTENT(INOUT) :: co2ice(ngrid,nslope) ! Physical x Slope field: co2 ice on the subgrid slopes [kg/m^2] 43 REAL,INTENT(INOUT) :: flag_co2flow(ngrid,nslope) ! flag to see if there is flow on the subgrid slopes 44 REAL,INTENT(INOUT) :: flag_co2flow_mesh(ngrid) ! same but within the mesh 45 39 real, dimension(ngrid,nslope), intent(inout) :: co2ice ! Physical x Slope field: co2 ice on the subgrid slopes [kg/m^2] 40 real, dimension(ngrid,nslope), intent(inout) :: flag_co2flow ! flag to see if there is flow on the subgrid slopes 41 real, dimension(ngrid), intent(inout) :: flag_co2flow_mesh ! same but within the mesh 46 42 47 43 ! Local 48 REAL :: Tcond(ngrid,nslope) !Physical field: CO2 condensation temperature [K]49 REAL :: hmax(ngrid,nslope)! Physical x Slope field: maximum thickness for co2 glacier before flow44 real, dimension(ngrid,nslope) :: Tcond ! Physical field: CO2 condensation temperature [K] 45 real, dimension(ngrid,nslope) :: hmax ! Physical x Slope field: maximum thickness for co2 glacier before flow 50 46 51 47 !----------------------------- 52 call computeTcondCO2(timelen,ngrid,nslope,vmr_co2_PEM,ps_GCM,global_ave_ps_GCM,global_ave_ps_PEM,Tcond) 53 54 call compute_hmaxglaciers(ngrid,nslope,iflat,def_slope_mean,Tcond,"co2",hmax) 55 56 call transfer_ice_duringflow(ngrid,nslope,iflat, subslope_dist,def_slope_mean,hmax,Tcond,"co2",co2ice,flag_co2flow,flag_co2flow_mesh) 57 RETURN 58 end subroutine 59 60 61 62 63 64 subroutine h2oglaciers_evol(timelen,ngrid,nslope,iflat,subslope_dist,def_slope_mean,Tice,h2oice,flag_h2oflow,flag_h2oflow_mesh) 48 write(*,*) "Flow of CO2 glacier" 49 50 call computeTcondCO2(timelen,ngrid,nslope,vmr_co2_PEM,ps_PCM,global_avg_ps_PCM,global_avg_ps_PEM,Tcond) 51 call compute_hmaxglaciers(ngrid,nslope,iflat,def_slope_mean,Tcond,"co2",hmax) 52 call transfer_ice_duringflow(ngrid,nslope,iflat, subslope_dist,def_slope_mean,hmax,Tcond,"co2",co2ice,flag_co2flow,flag_co2flow_mesh) 53 54 END SUBROUTINE flow_co2glaciers 55 56 !======================================================================= 57 58 SUBROUTINE flow_h2oglaciers(timelen,ngrid,nslope,iflat,subslope_dist,def_slope_mean,Tice,h2oice,flag_h2oflow,flag_h2oflow_mesh) 65 59 66 60 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! … … 74 68 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 75 69 76 77 IMPLICIT NONE 70 implicit none 78 71 79 72 ! arguments … … 81 74 82 75 ! Inputs: 83 INTEGER,INTENT(IN) :: timelen,ngrid,nslope,iflat ! number of time sample, physical points, subslopes, index of the flat subslope84 REAL,INTENT(IN) :: subslope_dist(ngrid,nslope), def_slope_mean(ngrid) ! Physical points x Slopes : Distribution of the subgrid slopes; Slopes: values of the sub grid slope angles85 REAL,INTENT(IN) :: Tice(ngrid,nslope) ! Ice Temperature [K]76 integer,intent(in) :: timelen,ngrid,nslope,iflat ! number of time sample, physical points, subslopes, index of the flat subslope 77 real,intent(in) :: subslope_dist(ngrid,nslope), def_slope_mean(ngrid) ! Physical points x Slopes : Distribution of the subgrid slopes; Slopes: values of the sub grid slope angles 78 real,intent(in) :: Tice(ngrid,nslope) ! Ice Temperature [K] 86 79 ! Ouputs: 87 REAL,INTENT(INOUT) :: h2oice(ngrid,nslope) ! Physical x Slope field: co2 ice on the subgrid slopes [kg/m^2]88 REAL,INTENT(INOUT) :: flag_h2oflow(ngrid,nslope) ! flag to see if there is flow on the subgrid slopes89 REAL,INTENT(INOUT) :: flag_h2oflow_mesh(ngrid) ! same but within the mesh80 real,intent(inout) :: h2oice(ngrid,nslope) ! Physical x Slope field: co2 ice on the subgrid slopes [kg/m^2] 81 real,intent(inout) :: flag_h2oflow(ngrid,nslope) ! flag to see if there is flow on the subgrid slopes 82 real,intent(inout) :: flag_h2oflow_mesh(ngrid) ! same but within the mesh 90 83 ! Local 91 REAL:: hmax(ngrid,nslope) ! Physical x Slope field: maximum thickness for co2 glacier before flow84 real :: hmax(ngrid,nslope) ! Physical x Slope field: maximum thickness for co2 glacier before flow 92 85 93 86 !----------------------------- 94 95 call compute_hmaxglaciers(ngrid,nslope,iflat,def_slope_mean,Tice,"h2o",hmax) 96 call transfer_ice_duringflow(ngrid,nslope,iflat, subslope_dist,def_slope_mean,hmax,Tice,"h2o",h2oice,flag_h2oflow,flag_h2oflow_mesh) 97 98 RETURN 99 end subroutine 100 101 102 subroutine compute_hmaxglaciers(ngrid,nslope,iflat,def_slope_mean,Tice,name_ice,hmax) 87 write(*,*) "Flow of H2O glaciers" 88 89 call compute_hmaxglaciers(ngrid,nslope,iflat,def_slope_mean,Tice,"h2o",hmax) 90 call transfer_ice_duringflow(ngrid,nslope,iflat, subslope_dist,def_slope_mean,hmax,Tice,"h2o",h2oice,flag_h2oflow,flag_h2oflow_mesh) 91 92 END SUBROUTINE flow_h2oglaciers 93 94 !======================================================================= 95 96 SUBROUTINE compute_hmaxglaciers(ngrid,nslope,iflat,def_slope_mean,Tice,name_ice,hmax) 103 97 104 98 use abort_pem_mod, only: abort_pem … … 118 112 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 119 113 120 IMPLICIT NONE 114 implicit none 121 115 122 116 ! arguments … … 124 118 125 119 ! Inputs 126 INTEGER,INTENT(IN) :: ngrid,nslope ! # of grid points and subslopes127 INTEGER,INTENT(IN) :: iflat ! index of the flat subslope128 REAL,INTENT(IN) :: def_slope_mean(nslope) ! Slope field: Values of the subgrid slope angles [deg]129 REAL,INTENT(IN) :: Tice(ngrid,nslope) ! Physical field: ice temperature [K]130 character(len=3), INTENT(IN) :: name_ice ! Nature of the ice120 integer,intent(in) :: ngrid,nslope ! # of grid points and subslopes 121 integer,intent(in) :: iflat ! index of the flat subslope 122 real,intent(in) :: def_slope_mean(nslope) ! Slope field: Values of the subgrid slope angles [deg] 123 real,intent(in) :: Tice(ngrid,nslope) ! Physical field: ice temperature [K] 124 character(len=3), intent(in) :: name_ice ! Nature of the ice 131 125 ! Outputs 132 REAL,INTENT(OUT) :: hmax(ngrid,nslope) ! Physical grid x Slope field: maximum thickness before flaw [m]126 real,intent(out) :: hmax(ngrid,nslope) ! Physical grid x Slope field: maximum thickness before flaw [m] 133 127 ! Local 134 128 DOUBLE PRECISION :: tau_d ! characteristic basal drag, understood as the stress that an ice mass flowing under its weight balanced by viscosity. Value obtained from I.Smith 135 REAL:: rho(ngrid,nslope) ! co2 ice density [kg/m^3]136 INTEGER:: ig,islope ! loop variables137 REAL:: slo_angle129 real :: rho(ngrid,nslope) ! co2 ice density [kg/m^3] 130 integer :: ig,islope ! loop variables 131 real :: slo_angle 138 132 139 133 ! 1. Compute rho … … 167 161 ENDDO 168 162 ENDDO 169 RETURN 170 171 end subroutine 172 173 174 175 176 subroutine transfer_ice_duringflow(ngrid,nslope,iflat, subslope_dist,def_slope_mean,hmax,Tice,name_ice,qice,flag_flow,flag_flowmesh) 163 END SUBROUTINE compute_hmaxglaciers 164 165 !======================================================================= 166 167 SUBROUTINE transfer_ice_duringflow(ngrid,nslope,iflat,subslope_dist,def_slope_mean,hmax,Tice,name_ice,qice,flag_flow,flag_flowmesh) 177 168 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 178 169 !!! … … 196 187 197 188 ! Inputs 198 INTEGER, INTENT(IN) :: ngrid,nslope !# of physical points and subslope199 INTEGER, INTENT(IN) :: iflat ! index of the flat subslope200 REAL, INTENT(IN) :: subslope_dist(ngrid,nslope) ! Distribution of the subgrid slopes within the mesh201 REAL, INTENT(IN) :: def_slope_mean(nslope) ! values of the subgrid slopes202 REAL, INTENT(IN) :: hmax(ngrid,nslope) ! maximum height of the glaciers before initiating flow [m]203 REAL, INTENT(IN) :: Tice(ngrid,nslope) ! Ice temperature[K]204 character(len=3), INTENT(IN) :: name_ice ! Nature of the ice189 integer, intent(in) :: ngrid,nslope !# of physical points and subslope 190 integer, intent(in) :: iflat ! index of the flat subslope 191 real, intent(in) :: subslope_dist(ngrid,nslope) ! Distribution of the subgrid slopes within the mesh 192 real, intent(in) :: def_slope_mean(nslope) ! values of the subgrid slopes 193 real, intent(in) :: hmax(ngrid,nslope) ! maximum height of the glaciers before initiating flow [m] 194 real, intent(in) :: Tice(ngrid,nslope) ! Ice temperature[K] 195 character(len=3), intent(in) :: name_ice ! Nature of the ice 205 196 206 197 ! Outputs 207 REAL, INTENT(INOUT) :: qice(ngrid,nslope) ! CO2 in the subslope [kg/m^2]208 REAL, INTENT(INOUT) :: flag_flow(ngrid,nslope) ! boolean to check if there is flow on a subgrid slope209 REAL, INTENT(INOUT) :: flag_flowmesh(ngrid) ! boolean to check if there is flow in the mesh198 real, intent(inout) :: qice(ngrid,nslope) ! CO2 in the subslope [kg/m^2] 199 real, intent(inout) :: flag_flow(ngrid,nslope) ! boolean to check if there is flow on a subgrid slope 200 real, intent(inout) :: flag_flowmesh(ngrid) ! boolean to check if there is flow in the mesh 210 201 ! Local 211 INTEGERig,islope ! loop212 REALrho(ngrid,nslope) ! density of ice, temperature dependant [kg/m^3]213 INTEGERiaval ! ice will be transfered here202 integer ig,islope ! loop 203 real rho(ngrid,nslope) ! density of ice, temperature dependant [kg/m^3] 204 integer iaval ! ice will be transfered here 214 205 215 206 ! 0. Compute rho … … 268 259 ENDDO !islope 269 260 ENDDO !ig 270 RETURN 271 end subroutine 272 273 subroutine computeTcondCO2(timelen,ngrid,nslope,vmr_co2_PEM,ps_GCM,global_ave_ps_GCM,global_ave_ps_PEM,Tcond) 261 END SUBROUTINE 262 263 !======================================================================= 264 265 SUBROUTINE computeTcondCO2(timelen,ngrid,nslope,vmr_co2_PEM,ps_PCM,global_avg_ps_PCM,global_avg_ps_PEM,Tcond) 274 266 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 275 267 !!! … … 288 280 289 281 ! INPUT 290 INTEGER,INTENT(IN) :: timelen, ngrid,nslope ! # of timesample,physical points, subslopes 291 REAL,INTENT(IN) :: vmr_co2_PEM(ngrid,timelen) ! Physical points x times field: VMR of CO2 in the first layer [mol/mol] 292 REAL,INTENT(IN) :: ps_GCM(ngrid,timelen) ! Physical points x times field: surface pressure in the GCM [Pa] 293 REAL,INTENT(IN) :: global_ave_ps_GCM ! Global averaged surfacepressure in the GCM [Pa] 294 REAL, INTENT(IN) :: global_ave_ps_PEM ! Global averaged surface pressure computed during the PEM iteration 282 integer, intent(in) :: timelen, ngrid, nslope ! # of timesample, physical points, subslopes 283 real, dimension(ngrid,timelen), intent(in) :: vmr_co2_PEM ! Physical points x times field: VMR of CO2 in the first layer [mol/mol] 284 real, dimension(ngrid,timelen), intent(in) :: ps_PCM ! Physical points x times field: surface pressure in the PCM [Pa] 285 real, intent(in) :: global_avg_ps_PCM ! Global averaged surfacepressure in the PCM [Pa] 286 real, intent(in) :: global_avg_ps_PEM ! Global averaged surface pressure computed during the PEM iteration 287 295 288 ! OUTPUT 296 REAL,INTENT(OUT) :: Tcond(ngrid,nslope) ! Physical points: condensation temperature of CO2, yearly averaged289 real, dimension(ngrid,nslope), intent(out) :: Tcond ! Physical points: condensation temperature of CO2, yearly averaged 297 290 298 291 ! LOCAL 299 300 INTEGER :: ig,it,islope ! for loop 301 REAL :: ave ! intermediate to compute average 292 integer :: ig, it ! For loop 293 real :: ave ! Intermediate to compute average 302 294 303 295 !!!!!!!!!!!!!!!!!!!!!!!!!!!! 304 305 306 DO ig = 1,ngrid 307 ave = 0 308 DO it = 1,timelen 309 ave = ave + beta_clap_co2/(alpha_clap_co2-log(vmr_co2_PEM(ig,it)*ps_GCM(ig,it)*global_ave_ps_GCM/global_ave_ps_PEM/100)) 310 ENDDO 311 DO islope = 1,nslope 312 Tcond(ig,islope) = ave/timelen 313 ENDDO 314 ENDDO 315 RETURN 316 317 318 end subroutine 319 end module 296 do ig = 1,ngrid 297 ave = 0 298 do it = 1,timelen 299 ave = ave + beta_clap_co2/(alpha_clap_co2 - log(vmr_co2_PEM(ig,it)*ps_PCM(ig,it)*global_avg_ps_PCM/global_avg_ps_PEM/100)) 300 enddo 301 Tcond(ig,:) = ave/timelen 302 enddo 303 304 END SUBROUTINE computeTcondCO2 305 306 END MODULE glaciers_mod -
trunk/LMDZ.COMMON/libf/evolution/info_PEM_mod.F90
r3097 r3149 7 7 !======================================================================= 8 8 9 SUBROUTINE info_PEM(year_iter, criterion_stop,i_myear,n_myear)9 SUBROUTINE info_PEM(year_iter,stopPEM,i_myear,n_myear) 10 10 11 11 !======================================================================= … … 22 22 23 23 !----- Arguments 24 integer, intent(in) :: year_iter, criterion_stop! # of year and reason to stop24 integer, intent(in) :: year_iter, stopPEM ! # of year and reason to stop 25 25 integer, intent(in) :: i_myear, n_myear ! Current simulated Martian year and maximum number of Martian years to be simulated 26 26 … … 43 43 endif 44 44 open(1,file = 'info_PEM.txt',status = "old",position = "append",action = "write") 45 write(1,*) year_iter, i_myear, criterion_stop45 write(1,*) year_iter, i_myear, stopPEM 46 46 close(1) 47 47 else -
trunk/LMDZ.COMMON/libf/evolution/interpol_TI_PEM2PCM_mod.F90
r3148 r3149 1 MODULE interpol ate_TIPEM_TIGCM_mod1 MODULE interpol_TI_PEM2PCM_mod 2 2 3 3 implicit none … … 7 7 !======================================================================= 8 8 9 SUBROUTINE interpol ate_TIPEM_TIGCM(ngrid,nslope,nsoil_PEM,nsoil_GCM,TI_PEM,TI_GCM)9 SUBROUTINE interpol_TI_PEM2PCM(ngrid,nslope,nsoil_PEM,nsoil_PCM,TI_PEM,TI_PCM) 10 10 11 11 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 12 12 !!! 13 !!! Purpose: Transfer the thermal inertia from the PEM vertical grid to the GCM vertical grid13 !!! Purpose: Transfer the thermal inertia from the PEM vertical grid to the PCM vertical grid 14 14 !!! 15 15 !!! … … 27 27 integer, intent(in) :: nslope ! # of subslope wihtin the mesh 28 28 integer, intent(in) :: nsoil_PEM ! # of soil layers in the PEM 29 integer, intent(in) :: nsoil_ GCM ! # of soil layers in the GCM29 integer, intent(in) :: nsoil_PCM ! # of soil layers in the GCM 30 30 real, dimension(ngrid,nsoil_PEM,nslope), intent(in) :: TI_PEM ! Thermal inertia in the PEM vertical grid [J/m^2/K/s^{1/2}] 31 31 32 real, dimension(ngrid,nsoil_ GCM,nslope), intent(inout) :: TI_GCM ! Thermal inertia in the GCM vertical grid [J/m^2/K/s^{1/2}]32 real, dimension(ngrid,nsoil_PCM,nslope), intent(inout) :: TI_PCM ! Thermal inertia in the PCM vertical grid [J/m^2/K/s^{1/2}] 33 33 34 34 !----- Code 35 TI_ GCM(:,:,:) = TI_PEM(:,:nsoil_GCM,:)35 TI_PCM = TI_PEM(:,:nsoil_PCM,:) 36 36 37 END SUBROUTINE interpol ate_TIPEM_TIGCM37 END SUBROUTINE interpol_TI_PEM2PCM 38 38 39 END MODULE interpol ate_TIPEM_TIGCM_mod39 END MODULE interpol_TI_PEM2PCM_mod -
trunk/LMDZ.COMMON/libf/evolution/iostart_PEM.F90
r3050 r3149 5 5 !!! 6 6 !!! 7 !!! Author: LL, inspired by iostart from the GCM7 !!! Author: LL, inspired by iostart from the PCM 8 8 !!! 9 9 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! -
trunk/LMDZ.COMMON/libf/evolution/lask_param_mod.F90
r3076 r3149 13 13 real, dimension(:), allocatable, save :: yearlask ! year before present from Laskar et al. Tab 14 14 real, dimension(:), allocatable, save :: obllask ! obliquity [deg] 15 real, dimension(:), allocatable, save :: ecclask ! e xcentricity [deg]15 real, dimension(:), allocatable, save :: ecclask ! eccentricity [deg] 16 16 real, dimension(:), allocatable, save :: lsplask ! ls perihelie [deg] 17 17 integer, save :: last_ilask ! Index of the line in the file year_obl_lask.asc corresponding to the closest lower year to the current year -
trunk/LMDZ.COMMON/libf/evolution/nb_time_step_PCM_mod.F90
r3096 r3149 19 19 !======================================================================= 20 20 ! 21 ! Purpose: Read in the data_PCM_Y r*.nc the number of time step21 ! Purpose: Read in the data_PCM_Y*.nc the number of time steps 22 22 ! 23 23 ! Author: RV -
trunk/LMDZ.COMMON/libf/evolution/orbit_param_criterion_mod.F90
r3082 r3149 99 99 100 100 call getin('max_change_ecc',max_change_ecc) 101 max_ecc = min(e_elips + max_change_ecc,1. - 1.e-10) ! e x< 1.102 min_ecc = max(e_elips - max_change_ecc,0.) ! e x>= 0.101 max_ecc = min(e_elips + max_change_ecc,1. - 1.e-10) ! ecc < 1. 102 min_ecc = max(e_elips - max_change_ecc,0.) ! ecc >= 0. 103 103 write(*,*) 'Maximum eccentricity accepted =', max_ecc 104 104 write(*,*) 'Minimum eccentricity accepted =', min_ecc -
trunk/LMDZ.COMMON/libf/evolution/pem.F90
r3143 r3149 13 13 ! II Run 14 14 ! II_a Update pressure, ice and tracers 15 ! II_b Evolution of theice16 ! II_c CO2 & H2O glaciers flows15 ! II_b Evolution of ice 16 ! II_c Flow of glaciers 17 17 ! II_d Update surface and soil temperatures 18 18 ! II_e Outputs … … 28 28 PROGRAM pem 29 29 30 use phyetat0_mod, 31 use phyredem, 32 use netcdf, 33 use turb_mod, 34 use comslope_mod, 35 use logic_mod, 36 use mod_const_mpi, 30 use phyetat0_mod, only: phyetat0 31 use phyredem, only: physdem0, physdem1 32 use netcdf, only: nf90_open, NF90_NOWRITE, nf90_get_var, nf90_inq_varid, nf90_close 33 use turb_mod, only: q2, wstar 34 use comslope_mod, only: nslope, def_slope, def_slope_mean, subslope_dist, iflat, major_slope, ini_comslope_h 35 use logic_mod, only: iflag_phys 36 use mod_const_mpi, only: COMM_LMDZ 37 37 use infotrac 38 use geometry_mod, only: latitude_deg 39 use conf_pem_mod, only: conf_pem 40 use pemredem, only: pemdem0, pemdem1 41 use glaciers_mod, only: co2glaciers_evol, h2oglaciers_evol, co2glaciersflow, h2oglaciersflow 42 use criterion_pem_stop_mod, only: criterion_waterice_stop, criterion_co2_stop 43 use constants_marspem_mod, only: alpha_clap_co2, beta_clap_co2, alpha_clap_h2o, beta_clap_h2o, m_co2, & 44 m_noco2, threshold_h2o_frost2perennial, threshold_co2_frost2perennial 45 use evol_co2_ice_s_mod, only: evol_co2_ice_s 46 use evol_h2o_ice_s_mod, only: evol_h2o_ice_s 47 use comsoil_h_PEM, only: soil_pem, ini_comsoil_h_PEM, end_comsoil_h_PEM, nsoilmx_PEM, & 48 TI_PEM, inertiedat_PEM, & ! soil thermal inertia 49 tsoil_PEM, mlayer_PEM, layer_PEM, & ! Soil temp, number of subsurface layers, soil mid layer depths 50 fluxgeo, & ! Geothermal flux for the PEM and PCM 51 water_reservoir ! Water ressources 52 use adsorption_mod, only: regolith_adsorption, adsorption_pem, & ! Bool to check if adsorption, main subroutine 53 ini_adsorption_h_PEM, end_adsorption_h_PEM, & ! Allocate arrays 54 co2_adsorbded_phys, h2o_adsorbded_phys ! Mass of co2 and h2O adsorbded 55 use time_evol_mod, only: dt_pem, evol_orbit_pem, Max_iter_pem, convert_years, year_bp_ini 56 use orbit_param_criterion_mod, only: orbit_param_criterion 57 use recomp_orb_param_mod, only: recomp_orb_param 58 use ice_table_mod, only: porefillingice_depth, porefillingice_thickness, end_ice_table_porefilling, & 59 ini_ice_table_porefilling, computeice_table_equilibrium,compute_massh2o_exchange_ssi 60 use soil_thermalproperties_mod, only: update_soil_thermalproperties 61 use time_phylmdz_mod, only: daysec, dtphys, day_end 62 use abort_pem_mod, only: abort_pem 63 use soil_settings_PEM_mod, only: soil_settings_PEM 64 use compute_tendencies_slope_mod, only: compute_tendencies_slope 65 use info_PEM_mod, only: info_PEM 66 use interpolate_TIPEM_TIGCM_mod, only: interpolate_TIPEM_TIGCM 67 use nb_time_step_PCM_mod, only: nb_time_step_PCM 68 use pemetat0_mod, only: pemetat0 69 use read_data_PCM_mod, only: read_data_PCM 70 use recomp_tend_co2_slope_mod, only: recomp_tend_co2_slope 71 use soil_pem_compute_mod, only: soil_pem_compute 72 use writediagpem_mod, only: writediagpem 38 use geometry_mod, only: latitude_deg 39 use conf_pem_mod, only: conf_pem 40 use pemredem, only: pemdem0, pemdem1 41 use glaciers_mod, only: flow_co2glaciers, flow_h2oglaciers, co2_ice_flow, h2o_ice_flow 42 use stopping_crit_mod, only: stopping_crit_h2o_ice, stopping_crit_co2 43 use constants_marspem_mod, only: alpha_clap_co2, beta_clap_co2, alpha_clap_h2o, beta_clap_h2o, m_co2, & 44 m_noco2, inf_h2oice_threshold 45 use evol_ice_mod, only: evol_co2_ice, evol_h2o_ice 46 use comsoil_h_PEM, only: soil_pem, ini_comsoil_h_PEM, end_comsoil_h_PEM, nsoilmx_PEM, & 47 TI_PEM, inertiedat_PEM, & ! soil thermal inertia 48 tsoil_PEM, mlayer_PEM, layer_PEM, & ! Soil temp, number of subsurface layers, soil mid layer depths 49 fluxgeo ! Geothermal flux for the PEM and PCM 50 use adsorption_mod, only: regolith_adsorption, adsorption_pem, & ! Bool to check if adsorption, main subroutine 51 ini_adsorption_h_PEM, end_adsorption_h_PEM, & ! Allocate arrays 52 co2_adsorbded_phys, h2o_adsorbded_phys ! Mass of co2 and h2O adsorbded 53 use time_evol_mod, only: dt_pem, evol_orbit_pem, Max_iter_pem, convert_years, year_bp_ini 54 use orbit_param_criterion_mod, only: orbit_param_criterion 55 use recomp_orb_param_mod, only: recomp_orb_param 56 use ice_table_mod, only: porefillingice_depth, porefillingice_thickness, end_ice_table_porefilling, & 57 ini_ice_table_porefilling, computeice_table_equilibrium,compute_massh2o_exchange_ssi 58 use soil_thermalproperties_mod, only: update_soil_thermalproperties 59 use time_phylmdz_mod, only: daysec, dtphys, day_end 60 use abort_pem_mod, only: abort_pem 61 use soil_settings_PEM_mod, only: soil_settings_PEM 62 use compute_tend_mod, only: compute_tend 63 use info_PEM_mod, only: info_PEM 64 use interpol_TI_PEM2PCM_mod, only: interpol_TI_PEM2PCM 65 use nb_time_step_PCM_mod, only: nb_time_step_PCM 66 use pemetat0_mod, only: pemetat0 67 use read_data_PCM_mod, only: read_data_PCM 68 use recomp_tend_co2_slope_mod, only: recomp_tend_co2_slope 69 use soil_pem_compute_mod, only: soil_pem_compute 70 use writediagpem_mod, only: writediagpem 73 71 74 72 #ifndef CPP_STD … … 77 75 albedodat, zmea, zstd, zsig, zgam, zthe, & 78 76 hmons, summit, base,albedo_h2o_frost, & 79 frost_albedo_threshold, emissiv, watercaptag, perennial_co2ice, & 80 emisice, albedice 77 frost_albedo_threshold, emissiv, watercaptag, perennial_co2ice, emisice, albedice 81 78 use dimradmars_mod, only: totcloudfrac, albedo 82 79 use dust_param_mod, only: tauscaling 83 use tracer_mod, only: noms, igcm_h2o_ice, igcm_co2, mmol, igcm_h2o_vap ! Tracer names and molar masses80 use tracer_mod, only: noms, igcm_h2o_ice, igcm_co2, mmol, igcm_h2o_vap ! Tracer names and molar masses 84 81 use mod_phys_lmdz_para, only: is_parallel, is_sequential, is_mpi_root, is_omp_root, is_master 85 82 use planete_h, only: aphelie, periheli, year_day, peri_day, obliquit, iniorbit 86 use paleoclimate_mod, only: albedo_perennialco2 83 use paleoclimate_mod, only: albedo_perennialco2, paleoclimate 87 84 use comcstfi_h, only: pi, rad, g, cpp, mugaz, r 88 85 use surfini_mod, only: surfini … … 127 124 integer :: day_ini ! First day of the simulation 128 125 real :: pday ! Physical day 129 real :: time_phys ! Same as PCM130 real :: ptimestep ! Same as PCM131 real :: ztime_fin ! Same as PCM126 real :: time_phys ! Same as in PCM 127 real :: ptimestep ! Same as in PCM 128 real :: ztime_fin ! Same as in PCM 132 129 133 130 ! Variables to read start.nc … … 140 137 real, dimension(:,:,:), allocatable :: q ! champs advectes 141 138 real, dimension(ip1jmp1) :: ps ! pression au sol 142 real, dimension(:), allocatable :: ps_start_ GCM ! (ngrid) pression au sol143 real, dimension(:,:), allocatable :: ps_timeseries ! (ngrid x timelen) ! pression au sol instantannées139 real, dimension(:), allocatable :: ps_start_PCM ! (ngrid) surface pressure 140 real, dimension(:,:), allocatable :: ps_timeseries ! (ngrid x timelen) instantaneous surface pressure 144 141 real, dimension(ip1jmp1,llm) :: masse ! masse d'air 145 142 real, dimension(ip1jmp1) :: phis ! geopotentiel au sol … … 161 158 162 159 ! Variables for h2o_ice evolution 163 real :: ini_surf_h2o ! Initial surface of sublimating h2o ice 164 real :: global_ave_press_GCM ! constant: global average pressure retrieved in the GCM [Pa] 165 real :: global_ave_press_old ! constant: Global average pressure of initial/previous time step 166 real :: global_ave_press_new ! constant: Global average pressure of current time step 167 real, dimension(:,:), allocatable :: zplev_new ! Physical x Atmospheric field : mass of the atmospheric layers in the pem at current time step [kg/m^2] 168 real, dimension(:,:), allocatable :: zplev_gcm ! same but retrieved from the PCM [kg/m^2] 160 real, dimension(:,:), allocatable :: h2o_ice ! h2o ice in the PEM 161 real, dimension(:,:), allocatable :: h2o_ice_ini ! Initial amount of h2o ice in the PEM 162 real, dimension(:,:,:), allocatable :: min_h2o_ice ! Minima of h2o ice at each point for the PCM years [kg/m^2] 163 real :: h2o_surf_ini ! Initial surface of sublimating h2o ice 164 real :: global_avg_press_PCM ! constant: global average pressure retrieved in the PCM [Pa] 165 real :: global_avg_press_old ! constant: Global average pressure of initial/previous time step 166 real :: global_avg_press_new ! constant: Global average pressure of current time step 167 real, dimension(:,:), allocatable :: zplev_new ! Physical x Atmospheric field: mass of the atmospheric layers in the pem at current time step [kg/m^2] 168 real, dimension(:,:), allocatable :: zplev_PCM ! same but retrieved from the PCM [kg/m^2] 169 169 real, dimension(:,:,:), allocatable :: zplev_new_timeseries ! Physical x Atmospheric x Time: same as zplev_new, but in times series [kg/m ^2] 170 170 real, dimension(:,:,:), allocatable :: zplev_old_timeseries ! same but with the time series, for oldest time step 171 logical :: STOPPING_water ! Logical: is the criterion (% of change in the surface of sublimating water ice) reached? 172 logical :: STOPPING_1_water ! Logical: is there still water ice to sublimate? 173 logical :: STOPPING_pressure ! Logical: is the criterion (% of change in the surface pressure) reached? 174 integer :: criterion_stop ! which criterion is reached ? 1= h2o ice surf, 2 = co2 ice surf, 3 = ps, 4 = orb param 171 integer :: stopPEM ! which criterion is reached? 0 = no stopping; 1 = h2o ice surf; 2 = no h2o ice; 3 = co2 ice surf; 4 = ps; 5 = orb param; 6 = end of simu 175 172 real, save :: A, B, mmean ! Molar mass: intermediate A, B for computations of the mean molar mass of the layer [mol/kg] 176 173 real, dimension(:,:), allocatable :: q_h2o_PEM_phys ! Physics x Times: h2o mass mixing ratio computed in the PEM, first value comes from PCM [kg/kg] … … 181 178 182 179 ! Variables for co2_ice evolution 183 real :: ini_surf_co2 ! Initial surface of sublimating co2 ice184 logical :: STOPPING_co2 ! Logical: is the criterion (% of change in the surface of sublimating co2 ice) reached? 185 real, dimension(:,: ), allocatable :: vmr_co2_gcm ! Physics x Times co2 volume mixing ratio retrieve from the PCM [m^3/m^3]186 real , dimension(:,:), allocatable :: vmr_co2_pem_phys ! Physics x Times co2 volume mixing ratio used in the PEM187 real, dimension(:,:), allocatable :: q_co2_PEM_phys ! Physics x Times co2 mass mixing ratio in the first layer computed in the PEM, first value comes from PCM [kg/kg]188 real, dimension(:,:), allocatable :: co2frost_ini ! Initial amount of co2 frost (at the start of the PEM run)189 real, dimension(:,:), allocatable :: perennial_co2ice_ini ! Initial amoun of perennial co2 ice (at the start of the PEM run)180 real, dimension(:,:), allocatable :: co2_ice ! co2 ice in the PEM 181 real, dimension(:,:), allocatable :: co2_ice_ini ! Initial amount of co2 ice in the PEM 182 real, dimension(:,:,:), allocatable :: min_co2_ice ! Minimum of co2 ice at each point for the first year [kg/m^2] 183 real :: co2_surf_ini ! Initial surface of sublimating co2 ice 184 real, dimension(:,:), allocatable :: vmr_co2_PCM ! Physics x Times co2 volume mixing ratio retrieve from the PCM [m^3/m^3] 185 real, dimension(:,:), allocatable :: vmr_co2_PEM_phys ! Physics x Times co2 volume mixing ratio used in the PEM 186 real, dimension(:,:), allocatable :: q_co2_PEM_phys ! Physics x Times co2 mass mixing ratio in the first layer computed in the PEM, first value comes from PCM [kg/kg] 190 187 191 188 ! Variables for slopes 192 real, dimension(:,:), allocatable :: min_co2_ice_1 ! ngrid field: minimum of co2 ice at each point for the first year [kg/m^2] 193 real, dimension(:,:), allocatable :: min_co2_ice_2 ! ngrid field: minimum of co2 ice at each point for the second year [kg/m^2] 194 real, dimension(:,:), allocatable :: min_h2o_ice_1 ! ngrid field: minimum of water ice at each point for the first year [kg/m^2] 195 real, dimension(:,:), allocatable :: min_h2o_ice_2 ! ngrid field: minimum of water ice at each point for the second year [kg/m^2] 196 real, dimension(:,:,:), allocatable :: co2_ice_GCM ! Physics x NSLOPE x Times field: co2 ice given by the PCM [kg/m^2] 197 real, dimension(:,:), allocatable :: initial_co2_ice_sublim ! physical point field: Logical array indicating sublimating point of co2 ice 198 real, dimension(:,:), allocatable :: initial_h2o_ice ! physical point field: Logical array indicating if there is water ice at initial state 199 real, dimension(:,:), allocatable :: initial_co2_ice ! physical point field: Logical array indicating if there is co2 ice at initial state 200 real, dimension(:,:), allocatable :: tendencies_co2_ice ! physical point x slope field: Tendency of evolution of perennial co2 ice over a year 201 real, dimension(:,:), allocatable :: tendencies_co2_ice_ini ! physical point x slope field x nslope: Tendency of evolution of perennial co2 ice over a year in the PCM 202 real, dimension(:,:), allocatable :: tendencies_h2o_ice ! physical point x slope field: Tendency of evolution of perennial h2o ice 203 real, dimension(:,:), allocatable :: flag_co2flow ! (ngrid,nslope): Flag where there is a CO2 glacier flow 204 real, dimension(:), allocatable :: flag_co2flow_mesh ! (ngrid) : Flag where there is a CO2 glacier flow 205 real, dimension(:,:), allocatable :: flag_h2oflow ! (ngrid,nslope): Flag where there is a H2O glacier flow 206 real, dimension(:), allocatable :: flag_h2oflow_mesh ! (ngrid) : Flag where there is a H2O glacier flow 189 real, dimension(:,:,:), allocatable :: co2_ice_PCM ! Physics x NSLOPE x Times field: co2 ice given by the PCM [kg/m^2] 190 real, dimension(:,:), allocatable :: co2_ice_ini_sublim ! physical point field: Logical array indicating sublimating point of co2 ice 191 real, dimension(:,:), allocatable :: initial_h2o_ice ! physical point field: Logical array indicating if there is water ice at initial state 192 real, dimension(:,:), allocatable :: tend_co2_ice ! physical point x slope field: Tendency of evolution of perennial co2 ice over a year 193 real, dimension(:,:), allocatable :: tend_co2_ice_ini ! physical point x slope field x nslope: Tendency of evolution of perennial co2 ice over a year in the PCM 194 real, dimension(:,:), allocatable :: tend_h2o_ice ! physical point x slope field: Tendency of evolution of perennial h2o ice 195 real, dimension(:,:), allocatable :: flag_co2flow ! (ngrid,nslope): Flag where there is a CO2 glacier flow 196 real, dimension(:), allocatable :: flag_co2flow_mesh ! (ngrid) : Flag where there is a CO2 glacier flow 197 real, dimension(:,:), allocatable :: flag_h2oflow ! (ngrid,nslope): Flag where there is a H2O glacier flow 198 real, dimension(:), allocatable :: flag_h2oflow_mesh ! (ngrid) : Flag where there is a H2O glacier flow 207 199 208 200 ! Variables for surface and soil 209 real, dimension(:,:), allocatable :: tsurf_ave ! Physic x SLOPE field 210 real, dimension(:,:,:), allocatable :: tsoil_ave ! Physic x SOIL x SLOPE field 211 real, dimension(:,:,:), allocatable :: tsurf_ GCM_timeseries ! ngrid x SLOPE XTULES field: Surface Temperature in timeseries [K]212 real, dimension(:,:,:,:), allocatable :: tsoil_phys_PEM_timeseries ! IG x SLOPE XTULES field : NOn averaged Soil Temperature [K]213 real, dimension(:,:,:,:), allocatable :: tsoil_ GCM_timeseries ! IG x SLOPE XTULES field : NOn averaged Soil Temperature [K]214 real, dimension(:,:), allocatable :: tsurf_av e_yr1 ! Physic x SLOPE field: Averaged Surface Temperature of first call of the PCM [K]201 real, dimension(:,:), allocatable :: tsurf_ave ! Physic x SLOPE field: Averaged Surface Temperature [K] 202 real, dimension(:,:,:), allocatable :: tsoil_ave ! Physic x SOIL x SLOPE field: Averaged Soil Temperature [K] 203 real, dimension(:,:,:), allocatable :: tsurf_PCM_timeseries ! ngrid x SLOPE XTULES field: Surface Temperature in timeseries [K] 204 real, dimension(:,:,:,:), allocatable :: tsoil_phys_PEM_timeseries ! IG x SLOPE XTULES field: Non averaged Soil Temperature [K] 205 real, dimension(:,:,:,:), allocatable :: tsoil_PCM_timeseries ! IG x SLOPE XTULES field: Non averaged Soil Temperature [K] 206 real, dimension(:,:), allocatable :: tsurf_avg_yr1 ! Physic x SLOPE field: Averaged Surface Temperature of first call of the PCM [K] 215 207 real, dimension(:,:), allocatable :: TI_locslope ! Physic x Soil: Intermediate thermal inertia to compute Tsoil [SI] 216 208 real, dimension(:,:), allocatable :: Tsoil_locslope ! Physic x Soil: intermediate when computing Tsoil [K] 217 real, dimension(:), allocatable :: Tsurf_locslope ! Physic x Soil: Intermediate surface temperature 209 real, dimension(:), allocatable :: Tsurf_locslope ! Physic x Soil: Intermediate surface temperature to compute Tsoil [K] 218 210 real, dimension(:,:,:,:), allocatable :: watersoil_density_timeseries ! Physic x Soil x Slope x Times water soil density, time series [kg /m^3] 219 211 real, dimension(:,:), allocatable :: watersurf_density_ave ! Physic x Slope, water surface density, yearly averaged [kg/m^3] 220 212 real, dimension(:,:,:,:), allocatable :: watersoil_density_PEM_timeseries ! Physic x Soil x Slope x Times, water soil density, time series [kg/m^3] 221 213 real, dimension(:,:,:), allocatable :: watersoil_density_PEM_ave ! Physic x Soil x SLopes, water soil density, yearly averaged [kg/m^3] 222 real, dimension(:,:), allocatable :: Tsurfav e_before_saved ! Surface temperature saved from previous time step [K]214 real, dimension(:,:), allocatable :: Tsurfavg_before_saved ! Surface temperature saved from previous time step [K] 223 215 real, dimension(:), allocatable :: delta_co2_adsorbded ! Physics: quantity of CO2 that is exchanged because of adsorption / desorption [kg/m^2] 224 216 real, dimension(:), allocatable :: delta_h2o_adsorbded ! Physics: quantity of H2O that is exchanged because of adsorption / desorption [kg/m^2] … … 236 228 integer :: n_myear ! Maximum number of Martian years of the chained simulations 237 229 real :: timestep ! timestep [s] 238 real :: watercap_sum ! total mass of water cap [kg/m^2]239 real :: water_sum ! total mass of water in the mesh [kg/m^2]240 230 241 231 #ifdef CPP_STD … … 341 331 !------------------------ 342 332 ! I_b.1 Read start_evol.nc 343 allocate(ps_start_ GCM(ngrid))333 allocate(ps_start_PCM(ngrid)) 344 334 #ifndef CPP_1D 345 335 call dynetat0(start_name,vcov,ucov,teta,q,masse,ps,phis,time_0) 346 336 347 call gr_dyn_fi(1,iip1,jjp1,ngridmx,ps,ps_start_ GCM)337 call gr_dyn_fi(1,iip1,jjp1,ngridmx,ps,ps_start_PCM) 348 338 349 339 call iniconst !new … … 359 349 status = nf90_close(ncid) 360 350 361 call iniphysiq(iim,jjm,llm,(jjm-1)*iim+2,comm_lmdz,daysec,day_ini,dtphys/nsplit_phys, & 362 rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp,iflag_phys) 351 call iniphysiq(iim,jjm,llm,(jjm-1)*iim+2,comm_lmdz,daysec,day_ini,dtphys/nsplit_phys,rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp,iflag_phys) 363 352 #else 364 ps_start_ GCM(1) = ps(1)353 ps_start_PCM(1) = ps(1) 365 354 #endif 366 355 … … 387 376 #ifndef CPP_STD 388 377 call phyetat0(startfi_name,0,0,nsoilmx,ngrid,nlayer,nq,nqsoil,day_ini,time_phys,tsurf, & 389 tsoil,albedo,emis,q2,qsurf,qsoil,tauscaling,totcloudfrac,wstar, &378 tsoil,albedo,emis,q2,qsurf,qsoil,tauscaling,totcloudfrac,wstar, & 390 379 watercap,perennial_co2ice,def_slope,def_slope_mean,subslope_dist) 391 380 … … 414 403 allocate(inertiesoil(ngrid,nsoilmx,1)) 415 404 call phyetat0(.true.,ngrid,nlayer,startfi_name,0,0,nsoilmx,nq,nqsoil,day_ini,time_phys, & 416 tsurf_read_generic,tsoil_read_generic,emis_read_generic,q2, &417 qsurf_read_generic,qsoil_read_generic,cloudfrac,totcloudfrac,hice, &405 tsurf_read_generic,tsoil_read_generic,emis_read_generic,q2, & 406 qsurf_read_generic,qsoil_read_generic,cloudfrac,totcloudfrac,hice, & 418 407 rnat,pctsrf_sic,tslab,tsea_ice,sea_ice) 419 408 call surfini(ngrid,nq,qsurf_read_generic,albedo_read_generic,albedo_bareground,albedo_snow_SPECTV,albedo_co2_ice_SPECTV) … … 422 411 call ini_comslope_h(ngrid,1) 423 412 424 qsurf(:,:,1) = qsurf_read_generic (:,:)425 tsurf(:,1) = tsurf_read_generic (:)426 tsoil(:,:,1) = tsoil_read_generic (:,:)427 emis(:,1) = emis_read_generic (:)413 qsurf(:,:,1) = qsurf_read_generic 414 tsurf(:,1) = tsurf_read_generic 415 tsoil(:,:,1) = tsoil_read_generic 416 emis(:,1) = emis_read_generic 428 417 watercap(:,1) = 0. 429 418 watercaptag(:) = .false. 430 419 albedo(:,1,1) = albedo_read_generic(:,1) 431 420 albedo(:,2,1) = albedo_read_generic(:,2) 432 inertiesoil(:,:,1) = inertiedat (:,:)421 inertiesoil(:,:,1) = inertiedat 433 422 434 423 if (nslope == 1) then … … 440 429 441 430 ! Remove unphysical values of surface tracer 442 qsurf(:,:,1) = qsurf_read_generic (:,:)431 qsurf(:,:,1) = qsurf_read_generic 443 432 where (qsurf < 0.) qsurf = 0. 444 433 #endif … … 472 461 allocate(flag_h2oflow_mesh(ngrid)) 473 462 474 flag_co2flow (:,:)= 0475 flag_co2flow_mesh (:)= 0476 flag_h2oflow (:,:)= 0477 flag_h2oflow_mesh (:)= 0463 flag_co2flow = 0 464 flag_co2flow_mesh = 0 465 flag_h2oflow = 0 466 flag_h2oflow_mesh = 0 478 467 479 468 !------------------------ … … 486 475 allocate(tsoil_ave(ngrid,nsoilmx,nslope)) 487 476 allocate(watersoil_density_PEM_ave(ngrid,nsoilmx_PEM,nslope)) 488 allocate(vmr_co2_ gcm(ngrid,timelen))477 allocate(vmr_co2_PCM(ngrid,timelen)) 489 478 allocate(ps_timeseries(ngrid,timelen)) 490 allocate(min_co2_ice_1(ngrid,nslope)) 491 allocate(min_h2o_ice_1(ngrid,nslope)) 492 allocate(min_co2_ice_2(ngrid,nslope)) 493 allocate(min_h2o_ice_2(ngrid,nslope)) 494 allocate(tsurf_ave_yr1(ngrid,nslope)) 479 allocate(min_co2_ice(ngrid,nslope,2)) 480 allocate(min_h2o_ice(ngrid,nslope,2)) 481 allocate(tsurf_avg_yr1(ngrid,nslope)) 495 482 allocate(tsurf_ave(ngrid,nslope)) 496 allocate(tsurf_ GCM_timeseries(ngrid,nslope,timelen))497 allocate(tsoil_ GCM_timeseries(ngrid,nsoilmx,nslope,timelen))483 allocate(tsurf_PCM_timeseries(ngrid,nslope,timelen)) 484 allocate(tsoil_PCM_timeseries(ngrid,nsoilmx,nslope,timelen)) 498 485 allocate(q_co2_PEM_phys(ngrid,timelen)) 499 486 allocate(q_h2o_PEM_phys(ngrid,timelen)) 500 allocate(co2_ice_ GCM(ngrid,nslope,timelen))487 allocate(co2_ice_PCM(ngrid,nslope,timelen)) 501 488 allocate(watersurf_density_ave(ngrid,nslope)) 502 489 allocate(watersoil_density_timeseries(ngrid,nsoilmx,nslope,timelen)) 503 allocate(Tsurfav e_before_saved(ngrid,nslope))490 allocate(Tsurfavg_before_saved(ngrid,nslope)) 504 491 allocate(tsoil_phys_PEM_timeseries(ngrid,nsoilmx_PEM,nslope,timelen)) 505 492 allocate(watersoil_density_PEM_timeseries(ngrid,nsoilmx_PEM,nslope,timelen)) … … 508 495 allocate(delta_h2o_icetablesublim(ngrid)) 509 496 allocate(delta_h2o_adsorbded(ngrid)) 510 allocate(vmr_co2_ pem_phys(ngrid,timelen))497 allocate(vmr_co2_PEM_phys(ngrid,timelen)) 511 498 512 499 write(*,*) "Downloading data Y1..." 513 call read_data_PCM("data_PCM_Y1.nc",timelen, iim,jjm_value,ngrid,nslope,vmr_co2_ gcm,ps_timeseries,min_co2_ice_1,min_h2o_ice_1, &514 tsurf_av e_yr1,tsoil_ave, tsurf_GCM_timeseries,tsoil_GCM_timeseries,q_co2_PEM_phys,q_h2o_PEM_phys,&515 co2_ice_ GCM,watersurf_density_ave,watersoil_density_timeseries)500 call read_data_PCM("data_PCM_Y1.nc",timelen, iim,jjm_value,ngrid,nslope,vmr_co2_PCM,ps_timeseries,min_co2_ice(:,:,1),min_h2o_ice(:,:,1), & 501 tsurf_avg_yr1,tsoil_ave,tsurf_PCM_timeseries,tsoil_PCM_timeseries,q_co2_PEM_phys,q_h2o_PEM_phys, & 502 co2_ice_PCM,watersurf_density_ave,watersoil_density_timeseries) 516 503 write(*,*) "Downloading data Y1 done" 517 504 518 505 ! Then we read the evolution of water and co2 ice (and the mass mixing ratio) over the second year of the PCM run, saving only the minimum value 519 506 write(*,*) "Downloading data Y2" 520 call read_data_PCM("data_PCM_Y2.nc",timelen,iim,jjm_value,ngrid,nslope,vmr_co2_ gcm,ps_timeseries,min_co2_ice_2,min_h2o_ice_2, &521 tsurf_ave,tsoil_ave, tsurf_GCM_timeseries,tsoil_GCM_timeseries,q_co2_PEM_phys,q_h2o_PEM_phys,&522 co2_ice_ GCM,watersurf_density_ave,watersoil_density_timeseries)507 call read_data_PCM("data_PCM_Y2.nc",timelen,iim,jjm_value,ngrid,nslope,vmr_co2_PCM,ps_timeseries,min_co2_ice(:,:,2),min_h2o_ice(:,:,2), & 508 tsurf_ave,tsoil_ave,tsurf_PCM_timeseries,tsoil_PCM_timeseries,q_co2_PEM_phys,q_h2o_PEM_phys, & 509 co2_ice_PCM,watersurf_density_ave,watersoil_density_timeseries) 523 510 write(*,*) "Downloading data Y2 done" 524 511 … … 536 523 if (soil_pem) then 537 524 call soil_settings_PEM(ngrid,nslope,nsoilmx_PEM,nsoilmx,inertiesoil,TI_PEM) 538 do l = 1,nsoilmx 539 tsoil_PEM(:,l,:) = tsoil_ave(:,l,:) 540 tsoil_phys_PEM_timeseries(:,l,:,:) = tsoil_GCM_timeseries(:,l,:,:) 541 watersoil_density_PEM_timeseries(:,l,:,:) = watersoil_density_timeseries(:,l,:,:) 542 enddo 525 tsoil_PEM(:,1:nsoilmx,:) = tsoil_ave 526 tsoil_phys_PEM_timeseries(:,1:nsoilmx,:,:) = tsoil_PCM_timeseries 527 watersoil_density_PEM_timeseries(:,1:nsoilmx,:,:) = watersoil_density_timeseries 543 528 do l = nsoilmx + 1,nsoilmx_PEM 544 529 tsoil_PEM(:,l,:) = tsoil_ave(:,nsoilmx,:) 545 530 watersoil_density_PEM_timeseries(:,l,:,:) = watersoil_density_timeseries(:,nsoilmx,:,:) 546 531 enddo 547 watersoil_density_PEM_ave (:,:,:) = sum(watersoil_density_PEM_timeseries(:,:,:,:),4)/timelen532 watersoil_density_PEM_ave = sum(watersoil_density_PEM_timeseries,4)/timelen 548 533 endif !soil_pem 549 deallocate(tsoil_ave,tsoil_ GCM_timeseries)534 deallocate(tsoil_ave,tsoil_PCM_timeseries) 550 535 551 536 !------------------------ … … 553 538 ! I_f Compute tendencies 554 539 !------------------------ 555 allocate(tendencies_co2_ice(ngrid,nslope)) 556 allocate(tendencies_co2_ice_ini(ngrid,nslope)) 557 allocate(tendencies_h2o_ice(ngrid,nslope)) 540 allocate(tend_co2_ice(ngrid,nslope),tend_h2o_ice(ngrid,nslope)) 541 allocate(tend_co2_ice_ini(ngrid,nslope)) 558 542 559 543 ! Compute the tendencies of the evolution of ice over the years 560 call compute_tendencies_slope(ngrid,nslope,min_co2_ice_1,min_co2_ice_2,tendencies_co2_ice) 561 tendencies_co2_ice_ini(:,:) = tendencies_co2_ice(:,:) 562 call compute_tendencies_slope(ngrid,nslope,min_h2o_ice_1,min_h2o_ice_2,tendencies_h2o_ice) 563 564 deallocate(min_co2_ice_1,min_co2_ice_2,min_h2o_ice_1,min_h2o_ice_2) 544 call compute_tend(ngrid,nslope,min_co2_ice,tend_co2_ice) 545 call compute_tend(ngrid,nslope,min_h2o_ice,tend_h2o_ice) 546 tend_co2_ice_ini = tend_co2_ice 565 547 566 548 !------------------------ … … 568 550 ! I_g Save initial PCM situation 569 551 !------------------------ 570 allocate(initial_co2_ice_sublim(ngrid,nslope))571 allocate(initial_co2_ice(ngrid,nslope))572 allocate(initial_h2o_ice(ngrid,nslope))573 574 552 ! We save the places where water ice is sublimating 575 553 ! We compute the surface of water ice sublimating 576 ini_surf_co2= 0.577 ini_surf_h2o= 0.554 co2_surf_ini = 0. 555 h2o_surf_ini = 0. 578 556 Total_surface = 0. 579 557 do i = 1,ngrid 580 558 Total_surface = Total_surface + cell_area(i) 581 559 do islope = 1,nslope 582 if (tendencies_co2_ice(i,islope) < 0) then 583 initial_co2_ice_sublim(i,islope) = 1. 584 ini_surf_co2 = ini_surf_co2 + cell_area(i)*subslope_dist(i,islope) 585 else 586 initial_co2_ice_sublim(i,islope) = 0. 587 endif 588 if (qsurf(i,igcm_co2,islope) > 0) then 589 initial_co2_ice(i,islope) = 1. 590 else 591 initial_co2_ice(i,islope) = 0. 592 endif 593 if (tendencies_h2o_ice(i,islope) < 0) then 594 initial_h2o_ice(i,islope) = 1. 595 ini_surf_h2o = ini_surf_h2o + cell_area(i)*subslope_dist(i,islope) 596 else 597 initial_h2o_ice(i,islope) = 0. 598 endif 560 if (tend_co2_ice(i,islope) < 0.) co2_surf_ini = co2_surf_ini + cell_area(i)*subslope_dist(i,islope) 561 if (tend_h2o_ice(i,islope) < 0.) h2o_surf_ini = h2o_surf_ini + cell_area(i)*subslope_dist(i,islope) 599 562 enddo 600 563 enddo 601 564 602 write(*,*) "Total initial surface of co2 ice sublimating (slope) =", ini_surf_co2603 write(*,*) "Total initial surface of h2o ice sublimating (slope) =", ini_surf_h2o565 write(*,*) "Total initial surface of co2 ice sublimating (slope) =", co2_surf_ini 566 write(*,*) "Total initial surface of h2o ice sublimating (slope) =", h2o_surf_ini 604 567 write(*,*) "Total surface of the planet =", Total_surface 605 allocate(zplev_ gcm(ngrid,nlayer + 1))568 allocate(zplev_PCM(ngrid,nlayer + 1)) 606 569 607 570 do ig = 1,ngrid 608 zplev_ gcm(ig,:) = ap(:) + bp(:)*ps_start_GCM(ig)571 zplev_PCM(ig,:) = ap + bp*ps_start_PCM(ig) 609 572 enddo 610 573 611 global_ave_press_old = 0. 612 do i = 1,ngrid 613 global_ave_press_old = global_ave_press_old + cell_area(i)*ps_start_GCM(i)/Total_surface 614 enddo 615 616 global_ave_press_GCM = global_ave_press_old 617 global_ave_press_new = global_ave_press_old 618 write(*,*) "Initial global average pressure =", global_ave_press_GCM 574 global_avg_press_old = sum(cell_area*ps_start_PCM)/Total_surface 575 global_avg_press_PCM = global_avg_press_old 576 global_avg_press_new = global_avg_press_old 577 write(*,*) "Initial global average pressure =", global_avg_press_PCM 619 578 620 579 !------------------------ … … 622 581 ! I_h Read the startpem.nc 623 582 !------------------------ 583 allocate(co2_ice(ngrid,nslope),h2o_ice(ngrid,nslope)) 584 deallocate(min_co2_ice,min_h2o_ice) 585 624 586 call pemetat0("startpem.nc",ngrid,nsoilmx,nsoilmx_PEM,nslope,timelen,timestep,TI_PEM,tsoil_PEM,porefillingice_depth, & 625 porefillingice_thickness,tsurf_ave_yr1, tsurf_ave, q_co2_PEM_phys, q_h2o_PEM_phys,ps_timeseries, & 626 tsoil_phys_PEM_timeseries,tendencies_h2o_ice,tendencies_co2_ice,qsurf(:,igcm_co2,:), & 627 qsurf(:,igcm_h2o_ice,:),global_ave_press_GCM,watersurf_density_ave,watersoil_density_PEM_ave, & 628 co2_adsorbded_phys,delta_co2_adsorbded,h2o_adsorbded_phys,delta_h2o_adsorbded,water_reservoir) 629 630 delta_h2o_icetablesublim(:) = 0. 631 632 ! We save the initial values for the co2 frost and perennial ice 633 allocate(co2frost_ini(ngrid,nslope),perennial_co2ice_ini(ngrid,nslope)) 634 co2frost_ini = qsurf(:,igcm_co2,:) 635 perennial_co2ice_ini = perennial_co2ice 636 637 do ig = 1,ngrid 638 do islope = 1,nslope 639 qsurf(ig,igcm_h2o_ice,islope) = qsurf(ig,igcm_h2o_ice,islope) + water_reservoir(ig)*cos(pi*def_slope_mean(islope)/180.) 640 qsurf(ig,igcm_co2,islope) = qsurf(ig,igcm_co2,islope) + perennial_co2ice(ig,islope) 641 enddo 642 enddo 587 porefillingice_thickness,tsurf_avg_yr1,tsurf_ave,q_co2_PEM_phys,q_h2o_PEM_phys,ps_timeseries, & 588 tsoil_phys_PEM_timeseries,tend_h2o_ice,tend_co2_ice,co2_ice,h2o_ice,global_avg_press_PCM, & 589 watersurf_density_ave,watersoil_density_PEM_ave,co2_adsorbded_phys,delta_co2_adsorbded, & 590 h2o_adsorbded_phys,delta_h2o_adsorbded) 591 592 allocate(co2_ice_ini(ngrid,nslope)) 593 co2_ice_ini = co2_ice 594 595 delta_h2o_icetablesublim = 0. 643 596 644 597 if (adsorption_pem) then … … 648 601 do islope = 1,nslope 649 602 do l = 1,nsoilmx_PEM - 1 650 totmassco2_adsorbded = totmassco2_adsorbded + co2_adsorbded_phys(ig,l,islope)*(layer_PEM(l +1) - layer_PEM(l))* &603 totmassco2_adsorbded = totmassco2_adsorbded + co2_adsorbded_phys(ig,l,islope)*(layer_PEM(l + 1) - layer_PEM(l))* & 651 604 subslope_dist(ig,islope)/cos(pi*def_slope_mean(islope)/180.)*cell_area(ig) 652 totmassh2o_adsorbded = totmassh2o_adsorbded + h2o_adsorbded_phys(ig,l,islope)*(layer_PEM(l +1) - layer_PEM(l))* &605 totmassh2o_adsorbded = totmassh2o_adsorbded + h2o_adsorbded_phys(ig,l,islope)*(layer_PEM(l + 1) - layer_PEM(l))* & 653 606 subslope_dist(ig,islope)/cos(pi*def_slope_mean(islope)/180.)*cell_area(ig) 654 607 enddo 655 608 enddo 656 609 enddo 657 658 610 write(*,*) "Tot mass of CO2 in the regolith =", totmassco2_adsorbded 659 611 write(*,*) "Tot mass of H2O in the regolith =", totmassh2o_adsorbded 660 612 endif ! adsorption 661 deallocate(tsurf_av e_yr1)613 deallocate(tsurf_avg_yr1) 662 614 663 615 !------------------------ … … 684 636 !------------------------ 685 637 year_iter = 0 638 stopPEM = 0 686 639 687 640 do while (year_iter < year_iter_max .and. i_myear < n_myear) … … 690 643 do i = 1,ngrid 691 644 do islope = 1,nslope 692 global_av e_press_new = global_ave_press_new - g*cell_area(i)*tendencies_co2_ice(i,islope)*subslope_dist(i,islope)/cos(pi*def_slope_mean(islope)/180.)/Total_surface645 global_avg_press_new = global_avg_press_new - g*cell_area(i)*tend_co2_ice(i,islope)*subslope_dist(i,islope)/cos(pi*def_slope_mean(islope)/180.)/Total_surface 693 646 enddo 694 647 enddo … … 696 649 if (adsorption_pem) then 697 650 do i = 1,ngrid 698 global_av e_press_new = global_ave_press_new - g*cell_area(i)*delta_co2_adsorbded(i)/Total_surface651 global_avg_press_new = global_avg_press_new - g*cell_area(i)*delta_co2_adsorbded(i)/Total_surface 699 652 enddo 700 653 endif 701 write(*,*) 'Global average pressure old time step',global_av e_press_old702 write(*,*) 'Global average pressure new time step',global_av e_press_new654 write(*,*) 'Global average pressure old time step',global_avg_press_old 655 write(*,*) 'Global average pressure new time step',global_avg_press_new 703 656 704 657 ! II.a.2. Old pressure levels for the timeseries, this value is deleted when unused and recreated each time (big memory consuption) … … 714 667 write(*,*) "Recomputing the surface pressure timeserie adapted to the new pressure..." 715 668 do ig = 1,ngrid 716 ps_timeseries(ig,:) = ps_timeseries(ig,:)*global_av e_press_new/global_ave_press_old669 ps_timeseries(ig,:) = ps_timeseries(ig,:)*global_avg_press_new/global_avg_press_old 717 670 enddo 718 671 719 672 ! II.a.4. New pressure levels timeseries 720 allocate(zplev_new_timeseries(ngrid,nlayer +1,timelen))673 allocate(zplev_new_timeseries(ngrid,nlayer + 1,timelen)) 721 674 write(*,*) "Recomputing the new pressure levels timeserie adapted to the new pressure..." 722 675 do l = 1,nlayer + 1 … … 755 708 endif 756 709 mmean=1/(A*q_co2_PEM_phys(ig,t) + B) 757 vmr_co2_ pem_phys(ig,t) = q_co2_PEM_phys(ig,t)*mmean/m_co2710 vmr_co2_PEM_phys(ig,t) = q_co2_PEM_phys(ig,t)*mmean/m_co2 758 711 enddo 759 712 enddo … … 763 716 !------------------------ 764 717 ! II Run 765 ! II_b Evolution of the ice 766 !------------------------ 767 write(*,*) "Evolution of h2o ice" 768 call evol_h2o_ice_s(ngrid,nslope,cell_area,delta_h2o_adsorbded,delta_h2o_icetablesublim,qsurf(:,igcm_h2o_ice,:),tendencies_h2o_ice,STOPPING_1_water) 769 770 write(*,*) "Evolution of co2 ice" 771 call evol_co2_ice_s(qsurf(:,igcm_co2,:),tendencies_co2_ice,iim,jjm_value,ngrid,cell_area,nslope) 718 ! II_b Evolution of ice 719 !------------------------ 720 call evol_h2o_ice(ngrid,nslope,cell_area,delta_h2o_adsorbded,delta_h2o_icetablesublim,h2o_ice,tend_h2o_ice,stopPEM) 721 call evol_co2_ice(ngrid,nslope,co2_ice,tend_co2_ice) 772 722 773 723 !------------------------ 774 724 ! II Run 775 ! II_c CO2 & H2O glaciers flows 776 !------------------------ 777 write(*,*) "CO2 glacier flows" 778 if (co2glaciersflow) call co2glaciers_evol(timelen,ngrid,nslope,iflat,subslope_dist,def_slope_mean,vmr_co2_pem_phys,ps_timeseries, & 779 global_ave_press_GCM,global_ave_press_new,qsurf(:,igcm_co2,:),flag_co2flow,flag_co2flow_mesh) 780 781 write(*,*) "H2O glacier flows" 782 if (h2oglaciersflow) call h2oglaciers_evol(timelen,ngrid,nslope,iflat,subslope_dist,def_slope_mean,tsurf_ave,qsurf(:,igcm_h2o_ice,:),flag_h2oflow,flag_h2oflow_mesh) 725 ! II_c Flow of glaciers 726 !------------------------ 727 if (co2_ice_flow) call flow_co2glaciers(timelen,ngrid,nslope,iflat,subslope_dist,def_slope_mean,vmr_co2_PEM_phys,ps_timeseries, & 728 global_avg_press_PCM,global_avg_press_new,co2_ice,flag_co2flow,flag_co2flow_mesh) 729 if (h2o_ice_flow) call flow_h2oglaciers(timelen,ngrid,nslope,iflat,subslope_dist,def_slope_mean,tsurf_ave,h2o_ice,flag_h2oflow,flag_h2oflow_mesh) 783 730 784 731 !------------------------ … … 789 736 write(*,*) "Updating the new Tsurf" 790 737 bool_sublim = .false. 791 Tsurfav e_before_saved(:,:) = tsurf_ave(:,:)738 Tsurfavg_before_saved = tsurf_ave 792 739 do ig = 1,ngrid 793 740 do islope = 1,nslope 794 if ( initial_co2_ice(ig,islope) > 0.5 .and. qsurf(ig,igcm_co2,islope) < 1.e-10) then !co2ice disappeared, look for closest point without co2ice741 if (co2_ice_ini(ig,islope) > 0.5 .and. co2_ice(ig,islope) < 1.e-10) then ! co2 ice disappeared, look for closest point without co2ice 795 742 if (latitude_deg(ig) > 0) then 796 743 do ig_loop = ig,ngrid 797 744 do islope_loop = islope,iflat,-1 798 if ( initial_co2_ice(ig_loop,islope_loop) < 0.5 .and. qsurf(ig_loop,igcm_co2,islope_loop) < 1.e-10) then745 if (co2_ice_ini(ig_loop,islope_loop) < 0.5 .and. co2_ice(ig_loop,islope_loop) < 1.e-10) then 799 746 tsurf_ave(ig,islope) = tsurf_ave(ig_loop,islope_loop) 800 747 bool_sublim = .true. … … 807 754 do ig_loop = ig,1,-1 808 755 do islope_loop = islope,iflat 809 if( initial_co2_ice(ig_loop,islope_loop) < 0.5 .and. qsurf(ig_loop,igcm_co2,islope_loop) < 1.e-10) then756 if(co2_ice_ini(ig_loop,islope_loop) < 0.5 .and. co2_ice(ig_loop,islope_loop) < 1.e-10) then 810 757 tsurf_ave(ig,islope) = tsurf_ave(ig_loop,islope_loop) 811 758 bool_sublim = .true. … … 816 763 enddo 817 764 endif 818 initial_co2_ice(ig,islope) = 0819 if (( qsurf(ig,igcm_co2,islope) < 1.e-10) .and. (qsurf(ig,igcm_h2o_ice,islope) > frost_albedo_threshold)) then765 co2_ice_ini(ig,islope) = 0 766 if ((co2_ice(ig,islope) < 1.e-10) .and. (h2o_ice(ig,islope) > frost_albedo_threshold)) then 820 767 albedo(ig,1,islope) = albedo_h2o_frost 821 768 albedo(ig,2,islope) = albedo_h2o_frost … … 825 772 emis(ig,islope) = emissiv 826 773 endif 827 else if (( qsurf(ig,igcm_co2,islope) > 1.e-3) .and. (tendencies_co2_ice(ig,islope) > 1.e-10)) then !Put tsurf as tcond co2774 else if ((co2_ice(ig,islope) > 1.e-3) .and. (tend_co2_ice(ig,islope) > 1.e-10)) then ! Put tsurf as tcond co2 828 775 ave = 0. 829 776 do t = 1,timelen 830 if (co2_ice_ GCM(ig,islope,t) > 1.e-3) then831 ave = ave + beta_clap_co2/(alpha_clap_co2-log(vmr_co2_ pem_phys(ig,t)*ps_timeseries(ig,t)/100.))777 if (co2_ice_PCM(ig,islope,t) > 1.e-3) then 778 ave = ave + beta_clap_co2/(alpha_clap_co2-log(vmr_co2_PEM_phys(ig,t)*ps_timeseries(ig,t)/100.)) 832 779 else 833 ave = ave + tsurf_ GCM_timeseries(ig,islope,t)780 ave = ave + tsurf_PCM_timeseries(ig,islope,t) 834 781 endif 835 782 enddo … … 849 796 850 797 do t = 1,timelen 851 tsurf_ GCM_timeseries(:,:,t) = tsurf_GCM_timeseries(:,:,t) + (tsurf_ave(:,:) - Tsurfave_before_saved(:,:))798 tsurf_PCM_timeseries(:,:,t) = tsurf_PCM_timeseries(:,:,t) + tsurf_ave - Tsurfavg_before_saved 852 799 enddo 853 800 ! for the start 854 801 do ig = 1,ngrid 855 802 do islope = 1,nslope 856 tsurf(ig,islope) = tsurf(ig,islope) - (Tsurfav e_before_saved(ig,islope) - tsurf_ave(ig,islope))803 tsurf(ig,islope) = tsurf(ig,islope) - (Tsurfavg_before_saved(ig,islope) - tsurf_ave(ig,islope)) 857 804 enddo 858 805 enddo … … 868 815 ! Soil averaged 869 816 do islope = 1,nslope 870 TI_locslope (:,:)= TI_PEM(:,:,islope)817 TI_locslope = TI_PEM(:,:,islope) 871 818 do t = 1,timelen 872 Tsoil_locslope (:,:)= tsoil_phys_PEM_timeseries(:,:,islope,t)873 Tsurf_locslope (:) = tsurf_GCM_timeseries(:,islope,t)819 Tsoil_locslope = tsoil_phys_PEM_timeseries(:,:,islope,t) 820 Tsurf_locslope = tsurf_PCM_timeseries(:,islope,t) 874 821 call soil_pem_compute(ngrid,nsoilmx_PEM,.true.,TI_locslope,timestep/timelen,Tsurf_locslope,Tsoil_locslope) 875 822 call soil_pem_compute(ngrid,nsoilmx_PEM,.false.,TI_locslope,timestep/timelen,Tsurf_locslope,Tsoil_locslope) 876 tsoil_phys_PEM_timeseries(:,:,islope,t) = Tsoil_locslope (:,:)823 tsoil_phys_PEM_timeseries(:,:,islope,t) = Tsoil_locslope 877 824 do ig = 1,ngrid 878 825 do isoil = 1,nsoilmx_PEM … … 883 830 enddo 884 831 enddo 885 tsoil_PEM (:,:,:) = sum(tsoil_phys_PEM_timeseries(:,:,:,:),4)/timelen886 watersoil_density_PEM_ave (:,:,:) = sum(watersoil_density_PEM_timeseries(:,:,:,:),4)/timelen832 tsoil_PEM = sum(tsoil_phys_PEM_timeseries,4)/timelen 833 watersoil_density_PEM_ave = sum(watersoil_density_PEM_timeseries,4)/timelen 887 834 888 835 write(*,*) "Update of soil temperature done" … … 892 839 ! II_d.3 Update the ice table 893 840 write(*,*) "Compute ice table" 894 porefillingice_thickness_prev_iter (:,:) = porefillingice_thickness(:,:)841 porefillingice_thickness_prev_iter = porefillingice_thickness 895 842 call computeice_table_equilibrium(ngrid,nslope,nsoilmx_PEM,watercaptag,watersurf_density_ave,watersoil_density_PEM_ave,TI_PEM(:,1,:),porefillingice_depth,porefillingice_thickness) 896 843 call compute_massh2o_exchange_ssi(ngrid,nslope,nsoilmx_PEM,porefillingice_thickness_prev_iter,porefillingice_thickness,porefillingice_depth,tsoil_PEM,delta_h2o_icetablesublim) ! Mass of H2O exchange between the ssi and the atmosphere 897 844 898 845 ! II_d.4 Update the soil thermal properties 899 write(*,*) "Update soil propreties" 900 call update_soil_thermalproperties(ngrid,nslope,nsoilmx_PEM,tendencies_h2o_ice,qsurf(:,igcm_h2o_ice,:),global_ave_press_new,porefillingice_depth,porefillingice_thickness,TI_PEM) 846 call update_soil_thermalproperties(ngrid,nslope,nsoilmx_PEM,tend_h2o_ice,h2o_ice,global_avg_press_new,porefillingice_depth,porefillingice_thickness,TI_PEM) 901 847 902 848 ! II_d.5 Update the mass of the regolith adsorbed 903 849 if (adsorption_pem) then 904 call regolith_adsorption(ngrid,nslope,nsoilmx_PEM,timelen,tend encies_h2o_ice,tendencies_co2_ice,&905 qsurf(:,igcm_h2o_ice,:),qsurf(:,igcm_co2,:),tsoil_PEM,TI_PEM,ps_timeseries, &906 q_co2_PEM_phys,q_h2o_PEM_phys,h2o_adsorbded_phys,delta_h2o_adsorbded,co2_adsorbded_phys,delta_co2_adsorbded)850 call regolith_adsorption(ngrid,nslope,nsoilmx_PEM,timelen,tend_h2o_ice,tend_co2_ice, & 851 h2o_ice,co2_ice,tsoil_PEM,TI_PEM,ps_timeseries,q_co2_PEM_phys,q_h2o_PEM_phys, & 852 h2o_adsorbded_phys,delta_h2o_adsorbded,co2_adsorbded_phys,delta_co2_adsorbded) 907 853 908 854 totmassco2_adsorbded = 0. … … 911 857 do islope =1, nslope 912 858 do l = 1,nsoilmx_PEM - 1 913 totmassco2_adsorbded = totmassco2_adsorbded + co2_adsorbded_phys(ig,l,islope)*(layer_PEM(l +1) - layer_PEM(l))* &859 totmassco2_adsorbded = totmassco2_adsorbded + co2_adsorbded_phys(ig,l,islope)*(layer_PEM(l + 1) - layer_PEM(l))* & 914 860 subslope_dist(ig,islope)/cos(pi*def_slope_mean(islope)/180.)*cell_area(ig) 915 totmassh2o_adsorbded = totmassh2o_adsorbded + h2o_adsorbded_phys(ig,l,islope)*(layer_PEM(l +1) - layer_PEM(l))* &861 totmassh2o_adsorbded = totmassh2o_adsorbded + h2o_adsorbded_phys(ig,l,islope)*(layer_PEM(l + 1) - layer_PEM(l))* & 916 862 subslope_dist(ig,islope)/cos(pi*def_slope_mean(islope)/180.)*cell_area(ig) 917 863 enddo … … 927 873 ! II_e Outputs 928 874 !------------------------ 929 call writediagpem(ngrid,'ps_ave','Global average pressure','Pa',0,(/global_av e_press_new/))875 call writediagpem(ngrid,'ps_ave','Global average pressure','Pa',0,(/global_avg_press_new/)) 930 876 do islope = 1,nslope 931 877 write(str2(1:2),'(i2.2)') islope 932 call writediagpem(ngrid,'h2o_ice_s _slope'//str2,'H2O ice','kg.m-2',2,qsurf(:,igcm_h2o_ice,islope))933 call writediagpem(ngrid,' tendencies_h2o_ice_slope'//str2,'H2O ice tend','kg.m-2.year-1',2,tendencies_h2o_ice(:,islope))934 call writediagpem(ngrid,'tend encies_co2_ice_slope'//str2,'CO2 ice tend','kg.m-2.year-1',2,tendencies_co2_ice(:,islope))935 call writediagpem(ngrid,' co2ice_slope'//str2,'CO2 ice','kg.m-2',2,qsurf(:,igcm_co2,islope))878 call writediagpem(ngrid,'h2o_ice_slope'//str2,'H2O ice','kg.m-2',2,h2o_ice(:,islope)) 879 call writediagpem(ngrid,'co2_ice_slope'//str2,'CO2 ice','kg.m-2',2,co2_ice(:,islope)) 880 call writediagpem(ngrid,'tend_h2o_ice_slope'//str2,'H2O ice tend','kg.m-2.year-1',2,tend_h2o_ice(:,islope)) 881 call writediagpem(ngrid,'tend_co2_ice_slope'//str2,'CO2 ice tend','kg.m-2.year-1',2,tend_co2_ice(:,islope)) 936 882 call writediagpem(ngrid,'Flow_co2ice_slope'//str2,'CO2 ice flow','Boolean',2,flag_co2flow(:,islope)) 937 883 call writediagpem(ngrid,'tsurf_slope'//str2,'tsurf','K',2,tsurf(:,islope)) … … 942 888 ! II_f Update the tendencies 943 889 !------------------------ 944 write(*,*) "Adaptation of the new co2 tendencies to the current pressure" 945 call recomp_tend_co2_slope(ngrid,nslope,timelen,tendencies_co2_ice,tendencies_co2_ice_ini,qsurf(:,igcm_co2,:),emis,vmr_co2_gcm,vmr_co2_pem_phys,ps_timeseries, & 946 global_ave_press_GCM,global_ave_press_new) 890 call recomp_tend_co2_slope(ngrid,nslope,timelen,tend_co2_ice,tend_co2_ice_ini,co2_ice,emis,vmr_co2_PCM,vmr_co2_PEM_phys,ps_timeseries, & 891 global_avg_press_PCM,global_avg_press_new) 947 892 948 893 !------------------------ … … 950 895 ! II_g Checking the stopping criterion 951 896 !------------------------ 952 call criterion_waterice_stop(cell_area,ini_surf_h2o,qsurf(:,igcm_h2o_ice,:),STOPPING_water,ngrid,initial_h2o_ice) 953 954 call criterion_co2_stop(cell_area,ini_surf_co2,qsurf(:,igcm_co2,:),STOPPING_co2,STOPPING_pressure,ngrid, & 955 initial_co2_ice_sublim,global_ave_press_GCM,global_ave_press_new,nslope) 897 call stopping_crit_h2o_ice(cell_area,h2o_surf_ini,h2o_ice,stopPEM,ngrid) 898 call stopping_crit_co2(cell_area,co2_surf_ini,co2_ice,stopPEM,ngrid,global_avg_press_PCM,global_avg_press_new,nslope) 956 899 957 900 year_iter = year_iter + dt_pem 958 901 i_myear = i_myear + dt_pem 959 902 960 write(*,*) "Checking all the stopping criteria..." 961 if (STOPPING_water) then 962 write(*,*) "STOPPING because surface of water ice sublimating is too low, see message above", STOPPING_water 963 criterion_stop = 1 964 endif 965 if (STOPPING_1_water) then 966 write(*,*) "STOPPING because tendencies on water ice=0, see message above", STOPPING_1_water 967 criterion_stop = 1 968 endif 969 if (STOPPING_co2) then 970 write(*,*) "STOPPING because surface of co2 ice sublimating is too low, see message above", STOPPING_co2 971 criterion_stop = 2 972 endif 973 if (STOPPING_pressure) then 974 write(*,*) "STOPPING because surface global pressure changed too much, see message above", STOPPING_pressure 975 criterion_stop = 3 976 endif 977 if (year_iter >= year_iter_max) then 978 write(*,*) "STOPPING because maximum number of iterations reached" 979 criterion_stop = 4 980 endif 981 if (i_myear >= n_myear) then 982 write(*,*) "STOPPING because maximum number of Martian years to be simulated reached" 983 criterion_stop = 5 984 endif 985 986 if (STOPPING_water .or. STOPPING_1_water .or. STOPPING_co2 .or. STOPPING_pressure) then 903 write(*,*) "Checking the stopping criteria..." 904 if (year_iter >= year_iter_max) stopPEM = 5 905 if (i_myear >= n_myear) stopPEM = 6 906 if (stopPEM > 0) then 907 select case (stopPEM) 908 case(1) 909 write(*,*) "STOPPING because surface of water ice sublimating is too low:", stopPEM, "See message above." 910 case(2) 911 write(*,*) "STOPPING because tendencies on water ice = 0:", stopPEM, "See message above." 912 case(3) 913 write(*,*) "STOPPING because surface of co2 ice sublimating is too low:", stopPEM, "See message above." 914 case(4) 915 write(*,*) "STOPPING because surface global pressure changed too much:", stopPEM, "See message above." 916 case(5) 917 write(*,*) "STOPPING because maximum number of iterations due to orbital parameters is reached:", stopPEM 918 case(6) 919 write(*,*) "STOPPING because maximum number of Martian years to be simulated is reached:", stopPEM 920 case default 921 write(*,*) "STOPPING with unknown stopping criterion code:", stopPEM 922 end select 987 923 exit 988 924 else … … 992 928 endif 993 929 994 global_av e_press_old = global_ave_press_new995 996 enddo 930 global_avg_press_old = global_avg_press_new 931 932 enddo ! big time iteration loop of the pem 997 933 !------------------------------ END RUN -------------------------------- 998 934 … … 1005 941 1006 942 ! H2O ice 943 watercap = 0. 1007 944 do ig = 1,ngrid 1008 if (watercaptag(ig)) then 1009 watercap_sum = 0. 1010 do islope = 1,nslope 1011 ! water_reservoir and watercap have not changed since PCM call: here we check if we have accumulate frost or not. 1012 if (qsurf(ig,igcm_h2o_ice,islope) > water_reservoir(ig)*cos(pi*def_slope_mean(islope)/180.)) then 1013 ! 1st case: more ice than initialy. Put back ancien frost 1014 qsurf(ig,igcm_h2o_ice,islope) = qsurf(ig,igcm_h2o_ice,islope) - water_reservoir(ig)*cos(pi*def_slope_mean(islope)/180.) 1015 else 1016 ! 2nd case: ice sublimated. Then let's put qsurf = 0 and add the difference in watercap 1017 watercap(ig,islope) = qsurf(ig,igcm_h2o_ice,islope) 1018 qsurf(ig,igcm_h2o_ice,islope) = 0. 1019 endif 1020 watercap_sum = watercap_sum + watercap(ig,islope)*subslope_dist(ig,islope)/cos(pi*def_slope_mean(islope)/180.) 1021 watercap(ig,islope) = 0. 1022 enddo 1023 water_reservoir(ig) = water_reservoir(ig) + watercap_sum 945 if (sum(h2o_ice(ig,:)*subslope_dist(ig,:)/cos(pi*def_slope_mean(:)/180.)) > inf_h2oice_threshold) then 946 ! If there is enough ice to be considered as an infinite reservoir 947 watercaptag(ig) = .true. 948 else 949 ! If there too little ice to be considered as an infinite reservoir 950 ! Ice is transferred to the frost 951 watercaptag(ig) = .false. 952 qsurf(ig,igcm_h2o_ice,:) = qsurf(ig,igcm_h2o_ice,:) + h2o_ice(ig,:) 953 h2o_ice(ig,:) = 0. 1024 954 endif 1025 955 enddo 1026 956 1027 do ig = 1,ngrid1028 water_sum = 0.1029 do islope = 1,nslope1030 water_sum = water_sum + qsurf(ig,igcm_h2o_ice,islope)*subslope_dist(ig,islope)/cos(pi*def_slope_mean(islope)/180.)1031 enddo1032 if (.not. watercaptag(ig)) then ! let's check if we have an 'infinite' source of water that has been forming.1033 if (water_sum > threshold_h2o_frost2perennial) then ! the overall mesh can be considered as an infite source of water. No need to change the albedo: done in II.d.11034 watercaptag(ig) = .true.1035 water_reservoir(ig) = water_reservoir(ig) + threshold_h2o_frost2perennial/2. ! half of the excess ices goes to the reservoir, we let the rest to be frost1036 do islope = 1,nslope1037 qsurf(ig,igcm_h2o_ice,islope) = qsurf(ig,igcm_h2o_ice,islope) - threshold_h2o_frost2perennial/2.*cos(pi*def_slope_mean(islope)/180.)1038 enddo1039 endif1040 else ! let's check that the infinite source of water disapear1041 if ((water_sum + water_reservoir(ig)) < threshold_h2o_frost2perennial) then1042 watercaptag(ig) = .false.1043 do islope = 1,nslope1044 qsurf(ig,igcm_h2o_ice,islope) = qsurf(ig,igcm_h2o_ice,islope) + water_reservoir(ig)*cos(pi*def_slope_mean(islope)/180.)1045 enddo1046 water_reservoir(ig) = 0.1047 endif1048 endif1049 enddo1050 1051 ! CO2 ice1052 do ig = 1,ngrid1053 do islope = 1,nslope1054 if (qsurf(ig,igcm_co2,islope) == threshold_co2_frost2perennial) then1055 ! If co2 ice is equal to the threshold, then everything is transformed into perennial ice1056 perennial_co2ice(ig,islope) = threshold_co2_frost2perennial1057 qsurf(ig,igcm_co2,islope) = 0.1058 else if (qsurf(ig,igcm_co2,islope) > threshold_co2_frost2perennial) then1059 ! If co2 ice is superior to the threshold, then co2 frost is equal to the threshold (max possible value)1060 ! and the leftover is transformed into perennial ice1061 perennial_co2ice(ig,islope) = qsurf(ig,igcm_co2,islope) - threshold_co2_frost2perennial1062 qsurf(ig,igcm_co2,islope) = threshold_co2_frost2perennial1063 else1064 ! If co2 ice is inferior to the threshold, then we compare with the initial state1065 if (qsurf(ig,igcm_co2,islope) > perennial_co2ice_ini(ig,islope)) then1066 ! If co2 ice higher than the initial perennial ice, then the change is affected only to the frost1067 perennial_co2ice(ig,islope) = perennial_co2ice_ini(ig,islope)1068 qsurf(ig,igcm_co2,islope) = qsurf(ig,igcm_co2,islope) - perennial_co2ice_ini(ig,islope)1069 else1070 ! If co2 ice is lower than the initial perennial ice, then there is no frost anymore1071 perennial_co2ice(ig,islope) = qsurf(ig,igcm_co2,islope)1072 qsurf(ig,igcm_co2,islope) = 0.1073 endif1074 endif1075 enddo1076 enddo1077 1078 957 ! III_a.2 Tsoil update (for startfi) 1079 958 if (soil_pem) then 1080 call interpol ate_TIPEM_TIGCM(ngrid,nslope,nsoilmx_PEM,nsoilmx,TI_PEM,inertiesoil)1081 tsoil (:,:,:)= tsoil_phys_PEM_timeseries(:,1:nsoilmx,:,timelen)959 call interpol_TI_PEM2PCM(ngrid,nslope,nsoilmx_PEM,nsoilmx,TI_PEM,inertiesoil) 960 tsoil = tsoil_phys_PEM_timeseries(:,1:nsoilmx,:,timelen) 1082 961 endif 1083 962 1084 963 ! III_a.4 Pressure (for start) 1085 ps (:) = ps(:)*global_ave_press_new/global_ave_press_GCM1086 ps_start_ GCM(:) = ps_start_GCM(:)*global_ave_press_new/global_ave_press_GCM964 ps = ps*global_avg_press_new/global_avg_press_PCM 965 ps_start_PCM = ps_start_PCM*global_avg_press_new/global_avg_press_PCM 1087 966 1088 967 ! III_a.5 Tracer (for start) … … 1090 969 1091 970 do l = 1,nlayer + 1 1092 zplev_new(:,l) = ap(l) + bp(l)*ps_start_ GCM(:)971 zplev_new(:,l) = ap(l) + bp(l)*ps_start_PCM 1093 972 enddo 1094 973 … … 1097 976 do l = 1,llm - 1 1098 977 do ig = 1,ngrid 1099 q(ig,l,nnq) = q(ig,l,nnq)*(zplev_ gcm(ig,l) - zplev_gcm(ig,l + 1))/(zplev_new(ig,l) - zplev_new(ig,l + 1))978 q(ig,l,nnq) = q(ig,l,nnq)*(zplev_PCM(ig,l) - zplev_PCM(ig,l + 1))/(zplev_new(ig,l) - zplev_new(ig,l + 1)) 1100 979 enddo 1101 980 q(:,llm,nnq) = q(:,llm - 1,nnq) … … 1104 983 do l = 1,llm - 1 1105 984 do ig = 1,ngrid 1106 q(ig,l,nnq) = q(ig,l,nnq)*(zplev_ gcm(ig,l) - zplev_gcm(ig,l + 1))/(zplev_new(ig,l) - zplev_new(ig,l + 1)) &1107 + ((zplev_new(ig,l) - zplev_new(ig,l + 1)) - (zplev_ gcm(ig,l) - zplev_gcm(ig,l + 1)))/(zplev_new(ig,l) - zplev_new(ig,l + 1))985 q(ig,l,nnq) = q(ig,l,nnq)*(zplev_PCM(ig,l) - zplev_PCM(ig,l + 1))/(zplev_new(ig,l) - zplev_new(ig,l + 1)) & 986 + ((zplev_new(ig,l) - zplev_new(ig,l + 1)) - (zplev_PCM(ig,l) - zplev_PCM(ig,l + 1)))/(zplev_new(ig,l) - zplev_new(ig,l + 1)) 1108 987 enddo 1109 988 q(:,llm,nnq) = q(:,llm - 1,nnq) … … 1178 1057 call pemdem1("restartpem.nc",i_myear,nsoilmx_PEM,ngrid,nslope,tsoil_PEM, & 1179 1058 TI_PEM, porefillingice_depth,porefillingice_thickness, & 1180 co2_adsorbded_phys,h2o_adsorbded_phys, water_reservoir)1059 co2_adsorbded_phys,h2o_adsorbded_phys,h2o_ice) 1181 1060 write(*,*) "restartpem.nc has been written" 1182 call info_PEM(year_iter,criterion_stop,i_myear,n_myear) 1061 1062 call info_PEM(year_iter,stopPEM,i_myear,n_myear) 1183 1063 1184 1064 write(*,*) "The PEM has run for", year_iter, "Martian years." … … 1187 1067 write(*,*) "LL & RV & JBC: so far, so good!" 1188 1068 1189 deallocate(vmr_co2_ gcm,ps_timeseries,tsurf_GCM_timeseries,q_co2_PEM_phys,q_h2o_PEM_phys)1190 deallocate(co2_ice_ GCM,watersurf_density_ave,watersoil_density_timeseries,Tsurfave_before_saved)1069 deallocate(vmr_co2_PCM,ps_timeseries,tsurf_PCM_timeseries,q_co2_PEM_phys,q_h2o_PEM_phys) 1070 deallocate(co2_ice_PCM,watersurf_density_ave,watersoil_density_timeseries,Tsurfavg_before_saved) 1191 1071 deallocate(tsoil_phys_PEM_timeseries,watersoil_density_PEM_timeseries,watersoil_density_PEM_ave) 1192 deallocate(delta_co2_adsorbded,delta_h2o_adsorbded,vmr_co2_ pem_phys,delta_h2o_icetablesublim,porefillingice_thickness_prev_iter)1193 deallocate(co2 frost_ini,perennial_co2ice_ini)1072 deallocate(delta_co2_adsorbded,delta_h2o_adsorbded,vmr_co2_PEM_phys,delta_h2o_icetablesublim,porefillingice_thickness_prev_iter) 1073 deallocate(co2_ice_ini) 1194 1074 !----------------------------- END OUTPUT ------------------------------ 1195 1075 -
trunk/LMDZ.COMMON/libf/evolution/pemetat0.F90
r3143 r3149 7 7 !======================================================================= 8 8 9 SUBROUTINE pemetat0(filename,ngrid,nsoil_ GCM,nsoil_PEM,nslope,timelen,timestep,TI_PEM,tsoil_PEM,ice_table, ice_table_thickness,&10 tsurf_av e_yr1,tsurf_ave_yr2,q_co2,q_h2o,ps_inst,tsoil_inst,tend_h2oglaciers,tend_co2glaciers,co2ice,waterice,&11 global_av e_pressure,watersurf_ave,watersoil_ave, m_co2_regolith_phys,deltam_co2_regolith_phys,&12 m_h2o_regolith_phys,deltam_h2o_regolith_phys , water_reservoir)9 SUBROUTINE pemetat0(filename,ngrid,nsoil_PCM,nsoil_PEM,nslope,timelen,timestep,TI_PEM,tsoil_PEM,ice_table,ice_table_thickness, & 10 tsurf_avg_yr1,tsurf_avg_yr2,q_co2,q_h2o,ps_inst,tsoil_inst,tend_h2o_ice,tend_co2_ice,co2_ice,h2o_ice, & 11 global_avg_pressure,watersurf_avg,watersoil_avg,m_co2_regolith_phys,deltam_co2_regolith_phys, & 12 m_h2o_regolith_phys,deltam_h2o_regolith_phys) 13 13 14 14 use iostart_PEM, only: open_startphy, close_startphy, get_field, get_var 15 use comsoil_h_PEM, only: soil_pem, layer_PEM, mlayer_PEM, fluxgeo, inertiedat_PEM, water_reservoir_nom, depth_breccia, depth_bedrock, index_breccia, index_bedrock16 use comsoil_h, only: volcapa, inertiedat15 use comsoil_h_PEM, only: soil_pem, layer_PEM, mlayer_PEM, fluxgeo, inertiedat_PEM, ini_h2o_bigreservoir, depth_breccia, depth_bedrock, index_breccia, index_bedrock 16 use comsoil_h, only: volcapa, inertiedat 17 17 use adsorption_mod, only: regolith_adsorption, adsorption_pem 18 18 use ice_table_mod, only: computeice_table_equilibrium … … 26 26 #ifndef CPP_STD 27 27 use comcstfi_h, only: r, mugaz 28 use surfdat_h, only: watercaptag 28 use surfdat_h, only: watercaptag, perennial_co2ice 29 29 #else 30 30 use comcstfi_mod, only: r, mugaz … … 37 37 character(len=*), intent(in) :: filename ! name of the startfi_PEM.nc 38 38 integer, intent(in) :: ngrid ! # of physical grid points 39 integer, intent(in) :: nsoil_ GCM ! # of vertical grid points in the GCM39 integer, intent(in) :: nsoil_PCM ! # of vertical grid points in the PCM 40 40 integer, intent(in) :: nsoil_PEM ! # of vertical grid points in the PEM 41 41 integer, intent(in) :: nslope ! # of sub-grid slopes 42 42 integer, intent(in) :: timelen ! # time samples 43 43 real, intent(in) :: timestep ! time step [s] 44 real, intent(in) :: global_av e_pressure ! mean average pressure on the planet [Pa]45 real, dimension(ngrid,nslope), intent(in) :: tsurf_av e_yr1 ! surface temperature at the first year of GCM call [K]46 real, dimension(ngrid,nslope), intent(in) :: tsurf_av e_yr2 ! surface temperature at the second year of GCM call [K]44 real, intent(in) :: global_avg_pressure ! mean average pressure on the planet [Pa] 45 real, dimension(ngrid,nslope), intent(in) :: tsurf_avg_yr1 ! surface temperature at the first year of PCM call [K] 46 real, dimension(ngrid,nslope), intent(in) :: tsurf_avg_yr2 ! surface temperature at the second year of PCM call [K] 47 47 real, dimension(ngrid,timelen), intent(in) :: q_co2 ! MMR tracer co2 [kg/kg] 48 48 real, dimension(ngrid,timelen), intent(in) :: q_h2o ! MMR tracer h2o [kg/kg] 49 49 real, dimension(ngrid,timelen), intent(in) :: ps_inst ! surface pressure [Pa] 50 real, dimension(ngrid,nslope), intent(in) :: tend_h2oglaciers ! tendencies on h2o glaciers 51 real, dimension(ngrid,nslope), intent(in) :: tend_co2glaciers ! tendencies on co2 glaciers 52 real, dimension(ngrid,nslope), intent(in) :: co2ice ! co2 ice amount [kg/m^2] 53 real, dimension(ngrid,nslope), intent(in) :: waterice ! water ice amount [kg/m^2] 54 real, dimension(ngrid,nslope), intent(in) :: watersurf_ave ! surface water ice density, yearly averaged (kg/m^3) 50 real, dimension(ngrid,nslope), intent(in) :: tend_h2o_ice ! tendencies on h2o ice 51 real, dimension(ngrid,nslope), intent(in) :: tend_co2_ice ! tendencies on co2 ice 52 real, dimension(ngrid,nslope), intent(in) :: watersurf_avg ! surface water ice density, yearly averaged (kg/m^3) 55 53 ! outputs 56 54 real, dimension(ngrid), intent(out) :: deltam_co2_regolith_phys ! mass of co2 that is exchanged due to adsorption desorption [kg/m^2] 57 55 real, dimension(ngrid), intent(out) :: deltam_h2o_regolith_phys ! mass of h2o that is exchanged due to adsorption desorption [kg/m^2] 56 real, dimension(ngrid,nslope), intent(out) :: h2o_ice ! h2o ice amount [kg/m^2] 57 real, dimension(ngrid,nslope), intent(out) :: co2_ice ! co2 ice amount [kg/m^2] 58 58 real, dimension(ngrid,nsoil_PEM,nslope), intent(inout) :: TI_PEM ! soil (mid-layer) thermal inertia in the PEM grid [SI] 59 59 real, dimension(ngrid,nsoil_PEM,nslope), intent(inout) :: tsoil_PEM ! soil (mid-layer) temperature [K] … … 63 63 real, dimension(ngrid,nsoil_PEM,nslope), intent(inout) :: m_co2_regolith_phys ! mass of co2 adsorbed [kg/m^2] 64 64 real, dimension(ngrid,nsoil_PEM,nslope), intent(inout) :: m_h2o_regolith_phys ! mass of h2o adsorbed [kg/m^2] 65 real, dimension(ngrid), intent(inout) :: water_reservoir ! mass of h2o that is exchanged due to adsorption desorption [kg/m^2] 66 real, dimension(ngrid,nsoil_PEM,nslope), intent(inout) :: watersoil_ave ! surface water ice density, yearly averaged (kg/m^3) 65 real, dimension(ngrid,nsoil_PEM,nslope), intent(inout) :: watersoil_avg ! surface water ice density, yearly averaged (kg/m^3) 67 66 ! local 68 67 real, dimension(ngrid,nsoil_PEM,nslope) :: tsoil_startPEM ! soil temperature saved in the start [K] … … 75 74 character(2) :: num ! intermediate string to read PEM start sloped variables 76 75 real, dimension(ngrid,nsoil_PEM) :: tsoil_saved ! saved soil temperature [K] 77 real, dimension(ngrid,nsoil_PEM,nslope) :: tsoil_tmp_yr1 ! intermediate soil temperature during yr 1[K]76 real, dimension(ngrid,nsoil_PEM,nslope) :: tsoil_tmp_yr1 ! intermediate soil temperature during yr 1 [K] 78 77 real, dimension(ngrid,nsoil_PEM,nslope) :: tsoil_tmp_yr2 ! intermediate soil temperature during yr 2 [K] 79 78 real, dimension(ngrid,nsoil_PEM - 1) :: alph_tmp ! Intermediate for tsoil computation [] … … 82 81 83 82 #ifdef CPP_STD 84 logical, dimension(ngrid) :: watercaptag85 watercaptag(:) = .false.83 logical, dimension(ngrid) :: watercaptag 84 watercaptag(:) = .false. 86 85 #endif 87 86 … … 91 90 !!! 92 91 !!! Order: 0. Previous year of the PEM run 92 !!! Ice initialization 93 93 !!! 1. Thermal Inertia 94 94 !!! 2. Soil Temperature 95 95 !!! 3. Ice table 96 96 !!! 4. Mass of CO2 & H2O adsorbed 97 !!! 5. Water reservoir98 97 !!! 99 98 !!! /!\ This order must be respected ! … … 113 112 call open_startphy(filename) 114 113 114 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 115 #ifndef CPP_STD 116 ! h2o ice 117 h2o_ice = 0. 118 call get_field("h2o_ice",h2o_ice,found) 119 if (.not. found) then 120 write(*,*)'Pemetat0: failed loading <h2o_ice>' 121 write(*,*)'will reconstruct the values from watercaptag' 122 write(*,*)'with default value ''ini_h2o_bigreservoir''' 123 do ig = 1,ngrid 124 if (watercaptag(ig)) h2o_ice(ig,:) = ini_h2o_bigreservoir 125 enddo 126 endif 127 128 ! co2 ice 129 co2_ice = perennial_co2ice 130 #endif 131 115 132 if (soil_pem) then 116 133 134 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 117 135 !1. Thermal Inertia 118 136 ! a. General case 119 do islope = 1,nslope 120 write(num,'(i2.2)') islope 121 call get_field("TI_PEM_slope"//num,TI_startPEM(:,:,islope),found) 137 do islope = 1,nslope 138 write(num,'(i2.2)') islope 139 call get_field("TI_PEM_slope"//num,TI_startPEM(:,:,islope),found) 140 if (.not. found) then 141 write(*,*)'PEM settings: failed loading < TI_PEM_slope'//num//'>' 142 write(*,*)'will reconstruct the values of TI_PEM' 143 144 do ig = 1,ngrid 145 if (TI_PEM(ig,index_breccia,islope) < TI_breccia) then 146 !!! transition 147 delta = depth_breccia 148 TI_PEM(ig,index_breccia+1,islope) = sqrt((layer_PEM(index_breccia + 1) - layer_PEM(index_breccia))/ & 149 (((delta - layer_PEM(index_breccia))/(TI_PEM(ig,index_breccia,islope)**2)) + & 150 ((layer_PEM(index_breccia + 1) - delta)/(TI_breccia**2)))) 151 do iloop=index_breccia+2,index_bedrock 152 TI_PEM(ig,iloop,islope) = TI_breccia 153 enddo 154 else ! we keep the high ti values 155 do iloop = index_breccia + 1,index_bedrock 156 TI_PEM(ig,iloop,islope) = TI_PEM(ig,index_breccia,islope) 157 enddo 158 endif ! TI PEM and breccia comparison 159 !! transition 160 delta = depth_bedrock 161 TI_PEM(ig,index_bedrock + 1,islope) = sqrt((layer_PEM(index_bedrock + 1) - layer_PEM(index_bedrock))/ & 162 (((delta - layer_PEM(index_bedrock))/(TI_PEM(ig,index_bedrock,islope)**2)) + & 163 ((layer_PEM(index_bedrock + 1) - delta)/(TI_bedrock**2)))) 164 do iloop = index_bedrock + 2,nsoil_PEM 165 TI_PEM(ig,iloop,islope) = TI_bedrock 166 enddo 167 enddo 168 else ! found 169 do iloop = nsoil_PCM + 1,nsoil_PEM 170 TI_PEM(:,iloop,islope) = TI_startPEM(:,iloop,islope) ! ! 1st layers can change because of the presence of ice at the surface, so we don't change it here. 171 enddo 172 endif ! not found 173 enddo ! islope 174 175 write(*,*) 'PEMETAT0: THERMAL INERTIA done' 176 177 ! b. Special case for inertiedat, inertiedat_PEM 178 call get_field("inertiedat_PEM",inertiedat_PEM,found) 179 if (.not.found) then 180 do iloop = 1,nsoil_PCM 181 inertiedat_PEM(:,iloop) = inertiedat(:,iloop) 182 enddo 183 !!! zone de transition 184 delta = depth_breccia 185 do ig = 1,ngrid 186 if (inertiedat_PEM(ig,index_breccia).lt.TI_breccia) then 187 inertiedat_PEM(ig,index_breccia+1) = sqrt((layer_PEM(index_breccia+1)-layer_PEM(index_breccia))/ & 188 (((delta-layer_PEM(index_breccia))/(inertiedat(ig,index_breccia)**2))+ & 189 ((layer_PEM(index_breccia+1)-delta)/(TI_breccia**2)))) 190 191 do iloop = index_breccia+2,index_bedrock 192 inertiedat_PEM(ig,iloop) = TI_breccia 193 enddo 194 else 195 do iloop=index_breccia+1,index_bedrock 196 inertiedat_PEM(ig,iloop) = inertiedat_PEM(ig,nsoil_PCM) 197 enddo 198 endif ! comparison ti breccia 199 enddo ! ig 200 201 !!! zone de transition 202 delta = depth_bedrock 203 do ig = 1,ngrid 204 inertiedat_PEM(ig,index_bedrock+1) = sqrt((layer_PEM(index_bedrock+1)-layer_PEM(index_bedrock))/ & 205 (((delta-layer_PEM(index_bedrock))/(inertiedat_PEM(ig,index_bedrock)**2))+ & 206 ((layer_PEM(index_bedrock+1)-delta)/(TI_bedrock**2)))) 207 enddo 208 209 do iloop = index_bedrock + 2, nsoil_PEM 210 do ig = 1,ngrid 211 inertiedat_PEM(ig,iloop) = TI_bedrock 212 enddo 213 enddo 214 endif ! not found 215 216 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 217 !2. Soil Temperature 218 do islope=1,nslope 219 write(num,fmt='(i2.2)') islope 220 call get_field("tsoil_PEM_slope"//num,tsoil_startPEM(:,:,islope),found) 221 if (.not.found) then 222 write(*,*)'PEM settings: failed loading <tsoil_PEM_slope'//num//'>' 223 write(*,*)'will reconstruct the values of Tsoil' 224 ! do ig = 1,ngrid 225 ! kcond = (TI_PEM(ig,index_breccia+1,islope)*TI_PEM(ig,index_breccia+1,islope))/volcapa 226 ! tsoil_PEM(ig,index_breccia+1,islope) = tsoil_PEM(ig,index_breccia,islope) + fluxgeo/kcond*(mlayer_PEM(index_breccia)-mlayer_PEM(index_breccia-1)) 227 ! do iloop=index_breccia+2,index_bedrock 228 ! kcond = (TI_PEM(ig,iloop,islope)*TI_PEM(ig,iloop,islope))/volcapa 229 ! tsoil_PEM(ig,iloop,islope) = tsoil_PEM(ig,index_breccia+1,islope) + fluxgeo/kcond*(mlayer_PEM(iloop-1)-mlayer_PEM(index_breccia)) 230 ! enddo 231 ! kcond = (TI_PEM(ig,index_bedrock+1,islope)*TI_PEM(ig,index_bedrock+1,islope))/volcapa 232 ! tsoil_PEM(ig,index_bedrock+1,islope) = tsoil_PEM(ig,index_bedrock,islope) + fluxgeo/kcond*(mlayer_PEM(index_bedrock)-mlayer_PEM(index_bedrock-1)) 233 ! 234 ! do iloop=index_bedrock+2,nsoil_PEM 235 ! kcond = (TI_PEM(ig,iloop,islope)*TI_PEM(ig,iloop,islope))/volcapa 236 ! tsoil_PEM(ig,iloop,islope) = tsoil_PEM(ig,index_bedrock+1,islope) + fluxgeo/kcond*(mlayer_PEM(iloop-1)-mlayer_PEM(index_bedrock)) 237 ! enddo 238 ! enddo 239 call soil_pem_ini(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_avg_yr2(:,islope),tsoil_PEM(:,:,islope)) 240 call soil_pem_compute(ngrid,nsoil_PEM,.true.,TI_PEM(:,:,islope),timestep,tsurf_avg_yr2(:,islope),tsoil_PEM(:,:,islope)) 241 else 242 ! predictor corrector: restart from year 1 of the PCM and build the evolution of 243 ! tsoil at depth 244 tsoil_tmp_yr1(:,:,islope) = tsoil_startPEM(:,:,islope) 245 call soil_pem_compute(ngrid,nsoil_PEM,.true.,TI_PEM(:,:,islope),timestep,tsurf_avg_yr1(:,islope),tsoil_tmp_yr1(:,:,islope)) 246 call soil_pem_compute(ngrid,nsoil_PEM,.false.,TI_PEM(:,:,islope),timestep,tsurf_avg_yr1(:,islope),tsoil_tmp_yr1(:,:,islope)) 247 tsoil_tmp_yr2(:,:,islope) = tsoil_tmp_yr1(:,:,islope) 248 call soil_pem_compute(ngrid,nsoil_PEM,.true.,TI_PEM(:,:,islope),timestep,tsurf_avg_yr2(:,islope),tsoil_tmp_yr2(:,:,islope)) 249 250 do iloop = nsoil_PCM+1,nsoil_PEM 251 tsoil_PEM(:,iloop,islope) = tsoil_tmp_yr2(:,iloop,islope) 252 enddo 253 endif !found 254 255 do it = 1,timelen 256 do isoil = nsoil_PCM+1,nsoil_PEM 257 tsoil_inst(:,isoil,islope,it) = tsoil_PEM(:,isoil,islope) 258 enddo 259 enddo 260 do isoil = nsoil_PCM+1,nsoil_PEM 261 do ig = 1,ngrid 262 watersoil_avg(ig,isoil,islope) = exp(beta_clap_h2o/tsoil_PEM(ig,isoil,islope) + alpha_clap_h2o)/tsoil_PEM(ig,isoil,islope)*mmol(igcm_h2o_vap)/(mugaz*r) 263 enddo 264 enddo 265 enddo ! islope 266 write(*,*) 'PEMETAT0: SOIL TEMP done' 267 268 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 269 !3. Ice Table 270 call get_field("ice_table",ice_table,found) 122 271 if (.not. found) then 123 write(*,*)'PEM settings: failed loading <TI_PEM_slope'//num//'>' 124 write(*,*)'will reconstruct the values of TI_PEM' 125 272 write(*,*)'PEM settings: failed loading <ice_table>' 273 write(*,*)'will reconstruct the values of the ice table given the current state' 274 ice_table = -1 ! by default, no ice table 275 ice_table_thickness = -1 ! by default, no ice table 276 call computeice_table_equilibrium(ngrid,nslope,nsoil_PEM,watercaptag,watersurf_avg,watersoil_avg, TI_PEM(:,1,:),ice_table,ice_table_thickness) 277 call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM,tend_h2o_ice,h2o_ice,global_avg_pressure,ice_table,ice_table_thickness,TI_PEM) 278 do islope = 1,nslope 279 call soil_pem_ini(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_avg_yr2(:,islope),tsoil_PEM(:,:,islope)) 280 enddo 281 endif 282 283 write(*,*) 'PEMETAT0: ICE TABLE done' 284 285 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 286 !4. CO2 & H2O Adsorption 287 if (adsorption_pem) then 288 do islope = 1,nslope 289 write(num,fmt='(i2.2)') islope 290 call get_field("mco2_reg_ads_slope"//num,m_co2_regolith_phys(:,:,islope),found) 291 if (.not. found) then 292 m_co2_regolith_phys = 0. 293 exit 294 endif 295 enddo 296 do islope=1,nslope 297 write(num,fmt='(i2.2)') islope 298 call get_field("mh2o_reg_ads_slope"//num,m_h2o_regolith_phys(:,:,islope),found2) 299 if (.not. found2) then 300 m_h2o_regolith_phys = 0. 301 exit 302 endif 303 enddo 304 305 call regolith_adsorption(ngrid,nslope,nsoil_PEM,timelen,tend_h2o_ice,tend_co2_ice,h2o_ice,co2_ice,tsoil_PEM,TI_PEM,ps_inst,q_co2,q_h2o, & 306 m_h2o_regolith_phys,deltam_h2o_regolith_phys, m_co2_regolith_phys,deltam_co2_regolith_phys) 307 308 if (.not. found) deltam_co2_regolith_phys = 0. 309 if (.not.found2) deltam_h2o_regolith_phys = 0. 310 311 write(*,*) 'PEMETAT0: CO2 & H2O adsorption done' 312 endif ! adsorption_pem 313 endif ! soil_pem 314 315 call close_startphy 316 317 else !No startfi, let's build all by hand 318 319 ! h2o ice 320 h2o_ice = 0. 321 write(*,*)'There is no "startpem.nc" so ''h2o_ice'' is reconstructed from watercaptag with default value ''ini_h2o_bigreservoir''.' 322 do ig = 1,ngrid 323 if (watercaptag(ig)) h2o_ice(ig,:) = ini_h2o_bigreservoir 324 enddo 325 326 ! co2 ice 327 co2_ice = perennial_co2ice 328 329 if (soil_pem) then 330 331 !a) Thermal inertia 332 do islope = 1,nslope 126 333 do ig = 1,ngrid 127 334 if (TI_PEM(ig,index_breccia,islope) < TI_breccia) then 128 335 !!! transition 129 336 delta = depth_breccia 130 TI_PEM(ig,index_breccia +1,islope) = sqrt((layer_PEM(index_breccia + 1) -layer_PEM(index_breccia))/ &131 (((delta - layer_PEM(index_breccia))/(TI_PEM(ig,index_breccia,islope)**2))+ &132 ((layer_PEM(index_breccia + 1) -delta)/(TI_breccia**2))))133 do iloop=index_breccia +2,index_bedrock337 TI_PEM(ig,index_breccia + 1,islope) = sqrt((layer_PEM(index_breccia+1)-layer_PEM(index_breccia))/ & 338 (((delta-layer_PEM(index_breccia))/(TI_PEM(ig,index_breccia,islope)**2))+ & 339 ((layer_PEM(index_breccia+1)-delta)/(TI_breccia**2)))) 340 do iloop=index_breccia + 2,index_bedrock 134 341 TI_PEM(ig,iloop,islope) = TI_breccia 135 342 enddo 136 343 else ! we keep the high ti values 137 do iloop =index_breccia + 1,index_bedrock344 do iloop=index_breccia + 1,index_bedrock 138 345 TI_PEM(ig,iloop,islope) = TI_PEM(ig,index_breccia,islope) 139 346 enddo 140 endif ! TI PEM and breccia comparison347 endif 141 348 !! transition 142 349 delta = depth_bedrock 143 TI_PEM(ig,index_bedrock + 1,islope) = sqrt((layer_PEM(index_bedrock + 1) -layer_PEM(index_bedrock))/ &144 (((delta - layer_PEM(index_bedrock))/(TI_PEM(ig,index_bedrock,islope)**2))+ &145 ((layer_PEM(index_bedrock + 1) - delta)/(TI_bedrock**2))))350 TI_PEM(ig,index_bedrock + 1,islope) = sqrt((layer_PEM(index_bedrock+1)-layer_PEM(index_bedrock))/ & 351 (((delta-layer_PEM(index_bedrock))/(TI_PEM(ig,index_bedrock,islope)**2))+ & 352 ((layer_PEM(index_bedrock+1)-delta)/(TI_breccia**2)))) 146 353 do iloop = index_bedrock + 2,nsoil_PEM 147 354 TI_PEM(ig,iloop,islope) = TI_bedrock 148 355 enddo 149 356 enddo 150 else ! found 151 do iloop = nsoil_GCM + 1,nsoil_PEM 152 TI_PEM(:,iloop,islope) = TI_startPEM(:,iloop,islope) ! ! 1st layers can change because of the presence of ice at the surface, so we don't change it here. 153 enddo 154 endif ! not found 155 enddo ! islope 156 157 write(*,*) 'PEMETAT0: THERMAL INERTIA done' 158 159 ! b. Special case for inertiedat, inertiedat_PEM 160 call get_field("inertiedat_PEM",inertiedat_PEM,found) 161 if(.not.found) then 162 do iloop = 1,nsoil_GCM 163 inertiedat_PEM(:,iloop) = inertiedat(:,iloop) 164 enddo 165 !!! zone de transition 166 delta = depth_breccia 167 do ig = 1,ngrid 168 if(inertiedat_PEM(ig,index_breccia).lt.TI_breccia) then 169 inertiedat_PEM(ig,index_breccia+1) = sqrt((layer_PEM(index_breccia+1)-layer_PEM(index_breccia))/ & 170 (((delta-layer_PEM(index_breccia))/(inertiedat(ig,index_breccia)**2))+ & 171 ((layer_PEM(index_breccia+1)-delta)/(TI_breccia**2)))) 172 173 do iloop = index_breccia+2,index_bedrock 174 inertiedat_PEM(ig,iloop) = TI_breccia 175 enddo 176 177 else 178 do iloop=index_breccia+1,index_bedrock 179 inertiedat_PEM(ig,iloop) = inertiedat_PEM(ig,nsoil_GCM) 180 enddo 181 endif ! comparison ti breccia 182 enddo!ig 183 184 !!! zone de transition 185 delta = depth_bedrock 186 do ig = 1,ngrid 187 inertiedat_PEM(ig,index_bedrock+1) = sqrt((layer_PEM(index_bedrock+1)-layer_PEM(index_bedrock))/ & 188 (((delta-layer_PEM(index_bedrock))/(inertiedat_PEM(ig,index_bedrock)**2))+ & 189 ((layer_PEM(index_bedrock+1)-delta)/(TI_bedrock**2)))) 190 enddo 191 192 do iloop = index_bedrock+2, nsoil_PEM 193 do ig = 1,ngrid 194 inertiedat_PEM(ig,iloop) = TI_bedrock 195 enddo 196 enddo 197 endif ! not found 198 199 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 200 !2. Soil Temperature 201 do islope=1,nslope 202 write(num,fmt='(i2.2)') islope 203 call get_field("tsoil_PEM_slope"//num,tsoil_startPEM(:,:,islope),found) 204 if(.not.found) then 205 write(*,*)'PEM settings: failed loading <tsoil_PEM_slope'//num//'>' 206 write(*,*)'will reconstruct the values of Tsoil' 207 ! do ig = 1,ngrid 208 ! kcond = (TI_PEM(ig,index_breccia+1,islope)*TI_PEM(ig,index_breccia+1,islope))/volcapa 209 ! tsoil_PEM(ig,index_breccia+1,islope) = tsoil_PEM(ig,index_breccia,islope) + fluxgeo/kcond*(mlayer_PEM(index_breccia)-mlayer_PEM(index_breccia-1)) 210 ! do iloop=index_breccia+2,index_bedrock 211 ! kcond = (TI_PEM(ig,iloop,islope)*TI_PEM(ig,iloop,islope))/volcapa 212 ! tsoil_PEM(ig,iloop,islope) = tsoil_PEM(ig,index_breccia+1,islope) + fluxgeo/kcond*(mlayer_PEM(iloop-1)-mlayer_PEM(index_breccia)) 213 ! enddo 214 ! kcond = (TI_PEM(ig,index_bedrock+1,islope)*TI_PEM(ig,index_bedrock+1,islope))/volcapa 215 ! tsoil_PEM(ig,index_bedrock+1,islope) = tsoil_PEM(ig,index_bedrock,islope) + fluxgeo/kcond*(mlayer_PEM(index_bedrock)-mlayer_PEM(index_bedrock-1)) 357 enddo 358 359 do iloop = 1,nsoil_PCM 360 inertiedat_PEM(:,iloop) = inertiedat(:,iloop) 361 enddo 362 !!! zone de transition 363 delta = depth_breccia 364 do ig = 1,ngrid 365 if (inertiedat_PEM(ig,index_breccia) < TI_breccia) then 366 inertiedat_PEM(ig,index_breccia + 1) = sqrt((layer_PEM(index_breccia + 1) - layer_PEM(index_breccia))/ & 367 (((delta - layer_PEM(index_breccia))/(inertiedat(ig,index_breccia)**2)) + & 368 ((layer_PEM(index_breccia + 1)-delta)/(TI_breccia**2)))) 369 do iloop = index_breccia + 2,index_bedrock 370 inertiedat_PEM(ig,iloop) = TI_breccia 371 enddo 372 else 373 do iloop = index_breccia + 1,index_bedrock 374 inertiedat_PEM(ig,iloop) = inertiedat_PEM(ig,index_breccia) 375 enddo 376 endif 377 enddo 378 379 !!! zone de transition 380 delta = depth_bedrock 381 do ig = 1,ngrid 382 inertiedat_PEM(ig,index_bedrock + 1) = sqrt((layer_PEM(index_bedrock + 1) - layer_PEM(index_bedrock))/ & 383 (((delta - layer_PEM(index_bedrock))/(inertiedat_PEM(ig,index_bedrock)**2)) + & 384 ((layer_PEM(index_bedrock + 1) - delta)/(TI_bedrock**2)))) 385 enddo 386 387 do iloop = index_bedrock + 2,nsoil_PEM 388 do ig = 1,ngrid 389 inertiedat_PEM(ig,iloop) = TI_bedrock 390 enddo 391 enddo 392 393 write(*,*) 'PEMETAT0: TI done' 394 395 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 396 !b) Soil temperature 397 do islope = 1,nslope 398 ! do ig = 1,ngrid 399 ! kcond = (TI_PEM(ig,index_breccia+1,islope)*TI_PEM(ig,index_breccia+1,islope))/volcapa 400 ! tsoil_PEM(ig,index_breccia+1,islope) = tsoil_PEM(ig,index_breccia,islope) + fluxgeo/kcond*(mlayer_PEM(index_breccia)-mlayer_PEM(index_breccia-1)) 216 401 ! 217 ! do iloop=index_bedrock+2,nsoil_PEM 218 ! kcond = (TI_PEM(ig,iloop,islope)*TI_PEM(ig,iloop,islope))/volcapa 219 ! tsoil_PEM(ig,iloop,islope) = tsoil_PEM(ig,index_bedrock+1,islope) + fluxgeo/kcond*(mlayer_PEM(iloop-1)-mlayer_PEM(index_bedrock)) 220 ! enddo 221 ! enddo 222 223 224 call soil_pem_ini(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_ave_yr2(:,islope),tsoil_PEM(:,:,islope)) 225 call soil_pem_compute(ngrid,nsoil_PEM,.true.,TI_PEM(:,:,islope),timestep,tsurf_ave_yr2(:,islope),tsoil_PEM(:,:,islope)) 226 227 228 else 229 ! predictor corrector: restart from year 1 of the GCM and build the evolution of 230 ! tsoil at depth 231 232 tsoil_tmp_yr1(:,:,islope) = tsoil_startPEM(:,:,islope) 233 call soil_pem_compute(ngrid,nsoil_PEM,.true.,TI_PEM(:,:,islope),timestep,tsurf_ave_yr1(:,islope),tsoil_tmp_yr1(:,:,islope)) 234 call soil_pem_compute(ngrid,nsoil_PEM,.false.,TI_PEM(:,:,islope),timestep,tsurf_ave_yr1(:,islope),tsoil_tmp_yr1(:,:,islope)) 235 tsoil_tmp_yr2(:,:,islope) = tsoil_tmp_yr1(:,:,islope) 236 call soil_pem_compute(ngrid,nsoil_PEM,.true.,TI_PEM(:,:,islope),timestep,tsurf_ave_yr2(:,islope),tsoil_tmp_yr2(:,:,islope)) 237 238 239 do iloop = nsoil_GCM+1,nsoil_PEM 240 tsoil_PEM(:,iloop,islope) = tsoil_tmp_yr2(:,iloop,islope) 241 enddo 242 endif !found 243 244 do it = 1,timelen 245 do isoil = nsoil_GCM+1,nsoil_PEM 246 tsoil_inst(:,isoil,islope,it) = tsoil_PEM(:,isoil,islope) 247 enddo 248 enddo 249 do isoil = nsoil_GCM+1,nsoil_PEM 250 do ig = 1,ngrid 251 watersoil_ave(ig,isoil,islope) = exp(beta_clap_h2o/tsoil_PEM(ig,isoil,islope) + alpha_clap_h2o)/tsoil_PEM(ig,isoil,islope)*mmol(igcm_h2o_vap)/(mugaz*r) 252 enddo 253 enddo 254 enddo ! islope 255 256 write(*,*) 'PEMETAT0: SOIL TEMP done' 257 258 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 259 !3. Ice Table 260 call get_field("ice_table",ice_table,found) 261 if(.not.found) then 262 write(*,*)'PEM settings: failed loading <ice_table>' 263 write(*,*)'will reconstruct the values of the ice table given the current state' 264 ice_table(:,:) = -1 ! by default, no ice table 265 ice_table_thickness(:,:) = -1 ! by default, no ice table 266 call computeice_table_equilibrium(ngrid,nslope,nsoil_PEM,watercaptag,watersurf_ave,watersoil_ave, TI_PEM(:,1,:),ice_table,ice_table_thickness) 267 call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM,tend_h2oglaciers,waterice,global_ave_pressure,ice_table,ice_table_thickness,TI_PEM) 268 do islope = 1,nslope 269 call soil_pem_ini(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_ave_yr2(:,islope),tsoil_PEM(:,:,islope)) 270 enddo 271 endif 272 273 write(*,*) 'PEMETAT0: ICE TABLE done' 274 275 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 276 !4. CO2 & H2O Adsorption 277 if(adsorption_pem) then 278 do islope=1,nslope 279 write(num,fmt='(i2.2)') islope 280 call get_field("mco2_reg_ads_slope"//num,m_co2_regolith_phys(:,:,islope),found) 281 if((.not.found)) then 282 m_co2_regolith_phys(:,:,:) = 0. 283 exit 284 endif 285 286 enddo 287 288 do islope=1,nslope 289 write(num,fmt='(i2.2)') islope 290 call get_field("mh2o_reg_ads_slope"//num,m_h2o_regolith_phys(:,:,islope),found2) 291 if((.not.found2)) then 292 m_h2o_regolith_phys(:,:,:) = 0. 293 exit 294 endif 295 296 enddo 297 298 call regolith_adsorption(ngrid,nslope,nsoil_PEM,timelen,tend_h2oglaciers,tend_co2glaciers,waterice,co2ice,tsoil_PEM,TI_PEM,ps_inst,q_co2,q_h2o, & 299 m_h2o_regolith_phys,deltam_h2o_regolith_phys, m_co2_regolith_phys,deltam_co2_regolith_phys) 300 301 if((.not.found)) then 302 deltam_co2_regolith_phys(:) = 0. 303 endif 304 if((.not.found2)) then 305 deltam_h2o_regolith_phys(:) = 0. 306 endif 307 write(*,*) 'PEMETAT0: CO2 & H2O adsorption done' 308 endif 309 endif ! soil_pem 310 311 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 312 !. 5 water reservoir 313 #ifndef CPP_STD 314 water_reservoir = 0. 315 call get_field("water_reservoir",water_reservoir,found) 316 if (.not. found) then 317 write(*,*)'Pemetat0: failed loading <water_reservoir>' 318 write(*,*)'will reconstruct the values from watercaptag' 319 where (watercaptag) water_reservoir = water_reservoir_nom 320 endif 321 #endif 322 323 call close_startphy 324 325 else !No startfi, let's build all by hand 326 327 if (soil_pem) then 328 329 !a) Thermal inertia 330 do islope = 1,nslope 331 do ig = 1,ngrid 332 333 if(TI_PEM(ig,index_breccia,islope).lt.TI_breccia) then 334 !!! transition 335 delta = depth_breccia 336 TI_PEM(ig,index_breccia+1,islope) =sqrt((layer_PEM(index_breccia+1)-layer_PEM(index_breccia))/ & 337 (((delta-layer_PEM(index_breccia))/(TI_PEM(ig,index_breccia,islope)**2))+ & 338 ((layer_PEM(index_breccia+1)-delta)/(TI_breccia**2)))) 339 340 do iloop=index_breccia+2,index_bedrock 341 TI_PEM(ig,iloop,islope) = TI_breccia 342 enddo 343 else ! we keep the high ti values 344 do iloop=index_breccia+1,index_bedrock 345 TI_PEM(ig,iloop,islope) = TI_PEM(ig,index_breccia,islope) 346 enddo 347 endif 348 349 !! transition 350 delta = depth_bedrock 351 TI_PEM(ig,index_bedrock+1,islope) = sqrt((layer_PEM(index_bedrock+1)-layer_PEM(index_bedrock))/ & 352 (((delta-layer_PEM(index_bedrock))/(TI_PEM(ig,index_bedrock,islope)**2))+ & 353 ((layer_PEM(index_bedrock+1)-delta)/(TI_breccia**2)))) 354 do iloop=index_bedrock+2,nsoil_PEM 355 TI_PEM(ig,iloop,islope) = TI_bedrock 356 enddo 357 enddo 358 enddo 359 360 do iloop = 1,nsoil_GCM 361 inertiedat_PEM(:,iloop) = inertiedat(:,iloop) 362 enddo 363 !!! zone de transition 364 delta = depth_breccia 365 do ig = 1,ngrid 366 if(inertiedat_PEM(ig,index_breccia).lt.TI_breccia) then 367 inertiedat_PEM(ig,index_breccia+1) = sqrt((layer_PEM(index_breccia+1)-layer_PEM(index_breccia))/ & 368 (((delta-layer_PEM(index_breccia))/(inertiedat(ig,index_breccia)**2))+ & 369 ((layer_PEM(index_breccia+1)-delta)/(TI_breccia**2)))) 370 371 372 do iloop = index_breccia+2,index_bedrock 373 374 inertiedat_PEM(ig,iloop) = TI_breccia 375 376 enddo 377 else 378 do iloop = index_breccia+1,index_bedrock 379 inertiedat_PEM(ig,iloop) = inertiedat_PEM(ig,index_breccia) 380 enddo 381 382 endif 383 enddo 384 385 !!! zone de transition 386 delta = depth_bedrock 387 do ig = 1,ngrid 388 inertiedat_PEM(ig,index_bedrock+1) = sqrt((layer_PEM(index_bedrock+1)-layer_PEM(index_bedrock))/ & 389 (((delta-layer_PEM(index_bedrock))/(inertiedat_PEM(ig,index_bedrock)**2))+ & 390 ((layer_PEM(index_bedrock+1)-delta)/(TI_bedrock**2)))) 391 enddo 392 393 394 395 do iloop = index_bedrock+2, nsoil_PEM 396 do ig = 1,ngrid 397 inertiedat_PEM(ig,iloop) = TI_bedrock 398 enddo 399 enddo 400 401 write(*,*) 'PEMETAT0: TI done' 402 403 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 404 !b) Soil temperature 405 do islope = 1,nslope 406 ! do ig = 1,ngrid 407 ! kcond = (TI_PEM(ig,index_breccia+1,islope)*TI_PEM(ig,index_breccia+1,islope))/volcapa 408 ! tsoil_PEM(ig,index_breccia+1,islope) = tsoil_PEM(ig,index_breccia,islope) + fluxgeo/kcond*(mlayer_PEM(index_breccia)-mlayer_PEM(index_breccia-1)) 402 ! do iloop=index_breccia+2,index_bedrock 403 ! kcond = (TI_PEM(ig,iloop,islope)*TI_PEM(ig,iloop,islope))/volcapa 404 ! tsoil_PEM(ig,iloop,islope) = tsoil_PEM(ig,index_breccia+1,islope) + fluxgeo/kcond*(mlayer_PEM(iloop-1)-mlayer_PEM(index_breccia)) 405 ! enddo 406 ! kcond = (TI_PEM(ig,index_bedrock+1,islope)*TI_PEM(ig,index_bedrock+1,islope))/volcapa 407 ! tsoil_PEM(ig,index_bedrock+1,islope) = tsoil_PEM(ig,index_bedrock,islope) + fluxgeo/kcond*(mlayer_PEM(index_bedrock)-mlayer_PEM(index_bedrock-1)) 409 408 ! 410 ! do iloop=index_breccia+2,index_bedrock 411 ! kcond = (TI_PEM(ig,iloop,islope)*TI_PEM(ig,iloop,islope))/volcapa 412 ! tsoil_PEM(ig,iloop,islope) = tsoil_PEM(ig,index_breccia+1,islope) + fluxgeo/kcond*(mlayer_PEM(iloop-1)-mlayer_PEM(index_breccia)) 413 ! enddo 414 ! kcond = (TI_PEM(ig,index_bedrock+1,islope)*TI_PEM(ig,index_bedrock+1,islope))/volcapa 415 ! tsoil_PEM(ig,index_bedrock+1,islope) = tsoil_PEM(ig,index_bedrock,islope) + fluxgeo/kcond*(mlayer_PEM(index_bedrock)-mlayer_PEM(index_bedrock-1)) 416 417 ! do iloop=index_bedrock+2,nsoil_PEM 418 ! kcond = (TI_PEM(ig,iloop,islope)*TI_PEM(ig,iloop,islope))/volcapa 419 ! tsoil_PEM(ig,iloop,islope) = tsoil_PEM(ig,index_bedrock+1,islope) + fluxgeo/kcond*(mlayer_PEM(iloop-1)-mlayer_PEM(index_bedrock)) 420 ! enddo 421 422 ! enddo 423 424 call soil_pem_ini(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_ave_yr2(:,islope),tsoil_PEM(:,:,islope)) 425 call soil_pem_compute(ngrid,nsoil_PEM,.true.,TI_PEM(:,:,islope),timestep,tsurf_ave_yr2(:,islope),tsoil_PEM(:,:,islope)) 426 427 ! First raw initialization 428 do it = 1,timelen 429 do isoil = nsoil_GCM+1,nsoil_PEM 430 tsoil_inst(:,isoil,islope,it) = tsoil_PEM(:,isoil,islope) 431 enddo 432 enddo 433 434 do it = 1,timelen 435 do isoil = nsoil_GCM+1,nsoil_PEM 436 call soil_pem_ini(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_ave_yr2(:,islope),tsoil_inst(:,:,islope,it)) 437 enddo 438 enddo 439 440 do isoil = nsoil_GCM+1,nsoil_PEM 441 do ig = 1,ngrid 442 watersoil_ave(ig,isoil,islope) = exp(beta_clap_h2o/tsoil_PEM(ig,isoil,islope) + alpha_clap_h2o)/tsoil_PEM(ig,isoil,islope)*mmol(igcm_h2o_vap)/(mugaz*r) 443 enddo 444 enddo 445 enddo !islope 446 write(*,*) 'PEMETAT0: TSOIL done' 409 ! do iloop=index_bedrock+2,nsoil_PEM 410 ! kcond = (TI_PEM(ig,iloop,islope)*TI_PEM(ig,iloop,islope))/volcapa 411 ! tsoil_PEM(ig,iloop,islope) = tsoil_PEM(ig,index_bedrock+1,islope) + fluxgeo/kcond*(mlayer_PEM(iloop-1)-mlayer_PEM(index_bedrock)) 412 ! enddo 413 ! enddo 414 call soil_pem_ini(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_avg_yr2(:,islope),tsoil_PEM(:,:,islope)) 415 call soil_pem_compute(ngrid,nsoil_PEM,.true.,TI_PEM(:,:,islope),timestep,tsurf_avg_yr2(:,islope),tsoil_PEM(:,:,islope)) 416 417 ! First raw initialization 418 do it = 1,timelen 419 do isoil = nsoil_PCM + 1,nsoil_PEM 420 tsoil_inst(:,isoil,islope,it) = tsoil_PEM(:,isoil,islope) 421 enddo 422 enddo 423 424 do it = 1,timelen 425 do isoil = nsoil_PCM + 1,nsoil_PEM 426 call soil_pem_ini(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_avg_yr2(:,islope),tsoil_inst(:,:,islope,it)) 427 enddo 428 enddo 429 430 do isoil = nsoil_PCM + 1,nsoil_PEM 431 do ig = 1,ngrid 432 watersoil_avg(ig,isoil,islope) = exp(beta_clap_h2o/tsoil_PEM(ig,isoil,islope) + alpha_clap_h2o)/tsoil_PEM(ig,isoil,islope)*mmol(igcm_h2o_vap)/(mugaz*r) 433 enddo 434 enddo 435 enddo !islope 436 write(*,*) 'PEMETAT0: TSOIL done' 447 437 448 438 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 449 439 !c) Ice table 450 ice_table(:,:)= -1. ! by default, no ice table451 ice_table_thickness(:,:)= -1.452 call computeice_table_equilibrium(ngrid,nslope,nsoil_PEM,watercaptag,watersurf_ave,watersoil_ave,TI_PEM(:,1,:),ice_table,ice_table_thickness)453 call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM,tend_h2oglaciers,waterice,global_ave_pressure,ice_table,ice_table_thickness,TI_PEM)454 do islope = 1,nslope455 call soil_pem_ini(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_ave_yr2(:,islope),tsoil_PEM(:,:,islope))456 enddo457 write(*,*) 'PEMETAT0: Ice table done'440 ice_table = -1. ! by default, no ice table 441 ice_table_thickness = -1. 442 call computeice_table_equilibrium(ngrid,nslope,nsoil_PEM,watercaptag,watersurf_avg,watersoil_avg,TI_PEM(:,1,:),ice_table,ice_table_thickness) 443 call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM,tend_h2o_ice,h2o_ice,global_avg_pressure,ice_table,ice_table_thickness,TI_PEM) 444 do islope = 1,nslope 445 call soil_pem_ini(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_avg_yr2(:,islope),tsoil_PEM(:,:,islope)) 446 enddo 447 write(*,*) 'PEMETAT0: Ice table done' 458 448 459 449 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 460 450 !d) Regolith adsorbed 461 if (adsorption_pem) then 462 m_co2_regolith_phys(:,:,:) = 0. 463 m_h2o_regolith_phys(:,:,:) = 0. 464 465 call regolith_adsorption(ngrid,nslope,nsoil_PEM,timelen,tend_h2oglaciers,tend_co2glaciers,waterice,co2ice,tsoil_PEM,TI_PEM,ps_inst,q_co2,q_h2o, & 466 m_h2o_regolith_phys,deltam_h2o_regolith_phys, m_co2_regolith_phys,deltam_co2_regolith_phys) 467 468 deltam_co2_regolith_phys(:) = 0. 469 deltam_h2o_regolith_phys(:) = 0. 470 endif 471 472 write(*,*) 'PEMETAT0: CO2 adsorption done' 473 endif !soil_pem 474 475 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 476 !. e) water reservoir 477 #ifndef CPP_STD 478 water_reservoir = 0. 479 where (watercaptag) water_reservoir = water_reservoir_nom 480 #endif 481 451 if (adsorption_pem) then 452 m_co2_regolith_phys = 0. 453 m_h2o_regolith_phys = 0. 454 call regolith_adsorption(ngrid,nslope,nsoil_PEM,timelen,tend_h2o_ice,tend_co2_ice,h2o_ice,co2_ice,tsoil_PEM,TI_PEM,ps_inst,q_co2,q_h2o, & 455 m_h2o_regolith_phys,deltam_h2o_regolith_phys, m_co2_regolith_phys,deltam_co2_regolith_phys) 456 deltam_co2_regolith_phys = 0. 457 deltam_h2o_regolith_phys = 0. 458 endif 459 460 write(*,*) 'PEMETAT0: CO2 adsorption done' 461 endif !soil_pem 482 462 endif ! of if (startphy_file) 483 463 … … 495 475 496 476 END MODULE pemetat0_mod 497 -
trunk/LMDZ.COMMON/libf/evolution/pemredem.F90
r3082 r3149 1 module pemredem 1 MODULE pemredem 2 2 3 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 3 4 !!! 4 !!! Purpose: Write specific netcdf restart for the PEM 5 !!! 6 !!! 7 !!! Author: LL, inspired by phyredem from the GCM5 !!! Purpose: Write specific netcdf restart for the PEM 6 !!! 7 !!! 8 !!! Author: LL, inspired by phyredem from the PCM 8 9 !!! 9 10 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! … … 11 12 implicit none 12 13 14 !======================================================================= 13 15 contains 16 !======================================================================= 14 17 15 subroutine pemdem0(filename,lonfi,latfi,cell_area,nsoil_PEM,ngrid,day_ini,time,nslope,def_slope,subslope_dist) 18 SUBROUTINE pemdem0(filename,lonfi,latfi,cell_area,nsoil_PEM,ngrid,day_ini,time,nslope,def_slope,subslope_dist) 19 16 20 ! create physics restart file and write time-independent variables 17 use comsoil_h_PEM, only: soil_pem,mlayer_PEM,fluxgeo,inertiedat_PEM 18 use iostart_PEM, only: open_restartphy, close_restartphy, put_var, put_field, length 19 use mod_grid_phy_lmdz, only: klon_glo 20 use time_phylmdz_mod, only: daysec 21 use comsoil_h_PEM, only: soil_pem,mlayer_PEM,fluxgeo,inertiedat_PEM 22 use iostart_PEM, only: open_restartphy, close_restartphy, put_var, put_field, length 23 use mod_grid_phy_lmdz, only: klon_glo 24 use time_phylmdz_mod, only: daysec 25 21 26 #ifndef CPP_STD 22 use planete_h, only: aphelie, emin_turb, lmixmin, obliquit, peri_day, periheli, year_day23 use comcstfi_h, only: g, mugaz, omeg, rad, rcp27 use planete_h, only: aphelie, emin_turb, lmixmin, obliquit, peri_day, periheli, year_day 28 use comcstfi_h, only: g, mugaz, omeg, rad, rcp 24 29 #else 25 use planete_mod, only: apoastr, emin_turb, lmixmin, obliquit, peri_day, periastr, year_day26 use comcstfi_mod, only: g, mugaz, omeg, rad, rcp30 use planete_mod, only: apoastr, emin_turb, lmixmin, obliquit, peri_day, periastr, year_day 31 use comcstfi_mod, only: g, mugaz, omeg, rad, rcp 27 32 #endif 28 33 29 implicit none 30 31 character(len=*), intent(in) :: filename 32 real, intent(in) :: lonfi(ngrid) 33 real, intent(in) :: latfi(ngrid) 34 integer, intent(in) :: nsoil_PEM 35 integer, intent(in) :: ngrid 36 real, intent(in) :: day_ini 37 real, intent(in) :: time 38 real, intent(in) :: cell_area(ngrid) !boundaries for bining of the slopes 39 integer, intent(in) :: nslope 40 real, intent(in) :: def_slope(nslope+1) !boundaries for bining of the slopes 41 real, intent(in) :: subslope_dist(ngrid,nslope) !undermesh statistics 42 43 ! Create physics start file 44 call open_restartphy(filename) 45 46 ! Write the mid-layer depths 47 call put_var("soildepth","Soil mid-layer depth",mlayer_PEM) 48 49 ! Write longitudes 50 call put_field("longitude","Longitudes of physics grid",lonfi) 51 52 ! Write latitudes 53 call put_field("latitude","Latitudes of physics grid",latfi) 54 55 ! Write mesh areas 56 call put_field("area","Mesh area",cell_area) 57 58 ! Multidimensionnal variables (nogcm undermesh slope statistics) 59 call put_var("def_slope","slope criterium stages",def_slope) 60 call put_field("subslope_dist","under mesh slope distribution",subslope_dist) 34 implicit none 61 35 36 character(*), intent(in) :: filename 37 integer, intent(in) :: nsoil_PEM, ngrid, nslope 38 real, dimension(ngrid), intent(in) :: lonfi, latfi 39 real, intent(in) :: day_ini, time 40 real, dimension(ngrid), intent(in) :: cell_area ! boundaries for bining of the slopes 41 real, dimension(ngrid + 1), intent(in) :: def_slope ! boundaries for bining of the slopes 42 real, dimension(ngrid,nslope), intent(in) :: subslope_dist ! undermesh statistics 62 43 63 ! Close file 64 call close_restartphy 65 66 end subroutine pemdem0 44 ! Create physics start file 45 call open_restartphy(filename) 67 46 68 subroutine pemdem1(filename,i_myear,nsoil_PEM,ngrid,nslope, & 69 tsoil_slope_PEM,inertiesoil_slope_PEM,ice_table_depth,ice_table_thickness, & 70 m_co2_regolith,m_h2o_regolith,water_reservoir) 47 ! Write the mid-layer depths 48 call put_var("soildepth","Soil mid-layer depth",mlayer_PEM) 71 49 50 ! Write longitudes 51 call put_field("longitude","Longitudes of physics grid",lonfi) 72 52 73 ! write time-dependent variable to restart file 74 use iostart_PEM, only: open_restartphy, close_restartphy, put_var, put_field 75 use comsoil_h_PEM, only: mlayer_PEM,fluxgeo, inertiedat_PEM,soil_pem 76 use time_evol_mod, only: year_bp_ini, convert_years 77 78 implicit none 79 53 ! Write latitudes 54 call put_field("latitude","Latitudes of physics grid",latfi) 55 56 ! Write mesh areas 57 call put_field("area","Mesh area",cell_area) 58 59 ! Multidimensionnal variables (nopcm undermesh slope statistics) 60 call put_var("def_slope","slope criterium stages",def_slope) 61 call put_field("subslope_dist","under mesh slope distribution",subslope_dist) 62 63 ! Close file 64 call close_restartphy 65 66 END SUBROUTINE pemdem0 67 68 !======================================================================= 69 70 SUBROUTINE pemdem1(filename,i_myear,nsoil_PEM,ngrid,nslope,tsoil_slope_PEM,inertiesoil_slope_PEM, & 71 ice_table_depth,ice_table_thickness,m_co2_regolith,m_h2o_regolith,h2o_ice) 72 73 ! write time-dependent variable to restart file 74 use iostart_PEM, only: open_restartphy, close_restartphy, put_var, put_field 75 use comsoil_h_PEM, only: mlayer_PEM,fluxgeo, inertiedat_PEM, soil_pem 76 use time_evol_mod, only: year_bp_ini, convert_years 77 78 implicit none 79 80 80 #ifndef CPP_STD 81 include "callkeys.h"81 include "callkeys.h" 82 82 #endif 83 84 character(len=*), intent(in) :: filename85 integer, intent(in) :: nsoil_PEM, ngrid, nslope, i_myear86 real, intent(in) :: tsoil_slope_PEM(ngrid,nsoil_PEM,nslope) !under mesh bining according to slope87 real, intent(in) :: inertiesoil_slope_PEM(ngrid,nsoil_PEM,nslope) !under mesh bining according to slope88 real, intent(in) :: ice_table_depth(ngrid,nslope) !under mesh bining according to slope89 real, intent(in) :: ice_table_thickness(ngrid,nslope) !under mesh bining according to slope90 real, intent(in) :: m_co2_regolith(ngrid,nsoil_PEM,nslope)91 real, intent(in) :: m_h2o_regolith(ngrid,nsoil_PEM,nslope)92 real, intent(in) :: water_reservoir(ngrid)93 83 94 integer :: islope 95 character*2 :: num 96 integer :: iq 97 character(len=30) :: txt ! To store some text 98 real :: Year ! Year of the simulation 84 character(*), intent(in) :: filename 85 integer, intent(in) :: nsoil_PEM, ngrid, nslope, i_myear 86 real, dimension(ngrid,nsoil_PEM,nslope), intent(in) :: tsoil_slope_PEM ! under mesh bining according to slope 87 real, dimension(ngrid,nsoil_PEM,nslope), intent(in) :: inertiesoil_slope_PEM ! under mesh bining according to slope 88 real, dimension(ngrid,nslope), intent(in) :: ice_table_depth ! under mesh bining according to slope 89 real, dimension(ngrid,nslope), intent(in) :: ice_table_thickness ! under mesh bining according to slope 90 real, dimension(ngrid,nsoil_PEM,nslope), intent(in) :: m_co2_regolith, m_h2o_regolith 91 real, dimension(ngrid,nslope), intent(in) :: h2o_ice 99 92 100 ! Open file 101 call open_restartphy(filename) 102 103 ! First variable to write must be "Time", in order to correctly 104 ! set time counter in file 105 Year = (year_bp_ini + i_myear)*convert_years 106 call put_var("Time","Year of simulation",Year) 107 call put_field('water_reservoir','water_reservoir',water_reservoir,Year) 93 integer :: islope 94 character(2) :: num 95 integer :: iq 96 character(30) :: txt ! To store some text 97 real :: Year ! Year of the simulation 108 98 109 if(soil_pem) then 110 99 ! Open file 100 call open_restartphy(filename) 101 102 ! First variable to write must be "Time", in order to correctly 103 ! set time counter in file 104 Year = (year_bp_ini + i_myear)*convert_years 105 call put_var("Time","Year of simulation",Year) 106 call put_field('h2o_ice','h2o_ice',h2o_ice,Year) 107 108 if (soil_pem) then 111 109 ! Multidimensionnal variables (undermesh slope statistics) 112 do islope = 1,nslope 113 write(num,fmt='(i2.2)') islope 114 call put_field("tsoil_PEM_slope"//num,"Soil temperature by slope type", & 115 tsoil_slope_PEM(:,:,islope),Year) 116 call put_field("TI_PEM_slope"//num,"Soil Thermal Inertia by slope type", & 117 inertiesoil_slope_PEM(:,:,islope),Year) 110 do islope = 1,nslope 111 write(num,fmt='(i2.2)') islope 112 call put_field("tsoil_PEM_slope"//num,"Soil temperature by slope type",tsoil_slope_PEM(:,:,islope),Year) 113 call put_field("TI_PEM_slope"//num,"Soil Thermal Inertia by slope type",inertiesoil_slope_PEM(:,:,islope),Year) 114 call put_field("mco2_reg_ads_slope"//num, "Mass of co2 adsorbded in the regolith",m_co2_regolith(:,:,islope),Year) 115 call put_field("mh2o_reg_ads_slope"//num, "Mass of h2o adsorbded in the regolith",m_h2o_regolith(:,:,islope),Year) 116 enddo 117 call put_field("ice_table_depth","Depth of ice table",ice_table_depth,Year) 118 call put_field("ice_table_thickness","Depth of ice table",ice_table_thickness,Year) 119 call put_field("inertiedat_PEM","Thermal inertie of PEM ",inertiedat_PEM,Year) 120 endif ! soil_pem 118 121 119 call put_field("mco2_reg_ads_slope"//num, "Mass of co2 adsorbded in the regolith", & 120 m_co2_regolith(:,:,islope),Year) 121 call put_field("mh2o_reg_ads_slope"//num, "Mass of h2o adsorbded in the regolith", & 122 m_h2o_regolith(:,:,islope),Year) 123 enddo 122 ! Close file 123 call close_restartphy 124 124 125 call put_field("ice_table_depth","Depth of ice table",ice_table_depth,Year) 125 END SUBROUTINE pemdem1 126 126 127 call put_field("ice_table_thickness","Depth of ice table",ice_table_thickness,Year) 128 129 call put_field("inertiedat_PEM","Thermal inertie of PEM ",inertiedat_PEM,Year) 130 131 endif !soil_pem 132 133 ! Close file 134 call close_restartphy 135 136 end subroutine pemdem1 137 138 end module pemredem 127 END MODULE pemredem -
trunk/LMDZ.COMMON/libf/evolution/read_data_PCM_mod.F90
r3143 r3149 15 15 !======================================================================= 16 16 17 SUBROUTINE read_data_PCM(filename,timelen,iim_input,jjm_input,ngrid,nslope,vmr_co2_ gcm_phys,ps_timeseries, &18 min_co2_ice,min_h2o_ice,tsurf_av e,tsoil_ave,tsurf_gcm,tsoil_gcm,q_co2,q_h2o,co2_ice_slope, &19 watersurf_density_av e,watersoil_density)17 SUBROUTINE read_data_PCM(filename,timelen,iim_input,jjm_input,ngrid,nslope,vmr_co2_PCM_phys,ps_timeseries, & 18 min_co2_ice,min_h2o_ice,tsurf_avg,tsoil_avg,tsurf_PCM,tsoil_PCM,q_co2,q_h2o,co2_ice_slope, & 19 watersurf_density_avg,watersoil_density) 20 20 use comsoil_h, only: nsoilmx 21 21 use comsoil_h_PEM, only: soil_pem … … 36 36 ! Arguments: 37 37 38 character( len =*), intent(in) :: filename ! File name39 integer, 40 integer 38 character(*), intent(in) :: filename ! File name 39 integer, intent(in) :: timelen ! number of times stored in the file 40 integer, intent(in) :: iim_input, jjm_input, ngrid, nslope ! number of points in the lat x lon dynamical grid, number of subgrid slopes 41 41 ! Ouputs 42 42 real, dimension(ngrid,nslope), intent(out) :: min_co2_ice ! Minimum of co2 ice per slope of the year [kg/m^2] 43 43 real, dimension(ngrid,nslope), intent(out) :: min_h2o_ice ! Minimum of h2o ice per slope of the year [kg/m^2] 44 real, dimension(ngrid,timelen), intent(out) :: vmr_co2_ gcm_phys ! Physics x Times co2 volume mixing ratio retrieve from the PCM [m^3/m^3]44 real, dimension(ngrid,timelen), intent(out) :: vmr_co2_PCM_phys ! Physics x Times co2 volume mixing ratio retrieve from the PCM [m^3/m^3] 45 45 real, dimension(ngrid,timelen), intent(out) :: ps_timeseries ! Surface Pressure [Pa] 46 46 real, dimension(ngrid,timelen), intent(out) :: q_co2 ! CO2 mass mixing ratio in the first layer [kg/m^3] 47 47 real, dimension(ngrid,timelen), intent(out) :: q_h2o ! H2O mass mixing ratio in the first layer [kg/m^3] 48 real, dimension(ngrid,nslope,timelen), intent(out) :: co2_ice_slope ! co2 ice amount per 48 real, dimension(ngrid,nslope,timelen), intent(out) :: co2_ice_slope ! co2 ice amount per slope of the year [kg/m^2] 49 49 !SOIL 50 real, dimension(ngrid,nslope), intent(out) :: tsurf_av e! Average surface temperature of the concatenated file [K]51 real, dimension(ngrid,nsoilmx,nslope), intent(out) :: tsoil_av e! Average soil temperature of the concatenated file [K]52 real, dimension(ngrid,nslope,timelen), intent(out) :: tsurf_ gcm! Surface temperature of the concatenated file, time series [K]53 real, dimension(ngrid,nsoilmx,nslope,timelen), intent(out) :: tsoil_ gcm! Soil temperature of the concatenated file, time series [K]54 real, dimension(ngrid,nslope), intent(out) :: watersurf_density_av e! Water density at the surface [kg/m^3]50 real, dimension(ngrid,nslope), intent(out) :: tsurf_avg ! Average surface temperature of the concatenated file [K] 51 real, dimension(ngrid,nsoilmx,nslope), intent(out) :: tsoil_avg ! Average soil temperature of the concatenated file [K] 52 real, dimension(ngrid,nslope,timelen), intent(out) :: tsurf_PCM ! Surface temperature of the concatenated file, time series [K] 53 real, dimension(ngrid,nsoilmx,nslope,timelen), intent(out) :: tsoil_PCM ! Soil temperature of the concatenated file, time series [K] 54 real, dimension(ngrid,nslope), intent(out) :: watersurf_density_avg ! Water density at the surface [kg/m^3] 55 55 real, dimension(ngrid,nsoilmx,nslope,timelen), intent(out) :: watersoil_density ! Water density in the soil layer, time series [kg/m^3] 56 56 !======================================================================= … … 67 67 real, dimension(iim_input + 1,jjm_input + 1,nslope,timelen) :: watercap 68 68 real, dimension(iim_input + 1,jjm_input + 1,nslope,timelen) :: perennial_co2ice 69 real, dimension(iim_input + 1,jjm_input + 1,timelen) :: vmr_co2_ gcm! CO2 volume mixing ratio in the first layer [mol/m^3]70 real, dimension(iim_input + 1,jjm_input + 1,timelen) :: ps_ GCM ! Surface Pressure [Pa]69 real, dimension(iim_input + 1,jjm_input + 1,timelen) :: vmr_co2_PCM ! CO2 volume mixing ratio in the first layer [mol/m^3] 70 real, dimension(iim_input + 1,jjm_input + 1,timelen) :: ps_PCM ! Surface Pressure [Pa] 71 71 real, dimension(iim_input + 1,jjm_input + 1,nslope) :: min_co2_ice_dyn 72 72 real, dimension(iim_input + 1,jjm_input + 1,nslope) :: min_h2o_ice_dyn 73 real, dimension(iim_input + 1,jjm_input + 1,nslope) :: tsurf_av e_dyn ! Average surface temperature of the concatenated file [K]74 real, dimension(iim_input + 1,jjm_input + 1,nsoilmx,nslope) :: tsoil_av e_dyn ! Average soil temperature of the concatenated file [K]75 real, dimension(iim_input + 1,jjm_input + 1,nslope,timelen) :: tsurf_ gcm_dyn ! Surface temperature of the concatenated file, time series [K]76 real, dimension(iim_input + 1,jjm_input + 1,nsoilmx,nslope,timelen) :: tsoil_ gcm_dyn ! Soil temperature of the concatenated file, time series [K]73 real, dimension(iim_input + 1,jjm_input + 1,nslope) :: tsurf_avg_dyn ! Average surface temperature of the concatenated file [K] 74 real, dimension(iim_input + 1,jjm_input + 1,nsoilmx,nslope) :: tsoil_avg_dyn ! Average soil temperature of the concatenated file [K] 75 real, dimension(iim_input + 1,jjm_input + 1,nslope,timelen) :: tsurf_PCM_dyn ! Surface temperature of the concatenated file, time series [K] 76 real, dimension(iim_input + 1,jjm_input + 1,nsoilmx,nslope,timelen) :: tsoil_PCM_dyn ! Soil temperature of the concatenated file, time series [K] 77 77 real, dimension(iim_input + 1,jjm_input + 1,timelen) :: q_co2_dyn ! CO2 mass mixing ratio in the first layer [kg/m^3] 78 78 real, dimension(iim_input + 1,jjm_input + 1,timelen) :: q_h2o_dyn ! H2O mass mixing ratio in the first layer [kg/m^3] 79 79 real, dimension(iim_input + 1,jjm_input + 1,nslope,timelen) :: co2_ice_slope_dyn ! co2 ice amount per slope of the year [kg/m^2] 80 80 real, dimension(iim_input + 1,jjm_input + 1,nslope,timelen) :: watersurf_density_dyn ! Water density at the surface, time series [kg/m^3] 81 real, dimension(iim_input + 1,jjm_input + 1,nslope) :: watersurf_density_dyn_av e! Water density at the surface, dynamic grid, yearly averaged [kg/m^3]81 real, dimension(iim_input + 1,jjm_input + 1,nslope) :: watersurf_density_dyn_avg ! Water density at the surface, dynamic grid, yearly averaged [kg/m^3] 82 82 real, dimension(iim_input + 1,jjm_input + 1,nsoilmx,nslope,timelen) :: watersoil_density_dyn ! Water density in the soil layer, time series [kg/m^3] 83 83 real, dimension(ngrid,nslope,timelen) :: watersurf_density ! Water density at the surface, physical grid, time series [kg/m^3] … … 88 88 89 89 ! Dowload the data from the file 90 call get_var3("ps",ps_ GCM)90 call get_var3("ps",ps_PCM) 91 91 write(*,*) "Data for surface pressure downloaded!" 92 92 … … 104 104 write(*,*) "Data for h2o_ice_s downloaded!" 105 105 106 call get_var3("tsurf",tsurf_ gcm_dyn(:,:,1,:))106 call get_var3("tsurf",tsurf_PCM_dyn(:,:,1,:)) 107 107 write(*,*) "Data for tsurf downloaded!" 108 108 … … 115 115 116 116 if (soil_pem) then 117 call get_var4("soiltemp",tsoil_ gcm_dyn(:,:,:,1,:))117 call get_var4("soiltemp",tsoil_PCM_dyn(:,:,:,1,:)) 118 118 write(*,*) "Data for soiltemp downloaded!" 119 119 … … 140 140 do islope = 1,nslope 141 141 write(num,'(i2.2)') islope 142 call get_var3("tsurf_slope"//num,tsurf_ gcm_dyn(:,:,islope,:))142 call get_var3("tsurf_slope"//num,tsurf_PCM_dyn(:,:,islope,:)) 143 143 enddo 144 144 write(*,*) "Data for tsurf downloaded!" … … 160 160 do islope = 1,nslope 161 161 write(num,'(i2.2)') islope 162 call get_var4("soiltemp_slope"//num,tsoil_ gcm_dyn(:,:,:,islope,:))162 call get_var4("soiltemp_slope"//num,tsoil_PCM_dyn(:,:,:,islope,:)) 163 163 enddo 164 164 write(*,*) "Data for soiltemp downloaded!" … … 182 182 write(*,*) "Computing the min of h2o_ice..." 183 183 where (h2o_ice_s_dyn < 0.) h2o_ice_s_dyn = 0. 184 min_h2o_ice_dyn (:,:,:)= minval(h2o_ice_s_dyn + watercap,4)184 min_h2o_ice_dyn = minval(h2o_ice_s_dyn + watercap,4) 185 185 write(*,*) "Computing the min of co2_ice..." 186 186 where (co2_ice_slope_dyn < 0.) co2_ice_slope_dyn = 0. 187 min_co2_ice_dyn (:,:,:)= minval(co2_ice_slope_dyn + perennial_co2ice,4)187 min_co2_ice_dyn = minval(co2_ice_slope_dyn + perennial_co2ice,4) 188 188 189 189 ! Compute averages over the year for each point 190 190 write(*,*) "Computing the average of tsurf..." 191 tsurf_av e_dyn(:,:,:) = sum(tsurf_gcm_dyn(:,:,:,:),4)/timelen191 tsurf_avg_dyn = sum(tsurf_PCM_dyn,4)/timelen 192 192 193 193 if (soil_pem) then 194 194 write(*,*) "Computing average of tsoil..." 195 tsoil_av e_dyn(:,:,:,:) = sum(tsoil_gcm_dyn(:,:,:,:,:),5)/timelen195 tsoil_avg_dyn = sum(tsoil_PCM_dyn,5)/timelen 196 196 write(*,*) "Computing average of waterdensity_surface..." 197 watersurf_density_dyn_av e(:,:,:) = sum(watersurf_density_dyn(:,:,:,:),4)/timelen197 watersurf_density_dyn_avg = sum(watersurf_density_dyn,4)/timelen 198 198 endif 199 199 … … 215 215 endif 216 216 mmean = 1/(A*q_co2_dyn(i,j,t) + B) 217 vmr_co2_ gcm(i,j,t) = q_co2_dyn(i,j,t)*mmean/m_co2217 vmr_co2_PCM(i,j,t) = q_co2_dyn(i,j,t)*mmean/m_co2 218 218 enddo 219 219 enddo … … 221 221 222 222 #ifndef CPP_1D 223 call gr_dyn_fi(timelen,iim_input + 1,jjm_input + 1,ngrid,vmr_co2_ gcm,vmr_co2_gcm_phys)224 call gr_dyn_fi(timelen,iim_input + 1,jjm_input + 1,ngrid,ps_ GCM,ps_timeseries)223 call gr_dyn_fi(timelen,iim_input + 1,jjm_input + 1,ngrid,vmr_co2_PCM,vmr_co2_PCM_phys) 224 call gr_dyn_fi(timelen,iim_input + 1,jjm_input + 1,ngrid,ps_PCM,ps_timeseries) 225 225 call gr_dyn_fi(timelen,iim_input + 1,jjm_input + 1,ngrid,q_co2_dyn,q_co2) 226 226 call gr_dyn_fi(timelen,iim_input + 1,jjm_input + 1,ngrid,q_h2o_dyn,q_h2o) … … 231 231 if (soil_pem) then 232 232 do l = 1,nsoilmx 233 call gr_dyn_fi(1,iim_input + 1,jjm_input + 1,ngrid,tsoil_av e_dyn(:,:,l,islope),tsoil_ave(:,l,islope))233 call gr_dyn_fi(1,iim_input + 1,jjm_input + 1,ngrid,tsoil_avg_dyn(:,:,l,islope),tsoil_avg(:,l,islope)) 234 234 do t = 1,timelen 235 call gr_dyn_fi(1,iim_input + 1,jjm_input + 1,ngrid,tsoil_ gcm_dyn(:,:,l,islope,t),tsoil_gcm(:,l,islope,t))235 call gr_dyn_fi(1,iim_input + 1,jjm_input + 1,ngrid,tsoil_PCM_dyn(:,:,l,islope,t),tsoil_PCM(:,l,islope,t)) 236 236 call gr_dyn_fi(1,iim_input + 1,jjm_input + 1,ngrid,watersoil_density_dyn(:,:,l,islope,t),watersoil_density(:,l,islope,t)) 237 237 enddo 238 238 enddo 239 call gr_dyn_fi(1,iim_input + 1,jjm_input + 1,ngrid,watersurf_density_dyn_av e(:,:,islope),watersurf_density_ave(:,islope))239 call gr_dyn_fi(1,iim_input + 1,jjm_input + 1,ngrid,watersurf_density_dyn_avg(:,:,islope),watersurf_density_avg(:,islope)) 240 240 endif ! soil_pem 241 241 do t = 1,timelen 242 call gr_dyn_fi(1,iim_input + 1,jjm_input + 1,ngrid,tsurf_ GCM_dyn(:,:,islope,t),tsurf_GCM(:,islope,t))242 call gr_dyn_fi(1,iim_input + 1,jjm_input + 1,ngrid,tsurf_PCM_dyn(:,:,islope,t),tsurf_PCM(:,islope,t)) 243 243 call gr_dyn_fi(1,iim_input + 1,jjm_input + 1,ngrid,co2_ice_slope_dyn(:,:,islope,t),co2_ice_slope(:,islope,t)) 244 244 enddo 245 245 enddo 246 246 247 call gr_dyn_fi(nslope,iim_input + 1,jjm_input + 1,ngrid,tsurf_av e_dyn,tsurf_ave)247 call gr_dyn_fi(nslope,iim_input + 1,jjm_input + 1,ngrid,tsurf_avg_dyn,tsurf_avg) 248 248 #else 249 vmr_co2_ gcm_phys(1,:) = vmr_co2_gcm(1,1,:)250 ps_timeseries(1,:) = ps_ GCM(1,1,:)249 vmr_co2_PCM_phys(1,:) = vmr_co2_PCM(1,1,:) 250 ps_timeseries(1,:) = ps_PCM(1,1,:) 251 251 q_co2(1,:) = q_co2_dyn(1,1,:) 252 252 q_h2o(1,:) = q_h2o_dyn(1,1,:) … … 254 254 min_h2o_ice(1,:) = min_h2o_ice_dyn(1,1,:) 255 255 if (soil_pem) then 256 tsoil_av e(1,:,:) = tsoil_ave_dyn(1,1,:,:)257 tsoil_ gcm(1,:,:,:) = tsoil_gcm_dyn(1,1,:,:,:)256 tsoil_avg(1,:,:) = tsoil_avg_dyn(1,1,:,:) 257 tsoil_PCM(1,:,:,:) = tsoil_PCM_dyn(1,1,:,:,:) 258 258 watersoil_density(1,:,:,:) = watersoil_density_dyn(1,1,:,:,:) 259 watersurf_density_av e(1,:) = watersurf_density_dyn_ave(1,1,:)259 watersurf_density_avg(1,:) = watersurf_density_dyn_avg(1,1,:) 260 260 endif ! soil_pem 261 tsurf_ GCM(1,:,:) = tsurf_GCM_dyn(1,1,:,:)261 tsurf_PCM(1,:,:) = tsurf_PCM_dyn(1,1,:,:) 262 262 co2_ice_slope(1,:,:) = co2_ice_slope_dyn(1,1,:,:) 263 tsurf_av e(1,:) = tsurf_ave_dyn(1,1,:)263 tsurf_avg(1,:) = tsurf_avg_dyn(1,1,:) 264 264 #endif 265 265 -
trunk/LMDZ.COMMON/libf/evolution/recomp_tend_co2_slope_mod.F90
r3130 r3149 8 8 9 9 SUBROUTINE recomp_tend_co2_slope(ngrid,nslope,timelen,tendencies_co2_ice_phys,tendencies_co2_ice_phys_ini,co2ice_slope,emissivity_slope, & 10 vmr_co2_ gcm,vmr_co2_pem,ps_GCM_2,global_ave_press_GCM,global_ave_press_new)10 vmr_co2_PCM,vmr_co2_pem,ps_PCM_2,global_avg_press_PCM,global_avg_press_new) 11 11 12 use constants_marspem_mod, only : alpha_clap_co2, beta_clap_co2, sigmaB, Lco2, sols_per_my, sec_per_sol12 use constants_marspem_mod, only : alpha_clap_co2, beta_clap_co2, sigmaB, Lco2, sols_per_my, sec_per_sol 13 13 14 14 implicit none … … 24 24 ! INPUT 25 25 integer, intent(in) :: timelen, ngrid, nslope 26 real, dimension(ngrid,timelen), intent(in) :: vmr_co2_ gcm! physical point field : Volume mixing ratio of co2 in the first layer26 real, dimension(ngrid,timelen), intent(in) :: vmr_co2_PCM ! physical point field : Volume mixing ratio of co2 in the first layer 27 27 real, dimension(ngrid,timelen), intent(in) :: vmr_co2_pem ! physical point field : Volume mixing ratio of co2 in the first layer 28 real, dimension(ngrid,timelen), intent(in) :: ps_ GCM_2 ! physical point field : Surface pressure in the GCM29 real, intent(in) :: global_av e_press_GCM ! global averaged pressure at previous timestep30 real, intent(in) :: global_av e_press_new ! global averaged pressure at current timestep28 real, dimension(ngrid,timelen), intent(in) :: ps_PCM_2 ! physical point field : Surface pressure in the PCM 29 real, intent(in) :: global_avg_press_PCM ! global averaged pressure at previous timestep 30 real, intent(in) :: global_avg_press_new ! global averaged pressure at current timestep 31 31 real, dimension(ngrid,nslope), intent(in) :: tendencies_co2_ice_phys_ini ! physical point field : Evolution of perennial ice over one year 32 real, dimension(ngrid,nslope), intent(in) :: co2ice_slope ! CO2 ice per mesh and sub-grid slope (kg/m^2)32 real, dimension(ngrid,nslope), intent(in) :: co2ice_slope ! CO2 ice per mesh and sub-grid slope (kg/m^2) 33 33 real, dimension(ngrid,nslope), intent(in) :: emissivity_slope ! Emissivity per mesh and sub-grid slope(1) 34 34 ! OUTPUT … … 40 40 real :: coef, ave 41 41 42 write(*,*) "Update of the CO2 tendency from the current pressure" 43 42 44 ! Evolution of the water ice for each physical point 43 45 do i = 1,ngrid … … 47 49 if (co2ice_slope(i,islope) > 1.e-4 .and. abs(tendencies_co2_ice_phys(i,islope)) > 1.e-5) then 48 50 do t=1,timelen 49 ave = ave + (beta_clap_co2/(alpha_clap_co2-log(vmr_co2_ gcm(i,t)*ps_GCM_2(i,t)/100.)))**4 &50 - (beta_clap_co2/(alpha_clap_co2-log(vmr_co2_pem(i,t)*ps_ GCM_2(i,t)*(global_ave_press_new/global_ave_press_GCM)/100.)))**451 ave = ave + (beta_clap_co2/(alpha_clap_co2-log(vmr_co2_PCM(i,t)*ps_PCM_2(i,t)/100.)))**4 & 52 - (beta_clap_co2/(alpha_clap_co2-log(vmr_co2_pem(i,t)*ps_PCM_2(i,t)*(global_avg_press_new/global_avg_press_PCM)/100.)))**4 51 53 enddo 52 54 endif -
trunk/LMDZ.COMMON/libf/evolution/soil_settings_PEM_mod.F90
r3123 r3149 7 7 !======================================================================= 8 8 9 SUBROUTINE soil_settings_PEM(ngrid,nslope,nsoil_PEM,nsoil_ GCM,TI_GCM,TI_PEM)9 SUBROUTINE soil_settings_PEM(ngrid,nslope,nsoil_PEM,nsoil_PCM,TI_PCM,TI_PEM) 10 10 11 11 ! use netcdf … … 39 39 integer, intent(in) :: nslope ! # of subslope wihtin the mesh 40 40 integer, intent(in) :: nsoil_PEM ! # of soil layers in the PEM 41 integer, intent(in) :: nsoil_ GCM ! # of soil layers in the GCM42 real, dimension(ngrid,nsoil_ GCM,nslope), intent(in) :: TI_GCM ! Thermal inertia in the GCM [SI]41 integer, intent(in) :: nsoil_PCM ! # of soil layers in the PCM 42 real, dimension(ngrid,nsoil_PCM,nslope), intent(in) :: TI_PCM ! Thermal inertia in the PCM [SI] 43 43 44 44 real, dimension(ngrid,nsoil_PEM,nslope), intent(inout) :: TI_PEM ! Thermal inertia in the PEM [SI] … … 57 57 lay1 = 2.e-4 58 58 alpha = 2 59 do iloop = 0,nsoil_ GCM - 159 do iloop = 0,nsoil_PCM - 1 60 60 mlayer_PEM(iloop) = lay1*(1+iloop**2.9*(1-exp(-real(iloop)/20.))) 61 61 enddo 62 62 63 63 do iloop = 0, nsoil_PEM-1 64 if(lay1*(alpha**(iloop-0.5)) > mlayer_PEM(nsoil_ GCM-1)) then64 if(lay1*(alpha**(iloop-0.5)) > mlayer_PEM(nsoil_PCM-1)) then 65 65 index_powerlaw = iloop 66 66 exit … … 68 68 enddo 69 69 70 do iloop = nsoil_ GCM, nsoil_PEM-171 mlayer_PEM(iloop) = lay1*(alpha**(index_powerlaw + (iloop-nsoil_ GCM)-0.5))70 do iloop = nsoil_PCM, nsoil_PEM-1 71 mlayer_PEM(iloop) = lay1*(alpha**(index_powerlaw + (iloop-nsoil_PCM)-0.5)) 72 72 enddo 73 73 … … 83 83 do ig = 1,ngrid 84 84 do islope = 1,nslope 85 do iloop = 1,nsoil_ GCM86 TI_PEM(ig,iloop,islope) = TI_ GCM(ig,iloop,islope)85 do iloop = 1,nsoil_PCM 86 TI_PEM(ig,iloop,islope) = TI_PCM(ig,iloop,islope) 87 87 enddo 88 if (nsoil_PEM > nsoil_ GCM) then89 do iloop = nsoil_ GCM + 1,nsoil_PEM90 TI_PEM(ig,iloop,islope) = TI_ GCM(ig,nsoil_GCM,islope)88 if (nsoil_PEM > nsoil_PCM) then 89 do iloop = nsoil_PCM + 1,nsoil_PEM 90 TI_PEM(ig,iloop,islope) = TI_PCM(ig,nsoil_PCM,islope) 91 91 enddo 92 92 endif -
trunk/LMDZ.COMMON/libf/evolution/soil_thermalproperties_mod.F90
r3130 r3149 89 89 REAL :: ice_bottom_depth 90 90 91 write(*,*) "Update soil propreties" 92 91 93 ! 1. Modification of the regolith thermal inertia. 92 93 94 95 94 do islope = 1,nslope 96 95 regolith_inertia(:,islope) = inertiedat_PEM(:,1) … … 112 111 113 112 ! 2. Build new Thermal Inertia 114 115 113 do islope=1,nslope 116 114 do ig = 1,ngrid -
trunk/LMDZ.COMMON/libf/evolution/stopping_crit_mod.F90
r3148 r3149 1 MODULE criterion_pem_stop_mod1 MODULE stopping_crit_mod 2 2 3 3 implicit none 4 4 5 ! ----------------------------------------------------------------------5 !======================================================================= 6 6 contains 7 ! ----------------------------------------------------------------------7 !======================================================================= 8 8 9 9 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! … … 14 14 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 15 15 16 SUBROUTINE criterion_waterice_stop(cell_area,ini_surf,qsurf,STOPPING,ngrid,initial_h2o_ice)16 SUBROUTINE stopping_crit_h2o_ice(cell_area,surf_ini,h2o_ice,stopPEM,ngrid) 17 17 18 18 use time_evol_mod, only: water_ice_criterion … … 23 23 !======================================================================= 24 24 ! 25 ! Routine that checks if the waterice criterion to stop the PEM is reached25 ! Routine to check if the h2o ice criterion to stop the PEM is reached 26 26 ! 27 27 !======================================================================= … … 30 30 ! ---------- 31 31 ! INPUT 32 integer, intent(in) :: ngrid ! # of physical grid points 33 real, dimension(ngrid), intent(in) :: cell_area ! Area of the cells 34 real, dimension(ngrid,nslope), intent(in) :: qsurf ! Actual density of water ice 35 real, intent(in) :: ini_surf ! Initial surface of h2o ice that was sublimating 36 real, dimension(ngrid,nslope), intent(in) :: initial_h2o_ice ! Grid point that initialy were covered by h2o_ice 32 integer, intent(in) :: ngrid ! # of physical grid points 33 real, dimension(ngrid), intent(in) :: cell_area ! Area of the cells 34 real, dimension(ngrid,nslope), intent(in) :: h2o_ice ! Actual density of water ice 35 real, intent(in) :: surf_ini ! Initial surface of h2o ice that was sublimating 37 36 ! OUTPUT 38 logical, intent(out) :: STOPPING ! Is the criterion reached? 37 integer, intent(inout) :: stopPEM ! Stopping criterion code 39 38 ! local: 40 39 ! ------ 41 integer :: i, islope 42 real :: present_surf ! Initial/Actual surface of waterice40 integer :: i, islope ! Loop 41 real :: surf_now ! Current surface of h2o ice 43 42 44 43 !======================================================================= 45 ! Initialisation to false46 STOPPING = .false.47 48 44 ! Computation of the present surface of h2o ice 49 present_surf= 0.45 surf_now = 0. 50 46 do i = 1,ngrid 51 47 do islope = 1,nslope 52 if ( initial_h2o_ice(i,islope) > 0.5 .and. qsurf(i,islope) > 0.) present_surf = present_surf+ cell_area(i)*subslope_dist(i,islope)48 if (h2o_ice(i,islope) > 0.) surf_now = surf_now + cell_area(i)*subslope_dist(i,islope) 53 49 enddo 54 50 enddo 55 51 56 52 ! Check of the criterion 57 if ( present_surf < ini_surf*(1. - water_ice_criterion)) then58 STOPPING = .true.59 write(*,*) "Reason of stopping: the surface of water ice sublimating reach the threshold"60 write(*,*) " present_surf < ini_surf*(1. - water_ice_criterion)", present_surf < ini_surf*(1. - water_ice_criterion)61 write(*,*) "Current surface of water ice sublimating =", present_surf62 write(*,*) "Initial surface of water ice sublimating =", ini_surf53 if (surf_now < surf_ini*(1. - water_ice_criterion)) then 54 stopPEM = 1 55 write(*,*) "Reason of stopping: the surface of water ice sublimating reaches the threshold" 56 write(*,*) "surf_now < surf_ini*(1. - water_ice_criterion)", surf_now < surf_ini*(1. - water_ice_criterion) 57 write(*,*) "Current surface of water ice sublimating =", surf_now 58 write(*,*) "Initial surface of water ice sublimating =", surf_ini 63 59 write(*,*) "Percentage of change accepted =", water_ice_criterion*100 64 endif 65 if (present_surf > ini_surf*(1. + water_ice_criterion)) then 66 STOPPING = .true. 67 write(*,*) "Reason of stopping: the surface of water ice sublimating reach the threshold" 68 write(*,*) "present_surf > ini_surf*(1. + water_ice_criterion)", present_surf > ini_surf*(1. + water_ice_criterion) 69 write(*,*) "Current surface of water ice sublimating =", present_surf 70 write(*,*) "Initial surface of water ice sublimating =", ini_surf 60 else if (surf_now > surf_ini*(1. + water_ice_criterion)) then 61 stopPEM = 1 62 write(*,*) "Reason of stopping: the surface of water ice sublimating reaches the threshold" 63 write(*,*) "surf_now > surf_ini*(1. + water_ice_criterion)", surf_now > surf_ini*(1. + water_ice_criterion) 64 write(*,*) "Current surface of water ice sublimating =", surf_now 65 write(*,*) "Initial surface of water ice sublimating =", surf_ini 71 66 write(*,*) "Percentage of change accepted =", water_ice_criterion*100 72 67 endif 73 68 74 if ( ini_surf < 1.e-5 .and. ini_surf > -1.e-5) STOPPING = .false.69 if (abs(surf_ini) < 1.e-5) stopPEM = 0 75 70 76 END SUBROUTINE criterion_waterice_stop71 END SUBROUTINE stopping_crit_h2o_ice 77 72 78 ! ----------------------------------------------------------------------73 !======================================================================= 79 74 80 SUBROUTINE criterion_co2_stop(cell_area,ini_surf,qsurf,STOPPING_ice,STOPPING_ps,ngrid,initial_co2_ice,global_ave_press_GCM,global_ave_press_new,nslope)75 SUBROUTINE stopping_crit_co2(cell_area,surf_ini,co2_ice,stopPEM,ngrid,global_avg_press_PCM,global_avg_press_new,nslope) 81 76 82 77 use time_evol_mod, only: co2_ice_criterion, ps_criterion … … 87 82 !======================================================================= 88 83 ! 89 ! Routine that checksif the co2 and pressure criteria to stop the PEM are reached84 ! Routine to check if the co2 and pressure criteria to stop the PEM are reached 90 85 ! 91 86 !======================================================================= … … 96 91 integer, intent(in) :: ngrid, nslope ! # of grid physical grid points 97 92 real, dimension(ngrid), intent(in) :: cell_area ! Area of the cells 98 real, dimension(ngrid,nslope), intent(in) :: qsurf ! Actual density of water ice 99 real, intent(in) :: ini_surf ! Initial surface of co2 ice that was sublimating 100 real, dimension(ngrid,nslope), intent(in) :: initial_co2_ice ! Grid point that initialy were covered by co2_ice 101 real, intent(in) :: global_ave_press_GCM ! Planet average pressure from the PCM start files 102 real, intent(in) :: global_ave_press_new ! Planet average pressure from the PEM computations 93 real, dimension(ngrid,nslope), intent(in) :: co2_ice ! Actual density of water ice 94 real, intent(in) :: surf_ini ! Initial surface of co2 ice that was sublimating 95 real, intent(in) :: global_avg_press_PCM ! Planet average pressure from the PCM start files 96 real, intent(in) :: global_avg_press_new ! Planet average pressure from the PEM computations 103 97 ! OUTPUT 104 logical, intent(out) :: STOPPING_ice ! Is the criterion for co2 ice reached? 105 logical, intent(out) :: STOPPING_ps ! Is the criterion for pressure reached? 98 integer, intent(inout) :: stopPEM ! Stopping criterion code 99 106 100 ! local: 107 101 ! ------ 108 integer :: i, islope 109 real :: present_surf ! Initial/Actual surface of waterice102 integer :: i, islope ! Loop 103 real :: surf_now ! Current surface of co2 ice 110 104 111 105 !======================================================================= 112 ! Initialisation to false113 STOPPING_ice = .false.114 STOPPING_ps = .false.115 116 106 ! Computation of the present surface of co2 ice 117 present_surf= 0.107 surf_now = 0. 118 108 do i = 1,ngrid 119 109 do islope = 1,nslope 120 if ( initial_co2_ice(i,islope) > 0.5 .and. qsurf(i,islope) > 0.) present_surf = present_surf+ cell_area(i)*subslope_dist(i,islope)110 if (co2_ice(i,islope) > 0.) surf_now = surf_now + cell_area(i)*subslope_dist(i,islope) 121 111 enddo 122 112 enddo 123 113 124 114 ! Check of the criterion 125 if ( present_surf < ini_surf*(1. - co2_ice_criterion)) then126 STOPPING_ice = .true.127 write(*,*) "Reason of stopping: the surface of co2 ice sublimating reache dthe threshold"128 write(*,*) " present_surf < ini_surf*(1. - co2_ice_criterion)", present_surf < ini_surf*(1. - co2_ice_criterion)129 write(*,*) "Current surface of co2 ice sublimating =", present_surf130 write(*,*) "Initial surface of co2 ice sublimating =", ini_surf115 if (surf_now < surf_ini*(1. - co2_ice_criterion)) then 116 stopPEM = 3 117 write(*,*) "Reason of stopping: the surface of co2 ice sublimating reaches the threshold" 118 write(*,*) "surf_now < surf_ini*(1. - co2_ice_criterion)", surf_now < surf_ini*(1. - co2_ice_criterion) 119 write(*,*) "Current surface of co2 ice sublimating =", surf_now 120 write(*,*) "Initial surface of co2 ice sublimating =", surf_ini 131 121 write(*,*) "Percentage of change accepted =", co2_ice_criterion*100. 132 endif 133 if (present_surf > ini_surf*(1. + co2_ice_criterion)) then 134 STOPPING_ice = .true. 135 write(*,*) "Reason of stopping: the surface of co2 ice sublimating reach the threshold" 136 write(*,*) "present_surf > ini_surf*(1. + co2_ice_criterion)", present_surf > ini_surf*(1. + co2_ice_criterion) 137 write(*,*) "Current surface of co2 ice sublimating =", present_surf 138 write(*,*) "Initial surface of co2 ice sublimating =", ini_surf 122 else if (surf_now > surf_ini*(1. + co2_ice_criterion)) then 123 stopPEM = 3 124 write(*,*) "Reason of stopping: the surface of co2 ice sublimating reaches the threshold" 125 write(*,*) "surf_now > surf_ini*(1. + co2_ice_criterion)", surf_now > surf_ini*(1. + co2_ice_criterion) 126 write(*,*) "Current surface of co2 ice sublimating =", surf_now 127 write(*,*) "Initial surface of co2 ice sublimating =", surf_ini 139 128 write(*,*) "Percentage of change accepted =", co2_ice_criterion*100. 140 129 endif 141 130 142 if (abs( ini_surf) < 1.e-5) STOPPING_ice= .false.131 if (abs(surf_ini) < 1.e-5) stopPEM = .false. 143 132 144 if (global_av e_press_new < global_ave_press_GCM*(1. - ps_criterion)) then145 STOPPING_ps = .true.146 write(*,*) "Reason of stopping: the global pressure reach the threshold"147 write(*,*) "global_av e_press_new < global_ave_press_GCM*(1. - ps_criterion)", global_ave_press_new < global_ave_press_GCM*(1. - ps_criterion)148 write(*,*) "Current global pressure =", global_av e_press_new149 write(*,*) "PCM global pressure =", global_av e_press_GCM133 if (global_avg_press_new < global_avg_press_PCM*(1. - ps_criterion)) then 134 stopPEM = 4 135 write(*,*) "Reason of stopping: the global pressure reaches the threshold" 136 write(*,*) "global_avg_press_new < global_avg_press_PCM*(1. - ps_criterion)", global_avg_press_new < global_avg_press_PCM*(1. - ps_criterion) 137 write(*,*) "Current global pressure =", global_avg_press_new 138 write(*,*) "PCM global pressure =", global_avg_press_PCM 150 139 write(*,*) "Percentage of change accepted =", ps_criterion*100. 151 endif 152 if (global_ave_press_new > global_ave_press_GCM*(1. + ps_criterion)) then 153 STOPPING_ps = .true. 154 write(*,*) "Reason of stopping: the global pressure reach the threshold" 155 write(*,*) "global_ave_press_new > global_ave_press_GCM*(1. + ps_criterion)", global_ave_press_new > global_ave_press_GCM*(1. + ps_criterion) 156 write(*,*) "Current global pressure =", global_ave_press_new 157 write(*,*) "PCM global pressure =", global_ave_press_GCM 140 else if (global_avg_press_new > global_avg_press_PCM*(1. + ps_criterion)) then 141 stopPEM = 4 142 write(*,*) "Reason of stopping: the global pressure reaches the threshold" 143 write(*,*) "global_avg_press_new > global_avg_press_PCM*(1. + ps_criterion)", global_avg_press_new > global_avg_press_PCM*(1. + ps_criterion) 144 write(*,*) "Current global pressure =", global_avg_press_new 145 write(*,*) "PCM global pressure =", global_avg_press_PCM 158 146 write(*,*) "Percentage of change accepted =", ps_criterion*100. 159 147 endif 160 148 161 END SUBROUTINE criterion_co2_stop149 END SUBROUTINE stopping_crit_co2 162 150 163 151 END MODULE -
trunk/LMDZ.COMMON/libf/evolution/time_evol_mod.F90
r3076 r3149 12 12 logical :: evol_orbit_pem ! True if we want to follow the orbital parameters of obl_ecc_lsp.asc, read in evol.def 13 13 logical :: var_obl ! True if we want the PEM to follow obl_ecc_lsp.asc parameters for obliquity 14 logical :: var_ecc ! True if we want the PEM to follow obl_ecc_lsp.asc parameters for e xcenticity14 logical :: var_ecc ! True if we want the PEM to follow obl_ecc_lsp.asc parameters for eccenticity 15 15 logical :: var_lsp ! True if we want the PEM to follow obl_ecc_lsp.asc parameters for ls perihelie 16 16
Note: See TracChangeset
for help on using the changeset viewer.