CNVegCarbonFluxType.F90 Source File


Source Code

module CNVegCarbonFluxType

#include "shr_assert.h"

  !-----------------------------------------------------------------------
  !
  ! !USES:
  use shr_kind_mod                       , only : r8 => shr_kind_r8
  use shr_infnan_mod                     , only : nan => shr_infnan_nan, assignment(=)
  use shr_log_mod                        , only : errMsg => shr_log_errMsg
  use decompMod                          , only : bounds_type
  use SoilBiogeochemDecompCascadeConType , only : decomp_cascade_con
  use clm_varpar                         , only : ndecomp_cascade_transitions, ndecomp_pools
  use clm_varpar                         , only : nlevdecomp_full, nlevgrnd, nlevdecomp
  use clm_varcon                         , only : spval, dzsoi_decomp
  use clm_varctl                         , only : use_cndv, use_c13, use_nitrif_denitrif, use_crop
  use clm_varctl                         , only : use_grainproduct
  use clm_varctl                         , only : iulog
  use landunit_varcon                    , only : istsoil, istcrop, istdlak 
  use pftconMod                          , only : npcropmin
  use LandunitType                       , only : lun                
  use ColumnType                         , only : col                
  use PatchType                          , only : patch                
  use AnnualFluxDribbler                 , only : annual_flux_dribbler_type, annual_flux_dribbler_gridcell
  use dynSubgridControlMod               , only : get_for_testing_allow_non_annual_changes
  use abortutils                         , only : endrun
  ! 
  ! !PUBLIC TYPES:
  implicit none
  private
  !
  type, public :: cnveg_carbonflux_type

     ! gap mortality fluxes
     real(r8), pointer :: m_leafc_to_litter_patch                   (:)     ! leaf C mortality (gC/m2/s)
     real(r8), pointer :: m_leafc_storage_to_litter_patch           (:)     ! leaf C storage mortality (gC/m2/s)
     real(r8), pointer :: m_leafc_xfer_to_litter_patch              (:)     ! leaf C transfer mortality (gC/m2/s)
     real(r8), pointer :: m_frootc_to_litter_patch                  (:)     ! fine root C mortality (gC/m2/s)
     real(r8), pointer :: m_frootc_storage_to_litter_patch          (:)     ! fine root C storage mortality (gC/m2/s)
     real(r8), pointer :: m_frootc_xfer_to_litter_patch             (:)     ! fine root C transfer mortality (gC/m2/s)
     real(r8), pointer :: m_livestemc_to_litter_patch               (:)     ! live stem C mortality (gC/m2/s)
     real(r8), pointer :: m_livestemc_storage_to_litter_patch       (:)     ! live stem C storage mortality (gC/m2/s)
     real(r8), pointer :: m_livestemc_xfer_to_litter_patch          (:)     ! live stem C transfer mortality (gC/m2/s)
     real(r8), pointer :: m_deadstemc_to_litter_patch               (:)     ! dead stem C mortality (gC/m2/s)
     real(r8), pointer :: m_deadstemc_storage_to_litter_patch       (:)     ! dead stem C storage mortality (gC/m2/s)
     real(r8), pointer :: m_deadstemc_xfer_to_litter_patch          (:)     ! dead stem C transfer mortality (gC/m2/s)
     real(r8), pointer :: m_livecrootc_to_litter_patch              (:)     ! live coarse root C mortality (gC/m2/s)
     real(r8), pointer :: m_livecrootc_storage_to_litter_patch      (:)     ! live coarse root C storage mortality (gC/m2/s)
     real(r8), pointer :: m_livecrootc_xfer_to_litter_patch         (:)     ! live coarse root C transfer mortality (gC/m2/s)
     real(r8), pointer :: m_deadcrootc_to_litter_patch              (:)     ! dead coarse root C mortality (gC/m2/s)
     real(r8), pointer :: m_deadcrootc_storage_to_litter_patch      (:)     ! dead coarse root C storage mortality (gC/m2/s)
     real(r8), pointer :: m_deadcrootc_xfer_to_litter_patch         (:)     ! dead coarse root C transfer mortality (gC/m2/s)
     real(r8), pointer :: m_gresp_storage_to_litter_patch           (:)     ! growth respiration storage mortality (gC/m2/s)
     real(r8), pointer :: m_gresp_xfer_to_litter_patch              (:)     ! growth respiration transfer mortality (gC/m2/s)

     ! harvest mortality fluxes
     real(r8), pointer :: hrv_leafc_to_litter_patch                 (:)     ! leaf C harvest mortality (gC/m2/s)
     real(r8), pointer :: hrv_leafc_storage_to_litter_patch         (:)     ! leaf C storage harvest mortality (gC/m2/s)
     real(r8), pointer :: hrv_leafc_xfer_to_litter_patch            (:)     ! leaf C transfer harvest mortality (gC/m2/s)
     real(r8), pointer :: hrv_frootc_to_litter_patch                (:)     ! fine root C harvest mortality (gC/m2/s)
     real(r8), pointer :: hrv_frootc_storage_to_litter_patch        (:)     ! fine root C storage harvest mortality (gC/m2/s)
     real(r8), pointer :: hrv_frootc_xfer_to_litter_patch           (:)     ! fine root C transfer harvest mortality (gC/m2/s)
     real(r8), pointer :: hrv_livestemc_to_litter_patch             (:)     ! live stem C harvest mortality (gC/m2/s)
     real(r8), pointer :: hrv_livestemc_storage_to_litter_patch     (:)     ! live stem C storage harvest mortality (gC/m2/s)
     real(r8), pointer :: hrv_livestemc_xfer_to_litter_patch        (:)     ! live stem C transfer harvest mortality (gC/m2/s)
     real(r8), pointer :: hrv_deadstemc_storage_to_litter_patch     (:)     ! dead stem C storage harvest mortality (gC/m2/s)
     real(r8), pointer :: hrv_deadstemc_xfer_to_litter_patch        (:)     ! dead stem C transfer harvest mortality (gC/m2/s)
     real(r8), pointer :: hrv_livecrootc_to_litter_patch            (:)     ! live coarse root C harvest mortality (gC/m2/s)
     real(r8), pointer :: hrv_livecrootc_storage_to_litter_patch    (:)     ! live coarse root C storage harvest mortality (gC/m2/s)
     real(r8), pointer :: hrv_livecrootc_xfer_to_litter_patch       (:)     ! live coarse root C transfer harvest mortality (gC/m2/s)
     real(r8), pointer :: hrv_deadcrootc_to_litter_patch            (:)     ! dead coarse root C harvest mortality (gC/m2/s)
     real(r8), pointer :: hrv_deadcrootc_storage_to_litter_patch    (:)     ! dead coarse root C storage harvest mortality (gC/m2/s)
     real(r8), pointer :: hrv_deadcrootc_xfer_to_litter_patch       (:)     ! dead coarse root C transfer harvest mortality (gC/m2/s)
     real(r8), pointer :: hrv_gresp_storage_to_litter_patch         (:)     ! growth respiration storage harvest mortality (gC/m2/s)
     real(r8), pointer :: hrv_gresp_xfer_to_litter_patch            (:)     ! growth respiration transfer harvest mortality (gC/m2/s)
     real(r8), pointer :: hrv_xsmrpool_to_atm_patch                 (:)     ! excess MR pool harvest mortality (gC/m2/s)

     ! fire fluxes 
     real(r8), pointer :: m_leafc_to_fire_patch                     (:)     ! (gC/m2/s) fire C emissions from leafc 
     real(r8), pointer :: m_leafc_storage_to_fire_patch             (:)     ! (gC/m2/s) fire C emissions from leafc_storage             
     real(r8), pointer :: m_leafc_xfer_to_fire_patch                (:)     ! (gC/m2/s) fire C emissions from leafc_xfer
     real(r8), pointer :: m_livestemc_to_fire_patch                 (:)     ! (gC/m2/s) fire C emissions from livestemc
     real(r8), pointer :: m_livestemc_storage_to_fire_patch         (:)     ! (gC/m2/s) fire C emissions from livestemc_storage       
     real(r8), pointer :: m_livestemc_xfer_to_fire_patch            (:)     ! (gC/m2/s) fire C emissions from livestemc_xfer
     real(r8), pointer :: m_deadstemc_to_fire_patch                 (:)     ! (gC/m2/s) fire C emissions from deadstemc_xfer
     real(r8), pointer :: m_deadstemc_storage_to_fire_patch         (:)     ! (gC/m2/s) fire C emissions from deadstemc_storage         
     real(r8), pointer :: m_deadstemc_xfer_to_fire_patch            (:)     ! (gC/m2/s) fire C emissions from deadstemc_xfer
     real(r8), pointer :: m_frootc_to_fire_patch                    (:)     ! (gC/m2/s) fire C emissions from frootc
     real(r8), pointer :: m_frootc_storage_to_fire_patch            (:)     ! (gC/m2/s) fire C emissions from frootc_storage
     real(r8), pointer :: m_frootc_xfer_to_fire_patch               (:)     ! (gC/m2/s) fire C emissions from frootc_xfer
     real(r8), pointer :: m_livecrootc_to_fire_patch                (:)     ! (gC/m2/s) fire C emissions from livecrootc
     real(r8), pointer :: m_livecrootc_storage_to_fire_patch        (:)     ! (gC/m2/s) fire C emissions from livecrootc_storage     
     real(r8), pointer :: m_livecrootc_xfer_to_fire_patch           (:)     ! (gC/m2/s) fire C emissions from livecrootc_xfer
     real(r8), pointer :: m_deadcrootc_to_fire_patch                (:)     ! (gC/m2/s) fire C emissions from deadcrootc
     real(r8), pointer :: m_deadcrootc_storage_to_fire_patch        (:)     ! (gC/m2/s) fire C emissions from deadcrootc_storage 
     real(r8), pointer :: m_deadcrootc_xfer_to_fire_patch           (:)     ! (gC/m2/s) fire C emissions from deadcrootc_xfer
     real(r8), pointer :: m_gresp_storage_to_fire_patch             (:)     ! (gC/m2/s) fire C emissions from gresp_storage 
     real(r8), pointer :: m_gresp_xfer_to_fire_patch                (:)     ! (gC/m2/s) fire C emissions from gresp_xfer
     real(r8), pointer :: m_leafc_to_litter_fire_patch              (:)     ! (gC/m2/s) from leafc to litter c due to fire
     real(r8), pointer :: m_leafc_storage_to_litter_fire_patch      (:)     ! (gC/m2/s) from leafc_storage to litter C  due to fire               
     real(r8), pointer :: m_leafc_xfer_to_litter_fire_patch         (:)     ! (gC/m2/s) from leafc_xfer to litter C  due to fire               
     real(r8), pointer :: m_livestemc_to_litter_fire_patch          (:)     ! (gC/m2/s) from livestemc to litter C  due to fire               
     real(r8), pointer :: m_livestemc_storage_to_litter_fire_patch  (:)     ! (gC/m2/s) from livestemc_storage to litter C due to fire      
     real(r8), pointer :: m_livestemc_xfer_to_litter_fire_patch     (:)     ! (gC/m2/s) from livestemc_xfer to litter C due to fire      
     real(r8), pointer :: m_livestemc_to_deadstemc_fire_patch       (:)     ! (gC/m2/s) from livestemc to deadstemc due to fire       
     real(r8), pointer :: m_deadstemc_to_litter_fire_patch          (:)     ! (gC/m2/s) from deadstemc to litter C due to fire      
     real(r8), pointer :: m_deadstemc_storage_to_litter_fire_patch  (:)     ! (gC/m2/s) from deadstemc_storage to litter C due to fire               
     real(r8), pointer :: m_deadstemc_xfer_to_litter_fire_patch     (:)     ! (gC/m2/s) from deadstemc_xfer to litter C due to fire               
     real(r8), pointer :: m_frootc_to_litter_fire_patch             (:)     ! (gC/m2/s) from frootc to litter C due to fire               
     real(r8), pointer :: m_frootc_storage_to_litter_fire_patch     (:)     ! (gC/m2/s) from frootc_storage to litter C due to fire               
     real(r8), pointer :: m_frootc_xfer_to_litter_fire_patch        (:)     ! (gC/m2/s) from frootc_xfer to litter C due to fire               
     real(r8), pointer :: m_livecrootc_to_litter_fire_patch         (:)     ! (gC/m2/s) from livecrootc to litter C due to fire                     
     real(r8), pointer :: m_livecrootc_storage_to_litter_fire_patch (:)     ! (gC/m2/s) from livecrootc_storage to litter C due to fire                     
     real(r8), pointer :: m_livecrootc_xfer_to_litter_fire_patch    (:)     ! (gC/m2/s) from livecrootc_xfer to litter C due to fire                     
     real(r8), pointer :: m_livecrootc_to_deadcrootc_fire_patch     (:)     ! (gC/m2/s) from livecrootc to deadstemc due to fire        
     real(r8), pointer :: m_deadcrootc_to_litter_fire_patch         (:)     ! (gC/m2/s) from deadcrootc to litter C due to fire                       
     real(r8), pointer :: m_deadcrootc_storage_to_litter_fire_patch (:)     ! (gC/m2/s) from deadcrootc_storage to litter C due to fire                       
     real(r8), pointer :: m_deadcrootc_xfer_to_litter_fire_patch    (:)     ! (gC/m2/s) from deadcrootc_xfer to litter C due to fire                       
     real(r8), pointer :: m_gresp_storage_to_litter_fire_patch      (:)     ! (gC/m2/s) from gresp_storage to litter C due to fire                       
     real(r8), pointer :: m_gresp_xfer_to_litter_fire_patch         (:)     ! (gC/m2/s) from gresp_xfer to litter C due to fire                       

     ! phenology fluxes from transfer pools                     
     real(r8), pointer :: grainc_xfer_to_grainc_patch               (:)     ! grain C growth from storage for prognostic crop(gC/m2/s)
     real(r8), pointer :: leafc_xfer_to_leafc_patch                 (:)     ! leaf C growth from storage (gC/m2/s)
     real(r8), pointer :: frootc_xfer_to_frootc_patch               (:)     ! fine root C growth from storage (gC/m2/s)
     real(r8), pointer :: livestemc_xfer_to_livestemc_patch         (:)     ! live stem C growth from storage (gC/m2/s)
     real(r8), pointer :: deadstemc_xfer_to_deadstemc_patch         (:)     ! dead stem C growth from storage (gC/m2/s)
     real(r8), pointer :: livecrootc_xfer_to_livecrootc_patch       (:)     ! live coarse root C growth from storage (gC/m2/s)
     real(r8), pointer :: deadcrootc_xfer_to_deadcrootc_patch       (:)     ! dead coarse root C growth from storage (gC/m2/s)

     ! leaf and fine root litterfall fluxes                          
     real(r8), pointer :: leafc_to_litter_patch                     (:)     ! leaf C litterfall (gC/m2/s)
     real(r8), pointer :: leafc_to_litter_fun_patch                 (:)     ! leaf C litterfall used by FUN (gC/m2/s)
     real(r8), pointer :: frootc_to_litter_patch                    (:)     ! fine root C litterfall (gC/m2/s)
     real(r8), pointer :: livestemc_to_litter_patch                 (:)     ! live stem C litterfall (gC/m2/s)
     real(r8), pointer :: grainc_to_food_patch                      (:)     ! grain C to food for prognostic crop(gC/m2/s)
     real(r8), pointer :: grainc_to_seed_patch                      (:)     ! grain C to seed for prognostic crop(gC/m2/s)

     ! maintenance respiration fluxes     
     real(r8), pointer :: cpool_to_resp_patch                       (:)     ! CNflex excess C maintenance respiration (gC/m2/s)
     real(r8), pointer :: cpool_to_leafc_resp_patch                 (:)     ! CNflex excess C maintenance respiration (gC/m2/s)
     real(r8), pointer :: cpool_to_leafc_storage_resp_patch         (:)     ! CNflex excess C maintenance respiration (gC/m2/s)
     real(r8), pointer :: cpool_to_frootc_resp_patch                (:)     ! CNflex excess C maintenance respiration (gC/m2/s)
     real(r8), pointer :: cpool_to_frootc_storage_resp_patch        (:)     ! CNflex excess C maintenance respiration (gC/m2/s)
     real(r8), pointer :: cpool_to_livecrootc_resp_patch            (:)     ! CNflex excess C maintenance respiration (gC/m2/s)
     real(r8), pointer :: cpool_to_livecrootc_storage_resp_patch    (:)     ! CNflex excess C maintenance respiration (gC/m2/s)
     real(r8), pointer :: cpool_to_livestemc_resp_patch             (:)     ! CNflex excess C maintenance respiration (gC/m2/s)
     real(r8), pointer :: cpool_to_livestemc_storage_resp_patch     (:)     ! CNflex excess C maintenance respiration (gC/m2/s)
     real(r8), pointer :: leaf_mr_patch                             (:)     ! leaf maintenance respiration (gC/m2/s)
     real(r8), pointer :: froot_mr_patch                            (:)     ! fine root maintenance respiration (gC/m2/s)
     real(r8), pointer :: livestem_mr_patch                         (:)     ! live stem maintenance respiration (gC/m2/s)
     real(r8), pointer :: livecroot_mr_patch                        (:)     ! live coarse root maintenance respiration (gC/m2/s)
     real(r8), pointer :: grain_mr_patch                            (:)     ! crop grain or organs maint. respiration (gC/m2/s)
     real(r8), pointer :: leaf_curmr_patch                          (:)     ! leaf maintenance respiration from current GPP (gC/m2/s)
     real(r8), pointer :: froot_curmr_patch                         (:)     ! fine root maintenance respiration from current GPP (gC/m2/s)
     real(r8), pointer :: livestem_curmr_patch                      (:)     ! live stem maintenance respiration from current GPP (gC/m2/s)
     real(r8), pointer :: livecroot_curmr_patch                     (:)     ! live coarse root maintenance respiration from current GPP (gC/m2/s)
     real(r8), pointer :: grain_curmr_patch                         (:)     ! crop grain or organs maint. respiration from current GPP (gC/m2/s)
     real(r8), pointer :: leaf_xsmr_patch                           (:)     ! leaf maintenance respiration from storage (gC/m2/s)
     real(r8), pointer :: froot_xsmr_patch                          (:)     ! fine root maintenance respiration from storage (gC/m2/s)
     real(r8), pointer :: livestem_xsmr_patch                       (:)     ! live stem maintenance respiration from storage (gC/m2/s)
     real(r8), pointer :: livecroot_xsmr_patch                      (:)     ! live coarse root maintenance respiration from storage (gC/m2/s)
     real(r8), pointer :: grain_xsmr_patch                          (:)     ! crop grain or organs maint. respiration from storage (gC/m2/s)

     ! photosynthesis fluxes                                   
     real(r8), pointer :: psnsun_to_cpool_patch                     (:)     ! C fixation from sunlit canopy (gC/m2/s)
     real(r8), pointer :: psnshade_to_cpool_patch                   (:)     ! C fixation from shaded canopy (gC/m2/s)

     ! allocation fluxes, from current GPP                     
     real(r8), pointer :: cpool_to_xsmrpool_patch                   (:)     ! allocation to maintenance respiration storage pool (gC/m2/s)
     real(r8), pointer :: cpool_to_grainc_patch                     (:)     ! allocation to grain C for prognostic crop(gC/m2/s)
     real(r8), pointer :: cpool_to_grainc_storage_patch             (:)     ! allocation to grain C storage for prognostic crop(gC/m2/s)
     real(r8), pointer :: cpool_to_leafc_patch                      (:)     ! allocation to leaf C (gC/m2/s)
     real(r8), pointer :: cpool_to_leafc_storage_patch              (:)     ! allocation to leaf C storage (gC/m2/s)
     real(r8), pointer :: cpool_to_frootc_patch                     (:)     ! allocation to fine root C (gC/m2/s)
     real(r8), pointer :: cpool_to_frootc_storage_patch             (:)     ! allocation to fine root C storage (gC/m2/s)
     real(r8), pointer :: cpool_to_livestemc_patch                  (:)     ! allocation to live stem C (gC/m2/s)
     real(r8), pointer :: cpool_to_livestemc_storage_patch          (:)     ! allocation to live stem C storage (gC/m2/s)
     real(r8), pointer :: cpool_to_deadstemc_patch                  (:)     ! allocation to dead stem C (gC/m2/s)
     real(r8), pointer :: cpool_to_deadstemc_storage_patch          (:)     ! allocation to dead stem C storage (gC/m2/s)
     real(r8), pointer :: cpool_to_livecrootc_patch                 (:)     ! allocation to live coarse root C (gC/m2/s)
     real(r8), pointer :: cpool_to_livecrootc_storage_patch         (:)     ! allocation to live coarse root C storage (gC/m2/s)
     real(r8), pointer :: cpool_to_deadcrootc_patch                 (:)     ! allocation to dead coarse root C (gC/m2/s)
     real(r8), pointer :: cpool_to_deadcrootc_storage_patch         (:)     ! allocation to dead coarse root C storage (gC/m2/s)
     real(r8), pointer :: cpool_to_gresp_storage_patch              (:)     ! allocation to growth respiration storage (gC/m2/s)

     ! growth respiration fluxes                               
     real(r8), pointer :: xsmrpool_to_atm_patch                     (:)     ! excess MR pool harvest mortality (gC/m2/s)
     real(r8), pointer :: xsmrpool_to_atm_col                       (:)     ! excess MR pool harvest mortality (gC/m2/s) (p2c)
     real(r8), pointer :: xsmrpool_to_atm_grc                       (:)     ! excess MR pool harvest mortality (gC/m2/s) (p2g)
     real(r8), pointer :: cpool_leaf_gr_patch                       (:)     ! leaf growth respiration (gC/m2/s)
     real(r8), pointer :: cpool_leaf_storage_gr_patch               (:)     ! leaf growth respiration to storage (gC/m2/s)
     real(r8), pointer :: transfer_leaf_gr_patch                    (:)     ! leaf growth respiration from storage (gC/m2/s)
     real(r8), pointer :: cpool_froot_gr_patch                      (:)     ! fine root growth respiration (gC/m2/s)
     real(r8), pointer :: cpool_froot_storage_gr_patch              (:)     ! fine root  growth respiration to storage (gC/m2/s)
     real(r8), pointer :: transfer_froot_gr_patch                   (:)     ! fine root  growth respiration from storage (gC/m2/s)
     real(r8), pointer :: cpool_livestem_gr_patch                   (:)     ! live stem growth respiration (gC/m2/s)
     real(r8), pointer :: cpool_livestem_storage_gr_patch           (:)     ! live stem growth respiration to storage (gC/m2/s)
     real(r8), pointer :: transfer_livestem_gr_patch                (:)     ! live stem growth respiration from storage (gC/m2/s)
     real(r8), pointer :: cpool_deadstem_gr_patch                   (:)     ! dead stem growth respiration (gC/m2/s)
     real(r8), pointer :: cpool_deadstem_storage_gr_patch           (:)     ! dead stem growth respiration to storage (gC/m2/s)
     real(r8), pointer :: transfer_deadstem_gr_patch                (:)     ! dead stem growth respiration from storage (gC/m2/s)
     real(r8), pointer :: cpool_livecroot_gr_patch                  (:)     ! live coarse root growth respiration (gC/m2/s)
     real(r8), pointer :: cpool_livecroot_storage_gr_patch          (:)     ! live coarse root growth respiration to storage (gC/m2/s)
     real(r8), pointer :: transfer_livecroot_gr_patch               (:)     ! live coarse root growth respiration from storage (gC/m2/s)
     real(r8), pointer :: cpool_deadcroot_gr_patch                  (:)     ! dead coarse root growth respiration (gC/m2/s)
     real(r8), pointer :: cpool_deadcroot_storage_gr_patch          (:)     ! dead coarse root growth respiration to storage (gC/m2/s)
     real(r8), pointer :: transfer_deadcroot_gr_patch               (:)     ! dead coarse root growth respiration from storage (gC/m2/s)

     ! growth respiration for prognostic crop model
     real(r8), pointer :: cpool_grain_gr_patch                      (:)     ! grain growth respiration (gC/m2/s)
     real(r8), pointer :: cpool_grain_storage_gr_patch              (:)     ! grain growth respiration to storage (gC/m2/s)
     real(r8), pointer :: transfer_grain_gr_patch                   (:)     ! grain growth respiration from storage (gC/m2/s)

     ! annual turnover of storage to transfer pools            
     real(r8), pointer :: grainc_storage_to_xfer_patch              (:)     ! grain C shift storage to transfer for prognostic crop model (gC/m2/s)
     real(r8), pointer :: leafc_storage_to_xfer_patch               (:)     ! leaf C shift storage to transfer (gC/m2/s)
     real(r8), pointer :: frootc_storage_to_xfer_patch              (:)     ! fine root C shift storage to transfer (gC/m2/s)
     real(r8), pointer :: livestemc_storage_to_xfer_patch           (:)     ! live stem C shift storage to transfer (gC/m2/s)
     real(r8), pointer :: deadstemc_storage_to_xfer_patch           (:)     ! dead stem C shift storage to transfer (gC/m2/s)
     real(r8), pointer :: livecrootc_storage_to_xfer_patch          (:)     ! live coarse root C shift storage to transfer (gC/m2/s)
     real(r8), pointer :: deadcrootc_storage_to_xfer_patch          (:)     ! dead coarse root C shift storage to transfer (gC/m2/s)
     real(r8), pointer :: gresp_storage_to_xfer_patch               (:)     ! growth respiration shift storage to transfer (gC/m2/s)

     ! turnover of livewood to deadwood
     real(r8), pointer :: livestemc_to_deadstemc_patch              (:)     ! live stem C turnover (gC/m2/s)
     real(r8), pointer :: livecrootc_to_deadcrootc_patch            (:)     ! live coarse root C turnover (gC/m2/s)

     ! phenology: litterfall and crop fluxes
     real(r8), pointer :: phenology_c_to_litr_met_c_col             (:,:)   ! C fluxes associated with phenology (litterfall and crop) to litter metabolic pool (gC/m3/s)
     real(r8), pointer :: phenology_c_to_litr_cel_c_col             (:,:)   ! C fluxes associated with phenology (litterfall and crop) to litter cellulose pool (gC/m3/s)
     real(r8), pointer :: phenology_c_to_litr_lig_c_col             (:,:)   ! C fluxes associated with phenology (litterfall and crop) to litter lignin pool (gC/m3/s)

     ! gap mortality
     real(r8), pointer :: gap_mortality_c_to_litr_met_c_col         (:,:)   ! C fluxes associated with gap mortality to litter metabolic pool (gC/m3/s)
     real(r8), pointer :: gap_mortality_c_to_litr_cel_c_col         (:,:)   ! C fluxes associated with gap mortality to litter cellulose pool (gC/m3/s)
     real(r8), pointer :: gap_mortality_c_to_litr_lig_c_col         (:,:)   ! C fluxes associated with gap mortality to litter lignin pool (gC/m3/s)
     real(r8), pointer :: gap_mortality_c_to_cwdc_col               (:,:)   ! C fluxes associated with gap mortality to CWD pool (gC/m3/s)

     ! fire
     real(r8), pointer :: fire_mortality_c_to_cwdc_col              (:,:)   ! C fluxes associated with fire mortality to CWD pool (gC/m3/s)

     ! harvest
     real(r8), pointer :: harvest_c_to_litr_met_c_col               (:,:)   ! C fluxes associated with harvest to litter metabolic pool (gC/m3/s)
     real(r8), pointer :: harvest_c_to_litr_cel_c_col               (:,:)   ! C fluxes associated with harvest to litter cellulose pool (gC/m3/s)
     real(r8), pointer :: harvest_c_to_litr_lig_c_col               (:,:)   ! C fluxes associated with harvest to litter lignin pool (gC/m3/s)
     real(r8), pointer :: harvest_c_to_cwdc_col                     (:,:)   ! C fluxes associated with harvest to CWD pool (gC/m3/s)
     real(r8), pointer :: grainc_to_cropprodc_patch                 (:)     ! grain C to crop product pool (gC/m2/s)
     real(r8), pointer :: grainc_to_cropprodc_col                   (:)     ! grain C to crop product pool (gC/m2/s)

     ! fire fluxes
     real(r8), pointer :: m_decomp_cpools_to_fire_vr_col            (:,:,:) ! vertically-resolved decomposing C fire loss (gC/m3/s)
     real(r8), pointer :: m_decomp_cpools_to_fire_col               (:,:)   ! vertically-integrated (diagnostic) decomposing C fire loss (gC/m2/s)
     real(r8), pointer :: m_c_to_litr_met_fire_col                  (:,:)   ! C from leaf, froot, xfer and storage C to litter labile C by fire (gC/m3/s) 
     real(r8), pointer :: m_c_to_litr_cel_fire_col                  (:,:)   ! C from leaf, froot, xfer and storage C to litter cellulose C by fire (gC/m3/s) 
     real(r8), pointer :: m_c_to_litr_lig_fire_col                  (:,:)   ! C from leaf, froot, xfer and storage C to litter lignin C by fire (gC/m3/s) 

     ! dynamic landcover fluxes
     real(r8), pointer :: dwt_seedc_to_leaf_patch                   (:)     ! (gC/m2/s) seed source to patch-level; although this is a patch-level flux, it is expressed per unit GRIDCELL area
     real(r8), pointer :: dwt_seedc_to_leaf_grc                     (:)     ! (gC/m2/s) dwt_seedc_to_leaf_patch summed to the gridcell-level
     real(r8), pointer :: dwt_seedc_to_deadstem_patch               (:)     ! (gC/m2/s) seed source to patch-level; although this is a patch-level flux, it is expressed per unit GRIDCELL area
     real(r8), pointer :: dwt_seedc_to_deadstem_grc                 (:)     ! (gC/m2/s) dwt_seedc_to_leaf_patch summed to the gridcell-level
     real(r8), pointer :: dwt_conv_cflux_patch                      (:)     ! (gC/m2/s) conversion C flux (immediate loss to atm); although this is a patch-level flux, it is expressed per unit GRIDCELL area
     real(r8), pointer :: dwt_conv_cflux_grc                        (:)     ! (gC/m2/s) dwt_conv_cflux_patch summed to the gridcell-level
     real(r8), pointer :: dwt_conv_cflux_dribbled_grc               (:)     ! (gC/m2/s) dwt_conv_cflux_grc dribbled evenly throughout the year
     real(r8), pointer :: dwt_wood_productc_gain_patch              (:)     ! (gC/m2/s) addition to wood product pools from landcover change; although this is a patch-level flux, it is expressed per unit GRIDCELL area
     real(r8), pointer :: dwt_crop_productc_gain_patch              (:)     ! (gC/m2/s) addition to crop product pools from landcover change; although this is a patch-level flux, it is expressed per unit GRIDCELL area
     real(r8), pointer :: dwt_slash_cflux_col                       (:)     ! (gC/m2/s) conversion slash flux due to landcover change
     real(r8), pointer :: dwt_frootc_to_litr_met_c_col              (:,:)   ! (gC/m3/s) fine root to litter due to landcover change
     real(r8), pointer :: dwt_frootc_to_litr_cel_c_col              (:,:)   ! (gC/m3/s) fine root to litter due to landcover change
     real(r8), pointer :: dwt_frootc_to_litr_lig_c_col              (:,:)   ! (gC/m3/s) fine root to litter due to landcover change
     real(r8), pointer :: dwt_livecrootc_to_cwdc_col                (:,:)   ! (gC/m3/s) live coarse root to CWD due to landcover change
     real(r8), pointer :: dwt_deadcrootc_to_cwdc_col                (:,:)   ! (gC/m3/s) dead coarse root to CWD due to landcover change

     ! crop fluxes
     real(r8), pointer :: crop_seedc_to_leaf_patch                  (:)     ! (gC/m2/s) seed source to leaf, for crops

     ! summary (diagnostic) flux variables, not involved in mass balance
     real(r8), pointer :: gpp_before_downreg_patch                  (:)     ! (gC/m2/s) gross primary production before down regulation
     real(r8), pointer :: current_gr_patch                          (:)     ! (gC/m2/s) growth resp for new growth displayed in this timestep
     real(r8), pointer :: transfer_gr_patch                         (:)     ! (gC/m2/s) growth resp for transfer growth displayed in this timestep
     real(r8), pointer :: storage_gr_patch                          (:)     ! (gC/m2/s) growth resp for growth sent to storage for later display
     real(r8), pointer :: plant_calloc_patch                        (:)     ! (gC/m2/s) total allocated C flux 
     real(r8), pointer :: excess_cflux_patch                        (:)     ! (gC/m2/s) C flux not allocated due to downregulation 
     real(r8), pointer :: prev_leafc_to_litter_patch                (:)     ! (gC/m2/s) previous timestep leaf C litterfall flux 
     real(r8), pointer :: prev_frootc_to_litter_patch               (:)     ! (gC/m2/s) previous timestep froot C litterfall flux 
     real(r8), pointer :: availc_patch                              (:)     ! (gC/m2/s) C flux available for allocation 
     real(r8), pointer :: xsmrpool_recover_patch                    (:)     ! (gC/m2/s) C flux assigned to recovery of negative cpool
     real(r8), pointer :: xsmrpool_c13ratio_patch                   (:)     ! C13/C(12+13) ratio for xsmrpool (proportion)

     real(r8), pointer :: cwdc_hr_col                               (:)     ! (gC/m2/s) col-level coarse woody debris C heterotrophic respiration
     real(r8), pointer :: cwdc_loss_col                             (:)     ! (gC/m2/s) col-level coarse woody debris C loss
     real(r8), pointer :: litterc_loss_col                          (:)     ! (gC/m2/s) col-level litter C loss
     real(r8), pointer :: frootc_alloc_patch                        (:)     ! (gC/m2/s) patch-level fine root C alloc
     real(r8), pointer :: frootc_loss_patch                         (:)     ! (gC/m2/s) patch-level fine root C loss
     real(r8), pointer :: leafc_alloc_patch                         (:)     ! (gC/m2/s) patch-level leaf C alloc
     real(r8), pointer :: leafc_loss_patch                          (:)     ! (gC/m2/s) patch-level leaf C loss
     real(r8), pointer :: woodc_alloc_patch                         (:)     ! (gC/m2/s) patch-level wood C alloc
     real(r8), pointer :: woodc_loss_patch                          (:)     ! (gC/m2/s) patch-level wood C loss

     real(r8), pointer :: gpp_patch                                 (:)     ! (gC/m2/s) patch gross primary production 
     real(r8), pointer :: gpp_col                                   (:)     ! (gC/m2/s) column GPP flux before downregulation  (p2c)         
     real(r8), pointer :: rr_patch                                  (:)     ! (gC/m2/s) root respiration (fine root MR + total root GR)
     real(r8), pointer :: rr_col                                    (:)     ! (gC/m2/s) root respiration (fine root MR + total root GR) (p2c)
     real(r8), pointer :: mr_patch                                  (:)     ! (gC/m2/s) maintenance respiration
     real(r8), pointer :: gr_patch                                  (:)     ! (gC/m2/s) total growth respiration
     real(r8), pointer :: ar_patch                                  (:)     ! (gC/m2/s) patch autotrophic respiration (MR + GR)
     real(r8), pointer :: ar_col                                    (:)     ! (gC/m2/s) column autotrophic respiration (MR + GR) (p2c)      
     real(r8), pointer :: npp_patch                                 (:)     ! (gC/m2/s) patch net primary production
     real(r8), pointer :: npp_col                                   (:)     ! (gC/m2/s) column net primary production (p2c)                  
     real(r8), pointer :: agnpp_patch                               (:)     ! (gC/m2/s) aboveground NPP
     real(r8), pointer :: bgnpp_patch                               (:)     ! (gC/m2/s) belowground NPP
     real(r8), pointer :: litfall_patch                             (:)     ! (gC/m2/s) patch litterfall (leaves and fine roots)
     real(r8), pointer :: wood_harvestc_patch                       (:)     ! (gC/m2/s) patch-level wood harvest (to product pools)
     real(r8), pointer :: wood_harvestc_col                         (:)     ! (gC/m2/s) column-level wood harvest (to product pools) (p2c)
     real(r8), pointer :: slash_harvestc_patch                      (:)     ! (gC/m2/s) patch-level slash from harvest (to litter)
     real(r8), pointer :: cinputs_patch                             (:)     ! (gC/m2/s) patch-level carbon inputs (for balance checking)
     real(r8), pointer :: coutputs_patch                            (:)     ! (gC/m2/s) patch-level carbon outputs (for balance checking)
     real(r8), pointer :: sr_col                                    (:)     ! (gC/m2/s) total soil respiration (HR + root resp)
     real(r8), pointer :: er_col                                    (:)     ! (gC/m2/s) total ecosystem respiration, autotrophic + heterotrophic
     real(r8), pointer :: litfire_col                               (:)     ! (gC/m2/s) litter fire losses
     real(r8), pointer :: somfire_col                               (:)     ! (gC/m2/s) soil organic matter fire losses
     real(r8), pointer :: totfire_col                               (:)     ! (gC/m2/s) total ecosystem fire losses
     real(r8), pointer :: hrv_xsmrpool_to_atm_col                   (:)     ! (gC/m2/s) excess MR pool harvest mortality (p2c)

     ! fire code
     real(r8), pointer :: fire_closs_patch                          (:)     ! (gC/m2/s) total fire C loss 
     real(r8), pointer :: fire_closs_p2c_col                        (:)     ! (gC/m2/s) patch2col averaged column-level fire C loss (p2c)
     real(r8), pointer :: fire_closs_col                            (:)     ! (gC/m2/s) total patch-level fire C loss 

     ! temporary and annual sums
     real(r8), pointer :: tempsum_litfall_patch                     (:)     ! (gC/m2/yr) temporary annual sum of litfall (CNDV only for now)
     real(r8), pointer :: annsum_litfall_patch                      (:)     ! (gC/m2/yr) annual sum of litfall (CNDV only for now)
     real(r8), pointer :: tempsum_npp_patch                         (:)     ! (gC/m2/yr) temporary annual sum of NPP 
     real(r8), pointer :: annsum_npp_patch                          (:)     ! (gC/m2/yr) annual sum of NPP 
     real(r8), pointer :: annsum_npp_col                            (:)     ! (gC/m2/yr) annual sum of NPP, averaged from patch-level
     real(r8), pointer :: lag_npp_col                               (:)     ! (gC/m2/yr) lagged net primary production

     ! Summary C fluxes. 
     real(r8), pointer :: nep_col        (:) ! (gC/m2/s) net ecosystem production, excludes fire, landuse, and harvest flux, positive for sink
     real(r8), pointer :: nbp_grc        (:) ! (gC/m2/s) net biome production, includes fire, landuse, harvest and hrv_xsmrpool flux, positive for sink (same as net carbon exchange between land and atmosphere)
     real(r8), pointer :: nee_grc        (:) ! (gC/m2/s) net ecosystem exchange of carbon, includes fire and hrv_xsmrpool, excludes landuse and harvest flux, positive for source 

     ! Dynamic landcover fluxnes
     real(r8), pointer :: landuseflux_grc(:) ! (gC/m2/s) dwt_conv_cflux+product_closs
     real(r8), pointer :: npp_Nactive_patch                         (:)     ! C used by mycorrhizal uptake    (gC/m2/s)
     real(r8), pointer :: npp_burnedoff_patch                       (:)     ! C that cannot be used for N uptake   (gC/m2/s)
     real(r8), pointer :: npp_Nnonmyc_patch                         (:)     ! C used by non-myc uptake        (gC/m2/s)
     real(r8), pointer :: npp_Nam_patch                             (:)     ! C used by AM plant              (gC/m2/s)
     real(r8), pointer :: npp_Necm_patch                            (:)     ! C used by ECM plant             (gC/m2/s)
     real(r8), pointer :: npp_Nactive_no3_patch                     (:)     ! C used by mycorrhizal uptake    (gC/m2/s)
     real(r8), pointer :: npp_Nactive_nh4_patch                     (:)     ! C used by mycorrhizal uptake    (gC/m2/s)
     real(r8), pointer :: npp_Nnonmyc_no3_patch                     (:)     ! C used by non-myc               (gC/m2/s)
     real(r8), pointer :: npp_Nnonmyc_nh4_patch                     (:)     ! C used by non-myc               (gC/m2/s)
     real(r8), pointer :: npp_Nam_no3_patch                         (:)     ! C used by AM plant              (gC/m2/s)
     real(r8), pointer :: npp_Nam_nh4_patch                         (:)     ! C used by AM plant              (gC/m2/s)
     real(r8), pointer :: npp_Necm_no3_patch                        (:)     ! C used by ECM plant             (gC/m2/s)
     real(r8), pointer :: npp_Necm_nh4_patch                        (:)     ! C used by ECM plant             (gC/m2/s)
     real(r8), pointer :: npp_Nfix_patch                            (:)     ! C used by Symbiotic BNF         (gC/m2/s)
     real(r8), pointer :: npp_Nretrans_patch                        (:)     ! C used by retranslocation       (gC/m2/s)
     real(r8), pointer :: npp_Nuptake_patch                         (:)     ! Total C used by N uptake in FUN (gC/m2/s)
     real(r8), pointer :: npp_growth_patch                         (:)     ! Total C u for growth in FUN      (gC/m2/s)   
     real(r8), pointer :: leafc_change_patch                        (:)     ! Total used C from leaves        (gC/m2/s)
     real(r8), pointer :: soilc_change_patch                        (:)     ! Total used C from soil          (gC/m2/s)
 
