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

    r136 r257  
    3939  USE stomate_assimtemp 
    4040  USE stomate_lcchange 
    41  
    4241  !  USE Write_Field_p 
    4342 
     
    7069  END SUBROUTINE StomateLpj_clear 
    7170 
    72   SUBROUTINE StomateLpj (npts, dt_days, EndOfYear, & 
     71  SUBROUTINE StomateLpj (npts, dt_days, EndOfYear, EndOfMonth, & 
    7372       neighbours, resolution, & 
    7473       clay, herbivores, & 
     
    9493       t_photo_min, t_photo_opt, t_photo_max,bm_to_litter, & 
    9594       prod10,prod100,flux10, flux100, veget_max_new, & 
    96        convflux,cflux_prod10,cflux_prod100, harvest_above, lcchange) 
     95       convflux,cflux_prod10,cflux_prod100, harvest_above, lcchange, & 
     96       fpc_max) 
    9797 
    9898    ! 
     
    168168    ! maintenance respiration of different plant parts (gC/day/m**2 of ground) 
    169169    REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(in)             :: resp_maint_part 
     170    ! "maximal" coverage fraction of a PFT (LAI -> infinity) on ground  
     171    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                  :: fpc_max 
    170172 
    171173    ! 0.2 modified fields 
     
    264266    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                 :: height 
    265267    ! fraction of soil covered by dead leaves 
    266     REAL(r_std), DIMENSION(npts), INTENT(out)                      :: deadleaf_cover 
     268    REAL(r_std), DIMENSION(npts), INTENT(inout)                      :: deadleaf_cover 
    267269    ! Maximum rate of carboxylation 
    268270    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                 :: vcmax 
     
    301303    ! Do update of yearly variables? This variable must be .TRUE. once a year 
    302304    LOGICAL, INTENT(in)                                                :: EndOfYear 
    303  
     305    ! Do update of monthly variables ? This variable must be .TRUE. once a month 
     306    LOGICAL, INTENT(in)                                                :: EndOfMonth 
    304307 
    305308    ! 0.4 local 
     
    321324    ! crown area of individuals (m**2) 
    322325    REAL(r_std), DIMENSION(npts,nvm)                               :: cn_ind 
     326    ! woodmass of individuals (gC) 
     327    REAL(r_std), DIMENSION(npts,nvm)                               :: woodmass_ind 
    323328    ! fraction that goes into plant part 
    324329    REAL(r_std), DIMENSION(npts,nvm,nparts)                        :: f_alloc 
     
    337342    ! "maximal" coverage fraction of a PFT (LAI -> infinity) on ground 
    338343    REAL(r_std),DIMENSION(npts,nvm)                                :: veget_max_old 
     344 
     345    ! fraction of individual dying this time step 
     346    REAL(r_std), DIMENSION(npts,nvm)                               :: mortality 
    339347 
    340348    REAL(r_std), DIMENSION(npts)                                   :: vartmp 
     
    367375    bm_to_litter(:,:,:) = zero 
    368376    cn_ind(:,:) = zero 
     377    woodmass_ind(:,:) = zero 
    369378    veget_max_old(:,:) = veget_max(:,:) 
    370379 
    371     ! 
    372     ! 1.3 Prescribe some vegetation characteristics if the vegetation is not dynamic 
     380    ! 1.3 Calculate some vegetation characteristics 
     381 
     382    ! 
     383    ! 1.3.1 Calculate some vegetation characteristics (cn_ind and height) from 
     384    !     state variables if running DGVM or dynamic mortality in static cover mode 
     385    ! 
     386    IF ( control%ok_dgvm .OR. .NOT.lpj_gap_const_mort) THEN 
     387       IF(control%ok_dgvm) THEN 
     388          WHERE (ind(:,:).GT.min_stomate) 
     389             woodmass_ind(:,:) = & 
     390                  ((biomass(:,:,isapabove)+biomass(:,:,isapbelow) & 
     391                  +biomass(:,:,iheartabove)+biomass(:,:,iheartbelow)) &  
     392                  *veget_max(:,:))/ind(:,:) 
     393          ENDWHERE 
     394       ELSE 
     395          WHERE (ind(:,:).GT.min_stomate) 
     396             woodmass_ind(:,:) = & 
     397                  (biomass(:,:,isapabove)+biomass(:,:,isapbelow) & 
     398                  +biomass(:,:,iheartabove)+biomass(:,:,iheartbelow))/ind(:,:) 
     399          ENDWHERE 
     400       ENDIF 
     401 
     402       CALL crown (npts,  PFTpresent, & 
     403            ind, biomass, woodmass_ind, & 
     404            veget_max, cn_ind, height) 
     405    ENDIF 
     406 
     407    ! 
     408    ! 1.3.2 Prescribe some vegetation characteristics if the vegetation is not dynamic 
    373409    !     IF the DGVM is not activated, the density of individuals and their crown 
    374410    !     areas don't matter, but they should be defined for the case we switch on 
     
    389425 
    390426    CALL constraints (npts, dt_days, & 
    391          t2m_month, t2m_min_daily, when_growthinit, & 
     427         t2m_month, t2m_min_daily,when_growthinit, & 
    392428         adapted, regenerate) 
    393429 
     
    404440       CALL pftinout (npts, dt_days, adapted, regenerate, & 
    405441            neighbours, veget, veget_max, & 
    406             biomass, ind, age, leaf_frac, npp_longterm, lm_lastyearmax, senescence, & 
     442            biomass, ind, cn_ind, age, leaf_frac, npp_longterm, lm_lastyearmax, senescence, & 
    407443            PFTpresent, everywhere, when_growthinit, need_adjacent, RIP_time, & 
    408444            co2_to_bm, & 
     
    417453       CALL kill (npts, 'pftinout  ', lm_lastyearmax, & 
    418454            ind, PFTpresent, cn_ind, biomass, senescence, RIP_time, & 
    419             lai, age, leaf_age, leaf_frac, & 
     455            lai, age, leaf_age, leaf_frac, npp_longterm, & 
    420456            when_growthinit, everywhere, veget, veget_max, bm_to_litter) 
    421457 
     
    423459       ! 3.3 calculate new crown area and maximum vegetation cover 
    424460       ! 
     461       ! 
     462       ! unsure whether this is really required 
     463       ! - in theory this could ONLY be done at the END of stomate_lpj 
     464       ! 
     465 
     466       ! calculate woodmass of individual tree 
     467       WHERE ((ind(:,:).GT.min_stomate)) 
     468          WHERE  ( veget_max(:,:) .GT. min_stomate) 
     469             woodmass_ind(:,:) = & 
     470                  ((biomass(:,:,isapabove)+biomass(:,:,isapbelow) & 
     471                  +biomass(:,:,iheartabove)+biomass(:,:,iheartbelow))*veget_max(:,:))/ind(:,:) 
     472          ELSEWHERE 
     473             woodmass_ind(:,:) =(biomass(:,:,isapabove)+biomass(:,:,isapbelow) & 
     474                  +biomass(:,:,iheartabove)+biomass(:,:,iheartbelow))/ind(:,:) 
     475          ENDWHERE 
     476 
     477       ENDWHERE 
    425478 
    426479       CALL crown (npts, PFTpresent, & 
    427             ind, biomass, & 
     480            ind, biomass, woodmass_ind, & 
    428481            veget_max, cn_ind, height) 
    429482 
     
    487540         resp_maint, resp_growth, npp_daily) 
    488541 
    489     IF ( control%ok_dgvm ) THEN 
     542    IF ( control%ok_dgvm .OR. .NOT.lpj_gap_const_mort) THEN 
     543       CALL kill (npts, 'npp       ', lm_lastyearmax,  & 
     544            ind, PFTpresent, cn_ind, biomass, senescence, RIP_time, & 
     545            lai, age, leaf_age, leaf_frac, npp_longterm, & 
     546            when_growthinit, everywhere, veget, veget_max, bm_to_litter) 
    490547 
    491548       ! new provisional crown area and maximum vegetation cover after growth 
     549       IF(control%ok_dgvm) THEN 
     550          WHERE (ind(:,:).GT.min_stomate) 
     551             woodmass_ind(:,:) = & 
     552                  ((biomass(:,:,isapabove)+biomass(:,:,isapbelow) & 
     553                  +biomass(:,:,iheartabove)+biomass(:,:,iheartbelow)) &  
     554                  *veget_max(:,:))/ind(:,:) 
     555          ENDWHERE 
     556       ELSE 
     557          WHERE (ind(:,:).GT.min_stomate) 
     558             woodmass_ind(:,:) = & 
     559                  (biomass(:,:,isapabove)+biomass(:,:,isapbelow) & 
     560                  +biomass(:,:,iheartabove)+biomass(:,:,iheartbelow))/ind(:,:) 
     561          ENDWHERE 
     562       ENDIF 
    492563 
    493564       CALL crown (npts, PFTpresent, & 
    494             ind, biomass, & 
     565            ind, biomass, woodmass_ind,& 
    495566            veget_max, cn_ind, height) 
    496567 
     
    513584       CALL kill (npts, 'fire      ', lm_lastyearmax, & 
    514585            ind, PFTpresent, cn_ind, biomass, senescence, RIP_time, & 
    515             lai, age, leaf_age, leaf_frac, & 
     586            lai, age, leaf_age, leaf_frac, npp_longterm, & 
    516587            when_growthinit, everywhere, veget, veget_max, bm_to_litter) 
    517588 
     
    524595    CALL gap (npts, dt_days, & 
    525596         npp_longterm, turnover_longterm, lm_lastyearmax, & 
    526          PFTpresent, biomass, ind, bm_to_litter) 
     597         PFTpresent, biomass, ind, bm_to_litter, mortality) 
    527598 
    528599    IF ( control%ok_dgvm ) THEN 
     
    532603       CALL kill (npts, 'gap       ', lm_lastyearmax, & 
    533604            ind, PFTpresent, cn_ind, biomass, senescence, RIP_time, & 
    534             lai, age, leaf_age, leaf_frac, & 
     605            lai, age, leaf_age, leaf_frac, npp_longterm, & 
    535606            when_growthinit, everywhere, veget, veget_max, bm_to_litter) 
    536607 
     
    570641 
    571642       CALL light (npts, dt_days, & 
    572             PFTpresent, cn_ind, lai, maxfpc_lastyear, & 
    573             ind, biomass, veget_lastlight, bm_to_litter) 
     643            veget_max, fpc_max, PFTpresent, cn_ind, lai, maxfpc_lastyear, & 
     644            lm_lastyearmax, ind, biomass, veget_lastlight, bm_to_litter, mortality) 
    574645 
    575646       ! 
     
    579650       CALL kill (npts, 'light     ', lm_lastyearmax, & 
    580651            ind, PFTpresent, cn_ind, biomass, senescence, RIP_time, & 
    581             lai, age, leaf_age, leaf_frac, & 
     652            lai, age, leaf_age, leaf_frac, npp_longterm, & 
    582653            when_growthinit, everywhere, veget, veget_max, bm_to_litter) 
    583654 
     
    588659    ! 
    589660 
    590     IF ( control%ok_dgvm ) THEN 
     661    IF ( control%ok_dgvm .OR. .NOT.lpj_gap_const_mort ) THEN 
    591662 
    592663       ! 
     
    597668            neighbours, resolution, need_adjacent, herbivores, & 
    598669            precip_lastyear, gdd0_lastyear, lm_lastyearmax, & 
    599             cn_ind, lai, avail_tree, avail_grass, & 
     670            cn_ind, lai, avail_tree, avail_grass, npp_longterm, & 
    600671            leaf_age, leaf_frac, & 
    601             ind, biomass, age, everywhere, co2_to_bm, veget_max) 
     672            ind, biomass, age, everywhere, co2_to_bm, veget_max, woodmass_ind) 
    602673 
    603674       ! 
     
    606677 
    607678       CALL crown (npts, PFTpresent, & 
    608             ind, biomass, & 
     679            ind, biomass, woodmass_ind, & 
    609680            veget_max, cn_ind, height) 
    610681 
     
    617688    CALL cover (npts, cn_ind, ind, biomass, & 
    618689         veget_max, veget_max_old, veget, & 
    619          lai, litter, carbon) 
     690         lai, litter, carbon, turnover_daily, bm_to_litter) 
    620691 
    621692    ! 
     
    645716               prod10,prod100,convflux,cflux_prod10,cflux_prod100,leaf_frac,& 
    646717               npp_longterm, lm_lastyearmax, litter, carbon) 
    647  
    648718       ENDIF 
    649719    ENDIF 
    650 !MM déplacement pour initialisation correcte des grandeurs cumulées : 
     720    !MM déplacement pour initialisation correcte des grandeurs cumulées : 
    651721    cflux_prod_total(:) = convflux(:) + cflux_prod10(:) + cflux_prod100(:) 
    652722    prod10_total(:)=SUM(prod10,dim=2) 
     
    736806    CALL histwrite (hist_id_stomate, 'CO2_TAKEN', itime, & 
    737807         co2_to_bm, npts*nvm, horipft_index) 
     808!MM : histdef à construire !  
     809!!$   CALL histwrite (hist_id_stomate, 'CN_IND', itime, & 
     810!!$                    cn_ind, npts*nvm, horipft_index) 
     811!!$   CALL histwrite (hist_id_stomate, 'WOODMASS_IND', itime, & 
     812!!$                    woodmass_ind, npts*nvm, horipft_index) 
    738813    ! land cover change 
    739814    CALL histwrite (hist_id_stomate, 'CONVFLUX', itime, & 
     
    833908       vartmp(:)=SUM(tot_live_biomass*veget_max,dim=2)/1e3*contfrac 
    834909       CALL histwrite (hist_id_stomate_IPCC, "cVeg", itime, & 
    835          vartmp, npts, hori_index) 
     910            vartmp, npts, hori_index) 
    836911       vartmp(:)=SUM(tot_litter_carb*veget_max,dim=2)/1e3*contfrac 
    837912       CALL histwrite (hist_id_stomate_IPCC, "cLitter", itime, & 
    838          vartmp, npts, hori_index) 
     913            vartmp, npts, hori_index) 
    839914       vartmp(:)=SUM(tot_soil_carb*veget_max,dim=2)/1e3*contfrac 
    840915       CALL histwrite (hist_id_stomate_IPCC, "cSoil", itime, & 
    841          vartmp, npts, hori_index) 
     916            vartmp, npts, hori_index) 
    842917       vartmp(:)=(prod10_total + prod100_total)/1e3 
    843918       CALL histwrite (hist_id_stomate_IPCC, "cProduct", itime, & 
    844          vartmp, npts, hori_index) 
     919            vartmp, npts, hori_index) 
    845920       vartmp(:)=SUM(lai*veget_max,dim=2)*contfrac 
    846921       CALL histwrite (hist_id_stomate_IPCC, "lai", itime, & 
    847          vartmp, npts, hori_index) 
     922            vartmp, npts, hori_index) 
    848923       vartmp(:)=SUM(gpp_daily*veget_max,dim=2)/1e3/one_day*contfrac 
    849924       CALL histwrite (hist_id_stomate_IPCC, "gpp", itime, & 
    850          vartmp, npts, hori_index) 
     925            vartmp, npts, hori_index) 
    851926       vartmp(:)=SUM((resp_maint+resp_growth)*veget_max,dim=2)/1e3/one_day*contfrac 
    852927       CALL histwrite (hist_id_stomate_IPCC, "ra", itime, & 
    853          vartmp, npts, hori_index) 
     928            vartmp, npts, hori_index) 
    854929       vartmp(:)=SUM(npp_daily*veget_max,dim=2)/1e3/one_day*contfrac 
    855930       CALL histwrite (hist_id_stomate_IPCC, "npp", itime, & 
    856          vartmp, npts, hori_index) 
     931            vartmp, npts, hori_index) 
    857932       vartmp(:)=SUM(resp_hetero*veget_max,dim=2)/1e3/one_day*contfrac 
    858933       CALL histwrite (hist_id_stomate_IPCC, "rh", itime, & 
    859          vartmp, npts, hori_index) 
     934            vartmp, npts, hori_index) 
    860935       vartmp(:)=SUM(co2_fire*veget_max,dim=2)/1e3/one_day*contfrac 
    861936       CALL histwrite (hist_id_stomate_IPCC, "fFire", itime, & 
    862          vartmp, npts, hori_index) 
     937            vartmp, npts, hori_index) 
    863938       vartmp(:)=harvest_above/1e3/one_day*contfrac 
    864939       CALL histwrite (hist_id_stomate_IPCC, "fHarvest", itime, & 
    865          vartmp, npts, hori_index) 
     940            vartmp, npts, hori_index) 
    866941       vartmp(:)=cflux_prod_total/1e3/one_day*contfrac 
    867942       CALL histwrite (hist_id_stomate_IPCC, "fLuc", itime, & 
    868          vartmp, npts, hori_index) 
     943            vartmp, npts, hori_index) 
    869944       vartmp(:)=(SUM((gpp_daily-(resp_maint+resp_growth+resp_hetero)-co2_fire) & 
    870945            &        *veget_max,dim=2)-cflux_prod_total-harvest_above)/1e3/one_day*contfrac 
    871946       CALL histwrite (hist_id_stomate_IPCC, "nbp", itime, & 
    872          vartmp, npts, hori_index) 
     947            vartmp, npts, hori_index) 
    873948       vartmp(:)=SUM(tot_bm_to_litter*veget_max,dim=2)/1e3/one_day*contfrac 
    874949       CALL histwrite (hist_id_stomate_IPCC, "fVegLitter", itime, & 
    875          vartmp, npts, hori_index) 
     950            vartmp, npts, hori_index) 
    876951       vartmp(:)=SUM(SUM(soilcarbon_input,dim=2)*veget_max,dim=2)/1e3/one_day*contfrac 
    877952       CALL histwrite (hist_id_stomate_IPCC, "fLitterSoil", itime, & 
    878          vartmp, npts, hori_index) 
     953            vartmp, npts, hori_index) 
    879954       vartmp(:)=SUM(biomass(:,:,ileaf)*veget_max,dim=2)/1e3*contfrac 
    880955       CALL histwrite (hist_id_stomate_IPCC, "cLeaf", itime, & 
    881          vartmp, npts, hori_index) 
     956            vartmp, npts, hori_index) 
    882957       vartmp(:)=SUM((biomass(:,:,isapabove)+biomass(:,:,iheartabove))*veget_max,dim=2)/1e3*contfrac 
    883958       CALL histwrite (hist_id_stomate_IPCC, "cWood", itime, & 
    884          vartmp, npts, hori_index) 
     959            vartmp, npts, hori_index) 
    885960       vartmp(:)=SUM(( biomass(:,:,iroot) + biomass(:,:,isapbelow) + biomass(:,:,iheartbelow) ) & 
    886961            &        *veget_max,dim=2)/1e3*contfrac 
    887962       CALL histwrite (hist_id_stomate_IPCC, "cRoot", itime, & 
    888          vartmp, npts, hori_index) 
     963            vartmp, npts, hori_index) 
    889964       vartmp(:)=SUM(( biomass(:,:,icarbres) + biomass(:,:,ifruit))*veget_max,dim=2)/1e3*contfrac 
    890965       CALL histwrite (hist_id_stomate_IPCC, "cMisc", itime, & 
    891          vartmp, npts, hori_index) 
     966            vartmp, npts, hori_index) 
    892967       vartmp(:)=SUM((litter(:,istructural,:,iabove)+litter(:,imetabolic,:,iabove))*veget_max,dim=2)/1e3*contfrac 
    893968       CALL histwrite (hist_id_stomate_IPCC, "cLitterAbove", itime, & 
    894          vartmp, npts, hori_index) 
     969            vartmp, npts, hori_index) 
    895970       vartmp(:)=SUM((litter(:,istructural,:,ibelow)+litter(:,imetabolic,:,ibelow))*veget_max,dim=2)/1e3*contfrac 
    896971       CALL histwrite (hist_id_stomate_IPCC, "cLitterBelow", itime, & 
    897          vartmp, npts, hori_index) 
     972            vartmp, npts, hori_index) 
    898973       vartmp(:)=SUM(carbon(:,iactive,:)*veget_max,dim=2)/1e3*contfrac 
    899974       CALL histwrite (hist_id_stomate_IPCC, "cSoilFast", itime, & 
    900          vartmp, npts, hori_index) 
     975            vartmp, npts, hori_index) 
    901976       vartmp(:)=SUM(carbon(:,islow,:)*veget_max,dim=2)/1e3*contfrac 
    902977       CALL histwrite (hist_id_stomate_IPCC, "cSoilMedium", itime, & 
    903          vartmp, npts, hori_index) 
     978            vartmp, npts, hori_index) 
    904979       vartmp(:)=SUM(carbon(:,ipassive,:)*veget_max,dim=2)/1e3*contfrac 
    905980       CALL histwrite (hist_id_stomate_IPCC, "cSoilSlow", itime, & 
    906          vartmp, npts, hori_index) 
     981            vartmp, npts, hori_index) 
    907982       DO j=1,nvm 
    908983          histvar(:,j)=veget_max(:,j)*contfrac(:)*100 
    909984       ENDDO 
    910985       CALL histwrite (hist_id_stomate_IPCC, "landCoverFrac", itime, & 
    911          histvar, npts*nvm, horipft_index) 
    912        vartmp(:)=(veget_max(:,3)+veget_max(:,6)+veget_max(:,8)+veget_max(:,9))*contfrac*100 
     986            histvar, npts*nvm, horipft_index) 
     987 
     988       ! >> DS to be modified for the externalisation 
     989!       vartmp(:)=(veget_max(:,3)+veget_max(:,6)+veget_max(:,8)+veget_max(:,9))*contfrac*100 
     990       vartmp(:)=zero 
     991       DO j=2,nvm 
     992          IF(is_deciduous(j)) THEN 
     993             vartmp(:) = vartmp(:) + veget_max(:,j)*contfrac*100 
     994          ENDIF 
     995       ENDDO 
    913996       CALL histwrite (hist_id_stomate_IPCC, "treeFracPrimDec", itime, & 
    914           vartmp, npts, hori_index) 
    915        vartmp(:)=(veget_max(:,2)+veget_max(:,4)+veget_max(:,5)+veget_max(:,7))*contfrac*100 
     997            vartmp, npts, hori_index) 
     998       !- 
     999!       vartmp(:)=(veget_max(:,2)+veget_max(:,4)+veget_max(:,5)+veget_max(:,7))*contfrac*100 
     1000       vartmp(:)=zero 
     1001       DO j=2,nvm 
     1002          IF(is_evergreen(j)) THEN 
     1003             vartmp(:) = vartmp(:) + veget_max(:,j)*contfrac*100 
     1004          ENDIF 
     1005       ENDDO 
    9161006       CALL histwrite (hist_id_stomate_IPCC, "treeFracPrimEver", itime, & 
    917          vartmp, npts, hori_index) 
    918        vartmp(:)=(veget_max(:,10)+veget_max(:,12))*contfrac*100 
     1007            vartmp, npts, hori_index) 
     1008       !- 
     1009!       vartmp(:)=(veget_max(:,10)+veget_max(:,12))*contfrac*100 
     1010       vartmp(:)=zero 
     1011       DO j=2,nvm 
     1012          IF(is_c3(j)) THEN 
     1013             vartmp(:) = vartmp(:) + veget_max(:,j)*contfrac*100 
     1014          ENDIF 
     1015       ENDDO 
    9191016       CALL histwrite (hist_id_stomate_IPCC, "c3PftFrac", itime, & 
    920          vartmp, npts, hori_index) 
    921        vartmp(:)=(veget_max(:,11)+veget_max(:,13))*contfrac*100 
     1017            vartmp, npts, hori_index) 
     1018       !- 
     1019 !      vartmp(:)=(veget_max(:,11)+veget_max(:,13))*contfrac*100 
     1020       vartmp(:)=zero 
     1021       DO j=2,nvm 
     1022          IF(is_c4(j)) THEN 
     1023             vartmp(:) = vartmp(:) + veget_max(:,j)*contfrac*100 
     1024          ENDIF 
     1025       ENDDO 
    9221026       CALL histwrite (hist_id_stomate_IPCC, "c4PftFrac", itime, & 
    923          vartmp, npts, hori_index) 
     1027            vartmp, npts, hori_index) 
     1028       !>> End modif 
     1029        
     1030 
    9241031       vartmp(:)=SUM(resp_growth*veget_max,dim=2)/1e3/one_day*contfrac 
    9251032       CALL histwrite (hist_id_stomate_IPCC, "rGrowth", itime, & 
    926          vartmp, npts, hori_index) 
     1033            vartmp, npts, hori_index) 
    9271034       vartmp(:)=SUM(resp_maint*veget_max,dim=2)/1e3/one_day*contfrac 
    9281035       CALL histwrite (hist_id_stomate_IPCC, "rMaint", itime, & 
    929          vartmp, npts, hori_index) 
     1036            vartmp, npts, hori_index) 
    9301037       vartmp(:)=SUM(bm_alloc(:,:,ileaf)*veget_max,dim=2)/1e3/one_day*contfrac 
    9311038       CALL histwrite (hist_id_stomate_IPCC, "nppLeaf", itime, & 
    932          vartmp, npts, hori_index) 
     1039            vartmp, npts, hori_index) 
    9331040       vartmp(:)=SUM(bm_alloc(:,:,isapabove)*veget_max,dim=2)/1e3/one_day*contfrac 
    9341041       CALL histwrite (hist_id_stomate_IPCC, "nppWood", itime, & 
    935          vartmp, npts, hori_index) 
     1042            vartmp, npts, hori_index) 
    9361043       vartmp(:)=SUM(( bm_alloc(:,:,isapbelow) + bm_alloc(:,:,iroot) )*veget_max,dim=2)/1e3/one_day*contfrac 
    9371044       CALL histwrite (hist_id_stomate_IPCC, "nppRoot", itime, & 
    938          vartmp, npts, hori_index) 
     1045            vartmp, npts, hori_index) 
    9391046 
    9401047       CALL histwrite (hist_id_stomate_IPCC, 'RESOLUTION_X', itime, & 
Note: See TracChangeset for help on using the changeset viewer.