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