SURFEX v8.1
General documentation of Surfex
snowcro.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 ! ##########################################################################
6  SUBROUTINE snowcro(HSNOWRES, TPTIME, OGLACIER, HIMPLICIT_WIND, &
7  PPEW_A_COEF, PPEW_B_COEF, &
8  PPET_A_COEF, PPEQ_A_COEF, PPET_B_COEF, PPEQ_B_COEF, &
9  PSNOWSWE,PSNOWRHO,PSNOWHEAT,PSNOWALB, &
10  PSNOWGRAN1,PSNOWGRAN2,PSNOWHIST,PSNOWAGE, &
11  PTSTEP,PPS,PSR,PRR,PPSN3L, &
12  PTA,PTG,PSW_RAD,PQA,PVMOD,PLW_RAD, PRHOA, &
13  PUREF,PEXNS,PEXNA,PDIRCOSZW, &
14  PZREF,PZ0,PZ0EFF,PZ0H,PALB, &
15  PSOILCOND,PD_G, &
16  PSNOWLIQ,PSNOWTEMP,PSNOWDZ, &
17  PTHRUFAL,PGRNDFLUX,PEVAPCOR,PRNSNOW,PHSNOW,PGFLUXSNOW, &
18  PHPSNOW,PLES3L,PLEL3L,PEVAP,PSNDRIFT,PRI, &
19  PEMISNOW,PCDSNOW,PUSTAR,PCHSNOW,PSNOWHMASS,PQS, &
20  PPERMSNOWFRAC,PZENITH,PXLAT,PXLON, &
21  OSNOWDRIFT,OSNOWDRIFT_SUBLIM,OSNOW_ABS_ZENITH, &
22  HSNOWMETAMO,HSNOWRAD)
23 ! ##########################################################################
24 !
25 !!**** *SNOWCRO*
26 !!
27 !! PURPOSE
28 !! -------
29 !
30 ! Detailed snowpack scheme Crocus, computationnally based on the
31 ! 3-Layer snow scheme option (Boone and Etchevers 1999)
32 ! For shallow snow cover, Default method of Douville et al. (1995)
33 ! used with this option: Model "turns on" when snow sufficiently
34 ! deep/above some preset critical snow depth.
35 !
36 !
37 !
38 !
39 !!** METHOD
40 !! ------
41 !
42 ! Direct calculation
43 !
44 !! EXTERNAL
45 !! --------
46 !
47 ! None
48 !!
49 !! IMPLICIT ARGUMENTS
50 !! ------------------
51 !!
52 !!
53 !!
54 !! REFERENCE
55 !! ---------
56 !!
57 !! ISBA: Belair (1995)
58 !! ISBA: Noilhan and Planton (1989)
59 !! ISBA: Noilhan and Mahfouf (1996)
60 !! ISBA-ES: Boone and Etchevers (2001)
61 !! Crocus : Brun et al., 1989 (J. Glaciol.)
62 !! Crocus : Brun et al., 1992 (J. Glaciol.)
63 !! Crocus : Vionnet et al., in prep (Geosci. Mod. Devel. Discuss.)
64 !!
65 !!
66 !! AUTHOR
67 !! ------
68 !! A. Boone * Meteo-France *
69 !! V. Vionnet * Meteo-France *
70 !! E. Brun * Meteo-France *
71 !!
72 !! MODIFICATIONS
73 !! -------------
74 !! Original 7/99
75 !! Modified by A.Boone 05/02 (code, not physics)
76 !! Modified by A.Boone 11/04 i) maximum density limit imposed (although
77 !! rarely if ever reached), ii) check to
78 !! see if upermost layer completely sublimates
79 !! during a timestep (as snowpack becomes vanishly
80 !! thin), iii) impose maximum grain size limit
81 !! in radiation transmission computation.
82 !!
83 !! Modified by B. Decharme (03/2009): Consistency with Arpege permanent
84 !! snow/ice treatment (LGLACIER for alb)
85 !! Modified by A. Boone (04/2010): Implicit coupling and replace Qsat and DQsat
86 !! by Qsati and DQsati, respectively.
87 !! Modified by E. Brun, V. Vionnet, S. Morin (05/2011):
88 !! Addition of Crocus processes and
89 !! parametrizations to
90 !! the SNOW-3L code. This includes the dynamic handling
91 !! of snow layers and the inclusion of snow metamorphism
92 !! rules similar to the original Crocus implementation.
93 !! Modified by B. Decharme (09/2012): New wind implicitation
94 !!
95 !! Modified by M. Lafaysse (07/2012) :
96 !! * Albedo and roughness parametrizations
97 !! for surface ice over glaciers
98 !! MODIF 2012-10-03 : don't modify roughness if implicit coupling
99 !! (test PPEW_A_COEF == 0. )
100 !! * SNOWCROALB is now called by SNOWCRORAD to remove duplicated code
101 !! * Parameters for albedo are moved to modd_snow_par
102 !! * PSNOWAGE is stored as an age
103 !! (days since snowfall) and not as a date
104 !! to allow spinup simulations
105 !! * New rules for optimal discretization of very thick snowpacks
106 !! * Optional outputs for debugging
107 !!
108 !! Modified by E. Brun and M. Lafaysse (07/2012) :
109 !! * Implement sublimation in SNOWDRIFT
110 !! * Flag in namelist to activate SNOWDRIFT and SNOWDRIFT_SUBLIM
111 !! Modified by E. Brun and M. Lafaysse (08/2012) :
112 !! * XUEPSI replaced by 0 in the if statement of case 1.3.3.2 (SNOWCROMETAMO)
113 !! * If SNOWDRIFT is activated the wind do not modify grain types during snowfall
114 !! (redundant with snowdrift)
115 !! Modified by E. Brun (24/09/2012) :
116 !! * Correction coupling coefficient for specific humidity in SNOWCROEBUD
117 !! * PSFCFRZ(:) = 1.0 for systematic solid/vapor latent fluxes in SNOWCROEBUD
118 !! Modified by C. Carmagnola (3/2013):
119 !! * Dendricity and size replaced by the optical diameter
120 !! * Test of different evolution laws for the optical diameter
121 !!
122 !! Modified by B. Decharme (08/2013): Qsat as argument (needed for coupling with atm)
123 !! add PSNDRIFT
124 !!
125 !!
126 !-------------------------------------------------------------------------------
127 !
128 !* 0. DECLARATIONS
129 ! ------------
130 !
132 !
133 USE modd_csts, ONLY : xtt, xrholw, xlmtt,xlstt,xlvtt, xcl, xci, xpi, xrholi
134 USE modd_snow_par, ONLY : xz0icez0snow, xrhothreshold_ice, xpercentagepore
137 !
138 USE mode_snow3l
139 USE mode_tartes, ONLY : snowcro_tartes
140 !
141 USE mode_crodebug
142 !
143 USE modi_abor1_sfx
144 !
145 USE yomhook ,ONLY : lhook, dr_hook
146 USE parkind1 ,ONLY : jprb
147 !
148 ! this module is not used anymore
149 ! USE MODI_GREGODSTRATI
150 !
151 IMPLICIT NONE
152 !
153 !
154 !* 0.1 declarations of arguments
155 !
156 REAL, INTENT(IN) :: PTSTEP
157 ! PTSTEP = time step of the integration
158 TYPE(date_time), INTENT(IN) :: TPTIME ! current date and time
159 !
160  CHARACTER(LEN=*), INTENT(IN) :: HSNOWRES
161 ! HSNOWRES = ISBA-SNOW3L turbulant exchange option
162 ! 'DEF' = Default: Louis (ISBA: Noilhan and Mahfouf 1996)
163 ! 'RIL' = Limit Richarson number under very stable
164 ! conditions (currently testing)
165 LOGICAL, INTENT(IN) :: OGLACIER ! True = Over permanent snow and ice,
166 ! initialise WGI=WSAT,
167 ! Hsnow>=10m and allow 0.8<SNOALB<0.85
168  ! False = No specific treatment
169 !
170  CHARACTER(LEN=*), INTENT(IN) :: HIMPLICIT_WIND ! wind implicitation option
171 ! ! 'OLD' = direct
172 ! ! 'NEW' = Taylor serie, order 1
173 !
174 REAL, DIMENSION(:), INTENT(IN) :: PPS, PTA, PSW_RAD, PQA, PVMOD, PLW_RAD, PSR, PRR
175 ! PSW_RAD = incoming solar radiation (W/m2)
176 ! PLW_RAD = atmospheric infrared radiation (W/m2)
177 ! PRR = rain rate [kg/(m2 s)]
178 ! PSR = snow rate (SWE) [kg/(m2 s)]
179 ! PTA = atmospheric temperature at level za (K)
180 ! PVMOD = modulus of the wind parallel to the orography (m/s)
181 ! PPS = surface pressure
182 ! PQA = atmospheric specific humidity
183 ! at level za
184 !
185 REAL, DIMENSION(:), INTENT(IN) :: PTG, PSOILCOND, PD_G, PPSN3L
186 ! PTG = Surface soil temperature (effective
187 ! temperature the of layer lying below snow)
188 ! PSOILCOND = soil thermal conductivity [W/(m K)]
189 ! PD_G = Assumed first soil layer thickness (m)
190 ! Used to calculate ground/snow heat flux
191 ! PPSN3L = snow fraction
192 !
193 REAL, DIMENSION(:), INTENT(IN) :: PZREF, PUREF, PEXNS, PEXNA, PDIRCOSZW, PRHOA, PZ0, PZ0EFF, &
194  PALB, PZ0H, PPERMSNOWFRAC
195 ! PZ0EFF = roughness length for momentum
196 ! PZ0 = grid box average roughness length
197 ! PZ0H = grid box average roughness length for heat
198 ! PZREF = reference height of the first
199 ! atmospheric level
200 ! PUREF = reference height of the wind
201 ! PRHOA = air density
202 ! PEXNS = Exner function at surface
203 ! PEXNA = Exner function at lowest atmos level
204 ! PDIRCOSZW = Cosinus of the angle between the
205 ! normal to the surface and the vertical
206 ! PALB = soil/vegetation albedo
207 ! PPERMSNOWFRAC = fraction of permanet snow/ice
208 !
209 REAL, DIMENSION(:), INTENT(IN) :: PPEW_A_COEF, PPEW_B_COEF, &
210  PPET_A_COEF, PPEQ_A_COEF, PPET_B_COEF, &
211  PPEQ_B_COEF
212 ! PPEW_A_COEF = wind coefficient (m2s/kg)
213 ! PPEW_B_COEF = wind coefficient (m/s)
214 ! PPET_A_COEF = A-air temperature coefficient
215 ! PPET_B_COEF = B-air temperature coefficient
216 ! PPEQ_A_COEF = A-air specific humidity coefficient
217 ! PPEQ_B_COEF = B-air specific humidity coefficient
218 !
219 REAL, DIMENSION(:), INTENT(INOUT) :: PSNOWALB
220 ! PSNOWALB = Prognostic surface snow albedo
221 ! (does not include anything but
222 ! the actual snow cover)
223 !
224 REAL, DIMENSION(:,:), INTENT(INOUT) :: PSNOWHEAT, PSNOWRHO, PSNOWSWE
225 ! PSNOWHEAT = Snow layer(s) heat content (J/m2)
226 ! PSNOWRHO = Snow layer(s) averaged density (kg/m3)
227 ! PSNOWSWE = Snow layer(s) liquid Water Equivalent (SWE:kg m-2)
228 !
229 REAL, DIMENSION(:,:), INTENT(INOUT) :: PSNOWGRAN1, PSNOWGRAN2, PSNOWHIST
230 ! PSNOWGRAN1 = Snow layers grain feature 1
231 ! PSNOWGRAN2 = Snow layer grain feature 2
232 ! PSNOWHIST = Snow layer grain historical
233 ! parameter (only for non
234 ! dendritic snow)
235 REAL, DIMENSION(:,:), INTENT(INOUT) :: PSNOWAGE ! Snow grain age
236 !
237 REAL, DIMENSION(:,:), INTENT(OUT) :: PSNOWLIQ, PSNOWTEMP, PSNOWDZ
238 ! PSNOWLIQ = Snow layer(s) liquid water content (m)
239 ! PSNOWTEMP = Snow layer(s) temperature (m)
240 ! PSNOWDZ = Snow layer(s) thickness (m)
241 !
242 REAL, DIMENSION(:), INTENT(OUT) :: PTHRUFAL, PGRNDFLUX, PEVAPCOR
243 ! PTHRUFAL = rate that liquid water leaves snow pack:
244 ! paritioned into soil infiltration/runoff
245 ! by ISBA [kg/(m2 s)]
246 ! PGRNDFLUX = soil/snow interface heat flux (W/m2)
247 ! PEVAPCOR = evaporation/sublimation correction term:
248 ! extract any evaporation exceeding the
249 ! actual snow cover (as snow vanishes)
250 ! and apply it as a surface soil water
251 ! sink. [kg/(m2 s)]
252 !
253 REAL, DIMENSION(:), INTENT(OUT) :: PRNSNOW, PHSNOW, PGFLUXSNOW, PLES3L, PLEL3L, &
254  PHPSNOW, PCDSNOW, PUSTAR, PEVAP, PSNDRIFT
255 ! PLES3L = evaporation heat flux from snow (W/m2)
256 ! PLEL3L = sublimation (W/m2)
257 ! PHPSNOW = heat release from rainfall (W/m2)
258 ! PRNSNOW = net radiative flux from snow (W/m2)
259 ! PHSNOW = sensible heat flux from snow (W/m2)
260 ! PGFLUXSNOW = net heat flux from snow (W/m2)
261 ! PCDSNOW = drag coefficient for momentum over snow
262 ! PUSTAR = friction velocity over snow (m/s)
263 ! PEVAP = total evaporative flux (kg/m2/s)
264 ! PSNDRIFT = blowing snow sublimation (kg/m2/s)
265 !
266 REAL, DIMENSION(:), INTENT(OUT) :: PCHSNOW, PEMISNOW, PSNOWHMASS
267 ! PEMISNOW = snow surface emissivity
268 ! PCHSNOW = drag coefficient for heat over snow
269 ! PSNOWHMASS = heat content change due to mass
270 ! changes in snowpack (J/m2): for budget
271 ! calculations only.
272 !
273 REAL, DIMENSION(:), INTENT(OUT) :: PRI, PQS
274 ! PRI = Ridcharson number
275 ! PQS = surface humidity
276 !
277 REAL, DIMENSION(:), INTENT(IN) :: PZENITH ! solar zenith angle
278 REAL, DIMENSION(:), INTENT(IN) :: PXLAT,PXLON ! LAT/LON after packing
279 !
280 LOGICAL, INTENT(IN) :: OSNOWDRIFT, OSNOWDRIFT_SUBLIM ! activate snowdrift, sublimation during drift
281 LOGICAL, INTENT(IN) :: OSNOW_ABS_ZENITH ! activate parametrization of solar absorption for polar regions
282  CHARACTER(3), INTENT(IN) :: HSNOWMETAMO, HSNOWRAD
283  !-----------------------
284  ! Metamorphism scheme
285  ! HSNOWMETAMO=B92 Brun et al 1992
286  ! HSNOWMETAMO=C13 Carmagnola et al 2014
287  ! HSNOWMETAMO=T07 Taillandier et al 2007
288  ! HSNOWMETAMO=F06 Flanner et al 2006
289  !-----------------------
290  ! Radiative transfer scheme
291  ! HSNOWMETAMO=B92 Brun et al 1992
292  ! HSNOWMETAMO=TAR TARTES (Libois et al 2013)
293  ! HSNOWMETAMO=TA1 TARTES with constant impurities
294  ! HSNOWMETAMO=TA2 TARTES with constant impurities as function of ageing
295  !-----------------------
296 !* 0.2 declarations of local variables
297 !
298 REAL, DIMENSION(SIZE(PSNOWRHO,1),SIZE(PSNOWRHO,2),NPNIMP) :: ZSNOWIMP_DENSITY !impurities density (kg/m^3) (npoints,nlayer,ntypes_impurities)
299 REAL, DIMENSION(SIZE(PSNOWRHO,1),SIZE(PSNOWRHO,2),NPNIMP) :: ZSNOWIMP_CONTENT !impurities content (g/g) (npoints,nlayer,ntypes_impurities)
300 !
301 REAL, DIMENSION(SIZE(PSNOWRHO,1),SIZE(PSNOWRHO,2)) :: ZSNOWTEMP, ZSCAP, ZSNOWDZN, ZSCOND, ZRADSINK
302 ! ZSNOWTEMP = Snow layer(s) averaged temperature (K)
303 ! ZSCAP = Snow layer(s) heat capacity [J/(K m3)]
304 ! ZSNOWDZN = Updated snow layer thicknesses (m)
305 ! ZSCOND = Snow layer(s) thermal conducivity [W/(m K)]
306 ! ZRADSINK = Snow solar Radiation source terms (W/m2)
307 !
308 REAL, DIMENSION(SIZE(PSNOWRHO,1),SIZE(PSNOWRHO,2)) :: ZWHOLDMAX
309 !
310 !For now these values are constant
311 REAL, DIMENSION(SIZE(PSNOWRHO,1),SIZE(PSNOWRHO,2)) :: ZSNOWG0 ! asymmetry parameter of snow grains at nr=1.3 and at non absorbing wavelengths (no unit) (npoints,nlayer)
312 REAL, DIMENSION(SIZE(PSNOWRHO,1),SIZE(PSNOWRHO,2)) :: ZSNOWY0 ! Value of y of snow grains at nr=1.3 (no unit
313 REAL, DIMENSION(SIZE(PSNOWRHO,1),SIZE(PSNOWRHO,2)) :: ZSNOWW0 ! Value of W of snow grains at nr=1.3 (no unit)
314 REAL, DIMENSION(SIZE(PSNOWRHO,1),SIZE(PSNOWRHO,2)) :: ZSNOWB0 ! absorption enhancement parameter of snow grains at nr=1.3 and at non absorbing wavelengths (no unit)
315 !
316 !spectral albedo (3 bands for now) :: ready to output if necessary
317 REAL, DIMENSION(SIZE(PSNOWRHO,1),3) :: ZSPECTRALALBEDO
318 !
319 REAL, DIMENSION(SIZE(PTA)) :: ZSNOWBIS
320 ! ZSNOWBIS = Total snow depth after snowfall
321 !
322 REAL, DIMENSION(SIZE(PTA)) :: ZSNOW, ZSFCFRZ, ZTSTERM1, ZTSTERM2, ZCT, ZRA, ZSNOWFLUX, ZSNOWTEMPO1
323 ! ZSNOW = Total snow depth (m)
324 ! ZCT = inverse of the product of snow heat capacity
325 ! and layer thickness [(m2 K)/J]
326 ! ZRA = Surface aerodynamic resistance
327 ! ZTSTERM1,ZTSTERM2 = Surface energy budget coefficients
328 ! ZSNOWFLUX = heat flux between 1st and 2nd snow layers:
329 ! used during surface melting (W/m2)
330 ! ZSNOWTEMPO1= value of uppermost snow temperature
331 ! before time integration (K)
332 !
333 REAL, DIMENSION(SIZE(PTA)) :: ZRSRA, ZDQSAT, ZQSAT, ZRADXS, ZLIQHEATXS, ZLWUPSNOW
334 ! ZRSRA = air density over aerodynamic resistance
335 ! ZDQSAT = derrivative of saturation specific humidity
336 ! ZQSAT = saturation specific humidity
337 ! ZRADXS = shortwave radiation absorbed by soil surface
338 ! (for thin snow sover) (W m-2)
339 ! ZLIQHEATXS = excess snowpack heating for vanishingly thin
340 ! snow cover: add energy to snow/ground heat
341 ! flux (W m-2)
342 ! ZLWUPSNOW = upwelling longwave raaditive flux (W m-2)
343 !
344 REAL, DIMENSION(SIZE(PTA)) :: ZUSTAR2_IC, ZTA_IC, ZQA_IC, &
345  ZPET_A_COEF_T, ZPEQ_A_COEF_T, ZPET_B_COEF_T, ZPEQ_B_COEF_T
346 ! ZUSTAR2_IC = implicit lowest atmospheric level friction (m2/s2)
347 ! ZTA_IC = implicit lowest atmospheric level air temperature
348 ! ZQA_IC = implicit lowest atmospheric level specific humidity
349 ! ZPET_A_COEF_T = transformed A-air temperature coefficient
350 ! ZPET_B_COEF_T = transformed B-air temperature coefficient
351 ! ZPEQ_A_COEF_T = transformed A-air specific humidity coefficient
352 ! ZPEQ_B_COEF_T = transformed B-air specific humidity coefficient
353 !
354 REAL, DIMENSION(SIZE(PTA)) :: ZSNOWRHOF, ZSNOWDZF, ZSNOWGRAN1F, ZSNOWGRAN2F, ZSNOWHISTF
355 REAL, DIMENSION(SIZE(PTA)) :: ZSNOWAGEF
356 
357 ! New roughness lengths in case of glaciers without snow.
358 REAL, DIMENSION(SIZE(PTA)) :: ZZ0_SNOWICE, ZZ0H_SNOWICE, ZZ0EFF_SNOWICE
359 !
360 !To control and print eneregy balance
361 REAL , DIMENSION(SIZE(PTA)) :: ZSUMMASS_INI,ZSUMHEAT_INI,ZSUMMASS_FIN,ZSUMHEAT_FIN
362 !
363 REAL, DIMENSION(SIZE(PTA)) :: ZMASSBALANCE, ZENERGYBALANCE, ZEVAPCOR2
364 !
365 INTEGER, DIMENSION(SIZE(PTA)) :: INLVLS_USE ! varying number of effective layers
366 !
367 LOGICAL, DIMENSION(SIZE(PTA)) :: GSNOWFALL,GMODIF_MAILLAGE
368 ! GSNOWFALL = FLAG if snowfall exceed PSNOW/10, used for
369 ! grid updating.
370 !
371 REAL :: ZTSTEPDAYS ! time step in days
372 !
373 LOGICAL :: GCOND_GRAIN, GCOND_YEN
374 !
375 LOGICAL :: GCROINFOPRINT ! print daily informations
376 LOGICAL :: GCRODEBUGPRINT, GCRODEBUGDETAILSPRINT, GCRODEBUGPRINTATM ! print diagnostics for debugging
377 LOGICAL :: GCRODEBUGPRINTBALANCE
378 !
379 INTEGER :: JJ,JST ! looping indexes
380 INTEGER :: IPRINT ! gridpoint number to be printed
381 INTEGER :: IDEBUG
382 !
383 REAL(KIND=JPRB) :: ZHOOK_HANDLE
384 !
385 IF (lhook) CALL dr_hook('SNOWCRO',0,zhook_handle)
386 !
387 !***************************************PRINT IN**********************************************
388 ! Look if we have to print snow profiles for debugging
389 gcroinfoprint = lcrodailyinfo .AND. (tptime%TIME ==0.0)
390 !***************************************PRINT OUT*********************************************
391 !***************************************DEBUG IN**********************************************
392 gcrodebugprintbalance = ( tptime%TDATE%YEAR*10000 + tptime%TDATE%MONTH*100 + tptime%TDATE%DAY &
393  >= ntimecrodebug ) .AND. &
394  ( tptime%TIME/3600. >= nhourcrodebug ) .AND. &
395  ( tptime%TDATE%YEAR*10000 + tptime%TDATE%MONTH*100 + tptime%TDATE%DAY &
396  < nendcrodebug )
397 !
398 IF (lcrodebug) THEN
399  gcrodebugprint = gcrodebugprintbalance
400  gcrodebugdetailsprint = lcrodebugdetails .AND. gcrodebugprint
401  gcrodebugprintatm = lcrodebugatm .AND. gcrodebugprint
402 ELSE
403  gcrodebugprint = .false.
404  gcrodebugdetailsprint = .false.
405  gcrodebugprintatm = .false.
406 END IF
407 
408 !
409 ! Look if we have to compute and print energy balance control
410 gcrodebugprintbalance = lcontrolbalance .AND. gcrodebugprintbalance
411 !
412 IF ( lcrodebug .OR. gcroinfoprint .OR. gcrodebugprintbalance ) THEN
413  !
414  IF ( xlatcrodebug >= -90 .AND. xloncrodebug >= -180. ) THEN
415  CALL getpoint_crodebug(pxlat,pxlon,idebug)
416  ELSE
417  idebug = npointcrodebug
418  END IF
419  !
420  ! For parallel runs : we just want to do this for the thread where there is this point.
421  IF ( xlatcrodebug >= -90 .AND. xloncrodebug >= -180. ) THEN
422  IF ( abs( pxlat(idebug)-xlatcrodebug ) + abs(pxlon(idebug) - xloncrodebug) > 0.1 ) THEN
423  gcrodebugprint = .false.
424  gcrodebugdetailsprint = .false.
425  gcrodebugprintatm = .false.
426  END IF
427  END IF
428  !
429 END IF
430 !***************************************DEBUG OUT*********************************************
431 !
432 IF ( hsnowrad=="TAR" .OR. hsnowrad=="TA1" .OR. hsnowrad=="TA2" ) THEN
433  !For now fix constant values
434  zsnowg0 = xpsnowg0
435  zsnowy0 = xpsnowy0
436  zsnoww0 = xpsnoww0
437  zsnowb0 = xpsnowb0
438  !
439  zsnowimp_density = 1500.
440  ! ZSNOWIMP_CONTENT=25.0E-9
441  !
442 END IF
443 !
444 zustar2_ic = 0.0
445 zta_ic = 0.0
446 zqa_ic = 0.0
447 !
448 gcond_grain = .true.
449 gcond_yen = .true.!FALSE. !(if TRUE : use of the Yen (1981) thermal conductivity paramztrization ;
450 ! otherwise, use the default ISBA-ES thermal conductivity parametrization)
451 !
452 pgrndflux = 0.
453 psnowhmass = 0.
454 phsnow = 0.
455 prnsnow = 0.
456 ples3l = 0.
457 plel3l = 0.
458 phpsnow = 0.
459 pevapcor = 0.
460 pthrufal = 0.
461 !
462 ! pour imprimer des diagnostics sur un des points
463 iprint = 1
464 !
465 ! - - ---------------------------------------------------
466 !
467 ! 0. Initialization
468 ! --------------
469 ! NOTE that snow layer thickness is used throughout this code: SWE
470 ! is only used to diagnose the thickness at the beginning of this routine
471 ! and it is updated at the end of this routine.
472 !
473 ! Initialization of the actual number of snow layers, total snow depth
474 ! and layer thicknesses
475 !
476 zsnowtemp(:,:) = 0.
477 !
478 gsnowfall(:) = .false.
479 inlvls_use(:) = 0
480 DO jst = 1,SIZE(psnowswe(:,:),2)
481  DO jj = 1,SIZE(zsnow)
482  IF ( psnowswe(jj,jst)>0. ) THEN
483  psnowdz(jj,jst) = psnowswe(jj,jst) / psnowrho(jj,jst)
484  inlvls_use(jj) = jst
485  ELSE
486  psnowdz(jj,jst) = 0.
487  ENDIF
488  ENDDO ! end loop snow layers
489 ENDDO ! end loop grid points
490 ! Incrementation of snow layers age
491 ztstepdays = ptstep/86400. ! time step in days
492 WHERE ( psnowswe>0 ) psnowage = psnowage + ztstepdays
493 !
494 !***************************************PRINT IN**********************************************
495 !
496 !Compute total SWE and heat for energy control
497 IF ( gcrodebugprintbalance ) THEN
498  DO jj = 1,SIZE(zsnow)
499  zsummass_ini(jj) = sum(psnowswe(jj,1:inlvls_use(jj)))
500  zsumheat_ini(jj) = sum(psnowheat(jj,1:inlvls_use(jj)))
501  ENDDO ! end loop grid points
502 ENDIF
503 !
504 ! Print of some simulation characteristics
505 IF(gcroinfoprint) THEN
506  CALL snowcroprintdate()
507  WRITE(*,fmt="(A12,I3,A12,I4)") 'nlayer:',inlvls_use(idebug), ' nbpoints:', SIZE(zsnow)
508 ! WRITE(*,*) 'PZ0H: ', PZ0H(IDEBUG)
509  WRITE(*,*) 'Snow fraction =',ppsn3l(idebug)
510 ENDIF
511 !
512 !***************************************PRINT OUT*********************************************
513 !***************************************DEBUG IN**********************************************
514 IF (gcrodebugprint) THEN
515  CALL snowcroprintdate()
516  CALL snowcroprintprofile("crocus initialization",inlvls_use(idebug),lprintgran, &
517  psnowdz(idebug,:),psnowrho(idebug,:),psnowtemp(idebug,:), &
518  psnowliq(idebug,:),psnowheat(idebug,:),psnowgran1(idebug,:),&
519  psnowgran2(idebug,:),psnowhist(idebug,:),psnowage(idebug,:),&
520  hsnowmetamo)
521 END IF
522 !
523 IF (gcrodebugprintatm) THEN
524  CALL snowcroprintatm("forcing data :",pta(idebug),pqa(idebug),pvmod(idebug), &
525  prr(idebug),psr(idebug),psw_rad(idebug),plw_rad(idebug), &
526  ptg(idebug),psoilcond(idebug),pd_g(idebug),ppsn3l(idebug) )
527 END IF
528 !***************************************DEBUG OUT********************************************
529 !
530 !* 1. Snow total depth
531 ! ----------------
532 !
533 zsnow(:) = 0.
534 DO jj = 1,SIZE(zsnow)
535  zsnow(jj) = sum(psnowdz(jj,1:inlvls_use(jj)))
536 ENDDO
537 !
538 zsnowbis(:) = zsnow(:)
539 !
540 !* 2. Snowfall
541 ! --------
542 ! Calculate uppermost density and thickness changes due to snowfall,
543 ! and add heat content of falling snow
544 !
545  CALL snownlfall_upgrid(tptime, oglacier, &
546  ptstep,psr,pta,pvmod,zsnowbis,psnowrho,psnowdz, &
547  psnowheat,psnowhmass,psnowalb,ppermsnowfrac, &
548  psnowgran1,psnowgran2,gsnowfall,zsnowdzn, &
549  zsnowrhof,zsnowdzf,zsnowgran1f,zsnowgran2f, zsnowhistf, &
550  zsnowagef,gmodif_maillage,inlvls_use,osnowdrift,pz0eff,puref,&
551  hsnowmetamo)
552 !
553 !***************************************DEBUG IN**********************************************
554 IF (gcrodebugdetailsprint) THEN
555  CALL snowcroprintprofile("after SNOWFALL_UPGRID",inlvls_use(idebug),lprintgran, &
556  psnowdz(idebug,:),psnowrho(idebug,:),psnowtemp(idebug,:), &
557  psnowliq(idebug,:),psnowheat(idebug,:),psnowgran1(idebug,:),&
558  psnowgran2(idebug,:),psnowhist(idebug,:),psnowage(idebug,:),&
559  hsnowmetamo )
560 ENDIF
561 !***************************************DEBUG OUT**********************************************
562 !
563 zsnow(:) = zsnowbis(:)
564 !
565 !* 3. Update grid/discretization
566 ! --------------------------
567 ! Reset grid to conform to model specifications:
568 !
569 DO jj=1,SIZE(zsnow)
570  !
571  IF ( gmodif_maillage(jj) ) THEN
572  CALL snownlgridfresh_1d(jj,zsnow(jj),psnowdz(jj,:),zsnowdzn(jj,:),psnowrho(jj,:), &
573  psnowheat(jj,:),psnowgran1(jj,:),psnowgran2(jj,:), &
574  psnowhist(jj,:),psnowage(jj,:),gsnowfall(jj),zsnowrhof(jj), &
575  zsnowdzf(jj),psnowhmass(jj),zsnowgran1f(jj),zsnowgran2f(jj), &
576  zsnowhistf(jj),zsnowagef(jj),inlvls_use(jj),hsnowmetamo )
577  ENDIF
578  !
579 ENDDO
580 !
581 !***************************************DEBUG IN**********************************************
582 IF (gcrodebugdetailsprint) THEN
583  CALL snowcroprintprofile("after SNOWNLGRIDFRESH_1D",inlvls_use(idebug),lprintgran, &
584  psnowdz(idebug,:),psnowrho(idebug,:),psnowtemp(idebug,:), &
585  psnowliq(idebug,:),psnowheat(idebug,:),psnowgran1(idebug,:),&
586  psnowgran2(idebug,:),psnowhist(idebug,:),psnowage(idebug,:),&
587  hsnowmetamo )
588 ENDIF
589 !***************************************DEBUG OUT**********************************************
590 !
591 !* 4. Liquid water content and snow temperature
592 ! -----------------------------------------
593 !
594 ! First diagnose snow temperatures and liquid
595 ! water portion of the snow from snow heat content:
596 ! update some snow layers parameters after new discretization
597 !
598 DO jj = 1,SIZE(zsnow)
599  !
600  ! active layers
601  DO jst=1,inlvls_use(jj)
602  psnowswe(jj,jst) = psnowdz(jj,jst) * psnowrho(jj,jst)
603 !
604  zscap(jj,jst) = psnowrho(jj,jst) * xci
605 !
606  zsnowtemp(jj,jst) = xtt + &
607  ( ( psnowheat(jj,jst)/psnowdz(jj,jst) + xlmtt*psnowrho(jj,jst) )/zscap(jj,jst) )
608 !
609  psnowliq(jj,jst) = max( 0.0, zsnowtemp(jj,jst)-xtt ) * zscap(jj,jst) * &
610  psnowdz(jj,jst) / (xlmtt*xrholw)
611 !
612  zsnowtemp(jj,jst) = min( xtt, zsnowtemp(jj,jst) )
613  ENDDO ! end loop active snow layers
614  !
615  ! unactive layers
616  DO jst = inlvls_use(jj)+1,SIZE(psnowswe,2)
617  psnowswe(jj,jst) = 0.0
618  psnowrho(jj,jst) = 999.
619  psnowdz(jj,jst) = 0.
620  psnowgran1(jj,jst) = 0.
621  psnowgran2(jj,jst) = 0.
622  psnowhist(jj,jst) = 0.
623  psnowage(jj,jst) = 0.
624  psnowheat(jj,jst) = 0.
625  zsnowtemp(jj,jst) = xtt
626  psnowliq(jj,jst) = 0.
627  ENDDO ! end loop unactive snow layers
628  !
629 ENDDO ! end loop grid points
630 !
631 !***************************************DEBUG IN**********************************************
632 IF (gcrodebugdetailsprint) THEN
633  CALL snowcroprintprofile("after liquid water/temperature diagnostic", &
634  inlvls_use(idebug),lprintgran, &
635  psnowdz(idebug,:),psnowrho(idebug,:),psnowtemp(idebug,:), &
636  psnowliq(idebug,:),psnowheat(idebug,:),psnowgran1(idebug,:),&
637  psnowgran2(idebug,:),psnowhist(idebug,:),psnowage(idebug,:),&
638  hsnowmetamo )
639 ENDIF
640 !***************************************DEBUG OUT**********************************************
641 !
642 ! 4.BIS Snow metamorphism
643 ! -----------------
644 !
645  CALL snowcrometamo(psnowdz,psnowgran1,psnowgran2,psnowhist,zsnowtemp, &
646  psnowliq,ptstep,psnowswe,inlvls_use,psnowage,hsnowmetamo )
647 !
648 !***************************************DEBUG IN**********************************************
649 IF (gcrodebugdetailsprint) THEN
650  CALL snowcroprintprofile("after SNOWCROMETAMO", inlvls_use(idebug),lprintgran, &
651  psnowdz(idebug,:),psnowrho(idebug,:),psnowtemp(idebug,:), &
652  psnowliq(idebug,:),psnowheat(idebug,:),psnowgran1(idebug,:),&
653  psnowgran2(idebug,:),psnowhist(idebug,:),psnowage(idebug,:),&
654  hsnowmetamo )
655 ENDIF
656 !***************************************DEBUG OUT**********************************************
657 !
658 !* 5. Snow Compaction
659 ! ---------------
660 ! Calculate snow density: compaction/aging: density increases
661 !
662  CALL snowcrocompactn(ptstep,psnowrho,psnowdz,zsnowtemp,zsnow, &
663  psnowgran1,psnowgran2,psnowhist,psnowliq,inlvls_use,pdircoszw,&
664  hsnowmetamo)
665 !
666 !***************************************DEBUG IN**********************************************
667 IF (gcrodebugdetailsprint) THEN
668  CALL snowcroprintprofile("after SNOWCROCOMPACTN", inlvls_use(idebug),lprintgran, &
669  psnowdz(idebug,:),psnowrho(idebug,:),psnowtemp(idebug,:), &
670  psnowliq(idebug,:),psnowheat(idebug,:),psnowgran1(idebug,:),&
671  psnowgran2(idebug,:),psnowhist(idebug,:),psnowage(idebug,:),&
672  hsnowmetamo )
673 ENDIF
674 !***************************************DEBUG OUT**********************************************
675 !
676 !* 5.1 Snow Compaction and Metamorphism due to snow drift
677 ! ---------------
678 psndrift(:) = 0.0
679 IF (osnowdrift) THEN
680  CALL snowdrift(ptstep, pvmod, psnowrho,psnowdz, zsnow, &
681  psnowgran1,psnowgran2,psnowhist,inlvls_use,pta,pqa,pps,prhoa,&
682  pz0eff,puref,osnowdrift_sublim,hsnowmetamo,psndrift)
683 ENDIF
684 !***************************************DEBUG IN**********************************************
685 IF (gcrodebugdetailsprint) THEN
686  CALL snowcroprintprofile("after SNOWDRIFT", inlvls_use(idebug),lprintgran, &
687  psnowdz(idebug,:),psnowrho(idebug,:),psnowtemp(idebug,:), &
688  psnowliq(idebug,:),psnowheat(idebug,:),psnowgran1(idebug,:),&
689  psnowgran2(idebug,:),psnowhist(idebug,:),psnowage(idebug,:),&
690  hsnowmetamo )
691 ENDIF
692 !***************************************DEBUG OUT**********************************************
693 !
694 ! Update snow heat content (J/m2) using dry density instead of total density:
695 !
696 DO jj = 1,SIZE(zsnow)
697  DO jst = 1,inlvls_use(jj)
698  zscap(jj,jst) = ( psnowrho(jj,jst) - &
699  psnowliq(jj,jst) * xrholw / max( psnowdz(jj,jst),xsnowdzmin) ) * xci
700  psnowheat(jj,jst) = psnowdz(jj,jst) * &
701  ( zscap(jj,jst)*(zsnowtemp(jj,jst)-xtt) - xlmtt*psnowrho(jj,jst) ) + &
702  xlmtt * xrholw * psnowliq(jj,jst)
703  ENDDO ! end loop snow layers
704 ENDDO ! end loop grid points
705 !
706 !***************************************DEBUG IN**********************************************
707 IF (gcrodebugdetailsprint) THEN
708  CALL snowcroprintprofile("after update snow heat content", inlvls_use(idebug),lprintgran,&
709  psnowdz(idebug,:),psnowrho(idebug,:),psnowtemp(idebug,:), &
710  psnowliq(idebug,:),psnowheat(idebug,:),psnowgran1(idebug,:), &
711  psnowgran2(idebug,:),psnowhist(idebug,:),psnowage(idebug,:), &
712  hsnowmetamo )
713 ENDIF
714 !***************************************DEBUG OUT********************************************
715 !
716 !* 6. Solar radiation transmission
717 ! -----------------------------
718 !
719 ! Heat source (-sink) term due to shortwave
720 ! radiation transmission within the snowpack:
721 !
722 SELECT CASE (hsnowrad)
723  CASE ("TA1")
724  zsnowimp_content(:,:,1) = 0.0
725  CASE ("TA2")
726  zsnowimp_content(:,:,1) = 100.0e-9
727  CASE ("TAR")
728  zsnowimp_content(:,:,1) = 2. * psnowage(:,:) * 1e-9
729  CASE DEFAULT
730 END SELECT
731 !
732 SELECT CASE (hsnowrad)
733  CASE ("B92")
734  CALL snowcrorad(tptime,oglacier, &
735  psw_rad,psnowalb,psnowdz,psnowrho, &
736  palb,zradsink,zradxs, &
737  psnowgran1, psnowgran2, psnowage,pps, &
738  pzenith, ppermsnowfrac,inlvls_use, &
739  osnow_abs_zenith,hsnowmetamo)
740  !
741  CASE ("TAR","TA1","TA2")
742  CALL snowcro_tartes(psnowgran1,psnowgran2,psnowrho,psnowdz,zsnowg0,zsnowy0,zsnoww0, &
743  zsnowb0,zsnowimp_density,zsnowimp_content,palb,psw_rad,pzenith, &
744  inlvls_use,psnowalb,zradsink,zradxs,gcrodebugdetailsprint,hsnowmetamo)
745  !
746  CASE DEFAULT
747  CALL abor1_sfx("UNKNOWN CSNOWRAD OPTION")
748  !
749 END SELECT
750 !
751 !***************************************DEBUG IN**********************************************
752 IF (gcrodebugdetailsprint) THEN
753  CALL snowcroprintprofile("after SNOWCRORAD", inlvls_use(idebug),lprintgran, &
754  psnowdz(idebug,:),psnowrho(idebug,:),psnowtemp(idebug,:), &
755  psnowliq(idebug,:),psnowheat(idebug,:),psnowgran1(idebug,:), &
756  psnowgran2(idebug,:),psnowhist(idebug,:),psnowage(idebug,:), &
757  hsnowmetamo)
758 ENDIF
759 !***************************************DEBUG OUT********************************************
760 !
761 !* 7. Heat transfer and surface energy budget
762 ! ---------------------------------------
763 ! Snow thermal conductivity:
764 !
765  CALL snowcrothrm(psnowrho,zscond,zsnowtemp,pps,psnowliq,gcond_grain,gcond_yen)
766 !
767 !***************************************DEBUG IN**********************************************
768 IF (gcrodebugdetailsprint) THEN
769  CALL snowcroprintprofile("after SNOWCROTHRM", inlvls_use(idebug),lprintgran, &
770  psnowdz(idebug,:),psnowrho(idebug,:),psnowtemp(idebug,:), &
771  psnowliq(idebug,:),psnowheat(idebug,:),psnowgran1(idebug,:), &
772  psnowgran2(idebug,:),psnowhist(idebug,:),psnowage(idebug,:), &
773  hsnowmetamo)
774 ENDIF
775 !***************************************DEBUG OUT********************************************
776 !
777 ! Precipitation heating term:
778 ! Rainfall renders it's heat to the snow when it enters
779 ! the snowpack:
780 !
781 phpsnow(:) = prr(:) * xcl * ( max( xtt,pta(:) ) - xtt ) ! (W/m2)
782 !
783 ! Surface Energy Budget calculations using ISBA linearized form
784 ! and standard ISBA turbulent transfer formulation
785 !
786 IF ( all(ppew_a_coef==0.) ) THEN
787  !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
788  ! Modif Matthieu Lafaysse for glaciers
789  ! For surface ice, modify roughness lengths
790  ! Only if not implicit coupling
791  !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
792  WHERE( psnowrho(:,1)>xrhothreshold_ice )
793  zz0_snowice = pz0 * xz0icez0snow
794  zz0h_snowice = pz0h * xz0icez0snow
795  zz0eff_snowice = pz0eff * xz0icez0snow
796  ELSEWHERE
797  zz0_snowice = pz0
798  zz0h_snowice = pz0h
799  zz0eff_snowice = pz0eff
800  ENDWHERE
801 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
802 ELSE
803  zz0_snowice = pz0
804  zz0h_snowice = pz0h
805  zz0eff_snowice = pz0eff
806 END IF
807 
808  CALL snowcroebud(hsnowres, himplicit_wind, &
809  ppew_a_coef, ppew_b_coef, &
810  ppet_a_coef, ppeq_a_coef, ppet_b_coef, ppeq_b_coef, &
811  xsnowdzmin, &
812  pzref,zsnowtemp(:,1),psnowrho(:,1),psnowliq(:,1),zscap(:,1), &
813  zscond(:,1),zscond(:,2), &
814  puref,pexns,pexna,pdircoszw,pvmod, &
815  plw_rad,psw_rad,pta,pqa,pps,ptstep, &
816  psnowdz(:,1),psnowdz(:,2),psnowalb,zz0_snowice, &
817  zz0eff_snowice,zz0h_snowice, &
818  zsfcfrz,zradsink(:,1),phpsnow, &
819  zct,pemisnow,prhoa,ztsterm1,ztsterm2,zra,pcdsnow,pchsnow, &
820  zqsat, zdqsat, zrsra, zustar2_ic, pri, &
821  zpet_a_coef_t,zpeq_a_coef_t,zpet_b_coef_t,zpeq_b_coef_t )
822 !
823 !***************************************DEBUG IN**********************************************
824 IF (gcrodebugdetailsprint) THEN
825  CALL snowcroprintprofile("after SNOWCROEBUD", inlvls_use(idebug),lprintgran, &
826  psnowdz(idebug,:),psnowrho(idebug,:),psnowtemp(idebug,:), &
827  psnowliq(idebug,:),psnowheat(idebug,:),psnowgran1(idebug,:), &
828  psnowgran2(idebug,:),psnowhist(idebug,:),psnowage(idebug,:), &
829  hsnowmetamo)
830 ENDIF
831 !***************************************DEBUG OUT********************************************
832 !
833 ! Heat transfer: simple diffusion along the thermal gradient
834 !
835 zsnowtempo1(:) = zsnowtemp(:,1) ! save surface snow temperature before update
836 !
837  CALL snowcrosolvt(ptstep,xsnowdzmin,psnowdz,zscond,zscap,ptg, &
838  psoilcond,pd_g,zradsink,zct,ztsterm1,ztsterm2, &
839  zpet_a_coef_t,zpeq_a_coef_t,zpet_b_coef_t,zpeq_b_coef_t, &
840  zta_ic,zqa_ic,pgrndflux, zsnowtemp ,zsnowflux, &
841  inlvls_use )
842 !
843 !***************************************DEBUG IN**********************************************
844 IF (gcrodebugdetailsprint) THEN
845  CALL snowcroprintprofile("after SNOWCROSOLVT", inlvls_use(idebug),lprintgran, &
846  psnowdz(idebug,:),psnowrho(idebug,:),psnowtemp(idebug,:), &
847  psnowliq(idebug,:),psnowheat(idebug,:),psnowgran1(idebug,:), &
848  psnowgran2(idebug,:),psnowhist(idebug,:),psnowage(idebug,:), &
849  hsnowmetamo)
850 ENDIF
851 !***************************************DEBUG OUT********************************************
852 !
853 !* 8. Surface fluxes
854 ! --------------
855 !
856  CALL snowcroflux(zsnowtemp(:,1),psnowdz(:,1),pexns,pexna, &
857  zustar2_ic, &
858  ptstep,psnowalb,psw_rad,pemisnow,zlwupsnow,plw_rad, &
859  zta_ic,zsfcfrz,zqa_ic,phpsnow, &
860  zsnowtempo1,zsnowflux,zct,zradsink(:,1), &
861  zqsat,zdqsat,zrsra, &
862  prnsnow,phsnow,pgfluxsnow,ples3l,plel3l,pevap, &
863  pustar )
864 !
865 !***************************************DEBUG IN**********************************************
866 IF (gcrodebugdetailsprint) THEN
867  CALL snowcroprintprofile("after SNOWCROFLUX", inlvls_use(idebug),lprintgran, &
868  psnowdz(idebug,:),psnowrho(idebug,:),psnowtemp(idebug,:), &
869  psnowliq(idebug,:),psnowheat(idebug,:),psnowgran1(idebug,:), &
870  psnowgran2(idebug,:),psnowhist(idebug,:),psnowage(idebug,:), &
871  hsnowmetamo)
872 ENDIF
873 !***************************************DEBUG OUT********************************************
874 !
875 !* 9. Snow melt
876 ! ---------
877 !
878 ! First Test to see if snow pack vanishes during this time step:
879 !
880  CALL snowcrogone(ptstep,plel3l,ples3l,psnowrho, &
881  psnowheat,zradsink,pevapcor,pthrufal,pgrndflux, &
882  pgfluxsnow,psnowdz,psnowliq,zsnowtemp,zradxs, &
883  prr,inlvls_use )
884 !
885 !***************************************DEBUG IN**********************************************
886 IF (gcrodebugdetailsprint) THEN
887  CALL snowcroprintprofile("after SNOWCROGONE", inlvls_use(idebug),lprintgran, &
888  psnowdz(idebug,:),psnowrho(idebug,:),psnowtemp(idebug,:), &
889  psnowliq(idebug,:),psnowheat(idebug,:),psnowgran1(idebug,:), &
890  psnowgran2(idebug,:),psnowhist(idebug,:),psnowage(idebug,:), &
891  hsnowmetamo)
892 ENDIF
893 !***************************************DEBUG OUT********************************************
894 !
895 ! Add radiation not absorbed by snow to soil/vegetation interface flux
896 ! (for thin snowpacks):
897 !
898 pgrndflux(:) = pgrndflux(:) + zradxs(:)
899 !
900 ! Second Test to see if one or several snow layers vanishe during this time
901 ! step. In such a case, the concerned snow layers are agregated to neighbours
902 
903  CALL snowcrolayer_gone(ptstep,zscap,zsnowtemp,psnowdz, &
904  psnowrho,psnowliq,psnowgran1,psnowgran2, &
905  psnowhist,psnowage,ples3l, inlvls_use )
906 !
907 !***************************************DEBUG IN**********************************************
908 IF (gcrodebugdetailsprint) THEN
909  CALL snowcroprintprofile("after SNOWCROLAYER_GONE", inlvls_use(idebug),lprintgran, &
910  psnowdz(idebug,:),psnowrho(idebug,:),psnowtemp(idebug,:), &
911  psnowliq(idebug,:),psnowheat(idebug,:),psnowgran1(idebug,:), &
912  psnowgran2(idebug,:),psnowhist(idebug,:),psnowage(idebug,:), &
913  hsnowmetamo)
914 ENDIF
915 !***************************************DEBUG OUT********************************************
916 !
917 ! For partial melt: transform excess heat content into snow liquid:
918 !
919  CALL snowcromelt(zscap,zsnowtemp,psnowdz,psnowrho,psnowliq,inlvls_use)
920 !
921 !***************************************DEBUG IN**********************************************
922 IF (gcrodebugdetailsprint) THEN
923  CALL snowcroprintprofile("after SNOWCROMELT", inlvls_use(idebug),lprintgran, &
924  psnowdz(idebug,:),psnowrho(idebug,:),psnowtemp(idebug,:), &
925  psnowliq(idebug,:),psnowheat(idebug,:),psnowgran1(idebug,:), &
926  psnowgran2(idebug,:),psnowhist(idebug,:),psnowage(idebug,:), &
927  hsnowmetamo)
928 ENDIF
929 !***************************************DEBUG OUT********************************************
930 !
931 !* 10. Snow water flow and refreezing
932 ! ------------------------------
933 ! Liquid water vertical transfer and possible snowpack runoff
934 ! And refreezing/freezing of meltwater/rainfall (ripening of the snow)
935 !
936  CALL snowcrorefrz(ptstep,prr,psnowrho,zsnowtemp,psnowdz,psnowliq,pthrufal, &
937  zscap,plel3l,inlvls_use )
938 !
939 !***************************************DEBUG IN**********************************************
940 IF (gcrodebugdetailsprint) THEN
941  CALL snowcroprintprofile("after SNOWCROREFRZ", inlvls_use(idebug),lprintgran, &
942  psnowdz(idebug,:),psnowrho(idebug,:),psnowtemp(idebug,:), &
943  psnowliq(idebug,:),psnowheat(idebug,:),psnowgran1(idebug,:), &
944  psnowgran2(idebug,:),psnowhist(idebug,:),psnowage(idebug,:), &
945  hsnowmetamo)
946 ENDIF
947 !***************************************DEBUG OUT********************************************
948 !
949 !* 11. Snow Evaporation/Sublimation mass updates:
950 ! ------------------------------------------
951 !
952  CALL snowcroevapn(ples3l,ptstep,zsnowtemp(:,1),psnowrho(:,1), &
953  psnowdz(:,1),pevapcor,psnowhmass )
954 !
955 !***************************************DEBUG IN**********************************************
956 IF (gcrodebugdetailsprint) THEN
957  CALL snowcroprintprofile("after SNOWCROEVAPN", inlvls_use(idebug),lprintgran, &
958  psnowdz(idebug,:),psnowrho(idebug,:),psnowtemp(idebug,:), &
959  psnowliq(idebug,:),psnowheat(idebug,:),psnowgran1(idebug,:), &
960  psnowgran2(idebug,:),psnowhist(idebug,:),psnowage(idebug,:), &
961  hsnowmetamo)
962 ENDIF
963 !***************************************DEBUG OUT********************************************
964 !
965 ! If all snow in uppermost layer evaporates/sublimates, re-distribute
966 ! grid (below could be evoked for vanishingly thin snowpacks):
967 !
968  CALL snowcroevapgone(psnowheat,psnowdz,psnowrho,zsnowtemp,psnowliq,psnowgran1, &
969  psnowgran2,psnowhist,psnowage,inlvls_use,hsnowmetamo )
970 !
971 !***************************************DEBUG IN**********************************************
972 IF (gcrodebugdetailsprint) THEN
973  CALL snowcroprintprofile("after SNOWCROEVAPGONE", inlvls_use(idebug),lprintgran, &
974  psnowdz(idebug,:),psnowrho(idebug,:),psnowtemp(idebug,:), &
975  psnowliq(idebug,:),psnowheat(idebug,:),psnowgran1(idebug,:), &
976  psnowgran2(idebug,:),psnowhist(idebug,:),psnowage(idebug,:), &
977  hsnowmetamo)
978 ENDIF
979 !***************************************DEBUG OUT********************************************
980 !
981 !* 12. Update surface albedo:
982 ! ----------------------
983 ! Snow clear sky albedo:
984 !
985 IF ( hsnowrad=='B92' ) THEN
986  CALL snowcroalb(tptime,oglacier, &
987  psnowalb,zspectralalbedo,psnowdz(:,1),psnowrho(:,1:2), &
988  ppermsnowfrac,psnowgran1(:,1),psnowgran2(:,1), &
989  psnowage(:,1),psnowgran1(:,2),psnowgran2(:,2),psnowage(:,2), &
990  pps, pzenith, inlvls_use, hsnowmetamo)
991  !the albedo is not updated in the case of TARTES scheme
992 ENDIF
993 !
994 !* 13. Update snow heat content:
995 ! -------------------------
996 ! Update the heat content (variable stored each time step)
997 ! using current snow temperature and liquid water content:
998 !
999 ! First, make check to make sure heat content not too large
1000 ! (this can result due to signifigant heating of thin snowpacks):
1001 ! add any excess heat to ground flux:
1002 !
1003 DO jj = 1,SIZE(zsnow)
1004 ! active layers
1005  DO jst = 1,inlvls_use(jj)
1006  zwholdmax(jj,jst) = xpercentagepore/xrholi * (psnowdz(jj,jst) * &
1007  (xrholi-psnowrho(jj,jst)) + psnowliq(jj,jst)*xrholw)
1008  zliqheatxs(jj) = max( 0.0, (psnowliq(jj,jst) - zwholdmax(jj,jst)) * xrholw ) * xlmtt/ptstep
1009  psnowliq(jj,jst) = psnowliq(jj,jst) - zliqheatxs(jj)*ptstep/(xrholw*xlmtt)
1010  psnowliq(jj,jst) = max( 0.0, psnowliq(jj,jst) )
1011  pgrndflux(jj) = pgrndflux(jj) + zliqheatxs(jj)
1012  psnowtemp(jj,jst) = zsnowtemp(jj,jst)
1013 ! Heat content using total density
1014  zscap(jj,jst) = psnowrho(jj,jst) * xci
1015  psnowheat(jj,jst) = psnowdz(jj,jst) * &
1016  ( zscap(jj,jst)*(psnowtemp(jj,jst)-xtt) - xlmtt*psnowrho(jj,jst) ) + &
1017  xlmtt * xrholw * psnowliq(jj,jst)
1018 !
1019  psnowswe(jj,jst) = psnowdz(jj,jst) * psnowrho(jj,jst)
1020  ENDDO ! end loop active snow layers
1021 !
1022 ! unactive layers
1023  DO jst = inlvls_use(jj)+1,SIZE(psnowswe,2)
1024  psnowswe(jj,jst) = 0.
1025  psnowheat(jj,jst) = 0.
1026  psnowrho(jj,jst) = 999.
1027  psnowtemp(jj,jst) = 0.
1028  psnowdz(jj,jst) = 0.
1029  ENDDO ! end loop unactive snow layers
1030 !
1031 ENDDO ! end loop grid points
1032 !
1033 ! print some final diagnostics
1034 ! ! ! IF (INLVLS_USE(I)>0) THEN
1035 ! ! ! WRITE(*,FMT="(I4,2I4,F4.0,A7,F5.2,A10,F7.1,A11,F6.2,A13,F6.2)") &
1036 ! ! ! TPTIME%TDATE%YEAR,TPTIME%TDATE%MONTH,TPTIME%TDATE%DAY,TPTIME%TIME/3600.,&
1037 ! ! ! 'HTN= ',SUM(PSNOWDZ(I,1:INLVLS_USE(I))), 'FLUX Sol=', PGRNDFLUX(I),&
1038 ! ! ! 'Tsurf_sol=',PTG(I)-273.16, 'Tbase_neige=',PSNOWTEMP(I,INLVLS_USE(I))-273.16
1039 ! ! ! ENDIF
1040 !
1041 !***************************************DEBUG IN*********************************************
1042 IF (gcrodebugprint) THEN
1043  CALL snowcroprintdate()
1044  CALL snowcroprintprofile("CROCUS : end of time step",inlvls_use(idebug),lprintgran, &
1045  psnowdz(idebug,:),psnowrho(idebug,:),psnowtemp(idebug,:),psnowliq(idebug,:), &
1046  psnowheat(idebug,:),psnowgran1(idebug,:),psnowgran2(idebug,:), &
1047  psnowhist(idebug,:),psnowage(idebug,:), hsnowmetamo)
1048 END IF
1049 !***************************************DEBUG OUT********************************************
1050 !***************************************PRINT IN*********************************************
1051 ! check suspect low temperature
1052 DO jj = 1,SIZE(zsnow)
1053 !IF(INLVLS_USE(JJ)>0) WRITE(*,*) 'SOL:',JJ,INLVLS_USE(JJ),PGRNDFLUX(JJ),PTG(JJ),&
1054 ! PSNOWTEMP(jj,INLVLS_USE(JJ)),PSNOWTEMP(jj,1),PZENITH(JJ)
1055  DO jst = 1,inlvls_use(jj)
1056  IF ( psnowtemp(jj,jst) < 100. ) THEN
1057  WRITE(*,*) 'pb tempe snow :',psnowtemp(jj,jst)
1058  WRITE(*,fmt='("DATE:",2(I2.2,"/"),I4.4,F3.0)') &
1059  tptime%TDATE%DAY,tptime%TDATE%MONTH,tptime%TDATE%YEAR,tptime%TIME/3600.
1060  WRITE(*,*) 'point',jj,"/",SIZE(zsnow)
1061  WRITE(*,*) 'layer',jst
1062  WRITE(*,*) 'pressure',pps(jj)
1063  WRITE(*,*) 'slope',acos(pdircoszw(jj))*(180./xpi),"deg"
1064  WRITE(*,*) 'XLAT=',pxlat(jj),'XLON=',pxlon(jj)
1065  WRITE(*,*) 'solar radiation=',psw_rad(jj)
1066  WRITE(*,*) 'INLVLS_USE(JJ):',inlvls_use(jj)
1067  WRITE(*,*) psnowdz(jj,1:inlvls_use(jj))
1068  WRITE(*,*) psnowrho(jj,1:inlvls_use(jj))
1069  WRITE(*,*) psnowtemp(jj,1:inlvls_use(jj))
1070  CALL abor1_sfx('SNOWCRO: erreur tempe snow')
1071  ENDIF
1072  ENDDO
1073 ENDDO
1074 !***************************************PRINT OUT*********************************************
1075 !***************************************DEBUG IN*********************************************
1076 !Control and print energy balance
1077 IF (gcrodebugprintbalance) THEN
1078  !
1079  zsummass_fin(idebug) = sum( psnowswe(idebug,1:inlvls_use(idebug)) )
1080  zsumheat_fin(idebug) = sum( psnowheat(idebug,1:inlvls_use(idebug)) )
1081  !
1082  CALL get_balance(zsummass_ini(idebug),zsumheat_ini(idebug),zsummass_fin(idebug), &
1083  zsumheat_fin(idebug),psr(idebug),prr(idebug),pthrufal(idebug), &
1084  pevap(idebug),pevapcor(idebug),pgrndflux(idebug),phsnow(idebug),&
1085  prnsnow(idebug),plel3l(idebug),ples3l(idebug),phpsnow(idebug), &
1086  psnowhmass(idebug),psnowdz(idebug,1),ptstep, &
1087  zmassbalance(idebug),zenergybalance(idebug),zevapcor2(idebug) )
1088  !
1089  CALL snowcroprintbalance(zsummass_ini(idebug),zsumheat_ini(idebug),zsummass_fin(idebug), &
1090  zsumheat_fin(idebug),psr(idebug),prr(idebug),pthrufal(idebug), &
1091  pevap(idebug),pevapcor(idebug),pgrndflux(idebug),phsnow(idebug),&
1092  prnsnow(idebug),plel3l(idebug),ples3l(idebug),phpsnow(idebug), &
1093  psnowhmass(idebug),psnowdz(idebug,1),ptstep, &
1094  zmassbalance(idebug),zenergybalance(idebug),zevapcor2(idebug))
1095  !
1096 ENDIF
1097 !
1098 IF (lpstopbalance) THEN
1099  !
1100  ! bilan pour tous points pour test eventuel sur depassement seuil des residus
1101  DO jj=1, SIZE(zsnow)
1102  !
1103  zsummass_fin(jj) = sum( psnowswe(jj,1:inlvls_use(jj)) )
1104  zsumheat_fin(jj) = sum( psnowheat(jj,1:inlvls_use(jj)) )
1105  !
1106  CALL get_balance(zsummass_ini(jj),zsumheat_ini(jj),zsummass_fin(jj), &
1107  zsumheat_fin(jj),psr(jj),prr(jj),pthrufal(jj), &
1108  pevap(jj),pevapcor(jj),pgrndflux(jj),phsnow(jj), &
1109  prnsnow(jj),plel3l(jj),ples3l(jj),phpsnow(jj), &
1110  psnowhmass(jj),psnowdz(jj,1),ptstep, &
1111  zmassbalance(jj),zenergybalance(jj),zevapcor2(jj) )
1112  !
1113  ENDDO ! end loop grid points
1114  !
1115  CALL snowcrostopbalance(zmassbalance(:),zenergybalance(:))
1116  !
1117 END IF
1118 !***************************************DEBUG OUT********************************************
1119 !
1120 pqs(:) = zqsat(:)
1121 !
1122 IF (lhook) CALL dr_hook('SNOWCRO',1,zhook_handle)
1123 !
1124 CONTAINS
1125 !
1126 !####################################################################
1127 !####################################################################
1128 !####################################################################
1129  SUBROUTINE snowcrocompactn(PTSTEP,PSNOWRHO,PSNOWDZ, &
1130  PSNOWTEMP,PSNOW,PSNOWGRAN1,PSNOWGRAN2,PSNOWHIST, &
1131  PSNOWLIQ,INLVLS_USE,PDIRCOSZW,HSNOWMETAMO )
1132 !
1133 !! PURPOSE
1134 !! -------
1135 ! Snow compaction due to overburden and settling.
1136 ! Mass is unchanged: layer thickness is reduced
1137 ! in proportion to density increases. Method
1138 ! directly inherited from Crocus v2.4 and
1139 ! coarsely described in Brun et al., J. Glac 1989 and 1992
1140 !
1141 ! de/e = -sigma/eta * dt
1142 !
1143 ! where e is layer thickness, sigma is the vertical stress, dt is the
1144 ! time step and eta is the snow viscosity
1145 ! * sigma is currently calculated taking into account only the overburden
1146 ! (a term representing "metamorphism stress" in fresh snow may be added
1147 ! in the future)
1148 ! * eta is computed as a function of snowtype, density and temperature
1149 !
1150 ! The local slope is taken into account, through the variable PDIRCOSZW
1151 ! which is directly the cosine of the local slope
1152 !
1153 !
1154 ! HISTORY:
1155 ! Basic structure from ISBA-ES model (Boone and Etchevers, 2001)
1156 ! Implementation of Crocus laws : E. Brun, S. Morin, J.-M. Willemet July 2010.
1157 ! Implementation of slope effect on settling : V. Vionnet, S. Morin May 2011
1158 !
1159 !
1160 USE modd_csts, ONLY : xtt, xg
1161 USE modd_snow_par, ONLY : xrhosmax_es
1162 USE modd_snow_metamo
1163 !
1164 IMPLICIT NONE
1165 !
1166 !* 0.1 declarations of arguments
1167 !
1168 REAL, INTENT(IN) :: PTSTEP ! Time step UNIT : s
1169 REAL, DIMENSION(:), INTENT(IN) :: PDIRCOSZW ! cosine of local slope
1170 !
1171 REAL, DIMENSION(:,:), INTENT(IN) :: PSNOWTEMP ! Snow temperature UNIT : K
1172 !
1173 REAL, DIMENSION(:,:), INTENT(INOUT) :: PSNOWRHO, PSNOWDZ ! Density UNIT : kg m-3, Layer thickness UNIT : m
1174 !
1175 REAL, DIMENSION(:), INTENT(OUT) :: PSNOW ! Snowheight UNIT : m
1176 !
1177 REAL, DIMENSION(:,:), INTENT(IN) :: PSNOWGRAN1, PSNOWGRAN2, PSNOWHIST, &!Snowtype variables
1178  PSNOWLIQ ! Snow liquid water content UNIT ???
1179 INTEGER, DIMENSION(:), INTENT(IN) :: INLVLS_USE ! Number of snow layers used
1180  CHARACTER(3), INTENT(IN) :: HSNOWMETAMO ! metamorphism scheme
1181 !
1182 !* 0.2 declarations of local variables
1183 !
1184 REAL, DIMENSION(SIZE(PSNOWRHO,1),SIZE(PSNOWRHO,2)) :: ZSNOWRHO2, &! work snow density UNIT : kg m-3
1185  ZVISCOSITY, &! Snow viscosity UNIT : N m-2 s (= Pa s)
1186  ZSMASS !, & ! overburden mass for a given layer UNIT : kg m-2
1187 ! ZWSNOWDZ ! mass of each snow layer UNIT : kg m-2
1188 !
1189 INTEGER :: JJ,JST ! looping indexes
1190 !
1191 REAL(KIND=JPRB) :: ZHOOK_HANDLE
1192 !
1193 !-------------------------------------------------------------------------------
1194 !
1195 ! 1. Cumulative snow mass (kg/m2):
1196 ! --------------------------------
1197 !
1198 IF (lhook) CALL dr_hook('SNOWCROCOMPACTN',0,zhook_handle)
1199 !
1200 DO jj = 1,SIZE(psnow)
1201  zsmass(jj,1) = 0.0
1202  DO jst = 2,inlvls_use(jj)
1203  zsmass(jj,jst) = zsmass(jj,jst-1) + psnowdz(jj,jst-1) * psnowrho(jj,jst-1)
1204  ENDDO
1205  zsmass(jj,1) = 0.5 * psnowdz(jj,1) * psnowrho(jj,1) ! overburden of half the mass of the uppermost layer applied to itself
1206 ENDDO
1207 
1208 !
1209 ! 2. Compaction/Settling
1210 ! ----------------------
1211 !
1212 DO jj = 1,SIZE(psnow)
1213  !
1214  DO jst = 1,inlvls_use(jj)
1215  !
1216  ! Snow viscosity basic equation (depend on temperature and density only):
1217  zviscosity(jj,jst) = xvvisc1 * &
1218  exp( xvvisc3*psnowrho(jj,jst) + xvvisc4*abs(xtt-psnowtemp(jj,jst)) ) * &
1219  psnowrho(jj,jst) / xvro11
1220  !
1221  ! Equations below apply changes to the basic viscosity value, based on snow microstructure properties
1222  IF ( psnowliq(jj,jst)>0.0 ) THEN
1223  zviscosity(jj,jst) = zviscosity(jj,jst) / &
1224  ( xvvisc5 + xvvisc6*psnowliq(jj,jst)/psnowdz(jj,jst) )
1225  ENDIF
1226  !
1227  IF( psnowliq(jj,jst)/psnowdz(jj,jst)<=0.01 .AND. psnowhist(jj,jst)>=nvhis2 ) THEN
1228  zviscosity(jj,jst) = zviscosity(jj,jst) * xvvisc7
1229  ENDIF
1230  !
1231  IF ( psnowhist(jj,jst)==nvhis1 ) THEN
1232  !
1233  IF ( hsnowmetamo=="B92" ) THEN
1234  !
1235  IF ( psnowgran1(jj,jst)>=0. .AND. psnowgran1(jj,jst)<xvgran6 ) THEN
1236  zviscosity(jj,jst) = zviscosity(jj,jst) * &
1237  min( 4., exp( min( xvdiam1, &
1238  psnowgran2(jj,jst) -xvdiam4 ) / xvdiam6 ) )
1239  ENDIF
1240  !
1241  ELSEIF ( psnowgran1(jj,jst)>=xvdiam6*(4.-psnowgran2(jj,jst)) .AND. psnowgran2(jj,jst)<xvgran6/xvgran1 ) THEN
1242  zviscosity(jj,jst) = zviscosity(jj,jst) * &
1243  min( 4., exp( min( xvdiam1, &
1244  (xvdiam6*(4.-psnowgran2(jj,jst)))-xvdiam4 ) / xvdiam6 ) )
1245  ENDIF
1246  !
1247  ENDIF
1248  !
1249  ! Calculate new snow snow density: compaction from weight/over-burden
1250  zsnowrho2(jj,jst) = psnowrho(jj,jst) + psnowrho(jj,jst) * ptstep * &
1251  ( xg*pdircoszw(jj)*zsmass(jj,jst)/zviscosity(jj,jst) )
1252  !
1253  ! Calculate new grid thickness in response to density change
1254  psnowdz(jj,jst) = psnowdz(jj,jst) * ( psnowrho(jj,jst)/zsnowrho2(jj,jst) )
1255  !
1256  ! Update density (kg m-3):
1257  psnowrho(jj,jst) = zsnowrho2(jj,jst)
1258  !
1259  ENDDO ! end loop snow layers
1260  !
1261 ENDDO ! end loop grid points
1262 !
1263 !
1264 ! 3. Update total snow depth:
1265 ! -----------------------------------------------
1266 !
1267 DO jj = 1,SIZE(psnowdz,1)
1268  psnow(jj) = sum( psnowdz(jj,1:inlvls_use(jj)) )
1269 ENDDO
1270 !
1271 IF (lhook) CALL dr_hook('SNOWCROCOMPACTN',1,zhook_handle)
1272 
1273 !
1274 !-------------------------------------------------------------------------------
1275 !
1276 END SUBROUTINE snowcrocompactn
1277 
1278 
1279 !####################################################################
1280 !####################################################################
1281 !####################################################################
1282 SUBROUTINE snowcrometamo(PSNOWDZ,PSNOWGRAN1, PSNOWGRAN2, &
1283  PSNOWHIST, PSNOWTEMP, PSNOWLIQ, PTSTEP, &
1284  PSNOWSWE,INLVLS_USE, PSNOWAGE, HSNOWMETAMO)
1285 !
1286 
1287 !**** *METAMO* - METAMORPHOSE DES GRAINS
1288 ! - SNOW METAMORPHISM
1289 ! OBJET.
1290 ! ------
1291 ! METAMORPHOSE DU MANTEAU NEIGEUX.
1292 ! EVOLUTION DU TYPE DE GRAINS
1293 ! MISE A JOUR DES VARIABLES HISTORIQUES.
1294 ! METAMORPHISM OF THE SNOW GRAINS,
1295 ! HISTORICAL VARIABLES
1296 
1297 !** INTERFACE.
1298 ! ----------
1299 ! FORMALISME ADOPTE POUR LA REPRESENTATION DES GRAINS :
1300 ! FORMALISM FOR THE REPRESENTATION OF GRAINS
1301 ! -----------------------------------------------------
1302 
1303 
1304 ! 1 - -1 NEIGE FRAICHE
1305 ! / \ | -------------
1306 ! / \ | DENDRICITE DECRITE EN TERME
1307 ! / \ | DENDRICITY DE DENDRICITE ET
1308 ! / \ | SPHERICITE
1309 ! 2---------3 - 0 DESCRIBED WITH
1310 ! SPHERICITY AND
1311 ! |---------| DENDRICITY
1312 ! 0 1
1313 ! SPHERICITE
1314 ! SPHERICITY
1315 
1316 ! 4---------5 -
1317 ! | | |
1318 ! | | | DIAMETRE (OU TAILLE)
1319 ! | | | DIAMETER (OR SIZE )
1320 ! | | |
1321 ! | | | NEIGE NON DENDRITIQUE
1322 ! 6---------7 - ---------------------
1323 
1324 ! SPHERICITE ET TAILLE
1325 ! SPHERICITY AND SIZE
1326 
1327 ! LES VARIABLES DU MODELE :
1328 ! -------------------------
1329 ! CAS DENDRITIQUE CAS NON DENDRITIQUE
1330 !
1331 ! SGRAN1(JST) : DENDRICITE SGRAN1(JST) : SPHERICITE
1332 ! SGRAN2(JST) : SPHERICITE SGRAN2(JST) : TAILLE (EN METRE)
1333 ! SIZE
1334 
1335 !
1336 ! CAS DENDRITIQUE/ DENDRITIC CASE
1337 ! -------------------------------
1338 ! SGRAN1(JST) VARIE DE -XVGRAN1 (-99 PAR DEFAUT) (ETOILE) A 0
1339 ! (DENDRICITY) >D OU LA DIVISION PAR -XVGRAN1 POUR OBTENIR DES VALEURS
1340 ! ENTRE 1 ET 0
1341 ! VARIES FROM -XVGRAN1 (DEFAULT -99) (FRESH SNOW) TO 0
1342 ! DIVISION BY -XVGRAN1 TO OBTAIN VALUES BETWEEN 0 AND 1
1343 
1344 ! SGRAN2(JST) VARIE DE 0 (CAS COMPLETEMENT ANGULEUX) A XVGRAN1
1345 ! (SPHERICITY) (99 PAR DEFAUT)
1346 ! >D OU LA DIVISION PAR XVGRAN1 POUR OBTENIR DES VALEURS
1347 ! ENTRE 0 ET 1
1348 ! VARIES FROM 0 (SPHERICITY=0) TO XVGRAN1
1349 
1350 
1351 ! CAS NON DENDRITIQUE / NON DENDRITIC CASE
1352 ! ---------------------------------------
1353 
1354 ! SGRAN1(JST) VARIE DE 0 (CAS COMPLETEMENT ANGULEUX) A XVGRAN1
1355 ! (SPHERICITY) (99 PAR DEFAUT) (CAS SPHERIQUE)
1356 ! >D OU LA DIVISION PAR XVGRAN1 POUR OBTENIR DES VALEURS
1357 ! ENTRE 0 ET 1
1358 ! VARIES FROM 0 TO 99
1359 
1360 ! SGRAN2(JST) EST SUPERIEUR A XVDIAM1-SPHERICITE (3.E-4 M) ET NE FAIT QUE CROITRE
1361 ! (SIZE) IS GREATER THAN XVDIAM1-SPHERICITE (3.E-4 M) ALWAYS INCREASE
1362 
1363 
1364 ! EXEMPLES : POINTS CARACTERISTIQUES DE LA FIGURE
1365 ! --------
1366 
1367 ! SGRAN1 SGRAN2 DENDRICITE SPHERICITE TAILLE
1368 ! DENDRICITY SPHERICITY SIZE
1369 ! --------------------------------------------------------------
1370 ! (M)
1371 ! 1 -XVGRAN1 VNSPH3 1 0.5
1372 ! 2 0 0 0 0
1373 ! 3 0 XVGRAN1 0 1
1374 ! 4 0 XVDIAM1 0 4.E-4
1375 ! 5 XVGRAN1 XVDIAM1-XVSPHE1 1 3.E-4
1376 ! 6 0 -- 0 --
1377 ! 7 XVGRAN1 -- 1 --
1378 
1379 ! PAR DEFAUT : XVGRAN1 =99 VNSPH3=50 XVSPHE1=1. XVDIAM1=4.E-4
1380 
1381 
1382 ! METHODE.
1383 ! --------
1384 ! EVOLUTION DES TYPES DE GRAINS : SELON LES LOIS DECRITES
1385 ! DANS BRUN ET AL (1992)
1386 ! PLUSIEURS CAS SONT A DISTINGUER
1387 ! 1.2 NEIGE HUMIDE
1388 ! 1.3 METAMORPHOSE NEIGE SECHE
1389 ! 1.3.1 FAIBLE GRADIENT
1390 ! 1.3.2 GRADIENT MOYEN
1391 ! 1.3.3 FORT GRADIENT
1392 ! DANS CHAQUE CAS ON SEPARE NEIGE DENDRITIQUE ET NON DENDRITIQUE
1393 ! LE PASSAGE DENDRITIQUE => NON DENDRITIQUE SE FAIT LORSQUE
1394 ! SGRAN1 DEVIENT > 0
1395 
1396 ! TASSEMENT : LOIS DE VISCOSITE ADAPTEE SELON LE TYPE DE GRAINS
1397 
1398 ! VARIABLES HISTORIQUES (CAS NON DENDRITIQUE SEULEMENT)
1399 
1400 ! MSHIST DEFAUT
1401 ! 0 CAS NORMAL
1402 ! NVHIS1 1 GRAINS ANGULEUX
1403 ! NVHIS2 2 GRAINS AYANT ETE EN PRESENCE D EAU LIQUIDE
1404 ! MAIS N'AYANT PAS EU DE CARATERE ANGULEUX
1405 ! NVHIS3 3 GRAINS AYANT ETE EN PRESENCE D EAU LIQUIDE
1406 ! AYANT EU AUPARAVANT UN CARACTERE ANGULEUX
1407 
1408 ! GRAIN METAMORPHISM ACCORDING TO BRUN ET AL (1992)
1409 ! THE DIFFERENT CASES ARE :
1410 ! 1.2 WET SNOW
1411 ! 1.3 DRY SNOW
1412 ! 1.3.1. LOW TEMPERATURE GRADIENT
1413 ! 1.3.2. MODERATE TEMPERATURE GRADIENT
1414 ! 1.3.3. HIGH TEMPERATURE GRADIENTi
1415 ! THE CASE OF DENTRITIC OR NON DENDRITIC SNOW IS TREATED SEPARATELY
1416 ! THE LIMIT DENTRITIC ==> NON DENDRITIC IS REACHED WHEN SGRAN1>0
1417 
1418 ! SNOW SETTLING : VISCOSITY DEPENDS ON THE GRAIN TYPES
1419 
1420 ! HISTORICAL VARIABLES (NON DENDRITIC CASE)
1421 ! MSHIST DEFAUT
1422 ! 0 CAS NORMAL
1423 ! NVHIS1 1 FACETED CRISTAL
1424 ! NVHIS2 2 LIQUID WATER AND NO FACETED CRISTALS BEFORE
1425 ! NVHIS3 3 LIQUID WATER AND FACETED CRISTALS BEFORE
1426 
1427 ! EXTERNES.
1428 ! ---------
1429 
1430 ! REFERENCES.
1431 ! -----------
1432 
1433 ! AUTEURS.
1434 ! --------
1435 ! ERIC BRUN ET AL. - JOURNAL OF GLACIOLOGY 1989/1992.
1436 
1437 ! MODIFICATIONS.
1438 ! --------------
1439 ! 08/95: YANNICK DANIELOU - CODAGE A LA NORME DOCTOR.
1440 ! 09/96: ERIC MARTIN - CORRECTION COMMENTAIRES
1441 ! 03/06: JM Willemet - F90 and SI units
1442 ! 08/06: JM Willemet - new formulation for TEL (Mwat/(Mice+Mwat) instead of Mwat/Mice.
1443 ! Threshold on the diameter increasing of the wet grains.
1444 ! 01/07 : JM Willemet - CORRECTION DES COUCHES SATUREES SUBISSANT DU TASSEMENT
1445 ! CORRECTION ON THE SATURATED LAYERS WHICH ARE SETTLED
1446 ! 12/12: CM Carmagnola - Dendricity and size replaced by the optical diameter
1447 ! - Test of different evolution laws for the optical diameter
1448 ! 08/13: M Lafaysse - Simplification of historical parameter computation (logicals GNONDENDRITIC, GFACETED, GSPHE_LW)
1449  !
1450 USE modd_snow_metamo
1451 USE modd_csts, ONLY : xtt, xpi, xrholw, xrholi
1452 USE modd_surf_par, ONLY : xundef
1453 !
1454 USE mode_snow3l
1455 !
1456 IMPLICIT NONE
1457 !
1458 ! 0.1 declarations of arguments
1459 !
1460 REAL, DIMENSION(:,:), INTENT(IN) :: PSNOWDZ, PSNOWTEMP, PSNOWLIQ, PSNOWSWE
1461 !
1462 REAL, DIMENSION(:,:), INTENT(INOUT) :: PSNOWGRAN1, PSNOWGRAN2, PSNOWHIST
1463 !
1464 REAL, INTENT(IN) :: PTSTEP
1465 !
1466 INTEGER, DIMENSION(:), INTENT(IN) :: INLVLS_USE
1467 !
1468 REAL, DIMENSION(:,:), INTENT(IN) :: PSNOWAGE
1469 !
1470  CHARACTER(3), INTENT(IN) :: HSNOWMETAMO ! metamorphism scheme
1471 !
1472 ! 0.2 declaration of local variables
1473 !
1474 REAL :: ZGRADT, ZTELM, ZVDENT, ZDENT, ZSPHE, ZVAP, ZDANGL, &
1475  ZSIZE, ZSSA, ZSSA0, ZSSA_T, ZSSA_T_DT, ZA, ZB, ZC, &
1476  ZA2, ZB2, ZC2, ZOPTD, ZOPTR, ZOPTR0, ZDRDT
1477 REAL :: ZVDENT1, ZVDENT2, ZVSPHE, ZCOEF_SPH
1478 REAL :: ZDENOM1, ZDENOM2, ZFACT1, ZFACT2
1479 INTEGER :: INLVLS
1480 INTEGER :: JST,JJ !Loop controls
1481 INTEGER :: IDRHO, IDGRAD, IDTEMP !Indices for values from Flanner 2006
1482 LOGICAL :: GNONDENDRITIC ,GFACETED, GSPHE_LW
1483 LOGICAL :: GCOND_B92, GCOND_C13, GCOND_SPH
1484 !
1485 REAL(KIND=JPRB) :: ZHOOK_HANDLE
1486 !
1487 ! INITIALISATION
1488 ! --------------
1489 !
1490 IF (lhook) CALL dr_hook('SNOWCROMETAMO',0,zhook_handle)
1491 !
1492 inlvls = SIZE(psnowgran1(:,:),2) ! total snow layers
1493 !
1494 !* 1. METAMORPHOSES DANS LES STRATES. / METAMORPHISM
1495 ! -----------------------------------------------
1496 DO jj = 1,SIZE(psnowrho,1)
1497  !
1498  DO jst = 1,inlvls_use(jj)
1499  !
1500  ! 1.1 INITIALISATION: GRADIENT DE TEMPERATURE / TEMPERATURE GRADIENT
1501  IF ( jst==inlvls_use(jj) ) THEN
1502  zgradt = abs(psnowtemp(jj,jst) - psnowtemp(jj,jst-1))*2. / (psnowdz(jj,jst-1) + psnowdz(jj,jst))
1503  ELSEIF ( jst==1 ) THEN
1504  zgradt = abs(psnowtemp(jj,jst+1) - psnowtemp(jj,jst) )*2. / (psnowdz(jj,jst) + psnowdz(jj,jst+1))
1505  ELSE
1506  zgradt = abs(psnowtemp(jj,jst+1) - psnowtemp(jj,jst-1))*2. / &
1507  (psnowdz(jj,jst-1) + psnowdz(jj,jst)*2. + psnowdz(jj,jst+1))
1508  ENDIF
1509  !
1510  IF ( psnowliq(jj,jst)>xuepsi ) THEN
1511  ! 1.2 METAMORPHOSE HUMIDE. / WET SNOW METAMORPHISM
1512  !
1513  ! TENEUR EN EAU LIQUIDE / LIQUID WATER CONTENT
1514  ztelm = xupourc * psnowliq(jj,jst) * xrholw / psnowswe(jj,jst)
1515  !
1516  ! VITESSES DE DIMINUTION DE LA DENDRICITE / RATE OF THE DENDRICITY DECREASE
1517  zvdent1 = max( xvdent2 * ztelm**nvdent1, xvdent1 * exp(xvvap1/xtt) )
1518  zvdent2 = zvdent1
1519  ! CONDITION POUR LE CAS NON DENDRITIQUE NON SPHERIQUE
1520  gcond_b92 = ( psnowgran1(jj,jst)<xvgran1-xuepsi )
1521  gcond_c13 = .true. ! CONDITION POUR LE CALCUL DE SNOWGRAN1
1522  ! X COEF
1523  zvsphe = xvsphe1
1524  ! FOR C13
1525  zcoef_sph = 2.
1526  !
1527  ELSEIF ( zgradt<xvgrat1 ) THEN
1528  ! 1.3.1 METAMORPHOSE SECHE FAIBLE/ DRY LOW GRADIENT (0-5 DEG/M).
1529  !
1530  zvap = exp( xvvap1/psnowtemp(jj,jst) )
1531  !
1532  ! VITESSES DE DIMINUTION DE LA DENDRICITE / RATE OF THE DENDRICITY DECREASE
1533  zvdent1 = xvdent1 * zvap
1534  zvdent2 = xvsphe2 * zvap
1535  ! CONDITION POUR LE CAS NON DENDRITIQUE SPHERICITE NON LIMITEE
1536  gcond_b92 = ( psnowhist(jj,jst)/=nvhis1 .OR. psnowgran2(jj,jst)<xvdiam2 )
1537  gcond_c13 = ( hsnowmetamo=='C13' ) ! CONDITION POUR LE CALCUL DE SNOWGRAN1
1538  ! X COEF
1539  zvsphe = xvsphe1
1540  ! FOR C13
1541  zcoef_sph = 2.
1542  !
1543  ELSE
1544  ! 1.3.2 METAMORPHOSE SECHE GRADIENT MOYEN / DRY MODERATE (5-15).
1545  ! 1.3.3 METAMORPHOSE SECHE FORT / DRY HIGH GRADIENT
1546  !
1547  zvap = exp( xvvap1/psnowtemp(jj,jst) ) * (zgradt)**xvvap2
1548  !
1549  ! VITESSES DE DIMINUTION DE LA DENDRICITE / RATE OF THE DENDRICITY DECREASE
1550  zvdent1 = xvdent1 * zvap
1551  zvdent2 = - xvdent1 * zvap
1552  ! CONDITION POUR LE CAS NON DENDRITIQUE NON COMPLETEMENT ANGULEUX
1553  gcond_b92 = ( zgradt<xvgrat2 .OR. psnowgran1(jj,jst)>0. )
1554  gcond_c13 = ( hsnowmetamo=='C13' ) ! CONDITION POUR LE CALCUL DE SNOWGRAN1
1555  ! X COEF
1556  zvsphe = xundef
1557  ! FOR C13
1558  zcoef_sph = 3.
1559  !
1560  ENDIF
1561  !
1562  IF ( hsnowmetamo=="B92" ) THEN
1563  !
1564  !------------------------------------------------
1565  ! BRUN et al. 1992 (B92)
1566  !
1567  ! -> Wet snow and dry snow
1568  ! -> Evolution of dendricity, sphericity and size
1569  !------------------------------------------------
1570  !
1571  IF ( psnowgran1(jj,jst)<-xuepsi ) THEN
1572  ! 1.2.1 CAS DENDRITIQUE/DENDRITIC CASE.
1573  !
1574  ! / CALCUL NOUVELLE DENDRICITE ET SPHERICITE.
1575  zdent = - psnowgran1(jj,jst)/xvgran1 - zvdent1 * ptstep
1576  zsphe = psnowgran2(jj,jst)/xvgran1 + zvdent2 * ptstep
1577  CALL set_thresh(zgradt,psnowliq(jj,jst),zsphe)
1578  IF( zdent<=xuepsi ) THEN
1579  ! EVOLUTION DE SGRAN1 ET SGRAN2 ET TEST PASSAGE DENDRITIQUE > NON DENDRITIQUE.
1580  psnowgran1(jj,jst) = zsphe * xvgran1
1581  psnowgran2(jj,jst) = xvdiam1 - xvdiam5 * min( zsphe, zvsphe )
1582  ELSE
1583  psnowgran1(jj,jst) = -zdent * xvgran1
1584  psnowgran2(jj,jst) = zsphe * xvgran1
1585  ENDIF
1586  !
1587  ELSEIF ( gcond_b92 ) THEN
1588  ! 1.2.2 CAS NON DENDRITIQUE ET
1589  ! NON COMPLETEMENT SPHERIQUE / NON DENDRITIC AND NOT COMPLETELY SPHERIC CASE
1590  ! OU SPHERICITE NON LIMITEE
1591  ! OU NON COMPLETEMENT ANGULEUX
1592  !
1593  ! . EVOLUTION DE LA SPHERICITE SEULEMENT / EVOLUTION OF SPHERICITY ONLY (NOT SIZE)
1594  zsphe = psnowgran1(jj,jst)/xvgran1 + zvdent2 * ptstep
1595  CALL set_thresh(zgradt,psnowliq(jj,jst),zsphe)
1596  psnowgran1(jj,jst) = zsphe * xvgran1
1597  !
1598  ELSEIF ( psnowliq(jj,jst)>xuepsi ) THEN
1599  ! 1.2.3 CAS NON DENDRITIQUE ET SPHERIQUE/NON DENDRITIC AND SPHERIC EN METAMORPHOSE HUMIDE
1600  !
1601  ! EVOLUTION DE LA TAILLE SEULEMENT/EVOLUTION OF SIZE ONLY
1602  CALL get_gran(ptstep,ztelm,psnowgran2(jj,jst))
1603  !
1604  ELSEIF ( zgradt<xvgrat1 ) THEN
1605  ! 1.2.4. CAS HISTORIQUE=2 OU 3 ET GROS GRAINS SPHERICITE LIMITEE / CASE HISTORY=2 OR 3 AND BIG GRAINS LIMITED SPHERICITY
1606  !
1607  zsphe = psnowgran1(jj,jst)/xvgran1 + &
1608  zvdent2 * ptstep * exp( min( 0., xvdiam3-psnowgran2(jj,jst) ) / xvdiam6 )
1609  zsphe = min( zsphe, xvsphe3 )
1610  CALL set_thresh(zgradt,psnowliq(jj,jst),zsphe)
1611  psnowgran1(jj,jst) = zsphe * xvgran1
1612  !
1613  ELSE
1614  ! 1.2.5. CAS NON DENDRITIQUE ET ANGULEUX/DENDRITIC AND SPERICITY=0.
1615  !
1616  zdangl = snow3l_marbouty(psnowrho(jj,jst),psnowtemp(jj,jst),zgradt)
1617  psnowgran2(jj,jst) = psnowgran2(jj,jst) + zdangl * xvfi * ptstep
1618  !
1619  ENDIF
1620  !
1621  ELSE
1622  !
1623  !------------------------------------------------
1624  ! CARMAGNOLA et al. 2013 (C13)
1625  !
1626  ! -> Wet snow
1627  ! -> Evolution of optical diameter and sphericity
1628  !------------------------------------------------
1629  !
1630  ! SPHERICITY
1631  zsphe = psnowgran2(jj,jst) + zvdent2 * ptstep
1632  CALL set_thresh(zgradt,psnowliq(jj,jst),zsphe)
1633  IF ( psnowliq(jj,jst)>xuepsi .OR. zgradt<xvgrat1 ) THEN
1634  gcond_sph = ( zsphe < 1.-xuepsi )
1635  ELSE
1636  gcond_sph = ( zsphe > xuepsi )
1637  ENDIF
1638  !
1639  IF ( gcond_c13 .AND. psnowgran1(jj,jst)<xvdiam6*(4.-zsphe)-xuepsi ) THEN
1640  ! 1.1.1 CAS DENDRITIQUE/DENDRITIC CASE.
1641  !
1642  IF ( gcond_sph ) THEN
1643  psnowgran1(jj,jst) = psnowgran1(jj,jst) + xvdiam6 * ptstep * &
1644  ( zvdent2*(psnowgran1(jj,jst)/xvdiam6-1.)/(zsphe-3.) - &
1645  zvdent1*(zsphe-3.) )
1646  ELSE
1647  psnowgran1(jj,jst) = psnowgran1(jj,jst) + xvdiam6 * ptstep * zvdent1 * zcoef_sph
1648  ENDIF
1649  !
1650  ELSEIF ( gcond_c13 .AND. gcond_sph ) THEN
1651  ! 1.2.2 CAS NON DENDRITIQUE ET
1652  ! NON COMPLETEMENT SPHERIQUE / NON DENDRITIC AND NOT COMPLETELY SPHERIC CASE
1653  ! OU NON COMPLETEMENT ANGULEUX
1654  !
1655  psnowgran1(jj,jst) = psnowgran1(jj,jst) - xvdiam6 * ptstep * zvdent2 * 2.* zsphe
1656  !
1657  ELSEIF ( psnowliq(jj,jst)>xuepsi ) THEN
1658  ! 1.2.3 CAS NON DENDRITIQUE ET SPHERIQUE/NON DENDRITIC AND SPHERIC EN METAMORPHOSE HUMIDE
1659  !
1660  ! NON DENDRITIC AND SPHERIC: EVOLUTION OF SIZE ONLY
1661  CALL get_gran(ptstep,ztelm,psnowgran1(jj,jst))
1662  !
1663  ELSEIF ( gcond_c13 .AND. zgradt>=xvgrat2 ) THEN
1664  !
1665  zdangl = snow3l_marbouty(psnowrho(jj,jst),psnowtemp(jj,jst),zgradt)
1666  psnowgran1(jj,jst) = psnowgran1(jj,jst) + 0.5 * zdangl * xvfi * ptstep
1667  !
1668  ENDIF
1669  !
1670  psnowgran2(jj,jst) = zsphe
1671  !
1672  !---------------------------------
1673  ! TAILLANDIER et al. 2007 (T07)
1674  !
1675  ! -> Dry snow
1676  ! -> Evolution of optical diameter
1677  !---------------------------------
1678  !
1679  IF ( psnowliq(jj,jst)<=xuepsi .AND. hsnowmetamo=='T07' ) THEN
1680  !
1681  ! WRITE(*,*) csnowmetamo,': you are using T07 formulation!!'
1682  !
1683  ! Coefficients from Taillander et al. 2007
1684  zssa0 = 6./( xrholi*xvdiam6 ) * 10.
1685  !
1686  za = 0.659*zssa0 - 27.2 * ( psnowtemp(jj,jst)-273.15-2.03 ) ! TG conditions
1687  zb = 0.0961*zssa0 - 3.44 * ( psnowtemp(jj,jst)-273.15+1.90 )
1688  zc = -0.341*zssa0 - 27.2 * ( psnowtemp(jj,jst)-273.15-2.03 )
1689  za2 = 0.629*zssa0 - 15.0 * ( psnowtemp(jj,jst)-273.15-11.2 ) ! ET conditions
1690  zb2 = 0.0760*zssa0 - 1.76 * ( psnowtemp(jj,jst)-273.15-2.96 )
1691  zc2 = -0.371*zssa0 - 15.0 * ( psnowtemp(jj,jst)-273.15-11.2 )
1692  !
1693  ! Compute SSA (method from Jacobi, 2010)
1694 ! ZSSA = 6./(XRHOLI*PSNOWGRAN1(JJ,JST))*10.
1695 ! ZSSA_t = (0.5+0.5*TANH(0.5*(ZGRADT-10.)))*(ZA-ZB*LOG(PSNOWAGE(JJ,JST)*24+EXP(ZC/ZB))) + &
1696 ! (0.5-0.5*TANH(0.5*(ZGRADT-10.)))*(ZA2-ZB2*LOG(PSNOWAGE(JJ,JST)*24+EXP(ZC2/ZB2)))
1697 !
1698 ! ZSSA_t_dt = (0.5+0.5*TANH(0.5*(ZGRADT-10.)))*(ZA-ZB*LOG(PSNOWAGE(JJ,JST)*24+PTSTEP/3600.+EXP(ZC/ZB))) + &
1699 ! (0.5-0.5*TANH(0.5*(ZGRADT-10.)))*(ZA2-ZB2*LOG(PSNOWAGE(JJ,JST)*24+PTSTEP/3600.+EXP(ZC2/ZB2)))
1700 !
1701 ! ZSSA = ZSSA + (ZSSA_t_dt-ZSSA_t)
1702 !
1703 ! ZSSA = MAX(ZSSA,8.*10.)
1704 !
1705 ! PSNOWGRAN1(JJ,JST) = 6./(XRHOLI*ZSSA)*10.
1706  !
1707  ! Compute SSA (rate equation with Taylor series)
1708  zssa = 6./( xrholi*psnowgran1(jj,jst) ) * 10.
1709  !
1710  zdenom1 = (psnowage(jj,jst)*24.) + exp(zc/zb)
1711  zdenom2 = (psnowage(jj,jst)*24.) + exp(zc2/zb2)
1712  zfact1 = 0.5 + 0.5*tanh( 0.5*(zgradt-10.) )
1713  zfact2 = 0.5 - 0.5*tanh( 0.5*(zgradt-10.) )
1714  zssa = zssa + (ptstep/3600.) * ( zfact1 * (-zb/zdenom1) + zfact2 * (-zb2/zdenom2) + &
1715  (ptstep/3600.) * ( zfact1 * (zb/zdenom1**2.) + zfact2 * (zb2/zdenom2**2.) ) * 1./2. )
1716  !ZSSA = ZSSA + (PTSTEP/3600.) * ( ZFACT1 * ZB /ZDENOM1 * ( 1./ZDENOM1 * (PTSTEP/3600.) * 1./2. - 1. ) + &
1717  ! ZFACT2 * ZB2/ZDENOM2 * ( 1./ZDENOM2 * (PTSTEP/3600.) * 1./2. - 1. ) )
1718  !
1719  zssa = max( zssa, 8.*10. )
1720  !
1721  psnowgran1(jj,jst) = 6./( xrholi*zssa ) * 10.
1722  !
1723  !---------------------------------
1724  ! FLANNER et al. 2006 (F06)
1725  !
1726  ! -> Dry snow
1727  ! -> Evolution of optical diameter
1728  !---------------------------------
1729  ELSEIF ( psnowliq(jj,jst)<=xuepsi .AND. hsnowmetamo=='F06' )THEN
1730  !
1731  ! WRITE(*,*) CSNOWMETAMO,': you are using F06 formulation!!'
1732  !
1733  ! XDRDT0(dens,gradT,T), XTAU(dens,gradT,T), XKAPPA(dens,gradT,T)
1734  ! dens: [1-8 <-> 50.-400. kg/m3]
1735  ! gradT: [1-31 <-> 0.-300. K/m]
1736  ! T: [1-11 <-> 223.15-273.15 K]
1737  !
1738  ! Select indices of density, temperature gradient and temperature
1739  idrho = min( abs( int( (psnowrho(jj,jst)-25.)/50. ) + 1 ), 8 )
1740  idgrad = min( abs( int( (zgradt-5.)/10.+2. ) ), 31 )
1741  idtemp = min( abs( int( (psnowtemp(jj,jst)-225.65 )/5.+2. ) ), 11 )
1742  IF ( psnowtemp(jj,jst)<221. ) idtemp = 1
1743  !
1744  ! Compute SSA
1745  zoptr0 = xvdiam6/2. * 10.**6.
1746  zoptr = psnowgran1(jj,jst)/2. * 10.**6.
1747  zdrdt = xdrdt0(idrho,idgrad,idtemp) * &
1748  ( xtau(idrho,idgrad,idtemp) / &
1749  ( zoptr - zoptr0 + xtau(idrho,idgrad,idtemp) ) )**(1./xkappa(idrho,idgrad,idtemp))
1750  zoptr = zoptr + zdrdt * ptstep/3600.
1751  zoptr = min( zoptr, 3./(xrholi*2.) * 10.**6.)
1752  !
1753  psnowgran1(jj,jst) = zoptr * 2./10.**6.
1754  !
1755  ENDIF
1756  !
1757  ENDIF
1758  !
1759  ENDDO
1760  !
1761 ENDDO
1762 
1763 !* 2. MISE A JOUR VARIABLES HISTORIQUES (CAS NON DENDRITIQUE).
1764 ! UPDATE OF THE HISTORICAL VARIABLES
1765 ! --------------------------------------------------------
1766 DO jj = 1,SIZE(psnowrho,1)
1767  !
1768  DO jst = 1,inlvls_use(jj)
1769  !
1770  IF ( hsnowmetamo=='B92' ) THEN
1771  !
1772  !non dendritic
1773  gnondendritic = ( psnowgran1(jj,jst)>=0. )
1774  IF ( gnondendritic ) THEN
1775  !faceted crystals
1776  gfaceted = ( psnowgran1(jj,jst)<xvsphe4 .AND. psnowhist(jj,jst)==0. )
1777  !spheric and liquid water
1778  gsphe_lw = ( xvgran1-psnowgran1(jj,jst)<xvsphe4 .AND. psnowliq(jj,jst)/psnowdz(jj,jst)>xvtelv1 )
1779  END IF
1780  !
1781  ELSE
1782  !
1783  !non dendritic
1784  gnondendritic = ( psnowgran1(jj,jst)>=xvdiam6*(4.-psnowgran2(jj,jst))-xuepsi )
1785  IF ( gnondendritic ) THEN
1786  !faceted crystals
1787  gfaceted = ( psnowgran2(jj,jst)<xvsphe4/xvgran1 .AND. psnowhist(jj,jst)==0. )
1788  !spheric and liquid water
1789  gsphe_lw = ( xvsphe1-psnowgran2(jj,jst)<xvsphe4/xvgran1 .AND. psnowliq(jj,jst)/psnowdz(jj,jst)>xvtelv1 )
1790  END IF
1791  !
1792  ENDIF
1793  !
1794  IF ( gnondendritic ) THEN
1795  !
1796  IF ( gfaceted ) THEN
1797  !
1798  psnowhist(jj,jst) = nvhis1
1799  !
1800  ELSEIF ( gsphe_lw ) THEN
1801  !
1802  IF (psnowhist(jj,jst)==0.) psnowhist(jj,jst) = nvhis2
1803  IF (psnowhist(jj,jst)==nvhis1) psnowhist(jj,jst) = nvhis3
1804  !
1805  ELSEIF ( psnowtemp(jj,jst) < xtt ) THEN
1806  !
1807  IF(psnowhist(jj,jst)==nvhis2) psnowhist(jj,jst) = nvhis4
1808  IF(psnowhist(jj,jst)==nvhis3) psnowhist(jj,jst) = nvhis5
1809  !
1810  ENDIF
1811  !
1812  ENDIF
1813  !
1814  ENDDO
1815  !
1816 ENDDO
1817 !
1818 IF (lhook) CALL dr_hook('SNOWCROMETAMO',1,zhook_handle)
1819 !
1820 END SUBROUTINE snowcrometamo
1821 !
1822 !####################################################################
1823 !####################################################################
1824 SUBROUTINE set_thresh(PGRADT,PSNOWLIQ,PSPHE)
1826 USE modd_snow_metamo, ONLY : xuepsi, xvgrat1
1827 !
1828 IMPLICIT NONE
1829 !
1830 REAL, INTENT(IN) :: PGRADT
1831 REAL, INTENT(IN) :: PSNOWLIQ
1832 REAL, INTENT(INOUT) :: PSPHE
1833 !
1834 IF ( psnowliq>xuepsi .OR. pgradt<xvgrat1 ) THEN
1835  psphe = min(1.,psphe)
1836 ELSE
1837  psphe = max(0.,psphe)
1838 ENDIF
1839 !
1840 END SUBROUTINE set_thresh
1841 !####################################################################
1842 !####################################################################
1843 SUBROUTINE get_gran(PTSTEP,PTELM,PGRAN)
1845 USE modd_csts, ONLY : xpi
1847 !
1848 IMPLICIT NONE
1849 !
1850 REAL, INTENT(IN) :: PTSTEP, PTELM
1851 REAL, INTENT(INOUT) :: PGRAN
1852 !
1853 REAL(KIND=JPRB) :: ZHOOK_HANDLE
1854 !
1855 IF (lhook) CALL dr_hook('SNOWCRO:GET_GRAN',0,zhook_handle)
1856 !
1857 pgran = 2. * ( 3./(4.*xpi) * &
1858  ( 4. * xpi/3. * (pgran/2.)**3 + &
1859  ( xvtail1 + xvtail2 * ptelm**nvdent1 ) * ptstep ) )**(1./3.)
1860 !
1861 IF (lhook) CALL dr_hook('SNOWCRO:GET_GRAN',1,zhook_handle)
1862 !
1863 END SUBROUTINE get_gran
1864 !
1865 !####################################################################
1866 !####################################################################
1867 !####################################################################
1868 !
1869 SUBROUTINE snowcroalb(TPTIME,OGLACIER, &
1870  PALBEDOSC,PSPECTRALALBEDO,PSNOWDZ, &
1871  PSNOWRHO,PPERMSNOWFRAC, &
1872  PSNOWGRAN1_TOP,PSNOWGRAN2_TOP,PSNOWAGE_TOP, &
1873  PSNOWGRAN1_BOT,PSNOWGRAN2_BOT,PSNOWAGE_BOT, &
1874  PPS, PZENITH, KNLVLS_USE ,HSNOWMETAMO )
1876 !! PURPOSE
1877 !! -------
1878 ! Calculate the snow surface albedo. Use the method of original
1879 ! Crocus which considers a specified spectral distribution of solar
1880 ! solar radiation (to be replaced by an input forcing when available)
1881 ! In addition to original crocus, the top 2 surface snow layers are
1882 ! considered in the calculation, using an arbitrary weighting, in order
1883 ! to avoid time discontinuities due to layers agregation
1884 ! Ageing depends on the presence of permanent snow cover
1885 !
1886 USE modd_snow_par, ONLY : xansmax, xansmin,xaglamin, xaglamax, &
1887  xvrpre1,xvrpre2,xvaging_noglacier, &
1888  xvaging_glacier, xvspec1,xvspec2, &
1889  xvspec3, xvw1,xvw2,xvd1,xvd2
1890 
1891 USE modd_type_date_surf, ONLY : date_time
1892 !
1893 USE mode_snow3l
1894 !
1895 IMPLICIT NONE
1896 !
1897 !* 0.1 declarations of arguments
1898 !
1899 TYPE(date_time), INTENT(IN) :: TPTIME ! current date and time
1900 LOGICAL, INTENT(IN) :: OGLACIER ! True = Over permanent snow and ice,
1901 ! initialise WGI=WSAT,
1902 ! Hsnow>=10m and allow 0.8<SNOALB<0.85
1903  ! False = No specific treatment
1904 REAL, DIMENSION(:), INTENT(IN) :: PSNOWDZ,PPERMSNOWFRAC
1905 !
1906 REAL,DIMENSION(:,:), INTENT(IN) :: PSNOWRHO ! For now only the 2 first layers are required
1907 !
1908 REAL, DIMENSION(:), INTENT(INOUT) :: PALBEDOSC
1909 !
1910 REAL, DIMENSION(:,:), INTENT(OUT) :: PSPECTRALALBEDO ! Albedo in the different spectral bands
1911 !
1912 REAL, DIMENSION(:), INTENT(IN) :: PSNOWGRAN1_TOP,PSNOWGRAN2_TOP,PSNOWAGE_TOP, &
1913  PSNOWGRAN1_BOT,PSNOWGRAN2_BOT,PSNOWAGE_BOT, PPS
1914 INTEGER, DIMENSION(:), INTENT(IN) :: KNLVLS_USE
1915 !
1916 REAL, DIMENSION(:), INTENT(IN) :: PZENITH ! solar zenith angle for future use
1917 !
1918  CHARACTER(3),INTENT(IN) :: HSNOWMETAMO ! metamorphism scheme
1919 !
1920 !* 0.2 declarations of local variables
1921 !
1922 REAL, DIMENSION(SIZE(PSNOWRHO,1),3) :: ZALB_TOP, ZALB_BOT
1923 !
1924 REAL, DIMENSION(SIZE(PSNOWRHO,1)) :: ZANSMIN, ZANSMAX, ZMIN, ZMAX
1925 REAL, DIMENSION(SIZE(PSNOWRHO,1)) :: ZFAC_TOP, ZFAC_BOT
1926 !
1927 REAL, DIMENSION(SIZE(PALBEDOSC)) :: ZVAGE1
1928 !
1929 !REAL :: ZAGE_NOW
1930 !
1931 INTEGER :: JJ ! looping indexes
1932 !
1933 REAL(KIND=JPRB) :: ZHOOK_HANDLE
1934 !-------------------------------------------------------------------------------
1935 !
1936 IF (lhook) CALL dr_hook('SNOWCROALB',0,zhook_handle)
1937 !
1938 ! 0. Initialize:
1939 ! ------------------
1940 !
1941 ! PRINT*,XVAGING_NOGLACIER,XVAGING_GLACIER
1942 IF ( oglacier ) THEN
1943  zansmin(:) = xaglamin * ppermsnowfrac(:) + xansmin * (1.0-ppermsnowfrac(:))
1944  zansmax(:) = xaglamax * ppermsnowfrac(:) + xansmax * (1.0-ppermsnowfrac(:))
1945  zvage1(:) = xvaging_glacier * ppermsnowfrac(:) + xvaging_noglacier * (1.0-ppermsnowfrac(:))
1946 ELSE
1947  zansmin(:) = xansmin
1948  zansmax(:) = xansmax
1949  zvage1(:) = xvaging_noglacier
1950 ENDIF
1951 !
1952 ! ! ! ! ! ! date computation for ageing effects
1953 ! ! ! ! ! CALL GREGODSTRATI(TPTIME%TDATE%YEAR,TPTIME%TDATE%MONTH,TPTIME%TDATE%DAY, &
1954 ! ! ! ! ! TPTIME%TIME,ZAGE_NOW)
1955 !
1956 ! coherence control
1957 ! to remove when initialization routines will be updated
1958 IF ( minval(psnowage_bot)<0. ) THEN
1959  CALL abor1_sfx('FATAL ERROR in SNOWCRO: Snow layer age inconsistent : check initialization routine. !')
1960 END IF
1961 !
1962 ! ! ! ! ! ! should be moved with other time controls to not compute MAXVAL(PSNOWAGE_TOP) at each time step
1963 ! ! ! ! ! IF ((ZAGE_NOW - MAXVAL(PSNOWAGE_TOP))<-0.001) THEN
1964 ! ! ! ! ! WRITE(*,*),"ZAGE_NOW=",ZAGE_NOW
1965 ! ! ! ! ! WRITE(*,*),"MAXVAL(PSNOWAGE_TOP)=",MAXVAL(PSNOWAGE_TOP)
1966 ! ! ! ! ! CALL ABOR1_SFX(&
1967 ! ! ! ! ! 'FATAL ERROR in SNOWCRO: Snow layer date inconsistent with the current day !')
1968 ! ! ! ! ! END IF
1969 !
1970 DO jj=1, SIZE(palbedosc)
1971  !
1972  IF ( knlvls_use(jj)==0 ) THEN
1973  ! case with no snow on the ground
1974  palbedosc(jj) = zansmin(jj)
1975  ELSE
1976  !
1977  CALL get_alb(jj,psnowrho(jj,1),pps(jj),zvage1(jj),psnowgran1_top(jj),&
1978  psnowgran2_top(jj),psnowage_top(jj),zalb_top(jj,:),hsnowmetamo)
1979  !
1980 ! IF (KNLVLS_USE(JJ)>=1) THEN
1981  IF ( knlvls_use(jj)>=2 ) THEN !modif ML
1982  ! second surface layer when it exists
1983  !
1984  CALL get_alb(jj,psnowrho(jj,2),pps(jj),zvage1(jj),psnowgran1_bot(jj),&
1985  psnowgran2_bot(jj),min(365.,psnowage_bot(jj)),zalb_bot(jj,:),hsnowmetamo)
1986  !
1987  ELSE
1988  ! when it does not exist, the second surface layer gets top layer albedo
1989  zalb_bot(jj,1) = zalb_top(jj,1)
1990  zalb_bot(jj,2) = zalb_top(jj,2)
1991  zalb_bot(jj,3) = zalb_top(jj,3)
1992  ENDIF
1993  !
1994  ! computation of spectral albedo over 3 bands taking into account the respective
1995  ! depths of top layers
1996  zmin(jj) = min( 1., psnowdz(jj)/xvd1 )
1997  zmax(jj) = max( 0., (psnowdz(jj)-xvd1)/xvd2 )
1998  zfac_top(jj) = xvw1 * zmin(jj) + xvw2 * min( 1., zmax(jj) )
1999  zfac_bot(jj) = xvw1 * ( 1. - zmin(jj) ) + xvw2 * ( 1. - min( 1., zmax(jj) ) )
2000  pspectralalbedo(jj,1) = zfac_top(jj) * zalb_top(jj,1) + zfac_bot(jj) * zalb_bot(jj,1)
2001  pspectralalbedo(jj,2) = zfac_top(jj) * zalb_top(jj,2) + zfac_bot(jj) * zalb_bot(jj,2)
2002  pspectralalbedo(jj,3) = zfac_top(jj) * zalb_top(jj,3) + zfac_bot(jj) * zalb_bot(jj,3)
2003  !
2004  ! arbitrarily specified spectral distribution
2005  ! to be changed when solar radiation distribution is an input variable
2006  palbedosc(jj) = xvspec1 * pspectralalbedo(jj,1) + &
2007  xvspec2 * pspectralalbedo(jj,2) + &
2008  xvspec3 * pspectralalbedo(jj,3)
2009  !
2010  ENDIF ! end case with snow on the ground
2011  !
2012 ENDDO ! end loop grid points
2013 !
2014 IF (lhook) CALL dr_hook('SNOWCROALB',1,zhook_handle)
2015 !-------------------------------------------------------------------------------
2016 !
2017 END SUBROUTINE snowcroalb
2018 !####################################################################
2019 SUBROUTINE get_alb(KJ,PSNOWRHO_IN,PPS_IN,PVAGE1,PSNOWGRAN1,PSNOWGRAN2,PSNOWAGE,PALB,&
2020  HSNOWMETAMO)
2021 !
2022 USE modd_snow_par, ONLY : xalbice1, xalbice2, xalbice3, &
2023  xrhothreshold_ice, &
2024  xvalb2, xvalb3, xvalb4, xvalb5, &
2025  xvalb6, xvalb7, xvalb8, xvalb9, &
2026  xvalb10, xvalb11, xvdiop1, &
2027  xvrpre1, xvrpre2, xvpres1
2028 !
2029 USE mode_snow3l, ONLY : get_diam
2030 !
2031 IMPLICIT NONE
2032 !
2033 INTEGER, INTENT(IN) :: KJ
2034 REAL, INTENT(IN) :: PSNOWRHO_IN, PPS_IN
2035 REAL, INTENT(IN) :: PVAGE1
2036 REAL, INTENT(IN) :: PSNOWGRAN1, PSNOWGRAN2, PSNOWAGE
2037 REAL, DIMENSION(3), INTENT(OUT) :: PALB
2038 !
2039  CHARACTER(3),INTENT(IN)::HSNOWMETAMO
2040 !
2041 REAL :: ZDIAM, ZDIAM_SQRT
2042 !
2043 REAL(KIND=JPRB) :: ZHOOK_HANDLE
2044 !
2045 IF (lhook) CALL dr_hook('SNOWCRO:GET_ALB',0,zhook_handle)
2046 !
2047 IF ( psnowrho_in<xrhothreshold_ice ) THEN
2048  ! Normal case (snow)
2049  CALL get_diam(psnowgran1,psnowgran2,zdiam,hsnowmetamo)
2050  zdiam_sqrt = sqrt(zdiam)
2051  palb(1) = min( xvalb2 - xvalb3*zdiam_sqrt, xvalb4 )
2052  palb(2) = max( 0.3, xvalb5 - xvalb6*zdiam_sqrt )
2053  zdiam = min( zdiam, xvdiop1 )
2054  zdiam_sqrt = sqrt(zdiam)
2055  palb(3) = max( 0., xvalb7*zdiam - xvalb8*zdiam_sqrt + xvalb9 )
2056  ! AGE CORRECTION ONLY FOR VISIBLE BAND
2057 
2058 ! ! ! ! ! PALB(1)=MAX(XVALB11,PALB(1)-MIN(MAX(PPS_IN/XVPRES1,XVRPRE1), &
2059 ! ! ! ! ! XVRPRE2)*XVALB10*MIN(365.,ZAGE_NOW-PSNOWAGE)/PVAGE1)
2060 
2061  palb(1) = max( xvalb11, palb(1) - min( max(pps_in/xvpres1,xvrpre1), xvrpre2 ) * &
2062  xvalb10 * psnowage / pvage1 )
2063 ELSE
2064  ! Prescribed spectral albedo for surface ice
2065  palb(1) = xalbice1
2066  palb(2) = xalbice2
2067  palb(3) = xalbice3
2068 ENDIF
2069 !
2070 IF (lhook) CALL dr_hook('SNOWCRO:GET_ALB',1,zhook_handle)
2071 !
2072 END SUBROUTINE get_alb
2073 !
2074 !####################################################################
2075 !####################################################################
2076 SUBROUTINE snowcrorad(TPTIME, OGLACIER, &
2077  PSW_RAD, PSNOWALB, PSNOWDZ, &
2078  PSNOWRHO, PALB, PRADSINK, PRADXS, &
2079  PSNOWGRAN1, PSNOWGRAN2, PSNOWAGE,PPS, &
2080  PZENITH, PPERMSNOWFRAC,KNLVLS_USE, &
2081  OSNOW_ABS_ZENITH,HSNOWMETAMO)
2083 !! PURPOSE
2084 !! -------
2085 ! Calculate the transmission of shortwave (solar) radiation
2086 ! through the snowpack (using a form of Beer's Law: exponential
2087 ! decay of radiation with increasing snow depth).
2088 ! Needs a first calculation of the albedo to stay coherent with
2089 ! ISBA-ES ==> make sure to keep SNOWCRORAD coherent with SNOWCROALB
2090 !
2091 USE modd_snow_par, ONLY : xwcrn, xansmax, xansmin, xans_todry, &
2092  xsnowdmin, xans_t, xaglamin, xaglamax, &
2093  xd1, xd2, xd3, xx, xvspec1, xvspec2, xvspec3, &
2094  xvbeta1, xvbeta2, xvbeta3, xvbeta4, xvbeta5
2095 USE modd_type_date_surf, ONLY : date_time
2096 !
2097 USE mode_snow3l, ONLY : get_diam
2098 !
2099 IMPLICIT NONE
2100 !
2101 !* 0.1 declarations of arguments
2102 !
2103 TYPE(date_time), INTENT(IN) :: TPTIME ! current date and time
2104 LOGICAL, INTENT(IN) :: OGLACIER ! True = Over permanent snow and ice,
2105 ! initialise WGI=WSAT,
2106 ! Hsnow>=10m and allow 0.8<SNOALB<0.85
2107  ! False = No specific treatment
2108 !
2109 REAL, DIMENSION(:), INTENT(IN) :: PSW_RAD, PSNOWALB, PALB,PPERMSNOWFRAC
2110 !
2111 REAL, DIMENSION(:,:), INTENT(IN) :: PSNOWRHO, PSNOWDZ
2112 !
2113 LOGICAL, INTENT(IN) :: OSNOW_ABS_ZENITH ! parametrization for polar regions (not physic but better results)
2114 ! ! default FALSE
2115  CHARACTER(3), INTENT(IN) :: HSNOWMETAMO
2116 !
2117 REAL, DIMENSION(:), INTENT(OUT) :: PRADXS
2118 !
2119 REAL, DIMENSION(:,:), INTENT(OUT) :: PRADSINK
2120 !
2121 REAL, DIMENSION(:,:), INTENT(IN) :: PSNOWGRAN1, PSNOWGRAN2, PSNOWAGE
2122 REAL, DIMENSION(:), INTENT(IN) :: PPS
2123 INTEGER, DIMENSION(:), INTENT(IN) :: KNLVLS_USE
2124 REAL, DIMENSION(:), INTENT(IN) :: PZENITH
2125 !
2126 !* 0.2 declarations of local variables
2127 !
2128 REAL, DIMENSION(SIZE(PSNOWRHO,1)) :: ZRADTOT
2129 REAL, DIMENSION(SIZE(PSNOWRHO,1)) :: ZALB_NEW
2130 REAL, DIMENSION(SIZE(PSNOWRHO,1),3) :: ZALB !albedo 3 bands
2131 REAL, DIMENSION(SIZE(PSNOWRHO,2)) :: ZDIAM
2132 REAL, DIMENSION(SIZE(PSNOWRHO,2),3) :: ZBETA
2133 REAL, DIMENSION(3) :: ZOPTICALPATH, ZFACT
2134 REAL :: ZPROJLAT
2135 !
2136 INTEGER :: JJ,JST,JB ! looping indexes
2137 !
2138 REAL(KIND=JPRB) :: ZHOOK_HANDLE
2139 !-------------------------------------------------------------------------------
2140 IF (lhook) CALL dr_hook('SNOWCRORAD',0,zhook_handle)
2141 !
2142 ! 0. Initialization:
2143 ! ------------------
2144 !
2145 pradsink(:,:) = 0.
2146 !
2147 ! 1. Computation of the new albedo (see SNOWCROALB):
2148 ! -----------------------------------
2149 !
2150  CALL snowcroalb(tptime,oglacier, &
2151  zalb_new,zalb,psnowdz(:,1),psnowrho(:,1:2), &
2152  ppermsnowfrac,psnowgran1(:,1),psnowgran2(:,1), &
2153  psnowage(:,1),psnowgran1(:,2),psnowgran2(:,2),psnowage(:,2), &
2154  pps, pzenith, knlvls_use, hsnowmetamo )
2155 !
2156 DO jj = 1,SIZE(psw_rad)
2157  !
2158  DO jst = 1,knlvls_use(jj)
2159  CALL get_diam(psnowgran1(jj,jst),psnowgran2(jj,jst),zdiam(jst),hsnowmetamo)
2160  ENDDO ! end loop snow layers
2161  !
2162  ! 2. Extinction of net shortwave radiation
2163  ! ----------------------------------------
2164  ! First calculates extinction coefficients fn of grain size and density
2165  ! then calculates exctinction in the layer and increases optical path length
2166  !
2167  ! Coefficient for taking into account the increase of path length of rays
2168  ! in snow due to zenithal angle
2169  zprojlat = 1. / max( xuepsi, cos(pzenith(jj)) )
2170  !
2171  pradsink(jj,:) = -psw_rad(jj) * ( 1.-psnowalb(jj) ) / ( 1.-zalb_new(jj) )
2172  !
2173  ! Initialize optical depth
2174  zopticalpath(1) = 0.
2175  zopticalpath(2) = 0.
2176  zopticalpath(3) = 0.
2177  !
2178  DO jst = 1,knlvls_use(jj)
2179  !
2180  zbeta(jst,1) = max( xvbeta1 * psnowrho(jj,jst) / sqrt(zdiam(jst)), xvbeta2 )
2181  zbeta(jst,2) = max( xvbeta3 * psnowrho(jj,jst) / sqrt(zdiam(jst)), xvbeta4 )
2182  zbeta(jst,3) = xvbeta5
2183  !
2184  zfact(:) = 0.
2185  DO jb = 1,3
2186  zopticalpath(jb) = zopticalpath(jb) + zbeta(jst,jb) * psnowdz(jj,jst)
2187  IF (osnow_abs_zenith) THEN
2188  !This formulation is incorrect but it compensate partly the fact that the albedo formulation does not account for zenithal angle
2189  zfact(jb) = (1.-zalb(jj,jb)) * exp( -zopticalpath(jb)*zprojlat)
2190  ELSE
2191  zfact(jb) = (1.-zalb(jj,jb)) * exp( -zopticalpath(jb) )
2192  ENDIF
2193  ENDDO
2194  !
2195  pradsink(jj,jst) = pradsink(jj,jst) * &
2196  ( xvspec1*zfact(1) + xvspec2*zfact(2) + xvspec3*zfact(3) )
2197  !
2198  ENDDO ! end loop snow layers
2199  !
2200  ! For thin snow packs, radiation might reach base of
2201  ! snowpack and the reflected energy can be absorbed by the bottom of snow layer:
2202  ! THIS PROCESS IS NOT SIMULATED
2203  !
2204  ! 4. Excess radiation not absorbed by snowpack (W/m2)JJ
2205  ! ----------------------------------------------------
2206  !
2207  pradxs(jj) = -pradsink( jj,knlvls_use(jj) )
2208  !
2209 ENDDO !end loop grid points
2210 !
2211 IF (lhook) CALL dr_hook('SNOWCRORAD',1,zhook_handle)
2212 !-------------------------------------------------------------------------------
2213 !
2214 END SUBROUTINE snowcrorad
2215 !####################################################################
2216 !####################################################################
2217 !####################################################################
2218 SUBROUTINE snowcrothrm(PSNOWRHO,PSCOND,PSNOWTEMP,PPS,PSNOWLIQ, &
2219  OCOND_GRAIN,OCOND_YEN )
2221 !! PURPOSE
2222 !! -------
2223 ! Calculate snow thermal conductivity from
2224 ! Sun et al. 1999, J. of Geophys. Res., 104, 19587-19579
2225 ! (vapor) and Anderson, 1976, NOAA Tech. Rep. NWS 19 (snow).
2226 !
2227 ! Upon activation of flag OCOND_YEN, use the Yen (1981) formula for thermal conductivity
2228 ! This formula was originally used in Crocus.
2229 !
2230 USE modd_csts, ONLY : xp00, xcondi, xrholw
2231 USE modd_snow_par, ONLY : xsnowthrmcond1, xsnowthrmcond2, xsnowthrmcond_avap, &
2232  xsnowthrmcond_bvap, xsnowthrmcond_cvap, xvrkz6
2233 !
2234 IMPLICIT NONE
2235 !
2236 !* 0.1 declarations of arguments
2237 !
2238 REAL, DIMENSION(:), INTENT(IN) :: PPS
2239 REAL, DIMENSION(:,:), INTENT(IN) :: PSNOWTEMP, PSNOWRHO, PSNOWLIQ
2240 REAL, DIMENSION(:,:), INTENT(OUT) :: PSCOND
2241 LOGICAL, INTENT(IN) :: OCOND_GRAIN, OCOND_YEN
2242 !
2243 !* 0.2 declarations of local variables
2244 !
2245 INTEGER :: JJ, JST ! looping indexes
2246 !
2247 REAL(KIND=JPRB) :: ZHOOK_HANDLE
2248 !-------------------------------------------------------------------------------
2249 IF (lhook) CALL dr_hook('SNOWCROTHRM',0,zhook_handle)
2250 !
2251 ! 1. Snow thermal conductivity
2252 ! ----------------------------
2253 !
2254 DO jst = 1,SIZE(psnowrho(:,:),2)
2255  !
2256  DO jj = 1,SIZE(psnowrho(:,:),1)
2257  !
2258  IF ( ocond_yen ) THEN
2259  pscond(jj,jst) = xcondi * exp( xvrkz6 * log( psnowrho(jj,jst)/xrholw ) )
2260  ELSE
2261  pscond(jj,jst) = ( xsnowthrmcond1 + &
2262  xsnowthrmcond2 * psnowrho(jj,jst) * psnowrho(jj,jst) ) + &
2263  max( 0.0, ( xsnowthrmcond_avap + &
2264  ( xsnowthrmcond_bvap/(psnowtemp(jj,jst) + xsnowthrmcond_cvap) ) ) &
2265  * (xp00/pps(jj)) )
2266  ENDIF
2267  !
2268  ! Snow thermal conductivity is set to be above 0.04 W m-1 K-1
2269  IF ( ocond_grain ) THEN
2270  pscond(jj,jst) = max( 0.04, pscond(jj,jst) )
2271  ! Snow thermal conductivity is annihilated in presence of liquid water
2272  IF( psnowliq(jj,jst)>xuepsi ) pscond(jj,jst) = 0.01 * pscond(jj,jst)
2273  ENDIF
2274  !
2275  ENDDO ! end loop JST
2276  !
2277 ENDDO ! end loop JST
2278 !
2279 IF (lhook) CALL dr_hook('SNOWCROTHRM',1,zhook_handle)
2280 !
2281 END SUBROUTINE snowcrothrm
2282 !####################################################################
2283 !####################################################################
2284 !####################################################################
2285 SUBROUTINE snowcroebud(HSNOWRES, HIMPLICIT_WIND, &
2286  PPEW_A_COEF, PPEW_B_COEF, &
2287  PPET_A_COEF, PPEQ_A_COEF, PPET_B_COEF, PPEQ_B_COEF, &
2288  PSNOWDZMIN, &
2289  PZREF,PTS,PSNOWRHO,PSNOWLIQ,PSCAP,PSCOND1,PSCOND2, &
2290  PUREF,PEXNS,PEXNA,PDIRCOSZW,PVMOD, &
2291  PLW_RAD,PSW_RAD,PTA,PQA,PPS,PTSTEP, &
2292  PSNOWDZ1,PSNOWDZ2,PALBT,PZ0,PZ0EFF,PZ0H, &
2293  PSFCFRZ,PRADSINK,PHPSNOW, &
2294  PCT,PEMIST,PRHOA,PTSTERM1,PTSTERM2,PRA,PCDSNOW,PCHSNOW, &
2295  PQSAT,PDQSAT,PRSRA,PUSTAR2_IC, PRI, &
2296  PPET_A_COEF_T,PPEQ_A_COEF_T,PPET_B_COEF_T,PPEQ_B_COEF_T )
2297 !
2298 !! PURPOSE
2299 !! -------
2300 ! Calculate surface energy budget linearization (terms) and turbulent
2301 ! exchange coefficients/resistance between surface and atmosphere.
2302 ! (Noilhan and Planton 1989; Giordani 1993; Noilhan and Mahfouf 1996)
2303 !
2304 !! MODIFICATIONS
2305 !! -------------
2306 !! Original A. Boone
2307 !! Modified by E. Brun (24/09/2012) :
2308 !! * Correction coupling coefficient for specific humidity in SNOWCROEBUD
2309 !! * PSFCFRZ(:) = 1.0 for systematic solid/vapor latent fluxes in SNOWCROEBUD
2310 !! Modified by B. Decharme 09/12 new wind implicitation
2311 !
2312 USE modd_surf_par, ONLY : xundef
2313 USE modd_csts, ONLY : xcpd, xrholw, xstefan, xlvtt, xlstt, xrholw
2314 USE modd_snow_par, ONLY : x_ri_max, xemissn
2315 !
2316 USE mode_thermos
2317 !
2318 USE modi_surface_ri
2319 USE modi_surface_aero_cond
2320 USE modi_surface_cd
2321 !
2322 IMPLICIT NONE
2323 !
2324 !* 0.1 declarations of arguments
2325 !
2326 REAL, INTENT(IN) :: PTSTEP, PSNOWDZMIN
2327 !
2328  CHARACTER(LEN=*), INTENT(IN) :: HSNOWRES ! type of sfc resistance
2329 ! DEFAULT=Louis (1979), standard ISBA
2330 ! method. Option to limit Ri number
2331 ! for very stable conditions
2332 !
2333  CHARACTER(LEN=*), INTENT(IN) :: HIMPLICIT_WIND ! wind implicitation option
2334 ! ! 'OLD' = direct
2335 ! ! 'NEW' = Taylor serie, order 1
2336 !
2337 REAL, DIMENSION(:), INTENT(IN) :: PPEW_A_COEF, PPEW_B_COEF, &
2338  PPET_A_COEF, PPEQ_A_COEF, PPET_B_COEF, &
2339  PPEQ_B_COEF
2340 ! PPEW_A_COEF = wind coefficient (m2s/kg)
2341 ! PPEW_B_COEF = wind coefficient (m/s)
2342 ! PPET_A_COEF = A-air temperature coefficient
2343 ! PPET_B_COEF = B-air temperature coefficient
2344 ! PPEQ_A_COEF = A-air specific humidity coefficient
2345 ! PPEQ_B_COEF = B-air specific humidity coefficient
2346 !
2347 REAL, DIMENSION(:), INTENT(IN) :: PZREF, PTS, PSNOWDZ1, PSNOWDZ2, &
2348  PRADSINK, PSNOWRHO, PSNOWLIQ, PSCAP, &
2349  PSCOND1, PSCOND2, &
2350  PZ0, PHPSNOW, &
2351  PALBT, PZ0EFF, PZ0H
2352 !
2353 REAL, DIMENSION(:), INTENT(IN) :: PSW_RAD, PLW_RAD, PTA, PQA, PPS, PRHOA
2354 !
2355 REAL, DIMENSION(:), INTENT(IN) :: PUREF, PEXNS, PEXNA, PDIRCOSZW, PVMOD
2356 !
2357 REAL, DIMENSION(:), INTENT(OUT) :: PTSTERM1, PTSTERM2, PEMIST, PRA, &
2358  PCT, PSFCFRZ, PCDSNOW, PCHSNOW, &
2359  PQSAT, PDQSAT, PRSRA
2360 !
2361 REAL, DIMENSION(:), INTENT(OUT) :: PUSTAR2_IC, &
2362  PPET_A_COEF_T, PPEQ_A_COEF_T, &
2363  PPET_B_COEF_T, PPEQ_B_COEF_T
2364 !
2365 REAL, DIMENSION(:), INTENT(OUT) :: PRI
2366 !
2367 !* 0.2 declarations of local variables
2368 !
2369 REAL, DIMENSION(SIZE(PTS)) :: ZAC, ZRI, &
2370  ZSCONDA, ZA, ZB, ZC, &
2371  ZCDN, ZSNOWDZM1, ZSNOWDZM2, &
2372  ZVMOD, ZUSTAR2, ZTS3, ZLVT, &
2373  Z_CCOEF
2374 REAL, DIMENSION(SIZE(PTS)) :: ZSNOWEVAPX, ZDENOM, ZNUMER
2375 !
2376 INTEGER :: JJ ! looping indexes
2377 !
2378 REAL(KIND=JPRB) :: ZHOOK_HANDLE
2379 !-------------------------------------------------------------------------------
2380 !
2381 ! 1. New saturated specific humidity and derrivative:
2382 ! ---------------------------------------------------
2383 !
2384 IF (lhook) CALL dr_hook('SNOWCROEBUD',0,zhook_handle)
2385 !
2386 zri(:) = xundef
2387 !
2388 pqsat(:) = qsati(pts(:),pps(:))
2389 pdqsat(:) = dqsati(pts(:),pps(:),pqsat(:))
2390 !
2391 ! 2. Surface properties:
2392 ! ----------------------
2393 ! It might be of interest to use snow-specific roughness
2394 ! or a temperature dependence on emissivity:
2395 ! but for now, use ISBA defaults.
2396 !
2397 pemist(:) = xemissn
2398 !
2399 ! 2. Computation of resistance and drag coefficient
2400 ! -------------------------------------------------
2401 !
2402  CALL surface_ri(pts, pqsat, pexns, pexna, pta, pqa, &
2403  pzref, puref, pdircoszw, pvmod, zri )
2404 !
2405 ! Simple adaptation of method by Martin and Lejeune (1998)
2406 ! to apply a lower limit to turbulent transfer coef
2407 ! by defining a maximum Richarson number for stable
2408 ! conditions:
2409 !
2410 IF ( hsnowres=='RIL' ) THEN
2411  DO jj=1,SIZE(zri)
2412  zri(jj) = min( x_ri_max, zri(jj) )
2413  ENDDO
2414 ENDIF
2415 !
2416 pri(:) = zri(:)
2417 !
2418 ! Surface aerodynamic resistance for heat transfers
2419 !
2420  CALL surface_aero_cond(zri, pzref, puref, pvmod, pz0, pz0h, zac, pra, pchsnow)
2421 !
2422 prsra(:) = prhoa(:) / pra(:)
2423 !
2424 ! For atmospheric model coupling:
2425 !
2426  CALL surface_cd(zri, pzref, puref, pz0eff, pz0h, pcdsnow, zcdn)
2427 !
2428 !
2429 ! Modify flux-form implicit coupling coefficients:
2430 ! - wind components:
2431 !
2432 znumer(:) = pcdsnow(:)*pvmod(:)
2433 zdenom(:) = prhoa(:) * pcdsnow(:) * pvmod(:) * ppew_a_coef(:)
2434 IF(himplicit_wind=='OLD')THEN
2435 ! old implicitation
2436  zustar2(:) = ( znumer(:) * ppew_b_coef(:) ) / ( 1.0 - zdenom(:) )
2437 ELSE
2438 ! new implicitation
2439  zustar2(:) = ( znumer(:) * ( 2.*ppew_b_coef(:) - pvmod(:) ) ) / ( 1.0 - 2.0*zdenom(:) )
2440 ENDIF
2441 !
2442 zvmod(:) = prhoa(:)*ppew_a_coef(:)*zustar2(:) + ppew_b_coef(:)
2443 zvmod(:) = max( zvmod(:),0. )
2444 !
2445 WHERE ( ppew_a_coef(:)/= 0. )
2446  zustar2(:) = max( ( zvmod(:) - ppew_b_coef(:) ) / (prhoa(:)*ppew_a_coef(:)), 0. )
2447 ENDWHERE
2448 !
2449 ! implicit wind friction
2450 zustar2(:) = max( zustar2(:),0. )
2451 !
2452 pustar2_ic(:) = zustar2(:)
2453 !
2454 ! 3. Calculate linearized surface energy budget components:
2455 ! ---------------------------------------------------------
2456 ! To prevent numerical difficulties for very thin snow
2457 ! layers, limit the grid "thinness": this is important as
2458 ! layers become vanishing thin:
2459 !
2460 zsnowdzm1(:) = max( psnowdz1(:), psnowdzmin )
2461 zsnowdzm2(:) = max( psnowdz2(:), psnowdzmin )
2462 !
2463 ! Surface thermal inertia:
2464 !
2465 pct(:) = 1.0 / ( pscap(:)*zsnowdzm1(:) )
2466 !
2467 ! Fraction of surface frozen (sublimation) with the remaining
2468 ! fraction being liquid (evaporation):
2469 !
2470 psfcfrz(:) = 1.0
2471 !
2472 ! Thermal conductivity between uppermost and lower snow layers:
2473 !
2474 zsconda(:) = ( zsnowdzm1(:)*pscond1(:) + zsnowdzm2(:)*pscond2(:) ) / &
2475  ( zsnowdzm1(:) + zsnowdzm2(:) )
2476 !
2477 ! Transform implicit coupling coefficients:
2478 ! Note, surface humidity is 100% over snow.
2479 !
2480 ! - specific humidity:
2481 !
2482 z_ccoef(:) = 1.0 - ppeq_a_coef(:) * prsra(:)
2483 !
2484 ppeq_a_coef_t(:) = - ppeq_a_coef(:) * prsra(:) * pdqsat(:) / z_ccoef(:)
2485 !
2486 ppeq_b_coef_t(:) = ( ppeq_b_coef(:) &
2487  - ppeq_a_coef(:) * prsra(:) * (pqsat(:) - pdqsat(:)*pts(:)) ) / z_ccoef(:)
2488 !
2489 ! - air temperature:
2490 ! (assumes A and B correspond to potential T):
2491 !
2492 z_ccoef(:) = ( 1.0 - ppet_a_coef(:) * prsra(:) ) / pexna(:)
2493 !
2494 ppet_a_coef_t(:) = - ppet_a_coef(:) * prsra(:) / ( pexns(:) * z_ccoef(:) )
2495 !
2496 ppet_b_coef_t(:) = ppet_b_coef(:) / z_ccoef(:)
2497 !
2498 !
2499 ! Energy budget solution terms:
2500 !
2501 zts3(:) = pemist(:) * xstefan * pts(:)**3
2502 zlvt(:) = (1.-psfcfrz(:))*xlvtt + psfcfrz(:)*xlstt
2503 !
2504 za(:) = 1./ptstep + pct(:) * &
2505  ( 4. * zts3(:) + prsra(:) * zlvt(:) * ( pdqsat(:) - ppeq_a_coef_t(:) ) &
2506  + prsra(:) * xcpd * ( (1./pexns(:))-(ppet_a_coef_t(:)/pexna(:)) ) &
2507  + ( 2*zsconda(:) / ( zsnowdzm2(:)+zsnowdzm1(:) ) ) )
2508 !
2509 zb(:) = 1./ptstep + pct(:) * &
2510  ( 3. * zts3(:) + prsra(:) * zlvt(:) * pdqsat(:) )
2511 !
2512 zc(:) = pct(:) * ( - prsra(:) * zlvt(:) * ( pqsat(:) - ppeq_b_coef_t(:) ) &
2513  + prsra(:) * xcpd * ppet_b_coef_t(:) / pexna(:) &
2514  + psw_rad(:) * (1. - palbt(:)) + pemist(:) * plw_rad(:) &
2515  + phpsnow(:) + pradsink(:) )
2516 !
2517 !
2518 ! Coefficients needed for implicit solution
2519 ! of linearized surface energy budget:
2520 !
2521 ptsterm2(:) = 2. * zsconda(:) * pct(:) / ( za(:) * (zsnowdzm2(:)+zsnowdzm1(:) ) )
2522 !
2523 ptsterm1(:) = ( pts(:)*zb(:) + zc(:) ) / za(:)
2524 !
2525 IF (lhook) CALL dr_hook('SNOWCROEBUD',1,zhook_handle)
2526 !
2527 END SUBROUTINE snowcroebud
2528 !####################################################################
2529 !####################################################################
2530 !####################################################################
2531 SUBROUTINE snowcrosolvt(PTSTEP,PSNOWDZMIN, &
2532  PSNOWDZ,PSCOND,PSCAP,PTG, &
2533  PSOILCOND,PD_G, &
2534  PRADSINK,PCT,PTERM1,PTERM2, &
2535  PPET_A_COEF_T,PPEQ_A_COEF_T, &
2536  PPET_B_COEF_T,PPEQ_B_COEF_T, &
2537  PTA_IC, PQA_IC, &
2538  PGBAS,PSNOWTEMP,PSNOWFLUX, &
2539  KNLVLS_USE )
2541 !! PURPOSE
2542 !! -------
2543 ! This subroutine solves the 1-d diffusion of 'ZSNOWTEMP' using a
2544 ! layer averaged set of equations which are time differenced
2545 ! using the backward-difference scheme (implicit).
2546 ! The eqs are solved rapidly by taking advantage of the
2547 ! fact that the matrix is tridiagonal. This is a very
2548 ! general routine and can be used for the 1-d diffusion of any
2549 ! quantity as long as the diffusity is not a function of the
2550 ! quantity being diffused. Aaron Boone 8-98. Soln to the eq:
2551 !
2552 ! c dQ d k dQ dS
2553 ! -- = -- -- - --
2554 ! dt dx dx dx
2555 !
2556 ! where k = k(x) (thermal conductivity), c = c(x) (heat capacity)
2557 ! as an eg. for temperature/heat eq. S is a sink (-source) term.
2558 ! Diffusivity is k/c
2559 !
2560 !! MODIFICATIONS
2561 !! -------------
2562 !! Original A. Boone
2563 !! 05/2011: Brun Special treatment to tackle the variable number
2564 !! of snow layers
2565 !
2566 USE modd_csts, ONLY : xtt
2567 !
2569 !
2570 IMPLICIT NONE
2571 !
2572 !* 0.1 declarations of arguments
2573 !
2574 REAL, INTENT(IN) :: PTSTEP, PSNOWDZMIN
2575 !
2576 REAL, DIMENSION(:), INTENT(IN) :: PTG, PSOILCOND, PD_G, &
2577  PCT, PTERM1, PTERM2
2578 
2579 !
2580 REAL, DIMENSION(:,:), INTENT(IN) :: PSNOWDZ, PSCOND, PSCAP, &
2581  PRADSINK
2582 !
2583 REAL, DIMENSION(:), INTENT(IN) :: PPET_A_COEF_T, PPEQ_A_COEF_T, &
2584  PPET_B_COEF_T, PPEQ_B_COEF_T
2585 !
2586 REAL, DIMENSION(:,:), INTENT(INOUT) :: PSNOWTEMP
2587 !
2588 REAL, DIMENSION(:), INTENT(OUT) :: PGBAS, PSNOWFLUX, PTA_IC, PQA_IC
2589 !
2590 INTEGER, DIMENSION(:), INTENT(IN) :: KNLVLS_USE
2591 !
2592 !* 0.2 declarations of local variables
2593 !
2594 REAL, DIMENSION(SIZE(PSNOWDZ,1),SIZE(PSNOWDZ,2)) :: ZSNOWTEMP, ZDTERM, ZCTERM, &
2595  ZFRCV, ZAMTRX, ZBMTRX, &
2596  ZCMTRX
2597 !
2598 REAL, DIMENSION(SIZE(PSNOWDZ,1),SIZE(PSNOWDZ,2)) :: ZWORK1, ZWORK2, ZDZDIF, &
2599  ZSNOWDZM
2600 !
2601 REAL, DIMENSION(SIZE(PSNOWDZ,1),SIZE(PSNOWDZ,2)-1) :: ZSNOWTEMP_M, &
2602  ZFRCV_M, ZAMTRX_M, &
2603  ZBMTRX_M, ZCMTRX_M
2604 !
2605 REAL, DIMENSION(SIZE(PTG)) :: ZGBAS, ZSNOWTEMP_DELTA
2606 !
2607 INTEGER :: JJ, JST ! looping indexes
2608 INTEGER :: INLVLS
2609 !
2610 REAL(KIND=JPRB) :: ZHOOK_HANDLE
2611 !-------------------------------------------------------------------------------
2612 IF (lhook) CALL dr_hook('SNOWCROSOLVT',0,zhook_handle)
2613 !
2614 ! 0. Initialize:
2615 ! ------------------
2616 !
2617 zsnowtemp(:,:) = psnowtemp(:,:)
2618 inlvls = SIZE(psnowdz(:,:),2)
2619 !
2620 ! 1. Calculate tri-diagnoal matrix coefficients:
2621 ! ----------------------------------------------
2622 ! For heat transfer, assume a minimum grid
2623 ! thickness (to prevent numerical
2624 ! problems for very thin snow cover):
2625 !
2626 DO jj=1,SIZE(ptg)
2627  !
2628  DO jst = knlvls_use(jj),1,-1
2629  !
2630  zsnowdzm(jj,jst) = max( psnowdz(jj,jst), psnowdzmin )
2631  !
2632  zwork1(jj,jst) = zsnowdzm(jj,jst) * pscond(jj,jst)
2633  !
2634  IF ( jst<knlvls_use(jj) ) THEN
2635  !
2636  zdzdif(jj,jst) = zsnowdzm(jj,jst) + zsnowdzm(jj,jst+1)
2637  !
2638  zwork2(jj,jst) = zsnowdzm(jj,jst+1) * pscond(jj,jst+1)
2639  !
2640  ELSE
2641  !
2642  zdzdif(jj,jst) = zsnowdzm(jj,jst) + pd_g(jj)
2643  !
2644  zwork2(jj,jst) = pd_g(jj) * psoilcond(jj)
2645  !
2646  ENDIF
2647  !
2648  zdterm(jj,jst) = 2.0 * ( zwork1(jj,jst) + zwork2(jj,jst) ) / zdzdif(jj,jst)**2
2649  !
2650  zcterm(jj,jst) = pscap(jj,jst) * zsnowdzm(jj,jst) / ptstep
2651  !
2652  ENDDO
2653  !
2654 ENDDO
2655 !
2656 ! 2. Set up tri-diagonal matrix
2657 ! -----------------------------
2658 !
2659 zamtrx(:,:) = 0.
2660 zbmtrx(:,:) = 0.
2661 zcmtrx(:,:) = 0.
2662 zfrcv(:,:) = 0.
2663 ! Upper BC
2664 !
2665 zamtrx(:,1) = 0.0
2666 zbmtrx(:,1) = 1. / ( pct(:)*ptstep )
2667 zcmtrx(:,1) = - pterm2(:) * zbmtrx(:,1)
2668 zfrcv(:,1) = pterm1(:) * zbmtrx(:,1)
2669 !
2670 DO jj = 1,SIZE(ptg)
2671  !
2672  DO jst = 2,knlvls_use(jj)
2673  !
2674  ! Interior Grid & Lower BC
2675  zamtrx(jj,jst) = -zdterm(jj,jst-1)
2676  zbmtrx(jj,jst) = zcterm(jj,jst) + zdterm(jj,jst-1) + zdterm(jj,jst)
2677  zfrcv(jj,jst) = zcterm(jj,jst)*psnowtemp(jj,jst) - (pradsink(jj,jst-1)-pradsink(jj,jst))
2678  !
2679  IF ( jst<knlvls_use(jj) ) THEN
2680  zcmtrx(jj,jst) = -zdterm(jj,jst)
2681  ELSE
2682  zcmtrx(jj,jst) = 0.0
2683  zfrcv(jj,jst) = zfrcv(jj,jst) + zdterm(jj,jst)*ptg(jj)
2684  ENDIF
2685  !
2686  ENDDO
2687  !
2688 ENDDO
2689 !
2690 ! 4. Compute solution vector
2691 ! --------------------------
2692 !
2693  CALL tridiag_ground_snowcro(zamtrx,zbmtrx,zcmtrx,zfrcv,zsnowtemp,knlvls_use,0)
2694 !
2695 ! Heat flux between surface and 2nd snow layers: (W/m2)
2696 !
2697 psnowflux(:) = zdterm(:,1) * ( zsnowtemp(:,1) - zsnowtemp(:,2) )
2698 !
2699 ! 5. Snow melt case
2700 ! -----------------
2701 ! If melting in uppermost layer, assume surface layer
2702 ! temperature at freezing point and re-evaluate lower
2703 ! snowpack temperatures. This is done as it is most likely
2704 ! most signigant melting will occur within a time step in surface layer.
2705 ! Surface energy budget (and fluxes) will
2706 ! be re-calculated (outside of this routine):
2707 !
2708 zamtrx_m(:,1) = 0.0
2709 zbmtrx_m(:,1) = zcterm(:,2) + zdterm(:,1) + zdterm(:,2)
2710 zcmtrx_m(:,1) = -zdterm(:,2)
2711 zfrcv_m(:,1) = zcterm(:,2)*psnowtemp(:,2) - (pradsink(:,1)-pradsink(:,2)) + zdterm(:,1)*xtt
2712 !
2713 DO jj = 1,SIZE(ptg)
2714  DO jst = 2,knlvls_use(jj)-1
2715  zamtrx_m(jj,jst) = zamtrx(jj,jst+1)
2716  zbmtrx_m(jj,jst) = zbmtrx(jj,jst+1)
2717  zcmtrx_m(jj,jst) = zcmtrx(jj,jst+1)
2718  zfrcv_m(jj,jst) = zfrcv(jj,jst+1)
2719  zsnowtemp_m(jj,jst) = psnowtemp(jj,jst+1)
2720  ENDDO
2721 ENDDO
2722 !
2723  CALL tridiag_ground_snowcro(zamtrx_m,zbmtrx_m,zcmtrx_m,zfrcv_m,zsnowtemp_m,knlvls_use,1)
2724 !
2725 ! If melting for 2 consecuative time steps, then replace current T-profile
2726 ! with one assuming T=Tf in surface layer:
2727 !
2728 zsnowtemp_delta(:) = 0.0
2729 !
2730 WHERE( zsnowtemp(:,1)>xtt .AND. psnowtemp(:,1)>=xtt )
2731  psnowflux(:) = zdterm(:,1) * ( xtt-zsnowtemp_m(:,1) )
2732  zsnowtemp_delta(:) = 1.0
2733 END WHERE
2734 !
2735 DO jj = 1,SIZE(ptg)
2736  DO jst = 2,knlvls_use(jj)
2737  zsnowtemp(jj,jst) = zsnowtemp_delta(jj) * zsnowtemp_m(jj,jst-1) + &
2738  (1.0-zsnowtemp_delta(jj)) * zsnowtemp(jj,jst)
2739  ENDDO
2740 ENDDO
2741 !
2742 ! 6. Lower boundary flux:
2743 ! -----------------------
2744 ! NOTE: evaluate this term assuming the snow layer
2745 ! can't exceed the freezing point as this adjustment
2746 ! is made in melting routine. Then must adjust temperature
2747 ! to conserve energy:
2748 !
2749 DO jj=1, SIZE(ptg)
2750  zgbas(jj) = zdterm(jj,knlvls_use(jj)) * ( zsnowtemp(jj,knlvls_use(jj)) - ptg(jj) )
2751  pgbas(jj) = zdterm(jj,knlvls_use(jj)) * ( min( xtt, zsnowtemp(jj,knlvls_use(jj)) ) - ptg(jj) )
2752  zsnowtemp(jj,knlvls_use(jj)) = zsnowtemp(jj,knlvls_use(jj)) + &
2753  ( zgbas(jj)-pgbas(jj) ) / zcterm(jj,knlvls_use(jj))
2754 ENDDO
2755 !
2756 ! 7. Update temperatute profile in time:
2757 ! --------------------------------------
2758 !
2759 DO jj=1, SIZE(ptg)
2760  psnowtemp(jj,1:knlvls_use(jj)) = zsnowtemp(jj,1:knlvls_use(jj))
2761 ENDDO
2762 !
2763 !
2764 ! 8. Compute new (implicit) air T and specific humidity
2765 ! -----------------------------------------------------
2766 !
2767 pta_ic(:) = ppet_b_coef_t(:) + ppet_a_coef_t(:) * psnowtemp(:,1)
2768 !
2769 pqa_ic(:) = ppeq_b_coef_t(:) + ppeq_a_coef_t(:) * psnowtemp(:,1)
2770 !
2771 IF (lhook) CALL dr_hook('SNOWCROSOLVT',1,zhook_handle)
2772 !
2773 END SUBROUTINE snowcrosolvt
2774 !####################################################################
2775 !####################################################################
2776 !####################################################################
2777 SUBROUTINE snowcromelt(PSCAP,PSNOWTEMP,PSNOWDZ, &
2778  PSNOWRHO,PSNOWLIQ,KNLVLS_USE )
2780 !! PURPOSE
2781 !! -------
2782 ! Calculate snow melt (resulting from surface fluxes, ground fluxes,
2783 ! or internal shortwave radiation absorbtion). It is used to
2784 ! augment liquid water content, maintain temperatures
2785 ! at or below freezing, and possibly reduce the mass
2786 ! or compact the layer(s).
2787 !
2788 USE modd_csts,ONLY : xtt, xlmtt, xrholw, xrholi
2789 !
2790 USE mode_snow3l
2791 !
2792 IMPLICIT NONE
2793 !
2794 !* 0.1 declarations of arguments
2795 !
2796 REAL, DIMENSION(:,:), INTENT(IN) :: PSCAP
2797 !
2798 REAL, DIMENSION(:,:), INTENT(INOUT) :: PSNOWDZ, PSNOWTEMP, PSNOWRHO, &
2799  PSNOWLIQ
2800 !
2801 INTEGER, DIMENSION(:), INTENT(IN) :: KNLVLS_USE
2802 !
2803 !* 0.2 declarations of local variables
2804 !
2805 REAL, DIMENSION(SIZE(PSNOWRHO,1),SIZE(PSNOWRHO,2)) :: ZPHASE, ZCMPRSFACT, &
2806  ZSNOWLWE, &
2807  ZSNOWMELT, ZSNOWTEMP
2808 !
2809 INTEGER :: JJ, JST ! looping indexes
2810 !
2811 REAL(KIND=JPRB) :: ZHOOK_HANDLE
2812 !-------------------------------------------------------------------------------
2813 IF (lhook) CALL dr_hook('SNOWCROMELT',0,zhook_handle)
2814 !
2815 ! 0. Initialize:
2816 ! ---------------------------
2817 !
2818 DO jj = 1,SIZE(psnowdz,1)
2819  DO jst = 1,knlvls_use(jj)
2820  zphase (jj,jst) = 0.0
2821  zcmprsfact(jj,jst) = 0.0
2822  zsnowlwe (jj,jst) = 0.0
2823  zsnowmelt (jj,jst) = 0.0
2824  zsnowtemp (jj,jst) = 0.0
2825  ENDDO
2826 ENDDO
2827 !
2828 ! 1. Determine amount of melt in each layer:
2829 ! ------------------------------------------
2830 !
2831 DO jj = 1,SIZE(psnowdz,1)
2832  !
2833  DO jst = 1,knlvls_use(jj)
2834  !
2835  ! total liquid equivalent water content of snow(m):
2836  zsnowlwe(jj,jst) = psnowrho(jj,jst) * psnowdz(jj,jst) / xrholw
2837  !
2838  ! melt snow if excess energy and snow available:
2839  ! phase change(j/m2)
2840  zphase(jj,jst) = min( pscap(jj,jst) * max(0.0,psnowtemp(jj,jst)-xtt) * psnowdz(jj,jst), &
2841  max(0.0,zsnowlwe(jj,jst)-psnowliq(jj,jst)) * xlmtt * xrholw )
2842  !
2843  ! update snow liq water content and temperature if melting:
2844  ! liquid water available for next layer from melting of snow
2845  ! which is assumed to be leaving the current layer(m):
2846  zsnowmelt(jj,jst) = zphase(jj,jst) / (xlmtt*xrholw)
2847  !
2848  ! cool off snow layer temperature due to melt:
2849  zsnowtemp(jj,jst) = psnowtemp(jj,jst) - zphase(jj,jst) / (pscap(jj,jst)*psnowdz(jj,jst))
2850  !
2851  ! difference with isba_es: zmeltxs should never be different of 0.
2852  ! because of the introduction of the tests in llayergone
2853  psnowtemp(jj,jst) = zsnowtemp(jj,jst)
2854  !
2855  ! the control below should be suppressed after further tests
2856  IF (psnowtemp(jj,jst)-xtt > xuepsi) THEN
2857  WRITE(*,*) 'pb dans MELT PSNOWTEMP(JJ,JST) >XTT:', jj,jst, psnowtemp(jj,jst)
2858  CALL abor1_sfx('SNOWCRO: pb dans MELT')
2859  ENDIF
2860  !
2861  ! Loss of snowpack depth: (m) and liquid equiv (m):
2862  ! Compression factor for melt loss: this decreases
2863  ! layer thickness and increases density thereby leaving
2864  ! total SWE constant.
2865  !
2866  ! Difference with ISBA_ES: All melt is considered to decrease the depth
2867  ! without consideration to the irreducible content
2868  !
2869  zcmprsfact(jj,jst) = ( zsnowlwe(jj,jst) - (psnowliq(jj,jst)+zsnowmelt(jj,jst)) ) &
2870  / ( zsnowlwe(jj,jst) - psnowliq(jj,jst) )
2871  psnowdz(jj,jst) = psnowdz(jj,jst) * zcmprsfact(jj,jst)
2872  psnowrho(jj,jst) = zsnowlwe(jj,jst) * xrholw / psnowdz(jj,jst)
2873  !
2874  ! 2. Add snow melt to current snow liquid water content:
2875  ! ------------------------------------------------------
2876  !
2877  psnowliq(jj,jst) = psnowliq(jj,jst) + zsnowmelt(jj,jst)
2878  !
2879  ENDDO ! loop JST active snow layers
2880 ENDDO ! loop JJ grid points
2881 !
2882 IF (lhook) CALL dr_hook('SNOWCROMELT',1,zhook_handle)
2883 !
2884 END SUBROUTINE snowcromelt
2885 !####################################################################
2886 !####################################################################
2887 !####################################################################
2888 SUBROUTINE snowcrorefrz(PTSTEP,PRR, &
2889  PSNOWRHO,PSNOWTEMP,PSNOWDZ,PSNOWLIQ, &
2890  PTHRUFAL, PSCAP, PLEL3L,KNLVLS_USE )
2892 !! PURPOSE
2893 !! -------
2894 ! Calculate any freezing/refreezing of liquid water in the snowpack.
2895 ! Also, calculate liquid water transmission and snow runoff.
2896 ! Refreezing causes densification of a layer.
2897 !
2898 USE modd_csts, ONLY : xtt, xlmtt, xrholw, xci,xrholi
2899 USE modd_snow_par, ONLY : xsnowdmin
2900 !
2901 USE mode_snow3l
2902 !
2903 IMPLICIT NONE
2904 !
2905 !* 0.1 declarations of arguments
2906 !
2907 REAL, INTENT(IN) :: PTSTEP
2908 !
2909 REAL, DIMENSION(:), INTENT(IN) :: PRR
2910 !
2911 REAL, DIMENSION(:,:), INTENT(INOUT) :: PSNOWDZ, PSNOWTEMP, PSNOWLIQ, PSNOWRHO
2912 !
2913 REAL, DIMENSION(:), INTENT(INOUT) :: PTHRUFAL
2914 !
2915 ! modifs_EB layers
2916 INTEGER, DIMENSION(:), INTENT(IN) :: KNLVLS_USE
2917 REAL, DIMENSION(:,:), INTENT(IN) :: PSCAP
2918 REAL, DIMENSION(:), INTENT(IN) :: PLEL3L
2919 !
2920 !* 0.2 declarations of local variables
2921 !
2922 REAL, DIMENSION(SIZE(PSNOWRHO,1),SIZE(PSNOWRHO,2)) :: ZPHASE, &
2923  ZSNOWLIQ, ZSNOWRHO, &
2924  ZWHOLDMAX, ZSNOWDZ, &
2925  ZSNOWTEMP
2926 !
2927 REAL, DIMENSION(SIZE(PSNOWRHO,1),0:SIZE(PSNOWRHO,2)) :: ZFLOWLIQ
2928 !
2929 REAL :: ZDENOM, ZNUMER
2930 !
2931 INTEGER :: JJ, JST ! looping indexes
2932 INTEGER :: INLVLS ! maximum snow layers number
2933 !
2934 REAL(KIND=JPRB) :: ZHOOK_HANDLE
2935 !
2936 !-------------------------------------------------------------------------------
2937 IF (lhook) CALL dr_hook('SNOWCROREFRZ',0,zhook_handle)
2938 !
2939 ! 0. Initialize:
2940 ! --------------
2941 !
2942 inlvls = SIZE(psnowdz,2)
2943 !
2944 DO jj=1,SIZE(psnowdz,1)
2945  DO jst=1,knlvls_use(jj)
2946  zsnowrho(jj,jst) = psnowrho(jj,jst)
2947  zsnowtemp(jj,jst) = psnowtemp(jj,jst)
2948  zwholdmax(jj,jst) = xpercentagepore/xrholi * (psnowdz(jj,jst) * &
2949  (xrholi-psnowrho(jj,jst)) + psnowliq(jj,jst)*xrholw)
2950  ENDDO
2951 ENDDO
2952 !
2953 DO jj = 1,SIZE(psnowdz,1) ! loop JJ grid points
2954  !
2955  ! 1. Increases Liquid Water of top layer from rain
2956  ! ---------------------------------------------
2957  !
2958  ! Rainfall (m) initialises the liquid flow whih feeds the top layer
2959  ! and evaporation/condensation are taken into account
2960  !
2961  IF ( knlvls_use(jj)>0. ) THEN
2962  zflowliq(jj,0) = prr(jj) * ptstep / xrholw
2963  zflowliq(jj,0) = max(0., zflowliq(jj,0) - plel3l(jj)*ptstep/(xlvtt*xrholw))
2964  ELSE
2965  zflowliq(jj,0) = 0
2966  ENDIF
2967  !
2968  DO jst=1,knlvls_use(jj) ! loop JST active snow layers
2969  !
2970  ! 2. Increases Liquid Water from the upper layers flow (or rain for top layer)
2971  ! -----------------------------
2972  psnowliq(jj,jst) = psnowliq(jj,jst) + zflowliq(jj,jst-1)
2973  !
2974  ! 3. Freezes liquid water in any cold layers
2975  ! ---------------------------------------
2976  !
2977  ! Calculate the maximum possible refreezing
2978  zphase(jj,jst) = min( pscap(jj,jst)* max(0.0, xtt - zsnowtemp(jj,jst)) * psnowdz(jj,jst), &
2979  psnowliq(jj,jst) * xlmtt * xrholw )
2980  !
2981  ! Reduce liquid content if freezing occurs:
2982  zsnowliq(jj,jst) = psnowliq(jj,jst) - zphase(jj,jst)/(xlmtt*xrholw)
2983  !
2984  ! Warm layer and reduce liquid if freezing occurs:
2985  zsnowdz(jj,jst) = max(xsnowdmin/inlvls, psnowdz(jj,jst))
2986  !
2987  !
2988  ! Difference with ISBA-ES: a possible cooling of current refreezing water
2989  ! is taken into account to calculate temperature change
2990  znumer = ( zsnowrho(jj,jst) * zsnowdz(jj,jst) - ( psnowliq(jj,jst) - zflowliq(jj,jst-1) ) * xrholw )
2991  zdenom = ( zsnowrho(jj,jst) * zsnowdz(jj,jst) - ( zsnowliq(jj,jst) - zflowliq(jj,jst-1) ) * xrholw )
2992  !
2993  psnowtemp(jj,jst) = xtt + ( zsnowtemp(jj,jst)-xtt )*znumer/zdenom + zphase(jj,jst)/( xci*zdenom )
2994  !
2995  ! 4. Calculate flow from the excess of holding capacity
2996  ! --------------------------------------------------------------
2997  !
2998  ! Any water in excess of the maximum holding space for liquid water
2999  ! amount is drained into next layer down.
3000  zflowliq(jj,jst) = max( 0., zsnowliq(jj,jst)-zwholdmax(jj,jst) )
3001  !
3002  zsnowliq(jj,jst) = zsnowliq(jj,jst) - zflowliq(jj,jst)
3003  !
3004  ! 5. Density is adjusted to conserve the mass
3005  ! --------------------------------------------------------------
3006  znumer = ( zsnowrho(jj,jst) * psnowdz(jj,jst) - ( zflowliq(jj,jst) - zflowliq(jj,jst-1) ) * xrholw )
3007  !
3008  zsnowrho(jj,jst) = znumer / zsnowdz(jj,jst)
3009  !
3010  ! keeps snow denisty below ice density
3011  IF ( zsnowrho(jj,jst)>xrholi ) THEN
3012  psnowdz(jj,jst) = psnowdz(jj,jst) * zsnowrho(jj,jst) / xrholi
3013  zsnowrho(jj,jst) = xrholi
3014  ENDIF
3015  !
3016  ! 6. Update thickness and density and any freezing:
3017  ! ----------------------------------------------
3018  psnowrho(jj,jst) = zsnowrho(jj,jst)
3019  psnowliq(jj,jst) = zsnowliq(jj,jst)
3020  !
3021  ENDDO ! loop JST active snow layers
3022  !
3023  ! Any remaining throughflow after freezing is available to
3024  ! the soil for infiltration or surface runoff (m).
3025  ! I.E. This is the amount of water leaving the snowpack:
3026  ! Rate water leaves the snowpack [kg/(m2 s)]:
3027  !
3028  pthrufal(jj) = pthrufal(jj) + zflowliq(jj,knlvls_use(jj)) * xrholw / ptstep
3029  !
3030 ENDDO ! loop JJ grid points
3031 !
3032 IF (lhook) CALL dr_hook('SNOWCROREFRZ',1,zhook_handle)
3033 !
3034 END SUBROUTINE snowcrorefrz
3035 !####################################################################
3036 SUBROUTINE get_rho(PRHO_IN,PDZ,PSNOWLIQ,PFLOWLIQ,PRHO_OUT)
3038 USE modd_csts, ONLY : xrholw
3039 !
3040 IMPLICIT NONE
3041 !
3042 REAL, INTENT(IN) :: PRHO_IN, PDZ, PSNOWLIQ,PFLOWLIQ
3043 REAL, INTENT(OUT) :: PRHO_OUT
3044 !
3045 REAL(KIND=JPRB) :: ZHOOK_HANDLE
3046 !
3047 IF (lhook) CALL dr_hook('SNOWCRO:GET_RHO',0,zhook_handle)
3048 !
3049 prho_out = ( prho_in * pdz - ( psnowliq - pflowliq ) * xrholw )
3050 !
3051 IF (lhook) CALL dr_hook('SNOWCRO:GET_RHO',1,zhook_handle)
3052 !
3053 END SUBROUTINE get_rho
3054 !####################################################################
3055 !####################################################################
3056 SUBROUTINE snowcroflux(PSNOWTEMP,PSNOWDZ,PEXNS,PEXNA, &
3057  PUSTAR2_IC, &
3058  PTSTEP,PALBT,PSW_RAD,PEMIST,PLWUPSNOW, &
3059  PLW_RAD,PTA,PSFCFRZ,PQA,PHPSNOW, &
3060  PSNOWTEMPO1,PSNOWFLUX,PCT,PRADSINK, &
3061  PQSAT,PDQSAT,PRSRA, &
3062  PRN,PH,PGFLUX,PLES3L,PLEL3L,PEVAP, &
3063  PUSTAR )
3065 !! PURPOSE
3066 !! -------
3067 ! Calculate the surface fluxes (atmospheric/surface).
3068 ! (Noilhan and Planton 1989; Noilhan and Mahfouf 1996)
3069 !
3070 USE modd_csts,ONLY : xtt
3071 !
3072 USE mode_thermos
3073 !
3074 IMPLICIT NONE
3075 !
3076 !* 0.1 declarations of arguments
3077 !
3078 REAL, INTENT(IN) :: PTSTEP
3079 !
3080 REAL, DIMENSION(:), INTENT(IN) :: PSNOWDZ, PSNOWTEMPO1, PSNOWFLUX, PCT, &
3081  PRADSINK, PEXNS, PEXNA
3082 !
3083 REAL, DIMENSION(:), INTENT(IN) :: PALBT, PSW_RAD, PEMIST, PLW_RAD, &
3084  PTA, PSFCFRZ, PQA, &
3085  PHPSNOW, PQSAT, PDQSAT, PRSRA, &
3086  PUSTAR2_IC
3087 !
3088 REAL, DIMENSION(:), INTENT(INOUT) :: PSNOWTEMP
3089 !
3090 REAL, DIMENSION(:), INTENT(OUT) :: PRN, PH, PGFLUX, PLES3L, PLEL3L, &
3091  PEVAP, PLWUPSNOW, PUSTAR
3092 !
3093 !* 0.2 declarations of local variables
3094 !
3095 REAL, DIMENSION(SIZE(PSNOWDZ)) :: ZEVAPC, ZSNOWTEMP
3096 REAL :: ZSMSNOW, ZGFLUX
3097 !
3098 INTEGER :: JJ
3099 !
3100 REAL(KIND=JPRB) :: ZHOOK_HANDLE
3101 !-------------------------------------------------------------------------------
3102 IF (lhook) CALL dr_hook('SNOWCROFLUX',0,zhook_handle)
3103 !
3104 ! 0. Initialize:
3105 ! --------------
3106 !
3107 ! 1. Flux calculations when melt not occuring at surface (W/m2):
3108 ! --------------------------------------------------------------
3109 !
3110 DO jj = 1,SIZE(palbt)
3111  !
3112  CALL get_flux(palbt(jj),pemist(jj),psw_rad(jj),plw_rad(jj), &
3113  pexns(jj),pexna(jj),pta(jj),pqa(jj),prsra(jj), &
3114  pqsat(jj),pdqsat(jj),psfcfrz(jj),phpsnow(jj), &
3115  psnowtemp(jj),psnowtempo1(jj), &
3116  prn(jj),ph(jj),zevapc(jj), &
3117  ples3l(jj),plel3l(jj),zgflux )
3118  !
3119  IF ( psnowtemp(jj)>xtt ) THEN
3120  !
3121  IF ( psnowtempo1(jj)<xtt ) THEN
3122  !
3123  ! 2. Initial melt adjustment
3124  ! --------------------------
3125  ! If energy avalabile to melt snow, then recalculate fluxes
3126  ! at the freezing point and add residual heat to layer
3127  ! average heat.
3128  !
3129  ! A) If temperature change is > 0 and passes freezing point this timestep,
3130  ! then recalculate fluxes at freezing point and excess energy
3131  ! will be used outside of this routine to change snow heat content:
3132  !
3133  ! WRITE (*,*) 'attention test LFLUX traitement XTT supprime!'
3134  !
3135  CALL get_flux(palbt(jj),pemist(jj),psw_rad(jj),plw_rad(jj), &
3136  pexns(jj),pexna(jj), pta(jj),pqa(jj),prsra(jj), &
3137  pqsat(jj),pdqsat(jj),psfcfrz(jj),phpsnow(jj), &
3138  xtt,psnowtempo1(jj), &
3139  prn(jj),ph(jj),zevapc(jj), &
3140  ples3l(jj),plel3l(jj),pgflux(jj) )
3141  !
3142  zsmsnow = zgflux - pgflux(jj)
3143  !
3144  ! This will be used to change heat content of snow:
3145  zsnowtemp(jj) = psnowtemp(jj) - zsmsnow * ptstep * pct(jj)
3146  !
3147  ELSE
3148  !
3149  ! 3. Ongoing melt adjustment: explicit solution
3150  ! ---------------------------------------------
3151  ! If temperature change is 0 and at freezing point this timestep,
3152  ! then recalculate fluxes and surface temperature *explicitly*
3153  ! as this is *exact* for snow at freezing point (Brun, Martin)
3154  !
3155  CALL get_flux(palbt(jj),pemist(jj),psw_rad(jj),plw_rad(jj), &
3156  pexns(jj),pexna(jj), pta(jj),pqa(jj),prsra(jj), &
3157  pqsat(jj),pdqsat(jj),psfcfrz(jj),phpsnow(jj), &
3158  xtt,xtt, &
3159  prn(jj),ph(jj),zevapc(jj), &
3160  ples3l(jj),plel3l(jj),pgflux(jj) )
3161  !
3162  zsnowtemp(jj) = xtt + ptstep * pct(jj) * ( pgflux(jj) + pradsink(jj) - psnowflux(jj) )
3163  !
3164  ENDIF
3165  !
3166  ELSE
3167  !
3168  zsnowtemp(jj) = psnowtemp(jj)
3169  !
3170  pgflux(jj) = zgflux
3171  !
3172  ENDIF
3173  !
3174 ENDDO
3175 !
3176 ! 4. Update surface temperature:
3177 ! ------------------------------
3178 !
3179 psnowtemp(:) = zsnowtemp(:)
3180 !
3181 ! 5. Final evaporative flux (kg/m2/s)
3182 !
3183 pevap(:) = zevapc(:)
3184  !WRITE(*,*) 'Flux surface:',PGFLUX(1),PRN(1),PH(1), ZLE(1), PHPSNOW(1)
3185 !
3186 ! 5. Friction velocity
3187 ! --------------------
3188 !
3189 pustar(:) = sqrt(pustar2_ic(:))
3190 !
3191 IF (lhook) CALL dr_hook('SNOWCROFLUX',1,zhook_handle)
3192 !
3193 END SUBROUTINE snowcroflux
3194 !####################################################################
3195 SUBROUTINE get_flux(PALBT,PEMIST,PSW_RAD,PLW_RAD,PEXNS,PEXNA, &
3196  PTA,PQA,PRSRA,PQSAT,PDQSAT,PSFCFRZ,PHPSNOW, &
3197  PSNOWTEMP,PSNOWTEMPO1, &
3198  PRN,PH,PEVAPC,PLES3L,PLEL3L,PGFLUX )
3200 USE modd_csts,ONLY : xstefan, xcpd, xlstt, xlvtt
3201 !
3202 IMPLICIT NONE
3203 !
3204 REAL, INTENT(IN) :: PALBT, PEMIST
3205 REAL, INTENT(IN) :: PSW_RAD, PLW_RAD
3206 REAL, INTENT(IN) :: PEXNS, PEXNA
3207 REAL, INTENT(IN) :: PTA, PQA, PRSRA, PQSAT, PDQSAT, PSFCFRZ, PHPSNOW
3208 REAL, INTENT(IN) :: PSNOWTEMP,PSNOWTEMPO1
3209 REAL, INTENT(OUT):: PRN, PH, PEVAPC, PLES3L, PLEL3L, PGFLUX
3210 !
3211 REAL :: ZLE, ZDELTAT, ZLWUPSNOW, ZSNOWTO3
3212 !
3213 REAL(KIND=JPRB) :: ZHOOK_HANDLE
3214 !
3215 IF (lhook) CALL dr_hook('SNOWCRO:GET_FLUX',0,zhook_handle)
3216 !
3217 zsnowto3 = psnowtempo1**3 ! to save some CPU time, store this
3218 !
3219 zdeltat = psnowtemp - psnowtempo1 ! surface T time change:
3220 !
3221 zlwupsnow = pemist * xstefan * zsnowto3 * ( psnowtempo1 + 4.*zdeltat )
3222 !
3223 prn = ( 1.-palbt )*psw_rad + pemist*plw_rad - zlwupsnow
3224 !
3225 ph = prsra * xcpd * ( psnowtemp/pexns - pta/pexna )
3226 !
3227 pevapc = prsra * ( (pqsat - pqa) + pdqsat*zdeltat )
3228 !
3229 ples3l = psfcfrz * xlstt * pevapc
3230 !
3231 plel3l = (1.-psfcfrz) * xlvtt * pevapc
3232 !
3233 zle = ples3l + plel3l
3234 !
3235 pgflux = prn - ph - zle + phpsnow
3236 !
3237 IF (lhook) CALL dr_hook('SNOWCRO:GET_FLUX',1,zhook_handle)
3238 !
3239 END SUBROUTINE get_flux
3240 !
3241 !####################################################################
3242 !####################################################################
3243 SUBROUTINE snowcroevapn(PLES3L,PTSTEP,PSNOWTEMP,PSNOWRHO, &
3244  PSNOWDZ,PEVAPCOR,PSNOWHMASS )
3246 !! PURPOSE
3247 !! -------
3248 ! Remove mass from uppermost snow layer in response to
3249 ! evaporation (liquid) and sublimation.
3250 !
3251 !! MODIFICATIONS
3252 !! -------------
3253 !! Original A. Boone
3254 !! 05/2011: E. Brun Takes only into account sublimation and solid
3255 !! condensation. Evaporation and liquid condensation
3256 !! are taken into account in SNOWCROREFRZ
3257 !
3258 USE modd_csts, ONLY : xlstt, xlmtt, xci, xtt
3259 !
3260 IMPLICIT NONE
3261 !
3262 !* 0.1 declarations of arguments
3263 !
3264 REAL, INTENT(IN) :: PTSTEP
3265 !
3266 REAL, DIMENSION(:), INTENT(IN) :: PSNOWTEMP
3267 !
3268 REAL, DIMENSION(:), INTENT(IN) :: PLES3L ! (W/m2)
3269 !
3270 REAL, DIMENSION(:), INTENT(INOUT) :: PSNOWRHO, PSNOWDZ, PSNOWHMASS, &
3271  PEVAPCOR
3272 !
3273 !* 0.2 declarations of local variables
3274 !
3275 REAL, DIMENSION(SIZE(PLES3L)) :: ZSNOWEVAPS, ZSNOWEVAP, ZSNOWEVAPX, &
3276  ZSNOWDZ, ZEVAPCOR
3277 ! ZEVAPCOR = for vanishingy thin snow cover,
3278 ! allow any excess evaporation
3279 ! to be extracted from the soil
3280 ! to maintain an accurate water
3281 ! balance [kg/(m2 s)]
3282 !
3283 REAL(KIND=JPRB) :: ZHOOK_HANDLE
3284 !-------------------------------------------------------------------------------
3285 IF (lhook) CALL dr_hook('SNOWCROEVAPN',0,zhook_handle)
3286 !
3287 ! 0. Initialize:
3288 ! --------------
3289 !
3290 zevapcor(:) = 0.0
3291 zsnowevaps(:) = 0.0
3292 zsnowevap(:) = 0.0
3293 zsnowevapx(:) = 0.0
3294 zsnowdz(:) = 0.0
3295 !
3296 WHERE ( psnowdz>0.0 )
3297  !
3298  ! 1. Sublimation/condensation of snow ice
3299  ! ----------------------------------------
3300  ! Reduce layer thickness and total snow depth
3301  ! if sublimation: add to correction term if potential
3302  ! sublimation exceeds available snow cover.
3303  !
3304  zsnowevaps(:) = ples3l(:) * ptstep / ( xlstt*psnowrho(:) )
3305  zsnowdz(:) = psnowdz(:) - zsnowevaps(:)
3306  psnowdz(:) = max( 0.0, zsnowdz(:) )
3307  zevapcor(:) = zevapcor(:) + max(0.0,-zsnowdz(:)) * psnowrho(:) / ptstep
3308  !
3309  ! Total heat content change due to snowfall and sublimation (added here):
3310  ! (for budget calculations):
3311  !
3312  psnowhmass(:) = psnowhmass(:) &
3313  - ples3l(:) * (ptstep/xlstt) * ( xci * (psnowtemp(:)-xtt) - xlmtt )
3314  !
3315 END WHERE
3316 !
3317 ! 3. Update evaporation correction term:
3318 ! --------------------------------------
3319 !
3320 pevapcor(:) = pevapcor(:) + zevapcor(:)
3321 !
3322 IF (lhook) CALL dr_hook('SNOWCROEVAPN',1,zhook_handle)
3323 !
3324 !-------------------------------------------------------------------------------
3325 !
3326 END SUBROUTINE snowcroevapn
3327 !####################################################################
3328 !####################################################################
3329 !####################################################################
3330 SUBROUTINE snowcrogone(PTSTEP,PLEL3L,PLES3L,PSNOWRHO, &
3331  PSNOWHEAT,PRADSINK_2D,PEVAPCOR,PTHRUFAL,PGRNDFLUX, &
3332  PGFLUXSNOW,PSNOWDZ,PSNOWLIQ,PSNOWTEMP,PRADXS, &
3333  PRR,KNLVLS_USE )
3334 !
3335 !! PURPOSE
3336 !! -------
3337 ! Account for the case when the last trace of snow melts
3338 ! during a time step: ensure mass and heat balance of
3339 ! snow AND underlying surface.
3340 ! Original A. Boone
3341 ! 05/2011: E. Brun Takes into account sublimation and PGRNDFLUX
3342 ! Adds rain and evaporation/liquid condensation
3343 ! in PTHRUFAL
3344 !
3345 USE modd_csts,ONLY : xtt, xlstt, xlvtt
3346 !
3347 IMPLICIT NONE
3348 !
3349 !* 0.1 declarations of arguments
3350 !
3351 REAL, INTENT(IN) :: PTSTEP
3352 !
3353 REAL, DIMENSION(:), INTENT(IN) :: PLEL3L, PLES3L, PGFLUXSNOW,PRR
3354 !
3355 REAL, DIMENSION(:,:), INTENT(IN) :: PRADSINK_2D
3356 !
3357 REAL, DIMENSION(:,:), INTENT(IN) :: PSNOWRHO, PSNOWHEAT
3358 !
3359 REAL, DIMENSION(:), INTENT(INOUT) :: PGRNDFLUX, PRADXS
3360 !
3361 REAL, DIMENSION(:,:), INTENT(INOUT) :: PSNOWDZ, PSNOWLIQ, PSNOWTEMP
3362 !
3363 REAL, DIMENSION(:), INTENT(OUT) :: PTHRUFAL ! melt water [kg/(m2 s)]
3364 !
3365 REAL, DIMENSION(:), INTENT(OUT) :: PEVAPCOR ! [kg/(m2 s)]
3366 ! PEVAPCOR = for vanishingy thin snow cover,
3367 ! allow any excess evaporation
3368 ! to be extracted from the soil
3369 ! to maintain an accurate water
3370 ! balance.
3371 !
3372 INTEGER, DIMENSION(:), INTENT(INOUT) :: KNLVLS_USE
3373 !
3374 !* 0.2 declarations of local variables
3375 !
3376 REAL, DIMENSION(SIZE(PLES3L)) :: ZRADSINK
3377 REAL, DIMENSION(SIZE(PLES3L)) :: ZSNOWHEATC
3378 INTEGER, DIMENSION(SIZE(PLES3L)) :: ISNOWGONE_DELTA
3379 !
3380 INTEGER :: JJ
3381 !
3382 REAL(KIND=JPRB) :: ZHOOK_HANDLE
3383 !-------------------------------------------------------------------------------
3384 IF (lhook) CALL dr_hook('SNOWCROGONE',0,zhook_handle)
3385 !
3386 ! 0. Initialize:
3387 ! --------------
3388 !
3389 pevapcor(:) = 0.0
3390 pthrufal(:) = 0.0
3391 !
3392 DO jj = 1,SIZE(zradsink)
3393  zradsink(jj) = pradsink_2d(jj,inlvls_use(jj))
3394  zsnowheatc(jj) = sum(psnowheat(jj,1:inlvls_use(jj))) !total heat content (J m-2)
3395 END DO
3396 !
3397 isnowgone_delta(:) = 1
3398 !
3399 ! 1. Simple test to see if snow vanishes:
3400 ! ---------------------------------------
3401 ! If so, set thicknesses (and therefore mass and heat) and liquid content
3402 ! to zero, and adjust fluxes of water, evaporation and heat into underlying
3403 ! surface.
3404 !
3405 ! takes into account the heat content corresponding to the occasional
3406 ! sublimation and then PGRNDFLUX
3407 !
3408 zsnowheatc(:) = zsnowheatc(:) + max( 0., ples3l(:)*ptstep/xlstt ) * xlmtt
3409 !
3410 WHERE ( pgfluxsnow(:)+zradsink(:)-pgrndflux(:) >= (-zsnowheatc(:)/ptstep) )
3411  pgrndflux(:) = pgfluxsnow(:) + (zsnowheatc(:)/ptstep)
3412  pevapcor(:) = ples3l(:)/xlstt
3413  pradxs(:) = 0.0
3414  isnowgone_delta(:) = 0 ! FLAG...if=0 then snow vanishes, else=1
3415 END WHERE
3416 !
3417 ! 2. Final update of snow state and computation of corresponding flow
3418 ! Only if snow vanishes
3419 ! -----------------------------
3420 !
3421 pthrufal(:) = 0.
3422 !
3423 DO jj=1, SIZE(zradsink)
3424  !
3425  IF(isnowgone_delta(jj) == 0 ) THEN
3426  pthrufal(jj) = pthrufal(jj) + &
3427  sum( psnowrho(jj,1:inlvls_use(jj))*psnowdz(jj,1:inlvls_use(jj)) ) / ptstep
3428 ! takes into account rain and condensation/evaporation
3429  pthrufal(jj) = pthrufal(jj) + prr(jj) - plel3l(jj)/xlvtt
3430  psnowtemp(jj,:) = xtt
3431  psnowdz(jj,:) = 0.
3432  psnowliq(jj,:) = 0.
3433  inlvls_use(jj) = 0
3434  ENDIF
3435  !
3436 ENDDO
3437 !
3438 IF (lhook) CALL dr_hook('SNOWCROGONE',1,zhook_handle)
3439 !
3440 END SUBROUTINE snowcrogone
3441 !####################################################################
3442 !####################################################################
3443 !####################################################################
3444 SUBROUTINE snowcroevapgone(PSNOWHEAT,PSNOWDZ,PSNOWRHO,PSNOWTEMP,PSNOWLIQ, &
3445  PSNOWGRAN1,PSNOWGRAN2,PSNOWHIST,PSNOWAGE,KNLVLS_USE,&
3446  HSNOWMETAMO)
3447 !
3448 !! PURPOSE
3449 !! -------
3450 !
3451 ! If all snow in uppermost layer evaporates/sublimates, re-distribute
3452 ! grid (below assumes very thin snowpacks so layer-thicknesses are
3453 ! constant).
3454 ! Original A. Boone
3455 ! 05/2011: E. Brun Takes into account previous changes in the energy
3456 ! content
3457 !
3458 !
3459 USE modd_csts, ONLY : xtt, xrholw, xlmtt, xci
3460 USE modd_snow_par, ONLY : xrhosmin_es, xsnowdmin, xrhosmax_es
3461 USE mode_snow3l
3462 USE modd_snow_metamo
3464 !
3465 IMPLICIT NONE
3466 !
3467 !* 0.1 declarations of arguments
3468 !
3469 REAL, DIMENSION(:,:), INTENT(INOUT) :: PSNOWRHO ! snow density profile (kg/m3)
3470 REAL, DIMENSION(:,:), INTENT(INOUT) :: PSNOWDZ ! snow layer thickness profile (m)
3471 REAL, DIMENSION(:,:), INTENT(INOUT) :: PSNOWHEAT ! snow heat content/enthalpy (J/m2)
3472 REAL, DIMENSION(:,:), INTENT(INOUT) :: PSNOWGRAN1 ! snow grain parameter 1 (-)
3473 REAL, DIMENSION(:,:), INTENT(INOUT) :: PSNOWGRAN2 ! snow grain parameter 2 (-)
3474 REAL, DIMENSION(:,:), INTENT(INOUT) :: PSNOWHIST ! snow grain historical variable (-)
3475 REAL, DIMENSION(:,:), INTENT(INOUT) :: PSNOWAGE ! Snow grain age
3476 !
3477 REAL, DIMENSION(:,:), INTENT(INOUT) :: PSNOWTEMP ! snow temperature profile (K)
3478 REAL, DIMENSION(:,:), INTENT(INOUT) :: PSNOWLIQ ! snow liquid water profile (m)
3479 !
3480 INTEGER, DIMENSION(:), INTENT(IN) :: KNLVLS_USE
3481  CHARACTER(3), INTENT(IN) :: HSNOWMETAMO ! metamorphism scheme
3482 !
3483 !* 0.2 declarations of local variables
3484 !
3485 REAL, DIMENSION(SIZE(PSNOWDZ,1)) :: ZSNOWHEAT_1D ! total heat content (J/m2)
3486 REAL, DIMENSION(SIZE(PSNOWDZ,1)) :: ZSNOWRHO_1D ! total snowpack average density (kg/m3)
3487 REAL, DIMENSION(SIZE(PSNOWDZ,1)) :: ZSNOW ! total snow depth (m)
3488 REAL, DIMENSION(SIZE(PSNOWDZ,1)) :: ZSCAP ! Snow layer heat capacity (J/K/m3)
3489 REAL, DIMENSION(SIZE(PSNOWDZ,1)) :: ZNDENT ! Number of dendritic layers (-)
3490 REAL, DIMENSION(SIZE(PSNOWDZ,1)) :: ZNVIEU ! Number of non dendritic layers (-)
3491 REAL, DIMENSION(SIZE(PSNOWDZ,1)) :: ZSNOWAGE_1D ! total snowpack average
3492 !age (days)
3493 REAL, DIMENSION(SIZE(PSNOWRHO,1),SIZE(PSNOWRHO,2)) :: ZSNOWGRAN1N, &
3494  ZSNOWGRAN2N,ZSNOWHISTN
3495 !
3496 LOGICAL :: GDENDRITIC
3497 !
3498 INTEGER :: JJ, JST ! loop control
3499 !
3500 REAL(KIND=JPRB) :: ZHOOK_HANDLE
3501 !-------------------------------------------------------------------------------
3502 IF (lhook) CALL dr_hook('SNOWCROEVAPGONE',0,zhook_handle)
3503 !
3504 ! Initialize:
3505 !
3506 zsnowheat_1d(:) = 0.
3507 zsnow(:) = 0.
3508 zsnowrho_1d(:) = 0.
3509 zndent(:) = 0.
3510 znvieu(:) = 0.
3511 zsnowage_1d(:) = 0.
3512 zscap(:) = 0.
3513 !
3514 ! First, determine where uppermost snow layer has completely
3515 ! evaporated/sublimated (as it becomes thin):
3516 DO jj = 1,SIZE(psnowrho,1)
3517  !
3518  IF ( psnowdz(jj,1)==0.0 ) THEN
3519  !
3520  DO jst = 2,knlvls_use(jj)
3521  !
3522  zsnowheat_1d(jj) = zsnowheat_1d(jj) + psnowdz(jj,jst) * &
3523  ( psnowrho(jj,jst)*xci * (zsnowtemp(jj,jst)-xtt) &
3524  - xlmtt * psnowrho(jj,jst) ) &
3525  + xlmtt * xrholw * psnowliq(jj,jst)
3526  zsnow(jj) = zsnow(jj) + psnowdz(jj,jst)
3527  zsnowrho_1d(jj) = zsnowrho_1d(jj) + psnowdz(jj,jst) * psnowrho(jj,jst)
3528  zsnowage_1d(jj) = zsnowage_1d(jj) + psnowdz(jj,jst) * psnowrho(jj,jst) * psnowage(jj,jst)
3529  !
3530  ! snow grains
3531  IF ( hsnowmetamo=='B92' ) THEN
3532  gdendritic = ( psnowgran1(jj,jst)<-xepsi )
3533  ELSE
3534  gdendritic = ( psnowgran1(jj,jst)<xvdiam6*(4.-psnowgran2(jj,jst))-xuepsi )
3535  ENDIF
3536  !
3537  IF ( gdendritic ) THEN ! Dendritic snow
3538  zndent(jj) = zndent(jj) + 1.0
3539  ELSE ! Non dendritic snow
3540  znvieu(jj) = znvieu(jj) + 1.0
3541  ENDIF
3542  !
3543  ENDDO
3544  !
3545  ENDIF
3546  !
3547 END DO
3548 !
3549 zsnowrho_1d(:) = zsnowrho_1d(:) / max( xsnowdmin, zsnow(:) )
3550 zsnowage_1d(:) = zsnowage_1d(:) / max( xsnowdmin, zsnow(:) * zsnowrho_1d(:) )
3551 zsnowrho_1d(:) = max( xrhosmin_es, min( xrhosmax_es, zsnowrho_1d(:) ) )
3552 !
3553 ! Where uppermost snow layer has vanished, redistribute vertical
3554 ! snow mass and heat profiles (and associated quantities):
3555 !
3556  CALL snow3lavgrain(psnowgran1,psnowgran2,psnowhist, &
3557  zsnowgran1n,zsnowgran2n,zsnowhistn,zndent,znvieu,&
3558  hsnowmetamo)
3559 !
3560 DO jj=1,SIZE(psnowrho,1)
3561  !
3562  IF( zsnow(jj)/=0.0 ) THEN
3563  !
3564  psnowdz(jj,1:knlvls_use(jj)) = zsnow(jj) / knlvls_use(jj)
3565  psnowheat(jj,1:knlvls_use(jj)) = zsnowheat_1d(jj) / knlvls_use(jj)
3566  psnowrho(jj,1:knlvls_use(jj)) = zsnowrho_1d(jj)
3567  !
3568  zscap(jj) = zsnowrho_1d(jj) * xci
3569  !
3570  DO jst = 1,knlvls_use(jj)
3571  !
3572  psnowtemp(jj,jst) = xtt + ( ( (psnowheat(jj,jst)/psnowdz(jj,jst)) &
3573  + xlmtt*psnowrho(jj,jst) ) / zscap(jj) )
3574  psnowtemp(jj,jst) = min( xtt, psnowtemp(jj,jst) )
3575  !
3576  psnowliq(jj,jst) = max( 0.0, psnowtemp(jj,jst)-xtt ) * zscap(jj) * &
3577  psnowdz(jj,jst) / (xlmtt*xrholw)
3578  !
3579  ENDDO
3580  !
3581  ENDIF
3582  !
3583 ENDDO
3584 !
3585 IF (lhook) CALL dr_hook('SNOWCROEVAPGONE',1,zhook_handle)
3586 !
3587 END SUBROUTINE snowcroevapgone
3588 !
3589 !####################################################################
3590 !####################################################################
3591 !####################################################################
3592 SUBROUTINE snownlfall_upgrid(TPTIME, OGLACIER,PTSTEP,PSR,PTA,PVMOD, &
3593  PSNOW,PSNOWRHO,PSNOWDZ,PSNOWHEAT,PSNOWHMASS, &
3594  PSNOWALB,PPERMSNOWFRAC,PSNOWGRAN1,PSNOWGRAN2, &
3595  GSNOWFALL,PSNOWDZN,PSNOWRHOF,PSNOWDZF, &
3596  PSNOWGRAN1F,PSNOWGRAN2F,PSNOWHISTF,PSNOWAGEF, &
3597  OMODIF_GRID,KNLVLS_USE,OSNOWDRIFT,PZ0EFF,PUREF,&
3598  HSNOWMETAMO)
3599 !
3600 !! PURPOSE
3601 !! -------
3602 ! Adds new snowfall and updates the vertical grid in order to keep an
3603 ! optimal discertisation
3604 !
3605 !! AUTHOR
3606 !! ------
3607 !! E. Brun * Meteo-France *
3608 !!
3609 !
3610 !!
3611 !! MODIFICATIONS
3612 !! ------
3613 !!
3614 !! 2014-02-05 V. Vionnet: wind speed in the parameterization for new snow
3615 !! density and characteristic of grains of new snow
3616 !! are taken at a reference height
3617 !! 2014-06-03 M. Lafaysse : threshold on PZ0EFF
3618 !!
3619 USE modd_type_date_surf, ONLY: date_time
3620 USE modd_csts, ONLY : xlmtt, xtt, xci
3621 USE modd_snow_metamo, ONLY : xnden1, xnden2, xnden3, xgran, &
3623 !
3624 USE modd_snow_par, ONLY : xrhosmin_es, xsnowdmin, xansmax, xaglamax, xsnowcritd, &
3625  xdzmin_top, xdzmin_top_bis, xdzmin_bot, xsplit_coef, &
3626  xagreg_coef_1, xagreg_coef_2, xdz1, xdz2, xdz3, xdz3_bis,&
3627  xdz4, xdz5, xdz_base, xdz_internal, xscale_cm, &
3628  xdzmax_internal, xdzmin_top_extrem, xsnowfall_threshold, &
3629  xratio_newlayer, xdepth_threshold1, xdepth_threshold2, &
3630  xdepth_surface, xdiff_1, xdiff_max, xscale_diff, &
3631  xsnowfall_a_sn, xsnowfall_b_sn, xsnowfall_c_sn
3632 !
3633 USE mode_snow3l
3634 !
3635 IMPLICIT NONE
3636 !
3637 !* 0.1 declarations of arguments
3638 !
3639 TYPE(date_time), INTENT(IN) :: TPTIME ! current date and time
3640 LOGICAL, INTENT(IN) :: OGLACIER ! True = Over permanent snow and ice,
3641 ! initialise WGI=WSAT,
3642 ! Hsnow>=10m and allow 0.8<SNOALB<0.85
3643  ! False = No specific treatment
3644 !
3645 REAL, INTENT(IN) :: PTSTEP
3646 !
3647 REAL, DIMENSION(:), INTENT(IN) :: PSR, PTA, PVMOD, PPERMSNOWFRAC
3648 !
3649 REAL, DIMENSION(:),INTENT(IN) :: PZ0EFF,PUREF
3650 !
3651 REAL, DIMENSION(:), INTENT(INOUT) :: PSNOW, PSNOWALB
3652 !
3653 REAL, DIMENSION(:,:), INTENT(IN) :: PSNOWRHO, PSNOWDZ, PSNOWHEAT
3654 !
3655 REAL, DIMENSION(:), INTENT(OUT) :: PSNOWHMASS
3656 !
3657 REAL, DIMENSION(:,:), INTENT(IN) :: PSNOWGRAN1, PSNOWGRAN2
3658 !
3659 LOGICAL, DIMENSION(:), INTENT(INOUT) :: GSNOWFALL
3660 !
3661 ! Fresh snow characteristics
3662 REAL, DIMENSION(:), INTENT(OUT) :: PSNOWRHOF, PSNOWDZF
3663 REAL, DIMENSION(:), INTENT(OUT) :: PSNOWGRAN1F, PSNOWGRAN2F, PSNOWHISTF
3664 REAL, DIMENSION(:), INTENT(OUT) :: PSNOWAGEF
3665 ! New vertical grid
3666 REAL, DIMENSION(:,:), INTENT(OUT) :: PSNOWDZN
3667 !
3668 LOGICAL, DIMENSION(:), INTENT(OUT) :: OMODIF_GRID
3669 !
3670 INTEGER, DIMENSION(:), INTENT(INOUT) :: KNLVLS_USE
3671 
3672 LOGICAL,INTENT(IN) :: OSNOWDRIFT ! if snowdrift then grain types are not modified by wind
3673  CHARACTER(3), INTENT(IN) :: HSNOWMETAMO ! metamorphism scheme
3674 !* 0.2 declarations of local variables
3675 !
3676 !
3677 LOGICAL, DIMENSION(SIZE(PTA)) :: GAGREG_SURF
3678 !
3679 REAL, DIMENSION(SIZE(PTA)) :: ZSNOWFALL, ZSNOWTEMP, ZSCAP, ZANSMAX
3680 !
3681 REAL, DIMENSION(SIZE(PSNOWRHO,1),SIZE(PSNOWRHO,2)) :: ZDZOPT
3682 !
3683 REAL :: ZZ0EFF
3684 !
3685 REAL :: ZAGE_NOW
3686 REAL :: ZSNOW_UPPER, ZSNOW_UPPER2 ! snow depth treatednormally (<= XDEPTH_SURFACE)
3687 REAL :: ZCOEF_DEPTH !coefficient for repartition of deep snow above 3 meters
3688 REAL :: ZTHICKNESS_INTERMEDIATE, ZTHICKNESS2
3689 REAL :: ZPENALTY, ZDIFTYPE_INF, ZDIFTYPE_SUP, ZCRITSIZE, ZCRITSIZE_INF, ZCRITSIZE_SUP
3690 REAL :: ZSNOW2L, ZCOEF
3691 !
3692 INTEGER :: INB_DEEP_LAYER, INB_UPPER_LAYER !separation between deep and upper layers
3693  ! if snow depth below XDEPTH_SURFACE then INB_DEEP_LAYER=0
3694 INTEGER :: INB_MIN_LAYERS ! why this test ?
3695 INTEGER :: INB_INTERMEDIATE ! number of intermediate layers (constant optimal gridding)
3696 INTEGER :: IEND_INTERMEDIATE ! layer indice for bottom of intermediate layers
3697 INTEGER :: JSTDEEP, JSTEND
3698 INTEGER :: JST_1, JJ_A_AGREG_SUP, JJ_A_AGREG_INF, JJ_A_DEDOUB
3699 INTEGER :: INLVLS, INLVLSMIN, INLVLSMAX, JJ, JST
3700 !
3701 ! Coefficient to adjust wind speed at the height used in the parameterization
3702 ! for:
3703 ! - density of new snow
3704 ! - sphericity and dendricity of new snow
3705 ! Default values : 10 m for new snow (Pahaut, 1976) and 5 m for characteristics
3706 ! of snow grains (Guyomarc'h et Merindol, 1998)
3707 REAL, PARAMETER :: PPHREF_WIND_RHO = 10.
3708 REAL, PARAMETER :: PPHREF_WIND_GRAIN = 5.
3709 REAL, PARAMETER :: PPHREF_WIND_MIN = min(pphref_wind_rho,pphref_wind_grain)*0.5
3710 REAL, DIMENSION(SIZE(PTA)) :: ZWIND_RHO
3711 REAL, DIMENSION(SIZE(PTA)) :: ZWIND_GRAIN
3712 !
3713 REAL(KIND=JPRB) :: ZHOOK_HANDLE
3714 !
3715 !* 1.0 Initialization and snowage calculation for the present date
3716 !
3717 IF (lhook) CALL dr_hook('SNOWNLFALL_UPGRID',0,zhook_handle)
3718 !
3719 inlvls = SIZE (psnowrho(:,:),2)
3720 inlvlsmax = SIZE (psnowrho(:,:),2)
3721 inlvlsmin = 3
3722 !
3723 zsnowtemp(:) = xtt
3724 zsnowfall(:) = 0.0 !Matthieu Lafaysse 21/09/2012
3725 !
3726 gsnowfall(:) =.false.
3727 gagreg_surf(:) =.false.
3728 !
3729 psnowhmass(:) = 0.0
3730 psnowrhof(:) = 0.0
3731 psnowdzf(:) = 0.0
3732 psnowgran1f(:) = 0.0
3733 psnowgran2f(:) = 0.0
3734 psnowhistf(:) = 0.0
3735 psnowdzn(:,:) = psnowdz(:,:)
3736 !
3737 omodif_grid(:) = .false.
3738 !
3739 !************************************************************************************
3740 !* 1.1 Calculation of the optimal vertical grid size ZDZOPT
3741 ! as a function of maximum number of layers and of current
3742 ! snow depth (modified 05/06/2012 by Matthieu Lafaysse)
3743 !
3744 ! KNLVLS_USE(JJ) > INB_MIN_LAYERS =>
3745 ! KNLVLS_USE(JJ) > 2 + INLVLSMAX/3 =>
3746 ! ( KNLVLS_USE(JJ) + INLVLSMAX ) / 6 > (2 + INLVLSMAX/3 + INLVLSMAX) / 6 =>
3747 ! INB_DEEP_LAYER > (2 + 4*INLVLSMAX/3 ) / 6 >= 1
3748 inb_min_layers = 2 + inlvlsmax/3
3749 !
3750 DO jj = 1,SIZE(psnow(:))
3751  !
3752  IF ( psnow(jj)>xdepth_threshold2 .AND. knlvls_use(jj)>inb_min_layers ) THEN
3753  ! for very thick snowpack with enough snow layers
3754  ! special treatment
3755  ! we put the highest thickness in the lowest layers
3756  ! about 1/3 of layers for all snow except XDEPTH_SURFACE=3 first meters
3757  !
3758  !number of "deep layers"
3759  inb_deep_layer = ( knlvls_use(jj) + inlvlsmax ) / 6
3760  !
3761  !number of "upper layers"
3762  inb_upper_layer = knlvls_use(jj) - inb_deep_layer
3763  !
3764  !thickness of "upper layers"
3765  zsnow_upper = xdepth_surface
3766  !
3767  !Arithmetic serie : 1+2+3+...+INB_DEEP_LAYER=INB_DEEP_LAYER*(INB_DEEP_LAYER+1)/2
3768  zcoef_depth = ( psnow(jj) - xdepth_surface ) * 2. / ( (inb_deep_layer+1) * inb_deep_layer )
3769  !
3770  ! deep layers optimal thickness :
3771  ! increasing thickness with depth
3772  DO jstdeep = 1,inb_deep_layer
3773  jst = inb_upper_layer + jstdeep
3774  zdzopt(jj,jst) = zcoef_depth * jstdeep
3775  !This sum is equal to PSNOW(JJ)-XDEPTH_SURFACE
3776  ENDDO
3777  !
3778  ELSE
3779  !
3780  inb_upper_layer = knlvls_use(jj)
3781  !
3782  zsnow_upper = psnow(jj)
3783  !
3784  END IF
3785  !
3786  !on force le ZDZOPT des 3 premières couches à ZSNOW_UPPER/3 maximum, chacune.
3787  ! => si on n'a qu'une couche, ZDZOPT(1) = ZSNOW_UPPER/3
3788  ! quel que soit INB_UPPER_LAYER
3789  !
3790  zsnow_upper2 = zsnow_upper / max( inlvlsmin, inb_upper_layer )
3791  !
3792  zdzopt(jj,1) = min( xdz1, zsnow_upper2 )
3793  IF ( knlvls_use(jj)>=2 ) zdzopt(jj,2) = min( xdz2, zsnow_upper2 )
3794  IF ( knlvls_use(jj)>=3 ) zdzopt(jj,3) = min( xdz3, zsnow_upper2 )
3795  !
3796  IF ( inb_upper_layer>0 ) THEN
3797  !
3798  zsnow_upper2 = zsnow_upper / inb_upper_layer
3799  !
3800  ! dans ce cas, à partir de la 3ème couche, on prend la fraction du nombre de
3801  ! couches supérieures total, pour les couches jusqu'à 5
3802  !
3803  !ML : replace > by >= on 12-12-20 because the last layer was not initialised in case of thick snowpacks
3804  IF ( inb_upper_layer>=3 ) zdzopt(jj,3) = min( xdz3_bis, zsnow_upper2 )
3805  IF ( inb_upper_layer>=4 ) zdzopt(jj,4) = min( xdz4 , zsnow_upper2 )
3806  IF ( inb_upper_layer>=5 ) zdzopt(jj,5) = min( xdz5 , zsnow_upper2 )
3807  !
3808  IF ( inb_upper_layer==knlvls_use(jj) ) THEN
3809  ! si on n'a pas de couches profondes
3810  !
3811  ! dans ce cas, on reprend ZSNOW_UPPER/3 maximum pour la dernière couche
3812  !
3813  ! last layer of' upper layers' : normal case : thin layer
3814  zdzopt(jj,inb_upper_layer) = min( xdz_base, zsnow_upper/max(inlvlsmin,inb_upper_layer) )
3815  !
3816  ! ZTHICKNESS_INTERMEDIATE contient ce qu'il reste d'épaisseur disponible
3817  ! dans les couches supérieures
3818  !remaining snow for remaining layers
3819  zthickness_intermediate = zsnow_upper - sum(zdzopt(jj,1:5)) - zdzopt(jj,inb_upper_layer)
3820 
3821  IF ( zsnow_upper<=xdepth_threshold1 .OR. inb_upper_layer<8 ) THEN
3822  inb_intermediate = inb_upper_layer - 6
3823  iend_intermediate = inb_upper_layer - 1
3824  ELSE
3825  ! si INB_UPPER_LAYER>=8, les avant et avant-dernière couches ne sont pas
3826  ! considérées commes intermédiaires
3827  inb_intermediate = inb_upper_layer - 8
3828  iend_intermediate = inb_upper_layer - 3
3829  ! dans ce cas, on garde un peu d'épaisseur pour les deux couches restantes
3830  IF ( inb_intermediate>0 ) THEN
3831  zthickness_intermediate = zthickness_intermediate * inb_intermediate / float(inb_intermediate+1)
3832  END IF
3833  END IF
3834  !
3835  ELSE
3836  ! si on a des couches profondes, les couches intermédiaires sont celles
3837  ! qui restent quand on a enlevé les 5 premières des couches supérieures
3838  !
3839  ! case with very thick snowpacks :
3840  ! the last layer of upper layers is not an exception
3841  zthickness_intermediate = zsnow_upper - sum(zdzopt(jj,1:5))
3842  inb_intermediate = inb_upper_layer - 5
3843  iend_intermediate = inb_upper_layer
3844  !
3845  END IF
3846  !
3847  ! For thick snowpack : add maximum value of optimal thickness to avoid too
3848  ! large differencies between layers
3849  IF ( inb_intermediate>0 ) THEN
3850  !
3851  zthickness2 = max( xdz_internal, zthickness_intermediate/inb_intermediate )
3852  !
3853  jstend = min( iend_intermediate,10 )
3854  DO jst = 6,jstend
3855  zdzopt(jj,jst) = min( xdzmax_internal(jst-5), zthickness2 )
3856  END DO
3857  !
3858  IF ( iend_intermediate>10 ) THEN
3859  DO jst = 11,iend_intermediate
3860  zdzopt(jj,jst) = zthickness2
3861  END DO
3862  END IF
3863  !
3864  END IF
3865  !
3866  IF ( zsnow_upper>=xdepth_threshold1 .AND. inb_upper_layer>=8 ) THEN
3867  !Linear interpolation of optimal thickness between layers N-3 and N :
3868  zdzopt(jj,inb_upper_layer-2) = 0.34*zdzopt(jj,inb_upper_layer) + &
3869  0.66*zdzopt(jj,inb_upper_layer-3)
3870  zdzopt(jj,inb_upper_layer-1) = 0.66*zdzopt(jj,inb_upper_layer) + &
3871  0.34*zdzopt(jj,inb_upper_layer-3)
3872  ENDIF
3873  !
3874  END IF
3875  !
3876 END DO
3877 !
3878 !************************************************************************************
3879 !This was the initial code for optimal layers until may 2012
3880 !
3881 ! ! ! ! !
3882 ! ! ! ! ! !* 1.1 Calculation of the optimal vertical grid size
3883 ! ! ! ! ! ! as a function of maximum number of layers and of current
3884 ! ! ! ! ! ! snow depth
3885 ! ! ! ! ! !
3886 ! ! ! ! ! DO JJ=1, SIZE(PSNOW(:))
3887 ! ! ! ! ! ZDZOPT(JJ,1) = MIN(XDZ1,PSNOW(JJ)/MAX(INLVLSMIN,KNLVLS_USE(JJ)))
3888 ! ! ! ! ! ZDZOPT(JJ,2) = MIN(XDZ2,PSNOW(JJ)/MAX(INLVLSMIN,KNLVLS_USE(JJ)))
3889 ! ! ! ! ! ZDZOPT(JJ,3) = MIN(XDZ3,PSNOW(JJ)/MAX(INLVLSMIN,KNLVLS_USE(JJ)))
3890 ! ! ! ! ! IF (KNLVLS_USE(JJ)>3) ZDZOPT(JJ,3) = MIN(XDZ3_BIS,PSNOW(JJ)/KNLVLS_USE(JJ))
3891 ! ! ! ! ! IF (KNLVLS_USE(JJ)>4) ZDZOPT(JJ,4) = MIN(XDZ4,PSNOW(JJ)/KNLVLS_USE(JJ))
3892 ! ! ! ! ! IF (KNLVLS_USE(JJ)>5) ZDZOPT(JJ,5) = MIN(XDZ5,PSNOW(JJ)/KNLVLS_USE(JJ))
3893 ! ! ! ! ! IF (KNLVLS_USE(JJ)>0) ZDZOPT(JJ,KNLVLS_USE(JJ))= &
3894 ! ! ! ! ! MIN(XDZ_BASE,PSNOW(JJ)/MAX(INLVLSMIN,KNLVLS_USE(JJ)))
3895 ! ! ! ! ! DO JST=6,KNLVLS_USE(JJ)-1,1
3896 ! ! ! ! ! ZDZOPT(JJ,JST) = MAX(XDZ_INTERNAL,(PSNOW(JJ) - SUM(ZDZOPT(JJ,1:5))- &
3897 ! ! ! ! ! ZDZOPT(JJ,KNLVLS_USE(JJ))) /(KNLVLS_USE(JJ)-6))
3898 ! ! ! ! ! END DO
3899 ! ! ! ! ! END DO
3900 ! ! ! ! ! !
3901 ! ! ! ! !
3902 !
3903 !************************************************************************************
3904 !
3905 !* 2.0 Fresh snow characteristics
3906 !
3907 !
3908 !
3909 ! Heat content of newly fallen snow (J/m2):
3910 ! NOTE for now we assume the snowfall has
3911 ! the temperature of the snow surface upon reaching the snow.
3912 ! This is done as opposed to using the air temperature since
3913 ! this flux is quite small and has little to no impact
3914 ! on the time scales of interest. If we use the above assumption
3915 ! then, then the snowfall advective heat flux is zero.
3916 !!
3917 DO jj = 1,SIZE(psnow(:))
3918  !
3919  IF ( psr(jj)>0.0 ) THEN
3920  !
3921  ! newly fallen snow characteristics:
3922  IF ( knlvls_use(jj)>0 ) THEN !Case of new snowfall on a previously snow-free surface
3923  zscap(jj) = xci*psnowrho(jj,1)
3924  zsnowtemp(jj) = xtt + ( psnowheat(jj,1) + xlmtt*psnowrho(jj,1)*psnowdz(jj,1) ) / &
3925  ( zscap(jj) * max( xsnowdmin/inlvls, psnowdz(jj,1) ) )
3926  ELSE ! case with bare ground
3927  zsnowtemp(jj) = pta(jj)
3928  ENDIF
3929  zsnowtemp(jj) = min( xtt, zsnowtemp(jj) )
3930  !
3931  !
3932  ! Wind speeds at reference heights for new snow density and charactristics of
3933  ! grains of new snow
3934  ! Computed from PVMOD at PUREF (m) assuming a log profile in the SBL
3935  ! and a roughness length equal to PZ0EFF
3936  !
3937  zz0eff=min(pz0eff(jj),puref(jj)*0.5,pphref_wind_min)
3938 
3939  zwind_rho(jj) = pvmod(jj)*log(pphref_wind_rho/zz0eff)/ &
3940  log(puref(jj)/zz0eff)
3941  zwind_grain(jj) = pvmod(jj)*log(pphref_wind_grain/zz0eff)/ &
3942  log(puref(jj)/zz0eff)
3943 
3944  psnowhmass(jj) = psr(jj) * ( xci * ( zsnowtemp(jj)-xtt ) - xlmtt ) * ptstep
3945  !
3946  psnowrhof(jj) = max( xrhosmin_es, xsnowfall_a_sn + &
3947  xsnowfall_b_sn * ( pta(jj)-xtt ) + &
3948  xsnowfall_c_sn * min( pvmod(jj), sqrt(zwind_rho(jj) ) ) )
3949  zsnowfall(jj) = psr(jj) * ptstep / psnowrhof(jj) ! snowfall thickness (m)
3950  psnow(jj) = psnow(jj) + zsnowfall(jj)
3951  psnowdzf(jj) = zsnowfall(jj)
3952  !
3953  IF ( hsnowmetamo=='B92' ) THEN
3954  !
3955  IF ( osnowdrift ) THEN
3956  psnowgran1f(jj) = -xgran
3957  psnowgran2f(jj) = xnsph3
3958  ELSE
3959  psnowgran1f(jj) = max( min( xnden1*zwind_grain(jj)-xnden2, xnden3 ), -xgran )
3960  psnowgran2f(jj) = min( max( xnsph1*zwind_grain(jj)+xnsph2, xnsph3 ), xnsph4 )
3961  END IF
3962  !
3963  ELSE
3964  !
3965  IF ( osnowdrift ) THEN
3966  psnowgran1f(jj) = xvdiam6
3967  psnowgran2f(jj) = xnsph3/xgran
3968  ELSE
3969  psnowgran2f(jj) = min( max( xnsph1*zwind_grain(jj)+xnsph2, xnsph3 ), xnsph4 ) / xgran
3970  zcoef = max( min( xnden1*zwind_grain(jj)-xnden2, xnden3 ), -xgran ) / ( -xgran )
3971  psnowgran1f(jj) = xvdiam6 * &
3972  ( zcoef + ( 1.- zcoef ) * &
3973  ( 3.*psnowgran2f(jj) + 4.*(1.-psnowgran2f(jj)) ) )
3974  END IF
3975  !
3976  ENDIF
3977  !
3978  psnowhistf(jj) = 0.0
3979  psnowagef(jj) = 0.0
3980  gsnowfall(jj) = .true.
3981  omodif_grid(jj) = .true.
3982  !
3983  ENDIF
3984  !
3985 ENDDO
3986 !
3987 ! intialize the albedo:
3988 ! penser a changer 0.000001 par XUEPSI
3989 IF(oglacier)THEN
3990  zansmax(:) = xaglamax * ppermsnowfrac(:) + xansmax * (1.0-ppermsnowfrac(:))
3991 ELSE
3992  zansmax(:) = xansmax
3993 ENDIF
3994 !
3995 WHERE( gsnowfall(:) .AND. abs(psnow(:)-zsnowfall(:))< 0.000001 )
3996  psnowalb(:) = zansmax(:)
3997 END WHERE
3998 !
3999 ! Computation of the new grid size
4000 ! It starts with successive exclusive cases
4001 ! Each case is described inside the corresponding condition
4002 !
4003 ! cases with fresh snow
4004 !
4005 DO jj=1,SIZE(psnow(:)) ! grid point loop
4006  !
4007  IF( .NOT.gsnowfall(jj) .AND. psnow(jj)>=xsnowcritd .AND. knlvls_use(jj)>=inlvlsmin ) THEN
4008  !
4009  ! no fresh snow + deep enough snowpack + enough snow layers ==> no change
4010  !
4011  ELSEIF( psnow(jj)<xsnowcritd .OR. knlvls_use(jj)<inlvlsmin .OR. psnow(jj)==zsnowfall(jj) ) THEN
4012  !
4013  ! too shallow snowpack or too few layers or only fresh snow
4014  ! ==> uniform grid and identical snow layers / number depends on snow depth
4015  omodif_grid(jj) = .true.
4016  knlvls_use(jj) = max( inlvlsmin, min( inlvlsmax, int(psnow(jj)*xscale_cm) ) )
4017  psnowdzn(jj,1:knlvls_use(jj)) = psnow(jj) / knlvls_use(jj)
4018  !
4019  ELSE
4020  !
4021  ! fresh snow over snow covered ground + enough snow layers
4022  omodif_grid(jj) = .true.
4023  zdiftype_sup = snow3ldiftyp( psnowgran1(jj,1),psnowgran1f(jj), &
4024  psnowgran2(jj,1),psnowgran2f(jj),hsnowmetamo )
4025  !
4026  IF ( ( zdiftype_sup<xdiff_1 .AND. psnowdz(jj,1)< zdzopt(jj,1) ) .OR. &
4027  ( psr(jj)<xsnowfall_threshold .AND. psnowdz(jj,1)<2.*zdzopt(jj,1) ) .OR. &
4028  psnowdz(jj,1)<xdzmin_top_extrem ) THEN
4029  !
4030  ! Fresh snow is similar to a shallow surface layer (< ZDZOPT)
4031  ! or snowfall is very low and the surface layer not too deep (< 2*ZDZOPT) [NEW CONDITION 11/2012]
4032  ! or the surface layer is extremely thin (< XDZMIN_TOP_EXTREM) [NEW CONDITION 11/2012]
4033  ! The two new conditions are necessary for forcings with very low precipitation
4034  ! (e.g. ERA interim reanalyses, or climate models)
4035  ! ==> fresh snow is agregated to the surface layer
4036  psnowdzn(jj,1) = psnowdz(jj,1) + psnowdzf(jj)
4037  DO jst = knlvls_use(jj),2,-1
4038  psnowdzn(jj,jst) = psnowdz(jj,jst)
4039  ENDDO
4040  !
4041  ELSEIF ( knlvls_use(jj)<inlvlsmax ) THEN
4042  !
4043  ! fresh snow is too different from the surface or the surface is too deep
4044  ! and there is room for extra layers ==> we create a new layer
4045  knlvls_use(jj)=knlvls_use(jj)+1
4046  !
4047  IF ( psnowdzf(jj)>xratio_newlayer*psnowdz(jj,2) ) THEN
4048  !
4049  ! Snowfall is sufficient to create a new layer not lower than 1/10 of the second layer
4050  psnowdzn(jj,1) = psnowdzf(jj)
4051  DO jst = knlvls_use(jj),2,-1
4052  psnowdzn(jj, jst) = psnowdz(jj,jst-1)
4053  ENDDO
4054  !
4055  ELSE
4056  ! The ratio would be lower than 1/10 : [NEW : 11/2012]
4057  ! aggregate a part of the old layer with fresh snow to limit the ratio to 1/10.
4058  zsnow2l = psnowdzf(jj) + psnowdz(jj,1)
4059  psnowdzn(jj,1) = xratio_newlayer * zsnow2l
4060  psnowdzn(jj,2) = (1.-xratio_newlayer) * zsnow2l
4061  DO jst = knlvls_use(jj),3,-1
4062  psnowdzn(jj,jst) = psnowdz(jj,jst-1)
4063  ENDDO
4064  !
4065  ENDIF
4066  !
4067  ELSE
4068  !
4069  ! fresh snow is too different from the surface or the surface is too deep
4070  ! and there is no room for extra layers
4071  ! ==> we agregate internal most similar snowlayers and create a new surface layer
4072  jj_a_agreg_sup = 1
4073  jj_a_agreg_inf = 2
4074  !
4075  DO jst = 1,knlvls_use(jj)
4076  !
4077  IF ( jst>1 ) THEN
4078  !
4079  zcritsize_sup = xscale_diff * ( psnowdz(jj,jst) /zdzopt(jj,jst) + &
4080  psnowdz(jj,jst-1)/zdzopt(jj,jst-1) )
4081  zdiftype_sup = snow3ldiftyp( psnowgran1(jj,jst-1),psnowgran1(jj,jst), &
4082  psnowgran2(jj,jst-1),psnowgran2(jj,jst), &
4083  hsnowmetamo )
4084  !
4085  IF ( zdiftype_sup+zcritsize_sup<zpenalty ) THEN
4086  zpenalty = zdiftype_sup + zcritsize_sup
4087  jj_a_agreg_sup = jst - 1
4088  jj_a_agreg_inf = jst
4089  ENDIF
4090  !
4091  ENDIF
4092  !
4093  IF ( jst<knlvls_use(jj) ) THEN
4094  !
4095  zcritsize_inf = xscale_diff * ( psnowdz(jj,jst) /zdzopt(jj,jst) + &
4096  psnowdz(jj,jst+1)/zdzopt(jj,jst+1) )
4097  !
4098  IF ( jst==1 ) THEN
4099  zdiftype_inf = snow3ldiftyp( psnowgran1(jj,1),psnowgran1f(jj), &
4100  psnowgran2(jj,1),psnowgran2f(jj), &
4101  hsnowmetamo)
4102  !
4103  zpenalty = zdiftype_inf + zcritsize_inf
4104  ELSE
4105  zdiftype_inf = snow3ldiftyp( psnowgran1(jj,jst+1),psnowgran1(jj,jst), &
4106  psnowgran2(jj,jst+1),psnowgran2(jj,jst), &
4107  hsnowmetamo)
4108  !
4109  IF ( zdiftype_inf+zcritsize_inf<zpenalty ) THEN
4110  zpenalty = zdiftype_inf + zcritsize_inf
4111  jj_a_agreg_sup = jst
4112  jj_a_agreg_inf = jst + 1
4113  ENDIF
4114  ENDIF
4115  !
4116  ENDIF
4117  !
4118  ENDDO
4119  !
4120  ! agregation of the similar layers and shift of upper layers
4121  psnowdzn(jj,jj_a_agreg_inf) = psnowdz(jj,jj_a_agreg_inf) + psnowdz(jj,jj_a_agreg_sup)
4122  DO jst = jj_a_agreg_sup,2,-1
4123  psnowdzn(jj,jst) = psnowdz(jj,jst-1)
4124  ENDDO
4125  psnowdzn(jj,1) = psnowdzf(jj)
4126  !
4127  ! Limit the ratio between the new layer and the one beneath (ratio 1/10)
4128  ! [NEW : 11/2012]
4129  IF( psnowdzn(jj,1)<xratio_newlayer*psnowdzn(jj,2) ) THEN
4130  zsnow2l = psnowdzn(jj,1) + psnowdzn(jj,2)
4131  psnowdzn(jj,1) = xratio_newlayer * zsnow2l
4132  psnowdzn(jj,2) = (1.-xratio_newlayer) * zsnow2l
4133  ENDIF
4134  !
4135  ENDIF
4136  !
4137  ENDIF ! end of the case with fresh snow
4138  !
4139 ENDDO ! end loop grid points
4140 !
4141 ! cases with no fresh snow and no previous grid resize
4142 !
4143 IF ( inlvlsmin==inlvlsmax ) THEN ! specific case with INLSVSMIN = INLVLSMAX (INLVLS)
4144  !
4145  ! check if surface layer depth is too small
4146  ! in such a case looks for an other layer to be split
4147  DO jj = 1,SIZE(psnow(:)) ! loop grid points
4148  !
4149  IF ( .NOT.omodif_grid(jj) .AND. psnowdz(jj,1)<xdzmin_top ) THEN
4150  omodif_grid(jj) = .true.
4151  CALL get_snowdzn_deb(inlvls,psnowdz(jj,:),zdzopt(jj,:),psnowdzn(jj,:))
4152  gagreg_surf(jj) = .true.
4153  ENDIF
4154  ! check if bottom layer depth is too small
4155  ! in such a case agregation with upper layer and
4156  ! looks for an other layer to be splitted
4157  IF( .NOT.omodif_grid(jj) .AND. psnowdz(jj,inlvls)<xdzmin_top ) THEN
4158  omodif_grid(jj) = .true.
4159  CALL get_snowdzn_end(inlvls,psnowdz(jj,:),zdzopt(jj,:),psnowdzn(jj,:))
4160  ENDIF
4161  !
4162  ENDDO ! end grid points loop
4163  !
4164 ENDIF ! end specific case INLSVSMIN = INLVLSMAX
4165 !
4166 ! case without new snowfall and INVLS > INLVLSMIN
4167 !
4168 DO jj=1,SIZE(psnow(:))
4169  !
4170  ! check if surface layer depth is too small
4171  ! in such a case agregation with layer beneath
4172  ! in case of reaching INLVLSMIN, looks for an other layer to be splitted
4173  IF( .NOT.gsnowfall(jj) .AND. psnow(jj)>xsnowcritd .AND. &
4174  .NOT.omodif_grid(jj) .AND. psnowdz(jj,1)<xdzmin_top_bis ) THEN ! case shallow surface layer
4175  !
4176  omodif_grid(jj) = .true.
4177  !
4178  IF( knlvls_use(jj)>inlvlsmin ) THEN ! case minimum not reached
4179  knlvls_use(jj) = knlvls_use(jj) - 1
4180  psnowdzn(jj,1) = psnowdz(jj,1) + psnowdz(jj,2)
4181  DO jst = 2,knlvls_use(jj)
4182  psnowdzn(jj,jst) = psnowdz(jj,jst+1)
4183  ENDDO
4184  ELSE ! case minimum reached
4185  CALL get_snowdzn_deb(knlvls_use(jj),psnowdz(jj,:),zdzopt(jj,:),psnowdzn(jj,:))
4186  ENDIF ! end case minimum reached end case shallow surface layer
4187  !
4188  gagreg_surf(jj) = .true.
4189  !
4190  ENDIF
4191  !
4192  ! check if bottom layer depth is too small
4193  ! in such a case agregation with above layer
4194  ! in case of reaching INLVLSMIN, looks for an other layer to be splitted
4195  ! case shallow bottom layer
4196  IF( .NOT.gsnowfall(jj) .AND. psnow(jj)> xsnowcritd .AND. &
4197  .NOT.omodif_grid(jj) .AND. psnowdz(jj,knlvls_use(jj))<xdzmin_top .AND. &
4198  .NOT.gagreg_surf(jj) ) THEN
4199  !
4200  omodif_grid(jj) = .true.
4201  !
4202  IF ( knlvls_use(jj)>inlvlsmin ) THEN ! case minimum not reached
4203  knlvls_use(jj) = knlvls_use(jj) - 1
4204  psnowdzn(jj,knlvls_use(jj)) = psnowdz(jj,knlvls_use(jj)) + psnowdz(jj,knlvls_use(jj)+1)
4205  ELSE ! case minimum reached
4206  CALL get_snowdzn_end(knlvls_use(jj),psnowdz(jj,:),zdzopt(jj,:),psnowdzn(jj,:))
4207  ENDIF ! end case minimum reached end case shallow surface layer
4208  !
4209  ENDIF
4210  !
4211 ENDDO ! end grid points loop
4212 !
4213 ! case whithout new snow fall and without a previous grid resize
4214 ! looks for a shallow layer to be splitted according to its depth and to
4215 ! the optimal grid size
4216 DO jj = 1,SIZE(psnow(:))
4217  !
4218  IF ( .NOT.omodif_grid(jj) .AND. inlvls_use(jj)<inlvls-3 )THEN
4219  !
4220  DO jst = 1,inlvls-4
4221  !
4222  IF ( jst<=knlvls_use(jj) .AND. .NOT.omodif_grid(jj) ) THEN
4223  !
4224  IF( psnowdz(jj,jst) > &
4225  ( xsplit_coef - float( inlvls-knlvls_use(jj) )/max( 1., float( inlvls-inlvlsmin ) ) ) &
4226  * zdzopt(jj,jst) ) THEN
4227  !
4228  DO jst_1 = knlvls_use(jj)+1,jst+2,-1
4229  psnowdzn(jj,jst_1) = psnowdz(jj,jst_1-1)
4230  zdzopt(jj,jst_1) = zdzopt(jj,jst_1-1)
4231  ENDDO
4232  !
4233  ! generale case : old layer divided in two equal layers
4234  IF ( jst/=1 .OR. psnowdz(jj,jst)<3.*zdzopt(jj,1) ) THEN
4235  psnowdzn(jj,jst+1) = 0.5*psnowdz(jj,jst)
4236  psnowdzn(jj,jst) = psnowdzn(jj,jst+1)
4237  ELSE
4238  ! if thick surface layer : force the surface layer to this value to avoid successive resizing
4239  ! [NEW : 11/2012]
4240  psnowdzn(jj,1) = 1.5 * zdzopt(jj,1)
4241  psnowdzn(jj,2) = psnowdz(jj,jst) - psnowdzn(jj,1)
4242  ENDIF
4243  !
4244  knlvls_use(jj) = knlvls_use(jj) + 1
4245  omodif_grid(jj) = .true.
4246  !
4247  ENDIF
4248  !
4249  ENDIF
4250  !
4251  ENDDO
4252  !
4253  ENDIF
4254  !
4255 ENDDO
4256 !
4257 ! case whithout new snow fall and without a previous grid resize
4258 ! looks for a deep layer to be agregated to the layer beneath if similar
4259 ! according to its depth and to the optimal grid size
4260 !
4261 !NB : allow these changes for 5 layers and more [NEW] (before : 6 layers)
4262 !
4263 DO jj = 1,SIZE(psnow(:))
4264  !
4265  IF ( .NOT.omodif_grid(jj) ) THEN
4266  !
4267  DO jst = 2,inlvls
4268  !
4269  IF ( jst<=knlvls_use(jj)-1 .AND. knlvls_use(jj)>inlvlsmin+1 .AND. .NOT.omodif_grid(jj) ) THEN
4270  !
4271  zdiftype_inf = snow3ldiftyp( psnowgran1(jj,jst+1),psnowgran1(jj, jst), &
4272  psnowgran2(jj,jst+1),psnowgran2(jj, jst), &
4273  hsnowmetamo)
4274  zdiftype_inf = max( xdiff_1, min( xdiff_max, zdiftype_inf ) )
4275  !
4276  IF( psnowdz(jj,jst) < zdzopt(jj,jst) * xagreg_coef_1 / zdiftype_inf .AND. &
4277  psnowdz(jj,jst) + psnowdz(jj,jst+1) < &
4278  xagreg_coef_2 * max( zdzopt(jj,jst),zdzopt(jj,jst+1) ) ) THEN
4279  !
4280  psnowdzn(jj,jst) = psnowdz(jj,jst) + psnowdz(jj,jst+1)
4281  zdzopt(jj,jst) = zdzopt(jj,jst+1)
4282  DO jst_1 = jst+1,knlvls_use(jj)-1
4283  psnowdzn(jj,jst_1) = psnowdz(jj,jst_1+1)
4284  zdzopt(jj,jst_1) = zdzopt(jj,jst_1+1)
4285  ENDDO
4286  knlvls_use(jj) = knlvls_use(jj)-1
4287  omodif_grid(jj)=.true.
4288  !
4289  ENDIF
4290  !
4291  ENDIF
4292  !
4293  ENDDO
4294  !
4295  ENDIF
4296  !
4297 ENDDO
4298 !
4299 ! [NEW : 11/2012]
4300 ! In case of very low snow fall checks if a new internal snow layer is too shallow
4301 ! even if a the grid has already been resized in this time step
4302 ! starts from bottom to INLVS_USE-3 until old and new grid differ
4303 DO jj = 1,SIZE(psnow(:))
4304  !
4305  IF ( .NOT.gsnowfall(jj) .OR. knlvls_use(jj)<inlvlsmin+3 ) cycle ! go to next point
4306  !
4307  IF( abs( psnowdzn(jj,knlvls_use(jj)) - psnowdz(jj,knlvls_use(jj)) ) > xuepsi ) cycle ! go to next point
4308  !
4309  ! bottom layer
4310  IF( psnowdzn(jj,knlvls_use(jj))<xdzmin_top ) THEN ! case shallow bottom layer
4311  !
4312  knlvls_use(jj) = knlvls_use(jj)-1
4313  psnowdzn(jj,knlvls_use(jj)) = psnowdzn(jj,knlvls_use(jj)) + psnowdzn(jj,knlvls_use(jj)+1)
4314  psnowdzn(jj,knlvls_use(jj)+1) = 0.
4315  !
4316  ELSE
4317  !
4318  ! internal layer
4319  DO jst = knlvls_use(jj)-1,4,-1
4320  !
4321  IF ( abs( psnowdzn(jj,jst) - psnowdz(jj,jst) ) > xuepsi ) EXIT ! old/new grid differ ==> go to next grid point
4322  !
4323  IF ( psnowdzn(jj,jst)> 0.001 ) cycle
4324  !
4325  ! If an internal layer is too shallow, it is merged with the upper layer
4326  psnowdzn(jj,jst-1) = psnowdzn(jj,jst) + psnowdzn(jj,jst-1)
4327  knlvls_use(jj) = knlvls_use(jj) - 1
4328  !
4329  ! shifts the lower layers
4330  DO jst_1 = jst,inlvls_use(jj)
4331  psnowdzn(jj,jst_1) = psnowdz(jj,jst_1+1)
4332  zdzopt(jj,jst_1) = zdzopt(jj,jst_1+1)
4333  ENDDO
4334  psnowdzn(jj,inlvls_use(jj)+1) = 0.
4335  !
4336  EXIT ! goto to next grid point
4337  !
4338  ENDDO ! end loop internal layers
4339  !
4340  ENDIF
4341  !
4342 ENDDO ! end grid loops for checking shallow layers
4343 !
4344 !final check of the consistensy of the new grid size
4345 !
4346 DO jj = 1,SIZE(psnow(:))
4347  !
4348  IF ( abs( sum( psnowdzn(jj,1:knlvls_use(jj)) ) - psnow(jj) ) > xuepsi ) THEN
4349  !
4350  WRITE(*,*) 'error in grid resizing', jj, knlvls_use(jj), sum( psnowdzn(jj,1:knlvls_use(jj)) ), &
4351  psnow(jj), sum( psnowdzn(jj,1:inlvls_use(jj)) )-psnow(jj), &
4352  zsnowfall(jj)
4353  WRITE( *,*) 'JJ , PSNOWDZ(JJ):',jj , psnowdz(jj,:)
4354  WRITE( *,*) 'JJ , PSNOWDZN(JJ):',jj , psnowdzn(jj,:)
4355  !
4356  CALL abor1_sfx("SNOWCRO: error in grid resizing")
4357  !
4358  ENDIF
4359  !
4360 ENDDO
4361 !
4362 IF (lhook) CALL dr_hook('SNOWNLFALL_UPGRID',1,zhook_handle)
4363 !
4364 END SUBROUTINE snownlfall_upgrid
4365 
4366 !###############################################################################
4367 SUBROUTINE get_snowdzn_deb(KNLVLS,PSNOWDZ,PDZOPT,PSNOWDZN)
4369 USE modd_snow_par, ONLY : xdzmin_top, xdzmin_bot
4370 !
4371 IMPLICIT NONE
4372 !
4373 INTEGER, INTENT(IN) :: KNLVLS
4374 REAL, DIMENSION(:), INTENT(IN) :: PSNOWDZ, PDZOPT
4375 REAL, DIMENSION(:), INTENT(OUT) :: PSNOWDZN
4376 !
4377 REAL :: ZPENALTY, ZCRITSIZE
4378 INTEGER :: JJ_A_DEDOUB, JST
4379 !
4380 REAL(KIND=JPRB) :: ZHOOK_HANDLE
4381 !
4382 IF (lhook) CALL dr_hook('SNOWCRO:GET_SNOWDZN_DEB',0,zhook_handle)
4383 !
4384 zpenalty = psnowdz(2) / pdzopt(2)
4385 IF( psnowdz(2)<xdzmin_top ) zpenalty = 0.
4386 jj_a_dedoub = 2
4387 !
4388 DO jst = 3,knlvls
4389  zcritsize = psnowdz(jst) / pdzopt(jst)
4390  IF ( jst==knlvls .AND. psnowdz(jst)<xdzmin_bot ) zcritsize = 0.
4391  IF ( zcritsize>zpenalty ) THEN
4392  zpenalty = zcritsize
4393  jj_a_dedoub = jst
4394  ENDIF
4395 ENDDO
4396 !
4397 IF ( jj_a_dedoub==2 ) THEN ! case splitted layer == 2
4398  psnowdzn(1) = 0.5 * ( psnowdz(1) + psnowdz(2) )
4399  psnowdzn(2) = psnowdzn(1)
4400 ELSE ! case splitted layer =/ 2
4401  psnowdzn(1) = psnowdz(1) + psnowdz(2)
4402  DO jst = 2,jj_a_dedoub-2
4403  psnowdzn(jst) = psnowdz(jst+1)
4404  ENDDO
4405  psnowdzn(jj_a_dedoub-1) = 0.5 * psnowdz(jj_a_dedoub)
4406  psnowdzn(jj_a_dedoub) = psnowdzn(jj_a_dedoub-1)
4407 ENDIF ! end case splitted layer =/ 2
4408 !
4409 IF (lhook) CALL dr_hook('SNOWCRO:GET_SNOWDZN_DEB',1,zhook_handle)
4410 !
4411 END SUBROUTINE get_snowdzn_deb
4412 !
4413 !###############################################################################
4414 SUBROUTINE get_snowdzn_end(KNLVLS,PSNOWDZ,PDZOPT,PSNOWDZN)
4416 USE modd_snow_par, ONLY : xdzmin_top, xdzmin_bot
4417 !
4418 IMPLICIT NONE
4419 !
4420 INTEGER, INTENT(IN) :: KNLVLS
4421 REAL, DIMENSION(:), INTENT(IN) :: PSNOWDZ, PDZOPT
4422 REAL, DIMENSION(:), INTENT(OUT) :: PSNOWDZN
4423 !
4424 REAL :: ZPENALTY, ZCRITSIZE
4425 INTEGER :: JJ_A_DEDOUB, JST
4426 !
4427 REAL(KIND=JPRB) :: ZHOOK_HANDLE
4428 !
4429 IF (lhook) CALL dr_hook('SNOWCRO:GET_SNOWDZN_END',0,zhook_handle)
4430 !
4431 zpenalty = psnowdz(knlvls-2) / pdzopt(knlvls-2)
4432 jj_a_dedoub = knlvls - 2
4433 !
4434 DO jst = max(1,knlvls-3),1,-1
4435  zcritsize = psnowdz(jst) / pdzopt(jst)
4436  IF ( jst==1 .AND. psnowdz(jst)<xdzmin_bot ) zcritsize = 0.
4437  IF ( zcritsize>zpenalty ) THEN
4438  zpenalty = zcritsize
4439  jj_a_dedoub = jst
4440  ENDIF
4441 ENDDO
4442 !
4443 IF ( jj_a_dedoub==knlvls-1 ) THEN ! case splitted layer == 2
4444  psnowdzn(knlvls) = 0.5 * (psnowdz(knlvls-1)+psnowdz(knlvls))
4445  psnowdzn(knlvls-1) = psnowdzn(knlvls)
4446 ELSE ! case splitted layer =/ 2
4447  psnowdzn(knlvls) = psnowdz(knlvls-1) + psnowdz(knlvls)
4448  DO jst = knlvls-1,jj_a_dedoub+2,-1
4449  psnowdzn(jst) = psnowdz(jst-1)
4450  ENDDO
4451  psnowdzn(jj_a_dedoub+1) = 0.5 * psnowdz(jj_a_dedoub)
4452  psnowdzn(jj_a_dedoub ) = psnowdzn(jj_a_dedoub+1)
4453 ENDIF ! end case splitted layer =/ 2
4454 !
4455 IF (lhook) CALL dr_hook('SNOWCRO:GET_SNOWDZN_END',1,zhook_handle)
4456 !
4457 END SUBROUTINE get_snowdzn_end
4458 !
4459 !###############################################################################
4460 !################################################################################
4461 !################################################################################
4462 !
4463 SUBROUTINE snownlgridfresh_1d (KJ,PSNOW,PSNOWDZ,PSNOWDZN, &
4464  PSNOWRHO,PSNOWHEAT,PSNOWGRAN1,PSNOWGRAN2, &
4465  PSNOWHIST,PSNOWAGE,GSNOWFALL, &
4466  PSNOWRHOF, PSNOWDZF,PSNOWHEATF,PSNOWGRAN1F, &
4467  PSNOWGRAN2F, PSNOWHISTF,PSNOWAGEF, &
4468  KNLVLS_USE, HSNOWMETAMO )
4469 !
4470 !! PURPOSE
4471 !! -------
4472 ! Snow mass,heat and characteristics redistibution in case of
4473 ! grid resizing. Total mass and heat content of the overall snowpack
4474 ! unchanged/conserved within this routine.
4475 ! Grain size and type of mixed layers is deduced from the conservation
4476 ! of the average optical size
4477 !
4478 !! AUTHOR
4479 !! ------
4480 !! E. Brun * Meteo-France *
4481 !!
4482 !
4483 USE modd_snow_par, ONLY : xd1,xd2,xd3,xx,xvalb5,xvalb6
4484 USE mode_snow3l, ONLY : get_mass_heat
4485 !
4486 IMPLICIT NONE
4487 !
4488 !
4489 !* 0.1 declarations of arguments
4490 !
4491 INTEGER, INTENT(IN) :: KJ
4492 REAL, INTENT(IN) :: PSNOW
4493 !
4494 REAL, DIMENSION(:), INTENT(INOUT) :: PSNOWHEAT, PSNOWRHO, PSNOWDZ, &
4495  PSNOWDZN, PSNOWGRAN1, PSNOWGRAN2, &
4496  PSNOWHIST
4497 REAL, DIMENSION(:), INTENT(INOUT) :: PSNOWAGE
4498 REAL, INTENT(IN) :: PSNOWRHOF, PSNOWDZF,PSNOWHEATF, &
4499  PSNOWGRAN1F,PSNOWGRAN2F, PSNOWHISTF
4500 REAL, INTENT(IN) :: PSNOWAGEF
4501 !
4502 INTEGER, INTENT(IN) :: KNLVLS_USE
4503 !
4504 LOGICAL, INTENT(IN) :: GSNOWFALL
4505 !
4506  CHARACTER(3),INTENT(IN) :: HSNOWMETAMO
4507 !
4508 !* 0.2 declarations of local variables
4509 !
4510 REAL, DIMENSION(SIZE(PSNOWRHO,1)+1) :: ZSNOWRHOO,ZSNOWGRAN1O,ZSNOWGRAN2O, &
4511  ZSNOWHEATO,ZSNOWHISTO,ZSNOWDZO, &
4512  ZSNOWZTOP_OLD,ZSNOWZBOT_OLD
4513 REAL,DIMENSION(SIZE(PSNOWRHO,1)+1) :: ZSNOWAGEO
4514 !
4515 REAL, DIMENSION(SIZE(PSNOWRHO,1)) :: ZSNOWRHON,ZSNOWGRAN1N,ZSNOWGRAN2N, &
4516  ZSNOWHEATN,ZSNOWHISTN, &
4517  ZSNOWZTOP_NEW,ZSNOWZBOT_NEW
4518 REAL,DIMENSION(SIZE(PSNOWRHO,1)) ::ZSNOWAGEN
4519 !
4520 REAL :: ZMASTOTN, ZMASTOTO, ZSNOWHEAN, ZSNOWHEAO
4521 REAL :: ZPSNOW_OLD, ZPSNOW_NEW
4522 !
4523 INTEGER :: INLVLS_OLD, INLVLS_NEW
4524 INTEGER :: JST
4525 !
4526 LOGICAL :: GDIAM
4527 !
4528 REAL(KIND=JPRB) :: ZHOOK_HANDLE
4529 !-------------------------------------------------------------------------------
4530 IF (lhook) CALL dr_hook('SNOWNLGRIDFRESH_1D',0,zhook_handle)
4531 !
4532 ! 0. Initialization:
4533 ! ------------------
4534 !
4535 ! starts by checking the consistency between both vertical grid sizes
4536 inlvls_new = knlvls_use
4537 inlvls_old = -1
4538 !
4539 zpsnow_new = 0.
4540 zpsnow_old = 0.
4541 !
4542 DO jst = 1,inlvls_new
4543  zpsnow_new = zpsnow_new + psnowdzn(jst)
4544 ENDDO
4545 !
4546 IF ( abs( zpsnow_new - psnowdzf )<xuepsi ) THEN
4547  inlvls_old = 0
4548 ELSE
4549  DO jst = 1,SIZE(psnowrho)
4550  IF ( psnowdz(jst)>=xuepsi ) THEN
4551  zpsnow_old = zpsnow_old + psnowdz(jst)
4552  IF ( abs( zpsnow_new - psnowdzf - zpsnow_old )<xuepsi ) THEN
4553  inlvls_old = jst
4554  ENDIF
4555  ENDIF
4556  ENDDO
4557  IF ( inlvls_old==-1 ) THEN
4558  WRITE(*,*)'pb INLVLS_OLD INLVLS_NEW=',inlvls_new
4559  WRITE(*,*)'pb INLVLS_OLD',psnowdzf
4560  WRITE(*,*)'pb INLVLS_OLD',psnowdzn
4561  WRITE(*,*)'pb INLVLS_OLD',psnowdz
4562  CALL abor1_sfx('SNOWCRO: Error INLVLS_OLD')
4563  ENDIF
4564 ENDIF
4565 !
4566 IF ( gsnowfall ) inlvls_old = inlvls_old + 1
4567 !
4568 zpsnow_old = psnow
4569 zpsnow_new = zpsnow_old
4570 !
4571 ! initialization of variables describing the initial snowpack + new snowfall
4572 !
4573 IF ( gsnowfall ) THEN
4574  DO jst = 2,inlvls_old
4575  zsnowdzo(jst) = psnowdz(jst-1)
4576  zsnowrhoo(jst) = psnowrho(jst-1)
4577  zsnowheato(jst) = psnowheat(jst-1)
4578  zsnowgran1o(jst) = psnowgran1(jst-1)
4579  zsnowgran2o(jst) = psnowgran2(jst-1)
4580  zsnowhisto(jst) = psnowhist(jst-1)
4581  zsnowageo(jst) = psnowage(jst-1)
4582  ENDDO
4583  zsnowdzo(1) = psnowdzf
4584  zsnowrhoo(1) = psnowrhof
4585  zsnowheato(1) = psnowheatf
4586  zsnowgran1o(1) = psnowgran1f
4587  zsnowgran2o(1) = psnowgran2f
4588  zsnowhisto(1) = psnowhistf
4589  zsnowageo(1) = psnowagef
4590 ELSE
4591  DO jst = 1,inlvls_old
4592  zsnowdzo(jst) = psnowdz(jst)
4593  zsnowrhoo(jst) = psnowrho(jst)
4594  zsnowheato(jst) = psnowheat(jst)
4595  zsnowgran1o(jst) = psnowgran1(jst)
4596  zsnowgran2o(jst) = psnowgran2(jst)
4597  zsnowhisto(jst) = psnowhist(jst)
4598  zsnowageo(jst) = psnowage(jst)
4599  ENDDO
4600 ENDIF
4601 !
4602 ! 1. Calculate vertical grid limits (m):
4603 ! --------------------------------------
4604 !
4605 zsnowztop_old(1) = zpsnow_old
4606 zsnowztop_new(1) = zpsnow_new
4607 !
4608 DO jst = 1,inlvls_old
4609  IF ( jst>1 ) zsnowztop_old(jst) = zsnowzbot_old(jst-1)
4610  zsnowzbot_old(jst) = zsnowztop_old(jst) - zsnowdzo(jst)
4611 ENDDO
4612 !
4613 DO jst = 1,inlvls_new
4614  IF ( jst>1 ) zsnowztop_new(jst) = zsnowzbot_new(jst-1)
4615  zsnowzbot_new(jst) = zsnowztop_new(jst) - psnowdzn(jst)
4616 ENDDO
4617 !
4618 ! Check consistency
4619 IF ( abs(zsnowzbot_old(inlvls_old)) > 0.00001 ) WRITE (*,*) 'Error bottom OLD'
4620 !
4621 zsnowzbot_old(inlvls_old) = 0.
4622 !
4623 ! Check consistency
4624 if ( abs(zsnowzbot_new(inlvls_new)) > 0.00001 ) WRITE (*,*) 'Error bottom NEW'
4625 !
4626 zsnowzbot_new(inlvls_new) = 0.
4627 !
4628 ! 3. Calculate mass, heat, charcateristics mixing due to vertical grid resizing:
4629 ! --------------------------------------------------------------------
4630 !
4631 ! loop over the new snow layers
4632 ! Summ or avergage of the constituting quantities of the old snow layers
4633 ! which are totally or partially inserted in the new snow layer
4634  CALL get_mass_heat(kj,inlvls_new,inlvls_old, &
4635  zsnowztop_old,zsnowztop_new,zsnowzbot_old,zsnowzbot_new, &
4636  zsnowrhoo,zsnowdzo,zsnowgran1o,zsnowgran2o,zsnowhisto, &
4637  zsnowageo,zsnowheato, &
4638  zsnowrhon,psnowdzn,zsnowgran1n,zsnowgran2n,zsnowhistn, &
4639  zsnowagen,zsnowheatn,hsnowmetamo )
4640 !
4641 ! check of consistency between new and old snowpacks
4642 zsnowhean = 0.
4643 zmastotn = 0.
4644 zsnowheao = 0.
4645 zmastoto = 0.
4646 zpsnow_new = 0.
4647 zpsnow_old = 0.
4648 !
4649 DO jst = 1,inlvls_new
4650  zsnowhean = zsnowhean + zsnowheatn(jst)
4651  zmastotn = zmastotn + zsnowrhon(jst) * psnowdzn(jst)
4652  zpsnow_new = zpsnow_new + psnowdzn(jst)
4653 ENDDO
4654 !
4655 DO jst = 1,inlvls_old
4656  zsnowheao = zsnowheao + zsnowheato(jst)
4657  zmastoto = zmastoto + zsnowrhoo(jst) * zsnowdzo(jst)
4658  zpsnow_old = zpsnow_old + zsnowdzo(jst)
4659 ENDDO
4660 !
4661 IF ( abs( zsnowhean-zsnowheao )>0.0001 .OR. abs( zmastotn-zmastoto )>0.0001 .OR. &
4662  abs( zpsnow_new-zpsnow_old )> 0.0001 ) THEN
4663  WRITE(*,*) 'Warning diff', zsnowhean-zsnowheao,zmastotn-zmastoto,zpsnow_new-zpsnow_old
4664 ENDIF
4665 !
4666 ! 5. Update mass (density and thickness) and heat:
4667 ! ------------------------------------------------
4668 !
4669 psnowdz(:) = psnowdzn(:)
4670 !
4671 psnowrho(:) = zsnowrhon(:)
4672 psnowheat(:) = zsnowheatn(:)
4673 psnowgran1(:) = zsnowgran1n(:)
4674 psnowgran2(:) = zsnowgran2n(:)
4675 psnowhist(:) = zsnowhistn(:)
4676 !
4677 psnowage(:) = zsnowagen(:)
4678 !
4679 IF (lhook) CALL dr_hook('SNOWNLGRIDFRESH_1D',1,zhook_handle)
4680 !
4681 END SUBROUTINE snownlgridfresh_1d
4682 !####################################################################
4683 !####################################################################
4684 !###################################################################
4685 SUBROUTINE snowdrift(PTSTEP,PVMOD,PSNOWRHO,PSNOWDZ,PSNOW, &
4686  PSNOWGRAN1,PSNOWGRAN2,PSNOWHIST,KNLVLS_USE, &
4687  PTA,PQA,PPS,PRHOA,PZ0EFF,PUREF, &
4688  OSNOWDRIFT_SUBLIM,HSNOWMETAMO,PSNDRIFT )
4690 !! PURPOSE
4691 !! -------
4692 ! Snow compaction and metamorphism due to drift
4693 ! Mass is unchanged: layer thickness is reduced
4694 ! in proportion to density increases. Method inspired from
4695 ! Brun et al. (1997) and Guyomarch
4696 !
4697 ! - computes a mobility index of each snow layer from its grains, density
4698 ! and history
4699 ! - computes a drift index of each layer from its mobility and wind speed
4700 ! - computes a transport index with an exponential decay taking into
4701 ! account its depth and the mobility of upper layers
4702 ! - increases density and changes grains in case of transport
4703 !
4704 ! HISTORY:
4705 ! Basic parameterization from Crocus/ARPEGE Coupling (1997)
4706 ! Implementation in V5
4707 ! Insertion in V6 of grains type evolution in case of dendritic snow (V.
4708 ! Vionnet)
4709 ! 07/2012 (for V7.3): E. Brun, M. Lafaysse : optional sublimation of drifted snow
4710 ! 2012-09-20 : bug correction : ZFF was not computed if LSNOWDRIFT_SUBLIM=FALSE.
4711 !
4712 ! 2014-02-05 V. Vionnet: systematic use of 5m wind speed to compute drift index
4713 ! 2014-06-03 M. Lafaysse: threshold on PZ0EFF
4714 
4715 USE modd_csts,ONLY : xtt
4716 USE mode_thermos
4717 
4718 USE modd_snow_par, ONLY : xvtime, xvromax, xvromin, xvmob1, &
4719  xvmob2, xvmob3, xvmob4, xvdrift1, xvdrift2, xvdrift3, &
4720  xvsizemin, xcoef_ff, xcoef_effect, xqs_ref
4721 !
4722 IMPLICIT NONE
4723 !
4724 !* 0.1 declarations of arguments
4725 !
4726 REAL, INTENT(IN) :: PTSTEP
4727 !
4728 REAL, DIMENSION(:), INTENT(IN) :: PTA, PQA, PPS, PRHOA
4729 !
4730 REAL, DIMENSION(:), INTENT(IN) :: PVMOD
4731 !
4732 INTEGER, DIMENSION(:), INTENT(IN) :: KNLVLS_USE
4733 !
4734 REAL, DIMENSION(:),INTENT(IN) :: PZ0EFF,PUREF
4735 !
4736 LOGICAL,INTENT(IN) :: OSNOWDRIFT_SUBLIM
4737 !
4738  CHARACTER(3), INTENT(IN) :: HSNOWMETAMO ! metamorphism scheme
4739 !
4740 REAL, DIMENSION(:,:), INTENT(INOUT) :: PSNOWRHO, PSNOWDZ,PSNOWGRAN1, &
4741  PSNOWGRAN2,PSNOWHIST
4742 REAL, DIMENSION(:), INTENT(OUT) :: PSNOW
4743 REAL, DIMENSION(:), INTENT(OUT) :: PSNDRIFT !blowing snow sublimation (kg/m2/s)
4744 !
4745 !* 0.2 declarations of local variables
4746 !
4747 REAL, DIMENSION(SIZE(PSNOWRHO,1),SIZE(PSNOWRHO,2)) :: ZSNOWRHO2
4748 REAL, DIMENSION(SIZE(PSNOWRHO,1) ) :: ZSNOWDZ1
4749 !
4750 REAL, DIMENSION(SIZE(PSNOWRHO,1)) :: ZQSATI, ZFF ! QS wrt ice, gust speed
4751 !
4752 REAL :: ZZ0EFF
4753 !
4754 REAL :: ZPROFEQU, ZRMOB, ZRDRIFT, ZRT, ZDRO, ZDGR1, ZDGR2
4755 REAL :: ZVT ! 5m wind speed threshold for surface
4756 !transport
4757 REAL :: ZQS_EFFECT ! effect of QS on snow
4758 REAL :: ZWIND_EFFECT ! effect of wind on snow
4759 REAL :: ZDRIFT_EFFECT ! effect of QS and wind on snow
4760 ! transformation
4761 REAL :: ZQS !Blowing snow sublimation (kg/m2/s)
4762 REAL :: ZRHI, ZFACT
4763 !
4764 INTEGER :: JJ,JST ! looping indexes
4765 !
4766 REAL(KIND=JPRB) :: ZHOOK_HANDLE
4767 !
4768 ! Reference height for wind speed used to dertermine the occurrence of blowing snow
4769 REAL, PARAMETER :: PPHREF_WIND=5.
4770 REAL, PARAMETER :: PPHREF_MIN=pphref_wind/2.
4771 !
4772 !-------------------------------------------------------------------------------
4773 IF (lhook) CALL dr_hook('SNOWDRIFT',0,zhook_handle)
4774 !
4775 ! 0. Initialization:
4776 ! ------------------
4777 !
4778 zsnowdz1(:) = psnowdz(:,1)
4779 !
4780 DO jj = 1,SIZE(psnow)
4781  DO jst = 1,knlvls_use(jj)
4782  zsnowrho2(jj,jst) = psnowrho(jj,jst)
4783  ENDDO
4784 ENDDO
4785 !
4786 IF ( osnowdrift_sublim ) THEN
4787  zqsati(:) = qsati( pta(:),pps(:) )
4788 END IF
4789 !
4790 ! 1. Computation of drift and induced settling and metamorphism
4791 ! ------------------
4792 !
4793 DO jj=1, SIZE(psnow)
4794  !
4795  ! gust speed at 5m above the snowpack
4796  ! Computed from PVMOD at PUREF (m) assuming a log profile in the SBL
4797  ! and a roughness length equal to PZ0EFF
4798  zz0eff=min(pz0eff(jj),puref(jj)*0.5,pphref_min)
4799  zff(jj) = xcoef_ff*pvmod(jj)*log(pphref_wind/zz0eff)/log(puref(jj)/zz0eff)
4800  !
4801  ! initialization decay coeff
4802  zprofequ = 0.
4803  !
4804  DO jst = 1,knlvls_use(jj)
4805  !
4806  zfact = 1.25 - 1.25 * ( max( psnowrho(jj,jst), xvromin ) - xvromin )/1000./xvmob1
4807  !
4808  IF ( hsnowmetamo=='B92' ) THEN
4809  !
4810  ! mobility index computation of a layer as a function of its properties
4811  IF( psnowgran1(jj,jst)<0. ) THEN
4812  ! dendritic case
4813  zrmob = 0.34 * ( 0.5 - ( 0.75*psnowgran1(jj,jst) + 0.5*psnowgran2(jj,jst) )/99. ) + &
4814  0.66 * zfact
4815  ELSE
4816  ! non dendritic case
4817  zrmob = 0.34 * ( xvmob2 - xvmob2*psnowgran1(jj,jst)/99. - xvmob3*psnowgran2(jj,jst)*1000. ) + &
4818  0.66 * zfact
4819  ENDIF
4820  !
4821  ELSE
4822  !
4823  IF ( psnowgran1(jj,jst)<xvdiam6*(4.-psnowgran2(jj,jst))-xuepsi ) THEN
4824  ! dendritic case
4825  zrmob = 0.34 * ( 0.5 + 0.75 * &
4826  ( psnowgran1(jj,jst)/xvdiam6-4.+psnowgran2(jj,jst) )/( psnowgran2(jj,jst)-3. ) &
4827  - 0.5 * psnowgran2(jj,jst) ) + &
4828  0.66 * zfact
4829  ELSE
4830  ! non dendritic case
4831  zrmob = 0.34 * ( xvmob2 - xvmob2 * psnowgran2(jj,jst) &
4832  - xvmob3 * (4.-psnowgran2(jj,jst))*xvdiam6*1000. ) + &
4833  0.66 * zfact
4834  ENDIF
4835  !
4836  ENDIF
4837  !
4838  ! correction in case of former wet snow
4839  IF ( psnowhist(jj,jst) >= 2. ) zrmob = min(zrmob, xvmob4)
4840  !
4841  ! computation of drift index supposing no overburden snow
4842  zrdrift = zrmob - ( xvdrift1 * exp( -xvdrift2*zff(jj) ) - 1.)
4843  ! modif_EB exit loop if there is no drift
4844  IF ( zrdrift<=0. ) EXIT
4845  !
4846  ! update the decay coeff by half the current layer
4847  zprofequ = zprofequ + 0.5 * psnowdz(jj,jst) * 0.1 * ( xvdrift3 - zrdrift )
4848  ! computation of the drift index inclunding the decay by overburden snow
4849  zrt = max( 0., zrdrift * exp( -zprofequ*100 ) )
4850  !
4851  IF ( osnowdrift_sublim .AND. jst==1 ) THEN
4852  !Specific case for blowing snow sublimation
4853  ! computation of wind speed threshold QSATI and RH withe respect to ice
4854  zvt = -log( (zrmob+1.)/xvdrift1 ) / xvdrift2
4855  zrhi = pqa(jj) / zqsati(jj)
4856  ! computation of sublimation rate according to Gordon's PhD
4857  zqs = 0.0018 * (xtt/pta(jj))**4 * zvt * prhoa(jj) * zqsati(jj) * &
4858  (1.-zrhi) * (zff(jj)/zvt)**3.6
4859  ! WRITE(*,*) 'surface Vt vent*coef ZRDRIFT ZRMOB :',ZVT,&
4860  ! ZFF(JJ),ZRDRIFT,ZRMOB
4861  ! WRITE(*,*) 'V>Vt ZQS :',ZQS
4862  ! surface depth decrease in case of blowing snow sublimation
4863  ! WRITE(*,*) 'V>Vt DSWE DZ Z:',- MAX(0.,ZQS)*PTSTEP/COEF_FF,
4864  ! - MAX(0.,ZQS)*PTSTEP/COEF_FF/PSNOWRHO(JJ,JST),PSNOWDZ(JJ,JST)
4865  ! 2 lignes ci-dessous a valider pour avoir sublim drift
4866  psnowdz(jj,jst) = max( 0.5*psnowdz(jj,jst), &
4867  psnowdz(jj,jst) - max(0.,zqs) * ptstep/xcoef_ff/psnowrho(jj,jst) )
4868  psndrift(jj) = (zsnowdz1(jj)-psnowdz(jj,jst))*psnowrho(jj,jst)/ptstep
4869  ELSE
4870  zqs = 0.
4871  END IF
4872  !
4873  zqs_effect = min( 3., max( 0.,zqs )/xqs_ref ) * zrt
4874  zwind_effect = xcoef_effect * zrt
4875  zdrift_effect = ( zqs_effect + zwind_effect ) * ptstep / xcoef_ff / xvtime
4876  ! WRITE(*,*) 'ZQS_EFFECT,ZWIND_EFFECT,ZDRIFT_EFFECT:',ZQS_EFFECT,ZWIND_EFFECT,ZDRIFT_EFFECT
4877  !
4878  ! settling by wind transport only in case of not too dense snow
4879  IF( psnowrho(jj,jst) < xvromax ) THEN
4880  zdro = zdrift_effect * ( xvromax - psnowrho(jj,jst) )
4881  psnowrho(jj,jst) = min( xvromax , psnowrho(jj,jst) + zdro )
4882  psnowdz(jj,jst) = psnowdz(jj,jst) * zsnowrho2(jj,jst) / psnowrho(jj,jst)
4883  ENDIF
4884  !
4885  IF ( hsnowmetamo=='B92' ) THEN
4886  !
4887  ! metamorphism induced by snow drift
4888  IF ( psnowgran1(jj,jst)<0. ) THEN
4889  ! dendritic case
4890  zdgr1 = zdrift_effect * ( -psnowgran1(jj,jst) ) * 0.5
4891  psnowgran1(jj,jst) = psnowgran1(jj,jst) + min( zdgr1, -0.99 * psnowgran1(jj,jst) )
4892  ! modif_VV_140910
4893  zdgr2 = zdrift_effect * ( 99. - psnowgran2(jj,jst) )
4894  psnowgran2(jj,jst) = min( 99., psnowgran2(jj,jst) + zdgr2 )
4895  ! fin modif_VV_140910
4896  ELSE
4897  ! non dendritic case
4898  zdgr1 = zdrift_effect * ( 99. - psnowgran1(jj,jst) )
4899  zdgr2 = zdrift_effect * 5. / 10000.
4900  psnowgran1(jj,jst) = min( 99., psnowgran1(jj,jst) + zdgr1 )
4901  psnowgran2(jj,jst) = max( xvsizemin, psnowgran2(jj,jst) - zdgr2 )
4902  ENDIF
4903  !
4904  ELSE
4905  !
4906  ! dendritic case
4907  IF ( psnowgran1(jj,jst)<xvdiam6*(4.-psnowgran2(jj,jst))-xuepsi ) THEN
4908  !
4909  zdgr1 = min( zdrift_effect * ( ( psnowgran1(jj,jst)/xvdiam6-4.+psnowgran2(jj,jst) )/ &
4910  (psnowgran2(jj,jst)-3.) ) * 0.5, &
4911  0.99 * ( ( psnowgran1(jj,jst)/xvdiam6-4.+ psnowgran2(jj,jst))/ &
4912  (psnowgran2(jj,jst)-3.) ) )
4913  zdgr2 = zdrift_effect * ( 1.-psnowgran2(jj,jst) )
4914  !
4915  psnowgran1(jj,jst) = psnowgran1(jj,jst) + xvdiam6 * &
4916  ( zdgr2 * ( (psnowgran1(jj,jst)/xvdiam6-1.)/(psnowgran2(jj,jst)-3.) ) - &
4917  zdgr1 * ( psnowgran2(jj,jst)-3. ) )
4918  psnowgran2(jj,jst) = min(1.,psnowgran2(jj,jst)+zdgr2)
4919  ! non dendritic case
4920  ELSE
4921  !
4922  zdgr1 = zdrift_effect * 5./10000.
4923  zdgr2 = zdrift_effect * (1.-psnowgran2(jj,jst))
4924  !
4925  psnowgran1(jj,jst) = psnowgran1(jj,jst) - 2. * xvdiam6 * psnowgran2(jj,jst) * zdgr2
4926  psnowgran2(jj,jst) = min( 1., psnowgran2(jj,jst)+zdgr2 )
4927  !
4928  ENDIF
4929  !
4930  ENDIF
4931  !
4932  ! update the decay coeff by half the current layer
4933  zprofequ = zprofequ + 0.5 * psnowdz(jj,jst) * 0.1 * ( xvdrift3 - zrdrift )
4934  !
4935  ENDDO ! snow layers loop
4936  !
4937 ENDDO ! grid points loop
4938 !
4939 ! 2. Update total snow depth:
4940 ! -----------------------------------------------
4941 !
4942 ! Compaction of total snowpack depth
4943 !
4944 DO jj = 1,SIZE(psnowdz,1)
4945  psnow(jj) = sum( psnowdz(jj,1:knlvls_use(jj)) )
4946 ENDDO
4947 !
4948 IF (lhook) CALL dr_hook('SNOWDRIFT',1,zhook_handle)
4949 !
4950 END SUBROUTINE snowdrift
4951 !####################################################################
4952 !###################################################################
4953 !####################################################################
4954 !####################################################################
4955 SUBROUTINE snowcrolayer_gone(PTSTEP,PSCAP,PSNOWTEMP,PSNOWDZ, &
4956  PSNOWRHO,PSNOWLIQ,PSNOWGRAN1,PSNOWGRAN2, &
4957  PSNOWHIST,PSNOWAGE,PLES3L,KNLVLS_USE )
4959 !
4960 !! PURPOSE
4961 ! Account for the case when one or several snow layers melt
4962 ! during a time step:
4963 ! in that case, merge these layers with the underlying layer
4964 ! except for the bottom layer which is merged to the abovelying layer
4965 ! energy and mass are conserved
4966 ! a new merged layer keeps the grain, histo and age properties of the
4967 ! non-melted layer
4968 !
4969 USE modd_csts,ONLY : xtt, xlmtt, xrholw, xrholi, xlvtt, xci
4970 !
4971 USE mode_snow3l
4972 !
4973 IMPLICIT NONE
4974 !
4975 !* 0.1 declarations of arguments
4976 !
4977 REAL, INTENT(IN) :: PTSTEP
4978 !
4979 REAL, DIMENSION(:,:), INTENT(INOUT) :: PSCAP
4980 !
4981 REAL, DIMENSION(:,:), INTENT(INOUT) :: PSNOWDZ, PSNOWTEMP, PSNOWRHO, PSNOWLIQ
4982 REAL, DIMENSION(:,:), INTENT(INOUT) :: PSNOWGRAN1,PSNOWGRAN2,PSNOWHIST,PSNOWAGE
4983 !
4984 INTEGER, DIMENSION(:), INTENT(INOUT) :: KNLVLS_USE !
4985 !
4986 REAL, DIMENSION(:), INTENT(IN) :: PLES3L
4987 !
4988 !* 0.2 declarations of local variables
4989 !
4990 REAL :: ZHEAT, ZMASS, ZDZ, ZLIQ, ZSNOWLWE
4991 !
4992 INTEGER :: JJ,JST,JST_1, JST_2, JST_MAX, IDIFF_LAYER ! loop counter
4993 INTEGER :: ID_1, ID_2
4994 !
4995 REAL(KIND=JPRB) :: ZHOOK_HANDLE
4996 !-------------------------------------------------------------------------------
4997 !
4998 IF (lhook) CALL dr_hook('SNOWCROLAYER_GONE',0,zhook_handle)
4999 !
5000 DO jj=1,SIZE(psnowrho,1) ! loop on gridpoints
5001  !
5002  jst_max = knlvls_use(jj)
5003  !
5004  idiff_layer = 0 ! used as shift counter of previously melted layers
5005  !
5006  DO jst_1 = jst_max,1-jst_max,-1 ! loop on 2 x layers in case of multi melt
5007  !
5008  jst = jst_1 + idiff_layer
5009  !
5010  ! Merge is possible only in case of 2 active layers or more
5011  IF ( jst>=1 .AND. knlvls_use(jj)>1 ) THEN
5012  !
5013  ! Total Liquid equivalent water content of snow (m):
5014  zsnowlwe = psnowrho(jj,jst) * psnowdz(jj,jst) / xrholw
5015  !
5016  ! Consideration of sublimation if any
5017  IF ( jst==1 ) zsnowlwe = zsnowlwe - max( 0., ples3l(jj)*ptstep/(xlstt*xrholw) )
5018  !
5019  ! Test if avalaible energy exceeds total latent heat
5020  IF ( pscap(jj,jst) * max( 0.0, psnowtemp(jj,jst)-xtt ) * psnowdz(jj,jst) >= &
5021  ( ( zsnowlwe-psnowliq(jj,jst) ) * xlmtt * xrholw ) - xuepsi ) THEN
5022  !
5023  IF ( jst==knlvls_use(jj) ) THEN
5024  id_1 = jst-1
5025  id_2 = jst
5026  ELSE
5027  id_1 = jst
5028  id_2 = jst + 1
5029  ENDIF
5030  !
5031  ! Case of a total melt of the bottom layer: merge with above layer
5032  ! which keeps its grain, histo and age properties
5033  zheat = 0.
5034  zmass = 0.
5035  zdz = 0.
5036  zliq = 0.
5037  DO jst_2 = id_1,id_2
5038  zheat = zheat + &
5039  psnowdz(jj,jst_2) * &
5040  ( pscap(jj,jst_2)*( psnowtemp(jj,jst_2)-xtt ) - xlmtt*psnowrho(jj,jst_2) ) + &
5041  xlmtt * xrholw * psnowliq(jj,jst_2)
5042  zmass = zmass + psnowdz(jj,jst_2) * psnowrho(jj,jst_2)
5043  zdz = zdz + psnowdz(jj,jst_2)
5044  zliq = zliq + psnowliq(jj,jst_2)
5045  ENDDO
5046  !
5047  psnowdz(jj,id_1) = zdz
5048  psnowrho(jj,id_1) = zmass / zdz
5049  psnowliq(jj,id_1) = zliq
5050  !
5051  ! Temperature of the merged layer is deduced from the heat content
5052  pscap(jj,id_1) = ( psnowrho(jj,id_1) - &
5053  psnowliq(jj,id_1) * xrholw / &
5054  max( psnowdz(jj,id_1),xsnowdzmin ) ) * xci
5055  psnowtemp(jj,id_1) = xtt + &
5056  ( ( ( ( zheat - xlmtt*xrholw*psnowliq(jj,id_1) ) / psnowdz(jj,id_1) ) + &
5057  xlmtt*psnowrho(jj,id_1) ) &
5058  / pscap(jj,id_1) )
5059  !
5060  IF( jst/=knlvls_use(jj) ) THEN
5061  !
5062  psnowgran1(jj,jst) = psnowgran1(jj,jst+1)
5063  psnowgran2(jj,jst) = psnowgran2(jj,jst+1)
5064  psnowhist(jj,jst) = psnowhist(jj,jst+1)
5065  psnowage(jj,jst) = psnowage(jj,jst+1)
5066  !
5067  ! Shift the above layers
5068  DO jst_2 = jst+1,knlvls_use(jj)-1
5069  psnowtemp(jj,jst_2) = psnowtemp(jj,jst_2+1)
5070  pscap(jj,jst_2) = pscap(jj,jst_2+1)
5071  psnowdz(jj,jst_2) = psnowdz(jj,jst_2+1)
5072  psnowrho(jj,jst_2) = psnowrho(jj,jst_2+1)
5073  psnowliq(jj,jst_2) = psnowliq(jj,jst_2+1)
5074  psnowgran1(jj,jst_2) = psnowgran1(jj,jst_2+1)
5075  psnowgran2(jj,jst_2) = psnowgran2(jj,jst_2+1)
5076  psnowhist(jj,jst_2) = psnowhist(jj,jst_2+1)
5077  psnowage(jj,jst_2) = psnowage(jj,jst_2+1)
5078  ENDDO ! loop JST_2
5079  !
5080  ! Update the shift counter IDIFF_LAYER
5081  idiff_layer = idiff_layer + 1
5082  !
5083  ENDIF ! end test of bottom layer
5084  !
5085  ! Decrease the number of active snow layers
5086  knlvls_use(jj) = knlvls_use(jj) - 1
5087  !
5088  ENDIF ! end test on availibility of energy
5089  !
5090  ENDIF ! end test on the number of remaining active layers
5091  !
5092  ENDDO ! end loop on the snow layers
5093  !
5094 ENDDO ! end loop gridpoints
5095 !
5096 IF (lhook) CALL dr_hook('SNOWCROLAYER_GONE',1,zhook_handle)
5097 !
5098 END SUBROUTINE snowcrolayer_gone
5099 !####################################################################
5100 !###################################################################
5101 !####################################################################
5102 !###################################################################
5103 SUBROUTINE snowcroprintprofile(HINFO,KLAYERS,OPRINTGRAN,PSNOWDZ,PSNOWRHO, &
5104  PSNOWTEMP,PSNOWLIQ,PSNOWHEAT,PSNOWGRAN1, &
5105  PSNOWGRAN2,PSNOWHIST,PSNOWAGE,HSNOWMETAMO )
5106 !
5107 ! Matthieu Lafaysse 08/06/2012
5108 ! This routine prints the snow profile of a given point for debugging
5109 !
5110 !to compute SSA
5111 USE modd_csts, ONLY : xrholi
5112 USE modd_snow_par, ONLY : xd1, xd2, xd3, xx
5113 !
5114 IMPLICIT NONE
5115 !
5116  CHARACTER(*), INTENT(IN) :: HINFO
5117 LOGICAL, INTENT(IN) :: OPRINTGRAN
5118 INTEGER, INTENT(IN) :: KLAYERS
5119 REAL, DIMENSION(:), INTENT(IN) :: PSNOWDZ,PSNOWRHO,PSNOWTEMP,PSNOWLIQ, &
5120  PSNOWHEAT,PSNOWGRAN1,PSNOWGRAN2, &
5121  PSNOWHIST,PSNOWAGE
5122  CHARACTER(3), INTENT(IN) :: HSNOWMETAMO
5123 !
5124 REAL, DIMENSION(KLAYERS) :: ZSNOWSSA
5125 REAL :: ZDIAM
5126 !
5127 INTEGER :: JST
5128 !
5129 REAL(KIND=JPRB) :: ZHOOK_HANDLE
5130 !
5131 IF (lhook) CALL dr_hook('SNOWCROPRINTPROFILE',0,zhook_handle)
5132 !
5133 WRITE(*,*)
5134 WRITE(*,*)trim(hinfo)
5135 !
5136 IF (oprintgran) THEN
5137  !
5138  ! Compute SSA from SNOWGRAN1 and SNOWGRAN2
5139  IF ( hsnowmetamo=='B92' ) THEN
5140  !
5141  DO jst = 1,klayers
5142  !
5143  IF ( psnowgran1(jst)<0. ) THEN
5144  zdiam = -psnowgran1(jst)*xd1/xx + (1.+psnowgran1(jst)/xx) * &
5145  ( psnowgran2(jst)*xd2/xx + (1.-psnowgran2(jst)/xx) * xd3 )
5146  zdiam = zdiam/10000.
5147  ELSE
5148  zdiam = psnowgran2(jst)*psnowgran1(jst)/xx + &
5149  max( 0.0004, 0.5*psnowgran2(jst) ) * ( 1.-psnowgran1(jst)/xx )
5150  ENDIF
5151  zsnowssa(jst) = 6. / (xrholi*zdiam)
5152  !
5153  END DO
5154  !
5155  ELSE
5156  !
5157  zsnowssa = 6. / (xrholi*psnowgran1)
5158  !
5159  ENDIF
5160  !
5161  WRITE(*,'(9(A12,"|"))')"-------------","-------------","-------------",&
5162  "-------------","-------------","-------------","-------------",&
5163  "-------------","-------------"
5164  WRITE(*,'(9(A12,"|"))')"PSNOWDZ","PSNOWRHO","PSNOWTEMP","PSNOWLIQ","PSNOWHEAT",&
5165  "PSNOWGRAN1","PSNOWGRAN2","PSNOWHIST","PSNOWAGE"
5166  WRITE(*,'(9(A12,"|"))')"-------------","-------------","-------------",&
5167  "-------------","-------------","-------------","-------------",&
5168  "-------------","-------------"
5169  DO jst = 1,klayers
5170  WRITE(*,'(9(ES12.3,"|")," L",I2.2)') psnowdz(jst),psnowrho(jst),psnowtemp(jst), &
5171  psnowliq(jst),psnowheat(jst),psnowgran1(jst), &
5172  psnowgran2(jst),psnowhist(jst),psnowage(jst),jst
5173  ENDDO
5174  WRITE(*,'(9(A12,"|"))')"-------------","-------------","-------------",&
5175  "-------------","-------------","-------------","-------------",&
5176  "-------------","-------------"
5177  !
5178 ELSE
5179  !
5180  WRITE(*,'(5(A12,"|"))')"------------","------------","------------",&
5181  "------------","------------"
5182  WRITE(*,'(5(A12,"|"))')"PSNOWDZ","PSNOWRHO","PSNOWTEMP","PSNOWLIQ","PSNOWHEAT"
5183  WRITE(*,'(5(A12,"|"))')"------------","------------","------------",&
5184  "------------","------------"
5185  DO jst = 1,klayers
5186  WRITE(*,'(5(ES12.3,"|")," L",I2.2)') psnowdz(jst),psnowrho(jst),psnowtemp(jst),&
5187  psnowliq(jst),psnowheat(jst),jst
5188  ENDDO
5189  WRITE(*,'(5(A12,"|"))')"------------","------------","------------",&
5190  "------------","------------"
5191  !
5192 END IF
5193 !
5194 WRITE(*,*)
5195 !
5196 IF (lhook) CALL dr_hook('SNOWCROPRINTPROFILE',1,zhook_handle)
5197 !
5198 END SUBROUTINE snowcroprintprofile
5199 !####################################################################
5200 !###################################################################
5201 SUBROUTINE snowcroprintatm(CINFO,PTA,PQA,PVMOD,PRR,PSR,PSW_RAD,PLW_RAD, &
5202  PTG, PSOILCOND,PD_G,PPSN3L )
5203 
5204 ! Matthieu Lafaysse 08/06/2012
5205 ! This routine prints the atmospheric forcing of a given point for debugging
5206 ! and ground data
5207 
5208 IMPLICIT NONE
5209 
5210  CHARACTER(*), INTENT(IN) :: CINFO
5211 REAL, INTENT(IN) :: PTA,PQA,PVMOD,PRR,PSR,PSW_RAD,PLW_RAD
5212 REAL, INTENT(IN) :: PTG, PSOILCOND, PD_G, PPSN3L
5213 !
5214 INTEGER :: JST
5215 !
5216 REAL(KIND=JPRB) :: ZHOOK_HANDLE
5217 !
5218 IF (lhook) CALL dr_hook('SNOWCROPRINTATM',0,zhook_handle)
5219 !
5220  CALL snowcroprintdate()
5221 !
5222 WRITE(*,*)
5223 WRITE(*,*)trim(cinfo)
5224 WRITE(*,'(4(A12,"|"))')"------------","------------","------------",&
5225 "------------"
5226 WRITE(*,'(4(A12,"|"))')"PTA","PQA","PRR","PSR"
5227 WRITE(*,'(4(A12,"|"))')"------------","------------","------------",&
5228 "------------"
5229 WRITE(*,'(4(ES12.3,"|")," meteo1")')pta,pqa,prr,psr
5230 WRITE(*,'(4(A12,"|"))')"------------","------------","------------",&
5231 "------------"
5232 WRITE(*,'(3(A12,"|"))')"------------","------------","------------"
5233 WRITE(*,'(3(A12,"|"))')"PSW_RAD","PLW_RAD","PVMOD"
5234 WRITE(*,'(3(A12,"|"))')"------------","------------","------------"
5235 WRITE(*,'(3(ES12.3,"|")," meteo2")')psw_rad,plw_rad,pvmod
5236 WRITE(*,'(3(A12,"|"))')"------------","------------","------------"
5237 WRITE(*,*)
5238 WRITE(*,*)"Ground :"
5239 WRITE(*,'(4(A12,"|"))')"------------","------------","------------",&
5240 "------------"
5241 WRITE(*,'(4(A12,"|"))')"PTG","PSOILCOND","PD_G","PPSN3L"
5242 WRITE(*,'(4(A12,"|"))')"------------","------------","------------",&
5243 "------------"
5244 WRITE(*,'(4(ES12.3,"|")," soil")')ptg,psoilcond,pd_g,ppsn3l
5245 WRITE(*,'(4(A12,"|"))')"------------","------------","------------",&
5246 "------------"
5247 !
5248 IF (lhook) CALL dr_hook('SNOWCROPRINTATM',1,zhook_handle)
5249 !
5250 END SUBROUTINE snowcroprintatm
5251 !
5252 !####################################################################
5253 SUBROUTINE snowcrostopbalance(PMASSBALANCE,PENERGYBALANCE)
5256 !
5257 USE modi_abor1_sfx
5258 !
5259 ! stop if energy and mass balances are not closed
5260 !
5261 IMPLICIT NONE
5262 !
5263 REAL , DIMENSION(:), INTENT(IN) :: PMASSBALANCE, PENERGYBALANCE
5264 !
5265 REAL,DIMENSION(SIZE(PSR)) :: ZMASSBALANCE,ZENERGYBALANCE
5266 !
5267 REAL(KIND=JPRB) :: ZHOOK_HANDLE
5268 !
5269 IF (lhook) CALL dr_hook('SNOWCROSTOPBALANCE',0,zhook_handle)
5270 !
5271 IF ( any( pmassbalance > xwarning_massbalance ) ) &
5272  CALL abor1_sfx("SNOWCRO: WARNING MASS BALANCE !")
5273 IF ( any( penergybalance > xwarning_energybalance ) ) &
5274  CALL abor1_sfx("SNOWCRO: WARNING ENERGY BALANCE !")
5275 !
5276 IF (lhook) CALL dr_hook('SNOWCROSTOPBALANCE',1,zhook_handle)
5277 !
5278 END SUBROUTINE snowcrostopbalance
5279 !
5280 !###################################################################
5281 SUBROUTINE snowcroprintbalance(PSUMMASS_INI,PSUMHEAT_INI,PSUMMASS_FIN,PSUMHEAT_FIN, &
5282  PSR,PRR,PTHRUFAL,PEVAP,PEVAPCOR,PGRNDFLUX,PHSNOW, &
5283  PRNSNOW,PLEL3L,PLES3L,PHPSNOW,PSNOWHMASS,PSNOWDZ, &
5284  PTSTEP,PMASSBALANCE,PENERGYBALANCE,PEVAPCOR2 )
5285 !
5286 ! Matthieu Lafaysse / Eric Brun 03/10/2012
5287 ! Print energy and mass balances.
5288 !
5289 IMPLICIT NONE
5290 !
5291 REAL, INTENT(IN) :: PSUMMASS_INI,PSUMHEAT_INI,PSUMMASS_FIN,PSUMHEAT_FIN
5292 REAL, INTENT(IN) :: PSR,PRR,PTHRUFAL,PEVAP,PEVAPCOR
5293 REAL, INTENT(IN) :: PGRNDFLUX,PHSNOW,PRNSNOW,PLEL3L,PLES3L,PHPSNOW,PSNOWHMASS
5294 REAL, INTENT(IN) :: PSNOWDZ !first layer
5295 REAL, INTENT(IN) :: PTSTEP !time step
5296 REAL, INTENT(IN) :: PMASSBALANCE, PENERGYBALANCE, PEVAPCOR2
5297 !
5298 REAL(KIND=JPRB) :: ZHOOK_HANDLE
5299 !
5300 IF (lhook) CALL dr_hook('SNOWCROPRINTBALANCE',0,zhook_handle)
5301 !
5302 WRITE(*,*) ' '
5303 WRITE(*,fmt='(A1,67("+"),A1)') "+","+"
5304 !
5305  CALL snowcroprintdate()
5306 !
5307 WRITE(*,*) ' '
5308 !
5309 ! print des residus de bilan et des differents termes pour le point
5310 WRITE (*,fmt="(A25,1x,E17.10)") 'final mass (kg/m2) =' , psummass_fin
5311 WRITE (*,fmt="(A25,1x,E17.10)") 'final energy (J/m2) =', zsumheat_fin
5312 WRITE(*,*) ' '
5313 !
5314 WRITE(*,fmt="(A25,1x,E17.10)") 'mass balance (kg/m2) =', pmassbalance
5315 !
5316 WRITE(*,*) ' '
5317 WRITE(*,fmt="(A35)") 'mass balance contribution (kg/m2) '
5318 WRITE(*,fmt="(A51,1x,E17.10)") 'delta mass:', (psummass_fin-psummass_ini)
5319 WRITE(*,fmt="(A51,1x,E17.10)") 'hoar or condensation (>0 towards snow):', -pevap * ptstep
5320 WRITE(*,fmt="(A51,1x,E17.10)") 'rain:', prr * ptstep
5321 WRITE(*,fmt="(A51,1x,E17.10)") 'snow:', psr * ptstep
5322 WRITE(*,fmt="(A51,1x,E17.10)") 'run-off:', pthrufal * ptstep
5323 WRITE(*,fmt="(A51,1x,E17.10)") 'evapcor:', pevapcor * ptstep
5324 !
5325 WRITE(*,fmt='(A1,55("-"),A1)')"+","+"
5326 WRITE(*,*) ' '
5327 !
5328 WRITE(*,fmt="(A25,4(1x,E17.10))") 'energy balance (W/m2)=',penergybalance
5329 !
5330 WRITE(*,*) ' '
5331 WRITE(*,fmt="(A55)") 'energy balance contribution (W/m2) >0 towards snow :'
5332 WRITE(*,fmt="(A51,1x,E17.10)") 'delta heat:', (zsumheat_fin-zsumheat_ini)/ptstep
5333 WRITE(*,fmt="(A51,1x,E17.10)") 'radiation (LW + SW):', prnsnow
5334 WRITE(*,fmt="(A51,1x,E17.10)") 'sensible flux :', -phsnow
5335 WRITE(*,fmt="(A51,1x,E17.10)") 'ground heat flux :', -pgrndflux
5336 WRITE(*,fmt="(A51,1x,E17.10)") 'liquid latent flux:', -plel3l
5337 WRITE(*,fmt="(A51,1x,E17.10)") 'solid latent flux:', -ples3l
5338 WRITE(*,fmt="(A51,1x,E17.10)") 'rain sensible heat:', phpsnow
5339 WRITE(*,fmt="(A51,1x,E17.10)") 'snowfall/hoar heat (sensible + melt heat):', psnowhmass/ptstep
5340 WRITE(*,fmt="(A51,1x,E17.10)") 'evapcor:', pevapcor2
5341 WRITE(*,fmt='(A1,67("+"),A1)')"+","+"
5342 !
5343 IF (lhook) CALL dr_hook('SNOWCROPRINTBALANCE',1,zhook_handle)
5344 !
5345 END SUBROUTINE snowcroprintbalance
5346 !
5347 !####################################################################
5348 SUBROUTINE get_balance(PSUMMASS_INI,PSUMHEAT_INI,PSUMMASS_FIN,PSUMHEAT_FIN, &
5349  PSR,PRR,PTHRUFAL,PEVAP,PEVAPCOR,PGRNDFLUX,PHSNOW, &
5350  PRNSNOW,PLEL3L,PLES3L,PHPSNOW,PSNOWHMASS,PSNOWDZ, &
5351  PTSTEP,PMASSBALANCE,PENERGYBALANCE,PEVAPCOR2 )
5352 !
5353 IMPLICIT NONE
5354 !
5355 REAL, INTENT(IN) :: PSUMMASS_INI,PSUMHEAT_INI,PSUMMASS_FIN,PSUMHEAT_FIN
5356 REAL, INTENT(IN) :: PSR,PRR,PTHRUFAL,PEVAP,PEVAPCOR
5357 REAL, INTENT(IN) :: PGRNDFLUX,PHSNOW,PRNSNOW,PLEL3L,PLES3L,PHPSNOW,PSNOWHMASS
5358 REAL, INTENT(IN) :: PSNOWDZ !first layer
5359 REAL, INTENT(IN) :: PTSTEP !time step
5360 !
5361 REAL, INTENT(OUT) :: PMASSBALANCE, PENERGYBALANCE, PEVAPCOR2
5362 !
5363 REAL(KIND=JPRB) :: ZHOOK_HANDLE
5364 !
5365 IF (lhook) CALL dr_hook('SNOWCRO:GET_BALANCE',0,zhook_handle)
5366 !
5367 pmassbalance = psummass_fin - psummass_ini - &
5368  ( psr + prr - pthrufal - pevap + pevapcor ) * ptstep
5369 !
5370 pevapcor2 = pevapcor * psnowdz / max( xuepsi,psnowdz ) * &
5371  ( abs(plel3l) * xlvtt / max( xuepsi,abs(plel3l) ) + &
5372  abs(ples3l) * xlstt / max( xuepsi,abs(ples3l) ) )
5373 !
5374 penergybalance = ( psumheat_fin-psumheat_ini ) / ptstep - &
5375  ( -pgrndflux - phsnow + prnsnow - plel3l - ples3l + phpsnow ) - &
5376  psnowhmass / ptstep - pevapcor2
5377 !
5378 IF (lhook) CALL dr_hook('SNOWCRO:GET_BALANCE',1,zhook_handle)
5379 !
5380 END SUBROUTINE get_balance
5381 !
5382 !###################################################################
5383 SUBROUTINE snowcroprintdate()
5385 IMPLICIT NONE
5386 !
5387 REAL(KIND=JPRB) :: ZHOOK_HANDLE
5388 !
5389 IF (lhook) CALL dr_hook('SNOWCROPRINTDATE',0,zhook_handle)
5390 !
5391 WRITE(*,fmt='(I4.4,2("-",I2.2)," Hour=",F5.2)') &
5392  tptime%TDATE%YEAR, tptime%TDATE%MONTH, tptime%TDATE%DAY, tptime%TIME/3600.
5393 !
5394 IF (lhook) CALL dr_hook('SNOWCROPRINTDATE',1,zhook_handle)
5395 !
5396 END SUBROUTINE snowcroprintdate
5397 !####################################################################
5398 !###################################################################
5399 !
5400 END SUBROUTINE snowcro
real, parameter xvfi
static const char * trim(const char *name, int *n)
Definition: drhook.c:2383
logical, parameter lpstopbalance
real, parameter xvvap1
logical lcrodailyinfo
integer nendcrodebug
real, parameter xvsphe2
real, parameter xpsnowg0
real, parameter xsnowdzmin
real, parameter xuepsi
real, save xcpd
Definition: modd_csts.F90:63
real, parameter xvvisc5
subroutine snowcroevapn(PLES3L, PTSTEP, PSNOWTEMP, PSNOWRHO, PSNOWDZ, PEVAPCOR, PSNOWHMASS)
Definition: snowcro.F90:3245
subroutine surface_ri(PTG, PQS, PEXNS, PEXNA, PTA, PQA, PZREF, PUREF, PDIRCOSZW, PVMOD, PRI)
Definition: surface_ri.F90:8
real, parameter xnden1
real, save xstefan
Definition: modd_csts.F90:59
integer, parameter nvdent1
logical lcrodebugdetails
subroutine snowcrogone(PTSTEP, PLEL3L, PLES3L, PSNOWRHO,
Definition: snowcro.F90:3331
real, parameter xpsnowy0
real, parameter xvgran1
subroutine snowcroprintatm(CINFO, PTA, PQA, PVMOD, PRR, PSR, PSW_RAD, PLW_RAD,
Definition: snowcro.F90:5202
real, parameter xvdent1
integer, parameter nvhis5
real, parameter xvsphe3
subroutine snowcroevapgone(PSNOWHEAT, PSNOWDZ, PSNOWRHO, PSNOWTEMP, PSNOWLIQ
Definition: snowcro.F90:3445
real, parameter xvvap2
real, save xlvtt
Definition: modd_csts.F90:70
real, parameter xvgran6
real, parameter xpsnowb0
real, save xpi
Definition: modd_csts.F90:43
subroutine snowcroprintprofile(HINFO, KLAYERS, OPRINTGRAN, PSNOWDZ, PSNOWRHO
Definition: snowcro.F90:5104
real, parameter xvtail2
subroutine snowcrostopbalance(PMASSBALANCE, PENERGYBALANCE)
Definition: snowcro.F90:5254
real, save xlstt
Definition: modd_csts.F90:71
real, parameter xvvisc4
subroutine snowcrolayer_gone(PTSTEP, PSCAP, PSNOWTEMP, PSNOWDZ, PSNOWRHO, PSNOWLIQ, PSNOWGRAN1, PSNOWGRAN2, PSNOWHIST, PSNOWAGE, PLES3L, KNLVLS_USE)
Definition: snowcro.F90:4958
subroutine snownlfall_upgrid(TPTIME, OGLACIER, PTSTEP, PSR, PTA, PVMOD,
Definition: snowcro.F90:3593
subroutine snowcroflux(PSNOWTEMP, PSNOWDZ, PEXNS, PEXNA, PUSTAR2_IC, PTSTEP, PALBT, PSW_RAD, PEMIST, PLWUPSNOW, PLW_RAD, PTA, PSFCFRZ, PQA, PHPSNOW, PSNOWTEMPO1, PSNOWFLUX, PCT, PRADSINK, PQSAT, PDQSAT, PRSRA, PRN, PH, PGFLUX, PLES3L, PLEL3L, PEVAP, PUSTAR)
Definition: snowcro.F90:3064
integer, parameter nvhis4
subroutine get_gran(PTSTEP, PTELM, PGRAN)
Definition: snowcro.F90:1844
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:7
logical lcontrolbalance
subroutine snowcrocompactn(PTSTEP, PSNOWRHO, PSNOWDZ,
Definition: snowcro.F90:1130
real, parameter xundef
real xwarning_energybalance
real, parameter xnden3
real, dimension(:,:,:), pointer xdrdt0
real, save xcondi
Definition: modd_csts.F90:82
subroutine surface_aero_cond(PRI, PZREF, PUREF, PVMOD, PZ0, PZ0H, PAC, PRA, PCH)
integer, dimension(nvegtype_old), parameter npnimp
subroutine snowcrorad(TPTIME, OGLACIER, PSW_RAD, PSNOWALB, PSNOWDZ, PSNOWRHO, PALB, PRADSINK, PRADXS, PSNOWGRAN1, PSNOWGRAN2, PSNOWAGE, PPS, PZENITH, PPERMSNOWFRAC, KNLVLS_USE, OSNOW_ABS_ZENITH, HSNOWMETAMO)
Definition: snowcro.F90:2082
real, parameter xepsi
real, parameter xnsph2
real, save xg
Definition: modd_csts.F90:55
integer, parameter jprb
Definition: parkind1.F90:32
subroutine snowcrometamo(PSNOWDZ, PSNOWGRAN1, PSNOWGRAN2, PSNOWHIST, PSNOWTEMP, PSNOWLIQ, PTSTEP, PSNOWSWE, INLVLS_USE, PSNOWAGE, HSNOWMETAMO)
Definition: snowcro.F90:1285
subroutine getpoint_crodebug(PLAT, PLON, KDEBUG)
real, dimension(:,:,:), pointer xkappa
subroutine get_snowdzn_end(KNLVLS, PSNOWDZ, PDZOPT, PSNOWDZN)
Definition: snowcro.F90:4415
subroutine snowcrothrm(PSNOWRHO, PSCOND, PSNOWTEMP, PPS, PSNOWLIQ, OCOND_GRAIN, OCOND_YEN)
Definition: snowcro.F90:2220
subroutine get_rho(PRHO_IN, PDZ, PSNOWLIQ, PFLOWLIQ, PRHO_OUT)
Definition: snowcro.F90:3037
real, parameter xvdiam1
real xwarning_massbalance
real, parameter xvsphe4
subroutine snowcroalb(TPTIME, OGLACIER, PALBEDOSC, PSPECTRALALBEDO, PSNOWDZ, PSNOWRHO, PPERMSNOWFRAC, PSNOWGRAN1_TOP, PSNOWGRAN2_TOP, PSNOWAGE_TOP, PSNOWGRAN1_BOT, PSNOWGRAN2_BOT, PSNOWAGE_BOT, PPS, PZENITH, KNLVLS_USE, HSNOWMETAMO)
Definition: snowcro.F90:1875
real, parameter xvgrat2
subroutine get_snowdzn_deb(KNLVLS, PSNOWDZ, PDZOPT, PSNOWDZN)
Definition: snowcro.F90:4368
real, parameter xgran
real, save xci
Definition: modd_csts.F90:65
real, parameter xvdiam5
real, parameter xpsnoww0
subroutine snowcroebud(HSNOWRES, HIMPLICIT_WIND,
Definition: snowcro.F90:2286
subroutine get_flux(PALBT, PEMIST, PSW_RAD, PLW_RAD, PEXNS, PEXNA, PTA, PQA, PRSRA, PQSAT, PDQSAT, PSFCFRZ, PHPSNOW, PSNOWTEMP, PSNOWTEMPO1, PRN, PH, PEVAPC, PLES3L, PLEL3L, PGFLUX)
Definition: snowcro.F90:3199
real, parameter xvgrat1
integer, parameter nvhis2
subroutine surface_cd(PRI, PZREF, PUREF, PZ0EFF, PZ0H, PCD, PCDN)
Definition: surface_cd.F90:8
real, parameter xvtail1
real, save xcl
Definition: modd_csts.F90:65
real, parameter xvsphe1
real, parameter xvdiam2
real, parameter xnden2
subroutine snowcroprintdate()
Definition: snowcro.F90:5384
intent(out) overrides sub arrays one Sort by the least significant key first sum(iindex(1:n))
real, parameter xvdiam6
subroutine snowcrorefrz(PTSTEP, PRR, PSNOWRHO, PSNOWTEMP, PSNOWDZ, PSNOWLIQ, PTHRUFAL, PSCAP, PLEL3L, KNLVLS_USE)
Definition: snowcro.F90:2891
logical lhook
Definition: yomhook.F90:15
real, save xrholi
Definition: modd_csts.F90:81
subroutine snownlgridfresh_1d(KJ, PSNOW, PSNOWDZ, PSNOWDZN,
Definition: snowcro.F90:4464
real, parameter xvvisc3
subroutine snowcrosolvt(PTSTEP, PSNOWDZMIN, PSNOWDZ, PSCOND, PSCAP, PTG, PSOILCOND, PD_G, PRADSINK, PCT, PTERM1, PTERM2, PPET_A_COEF_T, PPEQ_A_COEF_T, PPET_B_COEF_T, PPEQ_B_COEF_T, PTA_IC, PQA_IC, PGBAS, PSNOWTEMP, PSNOWFLUX, KNLVLS_USE)
Definition: snowcro.F90:2540
real, parameter xnsph4
integer, parameter nvhis3
subroutine snowcro(HSNOWRES, TPTIME, OGLACIER, HIMPLICIT_WIND,
Definition: snowcro.F90:7
real, parameter xupourc
subroutine snowcromelt(PSCAP, PSNOWTEMP, PSNOWDZ, PSNOWRHO, PSNOWLIQ, KNLVLS_USE)
Definition: snowcro.F90:2779
integer, parameter nvhis1
real, parameter xvvisc7
real, dimension(:,:,:), pointer xtau
real, parameter xvvisc6
integer nhourcrodebug
subroutine set_thresh(PGRADT, PSNOWLIQ, PSPHE)
Definition: snowcro.F90:1825
subroutine snowdrift(PTSTEP, PVMOD, PSNOWRHO, PSNOWDZ, PSNOW, PSNOWGRAN1, PSNOWGRAN2, PSNOWHIST, KNLVLS_USE, PTA, PQA, PPS, PRHOA, PZ0EFF, PUREF, OSNOWDRIFT_SUBLIM, HSNOWMETAMO, PSNDRIFT)
Definition: snowcro.F90:4689
real, parameter xvdiam4
subroutine get_alb(KJ, PSNOWRHO_IN, PPS_IN, PVAGE1, PSNOWGRAN1, PSNOWGRAN2, PS
Definition: snowcro.F90:2020
real, parameter xvvisc1
subroutine snowcro_tartes(PSNOWGRAN1, PSNOWGRAN2, PSNOWRHO, PSNOWDZ, PSNOWG0, PSNOWY0, PSNOWW0, PSNOWB0, PSNOWIMP_DENSITY, PSNOWIMP_CONTENT, PALB, PSW_RAD, PZENITH, KNLVLS_USE, PSNOWALB, PRADSINK, PRADXS, ODEBUG, HSNOWMETAMO)
real, save xrholw
Definition: modd_csts.F90:64
logical lprintgran
subroutine get_balance(PSUMMASS_INI, PSUMHEAT_INI, PSUMMASS_FIN, PSUMHEAT_F
Definition: snowcro.F90:5349
real, parameter xnsph1
real, parameter xvdent2
real, save xtt
Definition: modd_csts.F90:66
real, parameter xvro11
real, save xlmtt
Definition: modd_csts.F90:72
real, save xp00
Definition: modd_csts.F90:57
real, parameter xvtelv1
real, parameter xnsph3
subroutine snowcroprintbalance(PSUMMASS_INI, PSUMHEAT_INI, PSUMMASS_FIN, PS
Definition: snowcro.F90:5282
logical lcrodebugatm
integer ntimecrodebug
integer npointcrodebug
real, parameter xvdiam3