Ignore:
Timestamp:
2021-10-20T18:39:22+02:00 (3 years ago)
Author:
josefine.ghattas
Message:

Corrected bug on carbon balance closure. See ticket #785
Integration in branch 2_2 done by P. Cadule

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_sechiba/slowproc.f90

    r7325 r7326  
    283283                                  frac_nobio,    njsc,         veget_max,      fraclut,           & 
    284284                                  nwdfraclut,    tot_bare_soil,totfrac_nobio,  qsintmax,          & 
    285                                   co2_to_bm,     temp_growth) 
     285                                  temp_growth) 
    286286 
    287287!! 0.1 Input variables 
     
    302302     
    303303!! 0.2 Output variables  
    304     REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(out)     :: co2_to_bm      !! Virtual gpp per average ground area (gC m^{-2} dt_stomate^{-1}) 
    305304    REAL(r_std),DIMENSION (kjpindex), INTENT (out)         :: temp_growth    !! Growth temperature (°C) - Is equal to t2m_month  
    306305    INTEGER(i_std), DIMENSION(kjpindex), INTENT(out)       :: njsc           !! Index of the dominant soil textural class in the grid cell (1-nscm, unitless) 
     
    365364             contfrac,       totfrac_nobio,          clayfraction, temp_air,          & 
    366365             lai,            veget,                  veget_max,                       & 
    367              co2_to_bm,      deadleaf_cover,         assim_param,  temp_growth ) 
    368     ELSE 
    369        !! ok_stomate is not activated 
    370        !! Define the CO2 fluxes to zero (no carbone cycle) 
    371        co2_to_bm(:,:) = zero 
     366             deadleaf_cover,         assim_param,  temp_growth ) 
    372367    ENDIF 
    373368     
     
    447442       rest_id, hist_id, hist2_id, rest_id_stom, hist_id_stom, hist_id_stom_IPCC, & 
    448443       co2_flux, fco2_lu, fco2_wh, fco2_ha, & 
    449        co2_to_bm, temp_growth, tot_bare_soil) 
     444       temp_growth, tot_bare_soil) 
    450445   
    451446!! INTERFACE DESCRIPTION 
     
    484479    REAL(r_std),DIMENSION (kjpindex), INTENT (out)      :: fco2_wh             !! CO2 Flux to Atmosphere from Wood Harvesting (gC m^{-2} dt_stomate^{-1}) 
    485480    REAL(r_std),DIMENSION (kjpindex), INTENT (out)      :: fco2_ha             !! CO2 Flux to Atmosphere from Crop Harvesting (gC m^{-2} dt_stomate^{-1}) 
    486     REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(out)  :: co2_to_bm           !! virtual gpp flux per average ground area (gC m^{-2} dt_stomate^{-1}) 
    487481    REAL(r_std),DIMENSION (kjpindex), INTENT (out)      :: temp_growth         !! Growth temperature (°C) - Is equal to t2m_month  
    488482    REAL(r_std), DIMENSION (kjpindex), INTENT(out)      :: tot_bare_soil       !! Total evaporating bare soil fraction in the mesh 
     
    595589            rest_id_stom, hist_id_stom, hist_id_stom_IPCC, & 
    596590            co2_flux, fco2_lu, fco2_wh, fco2_ha, & 
    597             resp_maint, resp_hetero, resp_growth, co2_to_bm, temp_growth) 
     591            resp_maint, resp_hetero, resp_growth, temp_growth) 
    598592 
    599593 
     
    664658       fco2_wh(:) = zero 
    665659       fco2_ha(:) = zero 
    666        co2_to_bm(:,:) = zero 
    667660    ENDIF 
    668661 
     
    746739                                frac_nobio, veget_max, reinf_slope,          & 
    747740                                ks,  nvan, avan, mcr, mcs, mcfc, mcw,        & 
    748                                 co2_to_bm,  assim_param, frac_age ) 
     741                                assim_param, frac_age ) 
    749742 
    750743!! 0.1 Input variables 
     
    768761    REAL(r_std),DIMENSION (kjpindex), INTENT(in)         :: mcfc           !! Volumetric water content at field capacity (m^{3} m^{-3}) 
    769762    REAL(r_std),DIMENSION (kjpindex), INTENT(in)         :: mcw            !! Volumetric water content at wilting point (m^{3} m^{-3}) 
    770  
    771     REAL(r_std),DIMENSION (kjpindex,nvm),INTENT(in)      :: co2_to_bm      !! virtual gpp flux between atmosphere and biosphere 
    772763    REAL(r_std),DIMENSION (kjpindex,nvm,npco2),INTENT (in):: assim_param   !! min+max+opt temperatures & vmax for photosynthesis (K, \mumol m^{-2} s^{-1}) 
    773764    REAL(r_std),DIMENSION (kjpindex,nvm,nleafages), INTENT(in):: frac_age  !! Age efficacity from STOMATE for isoprene 
     
    842833    ! 2.2 Write restart variables managed by STOMATE 
    843834    IF ( ok_stomate ) THEN 
    844        CALL stomate_finalize (kjit, kjpindex, indexLand, clayfraction, co2_to_bm, assim_param)  
     835       CALL stomate_finalize (kjit, kjpindex, indexLand, clayfraction, assim_param)  
    845836    ENDIF 
    846837     
Note: See TracChangeset for help on using the changeset viewer.