!     real(r8), pointer :: soilc_change_col                          (:)     ! Total used C from soil          (gC/m2/s)

     ! Objects that help convert once-per-year dynamic land cover changes into fluxes
     ! that are dribbled throughout the year
     type(annual_flux_dribbler_type) :: dwt_conv_cflux_dribbler
     type(annual_flux_dribbler_type) :: hrv_xsmrpool_to_atm_dribbler
     logical, private  :: dribble_crophrv_xsmrpool_2atm
   contains

     procedure , public  :: Init   
     procedure , private :: InitAllocate 
     procedure , private :: InitHistory
     procedure , private :: InitCold
     procedure , public  :: Restart
     procedure , private :: RestartBulkOnly    ! Handle restart fields only present for bulk C
     procedure , private :: RestartAllIsotopes ! Handle restart fields present for both bulk C and isotopes
     procedure , public  :: SetValues
     procedure , public  :: ZeroDWT
     procedure , public  :: Summary => Summary_carbonflux 

  end type cnveg_carbonflux_type

  character(len=*), parameter, private :: sourcefile = &
       __FILE__
  !------------------------------------------------------------------------

contains
   
  !------------------------------------------------------------------------
  subroutine Init(this, bounds, carbon_type, dribble_crophrv_xsmrpool_2atm)

    class(cnveg_carbonflux_type) :: this
    type(bounds_type), intent(in) :: bounds  
    character(len=3) , intent(in) :: carbon_type ! one of ['c12', c13','c14']
    logical          , intent(in) :: dribble_crophrv_xsmrpool_2atm

    this%dribble_crophrv_xsmrpool_2atm = dribble_crophrv_xsmrpool_2atm
    call this%InitAllocate ( bounds, carbon_type)
    call this%InitHistory ( bounds, carbon_type )
    call this%InitCold (bounds )

  end subroutine Init

  !------------------------------------------------------------------------
  subroutine InitAllocate(this, bounds, carbon_type)
    !
    ! !ARGUMENTS:
    class (cnveg_carbonflux_type) :: this 
    type(bounds_type), intent(in) :: bounds 
    character(len=*) , intent(in) :: carbon_type ! one of ['c12', c13','c14']
    !
    ! !LOCAL VARIABLES:
    integer           :: begp,endp
    integer           :: begc,endc
    integer           :: begg,endg
    logical           :: allows_non_annual_delta
    character(len=:), allocatable :: carbon_type_suffix
    !------------------------------------------------------------------------

    begp = bounds%begp; endp = bounds%endp
    begc = bounds%begc; endc = bounds%endc
    begg = bounds%begg; endg = bounds%endg

    allocate(this%m_leafc_to_litter_patch                   (begp:endp)) ; this%m_leafc_to_litter_patch                   (:) = nan
    allocate(this%m_frootc_to_litter_patch                  (begp:endp)) ; this%m_frootc_to_litter_patch                  (:) = nan
    allocate(this%m_leafc_storage_to_litter_patch           (begp:endp)) ; this%m_leafc_storage_to_litter_patch           (:) = nan
    allocate(this%m_frootc_storage_to_litter_patch          (begp:endp)) ; this%m_frootc_storage_to_litter_patch          (:) = nan
    allocate(this%m_livestemc_storage_to_litter_patch       (begp:endp)) ; this%m_livestemc_storage_to_litter_patch       (:) = nan
    allocate(this%m_deadstemc_storage_to_litter_patch       (begp:endp)) ; this%m_deadstemc_storage_to_litter_patch       (:) = nan
    allocate(this%m_livecrootc_storage_to_litter_patch      (begp:endp)) ; this%m_livecrootc_storage_to_litter_patch      (:) = nan
    allocate(this%m_deadcrootc_storage_to_litter_patch      (begp:endp)) ; this%m_deadcrootc_storage_to_litter_patch      (:) = nan
    allocate(this%m_leafc_xfer_to_litter_patch              (begp:endp)) ; this%m_leafc_xfer_to_litter_patch              (:) = nan
    allocate(this%m_frootc_xfer_to_litter_patch             (begp:endp)) ; this%m_frootc_xfer_to_litter_patch             (:) = nan
    allocate(this%m_livestemc_xfer_to_litter_patch          (begp:endp)) ; this%m_livestemc_xfer_to_litter_patch          (:) = nan
    allocate(this%m_deadstemc_xfer_to_litter_patch          (begp:endp)) ; this%m_deadstemc_xfer_to_litter_patch          (:) = nan
    allocate(this%m_livecrootc_xfer_to_litter_patch         (begp:endp)) ; this%m_livecrootc_xfer_to_litter_patch         (:) = nan
    allocate(this%m_deadcrootc_xfer_to_litter_patch         (begp:endp)) ; this%m_deadcrootc_xfer_to_litter_patch         (:) = nan
    allocate(this%m_livestemc_to_litter_patch               (begp:endp)) ; this%m_livestemc_to_litter_patch               (:) = nan
    allocate(this%m_deadstemc_to_litter_patch               (begp:endp)) ; this%m_deadstemc_to_litter_patch               (:) = nan
    allocate(this%m_livecrootc_to_litter_patch              (begp:endp)) ; this%m_livecrootc_to_litter_patch              (:) = nan
    allocate(this%m_deadcrootc_to_litter_patch              (begp:endp)) ; this%m_deadcrootc_to_litter_patch              (:) = nan
    allocate(this%m_gresp_storage_to_litter_patch           (begp:endp)) ; this%m_gresp_storage_to_litter_patch           (:) = nan
    allocate(this%m_gresp_xfer_to_litter_patch              (begp:endp)) ; this%m_gresp_xfer_to_litter_patch              (:) = nan
    allocate(this%hrv_leafc_to_litter_patch                 (begp:endp)) ; this%hrv_leafc_to_litter_patch                 (:) = nan
    allocate(this%hrv_leafc_storage_to_litter_patch         (begp:endp)) ; this%hrv_leafc_storage_to_litter_patch         (:) = nan
    allocate(this%hrv_leafc_xfer_to_litter_patch            (begp:endp)) ; this%hrv_leafc_xfer_to_litter_patch            (:) = nan
    allocate(this%hrv_frootc_to_litter_patch                (begp:endp)) ; this%hrv_frootc_to_litter_patch                (:) = nan
    allocate(this%hrv_frootc_storage_to_litter_patch        (begp:endp)) ; this%hrv_frootc_storage_to_litter_patch        (:) = nan
    allocate(this%hrv_frootc_xfer_to_litter_patch           (begp:endp)) ; this%hrv_frootc_xfer_to_litter_patch           (:) = nan
    allocate(this%hrv_livestemc_to_litter_patch             (begp:endp)) ; this%hrv_livestemc_to_litter_patch             (:) = nan
    allocate(this%hrv_livestemc_storage_to_litter_patch     (begp:endp)) ; this%hrv_livestemc_storage_to_litter_patch     (:) = nan
    allocate(this%hrv_livestemc_xfer_to_litter_patch        (begp:endp)) ; this%hrv_livestemc_xfer_to_litter_patch        (:) = nan
    allocate(this%hrv_deadstemc_storage_to_litter_patch     (begp:endp)) ; this%hrv_deadstemc_storage_to_litter_patch     (:) = nan
    allocate(this%hrv_deadstemc_xfer_to_litter_patch        (begp:endp)) ; this%hrv_deadstemc_xfer_to_litter_patch        (:) = nan
    allocate(this%hrv_livecrootc_to_litter_patch            (begp:endp)) ; this%hrv_livecrootc_to_litter_patch            (:) = nan
    allocate(this%hrv_livecrootc_storage_to_litter_patch    (begp:endp)) ; this%hrv_livecrootc_storage_to_litter_patch    (:) = nan
    allocate(this%hrv_livecrootc_xfer_to_litter_patch       (begp:endp)) ; this%hrv_livecrootc_xfer_to_litter_patch       (:) = nan
    allocate(this%hrv_deadcrootc_to_litter_patch            (begp:endp)) ; this%hrv_deadcrootc_to_litter_patch            (:) = nan
    allocate(this%hrv_deadcrootc_storage_to_litter_patch    (begp:endp)) ; this%hrv_deadcrootc_storage_to_litter_patch    (:) = nan
    allocate(this%hrv_deadcrootc_xfer_to_litter_patch       (begp:endp)) ; this%hrv_deadcrootc_xfer_to_litter_patch       (:) = nan
    allocate(this%hrv_gresp_storage_to_litter_patch         (begp:endp)) ; this%hrv_gresp_storage_to_litter_patch         (:) = nan
    allocate(this%hrv_gresp_xfer_to_litter_patch            (begp:endp)) ; this%hrv_gresp_xfer_to_litter_patch            (:) = nan
    allocate(this%hrv_xsmrpool_to_atm_patch                 (begp:endp)) ; this%hrv_xsmrpool_to_atm_patch                 (:) = 0.0_r8
    allocate(this%m_leafc_to_fire_patch                     (begp:endp)) ; this%m_leafc_to_fire_patch                     (:) = nan
    allocate(this%m_leafc_storage_to_fire_patch             (begp:endp)) ; this%m_leafc_storage_to_fire_patch             (:) = nan
    allocate(this%m_leafc_xfer_to_fire_patch                (begp:endp)) ; this%m_leafc_xfer_to_fire_patch                (:) = nan
    allocate(this%m_livestemc_to_fire_patch                 (begp:endp)) ; this%m_livestemc_to_fire_patch                 (:) = nan
    allocate(this%m_livestemc_storage_to_fire_patch         (begp:endp)) ; this%m_livestemc_storage_to_fire_patch         (:) = nan
    allocate(this%m_livestemc_xfer_to_fire_patch            (begp:endp)) ; this%m_livestemc_xfer_to_fire_patch            (:) = nan
    allocate(this%m_deadstemc_to_fire_patch                 (begp:endp)) ; this%m_deadstemc_to_fire_patch                 (:) = nan
    allocate(this%m_deadstemc_storage_to_fire_patch         (begp:endp)) ; this%m_deadstemc_storage_to_fire_patch         (:) = nan
    allocate(this%m_deadstemc_xfer_to_fire_patch            (begp:endp)) ; this%m_deadstemc_xfer_to_fire_patch            (:) = nan
    allocate(this%m_frootc_to_fire_patch                    (begp:endp)) ; this%m_frootc_to_fire_patch                    (:) = nan
    allocate(this%m_frootc_storage_to_fire_patch            (begp:endp)) ; this%m_frootc_storage_to_fire_patch            (:) = nan
    allocate(this%m_frootc_xfer_to_fire_patch               (begp:endp)) ; this%m_frootc_xfer_to_fire_patch               (:) = nan
    allocate(this%m_livecrootc_to_fire_patch                (begp:endp)) ; this%m_livecrootc_to_fire_patch                (:) = nan
    allocate(this%m_livecrootc_storage_to_fire_patch        (begp:endp)) ; this%m_livecrootc_storage_to_fire_patch        (:) = nan
    allocate(this%m_livecrootc_xfer_to_fire_patch           (begp:endp)) ; this%m_livecrootc_xfer_to_fire_patch           (:) = nan
    allocate(this%m_deadcrootc_to_fire_patch                (begp:endp)) ; this%m_deadcrootc_to_fire_patch                (:) = nan
    allocate(this%m_deadcrootc_storage_to_fire_patch        (begp:endp)) ; this%m_deadcrootc_storage_to_fire_patch        (:) = nan
    allocate(this%m_deadcrootc_xfer_to_fire_patch           (begp:endp)) ; this%m_deadcrootc_xfer_to_fire_patch           (:) = nan
    allocate(this%m_gresp_storage_to_fire_patch             (begp:endp)) ; this%m_gresp_storage_to_fire_patch             (:) = nan
    allocate(this%m_gresp_xfer_to_fire_patch                (begp:endp)) ; this%m_gresp_xfer_to_fire_patch                (:) = nan
    allocate(this%m_leafc_to_litter_fire_patch              (begp:endp)) ; this%m_leafc_to_litter_fire_patch              (:) = nan
    allocate(this%m_leafc_storage_to_litter_fire_patch      (begp:endp)) ; this%m_leafc_storage_to_litter_fire_patch      (:) = nan
    allocate(this%m_leafc_xfer_to_litter_fire_patch         (begp:endp)) ; this%m_leafc_xfer_to_litter_fire_patch         (:) = nan
    allocate(this%m_livestemc_to_litter_fire_patch          (begp:endp)) ; this%m_livestemc_to_litter_fire_patch          (:) = nan
    allocate(this%m_livestemc_storage_to_litter_fire_patch  (begp:endp)) ; this%m_livestemc_storage_to_litter_fire_patch  (:) = nan
    allocate(this%m_livestemc_xfer_to_litter_fire_patch     (begp:endp)) ; this%m_livestemc_xfer_to_litter_fire_patch     (:) = nan
    allocate(this%m_livestemc_to_deadstemc_fire_patch       (begp:endp)) ; this%m_livestemc_to_deadstemc_fire_patch       (:) = nan
    allocate(this%m_deadstemc_to_litter_fire_patch          (begp:endp)) ; this%m_deadstemc_to_litter_fire_patch          (:) = nan
    allocate(this%m_deadstemc_storage_to_litter_fire_patch  (begp:endp)) ; this%m_deadstemc_storage_to_litter_fire_patch  (:) = nan
    allocate(this%m_deadstemc_xfer_to_litter_fire_patch     (begp:endp)) ; this%m_deadstemc_xfer_to_litter_fire_patch     (:) = nan
    allocate(this%m_frootc_to_litter_fire_patch             (begp:endp)) ; this%m_frootc_to_litter_fire_patch             (:) = nan
    allocate(this%m_frootc_storage_to_litter_fire_patch     (begp:endp)) ; this%m_frootc_storage_to_litter_fire_patch     (:) = nan
    allocate(this%m_frootc_xfer_to_litter_fire_patch        (begp:endp)) ; this%m_frootc_xfer_to_litter_fire_patch        (:) = nan
    allocate(this%m_livecrootc_to_litter_fire_patch         (begp:endp)) ; this%m_livecrootc_to_litter_fire_patch         (:) = nan
    allocate(this%m_livecrootc_storage_to_litter_fire_patch (begp:endp)) ; this%m_livecrootc_storage_to_litter_fire_patch (:) = nan
    allocate(this%m_livecrootc_xfer_to_litter_fire_patch    (begp:endp)) ; this%m_livecrootc_xfer_to_litter_fire_patch    (:) = nan
    allocate(this%m_livecrootc_to_deadcrootc_fire_patch     (begp:endp)) ; this%m_livecrootc_to_deadcrootc_fire_patch     (:) = nan
    allocate(this%m_deadcrootc_to_litter_fire_patch         (begp:endp)) ; this%m_deadcrootc_to_litter_fire_patch         (:) = nan
    allocate(this%m_deadcrootc_storage_to_litter_fire_patch (begp:endp)) ; this%m_deadcrootc_storage_to_litter_fire_patch (:) = nan
    allocate(this%m_deadcrootc_xfer_to_litter_fire_patch    (begp:endp)) ; this%m_deadcrootc_xfer_to_litter_fire_patch    (:) = nan
    allocate(this%m_gresp_storage_to_litter_fire_patch      (begp:endp)) ; this%m_gresp_storage_to_litter_fire_patch      (:) = nan
    allocate(this%m_gresp_xfer_to_litter_fire_patch         (begp:endp)) ; this%m_gresp_xfer_to_litter_fire_patch         (:) = nan
    allocate(this%leafc_xfer_to_leafc_patch                 (begp:endp)) ; this%leafc_xfer_to_leafc_patch                 (:) = nan
    allocate(this%frootc_xfer_to_frootc_patch               (begp:endp)) ; this%frootc_xfer_to_frootc_patch               (:) = nan
    allocate(this%livestemc_xfer_to_livestemc_patch         (begp:endp)) ; this%livestemc_xfer_to_livestemc_patch         (:) = nan
    allocate(this%deadstemc_xfer_to_deadstemc_patch         (begp:endp)) ; this%deadstemc_xfer_to_deadstemc_patch         (:) = nan
    allocate(this%livecrootc_xfer_to_livecrootc_patch       (begp:endp)) ; this%livecrootc_xfer_to_livecrootc_patch       (:) = nan
    allocate(this%deadcrootc_xfer_to_deadcrootc_patch       (begp:endp)) ; this%deadcrootc_xfer_to_deadcrootc_patch       (:) = nan
    allocate(this%leafc_to_litter_patch                     (begp:endp)) ; this%leafc_to_litter_patch                     (:) = nan
    allocate(this%leafc_to_litter_fun_patch                 (begp:endp)) ; this%leafc_to_litter_fun_patch                 (:) = nan
    allocate(this%frootc_to_litter_patch                    (begp:endp)) ; this%frootc_to_litter_patch                    (:) = nan
    allocate(this%cpool_to_resp_patch                       (begp:endp)) ; this%cpool_to_resp_patch                       (:) = nan
    allocate(this%cpool_to_leafc_resp_patch                 (begp:endp)) ; this%cpool_to_leafc_resp_patch                 (:) = nan
    allocate(this%cpool_to_leafc_storage_resp_patch         (begp:endp)) ; this%cpool_to_leafc_storage_resp_patch         (:) = nan
    allocate(this%cpool_to_frootc_resp_patch                (begp:endp)) ; this%cpool_to_frootc_resp_patch                (:) = nan
    allocate(this%cpool_to_frootc_storage_resp_patch        (begp:endp)) ; this%cpool_to_frootc_storage_resp_patch        (:) = nan
    allocate(this%cpool_to_livecrootc_resp_patch            (begp:endp)) ; this%cpool_to_livecrootc_resp_patch            (:) = nan
    allocate(this%cpool_to_livecrootc_storage_resp_patch    (begp:endp)) ; this%cpool_to_livecrootc_storage_resp_patch    (:) = nan
    allocate(this%cpool_to_livestemc_resp_patch             (begp:endp)) ; this%cpool_to_livestemc_resp_patch             (:) = nan
    allocate(this%cpool_to_livestemc_storage_resp_patch     (begp:endp)) ; this%cpool_to_livestemc_storage_resp_patch     (:) = nan
    allocate(this%leaf_mr_patch                             (begp:endp)) ; this%leaf_mr_patch                             (:) = nan
    allocate(this%froot_mr_patch                            (begp:endp)) ; this%froot_mr_patch                            (:) = nan
    allocate(this%livestem_mr_patch                         (begp:endp)) ; this%livestem_mr_patch                         (:) = nan
    allocate(this%livecroot_mr_patch                        (begp:endp)) ; this%livecroot_mr_patch                        (:) = nan
    allocate(this%grain_mr_patch                            (begp:endp)) ; this%grain_mr_patch                            (:) = nan
    allocate(this%leaf_curmr_patch                          (begp:endp)) ; this%leaf_curmr_patch                          (:) = nan
    allocate(this%froot_curmr_patch                         (begp:endp)) ; this%froot_curmr_patch                         (:) = nan
    allocate(this%livestem_curmr_patch                      (begp:endp)) ; this%livestem_curmr_patch                      (:) = nan
    allocate(this%livecroot_curmr_patch                     (begp:endp)) ; this%livecroot_curmr_patch                     (:) = nan
    allocate(this%grain_curmr_patch                         (begp:endp)) ; this%grain_curmr_patch                         (:) = nan
    allocate(this%leaf_xsmr_patch                           (begp:endp)) ; this%leaf_xsmr_patch                           (:) = nan
    allocate(this%froot_xsmr_patch                          (begp:endp)) ; this%froot_xsmr_patch                          (:) = nan
    allocate(this%livestem_xsmr_patch                       (begp:endp)) ; this%livestem_xsmr_patch                       (:) = nan
    allocate(this%livecroot_xsmr_patch                      (begp:endp)) ; this%livecroot_xsmr_patch                      (:) = nan
    allocate(this%grain_xsmr_patch                          (begp:endp)) ; this%grain_xsmr_patch                          (:) = nan
    allocate(this%psnsun_to_cpool_patch                     (begp:endp)) ; this%psnsun_to_cpool_patch                     (:) = nan
    allocate(this%psnshade_to_cpool_patch                   (begp:endp)) ; this%psnshade_to_cpool_patch                   (:) = nan
    allocate(this%cpool_to_xsmrpool_patch                   (begp:endp)) ; this%cpool_to_xsmrpool_patch                   (:) = nan
    allocate(this%cpool_to_leafc_patch                      (begp:endp)) ; this%cpool_to_leafc_patch                      (:) = nan
    allocate(this%cpool_to_leafc_storage_patch              (begp:endp)) ; this%cpool_to_leafc_storage_patch              (:) = nan
    allocate(this%cpool_to_frootc_patch                     (begp:endp)) ; this%cpool_to_frootc_patch                     (:) = nan
    allocate(this%cpool_to_frootc_storage_patch             (begp:endp)) ; this%cpool_to_frootc_storage_patch             (:) = nan
    allocate(this%cpool_to_livestemc_patch                  (begp:endp)) ; this%cpool_to_livestemc_patch                  (:) = nan
    allocate(this%cpool_to_livestemc_storage_patch          (begp:endp)) ; this%cpool_to_livestemc_storage_patch          (:) = nan
    allocate(this%cpool_to_deadstemc_patch                  (begp:endp)) ; this%cpool_to_deadstemc_patch                  (:) = nan
    allocate(this%cpool_to_deadstemc_storage_patch          (begp:endp)) ; this%cpool_to_deadstemc_storage_patch          (:) = nan
    allocate(this%cpool_to_livecrootc_patch                 (begp:endp)) ; this%cpool_to_livecrootc_patch                 (:) = nan
    allocate(this%cpool_to_livecrootc_storage_patch         (begp:endp)) ; this%cpool_to_livecrootc_storage_patch         (:) = nan
    allocate(this%cpool_to_deadcrootc_patch                 (begp:endp)) ; this%cpool_to_deadcrootc_patch                 (:) = nan
    allocate(this%cpool_to_deadcrootc_storage_patch         (begp:endp)) ; this%cpool_to_deadcrootc_storage_patch         (:) = nan
    allocate(this%cpool_to_gresp_storage_patch              (begp:endp)) ; this%cpool_to_gresp_storage_patch              (:) = nan
    allocate(this%cpool_leaf_gr_patch                       (begp:endp)) ; this%cpool_leaf_gr_patch                       (:) = nan
    allocate(this%cpool_leaf_storage_gr_patch               (begp:endp)) ; this%cpool_leaf_storage_gr_patch               (:) = nan
    allocate(this%transfer_leaf_gr_patch                    (begp:endp)) ; this%transfer_leaf_gr_patch                    (:) = nan
    allocate(this%cpool_froot_gr_patch                      (begp:endp)) ; this%cpool_froot_gr_patch                      (:) = nan
    allocate(this%cpool_froot_storage_gr_patch              (begp:endp)) ; this%cpool_froot_storage_gr_patch              (:) = nan
    allocate(this%transfer_froot_gr_patch                   (begp:endp)) ; this%transfer_froot_gr_patch                   (:) = nan
    allocate(this%cpool_livestem_gr_patch                   (begp:endp)) ; this%cpool_livestem_gr_patch                   (:) = nan
    allocate(this%cpool_livestem_storage_gr_patch           (begp:endp)) ; this%cpool_livestem_storage_gr_patch           (:) = nan
    allocate(this%transfer_livestem_gr_patch                (begp:endp)) ; this%transfer_livestem_gr_patch                (:) = nan
    allocate(this%cpool_deadstem_gr_patch                   (begp:endp)) ; this%cpool_deadstem_gr_patch                   (:) = nan
    allocate(this%cpool_deadstem_storage_gr_patch           (begp:endp)) ; this%cpool_deadstem_storage_gr_patch           (:) = nan
    allocate(this%transfer_deadstem_gr_patch                (begp:endp)) ; this%transfer_deadstem_gr_patch                (:) = nan
    allocate(this%cpool_livecroot_gr_patch                  (begp:endp)) ; this%cpool_livecroot_gr_patch                  (:) = nan
    allocate(this%cpool_livecroot_storage_gr_patch          (begp:endp)) ; this%cpool_livecroot_storage_gr_patch          (:) = nan
    allocate(this%transfer_livecroot_gr_patch               (begp:endp)) ; this%transfer_livecroot_gr_patch               (:) = nan
    allocate(this%cpool_deadcroot_gr_patch                  (begp:endp)) ; this%cpool_deadcroot_gr_patch                  (:) = nan
    allocate(this%cpool_deadcroot_storage_gr_patch          (begp:endp)) ; this%cpool_deadcroot_storage_gr_patch          (:) = nan
    allocate(this%transfer_deadcroot_gr_patch               (begp:endp)) ; this%transfer_deadcroot_gr_patch               (:) = nan
    allocate(this%leafc_storage_to_xfer_patch               (begp:endp)) ; this%leafc_storage_to_xfer_patch               (:) = nan
    allocate(this%frootc_storage_to_xfer_patch              (begp:endp)) ; this%frootc_storage_to_xfer_patch              (:) = nan
    allocate(this%livestemc_storage_to_xfer_patch           (begp:endp)) ; this%livestemc_storage_to_xfer_patch           (:) = nan
    allocate(this%deadstemc_storage_to_xfer_patch           (begp:endp)) ; this%deadstemc_storage_to_xfer_patch           (:) = nan
    allocate(this%livecrootc_storage_to_xfer_patch          (begp:endp)) ; this%livecrootc_storage_to_xfer_patch          (:) = nan
    allocate(this%deadcrootc_storage_to_xfer_patch          (begp:endp)) ; this%deadcrootc_storage_to_xfer_patch          (:) = nan
    allocate(this%gresp_storage_to_xfer_patch               (begp:endp)) ; this%gresp_storage_to_xfer_patch               (:) = nan
    allocate(this%livestemc_to_deadstemc_patch              (begp:endp)) ; this%livestemc_to_deadstemc_patch              (:) = nan
    allocate(this%livecrootc_to_deadcrootc_patch            (begp:endp)) ; this%livecrootc_to_deadcrootc_patch            (:) = nan
    allocate(this%current_gr_patch                          (begp:endp)) ; this%current_gr_patch                          (:) = nan
    allocate(this%transfer_gr_patch                         (begp:endp)) ; this%transfer_gr_patch                         (:) = nan
    allocate(this%storage_gr_patch                          (begp:endp)) ; this%storage_gr_patch                          (:) = nan
    allocate(this%plant_calloc_patch                        (begp:endp)) ; this%plant_calloc_patch                        (:) = nan
    allocate(this%excess_cflux_patch                        (begp:endp)) ; this%excess_cflux_patch                        (:) = nan
    allocate(this%prev_leafc_to_litter_patch                (begp:endp)) ; this%prev_leafc_to_litter_patch                (:) = nan
    allocate(this%prev_frootc_to_litter_patch               (begp:endp)) ; this%prev_frootc_to_litter_patch               (:) = nan
    allocate(this%gpp_before_downreg_patch                  (begp:endp)) ; this%gpp_before_downreg_patch                  (:) = nan
    allocate(this%availc_patch                              (begp:endp)) ; this%availc_patch                              (:) = nan
    allocate(this%xsmrpool_recover_patch                    (begp:endp)) ; this%xsmrpool_recover_patch                    (:) = nan
    allocate(this%xsmrpool_c13ratio_patch                   (begp:endp)) ; this%xsmrpool_c13ratio_patch                   (:) = nan

    allocate(this%cpool_to_grainc_patch                     (begp:endp)) ; this%cpool_to_grainc_patch                     (:) = nan
    allocate(this%cpool_to_grainc_storage_patch             (begp:endp)) ; this%cpool_to_grainc_storage_patch             (:) = nan
    allocate(this%livestemc_to_litter_patch                 (begp:endp)) ; this%livestemc_to_litter_patch                 (:) = nan
    allocate(this%grainc_to_food_patch                      (begp:endp)) ; this%grainc_to_food_patch                      (:) = nan
    allocate(this%grainc_to_seed_patch                      (begp:endp)) ; this%grainc_to_seed_patch                      (:) = nan
    allocate(this%grainc_xfer_to_grainc_patch               (begp:endp)) ; this%grainc_xfer_to_grainc_patch               (:) = nan
    allocate(this%cpool_grain_gr_patch                      (begp:endp)) ; this%cpool_grain_gr_patch                      (:) = nan
    allocate(this%cpool_grain_storage_gr_patch              (begp:endp)) ; this%cpool_grain_storage_gr_patch              (:) = nan
    allocate(this%transfer_grain_gr_patch                   (begp:endp)) ; this%transfer_grain_gr_patch                   (:) = nan
    allocate(this%xsmrpool_to_atm_patch                     (begp:endp)) ; this%xsmrpool_to_atm_patch                     (:) = 0.0_r8
    allocate(this%xsmrpool_to_atm_col                       (begc:endc)) ; this%xsmrpool_to_atm_col                       (:) = 0.0_r8
    allocate(this%xsmrpool_to_atm_grc                       (begg:endg)) ; this%xsmrpool_to_atm_grc                       (:) = 0.0_r8
    allocate(this%grainc_storage_to_xfer_patch              (begp:endp)) ; this%grainc_storage_to_xfer_patch              (:) = nan
    allocate(this%frootc_alloc_patch                        (begp:endp)) ; this%frootc_alloc_patch                        (:) = nan
    allocate(this%frootc_loss_patch                         (begp:endp)) ; this%frootc_loss_patch                         (:) = nan
    allocate(this%leafc_alloc_patch                         (begp:endp)) ; this%leafc_alloc_patch                         (:) = nan
    allocate(this%leafc_loss_patch                          (begp:endp)) ; this%leafc_loss_patch                          (:) = nan
    allocate(this%woodc_alloc_patch                         (begp:endp)) ; this%woodc_alloc_patch                         (:) = nan
    allocate(this%woodc_loss_patch                          (begp:endp)) ; this%woodc_loss_patch                          (:) = nan

    allocate(this%phenology_c_to_litr_met_c_col     (begc:endc,1:nlevdecomp_full)); 
    this%phenology_c_to_litr_met_c_col (:,:)=nan
    
    allocate(this%phenology_c_to_litr_cel_c_col     (begc:endc,1:nlevdecomp_full)); this%phenology_c_to_litr_cel_c_col (:,:)=nan
    allocate(this%phenology_c_to_litr_lig_c_col     (begc:endc,1:nlevdecomp_full)); this%phenology_c_to_litr_lig_c_col (:,:)=nan

    allocate(this%gap_mortality_c_to_litr_met_c_col (begc:endc,1:nlevdecomp_full)); this%gap_mortality_c_to_litr_met_c_col(:,:)=nan
    allocate(this%gap_mortality_c_to_litr_cel_c_col (begc:endc,1:nlevdecomp_full)); this%gap_mortality_c_to_litr_cel_c_col(:,:)=nan
    allocate(this%gap_mortality_c_to_litr_lig_c_col (begc:endc,1:nlevdecomp_full)); this%gap_mortality_c_to_litr_lig_c_col(:,:)=nan

    allocate(this%gap_mortality_c_to_cwdc_col       (begc:endc,1:nlevdecomp_full)); this%gap_mortality_c_to_cwdc_col  (:,:)=nan
    allocate(this%fire_mortality_c_to_cwdc_col      (begc:endc,1:nlevdecomp_full)); this%fire_mortality_c_to_cwdc_col (:,:)=nan
    allocate(this%m_c_to_litr_met_fire_col          (begc:endc,1:nlevdecomp_full)); this%m_c_to_litr_met_fire_col     (:,:)=nan
    allocate(this%m_c_to_litr_cel_fire_col          (begc:endc,1:nlevdecomp_full)); this%m_c_to_litr_cel_fire_col     (:,:)=nan
    allocate(this%m_c_to_litr_lig_fire_col          (begc:endc,1:nlevdecomp_full)); this%m_c_to_litr_lig_fire_col     (:,:)=nan
    allocate(this%harvest_c_to_litr_met_c_col       (begc:endc,1:nlevdecomp_full)); this%harvest_c_to_litr_met_c_col  (:,:)=nan
    allocate(this%harvest_c_to_litr_cel_c_col       (begc:endc,1:nlevdecomp_full)); this%harvest_c_to_litr_cel_c_col  (:,:)=nan
    allocate(this%harvest_c_to_litr_lig_c_col       (begc:endc,1:nlevdecomp_full)); this%harvest_c_to_litr_lig_c_col  (:,:)=nan
    allocate(this%harvest_c_to_cwdc_col             (begc:endc,1:nlevdecomp_full)); this%harvest_c_to_cwdc_col        (:,:)=nan

    allocate(this%dwt_slash_cflux_col               (begc:endc))                  ; this%dwt_slash_cflux_col (:) =nan
    allocate(this%dwt_frootc_to_litr_met_c_col      (begc:endc,1:nlevdecomp_full)); this%dwt_frootc_to_litr_met_c_col (:,:)=nan
    allocate(this%dwt_frootc_to_litr_cel_c_col      (begc:endc,1:nlevdecomp_full)); this%dwt_frootc_to_litr_cel_c_col (:,:)=nan
    allocate(this%dwt_frootc_to_litr_lig_c_col      (begc:endc,1:nlevdecomp_full)); this%dwt_frootc_to_litr_lig_c_col (:,:)=nan
    allocate(this%dwt_livecrootc_to_cwdc_col        (begc:endc,1:nlevdecomp_full)); this%dwt_livecrootc_to_cwdc_col   (:,:)=nan
    allocate(this%dwt_deadcrootc_to_cwdc_col        (begc:endc,1:nlevdecomp_full)); this%dwt_deadcrootc_to_cwdc_col   (:,:)=nan

    allocate(this%dwt_seedc_to_leaf_patch           (begp:endp))                  ; this%dwt_seedc_to_leaf_patch   (:)  =nan
    allocate(this%dwt_seedc_to_leaf_grc             (begg:endg))                  ; this%dwt_seedc_to_leaf_grc     (:)  =nan
    allocate(this%dwt_seedc_to_deadstem_patch       (begp:endp))                  ; this%dwt_seedc_to_deadstem_patch(:)  =nan
    allocate(this%dwt_seedc_to_deadstem_grc         (begg:endg))                  ; this%dwt_seedc_to_deadstem_grc (:)  =nan
    allocate(this%dwt_conv_cflux_patch              (begp:endp))                  ; this%dwt_conv_cflux_patch      (:)  =nan
    allocate(this%dwt_conv_cflux_grc                (begg:endg))                  ; this%dwt_conv_cflux_grc        (:)  =nan
    allocate(this%dwt_conv_cflux_dribbled_grc       (begg:endg))                  ; this%dwt_conv_cflux_dribbled_grc(:)  =nan
    allocate(this%dwt_wood_productc_gain_patch      (begp:endp))                  ; this%dwt_wood_productc_gain_patch(:)  =nan
    allocate(this%dwt_crop_productc_gain_patch      (begp:endp))                  ; this%dwt_crop_productc_gain_patch(:) =nan

    allocate(this%crop_seedc_to_leaf_patch          (begp:endp))                  ; this%crop_seedc_to_leaf_patch  (:)  =nan

    allocate(this%cwdc_hr_col                       (begc:endc))                  ; this%cwdc_hr_col               (:)  =nan
    allocate(this%cwdc_loss_col                     (begc:endc))                  ; this%cwdc_loss_col             (:)  =nan
    allocate(this%litterc_loss_col                  (begc:endc))                  ; this%litterc_loss_col          (:)  =nan

    allocate(this%grainc_to_cropprodc_patch(begp:endp))
    this%grainc_to_cropprodc_patch(:) = nan

    allocate(this%grainc_to_cropprodc_col(begc:endc))
    this%grainc_to_cropprodc_col(:) = nan

    allocate(this%m_decomp_cpools_to_fire_vr_col(begc:endc,1:nlevdecomp_full,1:ndecomp_pools))                
    this%m_decomp_cpools_to_fire_vr_col(:,:,:)= nan

    allocate(this%m_decomp_cpools_to_fire_col(begc:endc,1:ndecomp_pools))                                     
    this%m_decomp_cpools_to_fire_col(:,:)= nan

    allocate(this%m_decomp_cpools_to_fire_vr_col(begc:endc,1:nlevdecomp_full,1:ndecomp_pools))                
    this%m_decomp_cpools_to_fire_vr_col(:,:,:)= nan

    allocate(this%m_decomp_cpools_to_fire_col(begc:endc,1:ndecomp_pools))                                     
    this%m_decomp_cpools_to_fire_col(:,:)= nan

    allocate(this%rr_patch                (begp:endp)) ; this%rr_patch                (:) = nan
    allocate(this%mr_patch                (begp:endp)) ; this%mr_patch                (:) = nan
    allocate(this%gr_patch                (begp:endp)) ; this%gr_patch                (:) = nan
    allocate(this%ar_patch                (begp:endp)) ; this%ar_patch                (:) = nan
    allocate(this%npp_patch               (begp:endp)) ; this%npp_patch               (:) = nan
    allocate(this%agnpp_patch             (begp:endp)) ; this%agnpp_patch             (:) = nan
    allocate(this%bgnpp_patch             (begp:endp)) ; this%bgnpp_patch             (:) = nan
    allocate(this%litfall_patch           (begp:endp)) ; this%litfall_patch           (:) = nan
    allocate(this%wood_harvestc_patch     (begp:endp)) ; this%wood_harvestc_patch     (:) = nan
    allocate(this%slash_harvestc_patch    (begp:endp)) ; this%slash_harvestc_patch    (:) = nan
    allocate(this%cinputs_patch           (begp:endp)) ; this%cinputs_patch           (:) = nan
    allocate(this%coutputs_patch          (begp:endp)) ; this%coutputs_patch          (:) = nan
    allocate(this%gpp_patch               (begp:endp)) ; this%gpp_patch               (:) = nan
    allocate(this%fire_closs_patch        (begp:endp)) ; this%fire_closs_patch        (:) = nan
    allocate(this%sr_col                  (begc:endc)) ; this%sr_col                  (:) = nan
    allocate(this%er_col                  (begc:endc)) ; this%er_col                  (:) = nan
    allocate(this%litfire_col             (begc:endc)) ; this%litfire_col             (:) = nan
    allocate(this%somfire_col             (begc:endc)) ; this%somfire_col             (:) = nan
    allocate(this%totfire_col             (begc:endc)) ; this%totfire_col             (:) = nan
    allocate(this%rr_col                  (begc:endc)) ; this%rr_col                  (:) = nan
    allocate(this%ar_col                  (begc:endc)) ; this%ar_col                  (:) = nan
    allocate(this%gpp_col                 (begc:endc)) ; this%gpp_col                 (:) = nan
    allocate(this%npp_col                 (begc:endc)) ; this%npp_col                 (:) = nan
    allocate(this%fire_closs_p2c_col      (begc:endc)) ; this%fire_closs_p2c_col      (:) = nan
    allocate(this%fire_closs_col          (begc:endc)) ; this%fire_closs_col          (:) = nan
    allocate(this%wood_harvestc_col       (begc:endc)) ; this%wood_harvestc_col       (:) = nan
    allocate(this%hrv_xsmrpool_to_atm_col (begc:endc)) ; this%hrv_xsmrpool_to_atm_col (:) = 0.0_r8
    allocate(this%tempsum_npp_patch       (begp:endp)) ; this%tempsum_npp_patch       (:) = nan
    allocate(this%annsum_npp_patch        (begp:endp)) ; this%annsum_npp_patch        (:) = nan
    allocate(this%tempsum_litfall_patch   (begp:endp)) ; this%tempsum_litfall_patch   (:) = nan
    allocate(this%annsum_litfall_patch    (begp:endp)) ; this%annsum_litfall_patch    (:) = nan
    allocate(this%annsum_npp_col          (begc:endc)) ; this%annsum_npp_col          (:) = nan
    allocate(this%lag_npp_col             (begc:endc)) ; this%lag_npp_col             (:) = spval

    allocate(this%nep_col                 (begc:endc)) ; this%nep_col                 (:) = nan
    allocate(this%nbp_grc                 (begg:endg)) ; this%nbp_grc                 (:) = nan
    allocate(this%nee_grc                 (begg:endg)) ; this%nee_grc                 (:) = nan
    allocate(this%landuseflux_grc         (begg:endg)) ; this%landuseflux_grc         (:) = nan
    allocate(this%npp_Nactive_patch       (begp:endp)) ; this%npp_Nactive_patch       (:) = nan
    allocate(this%npp_burnedoff_patch     (begp:endp)) ; this%npp_burnedoff_patch     (:) = nan
    allocate(this%npp_Nnonmyc_patch       (begp:endp)) ; this%npp_Nnonmyc_patch       (:) = nan
    allocate(this%npp_Nam_patch           (begp:endp)) ; this%npp_Nam_patch           (:) = nan
    allocate(this%npp_Necm_patch          (begp:endp)) ; this%npp_Necm_patch          (:) = nan
    allocate(this%npp_Nactive_no3_patch   (begp:endp)) ; this%npp_Nactive_no3_patch   (:) = nan
    allocate(this%npp_Nactive_nh4_patch   (begp:endp)) ; this%npp_Nactive_nh4_patch   (:) = nan
    allocate(this%npp_Nnonmyc_no3_patch   (begp:endp)) ; this%npp_Nnonmyc_no3_patch   (:) = nan
    allocate(this%npp_Nnonmyc_nh4_patch   (begp:endp)) ; this%npp_Nnonmyc_nh4_patch   (:) = nan
    allocate(this%npp_Nam_no3_patch       (begp:endp)) ; this%npp_Nam_no3_patch       (:) = nan
    allocate(this%npp_Nam_nh4_patch       (begp:endp)) ; this%npp_Nam_nh4_patch       (:) = nan
    allocate(this%npp_Necm_no3_patch      (begp:endp)) ; this%npp_Necm_no3_patch      (:) = nan
    allocate(this%npp_Necm_nh4_patch      (begp:endp)) ; this%npp_Necm_nh4_patch      (:) = nan
    allocate(this%npp_Nfix_patch          (begp:endp)) ; this%npp_Nfix_patch          (:) = nan
    allocate(this%npp_Nretrans_patch      (begp:endp)) ; this%npp_Nretrans_patch      (:) = nan
    allocate(this%npp_Nuptake_patch       (begp:endp)) ; this%npp_Nuptake_patch       (:) = nan
    allocate(this%npp_growth_patch       (begp:endp)) ; this%npp_growth_patch       (:) = nan
    allocate(this%leafc_change_patch      (begp:endp)) ; this%leafc_change_patch      (:) = nan
    allocate(this%soilc_change_patch      (begp:endp)) ; this%soilc_change_patch      (:) = nan

    ! Construct restart field names consistently to what is done in SpeciesNonIsotope &
    ! SpeciesIsotope, to aid future migration to that infrastructure
    if (carbon_type == 'c12') then
       carbon_type_suffix = 'c'
    else if (carbon_type == 'c13') then
       carbon_type_suffix = 'c_13'
    else if (carbon_type == 'c14') then
       carbon_type_suffix = 'c_14'
    else
       write(iulog,*) 'CNVegCarbonFluxType InitAllocate: Unknown carbon_type: ', trim(carbon_type)
       call endrun(msg='CNVegCarbonFluxType InitAllocate: Unknown carbon_type: ' // &
            errMsg(sourcefile, __LINE__))
    end if

    ! Note that, for both of these dribblers, we set allows_non_annual_delta to false
    ! because we expect both land cover change and harvest to be applied entirely at the
    ! start of the year, and want to be notified if this changes. If this behavior is
    ! changed intentionally, then this setting of allows_non_annual_delta to .false. can
    ! safely be removed.
    !
    ! However, we do keep allows_non_annual_delta = .true. for the dwt_conv_cflux_dribbler if
    ! running with CNDV, because (in contrast with other land cover change) CNDV currently
    ! still interpolates land cover change throughout the year.
    if (get_for_testing_allow_non_annual_changes()) then
       allows_non_annual_delta = .true.
    else if (use_cndv) then
       allows_non_annual_delta = .true.
    else
       allows_non_annual_delta = .false.
    end if
    this%dwt_conv_cflux_dribbler = annual_flux_dribbler_gridcell( &
         bounds = bounds, &
         name = 'dwt_conv_flux_' // carbon_type_suffix, &
         units = 'gC/m^2', &
         allows_non_annual_delta = allows_non_annual_delta)
    this%hrv_xsmrpool_to_atm_dribbler = annual_flux_dribbler_gridcell( &
         bounds = bounds, &
         name = 'hrv_xsmrpool_to_atm_' // carbon_type_suffix, &
         units = 'gC/m^2', &
         allows_non_annual_delta = .false.)

  end subroutine InitAllocate

  !------------------------------------------------------------------------
  subroutine InitHistory(this, bounds, carbon_type)
    !
    ! !DESCRIPTION:
    ! add history fields for all CN variables, always set as default='inactive'
    !
    ! !USES:
    use clm_varpar , only : nlevdecomp, nlevdecomp_full, nlevgrnd
    use clm_varctl , only : hist_wrtch4diag
    use CNSharedParamsMod, only: use_fun
    use histFileMod, only : hist_addfld1d, hist_addfld2d, hist_addfld_decomp 
    !
    ! !ARGUMENTS:
    class(cnveg_carbonflux_type) :: this    
    type(bounds_type)         , intent(in) :: bounds 
    character(len=3)          , intent(in) :: carbon_type ! one of ['c12', c13','c14']
    !
    ! !LOCAL VARIABLES:
    integer           :: k,l,ii,jj 
    character(8)      :: vr_suffix
    character(10)     :: active
    integer           :: begp,endp
    integer           :: begc,endc
    integer           :: begg,endg
    character(24)     :: fieldname
    character(100)    :: longname
    real(r8), pointer :: data1dptr(:)   ! temp. pointer for slicing larger arrays
    real(r8), pointer :: data2dptr(:,:) ! temp. pointer for slicing larger arrays
    !---------------------------------------------------------------------

    begp = bounds%begp; endp = bounds%endp
    begc = bounds%begc; endc = bounds%endc
    begg = bounds%begg; endg = bounds%endg

    if (nlevdecomp > 1) then
       vr_suffix = "_vr"
    else 
       vr_suffix = ""
    endif

    !-------------------------------
    ! C flux variables - patch
    !-------------------------------

    if (carbon_type == 'c12') then

       if (use_crop) then
          this%grainc_to_food_patch(begp:endp) = spval
          call hist_addfld1d (fname='GRAINC_TO_FOOD', units='gC/m^2/s', &
               avgflag='A', long_name='grain C to food', &
               ptr_patch=this%grainc_to_food_patch)

          this%grainc_to_seed_patch(begp:endp) = spval
          call hist_addfld1d (fname='GRAINC_TO_SEED', units='gC/m^2/s', &
               avgflag='A', long_name='grain C to seed', &
               ptr_patch=this%grainc_to_seed_patch)
       end if

       this%litterc_loss_col(begc:endc) = spval
       call hist_addfld1d (fname='LITTERC_LOSS', units='gC/m^2/s', &
            avgflag='A', long_name='litter C loss', &
            ptr_col=this%litterc_loss_col)

       this%woodc_alloc_patch(begp:endp) = spval
       call hist_addfld1d (fname='WOODC_ALLOC', units='gC/m^2/s', &
            avgflag='A', long_name='wood C eallocation', &
            ptr_patch=this%woodc_alloc_patch)

       this%woodc_loss_patch(begp:endp) = spval
       call hist_addfld1d (fname='WOODC_LOSS', units='gC/m^2/s', &
            avgflag='A', long_name='wood C loss', &
            ptr_patch=this%woodc_loss_patch)

       this%leafc_loss_patch(begp:endp) = spval
       call hist_addfld1d (fname='LEAFC_LOSS', units='gC/m^2/s', &
            avgflag='A', long_name='leaf C loss', &
            ptr_patch=this%leafc_loss_patch)

       this%leafc_alloc_patch(begp:endp) = spval
       call hist_addfld1d (fname='LEAFC_ALLOC', units='gC/m^2/s', &
            avgflag='A', long_name='leaf C allocation', &
            ptr_patch=this%leafc_alloc_patch)

       this%frootc_loss_patch(begp:endp) = spval
       call hist_addfld1d (fname='FROOTC_LOSS', units='gC/m^2/s', &
            avgflag='A', long_name='fine root C loss', &
            ptr_patch=this%frootc_loss_patch)

       this%frootc_alloc_patch(begp:endp) = spval
       call hist_addfld1d (fname='FROOTC_ALLOC', units='gC/m^2/s', &
            avgflag='A', long_name='fine root C allocation', &
            ptr_patch=this%frootc_alloc_patch)

       this%m_leafc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LEAFC_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='leaf C mortality', &
            ptr_patch=this%m_leafc_to_litter_patch, default='inactive')

       this%m_frootc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_FROOTC_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='fine root C mortality', &
            ptr_patch=this%m_frootc_to_litter_patch, default='inactive')

       this%m_leafc_storage_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LEAFC_STORAGE_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='leaf C storage mortality', &
            ptr_patch=this%m_leafc_storage_to_litter_patch, default='inactive')

       this%m_frootc_storage_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_FROOTC_STORAGE_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='fine root C storage mortality', &
            ptr_patch=this%m_frootc_storage_to_litter_patch, default='inactive')

       this%m_livestemc_storage_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LIVESTEMC_STORAGE_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='live stem C storage mortality', &
            ptr_patch=this%m_livestemc_storage_to_litter_patch, default='inactive')

       this%m_deadstemc_storage_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_DEADSTEMC_STORAGE_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='dead stem C storage mortality', &
            ptr_patch=this%m_deadstemc_storage_to_litter_patch, default='inactive')

       this%m_livecrootc_storage_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LIVECROOTC_STORAGE_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='live coarse root C storage mortality', &
            ptr_patch=this%m_livecrootc_storage_to_litter_patch, default='inactive')

       this%m_deadcrootc_storage_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_DEADCROOTC_STORAGE_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='dead coarse root C storage mortality', &
            ptr_patch=this%m_deadcrootc_storage_to_litter_patch, default='inactive')

       this%m_leafc_xfer_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LEAFC_XFER_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='leaf C transfer mortality', &
            ptr_patch=this%m_leafc_xfer_to_litter_patch, default='inactive')

       this%m_frootc_xfer_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_FROOTC_XFER_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='fine root C transfer mortality', &
            ptr_patch=this%m_frootc_xfer_to_litter_patch, default='inactive')

       this%m_livestemc_xfer_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LIVESTEMC_XFER_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='live stem C transfer mortality', &
            ptr_patch=this%m_livestemc_xfer_to_litter_patch, default='inactive')

       this%m_deadstemc_xfer_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_DEADSTEMC_XFER_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='dead stem C transfer mortality', &
            ptr_patch=this%m_deadstemc_xfer_to_litter_patch, default='inactive')

       this%m_livecrootc_xfer_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LIVECROOTC_XFER_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='live coarse root C transfer mortality', &
            ptr_patch=this%m_livecrootc_xfer_to_litter_patch, default='inactive')

       this%m_deadcrootc_xfer_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_DEADCROOTC_XFER_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='dead coarse root C transfer mortality', &
            ptr_patch=this%m_deadcrootc_xfer_to_litter_patch, default='inactive')

       this%m_livestemc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LIVESTEMC_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='live stem C mortality', &
            ptr_patch=this%m_livestemc_to_litter_patch, default='inactive')

       this%m_deadstemc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_DEADSTEMC_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='dead stem C mortality', &
            ptr_patch=this%m_deadstemc_to_litter_patch, default='inactive')

       this%m_livecrootc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LIVECROOTC_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='live coarse root C mortality', &
            ptr_patch=this%m_livecrootc_to_litter_patch, default='inactive')

       this%m_deadcrootc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_DEADCROOTC_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='dead coarse root C mortality', &
            ptr_patch=this%m_deadcrootc_to_litter_patch, default='inactive')

       this%m_gresp_storage_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_GRESP_STORAGE_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='growth respiration storage mortality', &
            ptr_patch=this%m_gresp_storage_to_litter_patch, default='inactive')

       this%m_gresp_xfer_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_GRESP_XFER_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='growth respiration transfer mortality', &
            ptr_patch=this%m_gresp_xfer_to_litter_patch, default='inactive')

       this%m_leafc_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LEAFC_TO_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='leaf C fire loss', &
            ptr_patch=this%m_leafc_to_fire_patch, default='inactive')

       this%m_leafc_storage_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LEAFC_STORAGE_TO_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='leaf C storage fire loss', &
            ptr_patch=this%m_leafc_storage_to_fire_patch, default='inactive')

       this%m_leafc_xfer_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LEAFC_XFER_TO_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='leaf C transfer fire loss', &
            ptr_patch=this%m_leafc_xfer_to_fire_patch, default='inactive')

       this%m_livestemc_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LIVESTEMC_TO_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='live stem C fire loss', &
            ptr_patch=this%m_livestemc_to_fire_patch, default='inactive')

       this%m_livestemc_storage_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LIVESTEMC_STORAGE_TO_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='live stem C storage fire loss', &
            ptr_patch=this%m_livestemc_storage_to_fire_patch, default='inactive')

       this%m_livestemc_xfer_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LIVESTEMC_XFER_TO_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='live stem C transfer fire loss', &
            ptr_patch=this%m_livestemc_xfer_to_fire_patch, default='inactive')

       this%m_deadstemc_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_DEADSTEMC_TO_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='dead stem C fire loss', &
            ptr_patch=this%m_deadstemc_to_fire_patch, default='inactive')

       this%m_deadstemc_storage_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_DEADSTEMC_STORAGE_TO_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='dead stem C storage fire loss', &
            ptr_patch=this%m_deadstemc_storage_to_fire_patch, default='inactive')

       this%m_deadstemc_xfer_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_DEADSTEMC_XFER_TO_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='dead stem C transfer fire loss', &
            ptr_patch=this%m_deadstemc_xfer_to_fire_patch, default='inactive')

       this%m_frootc_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_FROOTC_TO_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='fine root C fire loss', &
            ptr_patch=this%m_frootc_to_fire_patch, default='inactive')

       this%m_frootc_storage_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_FROOTC_STORAGE_TO_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='fine root C storage fire loss', &
            ptr_patch=this%m_frootc_storage_to_fire_patch, default='inactive')

       this%m_frootc_xfer_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_FROOTC_XFER_TO_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='fine root C transfer fire loss', &
            ptr_patch=this%m_frootc_xfer_to_fire_patch, default='inactive')

       this%m_livecrootc_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LIVEROOTC_TO_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='live root C fire loss', &
            ptr_patch=this%m_livecrootc_to_fire_patch, default='inactive')

       this%m_livecrootc_storage_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LIVEROOTC_STORAGE_TO_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='live root C storage fire loss', &
            ptr_patch=this%m_livecrootc_storage_to_fire_patch, default='inactive')

       this%m_livecrootc_xfer_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LIVEROOTC_XFER_TO_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='live root C transfer fire loss', &
            ptr_patch=this%m_livecrootc_xfer_to_fire_patch, default='inactive')

       this%m_deadcrootc_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_DEADROOTC_TO_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='dead root C fire loss', &
            ptr_patch=this%m_deadcrootc_to_fire_patch, default='inactive')

       this%m_deadcrootc_storage_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_DEADROOTC_STORAGE_TO_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='dead root C storage fire loss', &
            ptr_patch=this%m_deadcrootc_storage_to_fire_patch, default='inactive')

       this%m_deadcrootc_xfer_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_DEADROOTC_XFER_TO_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='dead root C transfer fire loss', &
            ptr_patch=this%m_deadcrootc_xfer_to_fire_patch, default='inactive')

       this%m_gresp_storage_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_GRESP_STORAGE_TO_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='growth respiration storage fire loss', &
            ptr_patch=this%m_gresp_storage_to_fire_patch, default='inactive')

       this%m_gresp_xfer_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_GRESP_XFER_TO_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='growth respiration transfer fire loss', &
            ptr_patch=this%m_gresp_xfer_to_fire_patch, default='inactive')

       this%m_leafc_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LEAFC_TO_LITTER_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='leaf C fire mortality to litter', &
            ptr_patch=this%m_leafc_to_litter_fire_patch, default='inactive')

       ! add by F. Li and S. Levis
       this%m_leafc_storage_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LEAFC_STORAGE_TO_LITTER_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='leaf C fire mortality to litter', &
            ptr_patch=this%m_leafc_storage_to_litter_fire_patch, default='inactive')

       this%m_leafc_xfer_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LEAFC_XFER_TO_LITTER_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='leaf C transfer fire mortality to litter', &
            ptr_patch=this%m_leafc_xfer_to_litter_fire_patch, default='inactive')

       this%m_livestemc_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LIVESTEMC_TO_LITTER_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='live stem C fire mortality to litter', &
            ptr_patch=this%m_livestemc_to_litter_fire_patch, default='inactive')

       this%m_livestemc_storage_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LIVESTEMC_STORAGE_TO_LITTER_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='live stem C storage fire mortality to litter', &
            ptr_patch=this%m_livestemc_storage_to_litter_fire_patch, default='inactive')

       this%m_livestemc_xfer_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LIVESTEMC_XFER_TO_LITTER_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='live stem C transfer fire mortality to litter', &
            ptr_patch=this%m_livestemc_xfer_to_litter_fire_patch, default='inactive')

       this%m_livestemc_to_deadstemc_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LIVESTEMC_TO_DEADSTEMC_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='live stem C fire mortality to dead stem C', &
            ptr_patch=this%m_livestemc_to_deadstemc_fire_patch, default='inactive')

       this%m_deadstemc_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_DEADSTEMC_TO_LITTER_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='dead stem C fire mortality to litter', &
            ptr_patch=this%m_deadstemc_to_litter_fire_patch, default='inactive')

       this%m_deadstemc_storage_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_DEADSTEMC_STORAGE_TO_LITTER_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='dead stem C storage fire mortality to litter', &
            ptr_patch=this%m_deadstemc_storage_to_litter_fire_patch, default='inactive')

       this%m_deadstemc_xfer_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_DEADSTEMC_XFER_TO_LITTER_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='dead stem C transfer fire mortality to litter', &
            ptr_patch=this%m_deadstemc_xfer_to_litter_fire_patch, default='inactive')

       this%m_frootc_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_FROOTC_TO_LITTER_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='fine root C fire mortality to litter', &
            ptr_patch=this%m_frootc_to_litter_fire_patch, default='inactive')

       this%m_frootc_storage_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_FROOTC_STORAGE_TO_LITTER_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='fine root C storage fire mortality to litter', &
            ptr_patch=this%m_frootc_storage_to_litter_fire_patch, default='inactive')

       this%m_frootc_xfer_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_FROOTC_XFER_TO_LITTER_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='fine root C transfer fire mortality to litter', &
            ptr_patch=this%m_frootc_xfer_to_litter_fire_patch, default='inactive')

       this%m_livecrootc_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LIVEROOTC_TO_LITTER_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='live root C fire mortality to litter', &
            ptr_patch=this%m_livecrootc_to_litter_fire_patch, default='inactive')

       this%m_livecrootc_storage_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LIVEROOTC_STORAGE_TO_LITTER_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='live root C storage fire mortality to litter', &
            ptr_patch=this%m_livecrootc_storage_to_litter_fire_patch, default='inactive')

       this%m_livecrootc_xfer_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LIVEROOTC_XFER_TO_LITTER_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='live root C transfer fire mortality to litter', &
            ptr_patch=this%m_livecrootc_xfer_to_litter_fire_patch, default='inactive')

       this%m_livecrootc_to_deadcrootc_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LIVEROOTC_TO_DEADROOTC_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='live root C fire mortality to dead root C', &
            ptr_patch=this%m_livecrootc_to_deadcrootc_fire_patch, default='inactive')


       this%m_deadcrootc_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_DEADROOTC_TO_LITTER_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='dead root C fire mortality to litter', &
            ptr_patch=this%m_deadcrootc_to_litter_fire_patch, default='inactive')

       this%m_deadcrootc_storage_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_DEADROOTC_STORAGE_TO_LITTER_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='dead root C storage fire mortality to litter', &
            ptr_patch=this%m_deadcrootc_storage_to_litter_fire_patch, default='inactive')

       this%m_deadcrootc_xfer_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_DEADROOTC_XFER_TO_LITTER_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='dead root C transfer fire mortality to litter', &
            ptr_patch=this%m_deadcrootc_xfer_to_litter_fire_patch, default='inactive')

       this%m_livecrootc_storage_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_LIVECROOTC_STORAGE_TO_LITTER_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='live coarse root C fire mortality to litter', &
            ptr_patch=this%m_livecrootc_storage_to_litter_fire_patch, default='inactive')

       this%m_deadcrootc_storage_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_DEADCROOTC_STORAGE_TO_LITTER_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='dead coarse root C storage fire mortality to litter', &
            ptr_patch=this%m_deadcrootc_storage_to_litter_fire_patch,  default='inactive')

       this%m_gresp_storage_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_GRESP_STORAGE_TO_LITTER_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='growth respiration storage fire mortality to litter', &
            ptr_patch=this%m_gresp_storage_to_litter_fire_patch, default='inactive')

       this%m_gresp_xfer_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='M_GRESP_XFER_TO_LITTER_FIRE', units='gC/m^2/s', &
            avgflag='A', long_name='growth respiration transfer fire mortality to litter', &
            ptr_patch=this%m_gresp_xfer_to_litter_fire_patch, default='inactive')   

       this%leafc_xfer_to_leafc_patch(begp:endp) = spval
       call hist_addfld1d (fname='LEAFC_XFER_TO_LEAFC', units='gC/m^2/s', &
            avgflag='A', long_name='leaf C growth from storage', &
            ptr_patch=this%leafc_xfer_to_leafc_patch, default='inactive')

       this%frootc_xfer_to_frootc_patch(begp:endp) = spval
       call hist_addfld1d (fname='FROOTC_XFER_TO_FROOTC', units='gC/m^2/s', &
            avgflag='A', long_name='fine root C growth from storage', &
            ptr_patch=this%frootc_xfer_to_frootc_patch, default='inactive')

       this%livestemc_xfer_to_livestemc_patch(begp:endp) = spval
       call hist_addfld1d (fname='LIVESTEMC_XFER_TO_LIVESTEMC', units='gC/m^2/s', &
            avgflag='A', long_name='live stem C growth from storage', &
            ptr_patch=this%livestemc_xfer_to_livestemc_patch, default='inactive')

       this%deadstemc_xfer_to_deadstemc_patch(begp:endp) = spval
       call hist_addfld1d (fname='DEADSTEMC_XFER_TO_DEADSTEMC', units='gC/m^2/s', &
            avgflag='A', long_name='dead stem C growth from storage', &
            ptr_patch=this%deadstemc_xfer_to_deadstemc_patch, default='inactive')

       this%livecrootc_xfer_to_livecrootc_patch(begp:endp) = spval
       call hist_addfld1d (fname='LIVECROOTC_XFER_TO_LIVECROOTC', units='gC/m^2/s', &
            avgflag='A', long_name='live coarse root C growth from storage', &
            ptr_patch=this%livecrootc_xfer_to_livecrootc_patch, default='inactive')

       this%deadcrootc_xfer_to_deadcrootc_patch(begp:endp) = spval
       call hist_addfld1d (fname='DEADCROOTC_XFER_TO_DEADCROOTC', units='gC/m^2/s', &
            avgflag='A', long_name='dead coarse root C growth from storage', &
            ptr_patch=this%deadcrootc_xfer_to_deadcrootc_patch, default='inactive')

       this%leafc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='LEAFC_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='leaf C litterfall', &
            ptr_patch=this%leafc_to_litter_patch, default='inactive')

       if ( use_fun ) then
          this%leafc_to_litter_fun_patch(begp:endp) = spval
          call hist_addfld1d (fname='LEAFC_TO_LITTER_FUN', units='gC/m^2/s', &
               avgflag='A', long_name='leaf C litterfall used by FUN', &
               ptr_patch=this%leafc_to_litter_fun_patch)
       end if

       this%frootc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='FROOTC_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='fine root C litterfall', &
            ptr_patch=this%frootc_to_litter_patch, default='inactive')
            
       this%cpool_to_resp_patch(begp:endp) = spval
       call hist_addfld1d (fname='EXCESSC_MR', units='gC/m^2/s', &
            avgflag='A', long_name='excess C maintenance respiration', &
            ptr_patch=this%cpool_to_resp_patch, default='inactive')
       this%leaf_mr_patch(begp:endp) = spval
       call hist_addfld1d (fname='LEAF_MR', units='gC/m^2/s', &
            avgflag='A', long_name='leaf maintenance respiration', &
            ptr_patch=this%leaf_mr_patch)

       this%froot_mr_patch(begp:endp) = spval
       call hist_addfld1d (fname='FROOT_MR', units='gC/m^2/s', &
            avgflag='A', long_name='fine root maintenance respiration', &
            ptr_patch=this%froot_mr_patch, default='inactive')

       this%livestem_mr_patch(begp:endp) = spval
       call hist_addfld1d (fname='LIVESTEM_MR', units='gC/m^2/s', &
            avgflag='A', long_name='live stem maintenance respiration', &
            ptr_patch=this%livestem_mr_patch, default='inactive')

       this%livecroot_mr_patch(begp:endp) = spval
       call hist_addfld1d (fname='LIVECROOT_MR', units='gC/m^2/s', &
            avgflag='A', long_name='live coarse root maintenance respiration', &
            ptr_patch=this%livecroot_mr_patch, default='inactive')

       this%psnsun_to_cpool_patch(begp:endp) = spval
       call hist_addfld1d (fname='PSNSUN_TO_CPOOL', units='gC/m^2/s', &
            avgflag='A', long_name='C fixation from sunlit canopy', &
            ptr_patch=this%psnsun_to_cpool_patch)

       this%psnshade_to_cpool_patch(begp:endp) = spval
       call hist_addfld1d (fname='PSNSHADE_TO_CPOOL', units='gC/m^2/s', &
            avgflag='A', long_name='C fixation from shaded canopy', &
            ptr_patch=this%psnshade_to_cpool_patch)

       this%cpool_to_leafc_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_TO_LEAFC', units='gC/m^2/s', &
            avgflag='A', long_name='allocation to leaf C', &
            ptr_patch=this%cpool_to_leafc_patch, default='inactive')

       this%cpool_to_leafc_storage_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_TO_LEAFC_STORAGE', units='gC/m^2/s', &
            avgflag='A', long_name='allocation to leaf C storage', &
            ptr_patch=this%cpool_to_leafc_storage_patch, default='inactive')

       this%cpool_to_frootc_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_TO_FROOTC', units='gC/m^2/s', &
            avgflag='A', long_name='allocation to fine root C', &
            ptr_patch=this%cpool_to_frootc_patch, default='inactive')

       this%cpool_to_frootc_storage_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_TO_FROOTC_STORAGE', units='gC/m^2/s', &
            avgflag='A', long_name='allocation to fine root C storage', &
            ptr_patch=this%cpool_to_frootc_storage_patch, default='inactive')

       this%cpool_to_livestemc_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_TO_LIVESTEMC', units='gC/m^2/s', &
            avgflag='A', long_name='allocation to live stem C', &
            ptr_patch=this%cpool_to_livestemc_patch, default='inactive')

       this%cpool_to_livestemc_storage_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_TO_LIVESTEMC_STORAGE', units='gC/m^2/s', &
            avgflag='A', long_name='allocation to live stem C storage', &
            ptr_patch=this%cpool_to_livestemc_storage_patch, default='inactive')

       this%cpool_to_deadstemc_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_TO_DEADSTEMC', units='gC/m^2/s', &
            avgflag='A', long_name='allocation to dead stem C', &
            ptr_patch=this%cpool_to_deadstemc_patch, default='inactive')

       this%cpool_to_deadstemc_storage_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_TO_DEADSTEMC_STORAGE', units='gC/m^2/s', &
            avgflag='A', long_name='allocation to dead stem C storage', &
            ptr_patch=this%cpool_to_deadstemc_storage_patch, default='inactive')

       this%cpool_to_livecrootc_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_TO_LIVECROOTC', units='gC/m^2/s', &
            avgflag='A', long_name='allocation to live coarse root C', &
            ptr_patch=this%cpool_to_livecrootc_patch, default='inactive')

       this%cpool_to_livecrootc_storage_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_TO_LIVECROOTC_STORAGE', units='gC/m^2/s', &
            avgflag='A', long_name='allocation to live coarse root C storage', &
            ptr_patch=this%cpool_to_livecrootc_storage_patch, default='inactive')

       this%cpool_to_deadcrootc_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_TO_DEADCROOTC', units='gC/m^2/s', &
            avgflag='A', long_name='allocation to dead coarse root C', &
            ptr_patch=this%cpool_to_deadcrootc_patch, default='inactive')

       this%cpool_to_deadcrootc_storage_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_TO_DEADCROOTC_STORAGE', units='gC/m^2/s', &
            avgflag='A', long_name='allocation to dead coarse root C storage', &
            ptr_patch=this%cpool_to_deadcrootc_storage_patch, default='inactive')

       this%cpool_to_gresp_storage_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_TO_GRESP_STORAGE', units='gC/m^2/s', &
            avgflag='A', long_name='allocation to growth respiration storage', &
            ptr_patch=this%cpool_to_gresp_storage_patch, default='inactive')

       this%cpool_leaf_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_LEAF_GR', units='gC/m^2/s', &
            avgflag='A', long_name='leaf growth respiration', &
            ptr_patch=this%cpool_leaf_gr_patch, default='inactive')

       this%cpool_leaf_storage_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_LEAF_STORAGE_GR', units='gC/m^2/s', &
            avgflag='A', long_name='leaf growth respiration to storage', &
            ptr_patch=this%cpool_leaf_storage_gr_patch, default='inactive')

       this%transfer_leaf_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='TRANSFER_LEAF_GR', units='gC/m^2/s', &
            avgflag='A', long_name='leaf growth respiration from storage', &
            ptr_patch=this%transfer_leaf_gr_patch, default='inactive')

       this%cpool_froot_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_FROOT_GR', units='gC/m^2/s', &
            avgflag='A', long_name='fine root growth respiration', &
            ptr_patch=this%cpool_froot_gr_patch, default='inactive')

       this%cpool_froot_storage_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_FROOT_STORAGE_GR', units='gC/m^2/s', &
            avgflag='A', long_name='fine root  growth respiration to storage', &
            ptr_patch=this%cpool_froot_storage_gr_patch, default='inactive')

       this%transfer_froot_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='TRANSFER_FROOT_GR', units='gC/m^2/s', &
            avgflag='A', long_name='fine root  growth respiration from storage', &
            ptr_patch=this%transfer_froot_gr_patch, default='inactive')

       this%cpool_livestem_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_LIVESTEM_GR', units='gC/m^2/s', &
            avgflag='A', long_name='live stem growth respiration', &
            ptr_patch=this%cpool_livestem_gr_patch, default='inactive')

       this%cpool_livestem_storage_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_LIVESTEM_STORAGE_GR', units='gC/m^2/s', &
            avgflag='A', long_name='live stem growth respiration to storage', &
            ptr_patch=this%cpool_livestem_storage_gr_patch, default='inactive')

       this%transfer_livestem_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='TRANSFER_LIVESTEM_GR', units='gC/m^2/s', &
            avgflag='A', long_name='live stem growth respiration from storage', &
            ptr_patch=this%transfer_livestem_gr_patch, default='inactive')

       this%cpool_deadstem_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_DEADSTEM_GR', units='gC/m^2/s', &
            avgflag='A', long_name='dead stem growth respiration', &
            ptr_patch=this%cpool_deadstem_gr_patch, default='inactive')

       this%cpool_deadstem_storage_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_DEADSTEM_STORAGE_GR', units='gC/m^2/s', &
            avgflag='A', long_name='dead stem growth respiration to storage', &
            ptr_patch=this%cpool_deadstem_storage_gr_patch, default='inactive')

       this%transfer_deadstem_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='TRANSFER_DEADSTEM_GR', units='gC/m^2/s', &
            avgflag='A', long_name='dead stem growth respiration from storage', &
            ptr_patch=this%transfer_deadstem_gr_patch, default='inactive')

       this%cpool_livecroot_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_LIVECROOT_GR', units='gC/m^2/s', &
            avgflag='A', long_name='live coarse root growth respiration', &
            ptr_patch=this%cpool_livecroot_gr_patch, default='inactive')

       this%cpool_livecroot_storage_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_LIVECROOT_STORAGE_GR', units='gC/m^2/s', &
            avgflag='A', long_name='live coarse root growth respiration to storage', &
            ptr_patch=this%cpool_livecroot_storage_gr_patch, default='inactive')

       this%transfer_livecroot_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='TRANSFER_LIVECROOT_GR', units='gC/m^2/s', &
            avgflag='A', long_name='live coarse root growth respiration from storage', &
            ptr_patch=this%transfer_livecroot_gr_patch, default='inactive')

       this%cpool_deadcroot_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_DEADCROOT_GR', units='gC/m^2/s', &
            avgflag='A', long_name='dead coarse root growth respiration', &
            ptr_patch=this%cpool_deadcroot_gr_patch, default='inactive')

       this%cpool_deadcroot_storage_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='CPOOL_DEADCROOT_STORAGE_GR', units='gC/m^2/s', &
            avgflag='A', long_name='dead coarse root growth respiration to storage', &
            ptr_patch=this%cpool_deadcroot_storage_gr_patch, default='inactive')

       this%transfer_deadcroot_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='TRANSFER_DEADCROOT_GR', units='gC/m^2/s', &
            avgflag='A', long_name='dead coarse root growth respiration from storage', &
            ptr_patch=this%transfer_deadcroot_gr_patch, default='inactive')

       this%leafc_storage_to_xfer_patch(begp:endp) = spval
       call hist_addfld1d (fname='LEAFC_STORAGE_TO_XFER', units='gC/m^2/s', &
            avgflag='A', long_name='leaf C shift storage to transfer', &
            ptr_patch=this%leafc_storage_to_xfer_patch, default='inactive')

       this%frootc_storage_to_xfer_patch(begp:endp) = spval
       call hist_addfld1d (fname='FROOTC_STORAGE_TO_XFER', units='gC/m^2/s', &
            avgflag='A', long_name='fine root C shift storage to transfer', &
            ptr_patch=this%frootc_storage_to_xfer_patch, default='inactive')

       this%livestemc_storage_to_xfer_patch(begp:endp) = spval
       call hist_addfld1d (fname='LIVESTEMC_STORAGE_TO_XFER', units='gC/m^2/s', &
            avgflag='A', long_name='live stem C shift storage to transfer', &
            ptr_patch=this%livestemc_storage_to_xfer_patch, default='inactive')

       this%deadstemc_storage_to_xfer_patch(begp:endp) = spval
       call hist_addfld1d (fname='DEADSTEMC_STORAGE_TO_XFER', units='gC/m^2/s', &
            avgflag='A', long_name='dead stem C shift storage to transfer', &
            ptr_patch=this%deadstemc_storage_to_xfer_patch, default='inactive')

       this%livecrootc_storage_to_xfer_patch(begp:endp) = spval
       call hist_addfld1d (fname='LIVECROOTC_STORAGE_TO_XFER', units='gC/m^2/s', &
            avgflag='A', long_name='live coarse root C shift storage to transfer', &
            ptr_patch=this%livecrootc_storage_to_xfer_patch, default='inactive')

       this%deadcrootc_storage_to_xfer_patch(begp:endp) = spval
       call hist_addfld1d (fname='DEADCROOTC_STORAGE_TO_XFER', units='gC/m^2/s', &
            avgflag='A', long_name='dead coarse root C shift storage to transfer', &
            ptr_patch=this%deadcrootc_storage_to_xfer_patch, default='inactive')

       this%gresp_storage_to_xfer_patch(begp:endp) = spval
       call hist_addfld1d (fname='GRESP_STORAGE_TO_XFER', units='gC/m^2/s', &
            avgflag='A', long_name='growth respiration shift storage to transfer', &
            ptr_patch=this%gresp_storage_to_xfer_patch, default='inactive')

       this%livestemc_to_deadstemc_patch(begp:endp) = spval
       call hist_addfld1d (fname='LIVESTEMC_TO_DEADSTEMC', units='gC/m^2/s', &
            avgflag='A', long_name='live stem C turnover', &
            ptr_patch=this%livestemc_to_deadstemc_patch, default='inactive')

       this%livecrootc_to_deadcrootc_patch(begp:endp) = spval
       call hist_addfld1d (fname='LIVECROOTC_TO_DEADCROOTC', units='gC/m^2/s', &
            avgflag='A', long_name='live coarse root C turnover', &
            ptr_patch=this%livecrootc_to_deadcrootc_patch, default='inactive')

       this%gpp_before_downreg_patch(begp:endp) = spval
       call hist_addfld1d (fname='INIT_GPP', units='gC/m^2/s', &
            avgflag='A', long_name='GPP flux before downregulation', &
            ptr_patch=this%gpp_before_downreg_patch, default='inactive')

       this%current_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='CURRENT_GR', units='gC/m^2/s', &
            avgflag='A', long_name='growth resp for new growth displayed in this timestep', &
            ptr_patch=this%current_gr_patch, default='inactive')

       this%transfer_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='TRANSFER_GR', units='gC/m^2/s', &
            avgflag='A', long_name='growth resp for transfer growth displayed in this timestep', &
            ptr_patch=this%transfer_gr_patch, default='inactive')

       this%storage_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='STORAGE_GR', units='gC/m^2/s', &
            avgflag='A', long_name='growth resp for growth sent to storage for later display', &
            ptr_patch=this%storage_gr_patch, default='inactive')

       this%availc_patch(begp:endp) = spval
       call hist_addfld1d (fname='AVAILC', units='gC/m^2/s', &
            avgflag='A', long_name='C flux available for allocation', &
            ptr_patch=this%availc_patch, default='inactive')

       this%plant_calloc_patch(begp:endp) = spval
       call hist_addfld1d (fname='PLANT_CALLOC', units='gC/m^2/s', &
            avgflag='A', long_name='total allocated C flux', &
            ptr_patch=this%plant_calloc_patch, default='inactive')

       this%excess_cflux_patch(begp:endp) = spval
       call hist_addfld1d (fname='EXCESS_CFLUX', units='gC/m^2/s', &
            avgflag='A', long_name='C flux not allocated due to downregulation', &
            ptr_patch=this%excess_cflux_patch, default='inactive')

       this%prev_leafc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='PREV_LEAFC_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='previous timestep leaf C litterfall flux', &
            ptr_patch=this%prev_leafc_to_litter_patch, default='inactive')

       this%prev_frootc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='PREV_FROOTC_TO_LITTER', units='gC/m^2/s', &
            avgflag='A', long_name='previous timestep froot C litterfall flux', &
            ptr_patch=this%prev_frootc_to_litter_patch, default='inactive')

       this%xsmrpool_recover_patch(begp:endp) = spval
       call hist_addfld1d (fname='XSMRPOOL_RECOVER', units='gC/m^2/s', &
            avgflag='A', long_name='C flux assigned to recovery of negative xsmrpool', &
            ptr_patch=this%xsmrpool_recover_patch)

        this%gpp_patch(begp:endp) = spval
        call hist_addfld1d (fname='GPP', units='gC/m^2/s', &
             avgflag='A', long_name='gross primary production', &
             ptr_patch=this%gpp_patch)

        this%rr_patch(begp:endp) = spval
        call hist_addfld1d (fname='RR', units='gC/m^2/s', &
             avgflag='A', long_name='root respiration (fine root MR + total root GR)', &
             ptr_patch=this%rr_patch)

        this%mr_patch(begp:endp) = spval
        call hist_addfld1d (fname='MR', units='gC/m^2/s', &
             avgflag='A', long_name='maintenance respiration', &
             ptr_patch=this%mr_patch)

        this%gr_patch(begp:endp) = spval
        call hist_addfld1d (fname='GR', units='gC/m^2/s', &
             avgflag='A', long_name='total growth respiration', &
             ptr_patch=this%gr_patch)

        this%ar_patch(begp:endp) = spval
        call hist_addfld1d (fname='AR', units='gC/m^2/s', &
             avgflag='A', long_name='autotrophic respiration (MR + GR)', &
             ptr_patch=this%ar_patch)

        this%npp_patch(begp:endp) = spval
        call hist_addfld1d (fname='NPP', units='gC/m^2/s', &
             avgflag='A', long_name='net primary production', &
             ptr_patch=this%npp_patch)

        this%agnpp_patch(begp:endp) = spval
        call hist_addfld1d (fname='AGNPP', units='gC/m^2/s', &
             avgflag='A', long_name='aboveground NPP', &
             ptr_patch=this%agnpp_patch)

        this%bgnpp_patch(begp:endp) = spval
        call hist_addfld1d (fname='BGNPP', units='gC/m^2/s', &
             avgflag='A', long_name='belowground NPP', &
             ptr_patch=this%bgnpp_patch)

        this%litfall_patch(begp:endp) = spval
        call hist_addfld1d (fname='LITFALL', units='gC/m^2/s', &
             avgflag='A', long_name='litterfall (leaves and fine roots)', &
             ptr_patch=this%litfall_patch)

        this%wood_harvestc_patch(begp:endp) = spval
        call hist_addfld1d (fname='WOOD_HARVESTC', units='gC/m^2/s', &
             avgflag='A', long_name='wood harvest carbon (to product pools)', &
             ptr_patch=this%wood_harvestc_patch)

        this%slash_harvestc_patch(begp:endp) = spval
        call hist_addfld1d (fname='SLASH_HARVESTC', units='gC/m^2/s', &
             avgflag='A', long_name='slash harvest carbon (to litter)', &
             ptr_patch=this%slash_harvestc_patch)

        this%fire_closs_patch(begp:endp) = spval
        call hist_addfld1d (fname='PFT_FIRE_CLOSS', units='gC/m^2/s', &
             avgflag='A', long_name='total patch-level fire C loss for non-peat fires outside land-type converted region', &
             ptr_patch=this%fire_closs_patch)

        if ( use_fun ) then
          this%npp_Nactive_patch(begp:endp)  = spval
          call hist_addfld1d (fname='NPP_NACTIVE', units='gC/m^2/s',     &
               avgflag='A', long_name='Mycorrhizal N uptake used C',     &
               ptr_patch=this%npp_Nactive_patch)

          ! BUG(wjs, 2016-04-13, bugz 2292) This field has a threading bug. Making it
          ! inactive for now.
          this%npp_burnedoff_patch(begp:endp)  = spval
          call hist_addfld1d (fname='NPP_BURNEDOFF', units='gC/m^2/s',     &
               avgflag='A', long_name='C that cannot be used for N uptake',     &
               ptr_patch=this%npp_burnedoff_patch, default='inactive')
  
          this%npp_Nnonmyc_patch(begp:endp)  = spval
          call hist_addfld1d (fname='NPP_NNONMYC', units='gC/m^2/s',     &
               avgflag='A', long_name='Non-mycorrhizal N uptake used C', &
               ptr_patch=this%npp_Nnonmyc_patch)

          this%npp_Nam_patch(begp:endp)      = spval
          call hist_addfld1d (fname='NPP_NAM', units='gC/m^2/s',         &
               avgflag='A', long_name='AM-associated N uptake used C',   &
               ptr_patch=this%npp_Nam_patch)

          this%npp_Necm_patch(begp:endp)     = spval
          call hist_addfld1d (fname='NPP_NECM', units='gC/m^2/s',        &
               avgflag='A', long_name='ECM-associated N uptake used C',  &
               ptr_patch=this%npp_Necm_patch)

          if (use_nitrif_denitrif) then
             this%npp_Nactive_no3_patch(begp:endp)  = spval
             call hist_addfld1d (fname='NPP_NACTIVE_NO3', units='gC/m^2/s', &
                  avgflag='A', long_name='Mycorrhizal N uptake used C',     &
                  ptr_patch=this%npp_Nactive_no3_patch)

             this%npp_Nactive_nh4_patch(begp:endp)  = spval
             call hist_addfld1d (fname='NPP_NACTIVE_NH4', units='gC/m^2/s', &
                  avgflag='A', long_name='Mycorrhizal N uptake use C',      &
                  ptr_patch=this%npp_Nactive_nh4_patch)

             this%npp_Nnonmyc_no3_patch(begp:endp)  = spval
             call hist_addfld1d (fname='NPP_NNONMYC_NO3', units='gC/m^2/s', &
                  avgflag='A', long_name='Non-mycorrhizal N uptake use C',  &
                  ptr_patch=this%npp_Nnonmyc_no3_patch)

             this%npp_Nnonmyc_nh4_patch(begp:endp)  = spval
             call hist_addfld1d (fname='NPP_NNONMYC_NH4', units='gC/m^2/s', &
                  avgflag='A', long_name='Non-mycorrhizal N uptake use C',  &
                  ptr_patch=this%npp_Nnonmyc_nh4_patch)

             this%npp_Nam_no3_patch(begp:endp)      = spval
             call hist_addfld1d (fname='NPP_NAM_NO3', units='gC/m^2/s',     &
                  avgflag='A', long_name='AM-associated N uptake use C',    &
                  ptr_patch=this%npp_Nam_no3_patch)

             this%npp_Nam_nh4_patch(begp:endp)      = spval
             call hist_addfld1d (fname='NPP_NAM_NH4', units='gC/m^2/s',     &
                  avgflag='A', long_name='AM-associated N uptake use C',    &
                  ptr_patch=this%npp_Nam_nh4_patch)

             this%npp_Necm_no3_patch(begp:endp)     = spval
             call hist_addfld1d (fname='NPP_NECM_NO3', units='gC/m^2/s',    &
                  avgflag='A', long_name='ECM-associated N uptake used C',  &
                  ptr_patch=this%npp_Necm_no3_patch)

             this%npp_Necm_nh4_patch(begp:endp)     = spval
             call hist_addfld1d (fname='NPP_NECM_NH4', units='gC/m^2/s',     &
                  avgflag='A', long_name='ECM-associated N uptake use C',    &
                  ptr_patch=this%npp_Necm_nh4_patch)
          end if

          this%npp_Nfix_patch(begp:endp)     = spval
          call hist_addfld1d (fname='NPP_NFIX', units='gC/m^2/s',         &
               avgflag='A', long_name='Symbiotic BNF uptake used C',      &
               ptr_patch=this%npp_Nfix_patch)

          this%npp_Nretrans_patch(begp:endp) = spval
          call hist_addfld1d (fname='NPP_NRETRANS', units='gC/m^2/s',     &
              avgflag='A', long_name='Retranslocated N uptake flux',      &
              ptr_patch=this%npp_Nretrans_patch)

          this%npp_Nuptake_patch(begp:endp) = spval
          call hist_addfld1d (fname='NPP_NUPTAKE', units='gC/m^2/s',      &
               avgflag='A', long_name='Total C used by N uptake in FUN',  &
               ptr_patch=this%npp_Nuptake_patch)

          this%npp_growth_patch(begp:endp) = spval
          call hist_addfld1d (fname='NPP_GROWTH', units='gC/m^2/s',      &
               avgflag='A', long_name='Total C used for growth in FUN',  &
               ptr_patch=this%npp_growth_patch)

          this%leafc_change_patch(begp:endp) = spval
          call hist_addfld1d (fname='LEAFC_CHANGE', units='gC/m^2/s',     &
               avgflag='A', long_name='C change in leaf',                 &
               ptr_patch=this%leafc_change_patch)

          this%soilc_change_patch(begp:endp) = spval
          call hist_addfld1d (fname='SOILC_CHANGE', units='gC/m^2/s',     &
               avgflag='A', long_name='C change in soil',                 &
               ptr_patch=this%soilc_change_patch)
      end if
