SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
hydro_dt92.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_dt92(PTSTEP, &
7  prunoffb, pwwilt, &
8  prunoffd, pwsat, &
9  pwg2, pwgi2, &
10  ppg, pruisdt )
11 ! #####################################################################
12 !
13 !!**** *HYDRO_DT92*
14 !!
15 !! PURPOSE
16 !! -------
17 !
18 ! Calculates the evolution of the water variables, i.e., the superficial
19 ! and deep-soil volumetric water content (wg and w2), the equivalent
20 ! liquid water retained in the vegetation canopy (Wr), the equivalent
21 ! water of the snow canopy (Ws), and also of the albedo and density of
22 ! the snow (i.e., ALBS and RHOS). Also determine the runoff and drainage
23 ! into the soil.
24 !
25 !
26 !!** METHOD
27 !! ------
28 !
29 !! EXTERNAL
30 !! --------
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 !! 16/05/02 (A. Boone) comments, F90 code standardization
57 !-------------------------------------------------------------------------------
58 !
59 !* 0. DECLARATIONS
60 ! ------------
61 !
62 USE modd_csts,ONLY : xrholw
63 !
64 !
65 USE yomhook ,ONLY : lhook, dr_hook
66 USE parkind1 ,ONLY : jprb
67 !
68 IMPLICIT NONE
69 !
70 !* 0.1 declarations of arguments
71 !
72 !
73 !
74 REAL, INTENT(IN) :: ptstep
75 ! timestep of the integration (s)
76 !
77 REAL, DIMENSION(:), INTENT(IN) :: pwwilt ! the wilting point volumetric
78 ! ! water content (m3 m-3)
79 REAL, DIMENSION(:), INTENT(IN) :: prunoffb ! slope of the runoff curve (-)
80 !
81 !
82 REAL, DIMENSION(:), INTENT(IN) :: prunoffd, pwsat
83 ! PRUNOFFD = soil depth over which degree of saturation
84 ! used for runoff calculation (m)
85 ! PWSAT = saturation volumetric water content
86 ! of the soil (m3 m-3)
87 !
88 REAL, DIMENSION(:), INTENT(IN) :: pwg2, pwgi2
89 ! PWG2 = bulk root-soil moisture at 't+dt' (m3 m-3)
90 ! PWGI2 = bulk deep-soil ice at 't+dt' (m3 m-3)
91 !
92 REAL, DIMENSION(:), INTENT(INOUT) :: ppg
93 ! PPG = enters as rainfall/Canopy drip/snowmelt
94 ! throughfall rate, leaves as infiltration
95 ! rate for Force-Restore method, and potential
96 ! infiltration rate for diffusion method (kg m-2 s-1)
97 REAL, DIMENSION(:), INTENT(OUT) :: pruisdt
98 ! PRUISDT = sub-grid surface runoff rate (kg m-2 s-1)
99 !
100 !
101 !* 0.2 declarations of local variables
102 !
103 !
104 REAL, DIMENSION(SIZE(PRUNOFFD)) :: zpas, zpg_ini, zwg2
105 REAL(KIND=JPRB) :: zhook_handle
106 ! ZWG2 = Total vol. water content
107 ! of layer for calculating runoff (m3 m-3)
108 !
109 !-------------------------------------------------------------------------------
110 !
111 IF (lhook) CALL dr_hook('HYDRO_DT92',0,zhook_handle)
112 zpas(:) = 0.
113 zpg_ini(:) = 0.
114 zwg2(:) = 0.
115 !
116 pruisdt(:) = 0.
117 !
118 !-------------------------------------------------------------------------------
119 !
120 !
121 !* 1. Dumenil et Todini (1992) RUNOFF SCHEME
122 ! ---------------------------------------
123 !
124 zpg_ini(:)= ppg(:)
125 !
126 zwg2(:) = min(pwsat(:), pwg2(:) + pwgi2(:))
127 !
128 ! Setting the expression below to 0 and solving for PG yields the critical throughfall rate:
129 !
130 zpas(:) = (1.- (zwg2(:)-pwwilt(:))/(pwsat(:)-pwwilt(:)) )**(1./ (1.+prunoffb(:)) ) - &
131  ppg(:)*ptstep/(xrholw*prunoffd(:) )/( (1. + prunoffb(:))* (pwsat(:)-pwwilt(:)) )
132 !
133 zpas(:) = max(0.0, zpas(:)) ! Limit it to within a physical range:
134 !
135 ! Surface runoff calculation:
136 ! If PAS is <= 0 (i.e. throughfall rate is large enough), then method
137 ! collapses into a saturated bucket type model.
138 !
139 pruisdt(:) = ppg(:)*ptstep/(xrholw*prunoffd(:) ) - ( pwsat(:)-zwg2(:) ) &
140  + (pwsat(:)-pwwilt(:))* ( zpas(:)**(1.+prunoffb(:)) )
141 !
142 pruisdt(:) = max(0.0, pruisdt(:))
143 !
144 ! Reduce infiltration into the soil by the runoff:
145 !
146 ppg(:) = ppg(:) - pruisdt(:)/ptstep*xrholw*prunoffd(:)
147 !
148 ! Supress numerical artifacts:
149 !
150 WHERE (ppg(:)<=0. .OR. pruisdt(:)<=0.)
151  pruisdt(:) = 0.
152  ppg(:) = zpg_ini(:)
153 END WHERE
154 !
155 ! supress runoff over sufficiently dry soils: HERE chosen to be if the average
156 ! water content is less than the wilting point:
157 !
158 WHERE (zwg2(:)<=pwwilt(:))
159  pruisdt(:) = 0.
160  ppg(:) = zpg_ini(:)
161 END WHERE
162 IF (lhook) CALL dr_hook('HYDRO_DT92',1,zhook_handle)
163 !
164 !-------------------------------------------------------------------------------
165 !
166 END SUBROUTINE hydro_dt92
subroutine hydro_dt92(PTSTEP, PRUNOFFB, PWWILT, PRUNOFFD, PWSAT, PWG2, PWGI2, PPG, PRUISDT)
Definition: hydro_dt92.F90:6