source: tags/ORCHIDEE_4_1/ORCHIDEE/src_stomate/stomate.f90 @ 7761

Last change on this file since 7761 was 7686, checked in by sebastiaan.luyssaert, 2 years ago

Contributes to #814. This commit has not been tested for the two test cases with interacting disturbances.

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