source: branches/publications/ORCHIDEE-PEAT_r5488/src_stomate/stomate_io.f90 @ 5491

Last change on this file since 5491 was 5323, checked in by chunjing.qiu, 6 years ago

Add oldpeat

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