SURFEX v7.3
General documentation of Surfex
 All Classes Files Functions Variables Typedefs
/home/dasprezs/EXPORT_v7_3/src/SURFEX/nitro_decline.F90
Go to the documentation of this file.
00001 !     #########
00002 SUBROUTINE NITRO_DECLINE(HPHOTO, HRESPSL, OTR_ML, KSPINW ,            &
00003                 PBSLAI_NITRO, PSEFOLD, PGMES, PANMAX, PANDAY,         &
00004                 PLAT, PLAIMIN, PVEGTYPE, PTAU_WOOD,                   &
00005                 PANFM, PLAI, PBIOMASS, PRESP_BIOMASS, PBIOMASS_LEAF,  &
00006                 PINCREASE ,PTURNOVER                                  )  
00007 !
00008 !   ###############################################################
00009 !!**  NITRO_DECLINE 
00010 !!
00011 !!    PURPOSE
00012 !!    -------
00013 !!
00014 !!**  METHOD
00015 !!    ------
00016 !!     Calvet and Soussana (2001) and Gibelin et al. (2006) for nitrogen dilution.
00017 !!     Gibelin et al. (2008) : New biomass reservoirs, and new method for allocation, 
00018 !!     mortality and respiration.
00019 !!
00020 !!    EXTERNAL
00021 !!    --------
00022 !!    none
00023 !!
00024 !!    IMPLICIT ARGUMENTS
00025 !!    ------------------
00026 !!      
00027 !!    none
00028 !!
00029 !!    REFERENCE
00030 !!    ---------
00031 !!
00032 !! Calvet and Soussana (2001), "Modelling CO2-enrichment effects using an
00033 !! interactive vegetation SVAT scheme", Agricultural and Forest Meteorology, Vol. 108
00034 !! pp. 129-152
00035 !! Gibelin et al. (2008), "Modelling energy and CO2 fluxes with an interactive vegetation 
00036 !! land surface model - Evaluation at high and middle latitudes", 
00037 !! Agricultural and Forest Meteorology, Vol. 148 , pp. 1611-1628
00038 !!      
00039 !!    AUTHOR
00040 !!    ------
00041 !!
00042 !!      A.-L. Gibelin           * Meteo-France *
00043 !!      (following Belair)
00044 !!
00045 !!    MODIFICATIONS
00046 !!    -------------
00047 !!      Original    27/01/03 
00048 !!
00049 !!      P Le Moigne  09/2005 : AGS modifs of L. Jarlan
00050 !!      A.L. Gibelin 04/2009 : BIOMASS and RESP_BIOMASS arrays
00051 !!      A.L. Gibelin 04/2009 : Suppress unused arguments
00052 !!      A.L. Gibelin 04/2009 : Suppress unused modules and add ONLY
00053 !!      A.L. Gibelin 04/2009 : adaptation to SURFEX environment
00054 !!      A.   Barbu   01/2011 : modification of active biomass,leaf reservoir (see nitro_decline.f90)
00055 !!      C.   Delire  04/2012 : spinup wood carbon
00056 !!      B.   Decharme 05/2012 : Optimization
00057 !!                              ZCC_NITRO and ZBIOMASST_LIM in modd_co2v_par.F90
00058 !
00059 !-------------------------------------------------------------------------------
00060 !
00061 !*       0.     DECLARATIONS
00062 !               ------------
00063 !
00064 USE MODD_CSTS,           ONLY : XPI, XDAY
00065 USE MODD_CO2V_PAR,       ONLY : XPCCO2, XCC_NIT, XCA_NIT, XMC, &
00066                                 XMCO2, XCC_NITRO, XBIOMASST_LIM 
00067 USE MODD_DATA_COVER_PAR, ONLY : NVT_TREE, NVT_EVER, NVT_CONI
00068 !
00069 USE YOMHOOK   ,ONLY : LHOOK,   DR_HOOK
00070 USE PARKIND1  ,ONLY : JPRB
00071 !
00072 IMPLICIT NONE
00073 !
00074 !*      0.1    declarations of arguments
00075 !
00076  CHARACTER(LEN=*),     INTENT(IN) :: HPHOTO           ! Kind of photosynthesis
00077 !                                                    ! 'NON'
00078 !                                                    ! 'AGS'
00079 !                                                    ! 'LAI'
00080 !                                                    ! 'AST'
00081 !                                                    ! 'LST'
00082  CHARACTER(LEN=3),     INTENT(IN) :: HRESPSL          ! Soil Respiration
00083 !                                                    ! 'DEF' = Norman 1992
00084 !                                                    ! 'PRM' = Rivalland PhD Thesis (2003)
00085 !                                                    ! 'CNT' = CENTURY model (Gibelin 2008)
00086 LOGICAL,              INTENT(IN) :: OTR_ML           ! new TR
00087 INTEGER, INTENT(IN)              :: KSPINW           ! wood spinup
00088 !
00089 REAL,   DIMENSION(:), INTENT(IN) :: PBSLAI_NITRO     ! ratio of biomass to LAI
00090 REAL,   DIMENSION(:), INTENT(IN) :: PSEFOLD          ! e-folding time for senescence (s)
00091 REAL,   DIMENSION(:), INTENT(IN) :: PGMES            ! mesophyll conductance (m s-1)
00092 REAL,   DIMENSION(:), INTENT(IN) :: PANMAX           ! maximum photosynthesis rate
00093 REAL,   DIMENSION(:), INTENT(IN) :: PANDAY           ! daily net CO2 accumulation
00094 REAL,   DIMENSION(:), INTENT(IN) :: PLAT             ! latitude of each grid point
00095 REAL,   DIMENSION(:), INTENT(IN) :: PLAIMIN          ! minimum LAI
00096 REAL, DIMENSION(:,:), INTENT(IN) :: PVEGTYPE         ! fraction of each vegetation
00097 REAL,   DIMENSION(:), INTENT(IN) :: PTAU_WOOD        ! residence time in wood (s)
00098 REAL,   DIMENSION(:), INTENT(IN) :: PLAI             ! leaf area index (LAI) 
00099 !
00100 REAL,   DIMENSION(:), INTENT(INOUT) :: PANFM         ! maximum leaf assimilation
00101 REAL, DIMENSION(:,:), INTENT(INOUT) :: PBIOMASS      ! biomass reservoirs
00102 REAL, DIMENSION(:,:), INTENT(INOUT) :: PRESP_BIOMASS ! cumulated daily biomass respiration (kgDM m-2 day-1)
00103 !
00104 REAL,   DIMENSION(:), INTENT(OUT)   :: PBIOMASS_LEAF ! temporary leaf biomass
00105 REAL, DIMENSION(:,:), INTENT(OUT)   :: PINCREASE     ! increment of biomass
00106 REAL, DIMENSION(:,:), INTENT(OUT)   :: PTURNOVER     ! biomass turnover going into litter (gC m-2 s-1)
00107 !
00108 !*      0.2    declarations of local variables
00109 !
00110 REAL                            :: ZBMCOEF
00111 REAL,    DIMENSION(SIZE(PLAI))  :: ZXSEFOLD        ! e-folding time for senescence corrected (days)
00112 REAL,    DIMENSION(SIZE(PLAI))  :: ZLAIB_NITRO     ! LAI correction parameter used in sefold calculation
00113 REAL,    DIMENSION(SIZE(PLAI))  :: ZASSIM          ! assimilation
00114 REAL,    DIMENSION(SIZE(PLAI))  :: ZBIOMASST       ! leaf + active structural biomass
00115 !
00116 REAL, DIMENSION(SIZE(PLAI),SIZE(PBIOMASS,2))  :: ZINCREASE
00117 REAL, DIMENSION(SIZE(PLAI),SIZE(PBIOMASS,2))  :: ZBIOMASS      ! temporary biomass reservoirs
00118 REAL, DIMENSION(SIZE(PLAI),SIZE(PBIOMASS,2))  :: ZDECLINE      ! biomass decline (storage+mortality) (kgDM m-2 day-1)
00119 REAL, DIMENSION(SIZE(PLAI),SIZE(PBIOMASS,2))  :: ZSTORAGE      ! storage (part of decline kgDM m-2 day-1)
00120 REAL, DIMENSION(SIZE(PLAI))                   :: ZMORT_LEAF    ! leaf mortality
00121 !
00122 REAL, DIMENSION(SIZE(PLAI))                   :: ZWORK
00123 LOGICAL, DIMENSION(SIZE(PLAI))                :: LMASK_ASSIM, LMASK_VEGTYP
00124 !
00125 REAL(KIND=JPRB) :: ZHOOK_HANDLE
00126 !
00127 INTEGER :: JSPIN, JI, INI
00128 !
00129 ! correspondence between array indices and biomass compartments
00130 ! LEAF = 1
00131 ! STRUCT_ACT = 2
00132 ! STRUCT_PAS = 3
00133 ! STRUCT_BELOW = 4
00134 ! WOOD_ABOVE = 5
00135 ! WOOD_BELOW = 6
00136 !
00137 !-------------------------------------------------------------------------------
00138 !
00139 ! 1 - Initialisations
00140 ! -------------------
00141 !
00142 IF (LHOOK) CALL DR_HOOK('NITRO_DECLINE',0,ZHOOK_HANDLE)
00143 !
00144 INI = SIZE(PLAI)
00145 !
00146 ZXSEFOLD(:)         = 0.0
00147 ZLAIB_NITRO(:)      = 0.0
00148 ZBIOMASST(:)        = 0.0
00149 ZASSIM(:)           = 0.0
00150 ZBIOMASS(:,:)       = 0.0
00151 ZDECLINE(:,:)       = 0.0
00152 ZINCREASE(:,:)      = 0.0
00153 ZSTORAGE(:,:)       = 0.0
00154 ZMORT_LEAF(:)       = 0.0
00155 !---------------------------------------------------
00156 !
00157 ZBMCOEF     = XMC/(XMCO2*XPCCO2)
00158 !
00159 !-----------------------------------------------------------------
00160 !avoid possible but unlikely negative values for biomass:        
00161 !
00162 PBIOMASS(:,1) = MAX(PBIOMASS(:,1),0.0)
00163 !
00164 ! current leaf biomass value:
00165 !
00166 PBIOMASS_LEAF(:) = PBIOMASS(:,1)
00167 !
00168 !-------------------------------------------------------------------------------
00169 !
00170 ! Once a day (at midnight),repartition of net assimilation and mortality 
00171 ! into different biomass compartments.
00172 !
00173 ! 2 - Evolution of leaf biomass and senescence calculations
00174 ! ---------------------------------------------------------
00175 !
00176 ! coef c for biomass in kg/m2 now in modd_co2v_par.F90 (XCC_NITRO)
00177 !
00178 ! LAI correction for shadow effect
00179 IF (OTR_ML) THEN
00180   ZLAIB_NITRO(:) = 5.30
00181 ELSE
00182   ZLAIB_NITRO(:) = MAX( 5.76-0.64*ATAN(ABS(PLAT(:))*XPI/180.),3.8 )
00183 ENDIF
00184 !
00185 !
00186 ! leaf life expectancy
00187 !
00188 ZWORK(:) = 0.0
00189 WHERE(PGMES(:)>0.0)
00190       ZWORK(:) = 0.321*LOG(PGMES(:)*1000.)
00191       ZWORK(:) = EXP(ZWORK(:))*PLAI(:)/ZLAIB_NITRO(:)
00192 ENDWHERE
00193 ! before optimization
00194 !ZXSEFOLD(:)= PSEFOLD(:) * MAX(((PGMES(:)*1000.)**0.321)*PLAI(:)/ZLAIB_NITRO(:), 1.) * ...
00195 ZXSEFOLD(:) = PSEFOLD(:) * MAX(1.0,ZWORK(:)) * MIN(1.0,PANFM(:)/PANMAX(:)) / XDAY
00196 !
00197 ! avoid possible but unlikely division by zero
00198 !
00199 ZXSEFOLD(:) = MAX(1.0E-8,ZXSEFOLD(:))
00200 !
00201 ! limitation of leaf life expectancy
00202 !
00203 ! OLD   ZXSEFOLD(:) = MAX(5.,ZXSEFOLD(:))
00204 ! Following Marita's work limitation of the senesence
00205 ZXSEFOLD(:) = MAX(PSEFOLD(:)/XDAY/10.0,ZXSEFOLD(:))
00206 !
00207 ! senesence of active biomass
00208 !
00209 ZDECLINE(:,1) = MIN(PBIOMASS_LEAF(:)-PLAIMIN(:)*PBSLAI_NITRO(:), &
00210                     PBIOMASS_LEAF(:)*(1.0-EXP(-1.0/ZXSEFOLD(:))))
00211 !
00212 ! avoid negative values due to computation precision
00213 !
00214 ZDECLINE(:,1) = MAX(ZDECLINE(:,1),0.0)
00215 !
00216 ! current leaf biomass with assimilation and senescence
00217 !
00218 PBIOMASS_LEAF(:) = PBIOMASS_LEAF(:) - ZDECLINE(:,1)
00219 !
00220 ! daily active biomass assimilation
00221 !
00222 ZASSIM(:) = PANDAY(:)*ZBMCOEF
00223 !
00224 !-------------------------------------------------------------------------------
00225 !
00226 ! 3 - Evolution of active structural biomass
00227 ! ------------------------------------------
00228 !
00229 ZWORK(:) = 0.0
00230 WHERE(PBIOMASS_LEAF(:)>0.0)
00231       ZWORK(:) = (1.0/(1.0-XCA_NIT))*LOG(PBIOMASS_LEAF(:)/XCC_NITRO)
00232       ZWORK(:) = EXP(ZWORK(:))
00233 ENDWHERE
00234 !
00235 WHERE (ZASSIM(:) >= ZDECLINE(:,1))
00236   !
00237   ! 3.1 - Growing phase : plant nitrogen decline theory
00238   !
00239   ! the growth allometric law is applied
00240   ! repartition of total biomass    
00241   !
00242   !before optimization
00243   !ZBIOMASST(:)= MAX(PBIOMASS_LEAF(:), (PBIOMASS_LEAF(:)/XCC_NITRO)**(1.0/(1.0-XCA_NIT)))  
00244   ZBIOMASST(:) = MAX(PBIOMASS_LEAF(:), ZWORK(:))
00245   !
00246   ! active structural biomass increment and storage
00247   !
00248   ZBIOMASS(:,2)  = ZBIOMASST(:)  - PBIOMASS_LEAF(:)
00249   ZDECLINE(:,2)  = ZBIOMASS(:,2) * (1.0-EXP(-1.0*XDAY/PSEFOLD(:)))
00250   ZSTORAGE(:,1)  = ZBIOMASS(:,2) - PBIOMASS(:,2) + ZDECLINE(:,2) + PRESP_BIOMASS(:,2)
00251   !
00252 ELSE WHERE
00253   !
00254   ! 3.2 - Senescence phase
00255   !
00256   ! the active structural biomass dies exponentially at the lowest rate
00257   !
00258   ZSTORAGE(:,1) = 0.0
00259   ZDECLINE(:,2) = PBIOMASS(:,2) * (1.0-EXP(-1.0*XDAY/PSEFOLD(:)))
00260   ZBIOMASS(:,2) = PBIOMASS(:,2) - ZDECLINE(:,2) - PRESP_BIOMASS(:,2)
00261   !
00262   !  Avoid negative values of biomass
00263   !  No test on ZDECLINE(:,2) as it is not used after, or recalculated
00264   !  No test on PRESP_BIOMASS(:,2) as it should be smaller than PBIOMASS(:,2)
00265   !  otherwise there are irrealistic values of temperature     
00266   !
00267   ZBIOMASS(:,2) = MAX(ZBIOMASS(:,2),0.0)
00268   !
00269   ZBIOMASST(:) = PBIOMASS_LEAF(:) + ZBIOMASS(:,2)
00270   !
00271 END WHERE
00272 !
00273 ! 3.3 - Flow to the passive structural biomass: cut or growth after senescence
00274 ! Biomass is taken from active structural biomass, not from senescence of leaves
00275 ! 
00276 ZINCREASE(:,1) = ZASSIM(:)
00277 ZINCREASE(:,2) = ZSTORAGE(:,1)
00278 ZINCREASE(:,3) = -MIN(ZSTORAGE(:,1),0.0)
00279 !
00280 ZSTORAGE (:,1) = MAX(0.0,ZSTORAGE(:,1))
00281 !
00282 ! 3.4 - Mass conservation : leaf biomass sensecence must be >= structural storage
00283 !
00284 WHERE( ZSTORAGE(:,1) > ZDECLINE(:,1))
00285   ZDECLINE(:,2)    = PBIOMASS(:,2) * (1.0 - EXP(-1.0*XDAY/PSEFOLD(:)))
00286   ZBIOMASST(:)     = PBIOMASS(:,1) + PBIOMASS(:,2) - ZDECLINE(:,2) - PRESP_BIOMASS(:,2)  
00287 END WHERE
00288 !
00289 ZWORK(:) = 0.0
00290 WHERE( ZBIOMASST(:) > 0.0)
00291       ZWORK(:) = (1.0-XCA_NIT)*LOG(ZBIOMASST(:))
00292       ZWORK(:) = EXP(ZWORK(:))
00293 ENDWHERE
00294 !
00295 WHERE( ZSTORAGE(:,1) > ZDECLINE(:,1))
00296   !   
00297   !before optimization
00298   !PBIOMASS_LEAF(:)= ZCC_NITRO * (ZBIOMASST(:)**(1.0-XCA_NIT))
00299   PBIOMASS_LEAF(:) = XCC_NITRO * ZWORK(:)
00300   ZBIOMASS(:,2)    = ZBIOMASST(:)  - PBIOMASS_LEAF(:)
00301   ZDECLINE(:,1)    = PBIOMASS(:,1) - PBIOMASS_LEAF(:)
00302   ZSTORAGE(:,1)    = ZBIOMASS(:,2) - PBIOMASS(:,2) + ZDECLINE(:,2) + PRESP_BIOMASS(:,2)  
00303   !
00304   ZINCREASE(:,2) = ZSTORAGE(:,1)
00305   !
00306 END WHERE
00307 !
00308 !-------------------------------------------------------------------------------
00309 !
00310 ! 4 - Evolution of other biomass pools and final calculations
00311 ! -----------------------------------------------------------
00312 !
00313 ! 4.1 - Mortality of leaf biomass
00314 !
00315 ZMORT_LEAF(:) = MAX(0.0, ZDECLINE(:,1) - ZSTORAGE(:,1))
00316 !
00317 ZBIOMASS(:,3) = PBIOMASS(:,3)
00318 !
00319 IF (HPHOTO=='NIT') THEN
00320   !
00321   ! senesence of deep-structural biomass
00322   !
00323   ZDECLINE(:,3) = ZBIOMASS(:,3)*(1.0-EXP(-1.0*XDAY/PSEFOLD(:)))          
00324   !
00325   ! threshold value for leaf biomass and total above ground biomass in nitrogen
00326   ! dilution theory now in modd_co2v_par.F90 (XBIOMASST_LIM)
00327   !
00328   ! emergency deep structural biomass
00329   WHERE((ZBIOMASST(:) <= XBIOMASST_LIM) .AND. (ZXSEFOLD(:) > 1.0))
00330     ZBIOMASS(:,3) = ZBIOMASS(:,3) + ZMORT_LEAF(:)
00331   END WHERE
00332   !
00333 ELSEIF (HPHOTO=='NCB') THEN
00334   !
00335   ! 4.2 - Evolution of the other reservoirs
00336   ! 4.2.1 - senesence, avoiding negative values of biomass
00337   !
00338   ZDECLINE(:,3) = MIN(PBIOMASS(:,3)*(1.0-EXP(-1.0*XDAY/(PSEFOLD(:)/4.))), &
00339                       PBIOMASS(:,3)-PRESP_BIOMASS(:,3))            
00340   ZDECLINE(:,4) = MIN(PBIOMASS(:,4)*(1.0-EXP(-1.0*XDAY/PSEFOLD(:))), &
00341                       PBIOMASS(:,4)-PRESP_BIOMASS(:,4))
00342   !
00343   WHERE (PVEGTYPE(:,NVT_TREE)+PVEGTYPE(:,NVT_CONI)+PVEGTYPE(:,NVT_EVER) >= 0.5)
00344     ! Woody
00345     ZDECLINE(:,5) = PBIOMASS(:,5)*(1.0-EXP(-1.0*XDAY/PTAU_WOOD(:)))
00346     ZDECLINE(:,6) = PBIOMASS(:,6)*(1.0-EXP(-1.0*XDAY/PTAU_WOOD(:)))
00347   ELSEWHERE
00348     ! Herbaceous
00349     ZDECLINE(:,5) = 0.
00350     ZDECLINE(:,6) = 0.
00351   END WHERE
00352   !
00353   ! 4.2.2 - storage (part of decline used as input for other reservoirs)
00354   !
00355   LMASK_ASSIM (:)=(ZASSIM(:) >= ZDECLINE(:,1))
00356   LMASK_VEGTYP(:)=(PVEGTYPE(:,NVT_TREE)+PVEGTYPE(:,NVT_CONI)+PVEGTYPE(:,NVT_EVER)>=0.5)
00357   !
00358   WHERE (LMASK_ASSIM(:))
00359     !
00360     ! Remaining mortality is stored in roots.
00361     ZINCREASE(:,4)   = ZMORT_LEAF(:)
00362     !      
00363     ! Growing phase, all leaf decline is used as storage.
00364     ZSTORAGE(:,1)    = ZSTORAGE(:,1) + ZINCREASE(:,4)
00365     ZMORT_LEAF(:)    = ZMORT_LEAF(:) - ZINCREASE(:,4)
00366     !      
00367     ZSTORAGE(:,2)    = ZDECLINE(:,2)
00368     ZSTORAGE(:,3)    = ZDECLINE(:,3)
00369     !   
00370   ELSEWHERE
00371     !
00372     ! Senescence, a part of mortality is stored in roots, limited by assimilation rate.
00373     ZINCREASE(:,4)   = MIN(MAX(0.5*ZASSIM(:),0.) , 0.5*ZMORT_LEAF(:))
00374     !
00375     ZSTORAGE(:,1)    = ZSTORAGE(:,1) + ZINCREASE(:,4)
00376     ZMORT_LEAF(:)    = ZMORT_LEAF(:) - ZINCREASE(:,4)
00377     !   
00378   END WHERE
00379   !
00380   WHERE(LMASK_ASSIM(:).AND.LMASK_VEGTYP(:))
00381       ! Woody
00382       ZSTORAGE(:,4)  = ZDECLINE(:,4)
00383       !
00384       ZINCREASE(:,4) = ZINCREASE(:,4) + 0.3* (ZSTORAGE(:,2) + ZSTORAGE(:,3))
00385       ZINCREASE(:,5) =                  0.7* (ZSTORAGE(:,2) + ZSTORAGE(:,3))
00386       ZINCREASE(:,6) = ZSTORAGE(:,4)
00387       !
00388   ELSEWHERE(LMASK_ASSIM(:).AND..NOT.LMASK_VEGTYP(:))
00389       ! Herbaceous
00390       ZSTORAGE(:,4)  = 0.
00391       !
00392       ZINCREASE(:,4) = ZINCREASE(:,4) + ZSTORAGE(:,2) + ZSTORAGE(:,3)
00393       !
00394   END WHERE
00395   !
00396   WHERE (.NOT.LMASK_ASSIM(:).AND.LMASK_VEGTYP(:))
00397       ! Woody
00398       ! Senescence, only a part of decline is used as storage
00399       ZSTORAGE(:,2)  = 0.5*ZDECLINE(:,2)
00400       ZSTORAGE(:,3)  = 0.5*ZDECLINE(:,3)
00401       ZSTORAGE(:,4)  = 0.5*ZDECLINE(:,4)
00402       !
00403       ZINCREASE(:,5) = ZSTORAGE(:,2) + ZSTORAGE(:,3)
00404       ZINCREASE(:,6) = ZSTORAGE(:,4)
00405       !
00406   ELSEWHERE(.NOT.LMASK_ASSIM(:).AND..NOT.LMASK_VEGTYP(:))
00407       !  Herbaceous
00408       ! Senescence, no storage
00409       ZSTORAGE(:,2)  = 0.
00410       ZSTORAGE(:,3)  = 0.
00411       ZSTORAGE(:,4)  = 0.
00412       !
00413   END WHERE
00414   !
00415   ZSTORAGE(:,5) = 0.
00416   ZSTORAGE(:,6) = 0.
00417   !
00418   ! 4.2.3 - mortality (senescence - storage) and turnover
00419   !
00420   IF (HRESPSL=='CNT') THEN
00421     PTURNOVER(:,1) = ZMORT_LEAF(:)*1000.*XPCCO2/XDAY
00422     PTURNOVER(:,2) = (ZDECLINE(:,2) - ZSTORAGE(:,2))*1000.*XPCCO2/XDAY
00423     PTURNOVER(:,3) = (ZDECLINE(:,3) - ZSTORAGE(:,3))*1000.*XPCCO2/XDAY
00424     PTURNOVER(:,4) = (ZDECLINE(:,4) - ZSTORAGE(:,4))*1000.*XPCCO2/XDAY
00425     PTURNOVER(:,5) = (ZDECLINE(:,5) - ZSTORAGE(:,5))*1000.*XPCCO2/XDAY
00426     PTURNOVER(:,6) = (ZDECLINE(:,6) - ZSTORAGE(:,6))*1000.*XPCCO2/XDAY
00427   ENDIF
00428   !
00429 ENDIF
00430 !
00431 !
00432 ! 4.3 - Re-initialisations for next time step
00433 !
00434 ZBIOMASS(:,3) = ZBIOMASS(:,3) + ZINCREASE(:,3) - ZDECLINE(:,3) - PRESP_BIOMASS(:,3)
00435 !
00436 ! Add net accumulated CO2 assimilation 
00437 PBIOMASS_LEAF(:) = PBIOMASS_LEAF(:) + ZASSIM(:)
00438 !
00439 ! re-initialisation of biomass compartments values: X(day) <-- X(day-1)
00440 PBIOMASS(:,1) = PBIOMASS_LEAF(:)
00441 PBIOMASS(:,2) = ZBIOMASS(:,2)
00442 PBIOMASS(:,3) = ZBIOMASS(:,3)
00443 !
00444 ! re-initialisation of respiration and assimilation terms
00445 PRESP_BIOMASS(:,2) = 0.0
00446 PRESP_BIOMASS(:,3) = 0.0
00447 PANFM(:) = 0.0
00448 !
00449 !
00450 ! 4.2.4 - evolution of reservoirs
00451 !
00452 IF (HPHOTO=='NIT') THEN
00453   !
00454   PBIOMASS(:,3) = MAX(PBIOMASS(:,3),0.0)
00455   !
00456 ELSEIF (HPHOTO=='NCB') THEN
00457   !
00458   ZBIOMASS(:,4) = PBIOMASS(:,4) + ZINCREASE(:,4) - ZDECLINE(:,4) - PRESP_BIOMASS(:,4)
00459   !
00460 !
00461   ZBIOMASS(:,5) = PBIOMASS(:,5)
00462   ZBIOMASS(:,6) = PBIOMASS(:,6)
00463 !
00464   DO JSPIN = 1, KSPINW
00465     DO JI = 1,INI
00466        IF(LMASK_VEGTYP(JI))THEN
00467          !Woody
00468          ZBIOMASS(JI,5) = ZBIOMASS(JI,5) + ZINCREASE(JI,5) - ZDECLINE(JI,5)
00469          ZBIOMASS(JI,6) = ZBIOMASS(JI,6) + ZINCREASE(JI,6) - ZDECLINE(JI,6)
00470          ZDECLINE(JI,5) = ZBIOMASS(JI,5)*(1.0-EXP((-1.0*XDAY)/PTAU_WOOD(JI)))
00471          ZDECLINE(JI,6) = ZBIOMASS(JI,6)*(1.0-EXP((-1.0*XDAY)/PTAU_WOOD(JI)))
00472        ELSE   
00473          !Herbaceous
00474          ZBIOMASS(JI,5) = 0.
00475          ZBIOMASS(JI,6) = 0.
00476        ENDIF
00477     ENDDO
00478   ENDDO
00479 !
00480   PBIOMASS(:,4) = ZBIOMASS(:,4)
00481   PBIOMASS(:,5) = ZBIOMASS(:,5)
00482   PBIOMASS(:,6) = ZBIOMASS(:,6)
00483   !
00484   PRESP_BIOMASS(:,4) = 0.0
00485   !
00486   PINCREASE(:,:) = ZINCREASE(:,:)
00487 !  
00488 ENDIF
00489 !
00490 IF (LHOOK) CALL DR_HOOK('NITRO_DECLINE',1,ZHOOK_HANDLE)
00491 !
00492 END SUBROUTINE NITRO_DECLINE