- Timestamp:
- Nov 7, 2024, 2:48:08 PM (2 weeks ago)
- Location:
- trunk/LMDZ.COMMON/libf/evolution
- Files:
-
- 21 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.COMMON/libf/evolution/NS_tridag.F90
r3493 r3498 27 27 enddo 28 28 ! return 29 END 29 END SUBROUTINE tridag 30 30 ! (C) Copr. 1986-92 Numerical Recipes Software 0(9p#31(+. -
trunk/LMDZ.COMMON/libf/evolution/adsorption_mod.F90
r3456 r3498 40 40 41 41 !======================================================================= 42 SUBROUTINE regolith_adsorption(ngrid,nslope,nsoil_PEM,timelen, tend_h2oglaciers,tend_co2glaciers,waterice,co2ice,tsoil_PEM,TI_PEM,ps,q_co2,q_h2o, &42 SUBROUTINE regolith_adsorption(ngrid,nslope,nsoil_PEM,timelen,d_h2oglaciers,d_co2glaciers,waterice,co2ice,tsoil_PEM,TI_PEM,ps,q_co2,q_h2o, & 43 43 m_h2o_completesoil,delta_mh2oreg, m_co2_completesoil,delta_mco2reg) 44 44 … … 47 47 ! Inputs 48 48 integer, intent(in) :: ngrid, nslope, nsoil_PEM, timelen ! size dimension: physics x subslope x soil x timeseries 49 real, dimension(ngrid,nslope), intent(in) :: tend_h2oglaciers, tend_co2glaciers ! tendancies on the glaciers [1]49 real, dimension(ngrid,nslope), intent(in) :: d_h2oglaciers, d_co2glaciers ! tendancies on the glaciers [1] 50 50 real, dimension(ngrid,nslope), intent(in) :: waterice ! water ice at the surface [kg/m^2] 51 51 real, dimension(ngrid,nslope), intent(in) :: co2ice ! co2 ice at the surface [kg/m^2] … … 66 66 ! ------------- 67 67 ! Compute H2O adsorption, then CO2 adsorption 68 call regolith_h2oadsorption(ngrid,nslope,nsoil_PEM,timelen, tend_h2oglaciers,tend_co2glaciers,waterice,co2ice,ps,q_co2,q_h2o,tsoil_PEM,TI_PEM, &68 call regolith_h2oadsorption(ngrid,nslope,nsoil_PEM,timelen,d_h2oglaciers,d_co2glaciers,waterice,co2ice,ps,q_co2,q_h2o,tsoil_PEM,TI_PEM, & 69 69 theta_h2o_adsorbded,m_h2o_completesoil,delta_mh2oreg) 70 call regolith_co2adsorption(ngrid,nslope,nsoil_PEM,timelen, tend_h2oglaciers,tend_co2glaciers,waterice,co2ice,ps,q_co2,q_h2o, &70 call regolith_co2adsorption(ngrid,nslope,nsoil_PEM,timelen,d_h2oglaciers,d_co2glaciers,waterice,co2ice,ps,q_co2,q_h2o, & 71 71 tsoil_PEM,TI_PEM,m_co2_completesoil,delta_mco2reg) 72 72 … … 74 74 75 75 !======================================================================= 76 SUBROUTINE regolith_h2oadsorption(ngrid,nslope,nsoil_PEM,timelen, tend_h2oglaciers,tend_co2glaciers,waterice,co2ice,ps,q_co2,q_h2o,tsoil_PEM,TI_PEM, &76 SUBROUTINE regolith_h2oadsorption(ngrid,nslope,nsoil_PEM,timelen,d_h2oglaciers,d_co2glaciers,waterice,co2ice,ps,q_co2,q_h2o,tsoil_PEM,TI_PEM, & 77 77 theta_h2o_adsorbded,m_h2o_completesoil,delta_mreg) 78 78 … … 100 100 ! Inputs 101 101 integer, intent(in) :: ngrid, nslope, nsoil_PEM,timelen ! Size dimension 102 real, dimension(ngrid,nslope), intent(in) :: tend_h2oglaciers, tend_co2glaciers ! Tendencies on the glaciers ()102 real, dimension(ngrid,nslope), intent(in) :: d_h2oglaciers, d_co2glaciers ! Tendencies on the glaciers () 103 103 real, dimension(ngrid,nslope), intent(in) :: waterice ! Water ice at the surface [kg/m^2] 104 104 real, dimension(ngrid,nslope), intent(in) :: co2ice ! CO2 ice at the surface [kg/m^2] … … 151 151 do ig = 1,ngrid 152 152 do islope = 1,nslope 153 if (abs( tend_h2oglaciers(ig,islope)) > 1.e-5 .and. abs(waterice(ig,islope)) > 0.) ispermanent_h2oglaciers(ig,islope) = .true.154 if (abs( tend_co2glaciers(ig,islope)) > 1.e-5 .and. abs(co2ice(ig,islope)) > 0.) ispermanent_co2glaciers(ig,islope) = .true.153 if (abs(d_h2oglaciers(ig,islope)) > 1.e-5 .and. abs(waterice(ig,islope)) > 0.) ispermanent_h2oglaciers(ig,islope) = .true. 154 if (abs(d_co2glaciers(ig,islope)) > 1.e-5 .and. abs(co2ice(ig,islope)) > 0.) ispermanent_co2glaciers(ig,islope) = .true. 155 155 enddo 156 156 enddo … … 224 224 !!! 225 225 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 226 SUBROUTINE regolith_co2adsorption(ngrid,nslope,nsoil_PEM,timelen, tend_h2oglaciers,tend_co2glaciers,waterice,co2ice,ps,q_co2,q_h2o,tsoil_PEM,TI_PEM,m_co2_completesoil,delta_mreg)226 SUBROUTINE regolith_co2adsorption(ngrid,nslope,nsoil_PEM,timelen,d_h2oglaciers,d_co2glaciers,waterice,co2ice,ps,q_co2,q_h2o,tsoil_PEM,TI_PEM,m_co2_completesoil,delta_mreg) 227 227 228 228 use comsoil_h_PEM, only: layer_PEM, index_breccia, index_breccia … … 244 244 real, dimension(ngrid,nsoil_PEM,nslope), intent(in) :: tsoil_PEM ! Mean Soil Temperature [K] 245 245 real, dimension(ngrid,nsoil_PEM,nslope), intent(in) :: TI_PEM ! Mean Thermal Inertia [USI] 246 real, dimension(ngrid,nslope), intent(in) :: tend_h2oglaciers, tend_co2glaciers ! Tendencies on the glaciers ()246 real, dimension(ngrid,nslope), intent(in) :: d_h2oglaciers, d_co2glaciers ! Tendencies on the glaciers () 247 247 real, dimension(ngrid,timelen), intent(in) :: q_co2, q_h2o ! Mass mixing ratio of co2 and h2o in the first layer (kg/kg) 248 248 real, dimension(ngrid,nslope), intent(in) :: waterice ! Water ice at the surface [kg/m^2] … … 292 292 do ig = 1,ngrid 293 293 do islope = 1,nslope 294 if (abs( tend_h2oglaciers(ig,islope)) > 1.e-5 .and. abs(waterice(ig,islope)) > 0.) ispermanent_h2oglaciers(ig,islope) = .true.295 if (abs( tend_co2glaciers(ig,islope)) > 1.e-5 .and. abs(co2ice(ig,islope)) > 0.) ispermanent_co2glaciers(ig,islope) = .true.294 if (abs(d_h2oglaciers(ig,islope)) > 1.e-5 .and. abs(waterice(ig,islope)) > 0.) ispermanent_h2oglaciers(ig,islope) = .true. 295 if (abs(d_co2glaciers(ig,islope)) > 1.e-5 .and. abs(co2ice(ig,islope)) > 0.) ispermanent_co2glaciers(ig,islope) = .true. 296 296 enddo 297 297 enddo … … 317 317 318 318 ! 1. Compute the fraction of the pores occupied by H2O 319 call regolith_h2oadsorption(ngrid,nslope,nsoil_PEM,timelen, tend_h2oglaciers,tend_co2glaciers,waterice,co2ice,ps,q_co2,q_h2o,tsoil_PEM,TI_PEM, &319 call regolith_h2oadsorption(ngrid,nslope,nsoil_PEM,timelen,d_h2oglaciers,d_co2glaciers,waterice,co2ice,ps,q_co2,q_h2o,tsoil_PEM,TI_PEM, & 320 320 theta_h2o_adsorbed, m_h2o_adsorbed,delta_mh2o) 321 321 -
trunk/LMDZ.COMMON/libf/evolution/changelog.txt
r3495 r3498 472 472 - The execution command line in the job scripts that should be modified by the user according to the set-up is now given as an argument at the beginning to be more identifiable and adaptable; 473 473 - Making the job scripts more robust to detect a successful end. 474 475 == 07/11/2024 == JBC 476 - Correction of the variable name for the ice table depth in "pemetat0.F90". So it is now got as intended from the "startpem.nc" file; 477 - Renaming of the tendencies in the PEM with the prefix 'd_' instead of 'tend_'; 478 - Modification of the PEM time step type from integer to real. As a consequence, all time variables are now of real type. This change adds the possibility to consider fractions of year as time step. -
trunk/LMDZ.COMMON/libf/evolution/compute_tend_mod.F90
r3367 r3498 7 7 !======================================================================= 8 8 9 SUBROUTINE compute_tend(ngrid,nslope,min_ice, tendencies_ice)9 SUBROUTINE compute_tend(ngrid,nslope,min_ice,d_ice) 10 10 11 11 implicit none … … 25 25 26 26 ! OUTPUT 27 real, dimension(ngrid,nslope), intent(out) :: tendencies_ice ! Difference between the minima = evolution of perennial ice27 real, dimension(ngrid,nslope), intent(out) :: d_ice ! Difference between the minima = evolution of perennial ice 28 28 !======================================================================= 29 29 ! We compute the difference 30 tendencies_ice = min_ice(:,:,2) - min_ice(:,:,1)30 d_ice = min_ice(:,:,2) - min_ice(:,:,1) 31 31 32 32 ! If the difference is too small, then there is no evolution 33 where (abs( tendencies_ice) < 1.e-10) tendencies_ice = 0.33 where (abs(d_ice) < 1.e-10) d_ice = 0. 34 34 35 35 ! If the minimum over the last year is 0, then we have no perennial ice 36 where (abs(min_ice(:,:,2)) < 1.e-10) tendencies_ice = 0.36 where (abs(min_ice(:,:,2)) < 1.e-10) d_ice = 0. 37 37 38 38 END SUBROUTINE compute_tend -
trunk/LMDZ.COMMON/libf/evolution/conf_pem.F90
r3490 r3498 23 23 #endif 24 24 25 use time_evol_mod, only: year_bp_ini, dt _pem, h2o_ice_crit, co2_ice_crit, ps_criterion, Max_iter_pem, &26 evol_orbit_pem, var_obl, var_ecc, var_lsp, convert_years, ecritpem25 use time_evol_mod, only: year_bp_ini, dt, h2o_ice_crit, co2_ice_crit, ps_criterion, Max_iter_pem, & 26 evol_orbit_pem, var_obl, var_ecc, var_lsp, convert_years, ecritpem 27 27 use comsoil_h_pem, only: soil_pem, fluxgeo, ini_huge_h2oice, depth_breccia, depth_bedrock, reg_thprop_dependp 28 28 use adsorption_mod, only: adsorption_pem … … 34 34 implicit none 35 35 36 integer, intent(out) :: i_myear, n_myears ! Current simulated Martian year and maximum number of Martian years to be simulated36 real, intent(out) :: i_myear, n_myears ! Current simulated Martian year and maximum number of Martian years to be simulated 37 37 38 38 character(20), parameter :: modname ='conf_pem' … … 64 64 year_bp_ini = 0. 65 65 call getin('year_earth_bp_ini',year_earth_bp_ini) 66 year_bp_ini = int(year_earth_bp_ini/convert_years)66 year_bp_ini = year_earth_bp_ini/convert_years 67 67 68 68 var_obl = .true. … … 91 91 call getin('ps_criterion',ps_criterion) 92 92 93 dt _pem = 194 call getin('dt _pem', dt_pem)93 dt = 1. 94 call getin('dt',dt) 95 95 96 96 !#---------- Subsurface parameters ----------# … … 128 128 call abort_physic(modname,"Ice table must be used when soil_pem = T",1) 129 129 endif 130 if (icetable_equilibrium .or. icetable_dynamic) then 131 write(*,*) 'Ice table is asked to be computed both by the equilibrium and dynamic method.' 132 write(*,*) 'The dynamic method is then chosen.' 133 endif 130 134 131 135 if ((.not. soil_pem) .and. adsorption_pem) then … … 144 148 endif 145 149 146 if (evol_orbit_pem .and. year_bp_ini == 0.) then147 write(*,*) 'You want to follow the file obl_ecc_lsp.asc for changing orbparameters,'150 if (evol_orbit_pem .and. abs(year_bp_ini) < 1.e-10) then 151 write(*,*) 'You want to follow the file "obl_ecc_lsp.asc" for changing orbital parameters,' 148 152 write(*,*) 'but you did not specify from which year to start.' 149 call abort_physic(modname,"evol_orbit_pem=.true. but year_bp_ini =0",1)153 call abort_physic(modname,"evol_orbit_pem=.true. but year_bp_ini = 0",1) 150 154 endif 151 155 -
trunk/LMDZ.COMMON/libf/evolution/deftank/README
r3495 r3498 7 7 (ii) nPCM_ini -> the number of initial PCM runs (at least 2); 8 8 (iii) nPCM -> the number of PCM runs between each PEM run (usually 2); 9 (iv) mode -> the launching mode (0 = "processing scripts"; any other values = "submitting jobs"). The former option is usually used to process the script on a local machine while the latter is used to submit jobs on supercomputer.9 (iv) mode -> the launching mode (0 = "processing scripts"; any other values = "submitting jobs"). The former option is usually used to process the script on a local machine while the latter is used to submit jobs on a supercomputer. 10 10 The script can take an argument: 11 11 - If there is no argument, then the script initiates a PEM simulation from scratch. -
trunk/LMDZ.COMMON/libf/evolution/deftank/launchPEM.sh
r3495 r3498 14 14 ############################################### 15 15 # Set the number of years to be simulated, either Martian or Earth years: 16 n_mars_years=100 17 #n_earth_years=300 16 n_mars_years=100. 17 #n_earth_years=300. 18 18 19 19 # Set the number of initial PCM runs (>= 2): … … 23 23 nPCM=2 24 24 25 # Set the launching mode (0 = "processing scripts"; any other values = "submitting jobs"). The former option is usually used to process the script on a local machine while the latter is used to submit jobs on supercomputer:25 # Set the launching mode (0 = "processing scripts"; any other values = "submitting jobs"). The former option is usually used to process the script on a local machine while the latter is used to submit jobs on a supercomputer: 26 26 mode=1 27 27 ######################################################################## -
trunk/LMDZ.COMMON/libf/evolution/deftank/lib_launchPEM.sh
r3495 r3498 52 52 53 53 if [ -v n_mars_years ] && [ ! -z "$n_mars_years" ]; then 54 if [ $n_mars_years -lt 1]; then54 if [ $n_mars_years -lt 0. ]; then 55 55 echo "Error: the value of 'n_mars_years' must be >0!" 56 56 errlaunch 57 57 fi 58 58 elif [ -v n_earth_years ] && [ ! -z "$n_earth_years" ]; then 59 if [ $n_earth_years -lt 1]; then59 if [ $n_earth_years -lt 0. ]; then 60 60 echo "Error: the value of 'n_earth_years' must be >0!" 61 61 errlaunch … … 132 132 echo "Number of years to be simulated: $n_myear Martian years." 133 133 elif [ -v n_earth_years ]; then 134 n_myear=$(echo " ($n_earth_years/$convert_years + 0.999999)/1" | bc) # Ceiling of n_earth_years/convert_years134 n_myear=$(echo "$n_earth_years/$convert_years" | bc -l) 135 135 echo "Number of years to be simulated: $n_earth_years Earth years = $n_myear Martian years." 136 136 fi … … 141 141 echo "This is a chained simulation for PEM and PCM runs in $dir on $machine by $user." 142 142 convertyears 143 i_myear=0 143 i_myear=0. 144 144 iPEM=1 145 145 iPCM=1 … … 176 176 errlaunch 177 177 fi 178 else # Mode: launching jobs178 else # Mode: submitting jobs 179 179 cp PCMrun.job PCMrun${iPCM}.job 180 180 sed -i -E "s/($name_job[^0-9]*[0-9]*[^0-9]*)[0-9]+$/\1${iPCM}/" PCMrun${iPCM}.job … … 187 187 fi 188 188 ((iPCM++)) 189 ((i_myear++))189 i_myear = $(echo "$i_myear + 1." | bc - l) 190 190 ((ii++)) 191 191 else … … 201 201 errlaunch 202 202 fi 203 else # Mode: launching jobs203 else # Mode: submitting jobs 204 204 cp PCMrun.job PCMrun${iPCM}.job 205 205 sed -i -E "s/($name_job[^0-9]*[0-9]*[^0-9]*)[0-9]+$/\1${iPCM}/" PCMrun${iPCM}.job … … 209 209 fi 210 210 ((iPCM++)) 211 ((i_myear++))211 i_myear = $(echo "$i_myear + 1." | bc - l) 212 212 else 213 213 endlaunch … … 226 226 errlaunch 227 227 fi 228 else # Mode: launching jobs228 else # Mode: submitting jobs 229 229 sed -i -E "s/($name_job[^0-9]*[0-9]*[^0-9]*)[0-9]+$/\1${iPEM}/" PEMrun.job 230 230 jobID=$(eval "$submit_job PEMrun.job") … … 255 255 errlaunch 256 256 fi 257 else # Mode: launching jobs257 else # Mode: submitting jobs 258 258 sed -i -E "s/($name_job[^0-9]*[0-9]*[^0-9]*)[0-9]+$/\1${iPEM}/" PEMrun.job 259 259 jobID=$(eval "$submit_dependjob=afterok:${jobID} PEMrun.job") -
trunk/LMDZ.COMMON/libf/evolution/deftank/run_PEM.def
r3339 r3498 39 39 # ps_criterion = 0.15 40 40 41 # Time step length of the PEM in Martian years? Default = 1 42 # dt _pem=141 # Time step length of the PEM in Martian years? Default = 1. 42 # dt=1 43 43 44 44 #---------- Subsurface parameters ----------# -
trunk/LMDZ.COMMON/libf/evolution/evol_ice_mod.F90
r3368 r3498 7 7 !======================================================================= 8 8 9 SUBROUTINE evol_co2_ice(ngrid,nslope,co2_ice, tend_co2_ice)9 SUBROUTINE evol_co2_ice(ngrid,nslope,co2_ice,d_co2ice) 10 10 11 use time_evol_mod, only: dt _pem11 use time_evol_mod, only: dt 12 12 13 13 implicit none … … 25 25 ! OUTPUT 26 26 real, dimension(ngrid,nslope), intent(inout) :: co2_ice ! Previous and actual density of CO2 ice 27 real, dimension(ngrid,nslope), intent(inout) :: tend_co2_ice ! Evolution of perennial ice over one year27 real, dimension(ngrid,nslope), intent(inout) :: d_co2ice ! Evolution of perennial ice over one year 28 28 29 29 ! local: … … 35 35 36 36 co2_ice_old = co2_ice 37 co2_ice = co2_ice + tend_co2_ice*dt_pem37 co2_ice = co2_ice + d_co2ice*dt 38 38 where (co2_ice < 0.) 39 39 co2_ice = 0. 40 tend_co2_ice = -co2_ice_old/dt_pem40 d_co2ice = -co2_ice_old/dt 41 41 end where 42 42 … … 45 45 !======================================================================= 46 46 47 SUBROUTINE evol_h2o_ice(ngrid,nslope,cell_area,delta_h2o_adsorbded,delta_h2o_icetablesublim,h2o_ice, tend_h2o_ice,stopPEM)47 SUBROUTINE evol_h2o_ice(ngrid,nslope,cell_area,delta_h2o_adsorbded,delta_h2o_icetablesublim,h2o_ice,d_h2oice,stopPEM) 48 48 49 use time_evol_mod, only: dt _pem49 use time_evol_mod, only: dt 50 50 use comslope_mod, only: subslope_dist, def_slope_mean 51 51 … … 73 73 ! OUTPUT 74 74 real, dimension(ngrid,nslope), intent(inout) :: h2o_ice ! Previous and actual density of h2o ice (kg/m^2) 75 real, dimension(ngrid,nslope), intent(inout) :: tend_h2o_ice ! Evolution of perennial ice over one year (kg/m^2/year)75 real, dimension(ngrid,nslope), intent(inout) :: d_h2oice ! Evolution of perennial ice over one year (kg/m^2/year) 76 76 integer, intent(inout) :: stopPEM ! Stopping criterion code 77 77 … … 80 80 integer :: i, islope ! Loop variables 81 81 real :: pos_tend, neg_tend, real_coefficient, negative_part ! Variable to conserve h2o 82 real, dimension(ngrid,nslope) :: new_tend encies! Tendencies computed in order to conserve h2o ice on the surface, only exchange between surface are done82 real, dimension(ngrid,nslope) :: new_tend ! Tendencies computed in order to conserve h2o ice on the surface, only exchange between surface are done 83 83 !======================================================================= 84 84 if (ngrid /= 1) then ! Not in 1D … … 99 99 do islope = 1,nslope 100 100 if (h2o_ice(i,islope) > 0.) then 101 if ( tend_h2o_ice(i,islope) > 0.) then102 pos_tend = pos_tend + tend_h2o_ice(i,islope)*cell_area(i)*subslope_dist(i,islope)/cos(def_slope_mean(islope)*pi/180.)101 if (d_h2oice(i,islope) > 0.) then 102 pos_tend = pos_tend + d_h2oice(i,islope)*cell_area(i)*subslope_dist(i,islope)/cos(def_slope_mean(islope)*pi/180.) 103 103 else 104 neg_tend = neg_tend - tend_h2o_ice(i,islope)*cell_area(i)*subslope_dist(i,islope)/cos(def_slope_mean(islope)*pi/180.)104 neg_tend = neg_tend - d_h2oice(i,islope)*cell_area(i)*subslope_dist(i,islope)/cos(def_slope_mean(islope)*pi/180.) 105 105 endif 106 106 endif … … 108 108 enddo 109 109 110 new_tend encies= 0.110 new_tend = 0. 111 111 if (abs(pos_tend) < 1.e-10 .or. abs(neg_tend) < 1.e-10) then 112 112 write(*,*) "Reason of stopping: there is no sublimating or condensing h2o ice!" … … 118 118 ! We adapt the tendencies to conserve h2o and do only exchange between grid points 119 119 if (neg_tend > pos_tend .and. pos_tend > 0.) then ! More sublimation on the planet than condensation 120 where ( tend_h2o_ice < 0.) ! We lower the sublimating rate by a coefficient121 new_tend encies = tend_h2o_ice*pos_tend/neg_tend120 where (d_h2oice < 0.) ! We lower the sublimating rate by a coefficient 121 new_tend = d_h2oice*pos_tend/neg_tend 122 122 elsewhere ! We don't change the condensing rate 123 new_tend encies = tend_h2o_ice123 new_tend = d_h2oice 124 124 end where 125 125 else if (neg_tend < pos_tend .and. neg_tend > 0.) then ! More condensation on the planet than sublimation 126 where ( tend_h2o_ice < 0.) ! We don't change the sublimating rate127 new_tend encies = tend_h2o_ice126 where (d_h2oice < 0.) ! We don't change the sublimating rate 127 new_tend = d_h2oice 128 128 elsewhere ! We lower the condensing rate by a coefficient 129 new_tend encies = tend_h2o_ice*neg_tend/pos_tend129 new_tend = d_h2oice*neg_tend/pos_tend 130 130 end where 131 131 endif … … 133 133 134 134 ! Evolution of the h2o ice for each physical point 135 h2o_ice = h2o_ice + new_tend encies*dt_pem135 h2o_ice = h2o_ice + new_tend*dt 136 136 137 137 ! We compute the amount of h2o that is sublimated in excess … … 142 142 negative_part = negative_part - h2o_ice(i,islope)*cell_area(i)*subslope_dist(i,islope)/cos(def_slope_mean(islope)*pi/180.) 143 143 h2o_ice(i,islope) = 0. 144 tend_h2o_ice(i,islope) = 0.144 d_h2oice(i,islope) = 0. 145 145 endif 146 146 enddo … … 157 157 do islope = 1,nslope 158 158 do i = 1,ngrid 159 if (new_tend encies(i,islope) > 0.) h2o_ice(i,islope) = h2o_ice(i,islope) - new_tendencies(i,islope)*real_coefficient*dt_pem*cos(def_slope_mean(islope)*pi/180.)159 if (new_tend(i,islope) > 0.) h2o_ice(i,islope) = h2o_ice(i,islope) - new_tend(i,islope)*real_coefficient*dt*cos(def_slope_mean(islope)*pi/180.) 160 160 enddo 161 161 enddo 162 162 else ! ngrid == 1, i.e. in 1D 163 h2o_ice = h2o_ice + tend_h2o_ice*dt_pem163 h2o_ice = h2o_ice + d_h2oice*dt 164 164 endif 165 165 -
trunk/LMDZ.COMMON/libf/evolution/ice_table_mod.F90
r3493 r3498 10 10 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 11 11 12 logical , save:: icetable_equilibrium ! Boolean to say if the PEM needs to recompute the icetable depth when at equilibrium13 logical , save:: icetable_dynamic ! Boolean to say if the PEM needs to recompute the icetable depth with the dynamic method14 real, allocatable, dimension(:,:) 15 real, allocatable, dimension(:,:) 16 real, allocatable, dimension(:,:,:) 12 logical :: icetable_equilibrium ! Boolean to say if the PEM needs to recompute the icetable depth when at equilibrium 13 logical :: icetable_dynamic ! Boolean to say if the PEM needs to recompute the icetable depth with the dynamic method 14 real, allocatable, dimension(:,:) :: icetable_depth ! ngrid x nslope: Depth of the ice table [m] 15 real, allocatable, dimension(:,:) :: icetable_thickness ! ngrid x nslope: Thickness of the ice table [m] 16 real, allocatable, dimension(:,:,:) :: ice_porefilling ! the amout of porefilling in each layer in each grid [m^3/m^3] 17 17 18 18 !----------------------------------------------------------------------- -
trunk/LMDZ.COMMON/libf/evolution/info_PEM_mod.F90
r3387 r3498 9 9 !======================================================================= 10 10 11 SUBROUTINE info_PEM( year_iter,stopPEM,i_myear,n_myear)11 SUBROUTINE info_PEM(i_myear_leg,stopPEM,i_myear,n_myear) 12 12 13 13 !======================================================================= … … 24 24 25 25 !----- Arguments 26 integer, intent(in) :: year_iter, stopPEM ! # of year and reason to stop 27 integer, intent(in) :: i_myear, n_myear ! Current simulated Martian year and maximum number of Martian years to be simulated 26 integer, intent(in) :: stopPEM ! Reason to stop 27 real, intent(in) :: i_myear_leg ! # of years 28 real, intent(in) :: i_myear, n_myear ! Current simulated Martian year and maximum number of Martian years to be simulated 28 29 29 30 !----- Local variables … … 35 36 inquire(file = 'info_PEM.txt',exist = ok) 36 37 if (ok) then 37 write(ich1,'( i0)') i_myear38 write(ich2,'( i0)') n_myear38 write(ich1,'(f0.4)') i_myear 39 write(ich2,'(f0.4)') n_myear 39 40 write(fch,'(f0.4)') convert_years ! 4 digits to the right of the decimal point to respect the precision of Martian year in "launch_pem.sh" 40 41 write(ich3,'(i0)') iPCM … … 51 52 ! Martian date, Number of Martians years done by the PEM run, Number of Martians years done by the chainded simulation, Code of the stopping criterion 52 53 ! The conversion ratio from Planetary years to Earth years is given in the header of the file 53 write(1,*) year_bp_ini + i_myear, year_iter, i_myear, stopPEM54 write(1,*) year_bp_ini + i_myear, i_myear_leg, i_myear, stopPEM 54 55 close(1) 55 56 else -
trunk/LMDZ.COMMON/libf/evolution/layering_mod.F90
r3430 r3498 18 18 19 19 ! Physical parameters 20 real, parameter :: tend_dust = 5.78e-2! Tendency of dust [kg.m-2.y-1]20 real, parameter :: d_dust = 5.78e-2 ! Tendency of dust [kg.m-2.y-1] 21 21 real, parameter :: dry_lag_porosity = 0.5 ! Porosity of dust lag 22 22 real, parameter :: dry_regolith_porosity = 0.45 ! Porosity of regolith … … 452 452 !======================================================================= 453 453 ! Layering algorithm 454 SUBROUTINE make_layering(this, tend_co2ice,tend_h2oice,tend_dust,new_str,new_lag1,new_lag2,stopPEM,current1,current2)454 SUBROUTINE make_layering(this,d_co2ice,d_h2oice,d_dust,new_str,new_lag1,new_lag2,stopPEM,current1,current2) 455 455 456 456 implicit none … … 461 461 logical, intent(inout) :: new_str, new_lag1, new_lag2 462 462 integer, intent(inout) :: stopPEM 463 real, intent(in) :: tend_co2ice, tend_h2oice, tend_dust464 465 !---- Local variables 466 real :: htend_co2ice, htend_h2oice, htend_dust463 real, intent(in) :: d_co2ice, d_h2oice, d_dust 464 465 !---- Local variables 466 real :: dh_co2ice, dh_h2oice, dh_dust 467 467 real :: h_co2ice_old, h_h2oice_old, h_dust_old 468 468 real :: thickness, h2subl, h2subl_tot, h2lift, h2lift_tot … … 471 471 472 472 !---- Code 473 htend_co2ice = tend_co2ice/rho_co2ice474 htend_h2oice = tend_h2oice/rho_h2oice475 htend_dust = tend_dust/rho_dust476 477 if ( htend_dust < 0.) then ! Dust lifting only478 if (abs( htend_co2ice) > eps .or. abs(htend_h2oice) > eps) error stop 'Situation not managed: dust lifting + CO2/H2O ice condensation/sublimation!'473 dh_co2ice = d_co2ice/rho_co2ice 474 dh_h2oice = d_h2oice/rho_h2oice 475 dh_dust = d_dust/rho_dust 476 477 if (dh_dust < 0.) then ! Dust lifting only 478 if (abs(dh_co2ice) > eps .or. abs(dh_h2oice) > eps) error stop 'Situation not managed: dust lifting + CO2/H2O ice condensation/sublimation!' 479 479 write(*,'(a)') ' Stratification -> Dust lifting' 480 h2lift_tot = abs( htend_dust)480 h2lift_tot = abs(dh_dust) 481 481 do while (h2lift_tot > 0. .and. associated(current1)) 482 482 ! Is the considered stratum a dust lag? … … 508 508 509 509 !------ Dust sedimentation only 510 if (abs( htend_co2ice) < eps .and. abs(htend_h2oice) < eps) then510 if (abs(dh_co2ice) < eps .and. abs(dh_h2oice) < eps) then 511 511 write(*,'(a)') ' Stratification -> Dust sedimentation' 512 512 ! New stratum at the layering top by sedimentation of dust 513 thickness = htend_dust/(1. - dry_regolith_porosity)513 thickness = dh_dust/(1. - dry_regolith_porosity) 514 514 if (thickness > 0.) then ! Only if the stratum is building up 515 515 if (new_str) then 516 call add_stratum(this,thickness,this%top%top_elevation + thickness,0.,0., htend_dust/thickness,dry_regolith_porosity)516 call add_stratum(this,thickness,this%top%top_elevation + thickness,0.,0.,dh_dust/thickness,dry_regolith_porosity) 517 517 new_str = .false. 518 518 else … … 523 523 524 524 !------ Condensation of CO2 ice + H2O ice 525 else if (( htend_co2ice >= 0. .and. htend_h2oice > 0.) .or. (htend_co2ice > 0. .and. htend_h2oice >= 0.)) then525 else if ((dh_co2ice >= 0. .and. dh_h2oice > 0.) .or. (dh_co2ice > 0. .and. dh_h2oice >= 0.)) then 526 526 write(*,'(a)') ' Stratification -> CO2 and H2O ice condensation' 527 527 ! New stratum at the layering top by condensation of CO2 and H2O ice 528 thickness = htend_co2ice/(1. - co2ice_porosity) + htend_h2oice/(1. - h2oice_porosity) + htend_dust528 thickness = dh_co2ice/(1. - co2ice_porosity) + dh_h2oice/(1. - h2oice_porosity) + dh_dust 529 529 if (thickness > 0.) then ! Only if the stratum is building up 530 530 if (new_str) then 531 call add_stratum(this,thickness,this%top%top_elevation + thickness, htend_co2ice/thickness,htend_h2oice/thickness,htend_dust/thickness,1. - (htend_co2ice/thickness + htend_h2oice/thickness + htend_dust/thickness))531 call add_stratum(this,thickness,this%top%top_elevation + thickness,dh_co2ice/thickness,dh_h2oice/thickness,dh_dust/thickness,1. - (dh_co2ice/thickness + dh_h2oice/thickness + dh_dust/thickness)) 532 532 new_str = .false. 533 533 else … … 538 538 539 539 !------ Sublimation of CO2 ice + Condensation of H2O ice 540 else if ( htend_co2ice < 0. .and. htend_h2oice > 0.) then540 else if (dh_co2ice < 0. .and. dh_h2oice > 0.) then 541 541 write(*,'(a)') ' Stratification -> Sublimation of CO2 ice + Condensation of H2O ice' 542 542 ! CO2 ice sublimation in the considered stratum + New stratum for dust lag 543 h2subl_tot = abs( htend_co2ice)543 h2subl_tot = abs(dh_co2ice) 544 544 do while (h2subl_tot > 0. .and. associated(current1)) 545 545 h_co2ice_old = current1%co2ice_volfrac*current1%thickness … … 585 585 endif 586 586 ! New stratum at the layering top by condensation of H2O ice 587 thickness = htend_h2oice/(1. - h2oice_porosity) + htend_dust587 thickness = dh_h2oice/(1. - h2oice_porosity) + dh_dust 588 588 if (thickness > 0.) then ! Only if the stratum is building up 589 589 if (new_str) then 590 call add_stratum(this,thickness,this%top%top_elevation + thickness,0., htend_h2oice/thickness,htend_dust/thickness,1. - (htend_h2oice/thickness + htend_dust/thickness))590 call add_stratum(this,thickness,this%top%top_elevation + thickness,0.,dh_h2oice/thickness,dh_dust/thickness,1. - (dh_h2oice/thickness + dh_dust/thickness)) 591 591 new_str = .false. 592 592 else … … 597 597 598 598 !------ Sublimation of CO2 ice + H2O ice 599 else if (( htend_co2ice <= 0. .and. htend_h2oice < 0.) .or. (htend_co2ice < 0. .and. htend_h2oice <= 0.)) then599 else if ((dh_co2ice <= 0. .and. dh_h2oice < 0.) .or. (dh_co2ice < 0. .and. dh_h2oice <= 0.)) then 600 600 write(*,'(a)') ' Stratification -> Sublimation of CO2 and H2O ice' 601 601 ! CO2 ice sublimation in the considered stratum + New stratum for dust lag 602 h2subl_tot = abs( htend_co2ice)602 h2subl_tot = abs(dh_co2ice) 603 603 do while (h2subl_tot > 0. .and. associated(current1)) 604 604 h_co2ice_old = current1%co2ice_volfrac*current1%thickness … … 644 644 endif 645 645 ! H2O ice sublimation in the considered stratum + New stratum for dust lag 646 h2subl_tot = abs( htend_h2oice)646 h2subl_tot = abs(dh_h2oice) 647 647 do while (h2subl_tot > 0. .and. associated(current2)) 648 648 h_co2ice_old = current2%co2ice_volfrac*current2%thickness … … 689 689 690 690 !------ Condensation of CO2 ice + Sublimation of H2O ice 691 else if ( htend_co2ice > 0. .and. htend_h2oice < 0.) then691 else if (dh_co2ice > 0. .and. dh_h2oice < 0.) then 692 692 error stop 'Impossible situation: CO2 ice condensation + H2O ice sublimation!' 693 693 endif -
trunk/LMDZ.COMMON/libf/evolution/orbit_param_criterion_mod.F90
r3399 r3498 15 15 !======================================================================= 16 16 17 SUBROUTINE orbit_param_criterion(i_myear, year_iter_max)17 SUBROUTINE orbit_param_criterion(i_myear,n_myear_leg) 18 18 19 19 #ifdef CPP_IOIPSL … … 38 38 ! Input Variables 39 39 !-------------------------------------------------------- 40 integer, intent(in) :: i_myear ! Martian year of the simulation40 real, intent(in) :: i_myear ! Martian year of the simulation 41 41 42 42 !-------------------------------------------------------- 43 43 ! Output Variables 44 44 !-------------------------------------------------------- 45 integer, intent(out) :: year_iter_max! Maximum number of iteration of the PEM before orb changes too much45 real, intent(out) :: n_myear_leg ! Maximum number of iteration of the PEM before orb changes too much 46 46 47 47 !-------------------------------------------------------- 48 48 ! Local variables 49 49 !-------------------------------------------------------- 50 integer:: Year ! Year of the simulation50 real :: Year ! Year of the simulation 51 51 real :: Lsp ! Ls perihelion 52 52 real :: max_change_obl, max_change_ecc, max_change_lsp ! Maximum admissible change 53 53 real :: max_obl, max_ecc, max_lsp ! Maximum value of orbit param given the admissible change 54 54 real :: min_obl, min_ecc, min_lsp ! Minimum value of orbit param given the admissible change 55 integer:: max_obl_iter, max_ecc_iter, max_lsp_iter ! Maximum year iteration before reaching an inadmissible value of orbit param55 real :: max_obl_iter, max_ecc_iter, max_lsp_iter ! Maximum year iteration before reaching an inadmissible value of orbit param 56 56 integer :: ilask ! Loop variable 57 57 real :: xa, xb, ya, yb ! Variables for interpolation … … 113 113 ! If we do not want some orb parameter to change, they should not be a stopping criterion, 114 114 ! So the number of iteration corresponding is set to maximum 115 max_obl_iter = 1000000 116 max_ecc_iter = 1000000 117 max_lsp_iter = 1000000 115 max_obl_iter = 1000000. 116 max_ecc_iter = 1000000. 117 max_lsp_iter = 1000000. 118 118 119 119 ! The maximum reachable year is found by interpolation according to the maximum admissible change of orbital parameters … … 136 136 yb = obllask(ilask - 1) 137 137 if (yb < min_obl) then ! The minimum accepted is overtaken 138 max_obl_iter = floor((min_obl - ya)*(xb - xa)/(yb - ya) + xa)- Year138 max_obl_iter = (min_obl - ya)*(xb - xa)/(yb - ya) + xa - Year 139 139 found_obl = .true. 140 140 else if (max_obl < yb) then ! The maximum accepted is overtaken 141 max_obl_iter = floor((max_obl - ya)*(xb - xa)/(yb - ya) + xa)- Year141 max_obl_iter = (max_obl - ya)*(xb - xa)/(yb - ya) + xa - Year 142 142 found_obl = .true. 143 143 endif … … 149 149 yb = ecclask(ilask - 1) 150 150 if (yb < min_ecc) then ! The minimum accepted is overtaken 151 max_ecc_iter = floor((min_ecc - ya)*(xb - xa)/(yb - ya) + xa)- Year151 max_ecc_iter = (min_ecc - ya)*(xb - xa)/(yb - ya) + xa - Year 152 152 found_ecc = .true. 153 153 else if (max_ecc < yb) then ! The maximum accepted is overtaken 154 max_ecc_iter = floor((max_ecc - ya)*(xb - xa)/(yb - ya) + xa)- Year154 max_ecc_iter = (max_ecc - ya)*(xb - xa)/(yb - ya) + xa - Year 155 155 found_ecc = .true. 156 156 endif … … 187 187 endif 188 188 if (yb < min_lsp) then ! The minimum accepted is overtaken 189 max_lsp_iter = floor((min_lsp - ya)*(xb - xa)/(yb - ya) + xa)- Year189 max_lsp_iter = (min_lsp - ya)*(xb - xa)/(yb - ya) + xa - Year 190 190 found_lsp = .true. 191 191 else if (max_lsp < yb) then ! The maximum accepted is overtaken 192 max_lsp_iter = floor((max_lsp - ya)*(xb - xa)/(yb - ya) + xa)- Year192 max_lsp_iter = (max_lsp - ya)*(xb - xa)/(yb - ya) + xa - Year 193 193 found_lsp = .true. 194 194 endif … … 206 206 write(*,*) 'Max. number of iterations for the Lsp parameter =', max_lsp_iter 207 207 208 year_iter_max= min(max_obl_iter,max_ecc_iter,max_lsp_iter)209 year_iter_max = max(year_iter_max,1) 210 write(*,*) 'So the max. number of iterations for the orbital criteria =', year_iter_max208 n_myear_leg = min(max_obl_iter,max_ecc_iter,max_lsp_iter) 209 if (n_myear_leg < 1.) n_myear_leg = 1. ! n_myear_leg should be at least equal to 1 210 write(*,*) 'So the max. number of iterations for the orbital criteria =', n_myear_leg 211 211 212 212 END SUBROUTINE orbit_param_criterion -
trunk/LMDZ.COMMON/libf/evolution/pem.F90
r3493 r3498 51 51 ini_adsorption_h_PEM, end_adsorption_h_PEM, & ! Allocate arrays 52 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_ini53 use time_evol_mod, only: dt, evol_orbit_pem, Max_iter_pem, convert_years, year_bp_ini 54 54 use orbit_param_criterion_mod, only: orbit_param_criterion 55 55 use recomp_orb_param_mod, only: recomp_orb_param … … 70 70 use writediagpem_mod, only: writediagpem, writediagsoilpem 71 71 use co2condens_mod, only: CO2cond_ps 72 use layering_mod, only: tend_dust, ptrarray, stratum, layering, ini_layering, del_layering, make_layering, get_nb_str_max, nb_str_max, layering_algo72 use layering_mod, only: d_dust, ptrarray, stratum, layering, ini_layering, del_layering, make_layering, get_nb_str_max, nb_str_max, layering_algo 73 73 74 74 #ifndef CPP_STD … … 195 195 196 196 ! Variables for slopes 197 real, dimension(:,:), allocatable :: tend_co2_ice! physical point x slope field: Tendency of evolution of perennial co2 ice over a year198 real, dimension(:,:), allocatable :: tend_co2_ice_ini! physical point x slope field: Tendency of evolution of perennial co2 ice over a year in the PCM199 real, dimension(:,:), allocatable :: tend_h2o_ice! physical point x slope field: Tendency of evolution of perennial h2o ice200 real, dimension(:,:), allocatable :: flag_co2flow 201 real, dimension(:), allocatable :: flag_co2flow_mesh 202 real, dimension(:,:), allocatable :: flag_h2oflow 203 real, dimension(:), allocatable :: flag_h2oflow_mesh 197 real, dimension(:,:), allocatable :: d_co2ice ! physical point x slope field: Tendency of evolution of perennial co2 ice over a year 198 real, dimension(:,:), allocatable :: d_co2ice_ini ! physical point x slope field: Tendency of evolution of perennial co2 ice over a year in the PCM 199 real, dimension(:,:), allocatable :: d_h2oice ! physical point x slope field: Tendency of evolution of perennial h2o ice 200 real, dimension(:,:), allocatable :: flag_co2flow ! (ngrid,nslope): Flag where there is a CO2 glacier flow 201 real, dimension(:), allocatable :: flag_co2flow_mesh ! (ngrid) : Flag where there is a CO2 glacier flow 202 real, dimension(:,:), allocatable :: flag_h2oflow ! (ngrid,nslope): Flag where there is a H2O glacier flow 203 real, dimension(:), allocatable :: flag_h2oflow_mesh ! (ngrid) : Flag where there is a H2O glacier flow 204 204 205 205 ! Variables for surface and soil … … 230 230 ! Some variables for the PEM run 231 231 real, parameter :: year_step = 1 ! Timestep for the pem 232 integer :: year_iter! Number of iteration233 integer :: year_iter_max! Maximum number of iterations before stopping234 integer:: i_myear ! Global number of Martian years of the chained simulations235 integer:: n_myear ! Maximum number of Martian years of the chained simulations232 real :: i_myear_leg ! Number of iteration 233 real :: n_myear_leg ! Maximum number of iterations before stopping 234 real :: i_myear ! Global number of Martian years of the chained simulations 235 real :: n_myear ! Maximum number of Martian years of the chained simulations 236 236 real :: timestep ! Timestep [s] 237 237 character(20) :: job_id ! Job id provided as argument passed on the command line when the program was invoked … … 604 604 ! I_f Compute tendencies 605 605 !------------------------ 606 allocate( tend_co2_ice(ngrid,nslope),tend_h2o_ice(ngrid,nslope))607 allocate( tend_co2_ice_ini(ngrid,nslope))606 allocate(d_co2ice(ngrid,nslope),d_h2oice(ngrid,nslope)) 607 allocate(d_co2ice_ini(ngrid,nslope)) 608 608 609 609 ! Compute the tendencies of the evolution of ice over the years 610 call compute_tend(ngrid,nslope,min_co2_ice, tend_co2_ice)611 call compute_tend(ngrid,nslope,min_h2o_ice, tend_h2o_ice)612 tend_co2_ice_ini = tend_co2_ice610 call compute_tend(ngrid,nslope,min_co2_ice,d_co2ice) 611 call compute_tend(ngrid,nslope,min_h2o_ice,d_h2oice) 612 d_co2ice_ini = d_co2ice 613 613 deallocate(min_co2_ice,min_h2o_ice) 614 614 … … 646 646 call pemetat0("startpem.nc",ngrid,nsoilmx,nsoilmx_PEM,nslope,timelen,timestep,TI_PEM,tsoil_PEM,icetable_depth, & 647 647 icetable_thickness,ice_porefilling,tsurf_avg_yr1,tsurf_avg,q_co2_PEM_phys,q_h2o_PEM_phys, & 648 ps_timeseries,tsoil_phys_PEM_timeseries, tend_h2o_ice,tend_co2_ice,co2_ice,h2o_ice,&649 global_avg_press_PCM,watersurf_density_avg,watersoil_density_PEM_avg,co2_adsorbded_phys, 648 ps_timeseries,tsoil_phys_PEM_timeseries,d_h2oice,d_co2ice,co2_ice,h2o_ice, & 649 global_avg_press_PCM,watersurf_density_avg,watersoil_density_PEM_avg,co2_adsorbded_phys, & 650 650 delta_co2_adsorbded,h2o_adsorbded_phys,delta_h2o_adsorbded,stratif) 651 651 … … 662 662 do islope = 1,nslope 663 663 if (co2_ice(i,islope) > 0.) is_co2ice_ini(i,islope) = .true. 664 if ( tend_co2_ice(i,islope) < 0. .and. co2_ice(i,islope) > 0.) then664 if (d_co2ice(i,islope) < 0. .and. co2_ice(i,islope) > 0.) then 665 665 ini_co2ice_sublim(i,islope) = .true. 666 666 co2ice_ini_surf = co2ice_ini_surf + cell_area(i)*subslope_dist(i,islope) 667 667 endif 668 if ( tend_h2o_ice(i,islope) < 0. .and. h2o_ice(i,islope) > 0.) then668 if (d_h2oice(i,islope) < 0. .and. h2o_ice(i,islope) > 0.) then 669 669 ini_h2oice_sublim(i,islope) = .true. 670 670 h2oice_ini_surf = h2oice_ini_surf + cell_area(i)*subslope_dist(i,islope) … … 712 712 #endif 713 713 714 year_iter_max= Max_iter_pem715 if (evol_orbit_pem) call orbit_param_criterion(i_myear, year_iter_max)714 n_myear_leg = Max_iter_pem 715 if (evol_orbit_pem) call orbit_param_criterion(i_myear,n_myear_leg) 716 716 717 717 !-------------------------- END INITIALIZATION ------------------------- … … 722 722 ! II_a Update pressure, ice and tracers 723 723 !------------------------ 724 year_iter= 0724 i_myear_leg = 0 725 725 stopPEM = 0 726 726 if (layering_algo) then … … 737 737 endif 738 738 739 do while ( year_iter < year_iter_max.and. i_myear < n_myear)739 do while (i_myear_leg < n_myear_leg .and. i_myear < n_myear) 740 740 ! II.a.1. Compute updated global pressure 741 741 write(*,*) "Recomputing the new pressure..." 742 742 do i = 1,ngrid 743 743 do islope = 1,nslope 744 global_avg_press_new = global_avg_press_new - CO2cond_ps*g*cell_area(i)* tend_co2_ice(i,islope)*subslope_dist(i,islope)/cos(pi*def_slope_mean(islope)/180.)/Total_surface744 global_avg_press_new = global_avg_press_new - CO2cond_ps*g*cell_area(i)*d_co2ice(i,islope)*subslope_dist(i,islope)/cos(pi*def_slope_mean(islope)/180.)/Total_surface 745 745 enddo 746 746 enddo … … 817 817 ! II_b Evolution of ice 818 818 !------------------------ 819 call evol_h2o_ice(ngrid,nslope,cell_area,delta_h2o_adsorbded,delta_h2o_icetablesublim,h2o_ice, tend_h2o_ice,stopPEM)820 call evol_co2_ice(ngrid,nslope,co2_ice, tend_co2_ice)819 call evol_h2o_ice(ngrid,nslope,cell_area,delta_h2o_adsorbded,delta_h2o_icetablesublim,h2o_ice,d_h2oice,stopPEM) 820 call evol_co2_ice(ngrid,nslope,co2_ice,d_co2ice) 821 821 if (layering_algo) then 822 822 do islope = 1,nslope 823 823 do ig = 1,ngrid 824 call make_layering(stratif(ig,islope), tend_co2_ice(ig,islope),tend_h2o_ice(ig,islope),tend_dust,new_str(ig,islope),new_lag1(ig,islope),new_lag2(ig,islope),stopPEM,current1(ig,islope)%p,current2(ig,islope)%p)824 call make_layering(stratif(ig,islope),d_co2ice(ig,islope),d_h2oice(ig,islope),d_dust,new_str(ig,islope),new_lag1(ig,islope),new_lag2(ig,islope),stopPEM,current1(ig,islope)%p,current2(ig,islope)%p) 825 825 enddo 826 826 enddo … … 832 832 !------------------------ 833 833 if (co2ice_flow .and. nslope > 1) call flow_co2glaciers(timelen,ngrid,nslope,iflat,subslope_dist,def_slope_mean,vmr_co2_PEM_phys,ps_timeseries, & 834 global_avg_press_PCM,global_avg_press_new,co2_ice,flag_co2flow,flag_co2flow_mesh)834 global_avg_press_PCM,global_avg_press_new,co2_ice,flag_co2flow,flag_co2flow_mesh) 835 835 if (h2oice_flow .and. nslope > 1) call flow_h2oglaciers(timelen,ngrid,nslope,iflat,subslope_dist,def_slope_mean,tsurf_avg,h2o_ice,flag_h2oflow,flag_h2oflow_mesh) 836 836 … … 878 878 emis(ig,islope) = emissiv 879 879 endif 880 else if ((co2_ice(ig,islope) > 1.e-3) .and. ( tend_co2_ice(ig,islope) > 1.e-10)) then ! Put tsurf as tcond co2880 else if ((co2_ice(ig,islope) > 1.e-3) .and. (d_co2ice(ig,islope) > 1.e-10)) then ! Put tsurf as tcond co2 881 881 ave = 0. 882 882 do t = 1,timelen … … 945 945 946 946 ! II_d.4 Update the soil thermal properties 947 call update_soil_thermalproperties(ngrid,nslope,nsoilmx_PEM, tend_h2o_ice,h2o_ice,global_avg_press_new,icetable_depth,icetable_thickness,TI_PEM)947 call update_soil_thermalproperties(ngrid,nslope,nsoilmx_PEM,d_h2oice,h2o_ice,global_avg_press_new,icetable_depth,icetable_thickness,TI_PEM) 948 948 949 949 ! II_d.5 Update the mass of the regolith adsorbed 950 950 if (adsorption_pem) then 951 call regolith_adsorption(ngrid,nslope,nsoilmx_PEM,timelen, tend_h2o_ice,tend_co2_ice, &951 call regolith_adsorption(ngrid,nslope,nsoilmx_PEM,timelen,d_h2oice,d_co2ice, & 952 952 h2o_ice,co2_ice,tsoil_PEM,TI_PEM,ps_timeseries,q_co2_PEM_phys,q_h2o_PEM_phys, & 953 953 h2o_adsorbded_phys,delta_h2o_adsorbded,co2_adsorbded_phys,delta_co2_adsorbded) … … 986 986 call writediagpem(ngrid,'h2o_ice_slope'//str2,'H2O ice','kg.m-2',2,h2o_ice(:,islope)) 987 987 call writediagpem(ngrid,'co2_ice_slope'//str2,'CO2 ice','kg.m-2',2,co2_ice(:,islope)) 988 call writediagpem(ngrid,' tend_h2o_ice_slope'//str2,'H2O ice tend','kg.m-2.year-1',2,tend_h2o_ice(:,islope))989 call writediagpem(ngrid,' tend_co2_ice_slope'//str2,'CO2 ice tend','kg.m-2.year-1',2,tend_co2_ice(:,islope))988 call writediagpem(ngrid,'d_h2oice_slope'//str2,'H2O ice tend','kg.m-2.year-1',2,d_h2oice(:,islope)) 989 call writediagpem(ngrid,'d_co2ice_slope'//str2,'CO2 ice tend','kg.m-2.year-1',2,d_co2ice(:,islope)) 990 990 call writediagpem(ngrid,'Flow_co2ice_slope'//str2,'CO2 ice flow','Boolean',2,flag_co2flow(:,islope)) 991 991 call writediagpem(ngrid,'tsurf_slope'//str2,'tsurf','K',2,tsurf(:,islope)) … … 1012 1012 ! II_f Update the tendencies 1013 1013 !------------------------ 1014 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, &1014 call recomp_tend_co2_slope(ngrid,nslope,timelen,d_co2ice,d_co2ice_ini,co2_ice,emis,vmr_co2_PCM,vmr_co2_PEM_phys,ps_timeseries, & 1015 1015 global_avg_press_PCM,global_avg_press_new) 1016 1016 … … 1023 1023 call stopping_crit_h2o_ice(cell_area,h2oice_ini_surf,ini_h2oice_sublim,h2o_ice,stopPEM,ngrid) 1024 1024 call stopping_crit_co2(cell_area,co2ice_ini_surf,ini_co2ice_sublim,co2_ice,stopPEM,ngrid,global_avg_press_PCM,global_avg_press_new,nslope) 1025 year_iter = year_iter + dt_pem1026 i_myear = i_myear + dt _pem1027 if (stopPEM <= 0 .and. year_iter >= year_iter_max) stopPEM = 51025 i_myear_leg = i_myear_leg + dt 1026 i_myear = i_myear + dt 1027 if (stopPEM <= 0 .and. i_myear_leg >= n_myear_leg) stopPEM = 5 1028 1028 if (stopPEM <= 0 .and. i_myear >= n_myear) stopPEM = 6 1029 1029 call system_clock(c2) … … 1053 1053 else 1054 1054 write(*,*) "The PEM can continue!" 1055 write(*,*) "Number of iterations of the PEM: year_iter =", year_iter1055 write(*,*) "Number of iterations of the PEM: i_myear_leg =", i_myear_leg 1056 1056 write(*,*) "Number of simulated Martian years: i_myear =", i_myear 1057 1057 endif … … 1151 1151 enddo 1152 1152 1153 if (evol_orbit_pem) call recomp_orb_param(i_myear, year_iter)1153 if (evol_orbit_pem) call recomp_orb_param(i_myear,i_myear_leg) 1154 1154 1155 1155 !------------------------ … … 1213 1213 write(*,*) "restartpem.nc has been written" 1214 1214 1215 call info_PEM( year_iter,stopPEM,i_myear,n_myear)1216 1217 write(*,*) "The PEM has run for", year_iter, "Martian years."1215 call info_PEM(i_myear_leg,stopPEM,i_myear,n_myear) 1216 1217 write(*,*) "The PEM has run for", i_myear_leg, "Martian years." 1218 1218 write(*,*) "The chained simulation has run for", i_myear, "Martian years =", i_myear*convert_years, "Earth years." 1219 1219 write(*,*) "The reached date is now", (year_bp_ini + i_myear)*convert_years, "Earth years." 1220 write(*,*) " LL & RV & JBC: so far, so good!"1220 write(*,*) "PEM: so far, so good!" 1221 1221 1222 1222 if (layering_algo) then -
trunk/LMDZ.COMMON/libf/evolution/pemetat0.F90
r3493 r3498 8 8 9 9 SUBROUTINE pemetat0(filename,ngrid,nsoil_PCM,nsoil_PEM,nslope,timelen,timestep,TI_PEM,tsoil_PEM,ice_table_depth,ice_table_thickness, & 10 ice_porefilling,tsurf_avg_yr1,tsurf_avg_yr2,q_co2,q_h2o,ps_inst,tsoil_inst, tend_h2o_ice,tend_co2_ice,co2_ice,h2o_ice, &10 ice_porefilling,tsurf_avg_yr1,tsurf_avg_yr2,q_co2,q_h2o,ps_inst,tsoil_inst,d_h2oice,d_co2ice,co2_ice,h2o_ice, & 11 11 global_avg_pressure,watersurf_avg,watersoil_avg,m_co2_regolith_phys,deltam_co2_regolith_phys, & 12 12 m_h2o_regolith_phys,deltam_h2o_regolith_phys,stratif) … … 49 49 real, dimension(ngrid,timelen), intent(in) :: q_h2o ! MMR tracer h2o [kg/kg] 50 50 real, dimension(ngrid,timelen), intent(in) :: ps_inst ! surface pressure [Pa] 51 real, dimension(ngrid,nslope), intent(in) :: tend_h2o_ice ! tendencies on h2o ice52 real, dimension(ngrid,nslope), intent(in) :: tend_co2_ice ! tendencies on co2 ice51 real, dimension(ngrid,nslope), intent(in) :: d_h2oice ! tendencies on h2o ice 52 real, dimension(ngrid,nslope), intent(in) :: d_co2ice ! tendencies on co2 ice 53 53 real, dimension(ngrid,nslope), intent(in) :: watersurf_avg ! surface water ice density, yearly averaged (kg/m^3) 54 54 ! outputs … … 105 105 inquire(file = filename,exist = startpem_file) 106 106 107 write(*,*)'Is start PEM?',startpem_file107 write(*,*)'Is there a "startpem" file?',startpem_file 108 108 109 109 !0.2 Set to default values … … 315 315 write(*,*)'will reconstruct the values of the ice table given the current state' 316 316 call computeice_table_equilibrium(ngrid,nslope,nsoil_PEM,watercaptag,watersurf_avg,watersoil_avg, TI_PEM(:,1,:),ice_table_depth,ice_table_thickness) 317 call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM, tend_h2o_ice,h2o_ice,global_avg_pressure,ice_table_depth,ice_table_thickness,TI_PEM)317 call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM,d_h2oice,h2o_ice,global_avg_pressure,ice_table_depth,ice_table_thickness,TI_PEM) 318 318 do islope = 1,nslope 319 319 call ini_tsoil_pem(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_avg_yr2(:,islope),tsoil_PEM(:,:,islope)) … … 327 327 write(*,*)'will reconstruct the values of the ice table given the current state' 328 328 call computeice_table_equilibrium(ngrid,nslope,nsoil_PEM,watercaptag,watersurf_avg,watersoil_avg, TI_PEM(:,1,:),ice_table_depth,ice_table_thickness) 329 call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM, tend_h2o_ice,h2o_ice,global_avg_pressure,ice_table_depth,ice_table_thickness,TI_PEM)329 call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM,d_h2oice,h2o_ice,global_avg_pressure,ice_table_depth,ice_table_thickness,TI_PEM) 330 330 do islope = 1,nslope 331 331 call ini_tsoil_pem(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_avg_yr2(:,islope),tsoil_PEM(:,:,islope)) … … 360 360 enddo 361 361 362 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, &362 call regolith_adsorption(ngrid,nslope,nsoil_PEM,timelen,d_h2oice,d_co2ice,h2o_ice,co2_ice,tsoil_PEM,TI_PEM,ps_inst,q_co2,q_h2o, & 363 363 m_h2o_regolith_phys,deltam_h2o_regolith_phys, m_co2_regolith_phys,deltam_co2_regolith_phys) 364 364 … … 504 504 if (icetable_equilibrium) then 505 505 call computeice_table_equilibrium(ngrid,nslope,nsoil_PEM,watercaptag,watersurf_avg,watersoil_avg,TI_PEM(:,1,:),ice_table_depth,ice_table_thickness) 506 call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM, tend_h2o_ice,h2o_ice,global_avg_pressure,ice_table_depth,ice_table_thickness,TI_PEM)506 call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM,d_h2oice,h2o_ice,global_avg_pressure,ice_table_depth,ice_table_thickness,TI_PEM) 507 507 do islope = 1,nslope 508 508 call ini_tsoil_pem(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_avg_yr2(:,islope),tsoil_PEM(:,:,islope)) … … 512 512 ice_porefilling = 0. 513 513 ice_table_depth = 0. 514 call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM, tend_h2o_ice,h2o_ice,global_avg_pressure,ice_table_depth,ice_table_thickness,TI_PEM)514 call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM,d_h2oice,h2o_ice,global_avg_pressure,ice_table_depth,ice_table_thickness,TI_PEM) 515 515 do islope = 1,nslope 516 516 call ini_tsoil_pem(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_avg_yr2(:,islope),tsoil_PEM(:,:,islope)) … … 524 524 m_co2_regolith_phys = 0. 525 525 m_h2o_regolith_phys = 0. 526 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, &526 call regolith_adsorption(ngrid,nslope,nsoil_PEM,timelen,d_h2oice,d_co2ice,h2o_ice,co2_ice,tsoil_PEM,TI_PEM,ps_inst,q_co2,q_h2o, & 527 527 m_h2o_regolith_phys,deltam_h2o_regolith_phys, m_co2_regolith_phys,deltam_co2_regolith_phys) 528 528 deltam_co2_regolith_phys = 0. -
trunk/LMDZ.COMMON/libf/evolution/pemredem.F90
r3493 r3498 73 73 74 74 character(*), intent(in) :: filename 75 integer, intent(in) :: nsoil_PEM, ngrid, nslope, i_myear 75 integer, intent(in) :: nsoil_PEM, ngrid, nslope 76 real, intent(in) :: i_myear 76 77 real, dimension(ngrid,nsoil_PEM,nslope), intent(in) :: tsoil_slope_PEM ! under mesh bining according to slope 77 78 real, dimension(ngrid,nsoil_PEM,nslope), intent(in) :: inertiesoil_slope_PEM ! under mesh bining according to slope -
trunk/LMDZ.COMMON/libf/evolution/recomp_orb_param_mod.F90
r3206 r3498 13 13 !======================================================================= 14 14 15 SUBROUTINE recomp_orb_param(i_myear, year_iter)15 SUBROUTINE recomp_orb_param(i_myear,i_myear_leg) 16 16 17 17 use time_evol_mod, only: year_bp_ini, var_obl, var_ecc, var_lsp … … 30 30 ! Input Variables 31 31 !-------------------------------------------------------- 32 integer, intent(in) :: i_myear ! Number of simulated Martian years33 integer, intent(in) :: year_iter! Number of iterations of the PEM32 real, intent(in) :: i_myear ! Number of simulated Martian years 33 real, intent(in) :: i_myear_leg ! Number of iterations of the PEM 34 34 35 35 !-------------------------------------------------------- … … 40 40 ! Local variables 41 41 !-------------------------------------------------------- 42 integer:: Year ! Year of the simulation42 real :: Year ! Year of the simulation 43 43 real :: Lsp ! Ls perihelion 44 44 integer :: ilask ! Loop variable … … 61 61 Lsp = lsperi*180./pi ! We convert in degree 62 62 63 write(*,*) 'recomp_orb_param, Old year =', Year - year_iter63 write(*,*) 'recomp_orb_param, Old year =', Year - i_myear_leg 64 64 write(*,*) 'recomp_orb_param, Old obl. =', obliquit 65 65 write(*,*) 'recomp_orb_param, Old ecc. =', e_elips -
trunk/LMDZ.COMMON/libf/evolution/recomp_tend_co2_slope_mod.F90
r3381 r3498 7 7 !======================================================================= 8 8 9 SUBROUTINE recomp_tend_co2_slope(ngrid,nslope,timelen, tendencies_co2_ice_phys,tendencies_co2_ice_phys_ini,co2ice_slope,emissivity_slope, &9 SUBROUTINE recomp_tend_co2_slope(ngrid,nslope,timelen,d_co2ice_phys,d_co2ice_phys_ini,co2ice_slope,emissivity_slope, & 10 10 vmr_co2_PCM,vmr_co2_pem,ps_PCM_2,global_avg_press_PCM,global_avg_press_new) 11 11 … … 29 29 real, intent(in) :: global_avg_press_PCM ! global averaged pressure at previous timestep 30 30 real, intent(in) :: global_avg_press_new ! global averaged pressure at current timestep 31 real, dimension(ngrid,nslope), intent(in) :: tendencies_co2_ice_phys_ini ! physical point field: Evolution of perennial ice over one year31 real, dimension(ngrid,nslope), intent(in) :: d_co2ice_phys_ini ! physical point field: Evolution of perennial ice over one year 32 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 35 real, dimension(ngrid,nslope), intent(inout) :: tendencies_co2_ice_phys ! physical point field: Evolution of perennial ice over one year35 real, dimension(ngrid,nslope), intent(inout) :: d_co2ice_phys ! physical point field: Evolution of perennial ice over one year 36 36 37 37 ! local: … … 47 47 coef = sols_per_my*sec_per_sol*emissivity_slope(i,islope)*sigmaB/Lco2 48 48 ave = 0. 49 if (co2ice_slope(i,islope) > 1.e-4 .and. abs( tendencies_co2_ice_phys(i,islope)) > 1.e-5) then49 if (co2ice_slope(i,islope) > 1.e-4 .and. abs(d_co2ice_phys(i,islope)) > 1.e-5) then 50 50 do t=1,timelen 51 51 ave = ave + (beta_clap_co2/(alpha_clap_co2-log(vmr_co2_PCM(i,t)*ps_PCM_2(i,t)/100.)))**4 & … … 53 53 enddo 54 54 if (ave < 1e-4) ave = 0. 55 tendencies_co2_ice_phys(i,islope) = tendencies_co2_ice_phys_ini(i,islope) - coef*ave/timelen55 d_co2ice_phys(i,islope) = d_co2ice_phys_ini(i,islope) - coef*ave/timelen 56 56 endif 57 57 enddo -
trunk/LMDZ.COMMON/libf/evolution/time_evol_mod.F90
r3214 r3498 3 3 implicit none 4 4 5 integer:: year_bp_ini ! Initial year (in Planetary years) of the simulation of the PEM defined in run.def (in Earth years)6 integer :: dt_pem! Time step used by the PEM in Planetary years5 real :: year_bp_ini ! Initial year (in Planetary years) of the simulation of the PEM defined in run.def (in Earth years) 6 real :: dt ! Time step used by the PEM in Planetary years 7 7 real :: convert_years ! Conversion ratio from Planetary years to Earth years 8 8 real :: h2o_ice_crit ! Percentage of change of the surface of h2o ice sublimating before stopping the PEM 9 9 real :: co2_ice_crit ! Percentage of change of the surface of co2 ice sublimating before stopping the PEM 10 10 real :: ps_criterion ! Percentage of change of averaged surface pressure before stopping the PEM 11 integer :: Max_iter_pem ! Maximal number of iteration when converging to a steady state, read in evol.def11 integer :: Max_iter_pem ! Maximal number of iterations when converging to a steady state, read in evol.def 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 -
trunk/LMDZ.COMMON/libf/evolution/writediagpem.F90
r3345 r3498 51 51 use mod_phys_lmdz_para, only: is_parallel, is_mpi_root, is_master, gather 52 52 use mod_grid_phy_lmdz, only: klon_glo, Grid1Dto2D_glo, nbp_lon, nbp_lat, nbp_lev, grid_type, unstructured 53 use time_evol_mod, only: ecritpem, dt _pem53 use time_evol_mod, only: ecritpem, dt 54 54 55 55 implicit none … … 255 255 ! to writediagpem 256 256 !------------------------------------------------------------------------ 257 if (nom == firstnom) zitau = zitau + dt_pem257 if (nom == firstnom) zitau = zitau + 1 258 258 259 259 !-------------------------------------------------------- … … 600 600 use mod_grid_phy_lmdz, only: klon_glo, Grid1Dto2D_glo, nbp_lon, nbp_lat 601 601 use mod_grid_phy_lmdz, only: grid_type, unstructured 602 use time_evol_mod, only: ecritpem, dt _pem602 use time_evol_mod, only: ecritpem, dt 603 603 use iniwritesoil_mod, only: iniwritesoil 604 604 … … 747 747 if (name.eq.firstname) then 748 748 ! if we run across 'firstname', then it is a new time step 749 zitau = zitau + dt _pem749 zitau = zitau + dt 750 750 endif 751 751
Note: See TracChangeset
for help on using the changeset viewer.