source: trunk/LMDZ.COMMON/libf/evolution/config_pem.F90 @ 3996

Last change on this file since 3996 was 3991, checked in by jbclement, 5 weeks ago

PEM:
Apply documentation template everywhere: standardized headers format with short description, separators between functions/subroutines, normalized code sections, aligned dependencies/arguments/variables declaration.
JBC

File size: 6.8 KB
Line 
1MODULE config_pem
2!-----------------------------------------------------------------------
3! NAME
4!     config_pem
5!
6! DESCRIPTION
7!     Read and apply parameters for a PEM run from run_pem.def.
8!
9! AUTHORS & DATE
10!     R. Vandemeulebrouck
11!     JB Clement, 2023-2025
12!
13! NOTES
14!
15!-----------------------------------------------------------------------
16
17! DECLARATION
18! -----------
19implicit none
20
21contains
22!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
23
24!=======================================================================
25SUBROUTINE read_rundef(i_myear,nyears_tot)
26!-----------------------------------------------------------------------
27! NAME
28!     read_rundef
29!
30! DESCRIPTION
31!     Read PEM runtime configuration from getin keys and launchPEM.info,
32!     then set module-scoped parameters accordingly.
33!
34! AUTHORS & DATE
35!     R. Vandemeulebrouck
36!     JB Clement, 2023-2025
37!
38! NOTES
39!
40!-----------------------------------------------------------------------
41
42! DEPENDENCIES
43! ------------
44#ifdef CPP_IOIPSL
45    use IOIPSL,          only: getin
46#else
47    ! if not using IOIPSL, we still need to use (a local version of) getin
48    use ioipsl_getincom, only: getin
49#endif
50use evolution,        only: year_bp_ini, dt, nyears_max, evol_orbit, var_obl, var_ecc, var_lsp, convert_years
51use stopping_crit,    only: h2oice_crit, co2ice_crit, ps_crit
52use soil,             only: do_soil, fluxgeo, h2oice_huge_ini, depth_breccia, depth_bedrock, reg_thprop_dependp
53use sorption,         only: do_sorption
54use glaciers,         only: h2oice_flow, co2ice_flow
55use surf_ice,         only: h2oice_cap_threshold
56use ice_table,        only: icetable_equilibrium, icetable_dynamic
57use layered_deposits, only: layering_algo, d_dust, impose_dust_ratio, dust2ice_ratio
58use info_pem,         only: iPCM, iPEM, nPCM, nPCM_ini
59use outputs,          only: output_rate
60
61! DECLARATION
62! -----------
63implicit none
64
65! ARGUMENTS
66! ---------
67real, intent(out) :: i_myear, nyears_tot ! Current simulated Martian year and maximum number of Martian years to be simulated
68
69! LOCAL VARIABLES
70! ---------------
71character(20), parameter :: modname ='read_rundef'
72integer                  :: ierr
73integer                  :: year_earth_bp_ini ! Initial year (in Earth years) of the simulation of the PEM defined in run.def
74
75! CODE
76! ----
77! #---------- Martian years parameters from launching script ----------#
78open(100,file = 'launchPEM.info',status = 'old',form = 'formatted',action = 'read',iostat = ierr)
79if (ierr /= 0) then
80    write(*,*) 'Cannot find required file "launchPEM.info"!'
81    write(*,*) 'It should be created by the launching script...'
82    stop
83else
84    read(100,*) i_myear, nyears_tot, convert_years, iPCM, iPEM, nPCM, nPCM_ini
85endif
86close(100)
87
88!#---------- Output parameters ----------#
89output_rate = 1 ! Default value: every year
90call getin('output_rate',output_rate)
91
92!#---------- Orbital parameters ----------#
93evol_orbit = .false.
94call getin('evol_orbit',evol_orbit)
95
96year_earth_bp_ini = 0.
97call getin('year_earth_bp_ini',year_earth_bp_ini)
98year_bp_ini = year_earth_bp_ini/convert_years
99
100var_obl = .true.
101call getin('var_obl',var_obl)
102write(*,*) 'Does obliquity vary?',var_obl
103
104var_ecc = .true.
105call getin('var_ecc',var_ecc)
106write(*,*) 'Does eccentricity vary?',var_ecc
107
108var_lsp = .true.
109call getin('var_lsp',var_lsp)
110write(*,*) 'Does Ls peri vary?',var_lsp
111
112!#---------- Stopping criteria parameters ----------#
113nyears_max = 100000000.
114call getin('nyears_max',nyears_max)
115write(*,*) 'nyears_max =',nyears_max
116
117h2oice_crit = 0.2
118call getin('h2oice_crit',h2oice_crit)
119write(*,*) 'h2oice_crit =',h2oice_crit
120
121co2ice_crit = 0.2
122call getin('co2ice_crit',co2ice_crit)
123write(*,*) 'co2ice_crit =',co2ice_crit
124
125ps_crit = 0.15
126call getin('ps_crit',ps_crit)
127write(*,*) 'ps_crit =',ps_crit
128
129dt = 1.
130call getin('dt',dt)
131
132!#---------- Subsurface parameters ----------#
133do_soil = .true.
134call getin('do_soil',do_soil)
135
136do_sorption = .false.
137call getin('do_sorption',do_sorption)
138
139reg_thprop_dependp = .false.
140call getin('reg_thprop_dependp',reg_thprop_dependp)
141write(*,*) 'Thermal properties of the regolith vary with pressure ?', reg_thprop_dependp
142
143fluxgeo = 0.
144call getin('fluxgeo',fluxgeo)
145write(*,*) 'Flux Geothermal is set to',fluxgeo
146
147depth_breccia = 10.
148call getin('depth_breccia',depth_breccia)
149write(*,*) 'Depth of breccia is set to',depth_breccia
150
151depth_bedrock = 1000.
152call getin('depth_bedrock',depth_bedrock)
153write(*,*) 'Depth of bedrock is set to',depth_bedrock
154
155icetable_equilibrium = .true.
156call getin('icetable_equilibrium',icetable_equilibrium)
157write(*,*) 'Is the ice table computed at equilibrium?', icetable_equilibrium
158
159icetable_dynamic = .false.
160call getin('icetable_dynamic',icetable_dynamic)
161write(*,*) 'Is the ice table computed with the dynamic method?', icetable_dynamic
162if ((.not. do_soil) .and. (icetable_equilibrium .or. icetable_dynamic)) then
163    write(*,*) 'Ice table (equilibrium or dynamic method) must be used when do_soil = T'
164    call abort_physic(modname,"Ice table must be used when do_soil = T",1)
165endif
166if (icetable_equilibrium .and. icetable_dynamic) then
167    write(*,*) 'Ice table is asked to be computed both by the equilibrium and dynamic method.'
168    write(*,*) 'The dynamic method is then chosen.'
169    icetable_equilibrium = .false.
170endif
171
172if ((.not. do_soil) .and. do_sorption) then
173    write(*,*) 'Adsorption must be used when do_soil = T'
174    call abort_physic(modname,"Adsorption must be used when do_soil = T",1)
175endif
176
177if ((.not. do_soil) .and. (fluxgeo > 0.)) then
178    write(*,*) 'Soil is not activated but Flux Geo > 0.'
179    call abort_physic(modname,"Soil is not activated but Flux Geo > 0.",1)
180endif
181
182if ((.not. do_soil) .and. reg_thprop_dependp) then
183    write(*,*) 'Regolith properties vary with Ps only when soil is set to true'
184    call abort_physic(modname,'Regolith properties vary with Ps only when soil is set to true',1)
185endif
186
187if (evol_orbit .and. abs(year_bp_ini) < 1.e-10) then
188    write(*,*) 'You want to follow the file "obl_ecc_lsp.asc" for changing orbital parameters,'
189    write(*,*) 'but you did not specify from which year to start.'
190    call abort_physic(modname,"evol_orbit=.true. but year_bp_ini = 0",1)
191endif
192
193!#---------- Ice management parameters ----------#
194h2oice_huge_ini = 9200. ! kg.m-2 (= 10 m)
195call getin('h2oice_huge_ini',h2oice_huge_ini)
196
197h2oice_cap_threshold = 460. ! kg.m-2 (= 0.5 m)
198call getin('h2oice_cap_threshold',h2oice_cap_threshold)
199
200h2oice_flow = .true.
201call getin('h2oice_flow',h2oice_flow)
202
203co2ice_flow = .true.
204call getin('co2ice_flow',co2ice_flow)
205
206!#---------- Layering parameters ----------#
207layering_algo = .false.
208call getin('layering',layering_algo)
209
210d_dust = 1.e-3 ! kg.m-2.y-1
211call getin('d_dust',d_dust)
212
213impose_dust_ratio = .false.
214call getin('impose_dust_ratio',impose_dust_ratio)
215
216dust2ice_ratio = 0.01
217call getin('dust2ice_ratio',dust2ice_ratio)
218
219END SUBROUTINE read_rundef
220!=======================================================================
221
222END MODULE config_pem
Note: See TracBrowser for help on using the repository browser.