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

Last change on this file since 7326 was 7326, checked in by josefine.ghattas, 3 years ago

Corrected bug on carbon balance closure. See ticket #785
Integration in branch 2_2 done by P. Cadule

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