Ignore:
Timestamp:
2011-03-08T10:00:09+01:00 (13 years ago)
Author:
didier.solyga
Message:

Change herbivory model : herbivores is pft-dependent now (with N.Vuichard & N.Viovy)

File:
1 edited

Legend:

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

    r64 r135  
    166166    ! sum of natural fpcs 
    167167    REAL(r_std), DIMENSION(npts)                            :: sumfpc_nat 
     168!!$ 01/03/2011 NVuichard, NViovy and DS : correcting herbivores : now  weighttot 
     169!!$ nlflong_nat, green_age are pft-dependants 
    168170    ! weights 
    169     REAL(r_std), DIMENSION(npts)                            :: weighttot 
     171    REAL(r_std), DIMENSION(npts,nvm)                            :: weighttot 
    170172    ! natural long-term leaf NPP ( gC/m**2/year) 
    171     REAL(r_std), DIMENSION(npts)                            :: nlflong_nat 
     173    REAL(r_std), DIMENSION(npts,nvm)                            :: nlflong_nat 
    172174    ! residence time of green tissue (years) 
    173     REAL(r_std), DIMENSION(npts)                            :: green_age 
     175    REAL(r_std), DIMENSION(npts,nvm)                            :: green_age 
     176 
     177! ds 04/03    Old formulation for herbivores 
     178!!$    ! weights 
     179!!$    REAL(r_std), DIMENSION(npts)                            :: weighttot 
     180!!$    ! natural long-term leaf NPP ( gC/m**2/year) 
     181!!$    REAL(r_std), DIMENSION(npts)                            :: nlflong_nat 
     182!!$    ! residence time of green tissue (years) 
     183!!$    REAL(r_std), DIMENSION(npts)                            :: green_age 
     184 
    174185    ! herbivore consumption (gC/m**2/day) 
    175186    REAL(r_std), DIMENSION(npts)                            :: consumption 
     
    927938    ! 
    928939 
    929     nlflong_nat(:) = zero 
    930     weighttot(:) = zero 
    931     green_age(:) = zero 
     940!!$ 01/03/2011 NVuichard, NViovy and DS : correcting herbivory activity : now  weighttot 
     941!!$ nlflong_nat, green_age are pft-dependants 
     942 
     943!!$    nlflong_nat(:) = zero 
     944!!$    weighttot(:) = zero 
     945!!$    green_age(:) = zero 
     946!!$    ! 
     947!!$    DO j = 2,nvm 
     948!!$       ! 
     949!!$       IF ( natural(j) ) THEN 
     950!!$          ! 
     951!!$          weighttot(:) = weighttot(:) + lm_lastyearmax(:,j) 
     952!!$          nlflong_nat(:) = nlflong_nat(:) + npp_longterm(:,j) * leaf_frac_hvc 
     953!!$          ! 
     954!!$          IF ( pheno_model(j) .EQ. 'none' ) THEN 
     955!!$             green_age(:) = green_age(:) + green_age_ever * lm_lastyearmax(:,j) 
     956!!$          ELSE 
     957!!$             green_age(:) = green_age(:) + green_age_dec * lm_lastyearmax(:,j) 
     958!!$          ENDIF 
     959!!$          ! 
     960!!$       ENDIF 
     961!!$       ! 
     962!!$    ENDDO 
     963!!$    ! 
     964!!$    WHERE ( weighttot(:) .GT. zero ) 
     965!!$       green_age(:) = green_age(:) / weighttot(:) 
     966!!$    ELSEWHERE 
     967!!$       green_age(:) = 1. 
     968!!$    ENDWHERE 
     969!!$ 
     970!!$    ! 
     971!!$    ! 22.2 McNaughton et al. give herbivore consumption as a function of annual leaf NPP. 
     972!!$    !      The annual leaf NPP can give us an idea about the edible biomass: 
     973!!$    ! 
     974!!$ 
     975!!$    DO j = 2,nvm 
     976!!$       ! 
     977!!$       IF ( natural(j) ) THEN 
     978!!$          ! 
     979!!$          WHERE ( nlflong_nat(:) .GT. zero ) 
     980!!$             consumption(:) = hvc1 * nlflong_nat(:) ** hvc2 
     981!!$             herbivores(:,j) = one_year * green_age(:) * nlflong_nat(:) / consumption(:) 
     982!!$          ELSEWHERE 
     983!!$             herbivores(:,j) = 100000. 
     984!!$          ENDWHERE 
     985!!$          ! 
     986!!$       ELSE 
     987!!$          ! 
     988!!$          herbivores(:,j) = 100000. 
     989!!$          ! 
     990!!$       ENDIF 
     991!!$       ! 
     992!!$    ENDDO 
     993!!$    herbivores(:,ibare_sechiba) = zero 
     994 
     995    nlflong_nat(:,:) = zero 
     996    weighttot(:,:) = zero 
     997    green_age(:,:) = zero 
    932998    ! 
    933999    DO j = 2,nvm 
     
    9351001       IF ( natural(j) ) THEN 
    9361002          ! 
    937           weighttot(:) = weighttot(:) + lm_lastyearmax(:,j) 
    938           nlflong_nat(:) = nlflong_nat(:) + npp_longterm(:,j) * leaf_frac_hvc 
     1003          weighttot(:,j) = lm_lastyearmax(:,j) 
     1004          nlflong_nat(:,j) = npp_longterm(:,j) * leaf_frac_hvc 
    9391005          ! 
    9401006          IF ( pheno_model(j) .EQ. 'none' ) THEN 
    941              green_age(:) = green_age(:) + green_age_ever * lm_lastyearmax(:,j) 
     1007             green_age(:,j) = green_age_ever * lm_lastyearmax(:,j) 
    9421008          ELSE 
    943              green_age(:) = green_age(:) + green_age_dec * lm_lastyearmax(:,j) 
     1009             green_age(:,j) = green_age_dec * lm_lastyearmax(:,j) 
    9441010          ENDIF 
    9451011          ! 
     
    9481014    ENDDO 
    9491015    ! 
    950     WHERE ( weighttot(:) .GT. zero ) 
    951        green_age(:) = green_age(:) / weighttot(:) 
     1016    WHERE ( weighttot(:,:) .GT. zero ) 
     1017       green_age(:,:) = green_age(:,:) / weighttot(:,:) 
    9521018    ELSEWHERE 
    953        green_age(:) = 1. 
     1019       green_age(:,:) = un 
    9541020    ENDWHERE 
    9551021 
     
    9631029       IF ( natural(j) ) THEN 
    9641030          ! 
    965           WHERE ( nlflong_nat(:) .GT. zero ) 
    966              consumption(:) = hvc1 * nlflong_nat(:) ** hvc2 
    967              herbivores(:,j) = one_year * green_age(:) * nlflong_nat(:) / consumption(:) 
     1031          WHERE ( nlflong_nat(:,j) .GT. zero ) 
     1032             consumption(:) = hvc1 * nlflong_nat(:,j) ** hvc2 
     1033             herbivores(:,j) = one_year * green_age(:,j) * nlflong_nat(:,j) / consumption(:) 
    9681034          ELSEWHERE 
    9691035             herbivores(:,j) = 100000. 
Note: See TracChangeset for help on using the changeset viewer.