SURFEX v8.1
General documentation of Surfex
soilstress.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 soilstress( HISBA, PF2, KK, PK, PEK, PF2WGHT, PF5 )
7 ! ####################################################################
8 !
9 !!**** *SOILSTRESS*
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 ! Calculates the vegetation stress due to soil water
15 !
16 !
17 !!** METHOD
18 !! ------
19 !
20 ! Calculates the F2 coefficient.
21 !
22 !
23 !! EXTERNAL
24 !! --------
25 !!
26 !! none
27 !!
28 !! IMPLICIT ARGUMENTS
29 !! ------------------
30 !!
31 !! none
32 !!
33 !!
34 !! REFERENCE
35 !! ---------
36 !!
37 !! Noilhan and Planton (1989)
38 !! Belair (1995)
39 !!
40 !! AUTHOR
41 !! ------
42 !!
43 !! S. Belair * Meteo-France *
44 !!
45 !! MODIFICATIONS
46 !! -------------
47 !! Original 13/03/95
48 !! (P.Jabouille) 13/11/96 mininum value for ZF1
49 !! (V. Masson) 28/08/98 add PF2 for Calvet (1998) CO2 computations
50 !! (B. Decharme) 07/15 Suppress numerical adjustement for PF2
51 !! (B. Decharme) 01/17 Suppress soil/vegetation parameters modification
52 !! for DIF due to the presence of ice to ensure maximum
53 !! vegetation stress when soil ice is important. Indeed,
54 !! soil ice acts as drought events for vegetation stress
55 !-------------------------------------------------------------------------------
56 !
57 !* 0. DECLARATIONS
58 ! ------------
59 !
61 !
62 USE modd_isba_par, ONLY : xdenom_min
63 !
64 USE yomhook ,ONLY : lhook, dr_hook
65 USE parkind1 ,ONLY : jprb
66 !
67 IMPLICIT NONE
68 !
69 !* 0.1 declarations of arguments
70 !
71 !
72  CHARACTER(LEN=*), INTENT(IN) :: HISBA ! type of soil (Force-Restore OR Diffusion)
73 ! ! '2-L'
74 ! ! '3-L'
75 ! ! 'DIF' ISBA-DF
76 !
77 REAL, DIMENSION(:), INTENT(OUT) :: PF2 ! water stress coefficient
78 !
79 TYPE(isba_k_t), INTENT(INOUT) :: KK
80 TYPE(isba_p_t), INTENT(INOUT) :: PK
81 TYPE(isba_pe_t), INTENT(INOUT) :: PEK
82 !
83 REAL, DIMENSION(:), INTENT(OUT) :: PF5 ! water stress coefficient for Hv (based on F2):
84 ! ! Verify that Etv=>0 as F2=>0
85 !
86 REAL, DIMENSION(:,:), INTENT(OUT):: PF2WGHT ! water stress coefficient profile (ISBA-DF)
87 !
88 !
89 !* 0.2 declarations of local variables
90 !
91 !
92 REAL, DIMENSION(SIZE(KK%XWFC,1)) :: ZWFC_AVGZ, ZWSAT_AVGZ, ZWWILT_AVGZ
93 ! ZWFC_AVGZ = field capacity averaged over entire soil column
94 ! ZWSAT_AVGZ = porosity averaged over entire soil column
95 ! ZWWILT_AVGZ = wilting point averaged over entire soil column
96 !
97 REAL :: ZROOTFRACN
98 ! ZROOTFRACN = Normalized root fraction weights
99 !
100 INTEGER :: INI, INL, JJ, JL, IDEPTH
101 !
102 !
103 !* 0.3 declarations of local parameters:
104 !
105 REAL(KIND=JPRB) :: ZHOOK_HANDLE
106 !
107 !-------------------------------------------------------------------------------
108 !
109 !* 0. Initialization of variables:
110 ! ----------------------------
111 !
112 IF (lhook) CALL dr_hook('SOILSTRESS',0,zhook_handle)
113 !
114 ini=SIZE(pek%XWG,1)
115 IF (SIZE(pk%NWG_LAYER)>0) THEN
116  inl=maxval(pk%NWG_LAYER(:))
117 ELSE
118  inl=0
119 ENDIF
120 !
121 pf2(:) = 0.0
122 pf2wght(:,:) = 0.0
123 !
124 zwfc_avgz(:) = 0.
125 zwsat_avgz(:) = 0.
126 zwwilt_avgz(:) = 0.
127 !
128 !-------------------------------------------------------------------------------
129 !
130 !* 2. THE 'PF2' FACTOR
131 ! ----------------
132 ! This factor takes into account the effect
133 ! of the water stress on the surface
134 ! resistance
135 !
136 ! - For humid soils (> WFC), this factor does not
137 ! increase the stomatal resistance
138 ! - The stomatal resistance should be large
139 ! when the soil is very dry (< WILT)
140 !
141 IF(hisba =='DIF')THEN
142 !
143 ! If using the diffusion option, then calculate transpiration weights
144 ! and the mean root-zone soil water stress factor F2:
145 !
146 !---------------------------------------------------------
147 ! First layer
148 !---------------------------------------------------------
149 !
150 ! Calculate the soil water stress factor for each layer:
151  pf2wght(:,1) = (pek%XWG(:,1)-kk%XWWILT(:,1))/(kk%XWFC(:,1)-kk%XWWILT(:,1))
152 !
153 ! Normalize the transpiration weights by root fraction:
154  pf2wght(:,1) = pk%XROOTFRAC(:,1)*max(0.0,min(1.0,pf2wght(:,1)))
155 !
156 ! Net soil water stress for entire root zone:
157  pf2(:) = pf2wght(:,1)
158 !
159 !---------------------------------------------------------
160 ! Other layers
161 !---------------------------------------------------------
162 !
163  DO jl=2,inl
164  DO jj=1,ini
165 !
166  idepth=pk%NWG_LAYER(jj)
167  IF(jl<=idepth)THEN
168 !
169 ! Calculate normalized root fraction weights:
170  zrootfracn = pk%XROOTFRAC(jj,jl) - pk%XROOTFRAC(jj,jl-1)
171 !
172 ! Calculate the soil water stress factor for each layer:
173  pf2wght(jj,jl) = (pek%XWG(jj,jl)-kk%XWWILT(jj,jl))/(kk%XWFC(jj,jl)-kk%XWWILT(jj,jl))
174 !
175 ! Normalize the transpiration weights by root fraction:
176  pf2wght(jj,jl) = zrootfracn*max(0.0,min(1.0,pf2wght(jj,jl)))
177 !
178 ! Net soil water stress for entire root zone:
179  pf2(jj) = pf2(jj) + pf2wght(jj,jl)
180 !
181  ENDIF
182 !
183  ENDDO
184  ENDDO
185 !
186 ELSE
187 !
188 ! When using the Force-Restore (FR) soil option, the soil properties
189 ! are assumed to be homogeneous in the vertical. Therefore, simply
190 ! use the properties for the uppermost soil layer when defining
191 ! soil properties for local computations.
192 !
193 ! Due to the presence of ice, modify soil parameters:
194 !
195  zwsat_avgz(:) = kk%XWSAT (:,1) - pek%XWGI(:,2)
196  zwfc_avgz(:) = kk%XWFC (:,1)*zwsat_avgz(:)/kk%XWSAT(:,1)
197  zwwilt_avgz(:) = kk%XWWILT(:,1)*zwsat_avgz(:)/kk%XWSAT(:,1)
198 !
199 ! Compute the water stress factor:
200 !
201  pf2(:) = (pek%XWG(:,2)-zwwilt_avgz(:))/(zwfc_avgz(:)-zwwilt_avgz(:))
202  pf2(:) = max(0.0,min(1.0, pf2(:)))
203 !
204 !
205 ENDIF
206 !
207 ! Function to cause Etv to approach 0 as F2 goes to 0:
208 !
209 pf5(:) = pf2(:)
210 !
211 IF (lhook) CALL dr_hook('SOILSTRESS',1,zhook_handle)
212 !
213 !-------------------------------------------------------------------------------
214 !
215 END SUBROUTINE soilstress
integer, parameter jprb
Definition: parkind1.F90:32
subroutine soilstress(HISBA, PF2, KK, PK, PEK, PF2WGHT, PF5)
Definition: soilstress.F90:7
logical lhook
Definition: yomhook.F90:15