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

Last change on this file since 3493 was 3490, checked in by jbclement, 2 weeks ago

PEM:
Correction of initialization of 'icetable_dynamic' and the management of the flag.
JBC

File size: 6.0 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, h2o_ice_crit, co2_ice_crit, ps_criterion, Max_iter_pem, &
26                          evol_orbit_pem, var_obl, var_ecc, var_lsp, convert_years, ecritpem
27use comsoil_h_pem,         only: soil_pem, fluxgeo, ini_huge_h2oice, depth_breccia, depth_bedrock, reg_thprop_dependp
28use adsorption_mod,        only: adsorption_pem
29use glaciers_mod,          only: h2oice_flow, co2ice_flow, inf_h2oice_threshold, metam_co2ice_threshold, metam_h2oice_threshold, metam_h2oice, metam_co2ice
30use ice_table_mod,         only: icetable_equilibrium, icetable_dynamic
31use layering_mod,          only: layering_algo
32use info_PEM_mod,          only: iPCM, iPEM, nPCM, nPCM_ini
33
34implicit none
35
36integer, intent(out) :: i_myear, n_myears ! Current simulated Martian year and maximum number of Martian years to be simulated
37
38character(20), parameter :: modname ='conf_pem'
39integer                  :: ierr
40integer                  :: year_earth_bp_ini ! Initial year (in Earth years) of the simulation of the PEM defined in run.def
41
42!PEM parameters
43
44! #---------- Martian years parameters from launching script
45open(100,file = 'info_PEM.txt',status = 'old',form = 'formatted',iostat = ierr)
46if (ierr /= 0) then
47    write(*,*) 'Cannot find required file "info_PEM.txt"!'
48    write(*,*) 'It should be created by the launching script...'
49    stop
50else
51    read(100,*) i_myear, n_myears, convert_years, iPCM, iPEM, nPCM, nPCM_ini
52endif
53close(100)
54
55!#---------- Output parameters ----------#
56! Frequency of outputs for the PEM
57ecritpem = 1 ! Default value: every year
58call getin('ecritpem',ecritpem)
59
60!#---------- Orbital parameters ----------#
61evol_orbit_pem = .false.
62call getin('evol_orbit_pem',evol_orbit_pem)
63
64year_bp_ini = 0.
65call getin('year_earth_bp_ini',year_earth_bp_ini)
66year_bp_ini = int(year_earth_bp_ini/convert_years)
67
68var_obl = .true.
69call getin('var_obl',var_obl)
70write(*,*) 'Does obliquity vary ?',var_obl
71
72var_ecc = .true.
73call getin('var_ecc',var_ecc)
74write(*,*) 'Does eccentricity vary ?',var_ecc
75
76var_lsp = .true.
77call getin('var_lsp',var_lsp)
78write(*,*) 'Does Ls peri vary ?',var_lsp
79
80!#---------- Stopping criteria parameters ----------#
81Max_iter_pem = 100000000
82call getin('Max_iter_pem',Max_iter_pem)
83
84h2o_ice_crit = 0.2
85call getin('h2o_ice_crit',h2o_ice_crit)
86
87co2_ice_crit = 0.2
88call getin('co2_ice_crit',co2_ice_crit)
89
90ps_criterion = 0.15
91call getin('ps_criterion',ps_criterion)
92
93dt_pem = 1
94call getin('dt_pem', dt_pem)
95
96!#---------- Subsurface parameters ----------#
97soil_pem = .true.
98call getin('soil_pem',soil_pem)
99
100adsorption_pem = .false.
101call getin('adsorption_pem',adsorption_pem)
102
103reg_thprop_dependp = .false.
104call getin('reg_thprop_dependp',reg_thprop_dependp)
105write(*,*) 'Thermal properties of the regolith vary with pressure ?', reg_thprop_dependp
106
107fluxgeo = 0.
108call getin('fluxgeo',fluxgeo)
109write(*,*) 'Flux Geothermal is set to',fluxgeo
110
111depth_breccia = 10.
112call getin('depth_breccia',depth_breccia)
113write(*,*) 'Depth of breccia is set to',depth_breccia
114
115depth_bedrock = 1000.
116call getin('depth_bedrock',depth_bedrock)
117write(*,*) 'Depth of bedrock is set to',depth_bedrock
118
119icetable_equilibrium = .true.
120call getin('icetable_equilibrium',icetable_equilibrium)
121write(*,*) 'Is the ice table computed at equilibrium?', icetable_equilibrium
122
123icetable_dynamic = .false.
124call getin('icetable_dynamic',icetable_dynamic)
125write(*,*) 'Is the ice table computed with the dynamic method?', icetable_dynamic
126if ((.not. soil_pem) .and. (icetable_equilibrium .or. icetable_dynamic)) then
127    write(*,*) 'Ice table (equilibrium or dynamic method) must be used when soil_pem = T'
128    call abort_physic(modname,"Ice table must be used when soil_pem = T",1)
129endif
130
131if ((.not. soil_pem) .and. adsorption_pem) then
132    write(*,*) 'Adsorption must be used when soil_pem = T'
133    call abort_physic(modname,"Adsorption must be used when soil_pem = T",1)
134endif
135
136if ((.not. soil_pem) .and. (fluxgeo > 0.)) then
137    write(*,*) 'Soil is not activated but Flux Geo > 0.'
138    call abort_physic(modname,"Soil is not activated but Flux Geo > 0.",1)
139endif
140
141if ((.not. soil_pem) .and. reg_thprop_dependp) then
142    write(*,*) 'Regolith properties vary with Ps only when soil is set to true'
143    call abort_physic(modname,'Regolith properties vary with Ps only when soil is set to true',1)
144endif
145
146if (evol_orbit_pem .and. year_bp_ini == 0.) then
147    write(*,*) 'You want to follow the file obl_ecc_lsp.asc for changing orb parameters,'
148    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)
150endif
151
152!#---------- Ice management parameters ----------#
153ini_huge_h2oice = 9200. ! kg.m-2 (= 10 m)
154call getin('ini_huge_h2oice',ini_huge_h2oice)
155
156inf_h2oice_threshold = 460. ! kg.m-2 (= 0.5 m)
157call getin('inf_h2oice_threshold',inf_h2oice_threshold)
158
159metam_h2oice = .false.
160call getin('metam_h2oice',metam_h2oice)
161
162metam_h2oice_threshold = 460. ! kg.m-2 (= 0.5 m)
163call getin('metam_h2oice_threshold',metam_h2oice_threshold)
164
165h2oice_flow = .true.
166call getin('h2oice_flow',h2oice_flow)
167
168metam_co2ice = .false.
169call getin('metam_co2ice',metam_co2ice)
170
171metam_co2ice_threshold = 16500. ! kg.m-2 (= 10 m)
172call getin('metam_co2ice_threshold',metam_co2ice_threshold)
173
174co2ice_flow = .true.
175call getin('co2ice_flow',co2ice_flow)
176
177!#---------- Layering parameters ----------#
178layering_algo = .false.
179call getin('layering',layering_algo)
180
181END SUBROUTINE conf_pem
182
183END MODULE conf_pem_mod
Note: See TracBrowser for help on using the repository browser.