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_kill.f90

    r64 r257  
    2525  SUBROUTINE kill (npts, whichroutine, lm_lastyearmax, & 
    2626       ind, PFTpresent, cn_ind, biomass, senescence, RIP_time, & 
    27        lai, age, leaf_age, leaf_frac, & 
     27       lai, age, leaf_age, leaf_frac, npp_longterm, & 
    2828       when_growthinit, everywhere, veget, veget_max, bm_to_litter) 
    2929 
     
    3737    INTEGER(i_std), INTENT(in)                                       :: npts 
    3838    ! message 
    39     CHARACTER*10, INTENT(in)                                  :: whichroutine 
     39    CHARACTER(LEN=10), INTENT(in)                                  :: whichroutine 
    4040    ! last year's maximum leaf mass, for each PFT (gC/(m**2 of ground)) 
    4141    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)              :: lm_lastyearmax 
     
    7272    ! "maximal" coverage fraction of a PFT (LAI -> infinity) on ground 
    7373    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: veget_max 
     74    ! "long term" net primary productivity (gC/(m**2 of ground)/year) 
     75    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: npp_longterm  
    7476    ! conversion of biomass to litter (gC/(m**2 of ground)) / day 
    7577    REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)    :: bm_to_litter 
     
    98100          ! the "was_killed" business is necessary for a more efficient code on the VPP 
    99101 
    100           WHERE ( PFTpresent(:,j) .AND. & 
    101                ( ( ind(:,j) .LT. min_stomate ) .OR. & 
    102                ( lm_lastyearmax(:,j) .LT. min_stomate ) ) ) 
    103  
     102          IF ( control%ok_dgvm ) THEN 
     103             WHERE ( PFTpresent(:,j) .AND. & 
     104                  ( ( ind(:,j) .LT. min_stomate ) .OR. & 
     105                  ( lm_lastyearmax(:,j) .LT. min_stomate ) ) ) 
     106              
    104107             was_killed(:) = .TRUE. 
    105  
    106           ENDWHERE 
     108              
     109             ENDWHERE 
     110           
     111          ELSE 
     112             WHERE ( PFTpresent(:,j) .AND. &  
     113                  (biomass(:,j,icarbres) .LE.zero .OR. &  
     114                  biomass(:,j,iroot).LT.-min_stomate .OR. biomass(:,j,ileaf).LT.-min_stomate ).AND. &  
     115                  ind(:,j).GT. zero) 
     116 
     117                was_killed(:) = .TRUE. 
     118 
     119             ENDWHERE 
     120 
     121             IF(.NOT.tree(j).AND..NOT.lpj_gap_const_mort)THEN 
     122                WHERE ( was_killed(:) ) 
     123 
     124                   npp_longterm(:,j)=500. 
     125 
     126                ENDWHERE 
     127             ENDIF 
     128 
     129          ENDIF 
    107130 
    108131          IF ( ANY( was_killed(:) ) ) THEN 
    109132 
    110133             WHERE ( was_killed(:) ) 
    111  
    112                 ind(:,j) = 0.0 
    113134 
    114135                bm_to_litter(:,j,ileaf) = bm_to_litter(:,j,ileaf) + biomass(:,j,ileaf) 
     
    123144                bm_to_litter(:,j,icarbres) = bm_to_litter(:,j,icarbres) + biomass(:,j,icarbres) 
    124145 
    125                 biomass(:,j,ileaf) = 0.0 
    126                 biomass(:,j,isapabove) = 0.0 
    127                 biomass(:,j,isapbelow) = 0.0 
    128                 biomass(:,j,iheartabove) = 0.0 
    129                 biomass(:,j,iheartbelow) = 0.0 
    130                 biomass(:,j,iroot) = 0.0 
    131                 biomass(:,j,ifruit) = 0.0 
    132                 biomass(:,j,icarbres) = 0.0 
    133  
    134                 PFTpresent(:,j) = .FALSE. 
    135  
    136                 cn_ind(:,j) = 0.0 
     146                biomass(:,j,ileaf) = zero 
     147                biomass(:,j,isapabove) = zero 
     148                biomass(:,j,isapbelow) = zero 
     149                biomass(:,j,iheartabove) = zero 
     150                biomass(:,j,iheartbelow) = zero 
     151                biomass(:,j,iroot) = zero 
     152                biomass(:,j,ifruit) = zero 
     153                biomass(:,j,icarbres) = zero 
     154 
     155             ENDWHERE   ! number of individuals very low 
     156 
     157             IF (control%ok_dgvm) THEN 
     158 
     159                WHERE ( was_killed(:) ) 
     160                   PFTpresent(:,j) = .FALSE. 
     161 
     162                   veget_max(:,j) = zero 
     163                    
     164                   RIP_time(:,j) = zero 
     165 
     166                ENDWHERE  ! number of individuals very low 
     167 
     168             ENDIF 
     169 
     170             WHERE ( was_killed(:) ) 
     171 
     172                ind(:,j) = zero 
     173 
     174                cn_ind(:,j) = zero 
    137175 
    138176                senescence(:,j) = .FALSE. 
    139177 
    140  
    141                 age(:,j) = 0.0 
    142  
    143                 when_growthinit(:,j) = undef 
    144  
    145                 everywhere(:,j) = 0.0 
    146  
    147                 veget(:,j) = 0.0 
    148  
    149                 veget_max(:,j) = 0.0 
    150  
    151                 RIP_time(:,j) = 0.0 
     178                age(:,j) = zero 
     179 
     180                ! SZ: why undef ??? this causes a delay in reestablishment 
     181                !when_growthinit(:,j) = undef 
     182                when_growthinit(:,j) = large_value  
     183 
     184                everywhere(:,j) = zero 
     185 
     186                veget(:,j) = zero 
    152187 
    153188             ENDWHERE   ! number of individuals very low 
     
    157192                WHERE ( was_killed(:) ) 
    158193 
    159                    leaf_age(:,j,m) = 0.0  
    160                    leaf_frac(:,j,m) = 0.0  
     194                   leaf_age(:,j,m) = zero  
     195                   leaf_frac(:,j,m) = zero  
    161196 
    162197                ENDWHERE 
Note: See TracChangeset for help on using the changeset viewer.