source: branches/publications/ORCHIDEE-LEAK-r5919/src_parameters/constantes_soil.f90 @ 5925

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