source: branches/ORCHIDEE_3_CMIP6/ORCHIDEE/src_stomate/stomate_io.f90 @ 8367

Last change on this file since 8367 was 7245, checked in by nicolas.vuichard, 3 years ago

improve Carbon mass balance closure. See ticket #785

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 115.7 KB
Line 
1
2! =================================================================================================================================
3! MODULE       : stomate_io
4!
5! CONTACT      : orchidee-help _at_ listes.ipsl.fr
6!
7! LICENCE      : IPSL (2006)
8! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
9!
10!>\BRIEF       Module for read and write of restart files for all stomate modules.
11!!
12!!\n DESCRIPTION : This module contains the subroutines readstart and writerestart. All variables that will be read or written
13!!                 are passed as argument to the subroutines. The subroutine readstart is called from stomate_initialize and
14!!                 writerestart is called from stomate_finalize.
15!!                 Note: Not all variables saved in the start files are absolutely necessary. However, Sechiba's and Stomate's
16!!                 PFTs are not necessarily identical, and for that case this information needs to be saved.
17!!
18!!
19!! RECENT CHANGE(S) : None
20!!
21!! REFERENCE(S) : None
22!!
23!! SVN :
24!! $HeadURL$
25!! $Date$
26!! $Revision$
27!! \n
28!_ ================================================================================================================================
29MODULE stomate_io
30  USE stomate_data
31  USE constantes
32  USE constantes_soil
33  USE mod_orchidee_para
34  USE ioipsl_para 
35  !-
36  IMPLICIT NONE
37  !-
38  PRIVATE
39  PUBLIC readstart, writerestart
40  !-
41  ! reference temperature (K)
42  !-
43  REAL(r_std),ALLOCATABLE,DIMENSION(:),SAVE :: trefe
44!$OMP THREADPRIVATE(trefe)
45  !-
46CONTAINS
47
48!! ================================================================================================================================
49!! SUBROUTINE   : readstart
50!!
51!>\BRIEF        Read all variables for stomate from restart file.
52!!
53!! DESCRIPTION  : Read all variables for stomate from restart file.
54!!                Initialize the variables if they were not found in the restart file or if there was no restart file.
55!!               
56!! \n
57!_ ================================================================================================================================
58
59  SUBROUTINE readstart &
60       & (npts, index, lalo, resolution, temp_air, dt_days, date_loc, &
61       &  ind, adapted, regenerate, moiavail_daily, gdd_init_date, litterhum_daily, &
62       &  t2m_daily, t2m_min_daily, tsurf_daily, tsoil_daily, &
63       &  soilhum_daily, precip_daily, &
64       &  gpp_daily, npp_daily, turnover_daily, &
65       &  moiavail_month, moiavail_week, moiavail_growingseason, t2m_longterm, tau_longterm, &
66       &  t2m_month, t2m_week, tsoil_month, soilhum_month, &
67       &  fireindex, firelitter, &
68       &  maxmoiavail_lastyear, maxmoiavail_thisyear, &
69       &  minmoiavail_lastyear, minmoiavail_thisyear, &
70       &  maxgppweek_lastyear, maxgppweek_thisyear, &
71       &  gdd0_lastyear, gdd0_thisyear, precip_lastyear, precip_thisyear, &
72       &  gdd_m5_dormance,  gdd_from_growthinit, gdd_midwinter, ncd_dormance, ngd_minus5, &
73       &  PFTpresent, npp_longterm, croot_longterm, lm_lastyearmax, lm_thisyearmax, &
74       &  maxfpc_lastyear, maxfpc_thisyear, &
75       &  turnover_longterm, gpp_week, biomass, resp_maint_part, &
76       &  leaf_age, leaf_frac, senescence, when_growthinit, age, &
77       &  resp_hetero, resp_maint, resp_growth,resp_excess, co2_fire, co2_to_bm_dgvm, &
78       &  n_to_bm, veget_lastlight, everywhere, need_adjacent, RIP_time, &
79       &  time_hum_min, hum_min_dormance, &
80       &  litter, dead_leaves, &
81       &  som, lignin_struc, lignin_wood, turnover_time, &
82       &  co2_flux, fco2_lu, fco2_wh, fco2_ha, &
83       &  prod10,prod100,flux10, flux100, &
84       &  convflux, cflux_prod10, cflux_prod100, &
85       &  prod10_harvest,prod100_harvest,flux10_harvest, flux100_harvest, &
86       &  convflux_harvest, cflux_prod10_harvest, cflux_prod100_harvest, &
87       &  convfluxpft, fDeforestToProduct, fLulccResidue, fHarvestToProduct, &
88       &  woodharvestpft, bm_to_litter, tree_bm_to_litter, carb_mass_total, nflux_prod,&
89       &  nflux_prod_harvest, Tseason, Tseason_length, Tseason_tmp, & 
90       &  Tmin_spring_time, begin_leaves, onset_date, &
91       &  global_years, ok_equilibrium, nbp_accu, nbp_flux, &
92       &  MatrixV, VectorU, previous_stock, current_stock, assim_param, &
93       &  CN_som_litter_longterm, tau_CN_longterm, KF, k_latosa_adapt, &
94       &  rue_longterm, cn_leaf_min_season, nstress_season, soil_n_min, p_O2,bact, &
95       &  deepSOM_a, deepSOM_s, deepSOM_p, O2_soil, CH4_soil, O2_snow, CH4_snow, &
96       &  heat_Zimov, altmax, depth_organic_soil, fixed_cryoturbation_depth, cn_leaf_init_2D, harvest_above, sugar_load)
97
98    !---------------------------------------------------------------------
99    !- read start file
100    !---------------------------------------------------------------------
101    !-
102    ! 0 declarations
103    !-
104    ! 0.1 input
105    !-
106    ! Domain size
107    INTEGER(i_std),INTENT(in) :: npts
108    ! Indices of the points on the map
109    INTEGER(i_std),DIMENSION(npts),INTENT(in) :: index
110    ! Geogr. coordinates (latitude,longitude) (degrees)
111    REAL(r_std),DIMENSION(npts,2),INTENT(in) :: lalo
112    ! size in x an y of the grid (m)
113    REAL(r_std),DIMENSION(npts,2),INTENT(in) :: resolution
114    REAL(r_std),DIMENSION(npts),INTENT(in)   :: temp_air                !! Air temperature from forcing file or coupled model (K)
115    REAL(r_std),DIMENSION(npts,nvm), INTENT(in)  :: cn_leaf_init_2D     !! initial leaf C/N ratio
116    !-
117    ! 0.2 output
118    !-
119    ! time step of STOMATE in days
120    REAL(r_std),INTENT(out) :: dt_days
121    ! date_loc (d)
122    INTEGER(i_std),INTENT(out) :: date_loc
123    ! density of individuals (1/m**2)
124    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: ind
125    ! Winter too cold? between 0 and 1
126    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: adapted
127    ! Winter sufficiently cold? between 0 and 1
128    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: regenerate
129    ! daily moisture availability
130    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: moiavail_daily
131    ! date for beginning of gdd count
132    REAL(r_std),DIMENSION(npts,2),INTENT(out) :: gdd_init_date
133    ! daily litter humidity
134    REAL(r_std),DIMENSION(npts),INTENT(out)      :: litterhum_daily
135    ! daily 2 meter temperatures (K)
136    REAL(r_std),DIMENSION(npts),INTENT(out)      :: t2m_daily
137    ! daily minimum 2 meter temperatures (K)
138    REAL(r_std),DIMENSION(npts),INTENT(out)      :: t2m_min_daily
139    ! daily surface temperatures (K)
140    REAL(r_std),DIMENSION(npts),INTENT(out)      :: tsurf_daily
141    ! daily soil temperatures (K)
142    REAL(r_std),DIMENSION(npts,nslm),INTENT(out) :: tsoil_daily
143    ! daily soil humidity
144    REAL(r_std),DIMENSION(npts,nslm),INTENT(out) :: soilhum_daily
145    ! daily precipitations (mm/day) (for phenology)
146    REAL(r_std),DIMENSION(npts),INTENT(out)      :: precip_daily
147    ! daily gross primary productivity (gC/m**2/day)
148    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: gpp_daily
149    ! daily net primary productivity (gC/m**2/day)
150    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: npp_daily
151    ! daily turnover rates (gC/m**2/day)
152    REAL(r_std),DIMENSION(npts,nvm,nparts,nelements),INTENT(out) :: turnover_daily
153    ! "monthly" moisture availability
154    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: moiavail_month
155    ! "weekly" moisture availability
156    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: moiavail_week
157    ! mean growing season moisture availability (used for allocation response)
158    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: moiavail_growingseason
159    ! "long term" 2 meter temperatures (K)
160    REAL(r_std),DIMENSION(npts),INTENT(out)      :: t2m_longterm
161    ! "tau_longterm"
162    REAL(r_std), INTENT(out)        :: tau_longterm
163    ! "monthly" 2 meter temperatures (K)
164    REAL(r_std),DIMENSION(npts),INTENT(out)      :: t2m_month
165    ! "seasonal" 2 meter temperatures (K)
166    REAL(r_std),DIMENSION(npts),INTENT(out)      :: Tseason
167    ! temporary variable to calculate Tseason
168    REAL(r_std),DIMENSION(npts),INTENT(out)      :: Tseason_length
169    ! temporary variable to calculate Tseason
170    REAL(r_std),DIMENSION(npts),INTENT(out)      :: Tseason_tmp
171    REAL(r_std),DIMENSION(npts,nvm),INTENT(out)  :: Tmin_spring_time
172    REAL(r_std),DIMENSION(npts,nvm),INTENT(out)  :: onset_date
173    LOGICAL,DIMENSION(npts,nvm),INTENT(out)      :: begin_leaves
174
175    ! "weekly" 2 meter temperatures (K)
176    REAL(r_std),DIMENSION(npts),INTENT(out)      :: t2m_week
177    ! "monthly" soil temperatures (K)
178    REAL(r_std),DIMENSION(npts,nslm),INTENT(out) :: tsoil_month
179    ! "monthly" soil humidity
180    REAL(r_std),DIMENSION(npts,nslm),INTENT(out) :: soilhum_month
181    ! Probability of fire
182    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: fireindex
183    ! Longer term total litter above the ground, gC/m**2 of ground
184    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: firelitter
185    ! last year's maximum moisture availability
186    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: maxmoiavail_lastyear
187    ! this year's maximum moisture availability
188    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: maxmoiavail_thisyear
189    ! last year's minimum moisture availability
190    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: minmoiavail_lastyear
191    ! this year's minimum moisture availability
192    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: minmoiavail_thisyear
193    ! last year's maximum weekly GPP
194    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: maxgppweek_lastyear
195    ! this year's maximum weekly GPP
196    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: maxgppweek_thisyear
197    ! last year's annual GDD0
198    REAL(r_std),DIMENSION(npts),INTENT(out)      :: gdd0_lastyear
199    ! this year's annual GDD0
200    REAL(r_std),DIMENSION(npts),INTENT(out)      :: gdd0_thisyear
201    ! last year's annual precipitation (mm/year)
202    REAL(r_std),DIMENSION(npts),INTENT(out)      :: precip_lastyear
203    ! this year's annual precipitation (mm/year)
204    REAL(r_std),DIMENSION(npts),INTENT(out)      :: precip_thisyear
205    ! growing degree days, threshold -5 deg C (for phenology)
206    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: gdd_m5_dormance
207    ! growing degree days, from begin of season
208    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: gdd_from_growthinit
209    ! growing degree days since midwinter (for phenology)
210    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: gdd_midwinter
211    ! number of chilling days since leaves were lost (for phenology)
212    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: ncd_dormance
213    ! number of growing days, threshold -5 deg C (for phenology)
214    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: ngd_minus5
215    ! PFT exists (equivalent to fpc_max > 0 for natural PFTs)
216    LOGICAL,DIMENSION(npts,nvm),INTENT(out)    :: PFTpresent
217    ! "long term" net primary productivity (gC/m**2/year)
218    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: npp_longterm
219    ! "long term" root carbon mass (gC/m**2/year)
220    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: croot_longterm
221    ! last year's maximum leaf mass, for each PFT (gC/m**2)
222    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: lm_lastyearmax
223    ! this year's maximum leaf mass, for each PFT (gC/m**2)
224    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: lm_thisyearmax
225    ! last year's maximum fpc for each natural PFT, on ground
226    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: maxfpc_lastyear
227    ! this year's maximum fpc for each PFT,
228    ! on *total* ground (see stomate_season)
229    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: maxfpc_thisyear
230    ! "long term" turnover rate (gC/m**2/year)
231    REAL(r_std),DIMENSION(npts,nvm,nparts,nelements),INTENT(out) :: turnover_longterm
232    ! "weekly" GPP (gC/day/(m**2 covered)
233    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: gpp_week
234    ! biomass (gC/m**2)
235    REAL(r_std),DIMENSION(npts,nvm,nparts,nelements),INTENT(out) :: biomass
236    ! maintenance resp (gC/m**2)
237    REAL(r_std),DIMENSION(npts,nvm,nparts),INTENT(out) :: resp_maint_part
238    ! leaf age (days)
239    REAL(r_std),DIMENSION(npts,nvm,nleafages),INTENT(out) :: leaf_age
240    ! fraction of leaves in leaf age class
241    REAL(r_std),DIMENSION(npts,nvm,nleafages),INTENT(out) :: leaf_frac
242    ! is the plant senescent ?
243    !(only for deciduous trees - carbohydrate reserve)
244    LOGICAL,DIMENSION(npts,nvm),INTENT(out) :: senescence
245    ! how many days ago was the beginning of the growing season
246    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: when_growthinit
247    ! mean age (years)
248    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: age
249    ! heterotrophic respiration (gC/day/m**2)
250    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: resp_hetero
251    ! maintenance respiration (gC/day/m**2)
252    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: resp_maint
253    ! growth respiration (gC/day/m**2)
254    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: resp_growth
255    ! excess respiration (gC/day/m**2)
256    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: resp_excess
257    ! carbon emitted into the atmosphere by fire (living and dead biomass)
258    ! (in gC/m**2/time step)
259    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: co2_fire
260    ! biomass uptaken (gC/(m**2 of total ground)/day)
261    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: co2_to_bm_dgvm
262    ! biomass uptaken (gN/(m**2 of total ground)/day)
263    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: n_to_bm
264    ! vegetation fractions (on ground) after last light competition
265    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: veget_lastlight
266    ! is the PFT everywhere in the grid box or very localized
267    ! (after its introduction)
268    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: everywhere
269    ! in order for this PFT to be introduced,
270    ! does it have to be present in an adjacent grid box?
271    LOGICAL,DIMENSION(npts,nvm),INTENT(out) :: need_adjacent
272    ! How much time ago was the PFT eliminated for the last time (y)
273    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: RIP_time
274    ! time elapsed since strongest moisture availability (d)
275    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: time_hum_min
276    ! minimum moisture during dormance
277    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: hum_min_dormance
278    ! fraction of litter above the ground belonging to different PFTs
279    ! separated for natural and agricultural PFTs.
280    REAL(r_std),DIMENSION(npts,nlitt,nvm,nlevs,nelements),INTENT(out):: litter
281    ! dead leaves on ground, per PFT, metabolic and structural,
282    ! in gC/(m**2 of ground)
283    REAL(r_std),DIMENSION(npts,nvm,nlitt),INTENT(out) :: dead_leaves
284    ! Soil Organic Matter pool: active, slow, or passive, (gC (or N)/m**2)
285    REAL(r_std),DIMENSION(npts,ncarb,nvm,nelements),INTENT(out) :: som
286    ! ratio Lignine/Carbon in structural litter, above and below ground,(gC/m**2)
287    REAL(r_std),DIMENSION(npts,nvm,nlevs),INTENT(out) :: lignin_struc
288    ! ratio Lignine/Carbon in woody litter, above and below ground,(gC/m**2)
289    REAL(r_std),DIMENSION(npts,nvm,nlevs),INTENT(out) :: lignin_wood
290    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: turnover_time
291
292    ! For Spinup matrix resolution
293    INTEGER(i_std), INTENT(out) :: global_years   
294    LOGICAL, DIMENSION(npts), INTENT(out) :: ok_equilibrium
295    REAL(r_std), DIMENSION(npts), INTENT(out) :: nbp_accu  !! Accumulated Net Biospheric Production over the year
296    REAL(r_std), DIMENSION(npts), INTENT(out) :: nbp_flux  !! Net Biospheric Production over the year
297    !-
298    REAL(r_std), DIMENSION(npts,nvm,nbpools,nbpools), INTENT(out) :: MatrixV
299    REAL(r_std), DIMENSION(npts,nvm,nbpools), INTENT(out) :: VectorU
300    REAL(r_std), DIMENSION(npts,nvm,nbpools), INTENT(out) :: previous_stock
301    REAL(r_std), DIMENSION(npts,nvm,nbpools), INTENT(out) :: current_stock
302    REAL(r_std), DIMENSION(npts,nvm,nbpools), INTENT(out) :: CN_som_litter_longterm !! Longterm CN ratio of litter and som pools (gC/gN)
303    REAL(r_std), INTENT(out)                              :: tau_CN_longterm  !! Counter used for calculating the longterm CN ratio of SOM and litter pools (seconds)
304    REAL(r_std), DIMENSION(npts,nvm,npco2),   INTENT(out) :: assim_param
305
306    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)           :: KF             !! Scaling factor to convert sapwood mass                     
307                                                                              !! into leaf mass (m)
308    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)           :: k_latosa_adapt !! Leaf to sapwood area adapted for water       
309                                                                              !! stress. Adaptation takes place at the
310                                                                              !! end of the year (m)
311    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                       :: rue_longterm            !! longterm radiation use efficiency
312    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                       :: cn_leaf_min_season          !! Seasonal min CN ratio of leaves
313    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                       :: nstress_season          !! N-related seasonal stress (used for allocation)
314   
315    REAL(r_std), DIMENSION(npts,nvm,nnspec), INTENT(out)                :: soil_n_min              !! mineral nitrogen in the soil (gN/m**2) 
316                                                                                                   !! (first index=npts, second index=nvm, third index=nnspec)
317    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                       :: p_O2                    !! partial pressure of oxigen in the soil (hPa)
318                                                                                                   !! (first index=npts, second index=nvm)
319                     
320    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                       :: bact                    !! denitrifier biomass (gC/m**2)
321                                                                                                   !! (first index=npts, second index=nvm)
322 
323    !-
324    REAL(r_std), DIMENSION(npts,ngrnd,nvm,nelements),INTENT(out) :: deepSOM_a
325    REAL(r_std), DIMENSION(npts,ngrnd,nvm,nelements),INTENT(out) :: deepSOM_s
326    REAL(r_std), DIMENSION(npts,ngrnd,nvm,nelements),INTENT(out) :: deepSOM_p
327    REAL(r_std), DIMENSION(npts,ngrnd,nvm),INTENT(out)           :: O2_soil
328    REAL(r_std), DIMENSION(npts,ngrnd,nvm),INTENT(out)           :: CH4_soil
329    REAL(r_std), DIMENSION(npts,nsnow,nvm),INTENT(out)           :: O2_snow
330    REAL(r_std), DIMENSION(npts,nsnow,nvm),INTENT(out)           :: CH4_snow
331    REAL(r_std), DIMENSION(npts,ngrnd,nvm), INTENT(out)          :: heat_Zimov !! heating associated with decomposition [W/m**3 soil]
332    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                :: altmax     !! Active layer thickness (m)
333    REAL(r_std), DIMENSION(npts),INTENT(out)                     :: depth_organic_soil !! Depth at which there is still organic matter (m)
334    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                :: fixed_cryoturbation_depth !! Depth to hold cryoturbation to for fixed runs 
335    REAL(r_std), DIMENSION(npts,nelements), INTENT(out)          :: harvest_above
336    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                :: sugar_load                !! Relative sugar loading of the labile pool (unitless)
337    ! 0.4 local
338    !-
339    ! date, real
340    REAL(r_std) :: date_real
341    ! PFT exists (equivalent to fpc_max > 0 for natural PFTs), real
342    REAL(r_std),DIMENSION(npts,nvm) :: PFTpresent_real
343    ! is the plant senescent ?
344    ! (only for deciduous trees - carbohydrate reserve), real
345    REAL(r_std),DIMENSION(npts,nvm) :: senescence_real
346    REAL(r_std),DIMENSION(npts,nvm) :: begin_leaves_real
347    ! in order for this PFT to be introduced,
348    ! does it have to be present in an adjacent grid box? - real
349    REAL(r_std),DIMENSION(npts,nvm) :: need_adjacent_real
350    ! To store variables names for I/O
351    CHARACTER(LEN=80) :: var_name
352    ! string suffix indicating an index
353    CHARACTER(LEN=10) :: part_str
354    ! string suffix indicating litter type
355    CHARACTER(LEN=4),DIMENSION(nlitt) :: litter_str
356    ! string suffix indicating level
357    CHARACTER(LEN=2),DIMENSION(nlevs) :: level_str
358    ! temporary storage
359    REAL(r_std),DIMENSION(1) :: xtmp
360    ! index
361    INTEGER(i_std) :: j,k,l,m
362    ! reference temperature (K)
363
364    CHARACTER(LEN=2),DIMENSION(nelements) :: element_str   !! string suffix indicating element
365    REAL(r_std), DIMENSION(1) :: temp_global_years
366    CHARACTER(LEN=6), DIMENSION(nbpools) :: pools_str
367    REAL(r_std), DIMENSION(npts) :: ok_equilibrium_real   
368
369    ! land cover change variables
370    ! products remaining in the 10/100 year-turnover pool after the annual release for each compartment
371    ! (10 or 100 + 1 : input from year of land cover change)
372    REAL(r_std),DIMENSION(npts, nvm),INTENT(out)                           :: co2_flux
373    REAL(r_std),DIMENSION(npts),INTENT(out)                                :: fco2_lu
374    REAL(r_std),DIMENSION(npts),INTENT(out)                                :: fco2_wh
375    REAL(r_std),DIMENSION(npts),INTENT(out)                                :: fco2_ha
376    REAL(r_std),DIMENSION(npts,0:10),INTENT(out)                           :: prod10
377    REAL(r_std),DIMENSION(npts,0:100),INTENT(out)                          :: prod100
378    ! annual release from the 10/100 year-turnover pool compartments
379    REAL(r_std),DIMENSION(npts,10),INTENT(out)                           :: flux10
380    REAL(r_std),DIMENSION(npts,100),INTENT(out)                          :: flux100
381    REAL(r_std), DIMENSION(npts), INTENT(out)                            :: convflux
382    REAL(r_std), DIMENSION(npts), INTENT(out)                            :: cflux_prod10
383    REAL(r_std), DIMENSION(npts), INTENT(out)                            :: cflux_prod100
384    ! wood harvest variables
385    ! products remaining in the 10/100 year-turnover pool after the annual release for each compartment
386    ! (10 or 100 + 1 : input from year of land cover change)
387    REAL(r_std),DIMENSION(npts,0:10),INTENT(out)                           :: prod10_harvest
388    REAL(r_std),DIMENSION(npts,0:100),INTENT(out)                          :: prod100_harvest
389    ! annual release from the 10/100 year-turnover pool compartments
390    REAL(r_std),DIMENSION(npts,10),INTENT(out)                           :: flux10_harvest
391    REAL(r_std),DIMENSION(npts,100),INTENT(out)                          :: flux100_harvest
392    REAL(r_std), DIMENSION(npts), INTENT(out)                            :: convflux_harvest
393    REAL(r_std), DIMENSION(npts), INTENT(out)                            :: cflux_prod10_harvest
394    REAL(r_std), DIMENSION(npts), INTENT(out)                            :: cflux_prod100_harvest
395    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                        :: convfluxpft
396    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                        :: fDeforestToProduct
397    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                        :: fLulccResidue
398    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                        :: fHarvestToProduct
399    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                        :: woodharvestpft
400    REAL(r_std),DIMENSION(npts,nvm,nparts,nelements),INTENT(out)         :: bm_to_litter
401    REAL(r_std),DIMENSION(npts,nvm,nparts,nelements),INTENT(out)         :: tree_bm_to_litter
402    REAL(r_std),DIMENSION(npts),INTENT(out)                              :: carb_mass_total
403    REAL(r_std), DIMENSION(npts), INTENT(out)                            :: nflux_prod
404    REAL(r_std), DIMENSION(npts), INTENT(out)                            :: nflux_prod_harvest
405    REAL(r_std),DIMENSION(npts,nvm)                                      :: vcmax_tmp
406
407    ! Permafrost carbon processes
408    LOGICAL :: read_input_deepC_a
409    LOGICAL :: read_input_deepC_s
410    LOGICAL :: read_input_deepC_p
411    LOGICAL :: read_input_thawed_humidity
412    LOGICAL :: read_input_depth_organic_soil
413
414    !---------------------------------------------------------------------
415    IF (printlev >= 3) WRITE(numout,*) 'Entering readstart'
416    !-
417    ! 1 string definitions
418    !-
419    DO l=1,nlitt
420       IF     (l == imetabolic) THEN
421          litter_str(l) = 'met'
422       ELSEIF (l == istructural) THEN
423          litter_str(l) = 'str'
424       ELSEIF (l == iwoody) THEN
425          litter_str(l) = 'wood'
426       ELSE
427          CALL ipslerr_p(3,'stomate_io readstart', 'Define litter_str','','')
428       ENDIF
429    ENDDO
430    !-
431    DO l=1,nlevs
432       IF     (l == iabove) THEN
433          level_str(l) = 'ab'
434       ELSEIF (l == ibelow) THEN
435          level_str(l) = 'be'
436       ELSE
437          CALL ipslerr_p(3,'stomate_io readstart','Define level_str','','')
438       ENDIF
439    ENDDO
440
441    pools_str(1:nbpools) =(/'str_ab ','str_be ','met_ab ','met_be ','wood_ab','wood_be',& 
442         & 'actif  ','slow   ','passif ','surface'/) 
443    !-
444    DO l=1,nelements
445       IF     (l == icarbon) THEN
446          element_str(l) = ''
447       ELSEIF (l == initrogen) THEN
448          element_str(l) = '_n'
449       ELSE
450          CALL ipslerr_p(3,'stomate_io readstart','Define element_str','','')
451       ENDIF
452    ENDDO
453    !-
454    ! 2 run control
455    !-
456    ! 2.2 time step of STOMATE in days
457    !-    If the variable is not in the restart file, then un will be used as default value
458    CALL restget_p(rest_id_stomate, 'dt_days', itime, .TRUE., un, dt_days)
459    !-
460    ! 2.3 date
461    !-    If the variable is not in the restart file, then zero will be used as default value
462    CALL restget_p (rest_id_stomate, 'date', itime, .TRUE., zero, date_real)
463    date_loc = NINT(date_real)
464    !-
465    ! 3 daily meteorological variables
466    !-
467    moiavail_daily(:,:) = val_exp
468    var_name = 'moiavail_daily'
469    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
470         &              .TRUE., moiavail_daily, 'gather', nbp_glo, index_g)
471    IF (ALL(moiavail_daily(:,:) == val_exp)) moiavail_daily(:,:) = zero
472    !-
473    gdd_init_date(:,:) = val_exp
474    var_name = 'gdd_init_date'
475    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 2 , 1, itime, &
476         &              .TRUE., gdd_init_date, 'gather', nbp_glo, index_g)
477    ! Keep val_exp as initial value for gdd_init_date(:,2)
478    IF (ALL(gdd_init_date(:,1) == val_exp)) gdd_init_date(:,1) = 365.
479
480    !-
481    litterhum_daily(:) = val_exp
482    var_name = 'litterhum_daily'
483    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
484         &              .TRUE., litterhum_daily, 'gather', nbp_glo, index_g)
485    IF (ALL(litterhum_daily(:) == val_exp)) litterhum_daily(:) = zero
486    !-
487    t2m_daily(:) = val_exp
488    var_name = 't2m_daily'
489    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
490         &                .TRUE., t2m_daily, 'gather', nbp_glo, index_g)
491    IF (ALL(t2m_daily(:) == val_exp)) t2m_daily(:) = zero
492    !-
493    t2m_min_daily(:) = val_exp
494    var_name = 't2m_min_daily'
495    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
496         &                .TRUE., t2m_min_daily, 'gather', nbp_glo, index_g)
497    IF (ALL(t2m_min_daily(:) == val_exp)) t2m_min_daily(:) = large_value
498    !-
499    tsurf_daily(:) = val_exp
500    var_name = 'tsurf_daily'
501    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
502         &                .TRUE., tsurf_daily, 'gather', nbp_glo, index_g)
503    ! The initial value is set to the current temperature at 2m
504    IF (ALL(tsurf_daily(:) == val_exp)) tsurf_daily(:) = temp_air(:)
505    !-
506    tsoil_daily(:,:) = val_exp
507    var_name = 'tsoil_daily'
508    CALL restget_p (rest_id_stomate, var_name, nbp_glo,   nslm, 1, itime, &
509         &                .TRUE., tsoil_daily, 'gather', nbp_glo, index_g)
510    IF (ALL(tsoil_daily(:,:) == val_exp)) tsoil_daily(:,:) = zero
511    !-
512    soilhum_daily(:,:) = val_exp
513    var_name = 'soilhum_daily'
514    CALL restget_p (rest_id_stomate, var_name, nbp_glo,   nslm, 1, itime, &
515         &                .TRUE., soilhum_daily, 'gather', nbp_glo, index_g)
516    IF (ALL(soilhum_daily(:,:) == val_exp)) soilhum_daily(:,:) = zero
517    !-
518    precip_daily(:) = val_exp
519    var_name = 'precip_daily'
520    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
521         &                .TRUE., precip_daily, 'gather', nbp_glo, index_g)
522    IF (ALL(precip_daily(:) == val_exp)) precip_daily(:) = zero
523    !-
524    ! 4 productivities
525    !-
526    gpp_daily(:,:) = val_exp
527    var_name = 'gpp_daily'
528    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
529         &              .TRUE., gpp_daily, 'gather', nbp_glo, index_g)
530    IF (ALL(gpp_daily(:,:) == val_exp)) gpp_daily(:,:) = zero
531    !-
532    npp_daily(:,:) = val_exp
533    var_name = 'npp_daily'
534    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
535         &              .TRUE., npp_daily, 'gather', nbp_glo, index_g)
536    IF (ALL(npp_daily(:,:) == val_exp)) npp_daily(:,:) = zero
537    !-
538    turnover_daily(:,:,:,:) = val_exp
539    CALL restget_p (rest_id_stomate, 'turnover_daily', nbp_glo, nvm, nparts, nelements, itime, &
540         &                .TRUE., turnover_daily, 'gather', nbp_glo, index_g)
541    IF (ALL(turnover_daily == val_exp)) turnover_daily = zero
542    !-
543    ! 5 monthly meteorological variables
544    !-
545    moiavail_month(:,:) = val_exp
546    var_name = 'moiavail_month'
547    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
548         &              .TRUE., moiavail_month, 'gather', nbp_glo, index_g)
549    IF (ALL(moiavail_month(:,:) == val_exp)) moiavail_month(:,:) = zero
550    !-
551    moiavail_week(:,:) = val_exp
552    var_name = 'moiavail_week'
553    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
554         &              .TRUE., moiavail_week, 'gather', nbp_glo, index_g)
555    IF (ALL(moiavail_week(:,:) == val_exp)) moiavail_week(:,:) = zero
556
557    moiavail_growingseason(:,:) = val_exp
558    var_name = 'moiavail_grow'
559    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
560         &              .TRUE., moiavail_growingseason, 'gather', nbp_glo, index_g)
561    IF (ALL(moiavail_growingseason(:,:) == val_exp)) moiavail_growingseason(:,:) = un
562   
563
564    !
565    ! Longterm temperature at 2m
566    !
567    var_name = 't2m_longterm'
568    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
569         &              .TRUE., t2m_longterm, 'gather', nbp_glo, index_g)
570
571    IF (ALL(t2m_longterm(:) == val_exp)) THEN
572       ! t2m_longterm is not in restart file
573       ! The initial value for the reference temperature is set to the current temperature
574       t2m_longterm(:)=temp_air(:)
575       ! Set the counter to 2 time steps
576       tau_longterm=2
577    ELSE
578       ! t2m_longterm was in the restart file
579       ! Now read tau_longterm
580       ! tau_longterm is a scalar, therefor only master process read this value
581       CALL restget_p (rest_id_stomate, 'tau_longterm', itime, .TRUE., val_exp, tau_longterm)
582       IF (tau_longterm == val_exp) THEN
583             ! tau_longterm is not found in restart file.
584             ! This is not normal as t2m_longterm was in restart file. Write a warning and initialize it to tau_longterm_max
585          CALL ipslerr(2, 'stomate_io readstart','tau_longterm was not in restart file',&
586               'But t2m_longterm was in restart file','')
587          tau_longterm = tau_longterm_max
588       END IF
589
590    END IF
591    !-
592    t2m_month(:) = val_exp
593    var_name = 't2m_month'
594    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
595         &              .TRUE., t2m_month, 'gather', nbp_glo, index_g)
596    IF (ALL(t2m_month(:) == val_exp)) t2m_month(:) = temp_air(:)
597   
598    CALL restget_p (rest_id_stomate, 'Tseason', nbp_glo, 1     , 1, itime, &
599         .TRUE., Tseason, 'gather', nbp_glo, index_g)
600    IF (ALL(Tseason(:) == val_exp)) Tseason(:) = temp_air(:)
601   
602    CALL restget_p (rest_id_stomate,'Tseason_length', nbp_glo, 1     , 1, itime, &
603         .TRUE., Tseason_length, 'gather', nbp_glo, index_g)
604    IF (ALL(Tseason_length(:) == val_exp)) Tseason_length(:) = zero
605   
606    CALL restget_p (rest_id_stomate, 'Tseason_tmp', nbp_glo, 1     , 1, itime, &
607         .TRUE., Tseason_tmp, 'gather', nbp_glo, index_g)
608    IF (ALL(Tseason_tmp(:) == val_exp)) Tseason_tmp(:) = zero
609
610    CALL restget_p (rest_id_stomate, 'Tmin_spring_time', nbp_glo, nvm, 1, itime, &
611         .TRUE., Tmin_spring_time, 'gather', nbp_glo, index_g)
612    IF (ALL(Tmin_spring_time(:,:) == val_exp)) Tmin_spring_time(:,:) = zero
613   
614    CALL restget_p (rest_id_stomate, 'onset_date', nbp_glo, nvm  , 1, itime, &
615         .TRUE., onset_date(:,:), 'gather', nbp_glo, index_g)
616    IF (ALL(onset_date(:,:) == val_exp)) onset_date(:,:) = zero
617
618    t2m_week(:) = val_exp
619    var_name = 't2m_week'
620    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
621         &              .TRUE., t2m_week, 'gather', nbp_glo, index_g)
622    ! The initial value is set to the current temperature
623    IF (ALL(t2m_week(:) == val_exp)) t2m_week(:) = temp_air(:)
624   
625    tsoil_month(:,:) = val_exp
626    var_name = 'tsoil_month'
627    CALL restget_p (rest_id_stomate, var_name, nbp_glo,   nslm, 1, itime, &
628         &              .TRUE., tsoil_month, 'gather', nbp_glo, index_g)
629
630    ! The initial value is set to the current temperature
631    IF (ALL(tsoil_month(:,:) == val_exp)) THEN
632       DO l=1,nslm
633          tsoil_month(:,l) = temp_air(:)
634       ENDDO
635    ENDIF
636    !-
637    soilhum_month(:,:) = val_exp
638    var_name = 'soilhum_month'
639    CALL restget_p (rest_id_stomate, var_name, nbp_glo,   nslm, 1, itime, &
640         &              .TRUE., soilhum_month, 'gather', nbp_glo, index_g)
641    IF (ALL(soilhum_month(:,:) == val_exp)) soilhum_month(:,:) = zero
642    !-
643    ! 6 fire probability
644    !-
645    fireindex(:,:) = val_exp
646    var_name = 'fireindex'
647    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
648         &              .TRUE., fireindex, 'gather', nbp_glo, index_g)
649    IF (ALL(fireindex(:,:) == val_exp)) fireindex(:,:) = zero
650    !-
651    firelitter(:,:) = val_exp
652    var_name = 'firelitter'
653    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
654         &              .TRUE., firelitter, 'gather', nbp_glo, index_g)
655    IF (ALL(firelitter(:,:) == val_exp)) firelitter(:,:) = zero
656    !-
657    ! 7 maximum and minimum moisture availabilities for tropic phenology
658    !-
659    maxmoiavail_lastyear(:,:) = val_exp
660    var_name = 'maxmoistr_last'
661    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
662         &              .TRUE., maxmoiavail_lastyear, 'gather', nbp_glo, index_g)
663    IF (ALL(maxmoiavail_lastyear(:,:) == val_exp)) &
664         &     maxmoiavail_lastyear(:,:) = zero
665    !-
666    maxmoiavail_thisyear(:,:) = val_exp
667    var_name = 'maxmoistr_this'
668    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
669         &              .TRUE., maxmoiavail_thisyear, 'gather', nbp_glo, index_g)
670    IF (ALL(maxmoiavail_thisyear(:,:) == val_exp)) &
671         &     maxmoiavail_thisyear(:,:) = zero
672    !-
673    minmoiavail_lastyear(:,:) = val_exp
674    var_name = 'minmoistr_last'
675    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
676         &              .TRUE., minmoiavail_lastyear, 'gather', nbp_glo, index_g)
677    IF (ALL(minmoiavail_lastyear(:,:) == val_exp)) &
678         &     minmoiavail_lastyear(:,:) = un
679    !-
680    minmoiavail_thisyear(:,:) = val_exp
681    var_name = 'minmoistr_this'
682    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
683         &              .TRUE., minmoiavail_thisyear, 'gather', nbp_glo, index_g)
684    IF (ALL( minmoiavail_thisyear(:,:) == val_exp)) &
685         &     minmoiavail_thisyear(:,:) = un
686    !-
687    ! 8 maximum "weekly" GPP
688    !-
689    maxgppweek_lastyear(:,:) = val_exp
690    var_name = 'maxgppweek_lastyear'
691    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
692         &              .TRUE., maxgppweek_lastyear, 'gather', nbp_glo, index_g)
693    IF (ALL(maxgppweek_lastyear(:,:) == val_exp)) &
694         &     maxgppweek_lastyear(:,:) = zero
695    !-
696    maxgppweek_thisyear(:,:) = val_exp
697    var_name = 'maxgppweek_thisyear'
698    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
699         &              .TRUE., maxgppweek_thisyear, 'gather', nbp_glo, index_g)
700    IF (ALL(maxgppweek_thisyear(:,:) == val_exp)) &
701         &     maxgppweek_thisyear(:,:) = zero
702    !-
703    ! 9 annual GDD0
704    !-
705    gdd0_thisyear(:) = val_exp
706    var_name = 'gdd0_thisyear'
707    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
708         &              .TRUE., gdd0_thisyear, 'gather', nbp_glo, index_g)
709    IF (ALL(gdd0_thisyear(:) == val_exp)) gdd0_thisyear(:) = zero
710    !-
711    gdd0_lastyear(:) = val_exp
712    var_name = 'gdd0_lastyear'
713    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
714         &              .TRUE., gdd0_lastyear, 'gather', nbp_glo, index_g)
715    IF (ALL(gdd0_lastyear(:) == val_exp)) gdd0_lastyear(:) = gdd_crit_estab
716    !-
717    ! 10 annual precipitation
718    !-
719    precip_thisyear(:) = val_exp
720    var_name = 'precip_thisyear'
721    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
722         &              .TRUE., precip_thisyear, 'gather', nbp_glo, index_g)
723    IF (ALL(precip_thisyear(:) == val_exp)) precip_thisyear(:) = zero
724    !-
725    precip_lastyear(:) = val_exp
726    var_name = 'precip_lastyear'
727    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
728         &              .TRUE., precip_lastyear, 'gather', nbp_glo, index_g)
729    IF (ALL(precip_lastyear(:) == val_exp)) &
730         &     precip_lastyear(:) = precip_crit
731    !-
732    ! 11 derived "biometeorological" variables
733    !-
734    gdd_m5_dormance(:,:) = val_exp
735    var_name = 'gdd_m5_dormance'
736    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
737         &              .TRUE., gdd_m5_dormance, 'gather', nbp_glo, index_g)
738    IF (ALL(gdd_m5_dormance(:,:) == val_exp)) &
739         &     gdd_m5_dormance(:,:) = undef
740    !-
741    gdd_from_growthinit(:,:) = val_exp
742    var_name = 'gdd_from_growthinit'
743    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
744         &              .TRUE., gdd_from_growthinit, 'gather', nbp_glo, index_g)
745    IF (ALL(gdd_from_growthinit(:,:) == val_exp)) &
746         &     gdd_from_growthinit(:,:) = zero
747    !-
748    gdd_midwinter(:,:) = val_exp
749    var_name = 'gdd_midwinter'
750    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
751         &              .TRUE., gdd_midwinter, 'gather', nbp_glo, index_g)
752    IF (ALL(gdd_midwinter(:,:) == val_exp)) gdd_midwinter(:,:) = undef
753    !-
754    ncd_dormance(:,:) = val_exp
755    var_name = 'ncd_dormance'
756    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
757         &              .TRUE., ncd_dormance, 'gather', nbp_glo, index_g)
758    IF (ALL(ncd_dormance(:,:) == val_exp)) ncd_dormance(:,:) = undef
759    !-
760    ngd_minus5(:,:) = val_exp
761    var_name = 'ngd_minus5'
762    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
763         &              .TRUE., ngd_minus5, 'gather', nbp_glo, index_g)
764    IF (ALL(ngd_minus5(:,:) == val_exp)) ngd_minus5(:,:) = zero
765    !-
766    time_hum_min(:,:) = val_exp
767    var_name = 'time_hum_min'
768    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
769         &              .TRUE., time_hum_min, 'gather', nbp_glo, index_g)
770    IF (ALL(time_hum_min(:,:) == val_exp)) time_hum_min(:,:) = undef
771    !-
772    hum_min_dormance(:,:) = val_exp
773    var_name = 'hum_min_dormance'
774    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
775         &              .TRUE., hum_min_dormance, 'gather', nbp_glo, index_g)
776    IF (ALL(hum_min_dormance(:,:) == val_exp)) &
777         &     hum_min_dormance(:,:) = undef
778    !-
779    ! 12 Plant status
780    !-
781    PFTpresent_real(:,:) = val_exp
782    var_name = 'PFTpresent'
783    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
784         &              .TRUE., PFTpresent_real, 'gather', nbp_glo, index_g)
785    IF (ALL(PFTpresent_real(:,:) == val_exp)) PFTpresent_real(:,:) = zero
786    WHERE (PFTpresent_real(:,:) >= .5)
787       PFTpresent = .TRUE.
788    ELSEWHERE
789       PFTpresent = .FALSE.
790    ENDWHERE
791    !-
792    ind(:,:) = val_exp
793    var_name = 'ind'
794    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
795         &              .TRUE., ind, 'gather', nbp_glo, index_g)
796    IF (ALL(ind(:,:) == val_exp)) ind(:,:) = zero
797    !-
798    adapted(:,:) = val_exp
799    var_name = 'adapted'
800    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
801         &              .TRUE., adapted, 'gather', nbp_glo, index_g)
802    IF (ALL(adapted(:,:) == val_exp)) adapted(:,:) = zero
803    !-
804    regenerate(:,:) = val_exp
805    var_name = 'regenerate'
806    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
807         &              .TRUE., regenerate, 'gather', nbp_glo, index_g)
808    IF (ALL(regenerate(:,:) == val_exp)) regenerate(:,:) = zero
809    !-
810    npp_longterm(:,:) = val_exp
811    var_name = 'npp_longterm'
812    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
813         &              .TRUE., npp_longterm, 'gather', nbp_glo, index_g)
814    IF (ALL(npp_longterm(:,:) == val_exp)) npp_longterm(:,:) = zero
815    !-
816    croot_longterm(:,:) = val_exp
817    var_name = 'croot_longterm'
818    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
819         &              .TRUE., croot_longterm, 'gather', nbp_glo, index_g)
820    IF (ALL(croot_longterm(:,:) == val_exp)) croot_longterm(:,:) = zero
821    !-
822    lm_lastyearmax(:,:) = val_exp
823    var_name = 'lm_lastyearmax'
824    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
825         &              .TRUE., lm_lastyearmax, 'gather', nbp_glo, index_g)
826    IF (ALL(lm_lastyearmax(:,:) == val_exp)) lm_lastyearmax(:,:) = zero
827    !-
828    lm_thisyearmax(:,:) = val_exp
829    var_name = 'lm_thisyearmax'
830    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
831         &              .TRUE., lm_thisyearmax, 'gather', nbp_glo, index_g)
832    IF (ALL(lm_thisyearmax(:,:) == val_exp)) lm_thisyearmax(:,:) = zero
833    !-
834    maxfpc_lastyear(:,:) = val_exp
835    var_name = 'maxfpc_lastyear'
836    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
837         &              .TRUE., maxfpc_lastyear, 'gather', nbp_glo, index_g)
838    IF (ALL(maxfpc_lastyear(:,:) == val_exp)) maxfpc_lastyear(:,:) = zero
839    !-
840    maxfpc_thisyear(:,:) = val_exp
841    var_name = 'maxfpc_thisyear'
842    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
843         &              .TRUE., maxfpc_thisyear, 'gather', nbp_glo, index_g)
844    IF (ALL(maxfpc_thisyear(:,:) == val_exp)) maxfpc_thisyear(:,:) = zero
845    !-
846    turnover_time(:,:) = val_exp
847    var_name = 'turnover_time'
848    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
849         &              .TRUE., turnover_time, 'gather', nbp_glo, index_g)
850    IF ( ALL( turnover_time(:,:) == val_exp)) turnover_time(:,:) = 100.
851    !-
852    turnover_longterm(:,:,:,:) = val_exp
853    CALL restget_p (rest_id_stomate, 'turnover_loterm', nbp_glo, nvm, nparts, nelements, itime, &
854         &              .TRUE., turnover_longterm, 'gather', nbp_glo, index_g)
855    IF (ALL(turnover_longterm == val_exp)) turnover_longterm = zero
856    !-
857    gpp_week(:,:) = val_exp
858    var_name = 'gpp_week'
859    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
860         &              .TRUE., gpp_week, 'gather', nbp_glo, index_g)
861    IF (ALL(gpp_week(:,:) == val_exp)) gpp_week(:,:) = zero
862    !-
863    biomass(:,:,:,:) = val_exp
864    CALL restget_p (rest_id_stomate, 'biomass', nbp_glo, nvm, nparts, nelements, itime, &
865         &                   .TRUE., biomass, 'gather', nbp_glo, index_g)
866    IF (ALL(biomass == val_exp)) biomass = zero
867    !-
868    resp_maint_part(:,:,:) = val_exp
869    var_name = 'maint_resp'
870    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , nparts, itime, &
871         &                   .TRUE., resp_maint_part, 'gather', nbp_glo, index_g)
872    IF (ALL(resp_maint_part == val_exp)) resp_maint_part(:,:,:) = zero
873    !-
874    leaf_age(:,:,:) = val_exp
875    var_name = 'leaf_age'
876    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , nleafages, itime, &
877         &                   .TRUE., leaf_age, 'gather', nbp_glo, index_g)
878    IF (ALL(leaf_age == val_exp)) leaf_age(:,:,:) = zero
879    !-
880    leaf_frac(:,:,:) = val_exp
881    var_name = 'leaf_frac'
882    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , nleafages, itime, &
883         &                  .TRUE., leaf_frac, 'gather', nbp_glo, index_g)
884    IF (ALL(leaf_frac == val_exp)) leaf_frac(:,:,:) = zero
885    !-
886    senescence_real(:,:) = val_exp
887    var_name = 'senescence'
888    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
889         &                .TRUE., senescence_real, 'gather', nbp_glo, index_g)
890    IF (ALL(senescence_real(:,:) == val_exp)) senescence_real(:,:) = zero
891    WHERE ( senescence_real(:,:) >= .5 )
892       senescence = .TRUE.
893    ELSEWHERE
894       senescence = .FALSE.
895    ENDWHERE
896
897
898    ! Read real value for begin_leaves
899    CALL restget_p (rest_id_stomate, 'begin_leaves', nbp_glo, nvm  , 1, itime, &
900         .TRUE., begin_leaves_real, 'gather', nbp_glo, index_g)
901    IF (ALL(begin_leaves_real(:,:) == val_exp)) begin_leaves_real(:,:) = zero
902
903    ! Transform into logical needed by the modele
904    WHERE ( begin_leaves_real(:,:) >= 0.5 )
905       begin_leaves = .TRUE.
906    ELSEWHERE
907       begin_leaves = .FALSE.
908    ENDWHERE
909
910
911    when_growthinit(:,:) = val_exp
912    var_name = 'when_growthinit'
913    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
914         &                .TRUE., when_growthinit, 'gather', nbp_glo, index_g)
915    IF (ALL(when_growthinit(:,:) == val_exp)) &
916         &     when_growthinit(:,:) = 240.
917
918    !-
919    age(:,:) = val_exp
920    var_name = 'age'
921    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
922         &                .TRUE., age, 'gather', nbp_glo, index_g)
923    IF (ALL(age(:,:) == val_exp)) age(:,:) = zero
924    !-
925    ! 13 CO2
926    !-
927    resp_hetero(:,:) = val_exp
928    var_name = 'resp_hetero'
929    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
930         &                .TRUE., resp_hetero, 'gather', nbp_glo, index_g)
931    IF (ALL(resp_hetero(:,:) == val_exp)) resp_hetero(:,:) = zero
932    !-
933    resp_maint(:,:) = val_exp
934    var_name = 'resp_maint'
935    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
936         &                .TRUE., resp_maint, 'gather', nbp_glo, index_g)
937    IF (ALL(resp_maint(:,:) == val_exp)) resp_maint(:,:) = zero
938    !-
939    resp_growth(:,:) = val_exp
940    var_name = 'resp_growth'
941    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
942         &                .TRUE., resp_growth, 'gather', nbp_glo, index_g)
943    IF (ALL(resp_growth(:,:) == val_exp)) resp_growth(:,:) = zero
944    !-
945    resp_excess(:,:) = val_exp
946    var_name = 'resp_excess'
947    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
948         &                .TRUE., resp_excess, 'gather', nbp_glo, index_g)
949    IF (ALL(resp_excess(:,:) == val_exp)) resp_excess(:,:) = zero
950    !-
951    co2_fire(:,:) = val_exp
952    var_name = 'co2_fire'
953    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
954         &                .TRUE., co2_fire, 'gather', nbp_glo, index_g)
955    IF (ALL(co2_fire(:,:) == val_exp)) co2_fire(:,:) = zero
956    !-
957    co2_to_bm_dgvm(:,:) = val_exp
958    var_name = 'co2_to_bm_dgvm'
959    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
960         &                .TRUE., co2_to_bm_dgvm, 'gather', nbp_glo, index_g)
961    IF (ALL(co2_to_bm_dgvm(:,:) == val_exp)) co2_to_bm_dgvm(:,:) = zero
962
963    !-
964    n_to_bm(:,:) = val_exp
965    var_name = 'n_to_bm'
966    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
967         &                .TRUE., n_to_bm, 'gather', nbp_glo, index_g)
968    IF (ALL(n_to_bm(:,:) == val_exp)) n_to_bm(:,:) = zero
969    !-
970    ! 14 vegetation distribution after last light competition
971    !-
972    veget_lastlight(:,:) = val_exp
973    var_name = 'veget_lastlight'
974    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
975         &                .TRUE., veget_lastlight, 'gather', nbp_glo, index_g)
976    IF (ALL(veget_lastlight(:,:) == val_exp)) veget_lastlight(:,:) = zero
977    !-
978    ! 15 establishment criteria
979    !-
980    everywhere(:,:) = val_exp
981    var_name = 'everywhere'
982    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
983         &                .TRUE., everywhere, 'gather', nbp_glo, index_g)
984    IF (ALL(everywhere(:,:) == val_exp)) everywhere(:,:) = zero
985    !-
986    need_adjacent_real(:,:) = val_exp
987    var_name = 'need_adjacent'
988    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
989         &                .TRUE., need_adjacent_real, 'gather', nbp_glo, index_g)
990    IF (ALL(need_adjacent_real(:,:) == val_exp)) &
991         &     need_adjacent_real(:,:) = zero
992    WHERE ( need_adjacent_real(:,:) >= .5 )
993       need_adjacent = .TRUE.
994    ELSEWHERE
995       need_adjacent = .FALSE.
996    ENDWHERE
997    !-
998    RIP_time(:,:) = val_exp
999    var_name = 'RIP_time'
1000    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1001         &                .TRUE., RIP_time, 'gather', nbp_glo, index_g)
1002    IF (ALL(RIP_time(:,:) == val_exp)) RIP_time(:,:) = large_value
1003    !-
1004    ! 17 litter
1005    !-
1006    litter(:,:,:,:,:) = val_exp
1007    CALL restget_p (rest_id_stomate, 'litter', nbp_glo, nlitt, nvm, nlevs, nelements, itime, &
1008         &                     .TRUE., litter, 'gather', nbp_glo, index_g)
1009    IF (ALL(litter == val_exp)) litter = zero
1010    !-
1011    dead_leaves(:,:,:) = val_exp
1012    CALL restget_p (rest_id_stomate, 'dead_leaves', nbp_glo, nvm  , nlitt, itime, &
1013            &                   .TRUE., dead_leaves, 'gather', nbp_glo, index_g)
1014    IF (ALL(dead_leaves(:,:,:) == val_exp)) dead_leaves = zero
1015   
1016    som(:,:,:,:) = val_exp
1017    CALL restget_p (rest_id_stomate, 'carbon', nbp_glo, ncarb, nvm, itime, &
1018         &                   .TRUE., som(:,:,:,icarbon), 'gather', nbp_glo, index_g) 
1019    IF (ALL(som(:,:,:,icarbon) == val_exp)) THEN
1020       som(:,iactive,:,icarbon) = 1000. 
1021       som(:,isurface,:,icarbon) = 1000. 
1022       som(:,islow,:,icarbon) = 3000. 
1023       som(:,ipassive,:,icarbon) = 5000.
1024    ENDIF
1025
1026    CALL restget_p (rest_id_stomate, 'nitrogen', nbp_glo, ncarb , nvm, itime, & 
1027            &                   .TRUE., som(:,:,:,initrogen), 'gather', nbp_glo, index_g) 
1028    IF (ALL(som(:,:,:,initrogen) == val_exp)) THEN
1029       som(:,iactive,:,initrogen) = som(:,iactive,:,icarbon) / CN_target_iactive_ref 
1030       som(:,isurface,:,initrogen) = som(:,isurface,:,icarbon) / CN_target_isurface_ref 
1031       som(:,islow,:,initrogen) = som(:,islow,:,icarbon) / CN_target_islow_ref 
1032       som(:,ipassive,:,initrogen) =  som(:,ipassive,:,icarbon) / CN_target_ipassive_ref 
1033    ENDIF
1034    !-
1035    lignin_struc(:,:,:) = val_exp
1036    CALL restget_p &
1037            &    (rest_id_stomate, 'lignin_struc', nbp_glo, nvm, nlevs, itime, &
1038            &     .TRUE., lignin_struc, 'gather', nbp_glo, index_g)
1039    IF (ALL(lignin_struc == val_exp)) lignin_struc = zero
1040
1041    !-
1042    lignin_wood(:,:,:) = val_exp
1043    CALL restget_p &
1044            &    (rest_id_stomate, 'lignin_wood', nbp_glo, nvm, nlevs, itime, &
1045            &     .TRUE., lignin_wood, 'gather', nbp_glo, index_g)
1046    IF (ALL(lignin_wood == val_exp)) lignin_wood = zero
1047    !-
1048    ! 18 land cover change
1049    !-
1050    ! Read from restart file or set to zero if the variables or restart file were not found
1051
1052    var_name = 'co2_flux'
1053    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
1054         .TRUE., co2_flux, 'gather', nbp_glo, index_g)
1055    IF (ALL(co2_flux(:,:) == val_exp)) co2_flux(:,:) = zero
1056
1057    var_name = 'fco2_lu'
1058    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
1059         .TRUE., fco2_lu, 'gather', nbp_glo, index_g)
1060    IF (ALL(fco2_lu(:) == val_exp)) fco2_lu(:) = zero
1061
1062    var_name = 'fco2_wh'
1063    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
1064         .TRUE., fco2_wh, 'gather', nbp_glo, index_g)
1065    IF (ALL(fco2_wh(:) == val_exp)) fco2_wh(:) = zero
1066
1067    var_name = 'fco2_ha'
1068    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
1069         .TRUE., fco2_ha, 'gather', nbp_glo, index_g)
1070    IF (ALL(fco2_ha(:) == val_exp)) fco2_ha(:) = zero
1071
1072       
1073    IF (vegetmap_reset) THEN
1074       ! Reset vegetation map related variables instead of reading from restart file
1075       prod10(:,:) = zero
1076       prod100(:,:) = zero
1077       flux10(:,:) = zero
1078       flux100(:,:) = zero
1079       convflux(:) = zero
1080       cflux_prod10(:) = zero
1081       cflux_prod100(:) = zero
1082       convfluxpft(:,:) = zero
1083
1084    ELSE
1085       ! Read from restart file or set to zero if the variables or restart file were not found
1086       prod10(:,:) = val_exp
1087       var_name = 'prod10'
1088       CALL restget_p (rest_id_stomate, var_name, nbp_glo, 11     , 1, itime, &
1089            .TRUE., prod10, 'gather', nbp_glo, index_g)
1090       IF (ALL(prod10(:,:) == val_exp)) prod10(:,:) = zero
1091       
1092       prod100(:,:) = val_exp
1093       var_name = 'prod100'
1094       CALL restget_p (rest_id_stomate, var_name, nbp_glo, 101     , 1, itime, &
1095            .TRUE., prod100, 'gather', nbp_glo, index_g)
1096       IF (ALL(prod100(:,:) == val_exp)) prod100(:,:) = zero
1097             
1098       flux10(:,:) = val_exp
1099       var_name = 'flux10'
1100       CALL restget_p (rest_id_stomate, var_name, nbp_glo, 10     , 1, itime, &
1101            .TRUE., flux10, 'gather', nbp_glo, index_g)
1102       IF (ALL(flux10(:,:) == val_exp)) flux10(:,:) = zero
1103       
1104       flux100(:,:) = val_exp
1105       var_name = 'flux100'
1106       CALL restget_p (rest_id_stomate, var_name, nbp_glo, 100     , 1, itime, &
1107            .TRUE., flux100, 'gather', nbp_glo, index_g)
1108       IF (ALL(flux100(:,:) == val_exp)) flux100(:,:) = zero
1109       
1110       convflux(:) = val_exp
1111       var_name = 'convflux'
1112       CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
1113            .TRUE., convflux, 'gather', nbp_glo, index_g)
1114       IF (ALL(convflux(:) == val_exp)) convflux(:) = zero
1115       
1116       cflux_prod10(:) = val_exp
1117       var_name = 'cflux_prod10'
1118       CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
1119            .TRUE., cflux_prod10, 'gather', nbp_glo, index_g)
1120       IF (ALL(cflux_prod10(:) == val_exp)) cflux_prod10(:) = zero
1121       
1122       cflux_prod100(:) = val_exp
1123       var_name = 'cflux_prod100'
1124       CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
1125            .TRUE., cflux_prod100, 'gather', nbp_glo, index_g)
1126       IF (ALL(cflux_prod100(:) == val_exp)) cflux_prod100(:) = zero
1127       
1128       convfluxpft(:,:) = val_exp
1129       var_name = 'convfluxpft'
1130       CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1131            .TRUE., convfluxpft, 'gather', nbp_glo, index_g)
1132       IF (ALL(convfluxpft(:,:) == val_exp)) convfluxpft(:,:) = zero
1133    END IF
1134
1135    fDeforestToProduct(:,:) = val_exp
1136    var_name = 'fDeforestToProduct'
1137    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1138         &   .TRUE., fDeforestToProduct, 'gather', nbp_glo, index_g)
1139    IF (ALL(fDeforestToProduct(:,:) ==val_exp)) fDeforestToProduct(:,:) = zero
1140
1141    fLulccResidue(:,:) = val_exp
1142    var_name = 'fLulccResidue'
1143    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1144         &   .TRUE., fLulccResidue, 'gather', nbp_glo, index_g)
1145    IF (ALL(fLulccResidue(:,:) ==val_exp)) fLulccResidue(:,:) = zero
1146
1147    fHarvestToProduct(:,:) = val_exp
1148    var_name = 'fHarvestToProduct'
1149    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1150         &   .TRUE., fHarvestToProduct, 'gather', nbp_glo, index_g)
1151    IF (ALL(fHarvestToProduct(:,:) ==val_exp)) fHarvestToProduct(:,:) = zero
1152
1153    !-
1154    ! 18-bis wood harvest
1155    !-
1156    IF (do_wood_harvest) THEN
1157       prod10_harvest(:,:) = val_exp
1158       var_name = 'prod10_harvest'
1159       CALL restget_p (rest_id_stomate, var_name, nbp_glo, 11     , 1, itime, &
1160            .TRUE., prod10_harvest, 'gather', nbp_glo, index_g)
1161       IF (ALL(prod10_harvest(:,:) == val_exp)) prod10_harvest(:,:) = zero
1162       
1163       prod100_harvest(:,:) = val_exp
1164       var_name = 'prod100_harvest'
1165       CALL restget_p (rest_id_stomate, var_name, nbp_glo, 101     , 1, itime, &
1166            .TRUE., prod100_harvest, 'gather', nbp_glo, index_g)
1167       IF (ALL(prod100_harvest(:,:) == val_exp)) prod100_harvest(:,:) = zero
1168       
1169       flux10_harvest(:,:) = val_exp
1170       var_name = 'flux10_harvest'
1171       CALL restget_p (rest_id_stomate, var_name, nbp_glo, 10     , 1, itime, &
1172            .TRUE., flux10_harvest, 'gather', nbp_glo, index_g)
1173       IF (ALL(flux10_harvest(:,:) == val_exp)) flux10_harvest(:,:) = zero
1174       
1175       flux100_harvest(:,:) = val_exp
1176       var_name = 'flux100_harvest'
1177       CALL restget_p (rest_id_stomate, var_name, nbp_glo, 100     , 1, itime, &
1178            .TRUE., flux100_harvest, 'gather', nbp_glo, index_g)
1179       IF (ALL(flux100_harvest(:,:) == val_exp)) flux100_harvest(:,:) = zero
1180       
1181       convflux_harvest(:) = val_exp
1182       var_name = 'convflux_harvest'
1183       CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
1184            .TRUE., convflux_harvest, 'gather', nbp_glo, index_g)
1185       IF (ALL(convflux_harvest(:) == val_exp)) convflux_harvest(:) = zero
1186       
1187       cflux_prod10_harvest(:) = val_exp
1188       var_name = 'cflux_prod10_harvest'
1189       CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
1190            .TRUE., cflux_prod10_harvest, 'gather', nbp_glo, index_g)
1191       IF (ALL(cflux_prod10_harvest(:) == val_exp)) cflux_prod10_harvest(:) = zero
1192       
1193       cflux_prod100_harvest(:) = val_exp
1194       var_name = 'cfluxprod100_harvest'
1195       CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
1196            .TRUE., cflux_prod100_harvest, 'gather', nbp_glo, index_g)
1197       IF (ALL(cflux_prod100_harvest(:) == val_exp)) cflux_prod100_harvest(:) = zero
1198       
1199       woodharvestpft(:,:) = val_exp
1200       var_name = 'woodharvestpft'
1201       CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1202            .TRUE., woodharvestpft, 'gather', nbp_glo, index_g)
1203       IF (ALL(woodharvestpft(:,:) == val_exp)) woodharvestpft(:,:) = zero
1204    END IF
1205
1206
1207    bm_to_litter(:,:,:,:) = val_exp
1208    CALL restget_p (rest_id_stomate, 'bm_to_litter', nbp_glo, nvm, nparts, nelements, itime, &
1209        &                .TRUE., bm_to_litter, 'gather', nbp_glo, index_g)
1210    IF (ALL(bm_to_litter == val_exp)) bm_to_litter = zero
1211
1212    tree_bm_to_litter(:,:,:,:) = val_exp
1213    CALL restget_p (rest_id_stomate, 'tree_to_litter', nbp_glo, nvm, nparts, nelements, itime, &
1214          &                .TRUE., tree_bm_to_litter, 'gather', nbp_glo, index_g)
1215    IF (ALL(tree_bm_to_litter == val_exp)) tree_bm_to_litter = zero
1216
1217    carb_mass_total(:) = val_exp
1218    var_name = 'carb_mass_total'
1219    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
1220         &              .TRUE., carb_mass_total, 'gather', nbp_glo, index_g)
1221    IF (ALL(carb_mass_total(:) == val_exp)) carb_mass_total(:) = zero
1222
1223
1224    IF ( ok_soil_carbon_discretization ) THEN
1225       CALL restget_p (rest_id_stomate, 'deepSOM_a', nbp_glo, ngrnd, nvm, nelements,  itime, &
1226          .TRUE., deepSOM_a, 'gather', nbp_glo, index_g)
1227       IF (ALL(deepSOM_a == val_exp)) THEN
1228          deepSOM_a(:,:,:,icarbon) = 10.
1229          deepSOM_a(:,:,:,initrogen) = deepSOM_a(:,:,:,icarbon) / CN_target_iactive_ref
1230       ENDIF
1231
1232       CALL restget_p (rest_id_stomate, 'deepSOM_s', nbp_glo, ngrnd, nvm, nelements, itime, &
1233          .TRUE., deepSOM_s, 'gather', nbp_glo, index_g)
1234       IF (ALL(deepSOM_s == val_exp)) THEN
1235          deepSOM_s(:,:,:,icarbon) = 30.
1236          deepSOM_s(:,:,:,initrogen) = deepSOM_s(:,:,:,icarbon) / CN_target_islow_ref
1237       ENDIF
1238
1239       CALL restget_p (rest_id_stomate, 'deepSOM_p', nbp_glo, ngrnd, nvm, nelements, itime, &
1240          .TRUE., deepSOM_p, 'gather', nbp_glo, index_g)
1241       IF (ALL(deepSOM_p == val_exp)) THEN
1242          deepSOM_p(:,:,:,icarbon) = 50.
1243          deepSOM_p(:,:,:,initrogen) = deepSOM_p(:,:,:,icarbon) / CN_target_ipassive_ref
1244       ENDIF
1245
1246       CALL restget_p (rest_id_stomate, 'O2_soil', nbp_glo, ngrnd, nvm, itime, &
1247            .TRUE., O2_soil, 'gather', nbp_glo, index_g)
1248       IF (ALL(O2_soil == val_exp)) O2_soil = O2_init_conc
1249
1250       CALL restget_p (rest_id_stomate,'CH4_soil', nbp_glo, ngrnd, nvm, itime, &
1251            .TRUE., CH4_soil, 'gather', nbp_glo, index_g)
1252       IF (ALL(CH4_soil == val_exp)) CH4_soil = CH4_init_conc
1253
1254       CALL restget_p (rest_id_stomate, 'O2_snow', nbp_glo, nsnow, nvm, itime, &
1255            .TRUE., O2_snow, 'gather', nbp_glo, index_g)
1256       IF (ALL(O2_snow == val_exp)) O2_snow = O2_init_conc
1257
1258 
1259       CH4_snow(:,:,:) = val_exp
1260       CALL restget_p (rest_id_stomate,'CH4_snow', nbp_glo, nsnow, nvm, itime, &
1261            .TRUE., CH4_snow, 'gather', nbp_glo, index_g)
1262       IF (ALL(CH4_snow == val_exp)) CH4_snow = CH4_init_conc
1263   
1264       CALL restget_p (rest_id_stomate,'heat_Zimov', nbp_glo, ngrnd, nvm, itime, &
1265            .TRUE., heat_Zimov, 'gather', nbp_glo, index_g)
1266       IF (ALL(heat_Zimov == val_exp)) THEN
1267          heat_Zimov(:,:,:) = 0.0
1268       ENDIF
1269
1270       CALL restget_p (rest_id_stomate,'altmax', nbp_glo, nvm, 1, itime, &
1271            .TRUE., altmax, 'gather', nbp_glo, index_g)
1272       IF (ALL(altmax(:,:) == val_exp)) THEN
1273          altmax(:,:) = 0.0
1274       ENDIF
1275
1276       CALL restget_p (rest_id_stomate,'depth_organic_soil', nbp_glo, 1, 1, itime, &
1277           .TRUE., depth_organic_soil(:), 'gather', nbp_glo, index_g)
1278       IF (ALL(depth_organic_soil(:) == val_exp)) THEN
1279           depth_organic_soil(:) = 0.0
1280           read_input_depth_organic_soil = .TRUE.
1281       ENDIF
1282
1283       fixed_cryoturbation_depth(:,:) = val_exp
1284       CALL restget_p (rest_id_stomate,'fixed_cryoturb_depth', nbp_glo, nvm, 1, itime, &
1285            .TRUE., fixed_cryoturbation_depth, 'gather', nbp_glo, index_g)
1286       IF (ALL(fixed_cryoturbation_depth(:,:) == val_exp)) THEN
1287          fixed_cryoturbation_depth(:,:) = 0.0
1288       ENDIF
1289       
1290    ENDIF
1291   
1292
1293    nflux_prod(:) = val_exp
1294    var_name = 'nfluxprod'
1295    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
1296         &              .TRUE., nflux_prod, 'gather', nbp_glo, index_g)
1297    IF (ALL(nflux_prod(:) == val_exp)) nflux_prod(:) = zero
1298
1299    nflux_prod_harvest(:) = val_exp
1300    var_name = 'nfluxprodhar'
1301    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
1302         &              .TRUE., nflux_prod_harvest, 'gather', nbp_glo, index_g)
1303    IF (ALL(nflux_prod_harvest(:) == val_exp)) nflux_prod_harvest(:) = zero
1304    !-
1305    ! 19. Spinup
1306    !-
1307    IF (spinup_analytic) THEN
1308
1309       ! If the variable is not in the restart file, then zero will be used as default value
1310       CALL restget_p (rest_id_stomate, 'Global_years', itime, .TRUE., zero, global_years)
1311
1312       nbp_accu(:) = val_exp
1313       var_name = 'nbp_sum'
1314       CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
1315            &              .TRUE., nbp_accu, 'gather', nbp_glo, index_g)
1316       IF (ALL(nbp_accu(:) == val_exp)) nbp_accu(:) = zero   
1317
1318       nbp_flux(:) = val_exp
1319       var_name = 'nbp_flux'
1320       CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
1321            &              .TRUE., nbp_flux, 'gather', nbp_glo, index_g)
1322       IF (ALL(nbp_flux(:) == val_exp)) nbp_flux(:) = zero     
1323
1324       !-
1325       ok_equilibrium_real(:) = val_exp
1326       var_name = 'ok_equilibrium'
1327       CALL restget_p (rest_id_stomate, var_name, nbp_glo , 1  , 1, itime, &
1328            &                .TRUE., ok_equilibrium_real,'gather', nbp_glo, index_g)
1329       IF (ALL(ok_equilibrium_real(:) == val_exp)) ok_equilibrium_real(:) = zero
1330       WHERE(ok_equilibrium_real(:) >= 0.5) 
1331          ok_equilibrium = .TRUE.
1332       ELSEWHERE
1333          ok_equilibrium = .FALSE.
1334       ENDWHERE
1335
1336       MatrixV(:,:,:,:) = val_exp
1337       CALL restget_p (rest_id_stomate, 'MatrixV', nbp_glo, nvm, nbpools, nbpools, itime, &
1338                  &                     .TRUE., MatrixV, 'gather', nbp_glo, index_g)
1339       ! If nothing is found in the restart file, we initialize each submatrix by identity
1340       IF (ALL(MatrixV(:,:,:,:) == val_exp))  THEN     
1341          MatrixV(:,:,:,:) = zero       
1342          DO l = 1,nbpools           
1343             MatrixV(:,:,l,l) = un           
1344          END DO
1345       END IF
1346
1347       VectorU(:,:,:)  = val_exp
1348       CALL restget_p &
1349            &    (rest_id_stomate, 'Vector_U', nbp_glo, nvm, nbpools, itime, &
1350            &     .TRUE., VectorU, 'gather', nbp_glo, index_g)
1351       IF (ALL(VectorU == val_exp))  VectorU = zero
1352       
1353       previous_stock(:,:,:)  = val_exp
1354       CALL restget_p &
1355            &    (rest_id_stomate, 'previous_stock', nbp_glo, nvm, nbpools, itime, &
1356            &     .TRUE., previous_stock, 'gather', nbp_glo, index_g)
1357       IF (ALL(previous_stock == val_exp))  previous_stock = undef_sechiba
1358       
1359       current_stock(:,:,:)  = val_exp
1360       CALL restget_p &
1361            &    (rest_id_stomate, 'current_stock', nbp_glo, nvm, nbpools, itime, &
1362            &     .TRUE., current_stock, 'gather', nbp_glo, index_g)
1363       IF (ALL(current_stock == val_exp))  current_stock = zero
1364
1365       CN_som_litter_longterm(:,:,:)  = val_exp
1366       CALL restget_p &
1367            &    (rest_id_stomate, 'CN_longterm', nbp_glo, nvm, nbpools, itime, &
1368            &     .TRUE., CN_som_litter_longterm, 'gather', nbp_glo, index_g)
1369       IF (ALL(CN_som_litter_longterm == val_exp))  CN_som_litter_longterm = zero
1370
1371       ! If the variable is not in the restart file, then dt_sechiba/one_day will be used as default value
1372       CALL restget_p(rest_id_stomate, 'tau_CN_longterm', itime, .TRUE., dt_sechiba/one_day, tau_CN_longterm)
1373 
1374    ENDIF ! spinup_matrix_method
1375
1376    KF(:,:) = val_exp
1377    var_name = 'KF'
1378    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1379         &                .TRUE., KF, 'gather', nbp_glo, index_g)
1380    ! I don't want to set it equal to zero, since this is a problem if these
1381    ! values are not here!  Better it blows up later on
1382    !IF (ALL(KF(:,:) == val_exp)) KF(:,:) = zero
1383
1384    k_latosa_adapt(:,:) = val_exp
1385    var_name = 'k_latosa_adapt'
1386    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1387         &                .TRUE., k_latosa_adapt, 'gather', nbp_glo, index_g)
1388    DO m = 1,nvm
1389       IF (ALL(k_latosa_adapt(:,m) == val_exp)) k_latosa_adapt(:,m) = k_latosa_min(m)
1390    ENDDO
1391
1392    rue_longterm(:,:) = val_exp
1393    var_name = 'rue_longterm'
1394    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, &
1395         &        .TRUE., rue_longterm(:,:), 'gather', nbp_glo, index_g)
1396    IF (ALL(rue_longterm(:,:) == val_exp)) rue_longterm(:,:) = 1.
1397
1398    cn_leaf_min_season(:,:) = val_exp 
1399    var_name = 'cn_leaf_min_season' 
1400    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, & 
1401         &              .TRUE., cn_leaf_min_season, 'gather', nbp_glo, index_g) 
1402    IF ( ALL(cn_leaf_min_season(:,:) == val_exp) ) THEN
1403       DO m=1,nvm 
1404          cn_leaf_min_season(:,m) = cn_leaf_init_2D(:,m) 
1405       ENDDO
1406    ENDIF
1407   
1408    nstress_season(:,:) = val_exp 
1409    var_name = 'nstress_season' 
1410    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, & 
1411         &              .TRUE., nstress_season, 'gather', nbp_glo, index_g) 
1412    IF ( ALL(nstress_season(:,:) == val_exp) ) nstress_season(:,:)=1.0 
1413   
1414    soil_n_min(:,:,:) = val_exp 
1415    CALL restget_p (rest_id_stomate, 'soil_n_min', nbp_glo, nvm, nnspec, itime, & 
1416         &              .TRUE., soil_n_min, 'gather', nbp_glo, index_g) 
1417!    IF ( ALL(soil_n_min(:,:,k) == val_exp) ) soil_n_min(:,:,k)=100000000.
1418    IF ( ALL(soil_n_min == val_exp) ) soil_n_min=0. 
1419
1420    p_O2(:,:) = val_exp 
1421    var_name = 'p_O2'
1422    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, & 
1423         &              .TRUE., p_O2(:,:), 'gather', nbp_glo, index_g) 
1424    IF ( ALL(p_O2(:,:) == val_exp) ) p_O2(:,:)=200 
1425 
1426    bact(:,:) = val_exp 
1427    var_name = 'bact'
1428    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, & 
1429         &              .TRUE., bact(:,:), 'gather', nbp_glo, index_g) 
1430    IF ( ALL(bact(:,:) == val_exp) ) bact(:,:)=10 
1431 
1432
1433    ! Read assim_param from restart file. The initialization of assim_param will
1434    ! be done in stomate_var_init if the variable is not in the restart file.
1435    assim_param(:,:,:)  = val_exp
1436    CALL restget_p &
1437         &    (rest_id_stomate, 'assim_param', nbp_glo, nvm, npco2, itime, &
1438         &     .TRUE., assim_param, 'gather', nbp_glo, index_g)
1439
1440
1441    CALL restget_p (rest_id_stomate, 'harvest_above', nbp_glo, nelements  , 1, itime, & 
1442         .TRUE., harvest_above(:,:), 'gather', nbp_glo, index_g) 
1443    IF ( ALL(harvest_above(:,:) == val_exp) ) harvest_above(:,:) = 0. 
1444
1445    sugar_load(:,:) = val_exp
1446    var_name = 'sugar_load'
1447    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1448         &   .TRUE., sugar_load, 'gather', nbp_glo, index_g)
1449    IF (ALL(sugar_load(:,:) ==val_exp)) sugar_load(:,:) = un
1450
1451    IF (printlev >= 4) WRITE(numout,*) 'Leaving readstart'
1452    !-----------------------
1453  END SUBROUTINE readstart
1454
1455!! ================================================================================================================================
1456!! SUBROUTINE   : writerestart
1457!!
1458!>\BRIEF        Write all variables for stomate from restart file.
1459!!
1460!! DESCRIPTION  : Write all variables for stomate from restart file.
1461!!               
1462!! \n
1463!_ ================================================================================================================================
1464
1465  SUBROUTINE writerestart &
1466       & (npts, index, dt_days, date_loc, &
1467       &  ind, adapted, regenerate, moiavail_daily, gdd_init_date, litterhum_daily, &
1468       &  t2m_daily, t2m_min_daily, tsurf_daily, tsoil_daily, &
1469       &  soilhum_daily, precip_daily, gpp_daily, npp_daily, &
1470       &  turnover_daily, moiavail_month, moiavail_week, moiavail_growingseason,&
1471       &  t2m_longterm, tau_longterm, t2m_month, t2m_week, &
1472       &  tsoil_month, soilhum_month, fireindex, firelitter, &
1473       &  maxmoiavail_lastyear, maxmoiavail_thisyear, &
1474       &  minmoiavail_lastyear, minmoiavail_thisyear, &
1475       &  maxgppweek_lastyear, maxgppweek_thisyear, &
1476       &  gdd0_lastyear, gdd0_thisyear, precip_lastyear, precip_thisyear, &
1477       &  gdd_m5_dormance, gdd_from_growthinit, gdd_midwinter, ncd_dormance, ngd_minus5, &
1478       &  PFTpresent, npp_longterm, croot_longterm, lm_lastyearmax, lm_thisyearmax, &
1479       &  maxfpc_lastyear, maxfpc_thisyear, &
1480       &  turnover_longterm, gpp_week, biomass, resp_maint_part, &
1481       &  leaf_age, leaf_frac, senescence, when_growthinit, age, &
1482       &  resp_hetero, resp_maint, resp_growth,resp_excess, co2_fire, co2_to_bm_dgvm, &
1483       &  n_to_bm, veget_lastlight, everywhere, need_adjacent, RIP_time, &
1484       &  time_hum_min, hum_min_dormance, &
1485       &  litter, dead_leaves, &
1486       &  som, lignin_struc, lignin_wood, turnover_time, &
1487       &  co2_flux, fco2_lu, fco2_wh, fco2_ha,  &
1488       &  prod10,prod100 ,flux10, flux100, &
1489       &  convflux, cflux_prod10, cflux_prod100, & 
1490       &  prod10_harvest,prod100_harvest ,flux10_harvest, flux100_harvest, &
1491       &  convflux_harvest, cflux_prod10_harvest, cflux_prod100_harvest, &
1492       &  convfluxpft, fDeforestToProduct, fLulccResidue, fHarvestToProduct, &
1493       &  woodharvestpft, bm_to_litter, tree_bm_to_litter, carb_mass_total, nflux_prod, &
1494       &  nflux_prod_harvest, Tseason, Tseason_length, Tseason_tmp, & 
1495       &  Tmin_spring_time, begin_leaves, onset_date, &
1496       &  global_years, ok_equilibrium, nbp_accu, nbp_flux, &
1497       &  MatrixV, VectorU, previous_stock, current_stock, assim_param, &
1498       &  CN_som_litter_longterm, tau_CN_longterm, KF, k_latosa_adapt, &
1499       &  rue_longterm, cn_leaf_min_season, nstress_season, soil_n_min, p_O2, bact, &
1500       &  deepSOM_a, deepSOM_s, deepSOM_p, O2_soil, CH4_soil, O2_snow, CH4_snow, &
1501       &  heat_Zimov, altmax, depth_organic_soil, fixed_cryoturbation_depth, harvest_above, sugar_load) 
1502
1503    !---------------------------------------------------------------------
1504    !- write restart file
1505    !---------------------------------------------------------------------
1506    !-
1507    ! 0 declarations
1508    !-
1509    ! 0.1 input
1510    !-
1511    ! Domain size
1512    INTEGER(i_std),INTENT(in) :: npts
1513    ! Indices of the points on the map
1514    INTEGER(i_std),DIMENSION(npts),INTENT(in) :: index
1515    ! time step of STOMATE in days
1516    REAL(r_std),INTENT(in) :: dt_days
1517    ! date_loc (d)
1518    INTEGER(i_std),INTENT(in) :: date_loc
1519    ! density of individuals (1/m**2)
1520    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: ind
1521    ! Winter too cold? between 0 and 1
1522    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: adapted
1523    ! Winter sufficiently cold? between 0 and 1
1524    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: regenerate
1525    ! daily moisture availability
1526    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: moiavail_daily
1527    ! gdd init date
1528    REAL(r_std),DIMENSION(npts,2),INTENT(in) :: gdd_init_date
1529    ! daily litter humidity
1530    REAL(r_std),DIMENSION(npts),INTENT(in) :: litterhum_daily
1531    ! daily 2 meter temperatures (K)
1532    REAL(r_std),DIMENSION(npts),INTENT(in) :: t2m_daily
1533    ! daily minimum 2 meter temperatures (K)
1534    REAL(r_std),DIMENSION(npts),INTENT(in) :: t2m_min_daily
1535    ! daily surface temperatures (K)
1536    REAL(r_std),DIMENSION(npts),INTENT(in) :: tsurf_daily
1537    ! daily soil temperatures (K)
1538    REAL(r_std),DIMENSION(npts,nslm),INTENT(in) :: tsoil_daily
1539    ! daily soil humidity
1540    REAL(r_std),DIMENSION(npts,nslm),INTENT(in) :: soilhum_daily
1541    ! daily precipitations (mm/day) (for phenology)
1542    REAL(r_std),DIMENSION(npts),INTENT(in) :: precip_daily
1543    ! daily gross primary productivity (gC/m**2/day)
1544    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: gpp_daily
1545    ! daily net primary productivity (gC/m**2/day)
1546    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: npp_daily
1547    ! daily turnover rates (gC/m**2/day)
1548    REAL(r_std),DIMENSION(npts,nvm,nparts,nelements),INTENT(in) :: turnover_daily
1549    ! "monthly" moisture availability
1550    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: moiavail_month
1551    ! "weekly" moisture availability
1552    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: moiavail_week
1553    ! mean growing season moisture availability
1554    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: moiavail_growingseason
1555    ! "long term" 2 meter temperatures (K)
1556    REAL(r_std),DIMENSION(npts),INTENT(in) :: t2m_longterm
1557    ! "tau_longterm"
1558    REAL(r_std), INTENT(IN)             :: tau_longterm
1559    ! "monthly" 2 meter temperatures (K)
1560    REAL(r_std),DIMENSION(npts),INTENT(in) :: t2m_month
1561    ! "seasonal" 2 meter temperatures (K)
1562    REAL(r_std),DIMENSION(npts),INTENT(in)      :: Tseason
1563    ! temporary variable to calculate Tseason
1564    REAL(r_std),DIMENSION(npts),INTENT(in)      :: Tseason_length
1565    ! temporary variable to calculate Tseason
1566    REAL(r_std),DIMENSION(npts),INTENT(in)      :: Tseason_tmp
1567    REAL(r_std),DIMENSION(npts,nvm),INTENT(in)  :: Tmin_spring_time
1568    REAL(r_std),DIMENSION(npts,nvm),INTENT(in)  :: onset_date
1569    LOGICAL,DIMENSION(npts,nvm),INTENT(in)      :: begin_leaves
1570
1571    ! "weekly" 2 meter temperatures (K)
1572    REAL(r_std),DIMENSION(npts),INTENT(in) :: t2m_week
1573    ! "monthly" soil temperatures (K)
1574    REAL(r_std),DIMENSION(npts,nslm),INTENT(in) :: tsoil_month
1575    ! "monthly" soil humidity
1576    REAL(r_std),DIMENSION(npts,nslm),INTENT(in) :: soilhum_month
1577    ! Probability of fire
1578    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: fireindex
1579    ! Longer term total litter above the ground, gC/m**2 of ground
1580    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: firelitter
1581    ! last year's maximum moisture availability
1582    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: maxmoiavail_lastyear
1583    ! this year's maximum moisture availability
1584    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: maxmoiavail_thisyear
1585    ! last year's minimum moisture availability
1586    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: minmoiavail_lastyear
1587    ! this year's minimum moisture availability
1588    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: minmoiavail_thisyear
1589    ! last year's maximum weekly GPP
1590    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: maxgppweek_lastyear
1591    ! this year's maximum weekly GPP
1592    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: maxgppweek_thisyear
1593    ! last year's annual GDD0
1594    REAL(r_std),DIMENSION(npts),INTENT(in) :: gdd0_lastyear
1595    ! this year's annual GDD0
1596    REAL(r_std),DIMENSION(npts),INTENT(in) :: gdd0_thisyear
1597    ! last year's annual precipitation (mm/year)
1598    REAL(r_std),DIMENSION(npts),INTENT(in) :: precip_lastyear
1599    ! this year's annual precipitation (mm/year)
1600    REAL(r_std),DIMENSION(npts),INTENT(in) :: precip_thisyear
1601    ! growing degree days, threshold -5 deg C (for phenology)
1602    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: gdd_m5_dormance
1603    ! growing degree days, from begin of season (crops)
1604    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: gdd_from_growthinit
1605    ! growing degree days since midwinter (for phenology)
1606    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: gdd_midwinter
1607    ! number of chilling days since leaves were lost (for phenology)
1608    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: ncd_dormance
1609    ! number of growing days, threshold -5 deg C (for phenology)
1610    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: ngd_minus5
1611    ! PFT exists (equivalent to fpc_max > 0 for natural PFTs)
1612    LOGICAL,DIMENSION(npts,nvm),INTENT(in) :: PFTpresent
1613    ! "long term" net primary productivity (gC/m**2/year)
1614    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: npp_longterm
1615    ! "long term" root carbon mass (gC/m**2/year)
1616    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: croot_longterm
1617    ! last year's maximum leaf mass, for each PFT (gC/m**2)
1618    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: lm_lastyearmax
1619    ! this year's maximum leaf mass, for each PFT (gC/m**2)
1620    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: lm_thisyearmax
1621    ! last year's maximum fpc for each natural PFT, on ground
1622    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: maxfpc_lastyear
1623    ! this year's maximum fpc for each PFT,
1624    ! on *total* ground (see stomate_season)
1625    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: maxfpc_thisyear
1626    ! "long term" turnover rate (gC/m**2/year)
1627    REAL(r_std),DIMENSION(npts,nvm,nparts,nelements),INTENT(in) :: turnover_longterm
1628    ! "weekly" GPP (gC/day/(m**2 covered)
1629    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: gpp_week
1630    ! biomass (gC/m**2)
1631    REAL(r_std),DIMENSION(npts,nvm,nparts,nelements),INTENT(in) :: biomass
1632    ! maintenance respiration (gC/m**2)
1633    REAL(r_std),DIMENSION(npts,nvm,nparts),INTENT(in) :: resp_maint_part
1634    ! leaf age (days)
1635    REAL(r_std),DIMENSION(npts,nvm,nleafages),INTENT(in) :: leaf_age
1636    ! fraction of leaves in leaf age class
1637    REAL(r_std),DIMENSION(npts,nvm,nleafages),INTENT(in) :: leaf_frac
1638    ! is the plant senescent ?
1639    ! (only for deciduous trees - carbohydrate reserve)
1640    LOGICAL,DIMENSION(npts,nvm),INTENT(in) :: senescence
1641    ! how many days ago was the beginning of the growing season
1642    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: when_growthinit
1643    ! mean age (years)
1644    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: age
1645    ! heterotrophic respiration (gC/day/m**2)
1646    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: resp_hetero
1647    ! maintenance respiration (gC/day/m**2)
1648    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: resp_maint
1649    ! growth respiration (gC/day/m**2)
1650    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: resp_growth
1651    ! excess respiration (gC/day/m**2)
1652    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: resp_excess
1653    ! carbon emitted into the atmosphere by fire (living and dead biomass)
1654    ! (in gC/m**2/time step)
1655    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: co2_fire
1656    ! biomass uptaken (gC/(m**2 of total ground)/day)
1657    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: co2_to_bm_dgvm
1658    ! biomass uptaken (gN/(m**2 of total ground)/day)
1659    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: n_to_bm
1660    ! vegetation fractions (on ground) after last light competition
1661    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: veget_lastlight
1662    ! is the PFT everywhere in the grid box or very localized
1663    ! (after its introduction)
1664    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: everywhere
1665    ! in order for this PFT to be introduced,
1666    ! does it have to be present in an adjacent grid box?
1667    LOGICAL,DIMENSION(npts,nvm),INTENT(in) :: need_adjacent
1668    ! How much time ago was the PFT eliminated for the last time (y)
1669    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: RIP_time
1670    ! time elapsed since strongest moisture availability (d)
1671    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: time_hum_min
1672    ! minimum moisture during dormance
1673    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: hum_min_dormance
1674    ! fraction of litter above the ground belonging to different PFTs
1675    REAL(r_std),DIMENSION(npts,nlitt,nvm,nlevs,nelements),INTENT(in) :: litter
1676    ! dead leaves on ground, per PFT, metabolic and structural,
1677    ! in gC/(m**2 of ground)
1678    REAL(r_std),DIMENSION(npts,nvm,nlitt),INTENT(in) :: dead_leaves
1679    ! SOM pool: active, slow, or passive, (gC(orN)/m**2)
1680    REAL(r_std),DIMENSION(npts,ncarb,nvm,nelements),INTENT(in) :: som
1681   ! ratio Lignine/Carbon in structural litter, above and below ground, (gC/m**2)
1682    REAL(r_std),DIMENSION(npts,nvm,nlevs),INTENT(in) :: lignin_struc
1683    ! turnover_time of leaves
1684    ! ratio Lignine/Carbon in woody litter, above and below ground, (gC/m**2)
1685    REAL(r_std),DIMENSION(npts,nvm,nlevs),INTENT(in) :: lignin_wood
1686    ! turnover_time of leaves
1687    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: turnover_time
1688    REAL(r_std), DIMENSION(npts,nelements), INTENT(in)          :: harvest_above
1689    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                :: sugar_load  !! Relative sugar loading of the labile pool (unitless)
1690
1691    ! For Spinup matrix resolution
1692    INTEGER(i_std), INTENT(in) :: global_years   
1693    LOGICAL, DIMENSION(npts), INTENT(in) :: ok_equilibrium
1694    REAL(r_std), DIMENSION(npts), INTENT(in) :: nbp_accu  !! Accumulated Net Biospheric Production over the year
1695    REAL(r_std), DIMENSION(npts), INTENT(in) :: nbp_flux  !! Net Biospheric Production over the year
1696    !-
1697    REAL(r_std), DIMENSION(npts,nvm,nbpools,nbpools), INTENT(in) :: MatrixV
1698    REAL(r_std), DIMENSION(npts,nvm,nbpools), INTENT(in) :: VectorU
1699    REAL(r_std), DIMENSION(npts,nvm,nbpools), INTENT(in) :: previous_stock
1700    REAL(r_std), DIMENSION(npts,nvm,nbpools), INTENT(in) :: current_stock
1701    REAL(r_std), DIMENSION(npts,nvm,nbpools), INTENT(in) :: CN_som_litter_longterm !! Longterm CN ratio of litter and som pools (gC/gN)
1702    REAL(r_std), INTENT(in)                              :: tau_CN_longterm  !! Counter used for calculating the longterm CN ratio of SOM and litter pools (seconds)
1703    REAL(r_std), DIMENSION(npts,nvm,npco2),   INTENT(in) :: assim_param
1704    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)         :: KF                !! Scaling factor to convert sapwood mass
1705                                                                              !! into leaf mass (m)
1706    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)         :: k_latosa_adapt    !! Leaf to sapwood area adapted for water 
1707                                                                              !! stress. Adaptation takes place at the 
1708                                                                              !! end of the year (m)
1709    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)         :: rue_longterm      !! Longterm radiation use efficiency
1710
1711    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)         :: cn_leaf_min_season    !! Seasonal CN ratio of leaves
1712    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)         :: nstress_season    !! N-related seasonal stress (used for allocation)
1713   
1714    REAL(r_std), DIMENSION(npts,nvm,nnspec), INTENT(in)  :: soil_n_min        !! mineral nitrogen in the soil (gN/m**2) 
1715                                                                              !! (first index=npts, second index=nvm, third index=nnspec)   
1716    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)        :: p_O2               !! partial pressure of oxigen in the soil (hPa)
1717                                                                              !! (first index=npts, second index=nvm)
1718                                                       
1719    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)        :: bact               !! denitrifier biomass (gC/m**2)
1720                                                                                                   !! (first index=npts, second index=nvm)
1721
1722    ! Variables related to ok_soil_carbon_discretization
1723    REAL(r_std), DIMENSION(npts,ngrnd,nvm,nelements),INTENT(in) :: deepSOM_a
1724    REAL(r_std), DIMENSION(npts,ngrnd,nvm,nelements),INTENT(in) :: deepSOM_s
1725    REAL(r_std), DIMENSION(npts,ngrnd,nvm,nelements),INTENT(in) :: deepSOM_p
1726    REAL(r_std), DIMENSION(npts,ngrnd,nvm),INTENT(in)           :: O2_soil
1727    REAL(r_std), DIMENSION(npts,ngrnd,nvm),INTENT(in)           :: CH4_soil
1728    REAL(r_std), DIMENSION(npts,nsnow,nvm),INTENT(in)           :: O2_snow
1729    REAL(r_std), DIMENSION(npts,nsnow,nvm),INTENT(in)           :: CH4_snow
1730    REAL(r_std), DIMENSION(npts,ngrnd,nvm), INTENT(in)          :: heat_Zimov
1731    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                :: altmax
1732    REAL(r_std), DIMENSION(npts),INTENT(in)                     :: depth_organic_soil
1733    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                :: fixed_cryoturbation_depth
1734 
1735    !-
1736    ! 0.2 local
1737    !-
1738    ! date, real
1739    REAL(r_std) :: date_real
1740    ! PFT exists (equivalent to fpc_max > 0 for natural PFTs), real
1741    REAL(r_std),DIMENSION(npts,nvm) :: PFTpresent_real
1742    ! is the plant senescent ?
1743    ! (only for deciduous trees - carbohydrate reserve), real
1744    REAL(r_std),DIMENSION(npts,nvm) :: senescence_real
1745    REAL(r_std),DIMENSION(npts,nvm) :: begin_leaves_real
1746
1747    ! in order for this PFT to be introduced,
1748    ! does it have to be present in an adjacent grid box? - real
1749    REAL(r_std),DIMENSION(npts,nvm) :: need_adjacent_real
1750    ! To store variables names for I/O
1751    CHARACTER(LEN=80) :: var_name
1752    ! string suffix indicating an index
1753    CHARACTER(LEN=10) :: part_str
1754    ! string suffix indicating litter type
1755    CHARACTER(LEN=4),DIMENSION(nlitt) :: litter_str
1756    ! string suffix indicating level
1757    CHARACTER(LEN=2),DIMENSION(nlevs) :: level_str
1758    ! temporary storage
1759    REAL(r_std),DIMENSION(1) :: xtmp
1760    ! index
1761    INTEGER(i_std) :: j,k,l,m
1762    CHARACTER(LEN=2),DIMENSION(nelements) :: element_str  !! string suffix indicating element
1763    REAL(r_std), DIMENSION(1) :: temp_global_years
1764    CHARACTER(LEN=6),DIMENSION(nbpools) :: pools_str
1765    REAL(r_std), DIMENSION(npts) :: ok_equilibrium_real   
1766
1767    ! land cover change variables
1768    ! products remaining in the 10/100 year-turnover pool after the annual release for each compartment
1769    ! (10 or 100 + 1 : input from year of land cover change)
1770    REAL(r_std),DIMENSION(npts,nvm),INTENT(in)                            :: co2_flux
1771    REAL(r_std),DIMENSION(npts),INTENT(in)                                :: fco2_lu
1772    REAL(r_std),DIMENSION(npts),INTENT(in)                                :: fco2_wh
1773    REAL(r_std),DIMENSION(npts),INTENT(in)                                :: fco2_ha
1774    REAL(r_std),DIMENSION(npts,0:10),INTENT(in)                           :: prod10
1775    REAL(r_std),DIMENSION(npts,0:100),INTENT(in)                          :: prod100
1776    ! annual release from the 10/100 year-turnover pool compartments
1777    REAL(r_std),DIMENSION(npts,10),INTENT(in)                           :: flux10
1778    REAL(r_std),DIMENSION(npts,100),INTENT(in)                          :: flux100
1779    REAL(r_std), DIMENSION(npts), INTENT(in)                            :: convflux
1780    REAL(r_std), DIMENSION(npts), INTENT(in)                            :: cflux_prod10
1781    REAL(r_std), DIMENSION(npts), INTENT(in)                            :: cflux_prod100
1782
1783    ! wood harvest variables
1784    ! products remaining in the 10/100 year-turnover pool after the annual release for each compartment
1785    ! (10 or 100 + 1 : input from year of land cover change)
1786    REAL(r_std),DIMENSION(npts,0:10),INTENT(in)                           :: prod10_harvest
1787    REAL(r_std),DIMENSION(npts,0:100),INTENT(in)                          :: prod100_harvest
1788    ! annual release from the 10/100 year-turnover pool compartments
1789    REAL(r_std),DIMENSION(npts,10),INTENT(in)                           :: flux10_harvest
1790    REAL(r_std),DIMENSION(npts,100),INTENT(in)                          :: flux100_harvest
1791    REAL(r_std), DIMENSION(npts), INTENT(in)                            :: convflux_harvest
1792    REAL(r_std), DIMENSION(npts), INTENT(in)                            :: cflux_prod10_harvest
1793    REAL(r_std), DIMENSION(npts), INTENT(in)                            :: cflux_prod100_harvest
1794    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: convfluxpft
1795    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: fDeforestToProduct
1796    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: fLulccResidue
1797    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: fHarvestToProduct
1798    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: woodharvestpft
1799    REAL(r_std),DIMENSION(npts,nvm,nparts,nelements),INTENT(in)         :: bm_to_litter
1800    REAL(r_std),DIMENSION(npts,nvm,nparts,nelements),INTENT(in)         :: tree_bm_to_litter
1801    REAL(r_std),DIMENSION(npts),INTENT(in)                              :: carb_mass_total
1802    REAL(r_std), DIMENSION(npts), INTENT(in)                            :: nflux_prod
1803    REAL(r_std), DIMENSION(npts), INTENT(in)                            :: nflux_prod_harvest
1804    !---------------------------------------------------------------------
1805    IF (printlev >= 3) WRITE(numout,*) 'Entering writerestart'
1806    !-
1807    ! 1 string definitions
1808    !-
1809    DO l=1,nlitt
1810       IF     (l == imetabolic) THEN
1811          litter_str(l) = 'met'
1812       ELSEIF (l == istructural) THEN
1813          litter_str(l) = 'str'
1814       ELSEIF (l == iwoody) THEN
1815          litter_str(l) = 'wood'
1816       ELSE
1817          CALL ipslerr_p(3,'stomate_io writerestart','Define litter_str','','')
1818       ENDIF
1819    ENDDO
1820    !-
1821    DO l=1,nlevs
1822       IF     (l == iabove) THEN
1823          level_str(l) = 'ab'
1824       ELSEIF (l == ibelow) THEN
1825          level_str(l) = 'be'
1826       ELSE
1827          CALL ipslerr_p(3,'stomate_io writerestart','Define level_str','','')
1828       ENDIF
1829    ENDDO
1830    !-
1831    DO l=1,nelements
1832       IF     (l == icarbon) THEN
1833          element_str(l) = ''
1834       ELSEIF (l == initrogen) THEN
1835          element_str(l) = '_n'
1836       ELSE
1837          CALL ipslerr_p(3,'stomate_io writerestart','Define element_str','','')
1838       ENDIF
1839    ENDDO
1840    !-
1841    pools_str(1:nbpools) =(/'str_ab ','str_be ','met_ab ','met_be ','wood_ab','wood_be', & 
1842         & 'actif  ','slow   ','passif ','surface'/) 
1843
1844    !-
1845    IF (is_root_prc) THEN
1846       CALL ioconf_setatt_p ('UNITS','-')
1847       CALL ioconf_setatt_p ('LONG_NAME',' ')
1848    ENDIF
1849    !-
1850    ! 2 run control
1851    !-
1852    ! 2.2 time step of STOMATE in days
1853    !-
1854    CALL restput_p (rest_id_stomate, 'dt_days', itime, dt_days)
1855    !-
1856    ! 2.3 date
1857    !-
1858    CALL restput_p (rest_id_stomate, 'date', itime, date_loc)
1859    !-
1860    ! 3 daily meteorological variables
1861    !-
1862    var_name = 'moiavail_daily'
1863    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
1864         &                moiavail_daily, 'scatter', nbp_glo, index_g)
1865    !-
1866    var_name = 'gdd_init_date'
1867    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    2, 1, itime, &
1868         &              gdd_init_date, 'scatter', nbp_glo, index_g)
1869    !-
1870    var_name = 'litterhum_daily'
1871    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    1, 1, itime, &
1872         &                litterhum_daily, 'scatter', nbp_glo, index_g)
1873    !-
1874    var_name = 't2m_daily'
1875    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    1, 1, itime, &
1876         &                t2m_daily, 'scatter', nbp_glo, index_g)
1877    !-
1878    var_name = 't2m_min_daily'
1879    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    1, 1, itime, &
1880         &                t2m_min_daily, 'scatter', nbp_glo, index_g)
1881    !-
1882    var_name = 'tsurf_daily'
1883    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    1, 1, itime, &
1884         &                tsurf_daily, 'scatter', nbp_glo, index_g)
1885    !-
1886    var_name = 'tsoil_daily'
1887    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nslm, 1, itime, &
1888         &                tsoil_daily, 'scatter', nbp_glo, index_g)
1889    !-
1890    var_name = 'soilhum_daily'
1891    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nslm, 1, itime, &
1892         &                soilhum_daily, 'scatter', nbp_glo, index_g)
1893    !-
1894    var_name = 'precip_daily'
1895    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    1, 1, itime, &
1896         &                precip_daily, 'scatter', nbp_glo, index_g)
1897    !-
1898    ! 4 productivities
1899    !-
1900    var_name = 'gpp_daily'
1901    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
1902         &                gpp_daily, 'scatter', nbp_glo, index_g)
1903    !-
1904    var_name = 'npp_daily'
1905    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
1906         &                npp_daily, 'scatter', nbp_glo, index_g)
1907    !-
1908    CALL restput_p (rest_id_stomate, 'turnover_daily', nbp_glo, nvm, nparts, nelements, itime, &
1909         &                   turnover_daily, 'scatter', nbp_glo, index_g)
1910    !-
1911    ! 5 monthly meteorological variables
1912    !-
1913    var_name = 'moiavail_month'
1914    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
1915         &                moiavail_month, 'scatter', nbp_glo, index_g)
1916    !-
1917    var_name = 'moiavail_week'
1918    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
1919         &                moiavail_week, 'scatter', nbp_glo, index_g)
1920    !-
1921    var_name = 'moiavail_grow'
1922    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
1923         &                moiavail_growingseason, 'scatter', nbp_glo, index_g)
1924    !-
1925    var_name = 't2m_longterm'
1926    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    1, 1, itime, &
1927         &                t2m_longterm, 'scatter', nbp_glo, index_g)
1928   
1929    CALL restput_p (rest_id_stomate, 'tau_longterm', itime, tau_longterm)
1930       
1931
1932    var_name = 't2m_month'
1933    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    1, 1, itime, &
1934                         t2m_month, 'scatter', nbp_glo, index_g)
1935   
1936
1937    CALL restput_p (rest_id_stomate, 'Tseason', nbp_glo,    1, 1, itime, &
1938         Tseason, 'scatter', nbp_glo, index_g)
1939   
1940    CALL restput_p (rest_id_stomate, 'Tseason_length', nbp_glo,    1, 1, itime, &
1941         Tseason_length, 'scatter', nbp_glo, index_g)
1942   
1943    CALL restput_p (rest_id_stomate, 'Tseason_tmp', nbp_glo,    1, 1, itime, &
1944         Tseason_tmp, 'scatter', nbp_glo, index_g)
1945   
1946    CALL restput_p (rest_id_stomate, 'Tmin_spring_time', nbp_glo, nvm, 1, itime, &
1947         Tmin_spring_time, 'scatter', nbp_glo, index_g)
1948   
1949    CALL restput_p (rest_id_stomate, 'onset_date', nbp_glo, nvm, 1, itime, &
1950         onset_date(:,:), 'scatter', nbp_glo, index_g)
1951   
1952    var_name = 't2m_week'
1953    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    1, 1, itime, &
1954         &                t2m_week, 'scatter', nbp_glo, index_g)
1955    !-
1956    var_name = 'tsoil_month'
1957    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nslm, 1, itime, &
1958         &                tsoil_month, 'scatter', nbp_glo, index_g)
1959    !-
1960    var_name = 'soilhum_month'
1961    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nslm, 1, itime, &
1962         &                soilhum_month, 'scatter', nbp_glo, index_g)
1963    !-
1964    ! 6 fire probability
1965    !-
1966    var_name = 'fireindex'
1967    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
1968         &                fireindex, 'scatter', nbp_glo, index_g)
1969    !-
1970    var_name = 'firelitter'
1971    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
1972         &                firelitter, 'scatter', nbp_glo, index_g)
1973    !-
1974    ! 7 maximum and minimum moisture availabilities for tropic phenology
1975    !-
1976    var_name = 'maxmoistr_last'
1977    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
1978         &                maxmoiavail_lastyear, 'scatter', nbp_glo, index_g)
1979    !-
1980    var_name = 'maxmoistr_this'
1981    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
1982         &                maxmoiavail_thisyear, 'scatter', nbp_glo, index_g)
1983    !-
1984    var_name = 'minmoistr_last'
1985    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
1986         &                minmoiavail_lastyear, 'scatter', nbp_glo, index_g)
1987    !-
1988    var_name = 'minmoistr_this'
1989    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
1990         &                minmoiavail_thisyear, 'scatter', nbp_glo, index_g)
1991    !-
1992    ! 8 maximum "weekly" GPP
1993    !-
1994    var_name = 'maxgppweek_lastyear'
1995    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
1996         &                maxgppweek_lastyear, 'scatter', nbp_glo, index_g)
1997    !-
1998    var_name = 'maxgppweek_thisyear'
1999    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2000         &                maxgppweek_thisyear, 'scatter', nbp_glo, index_g)
2001    !-
2002    ! 9 annual GDD0
2003    !-
2004    var_name = 'gdd0_thisyear'
2005    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2006         &                gdd0_thisyear, 'scatter', nbp_glo, index_g)
2007    !-
2008    var_name = 'gdd0_lastyear'
2009    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2010         &                gdd0_lastyear, 'scatter', nbp_glo, index_g)
2011    !-
2012    ! 10 annual precipitation
2013    !-
2014    var_name = 'precip_thisyear'
2015    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2016         &                precip_thisyear, 'scatter', nbp_glo, index_g)
2017    !-
2018    var_name = 'precip_lastyear'
2019    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2020         &                precip_lastyear, 'scatter', nbp_glo, index_g)
2021    !-
2022    ! 11 derived "biometeorological" variables
2023    !-
2024    var_name = 'gdd_m5_dormance'
2025    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2026         &                gdd_m5_dormance, 'scatter', nbp_glo, index_g)
2027    !-
2028    var_name = 'gdd_from_growthinit'
2029    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2030         &              gdd_from_growthinit, 'scatter', nbp_glo, index_g)
2031    !-
2032    var_name = 'gdd_midwinter'
2033    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2034         &                gdd_midwinter, 'scatter', nbp_glo, index_g)
2035    !-
2036    var_name = 'ncd_dormance'
2037    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2038         &                ncd_dormance, 'scatter', nbp_glo, index_g)
2039    !-
2040    var_name = 'ngd_minus5'
2041    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2042         &                ngd_minus5, 'scatter', nbp_glo, index_g)
2043    !-
2044    var_name = 'time_hum_min'
2045    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2046         &                time_hum_min, 'scatter', nbp_glo, index_g)
2047    !-
2048    var_name = 'hum_min_dormance'
2049    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2050         &                hum_min_dormance, 'scatter', nbp_glo, index_g)
2051    !-
2052    ! 12 Plant status
2053    !-
2054    var_name = 'PFTpresent'
2055    WHERE ( PFTpresent(:,:) )
2056       PFTpresent_real = un
2057    ELSEWHERE
2058       PFTpresent_real = zero
2059    ENDWHERE
2060    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2061         &                PFTpresent_real, 'scatter', nbp_glo, index_g)
2062    !-
2063    var_name = 'ind'
2064    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2065         &                ind, 'scatter', nbp_glo, index_g)
2066    !-
2067    var_name = 'turnover_time'
2068    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2069         &                turnover_time, 'scatter', nbp_glo, index_g)
2070    !-
2071    var_name = 'adapted'
2072    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2073         &                adapted, 'scatter', nbp_glo, index_g)
2074    !-
2075    var_name = 'regenerate'
2076    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2077         &                regenerate, 'scatter', nbp_glo, index_g)
2078    !-
2079    var_name = 'npp_longterm'
2080    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2081         &                npp_longterm, 'scatter', nbp_glo, index_g)
2082    !-
2083    var_name = 'croot_longterm'
2084    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2085         &                croot_longterm, 'scatter', nbp_glo, index_g)
2086    !-
2087    var_name = 'lm_lastyearmax'
2088    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2089         &                lm_lastyearmax, 'scatter', nbp_glo, index_g)
2090    !-
2091    var_name = 'lm_thisyearmax'
2092    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2093         &                lm_thisyearmax, 'scatter', nbp_glo, index_g)
2094    !-
2095    var_name = 'maxfpc_lastyear'
2096    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2097         &                maxfpc_lastyear, 'scatter', nbp_glo, index_g)
2098    !-
2099    var_name = 'maxfpc_thisyear'
2100    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2101         &                maxfpc_thisyear, 'scatter', nbp_glo, index_g)
2102    !-
2103    CALL restput_p (rest_id_stomate, 'turnover_loterm', nbp_glo, nvm, nparts, nelements, itime, &
2104         &                   turnover_longterm, 'scatter', nbp_glo, index_g)
2105    !-
2106    var_name = 'gpp_week'
2107    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2108         &                gpp_week, 'scatter', nbp_glo, index_g)
2109    !-
2110    CALL restput_p (rest_id_stomate, 'biomass', nbp_glo, nvm, nparts, nelements, itime, &
2111         &                   biomass, 'scatter', nbp_glo, index_g)
2112    !-
2113    var_name = 'maint_resp'
2114    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, nparts, itime, &
2115         &                   resp_maint_part, 'scatter', nbp_glo, index_g)
2116    !-
2117    var_name = 'leaf_age'
2118    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, nleafages, itime, &
2119         &                  leaf_age, 'scatter', nbp_glo, index_g)
2120    !-
2121    var_name = 'leaf_frac'
2122    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, nleafages, itime, &
2123         &                   leaf_frac, 'scatter', nbp_glo, index_g)
2124    !-
2125    var_name = 'senescence'
2126    WHERE ( senescence(:,:) )
2127       senescence_real = un
2128    ELSEWHERE
2129       senescence_real = zero
2130    ENDWHERE
2131    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2132         &                senescence_real, 'scatter', nbp_glo, index_g)
2133 
2134    ! Transform the logical variable begin_leaves to real before writing to restart file
2135    WHERE ( begin_leaves(:,:) )
2136       begin_leaves_real = un
2137    ELSEWHERE
2138       begin_leaves_real = zero
2139    ENDWHERE
2140    CALL restput_p (rest_id_stomate, 'begin_leaves', nbp_glo, nvm, 1, itime, &
2141         begin_leaves_real, 'scatter', nbp_glo, index_g)
2142
2143
2144    var_name = 'when_growthinit'
2145    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2146         &                when_growthinit, 'scatter', nbp_glo, index_g)
2147    !-
2148    var_name = 'age'
2149    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
2150         &                age, 'scatter', nbp_glo, index_g)
2151    !-
2152    ! 13 CO2
2153    !-
2154    var_name = 'resp_hetero'
2155    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2156         &                resp_hetero, 'scatter', nbp_glo, index_g)
2157    !-
2158    var_name = 'resp_maint'
2159    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2160         &                resp_maint, 'scatter', nbp_glo, index_g)
2161    !-
2162    var_name = 'resp_growth'
2163    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2164         &                resp_growth, 'scatter', nbp_glo, index_g)
2165    !-
2166    var_name = 'resp_excess'
2167    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2168         &                resp_excess, 'scatter', nbp_glo, index_g)
2169    !-
2170    var_name = 'co2_fire'
2171    CALL restput_p (rest_id_stomate, var_name, nbp_glo,  nvm, 1, itime, &
2172         &                co2_fire, 'scatter', nbp_glo, index_g)
2173    !-
2174    var_name = 'co2_to_bm_dgvm'
2175    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2176         &                co2_to_bm_dgvm, 'scatter', nbp_glo, index_g)
2177    !-
2178    var_name = 'n_to_bm'
2179    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2180         &                n_to_bm, 'scatter', nbp_glo, index_g)
2181    !-
2182    ! 14 vegetation distribution after last light competition
2183    !-
2184    var_name = 'veget_lastlight'
2185    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2186         &                veget_lastlight, 'scatter', nbp_glo, index_g)
2187    !-
2188    ! 15 establishment criteria
2189    !-
2190    var_name = 'everywhere'
2191    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2192         &                everywhere, 'scatter', nbp_glo, index_g)
2193    !-
2194    var_name = 'need_adjacent'
2195    WHERE (need_adjacent(:,:))
2196       need_adjacent_real = un
2197    ELSEWHERE
2198       need_adjacent_real = zero
2199    ENDWHERE
2200    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2201         &                need_adjacent_real, 'scatter', nbp_glo, index_g)
2202    !-
2203    var_name = 'RIP_time'
2204    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2205         &                RIP_time, 'scatter', nbp_glo, index_g)
2206    !-
2207    ! 17 litter
2208    !-
2209    CALL restput_p (rest_id_stomate, 'litter', nbp_glo, nlitt, nvm, nlevs, nelements, itime, &
2210         &                     litter, 'scatter', nbp_glo, index_g)
2211    !-
2212    CALL restput_p (rest_id_stomate, 'dead_leaves', nbp_glo,  nvm, nlitt, itime, &
2213        &                   dead_leaves, 'scatter', nbp_glo, index_g)
2214    !-
2215    CALL restput_p (rest_id_stomate, 'carbon', nbp_glo, ncarb, nvm, itime, &
2216         &                   som(:,:,:,icarbon), 'scatter', nbp_glo, index_g)
2217    !-
2218    CALL restput_p (rest_id_stomate, 'nitrogen', nbp_glo, ncarb, nvm, itime, & 
2219         &                   som(:,:,:,initrogen), 'scatter', nbp_glo, index_g) 
2220    !-
2221    CALL restput_p &
2222         &      (rest_id_stomate, 'lignin_struc', nbp_glo, nvm, nlevs, itime, &
2223         &       lignin_struc, 'scatter', nbp_glo, index_g)
2224    !-
2225    CALL restput_p &
2226         &      (rest_id_stomate, 'lignin_wood', nbp_glo, nvm, nlevs, itime, &
2227         &       lignin_wood, 'scatter', nbp_glo, index_g)
2228    !-
2229    ! 18 land cover change
2230    !-
2231    var_name = 'co2_flux'
2232    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2233         &                co2_flux, 'scatter', nbp_glo, index_g)
2234    var_name = 'fco2_lu'
2235    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2236         &                fco2_lu, 'scatter', nbp_glo, index_g)
2237    var_name = 'fco2_wh'
2238    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2239         &                fco2_wh, 'scatter', nbp_glo, index_g)
2240    var_name = 'fco2_ha'
2241    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2242         &                fco2_ha, 'scatter', nbp_glo, index_g)
2243
2244    var_name = 'prod10'
2245    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 11, 1, itime, &
2246         &                prod10, 'scatter', nbp_glo, index_g)
2247    var_name = 'prod100'
2248    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 101, 1, itime, &
2249         &                prod100, 'scatter', nbp_glo, index_g)
2250    var_name = 'flux10'
2251    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 10, 1, itime, &
2252         &                flux10, 'scatter', nbp_glo, index_g)
2253    var_name = 'flux100'
2254    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 100, 1, itime, &
2255         &                flux100, 'scatter', nbp_glo, index_g)
2256
2257    var_name = 'convflux'
2258    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2259         &              convflux, 'scatter', nbp_glo, index_g)
2260    var_name = 'cflux_prod10'
2261    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2262         &              cflux_prod10, 'scatter', nbp_glo, index_g)
2263    var_name = 'cflux_prod100'
2264    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2265         &              cflux_prod100, 'scatter', nbp_glo, index_g)
2266    var_name = 'nfluxprod'
2267    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2268         &              nflux_prod, 'scatter', nbp_glo, index_g)
2269
2270    var_name = 'nfluxprodhar'
2271    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2272         &              nflux_prod_harvest, 'scatter', nbp_glo, index_g)
2273
2274    var_name = 'convfluxpft'
2275    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
2276         &              convfluxpft, 'scatter', nbp_glo, index_g)
2277
2278    var_name = 'fDeforestToProduct'
2279    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
2280         &              fDeforestToProduct, 'scatter', nbp_glo, index_g)
2281
2282    var_name = 'fLulccResidue'
2283    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
2284         &              fLulccResidue, 'scatter', nbp_glo, index_g)
2285
2286    var_name = 'fHarvestToProduct'
2287    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
2288         &              fHarvestToProduct, 'scatter', nbp_glo, index_g)
2289
2290    !-
2291    ! 18-bis wood harvest
2292    !-
2293    IF (do_wood_harvest) THEN
2294       var_name = 'prod10_harvest'
2295       CALL restput_p (rest_id_stomate, var_name, nbp_glo, 11, 1, itime, &
2296            prod10_harvest, 'scatter', nbp_glo, index_g)
2297       var_name = 'prod100_harvest'
2298       CALL restput_p (rest_id_stomate, var_name, nbp_glo, 101, 1, itime, &
2299            prod100_harvest, 'scatter', nbp_glo, index_g)
2300       var_name = 'flux10_harvest'
2301       CALL restput_p (rest_id_stomate, var_name, nbp_glo, 10, 1, itime, &
2302            flux10_harvest, 'scatter', nbp_glo, index_g)
2303       var_name = 'flux100_harvest'
2304       CALL restput_p (rest_id_stomate, var_name, nbp_glo, 100, 1, itime, &
2305            flux100_harvest, 'scatter', nbp_glo, index_g)
2306       var_name = 'convflux_harvest'
2307       CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2308            convflux_harvest, 'scatter', nbp_glo, index_g)
2309       var_name = 'cflux_prod10_harvest'
2310       CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2311            cflux_prod10_harvest, 'scatter', nbp_glo, index_g)
2312       var_name = 'cfluxprod100_harvest'
2313       CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2314            cflux_prod100_harvest, 'scatter', nbp_glo, index_g)
2315       var_name = 'woodharvestpft'
2316       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2317            woodharvestpft, 'scatter', nbp_glo, index_g)
2318    END IF
2319
2320    CALL restput_p (rest_id_stomate, 'bm_to_litter', nbp_glo, nvm, nparts, nelements, itime, &
2321          &                bm_to_litter, 'scatter', nbp_glo, index_g)
2322
2323    CALL restput_p (rest_id_stomate, 'tree_to_litter', nbp_glo, nvm, nparts, nelements, itime, &
2324          &                tree_bm_to_litter, 'scatter', nbp_glo, index_g)
2325
2326    CALL restput_p (rest_id_stomate, 'carb_mass_total', nbp_glo, 1, 1, itime, &
2327         &              carb_mass_total, 'scatter', nbp_glo, index_g)
2328
2329    IF ( ok_soil_carbon_discretization ) THEN
2330       CALL restput_p (rest_id_stomate, 'deepSOM_a', nbp_glo, ngrnd, nvm, nelements, itime, &
2331            deepSOM_a, 'scatter', nbp_glo, index_g)
2332     
2333       CALL restput_p (rest_id_stomate, 'deepSOM_s', nbp_glo, ngrnd, nvm, nelements, itime, &
2334            deepSOM_s, 'scatter', nbp_glo, index_g)
2335       
2336       CALL restput_p (rest_id_stomate, 'deepSOM_p', nbp_glo, ngrnd, nvm, nelements, itime, &
2337            deepSOM_p, 'scatter', nbp_glo, index_g)
2338       
2339       CALL restput_p (rest_id_stomate, 'O2_soil', nbp_glo, ngrnd, nvm, itime, &
2340            O2_soil, 'scatter', nbp_glo, index_g)
2341       CALL restput_p (rest_id_stomate, 'CH4_soil', nbp_glo, ngrnd, nvm, itime, &
2342            CH4_soil, 'scatter', nbp_glo, index_g)
2343       CALL restput_p (rest_id_stomate, 'O2_snow', nbp_glo, nsnow, nvm, itime, &
2344            O2_snow, 'scatter', nbp_glo, index_g)
2345       CALL restput_p (rest_id_stomate, 'CH4_snow', nbp_glo, nsnow, nvm, itime, &
2346            CH4_snow, 'scatter', nbp_glo, index_g)
2347
2348       CALL restput_p (rest_id_stomate, 'heat_Zimov', nbp_glo, ngrnd, nvm, itime, &
2349            heat_Zimov, 'scatter', nbp_glo, index_g)     
2350       CALL restput_p (rest_id_stomate, 'altmax', nbp_glo, nvm, 1, itime, &
2351            altmax, 'scatter', nbp_glo, index_g)
2352       CALL restput_p (rest_id_stomate, 'depth_organic_soil', nbp_glo, 1, 1, itime, &
2353                      depth_organic_soil, 'scatter', nbp_glo, index_g)
2354
2355       !Isa dbg : fixed_cryoturbation_depth -> fixed_cryoturb_depth
2356       var_name = 'fixed_cryoturb_depth'
2357       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2358            fixed_cryoturbation_depth, 'scatter', nbp_glo, index_g)
2359    ENDIF
2360    !-
2361    ! 19. Spinup
2362    !-
2363    IF (spinup_analytic) THEN
2364
2365       CALL restput_p (rest_id_stomate, 'Global_years', itime, global_years)
2366       
2367       var_name = 'nbp_sum'
2368       CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2369            &              nbp_accu, 'scatter', nbp_glo, index_g)
2370
2371       var_name = 'nbp_flux'
2372       CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2373            &              nbp_flux, 'scatter', nbp_glo, index_g)
2374
2375       var_name = 'ok_equilibrium'
2376       WHERE(ok_equilibrium(:))
2377          ok_equilibrium_real = un
2378       ELSEWHERE
2379          ok_equilibrium_real = zero
2380       ENDWHERE
2381       CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2382            &               ok_equilibrium_real, 'scatter', nbp_glo, index_g)
2383       
2384       CALL restput_p (rest_id_stomate, 'MatrixV', nbp_glo, nvm, nbpools, nbpools, itime, &
2385            &                MatrixV, 'scatter', nbp_glo, index_g)
2386         
2387       CALL restput_p (rest_id_stomate, 'Vector_U', nbp_glo, nvm, nbpools, itime, &
2388            &                VectorU, 'scatter', nbp_glo, index_g)
2389         
2390       CALL restput_p (rest_id_stomate, 'previous_stock', nbp_glo, nvm, nbpools, itime, &
2391            &                previous_stock, 'scatter', nbp_glo, index_g)
2392
2393       CALL restput_p (rest_id_stomate, 'current_stock', nbp_glo, nvm, nbpools, itime, &
2394            &                current_stock, 'scatter', nbp_glo, index_g)
2395
2396       CALL restput_p (rest_id_stomate, 'CN_longterm', nbp_glo, nvm, nbpools, itime, &
2397            &                CN_som_litter_longterm, 'scatter', nbp_glo, index_g)
2398
2399       CALL restput_p (rest_id_stomate, 'tau_CN_longterm', itime, tau_CN_longterm)
2400           
2401    ENDIF !(spinup_analytic)
2402
2403    !-
2404    var_name = 'KF'
2405    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2406          &              KF(:,:), 'scatter', nbp_glo, index_g)
2407    !-
2408    var_name = 'k_latosa_adapt'
2409    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2410          &              k_latosa_adapt(:,:), 'scatter', nbp_glo, index_g)
2411    !-
2412
2413    var_name = 'rue_longterm'
2414    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2415          &              rue_longterm(:,:), 'scatter', nbp_glo, index_g)
2416    !-
2417!!$    var_name = 'lai_target'
2418!!$    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2419!!$          &              lai_target(:,:), 'scatter', nbp_glo, index_g)
2420    !-
2421
2422 
2423    var_name = 'cn_leaf_min_season' 
2424    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & 
2425         &              cn_leaf_min_season(:,:), 'scatter', nbp_glo, index_g) 
2426    !-
2427    var_name = 'nstress_season' 
2428    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & 
2429         &              nstress_season(:,:), 'scatter', nbp_glo, index_g) 
2430    !-
2431    CALL restput_p (rest_id_stomate, 'soil_n_min', nbp_glo, nvm, nnspec, itime, & 
2432         &              soil_n_min, 'scatter', nbp_glo, index_g) 
2433    !-
2434    var_name = 'p_O2' 
2435    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & 
2436         &              p_O2(:,:), 'scatter', nbp_glo, index_g) 
2437    !-
2438    !-
2439    var_name = 'bact' 
2440    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & 
2441         &              bact(:,:), 'scatter', nbp_glo, index_g) 
2442    !-
2443    !-
2444    CALL restput_p (rest_id_stomate, 'assim_param', nbp_glo, nvm, npco2, itime, &
2445        &                assim_param, 'scatter', nbp_glo, index_g)
2446   
2447    CALL restput_p (rest_id_stomate, 'harvest_above', nbp_glo, nelements, 1, itime, & 
2448         harvest_above(:,:), 'scatter', nbp_glo, index_g) 
2449   
2450    var_name = 'sugar_load'
2451    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, &
2452         &              sugar_load, 'scatter', nbp_glo, index_g)
2453
2454    IF (printlev >= 4) WRITE(numout,*) 'Leaving writerestart'
2455    !--------------------------
2456  END SUBROUTINE writerestart
2457  !-
2458  !===
2459  !-
2460END MODULE stomate_io
Note: See TracBrowser for help on using the repository browser.