source: branches/publications/ORCHIDEE-LEAK-r5919/src_stomate/stomate.f90 @ 5925

Last change on this file since 5925 was 5919, checked in by ronny.lauerwald, 5 years ago

ORCHILEAK, version used for trends and biases in NEE and NBP in the Amazon basin

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