source: branches/publications/ORCHIDEE-PEAT_r5488/src_parameters/constantes_soil.f90 @ 6890

Last change on this file since 6890 was 4806, checked in by chunjing.qiu, 7 years ago

orchi-peat based on r4229

File size: 17.5 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()
55
56    USE ioipsl
57
58    IMPLICIT NONE
59
60    !! 0. Variables and parameters declaration
61
62    !! 0.4 Local variables
63
64    INTEGER(i_std), PARAMETER      :: error_level = 3         !! Switch to 2 to turn fatal errors into warnings.(1-3, unitless)
65    LOGICAL                        :: ok_freeze               !! Local variable used to set default values for all flags
66    !! controling the soil freezing scheme
67    !_ ================================================================================================================================
68
69    ! Following initializations are only done for option impose_param
70    IF ( ok_sechiba .AND. impose_param ) THEN
71
72       !Config Key   = DRY_SOIL_HEAT_CAPACITY
73       !Config Desc  = Dry soil Heat capacity of soils
74       !Config If    = OK_SECHIBA
75       !Config Def   = 1.80e+6
76       !Config Help  = Values taken from : PIELKE,'MESOSCALE METEOROLOGICAL MODELING',P.384.
77       !Config Units = [J.m^{-3}.K^{-1}]
78       CALL getin_p("DRY_SOIL_HEAT_CAPACITY",so_capa_dry)
79
80       !! Check parameter value (correct range)
81       IF ( so_capa_dry <= zero ) THEN
82          CALL ipslerr_p(error_level, "config_soil_parameters.", &
83               &     "Wrong parameter value for DRY_SOIL_HEAT_CAPACITY.", &
84               &     "This parameter should be positive. ", &
85               &     "Please, check parameter value in run.def. ")
86       END IF
87
88
89       !Config Key   = DRY_SOIL_HEAT_COND
90       !Config Desc  = Dry soil Thermal Conductivity of soils
91       !Config If    = OK_SECHIBA
92       !Config Def   = 0.40
93       !Config Help  = Values taken from : PIELKE,'MESOSCALE METEOROLOGICAL MODELING',P.384.
94       !Config Units = [W.m^{-2}.K^{-1}]
95       CALL getin_p("DRY_SOIL_HEAT_COND",so_cond_dry)
96
97       !! Check parameter value (correct range)
98       IF ( so_cond_dry <= zero ) THEN
99          CALL ipslerr_p(error_level, "config_soil_parameters.", &
100               &     "Wrong parameter value for DRY_SOIL_HEAT_COND.", &
101               &     "This parameter should be positive. ", &
102               &     "Please, check parameter value in run.def. ")
103       END IF
104
105
106       !Config Key   = WET_SOIL_HEAT_CAPACITY
107       !Config Desc  = Wet soil Heat capacity of soils
108       !Config If    = OK_SECHIBA
109       !Config Def   = 3.03e+6
110       !Config Help  =
111       !Config Units = [J.m^{-3}.K^{-1}]
112       CALL getin_p("WET_SOIL_HEAT_CAPACITY",so_capa_wet)
113
114       !! Check parameter value (correct range)
115       IF ( so_capa_wet <= zero ) THEN
116          CALL ipslerr_p(error_level, "config_soil_parameters.", &
117               &     "Wrong parameter value for WET_SOIL_HEAT_CAPACITY.", &
118               &     "This parameter should be positive. ", &
119               &     "Please, check parameter value in run.def. ")
120       END IF
121
122
123       !Config Key   = WET_SOIL_HEAT_COND
124       !Config Desc  = Wet soil Thermal Conductivity of soils
125       !Config If    = OK_SECHIBA
126       !Config Def   = 1.89
127       !Config Help  =
128       !Config Units = [W.m^{-2}.K^{-1}]
129       CALL getin_p("WET_SOIL_HEAT_COND",so_cond_wet)
130
131       !! Check parameter value (correct range)
132       IF ( so_cond_wet <= zero ) THEN
133          CALL ipslerr_p(error_level, "config_soil_parameters.", &
134               &     "Wrong parameter value for WET_SOIL_HEAT_COND.", &
135               &     "This parameter should be positive. ", &
136               &     "Please, check parameter value in run.def. ")
137       END IF
138
139
140       !Config Key   = SNOW_HEAT_COND
141       !Config Desc  = Thermal Conductivity of snow
142       !Config If    = OK_SECHIBA 
143       !Config Def   = 0.3
144       !Config Help  =
145       !Config Units = [W.m^{-2}.K^{-1}]
146       CALL getin_p("SNOW_HEAT_COND",sn_cond)
147
148       !! Check
149       IF ( sn_cond <= zero ) THEN
150          CALL ipslerr_p(error_level, "config_soil_parameters.", &
151               &     "Wrong parameter value for SNOW_HEAT_COND.", &
152               &     "This parameter should be positive. ", &
153               &     "Please, check parameter value in run.def. ")
154       END IF
155
156
157       !Config Key   = SNOW_DENSITY
158       !Config Desc  = Snow density for the soil thermodynamics
159       !Config If    = OK_SECHIBA
160       !Config Def   = 330.0
161       !Config Help  =
162       !Config Units = [-]
163       CALL getin_p("SNOW_DENSITY",sn_dens)
164
165       !! Check parameter value (correct range)
166       IF ( sn_dens <= zero ) THEN
167          CALL ipslerr_p(error_level, "config_soil_parameters.", &
168               &     "Wrong parameter value for SNOW_DENSITY.", &
169               &     "This parameter should be positive. ", &
170               &     "Please, check parameter value in run.def. ")
171       END IF
172
173
174       !! Calculation of snow capacity
175       !! If sn_dens is redefined by the user, sn_capa needs to be reset
176       sn_capa = 2100.0_r_std*sn_dens
177
178
179       !Config Key   = NOBIO_WATER_CAPAC_VOLUMETRI
180       !Config Desc  =
181       !Config If    = OK_SECHIBA and .NOT.(HYDROL_CWRR)
182       !Config Def   = 150.
183       !Config Help  =
184       !Config Units = [s/m^2]
185       CALL getin_p('NOBIO_WATER_CAPAC_VOLUMETRI',mx_eau_nobio)
186
187       !! Check parameter value (correct range)
188       IF ( mx_eau_nobio <= zero ) THEN
189          CALL ipslerr_p(error_level, "config_soil_parameters.", &
190               &     "Wrong parameter value for NOBIO_WATER_CAPAC_VOLUMETRI.", &
191               &     "This parameter should be positive. ", &
192               &     "Please, check parameter value in run.def. ")
193       END IF
194
195
196       !Config Key   = SECHIBA_QSINT
197       !Config Desc  = Interception reservoir coefficient
198       !Config If    = OK_SECHIBA
199       !Config Def   = 0.1
200       !Config Help  = Transforms leaf area index into size of interception reservoir
201       !Config         for slowproc_derivvar or stomate
202       !Config Units = [m]
203       CALL getin_p('SECHIBA_QSINT',qsintcst)
204
205       !! Check parameter value (correct range)
206       IF ( qsintcst <= zero ) THEN
207          CALL ipslerr_p(error_level, "config_soil_parameters.", &
208               &     "Wrong parameter value for SECHIBA_QSINT.", &
209               &     "This parameter should be positive. ", &
210               &     "Please, check parameter value in run.def. ")
211       END IF
212
213        !Config Key  = SOIL_LAYERS_DISCRE_METHOD
214        !Config Desc = Select which soil layer discretization method use
215        !Config If   =
216        !Config Def  = 0 (Thermix method)
217        !Config Help = 0 = thermix, 1 = permafrost, any other value is not valid
218        !Config Units= [FLAG]
219        SO_DISCRETIZATION_METHOD = 0
220        CALL getin_p('SOIL_LAYERS_DISCRE_METHOD', SO_DISCRETIZATION_METHOD)
221        !! Check parameter value (correct range)
222        IF ( SO_DISCRETIZATION_METHOD < zero .OR. SO_DISCRETIZATION_METHOD > deux ) THEN
223           CALL ipslerr_p(error_level, "config_soil_parameters.", &
224                &     "Wrong parameter value for SOIL_LAYERS_DISCRE_METHOD.", &
225                &     "Use 0 for thermix or 1 for permafrost method ", &
226                &     "Please, check parameter value in run.def. ")
227        END IF
228
229       IF ( .NOT.(hydrol_cwrr) ) THEN
230
231          !Config Key   = CHOISNEL_DIFF_MIN
232          !Config Desc  = Diffusion constant for the slow regime
233          !Config If    = OK_SECHIBA and .NOT.(HYDROL_CWRR)
234          !Config Def   = 0.001
235          !Config Help  =
236          !Config Units = [kg/m^2/dt]
237          CALL getin_p('CHOISNEL_DIFF_MIN',min_drain)
238
239          !! Check parameter value (correct range)
240          IF ( min_drain <= zero ) THEN
241             CALL ipslerr_p(error_level, "config_soil_parameters.", &
242                  &     "Wrong parameter value for CHOISNEL_DIFF_MIN.", &
243                  &     "This parameter should be positive. ", &
244                  &     "Please, check parameter value in run.def. ")
245          END IF
246
247
248          !Config Key   = CHOISNEL_DIFF_MAX
249          !Config Desc  = Diffusion constant for the fast regime
250          !Config If    = OK_SECHIBA and .NOT.(HYDROL_CWRR)
251          !Config Def   = 0.1
252          !Config Help  =
253          !Config Units = [kg/m^2/dt]
254          CALL getin_p('CHOISNEL_DIFF_MAX',max_drain)
255
256          !! Check parameter value (correct range)
257          IF (  ( max_drain <= zero ) .OR. ( max_drain <= min_drain ) ) THEN
258             CALL ipslerr_p(error_level, "config_soil_parameters.", &
259                  &     "Wrong parameter value for CHOISNEL_DIFF_MAX.", &
260                  &     "This parameter should be positive or greater than CHOISNEL_DIFF_MIN.", &
261                  &     "Please, check parameter value in run.def. ")
262          END IF
263
264
265          !Config Key   = CHOISNEL_DIFF_EXP
266          !Config Desc  = The exponential in the diffusion law
267          !Config If    = OK_SECHIBA and .NOT.(HYDROL_CWRR)
268          !Config Def   = 1.5
269          !Config Help  =
270          !Config Units = [-]
271          CALL getin_p('CHOISNEL_DIFF_EXP',exp_drain)
272
273          !! Check parameter value (correct range)
274          IF ( exp_drain <= zero ) THEN
275             CALL ipslerr_p(error_level, "config_soil_parameters.", &
276                  &     "Wrong parameter value for CHOISNEL_DIFF_EXP.", &
277                  &     "This parameter should be positive. ", &
278                  &     "Please, check parameter value in run.def. ")
279          END IF
280
281
282          !Config Key   = CHOISNEL_RSOL_CSTE
283          !Config Desc  = Constant in the computation of resistance for bare  soil evaporation
284          !Config If    = OK_SECHIBA and .NOT.(HYDROL_CWRR)
285          !Config Def   = 33.E3
286          !Config Help  =
287          !Config Units = [s/m^2]
288          CALL getin_p('CHOISNEL_RSOL_CSTE',rsol_cste)
289
290          !! Check parameter value (correct range)
291          IF ( rsol_cste <= zero ) THEN
292             CALL ipslerr_p(error_level, "config_soil_parameters.", &
293                  &     "Wrong parameter value for CHOISNEL_RSOL_CSTE.", &
294                  &     "This parameter should be positive. ", &
295                  &     "Please, check parameter value in run.def. ")
296          END IF
297
298
299          !Config Key   = HCRIT_LITTER
300          !Config Desc  = Scaling depth for litter humidity
301          !Config If    = OK_SECHIBA and .NOT.(HYDROL_CWRR)
302          !Config Def   = 0.08
303          !Config Help  =
304          !Config Units = [m]
305          CALL getin_p('HCRIT_LITTER',hcrit_litter)
306
307          !! Check parameter value (correct range)
308          IF ( hcrit_litter <= zero ) THEN
309             CALL ipslerr_p(error_level, "config_soil_parameters.", &
310                  &     "Wrong parameter value for HCRIT_LITTER.", &
311                  &     "This parameter should be positive. ", &
312                  &     "Please, check parameter value in run.def. ")
313          END IF
314
315       END IF
316
317    END IF ! IF ( ok_sechiba .AND. impose_param ) THEN
318
319!!!qcj++ peatland
320    CALL getin_p("TAU_PEAT",tau_peat)
321    CALL getin_p("Z_TAU",z_tau)
322    CALL getin_p('LIM1', lim1)
323    CALL getin_p('LIM2', lim2)
324    CALL getin_p('Q10_peat', q10_peat)
325    !! Variables related to soil freezing in thermosoil module
326    !
327    !Config Key  = OK_FREEZE
328    !Config Desc = Activate the complet soil freezing scheme
329    !Config If   = OK_SECHIBA
330    !Config Def  = FALSE
331    !Config Help = Activate soil freezing thermal effects. Activates soil freezing hydrological effects in CWRR scheme.
332    !Config Units= [FLAG]
333
334    ! ok_freeze is a flag that controls the default values for several flags controling
335    ! 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  = READ_REFTEMP
343    !Config Desc = Initialize soil temperature using climatological temperature
344    !Config If   =
345    !Config Def  = True/False depening on OK_FREEZE
346    !Config Help =
347    !Config Units= [FLAG]
348
349    IF (ok_freeze) THEN
350       read_reftemp = .TRUE.
351    ELSE
352       read_reftemp = .FALSE.
353    END IF
354    CALL getin_p ('READ_REFTEMP',read_reftemp)
355
356    !Config Key  = OK_FREEZE_THERMIX
357    !Config Desc = Activate thermal part of the soil freezing scheme
358    !Config If   =
359    !Config Def  = True if OK_FREEZE else false
360    !Config Help =
361    !Config Units= [FLAG]
362    IF (ok_freeze) THEN
363       ok_freeze_thermix = .TRUE.
364    ELSE
365       ok_freeze_thermix = .FALSE.
366    END IF
367    CALL getin_p ('OK_FREEZE_THERMIX',ok_freeze_thermix)
368
369
370    !Config Key  = OK_ECORR
371    !Config Desc = Energy correction for freezing
372    !Config If   = OK_FREEZE_THERMIX
373    !Config Def  = True if OK_FREEZE else false
374    !Config Help = Energy conservation : Correction to make sure that the same latent heat is
375    !Config        released and consumed during freezing and thawing
376    !Config Units= [FLAG]
377    IF (ok_freeze) THEN
378       ok_Ecorr = .TRUE.
379    ELSE
380       ok_Ecorr = .FALSE.
381    END IF
382    CALL getin_p ('OK_ECORR',ok_Ecorr)
383    IF (ok_Ecorr .AND. .NOT. ok_freeze_thermix) THEN
384       CALL ipslerr_p(3,'thermosoil_init','OK_ECORR cannot be activated without OK_FREEZE_THERMIX', &
385            'Adapt run parameters with OK_FREEZE_THERMIX=y','')
386    END IF
387
388    !Config Key = POROS
389    !Config Desc = Soil porosity
390    !Config If = OK_SECHIBA
391    !Config Def = 0.41
392    !Config Help = From USDA classification, mean value
393    !Config Units = [-]
394    poros=0.41
395    CALL getin_p('POROS',poros)
396
397
398    !Config Key = fr_dT
399    !Config Desc = Freezing window   
400    !Config If = OK_SECHIBA
401    !Config Def = 2.0
402    !Config Help =
403    !Config Units = [K]
404    fr_dT=2.0
405    CALL getin_p('FR_DT',fr_dT)
406
407
408    !! Variables related to soil Freezing in diffuco module
409
410    !Config Key  = OK_SNOWFACT
411    !Config Desc = Activates the smoothering of landscapes by snow,
412    !       e.g. reduces of the surface roughness length when snow is present.
413    !Config If   =
414    !Config Def  = True if OK_FREEZE else false
415    !Config Help =
416    !Config Units= [FLAG]
417
418    IF (ok_freeze) THEN
419       ok_snowfact = .TRUE.
420    ELSE
421       ok_snowfact = .FALSE.
422    END IF
423    CALL getin_p('OK_SNOWFACT', ok_snowfact)
424
425
426    !! Variables related to soil Freezing in hydrol module
427
428    !Config Key  = SMCMAX_FAO
429    !Config Desc = Fao Porosity 
430    !Config If   =
431    !Config Def  = 0.41_r_std, 0.43_r_std, 0.41_r_std
432    !Config Help =
433    !Config Units= [FLAG]
434    CALL getin_p('SMCMAX_FAO', SMCMAX_fao)
435
436    !Config Key  = OK_FREEZE_CWRR
437    !Config Desc = CWRR freezing scheme by I. Gouttevin
438    !Config If   =
439    !Config Def  = True if OK_FREEZE else false
440    !Config Help =
441    !Config Units= [FLAG]
442    IF (ok_freeze) THEN
443       ok_freeze_cwrr = .TRUE.
444    ELSE
445       ok_freeze_cwrr = .FALSE.
446    END IF
447    CALL getin_p('OK_FREEZE_CWRR',ok_freeze_cwrr)
448
449
450    IF (ok_freeze_cwrr) THEN
451       !Config Key  = OK_THERMODYNAMICAL_FREEZING
452       !Config Desc = Calculate frozen fraction thermodynamically
453       !Config If   = HYDROL_CWRR .AND. OK_FREEZE_CWRR
454       !Config Def  = True
455       !Config Help = Calculate frozen fraction thermodynamically if true,
456       !Config      = else calculate frozen fraction linearly
457       !Config Units= [FLAG]
458       ok_thermodynamical_freezing = .TRUE.
459       CALL getin_p('OK_THERMODYNAMICAL_FREEZING',ok_thermodynamical_freezing)
460    END IF
461
462
463    !! 1 Some initializations
464    !
465    !
466    !Config Key   = CHECK_CWRR
467    !Config Desc  = Check detailed CWRR water balance
468    !Config Def   = n
469    !Config If    = HYDROL_CWRR
470    !Config Help  = This parameters allows the user to check
471    !Config         the detailed water balance in each time step
472    !Config         of CWRR and stop execution if not correct
473    !Config Units = [FLAG]
474    !
475    check_cwrr = .FALSE.
476    CALL getin_p('CHECK_CWRR', check_cwrr)
477
478    !Config Key   = CHECK_CWRR2
479    !Config Desc  = Caluculate diagnostics to check CWRR water balance
480    !Config Def   = n
481    !Config If    = HYDROL_CWRR2
482    !Config Help  = The verifictaions are done in post-treatement
483    !Config Units = [FLAG]
484    !
485    check_cwrr2 = .FALSE.
486    CALL getin_p('CHECK_CWRR2', check_cwrr2)
487
488  END SUBROUTINE config_soil_parameters
489
490
491END MODULE constantes_soil
Note: See TracBrowser for help on using the repository browser.