source: branches/publications/ORCHIDEE-Clateral/src_stomate/stomate.f90 @ 7346

Last change on this file since 7346 was 7191, checked in by haicheng.zhang, 3 years ago

Implementing latral transfers of sediment and POC from land to ocean through river in ORCHILEAK

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 327.9 KB
Line 
1! =================================================================================================================================
2! MODULE       : stomate
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF       Groups the subroutines that: (1) initialize all variables in
10!! stomate, (2) read and write forcing files of stomate and the soil component,
11!! (3) aggregates and convert variables to handle the different time steps
12!! between sechiba and stomate, (4) call subroutines that govern major stomate
13!! processes (litter, soil, and vegetation dynamics) and (5) structures these tasks
14!! in stomate_main
15!!
16!!\n DESCRIPTION : None
17!!
18!! RECENT CHANGE(S) : None
19!!
20!! REFERENCE(S) : None
21!!
22!! SVN :
23!! $HeadURL$
24!! $Date$
25!! $Revision$
26!! \n
27!_ ================================================================================================================================
28
29MODULE stomate
30
31  ! Modules used:
32  USE netcdf
33  USE defprec
34  USE grid
35  USE time, ONLY : one_day, one_year, dt_sechiba, dt_stomate, LastTsYear, LastTsMonth
36  USE time, ONLY : year_end, month_end, day_end, sec_end
37  USE constantes
38  USE constantes_soil
39  USE pft_parameters
40  USE stomate_io
41  USE stomate_data
42  USE stomate_season
43  USE stomate_lpj
44  USE stomate_litter
45  USE stomate_vmax
46  USE stomate_soilcarbon
47  USE stomate_resp
48  USE mod_orchidee_para
49  USE ioipsl_para 
50  USE xios_orchidee
51
52  USE matrix_resolution
53 
54  IMPLICIT NONE
55
56  ! Private & public routines
57
58  PRIVATE
59  PUBLIC stomate_main,stomate_clear,init_forcing, stomate_forcing_read, stomate_initialize, stomate_finalize
60
61  INTERFACE stomate_accu
62     MODULE PROCEDURE stomate_accu_r1d, stomate_accu_r2d, stomate_accu_r3d
63  END INTERFACE
64
65  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:):: biomass              !! Biomass per ground area @tex $(gC m^{-2})$ @endtex
66!$OMP THREADPRIVATE(biomass)
67  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: veget_cov_max        !! Maximal fractional coverage: maximum share of a pixel
68                                                                         !! taken by a PFT
69!$OMP THREADPRIVATE(veget_cov_max)
70  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: ind                  !! Vegetation density, number of individuals per unit
71                                                                         !! ground area @tex $(m^{-2})$ @endtex
72!$OMP THREADPRIVATE(ind)
73  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: age                  !! Age of PFT it normalized by biomass - can increase and
74                                                                         !! decrease - (years)
75!$OMP THREADPRIVATE(age)
76  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: adapted              !! Winter too cold for PFT to survive (0-1, unitless)
77!$OMP THREADPRIVATE(adapted)
78  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: regenerate           !! Winter sufficiently cold to produce viable seeds
79                                                                         !! (0-1, unitless)
80!$OMP THREADPRIVATE(regenerate)
81  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: everywhere           !! Is the PFT everywhere in the grid box or very localized
82                                                                         !! (after its intoduction)
83!$OMP THREADPRIVATE(everywhere)
84  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: fireindex            !! Probability of fire (unitless)
85!$OMP THREADPRIVATE(fireindex)
86  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: veget_lastlight      !! Vegetation fractions (on ground) after last light
87                                                                         !! competition (unitless)
88!$OMP THREADPRIVATE(veget_lastlight)
89  REAL(r_std), ALLOCATABLE,SAVE,DIMENSION(:,:)   :: fpc_max              !! "maximal" coverage fraction of a grid box (LAI ->
90                                                                         !! infinity) on ground. [??CHECK??] It's set to zero here,
91                                                                         !! and then is used once in lpj_light.f90 to test if
92                                                                         !! fpc_nat is greater than it. Something seems missing
93!$OMP THREADPRIVATE(fpc_max)
94  LOGICAL,ALLOCATABLE,SAVE,DIMENSION(:,:)        :: PFTpresent           !! PFT exists (equivalent to veget > 0 for natural PFTs)
95!$OMP THREADPRIVATE(PFTpresent)
96  LOGICAL,ALLOCATABLE,SAVE,DIMENSION(:,:)        :: senescence           !! The PFT is senescent
97!$OMP THREADPRIVATE(senescence)
98  LOGICAL,ALLOCATABLE,SAVE,DIMENSION(:,:)        :: begin_leaves         !! Signal to start putting leaves on (true/false)
99!$OMP THREADPRIVATE(begin_leaves)
100  LOGICAL,ALLOCATABLE,SAVE,DIMENSION(:,:)        :: need_adjacent        !! This PFT needs to be in present in an adjacent gridbox
101                                                                         !! if it is to be introduced in a new gridbox
102!$OMP THREADPRIVATE(need_adjacent)
103!--
104  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: humrel_daily         !! Daily plant available water -root profile weighted
105                                                                         !! (0-1, unitless)
106!$OMP THREADPRIVATE(humrel_daily)
107  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: humrel_week          !! "Weekly" plant available water -root profile weighted
108                                                                         !! (0-1, unitless)
109!$OMP THREADPRIVATE(humrel_week)
110  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: humrel_month         !! "Monthly" plant available water -root profile weighted
111                                                                         !! (0-1, unitless)
112!$OMP THREADPRIVATE(humrel_month)
113  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: maxhumrel_lastyear   !! Last year's max plant available water -root profile
114                                                                         !! weighted (0-1, unitless)
115!$OMP THREADPRIVATE(maxhumrel_lastyear)
116  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: maxhumrel_thisyear   !! This year's max plant available water -root profile
117                                                                         !! weighted (0-1, unitless)
118!$OMP THREADPRIVATE(maxhumrel_thisyear)
119  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: minhumrel_lastyear   !! Last year's min plant available water -root profile
120                                                                         !! weighted (0-1, unitless) 
121!$OMP THREADPRIVATE(minhumrel_lastyear)
122  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: minhumrel_thisyear   !! This year's minimum plant available water -root profile
123                                                                         !! weighted (0-1, unitless)
124!$OMP THREADPRIVATE(minhumrel_thisyear)
125!--- 
126  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: t2m_daily            !! Daily air temperature at 2 meter (K)
127!$OMP THREADPRIVATE(t2m_daily)
128
129  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: Tseason              !! "seasonal" 2 meter temperatures (K)
130!$OMP THREADPRIVATE(Tseason)
131  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: Tseason_length       !! temporary variable to calculate Tseason
132!$OMP THREADPRIVATE(Tseason_length)
133  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: Tseason_tmp          !! temporary variable to calculate Tseason
134!$OMP THREADPRIVATE(Tseason_tmp)
135  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: Tmin_spring_time     !! Number of days after begin_leaves (leaf onset)
136!$OMP THREADPRIVATE(Tmin_spring_time)
137  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: onset_date           !! Date in the year at when the leaves started to grow(begin_leaves), only for diagnostics.
138!$OMP THREADPRIVATE(onset_date)
139  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: t2m_week             !! Mean "weekly" (default 7 days) air temperature at 2
140                                                                         !! meter (K) 
141!$OMP THREADPRIVATE(t2m_week)
142  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: t2m_month            !! Mean "monthly" (default 20 days) air temperature at 2
143                                                                         !! meter (K)
144!$OMP THREADPRIVATE(t2m_month)
145  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: t2m_longterm         !! Mean "Long term" (default 3 years) air temperature at
146                                                                         !! 2 meter (K)
147!$OMP THREADPRIVATE(t2m_longterm)
148  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: t2m_min_daily        !! Daily minimum air temperature at 2 meter (K)
149!$OMP THREADPRIVATE(t2m_min_daily)
150  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: tsurf_daily          !! Daily surface temperatures (K)
151!$OMP THREADPRIVATE(tsurf_daily)
152!---
153  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: precip_daily         !! Daily precipitations sum @tex $(mm day^{-1})$ @endtex
154!$OMP THREADPRIVATE(precip_daily)
155  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: precip_lastyear      !! Last year's annual precipitation sum
156                                                                         !! @tex $??(mm year^{-1})$ @endtex
157!$OMP THREADPRIVATE(precip_lastyear)
158  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: precip_thisyear      !! This year's annual precipitation sum
159                                                                         !! @tex $??(mm year^{-1})$ @endtex
160!$OMP THREADPRIVATE(precip_thisyear)
161!---
162  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: soilhum_daily        !! Daily soil humidity (0-1, unitless)
163!$OMP THREADPRIVATE(soilhum_daily)
164  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: soilhum_month        !! Soil humidity - integrated over a month (0-1, unitless)
165!$OMP THREADPRIVATE(soilhum_month)
166  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: tsoil_daily          !! Daily soil temperatures (K)
167!$OMP THREADPRIVATE(tsoil_daily)
168  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: tsoil_month          !! Soil temperatures at each soil layer integrated over a
169                                                                         !! month (K)
170!$OMP THREADPRIVATE(tsoil_month)
171!---
172  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: litterhum_daily      !! Daily litter humidity (0-1, unitless)
173!$OMP THREADPRIVATE(litterhum_daily)
174!---
175  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: control_moist_above  !! Moisture control of heterotrophic respiration 
176                                                                         !! (0-1, unitless)
177!$OMP THREADPRIVATE(control_moist_above)
178  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:) :: control_moist_soil  !! Moisture control of heterotrophic respiration
179                                                                         !! (0-1, unitless)
180!$OMP THREADPRIVATE(control_moist_soil)
181  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: moist_soil           !! Soil moiture (m3 H20 m-3 Soil)
182!$OMP THREADPRIVATE(moist_soil)
183  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:) :: soil_mc_Cforcing    !! Soil moiture per soil type (m3 H20 m-3 Soil)
184!$OMP THREADPRIVATE(soil_mc_Cforcing)
185  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:) :: floodout_Cforcing       !! flux out of floodplains
186!$OMP THREADPRIVATE(floodout_Cforcing)
187  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:) :: wat_flux0_Cforcing    !! Water flux in the first soil layers exported for soil C calculations
188!$OMP THREADPRIVATE(wat_flux0_Cforcing)
189  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:):: wat_flux_Cforcing    !! Water flux in the soil layers exported for soil C calculations
190!$OMP THREADPRIVATE(wat_flux_Cforcing)
191  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:) ::runoff_per_soil_Cforcing   !! Runoff per soil type [mm]
192!$OMP THREADPRIVATE(runoff_per_soil_Cforcing)
193  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:) ::drainage_per_soil_Cforcing  !! Drainage per soil type [mm]
194!$OMP THREADPRIVATE(drainage_per_soil_Cforcing)
195  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:) :: DOC_to_topsoil_Cforcing    !! DOC inputs to top of the soil column, from reinfiltration on
196                                                                              !! floodplains and from irrigation
197                                                                              !! @tex $(gC m^{-2} day{-1})$ @endtex
198!$OMP THREADPRIVATE(DOC_to_topsoil_Cforcing)
199  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:) :: DOC_to_subsoil_Cforcing    !! DOC inputs to bottom of the soil column, from returnflow
200                                                                              !! in swamps and lakes
201                                                                              !! @tex $(gC m^{-2} day{-1})$ @endtex
202!$OMP THREADPRIVATE(DOC_to_subsoil_Cforcing)
203  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:) :: precip2canopy_Cforcing     !! Precipitation onto the canopy
204!$OMP THREADPRIVATE(precip2canopy_Cforcing)
205  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:) :: precip2ground_Cforcing     !! Precipitation not intercepted by canopy
206!$OMP THREADPRIVATE(precip2ground_Cforcing)
207  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:) :: canopy2ground_Cforcing     !! Water flux from canopy to the ground
208!$OMP THREADPRIVATE(canopy2ground_Cforcing)
209  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)   :: flood_frac_Cforcing        !! flooded fraction of the grid box (1)
210!$OMP THREADPRIVATE(flood_frac_Cforcing)
211
212  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: control_temp_above   !! Temperature control of heterotrophic respiration at the
213                                                                         !! different soil levels (0-1, unitless)
214!$OMP THREADPRIVATE(control_temp_above)
215  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:)  :: control_temp_soil   !! Temperature control of heterotrophic respiration at the
216                                                                         !! different soil levels (0-1,unitless)
217!$OMP THREADPRIVATE(control_temp_soil)
218  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: control_moist_above_daily  !! Moisture control of heterotrophic respiration daily 
219                                                                             !! (0-1, unitless)
220!$OMP THREADPRIVATE(control_moist_above_daily)
221  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:) :: control_temp_above_daily   !!Temperature control of heterotrophic respiration, above
222                                                                           !! and below daily (0-1,unitless)
223!$OMP THREADPRIVATE(control_temp_above_daily)
224  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: control_moist_soil_daily  !! Moisture control of heterotrophic respiration daily
225                                                                         !! (0-1, unitless)
226!$OMP THREADPRIVATE(control_moist_soil_daily)
227  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: moist_soil_daily     !! Soil moiture daily (m3 H20 m-3 Soil)
228!$OMP THREADPRIVATE(moist_soil_daily)
229  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: soil_mc_Cforcing_daily   !! Soil moiture per soil type daily (m3 H20 m-3 Soil)
230!$OMP THREADPRIVATE(soil_mc_Cforcing_daily)
231  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:) :: floodout_Cforcing_daily       !! flux out of floodplains
232!$OMP THREADPRIVATE(floodout_Cforcing_daily)
233  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:) :: wat_flux0_Cforcing_daily    !! Water flux in the first soil layers exported for soil C calculations
234!$OMP THREADPRIVATE(wat_flux0_Cforcing_daily)
235  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:):: wat_flux_Cforcing_daily    !! Water flux in the soil layers exported for soil C calculations
236!$OMP THREADPRIVATE(wat_flux_Cforcing_daily)
237  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:) ::runoff_per_soil_Cforcing_daily   !! Runoff per soil type [mm]
238!$OMP THREADPRIVATE(runoff_per_soil_Cforcing_daily)
239  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:) ::drainage_per_soil_Cforcing_daily  !! Drainage per soil type [mm]
240!$OMP THREADPRIVATE(drainage_per_soil_Cforcing_daily)
241  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:) :: DOC_to_topsoil_Cforcing_daily    !! DOC inputs to top of the soil column, from reinfiltration on
242                                                                                  !! floodplains and from irrigation
243                                                                                  !! @tex $(gC m^{-2} day{-1})$ @endtex
244!$OMP THREADPRIVATE(DOC_to_topsoil_Cforcing_daily)
245  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:) :: DOC_to_subsoil_Cforcing_daily    !! DOC inputs to bottom of the soil column, from returnflow
246                                                                                  !! in swamps and lakes
247                                                                                  !! @tex $(gC m^{-2} day{-1})$ @endtex
248!$OMP THREADPRIVATE(DOC_to_subsoil_Cforcing_daily)
249  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:) :: precip2canopy_Cforcing_daily     !! Precipitation onto the canopy
250!$OMP THREADPRIVATE(precip2canopy_Cforcing)
251  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:) :: precip2ground_Cforcing_daily     !! Precipitation not intercepted by canopy
252!$OMP THREADPRIVATE(precip2ground_Cforcing)
253  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:) :: canopy2ground_Cforcing_daily     !! Water flux from canopy to the ground
254!$OMP THREADPRIVATE(canopy2ground_Cforcing)
255  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: flood_frac_Cforcing_daily     !! Flooded fraction of the grid box (1)
256!$OMP THREADPRIVATE(flood_Cforcing_daily)
257  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: control_temp_soil_daily   !! Temperature control of heterotrophic respiration, above
258                                                                         !! and below daily (0-1, unitless)
259  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: gdd_init_date        !! inital date for gdd count
260!$OMP THREADPRIVATE(gdd_init_date)
261
262  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: gdd_from_growthinit  !! gdd from beginning of season (C)
263!$OMP THREADPRIVATE(gdd_from_growthinit)
264  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: gdd0_lastyear        !! Last year's annual Growing Degree Days,
265                                                                         !! threshold 0 deg C (K)
266!$OMP THREADPRIVATE(gdd0_lastyear)
267  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: gdd0_thisyear        !! This year's annual Growing Degree Days,
268                                                                         !! threshold 0 deg C (K)
269!$OMP THREADPRIVATE(gdd0_thisyear)
270  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: gdd_m5_dormance      !! Growing degree days for onset of growing season,
271                                                                         !! threshold -5 deg C (K)
272!$OMP THREADPRIVATE(gdd_m5_dormance)
273  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: gdd_midwinter        !! Growing degree days for onset of growing season,
274                                                                         !! since midwinter (K)
275!$OMP THREADPRIVATE(gdd_midwinter)
276  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: ncd_dormance         !! Number of chilling days since leaves were lost (days)
277!$OMP THREADPRIVATE(ncd_dormance)
278  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: ngd_minus5           !! Number of growing days, threshold -5 deg C (days)
279!$OMP THREADPRIVATE(ngd_minus5)
280  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: hum_min_dormance     !! Minimum moisture during dormance (0-1, unitless)
281!$OMP THREADPRIVATE(hum_min_dormance)
282!---
283  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: gpp_daily            !! Daily gross primary productivity per ground area
284                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
285!$OMP THREADPRIVATE(gpp_daily)
286  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: gpp_week             !! Mean "weekly" (default 7 days) GPP 
287                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
288!$OMP THREADPRIVATE(gpp_week)
289  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: maxgppweek_lastyear  !! Last year's maximum "weekly" GPP 
290                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
291!$OMP THREADPRIVATE(maxgppweek_lastyear)
292  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: maxgppweek_thisyear  !! This year's maximum "weekly" GPP 
293                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex 
294!$OMP THREADPRIVATE(maxgppweek_thisyear)
295!---
296  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: npp_daily            !! Daily net primary productivity per ground area
297                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
298!$OMP THREADPRIVATE(npp_daily)
299  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: npp_longterm         !! "Long term" (default 3 years) net primary productivity
300                                                                         !! per ground area 
301                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex   
302!$OMP THREADPRIVATE(npp_longterm)
303  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: npp_equil            !! Equilibrium NPP written to forcesoil
304                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex
305!$OMP THREADPRIVATE(npp_equil)
306  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: npp_tot              !! Total NPP written to forcesoil
307                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex
308!$OMP THREADPRIVATE(npp_tot)
309!---
310  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: resp_maint_part_radia!! Maintenance respiration of different plant parts per
311                                                                         !! total ground area at Sechiba time step 
312                                                                         !! @tex $(gC m^{-2} dt_sechiba^{-1})$ @endtex
313!$OMP THREADPRIVATE(resp_maint_part_radia)
314  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: resp_maint_part      !! Maintenance respiration of different plant parts per
315                                                                         !! total ground area at Stomate time step
316                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
317!$OMP THREADPRIVATE(resp_maint_part)
318  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: resp_maint_radia     !! Maintenance respiration per ground area at Sechiba time
319                                                                         !! step   
320                                                                         !! @tex $(gC m^{-2} dt_sechiba^{-1})$ @endtex
321!$OMP THREADPRIVATE(resp_maint_radia)
322  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: resp_maint_d         !! Maintenance respiration per ground area at Stomate time
323                                                                         !! step 
324                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
325!$OMP THREADPRIVATE(resp_maint_d)
326  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: resp_growth_d        !! Growth respiration per ground area
327                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
328!$OMP THREADPRIVATE(resp_growth_d)
329  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: resp_hetero_d        !! Heterotrophic respiration per ground area
330                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
331!$OMP THREADPRIVATE(resp_hetero_d)
332  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: resp_hetero_radia    !! Heterothrophic respiration per ground area at Sechiba
333                                                                         !! time step
334                                                                         !! @tex $(gC m^{-2} dt_sechiba^{-1})$ @endtex
335!$OMP THREADPRIVATE(resp_hetero_radia)
336  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: tot_soil_resp_d      !! Belowground het resp + root resp per ground area
337                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
338!$OMP THREADPRIVATE(tot_soil_resp_d)
339!---
340  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)     :: turnover_time       !! Turnover time of grasses
341                                                                         !! @tex $(dt_stomate^{-1})$ @endtex
342!$OMP THREADPRIVATE(turnover_time)
343  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:) :: turnover_daily      !! Senescence-driven turnover (better: mortality) of
344                                                                         !! leaves and roots 
345                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
346!$OMP THREADPRIVATE(turnover_daily)
347  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:) :: turnover_littercalc !! Senescence-driven turnover (better: mortality) of
348                                                                         !! leaves and roots at Sechiba time step
349                                                                         !! @tex $(gC m^{-2} dt_sechiba^{-1})$ @endtex
350!$OMP THREADPRIVATE(turnover_littercalc)
351  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:) :: turnover_longterm   !! "Long term" (default 3 years) senescence-driven
352                                                                         !! turnover (better: mortality) of leaves and roots
353                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex
354!$OMP THREADPRIVATE(turnover_longterm)
355  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:) :: bm_to_litter        !! Background (not senescence-driven) mortality of biomass
356                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
357!$OMP THREADPRIVATE(bm_to_litter)
358  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:) :: bm_to_littercalc    !! conversion of biomass to litter per ground area at
359                                                                         !! Sechiba time step
360                                                                         !! @tex $(gC m^{-2} dt_sechiba^{-1})$ @endtex
361!$OMP THREADPRIVATE(bm_to_littercalc)
362  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: dead_leaves          !! Metabolic and structural pools of dead leaves on ground
363                                                                         !! per PFT @tex $(gC m^{-2})$ @endtex
364!$OMP THREADPRIVATE(dead_leaves)
365!  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:) :: litter_above        !! Above ground metabolic and structural litter
366!                                                                         !! per ground area
367!                                                                         !! @tex $(gC m^{-2})$ @endtex
368!$OMP THREADPRIVATE(litter_above)
369!  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:,:):: litter_below       !! Below ground metabolic and structural litter
370!                                                                         !! per ground area
371!                                                                         !! @tex $(gC m^{-2})$ @endtex
372!!$OMP THREADPRIVATE(litter_below))
373  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:,:) :: litter_above_Cforcing        !! Above ground metabolic and structural litter
374                                                                         !! per ground area
375                                                                         !! @tex $(gC m^{-2})$ @endtex
376!$OMP THREADPRIVATE(litter_above_Cforcing)
377  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:,:,:):: litter_below_Cforcing       !! Below ground metabolic and structural litter
378                                                                         !! per ground area
379                                                                         !! @tex $(gC m^{-2})$ @endtex
380!!$OMP THREADPRIVATE(litter_below_Cforcing))
381  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: litterpart           !! Fraction of litter above the ground belonging to
382                                                                         !! different litter pools (unitless)
383!$OMP THREADPRIVATE(litterpart)
384  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: firelitter           !! Total litter above the ground that could potentially
385                                                                         !! burn @tex $(gC m^{-2})$ @endtex
386!$OMP THREADPRIVATE(firelitter)
387  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:,:,:) :: soilcarbon_input     !! Quantity of carbon going into DOC pools from litter
388                                                                         !! decomposition per ground area  at Sechiba time step
389                                                                         !! @tex $(gC m^{-2} dt_sechiba^{-1})$ @endtex
390!$OMP THREADPRIVATE(soilcarbon_input)
391  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:,:)  :: soilcarbon_input_daily !! Daily quantity of carbon going into DOC pools from
392                                                                           !! litter decomposition per ground area
393                                                                           !! @tex $(gC m^{-2} day^{-1})$ @endtex
394!$OMP THREADPRIVATE(soilcarbon_input_daily)
395!  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:)  :: carbon             !! Soil carbon pools per ground area: active, slow, or
396                                                                         !! passive, @tex $(gC m^{-2})$ @endtex
397!$OMP THREADPRIVATE(carbon)
398!  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:,:,:)   :: DOC           !! Soil dissolved organic carbon free or adsorbed
399                                                                         !! detailled for each pools @tex $(gC m^{-2} of ground)$ @endtex
400!$OMP THREADPRIVATE(DOC)
401  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:) :: interception_storage  !! Wet deposition of DOC not infiltrating into the ground
402                                                                         !! @tex $(gCm^{-2} of ground)$ @endtex
403!$OMP THREADPRIVATE(interception_storage)
404!  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: lignin_struc_above   !! Ratio Lignine/Carbon in structural litter for above
405                                                                         !! ground compartments (unitless)
406!$OMP THREADPRIVATE(lignin_struc_above)
407!  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: lignin_struc_below   !! Ratio Lignine/Carbon in structural litter for below
408                                                                         !! ground compartments (unitless)
409!$OMP THREADPRIVATE(lignin_struc_below)
410  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)    :: lignin_struc_above_Cforcing   !! Ratio Lignine/Carbon in structural litter for above
411                                                                         !! ground compartments (unitless)
412!$OMP THREADPRIVATE(lignin_struc_above_Cforcing)
413  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:)  :: lignin_struc_below_Cforcing   !! Ratio Lignine/Carbon in structural litter for below
414                                                                         !! ground compartments (unitless)
415!$OMP THREADPRIVATE(lignin_struc_below_Cforcing)
416  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: lm_lastyearmax       !! Last year's maximum leaf mass per ground area for each
417                                                                         !! PFT @tex $(gC m^{-2})$ @endtex 
418!$OMP THREADPRIVATE(lm_lastyearmax)
419  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: lm_thisyearmax       !! This year's maximum leaf mass per ground area for each
420                                                                         !! PFT @tex $(gC m^{-2})$ @endtex 
421!$OMP THREADPRIVATE(lm_thisyearmax)
422  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: maxfpc_lastyear      !! Last year's maximum fpc for each natural PFT, on ground
423                                                                         !! [??CHECK] fpc but this ones look ok (computed in
424                                                                         !! season, used in light)??
425!$OMP THREADPRIVATE(maxfpc_lastyear)
426  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: maxfpc_thisyear      !! This year's maximum fpc for each PFT, on ground (see
427                                                                         !! stomate_season), [??CHECK] fpc but this ones look ok
428                                                                         !! (computed in season, used in light)??
429!$OMP THREADPRIVATE(maxfpc_thisyear)
430!---
431  REAL(r_std), ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: leaf_age             !! Age of different leaf classes (days)
432!$OMP THREADPRIVATE(leaf_age)
433  REAL(r_std), ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: leaf_frac            !! PFT fraction of leaf mass in leaf age class (0-1,
434                                                                         !! unitless)
435!$OMP THREADPRIVATE(leaf_frac)
436  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: when_growthinit      !! Days since beginning of growing season (days)
437!$OMP THREADPRIVATE(when_growthinit)
438  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: herbivores           !! Time constant of probability of a leaf to be eaten by a
439                                                                         !! herbivore (days)
440!$OMP THREADPRIVATE(herbivores)
441  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: RIP_time             !! How much time ago was the PFT eliminated for the last
442                                                                         !! time (year)
443!$OMP THREADPRIVATE(RIP_time)
444  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: time_hum_min         !! Time elapsed since strongest moisture limitation (days)
445!$OMP THREADPRIVATE(time_hum_min)
446!---
447  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: clay_fm              !! Soil clay content (0-1, unitless), parallel computing
448  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: clay_fm_g            !! Soil clay content (0-1, unitless), parallel computing
449  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: soil_ph_fm              !! Soil pH (0-14, pHunit), parallel computing
450  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: soil_ph_fm_g            !! Soil pH (0-14, pH unit), parallel computing
451  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: poor_soils_fm        !! Fraction of poor soils (0-1), parallel computing
452  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: poor_soils_fm_g      !! Fraction of poor soils (0-1), parallel computing
453  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: bulk_dens_fm         !! Soil bulk density (g cm-3), parallel computing
454  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: bulk_dens_fm_g       !! Soil bulk density (g cm-3), parallel computing
455  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: precip_fm            !! Daily precipitations sum @tex $(mm day^{-1})$ @endtex,
456                                                                         !! parallel computing
457  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: precip_fm_g          !! Daily precipitations sum @tex $(mm day^{-1})$ @endtex,
458                                                                         !! parallel computing
459  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: litterhum_daily_fm   !! Daily relative humidity of litter (0-1, unitless),
460                                                                         !! parallel computing
461  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: litterhum_daily_fm_g !! Daily relative humidity of litter (0-1, unitless),
462                                                                         !! parallel computing
463  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: t2m_daily_fm         !! Daily air temperature at 2 meter (K), parallel
464                                                                         !! computing
465  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: t2m_daily_fm_g       !! Daily air temperature at 2 meter (K), parallel
466                                                                         !! computing
467  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: t2m_min_daily_fm     !! Daily minimum air temperature at 2 meter (K),
468                                                                         !! parallel computing
469  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: t2m_min_daily_fm_g   !! Daily minimum air temperature at 2 meter (K),
470                                                                         !! parallel computing
471  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: tsurf_daily_fm       !! Daily surface temperatures (K), parallel
472                                                                         !! computing
473  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: tsurf_daily_fm_g     !! Daily surface temperatures (K), parallel
474                                                                         !! computing
475  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: tsoil_daily_fm       !! Daily soil temperatures (K), parallel computing
476  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: tsoil_daily_fm_g     !! Daily soil temperatures (K), parallel computing
477  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: soilhum_daily_fm     !! Daily soil humidity (0-1, unitless), parallel computing
478  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: soilhum_daily_fm_g   !! Daily soil humidity (0-1, unitless), parallel computing
479  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: humrel_daily_fm      !! Daily relative humidity of atmosphere (0-1, unitless),
480                                                                         !! parallel computing
481  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: humrel_daily_fm_g    !! Daily relative humidity of atmosphere (0-1, unitless),
482                                                                         !! parallel computing
483  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: gpp_daily_fm         !! Daily gross primary productivity per ground area
484                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex,
485                                                                         !! parallel computing
486  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: gpp_daily_fm_g       !! Daily gross primary productivity per ground area
487                                                                         !! @tex $(gC m^{-2} day^{-1})$ @endtex,
488                                                                         !! parallel computing
489  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: veget_fm             !! Vegetation coverage taking into account non-biological
490                                                                         !! coverage (unitless), parallel computing
491  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: veget_fm_g           !! Vegetation coverage taking into account non-biological
492                                                                         !! coverage (unitless), parallel computing
493  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: veget_max_fm         !! Maximum vegetation coverage taking into account
494                                                                         !! non-biological coverage (unitless), parallel computing
495  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: veget_max_fm_g       !! Maximum vegetation coverage taking into account none
496                                                                         !! biological coverage (unitless), parallel computing
497  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: lai_fm               !! Leaf area index @tex $@tex $(m^2 m^{-2})$ @endtex$ @endtex,
498                                                                         !! parallel computing
499  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: lai_fm_g             !! Leaf area index @tex $@tex $(m^2 m^{-2})$ @endtex$ @endtex,
500                                                                         !! parallel computing
501!---
502  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: co2_fire             !! Carbon emitted to the atmosphere by burning living
503                                                                         !! and dead biomass
504                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
505!$OMP THREADPRIVATE(co2_fire)
506  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: co2_to_bm_dgvm       !! Psuedo-photosynthesis,C used to provide seedlings with
507                                                                         !! an initial biomass, arbitrarily removed from the
508                                                                         !! atmosphere 
509                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
510!$OMP THREADPRIVATE(co2_to_bm_dgvm)
511  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: nep_daily            !! Daily net CO2 flux (positive from atmosphere to land)
512                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
513!$OMP THREADPRIVATE(nep_daily)
514  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: nep_monthly          !! Monthly net CO2 flux (positive from atmosphere to land)
515                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
516!$OMP THREADPRIVATE(nep_monthly)
517  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: prod10               !! Wood products remaining in the 10 year-turnover pool
518                                                                         !! after the annual release for each compartment
519                                                                         !! @tex $(gC m^{-2})$ @endtex   
520                                                                         !! (0:10 input from year of land cover change),
521                                                                         !! dimension(#pixels,0:10 years
522!$OMP THREADPRIVATE(prod10)
523  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: prod100              !! Wood products remaining in the 100 year-turnover pool
524                                                                         !! after the annual release for each compartment
525                                                                         !! @tex $(gC m^{-2})$ @endtex 
526                                                                         !! (0:100 input from year of land cover change),
527                                                                         !! dimension(#pixels,0:100 years)
528!$OMP THREADPRIVATE(prod100)
529  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: flux10               !! Wood decomposition from the 10 year-turnover pool
530                                                                         !! compartments
531                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex
532                                                                         !! dimension(#pixels,0:10) 
533!$OMP THREADPRIVATE(flux10)
534  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: flux100              !! Wood decomposition from the 100 year-turnover pool
535                                                                         !! compartments
536                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex
537                                                                         !! dimension(#pixels,0:100)
538!$OMP THREADPRIVATE(flux100)
539  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: convflux             !! Release during first year following land cover change
540                                                                         !! (paper, burned, etc...)
541                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex 
542!$OMP THREADPRIVATE(convflux)
543  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: cflux_prod10         !! Total annual release from the 10 year-turnover pool
544                                                                         !! sum of flux10 
545                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex
546!$OMP THREADPRIVATE(cflux_prod10)
547  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: cflux_prod100        !! Total annual release from the 100 year-turnover pool
548                                                                         !! sum of flux100
549                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex
550!$OMP THREADPRIVATE(cflux_prod100)
551  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: prod10_harvest       !! Wood products remaining in the 10 year-turnover pool
552                                                                         !! after the annual release for each compartment
553                                                                         !! @tex $(gC m^{-2})$ @endtex   
554                                                                         !! (0:10 input from year of wood harvest),
555                                                                         !! dimension(#pixels,0:10 years
556!$OMP THREADPRIVATE(prod10_harvest)
557  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: prod100_harvest      !! Wood products remaining in the 100 year-turnover pool
558                                                                         !! after the annual release for each compartment
559                                                                         !! @tex $(gC m^{-2})$ @endtex 
560                                                                         !! (0:100 input from year of wood harvest),
561                                                                         !! dimension(#pixels,0:100 years)
562!$OMP THREADPRIVATE(prod100_harvest)
563  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: flux10_harvest       !! Wood decomposition from the 10 year-turnover pool
564                                                                         !! compartments
565                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex
566                                                                         !! dimension(#pixels,0:10) 
567!$OMP THREADPRIVATE(flux10_harvest)
568  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: flux100_harvest      !! Wood decomposition from the 100 year-turnover pool
569                                                                         !! compartments
570                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex
571                                                                         !! dimension(#pixels,0:100)
572!$OMP THREADPRIVATE(flux100_harvest)
573  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: convflux_harvest     !! Release during first year following wood harvest
574                                                                         !! (paper, burned, etc...)
575                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex 
576!$OMP THREADPRIVATE(convflux_harvest)
577  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: cflux_prod10_harvest !! Total annual release from the 10 year-turnover pool
578                                                                         !! sum of flux10 
579                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex
580!$OMP THREADPRIVATE(cflux_prod10_harvest)
581  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: cflux_prod100_harvest!! Total annual release from the 100 year-turnover pool
582                                                                         !! sum of flux100
583                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex
584!$OMP THREADPRIVATE(cflux_prod100_harvest)
585  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: convfluxpft          !! Convflux per PFT                     
586!$OMP THREADPRIVATE(convfluxpft)
587  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: fDeforestToProduct   !! Deforested biomass into product pool due to anthropogenic                                                                                                           
588                                                                         !! land use change                   
589!$OMP THREADPRIVATE(fDeforestToProduct)   
590  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: fLulccResidue        !! Carbon mass flux into soil and litter due to anthropogenic land use or land cover change                                                                         
591!$OMP THREADPRIVATE(fLulccResidue)
592  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: fHarvestToProduct    !! Deforested biomass into product pool due to anthropogenic                                                                                       
593                                                                         !! land use
594!$OMP THREADPRIVATE(fHarvestToProduct)
595  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:):: woodharvestpft       !! New year wood harvest per  PFT
596!$OMP THREADPRIVATE(woodharvestpft)
597  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: harvest_above        !! Harvest of above ground biomass for agriculture -not
598                                                                         !! just from land use change
599                                                                         !! @tex $(??gC m^{-2} dt_stomate^{-1})$ @endtex
600!$OMP THREADPRIVATE(harvest_above)
601  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: carb_mass_total      !! Total on-site and off-site C pool
602                                                                         !! @tex $(??gC m^{-2})$ @endtex                       
603!$OMP THREADPRIVATE(carb_mass_total)
604!---
605  REAL(r_std), SAVE                              :: tau_longterm
606!$OMP THREADPRIVATE(tau_longterm)
607  REAL(r_std),SAVE                               :: dt_days=zero         !! Time step of STOMATE (days)
608!$OMP THREADPRIVATE(dt_days)
609  INTEGER(i_std),SAVE                            :: days_since_beg=0     !! Number of full days done since the start of the simulation
610!$OMP THREADPRIVATE(days_since_beg)
611  INTEGER(i_std),ALLOCATABLE,SAVE,DIMENSION(:)   :: nforce               !! Number of states calculated for the soil forcing
612                                                                         !! variables (unitless), dimension(::nparan*::nbyear) both
613                                                                         !! given in the run definition file   
614!$OMP THREADPRIVATE(nforce)
615  INTEGER(i_std),ALLOCATABLE,SAVE,DIMENSION(:)   :: isf                  !! Index for number of time steps that can be stored in
616                                                                         !! memory (unitless), dimension (#nsfm)
617!$OMP THREADPRIVATE(isf)
618  INTEGER(i_std),ALLOCATABLE,SAVE,DIMENSION(:)   :: nf_cumul             !! Number of years over which the average is calculated in
619                                                                         !! forcesoil when cumul flag is set, dimension (#nsft)
620                                                                         !! [??CHECK] definition the dimension is number of
621                                                                         !! timesteps in a year?
622!$OMP THREADPRIVATE(nf_cumul)
623  INTEGER(i_std), SAVE                           :: spinup_period        !! Period of years used to calculate the resolution of the system for spinup analytic.
624                                                                         !! This period correspond in most cases to the period of years of forcing data used
625  INTEGER,PARAMETER                              :: r_typ = nf90_real4   !! Specify data format (server dependent)
626  LOGICAL,ALLOCATABLE,SAVE,DIMENSION(:)          :: nf_written           !! Flag indicating whether the forcing data have been
627                                                                         !! written
628!$OMP THREADPRIVATE(nf_written)
629!---
630  LOGICAL, SAVE                                  :: do_slow=.FALSE.      !! Flag that determines whether stomate_accu calculates
631                                                                         !! the sum(do_slow=.FALSE.) or the mean
632                                                                         !! (do_slow=.TRUE.)
633!$OMP THREADPRIVATE(do_slow)
634  LOGICAL, SAVE                                  :: l_first_stomate = .TRUE.!! Is this the first call of stomate?
635!$OMP THREADPRIVATE(l_first_stomate)
636  LOGICAL, SAVE                                  :: cumul_forcing=.FALSE.!! flag for cumul of forcing if teststomate
637!$OMP THREADPRIVATE(cumul_forcing)
638  LOGICAL, SAVE                                  :: cumul_Cforcing=.FALSE.  !! Flag, if internal parameter cumul_Cforcing is
639                                                                            !! TRUE then ::nbyear (defined in run definition
640                                                                            !! file will be forced to 1 later in this module. If
641                                                                            !! FALSE the mean over ::nbyear is written in forcesoil
642!$OMP THREADPRIVATE(cumul_Cforcing)
643!---   
644  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: harvest_above_monthly   !! [??CHECK] post-processing - should be removed?
645!$OMP THREADPRIVATE(harvest_above_monthly)
646  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: cflux_prod_monthly      !! [??CHECK] post-processing - should be removed?
647!$OMP THREADPRIVATE(cflux_prod_monthly)
648!---
649  INTEGER(i_std), SAVE                               :: global_years        !! Global counter of years (year)
650!$OMP THREADPRIVATE(global_years)
651  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:)           :: ok_equilibrium      !! Logical array marking the points where the resolution is ok
652                                                                            !! (true/false)
653!$OMP THREADPRIVATE(ok_equilibrium)
654  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:)           :: carbon_eq           !! Logical array to mark the carbon pools at equilibrium ?
655                                                                            !! If true, the job stops. (true/false)
656!$OMP THREADPRIVATE(carbon_eq)
657  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)       :: nbp_accu            !! Accumulated Net Biospheric Production over the year (gC.m^2 )
658!$OMP THREADPRIVATE(nbp_accu)
659  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)       :: nbp_flux            !! Net Biospheric Production (gC.m^2.day^{-1})
660!$OMP THREADPRIVATE(nbp_flux)
661  REAL(r_std), ALLOCATABLE, DIMENSION(:,:,:,:)       :: matrixA             !! Matrix containing the fluxes between the carbon pools
662                                                                            !! per sechiba time step
663                                                                            !! @tex $(gC.m^2.day^{-1})$ @endtex
664!$OMP THREADPRIVATE(matrixA)
665  REAL(r_std), ALLOCATABLE, DIMENSION(:,:,:)         :: vectorB             !! Vector containing the litter increase per sechiba time step
666                                                                            !! @tex $(gC m^{-2})$ @endtex
667!$OMP THREADPRIVATE(vectorB)
668  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) :: MatrixV             !! Matrix containing the accumulated values of matrixA
669!$OMP THREADPRIVATE(MatrixV)
670  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:)   :: VectorU             !! Matrix containing the accumulated values of VectorB
671!$OMP THREADPRIVATE(VectorU)
672  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) :: MatrixW             !! Matrix containing the opposite of matrixA
673!$OMP THREADPRIVATE(MatrixW)
674  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:)   :: previous_stock      !! Array containing the carbon stock calculated by the analytical
675                                                                            !! method in the previous resolution
676!$OMP THREADPRIVATE(previous_stock)
677  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:)   :: current_stock       !! Array containing the carbon stock calculated by the analytical
678                                                                            !! method in the current resolution
679!$OMP THREADPRIVATE(current_stock)
680  REAL(r_std), SAVE                                  :: eps_carbon          !! Stopping criterion for carbon pools (unitless,0-1)
681!$OMP THREADPRIVATE(eps_carbon)
682  REAL(r_std),SAVE                                   :: dt_forcesoil        !! Time step of soil forcing file (days)
683!$OMP THREADPRIVATE(dt_forcesoil)
684  INTEGER(i_std),PARAMETER                           :: nparanmax=366       !! Maximum number of time steps per year for forcesoil
685  INTEGER(i_std),SAVE                                :: nparan              !! Number of time steps per year for forcesoil read from run definition (unitless)
686!$OMP THREADPRIVATE(nparan)
687  INTEGER(i_std),SAVE                                :: nbyear=1            !! Number of years saved for forcesoil (unitless)
688!$OMP THREADPRIVATE(nbyear)
689  INTEGER(i_std),SAVE                                :: iatt                !! Time step of forcing of soil processes (iatt = 1 to ::nparan*::nbyear)
690!$OMP THREADPRIVATE(iatt)
691  INTEGER(i_std),SAVE                                :: iatt_old=1          !! Previous ::iatt
692!$OMP THREADPRIVATE(iatt_old)
693  INTEGER(i_std),SAVE                                :: nsfm                !! Number of time steps that can be stored in memory (unitless)
694!$OMP THREADPRIVATE(nsfm)
695  INTEGER(i_std),SAVE                                :: nsft                !! Number of time steps in a year (unitless)
696!$OMP THREADPRIVATE(nsft)
697  INTEGER(i_std),SAVE                                :: iisf                !! Current pointer for teststomate (unitless)
698!$OMP THREADPRIVATE(iisf)
699  CHARACTER(LEN=100), SAVE                           :: forcing_name        !! Name of forcing file 1
700!$OMP THREADPRIVATE(forcing_name)
701  CHARACTER(LEN=100), SAVE                           :: Cforcing_name       !! Name of forcing file 2
702!$OMP THREADPRIVATE(Cforcing_name)
703  INTEGER(i_std),SAVE                                :: Cforcing_id         !! File identifer of file 2
704!$OMP THREADPRIVATE(Cforcing_id)   
705  INTEGER(i_std),PARAMETER                           :: ndm = 13            !! Maximum number of dimensions (unitless)
706
707 
708PUBLIC clay_fm, soil_ph_fm, poor_soils_fm, bulk_dens_fm, humrel_daily_fm, litterhum_daily_fm, t2m_daily_fm, &
709   & t2m_min_daily_fm, tsurf_daily_fm, tsoil_daily_fm, soilhum_daily_fm, &
710   & precip_fm, gpp_daily_fm, veget_fm, veget_max_fm, lai_fm
711PUBLIC  dt_days, days_since_beg, do_slow
712PUBLIC isf, nf_written
713
714CONTAINS
715 
716
717!! ================================================================================================================================
718!! SUBROUTINE   : stomate_initialize
719!!
720!>\BRIEF        Initialization routine for stomate module.
721!!
722!! DESCRIPTION  : Initialization routine for stomate module. Read options from parameter file, allocate variables, read variables
723!!                from restart file and initialize variables if necessary.
724!!               
725!! \n
726!_ ================================================================================================================================
727
728SUBROUTINE stomate_initialize &
729        (kjit,           kjpij,             kjpindex,                        &
730         rest_id_stom,   hist_id_stom,      hist_id_stom_IPCC,               &
731         index,          lalo,              neighbours,   resolution,        &
732         contfrac,       totfrac_nobio,     clay, bulk_dens, soil_ph, poor_soils,  &
733         t2m,                    lai,            veget,             veget_max,             &
734         co2_flux,       co2_to_bm_radia,   fco2_lu,      deadleaf_cover,  assim_param, temp_growth, &
735                 rootmass,litter_above, litter_below, carbon, DOC, lignin_struc_above,lignin_struc_below, depth_deepsoil)
736
737    IMPLICIT NONE
738    !! 0. Variable and parameter declaration
739    !! 0.1 Input variables
740    INTEGER(i_std),INTENT(in)                       :: kjit              !! Time step number (unitless)
741    INTEGER(i_std),INTENT(in)                       :: kjpij             !! Total size of the un-compressed grid (unitless)
742    INTEGER(i_std),INTENT(in)                       :: kjpindex          !! Domain size - terrestrial pixels only (unitless)
743    INTEGER(i_std),INTENT(in)                       :: rest_id_stom      !! STOMATE's _Restart_ file identifier (unitless)
744    INTEGER(i_std),INTENT(in)                       :: hist_id_stom      !! STOMATE's _history_ file identifier (unitless)
745    INTEGER(i_std),INTENT(in)                       :: hist_id_stom_IPCC !! STOMATE's IPCC _history_ file identifier(unitless)
746    INTEGER(i_std),DIMENSION(kjpindex),INTENT(in)   :: index             !! The indices of the terrestrial pixels only (unitless)
747    REAL(r_std),DIMENSION(kjpindex,2),INTENT(in)    :: lalo              !! Geographical coordinates (latitude,longitude) for pixels (degrees)
748    INTEGER(i_std),DIMENSION(kjpindex,NbNeighb),INTENT(in) :: neighbours !! Neighboring grid points if land for the DGVM (unitless)
749    REAL(r_std),DIMENSION(kjpindex,2),INTENT(in)    :: resolution        !! Size in x an y of the grid (m) - surface area of the gridbox
750    REAL(r_std),DIMENSION (kjpindex), INTENT (in)   :: contfrac          !! Fraction of continent in the grid cell (unitless)
751    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: totfrac_nobio     !! Fraction of grid cell covered by lakes, land ice, cities, ... (unitless)
752    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: clay              !! Clay fraction of soil (0-1, unitless)
753    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: bulk_dens         !! Soil bulk density (g cm-3)
754    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: soil_ph           !! Soil pH (0-14, pH unit)
755    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: poor_soils        !! Fraction of poor soils (0-1), see Lauerwald et al., GMD, for explanation   
756    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: t2m               !! 2 m air temperature (K)
757    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)  :: lai               !! Leaf area inex @tex $(m^2 m^{-2})$ @endtex
758    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)  :: veget             !! Fraction of vegetation type including
759                                                                         !! non-biological fraction (unitless)
760    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)  :: veget_max         !! Maximum fraction of vegetation type including
761                                                                         !! non-biological fraction (unitless)
762
763    !! 0.2 Output variables
764    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: co2_flux          !! CO2 flux between atmosphere and biosphere
765    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: co2_to_bm_radia   !! virtual gpp flux between atmosphere and biosphere
766    REAL(r_std),DIMENSION(kjpindex),INTENT(out)     :: fco2_lu           !! CO2 flux between atmosphere and biosphere from land-use (without forest management) 
767    REAL(r_std),DIMENSION(kjpindex),INTENT(out)     :: deadleaf_cover    !! Fraction of soil covered by dead leaves (unitless)
768    REAL(r_std),DIMENSION(kjpindex,nvm,npco2),INTENT(out) :: assim_param !! min+max+opt temperatures (K) & vmax for photosynthesis 
769                                                                         !! @tex $(\mu mol m^{-2}s^{-1})$ @endtex 
770    REAL(r_std),DIMENSION(kjpindex),INTENT(out)     :: temp_growth       !! Growth temperature (°C) 
771                                                                         !! Is equal to t2m_month
772        REAL(r_std),DIMENSION (kjpindex,nvm,nparts,nelements), INTENT (out)       :: rootmass       !! Belowground biomass
773                                                                                                    !! @tex $(gC m^{-2})$ @endtex
774        REAL(r_std),DIMENSION (kjpindex,nlitt,nvm,nelements), INTENT (out)        :: litter_above   !! Above ground metabolic and structural litter
775                                                                                                    !! @tex $(gC m^{-2})$ @endtex
776    REAL(r_std),DIMENSION (kjpindex,nlitt,nvm,nslmd,nelements), INTENT (out) :: litter_below   !! Below ground metabolic and structural litter
777                                                                                                !! per ground area                                                                                                                                                                                          !! per ground area
778                                                                                                                                                                            !! @tex $(gC m^{-2})$ @endtex
779        REAL(r_std),DIMENSION (kjpindex,ncarb,nvm,nslmd), INTENT (out)            :: carbon         !! Soil carbon pools per ground area: active, slow, or
780                                                                                                !! passive, @tex $(gC m^{-2})$ @endtex
781        REAL(r_std), DIMENSION(kjpindex,nvm,nslmd,ndoc,npool,nelements), INTENT(out) :: DOC        !! Dissolved Organic Carbon in soil
782                                                                                                !! The unit is given by m^2 of
783                                                                                                !! ground @tex $(gC m{-2} of ground)$ @endtex
784        REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)               :: lignin_struc_above       !! Ratio Lignin content in structural litter,
785                                                                                                !! above ground, (0-1, unitless)
786    REAL(r_std), DIMENSION(kjpindex,nvm,nslmd), INTENT(out)        :: lignin_struc_below       !! Ratio Lignin content in structural litter,
787                                                                                                !! below ground, (0-1, unitless)
788    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)              :: depth_deepsoil           !! Depth of the soil layer deeper than 2 m.
789                                                                                                !! When sediment deposition occuring, the original surface (0-2)
790                                                                                                                                                                            !! soil DOC, and SOC will enther into this layer.                                                                                                                                                                                             
791    !! 0.3 Local variables
792    REAL(r_std)                                   :: dt_days_read             !! STOMATE time step read in restart file (days)
793    INTEGER(i_std)                                :: l,k,ji, jv, i, j,ig, m      !! indices   
794    REAL(r_std),PARAMETER                         :: max_dt_days = 5.         !! Maximum STOMATE time step (days)
795    REAL(r_std),DIMENSION(kjpindex,nvm)           :: rprof                    !! Coefficient of the exponential functions that
796                                                                              !! relates root density to soil depth (unitless)
797    REAL(r_std),DIMENSION(kjpindex,nvm)           :: gpp_daily_x              !! "Daily" gpp for teststomate 
798                                                                              !! @tex $(??gC m^{-2} dt_stomate^{-1})$ @endtex
799    REAL(r_std),DIMENSION(kjpindex,nvm)           :: veget_cov                !! Fractional coverage: actually share of the pixel
800                                                                              !! covered by a PFT (fraction of ground area),
801                                                                              !! taking into account LAI ??(= grid scale fpc)??
802    INTEGER(i_std)                                :: ier                      !! Check errors in netcdf call (unitless)
803
804    INTEGER(i_std)                                :: max_totsize              !! Memory management - maximum memory size (Mb)
805    INTEGER(i_std)                                :: totsize_1step            !! Memory management - memory required to store one
806                                                                              !! time step on one processor (Mb)
807    INTEGER(i_std)                                :: totsize_tmp              !! Memory management - memory required to store one
808                                                                              !! time step on all processors(Mb)
809    INTEGER(i_std)                                :: vid                      !! Variable identifer of netCDF (unitless)
810    INTEGER(i_std)                                :: nneigh                   !! Number of neighbouring pixels
811    INTEGER(i_std)                                :: direct                   !!
812    INTEGER(i_std),DIMENSION(ndm)                 :: d_id                     !!
813
814
815!_ ================================================================================================================================
816    IF (printlev >=2) WRITE(numout,*) 'Inilization of stomate variables'
817    !! 1. Initialize variable
818    !! Update flag
819    l_first_stomate = .FALSE.
820   
821    !! 1.1 Store current time step in a common variable
822    itime = kjit
823   
824   
825    !! 1.3 PFT rooting depth across pixels, humescte is pre-defined
826    ! (constantes_veg.f90). It is defined as the coefficient of an exponential
827    ! function relating root density to depth
828    DO j=1,nvm
829       rprof(:,j) = 1./humcste(j)
830    ENDDO
831   
832    !! 1.4.0 Parameters for spinup
833    !
834    eps_carbon = 0.01
835    !Config Key   = EPS_CARBON
836    !Config Desc  = Allowed error on carbon stock
837    !Config If    = SPINUP_ANALYTIC
838    !Config Def   = 0.01
839    !Config Help  =
840    !Config Units = [%]   
841    CALL getin_p('EPS_CARBON',eps_carbon)       
842   
843   
844    !Config Key   = SPINUP_PERIOD
845    !Config Desc  = Period to calulcate equilibrium during spinup analytic
846    !Config If    = SPINUP_ANALYTIC
847    !Config Def   = -1
848    !Config Help  = Period corresponds in most cases to the number of years of forcing data used in the spinup.
849    !Config Units = [years]   
850    spinup_period = -1
851    CALL getin_p('SPINUP_PERIOD',spinup_period)       
852   
853    ! Check spinup_period values.
854    ! For periods uptil 6 years, to obtain equilibrium, a bigger period have to be used
855    ! and therefore spinup_period is adjusted to 10 years.
856    IF (spinup_analytic) THEN
857       IF (spinup_period <= 0) THEN
858          WRITE(numout,*) 'Error in parameter spinup_period. This parameter must be > 0 : spinup_period=',spinup_period
859          CALL ipslerr_p (3,'stomate_initialize', &
860               'Parameter spinup_period must be set to a positive integer.', &
861               'Set this parameter to the number of years of forcing data used for the spinup.', &
862               '')
863       ELSE IF (spinup_period <= 6) THEN
864          ! Adjust to bigger period. The period must be a multiple of the original period.
865          WRITE(numout,*) 'Initial spinup_period =',spinup_period,' will be adjusted.'
866          spinup_period = spinup_period*(INT(9/spinup_period)+1)
867       END IF
868       IF (printlev >=1) WRITE(numout,*) 'Spinup analytic is activated using eps_carbon=',&
869            eps_carbon, ' and spinup_period=',spinup_period
870    END IF
871   
872
873    !! 1.4.1 Allocate memory for all variables in stomate
874    ! Allocate memory for all variables in stomate, build new index
875    ! tables accounting for the PFTs, read and check flags and set file
876    ! identifier for restart and history files.
877    CALL stomate_init (kjpij, kjpindex, index, lalo, &
878         rest_id_stom, hist_id_stom, hist_id_stom_IPCC)
879   
880    !! 1.4.2 Initialization of PFT specific parameters
881    ! Initialization of PFT specific parameters i.e. sla from leaf life,
882    ! sapling characteristics (biomass), migration speed, critical diameter,
883    ! coldest tolerable temperature, critical values for phenology, maximum
884    ! life time of leaves, respiration coefficients and photosynthesis.
885    ! The subroutine also communicates settings read by stomate_constant_init.
886    CALL data (kjpindex, lalo)
887   
888    !! 1.4.3 Initial conditions
889   
890    !! 1.4.3.1 Read initial values for STOMATE's variables from the _restart_ file
891    ! ??Shouldn't this be included in stomate_init?? Looks like an initialization!
892    co2_flux(:,:) = zero
893    fco2_lu(:) = zero
894   
895    ! Get values from _restart_ file. Note that only ::kjpindex, ::index, ::lalo
896    ! and ::resolution are input variables, all others are output variables.
897        !WRITE(numout,*) 'STOMATE_ZHC1'
898        !WRITE(numout,*) 'litter_above: ', SUM(litter_above(:,:,:,icarbon)), SUM(turnover_daily),SUM(bm_to_litter)
899        !WRITE(numout,*) 'litter_below: ', SUM(litter_below(:,:,:,:,icarbon))
900    CALL readstart &
901         (kjpindex, index, lalo, resolution, t2m, &
902         dt_days_read, days_since_beg, &
903         ind, adapted, regenerate, &
904         humrel_daily, gdd_init_date, litterhum_daily, &
905         t2m_daily, t2m_min_daily, tsurf_daily, tsoil_daily, &
906         soilhum_daily, precip_daily, &
907         gpp_daily, npp_daily, turnover_daily, &
908         humrel_month, humrel_week, &
909         t2m_longterm, tau_longterm, t2m_month, t2m_week, &
910         tsoil_month, soilhum_month, fireindex, firelitter, &
911         maxhumrel_lastyear, maxhumrel_thisyear, &
912         minhumrel_lastyear, minhumrel_thisyear, &
913         maxgppweek_lastyear, maxgppweek_thisyear, &
914         gdd0_lastyear, gdd0_thisyear, &
915         precip_lastyear, precip_thisyear, &
916         gdd_m5_dormance,  gdd_from_growthinit, gdd_midwinter, ncd_dormance, ngd_minus5, &
917         PFTpresent, npp_longterm, lm_lastyearmax, lm_thisyearmax, &
918         maxfpc_lastyear, maxfpc_thisyear, &
919         turnover_longterm, gpp_week, biomass, resp_maint_part, &
920         leaf_age, leaf_frac, &
921         senescence, when_growthinit, age, &
922         resp_hetero_d, tot_soil_resp_d, resp_maint_d, resp_growth_d, co2_fire, co2_to_bm_dgvm, co2_to_bm_radia, &
923         veget_lastlight, everywhere, need_adjacent, RIP_time, &
924         time_hum_min, hum_min_dormance, &
925         litterpart, litter_above, litter_below, depth_deepsoil, dead_leaves, &
926         carbon, DOC, lignin_struc_above, lignin_struc_below, turnover_time,&
927         prod10,prod100,flux10, flux100, &
928         convflux, cflux_prod10, cflux_prod100, &
929         prod10_harvest,prod100_harvest,flux10_harvest, flux100_harvest, &
930         convflux_harvest, cflux_prod10_harvest, cflux_prod100_harvest, &
931         convfluxpft, fDeforestToProduct, fLulccResidue,fHarvestToProduct, &
932         woodharvestpft, bm_to_litter, carb_mass_total, &
933         Tseason, Tseason_length, Tseason_tmp, &
934         Tmin_spring_time, begin_leaves, onset_date, &
935         global_years, ok_equilibrium, nbp_accu, nbp_flux, &
936         MatrixV, VectorU, previous_stock, current_stock, assim_param, interception_storage)
937    !WRITE(numout,*) 'STOMATE_ZHC2'
938        !WRITE(numout,*) 'litter_above: ', SUM(litter_above(:,:,:,icarbon)), SUM(turnover_daily),SUM(bm_to_litter)
939        !WRITE(numout,*) 'litter_below: ', SUM(litter_below(:,:,:,:,icarbon))
940        !! Added by Haicheng Zhang
941        rootmass(:,:,:,:) = biomass(:,:,:,:)
942    !WRITE(numout,*) 'Stomate_restart_readin', carbon(:,1,:,1)
943    !! 1.4.5 Check time step
944       
945    !! 1.4.5.1 Allow STOMATE's time step to change although this is dangerous
946    IF (dt_days /= dt_days_read) THEN
947       WRITE(numout,*) 'slow_processes: STOMATE time step changes:', &
948            & dt_days_read,' -> ',dt_days
949    ENDIF
950   
951    !! 1.4.5.2 Time step has to be a multiple of a full day
952    IF ( ( dt_days-REAL(NINT(dt_days),r_std) ) > min_stomate ) THEN
953       WRITE(numout,*) 'slow_processes: STOMATE time step is not a mutiple of a full day:', &
954            & dt_days,' days.'
955       STOP
956    ENDIF
957   
958    !! 1.4.5.3 upper limit to STOMATE's time step
959    IF ( dt_days > max_dt_days ) THEN
960       WRITE(numout,*) 'slow_processes: STOMATE time step exceeds the maximum value:', &
961            & dt_days,' days > ', max_dt_days, ' days.' 
962       STOP
963    ENDIF
964   
965    !! 1.4.5.4 STOMATE time step must not be less than the forcing time step
966    IF ( dt_sechiba > dt_days*one_day ) THEN
967       WRITE(numout,*) &
968            & 'slow_processes: STOMATE time step ::dt_days smaller than forcing time step ::dt_sechiba'
969       STOP
970    ENDIF
971   
972    !! 1.4.5.6 Final message on time step
973    IF (printlev >=2) WRITE(numout,*) 'Slow_processes, STOMATE time step (days): ', dt_days
974   
975    !! 1.4.6 Write forcing file for teststomate
976    IF (ok_co2 .AND. allow_forcing_write) THEN
977       
978       !Config Key   = STOMATE_FORCING_NAME
979       !Config Desc  = Name of STOMATE's forcing file
980       !Config If    = OK_STOMATE
981       !Config Def   = NONE
982       !Config Help  = Name that will be given
983       !Config         to STOMATE's offline forcing file
984       !Config         Compatible with Nicolas Viovy's driver
985       !Config Units = [FILE]
986       forcing_name = stomate_forcing_name
987       CALL getin_p('STOMATE_FORCING_NAME',forcing_name)
988       
989       IF ( TRIM(forcing_name) /= 'NONE' ) THEN
990         
991          !! 1.4.6.1 Calculate steps that can be stored in memory
992          ! Action for the root processor only (parallel computing) 
993          IF (is_root_prc) CALL SYSTEM ('rm -f '//TRIM(forcing_name))
994          IF (printlev>=2) WRITE(numout,*) 'writing a forcing file for STOMATE.'
995         
996          !Config Key   = STOMATE_FORCING_MEMSIZE
997          !Config Desc  = Size of STOMATE forcing data in memory
998          !Config If    = OK_STOMATE
999          !Config Def   = 50
1000          !Config Help  = This variable determines how many
1001          !Config         forcing states will be kept in memory.
1002          !Config         Must be a compromise between memory
1003          !Config         use and frequeny of disk access.
1004          !Config Units = [MegaBytes]
1005          max_totsize = 50
1006          CALL getin_p('STOMATE_FORCING_MEMSIZE', max_totsize)     
1007          max_totsize = max_totsize*1000000
1008         
1009          totsize_1step = &
1010               SIZE(clay)*KIND(clay) &
1011               +SIZE(soil_ph)*KIND(soil_ph) &
1012               +SIZE(poor_soils)*KIND(poor_soils) &
1013               +SIZE(bulk_dens)*KIND(bulk_dens) &                         
1014               +SIZE(humrel_daily)*KIND(humrel_daily) &
1015               +SIZE(litterhum_daily)*KIND(litterhum_daily) &
1016               +SIZE(t2m_daily)*KIND(t2m_daily) &
1017               +SIZE(t2m_min_daily)*KIND(t2m_min_daily) &
1018               +SIZE(tsurf_daily)*KIND(tsurf_daily) &
1019               +SIZE(tsoil_daily)*KIND(tsoil_daily) &
1020               +SIZE(soilhum_daily)*KIND(soilhum_daily) &
1021               +SIZE(precip_daily)*KIND(precip_daily) &
1022               +SIZE(gpp_daily_x)*KIND(gpp_daily_x) &
1023               +SIZE(veget)*KIND(veget) &
1024               +SIZE(veget_max)*KIND(veget_max) &
1025               +SIZE(lai)*KIND(lai)
1026         
1027          ! Totsize_1step is the size on a single processor, sum
1028          ! all processors and send to all processors
1029          CALL reduce_sum(totsize_1step,totsize_tmp)
1030          CALL bcast(totsize_tmp)
1031          totsize_1step=totsize_tmp
1032         
1033          ! Total number of forcing steps
1034          nsft = INT(one_year/(dt_stomate/one_day))
1035         
1036          ! Number of forcing steps in memory
1037          nsfm = MIN(nsft, &
1038               MAX(1,NINT( REAL(max_totsize,r_std) &
1039               /REAL(totsize_1step,r_std))))
1040           
1041             
1042          !! 1.6.4.2 Allocate memory for variables containing forcing data 
1043          ! and initialize variables (set to zero).
1044          CALL init_forcing (kjpindex,nsfm,nsft)
1045         
1046          ! Indexing for writing forcing file
1047          isf(:) = (/ (i,i=1,nsfm) /)
1048          nf_written(:) = .FALSE.
1049          nf_cumul(:) = 0
1050          iisf = 0
1051         
1052          !! 1.6.4.3 Create netcdf file
1053          ! Create, define and populate a netcdf file containing the forcing data.
1054          ! For the root processor only (parallel computing). NF90_ are functions
1055          ! from and external library. 
1056          IF (is_root_prc) THEN
1057             IF (printlev>=3) WRITE(numout,*) 'Stomate_init: Create Cforcing file'
1058             ! Create new netCDF dataset
1059             ier = NF90_CREATE (TRIM(forcing_name),NF90_SHARE,forcing_id)
1060             
1061             ! Add variable attribute
1062             ! Note ::iim_g and ::jjm_g are dimensions of the global field and
1063             ! ::nbp_glo is the number of global continental points
1064             ier = NF90_PUT_ATT (forcing_id,NF90_GLOBAL,'dt_sechiba',dt_sechiba)
1065             ier = NF90_PUT_ATT (forcing_id,NF90_GLOBAL,'dt_stomate',dt_stomate)
1066             ier = NF90_PUT_ATT (forcing_id,NF90_GLOBAL, &
1067                  'nsft',REAL(nsft,r_std))
1068             ier = NF90_PUT_ATT (forcing_id,NF90_GLOBAL, &
1069                  'kjpij',REAL(iim_g*jjm_g,r_std))
1070             ier = NF90_PUT_ATT (forcing_id,NF90_GLOBAL, &
1071                  'kjpindex',REAL(nbp_glo,r_std))
1072             
1073             ! Add new dimension
1074             ier = NF90_DEF_DIM (forcing_id,'points',nbp_glo,d_id(1))
1075             ier = NF90_DEF_DIM (forcing_id,'layers',nslm,d_id(2))
1076             ier = NF90_DEF_DIM (forcing_id,'pft',nvm,d_id(3))
1077             direct=2
1078             ier = NF90_DEF_DIM (forcing_id,'direction',direct,d_id(4))
1079             nneigh=8
1080             ier = NF90_DEF_DIM (forcing_id,'nneigh',nneigh,d_id(5))
1081             ier = NF90_DEF_DIM (forcing_id,'time',NF90_UNLIMITED,d_id(6))
1082             ier = NF90_DEF_DIM (forcing_id,'nbparts',nparts,d_id(7))
1083             
1084             ! Add new variable
1085             ier = NF90_DEF_VAR (forcing_id,'points',    r_typ,d_id(1),vid)
1086             ier = NF90_DEF_VAR (forcing_id,'layers',    r_typ,d_id(2),vid)
1087             ier = NF90_DEF_VAR (forcing_id,'pft',       r_typ,d_id(3),vid)
1088             ier = NF90_DEF_VAR (forcing_id,'direction', r_typ,d_id(4),vid)
1089             ier = NF90_DEF_VAR (forcing_id,'nneigh',    r_typ,d_id(5),vid)
1090             ier = NF90_DEF_VAR (forcing_id,'time',      r_typ,d_id(6),vid)
1091             ier = NF90_DEF_VAR (forcing_id,'nbparts',   r_typ,d_id(7),vid)
1092             ier = NF90_DEF_VAR (forcing_id,'index',     r_typ,d_id(1),vid)
1093             ier = NF90_DEF_VAR (forcing_id,'contfrac',  r_typ,d_id(1),vid) 
1094             ier = NF90_DEF_VAR (forcing_id,'lalo', &
1095                  r_typ,(/ d_id(1),d_id(4) /),vid)
1096             ier = NF90_DEF_VAR (forcing_id,'neighbours', &
1097                  r_typ,(/ d_id(1),d_id(5) /),vid)
1098             ier = NF90_DEF_VAR (forcing_id,'resolution', &
1099                  r_typ,(/ d_id(1),d_id(4) /),vid)
1100             ier = NF90_DEF_VAR (forcing_id,'clay', &
1101                  r_typ,(/ d_id(1),d_id(6) /),vid)
1102             ier = NF90_DEF_VAR (forcing_id,'bulk_dens', &
1103                  r_typ,(/ d_id(1),d_id(6) /),vid)
1104             ier = NF90_DEF_VAR (forcing_id,'soil_ph', &
1105                  r_typ,(/ d_id(1),d_id(6) /),vid)
1106             ier = NF90_DEF_VAR (forcing_id,'poor_soils', &
1107                  r_typ,(/ d_id(1),d_id(6) /),vid)                               
1108             ier = NF90_DEF_VAR (forcing_id,'humrel', &
1109                  r_typ,(/ d_id(1),d_id(3),d_id(6) /),vid)
1110             ier = NF90_DEF_VAR (forcing_id,'litterhum', &
1111                  r_typ,(/ d_id(1),d_id(6) /),vid)
1112             ier = NF90_DEF_VAR (forcing_id,'t2m', &
1113                  r_typ,(/ d_id(1),d_id(6) /),vid)
1114             ier = NF90_DEF_VAR (forcing_id,'t2m_min', &
1115                  r_typ,(/ d_id(1),d_id(6) /),vid)
1116             ier = NF90_DEF_VAR (forcing_id,'tsurf', &
1117                  r_typ,(/ d_id(1),d_id(6) /),vid)
1118             ier = NF90_DEF_VAR (forcing_id,'tsoil', &
1119                  r_typ,(/ d_id(1),d_id(2),d_id(6) /),vid)
1120             ier = NF90_DEF_VAR (forcing_id,'soilhum', &
1121                  r_typ,(/ d_id(1),d_id(2),d_id(6) /),vid)
1122             ier = NF90_DEF_VAR (forcing_id,'precip', &
1123                  r_typ,(/ d_id(1),d_id(6) /),vid)
1124             ier = NF90_DEF_VAR (forcing_id,'gpp', &
1125                  r_typ,(/ d_id(1),d_id(3),d_id(6) /),vid)
1126             ier = NF90_DEF_VAR (forcing_id,'veget', &
1127                  r_typ,(/ d_id(1),d_id(3),d_id(6) /),vid)
1128             ier = NF90_DEF_VAR (forcing_id,'veget_max', &
1129                  r_typ,(/ d_id(1),d_id(3),d_id(6) /),vid)
1130             ier = NF90_DEF_VAR (forcing_id,'lai', &
1131                  r_typ,(/ d_id(1),d_id(3),d_id(6) /),vid)
1132             ier = NF90_ENDDEF (forcing_id)
1133             
1134             ! Given the name of a varaible, nf90_inq_varid finds the variable
1135             ! ID (::vid). Put data value(s) into variable ::vid
1136             ier = NF90_INQ_VARID (forcing_id,'points',vid)
1137             ier = NF90_PUT_VAR (forcing_id,vid, &
1138                  (/(REAL(i,r_std),i=1,nbp_glo) /))
1139             ier = NF90_INQ_VARID (forcing_id,'layers',vid)
1140             ier = NF90_PUT_VAR (forcing_id,vid,(/(REAL(i,r_std),i=1,nslm)/))
1141             ier = NF90_INQ_VARID (forcing_id,'pft',vid)
1142             ier = NF90_PUT_VAR (forcing_id,vid,(/(REAL(i,r_std),i=1,nvm)/))
1143             ier = NF90_INQ_VARID (forcing_id,'direction',vid)
1144             ier = NF90_PUT_VAR (forcing_id,vid,(/(REAL(i,r_std),i=1,2)/))
1145             ier = NF90_INQ_VARID (forcing_id,'nneigh',vid)
1146             ier = NF90_PUT_VAR (forcing_id,vid,(/(REAL(i,r_std),i=1,8)/))
1147             ier = NF90_INQ_VARID (forcing_id,'time',vid)
1148             ier = NF90_PUT_VAR (forcing_id,vid,(/(REAL(i,r_std),i=1,nsft)/))
1149             ier = NF90_INQ_VARID (forcing_id,'nbparts',vid)
1150             ier = NF90_PUT_VAR (forcing_id,vid,(/(REAL(i,r_std),i=1,nparts)/))
1151             ier = NF90_INQ_VARID (forcing_id,'index',vid) 
1152             ier = NF90_PUT_VAR (forcing_id,vid,REAL(index_g,r_std))
1153             ier = NF90_INQ_VARID (forcing_id,'contfrac',vid)
1154             ier = NF90_PUT_VAR (forcing_id,vid,REAL(contfrac_g,r_std))
1155             ier = NF90_INQ_VARID (forcing_id,'lalo',vid)
1156             ier = NF90_PUT_VAR (forcing_id,vid,lalo_g)
1157             !ym attention a neighbours, a modifier plus tard     
1158             ier = NF90_INQ_VARID (forcing_id,'neighbours',vid)
1159             ier = NF90_PUT_VAR (forcing_id,vid,REAL(neighbours_g,r_std))
1160             ier = NF90_INQ_VARID (forcing_id,'resolution',vid)
1161             ier = NF90_PUT_VAR (forcing_id,vid,resolution_g)
1162          ENDIF ! is_root_prc
1163       ENDIF ! (forcing_name) /= 'NONE'
1164    ENDIF ! ok_co2 =.TRUE.
1165   
1166    !! 1.4.7 write forcing file for forcesoil
1167    !! 1.4.7.1 Initialize
1168    !Config Key   = STOMATE_CFORCING_NAME
1169    !Config Desc  = Name of STOMATE's carbon forcing file
1170    !Config If    = OK_STOMATE
1171    !Config Def   = NONE
1172    !Config Help  = Name that will be given to STOMATE's carbon
1173    !Config         offline forcing file
1174    !Config         Compatible with Nicolas Viovy's driver
1175    !Config Units = [FILE]
1176    Cforcing_name = stomate_Cforcing_name
1177    CALL getin_p('STOMATE_CFORCING_NAME',Cforcing_name)
1178   
1179    IF ( TRIM(Cforcing_name) /= 'NONE' ) THEN
1180       
1181       ! Time step of forcesoil
1182       !Config Key   = FORCESOIL_STEP_PER_YEAR
1183       !Config Desc  = Number of time steps per year for carbon spinup.
1184       !Config If    = OK_STOMATE
1185       !Config Def   = 365
1186       !Config Help  = Number of time steps per year for carbon spinup.
1187       !Config Units = [days, months, year]
1188       nparan = 365
1189       CALL getin_p('FORCESOIL_STEP_PER_YEAR', nparan)
1190       
1191       ! Correct if setting is out of bounds
1192       IF ( nparan < 1 ) nparan = 1
1193       
1194       !Config Key   = FORCESOIL_NB_YEAR
1195       !Config Desc  = Number of years saved for carbon spinup.
1196       !Config If    = OK_STOMATE
1197       !Config Def   = 1
1198       !Config Help  = Number of years saved for carbon spinup. If internal parameter cumul_Cforcing is TRUE in stomate.f90
1199       !Config         Then this parameter is forced to one.
1200       !Config Units = [years]
1201       CALL getin_p('FORCESOIL_NB_YEAR', nbyear)
1202       
1203       ! Set ::nbyear to 1. if ::cumul_Cforcing=.TRUE.
1204       IF ( cumul_Cforcing ) THEN
1205          CALL ipslerr_p (1,'stomate', &
1206               'Internal parameter cumul_Cforcing is TRUE in stomate.f90', &
1207               'Parameter FORCESOIL_NB_YEAR is therefore forced to 1.', &
1208               '::nbyear is thus set to 1.')
1209          nbyear=1
1210       ENDIF
1211       
1212       ! Make use of ::nparan to calculate ::dt_forcesoil
1213       dt_forcesoil = zero
1214       nparan = nparan+1
1215       DO WHILE ( dt_forcesoil < dt_stomate/one_day )
1216          nparan = nparan-1
1217          IF ( nparan < 1 ) THEN
1218             STOP 'Problem with number of soil forcing time steps ::nparan < 1.'
1219          ENDIF
1220          dt_forcesoil = one_year/REAL(nparan,r_std)
1221       ENDDO
1222       IF ( nparan > nparanmax ) THEN
1223          STOP 'Problem with number of soil forcing time steps ::nparan > ::nparanmax'
1224       ENDIF
1225       IF (printlev>=2) WRITE(numout,*) 'Time step of soil forcing (d): ',dt_forcesoil
1226       
1227       ! Allocate memory for the forcing variables of soil dynamics
1228       ALLOCATE( nforce(nparan*nbyear))
1229       nforce(:) = 0
1230           ALLOCATE(control_moist_above(kjpindex,nvm,nparan*nbyear))
1231           ALLOCATE(control_moist_soil(kjpindex,nslmd,nvm,nparan*nbyear))
1232       ALLOCATE(npp_equil(kjpindex,nparan*nbyear))
1233       ALLOCATE(npp_tot(kjpindex))
1234       ALLOCATE(moist_soil(kjpindex,nslm,nparan*nbyear))
1235           ALLOCATE(soil_mc_Cforcing(kjpindex,nslm,nstm,nparan*nbyear))
1236           ALLOCATE(floodout_Cforcing(kjpindex,nparan*nbyear))
1237           ALLOCATE(wat_flux0_Cforcing(kjpindex,nstm,nparan*nbyear))
1238           ALLOCATE(wat_flux_Cforcing(kjpindex,nslm,nstm,nparan*nbyear))
1239           ALLOCATE(runoff_per_soil_Cforcing(kjpindex,nstm,nparan*nbyear))
1240           ALLOCATE(drainage_per_soil_Cforcing(kjpindex,nstm,nparan*nbyear))
1241           ALLOCATE(DOC_to_topsoil_Cforcing(kjpindex,nflow,nparan*nbyear))
1242           ALLOCATE(DOC_to_subsoil_Cforcing(kjpindex,nflow,nparan*nbyear))
1243           ALLOCATE(precip2canopy_Cforcing(kjpindex,nvm,nparan*nbyear))
1244           ALLOCATE(precip2ground_Cforcing(kjpindex,nvm,nparan*nbyear))
1245           ALLOCATE(canopy2ground_Cforcing(kjpindex,nvm,nparan*nbyear))
1246           ALLOCATE(flood_frac_Cforcing(kjpindex,nparan*nbyear))
1247           ALLOCATE(control_temp_above(kjpindex,nlitt,nparan*nbyear))
1248           ALLOCATE(control_temp_soil(kjpindex,nslmd,npool*2,nparan*nbyear))
1249           ALLOCATE(soilcarbon_input(kjpindex,nvm,nslmd,npool,nelements,nparan*nbyear))
1250           ALLOCATE(litter_above_Cforcing(kjpindex,nlitt,nvm,nelements,nparan*nbyear))
1251           ALLOCATE(litter_below_Cforcing(kjpindex,nlitt,nvm,nslmd,nelements,nparan*nbyear))
1252           ALLOCATE(lignin_struc_above_Cforcing(kjpindex,nvm,nparan*nbyear))
1253           ALLOCATE(lignin_struc_below_Cforcing(kjpindex,nvm,nslmd,nparan*nbyear))   
1254       
1255       ! Initialize variables, set to zero
1256         control_moist_above(:,:,:) = zero
1257         control_moist_soil(:,:,:,:) = zero       
1258     npp_equil(:,:) = zero
1259     npp_tot(:) = zero
1260         moist_soil(:,:,:) = zero
1261         soil_mc_Cforcing(:,:,:,:) = zero
1262         floodout_Cforcing(:,:) = zero
1263         wat_flux0_Cforcing(:,:,:) = zero
1264         wat_flux_Cforcing(:,:,:,:) = zero
1265         runoff_per_soil_Cforcing(:,:,:) = zero
1266         drainage_per_soil_Cforcing(:,:,:) = zero
1267         DOC_to_topsoil_Cforcing(:,:,:) = zero
1268         DOC_to_subsoil_Cforcing(:,:,:) = zero
1269         precip2canopy_Cforcing(:,:,:) = zero
1270         precip2ground_Cforcing(:,:,:) = zero
1271         canopy2ground_Cforcing(:,:,:) = zero 
1272         flood_frac_Cforcing(:,:) = zero
1273         control_temp_above(:,:,:) = zero
1274         control_temp_soil(:,:,:,:) = zero
1275         soilcarbon_input(:,:,:,:,:,:) = zero
1276         litter_above_Cforcing(:,:,:,:,:) = zero
1277         litter_below_Cforcing(:,:,:,:,:,:) = zero
1278         lignin_struc_above_Cforcing(:,:,:) = zero
1279         lignin_struc_below_Cforcing(:,:,:,:) = zero 
1280    ENDIF ! Cforcing_name) /= 'NONE'
1281   
1282    !! 1.4.8 Calculate STOMATE's vegetation fractions from veget, veget_max
1283    DO j=1,nvm
1284       WHERE ((1.-totfrac_nobio(:)) > min_sechiba)       
1285          ! Pixels with vegetation
1286          veget_cov(:,j) = veget(:,j)/( 1.-totfrac_nobio(:) )
1287          veget_cov_max(:,j) = veget_max(:,j)/( 1.-totfrac_nobio(:) )
1288       ELSEWHERE
1289          ! Pixels without vegetation
1290          veget_cov(:,j) = zero
1291          veget_cov_max(:,j) = zero
1292       ENDWHERE
1293    ENDDO ! Loop over PFTs
1294
1295    !! 1.4.9 Initialize non-zero variables
1296    CALL stomate_var_init &
1297         (kjpindex, veget_cov_max, leaf_age, leaf_frac, &
1298         dead_leaves, &
1299         veget, lai, deadleaf_cover, assim_param)
1300   
1301    ! Initialize land cover change variable
1302    ! ??Should be integrated in the subroutine??
1303    harvest_above(:) = zero
1304   
1305    ! Initialize temp_growth
1306    temp_growth(:)=t2m_month(:)-tp_00 
1307
1308     
1309  END SUBROUTINE stomate_initialize
1310 
1311
1312!! ================================================================================================================================
1313!! SUBROUTINE   : stomate_main
1314!!
1315!>\BRIEF        Manages variable initialisation, reading and writing forcing
1316!! files, aggregating data at stomate's time step (dt_stomate), aggregating data
1317!! at longer time scale (i.e. for phenology) and uses these forcing to calculate
1318!! CO2 fluxes (NPP and respirations) and C-pools (litter, soil, biomass, ...)
1319!!
1320!! DESCRIPTION  : The subroutine manages
1321!! divers tasks:
1322!! (1) Initializing all variables of stomate (first call)
1323!! (2) Reading and writing forcing data (last call)
1324!! (3) Adding CO2 fluxes to the IPCC history files
1325!! (4) Converting the time steps of variables to maintain consistency between
1326!! sechiba and stomate
1327!! (5) Use these variables to call stomate_lpj, maint_respiration, littercalc,
1328!! soilcarbon. The called subroutines handle: climate constraints
1329!! for PFTs, PFT dynamics, Phenology, Allocation, NPP (based on GPP and
1330!! authothropic respiration), fire, mortality, vmax, assimilation temperatures,
1331!! all turnover processes, light competition, sapling establishment, lai, 
1332!! land cover change and litter and soil dynamics.
1333!! (6) Use the spin-up method developed by Lardy (2011)(only if SPINUP_ANALYTIC
1334!! is set to TRUE).
1335!!
1336!! RECENT CHANGE(S) : None
1337!!
1338!! MAIN OUTPUT VARIABLE(S): deadleaf_cover, assim_param, lai, height, veget,
1339!! veget_max, resp_maint,
1340!! resp_hetero,resp_growth, co2_flux, fco2_lu.
1341!!
1342!! REFERENCES   :
1343!! - Lardy, R, et al., A new method to determine soil organic carbon equilibrium,
1344!! Environmental Modelling & Software (2011), doi:10.1016|j.envsoft.2011.05.016
1345!!
1346!! FLOWCHART    :
1347!! \latexonly
1348!! \includegraphics[scale=0.5]{stomatemainflow.png}
1349!! \endlatexonly
1350!! \n
1351!_ ================================================================================================================================
1352 
1353SUBROUTINE stomate_main &
1354       & (kjit, kjpij, kjpindex, &
1355       &  index, lalo, neighbours, resolution, contfrac, totfrac_nobio, clay, &
1356       &  t2m, temp_sol, stempdiag, &
1357       &  humrel, shumdiag, litterhumdiag, precip_rain, precip_snow, &
1358       &  gpp, deadleaf_cover, assim_param, &
1359       &  lai, frac_age, height, veget, veget_max, &
1360       &  veget_max_new, woodharvest, totfrac_nobio_new, fraclut, &
1361       &  rest_id_stom, hist_id_stom, hist_id_stom_IPCC, &
1362       &  co2_flux, fco2_lu, resp_maint,resp_hetero,resp_growth,co2_to_bm_radia,temp_growth, &
1363       &  soil_mc, soiltile, &
1364       &  litter_mc,floodout, runoff, drainage, wat_flux0, wat_flux,bulk_dens, soil_ph, poor_soils, &
1365       &  drainage_per_soil, runoff_per_soil, DOC_EXP_agg, &
1366       &  DOC_to_topsoil, DOC_to_subsoil, flood_frac, precip2canopy, precip2ground, canopy2ground, fastr, Cinp_manure, &
1367           &  rootmass,litter_above,litter_below,carbon,DOC, lignin_struc_above,lignin_struc_below, depth_deepsoil)   
1368    IMPLICIT NONE
1369
1370   
1371  !! 0. Variable and parameter declaration
1372
1373    !! 0.1 Input variables
1374
1375    INTEGER(i_std),INTENT(in)                       :: kjit              !! Time step number (unitless)
1376    INTEGER(i_std),INTENT(in)                       :: kjpindex          !! Domain size - terrestrial pixels only (unitless)
1377    INTEGER(i_std),INTENT(in)                       :: kjpij             !! Total size of the un-compressed grid (unitless)
1378    INTEGER(i_std),INTENT(in)                       :: rest_id_stom      !! STOMATE's _Restart_ file identifier (unitless)
1379    INTEGER(i_std),INTENT(in)                       :: hist_id_stom      !! STOMATE's _history_ file identifier (unitless)
1380    INTEGER(i_std),INTENT(in)                       :: hist_id_stom_IPCC !! STOMATE's IPCC _history_ file identifier
1381                                                                         !! (unitless)
1382    INTEGER(i_std),DIMENSION(kjpindex),INTENT(in)   :: index             !! Indices of the pixels on the map. Stomate uses a
1383                                                                         !! reduced grid excluding oceans. ::index contains
1384                                                                         !! the indices of the terrestrial pixels only
1385                                                                         !! (unitless)
1386    INTEGER(i_std),DIMENSION(kjpindex,NbNeighb),INTENT(in) :: neighbours !! Neighoring grid points if land for the DGVM
1387                                                                         !! (unitless)
1388    REAL(r_std),DIMENSION(kjpindex,2),INTENT(in)    :: lalo              !! Geographical coordinates (latitude,longitude)
1389                                                                         !! for pixels (degrees)
1390    REAL(r_std),DIMENSION(kjpindex,2),INTENT(in)    :: resolution        !! Size in x an y of the grid (m) - surface area of
1391                                                                         !! the gridbox
1392    REAL(r_std),DIMENSION (kjpindex), INTENT (in)   :: contfrac          !! Fraction of continent in the grid cell (unitless)
1393    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: totfrac_nobio     !! Fraction of grid cell covered by lakes, land
1394                                                                         !! ice, cities, ... (unitless)
1395    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: clay              !! Clay fraction of soil (0-1, unitless)
1396    REAL(r_std),DIMENSION(kjpindex),INTENT(inout)   :: bulk_dens         !! Soil bulk density (g cm-3)
1397    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: soil_ph           !! Soil pH (0-14, pH unit)
1398    REAL(r_std),DIMENSION(kjpindex),INTENT(inout)   :: poor_soils        !! Fraction of poor soils (0-1)       
1399    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)  :: humrel            !! Relative humidity ("moisture availability")
1400                                                                         !! (0-1, unitless)
1401    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: t2m               !! 2 m air temperature (K)
1402    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: temp_sol          !! Surface temperature (K)
1403    REAL(r_std),DIMENSION(kjpindex,nslm),INTENT(in) :: stempdiag         !! Soil temperature (K)
1404    REAL(r_std),DIMENSION(kjpindex,nslm),INTENT(in) :: shumdiag          !! Relative soil moisture (0-1, unitless)
1405    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: litterhumdiag     !! Litter humidity (0-1, unitless)
1406    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: precip_rain       !! Rain precipitation 
1407                                                                         !! @tex $(mm dt_stomate^{-1})$ @endtex
1408    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: precip_snow       !! Snow precipitation 
1409                                                                         !! @tex $(mm dt_stomate^{-1})$ @endtex
1410    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)  :: gpp               !! GPP of total ground area 
1411                                                                         !! @tex $(gC m^{-2} time step^{-1})$ @endtex
1412                                                                         !! Calculated in sechiba, account for vegetation
1413                                                                         !! cover and effective time step to obtain ::gpp_d
1414    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)  :: veget_max_new     !! New "maximal" coverage fraction of a PFT: only if
1415                                                                         !! vegetation is updated in slowproc
1416    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: woodharvest       !! Harvested wood biomass (gC m-2 yr-1)
1417    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: totfrac_nobio_new !! New fraction of nobio per gridcell
1418    REAL(r_std),DIMENSION(kjpindex, nlut),INTENT(in):: fraclut           !! Fraction of landuse tiles
1419    REAL(r_std),DIMENSION (kjpindex,nslm,nstm), INTENT(in)  :: soil_mc   !! soil moisture content \f($m^3 \times m^3$)\f
1420    REAL(r_std),DIMENSION (kjpindex,nstm), INTENT (in)      :: soiltile  !! Fraction of each soil tile (0-1, unitless)
1421    REAL(r_std),DIMENSION (kjpindex,nstm), INTENT(in):: litter_mc        !! litter moisture content \f($m^3 \times m^3$)\f
1422    REAL(r_std),DIMENSION (kjpindex), INTENT (in)   :: floodout          !! flux out of floodplains
1423    REAL(r_std),DIMENSION (kjpindex), INTENT (in)   :: runoff            !! Complete runoff
1424    REAL(r_std),DIMENSION (kjpindex), INTENT (in)   :: drainage          !! Drainage
1425    REAL(r_std),DIMENSION (kjpindex,nstm), INTENT(in)    :: wat_flux0           !! Water flux in the first soil layers exported for soil C calculations
1426    REAL(r_std),DIMENSION (kjpindex,nslm,nstm), INTENT(in)   :: wat_flux        !! Water flux in the soil layers exported for soil C calculations
1427    REAL(r_std),DIMENSION (kjpindex,nstm), INTENT (in)   :: runoff_per_soil     !! Runoff per soil type [mm]
1428    REAL(r_std),DIMENSION (kjpindex,nstm), INTENT (in)   :: drainage_per_soil   !! Drainage per soil type [mm]
1429    REAL(r_std),DIMENSION (kjpindex,nflow), INTENT(in)   :: DOC_to_topsoil      !! DOC inputs to top of the soil column, from reinfiltration on
1430                                                                                !! floodplains and from irrigation
1431                                                                                !! @tex $(gC m^{-2} day{-1})$ @endtex
1432    REAL(r_std),DIMENSION (kjpindex,nflow), INTENT(in)   :: DOC_to_subsoil      !! DOC inputs to bottom of the soil column, from returnflow
1433                                                                                !! in swamps and lakes
1434                                                                                !! @tex $(gC m^{-2} day{-1})$ @endtex
1435    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT(in)     :: canopy2ground       !! Waterflux from canopy to the ground
1436    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT(in)     :: precip2ground       !! Precipitation not intercepted by canopy
1437    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT(in)     :: precip2canopy       !! Precipitation onto the canopy 
1438    REAL(r_std),DIMENSION (kjpindex), INTENT(in)         :: flood_frac          !! Flooded fraction of grid box (-)     
1439    REAL(r_std),DIMENSION (kjpindex), INTENT(in)         :: fastr               !! Fast reservoir (mm) 
1440                REAL(r_std),DIMENSION (kjpindex,nvm), INTENT(in)     :: Cinp_manure         !! Manure-N input (g C m-2 day-1)                                                                                                                                                                                                                   
1441
1442    !! 0.2 Output variables
1443
1444        REAL(r_std),DIMENSION(kjpindex,nexp,nflow),INTENT(out) :: DOC_EXP_agg  !! DOC exports, diffrenet paths (nexp), in 
1445                                                                           !! @tex $(gC m^{-2} dt_sechiba^{-1})$ @endtex 
1446    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: co2_flux          !! CO2 flux between atmosphere and biosphere per
1447                                                                         !! average ground area
1448                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex 
1449                                                                         !! [??CHECK] sign convention?
1450    REAL(r_std),DIMENSION(kjpindex),INTENT(out)     :: fco2_lu           !! CO2 flux between atmosphere and biosphere from
1451                                                                         !! land-use (without forest management) 
1452                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex 
1453                                                                         !! [??CHECK] sign convention?
1454    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: resp_maint        !! Maitenance component of autotrophic respiration in
1455                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
1456    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: resp_growth       !! Growth component of autotrophic respiration in
1457                                                                         !! @tex ($gC m^{-2} dt_stomate^{-1}$) @endtex
1458    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: resp_hetero       !! Heterotrophic respiration in 
1459                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex 
1460    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: co2_to_bm_radia   !! Virtual gpp created for equilibrium of carbon mass 
1461                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex 
1462    REAL(r_std),DIMENSION(kjpindex),INTENT(out)     :: temp_growth       !! Growth temperature (°C) 
1463                                                                         !! Is equal to t2m_month
1464
1465    !! 0.3 Modified
1466   
1467    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(inout)       :: lai            !! Leaf area inex @tex $(m^2 m^{-2})$ @endtex
1468    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)          :: veget          !! Fraction of vegetation type including
1469                                                                              !! non-biological fraction (unitless)
1470    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(inout)       :: veget_max      !! Maximum fraction of vegetation type including
1471                                                                              !! non-biological fraction (unitless)
1472    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(inout)       :: height         !! Height of vegetation (m)
1473    REAL(r_std),DIMENSION(kjpindex,nvm,npco2),INTENT(inout) :: assim_param    !! min+max+opt temperatures (K) & vmax for
1474                                                                              !! photosynthesis 
1475                                                                              !! @tex $(\mu mol m^{-2}s^{-1})$ @endtex 
1476    REAL(r_std),DIMENSION(kjpindex),INTENT(inout)           :: deadleaf_cover !! Fraction of soil covered by dead leaves
1477                                                                              !! (unitless)
1478    REAL(r_std),DIMENSION(kjpindex,nvm,nleafages),INTENT(inout):: frac_age    !! Age efficacity from STOMATE
1479        REAL(r_std),DIMENSION (kjpindex,nvm,nparts,nelements), INTENT (inout)       :: rootmass     !! root biomass
1480                                                                                                    !! @tex $(gC m^{-2})$ @endtex
1481        REAL(r_std),DIMENSION (kjpindex,nlitt,nvm,nelements), INTENT (inout)        :: litter_above !! Above ground metabolic and structural litter
1482                                                                                                    !! @tex $(gC m^{-2})$ @endtex
1483    REAL(r_std),DIMENSION (kjpindex,nlitt,nvm,nslmd,nelements), INTENT (inout) :: litter_below !! Below ground metabolic and structural litter
1484                                                                                                !! per ground area                                                                                                                                                                                          !! per ground area
1485                                                                                                                                                                            !! @tex $(gC m^{-2})$ @endtex
1486        REAL(r_std),DIMENSION (kjpindex,ncarb,nvm,nslmd), INTENT (inout)                :: carbon       !! Soil carbon pools per ground area: active, slow, or
1487                                                                                                !! passive, @tex $(gC m^{-2})$ @endtex
1488    REAL(r_std), DIMENSION(kjpindex,nvm,nslmd,ndoc,npool,nelements), INTENT(inout) :: DOC          !! Dissolved Organic Carbon in soil
1489                                                                                                !! The unit is given by m^2 of
1490                                                                                                !! ground @tex $(gC m{-2} of ground)$ @endtex
1491    REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)              :: lignin_struc_above          !! Ratio Lignin content in structural litter,
1492                                                                                                !! above ground, (0-1, unitless)
1493        REAL(r_std), DIMENSION(kjpindex,nvm,nslmd), INTENT(inout)       :: lignin_struc_below          !! Ratio Lignin content in structural litter,
1494                                                                                                !! below ground, (0-1, unitless)                                                                                                                                                                                       
1495
1496    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (inout)                :: depth_deepsoil          !! Depth of the soil layer deeper than 2 m.
1497                                                                                                !! When sediment deposition occuring, the original surface (0-2)
1498                                                                                                                                                                            !! soil DOC, and SOC will enther into this layer.   
1499        !! 0.4 local variables
1500   
1501    REAL(r_std)                                   :: dt_days_read             !! STOMATE time step read in restart file (days)
1502    INTEGER(i_std)                                :: l,k,ji, jv, i, j, ig, m      !! indices   
1503    REAL(r_std),PARAMETER                         :: max_dt_days = 5.         !! Maximum STOMATE time step (days)
1504    REAL(r_std)                                   :: hist_days                !! Writing frequency for history file (days)
1505    REAL(r_std),DIMENSION(0:nslm)                 :: z_soil                   !! Variable to store depth of the different soil
1506                                                                              !! layers (m)
1507    REAL(r_std),DIMENSION(kjpindex,nvm)           :: rprof                    !! Coefficient of the exponential functions that
1508                                                                              !! relates root density to soil depth (unitless)
1509    REAL(r_std),DIMENSION(kjpindex)               :: cvegtot                  !! Total "vegetation" cover (unitless)
1510    REAL(r_std),DIMENSION(kjpindex)               :: precip                   !! Total liquid and solid precipitation 
1511                                                                              !! @tex $(??mm dt_stomate^{-1})$ @endtex
1512    REAL(r_std),DIMENSION(kjpindex,nvm)           :: gpp_d                    !! Gross primary productivity per ground area
1513                                                                              !! @tex $(??gC m^{-2} dt_stomate^{-1})$ @endtex 
1514    REAL(r_std),DIMENSION(kjpindex,nvm)           :: gpp_daily_x              !! "Daily" gpp for teststomate 
1515                                                                              !! @tex $(??gC m^{-2} dt_stomate^{-1})$ @endtex
1516    REAL(r_std), DIMENSION(kjpindex,nvm,nelements)      :: dry_dep_canopy     !! Increase in canopy storage of soluble OC & DOC
1517                                                                              !! @tex $(gC.m^{-2} dt{-1})$ @endtex
1518    REAL(r_std), DIMENSION(kjpindex,nvm,nelements)      :: DOC_precip2canopy  !! Wet deposition of DOC onto canopy
1519                                                                              !! @tex $(gC.m^{-2} dt{-1})$ @endtex
1520    REAL(r_std), DIMENSION(kjpindex,nvm,nelements)      :: DOC_precip2ground  !! Wet deposition of DOC not intecepted by canopy
1521                                                                              !! @tex $(gC.m^{-2} dt{-1})$ @endtex
1522    REAL(r_std), DIMENSION(kjpindex,nvm,nelements)      :: DOC_canopy2ground  !! DOC flux to ground with excess water from canopy
1523                                                                              !! @tex $(gC.m^{-2} dt{-1})$ @endtex
1524    REAL(r_std), DIMENSION(kjpindex,nvm,nelements)      :: DOC_infil          !! Wet deposition of DOC infiltrating into the ground
1525                                                                              !! @tex $(gC.m^{-2} dt{-1})$ @endtex
1526    REAL(r_std), DIMENSION(kjpindex,nvm,nelements)      :: DOC_noinfil        !! Wet deposition of DOC not infiltrating into the ground
1527                                                                              !! @tex $(gC.m^{-2} dt{-1})$ @endtex                                                                                                                                                       
1528        REAL(r_std),DIMENSION(kjpindex,nvm)           :: Cinp_manure_solid        !! Solid manure-C input (metabolic litter-C, gC.m^{-2} dt{-1})
1529        REAL(r_std),DIMENSION(kjpindex,nvm)           :: Cinp_manure_liquid       !! Liquid manure-C input (metabolic litter-C, gC.m^{-2} dt{-1})                                                                                                                                                         
1530    REAL(r_std),DIMENSION(kjpindex,nvm)           :: resp_hetero_litter       !! Litter heterotrophic respiration per ground area
1531                                                                              !! @tex $(gC m^{-2} day^{-1})$ @endtex 
1532                                                                              !! ??Same variable is also used to
1533                                                                              !! store heterotrophic respiration per ground area
1534                                                                              !! over ::dt_sechiba??
1535    REAL(r_std),DIMENSION(kjpindex,nvm)           :: resp_hetero_flood        !! Litter heterotrophic respiration per ground area
1536                                                                              !! @tex $(gC m^{-2} day^{-1})$ @endtex
1537                                                                              !! ??Same variable is also used to
1538                                                                              !! store heterotrophic respiration per ground area
1539                                                                              !! over ::dt_sechiba??                                                                                                                                                     
1540    REAL(r_std),DIMENSION(kjpindex,nvm)           :: resp_hetero_soil         !! soil heterotrophic respiration 
1541                                                                              !! @tex $(gC m^{-2} day^{-1})$ @endtex
1542    REAL(r_std),DIMENSION(kjpindex,nvm)           :: resp_flood_soil          !! soil heterotrophic respiration when flooded
1543                                                                              !! @tex $(gC m^{-2} day^{-1})$ @endtex
1544    REAL(r_std), DIMENSION(kjpindex,nvm,nexp,npool,nelements) :: DOC_EXP      !! Exported DOC through runoff, drainage, flood,
1545                                                                              !! The unit is give by m^2 of
1546                                                                              !! water @tex $(fC m{-2} of ground)$ @endtex
1547    REAL(r_std), DIMENSION(kjpindex,nvm,nexp,nflow,nelements) :: DOC_EXP_b    !! Exported DOC through runoff, drainage, flood,
1548                                                                              !! The unit is give by m^2 of
1549                                                                              !! water @tex $(fC m{-2} of ground)$ @endtex                                                                                                                                                       
1550    REAL(r_std),DIMENSION(kjpindex,nvm)           :: veget_cov                !! Fractional coverage: actually share of the pixel
1551                                                                              !! covered by a PFT (fraction of ground area),
1552                                                                              !! taking into account LAI ??(= grid scale fpc)??
1553    REAL(r_std),DIMENSION(kjpindex,nvm)           :: veget_cov_max_new        !! New value for maximal fractional coverage (unitless)
1554    REAL(r_std),DIMENSION(kjpindex,nvm)           :: vcmax                    !! Maximum rate of carboxylation
1555                                                                              !! @tex $(\mumol m^{-2} s^{-1})$ @endtex
1556    REAL(r_std),DIMENSION(kjpindex,nvm)           :: control_moist_above_inst !! Moisture control of heterotrophic respiration 
1557                                                                              !! (0-1, unitless)
1558    REAL(r_std),DIMENSION(kjpindex,nslmd,nvm)     :: control_moist_soil_inst  !! Moisture control of heterotrophic respiration
1559                                                                              !! (0-1,unitless)
1560    REAL(r_std),DIMENSION(kjpindex,nslm)          :: moist_soil_inst          !! Soil moiture daily (m3 H20 m-3 Soil) 
1561    REAL(r_std),DIMENSION(kjpindex,nslm,nstm)     :: soil_mc_Cforcing_inst    !! Soil moiture per soil type daily (m3 H20 m-3 Soil)
1562    REAL(r_std),DIMENSION (kjpindex)              :: floodout_Cforcing_inst   !! flux out of floodplains
1563    REAL(r_std),DIMENSION (kjpindex,nstm)         :: wat_flux0_Cforcing_inst  !! Water flux in the first soil layers exported for soil C calculations
1564    REAL(r_std),DIMENSION (kjpindex,nslm,nstm)    :: wat_flux_Cforcing_inst   !! Water flux in the soil layers exported for soil C calculations
1565    REAL(r_std),DIMENSION (kjpindex,nstm)         :: runoff_per_soil_Cforcing_inst            !! Runoff per soil type [mm]
1566    REAL(r_std),DIMENSION (kjpindex,nstm)         :: drainage_per_soil_Cforcing_inst          !! Drainage per soil type [mm]
1567    REAL(r_std),DIMENSION (kjpindex,nflow)        :: DOC_to_topsoil_Cforcing_inst  !! DOC inputs to top of the soil column, from reinfiltration on
1568                                                                                   !! floodplains and from irrigation
1569                                                                                   !! @tex $(gC m^{-2} day{-1})$ @endtex
1570    REAL(r_std),DIMENSION (kjpindex,nflow)        :: DOC_to_subsoil_Cforcing_inst  !! DOC inputs to bottom of the soil column, from returnflow
1571                                                                                   !! in swamps and lakes
1572                                                                                   !! @tex $(gC m^{-2} day{-1})$ @endtex
1573    REAL(r_std),DIMENSION(kjpindex,nvm)           :: precip2canopy_Cforcing_inst   !! Precipitation onto the canopy
1574    REAL(r_std),DIMENSION(kjpindex,nvm)           :: precip2ground_Cforcing_inst   !! Precipitation not intercepted by canopy
1575    REAL(r_std),DIMENSION(kjpindex,nvm)           :: canopy2ground_Cforcing_inst   !! Water flux from canopy to the ground
1576    REAL(r_std),DIMENSION (kjpindex)              :: flood_frac_Cforcing_inst  !! Flooded fraction of the grid box (1)
1577    REAL(r_std),DIMENSION(kjpindex,nlitt)               :: control_temp_above_inst  !! Temperature control of heterotrophic 
1578                                                                              !! respiration, above (0-1, unitless)
1579    REAL(r_std),DIMENSION(kjpindex,nslmd,npool*2)        :: control_temp_soil_inst   !! Temperature control of heterotrophic
1580                                                                              !! respiration, below (0-1, unitless)
1581
1582    REAL(r_std),DIMENSION(kjpindex,nvm,nslmd,npool,nelements) :: soilcarbon_input_inst   !! Quantity of carbon going into DOC pools from
1583                                                                              !! litter decomposition
1584                                                                              !! @tex $(gC m^{-2} day^{-1})$ @endtex
1585    REAL(r_std),DIMENSION(kjpindex,nvm,npool,nelements) :: floodcarbon_input_inst   !! Quantity of carbon going into DOC pools from
1586                                                                              !! litter decomposition
1587                                                                              !! @tex $(gC m^{-2} day^{-1})$ @endtex
1588 
1589    REAL(r_std),DIMENSION(kjpindex,nvm,nslmd,npool,nelements) :: DOC_input_inst !! Quantity of carbon going into dissolved organic carbon pools from
1590                                                                              !! litter decomposition
1591                                                                              !! @tex $(gC m^{-2} day^{-1})$ @endtex
1592    REAL(r_std), DIMENSION(kjpindex,nvm,nmbcomp,nelements)   :: check_intern  !! Contains the components of the internal
1593                                                                              !! mass balance chech for this routine
1594                                                                              !! @tex $(gC pixel^{-1} dt^{-1})$ @endtex
1595    REAL(r_std), DIMENSION(kjpindex,nvm,nelements) :: closure_intern          !! Check closure of internal mass balance
1596                                                                              !! @tex $(gC pixel^{-1} dt^{-1})$ @endtex
1597    REAL(r_std), DIMENSION(kjpindex,nvm,nelements) :: pool_start              !! Start and end pool of this routine
1598                                                                              !! @tex $(gC pixel^{-1} dt^{-1})$ @endtex
1599    REAL(r_std), DIMENSION(kjpindex,nvm,nelements) :: pool_end                !! Start and end pool of this routine
1600                                                                              !! @tex $(gC pixel^{-1} dt^{-1})$ @endtex   
1601    REAL(r_std), DIMENSION(kjpindex,nvm)           :: flood_root_radia        !! Root respiration in flooded area
1602                                                                              !! @tex $(gC m^{-2} dt_sechiba^{-1})$ @endtex
1603    INTEGER(i_std)                                :: ier                      !! Check errors in netcdf call (unitless)
1604    REAL(r_std)                                   :: sf_time                  !! Intermediate variable to calculate current time
1605                                                                              !! step
1606    INTEGER(i_std)                                :: max_totsize              !! Memory management - maximum memory size (Mb)
1607    INTEGER(i_std)                                :: totsize_1step            !! Memory management - memory required to store one
1608                                                                              !! time step on one processor (Mb)
1609    INTEGER(i_std)                                :: totsize_tmp              !! Memory management - memory required to store one
1610                                                                              !! time step on all processors(Mb)
1611    REAL(r_std)                                   :: xn                       !! How many times have we treated in this forcing
1612    REAL(r_std), DIMENSION(kjpindex)              :: vartmp                   !! Temporary variable
1613    INTEGER(i_std)                                :: vid                      !! Variable identifer of netCDF (unitless)
1614    INTEGER(i_std)                                :: nneigh                   !! Number of neighbouring pixels
1615    INTEGER(i_std)                                :: direct                   !! ??
1616    INTEGER(i_std),DIMENSION(ndm)                 :: d_id                     !! ??
1617    REAL(r_std)                                   :: net_nep_monthly          !! Integrated nep_monthly over all grid-cells on local domain
1618    REAL(r_std)                                   :: net_nep_monthly_sum      !! Integrated nep_monthly over all grid-cells on total domain(global)
1619    REAL(r_std),DIMENSION(nbp_glo)                :: clay_g                   !! Clay fraction of soil (0-1, unitless), parallel
1620                                                                              !! computing
1621    REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:,:)    :: soilcarbon_input_g       !! Quantity of carbon going into carbon pools from
1622                                                                              !! litter decomposition 
1623                                                                              !! @tex $(gC m^{-2} dt_sechiba^{-1})$ @endtex, parallel
1624                                                                              !! computing
1625    REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)      :: control_moist_g          !! Moisture control of heterotrophic respiration
1626                                                                              !! (0-1, unitless), parallel computing
1627    REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)      :: control_temp_g           !! Temperature control of heterotrophic respiration
1628                                                                              !! (0-1, unitless), parallel computing
1629    REAL(r_std),ALLOCATABLE,DIMENSION(:,:)        :: npp_equil_g              !! Equilibrium NPP written to forcesoil
1630                                                                              !! @tex $(gC m^{-2} year^{-1})$ @endtex, parallel
1631                                                                              !! computing
1632
1633    REAL(r_std)                                   :: net_cflux_prod_monthly_sum    !! AR5 output?? gC m2 month-1 (one variable for
1634                                                                                   !! reduce_sum and one for bcast??), parallel
1635                                                                                   !! computing
1636    REAL(r_std)                                   :: net_cflux_prod_monthly_tot    !! AR5 output?? gC m2 month-1 (one variable for
1637                                                                                   !! reduce_sum and one for bcast??), parallel
1638                                                                                   !! computing
1639    REAL(r_std)                                   :: net_harvest_above_monthly_sum !! AR5 output?? gC m2 month-1 (one variable for
1640                                                                                   !! reduce_sum and one for bcast??), parallel
1641                                                                                   !! computing
1642    REAL(r_std)                                   :: net_harvest_above_monthly_tot !! AR5 output?? gC m2 month-1 (one variable for
1643                                                                                   !! reduce_sum and one for bcast??), parallel
1644                                                                                   !! computing
1645    REAL(r_std)                                   :: net_biosp_prod_monthly_sum    !! AR5 output?? gC m2 month-1 (one variable for
1646                                                                                   !! reduce_sum and one for bcast??), parallel
1647                                                                                   !! computing
1648    REAL(r_std)                                   :: net_biosp_prod_monthly_tot    !! AR5 output?? gC m2 month-1 (one variable for
1649                                                                                   !! reduce_sum and one for bcast??), parallel
1650                                                                                   !! computing
1651    REAL(r_std), DIMENSION(kjpindex,nvm,nbpools)  :: carbon_stock                  !! Array containing the carbon stock for each pool
1652                                                                                   !! used by ORCHIDEE
1653    REAL(r_std)                                   :: soil_resp_modif               !! Factor scaling ref. CO2 conc. to soil respiration
1654       
1655!_ ================================================================================================================================
1656   
1657  !! 1. Initialize variables
1658
1659    !! 1.1 Store current time step in a common variable
1660    itime = kjit
1661   
1662    !! 1.3 PFT rooting depth across pixels, humescte is pre-defined
1663    ! (constantes_veg.f90). It is defined as the coefficient of an exponential
1664    ! function relating root density to depth
1665    DO j=1,nvm
1666       rprof(:,j) = 1./humcste(j)
1667    ENDDO
1668   
1669    !! 1.4 Initialize first call
1670    ! Set growth respiration to zero
1671    resp_growth=zero
1672
1673    ! Check that initialization is done
1674    IF (l_first_stomate) CALL ipslerr_p(3,'stomate_main','Initialization not yet done.','','')
1675   
1676    IF (printlev >= 4) THEN
1677       WRITE(numout,*) 'stomate_main: date=',days_since_beg,' ymds=', year_end, month_end, day_end, sec_end, &
1678            ' itime=', itime, ' do_slow=',do_slow
1679    ENDIF
1680
1681!! 3. Special treatment for some input arrays.
1682   
1683    !! 3.1 Sum of liquid and solid precipitation
1684    precip(:) = ( precip_rain(:) + precip_snow(:) )*one_day/dt_sechiba
1685   
1686    !! 3.2 Calculate STOMATE's vegetation fractions from veget and veget_max
1687    DO j=1,nvm 
1688       WHERE ((1.-totfrac_nobio(:)) > min_sechiba)
1689          ! Pixels with vegetation
1690          veget_cov(:,j) = veget(:,j)/( 1.-totfrac_nobio(:) )
1691          veget_cov_max(:,j) = veget_max(:,j)/( 1.-totfrac_nobio(:) )
1692       ELSEWHERE
1693          ! Pixels without vegetation
1694          veget_cov(:,j) = zero
1695          veget_cov_max(:,j) = zero
1696       ENDWHERE
1697    ENDDO
1698
1699    IF ( do_now_stomate_lcchange ) THEN
1700       DO j=1,nvm
1701          WHERE ((1.-totfrac_nobio_new(:)) > min_sechiba)
1702             ! Pixels with vegetation
1703             veget_cov_max_new(:,j) = veget_max_new(:,j)/( 1.-totfrac_nobio_new(:) )
1704          ELSEWHERE
1705             ! Pixels without vegetation
1706             veget_cov_max_new(:,j) = zero
1707          ENDWHERE
1708       ENDDO
1709    ENDIF
1710
1711    !! 3.3 Adjust time step of GPP
1712    ! No GPP for bare soil
1713    gpp_d(:,1) = zero
1714    ! GPP per PFT
1715    DO j = 2,nvm   
1716       WHERE (veget_cov_max(:,j) > min_stomate)
1717          ! The PFT is available on the pixel
1718          gpp_d(:,j) =  gpp(:,j)/ veget_cov_max(:,j)* one_day/dt_sechiba 
1719       ELSEWHERE
1720          ! The PFT is absent on the pixel
1721          gpp_d(:,j) = zero
1722       ENDWHERE
1723    ENDDO
1724
1725  !! 4. Calculate variables for dt_stomate (i.e. "daily")
1726
1727    ! Note: If dt_days /= 1, then variables 'xx_daily' (eg. half-daily or bi-daily) are by definition
1728    ! not expressed on a daily basis. This is not a problem but could be
1729    ! confusing
1730
1731    !! 4.1 Accumulate instantaneous variables (do_slow=.FALSE.)
1732    ! Accumulate instantaneous variables (do_slow=.FALSE.) and eventually
1733    ! calculate daily mean value (do_slow=.TRUE.)
1734    CALL stomate_accu (do_slow, humrel,        humrel_daily)
1735    CALL stomate_accu (do_slow, litterhumdiag, litterhum_daily)
1736    CALL stomate_accu (do_slow, t2m,           t2m_daily)
1737    CALL stomate_accu (do_slow, temp_sol,      tsurf_daily)
1738    CALL stomate_accu (do_slow, stempdiag,     tsoil_daily)
1739    CALL stomate_accu (do_slow, shumdiag,      soilhum_daily)
1740    CALL stomate_accu (do_slow, precip,        precip_daily)
1741    CALL stomate_accu (do_slow, gpp_d,         gpp_daily)
1742   
1743    !! 4.2 Daily minimum temperature
1744    t2m_min_daily(:) = MIN( t2m(:), t2m_min_daily(:) )
1745
1746    !! 4.3 Calculate maintenance respiration
1747    ! Note: lai is passed as output argument to overcome previous problems with
1748    ! natural and agricultural vegetation types.
1749    CALL maint_respiration &
1750         & (kjpindex,lai,t2m,t2m_longterm,stempdiag,height,veget_cov_max, &
1751         & rprof,biomass,resp_maint_part_radia)
1752                 
1753    Cinp_manure_solid(:,:) = zero
1754        Cinp_manure_liquid(:,:) = zero
1755        Cinp_manure_solid(:,:) = Cinp_manure*(un-f_liqmanure)* dt_sechiba/one_day
1756        Cinp_manure_liquid(:,:) = Cinp_manure*f_liqmanure* dt_sechiba/one_day
1757       
1758        !! Added by Haicheng Zhang, rootmass will be used to calculate the root-factor on soil erosion (erosion.f90)
1759        rootmass(:,:,:,:)=biomass(:,:,:,:)     
1760    ! Aggregate maintenance respiration across the different plant parts
1761    resp_maint_radia(:,:) = zero
1762    flood_root_radia(:,:) = zero
1763    DO j=2,nvm
1764       IF (lat_exp_doc) THEN
1765       flood_root_radia(:,j) = flood_frac(:) * resp_maint_part_radia(:,j,iroot)
1766       ELSE
1767          !do nothing
1768       ENDIF
1769       !
1770       DO k= 1, nparts
1771          resp_maint_radia(:,j) = resp_maint_radia(:,j) &
1772               & + resp_maint_part_radia(:,j,k)
1773       ENDDO
1774    ENDDO
1775   
1776    ! Maintenance respiration separated by plant parts
1777    resp_maint_part(:,:,:) = resp_maint_part(:,:,:) &
1778         & + resp_maint_part_radia(:,:,:)
1779   
1780    !! 4.4 Litter dynamics and litter heterothropic respiration
1781    ! Including: litter update, lignin content, PFT parts, litter decay,
1782    ! litter heterotrophic respiration, dead leaf soil cover.
1783    ! Note: there is no vertical discretisation in the soil for litter decay.
1784        resp_hetero_litter(:,:)=zero
1785        resp_hetero_flood(:,:)=zero
1786        resp_hetero_soil(:,:)=zero
1787        resp_flood_soil(:,:)=zero
1788        soilcarbon_input_inst(:,:,:,:,:)=zero
1789        floodcarbon_input_inst(:,:,:,:)=zero
1790       
1791    !WRITE(numout,*) 'STOMATE_ZHC3'
1792        !WRITE(numout,*) 'litter_above: ', MAXVAL(litter_above(:,:,:,icarbon)),MINVAL(litter_above(:,:,:,icarbon))
1793        !WRITE(numout,*) 'litter_below: ', MAXVAL(litter_below(:,:,:,:,icarbon)),MINVAL(litter_below(:,:,:,:,icarbon))
1794        !WRITE(numout,*) 'lignin_be',MAXVAL(lignin_struc_below)
1795        !WRITE(numout,*) 'SOC_max',MAXVAL(carbon),MAXVAL(DOC),MAXVAL(DOC_to_topsoil)
1796        !WRITE(numout,*) 'SOC_min',MINVAL(carbon),MINVAL(DOC),MINVAL(DOC_to_topsoil)   
1797        !WRITE(numout,*) 'SOCinp_min',MAXVAL(soilcarbon_input_inst),MINVAL(soilcarbon_input_inst), &
1798        !                               MAXVAL(floodcarbon_input_inst),MINVAL(floodcarbon_input_inst)
1799        !WRITE(numout,*) 'RH_min',MINVAL(resp_hetero_soil(:,:)),MINVAL(resp_hetero_litter(:,:)), &
1800        !                MINVAL(resp_hetero_flood(:,:)),MINVAL(resp_flood_soil(:,:))
1801        !WRITE(numout,*) 'RH_max',MAXVAL(resp_hetero_soil(:,:)),MAXVAL(resp_hetero_litter(:,:)), &
1802        !                MAXVAL(resp_hetero_flood(:,:)),MAXVAL(resp_flood_soil(:,:)), &
1803        !                               MAXVAL(control_moist_above_inst),MAXVAL(control_moist_soil_inst)
1804                                       
1805    !DO ig = 1,kjpindex
1806        !   DO m=1,nvm
1807        !         IF (resp_hetero_litter(ig,m).LT.zero .OR. resp_hetero_flood(ig,m).LT.zero &
1808        !            .OR. resp_hetero_soil(ig,m).LT.zero .OR. resp_flood_soil(ig,m).LT.zero) THEN
1809        !            WRITE(numout,*) 'Stomate_HetResp0',ig,m,resp_hetero_litter(ig,m),resp_hetero_flood(ig,m), &
1810        !                          & resp_hetero_soil(ig,m),resp_flood_soil(ig,m),resp_hetero_radia(ig,m)
1811        !          ENDIF
1812        !       ENDDO
1813    !ENDDO
1814           
1815        !DO ig = 1,kjpindex
1816        !   DO m=1,nvm
1817        !         IF (litter_above(ig,2,m,1).GT.1.0E+10 .OR.litter_above(ig,2,m,1).LT.0.0 .OR. ISNAN(litter_above(ig,2,m,1))) THEN
1818        !            WRITE(numout,*) 'Stomate_str1',ig,m,litter_above(ig,2,m,1),SUM(turnover_daily(ig,m,:,1)),SUM(bm_to_litter(ig,m,:,1))
1819        !         ENDIF
1820        !         IF (litter_above(ig,1,m,1).GT.1.0E+10 .OR.litter_above(ig,1,m,1).LT.0.0 .OR. ISNAN(litter_above(ig,1,m,1))) THEN
1821        !            WRITE(numout,*) 'Stomate_met1',ig,m,litter_above(ig,1,m,1),SUM(turnover_daily(ig,m,:,1)),SUM(bm_to_litter(ig,m,:,1))
1822        !         ENDIF
1823    !   ENDDO   
1824        !ENDDO
1825                                       
1826    turnover_littercalc(:,:,:,:) = turnover_daily(:,:,:,:) * dt_sechiba/one_day
1827    bm_to_littercalc(:,:,:,:)    = bm_to_litter(:,:,:,:) * dt_sechiba/one_day
1828       
1829    CALL littercalc (kjpindex, dt_sechiba/one_day, &
1830         turnover_littercalc, bm_to_littercalc, Cinp_manure_solid, &
1831         veget_cov_max, temp_sol, stempdiag, shumdiag, litterhumdiag, rprof, &
1832         litterpart, litter_above, litter_below, dead_leaves, &
1833         lignin_struc_above, lignin_struc_below, &
1834         deadleaf_cover, resp_hetero_litter, resp_hetero_flood,&
1835         control_temp_above_inst, control_temp_soil_inst, &
1836         control_moist_above_inst, control_moist_soil_inst, &
1837         litter_mc,soilcarbon_input_inst, floodcarbon_input_inst, soil_mc, soiltile, &
1838         clay, bulk_dens, soil_ph, poor_soils, carbon, flood_frac)               
1839        !WRITE(numout,*) 'STOMATE_ZHC4'
1840        !WRITE(numout,*) 'litter_above: ', MAXVAL(litter_above(:,:,:,icarbon)),MINVAL(litter_above(:,:,:,icarbon))
1841        !WRITE(numout,*) 'litter_below: ', MAXVAL(litter_below(:,:,:,:,icarbon)),MINVAL(litter_below(:,:,:,:,icarbon))
1842        !WRITE(numout,*) 'lignin_be',MAXVAL(lignin_struc_below)
1843        !WRITE(numout,*) 'SOC_max',MAXVAL(carbon),MAXVAL(DOC),MAXVAL(DOC_to_topsoil)
1844        !WRITE(numout,*) 'SOC_min',MINVAL(carbon),MINVAL(DOC),MINVAL(DOC_to_topsoil)   
1845        !WRITE(numout,*) 'SOCinp_min',MAXVAL(soilcarbon_input_inst),MINVAL(soilcarbon_input_inst), &
1846        !                               MAXVAL(floodcarbon_input_inst),MINVAL(floodcarbon_input_inst)
1847        !WRITE(numout,*) 'RH_min',MINVAL(resp_hetero_soil(:,:)),MINVAL(resp_hetero_litter(:,:)), &
1848        !                MINVAL(resp_hetero_flood(:,:)),MINVAL(resp_flood_soil(:,:))
1849        !WRITE(numout,*) 'RH_max',MAXVAL(resp_hetero_soil(:,:)),MAXVAL(resp_hetero_litter(:,:)), &
1850        !                MAXVAL(resp_hetero_flood(:,:)),MAXVAL(resp_flood_soil(:,:))
1851        !WRITE(numout,*) 'Cinput',MAXVAL(soilcarbon_input_inst),MAXVAL(floodcarbon_input_inst), &
1852        !                MAXVAL(control_temp_above_inst),MAXVAL(control_moist_soil_inst), &
1853        !                               MAXVAL(control_moist_above_inst),MAXVAL(control_moist_soil_inst)
1854    ! Heterothropic litter respiration during time step ::dt_sechiba @tex $(gC m^{-2})$ @endtex
1855    resp_hetero_litter(:,:) = resp_hetero_litter(:,:) * dt_sechiba/one_day
1856    resp_hetero_flood(:,:) = resp_hetero_flood(:,:) * dt_sechiba/one_day
1857 
1858    !! 4.5 Soil carbon dynamics and soil heterotrophic respiration
1859    ! Note: there is no vertical discretisation in the soil for litter decay.
1860!    CALL soilcarbon (kjpindex, clay, &
1861!         soilcarbon_input_inst, control_temp_inst, control_moist_inst, veget_cov_max, &
1862!         carbon, resp_hetero_soil, matrixA)
1863
1864    CALL soilcarbon (kjpindex, dt_sechiba/one_day, clay, &
1865         soilcarbon_input_inst, floodcarbon_input_inst, control_temp_soil_inst, control_moist_soil_inst, &
1866         carbon, resp_hetero_soil, resp_flood_soil, litter_above,litter_below,&
1867         shumdiag,DOC, moist_soil_inst, DOC_EXP, lignin_struc_above, &
1868         lignin_struc_below, floodout, runoff_per_soil, drainage_per_soil, wat_flux0,&
1869         wat_flux,bulk_dens,soil_ph, poor_soils, veget_cov_max, soil_mc, soiltile,&
1870         Cinp_manure_liquid, DOC_to_topsoil, DOC_to_subsoil, flood_frac, &
1871         precip2ground, precip2canopy, canopy2ground, &
1872         dry_dep_canopy, DOC_precip2ground, DOC_precip2canopy, DOC_canopy2ground, &
1873         DOC_infil, DOC_noinfil, interception_storage, biomass, fastr)
1874                                       
1875        !WRITE(numout,*) 'STOMATE_ZHC5'
1876        !WRITE(numout,*) 'litter_above: ', MAXVAL(litter_above(:,:,:,icarbon)),MINVAL(litter_above(:,:,:,icarbon))
1877        !WRITE(numout,*) 'litter_below: ', MAXVAL(litter_below(:,:,:,:,icarbon)),MINVAL(litter_below(:,:,:,:,icarbon))
1878        !WRITE(numout,*) 'lignin_be',MAXVAL(lignin_struc_below)
1879        !WRITE(numout,*) 'SOC_max',MAXVAL(carbon),MAXVAL(DOC),MAXVAL(DOC_to_topsoil)
1880        !WRITE(numout,*) 'SOC_min',MINVAL(carbon),MINVAL(DOC),MINVAL(DOC_to_topsoil)   
1881        !WRITE(numout,*) 'SOCinp_min',MAXVAL(soilcarbon_input_inst),MINVAL(soilcarbon_input_inst), &
1882        !                               MAXVAL(floodcarbon_input_inst),MINVAL(floodcarbon_input_inst)
1883    resp_hetero_soil(:,:) = resp_hetero_soil(:,:) * dt_sechiba/one_day
1884    resp_flood_soil(:,:) = resp_flood_soil(:,:) * dt_sechiba/one_day
1885
1886    ! Total heterothrophic respiration during time step ::dt_sechiba @tex $(gC m^{-2})$ @endtex
1887    resp_hetero_radia(:,:) = resp_hetero_litter(:,:) + resp_hetero_soil(:,:) &
1888         &                 + resp_hetero_flood(:,:) + resp_flood_soil(:,:)
1889
1890    ! Export of DOC during the time step ::dt_sechiba @tex $(gC m^{-3})$ @endtex
1891    !
1892    ! Accumulate DOC export per pixel and hydrological pathway for use as output variable
1893    ! Aggregate from DOC_EXP. To be used as input to routing.f90
1894        !DO ig = 1,kjpindex
1895        !   DO m=1,nvm
1896        !         IF (resp_hetero_d(ig,m).LT.zero .OR. tot_soil_resp_d(ig,m).LT.zero .OR.ISNAN(resp_hetero_d(ig,m))) THEN
1897        !            WRITE(numout,*) 'Stomate_HetResp2.1',ig,m,resp_hetero_d(ig,m),resp_hetero_radia(ig,m),tot_soil_resp_d(ig,m)
1898        !          ENDIF
1899        !       ENDDO
1900    !ENDDO
1901       
1902    DOC_EXP_b(:,:,:,:,:) = zero
1903    DOC_EXP_agg(:,:,:) = zero
1904    DO k=1,kjpindex
1905       DO m=2,nvm
1906           DO l=1, nexp
1907             DO i = 1,iact
1908                IF (.NOT. ISNAN(DOC_EXP(k,m,l,i,icarbon))) THEN
1909                   DOC_EXP_agg(k,l,idocl) = DOC_EXP_agg(k,l,idocl) + DOC_EXP(k,m,l,i,icarbon) * veget_max(k,m) * dt_sechiba/one_day
1910                   DOC_EXP_b(k,m,l,idocl,icarbon)=DOC_EXP_b(k,m,l,idocl,icarbon)+DOC_EXP(k,m,l,i,icarbon)*veget_max(k,m)
1911                ELSE
1912                   !Do nothing
1913                ENDIF
1914             ENDDO ! i = 1,iact
1915             DO i = islo,ipas
1916                IF (.NOT. ISNAN(DOC_EXP(k,m,l,i,icarbon))) THEN
1917                   DOC_EXP_agg(k,l,idocr) = DOC_EXP_agg(k,l,idocr) + DOC_EXP(k,m,l,i,icarbon) * veget_max(k,m) * dt_sechiba/one_day 
1918                   DOC_EXP_b(k,m,l,idocr,icarbon)=DOC_EXP_b(k,m,l,idocr,icarbon)+DOC_EXP(k,m,l,i,icarbon)*veget_max(k,m)
1919                ELSE
1920                   !Do nothing
1921                ENDIF
1922             ENDDO ! i = 1,iact
1923          ENDDO !l=1, nexp
1924          !
1925          IF (lat_CO2_fix) THEN
1926             soil_resp_modif = un
1927          ELSE !(lat_CO2_fix)
1928             IF ((un - flood_frac(k)) .GT. min_sechiba) THEN
1929                !! The varaiable soil_resp_modif is calculated based on all respiration in the soil rel. to a standard value of 4.25 g C/m2/day
1930                !! resp_hetero_litter and resp_hetero_soil are devied by the non-flooded fraction, because they only refer to the non-flooded fraction,
1931                !! but are reported relative to the whole cell area. resp_maint_part_radia(k,m,iroot), on the contrary, is the root respiration
1932                !! over the whole grid cell, as we do not represent reduced root respiration under flooded conditions, yet.
1933                soil_resp_modif = ((resp_hetero_litter(k,m) + resp_hetero_soil(k,m)) / (un - flood_frac(k)) &
1934                     + resp_maint_part_radia(k,m,iroot)) / (4.25 * dt_sechiba/one_day)
1935             ELSE !((un - flood_frac(k)) .GT. min_sechiba)
1936                soil_resp_modif = zero
1937             ENDIF !((un - flood_frac(k)) .GT. min_sechiba)
1938          ENDIF !(lat_CO2_fix)
1939          !
1940          DOC_EXP_agg(k,irunoff,iCO2aq) = DOC_EXP_agg(k,irunoff,iCO2aq) + runoff_per_soil(k,pref_soil_veg(m)) &
1941               &                        * 20e-4 * veget_max(k,m) * soil_resp_modif
1942          DOC_EXP_agg(k,idrainage,iCO2aq) = DOC_EXP_agg(k,idrainage,iCO2aq) + drainage_per_soil(k,pref_soil_veg(m)) &
1943               &                        * 20e-3 * veget_max(k,m) * soil_resp_modif
1944          DOC_EXP_agg(k,iflooded,iCO2aq) = DOC_EXP_agg(k,iflooded,iCO2aq) + (resp_hetero_flood(k,m)+resp_flood_soil(k,m) &
1945               &                         + flood_root_radia(k,m)) * veget_max(k,m)
1946                 
1947       ENDDO !m=2,13
1948    ENDDO !k=1,kjpindex         
1949    resp_hetero_d(:,:) = resp_hetero_d(:,:) + resp_hetero_radia(:,:)   
1950       
1951    !! 4.6 Accumulate instantaneous variables (do_slow=.FALSE.)
1952    ! Accumulate instantaneous variables (do_slow=.FALSE.) and eventually
1953    ! calculate daily mean value (do_slow=.TRUE.)
1954    !
1955    !! 4.6 Accumulate instantaneous variables (do_slow=.FALSE.)
1956    ! Accumulate instantaneous variables (do_slow=.FALSE.) and eventually
1957    ! calculate daily mean value (do_slow=.TRUE.)
1958    CALL stomate_accu (do_slow, control_moist_above_inst(:,:),control_moist_above_daily(:,:))
1959    CALL stomate_accu (do_slow, control_moist_soil_inst(:,:,:),control_moist_soil_daily(:,:,:))
1960    CALL stomate_accu (do_slow, moist_soil_inst, moist_soil_daily)
1961    CALL stomate_accu (do_slow, soil_mc, soil_mc_Cforcing_daily)
1962    CALL stomate_accu (do_slow, floodout, floodout_Cforcing_daily)
1963    CALL stomate_accu (do_slow, wat_flux0, wat_flux0_Cforcing_daily)
1964    CALL stomate_accu (do_slow, wat_flux, wat_flux_Cforcing_daily)
1965    CALL stomate_accu (do_slow, runoff_per_soil, runoff_per_soil_Cforcing_daily)
1966    CALL stomate_accu (do_slow, drainage_per_soil, drainage_per_soil_Cforcing_daily)
1967    CALL stomate_accu (do_slow, DOC_to_topsoil, DOC_to_topsoil_Cforcing_daily)
1968    CALL stomate_accu (do_slow, DOC_to_subsoil, DOC_to_subsoil_Cforcing_daily)
1969    CALL stomate_accu (do_slow, precip2ground, precip2ground_Cforcing_daily)
1970    CALL stomate_accu (do_slow, canopy2ground, canopy2ground_Cforcing_daily)
1971    CALL stomate_accu (do_slow, flood_frac, flood_frac_Cforcing_daily)
1972    CALL stomate_accu (do_slow, control_temp_above_inst, control_temp_above_daily)
1973    CALL stomate_accu (do_slow, control_temp_soil_inst, control_temp_soil_daily)
1974    DO j = 1,nslmd
1975       DO i = 1,npool
1976          DO k = 1, nelements
1977             CALL stomate_accu (do_slow, soilcarbon_input_inst(:,:,j,i,k), soilcarbon_input_daily(:,:,j,i,k))
1978          ENDDO
1979       ENDDO
1980    ENDDO
1981   
1982   !! 4.7 To accelerate the spin-up of SOC pool. Here we repeat the simulation of litter and SOC decomposition
1983   !!     For yrspin_acc years at the end of each year (Haicheng Zhang)
1984   IF (do_spinacc_hz) THEN
1985          DO i = 1,nspinacc
1986            !WRITE(numout,*) 'SUMstomate',i, SUM(litter_above),SUM(litter_below),SUM(carbon),SUM(DOC)
1987        CALL littercalc (kjpindex, dt_sechiba/one_day, &
1988           turnover_littercalc, bm_to_littercalc, Cinp_manure_solid, &
1989           veget_cov_max, temp_sol, stempdiag, shumdiag, litterhumdiag, rprof, &
1990           litterpart, litter_above, litter_below, dead_leaves, &
1991           lignin_struc_above, lignin_struc_below, &
1992           deadleaf_cover, resp_hetero_litter, resp_hetero_flood,&
1993           control_temp_above_inst, control_temp_soil_inst, &
1994           control_moist_above_inst, control_moist_soil_inst, &
1995           litter_mc,soilcarbon_input_inst, floodcarbon_input_inst, soil_mc, soiltile, &
1996           clay, bulk_dens, soil_ph, poor_soils, carbon, flood_frac)             
1997                 
1998            CALL soilcarbon (kjpindex, dt_sechiba/one_day, clay, &
1999           soilcarbon_input_inst, floodcarbon_input_inst, control_temp_soil_inst, control_moist_soil_inst, &
2000           carbon, resp_hetero_soil, resp_flood_soil, litter_above,litter_below,&
2001           shumdiag,DOC, moist_soil_inst, DOC_EXP, lignin_struc_above, &
2002           lignin_struc_below, floodout, runoff_per_soil, drainage_per_soil, wat_flux0,&
2003           wat_flux,bulk_dens,soil_ph, poor_soils, veget_cov_max, soil_mc, soiltile,&
2004           Cinp_manure_liquid, DOC_to_topsoil, DOC_to_subsoil, flood_frac, &
2005           precip2ground, precip2canopy, canopy2ground, &
2006           dry_dep_canopy, DOC_precip2ground, DOC_precip2canopy, DOC_canopy2ground, &
2007           DOC_infil, DOC_noinfil, interception_storage, biomass, fastr)
2008                   
2009          ENDDO ! DO i = 1,nspinacc
2010   ENDIF !IF (do_spinacc_hz) THEN
2011!! 5. Daily processes - performed at the end of the day
2012   
2013    IF (do_slow) THEN
2014
2015       !! 5.1 Update lai
2016       ! Use lai from stomate
2017       ! ?? check if this is the only time ok_pheno is used??
2018       ! ?? Looks like it is the only time. But this variables probably is defined
2019       ! in stomate_constants or something, in which case, it is difficult to track.
2020       IF (ok_pheno) THEN
2021          !! 5.1.1 Update LAI
2022          ! Set lai of bare soil to zero
2023          lai(:,ibare_sechiba) = zero
2024          ! lai for all PFTs
2025          DO j = 2, nvm
2026             lai(:,j) = biomass(:,j,ileaf,icarbon)*sla(j)
2027          ENDDO
2028          frac_age(:,:,:) = leaf_frac(:,:,:)
2029       ELSE 
2030          ! 5.1.2 Use a prescribed lai
2031          ! WARNING: code in setlai is identical to the lines above
2032          ! Update subroutine if LAI has to be forced
2033          CALL  setlai(kjpindex,lai) 
2034          frac_age(:,:,:) = zero
2035       ENDIF
2036
2037       !! 5.2 Calculate long-term "meteorological" and biological parameters
2038       ! mainly in support of calculating phenology. If LastTsYear=.TRUE.
2039       ! annual values are update (i.e. xx_lastyear).
2040       CALL season &
2041            &          (kjpindex, dt_days, &
2042            &           veget_cov, veget_cov_max, &
2043            &           humrel_daily, t2m_daily, tsoil_daily, soilhum_daily, lalo, &
2044            &           precip_daily, npp_daily, biomass, &
2045            &           turnover_daily, gpp_daily, when_growthinit, &
2046            &           maxhumrel_lastyear, maxhumrel_thisyear, &
2047            &           minhumrel_lastyear, minhumrel_thisyear, &
2048            &           maxgppweek_lastyear, maxgppweek_thisyear, &
2049            &           gdd0_lastyear, gdd0_thisyear, &
2050            &           precip_lastyear, precip_thisyear, &
2051            &           lm_lastyearmax, lm_thisyearmax, &
2052            &           maxfpc_lastyear, maxfpc_thisyear, &
2053            &           humrel_month, humrel_week, t2m_longterm, tau_longterm, &
2054            &           t2m_month, t2m_week, tsoil_month, soilhum_month, &
2055            &           npp_longterm, turnover_longterm, gpp_week, &
2056            &           gdd_m5_dormance, gdd_midwinter, ncd_dormance, ngd_minus5, &
2057            &           time_hum_min, hum_min_dormance, gdd_init_date, &
2058            &           gdd_from_growthinit, herbivores, &
2059            &           Tseason, Tseason_length, Tseason_tmp, &
2060            &           Tmin_spring_time, t2m_min_daily, begin_leaves, onset_date)
2061       
2062       !! 5.3 Use all processes included in stomate
2063
2064       !! 5.3.1  Activate stomate processes
2065       ! Activate stomate processes (the complete list of processes depends
2066       ! on whether the DGVM is used or not). Processes include: climate constraints
2067       ! for PFTs, PFT dynamics, Phenology, Allocation, NPP (based on GPP and
2068       ! authothropic respiration), fire, mortality, vmax, assimilation temperatures,
2069       ! all turnover processes, light competition, sapling establishment, lai and
2070       ! land cover change.
2071            !WRITE(numout,*) 'STOMATE_ZHC6'
2072            !WRITE(numout,*) 'litter_above: ', MAXVAL(litter_above(:,:,:,icarbon)),MINVAL(litter_above(:,:,:,icarbon))
2073                !WRITE(numout,*) 'litter_below: ', MAXVAL(litter_below(:,:,:,:,icarbon)),MINVAL(litter_below(:,:,:,:,icarbon))
2074                !WRITE(numout,*) 'lignin_be',MAXVAL(lignin_struc_below)
2075                !WRITE(numout,*) 'SOC_max',MAXVAL(carbon),MAXVAL(DOC),MAXVAL(DOC_to_topsoil)
2076                !WRITE(numout,*) 'SOC_min',MINVAL(carbon),MINVAL(DOC),MINVAL(DOC_to_topsoil)
2077           
2078       CALL StomateLpj &
2079            &            (kjpindex, dt_days, &
2080            &             neighbours, resolution, &
2081            &             clay, herbivores, &
2082            &             tsurf_daily, tsoil_daily, t2m_daily, t2m_min_daily, &
2083            &             litterhum_daily, soilhum_daily, &
2084            &             maxhumrel_lastyear, minhumrel_lastyear, &
2085            &             gdd0_lastyear, precip_lastyear, &
2086            &             humrel_month, humrel_week, t2m_longterm, t2m_month, t2m_week, &
2087            &             tsoil_month, soilhum_month, &
2088            &             gdd_m5_dormance,  gdd_from_growthinit, gdd_midwinter, ncd_dormance, ngd_minus5, &
2089            &             turnover_longterm, gpp_daily, &
2090            &             time_hum_min, maxfpc_lastyear, resp_maint_part,&
2091            &             PFTpresent, age, fireindex, firelitter, &
2092            &             leaf_age, leaf_frac, biomass, ind, adapted, regenerate, &
2093            &             senescence, when_growthinit, litterpart, litter_above, litter_below,depth_deepsoil, &
2094            &             dead_leaves, carbon, DOC, DOC_EXP_b, lignin_struc_above,&
2095            &             veget_cov_max, veget_cov_max_new, woodharvest, fraclut, npp_longterm, lm_lastyearmax, &
2096            &             veget_lastlight, everywhere, need_adjacent, RIP_time, &
2097            &             lai, rprof,npp_daily, turnover_daily, turnover_time,&
2098            &             soilcarbon_input_inst, &
2099            &             co2_to_bm_dgvm, co2_fire, &
2100            &             resp_hetero_d, tot_soil_resp_d, resp_maint_d, resp_growth_d, &
2101            &             height, deadleaf_cover, vcmax, &
2102            &             bm_to_litter,&
2103            &             prod10, prod100, flux10, flux100, &
2104            &             convflux, cflux_prod10, cflux_prod100, &
2105            &             prod10_harvest, prod100_harvest, flux10_harvest, flux100_harvest, &
2106            &             convflux_harvest, cflux_prod10_harvest, cflux_prod100_harvest, woodharvestpft, & 
2107            &             convfluxpft, fDeforestToProduct, fLulccResidue,fHarvestToProduct, &
2108            &             harvest_above, carb_mass_total, &
2109            &             fpc_max, matrixA, &
2110            &             Tseason, Tmin_spring_time, begin_leaves, onset_date, moist_soil)
2111       
2112       !! 5.3.2 Calculate the total CO2 flux from land use change
2113            !WRITE(numout,*) 'STOMATE_ZHC7'
2114                !WRITE(numout,*) 'litter_above: ', MAXVAL(litter_above(:,:,:,icarbon))
2115                !WRITE(numout,*) 'litter_below: ', MAXVAL(litter_below(:,:,:,:,icarbon))
2116                !WRITE(numout,*) 'lignin_be',MAXVAL(lignin_struc_below)
2117                !WRITE(numout,*) 'SOC_max',MAXVAL(carbon),MAXVAL(DOC),MAXVAL(DOC_to_topsoil)
2118                !WRITE(numout,*) 'SOC_min',MINVAL(carbon),MINVAL(DOC),MINVAL(DOC_to_topsoil)
2119               
2120       fco2_lu(:) = convflux(:) &
2121            &             + cflux_prod10(:)  &
2122            &             + cflux_prod100(:) &
2123            &             + harvest_above(:) &
2124            &             + convflux_harvest(:) &
2125            &             + cflux_prod10_harvest(:)  &
2126            &             + cflux_prod100_harvest(:)
2127       
2128       !! 5.4 Calculate veget and veget_max
2129       veget_max(:,:) = zero 
2130       DO j = 1, nvm
2131          veget_max(:,j) = veget_max(:,j) + &
2132               & veget_cov_max(:,j) * ( 1.-totfrac_nobio(:) )
2133       ENDDO
2134       
2135       !! 5.5 Photosynthesis parameters
2136       assim_param(:,:,ivcmax) = zero
2137       DO j = 2,nvm
2138          assim_param(:,j,ivcmax) = vcmax(:,j)
2139       ENDDO
2140       
2141       !! 5.6 Update forcing variables for soil carbon
2142       IF (TRIM(Cforcing_name) /= 'NONE') THEN
2143          npp_tot(:) = 0
2144          DO j=2,nvm
2145             npp_tot(:) = npp_tot(:) + npp_daily(:,j)
2146          ENDDO
2147          ! ::nbyear Number of years saved for carbon spinup
2148          sf_time = MODULO(REAL(days_since_beg,r_std)-1,one_year*REAL(nbyear,r_std))
2149          iatt=FLOOR(sf_time/dt_forcesoil) + 1
2150          IF (iatt == 0) iatt = iatt_old + 1
2151          IF ((iatt<iatt_old) .and. (.not. cumul_Cforcing)) THEN
2152             nforce(:)=0
2153                soilcarbon_input(:,:,:,:,:,:) = zero
2154                control_moist_above(:,:,:) = zero
2155                control_moist_soil(:,:,:,:) = zero
2156                moist_soil(:,:,:) = zero
2157                soil_mc_Cforcing(:,:,:,:) = zero
2158                floodout_Cforcing(:,:) = zero
2159                wat_flux0_Cforcing(:,:,:) = zero
2160                wat_flux_Cforcing(:,:,:,:) = zero
2161                runoff_per_soil_Cforcing(:,:,:) = zero
2162                drainage_per_soil_Cforcing(:,:,:) = zero
2163                DOC_to_topsoil_Cforcing(:,:,:) = zero
2164                DOC_to_subsoil_Cforcing(:,:,:) = zero
2165                precip2canopy_Cforcing(:,:,:) = zero
2166                precip2ground_Cforcing(:,:,:) = zero
2167                canopy2ground_Cforcing(:,:,:) = zero 
2168                flood_frac_Cforcing(:,:) = zero
2169                control_temp_above(:,:,:) = zero
2170                control_temp_soil(:,:,:,:) = zero
2171                litter_above_Cforcing(:,:,:,:,:) = zero
2172                litter_below_Cforcing(:,:,:,:,:,:) = zero
2173                npp_equil(:,:) = zero
2174                lignin_struc_above_Cforcing(:,:,:) = zero
2175                lignin_struc_below_Cforcing(:,:,:,:) = zero
2176          ENDIF
2177             iatt_old = iatt
2178             ! Update forcing
2179             nforce(iatt) = nforce(iatt)+1
2180             soilcarbon_input(:,:,:,:,:,iatt) = soilcarbon_input(:,:,:,:,:,iatt) + soilcarbon_input_daily(:,:,:,:,:)
2181             litter_above_Cforcing(:,:,:,:,iatt) = litter_above_Cforcing(:,:,:,:,iatt) + litter_above(:,:,:,:)
2182             litter_below_Cforcing(:,:,:,:,:,iatt) = litter_below_Cforcing(:,:,:,:,:,iatt) + litter_below(:,:,:,:,:)
2183             control_moist_above(:,:,iatt) = control_moist_above(:,:,iatt) + control_moist_above_daily(:,:)
2184             control_moist_soil(:,:,:,iatt) = control_moist_soil(:,:,:,iatt) + control_moist_soil_daily(:,:,:)
2185             moist_soil(:,:,iatt) = moist_soil(:,:,iatt) + moist_soil_daily(:,:)
2186             soil_mc_Cforcing(:,:,:,iatt) = soil_mc_Cforcing(:,:,:,iatt) + soil_mc_Cforcing_daily(:,:,:)
2187             floodout_Cforcing(:,iatt) = floodout_Cforcing(:,iatt) + floodout_Cforcing_daily(:)
2188             wat_flux0_Cforcing(:,:,iatt) = wat_flux0_Cforcing(:,:,iatt) + wat_flux0_Cforcing_daily(:,:)
2189             wat_flux_Cforcing(:,:,:,iatt) = wat_flux_Cforcing(:,:,:,iatt) + wat_flux_Cforcing_daily(:,:,:)
2190             runoff_per_soil_Cforcing(:,:,iatt) = runoff_per_soil_Cforcing(:,:,iatt) + runoff_per_soil_Cforcing_daily(:,:)
2191             drainage_per_soil_Cforcing(:,:,iatt) = drainage_per_soil_Cforcing(:,:,iatt) + drainage_per_soil_Cforcing_daily(:,:)
2192             DOC_to_topsoil_Cforcing(:,:,iatt) = DOC_to_topsoil_Cforcing(:,:,iatt) + DOC_to_topsoil_Cforcing_daily(:,:)
2193             DOC_to_subsoil_Cforcing(:,:,iatt) = DOC_to_subsoil_Cforcing(:,:,iatt) + DOC_to_subsoil_Cforcing_daily(:,:)
2194             precip2canopy_Cforcing(:,:,iatt) = precip2canopy_Cforcing(:,:,iatt) + precip2canopy_Cforcing_daily(:,:)
2195             precip2ground_Cforcing(:,:,iatt) = precip2ground_Cforcing(:,:,iatt) + precip2ground_Cforcing_daily(:,:)
2196             canopy2ground_Cforcing(:,:,iatt) = canopy2ground_Cforcing(:,:,iatt) + canopy2ground_Cforcing_daily(:,:)
2197             flood_frac_Cforcing(:,iatt) = flood_frac_Cforcing(:,iatt) + flood_frac_Cforcing_daily(:)
2198             control_temp_above(:,:,iatt) = control_temp_above(:,:,iatt) + control_temp_above_daily(:,:)
2199             control_temp_soil(:,:,:,iatt) = control_temp_soil(:,:,:,iatt) + control_temp_soil_daily(:,:,:)
2200             npp_equil(:,iatt) = npp_equil(:,iatt) + npp_tot(:)
2201             lignin_struc_above_Cforcing(:,:,iatt) = lignin_struc_above_Cforcing(:,:,iatt) + lignin_struc_above(:,:)
2202             lignin_struc_below_Cforcing(:,:,:,iatt) = lignin_struc_below_Cforcing(:,:,:,iatt) + lignin_struc_below(:,:,:)
2203       ENDIF
2204       
2205       !! 5.8 Write forcing file if ::ok_co2=.TRUE.
2206       ! Note: if STOMATE is run in coupled mode the forcing file is written
2207       ! If run in stand-alone mode, the forcing file is read!
2208       IF ( ok_co2 .AND. TRIM(forcing_name) /= 'NONE' ) THEN
2209         
2210          !! 5.8.1 Convert GPP to sechiba time steps
2211          ! GPP is multiplied by coverage to obtain forcing @tex $(gC m^{-2} dt_stomate^{-1})$\f \end@tex $(m^2 m^{-2})$ @endtexonly
2212          ! @tex$ m^{-2}$ @endtex remains in the units because ::veget_cov_max is a fraction, not a
2213          ! surface area. In sechiba values are ponderated by surface and frac_no_bio.
2214          ! At the beginning of stomate, the units are converted.
2215          ! When we use forcesoil we call sechiba_main and so we need the have the same units as in sechiba.
2216          gpp_daily_x(:,:) = zero
2217          DO j = 2, nvm             
2218             gpp_daily_x(:,j) = gpp_daily_x(:,j) + &
2219              & gpp_daily(:,j) * dt_stomate / one_day * veget_cov_max(:,j)
2220          ENDDO
2221         
2222          ! Bare soil moisture availability has not been treated
2223          ! in STOMATE, update it here
2224          humrel_daily(:,ibare_sechiba) = humrel(:,ibare_sechiba)   
2225
2226          ! Update index to store the next forcing step in memory
2227          iisf = iisf+1
2228
2229          ! How many times have we treated this forcing state
2230          xn = REAL(nf_cumul(isf(iisf)),r_std)
2231         
2232          !! 5.8.2 Cumulate forcing variables
2233          ! Cumulate forcing variables (calculate average)
2234          ! Note: precipitation is multiplied by dt_stomate/one_day to be consistent with
2235          ! the units in sechiba
2236          IF (cumul_forcing) THEN
2237             clay_fm(:,iisf) = (xn*clay_fm(:,iisf)+clay(:))/(xn+1.)
2238             soil_ph_fm(:,iisf) = (xn*soil_ph_fm(:,iisf)+soil_ph(:))/(xn+1.)
2239             poor_soils_fm(:,iisf) = (xn*poor_soils_fm(:,iisf)+poor_soils(:))/(xn+1.)
2240             bulk_dens_fm(:,iisf) = (xn*bulk_dens_fm(:,iisf)+bulk_dens(:))/(xn+1.)                       
2241             humrel_daily_fm(:,:,iisf) = &
2242                  & (xn*humrel_daily_fm(:,:,iisf) + humrel_daily(:,:))/(xn+1.)
2243             litterhum_daily_fm(:,iisf) = &
2244                  & (xn*litterhum_daily_fm(:,iisf)+litterhum_daily(:))/(xn+1.)
2245             t2m_daily_fm(:,iisf) = &
2246                  & (xn*t2m_daily_fm(:,iisf)+t2m_daily(:))/(xn+1.)
2247             t2m_min_daily_fm(:,iisf) = &
2248                  & (xn*t2m_min_daily_fm(:,iisf)+t2m_min_daily(:))/(xn+1.)
2249             tsurf_daily_fm(:,iisf) = &
2250                  & (xn*tsurf_daily_fm(:,iisf)+tsurf_daily(:))/(xn+1.)
2251             tsoil_daily_fm(:,:,iisf) = &
2252                  & (xn*tsoil_daily_fm(:,:,iisf)+tsoil_daily(:,:))/(xn+1.)
2253             soilhum_daily_fm(:,:,iisf) = &
2254                  & (xn*soilhum_daily_fm(:,:,iisf)+soilhum_daily(:,:))/(xn+1.)
2255             precip_fm(:,iisf) = &
2256                  & (xn*precip_fm(:,iisf)+precip_daily(:)*dt_stomate/one_day)/(xn+1.)
2257             gpp_daily_fm(:,:,iisf) = &
2258                  & (xn*gpp_daily_fm(:,:,iisf) + gpp_daily_x(:,:))/(xn+1.)
2259             veget_fm(:,:,iisf) = &
2260                  & (xn*veget_fm(:,:,iisf) + veget(:,:) )/(xn+1.)
2261             veget_max_fm(:,:,iisf) = &
2262                  & (xn*veget_max_fm(:,:,iisf) + veget_max(:,:) )/(xn+1.)
2263             lai_fm(:,:,iisf) = &
2264                  & (xn*lai_fm(:,:,iisf) + lai(:,:) )/(xn+1.)
2265          ELSE
2266             ! Here we just calculate the values
2267             clay_fm(:,iisf) = clay(:)
2268             soil_ph_fm(:,iisf) = soil_ph(:)
2269             poor_soils_fm(:,iisf) = poor_soils(:)
2270             bulk_dens_fm(:,iisf) = bulk_dens(:)                         
2271             humrel_daily_fm(:,:,iisf) = humrel_daily(:,:)
2272             litterhum_daily_fm(:,iisf) = litterhum_daily(:)
2273             t2m_daily_fm(:,iisf) = t2m_daily(:)
2274             t2m_min_daily_fm(:,iisf) =t2m_min_daily(:)
2275             tsurf_daily_fm(:,iisf) = tsurf_daily(:)
2276             tsoil_daily_fm(:,:,iisf) =tsoil_daily(:,:)
2277             soilhum_daily_fm(:,:,iisf) =soilhum_daily(:,:)
2278             precip_fm(:,iisf) = precip_daily(:)
2279             gpp_daily_fm(:,:,iisf) =gpp_daily_x(:,:)
2280             veget_fm(:,:,iisf) = veget(:,:)
2281             veget_max_fm(:,:,iisf) =veget_max(:,:)
2282             lai_fm(:,:,iisf) =lai(:,:)
2283          ENDIF
2284          nf_cumul(isf(iisf)) = nf_cumul(isf(iisf))+1
2285
2286          ! 5.8.3 Do we have to write the forcing states?
2287          IF (iisf == nsfm) THEN
2288
2289             !! 5.8.3.1 Write these forcing states
2290             CALL forcing_write(forcing_id,1,nsfm)
2291             ! determine which forcing states must be read
2292             isf(1) = isf(nsfm)+1
2293             IF ( isf(1) > nsft ) isf(1) = 1
2294             DO iisf = 2, nsfm
2295                isf(iisf) = isf(iisf-1)+1
2296                IF (isf(iisf) > nsft)  isf(iisf) = 1
2297             ENDDO
2298
2299             ! Read forcing variables - for debug use only
2300             ! CALL forcing_read(forcing_id,nsfm)
2301             iisf = 0
2302
2303          ENDIF
2304
2305       ENDIF
2306
2307
2308       !! 5.9 Compute daily CO2 flux diagnostics
2309       ! CO2 flux in @tex $gC m^{-2} s^{-1}$ @endtex (positive from atmosphere to land) is sum of:
2310       !   (1) co2 taken up by photosyntyhesis + (2) co2 taken up in the DGVM to establish saplings
2311       ! - (3) plants maintenance respiration  - (4) plants growth respiration
2312       ! - (5) heterotrophic respiration from ground
2313       ! - (6) co2 emission from fire
2314       ! co2_to_bm is not added as it is already encounted in gpp
2315       nep_daily(:,:)= gpp_daily(:,:)       &
2316                     - resp_maint_d(:,:)  - resp_growth_d(:,:)   &
2317                     - resp_hetero_d(:,:) - co2_fire(:,:) 
2318
2319       CALL xios_orchidee_send_field("nep",SUM(nep_daily*veget_cov_max,dim=2)/1e3/one_day)
2320       CALL xios_orchidee_send_field("rhSoil",SUM(resp_hetero_soil*veget_cov_max,dim=2)/1e3)
2321       CALL xios_orchidee_send_field("rhLitter",SUM(resp_hetero_litter*veget_cov_max,dim=2)/1e3)
2322           CALL xios_orchidee_send_field("Manure_LittC",Cinp_manure_solid/dt_sechiba*one_day) ! g C m-2 day-1 PFT-1
2323           CALL xios_orchidee_send_field("Manure_DOC",Cinp_manure_liquid/dt_sechiba*one_day) ! g C m-2 day-1 PFT-1                                                         
2324       
2325
2326       IF ( hist_id_stom_IPCC > 0 ) THEN
2327          vartmp(:) = SUM(nep_daily*veget_cov_max,dim=2)/1e3/one_day*contfrac
2328          CALL histwrite_p (hist_id_stom_IPCC, "nep", itime, &
2329               vartmp, kjpindex, hori_index)
2330       ENDIF
2331
2332       ! Cumulate nep, harvest and land use change fluxes
2333       nep_monthly(:,:) = nep_monthly(:,:) + nep_daily(:,:)
2334       harvest_above_monthly(:) = harvest_above_monthly(:) + harvest_above(:)
2335       cflux_prod_monthly(:) = cflux_prod_monthly(:) + convflux(:) + & 
2336        & cflux_prod10(:) + cflux_prod100(:) + convflux_harvest(:) + & 
2337        & cflux_prod10_harvest(:) + cflux_prod100_harvest(:)
2338     
2339       !! 5.10 Compute monthly CO2 fluxes
2340       IF ( LastTsMonth ) THEN
2341          !! 5.10.1 Write history file for monthly fluxes
2342          CALL histwrite_p (hist_id_stomate, 'CO2FLUX', itime, &
2343               nep_monthly, kjpindex*nvm, horipft_index)
2344         
2345          ! Integrate nep_monthly over all grid-cells on local domain
2346          net_nep_monthly = zero
2347          DO ji=1,kjpindex
2348             DO j=2,nvm
2349                net_nep_monthly = net_nep_monthly + &
2350                     nep_monthly(ji,j)*resolution(ji,1)*resolution(ji,2)*contfrac(ji)*veget_cov_max(ji,j)
2351             ENDDO
2352          ENDDO
2353          ! Change unit from gC/m2 grid-cell into PgC/m2 grid-cell
2354          net_nep_monthly = net_nep_monthly*1e-15
2355
2356     
2357          !! 5.10.2 Cumulative fluxes of land use cover change, harvest and net biosphere production
2358          ! Parallel processing, gather the information from different processors. first argument is the
2359          ! local variable, the second argument is the global variable. bcast send it to all processors.
2360          net_cflux_prod_monthly_sum = &
2361              &  SUM(cflux_prod_monthly(:)*resolution(:,1)*resolution(:,2)*contfrac(:))*1e-15
2362          CALL reduce_sum(net_cflux_prod_monthly_sum,net_cflux_prod_monthly_tot)
2363          CALL bcast(net_cflux_prod_monthly_tot)
2364          net_harvest_above_monthly_sum = &
2365             &   SUM(harvest_above_monthly(:)*resolution(:,1)*resolution(:,2)*contfrac(:))*1e-15
2366          CALL reduce_sum(net_harvest_above_monthly_sum,net_harvest_above_monthly_tot)
2367          CALL bcast(net_harvest_above_monthly_tot)
2368          CALL reduce_sum(net_nep_monthly,net_nep_monthly_sum)
2369          CALL bcast(net_nep_monthly_sum)
2370          net_biosp_prod_monthly_tot =  net_cflux_prod_monthly_tot + net_harvest_above_monthly_tot - net_nep_monthly_sum
2371         
2372          WRITE(numout,9010) 'GLOBAL net_cflux_prod_monthly    (Peta gC/month)  = ',net_cflux_prod_monthly_tot
2373          WRITE(numout,9010) 'GLOBAL net_harvest_above_monthly (Peta gC/month)  = ',net_harvest_above_monthly_tot
2374          WRITE(numout,9010) 'GLOBAL net_nep_monthly           (Peta gC/month)  = ',net_nep_monthly_sum
2375          WRITE(numout,9010) 'GLOBAL net_biosp_prod_monthly    (Peta gC/month)  = ',net_biosp_prod_monthly_tot
2376
23779010  FORMAT(A52,F17.14)
2378
2379          ! Reset Monthly values
2380          nep_monthly(:,:) = zero
2381          harvest_above_monthly(:) = zero
2382          cflux_prod_monthly(:)    = zero
2383
2384       ENDIF ! Monthly processes - at the end of the month
2385       
2386       IF (spinup_analytic) THEN
2387          nbp_accu(:) = nbp_accu(:) + (SUM(nep_daily(:,:) * veget_max(:,:),dim=2) - (convflux(:) + cflux_prod10(:) + &
2388                    cflux_prod100(:)) - (convflux_harvest(:) + cflux_prod10_harvest(:) + &
2389                    cflux_prod100_harvest(:))  - harvest_above(:))/1e3 
2390       ENDIF
2391
2392       !! 5.11 Reset daily variables
2393       humrel_daily(:,:) = zero
2394       litterhum_daily(:) = zero
2395       t2m_daily(:) = zero
2396       t2m_min_daily(:) = large_value
2397       tsurf_daily(:) = zero
2398       tsoil_daily(:,:) = zero
2399       soilhum_daily(:,:) = zero
2400       precip_daily(:) = zero
2401       gpp_daily(:,:) = zero
2402       resp_maint_part(:,:,:) =zero
2403       resp_hetero_d = zero
2404       tot_soil_resp_d = zero     
2405       IF (printlev >= 3) THEN
2406          WRITE(numout,*) 'stomate_main: daily processes done'
2407       ENDIF
2408
2409    ENDIF  ! Daily processes - at the end of the day
2410   
2411  !! 6. Outputs from Stomate
2412
2413    ! co2_flux receives a value from STOMATE only if STOMATE is activated.
2414    ! Otherwise, the calling hydrological module must do this itself.
2415
2416    !! 6.1 Respiration and fluxes
2417    resp_maint(:,:) = resp_maint_radia(:,:)*veget_cov_max(:,:)
2418    resp_maint(:,ibare_sechiba) = zero
2419    resp_growth(:,:)= resp_growth_d(:,:)*veget_cov_max(:,:)*dt_sechiba/one_day
2420    co2_to_bm_radia(:,:)=co2_to_bm_dgvm(:,:)*veget_cov_max(:,:)*dt_sechiba/one_day
2421    resp_hetero(:,:) = resp_hetero_radia(:,:)*veget_cov_max(:,:)
2422   
2423    !! 6.2 Derived CO2 fluxes
2424    ! CO2 flux in gC m^{-2} s^{-1} (positive towards the atmosphere) is sum of:
2425    ! (1) heterotrophic respiration from ground + (2) maintenance respiration
2426    ! from the plants + (3) growth respiration from the plants + (4) co2
2427    ! emissions from fire - (5) co2 taken up in the DGVM to establish
2428    ! saplings - (6) co2 taken up by photosyntyhesis
2429    ! co2_to_bm is not included here as it is already encounted in the gpp
2430    co2_flux(:,:) = resp_hetero(:,:) + resp_maint(:,:) + resp_growth(:,:) &
2431         & + co2_fire(:,:)*veget_cov_max(:,:)*dt_sechiba/one_day &
2432         & - gpp(:,:)
2433   
2434    temp_growth(:)=t2m_month(:)-tp_00 
2435   
2436  ! !! 7. Analytical spinup
2437
2438    ! IF (spinup_analytic) THEN
2439
2440       ! !! 7.1. Update V and U at sechiba time step
2441       ! DO m = 2,nvm
2442          ! DO j = 1,kjpindex
2443             ! ! V <- A * V
2444             ! MatrixV(j,m,:,:) = MATMUL(matrixA(j,m,:,:),MatrixV(j,m,:,:))
2445             ! ! U <- A*U + B
2446             ! VectorU(j,m,:) = MATMUL(matrixA(j,m,:,:),VectorU(j,m,:)) + vectorB(j,m,:)
2447          ! ENDDO ! loop pixels
2448       ! ENDDO ! loop PFTS
2449
2450
2451       ! !! 7.2. What happened at the end of the year ?
2452       ! IF (LastTsYear) THEN
2453
2454          ! !
2455          ! ! 7.2.1 Increase the years counter every LastTsYear which is the last sechiba time step of each year
2456          ! !
2457          ! global_years = global_years + 1
2458
2459
2460          ! !
2461          ! ! 7.2.3 Is global_years is a multiple of the period time ?
2462          ! !
2463
2464          ! !
2465          ! ! 3.2.1 When global_years is a multiple of the spinup_period, we calculate :
2466          ! !       1) the mean nbp flux over the period. This value is restarted
2467          ! !       2) we solve the matrix system by Gauss Jordan method
2468          ! !       3) We test if a point is at equilibrium : if yes, we mark the point (ok_equilibrium array)
2469          ! !       4) Then we reset the matrix
2470          ! !       5) We erase the carbon_stock calculated by ORCHIDEE by the one found by the method
2471          ! IF( MOD(global_years, spinup_period) == 0 ) THEN
2472             ! WRITE(numout,*) 'Spinup analytic : Calculate if system is in equlibrium. global_years=',global_years
2473             ! ! The number total of days during the forcing period is given by :
2474             ! !    spinup_period*365 (we consider only the noleap calendar)
2475             ! nbp_flux(:) = nbp_accu(:) / ( spinup_period * 365.)
2476             ! ! Reset the values
2477             ! nbp_accu(:) = zero
2478
2479             ! carbon_stock(:,ibare_sechiba,:) = zero
2480             ! ! Prepare the matrix for the resolution
2481             ! ! Add a temporary matrix W which contains I-MatrixV
2482             ! ! we should take the opposite of matrixV and add the identitiy : we solve (I-MatrixV)*C = VectorU
2483             ! MatrixW(:,:,:,:) = moins_un * MatrixV(:,:,:,:)
2484             ! DO jv = 1,nbpools
2485                ! MatrixW(:,:,jv,jv) =  MatrixW(:,:,jv,jv) + un
2486             ! ENDDO
2487             ! carbon_stock(:,:,:) = VectorU(:,:,:)
2488
2489             ! !
2490             ! !  Solve the linear system
2491             ! !
2492             ! DO m = 2,nvm
2493                ! DO j = 1,kjpindex
2494                   ! ! the solution will be stored in VectorU : so it should be restarted before
2495                   ! ! loop over npts and nvm, so we solved npts*(nvm-1) (7,7) linear systems
2496                   ! CALL gauss_jordan_method(nbpools,MatrixW(j,m,:,:),carbon_stock(j,m,:))
2497                ! ENDDO ! loop pixels
2498             ! ENDDO ! loop PFTS
2499
2500             ! ! Reset temporary matrixW
2501             ! MatrixW(:,:,:,:) = zero
2502
2503
2504             ! previous_stock(:,:,:) = current_stock(:,:,:)
2505             ! current_stock(:,:,:) = carbon_stock(:,:,:) 
2506             ! ! The relative error is calculated over the passive carbon pool (sum over the pfts) over the pixel.
2507             ! CALL error_L1_passive(kjpindex,nvm, nbpools, current_stock, previous_stock, veget_max, &
2508                  ! &                eps_carbon, carbon_eq)   
2509
2510             ! !! ok_equilibrium is saved,
2511             ! WHERE( carbon_eq(:) .AND. .NOT.(ok_equilibrium(:)) )
2512                ! ok_equilibrium(:) = .TRUE. 
2513             ! ENDWHERE
2514
2515             ! ! Reset matrixV for the pixel to the identity matrix and vectorU to zero
2516             ! MatrixV(:,:,:,:) = zero
2517             ! VectorU(:,:,:) = zero
2518             ! DO jv = 1,nbpools
2519                ! MatrixV(:,:,jv,jv) = un
2520             ! END DO
2521             ! IF (printlev >= 2) WRITE(numout,*) 'Reset for matrixV and VectorU done'   
2522
2523             ! !! Write the values found in the standard outputs of ORCHIDEE
2524             ! litter(:,istructural,:,iabove,icarbon) = carbon_stock(:,:,istructural_above)
2525             ! litter(:,istructural,:,ibelow,icarbon) = carbon_stock(:,:,istructural_below)
2526             ! litter(:,imetabolic,:,iabove,icarbon) = carbon_stock(:,:,imetabolic_above)
2527             ! litter(:,imetabolic,:,ibelow,icarbon) = carbon_stock(:,:,imetabolic_below)
2528             ! carbon(:,iactive,:) = carbon_stock(:,:,iactive_pool)
2529             ! carbon(:,islow,:) = carbon_stock(:,:,islow_pool)
2530             ! carbon(:,ipassive,:) = carbon_stock(:,:,ipassive_pool)
2531
2532             ! ! Final step, test if all points at the local domain are at equilibrium
2533             ! ! The simulation can be stopped when all local domains have reached the equilibrium
2534             ! IF (printlev >=1) THEN
2535                ! IF (ALL(ok_equilibrium)) THEN
2536                   ! WRITE(numout,*) 'Spinup analytic : Equilibrium for carbon pools is reached for current local domain'
2537                ! ELSE
2538                   ! WRITE(numout,*) 'Spinup analytic : Equilibrium for carbon pools is not yet reached for current local domain'
2539                ! END IF
2540             ! END IF
2541          ! ENDIF ! ( MOD(global_years,spinup_period) == 0)
2542       ! ENDIF ! (LastTsYear)
2543
2544    ! ENDIF !(spinup_analytic)
2545   
2546    IF (printlev >= 4) WRITE(numout,*) 'Leaving stomate_main'
2547
2548  END SUBROUTINE stomate_main
2549
2550!! ================================================================================================================================
2551!! SUBROUTINE   : stomate_finalize
2552!!
2553!>\BRIEF        Write variables to restart file
2554!!
2555!! DESCRIPTION  : Write variables to restart file
2556!! RECENT CHANGE(S) : None
2557!!
2558!! MAIN OUTPUT VARIABLE(S):
2559!!
2560!! REFERENCES   :
2561!!
2562!! \n
2563!_ ================================================================================================================================
2564
2565  SUBROUTINE stomate_finalize (kjit, kjpindex, index, clay, soil_ph, poor_soils, bulk_dens, &
2566                               soiltile, veget_max, co2_to_bm_radia, assim_param, &
2567                                                           litter_above, litter_below, carbon, DOC, lignin_struc_above, &
2568                                                           lignin_struc_below, depth_deepsoil) 
2569
2570    IMPLICIT NONE
2571    !! 0. Variable and parameter declaration
2572    !! 0.1 Input variables
2573    INTEGER(i_std),INTENT(in)                       :: kjit              !! Time step number (unitless)
2574    INTEGER(i_std),INTENT(in)                       :: kjpindex          !! Domain size - terrestrial pixels only (unitless)
2575    INTEGER(i_std),DIMENSION(kjpindex),INTENT(in)   :: index             !! Indices of the terrestrial pixels only (unitless)
2576    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: clay              !! Clay fraction of soil (0-1, unitless)
2577    REAL(r_std),DIMENSION(kjpindex),INTENT(inout)   :: bulk_dens         !! Soil bulk density (g cm-3)
2578    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: soil_ph           !! Soil pH (0-14, pH unit)
2579    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: poor_soils        !! Fraction of poor soils (0-1)
2580    REAL(r_std),DIMENSION(kjpindex,nstm),INTENT(in) :: soiltile              !! Fraction of each soil tile (0-1, unitless)     
2581    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)  :: co2_to_bm_radia   !! virtual gpp flux between atmosphere and biosphere
2582    REAL(r_std),DIMENSION(kjpindex,nvm,npco2),INTENT(in) :: assim_param  !! min+max+opt temperatures (K) & vmax for photosynthesis 
2583    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)  :: veget_max         !! New "maximal" coverage fraction of a PFT (LAI ->
2584                                                                         !! infinity) on ground only if EndOfYear is
2585                                                                         !! activated (unitless)
2586        REAL(r_std),DIMENSION (kjpindex,nlitt,nvm,nelements), INTENT (in)        :: litter_above   !! Above ground metabolic and structural litter
2587                                                                                                   !! @tex $(gC m^{-2})$ @endtex
2588    REAL(r_std),DIMENSION (kjpindex,nlitt,nvm,nslmd,nelements), INTENT (in) :: litter_below   !! Below ground metabolic and structural litter
2589                                                                                               !! per ground area                                                                                                                                                                                          !! per ground area
2590                                                                                                                                                                           !! @tex $(gC m^{-2})$ @endtex
2591        REAL(r_std),DIMENSION (kjpindex,ncarb,nvm,nslmd), INTENT (in)            :: carbon         !! Soil carbon pools per ground area: active, slow, or
2592                                                                                               !! passive, @tex $(gC m^{-2})$ @endtex
2593        REAL(r_std), DIMENSION(kjpindex,nvm,nslmd,ndoc,npool,nelements), INTENT(in) :: DOC        !! Dissolved Organic Carbon in soil
2594                                                                                               !! The unit is given by m^2 of
2595                                                                                               !! ground @tex $(gC m{-2} of ground)$ @endtex
2596    REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: lignin_struc_above       !! Ratio Lignin content in structural litter,
2597                                                                                               !! above ground, (0-1, unitless)
2598        REAL(r_std), DIMENSION(kjpindex,nvm,nslmd), INTENT(in)        :: lignin_struc_below       !! Ratio Lignin content in structural litter,
2599                                                                                               !! below ground, (0-1, unitless)
2600    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)              :: depth_deepsoil           !! Depth of the soil layer deeper than 2 m.
2601                                                                                               !! When sediment deposition occuring, the original surface (0-2)
2602                                                                                                                                                                           !! soil DOC, and SOC will enther into this layer.                                                                                                                                                                                   
2603    !! 0.4 Local variables
2604    REAL(r_std)                                   :: dt_days_read             !! STOMATE time step read in restart file (days)
2605    INTEGER(i_std)                                :: l,k,ji, jv, i, j, m      !! indices   
2606    REAL(r_std),PARAMETER                         :: max_dt_days = 5.         !! Maximum STOMATE time step (days)
2607    REAL(r_std)                                   :: hist_days                !! Writing frequency for history file (days)
2608    REAL(r_std),DIMENSION(0:nslm)                 :: z_soil                   !! Variable to store depth of the different soil layers (m)
2609    REAL(r_std),DIMENSION(kjpindex)               :: cvegtot                  !! Total "vegetation" cover (unitless)
2610    REAL(r_std),DIMENSION(kjpindex)               :: precip                   !! Total liquid and solid precipitation 
2611                                                                              !! @tex $(??mm dt_stomate^{-1})$ @endtex
2612    REAL(r_std),DIMENSION(kjpindex,nvm)           :: gpp_d                    !! Gross primary productivity per ground area
2613                                                                              !! @tex $(??gC m^{-2} dt_stomate^{-1})$ @endtex 
2614    REAL(r_std),DIMENSION(kjpindex,nvm)           :: gpp_daily_x              !! "Daily" gpp for teststomate 
2615                                                                              !! @tex $(??gC m^{-2} dt_stomate^{-1})$ @endtex
2616    REAL(r_std),DIMENSION(kjpindex,nvm)           :: resp_hetero_litter       !! Litter heterotrophic respiration per ground area
2617                                                                              !! @tex $(gC m^{-2} day^{-1})$ @endtex 
2618                                                                              !! ??Same variable is also used to
2619                                                                              !! store heterotrophic respiration per ground area
2620                                                                              !! over ::dt_sechiba??
2621    REAL(r_std),DIMENSION(kjpindex,nvm)           :: resp_hetero_soil         !! soil heterotrophic respiration 
2622                                                                              !! @tex $(gC m^{-2} day^{-1})$ @endtex                                                                                                                                                     
2623    REAL(r_std),DIMENSION(kjpindex,nvm)           :: veget_cov                !! Fractional coverage: actually share of the pixel
2624                                                                              !! covered by a PFT (fraction of ground area),
2625                                                                              !! taking into account LAI ??(= grid scale fpc)??
2626    REAL(r_std),DIMENSION(kjpindex,nvm)           :: vcmax                    !! Maximum rate of carboxylation
2627                                                                              !! @tex $(\mumol m^{-2} s^{-1})$ @endtex
2628    INTEGER(i_std)                                :: ier                      !! Check errors in netcdf call (unitless)
2629    REAL(r_std)                                   :: sf_time                  !! Intermediate variable to calculate current time
2630                                                                              !! step
2631    INTEGER(i_std)                                :: max_totsize              !! Memory management - maximum memory size (Mb)
2632    INTEGER(i_std)                                :: totsize_1step            !! Memory management - memory required to store one
2633                                                                              !! time step on one processor (Mb)
2634    INTEGER(i_std)                                :: totsize_tmp              !! Memory management - memory required to store one
2635                                                                              !! time step on all processors(Mb)
2636    REAL(r_std)                                   :: xn                       !! How many times have we treated in this forcing
2637    REAL(r_std), DIMENSION(kjpindex)              :: vartmp                   !! Temporary variable
2638    INTEGER(i_std)                                :: vid                      !! Variable identifer of netCDF (unitless)
2639    INTEGER(i_std)                                :: nneigh                   !! Number of neighbouring pixels
2640    INTEGER(i_std)                                :: direct                   !! ??
2641    INTEGER(i_std),DIMENSION(ndm)                 :: d_id                     !! ??
2642    REAL(r_std),DIMENSION(nbp_glo)                :: clay_g                   !! Clay fraction of soil (0-1, unitless), parallel
2643                                                                              !! computing
2644    REAL(r_std),DIMENSION(nbp_glo)                :: bulk_dens_g              !! Soil bulk density (g cm-3),  parallel
2645                                                                              !!
2646                                                                              !computing
2647    REAL(r_std),DIMENSION(nbp_glo)                :: soil_ph_g                !! pH of soil (0-14, pH unit), parallel
2648                                                                              !! computing
2649    REAL(r_std),DIMENSION(nbp_glo)                :: poor_soils_g             !! Fraction of poor soils (0-1), parallel
2650                                                                              !! computing
2651    REAL(r_std),DIMENSION(nbp_glo,nstm)           :: soiltile_g              !! soil type, parallel computing
2652    REAL(r_std),DIMENSION(nbp_glo,nvm)            :: veget_max_g              !! Maximum fraction of vegetation type including
2653                                                                              !! non-biological fraction (unitless),paralelle computing
2654
2655    REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:,:,:,:):: soilcarbon_input_g     !! Quantity of carbon going into DOC pools from
2656                                                                              !! litter decomposition 
2657                                                                              !! @tex $(gC m^{-2} dt_sechiba^{-1})$ @endtex, parallel
2658                                                                              !! computing
2659    REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)      :: control_moist_above_g    !! Moisture control of heterotrophic respiration 
2660                                                                              !! (0-1, unitless), parallel computing
2661    REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:,:)    :: control_moist_soil_g     !! Moisture control of heterotrophic respiration
2662                                                                              !! (0-1, unitless), parallel computing
2663    REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)      :: moist_soil_g             !! Soil moiture (m3 H20 m-3 Soil)
2664    REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:,:)    :: soil_mc_Cforcing_g       !! Soil moiture per soil type (m3 H20 m-3 Soil)
2665    REAL(r_std),ALLOCATABLE,DIMENSION(:,:)        :: floodout_Cforcing_g      !! flux out of floodplains
2666    REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)      :: wat_flux0_Cforcing_g     !! Water flux in the first soil layers exported for soil C calculations
2667    REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:,:)    :: wat_flux_Cforcing_g     !! Water flux in the soil layers exported for soil C calculations
2668    REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)      ::runoff_per_soil_Cforcing_g   !! Runoff per soil type [mm]
2669    REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)      ::drainage_per_soil_Cforcing_g !! Drainage per soil type [mm]
2670    REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)      :: DOC_to_topsoil_Cforcing_g           !! DOC inputs to top of the soil column, from reinfiltration on
2671                                                                              !! floodplains and from irrigation
2672                                                                              !! @tex $(gC m^{-2} day{-1})$ @endtex
2673    REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)      :: DOC_to_subsoil_Cforcing_g           !! DOC inputs to bottom of the soil column, from returnflow
2674                                                                              !! in swamps and lakes
2675                                                                              !! @tex $(gC m^{-2} day{-1})$ @endtex
2676    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:) :: precip2canopy_Cforcing_g !! Precipitation onto the canopy
2677    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:) :: precip2ground_Cforcing_g !! Precipitation not intercepted by canopy
2678    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:) :: canopy2ground_Cforcing_g !! Water flux from canopy to the ground
2679    REAL(r_std),ALLOCATABLE,DIMENSION(:,:)        :: flood_frac_Cforcing_g    !! flooded fraction of the grid box (1)
2680    REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)      :: control_temp_above_g     !! Temperature control of heterotrophic respiration
2681                                                                              !! (0-1, unitless), parallel computing
2682    REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:,:)    :: control_temp_soil_g      !! Temperature control of heterotrophic respiration
2683                                                                              !! (0-1, unitless), parallel computing
2684    REAL(r_std),ALLOCATABLE,DIMENSION(:,:)        :: npp_equil_g              !! Equilibrium NPP written to forcesoil
2685                                                                              !! @tex $(gC m^{-2} year^{-1})$ @endtex, parallel
2686                                                                              !! computing
2687   REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:,:,:) :: litter_above_g        !! Above ground metabolic and structural litter
2688                                                                              !! per ground area
2689                                                                              !! @tex $(gC m^{-2})$ @endtex, parallel
2690                                                                              !! computing
2691
2692   REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:,:,:,:):: litter_below_g       !! Below ground metabolic and structural litter
2693                                                                              !! per ground area
2694                                                                              !! @tex $(gC m^{-2})$ @endtex, parallel
2695                                                                              !! computing
2696  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)    :: lignin_struc_above_g    !! Ratio Lignine/Carbon in structural litter for above
2697                                                                              !! ground compartments (unitless), parallel
2698                                                                              !! computing
2699  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:,:)  :: lignin_struc_below_g    !! Ratio Lignine/Carbon in structural litter for below
2700                                                                              !! ground compartments (unitless), parallel
2701 
2702
2703    REAL(r_std)                                   :: net_cflux_prod_monthly_sum    !! AR5 output?? gC m2 month-1 (one variable for
2704                                                                                   !! reduce_sum and one for bcast??), parallel
2705                                                                                   !! computing
2706    REAL(r_std)                                   :: net_cflux_prod_monthly_tot    !! AR5 output?? gC m2 month-1 (one variable for
2707                                                                                   !! reduce_sum and one for bcast??), parallel
2708                                                                                   !! computing
2709    REAL(r_std)                                   :: net_harvest_above_monthly_sum !! AR5 output?? gC m2 month-1 (one variable for
2710                                                                                   !! reduce_sum and one for bcast??), parallel
2711                                                                                   !! computing
2712    REAL(r_std)                                   :: net_harvest_above_monthly_tot !! AR5 output?? gC m2 month-1 (one variable for
2713                                                                                   !! reduce_sum and one for bcast??), parallel
2714                                                                                   !! computing
2715    REAL(r_std)                                   :: net_biosp_prod_monthly_sum    !! AR5 output?? gC m2 month-1 (one variable for
2716                                                                                   !! reduce_sum and one for bcast??), parallel
2717                                                                                   !! computing
2718    REAL(r_std)                                   :: net_biosp_prod_monthly_tot    !! AR5 output?? gC m2 month-1 (one variable for
2719                                                                                   !! reduce_sum and one for bcast??), parallel
2720                                                                                   !! computing
2721    REAL(r_std), DIMENSION(kjpindex,nvm,nbpools)  :: carbon_stock                  !! Array containing the carbon stock for each pool
2722                                                                                   !! used by ORCHIDEE
2723
2724!_ ================================================================================================================================
2725   
2726    !! 1. Write restart file for stomate
2727    IF (printlev>=3) WRITE (numout,*) 'Write restart file for STOMATE'
2728       
2729    CALL writerestart &
2730         (kjpindex, index, &
2731         dt_days, days_since_beg, &
2732         ind, adapted, regenerate, &
2733         humrel_daily, gdd_init_date, litterhum_daily, &
2734         t2m_daily, t2m_min_daily, tsurf_daily, tsoil_daily, &
2735         soilhum_daily, precip_daily, &
2736         gpp_daily, npp_daily, turnover_daily, &
2737         humrel_month, humrel_week, &
2738         t2m_longterm, tau_longterm, t2m_month, t2m_week, &
2739         tsoil_month, soilhum_month, fireindex, firelitter, &
2740         maxhumrel_lastyear, maxhumrel_thisyear, &
2741         minhumrel_lastyear, minhumrel_thisyear, &
2742         maxgppweek_lastyear, maxgppweek_thisyear, &
2743         gdd0_lastyear, gdd0_thisyear, &
2744         precip_lastyear, precip_thisyear, &
2745         gdd_m5_dormance, gdd_from_growthinit, gdd_midwinter, ncd_dormance, ngd_minus5, &
2746         PFTpresent, npp_longterm, lm_lastyearmax, lm_thisyearmax, &
2747         maxfpc_lastyear, maxfpc_thisyear, &
2748         turnover_longterm, gpp_week, biomass, resp_maint_part, &
2749         leaf_age, leaf_frac, &
2750         senescence, when_growthinit, age, &
2751         resp_hetero_d, tot_soil_resp_d, resp_maint_d, resp_growth_d, co2_fire, co2_to_bm_dgvm, co2_to_bm_radia, &
2752         veget_lastlight, everywhere, need_adjacent, &
2753         RIP_time, &
2754         time_hum_min, hum_min_dormance, &
2755         litterpart, litter_above, litter_below, depth_deepsoil, dead_leaves, &
2756         carbon, DOC, lignin_struc_above, lignin_struc_below, turnover_time, &
2757         prod10,prod100,flux10, flux100, &
2758         convflux, cflux_prod10, cflux_prod100, &
2759         prod10_harvest,prod100_harvest,flux10_harvest, flux100_harvest, &
2760         convflux_harvest, cflux_prod10_harvest, cflux_prod100_harvest, &
2761         convfluxpft, fDeforestToProduct, fLulccResidue,fHarvestToProduct, &
2762         woodharvestpft, bm_to_litter, carb_mass_total, &
2763         Tseason, Tseason_length, Tseason_tmp, &
2764         Tmin_spring_time, begin_leaves, onset_date, &
2765         global_years, ok_equilibrium, nbp_accu, nbp_flux, &
2766         MatrixV, VectorU, previous_stock, current_stock, assim_param, interception_storage)
2767   
2768    !! 2. Write file with variables that force general processes in stomate
2769    IF (ok_co2 .AND. allow_forcing_write ) THEN
2770       IF ( TRIM(forcing_name) /= 'NONE' ) THEN 
2771          CALL forcing_write(forcing_id,1,iisf)
2772          ! Close forcing file
2773          IF (is_root_prc) ier = NF90_CLOSE (forcing_id)
2774          forcing_id=-1
2775       END IF
2776    END IF
2777   
2778    !! 3. Collect variables that force the soil processes in stomate
2779    IF (TRIM(Cforcing_name) /= 'NONE' ) THEN 
2780       
2781       !! Collet variables
2782       IF (printlev >= 1) WRITE(numout,*) 'stomate: writing the forcing file for carbon spinup'
2783       DO iatt = 1, nparan*nbyear
2784             IF ( nforce(iatt) > 0 ) THEN
2785                soilcarbon_input(:,:,:,:,:,iatt) = &
2786                     & soilcarbon_input(:,:,:,:,:,iatt)/REAL(nforce(iatt),r_std)
2787                litter_above_Cforcing(:,:,:,:,iatt) = &
2788                     & litter_above_Cforcing(:,:,:,:,iatt)/REAL(nforce(iatt),r_std)
2789                litter_below_Cforcing(:,:,:,:,:,iatt) = &
2790                     & litter_below_Cforcing(:,:,:,:,:,iatt)/REAL(nforce(iatt),r_std)
2791                control_moist_above(:,:,iatt) = &
2792                     & control_moist_above(:,:,iatt)/REAL(nforce(iatt),r_std)
2793                control_moist_soil(:,:,:,iatt) = &
2794                     & control_moist_soil(:,:,:,iatt)/REAL(nforce(iatt),r_std)
2795                moist_soil(:,:,iatt) = &
2796                     & moist_soil(:,:,iatt)/REAL(nforce(iatt),r_std)
2797                soil_mc_Cforcing(:,:,:,iatt) = &
2798                     & soil_mc_Cforcing(:,:,:,iatt)/REAL(nforce(iatt),r_std)
2799                floodout_Cforcing(:,iatt) = &
2800                     & floodout_Cforcing(:,iatt)/REAL(nforce(iatt),r_std)
2801                wat_flux0_Cforcing(:,:,iatt) = &
2802                     & wat_flux0_Cforcing(:,:,iatt)/REAL(nforce(iatt),r_std)
2803                wat_flux_Cforcing(:,:,:,iatt) = &
2804                     & wat_flux_Cforcing(:,:,:,iatt)/REAL(nforce(iatt),r_std)
2805                runoff_per_soil_Cforcing(:,:,iatt) = &
2806                     & runoff_per_soil_Cforcing(:,:,iatt)/REAL(nforce(iatt),r_std)
2807                drainage_per_soil_Cforcing(:,:,iatt) = &
2808                     & drainage_per_soil_Cforcing(:,:,iatt)/REAL(nforce(iatt),r_std)
2809                DOC_to_topsoil_Cforcing(:,:,iatt) = &
2810                     & DOC_to_topsoil_Cforcing(:,:,iatt)/REAL(nforce(iatt),r_std)
2811                DOC_to_subsoil_Cforcing(:,:,iatt) = &
2812                     & DOC_to_subsoil_Cforcing(:,:,iatt)/REAL(nforce(iatt),r_std)
2813                precip2canopy_Cforcing(:,:,iatt) = &
2814                     & precip2canopy_Cforcing(:,:,iatt)/REAL(nforce(iatt),r_std)
2815                precip2ground_Cforcing(:,:,iatt) = &
2816                     & precip2ground_Cforcing(:,:,iatt)/REAL(nforce(iatt),r_std)
2817                canopy2ground_Cforcing(:,:,iatt) = &
2818                     & canopy2ground_Cforcing(:,:,iatt)/REAL(nforce(iatt),r_std) 
2819                flood_frac_Cforcing(:,iatt) = &
2820                     & flood_frac_Cforcing(:,iatt)/REAL(nforce(iatt),r_std)
2821                control_temp_above(:,:,iatt) = &
2822                     & control_temp_above(:,:,iatt)/REAL(nforce(iatt),r_std)
2823                control_temp_soil(:,:,:,iatt) = &
2824                     & control_temp_soil(:,:,:,iatt)/REAL(nforce(iatt),r_std)
2825                npp_equil(:,iatt) = &
2826                     & npp_equil(:,iatt)/REAL(nforce(iatt),r_std)
2827                lignin_struc_above_Cforcing(:,:,iatt) = &
2828                     & lignin_struc_above_Cforcing(:,:,iatt)/REAL(nforce(iatt),r_std)
2829                lignin_struc_below_Cforcing(:,:,:,iatt) = &
2830                     & lignin_struc_below_Cforcing(:,:,:,iatt)/REAL(nforce(iatt),r_std)
2831             ELSE
2832                WRITE(numout,*) &
2833                     &         'We have no soil carbon forcing data for this time step:', &
2834                     &         iatt
2835                WRITE(numout,*) ' -> we set them to zero'
2836                soilcarbon_input(:,:,:,:,:,iatt) = zero
2837                litter_above_Cforcing(:,:,:,:,iatt) = zero
2838                litter_below_Cforcing(:,:,:,:,:,iatt) = zero
2839                control_moist_above(:,:,iatt) = zero
2840                control_moist_soil(:,:,:,iatt) = zero
2841                moist_soil(:,:,iatt) = zero
2842                soil_mc_Cforcing(:,:,:,iatt) = zero
2843                floodout_Cforcing(:,iatt) = zero
2844                wat_flux0_Cforcing(:,:,iatt) = zero
2845                wat_flux_Cforcing(:,:,:,iatt) = zero
2846                runoff_per_soil_Cforcing(:,:,iatt) = zero
2847                drainage_per_soil_Cforcing(:,:,iatt) = zero
2848                DOC_to_topsoil_Cforcing(:,:,iatt) = zero
2849                DOC_to_subsoil_Cforcing(:,:,iatt) = zero
2850                precip2canopy_Cforcing(:,:,iatt) = zero
2851                precip2ground_Cforcing(:,:,iatt) = zero
2852                canopy2ground_Cforcing(:,:,iatt) = zero   
2853                flood_frac_Cforcing(:,iatt) = zero
2854                control_temp_above(:,:,iatt) = zero
2855                control_temp_soil(:,:,:,iatt) = zero
2856                npp_equil(:,iatt) = zero
2857                lignin_struc_above_Cforcing(:,:,iatt) = zero
2858                lignin_struc_below_Cforcing(:,:,:,iatt) = zero
2859               ENDIF
2860       ENDDO
2861       
2862       ! Allocate memory for parallel computing
2863       IF (is_root_prc) THEN
2864             ALLOCATE(soilcarbon_input_g(nbp_glo,nvm,nslmd,npool,nelements,nparan*nbyear))
2865             ALLOCATE(control_moist_above_g(nbp_glo,nvm,nparan*nbyear))
2866             ALLOCATE(control_moist_soil_g(nbp_glo,nslmd,nvm,nparan*nbyear))
2867             ALLOCATE(moist_soil_g(nbp_glo,nslm,nparan*nbyear))
2868             ALLOCATE(soil_mc_Cforcing_g(nbp_glo,nslm,nstm,nparan*nbyear))
2869             ALLOCATE(floodout_Cforcing_g(nbp_glo,nparan*nbyear))
2870             ALLOCATE(wat_flux0_Cforcing_g(nbp_glo,nstm,nparan*nbyear))
2871             ALLOCATE(wat_flux_Cforcing_g(nbp_glo,nslm,nstm,nparan*nbyear))
2872             ALLOCATE(runoff_per_soil_Cforcing_g(nbp_glo,nstm,nparan*nbyear))
2873             ALLOCATE(drainage_per_soil_Cforcing_g(nbp_glo,nstm,nparan*nbyear))
2874             ALLOCATE(DOC_to_topsoil_Cforcing_g(nbp_glo,nflow,nparan*nbyear))
2875             ALLOCATE(DOC_to_subsoil_Cforcing_g(nbp_glo,nflow,nparan*nbyear))
2876             ALLOCATE(precip2canopy_Cforcing_g(kjpindex,nvm,nparan*nbyear))
2877             ALLOCATE(precip2ground_Cforcing_g(kjpindex,nvm,nparan*nbyear))
2878             ALLOCATE(canopy2ground_Cforcing_g(kjpindex,nvm,nparan*nbyear)) 
2879             ALLOCATE(flood_frac_Cforcing_g(nbp_glo,nparan*nbyear))
2880             ALLOCATE(control_temp_above_g(nbp_glo,nlitt,nparan*nbyear))
2881             ALLOCATE(control_temp_soil_g(nbp_glo,nslmd,npool*2,nparan*nbyear))
2882             ALLOCATE(npp_equil_g(nbp_glo,nparan*nbyear))
2883             ALLOCATE(litter_above_g(nbp_glo,nlitt,nvm,nelements,nparan*nbyear))
2884             ALLOCATE(litter_below_g(nbp_glo,nlitt,nvm,nslmd,nelements,nparan*nbyear))
2885             ALLOCATE(lignin_struc_above_g(nbp_glo,nvm,nparan*nbyear))
2886             ALLOCATE(lignin_struc_below_g(nbp_glo,nvm,nslmd,nparan*nbyear))
2887       ENDIF
2888       
2889       ! Gather distributed variables
2890          ! Gather distributed variables
2891          CALL gather(clay,clay_g)
2892          CALL gather(control_moist_above,control_moist_above_g)
2893          CALL gather(soil_ph,soil_ph_g)
2894          CALL gather(poor_soils,poor_soils_g)
2895          CALL gather(bulk_dens, bulk_dens_g)
2896          CALL gather(soiltile,soiltile_g)
2897          CALL gather(veget_max,veget_max_g)
2898          DO k= 1,nvm
2899             DO i =1,npool
2900                DO j=1,nslmd
2901                   CALL gather(soilcarbon_input(:,k,j,i,:,:),soilcarbon_input_g(:,k,j,i,:,:))
2902                ENDDO
2903             ENDDO
2904          ENDDO
2905          DO i =1,nlitt
2906             DO j=1,nvm
2907                CALL gather(litter_above_Cforcing(:,i,j,:,:),litter_above_g(:,i,j,:,:))
2908             ENDDO
2909          ENDDO
2910          DO i =1,nlitt
2911             DO j=1,nvm
2912                DO k = 1,nslmd
2913                            CALL gather(litter_below_Cforcing(:,i,j,k,:,:),litter_below_g(:,i,j,k,:,:))
2914                ENDDO
2915             ENDDO
2916          ENDDO
2917          CALL gather(control_moist_soil,control_moist_soil_g)
2918          CALL gather(moist_soil,moist_soil_g)
2919          CALL gather(soil_mc_Cforcing,soil_mc_Cforcing_g)
2920          CALL gather(floodout_Cforcing,floodout_Cforcing_g)
2921          CALL gather(wat_flux0_Cforcing,wat_flux0_Cforcing_g)
2922          DO j= 1, nslm
2923             DO i = 1, nstm
2924          CALL gather(wat_flux_Cforcing(:,j,i,:),wat_flux_Cforcing_g(:,j,i,:))
2925             ENDDO
2926          ENDDO
2927          CALL gather(runoff_per_soil_Cforcing,runoff_per_soil_Cforcing_g)
2928          CALL gather(drainage_per_soil_Cforcing,drainage_per_soil_Cforcing_g)
2929          CALL gather(DOC_to_topsoil_Cforcing,DOC_to_topsoil_Cforcing_g)
2930          CALL gather(DOC_to_subsoil_Cforcing,DOC_to_subsoil_Cforcing_g)
2931          CALL gather(precip2canopy_Cforcing,precip2canopy_Cforcing_g)
2932          CALL gather(precip2ground_Cforcing,precip2ground_Cforcing_g)
2933          CALL gather(canopy2ground_Cforcing,canopy2ground_Cforcing_g) 
2934          CALL gather(flood_frac_Cforcing,flood_frac_Cforcing_g)
2935          DO k = 1, nlitt
2936             CALL gather(control_temp_above(:,k,:),control_temp_above_g(:,k,:))
2937          ENDDO
2938          DO k = 1,2*npool
2939             CALL gather(control_temp_soil(:,:,k,:),control_temp_soil_g(:,:,k,:))
2940          ENDDO
2941          CALL gather(npp_equil,npp_equil_g)
2942          DO j=1,nvm
2943             DO k = 1,nslmd
2944                CALL gather(lignin_struc_below_Cforcing(:,j,k,:),lignin_struc_below_g(:,j,k,:))
2945             ENDDO
2946          ENDDO
2947          DO j=1,nvm
2948          CALL gather(lignin_struc_above_Cforcing(:,j,:),lignin_struc_above_g(:,j,:))
2949          ENDDO
2950       
2951       !! Create netcdf
2952       ! Create, define and populate a netcdf file containing the forcing data.
2953       ! For the root processor only (parallel computing). NF90_ are functions
2954       ! from and external library. 
2955       IF (is_root_prc) THEN
2956          IF (printlev>=2) WRITE (numout,*) 'Create Cforcing file : ',TRIM(Cforcing_name)
2957          ! Create new netCDF dataset
2958          ier = NF90_CREATE (TRIM(Cforcing_name),NF90_64BIT_OFFSET ,Cforcing_id)
2959          IF (ier /= NF90_NOERR) THEN
2960             WRITE (numout,*) 'Error in creating Cforcing file : ',TRIM(Cforcing_name)
2961             CALL ipslerr_p (3,'stomate_finalize', &
2962                  &        'PROBLEM creating Cforcing file', &
2963                  &        NF90_STRERROR(ier),'')
2964          END IF
2965         
2966             ! Add variable attribute
2967             ! Note ::nbp_glo is the number of global continental points
2968             ier = NF90_PUT_ATT (Cforcing_id,NF90_GLOBAL, &
2969                  &                        'kjpindex',REAL(nbp_glo,r_std))
2970             ier = NF90_PUT_ATT (Cforcing_id,NF90_GLOBAL, &
2971                  &                        'nparan',REAL(nparan,r_std))
2972             ier = NF90_PUT_ATT (Cforcing_id,NF90_GLOBAL, &
2973                  &                        'nbyear',REAL(nbyear,r_std))
2974         
2975             ! Add new dimension
2976             ier = NF90_DEF_DIM (Cforcing_id,'points',nbp_glo,d_id(1))
2977             ier = NF90_DEF_DIM (Cforcing_id,'carbtype',ncarb,d_id(2))
2978             ier = NF90_DEF_DIM (Cforcing_id,'vegtype',nvm,d_id(3))
2979             ier = NF90_DEF_DIM (Cforcing_id,'level',nlevs,d_id(4))
2980             ier = NF90_DEF_DIM (Cforcing_id,'time_step',NF90_UNLIMITED,d_id(5))
2981             ier = NF90_DEF_DIM (Cforcing_id,'solay',nslm,d_id(6))
2982             ier = NF90_DEF_DIM (Cforcing_id,'elements',nelements,d_id(7))
2983             ier = NF90_DEF_DIM (Cforcing_id,'littertype',nlitt,d_id(8))
2984             ier = NF90_DEF_DIM (Cforcing_id,'soiltype',nstm,d_id(9))
2985             ier = NF90_DEF_DIM (Cforcing_id,'pooltype',npool,d_id(10))
2986             ier = NF90_DEF_DIM (Cforcing_id,'dblepooltype',2*npool,d_id(11))
2987             ier = NF90_DEF_DIM (Cforcing_id,'flowingmatter',nflow,d_id(12))
2988             ier = NF90_DEF_DIM (Cforcing_id,'solaydeep',nslmd,d_id(13))                         
2989             ! Add new variable
2990             ier = NF90_DEF_VAR (Cforcing_id,'points',    r_typ,d_id(1),vid)
2991             ier = NF90_DEF_VAR (Cforcing_id,'carbtype',  r_typ,d_id(2),vid)
2992             ier = NF90_DEF_VAR (Cforcing_id,'vegtype',   r_typ,d_id(3),vid)
2993             ier = NF90_DEF_VAR (Cforcing_id,'level',     r_typ,d_id(4),vid)
2994             ier = NF90_DEF_VAR (Cforcing_id,'time_step', r_typ,d_id(5),vid)
2995             ier = NF90_DEF_VAR (Cforcing_id,'solay',     r_typ,d_id(6),vid)
2996             ier = NF90_DEF_VAR (Cforcing_id,'elements',  r_typ,d_id(7),vid)
2997             ier = NF90_DEF_VAR (Cforcing_id,'littertype',r_typ,d_id(8),vid)
2998             ier = NF90_DEF_VAR (Cforcing_id,'soiltype',  r_typ,d_id(9),vid)
2999             ier = NF90_DEF_VAR (Cforcing_id,'pooltype',  r_typ,d_id(10),vid)
3000             ier = NF90_DEF_VAR (Cforcing_id,'dblepooltype',  r_typ,d_id(11),vid)
3001                         ier = NF90_DEF_VAR (Cforcing_id,'flowingmatter', r_typ,d_id(12),vid)
3002                         ier = NF90_DEF_VAR (Cforcing_id,'solaydeep', r_typ,d_id(13),vid)
3003             ier = NF90_DEF_VAR (Cforcing_id,'index',     r_typ,d_id(1),vid)
3004             ier = NF90_DEF_VAR (Cforcing_id,'clay',      r_typ,d_id(1),vid)
3005             ier = NF90_DEF_VAR (Cforcing_id,'bulk_dens', r_typ,d_id(1),vid)
3006             ier = NF90_DEF_VAR (Cforcing_id,'soil_ph',   r_typ,d_id(1),vid)
3007             ier = NF90_DEF_VAR (Cforcing_id,'poor_soils',   r_typ,d_id(1),vid)
3008             ier = NF90_DEF_VAR (Cforcing_id,'soiltile', r_typ, &
3009                  &                        (/d_id(1),d_id(9) /),vid)
3010             ier = NF90_DEF_VAR (Cforcing_id,'veget_max', r_typ, &
3011                  &                        (/d_id(1),d_id(3) /),vid)
3012             ier = NF90_DEF_VAR (Cforcing_id,'soilcarbon_input',r_typ, &
3013                  &                        (/ d_id(1),d_id(3),d_id(13),d_id(10),d_id(7), d_id(5) /),vid)
3014             ier = NF90_DEF_VAR (Cforcing_id,'control_moist_above',r_typ, &
3015                  &                        (/ d_id(1),d_id(3),d_id(5) /),vid)
3016             ier = NF90_DEF_VAR (Cforcing_id,'control_moist_soil',r_typ, &
3017                  &                        (/ d_id(1),d_id(13),d_id(3),d_id(5) /),vid)
3018             ier = NF90_DEF_VAR (Cforcing_id,'moist_soil',r_typ, &
3019                  &                        (/ d_id(1),d_id(6),d_id(5) /),vid)
3020             ier = NF90_DEF_VAR (Cforcing_id,'soil_mc',r_typ, &
3021                  &                        (/ d_id(1),d_id(6),d_id(9),d_id(5) /),vid)
3022             ier = NF90_DEF_VAR (Cforcing_id,'floodout',r_typ, &
3023                  &                        (/ d_id(1),d_id(5) /),vid)
3024             ier = NF90_DEF_VAR (Cforcing_id,'wat_flux0',r_typ, &
3025                  &                        (/ d_id(1),d_id(9), d_id(5) /),vid)
3026             ier = NF90_DEF_VAR (Cforcing_id,'wat_flux',r_typ, &
3027                  &                        (/ d_id(1),d_id(6),d_id(9), d_id(5) /),vid)
3028             ier = NF90_DEF_VAR (Cforcing_id,'runoff_per_soil',r_typ, &
3029                  &                        (/ d_id(1),d_id(9), d_id(5) /),vid)
3030             ier = NF90_DEF_VAR (Cforcing_id,'drainage_per_soil',r_typ, &
3031                  &                        (/ d_id(1),d_id(9), d_id(5) /),vid)
3032             ier = NF90_DEF_VAR (Cforcing_id,'DOC_to_topsoil',r_typ, &
3033                  &                        (/ d_id(1),d_id(12), d_id(5) /),vid)
3034             ier = NF90_DEF_VAR (Cforcing_id,'DOC_to_subsoil',r_typ, &
3035                  &                        (/ d_id(1),d_id(12), d_id(5) /),vid)
3036             ier = NF90_DEF_VAR (Cforcing_id,'precip2canopy',r_typ, &
3037                  &                        (/ d_id(1),d_id(3), d_id(5) /),vid)
3038             ier = NF90_DEF_VAR (Cforcing_id,'precip2ground',r_typ, &
3039                  &                        (/ d_id(1),d_id(3), d_id(5) /),vid)
3040             ier = NF90_DEF_VAR (Cforcing_id,'canopy2ground',r_typ, &
3041                  &                        (/ d_id(1),d_id(3), d_id(5) /),vid) 
3042             ier = NF90_DEF_VAR (Cforcing_id,'flood_frac',r_typ, &
3043                  &                        (/ d_id(1), d_id(5) /),vid)
3044             ier = NF90_DEF_VAR (Cforcing_id,'control_temp_above',r_typ, &
3045                  &                        (/ d_id(1),d_id(8),d_id(5) /),vid)
3046             ier = NF90_DEF_VAR (Cforcing_id,'control_temp_soil',r_typ, &
3047                  &                        (/ d_id(1),d_id(13),d_id(11),d_id(5) /),vid)
3048             ier = NF90_DEF_VAR (Cforcing_id,'npp_equil',r_typ, &
3049                  &                        (/ d_id(1),d_id(5) /),vid)
3050             ier = NF90_DEF_VAR (Cforcing_id,'litter_above',r_typ, &
3051                  &                        (/ d_id(1),d_id(8),d_id(3),d_id(7), d_id(5) /),vid)
3052             ier = NF90_DEF_VAR (Cforcing_id,'litter_below',r_typ, &
3053                  &                        (/ d_id(1),d_id(8),d_id(3),d_id(13),d_id(7), d_id(5) /),vid)
3054             ier = NF90_DEF_VAR (Cforcing_id,'lignin_struc_below',r_typ, &
3055                  &                        (/ d_id(1),d_id(3),d_id(13), d_id(5) /),vid)
3056             ier = NF90_DEF_VAR (Cforcing_id,'lignin_struc_above',r_typ, &
3057                  &                        (/ d_id(1),d_id(3), d_id(5) /),vid)
3058             ier = NF90_ENDDEF (Cforcing_id)
3059             ! Given the name of a varaible, nf90_inq_varid finds the variable
3060             ier = NF90_INQ_VARID (Cforcing_id,'points',vid)
3061             ier = NF90_PUT_VAR (Cforcing_id,vid, &
3062                  &                          (/(REAL(i,r_std),i=1,nbp_glo)/))
3063             ier = NF90_INQ_VARID (Cforcing_id,'carbtype',vid)
3064             ier = NF90_PUT_VAR (Cforcing_id,vid, &
3065                  &                        (/(REAL(i,r_std),i=1,ncarb)/))
3066             ier = NF90_INQ_VARID (Cforcing_id,'vegtype',vid)
3067             ier = NF90_PUT_VAR (Cforcing_id,vid, &
3068                  &                            (/(REAL(i,r_std),i=1,nvm)/))
3069             ier = NF90_INQ_VARID (Cforcing_id,'level',vid)
3070             ier = NF90_PUT_VAR (Cforcing_id,vid, &
3071                  &                          (/(REAL(i,r_std),i=1,nlevs)/))
3072             ier = NF90_INQ_VARID (Cforcing_id,'time_step',vid)
3073             ier = NF90_PUT_VAR (Cforcing_id,vid, &
3074                  &                          (/(REAL(i,r_std),i=1,nparan*nbyear)/))
3075             ier = NF90_INQ_VARID (Cforcing_id,'solay',vid)
3076             ier = NF90_PUT_VAR (Cforcing_id,vid, &
3077                  &                          (/(REAL(i,r_std),i=1,nslm)/))
3078             ier = NF90_INQ_VARID (Cforcing_id,'elements',vid)
3079             ier = NF90_PUT_VAR (Cforcing_id,vid, &
3080                  &                          (/(REAL(i,r_std),i=1,nelements)/))
3081             ier = NF90_INQ_VARID (Cforcing_id,'littertype',vid)
3082             ier = NF90_PUT_VAR (Cforcing_id,vid, &
3083                  &                          (/(REAL(i,r_std),i=1,nlitt)/))
3084             ier = NF90_INQ_VARID (Cforcing_id,'soiltype',vid)
3085             ier = NF90_PUT_VAR (Cforcing_id,vid, &
3086                  &                          (/(REAL(i,r_std),i=1,nstm)/))
3087             ier = NF90_INQ_VARID (Cforcing_id,'pooltype',vid)
3088             ier = NF90_PUT_VAR (Cforcing_id,vid, &
3089                  &                          (/(REAL(i,r_std),i=1,npool)/))
3090             ier = NF90_INQ_VARID (Cforcing_id,'dblepooltype',vid)
3091             ier = NF90_PUT_VAR (Cforcing_id,vid, &
3092                  &                          (/(REAL(i,r_std),i=1,2*npool)/))
3093             ier = NF90_INQ_VARID (Cforcing_id,'flowingmatter',vid)
3094             ier = NF90_PUT_VAR (Cforcing_id,vid, &
3095                  &                          (/(REAL(i,r_std),i=1,nflow)/))
3096             ier = NF90_INQ_VARID (Cforcing_id,'solaydeep',vid)
3097             ier = NF90_PUT_VAR (Cforcing_id,vid, &
3098                  &                          (/(REAL(i,r_std),i=1,nslmd)/))
3099             ier = NF90_INQ_VARID (Cforcing_id,'index',vid)
3100             ier = NF90_PUT_VAR (Cforcing_id,vid, REAL(index_g,r_std) )
3101             ier = NF90_INQ_VARID (Cforcing_id,'clay',vid)
3102             ier = NF90_PUT_VAR (Cforcing_id,vid, clay_g )
3103             ier = NF90_INQ_VARID (Cforcing_id,'bulk_dens',vid)
3104             ier = NF90_PUT_VAR (Cforcing_id,vid, bulk_dens_g )
3105             ier = NF90_INQ_VARID (Cforcing_id,'soil_ph',vid)
3106             ier = NF90_PUT_VAR (Cforcing_id,vid, soil_ph_g )
3107             ier = NF90_INQ_VARID (Cforcing_id,'poor_soils',vid)
3108             ier = NF90_PUT_VAR (Cforcing_id,vid, poor_soils_g )
3109             ier = NF90_INQ_VARID (Cforcing_id,'soiltile',vid)
3110             ier = NF90_PUT_VAR (Cforcing_id,vid, soiltile_g )
3111             ier = NF90_INQ_VARID (Cforcing_id,'veget_max',vid)
3112             ier = NF90_PUT_VAR (Cforcing_id,vid, veget_max_g)
3113             ier = NF90_INQ_VARID (Cforcing_id,'soilcarbon_input',vid)
3114             ier = NF90_PUT_VAR (Cforcing_id,vid, soilcarbon_input_g )
3115             ier = NF90_INQ_VARID (Cforcing_id,'control_moist_above',vid)
3116             ier = NF90_PUT_VAR (Cforcing_id,vid, control_moist_above_g )
3117             ier = NF90_INQ_VARID (Cforcing_id,'control_moist_soil',vid)
3118             ier = NF90_PUT_VAR (Cforcing_id,vid, control_moist_soil_g )
3119             ier = NF90_INQ_VARID (Cforcing_id,'moist_soil',vid)
3120             ier = NF90_PUT_VAR (Cforcing_id,vid, moist_soil_g )
3121             ier = NF90_INQ_VARID (Cforcing_id,'soil_mc',vid)
3122             ier = NF90_PUT_VAR (Cforcing_id,vid, soil_mc_Cforcing_g)
3123             ier = NF90_INQ_VARID (Cforcing_id,'floodout',vid)
3124             ier = NF90_PUT_VAR (Cforcing_id,vid, floodout_Cforcing_g)
3125             ier = NF90_INQ_VARID (Cforcing_id,'wat_flux0',vid)
3126             ier = NF90_PUT_VAR (Cforcing_id,vid, wat_flux0_Cforcing_g)
3127             ier = NF90_INQ_VARID (Cforcing_id,'wat_flux',vid)
3128             ier = NF90_PUT_VAR (Cforcing_id,vid, wat_flux_Cforcing_g)
3129             ier = NF90_INQ_VARID (Cforcing_id,'runoff_per_soil',vid)
3130             ier = NF90_PUT_VAR (Cforcing_id,vid, runoff_per_soil_Cforcing_g)
3131             ier = NF90_INQ_VARID (Cforcing_id,'drainage_per_soil',vid)
3132             ier = NF90_PUT_VAR (Cforcing_id,vid, drainage_per_soil_Cforcing_g)
3133             ier = NF90_INQ_VARID (Cforcing_id,'DOC_to_topsoil',vid)
3134             ier = NF90_PUT_VAR (Cforcing_id,vid, DOC_to_topsoil_Cforcing_g)
3135             ier = NF90_INQ_VARID (Cforcing_id,'DOC_to_subsoil',vid)
3136             ier = NF90_PUT_VAR (Cforcing_id,vid, DOC_to_subsoil_Cforcing_g)
3137             ier = NF90_INQ_VARID (Cforcing_id,'precip2canopy',vid)
3138             ier = NF90_PUT_VAR (Cforcing_id,vid, precip2canopy_Cforcing_g)
3139             ier = NF90_INQ_VARID (Cforcing_id,'precip2ground',vid)
3140             ier = NF90_PUT_VAR (Cforcing_id,vid, precip2ground_Cforcing_g)
3141             ier = NF90_INQ_VARID (Cforcing_id,'canopy2ground',vid)
3142             ier = NF90_PUT_VAR (Cforcing_id,vid, canopy2ground_Cforcing_g)
3143             ier = NF90_INQ_VARID (Cforcing_id,'flood_frac',vid)
3144             ier = NF90_PUT_VAR (Cforcing_id,vid, flood_frac_Cforcing_g)
3145             ier = NF90_INQ_VARID (Cforcing_id,'control_temp_above',vid)
3146             ier = NF90_PUT_VAR (Cforcing_id,vid, control_temp_above_g )
3147             ier = NF90_INQ_VARID (Cforcing_id,'control_temp_soil',vid)
3148             ier = NF90_PUT_VAR (Cforcing_id,vid, control_temp_soil_g )
3149             ier = NF90_INQ_VARID (Cforcing_id,'npp_equil',vid)
3150             ier = NF90_PUT_VAR (Cforcing_id,vid, npp_equil_g )
3151             ier = NF90_INQ_VARID (Cforcing_id,'litter_above',vid)
3152             ier = NF90_PUT_VAR (Cforcing_id,vid, litter_above_g)
3153             ier = NF90_INQ_VARID (Cforcing_id,'litter_below',vid)
3154             ier = NF90_PUT_VAR (Cforcing_id,vid, litter_below_g)
3155             ier = NF90_INQ_VARID (Cforcing_id,'lignin_struc_above',vid)
3156             ier = NF90_PUT_VAR (Cforcing_id,vid, lignin_struc_above_g)
3157             ier = NF90_INQ_VARID (Cforcing_id,'lignin_struc_below',vid)
3158             ier = NF90_PUT_VAR (Cforcing_id,vid, lignin_struc_below_g)
3159         
3160          ! Close netCDF
3161          ier = NF90_CLOSE (Cforcing_id)
3162          IF (ier /= NF90_NOERR) THEN
3163             CALL ipslerr_p (3,'stomate_finalize', &
3164                  &        'PROBLEM in closing Cforcing file', &
3165                  &        NF90_STRERROR(ier),'')
3166          END IF
3167         
3168          Cforcing_id = -1
3169       ENDIF
3170
3171       ! Clear memory
3172       IF (is_root_prc) THEN
3173             DEALLOCATE(soilcarbon_input_g)
3174             DEALLOCATE(control_moist_above_g)
3175             DEALLOCATE(control_moist_soil_g)
3176             DEALLOCATE(moist_soil_g)
3177             DEALLOCATE(soil_mc_Cforcing_g)
3178             DEALLOCATE(floodout_Cforcing_g)
3179             DEALLOCATE(wat_flux0_Cforcing_g)
3180             DEALLOCATE(wat_flux_Cforcing_g)
3181             DEALLOCATE(runoff_per_soil_Cforcing_g)
3182             DEALLOCATE(drainage_per_soil_Cforcing_g)
3183             DEALLOCATE(DOC_to_topsoil_Cforcing_g)
3184             DEALLOCATE(DOC_to_subsoil_Cforcing_g)
3185             DEALLOCATE(canopy2ground_Cforcing_g)
3186             DEALLOCATE(precip2ground_Cforcing_g)
3187             DEALLOCATE(precip2canopy_Cforcing_g)
3188             DEALLOCATE(flood_frac_Cforcing_g)
3189             DEALLOCATE(control_temp_above_g)
3190             DEALLOCATE(control_temp_soil_g)
3191             DEALLOCATE(npp_equil_g)
3192             DEALLOCATE(litter_above_g)
3193             DEALLOCATE(litter_below_g)
3194             DEALLOCATE(lignin_struc_above_g)
3195             DEALLOCATE(lignin_struc_below_g)
3196       ENDIF
3197       
3198    ENDIF
3199 
3200  END SUBROUTINE stomate_finalize
3201
3202
3203!! ================================================================================================================================
3204!! SUBROUTINE   : stomate_init
3205!!
3206!>\BRIEF        The routine is called only at the first simulation. At that
3207!! time settings and flags are read and checked for internal consistency and
3208!! memory is allocated for the variables in stomate.
3209!!
3210!! DESCRIPTION  : The routine reads the
3211!! following flags from the run definition file:
3212!! -ipd (index of grid point for online diagnostics)\n
3213!! -ok_herbivores (flag to activate herbivores)\n
3214!! -treat_expansion (flag to activate PFT expansion across a pixel\n
3215!! -harvest_agri (flag to harvest aboveground biomass from agricultural PFTs)\n
3216!! \n
3217!! Check for inconsistent setting between the following flags:
3218!! -ok_stomate\n
3219!! -ok_dgvm\n
3220!! -ok_co2\n
3221!! \n
3222!! Memory is allocated for all the variables of stomate and new indexing tables
3223!! are build. New indexing tables are needed because a single pixel can conatin
3224!! several PFTs. The new indexing tables have separate indices for the different
3225!! PFTs. Similar index tables are build for land use cover change.\n
3226!! \n
3227!! Several global variables and land cover change variables are initialized to
3228!! zero.\n
3229!!
3230!! RECENT CHANGE(S) : None
3231!!
3232!! MAIN OUTPUT VARIABLE(S): Strictly speaking the subroutine has no output
3233!! variables. However, the routine allocates memory and builds new indexing
3234!! variables for later use.\n
3235!!
3236!! REFERENCE(S) : None
3237!!
3238!! FLOWCHART    : None
3239!! \n
3240!_ ================================================================================================================================
3241
3242  SUBROUTINE stomate_init &
3243       &  (kjpij, kjpindex, index, lalo, &
3244       &   rest_id_stom, hist_id_stom, hist_id_stom_IPCC)
3245
3246  !! 0. Variable and parameter declaration
3247
3248    !! 0.1 Input variables
3249
3250    INTEGER(i_std),INTENT(in)                    :: kjpij             !! Total size of the un-compressed grid, including
3251                                                                      !! oceans (unitless)
3252    INTEGER(i_std),INTENT(in)                    :: kjpindex          !! Domain size - number of terrestrial pixels
3253                                                                      !! (unitless)
3254    INTEGER(i_std),INTENT(in)                    :: rest_id_stom      !! STOMATE's _Restart_ file identifier
3255    INTEGER(i_std),INTENT(in)                    :: hist_id_stom      !! STOMATE's _history_ file identifier
3256    INTEGER(i_std),INTENT(in)                    :: hist_id_stom_IPCC !! STOMATE's IPCC _history_ file identifier
3257    INTEGER(i_std),DIMENSION(kjpindex),INTENT(in):: index             !! Indices of the terrestrial pixels on the global
3258                                                                      !! map
3259    REAL(r_std),DIMENSION(kjpindex,2),INTENT(in) :: lalo              !! Geogr. coordinates (latitude,longitude) (degrees)
3260   
3261    !! 0.2 Output variables
3262
3263    !! 0.3 Modified variables
3264
3265    !! 0.4 Local variables
3266
3267    LOGICAL                                      :: l_error           !! Check errors in netcdf call
3268    INTEGER(i_std)                               :: ier               !! Check errors in netcdf call
3269    INTEGER(i_std)                               :: ji,j,ipd,l        !! Indices
3270!_ ================================================================================================================================
3271   
3272  !! 1. Online diagnostics
3273
3274    IF ( kjpindex > 0 ) THEN
3275       !Config  Key  = STOMATE_DIAGPT
3276       !Config  Desc = Index of grid point for online diagnostics
3277       !Config If    = OK_STOMATE
3278       !Config  Def  = 1
3279       !Config  Help = This is the index of the grid point which
3280       !               will be used for online diagnostics.
3281       !Config Units = [-]
3282       ! By default ::ipd is set to 1
3283       ipd = 1
3284       ! Get ::ipd from run definition file
3285       CALL getin_p('STOMATE_DIAGPT',ipd)
3286       ipd = MIN( ipd, kjpindex )
3287       IF ( printlev >=3 ) THEN
3288          WRITE(numout,*) 'Stomate: '
3289          WRITE(numout,*) '  Index of grid point for online diagnostics: ',ipd
3290          WRITE(numout,*) '  Lon, lat:',lalo(ipd,2),lalo(ipd,1)
3291          WRITE(numout,*) '  Index of this point on GCM grid: ',index(ipd)
3292       END IF
3293    ENDIF
3294   
3295  !! 2. Check consistency of flags
3296
3297    IF ( ( .NOT. ok_stomate ) .AND. ok_dgvm ) THEN
3298       WRITE(numout,*) 'Cannot do dynamical vegetation without STOMATE.'
3299       WRITE(numout,*) 'Inconsistency between ::ok_stomate and ::ok_dgvm'
3300       WRITE(numout,*) 'Stop: fatal error'
3301       STOP
3302    ENDIF
3303
3304    IF ((.NOT.ok_co2).AND.ok_stomate) THEN
3305       WRITE(numout,*) 'Cannot call STOMATE without GPP.'
3306       WRITE(numout,*) 'Inconsistency between ::ok_stomate and ::ok_co2'
3307       WRITE(numout,*) 'Stop: fatal error'
3308       STOP
3309    ENDIF
3310
3311  !! 3. Communicate settings
3312   
3313    IF (printlev >=2) THEN
3314       WRITE(numout,*) 'stomate first call - overview of the activated flags:'
3315       WRITE(numout,*) '  Photosynthesis: ', ok_co2
3316       WRITE(numout,*) '  STOMATE: ', ok_stomate
3317       WRITE(numout,*) '  LPJ: ', ok_dgvm
3318    END IF
3319  !! 4. Allocate memory for STOMATE's variables
3320
3321    l_error = .FALSE.
3322
3323    ALLOCATE(veget_cov_max(kjpindex,nvm),stat=ier)
3324    l_error = l_error .OR. (ier /= 0)
3325    IF (l_error) THEN
3326       WRITE(numout,*) 'Memory allocation error for veget_cov_max. We stop. We need kjpindex*nvm words',kjpindex,nvm
3327       STOP 'stomate_init'
3328    ENDIF
3329
3330    ALLOCATE(ind(kjpindex,nvm),stat=ier)
3331    l_error = l_error .OR. (ier /= 0)
3332    IF (l_error) THEN
3333       WRITE(numout,*) 'Memory allocation error for ind. We stop. We need kjpindex*nvm words',kjpindex,nvm
3334       STOP 'stomate_init'
3335    ENDIF
3336
3337    ALLOCATE(adapted(kjpindex,nvm),stat=ier)
3338    l_error = l_error .OR. (ier /= 0)
3339    IF (l_error) THEN
3340       WRITE(numout,*) 'Memory allocation error for adapted. We stop. We need kjpindex*nvm words',kjpindex,nvm
3341       STOP 'stomate_init'
3342    ENDIF
3343
3344    ALLOCATE(regenerate(kjpindex,nvm),stat=ier)
3345    l_error = l_error .OR. (ier /= 0)
3346    IF (l_error) THEN
3347       WRITE(numout,*) 'Memory allocation error for regenerate. We stop. We need kjpindex*nvm words',kjpindex,nvm
3348       STOP 'stomate_init'
3349    ENDIF
3350
3351    ALLOCATE(humrel_daily(kjpindex,nvm),stat=ier)
3352    l_error = l_error .OR. (ier /= 0)
3353    IF (l_error) THEN
3354       WRITE(numout,*) 'Memory allocation error for humrel_daily. We stop. We need kjpindex*nvm words',kjpindex,nvm
3355       STOP 'stomate_init'
3356    ENDIF
3357
3358    ALLOCATE(litterhum_daily(kjpindex),stat=ier)
3359    l_error = l_error .OR. (ier /= 0)
3360    IF (l_error) THEN
3361       WRITE(numout,*) 'Memory allocation error for litterhum_daily. We stop. We need kjpindex words',kjpindex
3362       STOP 'stomate_init'
3363    ENDIF
3364
3365    ALLOCATE(t2m_daily(kjpindex),stat=ier)
3366    l_error = l_error .OR. (ier /= 0)
3367    IF (l_error) THEN
3368       WRITE(numout,*) 'Memory allocation error for t2m_daily. We stop. We need kjpindex words',kjpindex
3369       STOP 'stomate_init'
3370    ENDIF
3371
3372    ALLOCATE(t2m_min_daily(kjpindex),stat=ier)
3373    l_error = l_error .OR. (ier /= 0)
3374    IF (l_error) THEN
3375       WRITE(numout,*) 'Memory allocation error for t2m_min_daily. We stop. We need kjpindex words',kjpindex
3376       STOP 'stomate_init'
3377    ENDIF
3378
3379    ALLOCATE(tsurf_daily(kjpindex),stat=ier)
3380    l_error = l_error .OR. (ier /= 0)
3381    IF (l_error) THEN
3382       WRITE(numout,*) 'Memory allocation error for tsurf_daily. We stop. We need kjpindex words',kjpindex
3383       STOP 'stomate_init'
3384    ENDIF
3385
3386    ALLOCATE(tsoil_daily(kjpindex,nslm),stat=ier)
3387    l_error = l_error .OR. (ier /= 0)
3388    IF (l_error) THEN
3389       WRITE(numout,*) 'Memory allocation error for tsoil_daily. We stop. We need kjpindex*nslm words',kjpindex,nslm
3390       STOP 'stomate_init'
3391    ENDIF
3392
3393    ALLOCATE(soilhum_daily(kjpindex,nslm),stat=ier)
3394    l_error = l_error .OR. (ier /= 0)
3395    IF (l_error) THEN
3396       WRITE(numout,*) 'Memory allocation error for soilhum_daily. We stop. We need kjpindex*nslm words',kjpindex,nslm
3397       STOP 'stomate_init'
3398    ENDIF
3399
3400    ALLOCATE(precip_daily(kjpindex),stat=ier)
3401    l_error = l_error .OR. (ier /= 0)
3402    IF (l_error) THEN
3403       WRITE(numout,*) 'Memory allocation error for precip_daily. We stop. We need kjpindex words',kjpindex,nvm
3404       STOP 'stomate_init'
3405    ENDIF
3406
3407    ALLOCATE(gpp_daily(kjpindex,nvm),stat=ier)
3408    l_error = l_error .OR. (ier /= 0)
3409    IF (l_error) THEN
3410       WRITE(numout,*) 'Memory allocation error for gpp_daily. We stop. We need kjpindex*nvm words',kjpindex,nvm
3411       STOP 'stomate_init'
3412    ENDIF
3413
3414    ALLOCATE(npp_daily(kjpindex,nvm),stat=ier)
3415    l_error = l_error .OR. (ier /= 0)
3416    IF (l_error) THEN
3417       WRITE(numout,*) 'Memory allocation error for npp_daily. We stop. We need kjpindex*nvm words',kjpindex,nvm
3418       STOP 'stomate_init'
3419    ENDIF
3420
3421    ALLOCATE(turnover_daily(kjpindex,nvm,nparts,nelements),stat=ier)
3422    l_error = l_error .OR. (ier /= 0)
3423    IF (l_error) THEN
3424       WRITE(numout,*) 'Memory allocation error for turnover_daily. We stop. We need kjpindex*nvm*nparts*nelements words', &
3425       &   kjpindex,nvm,nparts,nelements
3426       STOP 'stomate_init'
3427    ENDIF
3428
3429    ALLOCATE(turnover_littercalc(kjpindex,nvm,nparts,nelements),stat=ier)
3430    l_error = l_error .OR. (ier /= 0)
3431    IF (l_error) THEN
3432       WRITE(numout,*) 'Memory allocation error for turnover_littercalc. We stop. We need kjpindex*nvm*nparts*nelements words', & 
3433        &  kjpindex,nvm,nparts,nelements
3434       STOP 'stomate_init'
3435    ENDIF
3436
3437    ALLOCATE(humrel_month(kjpindex,nvm),stat=ier)
3438    l_error = l_error .OR. (ier /= 0)
3439    IF (l_error) THEN
3440       WRITE(numout,*) 'Memory allocation error for humrel_month. We stop. We need kjpindex*nvm words',kjpindex,nvm
3441       STOP 'stomate_init'
3442    ENDIF
3443
3444    ALLOCATE(humrel_week(kjpindex,nvm),stat=ier)
3445    l_error = l_error .OR. (ier /= 0)
3446    IF (l_error) THEN
3447       WRITE(numout,*) 'Memory allocation error for humrel_week. We stop. We need kjpindex*nvm words',kjpindex,nvm
3448       STOP 'stomate_init'
3449    ENDIF
3450
3451    ALLOCATE(t2m_longterm(kjpindex),stat=ier)
3452    l_error = l_error .OR. (ier /= 0)
3453    IF (l_error) THEN
3454       WRITE(numout,*) 'Memory allocation error for t2m_longterm. We stop. We need kjpindex*nvm words',kjpindex,nvm
3455       STOP 'stomate_init'
3456    ENDIF
3457
3458    ALLOCATE(t2m_month(kjpindex),stat=ier)
3459    l_error = l_error .OR. (ier /= 0)
3460    IF (l_error) THEN
3461       WRITE(numout,*) 'Memory allocation error for t2m_month. We stop. We need kjpindex words',kjpindex
3462       STOP 'stomate_init'
3463    ENDIF
3464
3465    ALLOCATE(Tseason(kjpindex),stat=ier)
3466    l_error = l_error .OR. (ier /= 0)
3467    IF (l_error) THEN
3468       WRITE(numout,*) 'Memory allocation error for Tseason. We stop. We need kjpindex words',kjpindex
3469       STOP 'stomate_init'
3470    ENDIF
3471
3472    ALLOCATE(Tseason_length(kjpindex),stat=ier)
3473    l_error = l_error .OR. (ier /= 0)
3474    IF (l_error) THEN
3475       WRITE(numout,*) 'Memory allocation error for Tseason_length. We stop. We need kjpindex words',kjpindex
3476       STOP 'stomate_init'
3477    ENDIF
3478
3479    ALLOCATE(Tseason_tmp(kjpindex),stat=ier)
3480    l_error = l_error .OR. (ier /= 0)
3481    IF (l_error) THEN
3482       WRITE(numout,*) 'Memory allocation error for Tseason_tmp. We stop. We need kjpindex words',kjpindex
3483       STOP 'stomate_init'
3484    ENDIF
3485
3486    ALLOCATE(Tmin_spring_time(kjpindex,nvm),stat=ier)
3487    l_error = l_error .OR. (ier /= 0)
3488    IF (l_error) THEN
3489       WRITE(numout,*) 'Memory allocation error for Tmin_spring_time. We stop. We need kjpindex*nvm words',kjpindex,nvm
3490       STOP 'stomate_init'
3491    ENDIF
3492
3493    ALLOCATE(onset_date(kjpindex,nvm),stat=ier)
3494    l_error = l_error .OR. (ier /= 0)
3495    IF (l_error) THEN
3496       WRITE(numout,*) 'Memory allocation error for onset_date. We stop. We need kjpindex*nvm*nparts words',kjpindex,nvm,2
3497       STOP 'stomate_init'
3498    ENDIF
3499
3500    ALLOCATE(t2m_week(kjpindex),stat=ier)
3501    l_error = l_error .OR. (ier /= 0)
3502    IF (l_error) THEN
3503       WRITE(numout,*) 'Memory allocation error for t2m_week. We stop. We need kjpindex words',kjpindex
3504       STOP 'stomate_init'
3505    ENDIF
3506
3507    ALLOCATE(tsoil_month(kjpindex,nslm),stat=ier)
3508    l_error = l_error .OR. (ier /= 0)
3509    IF (l_error) THEN
3510       WRITE(numout,*) 'Memory allocation error for tsoil_month. We stop. We need kjpindex*nslm words',kjpindex,nslm
3511       STOP 'stomate_init'
3512    ENDIF
3513
3514    ALLOCATE(soilhum_month(kjpindex,nslm),stat=ier)
3515    l_error = l_error .OR. (ier /= 0)
3516    IF (l_error) THEN
3517       WRITE(numout,*) 'Memory allocation error for soilhum_month. We stop. We need kjpindex*nslm words',kjpindex,nslm
3518       STOP 'stomate_init'
3519    ENDIF
3520
3521    ALLOCATE(fireindex(kjpindex,nvm),stat=ier) 
3522    l_error = l_error .OR. (ier /= 0)
3523    IF (l_error) THEN
3524       WRITE(numout,*) 'Memory allocation error for fireindex. We stop. We need kjpindex*nvm words',kjpindex,nvm
3525       STOP 'stomate_init'
3526    ENDIF
3527
3528    ALLOCATE(firelitter(kjpindex,nvm),stat=ier)
3529    l_error = l_error .OR. (ier /= 0)
3530    IF (l_error) THEN
3531       WRITE(numout,*) 'Memory allocation error for firelitter. We stop. We need kjpindex*nvm words',kjpindex,nvm
3532       STOP 'stomate_init'
3533    ENDIF
3534
3535    ALLOCATE(maxhumrel_lastyear(kjpindex,nvm),stat=ier)
3536    l_error = l_error .OR. (ier /= 0)
3537    IF (l_error) THEN
3538       WRITE(numout,*) 'Memory allocation error for maxhumrel_lastyear. We stop. We need kjpindex*nvm words',kjpindex,nvm
3539       STOP 'stomate_init'
3540    ENDIF
3541
3542    ALLOCATE(maxhumrel_thisyear(kjpindex,nvm),stat=ier)
3543    l_error = l_error .OR. (ier /= 0)
3544    IF (l_error) THEN
3545       WRITE(numout,*) 'Memory allocation error for maxhumrel_thisyear. We stop. We need kjpindex*nvm words',kjpindex,nvm
3546       STOP 'stomate_init'
3547    ENDIF
3548
3549    ALLOCATE(minhumrel_lastyear(kjpindex,nvm),stat=ier)
3550    l_error = l_error .OR. (ier /= 0)
3551    IF (l_error) THEN
3552       WRITE(numout,*) 'Memory allocation error for minhumrel_lastyear. We stop. We need kjpindex*nvm words',kjpindex,nvm
3553       STOP 'stomate_init'
3554    ENDIF
3555
3556    ALLOCATE(minhumrel_thisyear(kjpindex,nvm),stat=ier)
3557    l_error = l_error .OR. (ier /= 0)
3558    IF (l_error) THEN
3559       WRITE(numout,*) 'Memory allocation error for minhumrel_thisyear. We stop. We need kjpindex*nvm words',kjpindex,nvm
3560       STOP 'stomate_init'
3561    ENDIF
3562
3563    ALLOCATE(maxgppweek_lastyear(kjpindex,nvm),stat=ier)
3564    l_error = l_error .OR. (ier /= 0)
3565    IF (l_error) THEN
3566       WRITE(numout,*) 'Memory allocation error for maxgppweek_lastyear. We stop. We need kjpindex*nvm words',kjpindex,nvm
3567       STOP 'stomate_init'
3568    ENDIF
3569
3570    ALLOCATE(maxgppweek_thisyear(kjpindex,nvm),stat=ier)
3571    l_error = l_error .OR. (ier /= 0)
3572    IF (l_error) THEN
3573       WRITE(numout,*) 'Memory allocation error for maxgppweek_thisyear. We stop. We need kjpindex*nvm words',kjpindex,nvm
3574       STOP 'stomate_init'
3575    ENDIF
3576
3577    ALLOCATE(gdd0_lastyear(kjpindex),stat=ier)
3578    l_error = l_error .OR. (ier /= 0)
3579    IF (l_error) THEN
3580       WRITE(numout,*) 'Memory allocation error for gdd0_lastyear. We stop. We need kjpindex words',kjpindex
3581       STOP 'stomate_init'
3582    ENDIF
3583
3584    ALLOCATE(gdd0_thisyear(kjpindex),stat=ier)
3585    l_error = l_error .OR. (ier /= 0)
3586    IF (l_error) THEN
3587       WRITE(numout,*) 'Memory allocation error for gdd0_thisyear. We stop. We need kjpindex words',kjpindex
3588       STOP 'stomate_init'
3589    ENDIF
3590
3591    ALLOCATE(gdd_init_date(kjpindex,2),stat=ier)
3592    l_error = l_error .OR. (ier /= 0)
3593    IF (l_error) THEN
3594       WRITE(numout,*) 'Memory allocation error for gdd_init_date. We stop. We need kjpindex*2 words',kjpindex,2
3595       STOP 'stomate_init'
3596    ENDIF
3597
3598    ALLOCATE(gdd_from_growthinit(kjpindex,nvm),stat=ier)
3599    l_error = l_error .OR. (ier /= 0)
3600    IF (l_error) THEN
3601       WRITE(numout,*) 'Memory allocation error for gdd_from_growthinit. We stop. We need kjpindex*nvm words',kjpindex,nvm
3602       STOP 'stomate_init'
3603    ENDIF
3604
3605    ALLOCATE(precip_lastyear(kjpindex),stat=ier)
3606    l_error = l_error .OR. (ier /= 0)
3607    IF (l_error) THEN
3608       WRITE(numout,*) 'Memory allocation error for precip_lastyear. We stop. We need kjpindex*nvm words',kjpindex
3609       STOP 'stomate_init'
3610    ENDIF
3611
3612    ALLOCATE(precip_thisyear(kjpindex),stat=ier)
3613    l_error = l_error .OR. (ier /= 0)
3614    IF (l_error) THEN
3615       WRITE(numout,*) 'Memory allocation error for precip_thisyear. We stop. We need kjpindex words',kjpindex
3616       STOP 'stomate_init'
3617    ENDIF
3618
3619    ALLOCATE(gdd_m5_dormance(kjpindex,nvm),stat=ier)
3620    l_error = l_error .OR. (ier /= 0)
3621    IF (l_error) THEN
3622       WRITE(numout,*) 'Memory allocation error for gdd_m5_dormance. We stop. We need kjpindex*nvm words',kjpindex,nvm
3623       STOP 'stomate_init'
3624    ENDIF
3625
3626    ALLOCATE(gdd_midwinter(kjpindex,nvm),stat=ier)
3627    l_error = l_error .OR. (ier /= 0)
3628    IF (l_error) THEN
3629       WRITE(numout,*) 'Memory allocation error for gdd_midwinter. We stop. We need kjpindex*nvm words',kjpindex,nvm
3630       STOP 'stomate_init'
3631    ENDIF
3632
3633    ALLOCATE(ncd_dormance(kjpindex,nvm),stat=ier)
3634    l_error = l_error .OR. (ier /= 0)
3635    IF (l_error) THEN
3636       WRITE(numout,*) 'Memory allocation error for ncd_dormance. We stop. We need kjpindex*nvm words',kjpindex,nvm
3637       STOP 'stomate_init'
3638    ENDIF
3639
3640    ALLOCATE(ngd_minus5(kjpindex,nvm),stat=ier)
3641    l_error = l_error .OR. (ier /= 0)
3642    IF (l_error) THEN
3643       WRITE(numout,*) 'Memory allocation error for ngd_minus5. We stop. We need kjpindex*nvm words',kjpindex,nvm
3644       STOP 'stomate_init'
3645    ENDIF
3646
3647    ALLOCATE(PFTpresent(kjpindex,nvm),stat=ier)
3648    l_error = l_error .OR. (ier /= 0)
3649    IF (l_error) THEN
3650       WRITE(numout,*) 'Memory allocation error for PFTpresent. We stop. We need kjpindex*nvm words',kjpindex,nvm
3651       STOP 'stomate_init'
3652    ENDIF
3653
3654    ALLOCATE(npp_longterm(kjpindex,nvm),stat=ier)
3655    l_error = l_error .OR. (ier /= 0)
3656    IF (l_error) THEN
3657       WRITE(numout,*) 'Memory allocation error for npp_longterm. We stop. We need kjpindex*nvm words',kjpindex,nvm
3658       STOP 'stomate_init'
3659    ENDIF
3660
3661    ALLOCATE(lm_lastyearmax(kjpindex,nvm),stat=ier)
3662    l_error = l_error .OR. (ier /= 0)
3663    IF (l_error) THEN
3664       WRITE(numout,*) 'Memory allocation error for lm_lastyearmax. We stop. We need kjpindex*nvm words',kjpindex,nvm
3665       STOP 'stomate_init'
3666    ENDIF
3667
3668    ALLOCATE(lm_thisyearmax(kjpindex,nvm),stat=ier)
3669    l_error = l_error .OR. (ier /= 0)
3670    IF (l_error) THEN
3671       WRITE(numout,*) 'Memory allocation error for lm_thisyearmax. We stop. We need kjpindex*nvm words',kjpindex,nvm
3672       STOP 'stomate_init'
3673    ENDIF
3674
3675    ALLOCATE(maxfpc_lastyear(kjpindex,nvm),stat=ier)
3676    l_error = l_error .OR. (ier /= 0)
3677    IF (l_error) THEN
3678       WRITE(numout,*) 'Memory allocation error for maxfpc_lastyear. We stop. We need kjpindex*nvm words',kjpindex,nvm
3679       STOP 'stomate_init'
3680    ENDIF
3681
3682    ALLOCATE(maxfpc_thisyear(kjpindex,nvm),stat=ier)
3683    l_error = l_error .OR. (ier /= 0)
3684    IF (l_error) THEN
3685       WRITE(numout,*) 'Memory allocation error for maxfpc_thisyear. We stop. We need kjpindex*nvm words',kjpindex,nvm
3686       STOP 'stomate_init'
3687    ENDIF
3688
3689    ALLOCATE(turnover_longterm(kjpindex,nvm,nparts,nelements),stat=ier)
3690    l_error = l_error .OR. (ier /= 0)
3691    IF (l_error) THEN
3692       WRITE(numout,*) 'Memory allocation error for turnover_longterm. We stop. We need kjpindex*nvm*nparts*nelements words', & 
3693       &    kjpindex,nvm,nparts,nelements
3694       STOP 'stomate_init'
3695    ENDIF
3696
3697    ALLOCATE(gpp_week(kjpindex,nvm),stat=ier)
3698    l_error = l_error .OR. (ier /= 0)
3699    IF (l_error) THEN
3700       WRITE(numout,*) 'Memory allocation error for gpp_week. We stop. We need kjpindex*nvm words',kjpindex,nvm
3701       STOP 'stomate_init'
3702    ENDIF
3703
3704    ALLOCATE(biomass(kjpindex,nvm,nparts,nelements),stat=ier)
3705    l_error = l_error .OR. (ier /= 0)
3706    IF (l_error) THEN
3707       WRITE(numout,*) 'Memory allocation error for biomass. We stop. We need kjpindex*nvm*nparts*nelements words', &
3708       &    kjpindex,nvm,nparts,nelements
3709       STOP 'stomate_init'
3710    ENDIF
3711
3712    ALLOCATE(senescence(kjpindex,nvm),stat=ier)
3713    l_error = l_error .OR. (ier /= 0)
3714    IF (l_error) THEN
3715       WRITE(numout,*) 'Memory allocation error for senescence. We stop. We need kjpindex*nvm words',kjpindex,nvm
3716       STOP 'stomate_init'
3717    ENDIF
3718
3719    ALLOCATE(begin_leaves(kjpindex,nvm),stat=ier)
3720    l_error = l_error .OR. (ier /= 0)
3721    IF (l_error) THEN
3722       WRITE(numout,*) 'Memory allocation error for begin_leaves. We stop. We need kjpindex*nvm words',kjpindex,nvm
3723       STOP 'stomate_init'
3724    ENDIF
3725
3726    ALLOCATE(when_growthinit(kjpindex,nvm),stat=ier)
3727    l_error = l_error .OR. (ier /= 0)
3728    IF (l_error) THEN
3729       WRITE(numout,*) 'Memory allocation error for when_growthinit. We stop. We need kjpindex*nvm words',kjpindex,nvm
3730       STOP 'stomate_init'
3731    ENDIF
3732
3733    ALLOCATE(age(kjpindex,nvm),stat=ier)
3734    l_error = l_error .OR. (ier /= 0)
3735    IF (l_error) THEN
3736       WRITE(numout,*) 'Memory allocation error for age. We stop. We need kjpindex*nvm words',kjpindex,nvm
3737       STOP 'stomate_init'
3738    ENDIF
3739
3740    ALLOCATE(resp_hetero_d(kjpindex,nvm),stat=ier)
3741    l_error = l_error .OR. (ier /= 0)
3742    IF (l_error) THEN
3743       WRITE(numout,*) 'Memory allocation error for resp_hetero_d. We stop. We need kjpindex*nvm words',kjpindex,nvm
3744       STOP 'stomate_init'
3745    ENDIF
3746       
3747    ALLOCATE(tot_soil_resp_d(kjpindex,nvm),stat=ier)
3748    l_error = l_error .OR. (ier /= 0)
3749    IF (l_error) THEN
3750       WRITE(numout,*) 'Memory allocation error for tot_soil_resp_d. We stop. We need kjpindex*nvm words',kjpindex,nvm
3751       STOP 'stomate_init'
3752    ENDIF
3753
3754    ALLOCATE(resp_hetero_radia(kjpindex,nvm),stat=ier)
3755    l_error = l_error .OR. (ier /= 0)
3756    IF (l_error) THEN
3757       WRITE(numout,*) 'Memory allocation error for resp_hetero_radia. We stop. We need kjpindex*nvm words',kjpindex,nvm
3758       STOP 'stomate_init'
3759    ENDIF
3760
3761    ALLOCATE(resp_maint_d(kjpindex,nvm),stat=ier)
3762    l_error = l_error .OR. (ier /= 0)
3763    IF (l_error) THEN
3764       WRITE(numout,*) 'Memory allocation error for resp_maint_d. We stop. We need kjpindex*nvm words',kjpindex,nvm
3765       STOP 'stomate_init'
3766    ENDIF
3767
3768    ALLOCATE(resp_growth_d(kjpindex,nvm),stat=ier)
3769    l_error = l_error .OR. (ier /= 0)
3770    IF (l_error) THEN
3771       WRITE(numout,*) 'Memory allocation error for resp_growth_d. We stop. We need kjpindex*nvm words',kjpindex,nvm
3772       STOP 'stomate_init'
3773    ENDIF
3774
3775    ALLOCATE(co2_fire(kjpindex,nvm),stat=ier)
3776    l_error = l_error .OR. (ier /= 0)
3777    IF (l_error) THEN
3778       WRITE(numout,*) 'Memory allocation error for co2_fire. We stop. We need kjpindex*nvm words',kjpindex,nvm
3779       STOP 'stomate_init'
3780    ENDIF
3781
3782    ALLOCATE(co2_to_bm_dgvm(kjpindex,nvm),stat=ier)
3783    l_error = l_error .OR. (ier /= 0)
3784    IF (l_error) THEN
3785       WRITE(numout,*) 'Memory allocation error for co2_to_bm_dgvm. We stop. We need kjpindex*nvm words',kjpindex,nvm
3786       STOP 'stomate_init'
3787    ENDIF
3788
3789    ALLOCATE(veget_lastlight(kjpindex,nvm),stat=ier)
3790    l_error = l_error .OR. (ier /= 0)
3791    IF (l_error) THEN
3792       WRITE(numout,*) 'Memory allocation error for veget_lastlight. We stop. We need kjpindex*nvm words',kjpindex,nvm
3793       STOP 'stomate_init'
3794    ENDIF
3795
3796    ALLOCATE(everywhere(kjpindex,nvm),stat=ier)
3797    l_error = l_error .OR. (ier /= 0)
3798    IF (l_error) THEN
3799       WRITE(numout,*) 'Memory allocation error for everywhere. We stop. We need kjpindex*nvm words',kjpindex,nvm
3800       STOP 'stomate_init'
3801    ENDIF
3802
3803    ALLOCATE(need_adjacent(kjpindex,nvm),stat=ier)
3804    l_error = l_error .OR. (ier /= 0)
3805    IF (l_error) THEN
3806       WRITE(numout,*) 'Memory allocation error for need_adjacent. We stop. We need kjpindex*nvm words',kjpindex,nvm
3807       STOP 'stomate_init'
3808    ENDIF
3809
3810    ALLOCATE(leaf_age(kjpindex,nvm,nleafages),stat=ier)
3811    l_error = l_error .OR. (ier /= 0)
3812    IF (l_error) THEN
3813       WRITE(numout,*) 'Memory allocation error for leaf_age. We stop. We need kjpindex*nvm*nleafages words', & 
3814       &      kjpindex,nvm,nleafages
3815       STOP 'stomate_init'
3816    ENDIF
3817
3818    ALLOCATE(leaf_frac(kjpindex,nvm,nleafages),stat=ier)
3819    l_error = l_error .OR. (ier /= 0)
3820    IF (l_error) THEN
3821       WRITE(numout,*) 'Memory allocation error for leaf_frac. We stop. We need kjpindex*nvm*nleafages words', & 
3822       &      kjpindex,nvm,nleafages
3823       STOP 'stomate_init'
3824    ENDIF
3825
3826    ALLOCATE(RIP_time(kjpindex,nvm),stat=ier)
3827    l_error = l_error .OR. (ier /= 0)
3828    IF (l_error) THEN
3829       WRITE(numout,*) 'Memory allocation error for RIP_time. We stop. We need kjpindex*nvm words',kjpindex,nvm
3830       STOP 'stomate_init'
3831    ENDIF
3832
3833    ALLOCATE(time_hum_min(kjpindex,nvm),stat=ier)
3834    l_error = l_error .OR. (ier /= 0)
3835    IF (l_error) THEN
3836       WRITE(numout,*) 'Memory allocation error for time_hum_min. We stop. We need kjpindex*nvm words',kjpindex,nvm
3837       STOP 'stomate_init'
3838    ENDIF
3839
3840    ALLOCATE(hum_min_dormance(kjpindex,nvm),stat=ier)
3841    l_error = l_error .OR. (ier /= 0)
3842    IF (l_error) THEN
3843       WRITE(numout,*) 'Memory allocation error for hum_min_dormance. We stop. We need kjpindex*nvm words',kjpindex,nvm
3844       STOP 'stomate_init'
3845    ENDIF
3846
3847    ALLOCATE(litterpart(kjpindex,nvm,nlitt),stat=ier)
3848    l_error = l_error .OR. (ier /= 0)
3849    IF (l_error) THEN
3850       WRITE(numout,*) 'Memory allocation error for litterpart. We stop. We need kjpindex*nvm*nlitt words',  &
3851       &  kjpindex,nvm,nlitt
3852       STOP 'stomate_init'
3853    ENDIF
3854
3855!    ALLOCATE(litter_above(kjpindex,nlitt,nvm,nelements),stat=ier)
3856!    l_error = l_error .OR. (ier /= 0)
3857!    IF (l_error) THEN
3858!       WRITE(numout,*) 'Memory allocation error for litter. We stop. We need kjpindex*nlitt*nvm*nelements words', &
3859!       &    kjpindex,nlitt,nvm,nelements
3860!       STOP 'stomate_init'
3861!    ENDIF
3862       
3863!    ALLOCATE(litter_below(kjpindex,nlitt,nvm,nslm,nelements),stat=ier)
3864!    l_error = l_error .OR. (ier /= 0)
3865!    IF (l_error) THEN
3866!       WRITE(numout,*) 'Memory allocation error for litter. We stop. We need kjpindex*nlitt*nvm*nslm*nelements words', &
3867!       &    kjpindex,nlitt,nvm,nslm,nelements
3868!       STOP 'stomate_init'
3869!    ENDIF
3870
3871    ALLOCATE(dead_leaves(kjpindex,nvm,nlitt),stat=ier)
3872    l_error = l_error .OR. (ier /= 0)
3873    IF (l_error) THEN
3874       WRITE(numout,*) 'Memory allocation error for dead_leaves. We stop. We need kjpindex*nvm*nlitt words', & 
3875       &   kjpindex,nvm,nlitt
3876       STOP 'stomate_init'
3877    ENDIF
3878
3879!    ALLOCATE(carbon(kjpindex,ncarb,nvm,nslm),stat=ier)
3880!    l_error = l_error .OR. (ier /= 0)
3881!    IF (l_error) THEN
3882!       WRITE(numout,*) 'Memory allocation error for carbon. We stop. We need kjpindex*ncarb*nvm*nslm words',kjpindex,ncarb,nvm,nslm
3883!       STOP 'stomate_init'
3884!    ENDIF
3885
3886    ALLOCATE(interception_storage(kjpindex,nvm,nelements),stat=ier)
3887    l_error = l_error .OR. (ier /= 0)
3888    IF (l_error) THEN
3889       WRITE(numout,*) 'Memory allocation error for interception_storage. We stop. We need kjpindex*nvm*nelements words',kjpindex,nvm,nelements
3890       STOP 'stomate_init'
3891    ENDIF
3892
3893!    ALLOCATE(lignin_struc_above(kjpindex,nvm),stat=ier)
3894!    l_error = l_error .OR. (ier /= 0)
3895!    IF (l_error) THEN
3896!       WRITE(numout,*) 'Memory allocation error for lignin_struc_above. We stop. We need kjpindex*nvm words',kjpindex,nvm
3897!       STOP 'stomate_init'
3898!    ENDIF
3899
3900!    ALLOCATE(lignin_struc_below(kjpindex,nvm,nslmd),stat=ier)
3901!    l_error = l_error .OR. (ier /= 0)
3902!    IF (l_error) THEN
3903!       WRITE(numout,*) 'Memory allocation error for lignin_struc_below. We stop. We need kjpindex*nvm*nlevs words',kjpindex,nvm,nslm+1
3904!       STOP 'stomate_init'
3905!    ENDIF
3906
3907    ALLOCATE(turnover_time(kjpindex,nvm),stat=ier)
3908    l_error = l_error .OR. (ier /= 0)
3909    IF (l_error) THEN
3910       WRITE(numout,*) 'Memory allocation error for turnover_time. We stop. We need kjpindex*nvm words',kjpindex,nvm
3911       STOP 'stomate_init'
3912    ENDIF
3913
3914    ALLOCATE(nep_daily(kjpindex,nvm),stat=ier)
3915    l_error = l_error .OR. (ier /= 0)
3916    IF (l_error) THEN
3917       WRITE(numout,*) 'Memory allocation error for nep_daily. We stop. We need kjpindex*nvm words',kjpindex,nvm
3918       STOP 'stomate_init'
3919    ENDIF
3920
3921    ALLOCATE(nep_monthly(kjpindex,nvm),stat=ier)
3922    l_error = l_error .OR. (ier /= 0)
3923    IF (l_error) THEN
3924       WRITE(numout,*) 'Memory allocation error for nep_monthly. We stop. We need kjpindex*nvm words',kjpindex,nvm
3925       STOP 'stomate_init'
3926    ENDIF
3927
3928    ALLOCATE (cflux_prod_monthly(kjpindex), stat=ier)
3929    l_error = l_error .OR. (ier /= 0)
3930    IF (l_error) THEN
3931       WRITE(numout,*) 'Memory allocation error for cflux_prod_monthly. We stop. We need kjpindex words',kjpindex
3932       STOP 'stomate_init'
3933    ENDIF
3934 
3935    ALLOCATE (harvest_above_monthly(kjpindex), stat=ier)
3936    l_error = l_error .OR. (ier /= 0)
3937    IF (l_error) THEN
3938       WRITE(numout,*) 'Memory allocation error for harvest_above_monthly. We stop. We need kjpindex words',kjpindex
3939       STOP 'stomate_init'
3940    ENDIF
3941
3942    ALLOCATE(bm_to_litter(kjpindex,nvm,nparts,nelements),stat=ier)
3943    l_error = l_error .OR. (ier /= 0)
3944    IF (l_error) THEN
3945       WRITE(numout,*) 'Memory allocation error for bm_to_litter. We stop. We need kjpindex*nvm*nparts*nelements words', & 
3946       &    kjpindex,nvm,nparts,nelements
3947       STOP 'stomate_init'
3948    ENDIF
3949
3950    ALLOCATE(bm_to_littercalc(kjpindex,nvm,nparts,nelements),stat=ier)
3951    l_error = l_error .OR. (ier /= 0)
3952    IF (l_error) THEN
3953       WRITE(numout,*) 'Memory allocation error for bm_to_littercalc. We stop. We need kjpindex*nvm*nparts*nelements words', &
3954       &   kjpindex,nvm,nparts,nelements
3955       STOP 'stomate_init'
3956    ENDIF
3957
3958    ALLOCATE(herbivores(kjpindex,nvm),stat=ier)
3959    l_error = l_error .OR. (ier /= 0)
3960    IF (l_error) THEN
3961       WRITE(numout,*) 'Memory allocation error for herbivores. We stop. We need kjpindex*nvm words',kjpindex,nvm
3962       STOP 'stomate_init'
3963    ENDIF
3964
3965    ALLOCATE(hori_index(kjpindex),stat=ier)
3966    l_error = l_error .OR. (ier /= 0)
3967    IF (l_error) THEN
3968       WRITE(numout,*) 'Memory allocation error for hori_index. We stop. We need kjpindex words',kjpindex
3969       STOP 'stomate_init'
3970    ENDIF
3971
3972    ALLOCATE(horipft_index(kjpindex*nvm),stat=ier)
3973    l_error = l_error .OR. (ier /= 0)
3974    IF (l_error) THEN
3975       WRITE(numout,*) 'Memory allocation error for horipft_index. We stop. We need kjpindex*nvm words',kjpindex*nvm
3976       STOP 'stomate_init'
3977    ENDIF
3978
3979    ALLOCATE(resp_maint_part_radia(kjpindex,nvm,nparts),stat=ier)
3980    l_error = l_error .OR. (ier /= 0)
3981    IF (l_error) THEN
3982       WRITE(numout,*) 'Memory allocation error for resp_maint_part_radia. We stop. We need kjpindex*nvm*nparts words', &
3983       &  kjpindex,nvm,nparts
3984       STOP 'stomate_init'
3985    ENDIF
3986
3987    ALLOCATE(resp_maint_radia(kjpindex,nvm),stat=ier)
3988    l_error = l_error .OR. (ier /= 0)
3989    IF (l_error) THEN
3990       WRITE(numout,*) 'Memory allocation error for resp_maint_radia. We stop. We need kjpindex*nvm words',kjpindex,nvm
3991       STOP 'stomate_init'
3992    ENDIF
3993
3994    ALLOCATE(resp_maint_part(kjpindex,nvm,nparts),stat=ier)
3995    l_error = l_error .OR. (ier /= 0)
3996    IF (l_error) THEN
3997       WRITE(numout,*) 'Memory allocation error for resp_maint_part. We stop. We need kjpindex*nvm*nparts words', &
3998       &    kjpindex,nvm,nparts
3999       STOP 'stomate_init'
4000    ENDIF
4001    resp_maint_part(:,:,:) = zero
4002
4003    ALLOCATE (horip10_index(kjpindex*10), stat=ier)
4004    l_error = l_error .OR. (ier /= 0)
4005    IF (l_error) THEN
4006       WRITE(numout,*) 'Memory allocation error for horip10_index. We stop. We need kjpindex*10 words',kjpindex,10
4007       STOP 'stomate_init'
4008    ENDIF
4009
4010    ALLOCATE (horip100_index(kjpindex*100), stat=ier)
4011    l_error = l_error .OR. (ier /= 0)
4012    IF (l_error) THEN
4013       WRITE(numout,*) 'Memory allocation error for horip100_index. We stop. We need kjpindex*100 words',kjpindex,100
4014       STOP 'stomate_init'
4015    ENDIF
4016
4017    ALLOCATE (horip11_index(kjpindex*11), stat=ier)
4018    l_error = l_error .OR. (ier /= 0)
4019    IF (l_error) THEN
4020       WRITE(numout,*) 'Memory allocation error for horip11_index. We stop. We need kjpindex*11 words',kjpindex,11
4021       STOP 'stomate_init'
4022    ENDIF
4023
4024    ALLOCATE (horip101_index(kjpindex*101), stat=ier)
4025    l_error = l_error .OR. (ier /= 0)
4026    IF (l_error) THEN
4027       WRITE(numout,*) 'Memory allocation error for horip101_index. We stop. We need kjpindex*101 words',kjpindex,101
4028       STOP 'stomate_init'
4029    ENDIF
4030
4031    ALLOCATE (prod10(kjpindex,0:10), stat=ier)
4032    l_error = l_error .OR. (ier /= 0)
4033    IF (l_error) THEN
4034       WRITE(numout,*) 'Memory allocation error for prod10. We stop. We need kjpindex*11 words',kjpindex,11
4035       STOP 'stomate_init'
4036    ENDIF
4037
4038    ALLOCATE (prod100(kjpindex,0:100), stat=ier)
4039    l_error = l_error .OR. (ier /= 0)
4040    IF (l_error) THEN
4041       WRITE(numout,*) 'Memory allocation error for prod100. We stop. We need kjpindex*101 words',kjpindex,101
4042       STOP 'stomate_init'
4043    ENDIF
4044
4045    ALLOCATE (flux10(kjpindex,10), stat=ier)
4046    l_error = l_error .OR. (ier /= 0)
4047    IF (l_error) THEN
4048       WRITE(numout,*) 'Memory allocation error for flux10. We stop. We need kjpindex*10 words',kjpindex,10
4049       STOP 'stomate_init'
4050    ENDIF
4051
4052    ALLOCATE (flux100(kjpindex,100), stat=ier)
4053    l_error = l_error .OR. (ier /= 0)
4054    IF (l_error) THEN
4055       WRITE(numout,*) 'Memory allocation error for flux100. We stop. We need kjpindex*100 words',kjpindex,100
4056       STOP 'stomate_init'
4057    ENDIF
4058
4059    ALLOCATE (convflux(kjpindex), stat=ier)
4060    l_error = l_error .OR. (ier /= 0)
4061    IF (l_error) THEN
4062       WRITE(numout,*) 'Memory allocation error for convflux. We stop. We need kjpindex words',kjpindex
4063       STOP 'stomate_init'
4064    ENDIF
4065
4066    ALLOCATE (cflux_prod10(kjpindex), stat=ier)
4067    l_error = l_error .OR. (ier /= 0)
4068    IF (l_error) THEN
4069       WRITE(numout,*) 'Memory allocation error for cflux_prod10. We stop. We need kjpindex words',kjpindex
4070       STOP 'stomate_init'
4071    ENDIF
4072
4073    ALLOCATE (cflux_prod100(kjpindex), stat=ier)
4074    l_error = l_error .OR. (ier /= 0)
4075    IF (l_error) THEN
4076       WRITE(numout,*) 'Memory allocation error for cflux_prod100. We stop. We need kjpindex words',kjpindex
4077       STOP 'stomate_init'
4078    ENDIF
4079
4080    ALLOCATE (prod10_harvest(kjpindex,0:10), stat=ier)
4081    l_error = l_error .OR. (ier /= 0)
4082    IF (l_error) THEN
4083       WRITE(numout,*) 'Memory allocation error for prod10_harvest. We stop. We need kjpindex*11 words',kjpindex,11
4084       STOP 'stomate_init'
4085    ENDIF
4086
4087    ALLOCATE (prod100_harvest(kjpindex,0:100), stat=ier)
4088    l_error = l_error .OR. (ier /= 0)
4089    IF (l_error) THEN
4090       WRITE(numout,*) 'Memory allocation error for prod100_harvest. We stop. We need kjpindex*101 words',kjpindex,101
4091       STOP 'stomate_init'
4092    ENDIF
4093
4094    ALLOCATE (flux10_harvest(kjpindex,10), stat=ier)
4095    l_error = l_error .OR. (ier /= 0)
4096    IF (l_error) THEN
4097       WRITE(numout,*) 'Memory allocation error for flux10_harvest. We stop. We need kjpindex*10 words',kjpindex,10
4098       STOP 'stomate_init'
4099    ENDIF
4100
4101    ALLOCATE (flux100_harvest(kjpindex,100), stat=ier)
4102    l_error = l_error .OR. (ier /= 0)
4103    IF (l_error) THEN
4104       WRITE(numout,*) 'Memory allocation error for flux100_harvest. We stop. We need kjpindex*100 words',kjpindex,100
4105       STOP 'stomate_init'
4106    ENDIF
4107
4108    ALLOCATE (convflux_harvest(kjpindex), stat=ier)
4109    l_error = l_error .OR. (ier /= 0)
4110    IF (l_error) THEN
4111       WRITE(numout,*) 'Memory allocation error for convflux_harvest. We stop. We need kjpindex words',kjpindex
4112       STOP 'stomate_init'
4113    ENDIF
4114
4115    ALLOCATE (cflux_prod10_harvest(kjpindex), stat=ier)
4116    l_error = l_error .OR. (ier /= 0)
4117    IF (l_error) THEN
4118       WRITE(numout,*) 'Memory allocation error for cflux_prod10_harvest. We stop. We need kjpindex words',kjpindex
4119       STOP 'stomate_init'
4120    ENDIF
4121
4122    ALLOCATE (cflux_prod100_harvest(kjpindex), stat=ier)
4123    l_error = l_error .OR. (ier /= 0)
4124    IF (l_error) THEN
4125       WRITE(numout,*) 'Memory allocation error for cflux_prod100_harvest. We stop. We need kjpindex words',kjpindex
4126       STOP 'stomate_init'
4127    ENDIF
4128
4129    ALLOCATE (woodharvestpft(kjpindex,nvm), stat=ier)
4130    l_error = l_error .OR. (ier /= 0)
4131    IF (l_error) THEN
4132       WRITE(numout,*) 'Memory allocation error for woodharvestpft. We stop. We need kjpindex*nvm words',kjpindex*nvm
4133       STOP 'stomate_init'
4134    ENDIF
4135
4136    ALLOCATE (convfluxpft(kjpindex,nvm), stat=ier)
4137    l_error = l_error .OR. (ier /= 0)
4138    IF (l_error) THEN
4139       WRITE(numout,*) 'Memory allocation error for convfluxpft. We stop. We need kjpindex*nvm words',kjpindex*nvm
4140       STOP 'stomate_init'
4141    ENDIF
4142
4143    ALLOCATE (fDeforestToProduct(kjpindex,nvm), stat=ier)
4144    l_error = l_error .OR. (ier /= 0)
4145    IF (l_error) THEN
4146       WRITE(numout,*) 'Memory allocation error for fDeforestToProduct. We stop. We need kjpindex*nvm words',kjpindex*nvm
4147       STOP 'stomate_init'
4148    ENDIF
4149
4150    ALLOCATE (fLulccResidue(kjpindex,nvm), stat=ier)
4151    l_error = l_error .OR. (ier /= 0)
4152    IF (l_error) THEN
4153       WRITE(numout,*) 'Memory allocation error for fLulccResidue. We stop. We need kjpindex*nvm words',kjpindex*nvm
4154       STOP 'stomate_init'
4155    ENDIF
4156
4157    ALLOCATE (fHarvestToProduct(kjpindex,nvm), stat=ier)
4158    l_error = l_error .OR. (ier /= 0)
4159    IF (l_error) THEN
4160       WRITE(numout,*) 'Memory allocation error for fHarvestToProduct. We stop. We need kjpindex*nvm words',kjpindex*nvm
4161       STOP 'stomate_init'
4162    ENDIF
4163
4164    ALLOCATE (harvest_above(kjpindex), stat=ier)
4165    l_error = l_error .OR. (ier /= 0)
4166    IF (l_error) THEN
4167       WRITE(numout,*) 'Memory allocation error for harvest_above. We stop. We need kjpindex words',kjpindex
4168       STOP 'stomate_init'
4169    ENDIF
4170
4171    ALLOCATE (carb_mass_total(kjpindex), stat=ier)
4172    l_error = l_error .OR. (ier /= 0)
4173    IF (l_error) THEN
4174       WRITE(numout,*) 'Memory allocation error for carb_mass_total. We stop. We need kjpindex words',kjpindex
4175       STOP 'stomate_init'
4176    ENDIF
4177
4178    ALLOCATE (soilcarbon_input_daily(kjpindex,nvm,nslmd,npool,nelements), stat=ier)
4179    l_error = l_error .OR. (ier /= 0)
4180    IF (l_error) THEN
4181       WRITE(numout,*) 'Memory allocation error for soilcarbon_input_daily. We stop. We need kjpindex*ncarb*nvm words', & 
4182       &    kjpindex,ncarb,nvm
4183       STOP 'stomate_init'
4184    ENDIF
4185
4186!    ALLOCATE(DOC(kjpindex,nvm,nslmd,ndoc,npool,nelements),stat=ier)
4187!    l_error = l_error .OR. (ier /= 0)
4188!    IF (l_error) THEN
4189!       WRITE(numout,*) 'Memory allocation error for DOC. We stop. We need kjpindex*nvm*nslm*ndoc*npool*nelements words',kjpindex,nvm,nslm,ndoc,npool,nelements
4190!       STOP 'stomate_init'
4191!    ENDIF
4192
4193    ALLOCATE (control_temp_above_daily(kjpindex,nlitt), stat=ier) 
4194    l_error = l_error .OR. (ier /= 0) 
4195    IF (l_error) THEN
4196       WRITE(numout,*) 'Memory allocation error for control_temp_above_daily. We stop. We need kjpindex*nlitt words',kjpindex,nlitt 
4197       STOP 'stomate_init' 
4198    ENDIF
4199
4200    ALLOCATE (control_temp_soil_daily(kjpindex,nslmd,npool*2), stat=ier)
4201    l_error = l_error .OR. (ier /= 0)
4202    IF (l_error) THEN
4203       WRITE(numout,*) 'Memory allocation error for control_temp_soil_daily. We stop. We need kjpindex*nslm*npool words',kjpindex,nslm,npool
4204       STOP 'stomate_init'
4205    ENDIF
4206
4207    ALLOCATE (control_moist_soil_daily(kjpindex,nslmd,nvm), stat=ier)
4208    l_error = l_error .OR. (ier /= 0)
4209    IF (l_error) THEN
4210       WRITE(numout,*) 'Memory allocation error for control_moist_soil_daily. We stop. We need kjpindex*nslm*nvm words',kjpindex,nslm,nvm
4211       STOP 'stomate_init'
4212    ENDIF
4213
4214    ALLOCATE (moist_soil_daily(kjpindex,nslm), stat=ier)
4215    l_error = l_error .OR. (ier /= 0)
4216    IF (l_error) THEN
4217       WRITE(numout,*) 'Memory allocation error for moist_soil_daily. We stop. We need kjpindex*nslm words',kjpindex,nslm
4218       STOP 'stomate_init'
4219    ENDIF
4220
4221    ALLOCATE (soil_mc_Cforcing_daily(kjpindex,nslm,nstm), stat=ier)
4222    l_error = l_error .OR. (ier /= 0)
4223    IF (l_error) THEN
4224       WRITE(numout,*) 'Memory allocation error for soil_mc_Cforcing_daily. We stop. We need kjpindex*nslm*nstm words',kjpindex,nslm,nstm
4225       STOP 'stomate_init'
4226    ENDIF
4227
4228    ALLOCATE (floodout_Cforcing_daily(kjpindex), stat=ier)
4229    l_error = l_error .OR. (ier /= 0)
4230    IF (l_error) THEN
4231       WRITE(numout,*) 'Memory allocation error for floodout_Cforcing_daily. We stop. We need kjpindex words',kjpindex
4232       STOP 'stomate_init'
4233    ENDIF
4234
4235    ALLOCATE (wat_flux0_Cforcing_daily(kjpindex,nstm), stat=ier)
4236    l_error = l_error .OR. (ier /= 0)
4237    IF (l_error) THEN
4238       WRITE(numout,*) 'Memory allocation error for wat_flux0_Cforcing_daily. We stop. We need kjpindex*nstm words',kjpindex,nstm
4239       STOP 'stomate_init'
4240    ENDIF
4241
4242    ALLOCATE (wat_flux_Cforcing_daily(kjpindex,nslm,nstm), stat=ier)
4243    l_error = l_error .OR. (ier /= 0)
4244    IF (l_error) THEN
4245       WRITE(numout,*) 'Memory allocation error for wat_flux_Cforcing_daily. We stop. We need kjpindex*nslm*nstm words',kjpindex,nslm,nstm
4246       STOP 'stomate_init'
4247    ENDIF
4248
4249    ALLOCATE (runoff_per_soil_Cforcing_daily(kjpindex,nstm), stat=ier)
4250    l_error = l_error .OR. (ier /= 0)
4251    IF (l_error) THEN
4252       WRITE(numout,*) 'Memory allocation error for runoff_per_soil_Cforcing_daily. We stop. We need kjpindex*nstm words',kjpindex,nstm
4253       STOP 'stomate_init'
4254    ENDIF
4255
4256    ALLOCATE (drainage_per_soil_Cforcing_daily(kjpindex,nstm), stat=ier)
4257    l_error = l_error .OR. (ier /= 0)
4258    IF (l_error) THEN
4259       WRITE(numout,*) 'Memory allocation error for drainage_per_soil_Cforcing_daily. We stop. We need kjpindex*nstm words',kjpindex,nstm
4260       STOP 'stomate_init'
4261    ENDIF
4262
4263    ALLOCATE (DOC_to_topsoil_Cforcing_daily(kjpindex,nflow), stat=ier)
4264    l_error = l_error .OR. (ier /= 0)
4265    IF (l_error) THEN
4266       WRITE(numout,*) 'Memory allocation error for DOC_to_topsoil_Cforcing_daily. We stop. We need kjpindex*nflow words',kjpindex,nflow
4267       STOP 'stomate_init'
4268    ENDIF
4269
4270    ALLOCATE (DOC_to_subsoil_Cforcing_daily(kjpindex,nflow), stat=ier)
4271    l_error = l_error .OR. (ier /= 0)
4272    IF (l_error) THEN
4273       WRITE(numout,*) 'Memory allocation error for DOC_to_subsoil_Cforcing_daily. We stop. We need kjpindex*nflow words',kjpindex,nflow
4274       STOP 'stomate_init'
4275    ENDIF
4276
4277    ALLOCATE (precip2canopy_Cforcing_daily(kjpindex,nvm), stat=ier)
4278    l_error = l_error .OR. (ier /= 0)
4279    IF (l_error) THEN
4280       WRITE(numout,*) 'Memory allocation error for precip2canopy_Cforcing_daily. We stop. We need kjpindex*nvm words',kjpindex,nvm
4281       STOP 'stomate_init'
4282    ENDIF
4283
4284    ALLOCATE (precip2ground_Cforcing_daily(kjpindex,nvm), stat=ier)
4285    l_error = l_error .OR. (ier /= 0)
4286    IF (l_error) THEN
4287       WRITE(numout,*) 'Memory allocation error for precip2ground_Cforcing_daily. We stop. We need kjpindex*nvm words',kjpindex,nvm
4288       STOP 'stomate_init'
4289    ENDIF
4290
4291    ALLOCATE (canopy2ground_Cforcing_daily(kjpindex,nvm), stat=ier)
4292    l_error = l_error .OR. (ier /= 0)
4293    IF (l_error) THEN
4294       WRITE(numout,*) 'Memory allocation error for canopy2ground_Cforcing_daily. We stop. We need kjpindex*nvm words',kjpindex,nvm
4295       STOP 'stomate_init'
4296    ENDIF
4297
4298    ALLOCATE (flood_frac_Cforcing_daily(kjpindex), stat=ier)
4299    l_error = l_error .OR. (ier /= 0)
4300    IF (l_error) THEN
4301       WRITE(numout,*) 'Memory allocation error for flood_frac_Cforcing_daily. We stop. We need kjpindex words',kjpindex
4302       STOP 'stomate_init'
4303    ENDIF
4304
4305    ALLOCATE (control_moist_above_daily(kjpindex,nvm), stat=ier) 
4306    l_error = l_error .OR. (ier /= 0) 
4307    IF (l_error) THEN
4308       WRITE(numout,*) 'Memory allocation error for control_moist_above_daily. We stop. We need kjpindex*nvm words',kjpindex,nvm 
4309       STOP 'stomate_init' 
4310    ENDIF
4311
4312    ALLOCATE (fpc_max(kjpindex,nvm), stat=ier)
4313    l_error = l_error .OR. (ier /= 0)
4314    IF (l_error) THEN
4315       WRITE(numout,*) 'Memory allocation error for fpc_max. We stop. We need kjpindex*nvm words',kjpindex,nvm
4316       STOP 'stomate_init'
4317    ENDIF
4318
4319    ALLOCATE(ok_equilibrium(kjpindex),stat=ier)
4320    l_error = l_error .OR. (ier /= 0) 
4321    IF (l_error) THEN
4322       WRITE(numout,*) 'Memory allocation error for ok_equilibrium. We stop. We need kjpindex words',kjpindex
4323       STOP 'stomate_init'
4324    ENDIF
4325
4326    ALLOCATE(carbon_eq(kjpindex),stat=ier)
4327    l_error = l_error .OR. (ier /= 0)
4328    IF (l_error) THEN
4329       WRITE(numout,*) 'Memory allocation error for carbon_eq. We stop. We need kjpindex words',kjpindex
4330       STOP 'stomate_init'
4331    ENDIF
4332
4333    ALLOCATE(nbp_accu(kjpindex),stat=ier)
4334    l_error = l_error .OR. (ier /= 0)
4335    IF (l_error) THEN
4336       WRITE(numout,*) 'Memory allocation error for nbp_accu. We stop. We need kjpindex words',kjpindex
4337       STOP 'stomate_init'
4338    ENDIF
4339
4340    ALLOCATE(nbp_flux(kjpindex),stat=ier)
4341    l_error = l_error .OR. (ier /= 0)
4342    IF (l_error) THEN
4343       WRITE(numout,*) 'Memory allocation error for nbp_flux. We stop. We need kjpindex words',kjpindex
4344       STOP 'stomate_init'
4345    ENDIF
4346
4347    ALLOCATE(matrixA(kjpindex,nvm,nbpools,nbpools),stat=ier)
4348    l_error = l_error .OR. (ier /= 0)
4349    IF (l_error) THEN
4350       WRITE(numout,*) 'Memory allocation error for matrixA. We stop. We need kjpindex*nvm*nbpools*nbpools words',  & 
4351       &     kjpindex, nvm, nbpools, nbpools
4352       STOP 'stomate_init'
4353    ENDIF
4354
4355    ALLOCATE(vectorB(kjpindex,nvm,nbpools),stat=ier)
4356    l_error = l_error .OR. (ier /= 0)
4357    IF (l_error) THEN
4358       WRITE(numout,*) 'Memory allocation error for vectorB. We stop. We need kjpindex*nvm*nbpools words',  & 
4359       &     kjpindex, nvm, nbpools
4360       STOP 'stomate_init'
4361    ENDIF
4362
4363    ALLOCATE(VectorU(kjpindex,nvm,nbpools),stat=ier)
4364    l_error = l_error .OR. (ier /= 0)
4365    IF (l_error) THEN
4366       WRITE(numout,*) 'Memory allocation error for VectorU. We stop. We need kjpindex*nvm*nbpools words',  & 
4367       &     kjpindex, nvm, nbpools
4368       STOP 'stomate_init'
4369    ENDIF
4370
4371    ALLOCATE(MatrixV(kjpindex,nvm,nbpools,nbpools),stat=ier)
4372    l_error = l_error .OR. (ier /= 0)
4373    IF (l_error) THEN
4374       WRITE(numout,*) 'Memory allocation error for MatrixV. We stop. We need kjpindex*nvm*nbpools*nbpools words',  & 
4375       &     kjpindex, nvm, nbpools, nbpools
4376       STOP 'stomate_init'
4377    ENDIF
4378
4379    ALLOCATE(MatrixW(kjpindex,nvm,nbpools,nbpools),stat=ier)
4380    l_error = l_error .OR. (ier /= 0)
4381    IF (l_error) THEN
4382       WRITE(numout,*) 'Memory allocation error for MatrixW. We stop. We need kjpindex*nvm*nbpools*nbpools words',  & 
4383       &     kjpindex, nvm, nbpools, nbpools
4384       STOP 'stomate_init'
4385    ENDIF
4386
4387    ALLOCATE(previous_stock(kjpindex,nvm,nbpools),stat=ier)
4388    l_error = l_error .OR. (ier /= 0)
4389    IF (l_error) THEN
4390       WRITE(numout,*) 'Memory allocation error for previous_stock. We stop. We need kjpindex*nvm*nbpools words',  & 
4391       &     kjpindex, nvm, nbpools
4392       STOP 'stomate_init'
4393    ENDIF
4394
4395    ALLOCATE(current_stock(kjpindex,nvm,nbpools),stat=ier)
4396    l_error = l_error .OR. (ier /= 0)
4397    IF (l_error) THEN
4398       WRITE(numout,*) 'Memory allocation error for current_stock. We stop. We need kjpindex*nvm*nbpools words',  & 
4399       &     kjpindex, nvm, nbpools
4400       STOP 'stomate_init'
4401    ENDIF
4402   
4403  !! 5. File definitions
4404
4405    ! Store history and restart files in common variables
4406    hist_id_stomate = hist_id_stom
4407    hist_id_stomate_IPCC = hist_id_stom_IPCC
4408    rest_id_stomate = rest_id_stom
4409   
4410    ! In STOMATE reduced grids are used containing only terrestrial pixels.
4411    ! Build a new indexing table for the vegetation fields separating
4412    ! between the different PFTs. Note that ::index has dimension (kjpindex)
4413    ! wheras ::indexpft has dimension (kjpindex*nvm).
4414
4415    hori_index(:) = index(:)
4416
4417    DO j = 1, nvm
4418       DO ji = 1, kjpindex
4419          horipft_index((j-1)*kjpindex+ji) = index(ji)+(j-1)*kjpij + offset_omp - offset_mpi
4420       ENDDO
4421    ENDDO
4422
4423    ! Similar index tables are build for the land cover change variables
4424    DO j = 1, 10
4425       DO ji = 1, kjpindex
4426          horip10_index((j-1)*kjpindex+ji) = index(ji)+(j-1)*kjpij + offset_omp - offset_mpi
4427       ENDDO
4428    ENDDO
4429
4430    DO j = 1, 100
4431       DO ji = 1, kjpindex
4432          horip100_index((j-1)*kjpindex+ji) = index(ji)+(j-1)*kjpij + offset_omp - offset_mpi
4433       ENDDO
4434    ENDDO
4435
4436    DO j = 1, 11
4437       DO ji = 1, kjpindex
4438          horip11_index((j-1)*kjpindex+ji) = index(ji)+(j-1)*kjpij + offset_omp - offset_mpi
4439       ENDDO
4440    ENDDO
4441
4442    DO j = 1, 101
4443       DO ji = 1, kjpindex
4444          horip101_index((j-1)*kjpindex+ji) = index(ji)+(j-1)*kjpij + offset_omp - offset_mpi
4445       ENDDO
4446    ENDDO
4447
4448  !! 6. Initialization of global and land cover change variables.
4449
4450    ! All variables are cumulative variables. bm_to_litter is not and is therefore
4451    ! excluded
4452    !   bm_to_litter(:,:,:) = zero
4453    nep_daily(:,:) = zero
4454    nep_monthly(:,:) = zero
4455    turnover_daily(:,:,:,:) = zero
4456    resp_hetero_d(:,:) = zero
4457    tot_soil_resp_d(:,:) = zero
4458    cflux_prod_monthly(:) = zero
4459    harvest_above_monthly(:) = zero
4460    control_moist_above_daily(:,:) = zero
4461    control_moist_soil_daily(:,:,:) = zero
4462    moist_soil_daily(:,:) = zero
4463    soil_mc_Cforcing_daily(:,:,:) = zero
4464    floodout_Cforcing_daily(:) = zero
4465    wat_flux0_Cforcing_daily(:,:) = zero
4466    wat_flux_Cforcing_daily(:,:,:) = zero
4467    runoff_per_soil_Cforcing_daily(:,:) = zero
4468    drainage_per_soil_Cforcing_daily(:,:) = zero
4469    DOC_to_topsoil_Cforcing_daily(:,:) = zero
4470    DOC_to_subsoil_Cforcing_daily(:,:) = zero
4471    precip2canopy_Cforcing_daily(:,:) = zero
4472    precip2ground_Cforcing_daily(:,:) = zero
4473    canopy2ground_Cforcing_daily(:,:) = zero 
4474    flood_frac_Cforcing_daily(:) = zero
4475    control_temp_above_daily(:,:) = zero
4476    control_temp_soil_daily(:,:,:) = zero
4477    soilcarbon_input_daily(:,:,:,:,:) = zero   
4478    ! Land cover change variables
4479    prod10(:,:)  = zero
4480    prod100(:,:) = zero
4481    flux10(:,:)  = zero
4482    flux100(:,:) = zero
4483    convflux(:)  = zero
4484    cflux_prod10(:) = zero
4485    cflux_prod100(:) = zero
4486    prod10_harvest(:,:)  = zero
4487    prod100_harvest(:,:) = zero
4488    flux10_harvest(:,:)  = zero
4489    flux100_harvest(:,:) = zero
4490    convflux_harvest(:)  = zero
4491    cflux_prod10_harvest(:) = zero
4492    cflux_prod100_harvest(:) = zero
4493    woodharvestpft(:,:) = zero
4494    fpc_max(:,:)=zero
4495 
4496    convfluxpft(:,:)=zero
4497    fDeforestToProduct(:,:)=zero
4498    fLulccResidue(:,:)=zero
4499    fHarvestToProduct(:,:)=zero
4500  END SUBROUTINE stomate_init
4501
4502
4503!! ================================================================================================================================
4504!! SUBROUTINE   : stomate_clear
4505!!
4506!>\BRIEF        Deallocate memory of the stomate variables.
4507!!
4508!! DESCRIPTION  : None
4509!!
4510!! RECENT CHANGE(S) : None
4511!!
4512!! MAIN OUTPUT VARIABLE(S): None
4513!!
4514!! REFERENCES   : None
4515!!
4516!! FLOWCHART    : None
4517!! \n
4518!_ ================================================================================================================================
4519 
4520  SUBROUTINE stomate_clear
4521
4522  !! 1. Deallocate all dynamics variables
4523
4524    IF (ALLOCATED(veget_cov_max)) DEALLOCATE(veget_cov_max)
4525    IF (ALLOCATED(ind)) DEALLOCATE(ind)
4526    IF (ALLOCATED(adapted)) DEALLOCATE(adapted)
4527    IF (ALLOCATED(regenerate)) DEALLOCATE(regenerate)
4528    IF (ALLOCATED(humrel_daily)) DEALLOCATE(humrel_daily)
4529    IF (ALLOCATED(gdd_init_date)) DEALLOCATE(gdd_init_date)
4530    IF (ALLOCATED(litterhum_daily)) DEALLOCATE(litterhum_daily)
4531    IF (ALLOCATED(t2m_daily))  DEALLOCATE(t2m_daily)
4532    IF (ALLOCATED(t2m_min_daily))  DEALLOCATE(t2m_min_daily)
4533    IF (ALLOCATED(tsurf_daily))  DEALLOCATE(tsurf_daily)
4534    IF (ALLOCATED(tsoil_daily)) DEALLOCATE(tsoil_daily)
4535    IF (ALLOCATED(soilhum_daily)) DEALLOCATE(soilhum_daily)
4536    IF (ALLOCATED(precip_daily)) DEALLOCATE(precip_daily)
4537    IF (ALLOCATED(gpp_daily)) DEALLOCATE(gpp_daily)
4538    IF (ALLOCATED(npp_daily)) DEALLOCATE(npp_daily)
4539    IF (ALLOCATED(turnover_daily)) DEALLOCATE(turnover_daily)
4540    IF (ALLOCATED(turnover_littercalc)) DEALLOCATE(turnover_littercalc)
4541    IF (ALLOCATED(humrel_month)) DEALLOCATE(humrel_month)
4542    IF (ALLOCATED(humrel_week)) DEALLOCATE(humrel_week)
4543    IF (ALLOCATED(t2m_longterm)) DEALLOCATE(t2m_longterm)
4544    IF (ALLOCATED(t2m_month)) DEALLOCATE(t2m_month)
4545    IF (ALLOCATED(Tseason)) DEALLOCATE(Tseason)
4546    IF (ALLOCATED(Tseason_length)) DEALLOCATE(Tseason_length)
4547    IF (ALLOCATED(Tseason_tmp)) DEALLOCATE(Tseason_tmp)
4548    IF (ALLOCATED(Tmin_spring_time)) DEALLOCATE(Tmin_spring_time)
4549    IF (ALLOCATED(onset_date)) DEALLOCATE(onset_date)
4550    IF (ALLOCATED(begin_leaves)) DEALLOCATE(begin_leaves)
4551    IF (ALLOCATED(t2m_week)) DEALLOCATE(t2m_week)
4552    IF (ALLOCATED(tsoil_month)) DEALLOCATE(tsoil_month)
4553    IF (ALLOCATED(soilhum_month)) DEALLOCATE(soilhum_month)
4554    IF (ALLOCATED(fireindex)) DEALLOCATE(fireindex)
4555    IF (ALLOCATED(firelitter)) DEALLOCATE(firelitter)
4556    IF (ALLOCATED(maxhumrel_lastyear)) DEALLOCATE(maxhumrel_lastyear)
4557    IF (ALLOCATED(maxhumrel_thisyear)) DEALLOCATE(maxhumrel_thisyear)
4558    IF (ALLOCATED(minhumrel_lastyear)) DEALLOCATE(minhumrel_lastyear)
4559    IF (ALLOCATED(minhumrel_thisyear)) DEALLOCATE(minhumrel_thisyear)
4560    IF (ALLOCATED(maxgppweek_lastyear)) DEALLOCATE(maxgppweek_lastyear)
4561    IF (ALLOCATED(maxgppweek_thisyear)) DEALLOCATE(maxgppweek_thisyear)
4562    IF (ALLOCATED(gdd0_lastyear)) DEALLOCATE(gdd0_lastyear)
4563    IF (ALLOCATED(gdd0_thisyear)) DEALLOCATE(gdd0_thisyear)
4564    IF (ALLOCATED(precip_lastyear)) DEALLOCATE(precip_lastyear)
4565    IF (ALLOCATED(precip_thisyear)) DEALLOCATE(precip_thisyear)
4566    IF (ALLOCATED(gdd_m5_dormance)) DEALLOCATE(gdd_m5_dormance)
4567    IF (ALLOCATED(gdd_from_growthinit)) DEALLOCATE(gdd_from_growthinit)
4568    IF (ALLOCATED(gdd_midwinter)) DEALLOCATE(gdd_midwinter)
4569    IF (ALLOCATED(ncd_dormance)) DEALLOCATE(ncd_dormance)
4570    IF (ALLOCATED(ngd_minus5))  DEALLOCATE(ngd_minus5)
4571    IF (ALLOCATED(PFTpresent)) DEALLOCATE(PFTpresent)
4572    IF (ALLOCATED(npp_longterm)) DEALLOCATE(npp_longterm)
4573    IF (ALLOCATED(lm_lastyearmax)) DEALLOCATE(lm_lastyearmax)
4574    IF (ALLOCATED(lm_thisyearmax)) DEALLOCATE(lm_thisyearmax)
4575    IF (ALLOCATED(maxfpc_lastyear)) DEALLOCATE(maxfpc_lastyear)
4576    IF (ALLOCATED(maxfpc_thisyear)) DEALLOCATE(maxfpc_thisyear)
4577    IF (ALLOCATED(turnover_longterm)) DEALLOCATE(turnover_longterm)
4578    IF (ALLOCATED(gpp_week)) DEALLOCATE(gpp_week)
4579    IF (ALLOCATED(biomass)) DEALLOCATE(biomass)
4580    IF (ALLOCATED(senescence)) DEALLOCATE(senescence)
4581    IF (ALLOCATED(when_growthinit)) DEALLOCATE(when_growthinit)
4582    IF (ALLOCATED(age))  DEALLOCATE(age)
4583    IF (ALLOCATED(resp_hetero_d)) DEALLOCATE(resp_hetero_d)
4584    IF (ALLOCATED(tot_soil_resp_d)) DEALLOCATE(tot_soil_resp_d) 
4585    IF (ALLOCATED(resp_hetero_radia)) DEALLOCATE(resp_hetero_radia)
4586    IF (ALLOCATED(resp_maint_d)) DEALLOCATE(resp_maint_d)
4587    IF (ALLOCATED(resp_growth_d)) DEALLOCATE(resp_growth_d)
4588    IF (ALLOCATED(co2_fire)) DEALLOCATE(co2_fire)
4589    IF (ALLOCATED(co2_to_bm_dgvm)) DEALLOCATE(co2_to_bm_dgvm)
4590    IF (ALLOCATED(veget_lastlight)) DEALLOCATE(veget_lastlight)
4591    IF (ALLOCATED(everywhere)) DEALLOCATE(everywhere)
4592    IF (ALLOCATED(need_adjacent)) DEALLOCATE(need_adjacent)
4593    IF (ALLOCATED(leaf_age)) DEALLOCATE(leaf_age)
4594    IF (ALLOCATED(leaf_frac)) DEALLOCATE(leaf_frac)
4595    IF (ALLOCATED(RIP_time)) DEALLOCATE(RIP_time)
4596    IF (ALLOCATED(time_hum_min)) DEALLOCATE(time_hum_min)
4597    IF (ALLOCATED(hum_min_dormance)) DEALLOCATE(hum_min_dormance)
4598    IF (ALLOCATED(litterpart)) DEALLOCATE(litterpart)
4599!    IF (ALLOCATED(litter_above)) DEALLOCATE(litter_above)
4600!    IF (ALLOCATED(litter_below)) DEALLOCATE(litter_below)
4601    IF (ALLOCATED(dead_leaves)) DEALLOCATE(dead_leaves)
4602!    IF (ALLOCATED(carbon)) DEALLOCATE(carbon)
4603    IF (ALLOCATED(interception_storage)) DEALLOCATE(interception_storage) 
4604!    IF (ALLOCATED(lignin_struc_above)) DEALLOCATE(lignin_struc_above)
4605!    IF (ALLOCATED(lignin_struc_below)) DEALLOCATE(lignin_struc_below)
4606    IF (ALLOCATED(turnover_time)) DEALLOCATE(turnover_time)
4607    IF (ALLOCATED(nep_daily)) DEALLOCATE(nep_daily)
4608    IF (ALLOCATED(nep_monthly)) DEALLOCATE(nep_monthly)
4609    IF (ALLOCATED(harvest_above_monthly)) DEALLOCATE (harvest_above_monthly)
4610    IF (ALLOCATED(cflux_prod_monthly)) DEALLOCATE (cflux_prod_monthly)
4611    IF (ALLOCATED(bm_to_litter)) DEALLOCATE(bm_to_litter)
4612    IF (ALLOCATED(bm_to_littercalc)) DEALLOCATE(bm_to_littercalc)
4613    IF (ALLOCATED(herbivores)) DEALLOCATE(herbivores)
4614    IF (ALLOCATED(resp_maint_part_radia)) DEALLOCATE(resp_maint_part_radia)
4615    IF (ALLOCATED(resp_maint_radia)) DEALLOCATE(resp_maint_radia)
4616    IF (ALLOCATED(resp_maint_part)) DEALLOCATE(resp_maint_part)
4617    IF (ALLOCATED(hori_index)) DEALLOCATE(hori_index)
4618    IF (ALLOCATED(horipft_index)) DEALLOCATE(horipft_index)
4619    IF (ALLOCATED(clay_fm)) DEALLOCATE(clay_fm)
4620    IF (ALLOCATED(bulk_dens_fm)) DEALLOCATE(bulk_dens_fm)
4621    IF (ALLOCATED(soil_ph_fm)) DEALLOCATE(soil_ph_fm)
4622    IF (ALLOCATED(poor_soils_fm)) DEALLOCATE(poor_soils_fm)
4623    IF (ALLOCATED(humrel_daily_fm)) DEALLOCATE(humrel_daily_fm)
4624    IF (ALLOCATED(litterhum_daily_fm))  DEALLOCATE(litterhum_daily_fm)
4625    IF (ALLOCATED(t2m_daily_fm))  DEALLOCATE(t2m_daily_fm)
4626    IF (ALLOCATED(t2m_min_daily_fm))  DEALLOCATE(t2m_min_daily_fm)
4627    IF (ALLOCATED(tsurf_daily_fm)) DEALLOCATE(tsurf_daily_fm)
4628    IF (ALLOCATED(tsoil_daily_fm)) DEALLOCATE(tsoil_daily_fm)
4629    IF (ALLOCATED(soilhum_daily_fm))  DEALLOCATE(soilhum_daily_fm)
4630    IF (ALLOCATED(precip_fm)) DEALLOCATE(precip_fm)
4631    IF (ALLOCATED(gpp_daily_fm))  DEALLOCATE(gpp_daily_fm)
4632    IF (ALLOCATED(veget_fm)) DEALLOCATE(veget_fm)
4633    IF (ALLOCATED(veget_max_fm)) DEALLOCATE(veget_max_fm)
4634    IF (ALLOCATED(lai_fm))  DEALLOCATE(lai_fm)
4635    !
4636    IF (ALLOCATED(ok_equilibrium)) DEALLOCATE(ok_equilibrium)
4637    IF (ALLOCATED(carbon_eq)) DEALLOCATE(carbon_eq)
4638    IF (ALLOCATED(matrixA)) DEALLOCATE(matrixA)
4639    IF (ALLOCATED(vectorB)) DEALLOCATE(vectorB)
4640    IF (ALLOCATED(MatrixV)) DEALLOCATE(MatrixV)
4641    IF (ALLOCATED(VectorU)) DEALLOCATE(VectorU)
4642    IF (ALLOCATED(MatrixW)) DEALLOCATE(MatrixW)
4643    IF (ALLOCATED(previous_stock)) DEALLOCATE(previous_stock)
4644    IF (ALLOCATED(current_stock)) DEALLOCATE(current_stock) 
4645    IF (ALLOCATED(nbp_accu)) DEALLOCATE(nbp_accu)
4646    IF (ALLOCATED(nbp_flux)) DEALLOCATE(nbp_flux)
4647
4648    IF (ALLOCATED(clay_fm_g)) DEALLOCATE(clay_fm_g)
4649    IF (ALLOCATED(humrel_daily_fm_g)) DEALLOCATE(humrel_daily_fm_g)
4650    IF (ALLOCATED(litterhum_daily_fm_g))  DEALLOCATE(litterhum_daily_fm_g)
4651    IF (ALLOCATED(t2m_daily_fm_g))  DEALLOCATE(t2m_daily_fm_g)
4652    IF (ALLOCATED(t2m_min_daily_fm_g))  DEALLOCATE(t2m_min_daily_fm_g)
4653    IF (ALLOCATED(tsurf_daily_fm_g)) DEALLOCATE(tsurf_daily_fm_g)
4654    IF (ALLOCATED(tsoil_daily_fm_g)) DEALLOCATE(tsoil_daily_fm_g)
4655    IF (ALLOCATED(soilhum_daily_fm_g))  DEALLOCATE(soilhum_daily_fm_g)
4656    IF (ALLOCATED(precip_fm_g)) DEALLOCATE(precip_fm_g)
4657    IF (ALLOCATED(gpp_daily_fm_g))  DEALLOCATE(gpp_daily_fm_g)
4658    IF (ALLOCATED(veget_fm_g)) DEALLOCATE(veget_fm_g)
4659    IF (ALLOCATED(veget_max_fm_g)) DEALLOCATE(veget_max_fm_g)
4660    IF (ALLOCATED(lai_fm_g))  DEALLOCATE(lai_fm_g)
4661   
4662    IF (ALLOCATED(isf)) DEALLOCATE(isf)
4663    IF (ALLOCATED(nf_written)) DEALLOCATE(nf_written)
4664    IF (ALLOCATED(nf_cumul)) DEALLOCATE(nf_cumul)
4665    IF (ALLOCATED(nforce)) DEALLOCATE(nforce)
4666    IF (ALLOCATED(control_moist_above)) DEALLOCATE(control_moist_above)
4667    IF (ALLOCATED(control_moist_soil)) DEALLOCATE(control_moist_soil)
4668    IF (ALLOCATED(moist_soil)) DEALLOCATE(moist_soil)
4669    IF (ALLOCATED(soil_mc_Cforcing)) DEALLOCATE(soil_mc_Cforcing)
4670    IF (ALLOCATED(floodout_Cforcing)) DEALLOCATE(floodout_Cforcing)
4671    IF (ALLOCATED(wat_flux0_Cforcing)) DEALLOCATE(wat_flux0_Cforcing)
4672    IF (ALLOCATED(wat_flux_Cforcing)) DEALLOCATE(wat_flux_Cforcing)
4673    IF (ALLOCATED(runoff_per_soil_Cforcing)) DEALLOCATE(runoff_per_soil_Cforcing)
4674    IF (ALLOCATED(drainage_per_soil_Cforcing)) DEALLOCATE(drainage_per_soil_Cforcing)
4675    IF (ALLOCATED(DOC_to_topsoil_Cforcing)) DEALLOCATE(DOC_to_topsoil_Cforcing)
4676    IF (ALLOCATED(DOC_to_subsoil_Cforcing)) DEALLOCATE(DOC_to_subsoil_Cforcing)
4677    IF (ALLOCATED(precip2canopy_Cforcing)) DEALLOCATE(precip2canopy_Cforcing)
4678    IF (ALLOCATED(precip2ground_Cforcing)) DEALLOCATE(precip2ground_Cforcing)
4679    IF (ALLOCATED(canopy2ground_Cforcing)) DEALLOCATE(canopy2ground_Cforcing) 
4680    IF (ALLOCATED(flood_frac_Cforcing)) DEALLOCATE(flood_frac_Cforcing)
4681    IF (ALLOCATED(control_temp_above)) DEALLOCATE(control_temp_above)
4682    IF (ALLOCATED(control_temp_soil)) DEALLOCATE(control_temp_soil)
4683    IF (ALLOCATED(soilcarbon_input)) DEALLOCATE(soilcarbon_input)
4684    IF ( ALLOCATED (horip10_index)) DEALLOCATE (horip10_index)
4685    IF ( ALLOCATED (horip100_index)) DEALLOCATE (horip100_index)
4686    IF ( ALLOCATED (horip11_index)) DEALLOCATE (horip11_index)
4687    IF ( ALLOCATED (horip101_index)) DEALLOCATE (horip101_index)
4688    IF ( ALLOCATED (prod10)) DEALLOCATE (prod10)
4689    IF ( ALLOCATED (prod100)) DEALLOCATE (prod100)
4690    IF ( ALLOCATED (flux10)) DEALLOCATE (flux10)
4691    IF ( ALLOCATED (flux100)) DEALLOCATE (flux100)
4692    IF ( ALLOCATED (convflux)) DEALLOCATE (convflux)
4693    IF ( ALLOCATED (cflux_prod10)) DEALLOCATE (cflux_prod10)
4694    IF ( ALLOCATED (cflux_prod100)) DEALLOCATE (cflux_prod100)
4695    IF ( ALLOCATED (prod10_harvest)) DEALLOCATE (prod10_harvest)
4696    IF ( ALLOCATED (prod100_harvest)) DEALLOCATE (prod100_harvest)
4697    IF ( ALLOCATED (flux10_harvest)) DEALLOCATE (flux10_harvest)
4698    IF ( ALLOCATED (flux100_harvest)) DEALLOCATE (flux100_harvest)
4699    IF ( ALLOCATED (convflux_harvest)) DEALLOCATE (convflux_harvest)
4700    IF ( ALLOCATED (cflux_prod10_harvest)) DEALLOCATE (cflux_prod10_harvest)
4701    IF ( ALLOCATED (cflux_prod100_harvest)) DEALLOCATE (cflux_prod100_harvest)
4702    IF ( ALLOCATED (woodharvestpft)) DEALLOCATE (woodharvestpft)
4703    IF ( ALLOCATED (convfluxpft)) DEALLOCATE (convfluxpft)
4704    IF ( ALLOCATED (fDeforestToProduct)) DEALLOCATE (fDeforestToProduct)
4705    IF ( ALLOCATED (fLulccResidue)) DEALLOCATE (fLulccResidue)
4706    IF ( ALLOCATED (fHarvestToProduct)) DEALLOCATE (fHarvestToProduct)
4707    IF ( ALLOCATED (harvest_above)) DEALLOCATE (harvest_above)
4708    IF ( ALLOCATED (soilcarbon_input_daily)) DEALLOCATE (soilcarbon_input_daily)
4709    IF ( ALLOCATED (control_temp_above_daily)) DEALLOCATE (control_temp_above_daily)
4710    IF ( ALLOCATED (control_temp_soil_daily)) DEALLOCATE (control_temp_soil_daily)
4711    IF ( ALLOCATED (control_moist_above_daily)) DEALLOCATE (control_moist_above_daily)
4712    IF ( ALLOCATED (control_moist_soil_daily)) DEALLOCATE (control_moist_soil_daily)
4713    IF ( ALLOCATED (moist_soil_daily)) DEALLOCATE (moist_soil_daily)
4714    IF ( ALLOCATED (soil_mc_Cforcing_daily)) DEALLOCATE (soil_mc_Cforcing_daily)
4715    IF (ALLOCATED(floodout_Cforcing_daily)) DEALLOCATE(floodout_Cforcing_daily)
4716    IF (ALLOCATED(wat_flux0_Cforcing_daily)) DEALLOCATE(wat_flux0_Cforcing_daily)
4717    IF (ALLOCATED(wat_flux_Cforcing_daily)) DEALLOCATE(wat_flux_Cforcing_daily)
4718    IF (ALLOCATED(runoff_per_soil_Cforcing_daily)) DEALLOCATE(runoff_per_soil_Cforcing_daily)
4719    IF (ALLOCATED(drainage_per_soil_Cforcing_daily)) DEALLOCATE(drainage_per_soil_Cforcing_daily)
4720    IF (ALLOCATED(DOC_to_topsoil_Cforcing_daily)) DEALLOCATE(DOC_to_topsoil_Cforcing_daily)
4721    IF (ALLOCATED(DOC_to_subsoil_Cforcing_daily)) DEALLOCATE(DOC_to_subsoil_Cforcing_daily)
4722    IF (ALLOCATED(precip2canopy_Cforcing_daily)) DEALLOCATE(precip2canopy_Cforcing_daily)
4723    IF (ALLOCATED(precip2ground_Cforcing_daily)) DEALLOCATE(precip2ground_Cforcing_daily)
4724    IF (ALLOCATED(canopy2ground_Cforcing_daily)) DEALLOCATE(canopy2ground_Cforcing_daily)
4725    IF (ALLOCATED(flood_frac_Cforcing_daily)) DEALLOCATE(flood_frac_Cforcing_daily)
4726    IF ( ALLOCATED (fpc_max)) DEALLOCATE (fpc_max)
4727    IF (ALLOCATED(litter_above_Cforcing)) DEALLOCATE(litter_above_Cforcing)
4728    IF (ALLOCATED(litter_below_Cforcing)) DEALLOCATE(litter_below_Cforcing)
4729    IF (ALLOCATED(lignin_struc_above_Cforcing)) DEALLOCATE(lignin_struc_above_Cforcing)
4730    IF (ALLOCATED(lignin_struc_below_Cforcing)) DEALLOCATE(lignin_struc_below_Cforcing)
4731
4732 !! 2. reset l_first
4733
4734    l_first_stomate=.TRUE.
4735
4736 !! 3. call to clear functions
4737
4738    CALL season_clear
4739    CALL stomatelpj_clear
4740    CALL littercalc_clear
4741    CALL vmax_clear
4742 
4743  END SUBROUTINE stomate_clear
4744
4745
4746!! ================================================================================================================================
4747!! SUBROUTINE   : stomate_var_init
4748!!
4749!>\BRIEF        Initialize variables of stomate with a none-zero initial value.
4750!! Subroutine is called only if ::ok_stomate = .TRUE. STOMATE diagnoses some
4751!! variables for SECHIBA : assim_param, deadleaf_cover, etc. These variables can
4752!! be recalculated from STOMATE's prognostic variables. Note that height is
4753!! saved in SECHIBA.
4754!!
4755!! DESCRIPTION  : None
4756!!
4757!! RECENT CHANGE(S) : None
4758!!
4759!! MAIN OUTPUT VARIABLE(S): leaf age (::leaf_age) and fraction of leaves in leaf
4760!! age class (::leaf_frac). The maximum water on vegetation available for
4761!! interception, fraction of soil covered by dead leaves
4762!! (::deadleaf_cover) and assimilation parameters (:: assim_param).
4763!!
4764!! REFERENCE(S) : None
4765!!
4766!! FLOWCHART    : None
4767!! \n
4768!_ ================================================================================================================================
4769 
4770  SUBROUTINE stomate_var_init &
4771       &  (kjpindex, veget_cov_max, leaf_age, leaf_frac, &
4772       &   dead_leaves, &
4773       &   veget, lai, deadleaf_cover, assim_param)
4774
4775
4776  !! 0. Variable and parameter declaration
4777
4778    !! 0.1 Input variables
4779
4780    INTEGER(i_std),INTENT(in)                             :: kjpindex        !! Domain size - terrestrial pixels only
4781    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)        :: veget           !! Fraction of pixel covered by PFT. Fraction
4782                                                                             !! accounts for none-biological land covers
4783                                                                             !! (unitless)
4784    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)        :: veget_cov_max   !! Fractional coverage: maximum share of the pixel
4785                                                                             !! covered by a PFT (unitless)
4786    REAL(r_std),DIMENSION(kjpindex,nvm,nlitt),INTENT(in)  :: dead_leaves     !! Metabolic and structural fraction of dead leaves
4787                                                                             !! per ground area
4788                                                                             !! @tex $(gC m^{-2})$ @endtex
4789    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)        :: lai             !! Leaf area index
4790                                                                             !! @tex $(m^2 m{-2})$ @endtex
4791    REAL(r_std),DIMENSION(kjpindex,nvm,nleafages),INTENT(in) :: leaf_age     !! Age of different leaf classes per PFT (days)
4792    REAL(r_std),DIMENSION(kjpindex,nvm,nleafages),INTENT(in) :: leaf_frac    !! Fraction of leaves in leaf age class per PFT
4793                                                                             !! (unitless; 1)     
4794
4795    !! 0.2 Modified variables
4796    REAL(r_std),DIMENSION(kjpindex,nvm,npco2),INTENT(inout) :: assim_param   !! min+max+opt temperatures (K) & vmax for
4797                                                                             !! photosynthesis 
4798   
4799    !! 0.3 Output variables
4800
4801    REAL(r_std),DIMENSION(kjpindex), INTENT (out)         :: deadleaf_cover  !! Fraction of soil covered by dead leaves
4802                                                                             !! (unitless)
4803
4804
4805    ! 0.4 Local variables
4806   
4807    REAL(r_std),PARAMETER                                 :: dt_0 = zero     !! Dummy time step, must be zero
4808    REAL(r_std),DIMENSION(kjpindex,nvm)                   :: vcmax           !! Dummy vcmax
4809                                                                             !! @tex $(\mu mol m^{-2} s^{-1})$ @endtex
4810    REAL(r_std),DIMENSION(kjpindex,nvm,nleafages)         :: leaf_age_tmp    !! Temporary variable
4811    REAL(r_std),DIMENSION(kjpindex,nvm,nleafages)         :: leaf_frac_tmp   !! Temporary variable
4812                                                                             !! (unitless; 1)     
4813    INTEGER(i_std)                                        :: j               !! Index (untiless)
4814   
4815!_ ================================================================================================================================   
4816
4817
4818    ! Calculate assim_param if it was not found in the restart file
4819    IF (ALL(assim_param(:,:,:)==val_exp)) THEN
4820       ! Use temporary leaf_age_tmp and leaf_frac_tmp to preserve the input variables from being modified by the subroutine vmax.
4821       leaf_age_tmp(:,:,:)=leaf_age(:,:,:)
4822       leaf_frac_tmp(:,:,:)=leaf_frac(:,:,:)
4823
4824       !! 1.1 Calculate a temporary vcmax (stomate_vmax.f90)
4825       CALL vmax (kjpindex, dt_0, leaf_age_tmp, leaf_frac_tmp, vcmax )
4826
4827       !! 1.2 transform into nvm vegetation types
4828       assim_param(:,:,ivcmax) = zero
4829       DO j = 2, nvm
4830          assim_param(:,j,ivcmax)=vcmax(:,j)
4831       ENDDO
4832    END IF
4833   
4834    !! 2. Dead leaf cover (stomate_litter.f90)
4835    CALL deadleaf (kjpindex, veget_cov_max, dead_leaves, deadleaf_cover)     
4836   
4837  END SUBROUTINE stomate_var_init
4838
4839
4840!! ================================================================================================================================
4841!! INTERFACE    : stomate_accu
4842!!
4843!>\BRIEF        Accumulate a variable for the time period specified by
4844!! dt_sechiba or calculate the mean value over the period of dt_stomate
4845!!
4846!! DESCRIPTION : Accumulate a variable for the time period specified by
4847!! dt_sechiba or calculate the mean value over the period of dt_stomate.
4848!! stomate_accu interface can be used for variables having 1, 2 or 3 dimensions.
4849!! The corresponding subruoutine stomate_accu_r1d, stomate_accu_r2d or
4850!! stomate_accu_r3d will be selected through the interface depending on the number of dimensions.
4851!!
4852!! RECENT CHANGE(S) : None
4853!!
4854!! MAIN OUTPUT VARIABLE(S): accumulated or mean variable ::field_out::
4855!!
4856!! REFERENCE(S) : None
4857!!
4858!! FLOWCHART    : None
4859!! \n
4860!_ ================================================================================================================================
4861 
4862  SUBROUTINE stomate_accu_r1d (ldmean, field_in, field_out)
4863   
4864  !! 0. Variable and parameter declaration
4865
4866    !! 0.1 Input variables
4867    LOGICAL,INTENT(in)                     :: ldmean    !! Flag to calculate the mean over
4868    REAL(r_std),DIMENSION(:),INTENT(in)    :: field_in  !! Field that needs to be accumulated
4869   
4870    !! 0.2 Modified variables
4871    REAL(r_std),DIMENSION(:),INTENT(inout) :: field_out !! Accumulated or mean field
4872
4873!_ ================================================================================================================================
4874
4875  !! 1. Accumulate field
4876
4877    field_out(:) = field_out(:)+field_in(:)*dt_sechiba
4878   
4879  !! 2. Mean fields
4880
4881    IF (ldmean) THEN
4882       field_out(:) = field_out(:)/dt_stomate
4883    ENDIF
4884
4885  END SUBROUTINE stomate_accu_r1d
4886
4887  SUBROUTINE stomate_accu_r2d (ldmean, field_in, field_out)
4888   
4889  !! 0. Variable and parameter declaration
4890
4891    !! 0.1 Input variables
4892    LOGICAL,INTENT(in)                       :: ldmean    !! Flag to calculate the mean over
4893    REAL(r_std),DIMENSION(:,:),INTENT(in)    :: field_in  !! Field that needs to be accumulated
4894   
4895    !! 0.2 Modified variables
4896    REAL(r_std),DIMENSION(:,:),INTENT(inout) :: field_out !! Accumulated or mean field
4897
4898!_ ================================================================================================================================
4899
4900  !! 1. Accumulate field
4901
4902    field_out(:,:) = field_out(:,:)+field_in(:,:)*dt_sechiba
4903   
4904  !! 2. Mean fields
4905
4906    IF (ldmean) THEN
4907       field_out(:,:) = field_out(:,:)/dt_stomate
4908    ENDIF
4909
4910  END SUBROUTINE stomate_accu_r2d
4911
4912  SUBROUTINE stomate_accu_r3d (ldmean, field_in, field_out)
4913   
4914  !! 0. Variable and parameter declaration
4915
4916    !! 0.1 Input variables
4917    LOGICAL,INTENT(in)                         :: ldmean    !! Flag to calculate the mean over
4918    REAL(r_std),DIMENSION(:,:,:),INTENT(in)    :: field_in  !! Field that needs to be accumulated
4919   
4920    !! 0.2 Modified variables
4921    REAL(r_std),DIMENSION(:,:,:),INTENT(inout) :: field_out !! Accumulated or mean field
4922
4923!_ ================================================================================================================================
4924
4925  !! 1. Accumulate field
4926
4927    field_out(:,:,:) = field_out(:,:,:)+field_in(:,:,:)*dt_sechiba
4928   
4929  !! 2. Mean fields
4930
4931    IF (ldmean) THEN
4932       field_out(:,:,:) = field_out(:,:,:)/dt_stomate
4933    ENDIF
4934
4935  END SUBROUTINE stomate_accu_r3d
4936
4937!! ================================================================================================================================
4938!! SUBROUTINE   : init_forcing
4939!!
4940!>\BRIEF        Allocate memory for the variables containing the forcing data.
4941!! The maximum size of the allocated memory is specified in run definition file
4942!! (::max_totsize) and needs to be a compromise between charging the memory and
4943!! accessing disks to get the forcing data.
4944!!
4945!! DESCRIPTION : None
4946!!
4947!! RECENT CHANGE(S) : None
4948!!
4949!! MAIN OUTPUT VARIABLE(S): Strictly speaking the subroutine has no output
4950!! variables. However, the routine allocates memory for later use.
4951!!
4952!! REFERENCE(S) : None
4953!!
4954!! FLOWCHART    : None
4955!! \n
4956!_ ================================================================================================================================
4957 
4958  SUBROUTINE init_forcing (kjpindex,nsfm,nsft_loc)
4959   
4960  !! 0. Variable and parameter declaration
4961
4962    !! 0.1 Input variables
4963    INTEGER(i_std),INTENT(in) :: kjpindex !! Domain size - terrestrial pixels only (unitless)
4964    INTEGER(i_std),INTENT(in) :: nsfm     !! Number of time steps that can be stored in memory (unitless)
4965    INTEGER(i_std),INTENT(in) :: nsft_loc !! Number of time steps in a year (unitless)
4966
4967   !! 0.2 Output variables
4968
4969   !! 0.3 Modified variables
4970
4971   !! 0.4 Local variables
4972
4973    LOGICAL                   :: l_error  !! Check errors in netcdf call
4974    INTEGER(i_std)            :: ier      !! Check errors in netcdf call
4975!_ ================================================================================================================================
4976   
4977  !! 1. Allocate memory
4978
4979    ! Note ::nvm is number of PFTs and ::nslm is number of soil layers
4980    l_error = .FALSE.
4981    ALLOCATE(clay_fm(kjpindex,nsfm),stat=ier)
4982    l_error = l_error .OR. (ier /= 0)
4983    IF (l_error) THEN
4984       WRITE(numout,*) 'Problem with memory allocation: forcing variables clay_fm ',kjpindex,nsfm
4985       STOP 'init_forcing'
4986    ENDIF
4987    ALLOCATE(soil_ph_fm(kjpindex,nsfm),stat=ier)
4988    l_error = l_error .OR. (ier /= 0)
4989    IF (l_error) THEN
4990       WRITE(numout,*) 'Problem with memory allocation: forcing variables soil_ph_fm ',kjpindex,nsfm
4991       STOP 'init_forcing'
4992    ENDIF
4993    ALLOCATE(poor_soils_fm(kjpindex,nsfm),stat=ier)
4994    l_error = l_error .OR. (ier /= 0)
4995    IF (l_error) THEN
4996       WRITE(numout,*) 'Problem with memory allocation: forcing variables poor_soils_fm ',kjpindex,nsfm
4997       STOP 'init_forcing'
4998    ENDIF
4999    ALLOCATE(bulk_dens_fm(kjpindex,nsfm),stat=ier)
5000    l_error = l_error .OR. (ier /= 0)
5001    IF (l_error) THEN
5002       WRITE(numout,*) 'Problem with memory allocation: forcing variables bulk_dens_fm ',kjpindex,nsfm
5003       STOP 'init_forcing'
5004    ENDIF
5005    ALLOCATE(humrel_daily_fm(kjpindex,nvm,nsfm),stat=ier)
5006    l_error = l_error .OR. (ier /= 0)
5007    IF (l_error) THEN
5008       WRITE(numout,*) 'Problem with memory allocation: forcing variables humrel_daily_fm ',kjpindex,nvm,nsfm
5009       STOP 'init_forcing'
5010    ENDIF
5011    ALLOCATE(litterhum_daily_fm(kjpindex,nsfm),stat=ier)
5012    l_error = l_error .OR. (ier /= 0)
5013    IF (l_error) THEN
5014       WRITE(numout,*) 'Problem with memory allocation: forcing variables litterhum_daily_fm ',kjpindex,nsfm
5015       STOP 'init_forcing'
5016    ENDIF
5017    ALLOCATE(t2m_daily_fm(kjpindex,nsfm),stat=ier)
5018    l_error = l_error .OR. (ier /= 0)
5019    IF (l_error) THEN
5020       WRITE(numout,*) 'Problem with memory allocation: forcing variables t2m_daily_fm ',kjpindex,nsfm
5021       STOP 'init_forcing'
5022    ENDIF
5023    ALLOCATE(t2m_min_daily_fm(kjpindex,nsfm),stat=ier)
5024    l_error = l_error .OR. (ier /= 0)
5025    IF (l_error) THEN
5026       WRITE(numout,*) 'Problem with memory allocation: forcing variables t2m_min_daily_fm ',kjpindex,nsfm
5027       STOP 'init_forcing'
5028    ENDIF
5029    ALLOCATE(tsurf_daily_fm(kjpindex,nsfm),stat=ier)
5030    l_error = l_error .OR. (ier /= 0)
5031    IF (l_error) THEN
5032       WRITE(numout,*) 'Problem with memory allocation: forcing variables tsurf_daily_fm ',kjpindex,nsfm
5033       STOP 'init_forcing'
5034    ENDIF
5035    ALLOCATE(tsoil_daily_fm(kjpindex,nslm,nsfm),stat=ier)
5036    l_error = l_error .OR. (ier /= 0)
5037    IF (l_error) THEN
5038       WRITE(numout,*) 'Problem with memory allocation: forcing variables tsoil_daily_fm ',kjpindex,nslm,nsfm
5039       STOP 'init_forcing'
5040    ENDIF
5041    ALLOCATE(soilhum_daily_fm(kjpindex,nslm,nsfm),stat=ier)
5042    l_error = l_error .OR. (ier /= 0)
5043    IF (l_error) THEN
5044       WRITE(numout,*) 'Problem with memory allocation: forcing variables soilhum_daily_fm ',kjpindex,nslm,nsfm
5045       STOP 'init_forcing'
5046    ENDIF
5047    ALLOCATE(precip_fm(kjpindex,nsfm),stat=ier)
5048    l_error = l_error .OR. (ier /= 0)
5049    IF (l_error) THEN
5050       WRITE(numout,*) 'Problem with memory allocation: forcing variables precip_fm ',kjpindex,nsfm
5051       STOP 'init_forcing'
5052    ENDIF
5053    ALLOCATE(gpp_daily_fm(kjpindex,nvm,nsfm),stat=ier)
5054    l_error = l_error .OR. (ier /= 0)
5055    IF (l_error) THEN
5056       WRITE(numout,*) 'Problem with memory allocation: forcing variables gpp_daily_fm ',kjpindex,nvm,nsfm
5057       STOP 'init_forcing'
5058    ENDIF
5059    ALLOCATE(veget_fm(kjpindex,nvm,nsfm),stat=ier)
5060    l_error = l_error .OR. (ier /= 0)
5061    IF (l_error) THEN
5062       WRITE(numout,*) 'Problem with memory allocation: forcing variables veget_fm ',kjpindex,nvm,nsfm
5063       STOP 'init_forcing'
5064    ENDIF
5065    ALLOCATE(veget_max_fm(kjpindex,nvm,nsfm),stat=ier)
5066    l_error = l_error .OR. (ier /= 0)
5067    IF (l_error) THEN
5068       WRITE(numout,*) 'Problem with memory allocation: forcing variables veget_max_fm ',kjpindex,nvm,nsfm
5069       STOP 'init_forcing'
5070    ENDIF
5071    ALLOCATE(lai_fm(kjpindex,nvm,nsfm),stat=ier)
5072    l_error = l_error .OR. (ier /= 0)
5073    IF (l_error) THEN
5074       WRITE(numout,*) 'Problem with memory allocation: forcing variables lai_fm ',kjpindex,nvm,nsfm
5075       STOP 'init_forcing'
5076    ENDIF
5077    ALLOCATE(isf(nsfm),stat=ier)
5078    l_error = l_error .OR. (ier /= 0)
5079    IF (l_error) THEN
5080       WRITE(numout,*) 'Problem with memory allocation: forcing variables isf ',nsfm
5081       STOP 'init_forcing'
5082    ENDIF
5083    ALLOCATE(nf_written(nsft_loc),stat=ier)
5084    l_error = l_error .OR. (ier /= 0)
5085    IF (l_error) THEN
5086       WRITE(numout,*) 'Problem with memory allocation: forcing variables nf_written ',nsft_loc
5087       STOP 'init_forcing'
5088    ENDIF
5089    ALLOCATE(nf_cumul(nsft_loc),stat=ier)
5090    l_error = l_error .OR. (ier /= 0)
5091    IF (l_error) THEN
5092       WRITE(numout,*) 'Problem with memory allocation: forcing variables nf_cumul ',nsft_loc
5093       STOP 'init_forcing'
5094    ENDIF
5095   
5096  !! 2. Allocate memory for the root processor only (parallel computing)
5097
5098    ! Where, ::nbp_glo is the number of global continental points
5099    IF (is_root_prc) THEN
5100       ALLOCATE(clay_fm_g(nbp_glo,nsfm),stat=ier)
5101       l_error = l_error .OR. (ier /= 0)
5102       IF (l_error) THEN
5103          WRITE(numout,*) 'Problem with memory allocation: forcing variables clay_fm_g ',nbp_glo,nsfm
5104          STOP 'init_forcing'
5105       ENDIF
5106       ALLOCATE(soil_ph_fm_g(nbp_glo,nsfm),stat=ier)
5107       l_error = l_error .OR. (ier /= 0)
5108       IF (l_error) THEN
5109          WRITE(numout,*) 'Problem with memory allocation: forcing variables soil_ph_fm_g ',nbp_glo,nsfm
5110          STOP 'init_forcing'
5111       ENDIF
5112       ALLOCATE(poor_soils_fm_g(nbp_glo,nsfm),stat=ier)
5113       l_error = l_error .OR. (ier /= 0)
5114       IF (l_error) THEN
5115          WRITE(numout,*) 'Problem with memory allocation: forcing variables poor_soils_fm_g ',nbp_glo,nsfm
5116          STOP 'init_forcing'
5117       ENDIF
5118       ALLOCATE(bulk_dens_fm_g(nbp_glo,nsfm),stat=ier)
5119       l_error = l_error .OR. (ier /= 0)
5120       IF (l_error) THEN
5121          WRITE(numout,*) 'Problem with memory allocation: forcing variables bulk_dens_fm_g ',nbp_glo,nsfm
5122          STOP 'init_forcing'
5123       ENDIF       
5124       ALLOCATE(humrel_daily_fm_g(nbp_glo,nvm,nsfm),stat=ier)
5125       l_error = l_error .OR. (ier /= 0)
5126       IF (l_error) THEN
5127          WRITE(numout,*) 'Problem with memory allocation: forcing variables humrel_daily_fm_g ',nbp_glo,nvm,nsfm
5128          STOP 'init_forcing'
5129       ENDIF
5130       ALLOCATE(litterhum_daily_fm_g(nbp_glo,nsfm),stat=ier)
5131       l_error = l_error .OR. (ier /= 0)
5132       IF (l_error) THEN
5133          WRITE(numout,*) 'Problem with memory allocation: forcing variables litterhum_daily_fm_g ',nbp_glo,nsfm
5134          STOP 'init_forcing'
5135       ENDIF
5136       ALLOCATE(t2m_daily_fm_g(nbp_glo,nsfm),stat=ier)
5137       l_error = l_error .OR. (ier /= 0)
5138       IF (l_error) THEN
5139          WRITE(numout,*) 'Problem with memory allocation: forcing variables t2m_daily_fm_g ',nbp_glo,nsfm
5140          STOP 'init_forcing'
5141       ENDIF
5142       ALLOCATE(t2m_min_daily_fm_g(nbp_glo,nsfm),stat=ier)
5143       l_error = l_error .OR. (ier /= 0)
5144       IF (l_error) THEN
5145          WRITE(numout,*) 'Problem with memory allocation: forcing variables t2m_min_daily_fm_g ',nbp_glo,nsfm
5146          STOP 'init_forcing'
5147       ENDIF
5148       ALLOCATE(tsurf_daily_fm_g(nbp_glo,nsfm),stat=ier)
5149       l_error = l_error .OR. (ier /= 0)
5150       IF (l_error) THEN
5151          WRITE(numout,*) 'Problem with memory allocation: forcing variables tsurf_daily_fm_g ',nbp_glo,nsfm
5152          STOP 'init_forcing'
5153       ENDIF
5154       ALLOCATE(tsoil_daily_fm_g(nbp_glo,nslm,nsfm),stat=ier)
5155       l_error = l_error .OR. (ier /= 0)
5156       IF (l_error) THEN
5157          WRITE(numout,*) 'Problem with memory allocation: forcing variables tsoil_daily_fm_g ',nbp_glo,nslm,nsfm
5158          STOP 'init_forcing'
5159       ENDIF
5160       ALLOCATE(soilhum_daily_fm_g(nbp_glo,nslm,nsfm),stat=ier)
5161       l_error = l_error .OR. (ier /= 0)
5162       IF (l_error) THEN
5163          WRITE(numout,*) 'Problem with memory allocation: forcing variables soilhum_daily_fm_g ',nbp_glo,nslm,nsfm
5164          STOP 'init_forcing'
5165       ENDIF
5166       ALLOCATE(precip_fm_g(nbp_glo,nsfm),stat=ier)
5167       l_error = l_error .OR. (ier /= 0)
5168       IF (l_error) THEN
5169          WRITE(numout,*) 'Problem with memory allocation: forcing variables precip_fm_g ',nbp_glo,nsfm
5170          STOP 'init_forcing'
5171       ENDIF
5172       ALLOCATE(gpp_daily_fm_g(nbp_glo,nvm,nsfm),stat=ier)
5173       l_error = l_error .OR. (ier /= 0)
5174       IF (l_error) THEN
5175          WRITE(numout,*) 'Problem with memory allocation: forcing variables gpp_daily_fm_g ',nbp_glo,nvm,nsfm
5176          STOP 'init_forcing'
5177       ENDIF
5178       ALLOCATE(veget_fm_g(nbp_glo,nvm,nsfm),stat=ier)
5179       l_error = l_error .OR. (ier /= 0)
5180       IF (l_error) THEN
5181          WRITE(numout,*) 'Problem with memory allocation: forcing variables veget_fm_g ',nbp_glo,nvm,nsfm
5182          STOP 'init_forcing'
5183       ENDIF
5184       ALLOCATE(veget_max_fm_g(nbp_glo,nvm,nsfm),stat=ier)
5185       l_error = l_error .OR. (ier /= 0)
5186       IF (l_error) THEN
5187          WRITE(numout,*) 'Problem with memory allocation: forcing variables veget_max_fm_g ',nbp_glo,nvm,nsfm
5188          STOP 'init_forcing'
5189       ENDIF
5190       ALLOCATE(lai_fm_g(nbp_glo,nvm,nsfm),stat=ier)
5191       l_error = l_error .OR. (ier /= 0)
5192       IF (l_error) THEN
5193          WRITE(numout,*) 'Problem with memory allocation: forcing variables lai_fm_g ',nbp_glo,nvm,nsfm
5194          STOP 'init_forcing'
5195       ENDIF
5196    ELSE
5197       ! Allocate memory for co-processors
5198       ALLOCATE(clay_fm_g(0,nsfm),stat=ier)
5199       ALLOCATE(soil_ph_fm_g(0,nsfm),stat=ier)
5200       ALLOCATE(poor_soils_fm_g(0,nsfm),stat=ier)
5201       ALLOCATE(bulk_dens_fm_g(0,nsfm),stat=ier)
5202       ALLOCATE(humrel_daily_fm_g(0,nvm,nsfm),stat=ier)
5203       ALLOCATE(litterhum_daily_fm_g(0,nsfm),stat=ier)
5204       ALLOCATE(t2m_daily_fm_g(0,nsfm),stat=ier)
5205       ALLOCATE(t2m_min_daily_fm_g(0,nsfm),stat=ier)
5206       ALLOCATE(tsurf_daily_fm_g(0,nsfm),stat=ier)
5207       ALLOCATE(tsoil_daily_fm_g(0,nslm,nsfm),stat=ier)
5208       ALLOCATE(soilhum_daily_fm_g(0,nslm,nsfm),stat=ier)
5209       ALLOCATE(precip_fm_g(0,nsfm),stat=ier)
5210       ALLOCATE(gpp_daily_fm_g(0,nvm,nsfm),stat=ier)
5211       ALLOCATE(veget_fm_g(0,nvm,nsfm),stat=ier)
5212       ALLOCATE(veget_max_fm_g(0,nvm,nsfm),stat=ier)
5213       ALLOCATE(lai_fm_g(0,nvm,nsfm),stat=ier)
5214    ENDIF ! is_root_proc
5215   
5216    IF (l_error) THEN
5217       WRITE(numout,*) 'Problem with memory allocation: forcing variables'
5218       STOP 'init_forcing'
5219    ENDIF
5220
5221  !! 3. Initilaize variables
5222
5223    CALL forcing_zero
5224   
5225  END SUBROUTINE init_forcing
5226
5227
5228!! ================================================================================================================================
5229!! SUBROUTINE   : forcing_zero
5230!!
5231!>\BRIEF        Initialize variables containing the forcing data; variables are
5232!! set to zero.
5233!!
5234!! DESCRIPTION  : None
5235!!
5236!! RECENT CHANGE(S) : None
5237!!
5238!! MAIN OUTPUT VARIABLE(S): None
5239!!
5240!! REFERENCES   : None
5241!!
5242!! FLOWCHART    : None
5243!! \n
5244!_ ================================================================================================================================
5245 
5246  SUBROUTINE forcing_zero
5247   
5248    clay_fm(:,:) = zero
5249    soil_ph_fm(:,:) = zero
5250    poor_soils_fm(:,:) = zero
5251    bulk_dens_fm(:,:) = zero   
5252    humrel_daily_fm(:,:,:) = zero
5253    litterhum_daily_fm(:,:) = zero
5254    t2m_daily_fm(:,:) = zero
5255    t2m_min_daily_fm(:,:) = zero
5256    tsurf_daily_fm(:,:) = zero
5257    tsoil_daily_fm(:,:,:) = zero
5258    soilhum_daily_fm(:,:,:) = zero
5259    precip_fm(:,:) = zero
5260    gpp_daily_fm(:,:,:) = zero
5261    veget_fm(:,:,:) = zero
5262    veget_max_fm(:,:,:) = zero
5263    lai_fm(:,:,:) = zero
5264   
5265  END SUBROUTINE forcing_zero
5266
5267
5268!! ================================================================================================================================
5269!! SUBROUTINE   : forcing_write
5270!!
5271!>\BRIEF        Appends data values to a netCDF file containing the forcing
5272!! variables of the general processes in stomate.
5273!!
5274!! DESCRIPTION  : None
5275!!
5276!! RECENT CHANGE(S) : None
5277!!
5278!! MAIN OUTPUT VARIABLE(S): netCDF file
5279!!
5280!! REFERENCES   : None
5281!!
5282!! FLOWCHART    : None
5283!! \n
5284!_ ================================================================================================================================
5285 
5286  SUBROUTINE forcing_write(forcing_id,ibeg,iend)
5287   
5288  !! 0. Variable and parameter declaration
5289
5290    !! 0.1 Input variables
5291
5292    INTEGER(i_std),INTENT(in)      :: forcing_id  !! File identifer of forcing file, assigned when netcdf is created
5293    INTEGER(i_std),INTENT(in)      :: ibeg, iend  !! First and last time step to be written
5294
5295    !! 0.2 Output variables
5296
5297    !! 0.3 Modified variables
5298
5299    !! 0.4 Local variables
5300
5301    INTEGER(i_std)                 :: ii          !! Index of isf where isf is the number of time steps that can be
5302                                                  !! stored in memory
5303    INTEGER(i_std)                 :: iblocks     !! Index of block that is written
5304    INTEGER(i_std)                 :: nblocks     !! Number of blocks that needs to be written
5305    INTEGER(i_std)                 :: ier         !! Check errors in netcdf call
5306    INTEGER(i_std),DIMENSION(0:2)  :: ifirst      !! First block in memory - changes with iblocks
5307    INTEGER(i_std),DIMENSION(0:2)  :: ilast       !! Last block in memory - changes with iblocks
5308    INTEGER(i_std),PARAMETER       :: ndm1 = 10   !! Maximum number of dimensions
5309    INTEGER(i_std),DIMENSION(ndm1) :: start       !! First block to write
5310    INTEGER(i_std)                 :: ndim        !! Dimensions of forcing to be added to the netCDF
5311    INTEGER(i_std),DIMENSION(ndm1) :: count_force !! Number of elements in each dimension 
5312    INTEGER(i_std)                 :: vid         !! Variable identifer of netCDF
5313!_ ================================================================================================================================
5314   
5315  !! 1. Determine number of blocks of forcing variables that are stored in memory
5316
5317    nblocks = 0
5318    ifirst(:) = 1
5319    ilast(:) = 1
5320    DO ii = ibeg, iend
5321       IF (     (nblocks /= 0) &
5322            &      .AND.(isf(ii) == isf(ilast(nblocks))+1)) THEN
5323          ! Last block found
5324          ilast(nblocks) = ii
5325       ELSE
5326          ! First block found
5327          nblocks = nblocks+1
5328          IF (nblocks > 2)  STOP 'Problem in forcing_write'
5329          ifirst(nblocks) = ii
5330          ilast(nblocks) = ii
5331       ENDIF
5332    ENDDO
5333
5334  !! 2. Gather distributed variables (parallel computing)
5335
5336    CALL gather(clay_fm,clay_fm_g)
5337    CALL gather(soil_ph_fm,soil_ph_fm_g)
5338    CALL gather(poor_soils_fm,poor_soils_fm_g)
5339    CALL gather(bulk_dens_fm,bulk_dens_fm_g)
5340    CALL gather(humrel_daily_fm,humrel_daily_fm_g)
5341    CALL gather(litterhum_daily_fm,litterhum_daily_fm_g)
5342    CALL gather(t2m_daily_fm,t2m_daily_fm_g)
5343    CALL gather(t2m_min_daily_fm,t2m_min_daily_fm_g)
5344    CALL gather(tsurf_daily_fm,tsurf_daily_fm_g)
5345    CALL gather(tsoil_daily_fm,tsoil_daily_fm_g)
5346    CALL gather(soilhum_daily_fm,soilhum_daily_fm_g)
5347    CALL gather(precip_fm,precip_fm_g)
5348    CALL gather(gpp_daily_fm,gpp_daily_fm_g)
5349    CALL gather(veget_fm,veget_fm_g)
5350    CALL gather(veget_max_fm,veget_max_fm_g)
5351    CALL gather(lai_fm,lai_fm_g)
5352 
5353 !! 3. Append data to netCDF file
5354   
5355    IF (is_root_prc) THEN
5356       ! The netCDF file has been created earlier in this module, a file ID is available
5357       ! and variables and dimensions have already been defined
5358       DO iblocks = 1, nblocks
5359          IF (ifirst(iblocks) /= ilast(iblocks)) THEN
5360             ndim = 2
5361             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5362             count_force(1:ndim) = SHAPE(clay_fm_g)
5363             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5364             ier = NF90_INQ_VARID (forcing_id,'clay',vid)
5365             ier = NF90_PUT_VAR (forcing_id,vid, &
5366                  &              clay_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
5367                  & start=start(1:ndim), count=count_force(1:ndim))
5368             ndim = 2
5369             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5370             count_force(1:ndim) = SHAPE(soil_ph_fm_g)
5371             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5372             ier = NF90_INQ_VARID (forcing_id,'soil_ph',vid)
5373             ier = NF90_PUT_VAR (forcing_id,vid, &
5374                  &              soil_ph_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
5375                  & start=start(1:ndim), count=count_force(1:ndim))
5376             ndim = 2
5377             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5378             count_force(1:ndim) = SHAPE(poor_soils_fm_g)
5379             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5380             ier = NF90_INQ_VARID (forcing_id,'poor_soils',vid)
5381             ier = NF90_PUT_VAR (forcing_id,vid, &
5382                  &              poor_soils_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
5383                  & start=start(1:ndim), count=count_force(1:ndim))
5384             ndim = 2
5385             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5386             count_force(1:ndim) = SHAPE(bulk_dens_fm_g)
5387             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5388             ier = NF90_INQ_VARID (forcing_id,'bulk_dens',vid)
5389             ier = NF90_PUT_VAR (forcing_id,vid, &
5390                  &              bulk_dens_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
5391                  & start=start(1:ndim), count=count_force(1:ndim))                               
5392             ndim = 3;
5393             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5394             count_force(1:ndim) = SHAPE(humrel_daily_fm_g)
5395             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5396             ier = NF90_INQ_VARID (forcing_id,'humrel',vid)
5397             ier = NF90_PUT_VAR (forcing_id, vid, &
5398                  &            humrel_daily_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
5399                  &            start=start(1:ndim), count=count_force(1:ndim))
5400             ndim = 2;
5401             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5402             count_force(1:ndim) = SHAPE(litterhum_daily_fm_g)
5403             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5404             ier = NF90_INQ_VARID (forcing_id,'litterhum',vid)
5405             ier = NF90_PUT_VAR (forcing_id, vid, &
5406                  &            litterhum_daily_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
5407                  & start=start(1:ndim), count=count_force(1:ndim))
5408             ndim = 2;
5409             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5410             count_force(1:ndim) = SHAPE(t2m_daily_fm_g)
5411             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5412             ier = NF90_INQ_VARID (forcing_id,'t2m',vid)
5413             ier = NF90_PUT_VAR (forcing_id, vid, &
5414                  &            t2m_daily_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
5415                  & start=start(1:ndim), count=count_force(1:ndim))
5416             ndim = 2;
5417             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5418             count_force(1:ndim) = SHAPE(t2m_min_daily_fm_g)
5419             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5420             ier = NF90_INQ_VARID (forcing_id,'t2m_min',vid)
5421             ier = NF90_PUT_VAR (forcing_id, vid, &
5422                  &            t2m_min_daily_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
5423                  & start=start(1:ndim), count=count_force(1:ndim))
5424             ndim = 2;
5425             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5426             count_force(1:ndim) = SHAPE(tsurf_daily_fm_g)
5427             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5428             ier = NF90_INQ_VARID (forcing_id,'tsurf',vid)
5429             ier = NF90_PUT_VAR (forcing_id, vid, &
5430                  &            tsurf_daily_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
5431                  & start=start(1:ndim), count=count_force(1:ndim))
5432             ndim = 3;
5433             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5434             count_force(1:ndim) = SHAPE(tsoil_daily_fm_g)
5435             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5436             ier = NF90_INQ_VARID (forcing_id,'tsoil',vid)
5437             ier = NF90_PUT_VAR (forcing_id, vid, &
5438                  &            tsoil_daily_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
5439                  & start=start(1:ndim), count=count_force(1:ndim))
5440             ndim = 3;
5441             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5442             count_force(1:ndim) = SHAPE(soilhum_daily_fm_g)
5443             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5444             ier = NF90_INQ_VARID (forcing_id,'soilhum',vid)
5445             ier = NF90_PUT_VAR (forcing_id, vid, &
5446                  &            soilhum_daily_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
5447                  & start=start(1:ndim), count=count_force(1:ndim))
5448             ndim = 2;
5449             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5450             count_force(1:ndim) = SHAPE(precip_fm_g)
5451             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5452             ier = NF90_INQ_VARID (forcing_id,'precip',vid)
5453             ier = NF90_PUT_VAR (forcing_id, vid, &
5454                  &            precip_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
5455                  & start=start(1:ndim), count=count_force(1:ndim))
5456             ndim = 3;
5457             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5458             count_force(1:ndim) = SHAPE(gpp_daily_fm_g)
5459             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5460             ier = NF90_INQ_VARID (forcing_id,'gpp',vid)
5461             ier = NF90_PUT_VAR (forcing_id, vid, &
5462                  &            gpp_daily_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
5463                  &            start=start(1:ndim), count=count_force(1:ndim))
5464             ndim = 3;
5465             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5466             count_force(1:ndim) = SHAPE(veget_fm_g)
5467             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5468             ier = NF90_INQ_VARID (forcing_id,'veget',vid)
5469             ier = NF90_PUT_VAR (forcing_id, vid, &
5470                  &            veget_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
5471                  &            start=start(1:ndim), count=count_force(1:ndim))
5472             ndim = 3;
5473             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5474             count_force(1:ndim) = SHAPE(veget_max_fm_g)
5475             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5476             ier = NF90_INQ_VARID (forcing_id,'veget_max',vid)
5477             ier = NF90_PUT_VAR (forcing_id, vid, &
5478                  &            veget_max_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
5479                  &            start=start(1:ndim), count=count_force(1:ndim))
5480             ndim = 3;
5481             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5482             count_force(1:ndim) = SHAPE(lai_fm_g)
5483             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5484             ier = NF90_INQ_VARID (forcing_id,'lai',vid)
5485             ier = NF90_PUT_VAR (forcing_id, vid, &
5486                  &            lai_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
5487                  &            start=start(1:ndim), count=count_force(1:ndim))
5488          ENDIF
5489       ENDDO
5490    ENDIF
5491   
5492  !! 4. Adjust flag of forcing file
5493    nf_written(isf(:)) = .TRUE.
5494
5495  END SUBROUTINE forcing_write
5496
5497 
5498!! ================================================================================================================================
5499!! SUBROUTINE   : stomate_forcing_read
5500!!
5501!>\BRIEF        Read forcing file.
5502!!
5503!! DESCRIPTION  : None
5504!!
5505!! RECENT CHANGE(S) : None
5506!!
5507!! MAIN OUTPUT VARIABLE(S): None
5508!!
5509!! REFERENCES   : None
5510!!
5511!! FLOWCHART    : None
5512!! \n
5513!_ ================================================================================================================================
5514 
5515  SUBROUTINE stomate_forcing_read(forcing_id,nsfm)
5516   
5517  !! 0. Variable and parameter declaration
5518
5519    !! 0.1 Input variables
5520
5521    INTEGER(i_std),INTENT(in)  :: forcing_id           !! File identifer of forcing file, assigned when netcdf is created
5522    INTEGER(i_std),INTENT(in)  :: nsfm                 !! Number of time steps stored in memory       
5523   
5524    !! 0.2 Output variables
5525
5526    !! 0.3 Modified variables
5527
5528    !! 0.4 Local variables
5529
5530    INTEGER(i_std)                 :: ii                !! Index of isf where isf is the number of time steps that can be stored in
5531                                                        !! memory
5532    INTEGER(i_std)                 :: iblocks           !! Index of block that is written
5533    INTEGER(i_std)                 :: nblocks           !! Number of blocks that needs to be written
5534    INTEGER(i_std)                 :: ier               !! Check error of netcdf call
5535    INTEGER(i_std),DIMENSION(0:2)  :: ifirst            !! First block in memory - changes with iblocks
5536    INTEGER(i_std),DIMENSION(0:2)  :: ilast             !! Last block in memory - changes with iblocks
5537    INTEGER(i_std),PARAMETER       :: ndm1 = 10          !! Maximum number of dimensions
5538    INTEGER(i_std),DIMENSION(ndm1) :: start             !! First block to write
5539    INTEGER(i_std)                 :: ndim              !! Dimensions of forcing to be added to the netCDF
5540    INTEGER(i_std),DIMENSION(ndm1) :: count_force       !! Number of elements in each dimension
5541    INTEGER(i_std)                 :: vid               !! Variable identifer of netCDF
5542    LOGICAL                        :: a_er=.FALSE.      !! Error catching from netcdf file
5543!_ ================================================================================================================================
5544
5545    IF (printlev >= 4) WRITE(numout,*) "stomate_forcing_read "
5546   
5547  !! 1. Set to zero if the corresponding forcing state
5548
5549    ! has not yet been written into the file 
5550    DO ii = 1, nsfm
5551       IF (.NOT.nf_written(isf(ii))) THEN
5552          clay_fm(:,ii) = zero
5553          soil_ph_fm(:,ii) = zero                 
5554          poor_soils_fm(:,ii) = zero
5555          bulk_dens_fm(:,ii) = zero               
5556          humrel_daily_fm(:,:,ii) = zero
5557          litterhum_daily_fm(:,ii) = zero
5558          t2m_daily_fm(:,ii) = zero
5559          t2m_min_daily_fm(:,ii) = zero
5560          tsurf_daily_fm(:,ii) = zero
5561          tsoil_daily_fm(:,:,ii) = zero
5562          soilhum_daily_fm(:,:,ii) = zero
5563          precip_fm(:,ii) = zero
5564          gpp_daily_fm(:,:,ii) = zero
5565          veget_fm(:,:,ii) = zero
5566          veget_max_fm(:,:,ii) = zero
5567          lai_fm(:,:,ii) = zero
5568       ENDIF
5569    ENDDO
5570   
5571  !! 2. determine blocks of forcing states that are contiguous in memory
5572
5573    nblocks = 0
5574    ifirst(:) = 1
5575    ilast(:) = 1
5576   
5577    DO ii = 1, nsfm
5578       IF (nf_written(isf(ii))) THEN
5579          IF (     (nblocks /= 0) &
5580               &        .AND.(isf(ii) == isf(ilast(nblocks))+1)) THEN
5581
5582             ! element is contiguous with last element found
5583             ilast(nblocks) = ii
5584          ELSE
5585
5586             ! found first element of new block
5587             nblocks = nblocks+1
5588             IF (nblocks > 2)  STOP 'Problem in stomate_forcing_read'
5589             
5590             ifirst(nblocks) = ii
5591             ilast(nblocks) = ii
5592          ENDIF
5593       ENDIF
5594    ENDDO
5595    IF (printlev >= 4) WRITE(numout,*) "stomate_forcing_read nblocks, ifirst, ilast",nblocks, ifirst, ilast
5596   
5597  !! 3. Read variable values
5598
5599    IF (is_root_prc) THEN
5600       DO iblocks = 1, nblocks
5601          IF (printlev >= 4) WRITE(numout,*) "stomate_forcing_read iblocks, ifirst(iblocks), ilast(iblocks)",iblocks, &
5602               ifirst(iblocks), ilast(iblocks)
5603          IF (ifirst(iblocks) /= ilast(iblocks)) THEN
5604             a_er=.FALSE.
5605             ndim = 2;
5606             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5607             count_force(1:ndim) = SHAPE(clay_fm_g)
5608             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5609             ier = NF90_INQ_VARID (forcing_id,'clay',vid)
5610             a_er = a_er.OR.(ier /= 0)
5611             ier = NF90_GET_VAR (forcing_id, vid, &
5612                  &            clay_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
5613                  &            start=start(1:ndim), count=count_force(1:ndim))
5614             a_er = a_er.OR.(ier /= 0)
5615                         
5616                         ndim = 2;
5617             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5618             count_force(1:ndim) = SHAPE(soil_ph_fm_g)
5619             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5620             ier = NF90_INQ_VARID (forcing_id,'soil_ph',vid)
5621             a_er = a_er.OR.(ier /= 0)
5622             ier = NF90_GET_VAR (forcing_id, vid, &
5623                  &            soil_ph_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
5624                  &            start=start(1:ndim), count=count_force(1:ndim))
5625             a_er = a_er.OR.(ier /= 0)
5626
5627             ndim = 2;
5628             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5629             count_force(1:ndim) = SHAPE(poor_soils_fm_g)
5630             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5631             ier = NF90_INQ_VARID (forcing_id,'poor_soils',vid)
5632             a_er = a_er.OR.(ier /= 0)
5633             ier = NF90_GET_VAR (forcing_id, vid, &
5634                  &            poor_soils_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
5635                  &            start=start(1:ndim), count=count_force(1:ndim))
5636             a_er = a_er.OR.(ier /= 0)
5637
5638             ndim = 2;
5639             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5640             count_force(1:ndim) = SHAPE(bulk_dens_fm_g)
5641             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5642             ier = NF90_INQ_VARID (forcing_id,'bulk_dens',vid)
5643             a_er = a_er.OR.(ier /= 0)
5644             ier = NF90_GET_VAR (forcing_id, vid, &
5645                  &            bulk_dens_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
5646                  &            start=start(1:ndim), count=count_force(1:ndim))
5647             a_er = a_er.OR.(ier /= 0)
5648                         
5649             ndim = 3;
5650             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5651             count_force(1:ndim) = SHAPE(humrel_daily_fm_g)
5652             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5653             ier = NF90_INQ_VARID (forcing_id,'humrel',vid)
5654             a_er = a_er.OR.(ier /= 0)
5655             ier = NF90_GET_VAR (forcing_id, vid, &
5656                  &            humrel_daily_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
5657                  &            start=start(1:ndim), count=count_force(1:ndim))
5658             a_er = a_er.OR.(ier /= 0)
5659
5660             ndim = 2;
5661             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5662             count_force(1:ndim) = SHAPE(litterhum_daily_fm_g)
5663             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5664             ier = NF90_INQ_VARID (forcing_id,'litterhum',vid)
5665             a_er = a_er.OR.(ier /= 0)
5666             ier = NF90_GET_VAR (forcing_id, vid, &
5667                  &              litterhum_daily_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
5668                  &            start=start(1:ndim), count=count_force(1:ndim))
5669             a_er = a_er.OR.(ier /= 0)
5670
5671             ndim = 2;
5672             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5673             count_force(1:ndim) = SHAPE(t2m_daily_fm_g)
5674             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5675             ier = NF90_INQ_VARID (forcing_id,'t2m',vid)
5676             a_er = a_er.OR.(ier /= 0)
5677             ier = NF90_GET_VAR (forcing_id, vid, &
5678                  &              t2m_daily_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
5679                  &            start=start(1:ndim), count=count_force(1:ndim))
5680             a_er = a_er.OR.(ier /= 0)
5681
5682             ndim = 2;
5683             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5684             count_force(1:ndim) = SHAPE(t2m_min_daily_fm_g)
5685             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5686             ier = NF90_INQ_VARID (forcing_id,'t2m_min',vid)
5687             a_er = a_er.OR.(ier /= 0)
5688             ier = NF90_GET_VAR (forcing_id, vid, &
5689                  &              t2m_min_daily_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
5690                  &            start=start(1:ndim), count=count_force(1:ndim))
5691             a_er = a_er.OR.(ier /= 0)
5692
5693             ndim = 2;
5694             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5695             count_force(1:ndim) = SHAPE(tsurf_daily_fm_g)
5696             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5697             ier = NF90_INQ_VARID (forcing_id,'tsurf',vid)
5698             a_er = a_er.OR.(ier /= 0)
5699             ier = NF90_GET_VAR (forcing_id, vid, &
5700                  &              tsurf_daily_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
5701                  &            start=start(1:ndim), count=count_force(1:ndim))
5702             a_er = a_er.OR.(ier /= 0)
5703
5704             ndim = 3;
5705             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5706             count_force(1:ndim) = SHAPE(tsoil_daily_fm_g)
5707             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5708             ier = NF90_INQ_VARID (forcing_id,'tsoil',vid)
5709             a_er = a_er.OR.(ier /= 0)
5710             ier = NF90_GET_VAR (forcing_id, vid, &
5711                  &              tsoil_daily_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
5712                  &            start=start(1:ndim), count=count_force(1:ndim))
5713             a_er = a_er.OR.(ier /= 0)
5714
5715             ndim = 3;
5716             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5717             count_force(1:ndim) = SHAPE(soilhum_daily_fm_g)
5718             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5719             ier = NF90_INQ_VARID (forcing_id,'soilhum',vid)
5720             a_er = a_er.OR.(ier /= 0)
5721             ier = NF90_GET_VAR (forcing_id, vid, &
5722                  &              soilhum_daily_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
5723                  &            start=start(1:ndim), count=count_force(1:ndim))
5724             a_er = a_er.OR.(ier /= 0)
5725
5726             ndim = 2;
5727             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5728             count_force(1:ndim) = SHAPE(precip_fm_g)
5729             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5730             ier = NF90_INQ_VARID (forcing_id,'precip',vid)
5731             a_er = a_er.OR.(ier /= 0)
5732             ier = NF90_GET_VAR (forcing_id, vid, &
5733                  &              precip_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
5734                  &            start=start(1:ndim), count=count_force(1:ndim))
5735             a_er = a_er.OR.(ier /= 0)
5736
5737             ndim = 3;
5738             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5739             count_force(1:ndim) = SHAPE(gpp_daily_fm_g)
5740             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5741             ier = NF90_INQ_VARID (forcing_id,'gpp',vid)
5742             a_er = a_er.OR.(ier /= 0)
5743             ier = NF90_GET_VAR (forcing_id, vid, &
5744                  &            gpp_daily_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
5745                  &            start=start(1:ndim), count=count_force(1:ndim))
5746             a_er = a_er.OR.(ier /= 0)
5747
5748             ndim = 3;
5749             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5750             count_force(1:ndim) = SHAPE(veget_fm_g)
5751             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5752             ier = NF90_INQ_VARID (forcing_id,'veget',vid)
5753             a_er = a_er.OR.(ier /= 0)
5754             ier = NF90_GET_VAR (forcing_id, vid, &
5755                  &            veget_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
5756                  &            start=start(1:ndim), count=count_force(1:ndim))
5757             a_er = a_er.OR.(ier /= 0)
5758
5759             ndim = 3;
5760             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5761             count_force(1:ndim) = SHAPE(veget_max_fm_g)
5762             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5763             ier = NF90_INQ_VARID (forcing_id,'veget_max',vid)
5764             a_er = a_er.OR.(ier /= 0)
5765             ier = NF90_GET_VAR (forcing_id, vid, &
5766                  &            veget_max_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
5767                  &            start=start(1:ndim), count=count_force(1:ndim))
5768             a_er = a_er.OR.(ier /= 0)
5769
5770             ndim = 3;
5771             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
5772             count_force(1:ndim) = SHAPE(lai_fm_g)
5773             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
5774             ier = NF90_INQ_VARID (forcing_id,'lai',vid)
5775             a_er = a_er.OR.(ier /= 0)
5776             ier = NF90_GET_VAR (forcing_id, vid, &
5777                  &            lai_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
5778                  &            start=start(1:ndim), count=count_force(1:ndim))
5779             a_er = a_er.OR.(ier /= 0)
5780             IF (a_er) THEN
5781                CALL ipslerr_p (3,'stomate_forcing_read', &
5782                     &        'PROBLEM when read forcing file', &
5783                     &        '','')
5784             ENDIF
5785
5786          ENDIF ! (ifirst(iblocks) /= ilast(iblocks))
5787       ENDDO ! iblocks
5788    ENDIF ! is_root_prc
5789
5790  !! 4. Distribute the variable over several processors
5791
5792    CALL scatter(clay_fm_g,clay_fm)
5793    CALL scatter(soil_ph_fm_g,soil_ph_fm)
5794    CALL scatter(poor_soils_fm_g,poor_soils_fm)
5795    CALL scatter(bulk_dens_fm_g,bulk_dens_fm)   
5796    CALL scatter(humrel_daily_fm_g,humrel_daily_fm)
5797    CALL scatter(litterhum_daily_fm_g,litterhum_daily_fm)
5798    CALL scatter(t2m_daily_fm_g,t2m_daily_fm)
5799    CALL scatter(t2m_min_daily_fm_g,t2m_min_daily_fm)
5800    CALL scatter(tsurf_daily_fm_g,tsurf_daily_fm)
5801    CALL scatter(tsoil_daily_fm_g,tsoil_daily_fm)
5802    CALL scatter(soilhum_daily_fm_g,soilhum_daily_fm)
5803    CALL scatter(precip_fm_g,precip_fm)
5804    CALL scatter(gpp_daily_fm_g,gpp_daily_fm)
5805    CALL scatter(veget_fm_g,veget_fm)
5806    CALL scatter(veget_max_fm_g,veget_max_fm)
5807    CALL scatter(lai_fm_g,lai_fm)
5808 
5809  END SUBROUTINE stomate_forcing_read
5810
5811
5812!! ================================================================================================================================
5813!! SUBROUTINE   : setlai
5814!!
5815!>\BRIEF        Routine to force the lai in STOMATE. The code in this routine
5816!! simply CALCULATES lai and is therefore not functional. The routine should be
5817!! rewritten if one wants to force lai.
5818!!
5819!! DESCRIPTION  : None
5820!!
5821!! RECENT CHANGE(S) : None
5822!!
5823!! MAIN OUTPUT VARIABLE(S): ::lai
5824!!
5825!! REFERENCE(S) : None
5826!!
5827!! FLOWCHART : None
5828!! \n
5829!_ ================================================================================================================================
5830 
5831  SUBROUTINE setlai(npts,lai)
5832
5833  !! 0 Variable and parameter declaration
5834 
5835    !! 0.1 Input variables
5836
5837    INTEGER(i_std),INTENT(in)                    :: npts !! Domain size - number of pixels (unitless)
5838   
5839    !! 0.2 Output variables
5840
5841    REAL(r_std),DIMENSION(npts,nvm),INTENT(out)  :: lai  !! PFT leaf area index @tex $(m^{2} m^{-2})$ @endtex
5842
5843    !! 0.3 Modified variables
5844
5845    !! 0.4 Local variables
5846
5847    INTEGER(i_std)                               :: j    !! index (unitless)
5848!_ ================================================================================================================================
5849   
5850    !! 1. Set lai for bare soil to zero
5851
5852    lai(:,ibare_sechiba) = zero
5853
5854    !! 2. Multiply foliage biomass by sla to calculate lai for all PFTs and pixels
5855
5856    DO j=2,nvm
5857       lai(:,j) = biomass(:,j,ileaf,icarbon)*sla(j)
5858    ENDDO
5859   
5860  END SUBROUTINE setlai
5861
5862END MODULE stomate
Note: See TracBrowser for help on using the repository browser.