SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
cotwo.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 cotwo(PCSP, PF2, PIA, PDS, PGAMMT, &
7  pfzero, pepso, panmax, pgmest, pgc, pdmax, &
8  pan, pgs, prd, plaitop, plai )
9 ! #########################################################################
10 !
11 !!**** *COTWO*
12 !!
13 !! PURPOSE
14 !! -------
15 !
16 ! Calculates net assimilation of CO2 and leaf conductance.
17 !
18 !!** METHOD
19 !! ------
20 ! Calvet et al. 1998 Forr. Agri. Met. [from model of Jacobs(1994)]
21 !!
22 !! EXTERNAL
23 !! --------
24 !! none
25 !!
26 !! IMPLICIT ARGUMENTS
27 !! ------------------
28 !!
29 !! USE MODD_CO2V_PAR
30 !!
31 !! REFERENCE
32 !! ---------
33 !!
34 !! Calvet et al. 1998 Forr. Agri. Met.
35 !!
36 !! AUTHOR
37 !! ------
38 !!
39 !! A. Boone * Meteo-France *
40 !! (following Belair)
41 !!
42 !! MODIFICATIONS
43 !! -------------
44 !! Original 27/10/97
45 !! L. Jarlan 27/10/04 : Add of photosynthesis (PPST variable) as output
46 !! of the routine in order to manage the calculation
47 !! of Soil respiration in cotwores and cotworestress
48 !! P Le Moigne 09/2005 AGS modifs of L. Jarlan
49 !! A.L. Gibelin 07/2009 : Suppress GPP and PPST as outputs
50 !! GPP is calculated in cotwores.f90 and cotworestress.f90
51 !! B. Decharme 2012 : optimization
52 !! C. Delire 2014 : Assuming a nitrogen profile with an exctinction coefficient
53 !! B. Decharme 07/15 : Bug = Add numerical adjustement for very dry soil
54 !!
55 !!
56 !-------------------------------------------------------------------------------
57 !
58 USE modd_csts, ONLY : xmv, xmd, xrholw
59 USE modd_co2v_par, ONLY : xrdcf, xairtoh2o, xco2toh2o, xcondstmin
60 USE modd_isba_par, ONLY : xdenom_min
61 !
62 !* 0. DECLARATIONS
63 ! ------------
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 ! Atmospheric forcing:
75 REAL, DIMENSION(:), INTENT(IN):: pcsp, pf2, pia, pds,pgammt
76 ! PCSP = atmospheric concentration of CO2
77 ! PF2 = normalized soil water stress
78 ! PIA = incident solar radiation
79 ! PDS = saturation deficit of atmosphere
80 ! verses the leaf surface (with correction)
81 ! PGAMMT = compensation point
82 !
83 ! Time constants:
84 !
85 REAL, DIMENSION(:), INTENT(IN) :: pfzero, pepso, panmax, pgmest, pgc, pdmax, plaitop, plai
86 ! PFZERO = ideal value of F, no photorespiration
87 ! or saturation deficit
88 ! PEPSO = maximum initial quantum use efficiency
89 ! (kgCO2 J-1 PAR)
90 ! PGAMM = CO2 conpensation concentration (kgCO2 kgAir-1)
91 ! PANMAX = maximum net assimilation
92 ! PGMEST = temperature response
93 ! of mesophyll conductance
94 ! PGC = cuticular conductance (m s-1)
95 ! PDMAX = maximum saturation deficit of
96 ! atmosphere tolerate by vegetation
97 ! PLAITOP = LAI (thickness of canopy) above considered layer
98 ! PLAI = canopy LAI
99 !
100 ! CO2 model outputs:
101 REAL, DIMENSION(:), INTENT(OUT) :: pan, pgs, prd
102 ! PAN = Net assimilation of CO2
103 ! PGS = Leaf conductance
104 ! PRD = Dark Respiration
105 !
106 !
107 !* 0.2 declarations of local variables
108 !
109 !
110 REAL, DIMENSION(SIZE(PAN)) :: zfmin, zdrap, zf, zwork
111 ! ZFMIN = minimum f factor
112 ! ZDRAP = ratio Ds/Dmax
113 ! ZF = factor related to diffusion
114 ! ZWORK = work array
115 !
116 REAL, DIMENSION(SIZE(PAN)) :: zcsp, zci, zcmin, zamin
117 ! ZCSP = atmospheric concentration
118 ! of CO2
119 ! ZCI = Leaf Internal concentration
120 ! of CO2
121 ! ZCMIN = minimim internal leaf
122 ! CO2 concentration
123 ! ZAMIN = minimum net
124 ! assimilation
125 !
126 REAL, DIMENSION(SIZE(PAN)) :: zam, zeps, zlef, zagr, zag
127 ! ZAM = net assimilation as a
128 ! function of CO2 deficit
129 ! ZEPS = initial quantum
130 ! use efficiency
131 ! ZLEF = leaf transpiration
132 ! ZAGR = assimilation rate ratio
133 ! ZAG = modified gross assimilation
134 ! rate
135 !
136 REAL, DIMENSION(SIZE(PAN)) :: zgsc, zgs
137 ! ZGSC = stomatal conductance to CO2
138 ! ZGS = cuticular conductance (m s-1)
139 !
140 INTEGER :: jj, iter
141 !
142 REAL(KIND=JPRB) :: zhook_handle
143 !
144 !-------------------------------------------------------------------------------
145 !
146 IF (lhook) CALL dr_hook('COTWO',0,zhook_handle)
147 !
148 !* X. COMPUTE PRELIMINARY QUANITIES NEEDED FOR CO2 MODEL
149 ! --------------------------------------------------
150 !
151 DO jj = 1, SIZE(pan)
152  !
153  !* X. BEGIN CO2 MODEL:
154  ! ----------------
155  !
156  ! Equation #s in
157  ! Jacob's Thesis:
158  !
159  zwork(jj) = max(pgc(jj)+pgmest(jj),xdenom_min)
160  !
161  ! Eq. 3.21
162  zfmin(jj) = pgc(jj)/zwork(jj) ! fmin
163  ! fmin <= f0, and so f <= f0
164  zfmin(jj) = min(zfmin(jj),pfzero(jj))
165  ! fmin > 0, and so PCI > PGAMMT
166  zfmin(jj) = max(zfmin(jj),xdenom_min)
167  !
168  ! f from specific humidity deficit ds (g kg-1)
169  !
170  IF (pdmax(jj).NE.0.) THEN
171  zdrap(jj)=min(1.0,pds(jj)/pdmax(jj))
172  ELSE
173  zdrap(jj)=1.
174  ENDIF
175  zf(jj) = pfzero(jj)*(1.0-zdrap(jj)) + zfmin(jj)*zdrap(jj)
176  !
177  zcsp(jj) = max(pcsp(jj),pgammt(jj)+1.e-6)
178  !
179  ! ci/cs ratio = f+(1.-f)*gammt/cs ; internal leaf CO2 concentration:
180  !
181  zci(jj) = zcsp(jj)*(zf(jj)+(1.0-zf(jj))*pgammt(jj)/zcsp(jj))
182  !
183  !
184  ! Eq. 3.23
185  zcmin(jj) = (pgc(jj)*zcsp(jj) + pgmest(jj)*pgammt(jj))/zwork(jj)
186  !
187  ! residual photosynthesis rate (kgCO2 kgAir-1 m s-1)
188  !
189  zamin(jj) = pgmest(jj)*(zcmin(jj)-pgammt(jj))
190  !
191  !
192  ! Eq. 3.12
193  !
194  ! light response curve (kgCO2 kgAir-1 m s-1)
195  !
196  zam(jj) = pgmest(jj)*(zci(jj)-pgammt(jj))
197  !
198  zam(jj) = -zam(jj)/panmax(jj)
199  zam(jj) = panmax(jj)*(1.0 - exp(zam(jj)))
200  zam(jj) = max(zam(jj),zamin(jj))
201  !
202  ! Assuming a nitrogen profile within the canopy with a Kn exctinction coefficient (Bonan et al, 2011)
203  ! that applies to dark respiration. Here Kn=0.2 (Mercado et al, 2009).
204  ! Rd is divised by LAI to be consistent with the logic of assimilation (calculated per unit LAI)
205  ! if not tropical forest, PLAITOP=0, PRD=ZAM*XRDCF
206  !
207  prd(jj) = zam(jj)*xrdcf/plai(jj)*exp(-0.2*plaitop(jj))
208  !
209  ! Initial quantum use efficiency (kgCO2 J-1 PAR m3 kgAir-1):
210  !
211  zeps(jj) = pepso(jj)*(zci(jj) - pgammt(jj))/(zci(jj) + 2.0*pgammt(jj))
212  !
213  IF (zam(jj)/=0.) THEN
214  pan(jj) = (zam(jj) + prd(jj))*( 1.0 - exp(-zeps(jj)*pia(jj) &
215  /(zam(jj) + prd(jj))) ) - prd(jj)
216  ELSE
217  pan(jj) = 0.
218  ENDIF
219  pan(jj) = max(-prd(jj),pan(jj))
220  !
221  ! Eq. 3.28
222  IF (zam(jj)/=0.) THEN
223  zagr(jj) = (pan(jj) + prd(jj))/(zam(jj) + prd(jj))
224  ELSE
225  zagr(jj)=0.
226  ENDIF
227  !
228  zag(jj) = pan(jj) - zamin(jj)*zdrap(jj)*zagr(jj) + &
229  prd(jj)*(1.0-zagr(jj))
230  !
231  zlef(jj) = 0.0 ! initialize leaf transpiration
232  !
233 ENDDO
234 !
235 ! Iterate bewteen GSC and LEF:
236 !
237 ! Iterations are for stomatal conductance and stomatal evaporation only
238 !
239 DO iter = 1, 3
240  !
241  DO jj = 1, SIZE(pan)
242  !
243  ! stomatal conductance for CO2 (m s-1):
244  !
245  zgsc(jj) = zag(jj)/(zcsp(jj) - zci(jj))
246  zgsc(jj) = max( xcondstmin, zgsc(jj))
247  zgsc(jj) = zgsc(jj) + xairtoh2o*zlef(jj)*( (zcsp(jj) + &
248  zci(jj))/(2.0*(zcsp(jj) - zci(jj))) )
249  !
250  IF (iter<3) THEN
251  !
252  zgs(jj) = 1.6*zgsc(jj)
253  !
254  ! compute transpiration (kgH2O kgAir-1 m s-1) from specific
255  ! humidity deficit
256  !
257  ! Eq. 3.5
258  zlef(jj) = zgs(jj)*pds(jj)
259  !
260  ENDIF
261  !
262  ENDDO
263  !
264 ENDDO
265 !
266 ! End of iterations
267 !
268 ! Final calculation of leaf conductance (stomatal AND cuticular)
269 !
270 ! Eq. 3.16
271 pgs(:) = xco2toh2o*zgsc(:) + pgc(:)
272 !
273 ! Prevent numerical artefact in plant transpiration when
274 ! soilstress is maximum (F2 = 0.0)
275 !
276 pgs(:) = pgs(:) * min(1.0,pf2(:)/xdenom_min)
277 !
278 IF (lhook) CALL dr_hook('COTWO',1,zhook_handle)
279 !
280 END SUBROUTINE cotwo
subroutine cotwo(PCSP, PF2, PIA, PDS, PGAMMT, PFZERO, PEPSO, PANMAX, PGMEST, PGC, PDMAX, PAN, PGS, PRD, PLAITOP, PLAI)
Definition: cotwo.F90:6