source: trunk/LMDZ.COMMON/libf/evolution/conf_pem.F90 @ 3152

Last change on this file since 3152 was 3149, checked in by jbclement, 19 months ago

PEM:

  • Simplification of the algorithm managing the stopping criteria;
  • Complete rework of the ice management in the PEM (H2O & CO2);

    Subroutines to evolve the H2O and CO2 ice are now in the same module "evol_ice_mod.F90".
    Tendencies are computed from the variation of "ice + frost" between the 2 PCM runs.
    Evolving ice in the PEM is now called 'h2o_ice' or 'co2_ice' (not anymore in 'qsurf' and free of 'water_reservoir').
    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).
    Simplification of the condition to compute the surface ice cover needed for the stopping criteria.
    Frost ('qsurf') is not evolved by the PEM and given back to the PCM.
    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').

  • Renaming of variables/subroutines for clarity;
  • Some cleanings throughout the code;
  • Small updates in files of the deftank.

JBC

File size: 5.2 KB
Line 
1MODULE conf_pem_mod
2
3!=======================================================================
4!
5! Purpose: Read the parameter for a PEM run in run_pem.def
6!
7! Author: RV, JBC
8!=======================================================================
9
10implicit none
11
12!=======================================================================
13contains
14!=======================================================================
15
16SUBROUTINE conf_pem(i_myear,n_myears)
17
18#ifdef CPP_IOIPSL
19    use IOIPSL,          only: getin
20#else
21    ! if not using IOIPSL, we still need to use (a local version of) getin
22    use ioipsl_getincom, only: getin
23#endif
24
25use time_evol_mod,    only: year_bp_ini, dt_pem, water_ice_criterion, co2_ice_criterion, ps_criterion, Max_iter_pem, &
26                          evol_orbit_pem, var_obl, var_ecc, var_lsp, convert_years
27use comsoil_h_pem,    only: soil_pem, fluxgeo, ini_h2o_bigreservoir, depth_breccia, depth_bedrock, reg_thprop_dependp
28use adsorption_mod,   only: adsorption_pem
29use glaciers_mod,     only: co2_ice_flow, h2o_ice_flow
30use ice_table_mod,    only: icetable_equilibrium, icetable_dynamic
31use time_phylmdz_mod, only: ecritphy
32
33implicit none
34
35integer, intent(out) :: i_myear, n_myears ! Current simulated Martian year and maximum number of Martian years to be simulated
36
37character(20), parameter :: modname ='conf_pem'
38integer                  :: ierr
39integer                  :: year_earth_bp_ini ! Initial year (in Earth years) of the simulation of the PEM defined in run.def
40
41!PEM parameters
42
43! #---------- Martian years parameters from launching script
44open(100,file = 'info_PEM.txt',status = 'old',form = 'formatted',iostat = ierr)
45if (ierr /= 0) then
46    write(*,*) 'Cannot find required file "info_PEM.txt"!'
47    write(*,*) 'It should be created by the launching script...'
48    stop
49else
50    read(100,*) i_myear, n_myears, convert_years
51endif
52close(100)
53
54! #---------- Output parameters
55! Frequency of outputs for the PEM
56ecritphy = 1 ! Default value: every year
57call getin('ecritpem',ecritphy)
58
59! #---------- Orbital parameters
60evol_orbit_pem = .false.
61call getin('evol_orbit_pem',evol_orbit_pem)
62
63year_bp_ini = 0.
64call getin('year_earth_bp_ini',year_earth_bp_ini)
65year_bp_ini = year_earth_bp_ini/convert_years
66
67var_obl = .true.
68call getin('var_obl',var_obl)
69write(*,*) 'Does obliquity vary ?',var_obl
70
71var_ecc = .true.
72call getin('var_ecc',var_ecc)
73write(*,*) 'Does eccentricity vary ?',var_ecc
74
75var_lsp = .true.
76call getin('var_lsp',var_lsp)
77write(*,*) 'Does Ls peri vary ?',var_lsp
78
79! #---------- Stopping criteria parameters
80Max_iter_pem = 100000000
81call getin('Max_iter_pem',Max_iter_pem)
82
83water_ice_criterion = 0.2
84call getin('water_ice_criterion',water_ice_criterion)
85
86co2_ice_criterion = 0.2
87call getin('co2_ice_criterion',co2_ice_criterion)
88
89ps_criterion = 0.15
90call getin('ps_criterion',ps_criterion)
91
92dt_pem = 1
93call getin('dt_pem', dt_pem)
94
95! #---------- Subsurface parameters
96soil_pem = .true.
97call getin('soil_pem',soil_pem)
98
99adsorption_pem = .true.
100call getin('adsorption_pem',adsorption_pem)
101
102co2_ice_flow = .true.
103call getin('co2_ice_flow',co2_ice_flow)
104
105h2o_ice_flow = .true.
106call getin('h2o_ice_flow',h2o_ice_flow)
107
108reg_thprop_dependp = .false.
109call getin('reg_thprop_dependp',reg_thprop_dependp)
110write(*,*)  'Thermal properties of the regolith vary with pressure ?', reg_thprop_dependp
111
112! #---------- Layering parameters
113fluxgeo = 0.
114call getin('fluxgeo',fluxgeo)
115write(*,*) 'Flux Geothermal is set to',fluxgeo
116
117depth_breccia = 10.
118call getin('depth_breccia',depth_breccia)
119write(*,*) 'Depth of breccia is set to',depth_breccia
120
121depth_bedrock = 1000.
122call getin('depth_bedrock',depth_bedrock)
123write(*,*) 'Depth of bedrock is set to',depth_bedrock
124
125icetable_equilibrium = .true.
126call getin('icetable_equilibrium',icetable_equilibrium)
127write(*,*)  'Is the ice table computed at equilibrium?', icetable_equilibrium
128
129icetable_dynamic = .false.
130call getin('icetable_dynamic',icetable_dynamic)
131write(*,*)  'Is the ice table computed with the dynamic method?', icetable_dynamic
132if ((.not. soil_pem) .and. ((icetable_equilibrium) .or. (icetable_dynamic))) then
133    write(*,*) 'Ice table  must be used when soil_pem = T'
134    call abort_physic(modname,"Ice table  must be used when soil_pem = T",1)
135endif
136
137if ((.not. soil_pem) .and. adsorption_pem) then
138    write(*,*) 'Adsorption must be used when soil_pem = T'
139    call abort_physic(modname,"Adsorption must be used when soil_pem = T",1)
140endif
141
142if ((.not. soil_pem) .and. (fluxgeo > 0.)) then
143    write(*,*) 'Soil is not activated but Flux Geo > 0.'
144    call abort_physic(modname,"Soil is not activated but Flux Geo > 0.",1)
145endif
146
147if ((.not. soil_pem) .and. reg_thprop_dependp) then
148    write(*,*) 'Regolith properties vary with Ps only when soil is set to true'
149    call abort_physic(modname,'Regolith properties vary with Ps only when soil is set to true',1)
150endif
151
152if (evol_orbit_pem .and. year_bp_ini == 0.) then
153    write(*,*)  'You want to follow the file obl_ecc_lsp.asc for changing orb parameters,'
154    write(*,*)  'but you did not specify from which year to start.'
155    call abort_physic(modname,"evol_orbit_pem=.true. but year_bp_ini=0",1)
156endif
157
158ini_h2o_bigreservoir = 1.e4
159call getin('ini_h2o_bigreservoir',ini_h2o_bigreservoir)
160
161END SUBROUTINE conf_pem
162
163END MODULE conf_pem_mod
Note: See TracBrowser for help on using the repository browser.