SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
snow_leaves_frac_meb.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 snow_leaves_frac_meb(PPSN, PPALPHAN, &
7  pwrvn, &
8  ptv, &
9  pchip, &
10  plaiv, &
11  pwrvnmax, &
12  pdeltavn, pmeltvn )
13 ! ############################################################################
14 !
15 !!**** *SNOW_LEAVES_FRAC_MEB*
16 !!
17 !! PURPOSE
18 !! -------
19 !
20 ! Calculate desnity, maximum snow load etc for intercepted snow
21 !
22 !!** METHOD
23 !! ------
24 !
25 !
26 !! EXTERNAL
27 !! --------
28 !!
29 !!
30 !! IMPLICIT ARGUMENTS
31 !! ------------------
32 !!
33 !!
34 !!
35 !! REFERENCE
36 !! ---------
37 !!
38 !!
39 !! AUTHOR
40 !! ------
41 !!
42 !! P. Samuelsson * SMHI *
43 !!
44 !! MODIFICATIONS
45 !! -------------
46 !! Original 02/2011
47 !-------------------------------------------------------------------------------
48 !
49 !* 0. DECLARATIONS
50 ! ------------
51 !
52 USE modd_csts, ONLY : xtt
53 !
54 USE modd_surf_par, ONLY : xundef
55 !
56 USE yomhook ,ONLY : lhook, dr_hook
57 USE parkind1 ,ONLY : jprb
58 !
59 IMPLICIT NONE
60 !
61 !* 0.1 declarations of arguments
62 !
63 REAL, DIMENSION(:), INTENT(IN) :: ppsn, ppalphan
64 ! PPSN =
65 ! PPALPHAN = snow/canopy transition coefficient
66 !
67 REAL, DIMENSION(:), INTENT(IN) :: pwrvn
68 ! PWRVN = snow retained on the foliage
69 !
70 REAL, DIMENSION(:), INTENT(IN) :: plaiv
71 ! PLAIV = canopy vegetation leaf area index
72 !
73 REAL, DIMENSION(:), INTENT(IN) :: pchip, ptv
74 ! PCHIP = view factor (for LW)
75 ! PTV = Canopy T (K)
76 !
77 REAL, DIMENSION(:), INTENT(OUT) :: pwrvnmax
78 ! PWRVNMAX = maximum equivalent snow content
79 ! in the canopy vegetation
80 !
81 REAL, DIMENSION(:), INTENT(OUT) :: pdeltavn
82 ! PDELTAVN = fraction of the canopy foliage covered
83 ! by intercepted snow
84 !
85 REAL, DIMENSION(:), INTENT(OUT) :: pmeltvn
86 ! PMELTVN = freeze/melt rate (kg m-2 s-1)
87 !
88 !* 0.2 declarations of local variables
89 !
90 !
91 REAL, DIMENSION(SIZE(PLAIV)) :: zlai,zfcp,zfracvn, zsnowrhov
92 ! ZLAI = weigthed leaf area index
93 ! ZFCP = snow interception factor
94 ! ZFRACVN = fraction of interception snow
95 ! ZSNOWRHOV = density of snow intercepted by the canopy (kg m-3)
96 !
97 REAL(KIND=JPRB) :: zhook_handle
98 !
99 !* 0.3 declarations of local parameters
100 !
101 ! For intercepted snow density
102 !
103 REAL, PARAMETER :: zrhovnpar1 = 67.92 ! (kg/m3)
104 REAL, PARAMETER :: zrhovnpar2 = 51.25 ! (kg/m3)
105 REAL, PARAMETER :: zrhovnpar3 = 2.59 ! (K)
106 !
107 ! For intercepted maximum snow load
108 !
109 REAL, PARAMETER :: zwrvnmaxpar1 = 6.3 ! (kg/m2)
110 REAL, PARAMETER :: zwrvnmaxpar2 = 0.27 ! (-)
111 REAL, PARAMETER :: zwrvnmaxpar3 = 46. ! (kg/m3)
112 
113 ! For intercepted snow evaporation efficiency
114 !
115 REAL, PARAMETER :: zdvnpar1 = 0.89 ! (-)
116 REAL, PARAMETER :: zdvnpar2 = -4.7 ! (-)
117 REAL, PARAMETER :: zdvnpar3 = 0.45 ! (-)
118 REAL, PARAMETER :: zdvnpar4 = 0.3 ! (-)
119 REAL, PARAMETER :: zmeltf = 5.556e-6 ! Snow melt factor
120 REAL, PARAMETER :: zlai_min = 0.001 ! (m2 m-2) Below this (numerical) threshold, interception
121  ! by the canopy is not assumed to occur
122  ! as canopy essentially buried.
123 REAL, PARAMETER :: zrhovn_tmax = 279.85403 ! (K) corresponds to a snow density of
124  ! 750 kg m-3 (presumably the max).
125  ! Obtained by inverting the snow density Eq
126  ! for Tv below assuming a density of 750
127 
128 !-------------------------------------------------------------------------------
129 !
130 !* 0. Initialization
131 ! --------------
132 !
133 IF (lhook) CALL dr_hook('SNOW_LEAVES_FRAC_MEB',0,zhook_handle)
134 !
135 zsnowrhov(:)= zrhovnpar1
136 !
137 zfracvn(:) = 0.0
138 zfcp(:) = 0.0
139 !
140 pdeltavn(:) = 0.0
141 pmeltvn(:) = 0.0
142 pwrvnmax(:) = 0.0
143 !
144 !
145 zlai(:) = plaiv(:)*(1.-ppsn(:)+ppsn(:)*(1.-ppalphan(:)))
146 !
147 ! If snow buries the vegetation canopy (i.e. ZLAI~=0), we do not need the following:
148 !
149 WHERE(zlai(:) > zlai_min .AND. plaiv(:)/=xundef)
150 !
151 ! Snow density
152 !
153  zsnowrhov(:)= zrhovnpar1 + zrhovnpar2*exp( (min(zrhovn_tmax,ptv(:))-xtt)/zrhovnpar3)
154 !
155 ! Intercepted maximum snow load
156 !
157  pwrvnmax(:) = zwrvnmaxpar1*(zwrvnmaxpar2+zwrvnmaxpar3/zsnowrhov(:)) * zlai(:)
158 !
159 ! Fraction of snow on vegetation canopy
160 !
161  zfracvn(:) = pwrvn(:)/pwrvnmax(:)
162 !
163 ! Snow evaporation efficiency coefficient which corresponds to
164 ! delta for intercepted water
165 !
166  pdeltavn(:) = zdvnpar1*zfracvn(:)**zdvnpar4/( 1.+exp( zdvnpar2*( zfracvn(:) - zdvnpar3 ) ) )
167 !
168 ! Melt rate (kg/m2/s)
169 !
170  pmeltvn(:) = zmeltf * ( ptv(:)-xtt ) * zfracvn(:)
171 !
172 END WHERE
173 !
174 IF (lhook) CALL dr_hook('SNOW_LEAVES_FRAC_MEB',1,zhook_handle)
175 !
176 END SUBROUTINE snow_leaves_frac_meb
177 
subroutine snow_leaves_frac_meb(PPSN, PPALPHAN, PWRVN, PTV, PCHIP, PLAIV, PWRVNMAX, PDELTAVN, PMELTVN)