SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
ini_surf_csts.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 SUBROUTINE ini_surf_csts
6 ! ##################
7 !
8 !!**** *INI_SURF_CSTS * - routine to initialize all surface parameter as
9 !! emissivity and albedo
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !!** METHOD
15 !! ------
16 !! The physical constants are set to their default numerical values
17 !! or specified in namelist NAM_SURF_CSTS
18 !!
19 !!
20 !! EXTERNAL
21 !! --------
22 !!
23 !!
24 !! IMPLICIT ARGUMENTS
25 !! ------------------
26 !!
27 !! REFERENCE
28 !! ---------
29 !!
30 !! AUTHOR
31 !! ------
32 !! B. Decharme * Meteo France *
33 !!
34 !! MODIFICATIONS
35 !! -------------
36 !! Original 08/2009
37 !! M Lafaysse 05/2014 : snow parameters
38 !! B. Decharme 05/13 : Add NAM_SURF_REPROD_OPER for versions reproductibility
39 !! P. Samuelsson 10/2014 MEB
40 !! B. Decharme 01/16 : Update XCFFV
41 !!
42 !-------------------------------------------------------------------------------
43 !
44 !* 0. DECLARATIONS
45 ! ------------
46 !
47 USE modd_surf_par, ONLY : xundef
48 USE modd_surf_conf, ONLY : cprogname
49 !
52 USE modd_meb_par, ONLY : xtau_lw, &
53  xragnc_factor, xkdelta_wr
54 USE modd_snow_par, ONLY : xemissn, xansmin, xansmax, &
55  xaglamin, xaglamax, xhgla, &
56  xwsnv, xz0sn, xz0hsn, &
57  xtau_smelt, &
58  xalbice1, xalbice2, xalbice3, &
59  xrhothreshold_ice, xz0icez0snow, &
60  xvaging_noglacier, xvaging_glacier, &
61  xpercentagepore, &
62  lmebrec, &
63  xansfracmel, xtempans, &
64  xansminmeb
65 !
66 USE modi_get_luout
67 USE modi_open_namelist
68 USE modi_close_namelist
69 USE mode_pos_surf
70 !
71 USE modd_reprod_oper, ONLY : xeverg_rsmin, xeverg_veg, &
72  cdgavg, cimplicit_wind, &
73  cqsat, ccharnock, cdgdif
75 !
76 USE yomhook ,ONLY : lhook, dr_hook
77 USE parkind1 ,ONLY : jprb
78 !
79 IMPLICIT NONE
80 !
81 INTEGER :: iluout ! unit of output listing file
82 INTEGER :: ilunam ! namelist file logical unit
83 LOGICAL :: gfound ! true if namelist is found
84 !
85 LOGICAL :: lreprod_oper
86 !
87 REAL(KIND=JPRB) :: zhook_handle
88 !
89 namelist/nam_surf_csts/ xemissn, xansmin, xansmax, xaglamin, xaglamax, &
90  xalbwat, xalbcoef_ta96, xalbsca_wat, xemiswat, &
91  xalbwatice, xemiswatice, xhgla, xwsnv, xcffv, &
92  xz0sn, xz0hsn, xtau_smelt, xalbseaice, &
93  xz0flood, xalbwatsnow, &
94  lmebrec, &
95  xansfracmel, xtempans, xansminmeb, &
96  xtau_lw, xragnc_factor
97 !
98 namelist/nam_surf_snow_csts/ xz0icez0snow, xrhothreshold_ice, &
99  xalbice1, xalbice2, xalbice3, &
100  xvaging_noglacier, xvaging_glacier, &
101  xpercentagepore
102 !
103 namelist/nam_reprod_oper/ lreprod_oper, xeverg_rsmin, xeverg_veg, &
104  cdgavg, cdgdif, cimplicit_wind, cqsat, &
105  ccharnock
106 !
107 !-------------------------------------------------------------------------------
108 !* 0. INIT
109 !-------------------------------------------------------------------------------
110 !
111 IF (lhook) CALL dr_hook('INI_SURF_CSTS',0,zhook_handle)
112 !
113 xalbwat = xundef
114 xalbseaice = xundef
115 xalbwatice = xundef
116 xalbwatsnow = xundef
117 xemiswat = xundef
118 xemiswatice = xundef
119 xemissn = xundef
120 !
121 !-------------------------------------------------------------------------------
122 !* 1. Default values
123 !-------------------------------------------------------------------------------
124 !
125 ! Minimum and maximum values of the albedo of snow:
126 !
127 xansmin = 0.50 ! (-)
128 xansmax = 0.85 ! (-)
129 !
130 ! Minimum and maximum values of the albedo of permanet snow/ice:
131 !
132 xaglamin = 0.8 ! (-)
133 xaglamax = 0.85 ! (-)
134 !
135 ! Use recommended settings for snow albedo (FALSE = ISBA default)
136 !
137 lmebrec=.false.
138 !
139 ! Fraction of maximum value of the albedo of snow that is reached for melting
140 ! snow
141 !
142 xansfracmel = 1.0 ! (-)
143 !
144 ! Threeshold temperature above which the snow albedo starts to decrease
145 !
146 xtempans = 274.15 ! (K)
147 !
148 ! Minimum value of the albedo of snow reached under canopy vegetation:
149 !
150 xansminmeb = 0.30 ! (-)
151 !
152 ! Height of aged snow in glacier case (allows Pn=1)
153 !
154 xhgla = 33.3 !(m)
155 !
156 ! Coefficient for calculation of snow fraction over vegetation
157 !
158 xwsnv = 5.0 !(-)
159 !
160 ! Water direct albedo coefficient (option "TA96")
161 !
162 xalbcoef_ta96 = 0.037
163 !
164 ! Water diffuse albedo
165 !
166 xalbsca_wat = 0.06
167 
168 ! Coefficient for calculation of floodplain fraction over vegetation
169 !
170 xcffv = 4.0
171 !
172 ! Roughness length of pure snow surface (m)
173 !
174 xz0sn = 0.001
175 !
176 ! Roughness length for heat of pure snow surface (m)
177 !
178 xz0hsn = 0.0001
179 !
180 ! Snow Melt timescale with D95 (s): needed to prevent time step
181 ! dependence of melt when snow fraction < unity.
182 !
183 xtau_smelt = 300.
184 !
185 ! Extinction coefficient for view factor for long-wave radiation
186 !
187 xtau_lw = 0.5 ! -
188 !
189 ! MEB resistance increase factor for canopy air sapce.
190 ! If=1, then NO effect. It is generally >=1
191 ! and is needed because the original parameterization
192 ! does not account for extremely stable conditions,
193 ! such as over a snowpack.
194 !
195 xragnc_factor= 200. ! -
196 !
197 ! MEB maximum intercepted water fraction (on vegetation)
198 !
199 xkdelta_wr = 0.25 ! -
200 !
201 ! NAM_SURF_SNOW_CSTS
202 !
203 ! Roughness length ratio between ice and snow
204 xz0icez0snow = 10.
205 !
206 ! 3 bands spectral albedo for glacier ice (CROCUS)
207 ! Default values from Lejeune et al 2009 (Zongo, Bolivia)
208 xalbice1 = 0.38
209 xalbice2 = 0.23
210 xalbice3 = 0.08
211 !
212 ! Gerbaux et al 2005 (Saint Sorlin)
213 ! PALBICE1=0.23
214 ! PALBICE2=0.16
215 ! PALBICE3=0.05
216 !
217 ! Density threshold for ice detection kg.m-3
218 xrhothreshold_ice = 850.
219 !
220 ! Parameters for ageing effect on albedo
221 xvaging_noglacier = 60.
222 xvaging_glacier = 900.
223 
224 ! percentage of the total pore volume to compute the max liquid water holding capacity !Pahaut 1976
225 xpercentagepore = 0.05
226 !
227 ! Roughness length for flood (m)
228 !
229 xz0flood = 0.0002
230 !-------------------------------------------------------------------------------
231 !
232 ! * Reproductibility for SURFEX OPER
233 !
234 lreprod_oper = .false. ! default
235 !
236 ! * Vegetation parameters for tropical forest
237 !
238 !XEVERG_RSMIN : old = 250. (Manzi 1993) but observations range
239 ! from 140 to 180. According to Delire et al. (1997) and
240 ! new tests over 6 local sites, 175. is recommended
241 ! Should be the default after check with AROME/ALADIN
242 !
243 xeverg_rsmin = 175. !Rsmin
244 !
245 !XEVERG_VEG : old = 0.99 (Manzi 1993) but according to Delire et al. (1997) and
246 ! new tests over 6 local sites, 1.0 is recommended because 0.99
247 ! induces unrealistic bare soil evaporation for Tropical forest
248 ! Should be the default after check with AROME/ALADIN
249 !
250 xeverg_veg = 1.0 !Veg fraction
251 !
252 ! * Soil depth average
253 !
254  cdgavg = 'INV'
255 !
256 ! * Soil depth with ISBA-DF
257 !
258  cdgdif = 'ROOT'
259 !
260 ! * wind implicitation option
261 !
262  cimplicit_wind = 'NEW'
263 !
264 ! * qsat computation
265 !
266  cqsat = 'NEW'
267 !
268 ! * Charnock parameter
269 !
270  ccharnock = 'NEW'
271 !
272 !-------------------------------------------------------------------------------
273 !* 2. User values
274 !-------------------------------------------------------------------------------
275 !
276  CALL get_luout(cprogname,iluout)
277 !
278  CALL open_namelist(cprogname,ilunam)
279 !
280  CALL posnam(ilunam,'NAM_SURF_CSTS',gfound,iluout)
281 IF (gfound) READ(unit=ilunam,nml=nam_surf_csts)
282 !
283 IF(lmebrec)THEN
284 ! Fraction of maximum value of the albedo of snow that is reached for melting
285 ! snow
286 !
287  xansfracmel = 0.85 ! (-)
288 !
289 ! Threeshold temperature above which the snow albedo starts to decrease
290 !
291  xtempans = 268.15 ! (K)
292 !
293 ENDIF
294 !
295  CALL posnam(ilunam,'NAM_SURF_SNOW_CSTS',gfound,iluout)
296 IF (gfound) READ(unit=ilunam,nml=nam_surf_snow_csts)
297 !
298 !-------------------------------------------------------------------------------
299 !* 3. For Reproductibility
300 !-------------------------------------------------------------------------------
301 !
302  CALL posnam(ilunam,'NAM_REPROD_OPER',gfound,iluout)
303 IF (gfound) READ(unit=ilunam,nml=nam_reprod_oper)
304 !
305  CALL test_nam_var_surf(iluout,'CDGAVG',cdgavg,'ARI','INV')
306  CALL test_nam_var_surf(iluout,'CDGDIF',cdgdif,'SOIL','ROOT')
307  CALL test_nam_var_surf(iluout,'CIMPLICIT_WIND',cimplicit_wind,'NEW','OLD')
308  CALL test_nam_var_surf(iluout,'CQSAT',cimplicit_wind,'NEW','OLD')
309  CALL test_nam_var_surf(iluout,'CCHARNOCK',cimplicit_wind,'NEW','OLD')
310 !
311  CALL test_nam_var_surf(iluout,'XEVERG_RSMIN',xeverg_rsmin,175.0,250.0)
312  CALL test_nam_var_surf(iluout,'XEVERG_VEG',xeverg_veg,1.0,0.99)
313 !
314 IF(lreprod_oper)THEN
315  xeverg_rsmin = 250.
316  xeverg_veg = 0.99
317  cdgavg = 'ARI'
318  cqsat = 'OLD'
319  ccharnock = 'OLD'
320 ENDIF
321 !
322 ! Water global albedo (option "UNIF")
323 !
324 IF(xalbwat==xundef)THEN
325  IF(lreprod_oper)THEN
326  xalbwat = 0.135
327  ELSE
328  xalbwat = 0.065
329  ENDIF
330 ENDIF
331 !
332 ! Sea ice albedo
333 !
334 IF(xalbseaice==xundef)THEN
335  IF(lreprod_oper)THEN
336  xalbseaice = 0.85
337  ELSE
338  xalbseaice = 0.71
339  ENDIF
340 ENDIF
341 !
342 ! water ice and snow albedo
343 !
344 IF(xalbwatice==xundef)THEN
345  IF(lreprod_oper)THEN
346  xalbwatice = 0.85
347  ELSE
348  xalbwatice = 0.40
349  ENDIF
350 ENDIF
351 !
352 IF(xalbwatsnow==xundef)THEN
353  IF(lreprod_oper)THEN
354  xalbwatsnow = 0.85
355  ELSE
356  xalbwatsnow = 0.60
357  ENDIF
358 ENDIF
359 !
360 ! Water emissivity
361 !
362 IF(xemiswat==xundef)THEN
363  IF(lreprod_oper)THEN
364  xemiswat = 0.98
365  ELSE
366  xemiswat = 0.96
367  ENDIF
368 ENDIF
369 !
370 ! Sea ice emissivity
371 !
372 IF(xemiswatice==xundef)THEN
373  IF(lreprod_oper)THEN
374  xemiswatice = 1.0
375  ELSE
376  xemiswatice = 0.97
377  ENDIF
378 ENDIF
379 !
380 !
381 ! Snow emissivity:
382 !
383 IF(xemissn==xundef)THEN
384  IF(lreprod_oper)THEN
385  xemissn = 1.0
386  ELSE
387  xemissn = 0.99
388  ENDIF
389 ENDIF
390 !
391 !-------------------------------------------------------------------------------
392 !
393  CALL close_namelist(cprogname,ilunam)
394 !
395 IF (lhook) CALL dr_hook('INI_SURF_CSTS',1,zhook_handle)
396 !
397 !-------------------------------------------------------------------------------
398 !
399 END SUBROUTINE ini_surf_csts
subroutine ini_surf_csts
subroutine close_namelist(HPROGRAM, KLUNAM)
subroutine posnam(KULNAM, HDNAML, OFOUND, KLUOUT)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine open_namelist(HPROGRAM, KLUNAM, HFILE)