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/stomate_season.f90

    r135 r257  
    174174    ! residence time of green tissue (years) 
    175175    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  
    185176    ! herbivore consumption (gC/m**2/day) 
    186177    REAL(r_std), DIMENSION(npts)                            :: consumption 
     178    ! fraction of each gridcell occupied by natural vegetation 
     179    REAL(r_std), DIMENSION(npts)                            :: fracnat 
    187180 
    188181    ! ========================================================================= 
     
    225218 
    226219       ! 1.2.1.1 "monthly" 
    227 !MM PAS PARALLELISE!! 
     220       !MM PAS PARALLELISE!! 
    228221       IF ( ABS( SUM( moiavail_month(:,2:nvm) ) ) .LT. min_stomate ) THEN 
    229222 
     
    277270 
    278271       ! 1.2.3 "monthly" soil temperatures 
    279 !MM PAS PARALLELISE!! 
     272       !MM PAS PARALLELISE!! 
    280273       IF ( ABS( SUM( tsoil_month(:,:) ) ) .LT. min_stomate ) THEN 
    281274 
     
    464457    !         detect a beginning of the growing season by declaring it dormant 
    465458    ! 
    466 !NVMODIF 
     459    !NVMODIF 
    467460    DO j = 2,nvm 
    468461       WHERE ( ( gpp_week(:,j) .LT. min_gpp_allowed ) .OR. &  
     
    470463            ( ( when_growthinit(:,j) .GT. 2.*one_year ) .AND. & 
    471464            ( biomass(:,j,icarbres) .GT. biomass(:,j,ileaf)*4. ) ) ) 
    472 !       WHERE ( ( gpp_week(:,j) .EQ. zero ) .OR. &  
    473 !            ( gpp_week(:,j) .LT. gppfrac_dormance * maxgppweek_lastyear(:,j) ) .OR. & 
    474 !            ( ( when_growthinit(:,j) .GT. 2.*one_year ) .AND. & 
    475 !            ( biomass(:,j,icarbres) .GT. biomass(:,j,ileaf)*4. ) ) ) 
    476            
     465       !       WHERE ( ( gpp_week(:,j) .EQ. zero ) .OR. &  
     466       !            ( gpp_week(:,j) .LT. gppfrac_dormance * maxgppweek_lastyear(:,j) ) .OR. & 
     467       !            ( ( when_growthinit(:,j) .GT. 2.*one_year ) .AND. & 
     468       !            ( biomass(:,j,icarbres) .GT. biomass(:,j,ileaf)*4. ) ) ) 
     469        
    477470          time_lowgpp(:,j) = time_lowgpp(:,j) + dt 
    478471           
     
    816809    ! 
    817810 
     811    IF(control%ok_dgvm ) THEN 
     812 
     813       fracnat(:) = un 
     814       DO j = 2,nvm 
     815          IF ( .NOT. natural(j) ) THEN 
     816             fracnat(:) = fracnat(:) - veget_max(:,j) 
     817          ENDIF 
     818       ENDDO 
     819 
     820    ENDIF 
     821 
    818822    IF ( control%ok_stomate ) THEN 
    819  
    820        DO j = 2,nvm 
    821           WHERE ( biomass(:,j,ileaf) .GT. lm_thisyearmax(:,j) ) 
    822              lm_thisyearmax(:,j) = biomass(:,j,ileaf) 
    823           ENDWHERE 
    824        ENDDO 
    825  
     823       IF(control%ok_dgvm ) THEN 
     824          DO j=2,nvm 
     825 
     826             IF ( natural(j) .AND. control%ok_dgvm ) THEN 
     827 
     828                WHERE ( fracnat(:) .GT. min_stomate .AND. biomass(:,j,ileaf).GT. lm_lastyearmax(:,j)*0.75 ) 
     829                   maxfpc_lastyear(:,j) = ( maxfpc_lastyear(:,j) * ( one_year/leaflife_tab(j)- dt ) + & 
     830                        veget(:,j) / fracnat(:) * dt ) / (one_year/leaflife_tab(j)) 
     831                ENDWHERE 
     832                maxfpc_thisyear(:,j) = maxfpc_lastyear(:,j) ! just to initialise value 
     833 
     834             ENDIF 
     835 
     836!NV : correct initialization 
     837!!$             WHERE(biomass(:,j,ileaf).GT. lm_lastyearmax(:,j)*0.75) 
     838!!$                lm_lastyearmax(:,j) = ( lm_lastyearmax(:,j) * ( one_year/leaflife_tab(j)- dt ) + & 
     839!!$                     biomass(:,j,ileaf) * dt ) / (one_year/leaflife_tab(j)) 
     840!!$             ENDWHERE 
     841!!$             lm_thisyearmax(:,j)=lm_lastyearmax(:,j) ! just to initialise value 
     842             WHERE (lm_thisyearmax(:,j) .GT. min_stomate) 
     843                WHERE(biomass(:,j,ileaf).GT. lm_thisyearmax(:,j)*0.75) 
     844                   lm_thisyearmax(:,j) = ( lm_thisyearmax(:,j) * ( one_year/leaflife_tab(j)- dt ) + & 
     845                        biomass(:,j,ileaf) * dt ) / (one_year/leaflife_tab(j)) 
     846                ENDWHERE 
     847             ELSEWHERE 
     848                lm_thisyearmax(:,j) =biomass(:,j,ileaf) 
     849             ENDWHERE 
     850 
     851          ENDDO 
     852 
     853       ELSE 
     854 
     855          DO j = 2,nvm 
     856             WHERE ( biomass(:,j,ileaf) .GT. lm_thisyearmax(:,j) ) 
     857                lm_thisyearmax(:,j) = biomass(:,j,ileaf) 
     858             ENDWHERE 
     859          ENDDO 
     860 
     861       ENDIF 
    826862    ELSE 
    827863 
     
    851887       ! 21.1 replace old values 
    852888       ! 
    853 !NVMODIF 
    854       maxmoiavail_lastyear(:,:) = (maxmoiavail_lastyear(:,:)*(tau_climatology-1)+ maxmoiavail_thisyear(:,:))/tau_climatology 
    855       minmoiavail_lastyear(:,:) = (minmoiavail_lastyear(:,:)*(tau_climatology-1)+ minmoiavail_thisyear(:,:))/tau_climatology 
    856       maxgppweek_lastyear(:,:) =( maxgppweek_lastyear(:,:)*(tau_climatology-1)+ maxgppweek_thisyear(:,:))/tau_climatology 
    857 !       maxmoiavail_lastyear(:,:) = maxmoiavail_thisyear(:,:) 
    858 !       minmoiavail_lastyear(:,:) = minmoiavail_thisyear(:,:) 
    859 !       maxgppweek_lastyear(:,:) = maxgppweek_thisyear(:,:) 
    860  
     889       !NVMODIF 
     890       maxmoiavail_lastyear(:,:) = (maxmoiavail_lastyear(:,:)*(tau_climatology-1)+ maxmoiavail_thisyear(:,:))/tau_climatology 
     891       minmoiavail_lastyear(:,:) = (minmoiavail_lastyear(:,:)*(tau_climatology-1)+ minmoiavail_thisyear(:,:))/tau_climatology 
     892       maxgppweek_lastyear(:,:) =( maxgppweek_lastyear(:,:)*(tau_climatology-1)+ maxgppweek_thisyear(:,:))/tau_climatology 
     893       !       maxmoiavail_lastyear(:,:) = maxmoiavail_thisyear(:,:) 
     894       !       minmoiavail_lastyear(:,:) = minmoiavail_thisyear(:,:) 
     895       !       maxgppweek_lastyear(:,:) = maxgppweek_thisyear(:,:) 
     896        
    861897       gdd0_lastyear(:) = gdd0_thisyear(:) 
    862898 
     
    909945       !        fpc_crit. 
    910946 
    911        ! calculate the sum of maxfpc_lastyear 
    912        sumfpc_nat(:) = zero 
    913        DO j = 2,nvm 
    914           sumfpc_nat(:) = sumfpc_nat(:) + maxfpc_lastyear(:,j) 
    915        ENDDO 
    916  
    917        ! scale so that the new sum is fpc_crit 
    918        DO j = 2,nvm  
    919           WHERE ( sumfpc_nat(:) .GT. fpc_crit ) 
    920              maxfpc_lastyear(:,j) = maxfpc_lastyear(:,j) * (fpc_crit/sumfpc_nat(:)) 
    921           ENDWHERE 
    922        ENDDO 
     947!!$       ! calculate the sum of maxfpc_lastyear 
     948!!$       sumfpc_nat(:) = zero 
     949!!$       DO j = 2,nvm 
     950!!$          sumfpc_nat(:) = sumfpc_nat(:) + maxfpc_lastyear(:,j) 
     951!!$       ENDDO 
     952!!$ 
     953!!$       ! scale so that the new sum is fpc_crit 
     954!!$       DO j = 2,nvm  
     955!!$          WHERE ( sumfpc_nat(:) .GT. fpc_crit ) 
     956!!$             maxfpc_lastyear(:,j) = maxfpc_lastyear(:,j) * (fpc_crit/sumfpc_nat(:)) 
     957!!$          ENDWHERE 
     958!!$       ENDDO 
    923959 
    924960    ENDIF  ! EndOfYear 
     
    941977!!$ nlflong_nat, green_age are pft-dependants 
    942978 
    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  
    995979    nlflong_nat(:,:) = zero 
    996980    weighttot(:,:) = zero 
Note: See TracChangeset for help on using the changeset viewer.