Changeset 335


Ignore:
Timestamp:
2011-07-21T14:50:33+02:00 (13 years ago)
Author:
didier.solyga
Message:

Synchronize ORCHIDEE_EXT with the revision 329 of the trunk

Location:
branches/ORCHIDEE_EXT/ORCHIDEE
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • branches/ORCHIDEE_EXT/ORCHIDEE/src_sechiba/intersurf.f90

    r326 r335  
    54335433         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, & 
    54345434         &               1,1,1, -99,32, ave(1), dt, hist_dt) 
     5435    ! Carbon Mass Variation 
     5436    CALL histdef (hist_id_stom_IPCC, & 
     5437         &               TRIM("cMassVariation"), & 
     5438         &               TRIM("Terrestrial Carbon Mass Variation"), & 
     5439         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, & 
     5440         &               1,1,1, -99,32, ave(1), dt, hist_dt) 
    54355441    ! Leaf Area Fraction 
    54365442    CALL histdef (hist_id_stom_IPCC, & 
  • branches/ORCHIDEE_EXT/ORCHIDEE/src_stomate/stomate.f90

    r311 r335  
    245245  ! This variable must be .TRUE. once a year 
    246246  LOGICAL, SAVE                                :: EndOfYear=.FALSE. 
    247 !!$  ! Land cover change flag 
    248 !!$  LOGICAL,SAVE                                 :: lcchange=.FALSE. 
    249247  ! Do update of monthly variables ? 
    250248  ! This variable must be .TRUE. once a month 
    251249  LOGICAL, SAVE                                :: EndOfMonth=.FALSE. 
    252   PUBLIC  dt_days, day_counter, date, do_slow, EndOfYear !, lcchange 
     250  PUBLIC  dt_days, day_counter, date, do_slow, EndOfYear 
    253251 
    254252 
     
    313311  ! harvest above ground biomass for agriculture 
    314312  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)                            :: harvest_above 
     313 
     314  ! Carbon Mass total 
     315  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)                            :: carb_mass_total 
    315316 
    316317CONTAINS 
     
    627628            &         carbon, black_carbon, lignin_struc,turnover_time,& 
    628629            &         prod10,prod100,flux10, flux100, & 
    629             &         convflux, cflux_prod10, cflux_prod100, bm_to_litter) 
     630            &         convflux, cflux_prod10, cflux_prod100, bm_to_litter, carb_mass_total) 
    630631 
    631632       ! 1.4 read the boundary conditions 
     
    10061007            &          carbon, black_carbon, lignin_struc,turnover_time,& 
    10071008            &          prod10,prod100,flux10, flux100, & 
    1008             &          convflux, cflux_prod10, cflux_prod100, bm_to_litter) 
     1009            &          convflux, cflux_prod10, cflux_prod100, bm_to_litter, carb_mass_total) 
    10091010 
    10101011       IF (ldforcing_write .AND. TRIM(forcing_name) /= 'NONE' ) THEN   
     
    13341335               &             t_photo_min, t_photo_opt, t_photo_max,bm_to_litter,& 
    13351336               &             prod10, prod100, flux10, flux100, veget_cov_max_new,& 
    1336                &             convflux, cflux_prod10, cflux_prod100, harvest_above, lcchange,& 
     1337               &             convflux, cflux_prod10, cflux_prod100, harvest_above, carb_mass_total, lcchange,& 
    13371338               &             fpc_max) 
    13381339 
     
    19901991    l_error = l_error .OR. (ier.NE.0) 
    19911992    ALLOCATE (harvest_above(kjpindex), stat=ier) 
     1993    l_error = l_error .OR. (ier.NE.0) 
     1994    ALLOCATE (carb_mass_total(kjpindex), stat=ier) 
    19921995    l_error = l_error .OR. (ier.NE.0) 
    19931996    ALLOCATE (soilcarbon_input_daily(kjpindex,ncarb,nvm), stat=ier) 
     
    24802483       ALLOCATE(lai_fm_g(nbp_glo,nvm,nsfm),stat=ier) 
    24812484       l_error = l_error .OR. (ier /= 0) 
     2485    ELSE 
     2486       ALLOCATE(clay_fm_g(0,nsfm),stat=ier) 
     2487       ALLOCATE(humrel_daily_fm_g(0,nvm,nsfm),stat=ier) 
     2488       ALLOCATE(litterhum_daily_fm_g(0,nsfm),stat=ier) 
     2489       ALLOCATE(t2m_daily_fm_g(0,nsfm),stat=ier) 
     2490       ALLOCATE(t2m_min_daily_fm_g(0,nsfm),stat=ier) 
     2491       ALLOCATE(tsurf_daily_fm_g(0,nsfm),stat=ier) 
     2492       ALLOCATE(tsoil_daily_fm_g(0,nbdl,nsfm),stat=ier) 
     2493       ALLOCATE(soilhum_daily_fm_g(0,nbdl,nsfm),stat=ier) 
     2494       ALLOCATE(precip_fm_g(0,nsfm),stat=ier) 
     2495       ALLOCATE(gpp_daily_fm_g(0,nvm,nsfm),stat=ier) 
     2496       ALLOCATE(resp_maint_part_fm_g(0,nvm,nparts,nsfm),stat=ier) 
     2497       ALLOCATE(veget_fm_g(0,nvm,nsfm),stat=ier) 
     2498       ALLOCATE(veget_max_fm_g(0,nvm,nsfm),stat=ier) 
     2499       ALLOCATE(lai_fm_g(0,nvm,nsfm),stat=ier) 
    24822500    ENDIF 
    24832501    ! 
  • branches/ORCHIDEE_EXT/ORCHIDEE/src_stomate/stomate_io.f90

    r257 r335  
    5555       &  carbon, black_carbon, lignin_struc,turnover_time, & 
    5656       &  prod10,prod100,flux10, flux100, & 
    57        &  convflux, cflux_prod10, cflux_prod100, bm_to_litter) 
     57       &  convflux, cflux_prod10, cflux_prod100, bm_to_litter, carb_mass_total) 
    5858    !--------------------------------------------------------------------- 
    5959    !- read start file 
     
    275275    REAL(r_std), DIMENSION(npts), INTENT(out)                            :: cflux_prod100 
    276276    REAL(r_std),DIMENSION(npts,nvm,nparts),INTENT(out)                   :: bm_to_litter 
     277    REAL(r_std),DIMENSION(npts),INTENT(out)                              :: carb_mass_total 
    277278    !--------------------------------------------------------------------- 
    278279    IF (bavard >= 3) WRITE(numout,*) 'Entering readstart' 
     
    940941    ENDDO 
    941942 
     943    carb_mass_total(:) = val_exp 
     944    var_name = 'carb_mass_total' 
     945    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, & 
     946         &              .TRUE., carb_mass_total, 'gather', nbp_glo, index_g) 
     947    IF (ALL(carb_mass_total(:) == val_exp)) carb_mass_total(:) = zero 
    942948    !- 
    943949 
     
    971977       &  carbon, black_carbon, lignin_struc, turnover_time, & 
    972978       &  prod10,prod100 ,flux10, flux100, & 
    973        &  convflux, cflux_prod10, cflux_prod100, bm_to_litter) 
     979       &  convflux, cflux_prod10, cflux_prod100, bm_to_litter, carb_mass_total) 
    974980 
    975981    !--------------------------------------------------------------------- 
     
    11791185    REAL(r_std), DIMENSION(npts), INTENT(in)                            :: cflux_prod100 
    11801186    REAL(r_std),DIMENSION(npts,nvm,nparts),INTENT(in)                   :: bm_to_litter 
     1187    REAL(r_std),DIMENSION(npts),INTENT(in)                              :: carb_mass_total 
    11811188    !--------------------------------------------------------------------- 
    11821189    IF (bavard >= 3) WRITE(numout,*) 'Entering writerestart' 
     
    16431650            &                bm_to_litter(:,:,k), 'scatter', nbp_glo, index_g) 
    16441651    ENDDO 
     1652    var_name = 'carb_mass_total' 
     1653    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & 
     1654         &              carb_mass_total, 'scatter', nbp_glo, index_g) 
    16451655    !- 
    16461656    IF (bavard >= 4) WRITE(numout,*) 'Leaving writerestart' 
     
    17331743    LOGICAL :: do_again 
    17341744    !--------------------------------------------------------------------- 
    1735     ! 
     1745    !- 
    17361746    ! 1 If this is the first call, calculate the reference temperature 
    17371747    !   and keep it in memory 
  • branches/ORCHIDEE_EXT/ORCHIDEE/src_stomate/stomate_lpj.f90

    r304 r335  
    9393       t_photo_min, t_photo_opt, t_photo_max,bm_to_litter, & 
    9494       prod10,prod100,flux10, flux100, veget_max_new, & 
    95        convflux,cflux_prod10,cflux_prod100, harvest_above, lcchange, & 
     95       convflux,cflux_prod10,cflux_prod100, harvest_above, carb_mass_total, lcchange, & 
    9696       fpc_max) 
    9797 
     
    296296    ! harvest above ground biomass for agriculture 
    297297    REAL(r_std), DIMENSION(npts), INTENT(inout)                       :: harvest_above 
     298    ! Carbon Mass total 
     299    REAL(r_std), DIMENSION(npts), INTENT(inout)                       :: carb_mass_total 
    298300 
    299301    ! land cover change flag 
     
    322324    ! total soil carbon (gC/(m**2)) 
    323325    REAL(r_std), DIMENSION(npts,nvm)                                   :: tot_soil_carb 
     326    ! Carbon Mass variation 
     327    REAL(r_std), DIMENSION(npts)                                      :: carb_mass_variation 
    324328    ! crown area of individuals (m**2) 
    325329    REAL(r_std), DIMENSION(npts,nvm)                               :: cn_ind 
     
    752756         &             bm_to_litter(:,:,iheartabove) + bm_to_litter(:,:,iroot) + & 
    753757         &             bm_to_litter(:,:,ifruit) + bm_to_litter(:,:,icarbres) 
     758 
     759    carb_mass_variation(:)=-carb_mass_total(:) 
     760    carb_mass_total(:)=SUM((tot_live_biomass+tot_litter_carb+tot_soil_carb)*veget_max,dim=2) + & 
     761         &                 (prod10_total + prod100_total) 
     762    carb_mass_variation(:)=carb_mass_total(:)+carb_mass_variation(:) 
    754763 
    755764    ! 
     
    917926       CALL histwrite (hist_id_stomate_IPCC, "cProduct", itime, & 
    918927            vartmp, npts, hori_index) 
     928       vartmp(:)=carb_mass_variation/1e3/one_day*contfrac 
     929       CALL histwrite (hist_id_stomate_IPCC, "cMassVariation", itime, & 
     930            vartmp, npts, hori_index) 
    919931       vartmp(:)=SUM(lai*veget_max,dim=2)*contfrac 
    920932       CALL histwrite (hist_id_stomate_IPCC, "lai", itime, & 
Note: See TracChangeset for help on using the changeset viewer.