! Stomate: Land cover change ! ! authors: M. Boisserie, P. Friedlingstein, P. Smith ! ! ! ! ! version 1.0: May 2008 ! !< $HeadURL$ !< $Date$ !< $Author$ !< $Revision$ ! IPSL (2006) ! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC ! MODULE stomate_lcchange ! modules used: USE ioipsl USE stomate_data USE pft_parameters USE constantes IMPLICIT NONE PRIVATE PUBLIC lcchange_main CONTAINS SUBROUTINE lcchange_main ( npts, dt_days, veget_max, veget_max_new,& biomass, ind, age, PFTpresent, senescence, when_growthinit, everywhere, veget,& co2_to_bm, bm_to_litter, turnover_daily, bm_sapl, tree, cn_ind,flux10,flux100, & prod10,prod100,& !!$,prod10_total,prod100_total,& convflux,& !!$,cflux_prod_total, cflux_prod10,cflux_prod100, leaf_frac,& npp_longterm, lm_lastyearmax, litter, carbon) IMPLICIT NONE ! 0 declarations ! 0.1 input ! Domain size INTEGER, INTENT(in) :: npts ! Time step (days) REAL(r_std), INTENT(in) :: dt_days ! new "maximal" coverage fraction of a PFT (LAI -> infinity) on ground REAL(r_std), DIMENSION(npts,nvm), INTENT(INOUT) :: veget_max_new ! biomass of sapling (gC/individu) REAL(r_std) , DIMENSION (nvm, nparts), INTENT(in) :: bm_sapl ! is pft a tree LOGICAL, DIMENSION(nvm), INTENT(in) :: tree ! 0.2 modified fields ! fractional coverage on natural/agricultural ground, taking into ! account LAI (=grid-scale fpc) REAL(r_std), DIMENSION(npts,nvm), INTENT(inout) :: veget ! "maximal" coverage fraction of a PFT (LAI -> infinity) on nat/agri ground REAL(r_std), DIMENSION(npts,nvm), INTENT(inout) :: veget_max ! biomass (gC/(m**2 of nat/agri ground)) REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout) :: biomass ! density of individuals 1/m**2 REAL(r_std), DIMENSION(npts,nvm), INTENT(inout) :: ind ! mean age (years) REAL(r_std), DIMENSION(npts,nvm), INTENT(inout) :: age ! is the plant senescent? (only for deciduous trees - carbohydrate reserve) ! set to .FALSE. if PFT is introduced or killed LOGICAL, DIMENSION(npts,nvm), INTENT(inout) :: senescence ! PFT exists LOGICAL, DIMENSION(npts,nvm), INTENT(inout) :: PFTpresent ! is the PFT everywhere in the grid box or very localized (after its introduction) REAL(r_std), DIMENSION(npts,nvm), INTENT(inout) :: everywhere ! how many days ago was the beginning of the growing season REAL(r_std), DIMENSION(npts,nvm), INTENT(inout) :: when_growthinit ! biomass uptaken (gC/(m**2)/day) !NV passage 2D REAL(r_std), DIMENSION(npts,nvm), INTENT(inout) :: co2_to_bm ! conversion of biomass to litter (gC/(m**2 of nat/agri ground)) / day REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout) :: bm_to_litter ! crown area (m**2) per ind. REAL(r_std), DIMENSION(npts,nvm), INTENT(inout) :: cn_ind ! products remaining in the 10/100 year-turnover pool after the annual release for each compartment ! (10 or 100 + 1 : input from year of land cover change) REAL(r_std), DIMENSION(npts,0:10), INTENT(inout) :: prod10 REAL(r_std), DIMENSION(npts,0:100), INTENT(inout) :: prod100 ! annual release from the 10/100 year-turnover pool compartments REAL(r_std), DIMENSION(npts,10), INTENT(inout) :: flux10 REAL(r_std), DIMENSION(npts,100), INTENT(inout) :: flux100 ! fraction of leaves in leaf age class REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout) :: leaf_frac ! last year's maximum leaf mass, for each PFT (gC/(m**2 of nat/agri ground)) REAL(r_std), DIMENSION(npts,nvm), INTENT(inout) :: lm_lastyearmax ! "long term" net primary productivity (gC/(m**2 of nat/agri ground)/year) REAL(r_std), DIMENSION(npts,nvm), INTENT(inout) :: npp_longterm ! metabolic and structural litter, above and below ground (gC/(m**2 of ground)) REAL(r_std),DIMENSION(npts,nlitt,nvm,nlevs), INTENT(inout) :: litter ! carbon pool: active, slow, or passive,(gC/(m**2 of ground)) REAL(r_std),DIMENSION(npts,ncarb,nvm), INTENT(inout) :: carbon ! 0.3 output ! release during first year following land cover change REAL(r_std), DIMENSION(npts), INTENT(out) :: convflux ! total annual release from the 10/100 year-turnover pool REAL(r_std), DIMENSION(npts), INTENT(out) :: cflux_prod10, cflux_prod100 !!$ ! total products remaining in the pool after the annual release !!$ REAL(r_std), DIMENSION(npts), INTENT(out) :: prod10_total, prod100_total !!$ !!$ ! total flux from conflux and the 10/100 year-turnover pool !!$ REAL(r_std), DIMENSION(npts), INTENT(out) :: cflux_prod_total ! Turnover rates (gC/(m**2 of ground)/day) REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout) :: turnover_daily ! 0.4 local ! indices INTEGER(i_std) :: i, j, k, l, m ! biomass increase (gC/(m**2 of ground)) REAL(r_std) :: bm_new ! biomass loss (gC /(m˛ of ground)) REAL(r_std),DIMENSION(npts,nparts) :: biomass_loss REAL(r_std) :: above ! Litter dilution (gC/m˛) REAL(r_std),DIMENSION(npts,nlitt,nlevs) :: dilu_lit ! Soil Carbondilution (gC/m˛) REAL(r_std),DIMENSION(npts,ncarb) :: dilu_soil_carbon ! vecteur de conversion REAL(r_std),DIMENSION(nvm) :: delta_veg ! vecteur de conversion REAL(r_std) :: delta_veg_sum ! change in number of individuals REAL(r_std),DIMENSION(npts,nvm) :: delta_ind ! ========================================================================= IF (bavard.GE.3) WRITE(numout,*) 'Entering lcchange_main' ! yearly initialisation prod10(:,0) = zero prod100(:,0) = zero above = zero convflux(:) = zero cflux_prod10(:) = zero cflux_prod100(:) = zero !!$ prod10_total(:) = zero !!$ prod100_total(:) = zero !!$ cflux_prod_total(:) = zero delta_ind(:,:) = zero delta_veg(:) = zero DO i = 1, npts ! Génération du vecteur de conversion delta_veg(:) = veget_max_new(i,:)-veget_max(i,:) delta_veg_sum = SUM(delta_veg,MASK=delta_veg.LT.0.) dilu_lit(i,:,:) = zero dilu_soil_carbon(i,:) = zero biomass_loss(i,:) = zero DO j=2, nvm IF ( delta_veg(j) < -min_stomate ) THEN dilu_lit(i,:,:)= dilu_lit(i,:,:) + delta_veg(j)*litter(i,:,j,:) / delta_veg_sum dilu_soil_carbon(i,:)= dilu_soil_carbon(i,:) + delta_veg(j) * carbon(i,:,j) / delta_veg_sum biomass_loss(i,:)=biomass_loss(i,:) + biomass(i,j,:)*delta_veg(j) / delta_veg_sum ENDIF ENDDO DO j=2, nvm IF ( delta_veg(j) > min_stomate) THEN ! in case of establishment of a new PFT or extension of its coverage in a gridcell IF (veget_max(i,j) .LT. min_stomate) THEN IF (tree(j)) THEN cn_ind(i,j) = cn_sapl(j) ELSE cn_ind(i,j) = un ENDIF ind(i,j)= delta_veg(j) / cn_ind(i,j) PFTpresent(i,j) = .TRUE. everywhere(i,j) = un senescence(i,j) = .FALSE. age(i,j) = zero when_growthinit(i,j) = large_value leaf_frac(i,j,1) = un npp_longterm(i,j) = npp_longterm_init lm_lastyearmax(i,j) = bm_sapl(j,ileaf) * ind(i,j) ENDIF IF ( cn_ind(i,j) > min_stomate ) THEN delta_ind(i,j) = delta_veg(j) / cn_ind(i,j) ENDIF DO k = 1, nparts !added shilong 060316 bm_new = delta_ind(i,j) * bm_sapl(j,k) IF (veget_max(i,j) .GT. min_stomate) THEN IF ((bm_new/delta_veg(j)) > biomass(i,j,k)) THEN bm_new = biomass(i,j,k)*delta_veg(j) ENDIF ENDIF biomass(i,j,k) = ( biomass(i,j,k) * veget_max(i,j) + bm_new ) / veget_max_new(i,j) !NV passage 2D co2_to_bm(i,j) = co2_to_bm(i,j)+ (bm_new* dt_days) / (one_year * veget_max_new(i,j)) ENDDO ! Dilution des reservoirs ! Litter litter(i,:,j,:)=(litter(i,:,j,:) * veget_max(i,j) + & dilu_lit(i,:,:) * delta_veg(j)) / veget_max_new(i,j) ! Soil carbon carbon(i,:,j)=(carbon(i,:,j) * veget_max(i,j) + dilu_soil_carbon(i,:) * delta_veg(j)) / veget_max_new(i,j) ! Litter input bm_to_litter(i,j,isapbelow) = bm_to_litter(i,j,isapbelow) + & & biomass_loss(i,isapbelow)*delta_veg(j) / veget_max_new(i,j) bm_to_litter(i,j,iheartbelow) = bm_to_litter(i,j,iheartbelow) + biomass_loss(i,iheartbelow) *delta_veg(j) & & / veget_max_new(i,j) bm_to_litter(i,j,iroot) = bm_to_litter(i,j,iroot) + biomass_loss(i,iroot)*delta_veg(j) / veget_max_new(i,j) bm_to_litter(i,j,ifruit) = bm_to_litter(i,j,ifruit) + biomass_loss(i,ifruit)*delta_veg(j) / veget_max_new(i,j) bm_to_litter(i,j,icarbres) = bm_to_litter(i,j,icarbres) + & & biomass_loss(i,icarbres) *delta_veg(j) / veget_max_new(i,j) bm_to_litter(i,j,ileaf) = bm_to_litter(i,j,ileaf) + biomass_loss(i,ileaf)*delta_veg(j) / veget_max_new(i,j) age(i,j)=age(i,j)*veget_max(i,j)/veget_max_new(i,j) ! End if PFT extension ELSE ! PFT in reduction above = biomass(i,j,isapabove) + biomass(i,j,iheartabove) convflux(i) = convflux(i) - ( coeff_lcchange_1(j) * above * delta_veg(j) ) ! - car delta_veg <0 prod10(i,0) = prod10(i,0) - ( coeff_lcchange_10(j) * above * delta_veg(j) ) prod100(i,0) = prod100(i,0) - ( coeff_lcchange_100(j) * above * delta_veg(j) ) ! End Biomass Export IF ( veget_max_new(i,j) .LT. min_stomate ) THEN ! Total reduction veget_max_new(i,j)= zero ind(i,j) = zero biomass(i,j,:) = zero PFTpresent(i,j) = .FALSE. senescence(i,j) = .FALSE. age(i,j) = zero when_growthinit(i,j) = undef everywhere(i,j) = zero carbon(i,:,j) = zero litter(i,:,j,:) = zero bm_to_litter(i,j,:) = zero turnover_daily(i,j,:) = zero ENDIF ENDIF ! End if PFT's coverage reduction ENDDO ! End loop on PFTs ! each year, update 10 year-turnover pool content following flux emission ! (linear decay (10%) of the initial carbon input) DO l = 0, 8 m = 10 - l cflux_prod10(i) = cflux_prod10(i) + flux10(i,m) prod10(i,m) = prod10(i,m-1) - flux10(i,m-1) !MM=>stomate_lpj.f90 prod10_total(i) = prod10_total(i) + prod10(i,m) flux10(i,m) = flux10(i,m-1) IF (prod10(i,m) .LT. 1.0) prod10(i,m) = zero !MM => quid de prod10_total ??? ENDDO cflux_prod10(i) = cflux_prod10(i) + flux10(i,1) flux10(i,1) = 0.1 * prod10(i,0) prod10(i,1) = prod10(i,0) !MM => quid du test IF (prod10(i,1) .LT. 1.0) prod10(i,1) = 0.0 ???? !MM=>stomate_lpj.f90 prod10_total(i) = prod10_total(i) + prod10(i,1) DO l = 0, 98 m = 100 - l cflux_prod100(i) = cflux_prod100(i) + flux100(i,m) prod100(i,m) = prod100(i,m-1) - flux100(i,m-1) !MM=>stomate_lpj.f90 prod100_total(i) = prod100_total(i) + prod100(i,m) flux100(i,m) = flux100(i,m-1) IF (prod100(i,m).LT.1.0) prod100(i,m) = zero ENDDO cflux_prod100(i) = cflux_prod100(i) + flux100(i,1) flux100(i,1) = 0.01 * prod100(i,0) prod100(i,1) = prod100(i,0) !MM=> IF (prod100(i,1).LT.1.0) prod100(i,1) = zero !MM=>stomate_lpj.f90 prod100_total(i) = prod100_total(i) + prod100(i,1) prod10(i,0) = zero prod100(i,0) = zero ENDDO ! End loop on npts veget_max(:,:) = veget_max_new(:,:) ! convert flux from /year into /time step convflux = convflux/one_year*dt_days cflux_prod10 = cflux_prod10/one_year*dt_days cflux_prod100 = cflux_prod100/one_year*dt_days !MM=>stomate_lpj.f90 cflux_prod_total(:) = convflux(:) + cflux_prod10(:) + cflux_prod100(:) IF (bavard.GE.4) WRITE(numout,*) 'Leaving lcchange_main' END SUBROUTINE lcchange_main END MODULE stomate_lcchange