source: branches/publications/ORCHIDEE_CAN_NHA/src_parameters/constantes_soil.f90 @ 8066

Last change on this file since 8066 was 2141, checked in by matthew.mcgrath, 11 years ago

DEV: Merging up to and including r2001

File size: 12.4 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(active_flags, impose_param)
55     
56     USE ioipsl
57
58     IMPLICIT NONE
59
60     !! 0. Variables and parameters declaration
61
62     !! 0.1 Input variables
63
64     TYPE(control_type), INTENT(in) :: active_flags            !! What parts of the code are activated ? (true/false) 
65     LOGICAL                        :: impose_param            !! Flag for imposing parameters in run.def
66    !! 0.4 Local variables
67
68     INTEGER(i_std), PARAMETER      :: error_level = 3         !! Switch to 2 to turn fatal errors into warnings.(1-3, unitless)
69     LOGICAL, SAVE                  :: first_call = .TRUE.     !! To keep first call trace (true/false)
70!$OMP THREADPRIVATE(first_call)
71
72!_ ================================================================================================================================
73     
74     IF ( first_call ) THEN
75
76        !Config Key   = THERMOSOIL_NBLEV
77        !Config Desc  = Number of soil level
78        !Config If    =
79        !Config Def   = 7
80        !Config Help  =
81        !Config Units = (-)
82        ngrnd=7
83        CALL getin_p("THERMOSOIL_NBLEV",ngrnd)
84
85
86        ! Following initializations are only done for option impose_param
87        IF ( active_flags%ok_sechiba .AND. impose_param ) THEN
88
89        !Config Key   = DRY_SOIL_HEAT_CAPACITY
90        !Config Desc  = Dry soil Heat capacity of soils
91        !Config If    = OK_SECHIBA
92        !Config Def   = 1.80e+6
93        !Config Help  = Values taken from : PIELKE,'MESOSCALE METEOROLOGICAL MODELING',P.384.
94        !Config Units = [J.m^{-3}.K^{-1}]
95        CALL getin_p("DRY_SOIL_HEAT_CAPACITY",so_capa_dry)
96       
97        !! Check parameter value (correct range)
98        IF ( so_capa_dry <= zero ) THEN
99           CALL ipslerr_p(error_level, "config_soil_parameters.", &
100                &     "Wrong parameter value for DRY_SOIL_HEAT_CAPACITY.", &
101                &     "This parameter should be positive. ", &
102                &     "Please, check parameter value in run.def. ")
103        END IF
104       
105
106        !Config Key   = DRY_SOIL_HEAT_COND
107        !Config Desc  = Dry soil Thermal Conductivity of soils
108        !Config If    = OK_SECHIBA
109        !Config Def   = 0.40
110        !Config Help  = Values taken from : PIELKE,'MESOSCALE METEOROLOGICAL MODELING',P.384.
111        !Config Units = [W.m^{-2}.K^{-1}]
112        CALL getin_p("DRY_SOIL_HEAT_COND",so_cond_dry)
113
114        !! Check parameter value (correct range)
115        IF ( so_cond_dry <= zero ) THEN
116           CALL ipslerr_p(error_level, "config_soil_parameters.", &
117                &     "Wrong parameter value for DRY_SOIL_HEAT_COND.", &
118                &     "This parameter should be positive. ", &
119                &     "Please, check parameter value in run.def. ")
120        END IF
121
122
123        !Config Key   = WET_SOIL_HEAT_CAPACITY
124        !Config Desc  = Wet soil Heat capacity of soils
125        !Config If    = OK_SECHIBA
126        !Config Def   = 3.03e+6
127        !Config Help  =
128        !Config Units = [J.m^{-3}.K^{-1}]
129        CALL getin_p("WET_SOIL_HEAT_CAPACITY",so_capa_wet)
130
131        !! Check parameter value (correct range)
132        IF ( so_capa_wet <= zero ) THEN
133           CALL ipslerr_p(error_level, "config_soil_parameters.", &
134               &     "Wrong parameter value for WET_SOIL_HEAT_CAPACITY.", &
135               &     "This parameter should be positive. ", &
136               &     "Please, check parameter value in run.def. ")
137        END IF
138
139
140        !Config Key   = WET_SOIL_HEAT_COND
141        !Config Desc  = Wet soil Thermal Conductivity of soils
142        !Config If    = OK_SECHIBA
143        !Config Def   = 1.89
144        !Config Help  =
145        !Config Units = [W.m^{-2}.K^{-1}]
146        CALL getin_p("WET_SOIL_HEAT_COND",so_cond_wet)
147
148        !! Check parameter value (correct range)
149        IF ( so_cond_wet <= zero ) THEN
150           CALL ipslerr_p(error_level, "config_soil_parameters.", &
151               &     "Wrong parameter value for WET_SOIL_HEAT_COND.", &
152               &     "This parameter should be positive. ", &
153               &     "Please, check parameter value in run.def. ")
154        END IF
155
156
157        !Config Key   = SNOW_HEAT_COND
158        !Config Desc  = Thermal Conductivity of snow
159        !Config If    = OK_SECHIBA 
160        !Config Def   = 0.3
161        !Config Help  =
162        !Config Units = [W.m^{-2}.K^{-1}]
163        CALL getin_p("SNOW_HEAT_COND",sn_cond)
164
165        !! Check
166        IF ( sn_cond <= zero ) THEN
167           CALL ipslerr_p(error_level, "config_soil_parameters.", &
168               &     "Wrong parameter value for SNOW_HEAT_COND.", &
169               &     "This parameter should be positive. ", &
170               &     "Please, check parameter value in run.def. ")
171        END IF
172
173
174        !Config Key   = SNOW_DENSITY
175        !Config Desc  = Snow density for the soil thermodynamics
176        !Config If    = OK_SECHIBA
177        !Config Def   = 330.0
178        !Config Help  =
179        !Config Units = [-]
180        CALL getin_p("SNOW_DENSITY",sn_dens)
181       
182        !! Check parameter value (correct range)
183        IF ( sn_dens <= zero ) THEN
184          CALL ipslerr_p(error_level, "config_soil_parameters.", &
185               &     "Wrong parameter value for SNOW_DENSITY.", &
186               &     "This parameter should be positive. ", &
187               &     "Please, check parameter value in run.def. ")
188        END IF
189
190
191        !! Calculation of snow capacity
192        !! If sn_dens is redefined by the user, sn_capa needs to be reset
193        sn_capa = 2100.0_r_std*sn_dens
194
195
196        !Config Key   = NOBIO_WATER_CAPAC_VOLUMETRI
197        !Config Desc  =
198        !Config If    = OK_SECHIBA and .NOT.(HYDROL_CWRR)
199        !Config Def   = 150.
200        !Config Help  =
201        !Config Units = [s/m^2]
202        CALL getin_p('NOBIO_WATER_CAPAC_VOLUMETRI',mx_eau_nobio)
203
204       !! Check parameter value (correct range)
205        IF ( mx_eau_nobio <= zero ) THEN
206           CALL ipslerr_p(error_level, "config_soil_parameters.", &
207               &     "Wrong parameter value for NOBIO_WATER_CAPAC_VOLUMETRI.", &
208               &     "This parameter should be positive. ", &
209               &     "Please, check parameter value in run.def. ")
210        END IF
211
212
213        !Config Key   = SECHIBA_QSINT
214        !Config Desc  = Interception reservoir coefficient
215        !Config If    = OK_SECHIBA
216        !Config Def   = 0.1
217        !Config Help  = Transforms leaf area index into size of interception reservoir
218        !Config         for slowproc_derivvar or stomate
219        !Config Units = [m]
220        CALL getin_p('SECHIBA_QSINT',qsintcst)
221
222        !! Check parameter value (correct range)
223        IF ( qsintcst <= zero ) THEN
224           CALL ipslerr_p(error_level, "config_soil_parameters.", &
225                &     "Wrong parameter value for SECHIBA_QSINT.", &
226                &     "This parameter should be positive. ", &
227                &     "Please, check parameter value in run.def. ")
228        END IF
229
230
231        IF ( .NOT.(active_flags%hydrol_cwrr) ) THEN
232           
233           !Config Key   = CHOISNEL_DIFF_MIN
234           !Config Desc  = Diffusion constant for the slow regime
235           !Config If    = OK_SECHIBA and .NOT.(HYDROL_CWRR)
236           !Config Def   = 0.001
237           !Config Help  =
238           !Config Units = [kg/m^2/dt]
239           CALL getin_p('CHOISNEL_DIFF_MIN',min_drain)
240
241           !! Check parameter value (correct range)
242           IF ( min_drain <= zero ) THEN
243              CALL ipslerr_p(error_level, "config_soil_parameters.", &
244                   &     "Wrong parameter value for CHOISNEL_DIFF_MIN.", &
245                   &     "This parameter should be positive. ", &
246                   &     "Please, check parameter value in run.def. ")
247            END IF
248
249
250           !Config Key   = CHOISNEL_DIFF_MAX
251           !Config Desc  = Diffusion constant for the fast regime
252           !Config If    = OK_SECHIBA and .NOT.(HYDROL_CWRR)
253           !Config Def   = 0.1
254           !Config Help  =
255           !Config Units = [kg/m^2/dt]
256           CALL getin_p('CHOISNEL_DIFF_MAX',max_drain)
257
258           !! Check parameter value (correct range)
259           IF (  ( max_drain <= zero ) .OR. ( max_drain <= min_drain ) ) THEN
260              CALL ipslerr_p(error_level, "config_soil_parameters.", &
261                   &     "Wrong parameter value for CHOISNEL_DIFF_MAX.", &
262                   &     "This parameter should be positive or greater than CHOISNEL_DIFF_MIN.", &
263                   &     "Please, check parameter value in run.def. ")
264           END IF
265
266
267           !Config Key   = CHOISNEL_DIFF_EXP
268           !Config Desc  = The exponential in the diffusion law
269           !Config If    = OK_SECHIBA and .NOT.(HYDROL_CWRR)
270           !Config Def   = 1.5
271           !Config Help  =
272           !Config Units = [-]
273           CALL getin_p('CHOISNEL_DIFF_EXP',exp_drain)
274           
275           !! Check parameter value (correct range)
276           IF ( exp_drain <= zero ) THEN
277              CALL ipslerr_p(error_level, "config_soil_parameters.", &
278                   &     "Wrong parameter value for CHOISNEL_DIFF_EXP.", &
279                   &     "This parameter should be positive. ", &
280                   &     "Please, check parameter value in run.def. ")
281           END IF
282
283
284           !Config Key   = CHOISNEL_RSOL_CSTE
285           !Config Desc  = Constant in the computation of resistance for bare  soil evaporation
286           !Config If    = OK_SECHIBA and .NOT.(HYDROL_CWRR)
287           !Config Def   = 33.E3
288           !Config Help  =
289           !Config Units = [s/m^2]
290           CALL getin_p('CHOISNEL_RSOL_CSTE',rsol_cste)
291
292           !! Check parameter value (correct range)
293           IF ( rsol_cste <= zero ) THEN
294              CALL ipslerr_p(error_level, "config_soil_parameters.", &
295                   &     "Wrong parameter value for CHOISNEL_RSOL_CSTE.", &
296                   &     "This parameter should be positive. ", &
297                   &     "Please, check parameter value in run.def. ")
298           END IF
299
300
301           !Config Key   = HCRIT_LITTER
302           !Config Desc  = Scaling depth for litter humidity
303           !Config If    = OK_SECHIBA and .NOT.(HYDROL_CWRR)
304           !Config Def   = 0.08
305           !Config Help  =
306           !Config Units = [m]
307           CALL getin_p('HCRIT_LITTER',hcrit_litter)
308
309           !! Check parameter value (correct range)
310           IF ( hcrit_litter <= zero ) THEN
311              CALL ipslerr_p(error_level, "config_soil_parameters.", &
312                   &     "Wrong parameter value for HCRIT_LITTER.", &
313                   &     "This parameter should be positive. ", &
314                   &     "Please, check parameter value in run.def. ")
315           END IF
316
317        END IF
318     
319        END IF ! IF ( active_flags%ok_sechiba .AND. impose_param ) THEN
320     
321        first_call =.FALSE.
322       
323     ENDIF
324     
325   END SUBROUTINE config_soil_parameters
326   
327
328END MODULE constantes_soil
Note: See TracBrowser for help on using the repository browser.