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

Last change on this file since 3296 was 3256, checked in by jbclement, 9 months ago

PEM:
Adaptation of threshold values for ice management (in particular 'inf_h2oice_threshold') to more realistic values.
JBC

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