source: branches/publications/ORCHIDEE-PEAT_r5488/src_stomate/lpj_cover.f90 @ 6890

Last change on this file since 6890 was 6890, checked in by bertrand.guenet, 4 years ago

update of forcesoil and lpj_cover

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 23.1 KB
Line 
1! =================================================================================================================================
2! MODULE       : lpj_cover
3!
4! CONTACT      : orchidee-help _at_ ipsl.jussieu.fr
5!
6! LICENCE      : IPSL (2006)
7!                This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF        Recalculate vegetation cover and LAI
10!!
11!!\n DESCRIPTION : None
12!!
13!! RECENT CHANGE(S) : Including permafrost carbon
14!!
15!! REFERENCE(S) :
16!!        Sitch, S., B. Smith, et al. (2003), Evaluation of ecosystem dynamics,
17!!        plant geography and terrestrial carbon cycling in the LPJ dynamic
18!!        global vegetation model, Global Change Biology, 9, 161-185.\n
19!!        Smith, B., I. C. Prentice, et al. (2001), Representation of vegetation
20!!        dynamics in the modelling of terrestrial ecosystems: comparing two
21!!        contrasting approaches within European climate space,
22!!        Global Ecology and Biogeography, 10, 621-637.\n
23!!
24!! SVN :
25!! $HeadURL$
26!! $Date$
27!! $Revision$
28!! \n
29!_ ================================================================================================================================
30
31MODULE lpj_cover
32
33  ! modules used:
34
35  USE ioipsl_para
36  USE stomate_data
37  USE pft_parameters
38  USE constantes_soil_var
39
40  IMPLICIT NONE
41
42  ! private & public routines
43
44  PRIVATE
45  PUBLIC cover
46
47CONTAINS
48
49!! ================================================================================================================================
50!! SUBROUTINE     : lpj_cover
51!!
52!>\BRIEF          Recalculate vegetation cover and LAI
53!!
54!!\n DESCRIPTION : Veget_max is first renewed here according to newly calculated foliage biomass in this calculation step
55!! Then, litter, soil carbon, and biomass are also recalcuted with taking into account the changes in Veget_max (i.e. delta_veg)
56!! Grid-scale fpc (foliage projected coverage) is calculated to obtain the shadede ground area by leaf's light capture
57!! Finally, grid-scale fpc is adjusted not to exceed 1.0
58!!
59!! RECENT CHANGE(S) : None
60!!
61!! MAIN OUTPUT VARIABLE(S) : ::lai (leaf area index, @tex $(m^2 m^{-2})$ @endtex),
62!! :: veget (fractional vegetation cover, unitless)
63!!
64!! REFERENCE(S)   : None
65!!
66!! FLOWCHART :
67!! \latexonly
68!!     \includegraphics[scale=0.5]{lpj_cover_flowchart.png}
69!! \endlatexonly
70!! \n
71!_ ================================================================================================================================
72
73  SUBROUTINE cover (npts, cn_ind, ind, biomass, &
74       veget_max, veget_max_old, lai, & 
75       litter, litter_avail, litter_not_avail, carbon, &
76       fuel_1hr, fuel_10hr, fuel_100hr, fuel_1000hr, &
77       turnover_daily, bm_to_litter, &
78       co2_to_bm, co2_fire, resp_hetero, resp_maint, resp_growth, gpp_daily, &
79       deepC_a, deepC_s, deepC_p)
80
81!! 0. Variable and parameter declaration
82
83    !! 0.1 Input variables
84
85    INTEGER(i_std), INTENT(in)                                  :: npts             !! Domain size (unitless) 
86    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                :: cn_ind           !! Crown area
87                                                                                    !! @tex $(m^2)$ @endtex per individual
88    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                :: ind              !! Number of individuals
89                                                                                    !! @tex $(m^{-2})$ @endtex
90    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                :: veget_max_old    !! "Maximal" coverage fraction of a PFT (LAI->
91                                                                                    !! infinity) on ground at beginning of time
92    !! 0.2 Output variables
93
94    !! 0.3 Modified variables
95
96    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)             :: lai                 !! Leaf area index OF AN INDIVIDUAL PLANT
97                                                                                       !! @tex $(m^2 m^{-2})$ @endtex
98    REAL(r_std), DIMENSION(npts,nlitt,nvm,nlevs,nelements), INTENT(inout) :: litter    !! Metabolic and structural litter, above and
99    REAL(r_std), DIMENSION(npts,nvm,nlitt,nelements), INTENT(inout)                 :: fuel_1hr
100    REAL(r_std), DIMENSION(npts,nvm,nlitt,nelements), INTENT(inout)                 :: fuel_10hr
101    REAL(r_std), DIMENSION(npts,nvm,nlitt,nelements), INTENT(inout)                 :: fuel_100hr
102    REAL(r_std), DIMENSION(npts,nvm,nlitt,nelements), INTENT(inout)                 :: fuel_1000hr
103                                                                                       !! below ground @tex $(gC m^{-2})$ @endtex
104    REAL(r_std), DIMENSION(npts,nlitt,nvm), INTENT(inout):: litter_avail
105    REAL(r_std), DIMENSION(npts,nlitt,nvm) , INTENT(inout):: litter_not_avail
106    REAL(r_std), DIMENSION(npts,ncarb,nvm), INTENT(inout)             :: carbon        !! Carbon pool: active, slow, or passive
107    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(inout) :: biomass        !! Biomass @tex $(gC m^{-2})$ @endtex
108    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                  :: veget_max      !! "Maximal" coverage fraction of a PFT (LAI->
109                                                                                       !! infinity) on ground (unitless)
110    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(inout) :: turnover_daily !! Turnover rates (gC m^{-2} day^{-1})
111    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(inout) :: bm_to_litter   !! Conversion of biomass to litter
112                                                                                       !! @tex $(gC m^{-2} day^{-1})$ @endtex
113    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: co2_to_bm             !! biomass up take for establishment           
114    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: co2_fire
115    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: resp_hetero
116    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: resp_maint
117    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: resp_growth
118    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: gpp_daily
119
120    REAL(r_std), DIMENSION(npts,ndeep,nvm), INTENT(inout)         :: deepC_a           !! Permafrost soil carbon (g/m**3) active
121    REAL(r_std), DIMENSION(npts,ndeep,nvm), INTENT(inout)         :: deepC_s           !! Permafrost soil carbon (g/m**3) slow
122    REAL(r_std), DIMENSION(npts,ndeep,nvm), INTENT(inout)         :: deepC_p           !! Permafrost soil carbon (g/m**3) passive
123
124    !! 0.4 Local variables
125
126    INTEGER(i_std)                                              :: i,j,k,m               !! Index (unitless)
127    REAL(r_std), DIMENSION(npts,nlitt,nlevs,nelements)          :: dilu_lit              !! Litter dilution @tex $(gC m^{-2})$ @endtex
128    REAL(r_std), DIMENSION(npts,ncarb)                          :: dilu_soil_carbon      !! Soil Carbondilution
129                                                                                         !! @tex $(gC m^{-2})$ @endtex
130    REAL(r_std), DIMENSION(npts,nparts,nelements)               :: dilu_bio              !! Biomass dilution
131    REAL(r_std), DIMENSION(npts)                                :: dilu_TCarbon
132    REAL(r_std), DIMENSION(npts,nparts,nelements)               :: dilu_turnover_daily
133    REAL(r_std), DIMENSION(npts,nparts,nelements)               :: dilu_bm_to_litter
134    REAL(r_std), DIMENSION(npts)                                :: dilu_co2flux_new
135    REAL(r_std), DIMENSION(npts)                                :: dilu_gpp_daily
136    REAL(r_std), DIMENSION(npts)                                :: dilu_resp_growth
137    REAL(r_std), DIMENSION(npts)                                :: dilu_resp_maint
138    REAL(r_std), DIMENSION(npts)                                :: dilu_resp_hetero
139    REAL(r_std), DIMENSION(npts)                                :: dilu_co2_to_bm
140    REAL(r_std), DIMENSION(npts)                                :: dilu_co2_fire
141    REAL(r_std), DIMENSION(npts,nvm)                            :: TCarbon
142    REAL(r_std), DIMENSION(npts,nvm)                            :: co2flux_new
143    REAL(r_std), DIMENSION(npts,nvm)                            :: co2flux_old
144    REAL(r_std), DIMENSION(npts,ncarb,nvm)                       :: carbon_old
145    REAL(r_std),DIMENSION(npts,ndeep,ncarb)                     :: dilu_soil_carbon_vertres !!vertically-resolved Soil Carbondilution (gC/m²)
146
147    REAL(r_std), DIMENSION(nvm)                                 :: delta_veg        !! Conversion factors (unitless)
148    REAL(r_std), DIMENSION(nvm)                                 :: reduct           !! Conversion factors (unitless)
149    REAL(r_std)                                                 :: delta_veg_sum    !! Conversion factors (unitless)
150    REAL(r_std)                                                 :: diff             !! Conversion factors (unitless)
151    REAL(r_std)                                                 :: sr               !! Conversion factors (unitless)
152    REAL(r_std), DIMENSION(npts)                                :: frac_nat         !! Conversion factors (unitless)
153    REAL(r_std), DIMENSION(npts)                                :: sum_vegettree    !! Conversion factors (unitless)
154    REAL(r_std), DIMENSION(npts)                                :: sum_vegetgrass   !! Conversion factors (unitless)
155    REAL(r_std), DIMENSION(npts)                                :: sum_veget_natveg !! Conversion factors (unitless)
156    REAL(r_std), DIMENSION(npts)                                :: vartmp           !! Temporary variable used to add history
157    REAL(r_std), DIMENSION(npts,nlitt,nelements)                :: dilu_f1hr        !! Litter dilution @tex $(gC m^{-2})$ @endtex
158    REAL(r_std), DIMENSION(npts,nlitt,nelements)                :: dilu_f10hr       !! Litter dilution @tex $(gC m^{-2})$ @endtex
159    REAL(r_std), DIMENSION(npts,nlitt,nelements)                :: dilu_f100hr      !! Litter dilution @tex $(gC m^{-2})$ @endtex
160    REAL(r_std), DIMENSION(npts,nlitt,nelements)                :: dilu_f1000hr     !! Litter dilution @tex $(gC m^{-2})$ @endtex
161!_ ================================================================================================================================
162
163 !! 1. If the vegetation is dynamic, calculate new maximum vegetation cover for natural plants
164 
165    IF ( ok_dgvm ) THEN
166
167       !! 1.1  Calculate initial values of vegetation cover
168       frac_nat(:) = un
169       sum_veget_natveg(:) = zero
170       veget_max(:,ibare_sechiba) = un
171       co2flux_new = undef
172       co2flux_old = undef
173       TCarbon = undef
174
175       carbon_old(:,:,:)=carbon(:,:,:)
176
177       DO j = 2,nvm ! loop over PFTs
178          IF ( natural(j) .AND. .NOT. pasture(j) .AND. .NOT. is_peat(j)) THEN
179             
180             ! Summation of individual tree crown area to get total foliar projected coverage
181             veget_max(:,j) = ind(:,j) * cn_ind(:,j)
182             sum_veget_natveg(:) = sum_veget_natveg(:) + veget_max(:,j)
183          ELSE
184             
185             !fraction occupied by agriculture needs to be substracted for the DGVM
186             !this is used below to constrain veget for natural vegetation, see below
187             frac_nat(:) = frac_nat(:) - veget_max(:,j)
188
189          ENDIF
190
191       ENDDO ! loop over PFTs
192
193       DO i = 1, npts ! loop over grid points
194     
195          ! Recalculation of vegetation projected coverage when ::frac_nat was below ::sum_veget_natveg
196          ! It means that non-natural vegetation will recover ::veget_max as natural vegetation
197          IF (sum_veget_natveg(i) .GT. frac_nat(i) .AND. frac_nat(i) .GT. min_stomate) THEN
198
199             DO j = 2,nvm ! loop over PFTs
200                IF( natural(j) .AND. .NOT. pasture(j) .AND. .NOT. is_peat(j)) THEN
201                   veget_max(i,j) =  veget_max(i,j) * frac_nat(i) / sum_veget_natveg(i)
202                ENDIF
203             ENDDO ! loop over PFTs
204
205          ENDIF
206       ENDDO ! loop over grid points
207   
208       ! Renew veget_max of bare soil as 0 to difference of veget_max (ibare_sechiba)
209       ! to current veget_max
210       DO j = 2,nvm ! loop over PFTs
211          veget_max(:,ibare_sechiba) = veget_max(:,ibare_sechiba) - veget_max(:,j)
212       ENDDO ! loop over PFTs
213       veget_max(:,ibare_sechiba) = MAX( veget_max(:,ibare_sechiba), zero )
214
215       !! 1.2 Calculate carbon fluxes between PFTs to maintain mass balance
216       !! Assure carbon closure when veget_max changes(delta_veg): if veget_max of some PFTs decrease, we use "dilu" to
217       !! record the corresponding lost in carbon (biomass, litter, soil carbon, gpp, respiration etc.) for
218       !! these PFTs, and re-allocate "dilu" to those PFTs with increasing veget_max.
219       DO i = 1, npts ! loop over grid points
220         
221          ! Calculate the change in veget_max between previous time step and current time step
222          delta_veg(:) = veget_max(i,:)-veget_max_old(i,:)
223          delta_veg_sum = SUM(delta_veg,MASK=delta_veg.LT.zero)
224
225          dilu_lit(i,:,:,:) = zero
226          dilu_f1hr(i,:,:) = zero
227          dilu_f10hr(i,:,:) = zero
228          dilu_f100hr(i,:,:) = zero
229          dilu_f1000hr(i,:,:) = zero
230          dilu_soil_carbon(i,:) = zero
231          dilu_soil_carbon_vertres(i,:,:) = zero
232
233          dilu_bio(i,:,:) = zero
234          dilu_TCarbon(i)=zero
235
236          dilu_turnover_daily(i,:,:)=zero
237          dilu_bm_to_litter(i,:,:)=zero
238          dilu_co2flux_new(i)=zero
239          dilu_gpp_daily(i)=zero
240          dilu_resp_growth(i)=zero
241          dilu_resp_maint(i)=zero
242          dilu_resp_hetero(i)=zero
243          dilu_co2_to_bm(i)=zero
244          dilu_co2_fire(i)=zero
245
246          ! Calculate TCarbon: total carbon including biomass, litter and soil carbon, as well as "today's" turnover and
247          ! bm_to_litter due to mortality, because today's turnover and bm_to_litter are not yet added into "litter" until tomorrow.
248          DO j=1, nvm
249                TCarbon(i,j)=SUM(biomass(i,j,:,icarbon))+SUM(carbon(i,:,j))+SUM(litter(i,:,j,:,icarbon))+SUM(turnover_daily(i,j,:,icarbon))+SUM(bm_to_litter(i,j,:,icarbon))
250                co2flux_old(i,j)=resp_maint(i,j)+resp_growth(i,j)+resp_hetero(i,j)+co2_fire(i,j)-co2_to_bm(i,j)-gpp_daily(i,j)
251                co2flux_new(i,j)=resp_maint(i,j)+resp_growth(i,j)+resp_hetero(i,j)+co2_fire(i,j)-co2_to_bm(i,j)-gpp_daily(i,j)
252          ENDDO
253
254          DO j=1, nvm ! loop over PFTs
255             IF ( delta_veg(j) < -min_stomate ) THEN
256                dilu_lit(i,:,:,:) =  dilu_lit(i,:,:,:) + delta_veg(j) * litter(i,:,j,:,:) / delta_veg_sum
257                dilu_f1hr(i,:,:) =  dilu_f1hr(i,:,:) + delta_veg(j) * fuel_1hr(i,j,:,:) / delta_veg_sum
258                dilu_f10hr(i,:,:) =  dilu_f10hr(i,:,:) + delta_veg(j) * fuel_10hr(i,j,:,:) / delta_veg_sum
259                dilu_f100hr(i,:,:) =  dilu_f100hr(i,:,:) + delta_veg(j) * fuel_100hr(i,j,:,:) / delta_veg_sum
260                dilu_f1000hr(i,:,:) =  dilu_f1000hr(i,:,:) + delta_veg(j) * fuel_1000hr(i,j,:,:) / delta_veg_sum
261                dilu_soil_carbon(i,:) =  dilu_soil_carbon(i,:) + delta_veg(j) * carbon(i,:,j) / delta_veg_sum
262                dilu_TCarbon(i)= dilu_TCarbon(i) + delta_veg(j) * TCarbon(i,j) / delta_veg_sum
263                dilu_turnover_daily(i,:,:)=dilu_turnover_daily(i,:,:)+delta_veg(j)*turnover_daily(i,j,:,:)/delta_veg_sum
264                dilu_bm_to_litter(i,:,:)=dilu_bm_to_litter(i,:,:)+delta_veg(j)*bm_to_litter(i,j,:,:)/delta_veg_sum
265                dilu_co2flux_new(i)=dilu_co2flux_new(i)+delta_veg(j)*co2flux_old(i,j)/delta_veg_sum
266                dilu_gpp_daily(i)=dilu_gpp_daily(i)+delta_veg(j)*gpp_daily(i,j)/delta_veg_sum
267                dilu_resp_growth(i)=dilu_resp_growth(i)+delta_veg(j)*resp_growth(i,j)/delta_veg_sum
268                dilu_resp_maint(i)=dilu_resp_maint(i)+delta_veg(j)*resp_maint(i,j)/delta_veg_sum
269                dilu_resp_hetero(i)=dilu_resp_hetero(i)+delta_veg(j)*resp_hetero(i,j)/delta_veg_sum
270                dilu_co2_to_bm(i)=dilu_co2_to_bm(i)+delta_veg(j)*co2_to_bm(i,j)/delta_veg_sum
271                dilu_co2_fire(i)=dilu_co2_fire(i)+delta_veg(j)*co2_fire(i,j)/delta_veg_sum
272             ENDIF
273          ENDDO ! loop over PFTs
274
275          DO j=1, nvm ! loop over PFTs
276             IF ( delta_veg(j) > min_stomate) THEN
277
278                ! Dilution of reservoirs
279                ! Recalculate the litter and soil carbon with taking into accout the change in
280                ! veget_max (delta_veg)
281                ! Litter
282                litter(i,:,j,:,:)=(litter(i,:,j,:,:) * veget_max_old(i,j) + dilu_lit(i,:,:,:) * delta_veg(j)) / veget_max(i,j)
283                fuel_1hr(i,j,:,:)=(fuel_1hr(i,j,:,:) * veget_max_old(i,j) + dilu_f1hr(i,:,:) * delta_veg(j)) / veget_max(i,j)
284                fuel_10hr(i,j,:,:)=(fuel_10hr(i,j,:,:) * veget_max_old(i,j) + dilu_f10hr(i,:,:) * delta_veg(j)) / veget_max(i,j)
285                fuel_100hr(i,j,:,:)=(fuel_100hr(i,j,:,:) * veget_max_old(i,j) + dilu_f100hr(i,:,:) * delta_veg(j)) / veget_max(i,j)
286                fuel_1000hr(i,j,:,:)=(fuel_1000hr(i,j,:,:) * veget_max_old(i,j) + dilu_f1000hr(i,:,:) * delta_veg(j)) / veget_max(i,j)
287                !JCADD available and not available litter for grazing
288                ! only not available litter change, available litter will not
289                ! change, because tree litter can not be eaten
290               IF (is_grassland_manag(j) .AND. is_grassland_grazed(j)) THEN
291                 litter_avail(i,:,j) = litter_avail(i,:,j) * veget_max_old(i,j) / veget_max(i,j)
292                 litter_not_avail(i,:,j) = litter(i,:,j,iabove,icarbon) - litter_avail(i,:,j)
293               ENDIF
294                !ENDJCADD   
295                !IF ( ok_pc ) THEN
296                !   deepC_a(i,:,j)=(deepC_a(i,:,j) * veget_max_old(i,j) + &
297                !        dilu_soil_carbon_vertres(i,:,iactive) * delta_veg(j)) / veget_max(i,j)
298                !   deepC_s(i,:,j)=(deepC_s(i,:,j) * veget_max_old(i,j) + &
299                !        dilu_soil_carbon_vertres(i,:,islow) * delta_veg(j)) / veget_max(i,j)
300                !   deepC_p(i,:,j)=(deepC_p(i,:,j) * veget_max_old(i,j) + &
301                !        dilu_soil_carbon_vertres(i,:,ipassive) * delta_veg(j)) / veget_max(i,j)
302                !ENDIF
303                ! Soil carbon
304                carbon(i,:,j)=(carbon(i,:,j) * veget_max_old(i,j) + dilu_soil_carbon(i,:) * delta_veg(j)) / veget_max(i,j)
305                IF ( ok_pc ) THEN
306                   IF (carbon_old(i,iactive,j) .GT. min_stomate) THEN
307                      deepC_a(i,:,j)=deepC_a(i,:,j)*carbon(i,iactive,j)/carbon_old(i,iactive,j)
308                   ENDIF
309                   IF (carbon_old(i,islow,j) .GT. min_stomate) THEN
310                      deepC_s(i,:,j)=deepC_s(i,:,j)*carbon(i,islow,j)/carbon_old(i,islow,j)
311                   ENDIF
312                   IF (carbon_old(i,ipassive,j) .GT. min_stomate) THEN
313                      deepC_p(i,:,j)=deepC_p(i,:,j)*carbon(i,ipassive,j)/carbon_old(i,ipassive,j)
314                   ENDIF
315                ENDIF
316
317                !biomass(i,j,:,:)=(biomass(i,j,:,:) * veget_max_old(i,j) + dilu_bio(i,:,:) * delta_veg(j)) / veget_max(i,j)
318                TCarbon(i,j)=(TCarbon(i,j) * veget_max_old(i,j) + dilu_TCarbon(i) * delta_veg(j)) / veget_max(i,j)
319
320                turnover_daily(i,j,:,:)=(turnover_daily(i,j,:,:)*veget_max_old(i,j)+dilu_turnover_daily(i,:,:)*delta_veg(j))/veget_max(i,j)
321                bm_to_litter(i,j,:,:)=(bm_to_litter(i,j,:,:)*veget_max_old(i,j)+dilu_bm_to_litter(i,:,:)*delta_veg(j))/veget_max(i,j)
322                co2flux_new(i,j)=(co2flux_old(i,j)*veget_max_old(i,j)+dilu_co2flux_new(i)*delta_veg(j))/veget_max(i,j)
323                gpp_daily(i,j)=(gpp_daily(i,j)*veget_max_old(i,j)+dilu_gpp_daily(i)*delta_veg(j))/veget_max(i,j)
324                resp_growth(i,j)=(resp_growth(i,j)*veget_max_old(i,j)+dilu_resp_growth(i)*delta_veg(j))/veget_max(i,j)
325                resp_maint(i,j)=(resp_maint(i,j)*veget_max_old(i,j)+dilu_resp_maint(i)*delta_veg(j))/veget_max(i,j)
326                resp_hetero(i,j)=(resp_hetero(i,j)*veget_max_old(i,j)+dilu_resp_hetero(i)*delta_veg(j))/veget_max(i,j)
327                co2_to_bm(i,j)=(co2_to_bm(i,j)*veget_max_old(i,j)+dilu_co2_to_bm(i)*delta_veg(j))/veget_max(i,j)
328                co2_fire(i,j)=(co2_fire(i,j)*veget_max_old(i,j)+dilu_co2_fire(i)*delta_veg(j))/veget_max(i,j)
329
330             ENDIF
331
332             IF(veget_max(i,j).GT.min_stomate) THEN
333
334                ! Correct biomass densities to conserve mass
335                ! since it's defined on veget_max
336                biomass(i,j,:,:) = biomass(i,j,:,:) * veget_max_old(i,j) / veget_max(i,j)
337
338             ENDIF
339
340          ENDDO ! loop over PFTs
341      ENDDO ! loop over grid points
342
343      vartmp(:)=SUM(co2flux_new*veget_max,dim=2)
344      CALL histwrite_p (hist_id_stomate, "tCO2FLUX", itime, vartmp, npts, hori_index)
345      vartmp(:)=SUM(co2flux_old*veget_max_old,dim=2)
346      CALL histwrite_p (hist_id_stomate, "tCO2FLUX_OLD", itime, vartmp, npts, hori_index)
347      vartmp(:)=SUM(TCarbon*veget_max,dim=2)
348      CALL histwrite_p (hist_id_stomate, "tCARBON", itime, vartmp, npts, hori_index)
349      vartmp(:)=SUM(gpp_daily*veget_max,dim=2)
350      CALL histwrite_p (hist_id_stomate, "tGPP", itime, vartmp, npts, hori_index)
351      vartmp(:)=SUM(resp_growth*veget_max,dim=2)
352      CALL histwrite_p (hist_id_stomate, "tRESP_GROWTH", itime, vartmp, npts, hori_index)
353      vartmp(:)=SUM(resp_maint*veget_max,dim=2)
354      CALL histwrite_p (hist_id_stomate, "tRESP_MAINT", itime, vartmp, npts, hori_index)
355      vartmp(:)=SUM(resp_hetero*veget_max,dim=2)
356      CALL histwrite_p (hist_id_stomate, "tRESP_HETERO", itime, vartmp, npts, hori_index)
357      vartmp(:)=SUM(co2_to_bm*veget_max,dim=2)
358      CALL histwrite_p (hist_id_stomate, "tCO2_TAKEN", itime, vartmp, npts, hori_index)
359      vartmp(:)=SUM(co2_fire*veget_max,dim=2)
360      CALL histwrite_p (hist_id_stomate, "tCO2_FIRE", itime, vartmp, npts, hori_index)
361      vartmp(:)=SUM(SUM(biomass(:,:,:,icarbon),dim=3)*veget_max,dim=2)
362      CALL histwrite_p (hist_id_stomate, "tBIOMASS", itime, vartmp, npts, hori_index)
363      vartmp(:)=SUM(SUM(SUM(litter(:,:,:,:,icarbon),dim=4),dim=2)*veget_max,dim=2)
364      CALL histwrite_p (hist_id_stomate, "tLITTER", itime, vartmp, npts, hori_index)
365      vartmp(:)=SUM(SUM(fuel_1hr(:,:,:,icarbon),dim=3)*veget_max,dim=2)
366      CALL histwrite_p (hist_id_stomate, "tFUEL1HR", itime, vartmp, npts, hori_index)
367      vartmp(:)=SUM(SUM(fuel_10hr(:,:,:,icarbon),dim=3)*veget_max,dim=2)
368      CALL histwrite_p (hist_id_stomate, "tFUEL10HR", itime, vartmp, npts, hori_index)
369      vartmp(:)=SUM(SUM(fuel_100hr(:,:,:,icarbon),dim=3)*veget_max,dim=2)
370      CALL histwrite_p (hist_id_stomate, "tFUEL100HR", itime, vartmp, npts, hori_index)
371      vartmp(:)=SUM(SUM(fuel_1000hr(:,:,:,icarbon),dim=3)*veget_max,dim=2)
372      CALL histwrite_p (hist_id_stomate, "tFUEL1000HR", itime, vartmp, npts, hori_index)
373      vartmp(:)=SUM(SUM(carbon,dim=2)*veget_max,dim=2)
374      CALL histwrite_p (hist_id_stomate, "tSOILC", itime, vartmp, npts, hori_index)
375
376      IF ( ok_pc ) THEN
377        vartmp(:)=SUM(SUM(deepC_a,dim=2)*veget_max,dim=2)
378        CALL histwrite_p (hist_id_stomate, "tDEEPCa", itime, vartmp, npts, hori_index)
379        vartmp(:)=SUM(SUM(deepC_s,dim=2)*veget_max,dim=2)
380        CALL histwrite_p (hist_id_stomate, "tDEEPCs", itime, vartmp, npts, hori_index)
381        vartmp(:)=SUM(SUM(deepC_p,dim=2)*veget_max,dim=2)
382        CALL histwrite_p (hist_id_stomate, "tDEEPCp", itime, vartmp, npts, hori_index)
383      ENDIF
384
385   ENDIF
386
387  END SUBROUTINE cover
388
389END MODULE lpj_cover
Note: See TracBrowser for help on using the repository browser.