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

Last change on this file since 3068 was 3039, checked in by jbclement, 2 years ago

Mars PEM:
Big cleaning of main program pem.F90 (indentation, declarations, comments, simplification of conditions/loops, etc).
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
[2864]10IMPLICIT NONE
[2859]11
[2864]12CONTAINS
[2859]13
[3039]14  SUBROUTINE conf_pem(i_myear,n_myears)
[2859]15
[2864]16#ifdef CPP_IOIPSL
17  use IOIPSL, only: getin
18#else
19  ! if not using IOIPSL, we still need to use (a local version of) getin
20  use ioipsl_getincom, only: getin
21#endif
22 
[3039]23  use time_evol_mod,  only: year_bp_ini, dt_pem, water_ice_criterion, co2_ice_criterion, ps_criterion, Max_iter_pem, &
24                            evol_orbit_pem, var_obl, var_ecc, var_lsp, convert_years
25  use comsoil_h_pem,  only: soil_pem, fluxgeo, water_reservoir_nom, depth_breccia, depth_bedrock, reg_thprop_dependp
26  use adsorption_mod, only: adsorption_pem
27  use glaciers_mod,   only: co2glaciersflow, h2oglaciersflow
28  use ice_table_mod,  only: icetable_equilibrium, icetable_dynamic
[2918]29
[3039]30  integer, intent(out) :: i_myear, n_myears ! Current simulated Martian year and maximum number of Martian years to be simulated
[2893]31
[3039]32  character(len=20), parameter :: modname ='conf_pem'
33  integer                      :: ierr
34  integer                      :: year_earth_bp_ini ! Initial year (in Earth years) of the simulation of the PEM defined in run.def
35
[2918]36!PEM parameters
[2893]37
[3039]38! #---------- Martian years parameters from launching script
39open(100,file = 'tmp_PEMyears.txt',status = 'old',form = 'formatted',iostat = ierr)
40if (ierr /= 0) then
41    write(*,*) 'Cannot find required file "tmp_PEMyears.txt"!'
42    write(*,*) 'It should be created by the launching script...'
43    stop
44else
45    read(100,*) i_myear, n_myears, convert_years
46endif
47close(100)
[2918]48
[3039]49! #---------- Orbital parameters
[2963]50  evol_orbit_pem=.false.
[3039]51  call getin('evol_orbit_pem',evol_orbit_pem)
[2918]52
[3039]53  year_bp_ini = 0.
54  call getin('year_earth_bp_ini',year_earth_bp_ini)
55  year_bp_ini = year_earth_bp_ini/convert_years
[2859]56
[2963]57  var_obl = .true.
[3039]58  call getin('var_obl',var_obl)
59  write(*,*) 'Does obliquity vary ?',var_obl
[2859]60
[3039]61  var_ecc = .true.
62  call getin('var_ecc',var_ecc)
63  write(*,*) 'Does excentricity vary ?',var_ecc
[2963]64
65  var_lsp = .true.
[3039]66  call getin('var_lsp',var_lsp)
67  write(*,*) 'Does Ls peri vary ?',var_lsp
[2963]68
[3039]69! #---------- Stopping criteria parameters
70  Max_iter_pem=100000000
71  call getin('Max_iter_pem', Max_iter_pem)
[2963]72
[2893]73  water_ice_criterion=0.2
[3039]74  call getin('water_ice_criterion', water_ice_criterion)
[2859]75
[2893]76  co2_ice_criterion=0.2
[3039]77  call getin('co2_ice_criterion', co2_ice_criterion)
[2893]78
[2888]79  ps_criterion = 0.15
[3039]80  call getin('ps_criterion',ps_criterion)
[2888]81
[2963]82  dt_pem=1
[3039]83  call getin('dt_pem', dt_pem)
[2859]84
[3039]85! #---------- Subsurface parameters
[2864]86  soil_pem=.true.
[3039]87  call getin('soil_pem', soil_pem)
[2859]88
[2888]89  adsorption_pem = .true.
[3039]90  call getin('adsorption_pem',adsorption_pem)
[2888]91
[2963]92  co2glaciersflow = .true.
[3039]93  call getin('co2glaciersflow', co2glaciersflow)
[2963]94
[2995]95  h2oglaciersflow = .true.
[3039]96  call getin('h2oglaciersflow', h2oglaciersflow)
[2995]97
[2963]98  reg_thprop_dependp = .false.
[3039]99  call getin('reg_thprop_dependp',reg_thprop_dependp)
100  write(*,*)  'Thermal properties of the regolith vary with pressure ?', reg_thprop_dependp
[2963]101
[3039]102! #---------- Layering parameters
[2888]103  fluxgeo = 0.
[3039]104  call getin('fluxgeo',fluxgeo)
105  write(*,*) 'Flux Geothermal is set to',fluxgeo
[2895]106   
107  depth_breccia   = 10.
[3039]108  call getin('depth_breccia',depth_breccia)
109  write(*,*) 'Depth of breccia is set to',depth_breccia
[2894]110
[2895]111  depth_bedrock   = 1000.
[3039]112  call getin('depth_bedrock',depth_bedrock)
113  write(*,*) 'Depth of bedrock is set to',depth_bedrock
[2895]114
[2961]115   icetable_equilibrium = .true.
[3039]116   call getin('icetable_equilibrium',icetable_equilibrium)
117   write(*,*)  'Is the ice table computed at equilibrium?', icetable_equilibrium
[2895]118
[2961]119   icetable_dynamic = .false.
[3039]120   call getin('icetable_dynamic',icetable_dynamic)
121   write(*,*)  'Is the ice table computed with the dynamic method?', icetable_dynamic
[2982]122  if ((.not.soil_pem).and.((icetable_equilibrium).or.(icetable_dynamic))) then
[3039]123       write(*,*) 'Ice table  must be used when soil_pem = T'
[2961]124       call abort_physic(modname,"Ice table  must be used when soil_pem = T",1)
125  endif
126
[2982]127  if ((.not.soil_pem).and.adsorption_pem) then
[3039]128       write(*,*) 'Adsorption must be used when soil_pem = T'
[2888]129       call abort_physic(modname,"Adsorption must be used when soil_pem = T",1)
[2893]130  endif
[2888]131 
[2982]132  if ((.not.soil_pem).and.(fluxgeo.gt.0.)) then
[3039]133       write(*,*) 'Soil is not activated but Flux Geo > 0.'
[2895]134       call abort_physic(modname,"Soil is not activated but Flux Geo > 0.",1)
[2893]135  endif
[2895]136 
[2982]137  if ((.not.soil_pem).and.reg_thprop_dependp) then
[3039]138     write(*,*) 'Regolith properties vary with Ps only when soil is set to true'
[2895]139     call abort_physic(modname,'Regolith properties vary with Ps only when soil is set to true',1)
140  endif
[2894]141
[3039]142  if (evol_orbit_pem .and. year_bp_ini == 0.) then
143     write(*,*)  'You want to follow the file obl_ecc_lsp.asc for changing orb parameters,'
144     write(*,*)  'but you did not specify from which year to start.'
[2895]145     call abort_physic(modname,"evol_orbit_pem=.true. but year_bp_ini=0",1)
146  endif
147
148  water_reservoir_nom = 1e4
[3039]149  call getin('water_reservoir_nom',water_reservoir_nom)
[2895]150
[2864]151  END SUBROUTINE conf_pem
[2859]152
153END MODULE conf_pem_mod
Note: See TracBrowser for help on using the repository browser.