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

Last change on this file since 5804 was 5605, checked in by josefine.ghattas, 6 years ago

Added new option VEGETMAP_RESET. This option should be used to to change vegetation map while keeping VEGET_UPDATE=0Y. This option will read the vegetation map even if it is stored in the restart file. It will also set to zero carbon related variables: prod10, prod100, flux10, flux100, convflux, cflux_prod10, cflux_prod100, convfluxpft(:,:)

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