! FUN Ends 

    end if  ! end of if-c12

    !-------------------------------
    ! C13 flux variables - patch
    !-------------------------------

    if ( carbon_type == 'c13') then

        this%gpp_patch(begp:endp) = spval
        call hist_addfld1d (fname='C13_GPP', units='gC13/m^2/s', &
             avgflag='A', long_name='C13 gross primary production', &
             ptr_patch=this%gpp_patch)

        this%rr_patch(begp:endp) = spval
        call hist_addfld1d (fname='C13_RR', units='gC13/m^2/s', &
             avgflag='A', long_name='C13 root respiration (fine root MR + total root GR)', &
             ptr_patch=this%rr_patch, default='inactive')

        this%mr_patch(begp:endp) = spval
        call hist_addfld1d (fname='C13_MR', units='gC13/m^2/s', &
             avgflag='A', long_name='C13 maintenance respiration', &
             ptr_patch=this%mr_patch, default='inactive')

        this%gr_patch(begp:endp) = spval
        call hist_addfld1d (fname='C13_GR', units='gC13/m^2/s', &
             avgflag='A', long_name='C13 total growth respiration', &
             ptr_patch=this%gr_patch, default='inactive')

        this%ar_patch(begp:endp) = spval
        call hist_addfld1d (fname='C13_AR', units='gC13/m^2/s', &
             avgflag='A', long_name='C13 autotrophic respiration (MR + GR)', &
             ptr_patch=this%ar_patch)

        this%npp_patch(begp:endp) = spval
        call hist_addfld1d (fname='C13_NPP', units='gC13/m^2/s', &
             avgflag='A', long_name='C13 net primary production', &
             ptr_patch=this%npp_patch, default='inactive')

        this%agnpp_patch(begp:endp) = spval
        call hist_addfld1d (fname='C13_AGNPP', units='gC13/m^2/s', &
             avgflag='A', long_name='C13 aboveground NPP', &
             ptr_patch=this%agnpp_patch, default='inactive')

        this%bgnpp_patch(begp:endp) = spval
        call hist_addfld1d (fname='C13_BGNPP', units='gC13/m^2/s', &
             avgflag='A', long_name='C13 belowground NPP', &
             ptr_patch=this%bgnpp_patch, default='inactive')

        this%litfall_patch(begp:endp) = spval
        call hist_addfld1d (fname='C13_LITFALL', units='gC13/m^2/s', &
             avgflag='A', long_name='C13 litterfall (leaves and fine roots)', &
             ptr_patch=this%litfall_patch, default='inactive')

        this%fire_closs_patch(begp:endp) = spval
        call hist_addfld1d (fname='C13_PFT_FIRE_CLOSS', units='gC13/m^2/s', &
             avgflag='A', long_name='C13 total patch-level fire C loss', &
             ptr_patch=this%fire_closs_patch, default='inactive')

       this%m_leafc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_LEAFC_TO_LITTER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 leaf C mortality', &
            ptr_patch=this%m_leafc_to_litter_patch, default='inactive')

       this%m_frootc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_FROOTC_TO_LITTER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 fine root C mortality', &
            ptr_patch=this%m_frootc_to_litter_patch, default='inactive')

       this%m_leafc_storage_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_LEAFC_STORAGE_TO_LITTER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 leaf C storage mortality', &
            ptr_patch=this%m_leafc_storage_to_litter_patch, default='inactive')

       this%m_frootc_storage_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_FROOTC_STORAGE_TO_LITTER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 fine root C storage mortality', &
            ptr_patch=this%m_frootc_storage_to_litter_patch, default='inactive')

       this%m_livestemc_storage_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_LIVESTEMC_STORAGE_TO_LITTER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live stem C storage mortality', &
            ptr_patch=this%m_livestemc_storage_to_litter_patch, default='inactive')

       this%m_deadstemc_storage_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_DEADSTEMC_STORAGE_TO_LITTER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead stem C storage mortality', &
            ptr_patch=this%m_deadstemc_storage_to_litter_patch, default='inactive')

       this%m_livecrootc_storage_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_LIVECROOTC_STORAGE_TO_LITTER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live coarse root C storage mortality', &
            ptr_patch=this%m_livecrootc_storage_to_litter_patch, default='inactive')

       this%m_deadcrootc_storage_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_DEADCROOTC_STORAGE_TO_LITTER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead coarse root C storage mortality', &
            ptr_patch=this%m_deadcrootc_storage_to_litter_patch, default='inactive')

       this%m_leafc_xfer_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_LEAFC_XFER_TO_LITTER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 leaf C transfer mortality', &
            ptr_patch=this%m_leafc_xfer_to_litter_patch, default='inactive')

       this%m_frootc_xfer_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_FROOTC_XFER_TO_LITTER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 fine root C transfer mortality', &
            ptr_patch=this%m_frootc_xfer_to_litter_patch, default='inactive')

       this%m_livestemc_xfer_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_LIVESTEMC_XFER_TO_LITTER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live stem C transfer mortality', &
            ptr_patch=this%m_livestemc_xfer_to_litter_patch, default='inactive')

       this%m_deadstemc_xfer_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_DEADSTEMC_XFER_TO_LITTER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead stem C transfer mortality', &
            ptr_patch=this%m_deadstemc_xfer_to_litter_patch, default='inactive')

       this%m_livecrootc_xfer_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_LIVECROOTC_XFER_TO_LITTER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live coarse root C transfer mortality', &
            ptr_patch=this%m_livecrootc_xfer_to_litter_patch, default='inactive')

       this%m_deadcrootc_xfer_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_DEADCROOTC_XFER_TO_LITTER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead coarse root C transfer mortality', &
            ptr_patch=this%m_deadcrootc_xfer_to_litter_patch, default='inactive')

       this%m_livestemc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_LIVESTEMC_TO_LITTER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live stem C mortality', &
            ptr_patch=this%m_livestemc_to_litter_patch, default='inactive')

       this%m_deadstemc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_DEADSTEMC_TO_LITTER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead stem C mortality', &
            ptr_patch=this%m_deadstemc_to_litter_patch, default='inactive')

       this%m_livecrootc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_LIVECROOTC_TO_LITTER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live coarse root C mortality', &
            ptr_patch=this%m_livecrootc_to_litter_patch, default='inactive')

       this%m_deadcrootc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_DEADCROOTC_TO_LITTER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead coarse root C mortality', &
            ptr_patch=this%m_deadcrootc_to_litter_patch, default='inactive')

       this%m_gresp_storage_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_GRESP_STORAGE_TO_LITTER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 growth respiration storage mortality', &
            ptr_patch=this%m_gresp_storage_to_litter_patch, default='inactive')

       this%m_gresp_xfer_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_GRESP_XFER_TO_LITTER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 growth respiration transfer mortality', &
            ptr_patch=this%m_gresp_xfer_to_litter_patch, default='inactive')

       this%m_leafc_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_LEAFC_TO_FIRE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 leaf C fire loss', &
            ptr_patch=this%m_leafc_to_fire_patch, default='inactive')

       this%m_frootc_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_FROOTC_TO_FIRE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 fine root C fire loss', &
            ptr_patch=this%m_frootc_to_fire_patch, default='inactive')

       this%m_leafc_storage_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_LEAFC_STORAGE_TO_FIRE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 leaf C storage fire loss', &
            ptr_patch=this%m_leafc_storage_to_fire_patch, default='inactive')

       this%m_frootc_storage_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_FROOTC_STORAGE_TO_FIRE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 fine root C storage fire loss', &
            ptr_patch=this%m_frootc_storage_to_fire_patch, default='inactive')

       this%m_livestemc_storage_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_LIVESTEMC_STORAGE_TO_FIRE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live stem C storage fire loss', &
            ptr_patch=this%m_livestemc_storage_to_fire_patch, default='inactive')

       this%m_deadstemc_storage_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_DEADSTEMC_STORAGE_TO_FIRE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead stem C storage fire loss', &
            ptr_patch=this%m_deadstemc_storage_to_fire_patch, default='inactive')

       this%m_livecrootc_storage_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_LIVECROOTC_STORAGE_TO_FIRE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live coarse root C storage fire loss', &
            ptr_patch=this%m_livecrootc_storage_to_fire_patch, default='inactive')

       this%m_deadcrootc_storage_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_DEADCROOTC_STORAGE_TO_FIRE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead coarse root C storage fire loss', &
            ptr_patch=this%m_deadcrootc_storage_to_fire_patch,  default='inactive')

       this%m_leafc_xfer_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_LEAFC_XFER_TO_FIRE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 leaf C transfer fire loss', &
            ptr_patch=this%m_leafc_xfer_to_fire_patch, default='inactive')

       this%m_frootc_xfer_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_FROOTC_XFER_TO_FIRE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 fine root C transfer fire loss', &
            ptr_patch=this%m_frootc_xfer_to_fire_patch, default='inactive')

       this%m_livestemc_xfer_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_LIVESTEMC_XFER_TO_FIRE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live stem C transfer fire loss', &
            ptr_patch=this%m_livestemc_xfer_to_fire_patch, default='inactive')

       this%m_deadstemc_xfer_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_DEADSTEMC_XFER_TO_FIRE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead stem C transfer fire loss', &
            ptr_patch=this%m_deadstemc_xfer_to_fire_patch, default='inactive')

       this%m_livecrootc_xfer_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_LIVECROOTC_XFER_TO_FIRE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live coarse root C transfer fire loss', &
            ptr_patch=this%m_livecrootc_xfer_to_fire_patch, default='inactive')

       this%m_deadcrootc_xfer_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_DEADCROOTC_XFER_TO_FIRE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead coarse root C transfer fire loss', &
            ptr_patch=this%m_deadcrootc_xfer_to_fire_patch, default='inactive')

       this%m_livestemc_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_LIVESTEMC_TO_FIRE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live stem C fire loss', &
            ptr_patch=this%m_livestemc_to_fire_patch, default='inactive')

       this%m_deadstemc_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_DEADSTEMC_TO_FIRE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead stem C fire loss', &
            ptr_patch=this%m_deadstemc_to_fire_patch, default='inactive')

       this%m_deadstemc_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_DEADSTEMC_TO_LITTER_FIRE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead stem C fire mortality to litter', &
            ptr_patch=this%m_deadstemc_to_litter_fire_patch, default='inactive')

       this%m_livecrootc_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_LIVECROOTC_TO_FIRE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live coarse root C fire loss', &
            ptr_patch=this%m_livecrootc_to_fire_patch, default='inactive')

       this%m_deadcrootc_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_DEADCROOTC_TO_FIRE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead coarse root C fire loss', &
            ptr_patch=this%m_deadcrootc_to_fire_patch, default='inactive')

       this%m_deadcrootc_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_DEADCROOTC_TO_LITTER_FIRE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead coarse root C fire mortality to litter', &
            ptr_patch=this%m_deadcrootc_to_litter_fire_patch, default='inactive')

       this%m_gresp_storage_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_GRESP_STORAGE_TO_FIRE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 growth respiration storage fire loss', &
            ptr_patch=this%m_gresp_storage_to_fire_patch, default='inactive')

       this%m_gresp_xfer_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_M_GRESP_XFER_TO_FIRE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 growth respiration transfer fire loss', &
            ptr_patch=this%m_gresp_xfer_to_fire_patch, default='inactive')

       this%leafc_xfer_to_leafc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_LEAFC_XFER_TO_LEAFC', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 leaf C growth from storage', &
            ptr_patch=this%leafc_xfer_to_leafc_patch, default='inactive')

       this%frootc_xfer_to_frootc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_FROOTC_XFER_TO_FROOTC', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 fine root C growth from storage', &
            ptr_patch=this%frootc_xfer_to_frootc_patch, default='inactive')

       this%livestemc_xfer_to_livestemc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_LIVESTEMC_XFER_TO_LIVESTEMC', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live stem C growth from storage', &
            ptr_patch=this%livestemc_xfer_to_livestemc_patch, default='inactive')

       this%deadstemc_xfer_to_deadstemc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_DEADSTEMC_XFER_TO_DEADSTEMC', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead stem C growth from storage', &
            ptr_patch=this%deadstemc_xfer_to_deadstemc_patch, default='inactive')

       this%livecrootc_xfer_to_livecrootc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_LIVECROOTC_XFER_TO_LIVECROOTC', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live coarse root C growth from storage', &
            ptr_patch=this%livecrootc_xfer_to_livecrootc_patch, default='inactive')

       this%deadcrootc_xfer_to_deadcrootc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_DEADCROOTC_XFER_TO_DEADCROOTC', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead coarse root C growth from storage', &
            ptr_patch=this%deadcrootc_xfer_to_deadcrootc_patch, default='inactive')

       this%leafc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_LEAFC_TO_LITTER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 leaf C litterfall', &
            ptr_patch=this%leafc_to_litter_patch, default='inactive')

       this%frootc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_FROOTC_TO_LITTER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 fine root C litterfall', &
            ptr_patch=this%frootc_to_litter_patch, default='inactive')

       this%leaf_mr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_LEAF_MR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 leaf maintenance respiration', &
            ptr_patch=this%leaf_mr_patch, default='inactive')

       this%froot_mr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_FROOT_MR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 fine root maintenance respiration', &
            ptr_patch=this%froot_mr_patch, default='inactive')

       this%livestem_mr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_LIVESTEM_MR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live stem maintenance respiration', &
            ptr_patch=this%livestem_mr_patch, default='inactive')

       this%livecroot_mr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_LIVECROOT_MR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live coarse root maintenance respiration', &
            ptr_patch=this%livecroot_mr_patch, default='inactive')

       this%psnsun_to_cpool_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_PSNSUN_TO_CPOOL', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 C fixation from sunlit canopy', &
            ptr_patch=this%psnsun_to_cpool_patch, default='inactive')

       this%psnshade_to_cpool_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_PSNSHADE_TO_CPOOL', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 C fixation from shaded canopy', &
            ptr_patch=this%psnshade_to_cpool_patch, default='inactive')

       this%cpool_to_leafc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_TO_LEAFC', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 allocation to leaf C', &
            ptr_patch=this%cpool_to_leafc_patch, default='inactive')

       this%cpool_to_leafc_storage_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_TO_LEAFC_STORAGE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 allocation to leaf C storage', &
            ptr_patch=this%cpool_to_leafc_storage_patch, default='inactive')

       this%cpool_to_frootc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_TO_FROOTC', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 allocation to fine root C', &
            ptr_patch=this%cpool_to_frootc_patch, default='inactive')

       this%cpool_to_frootc_storage_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_TO_FROOTC_STORAGE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 allocation to fine root C storage', &
            ptr_patch=this%cpool_to_frootc_storage_patch, default='inactive')

       this%cpool_to_livestemc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_TO_LIVESTEMC', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 allocation to live stem C', &
            ptr_patch=this%cpool_to_livestemc_patch, default='inactive')

       this%cpool_to_livestemc_storage_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_TO_LIVESTEMC_STORAGE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 allocation to live stem C storage', &
            ptr_patch=this%cpool_to_livestemc_storage_patch, default='inactive')

       this%cpool_to_deadstemc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_TO_DEADSTEMC', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 allocation to dead stem C', &
            ptr_patch=this%cpool_to_deadstemc_patch, default='inactive')

       this%cpool_to_deadstemc_storage_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_TO_DEADSTEMC_STORAGE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 allocation to dead stem C storage', &
            ptr_patch=this%cpool_to_deadstemc_storage_patch, default='inactive')

       this%cpool_to_livecrootc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_TO_LIVECROOTC', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 allocation to live coarse root C', &
            ptr_patch=this%cpool_to_livecrootc_patch, default='inactive')

       this%cpool_to_livecrootc_storage_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_TO_LIVECROOTC_STORAGE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 allocation to live coarse root C storage', &
            ptr_patch=this%cpool_to_livecrootc_storage_patch, default='inactive')

       this%cpool_to_deadcrootc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_TO_DEADCROOTC', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 allocation to dead coarse root C', &
            ptr_patch=this%cpool_to_deadcrootc_patch, default='inactive')

       this%cpool_to_deadcrootc_storage_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_TO_DEADCROOTC_STORAGE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 allocation to dead coarse root C storage', &
            ptr_patch=this%cpool_to_deadcrootc_storage_patch, default='inactive')

       this%cpool_to_gresp_storage_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_TO_GRESP_STORAGE', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 allocation to growth respiration storage', &
            ptr_patch=this%cpool_to_gresp_storage_patch, default='inactive')

       this%cpool_leaf_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_LEAF_GR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 leaf growth respiration', &
            ptr_patch=this%cpool_leaf_gr_patch, default='inactive')

       this%cpool_leaf_storage_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_LEAF_STORAGE_GR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 leaf growth respiration to storage', &
            ptr_patch=this%cpool_leaf_storage_gr_patch, default='inactive')

       this%transfer_leaf_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_TRANSFER_LEAF_GR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 leaf growth respiration from storage', &
            ptr_patch=this%transfer_leaf_gr_patch, default='inactive')

       this%cpool_froot_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_FROOT_GR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 fine root growth respiration', &
            ptr_patch=this%cpool_froot_gr_patch, default='inactive')

       this%cpool_froot_storage_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_FROOT_STORAGE_GR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 fine root  growth respiration to storage', &
            ptr_patch=this%cpool_froot_storage_gr_patch, default='inactive')

       this%transfer_froot_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_TRANSFER_FROOT_GR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 fine root  growth respiration from storage', &
            ptr_patch=this%transfer_froot_gr_patch, default='inactive')

       this%cpool_livestem_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_LIVESTEM_GR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live stem growth respiration', &
            ptr_patch=this%cpool_livestem_gr_patch, default='inactive')

       this%cpool_livestem_storage_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_LIVESTEM_STORAGE_GR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live stem growth respiration to storage', &
            ptr_patch=this%cpool_livestem_storage_gr_patch, default='inactive')

       this%transfer_livestem_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_TRANSFER_LIVESTEM_GR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live stem growth respiration from storage', &
            ptr_patch=this%transfer_livestem_gr_patch, default='inactive')

       this%cpool_deadstem_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_DEADSTEM_GR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead stem growth respiration', &
            ptr_patch=this%cpool_deadstem_gr_patch, default='inactive')

       this%cpool_deadstem_storage_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_DEADSTEM_STORAGE_GR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead stem growth respiration to storage', &
            ptr_patch=this%cpool_deadstem_storage_gr_patch, default='inactive')

       this%transfer_deadstem_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_TRANSFER_DEADSTEM_GR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead stem growth respiration from storage', &
            ptr_patch=this%transfer_deadstem_gr_patch, default='inactive')

       this%cpool_livecroot_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_LIVECROOT_GR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live coarse root growth respiration', &
            ptr_patch=this%cpool_livecroot_gr_patch, default='inactive')

       this%cpool_livecroot_storage_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_LIVECROOT_STORAGE_GR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live coarse root growth respiration to storage', &
            ptr_patch=this%cpool_livecroot_storage_gr_patch, default='inactive')

       this%transfer_livecroot_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_TRANSFER_LIVECROOT_GR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live coarse root growth respiration from storage', &
            ptr_patch=this%transfer_livecroot_gr_patch, default='inactive')

       this%cpool_deadcroot_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_DEADCROOT_GR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead coarse root growth respiration', &
            ptr_patch=this%cpool_deadcroot_gr_patch, default='inactive')

       this%cpool_deadcroot_storage_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CPOOL_DEADCROOT_STORAGE_GR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead coarse root growth respiration to storage', &
            ptr_patch=this%cpool_deadcroot_storage_gr_patch, default='inactive')

       this%transfer_deadcroot_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_TRANSFER_DEADCROOT_GR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead coarse root growth respiration from storage', &
            ptr_patch=this%transfer_deadcroot_gr_patch, default='inactive')

       this%leafc_storage_to_xfer_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_LEAFC_STORAGE_TO_XFER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 leaf C shift storage to transfer', &
            ptr_patch=this%leafc_storage_to_xfer_patch, default='inactive')

       this%frootc_storage_to_xfer_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_FROOTC_STORAGE_TO_XFER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 fine root C shift storage to transfer', &
            ptr_patch=this%frootc_storage_to_xfer_patch, default='inactive')

       this%livestemc_storage_to_xfer_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_LIVESTEMC_STORAGE_TO_XFER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live stem C shift storage to transfer', &
            ptr_patch=this%livestemc_storage_to_xfer_patch, default='inactive')

       this%deadstemc_storage_to_xfer_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_DEADSTEMC_STORAGE_TO_XFER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead stem C shift storage to transfer', &
            ptr_patch=this%deadstemc_storage_to_xfer_patch, default='inactive')

       this%livecrootc_storage_to_xfer_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_LIVECROOTC_STORAGE_TO_XFER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live coarse root C shift storage to transfer', &
            ptr_patch=this%livecrootc_storage_to_xfer_patch, default='inactive')

       this%deadcrootc_storage_to_xfer_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_DEADCROOTC_STORAGE_TO_XFER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 dead coarse root C shift storage to transfer', &
            ptr_patch=this%deadcrootc_storage_to_xfer_patch, default='inactive')

       this%gresp_storage_to_xfer_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_GRESP_STORAGE_TO_XFER', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 growth respiration shift storage to transfer', &
            ptr_patch=this%gresp_storage_to_xfer_patch, default='inactive')

       this%livestemc_to_deadstemc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_LIVESTEMC_TO_DEADSTEMC', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live stem C turnover', &
            ptr_patch=this%livestemc_to_deadstemc_patch, default='inactive')

       this%livecrootc_to_deadcrootc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_LIVECROOTC_TO_DEADCROOTC', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 live coarse root C turnover', &
            ptr_patch=this%livecrootc_to_deadcrootc_patch, default='inactive')

       this%current_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CURRENT_GR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 growth resp for new growth displayed in this timestep', &
            ptr_patch=this%current_gr_patch, default='inactive')

       this%transfer_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_TRANSFER_GR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 growth resp for transfer growth displayed in this timestep', &
            ptr_patch=this%transfer_gr_patch, default='inactive')

       this%storage_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_STORAGE_GR', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 growth resp for growth sent to storage for later display', &
            ptr_patch=this%storage_gr_patch, default='inactive')

       this%xsmrpool_c13ratio_patch(begp:endp) = spval
       call hist_addfld1d (fname='XSMRPOOL_C13RATIO', units='proportion', &
            avgflag='A', long_name='C13/C(12+13) ratio for xsmrpool', &
            ptr_patch=this%xsmrpool_c13ratio_patch, default='inactive')

    endif

    !-------------------------------
    ! C14 flux variables - patch
    !-------------------------------

    if ( carbon_type == 'c14' ) then

       this%m_leafc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_LEAFC_TO_LITTER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 leaf C mortality', &
            ptr_patch=this%m_leafc_to_litter_patch, default='inactive')

       this%m_frootc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_FROOTC_TO_LITTER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 fine root C mortality', &
            ptr_patch=this%m_frootc_to_litter_patch, default='inactive')

       this%m_leafc_storage_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_LEAFC_STORAGE_TO_LITTER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 leaf C storage mortality', &
            ptr_patch=this%m_leafc_storage_to_litter_patch, default='inactive')

       this%m_frootc_storage_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_FROOTC_STORAGE_TO_LITTER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 fine root C storage mortality', &
            ptr_patch=this%m_frootc_storage_to_litter_patch, default='inactive')

       this%m_livestemc_storage_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_LIVESTEMC_STORAGE_TO_LITTER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live stem C storage mortality', &
            ptr_patch=this%m_livestemc_storage_to_litter_patch, default='inactive')

       this%m_deadstemc_storage_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_DEADSTEMC_STORAGE_TO_LITTER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead stem C storage mortality', &
            ptr_patch=this%m_deadstemc_storage_to_litter_patch, default='inactive')

       this%m_livecrootc_storage_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_LIVECROOTC_STORAGE_TO_LITTER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live coarse root C storage mortality', &
            ptr_patch=this%m_livecrootc_storage_to_litter_patch, default='inactive')

       this%m_deadcrootc_storage_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_DEADCROOTC_STORAGE_TO_LITTER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead coarse root C storage mortality', &
            ptr_patch=this%m_deadcrootc_storage_to_litter_patch, default='inactive')

       this%m_leafc_xfer_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_LEAFC_XFER_TO_LITTER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 leaf C transfer mortality', &
            ptr_patch=this%m_leafc_xfer_to_litter_patch, default='inactive')

       this%m_frootc_xfer_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_FROOTC_XFER_TO_LITTER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 fine root C transfer mortality', &
            ptr_patch=this%m_frootc_xfer_to_litter_patch, default='inactive')

       this%m_livestemc_xfer_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_LIVESTEMC_XFER_TO_LITTER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live stem C transfer mortality', &
            ptr_patch=this%m_livestemc_xfer_to_litter_patch, default='inactive')

       this%m_deadstemc_xfer_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_DEADSTEMC_XFER_TO_LITTER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead stem C transfer mortality', &
            ptr_patch=this%m_deadstemc_xfer_to_litter_patch, default='inactive')

       this%m_livecrootc_xfer_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_LIVECROOTC_XFER_TO_LITTER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live coarse root C transfer mortality', &
            ptr_patch=this%m_livecrootc_xfer_to_litter_patch, default='inactive')

       this%m_deadcrootc_xfer_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_DEADCROOTC_XFER_TO_LITTER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead coarse root C transfer mortality', &
            ptr_patch=this%m_deadcrootc_xfer_to_litter_patch, default='inactive')

       this%m_livestemc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_LIVESTEMC_TO_LITTER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live stem C mortality', &
            ptr_patch=this%m_livestemc_to_litter_patch, default='inactive')

       this%m_deadstemc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_DEADSTEMC_TO_LITTER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead stem C mortality', &
            ptr_patch=this%m_deadstemc_to_litter_patch, default='inactive')

       this%m_livecrootc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_LIVECROOTC_TO_LITTER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live coarse root C mortality', &
            ptr_patch=this%m_livecrootc_to_litter_patch, default='inactive')

       this%m_deadcrootc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_DEADCROOTC_TO_LITTER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead coarse root C mortality', &
            ptr_patch=this%m_deadcrootc_to_litter_patch, default='inactive')

       this%m_gresp_storage_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_GRESP_STORAGE_TO_LITTER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 growth respiration storage mortality', &
            ptr_patch=this%m_gresp_storage_to_litter_patch, default='inactive')

       this%m_gresp_xfer_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_GRESP_XFER_TO_LITTER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 growth respiration transfer mortality', &
            ptr_patch=this%m_gresp_xfer_to_litter_patch, default='inactive')

       this%m_leafc_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_LEAFC_TO_FIRE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 leaf C fire loss', &
            ptr_patch=this%m_leafc_to_fire_patch, default='inactive')

       this%m_frootc_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_FROOTC_TO_FIRE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 fine root C fire loss', &
            ptr_patch=this%m_frootc_to_fire_patch, default='inactive')

       this%m_leafc_storage_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_LEAFC_STORAGE_TO_FIRE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 leaf C storage fire loss', &
            ptr_patch=this%m_leafc_storage_to_fire_patch, default='inactive')

       this%m_frootc_storage_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_FROOTC_STORAGE_TO_FIRE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 fine root C storage fire loss', &
            ptr_patch=this%m_frootc_storage_to_fire_patch, default='inactive')

       this%m_livestemc_storage_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_LIVESTEMC_STORAGE_TO_FIRE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live stem C storage fire loss', &
            ptr_patch=this%m_livestemc_storage_to_fire_patch, default='inactive')

       this%m_deadstemc_storage_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_DEADSTEMC_STORAGE_TO_FIRE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead stem C storage fire loss', &
            ptr_patch=this%m_deadstemc_storage_to_fire_patch, default='inactive')

       this%m_livecrootc_storage_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_LIVECROOTC_STORAGE_TO_FIRE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live coarse root C storage fire loss', &
            ptr_patch=this%m_livecrootc_storage_to_fire_patch, default='inactive')

       this%m_deadcrootc_storage_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_DEADCROOTC_STORAGE_TO_FIRE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead coarse root C storage fire loss', &
            ptr_patch=this%m_deadcrootc_storage_to_fire_patch,  default='inactive')

       this%m_leafc_xfer_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_LEAFC_XFER_TO_FIRE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 leaf C transfer fire loss', &
            ptr_patch=this%m_leafc_xfer_to_fire_patch, default='inactive')

       this%m_frootc_xfer_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_FROOTC_XFER_TO_FIRE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 fine root C transfer fire loss', &
            ptr_patch=this%m_frootc_xfer_to_fire_patch, default='inactive')

       this%m_livestemc_xfer_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_LIVESTEMC_XFER_TO_FIRE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live stem C transfer fire loss', &
            ptr_patch=this%m_livestemc_xfer_to_fire_patch, default='inactive')

       this%m_deadstemc_xfer_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_DEADSTEMC_XFER_TO_FIRE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead stem C transfer fire loss', &
            ptr_patch=this%m_deadstemc_xfer_to_fire_patch, default='inactive')

       this%m_livecrootc_xfer_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_LIVECROOTC_XFER_TO_FIRE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live coarse root C transfer fire loss', &
            ptr_patch=this%m_livecrootc_xfer_to_fire_patch, default='inactive')

       this%m_deadcrootc_xfer_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_DEADCROOTC_XFER_TO_FIRE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead coarse root C transfer fire loss', &
            ptr_patch=this%m_deadcrootc_xfer_to_fire_patch, default='inactive')

       this%m_livestemc_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_LIVESTEMC_TO_FIRE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live stem C fire loss', &
            ptr_patch=this%m_livestemc_to_fire_patch, default='inactive')

       this%m_deadstemc_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_DEADSTEMC_TO_FIRE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead stem C fire loss', &
            ptr_patch=this%m_deadstemc_to_fire_patch, default='inactive')

       this%m_deadstemc_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_DEADSTEMC_TO_LITTER_FIRE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead stem C fire mortality to litter', &
            ptr_patch=this%m_deadstemc_to_litter_fire_patch, default='inactive')

       this%m_livecrootc_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_LIVECROOTC_TO_FIRE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live coarse root C fire loss', &
            ptr_patch=this%m_livecrootc_to_fire_patch, default='inactive')

       this%m_deadcrootc_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_DEADCROOTC_TO_FIRE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead coarse root C fire loss', &
            ptr_patch=this%m_deadcrootc_to_fire_patch, default='inactive')

       this%m_deadcrootc_to_litter_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_DEADCROOTC_TO_LITTER_FIRE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead coarse root C fire mortality to litter', &
            ptr_patch=this%m_deadcrootc_to_litter_fire_patch, default='inactive')

       this%m_gresp_storage_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_GRESP_STORAGE_TO_FIRE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 growth respiration storage fire loss', &
            ptr_patch=this%m_gresp_storage_to_fire_patch, default='inactive')

       this%m_gresp_xfer_to_fire_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_M_GRESP_XFER_TO_FIRE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 growth respiration transfer fire loss', &
            ptr_patch=this%m_gresp_xfer_to_fire_patch, default='inactive')

       this%leafc_xfer_to_leafc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_LEAFC_XFER_TO_LEAFC', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 leaf C growth from storage', &
            ptr_patch=this%leafc_xfer_to_leafc_patch, default='inactive')

       this%frootc_xfer_to_frootc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_FROOTC_XFER_TO_FROOTC', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 fine root C growth from storage', &
            ptr_patch=this%frootc_xfer_to_frootc_patch, default='inactive')

       this%livestemc_xfer_to_livestemc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_LIVESTEMC_XFER_TO_LIVESTEMC', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live stem C growth from storage', &
            ptr_patch=this%livestemc_xfer_to_livestemc_patch, default='inactive')

       this%deadstemc_xfer_to_deadstemc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_DEADSTEMC_XFER_TO_DEADSTEMC', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead stem C growth from storage', &
            ptr_patch=this%deadstemc_xfer_to_deadstemc_patch, default='inactive')

       this%livecrootc_xfer_to_livecrootc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_LIVECROOTC_XFER_TO_LIVECROOTC', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live coarse root C growth from storage', &
            ptr_patch=this%livecrootc_xfer_to_livecrootc_patch, default='inactive')

       this%deadcrootc_xfer_to_deadcrootc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_DEADCROOTC_XFER_TO_DEADCROOTC', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead coarse root C growth from storage', &
            ptr_patch=this%deadcrootc_xfer_to_deadcrootc_patch, default='inactive')

       this%leafc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_LEAFC_TO_LITTER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 leaf C litterfall', &
            ptr_patch=this%leafc_to_litter_patch, default='inactive')

       this%frootc_to_litter_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_FROOTC_TO_LITTER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 fine root C litterfall', &
            ptr_patch=this%frootc_to_litter_patch, default='inactive')

       this%leaf_mr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_LEAF_MR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 leaf maintenance respiration', &
            ptr_patch=this%leaf_mr_patch, default='inactive')

       this%froot_mr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_FROOT_MR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 fine root maintenance respiration', &
            ptr_patch=this%froot_mr_patch, default='inactive')

       this%livestem_mr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_LIVESTEM_MR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live stem maintenance respiration', &
            ptr_patch=this%livestem_mr_patch, default='inactive')

       this%livecroot_mr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_LIVECROOT_MR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live coarse root maintenance respiration', &
            ptr_patch=this%livecroot_mr_patch, default='inactive')

       this%psnsun_to_cpool_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_PSNSUN_TO_CPOOL', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 C fixation from sunlit canopy', &
            ptr_patch=this%psnsun_to_cpool_patch, default='inactive')

       this%psnshade_to_cpool_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_PSNSHADE_TO_CPOOL', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 C fixation from shaded canopy', &
            ptr_patch=this%psnshade_to_cpool_patch, default='inactive')

       this%cpool_to_leafc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_TO_LEAFC', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 allocation to leaf C', &
            ptr_patch=this%cpool_to_leafc_patch, default='inactive')

       this%cpool_to_leafc_storage_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_TO_LEAFC_STORAGE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 allocation to leaf C storage', &
            ptr_patch=this%cpool_to_leafc_storage_patch, default='inactive')

       this%cpool_to_frootc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_TO_FROOTC', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 allocation to fine root C', &
            ptr_patch=this%cpool_to_frootc_patch, default='inactive')

       this%cpool_to_frootc_storage_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_TO_FROOTC_STORAGE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 allocation to fine root C storage', &
            ptr_patch=this%cpool_to_frootc_storage_patch, default='inactive')

       this%cpool_to_livestemc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_TO_LIVESTEMC', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 allocation to live stem C', &
            ptr_patch=this%cpool_to_livestemc_patch, default='inactive')

       this%cpool_to_livestemc_storage_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_TO_LIVESTEMC_STORAGE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 allocation to live stem C storage', &
            ptr_patch=this%cpool_to_livestemc_storage_patch, default='inactive')

       this%cpool_to_deadstemc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_TO_DEADSTEMC', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 allocation to dead stem C', &
            ptr_patch=this%cpool_to_deadstemc_patch, default='inactive')

       this%cpool_to_deadstemc_storage_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_TO_DEADSTEMC_STORAGE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 allocation to dead stem C storage', &
            ptr_patch=this%cpool_to_deadstemc_storage_patch, default='inactive')

       this%cpool_to_livecrootc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_TO_LIVECROOTC', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 allocation to live coarse root C', &
            ptr_patch=this%cpool_to_livecrootc_patch, default='inactive')

       this%cpool_to_livecrootc_storage_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_TO_LIVECROOTC_STORAGE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 allocation to live coarse root C storage', &
            ptr_patch=this%cpool_to_livecrootc_storage_patch, default='inactive')

       this%cpool_to_deadcrootc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_TO_DEADCROOTC', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 allocation to dead coarse root C', &
            ptr_patch=this%cpool_to_deadcrootc_patch, default='inactive')

       this%cpool_to_deadcrootc_storage_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_TO_DEADCROOTC_STORAGE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 allocation to dead coarse root C storage', &
            ptr_patch=this%cpool_to_deadcrootc_storage_patch, default='inactive')

       this%cpool_to_gresp_storage_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_TO_GRESP_STORAGE', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 allocation to growth respiration storage', &
            ptr_patch=this%cpool_to_gresp_storage_patch, default='inactive')

       this%cpool_leaf_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_LEAF_GR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 leaf growth respiration', &
            ptr_patch=this%cpool_leaf_gr_patch, default='inactive')

       this%cpool_leaf_storage_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_LEAF_STORAGE_GR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 leaf growth respiration to storage', &
            ptr_patch=this%cpool_leaf_storage_gr_patch, default='inactive')

       this%transfer_leaf_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_TRANSFER_LEAF_GR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 leaf growth respiration from storage', &
            ptr_patch=this%transfer_leaf_gr_patch, default='inactive')

       this%cpool_froot_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_FROOT_GR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 fine root growth respiration', &
            ptr_patch=this%cpool_froot_gr_patch, default='inactive')

       this%cpool_froot_storage_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_FROOT_STORAGE_GR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 fine root  growth respiration to storage', &
            ptr_patch=this%cpool_froot_storage_gr_patch, default='inactive')

       this%transfer_froot_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_TRANSFER_FROOT_GR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 fine root  growth respiration from storage', &
            ptr_patch=this%transfer_froot_gr_patch, default='inactive')

       this%cpool_livestem_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_LIVESTEM_GR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live stem growth respiration', &
            ptr_patch=this%cpool_livestem_gr_patch, default='inactive')

       this%cpool_livestem_storage_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_LIVESTEM_STORAGE_GR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live stem growth respiration to storage', &
            ptr_patch=this%cpool_livestem_storage_gr_patch, default='inactive')

       this%transfer_livestem_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_TRANSFER_LIVESTEM_GR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live stem growth respiration from storage', &
            ptr_patch=this%transfer_livestem_gr_patch, default='inactive')

       this%cpool_deadstem_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_DEADSTEM_GR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead stem growth respiration', &
            ptr_patch=this%cpool_deadstem_gr_patch, default='inactive')

       this%cpool_deadstem_storage_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_DEADSTEM_STORAGE_GR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead stem growth respiration to storage', &
            ptr_patch=this%cpool_deadstem_storage_gr_patch, default='inactive')

       this%transfer_deadstem_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_TRANSFER_DEADSTEM_GR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead stem growth respiration from storage', &
            ptr_patch=this%transfer_deadstem_gr_patch, default='inactive')

       this%cpool_livecroot_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_LIVECROOT_GR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live coarse root growth respiration', &
            ptr_patch=this%cpool_livecroot_gr_patch, default='inactive')

       this%cpool_livecroot_storage_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_LIVECROOT_STORAGE_GR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live coarse root growth respiration to storage', &
            ptr_patch=this%cpool_livecroot_storage_gr_patch, default='inactive')

       this%transfer_livecroot_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_TRANSFER_LIVECROOT_GR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live coarse root growth respiration from storage', &
            ptr_patch=this%transfer_livecroot_gr_patch, default='inactive')

       this%cpool_deadcroot_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_DEADCROOT_GR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead coarse root growth respiration', &
            ptr_patch=this%cpool_deadcroot_gr_patch, default='inactive')

       this%cpool_deadcroot_storage_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CPOOL_DEADCROOT_STORAGE_GR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead coarse root growth respiration to storage', &
            ptr_patch=this%cpool_deadcroot_storage_gr_patch, default='inactive')

       this%transfer_deadcroot_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_TRANSFER_DEADCROOT_GR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead coarse root growth respiration from storage', &
            ptr_patch=this%transfer_deadcroot_gr_patch, default='inactive')

       this%leafc_storage_to_xfer_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_LEAFC_STORAGE_TO_XFER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 leaf C shift storage to transfer', &
            ptr_patch=this%leafc_storage_to_xfer_patch, default='inactive')

       this%frootc_storage_to_xfer_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_FROOTC_STORAGE_TO_XFER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 fine root C shift storage to transfer', &
            ptr_patch=this%frootc_storage_to_xfer_patch, default='inactive')

       this%livestemc_storage_to_xfer_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_LIVESTEMC_STORAGE_TO_XFER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live stem C shift storage to transfer', &
            ptr_patch=this%livestemc_storage_to_xfer_patch, default='inactive')

       this%deadstemc_storage_to_xfer_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_DEADSTEMC_STORAGE_TO_XFER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead stem C shift storage to transfer', &
            ptr_patch=this%deadstemc_storage_to_xfer_patch, default='inactive')

       this%livecrootc_storage_to_xfer_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_LIVECROOTC_STORAGE_TO_XFER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live coarse root C shift storage to transfer', &
            ptr_patch=this%livecrootc_storage_to_xfer_patch, default='inactive')

       this%deadcrootc_storage_to_xfer_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_DEADCROOTC_STORAGE_TO_XFER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 dead coarse root C shift storage to transfer', &
            ptr_patch=this%deadcrootc_storage_to_xfer_patch, default='inactive')

       this%gresp_storage_to_xfer_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_GRESP_STORAGE_TO_XFER', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 growth respiration shift storage to transfer', &
            ptr_patch=this%gresp_storage_to_xfer_patch, default='inactive')

       this%livestemc_to_deadstemc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_LIVESTEMC_TO_DEADSTEMC', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live stem C turnover', &
            ptr_patch=this%livestemc_to_deadstemc_patch, default='inactive')

       this%livecrootc_to_deadcrootc_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_LIVECROOTC_TO_DEADCROOTC', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 live coarse root C turnover', &
            ptr_patch=this%livecrootc_to_deadcrootc_patch, default='inactive')

       this%current_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CURRENT_GR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 growth resp for new growth displayed in this timestep', &
            ptr_patch=this%current_gr_patch, default='inactive')

       this%transfer_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_TRANSFER_GR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 growth resp for transfer growth displayed in this timestep', &
            ptr_patch=this%transfer_gr_patch, default='inactive')

       this%storage_gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_STORAGE_GR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 growth resp for growth sent to storage for later display', &
            ptr_patch=this%storage_gr_patch, default='inactive')

       this%gpp_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_GPP', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 gross primary production', &
            ptr_patch=this%gpp_patch)

       this%rr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_RR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 root respiration (fine root MR + total root GR)', &
            ptr_patch=this%rr_patch, default='inactive')

       this%mr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_MR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 maintenance respiration', &
            ptr_patch=this%mr_patch, default='inactive')

       this%gr_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_GR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 total growth respiration', &
            ptr_patch=this%gr_patch, default='inactive')

       this%ar_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_AR', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 autotrophic respiration (MR + GR)', &
            ptr_patch=this%ar_patch)

       this%npp_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_NPP', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 net primary production', &
            ptr_patch=this%npp_patch, default='inactive')

       this%agnpp_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_AGNPP', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 aboveground NPP', &
            ptr_patch=this%agnpp_patch, default='inactive')

       this%bgnpp_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_BGNPP', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 belowground NPP', &
            ptr_patch=this%bgnpp_patch, default='inactive')

       this%litfall_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_LITFALL', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 litterfall (leaves and fine roots)', &
            ptr_patch=this%litfall_patch, default='inactive')

       this%fire_closs_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_PFT_FIRE_CLOSS', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 total patch-level fire C loss', &
            ptr_patch=this%fire_closs_patch, default='inactive')
    endif

    !-------------------------------
    ! C flux variables - column 
    !-------------------------------

    if (carbon_type == 'c12') then

       this%cwdc_loss_col(begc:endc) = spval
       call hist_addfld1d (fname='CWDC_LOSS', units='gC/m^2/s', &
            avgflag='A', long_name='coarse woody debris C loss', &
            ptr_col=this%cwdc_loss_col)

       this%m_decomp_cpools_to_fire_col(begc:endc,:)      = spval
       this%m_decomp_cpools_to_fire_vr_col(begc:endc,:,:) = spval
       do k = 1, ndecomp_pools
          if ( decomp_cascade_con%is_litter(k) .or. decomp_cascade_con%is_cwd(k) ) then
             data1dptr => this%m_decomp_cpools_to_fire_col(:,k)
             fieldname = 'M_'//trim(decomp_cascade_con%decomp_pool_name_history(k))//'C_TO_FIRE'
             longname =  trim(decomp_cascade_con%decomp_pool_name_long(k))//' C fire loss'
             call hist_addfld1d (fname=fieldname, units='gC/m^2/s',  &
                  avgflag='A', long_name=longname, &
                  ptr_col=data1dptr, default='inactive')

             if ( nlevdecomp_full > 1 ) then
                data2dptr => this%m_decomp_cpools_to_fire_vr_col(:,:,k)
                fieldname = 'M_'//trim(decomp_cascade_con%decomp_pool_name_history(k))//'C_TO_FIRE'//trim(vr_suffix)
                longname =  trim(decomp_cascade_con%decomp_pool_name_long(k))//' C fire loss'
                call hist_addfld_decomp (fname=fieldname, units='gC/m^3/s', type2d='levdcmp', &
                     avgflag='A', long_name=longname, &
                     ptr_col=data2dptr, default='inactive')
             endif
          endif
       end do

       this%dwt_seedc_to_leaf_grc(begg:endg) = spval
       call hist_addfld1d (fname='DWT_SEEDC_TO_LEAF', units='gC/m^2/s', &
            avgflag='A', long_name='seed source to patch-level leaf', &
            ptr_gcell=this%dwt_seedc_to_leaf_grc, default='inactive')

       this%dwt_seedc_to_leaf_patch(begp:endp) = spval
       call hist_addfld1d (fname='DWT_SEEDC_TO_LEAF_PATCH', units='gC/m^2/s', &
            avgflag='A', &
            long_name='patch-level seed source to patch-level leaf ' // &
            '(per-area-gridcell; only makes sense with dov2xy=.false.)', &
            ptr_patch=this%dwt_seedc_to_leaf_patch, default='inactive')

       this%dwt_seedc_to_deadstem_grc(begg:endg) = spval
       call hist_addfld1d (fname='DWT_SEEDC_TO_DEADSTEM', units='gC/m^2/s', &
            avgflag='A', long_name='seed source to patch-level deadstem', &
            ptr_gcell=this%dwt_seedc_to_deadstem_grc, default='inactive')

       this%dwt_seedc_to_deadstem_patch(begp:endp) = spval
       call hist_addfld1d (fname='DWT_SEEDC_TO_DEADSTEM_PATCH', units='gC/m^2/s', &
            avgflag='A', &
            long_name='patch-level seed source to patch-level deadstem ' // &
            '(per-area-gridcell; only makes sense with dov2xy=.false.)', &
            ptr_patch=this%dwt_seedc_to_deadstem_patch, default='inactive')

       this%dwt_conv_cflux_grc(begg:endg) = spval
       call hist_addfld1d (fname='DWT_CONV_CFLUX', units='gC/m^2/s', &
            avgflag='A', &
            long_name='conversion C flux (immediate loss to atm) (0 at all times except first timestep of year)', &
            ptr_gcell=this%dwt_conv_cflux_grc)

       this%dwt_conv_cflux_patch(begp:endp) = spval
       call hist_addfld1d (fname='DWT_CONV_CFLUX_PATCH', units='gC/m^2/s', &
            avgflag='A', &
            long_name='patch-level conversion C flux (immediate loss to atm) ' // &
            '(0 at all times except first timestep of year) ' // &
            '(per-area-gridcell; only makes sense with dov2xy=.false.)', &
            ptr_patch=this%dwt_conv_cflux_patch, default='inactive')

       this%dwt_conv_cflux_dribbled_grc(begg:endg) = spval
       call hist_addfld1d (fname='DWT_CONV_CFLUX_DRIBBLED', units='gC/m^2/s', &
            avgflag='A', &
            long_name='conversion C flux (immediate loss to atm), dribbled throughout the year', &
            ptr_gcell=this%dwt_conv_cflux_dribbled_grc)

       this%dwt_wood_productc_gain_patch(begp:endp) = spval
       call hist_addfld1d (fname='DWT_WOOD_PRODUCTC_GAIN_PATCH', units='gC/m^2/s', &
            avgflag='A', &
            long_name='patch-level landcover change-driven addition to wood product pools' // &
            '(0 at all times except first timestep of year) ' // &
            '(per-area-gridcell; only makes sense with dov2xy=.false.)', &
            ptr_patch=this%dwt_wood_productc_gain_patch, default='inactive')

        this%dwt_slash_cflux_col(begc:endc) = spval
        call hist_addfld1d (fname='DWT_SLASH_CFLUX', units='gC/m^2/s', &
             avgflag='A', long_name='slash C flux to litter and CWD due to land use', &
             ptr_col=this%dwt_slash_cflux_col)

       this%dwt_frootc_to_litr_met_c_col(begc:endc,:) = spval
       call hist_addfld_decomp (fname='DWT_FROOTC_TO_LITR_MET_C', units='gC/m^2/s',  type2d='levdcmp', &
            avgflag='A', long_name='fine root to litter due to landcover change', &
            ptr_col=this%dwt_frootc_to_litr_met_c_col, default='inactive')

       this%dwt_frootc_to_litr_cel_c_col(begc:endc,:) = spval
       call hist_addfld_decomp (fname='DWT_FROOTC_TO_LITR_CEL_C', units='gC/m^2/s',  type2d='levdcmp', &
            avgflag='A', long_name='fine root to litter due to landcover change', &
            ptr_col=this%dwt_frootc_to_litr_cel_c_col, default='inactive')

       this%dwt_frootc_to_litr_lig_c_col(begc:endc,:) = spval
       call hist_addfld_decomp (fname='DWT_FROOTC_TO_LITR_LIG_C', units='gC/m^2/s',  type2d='levdcmp', &
            avgflag='A', long_name='fine root to litter due to landcover change', &
            ptr_col=this%dwt_frootc_to_litr_lig_c_col, default='inactive')

       this%dwt_livecrootc_to_cwdc_col(begc:endc,:) = spval
       call hist_addfld_decomp (fname='DWT_LIVECROOTC_TO_CWDC', units='gC/m^2/s',  type2d='levdcmp', &
            avgflag='A', long_name='live coarse root to CWD due to landcover change', &
            ptr_col=this%dwt_livecrootc_to_cwdc_col, default='inactive')

       this%dwt_deadcrootc_to_cwdc_col(begc:endc,:) = spval
       call hist_addfld_decomp (fname='DWT_DEADCROOTC_TO_CWDC', units='gC/m^2/s',  type2d='levdcmp', &
            avgflag='A', long_name='dead coarse root to CWD due to landcover change', &
            ptr_col=this%dwt_deadcrootc_to_cwdc_col, default='inactive')

       this%crop_seedc_to_leaf_patch(begp:endp) = spval
       call hist_addfld1d (fname='CROP_SEEDC_TO_LEAF', units='gC/m^2/s', &
            avgflag='A', long_name='crop seed source to leaf', &
            ptr_patch=this%crop_seedc_to_leaf_patch, default='inactive')

        this%sr_col(begc:endc) = spval
        call hist_addfld1d (fname='SR', units='gC/m^2/s', &
             avgflag='A', long_name='total soil respiration (HR + root resp)', &
             ptr_col=this%sr_col)

        this%er_col(begc:endc) = spval
        call hist_addfld1d (fname='ER', units='gC/m^2/s', &
             avgflag='A', long_name='total ecosystem respiration, autotrophic + heterotrophic', &
             ptr_col=this%er_col)

        this%litfire_col(begc:endc) = spval
        call hist_addfld1d (fname='LITFIRE', units='gC/m^2/s', &
             avgflag='A', long_name='litter fire losses', &
             ptr_col=this%litfire_col, default='inactive')

        this%somfire_col(begc:endc) = spval
        call hist_addfld1d (fname='SOMFIRE', units='gC/m^2/s', &
             avgflag='A', long_name='soil organic matter fire losses', &
             ptr_col=this%somfire_col, default='inactive')

        this%totfire_col(begc:endc) = spval
        call hist_addfld1d (fname='TOTFIRE', units='gC/m^2/s', &
             avgflag='A', long_name='total ecosystem fire losses', &
             ptr_col=this%totfire_col, default='inactive')

        this%fire_closs_col(begc:endc) = spval
        call hist_addfld1d (fname='COL_FIRE_CLOSS', units='gC/m^2/s', &
             avgflag='A', long_name='total column-level fire C loss for non-peat fires outside land-type converted region', &
             ptr_col=this%fire_closs_col)

        this%annsum_npp_patch(begp:endp) = spval
        call hist_addfld1d (fname='ANNSUM_NPP', units='gC/m^2/yr', &
             avgflag='A', long_name='annual sum of NPP', &
             ptr_patch=this%annsum_npp_patch, default='inactive')

        this%annsum_npp_col(begc:endc) = spval
        call hist_addfld1d (fname='CANNSUM_NPP', units='gC/m^2/s', &
             avgflag='A', long_name='annual sum of column-level NPP', &
             ptr_col=this%annsum_npp_col, default='inactive')

       this%nep_col(begc:endc) = spval
       call hist_addfld1d (fname='NEP', units='gC/m^2/s', &
            avgflag='A', long_name='net ecosystem production, excludes fire, landuse, and harvest flux, positive for sink', &
            ptr_col=this%nep_col)

       this%nbp_grc(begg:endg) = spval
       call hist_addfld1d (fname='NBP', units='gC/m^2/s', &
            avgflag='A', long_name='net biome production, includes fire, landuse,'&
            //' harvest and hrv_xsmrpool flux (latter smoothed over the year), positive for sink'&
            //' (same as net carbon exchange between land and atmosphere)', &
            ptr_gcell=this%nbp_grc)

       this%nee_grc(begg:endg) = spval
       call hist_addfld1d (fname='NEE', units='gC/m^2/s', &
            avgflag='A', long_name='net ecosystem exchange of carbon,'&
            //' includes fire and hrv_xsmrpool (latter smoothed over the year),'&
            //' excludes landuse and harvest flux, positive for source', &
            ptr_gcell=this%nee_grc)

       this%landuseflux_grc(begg:endg) = spval
       call hist_addfld1d (fname='LAND_USE_FLUX', units='gC/m^2/s', &
            avgflag='A', &
            long_name='total C emitted from land cover conversion (smoothed over the year)'&
            //' and wood and grain product pools (NOTE: not a net value)', &
            ptr_gcell=this%landuseflux_grc)

   end if
    !-------------------------------
    ! C13 flux variables - column 
    !-------------------------------

    if ( carbon_type == 'c13' ) then

       this%m_decomp_cpools_to_fire_col(begc:endc,:) = spval
       this%m_decomp_cpools_to_fire_vr_col(begc:endc,:,:) = spval
       do k = 1, ndecomp_pools
          if ( decomp_cascade_con%is_litter(k) .or. decomp_cascade_con%is_cwd(k) ) then
             data1dptr => this%m_decomp_cpools_to_fire_col(:,k)
             fieldname = 'C13_M_'//trim(decomp_cascade_con%decomp_pool_name_history(k))//'C_TO_FIRE'
             longname =  'C13 '//trim(decomp_cascade_con%decomp_pool_name_long(k))//' C fire loss'
             call hist_addfld1d (fname=fieldname, units='gC13/m^2',  &
                  avgflag='A', long_name=longname, &
                  ptr_col=data1dptr, default='inactive')

             if ( nlevdecomp_full > 1 ) then
                data2dptr => this%m_decomp_cpools_to_fire_vr_col(:,:,k)
                fieldname = 'C13_M_'//trim(decomp_cascade_con%decomp_pool_name_history(k))//'C_TO_FIRE'//trim(vr_suffix)
                longname =  'C13 '//trim(decomp_cascade_con%decomp_pool_name_long(k))//' C fire loss'
                call hist_addfld_decomp (fname=fieldname, units='gC13/m^3',  type2d='levdcmp', &
                     avgflag='A', long_name=longname, &
                     ptr_col=data2dptr, default='inactive')
             end if
          endif
       end do

       this%dwt_seedc_to_leaf_grc(begg:endg) = spval
       call hist_addfld1d (fname='C13_DWT_SEEDC_TO_LEAF', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 seed source to patch-level leaf', &
            ptr_gcell=this%dwt_seedc_to_leaf_grc, default='inactive')

       this%dwt_seedc_to_leaf_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_DWT_SEEDC_TO_LEAF_PATCH', units='gC13/m^2/s', &
            avgflag='A', &
            long_name='patch-level C13 seed source to patch-level leaf ' // &
            '(per-area-gridcell; only makes sense with dov2xy=.false.)', &
            ptr_patch=this%dwt_seedc_to_leaf_patch, default='inactive')

       this%dwt_seedc_to_deadstem_grc(begg:endg) = spval
       call hist_addfld1d (fname='C13_DWT_SEEDC_TO_DEADSTEM', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 seed source to patch-level deadstem', &
            ptr_gcell=this%dwt_seedc_to_deadstem_grc, default='inactive')

       this%dwt_seedc_to_deadstem_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_DWT_SEEDC_TO_DEADSTEM_PATCH', units='gC13/m^2/s', &
            avgflag='A', &
            long_name='patch-level C13 seed source to patch-level deadstem ' // &
            '(per-area-gridcell; only makes sense with dov2xy=.false.)', &
            ptr_patch=this%dwt_seedc_to_deadstem_patch, default='inactive')

       this%dwt_conv_cflux_grc(begg:endg) = spval
       call hist_addfld1d (fname='C13_DWT_CONV_CFLUX', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 conversion C flux (immediate loss to atm) ' // &
            '(0 at all times except first timestep of year)', &
            ptr_gcell=this%dwt_conv_cflux_grc, default='inactive')

       this%dwt_conv_cflux_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_DWT_CONV_CFLUX_PATCH', units='gC13/m^2/s', &
            avgflag='A', &
            long_name='patch-level C13 conversion C flux (immediate loss to atm) ' // &
            '(0 at all times except first timestep of year) ' // &
            '(per-area-gridcell; only makes sense with dov2xy=.false.)', &
            ptr_patch=this%dwt_conv_cflux_patch, default='inactive')

       this%dwt_conv_cflux_dribbled_grc(begg:endg) = spval
       call hist_addfld1d (fname='C13_DWT_CONV_CFLUX_DRIBBLED', units='gC13/m^2/s', &
            avgflag='A', &
            long_name='C13 conversion C flux (immediate loss to atm), dribbled throughout the year', &
            ptr_gcell=this%dwt_conv_cflux_dribbled_grc, default='inactive')

       this%dwt_slash_cflux_col(begc:endc) = spval
       call hist_addfld1d (fname='C13_DWT_SLASH_CFLUX', units='gC/m^2/s', &
            avgflag='A', long_name='C13 slash C flux to litter and CWD due to land use', &
            ptr_col=this%dwt_slash_cflux_col, default='inactive')

       this%dwt_frootc_to_litr_met_c_col(begc:endc,:) = spval
       call hist_addfld_decomp (fname='C13_DWT_FROOTC_TO_LITR_MET_C', units='gC13/m^2/s',  type2d='levdcmp', &
            avgflag='A', long_name='C13 fine root to litter due to landcover change', &
            ptr_col=this%dwt_frootc_to_litr_met_c_col, default='inactive')

       this%dwt_frootc_to_litr_cel_c_col(begc:endc,:) = spval
       call hist_addfld_decomp (fname='C13_DWT_FROOTC_TO_LITR_CEL_C', units='gC13/m^2/s',  type2d='levdcmp', &
            avgflag='A', long_name='C13 fine root to litter due to landcover change', &
            ptr_col=this%dwt_frootc_to_litr_cel_c_col, default='inactive')

       this%dwt_frootc_to_litr_lig_c_col(begc:endc,:) = spval
       call hist_addfld_decomp (fname='C13_DWT_FROOTC_TO_LITR_LIG_C', units='gC13/m^2/s',  type2d='levdcmp', &
            avgflag='A', long_name='C13 fine root to litter due to landcover change', &
            ptr_col=this%dwt_frootc_to_litr_lig_c_col, default='inactive')

       this%dwt_livecrootc_to_cwdc_col(begc:endc,:) = spval
       call hist_addfld_decomp (fname='C13_DWT_LIVECROOTC_TO_CWDC', units='gC13/m^2/s',  type2d='levdcmp', &
            avgflag='A', long_name='C13 live coarse root to CWD due to landcover change', &
            ptr_col=this%dwt_livecrootc_to_cwdc_col, default='inactive')

       this%dwt_deadcrootc_to_cwdc_col(begc:endc,:) = spval
       call hist_addfld_decomp (fname='C13_DWT_DEADCROOTC_TO_CWDC', units='gC13/m^2/s',  type2d='levdcmp', &
            avgflag='A', long_name='C13 dead coarse root to CWD due to landcover change', &
            ptr_col=this%dwt_deadcrootc_to_cwdc_col, default='inactive')

       this%crop_seedc_to_leaf_patch(begp:endp) = spval
       call hist_addfld1d (fname='C13_CROP_SEEDC_TO_LEAF', units='gC13/m^2/s', &
            avgflag='A', long_name='C13 crop seed source to leaf', &
            ptr_patch=this%crop_seedc_to_leaf_patch, default='inactive')

        this%sr_col(begc:endc) = spval
        call hist_addfld1d (fname='C13_SR', units='gC13/m^2/s', &
             avgflag='A', long_name='C13 total soil respiration (HR + root resp)', &
             ptr_col=this%sr_col, default='inactive')

        this%er_col(begc:endc) = spval
        call hist_addfld1d (fname='C13_ER', units='gC13/m^2/s', &
             avgflag='A', long_name='C13 total ecosystem respiration, autotrophic + heterotrophic', &
             ptr_col=this%er_col, default='inactive')

        this%litfire_col(begc:endc) = spval
        call hist_addfld1d (fname='C13_LITFIRE', units='gC13/m^2/s', &
             avgflag='A', long_name='C13 litter fire losses', &
             ptr_col=this%litfire_col, default='inactive')

        this%somfire_col(begc:endc) = spval
        call hist_addfld1d (fname='C13_SOMFIRE', units='gC13/m^2/s', &
             avgflag='A', long_name='C13 soil organic matter fire losses', &
             ptr_col=this%somfire_col, default='inactive')

        this%totfire_col(begc:endc) = spval
        call hist_addfld1d (fname='C13_TOTFIRE', units='gC13/m^2/s', &
             avgflag='A', long_name='C13 total ecosystem fire losses', &
             ptr_col=this%totfire_col, default='inactive')

        this%fire_closs_col(begc:endc) = spval
        call hist_addfld1d (fname='C13_COL_FIRE_CLOSS', units='gC13/m^2/s', &
             avgflag='A', long_name='C13 total column-level fire C loss', &
             ptr_col=this%fire_closs_col, default='inactive')

        this%nep_col(begc:endc) = spval
        call hist_addfld1d (fname='C13_NEP', units='gC13/m^2/s', &
             avgflag='A', long_name='C13 net ecosystem production, excludes fire flux, positive for sink', &
             ptr_col=this%nep_col, default='inactive')

        this%nee_grc(begg:endg) = spval
        call hist_addfld1d (fname='C13_NEE', units='gC13/m^2/s', &
             avgflag='A', long_name='C13 net ecosystem exchange of carbon, includes fire flux, positive for source', &
             ptr_gcell=this%nee_grc, default='inactive')

        this%nbp_grc(begg:endg) = spval
        call hist_addfld1d (fname='C13_NBP', units='gC13/m^2/s', &
             avgflag='A', long_name='C13 net biome production, includes fire, landuse,'&
             //' harvest and hrv_xsmrpool flux (latter smoothed over the year), positive for sink'&
             //' (same as net carbon exchange between land and atmosphere)', &
             ptr_gcell=this%nbp_grc)

    endif

    !-------------------------------
    ! C14 flux variables - column 
    !-------------------------------

    if (carbon_type == 'c14') then

       this%m_decomp_cpools_to_fire_col(begc:endc,:)      = spval
       this%m_decomp_cpools_to_fire_vr_col(begc:endc,:,:) = spval
       do k = 1, ndecomp_pools
          if ( decomp_cascade_con%is_litter(k) .or. decomp_cascade_con%is_cwd(k) ) then
             data1dptr => this%m_decomp_cpools_to_fire_col(:,k)
             fieldname = 'C14_M_'//trim(decomp_cascade_con%decomp_pool_name_history(k))//'C_TO_FIRE'
             longname =  'C14 '//trim(decomp_cascade_con%decomp_pool_name_long(k))//' C fire loss'
             call hist_addfld1d (fname=fieldname, units='gC14/m^2',  &
                  avgflag='A', long_name=longname, &
                  ptr_col=data1dptr, default='inactive')

             if ( nlevdecomp_full > 1 ) then
                data2dptr => this%m_decomp_cpools_to_fire_vr_col(:,:,k)
                fieldname = 'C14_M_'//trim(decomp_cascade_con%decomp_pool_name_history(k))//'C_TO_FIRE'//trim(vr_suffix)
                longname =  'C14 '//trim(decomp_cascade_con%decomp_pool_name_long(k))//' C fire loss'
                call hist_addfld_decomp (fname=fieldname, units='gC14/m^3',  type2d='levdcmp', &
                     avgflag='A', long_name=longname, &
                     ptr_col=data2dptr, default='inactive')
             end if
          endif
       end do

       this%dwt_seedc_to_leaf_grc(begg:endg) = spval
       call hist_addfld1d (fname='C14_DWT_SEEDC_TO_LEAF', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 seed source to patch-level leaf', &
            ptr_gcell=this%dwt_seedc_to_leaf_grc, default='inactive')

       this%dwt_seedc_to_leaf_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_DWT_SEEDC_TO_LEAF_PATCH', units='gC14/m^2/s', &
            avgflag='A', &
            long_name='patch-level C14 seed source to patch-level leaf ' // &
            '(per-area-gridcell; only makes sense with dov2xy=.false.)', &
            ptr_patch=this%dwt_seedc_to_leaf_patch, default='inactive')

       this%dwt_seedc_to_deadstem_grc(begg:endg) = spval
       call hist_addfld1d (fname='C14_DWT_SEEDC_TO_DEADSTEM', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 seed source to patch-level deadstem', &
            ptr_gcell=this%dwt_seedc_to_deadstem_grc, default='inactive')

       this%dwt_seedc_to_deadstem_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_DWT_SEEDC_TO_DEADSTEM_PATCH', units='gC14/m^2/s', &
            avgflag='A', &
            long_name='patch-level C14 seed source to patch-level deadstem ' // &
            '(per-area-gridcell; only makes sense with dov2xy=.false.)', &
            ptr_patch=this%dwt_seedc_to_deadstem_patch, default='inactive')

       this%dwt_conv_cflux_grc(begg:endg) = spval
       call hist_addfld1d (fname='C14_DWT_CONV_CFLUX', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 conversion C flux (immediate loss to atm) ' // &
            '(0 at all times except first timestep of year)', &
            ptr_gcell=this%dwt_conv_cflux_grc, default='inactive')

       this%dwt_conv_cflux_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_DWT_CONV_CFLUX_PATCH', units='gC14/m^2/s', &
            avgflag='A', &
            long_name='patch-level C14 conversion C flux (immediate loss to atm) ' // &
            '(0 at all times except first timestep of year) ' // &
            '(per-area-gridcell; only makes sense with dov2xy=.false.)', &
            ptr_patch=this%dwt_conv_cflux_patch, default='inactive')

       this%dwt_conv_cflux_dribbled_grc(begg:endg) = spval
       call hist_addfld1d (fname='C14_DWT_CONV_CFLUX_DRIBBLED', units='gC14/m^2/s', &
            avgflag='A', &
            long_name='C14 conversion C flux (immediate loss to atm), dribbled throughout the year', &
            ptr_gcell=this%dwt_conv_cflux_dribbled_grc, default='inactive')

       this%dwt_slash_cflux_col(begc:endc) = spval
       call hist_addfld1d (fname='C14_DWT_SLASH_CFLUX', units='gC/m^2/s', &
            avgflag='A', long_name='C14 slash C flux to litter and CWD due to land use', &
            ptr_col=this%dwt_slash_cflux_col, default='inactive')

       this%dwt_frootc_to_litr_met_c_col(begc:endc,:) = spval
       call hist_addfld_decomp (fname='C14_DWT_FROOTC_TO_LITR_MET_C', units='gC14/m^2/s',  type2d='levdcmp', &
            avgflag='A', long_name='C14 fine root to litter due to landcover change', &
            ptr_col=this%dwt_frootc_to_litr_met_c_col, default='inactive')

       this%dwt_frootc_to_litr_cel_c_col(begc:endc,:) = spval
       call hist_addfld_decomp (fname='C14_DWT_FROOTC_TO_LITR_CEL_C', units='gC14/m^2/s',  type2d='levdcmp', &
            avgflag='A', long_name='C14 fine root to litter due to landcover change', &
            ptr_col=this%dwt_frootc_to_litr_cel_c_col, default='inactive')

       this%dwt_frootc_to_litr_lig_c_col(begc:endc,:) = spval
       call hist_addfld_decomp (fname='C14_DWT_FROOTC_TO_LITR_LIG_C', units='gC14/m^2/s',  type2d='levdcmp', &
            avgflag='A', long_name='C14 fine root to litter due to landcover change', &
            ptr_col=this%dwt_frootc_to_litr_lig_c_col, default='inactive')

       this%dwt_livecrootc_to_cwdc_col(begc:endc,:) = spval
       call hist_addfld_decomp (fname='C14_DWT_LIVECROOTC_TO_CWDC', units='gC14/m^2/s',  type2d='levdcmp', &
            avgflag='A', long_name='C14 live coarse root to CWD due to landcover change', &
            ptr_col=this%dwt_livecrootc_to_cwdc_col, default='inactive')

       this%dwt_deadcrootc_to_cwdc_col(begc:endc,:) = spval
       call hist_addfld_decomp (fname='C14_DWT_DEADCROOTC_TO_CWDC', units='gC14/m^2/s',  type2d='levdcmp', &
            avgflag='A', long_name='C14 dead coarse root to CWD due to landcover change', &
            ptr_col=this%dwt_deadcrootc_to_cwdc_col, default='inactive')

       this%crop_seedc_to_leaf_patch(begp:endp) = spval
       call hist_addfld1d (fname='C14_CROP_SEEDC_TO_LEAF', units='gC14/m^2/s', &
            avgflag='A', long_name='C14 crop seed source to leaf', &
            ptr_patch=this%crop_seedc_to_leaf_patch, default='inactive')

        this%sr_col(begc:endc) = spval
        call hist_addfld1d (fname='C14_SR', units='gC14/m^2/s', &
             avgflag='A', long_name='C14 total soil respiration (HR + root resp)', &
             ptr_col=this%sr_col, default='inactive')

        this%er_col(begc:endc) = spval
        call hist_addfld1d (fname='C14_ER', units='gC14/m^2/s', &
             avgflag='A', long_name='C14 total ecosystem respiration, autotrophic + heterotrophic', &
             ptr_col=this%er_col, default='inactive')

        this%litfire_col(begc:endc) = spval
        call hist_addfld1d (fname='C14_LITFIRE', units='gC14/m^2/s', &
             avgflag='A', long_name='C14 litter fire losses', &
             ptr_col=this%litfire_col, default='inactive')

        this%somfire_col(begc:endc) = spval
        call hist_addfld1d (fname='C14_SOMFIRE', units='gC14/m^2/s', &
             avgflag='A', long_name='C14 soil organic matter fire losses', &
             ptr_col=this%somfire_col, default='inactive')

        this%totfire_col(begc:endc) = spval
        call hist_addfld1d (fname='C14_TOTFIRE', units='gC14/m^2/s', &
             avgflag='A', long_name='C14 total ecosystem fire losses', &
             ptr_col=this%totfire_col, default='inactive')

        this%fire_closs_col(begc:endc) = spval
        call hist_addfld1d (fname='C14_COL_FIRE_CLOSS', units='gC14/m^2/s', &
             avgflag='A', long_name='C14 total column-level fire C loss', &
             ptr_col=this%fire_closs_col, default='inactive')

        this%nep_col(begc:endc) = spval
        call hist_addfld1d (fname='C14_NEP', units='gC14/m^2/s', &
             avgflag='A', long_name='C14 net ecosystem production, excludes fire flux, positive for sink', &
             ptr_col=this%nep_col, default='inactive')

        this%nee_grc(begg:endg) = spval
        call hist_addfld1d (fname='C14_NEE', units='gC14/m^2/s', &
             avgflag='A', long_name='C14 net ecosystem exchange of carbon, includes fire flux, positive for source', &
             ptr_gcell=this%nee_grc, default='inactive')

        this%nbp_grc(begg:endg) = spval
        call hist_addfld1d (fname='C14_NBP', units='gC13/m^2/s', &
             avgflag='A', long_name='C14 net biome production, includes fire, landuse,'&
             //' harvest and hrv_xsmrpool flux (latter smoothed over the year), positive for sink'&
             //' (same as net carbon exchange between land and atmosphere)', &
             ptr_gcell=this%nbp_grc)

    endif

  end subroutine InitHistory

  !-----------------------------------------------------------------------
  subroutine InitCold(this, bounds)
    !
    ! !ARGUMENTS:
    class(cnveg_carbonflux_type) :: this
    type(bounds_type), intent(in) :: bounds  
    !
    ! !LOCAL VARIABLES:
    integer :: p, c, l, j
    integer :: fc                                        ! filter index
    integer :: num_special_col                           ! number of good values in special_col filter
    integer :: num_special_patch                         ! number of good values in special_patch filter
    integer :: special_col(bounds%endc-bounds%begc+1)    ! special landunit filter - columns
    integer :: special_patch(bounds%endp-bounds%begp+1)  ! special landunit filter - patches
    !-----------------------------------------------------------------------

    ! Set column filters

    num_special_col = 0
    do c = bounds%begc, bounds%endc
       l = col%landunit(c)
       if (lun%ifspecial(l)) then
          num_special_col = num_special_col + 1
          special_col(num_special_col) = c
       end if
    end do

    ! Set patch filters

    num_special_patch = 0
    do p = bounds%begp,bounds%endp
       l = patch%landunit(p)

       if (lun%ifspecial(l)) then
          num_special_patch = num_special_patch + 1
          special_patch(num_special_patch) = p
       end if
    end do

    do p = bounds%begp,bounds%endp
       l = patch%landunit(p)
       this%gpp_before_downreg_patch(p)       = 0._r8
       ! WW should these be considered spval or 0?
       if (lun%ifspecial(l)) then
          this%availc_patch(p)                = spval
          this%xsmrpool_recover_patch(p)      = spval
          this%excess_cflux_patch(p)          = spval
          this%plant_calloc_patch(p)          = spval
          this%prev_leafc_to_litter_patch(p)  = spval
          this%prev_frootc_to_litter_patch(p) = spval
          this%leafc_to_litter_fun_patch(p)   = spval
          if ( use_c13 ) then
             this%xsmrpool_c13ratio_patch(p)  = spval
          endif
       end if
       if (lun%itype(l) == istsoil .or. lun%itype(l) == istcrop) then
          this%availc_patch(p)                = 0._r8
          this%xsmrpool_recover_patch(p)      = 0._r8
          this%excess_cflux_patch(p)          = 0._r8
          this%prev_leafc_to_litter_patch(p)  = 0._r8
          this%leafc_to_litter_fun_patch(p)   = 0._r8 
          this%prev_frootc_to_litter_patch(p) = 0._r8
          this%plant_calloc_patch(p)          = 0._r8
       end if
    end do

    do c = bounds%begc, bounds%endc
       l = col%landunit(c)

       ! also initialize dynamic landcover fluxes so that they have
       ! real values on first timestep, prior to calling pftdyn_cnbal
       if (lun%itype(l) == istsoil .or. lun%itype(l) == istcrop) then
          this%dwt_slash_cflux_col(c) = 0._r8
          do j = 1, nlevdecomp_full
             this%dwt_frootc_to_litr_met_c_col(c,j) = 0._r8
             this%dwt_frootc_to_litr_cel_c_col(c,j) = 0._r8
             this%dwt_frootc_to_litr_lig_c_col(c,j) = 0._r8
             this%dwt_livecrootc_to_cwdc_col(c,j)   = 0._r8
             this%dwt_deadcrootc_to_cwdc_col(c,j)   = 0._r8
          end do
       end if
    end do

    do p = bounds%begp,bounds%endp
       l = patch%landunit(p)

       this%gpp_patch(p)                 = 0._r8
       if (lun%ifspecial(l)) then
          this%tempsum_npp_patch(p)      = spval
          this%annsum_npp_patch(p)       = spval
          this%tempsum_litfall_patch(p)  = spval
          this%annsum_litfall_patch(p)   = spval
       end if
       if (lun%itype(l) == istsoil .or. lun%itype(l) == istcrop) then
          this%tempsum_npp_patch(p)      = 0._r8
          this%annsum_npp_patch(p)       = 0._r8
          this%tempsum_litfall_patch(p)  = 0._r8
          this%annsum_litfall_patch(p)   = 0._r8
       end if
    end do

    do c = bounds%begc, bounds%endc
       l = col%landunit(c)

       if (lun%ifspecial(l)) then
          this%annsum_npp_col(c) = spval
       end if

       ! also initialize dynamic landcover fluxes so that they have
       ! real values on first timestep, prior to calling pftdyn_cnbal
       if (lun%itype(l) == istsoil .or. lun%itype(l) == istcrop) then
          this%annsum_npp_col(c) = 0._r8   
       end if
    end do

    ! initialize fields for special filters

    call this%SetValues (&
         num_patch=num_special_patch, filter_patch=special_patch, value_patch=0._r8, &
         num_column=num_special_col, filter_column=special_col, value_column=0._r8)

  end subroutine InitCold

  !-----------------------------------------------------------------------
  subroutine Restart ( this, bounds, ncid, flag, carbon_type )
    !
    ! !DESCRIPTION: 
    ! Read/write CN restart data for carbon fluxes
    !
    ! !USES:
    use ncdio_pio, only : file_desc_t
    !
    ! !ARGUMENTS:
    class (cnveg_carbonflux_type) :: this
    type(bounds_type) , intent(in)    :: bounds 
    type(file_desc_t) , intent(inout) :: ncid   ! netcdf id
    character(len=*)  , intent(in)    :: flag   !'read' or 'write'
    character(len=*)  , intent(in)    :: carbon_type ! 'c12' or 'c13' or 'c14'
    !------------------------------------------------------------------------

    if (carbon_type == 'c12') then
       call this%RestartBulkOnly(bounds, ncid, flag)
    end if

    call this%RestartAllIsotopes(bounds, ncid, flag)

  end subroutine Restart


  !-----------------------------------------------------------------------
  subroutine RestartBulkOnly ( this, bounds, ncid, flag )
    !
    ! !DESCRIPTION: 
    ! Read/write CN restart data for carbon fluxes - fields only present for bulk C
    !
    ! !USES:
    use shr_infnan_mod   , only : isnan => shr_infnan_isnan, nan => shr_infnan_nan, assignment(=)
    use clm_time_manager , only : is_restart
    use clm_varcon       , only : c13ratio, c14ratio
    use clm_varctl       , only : use_lch4
    use CNSharedParamsMod, only : use_fun
    use restUtilMod
    use ncdio_pio
    !
    ! !ARGUMENTS:
    class (cnveg_carbonflux_type) :: this
    type(bounds_type) , intent(in)    :: bounds 
    type(file_desc_t) , intent(inout) :: ncid   ! netcdf id
    character(len=*)  , intent(in)    :: flag   !'read' or 'write'
    !
    ! !LOCAL VARIABLES:
    integer :: j,c ! indices
    logical :: readvar      ! determine if variable is on initial file
    !------------------------------------------------------------------------

    if (use_crop) then

       call restartvar(ncid=ncid, flag=flag,  varname='grainc_xfer_to_grainc', xtype=ncd_double,  &
            dim1name='pft', &
            long_name='grain C growth from storage', units='gC/m2/s', &
            interpinic_flag='interp', readvar=readvar, data=this%grainc_xfer_to_grainc_patch)

       call restartvar(ncid=ncid, flag=flag,  varname='livestemc_to_litter', xtype=ncd_double,  &
            dim1name='pft', &
            long_name='live stem C litterfall', units='gC/m2/s', &
            interpinic_flag='interp', readvar=readvar, data=this%livestemc_to_litter_patch)

       call restartvar(ncid=ncid, flag=flag,  varname='grainc_to_food', xtype=ncd_double,  &
            dim1name='pft', &
            long_name='grain C to food', units='gC/m2/s', &
            interpinic_flag='interp', readvar=readvar, data=this%grainc_to_food_patch)

       call restartvar(ncid=ncid, flag=flag,  varname='cpool_to_grainc', xtype=ncd_double,  &
            dim1name='pft', &
            long_name='allocation to grain C', units='gC/m2/s', &
            interpinic_flag='interp', readvar=readvar, data=this%cpool_to_grainc_patch)

       call restartvar(ncid=ncid, flag=flag,  varname='cpool_to_grainc_storage', xtype=ncd_double,  &
            dim1name='pft', &
            long_name='allocation to grain C storage', units='gC/m2/s', &
            interpinic_flag='interp', readvar=readvar, data=this%cpool_to_grainc_storage_patch)

       call restartvar(ncid=ncid, flag=flag,  varname='cpool_grain_gr', xtype=ncd_double,  &
            dim1name='pft', &
            long_name='grain growth respiration', units='gC/m2/s', &
            interpinic_flag='interp', readvar=readvar, data=this%cpool_grain_gr_patch)

       call restartvar(ncid=ncid, flag=flag,  varname='cpool_grain_storage_gr', xtype=ncd_double,  &
            dim1name='pft', &
            long_name='grain growth respiration to storage', units='gC/m2/s', &
            interpinic_flag='interp', readvar=readvar, data=this%cpool_grain_storage_gr_patch)

       call restartvar(ncid=ncid, flag=flag,  varname='transfer_grain_gr', xtype=ncd_double,  &
            dim1name='pft', &
            long_name='grain growth respiration from storage', units='gC/m2/s', &
            interpinic_flag='interp', readvar=readvar, data=this%transfer_grain_gr_patch)

       call restartvar(ncid=ncid, flag=flag,  varname='grainc_storage_to_xfer', xtype=ncd_double,  &
            dim1name='pft', &
            long_name='grain C shift storage to transfer', units='gC/m2/s', &
            interpinic_flag='interp', readvar=readvar, data=this%grainc_storage_to_xfer_patch)

    end if

    call restartvar(ncid=ncid, flag=flag, varname='gpp_pepv', xtype=ncd_double,  &
         dim1name='pft', &
         long_name='', units='', &
         interpinic_flag='interp', readvar=readvar, data=this%gpp_before_downreg_patch) 

    call restartvar(ncid=ncid, flag=flag, varname='availc', xtype=ncd_double,  &
         dim1name='pft', &
         long_name='', units='', &
         interpinic_flag='interp', readvar=readvar, data=this%availc_patch) 

    call restartvar(ncid=ncid, flag=flag, varname='xsmrpool_recover', xtype=ncd_double,  &
         dim1name='pft', &
         long_name='', units='', &
         interpinic_flag='interp', readvar=readvar, data=this%xsmrpool_recover_patch) 

    call restartvar(ncid=ncid, flag=flag, varname='plant_calloc', xtype=ncd_double,  &
         dim1name='pft', &
         long_name='', units='', &
         interpinic_flag='interp', readvar=readvar, data=this%plant_calloc_patch) 

    call restartvar(ncid=ncid, flag=flag, varname='excess_cflux', xtype=ncd_double,  &
         dim1name='pft', &
         long_name='', units='', &
         interpinic_flag='interp', readvar=readvar, data=this%excess_cflux_patch) 

    call restartvar(ncid=ncid, flag=flag, varname='prev_leafc_to_litter', xtype=ncd_double,  &
         dim1name='pft', &
         long_name='', units='', &
         interpinic_flag='interp', readvar=readvar, data=this%prev_leafc_to_litter_patch) 

    call restartvar(ncid=ncid, flag=flag, varname='prev_frootc_to_litter', xtype=ncd_double,  &
         dim1name='pft', &
         long_name='', units='', &
         interpinic_flag='interp', readvar=readvar, data=this%prev_frootc_to_litter_patch) 

    call restartvar(ncid=ncid, flag=flag, varname='tempsum_npp', xtype=ncd_double,  &
         dim1name='pft', &
         long_name='', units='', &
         interpinic_flag='interp', readvar=readvar, data=this%tempsum_npp_patch) 
 
    call restartvar(ncid=ncid, flag=flag, varname='annsum_npp', xtype=ncd_double,  &
         dim1name='pft', &
         long_name='', units='', &
         interpinic_flag='interp', readvar=readvar, data=this%annsum_npp_patch) 

    call restartvar(ncid=ncid, flag=flag, varname='col_lag_npp', xtype=ncd_double,  &
         dim1name='column', &
         long_name='', units='', &
         interpinic_flag='interp', readvar=readvar, data=this%lag_npp_col) 

    call restartvar(ncid=ncid, flag=flag, varname='cannsum_npp', xtype=ncd_double,  &
         dim1name='column', &
         long_name='', units='', &
         interpinic_flag='interp', readvar=readvar, data=this%annsum_npp_col) 

    call restartvar(ncid=ncid, flag=flag, varname='tempsum_litfall', xtype=ncd_double,  &
         dim1name='pft', &
         long_name='', units='', &
         interpinic_flag='interp', readvar=readvar, data=this%tempsum_litfall_patch)

    call restartvar(ncid=ncid, flag=flag, varname='annsum_litfall', xtype=ncd_double,  &
         dim1name='pft', &
         long_name='', units='', &
         interpinic_flag='interp', readvar=readvar, data=this%annsum_litfall_patch)

    if ( use_fun ) then
       call restartvar(ncid=ncid, flag=flag, varname='leafc_to_litter_fun', xtype=ncd_double,  &
            dim1name='pft', &
            long_name='', units='', &
            interpinic_flag='interp', readvar=readvar, data=this%leafc_to_litter_fun_patch)
        ! BACKWARDS_COMPATIBILITY(wrw, 2018-06-28) re. issue #426
        call set_missing_vals_to_constant(this%leafc_to_litter_fun_patch, 0._r8)
    end if

  end subroutine RestartBulkOnly


  !-----------------------------------------------------------------------
  subroutine RestartAllIsotopes ( this, bounds, ncid, flag )
    !
    ! !DESCRIPTION: 
    ! Read/write CN restart data for carbon fluxes - fields present for both bulk C and isotopes
    !
    ! !USES:
    use ncdio_pio, only : file_desc_t
    !
    ! !ARGUMENTS:
    class (cnveg_carbonflux_type) :: this
    type(bounds_type) , intent(in)    :: bounds 
    type(file_desc_t) , intent(inout) :: ncid   ! netcdf id
    character(len=*)  , intent(in)    :: flag   !'read' or 'write'
    !-----------------------------------------------------------------------

    call this%dwt_conv_cflux_dribbler%Restart(bounds, ncid, flag)
    call this%hrv_xsmrpool_to_atm_dribbler%Restart(bounds, ncid, flag)

  end subroutine RestartAllIsotopes

  !-----------------------------------------------------------------------
  subroutine SetValues ( this, &
       num_patch, filter_patch, value_patch, &
       num_column, filter_column, value_column)
    !
    ! !DESCRIPTION:
    ! Set carbon state fluxes
    !
    ! !ARGUMENTS:
    class (cnveg_carbonflux_type) :: this
    integer , intent(in) :: num_patch
    integer , intent(in) :: filter_patch(:)
    real(r8), intent(in) :: value_patch
    integer , intent(in) :: num_column
    integer , intent(in) :: filter_column(:)
    real(r8), intent(in) :: value_column
    !
    ! !LOCAL VARIABLES:
    integer :: fi,i     ! loop index
    integer :: j,k,l    ! indices
    !------------------------------------------------------------------------

    do fi = 1,num_patch
       i = filter_patch(fi)

       this%m_leafc_to_litter_patch(i)                   = value_patch
       this%m_frootc_to_litter_patch(i)                  = value_patch
       this%m_leafc_storage_to_litter_patch(i)           = value_patch
       this%m_frootc_storage_to_litter_patch(i)          = value_patch
       this%m_livestemc_storage_to_litter_patch(i)       = value_patch
       this%m_deadstemc_storage_to_litter_patch(i)       = value_patch
       this%m_livecrootc_storage_to_litter_patch(i)      = value_patch
       this%m_deadcrootc_storage_to_litter_patch(i)      = value_patch
       this%m_leafc_xfer_to_litter_patch(i)              = value_patch
       this%m_frootc_xfer_to_litter_patch(i)             = value_patch
       this%m_livestemc_xfer_to_litter_patch(i)          = value_patch
       this%m_deadstemc_xfer_to_litter_patch(i)          = value_patch
       this%m_livecrootc_xfer_to_litter_patch(i)         = value_patch
       this%m_deadcrootc_xfer_to_litter_patch(i)         = value_patch
       this%m_livestemc_to_litter_patch(i)               = value_patch
       this%m_deadstemc_to_litter_patch(i)               = value_patch
       this%m_livecrootc_to_litter_patch(i)              = value_patch
       this%m_deadcrootc_to_litter_patch(i)              = value_patch
       this%m_gresp_storage_to_litter_patch(i)           = value_patch
       this%m_gresp_xfer_to_litter_patch(i)              = value_patch
       this%hrv_leafc_to_litter_patch(i)                 = value_patch             
       this%hrv_leafc_storage_to_litter_patch(i)         = value_patch     
       this%hrv_leafc_xfer_to_litter_patch(i)            = value_patch        
       this%hrv_frootc_to_litter_patch(i)                = value_patch            
       this%hrv_frootc_storage_to_litter_patch(i)        = value_patch    
       this%hrv_frootc_xfer_to_litter_patch(i)           = value_patch       
       this%hrv_livestemc_to_litter_patch(i)             = value_patch         
       this%hrv_livestemc_storage_to_litter_patch(i)     = value_patch 
       this%hrv_livestemc_xfer_to_litter_patch(i)        = value_patch    
       this%hrv_deadstemc_storage_to_litter_patch(i)     = value_patch 
       this%hrv_deadstemc_xfer_to_litter_patch(i)        = value_patch    
       this%hrv_livecrootc_to_litter_patch(i)            = value_patch        
       this%hrv_livecrootc_storage_to_litter_patch(i)    = value_patch
       this%hrv_livecrootc_xfer_to_litter_patch(i)       = value_patch   
       this%hrv_deadcrootc_to_litter_patch(i)            = value_patch        
       this%hrv_deadcrootc_storage_to_litter_patch(i)    = value_patch
       this%hrv_deadcrootc_xfer_to_litter_patch(i)       = value_patch   
       this%hrv_gresp_storage_to_litter_patch(i)         = value_patch     
       this%hrv_gresp_xfer_to_litter_patch(i)            = value_patch        
       this%hrv_xsmrpool_to_atm_patch(i)                 = value_patch

       this%m_leafc_to_fire_patch(i)                     = value_patch
       this%m_leafc_storage_to_fire_patch(i)             = value_patch
       this%m_leafc_xfer_to_fire_patch(i)                = value_patch
       this%m_livestemc_to_fire_patch(i)                 = value_patch
       this%m_livestemc_storage_to_fire_patch(i)         = value_patch
       this%m_livestemc_xfer_to_fire_patch(i)            = value_patch
       this%m_deadstemc_to_fire_patch(i)                 = value_patch
       this%m_deadstemc_storage_to_fire_patch(i)         = value_patch
       this%m_deadstemc_xfer_to_fire_patch(i)            = value_patch
       this%m_frootc_to_fire_patch(i)                    = value_patch
       this%m_frootc_storage_to_fire_patch(i)            = value_patch
       this%m_frootc_xfer_to_fire_patch(i)               = value_patch
       this%m_livecrootc_to_fire_patch(i)                = value_patch
       this%m_livecrootc_storage_to_fire_patch(i)        = value_patch
       this%m_livecrootc_xfer_to_fire_patch(i)           = value_patch
       this%m_deadcrootc_to_fire_patch(i)                = value_patch
       this%m_deadcrootc_storage_to_fire_patch(i)        = value_patch
       this%m_deadcrootc_xfer_to_fire_patch(i)           = value_patch
       this%m_gresp_storage_to_fire_patch(i)             = value_patch
       this%m_gresp_xfer_to_fire_patch(i)                = value_patch

       this%m_leafc_to_litter_fire_patch(i)              = value_patch
       this%m_leafc_storage_to_litter_fire_patch(i)      = value_patch
       this%m_leafc_xfer_to_litter_fire_patch(i)         = value_patch
       this%m_livestemc_to_litter_fire_patch(i)          = value_patch
       this%m_livestemc_storage_to_litter_fire_patch(i)  = value_patch
       this%m_livestemc_xfer_to_litter_fire_patch(i)     = value_patch
       this%m_livestemc_to_deadstemc_fire_patch(i)       = value_patch
       this%m_deadstemc_to_litter_fire_patch(i)          = value_patch
       this%m_deadstemc_storage_to_litter_fire_patch(i)  = value_patch
       this%m_deadstemc_xfer_to_litter_fire_patch(i)     = value_patch
       this%m_frootc_to_litter_fire_patch(i)             = value_patch
       this%m_frootc_storage_to_litter_fire_patch(i)     = value_patch
       this%m_frootc_xfer_to_litter_fire_patch(i)        = value_patch
       this%m_livecrootc_to_litter_fire_patch(i)         = value_patch
       this%m_livecrootc_storage_to_litter_fire_patch(i) = value_patch
       this%m_livecrootc_xfer_to_litter_fire_patch(i)    = value_patch
       this%m_livecrootc_to_deadcrootc_fire_patch(i)     = value_patch
       this%m_deadcrootc_to_litter_fire_patch(i)         = value_patch
       this%m_deadcrootc_storage_to_litter_fire_patch(i) = value_patch
       this%m_deadcrootc_xfer_to_litter_fire_patch(i)    = value_patch
       this%m_gresp_storage_to_litter_fire_patch(i)      = value_patch
       this%m_gresp_xfer_to_litter_fire_patch(i)         = value_patch

       this%leafc_xfer_to_leafc_patch(i)                 = value_patch
       this%frootc_xfer_to_frootc_patch(i)               = value_patch
       this%livestemc_xfer_to_livestemc_patch(i)         = value_patch
       this%deadstemc_xfer_to_deadstemc_patch(i)         = value_patch
       this%livecrootc_xfer_to_livecrootc_patch(i)       = value_patch
       this%deadcrootc_xfer_to_deadcrootc_patch(i)       = value_patch
       this%leafc_to_litter_patch(i)                     = value_patch
       this%frootc_to_litter_patch(i)                    = value_patch
       this%cpool_to_resp_patch(i)                       = value_patch
       this%cpool_to_leafc_resp_patch(i)                 = value_patch
       this%cpool_to_leafc_storage_resp_patch(i)         = value_patch
       this%cpool_to_frootc_resp_patch(i)                = value_patch
       this%cpool_to_frootc_storage_resp_patch(i)        = value_patch
       this%cpool_to_livecrootc_resp_patch(i)            = value_patch
       this%cpool_to_livecrootc_storage_resp_patch(i)    = value_patch
       this%cpool_to_livestemc_resp_patch(i)             = value_patch
       this%cpool_to_livestemc_storage_resp_patch(i)     = value_patch
       this%leaf_mr_patch(i)                             = value_patch
       this%froot_mr_patch(i)                            = value_patch
       this%livestem_mr_patch(i)                         = value_patch
       this%livecroot_mr_patch(i)                        = value_patch
       this%grain_mr_patch(i)                            = value_patch
       this%leaf_curmr_patch(i)                          = value_patch
       this%froot_curmr_patch(i)                         = value_patch
       this%livestem_curmr_patch(i)                      = value_patch
       this%livecroot_curmr_patch(i)                     = value_patch
       this%grain_curmr_patch(i)                         = value_patch
       this%leaf_xsmr_patch(i)                           = value_patch
       this%froot_xsmr_patch(i)                          = value_patch
       this%livestem_xsmr_patch(i)                       = value_patch
       this%livecroot_xsmr_patch(i)                      = value_patch
       this%grain_xsmr_patch(i)                          = value_patch
       this%psnsun_to_cpool_patch(i)                     = value_patch
       this%psnshade_to_cpool_patch(i)                   = value_patch
       this%cpool_to_xsmrpool_patch(i)                   = value_patch
       this%cpool_to_leafc_patch(i)                      = value_patch
       this%cpool_to_leafc_storage_patch(i)              = value_patch
       this%cpool_to_frootc_patch(i)                     = value_patch
       this%cpool_to_frootc_storage_patch(i)             = value_patch
       this%cpool_to_livestemc_patch(i)                  = value_patch
       this%cpool_to_livestemc_storage_patch(i)          = value_patch
       this%cpool_to_deadstemc_patch(i)                  = value_patch
       this%cpool_to_deadstemc_storage_patch(i)          = value_patch
       this%cpool_to_livecrootc_patch(i)                 = value_patch
       this%cpool_to_livecrootc_storage_patch(i)         = value_patch
       this%cpool_to_deadcrootc_patch(i)                 = value_patch
       this%cpool_to_deadcrootc_storage_patch(i)         = value_patch
       this%cpool_to_gresp_storage_patch(i)              = value_patch
       this%cpool_leaf_gr_patch(i)                       = value_patch
       this%cpool_leaf_storage_gr_patch(i)               = value_patch
       this%transfer_leaf_gr_patch(i)                    = value_patch
       this%cpool_froot_gr_patch(i)                      = value_patch
       this%cpool_froot_storage_gr_patch(i)              = value_patch
       this%transfer_froot_gr_patch(i)                   = value_patch
       this%cpool_livestem_gr_patch(i)                   = value_patch
       this%cpool_livestem_storage_gr_patch(i)           = value_patch
       this%transfer_livestem_gr_patch(i)                = value_patch
       this%cpool_deadstem_gr_patch(i)                   = value_patch
       this%cpool_deadstem_storage_gr_patch(i)           = value_patch
       this%transfer_deadstem_gr_patch(i)                = value_patch
       this%cpool_livecroot_gr_patch(i)                  = value_patch
       this%cpool_livecroot_storage_gr_patch(i)          = value_patch
       this%transfer_livecroot_gr_patch(i)               = value_patch
       this%cpool_deadcroot_gr_patch(i)                  = value_patch
       this%cpool_deadcroot_storage_gr_patch(i)          = value_patch
       this%transfer_deadcroot_gr_patch(i)               = value_patch
       this%leafc_storage_to_xfer_patch(i)               = value_patch
       this%frootc_storage_to_xfer_patch(i)              = value_patch
       this%livestemc_storage_to_xfer_patch(i)           = value_patch
       this%deadstemc_storage_to_xfer_patch(i)           = value_patch
       this%livecrootc_storage_to_xfer_patch(i)          = value_patch
       this%deadcrootc_storage_to_xfer_patch(i)          = value_patch
       this%gresp_storage_to_xfer_patch(i)               = value_patch
       this%livestemc_to_deadstemc_patch(i)              = value_patch
       this%livecrootc_to_deadcrootc_patch(i)            = value_patch

       this%current_gr_patch(i)                          = value_patch
       this%transfer_gr_patch(i)                         = value_patch
       this%storage_gr_patch(i)                          = value_patch
       this%frootc_alloc_patch(i)                        = value_patch
       this%frootc_loss_patch(i)                         = value_patch
       this%leafc_alloc_patch(i)                         = value_patch
       this%leafc_loss_patch(i)                          = value_patch
       this%woodc_alloc_patch(i)                         = value_patch
       this%woodc_loss_patch(i)                          = value_patch

       this%crop_seedc_to_leaf_patch(i)                  = value_patch
       this%grainc_to_cropprodc_patch(i)                 = value_patch
    end do

    if ( use_crop )then
       do fi = 1,num_patch
          i = filter_patch(fi)
          this%xsmrpool_to_atm_patch(i)         = value_patch
          this%livestemc_to_litter_patch(i)     = value_patch
          this%grainc_to_food_patch(i)          = value_patch
          this%grainc_to_seed_patch(i)          = value_patch
          this%grainc_xfer_to_grainc_patch(i)   = value_patch
          this%cpool_to_grainc_patch(i)         = value_patch
          this%cpool_to_grainc_storage_patch(i) = value_patch
          this%cpool_grain_gr_patch(i)          = value_patch
          this%cpool_grain_storage_gr_patch(i)  = value_patch
          this%transfer_grain_gr_patch(i)       = value_patch
          this%grainc_storage_to_xfer_patch(i)  = value_patch
       end do
    end if

    do j = 1, nlevdecomp_full
       do fi = 1,num_column
          i = filter_column(fi)

          this%phenology_c_to_litr_met_c_col(i,j)     = value_column
          this%phenology_c_to_litr_cel_c_col(i,j)     = value_column
          this%phenology_c_to_litr_lig_c_col(i,j)     = value_column

          this%gap_mortality_c_to_litr_met_c_col(i,j) = value_column
          this%gap_mortality_c_to_litr_cel_c_col(i,j) = value_column
          this%gap_mortality_c_to_litr_lig_c_col(i,j) = value_column
          this%gap_mortality_c_to_cwdc_col(i,j)       = value_column

          this%fire_mortality_c_to_cwdc_col(i,j)      = value_column
          this%m_c_to_litr_met_fire_col(i,j)          = value_column
          this%m_c_to_litr_cel_fire_col(i,j)          = value_column  
          this%m_c_to_litr_lig_fire_col(i,j)          = value_column

          this%harvest_c_to_litr_met_c_col(i,j)       = value_column             
          this%harvest_c_to_litr_cel_c_col(i,j)       = value_column             
          this%harvest_c_to_litr_lig_c_col(i,j)       = value_column             
          this%harvest_c_to_cwdc_col(i,j)             = value_column          

       end do
    end do

    do k = 1, ndecomp_pools
       do j = 1, nlevdecomp_full
          do fi = 1,num_column
             i = filter_column(fi)
             this%m_decomp_cpools_to_fire_vr_col(i,j,k) = value_column
          end do
       end do
    end do

    do k = 1, ndecomp_pools
       do fi = 1,num_column
          i = filter_column(fi)
          this%m_decomp_cpools_to_fire_col(i,k) = value_column
       end do
    end do

    do fi = 1,num_column
       i = filter_column(fi)

       this%grainc_to_cropprodc_col(i)       = value_column
       this%cwdc_hr_col(i)                   = value_column
       this%cwdc_loss_col(i)                 = value_column
       this%litterc_loss_col(i)              = value_column

    end do

    do fi = 1,num_patch
       i = filter_patch(fi)

       this%gpp_patch(i)           = value_patch
       this%mr_patch(i)            = value_patch
       this%gr_patch(i)            = value_patch
       this%ar_patch(i)            = value_patch
       this%rr_patch(i)            = value_patch 
       this%npp_patch(i)           = value_patch 
       this%agnpp_patch(i)         = value_patch
       this%bgnpp_patch(i)         = value_patch
       this%litfall_patch(i)       = value_patch
       this%wood_harvestc_patch(i) = value_patch
       this%slash_harvestc_patch(i) = value_patch
       this%cinputs_patch(i)       = value_patch
       this%coutputs_patch(i)      = value_patch
       this%fire_closs_patch(i)    = value_patch
       this%npp_Nactive_patch(i)     = value_patch
       this%npp_burnedoff_patch(i)     = value_patch
       this%npp_Nnonmyc_patch(i)     = value_patch
       this%npp_Nam_patch(i)         = value_patch
       this%npp_Necm_patch(i)        = value_patch
       this%npp_Nactive_no3_patch(i) = value_patch
       this%npp_Nactive_nh4_patch(i) = value_patch
       this%npp_Nnonmyc_no3_patch(i) = value_patch
       this%npp_Nnonmyc_nh4_patch(i) = value_patch
       this%npp_Nam_no3_patch(i)     = value_patch
       this%npp_Nam_nh4_patch(i)     = value_patch
       this%npp_Necm_no3_patch(i)    = value_patch
       this%npp_Necm_nh4_patch(i)    = value_patch
       this%npp_Nfix_patch(i)        = value_patch
       this%npp_Nretrans_patch(i)    = value_patch
       this%npp_Nuptake_patch(i)     = value_patch
       this%npp_growth_patch(i)      = value_patch
       this%leafc_change_patch(i)    = value_patch
       this%soilc_change_patch(i)    = value_patch
    end do

    do fi = 1,num_column
       i  = filter_column(fi)

       this%sr_col(i)                  = value_column
       this%er_col(i)                  = value_column
       this%litfire_col(i)             = value_column
       this%somfire_col(i)             = value_column
       this%totfire_col(i)             = value_column
       this%fire_closs_col(i)          = value_column

       ! Zero p2c column fluxes
       this%rr_col(i)                  = value_column  
       this%ar_col(i)                  = value_column  
       this%gpp_col(i)                 = value_column 
       this%npp_col(i)                 = value_column 
       this%fire_closs_col(i)          = value_column 
       this%wood_harvestc_col(i)       = value_column 
       this%hrv_xsmrpool_to_atm_col(i) = value_column
       this%nep_col(i)                 = value_column
       if ( use_crop )then
          this%xsmrpool_to_atm_col(i)  = value_column
       end if

    end do

  end subroutine SetValues

  !-----------------------------------------------------------------------
  subroutine ZeroDwt( this, bounds )
    !
    ! !DESCRIPTION
    ! Initialize flux variables needed for dynamic land use.
    !
    ! !ARGUMENTS:
    class(cnveg_carbonflux_type) :: this
    type(bounds_type), intent(in)  :: bounds 
    !
    ! !LOCAL VARIABLES:
    integer  :: c, g, j          ! indices
    !-----------------------------------------------------------------------

    ! set conversion and product pool fluxes to 0 at the beginning of every timestep

    do g = bounds%begg, bounds%endg
       this%dwt_seedc_to_leaf_grc(g)        = 0._r8
       this%dwt_seedc_to_deadstem_grc(g)    = 0._r8
       this%dwt_conv_cflux_grc(g)           = 0._r8
    end do

    do c = bounds%begc,bounds%endc
       this%dwt_slash_cflux_col(c)              = 0._r8
    end do

    do j = 1, nlevdecomp_full
       do c = bounds%begc,bounds%endc
          this%dwt_frootc_to_litr_met_c_col(c,j)    = 0._r8
          this%dwt_frootc_to_litr_cel_c_col(c,j)    = 0._r8
          this%dwt_frootc_to_litr_lig_c_col(c,j)    = 0._r8
          this%dwt_livecrootc_to_cwdc_col(c,j)      = 0._r8
          this%dwt_deadcrootc_to_cwdc_col(c,j)      = 0._r8
       end do
    end do

  end subroutine ZeroDwt

  !-----------------------------------------------------------------------
  subroutine Summary_carbonflux(this, &
       bounds, num_soilc, filter_soilc, num_soilp, filter_soilp, &
       isotope, soilbiogeochem_hr_col, soilbiogeochem_lithr_col, &
       soilbiogeochem_decomp_cascade_ctransfer_col, &
       product_closs_grc)
    !
    ! !DESCRIPTION:
    ! Perform patch and column-level carbon summary calculations
    !
    ! !USES:
    use clm_time_manager                   , only: get_step_size
    use clm_varcon                         , only: secspday
    use clm_varctl                         , only: nfix_timeconst, carbon_resp_opt
    use subgridAveMod                      , only: p2c, c2g
    use SoilBiogeochemDecompCascadeConType , only: decomp_cascade_con
    use CNSharedParamsMod                  , only: use_fun
    !
    ! !ARGUMENTS:
    class(cnveg_carbonflux_type)   :: this
    type(bounds_type) , intent(in) :: bounds          
    integer           , intent(in) :: num_soilc       ! number of soil columns in filter
    integer           , intent(in) :: filter_soilc(:) ! filter for soil columns
    integer           , intent(in) :: num_soilp       ! number of soil patches in filter
    integer           , intent(in) :: filter_soilp(:) ! filter for soil patches
    character(len=*)  , intent(in) :: isotope   
    real(r8)          , intent(in) :: soilbiogeochem_hr_col(bounds%begc:)
    real(r8)          , intent(in) :: soilbiogeochem_lithr_col(bounds%begc:)
    real(r8)          , intent(in) :: soilbiogeochem_decomp_cascade_ctransfer_col(bounds%begc:,1:)
    real(r8)          , intent(in) :: product_closs_grc(bounds%begg:)
    !
    ! !LOCAL VARIABLES:
    integer  :: c,p,j,k,l,g     ! indices
    integer  :: fp,fc           ! lake filter indices
    real(r8) :: nfixlags, dtime ! temp variables for making lagged npp
    real(r8) :: maxdepth        ! depth to integrate soil variables
    real(r8) :: nep_grc(bounds%begg:bounds%endg)        ! nep_col averaged to gridcell
    real(r8) :: fire_closs_grc(bounds%begg:bounds%endg) ! fire_closs_col averaged to gridcell
    real(r8) :: hrv_xsmrpool_to_atm_grc(bounds%begg:bounds%endg) ! hrv_xsmrpool_to_atm_col averaged to gridcell (gC/m2/s)
    real(r8) :: hrv_xsmrpool_to_atm_delta_grc(bounds%begg:bounds%endg) ! hrv_xsmrpool_to_atm_col averaged to gridcell, expressed as a delta (not a flux) (gC/m2)
    real(r8) :: hrv_xsmrpool_to_atm_dribbled_grc(bounds%begg:bounds%endg) ! hrv_xsmrpool_to_atm, dribbled over the year (gC/m2/s)
    real(r8) :: dwt_conv_cflux_delta_grc(bounds%begg:bounds%endg)    ! dwt_conv_cflux_grc expressed as a total delta (not a flux) (gC/m2)
    !-----------------------------------------------------------------------

    SHR_ASSERT_ALL((ubound(product_closs_grc) == (/bounds%endg/)), errMsg(sourcefile, __LINE__))

    ! calculate patch-level summary carbon fluxes and states

    dtime = get_step_size()

    do fp = 1,num_soilp
       p = filter_soilp(fp)

       ! maintenance respiration (MR)
       if ( trim(isotope) == 'c13' .or. trim(isotope) == 'c14') then
          this%leaf_mr_patch(p)      = this%leaf_curmr_patch(p)      + this%leaf_xsmr_patch(p)
          this%froot_mr_patch(p)     = this%froot_curmr_patch(p)     + this%froot_xsmr_patch(p)
          this%livestem_mr_patch(p)  = this%livestem_curmr_patch(p)  + this%livestem_xsmr_patch(p)
          this%livecroot_mr_patch(p) = this%livecroot_curmr_patch(p) + this%livecroot_xsmr_patch(p)
       endif

       this%mr_patch(p)  = &
            this%leaf_mr_patch(p)     + &
            this%froot_mr_patch(p)    + &
            this%livestem_mr_patch(p) + &
            this%livecroot_mr_patch(p)

       if (carbon_resp_opt == 1) then
          this%mr_patch(p)  = &
               this%cpool_to_resp_patch(p)     + &
               this%leaf_mr_patch(p)     + &
               this%froot_mr_patch(p)    + &
               this%livestem_mr_patch(p) + &
               this%livecroot_mr_patch(p)
       end if
       if ( use_crop .and. patch%itype(p) >= npcropmin )then
          this%mr_patch(p) = &
               this%mr_patch(p) + &
               this%grain_mr_patch(p)
       end if

       ! growth respiration (GR)

       ! current GR is respired this time step for new growth displayed in this timestep
       this%current_gr_patch(p) = &
            this%cpool_leaf_gr_patch(p)      + &
            this%cpool_froot_gr_patch(p)     + &
            this%cpool_livestem_gr_patch(p)  + &
            this%cpool_deadstem_gr_patch(p)  + &
            this%cpool_livecroot_gr_patch(p) + &
            this%cpool_deadcroot_gr_patch(p)
       if ( use_crop .and. patch%itype(p) >= npcropmin )then
          this%current_gr_patch(p) = this%current_gr_patch(p) + &
               this%cpool_grain_gr_patch(p)
       end if


       ! transfer GR is respired this time step for transfer growth displayed in this timestep
       this%transfer_gr_patch(p) = &
            this%transfer_leaf_gr_patch(p)      + &
            this%transfer_froot_gr_patch(p)     + &
            this%transfer_livestem_gr_patch(p)  + &
            this%transfer_deadstem_gr_patch(p)  + &
            this%transfer_livecroot_gr_patch(p) + &
            this%transfer_deadcroot_gr_patch(p)
       if ( use_crop .and. patch%itype(p) >= npcropmin )then
          this%transfer_gr_patch(p) = this%transfer_gr_patch(p) + &
               this%transfer_grain_gr_patch(p)
       end if

       ! storage GR is respired this time step for growth sent to storage for later display
       this%storage_gr_patch(p) = &
            this%cpool_leaf_storage_gr_patch(p)      + &
            this%cpool_froot_storage_gr_patch(p)     + &
            this%cpool_livestem_storage_gr_patch(p)  + &
            this%cpool_deadstem_storage_gr_patch(p)  + &
            this%cpool_livecroot_storage_gr_patch(p) + &
            this%cpool_deadcroot_storage_gr_patch(p)

       if ( use_crop .and. patch%itype(p) >= npcropmin )then
          this%storage_gr_patch(p) = this%storage_gr_patch(p) + &
               this%cpool_grain_storage_gr_patch(p)
       end if

       ! GR is the sum of current + transfer + storage GR
       this%gr_patch(p) = &
            this%current_gr_patch(p)  + &
            this%transfer_gr_patch(p) + &
            this%storage_gr_patch(p)

       ! autotrophic respiration (AR) adn 
       if ( use_crop .and. patch%itype(p) >= npcropmin )then
          this%ar_patch(p) =           &
               this%mr_patch(p)      + &
               this%gr_patch(p)
          if ( .not. this%dribble_crophrv_xsmrpool_2atm ) this%ar_patch(p) = this%ar_patch(p) + &
                                             this%xsmrpool_to_atm_patch(p) ! xsmr... is -ve (slevis)
       else         
             this%ar_patch(p) =           &
                  this%mr_patch(p)      + &
                  this%gr_patch(p)         
       end if
       
       if (use_fun) then
          this%ar_patch(p) = this%ar_patch(p) + this%soilc_change_patch(p)
       end if
      
       ! gross primary production (GPP)
       this%gpp_patch(p) = &
            this%psnsun_to_cpool_patch(p) + &
            this%psnshade_to_cpool_patch(p)

       ! net primary production (NPP)      
       this%npp_patch(p) =      &
               this%gpp_patch(p) - &
               this%ar_patch(p)     

       ! root respiration (RR)
       this%rr_patch(p) =         &
            this%froot_mr_patch(p)                   + &
            this%cpool_froot_gr_patch(p)             + &
            this%cpool_livecroot_gr_patch(p)         + &
            this%cpool_deadcroot_gr_patch(p)         + &
            this%transfer_froot_gr_patch(p)          + &
            this%transfer_livecroot_gr_patch(p)      + &
            this%transfer_deadcroot_gr_patch(p)      + &
            this%cpool_froot_storage_gr_patch(p)     + &
            this%cpool_livecroot_storage_gr_patch(p) + &
            this%cpool_deadcroot_storage_gr_patch(p)

       ! update the annual NPP accumulator, for use in allocation code 
       if (trim(isotope) == 'bulk') then      
          this%tempsum_npp_patch(p) = &
               this%tempsum_npp_patch(p) + &
               this%npp_patch(p)
       end if

       ! aboveground NPP: leaf, live stem, dead stem (AGNPP)
       ! This is supposed to correspond as closely as possible to
       ! field measurements of AGNPP, so it ignores the storage pools
       ! and only treats the fluxes into displayed pools.

       this%agnpp_patch(p) = &
            this%cpool_to_leafc_patch(p)                  + &
            this%leafc_xfer_to_leafc_patch(p)             + &
            this%cpool_to_livestemc_patch(p)              + &
            this%livestemc_xfer_to_livestemc_patch(p)     + &
            this%cpool_to_deadstemc_patch(p)              + &
            this%deadstemc_xfer_to_deadstemc_patch(p)

       if ( use_crop .and. patch%itype(p) >= npcropmin )then
          this%agnpp_patch(p) =      &
               this%agnpp_patch(p) + &
               this%cpool_to_grainc_patch(p)            + &
               this%grainc_xfer_to_grainc_patch(p)
       end if

       ! belowground NPP: fine root, live coarse root, dead coarse root (BGNPP)
       ! This is supposed to correspond as closely as possible to
       ! field measurements of BGNPP, so it ignores the storage pools
       ! and only treats the fluxes into displayed pools.

       this%bgnpp_patch(p) = &
            this%cpool_to_frootc_patch(p)                   + &
            this%frootc_xfer_to_frootc_patch(p)             + &
            this%cpool_to_livecrootc_patch(p)               + &
            this%livecrootc_xfer_to_livecrootc_patch(p)     + &
            this%cpool_to_deadcrootc_patch(p)               + &
            this%deadcrootc_xfer_to_deadcrootc_patch(p)

       ! litterfall (LITFALL)

       this%litfall_patch(p) = &
            this%leafc_to_litter_patch(p)                     + &
            this%frootc_to_litter_patch(p)                    + &
            this%m_leafc_to_litter_patch(p)                   + &
            this%m_leafc_storage_to_litter_patch(p)           + &
            this%m_leafc_xfer_to_litter_patch(p)              + &
            this%m_frootc_to_litter_patch(p)                  + &
            this%m_frootc_storage_to_litter_patch(p)          + &
            this%m_frootc_xfer_to_litter_patch(p)             + &
            this%m_livestemc_to_litter_patch(p)               + &
            this%m_livestemc_storage_to_litter_patch(p)       + &
            this%m_livestemc_xfer_to_litter_patch(p)          + &
            this%m_deadstemc_to_litter_patch(p)               + &
            this%m_deadstemc_storage_to_litter_patch(p)       + &
            this%m_deadstemc_xfer_to_litter_patch(p)          + &
            this%m_livecrootc_to_litter_patch(p)              + &
            this%m_livecrootc_storage_to_litter_patch(p)      + &
            this%m_livecrootc_xfer_to_litter_patch(p)         + &
            this%m_deadcrootc_to_litter_patch(p)              + &
            this%m_deadcrootc_storage_to_litter_patch(p)      + &
            this%m_deadcrootc_xfer_to_litter_patch(p)         + &
            this%m_gresp_storage_to_litter_patch(p)           + &
            this%m_gresp_xfer_to_litter_patch(p)              + &
            
            this%m_leafc_to_litter_fire_patch(p)              + &
            this%m_leafc_storage_to_litter_fire_patch(p)      + &
            this%m_leafc_xfer_to_litter_fire_patch(p)         + &
            this%m_livestemc_to_litter_fire_patch(p)          + &
            this%m_livestemc_storage_to_litter_fire_patch(p)  + &
            this%m_livestemc_xfer_to_litter_fire_patch(p)     + &
            this%m_deadstemc_to_litter_fire_patch(p)          + &
            this%m_deadstemc_storage_to_litter_fire_patch(p)  + &
            this%m_deadstemc_xfer_to_litter_fire_patch(p)     + &
            this%m_frootc_to_litter_fire_patch(p)             + &
            this%m_frootc_storage_to_litter_fire_patch(p)     + &
            this%m_frootc_xfer_to_litter_fire_patch(p)        + &
            this%m_livecrootc_to_litter_fire_patch(p)         + &
            this%m_livecrootc_storage_to_litter_fire_patch(p) + &
            this%m_livecrootc_xfer_to_litter_fire_patch(p)    + &
            this%m_deadcrootc_to_litter_fire_patch(p)         + &
            this%m_deadcrootc_storage_to_litter_fire_patch(p) + &
            this%m_deadcrootc_xfer_to_litter_fire_patch(p)    + &
            this%m_gresp_storage_to_litter_fire_patch(p)      + &
            this%m_gresp_xfer_to_litter_fire_patch(p)         + &
            
            this%hrv_leafc_to_litter_patch(p)                 + &
            this%hrv_leafc_storage_to_litter_patch(p)         + &
            this%hrv_leafc_xfer_to_litter_patch(p)            + &
            this%hrv_frootc_to_litter_patch(p)                + &
            this%hrv_frootc_storage_to_litter_patch(p)        + &
            this%hrv_frootc_xfer_to_litter_patch(p)           + &
            this%hrv_livestemc_to_litter_patch(p)             + &
            this%hrv_livestemc_storage_to_litter_patch(p)     + &
            this%hrv_livestemc_xfer_to_litter_patch(p)        + &
            this%hrv_deadstemc_storage_to_litter_patch(p)     + &
            this%hrv_deadstemc_xfer_to_litter_patch(p)        + &
            this%hrv_livecrootc_to_litter_patch(p)            + &
            this%hrv_livecrootc_storage_to_litter_patch(p)    + &
            this%hrv_livecrootc_xfer_to_litter_patch(p)       + &
            this%hrv_deadcrootc_to_litter_patch(p)            + &
            this%hrv_deadcrootc_storage_to_litter_patch(p)    + &
            this%hrv_deadcrootc_xfer_to_litter_patch(p)       + &
            this%hrv_gresp_storage_to_litter_patch(p)         + &
            this%hrv_gresp_xfer_to_litter_patch(p)

       if ( use_crop .and. patch%itype(p) >= npcropmin )then
          this%litfall_patch(p) =      &
               this%litfall_patch(p) + &
               this%livestemc_to_litter_patch(p)

          if (.not. use_grainproduct) then
             this%litfall_patch(p) = &
                  this%litfall_patch(p) + &
                  this%grainc_to_food_patch(p)
          end if
       end if

       ! update the annual litfall accumulator, for use in mortality code

       if (use_cndv) then
          this%tempsum_litfall_patch(p) = &
               this%tempsum_litfall_patch(p) + &
               this%leafc_to_litter_patch(p) + &
               this%frootc_to_litter_patch(p)
       end if

       ! patch-level carbon losses to fire changed by F. Li and S. Levis

       this%fire_closs_patch(p) = &
            this%m_leafc_to_fire_patch(p)                + &
            this%m_leafc_storage_to_fire_patch(p)        + &
            this%m_leafc_xfer_to_fire_patch(p)           + &
            this%m_frootc_to_fire_patch(p)               + &
            this%m_frootc_storage_to_fire_patch(p)       + &
            this%m_frootc_xfer_to_fire_patch(p)          + &
            this%m_livestemc_to_fire_patch(p)            + &
            this%m_livestemc_storage_to_fire_patch(p)    + &
            this%m_livestemc_xfer_to_fire_patch(p)       + &
            this%m_deadstemc_to_fire_patch(p)            + &
            this%m_deadstemc_storage_to_fire_patch(p)    + &
            this%m_deadstemc_xfer_to_fire_patch(p)       + &
            this%m_livecrootc_to_fire_patch(p)           + &
            this%m_livecrootc_storage_to_fire_patch(p)   + &
            this%m_livecrootc_xfer_to_fire_patch(p)      + &
            this%m_deadcrootc_to_fire_patch(p)           + &
            this%m_deadcrootc_storage_to_fire_patch(p)   + &
            this%m_deadcrootc_xfer_to_fire_patch(p)      + &
            this%m_gresp_storage_to_fire_patch(p)        + &
            this%m_gresp_xfer_to_fire_patch(p)

       ! new summary variables for CLAMP

       ! (FROOTC_ALLOC) - fine root C allocation
       this%frootc_alloc_patch(p) = &
            this%frootc_xfer_to_frootc_patch(p)    + &
            this%cpool_to_frootc_patch(p)     

       ! (FROOTC_LOSS) - fine root C loss changed by F. Li and S. Levis
       this%frootc_loss_patch(p) = &
            this%m_frootc_to_litter_patch(p)       + &
            this%m_frootc_to_fire_patch(p)         + &
            this%m_frootc_to_litter_fire_patch(p)  + &
            this%hrv_frootc_to_litter_patch(p)     + &
            this%frootc_to_litter_patch(p)

       ! (LEAFC_ALLOC) - leaf C allocation
       this%leafc_alloc_patch(p) = &
            this%leafc_xfer_to_leafc_patch(p)    + &
            this%cpool_to_leafc_patch(p)     

       ! (LEAFC_LOSS) - leaf C loss changed by F. Li and S. Levis
       this%leafc_loss_patch(p) = &
            this%m_leafc_to_litter_patch(p)      + &
            this%m_leafc_to_fire_patch(p)        + &
            this%m_leafc_to_litter_fire_patch(p) + &
            this%hrv_leafc_to_litter_patch(p)    + &
            this%leafc_to_litter_patch(p)

       ! (WOODC_ALLOC) - wood C allocation
       this%woodc_alloc_patch(p) = &
            this%livestemc_xfer_to_livestemc_patch(p)   + &
            this%deadstemc_xfer_to_deadstemc_patch(p)   + &
            this%livecrootc_xfer_to_livecrootc_patch(p) + &
            this%deadcrootc_xfer_to_deadcrootc_patch(p) + &
            this%cpool_to_livestemc_patch(p)            + &
            this%cpool_to_deadstemc_patch(p)            + &
            this%cpool_to_livecrootc_patch(p)           + &
            this%cpool_to_deadcrootc_patch(p)

       ! (WOODC_LOSS) - wood C loss
       this%woodc_loss_patch(p) = &
            this%m_livestemc_to_litter_patch(p)            + &
            this%m_deadstemc_to_litter_patch(p)            + &
            this%m_livecrootc_to_litter_patch(p)           + &
            this%m_deadcrootc_to_litter_patch(p)           + &
            this%m_livestemc_to_fire_patch(p)              + &
            this%m_deadstemc_to_fire_patch(p)              + &
            this%m_livecrootc_to_fire_patch(p)             + &
            this%m_deadcrootc_to_fire_patch(p)             + &
            this%hrv_livestemc_to_litter_patch(p)          + &
            this%hrv_livestemc_storage_to_litter_patch(p)  + &
            this%hrv_livestemc_xfer_to_litter_patch(p)     + &
            this%wood_harvestc_patch(p)                    + &
            this%hrv_deadstemc_storage_to_litter_patch(p)  + &
            this%hrv_deadstemc_xfer_to_litter_patch(p)     + &
            this%hrv_livecrootc_to_litter_patch(p)         + &
            this%hrv_livecrootc_storage_to_litter_patch(p) + &
            this%hrv_livecrootc_xfer_to_litter_patch(p)    + &
            this%hrv_deadcrootc_to_litter_patch(p)         + &
            this%hrv_deadcrootc_storage_to_litter_patch(p) + &
            this%hrv_deadcrootc_xfer_to_litter_patch(p)   

       ! (Slash Harvest Flux) - Additional Wood Harvest Veg C Losses
       this%slash_harvestc_patch(p) = &
            this%hrv_leafc_to_litter_patch(p)              + &
            this%hrv_leafc_storage_to_litter_patch(p)      + &
            this%hrv_leafc_xfer_to_litter_patch(p)         + &
            this%hrv_frootc_to_litter_patch(p)             + &
            this%hrv_frootc_storage_to_litter_patch(p)     + &
            this%hrv_frootc_xfer_to_litter_patch(p)        + &
            this%hrv_livestemc_to_litter_patch(p)          + &
            this%hrv_livestemc_storage_to_litter_patch(p)  + &
            this%hrv_livestemc_xfer_to_litter_patch(p)     + &
            this%hrv_deadstemc_storage_to_litter_patch(p)  + &
            this%hrv_deadstemc_xfer_to_litter_patch(p)     + &
            this%hrv_livecrootc_to_litter_patch(p)         + &
            this%hrv_livecrootc_storage_to_litter_patch(p) + &
            this%hrv_livecrootc_xfer_to_litter_patch(p)    + &
            this%hrv_deadcrootc_to_litter_patch(p)         + &
            this%hrv_deadcrootc_storage_to_litter_patch(p) + &
            this%hrv_deadcrootc_xfer_to_litter_patch(p)    + &
            this%hrv_xsmrpool_to_atm_patch(p)              + &
            this%hrv_gresp_storage_to_litter_patch(p)      + &
            this%hrv_gresp_xfer_to_litter_patch(p)

    end do  ! end of patches loop

    !------------------------------------------------
    ! column variables
    !------------------------------------------------

    ! use p2c routine to get selected column-average patch-level fluxes and states

    call p2c(bounds, num_soilc, filter_soilc, &
         this%hrv_xsmrpool_to_atm_patch(bounds%begp:bounds%endp), &
         this%hrv_xsmrpool_to_atm_col(bounds%begc:bounds%endc))

    if (use_crop .and. this%dribble_crophrv_xsmrpool_2atm) then
       call p2c(bounds, num_soilc, filter_soilc, &
            this%xsmrpool_to_atm_patch(bounds%begp:bounds%endp), &
            this%xsmrpool_to_atm_col(bounds%begc:bounds%endc))

       call c2g( bounds = bounds, &
            carr = this%xsmrpool_to_atm_col(bounds%begc:bounds%endc), &
            garr = this%xsmrpool_to_atm_grc(bounds%begg:bounds%endg), &
            c2l_scale_type = 'unity', &
            l2g_scale_type = 'unity')
    end if

    call p2c(bounds, num_soilc, filter_soilc, &
         this%fire_closs_patch(bounds%begp:bounds%endp), &
         this%fire_closs_p2c_col(bounds%begc:bounds%endc))

    call p2c(bounds, num_soilc, filter_soilc, &
         this%npp_patch(bounds%begp:bounds%endp), &
         this%npp_col(bounds%begc:bounds%endc))

    call p2c(bounds, num_soilc, filter_soilc, &
         this%rr_patch(bounds%begp:bounds%endp), &
         this%rr_col(bounds%begc:bounds%endc))

    call p2c(bounds, num_soilc, filter_soilc, &
         this%ar_patch(bounds%begp:bounds%endp), &
         this%ar_col(bounds%begc:bounds%endc))

    call p2c(bounds, num_soilc, filter_soilc, &
         this%gpp_patch(bounds%begp:bounds%endp), &
         this%gpp_col(bounds%begc:bounds%endc))

    ! this code is to calculate an exponentially-relaxed npp value for use in NDynamics code

    if ( trim(isotope) == 'bulk') then
       if (nfix_timeconst > 0._r8 .and. nfix_timeconst < 500._r8 ) then
          nfixlags = nfix_timeconst * secspday
          do fc = 1,num_soilc
             c = filter_soilc(fc)
             if ( this%lag_npp_col(c) /= spval ) then
                this%lag_npp_col(c) = &
                     this%lag_npp_col(c) * exp(-dtime/nfixlags) + &
                     this%npp_col(c) * (1._r8 - exp(-dtime/nfixlags))
             else
                ! first timestep
                this%lag_npp_col(c) = this%npp_col(c)
             endif
          end do
       endif
    endif


    ! vertically integrate column-level carbon fire losses
    do l = 1, ndecomp_pools
       do j = 1,nlevdecomp
          do fc = 1,num_soilc
             c = filter_soilc(fc)
             this%m_decomp_cpools_to_fire_col(c,l) = &
                  this%m_decomp_cpools_to_fire_col(c,l) + &
                  this%m_decomp_cpools_to_fire_vr_col(c,j,l)*dzsoi_decomp(j)
          end do
       end do
    end do

    do fc = 1,num_soilc
       c = filter_soilc(fc)

       g = col%gridcell(c)

       ! litter fire losses (LITFIRE)
       this%litfire_col(c) = 0._r8

       ! soil organic matter fire losses (SOMFIRE)
       this%somfire_col(c) = 0._r8

       ! total ecosystem fire losses (TOTFIRE)
       this%totfire_col(c) = &
            this%litfire_col(c) + &
            this%somfire_col(c) 

       ! carbon losses to fire, including patch losses
       this%fire_closs_col(c) = this%fire_closs_p2c_col(c) 
       do l = 1, ndecomp_pools
          this%fire_closs_col(c) = &
               this%fire_closs_col(c) + &
               this%m_decomp_cpools_to_fire_col(c,l)
       end do

       ! total soil respiration, heterotrophic + root respiration (SR)
       this%sr_col(c) = &
            this%rr_col(c) + &
            soilbiogeochem_hr_col(c)

       ! total ecosystem respiration, autotrophic + heterotrophic (ER)
       this%er_col(c) = &
            this%ar_col(c) + &
            soilbiogeochem_hr_col(c)
       
       ! coarse woody debris heterotrophic respiration
       this%cwdc_hr_col(c) = 0._r8

       ! net ecosystem production, excludes fire flux, landcover change, 
       ! and loss from wood products, positive for sink (NEP)
       this%nep_col(c) = &
            this%gpp_col(c) - &
            this%er_col(c)

    end do

    call c2g( bounds = bounds, &
         carr = this%nep_col(bounds%begc:bounds%endc), &
         garr = nep_grc(bounds%begg:bounds%endg), &
         c2l_scale_type = 'unity', &
         l2g_scale_type = 'unity')

    call c2g( bounds = bounds, &
         carr = this%fire_closs_col(bounds%begc:bounds%endc), &
         garr = fire_closs_grc(bounds%begg:bounds%endg), &
         c2l_scale_type = 'unity', &
         l2g_scale_type = 'unity')

    call c2g( bounds = bounds, &
         carr = this%hrv_xsmrpool_to_atm_col(bounds%begc:bounds%endc), &
         garr = hrv_xsmrpool_to_atm_grc(bounds%begg:bounds%endg), &
         c2l_scale_type = 'unity', &
         l2g_scale_type = 'unity')
    hrv_xsmrpool_to_atm_delta_grc(bounds%begg:bounds%endg) = &
         hrv_xsmrpool_to_atm_grc(bounds%begg:bounds%endg) * dtime
    call this%hrv_xsmrpool_to_atm_dribbler%set_curr_delta(bounds, &
         hrv_xsmrpool_to_atm_delta_grc(bounds%begg:bounds%endg))
    call this%hrv_xsmrpool_to_atm_dribbler%get_curr_flux(bounds, &
         hrv_xsmrpool_to_atm_dribbled_grc(bounds%begg:bounds%endg))

    dwt_conv_cflux_delta_grc(bounds%begg:bounds%endg) = &
         this%dwt_conv_cflux_grc(bounds%begg:bounds%endg) * dtime
    call this%dwt_conv_cflux_dribbler%set_curr_delta(bounds, &
         dwt_conv_cflux_delta_grc(bounds%begg:bounds%endg))
    call this%dwt_conv_cflux_dribbler%get_curr_flux(bounds, &
         this%dwt_conv_cflux_dribbled_grc(bounds%begg:bounds%endg))

    do g = bounds%begg, bounds%endg
       ! net ecosystem exchange of carbon, includes fire flux and hrv_xsmrpool flux,
       ! positive for source (NEE)
       this%nee_grc(g) = &
            -nep_grc(g)       + &
            fire_closs_grc(g) + &
            hrv_xsmrpool_to_atm_dribbled_grc(g)

       this%landuseflux_grc(g) = &
            this%dwt_conv_cflux_dribbled_grc(g)   + &
            product_closs_grc(g)

       ! net biome production of carbon, positive for sink
       this%nbp_grc(g) = &
            -this%nee_grc(g)        - &
            this%landuseflux_grc(g)
       if ( this%dribble_crophrv_xsmrpool_2atm ) this%nbp_grc(g) = this%nbp_grc(g) - this%xsmrpool_to_atm_grc(g)
    end do

    ! coarse woody debris C loss
    do fc = 1,num_soilc
       c  = filter_soilc(fc)
       this%cwdc_loss_col(c)  = 0._r8
    end do
    associate(is_cwd    => decomp_cascade_con%is_cwd) ! TRUE => pool is a cwd pool   
      do l = 1, ndecomp_pools
         if ( is_cwd(l) ) then
            do fc = 1,num_soilc
               c = filter_soilc(fc)
               this%cwdc_loss_col(c) = &
                    this%cwdc_loss_col(c) + &
                    this%m_decomp_cpools_to_fire_col(c,l)
            end do
         end if
      end do
      do k = 1, ndecomp_cascade_transitions
         if ( is_cwd(decomp_cascade_con%cascade_donor_pool(k)) ) then
            do fc = 1,num_soilc
               c = filter_soilc(fc)
               this%cwdc_loss_col(c) = &
                    this%cwdc_loss_col(c) + &
                    soilbiogeochem_decomp_cascade_ctransfer_col(c,k)
            end do
         end if
      end do
    end associate


    ! litter C loss      
    do fc = 1,num_soilc
       c = filter_soilc(fc)
       this%litterc_loss_col(c) = soilbiogeochem_lithr_col(c)  
    end do
    associate(is_litter => decomp_cascade_con%is_litter) ! TRUE => pool is a litter pool
      do l = 1, ndecomp_pools
         if ( is_litter(l) ) then
            do fc = 1,num_soilc
               c = filter_soilc(fc)
               this%litterc_loss_col(c) = &
                    this%litterc_loss_col(c) + &
                    this%m_decomp_cpools_to_fire_col(c,l)
            end do
         end if
      end do
      do k = 1, ndecomp_cascade_transitions
         if ( is_litter(decomp_cascade_con%cascade_donor_pool(k)) ) then
            do fc = 1,num_soilc
               c = filter_soilc(fc)
               this%litterc_loss_col(c) = &
                    this%litterc_loss_col(c) + &
                    soilbiogeochem_decomp_cascade_ctransfer_col(c,k)
            end do
         end if
      end do
    end associate

  end subroutine Summary_carbonflux

end module CNVegCarbonFluxType