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

Last change on this file since 7508 was 7508, checked in by josefine.ghattas, 2 years ago
  • Removed DRY_SOIL_HEAT_COND and related variable so_cond_dry
  • Replaced previous scalar variable so_capa_dry with vector variable so_capa_dry_ns and moved read from run.def to thermosoil. In the end, so_capa_dry_ns is renamed so_capa_dry.

See ticket #780

No change in results.

File size: 9.1 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 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   = SNOW_HEAT_COND
74       !Config Desc  = Thermal Conductivity of snow
75       !Config If    = OK_SECHIBA 
76       !Config Def   = 0.3
77       !Config Help  =
78       !Config Units = [W.m^{-2}.K^{-1}]
79       CALL getin_p("SNOW_HEAT_COND",sn_cond)
80
81       !! Check
82       IF ( sn_cond <= zero ) THEN
83          CALL ipslerr_p(error_level, "config_soil_parameters.", &
84               &     "Wrong parameter value for SNOW_HEAT_COND.", &
85               &     "This parameter should be positive. ", &
86               &     "Please, check parameter value in run.def. ")
87       END IF
88
89
90       !Config Key   = SNOW_DENSITY
91       !Config Desc  = Snow density for the soil thermodynamics
92       !Config If    = OK_SECHIBA
93       !Config Def   = 330.0
94       !Config Help  =
95       !Config Units = [-]
96       CALL getin_p("SNOW_DENSITY",sn_dens)
97
98       !! Check parameter value (correct range)
99       IF ( sn_dens <= zero ) THEN
100          CALL ipslerr_p(error_level, "config_soil_parameters.", &
101               &     "Wrong parameter value for SNOW_DENSITY.", &
102               &     "This parameter should be positive. ", &
103               &     "Please, check parameter value in run.def. ")
104       END IF
105
106
107       !! Calculation of snow capacity
108       !! If sn_dens is redefined by the user, sn_capa needs to be reset
109       sn_capa = 2100.0_r_std*sn_dens
110
111
112       !Config Key   = NOBIO_WATER_CAPAC_VOLUMETRI
113       !Config Desc  =
114       !Config If    =
115       !Config Def   = 150.
116       !Config Help  =
117       !Config Units = [s/m^2]
118       CALL getin_p('NOBIO_WATER_CAPAC_VOLUMETRI',mx_eau_nobio)
119
120       !! Check parameter value (correct range)
121       IF ( mx_eau_nobio <= zero ) THEN
122          CALL ipslerr_p(error_level, "config_soil_parameters.", &
123               &     "Wrong parameter value for NOBIO_WATER_CAPAC_VOLUMETRI.", &
124               &     "This parameter should be positive. ", &
125               &     "Please, check parameter value in run.def. ")
126       END IF
127
128
129       !Config Key   = SECHIBA_QSINT
130       !Config Desc  = Interception reservoir coefficient
131       !Config If    = OK_SECHIBA
132       !Config Def   = 0.02
133       !Config Help  = Transforms leaf area index into size of interception reservoir
134       !Config         for slowproc_derivvar or stomate
135       !Config Units = [m]
136       CALL getin_p('SECHIBA_QSINT',qsintcst)
137
138       !! Check parameter value (correct range)
139       IF ( qsintcst <= zero ) THEN
140          CALL ipslerr_p(error_level, "config_soil_parameters.", &
141               &     "Wrong parameter value for SECHIBA_QSINT.", &
142               &     "This parameter should be positive. ", &
143               &     "Please, check parameter value in run.def. ")
144       END IF
145
146
147    END IF ! IF ( ok_sechiba .AND. impose_param ) THEN
148
149
150
151    !! Variables related to soil freezing in thermosoil module
152    !
153    !Config Key  = OK_FREEZE
154    !Config Desc = Activate the complet soil freezing scheme
155    !Config If   = OK_SECHIBA
156    !Config Def  = TRUE
157    !Config Help = Activate soil freezing thermal effects. Activates soil freezing hydrological effects in CWRR scheme.
158    !Config Units= [FLAG]
159
160    ! ok_freeze is a flag that controls the default values for several flags controling
161    ! the different soil freezing processes
162    ! Set ok_freeze=true for the complete soil freezing scheme
163    ! ok_freeze is a local variable only used in this subroutine
164    ok_freeze = .TRUE.
165    CALL getin_p('OK_FREEZE',ok_freeze)
166
167
168    !Config Key  = READ_REFTEMP
169    !Config Desc = Initialize soil temperature using climatological temperature
170    !Config If   =
171    !Config Def  = True/False depening on OK_FREEZE
172    !Config Help =
173    !Config Units= [FLAG]
174
175    IF (ok_freeze) THEN
176       read_reftemp = .TRUE.
177    ELSE
178       read_reftemp = .FALSE.
179    END IF
180    CALL getin_p ('READ_REFTEMP',read_reftemp)
181
182    !Config Key  = OK_FREEZE_THERMIX
183    !Config Desc = Activate thermal part of the soil freezing scheme
184    !Config If   =
185    !Config Def  = True if OK_FREEZE else false
186    !Config Help =
187    !Config Units= [FLAG]
188
189    IF (ok_freeze) THEN
190       ok_freeze_thermix = .TRUE.
191    ELSE
192       ok_freeze_thermix = .FALSE.
193    END IF
194    CALL getin_p ('OK_FREEZE_THERMIX',ok_freeze_thermix)
195
196
197    !Config Key  = OK_ECORR
198    !Config Desc = Energy correction for freezing
199    !Config If   = OK_FREEZE_THERMIX
200    !Config Def  = True if OK_FREEZE else false
201    !Config Help = Energy conservation : Correction to make sure that the same latent heat is
202    !Config        released and consumed during freezing and thawing
203    !Config Units= [FLAG]
204    IF (ok_freeze) THEN
205       ok_Ecorr = .TRUE.
206    ELSE
207       ok_Ecorr = .FALSE.
208    END IF
209    CALL getin_p ('OK_ECORR',ok_Ecorr)
210    IF (ok_Ecorr .AND. .NOT. ok_freeze_thermix) THEN
211       CALL ipslerr_p(3,'thermosoil_init','OK_ECORR cannot be activated without OK_FREEZE_THERMIX', &
212            'Adapt run parameters with OK_FREEZE_THERMIX=y','')
213    END IF
214
215    !Config Key  = OK_FREEZE_THAW_LATENT_HEAT
216    !Config Desc = Activate latent heat part of the soil freezing scheme
217    !Config If   =
218    !Config Def  = FALSE
219    !Config Help =
220    !Config Units= [FLAG]
221
222    ok_freeze_thaw_latent_heat = .FALSE.
223    CALL getin_p ('OK_FREEZE_THAW_LATENT_HEAT',ok_freeze_thaw_latent_heat)
224
225
226    !Config Key = fr_dT
227    !Config Desc = Freezing window   
228    !Config If = OK_SECHIBA
229    !Config Def = 2.0
230    !Config Help =
231    !Config Units = [K]
232    fr_dT=2.0
233    CALL getin_p('FR_DT',fr_dT)
234
235
236    !! Variables related to soil Freezing in hydrol module
237
238    !Config Key  = OK_FREEZE_CWRR
239    !Config Desc = CWRR freezing scheme by I. Gouttevin
240    !Config If   =
241    !Config Def  = True if OK_FREEZE else false
242    !Config Help =
243    !Config Units= [FLAG]
244
245    IF (ok_freeze) THEN
246       ok_freeze_cwrr = .TRUE.
247    ELSE
248       ok_freeze_cwrr = .FALSE.
249    END IF
250    CALL getin_p('OK_FREEZE_CWRR',ok_freeze_cwrr)
251
252
253    IF (ok_freeze_cwrr) THEN
254       !Config Key  = OK_THERMODYNAMICAL_FREEZING
255       !Config Desc = Calculate frozen fraction thermodynamically
256       !Config If   = OK_FREEZE_CWRR
257       !Config Def  = True
258       !Config Help = Calculate frozen fraction thermodynamically if true,
259       !Config      = else calculate frozen fraction linearly
260       !Config Units= [FLAG]
261       ok_thermodynamical_freezing = .TRUE.
262       CALL getin_p('OK_THERMODYNAMICAL_FREEZING',ok_thermodynamical_freezing)
263    END IF
264
265
266    !Config Key   = CHECK_CWRR
267    !Config Desc  = Calculate diagnostics to check CWRR water balance
268    !Config Def   = n
269    !Config If    =
270    !Config Help  = Diagnostics from module hydrol. The verifictaions are done in post-treatement
271    !Config Units = [FLAG]
272    check_cwrr = .FALSE.
273    CALL getin_p('CHECK_CWRR', check_cwrr)
274
275  END SUBROUTINE config_soil_parameters
276
277
278END MODULE constantes_soil
Note: See TracBrowser for help on using the repository browser.