source: branches/publications/ORCHIDEE_gmd-2018-261/src_stomate/stomate.f90 @ 7474

Last change on this file since 7474 was 4998, checked in by nicolas.vuichard, 7 years ago

rev29012018

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