source: branches/publications/ORCHIDEE-GMv3.2/ORCHIDEE/src_stomate/stomate_io.f90 @ 5816

Last change on this file since 5816 was 5816, checked in by jinfeng.chang, 5 years ago

copy ORCHIDEE-GMv3.2 for publication

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