source: branches/ORCHIDEE_2_2/ORCHIDEE/src_parameters/constantes_soil.f90 @ 7199

Last change on this file since 7199 was 7199, checked in by agnes.ducharne, 3 years ago

Inclusion of r6499, r6505, r6508 of the trunk, for consistent soil parameters in hydrola and thermosoil, as detailed in ticket #604. Checked step by step by 5d simulations on jean-zay: the only changes are weak and due to replacing poros=0.41 by variable mcs.

File size: 10.5 KB
RevLine 
[947]1! =================================================================================================================================
2! MODULE        : constantes_soil
3!
[4470]4! CONTACT       : orchidee-help _at_ listes.ipsl.fr
[947]5!
6! LICENCE       : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
[1475]9!>\BRIEF         "constantes_soil" module contains subroutine to initialize the parameters related to soil and hydrology.
[947]10!!
[1475]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".
[947]14!!
[1475]15!! RECENT CHANGE(S):
[947]16!!
17!! REFERENCE(S) :
18!!
19!! SVN          :
20!! $HeadURL: $
21!! $Date: $
22!! $Revision: $
23!! \n
24!_ ================================================================================================================================
25
26MODULE constantes_soil
27
[1475]28  USE constantes_soil_var
[947]29  USE constantes
[1392]30  USE ioipsl_para 
[1082]31
[947]32  IMPLICIT NONE
[1082]33
34CONTAINS
35
[3851]36
[1082]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
[3851]54  SUBROUTINE config_soil_parameters()
[1082]55
[3851]56    USE ioipsl
[1082]57
[3851]58    IMPLICIT NONE
[1082]59
[3851]60    !! 0. Variables and parameters declaration
61
[1082]62    !! 0.4 Local variables
63
[3851]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
[1082]67
[3851]68    !_ ================================================================================================================================
[2001]69
[3851]70    ! Following initializations are only done for option impose_param
71    IF ( ok_sechiba .AND. impose_param ) THEN
[2001]72
[3851]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)
[1082]80
[3851]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
[1082]88
89
[3851]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)
[1082]97
[3851]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
[1082]105
[3851]106
107       !Config Key   = SNOW_HEAT_COND
108       !Config Desc  = Thermal Conductivity of snow
109       !Config If    = OK_SECHIBA 
110       !Config Def   = 0.3
111       !Config Help  =
112       !Config Units = [W.m^{-2}.K^{-1}]
113       CALL getin_p("SNOW_HEAT_COND",sn_cond)
[1082]114
[3851]115       !! Check
116       IF ( sn_cond <= zero ) THEN
117          CALL ipslerr_p(error_level, "config_soil_parameters.", &
[1082]118               &     "Wrong parameter value for SNOW_HEAT_COND.", &
119               &     "This parameter should be positive. ", &
120               &     "Please, check parameter value in run.def. ")
[3851]121       END IF
[1082]122
123
[3851]124       !Config Key   = SNOW_DENSITY
125       !Config Desc  = Snow density for the soil thermodynamics
126       !Config If    = OK_SECHIBA
127       !Config Def   = 330.0
128       !Config Help  =
129       !Config Units = [-]
130       CALL getin_p("SNOW_DENSITY",sn_dens)
131
132       !! Check parameter value (correct range)
133       IF ( sn_dens <= zero ) THEN
[1082]134          CALL ipslerr_p(error_level, "config_soil_parameters.", &
135               &     "Wrong parameter value for SNOW_DENSITY.", &
136               &     "This parameter should be positive. ", &
137               &     "Please, check parameter value in run.def. ")
[3851]138       END IF
[1082]139
140
[3851]141       !! Calculation of snow capacity
142       !! If sn_dens is redefined by the user, sn_capa needs to be reset
143       sn_capa = 2100.0_r_std*sn_dens
[1082]144
145
[3851]146       !Config Key   = NOBIO_WATER_CAPAC_VOLUMETRI
147       !Config Desc  =
[5454]148       !Config If    =
[3851]149       !Config Def   = 150.
150       !Config Help  =
151       !Config Units = [s/m^2]
152       CALL getin_p('NOBIO_WATER_CAPAC_VOLUMETRI',mx_eau_nobio)
[1082]153
154       !! Check parameter value (correct range)
[3851]155       IF ( mx_eau_nobio <= zero ) THEN
156          CALL ipslerr_p(error_level, "config_soil_parameters.", &
[1082]157               &     "Wrong parameter value for NOBIO_WATER_CAPAC_VOLUMETRI.", &
158               &     "This parameter should be positive. ", &
159               &     "Please, check parameter value in run.def. ")
[3851]160       END IF
[1082]161
162
[3851]163       !Config Key   = SECHIBA_QSINT
164       !Config Desc  = Interception reservoir coefficient
165       !Config If    = OK_SECHIBA
[5034]166       !Config Def   = 0.02
[3851]167       !Config Help  = Transforms leaf area index into size of interception reservoir
168       !Config         for slowproc_derivvar or stomate
169       !Config Units = [m]
170       CALL getin_p('SECHIBA_QSINT',qsintcst)
[1082]171
[3851]172       !! Check parameter value (correct range)
173       IF ( qsintcst <= zero ) THEN
174          CALL ipslerr_p(error_level, "config_soil_parameters.", &
175               &     "Wrong parameter value for SECHIBA_QSINT.", &
176               &     "This parameter should be positive. ", &
177               &     "Please, check parameter value in run.def. ")
178       END IF
[1082]179
180
[3851]181    END IF ! IF ( ok_sechiba .AND. impose_param ) THEN
[2222]182
183
184
[3851]185    !! Variables related to soil freezing in thermosoil module
186    !
187    !Config Key  = OK_FREEZE
188    !Config Desc = Activate the complet soil freezing scheme
189    !Config If   = OK_SECHIBA
[4962]190    !Config Def  = TRUE
[3851]191    !Config Help = Activate soil freezing thermal effects. Activates soil freezing hydrological effects in CWRR scheme.
192    !Config Units= [FLAG]
[2222]193
[3851]194    ! ok_freeze is a flag that controls the default values for several flags controling
195    ! the different soil freezing processes
196    ! Set ok_freeze=true for the complete soil freezing scheme
197    ! ok_freeze is a local variable only used in this subroutine
[4962]198    ok_freeze = .TRUE.
[3851]199    CALL getin_p('OK_FREEZE',ok_freeze)
[2222]200
201
[3851]202    !Config Key  = READ_REFTEMP
203    !Config Desc = Initialize soil temperature using climatological temperature
204    !Config If   =
205    !Config Def  = True/False depening on OK_FREEZE
206    !Config Help =
207    !Config Units= [FLAG]
[2222]208
[3851]209    IF (ok_freeze) THEN
210       read_reftemp = .TRUE.
211    ELSE
212       read_reftemp = .FALSE.
213    END IF
214    CALL getin_p ('READ_REFTEMP',read_reftemp)
[2222]215
[3851]216    !Config Key  = OK_FREEZE_THERMIX
217    !Config Desc = Activate thermal part of the soil freezing scheme
218    !Config If   =
219    !Config Def  = True if OK_FREEZE else false
220    !Config Help =
221    !Config Units= [FLAG]
[2222]222
[3851]223    IF (ok_freeze) THEN
224       ok_freeze_thermix = .TRUE.
225    ELSE
226       ok_freeze_thermix = .FALSE.
227    END IF
228    CALL getin_p ('OK_FREEZE_THERMIX',ok_freeze_thermix)
[2222]229
230
[3851]231    !Config Key  = OK_ECORR
232    !Config Desc = Energy correction for freezing
233    !Config If   = OK_FREEZE_THERMIX
234    !Config Def  = True if OK_FREEZE else false
235    !Config Help = Energy conservation : Correction to make sure that the same latent heat is
236    !Config        released and consumed during freezing and thawing
237    !Config Units= [FLAG]
238    IF (ok_freeze) THEN
239       ok_Ecorr = .TRUE.
240    ELSE
241       ok_Ecorr = .FALSE.
242    END IF
243    CALL getin_p ('OK_ECORR',ok_Ecorr)
244    IF (ok_Ecorr .AND. .NOT. ok_freeze_thermix) THEN
245       CALL ipslerr_p(3,'thermosoil_init','OK_ECORR cannot be activated without OK_FREEZE_THERMIX', &
246            'Adapt run parameters with OK_FREEZE_THERMIX=y','')
247    END IF
[2222]248
[5150]249    !Config Key  = OK_FREEZE_THAW_LATENT_HEAT
250    !Config Desc = Activate latent heat part of the soil freezing scheme
251    !Config If   =
[5365]252    !Config Def  = FALSE
[5150]253    !Config Help =
254    !Config Units= [FLAG]
255
256    ok_freeze_thaw_latent_heat = .FALSE.
257    CALL getin_p ('OK_FREEZE_THAW_LATENT_HEAT',ok_freeze_thaw_latent_heat)
258
259
[3851]260    !Config Key = fr_dT
261    !Config Desc = Freezing window   
262    !Config If = OK_SECHIBA
263    !Config Def = 2.0
264    !Config Help =
265    !Config Units = [K]
266    fr_dT=2.0
267    CALL getin_p('FR_DT',fr_dT)
[2222]268
269
[3851]270    !! Variables related to soil Freezing in hydrol module
[3402]271
[3851]272    !Config Key  = OK_FREEZE_CWRR
273    !Config Desc = CWRR freezing scheme by I. Gouttevin
274    !Config If   =
275    !Config Def  = True if OK_FREEZE else false
276    !Config Help =
277    !Config Units= [FLAG]
[3402]278
[3851]279    IF (ok_freeze) THEN
280       ok_freeze_cwrr = .TRUE.
281    ELSE
282       ok_freeze_cwrr = .FALSE.
283    END IF
284    CALL getin_p('OK_FREEZE_CWRR',ok_freeze_cwrr)
[1082]285
[3851]286
287    IF (ok_freeze_cwrr) THEN
288       !Config Key  = OK_THERMODYNAMICAL_FREEZING
289       !Config Desc = Calculate frozen fraction thermodynamically
[5454]290       !Config If   = OK_FREEZE_CWRR
[3851]291       !Config Def  = True
292       !Config Help = Calculate frozen fraction thermodynamically if true,
293       !Config      = else calculate frozen fraction linearly
294       !Config Units= [FLAG]
295       ok_thermodynamical_freezing = .TRUE.
296       CALL getin_p('OK_THERMODYNAMICAL_FREEZING',ok_thermodynamical_freezing)
297    END IF
298
299
300    !Config Key   = CHECK_CWRR
[5506]301    !Config Desc  = Calculate diagnostics to check CWRR water balance
[3851]302    !Config Def   = n
[5454]303    !Config If    =
[5506]304    !Config Help  = Diagnostics from module hydrol. The verifictaions are done in post-treatement
[3851]305    !Config Units = [FLAG]
306    check_cwrr = .FALSE.
307    CALL getin_p('CHECK_CWRR', check_cwrr)
308
309  END SUBROUTINE config_soil_parameters
310
311
[947]312END MODULE constantes_soil
Note: See TracBrowser for help on using the repository browser.