source: branches/publications/ORCHIDEE-ICE_SurfaceMassBalance/src_stomate/stomate_io.f90 @ 8398

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