source: branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate/stomate_io.f90 @ 8418

Last change on this file since 8418 was 8418, checked in by bertrand.guenet, 5 months ago

The Moyano function describing the soil moisture effect on OM decomposition is added

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