source: branches/publications/ORCHIDEE_GLUC_r6545/src_parameters/constantes_soil.f90 @ 7442

Last change on this file since 7442 was 4719, checked in by albert.jornet, 7 years ago

Merge: from revisions [4491:4695/trunk/ORCHIDEE]

Merge done in [4671:4718/perso/albert.jornet/MICT_MERGE]

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