SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
hydro_snow.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 hydro_snow( OGLACIER, PTSTEP, PVEGTYPE, &
7  psr, ples, pmelt, &
8  psnowswe, psnowalb, psnowrho, ppg_melt )
9 ! #####################################################################
10 !
11 !!**** *HYDRO_SNOW*
12 !!
13 !! PURPOSE
14 !! -------
15 !
16 ! Calculates i) Snow water transfer to soil for both snow scheme options.
17 ! ii) the evolution of the snowpack using the Force-Restore
18 ! option of Douville et al. (1995): 'DEF'
19 ! Calculate the snow cover liquid water equivalent (Ws), the albedo and density of
20 ! the snow (i.e., SNOWALB and SNOWRHO). Also determine the runoff and drainage
21 ! into the soil.
22 !
23 !
24 !!** METHOD
25 !! ------
26 !
27 !! EXTERNAL
28 !! --------
29 !!REAL, DIMENSION(:), INTENT(INOUT) :: PTG
30 ! PTG = surface temperature at 't'
31 
32 !! none
33 !!
34 !! IMPLICIT ARGUMENTS
35 !! ------------------
36 !!
37 !!
38 !!
39 !! REFERENCE
40 !! ---------
41 !!
42 !! Noilhan and Planton (1989)
43 !! Belair (1995)
44 !!
45 !! AUTHOR
46 !! ------
47 !!
48 !! S. Belair * Meteo-France *
49 !!
50 !! MODIFICATIONS
51 !! -------------
52 !!
53 !! Original 14/03/95
54 !! 31/08/98 (V. Masson and F. Habets) add Dumenil et Todini
55 !! runoff scheme
56 !! 31/08/98 (V. Masson and A. Boone) add the third soil-water
57 !! reservoir (WG3,D3)
58 !! 14/05/02 (A. Boone) snow only, and skip code if '3-L' option in force
59 !! 03/2009 (B. Decharme) Consistency with Arpege permanent snow/ice treatment
60 !! (LGLACIER)
61 !-------------------------------------------------------------------------------
62 !
63 !* 0. DECLARATIONS
64 ! ------------
65 !
66 USE modd_csts, ONLY : xlstt, xlmtt, xday
67 USE modd_snow_par, ONLY : xans_t, xans_todry, xansmin, xansmax, &
68  xrhosmax, xrhosmin, xwcrn, xaglamin, &
69  xaglamax
70 USE modd_surf_par, ONLY : xundef
71 USE modd_data_cover_par, ONLY : nvt_snow
72 !
73 !
74 USE yomhook ,ONLY : lhook, dr_hook
75 USE parkind1 ,ONLY : jprb
76 !
77 IMPLICIT NONE
78 !
79 !* 0.1 declarations of arguments
80 !
81 !
82 LOGICAL, INTENT(IN) :: oglacier ! True = Over permanent snow and ice,
83 ! initialise WGI=WSAT,
84 ! Hsnow>=10m and allow 0.8<SNOALB<0.85
85  ! False = No specific treatment
86 REAL, INTENT(IN) :: ptstep
87 ! timestep of the integration
88 REAL, DIMENSION(:,:), INTENT(IN) :: pvegtype ! fraction of each vegetation
89 REAL, DIMENSION(:), INTENT(IN) :: psr, ples, pmelt
90 ! PSR = snow rate
91 ! PLES = latent heat of sublimation over the snow
92 ! PMELT = melting rate of snow
93 REAL, DIMENSION(:), INTENT(INOUT) :: psnowswe, psnowalb, psnowrho, ppg_melt
94 ! PSNOWSWE = equivalent water content of the
95 ! snow reservoir at time 't+dt'
96 ! PSNOWALB = albedo of the snow at 't+dt'
97 ! PSNOWRHO = density of the snow at 't+dt'
98 ! PPG_MELT = total water reaching the ground
99 !
100 !* 0.2 declarations of local variables
101 !
102 REAL, DIMENSION(SIZE(PSR)) :: zsnowswem, zwsx, zansmin, zansmax
103 ! Prognostic variables of ISBA at 't-dt'
104 ! ZSNOWSWEM = equivalent water content of the
105 ! snow reservoir
106 ! ZANSMIN = Minimum glacier albedo
107 ! ZANSMAX = Maximum glacier albedo
108 REAL(KIND=JPRB) :: zhook_handle
109 !
110 !-------------------------------------------------------------------------------
111 IF (lhook) CALL dr_hook('HYDRO_SNOW',0,zhook_handle)
112 !-------------------------------------------------------------------------------
113 !
114 !* Douville et al. (1995) 'DEF' snow option
115 ! ----------------------------------------
116 !
117 !* 1. Initialize:
118 ! -----------
119 !
120 zwsx(:) = 0.0
121 zansmin(:) = xansmin
122 zansmax(:) = xansmax
123 !
124 !
125 !* 2. Fields at time t-dt
126 ! -------------------
127 !
128 zsnowswem(:) = psnowswe(:)
129 !
130 !* 3. EVOLUTION OF THE SNOWPACK ('DEF' OPTION)
131 ! ----------------------------------------
132 !
133 !* 3.A EVOLUTION OF THE EQUIVALENT WATER CONTENT snowSWE ('DEF' option)
134 ! --------------------------------------------------------------
135 !
136 ! evolution of Ws (without melting)
137 !
138 psnowswe(:) = zsnowswem(:) + ptstep * ( psr(:) - ples(:)/xlstt - pmelt(:))
139 !
140 ! melting of snow: more liquid water
141 ! reaches the surface
142 !
143 ppg_melt(:) = ppg_melt(:) + pmelt(:)
144 !
145 ! removes very small values due to computation precision
146 !
147 WHERE(psnowswe(:) < 1.0e-10) psnowswe(:) = 0.
148 !
149 !-------------------------------------------------------------------------------
150 !
151 !* 3.B EVOLUTION OF SNOW ALBEDO
152 ! ------------------------
153 !
154 IF(oglacier)THEN
155  zansmin(:) = xaglamin * pvegtype(:,nvt_snow) + xansmin * (1.0-pvegtype(:,nvt_snow))
156  zansmax(:) = xaglamax * pvegtype(:,nvt_snow) + xansmax * (1.0-pvegtype(:,nvt_snow))
157 ELSE
158  zansmin(:) = xansmin
159  zansmax(:) = xansmax
160 ENDIF
161 ! the evolution of the snow albedo differs
162 ! if there is melting or not
163 !
164 WHERE (psnowswe > 0.0 )
165  !
166  WHERE ( zsnowswem > 0.0)
167  !
168  ! when there is melting
169  WHERE ( pmelt > 0.0 )
170  psnowalb(:) = (psnowalb(:)-zansmin(:))*exp(-xans_t*ptstep/xday) + zansmin(:) &
171  + psr(:)*ptstep/xwcrn*(zansmax(:)-zansmin(:))
172  ! when there is no melting
173  ELSEWHERE
174  psnowalb(:) = psnowalb(:) - xans_todry*ptstep/xday &
175  + psr(:)*ptstep/xwcrn*(zansmax(:)-zansmin(:))
176  END WHERE
177  !
178  ELSEWHERE (zsnowswem == 0.0)
179  !
180  ! new snow covered surface
181  psnowalb(:) = zansmax(:)
182  END WHERE
183  !
184  ! limits of the albedo
185  psnowalb(:) = min( zansmax(:), psnowalb(:) )
186  psnowalb(:) = max( zansmin(:), psnowalb(:) )
187 END WHERE
188 !
189 !-------------------------------------------------------------------------------
190 !
191 !* 3.C EVOLUTION OF SNOW DENSITY
192 ! -------------------------
193 !
194 ! as for the snow albedo, the density's
195 ! evolution will depend whether or not
196 ! the snow is melting
197 !
198 WHERE ( psnowswe > 0.0 )
199  WHERE ( zsnowswem > 0.0 )
200  zwsx(:) = max( psnowswe(:),psr(:)*ptstep)
201  psnowrho(:) = (psnowrho(:)-xrhosmax)*exp(-xans_t*ptstep/xday) + xrhosmax
202  psnowrho(:) = ( (zwsx(:)-psr(:)*ptstep) * psnowrho(:) &
203  + (psr(:)*ptstep) * xrhosmin ) / zwsx(:)
204  ELSEWHERE ( zsnowswem == 0.0)
205  psnowrho(:) = xrhosmin
206  END WHERE
207 END WHERE
208 !
209 !-------------------------------------------------------------------------------
210 !
211 !* 4. No SNOW
212 ! -------
213 !
214 WHERE ( psnowswe == 0.0 )
215  psnowrho(:) = xundef
216  psnowalb(:) = xundef
217 END WHERE
218 !
219 IF (lhook) CALL dr_hook('HYDRO_SNOW',1,zhook_handle)
220 !
221 !-------------------------------------------------------------------------------
222 !
223 END SUBROUTINE hydro_snow
subroutine hydro_snow(OGLACIER, PTSTEP, PVEGTYPE, PSR, PLES, PMELT, PSNOWSWE, PSNOWALB, PSNOWRHO, PPG_MELT)
Definition: hydro_snow.F90:6