Ignore:
Timestamp:
2011-06-17T14:02:17+02:00 (13 years ago)
Author:
didier.solyga
Message:

Externalized version merged with the trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/ORCHIDEE_EXT/ORCHIDEE/src_stomate/lpj_pftinout.f90

    r64 r257  
    3333  SUBROUTINE pftinout (npts, dt, adapted, regenerate, & 
    3434       neighbours, veget, veget_max, & 
    35        biomass, ind, age, leaf_frac, npp_longterm, lm_lastyearmax, senescence, & 
     35       biomass, ind, cn_ind, age, leaf_frac, npp_longterm, lm_lastyearmax, senescence, & 
    3636       PFTpresent, everywhere, when_growthinit, need_adjacent, RIP_time, & 
    3737       co2_to_bm, & 
     
    6666    ! density of individuals 1/m**2 
    6767    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: ind 
     68    ! crownarea of individuals m**2 
     69    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)              :: cn_ind 
    6870    ! mean age (years) 
    6971    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: age 
     
    104106    REAL(r_std), DIMENSION(npts)                               :: avail 
    105107    ! indices 
    106     INTEGER(i_std)                                             :: i,j 
     108    INTEGER(i_std)                                             :: i,j,m 
    107109    ! total woody vegetation cover 
    108110    REAL(r_std), DIMENSION(npts)                               :: sumfrac_wood 
     
    111113    ! we can introduce this PFT 
    112114    LOGICAL, DIMENSION(npts)                                  :: can_introduce 
     115    ! no real need for dimension(ntps) except for vectorisation 
     116    REAL(r_std), DIMENSION(npts)                               :: fracnat 
    113117 
    114118    ! ========================================================================= 
     
    132136    ! 
    133137 
    134     ! need to know total woody vegetation fraction 
    135  
     138    ! 2.1 Only natural part of the grid cell 
     139    ! 
     140    !SZ bug correction MERGE: need to subtract agricultural area! 
     141    ! fraction of agricultural surface 
     142    fracnat(:) = 1. 
     143    do j = 2,nvm 
     144       IF ( .NOT. natural(j) ) THEN 
     145          fracnat(:) = fracnat(:) - veget_max(:,j) 
     146       ENDIF 
     147    ENDDO 
     148 
     149    ! 
     150    ! 2.2 total woody fpc on grid 
     151    ! 
    136152    sumfrac_wood(:) = zero 
    137153 
    138154    DO j = 2,nvm 
    139  
    140        IF ( tree(j) ) THEN 
    141  
    142           sumfrac_wood(:) = sumfrac_wood(:) + veget(:,j) 
    143  
     155       !SZ problem here: agriculture, not convinced that this representation of LPJ is correct 
     156       !if agriculture is present, ind must be recalculated to correspond to the natural density... 
     157       ! since ind is per grid cell, can be achived by discounting for agricultura fraction 
     158       IF ( natural(j).AND.tree(j) ) THEN 
     159          WHERE(fracnat(:).GT.min_stomate) 
     160                sumfrac_wood(:) = sumfrac_wood(:) + cn_ind(:,j) * ind(:,j) / fracnat(:) &  
     161                     * ( 1. - exp( - lm_lastyearmax(:,j) * sla(j) * ext_coeff(j) ) ) 
     162                !lai changed to lm_last 
     163          ENDWHERE 
    144164       ENDIF 
    145  
    146165    ENDDO 
    147166 
Note: See TracChangeset for help on using the changeset viewer.