source: branches/publications/ORCHIDEE-LEAK-r5919/src_stomate/stomate_io.f90 @ 5925

Last change on this file since 5925 was 5919, checked in by ronny.lauerwald, 5 years ago

ORCHILEAK, version used for trends and biases in NEE and NBP in the Amazon basin

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