source: branches/publications/ORCHIDEE_CAN_r3069/src_parameters/constantes_soil.f90

Last change on this file was 2572, checked in by sebastiaan.luyssaert, 10 years ago

DEV: trunk changes up to and including src_parameters/* of r2203

File size: 18.1 KB
Line 
1! =================================================================================================================================
2! MODULE        : constantes_soil
3!
4! CONTACT       : orchidee-help _at_ ipsl.jussieu.fr
5!
6! LICENCE       : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF         "constantes_soil" module contains subroutine to initialize the parameters related to soil and hydrology.
10!!
11!!\n DESCRIPTION : "constantes_soil" module contains subroutine to initialize the parameters related to soil and hydrology.
12!!                 This module alos USE constates_soil and can therfor be used to acces the subroutines and the constantes.
13!!                 The constantes declarations can also be used seperatly with "USE constantes_soil_var".
14!!
15!! RECENT CHANGE(S):
16!!
17!! REFERENCE(S) :
18!!
19!! SVN          :
20!! $HeadURL: $
21!! $Date: $
22!! $Revision: $
23!! \n
24!_ ================================================================================================================================
25
26MODULE constantes_soil
27
28  USE constantes_soil_var
29  USE constantes
30  USE ioipsl_para 
31
32  IMPLICIT NONE
33
34CONTAINS
35
36 
37!! ================================================================================================================================
38!! SUBROUTINE   : config_soil_parameters
39!!
40!>\BRIEF        This subroutine reads in the configuration file all the parameters related to soil and hydrology.
41!!
42!! DESCRIPTION  : None
43!!
44!! RECENT CHANGE(S): None
45!!
46!! MAIN OUTPUT VARIABLE(S):
47!!
48!! REFERENCE(S) :
49!!
50!! FLOWCHART    :
51!! \n
52!_ ================================================================================================================================
53
54  SUBROUTINE config_soil_parameters(active_flags, impose_param)
55
56    USE ioipsl
57
58    IMPLICIT NONE
59
60    !! 0. Variables and parameters declaration
61
62    !! 0.1 Input variables
63
64    TYPE(control_type), INTENT(in) :: active_flags            !! What parts of the code are activated ? (true/false) 
65    LOGICAL                        :: impose_param            !! Flag for imposing parameters in run.def
66    !! 0.4 Local variables
67
68    INTEGER(i_std), PARAMETER      :: error_level = 3         !! Switch to 2 to turn fatal errors into warnings.(1-3, unitless)
69    LOGICAL                        :: ok_freeze               !! Local variable used to set default values for all flags 
70                                                              !! controling the soil freezing scheme
71    LOGICAL, SAVE                  :: first_call = .TRUE.     !! To keep first call trace (true/false)
72    !$OMP THREADPRIVATE(first_call)
73
74
75    !_ ================================================================================================================================
76
77    IF ( first_call ) THEN
78
79       !Config Key   = THERMOSOIL_NBLEV
80       !Config Desc  = Number of soil level
81       !Config If    =
82       !Config Def   = 7
83       !Config Help  =
84       !Config Units = (-)
85       ngrnd=7
86       CALL getin_p("THERMOSOIL_NBLEV",ngrnd)
87
88
89       ! Following initializations are only done for option impose_param
90       IF ( active_flags%ok_sechiba .AND. impose_param ) THEN
91
92          !Config Key   = DRY_SOIL_HEAT_CAPACITY
93          !Config Desc  = Dry soil Heat capacity of soils
94          !Config If    = OK_SECHIBA
95          !Config Def   = 1.80e+6
96          !Config Help  = Values taken from : PIELKE,'MESOSCALE METEOROLOGICAL MODELING',P.384.
97          !Config Units = [J.m^{-3}.K^{-1}]
98          CALL getin_p("DRY_SOIL_HEAT_CAPACITY",so_capa_dry)
99
100          !! Check parameter value (correct range)
101          IF ( so_capa_dry <= zero ) THEN
102             CALL ipslerr_p(error_level, "config_soil_parameters.", &
103                  &     "Wrong parameter value for DRY_SOIL_HEAT_CAPACITY.", &
104                  &     "This parameter should be positive. ", &
105                  &     "Please, check parameter value in run.def. ")
106          END IF
107
108
109          !Config Key   = DRY_SOIL_HEAT_COND
110          !Config Desc  = Dry soil Thermal Conductivity of soils
111          !Config If    = OK_SECHIBA
112          !Config Def   = 0.40
113          !Config Help  = Values taken from : PIELKE,'MESOSCALE METEOROLOGICAL MODELING',P.384.
114          !Config Units = [W.m^{-2}.K^{-1}]
115          CALL getin_p("DRY_SOIL_HEAT_COND",so_cond_dry)
116
117          !! Check parameter value (correct range)
118          IF ( so_cond_dry <= zero ) THEN
119             CALL ipslerr_p(error_level, "config_soil_parameters.", &
120                  &     "Wrong parameter value for DRY_SOIL_HEAT_COND.", &
121                  &     "This parameter should be positive. ", &
122                  &     "Please, check parameter value in run.def. ")
123          END IF
124
125
126          !Config Key   = WET_SOIL_HEAT_CAPACITY
127          !Config Desc  = Wet soil Heat capacity of soils
128          !Config If    = OK_SECHIBA
129          !Config Def   = 3.03e+6
130          !Config Help  =
131          !Config Units = [J.m^{-3}.K^{-1}]
132          CALL getin_p("WET_SOIL_HEAT_CAPACITY",so_capa_wet)
133
134          !! Check parameter value (correct range)
135          IF ( so_capa_wet <= zero ) THEN
136             CALL ipslerr_p(error_level, "config_soil_parameters.", &
137                  &     "Wrong parameter value for WET_SOIL_HEAT_CAPACITY.", &
138                  &     "This parameter should be positive. ", &
139                  &     "Please, check parameter value in run.def. ")
140          END IF
141
142
143          !Config Key   = WET_SOIL_HEAT_COND
144          !Config Desc  = Wet soil Thermal Conductivity of soils
145          !Config If    = OK_SECHIBA
146          !Config Def   = 1.89
147          !Config Help  =
148          !Config Units = [W.m^{-2}.K^{-1}]
149          CALL getin_p("WET_SOIL_HEAT_COND",so_cond_wet)
150
151          !! Check parameter value (correct range)
152          IF ( so_cond_wet <= zero ) THEN
153             CALL ipslerr_p(error_level, "config_soil_parameters.", &
154                  &     "Wrong parameter value for WET_SOIL_HEAT_COND.", &
155                  &     "This parameter should be positive. ", &
156                  &     "Please, check parameter value in run.def. ")
157          END IF
158
159
160          !Config Key   = SNOW_HEAT_COND
161          !Config Desc  = Thermal Conductivity of snow
162          !Config If    = OK_SECHIBA 
163          !Config Def   = 0.3
164          !Config Help  =
165          !Config Units = [W.m^{-2}.K^{-1}]
166          CALL getin_p("SNOW_HEAT_COND",sn_cond)
167
168          !! Check
169          IF ( sn_cond <= zero ) THEN
170             CALL ipslerr_p(error_level, "config_soil_parameters.", &
171                  &     "Wrong parameter value for SNOW_HEAT_COND.", &
172                  &     "This parameter should be positive. ", &
173                  &     "Please, check parameter value in run.def. ")
174          END IF
175
176
177          !Config Key   = SNOW_DENSITY
178          !Config Desc  = Snow density for the soil thermodynamics
179          !Config If    = OK_SECHIBA
180          !Config Def   = 330.0
181          !Config Help  =
182          !Config Units = [-]
183          CALL getin_p("SNOW_DENSITY",sn_dens)
184
185          !! Check parameter value (correct range)
186          IF ( sn_dens <= zero ) THEN
187             CALL ipslerr_p(error_level, "config_soil_parameters.", &
188                  &     "Wrong parameter value for SNOW_DENSITY.", &
189                  &     "This parameter should be positive. ", &
190                  &     "Please, check parameter value in run.def. ")
191          END IF
192
193
194          !! Calculation of snow capacity
195          !! If sn_dens is redefined by the user, sn_capa needs to be reset
196          sn_capa = 2100.0_r_std*sn_dens
197
198
199          !Config Key   = NOBIO_WATER_CAPAC_VOLUMETRI
200          !Config Desc  =
201          !Config If    = OK_SECHIBA and .NOT.(HYDROL_CWRR)
202          !Config Def   = 150.
203          !Config Help  =
204          !Config Units = [s/m^2]
205          CALL getin_p('NOBIO_WATER_CAPAC_VOLUMETRI',mx_eau_nobio)
206
207          !! Check parameter value (correct range)
208          IF ( mx_eau_nobio <= zero ) THEN
209             CALL ipslerr_p(error_level, "config_soil_parameters.", &
210                  &     "Wrong parameter value for NOBIO_WATER_CAPAC_VOLUMETRI.", &
211                  &     "This parameter should be positive. ", &
212                  &     "Please, check parameter value in run.def. ")
213          END IF
214
215
216          !Config Key   = SECHIBA_QSINT
217          !Config Desc  = Interception reservoir coefficient
218          !Config If    = OK_SECHIBA
219          !Config Def   = 0.1
220          !Config Help  = Transforms leaf area index into size of interception reservoir
221          !Config         for slowproc_derivvar or stomate
222          !Config Units = [m]
223          CALL getin_p('SECHIBA_QSINT',qsintcst)
224
225          !! Check parameter value (correct range)
226          IF ( qsintcst <= zero ) THEN
227             CALL ipslerr_p(error_level, "config_soil_parameters.", &
228                  &     "Wrong parameter value for SECHIBA_QSINT.", &
229                  &     "This parameter should be positive. ", &
230                  &     "Please, check parameter value in run.def. ")
231          END IF
232
233
234          IF ( .NOT.(active_flags%hydrol_cwrr) ) THEN
235
236             !Config Key   = CHOISNEL_DIFF_MIN
237             !Config Desc  = Diffusion constant for the slow regime
238             !Config If    = OK_SECHIBA and .NOT.(HYDROL_CWRR)
239             !Config Def   = 0.001
240             !Config Help  =
241             !Config Units = [kg/m^2/dt]
242             CALL getin_p('CHOISNEL_DIFF_MIN',min_drain)
243
244             !! Check parameter value (correct range)
245             IF ( min_drain <= zero ) THEN
246                CALL ipslerr_p(error_level, "config_soil_parameters.", &
247                     &     "Wrong parameter value for CHOISNEL_DIFF_MIN.", &
248                     &     "This parameter should be positive. ", &
249                     &     "Please, check parameter value in run.def. ")
250             END IF
251
252
253             !Config Key   = CHOISNEL_DIFF_MAX
254             !Config Desc  = Diffusion constant for the fast regime
255             !Config If    = OK_SECHIBA and .NOT.(HYDROL_CWRR)
256             !Config Def   = 0.1
257             !Config Help  =
258             !Config Units = [kg/m^2/dt]
259             CALL getin_p('CHOISNEL_DIFF_MAX',max_drain)
260
261             !! Check parameter value (correct range)
262             IF (  ( max_drain <= zero ) .OR. ( max_drain <= min_drain ) ) THEN
263                CALL ipslerr_p(error_level, "config_soil_parameters.", &
264                     &     "Wrong parameter value for CHOISNEL_DIFF_MAX.", &
265                     &     "This parameter should be positive or greater than CHOISNEL_DIFF_MIN.", &
266                     &     "Please, check parameter value in run.def. ")
267             END IF
268
269
270             !Config Key   = CHOISNEL_DIFF_EXP
271             !Config Desc  = The exponential in the diffusion law
272             !Config If    = OK_SECHIBA and .NOT.(HYDROL_CWRR)
273             !Config Def   = 1.5
274             !Config Help  =
275             !Config Units = [-]
276             CALL getin_p('CHOISNEL_DIFF_EXP',exp_drain)
277
278             !! Check parameter value (correct range)
279             IF ( exp_drain <= zero ) THEN
280                CALL ipslerr_p(error_level, "config_soil_parameters.", &
281                     &     "Wrong parameter value for CHOISNEL_DIFF_EXP.", &
282                     &     "This parameter should be positive. ", &
283                     &     "Please, check parameter value in run.def. ")
284             END IF
285
286
287             !Config Key   = CHOISNEL_RSOL_CSTE
288             !Config Desc  = Constant in the computation of resistance for bare  soil evaporation
289             !Config If    = OK_SECHIBA and .NOT.(HYDROL_CWRR)
290             !Config Def   = 33.E3
291             !Config Help  =
292             !Config Units = [s/m^2]
293             CALL getin_p('CHOISNEL_RSOL_CSTE',rsol_cste)
294
295             !! Check parameter value (correct range)
296             IF ( rsol_cste <= zero ) THEN
297                CALL ipslerr_p(error_level, "config_soil_parameters.", &
298                     &     "Wrong parameter value for CHOISNEL_RSOL_CSTE.", &
299                     &     "This parameter should be positive. ", &
300                     &     "Please, check parameter value in run.def. ")
301             END IF
302
303
304             !Config Key   = HCRIT_LITTER
305             !Config Desc  = Scaling depth for litter humidity
306             !Config If    = OK_SECHIBA and .NOT.(HYDROL_CWRR)
307             !Config Def   = 0.08
308             !Config Help  =
309             !Config Units = [m]
310             CALL getin_p('HCRIT_LITTER',hcrit_litter)
311
312             !! Check parameter value (correct range)
313             IF ( hcrit_litter <= zero ) THEN
314                CALL ipslerr_p(error_level, "config_soil_parameters.", &
315                     &     "Wrong parameter value for HCRIT_LITTER.", &
316                     &     "This parameter should be positive. ", &
317                     &     "Please, check parameter value in run.def. ")
318             END IF
319
320          END IF
321
322       END IF ! IF ( active_flags%ok_sechiba .AND. impose_param ) THEN
323
324       !! Variables related to soil freezing in thermosoil module
325       !
326       !Config Key  = OK_FREEZE
327       !Config Desc = Activate the complet soil freezing scheme
328       !Config If   = OK_SECHIBA
329       !Config Def  = FALSE
330       !Config Help = Activate soil freezing thermal effects. Activates soil
331       !              freezing hydrological effects in CWRR scheme.
332       !Config Units= [FLAG]
333
334       ! ok_freeze is a flag that controls the default values for several
335       ! flags controling the different soil freezing processes
336       ! Set ok_freeze=true for the complete soil freezing scheme
337       ! ok_freeze is a local variable only used in this subroutine
338       ok_freeze = .FALSE.
339       CALL getin_p('OK_FREEZE',ok_freeze)
340
341
342       !Config Key  = OK_ECORR
343       !Config Desc = Energy correction for freezing
344       !Config If   =
345       !Config Def  = True if OK_FREEZE else false
346       !Config Help = Energy conservation : Correction to make sure that
347       !              the same latent heat is
348       !Config        released and consumed during freezing and thawing
349       !Config Units= [FLAG]
350       IF (ok_freeze) THEN
351          ok_Ecorr = .TRUE.
352       ELSE
353          ok_Ecorr = .FALSE.
354       END IF
355       CALL getin_p ('OK_ECORR',ok_Ecorr)
356       !Config Key  = READ_PERMAFROST_MAP
357       !Config Desc = Read information about ice content, overburden and
358       !              permafrost type from IPA map
359       !Config If   =
360       !Config Def  = FALSE
361       !Config Help =
362       !Config Units= [FLAG]
363
364       read_permafrost_map = .FALSE.
365       CALL getin_p ('READ_PERMAFROST_MAP',read_permafrost_map)       
366
367       !Config Key  = READ_REFTEMP
368       !Config Desc = Initialize soil temperature using climatological temperature
369       !Config If   =
370       !Config Def  = True if OK_FREEZE else false
371       !Config Help =
372       !Config Units= [FLAG]
373       IF (ok_freeze) THEN
374          read_reftemp = .TRUE.
375       ELSE
376          read_reftemp = .FALSE.
377       END IF
378       CALL getin_p ('READ_REFTEMP',read_reftemp)
379
380       !Config Key  = OK_FREEZE_THERMIX
381       !Config Desc = Activate thermal part of the soil freezing scheme
382       !Config If   =
383       !Config Def  = True if OK_FREEZE else false
384       !Config Help =
385       !Config Units= [FLAG]
386       IF (ok_freeze) THEN
387          ok_freeze_thermix = .TRUE.
388       ELSE
389          ok_freeze_thermix = .FALSE.
390       END IF
391       CALL getin_p ('OK_FREEZE_THERMIX',ok_freeze_thermix)
392
393       !! Coherence check for number of thermosoil levels for long term
394       !! simulation where soil thermal inertia matters
395       !! It is highly recommnaded to use at least ngrnd=11 when soil
396       !! freezing is activated
397       IF (ok_freeze_thermix .AND. ngrnd < 11) THEN
398          WRITE(numout,*) 'ERROR : Incoherence between ok_freeze_thermix activated'
399          WRITE(numout,*) '        and ngrnd to small. Here used ngrnd=',ngrnd
400          WRITE(numout,*) 'Set THERMOSOIL_NBLEV=11 or higher in run.def parameter file'
401          WRITE(numout,*) '        or deactivate soil freezing'
402          CALL ipslerr_p(3,'thermosoil_init','Not enough thermodynamic soil levels for soil freezing', &
403               'Adapt run.def with at least THERMOSOIL_NBLEV=11','')
404       END IF
405
406
407       !Config Key = POROS
408       !Config Desc = Soil porosity
409       !Config If = OK_SECHIBA
410       !Config Def = 0.41
411       !Config Help = From USDA classification, mean value
412       !Config Units = [-]
413       poros=0.41
414       CALL getin_p('POROS',poros)
415
416
417       !Config Key = fr_dT
418       !Config Desc = Freezing window   
419       !Config If = OK_SECHIBA
420       !Config Def = 2.0
421       !Config Help =
422       !Config Units = [K]
423       fr_dT=2.0
424       CALL getin_p('FR_DT',fr_dT)
425
426
427       !! Variables related to soil Freezing in diffuco module
428
429       !Config Key  = OK_SNOWFACT
430       !Config Desc = Activates the smoothering of landscapes by snow,
431       !       e.g. reduces of the surface roughness length when snow is present.
432       !Config If   =
433       !Config Def  = True if OK_FREEZE else false
434       !Config Help =
435       !Config Units= [FLAG]
436       IF (ok_freeze) THEN
437          ok_snowfact = .TRUE.
438       ELSE
439          ok_snowfact = .FALSE.
440       END IF
441       CALL getin_p('OK_SNOWFACT', ok_snowfact)
442
443
444       !! Variables related to soil Freezing in hydrol module
445
446       !Config Key  = OK_FREEZE_CWRR
447       !Config Desc = CWRR freezing scheme by I. Gouttevin
448       !Config If   =
449       !Config Def  = True if OK_FREEZE else false
450       !Config Help =
451       !Config Units= [FLAG]
452       IF (ok_freeze) THEN
453          ok_freeze_cwrr = .TRUE.
454       ELSE
455          ok_freeze_cwrr = .FALSE.
456       END IF
457       CALL getin_p('OK_FREEZE_CWRR',ok_freeze_cwrr)
458
459
460       IF (ok_freeze_cwrr) THEN
461          !Config Key  = OK_THERMODYNAMICAL_FREEZING
462          !Config Desc = Calculate frozen fraction thermodynamically
463          !Config If   = HYDROL_CWRR .AND. OK_FREEZE_CWRR
464          !Config Def  = True
465          !Config Help = Calculate frozen fraction thermodynamically if true,
466          !Config      = else calculate frozen fraction linearly
467          !Config Units= [FLAG]
468          ok_thermodynamical_freezing = .TRUE.
469          CALL getin_p('OK_THERMODYNAMICAL_FREEZING',ok_thermodynamical_freezing)
470       END IF
471
472       first_call =.FALSE.
473
474    ENDIF
475
476  END SUBROUTINE config_soil_parameters
477
478
479END MODULE constantes_soil
Note: See TracBrowser for help on using the repository browser.