source: branches/publications/ORCHIDEE-GMv3.2/ORCHIDEE/src_sticslai/sticslai_io.f90 @ 6940

Last change on this file since 6940 was 6940, checked in by jinfeng.chang, 4 years ago

add missing files for ORCHIDEE-GMv3.2

File size: 104.4 KB
Line 
1!< $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/perso/albert.jornet/OMCROP/src_stomate/stomate_io.f90 $
2!< $Date: 2016-05-09 17:27:44 +0200 (Mon, 09 May 2016) $
3!< $Author: xuhui.wang $
4!< $Revision: 3419 $
5! IPSL (2006)
6!  This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
7!
8MODULE sticslai_io
9  !---------------------------------------------------------------------
10  !- Not all variables saved in the start files are absolutely necessary.
11  !- However, Sechiba's and Stomate's PFTs are not necessarily identical,
12  !- and for that case this information needs to be saved.
13  !---------------------------------------------------------------------
14  USE defprec
15  USE stomate_data
16  USE constantes
17  USE constantes_soil
18  USE mod_orchidee_para
19  USE ioipsl
20  USE ioipsl_para 
21  !-
22  IMPLICIT NONE
23  !-
24  PRIVATE
25  PUBLIC sticslai_io_readstart, sticslai_io_writestart
26  !-
27  ! reference temperature (K)
28  !-
29  REAL(r_std),ALLOCATABLE,DIMENSION(:),SAVE :: trefe
30!$OMP THREADPRIVATE(trefe)
31  !-
32CONTAINS
33  SUBROUTINE sticslai_io_writestart (npts, & 
34       &  f_crop_recycle,in_cycle, f_sen_lai, st2m_max_daily, wut_cm_daily, wus_cm_daily, evapot_daily, pdbiomass, pdmasec, &
35       &  masecveg, masec, dltams, gdh_daily, phoi, onarretesomcourdrp,  &
36       &  nsendltams, nsendltai, nsenpfeuilverte, nsendurvie, nsenndurvie, densiteequiv, &
37       &  nplt, tursla, ssla, pfeuilverte, bsenlai, &
38       &  zrac, nrec, nlan, tcult, udevair, udevcult, ndrp, rfvi, nlev, nger, etatvernal, &
39       &  caljvc, rfpi, upvt, utp, somcour, somcourdrp, somcourutp, tdevelop, somtemp, &
40       &  somcourfauche, stpltger, R_stamflax, R_stlaxsen, R_stsenlan, stlevflo, nflo, &
41       &  R_stlevdrp, R_stflodrp, R_stdrpmat, nmat, nlax, nrecbutoir, group, ndebdes, R_stdrpdes, densite, &
42       &  densitelev, coeflev, densiteger, somelong, somger, humectation, nbjhumec, &
43       &  somtemphumec, stpltlev, namf, stmatrec, tustress, lai, somfeuille, pdlai, &
44       &  nbfeuille, reajust, ulai, pdulai, efdensite, tempeff, nstopfeuille, deltai, vmax, nsen, &
45       &  laisen, pdlaisen, dltaisenat, nsencour, dltamsen, dltaisen, fgellev, &
46       &  gelee, fstressgel, R_stlevamf, dernier_n, durvieI, durvie, ndebsen, somsenreste, &
47       &  humrel, swfac, turfac, senfac,mafeuiljaune, msneojaune, &
48       &  v_dltams, fgelflo, pdircarb, ircarb, nbgrains, pgrain, vitmoy, nbgraingel, pgraingel, &
49       &  dltags, ftempremp, magrain, pdmagrain, nbj0remp, pdsfruittot, repracmax, repracmin, &
50       &  kreprac, somtemprac, urac, reprac, nstoprac, c_reserve, c_leafb, gslen, drylen,  &
51       &  nboxmax, box_ndays, box_lai, box_lairem, box_tdev, box_biom, box_biomrem, box_durage, box_somsenbase, &
52       &  cyc_num, cyc_num_tot,rot_cmd_store, plantdate, plantdate_now )
53
54
55 ! 0.1 Inputs Variables
56
57    ! Domain size
58    INTEGER(i_std),INTENT(in) :: npts
59    LOGICAL, DIMENSION(npts, nvm), INTENT(IN)       :: in_cycle 
60    LOGICAL, DIMENSION(npts, nvm), INTENT(IN)       :: f_sen_lai
61    LOGICAL, DIMENSION(npts, nvm), INTENT(IN)       :: f_crop_recycle 
62    ! daily maximum 2 meter temperatures (K)
63    REAL(r_std), DIMENSION(npts), INTENT(IN)      :: st2m_max_daily
64    ! daily value of soil temperature at the resolution of 1 cm, the second dimension is 3
65    ! the three layers around sowing layer
66    REAL(r_std), DIMENSION(npts, nvm, 3), INTENT(IN)    :: wut_cm_daily
67    ! daily mean value of soil relative humidity at the resolution of 1 cm, the second dimension is 3
68    ! the three layers around sowing layer
69    REAL(r_std), DIMENSION(npts, nvm, 3), INTENT(IN)    :: wus_cm_daily
70    ! daily potential evapotranspiration
71    REAL(r_std), DIMENSION(npts), INTENT(IN)      :: evapot_daily
72    ! biomass of previous day, t/ha
73    REAL(r_std), DIMENSION(npts, nvm), INTENT(IN)      :: pdbiomass
74    REAL(r_std), DIMENSION(npts, nvm), INTENT(IN)      :: pdmasec
75    ! vegetative biomass
76    REAL(r_std), DIMENSION(npts, nvm), INTENT(IN)      :: masecveg   
77    ! aboveground dry matter (t ha-1)
78    REAL(r_std), DIMENSION(npts, nvm), INTENT(IN)      :: masec
79    ! growth rate of plant, it means the delta total biomass increment (t ha-1)
80    REAL(r_std), DIMENSION(npts, nvm), INTENT(IN)      :: dltams
81    ! daily gdh calculated according to halfhourly temperature // transmitted from stomate.f90 gdh_daily
82    REAL(r_std), DIMENSION(npts, nvm), INTENT(IN)         :: gdh_daily 
83    ! Photoperiod // hours
84    REAL(r_std),  DIMENSION(npts), INTENT(IN)                             :: phoi 
85
86   
87    LOGICAL, DIMENSION(npts, nvm), INTENT(IN)           :: onarretesomcourdrp 
88    !INTEGER(i_std), DIMENSION(nvm), INTENT(IN)                           :: codeulaivernal
89    !INTEGER(i_std), DIMENSION(npts, nvm), INTENT(IN)                :: nlevobs    ! the following variables ended with obs are only used for forcing simulation. 
90    !INTEGER(i_std), DIMENSION(npts, nvm), INTENT(IN)                :: namfobs    ! the initial value should be always 999
91    !INTEGER(i_std), DIMENSION(npts, nvm), INTENT(IN)                :: nfloobs 
92    !INTEGER(i_std), DIMENSION(npts, nvm), INTENT(IN)                :: nlanobs 
93    !INTEGER(i_std), DIMENSION(npts, nvm), INTENT(IN)                :: nlaxobs 
94    !INTEGER(i_std), DIMENSION(npts, nvm), INTENT(IN)                :: nmatobs 
95    !INTEGER(i_std), DIMENSION(npts, nvm), INTENT(IN)                :: nrecobs 
96    !INTEGER(i_std), DIMENSION(npts, nvm), INTENT(IN)                :: nsenobs 
97    !INTEGER(i_std), DIMENSION(npts, nvm), INTENT(IN)                :: ndrpobs 
98
99    ! LAIdev SPECIFIC
100    REAL(r_std), DIMENSION(npts, nvm), INTENT(IN)        :: nsendltams
101    REAL(r_std), DIMENSION(npts, nvm), INTENT(IN)        :: nsendltai
102    REAL(r_std), DIMENSION(npts, nvm), INTENT(IN)        :: nsenpfeuilverte
103    REAL(r_std), DIMENSION(npts, nvm), INTENT(IN)        :: nsendurvie
104    REAL(r_std), DIMENSION(npts, nvm), INTENT(IN)        :: nsenndurvie
105    REAL(r_std), DIMENSION(npts, nvm), INTENT(IN)        :: densiteequiv
106    INTEGER(i_std), DIMENSION(npts, nvm), INTENT(IN)        :: nplt
107    REAL(r_std), DIMENSION(npts, nvm), INTENT(IN)        :: tursla
108    REAL(r_std), DIMENSION(npts, nvm), INTENT(IN)        :: ssla
109    REAL(r_std), DIMENSION(npts, nvm), INTENT(IN)        :: pfeuilverte
110    REAL(r_std), DIMENSION(npts, nvm), INTENT(IN)        :: bsenlai
111   
112    ! variables are involved in DEVELOPMENT
113
114    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: zrac
115    INTEGER(i_std), DIMENSION(npts, nvm), INTENT(IN)        :: nrec
116    INTEGER(i_std), DIMENSION(npts, nvm), INTENT(IN)        :: nlan
117    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: tcult
118    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: udevair
119    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: udevcult
120    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(IN)        :: ndrp
121    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: rfvi
122    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(IN)        :: nlev
123    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(IN)        :: nger
124    logical,    DIMENSION(npts, nvm), INTENT(IN)        :: etatvernal
125    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: caljvc
126    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: rfpi
127    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: upvt
128    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: utp
129    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: somcour
130    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: somcourdrp
131    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: somcourutp
132    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: tdevelop
133    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: somtemp
134    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: somcourfauche
135    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: stpltger
136    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: R_stamflax
137    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: R_stlaxsen
138    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: R_stsenlan
139    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: stlevflo
140    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(IN)        :: nflo
141    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: R_stlevdrp
142    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: R_stflodrp
143    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: R_stdrpmat
144    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(IN)        :: nmat
145    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(IN)        :: nlax
146    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(IN)        :: nrecbutoir
147    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: group
148    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(IN)        :: ndebdes
149    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: R_stdrpdes
150    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: densite
151    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: densitelev
152    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: coeflev
153    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: densiteger
154    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: somelong
155    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: somger
156    logical,    DIMENSION(npts, nvm), INTENT(IN)        :: humectation
157    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(IN)        :: nbjhumec
158    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: somtemphumec
159    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: stpltlev
160    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(IN)        :: namf
161    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: stmatrec
162 
163    ! these variables are involved in Lai_calculation
164     
165    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: tustress
166    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: lai
167    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: somfeuille
168    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: pdlai
169    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(IN)        :: nbfeuille
170    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: reajust
171    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: ulai
172    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: pdulai
173    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: efdensite
174    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: tempeff
175    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(IN)        :: nstopfeuille
176    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: deltai
177    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: vmax
178    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(IN)        :: nsen
179    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: laisen
180    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: pdlaisen
181    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)        :: dltaisenat
182
183    ! these variables are involved in the LAIsenescence
184
185    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(IN)      :: nsencour
186    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)      :: dltamsen
187    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)      :: dltaisen
188    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)      :: fgellev
189    logical,    DIMENSION(npts, nvm), INTENT(IN)      :: gelee
190    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)      :: fstressgel
191    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)      :: R_stlevamf
192    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(IN)      :: dernier_n
193    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)      :: durvieI
194    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)      :: durvie
195    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(IN)      :: ndebsen
196    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)      :: somsenreste
197    INTEGER(i_std), INTENT(IN)     :: nboxmax
198    INTEGER(i_std),   DIMENSION(npts, nvm, nboxmax), INTENT(IN) :: box_ndays
199    REAL(r_std),   DIMENSION(npts, nvm) :: boxtemp
200    REAL(r_std),   DIMENSION(npts, nvm, nboxmax), INTENT(IN) :: box_lai
201    REAL(r_std),   DIMENSION(npts, nvm, nboxmax), INTENT(IN) :: box_lairem
202    REAL(r_std),   DIMENSION(npts, nvm, nboxmax), INTENT(IN) :: box_tdev
203    REAL(r_std),   DIMENSION(npts, nvm, nboxmax), INTENT(IN) :: box_biom
204    REAL(r_std),   DIMENSION(npts, nvm, nboxmax), INTENT(IN) :: box_biomrem
205    REAL(r_std),   DIMENSION(npts, nvm, nboxmax), INTENT(IN) :: box_durage
206    REAL(r_std),   DIMENSION(npts, nvm, nboxmax), INTENT(IN) :: box_somsenbase
207
208    ! these variables are involved in STRESS calculation
209   
210    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)      :: humrel
211    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)      :: swfac
212    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)      :: turfac
213    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)      :: senfac
214
215    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)      :: mafeuiljaune 
216    REAL(r_std),    DIMENSION(npts, nvm), INTENT(IN)      :: msneojaune
217    ! these variables are involved in the CARBON ALLOCATION calculation
218
219    ! grain related   
220    REAL(r_std),    DIMENSION(npts, nvm, vlength)      ,INTENT(IN)       :: v_dltams
221    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(IN)       :: fgelflo
222    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(IN)       :: pdircarb
223    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(IN)       :: ircarb
224    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(IN)       :: nbgrains
225    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(IN)       :: pgrain
226    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(IN)       :: vitmoy
227    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(IN)       :: nbgraingel
228    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(IN)       :: pgraingel
229    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(IN)       :: dltags
230    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(IN)       :: ftempremp
231    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(IN)       :: magrain
232    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(IN)       :: pdmagrain
233    INTEGER(i_std), DIMENSION(npts, nvm)      ,INTENT(IN)       :: nbj0remp 
234    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(IN)       :: pdsfruittot
235
236    ! reprac related
237
238    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(IN)       :: repracmax
239    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(IN)       :: repracmin
240    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(IN)       :: kreprac
241    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(IN)       :: somtemprac
242    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(IN)       :: urac
243    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(IN)       :: reprac
244    INTEGER(i_std), DIMENSION(npts, nvm)      ,INTENT(IN)       :: nstoprac 
245
246    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(IN)       :: c_reserve
247    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(IN)       :: c_leafb
248    INTEGER(i_std), DIMENSION(npts, nvm)      ,INTENT(IN)       :: gslen 
249    INTEGER(i_std), DIMENSION(npts, nvm)      ,INTENT(IN)       :: drylen 
250    INTEGER(i_std), DIMENSION(npts, nvm)      ,INTENT(IN)       :: cyc_num
251    INTEGER(i_std), DIMENSION(npts)           ,INTENT(IN)       :: cyc_num_tot
252    INTEGER(i_std), DIMENSION(npts, rot_cmd_max, cyc_rot_max) ,INTENT(IN) :: rot_cmd_store
253    INTEGER(i_std), DIMENSION(npts, nvm, cyc_rot_max) ,INTENT(IN) :: plantdate
254    INTEGER(i_std), DIMENSION(npts, nvm) ,INTENT(IN) :: plantdate_now
255!! some temporary variable in type of real for restput
256    REAL(r_std), DIMENSION(npts, nvm)                           :: cyc_num_real
257    REAL(r_std), DIMENSION(npts)                                :: cyc_num_tot_real
258    REAL(r_std), DIMENSION(npts, rot_cmd_max, cyc_rot_max)      :: rot_cmd_store_real
259    REAL(r_std), DIMENSION(npts, nvm, cyc_rot_max)              :: plantdate_real
260    REAL(r_std), DIMENSION(npts, nvm)              :: plantdate_now_real
261
262 ! 0.4 Local variables
263
264    ! STICS--local
265    REAL(r_std), DIMENSION(npts, nvm)                                 :: in_cycle_real       
266    REAL(r_std), DIMENSION(npts, nvm)                                 :: f_sen_lai_real       
267    REAL(r_std), DIMENSION(npts, nvm)                                 :: f_crop_recycle_real       
268    REAL(r_std), DIMENSION(npts, nvm)                                 :: onarretesomcourdrp_real       
269    REAL(r_std), DIMENSION(npts, nvm)                                 :: humectation_real       
270
271    !REAL(r_std), DIMENSION(nvm)                                       :: codeulaivernal_real       
272   
273    !REAL(r_std), DIMENSION(npts, nvm)                                 :: nlevobs_real
274    !REAL(r_std), DIMENSION(npts, nvm)                                 :: namfobs_real
275    !REAL(r_std), DIMENSION(npts, nvm)                                 :: nfloobs_real 
276    !REAL(r_std), DIMENSION(npts, nvm)                                 :: nlanobs_real 
277    !REAL(r_std), DIMENSION(npts, nvm)                                 :: nlaxobs_real 
278    !REAL(r_std), DIMENSION(npts, nvm)                                 :: nmatobs_real 
279    !REAL(r_std), DIMENSION(npts, nvm)                                 :: nrecobs_real 
280    !REAL(r_std), DIMENSION(npts, nvm)                                 :: nsenobs_real 
281    !REAL(r_std), DIMENSION(npts, nvm)                                 :: ndrpobs_real 
282
283    REAL(r_std), DIMENSION(npts, nvm)                                 :: etatvernal_real 
284    REAL(r_std), DIMENSION(npts, nvm)                                 :: gelee_real 
285
286    ! To store variables names for I/O
287    CHARACTER(LEN=80) :: var_name
288    ! string suffix indicating an index
289    CHARACTER(LEN=10) :: part_str
290    ! string suffix indicating biomass type crops
291    CHARACTER(LEN=10) :: box_str
292
293    !var_name = 'f_crop_init'
294    !WHERE (f_crop_init)
295    !   f_crop_init_real = un
296    !ELSEWHERE
297    !   f_crop_init_real = zero
298    !ENDWHERE
299    !CALL restput_p (rest_id_stomate, var_name, nbp_glo,   1, 1, itime, &
300    !     &                 f_crop_init_real, 'scatter', nbp_glo, index_g)
301   
302    var_name = 'f_crop_recycle'
303    WHERE (f_crop_recycle(:,:))
304       f_crop_recycle_real = un
305    ELSEWHERE
306       f_crop_recycle_real = zero
307    ENDWHERE
308    CALL restput_p (rest_id_stomate, var_name, nbp_glo,   nvm, 1, itime, &
309         &                 f_crop_recycle_real, 'scatter', nbp_glo, index_g)
310
311    var_name = 'in_cycle'
312    WHERE (in_cycle(:,:))
313       in_cycle_real = un
314    ELSEWHERE
315       in_cycle_real = zero
316    ENDWHERE
317    CALL restput_p (rest_id_stomate, var_name, nbp_glo,   nvm, 1, itime, &
318         &                 in_cycle_real, 'scatter', nbp_glo, index_g)
319
320    var_name = 'f_sen_lai'
321    WHERE (f_sen_lai(:,:))
322       f_sen_lai_real = un
323    ELSEWHERE
324       f_sen_lai_real = zero
325    ENDWHERE
326    CALL restput_p (rest_id_stomate, var_name, nbp_glo,   nvm, 1, itime, &
327         &                 f_sen_lai_real, 'scatter', nbp_glo, index_g)
328   
329    var_name = 'st2m_max_daily'
330    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
331         &               st2m_max_daily, 'scatter', nbp_glo, index_g)
332
333
334    CALL restput_p (rest_id_stomate, 'wut_cm_daily', nbp_glo, nvm     , 3, itime, &
335            &               wut_cm_daily, 'scatter', nbp_glo, index_g)
336
337    CALL restput_p (rest_id_stomate, 'wus_cm_daily', nbp_glo, nvm   , 3, itime, &
338            &               wus_cm_daily, 'scatter', nbp_glo, index_g)
339
340    var_name = 'evapot_daily'
341    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
342         &               evapot_daily, 'scatter', nbp_glo, index_g)
343
344    var_name = 'pdbiomass'
345    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
346         &               pdbiomass, 'scatter', nbp_glo, index_g)
347
348    var_name = 'pdmasec'
349    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
350         &               pdmasec, 'scatter', nbp_glo, index_g)
351
352    var_name = 'masecveg'
353    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
354         &               masecveg, 'scatter', nbp_glo, index_g)
355
356    var_name = 'masec'
357    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
358         &               masec, 'scatter', nbp_glo, index_g)
359
360    var_name = 'dltams'
361    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
362         &               dltams, 'scatter', nbp_glo, index_g)
363
364    var_name = 'gdh_daily'
365    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
366         &               gdh_daily, 'scatter', nbp_glo, index_g)
367
368    var_name = 'phoi'
369    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
370         &               phoi, 'scatter', nbp_glo, index_g)
371
372    var_name = 'onarretesomcourdrp'
373    WHERE (onarretesomcourdrp(:, :))
374       onarretesomcourdrp_real = un
375    ELSEWHERE
376       onarretesomcourdrp_real = zero
377    ENDWHERE
378    CALL restput_p (rest_id_stomate, var_name, nbp_glo,   nvm, 1, itime, &
379         &                 onarretesomcourdrp_real, 'scatter', nbp_glo, index_g)
380
381    !var_name = 'codeulaivernal'
382    !codeulaivernal_real = FLOAT(codeulaivernal)
383    !CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
384    !     &               codeulaivernal_real, 'scatter', nbp_glo, index_g)
385 
386    !var_name = 'nlevobs'
387    !nlevobs_real = FLOAT(nlevobs)
388    !CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
389    !     &               nlevobs_real, 'scatter', nbp_glo, index_g)
390
391    !var_name = 'namfobs'
392    !namfobs_real = FLOAT(namfobs)
393    !CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
394    !     &               namfobs_real, 'scatter', nbp_glo, index_g)
395
396    !var_name = 'nfloobs'
397    !nfloobs_real = FLOAT(nfloobs)
398    !CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
399    !     &               nfloobs_real, 'scatter', nbp_glo, index_g)
400
401    !var_name = 'nlanobs'
402    !nlanobs_real = FLOAT(nlanobs)
403    !CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
404    !     &               nlanobs_real, 'scatter', nbp_glo, index_g)
405
406    !var_name = 'nlaxobs'
407    !nlaxobs_real = FLOAT(nlaxobs)
408    !CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
409    !     &               nlaxobs_real, 'scatter', nbp_glo, index_g)
410
411    !var_name = 'nmatobs'
412    !nmatobs_real = FLOAT(nmatobs)
413    !CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
414    !     &               nmatobs_real, 'scatter', nbp_glo, index_g)
415
416    !var_name = 'nrecobs'
417    !nrecobs_real = FLOAT(nrecobs)
418    !CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
419    !     &               nrecobs_real, 'scatter', nbp_glo, index_g)
420
421    !var_name = 'nsenobs'
422    !nsenobs_real = FLOAT(nsenobs)
423    !CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
424    !     &               nsenobs_real, 'scatter', nbp_glo, index_g)
425
426
427    !var_name = 'ndrpobs'
428    !ndrpobs_real = FLOAT(ndrpobs)
429    !CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
430    !     &               ndrpobs_real, 'scatter', nbp_glo, index_g)
431
432
433    var_name = 'nsendltams'
434    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
435         &               nsendltams, 'scatter', nbp_glo, index_g)
436
437    var_name = 'nsendltai'
438    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
439         &               nsendltai, 'scatter', nbp_glo, index_g)
440
441    var_name = 'nsenpfeuilverte'
442    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
443         &               nsenpfeuilverte, 'scatter', nbp_glo, index_g)
444
445    var_name = 'nsendurvie'
446    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
447         &               nsendurvie, 'scatter', nbp_glo, index_g)
448
449    var_name = 'nsenndurvie'
450    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
451         &               nsenndurvie, 'scatter', nbp_glo, index_g)
452
453    var_name = 'densiteequiv'
454    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
455         &               densiteequiv, 'scatter', nbp_glo, index_g)
456
457    var_name = 'nplt'
458    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
459         &               nplt, 'scatter', nbp_glo, index_g)
460
461    var_name = 'tursla'
462    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
463         &               tursla, 'scatter', nbp_glo, index_g)
464
465    var_name = 'ssla'
466    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
467         &               ssla, 'scatter', nbp_glo, index_g)
468
469    var_name = 'pfeuilverte'
470    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
471         &               pfeuilverte, 'scatter', nbp_glo, index_g)
472
473    var_name = 'bsenlai'
474    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
475         &               bsenlai, 'scatter', nbp_glo, index_g)
476
477    var_name = 'zrac'
478    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
479         &               zrac, 'scatter', nbp_glo, index_g)
480
481    var_name = 'nrec'
482    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
483         &               nrec, 'scatter', nbp_glo, index_g)
484
485    var_name = 'nlan'
486    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
487         &               nlan, 'scatter', nbp_glo, index_g)
488
489    var_name = 'tcult'
490    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
491         &               tcult, 'scatter', nbp_glo, index_g)
492
493    var_name = 'udevair'
494    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
495         &               udevair, 'scatter', nbp_glo, index_g)
496
497    var_name = 'udevcult'
498    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
499         &               udevcult, 'scatter', nbp_glo, index_g)
500
501    var_name = 'ndrp'
502    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
503         &               ndrp, 'scatter', nbp_glo, index_g)
504
505    var_name = 'rfvi'
506    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
507         &               rfvi, 'scatter', nbp_glo, index_g)
508
509    var_name = 'nlev'
510    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
511         &               nlev, 'scatter', nbp_glo, index_g)
512
513    var_name = 'nger'
514    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
515         &               nger, 'scatter', nbp_glo, index_g)
516
517    var_name = 'etatvernal'
518    WHERE ( etatvernal(:,:) )
519       etatvernal_real = un
520    ELSEWHERE
521       etatvernal_real = zero
522    ENDWHERE
523    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
524         &               etatvernal_real, 'scatter', nbp_glo, index_g)
525
526    var_name = 'caljvc'
527    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
528         &               caljvc, 'scatter', nbp_glo, index_g)
529
530    var_name = 'rfpi'
531    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
532         &               rfpi, 'scatter', nbp_glo, index_g)
533
534    var_name = 'upvt'
535    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
536         &               upvt, 'scatter', nbp_glo, index_g)
537
538    var_name = 'utp'
539    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
540         &               utp, 'scatter', nbp_glo, index_g)
541
542    var_name = 'somcour'
543    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
544         &               somcour, 'scatter', nbp_glo, index_g)
545
546    var_name = 'somcourdrp'
547    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
548         &               somcourdrp, 'scatter', nbp_glo, index_g)
549
550    var_name = 'somcourutp'
551    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
552         &               somcourutp, 'scatter', nbp_glo, index_g)
553
554    var_name = 'tdevelop'
555    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
556         &               tdevelop, 'scatter', nbp_glo, index_g)
557
558    var_name = 'somtemp'
559    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
560         &               somtemp, 'scatter', nbp_glo, index_g)
561
562    var_name = 'somcourfauche'
563    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
564         &               somcourfauche, 'scatter', nbp_glo, index_g)
565
566    var_name = 'stpltger'
567    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
568         &               stpltger, 'scatter', nbp_glo, index_g)
569
570    var_name = 'R_stlaxsen'
571    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
572         &               R_stlaxsen, 'scatter', nbp_glo, index_g)
573
574    var_name = 'R_stamflax'
575    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
576         &               R_stamflax, 'scatter', nbp_glo, index_g)
577
578    var_name = 'R_stsenlan'
579    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
580         &               R_stsenlan, 'scatter', nbp_glo, index_g)
581
582    var_name = 'stlevflo'
583    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
584         &               stlevflo, 'scatter', nbp_glo, index_g)
585
586    var_name = 'nflo'
587    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
588         &               nflo, 'scatter', nbp_glo, index_g)
589
590    var_name = 'R_stlevdrp'
591    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
592         &               R_stlevdrp, 'scatter', nbp_glo, index_g)
593
594    var_name = 'R_stflodrp'
595    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
596         &               R_stflodrp, 'scatter', nbp_glo, index_g)
597
598    var_name = 'R_stdrpmat'
599    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
600         &               R_stdrpmat, 'scatter', nbp_glo, index_g)
601
602    var_name = 'nmat'
603    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
604         &               nmat, 'scatter', nbp_glo, index_g)
605
606    var_name = 'nlax'
607    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
608         &               nlax, 'scatter', nbp_glo, index_g)
609
610    var_name = 'nrecbutoir'
611    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
612         &               nrecbutoir, 'scatter', nbp_glo, index_g)
613
614    var_name = 'group'
615    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
616         &               group, 'scatter', nbp_glo, index_g)
617
618    var_name = 'ndebdes'
619    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
620         &               ndebdes, 'scatter', nbp_glo, index_g)
621
622    var_name = 'R_stdrpdes'
623    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
624         &               R_stdrpdes, 'scatter', nbp_glo, index_g)
625
626    var_name = 'densite'
627    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
628         &               densite, 'scatter', nbp_glo, index_g)
629
630    var_name = 'densitelev'
631    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
632         &               densitelev, 'scatter', nbp_glo, index_g)
633
634    var_name = 'coeflev'
635    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
636         &               coeflev, 'scatter', nbp_glo, index_g)
637
638    var_name = 'densiteger'
639    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
640         &               densiteger, 'scatter', nbp_glo, index_g)
641
642    var_name = 'somelong'
643    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
644         &               somelong, 'scatter', nbp_glo, index_g)
645
646    var_name = 'somger'
647    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
648         &               somger, 'scatter', nbp_glo, index_g)
649
650    var_name = 'humectation'
651    WHERE (humectation(:, :))
652       humectation_real = un
653    ELSEWHERE
654       humectation_real = zero
655    ENDWHERE
656    CALL restput_p (rest_id_stomate, var_name, nbp_glo,   nvm, 1, itime, &
657         &                 humectation_real, 'scatter', nbp_glo, index_g)
658
659    var_name = 'nbjhumec'
660    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
661         &               nbjhumec, 'scatter', nbp_glo, index_g)
662
663    var_name = 'somtemphumec'
664    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
665         &               somtemphumec, 'scatter', nbp_glo, index_g)
666
667    var_name = 'stpltlev'
668    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
669         &               stpltlev, 'scatter', nbp_glo, index_g)
670
671    var_name = 'namf'
672    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
673         &               namf, 'scatter', nbp_glo, index_g)
674
675    var_name = 'stmatrec'
676    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
677         &               stmatrec, 'scatter', nbp_glo, index_g)
678
679    var_name = 'tustress'
680    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
681         &               tustress, 'scatter', nbp_glo, index_g)
682
683    var_name = 'lai'
684    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
685         &               lai, 'scatter', nbp_glo, index_g)
686
687    var_name = 'somfeuille'
688    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
689         &               somfeuille, 'scatter', nbp_glo, index_g)
690
691    var_name = 'pdlai'
692    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
693         &               pdlai, 'scatter', nbp_glo, index_g)
694
695    var_name = 'nbfeuille'
696    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
697         &               nbfeuille, 'scatter', nbp_glo, index_g)
698
699    var_name = 'reajust'
700    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
701         &               reajust, 'scatter', nbp_glo, index_g)
702
703    var_name = 'ulai'
704    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
705         &               ulai, 'scatter', nbp_glo, index_g)
706
707    var_name = 'pdulai'
708    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
709         &               pdulai, 'scatter', nbp_glo, index_g)
710
711    var_name = 'efdensite'
712    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
713         &               efdensite, 'scatter', nbp_glo, index_g)
714
715    var_name = 'tempeff'
716    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
717         &               tempeff, 'scatter', nbp_glo, index_g)
718
719    var_name = 'nstopfeuille'
720    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
721         &               nstopfeuille, 'scatter', nbp_glo, index_g)
722
723    var_name = 'deltai'
724    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
725         &               deltai, 'scatter', nbp_glo, index_g)
726
727    var_name = 'vmax'
728    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
729         &               vmax, 'scatter', nbp_glo, index_g)
730
731    var_name = 'nsen'
732    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
733         &               nsen, 'scatter', nbp_glo, index_g)
734
735    var_name = 'laisen'
736    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
737         &               laisen, 'scatter', nbp_glo, index_g)
738
739    var_name = 'pdlaisen'
740    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
741         &               pdlaisen, 'scatter', nbp_glo, index_g)
742
743    var_name = 'dltaisenat'
744    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
745         &               dltaisenat, 'scatter', nbp_glo, index_g)
746
747    var_name = 'nsencour'
748    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
749         &               nsencour, 'scatter', nbp_glo, index_g)
750
751    var_name = 'dltamsen'
752    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
753         &               dltamsen, 'scatter', nbp_glo, index_g)
754
755    var_name = 'dltaisen'
756    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
757         &               dltaisen, 'scatter', nbp_glo, index_g)
758
759    var_name = 'fgellev'
760    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
761         &               fgellev, 'scatter', nbp_glo, index_g)
762
763    var_name = 'gelee'
764    WHERE ( gelee(:,:) )
765       gelee_real = un
766    ELSEWHERE
767       gelee_real = zero
768    ENDWHERE
769    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
770         &               gelee_real, 'scatter', nbp_glo, index_g)
771
772    var_name = 'fstressgel'
773    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
774         &               fstressgel, 'scatter', nbp_glo, index_g)
775
776    var_name = 'laisen'
777    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
778         &               laisen, 'scatter', nbp_glo, index_g)
779
780    var_name = 'R_stlevamf'
781    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
782         &               R_stlevamf, 'scatter', nbp_glo, index_g)
783
784    var_name = 'dernier_n'
785    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
786         &               dernier_n, 'scatter', nbp_glo, index_g)
787
788    var_name = 'durvieI'
789    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
790         &               durvieI, 'scatter', nbp_glo, index_g)
791
792    var_name = 'durvie'
793    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
794         &               durvie, 'scatter', nbp_glo, index_g)
795
796    var_name = 'ndebsen'
797    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
798         &               ndebsen, 'scatter', nbp_glo, index_g)
799
800    var_name = 'somsenreste'
801    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
802         &               somsenreste, 'scatter', nbp_glo, index_g)
803
804    var_name = 'humrel'
805    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
806         &               humrel, 'scatter', nbp_glo, index_g)
807
808    var_name = 'swfac'
809    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
810         &               swfac, 'scatter', nbp_glo, index_g)
811
812    var_name = 'turfac'
813    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
814         &               turfac, 'scatter', nbp_glo, index_g)
815
816    var_name = 'senfac'
817    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
818         &               senfac, 'scatter', nbp_glo, index_g)
819 
820
821    var_name = 'mafeuiljaune'
822    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
823         &               mafeuiljaune, 'scatter', nbp_glo, index_g)
824
825    var_name = 'msneojaune'
826    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
827         &               msneojaune, 'scatter', nbp_glo, index_g)
828
829!    var_name = 'myvar'
830!    CALL restput_p(rest_id_stomate, var_name, nbp_glo, nvm, nboxmax, itime, &
831!        &                myvar, 'scatter', nbp_glo, index_g)
832
833     CALL restput_p (rest_id_stomate, 'box_ndays', nbp_glo, nvm     , nboxmax, itime, &
834            &                REAL(box_ndays), 'scatter', nbp_glo, index_g)
835
836     CALL restput_p(rest_id_stomate, 'box_lai', nbp_glo, nvm     , nboxmax, itime, &
837            &                box_lai, 'scatter', nbp_glo, index_g) 
838
839     CALL restput_p(rest_id_stomate, 'box_lairem', nbp_glo, nvm     , nboxmax, itime, &
840            &                box_lairem, 'scatter', nbp_glo, index_g)
841
842     CALL restput_p(rest_id_stomate, 'box_tdev', nbp_glo, nvm     , nboxmax, itime, &
843            &                box_tdev, 'scatter', nbp_glo, index_g)
844
845     CALL restput_p(rest_id_stomate, 'box_biom', nbp_glo, nvm     , nboxmax, itime, &
846            &                box_biom, 'scatter', nbp_glo, index_g)
847
848    CALL restput_p(rest_id_stomate, 'box_biomrem', nbp_glo, nvm     , nboxmax, itime, &
849            &                box_biomrem, 'scatter', nbp_glo, index_g)
850
851    CALL restput_p(rest_id_stomate, 'box_durage', nbp_glo, nvm     , nboxmax, itime, &
852            &                box_durage, 'scatter', nbp_glo, index_g)
853
854    CALL restput_p(rest_id_stomate, 'box_somsenbase', nbp_glo, nvm     , nboxmax, itime, &
855            &                box_somsenbase, 'scatter', nbp_glo, index_g)
856
857 
858    ! STICS:: CARBON ALLOCATION
859    CALL restput_p (rest_id_stomate, 'v_dltams', nbp_glo, nvm     , vlength, itime, &
860         &               v_dltams, 'scatter', nbp_glo, index_g)
861 
862    var_name = 'fgelflo'
863    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
864         &               fgelflo, 'scatter', nbp_glo, index_g)
865
866    var_name = 'pdircarb'
867    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
868         &               pdircarb, 'scatter', nbp_glo, index_g)
869
870
871    var_name = 'ircarb'
872    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
873         &               ircarb, 'scatter', nbp_glo, index_g)
874
875    var_name = 'nbgrains'
876    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
877         &               nbgrains, 'scatter', nbp_glo, index_g)
878
879    var_name = 'pgrain'
880    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
881         &               pgrain, 'scatter', nbp_glo, index_g)
882
883    var_name = 'vitmoy'
884    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
885         &               vitmoy, 'scatter', nbp_glo, index_g)
886
887    var_name = 'nbgraingel'
888    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
889         &               nbgraingel, 'scatter', nbp_glo, index_g)
890
891    var_name = 'pgraingel'
892    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
893         &               pgraingel, 'scatter', nbp_glo, index_g)
894
895    var_name = 'dltags'
896    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
897         &               dltags, 'scatter', nbp_glo, index_g)
898
899    var_name = 'ftempremp'
900    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
901         &               ftempremp, 'scatter', nbp_glo, index_g)
902
903    var_name = 'magrain'
904    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
905         &               magrain, 'scatter', nbp_glo, index_g)
906
907    var_name = 'pdmagrain'
908    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
909         &               pdmagrain, 'scatter', nbp_glo, index_g)
910
911
912    var_name = 'nbj0remp'
913    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
914         &               nbj0remp, 'scatter', nbp_glo, index_g)
915 
916    !var_name = 'nbj0remp'
917    !CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
918    !     &               nbj0remp, 'scatter', nbp_glo, index_g)
919
920    var_name = 'pdsfruittot'
921    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
922         &               pdsfruittot, 'scatter', nbp_glo, index_g)
923
924    var_name = 'repracmax'
925    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
926         &               repracmax, 'scatter', nbp_glo, index_g)
927
928    var_name = 'repracmin'
929    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
930         &               repracmin, 'scatter', nbp_glo, index_g)
931
932    var_name = 'kreprac'
933    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
934         &               kreprac, 'scatter', nbp_glo, index_g)
935
936    var_name = 'somtemprac'
937    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
938         &               somtemprac, 'scatter', nbp_glo, index_g)
939
940    var_name = 'urac'
941    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
942         &               urac, 'scatter', nbp_glo, index_g)
943
944    var_name = 'reprac'
945    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
946         &               reprac, 'scatter', nbp_glo, index_g)
947
948
949    var_name = 'nstoprac'
950    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
951         &               nstoprac, 'scatter', nbp_glo, index_g)
952
953
954    var_name = 'c_leafb'
955    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
956         &               c_leafb, 'scatter', nbp_glo, index_g)
957
958    var_name = 'c_reserve'
959    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
960         &               c_reserve, 'scatter', nbp_glo, index_g)
961   
962    var_name = 'gslen'
963    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
964         &               gslen, 'scatter', nbp_glo, index_g)
965
966    var_name = 'drylen'
967    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
968         &               drylen, 'scatter', nbp_glo, index_g)
969    IF (ok_rotate) THEN
970        var_name = 'cyc_num'
971        CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
972             &               cyc_num, 'scatter', nbp_glo, index_g)
973   
974        var_name = 'cyc_num_tot'
975        CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
976             &               cyc_num_tot, 'scatter', nbp_glo, index_g)
977   
978        var_name = 'rot_cmd_store'
979        CALL restput_p (rest_id_stomate, var_name, nbp_glo, rot_cmd_max, cyc_rot_max, itime, &
980             &               rot_cmd_store, 'scatter', nbp_glo, index_g)
981    ENDIF
982    var_name = 'plantdate'
983    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, cyc_rot_max, itime, &
984         &                plantdate, 'scatter', nbp_glo, index_g)
985
986    var_name = 'plantdate_now'
987    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1   , itime, &
988         &                plantdate_now, 'scatter', nbp_glo, index_g)
989
990  END SUBROUTINE sticslai_io_writestart
991  !-
992  !===
993  !-
994  SUBROUTINE sticslai_io_readstart (npts, & 
995       & f_crop_recycle, in_cycle, f_sen_lai, st2m_max_daily, wut_cm_daily, wus_cm_daily, evapot_daily, pdbiomass, pdmasec, &
996       & masecveg, masec, dltams, gdh_daily, phoi, onarretesomcourdrp,  &
997       & nsendltams, nsendltai, nsenpfeuilverte, nsendurvie, nsenndurvie, densiteequiv, &
998       & nplt, tursla, ssla, pfeuilverte, bsenlai, &
999       & zrac, nrec, nlan, tcult, udevair, udevcult, ndrp, rfvi, nlev, nger, etatvernal, &
1000       & caljvc, rfpi, upvt, utp, somcour, somcourdrp, somcourutp, tdevelop, somtemp, &
1001       & somcourfauche, stpltger, R_stamflax, R_stlaxsen, R_stsenlan, stlevflo, nflo, &
1002       & R_stlevdrp, R_stflodrp, R_stdrpmat, nmat, nlax, nrecbutoir, group, ndebdes, R_stdrpdes, densite, &
1003       & densitelev, coeflev, densiteger, somelong, somger, humectation, nbjhumec, &
1004       & somtemphumec, stpltlev, namf, stmatrec, tustress, lai, somfeuille, pdlai, &
1005       & nbfeuille, reajust, ulai, pdulai, efdensite, tempeff, nstopfeuille, deltai, vmax, nsen, &
1006       & laisen, pdlaisen, dltaisenat, nsencour, dltamsen, dltaisen, fgellev, &
1007       & gelee, fstressgel, R_stlevamf, dernier_n, durvieI, durvie, ndebsen, somsenreste, &
1008       & humrel, swfac, turfac, senfac, mafeuiljaune, msneojaune,&
1009       & v_dltams, fgelflo, pdircarb, ircarb, nbgrains, pgrain, vitmoy, nbgraingel, pgraingel, &
1010       & dltags, ftempremp, magrain, pdmagrain, nbj0remp, pdsfruittot, repracmax, repracmin, &
1011       & kreprac, somtemprac, urac, reprac, nstoprac, c_reserve, c_leafb, gslen, drylen, &
1012       & nboxmax, box_ndays, box_lai, box_lairem, box_tdev, box_biom, box_biomrem,box_durage, box_somsenbase )
1013!!!!! end crop, xuhui
1014    !---------------------------------------------------------------------
1015    !- read start file
1016    !---------------------------------------------------------------------
1017    !-
1018    ! 0 declarations
1019    !-
1020    ! 0.1 input
1021    !-
1022    ! Domain size
1023    INTEGER(i_std),INTENT(in) :: npts
1024    ! Indices of the points on the map
1025!!!!! crops
1026
1027    !LOGICAL, INTENT(OUT)       :: f_crop_init
1028    LOGICAL, DIMENSION(npts, nvm), INTENT(OUT)       :: f_crop_recycle 
1029    LOGICAL, DIMENSION(npts, nvm), INTENT(OUT)       :: in_cycle 
1030    LOGICAL, DIMENSION(npts, nvm), INTENT(OUT)       :: f_sen_lai 
1031    ! daily maximum 2 meter temperatures (K)
1032    REAL(r_std), DIMENSION(npts), INTENT(OUT)      :: st2m_max_daily
1033    ! daily value of soil temperature at the resolution of 1 cm, the second dimension is 3
1034    ! the three layers around sowing layer
1035    REAL(r_std), DIMENSION(npts, nvm, 3), INTENT(OUT)    :: wut_cm_daily
1036    ! daily mean value of soil relative humidity at the resolution of 1 cm, the second dimension is 3
1037    ! the three layers around sowing layer
1038    REAL(r_std), DIMENSION(npts, nvm, 3), INTENT(OUT)    :: wus_cm_daily
1039    ! daily potential evapotranspiration
1040    REAL(r_std), DIMENSION(npts), INTENT(OUT)      :: evapot_daily
1041    ! biomass of previous day, t/ha
1042    REAL(r_std), DIMENSION(npts, nvm), INTENT(OUT)      :: pdbiomass
1043    REAL(r_std), DIMENSION(npts, nvm), INTENT(OUT)      :: pdmasec
1044    ! vegetative biomass
1045    REAL(r_std), DIMENSION(npts, nvm), INTENT(OUT)      :: masecveg   
1046    ! aboveground dry matter (t ha-1)
1047    REAL(r_std), DIMENSION(npts, nvm), INTENT(OUT)      :: masec
1048    ! growth rate of plant, it means the delta total biomass increment (t ha-1)
1049    REAL(r_std), DIMENSION(npts, nvm), INTENT(OUT)      :: dltams
1050    ! daily gdh calculated according to halfhourly temperature // transmitted from stomate.f90 gdh_daily
1051    REAL(r_std), DIMENSION(npts, nvm), INTENT(OUT)         :: gdh_daily 
1052    ! Photoperiod // hours
1053    REAL(r_std),  DIMENSION(npts), INTENT(OUT)                             :: phoi 
1054
1055   
1056    LOGICAL, DIMENSION(npts, nvm), INTENT(OUT)           :: onarretesomcourdrp 
1057    !INTEGER(i_std), DIMENSION(nvm), INTENT(OUT)                           :: codeulaivernal
1058    !INTEGER(i_std), DIMENSION(npts, nvm), INTENT(OUT)                :: nlevobs    ! the following variables ended with obs are only used for forcing simulation. 
1059    !INTEGER(i_std), DIMENSION(npts, nvm), INTENT(OUT)                :: namfobs    ! the initial value should be always 999
1060    !INTEGER(i_std), DIMENSION(npts, nvm), INTENT(OUT)                :: nfloobs 
1061    !INTEGER(i_std), DIMENSION(npts, nvm), INTENT(OUT)                :: nlanobs 
1062    !INTEGER(i_std), DIMENSION(npts, nvm), INTENT(OUT)                :: nlaxobs 
1063    !INTEGER(i_std), DIMENSION(npts, nvm), INTENT(OUT)                :: nmatobs 
1064    !INTEGER(i_std), DIMENSION(npts, nvm), INTENT(OUT)                :: nrecobs 
1065    !INTEGER(i_std), DIMENSION(npts, nvm), INTENT(OUT)                :: nsenobs 
1066    !INTEGER(i_std), DIMENSION(npts, nvm), INTENT(OUT)                :: ndrpobs 
1067
1068    ! LAIdev SPECIFIC
1069    REAL(r_std), DIMENSION(npts, nvm), INTENT(OUT)        :: nsendltams
1070    REAL(r_std), DIMENSION(npts, nvm), INTENT(OUT)        :: nsendltai
1071    REAL(r_std), DIMENSION(npts, nvm), INTENT(OUT)        :: nsenpfeuilverte
1072    REAL(r_std), DIMENSION(npts, nvm), INTENT(OUT)        :: nsendurvie
1073    REAL(r_std), DIMENSION(npts, nvm), INTENT(OUT)        :: nsenndurvie
1074    REAL(r_std), DIMENSION(npts, nvm), INTENT(OUT)        :: densiteequiv
1075    INTEGER(i_std), DIMENSION(npts, nvm), INTENT(OUT)        :: nplt
1076    REAL(r_std), DIMENSION(npts, nvm), INTENT(OUT)        :: tursla
1077    REAL(r_std), DIMENSION(npts, nvm), INTENT(OUT)        :: ssla
1078    REAL(r_std), DIMENSION(npts, nvm), INTENT(OUT)        :: pfeuilverte
1079    REAL(r_std), DIMENSION(npts, nvm), INTENT(OUT)        :: bsenlai
1080   
1081    ! variables are involved in DEVELOPMENT
1082
1083    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: zrac
1084    INTEGER(i_std), DIMENSION(npts, nvm), INTENT(OUT)        :: nrec
1085    INTEGER(i_std), DIMENSION(npts, nvm), INTENT(OUT)        :: nlan
1086    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: tcult
1087    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: udevair
1088    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: udevcult
1089    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: ndrp
1090    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: rfvi
1091    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: nlev
1092    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: nger
1093    logical,    DIMENSION(npts, nvm), INTENT(OUT)        :: etatvernal
1094    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: caljvc
1095    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: rfpi
1096    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: upvt
1097    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: utp
1098    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: somcour
1099    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: somcourdrp
1100    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: somcourutp
1101    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: tdevelop
1102    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: somtemp
1103    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: somcourfauche
1104    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: stpltger
1105    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: R_stamflax
1106    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: R_stlaxsen
1107    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: R_stsenlan
1108    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: stlevflo
1109    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: nflo
1110    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: R_stlevdrp
1111    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: R_stflodrp
1112    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: R_stdrpmat
1113    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: nmat
1114    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: nlax
1115    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: nrecbutoir
1116    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: group
1117    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: ndebdes
1118    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: R_stdrpdes
1119    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: densite
1120    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: densitelev
1121    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: coeflev
1122    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: densiteger
1123    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: somelong
1124    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: somger
1125    logical,    DIMENSION(npts, nvm), INTENT(OUT)        :: humectation
1126    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: nbjhumec
1127    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: somtemphumec
1128    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: stpltlev
1129    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: namf
1130    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: stmatrec
1131 
1132    ! these variables are involved in Lai_calculation
1133     
1134    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: tustress
1135    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: lai
1136    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: somfeuille
1137    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: pdlai
1138    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: nbfeuille
1139    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: reajust
1140    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: ulai
1141    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: pdulai
1142    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: efdensite
1143    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: tempeff
1144    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: nstopfeuille
1145    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: deltai
1146    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: vmax
1147    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: nsen
1148    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: laisen
1149    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: pdlaisen
1150    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)        :: dltaisenat
1151
1152    ! these variables are involved in the LAIsenescence
1153
1154    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(OUT)      :: nsencour
1155    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)      :: dltamsen
1156    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)      :: dltaisen
1157    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)      :: fgellev
1158    logical,    DIMENSION(npts, nvm), INTENT(OUT)      :: gelee
1159    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)      :: fstressgel
1160    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)      :: R_stlevamf
1161    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(OUT)      :: dernier_n
1162    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)      :: durvieI
1163    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)      :: durvie
1164    INTEGER(i_std),    DIMENSION(npts, nvm), INTENT(OUT)      :: ndebsen
1165    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)      :: somsenreste
1166
1167    INTEGER(i_std), INTENT(IN)                             :: nboxmax   
1168    INTEGER(i_std),    DIMENSION(npts, nvm, nboxmax), INTENT(OUT)      :: box_ndays   
1169    REAL(r_std),    DIMENSION(npts, nvm, nboxmax)                   :: boxtemp
1170    REAL(r_std),    DIMENSION(npts, nvm, nboxmax), INTENT(OUT)      :: box_lai
1171    REAL(r_std),    DIMENSION(npts, nvm, nboxmax), INTENT(OUT)      :: box_lairem
1172    REAL(r_std),    DIMENSION(npts, nvm, nboxmax), INTENT(OUT)      :: box_tdev
1173    REAL(r_std),    DIMENSION(npts, nvm, nboxmax), INTENT(OUT)      :: box_biom
1174    REAL(r_std),    DIMENSION(npts, nvm, nboxmax), INTENT(OUT)      :: box_biomrem
1175    REAL(r_std),    DIMENSION(npts, nvm, nboxmax), INTENT(OUT)      :: box_durage
1176    REAL(r_std),    DIMENSION(npts, nvm, nboxmax), INTENT(OUT)      :: box_somsenbase
1177   
1178
1179    ! these variables are involved in STRESS calculation
1180   
1181    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)      :: humrel
1182    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)      :: swfac
1183    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)      :: turfac
1184    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)      :: senfac
1185
1186    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)      :: mafeuiljaune
1187    REAL(r_std),    DIMENSION(npts, nvm), INTENT(OUT)      :: msneojaune
1188    ! these variables are involved in the CARBON ALLOCATION calculation
1189
1190    ! grain related   
1191    REAL(r_std),    DIMENSION(npts, nvm, vlength)      ,INTENT(OUT)       :: v_dltams
1192    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(OUT)       :: fgelflo
1193    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(OUT)       :: pdircarb
1194    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(OUT)       :: ircarb
1195    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(OUT)       :: nbgrains
1196    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(OUT)       :: pgrain
1197    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(OUT)       :: vitmoy
1198    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(OUT)       :: nbgraingel
1199    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(OUT)       :: pgraingel
1200    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(OUT)       :: dltags
1201    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(OUT)       :: ftempremp
1202    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(OUT)       :: magrain
1203    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(OUT)       :: pdmagrain
1204    INTEGER(i_std), DIMENSION(npts, nvm)      ,INTENT(OUT)       :: nbj0remp 
1205    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(OUT)       :: pdsfruittot
1206
1207    ! reprac related
1208
1209    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(OUT)       :: repracmax
1210    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(OUT)       :: repracmin
1211    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(OUT)       :: kreprac
1212    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(OUT)       :: somtemprac
1213    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(OUT)       :: urac
1214    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(OUT)       :: reprac
1215    INTEGER(i_std), DIMENSION(npts, nvm)      ,INTENT(OUT)       :: nstoprac
1216
1217    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(OUT)       :: c_reserve
1218    REAL(r_std),    DIMENSION(npts, nvm)      ,INTENT(OUT)       :: c_leafb
1219
1220    INTEGER(i_std), DIMENSION(npts, nvm)      ,INTENT(OUT)       :: gslen 
1221    INTEGER(i_std), DIMENSION(npts, nvm)      ,INTENT(OUT)       :: drylen 
1222
1223!!!!! xuhui
1224    ! STICS--local
1225    CHARACTER(LEN=100)                                            :: var_name !! for restget_p
1226    REAL(r_std), DIMENSION(npts, nvm)                                 :: in_cycle_real       
1227    REAL(r_std), DIMENSION(npts, nvm)                                 :: f_sen_lai_real       
1228    REAL(r_std), DIMENSION(npts, nvm)                                 :: f_crop_recycle_real       
1229    REAL(r_std), DIMENSION(npts, nvm)                                 :: onarretesomcourdrp_real       
1230    REAL(r_std), DIMENSION(npts, nvm)                                 :: humectation_real       
1231
1232    !REAL(r_std), DIMENSION(nvm)                                       :: codeulaivernal_real       
1233   
1234    !REAL(r_std), DIMENSION(npts, nvm)                                 :: nlevobs_real
1235    !REAL(r_std), DIMENSION(npts, nvm)                                 :: namfobs_real
1236    !REAL(r_std), DIMENSION(npts, nvm)                                 :: nfloobs_real 
1237    !REAL(r_std), DIMENSION(npts, nvm)                                 :: nlanobs_real 
1238    !REAL(r_std), DIMENSION(npts, nvm)                                 :: nlaxobs_real 
1239    !REAL(r_std), DIMENSION(npts, nvm)                                 :: nmatobs_real 
1240    !REAL(r_std), DIMENSION(npts, nvm)                                 :: nrecobs_real 
1241    !REAL(r_std), DIMENSION(npts, nvm)                                 :: nsenobs_real 
1242    !REAL(r_std), DIMENSION(npts, nvm)                                 :: ndrpobs_real 
1243
1244    REAL(r_std), DIMENSION(npts, nvm)                                 :: etatvernal_real 
1245    REAL(r_std), DIMENSION(npts, nvm)                                 :: gelee_real 
1246
1247
1248    INTEGER(i_std)                                :: l,k,ji, jv, i, j, m      !! indices   
1249!!!!! xuhui
1250
1251    !---------------------------------------------------------------------
1252    IF (printlev >= 3) WRITE(numout,*) 'Entering readstart_sticslai_io'
1253
1254!ENDJCADD
1255!!!!! crops
1256
1257    !f_crop_init_real = val_exp
1258    !var_name = 'f_crop_init'
1259    !CALL restget_p (rest_id_stomate, var_name, nbp_glo,   1, 1, itime, &
1260    !     &                .TRUE., f_crop_init_real, 'gather', nbp_glo, index_g)
1261    !IF (f_crop_init_real == val_exp) f_crop_init_real = zero
1262    !WHERE (f_crop_init_real == 1)
1263    !   f_crop_init = .TRUE.
1264    !ELSEWHERE
1265    !   f_crop_init = .FALSE.
1266    !ENDWHERE
1267   
1268    f_crop_recycle_real(:, :) = val_exp
1269    var_name = 'f_crop_recycle'
1270    CALL restget_p (rest_id_stomate, var_name, nbp_glo,   nvm, 1, itime, &
1271         &                .TRUE., f_crop_recycle_real, 'gather', nbp_glo, index_g)
1272    IF (ALL(f_crop_recycle_real(:, :) == val_exp)) f_crop_recycle_real(:, :) = zero
1273    WHERE (f_crop_recycle_real(:, :) == un)
1274       f_crop_recycle = .TRUE.
1275    ELSEWHERE
1276       f_crop_recycle = .FALSE.
1277    ENDWHERE
1278
1279    in_cycle_real(:, :) = val_exp
1280    var_name = 'in_cycle'
1281    CALL restget_p (rest_id_stomate, var_name, nbp_glo,   nvm, 1, itime, &
1282         &                .TRUE., in_cycle_real, 'gather', nbp_glo, index_g)
1283    IF (ALL(in_cycle_real(:, :) == val_exp)) in_cycle_real(:, :) = zero
1284    WHERE (in_cycle_real(:, :) == un)
1285       in_cycle = .TRUE.
1286    ELSEWHERE
1287       in_cycle = .FALSE.
1288    ENDWHERE
1289   
1290    f_sen_lai_real(:, :) = val_exp
1291    var_name = 'f_sen_lai'
1292    CALL restget_p (rest_id_stomate, var_name, nbp_glo,   nvm, 1, itime, &
1293         &                .TRUE., f_sen_lai_real, 'gather', nbp_glo, index_g)
1294    IF (ALL(f_sen_lai_real(:, :) == val_exp)) f_sen_lai_real(:, :) = un
1295    WHERE (f_sen_lai_real(:, :) == un)
1296       f_sen_lai = .TRUE.
1297    ELSEWHERE
1298       f_sen_lai = .FALSE.
1299    ENDWHERE
1300   
1301    st2m_max_daily(:) = val_exp
1302    var_name = 'st2m_max_daily'
1303    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
1304         &              .TRUE., st2m_max_daily, 'gather', nbp_glo, index_g)
1305    IF (ALL(st2m_max_daily(:) == val_exp)) st2m_max_daily(:) = zero
1306
1307    wut_cm_daily(:, :, :) = val_exp
1308    CALL restget_p (rest_id_stomate, 'wut_cm_daily', nbp_glo, nvm, 3, itime, &
1309         &              .TRUE., wut_cm_daily, 'gather', nbp_glo, index_g)
1310    IF (ALL(wut_cm_daily == val_exp)) wut_cm_daily = zero
1311
1312
1313    wus_cm_daily(:, :, :) = val_exp
1314    CALL restget_p (rest_id_stomate, 'wus_cm_daily', nbp_glo,  nvm , 3, itime, &
1315         &              .TRUE., wus_cm_daily, 'gather', nbp_glo, index_g)
1316    IF (ALL(wus_cm_daily == val_exp)) wus_cm_daily = zero
1317
1318
1319    evapot_daily(:) = val_exp
1320    var_name = 'evapot_daily'
1321    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
1322         &              .TRUE., evapot_daily, 'gather', nbp_glo, index_g)
1323    IF (ALL(evapot_daily(:) == val_exp)) evapot_daily(:) = zero
1324
1325    pdbiomass(:, :) = val_exp
1326    var_name = 'pdbiomass'
1327    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1328         &              .TRUE., pdbiomass, 'gather', nbp_glo, index_g)
1329    IF (ALL(pdbiomass(:, :) == val_exp)) pdbiomass(:, :) = zero
1330
1331    pdmasec(:, :) = val_exp
1332    var_name = 'pdmasec'
1333    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1334         &              .TRUE., pdmasec, 'gather', nbp_glo, index_g)
1335    IF (ALL(pdmasec(:, :) == val_exp)) pdmasec(:, :) = zero
1336
1337    masecveg(:, :) = val_exp
1338    var_name = 'masecveg'
1339    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1340         &              .TRUE., masecveg, 'gather', nbp_glo, index_g)
1341    IF (ALL(masecveg(:, :) == val_exp)) masecveg(:, :) = zero
1342
1343    masec(:, :) = val_exp
1344    var_name = 'masec'
1345    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1346         &              .TRUE., masec, 'gather', nbp_glo, index_g)
1347    IF (ALL(masec(:, :) == val_exp)) masec(:, :) = zero
1348
1349    dltams(:, :) = val_exp
1350    var_name = 'dltams'
1351    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1352         &              .TRUE., dltams, 'gather', nbp_glo, index_g)
1353    IF (ALL(dltams(:, :) == val_exp)) dltams(:, :) = zero
1354
1355    gdh_daily(:, :) = val_exp
1356    var_name = 'gdh_daily'
1357    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1358         &              .TRUE., gdh_daily, 'gather', nbp_glo, index_g)
1359    IF (ALL(gdh_daily(:, :) == val_exp)) gdh_daily(:, :) = zero
1360
1361    phoi(:) = val_exp
1362    var_name = 'phoi'
1363    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
1364         &              .TRUE., phoi, 'gather', nbp_glo, index_g)
1365    IF (ALL(phoi(:) == val_exp)) phoi(:) = zero
1366
1367    onarretesomcourdrp_real(:, :) = val_exp
1368    var_name = 'onarretesomcourdrp'
1369    CALL restget_p (rest_id_stomate, var_name, nbp_glo,   nvm, 1, itime, &
1370         &                .TRUE., onarretesomcourdrp_real, 'gather', nbp_glo, index_g)
1371    IF (ALL(onarretesomcourdrp_real(:, :) == val_exp)) onarretesomcourdrp_real(:, :) = zero
1372    WHERE (onarretesomcourdrp_real(:, :) == un)
1373       onarretesomcourdrp = .TRUE.
1374    ELSEWHERE
1375       onarretesomcourdrp = .FALSE.
1376    ENDWHERE
1377
1378    !codeulaivernal(:) = val_exp
1379    !var_name = 'codeulaivernal'
1380    !CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1     , 1, itime, &
1381    !     &              .TRUE., codeulaivernal_real, 'gather', nbp_glo, index_g)
1382    !IF (ALL(codeulaivernal_real(:) == val_exp)) codeulaivernal_real(:) = zero
1383    !codeulaivernal = INT(codeulaivernal_real)
1384
1385    !nlevobs(:, :) = val_exp
1386    !var_name = 'nlevobs'
1387    !CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1388    !     &              .TRUE., nlevobs_real, 'gather', nbp_glo, index_g)
1389    !IF (ALL(nlevobs_real(:, :) == val_exp)) nlevobs_real(:, :) = zero
1390    !nlevobs = INT(nlevobs_real)
1391
1392    !namfobs(:, :) = val_exp
1393    !var_name = 'namfobs'
1394    !CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1395    !     &              .TRUE., namfobs_real, 'gather', nbp_glo, index_g)
1396    !IF (ALL(namfobs_real(:, :) == val_exp)) namfobs_real(:, :) = zero
1397    !namfobs = INT(namfobs_real)
1398
1399    !nfloobs(:, :) = val_exp
1400    !var_name = 'nfloobs'
1401    !CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1402    !     &              .TRUE., nfloobs_real, 'gather', nbp_glo, index_g)
1403    !IF (ALL(nfloobs_real(:, :) == val_exp)) nfloobs_real(:, :) = zero
1404    !nfloobs = INT(nfloobs_real)
1405
1406    !nlanobs(:, :) = val_exp
1407    !var_name = 'nlanobs'
1408    !CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1409    !     &              .TRUE., nlanobs_real, 'gather', nbp_glo, index_g)
1410    !IF (ALL(nlanobs_real(:, :) == val_exp)) nlanobs_real(:, :) = zero
1411    !nlanobs = INT(nlanobs_real)
1412
1413    !nlaxobs(:, :) = val_exp
1414    !var_name = 'nlaxobs'
1415    !CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1416    !     &              .TRUE., nlaxobs_real, 'gather', nbp_glo, index_g)
1417    !IF (ALL(nlaxobs_real(:, :) == val_exp)) nlaxobs_real(:, :) = zero
1418    !nlaxobs = INT(nlaxobs_real)
1419
1420    !nmatobs(:, :) = val_exp
1421    !var_name = 'nmatobs'
1422    !CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1423    !     &              .TRUE., nmatobs_real, 'gather', nbp_glo, index_g)
1424    !IF (ALL(nmatobs_real(:, :) == val_exp)) nmatobs_real(:, :) = zero
1425    !nmatobs = INT(nmatobs_real)
1426
1427    !nrecobs(:, :) = val_exp
1428    !var_name = 'nrecobs'
1429    !CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1430    !     &              .TRUE., nrecobs_real, 'gather', nbp_glo, index_g)
1431    !IF (ALL(nrecobs_real(:, :) == val_exp)) nrecobs_real(:, :) = zero
1432    !nrecobs = INT(nrecobs_real)
1433
1434    !nsenobs(:, :) = val_exp
1435    !var_name = 'nsenobs'
1436    !CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1437    !     &              .TRUE., nsenobs_real, 'gather', nbp_glo, index_g)
1438    !IF (ALL(nsenobs_real(:, :) == val_exp)) nsenobs_real(:, :) = zero
1439    !nsenobs = INT(nsenobs_real)
1440
1441
1442    !ndrpobs(:, :) = val_exp
1443    !var_name = 'ndrpobs'
1444    !CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1445    !     &              .TRUE., ndrpobs_real, 'gather', nbp_glo, index_g)
1446    !IF (ALL(ndrpobs_real(:, :) == val_exp)) ndrpobs_real(:, :) = zero
1447    !ndrpobs = INT(ndrpobs_real)
1448
1449
1450
1451
1452    nsendltams(:, :) = val_exp
1453    var_name = 'nsendltams'
1454    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1455         &              .TRUE., nsendltams, 'gather', nbp_glo, index_g)
1456    IF (ALL(nsendltams(:, :) == val_exp)) nsendltams(:, :) = zero
1457
1458    nsendltai(:, :) = val_exp
1459    var_name = 'nsendltai'
1460    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1461         &              .TRUE., nsendltai, 'gather', nbp_glo, index_g)
1462    IF (ALL(nsendltai(:, :) == val_exp)) nsendltai(:, :) = zero
1463
1464    nsenpfeuilverte(:, :) = val_exp
1465    var_name = 'nsenpfeuilverte'
1466    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1467         &              .TRUE., nsenpfeuilverte, 'gather', nbp_glo, index_g)
1468    IF (ALL(nsenpfeuilverte(:, :) == val_exp)) nsenpfeuilverte(:, :) = zero
1469
1470    nsendurvie(:, :) = val_exp
1471    var_name = 'nsendurvie'
1472    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1473         &              .TRUE., nsendurvie, 'gather', nbp_glo, index_g)
1474    IF (ALL(nsendurvie(:, :) == val_exp)) nsendurvie(:, :) = zero
1475
1476    nsenndurvie(:, :) = val_exp
1477    var_name = 'nsenndurvie'
1478    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1479         &              .TRUE., nsenndurvie, 'gather', nbp_glo, index_g)
1480    IF (ALL(nsenndurvie(:, :) == val_exp)) nsenndurvie(:, :) = zero
1481
1482    densiteequiv(:, :) = val_exp
1483    var_name = 'densiteequiv'
1484    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1485         &              .TRUE., densiteequiv, 'gather', nbp_glo, index_g)
1486    IF (ALL(densiteequiv(:, :) == val_exp)) densiteequiv(:, :) = zero
1487
1488    nplt(:, :) = val_exp
1489    var_name = 'nplt'
1490    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1491         &              .TRUE., nplt, 'gather', nbp_glo, index_g)
1492    IF (ALL(nplt(:, :) == val_exp)) nplt(:, :) = zero
1493
1494    tursla(:, :) = val_exp
1495    var_name = 'tursla'
1496    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1497         &              .TRUE., tursla, 'gather', nbp_glo, index_g)
1498    IF (ALL(tursla(:, :) == val_exp)) tursla(:, :) = un
1499
1500    ssla(:, :) = val_exp
1501    var_name = 'ssla'
1502    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1503         &              .TRUE., ssla, 'gather', nbp_glo, index_g)
1504    IF (ALL(ssla(:, :) == val_exp)) ssla(:, :) = zero
1505
1506    pfeuilverte(:, :) = val_exp
1507    var_name = 'pfeuilverte'
1508    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1509         &              .TRUE., pfeuilverte, 'gather', nbp_glo, index_g)
1510    IF (ALL(pfeuilverte(:, :) == val_exp)) pfeuilverte(:, :) = zero
1511
1512    bsenlai(:, :) = val_exp
1513    var_name = 'bsenlai'
1514    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1515         &              .TRUE., bsenlai, 'gather', nbp_glo, index_g)
1516    IF (ALL(bsenlai(:, :) == val_exp)) bsenlai(:, :) = zero
1517
1518    zrac(:, :) = val_exp
1519    var_name = 'zrac'
1520    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1521         &              .TRUE., zrac, 'gather', nbp_glo, index_g)
1522    IF (ALL(zrac(:, :) == val_exp)) zrac(:, :) = zero
1523
1524    nrec(:, :) = val_exp
1525    var_name = 'nrec'
1526    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1527         &              .TRUE., nrec, 'gather', nbp_glo, index_g)
1528    IF (ALL(nrec(:, :) == val_exp)) nrec(:, :) = zero
1529
1530    nlan(:, :) = val_exp
1531    var_name = 'nlan'
1532    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1533         &              .TRUE., nlan, 'gather', nbp_glo, index_g)
1534    IF (ALL(nlan(:, :) == val_exp)) nlan(:, :) = zero
1535
1536    tcult(:, :) = val_exp
1537    var_name = 'tcult'
1538    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1539         &              .TRUE., tcult, 'gather', nbp_glo, index_g)
1540    IF (ALL(tcult(:, :) == val_exp)) tcult(:, :) = zero
1541
1542    udevair(:, :) = val_exp
1543    var_name = 'udevair'
1544    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1545         &              .TRUE., udevair, 'gather', nbp_glo, index_g)
1546    IF (ALL(udevair(:, :) == val_exp)) udevair(:, :) = zero
1547
1548    udevcult(:, :) = val_exp
1549    var_name = 'udevcult'
1550    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1551         &              .TRUE., udevcult, 'gather', nbp_glo, index_g)
1552    IF (ALL(udevcult(:, :) == val_exp)) udevcult(:, :) = zero
1553
1554    ndrp(:, :) = val_exp
1555    var_name = 'ndrp'
1556    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1557         &              .TRUE., ndrp, 'gather', nbp_glo, index_g)
1558    IF (ALL(ndrp(:, :) == val_exp)) ndrp(:, :) = zero
1559
1560    rfvi(:, :) = val_exp
1561    var_name = 'rfvi'
1562    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1563         &              .TRUE., rfvi, 'gather', nbp_glo, index_g)
1564    IF (ALL(rfvi(:, :) == val_exp)) rfvi(:, :) = zero
1565
1566    nlev(:, :) = val_exp
1567    var_name = 'nlev'
1568    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1569         &              .TRUE., nlev, 'gather', nbp_glo, index_g)
1570    IF (ALL(nlev(:, :) == val_exp)) nlev(:, :) = zero
1571
1572    nger(:, :) = val_exp
1573    var_name = 'nger'
1574    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1575         &              .TRUE., nger, 'gather', nbp_glo, index_g)
1576    IF (ALL(nger(:, :) == val_exp)) nger(:, :) = zero
1577
1578    etatvernal_real(:, :) = val_exp
1579    var_name = 'etatvernal'
1580    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1581         &              .TRUE., etatvernal_real, 'gather', nbp_glo, index_g)
1582    IF (ALL(etatvernal_real(:, :) == val_exp)) etatvernal_real(:, :) = zero
1583    WHERE (etatvernal_real(:,:) == un)
1584       etatvernal = .TRUE.
1585    ELSEWHERE
1586       etatvernal = .FALSE.
1587    ENDWHERE
1588   
1589
1590    caljvc(:, :) = val_exp
1591    var_name = 'caljvc'
1592    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1593         &              .TRUE., caljvc, 'gather', nbp_glo, index_g)
1594    IF (ALL(caljvc(:, :) == val_exp)) caljvc(:, :) = zero
1595
1596    rfpi(:, :) = val_exp
1597    var_name = 'rfpi'
1598    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1599         &              .TRUE., rfpi, 'gather', nbp_glo, index_g)
1600    IF (ALL(rfpi(:, :) == val_exp)) rfpi(:, :) = zero
1601
1602    upvt(:, :) = val_exp
1603    var_name = 'upvt'
1604    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1605         &              .TRUE., upvt, 'gather', nbp_glo, index_g)
1606    IF (ALL(upvt(:, :) == val_exp)) upvt(:, :) = zero
1607
1608    utp(:, :) = val_exp
1609    var_name = 'utp'
1610    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1611         &              .TRUE., utp, 'gather', nbp_glo, index_g)
1612    IF (ALL(utp(:, :) == val_exp)) utp(:, :) = zero
1613
1614    somcour(:, :) = val_exp
1615    var_name = 'somcour'
1616    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1617         &              .TRUE., somcour, 'gather', nbp_glo, index_g)
1618    IF (ALL(somcour(:, :) == val_exp)) somcour(:, :) = zero
1619
1620    somcourdrp(:, :) = val_exp
1621    var_name = 'somcourdrp'
1622    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1623         &              .TRUE., somcourdrp, 'gather', nbp_glo, index_g)
1624    IF (ALL(somcourdrp(:, :) == val_exp)) somcourdrp(:, :) = zero
1625
1626    somcourutp(:, :) = val_exp
1627    var_name = 'somcourutp'
1628    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1629         &              .TRUE., somcourutp, 'gather', nbp_glo, index_g)
1630    IF (ALL(somcourutp(:, :) == val_exp)) somcourutp(:, :) = zero
1631
1632    tdevelop(:, :) = val_exp
1633    var_name = 'tdevelop'
1634    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1635         &              .TRUE., tdevelop, 'gather', nbp_glo, index_g)
1636    IF (ALL(tdevelop(:, :) == val_exp)) tdevelop(:, :) = zero
1637
1638    somtemp(:, :) = val_exp
1639    var_name = 'somtemp'
1640    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1641         &              .TRUE., somtemp, 'gather', nbp_glo, index_g)
1642    IF (ALL(somtemp(:, :) == val_exp)) somtemp(:, :) = zero
1643
1644    somcourfauche(:, :) = val_exp
1645    var_name = 'somcourfauche'
1646    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1647         &              .TRUE., somcourfauche, 'gather', nbp_glo, index_g)
1648    IF (ALL(somcourfauche(:, :) == val_exp)) somcourfauche(:, :) = zero
1649
1650    stpltger(:, :) = val_exp
1651    var_name = 'stpltger'
1652    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1653         &              .TRUE., stpltger, 'gather', nbp_glo, index_g)
1654    IF (ALL(stpltger(:, :) == val_exp)) THEN
1655       DO j= 1, nvm
1656          stpltger(:, j) = SP_stpltger(j)
1657       ENDDO
1658    ENDIF
1659
1660    R_stlaxsen(:, :) = val_exp
1661    var_name = 'R_stlaxsen'
1662    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1663         &              .TRUE., R_stlaxsen, 'gather', nbp_glo, index_g)
1664    IF (ALL(R_stlaxsen(:, :) == val_exp)) THEN
1665       DO j= 1, nvm
1666          R_stlaxsen(:, j) = SP_stlaxsen(j)
1667       ENDDO
1668    ENDIF
1669
1670
1671    R_stamflax(:, :) = val_exp
1672    var_name = 'R_stamflax'
1673    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1674         &              .TRUE., R_stamflax, 'gather', nbp_glo, index_g)
1675    IF (ALL(R_stamflax(:, :) == val_exp)) THEN
1676       DO j= 1, nvm
1677          R_stamflax(:, j) = SP_stamflax(j)
1678       ENDDO
1679    ENDIF
1680
1681    R_stsenlan(:, :) = val_exp
1682    var_name = 'R_stsenlan'
1683    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1684         &              .TRUE., R_stsenlan, 'gather', nbp_glo, index_g)
1685    IF (ALL(R_stsenlan(:, :) == val_exp)) THEN
1686       DO j= 1, nvm
1687          R_stsenlan(:, j) = SP_stsenlan(j)
1688       ENDDO
1689    ENDIF
1690
1691    stlevflo(:, :) = val_exp
1692    var_name = 'stlevflo'
1693    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1694         &              .TRUE., stlevflo, 'gather', nbp_glo, index_g)
1695    IF (ALL(stlevflo(:, :) == val_exp)) THEN
1696       DO j= 1, nvm
1697          stlevflo(:, j) = SP_stlevdrp(j) - SP_stflodrp(j)
1698       ENDDO
1699    ENDIF
1700
1701    nflo(:, :) = val_exp
1702    var_name = 'nflo'
1703    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1704         &              .TRUE., nflo, 'gather', nbp_glo, index_g)
1705    IF (ALL(nflo(:, :) == val_exp)) nflo(:, :) = zero
1706
1707    R_stlevdrp(:, :) = val_exp
1708    var_name = 'R_stlevdrp'
1709    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1710         &              .TRUE., R_stlevdrp, 'gather', nbp_glo, index_g)
1711    IF (ALL(R_stlevdrp(:, :) == val_exp)) THEN
1712       DO j= 1, nvm
1713          R_stlevdrp(:, j) = SP_stlevdrp(j)
1714       ENDDO
1715    ENDIF
1716
1717    R_stflodrp(:, :) = val_exp
1718    var_name = 'R_stflodrp'
1719    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1720         &              .TRUE., R_stflodrp, 'gather', nbp_glo, index_g)
1721    IF (ALL(R_stflodrp(:, :) == val_exp)) THEN
1722       DO j= 1, nvm
1723          R_stflodrp(:, j) = SP_stflodrp(j)
1724       ENDDO
1725    ENDIF
1726
1727    R_stdrpmat(:, :) = val_exp
1728    var_name = 'R_stdrpmat'
1729    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1730         &              .TRUE., R_stdrpmat, 'gather', nbp_glo, index_g)
1731    IF (ALL(R_stdrpmat(:, :) == val_exp)) THEN
1732       DO j= 1, nvm
1733          R_stdrpmat(:, j) = SP_stdrpmat(j)
1734       ENDDO
1735    ENDIF
1736
1737    nmat(:, :) = val_exp
1738    var_name = 'nmat'
1739    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1740         &              .TRUE., nmat, 'gather', nbp_glo, index_g)
1741    IF (ALL(nmat(:, :) == val_exp)) nmat(:, :) = zero
1742
1743    nlax(:, :) = val_exp
1744    var_name = 'nlax'
1745    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1746         &              .TRUE., nlax, 'gather', nbp_glo, index_g)
1747    IF (ALL(nlax(:, :) == val_exp)) nlax(:, :) = zero
1748
1749    nrecbutoir(:, :) = val_exp
1750    var_name = 'nrecbutoir'
1751    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1752         &              .TRUE., nrecbutoir, 'gather', nbp_glo, index_g)
1753    IF (ALL(nrecbutoir(:, :) == val_exp)) nrecbutoir(:, :) = 999.0
1754
1755    group(:, :) = val_exp
1756    var_name = 'group'
1757    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1758         &              .TRUE., group, 'gather', nbp_glo, index_g)
1759    IF (ALL(group(:, :) == val_exp)) group(:, :) = zero
1760
1761    ndebdes(:, :) = val_exp
1762    var_name = 'ndebdes'
1763    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1764         &              .TRUE., ndebdes, 'gather', nbp_glo, index_g)
1765    IF (ALL(ndebdes(:, :) == val_exp)) ndebdes(:, :) = zero
1766
1767    R_stdrpdes(:, :) = val_exp
1768    var_name = 'R_stdrpdes'
1769    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1770         &              .TRUE., R_stdrpdes, 'gather', nbp_glo, index_g)
1771    IF (ALL(R_stdrpdes(:, :) == val_exp)) THEN
1772       DO j= 1, nvm
1773          R_stdrpdes(:, j) = SP_stdrpdes(j)
1774       ENDDO
1775    ENDIF
1776
1777    densite(:, :) = val_exp
1778    var_name = 'densite'
1779    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1780         &              .TRUE., densite, 'gather', nbp_glo, index_g)
1781    IF (ALL(densite(:, :) == val_exp)) densite(:, :) = zero
1782
1783    densitelev(:, :) = val_exp
1784    var_name = 'densitelev'
1785    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1786         &              .TRUE., densitelev, 'gather', nbp_glo, index_g)
1787    IF (ALL(densitelev(:, :) == val_exp)) densitelev(:, :) = zero
1788
1789    coeflev(:, :) = val_exp
1790    var_name = 'coeflev'
1791    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1792         &              .TRUE., coeflev, 'gather', nbp_glo, index_g)
1793    IF (ALL(coeflev(:, :) == val_exp)) coeflev(:, :) = un
1794
1795    densiteger(:, :) = val_exp
1796    var_name = 'densiteger'
1797    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1798         &              .TRUE., densiteger, 'gather', nbp_glo, index_g)
1799    IF (ALL(densiteger(:, :) == val_exp)) densiteger(:, :) = zero
1800
1801    somelong(:, :) = val_exp
1802    var_name = 'somelong'
1803    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1804         &              .TRUE., somelong, 'gather', nbp_glo, index_g)
1805    IF (ALL(somelong(:, :) == val_exp)) somelong(:, :) = zero
1806
1807    somger(:, :) = val_exp
1808    var_name = 'somger'
1809    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1810         &              .TRUE., somger, 'gather', nbp_glo, index_g)
1811    IF (ALL(somger(:, :) == val_exp)) somger(:, :) = zero
1812
1813    humectation_real(:, :) = val_exp
1814    var_name = 'humectation'
1815    CALL restget_p (rest_id_stomate, var_name, nbp_glo,   nvm, 1, itime, &
1816         &                .TRUE., humectation_real, 'gather', nbp_glo, index_g)
1817    IF (ALL(humectation_real(:, :) == val_exp)) humectation_real(:, :) = zero
1818    WHERE (humectation_real(:, :) == un)
1819       humectation = .TRUE.
1820    ELSEWHERE
1821       humectation = .FALSE.
1822    ENDWHERE
1823
1824    nbjhumec(:, :) = val_exp
1825    var_name = 'nbjhumec'
1826    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1827         &              .TRUE., nbjhumec, 'gather', nbp_glo, index_g)
1828    IF (ALL(nbjhumec(:, :) == val_exp)) nbjhumec(:, :) = zero
1829
1830    somtemphumec(:, :) = val_exp
1831    var_name = 'somtemphumec'
1832    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1833         &              .TRUE., somtemphumec, 'gather', nbp_glo, index_g)
1834    IF (ALL(somtemphumec(:, :) == val_exp)) somtemphumec(:, :) = zero
1835
1836    stpltlev(:, :) = val_exp
1837    var_name = 'stpltlev'
1838    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1839         &              .TRUE., stpltlev, 'gather', nbp_glo, index_g)
1840    IF (ALL(stpltlev(:, :) == val_exp)) stpltlev(:, :) = zero
1841
1842    namf(:, :) = val_exp
1843    var_name = 'namf'
1844    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1845         &              .TRUE., namf, 'gather', nbp_glo, index_g)
1846    IF (ALL(namf(:, :) == val_exp)) namf(:, :) = zero
1847
1848    stmatrec(:, :) = val_exp
1849    var_name = 'stmatrec'
1850    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1851         &              .TRUE., stmatrec, 'gather', nbp_glo, index_g)
1852    IF (ALL(stmatrec(:, :) == val_exp)) stmatrec(:, :) = zero
1853
1854    tustress(:, :) = val_exp
1855    var_name = 'tustress'
1856    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1857         &              .TRUE., tustress, 'gather', nbp_glo, index_g)
1858    IF (ALL(tustress(:, :) == val_exp)) tustress(:, :) = 1.0
1859
1860    lai(:, :) = val_exp
1861    var_name = 'lai'
1862    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1863         &              .TRUE., lai, 'gather', nbp_glo, index_g)
1864    IF (ALL(lai(:, :) == val_exp)) lai(:, :) = zero
1865
1866    somfeuille(:, :) = val_exp
1867    var_name = 'somfeuille'
1868    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1869         &              .TRUE., somfeuille, 'gather', nbp_glo, index_g)
1870    IF (ALL(somfeuille(:, :) == val_exp)) somfeuille(:, :) = zero
1871
1872    pdlai(:, :) = val_exp
1873    var_name = 'pdlai'
1874    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1875         &              .TRUE., pdlai, 'gather', nbp_glo, index_g)
1876    IF (ALL(pdlai(:, :) == val_exp)) pdlai(:, :) = zero
1877
1878    nbfeuille(:, :) = val_exp
1879    var_name = 'nbfeuille'
1880    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1881         &              .TRUE., nbfeuille, 'gather', nbp_glo, index_g)
1882    IF (ALL(nbfeuille(:, :) == val_exp)) nbfeuille(:, :) = zero
1883
1884    reajust(:, :) = val_exp
1885    var_name = 'reajust'
1886    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1887         &              .TRUE., reajust, 'gather', nbp_glo, index_g)
1888    IF (ALL(reajust(:, :) == val_exp)) reajust(:, :) = zero
1889
1890    ulai(:, :) = val_exp
1891    var_name = 'ulai'
1892    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1893         &              .TRUE., ulai, 'gather', nbp_glo, index_g)
1894    IF (ALL(ulai(:, :) == val_exp)) ulai(:, :) = zero
1895
1896    pdulai(:, :) = val_exp
1897    var_name = 'pdulai'
1898    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1899         &              .TRUE., pdulai, 'gather', nbp_glo, index_g)
1900    IF (ALL(pdulai(:, :) == val_exp)) pdulai(:, :) = zero
1901
1902    efdensite(:, :) = val_exp
1903    var_name = 'efdensite'
1904    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1905         &              .TRUE., efdensite, 'gather', nbp_glo, index_g)
1906    IF (ALL(efdensite(:, :) == val_exp)) efdensite(:, :) = zero
1907
1908    tempeff(:, :) = val_exp
1909    var_name = 'tempeff'
1910    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1911         &              .TRUE., tempeff, 'gather', nbp_glo, index_g)
1912    IF (ALL(tempeff(:, :) == val_exp)) tempeff(:, :) = zero
1913
1914    nstopfeuille(:, :) = val_exp
1915    var_name = 'nstopfeuille'
1916    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1917         &              .TRUE., nstopfeuille, 'gather', nbp_glo, index_g)
1918    IF (ALL(nstopfeuille(:, :) == val_exp)) nstopfeuille(:, :) = zero
1919
1920    deltai(:, :) = val_exp
1921    var_name = 'deltai'
1922    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1923         &              .TRUE., deltai, 'gather', nbp_glo, index_g)
1924    IF (ALL(deltai(:, :) == val_exp)) deltai(:, :) = zero
1925
1926    vmax(:, :) = val_exp
1927    var_name = 'vmax'
1928    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1929         &              .TRUE., vmax, 'gather', nbp_glo, index_g)
1930    IF (ALL(vmax(:, :) == val_exp)) vmax(:, :) = zero
1931
1932    nsen(:, :) = val_exp
1933    var_name = 'nsen'
1934    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1935         &              .TRUE., nsen, 'gather', nbp_glo, index_g)
1936    IF (ALL(nsen(:, :) == val_exp)) nsen(:, :) = zero
1937
1938
1939    laisen(:, :) = val_exp
1940    var_name = 'laisen'
1941    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1942         &              .TRUE., laisen, 'gather', nbp_glo, index_g)
1943    IF (ALL(laisen(:, :) == val_exp)) laisen(:, :) = zero
1944
1945    pdlaisen(:, :) = val_exp
1946    var_name = 'pdlaisen'
1947    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1948         &              .TRUE., pdlaisen, 'gather', nbp_glo, index_g)
1949    IF (ALL(pdlaisen(:, :) == val_exp)) pdlaisen(:, :) = zero
1950
1951    dltaisenat(:, :) = val_exp
1952    var_name = 'dltaisenat'
1953    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1954         &              .TRUE., dltaisenat, 'gather', nbp_glo, index_g)
1955    IF (ALL(dltaisenat(:, :) == val_exp)) dltaisenat(:, :) = zero
1956
1957    nsencour(:, :) = val_exp
1958    var_name = 'nsencour'
1959    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1960         &              .TRUE., nsencour, 'gather', nbp_glo, index_g)
1961    IF (ALL(nsencour(:, :) == val_exp)) nsencour(:, :) = zero
1962    nsencour = INT(nsencour)
1963
1964    dltamsen(:, :) = val_exp
1965    var_name = 'dltamsen'
1966    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1967         &              .TRUE., dltamsen, 'gather', nbp_glo, index_g)
1968    IF (ALL(dltamsen(:, :) == val_exp)) dltamsen(:, :) = zero
1969
1970    dltaisen(:, :) = val_exp
1971    var_name = 'dltaisen'
1972    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1973         &              .TRUE., dltaisen, 'gather', nbp_glo, index_g)
1974    IF (ALL(dltaisen(:, :) == val_exp)) dltaisen(:, :) = zero
1975
1976    fgellev(:, :) = val_exp
1977    var_name = 'fgellev'
1978    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1979         &              .TRUE., fgellev, 'gather', nbp_glo, index_g)
1980    IF (ALL(fgellev(:, :) == val_exp)) fgellev(:, :) = un
1981
1982    gelee_real(:, :) = val_exp
1983    var_name = 'gelee'
1984    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1985         &              .TRUE., gelee_real, 'gather', nbp_glo, index_g)
1986    IF (ALL(gelee_real(:, :) == val_exp)) gelee_real(:, :) = zero
1987    WHERE (gelee_real(:,:) == un)
1988       gelee = .TRUE.
1989    ELSEWHERE
1990       gelee = .FALSE.
1991    ENDWHERE
1992
1993    fstressgel(:, :) = val_exp
1994    var_name = 'fstressgel'
1995    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
1996         &              .TRUE., fstressgel, 'gather', nbp_glo, index_g)
1997    IF (ALL(fstressgel(:, :) == val_exp)) fstressgel(:, :) = zero
1998
1999    R_stlevamf(:, :) = val_exp
2000    var_name = 'R_stlevamf'
2001    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2002         &              .TRUE., R_stlevamf, 'gather', nbp_glo, index_g)
2003    IF (ALL(R_stlevamf(:, :) == val_exp)) THEN
2004       DO j= 1, nvm
2005          R_stlevamf(:, j) = SP_stlevamf(j)
2006       ENDDO
2007    ENDIF
2008
2009    dernier_n(:, :) = val_exp
2010    var_name = 'dernier_n'
2011    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2012         &              .TRUE., dernier_n, 'gather', nbp_glo, index_g)
2013    IF (ALL(dernier_n(:, :) == val_exp)) dernier_n(:, :) = zero
2014
2015    durvieI(:, :) = val_exp
2016    var_name = 'durvieI'
2017    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2018         &              .TRUE., durvieI, 'gather', nbp_glo, index_g)
2019    IF (ALL(durvieI(:, :) == val_exp)) durvieI(:, :) = zero
2020
2021    durvie(:, :) = val_exp
2022    var_name = 'durvie'
2023    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2024         &              .TRUE., durvie, 'gather', nbp_glo, index_g)
2025    IF (ALL(durvie(:, :) == val_exp)) durvie(:, :) = zero
2026
2027    ndebsen(:, :) = val_exp
2028    var_name = 'ndebsen'
2029    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2030         &              .TRUE., ndebsen, 'gather', nbp_glo, index_g)
2031    IF (ALL(ndebsen(:, :) == val_exp)) ndebsen(:, :) = zero
2032
2033    somsenreste(:, :) = val_exp
2034    var_name = 'somsenreste'
2035    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2036         &              .TRUE., somsenreste, 'gather', nbp_glo, index_g)
2037    IF (ALL(somsenreste(:, :) == val_exp)) somsenreste(:, :) = zero
2038
2039    humrel(:, :) = val_exp
2040    var_name = 'humrel'
2041    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2042         &              .TRUE., humrel, 'gather', nbp_glo, index_g)
2043    IF (ALL(humrel(:, :) == val_exp)) humrel(:, :) = zero
2044
2045    swfac(:, :) = val_exp
2046    var_name = 'swfac'
2047    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2048         &              .TRUE., swfac, 'gather', nbp_glo, index_g)
2049    IF (ALL(swfac(:, :) == val_exp)) swfac(:, :) = un
2050
2051    turfac(:, :) = val_exp
2052    var_name = 'turfac'
2053    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2054         &              .TRUE., turfac, 'gather', nbp_glo, index_g)
2055    IF (ALL(turfac(:, :) == val_exp)) turfac(:, :) = un
2056
2057    senfac(:, :) = val_exp
2058    var_name = 'senfac'
2059    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2060         &              .TRUE., senfac, 'gather', nbp_glo, index_g)
2061    IF (ALL(senfac(:, :) == val_exp)) senfac(:, :) = un
2062 
2063
2064    mafeuiljaune(:, :) = val_exp
2065    var_name = 'mafeuiljaune'
2066    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2067         &              .TRUE., mafeuiljaune, 'gather', nbp_glo, index_g)
2068    IF (ALL(mafeuiljaune(:, :) == val_exp)) mafeuiljaune(:, :) = un
2069   
2070    msneojaune(:, :) = val_exp
2071    var_name = 'msneojaune'
2072    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2073         &              .TRUE., msneojaune, 'gather', nbp_glo, index_g)
2074    IF (ALL(msneojaune(:, :) == val_exp)) msneojaune(:, :) = un
2075
2076    box_ndays(:,:,:) = 0
2077    box_lai(:,:,:) = 0.
2078    box_lairem(:,:,:) = 0.
2079    box_tdev(:,:,:) = 0.
2080    box_biom(:,:,:) = 0.
2081    box_biomrem(:,:,:) = 0.
2082    box_durage(:,:,:) = 0.
2083    box_somsenbase(:,:,:) = 0.
2084    CALL restget_p(rest_id_stomate, 'box_ndays', nbp_glo, nvm,  nboxmax, itime, &
2085             &              .TRUE., box_ndays, 'gather', nbp_glo, index_g)
2086    IF (ALL(box_ndays == val_exp)) box_ndays = 0
2087
2088    CALL restget_p(rest_id_stomate, 'box_lai', nbp_glo, nvm,   nboxmax, itime, &
2089            &               .TRUE., box_lai, 'gather', nbp_glo, index_g)
2090    IF (ALL(box_lai == val_exp)) box_lai = 0.
2091
2092    CALL restget_p(rest_id_stomate, 'box_lairem', nbp_glo, nvm,   nboxmax, itime, &
2093            &               .TRUE., box_lairem, 'gather', nbp_glo, index_g)
2094    IF (ALL(box_lairem == val_exp)) box_lairem = 0.
2095
2096    CALL restget_p(rest_id_stomate, 'box_tdev', nbp_glo, nvm,   nboxmax, itime, &
2097            &               .TRUE., box_tdev, 'gather', nbp_glo, index_g)
2098    IF (ALL(box_tdev == val_exp)) box_tdev = 0.
2099
2100    CALL restget_p(rest_id_stomate, 'box_biom', nbp_glo, nvm,   nboxmax, itime, &
2101            &               .TRUE., box_biom, 'gather', nbp_glo, index_g)
2102    IF (ALL(box_biom == val_exp)) box_biom = 0.
2103
2104    CALL restget_p(rest_id_stomate, 'box_biomrem', nbp_glo, nvm,   nboxmax, itime, &
2105            &               .TRUE., box_biomrem, 'gather', nbp_glo, index_g)
2106    IF (ALL(box_biomrem == val_exp)) box_biomrem = 0.
2107
2108    CALL restget_p(rest_id_stomate, 'box_durage', nbp_glo, nvm,   nboxmax, itime, &
2109            &               .TRUE., box_durage, 'gather', nbp_glo, index_g)
2110    IF (ALL(box_durage == val_exp)) box_durage = 0.
2111
2112    CALL restget_p(rest_id_stomate, 'box_somsenbase', nbp_glo, nvm,   nboxmax, itime, &
2113            &               .TRUE., box_somsenbase, 'gather', nbp_glo, index_g)
2114    IF (ALL(box_somsenbase == val_exp)) box_somsenbase = 0.
2115 
2116    ! STICS:: CARBON ALLOCATION
2117   
2118   
2119    v_dltams(:,:,:) = val_exp
2120    CALL restget_p (rest_id_stomate, 'v_dltams', nbp_glo, nvm  , vlength, itime, &
2121            &                .TRUE., v_dltams, 'gather', nbp_glo, index_g)
2122    IF (ALL(v_dltams == val_exp))  v_dltams = zero
2123
2124    fgelflo(:, :) = val_exp
2125    var_name = 'fgelflo'
2126    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2127         &              .TRUE., fgelflo, 'gather', nbp_glo, index_g)
2128    IF (ALL(fgelflo(:, :) == val_exp)) fgelflo(:, :) = un
2129
2130    pdircarb(:, :) = val_exp
2131    var_name = 'pdircarb'
2132    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2133         &              .TRUE., pdircarb, 'gather', nbp_glo, index_g)
2134    IF (ALL(pdircarb(:, :) == val_exp)) pdircarb(:, :) = zero
2135
2136    ircarb(:, :) = val_exp
2137    var_name = 'ircarb'
2138    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2139         &              .TRUE., ircarb, 'gather', nbp_glo, index_g)
2140    IF (ALL(ircarb(:, :) == val_exp)) ircarb(:, :) = zero
2141
2142    nbgrains(:, :) = val_exp
2143    var_name = 'nbgrains'
2144    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2145         &              .TRUE., nbgrains, 'gather', nbp_glo, index_g)
2146    IF (ALL(nbgrains(:, :) == val_exp)) nbgrains(:, :) = zero
2147
2148    pgrain(:, :) = val_exp
2149    var_name = 'pgrain'
2150    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2151         &              .TRUE., pgrain, 'gather', nbp_glo, index_g)
2152    IF (ALL(pgrain(:, :) == val_exp)) pgrain(:, :) = zero
2153
2154    vitmoy(:, :) = val_exp
2155    var_name = 'vitmoy'
2156    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2157         &              .TRUE., vitmoy, 'gather', nbp_glo, index_g)
2158    IF (ALL(vitmoy(:, :) == val_exp)) vitmoy(:, :) = zero
2159
2160    nbgraingel(:, :) = val_exp
2161    var_name = 'nbgraingel'
2162    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2163         &              .TRUE., nbgraingel, 'gather', nbp_glo, index_g)
2164    IF (ALL(nbgraingel(:, :) == val_exp)) nbgraingel(:, :) = zero
2165
2166    pgraingel(:, :) = val_exp
2167    var_name = 'pgraingel'
2168    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2169         &              .TRUE., pgraingel, 'gather', nbp_glo, index_g)
2170    IF (ALL(pgraingel(:, :) == val_exp)) pgraingel(:, :) = zero
2171
2172    dltags(:, :) = val_exp
2173    var_name = 'dltags'
2174    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2175         &              .TRUE., dltags, 'gather', nbp_glo, index_g)
2176    IF (ALL(dltags(:, :) == val_exp)) dltags(:, :) = zero
2177
2178    ftempremp(:, :) = val_exp
2179    var_name = 'ftempremp'
2180    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2181         &              .TRUE., ftempremp, 'gather', nbp_glo, index_g)
2182    IF (ALL(ftempremp(:, :) == val_exp)) ftempremp(:, :) = zero
2183
2184    magrain(:, :) = val_exp
2185    var_name = 'magrain'
2186    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2187         &              .TRUE., magrain, 'gather', nbp_glo, index_g)
2188    IF (ALL(magrain(:, :) == val_exp)) magrain(:, :) = zero
2189
2190    pdmagrain(:, :) = val_exp
2191    var_name = 'pdmagrain'
2192    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2193         &              .TRUE., pdmagrain, 'gather', nbp_glo, index_g)
2194    IF (ALL(pdmagrain(:, :) == val_exp)) pdmagrain(:, :) = zero
2195
2196    nbj0remp(:, :) = val_exp
2197    var_name = 'nbj0remp'
2198    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2199         &              .TRUE., nbj0remp, 'gather', nbp_glo, index_g)
2200    IF (ALL(nbj0remp(:, :) == val_exp)) nbj0remp(:, :) = zero
2201
2202   
2203    !nbj0remp(:, :) = val_exp
2204    !var_name = 'nbj0remp'
2205    !CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2206    !     &              .TRUE., nbj0remp, 'gather', nbp_glo, index_g)
2207    !IF (ALL(nbj0remp(:, :) == val_exp)) nbj0remp(:, :) = zero
2208
2209    pdsfruittot(:, :) = val_exp
2210    var_name = 'pdsfruittot'
2211    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2212         &              .TRUE., pdsfruittot, 'gather', nbp_glo, index_g)
2213    IF (ALL(pdsfruittot(:, :) == val_exp)) pdsfruittot(:, :) = zero
2214
2215    repracmax(:, :) = val_exp
2216    var_name = 'repracmax'
2217    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2218         &              .TRUE., repracmax, 'gather', nbp_glo, index_g)
2219    IF (ALL(repracmax(:, :) == val_exp)) repracmax(:, :) = zero
2220
2221    repracmin(:, :) = val_exp
2222    var_name = 'repracmin'
2223    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2224         &              .TRUE., repracmin, 'gather', nbp_glo, index_g)
2225    IF (ALL(repracmin(:, :) == val_exp)) repracmin(:, :) = zero
2226
2227    kreprac(:, :) = val_exp
2228    var_name = 'kreprac'
2229    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2230         &              .TRUE., kreprac, 'gather', nbp_glo, index_g)
2231    IF (ALL(kreprac(:, :) == val_exp)) kreprac(:, :) = zero
2232
2233    somtemprac(:, :) = val_exp
2234    var_name = 'somtemprac'
2235    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2236         &              .TRUE., somtemprac, 'gather', nbp_glo, index_g)
2237    IF (ALL(somtemprac(:, :) == val_exp)) somtemprac(:, :) = zero
2238
2239    urac(:, :) = val_exp
2240    var_name = 'urac'
2241    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2242         &              .TRUE., urac, 'gather', nbp_glo, index_g)
2243    IF (ALL(urac(:, :) == val_exp)) urac(:, :) = zero
2244
2245    reprac(:, :) = val_exp
2246    var_name = 'reprac'
2247    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2248         &              .TRUE., reprac, 'gather', nbp_glo, index_g)
2249    IF (ALL(reprac(:, :) == val_exp)) reprac(:, :) = zero
2250
2251    c_reserve(:, :) = val_exp
2252    var_name = 'c_reserve'
2253    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2254         &              .TRUE., c_reserve, 'gather', nbp_glo, index_g)
2255    IF (ALL(c_reserve(:, :) == val_exp)) c_reserve(:, :) = zero
2256
2257
2258    nstoprac(:, :) = val_exp
2259    var_name = 'nstoprac'
2260    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2261         &              .TRUE., nstoprac, 'gather', nbp_glo, index_g)
2262    IF (ALL(nstoprac(:, :) == val_exp)) nstoprac(:, :) = zero
2263
2264
2265    var_name = 'c_leafb'
2266    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2267         &              .TRUE., c_leafb, 'gather', nbp_glo, index_g)
2268    IF (ALL(c_leafb(:, :) == val_exp)) c_leafb(:, :) = zero
2269
2270    gslen(:, :) = val_exp
2271    var_name = 'gslen'
2272    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2273         &              .TRUE., gslen, 'gather', nbp_glo, index_g)
2274    IF (ALL(gslen(:, :) == val_exp)) gslen(:, :) = zero
2275
2276    drylen(:, :) = val_exp
2277    var_name = 'drylen'
2278    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, &
2279         &              .TRUE., drylen, 'gather', nbp_glo, index_g)
2280    IF (ALL(drylen(:, :) == val_exp)) drylen(:, :) = zero
2281!!!!! xuhui
2282 
2283    IF (printlev >= 4) WRITE(numout,*) 'Leaving readstart'
2284    !-----------------------
2285  END SUBROUTINE sticslai_io_readstart
2286  !-
2287  !===
2288  !-
2289END MODULE sticslai_io
2290
Note: See TracBrowser for help on using the repository browser.