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

Last change on this file since 3078 was 3076, checked in by jbclement, 2 years ago

PEM:
Big cleaning/improvements of the PEM:

  • Conversion of "abort_pem.F" and "soil_settings_PEM.F" into Fortran 90;
  • Transformation of every PEM subroutines into module;
  • Rewriting of many subroutines with modern Fortran syntax;
  • Correction of a bug in "pem.F90" when calling 'recomp_tend_co2_slope'. The arguments were given in disorder and emissivity was missing;
  • Update of "launch_pem.sh" in deftank.

JBC

File size: 5.0 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
[3076]25use time_evol_mod,  only: year_bp_ini, dt_pem, water_ice_criterion, co2_ice_criterion, ps_criterion, Max_iter_pem, &
26                          evol_orbit_pem, var_obl, var_ecc, var_lsp, convert_years
27use comsoil_h_pem,  only: soil_pem, fluxgeo, water_reservoir_nom, depth_breccia, depth_bedrock, reg_thprop_dependp
28use adsorption_mod, only: adsorption_pem
29use glaciers_mod,   only: co2glaciersflow, h2oglaciersflow
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
43open(100,file = 'tmp_PEMyears.txt',status = 'old',form = 'formatted',iostat = ierr)
44if (ierr /= 0) then
45    write(*,*) 'Cannot find required file "tmp_PEMyears.txt"!'
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
[3039]53! #---------- Orbital parameters
[3076]54evol_orbit_pem = .false.
55call getin('evol_orbit_pem',evol_orbit_pem)
[2918]56
[3076]57year_bp_ini = 0.
58call getin('year_earth_bp_ini',year_earth_bp_ini)
59year_bp_ini = year_earth_bp_ini/convert_years
[2859]60
[3076]61var_obl = .true.
62call getin('var_obl',var_obl)
63write(*,*) 'Does obliquity vary ?',var_obl
[2859]64
[3076]65var_ecc = .true.
66call getin('var_ecc',var_ecc)
67write(*,*) 'Does excentricity vary ?',var_ecc
[2963]68
[3076]69var_lsp = .true.
70call getin('var_lsp',var_lsp)
71write(*,*) 'Does Ls peri vary ?',var_lsp
[2963]72
[3039]73! #---------- Stopping criteria parameters
[3076]74Max_iter_pem = 100000000
75call getin('Max_iter_pem',Max_iter_pem)
[2963]76
[3076]77water_ice_criterion = 0.2
78call getin('water_ice_criterion',water_ice_criterion)
[2859]79
[3076]80co2_ice_criterion = 0.2
81call getin('co2_ice_criterion',co2_ice_criterion)
[2893]82
[3076]83ps_criterion = 0.15
84call getin('ps_criterion',ps_criterion)
[2888]85
[3076]86dt_pem = 1
87call getin('dt_pem', dt_pem)
[2859]88
[3039]89! #---------- Subsurface parameters
[3076]90soil_pem = .true.
91call getin('soil_pem',soil_pem)
[2859]92
[3076]93adsorption_pem = .true.
94call getin('adsorption_pem',adsorption_pem)
[2888]95
[3076]96co2glaciersflow = .true.
97call getin('co2glaciersflow',co2glaciersflow)
[2963]98
[3076]99h2oglaciersflow = .true.
100call getin('h2oglaciersflow',h2oglaciersflow)
[2995]101
[3076]102reg_thprop_dependp = .false.
103call getin('reg_thprop_dependp',reg_thprop_dependp)
104write(*,*)  'Thermal properties of the regolith vary with pressure ?', reg_thprop_dependp
[2963]105
[3039]106! #---------- Layering parameters
[3076]107fluxgeo = 0.
108call getin('fluxgeo',fluxgeo)
109write(*,*) 'Flux Geothermal is set to',fluxgeo
[2894]110
[3076]111depth_breccia = 10.
112call getin('depth_breccia',depth_breccia)
113write(*,*) 'Depth of breccia is set to',depth_breccia
[2895]114
[3076]115depth_bedrock = 1000.
116call getin('depth_bedrock',depth_bedrock)
117write(*,*) 'Depth of bedrock is set to',depth_bedrock
[2895]118
[3076]119icetable_equilibrium = .true.
120call getin('icetable_equilibrium',icetable_equilibrium)
121write(*,*)  'Is the ice table computed at equilibrium?', icetable_equilibrium
[2961]122
[3076]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  must be used when soil_pem = T'
128    call abort_physic(modname,"Ice table  must be used when soil_pem = T",1)
129endif
[2894]130
[3076]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
[2895]135
[3076]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
[2895]140
[3076]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
[2859]145
[3076]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
152water_reservoir_nom = 1.e4
153call getin('water_reservoir_nom',water_reservoir_nom)
154
155END SUBROUTINE conf_pem
156
[2859]157END MODULE conf_pem_mod
Note: See TracBrowser for help on using the repository browser.