Ignore:
Timestamp:
2019-11-29T15:58:40+01:00 (5 years ago)
Author:
josefine.ghattas
Message:

Integrated correction of diagnostic variables rhSoil and rhLitter as done in the trunk rev [6362]. See ticket #630

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate/stomate.f90

    r6319 r6369  
    259259                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex 
    260260!$OMP THREADPRIVATE(resp_hetero_d) 
     261  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: resp_hetero_litter_d !! Heterotrophic respiration from litter per ground area  
     262                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex 
     263!$OMP THREADPRIVATE(resp_hetero_litter_d) 
     264  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: resp_hetero_soil_d   !! Heterotrophic respiration from soil per ground area  
     265                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex 
     266!$OMP THREADPRIVATE(resp_hetero_soil_d) 
    261267  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: resp_hetero_radia    !! Heterothrophic respiration per ground area at Sechiba 
    262268                                                                         !! time step  
     
    15051511    resp_hetero_radia(:,:) = resp_hetero_litter(:,:) + resp_hetero_soil(:,:) 
    15061512    resp_hetero_d(:,:) = resp_hetero_d(:,:) + resp_hetero_radia(:,:) 
     1513    resp_hetero_litter_d(:,:) = resp_hetero_litter_d(:,:) + resp_hetero_litter(:,:) 
     1514    resp_hetero_soil_d(:,:) = resp_hetero_soil_d(:,:) + resp_hetero_soil(:,:) 
     1515 
    15071516     
    15081517    !! 4.6 Accumulate instantaneous variables (do_slow=.FALSE.)  
     
    15951604            &             control_moist_inst, control_temp_inst, soilcarbon_input_inst, & 
    15961605            &             co2_to_bm_dgvm, co2_fire, & 
    1597             &             resp_hetero_d, resp_maint_d, resp_growth_d, & 
     1606            &             resp_hetero_d, resp_hetero_litter_d, resp_hetero_soil_d, resp_maint_d, resp_growth_d, & 
    15981607            &             height, deadleaf_cover, vcmax, & 
    15991608            &             bm_to_litter,& 
     
    17671776 
    17681777       CALL xios_orchidee_send_field("nep",SUM(nep_daily*veget_cov_max,dim=2)/1e3/one_day) 
    1769        CALL xios_orchidee_send_field("rhSoil",SUM(resp_hetero_soil*veget_cov_max,dim=2)/1e3) 
    1770        CALL xios_orchidee_send_field("rhLitter",SUM(resp_hetero_litter*veget_cov_max,dim=2)/1e3) 
    17711778 
    17721779       ! Calculate co2_flux as (-1)*nep_daily*veget_cov_max.  
     
    18531860       resp_maint_part(:,:,:)=zero 
    18541861       resp_hetero_d=zero 
     1862       resp_hetero_litter_d=zero 
     1863       resp_hetero_soil_d=zero 
     1864 
    18551865       IF (printlev >= 3) THEN 
    18561866          WRITE(numout,*) 'stomate_main: daily processes done' 
     
    28302840    ENDIF 
    28312841 
     2842    ALLOCATE(resp_hetero_litter_d(kjpindex,nvm),stat=ier) 
     2843    l_error = l_error .OR. (ier /= 0) 
     2844    IF (l_error) THEN 
     2845       WRITE(numout,*) 'Memory allocation error for resp_hetero_litter_d. We stop. We need kjpindex*nvm words',kjpindex,nvm 
     2846       STOP 'stomate_init' 
     2847    ENDIF 
     2848 
     2849    ALLOCATE(resp_hetero_soil_d(kjpindex,nvm),stat=ier) 
     2850    l_error = l_error .OR. (ier /= 0) 
     2851    IF (l_error) THEN 
     2852       WRITE(numout,*) 'Memory allocation error for resp_hetero_soil_d. We stop. We need kjpindex*nvm words',kjpindex,nvm 
     2853       STOP 'stomate_init' 
     2854    ENDIF 
     2855 
    28322856    ALLOCATE(resp_hetero_radia(kjpindex,nvm),stat=ier) 
    28332857    l_error = l_error .OR. (ier /= 0) 
     
    34253449    turnover_daily(:,:,:,:) = zero 
    34263450    resp_hetero_d(:,:) = zero 
     3451    resp_hetero_litter_d(:,:) = zero 
     3452    resp_hetero_soil_d(:,:) = zero 
    34273453    nep_daily(:,:) = zero 
    34283454    nep_monthly(:,:) = zero 
     
    35383564    IF (ALLOCATED(age))  DEALLOCATE(age) 
    35393565    IF (ALLOCATED(resp_hetero_d)) DEALLOCATE(resp_hetero_d) 
     3566    IF (ALLOCATED(resp_hetero_litter_d)) DEALLOCATE(resp_hetero_litter_d) 
     3567    IF (ALLOCATED(resp_hetero_soil_d)) DEALLOCATE(resp_hetero_soil_d) 
    35403568    IF (ALLOCATED(resp_hetero_radia)) DEALLOCATE(resp_hetero_radia) 
    35413569    IF (ALLOCATED(resp_maint_d)) DEALLOCATE(resp_maint_d) 
Note: See TracChangeset for help on using the changeset viewer.