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

Last change on this file since 3082 was 3082, checked in by jbclement, 16 months ago

PEM:

  • Correction of a bug in the initialization of constants. The correct modules are now used: 'comcstfi_h' (and no longer 'comconst_mod'!) in the general case and 'comcstfi_mod' in the case of generic model;
  • Addition of the variable 'ecritpem' in "run_PEM.def" to set the frequency of outputs in the "diagfi.nc". By default, 'ecritpem = 1' which means there is one output at each PEM year.

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, water_reservoir_nom, depth_breccia, depth_bedrock, reg_thprop_dependp
28use adsorption_mod,   only: adsorption_pem
29use glaciers_mod,     only: co2glaciersflow, h2oglaciersflow
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 = 'tmp_PEMyears.txt',status = 'old',form = 'formatted',iostat = ierr)
45if (ierr /= 0) then
46    write(*,*) 'Cannot find required file "tmp_PEMyears.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 excentricity 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
102co2glaciersflow = .true.
103call getin('co2glaciersflow',co2glaciersflow)
104
105h2oglaciersflow = .true.
106call getin('h2oglaciersflow',h2oglaciersflow)
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
158water_reservoir_nom = 1.e4
159call getin('water_reservoir_nom',water_reservoir_nom)
160
161END SUBROUTINE conf_pem
162
163END MODULE conf_pem_mod
Note: See TracBrowser for help on using the repository browser.