source: tags/ORCHIDEE_4_1/ORCHIDEE/src_stomate/stomate_io.f90 @ 7852

Last change on this file since 7852 was 7661, checked in by sebastiaan.luyssaert, 2 years ago

correction of bare soil carbon pools following ORCHIDEE 3 r7569

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 165.6 KB
Line 
1! =================================================================================================================================
2! MODULE       : stomate_io
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF       Module for read and write of restart files for all stomate modules.
10!!
11!!\n DESCRIPTION : This module contains the subroutines readstart and writerestart. All variables that will be read or written
12!!                 are passed as argument to the subroutines. The subroutine readstart is called from stomate_initialize and
13!!                 writerestart is called from stomate_finalize.
14!!                 Note: Not all variables saved in the start files are absolutely necessary. However, Sechiba's and Stomate's
15!!                 PFTs are not necessarily identical, and for that case this information needs to be saved.
16!!
17!!
18!! RECENT CHANGE(S) : None
19!!
20!! REFERENCE(S) : None
21!!
22!! SVN :
23!! $HeadURL$
24!! $Date$
25!! $Revision$
26!! \n
27!_ ================================================================================================================================
28MODULE stomate_io
29  USE stomate_data
30  USE constantes
31  USE constantes_soil
32  USE mod_orchidee_para
33  USE ioipsl_para
34  USE structures
35  !-
36  IMPLICIT NONE
37  !-
38  PRIVATE
39  PUBLIC readrestart, writerestart
40  !-
41  ! reference temperature (K)
42  !-
43  REAL(r_std),ALLOCATABLE,DIMENSION(:),SAVE :: trefe
44!$OMP THREADPRIVATE(trefe)
45  !-
46CONTAINS
47
48
49!! ================================================================================================================================
50!! SUBROUTINE   : readrestart
51!!
52!>\BRIEF        Read all variables for stomate from restart file.
53!!
54!! DESCRIPTION  : Read all variables for stomate from restart file.
55!!                Initialize the variables if they were not found in the restart file or if there was no restart file.
56!!               
57!! \n
58!_ ================================================================================================================================
59
60  SUBROUTINE readrestart &
61       & (npts, index, lalo, temp_air, dt_days, date_loc, &
62       &  adapted, regenerate, vegstress_day, gdd_init_date, litterhum_daily, &
63       &  t2m_daily, t2m_min_daily, tsurf_daily, tsoil_daily, &
64       &  precip_daily, &
65       &  gpp_daily, npp_daily, turnover_daily, turnover_resid, &
66       &  vegstress_month, vegstress_week, vegstress_season, &
67       &  t2m_longterm, tau_longterm, t2m_month, t2m_week, &
68       &  tsoil_month, fireindex, firelitter, &
69       &  maxvegstress_lastyear, maxvegstress_thisyear, &
70       &  minvegstress_lastyear, minvegstress_thisyear, &
71       &  maxgppweek_lastyear, maxgppweek_thisyear, &
72       &  gdd0_lastyear, gdd0_thisyear, &
73       &  precip_lastyear, precip_thisyear, &
74       &  gdd_m5_dormance,  gdd_from_growthinit, gdd_midwinter, &
75       &  ncd_dormance, ngd_minus5, &
76       &  PFTpresent, npp_longterm, croot_longterm, n_reserve_longterm, lm_lastyearmax, &
77       &  lm_thisyearmax, maxfpc_lastyear, maxfpc_thisyear, &
78       &  turnover_longterm, gpp_week, resp_maint_part, resp_maint_week, &
79       &  leaf_age, leaf_frac, leaf_age_crit, plant_status, when_growthinit, age, &
80       &  resp_hetero, resp_maint, resp_growth, co2_fire, &
81       &  atm_to_bm, &
82       &  veget_lastlight, everywhere, need_adjacent, RIP_time, &
83       &  time_hum_min, hum_min_dormance, &
84       &  litter, dead_leaves, &
85       &  som, lignin_struc, lignin_wood, turnover_time, &
86       &  co2_flux, fco2_lu, fco2_wh, fco2_ha, &
87       &  prod_s, prod_m, prod_l, flux_s, flux_m, flux_l, &
88       &  fDeforestToProduct, fLulccResidue, fHarvestToProduct, &
89       &  bm_to_litter, bm_to_litter_resid, tree_bm_to_litter, &
90       &  tree_bm_to_litter_resid, carb_mass_total, &
91       &  Tseason, Tseason_length, Tseason_tmp, & 
92       &  Tmin_spring_time, &
93       &  global_years, ok_equilibrium, nbp_accu_flux, &
94       &  nbp_pool_start, &
95       &  MatrixV, VectorU, previous_stock, current_stock, &
96       &  assim_param, CN_som_litter_longterm, &
97       &  tau_CN_longterm, KF, k_latosa_adapt, &
98       &  rue_longterm, cn_leaf_min_season, nstress_season, &
99       &  soil_n_min, p_O2, bact, &
100       &  forest_managed, &
101       &  species_change_map, fm_change_map, lpft_replant, lai_per_level, &
102       &  laieff_fit, wstress_season, wstress_month, &
103       &  age_stand, rotation_n, last_cut, mai, pai, &
104       &  previous_wood_volume, mai_count, coppice_dens, &
105       &  light_tran_to_floor_season, daylight_count, veget_max, gap_area_save, &
106       &  deepSOM_a, deepSOM_s, deepSOM_p, O2_soil, CH4_soil, O2_snow, CH4_snow, &
107       &  heat_Zimov, altmax, depth_organic_soil, fixed_cryoturbation_depth, &
108       &  cn_leaf_init_2D, sugar_load, harvest_cut, &
109       &  harvest_pool_acc, harvest_area_acc, burried_litter, burried_fresh_ltr, &
110       &  burried_fresh_som, burried_bact, burried_fungivores, &
111       &  burried_min_nitro,burried_som, &
112       &  burried_deepSOM_a, burried_deepSOM_s, burried_deepSOM_p, &
113       &  wood_leftover_legacy,beetle_pop_legacy,season_drought_legacy, &
114       &  risk_index_legacy, beetle_diapause, sumTeff, &
115       &  beetle_generation_index, beetle_damage_legacy, beetle_flyaway, epidemic, & 
116       &  is_storm, count_storm, biomass_init_drought, kill_vessels, &
117       &  vessel_loss_previous, grow_season_len, doy_start_gs, doy_end_gs, &
118       &  mean_start_gs, total_ba_init)
119
120
121    IMPLICIT NONE
122
123    ! 0 declarations
124    !-
125    ! 0.1 input
126    !-
127    INTEGER(i_std),INTENT(in)                              :: npts                     !! Domain size
128    INTEGER(i_std),DIMENSION(:),INTENT(in)                 :: index                    !! Indices of the points on the map
129    REAL(r_std),DIMENSION(:,:),INTENT(in)                  :: lalo                     !! Geogr. coordinates (latitude,longitude) (degrees)
130    REAL(r_std),DIMENSION(:),INTENT(in)                    :: temp_air                 !! Air temperature from forcing file or coupled model (K)
131    REAL(r_std),DIMENSION(:,:), INTENT(in)                 :: cn_leaf_init_2D          !! initial leaf C/N ratio
132    REAL(r_std),DIMENSION(:,:),INTENT(in)                  :: veget_max                !! Maximum fraction of vegetation type including
133                                                                                       !! non-biological fraction (unitless)
134 
135    !-
136    ! 0.2 output
137    !-
138    REAL(r_std),INTENT(out)                                :: dt_days                  !! time step of STOMATE in days
139    INTEGER(i_std),INTENT(out)                             :: date_loc                 !! date_loc (d)
140    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: adapted                  !! Winter too cold? between 0 and 1
141    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: regenerate               !! Winter sufficiently cold? between 0 and 1
142    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: vegstress_day         !! daily moisture availability
143    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: gdd_init_date            !! date for beginning of gdd count
144    REAL(r_std),DIMENSION(:),INTENT(out)                   :: litterhum_daily          !! daily litter humidity
145    REAL(r_std),DIMENSION(:),INTENT(out)                   :: t2m_daily                !! daily 2 meter temperatures (K)
146    REAL(r_std),DIMENSION(:),INTENT(out)                   :: t2m_min_daily            !! daily minimum 2 meter temperatures (K)
147    REAL(r_std),DIMENSION(:),INTENT(out)                   :: tsurf_daily              !! daily surface temperatures (K)
148    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: tsoil_daily              !! daily soil temperatures (K)
149    REAL(r_std),DIMENSION(:),INTENT(out)                   :: precip_daily             !! daily precipitations (mm/day) (for phenology)
150    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: gpp_daily                !! daily gross primary productivity (gC/m**2/day)
151    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: npp_daily                !! daily net primary productivity (gC/m**2/day)
152    REAL(r_std),DIMENSION(:,:,:,:),INTENT(out)             :: turnover_daily           !! daily turnover rates (gC/m**2/day)
153    REAL(r_std),DIMENSION(:,:,:,:),INTENT(out)             :: turnover_resid           !! The turnover left from turnover_daily at any given time step 
154                                                                                       !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
155    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: vegstress_month       !! "monthly" moisture availability
156    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: vegstress_week        !! "weekly" moisture availability
157    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: vegstress_season      !! mean growing season moisture availability (used for allocation response)
158    REAL(r_std),DIMENSION(:),INTENT(out)                   :: t2m_longterm             !! "long term" 2 meter temperatures (K)
159    REAL(r_std), INTENT(out)                               :: tau_longterm             !! "tau_longterm"
160    REAL(r_std),DIMENSION(:),INTENT(out)                   :: t2m_month                !! "monthly" 2 meter temperatures (K)
161    REAL(r_std),DIMENSION(:),INTENT(out)                   :: Tseason                  !! "seasonal" 2 meter temperatures (K)
162    REAL(r_std),DIMENSION(:),INTENT(out)                   :: Tseason_length           !! temporary variable to calculate Tseason
163    REAL(r_std),DIMENSION(:),INTENT(out)                   :: Tseason_tmp              !! temporary variable to calculate Tseason
164    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: Tmin_spring_time         !!
165    REAL(r_std),DIMENSION(:),INTENT(out)                   :: t2m_week                 !! "weekly" 2 meter temperatures (K)
166    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: tsoil_month              !! "monthly" soil temperatures (K)
167    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: fireindex                !! Probability of fire
168    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: firelitter               !! Longer term total litter above the ground, gC/m**2 of ground
169    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: maxvegstress_lastyear !! last year's maximum moisture availability
170    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: maxvegstress_thisyear !! this year's maximum moisture availability
171    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: minvegstress_lastyear !! last year's minimum moisture availability
172    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: minvegstress_thisyear !! this year's minimum moisture availability
173    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: maxgppweek_lastyear      !! last year's maximum weekly GPP
174    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: maxgppweek_thisyear      !! this year's maximum weekly GPP
175    REAL(r_std),DIMENSION(:),INTENT(out)                   :: gdd0_lastyear            !! last year's annual GDD0
176    REAL(r_std),DIMENSION(:),INTENT(out)                   :: gdd0_thisyear            !! this year's annual GDD0
177    REAL(r_std),DIMENSION(:),INTENT(out)                   :: precip_lastyear          !! last year's annual precipitation (mm/year)
178    REAL(r_std),DIMENSION(:),INTENT(out)                   :: precip_thisyear          !! this year's annual precipitation (mm/year)
179    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: gdd_m5_dormance          !! growing degree days, threshold -5 deg C (for phenology)
180    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: gdd_from_growthinit      !! growing degree days, from begin of season
181    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: gdd_midwinter            !! growing degree days since midwinter (for phenology)
182    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: ncd_dormance             !! number of chilling days since leaves were lost (for phenology)
183    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: ngd_minus5               !! number of growing days, threshold -5 deg C (for phenology)
184    LOGICAL,DIMENSION(:,:),INTENT(out)                     :: PFTpresent               !! PFT exists (equivalent to fpc_max > 0 for natural PFTs)
185    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: npp_longterm             !! "long term" net primary productivity (gC/m**2/year)
186    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: croot_longterm           !! "long term" root carbon mass (gC/m**2/year)
187    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: n_reserve_longterm       !! "long term" actual to potential N reserve pool (unitless)
188    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: lm_lastyearmax           !! last year's maximum leaf mass, for each PFT (gC/m**2)
189    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: lm_thisyearmax           !! this year's maximum leaf mass, for each PFT (gC/m**2)
190    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: maxfpc_lastyear          !! last year's maximum fpc for each natural PFT, on ground
191    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: maxfpc_thisyear          !! this year's maximum fpc for each PFT, on *total* ground (see stomate_season)   
192    REAL(r_std),DIMENSION(:,:,:,:),INTENT(out)             :: turnover_longterm        !! "long term" turnover rate (gC/m**2/year)
193    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: gpp_week                 !! "weekly" GPP (gC/day/(m**2 covered)
194    REAL(r_std),DIMENSION(:,:,:),INTENT(out)               :: resp_maint_part          !! maintenance resp (gC/m**2)
195    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: resp_maint_week          !! "weekly" maintenance respiration (gC/day/(m**2 covered)
196    REAL(r_std),DIMENSION(:,:,:),INTENT(out)               :: leaf_age                 !! leaf age (days)
197    REAL(r_std),DIMENSION(:,:,:),INTENT(out)               :: leaf_frac                !! fraction of leaves in leaf age class
198    REAL(r_std), DIMENSION(:,:),INTENT(out)                :: leaf_age_crit            !! critical leaf age (days)
199    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: plant_status             !! Growth and phenological status of the plant
200                                                                                       !! The different stati are defined in constantes
201    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: when_growthinit          !! how many days ago was the beginning of the growing season
202    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: age                      !! mean age (years)
203    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: resp_hetero              !! heterotrophic respiration (gC/day/m**2)
204    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: resp_maint               !! maintenance respiration (gC/day/m**2)
205    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: resp_growth              !! growth respiration (gC/day/m**2)
206    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: co2_fire                 !! carbon emitted into the atmosphere by fire (living and dead biomass)
207                                                                                       !! (in gC/m**2/time step)
208    REAL(r_std),DIMENSION(:,:,:),INTENT(out)               :: atm_to_bm                !! biomass taken from the atmosphere (gC or gN /(m**2 of total ground)/day)
209    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: veget_lastlight          !! vegetation fractions (on ground) after last light competition
210    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: everywhere               !! is the PFT everywhere in the grid box or very localized (after its introduction)
211    LOGICAL,DIMENSION(:,:),INTENT(out)                     :: need_adjacent            !! in order for this PFT to be introduced, does it have to be present in an adjacent grid box?
212    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: RIP_time                 !! How much time ago was the PFT eliminated for the last time (y)
213    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: time_hum_min             !! time elapsed since strongest moisture availability (d)
214    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: hum_min_dormance         !! minimum moisture during dormance
215    REAL(r_std),DIMENSION(:,:,:,:,:),INTENT(out)           :: litter                   !! fraction of litter above the ground belonging to different PFTs
216                                                                                       !! separated for natural and agricultural PFTs.
217    REAL(r_std),DIMENSION(:,:,:),INTENT(out)               :: dead_leaves              !! dead leaves on ground, per PFT, metabolic and structural in gC/(m**2 of ground)
218    REAL(r_std),DIMENSION(:,:,:,:),INTENT(out)             :: som                      !! Soil Organic Matter pool: active, slow, or passive, (gC (or N)/m**2)
219    REAL(r_std),DIMENSION(:,:,:),INTENT(out)               :: lignin_struc             !! ratio Lignine/Carbon in structural litter, above and below ground,(gC/m**2)
220    REAL(r_std),DIMENSION(:,:,:),INTENT(out)               :: lignin_wood              !! ratio Lignine/Carbon in woody litter, above and below ground,(gC/m**2)
221    REAL(r_std),DIMENSION(:,:,:),INTENT(out)               :: turnover_time            !!
222    INTEGER(i_std), INTENT(out)                            :: global_years             !! for spinup matrix 
223    LOGICAL, DIMENSION(:), INTENT(out)                     :: ok_equilibrium           !! for spinup matrix 
224    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: nbp_accu_flux            !! accumulated Net Biospheric Production over the whole simulationm (gC/N m-2)
225    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: nbp_pool_start           !! C an dN stocks at previous time step (gC/N m-2)
226    REAL(r_std), DIMENSION(:,:,:,:), INTENT(out)           :: MatrixV                  !!
227    REAL(r_std), DIMENSION(:,:,:), INTENT(out)             :: VectorU                  !!
228    REAL(r_std), DIMENSION(:,:,:), INTENT(out)             :: previous_stock           !!
229    REAL(r_std), DIMENSION(:,:,:), INTENT(out)             :: current_stock            !!
230    REAL(r_std), DIMENSION(:,:,:), INTENT(out)             :: CN_som_litter_longterm   !! Longterm CN ratio of litter and som pools (gC/gN)
231    REAL(r_std), INTENT(out)                               :: tau_CN_longterm          !! Counter used for calculating the longterm CN ratio of SOM and litter pools (seconds)
232    REAL(r_std), DIMENSION(:,:,:), INTENT(out)             :: assim_param              !!
233    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: KF                       !! Scaling factor to convert sapwood mass into leaf mass (m)
234    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: k_latosa_adapt           !! Leaf to sapwood area adapted for water stress. Adaptation takes place at the end of the year (m)
235    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: mai                      !! The mean annual increment @tex $(m**3 / m**2 / year)$ @endtex
236    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: pai                      !! The period annual increment @tex $(m**3 / m**2 / year)$ @endtex
237    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: previous_wood_volume     !! The volume of the tree trunks in a stand for the previous year. @tex $(m**3 / m**2 )$ @endtex
238    INTEGER(i_std), DIMENSION(:,:),INTENT(out)             :: mai_count                !! The number of times we've calculated the volume increment for a stand
239    REAL(r_std), DIMENSION(:,:),INTENT(out)                :: coppice_dens             !! The density of a coppice at the first cutting. @tex $( 1 / m**2 )$ @endtex
240    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: rue_longterm             !! longterm radiation use efficiency
241    INTEGER(i_std), DIMENSION(:,:), INTENT(out)            :: age_stand                !! Age of stand (years)
242    INTEGER(i_std), DIMENSION(:,:), INTENT(out)            :: rotation_n               !! Rotation number (number of rotation since pft is managed)
243    INTEGER(i_std), DIMENSION(:,:), INTENT(out)            :: last_cut                 !! Years since last thinning (years)
244    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: cn_leaf_min_season       !! Seasonal min CN ratio of leaves
245    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: nstress_season           !! N-related seasonal stress (used for allocation)
246    REAL(r_std), DIMENSION(:,:,:), INTENT(out)             :: soil_n_min               !! mineral nitrogen in the soil (gN/m**2) (first index=npts, second index=nvm, third index=nnspec)
247    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: p_O2                     !! partial pressure of oxigen in the soil (hPa)(first index=npts, second index=nvm)
248    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: bact                     !! denitrifier biomass (gC/m**2) (first index=npts, second index=nvm)
249    INTEGER(i_std), DIMENSION(:,:), INTENT(out)            :: forest_managed           !! forest management flag
250    REAL(r_std), DIMENSION(:,0:,:,:,:), INTENT(out)        :: prod_s                   !!
251    REAL(r_std), DIMENSION(:,0:,:,:,:), INTENT(out)        :: prod_m                   !!
252    REAL(r_std), DIMENSION(:,0:,:,:,:), INTENT(out)        :: prod_l                   !!
253    REAL(r_std), DIMENSION(:,:,:,:,:), INTENT(out)         :: flux_s                   !!
254    REAL(r_std), DIMENSION(:,:,:,:,:), INTENT(out)         :: flux_m                   !!
255    REAL(r_std), DIMENSION(:,:,:,:,:), INTENT(out)         :: flux_l                   !!
256    INTEGER(i_std), DIMENSION(:,:), INTENT(out)            :: species_change_map       !! A map which gives the PFT number that each PFT will be replanted as in case of a clearcut.
257                                                                                       !! (1-nvm,unitless)
258    INTEGER(i_std), DIMENSION(:,:), INTENT(out)            :: fm_change_map            !! A map which gives the desired FM strategy when the PFT will be replanted after a clearcut.
259                                                                                       !! (1-nvm,unitless)
260    LOGICAL, DIMENSION(:,:), INTENT(out)                   :: lpft_replant             !! Indicates if this PFT has either died this year or been clearcut/coppiced.  If it has, it is not
261                                                                                       !! replanted until the end of the year.
262    REAL(r_std), DIMENSION(:,:,:),INTENT(out)              :: lai_per_level            !! The amount of LAI in each physical canopy level. @tex $( m**2 / m**2 )$ @endtex
263    REAL(r_std), DIMENSION(:,:,:,:),INTENT(out)            :: deepSOM_a                !!
264    REAL(r_std), DIMENSION(:,:,:,:),INTENT(out)            :: deepSOM_s                !!
265    REAL(r_std), DIMENSION(:,:,:,:),INTENT(out)            :: deepSOM_p                !!
266    REAL(r_std), DIMENSION(:,:,:),INTENT(out)              :: O2_soil                  !!
267    REAL(r_std), DIMENSION(:,:,:),INTENT(out)              :: CH4_soil                 !!
268    REAL(r_std), DIMENSION(:,:,:),INTENT(out)              :: O2_snow                  !!
269    REAL(r_std), DIMENSION(:,:,:),INTENT(out)              :: CH4_snow                 !!
270    REAL(r_std), DIMENSION(:,:,:), INTENT(out)             :: heat_Zimov               !! heating associated with decomposition [W/m**3 soil]
271    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: altmax                   !! Active layer thickness (m)
272    REAL(r_std), DIMENSION(:),INTENT(out)                  :: depth_organic_soil       !! Depth at which there is still organic matter (m)
273    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: fixed_cryoturbation_depth!! Depth to hold cryoturbation to for fixed runs 
274    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: sugar_load               !! Relative sugar loading of the labile pool (unitless)
275    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: harvest_cut              !! Type of cutting that was used for the harvest (unitless)
276    TYPE(laieff_type),DIMENSION (:,:,:),INTENT(out)        :: laieff_fit               !! Fitted parameters for the effective LAI
277    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: wstress_season           !! Water stress factor, based on hum_rel_daily (unitless, 0-1)
278    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: wstress_month            !! Water stress factor, based on hum_rel_daily (unitless, 0-1)
279    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: fDeforestToProduct       !!
280    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: fLulccResidue            !!
281    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: fHarvestToProduct        !!
282    REAL(r_std),DIMENSION(:,:,:,:),INTENT(out)             :: bm_to_litter             !! Background (not senescence-driven) mortality of biomass
283                                                                                       !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
284    REAL(r_std),DIMENSION(:,:,:,:),INTENT(out)             :: bm_to_litter_resid       !! Left over bm_to_litter at any specific time step
285                                                                                       !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
286    REAL(r_std),DIMENSION(:,:,:,:),INTENT(out)             :: tree_bm_to_litter        !! Conversion of biomass to litter
287                                                                                       !! @tex $(gC m^{-2} dtslow^{-1})$ @endtex
288    REAL(r_std),DIMENSION(:,:,:,:),INTENT(out)             :: tree_bm_to_litter_resid  !! Left over bm_to_litter_resid. Written here, used in stomate.f90
289                                                                                       !! @tex $(gC m^{-2} dtslow^{-1})$ @endtex
290    REAL(r_std),DIMENSION(:),INTENT(out)                   :: carb_mass_total          !!
291    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: light_tran_to_floor_season !! Mean seasonal fraction of light transmitted to the forest floor (unitless, 0-1)
292    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: daylight_count           !! Time steps dt_radia during daylight and when there is growth (gpp>0)
293    REAL(r_std), DIMENSION(:,:,:), INTENT(out)             :: gap_area_save            !! Total gap area created by more than 30% basal area loss
294                                                                                       !! in the last 5 years (m^{2})     
295    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: total_ba_init            !! Total basal area saved at the first day of the year (m^{2}/m^{2})
296    REAL(r_std), DIMENSION(:,:,:), INTENT(out)             :: season_drought_legacy    !! mean growing season moisture availability
297    REAL(r_std), DIMENSION(:,:,:), INTENT(out)             :: wood_leftover_legacy     !!
298    REAL(r_std), DIMENSION(:,:,:), INTENT(out)             :: risk_index_legacy        !!
299    INTEGER(i_std), DIMENSION(:,:), INTENT(out)            :: beetle_diapause          !!
300    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: sumTeff                  !! sum of temp of beetle phenology
301    REAL(r_std), DIMENSION(:,:,:),INTENT(out)              :: beetle_pop_legacy        !! biomass of tree from the same species that was infected during the previous timestep
302    REAL(r_std), DIMENSION(:,:),INTENT(out)                :: beetle_flyaway
303    REAL(r_std), DIMENSION(:,:,:), INTENT(out)             :: beetle_damage_legacy         !!
304    REAL(r_std), DIMENSION(:,:,:), INTENT(out)             :: beetle_generation_index  !! number of generation that BB can achieved in one year
305    REAL(r_std), DIMENSION(:,:),INTENT(out)                :: epidemic
306    LOGICAL, DIMENSION(:),INTENT(out)                      :: is_storm
307    INTEGER(i_std), DIMENSION(:),INTENT(out)               :: count_storm
308    REAL(r_std),DIMENSION(:,:,:,:),INTENT(out)             :: harvest_pool_acc          !! Records the quantity of wood harvested and thinned due to forest management and LCC.
309    REAL(r_std), DIMENSION(:,:), INTENT(out)               :: harvest_area_acc         !! Harvested area (m^{2})
310    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: co2_flux                 !!
311    REAL(r_std),DIMENSION(:),INTENT(out)                   :: fco2_lu                  !!
312    REAL(r_std),DIMENSION(:),INTENT(out)                   :: fco2_wh                  !!
313    REAL(r_std),DIMENSION(:),INTENT(out)                   :: fco2_ha                  !!
314    REAL(r_std),DIMENSION(:,:,:,:),INTENT(out)             :: burried_litter           !! Litter burried under non-biological land uses (gC orNm-2)
315    REAL(r_std),DIMENSION(:,:,:),INTENT(out)               :: burried_fresh_ltr        !! Fresh litter burried under non-biological land uses (gC orN m-2)
316    REAL(r_std),DIMENSION(:,:,:),INTENT(out)               :: burried_fresh_som        !! Fresh som burried under non-biological land uses (gC or Nm-2)
317    REAL(r_std),DIMENSION(:),INTENT(out)                   :: burried_bact             !! Bacteria burried under non-biological land uses (gC m-2)
318    REAL(r_std),DIMENSION(:),INTENT(out)                   :: burried_fungivores       !! Fungivores burried under non-biological land uses (gN m-2)
319    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: burried_min_nitro        !! Mineral nitrogen burried under non-biological land uses(gC or N m-2)
320    REAL(r_std),DIMENSION(:,:,:),INTENT(out)               :: burried_som              !! Som burried under non-biological land uses (gC or N m-2)
321    REAL(r_std),DIMENSION(:,:,:),INTENT(out)               :: burried_deepSOM_a        !! Som burried under non-biological land uses (gC or N m-3)
322    REAL(r_std),DIMENSION(:,:,:),INTENT(out)               :: burried_deepSOM_s        !! Som burried under non-biological land uses (gC or N m-3)
323    REAL(r_std),DIMENSION(:,:,:),INTENT(out)               :: burried_deepSOM_p        !! Som burried under non-biological land uses (gC or N m-3)
324    REAL(r_std),DIMENSION(:,:,:,:,:),INTENT(out)           :: biomass_init_drought     !! Biomass of heartwood or sapwood before onset of drought.
325                                                                                       !! Used to compute turnover on same reference biomass in
326                                                                                       !! stomate_turnover.f90. Should remain the same along one
327                                                                                       !! entire drought episode and be updated inbetween
328                                                                                       !! droughts (gCor N tree-1).
329    LOGICAL,DIMENSION(:,:),INTENT(out)                     :: kill_vessels             !! Flag to kill vessels at the end of the day when there is embolism.
330    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: vessel_loss_previous     !! vessel loss at the previous time step
331    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: grow_season_len          !! growing season length in days for deciduous PFTs.
332    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: doy_start_gs             !! growing season starting day of year (DOY) for deciduous PFTs.
333    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: doy_end_gs               !! growing season end day of year (DOY) for deciduous PFTs.
334    REAL(r_std),DIMENSION(:,:),INTENT(out)                 :: mean_start_gs            !! mean growing season starting day for deciduous PFTs.
335   
336
337  !! 0.4 Local variables
338   
339    REAL(r_std)                                                         :: date_real
340    REAL(r_std),DIMENSION(npts,nvm)                                     :: PFTpresent_real         !! PFT exists (equivalent to fpc_max > 0 for natural PFTs), real
341    REAL(r_std),DIMENSION(npts)                                         :: is_storm_real
342    REAL(r_std),DIMENSION(npts)                                         :: count_storm_real
343
344    REAL(r_std),DIMENSION(npts,nvm)                                     :: need_adjacent_real      !! in order for this PFT to be introduced,
345                                                                                                   !! does it have to be present in an adjacent grid box? - real
346    CHARACTER(LEN=80)                                                   :: var_name                !! To store variables names for I/O
347    CHARACTER(LEN=10)                                                   :: part_st                 !! string suffix indicating an index
348    CHARACTER(LEN=10)                                                   :: circ_str                !! string suffix indicating an index           
349    REAL(r_std),DIMENSION(1)                                            :: xtmp                    !! temporary storage
350    INTEGER(i_std)                                                      :: j,k,l,m                 !! index
351    CHARACTER(LEN=2),DIMENSION(nelements)                               :: element_str             !! string suffix indicating element
352    CHARACTER(LEN=6), DIMENSION(nbpools)                                :: pools_str
353    REAL(r_std), DIMENSION(npts)                                        :: ok_equilibrium_real   
354    INTEGER                                                             :: n,ilev,ipts, igrn       !! Indices
355    INTEGER                                                             :: ivm,icarb,iele          !! Indices
356    REAL(r_std), DIMENSION(npts,nvm)                                    :: temp_real               !! temporary real to allow restget
357                                                                                                   !! to work on multi-dimensional integers
358    REAL(r_std), DIMENSION(npts,nvm)                                    :: r_replant               !! Getting logical values from the restart
359                                                                                                   !! is not possible, so this is a temporary
360                                                                                                   !! array where 1.0 is TRUE.
361    REAL(r_std),DIMENSION(npts,nvm,nlevels_tot,nparams_laieff)          :: temp_array              !! To store structure values for I/O
362    CHARACTER(LEN=10)                                                   :: part_str2               !! string suffix indicating an index
363    CHARACTER(LEN=2), DIMENSION(wind_years+1)                           :: wyear_str               !! string suffix indicating wind year index
364    CHARACTER(LEN=2)                                                    :: pyear_str               !! string suffix indicating year index for pest module
365    CHARACTER(LEN=10), DIMENSION(nlctypes)                              :: lctype_str              !! string suffix for the land cover type
366    REAL(r_std), DIMENSION(0:ngrnd)                                     :: zf_soil
367
368    ! Permafrost carbon processes
369    LOGICAL :: read_input_deepC_a
370    LOGICAL :: read_input_deepC_s
371    LOGICAL :: read_input_deepC_p
372    LOGICAL :: read_input_thawed_humidity
373    LOGICAL :: read_input_depth_organic_soil
374
375!_ ================================================================================================================================
376
377    IF (printlev >= 3) WRITE(numout,*) 'Entering readrestart'
378    !-
379    ! 1 string definitions
380    !-
381    DO l=1,nlctypes
382       IF (l == iforest) THEN
383          lctype_str(l) = '_forest'
384       ELSEIF (l == igrass) THEN
385          lctype_str(l) = '_grass'
386       ELSEIF (l == icrop) THEN
387          lctype_str(l) = '_crop'
388       ELSE
389          CALL ipslerr_p(3,'stomate_io readrestart','Define lctype_str(l)','','')
390       ENDIF   
391    END DO
392    !-
393    pools_str(1:nbpools) =(/'str_ab ','str_be ','met_ab ','met_be ','wood_ab','wood_be',& 
394         & 'actif  ','slow   ','passif ','surface'/) 
395    !-
396    DO l=1,nelements
397       IF     (l == icarbon) THEN
398          element_str(l) = '_c'
399       ELSEIF (l == initrogen) THEN
400          element_str(l) = '_n'
401       ELSE
402          CALL ipslerr_p(3,'stomate_io readrestart','Define element_str','','')
403       ENDIF
404    ENDDO
405
406    ! Vertical soil layers
407    zf_soil(1:ngrnd) = zlt(:)
408    zf_soil(0) = 0.
409
410    !-
411    ! 2 run control
412    !-
413    ! 2.2 time step of STOMATE in days
414    !-    If the variable is not in the restart file, then un will be used as default value
415    CALL restget_p(rest_id_stomate, 'dt_days', itime, .TRUE., un, dt_days)
416    !-
417    ! 2.3 date
418    !-    If the variable is not in the restart file, then zero will be used as default value
419    CALL restget_p (rest_id_stomate, 'date', itime, .TRUE., zero, date_real)
420    date_loc = NINT(date_real)
421    !-
422    ! 3 daily meteorological variables
423    !-
424    vegstress_day(:,:) = val_exp
425    var_name = 'vegstress_day'
426    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
427         &              .TRUE., vegstress_day, 'gather', nbp_glo, index_g)
428    IF (ALL(vegstress_day(:,:) == val_exp)) vegstress_day(:,:) = zero
429    !-
430    gdd_init_date(:,:) = val_exp
431    var_name = 'gdd_init_date'
432    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 2, 1, itime, &
433         &              .TRUE., gdd_init_date, 'gather', nbp_glo, index_g)
434    ! Keep val_exp as initial value for gdd_init_date(:,2)
435    IF (ALL(gdd_init_date(:,1) == val_exp)) gdd_init_date(:,1) = 365.
436
437    !-
438    litterhum_daily(:) = val_exp
439    var_name = 'litterhum_daily'
440    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
441         &              .TRUE., litterhum_daily, 'gather', nbp_glo, index_g)
442    IF (ALL(litterhum_daily(:) == val_exp)) litterhum_daily(:) = zero
443    !-
444    t2m_daily(:) = val_exp
445    var_name = 't2m_daily'
446    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
447         &                .TRUE., t2m_daily, 'gather', nbp_glo, index_g)
448    IF (ALL(t2m_daily(:) == val_exp)) t2m_daily(:) = zero
449    !-
450    t2m_min_daily(:) = val_exp
451    var_name = 't2m_min_daily'
452    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
453         &                .TRUE., t2m_min_daily, 'gather', nbp_glo, index_g)
454    IF (ALL(t2m_min_daily(:) == val_exp)) t2m_min_daily(:) = large_value
455    !-
456    tsurf_daily(:) = val_exp
457    var_name = 'tsurf_daily'
458    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
459         &                .TRUE., tsurf_daily, 'gather', nbp_glo, index_g)
460    ! The initial value is set to the current temperature at 2m
461    IF (ALL(tsurf_daily(:) == val_exp)) tsurf_daily(:) = temp_air(:)
462    !-
463    tsoil_daily(:,:) = val_exp
464    var_name = 'tsoil_daily'
465    CALL restget_p (rest_id_stomate, var_name, nbp_glo,   nslm, 1, itime, &
466         &                .TRUE., tsoil_daily, 'gather', nbp_glo, index_g)
467    IF (ALL(tsoil_daily(:,:) == val_exp)) tsoil_daily(:,:) = zero
468    !-
469    precip_daily(:) = val_exp
470    var_name = 'precip_daily'
471    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
472         &                .TRUE., precip_daily, 'gather', nbp_glo, index_g)
473    IF (ALL(precip_daily(:) == val_exp)) precip_daily(:) = zero
474    !-
475    ! 4 productivities
476    !-
477    gpp_daily(:,:) = val_exp
478    var_name = 'gpp_daily'
479    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
480         &              .TRUE., gpp_daily, 'gather', nbp_glo, index_g)
481    IF (ALL(gpp_daily(:,:) == val_exp)) gpp_daily(:,:) = zero
482    !-
483    npp_daily(:,:) = val_exp
484    var_name = 'npp_daily'
485    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
486         &              .TRUE., npp_daily, 'gather', nbp_glo, index_g)
487    IF (ALL(npp_daily(:,:) == val_exp)) npp_daily(:,:) = zero
488    !-
489    turnover_daily(:,:,:,:) = val_exp
490    CALL restget_p (rest_id_stomate, 'turnover_daily', nbp_glo, nvm, nparts, nelements, itime, & 
491        &                .TRUE., turnover_daily, 'gather', nbp_glo, index_g) 
492    IF (ALL(turnover_daily  == val_exp)) turnover_daily(:,:,:,:) = zero
493    !-
494    CALL restget_p (rest_id_stomate, 'turnover_resid', nbp_glo, nvm, nparts, nelements, itime, & 
495        &                .TRUE., turnover_resid, 'gather', nbp_glo, index_g) 
496    IF (ALL(turnover_resid  == val_exp)) turnover_resid(:,:,:,:) = zero
497
498    !-
499    ! 5 monthly meteorological variables
500    !-
501    ! The following variables vegstress_month and vegstress_week
502    ! are not initialized here if they were not found in the restart file. Initalization will be done in
503    ! stomate_season with daily variables calculated in stomate.
504    vegstress_month(:,:) = val_exp
505    var_name = 'vegstress_month'
506    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
507         &              .TRUE., vegstress_month, 'gather', nbp_glo, index_g)
508   
509    vegstress_week(:,:) = val_exp
510    var_name = 'vegstress_week'
511    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
512         &              .TRUE., vegstress_week, 'gather', nbp_glo, index_g)
513
514    ! vegstress_season is intialized to 1 if not found in restart file in oposite of the variable above
515    vegstress_season(:,:) = val_exp
516    var_name = 'vegstress_season'
517    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
518         &              .TRUE., vegstress_season, 'gather', nbp_glo, index_g)
519    IF (ALL(vegstress_season(:,:) == val_exp)) vegstress_season(:,:) = un
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       CALL restget_p (rest_id_stomate, 'tau_longterm', itime, .TRUE., val_exp, tau_longterm)
540       IF (tau_longterm == val_exp) THEN
541             ! tau_longterm is not found in restart file.
542             ! This is not normal as t2m_longterm was in restart file. Write a warning and initialize it to tau_longterm_max
543          CALL ipslerr(2, 'stomate_io readrestart','tau_longterm was not in restart file',&
544               'But t2m_longterm was in restart file','')
545          tau_longterm = tau_longterm_max
546       END IF
547
548    END IF
549    !-
550    t2m_month(:) = val_exp
551    var_name = 't2m_month'
552    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
553         &              .TRUE., t2m_month, 'gather', nbp_glo, index_g)
554    IF (ALL(t2m_month(:) == val_exp)) t2m_month(:) = temp_air(:)
555   
556    CALL restget_p (rest_id_stomate, 'Tseason', nbp_glo, 1     , 1, itime, &
557         .TRUE., Tseason, 'gather', nbp_glo, index_g)
558    IF (ALL(Tseason(:) == val_exp)) Tseason(:) = temp_air(:)
559   
560    CALL restget_p (rest_id_stomate,'Tseason_length', nbp_glo, 1     , 1, itime, &
561         .TRUE., Tseason_length, 'gather', nbp_glo, index_g)
562    IF (ALL(Tseason_length(:) == val_exp)) Tseason_length(:) = zero
563   
564    CALL restget_p (rest_id_stomate, 'Tseason_tmp', nbp_glo, 1     , 1, itime, &
565         .TRUE., Tseason_tmp, 'gather', nbp_glo, index_g)
566    IF (ALL(Tseason_tmp(:) == val_exp)) Tseason_tmp(:) = zero
567
568    CALL restget_p (rest_id_stomate, 'Tmin_spring_time', nbp_glo, nvm, 1, itime, &
569         .TRUE., Tmin_spring_time, 'gather', nbp_glo, index_g)
570    IF (ALL(Tmin_spring_time(:,:) == val_exp)) Tmin_spring_time(:,:) = zero
571
572    t2m_week(:) = val_exp
573    var_name = 't2m_week'
574    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
575         &              .TRUE., t2m_week, 'gather', nbp_glo, index_g)
576    ! The initial value is set to the current temperature
577    IF (ALL(t2m_week(:) == val_exp)) t2m_week(:) = temp_air(:)
578   
579    tsoil_month(:,:) = val_exp
580    var_name = 'tsoil_month'
581    CALL restget_p (rest_id_stomate, var_name, nbp_glo,   nslm, 1, itime, &
582         &              .TRUE., tsoil_month, 'gather', nbp_glo, index_g)
583
584    ! The initial value is set to the current temperature
585    IF (ALL(tsoil_month(:,:) == val_exp)) THEN
586       DO l=1,nslm
587          tsoil_month(:,l) = temp_air(:)
588       ENDDO
589    ENDIF
590    !-
591
592    wstress_season(:,:) = val_exp
593    var_name = 'wstress_season'
594    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
595         &                .TRUE., wstress_season, 'gather', nbp_glo, index_g)
596    IF (ALL(wstress_season(:,:) == val_exp)) wstress_season(:,:) = un
597    !-
598    wstress_month(:,:) = val_exp
599    var_name = 'wstress_month'
600    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
601         &                .TRUE., wstress_month, 'gather', nbp_glo, index_g)
602    IF (ALL(wstress_month(:,:) == val_exp)) wstress_month(:,:) = un
603    !-
604    ! 6 fire probability
605    !-
606    fireindex(:,:) = val_exp
607    var_name = 'fireindex'
608    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
609         &              .TRUE., fireindex, 'gather', nbp_glo, index_g)
610    IF (ALL(fireindex(:,:) == val_exp)) fireindex(:,:) = zero
611    !-
612    firelitter(:,:) = val_exp
613    var_name = 'firelitter'
614    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
615         &              .TRUE., firelitter, 'gather', nbp_glo, index_g)
616    IF (ALL(firelitter(:,:) == val_exp)) firelitter(:,:) = zero
617    !-
618    ! 7 maximum and minimum moisture availabilities for tropic phenology
619    !-
620    maxvegstress_lastyear(:,:) = val_exp
621    var_name = 'maxmoistr_last'
622    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
623         &              .TRUE., maxvegstress_lastyear, 'gather', nbp_glo, index_g)
624    IF (ALL(maxvegstress_lastyear(:,:) == val_exp)) &
625         &     maxvegstress_lastyear(:,:) = zero
626    !-
627    maxvegstress_thisyear(:,:) = val_exp
628    var_name = 'maxmoistr_this'
629    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
630         &              .TRUE., maxvegstress_thisyear, 'gather', nbp_glo, index_g)
631    IF (ALL(maxvegstress_thisyear(:,:) == val_exp)) &
632         &     maxvegstress_thisyear(:,:) = zero
633    !-
634    minvegstress_lastyear(:,:) = val_exp
635    var_name = 'minmoistr_last'
636    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
637         &              .TRUE., minvegstress_lastyear, 'gather', nbp_glo, index_g)
638    IF (ALL(minvegstress_lastyear(:,:) == val_exp)) &
639         &     minvegstress_lastyear(:,:) = un
640    !-
641    minvegstress_thisyear(:,:) = val_exp
642    var_name = 'minmoistr_this'
643    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
644         &              .TRUE., minvegstress_thisyear, 'gather', nbp_glo, index_g)
645    IF (ALL( minvegstress_thisyear(:,:) == val_exp)) &
646         &     minvegstress_thisyear(:,:) = large_value
647    !-
648    ! 8 maximum "weekly" GPP
649    !-
650    maxgppweek_lastyear(:,:) = val_exp
651    var_name = 'maxgppweek_lastyear'
652    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
653         &              .TRUE., maxgppweek_lastyear, 'gather', nbp_glo, index_g)
654    IF (ALL(maxgppweek_lastyear(:,:) == val_exp)) &
655         &     maxgppweek_lastyear(:,:) = zero
656    !-
657    maxgppweek_thisyear(:,:) = val_exp
658    var_name = 'maxgppweek_thisyear'
659    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
660         &              .TRUE., maxgppweek_thisyear, 'gather', nbp_glo, index_g)
661    IF (ALL(maxgppweek_thisyear(:,:) == val_exp)) &
662         &     maxgppweek_thisyear(:,:) = zero
663    !-
664    ! 9 annual GDD0
665    !-
666    gdd0_thisyear(:) = val_exp
667    var_name = 'gdd0_thisyear'
668    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
669         &              .TRUE., gdd0_thisyear, 'gather', nbp_glo, index_g)
670    IF (ALL(gdd0_thisyear(:) == val_exp)) gdd0_thisyear(:) = zero
671    !-
672    gdd0_lastyear(:) = val_exp
673    var_name = 'gdd0_lastyear'
674    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
675         &              .TRUE., gdd0_lastyear, 'gather', nbp_glo, index_g)
676    IF (ALL(gdd0_lastyear(:) == val_exp)) gdd0_lastyear(:) = gdd_crit_estab
677    !-
678    ! 10 annual precipitation
679    !-
680    precip_thisyear(:) = val_exp
681    var_name = 'precip_thisyear'
682    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
683         &              .TRUE., precip_thisyear, 'gather', nbp_glo, index_g)
684    IF (ALL(precip_thisyear(:) == val_exp)) precip_thisyear(:) = zero
685    !-
686    precip_lastyear(:) = val_exp
687    var_name = 'precip_lastyear'
688    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
689         &              .TRUE., precip_lastyear, 'gather', nbp_glo, index_g)
690    IF (ALL(precip_lastyear(:) == val_exp)) &
691         &     precip_lastyear(:) = precip_crit
692    !-
693    ! 11 derived "biometeorological" variables
694    !-
695    gdd_m5_dormance(:,:) = val_exp
696    var_name = 'gdd_m5_dormance'
697    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
698         &              .TRUE., gdd_m5_dormance, 'gather', nbp_glo, index_g)
699    IF (ALL(gdd_m5_dormance(:,:) == val_exp)) &
700         &     gdd_m5_dormance(:,:) = undef
701    !-
702    gdd_from_growthinit(:,:) = val_exp
703    var_name = 'gdd_from_growthinit'
704    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
705         &              .TRUE., gdd_from_growthinit, 'gather', nbp_glo, index_g)
706    IF (ALL(gdd_from_growthinit(:,:) == val_exp)) &
707         &     gdd_from_growthinit(:,:) = zero
708    !-
709    gdd_midwinter(:,:) = val_exp
710    var_name = 'gdd_midwinter'
711    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
712         &              .TRUE., gdd_midwinter, 'gather', nbp_glo, index_g)
713    IF (ALL(gdd_midwinter(:,:) == val_exp)) gdd_midwinter(:,:) = undef
714    !-
715    ncd_dormance(:,:) = val_exp
716    var_name = 'ncd_dormance'
717    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
718         &              .TRUE., ncd_dormance, 'gather', nbp_glo, index_g)
719    IF (ALL(ncd_dormance(:,:) == val_exp)) ncd_dormance(:,:) = undef
720    !-
721    ngd_minus5(:,:) = val_exp
722    var_name = 'ngd_minus5'
723    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
724         &              .TRUE., ngd_minus5, 'gather', nbp_glo, index_g)
725    IF (ALL(ngd_minus5(:,:) == val_exp)) ngd_minus5(:,:) = zero
726    !-
727    time_hum_min(:,:) = val_exp
728    var_name = 'time_hum_min'
729    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
730         &              .TRUE., time_hum_min, 'gather', nbp_glo, index_g)
731    IF (ALL(time_hum_min(:,:) == val_exp)) time_hum_min(:,:) = undef
732    !-
733    hum_min_dormance(:,:) = val_exp
734    var_name = 'hum_min_dormance'
735    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
736         &              .TRUE., hum_min_dormance, 'gather', nbp_glo, index_g)
737    IF (ALL(hum_min_dormance(:,:) == val_exp)) &
738         &     hum_min_dormance(:,:) = undef
739    !-
740    ! 12 Plant status
741    !-
742    CALL restget_p (rest_id_stomate, 'PFTpresent', nbp_glo, nvm  , 1, itime, &
743         &              .TRUE., PFTpresent_real, 'gather', nbp_glo, index_g)
744    IF (ALL(PFTpresent_real(:,:) == val_exp)) PFTpresent_real(:,:) = zero
745    WHERE (PFTpresent_real(:,:) >= .5)
746       PFTpresent = .TRUE.
747    ELSEWHERE
748       PFTpresent = .FALSE.
749    ENDWHERE
750
751    CALL restget_p (rest_id_stomate, 'is_storm', nbp_glo, 1, 1, itime, &
752         &              .TRUE., is_storm_real, 'gather', nbp_glo, index_g)
753    IF (ALL(is_storm_real(:) == val_exp)) is_storm_real(:) = zero
754    WHERE (is_storm_real(:) >= .5)
755       is_storm = .TRUE.
756    ELSEWHERE
757       is_storm = .FALSE.
758    ENDWHERE
759
760    CALL restget_p (rest_id_stomate, 'count_storm', nbp_glo, 1, 1, itime, &
761                        .TRUE., count_storm_real,'gather', nbp_glo, index_g)
762    count_storm = NINT(count_storm_real)
763
764    !-
765    !CALL restget_p (rest_id_stomate, 'ind', nbp_glo, nvm  , 1, itime, &
766    !     &              .TRUE., ind, 'gather', nbp_glo, index_g)
767    !IF (ALL(ind(:,:) == val_exp)) ind(:,:) = zero
768    !-
769    CALL restget_p (rest_id_stomate, 'adapted', nbp_glo, nvm  , 1, itime, &
770         &              .TRUE., adapted, 'gather', nbp_glo, index_g)
771    IF (ALL(adapted(:,:) == val_exp)) adapted(:,:) = zero
772    !-
773    CALL restget_p (rest_id_stomate, 'regenerate', nbp_glo, nvm  , 1, itime, &
774         &              .TRUE., regenerate, 'gather', nbp_glo, index_g)
775    IF (ALL(regenerate(:,:) == val_exp)) regenerate(:,:) = zero
776    !-
777    CALL restget_p (rest_id_stomate, 'npp_longterm', nbp_glo, nvm  , 1, itime, &
778         &              .TRUE., npp_longterm, 'gather', nbp_glo, index_g)
779    IF (ALL(npp_longterm(:,:) == val_exp)) npp_longterm(:,:) = zero
780    !-
781    CALL restget_p (rest_id_stomate, 'croot_longterm', nbp_glo, nvm  , 1, itime, &
782         &              .TRUE., croot_longterm, 'gather', nbp_glo, index_g)
783    IF (ALL(croot_longterm(:,:) == val_exp)) croot_longterm(:,:) = zero
784    !-
785    CALL restget_p (rest_id_stomate, 'n_reserve_longterm', nbp_glo, nvm  , 1, itime, &
786         &              .TRUE., n_reserve_longterm, 'gather', nbp_glo, index_g)
787    IF (ALL(n_reserve_longterm(:,:) == val_exp)) n_reserve_longterm(:,:) = un
788    !-
789    CALL restget_p (rest_id_stomate, 'lm_lastyearmax', nbp_glo, nvm  , 1, itime, &
790         &              .TRUE., lm_lastyearmax, 'gather', nbp_glo, index_g)
791    IF (ALL(lm_lastyearmax(:,:) == val_exp)) lm_lastyearmax(:,:) = zero
792    !-
793    CALL restget_p (rest_id_stomate, 'lm_thisyearmax', nbp_glo, nvm  , 1, itime, &
794         &              .TRUE., lm_thisyearmax, 'gather', nbp_glo, index_g)
795    IF (ALL(lm_thisyearmax(:,:) == val_exp)) lm_thisyearmax(:,:) = zero
796    !-
797    CALL restget_p (rest_id_stomate, 'maxfpc_lastyear', nbp_glo, nvm  , 1, itime, &
798         &              .TRUE., maxfpc_lastyear, 'gather', nbp_glo, index_g)
799    IF (ALL(maxfpc_lastyear(:,:) == val_exp)) maxfpc_lastyear(:,:) = zero
800    !-
801    CALL restget_p (rest_id_stomate, 'maxfpc_thisyear', nbp_glo, nvm  , 1, itime, &
802         &              .TRUE., maxfpc_thisyear, 'gather', nbp_glo, index_g)
803    IF (ALL(maxfpc_thisyear(:,:) == val_exp)) maxfpc_thisyear(:,:) = zero
804    !-
805    CALL restget_p (rest_id_stomate, 'turnover_time', nbp_glo, nvm  , nparts, itime, &
806         &              .TRUE., turnover_time, 'gather', nbp_glo, index_g)
807    IF ( ALL( turnover_time(:,:,:) == val_exp)) turnover_time(:,:,:) = 100.
808    !-
809    CALL restget_p (rest_id_stomate, 'turnover_longterm', nbp_glo, nvm, nparts, nelements, itime, & 
810         &              .TRUE., turnover_longterm, 'gather', nbp_glo, index_g) 
811    IF (ALL(turnover_longterm == val_exp)) turnover_longterm(:,:,:,:) = zero
812    !-
813    CALL restget_p (rest_id_stomate, 'gpp_week', nbp_glo, nvm  , 1, itime, &
814         &              .TRUE., gpp_week, 'gather', nbp_glo, index_g)
815    IF (ALL(gpp_week(:,:) == val_exp)) gpp_week(:,:) = zero
816    !-
817    CALL restget_p (rest_id_stomate, 'resp_maint_week', nbp_glo, nvm  , 1, itime, &
818         &              .TRUE., resp_maint_week, 'gather', nbp_glo, index_g)
819    IF (ALL(resp_maint_week(:,:) == val_exp)) resp_maint_week(:,:) = zero
820    !-
821    CALL restget_p (rest_id_stomate, 'lai_per_level', nbp_glo, nvm, nlevels_tot, itime, &
822         &               .TRUE., lai_per_level, 'gather', nbp_glo, index_g)
823    IF (ALL(lai_per_level == val_exp)) lai_per_level(:,:,:) = zero
824    !
825    ! This is ugly, since the restart routines were not developed to deal with structures.
826    ! But all I have to do is copy some things to arrays.
827    CALL restget_p (rest_id_stomate, 'laieff_fit', nbp_glo, nvm , nlevels_tot, nparams_laieff, itime, &
828          .TRUE., temp_array, 'gather', nbp_glo, index_g)
829    IF (ALL(temp_array == val_exp)) temp_array = zero
830
831    DO ipts=1,npts
832       DO ivm=1,nvm
833          DO ilev=1,nlevels_tot
834             laieff_fit(ipts,ivm,ilev)%a=temp_array(ipts,ivm,ilev,1)
835             laieff_fit(ipts,ivm,ilev)%b=temp_array(ipts,ivm,ilev,2)
836             laieff_fit(ipts,ivm,ilev)%c=temp_array(ipts,ivm,ilev,3)
837             laieff_fit(ipts,ivm,ilev)%d=temp_array(ipts,ivm,ilev,4)
838             laieff_fit(ipts,ivm,ilev)%e=temp_array(ipts,ivm,ilev,5)
839          ENDDO
840       ENDDO
841    ENDDO
842    !
843    CALL restget_p (rest_id_stomate, 'maint_resp', nbp_glo, nvm, nparts, itime, &
844         &                   .TRUE., resp_maint_part, 'gather', nbp_glo, index_g)
845    IF (ALL(resp_maint_part == val_exp)) resp_maint_part(:,:,:) = zero
846    !-
847    CALL restget_p (rest_id_stomate, 'leaf_age', nbp_glo, nvm, nleafages, itime, &
848         &                   .TRUE., leaf_age(:,:,:), 'gather', nbp_glo, index_g)
849    IF (ALL(leaf_age == val_exp)) leaf_age(:,:,:) = zero
850    !-
851    CALL restget_p (rest_id_stomate, 'leaf_frac', nbp_glo, nvm, nleafages, itime, &
852         &                  .TRUE., leaf_frac(:,:,:), 'gather', nbp_glo, index_g)
853    IF (ALL(leaf_frac(:,:,:) == val_exp)) leaf_frac(:,:,:) = zero
854    !-
855    ! leaf_age_crit depends on t2m_longterm and longevity_leaf. At
856    ! the initialization phase t2m_longterm is not yet known so, leag_age_crit
857    ! cannot yet be calculated (see stomate_season.f90). A work around is used
858    ! to guess leaf_age_crit for the first time step.
859    CALL restget_p (rest_id_stomate, 'leaf_age_crit', nbp_glo, nvm, 1, itime, &
860         &                  .TRUE., leaf_age_crit(:,:), 'gather', nbp_glo, index_g)
861    IF (ALL(leaf_age_crit(:,:) == val_exp)) THEN
862       leaf_age_crit(:,1) = zero
863       DO ivm = 2,nvm
864          leaf_age_crit(:,:) = longevity_leaf(ivm)
865       END DO
866    END IF
867    !-
868    CALL restget_p (rest_id_stomate, 'plant_status', nbp_glo, nvm  , 1, itime, &
869         &                .TRUE., plant_status, 'gather', nbp_glo, index_g)
870    IF (ALL(plant_status(:,:) == val_exp)) THEN
871       plant_status(:,:) = iprescribe
872       plant_status(:,ibare_sechiba) = inone
873    ENDIF
874    !-
875    CALL restget_p (rest_id_stomate, 'when_growthinit', nbp_glo, nvm  , 1, itime, &
876         &                .TRUE., when_growthinit, 'gather', nbp_glo, index_g)
877    IF (ALL(when_growthinit(:,:) == val_exp)) when_growthinit(:,:) = 240.
878    !-
879    CALL restget_p (rest_id_stomate, 'age', nbp_glo, nvm  , 1, itime, &
880         &                .TRUE., age, 'gather', nbp_glo, index_g)
881    IF (ALL(age(:,:) == val_exp)) age(:,:) = zero
882    !-
883    ! 13 CO2
884    !-
885    CALL restget_p (rest_id_stomate, 'resp_hetero', nbp_glo, nvm, 1, itime, &
886         &                .TRUE., resp_hetero, 'gather', nbp_glo, index_g)
887    IF (ALL(resp_hetero(:,:) == val_exp)) resp_hetero(:,:) = zero
888    !-
889    CALL restget_p (rest_id_stomate, 'resp_maint', nbp_glo, nvm  , 1, itime, &
890         &                .TRUE., resp_maint, 'gather', nbp_glo, index_g)
891    IF (ALL(resp_maint(:,:) == val_exp)) resp_maint(:,:) = zero
892    !-
893    CALL restget_p (rest_id_stomate, 'resp_growth', nbp_glo, nvm  , 1, itime, &
894         &                .TRUE., resp_growth, 'gather', nbp_glo, index_g)
895    IF (ALL(resp_growth(:,:) == val_exp)) resp_growth(:,:) = zero
896    !-
897    co2_fire(:,:) = val_exp
898    var_name = 'co2_fire'
899    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
900         &                .TRUE., co2_fire, 'gather', nbp_glo, index_g)
901    IF (ALL(co2_fire(:,:) == val_exp)) co2_fire(:,:) = zero
902    !-
903    CALL restget_p (rest_id_stomate, 'atm_to_bm', nbp_glo, nvm, nelements, itime, &
904         &                .TRUE., atm_to_bm, 'gather', nbp_glo, index_g)
905    IF (ALL(atm_to_bm == val_exp)) atm_to_bm(:,:,:) = zero
906
907    !-
908    ! 14 vegetation distribution after last light competition
909    !-
910    var_name = 'veget_lastlight'
911    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
912         &                .TRUE., veget_lastlight, 'gather', nbp_glo, index_g)
913    IF (ALL(veget_lastlight(:,:) == val_exp)) veget_lastlight(:,:) = zero
914    !-
915    ! 15 establishment criteria
916    !-
917    var_name = 'everywhere'
918    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
919         &                .TRUE., everywhere, 'gather', nbp_glo, index_g)
920    IF (ALL(everywhere(:,:) == val_exp)) everywhere(:,:) = zero
921    !-
922    var_name = 'need_adjacent'
923    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
924         &                .TRUE., need_adjacent_real, 'gather', nbp_glo, index_g)
925    IF (ALL(need_adjacent_real(:,:) == val_exp)) &
926         &     need_adjacent_real(:,:) = zero
927    WHERE ( need_adjacent_real(:,:) >= .5 )
928       need_adjacent = .TRUE.
929    ELSEWHERE
930       need_adjacent = .FALSE.
931    ENDWHERE
932    !-
933    var_name = 'RIP_time'
934    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
935         &                .TRUE., RIP_time, 'gather', nbp_glo, index_g)
936    IF (ALL(RIP_time(:,:) == val_exp)) RIP_time(:,:) = large_value
937    !-
938    ! 17 litter
939    !-
940    CALL restget_p (rest_id_stomate, 'litter_c', nbp_glo, nlitt, nvm, nlevs, itime, &
941         &                     .TRUE., litter(:,:,:,:,icarbon), 'gather', nbp_glo, index_g)
942    IF (ALL(litter(:,:,:,:,icarbon) == val_exp)) litter(:,:,:,:,icarbon) = zero
943    CALL restget_p (rest_id_stomate, 'litter_n', nbp_glo, nlitt, nvm, nlevs,itime, &
944         &                     .TRUE., litter(:,:,:,:,initrogen), 'gather', nbp_glo,index_g)
945    IF (ALL(litter(:,:,:,:,initrogen) == val_exp)) litter(:,:,:,:,initrogen) = zero
946
947    CALL restget_p (rest_id_stomate, 'dead_leaves', nbp_glo, nvm, nlitt, itime, &
948          &                   .TRUE., dead_leaves, 'gather', nbp_glo, index_g)
949    IF (ALL(dead_leaves == val_exp)) dead_leaves = zero
950
951    CALL restget_p (rest_id_stomate, 'soil_carbon', nbp_glo, ncarb, nvm, itime, &
952         &                   .TRUE., som(:,:,:,icarbon), 'gather', nbp_glo, index_g) 
953    ! Initialise the soil pools.
954    IF (ALL(som(:,:,:,icarbon) == val_exp)) THEN
955       ! We set the pools to zero for all PFTs
956       som(:,:,:,icarbon) = zero
957       ! Initialize all PFTs that are present. Note that PFT1 is
958       ! left at zero.
959       DO ivm = 2,nvm
960          WHERE (veget_max(:,ivm) .GT. min_stomate) 
961             ! Set the initial values for PFTs that are present. 
962             som(:,iactive,ivm,icarbon) = som_init_active 
963             som(:,isurface,ivm,icarbon) = som_init_surface 
964             som(:,islow,ivm,icarbon) = som_init_slow
965             som(:,ipassive,ivm,icarbon) = som_init_passive
966          END WHERE
967       ENDDO 
968    ENDIF
969
970    CALL restget_p (rest_id_stomate, 'soil_nitrogen', nbp_glo, ncarb, nvm, itime, & 
971         &                   .TRUE., som(:,:,:,initrogen), 'gather', nbp_glo, index_g) 
972    IF (ALL(som(:,:,:,initrogen) == val_exp)) THEN
973       som(:,iactive,:,initrogen) = som(:,iactive,:,icarbon) / CN_target_iactive_ref 
974       som(:,isurface,:,initrogen) = som(:,isurface,:,icarbon) / CN_target_isurface_ref 
975       som(:,islow,:,initrogen) = som(:,islow,:,icarbon) / CN_target_islow_ref 
976       som(:,ipassive,:,initrogen) =  som(:,ipassive,:,icarbon) / CN_target_ipassive_ref 
977    ENDIF
978
979    CALL restget_p (rest_id_stomate, 'lignin_struc', nbp_glo, nvm, nlevs, itime, &
980         &     .TRUE., lignin_struc, 'gather', nbp_glo, index_g)
981    IF (ALL(lignin_struc == val_exp)) lignin_struc(:,:,:) = zero
982
983    CALL restget_p (rest_id_stomate, 'lignin_wood', nbp_glo, nvm, nlevs, itime, &
984         &     .TRUE., lignin_wood, 'gather', nbp_glo, index_g)
985    IF (ALL(lignin_wood == val_exp)) lignin_wood(:,:,:) = zero
986
987
988    ! 18 Product use and LCC
989    !-
990
991    var_name = 'co2_flux'
992    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
993         .TRUE., co2_flux, 'gather', nbp_glo, index_g)
994    IF (ALL(co2_flux(:,:) == val_exp)) co2_flux(:,:) = zero
995
996    var_name = 'fco2_lu'
997    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
998         .TRUE., fco2_lu, 'gather', nbp_glo, index_g)
999    IF (ALL(fco2_lu(:) == val_exp)) fco2_lu(:) = zero
1000
1001    var_name = 'fco2_wh'
1002    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
1003         .TRUE., fco2_wh, 'gather', nbp_glo, index_g)
1004    IF (ALL(fco2_wh(:) == val_exp)) fco2_wh(:) = zero
1005
1006    var_name = 'fco2_ha'
1007    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
1008         .TRUE., fco2_ha, 'gather', nbp_glo, index_g)
1009    IF (ALL(fco2_ha(:) == val_exp)) fco2_ha(:) = zero
1010
1011       
1012    IF (vegetmap_reset) THEN
1013
1014       ! Reset vegetation map related variables instead of reading from restart file
1015       ! vegetmap_reset is an option to change vegetation map without activating LAND
1016       ! USE change for carbon fluxes. At the same time carbon related variables are
1017       ! reset to zero. Use this option to change vegetation map while keeping
1018       ! VEGET_UPDATE=0Y.
1019
1020       ! ChaoYue: Be very careful for these following lines though. The First 6
1021       ! variables all carry legacy information on harvest or land-use-change
1022       ! related pools. Simply reseting them to zero might lead to mass balance
1023       ! problem.
1024       prod_s(:,:,:,:,:) = zero
1025       prod_m(:,:,:,:,:) = zero
1026       prod_l(:,:,:,:,:) = zero
1027       flux_s(:,:,:,:,:) = zero
1028       flux_m(:,:,:,:,:) = zero
1029       flux_l(:,:,:,:,:) = zero
1030
1031    ELSE
1032
1033       DO l = 1,nlctypes
1034
1035          var_name = 'prod_s'//TRIM(lctype_str(l))
1036          CALL restget_p (rest_id_stomate, var_name, nbp_glo, nshort+1, nelements, nlanduse, itime, &
1037               &                .TRUE., prod_s(:,:,:,:,l), 'gather', nbp_glo, index_g)
1038          IF (ALL(prod_s(:,:,:,:,l) == val_exp)) prod_s(:,:,:,:,l) = zero
1039
1040          var_name = 'prod_m'//TRIM(lctype_str(l))
1041          CALL restget_p (rest_id_stomate, var_name, nbp_glo, nmedium+1, nelements, nlanduse, itime, &
1042               &                .TRUE., prod_m(:,:,:,:,l), 'gather', nbp_glo, index_g)
1043          IF (ALL(prod_m(:,:,:,:,l) == val_exp)) prod_m(:,:,:,:,l) = zero
1044         
1045          var_name = 'prod_l'//TRIM(lctype_str(l))
1046          CALL restget_p (rest_id_stomate, var_name, nbp_glo, nlong+1, nelements, nlanduse, itime, &
1047               &                .TRUE., prod_l(:,:,:,:,l), 'gather', nbp_glo, index_g)
1048          IF (ALL(prod_l(:,:,:,:,l) == val_exp)) prod_l(:,:,:,:,l) = zero
1049         
1050          var_name = 'flux_s'//TRIM(lctype_str(l))
1051          CALL restget_p (rest_id_stomate, var_name, nbp_glo, nshort , nelements, nlanduse, itime, &
1052               &                .TRUE., flux_s(:,:,:,:,l), 'gather', nbp_glo, index_g)
1053          IF (ALL(flux_s(:,:,:,:,l) == val_exp)) flux_s(:,:,:,:,l) = zero
1054         
1055          var_name = 'flux_m'//TRIM(lctype_str(l))
1056          CALL restget_p (rest_id_stomate, var_name, nbp_glo, nmedium, nelements, nlanduse, itime, &
1057            &                .TRUE., flux_m(:,:,:,:,l), 'gather', nbp_glo, index_g)
1058          IF (ALL(flux_m(:,:,:,:,l) == val_exp)) flux_m(:,:,:,:,l) = zero
1059         
1060          var_name = 'flux_l'//TRIM(lctype_str(l))
1061          CALL restget_p (rest_id_stomate, var_name, nbp_glo, nlong, nelements, nlanduse, itime, &
1062               &                .TRUE., flux_l(:,:,:,:,l), 'gather', nbp_glo, index_g)
1063          IF (ALL(flux_l(:,:,:,:,l) == val_exp)) flux_l(:,:,:,:,l) = zero
1064
1065       END DO
1066
1067    END IF  ! vegetmap_reset
1068
1069
1070    fDeforestToProduct(:,:) = val_exp
1071    var_name = 'fDeforestToProduct'
1072    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1073         &   .TRUE., fDeforestToProduct, 'gather', nbp_glo, index_g)
1074    IF (ALL(fDeforestToProduct(:,:) ==val_exp)) fDeforestToProduct(:,:) = zero
1075
1076    fLulccResidue(:,:) = val_exp
1077    var_name = 'fLulccResidue'
1078    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1079         &   .TRUE., fLulccResidue, 'gather', nbp_glo, index_g)
1080    IF (ALL(fLulccResidue(:,:) ==val_exp)) fLulccResidue(:,:) = zero
1081
1082    fHarvestToProduct(:,:) = val_exp
1083    var_name = 'fHarvestToProduct'
1084    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1085         &   .TRUE., fHarvestToProduct, 'gather', nbp_glo, index_g)
1086    IF (ALL(fHarvestToProduct(:,:) ==val_exp)) fHarvestToProduct(:,:) = zero
1087
1088    !-
1089    bm_to_litter(:,:,:,:) = val_exp
1090    CALL restget_p (rest_id_stomate, 'bm_to_litter', nbp_glo, nvm, nparts, nelements, itime, &
1091         &                .TRUE., bm_to_litter, 'gather', nbp_glo, index_g)
1092    IF (ALL(bm_to_litter == val_exp)) bm_to_litter(:,:,:,:) = zero
1093    !-
1094    bm_to_litter_resid(:,:,:,:) = val_exp
1095    CALL restget_p (rest_id_stomate, 'bm_to_litter_resid', nbp_glo, nvm, nparts, nelements, itime, &
1096         &                .TRUE., bm_to_litter_resid, 'gather', nbp_glo, index_g)
1097    IF (ALL(bm_to_litter_resid == val_exp)) bm_to_litter_resid(:,:,:,:) = zero
1098    !-
1099    tree_bm_to_litter(:,:,:,:) = val_exp
1100    CALL restget_p (rest_id_stomate, 'tree_to_litter', nbp_glo, nvm, nparts, nelements, itime, &
1101          &                .TRUE., tree_bm_to_litter, 'gather', nbp_glo, index_g)
1102    IF (ALL(tree_bm_to_litter == val_exp)) tree_bm_to_litter = zero
1103    !-
1104    tree_bm_to_litter_resid(:,:,:,:) = val_exp
1105    CALL restget_p (rest_id_stomate, 'tree_to_litter_resid', nbp_glo, nvm, nparts, nelements, itime, &
1106          &                .TRUE., tree_bm_to_litter_resid, 'gather', nbp_glo, index_g)
1107    IF (ALL(tree_bm_to_litter_resid == val_exp)) tree_bm_to_litter_resid = zero
1108    !-
1109    carb_mass_total(:) = val_exp
1110    var_name = 'carb_mass_total'
1111    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
1112         &              .TRUE., carb_mass_total, 'gather', nbp_glo, index_g)
1113    IF (ALL(carb_mass_total(:) == val_exp)) carb_mass_total(:) = zero
1114    !-
1115    harvest_pool_acc(:,:,:,:) = val_exp
1116    CALL restget_p (rest_id_stomate, 'harvest_pool_acc', nbp_glo, nvm, ndia_harvest+1, nelements, itime, &
1117         &                .TRUE., harvest_pool_acc, 'gather', nbp_glo, index_g)
1118    IF (ALL(harvest_pool_acc == val_exp)) harvest_pool_acc(:,:,:,:) = zero
1119    !-
1120    harvest_area_acc(:,:) = val_exp
1121    CALL restget_p (rest_id_stomate, 'harvest_area_acc', nbp_glo, nvm, 1, itime, &
1122         &                .TRUE., harvest_area_acc, 'gather', nbp_glo, index_g)
1123    IF (ALL(harvest_area_acc == val_exp)) harvest_area_acc(:,:) = zero
1124    !-
1125    IF ( ok_soil_carbon_discretization ) THEN
1126       deepSom_a(:,:,:,:) = val_exp
1127       CALL restget_p (rest_id_stomate, 'deepSOM_a', nbp_glo, ngrnd, nvm, nelements,  itime, &
1128          .TRUE., deepSOM_a, 'gather', nbp_glo, index_g)
1129       IF (ALL(deepSOM_a == val_exp)) THEN
1130          deepSOM_a(:,:,:,icarbon) = 10.
1131          deepSOM_a(:,:,:,initrogen) = deepSOM_a(:,:,:,icarbon) / CN_target_iactive_ref
1132       ENDIF
1133
1134       deepSom_s(:,:,:,:) = val_exp
1135       CALL restget_p (rest_id_stomate, 'deepSOM_s', nbp_glo, ngrnd, nvm, nelements, itime, &
1136          .TRUE., deepSOM_s, 'gather', nbp_glo, index_g)
1137       IF (ALL(deepSOM_s == val_exp)) THEN
1138          deepSOM_s(:,:,:,icarbon) = 30.
1139          deepSOM_s(:,:,:,initrogen) = deepSOM_s(:,:,:,icarbon) / CN_target_islow_ref
1140       ENDIF
1141       deepSom_p(:,:,:,:) = val_exp
1142       CALL restget_p (rest_id_stomate, 'deepSOM_p', nbp_glo, ngrnd, nvm, nelements, itime, &
1143          .TRUE., deepSOM_p, 'gather', nbp_glo, index_g)
1144       IF (ALL(deepSOM_p == val_exp)) THEN
1145          deepSOM_p(:,:,:,icarbon) = 50.
1146          deepSOM_p(:,:,:,initrogen) = deepSOM_p(:,:,:,icarbon) / CN_target_ipassive_ref
1147       ENDIF
1148
1149       CALL restget_p (rest_id_stomate, 'O2_soil', nbp_glo, ngrnd, nvm, itime, &
1150            .TRUE., O2_soil, 'gather', nbp_glo, index_g)
1151       IF (ALL(O2_soil == val_exp)) O2_soil = O2_init_conc
1152
1153       CALL restget_p (rest_id_stomate,'CH4_soil', nbp_glo, ngrnd, nvm, itime, &
1154            .TRUE., CH4_soil, 'gather', nbp_glo, index_g)
1155       IF (ALL(CH4_soil == val_exp)) CH4_soil = CH4_init_conc
1156
1157       CALL restget_p (rest_id_stomate, 'O2_snow', nbp_glo, nsnow, nvm, itime, &
1158            .TRUE., O2_snow, 'gather', nbp_glo, index_g)
1159       IF (ALL(O2_snow == val_exp)) O2_snow = O2_init_conc
1160
1161 
1162       CH4_snow(:,:,:) = val_exp
1163       CALL restget_p (rest_id_stomate,'CH4_snow', nbp_glo, nsnow, nvm, itime, &
1164            .TRUE., CH4_snow, 'gather', nbp_glo, index_g)
1165       IF (ALL(CH4_snow == val_exp)) CH4_snow = CH4_init_conc
1166   
1167       CALL restget_p (rest_id_stomate,'heat_Zimov', nbp_glo, ngrnd, nvm, itime, &
1168            .TRUE., heat_Zimov, 'gather', nbp_glo, index_g)
1169       IF (ALL(heat_Zimov == val_exp)) THEN
1170          heat_Zimov(:,:,:) = 0.0
1171       ENDIF
1172
1173       CALL restget_p (rest_id_stomate,'depth_organic_soil', nbp_glo, 1, 1, itime, &
1174           .TRUE., depth_organic_soil(:), 'gather', nbp_glo, index_g)
1175       IF (ALL(depth_organic_soil(:) == val_exp)) THEN
1176           depth_organic_soil(:) = 0.0
1177           read_input_depth_organic_soil = .TRUE.
1178       ENDIF
1179
1180       fixed_cryoturbation_depth(:,:) = val_exp
1181       CALL restget_p (rest_id_stomate,'fixed_cryoturb_depth', nbp_glo, nvm, 1, itime, &
1182            .TRUE., fixed_cryoturbation_depth, 'gather', nbp_glo, index_g)
1183       IF (ALL(fixed_cryoturbation_depth(:,:) == val_exp)) THEN
1184          fixed_cryoturbation_depth(:,:) = 0.0
1185       ENDIF
1186       
1187    ENDIF
1188
1189    CALL restget_p (rest_id_stomate,'altmax', nbp_glo, nvm, 1, itime, &
1190         .TRUE., altmax, 'gather', nbp_glo, index_g)
1191    IF (ALL(altmax(:,:) == val_exp)) THEN
1192       IF ( ok_soil_carbon_discretization ) THEN
1193          ! altmax will be calculated in stomate_soil_carbon_discretization
1194          altmax(:,:) = 0.0
1195       ELSE
1196          ! altmax will not be calculated in this configuration but it is used
1197          ! in hydrol_root_profile. Hence, altmax needs to get a value that does
1198          ! not affect the calculation of the root profile.
1199          altmax(:,:) = zdr(nslm)
1200       ENDIF
1201    ENDIF
1202   
1203    CALL restget_p (rest_id_stomate, 'nbp_accu_flux', nbp_glo, nelements, 1, itime, &
1204         &     .TRUE., nbp_accu_flux, 'gather', nbp_glo, index_g)
1205    IF (ALL(nbp_accu_flux == val_exp)) THEN
1206       ! There is no restart value which means that the model is at its very first
1207       ! time step. Most likley the user has seeded C and N in the soil to speed
1208       ! up the spinup. This C and N basically bypasses GPP and biological nitrogen
1209       ! fixation. As it once entered the ecosystems (although in the model-world
1210       ! we don really how and when) it should be accounted for in the consistency
1211       ! and mass balance checks.
1212       IF (ok_soil_carbon_discretization) THEN
1213          DO iele = 1,nelements
1214             nbp_accu_flux(:,iele) = zero
1215             DO igrn = 1,ngrnd
1216                nbp_accu_flux(:,iele) = nbp_accu_flux(:,iele) + &
1217                     SUM((deepSOM_a(:,igrn,:,iele) + deepSOM_s(:,igrn,:,iele) + &
1218                     deepSOM_p(:,igrn,:,iele)) * &
1219                     (zf_soil(igrn)-zf_soil(igrn-1)) * veget_max(:,:),2)
1220             END DO
1221          END DO
1222       ELSE
1223          DO iele = 1,nelements
1224             nbp_accu_flux(:,iele) = SUM(SUM(som(:,:,:,iele),2)*veget_max(:,:),2)
1225          END DO
1226       ENDIF
1227    ENDIF
1228
1229    ! nbp_pool_start and nbp_accu_flux should be identical. They are
1230    ! kept as independent variables such that this identity can be checked for
1231    ! in stomate.f90. If we would use a single variable the flux based nbp would
1232    ! contain some pool-based values or the other way around. We want to have
1233    ! two completely independent ways of calculating nbp.
1234    nbp_pool_start(:,:) = val_exp
1235    var_name = 'nbp_pool_start'
1236    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nelements, 1, itime, &
1237         &              .TRUE., nbp_pool_start(:,:), 'gather', nbp_glo, index_g)
1238    IF (ALL(nbp_pool_start(:,:) == val_exp))THEN
1239       ! There is no restart value which means that the model is at its very first
1240       ! time step. Most likley the user has seeded C and N in the soil to speed
1241       ! up the spinup. This C and N basically bypasses GPP and biological nitrogen
1242       ! fixation. As it once entered the ecosystems (although in the model-world
1243       ! we don really how and when) it should be accounted for in the consistency
1244       ! and mass balance checks.
1245       IF (ok_soil_carbon_discretization) THEN
1246          DO iele = 1,nelements
1247             nbp_pool_start(:,iele)=zero
1248             DO igrn = 1,ngrnd
1249                nbp_pool_start(:,iele) = nbp_pool_start(:,iele) + &
1250                     SUM((deepSOM_a(:,igrn,:,iele) + deepSOM_s(:,igrn,:,iele) + &
1251                     deepSOM_p(:,igrn,:,iele)) * &
1252                     (zf_soil(igrn)-zf_soil(igrn-1)) * veget_max(:,:),2)
1253             END DO
1254          END DO
1255       ELSE
1256          DO iele = 1,nelements
1257             nbp_pool_start(:,iele) = SUM(SUM(som(:,:,:,iele),2)*veget_max(:,:),2)
1258          END DO
1259       ENDIF
1260    ENDIF
1261    WRITE(numout,*) 'nbp start, ', nbp_pool_start(1,1)
1262    sugar_load(:,:) = val_exp
1263    var_name = 'sugar_load'
1264    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1265         &   .TRUE., sugar_load, 'gather', nbp_glo, index_g)
1266    IF (ALL(sugar_load(:,:) ==val_exp)) sugar_load(:,:) = un
1267
1268    harvest_cut(:,:) = val_exp
1269    var_name = 'harvest_cut'
1270    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1271         &   .TRUE., harvest_cut, 'gather', nbp_glo, index_g)
1272    IF (ALL(harvest_cut(:,:) ==val_exp)) harvest_cut(:,:) = zero
1273   
1274    burried_litter(:,:,:,:) = val_exp
1275    var_name = 'burried_litter'
1276    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nlitt, nlevs, nelements, itime, &
1277         &   .TRUE., burried_litter, 'gather', nbp_glo, index_g)
1278    IF (ALL(burried_litter(:,:,:,:) ==val_exp)) burried_litter(:,:,:,:) = zero
1279
1280    burried_fresh_ltr(:,:,:) = val_exp
1281    var_name = 'burried_fresh_ltr'
1282    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nparts, nelements, itime, &
1283         &   .TRUE., burried_fresh_ltr, 'gather', nbp_glo, index_g)
1284    IF (ALL(burried_fresh_ltr(:,:,:) ==val_exp)) burried_fresh_ltr(:,:,:) = zero
1285
1286    burried_fresh_som(:,:,:) = val_exp
1287    var_name = 'burried_fresh_som'
1288    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nparts, nelements, itime, &
1289         &   .TRUE., burried_fresh_som, 'gather', nbp_glo, index_g)
1290    IF (ALL(burried_fresh_som(:,:,:) ==val_exp)) burried_fresh_som(:,:,:) = zero
1291
1292    burried_bact(:) = val_exp
1293    var_name = 'burried_bact'
1294    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
1295         &   .TRUE., burried_bact, 'gather', nbp_glo, index_g)
1296    IF (ALL(burried_bact(:) ==val_exp)) burried_bact(:) = zero
1297
1298    burried_fungivores(:) = val_exp
1299    var_name = 'burried_fungivores'
1300    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
1301         &   .TRUE., burried_fungivores, 'gather', nbp_glo, index_g)
1302    IF (ALL(burried_fungivores(:) ==val_exp)) burried_fungivores(:) = zero
1303
1304    burried_min_nitro(:,:) = val_exp
1305    var_name = 'burried_min_nitro'
1306    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nnspec, 1, itime, &
1307         &   .TRUE., burried_min_nitro, 'gather', nbp_glo, index_g)
1308    IF (ALL(burried_min_nitro(:,:) ==val_exp)) burried_min_nitro(:,:) = zero
1309
1310    burried_som(:,:,:) = val_exp
1311    var_name = 'burried_som'
1312    CALL restget_p (rest_id_stomate, var_name, nbp_glo, ncarb, nelements, itime, &
1313         &   .TRUE., burried_som, 'gather', nbp_glo, index_g)
1314    IF (ALL(burried_som(:,:,:) ==val_exp)) burried_som(:,:,:) = zero
1315
1316    burried_deepSOM_a(:,:,:) = val_exp
1317    var_name = 'burried_deepSOM_a'
1318    CALL restget_p (rest_id_stomate, var_name, nbp_glo, ngrnd, nelements, itime, &
1319         &   .TRUE., burried_deepSOM_a, 'gather', nbp_glo, index_g)
1320    IF (ALL(burried_deepSOM_a(:,:,:) ==val_exp)) burried_deepSOM_a(:,:,:) = zero
1321
1322    burried_deepSOM_s(:,:,:) = val_exp
1323    var_name = 'burried_deepSOM_s'
1324    CALL restget_p (rest_id_stomate, var_name, nbp_glo, ngrnd, nelements, itime, &
1325         &   .TRUE., burried_deepSOM_s, 'gather', nbp_glo, index_g)
1326    IF (ALL(burried_deepSOM_s(:,:,:) ==val_exp)) burried_deepSOM_s(:,:,:) = zero
1327
1328    burried_deepSOM_p(:,:,:) = val_exp
1329    var_name = 'burried_deepSOM_p'
1330    CALL restget_p (rest_id_stomate, var_name, nbp_glo, ngrnd, nelements, itime, &
1331         &   .TRUE., burried_deepSOM_p, 'gather', nbp_glo, index_g)
1332    IF (ALL(burried_deepSOM_p(:,:,:) ==val_exp)) burried_deepSOM_p(:,:,:) = zero
1333
1334    ! If the variable is not in the restart file, then zero will be used as default value
1335    CALL restget_p (rest_id_stomate, 'Global_years', itime, .TRUE., zero, global_years)
1336
1337    !-
1338    ! 19. Spinup
1339    !-
1340    IF (spinup_analytic) THEN
1341
1342       !-
1343       ok_equilibrium_real(:) = val_exp
1344       var_name = 'ok_equilibrium'
1345       CALL restget_p (rest_id_stomate, var_name, nbp_glo , 1  , 1, itime, &
1346            &                .TRUE., ok_equilibrium_real,'gather', nbp_glo, index_g)
1347       IF (ALL(ok_equilibrium_real(:) == val_exp)) ok_equilibrium_real(:) = zero
1348       WHERE(ok_equilibrium_real(:) >= 0.5) 
1349          ok_equilibrium = .TRUE.
1350       ELSEWHERE
1351          ok_equilibrium = .FALSE.
1352       ENDWHERE
1353       !-
1354       MatrixV(:,:,:,:) = val_exp
1355       CALL restget_p (rest_id_stomate, 'MatrixV', nbp_glo, nvm, nbpools, nbpools, itime, &
1356                  &                     .TRUE., MatrixV, 'gather', nbp_glo, index_g)
1357       ! If nothing is found in the restart file, we initialize each submatrix by identity
1358       IF (ALL(MatrixV(:,:,:,:) == val_exp))  THEN     
1359          MatrixV(:,:,:,:) = zero       
1360          DO l = 1,nbpools           
1361             MatrixV(:,:,l,l) = un           
1362          END DO
1363       END IF
1364
1365       VectorU(:,:,:)  = val_exp
1366       CALL restget_p &
1367            &    (rest_id_stomate, 'Vector_U', nbp_glo, nvm, nbpools, itime, &
1368            &     .TRUE., VectorU, 'gather', nbp_glo, index_g)
1369       IF (ALL(VectorU == val_exp))  VectorU = zero
1370
1371       previous_stock(:,:,:)  = val_exp
1372       CALL restget_p &
1373            &    (rest_id_stomate, 'previous_stock', nbp_glo, nvm, nbpools, itime, &
1374            &     .TRUE., previous_stock, 'gather', nbp_glo, index_g)
1375       IF (ALL(previous_stock == val_exp))  previous_stock = undef_sechiba
1376
1377       current_stock(:,:,:)  = val_exp
1378       CALL restget_p &
1379            &    (rest_id_stomate, 'current_stock', nbp_glo, nvm, nbpools, itime, &
1380            &     .TRUE., current_stock, 'gather', nbp_glo, index_g)
1381       IF (ALL(current_stock == val_exp))  current_stock = zero
1382
1383       CN_som_litter_longterm(:,:,:)  = val_exp
1384       CALL restget_p &
1385            &    (rest_id_stomate, 'CN_longterm', nbp_glo, nvm, nbpools, itime, &
1386            &     .TRUE., CN_som_litter_longterm, 'gather', nbp_glo, index_g)
1387       IF (ALL(CN_som_litter_longterm == val_exp))  CN_som_litter_longterm = zero
1388
1389       ! If the variable is not in the restart file, then dt_sechiba/one_day will
1390       ! be used as default value
1391       CALL restget_p(rest_id_stomate, 'tau_CN_longterm', itime, &
1392            .TRUE., dt_sechiba/one_day, tau_CN_longterm)
1393 
1394    ENDIF ! spinup_matrix_method
1395
1396    KF(:,:) = val_exp
1397    CALL restget_p (rest_id_stomate, 'KF', nbp_glo, nvm  , 1, itime, &
1398         &                .TRUE., KF, 'gather', nbp_glo, index_g)
1399    ! I don't want to set it equal to zero, since this is a problem if these
1400    ! values are not here!  Better it blows up later on
1401    !IF (ALL(KF(:,:) == val_exp)) KF(:,:) = zero
1402
1403    k_latosa_adapt(:,:) = val_exp
1404    CALL restget_p (rest_id_stomate, 'k_latosa_adapt', nbp_glo, nvm  , 1, itime, &
1405         &                .TRUE., k_latosa_adapt, 'gather', nbp_glo, index_g)
1406    DO m = 1,nvm
1407       IF (ALL(k_latosa_adapt(:,m) == val_exp)) k_latosa_adapt(:,m) = k_latosa_min(m)
1408    ENDDO
1409
1410    rue_longterm(:,:) = val_exp
1411    var_name = 'rue_longterm'
1412    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, &
1413         &        .TRUE., rue_longterm(:,:), 'gather', nbp_glo, index_g)
1414    IF (ALL(rue_longterm(:,:) == val_exp)) rue_longterm(:,:) = 1.
1415
1416    cn_leaf_min_season(:,:) = val_exp 
1417    var_name = 'cn_leaf_min_season' 
1418    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, & 
1419         &              .TRUE., cn_leaf_min_season, 'gather', nbp_glo, index_g) 
1420    IF ( ALL(cn_leaf_min_season(:,:) == val_exp) ) THEN
1421       DO m=1,nvm 
1422          cn_leaf_min_season(:,m) = cn_leaf_init_2D(:,m) 
1423       ENDDO
1424    ENDIF
1425   
1426    nstress_season(:,:) = val_exp 
1427    var_name = 'nstress_season' 
1428    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, & 
1429         &              .TRUE., nstress_season, 'gather', nbp_glo, index_g) 
1430    IF ( ALL(nstress_season(:,:) == val_exp) ) nstress_season(:,:)=1.0 
1431   
1432    CALL restget_p (rest_id_stomate, 'soil_n_min', nbp_glo, nvm, nnspec, itime, & 
1433         &              .TRUE., soil_n_min, 'gather', nbp_glo, index_g) 
1434!    IF ( ALL(soil_n_min == val_exp) ) soil_n_min(:,:,:)=100000000.
1435    IF ( ALL(soil_n_min == val_exp) ) soil_n_min(:,:,:)=0. 
1436
1437    p_O2(:,:) = val_exp 
1438    var_name = 'p_O2'
1439    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, & 
1440         &              .TRUE., p_O2(:,:), 'gather', nbp_glo, index_g) 
1441    IF ( ALL(p_O2(:,:) == val_exp) ) p_O2(:,:)=200
1442
1443    bact(:,:) = val_exp 
1444    var_name = 'bact'
1445    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, & 
1446         &              .TRUE., bact(:,:), 'gather', nbp_glo, index_g) 
1447    IF ( ALL(bact(:,:) == val_exp) ) bact(:,:)=10 
1448
1449    var_name = 'age_stand'
1450    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1451         &              .TRUE., temp_real, 'gather', nbp_glo, index_g)
1452    IF ( ALL(temp_real(:,:) == val_exp) ) THEN
1453       age_stand(:,:) = 0
1454    ELSE
1455       age_stand = NINT(temp_real)
1456    ENDIF
1457    !-
1458    temp_real(:,:) = val_exp
1459    var_name = 'rotation_n'
1460    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1461         &              .TRUE., temp_real, 'gather', nbp_glo, index_g)
1462    IF ( ALL(temp_real(:,:) == val_exp) ) THEN
1463       rotation_n(:,:) = 1
1464    ELSE
1465       rotation_n(:,:) = NINT(temp_real(:,:))
1466    ENDIF
1467    !-
1468    temp_real(:,:) = val_exp
1469    var_name = 'last_cut'
1470    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1471         &              .TRUE., temp_real, 'gather', nbp_glo, index_g)
1472    IF ( ALL(temp_real(:,:) == val_exp) ) THEN
1473       last_cut(:,:) = 0
1474    ELSE
1475       last_cut(:,:) = NINT(temp_real(:,:))
1476    ENDIF
1477    !-
1478    mai(:,:) = val_exp
1479    var_name = 'mai'
1480    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1481         &              .TRUE., mai, 'gather', nbp_glo, index_g)
1482    IF ( ALL(mai(:,:) == val_exp) ) mai(:,:) = zero
1483    !-
1484    pai(:,:) = val_exp
1485    var_name = 'pai'
1486    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1487         &              .TRUE., pai, 'gather', nbp_glo, index_g)
1488    IF ( ALL(pai(:,:) == val_exp) ) pai(:,:) = zero
1489    !-
1490    previous_wood_volume(:,:) = val_exp
1491    var_name = 'previous_wood_volume'
1492    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1493         &              .TRUE., previous_wood_volume, 'gather', nbp_glo, index_g)
1494    IF ( ALL(previous_wood_volume(:,:) == val_exp) ) previous_wood_volume(:,:) = zero
1495    !-
1496    temp_real(:,:) = val_exp
1497    var_name = 'mai_count'
1498    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1499         &              .TRUE., temp_real, 'gather', nbp_glo, index_g)
1500    IF ( ALL(temp_real(:,:) == val_exp) ) THEN
1501       mai_count(:,:) = 0
1502    ELSE
1503       mai_count = NINT(temp_real)
1504    ENDIF
1505    !-
1506    coppice_dens(:,:) = val_exp
1507    var_name = 'coppice_dens'
1508    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1509         &              .TRUE., coppice_dens, 'gather', nbp_glo, index_g)
1510    IF ( ALL(coppice_dens(:,:) == val_exp) ) coppice_dens(:,:) = zero
1511    !-
1512    IF (.NOT.ok_change_species) THEN
1513       ! In the abscence of a ok_change_species the model has to be
1514       ! driven by a prescribed value for forest_managed. This
1515       ! prescribed value can come from either a FMmap which is
1516       ! read in or a value for ::FOREST_MANAGED_FORCED. In these
1517       ! cases the values in the restart file are ignored. 
1518    ELSE
1519       ! We have a ok_change_species which implies that we only want
1520       ! to read the FMmap once at the start of the simulation
1521       ! after which forest_managed becomes a prognostic variable
1522       ! (as it may change after a clear cut) and therefore the
1523       ! values from the maps are ignored and the value from the
1524       ! restart is used except at the first time step.
1525       temp_real(:,:) = val_exp
1526       var_name = 'fm_current'
1527       CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
1528            &              .TRUE., temp_real, 'gather', nbp_glo, index_g)
1529       IF ( ALL(temp_real(:,:) == val_exp) ) THEN
1530          ! This is the first time step. The restart is still empty
1531          ! so use the values from the FMmap as read in stomate.f90
1532          ! Nothing should be done
1533       ELSE
1534          ! As soon as there is something in the restart file these
1535          ! values are used to overwrite the values that were read
1536          ! from the FMmap.
1537          forest_managed = NINT(temp_real)
1538       ENDIF
1539       
1540    END IF
1541   
1542    ! The routines don't like to store integer variables.  So instead
1543    ! we create a real array.  If the value of the real array is one,
1544    ! we assign a value of TRUE to the logical array.  Anything
1545    ! else is .FALSE.
1546    r_replant(:,:) = val_exp
1547    var_name = 'sc_map'
1548    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, &
1549         &        .TRUE., r_replant(:,:), 'gather', nbp_glo, index_g)
1550    DO ipts=1,npts
1551       DO ivm=1,nvm
1552          IF( r_replant(ipts,ivm) .LT. nvm*2)THEN
1553             species_change_map(ipts,ivm)=NINT(r_replant(ipts,ivm))
1554          ELSE
1555             species_change_map(ipts,ivm)=0
1556          ENDIF
1557       ENDDO
1558    ENDDO
1559
1560    r_replant(:,:) = val_exp
1561    var_name = 'fmc_map'
1562    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, &
1563         &        .TRUE., r_replant(:,:), 'gather', nbp_glo, index_g)
1564    DO ipts=1,npts
1565       DO ivm=1,nvm
1566          IF( r_replant(ipts,ivm) .LT. nvm*2)THEN
1567             fm_change_map(ipts,ivm)=NINT(r_replant(ipts,ivm))
1568          ELSE
1569             fm_change_map(ipts,ivm)=0
1570          ENDIF
1571       ENDDO
1572    ENDDO
1573
1574    IF(ok_windthrow) THEN
1575
1576       gap_area_save(:,:,:) = val_exp
1577       var_name = 'gap_area_save'
1578       CALL restget_p &
1579            &    (rest_id_stomate, var_name, nbp_glo, nvm, wind_years, itime, &
1580            &     .TRUE., gap_area_save(:,:,:), 'gather', nbp_glo,index_g)
1581       IF (ALL(gap_area_save(:,:,:) == val_exp)) gap_area_save(:,:,:)= zero
1582
1583       total_ba_init(:,:) = val_exp
1584       var_name = 'total_ba_init'
1585       CALL restget_p &
1586            &    (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
1587            &     .TRUE., total_ba_init(:,:), 'gather', nbp_glo,index_g)
1588       IF (ALL(total_ba_init(:,:) == val_exp)) total_ba_init(:,:)= zero
1589    ENDIF
1590
1591    IF(ok_pest) THEN
1592
1593      ! Read legacy variables for pest_damage module
1594      wood_leftover_legacy(:,:,:) = val_exp
1595      DO l=1,legacy_years
1596        WRITE(pyear_str,'(I2.2)') l
1597        var_name = 'wood_leftover_'//pyear_str
1598        CALL restget_p &
1599            &    (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
1600            &     .TRUE., wood_leftover_legacy(:,:,l), 'gather', nbp_glo,index_g)
1601        IF (ALL(wood_leftover_legacy(:,:,l) == val_exp)) wood_leftover_legacy(:,:,l)= zero
1602      ENDDO
1603
1604      season_drought_legacy(:,:,:) = val_exp
1605      DO l=1,legacy_years
1606        WRITE(pyear_str,'(I2.2)') l
1607        var_name = 'season_drought_'//pyear_str
1608        CALL restget_p &
1609            &    (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
1610            &     .TRUE., season_drought_legacy(:,:,l), 'gather',nbp_glo,index_g)
1611        IF (ALL(season_drought_legacy(:,:,l) == val_exp)) season_drought_legacy(:,:,l)= un
1612      ENDDO
1613
1614      beetle_generation_index(:,:,:) = val_exp
1615      DO l=1,legacy_years
1616        WRITE(pyear_str,'(I2.2)') l
1617        var_name = 'beetle_generation_'//pyear_str
1618        CALL restget_p &
1619            &    (rest_id_stomate, var_name, nbp_glo, nvm,1, itime, &
1620            &     .TRUE., beetle_generation_index(:,:,l),'gather',nbp_glo,index_g)
1621        IF (ALL(beetle_generation_index(:,:,l) == val_exp)) beetle_generation_index(:,:,l)= un
1622      ENDDO
1623
1624      sumTeff(:,:) = val_exp
1625      CALL restget_p &
1626            &    (rest_id_stomate, 'sumTeff', nbp_glo, nvm,1, itime, &
1627            &     .TRUE.,sumTeff(:,:),'gather',nbp_glo,index_g)
1628      IF (ALL(sumTeff(:,:) == val_exp)) sumTeff(:,:)= zero
1629
1630      beetle_diapause(:,:) = val_exp
1631      CALL restget_p &
1632            &    (rest_id_stomate, 'beetle_diapause', nbp_glo, nvm,1, itime, &
1633            &     .TRUE., beetle_diapause(:,:),'gather',nbp_glo,index_g)
1634      IF (ALL(beetle_diapause(:,:) == val_exp)) beetle_diapause(:,:)= zero
1635
1636      beetle_pop_legacy(:,:,:) = val_exp
1637      DO l=1,legacy_years
1638        WRITE(pyear_str,'(I2.2)') l
1639        var_name = 'beetle_pop_'//pyear_str
1640        CALL restget_p &
1641           &    (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
1642           &     .TRUE., beetle_pop_legacy(:,:,l),'gather',nbp_glo,index_g)
1643        IF (ALL(beetle_pop_legacy(:,:,l) == val_exp)) beetle_pop_legacy(:,:,l)= zero
1644      ENDDO
1645
1646      beetle_damage_legacy(:,:,:) = val_exp
1647      DO l=1,beetle_legacy
1648        WRITE(pyear_str,'(I2.2)') l
1649        var_name = 'beetle_damage_legacy_'//pyear_str
1650        CALL restget_p &
1651            &    (rest_id_stomate, var_name, nbp_glo, nvm,1, itime, &
1652            &     .TRUE.,beetle_damage_legacy(:,:,l),'gather',nbp_glo,index_g)
1653        IF (ALL(beetle_damage_legacy(:,:,l) == val_exp)) beetle_damage_legacy(:,:,l)=zero
1654      ENDDO
1655
1656      beetle_flyaway(:,:) = val_exp
1657      CALL restget_p &
1658            &    (rest_id_stomate, 'beetle_flyaway', nbp_glo, nvm,1, itime, &
1659            &     .TRUE.,beetle_flyaway(:,:),'gather',nbp_glo,index_g)
1660      IF (ALL(beetle_flyaway(:,:) == val_exp)) beetle_flyaway(:,:)= un
1661
1662      risk_index_legacy(:,:,:) = val_exp
1663      DO l=1,legacy_years
1664        WRITE(pyear_str,'(I2.2)') l
1665        var_name = 'risk_index_legacy_'//pyear_str
1666        CALL restget_p &
1667            &    (rest_id_stomate, var_name, nbp_glo, nvm,1, itime, &
1668            &     .TRUE.,risk_index_legacy(:,:,l),'gather',nbp_glo,index_g)
1669        IF (ALL(risk_index_legacy(:,:,l) == val_exp)) risk_index_legacy(:,:,l)= zero
1670      ENDDO
1671
1672      epidemic(:,:) = val_exp
1673      CALL restget_p &
1674            &    (rest_id_stomate, 'epidemic', nbp_glo, nvm,1, itime, &
1675            &     .TRUE.,epidemic(:,:),'gather',nbp_glo,index_g)
1676      IF (ALL(epidemic(:,:) == val_exp))epidemic(:,:)= zero
1677
1678
1679
1680    ENDIF ! ok_pest
1681
1682    ! The routines don't like to store logical variables.  So instead
1683    ! we create a real array.  If the value of the real array is one,
1684    ! we assign a value of TRUE to the logical array.  Anything
1685    ! else is .FALSE.
1686    r_replant(:,:) = val_exp
1687    var_name = 'lpft_replant'
1688    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, &
1689         &        .TRUE., r_replant(:,:), 'gather', nbp_glo, index_g)
1690    DO ipts=1,npts
1691       DO ivm=1,nvm
1692          IF(ABS(r_replant(ipts,ivm) - un) .LT. 0.001)THEN
1693             lpft_replant(ipts,ivm)=.TRUE.
1694          ELSE
1695             lpft_replant(ipts,ivm)=.FALSE.
1696          ENDIF
1697       ENDDO
1698    ENDDO
1699     
1700    ! Read assim_param from restart file. The initialization of assim_param will
1701    ! be done in stomate_var_init if the variable is not in the restart file.
1702    assim_param(:,:,:)  = val_exp
1703    CALL restget_p &
1704         &    (rest_id_stomate, 'assim_param', nbp_glo, nvm, npco2, itime, &
1705         &     .TRUE., assim_param, 'gather', nbp_glo, index_g)
1706
1707    light_tran_to_floor_season(:,:) = val_exp 
1708    var_name = 'light_tran_season' 
1709    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & 
1710         &     .TRUE., light_tran_to_floor_season, 'gather', nbp_glo, index_g) 
1711    IF (ALL(light_tran_to_floor_season(:,:) == val_exp)) light_tran_to_floor_season = zero
1712
1713    CALL restget_p (rest_id_stomate, 'daylight_count', nbp_glo, nvm, 1,itime, &
1714         .TRUE., daylight_count(:,:), 'gather', nbp_glo, index_g)
1715    IF ( ALL(daylight_count(:,:) == val_exp) ) daylight_count(:,:) = 0.
1716
1717    ! Drought mortality
1718    DO l = 1,nelements
1719       var_name = 'bio_ini_drought'//TRIM(element_str(l))
1720       CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm, ncirc, nparts, itime, &
1721         &    .TRUE., biomass_init_drought(:,:,:,:,l), 'gather', nbp_glo, index_g)
1722       IF ( ALL(biomass_init_drought(:,:,:,:,l) == val_exp) ) biomass_init_drought(:,:,:,:,l) = 0.
1723    ENDDO
1724 
1725    CALL restget_p (rest_id_stomate, 'kill_vessels', nbp_glo, nvm  , 1, itime, &
1726         &   .TRUE., temp_real, 'gather', nbp_glo, index_g)
1727    IF (ALL(temp_real(:,:) == val_exp)) temp_real(:,:) = zero
1728    WHERE (temp_real(:,:) >= .5)
1729       kill_vessels = .TRUE.
1730    ELSEWHERE
1731       kill_vessels = .FALSE.
1732    ENDWHERE
1733
1734    CALL restget_p (rest_id_stomate, 'vessel_loss_previous', nbp_glo, nvm  , 1, itime, &
1735         &  .TRUE., vessel_loss_previous, 'gather', nbp_glo, index_g)
1736    IF (ALL(vessel_loss_previous(:,:) == val_exp)) vessel_loss_previous(:,:) = zero
1737
1738    ! Phenological variables
1739    CALL restget_p (rest_id_stomate, 'grow_season_len', nbp_glo, nvm  , 1, itime, &
1740         &  .TRUE., grow_season_len, 'gather', nbp_glo, index_g)
1741    IF (ALL(grow_season_len(:,:) == val_exp)) grow_season_len(:,:) = zero
1742
1743    CALL restget_p (rest_id_stomate, 'doy_start_gs', nbp_glo, nvm  , 1, itime, &
1744         &  .TRUE., doy_start_gs, 'gather', nbp_glo, index_g)
1745    IF (ALL(doy_start_gs(:,:) == val_exp)) doy_start_gs(:,:) = zero
1746
1747    CALL restget_p (rest_id_stomate, 'doy_end_gs', nbp_glo, nvm  , 1, itime, &
1748         &  .TRUE., doy_end_gs, 'gather', nbp_glo, index_g)
1749    IF (ALL(doy_end_gs(:,:) == val_exp)) doy_end_gs(:,:) = zero
1750
1751    CALL restget_p (rest_id_stomate, 'mean_start_gs', nbp_glo, nvm  , 1, itime, &
1752         &  .TRUE., mean_start_gs, 'gather', nbp_glo, index_g)
1753    IF (ALL(mean_start_gs(:,:) == val_exp)) mean_start_gs(:,:) = zero
1754
1755    IF (printlev >= 4) WRITE(numout,*) 'Leaving readrestart'
1756    !-----------------------
1757  END SUBROUTINE readrestart
1758
1759
1760!! ================================================================================================================================
1761!! SUBROUTINE   : writerestart
1762!!
1763!>\BRIEF        Write all variables for stomate from restart file.
1764!!
1765!! DESCRIPTION  : Write all variables for stomate from restart file.
1766!!               
1767!! \n
1768!_ ================================================================================================================================
1769
1770  SUBROUTINE writerestart &
1771       & (npts, index, dt_days, date_loc, &
1772       &  adapted, regenerate, vegstress_day, gdd_init_date, litterhum_daily, &
1773       &  t2m_daily, t2m_min_daily, tsurf_daily, tsoil_daily, &
1774       &  precip_daily, gpp_daily, npp_daily, &
1775       &  turnover_daily, turnover_resid, vegstress_month, &
1776       &  vegstress_week, vegstress_season, &
1777       &  t2m_longterm, tau_longterm, t2m_month, t2m_week, &
1778       &  tsoil_month, fireindex, firelitter, &
1779       &  maxvegstress_lastyear, maxvegstress_thisyear, &
1780       &  minvegstress_lastyear, minvegstress_thisyear, &
1781       &  maxgppweek_lastyear, maxgppweek_thisyear, &
1782       &  gdd0_lastyear, gdd0_thisyear, precip_lastyear, precip_thisyear, &
1783       &  gdd_m5_dormance, gdd_from_growthinit, gdd_midwinter, ncd_dormance, ngd_minus5, &
1784       &  PFTpresent, npp_longterm, croot_longterm, n_reserve_longterm, lm_lastyearmax, &
1785       &  lm_thisyearmax, maxfpc_lastyear, maxfpc_thisyear, &
1786       &  turnover_longterm, gpp_week, resp_maint_part, resp_maint_week, &
1787       &  leaf_age, leaf_frac, leaf_age_crit, plant_status, when_growthinit, age, &
1788       &  resp_hetero, resp_maint, resp_growth, &
1789       &  co2_fire, atm_to_bm, &
1790       &  veget_lastlight, everywhere, need_adjacent, RIP_time, &
1791       &  time_hum_min, hum_min_dormance, &
1792       &  litter, dead_leaves, &
1793       &  som, lignin_struc, lignin_wood, turnover_time, &
1794       &  co2_flux, fco2_lu, fco2_wh, fco2_ha,  &
1795       &  prod_s, prod_m, prod_l, &
1796       &  flux_s, flux_m, flux_l, &
1797       &  fDeforestToProduct, fLulccResidue, fHarvestToProduct, &
1798       &  bm_to_litter, bm_to_litter_resid, tree_bm_to_litter, &
1799       &  tree_bm_to_litter_resid, carb_mass_total, &
1800       &  Tseason, Tseason_length, Tseason_tmp, & 
1801       &  Tmin_spring_time, &
1802       &  global_years, ok_equilibrium, nbp_accu_flux, &
1803       &  nbp_pool_start, &
1804       &  MatrixV, VectorU, previous_stock, current_stock, &
1805       &  assim_param, CN_som_litter_longterm, &
1806       &  tau_CN_longterm, KF, k_latosa_adapt, &
1807       &  rue_longterm, cn_leaf_min_season, nstress_season, soil_n_min, p_O2, bact, &
1808       &  forest_managed, &
1809       &  species_change_map, fm_change_map, lpft_replant, lai_per_level, &
1810       &  laieff_fit, wstress_season, wstress_month,&
1811       &  age_stand, rotation_n, last_cut, mai, pai, &
1812       &  previous_wood_volume, mai_count, coppice_dens, &
1813       &  light_tran_to_floor_season,daylight_count, gap_area_save, &
1814       &  deepSOM_a, deepSOM_s, deepSOM_p, O2_soil, CH4_soil, O2_snow, CH4_snow, &
1815       &  heat_Zimov, altmax, depth_organic_soil, fixed_cryoturbation_depth, &
1816       &  sugar_load, harvest_cut, & 
1817       &  harvest_pool_acc, harvest_area_acc, burried_litter, burried_fresh_ltr, &
1818       &  burried_fresh_som, burried_bact, burried_fungivores, &
1819       &  burried_min_nitro,burried_som, &
1820       &  burried_deepSOM_a, burried_deepSOM_s, burried_deepSOM_p,&
1821       &  wood_leftover_legacy,beetle_pop_legacy,season_drought_legacy,&
1822       &  risk_index_legacy, beetle_diapause, sumTeff,&
1823       &  beetle_generation_index, beetle_damage_legacy, beetle_flyaway, epidemic, &
1824       &  is_storm, count_storm, biomass_init_drought, kill_vessels, &
1825       &  vessel_loss_previous, grow_season_len, doy_start_gs, doy_end_gs, &
1826       &  mean_start_gs, total_ba_init)
1827
1828 
1829    ! 0 declarations
1830    !-
1831    ! 0.1 input
1832    !-
1833    INTEGER(i_std),INTENT(in)                             :: npts                     !! Domain size
1834    INTEGER(i_std),DIMENSION(:),INTENT(in)                :: index                    !! Indices of the points on the map
1835    REAL(r_std),INTENT(in)                                :: dt_days                  !! time step of STOMATE in days
1836    INTEGER(i_std),INTENT(in)                             :: date_loc                 !! date_loc (d)
1837    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: adapted                  !! Winter too cold? between 0 and 1
1838    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: regenerate               !! Winter sufficiently cold? between 0 and 1
1839    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: vegstress_day         !! daily moisture availability
1840    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: gdd_init_date            !! date for beginning of gdd count
1841    REAL(r_std),DIMENSION(:),INTENT(in)                   :: litterhum_daily          !! daily litter humidity
1842    REAL(r_std),DIMENSION(:),INTENT(in)                   :: t2m_daily                !! daily 2 meter temperatures (K)
1843    REAL(r_std),DIMENSION(:),INTENT(in)                   :: t2m_min_daily            !! daily minimum 2 meter temperatures (K)
1844    REAL(r_std),DIMENSION(:),INTENT(in)                   :: tsurf_daily              !! daily surface temperatures (K)
1845    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: tsoil_daily              !! daily soil temperatures (K)
1846    REAL(r_std),DIMENSION(:),INTENT(in)                   :: precip_daily             !! daily precipitations (mm/day) (for phenology)
1847    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: gpp_daily                !! daily gross primary productivity (gC/m**2/day)
1848    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: npp_daily                !! daily net primary productivity (gC/m**2/day)
1849    REAL(r_std),DIMENSION(:,:,:,:),INTENT(in)             :: turnover_daily           !! daily turnover rates (gC/m**2/day)
1850    REAL(r_std),DIMENSION(:,:,:,:),INTENT(in)             :: turnover_resid           !! The turnover left from turnover_daily at any given time step 
1851                                                                                      !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
1852    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: vegstress_month       !! "monthly" moisture availability
1853    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: vegstress_week        !! "weekly" moisture availability
1854    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: vegstress_season      !! mean growing season moisture availability (used for allocation response)
1855    REAL(r_std),DIMENSION(:),INTENT(in)                   :: t2m_longterm             !! "long term" 2 meter temperatures (K)
1856    REAL(r_std), INTENT(in)                               :: tau_longterm             !! "tau_longterm"
1857    REAL(r_std),DIMENSION(:),INTENT(in)                   :: t2m_month                !! "monthly" 2 meter temperatures (K)
1858    REAL(r_std),DIMENSION(:),INTENT(in)                   :: Tseason                  !! "seasonal" 2 meter temperatures (K)
1859    REAL(r_std),DIMENSION(:),INTENT(in)                   :: Tseason_length           !! temporary variable to calculate Tseason
1860    REAL(r_std),DIMENSION(:),INTENT(in)                   :: Tseason_tmp              !! temporary variable to calculate Tseason
1861    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: Tmin_spring_time         !!
1862    REAL(r_std),DIMENSION(:),INTENT(in)                   :: t2m_week                 !! "weekly" 2 meter temperatures (K)
1863    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: tsoil_month              !! "monthly" soil temperatures (K)
1864    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: fireindex                !! Probability of fire
1865    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: firelitter               !! Longer term total litter above the ground, gC/m**2 of ground
1866    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: maxvegstress_lastyear !! last year's maximum moisture availability
1867    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: maxvegstress_thisyear !! this year's maximum moisture availability
1868    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: minvegstress_lastyear !! last year's minimum moisture availability
1869    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: minvegstress_thisyear !! this year's minimum moisture availability
1870    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: maxgppweek_lastyear      !! last year's maximum weekly GPP
1871    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: maxgppweek_thisyear      !! this year's maximum weekly GPP
1872    REAL(r_std),DIMENSION(:),INTENT(in)                   :: gdd0_lastyear            !! last year's annual GDD0
1873    REAL(r_std),DIMENSION(:),INTENT(in)                   :: gdd0_thisyear            !! this year's annual GDD0
1874    REAL(r_std),DIMENSION(:),INTENT(in)                   :: precip_lastyear          !! last year's annual precipitation (mm/year)
1875    REAL(r_std),DIMENSION(:),INTENT(in)                   :: precip_thisyear          !! this year's annual precipitation (mm/year)
1876    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: gdd_m5_dormance          !! growing degree days, threshold -5 deg C (for phenology)
1877    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: gdd_from_growthinit      !! growing degree days, from begin of season
1878    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: gdd_midwinter            !! growing degree days since midwinter (for phenology)
1879    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: ncd_dormance             !! number of chilling days since leaves were lost (for phenology)
1880    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: ngd_minus5               !! number of growing days, threshold -5 deg C (for phenology)
1881    LOGICAL,DIMENSION(:,:),INTENT(in)                     :: PFTpresent               !! PFT exists (equivalent to fpc_max > 0 for natural PFTs)
1882    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: npp_longterm             !! "long term" net primary productivity (gC/m**2/year)
1883    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: croot_longterm           !! "long term" root carbon mass (gC/m**2/year)
1884    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: n_reserve_longterm       !! "long term" actual to potential N reserve pool (unitless)
1885    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: lm_lastyearmax           !! last year's maximum leaf mass, for each PFT (gC/m**2)
1886    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: lm_thisyearmax           !! this year's maximum leaf mass, for each PFT (gC/m**2)
1887    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: maxfpc_lastyear          !! last year's maximum fpc for each natural PFT, on ground
1888    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: maxfpc_thisyear          !! this year's maximum fpc for each PFT, on *total* ground (see stomate_season)   
1889    REAL(r_std),DIMENSION(:,:,:,:),INTENT(in)             :: turnover_longterm        !! "long term" turnover rate (gC/m**2/year)
1890    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: gpp_week                 !! "weekly" GPP (gC/day/(m**2 covered)
1891    REAL(r_std),DIMENSION(:,:,:),INTENT(in)               :: resp_maint_part          !! maintenance resp (gC/m**2)
1892    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: resp_maint_week          !! "weekly" maintenance respiration (gC/day/(m**2 covered)
1893    REAL(r_std),DIMENSION(:,:,:),INTENT(in)               :: leaf_age                 !! leaf age (days)
1894    REAL(r_std),DIMENSION(:,:,:),INTENT(in)               :: leaf_frac                !! fraction of leaves in leaf age class
1895    REAL(r_std), DIMENSION(:,:),INTENT(in)                :: leaf_age_crit            !! critical leaf age (days)
1896    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: plant_status             !! Growth and phenological status of the plant
1897                                                                                       !! The different stati are defined in constantes
1898    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: when_growthinit          !! how many days ago was the beginning of the growing season
1899    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: age                      !! mean age (years)
1900    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: resp_hetero              !! heterotrophic respiration (gC/day/m**2)
1901    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: resp_maint               !! maintenance respiration (gC/day/m**2)
1902    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: resp_growth              !! growth respiration (gC/day/m**2)
1903    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: co2_fire                 !! carbon emitted into the atmosphere by fire (living and dead biomass)
1904                                                                                       !! (in gC/m**2/time step)
1905    REAL(r_std),DIMENSION(:,:,:),INTENT(in)               :: atm_to_bm                !! biomass taken from the atmosphere (gC or gN /(m**2 of total ground)/day)
1906    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: veget_lastlight          !! vegetation fractions (on ground) after last light competition
1907    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: everywhere               !! is the PFT everywhere in the grid box or very localized (after its introduction)
1908    LOGICAL,DIMENSION(:,:),INTENT(in)                     :: need_adjacent            !! in order for this PFT to be introduced, does it have to be present in an adjacent grid box?
1909    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: RIP_time                 !! How much time ago was the PFT eliminated for the last time (y)
1910    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: time_hum_min             !! time elapsed since strongest moisture availability (d)
1911    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: hum_min_dormance         !! minimum moisture during dormance
1912    REAL(r_std),DIMENSION(:,:,:,:,:),INTENT(in)           :: litter                   !! fraction of litter above the ground belonging to different PFTs
1913                                                                                       !! separated for natural and agricultural PFTs.
1914    REAL(r_std),DIMENSION(:,:,:),INTENT(in)               :: dead_leaves              !! dead leaves on ground, per PFT, metabolic and structural in gC/(m**2 of ground)
1915    REAL(r_std),DIMENSION(:,:,:,:),INTENT(in)             :: som                      !! Soil Organic Matter pool: active, slow, or passive, (gC (or N)/m**2)
1916    REAL(r_std),DIMENSION(:,:,:),INTENT(in)               :: lignin_struc             !! ratio Lignine/Carbon in structural litter, above and below ground,(gC/m**2)
1917    REAL(r_std),DIMENSION(:,:,:),INTENT(in)               :: lignin_wood              !! ratio Lignine/Carbon in woody litter, above and below ground,(gC/m**2)
1918    REAL(r_std),DIMENSION(:,:,:),INTENT(in)               :: turnover_time            !!
1919    INTEGER(i_std), INTENT(in)                            :: global_years             !! for spinup matrix 
1920    LOGICAL, DIMENSION(:), INTENT(in)                     :: ok_equilibrium           !! for spinup matrix 
1921    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: nbp_accu_flux            !! accumulated Net Biospheric Production over the whole simulationm (gC/N m-2)
1922    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: nbp_pool_start           !! C an dN stocks at previous time step (gC/N m-2)
1923    REAL(r_std), DIMENSION(:,:,:,:), INTENT(in)           :: MatrixV                  !!
1924    REAL(r_std), DIMENSION(:,:,:), INTENT(in)             :: VectorU                  !!
1925    REAL(r_std), DIMENSION(:,:,:), INTENT(in)             :: previous_stock           !!
1926    REAL(r_std), DIMENSION(:,:,:), INTENT(in)             :: current_stock            !!
1927    REAL(r_std), DIMENSION(:,:,:), INTENT(in)             :: CN_som_litter_longterm   !! Longterm CN ratio of litter and som pools (gC/gN)
1928    REAL(r_std), INTENT(in)                               :: tau_CN_longterm          !! Counter used for calculating the longterm CN ratio of SOM and litter pools (seconds)
1929    REAL(r_std), DIMENSION(:,:,:), INTENT(in)             :: assim_param              !!
1930    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: KF                       !! Scaling factor to convert sapwood mass into leaf mass (m)
1931    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: k_latosa_adapt           !! Leaf to sapwood area adapted for water stress. Adaptation takes place at the end of the year (m)
1932    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: mai                      !! The mean annual increment @tex $(m**3 / m**2 / year)$ @endtex
1933    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: pai                      !! The period annual increment @tex $(m**3 / m**2 / year)$ @endtex
1934    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: previous_wood_volume     !! The volume of the tree trunks in a stand for the previous year. @tex $(m**3 / m**2 )$ @endtex
1935    INTEGER(i_std), DIMENSION(:,:),INTENT(in)             :: mai_count                !! The number of times we've calculated the volume increment for a stand
1936    REAL(r_std), DIMENSION(:,:),INTENT(in)                :: coppice_dens             !! The density of a coppice at the first cutting. @tex $( 1 / m**2 )$ @endtex
1937    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: rue_longterm             !! longterm radiation use efficiency
1938    INTEGER(i_std), DIMENSION(:,:), INTENT(in)            :: age_stand                !! Age of stand (years)
1939    INTEGER(i_std), DIMENSION(:,:), INTENT(in)            :: rotation_n               !! Rotation number (number of rotation since pft is managed)
1940    INTEGER(i_std), DIMENSION(:,:), INTENT(in)            :: last_cut                 !! Years since last thinning (years)
1941    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: cn_leaf_min_season       !! Seasonal min CN ratio of leaves
1942    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: nstress_season           !! N-related seasonal stress (used for allocation)
1943    REAL(r_std), DIMENSION(:,:,:), INTENT(in)             :: soil_n_min               !! mineral nitrogen in the soil (gN/m**2) (first index=npts, second index=nvm, third index=nnspec)
1944    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: p_O2                     !! partial pressure of oxigen in the soil (hPa)(first index=npts, second index=nvm)
1945    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: bact                     !! denitrifier biomass (gC/m**2) (first index=npts, second index=nvm)
1946    INTEGER(i_std), DIMENSION(:,:), INTENT(in)            :: forest_managed           !! forest management flag
1947    REAL(r_std), DIMENSION(:,0:,:,:,:), INTENT(in)        :: prod_s                   !!
1948    REAL(r_std), DIMENSION(:,0:,:,:,:), INTENT(in)        :: prod_m                   !!
1949    REAL(r_std), DIMENSION(:,0:,:,:,:), INTENT(in)        :: prod_l                   !!
1950    REAL(r_std), DIMENSION(:,:,:,:,:), INTENT(in)         :: flux_s                   !!
1951    REAL(r_std), DIMENSION(:,:,:,:,:), INTENT(in)         :: flux_m                   !!
1952    REAL(r_std), DIMENSION(:,:,:,:,:), INTENT(in)         :: flux_l                   !!
1953    INTEGER(i_std), DIMENSION(:,:), INTENT(in)            :: species_change_map       !! A map which gives the PFT number that each PFT will be replanted as in case of a clearcut.
1954                                                                                       !! (1-nvm,unitless)
1955    INTEGER(i_std), DIMENSION(:,:), INTENT(in)            :: fm_change_map            !! A map which gives the desired FM strategy when the PFT will be replanted after a clearcut.
1956                                                                                       !! (1-nvm,unitless)
1957    LOGICAL, DIMENSION(:,:), INTENT(in)                   :: lpft_replant             !! Indicates if this PFT has either died this year or been clearcut/coppiced.  If it has, it is not
1958                                                                                       !! replanted until the end of the year.
1959    REAL(r_std), DIMENSION(:,:,:),INTENT(in)              :: lai_per_level            !! The amount of LAI in each physical canopy level. @tex $( m**2 / m**2 )$ @endtex
1960    REAL(r_std), DIMENSION(:,:,:,:),INTENT(in)            :: deepSOM_a                !!
1961    REAL(r_std), DIMENSION(:,:,:,:),INTENT(in)            :: deepSOM_s                !!
1962    REAL(r_std), DIMENSION(:,:,:,:),INTENT(in)            :: deepSOM_p                !!
1963    REAL(r_std), DIMENSION(:,:,:),INTENT(in)              :: O2_soil                  !!
1964    REAL(r_std), DIMENSION(:,:,:),INTENT(in)              :: CH4_soil                 !!
1965    REAL(r_std), DIMENSION(:,:,:),INTENT(in)              :: O2_snow                  !!
1966    REAL(r_std), DIMENSION(:,:,:),INTENT(in)              :: CH4_snow                 !!
1967    REAL(r_std), DIMENSION(:,:,:), INTENT(in)             :: heat_Zimov               !! heating associated with decomposition [W/m**3 soil]
1968    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: altmax                   !! Active layer thickness (m)
1969    REAL(r_std), DIMENSION(:),INTENT(in)                  :: depth_organic_soil       !! Depth at which there is still organic matter (m)
1970    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: fixed_cryoturbation_depth!! Depth to hold cryoturbation to for fixed runs 
1971    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: sugar_load               !! Relative sugar loading of the labile pool (unitless)
1972    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: harvest_cut              !! Type of cutting that was used for the harvest (unitless)
1973    TYPE(laieff_type),DIMENSION (:,:,:),INTENT(in)        :: laieff_fit               !! Fitted parameters for the effective LAI
1974    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: wstress_season           !! Water stress factor, based on hum_rel_daily (unitless, 0-1)
1975    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: wstress_month            !! Water stress factor, based on hum_rel_daily (unitless, 0-1)
1976    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: fDeforestToProduct       !!
1977    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: fLulccResidue            !!
1978    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: fHarvestToProduct        !!
1979    REAL(r_std),DIMENSION(:,:,:,:),INTENT(in)             :: bm_to_litter             !! Background (not senescence-driven) mortality of biomass
1980                                                                                      !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
1981    REAL(r_std),DIMENSION(:,:,:,:),INTENT(in)             :: bm_to_litter_resid       !! Left over bm_to_litter at any specific time step
1982                                                                                      !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex
1983    REAL(r_std),DIMENSION(:,:,:,:),INTENT(in)             :: tree_bm_to_litter        !! Conversion of biomass to litter
1984                                                                                      !! @tex $(gC m^{-2} dtslow^{-1})$ @endtex
1985    REAL(r_std),DIMENSION(:,:,:,:),INTENT(in)             :: tree_bm_to_litter_resid  !! Left over bm_to_litter_resid. Written here, used in stomate.f90
1986                                                                                      !! @tex $(gC m^{-2} dtslow^{-1})$ @endtex
1987    REAL(r_std),DIMENSION(:),INTENT(in)                   :: carb_mass_total          !!
1988    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: light_tran_to_floor_season !! Mean seasonal fraction of light transmitted to the forest floor (unitless, 0-1)
1989    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: daylight_count           !! Time steps dt_radia during daylight and when there is growth (gpp>0)
1990    REAL(r_std), DIMENSION(:,:,:), INTENT(in)             :: gap_area_save            !! Total gap area created by more than 30% basal area loss in the last 5 years (m^{2})
1991    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: total_ba_init            !! Total basal area saved at the first day of the year (m^{2}/m^{2})
1992    REAL(r_std), DIMENSION(:,:,:), INTENT(in)             :: season_drought_legacy    !! mean growing season moisture availability
1993    REAL(r_std), DIMENSION(:,:,:), INTENT(in)             :: wood_leftover_legacy     !!
1994    REAL(r_std), DIMENSION(:,:,:), INTENT(in)             :: risk_index_legacy        !!
1995    INTEGER(i_std), DIMENSION(:,:), INTENT(in)            :: beetle_diapause          !!
1996    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: sumTeff                  !! sum of temperazture for
1997                                                                                      !! beetle phenology
1998    REAL(r_std), DIMENSION(:,:,:),INTENT(in)              :: beetle_pop_legacy        !! biomass of tree from the same species that was infected during the previous timestep
1999    REAL(r_std), DIMENSION(:,:),INTENT(in)                :: beetle_flyaway
2000    REAL(r_std), DIMENSION(:,:,:), INTENT(in)             :: beetle_damage_legacy
2001    REAL(r_std), DIMENSION(:,:,:), INTENT(in)             :: beetle_generation_index  !! number of generation that BB can achieved in one year
2002    REAL(r_std), DIMENSION(:,:),INTENT(in)                :: epidemic
2003    LOGICAL,DIMENSION(:),INTENT(in)                       :: is_storm
2004    INTEGER(i_std),DIMENSION(:),INTENT(in)                :: count_storm
2005    REAL(r_std),DIMENSION(:,:,:,:),INTENT(in)             :: harvest_pool_acc         !! Records the quantity of wood harvested and thinned due to forest management and LCC.
2006    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: harvest_area_acc         !! Harvested area (m^{2})
2007    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: co2_flux                 !!
2008    REAL(r_std),DIMENSION(:),INTENT(in)                   :: fco2_lu                  !!
2009    REAL(r_std),DIMENSION(:),INTENT(in)                   :: fco2_wh                  !!
2010    REAL(r_std),DIMENSION(:),INTENT(in)                   :: fco2_ha                  !!
2011    REAL(r_std),DIMENSION(:,:,:,:),INTENT(in)             :: burried_litter           !! Litter burried under non-biological land uses (gC orNm-2)
2012    REAL(r_std),DIMENSION(:,:,:),INTENT(in)               :: burried_fresh_ltr        !! Fresh litter burried under non-biological land uses (gC orN m-2)
2013    REAL(r_std),DIMENSION(:,:,:),INTENT(in)               :: burried_fresh_som        !! Fresh som burried under non-biological land uses (gC or Nm-2)
2014    REAL(r_std),DIMENSION(:),INTENT(in)                   :: burried_bact             !! Bacteria burried under non-biological land uses (gC m-2)
2015    REAL(r_std),DIMENSION(:),INTENT(in)                   :: burried_fungivores       !! Fungivores burried under non-biological land uses (gN m-2)
2016    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: burried_min_nitro        !! Mineral nitrogen burried under non-biological land uses(gC or N m-2)
2017    REAL(r_std),DIMENSION(:,:,:),INTENT(in)               :: burried_som              !! Som burried under non-biological land uses (gC or N m-2)
2018    REAL(r_std),DIMENSION(:,:,:),INTENT(in)               :: burried_deepSOM_a        !! Som burried under non-biological land uses (gC or N m-3)
2019    REAL(r_std),DIMENSION(:,:,:),INTENT(in)               :: burried_deepSOM_s        !! Som burried under non-biological land uses (gC or N m-3)
2020    REAL(r_std),DIMENSION(:,:,:),INTENT(in)               :: burried_deepSOM_p        !! Som burried under non-biological land uses (gC or N m-3)
2021    REAL(r_std),DIMENSION(:,:,:,:,:),INTENT(in)           :: biomass_init_drought     !! Biomass of heartwood or sapwood before onset of drought.
2022                                                                                       !! Used to compute turnover on same reference biomass in
2023                                                                                       !! stomate_turnover.f90. Should remain the same along one
2024                                                                                       !! entire drought episode and be updated inbetween
2025                                                                                       !! droughts (gCor N tree-1).
2026    LOGICAL,DIMENSION(:,:),INTENT(in)                     :: kill_vessels             !! Flag to kill vessels at the end of the day when there is embolism.
2027    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: vessel_loss_previous     !! vessel loss at the previous time step
2028    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: grow_season_len          !! growing season length in days for deciduous PFTs.
2029    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: doy_start_gs             !! growing season starting day of year (DOY) for deciduous PFTs.
2030    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: doy_end_gs               !! growing season end day of year (DOY) for deciduous PFTs.
2031    REAL(r_std),DIMENSION(:,:),INTENT(in)                 :: mean_start_gs            !! mean growing season starting day for deciduous PFTs.
2032
2033
2034!! 0.4 Local variables
2035   
2036    REAL(r_std)                                                         :: date_real               !! date, real
2037    REAL(r_std),DIMENSION(npts,nvm)                                     :: PFTpresent_real         !! PFT exists (equivalent to fpc_max > 0 for natural PFTs), real
2038    REAL(r_std),DIMENSION(npts)                                         :: is_storm_real
2039   REAL(r_std),DIMENSION(npts)                                          :: count_storm_real
2040
2041    REAL(r_std),DIMENSION(npts,nvm)                                     :: need_adjacent_real      !! in order for this PFT to be introduced,
2042                                                                                                   !! does it have to be present in an adjacent grid box? - real
2043    CHARACTER(LEN=80)                                                   :: var_name                !! To store variables names for I/O
2044    CHARACTER(LEN=10)                                                   :: circ_str                !! string suffix indicating an index
2045    CHARACTER(LEN=10)                                                   :: part_str                !! string suffix indicating an index
2046    REAL(r_std), DIMENSION(npts)                                        :: ok_equilibrium_real     
2047    REAL(r_std),DIMENSION(1)                                            :: xtmp                    !! temporary storage
2048    INTEGER(i_std)                                                      :: j,k,l,m                 !! index
2049    CHARACTER(LEN=2),DIMENSION(nelements)                               :: element_str             !! string suffix indicating element
2050    CHARACTER(LEN=6),DIMENSION(nbpools)                                 :: pools_str
2051    INTEGER                                                             :: n,ilev,ipts,ivm         !! Indices
2052    REAL(r_std), DIMENSION(npts,nvm)                                    :: temp_real               !! temporary real to allow restget
2053                                                                                                   !! to work on multi-dimensional integers
2054    REAL(r_std), DIMENSION(npts,nvm)                                    :: r_replant               !! Getting logical values from the restart
2055                                                                                                   !! is not possible, so this is a temporary
2056                                                                                                   !! array where 1.0 is TRUE.
2057    REAL(r_std),DIMENSION(npts,nvm,nlevels_tot,nparams_laieff)          :: temp_array              !! To store structure values for I/O
2058    CHARACTER(LEN=10)                                                   :: part_str2               !! string suffix indicating an index
2059   
2060    CHARACTER(LEN=2), DIMENSION(wind_years+1)                           :: wyear_str               !! string suffix indicating wind year index
2061    CHARACTER(LEN=2)                                                    :: pyear_str               !! string suffix indicating year index for pest module
2062    CHARACTER(LEN=10), DIMENSION(nlctypes)                              :: lctype_str              !! string suffix for the land cover type
2063
2064!_ ================================================================================================================================
2065
2066    IF (printlev >= 3) WRITE(numout,*) 'Entering writerestart'
2067    !-
2068    ! 1 string definitions
2069    !-
2070    DO l=1,nlctypes
2071       IF (l == iforest) THEN
2072          lctype_str(l) = '_forest'
2073       ELSEIF (l == igrass) THEN
2074          lctype_str(l) = '_grass'
2075       ELSEIF (l == icrop) THEN
2076          lctype_str(l) = '_crop'
2077       ELSE
2078          CALL ipslerr_p(3,'stomate_io writerestart','Define lctype_str(l)','','')
2079       ENDIF   
2080    END DO
2081    !-
2082    DO l=1,nelements
2083       IF     (l == icarbon) THEN
2084          element_str(l) = '_c'
2085       ELSEIF (l == initrogen) THEN
2086          element_str(l) = '_n'
2087       ELSE
2088          CALL ipslerr_p(3,'stomate_io writerestart','Define element_str','','')
2089       ENDIF
2090    ENDDO
2091    !-
2092    pools_str(1:nbpools) =(/'str_ab ','str_be ','met_ab ','met_be ','wood_ab','wood_be', & 
2093         & 'actif  ','slow   ','passif ','surface'/) 
2094    !-
2095    IF (is_root_prc) THEN
2096       CALL ioconf_setatt_p ('UNITS','-')
2097       CALL ioconf_setatt_p ('LONG_NAME',' ')
2098    ENDIF
2099   
2100    !-
2101    ! 2.2 time step of STOMATE in days
2102    !-
2103    CALL restput_p (rest_id_stomate, 'dt_days', itime, dt_days)
2104    !-
2105    ! 2.3 date
2106    !-
2107    CALL restput_p (rest_id_stomate, 'date', itime, date_loc)
2108    !-
2109    ! 3 daily meteorological variables
2110    !-
2111    var_name = 'vegstress_day'
2112    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2113         &                vegstress_day, 'scatter', nbp_glo, index_g)
2114    !-
2115    var_name = 'gdd_init_date'
2116    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    2, 1, itime, &
2117         &              gdd_init_date, 'scatter', nbp_glo, index_g)
2118    !-
2119    var_name = 'litterhum_daily'
2120    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    1, 1, itime, &
2121         &                litterhum_daily, 'scatter', nbp_glo, index_g)
2122    !-
2123    var_name = 't2m_daily'
2124    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    1, 1, itime, &
2125         &                t2m_daily, 'scatter', nbp_glo, index_g)
2126    !-
2127    var_name = 't2m_min_daily'
2128    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    1, 1, itime, &
2129         &                t2m_min_daily, 'scatter', nbp_glo, index_g)
2130    !-
2131    var_name = 'tsurf_daily'
2132    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    1, 1, itime, &
2133         &                tsurf_daily, 'scatter', nbp_glo, index_g)
2134    !-
2135    var_name = 'tsoil_daily'
2136    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nslm, 1, itime, &
2137         &                tsoil_daily, 'scatter', nbp_glo, index_g)
2138    !-
2139    var_name = 'precip_daily'
2140    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    1, 1, itime, &
2141         &                precip_daily, 'scatter', nbp_glo, index_g)
2142    !-
2143    var_name = 'wstress_season'
2144    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2145         &                wstress_season, 'scatter', nbp_glo, index_g)
2146    !-
2147    var_name = 'wstress_month'
2148    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2149         &                wstress_month, 'scatter', nbp_glo, index_g)
2150    !-
2151    ! 4 productivities
2152    !-
2153    var_name = 'gpp_daily'
2154    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2155         &                gpp_daily, 'scatter', nbp_glo, index_g)
2156    !-
2157    var_name = 'npp_daily'
2158    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2159         &                npp_daily, 'scatter', nbp_glo, index_g)
2160    !-
2161    CALL restput_p (rest_id_stomate, 'turnover_daily', nbp_glo, nvm, nparts, nelements, itime, &
2162         &                   turnover_daily, 'scatter', nbp_glo, index_g)
2163    !-
2164    CALL restput_p (rest_id_stomate, 'turnover_resid', nbp_glo, nvm, nparts, nelements, itime, &
2165         &                   turnover_resid, 'scatter', nbp_glo, index_g)
2166
2167    !-
2168    ! 5 monthly meteorological variables
2169    !-
2170    var_name = 'vegstress_month'
2171    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2172         &                vegstress_month, 'scatter', nbp_glo, index_g)
2173    !-
2174    var_name = 'vegstress_week'
2175    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2176         &                vegstress_week, 'scatter', nbp_glo, index_g)
2177    !-
2178    var_name = 'vegstress_season'
2179    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2180         &                vegstress_season, 'scatter', nbp_glo, index_g)
2181    !-
2182    var_name = 't2m_longterm'
2183    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    1, 1, itime, &
2184         &                t2m_longterm, 'scatter', nbp_glo, index_g)
2185    !-
2186    var_name = 'tau_longterm'
2187    CALL restput_p (rest_id_stomate, var_name, itime, tau_longterm)
2188    !-   
2189    var_name = 't2m_month'
2190    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    1, 1, itime, &
2191                         t2m_month, 'scatter', nbp_glo, index_g)
2192    !-
2193    var_name = 'Tseason'
2194    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    1, 1, itime, &
2195         Tseason, 'scatter', nbp_glo, index_g)
2196    !-
2197    var_name = 'Tseason_length'
2198    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    1, 1, itime, &
2199         Tseason_length, 'scatter', nbp_glo, index_g)
2200    !-
2201    var_name = 'Tseason_tmp'
2202    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    1, 1, itime, &
2203         Tseason_tmp, 'scatter', nbp_glo, index_g)
2204    !-
2205    var_name = 'Tmin_spring_time'
2206    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2207         Tmin_spring_time, 'scatter', nbp_glo, index_g)
2208    !-
2209    var_name = 't2m_week'
2210    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    1, 1, itime, &
2211         &                t2m_week, 'scatter', nbp_glo, index_g)
2212    !-
2213    var_name = 'tsoil_month'
2214    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nslm, 1, itime, &
2215         &                tsoil_month, 'scatter', nbp_glo, index_g)
2216    !-
2217    ! 6 fire probability
2218    !-
2219    var_name = 'fireindex'
2220    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2221         &                fireindex, 'scatter', nbp_glo, index_g)
2222    !-
2223    var_name = 'firelitter'
2224    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2225         &                firelitter, 'scatter', nbp_glo, index_g)
2226    !-
2227    ! 7 maximum and minimum moisture availabilities for tropic phenology
2228    !-
2229    var_name = 'maxmoistr_last'
2230    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2231         &                maxvegstress_lastyear, 'scatter', nbp_glo, index_g)
2232    !-
2233    var_name = 'maxmoistr_this'
2234    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2235         &                maxvegstress_thisyear, 'scatter', nbp_glo, index_g)
2236    !-
2237    var_name = 'minmoistr_last'
2238    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2239         &                minvegstress_lastyear, 'scatter', nbp_glo, index_g)
2240    !-
2241    var_name = 'minmoistr_this'
2242    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2243         &                minvegstress_thisyear, 'scatter', nbp_glo, index_g)
2244    !-
2245    ! 8 maximum "weekly" GPP
2246    !-
2247    var_name = 'maxgppweek_lastyear'
2248    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2249         &                maxgppweek_lastyear, 'scatter', nbp_glo, index_g)
2250    !-
2251    var_name = 'maxgppweek_thisyear'
2252    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2253         &                maxgppweek_thisyear, 'scatter', nbp_glo, index_g)
2254    !-
2255    ! 9 annual GDD0
2256    !-
2257    var_name = 'gdd0_thisyear'
2258    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2259         &                gdd0_thisyear, 'scatter', nbp_glo, index_g)
2260    !-
2261    var_name = 'gdd0_lastyear'
2262    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2263         &                gdd0_lastyear, 'scatter', nbp_glo, index_g)
2264    !-
2265    ! 10 annual precipitation
2266    !-
2267    var_name = 'precip_thisyear'
2268    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2269         &                precip_thisyear, 'scatter', nbp_glo, index_g)
2270    !-
2271    var_name = 'precip_lastyear'
2272    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2273         &                precip_lastyear, 'scatter', nbp_glo, index_g)
2274
2275    !-
2276    ! 11 derived "biometeorological" variables
2277    !-
2278    var_name = 'gdd_m5_dormance'
2279    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2280         &                gdd_m5_dormance, 'scatter', nbp_glo, index_g)
2281    !-
2282    var_name = 'gdd_from_growthinit'
2283    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2284         &              gdd_from_growthinit, 'scatter', nbp_glo, index_g)
2285    !-
2286    var_name = 'gdd_midwinter'
2287    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2288         &                gdd_midwinter, 'scatter', nbp_glo, index_g)
2289    !-
2290    var_name = 'ncd_dormance'
2291    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2292         &                ncd_dormance, 'scatter', nbp_glo, index_g)
2293    !-
2294    var_name = 'ngd_minus5'
2295    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2296         &                ngd_minus5, 'scatter', nbp_glo, index_g)
2297    !-
2298    var_name = 'time_hum_min'
2299    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2300         &                time_hum_min, 'scatter', nbp_glo, index_g)
2301    !-
2302    var_name = 'hum_min_dormance'
2303    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2304         &                hum_min_dormance, 'scatter', nbp_glo, index_g)
2305
2306    !-
2307    ! 12 Plant status
2308    !-
2309    var_name = 'PFTpresent'
2310    WHERE ( PFTpresent(:,:) )
2311       PFTpresent_real = un
2312    ELSEWHERE
2313       PFTpresent_real = zero
2314    ENDWHERE
2315    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2316         &                PFTpresent_real, 'scatter', nbp_glo, index_g)
2317    !-
2318    var_name = 'is_storm'
2319    WHERE ( is_storm(:) )
2320       is_storm_real = un
2321    ELSEWHERE
2322       is_storm_real = zero
2323    ENDWHERE
2324    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2325         &                is_storm_real, 'scatter', nbp_glo, index_g)
2326    !-
2327    var_name = 'count_storm'
2328    count_storm_real = REAL(count_storm,r_std)
2329    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2330         &                count_storm_real, 'scatter', nbp_glo, index_g)
2331    !-
2332    var_name = 'turnover_time'
2333    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, nparts, itime, &
2334         &                turnover_time, 'scatter', nbp_glo, index_g)
2335    !-
2336    var_name = 'adapted'
2337    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2338         &                adapted, 'scatter', nbp_glo, index_g)
2339    !-
2340    var_name = 'regenerate'
2341    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2342         &                regenerate, 'scatter', nbp_glo, index_g)
2343    !-
2344    var_name = 'npp_longterm'
2345    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2346         &                npp_longterm, 'scatter', nbp_glo, index_g)
2347    !-
2348    var_name = 'croot_longterm'
2349    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2350         &                croot_longterm, 'scatter', nbp_glo, index_g)
2351    !-
2352    var_name = 'n_reserve_longterm'
2353    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2354         &                n_reserve_longterm, 'scatter', nbp_glo, index_g)
2355    !-
2356    var_name = 'lm_lastyearmax'
2357    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2358         &                lm_lastyearmax, 'scatter', nbp_glo, index_g)
2359    !-
2360    var_name = 'lm_thisyearmax'
2361    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2362         &                lm_thisyearmax, 'scatter', nbp_glo, index_g)
2363    !-
2364    var_name = 'maxfpc_lastyear'
2365    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2366         &                maxfpc_lastyear, 'scatter', nbp_glo, index_g)
2367    !-
2368    var_name = 'maxfpc_thisyear'
2369    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2370         &                maxfpc_thisyear, 'scatter', nbp_glo, index_g)
2371    !-
2372    var_name = 'turnover_longterm'
2373    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, nparts, nelements, itime, &
2374         &                turnover_longterm, 'scatter', nbp_glo, index_g)
2375    !-
2376    var_name = 'gpp_week'
2377    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2378         &                gpp_week, 'scatter', nbp_glo, index_g)
2379    !-
2380    var_name = 'maint_resp'
2381    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, nparts, itime, &
2382         &                   resp_maint_part, 'scatter', nbp_glo, index_g)
2383    !-
2384    var_name = 'resp_maint_week'
2385    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2386         &                resp_maint_week, 'scatter', nbp_glo, index_g)
2387    !-
2388    var_name = 'leaf_age'
2389    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, nleafages, itime, &
2390         &                  leaf_age, 'scatter', nbp_glo, index_g)
2391    !-
2392    var_name = 'leaf_frac'
2393    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, nleafages, itime, &
2394         &                   leaf_frac, 'scatter', nbp_glo, index_g)
2395    !-
2396    var_name = 'leaf_age_crit'
2397    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2398         &                   leaf_age_crit, 'scatter', nbp_glo, index_g)
2399    !-
2400    var_name = 'lai_per_level'
2401    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, nlevels_tot, itime, &
2402         &                   lai_per_level, 'scatter', nbp_glo, index_g)
2403    !
2404    DO ipts=1,npts
2405       DO ivm=1,nvm
2406          DO ilev=1,nlevels_tot
2407             temp_array(ipts,ivm,ilev,1)=laieff_fit(ipts,ivm,ilev)%a
2408             temp_array(ipts,ivm,ilev,2)=laieff_fit(ipts,ivm,ilev)%b
2409             temp_array(ipts,ivm,ilev,3)=laieff_fit(ipts,ivm,ilev)%c
2410             temp_array(ipts,ivm,ilev,4)=laieff_fit(ipts,ivm,ilev)%d
2411             temp_array(ipts,ivm,ilev,5)=laieff_fit(ipts,ivm,ilev)%e
2412          ENDDO
2413       ENDDO
2414    ENDDO
2415    CALL restput_p (rest_id_stomate, 'laieff_fit', nbp_glo, nvm, nlevels_tot, nparams_laieff, itime, &
2416               &                   temp_array, 'scatter', nbp_glo, index_g)
2417    !-
2418    var_name = 'plant_status'
2419    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2420         &                plant_status, 'scatter', nbp_glo, index_g)
2421    !-
2422    var_name = 'when_growthinit'
2423    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2424         &                when_growthinit, 'scatter', nbp_glo, index_g)
2425    !-
2426    var_name = 'age'
2427    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
2428         &                age, 'scatter', nbp_glo, index_g)
2429    !-
2430    ! 13 CO2
2431    !-
2432    var_name = 'resp_hetero'
2433    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2434         &                resp_hetero, 'scatter', nbp_glo, index_g)
2435    !-
2436    var_name = 'resp_maint'
2437    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2438         &                resp_maint, 'scatter', nbp_glo, index_g)
2439    !-
2440    var_name = 'resp_growth'
2441    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2442         &                resp_growth, 'scatter', nbp_glo, index_g)
2443    !-
2444    var_name = 'co2_fire'
2445    CALL restput_p (rest_id_stomate, var_name, nbp_glo,  nvm, 1, itime, &
2446         &                co2_fire, 'scatter', nbp_glo, index_g)
2447    !-
2448    var_name = 'atm_to_bm'
2449    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, nelements, itime, &
2450         &                atm_to_bm, 'scatter', nbp_glo, index_g)
2451    !-
2452    ! 14 vegetation distribution after last light competition
2453    !-
2454    var_name = 'veget_lastlight'
2455    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2456         &                veget_lastlight, 'scatter', nbp_glo, index_g)
2457    !-
2458    ! 15 establishment criteria
2459    !-
2460    var_name = 'everywhere'
2461    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2462         &                everywhere, 'scatter', nbp_glo, index_g)
2463    !-
2464    var_name = 'need_adjacent'
2465    WHERE (need_adjacent(:,:))
2466       need_adjacent_real = un
2467    ELSEWHERE
2468       need_adjacent_real = zero
2469    ENDWHERE
2470    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2471         &                need_adjacent_real, 'scatter', nbp_glo, index_g)
2472    !-
2473    var_name = 'RIP_time'
2474    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2475         &                RIP_time, 'scatter', nbp_glo, index_g)
2476    !-
2477    ! 17 litter
2478    !-
2479    var_name = 'litter_c'
2480    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nlitt, nvm, nlevs, itime, &
2481        &                 litter(:,:,:,:,icarbon), 'scatter', nbp_glo, index_g)
2482    !-
2483    var_name = 'litter_n'
2484    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nlitt, nvm, nlevs,itime, &
2485        &                 litter(:,:,:,:,initrogen), 'scatter', nbp_glo, index_g)
2486    !-
2487    var_name = 'dead_leaves'
2488    CALL restput_p (rest_id_stomate, var_name, nbp_glo,  nvm, nlitt, itime, &
2489        &                   dead_leaves, 'scatter', nbp_glo, index_g)
2490    !-
2491    var_name = 'soil_carbon'
2492    CALL restput_p (rest_id_stomate, var_name, nbp_glo, ncarb, nvm, itime, &
2493         &                   som(:,:,:,icarbon), 'scatter', nbp_glo, index_g)
2494    !-
2495    var_name = 'soil_nitrogen'
2496    CALL restput_p (rest_id_stomate, var_name, nbp_glo, ncarb, nvm, itime, & 
2497         &                   som(:,:,:,initrogen), 'scatter', nbp_glo, index_g)
2498    !-
2499    var_name = 'lignin_struc'
2500    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, nlevs, itime, &
2501         &                   lignin_struc, 'scatter', nbp_glo, index_g)
2502    !-
2503    var_name = 'lignin_wood'
2504    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, nlevs, itime, &
2505         &                   lignin_wood, 'scatter', nbp_glo, index_g)
2506    !-
2507    ! 18 land cover change
2508    !-
2509    var_name = 'co2_flux'
2510    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2511         &                co2_flux, 'scatter', nbp_glo, index_g)
2512    !-
2513    var_name = 'fco2_lu'
2514    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2515         &                fco2_lu, 'scatter', nbp_glo, index_g)
2516    !-
2517    var_name = 'fco2_wh'
2518    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2519         &                fco2_wh, 'scatter', nbp_glo, index_g)
2520    !-
2521    var_name = 'fco2_ha'
2522    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2523         &                fco2_ha, 'scatter', nbp_glo, index_g)
2524    !-
2525    DO l = 1,nlctypes
2526
2527       var_name = 'prod_s'//TRIM(lctype_str(l))
2528       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nshort+1, nelements, nlanduse, itime, &
2529            &                prod_s(:,:,:,:,l), 'scatter', nbp_glo, index_g)
2530       !-
2531       var_name = 'prod_m'//TRIM(lctype_str(l))
2532       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nmedium+1, nelements, nlanduse, itime, &
2533            &                prod_m(:,:,:,:,l), 'scatter', nbp_glo, index_g)
2534       !-
2535       var_name = 'prod_l'//TRIM(lctype_str(l))   
2536       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nlong+1, nelements, nlanduse, itime, &
2537            &                prod_l(:,:,:,:,l), 'scatter', nbp_glo, index_g)
2538       !-
2539       var_name = 'flux_s'//TRIM(lctype_str(l))
2540       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nshort, nelements, nlanduse, itime, &
2541            &                flux_s(:,:,:,:,l), 'scatter', nbp_glo, index_g)
2542       !-
2543       var_name = 'flux_m'//TRIM(lctype_str(l))
2544       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nmedium, nelements, nlanduse, itime, &
2545            &                flux_m(:,:,:,:,l), 'scatter', nbp_glo, index_g)
2546       !-
2547       var_name = 'flux_l'//TRIM(lctype_str(l))
2548       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nlong, nelements, nlanduse, itime, &
2549            &                flux_l(:,:,:,:,l), 'scatter', nbp_glo, index_g)
2550    END DO
2551    !-
2552    var_name = 'bm_to_litter'
2553    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, nparts, nelements, itime, &
2554         &                bm_to_litter, 'scatter', nbp_glo, index_g)
2555    !-
2556    var_name = 'bm_to_litter_resid'
2557    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, nparts, nelements, itime, &
2558         &                bm_to_litter_resid, 'scatter', nbp_glo, index_g)
2559    !-
2560    CALL restput_p (rest_id_stomate, 'tree_to_litter', nbp_glo, nvm, nparts, nelements, itime, &
2561          &                tree_bm_to_litter, 'scatter', nbp_glo, index_g)
2562    !-
2563    CALL restput_p (rest_id_stomate, 'tree_to_litter_resid', nbp_glo, nvm, nparts, nelements, itime, &
2564          &                tree_bm_to_litter_resid, 'scatter', nbp_glo, index_g)
2565    !-
2566    var_name = 'fDeforestToProduct'
2567    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
2568         &              fDeforestToProduct, 'scatter', nbp_glo, index_g)
2569    !-
2570    var_name = 'fLulccResidue'
2571    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
2572         &              fLulccResidue, 'scatter', nbp_glo, index_g)
2573    !-
2574    var_name = 'fHarvestToProduct'
2575    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm  , 1, itime, &
2576         &              fHarvestToProduct, 'scatter', nbp_glo, index_g)
2577    !-
2578    var_name = 'carb_mass_total'
2579    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2580         &              carb_mass_total, 'scatter', nbp_glo, index_g)
2581    !-
2582    var_name = 'harvest_pool_acc'
2583    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm,ndia_harvest+1, nelements,itime, &
2584         &                harvest_pool_acc, 'scatter', nbp_glo, index_g)
2585    !-
2586    var_name = 'harvest_area_acc'
2587    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2588         &                harvest_area_acc, 'scatter', nbp_glo, index_g)
2589
2590    !! C and N burried during land cover change
2591    var_name = 'burried_litter'
2592    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nlitt, nlevs, nelements, itime, &
2593         &                burried_litter, 'scatter', nbp_glo, index_g)
2594    !-
2595    var_name = 'burried_fresh_ltr'
2596    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nparts, nelements, itime, &
2597         &                burried_fresh_ltr, 'scatter', nbp_glo, index_g)
2598    !-
2599    var_name = 'burried_fresh_som'
2600    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nparts, nelements, itime, &
2601         &                burried_fresh_som, 'scatter', nbp_glo, index_g)
2602    !-
2603    var_name = 'burried_bact'
2604    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2605         &                burried_bact, 'scatter', nbp_glo, index_g)
2606    !-
2607    var_name = 'burried_fungivores'
2608    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2609         &                burried_fungivores, 'scatter', nbp_glo, index_g)
2610    !-
2611    var_name = 'burried_min_nitro'
2612    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nnspec, 1, itime, &
2613         &                burried_min_nitro, 'scatter', nbp_glo, index_g)
2614    !-
2615    var_name = 'burried_som'
2616    CALL restput_p (rest_id_stomate, var_name, nbp_glo, ncarb, nelements, itime, &
2617         &                burried_som, 'scatter', nbp_glo, index_g)
2618    !-
2619    var_name = 'burried_deepSOM_a'
2620    CALL restput_p (rest_id_stomate, var_name, nbp_glo, ngrnd, nelements, itime, &
2621         &                burried_deepSOM_a, 'scatter', nbp_glo, index_g)
2622    !-
2623    var_name = 'burried_deepSOM_s'
2624    CALL restput_p (rest_id_stomate, var_name, nbp_glo, ngrnd, nelements, itime, &
2625         &                burried_deepSOM_s, 'scatter', nbp_glo, index_g)
2626    !-
2627    var_name = 'burried_deepSOM_p'
2628    CALL restput_p (rest_id_stomate, var_name, nbp_glo, ngrnd, nelements, itime, &
2629         &                burried_deepSOM_p, 'scatter', nbp_glo, index_g)
2630    !-
2631    IF (ok_windthrow) THEN
2632       var_name = 'gap_area_save'
2633       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, wind_years, itime, &
2634            &             gap_area_save, 'scatter', nbp_glo, index_g)
2635       !-
2636       var_name = 'total_ba_init'
2637       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2638            &             total_ba_init, 'scatter', nbp_glo, index_g)
2639    ENDIF
2640    !-
2641    IF (ok_pest) THEN
2642       var_name = 'sumTeff'
2643       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm,1,itime, &
2644            &             sumTeff, 'scatter', nbp_glo, index_g)
2645       !-
2646       var_name = 'beetle_diapause'
2647       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm,1,itime, &
2648            &             beetle_diapause, 'scatter', nbp_glo, index_g)
2649       !-
2650       var_name = 'epidemic'
2651       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm,1,itime, &
2652            &             epidemic, 'scatter', nbp_glo, index_g)
2653       !-
2654       var_name = 'beetle_flyaway'
2655       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm,1,itime, &
2656            &             beetle_flyaway, 'scatter', nbp_glo, index_g)
2657       !-
2658
2659       DO l=1,legacy_years
2660
2661          WRITE(pyear_str,'(I2.2)') l
2662          var_name = 'wood_leftover_'//pyear_str
2663          CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2664               &     wood_leftover_legacy(:,:,l), 'scatter', nbp_glo, index_g)
2665          !-
2666          var_name = 'season_drought_'//pyear_str
2667          CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2668               &     season_drought_legacy(:,:,l), 'scatter', nbp_glo, index_g)
2669          !-
2670          var_name = 'beetle_generation_'//pyear_str
2671          CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm,1, itime, &
2672               &     beetle_generation_index(:,:,l), 'scatter', nbp_glo, index_g)
2673          !-
2674          var_name = 'beetle_pop_'//pyear_str
2675          CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm,1, itime, &
2676               &     beetle_pop_legacy(:,:,l), 'scatter', nbp_glo, index_g)
2677          !-
2678          var_name = 'risk_index_legacy_'//pyear_str
2679          CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm,1, itime, &
2680               &     risk_index_legacy(:,:,l), 'scatter', nbp_glo, index_g)
2681          !-
2682       ENDDO
2683       !-
2684       DO l=1,beetle_legacy
2685          WRITE(pyear_str,'(I2.2)') l
2686          var_name = 'beetle_damage_legacy_'//pyear_str
2687          CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm,1, itime, &
2688               &     beetle_damage_legacy(:,:,l), 'scatter', nbp_glo, index_g)
2689       ENDDO
2690    ENDIF
2691
2692    var_name = 'sugar_load'
2693    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, &
2694         &              sugar_load, 'scatter', nbp_glo, index_g)
2695
2696    var_name = 'harvest_cut'
2697    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, &
2698         &              harvest_cut, 'scatter', nbp_glo, index_g)
2699
2700    IF ( ok_soil_carbon_discretization ) THEN
2701       var_name= 'deepSOM_a'
2702       CALL restput_p (rest_id_stomate, var_name, nbp_glo, ngrnd, nvm, nelements, itime, &
2703            deepSOM_a, 'scatter', nbp_glo, index_g)
2704       !-
2705       var_name= 'deepSOM_s'
2706       CALL restput_p (rest_id_stomate, var_name, nbp_glo, ngrnd, nvm, nelements, itime, &
2707            deepSOM_s, 'scatter', nbp_glo, index_g)
2708       !-
2709       var_name= 'deepSOM_p' 
2710       CALL restput_p (rest_id_stomate, var_name, nbp_glo, ngrnd, nvm, nelements, itime, &
2711            deepSOM_p, 'scatter', nbp_glo, index_g)
2712       !-
2713       var_name= 'O2_soil' 
2714       CALL restput_p (rest_id_stomate, var_name, nbp_glo, ngrnd, nvm, itime, &
2715            O2_soil, 'scatter', nbp_glo, index_g)
2716       !-
2717       var_name= 'CH4_soil'
2718       CALL restput_p (rest_id_stomate, var_name, nbp_glo, ngrnd, nvm, itime, &
2719            CH4_soil, 'scatter', nbp_glo, index_g)
2720       !-
2721       var_name= 'O2_snow'
2722       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nsnow, nvm, itime, &
2723            O2_snow, 'scatter', nbp_glo, index_g)
2724       !-
2725       var_name= 'CH4_snow'
2726       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nsnow, nvm, itime, &
2727            CH4_snow, 'scatter', nbp_glo, index_g)
2728       !-
2729       var_name= 'heat_Zimov'
2730       CALL restput_p (rest_id_stomate, var_name, nbp_glo, ngrnd, nvm, itime, &
2731            heat_Zimov, 'scatter', nbp_glo, index_g)
2732       !-
2733       var_name= 'altmax' 
2734       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2735            altmax, 'scatter', nbp_glo, index_g)
2736       !-
2737       var_name= 'depth_organic_soil'
2738       CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2739                      depth_organic_soil, 'scatter', nbp_glo, index_g)
2740       !-
2741       var_name = 'fixed_cryoturb_depth'
2742       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2743            fixed_cryoturbation_depth, 'scatter', nbp_glo, index_g)
2744    ENDIF
2745    !-
2746    var_name = 'nbp_accu_flux'
2747    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nelements, 1, itime, &
2748         &              nbp_accu_flux, 'scatter', nbp_glo, index_g)
2749    !-
2750    var_name = 'nbp_pool_start'
2751    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nelements, 1, itime, &
2752         &              nbp_pool_start, 'scatter', nbp_glo, index_g)
2753    !-
2754    var_name = 'Global_years'
2755    CALL restput_p (rest_id_stomate, var_name, itime, global_years)
2756   
2757    !-
2758    ! 19. Spinup
2759    !-
2760    IF (spinup_analytic) THEN
2761
2762       var_name = 'ok_equilibrium'
2763       WHERE(ok_equilibrium(:))
2764          ok_equilibrium_real = un
2765       ELSEWHERE
2766          ok_equilibrium_real = zero
2767       ENDWHERE
2768       CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, &
2769            &               ok_equilibrium_real, 'scatter', nbp_glo, index_g)
2770       !-
2771       var_name = 'MatrixV'
2772       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, nbpools, nbpools, itime, &
2773            &                MatrixV, 'scatter', nbp_glo, index_g)
2774       !-
2775       var_name = 'Vector_U'
2776       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, nbpools, itime, &
2777            &                VectorU, 'scatter', nbp_glo, index_g)
2778       !-
2779       var_name = 'previous_stock'
2780       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, nbpools, itime, &
2781            &                previous_stock, 'scatter', nbp_glo, index_g)
2782       !-
2783       var_name = 'current_stock'
2784       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, nbpools, itime, &
2785            &                current_stock, 'scatter', nbp_glo, index_g)
2786       !-
2787       var_name = 'CN_longterm'
2788       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, nbpools, itime, &
2789            &                CN_som_litter_longterm, 'scatter', nbp_glo, index_g)
2790       !-
2791       var_name = 'tau_CN_longterm'
2792       CALL restput_p (rest_id_stomate, var_name, itime, tau_CN_longterm)
2793       
2794    ENDIF !(spinup_analytic)
2795
2796    !-
2797    var_name = 'KF'
2798    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2799          &              KF(:,:), 'scatter', nbp_glo, index_g)
2800    !-
2801    var_name = 'k_latosa_adapt'
2802    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2803          &              k_latosa_adapt(:,:), 'scatter', nbp_glo, index_g)
2804    !-
2805    var_name = 'rue_longterm'
2806    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2807          &              rue_longterm(:,:), 'scatter', nbp_glo, index_g)
2808    !-
2809    var_name = 'cn_leaf_min_season' 
2810    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & 
2811         &              cn_leaf_min_season(:,:), 'scatter', nbp_glo, index_g) 
2812    !-
2813    var_name = 'nstress_season' 
2814    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & 
2815         &              nstress_season(:,:), 'scatter', nbp_glo, index_g)
2816    !-
2817    var_name = 'soil_n_min' 
2818    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, nnspec, itime, & 
2819         &              soil_n_min, 'scatter', nbp_glo, index_g) 
2820    !-
2821    var_name = 'p_O2' 
2822    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & 
2823         &              p_O2(:,:), 'scatter', nbp_glo, index_g) 
2824    !-
2825    var_name = 'bact' 
2826    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & 
2827         &              bact(:,:), 'scatter', nbp_glo, index_g)
2828    !-
2829    var_name = 'age_stand'
2830    temp_real = REAL(age_stand,r_std)
2831    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2832         &              temp_real, 'scatter', nbp_glo, index_g)
2833    !-
2834    var_name = 'rotation_n'
2835    temp_real = REAL(rotation_n,r_std) 
2836    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2837         &              temp_real, 'scatter', nbp_glo, index_g)
2838    !-
2839    var_name = 'last_cut'
2840    temp_real = REAL(last_cut,r_std)
2841    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2842         &              temp_real, 'scatter', nbp_glo, index_g)
2843    !-
2844    var_name = 'mai'
2845    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2846         &              mai, 'scatter', nbp_glo, index_g)
2847    !-
2848    var_name = 'pai'
2849    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2850         &              pai, 'scatter', nbp_glo, index_g)
2851    !-
2852    var_name = 'coppice_dens'
2853    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2854         &              coppice_dens, 'scatter', nbp_glo, index_g)
2855    !-
2856    var_name = 'previous_wood_volume'
2857    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2858         &              previous_wood_volume, 'scatter', nbp_glo, index_g)
2859    !-
2860    var_name = 'mai_count'
2861    temp_real = REAL(mai_count,r_std)
2862    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2863         &              temp_real, 'scatter', nbp_glo, index_g)
2864    !-
2865    IF (ok_change_species) THEN
2866       var_name = 'fm_current'
2867       temp_real = REAL(forest_managed,r_std)
2868       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2869            &              temp_real, 'scatter', nbp_glo, index_g)
2870    END IF
2871
2872    !-
2873    ! For these next three variables, we have to convert to a real array first.
2874    r_replant(:,:)=REAL(species_change_map(:,:),r_std)
2875    var_name = 'sc_map'
2876    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2877         &              r_replant, 'scatter', nbp_glo, index_g)
2878    !-
2879    r_replant(:,:)=REAL(fm_change_map(:,:),r_std)
2880    var_name = 'fmc_map'
2881    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2882         &              r_replant, 'scatter', nbp_glo, index_g)
2883    !-
2884    DO ipts=1,npts
2885       DO ivm=1,nvm
2886          IF(lpft_replant(ipts,ivm))THEN
2887             r_replant(ipts,ivm)=un
2888          ELSE
2889             r_replant(ipts,ivm)=zero
2890          ENDIF
2891       END DO
2892    END DO
2893    var_name = 'lpft_replant'
2894    CALL restput_p(rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2895         &              r_replant, 'scatter', nbp_glo, index_g)
2896    !-
2897    CALL restput_p (rest_id_stomate, 'assim_param', nbp_glo, nvm, npco2, itime, &
2898        &                assim_param, 'scatter', nbp_glo, index_g)
2899   
2900    ! 21 Seasonal mean transmitted light for recruitment in DOFOCO 
2901    var_name = 'light_tran_season' 
2902    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & 
2903        &                light_tran_to_floor_season, 'scatter', nbp_glo, index_g)
2904    !-
2905    var_name = 'daylight_count'
2906    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime,&
2907    &                   daylight_count, 'scatter', nbp_glo, index_g)
2908    !-
2909    ! Drought mortality
2910    DO l = 1,nelements
2911       var_name = 'bio_ini_drought'//TRIM(element_str(l))
2912       CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, ncirc, nparts, itime, &
2913            biomass_init_drought(:,:,:,:,l), 'scatter', nbp_glo, index_g)
2914    ENDDO
2915    !-
2916    temp_real(:,:) = zero
2917    WHERE ( kill_vessels(:,:) )
2918       temp_real = un
2919    ENDWHERE
2920    var_name = 'kill_vessels'
2921    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2922         &   temp_real, 'scatter', nbp_glo, index_g)
2923    !-
2924    var_name = 'vessel_loss_previous'
2925    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2926         &  vessel_loss_previous(:,:), 'scatter', nbp_glo, index_g)
2927    !-
2928    var_name = 'grow_season_len'
2929    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2930         &  grow_season_len(:,:), 'scatter', nbp_glo, index_g)
2931    !-
2932    var_name = 'doy_start_gs'
2933    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2934         &  doy_start_gs(:,:), 'scatter', nbp_glo, index_g)
2935    !-
2936    var_name = 'doy_end_gs'
2937    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2938         &  doy_end_gs(:,:), 'scatter', nbp_glo, index_g)
2939    !-
2940    var_name = 'mean_start_gs'
2941    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, &
2942         &  mean_start_gs(:,:), 'scatter', nbp_glo, index_g)
2943
2944    !--------------------------
2945  END SUBROUTINE writerestart
2946  !-
2947  !===
2948  !-
2949END MODULE stomate_io
Note: See TracBrowser for help on using the repository browser.