source: branches/publications/ORCHIDEE_gmd-2018-57/src_parameters/constantes_soil.f90

Last change on this file was 3965, checked in by jan.polcher, 8 years ago

Merge with trunk at revision3959.
This includes all the developments made for CMIP6 and passage to XIOS2.
All conflicts are resolved and the code compiles.

But it still does not link because of an "undefined reference to `_intel_fast_memmove'"

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