source: branches/publications/ORCHIDEE_gmd-2018-57/src_stomate/stomate_io.f90 @ 5896

Last change on this file since 5896 was 3340, checked in by josefine.ghattas, 8 years ago

Ticket #239 : Removed option REFTEMP_FILE and subroutine get_reftemp.

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