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

Last change on this file since 3517 was 3517, checked in by jbclement, 10 days ago

PEM:
Committing the right correction in previous commit (r33516) would have been better...
JBC

File size: 6.4 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
[3498]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
[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
[3319]31use layering_mod,          only: layering_algo
[3349]32use info_PEM_mod,          only: iPCM, iPEM, nPCM, nPCM_ini
[2893]33
[3076]34implicit none
[3039]35
[3498]36real, intent(out) :: i_myear, n_myears ! Current simulated Martian year and maximum number of Martian years to be simulated
[3076]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
[2918]42!PEM parameters
[2893]43
[3039]44! #---------- Martian years parameters from launching script
[3096]45open(100,file = 'info_PEM.txt',status = 'old',form = 'formatted',iostat = ierr)
[3039]46if (ierr /= 0) then
[3096]47    write(*,*) 'Cannot find required file "info_PEM.txt"!'
[3039]48    write(*,*) 'It should be created by the launching script...'
49    stop
50else
[3349]51    read(100,*) i_myear, n_myears, convert_years, iPCM, iPEM, nPCM, nPCM_ini
[3039]52endif
53close(100)
[2918]54
[3159]55!#---------- Output parameters ----------#
[3082]56! Frequency of outputs for the PEM
[3214]57ecritpem = 1 ! Default value: every year
58call getin('ecritpem',ecritpem)
[3082]59
[3159]60!#---------- Orbital parameters ----------#
[3076]61evol_orbit_pem = .false.
62call getin('evol_orbit_pem',evol_orbit_pem)
[2918]63
[3516]64year_earth_bp_ini = 0.
[3076]65call getin('year_earth_bp_ini',year_earth_bp_ini)
[3498]66year_bp_ini = year_earth_bp_ini/convert_years
[2859]67
[3076]68var_obl = .true.
69call getin('var_obl',var_obl)
[3516]70write(*,*) 'Does obliquity vary?',var_obl
[2859]71
[3076]72var_ecc = .true.
73call getin('var_ecc',var_ecc)
[3516]74write(*,*) 'Does eccentricity vary?',var_ecc
[2963]75
[3076]76var_lsp = .true.
77call getin('var_lsp',var_lsp)
[3516]78write(*,*) 'Does Ls peri vary?',var_lsp
[2963]79
[3159]80!#---------- Stopping criteria parameters ----------#
[3076]81Max_iter_pem = 100000000
82call getin('Max_iter_pem',Max_iter_pem)
[3516]83write(*,*) 'Max_iter_pem =',Max_iter_pem
[2963]84
[3159]85h2o_ice_crit = 0.2
86call getin('h2o_ice_crit',h2o_ice_crit)
[3516]87write(*,*) 'h2o_ice_crit =',h2o_ice_crit
[2859]88
[3159]89co2_ice_crit = 0.2
90call getin('co2_ice_crit',co2_ice_crit)
[3516]91write(*,*) 'co2_ice_crit =',co2_ice_crit
[2893]92
[3076]93ps_criterion = 0.15
94call getin('ps_criterion',ps_criterion)
[3516]95write(*,*) 'ps_criterion =',ps_criterion
[2888]96
[3498]97dt = 1.
98call getin('dt',dt)
[2859]99
[3159]100!#---------- Subsurface parameters ----------#
[3076]101soil_pem = .true.
102call getin('soil_pem',soil_pem)
[2859]103
[3339]104adsorption_pem = .false.
[3076]105call getin('adsorption_pem',adsorption_pem)
[2888]106
[3076]107reg_thprop_dependp = .false.
108call getin('reg_thprop_dependp',reg_thprop_dependp)
[3490]109write(*,*) 'Thermal properties of the regolith vary with pressure ?', reg_thprop_dependp
[2963]110
[3076]111fluxgeo = 0.
112call getin('fluxgeo',fluxgeo)
113write(*,*) 'Flux Geothermal is set to',fluxgeo
[2894]114
[3076]115depth_breccia = 10.
116call getin('depth_breccia',depth_breccia)
117write(*,*) 'Depth of breccia is set to',depth_breccia
[2895]118
[3076]119depth_bedrock = 1000.
120call getin('depth_bedrock',depth_bedrock)
121write(*,*) 'Depth of bedrock is set to',depth_bedrock
[2895]122
[3076]123icetable_equilibrium = .true.
124call getin('icetable_equilibrium',icetable_equilibrium)
[3490]125write(*,*) 'Is the ice table computed at equilibrium?', icetable_equilibrium
[2961]126
[3076]127icetable_dynamic = .false.
128call getin('icetable_dynamic',icetable_dynamic)
[3490]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)
[3076]133endif
[3516]134if (icetable_equilibrium .and. icetable_dynamic) then
[3498]135    write(*,*) 'Ice table is asked to be computed both by the equilibrium and dynamic method.'
136    write(*,*) 'The dynamic method is then chosen.'
[3517]137    icetable_equilibrium = .false.
[3498]138endif
[2894]139
[3076]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
[2895]144
[3076]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
[2895]149
[3076]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
[2859]154
[3498]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,'
[3490]157    write(*,*) 'but you did not specify from which year to start.'
[3498]158    call abort_physic(modname,"evol_orbit_pem=.true. but year_bp_ini = 0",1)
[3076]159endif
160
[3159]161!#---------- Ice management parameters ----------#
[3256]162ini_huge_h2oice = 9200. ! kg.m-2 (= 10 m)
[3161]163call getin('ini_huge_h2oice',ini_huge_h2oice)
[3076]164
[3256]165inf_h2oice_threshold = 460. ! kg.m-2 (= 0.5 m)
[3159]166call getin('inf_h2oice_threshold',inf_h2oice_threshold)
167
[3161]168metam_h2oice = .false.
169call getin('metam_h2oice',metam_h2oice)
170
[3256]171metam_h2oice_threshold = 460. ! kg.m-2 (= 0.5 m)
[3159]172call getin('metam_h2oice_threshold',metam_h2oice_threshold)
173
[3161]174h2oice_flow = .true.
175call getin('h2oice_flow',h2oice_flow)
176
177metam_co2ice = .false.
178call getin('metam_co2ice',metam_co2ice)
179
[3256]180metam_co2ice_threshold = 16500. ! kg.m-2 (= 10 m)
[3159]181call getin('metam_co2ice_threshold',metam_co2ice_threshold)
182
[3161]183co2ice_flow = .true.
184call getin('co2ice_flow',co2ice_flow)
185
[3319]186!#---------- Layering parameters ----------#
187layering_algo = .false.
188call getin('layering',layering_algo)
189
[3076]190END SUBROUTINE conf_pem
191
[2859]192END MODULE conf_pem_mod
Note: See TracBrowser for help on using the repository browser.