source: branches/publications/ORCHIDEE_CN_CAN_r5698/src_stomate/stomate.f90 @ 7346

Last change on this file since 7346 was 5691, checked in by sebastiaan.luyssaert, 6 years ago

DEV: tested with 13, 37 and 64 PFTs with LCC on different pixels. Some configuration run for 20 years on a given pixel, other crash on another pixel. There is a mass balance problem in sapiens_lcc (ticket #482). This commit fixes a problem with PFT1 in littercalc. This PFT is now fully integrated in LCC and subsequent litter and soil dynamics. veget_max was changed in veget_cov_max where appropriate, a typo in enerbil was corrected.

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 341.4 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 vertical_soil_var
38  USE pft_parameters
39  USE structures
40  USE sapiens_forestry,   ONLY : read_in_fm_map, read_in_litter_map, &
41                                 read_in_species_change_map, &
42                                 read_in_desired_fm_map
43  USE stomate_io
44  USE stomate_data
45  USE stomate_season
46  USE stomate_lpj
47  USE stomate_litter
48  USE stomate_vmax
49  USE stomate_som_dynamics
50  USE stomate_resp
51  USE mod_orchidee_para
52  USE ioipsl_para 
53  USE xios_orchidee
54  USE function_library,   ONLY : check_biomass_sync, cc_to_lai, &
55                                 check_surface_area, check_mass_balance
56  USE matrix_resolution
57 
58  IMPLICIT NONE
59
60  ! Private & public routines
61
62  PRIVATE
63  PUBLIC stomate_main,stomate_clear,init_forcing, stomate_forcing_read, stomate_initialize, stomate_finalize, stomate_veget_update
64
65  INTERFACE stomate_accu 
66     MODULE PROCEDURE stomate_accu_r1d, stomate_accu_r2d, stomate_accu_r3d, stomate_accu_r4d
67  END INTERFACE
68
69  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: veget_cov_max        !! Maximal fractional coverage: maximum share of a pixel
70                                                                         !! taken by a PFT. Excluding no_bio fraction
71!$OMP THREADPRIVATE(veget_cov_max)
72
73  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: age                  !! Age of PFT it normalized by biomass - can increase and
74                                                                         !! decrease - (years)
75!$OMP THREADPRIVATE(age)
76  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: adapted              !! Winter too cold for PFT to survive (0-1, unitless)
77!$OMP THREADPRIVATE(adapted)
78  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: regenerate           !! Winter sufficiently cold to produce viable seeds
79                                                                         !! (0-1, unitless)
80!$OMP THREADPRIVATE(regenerate)
81  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: everywhere           !! Is the PFT everywhere in the grid box or very localized
82                                                                         !! (after its intoduction)
83!$OMP THREADPRIVATE(everywhere)
84  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: fireindex            !! Probability of fire (unitless)
85!$OMP THREADPRIVATE(fireindex)
86  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: veget_lastlight      !! Vegetation fractions (on ground) after last light
87                                                                         !! competition (unitless)
88!$OMP THREADPRIVATE(veget_lastlight)
89  REAL(r_std), ALLOCATABLE,SAVE,DIMENSION(:,:)   :: fpc_max              !! "maximal" coverage fraction of a grid box (LAI ->
90                                                                         !! infinity) on ground. [??CHECK??] It's set to zero here,
91                                                                         !! and then is used once in lpj_light.f90 to test if
92                                                                         !! fpc_nat is greater than it. Something seems missing
93!$OMP THREADPRIVATE(fpc_max)
94  LOGICAL,ALLOCATABLE,SAVE,DIMENSION(:,:)        :: PFTpresent           !! PFT exists (equivalent to veget > 0 for natural PFTs)
95!$OMP THREADPRIVA\TE(PFTpresent)
96  REAL,ALLOCATABLE,SAVE,DIMENSION(:,:)           :: plant_status         !! Growth and phenological status of the plant
97                                                                         !! Different stati defined in constantes
98!$OMP THREADPRIVATE(plant_status)
99  LOGICAL,ALLOCATABLE,SAVE,DIMENSION(:,:)        :: need_adjacent        !! This PFT needs to be in present in an adjacent gridbox
100                                                                         !! if it is to be introduced in a new gridbox
101!$OMP THREADPRIVATE(need_adjacent)
102!--
103  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: humrel_daily         !! Daily plant available water -root profile weighted
104                                                                         !! (0-1, unitless)
105!$OMP THREADPRIVATE(humrel_daily)
106
107  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: vir_humrel_daily     !! Virtual daily plant available water -root profile weighted
108                                                                         !! (0-1, unitless)
109!$OMP THREADPRIVATE(vir_humrel_daily)
110
111  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: stressed_daily       !! Accumulated proxy for stressed ecosystem functioning
112                                                                         !! see variable stressed defined in sechiba
113!$OMP THREADPRIVATE(stressed_daily)
114
115  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: unstressed_daily     !! Accumulated proxy for unstressed ecosystem functioning
116                                                                         !! see variable stressed defined in sechiba
117!$OMP THREADPRIVATE(unstressed_daily)
118 
119  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: daylight             !! Time steps dt_radia during daylight
120!$OMP THREADPRIVATE(daylight)
121
122 REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)     :: daylight_count    !! Time steps dt_radia during daylight and when there is growth (gpp>0)
123!$OMP THREADPRIVATE(daylight_count)
124
125  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: transpir_supply_daily !! Daily supply of water for transpiration @tex $(mm dt^{-1})$ @endtex
126! $OMP THREADPRIVATE(transpir_supply_daily)
127
128  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: vir_transpir_supply_daily !! Daily supply of water for transpiration
129                                                                         !! @tex $(mm dt^{-1})$ @endtex
130! $OMP THREADPRIVATE(vir_transpir_supply_daily)                                                                       
131 
132  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: transpir_daily       !! Daily demand of water for transpiration @tex $(mm dt^{-1})$ @endtex
133! $OMP THREADPRIVATE(transpir_daily)
134
135
136  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: humrel_week          !! "Weekly" plant available water -root profile weighted
137                                                                         !! (0-1, unitless)
138!$OMP THREADPRIVATE(humrel_week)
139  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: humrel_month         !! "Monthly" plant available water -root profile weighted
140                                                                         !! (0-1, unitless)
141!$OMP THREADPRIVATE(humrel_month)
142  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: humrel_growingseason !! Mean growing season moisture availability (used for
143                                                                         !! allocation response)
144!$OMP THREADPRIVATE(humrel_growingseason)
145  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: vir_humrel_growingseason !! Mean growing season moisture availability (used for
146                                                                         !! allocation response)
147!$OMP THREADPRIVATE(vir_humrel_growingseason)
148  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: maxhumrel_lastyear   !! Last year's max plant available water -root profile
149                                                                         !! weighted (0-1, unitless)
150!$OMP THREADPRIVATE(maxhumrel_lastyear)
151  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: maxhumrel_thisyear   !! This year's max plant available water -root profile
152                                                                         !! weighted (0-1, unitless)
153!$OMP THREADPRIVATE(maxhumrel_thisyear)
154  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: minhumrel_lastyear   !! Last year's min plant available water -root profile
155                                                                         !! weighted (0-1, unitless) 
156!$OMP THREADPRIVATE(minhumrel_lastyear)
157  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: minhumrel_thisyear   !! This year's minimum plant available water -root profile
158                                                                         !! weighted (0-1, unitless)
159!$OMP THREADPRIVATE(minhumrel_thisyear)
160!--- 
161  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: t2m_daily            !! Daily air temperature at 2 meter (K)
162!$OMP THREADPRIVATE(t2m_daily)
163
164  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: Tseason              !! "seasonal" 2 meter temperatures (K)
165!$OMP THREADPRIVATE(Tseason)
166  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: Tseason_length       !! temporary variable to calculate Tseason
167!$OMP THREADPRIVATE(Tseason_length)
168  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: Tseason_tmp          !! temporary variable to calculate Tseason
169!$OMP THREADPRIVATE(Tseason_tmp)
170  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: Tmin_spring_time
171!$OMP THREADPRIVATE(Tmin_spring_time)
172  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: onset_date           !! Date in the year at when the leaves started to grow(begin_leaves), only for diagnostics.
173!$OMP THREADPRIVATE(onset_date)
174  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: t2m_week             !! Mean "weekly" (default 7 days) air temperature at 2
175                                                                         !! meter (K) 
176!$OMP THREADPRIVATE(t2m_week)
177  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: t2m_month            !! Mean "monthly" (default 20 days) air temperature at 2
178                                                                         !! meter (K)
179!$OMP THREADPRIVATE(t2m_month)
180  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: t2m_longterm         !! Mean "Long term" (default 3 years) air temperature at
181                                                                         !! 2 meter (K)
182!$OMP THREADPRIVATE(t2m_longterm)
183  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: t2m_min_daily        !! Daily minimum air temperature at 2 meter (K)
184!$OMP THREADPRIVATE(t2m_min_daily)
185  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: tsurf_daily          !! Daily surface temperatures (K)
186!$OMP THREADPRIVATE(tsurf_daily)
187
188!---
189! variables added for windthrow module  ---
190  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)       :: wind_speed_daily    !! Daily maximum wind speed at 2 meter (ms-1)
191!$OMP THREADPRIVATE(wind_speed_daily)
192  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)       :: wind_max_daily      !! Temporary daily maximum speed used to calculate wind_speed_daily (ms-1)
193!$OMP THREADPRIVATE(wind_max_daily)
194  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)       :: soil_temp_daily     !! Daily maximum soil temperature at 0.8 meter below ground(K)
195!$OMP THREADPRIVATE(soil_temp_daily)
196  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)       :: soil_max_daily      !! Temporary daily maximum soil temperature used to calculate soil_temp_speed_daily (ms-1)
197!$OMP THREADPRIVATE(soil_max_daily)
198!---
199  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: precip_daily         !! Daily precipitations sum @tex $(mm day^{-1})$ @endtex
200!$OMP THREADPRIVATE(precip_daily)
201  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: precip_lastyear      !! Last year's annual precipitation sum
202                                                                         !! @tex $??(mm year^{-1})$ @endtex
203!$OMP THREADPRIVATE(precip_lastyear)
204  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: precip_thisyear      !! This year's annual precipitation sum
205                                                                         !! @tex $??(mm year^{-1})$ @endtex
206!$OMP THREADPRIVATE(precip_thisyear)
207!---
208  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: soilhum_daily        !! Daily soil humidity (0-1, unitless)
209!$OMP THREADPRIVATE(soilhum_daily)
210  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: soilhum_month        !! Soil humidity - integrated over a month (0-1, unitless)
211!$OMP THREADPRIVATE(soilhum_month)
212  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: tsoil_daily          !! Daily soil temperatures (K)
213!$OMP THREADPRIVATE(tsoil_daily)
214  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: tsoil_month          !! Soil temperatures at each soil layer integrated over a
215                                                                         !! month (K)
216!$OMP THREADPRIVATE(tsoil_month)
217!---
218  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: litterhum_daily      !! Daily litter humidity (0-1, unitless)
219!$OMP THREADPRIVATE(litterhum_daily)
220!---
221  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: control_moist        !! Moisture control of heterotrophic respiration
222                                                                         !! (0-1, unitless)
223!$OMP THREADPRIVATE(control_moist)
224 REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)   :: drainage             !! Fraction of water lost from the soil column by leaching (-) 
225!$OMP THREADPRIVATE(drainage)
226 REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)     :: drainage_daily       !! Daily Fraction of water lost from the soil column by leaching (-) 
227!$OMP THREADPRIVATE(drainage_daily)
228 REAL(r_std),ALLOCATABLE,SAVE, DIMENSION(:,:)    :: n_mineralisation_d   !! net nitrogen mineralisation of decomposing SOM                                                                                               !! (gN/m**2/day), supposed to be NH4 
229!$OMP THREADPRIVATE(n_mineralisation_d)
230 REAL(r_std),ALLOCATABLE,SAVE, DIMENSION(:,:,:)  :: plant_n_uptake_daily   !! Uptake of soil N by plants   
231                                                                         !! (gN/m**2/day) 
232!$OMP THREADPRIVATE(plant_n_uptake_daily)
233  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: control_temp         !! Temperature control of heterotrophic respiration at the
234                                                                         !! different soil levels (0-1, unitless)
235!$OMP THREADPRIVATE(control_temp)
236  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: control_moist_daily  !! Moisture control of heterotrophic respiration daily
237                                                                         !! (0-1, unitless)
238!$OMP THREADPRIVATE(control_moist_daily)
239  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: control_temp_daily   !! Temperature control of heterotrophic respiration, above
240                                                                         !! and below daily (0-1, unitless)
241!$OMP THREADPRIVATE(control_temp_daily)
242!---
243  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: gdd_init_date        !! inital date for gdd count
244!$OMP THREADPRIVATE(gdd_init_date)
245
246  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: gdd_from_growthinit  !! gdd from beginning of season (C)
247!$OMP THREADPRIVATE(gdd_from_growthinit)
248  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: gdd0_lastyear        !! Last year's annual Growing Degree Days,
249                                                                         !! threshold 0 deg C (K)
250!$OMP THREADPRIVATE(gdd0_lastyear)
251  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: gdd0_thisyear        !! This year's annual Growing Degree Days,
252                                                                         !! threshold 0 deg C (K)
253!$OMP THREADPRIVATE(gdd0_thisyear)
254  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: gdd_m5_dormance      !! Growing degree days for onset of growing season,
255                                                                         !! threshold -5 deg C (K)
256!$OMP THREADPRIVATE(gdd_m5_dormance)
257  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: gdd_midwinter        !! Growing degree days for onset of growing season,
258                                                                         !! since midwinter (K)
259!$OMP THREADPRIVATE(gdd_midwinter)
260  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: ncd_dormance         !! Number of chilling days since leaves were lost (days)
261!$OMP THREADPRIVATE(ncd_dormance)
262  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: ngd_minus5           !! Number of growing days, threshold -5 deg C (days)
263!$OMP THREADPRIVATE(ngd_minus5)
264  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: hum_min_dormance     !! Minimum moisture during dormance (0-1, unitless)
265!$OMP THREADPRIVATE(hum_min_dormance)
266!---
267  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: gpp_daily            !! Daily gross primary productivity per ground area
268                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
269!$OMP THREADPRIVATE(gpp_daily)
270  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: gpp_week             !! Mean "weekly" (default 7 days) GPP 
271                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
272!$OMP THREADPRIVATE(gpp_week)
273  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: maxgppweek_lastyear  !! Last year's maximum "weekly" GPP 
274                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
275!$OMP THREADPRIVATE(maxgppweek_lastyear)
276  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: maxgppweek_thisyear  !! This year's maximum "weekly" GPP 
277                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex 
278!$OMP THREADPRIVATE(maxgppweek_thisyear)
279!---
280  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: npp_daily            !! Daily net primary productivity per ground area
281                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
282!$OMP THREADPRIVATE(npp_daily)
283  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: npp_longterm         !! "Long term" (default 3 years) net primary productivity
284                                                                         !! per ground area 
285                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex   
286!$OMP THREADPRIVATE(npp_longterm)
287  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: npp_equil            !! Equilibrium NPP written to forcesoil
288                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex
289!$OMP THREADPRIVATE(npp_equil)
290  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: npp_tot              !! Total NPP written to forcesoil
291                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex
292!$OMP THREADPRIVATE(npp_tot)
293!---
294  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: resp_maint_part_radia!! Maintenance respiration of different plant parts per
295                                                                         !! total ground area at Sechiba time step 
296                                                                         !! @tex $(gC m^{-2} dt_sechiba^{-1})$ @endtex
297!$OMP THREADPRIVATE(resp_maint_part_radia)
298  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: resp_maint_part      !! Maintenance respiration of different plant parts per
299                                                                         !! total ground area at Stomate time step
300                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
301!$OMP THREADPRIVATE(resp_maint_part)
302  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: resp_maint_radia     !! Maintenance respiration per ground area at Sechiba time
303                                                                         !! step   
304                                                                         !! @tex $(gC m^{-2} dt_sechiba^{-1})$ @endtex
305!$OMP THREADPRIVATE(resp_maint_radia)
306  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: resp_maint_d         !! Maintenance respiration per ground area at Stomate time
307                                                                         !! step 
308                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
309!$OMP THREADPRIVATE(resp_maint_d)
310  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: resp_growth_d        !! Growth respiration per ground area
311                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
312!$OMP THREADPRIVATE(resp_growth_d)
313  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: resp_hetero_d        !! Heterotrophic respiration per ground area
314                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
315!$OMP THREADPRIVATE(resp_hetero_d)
316  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: resp_hetero_radia    !! Heterothrophic respiration per ground area at Sechiba
317                                                                         !! time step
318                                                                         !! @tex $(gC m^{-2} dt_sechiba^{-1})$ @endtex
319!$OMP THREADPRIVATE(resp_hetero_radia)
320!---
321  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)     :: turnover_time       !! Turnover time of grasses
322                                                                         !! @tex $(dt_stomate^{-1})$ @endtex
323!$OMP THREADPRIVATE(turnover_time)
324  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:) :: turnover_daily      !! Senescence-driven turnover (better: mortality) of
325                                                                         !! leaves and roots 
326                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
327!$OMP THREADPRIVATE(turnover_daily)
328  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:) :: turnover_littercalc !! Senescence-driven turnover (better: mortality) of
329                                                                         !! leaves and roots at Sechiba time step
330                                                                         !! @tex $(gC m^{-2} dt_sechiba^{-1})$ @endtex
331!$OMP THREADPRIVATE(turnover_littercalc)
332  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:) :: turnover_longterm   !! "Long term" (default 3 years) senescence-driven
333                                                                         !! turnover (better: mortality) of leaves and roots
334                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex
335!$OMP THREADPRIVATE(turnover_longterm)
336  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:) :: bm_to_litter        !! Background (not senescence-driven) mortality of biomass
337                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
338!$OMP THREADPRIVATE(bm_to_litter)
339  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:) :: bm_to_littercalc    !! conversion of biomass to litter per ground area at
340                                                                         !! Sechiba time step
341                                                                         !! @tex $(gC m^{-2} dt_sechiba^{-1})$ @endtex
342!$OMP THREADPRIVATE(bm_to_littercalc)
343  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: dead_leaves          !! Metabolic and structural pools of dead leaves on ground
344                                                                         !! per PFT @tex $(gC m^{-2})$ @endtex
345!$OMP THREADPRIVATE(dead_leaves)
346  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:,:):: litter             !! Above and below ground metabolic and structural litter
347                                                                         !! per ground area
348                                                                         !! @tex $(gC m^{-2})$ @endtex
349!$OMP THREADPRIVATE(litter)
350  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: firelitter           !! Total litter above the ground that could potentially
351                                                                         !! burn @tex $(gC m^{-2})$ @endtex
352!$OMP THREADPRIVATE(firelitter)
353  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:):: carbon_input     !! Quantity of carbon going into carbon pools from litter
354                                                                         !! decomposition per ground area  at Sechiba time step
355                                                                         !! @tex $(gC m^{-2} dt_sechiba^{-1})$ @endtex
356!$OMP THREADPRIVATE(carbon_input)
357  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:):: nitrogen_input       !! Quantity of nitrogen going into nitrogen pools from litter
358                                                                         !! decomposition per ground area  at Sechiba time step 
359                                                                         !! @tex $(gC m^{-2} dtradia^{-1})$ @endtex 
360!$OMP THREADPRIVATE(nitrogen_input)
361  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:)  :: som_input_daily !! Daily quantity of carbon going into carbon pools from
362                                                                           !! litter decomposition per ground area
363                                                                           !! @tex $(gC m^{-2} day^{-1})$ @endtex
364!$OMP THREADPRIVATE(som_input_daily)
365  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:,:)  :: som                !! Soil organic matter  pools per ground area: active, slow, or
366                                                                         !! passive, @tex $(gC or N m^{-2})$ @endtex
367!$OMP THREADPRIVATE(som)
368  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: lignin_struc         !! Ratio Lignine/Carbon in structural litter for above and
369                                                                         !! below ground compartments (unitless)
370!$OMP THREADPRIVATE(lignin_struc)
371  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: lignin_wood          !! Ratio Lignine/Carbon in woody litter for above and
372                                                                         !! below ground compartments (unitless)       
373!$OMP THREADPRIVATE(lignin_wood)
374  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: lm_lastyearmax       !! Last year's maximum leaf mass per ground area for each
375                                                                         !! PFT @tex $(gC m^{-2})$ @endtex 
376!$OMP THREADPRIVATE(lm_lastyearmax)
377  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: lm_thisyearmax       !! This year's maximum leaf mass per ground area for each
378                                                                         !! PFT @tex $(gC m^{-2})$ @endtex 
379!$OMP THREADPRIVATE(lm_thisyearmax)
380  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: maxfpc_lastyear      !! Last year's maximum fpc for each natural PFT, on ground
381                                                                         !! [??CHECK] fpc but this ones look ok (computed in
382                                                                         !! season, used in light)??
383!$OMP THREADPRIVATE(maxfpc_lastyear)
384  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: maxfpc_thisyear      !! This year's maximum fpc for each PFT, on ground (see
385                                                                         !! stomate_season), [??CHECK] fpc but this ones look ok
386                                                                         !! (computed in season, used in light)??
387!$OMP THREADPRIVATE(maxfpc_thisyear)
388!---
389  REAL(r_std), ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: leaf_age             !! Age of different leaf classes (days)
390!$OMP THREADPRIVATE(leaf_age)
391  REAL(r_std), ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: leaf_frac            !! PFT fraction of leaf mass in leaf age class (0-1,
392                                                                         !! unitless)
393!$OMP THREADPRIVATE(leaf_frac)
394  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: when_growthinit      !! Days since beginning of growing season (days)
395!$OMP THREADPRIVATE(when_growthinit)
396  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: herbivores           !! Time constant of probability of a leaf to be eaten by a
397                                                                         !! herbivore (days)
398!$OMP THREADPRIVATE(herbivores)
399  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: RIP_time             !! How much time ago was the PFT eliminated for the last
400                                                                         !! time (year)
401!$OMP THREADPRIVATE(RIP_time)
402  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: time_hum_min         !! Time elapsed since strongest moisture limitation (days)
403!$OMP THREADPRIVATE(time_hum_min)
404  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: drain_daily          !! daily fraction of water lost from the soil column by leaching (-) 
405!$OMP THREADPRIVATE(drain_daily)
406
407!---
408  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: clay_fm              !! Soil clay content (0-1, unitless), parallel computing
409  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: clay_fm_g            !! Soil clay content (0-1, unitless), parallel computing
410  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: silt_fm              !! Soil silt content (0-1, unitless), parallel computing
411  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: silt_fm_g            !! Soil silt content (0-1, unitless), parallel computing
412  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: bulk_fm              !! Bulk density (kg/m**3), parallel computing   
413  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: bulk_fm_g            !! Bulk density (kg/m**3), parallel computing
414
415  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: precip_fm            !! Daily precipitations sum @tex $(mm day^{-1})$ @endtex,
416                                                                         !! parallel computing
417  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: precip_fm_g          !! Daily precipitations sum @tex $(mm day^{-1})$ @endtex,
418                                                                         !! parallel computing
419  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: litterhum_daily_fm   !! Daily relative humidity of litter (0-1, unitless),
420                                                                         !! parallel computing
421  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: litterhum_daily_fm_g !! Daily relative humidity of litter (0-1, unitless),
422                                                                         !! parallel computing
423  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: t2m_daily_fm         !! Daily air temperature at 2 meter (K), parallel
424                                                                         !! computing
425  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: t2m_daily_fm_g       !! Daily air temperature at 2 meter (K), parallel
426                                                                         !! computing
427  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: t2m_min_daily_fm     !! Daily minimum air temperature at 2 meter (K),
428                                                                         !! parallel computing
429  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: t2m_min_daily_fm_g   !! Daily minimum air temperature at 2 meter (K),
430                                                                         !! parallel computing
431  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: tsurf_daily_fm       !! Daily surface temperatures (K), parallel
432                                                                         !! computing
433  REAL(r_std),ALLOCATABLE,DIMENSION(:,:)         :: tsurf_daily_fm_g     !! Daily surface temperatures (K), parallel
434                                                                         !! computing
435  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: tsoil_daily_fm       !! Daily soil temperatures (K), parallel computing
436  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: tsoil_daily_fm_g     !! Daily soil temperatures (K), parallel computing
437  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: soilhum_daily_fm     !! Daily soil humidity (0-1, unitless), parallel computing
438  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: soilhum_daily_fm_g   !! Daily soil humidity (0-1, unitless), parallel computing
439  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: humrel_daily_fm      !! Daily relative humidity of atmosphere (0-1, unitless),
440                                                                         !! parallel computing
441  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: humrel_daily_fm_g    !! Daily relative humidity of atmosphere (0-1, unitless),
442                                                                         !! parallel computing
443  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: gpp_daily_fm         !! Daily gross primary productivity per ground area
444                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex,
445                                                                         !! parallel computing
446  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: gpp_daily_fm_g       !! Daily gross primary productivity per ground area
447                                                                         !! @tex $(gC m^{-2} day^{-1})$ @endtex,
448                                                                         !! parallel computing
449  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: veget_fm             !! Vegetation coverage taking into account non-biological
450                                                                         !! coverage (unitless), parallel computing
451  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: veget_fm_g           !! Vegetation coverage taking into account non-biological
452                                                                         !! coverage (unitless), parallel computing
453  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: veget_max_fm         !! Maximum vegetation coverage taking into account
454                                                                         !! non-biological coverage (unitless), parallel computing
455  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: veget_max_fm_g       !! Maximum vegetation coverage taking into account none
456                                                                         !! biological coverage (unitless), parallel computing
457  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: lai_fm               !! Leaf area index @tex $@tex $(m^2 m^{-2})$ @endtex$ @endtex,
458                                                                         !! parallel computing
459  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)       :: lai_fm_g             !! Leaf area index @tex $@tex $(m^2 m^{-2})$ @endtex$ @endtex,
460                                                                         !! parallel computing
461  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)      :: drainage_fm           !! daily fraction of water lost from the soil column by leaching (-)                                                                           
462  REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)      :: drainage_fm_g         !! drain
463                                                                         !! parallel computing
464 REAL(r_std), ALLOCATABLE,SAVE,DIMENSION(:,:)   :: cn_leaf_min_season    !! Seasonal min CN ratio of leaves
465!$OMP THREADPRIVATE(cn_leaf_min_season)
466 REAL(r_std), ALLOCATABLE,SAVE,DIMENSION(:,:)   :: nstress_season        !! N-related seasonal stress (used for allocation)
467!$OMP THREADPRIVATE(nstress_season)
468 REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: soil_n_min            !! mineral nitrogen in the soil (gN/m**2)   
469                                                                         !! (first index=kjpindex, second index=nvm, third index=nnspec)   
470!$OMP THREADPRIVATE(soil_n_min)
471 REAL(r_std), ALLOCATABLE,SAVE,DIMENSION(:,:) :: p_O2                  !! partial pressure of oxigen in the soil (hPa)(first index=kjpindex, second index=nvm)
472!$OMP THREADPRIVATE(p_O2)
473                     
474 REAL(r_std), ALLOCATABLE,SAVE,DIMENSION(:,:) :: bact                  !! denitrifier biomass (gC/m**2)
475                                                                         !! (first index=kjpindex, second index=nvm)
476!$OMP THREADPRIVATE(bact)
477
478  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)   :: co2_fire              !! Carbon emitted to the atmosphere by burning living
479                                                                         !! and dead biomass
480                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
481!$OMP THREADPRIVATE(co2_fire)
482!!$  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: co2_to_bm_dgvm       !! Psuedo-photosynthesis,C used to provide seedlings with
483!!$                                                                         !! an initial biomass, arbitrarily removed from the
484!!$                                                                         !! atmosphere 
485!!$                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
486!!$!$OMP THREADPRIVATE(co2_to_bm_dgvm)
487!!$  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: n_to_bm              !! N taken from ?? to provide seedlings with
488!!$                                                                         !! an initial N biomass
489!!$                                                                         !! @tex $(gN m^{-2} dt_stomate^{-1})$ @endtex
490!!$!$OMP THREADPRIVATE(n_to_bm)
491  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: atm_to_bm            !! C and N taken from the atmosphere to provide seedlings
492                                                                         !! with an initial N biomass
493                                                                         !! @tex $(gN m^{-2} dt_stomate^{-1})$ @endtex
494!$OMP THREADPRIVATE(atm_to_bm)
495
496!!$  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: co2_flux_daily       !! Daily net CO2 flux between atmosphere and biosphere
497!!$                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
498!!$                                                                         !! [??CHECK] sign convention?
499!!$!$OMP THREADPRIVATE(co2_flux_daily)
500!!$  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: co2_flux_monthly     !! Monthly net CO2 flux between atmosphere and biosphere
501!!$                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
502!!$                                                                         !! [??CHECK] sign convention?
503!!$!$OMP THREADPRIVATE(co2_flux_monthly)
504
505  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: prod_s               !! Wood products remaining in the 1 year-turnover pool
506                                                                         !! after the annual release for each compartment
507                                                                         !! @tex $(gC m^{-2})$ @endtex   
508                                                                         !! (0:1 input from year of land cover change),
509                                                                         !! dimension(#pixels,0:1 years
510!$OMP THREADPRIVATE(prod_s)
511  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: prod_m               !! Wood products remaining in the 10 year-turnover pool
512                                                                         !! after the annual release for each compartment
513                                                                         !! @tex $(gC m^{-2})$ @endtex   
514                                                                         !! (0:10 input from year of land cover change),
515                                                                         !! dimension(#pixels,0:10 years
516!$OMP THREADPRIVATE(prod_m)
517  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: prod_l               !! Wood products remaining in the 100 year-turnover pool
518                                                                         !! after the annual release for each compartment
519                                                                         !! @tex $(gC m^{-2})$ @endtex 
520                                                                         !! (0:100 input from year of land cover change),
521                                                                         !! dimension(#pixels,0:100 years)
522!$OMP THREADPRIVATE(prod_l)
523  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: flux_s               !! Wood decomposition from the 1 year-turnover pool
524                                                                         !! compartments
525                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex
526                                                                         !! dimension(#pixels,0:1) 
527!$OMP THREADPRIVATE(flux_s)
528  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: flux_m               !! Wood decomposition from the 10 year-turnover pool
529                                                                         !! compartments
530                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex
531                                                                         !! dimension(#pixels,0:10) 
532!$OMP THREADPRIVATE(flux_m)
533  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:,:)  :: flux_l              !! Wood decomposition from the 100 year-turnover pool
534                                                                         !! compartments
535                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex
536                                                                         !! dimension(#pixels,0:100)
537!$OMP THREADPRIVATE(flux_l)
538  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: flux_prod_s         !! Release during first year following land cover change
539                                                                         !! (paper, burned, etc...)
540                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex 
541!$OMP THREADPRIVATE(flux_prod_s)
542  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: flux_prod_m         !! Total annual release from the 10 year-turnover pool
543                                                                         !! sum of flux_m 
544                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex
545!$OMP THREADPRIVATE(flux_prod_m)
546  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: flux_prod_l         !! Total annual release from the 100 year-turnover pool
547                                                                         !! sum of flux_l
548                                                                         !! @tex $(gC m^{-2} year^{-1})$ @endtex
549!$OMP THREADPRIVATE(flux_prod_l)
550  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: carb_mass_total      !! Total on-site and off-site C pool
551                                                                         !! @tex $(??gC m^{-2})$ @endtex                       
552!$OMP THREADPRIVATE(carb_mass_total)
553!---
554  REAL(r_std), SAVE                              :: tau_longterm
555!$OMP THREADPRIVATE(tau_longterm)
556  REAL(r_std),SAVE                               :: dt_days=zero         !! Time step of STOMATE (days)
557!$OMP THREADPRIVATE(dt_days)
558  INTEGER(i_std),SAVE                            :: date=0               !! Date (days)
559!$OMP THREADPRIVATE(date)
560  INTEGER(i_std),ALLOCATABLE,SAVE,DIMENSION(:)   :: nforce               !! Number of states calculated for the soil forcing
561                                                                         !! variables (unitless), dimension(::nparan*::nbyear) both
562                                                                         !! given in the run definition file   
563!$OMP THREADPRIVATE(nforce)
564  INTEGER(i_std),ALLOCATABLE,SAVE,DIMENSION(:)   :: isf                  !! Index for number of time steps that can be stored in
565                                                                         !! memory (unitless), dimension (#nsfm)
566!$OMP THREADPRIVATE(isf)
567  INTEGER(i_std),ALLOCATABLE,SAVE,DIMENSION(:)   :: nf_cumul             !! Number of years over which the average is calculated in
568                                                                         !! forcesoil when cumul flag is set, dimension (#nsft)
569                                                                         !! [??CHECK] definition the dimension is number of
570                                                                         !! timesteps in a year?
571!$OMP THREADPRIVATE(nf_cumul)
572  INTEGER(i_std), SAVE                           :: spinup_period        !! Period of years used to calculate the resolution of the system for spinup analytic.
573                                                                         !! This period correspond in most cases to the period of years of forcing data used
574  INTEGER,PARAMETER                              :: r_typ = nf90_real4   !! Specify data format (server dependent)
575  LOGICAL,ALLOCATABLE,SAVE,DIMENSION(:)          :: nf_written           !! Flag indicating whether the forcing data have been
576                                                                         !! written
577!$OMP THREADPRIVATE(nf_written)
578!---
579  LOGICAL, SAVE                                  :: do_slow=.FALSE.      !! Flag that determines whether stomate_accu calculates
580                                                                         !! the sum(do_slow=.FALSE.) or the mean
581                                                                         !! (do_slow=.TRUE.)
582!$OMP THREADPRIVATE(do_slow)
583  LOGICAL, SAVE                                  :: EndOfYear=.FALSE.    !! Update annual variables? This variable must be
584                                                                         !! .TRUE. once a year
585!$OMP THREADPRIVATE(EndOfYear)
586  LOGICAL, SAVE                                  :: EndOfMonth=.FALSE.   !! Update monthly variables? This variable must be
587                                                                         !!.TRUE. once a month
588!$OMP THREADPRIVATE(EndOfMonth)
589  LOGICAL, SAVE                                  :: l_first_stomate = .TRUE.!! Is this the first call of stomate?
590!$OMP THREADPRIVATE(l_first_stomate)
591  LOGICAL, SAVE                                  :: cumul_forcing=.FALSE.!! flag for cumul of forcing if teststomate
592!$OMP THREADPRIVATE(cumul_forcing)
593  LOGICAL, SAVE                                  :: cumul_Cforcing=.FALSE.  !! Flag, if internal parameter cumul_Cforcing is
594                                                                            !! TRUE then ::nbyear (defined in run definition
595                                                                            !! file will be forced to 1 later in this module. If
596                                                                            !! FALSE the mean over ::nbyear is written in forcesoil
597!$OMP THREADPRIVATE(cumul_Cforcing)
598!---
599
600  REAL(r_std),DIMENSION(:),ALLOCATABLE,SAVE      :: circ_class_dist   !! When the circumference class distribution
601                                                                      !! is redone due to empty classes, this is the
602                                                                      !! tree distribution used.  Notice that this distribution
603                                                                      !! is normalized after being read in.
604!$OMP THREADPRIVATE(circ_class_dist)
605  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE,SAVE  :: store_sum_delta_ba!! Sum of increase of basal area (m^2) which does not pass
606                                                                      !! through gap clean
607!$OMP THREADPRIVATE(store_sum_delta_ba)
608  REAL(r_std),DIMENSION(:),ALLOCATABLE,SAVE      :: st_dist           !! During self-thinning, we need to decide which
609                                                                      !! circumference classes to kill trees in.  This
610                                                                      !! is the distribution that tells us this.  Notice that
611                                                                      !! it is normalized after being read in.
612!$OMP THREADPRIVATE(st_dist)
613 
614!!$  !+++CHECK+++
615!!$  ! replaced by harvest_xxx. Seems like post processing for xios
616!!$  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: harvest_above_monthly   !! [??CHECK] post-processing - should be removed?
617!!$!$OMP THREADPRIVATE(harvest_above_monthly)
618!!$  !+++++++++++
619!!$
620!!$  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: flux_prod_monthly      !! [??CHECK] post-processing - should be removed?
621!!$!$OMP THREADPRIVATE(flux_prod_monthly)
622!---
623  INTEGER(i_std), SAVE                               :: global_years        !! Global counter of years (year)
624!$OMP THREADPRIVATE(global_years)
625  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:)           :: ok_equilibrium      !! Logical array marking the points where the resolution is ok
626                                                                            !! (true/false)
627!$OMP THREADPRIVATE(ok_equilibrium)
628  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:)           :: carbon_eq           !! Logical array to mark the carbon pools at equilibrium ?
629                                                                            !! If true, the job stops. (true/false)
630!$OMP THREADPRIVATE(carbon_eq)
631  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)       :: nbp_accu            !! Accumulated Net Biospheric Production over the year (gC.m^2 )
632!$OMP THREADPRIVATE(nbp_accu)
633  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:)     :: nbp_accu_pool       !! Accumulated pool-basaed Net Biospheric Production over the year (gC.m^2 )
634!$OMP THREADPRIVATE(nbp_accu_pool)
635  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)       :: nbp_flux            !! Net Biospheric Production (gC.m^2.day^{-1})
636!$OMP THREADPRIVATE(nbp_flux)
637  REAL(r_std), ALLOCATABLE, SAVE,DIMENSION(:,:)      :: nbp_pool            !! Pool-based Net Biospheric Production (gC.m^2.day^{-1})
638!$OMP THREADPRIVATE(nbp_pool)
639  REAL(r_std), ALLOCATABLE, SAVe,DIMENSION(:,:)      :: nbp_pool_start      !! Biomass pool as calculated from the
640                                                                            !! previous time step
641!$OMP THREADPRIVATE(nbp_pool_start)
642  REAL(r_std), ALLOCATABLE, SAVE,DIMENSION(:,:)      :: nbp_pool_end        !! Biomass pool calculated at the end
643                                                                            !! current time step
644!$OMP THREADPRIVATE(nbp_pool_end)
645  REAL(r_std), ALLOCATABLE, DIMENSION(:,:,:,:)       :: matrixA             !! matrix containing the fluxes between the carbon pools
646                                                                            !! per sechiba time step
647                                                                            !! @tex $(gC.m^2.day^{-1})$ @endtex
648!$OMP THREADPRIVATE(matrixA)
649  REAL(r_std), ALLOCATABLE, DIMENSION(:,:,:)         :: vectorB             !! vector containing the litter increase per sechiba time step
650                                                                            !! @tex $(gC m^{-2})$ @endtex
651!$OMP THREADPRIVATE(vectorB)
652  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) :: matrixV             !! matrix containing the accumulated values of matrixA
653!$OMP THREADPRIVATE(matrixV)
654  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:)   :: vectorU             !! matrix containing the accumulated values of vectorB
655!$OMP THREADPRIVATE(vectorU)
656  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) :: matrixW             !! matrix containing the opposite of matrixA
657!$OMP THREADPRIVATE(matrixW)
658  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:)   :: previous_stock      !! Array containing the carbon stock calculated by the analytical
659                                                                            !! method in the previous resolution
660!$OMP THREADPRIVATE(previous_stock)
661  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:)   :: current_stock       !! Array containing the carbon stock calculated by the analytical
662                                                                            !! method in the current resolution
663!$OMP THREADPRIVATE(current_stock)
664  REAL(r_std), SAVE                                  :: eps_carbon          !! Stopping criterion for carbon pools (unitless,0-1)
665!$OMP THREADPRIVATE(eps_carbon)
666    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)           :: sigma            !! Threshold for indivudal tree growth (m, trees whose
667                                                                         !! circumference is smaller than sigma don't grow much)
668!$OMP THREADPRIVATE(sigma)
669
670  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:,:)  :: age_stand        !! Age of stand (years)
671!$OMP THREADPRIVATE(age_stand)
672 
673  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:,:)  :: rotation_n       !! Rotation number (number of rotation since pft is managed)
674!$OMP THREADPRIVATE(rotation_n)
675 
676  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:,:)  :: last_cut         !! Years since last thinning (years)
677!$OMP THREADPRIVATE(last_cut)
678
679  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  :: CN_som_litter_longterm !! Longterm CN ratio of litter and som pools (gC/gN)
680
681  REAL(r_std), SAVE                                 :: tau_CN_longterm      !! Counter used for calculating the longterm CN ratio of SOM and litter pools (seconds)   
682
683  ! Functional Allocation
684
685  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:)     :: KF               !! Scaling factor to convert sapwood mass
686                                                                         !! into leaf mass (m). The initial value is calculated
687                                                                         !! in prescribe and updated during allocation
688!$OMP THREADPRIVATE(KF)
689
690  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:)     :: k_latosa_adapt   !! Leaf to sapwood area adapted for waterstress.
691                                                                         !! Adaptation takes place at the end of the year
692                                                                         !! (m)
693!$OMP THREADPRIVATE(k_latosa_adapt)
694
695  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) :: harvest_pool     !! The pool which records the quantity of
696                                                                         !! wood harvested and thinned due to forest
697                                                                         !! management and LCC. 
698                                                                         !! @tex $(gC m^{-2})$ @endtex
699!$OMP THREADPRIVATE(harvest_pool)
700
701  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:)     :: harvest_type     !! Type of management that resulted
702                                                                         !! in the harvest (unitless)
703!$OMP THREADPRIVATE(harvest_type) 
704
705  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:)     :: harvest_cut      !! Type of cutting that was used for the harvest
706                                                                         !! (unitless)
707!$OMP THREADPRIVATE(harvest_cut)
708
709  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:)     :: harvest_area     !! Harvested area (m^{2})
710!$OMP THREADPRIVATE(harvest_area) 
711
712  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:)   :: harvest_5y_area  !!Total harvested area in the last 5 years (m^{2})
713!$OMP THREADPRIVATE(harvest_5y_area)
714
715  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)       :: harvest_pool_bound       !! The boundaries of the diameter classes
716                                                                                 !! in the wood harvest pools
717                                                                                 !! @tex $(m)$ @endtex
718!$OMP THREADPRIVATE(harvest_pool_bound)
719
720  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:)     :: mai              !! The mean annual increment used in
721                                                                         !! forestry.  It is the average change
722                                                                         !! in the wood volume of of the trunk
723                                                                         !! over the lifetime of the forest.
724                                                                         !! @tex $(m**3 / m**2 / year)$ @endtex
725!$OMP THREADPRIVATE(mai)
726
727  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:)     :: pai              !! The period annual increment used in
728                                                                         !! forestry.  It is the average change
729                                                                         !! in the wood volume of of the trunk
730                                                                         !! over the past n_pai years of the forest,
731                                                                         !! where n_pai is defined in constants.f90.
732                                                                         !! @tex $(m**3 / m**2 / year)$ @endtex
733!$OMP THREADPRIVATE(pai)
734
735  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:)     :: previous_wood_volume !! The volume of the tree trunks
736                                                                         !! in a stand for the previous year.
737                                                                         !! @tex $(m**3 / m**2 )$ @endtex
738!$OMP THREADPRIVATE(previous_wood_volume)
739
740  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:,:)  :: mai_count        !! The number of times we've
741                                                                         !! calculated the volume increment
742                                                                         !! for a stand
743!$OMP THREADPRIVATE(mai_count)
744
745  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:)     :: coppice_dens     !! The density of a coppice at the first
746                                                                         !! cutting.
747                                                                         !! @tex $( 1 / m**2 )$ @endtex
748!$OMP THREADPRIVATE(coppice_dens)
749
750  REAL(r_std), ALLOCATABLE,SAVE,DIMENSION(:,:)   :: rue_longterm         !! Longterm radiation use efficiency (??units??)
751!$OMP THREADPRIVATE(rue_longterm)
752
753  REAL(r_std), ALLOCATABLE,SAVE,DIMENSION(:,:)   :: lab_fac              !! Activity of labile pool factor (??units??)
754
755  REAL(r_std),SAVE                                   :: dt_forcesoil        !! Time step of soil forcing file (days)
756!$OMP THREADPRIVATE(dt_forcesoil)
757  INTEGER(i_std),PARAMETER                           :: nparanmax=366       !! Maximum number of time steps per year for forcesoil
758  INTEGER(i_std),SAVE                                :: nparan              !! Number of time steps per year for forcesoil read from run definition (unitless)
759!$OMP THREADPRIVATE(nparan)
760  INTEGER(i_std),SAVE                                :: nbyear=1            !! Number of years saved for forcesoil (unitless)
761!$OMP THREADPRIVATE(nbyear)
762  INTEGER(i_std),SAVE                                :: iatt                !! Time step of forcing of soil processes (iatt = 1 to ::nparan*::nbyear)
763!$OMP THREADPRIVATE(iatt)
764  INTEGER(i_std),SAVE                                :: iatt_old=1          !! Previous ::iatt
765!$OMP THREADPRIVATE(iatt_old)
766  INTEGER(i_std),SAVE                                :: nsfm                !! Number of time steps that can be stored in memory (unitless)
767!$OMP THREADPRIVATE(nsfm)
768  INTEGER(i_std),SAVE                                :: nsft                !! Number of time steps in a year (unitless)
769!$OMP THREADPRIVATE(nsft)
770  INTEGER(i_std),SAVE                                :: iisf                !! Current pointer for teststomate (unitless)
771!$OMP THREADPRIVATE(iisf)
772  CHARACTER(LEN=100), SAVE                           :: forcing_name        !! Name of forcing file 1
773!$OMP THREADPRIVATE(forcing_name)
774  CHARACTER(LEN=100), SAVE                           :: Cforcing_name       !! Name of forcing file 2
775!$OMP THREADPRIVATE(Cforcing_name)
776  INTEGER(i_std),SAVE                                :: Cforcing_id         !! File identifer of file 2
777!$OMP THREADPRIVATE(Cforcing_id)   
778  INTEGER(i_std),PARAMETER                           :: ndm = 10            !! Maximum number of dimensions (unitless)
779
780INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:,:)  :: forest_managed   !! forest management flag (is the forest being managed?)
781                                                                         !! (0-4,unitless)
782!$OMP THREADPRIVATE(forest_managed)
783 
784  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:,:)  :: forest_managed_lastyear !! forest management flag for the previous year
785                                                                         !! (0-4,unitless)
786!$OMP THREADPRIVATE(forest_managed_lastyear)
787  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:,:)  :: species_change_map   !! A map which gives the PFT number that each
788                                                                         !! PFT will be replanted as in case of a clearcut.
789                                                                         !! (1-nvm,unitless)
790!$OMP THREADPRIVATE(species_change_map)
791  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:,:)  :: fm_change_map    !! A map which gives the desired FM strategy when
792                                                                         !! the PFT will be replanted after a clearcut.
793                                                                         !! (1-nvm,unitless)
794!$OMP THREADPRIVATE(fm_change_map)
795  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:,:)         :: lpft_replant     !! Indicates if this PFT has either died this year
796                                                                         !! or been clearcut/coppiced.  If it has, it is not
797                                                                         !! replanted until the end of the year.
798!$OMP THREADPRIVATE(lpft_replant)
799  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)       :: litter_demand    !! The amount of litter which will
800                                                                         !! be moved from forest to crop pools
801                                                                         !! at the end of the year.
802                                                                         !! @tex $( gC / year )$ @endtex
803!$OMP THREADPRIVATE(litter_demand)
804
805REAL(r_std), ALLOCATABLE, SAVE,DIMENSION(:,:)      :: wstress_season   !! Water stress factor, based on hum_rel_daily
806                                                                         !! (unitless, 0-1)
807!$OMP THREADPRIVATE(wstress_season)
808
809  REAL(r_std), ALLOCATABLE, SAVE,DIMENSION(:,:)     :: wstress_month    !! Water stress factor, based on hum_rel_daily
810                                                                         !! (unitless, 0-1)
811!$OMP THREADPRIVATE(wstress_month)
812
813REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:)    :: light_tran_to_level_season  !! Mean seasonal fraction of light transmitted
814                                                                                  !! to canopy levels
815!$OMP THREADPRIVATE(light_tran_to_level_season)
816
817 
818PUBLIC clay_fm, silt_fm, bulk_fm, humrel_daily_fm, litterhum_daily_fm, t2m_daily_fm, &
819   & t2m_min_daily_fm, tsurf_daily_fm, tsoil_daily_fm, soilhum_daily_fm, &
820   & precip_fm, gpp_daily_fm, veget_fm, veget_max_fm, lai_fm
821PUBLIC  dt_days, date, do_slow, EndOfYear
822PUBLIC isf, nf_written
823
824CONTAINS
825 
826
827!! ================================================================================================================================
828!! SUBROUTINE   : stomate_initialize
829!!
830!>\BRIEF        Initialization routine for stomate module.
831!!
832!! DESCRIPTION  : Initialization routine for stomate module. Read options from parameter file, allocate variables, read variables
833!!                from restart file and initialize variables if necessary.
834!!               
835!! \n
836!_ ================================================================================================================================
837
838SUBROUTINE stomate_initialize &
839        (kjit,           kjpij,             kjpindex,                        &
840         rest_id_stom,   hist_id_stom,      hist_id_stom_IPCC,               &
841         index,          lalo,              neighbours,   resolution,        &
842         contfrac,       totfrac_nobio,     clay,         silt,              &
843         bulk,           t2m,                                                &
844         veget,          veget_max,                                          &
845         co2_flux,       fco2_lu,           deadleaf_cover,  assim_param,    &
846         circ_class_biomass, circ_class_n,&
847         lai_per_level,  laieff_fit)
848
849    IMPLICIT NONE
850    !! 0. Variable and parameter declaration
851    !! 0.1 Input variables
852    INTEGER(i_std),INTENT(in)                       :: kjit              !! Time step number (unitless)
853    INTEGER(i_std),INTENT(in)                       :: kjpij             !! Total size of the un-compressed grid (unitless)
854    INTEGER(i_std),INTENT(in)                       :: kjpindex          !! Domain size - terrestrial pixels only (unitless)
855    INTEGER(i_std),INTENT(in)                       :: rest_id_stom      !! STOMATE's _Restart_ file identifier (unitless)
856    INTEGER(i_std),INTENT(in)                       :: hist_id_stom      !! STOMATE's _history_ file identifier (unitless)
857    INTEGER(i_std),INTENT(in)                       :: hist_id_stom_IPCC !! STOMATE's IPCC _history_ file identifier(unitless)
858    INTEGER(i_std),DIMENSION(kjpindex),INTENT(in)   :: index             !! The indices of the terrestrial pixels only (unitless)
859    REAL(r_std),DIMENSION(kjpindex,2),INTENT(in)    :: lalo              !! Geographical coordinates (latitude,longitude) for pixels (degrees)
860    INTEGER(i_std),DIMENSION(kjpindex,8),INTENT(in) :: neighbours        !! Neighoring grid points if land for the DGVM (unitless)
861    REAL(r_std),DIMENSION(kjpindex,2),INTENT(in)    :: resolution        !! Size in x an y of the grid (m) - surface area of the gridbox
862    REAL(r_std),DIMENSION (kjpindex), INTENT (in)   :: contfrac          !! Fraction of continent in the grid cell (unitless)
863    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: totfrac_nobio     !! Fraction of grid cell covered by lakes, land ice, cities, ... (unitless)
864    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: clay              !! Clay fraction of soil (0-1, unitless)
865    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: silt              !! Silt fraction of soil (0-1, unitless)
866    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: bulk              !! Bulk density (kg/m**3)
867    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: t2m               !! 2 m air temperature (K)
868    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)  :: veget             !! Fraction of vegetation type including
869                                                                         !! non-biological fraction (unitless)
870    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)  :: veget_max         !! Maximum fraction of vegetation type including
871                                                                         !! non-biological fraction (unitless)
872
873    !! 0.2 Output variables
874    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: co2_flux          !! CO2 flux between atmosphere and biosphere
875    REAL(r_std),DIMENSION(kjpindex),INTENT(out)     :: fco2_lu           !! CO2 flux between atmosphere and biosphere from land-use (without forest management) 
876    REAL(r_std),DIMENSION(kjpindex),INTENT(out)     :: deadleaf_cover    !! Fraction of soil covered by dead leaves (unitless)
877    REAL(r_std),DIMENSION(kjpindex,nvm,npco2),INTENT(out) :: assim_param !! min+max+opt temperatures (K) & vmax for photosynthesis 
878   
879    !! 0.3 Modified variables
880    REAL(r_std),DIMENSION(:,:,:,:,:),INTENT(inout)  :: circ_class_biomass!! Biomass per circumference class @tex $(gC tree^{-1})$ @endtex
881    REAL(r_std),DIMENSION(:,:,:),INTENT(inout)      :: circ_class_n      !! Number of trees within each circumference
882    REAL(r_std), DIMENSION(:,:,:), INTENT(inout)    :: lai_per_level     !! This is the LAI per vertical level
883                                                                         !! @tex $(m^{2} m^{-2})$ @endtex
884    TYPE(laieff_type),DIMENSION (:,:,:),INTENT(inout) &
885                                                    :: laieff_fit        !! Fitted parameters for the effective LAI
886
887    !! 0.4 Local variables
888    REAL(r_std)                                   :: dt_days_read         !! STOMATE time step read in restart file (days)
889    INTEGER(i_std)                                :: l,k,ji, jv, i, j, m  !! indices     
890    REAL(r_std),PARAMETER                         :: max_dt_days = 5.     !! Maximum STOMATE time step (days)
891    REAL(r_std),DIMENSION(kjpindex,nvm)           :: rprof                !! Coefficient of the exponential functions that
892                                                                          !! relates root density to soil depth (unitless)
893    REAL(r_std),DIMENSION(kjpindex,nvm)           :: gpp_daily_x          !! "Daily" gpp for teststomate 
894                                                                          !! @tex $(??gC m^{-2} dt_stomate^{-1})$ @endtex
895    REAL(r_std),DIMENSION(kjpindex,nvm)           :: veget_cov            !! Fractional coverage: actually share of the pixel
896                                                                          !! covered by a PFT (fraction of ground area covered),
897                                                                          !! taking into account LAI
898    INTEGER(i_std)                                :: ier                  !! Check errors in netcdf call (unitless)
899
900    INTEGER(i_std)                                :: max_totsize          !! Memory management - maximum memory size (Mb)
901    INTEGER(i_std)                                :: totsize_1step        !! Memory management - memory required to store one
902                                                                          !! time step on one processor (Mb)
903    INTEGER(i_std)                                :: totsize_tmp          !! Memory management - memory required to store one
904                                                                          !! time step on all processors(Mb)
905    INTEGER(i_std)                                :: vid                  !! Variable identifer of netCDF (unitless)
906    INTEGER(i_std)                                :: nneigh               !! Number of neighbouring pixels
907    INTEGER(i_std)                                :: direct               !!
908    INTEGER(i_std),DIMENSION(ndm)                 :: d_id                 !!
909    LOGICAL                                       :: l_error              !! error flag
910    REAL(r_std)                                   :: temp_total           !! Used for renormalizing
911    INTEGER(i_std),ALLOCATABLE, DIMENSION(:,:)    :: fm_map_temp          !! A temporary variable to hold the forest
912                                                                          !! management map which is read in from a file
913                                                                          !! (0-4,unitless)
914    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:)   :: species_map_temp     !! A temporary variable to hold the species
915                                                                          !! change map which is read in from a file
916                                                                          !! (1-nvm,unitless)
917    INTEGER(i_std)                                :: forest_managed_temp  !! Temporary variable to affect forest_managed(1,6)
918 !================================================================================================================================
919   
920    !! 1. Initialize variable
921
922    ! Initialize local printlev
923    !printlev_loc=get_printlev('stomate')
924
925    !! Update flag
926    l_first_stomate = .FALSE.
927   
928    !! 1.1 Store current time step in a common variable
929    itime = kjit
930   
931    !![DISPENSABLE] 1.2 Copy the depth of the different soil layers from diaglev specified in slow_proc
932   
933    !! 1.3 PFT rooting depth across pixels, humescte is pre-defined
934    ! (constantes_veg.f90). It is defined as the coefficient of an exponential
935    ! function relating root density to depth
936    DO j=1,nvm
937       rprof(:,j) = 1./humcste(j)
938    ENDDO
939   
940!!$    !! 1.3.1 Set lai
941!!$    lai(:,ibare_sechiba) = zero
942!!$    DO i = 1, kjpindex
943!!$       DO j = 2,nvm
944!!$          lai(i,j) = cc_to_lai(circ_class_biomass(i,j,:,ileaf,icarbon),circ_class_n(i,j,:),j)
945!!$       ENDDO
946!!$    ENDDO
947
948    !! 1.4.0 Parameters for spinup
949    !
950    eps_carbon = 0.01
951    !Config Key   = EPS_CARBON
952    !Config Desc  = Allowed error on carbon stock
953    !Config If    = SPINUP_ANALYTIC
954    !Config Def   = 0.01
955    !Config Help  =
956    !Config Units = [%]   
957    CALL getin_p('EPS_CARBON',eps_carbon)       
958   
959   
960    !Config Key   = SPINUP_PERIOD
961    !Config Desc  = Period to calulcate equilibrium during spinup analytic
962    !Config If    = SPINUP_ANALYTIC
963    !Config Def   = -1
964    !Config Help  = Period corresponds in most cases to the number of years of forcing data used in the spinup.
965    !Config Units = [years]   
966    spinup_period = -1
967    CALL getin_p('SPINUP_PERIOD',spinup_period)       
968   
969    ! Check spinup_period values.
970    ! For periods uptil 6 years, to obtain equilibrium, a bigger period have to be used
971    ! and therefore spinup_period is adjusted to 10 years.
972    IF (spinup_analytic) THEN
973       IF (spinup_period <= 0) THEN
974          WRITE(numout,*) 'Error in parameter spinup_period. This parameter must be > 0 : spinup_period=',spinup_period
975          CALL ipslerr_p (3,'stomate_initialize', &
976               'Parameter spinup_period must be set to a positive integer.', &
977               'Set this parameter to the number of years of forcing data used for the spinup.', &
978               '')
979       ELSE IF (spinup_period <= 6) THEN
980          ! Adjust to bigger period. The period must be a multiple of the original period.
981          WRITE(numout,*) 'Initial spinup_period =',spinup_period,' will be adjusted.'
982          spinup_period = spinup_period*(INT(9/spinup_period)+1)
983       END IF
984       WRITE(numout,*) 'Spinup analytic is activated using eps_carbon=',eps_carbon, ' and spinup_period=',spinup_period
985    END IF
986   
987    !! 1.4.0 Initialization of PFT specific parameters
988    ! Initialization of PFT specific parameters that have no value
989    ! for the bare soil PFT i.e. fire resistance, flamability, maximum lai,
990    ! settings for growing degree days (GDD), settings for senescence,
991    ! respiration coefficients, photosynthesis, etc.
992    ! [DISPENSABLE]
993   
994    !! 1.4.1 Allocate memory for all variables in stomate
995    ! Allocate memory for all variables in stomate, build new index
996    ! tables accounting for the PFTs, read and check flags and set file
997    ! identifier for restart and history files.
998    CALL stomate_init (kjpij, kjpindex, index, lalo, &
999         rest_id_stom, hist_id_stom, hist_id_stom_IPCC)
1000   
1001    !! 1.4.2 Initialization of PFT specific parameters
1002    ! Initialization of PFT specific parameters i.e. sla from leaf life,
1003    ! sapling characteristics (biomass), migration speed, critical diameter,
1004    ! coldest tolerable temperature, critical values for phenology, maximum
1005    ! life time of leaves, respiration coefficients and photosynthesis.
1006    ! The subroutine also communicates settings read by stomate_constant_init.
1007    CALL data (kjpindex, lalo)
1008   
1009    !! 1.4.3 Initial conditions
1010   
1011    !! 1.4.3.1 Read initial values for STOMATE's variables from
1012    !  the _restart_ file ??Shouldn't this be included in stomate_init??
1013    !  Looks like an initialization!
1014    co2_flux(:,:) = zero
1015    fco2_lu(:) = zero
1016   
1017    !! 1.4.3.2 Read the management status   
1018    !  This is the first call in this loop, It should just
1019    !  be initialised.
1020    forest_managed_lastyear(:,:) = 0
1021   
1022    !Config Key   = FOREST_MANAGED
1023    !Config Desc  = Forest management flag
1024    !Config If    = OK_STOMATE
1025    !Config Def   = 1: unmanaged, 2: high stand, 3: coppice,
1026    !               4: short rotation coppice
1027    !Config Help  =
1028    !Config Units = [-]
1029    ! forest management is always activated but a setting
1030    ! of ifm_none means don't do any human management.
1031    forest_managed(:,:) = ifm_none
1032    ! We need to things this was, instead of passing the whole array,
1033    ! since the domains of different processers will sometimes have
1034    ! different sizes, and calling MPI_BCAST with arrays of different
1035    ! sizes causes an error.  So we just read a single integer, BCAST
1036    ! that, and then change the arrays here.
1037    CALL getin_p('FOREST_MANAGED_FORCED',forest_managed_temp)
1038    IF(forest_managed_temp .NE. ifm_none)THEN
1039       forest_managed(:,:)=forest_managed_temp
1040    ENDIF
1041   
1042    ! We need to have the option to read the forest management
1043    ! strategy from a map (NetCDF file).  If this option is
1044    ! equal to Y, we will overwrite the forest_managed_forced
1045    ! option above, so you should be careful to only use one
1046    ! or the other.
1047    ! If we prescribe a species change we will also overwrite
1048    ! forest_managed so we don't want to read it from a file
1049    ! but we want to use the restart values
1050    IF(ok_read_fm_map)THEN
1051
1052       ! If we are using age classes, we read in the map in the same
1053       ! way but then we change it a bit to account for age classes.
1054       l_error = .FALSE.
1055       ALLOCATE(fm_map_temp(kjpindex,nvmap),stat=ier)
1056       l_error = l_error .OR. (ier /= 0)
1057       IF (l_error) THEN
1058          WRITE(numout,*) 'Problem with memory allocation: ' ,&
1059               'temporary FM map ',kjpindex,nvmap
1060          CALL ipslerr_p (3,'stomate_main', &
1061               'Problem with memory allocation','','')
1062       ENDIF
1063       
1064       CALL read_in_fm_map(kjpindex, lalo, neighbours, resolution, &
1065            contfrac, fm_map_temp)
1066       IF(nagec .GT. 1)THEN
1067          ! All age classes of the same PFT will have the same
1068          ! management
1069          DO jv = 1,nvm
1070             forest_managed(:,jv)=fm_map_temp(:,agec_group(jv))
1071          ENDDO
1072         
1073       ELSE
1074          forest_managed(:,:)=fm_map_temp(:,:)
1075         
1076       ENDIF
1077       
1078       DEALLOCATE(fm_map_temp)
1079       
1080    ENDIF
1081   
1082    ! Get values from _restart_ file. Note that only ::kjpindex, ::index, ::lalo
1083    ! and ::resolution are input variables, all others are output variables.
1084    CALL readstart &
1085         (kjpindex, index, lalo, resolution, t2m, &
1086         dt_days_read, date, &
1087         adapted, regenerate, &
1088         humrel_daily, gdd_init_date, litterhum_daily, &
1089         t2m_daily, t2m_min_daily, tsurf_daily, tsoil_daily, &
1090         soilhum_daily, precip_daily, &
1091         gpp_daily, npp_daily, turnover_daily, &
1092         humrel_month, humrel_week, humrel_growingseason,&
1093         t2m_longterm, tau_longterm, t2m_month, t2m_week, &
1094         tsoil_month, soilhum_month, fireindex, firelitter, &
1095         maxhumrel_lastyear, maxhumrel_thisyear, &
1096         minhumrel_lastyear, minhumrel_thisyear, &
1097         maxgppweek_lastyear, maxgppweek_thisyear, &
1098         gdd0_lastyear, gdd0_thisyear, &
1099         precip_lastyear, precip_thisyear, &
1100         gdd_m5_dormance,  gdd_from_growthinit, gdd_midwinter, &
1101         ncd_dormance, ngd_minus5, &
1102         PFTpresent, npp_longterm, lm_lastyearmax, lm_thisyearmax, &
1103         maxfpc_lastyear, maxfpc_thisyear, &
1104         turnover_longterm, gpp_week, resp_maint_part, &
1105         leaf_age, leaf_frac, plant_status, when_growthinit, age, &
1106         resp_hetero_d, resp_maint_d, resp_growth_d, co2_fire, atm_to_bm, &
1107         veget_lastlight, everywhere, need_adjacent, RIP_time, &
1108         time_hum_min, hum_min_dormance, &
1109         litter, dead_leaves, &
1110         som, lignin_struc, lignin_wood, turnover_time,&
1111         prod_s, prod_m, prod_l, flux_s, flux_m, flux_l, &
1112         flux_prod_s, flux_prod_m, flux_prod_l, &
1113         bm_to_litter, carb_mass_total, &
1114         Tseason, Tseason_length, Tseason_tmp, &
1115         Tmin_spring_time, onset_date, &
1116         global_years, ok_equilibrium, nbp_accu, nbp_flux, &
1117         nbp_accu_pool, nbp_pool, nbp_pool_start, &
1118         matrixV, vectorU, previous_stock, current_stock, &
1119         assim_param, CN_som_litter_longterm, &
1120         tau_CN_longterm, KF, k_latosa_adapt, &
1121         rue_longterm, cn_leaf_min_season, nstress_season, &
1122         soil_n_min, p_O2, bact, &
1123         circ_class_biomass, circ_class_n, store_sum_delta_ba, &
1124         forest_managed, forest_managed_lastyear, &
1125         species_change_map, fm_change_map, lpft_replant, lai_per_level, &
1126         laieff_fit, wstress_season, wstress_month, &
1127         age_stand, rotation_n, last_cut, mai, pai, &
1128         previous_wood_volume, mai_count, coppice_dens, &
1129         light_tran_to_level_season,veget_max, harvest_5y_area)
1130
1131    !! 1.4.3.4 Read litter raking map
1132    !  If we are doing litter raking, we need a map which
1133    !  tells us how much litter is required at every pixel.
1134    !  This number is independent of the PFTs. 
1135    IF(ok_litter_raking)THEN
1136       
1137       CALL read_in_litter_map(kjpindex, lalo, neighbours, resolution, &
1138            contfrac, litter_demand)
1139       
1140    ENDIF
1141
1142   
1143    !! 1.4.3.5 Read species with which to replant
1144    !  If we are doing species change, we need to read in the map or force
1145    !  the PFT values.  We do this after the restart because otherwise our
1146    !  values are overwritten. When we implement the species change we
1147    !  usually want to change FM as well (and sometime we even need it, i.e.,
1148    !  when the current FM strategy is to coppice and we change the species
1149    !  to a conifer tree than we will need to change FM because conifers are
1150    !  typically not coppiced). Species change and FM change were implemented
1151    !  separatly because that was easier to test and debug but not all
1152    !  combinations were tested. The recommended setting is read de FM_desired
1153    !  map when using species change.
1154    IF(ok_change_species)THEN
1155       
1156       IF(printlev_loc>=4) WRITE(numout,*) 'Use the species change code'
1157       
1158       ! Read species change map
1159       IF(ok_read_species_change_map)THEN
1160         
1161          WRITE(numout,*) 'Reading species change map'
1162         
1163          ! Allocate
1164          l_error = .FALSE.
1165          ALLOCATE(species_map_temp(kjpindex,nvmap),stat=ier)
1166          l_error = l_error .OR. (ier /= 0)
1167          IF (l_error) THEN
1168             WRITE(numout,*) 'Problem with memory allocation: ', &
1169                  kjpindex,nvmap
1170             CALL ipslerr_p (3,'stomate_main', &
1171                  'Problem with memory allocation',&
1172                  'temporary species change map','')
1173          ENDIF
1174         
1175          CALL read_in_species_change_map(kjpindex, lalo, neighbours, &
1176               resolution, contfrac, species_map_temp)
1177             
1178          ! If we are using age classes, we read in the map in the same
1179          ! way but then we change it a bit to account for age classes.
1180          IF(nagec .GT. 1)THEN
1181             
1182             ! All age classes of the same PFT will have the same
1183             ! management
1184             DO jv = 1,nvm
1185                species_change_map(:,jv)=species_map_temp(:,agec_group(jv))
1186             ENDDO
1187             
1188          ELSE
1189
1190             ! The number of pfts on the map is identical
1191             ! to the number of PFTs used in the simulation
1192             WRITE(numout,*) 'Reading single value for species change'
1193             species_change_map(:,:)=species_map_temp(:,:)
1194             
1195          ENDIF
1196
1197          DEALLOCATE(species_map_temp)
1198         
1199       ELSE
1200         
1201          IF(printlev_loc>=4) WRITE(numout,*) 'Species change map NOT read'
1202          IF(printlev_loc>=4) WRITE(numout,*) 'species_change_force, ', &
1203               species_change_force
1204          IF (species_change_force .EQ. -9999) THEN
1205
1206             ! If we end-up here the user has set-up the model
1207             ! such that we use the species_change code but only
1208             ! to change the management. To keep the code simple
1209             ! we will use a dummy species_change_map
1210             IF(printlev_loc>=4) WRITE(numout,*) 'Use veget_cov_max instead'
1211             
1212             ! All age classes of the same PFT will have the same
1213             ! management
1214             DO jv = 1,nvm
1215                species_change_map(:,jv) = agec_group(jv)
1216             ENDDO
1217             
1218          ELSE
1219             
1220             ! Use a single value (::species_change_force) instead
1221             ! of the information from a map. This was implemented
1222             ! as a feature for testing and/or debugging. It allows
1223             ! to test on a single pixel without reading maps.
1224             IF(printlev_loc>=4) WRITE(numout,*) 'Use ::species_change_force'
1225             species_change_map(:,:)=species_change_force
1226             
1227          ENDIF
1228         
1229       ENDIF
1230
1231       ! If we apply a species change we will also prescribe a new
1232       ! management strategy but we need to decide whether we will
1233       ! read the desired management from a map or use a single
1234       ! prescribed value instead
1235       
1236       ! Read species change map
1237       IF(ok_read_desired_fm_map)THEN
1238         
1239          WRITE(numout,*) 'Reading desired FM map'
1240          ! Allocate
1241          l_error = .FALSE.
1242          ALLOCATE(fm_map_temp(kjpindex,nvmap),stat=ier)
1243          l_error = l_error .OR. (ier /= 0)
1244          IF (l_error) THEN
1245             WRITE(numout,*) 'Problem with memory allocation: ', &
1246                  kjpindex,nvmap
1247             CALL ipslerr_p (3,'stomate_main', &
1248                  'Problem with memory allocation',&
1249                  'temporary fm change map','')
1250          ENDIF
1251         
1252          ! If we are using age classes, we read in the map in the same
1253          ! way but then we change it a bit to account for age classes.
1254          CALL read_in_desired_fm_map(kjpindex, lalo, neighbours, &
1255               resolution, contfrac, fm_map_temp)
1256         
1257          IF(nagec .GT. 1)THEN
1258             
1259             ! All age classes of the same PFT will have the same
1260             ! management
1261             DO jv = 1,nvm
1262                fm_change_map(:,jv)=fm_map_temp(:,agec_group(jv))
1263             ENDDO
1264             
1265          ELSE
1266             
1267             ! The number of pfts on the map is identical
1268             ! to the number of PFTs used in the simulation
1269             fm_change_map(:,:)=fm_map_temp(:,:)
1270             
1271          ENDIF
1272         
1273          DEALLOCATE(fm_map_temp)
1274         
1275       ELSE
1276         
1277          IF(printlev_loc>=4) WRITE(numout,*) 'fm change map NOT read'
1278          IF(printlev_loc>=4) WRITE(numout,*) 'fm_change_force, ',fm_change_force
1279          IF(fm_change_force .EQ. -9999) THEN
1280             
1281             ! If we end-up here the user has set-up the model
1282             ! such that we use the species_change code but only
1283             ! to change the species while keeping the management
1284             ! constant. To keep the code simple we will use a
1285             ! dummy fm_change_map
1286             IF(printlev_loc>=4) WRITE(numout,*) 'Use forest_managed instead'
1287             fm_change_map(:,:)=forest_managed(:,:)
1288             
1289          ELSE
1290             
1291             ! Use a single value (::species_change_force) instead
1292             ! of the information from a map. This was implemented
1293             ! as a feature for testing and/or debugging. It allows
1294             ! to test on a single pixel without reading maps.
1295             IF(printlev_loc>=4) WRITE(numout,*) 'Use ::fm_change_force'
1296             fm_change_map(:,:)=fm_change_force
1297             
1298          ENDIF
1299         
1300       ENDIF
1301       
1302    ENDIF
1303   
1304    !! 1.4.5 Check time step
1305       
1306    !! 1.4.5.1 Allow STOMATE's time step to change although this is dangerous
1307    IF (dt_days /= dt_days_read) THEN
1308       WRITE(numout,*) 'slow_processes: STOMATE time step changes:', &
1309            & dt_days_read,' -> ',dt_days
1310    ENDIF
1311   
1312    !! 1.4.5.2 Time step has to be a multiple of a full day
1313    IF ( ( dt_days-REAL(NINT(dt_days),r_std) ) > min_stomate ) THEN
1314       WRITE(numout,*) 'slow_processes: STOMATE time step is not a mutiple of a full day:', &
1315            & dt_days,' days.'
1316       STOP
1317    ENDIF
1318   
1319    !! 1.4.5.3 upper limit to STOMATE's time step
1320    IF ( dt_days > max_dt_days ) THEN
1321       WRITE(numout,*) 'slow_processes: STOMATE time step exceeds the maximum value:', &
1322            & dt_days,' days > ', max_dt_days, ' days.' 
1323       STOP
1324    ENDIF
1325   
1326    !! 1.4.5.4 STOMATE time step must not be less than the forcing time step
1327    IF ( dt_sechiba > dt_days*one_day ) THEN
1328       WRITE(numout,*) &
1329            & 'slow_processes: STOMATE time step ::dt_days smaller than forcing time step ::dt_sechiba'
1330       STOP
1331    ENDIF
1332   
1333    !! 1.4.5.6 Final message on time step
1334    WRITE(numout,*) 'Slow_processes, STOMATE time step (days): ', dt_days
1335   
1336    !! 1.4.6 Write forcing file for teststomate
1337    IF (allow_forcing_write) THEN
1338       
1339       !Config Key   = STOMATE_FORCING_NAME
1340       !Config Desc  = Name of STOMATE's forcing file
1341       !Config If    = OK_STOMATE
1342       !Config Def   = NONE
1343       !Config Help  = Name that will be given
1344       !Config         to STOMATE's offline forcing file
1345       !Config         Compatible with Nicolas Viovy's driver
1346       !Config Units = [FILE]
1347       forcing_name = stomate_forcing_name
1348       CALL getin_p('STOMATE_FORCING_NAME',forcing_name)
1349       
1350       IF ( TRIM(forcing_name) /= 'NONE' ) THEN
1351         
1352          !! 1.4.6.1 Calculate steps that can be stored in memory
1353          ! Action for the root processor only (parallel computing) 
1354          IF (is_root_prc) CALL SYSTEM ('rm -f '//TRIM(forcing_name))
1355          WRITE(numout,*) 'writing a forcing file for STOMATE.'
1356         
1357          !Config Key   = STOMATE_FORCING_MEMSIZE
1358          !Config Desc  = Size of STOMATE forcing data in memory
1359          !Config If    = OK_STOMATE
1360          !Config Def   = 50
1361          !Config Help  = This variable determines how many
1362          !Config         forcing states will be kept in memory.
1363          !Config         Must be a compromise between memory
1364          !Config         use and frequeny of disk access.
1365          !Config Units = [MegaBytes]
1366          max_totsize = 50
1367          CALL getin_p('STOMATE_FORCING_MEMSIZE', max_totsize)     
1368          max_totsize = max_totsize*1000000
1369         
1370          totsize_1step = &
1371               SIZE(clay)*KIND(clay) &
1372               +SIZE(silt)*KIND(silt) &
1373               +SIZE(bulk)*KIND(bulk) &
1374               +SIZE(humrel_daily)*KIND(humrel_daily) &
1375               +SIZE(litterhum_daily)*KIND(litterhum_daily) &
1376               +SIZE(t2m_daily)*KIND(t2m_daily) &
1377               +SIZE(t2m_min_daily)*KIND(t2m_min_daily) &
1378               +SIZE(tsurf_daily)*KIND(tsurf_daily) &
1379               +SIZE(tsoil_daily)*KIND(tsoil_daily) &
1380               +SIZE(soilhum_daily)*KIND(soilhum_daily) &
1381               +SIZE(precip_daily)*KIND(precip_daily) &
1382               +SIZE(gpp_daily_x)*KIND(gpp_daily_x) &
1383               +SIZE(veget)*KIND(veget) &
1384               +SIZE(veget_max)*KIND(veget_max) &
1385!!$               +SIZE(lai)*KIND(lai) &   
1386               +SIZE(drainage_daily)*KIND(drainage_daily) 
1387         
1388          ! Totsize_1step is the size on a single processor, sum
1389          ! all processors and send to all processors
1390          CALL reduce_sum(totsize_1step,totsize_tmp)
1391          CALL bcast(totsize_tmp)
1392          totsize_1step=totsize_tmp
1393         
1394          ! Total number of forcing steps
1395          nsft = INT(one_year/(dt_stomate/one_day))
1396         
1397          ! Number of forcing steps in memory
1398          nsfm = MIN(nsft, &
1399               MAX(1,NINT( REAL(max_totsize,r_std) &
1400               /REAL(totsize_1step,r_std))))
1401           
1402             
1403          !! 1.6.4.2 Allocate memory for variables containing forcing data 
1404          ! and initialize variables (set to zero).
1405          CALL init_forcing (kjpindex,nsfm,nsft)
1406         
1407          ! Indexing for writing forcing file
1408          isf(:) = (/ (i,i=1,nsfm) /)
1409          nf_written(:) = .FALSE.
1410          nf_cumul(:) = 0
1411          iisf = 0
1412         
1413          !! 1.6.4.3 Create netcdf file
1414          ! Create, define and populate a netcdf file containing the forcing data.
1415          ! For the root processor only (parallel computing). NF90_ are functions
1416          ! from and external library. 
1417          IF (is_root_prc) THEN
1418             
1419             ! Create new netCDF dataset
1420             ier = NF90_CREATE (TRIM(forcing_name),NF90_SHARE,forcing_id)
1421             
1422             ! Add variable attribute
1423             ! Note ::iim_g and ::jjm_g are dimensions of the global field and
1424             ! ::nbp_glo is the number of global continental points
1425             ier = NF90_PUT_ATT (forcing_id,NF90_GLOBAL,'dt_sechiba',dt_sechiba)
1426             ier = NF90_PUT_ATT (forcing_id,NF90_GLOBAL,'dt_stomate',dt_stomate)
1427             ier = NF90_PUT_ATT (forcing_id,NF90_GLOBAL, &
1428                  'nsft',REAL(nsft,r_std))
1429             ier = NF90_PUT_ATT (forcing_id,NF90_GLOBAL, &
1430                  'kjpij',REAL(iim_g*jjm_g,r_std))
1431             ier = NF90_PUT_ATT (forcing_id,NF90_GLOBAL, &
1432                  'kjpindex',REAL(nbp_glo,r_std))
1433             
1434             ! Add new dimension
1435             ier = NF90_DEF_DIM (forcing_id,'points',nbp_glo,d_id(1))
1436             ier = NF90_DEF_DIM (forcing_id,'layers',nbdl,d_id(2))
1437             ier = NF90_DEF_DIM (forcing_id,'pft',nvm,d_id(3))
1438             direct=2
1439             ier = NF90_DEF_DIM (forcing_id,'direction',direct,d_id(4))
1440             nneigh=8
1441             ier = NF90_DEF_DIM (forcing_id,'nneigh',nneigh,d_id(5))
1442             ier = NF90_DEF_DIM (forcing_id,'time',NF90_UNLIMITED,d_id(6))
1443             ier = NF90_DEF_DIM (forcing_id,'nbparts',nparts,d_id(7))
1444             
1445             ! Add new variable
1446             ier = NF90_DEF_VAR (forcing_id,'points',    r_typ,d_id(1),vid)
1447             ier = NF90_DEF_VAR (forcing_id,'layers',    r_typ,d_id(2),vid)
1448             ier = NF90_DEF_VAR (forcing_id,'pft',       r_typ,d_id(3),vid)
1449             ier = NF90_DEF_VAR (forcing_id,'direction', r_typ,d_id(4),vid)
1450             ier = NF90_DEF_VAR (forcing_id,'nneigh',    r_typ,d_id(5),vid)
1451             ier = NF90_DEF_VAR (forcing_id,'time',      r_typ,d_id(6),vid)
1452             ier = NF90_DEF_VAR (forcing_id,'nbparts',   r_typ,d_id(7),vid)
1453             ier = NF90_DEF_VAR (forcing_id,'index',     r_typ,d_id(1),vid)
1454             ier = NF90_DEF_VAR (forcing_id,'contfrac',  r_typ,d_id(1),vid) 
1455             ier = NF90_DEF_VAR (forcing_id,'lalo', &
1456                  r_typ,(/ d_id(1),d_id(4) /),vid)
1457             ier = NF90_DEF_VAR (forcing_id,'neighbours', &
1458                  r_typ,(/ d_id(1),d_id(5) /),vid)
1459             ier = NF90_DEF_VAR (forcing_id,'resolution', &
1460                  r_typ,(/ d_id(1),d_id(4) /),vid)
1461             ier = NF90_DEF_VAR (forcing_id,'clay', &
1462                  r_typ,(/ d_id(1),d_id(6) /),vid)
1463             ier = NF90_DEF_VAR (forcing_id,'silt', & 
1464                  r_typ,(/ d_id(1),d_id(6) /),vid) 
1465             ier = NF90_DEF_VAR (forcing_id,'bulk', & 
1466                  r_typ,(/ d_id(1),d_id(6) /),vid) 
1467             ier = NF90_DEF_VAR (forcing_id,'humrel', &
1468                  r_typ,(/ d_id(1),d_id(3),d_id(6) /),vid)
1469             ier = NF90_DEF_VAR (forcing_id,'litterhum', &
1470                  r_typ,(/ d_id(1),d_id(6) /),vid)
1471             ier = NF90_DEF_VAR (forcing_id,'t2m', &
1472                  r_typ,(/ d_id(1),d_id(6) /),vid)
1473             ier = NF90_DEF_VAR (forcing_id,'t2m_min', &
1474                  r_typ,(/ d_id(1),d_id(6) /),vid)
1475             ier = NF90_DEF_VAR (forcing_id,'tsurf', &
1476                  r_typ,(/ d_id(1),d_id(6) /),vid)
1477             ier = NF90_DEF_VAR (forcing_id,'tsoil', &
1478                  r_typ,(/ d_id(1),d_id(2),d_id(6) /),vid)
1479             ier = NF90_DEF_VAR (forcing_id,'soilhum', &
1480                  r_typ,(/ d_id(1),d_id(2),d_id(6) /),vid)
1481             ier = NF90_DEF_VAR (forcing_id,'precip', &
1482                  r_typ,(/ d_id(1),d_id(6) /),vid)
1483             ier = NF90_DEF_VAR (forcing_id,'gpp', &
1484                  r_typ,(/ d_id(1),d_id(3),d_id(6) /),vid)
1485             ier = NF90_DEF_VAR (forcing_id,'veget', &
1486                  r_typ,(/ d_id(1),d_id(3),d_id(6) /),vid)
1487             ier = NF90_DEF_VAR (forcing_id,'veget_max', &
1488                  r_typ,(/ d_id(1),d_id(3),d_id(6) /),vid)
1489!!$             ier = NF90_DEF_VAR (forcing_id,'lai', &
1490!!$                  r_typ,(/ d_id(1),d_id(3),d_id(6) /),vid)
1491             ier = NF90_DEF_VAR (forcing_id,'drainage', & 
1492                  r_typ,(/ d_id(1),d_id(6),d_id(6) /),vid) 
1493             ier = NF90_ENDDEF (forcing_id)
1494             
1495             ! Given the name of a varaible, nf90_inq_varid finds the variable
1496             ! ID (::vid). Put data value(s) into variable ::vid
1497             ier = NF90_INQ_VARID (forcing_id,'points',vid)
1498             ier = NF90_PUT_VAR (forcing_id,vid, &
1499                  (/(REAL(i,r_std),i=1,nbp_glo) /))
1500             ier = NF90_INQ_VARID (forcing_id,'layers',vid)
1501             ier = NF90_PUT_VAR (forcing_id,vid,(/(REAL(i,r_std),i=1,nbdl)/))
1502             ier = NF90_INQ_VARID (forcing_id,'pft',vid)
1503             ier = NF90_PUT_VAR (forcing_id,vid,(/(REAL(i,r_std),i=1,nvm)/))
1504             ier = NF90_INQ_VARID (forcing_id,'direction',vid)
1505             ier = NF90_PUT_VAR (forcing_id,vid,(/(REAL(i,r_std),i=1,2)/))
1506             ier = NF90_INQ_VARID (forcing_id,'nneigh',vid)
1507             ier = NF90_PUT_VAR (forcing_id,vid,(/(REAL(i,r_std),i=1,8)/))
1508             ier = NF90_INQ_VARID (forcing_id,'time',vid)
1509             ier = NF90_PUT_VAR (forcing_id,vid,(/(REAL(i,r_std),i=1,nsft)/))
1510             ier = NF90_INQ_VARID (forcing_id,'nbparts',vid)
1511             ier = NF90_PUT_VAR (forcing_id,vid,(/(REAL(i,r_std),i=1,nparts)/))
1512             ier = NF90_INQ_VARID (forcing_id,'index',vid) 
1513             ier = NF90_PUT_VAR (forcing_id,vid,REAL(index_g,r_std))
1514             ier = NF90_INQ_VARID (forcing_id,'contfrac',vid)
1515             ier = NF90_PUT_VAR (forcing_id,vid,REAL(contfrac_g,r_std))
1516             ier = NF90_INQ_VARID (forcing_id,'lalo',vid)
1517             ier = NF90_PUT_VAR (forcing_id,vid,lalo_g)
1518             !ym attention a neighbours, a modifier plus tard     
1519             ier = NF90_INQ_VARID (forcing_id,'neighbours',vid)
1520             ier = NF90_PUT_VAR (forcing_id,vid,REAL(neighbours_g,r_std))
1521             ier = NF90_INQ_VARID (forcing_id,'resolution',vid)
1522             ier = NF90_PUT_VAR (forcing_id,vid,resolution_g)
1523          ENDIF ! is_root_prc
1524       ENDIF ! (forcing_name) /= 'NONE'
1525    ENDIF 
1526   
1527    !! 1.4.7 write forcing file for forcesoil
1528    !! 1.4.7.1 Initialize
1529    !Config Key   = STOMATE_CFORCING_NAME
1530    !Config Desc  = Name of STOMATE's carbon forcing file
1531    !Config If    = OK_STOMATE
1532    !Config Def   = NONE
1533    !Config Help  = Name that will be given to STOMATE's carbon
1534    !Config         offline forcing file
1535    !Config         Compatible with Nicolas Viovy's driver
1536    !Config Units = [FILE]
1537    Cforcing_name = stomate_Cforcing_name
1538    CALL getin_p('STOMATE_CFORCING_NAME',Cforcing_name)
1539   
1540    IF ( TRIM(Cforcing_name) /= 'NONE' ) THEN
1541       
1542       ! Time step of forcesoil
1543       !Config Key   = FORCESOIL_STEP_PER_YEAR
1544       !Config Desc  = Number of time steps per year for carbon spinup.
1545       !Config If    = OK_STOMATE
1546       !Config Def   = 365
1547       !Config Help  = Number of time steps per year for carbon spinup.
1548       !Config Units = [days, months, year]
1549       nparan = 365
1550       CALL getin_p('FORCESOIL_STEP_PER_YEAR', nparan)
1551       
1552       ! Correct if setting is out of bounds
1553       IF ( nparan < 1 ) nparan = 1
1554       
1555       !Config Key   = FORCESOIL_NB_YEAR
1556       !Config Desc  = Number of years saved for carbon spinup.
1557       !Config If    = OK_STOMATE
1558       !Config Def   = 1
1559       !Config Help  = Number of years saved for carbon spinup. If internal parameter cumul_Cforcing is TRUE in stomate.f90
1560       !Config         Then this parameter is forced to one.
1561       !Config Units = [years]
1562       CALL getin_p('FORCESOIL_NB_YEAR', nbyear)
1563       
1564       ! Set ::nbyear to 1. if ::cumul_Cforcing=.TRUE.
1565       IF ( cumul_Cforcing ) THEN
1566          CALL ipslerr_p (1,'stomate', &
1567               'Internal parameter cumul_Cforcing is TRUE in stomate.f90', &
1568               'Parameter FORCESOIL_NB_YEAR is therefore forced to 1.', &
1569               '::nbyear is thus set to 1.')
1570          nbyear=1
1571       ENDIF
1572       
1573       ! Make use of ::nparan to calculate ::dt_forcesoil
1574       dt_forcesoil = zero
1575       nparan = nparan+1
1576       DO WHILE ( dt_forcesoil < dt_stomate/one_day )
1577          nparan = nparan-1
1578          IF ( nparan < 1 ) THEN
1579             STOP 'Problem with number of soil forcing time steps ::nparan < 1.'
1580          ENDIF
1581          dt_forcesoil = one_year/REAL(nparan,r_std)
1582       ENDDO
1583       IF ( nparan > nparanmax ) THEN
1584          STOP 'Problem with number of soil forcing time steps ::nparan > ::nparanmax'
1585       ENDIF
1586       WRITE(numout,*) 'Time step of soil forcing (d): ',dt_forcesoil
1587       
1588       ! Allocate memory for the forcing variables of soil dynamics
1589       ALLOCATE( nforce(nparan*nbyear))
1590       nforce(:) = 0
1591       ALLOCATE(control_moist(kjpindex,nlevs,nparan*nbyear))
1592       ALLOCATE(npp_equil(kjpindex,nparan*nbyear))
1593       ALLOCATE(npp_tot(kjpindex))
1594       ALLOCATE(control_temp(kjpindex,nlevs,nparan*nbyear))
1595       ALLOCATE(carbon_input(kjpindex,ncarb,nvm,nparan*nbyear)) 
1596       ALLOCATE(nitrogen_input(kjpindex,ncarb,nvm,nparan*nbyear)) 
1597       ALLOCATE(drainage(kjpindex,nvm,nparan*nbyear))         
1598
1599       ! Initialize variables, set to zero
1600       control_moist(:,:,:) = zero
1601       npp_equil(:,:) = zero
1602       npp_tot(:) = zero
1603       control_temp(:,:,:) = zero
1604       carbon_input(:,:,:,:) = zero
1605       nitrogen_input(:,:,:,:) = zero
1606       drainage(:,:,:) = zero 
1607    ENDIF ! Cforcing_name) /= 'NONE'
1608   
1609    !! 1.4.8 Calculate STOMATE's vegetation fractions from veget, veget_max
1610    DO j=1,nvm
1611       WHERE ((1.-totfrac_nobio(:)) > min_sechiba)       
1612          ! Pixels with vegetation
1613          veget_cov(:,j) = veget(:,j)/( 1.-totfrac_nobio(:) )
1614          veget_cov_max(:,j) = veget_max(:,j)/( 1.-totfrac_nobio(:) )
1615       ELSEWHERE
1616          ! Pixels without vegetation
1617          veget_cov(:,j) = zero
1618          veget_cov_max(:,j) = zero
1619       ENDWHERE
1620    ENDDO ! Loop over PFTs
1621
1622    !! 1.4.9 Initialize non-zero variables
1623    CALL stomate_var_init &
1624         (kjpindex, veget_cov_max, leaf_age, leaf_frac, &
1625         dead_leaves, &
1626         veget_cov, deadleaf_cover, assim_param, &
1627         circ_class_biomass, circ_class_n)
1628   
1629    l_error =.FALSE.
1630    ALLOCATE(circ_class_dist(ncirc),stat=ier)
1631    l_error = l_error .OR. (ier /= 0)
1632    IF (l_error) THEN
1633       WRITE(numout,*) ' Memory allocation error for circ_class_dist. ' // &
1634            'We need ncirc words = ',ncirc
1635       CALL ipslerr_p (3,'stomate_main', &
1636            'Memory allocation error for circ_class_dist','','')
1637    END IF
1638    !Config Key   = CIRC_CLASS_DIST
1639    !Config Desc  = The tree distribution to target if we have to redistribute.
1640    !Config if    = OK_STOMATE
1641    !Config Def   = 1
1642    !Config Help  =
1643    !Config Units = [-]
1644    circ_class_dist(:)=un
1645    CALL getin_p('CIRC_CLASS_DIST',circ_class_dist)
1646   
1647    ! Now we normalize the distribution
1648    temp_total=SUM(circ_class_dist(:))
1649    circ_class_dist(:)=circ_class_dist(:)/temp_total
1650    WRITE(numout,*) 'Target distribution for renormalization: ',circ_class_dist(:)
1651
1652    ALLOCATE(st_dist(ncirc),stat=ier)
1653    l_error = l_error .OR. (ier /= 0)
1654    IF (l_error) THEN
1655       WRITE(numout,*) ' Memory allocation error for st_dist. ' // &
1656            'We need ncirc words = ',ncirc
1657       CALL ipslerr_p (3,'stomate_main', &
1658            ' Memory allocation error for st_dist.','','')
1659    END IF
1660    !Config Key   = ST_DIST
1661    !Config Desc  = The distribution for killing trees in self-thinning.
1662    !Config if    = OK_STOMATE
1663    !Config Def   = circ_class_dist
1664    !Config Help  =
1665    !Config Units = [-]
1666    st_dist(:)=circ_class_dist(:)
1667    CALL getin_p('ST_DIST',st_dist)
1668   
1669    ! Now we normalize the distribution
1670    temp_total=SUM(st_dist(:))
1671    st_dist(:)=st_dist(:)/temp_total
1672    WRITE(numout,*) 'Target distribution for self-thinning: ',st_dist(:)
1673   
1674  END SUBROUTINE stomate_initialize
1675 
1676
1677!! ================================================================================================================================
1678!! SUBROUTINE   : stomate_main
1679!!
1680!>\BRIEF        Manages variable initialisation, reading and writing forcing
1681!! files, aggregating data at stomate's time step (dt_stomate), aggregating data
1682!! at longer time scale (i.e. for phenology) and uses these forcing to calculate
1683!! CO2 fluxes (NPP and respirations) and C-pools (litter, soil, biomass, ...)
1684!!
1685!! DESCRIPTION  : The subroutine manages
1686!! divers tasks:
1687!! (1) Initializing all variables of stomate (first call)
1688!! (2) Reading and writing forcing data (last call)
1689!! (3) Adding CO2 fluxes to the IPCC history files
1690!! (4) Converting the time steps of variables to maintain consistency between
1691!! sechiba and stomate
1692!! (5) Use these variables to call stomate_lpj, maint_respiration, littercalc,
1693!! som. The called subroutines handle: climate constraints
1694!! for PFTs, PFT dynamics, Phenology, Allocation, NPP (based on GPP and
1695!! authothropic respiration), fire, mortality, vmax, assimilation temperatures,
1696!! all turnover processes, light competition, sapling establishment, lai, 
1697!! land cover change and litter and soil dynamics.
1698!! (6) Use the spin-up method developed by Lardy (2011)(only if SPINUP_ANALYTIC
1699!! is set to TRUE).
1700!!
1701!! RECENT CHANGE(S) : None
1702!!
1703!! MAIN OUTPUT VARIABLE(S): deadleaf_cover, assim_param, lai, height, veget_cov,
1704!! veget_cov_max, resp_maint,
1705!! resp_hetero,resp_growth, co2_flux, fco2_lu.
1706!!
1707!! REFERENCES   :
1708!! - Lardy, R, et al., A new method to determine soil organic carbon equilibrium,
1709!! Environmental Modelling & Software (2011), doi:10.1016|j.envsoft.2011.05.016
1710!!
1711!! FLOWCHART    :
1712!! \latexonly
1713!! \includegraphics[scale=0.5]{stomatemainflow.png}
1714!! \endlatexonly
1715!! \n
1716!_ ================================================================================================================================
1717 
1718  SUBROUTINE stomate_main &
1719       & (kjit, kjpij, kjpindex, &
1720       &  index, lalo, neighbours, resolution, contfrac, &
1721       &  totfrac_nobio, clay, silt, bulk, &
1722       &  t2m, temp_sol, stempdiag, &
1723       &  humrel, shumdiag, litterhumdiag, precip_rain, precip_snow, &
1724       &  tmc_pft, drainage_pft, swc_pft, gpp, &
1725       &  deadleaf_cover, assim_param, &
1726       &  frac_age, height, veget, veget_max, &
1727       &  veget_max_new, totfrac_nobio_new, &
1728       &  hist_id, hist2_id, rest_id_stom, hist_id_stom, hist_id_stom_IPCC, &
1729       &  co2_flux, fco2_lu, resp_maint, resp_hetero, &
1730       &  resp_growth, temp_growth, &
1731       &  soil_pH, pb, n_input, circ_class_biomass, &
1732       &  circ_class_n, lai_per_level, &
1733       &  laieff_fit, h_array_out, z_array_out, max_height_store, &
1734       &  transpir, transpir_mod, transpir_supply, vir_transpir_supply, &
1735       &  coszang, stressed, unstressed, Isotrop_Tran_Tot_p, &
1736       &  u, v) 
1737
1738    IMPLICIT NONE
1739
1740
1741    !! 0. Variable and parameter declaration
1742
1743    !! 0.1 Input variables
1744
1745    INTEGER(i_std),INTENT(in)                       :: kjit              !! Time step number (unitless)
1746    INTEGER(i_std),INTENT(in)                       :: kjpindex          !! Domain size - terrestrial pixels only (unitless)
1747    INTEGER(i_std),INTENT(in)                       :: kjpij             !! Total size of the un-compressed grid (unitless)
1748    INTEGER(i_std),INTENT(in)                       :: rest_id_stom      !! STOMATE's _Restart_ file identifier (unitless)
1749    INTEGER(i_std),INTENT(in)                       :: hist_id_stom      !! STOMATE's _history_ file identifier (unitless)
1750    INTEGER(i_std),INTENT(in)                       :: hist_id_stom_IPCC !! STOMATE's IPCC _history_ file identifier
1751    !! (unitless)
1752    INTEGER(i_std),DIMENSION(kjpindex),INTENT(in)   :: index             !! Indices of the pixels on the map. Stomate uses a
1753    !! reduced grid excluding oceans. ::index contains
1754    !! the indices of the terrestrial pixels only
1755    !! (unitless)
1756    INTEGER(i_std),DIMENSION(kjpindex,8),INTENT(in) :: neighbours        !! Neighoring grid points if land for the DGVM
1757    !! (unitless)
1758    REAL(r_std),DIMENSION(kjpindex,2),INTENT(in)    :: lalo              !! Geographical coordinates (latitude,longitude)
1759    !! for pixels (degrees)
1760    REAL(r_std),DIMENSION(kjpindex,2),INTENT(in)    :: resolution        !! Size in x an y of the grid (m) - surface area of
1761    !! the gridbox
1762    REAL(r_std),DIMENSION (kjpindex), INTENT (in)   :: contfrac          !! Fraction of continent in the grid cell (unitless)
1763    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: totfrac_nobio     !! Fraction of grid cell covered by lakes, land
1764    !! ice, cities, ... (unitless)
1765    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: clay              !! Clay fraction of soil (0-1, unitless)
1766    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: silt              !! Silt fraction of soil (0-1, unitless)
1767    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: bulk              !! Bulk density (kg/m**3)
1768    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)  :: humrel            !! Relative humidity ("moisture availability")
1769    !! (0-1, unitless)
1770    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: t2m               !! 2 m air temperature (K)
1771    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: temp_sol          !! Surface temperature (K)
1772    REAL(r_std),DIMENSION(kjpindex,nbdl),INTENT(in) :: stempdiag         !! Soil temperature (K)
1773    REAL(r_std),DIMENSION(kjpindex,nbdl),INTENT(in) :: shumdiag          !! Relative soil moisture (0-1, unitless)
1774    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: litterhumdiag     !! Litter humidity (0-1, unitless)
1775    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)  :: transpir          !! transpiration @tex $(kg m^{-2} timestep^{-1})$
1776    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)  :: transpir_mod      !! transpir divided by veget_cov_max
1777    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)  :: transpir_supply   !! Supply of water for transpiration @tex $(mm dt^{-1})$ @endtex
1778    REAL(r_std),DIMENSION(:,:),INTENT(in)           :: vir_transpir_supply !! Virtual supply of water for transpiration to deal
1779    !! with water stress when PFT1 becomes vegetated in LCC
1780    !! @tex $(mm dt^{-1})$ @endtex
1781    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: precip_rain       !! Rain precipitation 
1782    !! @tex $(mm dt_stomate^{-1})$ @endtex
1783    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: precip_snow       !! Snow precipitation 
1784    !! @tex $(mm dt_stomate^{-1})$ @endtex
1785    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)  :: tmc_pft           !! Total soil water per PFT (mm/m2)
1786    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)  :: drainage_pft      !! Drainage per PFT (mm/m2)   
1787    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)  :: swc_pft           !! Relative Soil water content [tmcr:tmcs] per pft (-)   
1788    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)  :: gpp               !! GPP of total ground area 
1789   
1790! Import wind speed from stomate_main via slowproc
1791    REAL(r_std),DIMENSION(kjpindex),INTENT (in)     :: u                 !! Lowest level wind speed in direction u (m/s)
1792    REAL(r_std),DIMENSION(kjpindex),INTENT (in)     :: v                 !! Lowest level wind speed in direction v (m/s)
1793 
1794
1795!! @tex $(gC m^{-2} time step^{-1})$ @endtex
1796    !! Calculated in sechiba, account for vegetation
1797    !! cover and effective time step to obtain ::gpp_d
1798
1799    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(inout)  :: veget_max_new  !! New "maximal" coverage fraction of a PFT: only if
1800    !! vegetation is updated in slowproc
1801
1802    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: totfrac_nobio_new !! Old fraction of nobio per gridcell
1803    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: soil_pH           !! soil pH     
1804    REAL(r_std),DIMENSION(kjpindex), INTENT(in)     :: pb                !! Air pressure (hPa)
1805    REAL(r_std),DIMENSION(:,:,:),INTENT(inout)      :: n_input           !! Nitrogen inputs into the soil  (gN/m**2/timestep)
1806
1807    INTEGER(i_std),INTENT(in)                       :: hist_id           !! ?? [DISPENSABLE] SECHIBA's _history_ file
1808    !! identifier
1809    INTEGER(i_std),INTENT(in)                       :: hist2_id          !! ?? [DISPENSABLE] SECHIBA's _history_ file 2
1810    !! identifier
1811    REAL(r_std),DIMENSION(kjpindex), INTENT(in)     :: coszang           !! the cosine of the zenith angle   
1812    REAL(r_std),DIMENSION (:,:,:), INTENT (in)      :: Isotrop_Tran_Tot_p!! Transmitted radiation per level (unitless)
1813
1814
1815    !! 0.2 Output variables
1816
1817    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: co2_flux          !! CO2 flux between atmosphere and biosphere per
1818    !! average ground area
1819    !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex 
1820    !! [??CHECK] sign convention?
1821    REAL(r_std),DIMENSION(kjpindex),INTENT(out)     :: fco2_lu           !! CO2 flux between atmosphere and biosphere from
1822    !! land-use (without forest management) 
1823    !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex 
1824    !! [??CHECK] sign convention?
1825    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: resp_maint        !! Maitenance component of autotrophic respiration in
1826    !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
1827    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: resp_growth       !! Growth component of autotrophic respiration in
1828    !! @tex ($gC m^{-2} dt_stomate^{-1}$) @endtex
1829    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: resp_hetero       !! Heterotrophic respiration in 
1830    !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex 
1831    REAL(r_std),DIMENSION(kjpindex),INTENT(out)     :: temp_growth       !! Growth temperature (°C) 
1832    !! Is equal to t2m_month
1833    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: max_height_store  !! ???
1834
1835
1836    !! 0.3 Modified
1837
1838!!$    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(inout)       :: lai            !! Leaf area inex @tex $(m^2 m^{-2})$ @endtex
1839    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)          :: veget          !! Fraction of vegetation type including
1840    !! non-biological fraction (unitless)
1841    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(inout)       :: veget_max      !! Maximum fraction of vegetation type including
1842    !! non-biological fraction (unitless)
1843    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(inout)       :: height         !! Height of vegetation (m)
1844    REAL(r_std),DIMENSION(kjpindex,nvm,npco2),INTENT(inout) :: assim_param    !! min+max+opt temperatures (K) & vmax, nue and leaf N for
1845    !! photosynthesis 
1846    !! @tex $(\mu mol m^{-2}s^{-1})$ @endtex 
1847    REAL(r_std),DIMENSION(kjpindex),INTENT(inout)           :: deadleaf_cover !! Fraction of soil covered by dead leaves
1848    !! (unitless)
1849    REAL(r_std),DIMENSION(kjpindex,nvm,nleafages), &                          !! Age efficacity from STOMATE
1850         INTENT(inout)         :: frac_age       
1851    REAL(r_std), DIMENSION(kjpindex,nvm,ncirc,nparts,nelements), &            !! Biomass per circumference class @tex $(gC tree^{-1})$ @endtex
1852         INTENT(inout)                                      :: circ_class_biomass 
1853    REAL(r_std), DIMENSION(kjpindex,nvm,ncirc), &                             !! Number of trees within each circumference
1854         INTENT(inout)         :: circ_class_n   !! Biomass per PFT
1855    REAL(r_std), DIMENSION(:,:,:), INTENT(inout)            :: lai_per_level  !! This is the LAI per vertical level
1856    !! @tex $(m^{2} m^{-2})$ @endtex
1857    TYPE(laieff_type),DIMENSION (:,:,:), INTENT(inout)      :: laieff_fit     !! Fitted parameters for the effective LAI
1858
1859    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(inout)       :: stressed       !! adjusted ecosystem functioning. Takes the unit of the variable
1860    !! used as a proxy for waterstress (assigned in sechiba).
1861    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(inout)       :: unstressed     !! initial ecosystem functioning after the first calculation and
1862    !! before any recalculations. Takes the unit of the variable used
1863    !! as a proxy for unstressed (assigned in sechiba).
1864    REAL(r_std),DIMENSION(:,:,:,:), INTENT(inout)           :: h_array_out    !! An output of h_array, to use in sechiba
1865    REAL(r_std),DIMENSION(:,:,:,:), INTENT(inout)           :: z_array_out    !! An output of h_array, to use in sechiba
1866
1867
1868    !! 0.4 local variables
1869
1870    CHARACTER(LEN=2), DIMENSION(nelements)        :: element_str              !! string suffix indicating element   
1871    REAL(r_std)                                   :: dt_days_read             !! STOMATE time step read in restart file (days)
1872    INTEGER(i_std)                                :: l,k,ji, jv, i, j, m      !! indices   
1873    REAL(r_std),PARAMETER                         :: max_dt_days = 5.         !! Maximum STOMATE time step (days)
1874    REAL(r_std)                                   :: hist_days                !! Writing frequency for history file (days)
1875    REAL(r_std),DIMENSION(0:nbdl)                 :: z_soil                   !! Variable to store depth of the different soil
1876    !! layers (m)
1877    REAL(r_std),DIMENSION(kjpindex,nvm)           :: rprof                    !! Coefficient of the exponential functions that
1878    !! relates root density to soil depth (unitless)
1879    REAL(r_std),DIMENSION(kjpindex)               :: cvegtot                  !! Total "vegetation" cover (unitless)
1880    REAL(r_std),DIMENSION(kjpindex)               :: precip                   !! Total liquid and solid precipitation 
1881    !! @tex $(??mm dt_stomate^{-1})$ @endtex
1882    REAL(r_std),DIMENSION(kjpindex,nvm)           :: gpp_d                    !! Gross primary productivity per ground area
1883    !! @tex $(??gC m^{-2} dt_stomate^{-1})$ @endtex 
1884    REAL(r_std),DIMENSION(kjpindex,nvm)           :: gpp_daily_x              !! "Daily" gpp for teststomate 
1885    !! @tex $(??gC m^{-2} dt_stomate^{-1})$ @endtex
1886    REAL(r_std),DIMENSION(kjpindex,nvm)           :: resp_hetero_litter       !! Litter heterotrophic respiration per ground area
1887    !! @tex $(gC m^{-2} day^{-1})$ @endtex 
1888    !! ??Same variable is also used to
1889    !! store heterotrophic respiration per ground area
1890    !! over ::dt_sechiba??
1891    REAL(r_std),DIMENSION(nvm)                    :: ld_redistribute          !! logical set to redistribute som and litter
1892    REAL(r_std),DIMENSION(kjpindex,nvm)           :: resp_hetero_soil         !! soil heterotrophic respiration 
1893    !! @tex $(gC m^{-2} day^{-1})$ @endtex
1894    REAL(r_std),DIMENSION(kjpindex,nvm)           :: veget_cov                !! Fractional coverage: actually share of the pixel
1895    !! covered by a PFT (fraction of ground area),
1896    !! taking into account LAI ??(= grid scale fpc)??
1897    REAL(r_std),DIMENSION(kjpindex,nvm)           :: veget_cov_max_new        !! Old value for maximal fractional coverage (unitless)
1898    REAL(r_std),DIMENSION(kjpindex,nvm)           :: vcmax                    !! Maximum rate of carboxylation
1899    REAL(r_std),DIMENSION(kjpindex,nvm)           :: nue                      !! Nitrogen use Efficiency with impact of leaf age (umol CO2 (gN)-1 s-1)
1900    !! @tex $(\mumol m^{-2} s^{-1})$ @endtex
1901    REAL(r_std),DIMENSION(kjpindex,nlevs)         :: control_moist_inst       !! Moisture control of heterotrophic respiration
1902    !! (0-1, unitless)
1903    REAL(r_std),DIMENSION(kjpindex,nlevs)         :: control_temp_inst        !! Temperature control of heterotrophic
1904    !! respiration, above and below (0-1, unitless)
1905    REAL(r_std),DIMENSION(kjpindex,ncarb,nvm,nelements) :: som_input_inst     !! Quantity of carbon going into carbon pools from
1906    !! litter decomposition
1907    !! @tex $(gC m^{-2} day^{-1})$ @endtex
1908    !    REAL(r_std),DIMENSION(kjpindex,nvm,nnspec)    :: soil_n_min               !! Mineral nitrogen in the soil
1909    !                                                                              !! @tex $(gN m^{-2})$ @endtex
1910    INTEGER(i_std)                                :: ier                      !! Check errors in netcdf call (unitless)
1911    REAL(r_std)                                   :: sf_time                  !! Intermediate variable to calculate current time
1912    !! step
1913    INTEGER(i_std)                                :: max_totsize              !! Memory management - maximum memory size (Mb)
1914    INTEGER(i_std)                                :: totsize_1step            !! Memory management - memory required to store one
1915    !! time step on one processor (Mb)
1916    INTEGER(i_std)                                :: totsize_tmp              !! Memory management - memory required to store one
1917    !! time step on all processors(Mb)
1918    REAL(r_std)                                   :: xn                       !! How many times have we treated in this forcing
1919    REAL(r_std), DIMENSION(kjpindex)              :: vartmp                   !! Temporary variable
1920    INTEGER(i_std)                                :: vid                      !! Variable identifer of netCDF (unitless)
1921    INTEGER(i_std)                                :: nneigh                   !! Number of neighbouring pixels
1922    INTEGER(i_std)                                :: direct                   !! ??
1923    INTEGER(i_std),DIMENSION(ndm)                 :: d_id                     !! ??
1924!!$    REAL(r_std)                                   :: net_co2_flux_monthly     !! ??[DISPENSABLE]
1925!!$    REAL(r_std)                                   :: net_co2_flux_monthly_sum !! ??[DISPENSABLE]
1926!!$    REAL(r_std)                                   :: net_cflux_prod_monthly_sum    !! AR5 output?? gC m2 month-1 (one variable for
1927!!$                                                                                   !! reduce_sum and one for bcast??), parallel
1928!!$                                                                                   !! computing
1929!!$    REAL(r_std)                                   :: net_cflux_prod_monthly_tot    !! AR5 output?? gC m2 month-1 (one variable for
1930!!$                                                                                   !! reduce_sum and one for bcast??), parallel
1931!!$                                                                                   !! computing
1932!!$    REAL(r_std)                                   :: net_harvest_above_monthly_sum !! AR5 output?? gC m2 month-1 (one variable for
1933!!$                                                                                   !! reduce_sum and one for bcast??), parallel
1934!!$                                                                                   !! computing
1935!!$    REAL(r_std)                                   :: net_harvest_above_monthly_tot !! AR5 output?? gC m2 month-1 (one variable for
1936!!$                                                                                   !! reduce_sum and one for bcast??), parallel
1937!!$                                                                                   !! computing
1938!!$    REAL(r_std)                                   :: net_biosp_prod_monthly_sum    !! AR5 output?? gC m2 month-1 (one variable for
1939!!$                                                                                   !! reduce_sum and one for bcast??), parallel
1940!!$                                                                                   !! computing
1941!!$    REAL(r_std)                                   :: net_biosp_prod_monthly_tot    !! AR5 output?? gC m2 month-1 (one variable for
1942!!$                                                                                   !! reduce_sum and one for bcast??), parallel
1943!!$                                                                                   !! computing
1944    REAL(r_std), DIMENSION(kjpindex,nvm,nbpools)   :: carbon_stock                 !! Array containing the carbon stock for each pool
1945    !! used by ORCHIDEE
1946    REAL(r_std), DIMENSION(kjpindex,nvm,nionspec)  :: plant_n_uptake                 !! Uptake of soil N by plants 
1947    !! (gN/m**2/timestep) 
1948    REAL(r_std), DIMENSION(kjpindex,nvm)           :: n_mineralisation             !! net nitrogen mineralisation of decomposing SOM
1949    !! (gN/m**2/day), supposed to be NH4
1950    REAL(r_std), DIMENSION(kjpindex,nvm)           :: n_fungivores                 !! Fraction of N released for plant uptake due to
1951    !! fungivore consumption.
1952    REAL(r_std), DIMENSION(kjpindex,nvm)           :: resp_total_soil              !! soil heterotrophic respiration (gC/day/m**2 by PFT)
1953    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)
1954    REAL(r_std), DIMENSION(kjpindex,nvm)           :: tau_eff_root                 !! Effective root turnover time that accounts
1955    !! waterstress (days)
1956    REAL(r_std), DIMENSION(kjpindex,nvm)           :: tau_eff_sap                  !! Effective sapwood turnover time that accounts
1957    !! waterstress (days)
1958    REAL(r_std), DIMENSION(kjpindex,nvm)           :: tau_eff_leaf                 !! Effective leaf turnover time that accounts
1959    !! waterstress (days)
1960    REAL(r_std), DIMENSION(kjpindex,nvm)           :: wstress_adapt                !! Factor to account for a long acclimation of
1961    !! of the PFT to the long-term waterstress in
1962    !! the pixel
1963    REAL(r_std), DIMENSION(kjpindex,nvm,ninput)    :: input_dt_sechiba             !! Used to add pft index to N inputs
1964    REAL(r_std), DIMENSION(kjpindex,nvm,nionspec)  :: leaching                     !! mineral nitrogen leached from the soil
1965    REAL(r_std), DIMENSION(kjpindex,nvm,nnspec)    :: emission                     !! volatile losses of nitrogen (gN/m**2/timestep)
1966    REAL(r_std), DIMENSION(kjpindex,nvm,nmbcomp,nelements) &
1967         :: check_intern                 !! Contains the components of the internal
1968    !! mass balance chech for this routine
1969    !! @tex $(gC pixel^{-1} dt^{-1})$ @endtex
1970    REAL(r_std), DIMENSION(kjpindex,nvm,nelements) :: closure_intern               !! Check closure of internal mass balance
1971                                                                                   !! @tex $(gC pixel^{-1} dt^{-1})$ @endtex
1972    REAL(r_std), DIMENSION(kjpindex,nvm,nelements) :: pool_start                   !! Start and end pool of this routine
1973                                                                                   !! @tex $(gC pixel^{-1} dt^{-1})$ @endtex
1974    REAL(r_std), DIMENSION(kjpindex,nvm,nelements) :: pool_end                     !! Start and end pool of this routine
1975                                                                                   !! @tex $(gC pixel^{-1} dt^{-1})$ @endtex
1976    REAL(r_std), DIMENSION(kjpindex)               :: pixel_area                   !! surface area of the pixel @tex ($m^{2}$)
1977    REAL(r_std), DIMENSION(kjpindex,nvm)           :: veget_cov_max_begin              !! veget_max at the start of the routine.
1978                                                                                   !! Used for consistency checks
1979    REAL(r_std), DIMENSION(kjpindex,nelements)     :: mass_balance_closure         !! Missing mass in the carbon balance
1980                                                                                   !! @tex $(gC(N) pixel^{-1} dt^{-1})$ @endtex
1981    REAL(r_std), DIMENSION(kjpindex,nvm)           :: nbp                          !! Pool-based Net Biome production for each
1982                                                                                   !! time step
1983    INTEGER(i_std)                                 :: inspec, ininput, inionspec   !! Indices
1984    INTEGER(i_std)                                 :: ipts, ivm, ilitt, ilev, icir !! Indices
1985    INTEGER(i_std)                                 :: icarb, ipar, iele, imbc      !! Indices
1986
1987    ! Light for recruitment
1988    REAL(r_std),DIMENSION (kjpindex,nvm,nlevels_tot) &
1989         :: light_tran_to_level  !! Fraction of light transmitted to a given canopy level
1990    REAL(r_std),DIMENSION(kjpindex,nvm)            :: count_daylight       !! Time steps dt_radia during daylight
1991   
1992    ! Harvest area and wind speed for Windthrow
1993    REAL(r_std), DIMENSION(kjpindex,nvm,wind_years)    :: harvest_5y_area      !! total harvested area in the last 5 years
1994    REAL(r_std), DIMENSION(kjpindex)                   :: wind_speed_actual    !! Actualwind speed calculated from the actual half hourly
1995                                                                               !! values u and v as given in the driver (ms-1)
1996 
1997    !_ ================================================================================================================================
1998
1999    !! 1. Initialize variables
2000
2001    !! 1.1 Store current time step in a common variable
2002    itime = kjit
2003
2004    !![DISPENSABLE] 1.2 Copy the depth of the different soil layers from diaglev specified in slow_proc
2005
2006    !printlev=get_printlev('stomate')
2007
2008    !! 1.3 PFT rooting depth across pixels, humescte is pre-defined
2009    ! (constantes_veg.f90). It is defined as the coefficient of an exponential
2010    ! function relating root density to depth
2011    DO j=1,nvm
2012       rprof(:,j) = 1./humcste(j)
2013    ENDDO
2014
2015    !! 1.4 Initialize first call
2016    ! Set growth respiration to zero
2017    resp_growth(:,:) = zero
2018    atm_to_bm(:,:,:) = zero
2019    plant_n_uptake(:,:,:) = zero
2020    n_mineralisation(:,:) = zero
2021    mass_balance_closure(:,:) = zero 
2022
2023
2024    ! Check that initialization is done
2025    IF (l_first_stomate) CALL ipslerr_p(3,'stomate_main','Initialization not yet done.','','')
2026
2027     IF (printlev_loc >= 2) THEN
2028       IF(do_slow)THEN
2029          WRITE(numout,*) 'stomate_main: date=',date,' ymds=', year, month, day, sec, ' itime=', itime, ' do_slow=',do_slow
2030       ENDIF
2031     ENDIF
2032
2033    !! 3. Special treatment for some input arrays.
2034
2035    !! 3.1 Sum of liquid and solid precipitation
2036    precip(:) = ( precip_rain(:) + precip_snow(:) )*one_day/dt_sechiba
2037
2038    !! 3.2 Calculate STOMATE's vegetation fractions from veget and veget_max
2039    DO j=1,nvm 
2040       WHERE ((1.-totfrac_nobio(:)) > min_sechiba)
2041          ! Pixels with vegetation
2042          veget_cov(:,j) = veget(:,j)/( 1.-totfrac_nobio(:) )
2043          veget_cov_max(:,j) = veget_max(:,j)/( 1.-totfrac_nobio(:) )
2044       ELSEWHERE
2045          ! Pixels without vegetation
2046          veget_cov(:,j) = zero
2047          veget_cov_max(:,j) = zero
2048       ENDWHERE
2049    ENDDO
2050
2051    IF ( do_now_stomate_lcchange ) THEN
2052       DO j=1,nvm
2053          WHERE ((1.-totfrac_nobio_new(:)) > min_sechiba)
2054             ! Pixels with vegetation
2055             veget_cov_max_new(:,j) = veget_max_new(:,j)/( 1.-totfrac_nobio_new(:) )
2056          ELSEWHERE
2057             ! Pixels without vegetation
2058             veget_cov_max_new(:,j) = zero
2059          ENDWHERE
2060       ENDDO
2061    ENDIF
2062
2063    !! 3.3 Adjust time step of GPP
2064    ! No GPP for bare soil
2065    gpp_d(:,1) = zero
2066    ! GPP per PFT
2067    DO j = 2,nvm   
2068       WHERE (veget_cov_max(:,j) > min_stomate)
2069          ! The PFT is available on the pixel
2070          gpp_d(:,j) =  gpp(:,j)/ veget_cov_max(:,j)* one_day/dt_sechiba 
2071       ELSEWHERE
2072          ! The PFT is absent on the pixel
2073          gpp_d(:,j) = zero
2074       ENDWHERE
2075    ENDDO
2076
2077    !! 3.4 The first time step of the first day of the month 
2078    ! implies that the month is over
2079    IF ( day == 1 .AND. sec .LT. dt_sechiba ) THEN
2080       EndOfMonth=.TRUE.
2081    ELSE
2082       EndOfMonth=.FALSE.
2083    ENDIF
2084
2085
2086    !! 4. Calculate variables for dt_stomate (i.e. "daily")
2087
2088    ! Note: If dt_days /= 1, then variables 'xx_daily' (eg. half-daily or bi-daily) are by definition
2089    ! not expressed on a daily basis. This is not a problem but could be
2090    ! confusing
2091
2092    !! 4.1. Calculate water stress accounting for hydraulic architecture
2093    !  If hydraulic architecture is used, humrel_daily (water stress) for use in stomate is
2094    !  not determined from humrel as calculated in hydrol.f90, but it is calculated as the
2095    !  ratio between a proxy for stressed and unstressed ecosystem functioning.
2096    !  Nightvalues are exclude. On the first day of the simulation (no biomass)
2097    !  the stressed and unstressed proxies are probably both equal to the initilazed value (=zero,
2098    !  initialized in sechiba.f90), to avoid numerical issues in this case we set humrel_daily
2099    !  to 1. If hydraulic architecture is not used humrel_daily is calculated from humrel as
2100    !  determined in hydrol.
2101    IF (ok_hydrol_arch) THEN
2102       ! Accumulate the half hourly values into a daily value. Accumulate the
2103       ! stressed and unstressed proxy first and then take the average. We
2104       ! first accumulate and then take the ratio because that way we better
2105       ! account for the night time values. If we do it in the other order
2106       ! we need to assign a value to the ratio during the night. Whether we
2107       ! take zero or one, this will bias our waterstress number because
2108       ! the number of half hours during the night is different for the
2109       ! different pixels. So although water stress could be higher in the
2110       ! south than in the north. During the growing season, day are shorter
2111       ! in the south so if we set the ratio to 1 during the night, our daily
2112       ! water stress in the south may be less than in the north because we
2113       ! more 1's in the daily time series.
2114
2115       ! The order of the calculation may depend on the proxy used. For example,
2116       ! Accumulate transpir_supply and transpir first and then calculate ratio
2117       ! By doing this water stress is buffered (it is assumed that if
2118       ! ::transpir_supply is larger than ::transpir at one timestep it can buffer
2119       ! potential water stress in the next timestep. In reality this is not the
2120       ! case: transpir_supply is a potential value not a realized one.
2121       DO ipts = 1,kjpindex
2122
2123          ! The cosine of the zenith angle, is used to
2124          ! identify night values.
2125          IF (coszang(ipts) .LT. min_stomate) THEN
2126
2127             ! Redundant because the value will never be used
2128             ! For all pixels
2129             stressed(ipts,:) = zero
2130             unstressed(ipts,:) = zero
2131
2132             ! For PFT1 under LCC
2133             ! vir_stressed = zero
2134             ! vir_unstressed = zero
2135
2136          ELSE
2137
2138             ! No vegetation present so ecosystem functioning
2139             ! was not defined
2140             WHERE (veget_cov_max(ipts,:) .LT. min_stomate)
2141
2142                ! To avoid uninitialized values
2143                stressed(ipts,:) = zero
2144                unstressed(ipts,:) = zero
2145
2146                ! Update the values to avoid uninitialized fields
2147                ! in ::stressed_daily and ::unstressed_daily
2148                stressed_daily(ipts,:) = stressed_daily(ipts,:) + &
2149                     stressed(ipts,:)
2150                unstressed_daily(ipts,:) = unstressed_daily(ipts,:) + &
2151                     unstressed(ipts,:)
2152                daylight(ipts,:) = daylight(ipts,:) + 1
2153
2154                ! For PFT1 under LCC
2155                ! vir_stressed = zero
2156                ! vir_unstressed = zero
2157
2158             ELSEWHERE
2159
2160                ! The pixel and pft contain vegetation and their
2161                ! is daylight, store values to calculate the stress
2162                stressed_daily(ipts,:) = stressed_daily(ipts,:) + &
2163                     stressed(ipts,:)
2164                unstressed_daily(ipts,:) = unstressed_daily(ipts,:) + &
2165                     unstressed(ipts,:)
2166                daylight(ipts,:) = daylight(ipts,:) + 1
2167
2168
2169                ! For PFT1 under LCC
2170                ! vir_stressed = zero
2171                ! vir_unstressed = zero
2172
2173             ENDWHERE
2174
2175          ENDIF
2176
2177       ENDDO
2178
2179
2180       ! Calculate the mean waterstress value at the end of each day
2181       IF (do_slow) THEN
2182
2183          ! Calculate the ratio
2184          WHERE (unstressed_daily(:,:) .LT. min_stomate &
2185               .OR. stressed_daily(:,:) .LT. min_stomate)
2186
2187             ! No ecosystem function thus no data, we assume
2188             ! there is no water stress
2189             humrel_daily(:,:) = un
2190
2191          ELSEWHERE
2192
2193             ! Calculate water stress. If we first calculate
2194             ! the daily sum and then the ratio there is no need
2195             ! to divide by daylight. If we accumulate ratios
2196             ! we will have to divide by daylight. This is
2197             ! arbitrary. To do this properly we should calculate
2198             ! the turgor in the cells and calculate growth
2199             ! based on that see i.e. Fatichi et al 2013, New
2200             ! Phytologist. We use a simple numerical construct
2201             ! (the sqrt of the ratio) to overcome that complexity.
2202             humrel_daily(:,:) = stressed_daily(:,:) / &
2203                  unstressed_daily(:,:)
2204
2205          ENDWHERE
2206
2207          !+++CHECK+++
2208          ! This needs to be done outside the where loop so that
2209          ! all PFTs have vir_humrel_daily set.
2210          ! vir_humrel_daily will be needed when accounting for the
2211          ! water columns following a land cover change. It is partly
2212          ! calculated in sechiba hydrol_arch but it is not passed all
2213          ! the way to here. Check and fix. For the moment LCC does
2214          ! not account for the water columns so ::humrel_daily and
2215          ! ::vir_humrel_daily are equal to each other
2216          vir_humrel_daily(:,:) = humrel_daily(:,:)
2217          ! We have a problem.  wstress is no longer calculated in a way
2218          ! that allows for a virtual quantity, since it's the ratio of the
2219          ! stressed and unstressed GPPs...which cannot be calculated if there
2220          ! is no vegetation.  Therefore, for any PFTs which are not
2221          ! currently present we give the daily virtual waterstress to be
2222          ! equal to one.
2223          !+++++++++++
2224          !---TEMP---
2225          IF(printlev_loc>=4)THEN
2226             DO ipts=1,kjpindex
2227                DO ivm=1,nvm
2228                   IF( humrel_daily(ipts,ivm) .lt. 1.) THEN
2229                      WRITE(numout,*)'ivm,stressed_daily,unstressed_daily,diff,humrel_daily'
2230
2231                      WRITE(numout,*) ivm, stressed_daily(ipts,ivm),unstressed_daily(ipts,ivm),&
2232                           & stressed_daily(ipts,ivm)-unstressed_daily(ipts,ivm), humrel_daily(ipts,ivm) 
2233                   ENDIF
2234                ENDDO
2235             ENDDO
2236          ENDIF
2237          !----------
2238          ! Set to zero to start accumulating for the next day
2239          stressed_daily(:,:) = zero
2240          unstressed_daily(:,:) = zero
2241          daylight(:,:) = zero
2242
2243       ELSE
2244
2245          ! Set to a large value so that it is easy to detect problems
2246          ! This value should never be used. It should only be passed
2247          ! to other routine at the end of the day when do_slow is false
2248          humrel_daily(:,:) = large_value
2249          vir_humrel_daily(:,:) = large_value
2250
2251       ENDIF !(do_slow)
2252
2253    ELSE
2254       ! No hydrological architecture
2255       CALL stomate_accu (do_slow, humrel, humrel_daily)
2256
2257       ! The variable ::vir_humrel_arch was not defined for this case
2258       ! Assume no stress
2259       vir_humrel_daily = un
2260
2261    ENDIF ! (ok_hydrol_arch)
2262
2263
2264    ! Here we add some calculations for daily max/min for windthrow module
2265    IF (ok_windthrow) THEN
2266
2267       ! Accumulate the half hourly values into a daily value. Accumulate the
2268       ! daily wind speed first and then take the average. grnd_80 is the index
2269       ! of ngrnd closest to 80 cm depth.
2270       wind_speed_actual(:) = SQRT (u(:) * u(:) + v(:) * v(:))
2271       wind_max_daily(:) = MAX (wind_speed_actual(:),wind_max_daily(:) )
2272       soil_max_daily(:) = MAX (stempdiag(:,grnd_80),soil_max_daily(:) )
2273
2274       IF (do_slow) THEN
2275
2276          ! wind_speed_daily/soil_temp_daily will be passed to the wind_damage
2277          ! module. wind_max_daily/soil_max_daily reset to zero so they can be
2278          ! used again for the next day
2279          wind_speed_daily(:) = wind_max_daily(:)
2280          wind_max_daily(:) = zero
2281          soil_temp_daily(:) = soil_max_daily(:)
2282          soil_max_daily(:) = zero
2283
2284       ENDIF
2285
2286    ENDIF
2287
2288
2289    ! Debug
2290    IF (printlev_loc>=4) THEN
2291       IF(do_slow) THEN
2292          WRITE(numout,*) 'CHECK: humrel_daily after stomate_accu',&
2293               humrel_daily(:,:)
2294          WRITE(numout,*) 'CHECK: vir_humrel_daily after stomate_accu',&
2295               vir_humrel_daily(:,:)
2296       ENDIF
2297    ENDIF
2298    !-
2299
2300    !! Calculate the light that reaches each canopy layer
2301    !  Compute seasonal daytime transmitted light to canopy levels
2302    !  This quantity is used to calculate how much recruitment can occur
2303    !  underneath the canopy. Recruitment is simulated in stomate_prescribe.f90
2304    light_tran_to_level(:,:,:) = un
2305
2306    DO ipts=1,kjpindex
2307
2308       DO ivm=1,nvm
2309
2310          ! If we are at a daytime time step and there is growth (gpp>0) then
2311          ! accumulate instantaneous transmitted light to each canopy level
2312          IF ( coszang(ipts) .GT. min_stomate .AND. &
2313               gpp(ipts,ivm) .GT. min_stomate ) THEN
2314
2315             daylight_count(ipts,ivm) = daylight_count(ipts,ivm) + 1
2316
2317             DO ilev = nlevels_tot-1,1,-1
2318
2319                light_tran_to_level(ipts,ivm,ilev) = &
2320                     light_tran_to_level(ipts,ivm,ilev+1) * &
2321                     Isotrop_Tran_Tot_p(ipts,ivm,ilev+1)
2322
2323             ENDDO
2324
2325             ! Accumulate over the growing season
2326             light_tran_to_level_season(ipts,ivm,:) = &
2327                  light_tran_to_level_season(ipts,ivm,:) + &
2328                  light_tran_to_level(ipts,ivm,:)
2329
2330             ! Debug
2331             IF (printlev_loc.GT.4)THEN
2332                WRITE(numout,*) 'It is daytime and growth occurs, '&
2333                     &'daylight_count(ipts,ivm)= ', daylight_count(ipts,ivm)
2334                WRITE(numout,*) 'gpp(ipts,ivm)= ', gpp(ipts,ivm)
2335                WRITE(numout,*) 'fine resolution Absolute transmitted light '&
2336                     &'to each level (ivm,ipts,nlevels_tot) ',&
2337                     ivm,ipts,nlevels_tot
2338                DO ilev = nlevels_tot,1,-1
2339                   WRITE(numout,*) ilev,light_tran_to_level(ipts,ivm,ilev),&
2340                        Isotrop_Tran_Tot_p(ipts,ivm,ilev)
2341                ENDDO
2342             ENDIF
2343             !-
2344
2345          ENDIF   ! daytime and growing season
2346
2347       ENDDO
2348
2349       ! Calculate average transmitted light at the end of the year
2350       IF (EndOfYear) THEN
2351
2352          ! Calculate average transmitted light at the end of the year
2353          ! Only account for days during the growing season
2354          DO ivm=2,nvm
2355
2356             IF (daylight_count(ipts,ivm) .GT. zero) THEN
2357
2358                DO ilev=1,nlevels_tot
2359
2360                   light_tran_to_level_season(ipts,ivm,ilev) = &
2361                        light_tran_to_level_season(ipts,ivm,ilev) / &
2362                        daylight_count(ipts,ivm)
2363
2364                ENDDO
2365
2366             ELSE
2367
2368                ! There was no GPP during this year in this PFT. Most
2369                ! likely this implies that there is no vegetation. So,
2370                ! all the light is transmitted to the ground level.
2371                ! The fraction of transmitted light is thus set to 1.
2372                light_tran_to_level_season(ipts,ivm,:) = un
2373
2374             ENDIF
2375
2376             ! Debug
2377             IF(printlev_loc>=4)THEN
2378                WRITE(numout,*) 'DEBUG in stomate.f90 it is end of the ', &
2379                     'year in stomate.f90'
2380                WRITE(numout,*) 'daylight_count to divide by here is, ', &
2381                     daylight_count(ipts,:)
2382                WRITE(numout,*) 'transmitted light, ',&
2383                     light_tran_to_level_season(ipts,ivm,1),&
2384                     light_tran_to_level_season(ipts,ivm,10)
2385             ENDIF
2386             !-
2387          ENDDO
2388          ! Reset the counter for the next year
2389          daylight_count(:,:)=zero
2390
2391       ENDIF ! EndOfYear
2392
2393    ENDDO ! ipts=1,kjpindex
2394
2395    ! Debug
2396    IF(printlev_loc>=5)THEN
2397       IF (EndOfYear) THEN
2398          DO ipts=1,kjpindex             
2399             DO ivm=1,nvm
2400                WRITE(numout,*) 'Average absolute transmitted light &
2401                     & during the growing season to each canopy &
2402                     & level in stomate.f90 ', &
2403                     ivm,ipts,nlevels_tot
2404                DO ilev = nlevels_tot,1,-1
2405                   WRITE(numout,*) ilev,light_tran_to_level_season(ipts,ivm,ilev)
2406                ENDDO
2407             ENDDO
2408          ENDDO
2409       ENDIF
2410    ENDIF
2411    !-
2412    ! Write trans_to_light to output file. It is calculated at each subdaily
2413    ! timestep
2414    CALL xios_orchidee_send_field("LIGHT_TRAN_TO_LEVEL",light_tran_to_level(:,:,:))
2415
2416    !! 4.1 Accumulate instantaneous variables (do_slow=.FALSE.)
2417    ! Accumulate instantaneous variables (do_slow=.FALSE.) and eventually
2418    ! calculate daily mean value (do_slow=.TRUE.)
2419
2420    CALL stomate_accu (do_slow, litterhumdiag, litterhum_daily)
2421    CALL stomate_accu (do_slow, t2m,           t2m_daily)
2422    CALL stomate_accu (do_slow, temp_sol,      tsurf_daily)
2423    CALL stomate_accu (do_slow, stempdiag,     tsoil_daily)
2424    CALL stomate_accu (do_slow, shumdiag,      soilhum_daily)
2425    CALL stomate_accu (do_slow, precip,        precip_daily)
2426    CALL stomate_accu (do_slow, gpp_d,         gpp_daily)
2427    CALL stomate_accu (do_slow, drainage_pft, drainage_daily) 
2428
2429    !! 4.2 Daily minimum temperature
2430    t2m_min_daily(:) = MIN( t2m(:), t2m_min_daily(:) )
2431
2432    !! 4.3 Calculate maintenance respiration
2433    ! Note: lai is passed as output argument to overcome previous problems with
2434    ! natural and agricultural vegetation types.
2435    CALL maint_respiration (kjpindex, dt_sechiba, t2m, t2m_longterm, &
2436         stempdiag, gpp, gpp_week, lab_fac, &
2437         veget_cov_max, rprof, resp_maint_part_radia, &
2438         circ_class_n, circ_class_biomass)
2439
2440    ! Aggregate maintenance respiration across the different plant parts
2441    resp_maint_radia(:,:) = zero
2442    DO j=2,nvm
2443       DO k= 1, nparts
2444          resp_maint_radia(:,j) = resp_maint_radia(:,j) &
2445               & + resp_maint_part_radia(:,j,k)
2446       ENDDO
2447    ENDDO
2448
2449    ! Maintenance respiration separated by plant parts
2450    resp_maint_part(:,:,:) = resp_maint_part(:,:,:) &
2451         & + resp_maint_part_radia(:,:,:)
2452
2453    !! 4.4 Initialize check for mass balance closure
2454    !  Mass balance closure for the half-hourly (dt_sechiba)
2455    !  processes in stomate.f90. This test is always performed.
2456    !  If err_act.EQ.1 then the value of the mass balance error
2457    !  -if any- is written to the history file.
2458!!$    printlev_loc=get_printlev('stomate')
2459    check_intern(:,:,:,:) = zero
2460    pool_start(:,:,:) = zero
2461    DO iele = 1,nelements
2462
2463       ! atm_to_bm has as intent inout, the variable
2464       ! accumulates carbon over the course of a day.
2465       ! Use the difference between the start and end of
2466       ! this routine to account for the change in
2467       ! atm_to_bm
2468       check_intern(:,:,iatm2land,iele) = - un * &
2469            atm_to_bm(:,:,iele) * veget_cov_max(:,:) * dt_sechiba
2470
2471       ! Biomass pool (gC m-2)*(m2 m-2)
2472       DO ipar = 1,nparts
2473          pool_start(:,:,iele) = pool_start(:,:,iele) + &
2474               (turnover_daily(:,:,ipar,iele) + &
2475               bm_to_litter(:,:,ipar,iele)) * veget_cov_max(:,:) / &
2476               one_day * dt_sechiba
2477       ENDDO
2478
2479       ! Litter pool (gC m-2)*(m2 m-2)
2480       DO ilitt = 1,nlitt
2481          DO ilev = 1,nlevs
2482             pool_start(:,:,iele) = pool_start(:,:,iele) + &
2483                  litter(:,ilitt,:,ilev,iele) * veget_cov_max(:,:)
2484          ENDDO
2485       ENDDO
2486
2487       ! Soil carbon (gC m-2)*(m2 m-2)
2488       DO icarb = 1,ncarb
2489          pool_start(:,:,iele) = pool_start(:,:,iele) + &
2490               som(:,icarb,:,iele) * veget_cov_max(:,:)
2491       ENDDO
2492
2493    ENDDO ! # nelements
2494
2495    ! Account for the N-pool in the soil
2496    DO inspec = 1,nnspec
2497       pool_start(:,:,initrogen) = pool_start(:,:,initrogen) + &
2498            soil_n_min(:,:,inspec) * veget_cov_max(:,:)
2499    ENDDO
2500
2501    ! Initialize check for area conservation
2502    veget_cov_max_begin(:,:) = veget_cov_max(:,:)
2503   
2504    !! 4.5 Litter dynamics and litter heterothropic respiration
2505    !  Including: litter update, lignin content, PFT parts, litter decay,
2506    !  litter heterotrophic respiration, dead leaf soil cover.
2507    !  Note: there is no vertical discretisation in the soil for litter decay.
2508    n_mineralisation(:,:) = zero
2509    turnover_littercalc(:,:,:,:) = turnover_daily(:,:,:,:) * dt_sechiba/one_day
2510    bm_to_littercalc(:,:,:,:) = bm_to_litter(:,:,:,:) * dt_sechiba/one_day
2511
2512    CALL littercalc (kjpindex, &
2513         turnover_littercalc, bm_to_littercalc, &
2514         veget_cov_max, temp_sol, stempdiag, shumdiag, litterhumdiag, som, &
2515         clay, silt, soil_n_min, litter, dead_leaves, lignin_struc, &
2516         lignin_wood, n_mineralisation, deadleaf_cover, resp_hetero_litter, &
2517         som_input_inst, control_temp_inst, control_moist_inst, n_fungivores, &
2518         matrixA, vectorB, CN_target, CN_som_litter_longterm, tau_CN_longterm, &
2519         ld_redistribute, circ_class_biomass, circ_class_n)
2520
2521    !--- TEMP---!
2522    IF(printlev_loc>=4) THEN
2523       WRITE(numout,*) 'between litter and soil ' 
2524       WRITE(numout,*) 'n_mineralisation ', n_mineralisation(:,:)
2525       WRITE(numout,*) 'drainage_pft ', drainage_pft(:,:)
2526       WRITE(numout,*) 'control_temp_inst, ',control_temp_inst(:,:)
2527       WRITE(numout,*) 'control_moist_inst, ',control_moist_inst(:,:)
2528    ENDIF
2529
2530    !! 4.6 Soil carbon dynamics and soil heterotrophic respiration
2531    ! Note: there is no vertical discretisation in the soil for litter decay.
2532    CALL som_dynamics (kjpindex, clay, silt, veget_cov_max, &
2533         som_input_inst, control_temp_inst, control_moist_inst, drainage_pft,&
2534         CN_target, som, soil_n_min, resp_hetero_soil, matrixA, &
2535         n_mineralisation, CN_som_litter_longterm, tau_CN_longterm)
2536
2537    ! Heterothropic soil respiration during time step ::dt_sechiba
2538    ! @tex $(gC m^{-2})$ @endtex
2539    IF(printlev_loc >= 4) THEN
2540       WRITE(numout,*)'betweem som_dynamics and nitrogen_dynamics'
2541       WRITE(numout,*)'n_mineralisation ', n_mineralisation(:,:)       
2542       WRITE(numout,*)'resp_hetero_soil',resp_hetero_soil(:,:)
2543       WRITE(numout,*)'dt_sechiba',dt_sechiba 
2544       WRITE(numout,*)'one_day',one_day 
2545    ENDIF
2546
2547    ! Heterothropic litter respiration during time step ::dt_sechiba
2548    ! @tex $(gC m^{-2})$ @endtex
2549    resp_hetero_litter(:,:) = resp_hetero_litter(:,:) * dt_sechiba/one_day
2550
2551    !! resp_hetero_soil(:,1)=zero
2552    resp_hetero_soil(:,:) = resp_hetero_soil(:,:) * dt_sechiba/one_day
2553
2554    ! Total heterothrophic respiration during time step ::dt_sechiba
2555    ! @tex $(gC m^{-2})$ @endtex
2556    resp_hetero_radia(:,:) = resp_hetero_litter(:,:) + resp_hetero_soil(:,:)
2557    resp_hetero_d(:,:) = resp_hetero_d(:,:) + resp_hetero_radia(:,:)
2558
2559    ! Sum heterotrophic and autotrophic respiration in soil
2560    resp_total_soil(:,:) = resp_hetero_radia(:,:) + & 
2561         resp_maint_part_radia(:,:,isapbelow) + resp_maint_part_radia(:,:,iroot)
2562
2563    IF(ok_ncycle) THEN
2564
2565       CALL nitrogen_dynamics(kjpindex, clay, MAX(zero, un - silt - clay), & 
2566            stempdiag-tp_00, tmc_pft, drainage_pft, swc_pft, veget_cov_max, &
2567            resp_total_soil, som, & 
2568            n_input, soil_ph, n_mineralisation, pb, n_fungivores, & 
2569            plant_n_uptake, bulk, soil_n_min, p_O2, bact, atm_to_bm, &
2570            leaching, emission, input_dt_sechiba, ld_redistribute, circ_class_biomass, &
2571            circ_class_n) 
2572
2573    ENDIF
2574
2575    ! Accumulate over the day
2576    plant_n_uptake_daily(:,:,:) = plant_n_uptake_daily(:,:,:) + plant_n_uptake(:,:,:)
2577    n_mineralisation_d(:,:) = n_mineralisation_d(:,:) + n_mineralisation(:,:) 
2578
2579    !! 4.7 Accumulate instantaneous variables (do_slow=.FALSE.)
2580    ! Accumulate instantaneous variables (do_slow=.FALSE.) and eventually
2581    ! calculate daily mean value (do_slow=.TRUE.)
2582    CALL stomate_accu (do_slow, control_moist_inst, control_moist_daily)
2583    CALL stomate_accu (do_slow, control_temp_inst, control_temp_daily)
2584    CALL stomate_accu (do_slow, som_input_inst, som_input_daily)
2585
2586    !! 4.8 Check numerical consistency of this routine
2587    !  These checks only check the processes that happen
2588    !  every half-hour (dt_radia). This test is always
2589    !  performed. If err_act.EQ.1 then the value of the
2590    !  mass balance error -if any- is written to the
2591    !  history file.
2592!!$    printlev_loc=get_printlev('stomate')
2593
2594    !  Check surface area
2595    CALL check_surface_area("stomate dt_sechiba", kjpindex, veget_cov_max_begin, &
2596         veget_cov_max,'pixel')
2597
2598    ! 4.8.2 Mass balance closure (dt_radia)
2599    ! Calculate final carbon and nitrogen pools
2600    pool_end(:,:,:) = zero
2601    DO iele = 1,nelements
2602
2603       ! Litter pool
2604       DO ilitt = 1,nlitt
2605          DO ilev = 1,nlevs
2606             pool_end(:,:,iele) = pool_end(:,:,iele) + &
2607                  litter(:,ilitt,:,ilev,iele) * veget_cov_max(:,:)
2608          ENDDO
2609       ENDDO
2610
2611       ! Soil carbon and nitrogen
2612       DO icarb = 1,ncarb
2613          pool_end(:,:,iele) = pool_end(:,:,iele) + &
2614               som(:,icarb,:,iele) * veget_cov_max(:,:)
2615       ENDDO
2616
2617    ENDDO ! # nelements
2618
2619    ! The nitrogen pool in the soil may have changed
2620    DO inspec = 1,nnspec
2621       pool_end(:,:,initrogen) = pool_end(:,:,initrogen) + &
2622            soil_n_min(:,:,inspec) * veget_cov_max(:,:)
2623    ENDDO
2624
2625    DO ivm = 1,nvm
2626       pool_end(:,ivm,initrogen) = pool_end(:,ivm,initrogen) + &
2627            n_fungivores(:,ivm) * veget_cov_max(:,ivm)
2628    ENDDO
2629
2630    ! Calculate mass balance
2631    ! Specific processes
2632    check_intern(:,:,iland2atm,icarbon) = -un * (resp_hetero_litter(:,:) + &
2633         resp_hetero_soil(:,:)) * veget_cov_max(:,:)
2634
2635    DO ininput = 1,ninput
2636       check_intern(:,:,iatm2land,initrogen) = &
2637            check_intern(:,:,iatm2land,initrogen) + &
2638            input_dt_sechiba(:,:,ininput) * veget_cov_max(:,:)
2639    ENDDO
2640
2641    DO inspec= 1, nnspec
2642       check_intern(:,:,iland2atm,initrogen) = &
2643            check_intern(:,:,iland2atm,initrogen) &
2644            -un * (emission(:,:,inspec) * veget_cov_max(:,:))
2645    ENDDO
2646
2647    DO inionspec = 1, nionspec
2648       check_intern(:,:,ilat2out,initrogen) = &
2649            check_intern(:,:,ilat2out,initrogen) &
2650            -un * ( plant_n_uptake(:,:,inionspec) + &
2651            leaching(:,:,inionspec) ) * veget_cov_max(:,:)
2652    ENDDO
2653
2654    ! Common processes
2655    DO iele = 1,nelements
2656       check_intern(:,:,iatm2land,iele) = check_intern(:,:,iatm2land,iele) + &
2657            atm_to_bm(:,:,iele) * dt_sechiba * veget_cov_max(:,:)
2658       check_intern(:,:,ipoolchange,iele) = &
2659            -un * (pool_end(:,:,iele) - pool_start(:,:,iele))
2660    ENDDO
2661
2662    closure_intern(:,:,:) = zero
2663    DO imbc = 1,nmbcomp
2664       DO iele = 1,nelements
2665          ! Debug
2666          IF (printlev_loc>=4) WRITE(numout,*) &
2667               'check_intern, ivm, imbc, iele, ', imbc, &
2668               iele, SUM(check_intern(:,:,imbc,iele),2)
2669          !-
2670          closure_intern(:,:,iele) = closure_intern(:,:,iele) + &
2671               check_intern(:,:,imbc,iele)
2672       ENDDO
2673    ENDDO
2674
2675    CALL check_mass_balance("stomate dt_sechiba", closure_intern, kjpindex, &
2676         pool_end, pool_start, veget_cov_max, 'pft')
2677
2678    ! Accumulate the mass balance error over the course of the day
2679    ! If all is well the mass balance error is zero (.LT. min_stomate)
2680    DO iele = 1,nelements
2681       mass_balance_closure(:,iele) = mass_balance_closure(:,iele) + &
2682            SUM((closure_intern(:,:,iele) * veget_cov_max(:,:)),2)
2683    ENDDO
2684
2685    !! 5. Daily processes - performed at the end of the day
2686
2687    IF (do_slow) THEN
2688
2689       !+++CHECK+++
2690       ! No longer needed. lai is no longer passed
2691       ! circ_class_biomass and circ_class_n are now the
2692       ! prognostic variables.
2693!!$       !! 5.1 Update lai
2694!!$       ! Use lai from stomate
2695!!$       ! ?? check if this is the only time ok_pheno is used??
2696!!$       ! ?? Looks like it is the only time. But this variables probably is defined
2697!!$       ! in stomate_constants or something, in which case, it is difficult to track.
2698!!$       IF (ok_pheno) THEN
2699!!$          !! 5.1.1 Update LAI
2700!!$          ! Set lai of bare soil to zero
2701!!$          lai(:,ibare_sechiba) = zero
2702!!$          ! lai for all PFTs
2703!!$          DO ipts = 1, kjpindex
2704!!$             DO j = 2, nvm
2705!!$                lai(ipts,j) = cc_to_lai(circ_class_biomass(ipts,j,:,ileaf,icarbon),&
2706!!$                     circ_class_n(ipts,j,:),j)
2707!!$             ENDDO
2708!!$          ENDDO
2709!!$          frac_age(:,:,:) = leaf_frac(:,:,:)
2710!!$       ELSE
2711!!$          ! 5.1.2 Use a prescribed lai
2712!!$          ! WARNING: code in setlai is effectively the same as the lines above
2713!!$          ! Update subroutine if LAI should be prescribed. This is a bit an optimistic
2714!!$          ! function. It is rather difficult to force an lai with a dynamic allocation
2715!!$          ! and a dynamic nitrogen cycle. This will quickly result in inconsistencies.
2716!!$          CALL  setlai(kjpindex, lai, circ_class_biomass,circ_class_n)
2717!!$          frac_age(:,:,:) = zero
2718!!$       ENDIF
2719       !++++++++++++
2720
2721       !! 5.2 Calculate long-term "meteorological" and biological parameters
2722       ! mainly in support of calculating phenology. If ::EndOfYear=.TRUE.
2723       ! annual values are update (i.e. xx_lastyear).
2724       CALL season &
2725            &          (kjpindex, dt_days, EndOfYear, &
2726            &           veget_cov, veget_cov_max, &
2727            &           humrel_daily, t2m_daily, tsoil_daily, soilhum_daily, lalo, &
2728            &           precip_daily, npp_daily, circ_class_biomass, circ_class_n, &
2729            &           turnover_daily, gpp_daily, when_growthinit, &
2730            &           maxhumrel_lastyear, maxhumrel_thisyear, &
2731            &           minhumrel_lastyear, minhumrel_thisyear, &
2732            &           maxgppweek_lastyear, maxgppweek_thisyear, &
2733            &           gdd0_lastyear, gdd0_thisyear, &
2734            &           precip_lastyear, precip_thisyear, &
2735            &           lm_lastyearmax, lm_thisyearmax, &
2736            &           maxfpc_lastyear, maxfpc_thisyear, &
2737            &           humrel_month, humrel_week, t2m_longterm, tau_longterm, &
2738            &           t2m_month, t2m_week, tsoil_month, soilhum_month, &
2739            &           npp_longterm, turnover_longterm, gpp_week, plant_status, &
2740            &           gdd_m5_dormance, gdd_midwinter, ncd_dormance, ngd_minus5, &
2741            &           time_hum_min, hum_min_dormance, gdd_init_date, &
2742            &           gdd_from_growthinit, herbivores, &
2743            &           Tseason, Tseason_length, Tseason_tmp, &
2744            &           Tmin_spring_time, t2m_min_daily, onset_date, &
2745            &           cn_leaf_min_season,nstress_season, &
2746            &           humrel_growingseason,rue_longterm, harvest_area, &
2747            &           harvest_5y_area)
2748
2749       !! 5.4 Waterstress
2750
2751       !  The waterstress factor varies between 0.1 and 1 and is calculated
2752       !  from ::humrel_growingseason. The latter is only used in the allometric
2753       !  allocation and its time integral is determined by tau_sap for trees
2754       !  (see constantes_mtc.f90 for tau_sap and see pft_constantes.f90 for
2755       !  the definition of tau_hum_growingseason). The time integral for
2756       !  grasses and crops is a prescribed constant (see constantes.f90). By
2757       !  having ::wstress_fac working on the turnover, water stress is progated
2758       !  into LF.
2759       !  Because the calculated values for ::wstress_fac are too low for this purpose
2760       !  Sonke Zhaele multiply it by two in the N-branch. This approach maintains
2761       !  the physiological basis of KF while combining it with a simple
2762       !  multiplicative factor for water stress. Clearly after multiplication with
2763       !  2, wstress is closer to 1 and will thus result in a KF values closer to
2764       !  the physiologically expected KF.
2765       !  In this implementation we take the sqrt (this is done in stomate where
2766       !  ::humrel_daily is calculated from ::stressed and ::unstressed. The
2767       !  transformation from the ratio between stressed an unstressed gpp into a
2768       !  numerical value that is used in the allocation and turnover is arbitrairy.
2769       !  A more physiological approach accounting for turgor would be needed to de
2770       !  fundamentally better.
2771       !  Note that the current implementation allows for the plants to adapt to drought
2772       !  by adjusting its allocation. This is a long-term effect and it is long-term
2773       !  because ::humrel_growingseason integrates over ::tau_sap. For the moment no
2774       !  short term effects to drought are implemented. Short-term effects should be
2775       !  implmented on mortality (through loss of turgor, heat stress, carbon starvation).
2776
2777       wstress_season(:,1) = zero
2778       wstress_month(:,1) = zero
2779!!$       vir_wstress_fac(:,1) = zero
2780
2781       DO jv = 2,nvm
2782
2783          ! Calculate waterstress
2784          ! Water stress used in stomate
2785          ! Set wstress to 1-humrel so that the value is consistent with its
2786          ! meaning. wstress=0 indicates no stress, wstress=1 indicates stress
2787          wstress_season(:,jv) = un - MAX(humrel_growingseason(:,jv), min_water_stress)
2788          wstress_month(:,jv) = un - MAX(humrel_month(:,jv), min_water_stress)
2789!!$          vir_wstress_fac(:,jv) = MAX(vir_humrel_growingseason(:,jv), min_water_stress)
2790
2791          !+++CHECK+++
2792          ! The reduction of the leaf longevity should probably depend on
2793          ! the leaf skin temperature that will become available through
2794          ! the multi-layer energy budget. For the moment we don't have
2795          ! water stress on the leaves. A long term adaption could be
2796          ! through ::sla
2797          tau_eff_leaf(:,jv) = tau_leaf(jv) * un
2798
2799          ! The reduction of the root longevity depends on the soil moisture
2800          ! stress which we believe is reasonably well captured by our
2801          ! proxy for wstress. We need to produce more roots to take the water
2802          ! from those layers that have water.
2803          ! feedback to c-allocation has been switched off
2804          tau_eff_root(:,jv) = tau_root(jv) *  un
2805
2806          ! The reduction of sapwood longevity should depend on the cavitation
2807          ! which is calculated in hydrol_architecture. Should be linked
2808          ! once the memory of cavitation is calculated
2809          tau_eff_sap(:,jv) = tau_sap(jv) *  un
2810          !+++++++++
2811
2812       ENDDO
2813
2814       ! Add to history file
2815       CALL histwrite_p (hist_id_stomate, 'WSTRESS_SEASON', itime, &
2816            wstress_season(:,:), kjpindex*nvm, horipft_index)
2817       CALL histwrite_p (hist_id_stomate, 'WSTRESS_MONTH', itime, &
2818            wstress_month(:,:), kjpindex*nvm, horipft_index)
2819       CALL xios_orchidee_send_field("WSTRESS_SEASON",wstress_season(:,:))
2820       CALL xios_orchidee_send_field("WSTRESS_MONTH",wstress_month(:,:))
2821
2822       !! 5.3.1  Activate stomate processes
2823       ! Activate stomate processes (the complete list of processes depends
2824       ! on whether the DGVM is used or not). Processes include: climate constraints
2825       ! for PFTs, PFT dynamics, Phenology, Allocation, NPP (based on GPP and
2826       ! authothropic respiration), fire, mortality, vmax, assimilation temperatures,
2827       ! all turnover processes, light competition, sapling establishment, lai and
2828       ! land cover change.
2829       CALL stomate_lpj_vegetation (kjpindex, dt_days, EndOfYear, &
2830            &             neighbours, resolution, &
2831            &             herbivores, &
2832            &             tsurf_daily, tsoil_daily, t2m_daily, t2m_min_daily, &
2833            &             litterhum_daily, soilhum_daily, &
2834            &             maxhumrel_lastyear, minhumrel_lastyear, &
2835            &             gdd0_lastyear, precip_lastyear, &
2836            &             humrel_month, humrel_week, &
2837            &             t2m_longterm, t2m_month, t2m_week, &
2838            &             tsoil_month, soilhum_month, &
2839            &             gdd_m5_dormance,  gdd_from_growthinit, gdd_midwinter, ncd_dormance, ngd_minus5, &
2840            &             turnover_longterm, gpp_daily, &
2841            &             time_hum_min, hum_min_dormance, maxfpc_lastyear, resp_maint_part,&
2842            &             PFTpresent, age, fireindex, firelitter, &
2843            &             leaf_age, leaf_frac, adapted, regenerate, &
2844            &             plant_status, when_growthinit, litter, &
2845            &             dead_leaves, som, lignin_struc, lignin_wood, &
2846            &             veget_cov_max, veget_cov, veget_cov_max_new, npp_longterm, lm_lastyearmax, &
2847            &             veget_lastlight, everywhere, need_adjacent, RIP_time, &
2848            &             rprof, npp_daily, turnover_daily, turnover_time,&
2849            &             control_moist_inst, control_temp_inst, som_input_daily, &
2850            &             atm_to_bm, co2_fire, &
2851            &             resp_hetero_d, resp_maint_d, resp_growth_d, &
2852            &             height, deadleaf_cover, vcmax, nue, &
2853            &             bm_to_litter,&
2854            &             prod_s, prod_m, prod_l, flux_s, flux_m, flux_l, &
2855            &             flux_prod_s, flux_prod_m, flux_prod_l, carb_mass_total, &
2856            &             fpc_max, MatrixA, MatrixV, VectorB, VectorU, &
2857            &             Tseason, Tmin_spring_time, onset_date, KF, k_latosa_adapt,&
2858            &             cn_leaf_min_season, nstress_season, humrel_growingseason, soil_n_min, &
2859            &             rue_longterm, plant_n_uptake_daily, &
2860            &             circ_class_n, circ_class_biomass, forest_managed, forest_managed_lastyear, &
2861            &             tau_eff_leaf, tau_eff_sap, tau_eff_root, &
2862            &             species_change_map, fm_change_map, lpft_replant, &
2863            &             age_stand, rotation_n, last_cut, mai, pai, &
2864            &             previous_wood_volume, mai_count, coppice_dens, &
2865            &             lab_fac, circ_class_dist, store_sum_delta_ba, &
2866            &             harvest_pool_bound, harvest_pool, harvest_type, harvest_cut, harvest_area, &
2867            &             lai_per_level, laieff_fit, h_array_out, z_array_out, &
2868            &             max_height_store, &
2869            &             wstress_month, wstress_season, st_dist, litter_demand,&
2870            &             mass_balance_closure, light_tran_to_level_season, p_O2, bact, &
2871            &             CN_som_litter_longterm, nbp_pool_start,&
2872            &             wind_speed_daily, soil_temp_daily, harvest_5y_area)
2873
2874       ! Write the mass balance error accumulated over the course of day
2875       ! to the history file
2876       ! If err_act = 3  the model should stop as soon as there is an
2877       ! imbalance. Hence, when this block of code is reached it means
2878       ! there is no mass balanc error. In case err_act is 1 or 2, the
2879       ! model will not be stopped. It is thus possible to end up here
2880       ! and to write a mass balance error.
2881       DO iele = 1,nelements
2882          IF (iele == icarbon) THEN
2883             element_str(iele) = '_c'
2884          ELSEIF (iele == initrogen) THEN
2885             element_str(iele) = '_n'
2886          ELSE
2887             CALL ipslerr_p(3,'stomate.f90','Define label for iele','','')
2888          ENDIF
2889
2890          CALL histwrite_p (hist_id_stomate,'MB_CLOSURE'//TRIM(element_str(iele)), itime, &
2891               mass_balance_closure(:,iele), kjpindex, horipft_index)
2892          CALL xios_orchidee_send_field("MB_CLOSURE"//TRIM(element_str(iele)), &
2893               mass_balance_closure(:,iele)) 
2894       ENDDO
2895
2896       !! 5.5.2 Long term adaptation of allocation to water stress
2897       !  ::wstress season is calculated as the seasonal mean of the
2898       !  ratio between the stressed and unstressed GPP. If the plant
2899       !  experiences a short spell of drought, leaves will be killed
2900       !  (see stomate_turnover). However, when the drought stress is
2901       !  maintained during the season, it is assumed that the plant
2902       !  will economise its canopy and therefore adjust its allocation
2903       ! factors to grow less leaves. To avoid that the canopy can only
2904       ! shrink the plants will try to grow more leaves when they do
2905       ! not experience any water stress. Extending the LAI, however,
2906       ! increases the chances that the plant will experience drough
2907       ! stress in the future. These feedbacks should stabilize the LAI.
2908       wstress_adapt(:,:) = zero
2909       WHERE (wstress_season(:,:) .LT. 0.01)
2910
2911          ! Increase the leaf allocation by 5% over the whole
2912          ! year. If there was no water stress during the whole
2913          ! year, the following year more C will be allocated
2914          ! to the leaves.
2915          wstress_adapt(:,:) = 1.05
2916
2917       ELSEWHERE
2918
2919          wstress_adapt(:,:) = wstress_season(:,:)
2920
2921       ENDWHERE
2922
2923       !+++CHECK+++
2924       ! Don't use this adaptation
2925!!$       k_latosa_adapt(:,:) = k_latosa_adapt(:,:) * &
2926!!$            (wstress_adapt(:,:)**(un/365))
2927       !+++++++++++
2928
2929       DO j = 2,nvm
2930
2931          WHERE ( k_latosa_adapt(:,j) .GE. k_latosa_max(j) )
2932
2933             k_latosa_adapt(:,j) = k_latosa_max(j)
2934
2935          ENDWHERE
2936
2937       ENDDO
2938
2939       CALL histwrite_p (hist_id_stomate, 'K_LATOSA_ADAPT', itime, &
2940            k_latosa_adapt(:,:), kjpindex*nvm, horipft_index)
2941       CALL xios_orchidee_send_field("K_LATOSA_ADAPT",k_latosa_adapt)
2942
2943       !+++CHECK+++
2944       ! check units and variable names for new lcchange and product use
2945       !! 5.3.2 Calculate the total CO2 flux from land use change
2946       !fco2_lu(:) = convflux(:) &
2947       !     &             + flux_prod10(:)  &
2948       !     &             + flux_prod100(:) &
2949       !     &             + harvest_above(:)
2950       ! It is an output variable so we just gave it a value
2951       ! when looking at the history files the value zero should
2952       ! ring a bell that there is something wrong.
2953       !fco2_lu(:) = 0
2954       !+++++++++++
2955
2956       !! 5.4 Calculate veget_max
2957       veget_max(:,:) = zero 
2958       DO j = 1, nvm
2959          veget_max(:,j) = veget_max(:,j) + &
2960               & veget_cov_max(:,j) * ( 1.-totfrac_nobio(:) )
2961       ENDDO
2962
2963       !! 5.5 Photosynthesis parameters
2964       assim_param(:,:,ivcmax) = zero
2965       assim_param(:,:,inue)   = zero
2966       assim_param(:,:,ileafn) = zero
2967       DO j = 2,nvm
2968          assim_param(:,j,ivcmax) = vcmax(:,j)
2969          assim_param(:,j,inue)   = nue(:,j)
2970          assim_param(:,j,ileafn) = SUM(circ_class_biomass(:,j,:,ileaf,initrogen)*circ_class_n(:,j,:),2)
2971       ENDDO
2972
2973       !! 5.6 Update forcing variables for soil carbon
2974       IF (TRIM(Cforcing_name) /= 'NONE') THEN
2975          npp_tot(:) = 0
2976          DO j=2,nvm
2977             npp_tot(:) = npp_tot(:) + npp_daily(:,j)
2978          ENDDO
2979          ! ::nbyear Number of years saved for carbon spinup
2980          sf_time = MODULO(REAL(date,r_std)-1,one_year*REAL(nbyear,r_std))
2981          iatt=FLOOR(sf_time/dt_forcesoil) + 1
2982          IF (iatt == 0) iatt = iatt_old + 1
2983          IF ((iatt<iatt_old) .and. (.not. cumul_Cforcing)) THEN
2984             nforce(:)=0
2985             carbon_input(:,:,:,:) = zero
2986             nitrogen_input(:,:,:,:) = zero
2987             control_moist(:,:,:) = zero
2988             control_temp(:,:,:) = zero
2989             npp_equil(:,:) = zero
2990             drainage(:,:,:) = zero
2991          ENDIF
2992          iatt_old = iatt
2993          ! Update forcing
2994          nforce(iatt) = nforce(iatt)+1
2995          carbon_input(:,:,:,iatt) = carbon_input(:,:,:,iatt) + som_input_daily(:,:,:,icarbon)
2996          nitrogen_input(:,:,:,iatt) = nitrogen_input(:,:,:,iatt) + som_input_daily(:,:,:,initrogen)
2997          control_moist(:,:,iatt) = control_moist(:,:,iatt) + control_moist_daily(:,:)
2998          control_temp(:,:,iatt) = control_temp(:,:,iatt) + control_temp_daily(:,:)
2999          npp_equil(:,iatt) = npp_equil(:,iatt) + npp_tot(:)
3000          drainage(:,:,iatt) = drainage(:,:,iatt) + drainage_daily(:,:)
3001       ENDIF
3002
3003       !! 5.8 Write forcing file
3004       ! Note: if STOMATE is run in coupled mode the forcing file is written
3005       ! If run in stand-alone mode, the forcing file is read!
3006       IF ( TRIM(forcing_name) /= 'NONE' ) THEN
3007
3008          !! 5.8.1 Convert GPP to sechiba time steps
3009          ! GPP is multiplied by coverage to obtain forcing @tex $(gC m^{-2} dt_stomate^{-1})$\f \end@tex $(m^2 m^{-2})$ @endtexonly
3010          ! @tex$ m^{-2}$ @endtex remains in the units because ::veget_cov_max is a fraction, not a
3011          ! surface area. In sechiba values are ponderated by surface and frac_no_bio.
3012          ! At the beginning of stomate, the units are converted.
3013          ! When we use forcesoil we call sechiba_main and so we need the have the same units as in sechiba.
3014          gpp_daily_x(:,:) = zero
3015          DO j = 2, nvm             
3016             gpp_daily_x(:,j) = gpp_daily_x(:,j) + &
3017                  & gpp_daily(:,j) * dt_stomate / one_day * veget_cov_max(:,j)
3018          ENDDO
3019
3020          ! Bare soil moisture availability has not been treated
3021          ! in STOMATE, update it here
3022          humrel_daily(:,ibare_sechiba) = humrel(:,ibare_sechiba)   
3023
3024          ! Update index to store the next forcing step in memory
3025          iisf = iisf+1
3026
3027          ! How many times have we treated this forcing state
3028          xn = REAL(nf_cumul(isf(iisf)),r_std)
3029
3030          !! 5.8.2 Cumulate forcing variables
3031          ! Cumulate forcing variables (calculate average)
3032          ! Note: precipitation is multiplied by dt_stomate/one_day to be consistent with
3033          ! the units in sechiba
3034          IF (cumul_forcing) THEN
3035             clay_fm(:,iisf) = (xn*clay_fm(:,iisf)+clay(:))/(xn+1.)
3036             silt_fm(:,iisf) = (xn*silt_fm(:,iisf)+silt(:))/(xn+1.) 
3037             bulk_fm(:,iisf) = (xn*bulk_fm(:,iisf)+bulk(:))/(xn+1.) 
3038             humrel_daily_fm(:,:,iisf) = &
3039                  & (xn*humrel_daily_fm(:,:,iisf) + humrel_daily(:,:))/(xn+1.)
3040             litterhum_daily_fm(:,iisf) = &
3041                  & (xn*litterhum_daily_fm(:,iisf)+litterhum_daily(:))/(xn+1.)
3042             t2m_daily_fm(:,iisf) = &
3043                  & (xn*t2m_daily_fm(:,iisf)+t2m_daily(:))/(xn+1.)
3044             t2m_min_daily_fm(:,iisf) = &
3045                  & (xn*t2m_min_daily_fm(:,iisf)+t2m_min_daily(:))/(xn+1.)
3046             tsurf_daily_fm(:,iisf) = &
3047                  & (xn*tsurf_daily_fm(:,iisf)+tsurf_daily(:))/(xn+1.)
3048             tsoil_daily_fm(:,:,iisf) = &
3049                  & (xn*tsoil_daily_fm(:,:,iisf)+tsoil_daily(:,:))/(xn+1.)
3050             soilhum_daily_fm(:,:,iisf) = &
3051                  & (xn*soilhum_daily_fm(:,:,iisf)+soilhum_daily(:,:))/(xn+1.)
3052             precip_fm(:,iisf) = &
3053                  & (xn*precip_fm(:,iisf)+precip_daily(:)*dt_stomate/one_day)/(xn+1.)
3054             gpp_daily_fm(:,:,iisf) = &
3055                  & (xn*gpp_daily_fm(:,:,iisf) + gpp_daily_x(:,:))/(xn+1.)
3056             veget_fm(:,:,iisf) = &
3057                  & (xn*veget_fm(:,:,iisf) + veget(:,:) )/(xn+1.)
3058             veget_max_fm(:,:,iisf) = &
3059                  & (xn*veget_max_fm(:,:,iisf) + veget_max(:,:) )/(xn+1.)
3060!!$             lai_fm(:,:,iisf) = &
3061!!$                  & (xn*lai_fm(:,:,iisf) + lai(:,:) )/(xn+1.)
3062             drainage_fm(:,:,iisf) = & 
3063                  & (xn*drainage_fm(:,:,iisf) + drainage_daily(:,:) )/(xn+1.) 
3064          ELSE
3065             ! Here we just calculate the values
3066             clay_fm(:,iisf) = clay(:)
3067             silt_fm(:,iisf) = silt(:) 
3068             bulk_fm(:,iisf) = bulk(:) 
3069             humrel_daily_fm(:,:,iisf) = humrel_daily(:,:)
3070             litterhum_daily_fm(:,iisf) = litterhum_daily(:)
3071             t2m_daily_fm(:,iisf) = t2m_daily(:)
3072             t2m_min_daily_fm(:,iisf) =t2m_min_daily(:)
3073             tsurf_daily_fm(:,iisf) = tsurf_daily(:)
3074             tsoil_daily_fm(:,:,iisf) =tsoil_daily(:,:)
3075             soilhum_daily_fm(:,:,iisf) =soilhum_daily(:,:)
3076             precip_fm(:,iisf) = precip_daily(:)
3077             gpp_daily_fm(:,:,iisf) =gpp_daily_x(:,:)
3078             veget_fm(:,:,iisf) = veget(:,:)
3079             veget_max_fm(:,:,iisf) =veget_max(:,:)
3080!!$             lai_fm(:,:,iisf) =lai(:,:)
3081             drainage_fm(:,:,iisf) =drainage_daily(:,:) 
3082          ENDIF
3083          nf_cumul(isf(iisf)) = nf_cumul(isf(iisf))+1
3084
3085          ! 5.8.3 Do we have to write the forcing states?
3086          IF (iisf == nsfm) THEN
3087
3088             !! 5.8.3.1 Write these forcing states
3089             CALL forcing_write(forcing_id,1,nsfm)
3090             ! determine which forcing states must be read
3091             isf(1) = isf(nsfm)+1
3092             IF ( isf(1) > nsft ) isf(1) = 1
3093             DO iisf = 2, nsfm
3094                isf(iisf) = isf(iisf-1)+1
3095                IF (isf(iisf) > nsft)  isf(iisf) = 1
3096             ENDDO
3097
3098             ! Read forcing variables - for debug use only
3099             ! CALL forcing_read(forcing_id,nsfm)
3100             iisf = 0
3101
3102          ENDIF
3103
3104       ENDIF
3105
3106
3107!!$       !! 5.9 Compute daily CO2 flux (AR5 output - not essential)
3108!!$       ! CO2 flux in @tex $gC m^{-2} s^{-1}$ @endtex (positive towards the atmosphere) is sum of:
3109!!$       ! (1) heterotrophic respiration from ground + (2) maintenance respiration
3110!!$       ! from the plants + (3) growth respiration from the plants + (4) co2
3111!!$       ! emissions from fire - (5) co2 taken up in the DGVM to establish
3112!!$       ! saplings - (6) co2 taken up by photosyntyhesis
3113!!$       co2_flux_daily(:,:)=   &
3114!!$            & resp_maint_d(:,:) + resp_growth_d(:,:) + resp_hetero_d(:,:) + &
3115!!$            & co2_fire(:,:) - atm_to_bm(:,:,icarbon) - gpp_daily(:,:)
3116!!$
3117!!$     CALL xios_orchidee_send_field("nep",SUM(co2_flux_daily*veget_cov_max,dim=2)/1e3/one_day)
3118!!$
3119!!$       IF ( hist_id_stom_IPCC > 0 ) THEN
3120!!$          vartmp(:) = SUM(co2_flux_daily*veget_cov_max,dim=2)/1e3/one_day*contfrac
3121!!$          CALL histwrite_p (hist_id_stom_IPCC, "nep", itime, &
3122!!$               vartmp, kjpindex, hori_index)
3123!!$       ENDIF
3124!!$
3125!!$       ! See 5.9 for details on NEP + fire. At the monthly time step also
3126!!$       ! harvest and land use change are calculated
3127!!$       co2_flux_monthly(:,:) = co2_flux_monthly(:,:) + co2_flux_daily(:,:)
3128!!$       harvest_above_monthly(:) = harvest_above_monthly(:) + harvest_above(:)
3129!!$       flux_prod_monthly(:) = flux_prod_monthly(:) + convflux(:) + &
3130!!$        & flux_prod10(:) + flux_prod100(:)
3131!!$     
3132!!$       !! 5.10 Compute monthly CO2 fluxes
3133!!$       IF ( EndOfMonth ) THEN
3134!!$          !! 5.10.1 Write history file for monthly fluxes
3135!!$          CALL histwrite_p (hist_id_stomate, 'CO2FLUX', itime, &
3136!!$               co2_flux_monthly, kjpindex*nvm, horipft_index)
3137!!$         
3138!!$          !?? I (=VB) translated the French, but the whole stuff does not make sense to me.
3139!!$          ! If one deletes the montly cumulation,
3140!!$          ! one should not forget this change in resolution(:,1)*resolution(:,2)*contfrac(:)
3141!!$          ! Si on supprimer le cumul par mois,
3142!!$          ! il ne faut pas oublier cette modif resolution(:,1)*resolution(:,2)*contfrac(:)
3143!!$          ! Should be supressed, this is post-processing
3144!!$          DO j=2, nvm
3145!!$             co2_flux_monthly(:,j) = co2_flux_monthly(:,j)* &
3146!!$                  resolution(:,1)*resolution(:,2)*contfrac(:)
3147!!$          ENDDO
3148!!$
3149!!$          ! Should be supressed, this is post-processing
3150!!$          ! ?? How does it differ from co2_flux_monthly??
3151!!$          net_co2_flux_monthly = zero
3152!!$          DO ji=1,kjpindex
3153!!$             DO j=2,nvm
3154!!$                net_co2_flux_monthly = net_co2_flux_monthly + &
3155!!$                     &  co2_flux_monthly(ji,j)*veget_cov_max(ji,j)
3156!!$             ENDDO
3157!!$          ENDDO
3158!!$
3159!!$     
3160!!$          !! 5.10.2 Cumulative fluxes of land use cover change, harvest and net biosphere production
3161!!$          ! Parallel processing, gather the information from different processors. first argument is the lo
3162!!$          ! local variable, the second argument is the global variable. bcast send it to all processors.
3163!!$          net_flux_prod_monthly_sum = &
3164!!$              &  SUM(flux_prod_monthly(:)*resolution(:,1)*resolution(:,2)*contfrac(:))*1e-15
3165!!$          CALL reduce_sum(net_flux_prod_monthly_sum,net_flux_prod_monthly_tot)
3166!!$          CALL bcast(net_flux_prod_monthly_tot)
3167!!$          net_harvest_above_monthly_sum = &
3168!!$             &   SUM(harvest_above_monthly(:)*resolution(:,1)*resolution(:,2)*contfrac(:))*1e-15
3169!!$          CALL reduce_sum(net_harvest_above_monthly_sum,net_harvest_above_monthly_tot)
3170!!$          CALL bcast(net_harvest_above_monthly_tot)
3171!!$          net_co2_flux_monthly = net_co2_flux_monthly*1e-15
3172!!$          CALL reduce_sum(net_co2_flux_monthly,net_co2_flux_monthly_sum)
3173!!$          CALL bcast(net_co2_flux_monthly_sum)
3174!!$          net_biosp_prod_monthly_tot =  &
3175!!$             & ( net_co2_flux_monthly_sum + net_flux_prod_monthly_tot + &
3176!!$             & net_harvest_above_monthly_tot )
3177!!$         
3178!!$          WRITE(numout,9010) 'GLOBAL net_flux_prod_monthly    (Peta gC/month)  = ',net_flux_prod_monthly_tot
3179!!$          WRITE(numout,9010) 'GLOBAL net_harvest_above_monthly (Peta gC/month)  = ',net_harvest_above_monthly_tot
3180!!$          WRITE(numout,9010) 'GLOBAL net_co2_flux_monthly      (Peta gC/month)  = ',net_co2_flux_monthly_sum
3181!!$          WRITE(numout,9010) 'GLOBAL net_biosp_prod_monthly    (Peta gC/month)  = ',net_biosp_prod_monthly_tot
3182!!$
3183!!$9010  FORMAT(A52,F17.14)
3184!!$
3185!!$          ! Reset Monthly values
3186!!$          co2_flux_monthly(:,:) = zero
3187!!$          harvest_above_monthly(:) = zero
3188!!$          flux_prod_monthly(:)    = zero
3189!!$
3190!!$       ENDIF ! Monthly processes - at the end of the month
3191
3192    !   IF (spinup_analytic) THEN
3193    !   I (ASLA) Do not think we have to include the below calculations of
3194    !   nbp_accu. It is only used to calculate nbp_flux, but this variable is
3195    !   use for nothing except being written to the restart/being read from the
3196    !   restart. It is still included on CN, but there I do not see the use of
3197    !   it either. 
3198   
3199    !      WRITE(numout,*) 'ERROR:check the code. There was nothing defined yet'
3200    !      CALL ipslerr_p(3,'ERROR:check the code', &
3201    !           'there was nothing defined yet','','')
3202
3203!!$       CALL xios_orchidee_send_field("nep",SUM(co2_flux_daily*veget_cov_max,dim=2)/1e3/one_day)
3204
3205          !+++CHECK+++
3206    !      nbp_accu(:) = nbp_accu(:) + (-SUM(co2_flux_daily(:,:) * &
3207    !           veget_cov_max(:,:),dim=2) - (convflux(:) + flux_prod10(:) + &
3208    !           flux_prod100(:))  - harvest_above(:))/1e3
3209
3210          ! Daily NBP is used in the spin-up. Rather than starting from
3211          ! all the initial components as done previously we prefer to
3212          ! make use of the aggregated components calculated to check the
3213          ! mass balance closure. NBP is then the change in all
3214          ! biomass pools.
3215
3216          !+++CHECK+++
3217          ! pool_end and pool_begin need to be defined
3218!!$          nbp_accu(:) = nbp_accu(:) + &
3219!!$               SUM((pool_end(:,:,icarbon) - pool_start(:,:,icarbon)),2)
3220          !+++++++++++
3221
3222      ! ENDIF (spinup_analytic)
3223       !! 5.11 Reset daily variables
3224       humrel_daily(:,:) = zero
3225       litterhum_daily(:) = zero
3226       t2m_daily(:) = zero
3227       t2m_min_daily(:) = large_value
3228       tsurf_daily(:) = zero
3229       tsoil_daily(:,:) = zero
3230       soilhum_daily(:,:) = zero
3231       precip_daily(:) = zero
3232       gpp_daily(:,:) = zero
3233       resp_maint_part(:,:,:)=zero
3234       resp_hetero_d=zero
3235       drainage_daily(:,:) = zero 
3236       plant_n_uptake_daily(:,:,:)=zero 
3237       n_mineralisation_d(:,:)=zero 
3238       IF (printlev_loc >= 3) THEN
3239          WRITE(numout,*) 'stomate_main: daily processes done'
3240       ENDIF
3241
3242
3243       ! 5.12 pool-based NBP.
3244       ! Calculate the end pool for the pool-based NBP estimate
3245       IF( SPINUP_ANALYTIC ) THEN
3246          DO ipar = 1,nparts
3247             DO icir=1, ncirc
3248                nbp_pool_end(:,:) = nbp_pool_end(:,:) + &
3249                   (circ_class_biomass(:,:,icir,ipar,icarbon) * &
3250                   circ_class_n(:,:,icir)*veget_cov_max(:,:))
3251             ENDDO
3252          ENDDO
3253          ! To make sure we the carbon that leaves the ecosystem via heterotropic
3254          ! respiration
3255          ! in to account, the soil and litter pools are summed
3256          DO icarb = 1, ncarb
3257             nbp_pool_end(:,:) = nbp_pool_end(:,:) + &
3258               som(:,icarb,:,icarbon)*veget_cov_max(:,:)
3259          ENDDO
3260
3261          DO ilitt = 1,nlitt
3262             DO ilev =1,nlevs
3263                nbp_pool_end(:,:) = nbp_pool_end(:,:) + &
3264                   litter(:,ilitt,:,ilev,icarbon)*veget_cov_max(:,:)
3265             ENDDO
3266          ENDDO
3267
3268          ! Calculate nbp for each time step
3269          nbp(:,:)=nbp_pool_end(:,:) - nbp_pool_start(:,:)
3270          ! Calculate an accumulated pool-based NBP
3271          nbp_accu_pool(:,:) = nbp_accu_pool(:,:) + nbp(:,:)
3272   
3273          ! reset the nbp_pool_start and nbp_pool_end
3274          nbp_pool_start(:,:) = nbp_pool_end
3275          nbp_pool_end(:,:) = zero 
3276
3277          ! Write to output
3278          CALL xios_orchidee_send_field("NBP_pool",nbp)
3279       ENDIF ! SPINUP_ANALYTIC
3280 
3281    ENDIF  ! Daily processes - at the end of the day
3282
3283    !! 6. Outputs from Stomate
3284
3285    ! co2_flux receives a value from STOMATE only if STOMATE is activated.
3286    ! Otherwise, the calling hydrological module must do this itself.
3287
3288    !! 6.1 Respiration and fluxes
3289    resp_maint(:,:) = resp_maint_radia(:,:)*veget_cov_max(:,:)
3290    resp_maint(:,ibare_sechiba) = zero
3291    resp_growth(:,:)= resp_growth_d(:,:)*veget_cov_max(:,:)*dt_sechiba/one_day
3292    resp_hetero(:,:) = resp_hetero_radia(:,:)*veget_cov_max(:,:)
3293
3294    !! 6.2 Derived CO2 fluxes
3295    ! CO2 flux in gC m^{-2} s^{-1} (positive towards the atmosphere) is sum of:
3296    ! (1) heterotrophic respiration from ground + (2) maintenance respiration
3297    ! from the plants + (3) growth respiration from the plants + (4) co2
3298    ! emissions from fire - (5) co2 taken up in the DGVM to establish
3299    ! saplings - (6) co2 taken up by photosyntyhesis
3300    co2_flux(:,:) = resp_hetero(:,:) + resp_maint(:,:) + resp_growth(:,:) &
3301         & + (co2_fire(:,:)-atm_to_bm(:,:,icarbon))*veget_cov_max(:,:)/one_day &
3302         & - gpp(:,:)
3303
3304    temp_growth(:)=t2m_month(:)-tp_00 
3305
3306    !! 7. Analytical spinup
3307
3308    IF (spinup_analytic) THEN
3309
3310       tau_CN_longterm = tau_CN_longterm + dt_sechiba/one_day
3311
3312       !! 7.1. Update V and U at sechiba time step
3313       DO m = 2,nvm
3314          DO j = 1,kjpindex 
3315             ! V <- A * V
3316             matrixV(j,m,:,:) = MATMUL(matrixA(j,m,:,:),matrixV(j,m,:,:))
3317             ! U <- A*U + B
3318             vectorU(j,m,:) = MATMUL(matrixA(j,m,:,:),vectorU(j,m,:)) + vectorB(j,m,:)
3319          ENDDO ! loop pixels
3320       ENDDO ! loop PFTS
3321
3322
3323       !! 7.2. What happened at the end of the year ?
3324       IF (EndOfYear) THEN
3325
3326          !
3327          ! 7.2.1 Increase the years counter every EndOfyear
3328          !
3329          global_years = global_years + 1 
3330
3331
3332          !
3333          ! 7.2.3 Is global_years is a multiple of the period time ?
3334          !
3335
3336          !
3337          ! 3.2.1 When global_years is a multiple of the spinup_period, we calculate :
3338          !       1) the mean nbp flux over the period. This value is restarted
3339          !       2) we solve the matrix system by Gauss Jordan method
3340          !       3) We test if a point is at equilibrium : if yes, we mark the point (ok_equilibrium array)
3341          !       4) Then we reset the matrix
3342          !       5) We erase the carbon_stock calculated by ORCHIDEE by the one found by the method
3343          IF( MOD(global_years, spinup_period) == 0 ) THEN
3344             WRITE(numout,*) 'Spinup analytic : Calculate if system is in equlibrium. global_years=',global_years
3345             ! The number total of days during the forcing period is given by :
3346             !    spinup_period*365 (we consider only the noleap calendar)
3347             nbp_flux(:) = nbp_accu(:) / ( spinup_period * 365.)
3348             nbp_pool(:,:) = nbp_accu_pool(:,:) / ( spinup_period * 365.)
3349             ! write to output
3350             CALL xios_orchidee_send_field("NBP_pool_spinup",nbp_pool)
3351
3352             ! Reset the values
3353             nbp_accu(:) = zero
3354             nbp_accu_pool(:,:) = zero
3355
3356             carbon_stock(:,ibare_sechiba,:) = zero
3357             ! Prepare the matrix for the resolution
3358             ! Add a temporary matrix W which contains I-matrixV
3359             ! we should take the opposite of matrixV and add the identitiy : we solve (I-matrixV)*C = vectorU
3360             matrixW(:,:,:,:) = moins_un * matrixV(:,:,:,:)
3361             DO jv = 1,nbpools
3362                matrixW(:,:,jv,jv) =  matrixW(:,:,jv,jv) + un
3363             ENDDO
3364             carbon_stock(:,:,:) = vectorU(:,:,:)
3365
3366             !
3367             !  Solve the linear system
3368             !
3369             DO m = 2,nvm
3370                DO j = 1,kjpindex
3371                   ! the solution will be stored in vectorU : so it should be restarted before
3372                   ! loop over kjpindex and nvm, so we solved kjpindex*(nvm-1) (7,7) linear systems
3373                   CALL gauss_jordan_method(nbpools,matrixW(j,m,:,:),carbon_stock(j,m,:))
3374                ENDDO ! loop pixels
3375             ENDDO ! loop PFTS
3376
3377             ! Reset temporary matrixW
3378             matrixW(:,:,:,:) = zero 
3379
3380
3381             previous_stock(:,:,:) = current_stock(:,:,:)
3382             current_stock(:,:,:) = carbon_stock(:,:,:)
3383 
3384             ! The relative error is calculated over the passive carbon pool
3385             ! (sum over the pfts) over the pixel.
3386             CALL error_L1_passive(kjpindex,nvm, nbpools, current_stock, &
3387                  previous_stock, veget_cov_max, eps_carbon, carbon_eq)   
3388
3389             !! ok_equilibrium is saved,
3390             WHERE( carbon_eq(:) .AND. .NOT.(ok_equilibrium(:)) )
3391                ok_equilibrium(:) = .TRUE. 
3392             ENDWHERE
3393
3394             WRITE(numout,*) 'current_stock actif:',current_stock(test_grid,test_pft,iactive)
3395             WRITE(numout,*) 'current_stock slow:',current_stock(test_grid,test_pft,islow)
3396             WRITE(numout,*) 'current_stock passif:',current_stock(test_grid,test_pft,ipassive)
3397             WRITE(numout,*) 'current_stock surface:',current_stock(test_grid,test_pft,isurface)
3398
3399             ! Reset matrixV for the pixel to the identity matrix and vectorU to zero
3400             matrixV(:,:,:,:) = zero
3401             vectorU(:,:,:) = zero
3402             DO jv = 1,nbpools
3403                matrixV(:,:,jv,jv) = un
3404             END DO
3405             WRITE(numout,*) 'Reset for matrixV and vectorU done'   
3406
3407             !! Write the values found in the standard outputs of ORCHIDEE
3408             litter(:,istructural,:,iabove,icarbon) = carbon_stock(:,:,istructural_above)
3409             litter(:,istructural,:,ibelow,icarbon) = carbon_stock(:,:,istructural_below)
3410             litter(:,imetabolic,:,iabove,icarbon) = carbon_stock(:,:,imetabolic_above)
3411             litter(:,imetabolic,:,ibelow,icarbon) = carbon_stock(:,:,imetabolic_below)
3412             litter(:,iwoody,:,iabove,icarbon) = carbon_stock(:,:,iwoody_above)
3413             litter(:,iwoody,:,ibelow,icarbon) = carbon_stock(:,:,iwoody_below)
3414             som(:,iactive,:,icarbon) = carbon_stock(:,:,iactive_pool)
3415             som(:,isurface,:,icarbon) = carbon_stock(:,:,isurface_pool)
3416             som(:,islow,:,icarbon) = carbon_stock(:,:,islow_pool)
3417             som(:,ipassive,:,icarbon) = carbon_stock(:,:,ipassive_pool) 
3418
3419             litter(:,:,:,:,initrogen) = zero
3420             som(:,:,:,initrogen) = zero
3421
3422             WHERE( CN_som_litter_longterm(:,:,istructural_above) .GT. min_stomate)
3423                litter(:,istructural,:,iabove,initrogen) = carbon_stock(:,:,istructural_above) &
3424                     / CN_som_litter_longterm(:,:,istructural_above)
3425             ENDWHERE
3426
3427             WHERE( CN_som_litter_longterm(:,:,istructural_below) .GT. min_stomate)
3428                litter(:,istructural,:,ibelow,initrogen) = carbon_stock(:,:,istructural_below) &
3429                     / CN_som_litter_longterm(:,:,istructural_below)
3430             ENDWHERE
3431
3432             WHERE( CN_som_litter_longterm(:,:,imetabolic_above) .GT. min_stomate)
3433                litter(:,imetabolic,:,iabove,initrogen)  = carbon_stock(:,:,imetabolic_above)  &
3434                     / CN_som_litter_longterm(:,:,imetabolic_above)
3435             ENDWHERE
3436
3437             WHERE( CN_som_litter_longterm(:,:,imetabolic_below) .GT. min_stomate)
3438                litter(:,imetabolic,:,ibelow,initrogen)  = carbon_stock(:,:,imetabolic_below)  &
3439                     / CN_som_litter_longterm(:,:,imetabolic_below)
3440             ENDWHERE
3441
3442             WHERE( CN_som_litter_longterm(:,:,iwoody_above) .GT. min_stomate)
3443                litter(:,iwoody,:,iabove,initrogen)      = carbon_stock(:,:,iwoody_above)      &
3444                     / CN_som_litter_longterm(:,:,iwoody_above)   
3445             ENDWHERE
3446
3447             WHERE( CN_som_litter_longterm(:,:,iwoody_below) .GT. min_stomate)
3448                litter(:,iwoody,:,ibelow,initrogen)      = carbon_stock(:,:,iwoody_below)      &
3449                     / CN_som_litter_longterm(:,:,iwoody_below)   
3450             ENDWHERE
3451
3452             WHERE(CN_som_litter_longterm(:,:,iactive_pool) .GT. min_stomate)
3453                som(:,iactive,:,initrogen)               = carbon_stock(:,:,iactive_pool)      &
3454                     / CN_som_litter_longterm(:,:,iactive_pool)   
3455             ENDWHERE
3456
3457             WHERE(CN_som_litter_longterm(:,:,isurface_pool) .GT. min_stomate)
3458                som(:,isurface,:,initrogen)              = carbon_stock(:,:,isurface_pool)     &
3459                     / CN_som_litter_longterm(:,:,isurface_pool)   
3460             ENDWHERE
3461
3462             WHERE(CN_som_litter_longterm(:,:,islow_pool) .GT. min_stomate)
3463                som(:,islow,:,initrogen)                 = carbon_stock(:,:,islow_pool)        &
3464                     / CN_som_litter_longterm(:,:,islow_pool)     
3465             ENDWHERE
3466
3467             WHERE(CN_som_litter_longterm(:,:,ipassive_pool) .GT. min_stomate)
3468                som(:,ipassive,:,initrogen)              = carbon_stock(:,:,ipassive_pool)     &
3469                     / CN_som_litter_longterm(:,:,ipassive_pool)     
3470             ENDWHERE
3471
3472             CN_som_litter_longterm(:,:,:) = zero
3473             tau_CN_longterm = dt_sechiba/one_day
3474             ! Final step, test if all points at the local domain are at equilibrium
3475             ! The simulation can be stopped when all local domains have reached the equilibrium
3476             IF(ALL(ok_equilibrium)) THEN
3477                WRITE(numout,*) 'Spinup analytic : Equilibrium for carbon pools is reached for current local domain'
3478             ELSE
3479                WRITE(numout,*) 'Spinup analytic : Equilibrium for carbon pools is not yet reached for current local domain'
3480             END IF
3481          ENDIF ! ( MOD(global_years,spinup_period) == 0)
3482       ENDIF ! (EndOfYear)
3483
3484    ENDIF !(spinup_analytic)
3485
3486    IF (printlev >= 4) WRITE(numout,*) 'Leaving stomate_main'
3487
3488  END SUBROUTINE stomate_main
3489
3490!! ================================================================================================================================
3491!! SUBROUTINE   : stomate_finalize
3492!!
3493!>\BRIEF        Write variables to restart file
3494!!
3495!! DESCRIPTION  : Write variables to restart file
3496!! RECENT CHANGE(S) : None
3497!!
3498!! MAIN OUTPUT VARIABLE(S):
3499!!
3500!! REFERENCES   :
3501!!
3502!! \n
3503!_ ================================================================================================================================
3504
3505  SUBROUTINE stomate_finalize (kjit, kjpindex, index, clay, assim_param, silt, bulk, &
3506       circ_class_biomass, circ_class_n, lai_per_level, laieff_fit) 
3507   
3508    IMPLICIT NONE
3509   
3510    !! 0. Variable and parameter declaration
3511    !! 0.1 Input variables
3512    INTEGER(i_std),INTENT(in)                       :: kjit              !! Time step number (unitless)
3513    INTEGER(i_std),INTENT(in)                       :: kjpindex          !! Domain size - terrestrial pixels only (unitless)
3514    INTEGER(i_std),DIMENSION(kjpindex),INTENT(in)   :: index             !! Indices of the terrestrial pixels only (unitless)
3515    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: clay              !! Clay fraction of soil (0-1, unitless)
3516    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: silt              !! Silt fraction of soil (0-1, unitless)
3517    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: bulk              !! Bulk density (kg/m**3)
3518    REAL(r_std),DIMENSION(kjpindex,nvm,npco2),INTENT(in) :: assim_param  !! min+max+opt temperatures (K) & vmax for
3519                                                                         !! photosynthesis   
3520    REAL(r_std), DIMENSION(:,:,:,:,:), INTENT(in)   :: circ_class_biomass !!  Biomass components of the model tree 
3521                                                                         !! within a circumference class
3522                                                                         !! class @tex $(g C ind^{-1})$ @endtex
3523    REAL(r_std), DIMENSION(:,:,:), INTENT(in)       :: circ_class_n      !! Number of trees within each circumference
3524                                                                         !! class @tex $(m^{-2})$ @endtex
3525    REAL(r_std), DIMENSION(:,:,:), INTENT(in)       :: lai_per_level     !! This is the LAI per vertical level
3526                                                                         !! @tex $(m^{2} m^{-2})$
3527    TYPE(laieff_type),DIMENSION (:,:,:),INTENT(in) &
3528                                                   :: laieff_fit         !! Fitted parameters for the effective LAI
3529
3530!! 0.2 Output variables
3531
3532    !! 0.4 Local variables
3533    REAL(r_std)                                   :: dt_days_read             !! STOMATE time step read in restart file (days)
3534    INTEGER(i_std)                                :: l,k,ji, jv, i, j, m      !! indices   
3535    REAL(r_std),PARAMETER                         :: max_dt_days = 5.         !! Maximum STOMATE time step (days)
3536    REAL(r_std)                                   :: hist_days                !! Writing frequency for history file (days)
3537    REAL(r_std),DIMENSION(0:nbdl)                 :: z_soil                   !! Variable to store depth of the different soil layers (m)
3538    REAL(r_std),DIMENSION(kjpindex)               :: cvegtot                  !! Total "vegetation" cover (unitless)
3539    REAL(r_std),DIMENSION(kjpindex)               :: precip                   !! Total liquid and solid precipitation 
3540                                                                              !! @tex $(??mm dt_stomate^{-1})$ @endtex
3541    REAL(r_std),DIMENSION(kjpindex,nvm)           :: gpp_d                    !! Gross primary productivity per ground area
3542                                                                              !! @tex $(??gC m^{-2} dt_stomate^{-1})$ @endtex 
3543    REAL(r_std),DIMENSION(kjpindex,nvm)           :: gpp_daily_x              !! "Daily" gpp for teststomate 
3544                                                                              !! @tex $(??gC m^{-2} dt_stomate^{-1})$ @endtex
3545    REAL(r_std),DIMENSION(kjpindex,nvm)           :: resp_hetero_litter       !! Litter heterotrophic respiration per ground area
3546                                                                              !! @tex $(gC m^{-2} day^{-1})$ @endtex 
3547                                                                              !! ??Same variable is also used to
3548                                                                              !! store heterotrophic respiration per ground area
3549                                                                              !! over ::dt_sechiba??
3550    REAL(r_std),DIMENSION(kjpindex,nvm)           :: resp_hetero_soil         !! soil heterotrophic respiration 
3551                                                                              !! @tex $(gC m^{-2} day^{-1})$ @endtex
3552    REAL(r_std),DIMENSION(kjpindex,nvm)           :: veget_cov                !! Fractional coverage: actually share of the pixel
3553                                                                              !! covered by a PFT (fraction of ground area),
3554                                                                              !! taking into account LAI ??(= grid scale fpc)??
3555    REAL(r_std),DIMENSION(kjpindex,nvm)           :: vcmax                    !! Maximum rate of carboxylation
3556                                                                              !! @tex $(\mumol m^{-2} s^{-1})$ @endtex
3557    REAL(r_std),DIMENSION(kjpindex,nlevs)         :: control_moist_inst       !! Moisture control of heterotrophic respiration
3558                                                                              !! (0-1, unitless)
3559    REAL(r_std),DIMENSION(kjpindex,nlevs)         :: control_temp_inst        !! Temperature control of heterotrophic
3560                                                                              !! respiration, above and below (0-1, unitless)
3561    REAL(r_std),DIMENSION(kjpindex,ncarb,nvm,nelements)   :: som_input_inst   !! Quantity of carbon going into carbon pools from
3562                                                                              !! litter decomposition
3563                                                                              !! @tex $(gC m^{-2} day^{-1})$ @endtex
3564   
3565    INTEGER(i_std)                                :: ier                      !! Check errors in netcdf call (unitless)
3566    REAL(r_std)                                   :: sf_time                  !! Intermediate variable to calculate current time
3567                                                                              !! step
3568    INTEGER(i_std)                                :: max_totsize              !! Memory management - maximum memory size (Mb)
3569    INTEGER(i_std)                                :: totsize_1step            !! Memory management - memory required to store one
3570                                                                              !! time step on one processor (Mb)
3571    INTEGER(i_std)                                :: totsize_tmp              !! Memory management - memory required to store one
3572                                                                              !! time step on all processors(Mb)
3573    REAL(r_std)                                   :: xn                       !! How many times have we treated in this forcing
3574    REAL(r_std), DIMENSION(kjpindex)              :: vartmp                   !! Temporary variable
3575    INTEGER(i_std)                                :: vid                      !! Variable identifer of netCDF (unitless)
3576    INTEGER(i_std)                                :: nneigh                   !! Number of neighbouring pixels
3577    INTEGER(i_std)                                :: direct                   !! ??
3578    INTEGER(i_std),DIMENSION(ndm)                 :: d_id                     !! ??
3579    REAL(r_std),DIMENSION(nbp_glo)                :: clay_g                   !! Clay fraction of soil (0-1, unitless), parallel
3580                                                                              !! computing
3581    REAL(r_std),DIMENSION(nbp_glo)                :: silt_g                   !! Silt fraction of soil (0-1, unitless), parallel 
3582                                                                              !! computing
3583    REAL(r_std),DIMENSION(nbp_glo)                :: bulk_g                   !! Bulk density (kg/m**3), parallel                                                                                                                                                                 !! computing
3584    REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:,:)    :: carbon_input_g           !! Quantity of carbon going into carbon pools from
3585                                                                              !! litter decomposition 
3586                                                                              !! @tex $(gC m^{-2} dt_sechiba^{-1})$ @endtex, parallel
3587                                                                              !! computing
3588    REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:,:)    :: nitrogen_input_g         !! Quantity of nitrogen going into nitrogen pools from 
3589                                                                              !! litter decomposition   
3590                                                                              !! @tex $(gC m^{-2} dtradia^{-1})$ @endtex, parallel 
3591    REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)      :: control_moist_g          !! Moisture control of heterotrophic respiration
3592                                                                              !! (0-1, unitless), parallel computing
3593    REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)      :: control_temp_g           !! Temperature control of heterotrophic respiration
3594                                                                              !! (0-1, unitless), parallel computing
3595    REAL(r_std),ALLOCATABLE,DIMENSION(:,:)        :: npp_equil_g              !! Equilibrium NPP written to forcesoil
3596                                                                              !! @tex $(gC m^{-2} year^{-1})$ @endtex, parallel
3597                                                                              !! computing
3598
3599!!$    REAL(r_std)                                   :: net_flux_prod_monthly_sum    !! AR5 output?? gC m2 month-1 (one variable for
3600!!$                                                                                   !! reduce_sum and one for bcast??), parallel
3601!!$                                                                                   !! computing
3602!!$    REAL(r_std)                                   :: net_flux_prod_monthly_tot    !! AR5 output?? gC m2 month-1 (one variable for
3603!!$                                                                                   !! reduce_sum and one for bcast??), parallel
3604!!$                                                                                   !! computing
3605!!$    REAL(r_std)                                   :: net_harvest_above_monthly_sum !! AR5 output?? gC m2 month-1 (one variable for
3606!!$                                                                                   !! reduce_sum and one for bcast??), parallel
3607!!$                                                                                   !! computing
3608!!$    REAL(r_std)                                   :: net_harvest_above_monthly_tot !! AR5 output?? gC m2 month-1 (one variable for
3609!!$                                                                                   !! reduce_sum and one for bcast??), parallel
3610!!$                                                                                   !! computing
3611!!$    REAL(r_std)                                   :: net_biosp_prod_monthly_sum    !! AR5 output?? gC m2 month-1 (one variable for
3612!!$                                                                                   !! reduce_sum and one for bcast??), parallel
3613!!$                                                                                   !! computing
3614!!$    REAL(r_std)                                   :: net_biosp_prod_monthly_tot    !! AR5 output?? gC m2 month-1 (one variable for
3615!!$                                                                                   !! reduce_sum and one for bcast??), parallel
3616                                                                                   !! computing
3617    REAL(r_std), DIMENSION(kjpindex,nvm,nbpools)  :: carbon_stock                  !! Array containing the carbon stock for each pool
3618                                                                                   !! used by ORCHIDEE
3619   
3620
3621!_ ================================================================================================================================
3622   
3623    !! 1. Write restart file for stomate
3624    IF (printlev>=3) WRITE (numout,*) 'Write restart file for STOMATE' 
3625   
3626    CALL writerestart &
3627         (kjpindex, index, &
3628         dt_days, date, &
3629         adapted, regenerate, &
3630         humrel_daily, gdd_init_date, litterhum_daily, &
3631         t2m_daily, t2m_min_daily, tsurf_daily, tsoil_daily, &
3632         soilhum_daily, precip_daily, &
3633         gpp_daily, npp_daily, turnover_daily, &
3634         humrel_month, humrel_week, humrel_growingseason, &
3635         t2m_longterm, tau_longterm, t2m_month, t2m_week, &
3636         tsoil_month, soilhum_month, fireindex, firelitter, &
3637         maxhumrel_lastyear, maxhumrel_thisyear, &
3638         minhumrel_lastyear, minhumrel_thisyear, &
3639         maxgppweek_lastyear, maxgppweek_thisyear, &
3640         gdd0_lastyear, gdd0_thisyear, &
3641         precip_lastyear, precip_thisyear, &
3642         gdd_m5_dormance, gdd_from_growthinit, gdd_midwinter, ncd_dormance, ngd_minus5, &
3643         PFTpresent, npp_longterm, lm_lastyearmax, lm_thisyearmax, &
3644         maxfpc_lastyear, maxfpc_thisyear, &
3645         turnover_longterm, gpp_week, resp_maint_part, &
3646         leaf_age, leaf_frac, &
3647         plant_status, when_growthinit, age, &
3648         resp_hetero_d, resp_maint_d, resp_growth_d, co2_fire, atm_to_bm, &
3649         veget_lastlight, everywhere, need_adjacent, &
3650         RIP_time, &
3651         time_hum_min, hum_min_dormance, &
3652         litter, dead_leaves, &
3653         som, lignin_struc, lignin_wood,turnover_time,&
3654         prod_s, prod_m, prod_l, &
3655         flux_s, flux_m, flux_l, flux_prod_s, flux_prod_m, &
3656         flux_prod_l, bm_to_litter, carb_mass_total, &
3657         Tseason, Tseason_length, Tseason_tmp, &
3658         Tmin_spring_time, onset_date, &
3659         global_years, ok_equilibrium, nbp_accu, nbp_flux, &
3660         nbp_accu_pool, nbp_pool, nbp_pool_start, &
3661         matrixV, vectorU, previous_stock, current_stock, &
3662         assim_param, CN_som_litter_longterm, &
3663         tau_CN_longterm, KF, k_latosa_adapt, rue_longterm, &
3664         cn_leaf_min_season, &
3665         nstress_season, soil_n_min, p_O2, bact, &
3666         circ_class_biomass, circ_class_n, store_sum_delta_ba, &
3667         forest_managed, forest_managed_lastyear, &
3668         species_change_map, fm_change_map, lpft_replant, lai_per_level, &
3669         laieff_fit, wstress_season, wstress_month, &
3670         age_stand, rotation_n, last_cut, mai, pai, &
3671         previous_wood_volume, mai_count, coppice_dens, &
3672         light_tran_to_level_season, harvest_5y_area)
3673   
3674    !! 2. Write file with variables that force general processes in stomate
3675    IF ( allow_forcing_write ) THEN
3676       IF ( TRIM(forcing_name) /= 'NONE' ) THEN 
3677          CALL forcing_write(forcing_id,1,iisf)
3678          ! Close forcing file
3679          IF (is_root_prc) ier = NF90_CLOSE (forcing_id)
3680          forcing_id=-1
3681       END IF
3682    END IF
3683   
3684    !! 3. Collect variables that force the soil processes in stomate
3685    IF (TRIM(Cforcing_name) /= 'NONE' ) THEN 
3686       
3687       !! Collet variables
3688       WRITE(numout,*) &
3689            &      'stomate: writing the forcing file for carbon spinup'
3690       DO iatt = 1, nparan*nbyear
3691          IF ( nforce(iatt) > 0 ) THEN
3692             carbon_input(:,:,:,iatt) = &
3693                  & carbon_input(:,:,:,iatt)/REAL(nforce(iatt),r_std)
3694             nitrogen_input(:,:,:,iatt) = &
3695                  & nitrogen_input(:,:,:,iatt)/REAL(nforce(iatt),r_std)
3696             control_moist(:,:,iatt) = &
3697                  & control_moist(:,:,iatt)/REAL(nforce(iatt),r_std)
3698             control_temp(:,:,iatt) = &
3699                  & control_temp(:,:,iatt)/REAL(nforce(iatt),r_std)
3700             npp_equil(:,iatt) = &
3701                  & npp_equil(:,iatt)/REAL(nforce(iatt),r_std)
3702             drainage(:,:,iatt) = & 
3703                  &  drainage(:,:,iatt)/REAL(nforce(iatt),r_std) 
3704          ELSE
3705             WRITE(numout,*) &
3706                  &         'We have no soil carbon forcing data for this time step:', &
3707                  &         iatt
3708             WRITE(numout,*) ' -> we set them to zero'
3709             carbon_input(:,:,:,iatt) = zero
3710             nitrogen_input(:,:,:,iatt) = zero
3711             control_moist(:,:,iatt) = zero
3712             control_temp(:,:,iatt) = zero
3713             npp_equil(:,iatt) = zero
3714          ENDIF
3715       ENDDO
3716       
3717       ! Allocate memory for parallel computing
3718       IF (is_root_prc) THEN
3719          ALLOCATE(carbon_input_g(nbp_glo,ncarb,nvm,nparan*nbyear))
3720          ALLOCATE(nitrogen_input_g(nbp_glo,ncarb,nvm,nparan*nbyear))
3721          ALLOCATE(control_moist_g(nbp_glo,nlevs,nparan*nbyear))
3722          ALLOCATE(control_temp_g(nbp_glo,nlevs,nparan*nbyear))
3723          ALLOCATE(npp_equil_g(nbp_glo,nparan*nbyear))
3724       ENDIF
3725       
3726       ! Gather distributed variables
3727
3728       CALL gather(clay,clay_g)
3729       CALL gather(silt,silt_g) 
3730       CALL gather(bulk,bulk_g) 
3731       CALL gather(carbon_input,carbon_input_g)
3732       CALL gather(nitrogen_input,nitrogen_input_g)
3733       CALL gather(control_moist,control_moist_g)
3734       CALL gather(control_temp,control_temp_g)
3735       CALL gather(npp_equil,npp_equil_g)
3736       
3737       !! Create netcdf
3738       ! Create, define and populate a netcdf file containing the forcing data.
3739       ! For the root processor only (parallel computing). NF90_ are functions
3740       ! from and external library. 
3741       IF (is_root_prc) THEN
3742          WRITE (numout,*) 'Create Cforcing file : ',TRIM(Cforcing_name)
3743          ! Create new netCDF dataset
3744          ier = NF90_CREATE (TRIM(Cforcing_name),NF90_64BIT_OFFSET ,Cforcing_id)
3745          IF (ier /= NF90_NOERR) THEN
3746             WRITE (numout,*) 'Error in creating Cforcing file : ',TRIM(Cforcing_name)
3747             CALL ipslerr_p (3,'stomate_finalize', &
3748                  &        'PROBLEM creating Cforcing file', &
3749                  &        NF90_STRERROR(ier),'')
3750          END IF
3751         
3752          ! Add variable attribute
3753          ! Note ::nbp_glo is the number of global continental points
3754          ier = NF90_PUT_ATT (Cforcing_id,NF90_GLOBAL, &
3755               &                        'kjpindex',REAL(nbp_glo,r_std))
3756          ier = NF90_PUT_ATT (Cforcing_id,NF90_GLOBAL, &
3757               &                        'nparan',REAL(nparan,r_std))
3758          ier = NF90_PUT_ATT (Cforcing_id,NF90_GLOBAL, &
3759               &                        'nbyear',REAL(nbyear,r_std))
3760         
3761          ! Add new dimension
3762          ier = NF90_DEF_DIM (Cforcing_id,'points',nbp_glo,d_id(1))
3763          ier = NF90_DEF_DIM (Cforcing_id,'carbtype',ncarb,d_id(2))
3764          ier = NF90_DEF_DIM (Cforcing_id,'vegtype',nvm,d_id(3))
3765          ier = NF90_DEF_DIM (Cforcing_id,'level',nlevs,d_id(4))
3766          ier = NF90_DEF_DIM (Cforcing_id,'time_step',NF90_UNLIMITED,d_id(5))
3767         
3768          ! Add new variable
3769          ier = NF90_DEF_VAR (Cforcing_id,'points',    r_typ,d_id(1),vid)
3770          ier = NF90_DEF_VAR (Cforcing_id,'carbtype',  r_typ,d_id(2),vid)
3771          ier = NF90_DEF_VAR (Cforcing_id,'vegtype',   r_typ,d_id(3),vid)
3772          ier = NF90_DEF_VAR (Cforcing_id,'level',     r_typ,d_id(4),vid)
3773          ier = NF90_DEF_VAR (Cforcing_id,'time_step', r_typ,d_id(5),vid)
3774          ier = NF90_DEF_VAR (Cforcing_id,'index',     r_typ,d_id(1),vid)
3775          ier = NF90_DEF_VAR (Cforcing_id,'clay',      r_typ,d_id(1),vid)
3776          ier = NF90_DEF_VAR (Cforcing_id,'silt',      r_typ,d_id(1),vid) 
3777          ier = NF90_DEF_VAR (Cforcing_id,'bulk',      r_typ,d_id(1),vid) 
3778          ier = NF90_DEF_VAR (Cforcing_id,'carbon_input',r_typ, &
3779               &                        (/ d_id(1),d_id(2),d_id(3),d_id(5) /),vid)
3780          ier = NF90_DEF_VAR (Cforcing_id,'nitrogen_input',r_typ, &
3781               &                        (/ d_id(1),d_id(2),d_id(3),d_id(5) /),vid)
3782          ier = NF90_DEF_VAR (Cforcing_id,'control_moist',r_typ, &
3783               &                        (/ d_id(1),d_id(4),d_id(5) /),vid)
3784          ier = NF90_DEF_VAR (Cforcing_id,'control_temp',r_typ, &
3785               &                        (/ d_id(1),d_id(4),d_id(5) /),vid)
3786          ier = NF90_DEF_VAR (Cforcing_id,'npp_equil',r_typ, &
3787               &                        (/ d_id(1),d_id(5) /),vid)
3788
3789          ier = NF90_DEF_VAR (Cforcing_id,'drainage',r_typ, & 
3790               &                        (/ d_id(1),d_id(6),d_id(6) /),vid) 
3791          ier = NF90_ENDDEF (Cforcing_id)
3792         
3793          ! Given the name of a varaible, nf90_inq_varid finds the variable
3794          ! ID (::vid). Put data value(s) into variable ::vid
3795          ier = NF90_INQ_VARID (Cforcing_id,'points',vid)
3796          ier = NF90_PUT_VAR (Cforcing_id,vid, &
3797               &                          (/(REAL(i,r_std),i=1,nbp_glo)/))
3798          ier = NF90_INQ_VARID (Cforcing_id,'carbtype',vid)
3799          ier = NF90_PUT_VAR (Cforcing_id,vid, &
3800               &                        (/(REAL(i,r_std),i=1,ncarb)/))
3801          ier = NF90_INQ_VARID (Cforcing_id,'vegtype',vid)
3802          ier = NF90_PUT_VAR (Cforcing_id,vid, &
3803               &                            (/(REAL(i,r_std),i=1,nvm)/))
3804          ier = NF90_INQ_VARID (Cforcing_id,'level',vid)
3805          ier = NF90_PUT_VAR (Cforcing_id,vid, &
3806               &                          (/(REAL(i,r_std),i=1,nlevs)/))
3807          ier = NF90_INQ_VARID (Cforcing_id,'time_step',vid)
3808          ier = NF90_PUT_VAR (Cforcing_id,vid, &
3809               &                          (/(REAL(i,r_std),i=1,nparan*nbyear)/))
3810          ier = NF90_INQ_VARID (Cforcing_id,'index',vid)
3811          ier = NF90_PUT_VAR (Cforcing_id,vid, REAL(index_g,r_std) )
3812          ier = NF90_INQ_VARID (Cforcing_id,'clay',vid)
3813          ier = NF90_PUT_VAR (Cforcing_id,vid, clay_g )
3814          ier = NF90_INQ_VARID (Cforcing_id,'silt',vid) 
3815          ier = NF90_PUT_VAR (Cforcing_id,vid, silt_g ) 
3816          ier = NF90_INQ_VARID (Cforcing_id,'bulk',vid) 
3817          ier = NF90_PUT_VAR (Cforcing_id,vid, bulk_g ) 
3818          ier = NF90_INQ_VARID (Cforcing_id,'carbon_input',vid)
3819          ier = NF90_PUT_VAR (Cforcing_id,vid, carbon_input_g )
3820          ier = NF90_INQ_VARID (Cforcing_id,'nitrogen_input',vid)
3821          ier = NF90_PUT_VAR (Cforcing_id,vid, nitrogen_input_g )
3822          ier = NF90_INQ_VARID (Cforcing_id,'control_moist',vid)
3823          ier = NF90_PUT_VAR (Cforcing_id,vid, control_moist_g )
3824          ier = NF90_INQ_VARID (Cforcing_id,'control_temp',vid)
3825          ier = NF90_PUT_VAR (Cforcing_id,vid, control_temp_g )
3826          ier = NF90_INQ_VARID (Cforcing_id,'npp_equil',vid)
3827          ier = NF90_PUT_VAR (Cforcing_id,vid, npp_equil_g )
3828         
3829          ! Close netCDF
3830          ier = NF90_CLOSE (Cforcing_id)
3831          IF (ier /= NF90_NOERR) THEN
3832             CALL ipslerr_p (3,'stomate_finalize', &
3833                  &        'PROBLEM in closing Cforcing file', &
3834                  &        NF90_STRERROR(ier),'')
3835          END IF
3836         
3837          Cforcing_id = -1
3838       ENDIF
3839
3840       ! Clear memory
3841       IF (is_root_prc) THEN
3842          DEALLOCATE(carbon_input_g)
3843          DEALLOCATE(nitrogen_input_g)
3844          DEALLOCATE(control_moist_g)
3845          DEALLOCATE(control_temp_g)
3846          DEALLOCATE(npp_equil_g)
3847       ENDIF
3848       
3849    ENDIF
3850 
3851  END SUBROUTINE stomate_finalize
3852
3853
3854!! ================================================================================================================================
3855!! SUBROUTINE   : stomate_init
3856!!
3857!>\BRIEF        The routine is called only at the first simulation. At that
3858!! time settings and flags are read and checked for internal consistency and
3859!! memory is allocated for the variables in stomate.
3860!!
3861!! DESCRIPTION  : The routine reads the
3862!! following flags from the run definition file:
3863!! -ipd (index of grid point for online diagnostics)\n
3864!! -ok_herbivores (flag to activate herbivores)\n
3865!! -treat_expansion (flag to activate PFT expansion across a pixel\n
3866!! -harvest_agri (flag to harvest aboveground biomass from agricultural PFTs)\n
3867!! \n
3868!! Check for inconsistent setting between the following flags:
3869!! -ok_stomate\n
3870!! -ok_dgvm\n
3871!! \n
3872!! Memory is allocated for all the variables of stomate and new indexing tables
3873!! are build. New indexing tables are needed because a single pixel can conatin
3874!! several PFTs. The new indexing tables have separate indices for the different
3875!! PFTs. Similar index tables are build for land use cover change.\n
3876!! \n
3877!! Several global variables and land cover change variables are initialized to
3878!! zero.\n
3879!!
3880!! RECENT CHANGE(S) : None
3881!!
3882!! MAIN OUTPUT VARIABLE(S): Strictly speaking the subroutine has no output
3883!! variables. However, the routine allocates memory and builds new indexing
3884!! variables for later use.\n
3885!!
3886!! REFERENCE(S) : None
3887!!
3888!! FLOWCHART    : None
3889!! \n
3890!_ ================================================================================================================================
3891
3892  SUBROUTINE stomate_init &
3893       &  (kjpij, kjpindex, index, lalo, &
3894       &   rest_id_stom, hist_id_stom, hist_id_stom_IPCC)
3895
3896  !! 0. Variable and parameter declaration
3897
3898    !! 0.1 Input variables
3899
3900    INTEGER(i_std),INTENT(in)                    :: kjpij             !! Total size of the un-compressed grid, including
3901                                                                      !! oceans (unitless)
3902    INTEGER(i_std),INTENT(in)                    :: kjpindex          !! Domain size - number of terrestrial pixels
3903                                                                      !! (unitless)
3904    INTEGER(i_std),INTENT(in)                    :: rest_id_stom      !! STOMATE's _Restart_ file identifier
3905    INTEGER(i_std),INTENT(in)                    :: hist_id_stom      !! STOMATE's _history_ file identifier
3906    INTEGER(i_std),INTENT(in)                    :: hist_id_stom_IPCC !! STOMATE's IPCC _history_ file identifier
3907    INTEGER(i_std),DIMENSION(kjpindex),INTENT(in):: index             !! Indices of the terrestrial pixels on the global
3908                                                                      !! map
3909    REAL(r_std),DIMENSION(kjpindex,2),INTENT(in) :: lalo              !! Geogr. coordinates (latitude,longitude) (degrees)
3910   
3911    !! 0.2 Output variables
3912
3913    !! 0.3 Modified variables
3914
3915    !! 0.4 Local variables
3916
3917    LOGICAL                                      :: l_error           !! Check errors in netcdf call
3918    INTEGER(i_std)                               :: ier               !! Check errors in netcdf call
3919    INTEGER(i_std)                               :: ji,j,ipd,l        !! Indices
3920    INTEGER(i_std)                               :: idia              !! indices
3921!_ ================================================================================================================================
3922   
3923  !! 1. Online diagnostics
3924
3925    IF ( kjpindex > 0 ) THEN
3926       !Config  Key  = STOMATE_DIAGPT
3927       !Config  Desc = Index of grid point for online diagnostics
3928       !Config If    = OK_STOMATE
3929       !Config  Def  = 1
3930       !Config  Help = This is the index of the grid point which
3931       !               will be used for online diagnostics.
3932       !Config Units = [-]
3933       ! By default ::ipd is set to 1
3934       ipd = 1
3935       ! Get ::ipd from run definition file
3936       CALL getin_p('STOMATE_DIAGPT',ipd)
3937       ipd = MIN( ipd, kjpindex )
3938       WRITE(numout,*) 'Stomate: '
3939       WRITE(numout,*) '  Index of grid point for online diagnostics: ',ipd
3940       WRITE(numout,*) '  Lon, lat:',lalo(ipd,2),lalo(ipd,1)
3941       WRITE(numout,*) '  Index of this point on GCM grid: ',index(ipd)
3942       !
3943    ENDIF
3944   
3945  !! 2. Check consistency of flags
3946
3947    IF ( ( .NOT. ok_stomate ) .AND. ok_dgvm ) THEN
3948       WRITE(numout,*) 'Cannot do dynamical vegetation without STOMATE.'
3949       WRITE(numout,*) 'Inconsistency between ::ok_stomate and ::ok_dgvm'
3950       WRITE(numout,*) 'Stop: fatal error'
3951       STOP
3952    ENDIF
3953
3954  !! 3. Communicate settings
3955
3956    WRITE(numout,*) 'stomate first call - overview of the activated flags:'
3957    WRITE(numout,*) '  STOMATE: ', ok_stomate
3958    WRITE(numout,*) '  LPJ: ', ok_dgvm
3959   
3960  !! 4. Allocate memory for STOMATE's variables
3961
3962    l_error = .FALSE.
3963
3964    ALLOCATE(veget_cov_max(kjpindex,nvm),stat=ier)
3965    l_error = l_error .OR. (ier /= 0)
3966    IF (l_error) THEN
3967       WRITE(numout,*) 'Memory allocation error for veget_cov_max. We stop. We need kjpindex*nvm words',kjpindex,nvm
3968       STOP 'stomate_init'
3969    ENDIF
3970
3971    ALLOCATE(adapted(kjpindex,nvm),stat=ier)
3972    l_error = l_error .OR. (ier /= 0)
3973    IF (l_error) THEN
3974       WRITE(numout,*) 'Memory allocation error for adapted. We stop. We need kjpindex*nvm words',kjpindex,nvm
3975       STOP 'stomate_init'
3976    ENDIF
3977
3978    ALLOCATE(regenerate(kjpindex,nvm),stat=ier)
3979    l_error = l_error .OR. (ier /= 0)
3980    IF (l_error) THEN
3981       WRITE(numout,*) 'Memory allocation error for regenerate. We stop. We need kjpindex*nvm words',kjpindex,nvm
3982       STOP 'stomate_init'
3983    ENDIF
3984
3985    ALLOCATE(humrel_daily(kjpindex,nvm),stat=ier)
3986    l_error = l_error .OR. (ier /= 0)
3987    IF (l_error) THEN
3988       WRITE(numout,*) 'Memory allocation error for humrel_daily. We stop. We need kjpindex*nvm words',kjpindex,nvm
3989       STOP 'stomate_init'
3990    ENDIF
3991
3992    ALLOCATE(vir_humrel_daily(kjpindex,nvm),stat=ier)
3993    l_error = l_error .OR. (ier /= 0)
3994    IF (l_error) THEN
3995       WRITE(numout,*) 'Memory allocation error for vir_humrel_daily. We stop. We need kjpindex*nvm words',kjpindex,nvm
3996       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
3997    ENDIF
3998    vir_humrel_daily(:,:)=zero
3999
4000    ALLOCATE(stressed_daily(kjpindex,nvm),stat=ier)
4001    l_error = l_error .OR. (ier /= 0)
4002    IF (l_error) THEN
4003       WRITE(numout,*) 'Memory allocation error for stressed_daily. We stop. We need kjpindex*nvm words',kjpindex,nvm
4004       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4005    ENDIF
4006    stressed_daily = zero
4007
4008    ALLOCATE(unstressed_daily(kjpindex,nvm),stat=ier)
4009    l_error = l_error .OR. (ier /= 0)
4010    IF (l_error) THEN
4011       WRITE(numout,*) 'Memory allocation error for unstressed_daily. We stop. We need kjpindex*nvm words',kjpindex,nvm
4012       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4013    ENDIF
4014    unstressed_daily(:,:) = zero
4015
4016    ALLOCATE(daylight(kjpindex,nvm),stat=ier)
4017    l_error = l_error .OR. (ier /= 0)
4018    IF (l_error) THEN
4019       WRITE(numout,*) 'Memory allocation error for daylight. We stop. We need kjpindex*nvm words',kjpindex,nvm
4020       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4021    ENDIF
4022    daylight(:,:) = zero
4023
4024    ALLOCATE(light_tran_to_level_season(kjpindex,nvm,nlevels_tot),stat=ier)
4025    l_error = l_error .OR. (ier /= 0)
4026    IF (l_error) THEN
4027       WRITE(numout,*) 'Memory allocation error for light_tran_to_level_season. We stop. We need kjpindex*nvm*nlevels_tot words', &
4028            kjpindex,nvm,nlevels_tot
4029       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4030    ENDIF
4031    light_tran_to_level_season = zero
4032
4033    ALLOCATE(daylight_count(kjpindex,nvm),stat=ier)
4034    l_error = l_error .OR. (ier /= 0)
4035    IF (l_error) THEN
4036       WRITE(numout,*) 'Memory allocation error for daylight_count. We stop. We need kjpindex*nvm words',kjpindex,nvm
4037       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4038    ENDIF
4039    daylight_count(:,:) = zero
4040
4041    ALLOCATE(transpir_supply_daily(kjpindex,nvm),stat=ier)
4042    l_error = l_error .OR. (ier /= 0)
4043    IF (l_error) THEN
4044       WRITE(numout,*) 'Memory allocation error for transpir_supply_daily. We stop. We need kjpindex*nvm words',kjpindex,nvm
4045       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4046    ENDIF
4047    transpir_supply_daily=zero
4048
4049    ALLOCATE(vir_transpir_supply_daily(kjpindex,nvm),stat=ier)
4050    l_error = l_error .OR. (ier /= 0)
4051    IF (l_error) THEN
4052       WRITE(numout,*) 'Memory allocation error for vir_transpir_supply_daily. We stop. We need kjpindex*nvm words',kjpindex,nvm
4053       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4054    ENDIF
4055    vir_transpir_supply_daily=zero
4056
4057    ALLOCATE(transpir_daily(kjpindex,nvm),stat=ier)
4058    l_error = l_error .OR. (ier /= 0)
4059    IF (l_error) THEN
4060       WRITE(numout,*) 'Memory allocation error for transpir_daily. We stop. We need kjpindex*nvm words',kjpindex,nvm
4061       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4062    ENDIF
4063    transpir_daily=zero
4064
4065
4066    ALLOCATE(litterhum_daily(kjpindex),stat=ier)
4067    l_error = l_error .OR. (ier /= 0)
4068    IF (l_error) THEN
4069       WRITE(numout,*) 'Memory allocation error for litterhum_daily. We stop. We need kjpindex words',kjpindex
4070       STOP 'stomate_init'
4071    ENDIF
4072
4073    ALLOCATE(t2m_daily(kjpindex),stat=ier)
4074    l_error = l_error .OR. (ier /= 0)
4075    IF (l_error) THEN
4076       WRITE(numout,*) 'Memory allocation error for t2m_daily. We stop. We need kjpindex words',kjpindex
4077       STOP 'stomate_init'
4078    ENDIF
4079
4080    ALLOCATE(t2m_min_daily(kjpindex),stat=ier)
4081    l_error = l_error .OR. (ier /= 0)
4082    IF (l_error) THEN
4083       WRITE(numout,*) 'Memory allocation error for t2m_min_daily. We stop. We need kjpindex words',kjpindex
4084       STOP 'stomate_init'
4085    ENDIF
4086
4087    ALLOCATE(wind_speed_daily(kjpindex),stat=ier)
4088    l_error = l_error .OR. (ier /= 0)
4089    IF (l_error) THEN
4090       WRITE(numout,*) 'Memory allocation error for wind_speed_daily. We stop. We need kjpindex words',kjpindex
4091       STOP 'stomate_init'
4092    ENDIF
4093
4094    ALLOCATE(wind_max_daily(kjpindex),stat=ier)
4095    l_error = l_error .OR. (ier /= 0)
4096    IF (l_error) THEN
4097       WRITE(numout,*) 'Memory allocation error for wind_max_daily. We stop. We need kjpindex words',kjpindex
4098       STOP 'stomate_init'
4099    ENDIF
4100
4101    ALLOCATE(soil_temp_daily(kjpindex),stat=ier)
4102    l_error = l_error .OR. (ier /= 0)
4103    IF (l_error) THEN
4104       WRITE(numout,*) 'Memory allocation error for soil_temp_daily. We stop. We need kjpindex words',kjpindex
4105       STOP 'stomate_init'
4106    ENDIF
4107
4108    ALLOCATE(soil_max_daily(kjpindex),stat=ier)
4109    l_error = l_error .OR. (ier /= 0)
4110    IF (l_error) THEN
4111       WRITE(numout,*) 'Memory allocation error for soil_max_daily. We stop. We need kjpindex words',kjpindex
4112       STOP 'stomate_init'
4113    ENDIF
4114
4115    ALLOCATE(tsurf_daily(kjpindex),stat=ier)
4116    l_error = l_error .OR. (ier /= 0)
4117    IF (l_error) THEN
4118       WRITE(numout,*) 'Memory allocation error for tsurf_daily. We stop. We need kjpindex words',kjpindex
4119       STOP 'stomate_init'
4120    ENDIF
4121
4122    ALLOCATE(tsoil_daily(kjpindex,nbdl),stat=ier)
4123    l_error = l_error .OR. (ier /= 0)
4124    IF (l_error) THEN
4125       WRITE(numout,*) 'Memory allocation error for tsoil_daily. We stop. We need kjpindex*nbdl words',kjpindex,nbdl
4126       STOP 'stomate_init'
4127    ENDIF
4128
4129    ALLOCATE(soilhum_daily(kjpindex,nbdl),stat=ier)
4130    l_error = l_error .OR. (ier /= 0)
4131    IF (l_error) THEN
4132       WRITE(numout,*) 'Memory allocation error for soilhum_daily. We stop. We need kjpindex*nbdl words',kjpindex,nbdl
4133       STOP 'stomate_init'
4134    ENDIF
4135
4136    ALLOCATE(precip_daily(kjpindex),stat=ier)
4137    l_error = l_error .OR. (ier /= 0)
4138    IF (l_error) THEN
4139       WRITE(numout,*) 'Memory allocation error for precip_daily. We stop. We need kjpindex words',kjpindex,nvm
4140       STOP 'stomate_init'
4141    ENDIF
4142
4143    ALLOCATE(gpp_daily(kjpindex,nvm),stat=ier)
4144    l_error = l_error .OR. (ier /= 0)
4145    IF (l_error) THEN
4146       WRITE(numout,*) 'Memory allocation error for gpp_daily. We stop. We need kjpindex*nvm words',kjpindex,nvm
4147       STOP 'stomate_init'
4148    ENDIF
4149
4150    ALLOCATE(npp_daily(kjpindex,nvm),stat=ier)
4151    l_error = l_error .OR. (ier /= 0)
4152    IF (l_error) THEN
4153       WRITE(numout,*) 'Memory allocation error for npp_daily. We stop. We need kjpindex*nvm words',kjpindex,nvm
4154       STOP 'stomate_init'
4155    ENDIF
4156
4157    ALLOCATE(turnover_daily(kjpindex,nvm,nparts,nelements),stat=ier)
4158    l_error = l_error .OR. (ier /= 0)
4159    IF (l_error) THEN
4160       WRITE(numout,*) 'Memory allocation error for turnover_daily. We stop. We need kjpindex*nvm*nparts*nelements words', &
4161       &   kjpindex,nvm,nparts,nelements
4162       STOP 'stomate_init'
4163    ENDIF
4164
4165    ALLOCATE(turnover_littercalc(kjpindex,nvm,nparts,nelements),stat=ier)
4166    l_error = l_error .OR. (ier /= 0)
4167    IF (l_error) THEN
4168       WRITE(numout,*) 'Memory allocation error for turnover_littercalc. We stop. We need kjpindex*nvm*nparts*nelements words', & 
4169        &  kjpindex,nvm,nparts,nelements
4170       STOP 'stomate_init'
4171    ENDIF
4172
4173    ALLOCATE(humrel_month(kjpindex,nvm),stat=ier)
4174    l_error = l_error .OR. (ier /= 0)
4175    IF (l_error) THEN
4176       WRITE(numout,*) 'Memory allocation error for humrel_month. We stop. We need kjpindex*nvm words',kjpindex,nvm
4177       STOP 'stomate_init'
4178    ENDIF
4179
4180    ALLOCATE(humrel_week(kjpindex,nvm),stat=ier)
4181    l_error = l_error .OR. (ier /= 0)
4182    IF (l_error) THEN
4183       WRITE(numout,*) 'Memory allocation error for humrel_week. We stop. We need kjpindex*nvm words',kjpindex,nvm
4184       STOP 'stomate_init'
4185    ENDIF
4186
4187    ALLOCATE(humrel_growingseason(kjpindex,nvm),stat=ier)
4188    l_error = l_error .OR. (ier /= 0)
4189    IF (l_error) THEN
4190       WRITE(numout,*) 'Memory allocation error for humrel_growingseason. We stop. We need kjpindex*nvm words',kjpindex,nvm
4191       STOP 'stomate_init'
4192    ENDIF
4193
4194    ALLOCATE(vir_humrel_growingseason(kjpindex,nvm),stat=ier)
4195    l_error = l_error .OR. (ier /= 0)
4196
4197    ALLOCATE(t2m_longterm(kjpindex),stat=ier)
4198    l_error = l_error .OR. (ier /= 0)
4199    IF (l_error) THEN
4200       WRITE(numout,*) 'Memory allocation error for t2m_longterm. We stop. We need kjpindex*nvm words',kjpindex,nvm
4201       STOP 'stomate_init'
4202    ENDIF
4203
4204    ALLOCATE(t2m_month(kjpindex),stat=ier)
4205    l_error = l_error .OR. (ier /= 0)
4206    IF (l_error) THEN
4207       WRITE(numout,*) 'Memory allocation error for t2m_month. We stop. We need kjpindex words',kjpindex
4208       STOP 'stomate_init'
4209    ENDIF
4210
4211    ALLOCATE(Tseason(kjpindex),stat=ier)
4212    l_error = l_error .OR. (ier /= 0)
4213    IF (l_error) THEN
4214       WRITE(numout,*) 'Memory allocation error for Tseason. We stop. We need kjpindex words',kjpindex
4215       STOP 'stomate_init'
4216    ENDIF
4217
4218    ALLOCATE(Tseason_length(kjpindex),stat=ier)
4219    l_error = l_error .OR. (ier /= 0)
4220    IF (l_error) THEN
4221       WRITE(numout,*) 'Memory allocation error for Tseason_length. We stop. We need kjpindex words',kjpindex
4222       STOP 'stomate_init'
4223    ENDIF
4224
4225    ALLOCATE(Tseason_tmp(kjpindex),stat=ier)
4226    l_error = l_error .OR. (ier /= 0)
4227    IF (l_error) THEN
4228       WRITE(numout,*) 'Memory allocation error for Tseason_tmp. We stop. We need kjpindex words',kjpindex
4229       STOP 'stomate_init'
4230    ENDIF
4231
4232    ALLOCATE(Tmin_spring_time(kjpindex,nvm),stat=ier)
4233    l_error = l_error .OR. (ier /= 0)
4234    IF (l_error) THEN
4235       WRITE(numout,*) 'Memory allocation error for Tmin_spring_time. We stop. We need kjpindex*nvm words',kjpindex,nvm
4236       STOP 'stomate_init'
4237    ENDIF
4238
4239    ALLOCATE(onset_date(kjpindex,nvm,2),stat=ier)
4240    l_error = l_error .OR. (ier /= 0)
4241    IF (l_error) THEN
4242       WRITE(numout,*) 'Memory allocation error for onset_date. We stop. We need kjpindex*nvm*nparts words',kjpindex,nvm,2
4243       STOP 'stomate_init'
4244    ENDIF
4245
4246    ALLOCATE(t2m_week(kjpindex),stat=ier)
4247    l_error = l_error .OR. (ier /= 0)
4248    IF (l_error) THEN
4249       WRITE(numout,*) 'Memory allocation error for t2m_week. We stop. We need kjpindex words',kjpindex
4250       STOP 'stomate_init'
4251    ENDIF
4252
4253    ALLOCATE(tsoil_month(kjpindex,nbdl),stat=ier)
4254    l_error = l_error .OR. (ier /= 0)
4255    IF (l_error) THEN
4256       WRITE(numout,*) 'Memory allocation error for tsoil_month. We stop. We need kjpindex*nbdl words',kjpindex,nbdl
4257       STOP 'stomate_init'
4258    ENDIF
4259
4260    ALLOCATE(soilhum_month(kjpindex,nbdl),stat=ier)
4261    l_error = l_error .OR. (ier /= 0)
4262    IF (l_error) THEN
4263       WRITE(numout,*) 'Memory allocation error for soilhum_month. We stop. We need kjpindex*nbdl words',kjpindex,nbdl
4264       STOP 'stomate_init'
4265    ENDIF
4266
4267    ALLOCATE(fireindex(kjpindex,nvm),stat=ier) 
4268    l_error = l_error .OR. (ier /= 0)
4269    IF (l_error) THEN
4270       WRITE(numout,*) 'Memory allocation error for fireindex. We stop. We need kjpindex*nvm words',kjpindex,nvm
4271       STOP 'stomate_init'
4272    ENDIF
4273
4274    ALLOCATE(firelitter(kjpindex,nvm),stat=ier)
4275    l_error = l_error .OR. (ier /= 0)
4276    IF (l_error) THEN
4277       WRITE(numout,*) 'Memory allocation error for firelitter. We stop. We need kjpindex*nvm words',kjpindex,nvm
4278       STOP 'stomate_init'
4279    ENDIF
4280
4281    ALLOCATE(maxhumrel_lastyear(kjpindex,nvm),stat=ier)
4282    l_error = l_error .OR. (ier /= 0)
4283    IF (l_error) THEN
4284       WRITE(numout,*) 'Memory allocation error for maxhumrel_lastyear. We stop. We need kjpindex*nvm words',kjpindex,nvm
4285       STOP 'stomate_init'
4286    ENDIF
4287
4288    ALLOCATE(maxhumrel_thisyear(kjpindex,nvm),stat=ier)
4289    l_error = l_error .OR. (ier /= 0)
4290    IF (l_error) THEN
4291       WRITE(numout,*) 'Memory allocation error for maxhumrel_thisyear. We stop. We need kjpindex*nvm words',kjpindex,nvm
4292       STOP 'stomate_init'
4293    ENDIF
4294
4295    ALLOCATE(minhumrel_lastyear(kjpindex,nvm),stat=ier)
4296    l_error = l_error .OR. (ier /= 0)
4297    IF (l_error) THEN
4298       WRITE(numout,*) 'Memory allocation error for minhumrel_lastyear. We stop. We need kjpindex*nvm words',kjpindex,nvm
4299       STOP 'stomate_init'
4300    ENDIF
4301
4302    ALLOCATE(minhumrel_thisyear(kjpindex,nvm),stat=ier)
4303    l_error = l_error .OR. (ier /= 0)
4304    IF (l_error) THEN
4305       WRITE(numout,*) 'Memory allocation error for minhumrel_thisyear. We stop. We need kjpindex*nvm words',kjpindex,nvm
4306       STOP 'stomate_init'
4307    ENDIF
4308
4309    ALLOCATE(maxgppweek_lastyear(kjpindex,nvm),stat=ier)
4310    l_error = l_error .OR. (ier /= 0)
4311    IF (l_error) THEN
4312       WRITE(numout,*) 'Memory allocation error for maxgppweek_lastyear. We stop. We need kjpindex*nvm words',kjpindex,nvm
4313       STOP 'stomate_init'
4314    ENDIF
4315
4316    ALLOCATE(maxgppweek_thisyear(kjpindex,nvm),stat=ier)
4317    l_error = l_error .OR. (ier /= 0)
4318    IF (l_error) THEN
4319       WRITE(numout,*) 'Memory allocation error for maxgppweek_thisyear. We stop. We need kjpindex*nvm words',kjpindex,nvm
4320       STOP 'stomate_init'
4321    ENDIF
4322
4323    ALLOCATE(gdd0_lastyear(kjpindex),stat=ier)
4324    l_error = l_error .OR. (ier /= 0)
4325    IF (l_error) THEN
4326       WRITE(numout,*) 'Memory allocation error for gdd0_lastyear. We stop. We need kjpindex words',kjpindex
4327       STOP 'stomate_init'
4328    ENDIF
4329
4330    ALLOCATE(gdd0_thisyear(kjpindex),stat=ier)
4331    l_error = l_error .OR. (ier /= 0)
4332    IF (l_error) THEN
4333       WRITE(numout,*) 'Memory allocation error for gdd0_thisyear. We stop. We need kjpindex words',kjpindex
4334       STOP 'stomate_init'
4335    ENDIF
4336
4337    ALLOCATE(gdd_init_date(kjpindex,2),stat=ier)
4338    l_error = l_error .OR. (ier /= 0)
4339    IF (l_error) THEN
4340       WRITE(numout,*) 'Memory allocation error for gdd_init_date. We stop. We need kjpindex*2 words',kjpindex,2
4341       STOP 'stomate_init'
4342    ENDIF
4343
4344    ALLOCATE(gdd_from_growthinit(kjpindex,nvm),stat=ier)
4345    l_error = l_error .OR. (ier /= 0)
4346    IF (l_error) THEN
4347       WRITE(numout,*) 'Memory allocation error for gdd_from_growthinit. We stop. We need kjpindex*nvm words',kjpindex,nvm
4348       STOP 'stomate_init'
4349    ENDIF
4350
4351    ALLOCATE(precip_lastyear(kjpindex),stat=ier)
4352    l_error = l_error .OR. (ier /= 0)
4353    IF (l_error) THEN
4354       WRITE(numout,*) 'Memory allocation error for precip_lastyear. We stop. We need kjpindex*nvm words',kjpindex
4355       STOP 'stomate_init'
4356    ENDIF
4357
4358    ALLOCATE(precip_thisyear(kjpindex),stat=ier)
4359    l_error = l_error .OR. (ier /= 0)
4360    IF (l_error) THEN
4361       WRITE(numout,*) 'Memory allocation error for precip_thisyear. We stop. We need kjpindex words',kjpindex
4362       STOP 'stomate_init'
4363    ENDIF
4364
4365    ALLOCATE(gdd_m5_dormance(kjpindex,nvm),stat=ier)
4366    l_error = l_error .OR. (ier /= 0)
4367    IF (l_error) THEN
4368       WRITE(numout,*) 'Memory allocation error for gdd_m5_dormance. We stop. We need kjpindex*nvm words',kjpindex,nvm
4369       STOP 'stomate_init'
4370    ENDIF
4371
4372    ALLOCATE(gdd_midwinter(kjpindex,nvm),stat=ier)
4373    l_error = l_error .OR. (ier /= 0)
4374    IF (l_error) THEN
4375       WRITE(numout,*) 'Memory allocation error for gdd_midwinter. We stop. We need kjpindex*nvm words',kjpindex,nvm
4376       STOP 'stomate_init'
4377    ENDIF
4378
4379    ALLOCATE(ncd_dormance(kjpindex,nvm),stat=ier)
4380    l_error = l_error .OR. (ier /= 0)
4381    IF (l_error) THEN
4382       WRITE(numout,*) 'Memory allocation error for ncd_dormance. We stop. We need kjpindex*nvm words',kjpindex,nvm
4383       STOP 'stomate_init'
4384    ENDIF
4385
4386    ALLOCATE(ngd_minus5(kjpindex,nvm),stat=ier)
4387    l_error = l_error .OR. (ier /= 0)
4388    IF (l_error) THEN
4389       WRITE(numout,*) 'Memory allocation error for ngd_minus5. We stop. We need kjpindex*nvm words',kjpindex,nvm
4390       STOP 'stomate_init'
4391    ENDIF
4392
4393    ALLOCATE(PFTpresent(kjpindex,nvm),stat=ier)
4394    l_error = l_error .OR. (ier /= 0)
4395    IF (l_error) THEN
4396       WRITE(numout,*) 'Memory allocation error for PFTpresent. We stop. We need kjpindex*nvm words',kjpindex,nvm
4397       STOP 'stomate_init'
4398    ENDIF
4399
4400    ALLOCATE(npp_longterm(kjpindex,nvm),stat=ier)
4401    l_error = l_error .OR. (ier /= 0)
4402    IF (l_error) THEN
4403       WRITE(numout,*) 'Memory allocation error for npp_longterm. We stop. We need kjpindex*nvm words',kjpindex,nvm
4404       STOP 'stomate_init'
4405    ENDIF
4406
4407    ALLOCATE(lm_lastyearmax(kjpindex,nvm),stat=ier)
4408    l_error = l_error .OR. (ier /= 0)
4409    IF (l_error) THEN
4410       WRITE(numout,*) 'Memory allocation error for lm_lastyearmax. We stop. We need kjpindex*nvm words',kjpindex,nvm
4411       STOP 'stomate_init'
4412    ENDIF
4413
4414    ALLOCATE(lm_thisyearmax(kjpindex,nvm),stat=ier)
4415    l_error = l_error .OR. (ier /= 0)
4416    IF (l_error) THEN
4417       WRITE(numout,*) 'Memory allocation error for lm_thisyearmax. We stop. We need kjpindex*nvm words',kjpindex,nvm
4418       STOP 'stomate_init'
4419    ENDIF
4420
4421    ALLOCATE(maxfpc_lastyear(kjpindex,nvm),stat=ier)
4422    l_error = l_error .OR. (ier /= 0)
4423    IF (l_error) THEN
4424       WRITE(numout,*) 'Memory allocation error for maxfpc_lastyear. We stop. We need kjpindex*nvm words',kjpindex,nvm
4425       STOP 'stomate_init'
4426    ENDIF
4427
4428    ALLOCATE(maxfpc_thisyear(kjpindex,nvm),stat=ier)
4429    l_error = l_error .OR. (ier /= 0)
4430    IF (l_error) THEN
4431       WRITE(numout,*) 'Memory allocation error for maxfpc_thisyear. We stop. We need kjpindex*nvm words',kjpindex,nvm
4432       STOP 'stomate_init'
4433    ENDIF
4434
4435    ALLOCATE(turnover_longterm(kjpindex,nvm,nparts,nelements),stat=ier)
4436    l_error = l_error .OR. (ier /= 0)
4437    IF (l_error) THEN
4438       WRITE(numout,*) 'Memory allocation error for turnover_longterm. We stop. We need kjpindex*nvm*nparts*nelements words', & 
4439       &    kjpindex,nvm,nparts,nelements
4440       STOP 'stomate_init'
4441    ENDIF
4442
4443    ALLOCATE(gpp_week(kjpindex,nvm),stat=ier)
4444    l_error = l_error .OR. (ier /= 0)
4445    IF (l_error) THEN
4446       WRITE(numout,*) 'Memory allocation error for gpp_week. We stop. We need kjpindex*nvm words',kjpindex,nvm
4447       STOP 'stomate_init'
4448    ENDIF
4449
4450    ALLOCATE(plant_status(kjpindex,nvm),stat=ier)
4451    l_error = l_error .OR. (ier /= 0)
4452    IF (l_error) THEN
4453       WRITE(numout,*) 'Memory allocation error for plant_status. We stop. We need kjpindex*nvm words',kjpindex,nvm
4454       STOP 'stomate_init'
4455    ENDIF
4456
4457    ALLOCATE(when_growthinit(kjpindex,nvm),stat=ier)
4458    l_error = l_error .OR. (ier /= 0)
4459    IF (l_error) THEN
4460       WRITE(numout,*) 'Memory allocation error for when_growthinit. We stop. We need kjpindex*nvm words',kjpindex,nvm
4461       STOP 'stomate_init'
4462    ENDIF
4463
4464    ALLOCATE(age(kjpindex,nvm),stat=ier)
4465    l_error = l_error .OR. (ier /= 0)
4466    IF (l_error) THEN
4467       WRITE(numout,*) 'Memory allocation error for age. We stop. We need kjpindex*nvm words',kjpindex,nvm
4468       STOP 'stomate_init'
4469    ENDIF
4470
4471    ALLOCATE(resp_hetero_d(kjpindex,nvm),stat=ier)
4472    l_error = l_error .OR. (ier /= 0)
4473    IF (l_error) THEN
4474       WRITE(numout,*) 'Memory allocation error for resp_hetero_d. We stop. We need kjpindex*nvm words',kjpindex,nvm
4475       STOP 'stomate_init'
4476    ENDIF
4477
4478    ALLOCATE(resp_hetero_radia(kjpindex,nvm),stat=ier)
4479    l_error = l_error .OR. (ier /= 0)
4480    IF (l_error) THEN
4481       WRITE(numout,*) 'Memory allocation error for resp_hetero_radia. We stop. We need kjpindex*nvm words',kjpindex,nvm
4482       STOP 'stomate_init'
4483    ENDIF
4484
4485    ALLOCATE(resp_maint_d(kjpindex,nvm),stat=ier)
4486    l_error = l_error .OR. (ier /= 0)
4487    IF (l_error) THEN
4488       WRITE(numout,*) 'Memory allocation error for resp_maint_d. We stop. We need kjpindex*nvm words',kjpindex,nvm
4489       STOP 'stomate_init'
4490    ENDIF
4491
4492    ALLOCATE(resp_growth_d(kjpindex,nvm),stat=ier)
4493    l_error = l_error .OR. (ier /= 0)
4494    IF (l_error) THEN
4495       WRITE(numout,*) 'Memory allocation error for resp_growth_d. We stop. We need kjpindex*nvm words',kjpindex,nvm
4496       STOP 'stomate_init'
4497    ENDIF
4498
4499    ALLOCATE(co2_fire(kjpindex,nvm),stat=ier)
4500    l_error = l_error .OR. (ier /= 0)
4501    IF (l_error) THEN
4502       WRITE(numout,*) 'Memory allocation error for co2_fire. We stop. We need kjpindex*nvm words',kjpindex,nvm
4503       STOP 'stomate_init'
4504    ENDIF
4505
4506    ALLOCATE(atm_to_bm(kjpindex,nvm,nelements),stat=ier)
4507    l_error = l_error .OR. (ier /= 0)
4508    IF (l_error) THEN
4509       WRITE(numout,*) 'Memory allocation error for atm_to_bm. We stop. We need kjpindex*nvm words',kjpindex,nvm,nelements
4510       STOP 'stomate_init'
4511    ENDIF
4512
4513    ALLOCATE(veget_lastlight(kjpindex,nvm),stat=ier)
4514    l_error = l_error .OR. (ier /= 0)
4515    IF (l_error) THEN
4516       WRITE(numout,*) 'Memory allocation error for veget_lastlight. We stop. We need kjpindex*nvm words',kjpindex,nvm
4517       STOP 'stomate_init'
4518    ENDIF
4519
4520    ALLOCATE(everywhere(kjpindex,nvm),stat=ier)
4521    l_error = l_error .OR. (ier /= 0)
4522    IF (l_error) THEN
4523       WRITE(numout,*) 'Memory allocation error for everywhere. We stop. We need kjpindex*nvm words',kjpindex,nvm
4524       STOP 'stomate_init'
4525    ENDIF
4526
4527    ALLOCATE(need_adjacent(kjpindex,nvm),stat=ier)
4528    l_error = l_error .OR. (ier /= 0)
4529    IF (l_error) THEN
4530       WRITE(numout,*) 'Memory allocation error for need_adjacent. We stop. We need kjpindex*nvm words',kjpindex,nvm
4531       STOP 'stomate_init'
4532    ENDIF
4533
4534    ALLOCATE(leaf_age(kjpindex,nvm,nleafages),stat=ier)
4535    l_error = l_error .OR. (ier /= 0)
4536    IF (l_error) THEN
4537       WRITE(numout,*) 'Memory allocation error for leaf_age. We stop. We need kjpindex*nvm*nleafages words', & 
4538       &      kjpindex,nvm,nleafages
4539       STOP 'stomate_init'
4540    ENDIF
4541
4542    ALLOCATE(leaf_frac(kjpindex,nvm,nleafages),stat=ier)
4543    l_error = l_error .OR. (ier /= 0)
4544    IF (l_error) THEN
4545       WRITE(numout,*) 'Memory allocation error for leaf_frac. We stop. We need kjpindex*nvm*nleafages words', & 
4546       &      kjpindex,nvm,nleafages
4547       STOP 'stomate_init'
4548    ENDIF
4549
4550    ALLOCATE(RIP_time(kjpindex,nvm),stat=ier)
4551    l_error = l_error .OR. (ier /= 0)
4552    IF (l_error) THEN
4553       WRITE(numout,*) 'Memory allocation error for RIP_time. We stop. We need kjpindex*nvm words',kjpindex,nvm
4554       STOP 'stomate_init'
4555    ENDIF
4556
4557    ALLOCATE(time_hum_min(kjpindex,nvm),stat=ier)
4558    l_error = l_error .OR. (ier /= 0)
4559    IF (l_error) THEN
4560       WRITE(numout,*) 'Memory allocation error for time_hum_min. We stop. We need kjpindex*nvm words',kjpindex,nvm
4561       STOP 'stomate_init'
4562    ENDIF
4563
4564    ALLOCATE(hum_min_dormance(kjpindex,nvm),stat=ier)
4565    l_error = l_error .OR. (ier /= 0)
4566    IF (l_error) THEN
4567       WRITE(numout,*) 'Memory allocation error for hum_min_dormance. We stop. We need kjpindex*nvm words',kjpindex,nvm
4568       STOP 'stomate_init'
4569    ENDIF
4570
4571
4572    ALLOCATE(litter(kjpindex,nlitt,nvm,nlevs,nelements),stat=ier)
4573    l_error = l_error .OR. (ier /= 0)
4574    IF (l_error) THEN
4575       WRITE(numout,*) 'Memory allocation error for litter. We stop. We need kjpindex*nlitt*nvm*nlevs*nelements words', & 
4576       &    kjpindex,nlitt,nvm,nlevs,nelements
4577       STOP 'stomate_init'
4578    ENDIF
4579
4580    ALLOCATE(dead_leaves(kjpindex,nvm,nlitt),stat=ier)
4581    l_error = l_error .OR. (ier /= 0)
4582    IF (l_error) THEN
4583       WRITE(numout,*) 'Memory allocation error for dead_leaves. We stop. We need kjpindex*nvm*nlitt words', & 
4584       &   kjpindex,nvm,nlitt
4585       STOP 'stomate_init'
4586    ENDIF
4587
4588    ALLOCATE(som(kjpindex,ncarb,nvm,nelements),stat=ier)
4589    l_error = l_error .OR. (ier /= 0)
4590    IF (l_error) THEN
4591       WRITE(numout,*) 'Memory allocation error for som. We stop. We need kjpindex*ncarb*nvm*nelements words', &
4592            kjpindex,ncarb,nvm,nelements
4593       STOP 'stomate_init'
4594    ENDIF
4595
4596    ALLOCATE(lignin_struc(kjpindex,nvm,nlevs),stat=ier)
4597    l_error = l_error .OR. (ier /= 0)
4598    IF (l_error) THEN
4599       WRITE(numout,*) 'Memory allocation error for lignin_struc. We stop. We need kjpindex*nvm*nlevs words', &
4600            kjpindex,nvm,nlevs
4601       STOP 'stomate_init'
4602    ENDIF
4603
4604    ALLOCATE(lignin_wood(kjpindex,nvm,nlevs),stat=ier)
4605    l_error = l_error .OR. (ier /= 0)
4606    IF (l_error) THEN
4607       WRITE(numout,*) 'Memory allocation error for lignin_wood. We stop. We need kjpindex*nvm*nlevs words', &
4608            kjpindex,nvm,nlevs
4609       STOP 'stomate_init'
4610    ENDIF
4611
4612    ALLOCATE(turnover_time(kjpindex,nvm,nparts),stat=ier)
4613    l_error = l_error .OR. (ier /= 0)
4614    IF (l_error) THEN
4615       WRITE(numout,*) 'Memory allocation error for turnover_time. We stop. We need kjpindex*nvm words', &
4616            kjpindex,nvm
4617       STOP 'stomate_init'
4618    ENDIF
4619
4620!!$    ALLOCATE(co2_flux_daily(kjpindex,nvm),stat=ier)
4621!!$    l_error = l_error .OR. (ier /= 0)
4622!!$    IF (l_error) THEN
4623!!$       WRITE(numout,*) 'Memory allocation error for co2_flux_daily. We stop. We need kjpindex*nvm words',kjpindex,nvm
4624!!$       STOP 'stomate_init'
4625!!$    ENDIF
4626
4627!!$    ALLOCATE(co2_flux_monthly(kjpindex,nvm),stat=ier)
4628!!$    l_error = l_error .OR. (ier /= 0)
4629!!$    IF (l_error) THEN
4630!!$       WRITE(numout,*) 'Memory allocation error for co2_flux_monthly. We stop. We need kjpindex*nvm words',kjpindex,nvm
4631!!$       STOP 'stomate_init'
4632!!$    ENDIF
4633!!$
4634!!$    ALLOCATE (flux_prod_monthly(kjpindex), stat=ier)
4635!!$    l_error = l_error .OR. (ier /= 0)
4636!!$    IF (l_error) THEN
4637!!$       WRITE(numout,*) 'Memory allocation error for flux_prod_monthly. We stop. We need kjpindex words',kjpindex
4638!!$       STOP 'stomate_init'
4639!!$    ENDIF
4640!!$
4641!!$    ALLOCATE (harvest_above_monthly(kjpindex), stat=ier)
4642!!$    l_error = l_error .OR. (ier /= 0)
4643!!$    IF (l_error) THEN
4644!!$       WRITE(numout,*) 'Memory allocation error for harvest_above_monthly. We stop. We need kjpindex words',kjpindex
4645!!$       STOP 'stomate_init'
4646!!$    ENDIF
4647
4648    ALLOCATE(bm_to_litter(kjpindex,nvm,nparts,nelements),stat=ier)
4649    l_error = l_error .OR. (ier /= 0)
4650    IF (l_error) THEN
4651       WRITE(numout,*) 'Memory allocation error for bm_to_litter. We stop. We need kjpindex*nvm*nparts*nelements words', & 
4652       &    kjpindex,nvm,nparts,nelements
4653       STOP 'stomate_init'
4654    ENDIF
4655
4656    ALLOCATE(bm_to_littercalc(kjpindex,nvm,nparts,nelements),stat=ier)
4657    l_error = l_error .OR. (ier /= 0)
4658    IF (l_error) THEN
4659       WRITE(numout,*) 'Memory allocation error for bm_to_littercalc. We stop. We need kjpindex*nvm*nparts*nelements words', &
4660       &   kjpindex,nvm,nparts,nelements
4661       STOP 'stomate_init'
4662    ENDIF
4663
4664    ALLOCATE(herbivores(kjpindex,nvm),stat=ier)
4665    l_error = l_error .OR. (ier /= 0)
4666    IF (l_error) THEN
4667       WRITE(numout,*) 'Memory allocation error for herbivores. We stop. We need kjpindex*nvm words',kjpindex,nvm
4668       STOP 'stomate_init'
4669    ENDIF
4670
4671        ALLOCATE(resp_maint_part_radia(kjpindex,nvm,nparts),stat=ier)
4672    l_error = l_error .OR. (ier /= 0)
4673    IF (l_error) THEN
4674       WRITE(numout,*) 'Memory allocation error for resp_maint_part_radia. We stop. We need kjpindex*nvm*nparts words', &
4675       &  kjpindex,nvm,nparts
4676       STOP 'stomate_init'
4677    ENDIF
4678
4679    ALLOCATE(resp_maint_radia(kjpindex,nvm),stat=ier)
4680    l_error = l_error .OR. (ier /= 0)
4681    IF (l_error) THEN
4682       WRITE(numout,*) 'Memory allocation error for resp_maint_radia. We stop. We need kjpindex*nvm words',kjpindex,nvm
4683       STOP 'stomate_init'
4684    ENDIF
4685
4686    ALLOCATE(resp_maint_part(kjpindex,nvm,nparts),stat=ier)
4687    l_error = l_error .OR. (ier /= 0)
4688    IF (l_error) THEN
4689       WRITE(numout,*) 'Memory allocation error for resp_maint_part. We stop. We need kjpindex*nvm*nparts words', &
4690       &    kjpindex,nvm,nparts
4691       STOP 'stomate_init'
4692    ENDIF
4693    resp_maint_part(:,:,:) = zero
4694
4695    ALLOCATE(hori_index(kjpindex),stat=ier)
4696    l_error = l_error .OR. (ier /= 0)
4697    IF (l_error) THEN
4698       WRITE(numout,*) 'Memory allocation error for hori_index. We stop. We need kjpindex words',kjpindex
4699       STOP 'stomate_init'
4700    ENDIF
4701
4702    ALLOCATE(horipft_index(kjpindex*nvm),stat=ier)
4703    l_error = l_error .OR. (ier /= 0)
4704    IF (l_error) THEN
4705       WRITE(numout,*) 'Memory allocation error for horipft_index. We stop. We need kjpindex*nvm words',kjpindex*nvm
4706       STOP 'stomate_init'
4707    ENDIF
4708
4709    ALLOCATE(horican_index(kjpindex*nlevels_tot),stat=ier)
4710    l_error = l_error .OR. (ier /= 0)
4711    IF (l_error) THEN
4712       WRITE(numout,*) 'Memory allocation error for horican_index. We stop. We need kjpindex*nlevels_tot words',&
4713            kjpindex*nlevels_tot
4714       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4715    ENDIF
4716
4717    ALLOCATE(horicut_index(kjpindex*ncut_times),stat=ier)
4718    l_error = l_error .OR. (ier /= 0)
4719    IF (l_error) THEN
4720       WRITE(numout,*) 'Memory allocation error for horicut_index. We stop. We need kjpindex*ncut_times words',&
4721            kjpindex*ncut_times
4722       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4723    ENDIF
4724
4725    ALLOCATE (horip_s_index(kjpindex*nshort), stat=ier)
4726    l_error = l_error .OR. (ier /= 0)
4727    IF (l_error) THEN
4728       WRITE(numout,*) 'Memory allocation error for horip_s_index. We stop. We need kjpindex*10 words',kjpindex,nshort
4729       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4730    ENDIF
4731
4732    ALLOCATE (horip_m_index(kjpindex*nmedium), stat=ier)
4733    l_error = l_error .OR. (ier /= 0)
4734    IF (l_error) THEN
4735       WRITE(numout,*) 'Memory allocation error for horip_m_index. We stop. We need kjpindex*10 words',kjpindex,nmedium
4736       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4737    ENDIF
4738
4739    ALLOCATE (horip_l_index(kjpindex*100), stat=ier)
4740    l_error = l_error .OR. (ier /= 0)
4741    IF (l_error) THEN
4742       WRITE(numout,*) 'Memory allocation error for horip_l_index. We stop. We need kjpindex*100 words',kjpindex,nlong
4743       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4744    ENDIF
4745 
4746    ALLOCATE (horip_ss_index(kjpindex*(nshort+1)), stat=ier)
4747    l_error = l_error .OR. (ier /= 0)
4748    IF (l_error) THEN
4749       WRITE(numout,*) 'Memory allocation error for horip_ss_index. We stop. We need kjpindex*11 words',kjpindex,nshort+1
4750       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4751    ENDIF
4752
4753    ALLOCATE (horip_mm_index(kjpindex*(nmedium+1)), stat=ier)
4754    l_error = l_error .OR. (ier /= 0)
4755    IF (l_error) THEN
4756       WRITE(numout,*) 'Memory allocation error for horip_mm_index. We stop. We need kjpindex*11 words',kjpindex,nmedium+1
4757       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4758    ENDIF
4759
4760    ALLOCATE (horip_ll_index(kjpindex*(nlong+1)), stat=ier)
4761    l_error = l_error .OR. (ier /= 0)
4762    IF (l_error) THEN
4763       WRITE(numout,*) 'Memory allocation error for horip_ll_index. We stop. We need kjpindex*101 words',kjpindex,nlong+1
4764       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4765    ENDIF
4766
4767    ALLOCATE (prod_s(kjpindex,0:nshort,nelements), stat=ier)
4768    l_error = l_error .OR. (ier /= 0)
4769    IF (l_error) THEN
4770       WRITE(numout,*) 'Memory allocation error for prod_s. We stop. We need kjpindex*(nshort+1)*nelements words', &
4771            kjpindex,nshort+1,nelements
4772       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4773    ENDIF 
4774
4775    ALLOCATE (prod_m(kjpindex,0:nmedium,nelements), stat=ier)
4776    l_error = l_error .OR. (ier /= 0)
4777    IF (l_error) THEN
4778       WRITE(numout,*) 'Memory allocation error for prod_m. We stop. We need kjpindex*(nmedium+1)*nelements words', &
4779            kjpindex,nmedium+1,nelements
4780       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4781    ENDIF
4782
4783    ALLOCATE (prod_l(kjpindex,0:nlong,nelements), stat=ier)
4784    l_error = l_error .OR. (ier /= 0)
4785    IF (l_error) THEN
4786       WRITE(numout,*) 'Memory allocation error for prod_l. We stop. We need kjpindex*(nlong+1)*nelements words', &
4787            kjpindex,nlong+1,nelements
4788       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4789    ENDIF
4790
4791    ALLOCATE (flux_s(kjpindex,nshort,nelements), stat=ier)
4792    l_error = l_error .OR. (ier /= 0)
4793    IF (l_error) THEN
4794       WRITE(numout,*) 'Memory allocation error for flux_s. We stop. We need kjpindex*nshort*nelements words', &
4795            kjpindex,nshort,nelements
4796       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4797    ENDIF
4798
4799    ALLOCATE (flux_m(kjpindex,nmedium,nelements), stat=ier)
4800    l_error = l_error .OR. (ier /= 0)
4801    IF (l_error) THEN
4802       WRITE(numout,*) 'Memory allocation error for flux_m. We stop. We need kjpindex*nmedium words', &
4803            kjpindex,nmedium,nelements
4804       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4805    ENDIF
4806
4807    ALLOCATE (flux_l(kjpindex,nlong,nelements), stat=ier)
4808    l_error = l_error .OR. (ier /= 0)
4809    IF (l_error) THEN
4810       WRITE(numout,*) 'Memory allocation error for flux_l. We stop. We need kjpindex*nlong*nelements words', &
4811            kjpindex,nlong,nelements
4812       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4813    ENDIF
4814
4815    ALLOCATE (flux_prod_s(kjpindex,nelements), stat=ier)
4816    l_error = l_error .OR. (ier /= 0)
4817    IF (l_error) THEN
4818       WRITE(numout,*) 'Memory allocation error for flux_prod_s. We stop. We need kjpindex*nelements words',kjpindex,nelements
4819       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4820    ENDIF
4821
4822    ALLOCATE (flux_prod_m(kjpindex,nelements), stat=ier)
4823    l_error = l_error .OR. (ier /= 0)
4824    IF (l_error) THEN
4825       WRITE(numout,*) 'Memory allocation error for flux_prod_m. We stop. We need kjpindex*nelements words',kjpindex,nelements
4826       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4827    ENDIF
4828
4829    ALLOCATE (flux_prod_l(kjpindex,nelements), stat=ier)
4830    l_error = l_error .OR. (ier /= 0)
4831    IF (l_error) THEN
4832       WRITE(numout,*) 'Memory allocation error for flux_prod_l. We stop. We need kjpindex*nelements words',kjpindex,nelements
4833       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
4834    ENDIF
4835
4836    ALLOCATE (carb_mass_total(kjpindex), stat=ier)
4837    l_error = l_error .OR. (ier /= 0)
4838    IF (l_error) THEN
4839       WRITE(numout,*) 'Memory allocation error for carb_mass_total. We stop. We need kjpindex words',kjpindex
4840       STOP 'stomate_init'
4841    ENDIF
4842
4843    ALLOCATE (som_input_daily(kjpindex,ncarb,nvm,nelements), stat=ier)
4844    l_error = l_error .OR. (ier /= 0)
4845    IF (l_error) THEN
4846       WRITE(numout,*) 'Memory allocation error for som_input_daily. We stop. We need kjpindex*ncarb*nvm*nelements words', & 
4847       &    kjpindex,ncarb,nvm,nelements
4848       STOP 'stomate_init'
4849    ENDIF
4850
4851    ALLOCATE (control_temp_daily(kjpindex,nlevs), stat=ier)
4852    l_error = l_error .OR. (ier /= 0)
4853    IF (l_error) THEN
4854       WRITE(numout,*) 'Memory allocation error for control_temp_daily. We stop. We need kjpindex*nlevs words',kjpindex,nlevs
4855       STOP 'stomate_init'
4856    ENDIF
4857
4858    ALLOCATE (control_moist_daily(kjpindex,nlevs), stat=ier)
4859    l_error = l_error .OR. (ier /= 0)
4860    IF (l_error) THEN
4861       WRITE(numout,*) 'Memory allocation error for control_moist_daily. We stop. We need kjpindex*nlevs words',kjpindex,nlevs
4862       STOP 'stomate_init'
4863    ENDIF
4864
4865    ALLOCATE (fpc_max(kjpindex,nvm), stat=ier)
4866    l_error = l_error .OR. (ier /= 0)
4867    IF (l_error) THEN
4868       WRITE(numout,*) 'Memory allocation error for fpc_max. We stop. We need kjpindex*nvm words',kjpindex,nvm
4869       STOP 'stomate_init'
4870    ENDIF
4871
4872    ALLOCATE(cn_leaf_min_season(kjpindex,nvm),stat=ier) 
4873    l_error = l_error .OR. (ier /= 0) 
4874    IF (l_error) THEN
4875       WRITE(numout,*) 'Memory allocation error for cn_leaf_min_season. We stop. We need kjpindex*nvm words',kjpindex,nvm 
4876       STOP 'stomate_init' 
4877    ENDIF
4878 
4879    ALLOCATE(nstress_season(kjpindex,nvm),stat=ier) 
4880    l_error = l_error .OR. (ier /= 0) 
4881    IF (l_error) THEN
4882       WRITE(numout,*) 'Memory allocation error for nstress_season. We stop. We need kjpindex*nvm words',kjpindex,nvm 
4883       STOP 'stomate_init' 
4884    ENDIF
4885 
4886    ALLOCATE(soil_n_min(kjpindex,nvm,nnspec),stat=ier) 
4887    l_error = l_error .OR. (ier /= 0) 
4888    IF (l_error) THEN
4889       WRITE(numout,*) 'Memory allocation error for soil_n_min. We stop. We need kjpindex*nvm words',kjpindex,nvm,nnspec 
4890       STOP 'stomate_init' 
4891    ENDIF
4892
4893    ALLOCATE(p_O2(kjpindex,nvm),stat=ier) 
4894    l_error = l_error .OR. (ier /= 0) 
4895    IF (l_error) THEN
4896       WRITE(numout,*) 'Memory allocation error for p_O2. We stop. We need kjpindex*nvm words',kjpindex,nvm 
4897       STOP 'stomate_init' 
4898    ENDIF
4899
4900    ALLOCATE(bact(kjpindex,nvm),stat=ier) 
4901    l_error = l_error .OR. (ier /= 0) 
4902    IF (l_error) THEN
4903       WRITE(numout,*) 'Memory allocation error for bact. We stop. We need kjpindex*nvm words',kjpindex,nvm 
4904       STOP 'stomate_init' 
4905    ENDIF
4906
4907    ALLOCATE(ok_equilibrium(kjpindex),stat=ier)
4908    l_error = l_error .OR. (ier /= 0) 
4909    IF (l_error) THEN
4910       WRITE(numout,*) 'Memory allocation error for ok_equilibrium. We stop. We need kjpindex words',kjpindex
4911       STOP 'stomate_init'
4912    ENDIF
4913
4914    ALLOCATE(drainage_daily(kjpindex,nvm),stat=ier) 
4915    l_error = l_error .OR. (ier /= 0) 
4916    IF (l_error) THEN
4917       WRITE(numout,*) ' Memory allocation error for drainage_daily. We stop. We need kjpindex words = ',kjpindex,nvm 
4918       STOP 'drainage_daily' 
4919    ENDIF
4920 
4921    ALLOCATE (plant_n_uptake_daily(kjpindex,nvm,nionspec), stat=ier) 
4922    l_error = l_error .OR. (ier.NE.0) 
4923    IF (l_error) THEN
4924       WRITE(numout,*) ' Memory allocation error for plant_n_uptake_daily. We stop. We need kjpindex words = ',kjpindex*nvm*nionspec 
4925       STOP 'plant_n_uptake_daily' 
4926    ENDIF
4927 
4928    ALLOCATE (n_mineralisation_d(kjpindex,nvm), stat=ier) 
4929    l_error = l_error .OR. (ier.NE.0) 
4930    IF (l_error) THEN
4931       WRITE(numout,*) ' Memory allocation error for n_mineralisation_d. We stop. We need kjpindex words = ',kjpindex*nvm 
4932       STOP 'n_mineralisation_d' 
4933    ENDIF
4934
4935    ALLOCATE(carbon_eq(kjpindex),stat=ier)
4936    l_error = l_error .OR. (ier /= 0)
4937    IF (l_error) THEN
4938       WRITE(numout,*) 'Memory allocation error for carbon_eq. We stop. We need kjpindex words',kjpindex
4939       STOP 'stomate_init'
4940    ENDIF
4941
4942    ALLOCATE(nbp_accu(kjpindex),stat=ier)
4943    l_error = l_error .OR. (ier /= 0)
4944    IF (l_error) THEN
4945       WRITE(numout,*) 'Memory allocation error for nbp_accu. We stop. We need kjpindex words',kjpindex
4946       STOP 'stomate_init'
4947    ENDIF
4948
4949    ALLOCATE(nbp_accu_pool(kjpindex,nvm),stat=ier)
4950    l_error = l_error .OR. (ier /= 0)
4951    IF (l_error) THEN
4952       WRITE(numout,*) 'Memory allocation error for nbp_accu_pool. We stop. We need kjpindex*nvm words',kjpindex*nvm
4953       STOP 'stomate_init'
4954    ENDIF
4955
4956
4957    ALLOCATE(nbp_flux(kjpindex),stat=ier)
4958    l_error = l_error .OR. (ier /= 0)
4959    IF (l_error) THEN
4960       WRITE(numout,*) 'Memory allocation error for nbp_flux. We stop. We need kjpindex words',kjpindex
4961       STOP 'stomate_init'
4962    ENDIF
4963
4964    ALLOCATE(nbp_pool(kjpindex,nvm),stat=ier)
4965    l_error = l_error .OR. (ier /= 0)
4966    IF (l_error) THEN
4967       WRITE(numout,*) 'Memory allocation error for nbp_pool. We stop. We need kjpindex*nvm words',kjpindex*nvm
4968       STOP 'stomate_init'
4969    ENDIF
4970
4971    ALLOCATE(nbp_pool_start(kjpindex,nvm),stat=ier)
4972    l_error = l_error .OR. (ier /= 0)
4973    IF (l_error) THEN
4974       WRITE(numout,*) 'Memory allocation error for nbp_pool_start. We stop. We need kjpindex*nvm words',kjpindex*nvm
4975       STOP 'stomate_init'
4976    ENDIF
4977
4978    ALLOCATE(nbp_pool_end(kjpindex,nvm),stat=ier)
4979    l_error = l_error .OR. (ier /= 0)
4980    IF (l_error) THEN
4981       WRITE(numout,*) 'Memory allocation error for nbp_pool_end. We stop. We need kjpindex*nvm words',kjpindex*nvm
4982       STOP 'stomate_init'
4983    ENDIF
4984
4985    ALLOCATE(matrixA(kjpindex,nvm,nbpools,nbpools),stat=ier)
4986    l_error = l_error .OR. (ier /= 0)
4987    IF (l_error) THEN
4988       WRITE(numout,*) 'Memory allocation error for matrixA. We stop. We need kjpindex*nvm*nbpools*nbpools words',  & 
4989       &     kjpindex, nvm, nbpools, nbpools
4990       STOP 'stomate_init'
4991    ENDIF
4992
4993    ALLOCATE(vectorB(kjpindex,nvm,nbpools),stat=ier)
4994    l_error = l_error .OR. (ier /= 0)
4995    IF (l_error) THEN
4996       WRITE(numout,*) 'Memory allocation error for vectorB. We stop. We need kjpindex*nvm*nbpools words',  & 
4997       &     kjpindex, nvm, nbpools
4998       STOP 'stomate_init'
4999    ENDIF
5000
5001    ALLOCATE(vectorU(kjpindex,nvm,nbpools),stat=ier)
5002    l_error = l_error .OR. (ier /= 0)
5003    IF (l_error) THEN
5004       WRITE(numout,*) 'Memory allocation error for vectorU. We stop. We need kjpindex*nvm*nbpools words',  & 
5005       &     kjpindex, nvm, nbpools
5006       STOP 'stomate_init'
5007    ENDIF
5008
5009    ALLOCATE(matrixV(kjpindex,nvm,nbpools,nbpools),stat=ier)
5010    l_error = l_error .OR. (ier /= 0)
5011    IF (l_error) THEN
5012       WRITE(numout,*) 'Memory allocation error for matrixV. We stop. We need kjpindex*nvm*nbpools*nbpools words',  & 
5013       &     kjpindex, nvm, nbpools, nbpools
5014       STOP 'stomate_init'
5015    ENDIF
5016
5017    ALLOCATE(matrixW(kjpindex,nvm,nbpools,nbpools),stat=ier)
5018    l_error = l_error .OR. (ier /= 0)
5019    IF (l_error) THEN
5020       WRITE(numout,*) 'Memory allocation error for matrixW. We stop. We need kjpindex*nvm*nbpools*nbpools words',  & 
5021       &     kjpindex, nvm, nbpools, nbpools
5022       STOP 'stomate_init'
5023    ENDIF
5024
5025    ALLOCATE(previous_stock(kjpindex,nvm,nbpools),stat=ier)
5026    l_error = l_error .OR. (ier /= 0)
5027    IF (l_error) THEN
5028       WRITE(numout,*) 'Memory allocation error for previous_stock. We stop. We need kjpindex*nvm*nbpools words',  & 
5029       &     kjpindex, nvm, nbpools
5030       STOP 'stomate_init'
5031    ENDIF
5032
5033    ALLOCATE(current_stock(kjpindex,nvm,nbpools),stat=ier)
5034    l_error = l_error .OR. (ier /= 0)
5035    IF (l_error) THEN
5036       WRITE(numout,*) 'Memory allocation error for current_stock. We stop. We need kjpindex*nvm*nbpools words',  & 
5037       &     kjpindex, nvm, nbpools
5038       STOP 'stomate_init'
5039    ENDIF
5040
5041    ALLOCATE(CN_som_litter_longterm(kjpindex,nvm,nbpools),stat=ier)
5042    l_error = l_error .OR. (ier /= 0)
5043    IF (l_error) THEN
5044       WRITE(numout,*) 'Memory allocation error for CN_som_litter_longterm. We stop. We need kjpindex*nvm*nbpools words',  & 
5045       &     kjpindex, nvm, nbpools
5046       STOP 'stomate_init'
5047    ENDIF
5048   
5049    ALLOCATE(KF(kjpindex,nvm),stat=ier)
5050    l_error = l_error .OR. (ier /= 0)
5051    IF (l_error) THEN
5052       WRITE(numout,*) ' Memory allocation error for KF. We stop. We need nvm words = ',kjpindex*nvm
5053       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5054    ENDIF
5055    KF(:,:) = zero ! Is there a better place in the code for this?
5056
5057    ALLOCATE(k_latosa_adapt(kjpindex,nvm),stat=ier)
5058    l_error = l_error .OR. (ier /= 0)
5059    IF (l_error) THEN
5060       WRITE(numout,*) ' Memory allocation error for k_latosa_adapt. We stop. We need nvm words = ',kjpindex*nvm
5061       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5062    ENDIF
5063
5064    ALLOCATE(harvest_pool(kjpindex,nvm,ndia_harvest+1,nelements),stat=ier)
5065    l_error = l_error .OR. (ier /= 0)
5066    IF (l_error) THEN
5067       WRITE(numout,*) ' Memory allocation error for harvest_pool. We stop. We need many words = ',&
5068            kjpindex*nvm*(ndia_harvest+1)*nelements
5069       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5070    ENDIF
5071    harvest_pool(:,:,:,:) = zero
5072
5073    ALLOCATE(harvest_type(kjpindex,nvm),stat=ier)
5074    l_error = l_error .OR. (ier /= 0)
5075    IF (l_error) THEN
5076       WRITE(numout,*) ' Memory allocation error for harvest_type. We stop. We need many words = ',&
5077            kjpindex*nvm
5078       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5079    ENDIF
5080    harvest_type(:,:) = zero
5081
5082    ALLOCATE(harvest_cut(kjpindex,nvm),stat=ier)
5083    l_error = l_error .OR. (ier /= 0)
5084    IF (l_error) THEN
5085       WRITE(numout,*) ' Memory allocation error for harvest_cut. We stop. We need many words = ',&
5086            kjpindex*nvm
5087       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5088    ENDIF
5089    harvest_cut(:,:) = zero
5090
5091    ALLOCATE(harvest_area(kjpindex,nvm),stat=ier)
5092    l_error = l_error .OR. (ier /= 0)
5093    IF (l_error) THEN
5094       WRITE(numout,*) ' Memory allocation error for harvest_area. We stop. We need many words = ',&
5095            kjpindex*nvm
5096       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5097    ENDIF
5098    harvest_area(:,:) = zero
5099
5100    ALLOCATE(harvest_5y_area(kjpindex,nvm,wind_years),stat=ier)
5101    l_error = l_error .OR. (ier /= 0)
5102    IF (l_error) THEN
5103       WRITE(numout,*) ' Memory allocation error for harvest_5y_area. We stop. We need many words = ',&
5104            kjpindex*nvm*wind_years
5105       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5106    ENDIF
5107    harvest_5y_area(:,:,:)=zero
5108
5109    ALLOCATE(harvest_pool_bound(0:ndia_harvest+1),stat=ier)
5110    l_error = l_error .OR. (ier /= 0)
5111    IF (l_error) THEN
5112       WRITE(numout,*) ' Memory allocation error for harvest_pool_bound. ' // &
5113            'We stop. We need ndia_harvest+2 words = ',&
5114            ndia_harvest+2
5115       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5116    ENDIF
5117
5118    ! Here we can initialize the values of this array, too. They
5119    ! should never change over the course of the simulation.
5120    harvest_pool_bound(ndia_harvest+1) = val_exp
5121    DO idia = 0,ndia_harvest
5122       harvest_pool_bound(idia) = max_harvest_dia * &
5123            REAL(idia,r_std) / REAL(ndia_harvest,r_std)
5124    ENDDO
5125
5126    ALLOCATE(mai(kjpindex,nvm),stat=ier)
5127    l_error = l_error .OR. (ier /= 0)
5128    IF (l_error) THEN
5129       WRITE(numout,*) ' Memory allocation error for mai. ' // &
5130            'We stop. We need kjpindex*nvm words = ',&
5131            kjpindex*nvm
5132       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5133    ENDIF
5134
5135    ALLOCATE(pai(kjpindex,nvm),stat=ier)
5136    l_error = l_error .OR. (ier /= 0)
5137    IF (l_error) THEN
5138       WRITE(numout,*) ' Memory allocation error for pai. ' // &
5139            'We stop. We need kjpindex*nvm words = ',&
5140            kjpindex*nvm
5141       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5142    ENDIF
5143
5144    ALLOCATE(previous_wood_volume(kjpindex,nvm),stat=ier)
5145    l_error = l_error .OR. (ier /= 0)
5146    IF (l_error) THEN
5147       WRITE(numout,*) ' Memory allocation error for previous_wood_volume. ' // &
5148            'We stop. We need kjpindex*nvm words = ',&
5149            kjpindex*nvm
5150       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5151    ENDIF
5152   
5153    ALLOCATE(mai_count(kjpindex,nvm),stat=ier)
5154    l_error = l_error .OR. (ier /= 0)
5155    IF (l_error) THEN
5156       WRITE(numout,*) 'Memory allocation error for mai_count. We stop. We need kjpindex*nvm words',  & 
5157       &     kjpindex, nvm
5158       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5159    ENDIF
5160
5161    ALLOCATE(coppice_dens(kjpindex,nvm),stat=ier)
5162    l_error = l_error .OR. (ier /= 0)
5163    IF (l_error) THEN
5164       WRITE(numout,*) ' Memory allocation error for coppice_dens. ' // &
5165            'We stop. We need kjpindex*nvm words = ',&
5166            kjpindex*nvm
5167       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5168    ENDIF
5169
5170    ALLOCATE (rue_longterm(kjpindex,nvm), stat=ier)
5171    l_error = l_error .OR. (ier /= 0)
5172    IF (l_error) THEN
5173       WRITE(numout,*) 'Memory allocation error for rue_longterm. We stop. We need kjpindex*nlevs words',kjpindex,nvm
5174       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5175    ENDIF
5176    rue_longterm(:,:) = un
5177
5178    ALLOCATE (lab_fac(kjpindex,nvm), stat=ier)
5179    ! temp fix, initializing it here...the values get set in stomate_growth_fun_all,
5180    ! but they get used in stomate_resp beforehand, so maybe a code flow problem?
5181    lab_fac(:,:)=zero
5182    l_error = l_error .OR. (ier /= 0)
5183    IF (l_error) THEN
5184       WRITE(numout,*) 'Memory allocation error for lab_fac. We stop. We need kjpindex*nlevs words',kjpindex,nvm
5185       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5186    ENDIF
5187
5188    ALLOCATE(forest_managed(kjpindex,nvm),stat=ier)
5189    l_error = l_error .OR. (ier /= 0)
5190    IF (l_error) THEN
5191       WRITE(numout,*) 'Memory allocation error for forest_managed. We stop. We need kjpindex*nvm words',  & 
5192       &     kjpindex, nvm
5193       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5194    ENDIF
5195
5196    ALLOCATE(forest_managed_lastyear(kjpindex,nvm),stat=ier)
5197    l_error = l_error .OR. (ier /= 0)
5198    IF (l_error) THEN
5199       WRITE(numout,*) 'Memory allocation error for forest_managed_lastyear. We stop. We need kjpindex*nvm words',  & 
5200       &     kjpindex, nvm
5201       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5202    ENDIF
5203
5204    ALLOCATE(species_change_map(kjpindex,nvm),stat=ier)
5205    l_error = l_error .OR. (ier /= 0)
5206    IF (l_error) THEN
5207       WRITE(numout,*) 'Memory allocation error for species_change_map. We stop. We need kjpindex*nvm words',  & 
5208       &     kjpindex, nvm
5209       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5210    ENDIF
5211    species_change_map(:,:)=0
5212
5213    ALLOCATE(fm_change_map(kjpindex,nvm),stat=ier)
5214    l_error = l_error .OR. (ier /= 0)
5215    IF (l_error) THEN
5216       WRITE(numout,*) 'Memory allocation error for fm_change_map. We stop. We need kjpindex*nvm words',  & 
5217       &     kjpindex, nvm
5218       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5219    ENDIF
5220    fm_change_map(:,:)=0
5221
5222    ALLOCATE(lpft_replant(kjpindex,nvm),stat=ier)
5223    l_error = l_error .OR. (ier /= 0)
5224    IF (l_error) THEN
5225       WRITE(numout,*) 'Memory allocation error for lpft_replant. We stop. We need kjpindex*nvm words',  & 
5226       &     kjpindex, nvm
5227       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5228    ENDIF
5229    lpft_replant(:,:)=.FALSE.
5230
5231        ALLOCATE(age_stand(kjpindex,nvm),stat=ier)
5232    l_error = l_error .OR. (ier /= 0)
5233    IF (l_error) THEN
5234       WRITE(numout,*) 'Memory allocation error for age_stand. We stop. We need kjpindex*nvm words',  & 
5235       &     kjpindex, nvm
5236       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5237    ENDIF
5238
5239    ALLOCATE(rotation_n(kjpindex,nvm),stat=ier)
5240    l_error = l_error .OR. (ier /= 0)
5241    IF (l_error) THEN
5242       WRITE(numout,*) 'Memory allocation error for rotation_n. We stop. We need kjpindex*nvm words',  & 
5243       &     kjpindex, nvm
5244       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5245    ENDIF
5246
5247    ALLOCATE(last_cut(kjpindex,nvm),stat=ier)
5248    l_error = l_error .OR. (ier /= 0)
5249    IF (l_error) THEN
5250       WRITE(numout,*) 'Memory allocation error for last_cut. We stop. We need kjpindex*nvm words',  & 
5251       &     kjpindex, nvm
5252       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5253    ENDIF
5254
5255    ALLOCATE(sigma(kjpindex,nvm),stat=ier)
5256    l_error = l_error .OR. (ier /= 0)
5257    IF (l_error) THEN
5258       WRITE(numout,*) 'Memory allocation error for sigma. We stop. We need kjpindex*nvm words',  & 
5259       &     kjpindex, nvm
5260       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5261    ENDIF
5262
5263    ALLOCATE(litter_demand(kjpindex),stat=ier)
5264    l_error = l_error .OR. (ier /= 0)
5265    IF (l_error) THEN
5266       WRITE(numout,*) ' Memory allocation error for litter_demand. ' // &
5267            'We stop. We need kjpindex words = ',&
5268            kjpindex
5269       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5270    ENDIF
5271
5272    ALLOCATE(wstress_season(kjpindex,nvm),stat=ier)
5273    l_error = l_error .OR. (ier /= 0)
5274    IF (l_error) THEN
5275       WRITE(numout,*) ' Memory allocation error for wstress_season. ' // &
5276            'We stop. We need kjpindex*nvm words = ',&
5277            kjpindex, nvm
5278       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5279    ENDIF
5280
5281    ALLOCATE(wstress_month(kjpindex,nvm),stat=ier)
5282    l_error = l_error .OR. (ier /= 0)
5283    IF (l_error) THEN
5284       WRITE(numout,*) ' Memory allocation error for wstress_month. ' // &
5285            'We stop. We need kjpindex*nvm words = ',&
5286            kjpindex, nvm
5287       CALL ipslerr_p (3,'stomate_init', 'Memory allocation issue','','')
5288    ENDIF
5289
5290    ALLOCATE(store_sum_delta_ba(kjpindex,nvm,ncirc),stat=ier)
5291    l_error = l_error .OR. (ier /= 0)
5292    IF (l_error) THEN
5293       WRITE(numout,*) ' Memory allocation error for st_dist. ' // &
5294            'We need kjpindex*nvm*ncirc words = ',kjpindex,nvm,ncirc
5295       CALL ipslerr_p (3,'stomate_main', &
5296            ' Memory allocation error for store_sum_delta_ba.','','')
5297    END IF
5298
5299  !! 5. File definitions
5300
5301    ! Store history and restart files in common variables
5302    hist_id_stomate = hist_id_stom
5303    hist_id_stomate_IPCC = hist_id_stom_IPCC
5304    rest_id_stomate = rest_id_stom
5305   
5306    ! In STOMATE reduced grids are used containing only terrestrial pixels.
5307    ! Build a new indexing table for the vegetation fields separating
5308    ! between the different PFTs. Note that ::index has dimension (kjpindex)
5309    ! wheras ::indexpft has dimension (kjpindex*nvm).
5310
5311    hori_index(:) = index(:)
5312
5313    DO j = 1, nvm
5314       DO ji = 1, kjpindex
5315          horipft_index((j-1)*kjpindex+ji) = index(ji)+(j-1)*kjpij + offset_omp - offset_mpi
5316       ENDDO
5317    ENDDO
5318
5319     DO j = 1, nlevels_tot
5320       DO ji = 1, kjpindex
5321          horican_index((j-1)*kjpindex+ji) = index(ji)+(j-1)*kjpij + offset_omp - offset_mpi
5322       ENDDO
5323    ENDDO
5324
5325    DO j = 1, ncut_times
5326       DO ji = 1, kjpindex
5327          horicut_index((j-1)*kjpindex+ji) = index(ji)+(j-1)*kjpij + offset_omp - offset_mpi
5328       ENDDO
5329    ENDDO
5330
5331    ! Similar index tables are build for the wood use
5332    DO j = 1, nshort
5333       DO ji = 1, kjpindex
5334          horip_s_index((j-1)*kjpindex+ji) = &
5335               index(ji)+(j-1)*kjpij + offset_omp - offset_mpi
5336       ENDDO
5337    ENDDO
5338
5339    DO j = 1, nmedium
5340       DO ji = 1, kjpindex
5341          horip_m_index((j-1)*kjpindex+ji) = &
5342               index(ji)+(j-1)*kjpij + offset_omp - offset_mpi
5343       ENDDO
5344    ENDDO
5345   
5346    DO j = 1, nlong
5347       DO ji = 1, kjpindex
5348          horip_l_index((j-1)*kjpindex+ji) = &
5349               index(ji)+(j-1)*kjpij + offset_omp - offset_mpi
5350       ENDDO
5351    ENDDO
5352
5353    DO j = 1, nshort+1
5354       DO ji = 1, kjpindex
5355          horip_ss_index((j-1)*kjpindex+ji) = &
5356               index(ji)+(j-1)*kjpij + offset_omp - offset_mpi
5357       ENDDO
5358    ENDDO
5359
5360    DO j = 1, nmedium+1
5361       DO ji = 1, kjpindex
5362          horip_mm_index((j-1)*kjpindex+ji) = &
5363               index(ji)+(j-1)*kjpij + offset_omp - offset_mpi
5364       ENDDO
5365    ENDDO
5366
5367    DO j = 1, nlong+1
5368       DO ji = 1, kjpindex
5369          horip_ll_index((j-1)*kjpindex+ji) = &
5370               index(ji)+(j-1)*kjpij + offset_omp - offset_mpi
5371       ENDDO
5372    ENDDO
5373 
5374
5375  !! 6. Initialization of global and land cover change variables.
5376
5377    ! All variables are cumulative variables. bm_to_litter is not and is therefore
5378    ! excluded
5379    ! bm_to_litter(:,:,:) = zero
5380    turnover_daily(:,:,:,:) = zero
5381    resp_hetero_d(:,:) = zero
5382!!$    co2_flux_daily(:,:) = zero
5383!!$    co2_flux_monthly(:,:) = zero
5384!!$    flux_prod_monthly(:) = zero
5385!!$    harvest_above_monthly(:) = zero
5386    control_moist_daily(:,:) = zero
5387    control_temp_daily(:,:) = zero
5388    som_input_daily(:,:,:,:) = zero
5389    drainage_daily(:,:) = zero
5390    fpc_max(:,:)=zero
5391
5392    ! Land cover change variables
5393    prod_s(:,:,:)  = zero
5394    prod_m(:,:,:)  = zero
5395    prod_l(:,:,:) = zero
5396    flux_s(:,:,:)  = zero
5397    flux_m(:,:,:)  = zero
5398    flux_l(:,:,:) = zero
5399    flux_prod_s(:,:)  = zero
5400    flux_prod_m(:,:) = zero
5401    flux_prod_l(:,:) = zero
5402   
5403    ! n variables
5404    nstress_season(:,:) = zero 
5405    soil_n_min(:,:,:) = zero
5406    plant_n_uptake_daily(:,:,:)=zero 
5407    n_mineralisation_d(:,:)=zero 
5408
5409  END SUBROUTINE stomate_init
5410
5411
5412!! ================================================================================================================================
5413!! SUBROUTINE   : stomate_clear
5414!!
5415!>\BRIEF        Deallocate memory of the stomate variables.
5416!!
5417!! DESCRIPTION  : None
5418!!
5419!! RECENT CHANGE(S) : None
5420!!
5421!! MAIN OUTPUT VARIABLE(S): None
5422!!
5423!! REFERENCES   : None
5424!!
5425!! FLOWCHART    : None
5426!! \n
5427!_ ================================================================================================================================
5428 
5429  SUBROUTINE stomate_clear
5430
5431  !! 1. Deallocate all dynamics variables
5432
5433    IF (ALLOCATED(veget_cov_max)) DEALLOCATE(veget_cov_max)
5434    IF (ALLOCATED(adapted)) DEALLOCATE(adapted)
5435    IF (ALLOCATED(regenerate)) DEALLOCATE(regenerate)
5436    IF (ALLOCATED(humrel_daily)) DEALLOCATE(humrel_daily)
5437    IF (ALLOCATED(vir_humrel_daily)) DEALLOCATE(vir_humrel_daily)
5438    IF (ALLOCATED(transpir_supply_daily)) DEALLOCATE(transpir_supply_daily)
5439    IF (ALLOCATED(vir_transpir_supply_daily)) DEALLOCATE(vir_transpir_supply_daily)
5440    IF (ALLOCATED(transpir_daily)) DEALLOCATE(transpir_daily)
5441    IF (ALLOCATED(gdd_init_date)) DEALLOCATE(gdd_init_date)
5442    IF (ALLOCATED(litterhum_daily)) DEALLOCATE(litterhum_daily)
5443    IF (ALLOCATED(t2m_daily))  DEALLOCATE(t2m_daily)
5444    IF (ALLOCATED(t2m_min_daily))  DEALLOCATE(t2m_min_daily)
5445    IF (ALLOCATED(tsurf_daily))  DEALLOCATE(tsurf_daily)
5446    IF (ALLOCATED(tsoil_daily)) DEALLOCATE(tsoil_daily)
5447    IF (ALLOCATED(soilhum_daily)) DEALLOCATE(soilhum_daily)
5448    IF (ALLOCATED(precip_daily)) DEALLOCATE(precip_daily)
5449    IF (ALLOCATED(gpp_daily)) DEALLOCATE(gpp_daily)
5450    IF (ALLOCATED(npp_daily)) DEALLOCATE(npp_daily)
5451    IF (ALLOCATED(turnover_daily)) DEALLOCATE(turnover_daily)
5452    IF (ALLOCATED(turnover_littercalc)) DEALLOCATE(turnover_littercalc)
5453    IF (ALLOCATED(humrel_month)) DEALLOCATE(humrel_month)
5454    IF (ALLOCATED(humrel_week)) DEALLOCATE(humrel_week)
5455    IF (ALLOCATED(humrel_growingseason)) DEALLOCATE(humrel_growingseason)
5456    IF (ALLOCATED(vir_humrel_growingseason)) DEALLOCATE(vir_humrel_growingseason)
5457    IF (ALLOCATED(t2m_longterm)) DEALLOCATE(t2m_longterm)
5458    IF (ALLOCATED(t2m_month)) DEALLOCATE(t2m_month)
5459    IF (ALLOCATED(Tseason)) DEALLOCATE(Tseason)
5460    IF (ALLOCATED(Tseason_length)) DEALLOCATE(Tseason_length)
5461    IF (ALLOCATED(Tseason_tmp)) DEALLOCATE(Tseason_tmp)
5462    IF (ALLOCATED(Tmin_spring_time)) DEALLOCATE(Tmin_spring_time)
5463    IF (ALLOCATED(onset_date)) DEALLOCATE(onset_date)
5464!!$    IF (ALLOCATED(begin_leaves)) DEALLOCATE(begin_leaves)
5465    IF (ALLOCATED(t2m_week)) DEALLOCATE(t2m_week)
5466    IF (ALLOCATED(tsoil_month)) DEALLOCATE(tsoil_month)
5467    IF (ALLOCATED(soilhum_month)) DEALLOCATE(soilhum_month)
5468    IF (ALLOCATED(fireindex)) DEALLOCATE(fireindex)
5469    IF (ALLOCATED(firelitter)) DEALLOCATE(firelitter)
5470    IF (ALLOCATED(maxhumrel_lastyear)) DEALLOCATE(maxhumrel_lastyear)
5471    IF (ALLOCATED(maxhumrel_thisyear)) DEALLOCATE(maxhumrel_thisyear)
5472    IF (ALLOCATED(minhumrel_lastyear)) DEALLOCATE(minhumrel_lastyear)
5473    IF (ALLOCATED(minhumrel_thisyear)) DEALLOCATE(minhumrel_thisyear)
5474    IF (ALLOCATED(maxgppweek_lastyear)) DEALLOCATE(maxgppweek_lastyear)
5475    IF (ALLOCATED(maxgppweek_thisyear)) DEALLOCATE(maxgppweek_thisyear)
5476    IF (ALLOCATED(gdd0_lastyear)) DEALLOCATE(gdd0_lastyear)
5477    IF (ALLOCATED(gdd0_thisyear)) DEALLOCATE(gdd0_thisyear)
5478    IF (ALLOCATED(precip_lastyear)) DEALLOCATE(precip_lastyear)
5479    IF (ALLOCATED(precip_thisyear)) DEALLOCATE(precip_thisyear)
5480    IF (ALLOCATED(gdd_m5_dormance)) DEALLOCATE(gdd_m5_dormance)
5481    IF (ALLOCATED(gdd_from_growthinit)) DEALLOCATE(gdd_from_growthinit)
5482    IF (ALLOCATED(gdd_midwinter)) DEALLOCATE(gdd_midwinter)
5483    IF (ALLOCATED(ncd_dormance)) DEALLOCATE(ncd_dormance)
5484    IF (ALLOCATED(ngd_minus5))  DEALLOCATE(ngd_minus5)
5485    IF (ALLOCATED(PFTpresent)) DEALLOCATE(PFTpresent)
5486    IF (ALLOCATED(npp_longterm)) DEALLOCATE(npp_longterm)
5487    IF (ALLOCATED(lm_lastyearmax)) DEALLOCATE(lm_lastyearmax)
5488    IF (ALLOCATED(lm_thisyearmax)) DEALLOCATE(lm_thisyearmax)
5489    IF (ALLOCATED(maxfpc_lastyear)) DEALLOCATE(maxfpc_lastyear)
5490    IF (ALLOCATED(maxfpc_thisyear)) DEALLOCATE(maxfpc_thisyear)
5491    IF (ALLOCATED(turnover_longterm)) DEALLOCATE(turnover_longterm)
5492    IF (ALLOCATED(gpp_week)) DEALLOCATE(gpp_week)
5493    IF (ALLOCATED(plant_status)) DEALLOCATE(plant_status)
5494    IF (ALLOCATED(when_growthinit)) DEALLOCATE(when_growthinit)
5495    IF (ALLOCATED(age))  DEALLOCATE(age)
5496    IF (ALLOCATED(resp_hetero_d)) DEALLOCATE(resp_hetero_d)
5497    IF (ALLOCATED(resp_hetero_radia)) DEALLOCATE(resp_hetero_radia)
5498    IF (ALLOCATED(resp_maint_d)) DEALLOCATE(resp_maint_d)
5499    IF (ALLOCATED(resp_growth_d)) DEALLOCATE(resp_growth_d)
5500    IF (ALLOCATED(co2_fire)) DEALLOCATE(co2_fire)
5501!!$    IF (ALLOCATED(co2_to_bm_dgvm)) DEALLOCATE(co2_to_bm_dgvm)
5502!!$    IF (ALLOCATED(n_to_bm)) DEALLOCATE(n_to_bm)
5503    IF (ALLOCATED(atm_to_bm)) DEALLOCATE(atm_to_bm)
5504    IF (ALLOCATED(veget_lastlight)) DEALLOCATE(veget_lastlight)
5505    IF (ALLOCATED(everywhere)) DEALLOCATE(everywhere)
5506    IF (ALLOCATED(need_adjacent)) DEALLOCATE(need_adjacent)
5507    IF (ALLOCATED(leaf_age)) DEALLOCATE(leaf_age)
5508    IF (ALLOCATED(leaf_frac)) DEALLOCATE(leaf_frac)
5509    IF (ALLOCATED(RIP_time)) DEALLOCATE(RIP_time)
5510    IF (ALLOCATED(time_hum_min)) DEALLOCATE(time_hum_min)
5511    IF (ALLOCATED(hum_min_dormance)) DEALLOCATE(hum_min_dormance)
5512    IF (ALLOCATED(litter)) DEALLOCATE(litter)
5513    IF (ALLOCATED(dead_leaves)) DEALLOCATE(dead_leaves)
5514    IF (ALLOCATED(som)) DEALLOCATE(som)
5515    IF (ALLOCATED(lignin_struc)) DEALLOCATE(lignin_struc)
5516    IF (ALLOCATED(lignin_wood)) DEALLOCATE(lignin_wood)
5517    IF (ALLOCATED(turnover_time)) DEALLOCATE(turnover_time)
5518!!$    IF (ALLOCATED(co2_flux_daily)) DEALLOCATE(co2_flux_daily)
5519!!$    IF (ALLOCATED(co2_flux_monthly)) DEALLOCATE(co2_flux_monthly)
5520!!$    IF (ALLOCATED(harvest_above_monthly)) DEALLOCATE (harvest_above_monthly)
5521!!$    IF (ALLOCATED(flux_prod_monthly)) DEALLOCATE (flux_prod_monthly)
5522    IF (ALLOCATED(bm_to_litter)) DEALLOCATE(bm_to_litter)
5523    IF (ALLOCATED(bm_to_littercalc)) DEALLOCATE(bm_to_littercalc)
5524    IF (ALLOCATED(herbivores)) DEALLOCATE(herbivores)
5525    IF (ALLOCATED(resp_maint_part_radia)) DEALLOCATE(resp_maint_part_radia)
5526    IF (ALLOCATED(resp_maint_radia)) DEALLOCATE(resp_maint_radia)
5527    IF (ALLOCATED(resp_maint_part)) DEALLOCATE(resp_maint_part)
5528    IF (ALLOCATED(hori_index)) DEALLOCATE(hori_index)
5529    IF (ALLOCATED(horipft_index)) DEALLOCATE(horipft_index)
5530    IF (ALLOCATED(horican_index)) DEALLOCATE(horican_index)
5531    IF (ALLOCATED(horicut_index)) DEALLOCATE(horicut_index)
5532    IF (ALLOCATED(horip_s_index)) DEALLOCATE (horip_s_index)
5533    IF (ALLOCATED(horip_m_index)) DEALLOCATE (horip_m_index)
5534    IF (ALLOCATED(horip_l_index)) DEALLOCATE (horip_l_index)
5535    IF (ALLOCATED(horip_ss_index)) DEALLOCATE (horip_ss_index)
5536    IF (ALLOCATED(horip_mm_index)) DEALLOCATE (horip_mm_index)
5537    IF (ALLOCATED(horip_ll_index)) DEALLOCATE (horip_ll_index)
5538    IF (ALLOCATED(clay_fm)) DEALLOCATE(clay_fm)
5539    IF (ALLOCATED(silt_fm)) DEALLOCATE(silt_fm) 
5540    IF (ALLOCATED(bulk_fm)) DEALLOCATE(bulk_fm) 
5541    IF (ALLOCATED(humrel_daily_fm)) DEALLOCATE(humrel_daily_fm)
5542    IF (ALLOCATED(litterhum_daily_fm))  DEALLOCATE(litterhum_daily_fm)
5543    IF (ALLOCATED(t2m_daily_fm))  DEALLOCATE(t2m_daily_fm)
5544    IF (ALLOCATED(t2m_min_daily_fm))  DEALLOCATE(t2m_min_daily_fm)
5545    IF (ALLOCATED(tsurf_daily_fm)) DEALLOCATE(tsurf_daily_fm)
5546    IF (ALLOCATED(tsoil_daily_fm)) DEALLOCATE(tsoil_daily_fm)
5547    IF (ALLOCATED(soilhum_daily_fm))  DEALLOCATE(soilhum_daily_fm)
5548    IF (ALLOCATED(precip_fm)) DEALLOCATE(precip_fm)
5549    IF (ALLOCATED(gpp_daily_fm))  DEALLOCATE(gpp_daily_fm)
5550    IF (ALLOCATED(veget_fm)) DEALLOCATE(veget_fm)
5551    IF (ALLOCATED(veget_max_fm)) DEALLOCATE(veget_max_fm)
5552    IF (ALLOCATED(drainage_fm)) DEALLOCATE(drainage_fm) 
5553    !
5554    IF (ALLOCATED(ok_equilibrium)) DEALLOCATE(ok_equilibrium)
5555    IF (ALLOCATED(carbon_eq)) DEALLOCATE(carbon_eq)
5556    IF (ALLOCATED(matrixA)) DEALLOCATE(matrixA)
5557    IF (ALLOCATED(vectorB)) DEALLOCATE(vectorB)
5558    IF (ALLOCATED(matrixV)) DEALLOCATE(matrixV)
5559    IF (ALLOCATED(vectorU)) DEALLOCATE(vectorU)
5560    IF (ALLOCATED(matrixW)) DEALLOCATE(matrixW)
5561    IF (ALLOCATED(previous_stock)) DEALLOCATE(previous_stock)
5562    IF (ALLOCATED(current_stock)) DEALLOCATE(current_stock)
5563    IF (ALLOCATED(sigma)) DEALLOCATE (sigma) 
5564    IF (ALLOCATED(age_stand)) DEALLOCATE (age_stand)
5565    IF (ALLOCATED(rotation_n)) DEALLOCATE (rotation_n)
5566    IF (ALLOCATED(last_cut)) DEALLOCATE (last_cut)
5567    IF (ALLOCATED(CN_som_litter_longterm)) DEALLOCATE(CN_som_litter_longterm) 
5568    IF (ALLOCATED(KF)) DEALLOCATE (KF)
5569    IF (ALLOCATED(k_latosa_adapt)) DEALLOCATE (k_latosa_adapt)
5570    IF (ALLOCATED(harvest_pool)) DEALLOCATE (harvest_pool)
5571    IF (ALLOCATED(harvest_type)) DEALLOCATE (harvest_type)
5572    IF (ALLOCATED(harvest_cut)) DEALLOCATE (harvest_cut)
5573    IF (ALLOCATED(harvest_area)) DEALLOCATE (harvest_area)
5574    IF (ALLOCATED(harvest_5y_area)) DEALLOCATE (harvest_5y_area)
5575    IF (ALLOCATED(harvest_pool_bound)) DEALLOCATE (harvest_pool_bound)
5576    IF (ALLOCATED(prod_s)) DEALLOCATE (prod_s)
5577    IF (ALLOCATED(prod_m)) DEALLOCATE (prod_m)
5578    IF (ALLOCATED(prod_l)) DEALLOCATE (prod_l)
5579    IF (ALLOCATED(flux_s)) DEALLOCATE (flux_s)
5580    IF (ALLOCATED(flux_m)) DEALLOCATE (flux_m)
5581    IF (ALLOCATED(flux_l)) DEALLOCATE (flux_l)
5582    IF (ALLOCATED(flux_prod_s)) DEALLOCATE (flux_prod_s)
5583    IF (ALLOCATED(flux_prod_m)) DEALLOCATE (flux_prod_m)
5584    IF (ALLOCATED(flux_prod_l)) DEALLOCATE (flux_prod_l)
5585
5586    IF (ALLOCATED(mai)) DEALLOCATE (mai)
5587    IF (ALLOCATED(pai)) DEALLOCATE (pai)
5588    IF (ALLOCATED(previous_wood_volume)) DEALLOCATE (previous_wood_volume)
5589    IF (ALLOCATED(mai_count)) DEALLOCATE (mai_count)
5590    IF (ALLOCATED(coppice_dens)) DEALLOCATE (coppice_dens)
5591    IF (ALLOCATED(litter_demand)) DEALLOCATE (litter_demand)
5592    IF (ALLOCATED(wstress_season)) DEALLOCATE (wstress_season)
5593    IF (ALLOCATED(wstress_month)) DEALLOCATE (wstress_month)
5594    IF (ALLOCATED(rue_longterm)) DEALLOCATE (rue_longterm)
5595    IF (ALLOCATED(nbp_accu)) DEALLOCATE(nbp_accu)
5596    IF (ALLOCATED(nbp_accu_pool)) DEALLOCATE(nbp_accu_pool)
5597    IF (ALLOCATED(nbp_flux)) DEALLOCATE(nbp_flux)
5598    IF (ALLOCATED(nbp_pool)) DEALLOCATE(nbp_pool)
5599    IF (ALLOCATED(nbp_pool_start)) DEALLOCATE(nbp_pool_start)
5600    IF (ALLOCATED(nbp_pool_end)) DEALLOCATE(nbp_pool_end)
5601
5602    IF (ALLOCATED(clay_fm_g)) DEALLOCATE(clay_fm_g)
5603    IF (ALLOCATED(silt_fm_g)) DEALLOCATE(silt_fm_g) 
5604    IF (ALLOCATED(bulk_fm_g)) DEALLOCATE(bulk_fm_g) 
5605    IF (ALLOCATED(humrel_daily_fm_g)) DEALLOCATE(humrel_daily_fm_g)
5606    IF (ALLOCATED(litterhum_daily_fm_g))  DEALLOCATE(litterhum_daily_fm_g)
5607    IF (ALLOCATED(t2m_daily_fm_g))  DEALLOCATE(t2m_daily_fm_g)
5608    IF (ALLOCATED(t2m_min_daily_fm_g))  DEALLOCATE(t2m_min_daily_fm_g)
5609    IF (ALLOCATED(tsurf_daily_fm_g)) DEALLOCATE(tsurf_daily_fm_g)
5610    IF (ALLOCATED(tsoil_daily_fm_g)) DEALLOCATE(tsoil_daily_fm_g)
5611    IF (ALLOCATED(soilhum_daily_fm_g))  DEALLOCATE(soilhum_daily_fm_g)
5612    IF (ALLOCATED(precip_fm_g)) DEALLOCATE(precip_fm_g)
5613    IF (ALLOCATED(gpp_daily_fm_g))  DEALLOCATE(gpp_daily_fm_g)
5614    IF (ALLOCATED(veget_fm_g)) DEALLOCATE(veget_fm_g)
5615    IF (ALLOCATED(veget_max_fm_g)) DEALLOCATE(veget_max_fm_g)
5616!!$    IF (ALLOCATED(lai_fm_g))  DEALLOCATE(lai_fm_g)
5617    IF (ALLOCATED(drainage_fm_g))  DEALLOCATE(drainage_fm_g)   
5618 
5619    IF (ALLOCATED(isf)) DEALLOCATE(isf)
5620    IF (ALLOCATED(nf_written)) DEALLOCATE(nf_written)
5621    IF (ALLOCATED(nf_cumul)) DEALLOCATE(nf_cumul)
5622    IF (ALLOCATED(nforce)) DEALLOCATE(nforce)
5623    IF (ALLOCATED(control_moist)) DEALLOCATE(control_moist)
5624    IF (ALLOCATED(control_temp)) DEALLOCATE(control_temp)
5625    IF (ALLOCATED(carbon_input)) DEALLOCATE(carbon_input)
5626    IF (ALLOCATED(nitrogen_input)) DEALLOCATE(nitrogen_input)
5627    IF ( ALLOCATED (som_input_daily)) DEALLOCATE (som_input_daily)
5628    IF ( ALLOCATED (control_temp_daily)) DEALLOCATE (control_temp_daily)
5629    IF ( ALLOCATED (control_moist_daily)) DEALLOCATE (control_moist_daily)
5630
5631    IF ( ALLOCATED (drainage_daily)) DEALLOCATE(drainage_daily) 
5632    IF ( ALLOCATED (plant_n_uptake_daily)) DEALLOCATE(plant_n_uptake_daily) 
5633    IF ( ALLOCATED (n_mineralisation_d)) DEALLOCATE(n_mineralisation_d) 
5634    IF ( ALLOCATED (cn_leaf_min_season)) DEALLOCATE (cn_leaf_min_season) 
5635    IF ( ALLOCATED (nstress_season)) DEALLOCATE (nstress_season) 
5636    IF ( ALLOCATED (soil_n_min)) DEALLOCATE (soil_n_min) 
5637    IF ( ALLOCATED (p_O2)) DEALLOCATE (p_O2) 
5638    IF ( ALLOCATED (bact)) DEALLOCATE (bact) 
5639    IF ( ALLOCATED (fpc_max)) DEALLOCATE (fpc_max)
5640
5641    IF (ALLOCATED(forest_managed)) DEALLOCATE (forest_managed)
5642    IF (ALLOCATED(forest_managed_lastyear)) DEALLOCATE (forest_managed_lastyear)
5643    IF (ALLOCATED(species_change_map)) DEALLOCATE (species_change_map)
5644    IF (ALLOCATED(fm_change_map)) DEALLOCATE (fm_change_map) 
5645    IF (ALLOCATED(lpft_replant)) DEALLOCATE (lpft_replant)
5646
5647 !! 2. reset l_first
5648
5649    l_first_stomate=.TRUE.
5650
5651 !! 3. call to clear functions
5652
5653!!$    CALL get_reftemp_clear
5654    CALL season_clear
5655    CALL stomate_lpj_clear
5656    CALL littercalc_clear
5657    CALL vmax_clear
5658 
5659  END SUBROUTINE stomate_clear
5660
5661
5662!! ================================================================================================================================
5663!! SUBROUTINE   : stomate_var_init
5664!!
5665!>\BRIEF        Initialize variables of stomate with a none-zero initial value.
5666!! Subroutine is called only if ::ok_stomate = .TRUE. STOMATE diagnoses some
5667!! variables for SECHIBA : assim_param, deadleaf_cover, etc. These variables can
5668!! be recalculated from STOMATE's prognostic variables. Note that height is
5669!! saved in SECHIBA.
5670!!
5671!! DESCRIPTION  : None
5672!!
5673!! RECENT CHANGE(S) : None
5674!!
5675!! MAIN OUTPUT VARIABLE(S): leaf age (::leaf_age) and fraction of leaves in leaf
5676!! age class (::leaf_frac). The maximum water on vegetation available for
5677!! interception, fraction of soil covered by dead leaves
5678!! (::deadleaf_cover) and assimilation parameters (:: assim_param).
5679!!
5680!! REFERENCE(S) : None
5681!!
5682!! FLOWCHART    : None
5683!! \n
5684!_ ================================================================================================================================
5685 
5686  SUBROUTINE stomate_var_init &
5687       &  (kjpindex, veget_cov_max, leaf_age, leaf_frac, &
5688       &   dead_leaves, &
5689       &   veget_cov, deadleaf_cover, assim_param, &
5690       &   circ_class_biomass, circ_class_n)
5691
5692
5693  !! 0. Variable and parameter declaration
5694
5695    !! 0.1 Input variables
5696
5697    INTEGER(i_std),INTENT(in)                             :: kjpindex        !! Domain size - terrestrial pixels only
5698    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)        :: veget_cov           !! Fraction of pixel covered by PFT. Fraction
5699                                                                             !! accounts for none-biological land covers
5700                                                                             !! (unitless)
5701    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)        :: veget_cov_max   !! Fractional coverage: maximum share of the pixel
5702                                                                             !! covered by a PFT (unitless)
5703    REAL(r_std),DIMENSION(kjpindex,nvm,nlitt),INTENT(in)  :: dead_leaves     !! Metabolic and structural fraction of dead leaves
5704                                                                             !! per ground area
5705                                                                             !! @tex $(gC m^{-2})$ @endtex 
5706    REAL(r_std), DIMENSION(kjpindex,nvm,ncirc,nparts,nelements),INTENT(in)       :: circ_class_biomass         !! @tex $(gC m^{-2})$ @endtex
5707
5708    REAL(r_std), DIMENSION(kjpindex,nvm,ncirc),INTENT(in)        :: circ_class_n !! @tex $(gC m^{-2})$ @endtex
5709
5710
5711    !! 0.2 Modified variables
5712
5713    REAL(r_std),DIMENSION(kjpindex,nvm,nleafages),INTENT(inout) :: leaf_age  !! Age of different leaf classes per PFT (days)
5714    REAL(r_std),DIMENSION(kjpindex,nvm,nleafages),INTENT(inout) :: leaf_frac !! Fraction of leaves in leaf age class per PFT
5715                                                                             !! (unitless; 1)
5716   
5717    !! 0.3 Output variables
5718
5719    REAL(r_std),DIMENSION(kjpindex), INTENT (out)         :: deadleaf_cover  !! Fraction of soil covered by dead leaves
5720                                                                             !! (unitless)
5721    REAL(r_std),DIMENSION(kjpindex,nvm,npco2),INTENT(out) :: assim_param     !! min+max+opt temperatures (K) & vmax for
5722                                                                             !! photosynthesis 
5723                                                                             !! @tex $(\mumol m^{-2} s^{-1})$ @endtex
5724    ! 0.4 Local variables
5725   
5726    REAL(r_std),PARAMETER                                 :: dt_0 = zero     !! Dummy time step, must be zero
5727    REAL(r_std),DIMENSION(kjpindex,nvm)                   :: vcmax           !! Dummy vcmax
5728                                                                             !! @tex $(\mu mol m^{-2} s^{-1})$ @endtex
5729
5730    REAL(r_std),DIMENSION(kjpindex,nvm)                   :: nue             !! Nitrogen use Efficiency with impact of leaf age (umol CO2 (gN)-1 s-1)
5731                                                                             !! @tex $(\mu mol m^{-2} s^{-1})$ @endtex
5732    INTEGER(i_std)                                        :: j               !! Index (untiless)
5733   
5734!_ ================================================================================================================================   
5735
5736    ! Only if stomate is activated
5737    IF (printlev>=4) WRITE(numout,*) 'Entering stomate_var_init'
5738 
5739    !! 1. photosynthesis parameters
5740
5741    !! 1.1 vcmax (stomate_vmax.f90)
5742    CALL vmax (kjpindex, dt_0, leaf_age, leaf_frac, vcmax, nue )
5743
5744    IF (printlev_loc>=4) THEN
5745       WRITE(numout,*) 'vcmax, ', vcmax
5746       WRITE(numout,*) 'nue, ', nue
5747    ENDIF
5748   
5749    !! 1.3 transform into nvm vegetation types
5750    assim_param(:,:,ivcmax) = zero
5751    assim_param(:,:,inue) = zero 
5752    assim_param(:,:,ileafN) = zero 
5753    DO j = 2, nvm
5754       assim_param(:,j,ivcmax)=vcmax(:,j)
5755       assim_param(:,j,inue)=nue(:,j) 
5756       assim_param(:,j,ileafN)=SUM(circ_class_biomass(:,j,:,ileaf,initrogen)*circ_class_n(:,j,:),2)
5757    ENDDO
5758   
5759    !! 2. Dead leaf cover (stomate_litter.f90)
5760   
5761    CALL deadleaf (kjpindex, veget_cov_max, dead_leaves, deadleaf_cover)     
5762   
5763  END SUBROUTINE stomate_var_init
5764
5765
5766!! ================================================================================================================================
5767!! INTERFACE    : stomate_accu
5768!!
5769!>\BRIEF        Accumulate a variable for the time period specified by
5770!! dt_sechiba or calculate the mean value over the period of dt_stomate.
5771!!
5772!! DESCRIPTION  : Accumulate a variable for the time period specified by 
5773!! dt_sechiba or calculate the mean value over the period of dt_stomate.
5774!! stomate_accu interface can be used for variables having 1, 2 or 3 dimensions.
5775!! The corresponding subruoutine stomate_accu_r1d, stomate_accu_r2d or
5776!! stomate_accu_r3d will be selected through the interface depending on the number of dimensions.
5777!!
5778!! RECENT CHANGE(S) : None
5779!!
5780!! MAIN OUTPUT VARIABLE(S): accumulated or mean variable ::field_out::
5781!!
5782!! REFERENCE(S) : None
5783!!
5784!! FLOWCHART    : None
5785!! \n
5786!_ ================================================================================================================================
5787 
5788  SUBROUTINE stomate_accu_r1d (ldmean, field_in, field_out)
5789   
5790  !! 0. Variable and parameter declaration
5791
5792    !! 0.1 Input variables
5793    LOGICAL,INTENT(in)                     :: ldmean    !! Flag to calculate the mean over
5794    REAL(r_std),DIMENSION(:),INTENT(in)    :: field_in  !! Field that needs to be accumulated
5795   
5796    !! 0.2 Modified variables
5797    REAL(r_std),DIMENSION(:),INTENT(inout) :: field_out !! Accumulated or mean field
5798
5799!_ ================================================================================================================================
5800
5801  !! 1. Accumulate field
5802
5803    field_out(:) = field_out(:)+field_in(:)*dt_sechiba
5804   
5805  !! 2. Mean fields
5806    IF (ldmean) THEN
5807       field_out(:) = field_out(:)/dt_stomate
5808    ENDIF
5809
5810  END SUBROUTINE stomate_accu_r1d
5811
5812  SUBROUTINE stomate_accu_r2d (ldmean, field_in, field_out)
5813   
5814  !! 0. Variable and parameter declaration
5815
5816    !! 0.1 Input variables
5817    LOGICAL,INTENT(in)                       :: ldmean    !! Flag to calculate the mean over
5818    REAL(r_std),DIMENSION(:,:),INTENT(in)    :: field_in  !! Field that needs to be accumulated
5819   
5820    !! 0.2 Modified variables
5821    REAL(r_std),DIMENSION(:,:),INTENT(inout) :: field_out !! Accumulated or mean field
5822
5823!_ ================================================================================================================================
5824
5825  !! 1. Accumulate field
5826 
5827    field_out(:,:) = field_out(:,:)+field_in(:,:)*dt_sechiba
5828   
5829  !! 2. Mean fields
5830    IF (ldmean) THEN
5831       field_out(:,:) = field_out(:,:)/dt_stomate
5832    ENDIF
5833 
5834  END SUBROUTINE stomate_accu_r2d
5835
5836  SUBROUTINE stomate_accu_r3d (ldmean, field_in, field_out)
5837   
5838  !! 0. Variable and parameter declaration
5839
5840    !! 0.1 Input variables
5841    LOGICAL,INTENT(in)                         :: ldmean    !! Flag to calculate the mean over
5842    REAL(r_std),DIMENSION(:,:,:),INTENT(in)    :: field_in  !! Field that needs to be accumulated
5843   
5844    !! 0.2 Modified variables
5845    REAL(r_std),DIMENSION(:,:,:),INTENT(inout) :: field_out !! Accumulated or mean field
5846
5847!_ ================================================================================================================================
5848
5849  !! 1. Accumulate field
5850
5851    field_out(:,:,:) = field_out(:,:,:)+field_in(:,:,:)*dt_sechiba
5852   
5853  !! 2. Mean fields
5854
5855    IF (ldmean) THEN
5856       field_out(:,:,:) = field_out(:,:,:)/dt_stomate
5857    ENDIF
5858
5859  END SUBROUTINE stomate_accu_r3d
5860
5861  SUBROUTINE stomate_accu_r4d (ldmean, field_in, field_out)
5862
5863  !! 0. Variable and parameter declaration
5864
5865    !! 0.1 Input variables
5866    LOGICAL,INTENT(in)                           :: ldmean    !! Flag to calculate the mean over 
5867    REAL(r_std),DIMENSION(:,:,:,:),INTENT(in)    :: field_in  !! Field that needs to be accumulated
5868
5869    !! 0.2 Modified variables
5870    REAL(r_std),DIMENSION(:,:,:,:),INTENT(inout) :: field_out !! Accumulated or mean field
5871
5872!_ ================================================================================================================================
5873
5874  !! 1. Accumulate field
5875
5876    field_out(:,:,:,:) = field_out(:,:,:,:)+field_in(:,:,:,:)*dt_sechiba
5877
5878  !! 2. Mean fields
5879
5880    IF (ldmean) THEN
5881       field_out(:,:,:,:) = field_out(:,:,:,:)/dt_stomate
5882    ENDIF
5883
5884  END SUBROUTINE stomate_accu_r4d
5885
5886!! ================================================================================================================================
5887!! SUBROUTINE   : stomate_veget_update
5888!!
5889!>\BRIEF        After the vegetation has been updated some variables needs to be reinitialized for too small fractions
5890!!
5891!! DESCRIPTION :  After the vegetation has been updated some variables needs to be reinitialized for too small fractions.
5892!!                This subroutine is called from slowproc_veget after removing to small fractions.
5893!!
5894!! RECENT CHANGE(S) : These calculations were previously done in stomate_lcchange
5895!!
5896!! MAIN OUTPUT VARIABLE(S): None
5897!!
5898!! REFERENCE(S) : None
5899!!
5900!! FLOWCHART    : None
5901!! \n
5902!_ ================================================================================================================================
5903
5904  SUBROUTINE stomate_veget_update(kjpindex, veget_max)
5905
5906    !! 0. Variable and parameter declaration
5907    !! 0.1 Input variables
5908    INTEGER(i_std),INTENT(in)                       :: kjpindex          !! Local domain size - terrestrial pixels only (unitless)
5909    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)  :: veget_max         !! Maximum fraction of vegetation type including
5910                                                                         !! non-biological fraction (unitless)
5911    !! 0.3 Local variables
5912    INTEGER(i_std)                                  :: i, j              !! Indices
5913
5914    ! Only proceed if the initalization of stomate has been done
5915    IF (.NOT. l_first_stomate) THEN
5916
5917       ! Loop over all points on all pft's
5918       ! If the fraction is too small, reset the depending variables
5919       ! veget_max will be changed in slowproc_veget after this subroutine has been done.
5920       DO i = 1, kjpindex
5921          DO j=1, nvm
5922             IF ( veget_max(i,j) < min_vegfrac ) THEN
5923                PFTpresent(i,j) = .FALSE.
5924                plant_status(i,j) = idormant
5925                age(i,j) = zero
5926                when_growthinit(i,j) = undef
5927                everywhere(i,j) = zero
5928                som(i,:,j,:) = zero
5929                litter(i,:,j,:,:) = zero
5930                bm_to_litter(i,j,:,:) = zero
5931                turnover_daily(i,j,:,:) = zero
5932             ENDIF
5933          END DO
5934       END DO
5935    END IF
5936
5937  END SUBROUTINE stomate_veget_update
5938
5939!! ================================================================================================================================
5940!! SUBROUTINE   : init_forcing
5941!!
5942!>\BRIEF        Allocate memory for the variables containing the forcing data.
5943!! The maximum size of the allocated memory is specified in run definition file
5944!! (::max_totsize) and needs to be a compromise between charging the memory and
5945!! accessing disks to get the forcing data.
5946!!
5947!! DESCRIPTION : None
5948!!
5949!! RECENT CHANGE(S) : None
5950!!
5951!! MAIN OUTPUT VARIABLE(S): Strictly speaking the subroutine has no output
5952!! variables. However, the routine allocates memory for later use.
5953!!
5954!! REFERENCE(S) : None
5955!!
5956!! FLOWCHART    : None
5957!! \n
5958!_ ================================================================================================================================
5959 
5960  SUBROUTINE init_forcing (kjpindex,nsfm,nsft_loc)
5961   
5962  !! 0. Variable and parameter declaration
5963
5964    !! 0.1 Input variables
5965    INTEGER(i_std),INTENT(in) :: kjpindex !! Domain size - terrestrial pixels only (unitless)
5966    INTEGER(i_std),INTENT(in) :: nsfm     !! Number of time steps that can be stored in memory (unitless)
5967    INTEGER(i_std),INTENT(in) :: nsft_loc !! Number of time steps in a year (unitless)
5968
5969   !! 0.2 Output variables
5970
5971   !! 0.3 Modified variables
5972
5973   !! 0.4 Local variables
5974
5975    LOGICAL                   :: l_error  !! Check errors in netcdf call
5976    INTEGER(i_std)            :: ier      !! Check errors in netcdf call
5977!_ ================================================================================================================================
5978   
5979  !! 1. Allocate memory
5980
5981    ! Note ::nvm is number of PFTs and ::nbdl is number of soil layers
5982    l_error = .FALSE.
5983    ALLOCATE(clay_fm(kjpindex,nsfm),stat=ier)
5984    l_error = l_error .OR. (ier /= 0)
5985    IF (l_error) THEN
5986       WRITE(numout,*) 'Problem with memory allocation: forcing variables clay_fm ',kjpindex,nsfm
5987       STOP 'init_forcing'
5988    ENDIF
5989
5990    ALLOCATE(silt_fm(kjpindex,nsfm),stat=ier) 
5991    l_error = l_error .OR. (ier /= 0) 
5992    IF (l_error) THEN
5993       WRITE(numout,*) 'Problem with memory allocation: forcing variables silt_fm ',kjpindex,nsfm 
5994       STOP 'init_forcing' 
5995    ENDIF
5996    ALLOCATE(bulk_fm(kjpindex,nsfm),stat=ier) 
5997    l_error = l_error .OR. (ier /= 0) 
5998    IF (l_error) THEN
5999       WRITE(numout,*) 'Problem with memory allocation: forcing variables bulk_fm ',kjpindex,nsfm 
6000       STOP 'init_forcing' 
6001    ENDIF
6002
6003    ALLOCATE(humrel_daily_fm(kjpindex,nvm,nsfm),stat=ier)
6004    l_error = l_error .OR. (ier /= 0)
6005    IF (l_error) THEN
6006       WRITE(numout,*) 'Problem with memory allocation: forcing variables humrel_daily_fm ',kjpindex,nvm,nsfm
6007       STOP 'init_forcing'
6008    ENDIF
6009    ALLOCATE(litterhum_daily_fm(kjpindex,nsfm),stat=ier)
6010    l_error = l_error .OR. (ier /= 0)
6011    IF (l_error) THEN
6012       WRITE(numout,*) 'Problem with memory allocation: forcing variables litterhum_daily_fm ',kjpindex,nsfm
6013       STOP 'init_forcing'
6014    ENDIF
6015    ALLOCATE(t2m_daily_fm(kjpindex,nsfm),stat=ier)
6016    l_error = l_error .OR. (ier /= 0)
6017    IF (l_error) THEN
6018       WRITE(numout,*) 'Problem with memory allocation: forcing variables t2m_daily_fm ',kjpindex,nsfm
6019       STOP 'init_forcing'
6020    ENDIF
6021    ALLOCATE(t2m_min_daily_fm(kjpindex,nsfm),stat=ier)
6022    l_error = l_error .OR. (ier /= 0)
6023    IF (l_error) THEN
6024       WRITE(numout,*) 'Problem with memory allocation: forcing variables t2m_min_daily_fm ',kjpindex,nsfm
6025       STOP 'init_forcing'
6026    ENDIF
6027    ALLOCATE(tsurf_daily_fm(kjpindex,nsfm),stat=ier)
6028    l_error = l_error .OR. (ier /= 0)
6029    IF (l_error) THEN
6030       WRITE(numout,*) 'Problem with memory allocation: forcing variables tsurf_daily_fm ',kjpindex,nsfm
6031       STOP 'init_forcing'
6032    ENDIF
6033    ALLOCATE(tsoil_daily_fm(kjpindex,nbdl,nsfm),stat=ier)
6034    l_error = l_error .OR. (ier /= 0)
6035    IF (l_error) THEN
6036       WRITE(numout,*) 'Problem with memory allocation: forcing variables tsoil_daily_fm ',kjpindex,nbdl,nsfm
6037       STOP 'init_forcing'
6038    ENDIF
6039    ALLOCATE(soilhum_daily_fm(kjpindex,nbdl,nsfm),stat=ier)
6040    l_error = l_error .OR. (ier /= 0)
6041    IF (l_error) THEN
6042       WRITE(numout,*) 'Problem with memory allocation: forcing variables soilhum_daily_fm ',kjpindex,nbdl,nsfm
6043       STOP 'init_forcing'
6044    ENDIF
6045    ALLOCATE(precip_fm(kjpindex,nsfm),stat=ier)
6046    l_error = l_error .OR. (ier /= 0)
6047    IF (l_error) THEN
6048       WRITE(numout,*) 'Problem with memory allocation: forcing variables precip_fm ',kjpindex,nsfm
6049       STOP 'init_forcing'
6050    ENDIF
6051    ALLOCATE(gpp_daily_fm(kjpindex,nvm,nsfm),stat=ier)
6052    l_error = l_error .OR. (ier /= 0)
6053    IF (l_error) THEN
6054       WRITE(numout,*) 'Problem with memory allocation: forcing variables gpp_daily_fm ',kjpindex,nvm,nsfm
6055       STOP 'init_forcing'
6056    ENDIF
6057    ALLOCATE(veget_fm(kjpindex,nvm,nsfm),stat=ier)
6058    l_error = l_error .OR. (ier /= 0)
6059    IF (l_error) THEN
6060       WRITE(numout,*) 'Problem with memory allocation: forcing variables veget_fm ',kjpindex,nvm,nsfm
6061       STOP 'init_forcing'
6062    ENDIF
6063    ALLOCATE(veget_max_fm(kjpindex,nvm,nsfm),stat=ier)
6064    l_error = l_error .OR. (ier /= 0)
6065    IF (l_error) THEN
6066       WRITE(numout,*) 'Problem with memory allocation: forcing variables veget_max_fm ',kjpindex,nvm,nsfm
6067       STOP 'init_forcing'
6068    ENDIF
6069!!$    ALLOCATE(lai_fm(kjpindex,nvm,nsfm),stat=ier)
6070!!$    l_error = l_error .OR. (ier /= 0)
6071!!$    IF (l_error) THEN
6072!!$       WRITE(numout,*) 'Problem with memory allocation: forcing variables lai_fm ',kjpindex,nvm,nsfm
6073!!$       STOP 'init_forcing'
6074!!$    ENDIF
6075    ALLOCATE(drainage_fm(kjpindex,nvm,nsfm),stat=ier) 
6076    l_error = l_error .OR. (ier /= 0) 
6077    IF (l_error) THEN
6078       WRITE(numout,*) 'Problem with memory allocation: forcing variables drainage_fm ',kjpindex,nvm,nsfm 
6079       STOP 'init_forcing' 
6080    ENDIF
6081    ALLOCATE(isf(nsfm),stat=ier)
6082    l_error = l_error .OR. (ier /= 0)
6083    IF (l_error) THEN
6084       WRITE(numout,*) 'Problem with memory allocation: forcing variables isf ',nsfm
6085       STOP 'init_forcing'
6086    ENDIF
6087    ALLOCATE(nf_written(nsft_loc),stat=ier)
6088    l_error = l_error .OR. (ier /= 0)
6089    IF (l_error) THEN
6090       WRITE(numout,*) 'Problem with memory allocation: forcing variables nf_written ',nsft_loc
6091       STOP 'init_forcing'
6092    ENDIF
6093    ALLOCATE(nf_cumul(nsft_loc),stat=ier)
6094    l_error = l_error .OR. (ier /= 0)
6095    IF (l_error) THEN
6096       WRITE(numout,*) 'Problem with memory allocation: forcing variables nf_cumul ',nsft_loc
6097       STOP 'init_forcing'
6098    ENDIF
6099   
6100  !! 2. Allocate memory for the root processor only (parallel computing)
6101
6102    ! Where, ::nbp_glo is the number of global continental points
6103    IF (is_root_prc) THEN
6104       ALLOCATE(clay_fm_g(nbp_glo,nsfm),stat=ier)
6105       l_error = l_error .OR. (ier /= 0)
6106       IF (l_error) THEN
6107          WRITE(numout,*) 'Problem with memory allocation: forcing variables clay_fm_g ',nbp_glo,nsfm
6108          STOP 'init_forcing'
6109       ENDIF
6110       ALLOCATE(silt_fm_g(nbp_glo,nsfm),stat=ier) 
6111       l_error = l_error .OR. (ier /= 0) 
6112       IF (l_error) THEN
6113          WRITE(numout,*) 'Problem with memory allocation: forcing variables silt_fm_g ',nbp_glo,nsfm 
6114          STOP 'init_forcing' 
6115       ENDIF
6116       ALLOCATE(bulk_fm_g(nbp_glo,nsfm),stat=ier) 
6117       l_error = l_error .OR. (ier /= 0) 
6118       IF (l_error) THEN
6119          WRITE(numout,*) 'Problem with memory allocation: forcing variables bulk_fm_g ',nbp_glo,nsfm 
6120          STOP 'init_forcing' 
6121       ENDIF
6122       ALLOCATE(humrel_daily_fm_g(nbp_glo,nvm,nsfm),stat=ier)
6123       l_error = l_error .OR. (ier /= 0)
6124       IF (l_error) THEN
6125          WRITE(numout,*) 'Problem with memory allocation: forcing variables humrel_daily_fm_g ',nbp_glo,nvm,nsfm
6126          STOP 'init_forcing'
6127       ENDIF
6128       ALLOCATE(litterhum_daily_fm_g(nbp_glo,nsfm),stat=ier)
6129       l_error = l_error .OR. (ier /= 0)
6130       IF (l_error) THEN
6131          WRITE(numout,*) 'Problem with memory allocation: forcing variables litterhum_daily_fm_g ',nbp_glo,nsfm
6132          STOP 'init_forcing'
6133       ENDIF
6134       ALLOCATE(t2m_daily_fm_g(nbp_glo,nsfm),stat=ier)
6135       l_error = l_error .OR. (ier /= 0)
6136       IF (l_error) THEN
6137          WRITE(numout,*) 'Problem with memory allocation: forcing variables t2m_daily_fm_g ',nbp_glo,nsfm
6138          STOP 'init_forcing'
6139       ENDIF
6140       ALLOCATE(t2m_min_daily_fm_g(nbp_glo,nsfm),stat=ier)
6141       l_error = l_error .OR. (ier /= 0)
6142       IF (l_error) THEN
6143          WRITE(numout,*) 'Problem with memory allocation: forcing variables t2m_min_daily_fm_g ',nbp_glo,nsfm
6144          STOP 'init_forcing'
6145       ENDIF
6146       ALLOCATE(tsurf_daily_fm_g(nbp_glo,nsfm),stat=ier)
6147       l_error = l_error .OR. (ier /= 0)
6148       IF (l_error) THEN
6149          WRITE(numout,*) 'Problem with memory allocation: forcing variables tsurf_daily_fm_g ',nbp_glo,nsfm
6150          STOP 'init_forcing'
6151       ENDIF
6152       ALLOCATE(tsoil_daily_fm_g(nbp_glo,nbdl,nsfm),stat=ier)
6153       l_error = l_error .OR. (ier /= 0)
6154       IF (l_error) THEN
6155          WRITE(numout,*) 'Problem with memory allocation: forcing variables tsoil_daily_fm_g ',nbp_glo,nbdl,nsfm
6156          STOP 'init_forcing'
6157       ENDIF
6158       ALLOCATE(soilhum_daily_fm_g(nbp_glo,nbdl,nsfm),stat=ier)
6159       l_error = l_error .OR. (ier /= 0)
6160       IF (l_error) THEN
6161          WRITE(numout,*) 'Problem with memory allocation: forcing variables soilhum_daily_fm_g ',nbp_glo,nbdl,nsfm
6162          STOP 'init_forcing'
6163       ENDIF
6164       ALLOCATE(precip_fm_g(nbp_glo,nsfm),stat=ier)
6165       l_error = l_error .OR. (ier /= 0)
6166       IF (l_error) THEN
6167          WRITE(numout,*) 'Problem with memory allocation: forcing variables precip_fm_g ',nbp_glo,nsfm
6168          STOP 'init_forcing'
6169       ENDIF
6170       ALLOCATE(gpp_daily_fm_g(nbp_glo,nvm,nsfm),stat=ier)
6171       l_error = l_error .OR. (ier /= 0)
6172       IF (l_error) THEN
6173          WRITE(numout,*) 'Problem with memory allocation: forcing variables gpp_daily_fm_g ',nbp_glo,nvm,nsfm
6174          STOP 'init_forcing'
6175       ENDIF
6176       ALLOCATE(veget_fm_g(nbp_glo,nvm,nsfm),stat=ier)
6177       l_error = l_error .OR. (ier /= 0)
6178       IF (l_error) THEN
6179          WRITE(numout,*) 'Problem with memory allocation: forcing variables veget_fm_g ',nbp_glo,nvm,nsfm
6180          STOP 'init_forcing'
6181       ENDIF
6182       ALLOCATE(veget_max_fm_g(nbp_glo,nvm,nsfm),stat=ier)
6183       l_error = l_error .OR. (ier /= 0)
6184       IF (l_error) THEN
6185          WRITE(numout,*) 'Problem with memory allocation: forcing variables veget_max_fm_g ',nbp_glo,nvm,nsfm
6186          STOP 'init_forcing'
6187       ENDIF
6188!!$       ALLOCATE(lai_fm_g(nbp_glo,nvm,nsfm),stat=ier)
6189!!$       l_error = l_error .OR. (ier /= 0)
6190!!$       IF (l_error) THEN
6191!!$          WRITE(numout,*) 'Problem with memory allocation: forcing variables lai_fm_g ',nbp_glo,nvm,nsfm
6192!!$          STOP 'init_forcing'
6193!!$       ENDIF
6194       ALLOCATE(drainage_fm_g(nbp_glo,nvm,nsfm),stat=ier) 
6195       l_error = l_error .OR. (ier /= 0) 
6196       IF (l_error) THEN
6197          WRITE(numout,*) 'Problem with memory allocation: forcing variables drainage_fm_g ',nbp_glo,nvm,nsfm 
6198          STOP 'init_forcing' 
6199       ENDIF
6200    ELSE
6201       ! Allocate memory for co-processors
6202       ALLOCATE(clay_fm_g(0,nsfm),stat=ier)
6203       ALLOCATE(silt_fm_g(0,nsfm),stat=ier) 
6204       ALLOCATE(bulk_fm_g(0,nsfm),stat=ier) 
6205       ALLOCATE(humrel_daily_fm_g(0,nvm,nsfm),stat=ier)
6206       ALLOCATE(litterhum_daily_fm_g(0,nsfm),stat=ier)
6207       ALLOCATE(t2m_daily_fm_g(0,nsfm),stat=ier)
6208       ALLOCATE(t2m_min_daily_fm_g(0,nsfm),stat=ier)
6209       ALLOCATE(tsurf_daily_fm_g(0,nsfm),stat=ier)
6210       ALLOCATE(tsoil_daily_fm_g(0,nbdl,nsfm),stat=ier)
6211       ALLOCATE(soilhum_daily_fm_g(0,nbdl,nsfm),stat=ier)
6212       ALLOCATE(precip_fm_g(0,nsfm),stat=ier)
6213       ALLOCATE(gpp_daily_fm_g(0,nvm,nsfm),stat=ier)
6214       ALLOCATE(veget_fm_g(0,nvm,nsfm),stat=ier)
6215       ALLOCATE(veget_max_fm_g(0,nvm,nsfm),stat=ier)
6216!!$       ALLOCATE(lai_fm_g(0,nvm,nsfm),stat=ier)
6217       ALLOCATE(drainage_fm_g(0,nvm,nsfm),stat=ier) 
6218    ENDIF ! is_root_proc
6219   
6220    IF (l_error) THEN
6221       WRITE(numout,*) 'Problem with memory allocation: forcing variables'
6222       STOP 'init_forcing'
6223    ENDIF
6224
6225  !! 3. Initialize variables
6226
6227    CALL forcing_zero
6228   
6229  END SUBROUTINE init_forcing
6230
6231
6232!! ================================================================================================================================
6233!! SUBROUTINE   : forcing_zero
6234!!
6235!>\BRIEF        Initialize variables containing the forcing data; variables are
6236!! set to zero.
6237!!
6238!! DESCRIPTION  : None
6239!!
6240!! RECENT CHANGE(S) : None
6241!!
6242!! MAIN OUTPUT VARIABLE(S): None
6243!!
6244!! REFERENCES   : None
6245!!
6246!! FLOWCHART    : None
6247!! \n
6248!_ ================================================================================================================================
6249 
6250  SUBROUTINE forcing_zero
6251   
6252    clay_fm(:,:) = zero
6253    silt_fm(:,:) = zero 
6254    bulk_fm(:,:) = zero 
6255    humrel_daily_fm(:,:,:) = zero
6256    litterhum_daily_fm(:,:) = zero
6257    t2m_daily_fm(:,:) = zero
6258    t2m_min_daily_fm(:,:) = zero
6259    tsurf_daily_fm(:,:) = zero
6260    tsoil_daily_fm(:,:,:) = zero
6261    soilhum_daily_fm(:,:,:) = zero
6262    precip_fm(:,:) = zero
6263    gpp_daily_fm(:,:,:) = zero
6264    veget_fm(:,:,:) = zero
6265    veget_max_fm(:,:,:) = zero
6266!!$    lai_fm(:,:,:) = zero
6267    drainage_fm(:,:,:) = zero     
6268  END SUBROUTINE forcing_zero
6269
6270
6271!! ================================================================================================================================
6272!! SUBROUTINE   : forcing_write
6273!!
6274!>\BRIEF        Appends data values to a netCDF file containing the forcing
6275!! variables of the general processes in stomate.
6276!!
6277!! DESCRIPTION  : None
6278!!
6279!! RECENT CHANGE(S) : None
6280!!
6281!! MAIN OUTPUT VARIABLE(S): netCDF file
6282!!
6283!! REFERENCES   : None
6284!!
6285!! FLOWCHART    : None
6286!! \n
6287!_ ================================================================================================================================
6288 
6289  SUBROUTINE forcing_write(forcing_id,ibeg,iend)
6290   
6291  !! 0. Variable and parameter declaration
6292
6293    !! 0.1 Input variables
6294
6295    INTEGER(i_std),INTENT(in)      :: forcing_id  !! File identifer of forcing file, assigned when netcdf is created
6296    INTEGER(i_std),INTENT(in)      :: ibeg, iend  !! First and last time step to be written
6297
6298    !! 0.2 Output variables
6299
6300    !! 0.3 Modified variables
6301
6302    !! 0.4 Local variables
6303
6304    INTEGER(i_std)                 :: ii          !! Index of isf where isf is the number of time steps that can be
6305                                                  !! stored in memory
6306    INTEGER(i_std)                 :: iblocks     !! Index of block that is written
6307    INTEGER(i_std)                 :: nblocks     !! Number of blocks that needs to be written
6308    INTEGER(i_std)                 :: ier         !! Check errors in netcdf call
6309    INTEGER(i_std),DIMENSION(0:2)  :: ifirst      !! First block in memory - changes with iblocks
6310    INTEGER(i_std),DIMENSION(0:2)  :: ilast       !! Last block in memory - changes with iblocks
6311    INTEGER(i_std),PARAMETER       :: ndm = 10    !! Maximum number of dimensions
6312    INTEGER(i_std),DIMENSION(ndm)  :: start       !! First block to write
6313    INTEGER(i_std)                 :: ndim        !! Dimensions of forcing to be added to the netCDF
6314    INTEGER(i_std),DIMENSION(ndm)  :: count_force !! Number of elements in each dimension 
6315    INTEGER(i_std)                 :: vid         !! Variable identifer of netCDF
6316!_ ================================================================================================================================
6317   
6318  !! 1. Determine number of blocks of forcing variables that are stored in memory
6319
6320    nblocks = 0
6321    ifirst(:) = 1
6322    ilast(:) = 1
6323    DO ii = ibeg, iend
6324       IF (     (nblocks /= 0) &
6325            &      .AND.(isf(ii) == isf(ilast(nblocks))+1)) THEN
6326          ! Last block found
6327          ilast(nblocks) = ii
6328       ELSE
6329          ! First block found
6330          nblocks = nblocks+1
6331          IF (nblocks > 2)  STOP 'Problem in forcing_write'
6332          ifirst(nblocks) = ii
6333          ilast(nblocks) = ii
6334       ENDIF
6335    ENDDO
6336
6337  !! 2. Gather distributed variables (parallel computing)
6338
6339    CALL gather(clay_fm,clay_fm_g)
6340    CALL gather(silt_fm,silt_fm_g) 
6341    CALL gather(bulk_fm,bulk_fm_g) 
6342    CALL gather(humrel_daily_fm,humrel_daily_fm_g)
6343    CALL gather(litterhum_daily_fm,litterhum_daily_fm_g)
6344    CALL gather(t2m_daily_fm,t2m_daily_fm_g)
6345    CALL gather(t2m_min_daily_fm,t2m_min_daily_fm_g)
6346    CALL gather(tsurf_daily_fm,tsurf_daily_fm_g)
6347    CALL gather(tsoil_daily_fm,tsoil_daily_fm_g)
6348    CALL gather(soilhum_daily_fm,soilhum_daily_fm_g)
6349    CALL gather(precip_fm,precip_fm_g)
6350    CALL gather(gpp_daily_fm,gpp_daily_fm_g)
6351    CALL gather(veget_fm,veget_fm_g)
6352    CALL gather(veget_max_fm,veget_max_fm_g)
6353!!$    CALL gather(lai_fm,lai_fm_g)
6354    CALL gather(drainage_fm,drainage_fm_g) 
6355 !! 3. Append data to netCDF file
6356   
6357    IF (is_root_prc) THEN
6358       ! The netCDF file has been created earlier in this module, a file ID is available
6359       ! and variables and dimensions have already been defined
6360       DO iblocks = 1, nblocks
6361          IF (ifirst(iblocks) /= ilast(iblocks)) THEN
6362             ndim = 2
6363             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6364             count_force(1:ndim) = SHAPE(clay_fm_g)
6365             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6366             ier = NF90_INQ_VARID (forcing_id,'clay',vid)
6367             ier = NF90_PUT_VAR (forcing_id,vid, &
6368                  &              clay_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
6369                  & start=start(1:ndim), count=count_force(1:ndim))
6370             ndim = 2 
6371             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks)); 
6372             count_force(1:ndim) = SHAPE(silt_fm_g) 
6373             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1 
6374             ier = NF90_INQ_VARID (forcing_id,'silt',vid) 
6375             ier = NF90_PUT_VAR (forcing_id,vid, & 
6376                  &              silt_fm_g(:,ifirst(iblocks):ilast(iblocks)), & 
6377                  & start=start(1:ndim), count=count_force(1:ndim)) 
6378             ndim = 2 
6379             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks)); 
6380             count_force(1:ndim) = SHAPE(bulk_fm_g) 
6381             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1 
6382             ier = NF90_INQ_VARID (forcing_id,'bulk',vid) 
6383             ier = NF90_PUT_VAR (forcing_id,vid, & 
6384                  &              bulk_fm_g(:,ifirst(iblocks):ilast(iblocks)), & 
6385                  & start=start(1:ndim), count=count_force(1:ndim)) 
6386
6387             ndim = 3;
6388             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6389             count_force(1:ndim) = SHAPE(humrel_daily_fm_g)
6390             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6391             ier = NF90_INQ_VARID (forcing_id,'humrel',vid)
6392             ier = NF90_PUT_VAR (forcing_id, vid, &
6393                  &            humrel_daily_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
6394                  &            start=start(1:ndim), count=count_force(1:ndim))
6395             ndim = 2;
6396             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6397             count_force(1:ndim) = SHAPE(litterhum_daily_fm_g)
6398             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6399             ier = NF90_INQ_VARID (forcing_id,'litterhum',vid)
6400             ier = NF90_PUT_VAR (forcing_id, vid, &
6401                  &            litterhum_daily_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
6402                  & start=start(1:ndim), count=count_force(1:ndim))
6403             ndim = 2;
6404             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6405             count_force(1:ndim) = SHAPE(t2m_daily_fm_g)
6406             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6407             ier = NF90_INQ_VARID (forcing_id,'t2m',vid)
6408             ier = NF90_PUT_VAR (forcing_id, vid, &
6409                  &            t2m_daily_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
6410                  & start=start(1:ndim), count=count_force(1:ndim))
6411             ndim = 2;
6412             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6413             count_force(1:ndim) = SHAPE(t2m_min_daily_fm_g)
6414             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6415             ier = NF90_INQ_VARID (forcing_id,'t2m_min',vid)
6416             ier = NF90_PUT_VAR (forcing_id, vid, &
6417                  &            t2m_min_daily_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
6418                  & start=start(1:ndim), count=count_force(1:ndim))
6419             ndim = 2;
6420             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6421             count_force(1:ndim) = SHAPE(tsurf_daily_fm_g)
6422             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6423             ier = NF90_INQ_VARID (forcing_id,'tsurf',vid)
6424             ier = NF90_PUT_VAR (forcing_id, vid, &
6425                  &            tsurf_daily_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
6426                  & start=start(1:ndim), count=count_force(1:ndim))
6427             ndim = 3;
6428             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6429             count_force(1:ndim) = SHAPE(tsoil_daily_fm_g)
6430             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6431             ier = NF90_INQ_VARID (forcing_id,'tsoil',vid)
6432             ier = NF90_PUT_VAR (forcing_id, vid, &
6433                  &            tsoil_daily_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
6434                  & start=start(1:ndim), count=count_force(1:ndim))
6435             ndim = 3;
6436             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6437             count_force(1:ndim) = SHAPE(soilhum_daily_fm_g)
6438             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6439             ier = NF90_INQ_VARID (forcing_id,'soilhum',vid)
6440             ier = NF90_PUT_VAR (forcing_id, vid, &
6441                  &            soilhum_daily_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
6442                  & start=start(1:ndim), count=count_force(1:ndim))
6443             ndim = 2;
6444             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6445             count_force(1:ndim) = SHAPE(precip_fm_g)
6446             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6447             ier = NF90_INQ_VARID (forcing_id,'precip',vid)
6448             ier = NF90_PUT_VAR (forcing_id, vid, &
6449                  &            precip_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
6450                  & start=start(1:ndim), count=count_force(1:ndim))
6451             ndim = 3;
6452             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6453             count_force(1:ndim) = SHAPE(gpp_daily_fm_g)
6454             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6455             ier = NF90_INQ_VARID (forcing_id,'gpp',vid)
6456             ier = NF90_PUT_VAR (forcing_id, vid, &
6457                  &            gpp_daily_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
6458                  &            start=start(1:ndim), count=count_force(1:ndim))
6459             ndim = 3;
6460             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6461             count_force(1:ndim) = SHAPE(veget_fm_g)
6462             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6463             ier = NF90_INQ_VARID (forcing_id,'veget',vid)
6464             ier = NF90_PUT_VAR (forcing_id, vid, &
6465                  &            veget_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
6466                  &            start=start(1:ndim), count=count_force(1:ndim))
6467             ndim = 3;
6468             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6469             count_force(1:ndim) = SHAPE(veget_max_fm_g)
6470             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6471             ier = NF90_INQ_VARID (forcing_id,'veget_max',vid)
6472             ier = NF90_PUT_VAR (forcing_id, vid, &
6473                  &            veget_max_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
6474                  &            start=start(1:ndim), count=count_force(1:ndim))
6475!!$             ndim = 3;
6476!!$             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6477!!$             count_force(1:ndim) = SHAPE(lai_fm_g)
6478!!$             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6479!!$             ier = NF90_INQ_VARID (forcing_id,'lai',vid)
6480!!$             ier = NF90_PUT_VAR (forcing_id, vid, &
6481!!$                  &            lai_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
6482!!$                  &            start=start(1:ndim), count=count_force(1:ndim))
6483             ndim = 2; 
6484             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks)); 
6485             count_force(1:ndim) = SHAPE(drainage_fm_g) 
6486             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1 
6487             ier = NF90_INQ_VARID (forcing_id,'drainage',vid) 
6488             ier = NF90_PUT_VAR (forcing_id, vid, & 
6489                  &            drainage_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), & 
6490                  &            start=start(1:ndim), count=count_force(1:ndim)) 
6491          ENDIF
6492       ENDDO
6493    ENDIF
6494   
6495  !! 4. Adjust flag of forcing file
6496    nf_written(isf(:)) = .TRUE.
6497
6498  END SUBROUTINE forcing_write
6499
6500 
6501!! ================================================================================================================================
6502!! SUBROUTINE   : stomate_forcing_read
6503!!
6504!>\BRIEF        Read forcing file.
6505!!
6506!! DESCRIPTION  : None
6507!!
6508!! RECENT CHANGE(S) : None
6509!!
6510!! MAIN OUTPUT VARIABLE(S): None
6511!!
6512!! REFERENCES   : None
6513!!
6514!! FLOWCHART    : None
6515!! \n
6516!_ ================================================================================================================================
6517 
6518  SUBROUTINE stomate_forcing_read(forcing_id,nsfm)
6519   
6520  !! 0. Variable and parameter declaration
6521
6522    !! 0.1 Input variables
6523
6524    INTEGER(i_std),INTENT(in)  :: forcing_id           !! File identifer of forcing file, assigned when netcdf is created
6525    INTEGER(i_std),INTENT(in)  :: nsfm                 !! Number of time steps stored in memory       
6526   
6527    !! 0.2 Output variables
6528
6529    !! 0.3 Modified variables
6530
6531    !! 0.4 Local variables
6532
6533    INTEGER(i_std)                 :: ii                !! Index of isf where isf is the number of time steps that can be stored in
6534                                                        !! memory
6535    INTEGER(i_std)                 :: iblocks           !! Index of block that is written
6536    INTEGER(i_std)                 :: nblocks           !! Number of blocks that needs to be written
6537    INTEGER(i_std)                 :: ier               !! Check error of netcdf call
6538    INTEGER(i_std),DIMENSION(0:2)  :: ifirst            !! First block in memory - changes with iblocks
6539    INTEGER(i_std),DIMENSION(0:2)  :: ilast             !! Last block in memory - changes with iblocks
6540    INTEGER(i_std),PARAMETER       :: ndm = 10          !! Maximum number of dimensions
6541    INTEGER(i_std),DIMENSION(ndm)  :: start             !! First block to write
6542    INTEGER(i_std)                 :: ndim              !! Dimensions of forcing to be added to the netCDF
6543    INTEGER(i_std),DIMENSION(ndm)  :: count_force       !! Number of elements in each dimension
6544    INTEGER(i_std)                 :: vid               !! Variable identifer of netCDF
6545    LOGICAL, PARAMETER             :: check=.FALSE.     !! Flag for debugging
6546    LOGICAL                        :: a_er=.FALSE.      !! Error catching from netcdf file
6547!_ ================================================================================================================================
6548
6549    IF (check) WRITE(numout,*) "stomate_forcing_read "
6550   
6551  !! 1. Set to zero if the corresponding forcing state
6552
6553    ! has not yet been written into the file 
6554    DO ii = 1, nsfm
6555       IF (.NOT.nf_written(isf(ii))) THEN
6556          clay_fm(:,ii) = zero
6557          silt_fm(:,iisf) = zero 
6558          bulk_fm(:,iisf) = zero 
6559          humrel_daily_fm(:,:,ii) = zero
6560          litterhum_daily_fm(:,ii) = zero
6561          t2m_daily_fm(:,ii) = zero
6562          t2m_min_daily_fm(:,ii) = zero
6563          tsurf_daily_fm(:,ii) = zero
6564          tsoil_daily_fm(:,:,ii) = zero
6565          soilhum_daily_fm(:,:,ii) = zero
6566          precip_fm(:,ii) = zero
6567          gpp_daily_fm(:,:,ii) = zero
6568          veget_fm(:,:,ii) = zero
6569          veget_max_fm(:,:,ii) = zero
6570!!$          lai_fm(:,:,ii) = zero
6571          drainage_fm(:,:,iisf) = zero 
6572       ENDIF
6573    ENDDO
6574   
6575  !! 2. determine blocks of forcing states that are contiguous in memory
6576
6577    nblocks = 0
6578    ifirst(:) = 1
6579    ilast(:) = 1
6580   
6581    DO ii = 1, nsfm
6582       IF (nf_written(isf(ii))) THEN
6583          IF (     (nblocks /= 0) &
6584               &        .AND.(isf(ii) == isf(ilast(nblocks))+1)) THEN
6585
6586             ! element is contiguous with last element found
6587             ilast(nblocks) = ii
6588          ELSE
6589
6590             ! found first element of new block
6591             nblocks = nblocks+1
6592             IF (nblocks > 2)  STOP 'Problem in stomate_forcing_read'
6593             
6594             ifirst(nblocks) = ii
6595             ilast(nblocks) = ii
6596          ENDIF
6597       ENDIF
6598    ENDDO
6599    IF (check) WRITE(numout,*) "stomate_forcing_read nblocks, ifirst, ilast",nblocks, ifirst, ilast
6600   
6601  !! 3. Read variable values
6602
6603    IF (is_root_prc) THEN
6604       DO iblocks = 1, nblocks
6605          IF (check) WRITE(numout,*) "stomate_forcing_read iblocks, ifirst(iblocks), ilast(iblocks)",iblocks, &
6606               ifirst(iblocks), ilast(iblocks)
6607          IF (ifirst(iblocks) /= ilast(iblocks)) THEN
6608             a_er=.FALSE.
6609             ndim = 2;
6610             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6611             count_force(1:ndim) = SHAPE(clay_fm_g)
6612             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6613             ier = NF90_INQ_VARID (forcing_id,'clay',vid)
6614             a_er = a_er.OR.(ier /= 0)
6615             ier = NF90_GET_VAR (forcing_id, vid, &
6616                  &            clay_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
6617                  &            start=start(1:ndim), count=count_force(1:ndim))
6618             a_er = a_er.OR.(ier /= 0)
6619
6620
6621             ndim = 2; 
6622             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks)); 
6623             count_force(1:ndim) = SHAPE(silt_fm_g) 
6624             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1 
6625             ier = NF90_INQ_VARID (forcing_id,'silt',vid) 
6626             a_er = a_er.OR.(ier /= 0) 
6627             ier = NF90_GET_VAR (forcing_id, vid, & 
6628                  &            silt_fm_g(:,ifirst(iblocks):ilast(iblocks)), & 
6629                  &            start=start(1:ndim), count=count_force(1:ndim)) 
6630             a_er = a_er.OR.(ier /= 0) 
6631             
6632             ndim = 2; 
6633             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks)); 
6634             count_force(1:ndim) = SHAPE(bulk_fm_g) 
6635             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1 
6636             ier = NF90_INQ_VARID (forcing_id,'bulk',vid) 
6637             a_er = a_er.OR.(ier /= 0) 
6638             ier = NF90_GET_VAR (forcing_id, vid, & 
6639                  &            bulk_fm_g(:,ifirst(iblocks):ilast(iblocks)), & 
6640                  &            start=start(1:ndim), count=count_force(1:ndim)) 
6641             a_er = a_er.OR.(ier /= 0) 
6642             
6643             ndim = 3;
6644             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6645             count_force(1:ndim) = SHAPE(humrel_daily_fm_g)
6646             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6647             ier = NF90_INQ_VARID (forcing_id,'humrel',vid)
6648             a_er = a_er.OR.(ier /= 0)
6649             ier = NF90_GET_VAR (forcing_id, vid, &
6650                  &            humrel_daily_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
6651                  &            start=start(1:ndim), count=count_force(1:ndim))
6652             a_er = a_er.OR.(ier /= 0)
6653
6654             ndim = 2;
6655             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6656             count_force(1:ndim) = SHAPE(litterhum_daily_fm_g)
6657             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6658             ier = NF90_INQ_VARID (forcing_id,'litterhum',vid)
6659             a_er = a_er.OR.(ier /= 0)
6660             ier = NF90_GET_VAR (forcing_id, vid, &
6661                  &              litterhum_daily_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
6662                  &            start=start(1:ndim), count=count_force(1:ndim))
6663             a_er = a_er.OR.(ier /= 0)
6664
6665             ndim = 2;
6666             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6667             count_force(1:ndim) = SHAPE(t2m_daily_fm_g)
6668             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6669             ier = NF90_INQ_VARID (forcing_id,'t2m',vid)
6670             a_er = a_er.OR.(ier /= 0)
6671             ier = NF90_GET_VAR (forcing_id, vid, &
6672                  &              t2m_daily_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
6673                  &            start=start(1:ndim), count=count_force(1:ndim))
6674             a_er = a_er.OR.(ier /= 0)
6675
6676             ndim = 2;
6677             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6678             count_force(1:ndim) = SHAPE(t2m_min_daily_fm_g)
6679             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6680             ier = NF90_INQ_VARID (forcing_id,'t2m_min',vid)
6681             a_er = a_er.OR.(ier /= 0)
6682             ier = NF90_GET_VAR (forcing_id, vid, &
6683                  &              t2m_min_daily_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
6684                  &            start=start(1:ndim), count=count_force(1:ndim))
6685             a_er = a_er.OR.(ier /= 0)
6686
6687             ndim = 2;
6688             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6689             count_force(1:ndim) = SHAPE(tsurf_daily_fm_g)
6690             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6691             ier = NF90_INQ_VARID (forcing_id,'tsurf',vid)
6692             a_er = a_er.OR.(ier /= 0)
6693             ier = NF90_GET_VAR (forcing_id, vid, &
6694                  &              tsurf_daily_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
6695                  &            start=start(1:ndim), count=count_force(1:ndim))
6696             a_er = a_er.OR.(ier /= 0)
6697
6698             ndim = 3;
6699             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6700             count_force(1:ndim) = SHAPE(tsoil_daily_fm_g)
6701             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6702             ier = NF90_INQ_VARID (forcing_id,'tsoil',vid)
6703             a_er = a_er.OR.(ier /= 0)
6704             ier = NF90_GET_VAR (forcing_id, vid, &
6705                  &              tsoil_daily_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
6706                  &            start=start(1:ndim), count=count_force(1:ndim))
6707             a_er = a_er.OR.(ier /= 0)
6708
6709             ndim = 3;
6710             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6711             count_force(1:ndim) = SHAPE(soilhum_daily_fm_g)
6712             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6713             ier = NF90_INQ_VARID (forcing_id,'soilhum',vid)
6714             a_er = a_er.OR.(ier /= 0)
6715             ier = NF90_GET_VAR (forcing_id, vid, &
6716                  &              soilhum_daily_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
6717                  &            start=start(1:ndim), count=count_force(1:ndim))
6718             a_er = a_er.OR.(ier /= 0)
6719
6720             ndim = 2;
6721             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6722             count_force(1:ndim) = SHAPE(precip_fm_g)
6723             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6724             ier = NF90_INQ_VARID (forcing_id,'precip',vid)
6725             a_er = a_er.OR.(ier /= 0)
6726             ier = NF90_GET_VAR (forcing_id, vid, &
6727                  &              precip_fm_g(:,ifirst(iblocks):ilast(iblocks)), &
6728                  &            start=start(1:ndim), count=count_force(1:ndim))
6729             a_er = a_er.OR.(ier /= 0)
6730
6731             ndim = 3;
6732             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6733             count_force(1:ndim) = SHAPE(gpp_daily_fm_g)
6734             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6735             ier = NF90_INQ_VARID (forcing_id,'gpp',vid)
6736             a_er = a_er.OR.(ier /= 0)
6737             ier = NF90_GET_VAR (forcing_id, vid, &
6738                  &            gpp_daily_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
6739                  &            start=start(1:ndim), count=count_force(1:ndim))
6740             a_er = a_er.OR.(ier /= 0)
6741
6742             ndim = 3;
6743             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6744             count_force(1:ndim) = SHAPE(veget_fm_g)
6745             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6746             ier = NF90_INQ_VARID (forcing_id,'veget',vid)
6747             a_er = a_er.OR.(ier /= 0)
6748             ier = NF90_GET_VAR (forcing_id, vid, &
6749                  &            veget_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
6750                  &            start=start(1:ndim), count=count_force(1:ndim))
6751             a_er = a_er.OR.(ier /= 0)
6752
6753             ndim = 3;
6754             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6755             count_force(1:ndim) = SHAPE(veget_max_fm_g)
6756             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6757             ier = NF90_INQ_VARID (forcing_id,'veget_max',vid)
6758             a_er = a_er.OR.(ier /= 0)
6759             ier = NF90_GET_VAR (forcing_id, vid, &
6760                  &            veget_max_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
6761                  &            start=start(1:ndim), count=count_force(1:ndim))
6762             a_er = a_er.OR.(ier /= 0)
6763
6764!!$             ndim = 3;
6765!!$             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks));
6766!!$             count_force(1:ndim) = SHAPE(lai_fm_g)
6767!!$             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1
6768!!$             ier = NF90_INQ_VARID (forcing_id,'lai',vid)
6769!!$             a_er = a_er.OR.(ier /= 0)
6770!!$             ier = NF90_GET_VAR (forcing_id, vid, &
6771!!$                  &            lai_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
6772!!$                  &            start=start(1:ndim), count=count_force(1:ndim))
6773!!$             a_er = a_er.OR.(ier /= 0)
6774
6775             ndim = 2; 
6776             start(1:ndim) = 1; start(ndim) = isf(ifirst(iblocks)); 
6777             count_force(1:ndim) = SHAPE(drainage_fm_g) 
6778             count_force(ndim) = isf(ilast(iblocks))-isf(ifirst(iblocks))+1 
6779             ier = NF90_INQ_VARID (forcing_id,'drainage',vid) 
6780             a_er = a_er.OR.(ier /= 0) 
6781             ier = NF90_GET_VAR (forcing_id, vid, & 
6782                  &            drainage_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), & 
6783                  &            start=start(1:ndim), count=count_force(1:ndim)) 
6784             a_er = a_er.OR.(ier /= 0) 
6785             IF (a_er) THEN
6786                CALL ipslerr_p (3,'stomate_forcing_read', &
6787                     &        'PROBLEM when read forcing file', &
6788                     &        '','')
6789             ENDIF
6790
6791          ENDIF ! (ifirst(iblocks) /= ilast(iblocks))
6792       ENDDO ! iblocks
6793    ENDIF ! is_root_prc
6794
6795  !! 4. Distribute the variable over several processors
6796
6797    CALL scatter(clay_fm_g,clay_fm)
6798    CALL scatter(silt_fm_g,silt_fm) 
6799    CALL scatter(bulk_fm_g,bulk_fm) 
6800    CALL scatter(humrel_daily_fm_g,humrel_daily_fm)
6801    CALL scatter(litterhum_daily_fm_g,litterhum_daily_fm)
6802    CALL scatter(t2m_daily_fm_g,t2m_daily_fm)
6803    CALL scatter(t2m_min_daily_fm_g,t2m_min_daily_fm)
6804    CALL scatter(tsurf_daily_fm_g,tsurf_daily_fm)
6805    CALL scatter(tsoil_daily_fm_g,tsoil_daily_fm)
6806    CALL scatter(soilhum_daily_fm_g,soilhum_daily_fm)
6807    CALL scatter(precip_fm_g,precip_fm)
6808    CALL scatter(gpp_daily_fm_g,gpp_daily_fm)
6809    CALL scatter(veget_fm_g,veget_fm)
6810    CALL scatter(veget_max_fm_g,veget_max_fm)
6811!!$    CALL scatter(lai_fm_g,lai_fm)
6812    CALL scatter(drainage_fm_g,drainage_fm) 
6813  END SUBROUTINE stomate_forcing_read
6814
6815
6816!! ================================================================================================================================
6817!! SUBROUTINE   : setlai
6818!!
6819!>\BRIEF        Routine to force the lai in STOMATE. The code in this routine
6820!! simply CALCULATES lai and is therefore not functional. The routine should be
6821!! rewritten if one wants to force lai. Forcing lai with the new allocation is
6822!! not straightforward and would quickly (after 5 years ?) result in serious
6823!! inconsistencies
6824!!
6825!! DESCRIPTION  : None
6826!!
6827!! RECENT CHANGE(S) : None
6828!!
6829!! MAIN OUTPUT VARIABLE(S): ::lai
6830!!
6831!! REFERENCE(S) : None
6832!!
6833!! FLOWCHART : None
6834!! \n
6835!_ ================================================================================================================================
6836 
6837!!$  SUBROUTINE setlai(kjpindex,lai, circ_class_biomass, circ_class_n)
6838!!$
6839!!$  !! 0 Variable and parameter declaration
6840!!$ 
6841!!$    !! 0.1 Input variables
6842!!$
6843!!$    INTEGER(i_std),INTENT(in)                    :: kjpindex      !! Domain size - number of pixels (unitless)
6844!!$    REAL(r_std), DIMENSION(:,:,:,:,:), INTENT(in)  :: circ_class_biomass   !! Biomass per PFT @tex $(gC m^{-2})$ @endtex
6845!!$    REAL(r_std), DIMENSION(:,:,:), INTENT(in)  :: circ_class_n   !! Biomass per PFT @tex $(gC m^{-2})$ @endtex
6846!!$    !! 0.2 Output variables
6847!!$
6848!!$    REAL(r_std),DIMENSION(kjpindex,nvm), INTENT(out)  :: lai      !! PFT leaf area index @tex $(m^{2} m^{-2})$ @endtex
6849!!$
6850!!$    !! 0.3 Modified variables
6851!!$
6852!!$    !! 0.4 Local variables
6853!!$
6854!!$    INTEGER(i_std)                               :: j,i         !! index (unitless)
6855!!$!_ ================================================================================================================================
6856!!$   
6857!!$    !! 1. Set lai for bare soil to zero
6858!!$
6859!!$    lai(:,ibare_sechiba) = zero
6860!!$
6861!!$    !! 2. Multiply foliage biomass by sla to calculate lai for all PFTs and pixels
6862!!$    DO i=1, kjpindex
6863!!$        DO j=2,nvm
6864!!$            lai(i,j) = cc_to_lai(circ_class_biomass(i,j,:,ileaf,icarbon),circ_class_n(i,j,:),j)
6865!!$        ENDDO
6866!!$    ENDDO
6867!!$  END SUBROUTINE setlai
6868
6869
6870END MODULE stomate
Note: See TracBrowser for help on using the repository browser.