SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
nitro_decline.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 nitro_decline(HPHOTO, HRESPSL, OTR_ML, KSPINW , &
7  pbslai_nitro, psefold, pgmes, panmax, panday, &
8  plat, plaimin, pvegtype, ptau_wood, &
9  panfm, plai, pbiomass, presp_biomass, pbiomass_leaf, &
10  pincrease ,pturnover )
11 !
12 ! ###############################################################
13 !!** NITRO_DECLINE
14 !!
15 !! PURPOSE
16 !! -------
17 !!
18 !!** METHOD
19 !! ------
20 !! Calvet and Soussana (2001) and Gibelin et al. (2006) for nitrogen dilution.
21 !! Gibelin et al. (2008) : New biomass reservoirs, and new method for allocation,
22 !! mortality and respiration.
23 !!
24 !! EXTERNAL
25 !! --------
26 !! none
27 !!
28 !! IMPLICIT ARGUMENTS
29 !! ------------------
30 !!
31 !! none
32 !!
33 !! REFERENCE
34 !! ---------
35 !!
36 !! Calvet and Soussana (2001), "Modelling CO2-enrichment effects using an
37 !! interactive vegetation SVAT scheme", Agricultural and Forest Meteorology, Vol. 108
38 !! pp. 129-152
39 !! Gibelin et al. (2008), "Modelling energy and CO2 fluxes with an interactive vegetation
40 !! land surface model - Evaluation at high and middle latitudes",
41 !! Agricultural and Forest Meteorology, Vol. 148 , pp. 1611-1628
42 !!
43 !! AUTHOR
44 !! ------
45 !!
46 !! A.-L. Gibelin * Meteo-France *
47 !! (following Belair)
48 !!
49 !! MODIFICATIONS
50 !! -------------
51 !! Original 27/01/03
52 !!
53 !! P Le Moigne 09/2005 : AGS modifs of L. Jarlan
54 !! A.L. Gibelin 04/2009 : BIOMASS and RESP_BIOMASS arrays
55 !! A.L. Gibelin 04/2009 : Suppress unused arguments
56 !! A.L. Gibelin 04/2009 : Suppress unused modules and add ONLY
57 !! A.L. Gibelin 04/2009 : adaptation to SURFEX environment
58 !! A. Barbu 01/2011 : modification of active biomass,leaf reservoir (see nitro_decline.f90)
59 !! C. Delire 04/2012 : spinup wood carbon
60 !! R. Alkama 04/2012 : 19 vegtype rather than 12
61 !! B. Decharme 05/2012: Optimization
62 !! ZCC_NITRO and ZBIOMASST_LIM in modd_co2v_par.F90
63 !! C. Delire 01/2014 : sapwood respiration from IBIS
64 
65 !
66 !-------------------------------------------------------------------------------
67 !
68 !* 0. DECLARATIONS
69 ! ------------
70 !
71 USE modd_csts, ONLY : xpi, xday
72 USE modd_co2v_par, ONLY : xpcco2, xcc_nit, xca_nit, xmc, &
73  xmco2, xcc_nitro, xbiomasst_lim
74 USE modd_data_cover_par, ONLY : nvt_tebd, nvt_bone, nvt_trbe, nvt_trbd, &
75  nvt_tebe, nvt_tene, nvt_bobd, nvt_bond, &
76  nvt_shrb
77 !
78 USE yomhook ,ONLY : lhook, dr_hook
79 USE parkind1 ,ONLY : jprb
80 !
81 IMPLICIT NONE
82 !
83 !* 0.1 declarations of arguments
84 !
85  CHARACTER(LEN=*), INTENT(IN) :: hphoto ! Kind of photosynthesis
86 ! ! 'NON'
87 ! ! 'AGS'
88 ! ! 'LAI'
89 ! ! 'AST'
90 ! ! 'LST'
91  CHARACTER(LEN=3), INTENT(IN) :: hrespsl ! Soil Respiration
92 ! ! 'DEF' = Norman 1992
93 ! ! 'PRM' = Rivalland PhD Thesis (2003)
94 ! ! 'CNT' = CENTURY model (Gibelin 2008)
95 LOGICAL, INTENT(IN) :: otr_ml ! new TR
96 INTEGER, INTENT(IN) :: kspinw ! wood spinup
97 !
98 REAL, DIMENSION(:), INTENT(IN) :: pbslai_nitro ! ratio of biomass to LAI
99 REAL, DIMENSION(:), INTENT(IN) :: psefold ! e-folding time for senescence (s)
100 REAL, DIMENSION(:), INTENT(IN) :: pgmes ! mesophyll conductance (m s-1)
101 REAL, DIMENSION(:), INTENT(IN) :: panmax ! maximum photosynthesis rate
102 REAL, DIMENSION(:), INTENT(IN) :: panday ! daily net CO2 accumulation
103 REAL, DIMENSION(:), INTENT(IN) :: plat ! latitude of each grid point
104 REAL, DIMENSION(:), INTENT(IN) :: plaimin ! minimum LAI
105 REAL, DIMENSION(:,:), INTENT(IN) :: pvegtype ! fraction of each vegetation
106 REAL, DIMENSION(:), INTENT(IN) :: ptau_wood ! residence time in wood (s)
107 REAL, DIMENSION(:), INTENT(IN) :: plai ! leaf area index (LAI)
108 !
109 REAL, DIMENSION(:), INTENT(INOUT) :: panfm ! maximum leaf assimilation
110 REAL, DIMENSION(:,:), INTENT(INOUT) :: pbiomass ! biomass reservoirs
111 REAL, DIMENSION(:,:), INTENT(INOUT) :: presp_biomass ! cumulated daily biomass respiration (kgDM m-2 day-1)
112 !
113 REAL, DIMENSION(:), INTENT(OUT) :: pbiomass_leaf ! temporary leaf biomass
114 REAL, DIMENSION(:,:), INTENT(OUT) :: pincrease ! increment of biomass
115 REAL, DIMENSION(:,:), INTENT(OUT) :: pturnover ! biomass turnover going into litter (gC m-2 s-1)
116 !
117 !* 0.2 declarations of local variables
118 !
119 REAL :: zbmcoef
120 REAL, DIMENSION(SIZE(PLAI)) :: zxsefold ! e-folding time for senescence corrected (days)
121 REAL, DIMENSION(SIZE(PLAI)) :: zlaib_nitro ! LAI correction parameter used in sefold calculation
122 REAL, DIMENSION(SIZE(PLAI)) :: zassim ! assimilation
123 REAL, DIMENSION(SIZE(PLAI)) :: zbiomasst ! leaf + active structural biomass
124 !
125 REAL, DIMENSION(SIZE(PLAI),SIZE(PBIOMASS,2)) :: zincrease
126 REAL, DIMENSION(SIZE(PLAI),SIZE(PBIOMASS,2)) :: zbiomass ! temporary biomass reservoirs
127 REAL, DIMENSION(SIZE(PLAI),SIZE(PBIOMASS,2)) :: zdecline ! biomass decline (storage+mortality) (kgDM m-2 day-1)
128 REAL, DIMENSION(SIZE(PLAI),SIZE(PBIOMASS,2)) :: zstorage ! storage (part of decline kgDM m-2 day-1)
129 REAL, DIMENSION(SIZE(PLAI)) :: zmort_leaf ! leaf mortality
130 !
131 REAL, DIMENSION(SIZE(PLAI)) :: zwork,zresp
132 LOGICAL, DIMENSION(SIZE(PLAI)) :: gmask_assim
133 LOGICAL, DIMENSION(SIZE(PLAI)) :: gwoody
134 !
135 REAL(KIND=JPRB) :: zhook_handle
136 !
137 INTEGER :: jspin, ji, ini
138 !
139 ! correspondence between array indices and biomass compartments
140 ! LEAF = 1
141 ! STRUCT_ACT = 2
142 ! STRUCT_PAS = 3
143 ! STRUCT_BELOW = 4
144 ! WOOD_ABOVE = 5
145 ! WOOD_BELOW = 6
146 !
147 !-------------------------------------------------------------------------------
148 !
149 ! 1 - Initialisations
150 ! -------------------
151 !
152 IF (lhook) CALL dr_hook('NITRO_DECLINE',0,zhook_handle)
153 !
154 ini = SIZE(plai)
155 !
156 zxsefold(:) = 0.0
157 zlaib_nitro(:) = 0.0
158 zbiomasst(:) = 0.0
159 zassim(:) = 0.0
160 zbiomass(:,:) = 0.0
161 zdecline(:,:) = 0.0
162 zincrease(:,:) = 0.0
163 zstorage(:,:) = 0.0
164 zmort_leaf(:) = 0.0
165 !---------------------------------------------------
166 !
167 zbmcoef = xmc/(xmco2*xpcco2)
168 !
169 !-----------------------------------------------------------------
170 !avoid possible but unlikely negative values for biomass:
171 !
172 pbiomass(:,1) = max(pbiomass(:,1),0.0)
173 !
174 ! current leaf biomass value:
175 !
176 pbiomass_leaf(:) = pbiomass(:,1)
177 !
178 !-------------------------------------------------------------------------------
179 !
180 ! Once a day (at midnight),repartition of net assimilation and mortality
181 ! into different biomass compartments.
182 !
183 ! 2 - Evolution of leaf biomass and senescence calculations
184 ! ---------------------------------------------------------
185 !
186 ! coef c for biomass in kg/m2 now in modd_co2v_par.F90 (XCC_NITRO)
187 !
188 ! LAI correction for shadow effect
189 IF (otr_ml) THEN
190  zlaib_nitro(:) = 5.30
191 ELSE
192  zlaib_nitro(:) = max( 5.76-0.64*atan(abs(plat(:))*xpi/180.),3.8 )
193 ENDIF
194 !
195 !
196 ! leaf life expectancy
197 !
198 zwork(:) = 0.0
199 WHERE(pgmes(:)>0.0)
200  zwork(:) = 0.321*log(pgmes(:)*1000.)
201  zwork(:) = exp(zwork(:))*plai(:)/zlaib_nitro(:)
202 ENDWHERE
203 ! before optimization
204 !ZXSEFOLD(:)= PSEFOLD(:) * MAX(((PGMES(:)*1000.)**0.321)*PLAI(:)/ZLAIB_NITRO(:), 1.) * ...
205 zxsefold(:) = psefold(:) * max(1.0,zwork(:)) * min(1.0,panfm(:)/panmax(:)) / xday
206 !
207 ! avoid possible but unlikely division by zero
208 !
209 zxsefold(:) = max(1.0e-8,zxsefold(:))
210 !
211 ! limitation of leaf life expectancy
212 !
213 ! OLD ZXSEFOLD(:) = MAX(5.,ZXSEFOLD(:))
214 ! Following Marita's work limitation of the senesence
215 zxsefold(:) = max(psefold(:)/xday/10.0,zxsefold(:))
216 !
217 ! senesence of active biomass
218 !
219 zdecline(:,1) = min(pbiomass_leaf(:)-plaimin(:)*pbslai_nitro(:), &
220  pbiomass_leaf(:)*(1.0-exp(-1.0/zxsefold(:))))
221 !
222 ! avoid negative values due to computation precision
223 !
224 zdecline(:,1) = max(zdecline(:,1),0.0)
225 !
226 ! current leaf biomass with assimilation and senescence
227 !
228 pbiomass_leaf(:) = pbiomass_leaf(:) - zdecline(:,1)
229 !
230 ! daily active biomass assimilation
231 !
232 zassim(:) = panday(:)*zbmcoef
233 !
234 !-------------------------------------------------------------------------------
235 !
236 ! 3 - Evolution of active structural biomass
237 ! ------------------------------------------
238 !
239 zwork(:) = 0.0
240 WHERE(pbiomass_leaf(:)>0.0)
241  zwork(:) = (1.0/(1.0-xca_nit))*log(pbiomass_leaf(:)/xcc_nitro)
242  zwork(:) = exp(zwork(:))
243 ENDWHERE
244 !
245 WHERE (zassim(:) >= zdecline(:,1))
246  !
247  ! 3.1 - Growing phase : plant nitrogen decline theory
248  !
249  ! the growth allometric law is applied
250  ! repartition of total biomass
251  !
252  !before optimization
253  !ZBIOMASST(:)= MAX(PBIOMASS_LEAF(:), (PBIOMASS_LEAF(:)/XCC_NITRO)**(1.0/(1.0-XCA_NIT)))
254  zbiomasst(:) = max(pbiomass_leaf(:), zwork(:))
255  !
256  ! active structural biomass increment and storage
257  !
258  zbiomass(:,2) = zbiomasst(:) - pbiomass_leaf(:)
259  zdecline(:,2) = zbiomass(:,2) * (1.0-exp(-1.0*xday/psefold(:)))
260  zstorage(:,1) = zbiomass(:,2) - pbiomass(:,2) + zdecline(:,2) + presp_biomass(:,2)
261  !
262 ELSE WHERE
263  !
264  ! 3.2 - Senescence phase
265  !
266  ! the active structural biomass dies exponentially at the lowest rate
267  !
268  zstorage(:,1) = 0.0
269  zdecline(:,2) = pbiomass(:,2) * (1.0-exp(-1.0*xday/psefold(:)))
270  zbiomass(:,2) = pbiomass(:,2) - zdecline(:,2) - presp_biomass(:,2)
271  !
272  ! Avoid negative values of biomass
273  ! No test on ZDECLINE(:,2) as it is not used after, or recalculated
274  ! No test on PRESP_BIOMASS(:,2) as it should be smaller than PBIOMASS(:,2)
275  ! otherwise there are irrealistic values of temperature
276  !
277  zbiomass(:,2) = max(zbiomass(:,2),0.0)
278  !
279  zbiomasst(:) = pbiomass_leaf(:) + zbiomass(:,2)
280  !
281 END WHERE
282 !
283 ! 3.3 - Flow to the passive structural biomass: cut or growth after senescence
284 ! Biomass is taken from active structural biomass, not from senescence of leaves
285 !
286 zincrease(:,1) = zassim(:)
287 zincrease(:,2) = zstorage(:,1)
288 zincrease(:,3) = -min(zstorage(:,1),0.0)
289 !
290 zstorage(:,1) = max(0.0,zstorage(:,1))
291 !
292 ! 3.4 - Mass conservation : leaf biomass sensecence must be >= structural storage
293 !
294 WHERE( zstorage(:,1) > zdecline(:,1))
295  zdecline(:,2) = pbiomass(:,2) * (1.0 - exp(-1.0*xday/psefold(:)))
296  zbiomasst(:) = pbiomass(:,1) + pbiomass(:,2) - zdecline(:,2) - presp_biomass(:,2)
297 END WHERE
298 !
299 zwork(:) = 0.0
300 WHERE( zbiomasst(:) > 0.0)
301  zwork(:) = (1.0-xca_nit)*log(zbiomasst(:))
302  zwork(:) = exp(zwork(:))
303 ENDWHERE
304 !
305 WHERE( zstorage(:,1) > zdecline(:,1))
306  !
307  !before optimization
308  !PBIOMASS_LEAF(:)= ZCC_NITRO * (ZBIOMASST(:)**(1.0-XCA_NIT))
309  pbiomass_leaf(:) = xcc_nitro * zwork(:)
310  zbiomass(:,2) = zbiomasst(:) - pbiomass_leaf(:)
311  zdecline(:,1) = pbiomass(:,1) - pbiomass_leaf(:)
312  zstorage(:,1) = zbiomass(:,2) - pbiomass(:,2) + zdecline(:,2) + presp_biomass(:,2)
313  !
314  zincrease(:,2) = zstorage(:,1)
315  !
316 END WHERE
317 !
318 !-------------------------------------------------------------------------------
319 !
320 ! 4 - Evolution of other biomass pools and final calculations
321 ! -----------------------------------------------------------
322 !
323 ! 4.1 - Mortality of leaf biomass
324 !
325 zmort_leaf(:) = max(0.0, zdecline(:,1) - zstorage(:,1))
326 !
327 zbiomass(:,3) = pbiomass(:,3)
328 !
329 IF (hphoto=='NIT') THEN
330  !
331  ! senesence of deep-structural biomass
332  !
333  zdecline(:,3) = zbiomass(:,3)*(1.0-exp(-1.0*xday/psefold(:)))
334  !
335  ! threshold value for leaf biomass and total above ground biomass in nitrogen
336  ! dilution theory now in modd_co2v_par.F90 (XBIOMASST_LIM)
337  !
338  ! emergency deep structural biomass
339  WHERE((zbiomasst(:) <= xbiomasst_lim) .AND. (zxsefold(:) > 1.0))
340  zbiomass(:,3) = zbiomass(:,3) + zmort_leaf(:)
341  END WHERE
342  !
343 ELSEIF (hphoto=='NCB') THEN
344  !
345  gwoody = (pvegtype(:,nvt_tebd)+pvegtype(:,nvt_bone)+pvegtype(:,nvt_trbe)+ &
346  pvegtype(:,nvt_trbd)+pvegtype(:,nvt_tebe)+pvegtype(:,nvt_tene)+ &
347  pvegtype(:,nvt_bobd)+pvegtype(:,nvt_bond)+pvegtype(:,nvt_shrb) >= 0.5)
348  !
349  ! 4.2 - Evolution of the other reservoirs
350  ! 4.2.1 - senesence, avoiding negative values of biomass
351  !
352  zdecline(:,3) = min(pbiomass(:,3)*(1.0-exp(-1.0*xday/(psefold(:)/4.))), &
353  pbiomass(:,3)-presp_biomass(:,3))
354  zdecline(:,4) = min(pbiomass(:,4)*(1.0-exp(-1.0*xday/psefold(:))), &
355  pbiomass(:,4)-presp_biomass(:,4))
356  !
357  WHERE (gwoody(:))
358  ! Woody
359  zdecline(:,5) = min(pbiomass(:,5)*(1.0-exp(-1.0*xday/ptau_wood(:))), &
360  pbiomass(:,5)-presp_biomass(:,5))
361  zdecline(:,6) = pbiomass(:,6)*(1.0-exp(-1.0*xday/ptau_wood(:)))
362  ELSEWHERE
363  ! Herbaceous
364  zdecline(:,5) = 0.
365  zdecline(:,6) = 0.
366  END WHERE
367  !
368  ! 4.2.2 - storage (part of decline used as input for other reservoirs)
369  !
370  gmask_assim(:)=(zassim(:) >= zdecline(:,1))
371  !
372  WHERE (gmask_assim(:))
373  !
374  ! Remaining mortality is stored in roots.
375  zincrease(:,4) = zmort_leaf(:)
376  !
377  ! Growing phase, all leaf decline is used as storage.
378  zstorage(:,1) = zstorage(:,1) + zincrease(:,4)
379  zmort_leaf(:) = zmort_leaf(:) - zincrease(:,4)
380  !
381  zstorage(:,2) = zdecline(:,2)
382  zstorage(:,3) = zdecline(:,3)
383  !
384  ELSEWHERE
385  !
386  ! Senescence, a part of mortality is stored in roots, limited by assimilation rate.
387  zincrease(:,4) = min(max(0.5*zassim(:),0.) , 0.5*zmort_leaf(:))
388  !
389  zstorage(:,1) = zstorage(:,1) + zincrease(:,4)
390  zmort_leaf(:) = zmort_leaf(:) - zincrease(:,4)
391  !
392  END WHERE
393  !
394  WHERE(gmask_assim(:).AND.gwoody(:))
395  ! Woody
396  zstorage(:,4) = zdecline(:,4)
397  !
398  zincrease(:,4) = zincrease(:,4) + 0.3* (zstorage(:,2) + zstorage(:,3))
399  zincrease(:,5) = 0.7* (zstorage(:,2) + zstorage(:,3))
400  zincrease(:,6) = zstorage(:,4)
401  !
402  ELSEWHERE(gmask_assim(:).AND..NOT.gwoody(:))
403  ! Herbaceous
404  zstorage(:,4) = 0.
405  !
406  zincrease(:,4) = zincrease(:,4) + zstorage(:,2) + zstorage(:,3)
407  !
408  END WHERE
409  !
410  WHERE (.NOT.gmask_assim(:).AND.gwoody(:))
411  ! Woody
412  ! Senescence, only a part of decline is used as storage
413  zstorage(:,2) = 0.5*zdecline(:,2)
414  zstorage(:,3) = 0.5*zdecline(:,3)
415  zstorage(:,4) = 0.5*zdecline(:,4)
416  !
417  zincrease(:,5) = zstorage(:,2) + zstorage(:,3)
418  zincrease(:,6) = zstorage(:,4)
419  !
420  ELSEWHERE(.NOT.gmask_assim(:).AND..NOT.gwoody(:))
421  ! Herbaceous
422  ! Senescence, no storage
423  zstorage(:,2) = 0.
424  zstorage(:,3) = 0.
425  zstorage(:,4) = 0.
426  !
427  END WHERE
428  !
429  zstorage(:,5) = 0.
430  zstorage(:,6) = 0.
431  !
432  ! 4.2.3 - mortality (senescence - storage) and turnover
433  !
434  IF (hrespsl=='CNT') THEN
435  pturnover(:,1) = zmort_leaf(:)*1000.*xpcco2/xday
436  pturnover(:,2) = (zdecline(:,2) - zstorage(:,2))*1000.*xpcco2/xday
437  pturnover(:,3) = (zdecline(:,3) - zstorage(:,3))*1000.*xpcco2/xday
438  pturnover(:,4) = (zdecline(:,4) - zstorage(:,4))*1000.*xpcco2/xday
439  pturnover(:,5) = (zdecline(:,5) - zstorage(:,5))*1000.*xpcco2/xday
440  pturnover(:,6) = (zdecline(:,6) - zstorage(:,6))*1000.*xpcco2/xday
441  ENDIF
442  !
443 ENDIF
444 !
445 !
446 ! 4.3 - Re-initialisations for next time step
447 !
448 zbiomass(:,3) = zbiomass(:,3) + zincrease(:,3) - zdecline(:,3) - presp_biomass(:,3)
449 !
450 ! Add net accumulated CO2 assimilation
451 pbiomass_leaf(:) = pbiomass_leaf(:) + zassim(:)
452 !
453 ! re-initialisation of biomass compartments values: X(day) <-- X(day-1)
454 pbiomass(:,1) = pbiomass_leaf(:)
455 pbiomass(:,2) = zbiomass(:,2)
456 pbiomass(:,3) = zbiomass(:,3)
457 !
458 ! re-initialisation of respiration and assimilation terms
459 presp_biomass(:,2) = 0.0
460 presp_biomass(:,3) = 0.0
461 panfm(:) = 0.0
462 !
463 !
464 ! 4.2.4 - evolution of reservoirs
465 !
466 IF (hphoto=='NIT') THEN
467  !
468  pbiomass(:,3) = max(pbiomass(:,3),0.0)
469  !
470 ELSEIF (hphoto=='NCB') THEN
471  !
472  zbiomass(:,4) = pbiomass(:,4) + zincrease(:,4) - zdecline(:,4) - presp_biomass(:,4)
473  !
474 !
475  zbiomass(:,5) = pbiomass(:,5)
476  zbiomass(:,6) = pbiomass(:,6)
477  zresp(:) = presp_biomass(:,5)
478 !
479  DO jspin = 1, kspinw
480  DO ji = 1,ini
481  IF(gwoody(ji))THEN
482  !Woody
483  zbiomass(ji,5) = zbiomass(ji,5) + zincrease(ji,5) - zdecline(ji,5) - zresp(ji)
484  zbiomass(ji,6) = zbiomass(ji,6) + zincrease(ji,6) - zdecline(ji,6)
485  zdecline(ji,5) = zbiomass(ji,5)*(1.0-exp((-1.0*xday)/ptau_wood(ji)))
486  zdecline(ji,6) = zbiomass(ji,6)*(1.0-exp((-1.0*xday)/ptau_wood(ji)))
487  IF (pbiomass(ji,5) .gt. 0.0) zresp(ji) = presp_biomass(ji,5)/pbiomass(ji,5) * zbiomass(ji,5)
488  ELSE
489  !Herbaceous
490  zbiomass(ji,5) = 0.
491  zbiomass(ji,6) = 0.
492  ENDIF
493  ENDDO
494  ENDDO
495 !
496  pbiomass(:,4) = zbiomass(:,4)
497  pbiomass(:,5) = zbiomass(:,5)
498  pbiomass(:,6) = zbiomass(:,6)
499  !
500  presp_biomass(:,4) = 0.0
501  presp_biomass(:,5) = 0.0
502  !
503  pincrease(:,:) = zincrease(:,:)
504 !
505 ENDIF
506 !
507 IF (lhook) CALL dr_hook('NITRO_DECLINE',1,zhook_handle)
508 !
509 END SUBROUTINE nitro_decline
subroutine nitro_decline(HPHOTO, HRESPSL, OTR_ML, KSPINW, PBSLAI_NITRO, PSEFOLD, PGMES, PANMAX, PANDAY, PLAT, PLAIMIN, PVEGTYPE, PTAU_WOOD, PANFM, PLAI, PBIOMASS, PRESP_BIOMASS, PBIOMASS_LEAF, PINCREASE, PTURNOVER)