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

Last change on this file since 3983 was 3983, checked in by jbclement, 7 days ago

PEM:

  • Removing completely the ice metamorphism computed by a threshold at the end of the PCM (which was commented).
  • Addition of a module "metamorphism" to compute the PCM frost at the PEM beginning and give it back to the PCM at the PEM end. The frost is considered as the ice given by the PCM "startfi.nc" which is above the yearly minimum. Thereby, metamorphism is performed through this operation.
  • Ice reservoirs representation in the PEM is modernized.

JBC

File size: 6.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, 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
30use ice_table_mod,         only: icetable_equilibrium, icetable_dynamic
31use layering_mod,          only: layering_algo, d_dust, impose_dust_ratio, dust2ice_ratio
32use info_PEM_mod,          only: iPCM, iPEM, nPCM, nPCM_ini
33
34implicit none
35
36real, 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 = 'launchPEM.info',status = 'old',form = 'formatted',action = 'read',iostat = ierr)
46if (ierr /= 0) then
47    write(*,*) 'Cannot find required file "launchPEM.info"!'
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_earth_bp_ini = 0.
65call getin('year_earth_bp_ini',year_earth_bp_ini)
66year_bp_ini = 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)
83write(*,*) 'Max_iter_pem =',Max_iter_pem
84
85h2o_ice_crit = 0.2
86call getin('h2o_ice_crit',h2o_ice_crit)
87write(*,*) 'h2o_ice_crit =',h2o_ice_crit
88
89co2_ice_crit = 0.2
90call getin('co2_ice_crit',co2_ice_crit)
91write(*,*) 'co2_ice_crit =',co2_ice_crit
92
93ps_criterion = 0.15
94call getin('ps_criterion',ps_criterion)
95write(*,*) 'ps_criterion =',ps_criterion
96
97dt = 1.
98call getin('dt',dt)
99
100!#---------- Subsurface parameters ----------#
101soil_pem = .true.
102call getin('soil_pem',soil_pem)
103
104adsorption_pem = .false.
105call getin('adsorption_pem',adsorption_pem)
106
107reg_thprop_dependp = .false.
108call getin('reg_thprop_dependp',reg_thprop_dependp)
109write(*,*) 'Thermal properties of the regolith vary with pressure ?', reg_thprop_dependp
110
111fluxgeo = 0.
112call getin('fluxgeo',fluxgeo)
113write(*,*) 'Flux Geothermal is set to',fluxgeo
114
115depth_breccia = 10.
116call getin('depth_breccia',depth_breccia)
117write(*,*) 'Depth of breccia is set to',depth_breccia
118
119depth_bedrock = 1000.
120call getin('depth_bedrock',depth_bedrock)
121write(*,*) 'Depth of bedrock is set to',depth_bedrock
122
123icetable_equilibrium = .true.
124call getin('icetable_equilibrium',icetable_equilibrium)
125write(*,*) 'Is the ice table computed at equilibrium?', icetable_equilibrium
126
127icetable_dynamic = .false.
128call getin('icetable_dynamic',icetable_dynamic)
129write(*,*) 'Is the ice table computed with the dynamic method?', icetable_dynamic
130if ((.not. soil_pem) .and. (icetable_equilibrium .or. icetable_dynamic)) then
131    write(*,*) 'Ice table (equilibrium or dynamic method) must be used when soil_pem = T'
132    call abort_physic(modname,"Ice table must be used when soil_pem = T",1)
133endif
134if (icetable_equilibrium .and. icetable_dynamic) then
135    write(*,*) 'Ice table is asked to be computed both by the equilibrium and dynamic method.'
136    write(*,*) 'The dynamic method is then chosen.'
137    icetable_equilibrium = .false.
138endif
139
140if ((.not. soil_pem) .and. adsorption_pem) then
141    write(*,*) 'Adsorption must be used when soil_pem = T'
142    call abort_physic(modname,"Adsorption must be used when soil_pem = T",1)
143endif
144
145if ((.not. soil_pem) .and. (fluxgeo > 0.)) then
146    write(*,*) 'Soil is not activated but Flux Geo > 0.'
147    call abort_physic(modname,"Soil is not activated but Flux Geo > 0.",1)
148endif
149
150if ((.not. soil_pem) .and. reg_thprop_dependp) then
151    write(*,*) 'Regolith properties vary with Ps only when soil is set to true'
152    call abort_physic(modname,'Regolith properties vary with Ps only when soil is set to true',1)
153endif
154
155if (evol_orbit_pem .and. abs(year_bp_ini) < 1.e-10) then
156    write(*,*) 'You want to follow the file "obl_ecc_lsp.asc" for changing orbital parameters,'
157    write(*,*) 'but you did not specify from which year to start.'
158    call abort_physic(modname,"evol_orbit_pem=.true. but year_bp_ini = 0",1)
159endif
160
161!#---------- Ice management parameters ----------#
162ini_huge_h2oice = 9200. ! kg.m-2 (= 10 m)
163call getin('ini_huge_h2oice',ini_huge_h2oice)
164
165inf_h2oice_threshold = 460. ! kg.m-2 (= 0.5 m)
166call getin('inf_h2oice_threshold',inf_h2oice_threshold)
167
168h2oice_flow = .true.
169call getin('h2oice_flow',h2oice_flow)
170
171co2ice_flow = .true.
172call getin('co2ice_flow',co2ice_flow)
173
174!#---------- Layering parameters ----------#
175layering_algo = .false.
176call getin('layering',layering_algo)
177
178d_dust = 1.e-3 ! kg.m-2.y-1
179call getin('d_dust',d_dust)
180
181impose_dust_ratio = .false.
182call getin('impose_dust_ratio',impose_dust_ratio)
183
184dust2ice_ratio = 0.01
185call getin('dust2ice_ratio',dust2ice_ratio)
186
187END SUBROUTINE conf_pem
188
189END MODULE conf_pem_mod
Note: See TracBrowser for help on using the repository browser.