SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
veg.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 veg( PSW_RAD, PTA, PQA, PPS, PRGL, PLAI, PRSMIN, &
7  pgamma, pf2, prs )
8 ! ####################################################################
9 !
10 !!**** *VEG*
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 ! Calculates the surface stomatal resistance Rs
16 !
17 !
18 !!** METHOD
19 !! ------
20 !
21 ! First calculates the F coefficients (i.e., f, F1, F2, F3, and F4).
22 !
23 ! Then, we have
24 !
25 ! Rs = Rsmin / ( F1 F2 F3 F4 LAI )
26 !
27 !! EXTERNAL
28 !! --------
29 !!
30 !! none
31 !!
32 !! IMPLICIT ARGUMENTS
33 !! ------------------
34 !!
35 !! none
36 !!
37 !!
38 !! REFERENCE
39 !! ---------
40 !!
41 !! Noilhan and Planton (1989)
42 !! Belair (1995)
43 !!
44 !! AUTHOR
45 !! ------
46 !!
47 !! S. Belair * Meteo-France *
48 !!
49 !! MODIFICATIONS
50 !! -------------
51 !! Original 13/03/95
52 !! (P.Jabouille) 13/11/96 mininum value for ZF1
53 !! (V. Masson) 28/08/98 add PF2 for Calvet (1998) CO2 computations
54 !! (V. Masson) 01/03/03 puts PF2 in a separate routine
55 !! (A. Boone) 21/1&/11 Rs_max in MODD_ISBA_PAR
56 !! (B. Decharme) 07/15 Add numerical adjustement for F2 soilstress function
57 !-------------------------------------------------------------------------------
58 !
59 !* 0. DECLARATIONS
60 ! ------------
61 !
62 USE modd_isba_par, ONLY : xrs_max, xdenom_min
63 USE mode_thermos
64 !
65 !
66 USE yomhook ,ONLY : lhook, dr_hook
67 USE parkind1 ,ONLY : jprb
68 !
69 IMPLICIT NONE
70 !
71 !* 0.1 declarations of arguments
72 !
73 !
74 REAL, DIMENSION(:), INTENT(IN) :: psw_rad, pta, pqa, pps
75 ! PSW_RAD = incoming solar radiation
76 ! PTA = near-surface air temperature
77 ! PQA = near-surface air specific humidity
78 ! PPS = surface pressure
79 !
80 REAL, DIMENSION(:), INTENT(IN) :: prgl, plai, prsmin, pgamma
81 ! PRGL = coefficient in the Rs formulation
82 ! PLAI = leaf area index
83 ! PRSMIN = minimum surface resistance
84 ! PGAMMA = coef. in the Rs calculation
85 !
86 REAL, DIMENSION(:), INTENT(IN) :: pf2 ! water stress coefficient
87 REAL, DIMENSION(:), INTENT(OUT) :: prs ! ground stomatal resistance
88 !
89 !
90 !* 0.2 declarations of local variables
91 !
92 REAL, DIMENSION(SIZE(PSW_RAD)) :: zf, zf1, zf2, zf3, zf4
93 ! temporary factors necessary to
94 ! calculate the surface stomatao resistance
95 !
96 REAL, DIMENSION(SIZE(PSW_RAD)) :: zqsat
97 ! ZQSAT = specific humidity at saturation
98 !
99 !
100 !* 0.3 declarations of local parameters:
101 !
102 REAL, PARAMETER :: zfactr_min = 1.e-3 ! minimum value for some parameters
103 ! ! to prevent from being too small
104 REAL, PARAMETER :: zrs_min = 1.e-4 ! minimum canopy resistance (s m-1)
105 !
106 REAL(KIND=JPRB) :: zhook_handle
107 !
108 !-------------------------------------------------------------------------------
109 !
110 IF (lhook) CALL dr_hook('VEG',0,zhook_handle)
111 !
112 !* 1. THE 'ZF1' FACTOR
113 ! ---------------
114 ! This factor measures the influence
115 ! of the photosynthetically active radiation
116 !
117 zf(:) = 0.55*2.*psw_rad(:) / (prgl(:)+ xdenom_min ) / ( plai(:)+ xdenom_min )
118 !
119 zf1(:) = ( zf(:) + prsmin(:)/xrs_max) /( 1. + zf(:) )
120 zf1(:) = max( zf1(:), xdenom_min )
121 !
122 !-------------------------------------------------------------------------------
123 !
124 !* 2. THE 'ZF2' FACTOR
125 ! ----------------
126 !
127 ! This factor takes into account the effect
128 ! of the water stress on the surface
129 ! resistance (see soilstress.F90)
130 !
131 ! - For intermediate soils it ranges (F2_min =< F2 <= 1):
132 ! where F2_min is a small numerical threshold
133 !
134 zf2(:) = max(xdenom_min,pf2(:))
135 !
136 !-------------------------------------------------------------------------------
137 !
138 !* 3. THE 'ZF3' FACTOR
139 ! ----------------
140 ! This factor represents the effect of
141 ! vapor pressure deficit of the atmosphere.
142 ! For very humid air, the stomatal resistance
143 ! is a small, whereas it increases as the
144 ! air is drier.
145 !
146 !
147 zqsat(:) = qsat(pta(:),pps(:))
148 !
149 zf3(:) = max( 1. - pgamma(:)*( zqsat(:) - pqa(:) )*1000. , zfactr_min )
150 !
151 !-------------------------------------------------------------------------------
152 !
153 !* 4. THE 'ZF4' FACTOR
154 ! ----------------
155 ! This factor introduces an air temperature
156 ! dependance on the surface stomatal resistance
157 !
158 zf4(:) = max( 1.0 - 0.0016*(298.15-pta(:))**2, zfactr_min )
159 !
160 !-------------------------------------------------------------------------------
161 !
162 !* 5. THE SURFACE STOMATAL RESISTANCE
163 ! -------------------------------
164 !
165 ! use Jarvis-resistance (in standard ISBA version):
166 ! otherwise use Jacobs/ISBA-Ags method (see routine COTWORES)
167 !
168 prs(:) = prsmin(:) / ( plai(:)+ xdenom_min ) &
169  / zf1(:) / zf2(:) /zf3(:) / zf4(:)
170 !
171 prs(:) = min( prs(:), xrs_max)
172 prs(:) = max( prs(:), zrs_min)
173 !
174 IF (lhook) CALL dr_hook('VEG',1,zhook_handle)
175 !
176 !-------------------------------------------------------------------------------
177 !
178 END SUBROUTINE veg
subroutine veg(PSW_RAD, PTA, PQA, PPS, PRGL, PLAI, PRSMIN, PGAMMA, PF2, PRS)
Definition: veg.F90:6