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_stomate/stomate_io.f90

    r6319 r7326  
    7575       &  turnover_longterm, gpp_week, biomass, resp_maint_part, & 
    7676       &  leaf_age, leaf_frac, senescence, when_growthinit, age, & 
    77        &  resp_hetero, resp_maint, resp_growth, co2_fire, co2_to_bm_dgvm, co2_to_bm_radia, & 
     77       &  resp_hetero, resp_maint, resp_growth, co2_fire, co2_to_bm_dgvm, & 
    7878       &  veget_lastlight, everywhere, need_adjacent, RIP_time, & 
    7979       &  time_hum_min, hum_min_dormance, & 
     
    249249    ! biomass uptaken (gC/(m**2 of total ground)/day) 
    250250    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: co2_to_bm_dgvm 
    251     ! biomass uptaken (gC/(m**2 of total ground)/dt_sechiba) 
    252     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: co2_to_bm_radia 
    253251    ! vegetation fractions (on ground) after last light competition 
    254252    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: veget_lastlight 
     
    941939    IF (ALL(co2_to_bm_dgvm(:,:) == val_exp)) co2_to_bm_dgvm(:,:) = zero 
    942940 
    943     co2_to_bm_radia(:,:) = val_exp 
    944     var_name = 'co2_to_bm_radia' 
    945     CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, & 
    946          &                .TRUE., co2_to_bm_radia, 'gather', nbp_glo, index_g) 
    947     IF (ALL(co2_to_bm_radia(:,:) == val_exp)) co2_to_bm_radia(:,:) = zero 
    948941    !- 
    949942    ! 14 vegetation distribution after last light competition 
     
    13471340       &  turnover_longterm, gpp_week, biomass, resp_maint_part, & 
    13481341       &  leaf_age, leaf_frac, senescence, when_growthinit, age, & 
    1349        &  resp_hetero, resp_maint, resp_growth, co2_fire, co2_to_bm_dgvm, co2_to_bm_radia, & 
     1342       &  resp_hetero, resp_maint, resp_growth, co2_fire, co2_to_bm_dgvm, & 
    13501343       &  veget_lastlight, everywhere, need_adjacent, RIP_time, & 
    13511344       &  time_hum_min, hum_min_dormance, & 
     
    15131506    ! biomass uptaken (gC/(m**2 of total ground)/day) 
    15141507    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: co2_to_bm_dgvm 
    1515     ! biomass uptaken (gC/(m**2 of total ground)/dt_sechiba) 
    1516     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: co2_to_bm_radia 
    15171508    ! vegetation fractions (on ground) after last light competition 
    15181509    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: veget_lastlight 
     
    20242015    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & 
    20252016         &                co2_to_bm_dgvm, 'scatter', nbp_glo, index_g) 
    2026     !- 
    2027     var_name = 'co2_to_bm_radia' 
    2028     CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & 
    2029          &                co2_to_bm_radia, 'scatter', nbp_glo, index_g) 
    20302017    !- 
    20312018    ! 14 vegetation distribution after last light competition 
Note: See TracChangeset for help on using the changeset viewer.