1 | !> Module Stics |
---|
2 | !> - Description : Stics main module. |
---|
3 | !! This module contains the main subroutine of LAIdev for calculating the LAI of crops |
---|
4 | !! This module is built by XCW. // 06/06/2013 |
---|
5 | !> |
---|
6 | |
---|
7 | module Stics |
---|
8 | |
---|
9 | USE ioipsl ! USE the tools of ioipsl |
---|
10 | USE grid ! USE the module regarding the grid |
---|
11 | |
---|
12 | |
---|
13 | IMPLICIT NONE |
---|
14 | PUBLIC driver_stics |
---|
15 | |
---|
16 | !variable (parameters) declaration |
---|
17 | INTEGER(i_std), PARAMETER :: crop_nbjmax = 300 !!Maximum days of a crop cycle simulation |
---|
18 | |
---|
19 | CHARACTER(len=3) :: P_codeplante |
---|
20 | CHARACTER(len=3) :: P_stade0 |
---|
21 | INTEGER(i_std) :: P_iplt0 |
---|
22 | INTEGER(i_std) :: P_iwater |
---|
23 | CHARACTER(len=7) :: P_codesimul |
---|
24 | INTEGER(i_std) :: P_codelaitr |
---|
25 | REAL(r_std) :: P_slamax |
---|
26 | REAL(r_std) :: P_slamin |
---|
27 | INTEGER(i_std) :: P_codeperenne !! annual crop (1) or perennial crop (2) |
---|
28 | INTEGER(i_std) :: P_codcueille !! harvest option: cutting (1) or picking (2) |
---|
29 | INTEGER(i_std) :: P_codegdh !! hourly (1) or daily (2) calculation of development unit |
---|
30 | INTEGER(i_std) :: P_codetemp !! |
---|
31 | INTEGER(i_std) :: P_coderetflo |
---|
32 | INTEGER(i_std) :: P_codeinnact |
---|
33 | INTEGER(i_std) :: P_codeh2oact |
---|
34 | REAL(r_std) :: P_stressdev |
---|
35 | REAL(r_std) :: P_innlai |
---|
36 | REAL(r_std) :: P_innsenes |
---|
37 | INTEGER(i_std) :: P_codebfroid |
---|
38 | INTEGER(i_std) :: P_codephot |
---|
39 | INTEGER(i_std) :: P_codedormance |
---|
40 | INTEGER(i_std) :: P_codefauche !! option of cut modes for forage crops: yes (1) no (2) |
---|
41 | INTEGER(i_std) :: P_codetempfauche !! option of the reference temperature to compute cutting sum of temperatures : upvt (1) udevair (2) |
---|
42 | INTEGER(i_std) :: P_codlainet |
---|
43 | INTEGER(i_std) :: P_codeindetermin |
---|
44 | INTEGER(i_std) :: P_codeinitprec |
---|
45 | INTEGER(i_std) :: P_culturean |
---|
46 | REAL(r_std) :: P_jvc |
---|
47 | REAL(r_std) :: P_tfroid |
---|
48 | REAL(r_std) :: P_ampfroid |
---|
49 | REAL(r_std) :: P_jvcmini |
---|
50 | REAL(r_std) :: P_tgmin |
---|
51 | REAL(r_std) :: P_stpltger |
---|
52 | REAL(r_std) :: P_profsem |
---|
53 | REAL(r_std) :: P_propjgermin !! minimal proportion of the duration P_nbjgerlim when the temperature is higher than the temperature threshold P_Tdmax |
---|
54 | REAL(r_std) :: P_tdmax |
---|
55 | INTEGER(i_std) :: P_nbjgerlim !! Threshold number of day after grain imbibition without germination lack // days |
---|
56 | REAL(r_std) :: P_densitesem |
---|
57 | REAL(r_std) :: P_vigueurbat !! indicator of plant vigor allowing to emerge through the crust // between 0 and 1 // |
---|
58 | INTEGER(i_std) :: P_codepluiepoquet !! option to replace rainfall by irrigation at poquet depth in the case of poquet sowing // code 1/2 |
---|
59 | INTEGER(i_std) :: P_codehypo |
---|
60 | REAL(r_std) :: P_elmax |
---|
61 | REAL(r_std) :: P_belong |
---|
62 | REAL(r_std) :: P_celong |
---|
63 | INTEGER(i_std) :: P_nlevlim1 !! number of days after germination decreasing the emerged plants if emergence has not occur // days |
---|
64 | INTEGER(i_std) :: P_nlevlim2 !! number of days after germination after which the emerged plants are null // days |
---|
65 | INTEGER(i_std) :: P_codrecolte !! harvest mode : all the plant (1) or just the fruits (2) |
---|
66 | INTEGER(i_std) :: P_variete !! variety number in the technical file // SD |
---|
67 | INTEGER(i_std) :: P_codegermin !! option of simulation of a germination phase or a delay at the beginning of the crop (1) or direct starting (2) |
---|
68 | |
---|
69 | INTEGER(i_std) :: codeulaivernal |
---|
70 | REAL(r_std) :: P_swfacmin |
---|
71 | |
---|
72 | ! STICS:: LAI CALCULATION |
---|
73 | REAL(r_std) :: P_laiplantule |
---|
74 | REAL(r_std) :: P_vlaimax |
---|
75 | REAL(r_std) :: P_stlevamf |
---|
76 | REAL(r_std) :: P_stamflax |
---|
77 | REAL(r_std) :: P_udlaimax |
---|
78 | REAL(r_std) :: P_laicomp |
---|
79 | REAL(r_std) :: P_adens !! Interplant competition parameter |
---|
80 | REAL(r_std) :: P_bdens |
---|
81 | REAL(r_std) :: P_tcxstop |
---|
82 | REAL(r_std) :: P_tcmax |
---|
83 | REAL(r_std) :: P_tcmin |
---|
84 | REAL(r_std) :: P_dlaimax |
---|
85 | REAL(r_std) :: P_dlaimin |
---|
86 | REAL(r_std) :: P_pentlaimax |
---|
87 | REAL(r_std) :: P_tigefeuil !! stem (structural part)/leaf proportion // SD |
---|
88 | |
---|
89 | REAL(r_std) :: P_stlaxsen |
---|
90 | REAL(r_std) :: P_stsenlan !! Interplant competition parameter |
---|
91 | REAL(r_std) :: P_stlevdrp |
---|
92 | REAL(r_std) :: P_stflodrp |
---|
93 | REAL(r_std) :: P_stdrpmat |
---|
94 | REAL(r_std) :: P_stdrpdes |
---|
95 | REAL(r_std) :: P_phyllotherme |
---|
96 | REAL(r_std) :: P_lai0 |
---|
97 | REAL(r_std) :: P_tustressmin |
---|
98 | |
---|
99 | ! STICS:: LAI SENESCENCE |
---|
100 | INTEGER(i_std) :: P_nbfgellev |
---|
101 | INTEGER(i_std) :: P_maxgs |
---|
102 | REAL(r_std) :: P_ratiodurvieI |
---|
103 | REAL(r_std) :: P_durvieF |
---|
104 | REAL(r_std) :: P_ratiosen |
---|
105 | REAL(r_std) :: P_tdmin |
---|
106 | ! ! Xuhui 140321 |
---|
107 | ! INTEGER(i_std),SAVE :: doyhistst |
---|
108 | ! INTEGER(i_std),SAVE :: hist_sencour |
---|
109 | ! INTEGER(i_std),SAVE :: hist_latest |
---|
110 | ! REAL(r_std), DIMENSION(crop_nbjmax,5), SAVE :: histgrowth |
---|
111 | ! 5 variables are dltai dltams tdevelop ulai durvie |
---|
112 | ! intial these variables to zeros at Stics_init |
---|
113 | ! end 140321 |
---|
114 | |
---|
115 | ! STICS:: F_humerac |
---|
116 | |
---|
117 | REAL(r_std) :: P_sensrsec |
---|
118 | |
---|
119 | ! STICS:: GEL |
---|
120 | INTEGER(i_std) :: P_codgellev |
---|
121 | INTEGER(i_std) :: P_codgeljuv |
---|
122 | INTEGER(i_std) :: P_codgelveg |
---|
123 | REAL(r_std) :: P_tletale |
---|
124 | REAL(r_std) :: P_tdebgel |
---|
125 | REAL(r_std) :: P_tgellev10 |
---|
126 | REAL(r_std) :: P_tgellev90 |
---|
127 | REAL(r_std) :: P_tgeljuv10 |
---|
128 | REAL(r_std) :: P_tgeljuv90 |
---|
129 | REAL(r_std) :: P_tgelveg10 |
---|
130 | REAL(r_std) :: P_tgelveg90 |
---|
131 | ! STICS:: Photoperiod |
---|
132 | REAL(r_std) :: P_sensiphot |
---|
133 | REAL(r_std) :: P_phosat |
---|
134 | REAL(r_std) :: P_phobase |
---|
135 | |
---|
136 | INTEGER(i_std) :: P_codesla |
---|
137 | |
---|
138 | |
---|
139 | contains |
---|
140 | |
---|
141 | subroutine driver_stics(n, & ! IN |
---|
142 | in_cycle, & ! INout |
---|
143 | f_crop_recycle, & ! INOUT |
---|
144 | f_sen_lai, & ! INout |
---|
145 | t2m_daily, & ! IN |
---|
146 | t2m_min_daily, & ! IN |
---|
147 | gdh_daily, & ! IN |
---|
148 | phoi, & ! IN |
---|
149 | onarretesomcourdrp, & ! IN |
---|
150 | stempdiag_cm_daily, & ! IN |
---|
151 | shumdiag_cm_day, & ! IN |
---|
152 | ! nlevobs, & ! IN |
---|
153 | ! namfobs, & ! IN |
---|
154 | ! nfloobs, & ! IN |
---|
155 | ! nlanobs, & ! IN |
---|
156 | ! nlaxobs, & ! IN |
---|
157 | ! nmatobs, & ! IN |
---|
158 | ! nrecobs, & ! IN |
---|
159 | ! nsenobs, & ! IN |
---|
160 | ! ndrpobs, & ! IN |
---|
161 | dltams, & ! IN |
---|
162 | eop, & ! IN |
---|
163 | masec, & ! IN |
---|
164 | masecveg, & ! IN |
---|
165 | nsendltams, & ! INOUT |
---|
166 | nsendltai, & |
---|
167 | nsenpfeuilverte, & |
---|
168 | nsendurvie, & |
---|
169 | nsenndurvie, & |
---|
170 | densiteequiv, & |
---|
171 | nplt, & |
---|
172 | tursla, & |
---|
173 | sla, & |
---|
174 | pfeuilverte, & |
---|
175 | bsenlai, & |
---|
176 | zrac, & |
---|
177 | nrec, & |
---|
178 | nlan, & |
---|
179 | tcult, & |
---|
180 | udevair, & |
---|
181 | udevcult, & |
---|
182 | ndrp, & |
---|
183 | rfvi, & |
---|
184 | nlev, & |
---|
185 | nger, & |
---|
186 | etatvernal, & |
---|
187 | caljvc, & |
---|
188 | rfpi, & |
---|
189 | upvt, & |
---|
190 | utp, & |
---|
191 | somcour, & |
---|
192 | somcourdrp, & |
---|
193 | somcourutp, & |
---|
194 | tdevelop, & |
---|
195 | somtemp, & |
---|
196 | somcourfauche, & |
---|
197 | stpltger, & |
---|
198 | R_stamflax, & |
---|
199 | R_stlaxsen, & |
---|
200 | R_stsenlan, & |
---|
201 | stlevflo, & |
---|
202 | nflo, & |
---|
203 | R_stlevdrp, & |
---|
204 | R_stflodrp, & |
---|
205 | R_stdrpmat, & |
---|
206 | nmat, & |
---|
207 | nlax, & |
---|
208 | nrecbutoir, & |
---|
209 | group, & |
---|
210 | ndebdes, & |
---|
211 | R_stdrpdes, & |
---|
212 | densite, & |
---|
213 | densitelev, & |
---|
214 | coeflev, & |
---|
215 | densiteger, & |
---|
216 | somelong, & |
---|
217 | somger, & |
---|
218 | humectation, & |
---|
219 | nbjhumec, & |
---|
220 | somtemphumec, & |
---|
221 | stpltlev, & |
---|
222 | namf, & |
---|
223 | stmatrec, & |
---|
224 | tustress, & |
---|
225 | slai, & |
---|
226 | somfeuille, & |
---|
227 | pdlai, & |
---|
228 | nbfeuille, & |
---|
229 | reajust, & |
---|
230 | ulai, & |
---|
231 | pdulai, & |
---|
232 | efdensite, & |
---|
233 | tempeff, & |
---|
234 | nstopfeuille, & |
---|
235 | deltai, & |
---|
236 | vmax, & |
---|
237 | nsen, & |
---|
238 | laisen, & |
---|
239 | dltaisenat, & |
---|
240 | nsencour, & |
---|
241 | dltamsen, & |
---|
242 | dltaisen, & |
---|
243 | fgellev, & |
---|
244 | gelee, & |
---|
245 | fstressgel, & |
---|
246 | pdlaisen, & |
---|
247 | R_stlevamf, & |
---|
248 | dernier_n, & |
---|
249 | durvieI, & |
---|
250 | durvie, & |
---|
251 | ndebsen, & |
---|
252 | somsenreste, & |
---|
253 | shumrel, & |
---|
254 | humrel, & |
---|
255 | swfac, & |
---|
256 | turfac, & |
---|
257 | senfac, & ! INOUT |
---|
258 | mafeuiljaune, & |
---|
259 | msneojaune, & |
---|
260 | gslen, & |
---|
261 | drylen, & |
---|
262 | vswc, & |
---|
263 | !! parameters |
---|
264 | TP_codeplante, & |
---|
265 | TP_stade0, & |
---|
266 | TP_iplt0, & |
---|
267 | TP_iwater, & |
---|
268 | TP_codesimul, & |
---|
269 | TP_codelaitr,& |
---|
270 | TP_slamax,& |
---|
271 | TP_slamin,& |
---|
272 | TP_codeperenne,& |
---|
273 | TP_codcueille,& |
---|
274 | TP_codegdh,& |
---|
275 | TP_codetemp,& |
---|
276 | TP_coderetflo,& |
---|
277 | TP_codeinnact,& |
---|
278 | TP_codeh2oact,& |
---|
279 | TP_stressdev,& |
---|
280 | TP_innlai,& |
---|
281 | TP_innsenes,& |
---|
282 | TP_codebfroid,& |
---|
283 | TP_codephot,& |
---|
284 | TP_codedormance,& |
---|
285 | TP_codefauche,& |
---|
286 | TP_codetempfauche,& |
---|
287 | TP_codlainet,& |
---|
288 | TP_codeindetermin,& |
---|
289 | TP_codeinitprec,& |
---|
290 | TP_culturean,& |
---|
291 | TP_jvc,& |
---|
292 | TP_tfroid,& |
---|
293 | TP_ampfroid,& |
---|
294 | TP_jvcmini,& |
---|
295 | TP_tgmin,& |
---|
296 | TP_stpltger,& |
---|
297 | TP_profsem,& |
---|
298 | TP_propjgermin,& |
---|
299 | TP_tdmax,& |
---|
300 | TP_nbjgerlim,& |
---|
301 | TP_densitesem,& |
---|
302 | TP_vigueurbat,& |
---|
303 | TP_codepluiepoquet,& |
---|
304 | TP_codehypo,& |
---|
305 | TP_elmax,& |
---|
306 | TP_belong,& |
---|
307 | TP_celong,& |
---|
308 | TP_nlevlim1,& |
---|
309 | TP_nlevlim2,& |
---|
310 | TP_codrecolte,& |
---|
311 | TP_variete,& |
---|
312 | TP_codegermin,& |
---|
313 | T_codeulaivernal,& |
---|
314 | TP_swfacmin,& |
---|
315 | TP_laiplantule,& |
---|
316 | TP_vlaimax,& |
---|
317 | TP_stlevamf,& |
---|
318 | TP_stamflax,& |
---|
319 | TP_udlaimax,& |
---|
320 | TP_laicomp,& |
---|
321 | TP_adens,& |
---|
322 | TP_bdens,& |
---|
323 | TP_tcxstop,& |
---|
324 | TP_tcmax,& |
---|
325 | TP_tcmin,& |
---|
326 | TP_dlaimax,& |
---|
327 | TP_dlaimin,& |
---|
328 | TP_pentlaimax,& |
---|
329 | TP_tigefeuil,& |
---|
330 | TP_stlaxsen,& |
---|
331 | TP_stsenlan,& |
---|
332 | TP_stlevdrp,& |
---|
333 | TP_stflodrp,& |
---|
334 | TP_stdrpmat,& |
---|
335 | TP_stdrpdes,& |
---|
336 | TP_phyllotherme,& |
---|
337 | TP_lai0,& |
---|
338 | TP_tustressmin,& |
---|
339 | ! STICS:: SENESCENCE |
---|
340 | TP_nbfgellev,& |
---|
341 | TP_maxgs,& |
---|
342 | TP_ratiodurvieI,& |
---|
343 | TP_durvieF,& |
---|
344 | TP_ratiosen,& |
---|
345 | TP_tdmin,& |
---|
346 | ! STICS:: F_Humarec |
---|
347 | TP_sensrsec,& |
---|
348 | ! STICS:: GEL |
---|
349 | TP_codgellev,& |
---|
350 | TP_codgeljuv,& |
---|
351 | TP_codgelveg,& |
---|
352 | TP_tletale,& |
---|
353 | TP_tdebgel,& |
---|
354 | TP_tgellev10,& |
---|
355 | TP_tgellev90,& |
---|
356 | TP_tgeljuv10,& |
---|
357 | TP_tgeljuv90,& |
---|
358 | TP_tgelveg10,& |
---|
359 | TP_tgelveg90,& |
---|
360 | ! STICS:: Photoperiod |
---|
361 | TP_sensiphot,& |
---|
362 | TP_phosat,& |
---|
363 | TP_phobase,& |
---|
364 | histgrowth,& |
---|
365 | hist_sencour, & |
---|
366 | hist_latest, & |
---|
367 | doyhistst, & |
---|
368 | nbox, boxulai, boxndays, boxlai, boxlairem,boxtdev, boxbiom, boxbiomrem, boxdurage, boxsomsenbase, & |
---|
369 | codesla) |
---|
370 | |
---|
371 | |
---|
372 | implicit none |
---|
373 | |
---|
374 | ! DECLARATION |
---|
375 | |
---|
376 | ! 0.1 input |
---|
377 | ! These variables should be transmitted from ORCHIDEE or initialized only once |
---|
378 | |
---|
379 | |
---|
380 | integer(i_std), intent(IN) :: n ! simulation date // julian day |
---|
381 | logical, intent(inout) :: in_cycle |
---|
382 | logical, intent(inout) :: f_crop_recycle |
---|
383 | logical, intent(inout) :: f_sen_lai |
---|
384 | real(r_std), intent(IN) :: t2m_daily !> / Mean air temperature of the day // degree C |
---|
385 | real(r_std), intent(IN) :: t2m_min_daily !> / minimum air temperature of the day // degree C |
---|
386 | real(r_std), intent(IN) :: gdh_daily !> // daily gdh calculated according to halfhourly temperature // transmitted from stomate.f90 gdh_daily |
---|
387 | real(r_std), intent(IN) :: phoi !> // OUTPUT // Photoperiod // hours |
---|
388 | logical, intent(IN) :: onarretesomcourdrp |
---|
389 | real(r_std), intent(IN), dimension(3) :: stempdiag_cm_daily !> / soil temperature at 1 cm resolution for the sowing depth and neighbour layers // Degree C |
---|
390 | real(r_std), intent(IN), dimension(3) :: shumdiag_cm_day !> /soil moisture at 1 cm resolution for the sowing depth and neighbour layers // unit m3 m-3 with values ranging 0-1 |
---|
391 | !!!!! local variable |
---|
392 | integer(i_std) :: nlevobs ! the following variables ended with obs are only used for forcing simulation. |
---|
393 | integer(i_std) :: namfobs ! the initial value should be always 999 |
---|
394 | integer(i_std) :: nfloobs |
---|
395 | integer(i_std) :: nlanobs |
---|
396 | integer(i_std) :: nlaxobs |
---|
397 | integer(i_std) :: nmatobs |
---|
398 | integer(i_std) :: nrecobs |
---|
399 | integer(i_std) :: nsenobs |
---|
400 | integer(i_std) :: ndrpobs |
---|
401 | !!!!! local variable |
---|
402 | real(r_std), intent(IN) :: dltams ! biomass growth rate // t ha-1 day-1 |
---|
403 | real(r_std), intent(IN) :: eop ! potential evaportranspiration // mm |
---|
404 | real(r_std), intent(INOUT) :: masec ! aboveground biomass // t ha-1 |
---|
405 | real(r_std), intent(IN) :: masecveg ! vegetative dry matter // t ha-1 |
---|
406 | real(r_std), intent(IN) :: vswc ! volumetric soil water content |
---|
407 | |
---|
408 | ! 0.1 input--parameters |
---|
409 | |
---|
410 | CHARACTER(len=3), INTENT(IN) :: TP_codeplante |
---|
411 | CHARACTER(len=3), INTENT(IN) :: TP_stade0 |
---|
412 | INTEGER(i_std), INTENT(IN) :: TP_iplt0 |
---|
413 | INTEGER(i_std), INTENT(IN) :: TP_iwater |
---|
414 | CHARACTER(len=7), INTENT(IN) :: TP_codesimul |
---|
415 | INTEGER(i_std), INTENT(IN) :: TP_codelaitr |
---|
416 | REAL(r_std), INTENT(IN) :: TP_slamax |
---|
417 | REAL(r_std), INTENT(IN) :: TP_slamin |
---|
418 | INTEGER(i_std), INTENT(IN) :: TP_codeperenne !! annual crop (1) or perennial crop (2) |
---|
419 | INTEGER(i_std), INTENT(IN) :: TP_codcueille !! harvest option: cutting (1) or picking (2) |
---|
420 | INTEGER(i_std), INTENT(IN) :: TP_codegdh !! hourly (1) or daily (2) calculation of development unit |
---|
421 | INTEGER(i_std), INTENT(IN) :: TP_codetemp !! |
---|
422 | INTEGER(i_std), INTENT(IN) :: TP_coderetflo |
---|
423 | INTEGER(i_std), INTENT(IN) :: TP_codeinnact |
---|
424 | INTEGER(i_std), INTENT(IN) :: TP_codeh2oact |
---|
425 | REAL(r_std), INTENT(IN) :: TP_stressdev |
---|
426 | REAL(r_std), INTENT(IN) :: TP_innlai |
---|
427 | REAL(r_std), INTENT(IN) :: TP_innsenes |
---|
428 | INTEGER(i_std), INTENT(IN) :: TP_codebfroid |
---|
429 | INTEGER(i_std), INTENT(IN) :: TP_codephot |
---|
430 | INTEGER(i_std), INTENT(IN) :: TP_codedormance |
---|
431 | INTEGER(i_std), INTENT(IN) :: TP_codefauche !! option of cut modes for forage crops: yes (1), no (2) |
---|
432 | INTEGER(i_std), INTENT(IN) :: TP_codetempfauche !! option of the reference temperature to compute cutting sum of temperatures : upvt (1), udevair (2) |
---|
433 | INTEGER(i_std), INTENT(IN) :: TP_codlainet |
---|
434 | INTEGER(i_std), INTENT(IN) :: TP_codeindetermin |
---|
435 | INTEGER(i_std), INTENT(IN) :: TP_codeinitprec |
---|
436 | INTEGER(i_std), INTENT(IN) :: TP_culturean |
---|
437 | REAL(r_std), INTENT(IN) :: TP_jvc |
---|
438 | REAL(r_std), INTENT(IN) :: TP_tfroid |
---|
439 | REAL(r_std), INTENT(IN) :: TP_ampfroid |
---|
440 | REAL(r_std), INTENT(IN) :: TP_jvcmini |
---|
441 | REAL(r_std), INTENT(IN) :: TP_tgmin |
---|
442 | REAL(r_std), INTENT(IN) :: TP_stpltger |
---|
443 | REAL(r_std), INTENT(IN) :: TP_profsem |
---|
444 | REAL(r_std), INTENT(IN) :: TP_propjgermin !! minimal proportion of the duration TP_nbjgerlim when the temperature is higher than the temperature threshold TP_Tdmax |
---|
445 | REAL(r_std), INTENT(IN) :: TP_tdmax |
---|
446 | INTEGER(i_std), INTENT(IN) :: TP_nbjgerlim !! Threshold number of day after grain imbibition without germination lack // days |
---|
447 | REAL(r_std), INTENT(IN) :: TP_densitesem |
---|
448 | REAL(r_std), INTENT(IN) :: TP_vigueurbat !! indicator of plant vigor allowing to emerge through the crust // between 0 and 1 // |
---|
449 | INTEGER(i_std), INTENT(IN) :: TP_codepluiepoquet !! option to replace rainfall by irrigation at poquet depth in the case of poquet sowing // code 1/2 |
---|
450 | INTEGER(i_std), INTENT(IN) :: TP_codehypo |
---|
451 | REAL(r_std), INTENT(IN) :: TP_elmax |
---|
452 | REAL(r_std), INTENT(IN) :: TP_belong |
---|
453 | REAL(r_std), INTENT(IN) :: TP_celong |
---|
454 | INTEGER(i_std), INTENT(IN) :: TP_nlevlim1 !! number of days after germination decreasing the emerged plants if emergence has not occur // days |
---|
455 | INTEGER(i_std), INTENT(IN) :: TP_nlevlim2 !! number of days after germination after which the emerged plants are null // days |
---|
456 | INTEGER(i_std), INTENT(IN) :: TP_codrecolte !! harvest mode : all the plant (1) or just the fruits (2) |
---|
457 | INTEGER(i_std), INTENT(IN) :: TP_variete !! variety number in the technical file // SD |
---|
458 | INTEGER(i_std), INTENT(IN) :: TP_codegermin !! option of simulation of a germination phase or a delay at the beginning of the crop (1) or direct starting (2) |
---|
459 | |
---|
460 | INTEGER(i_std), INTENT(IN) :: T_codeulaivernal |
---|
461 | REAL(r_std), INTENT(IN) :: TP_swfacmin |
---|
462 | |
---|
463 | |
---|
464 | ! STICS:: LAI CALCULATION |
---|
465 | REAL(r_std), INTENT(IN) :: TP_laiplantule |
---|
466 | REAL(r_std), INTENT(IN) :: TP_vlaimax |
---|
467 | REAL(r_std), INTENT(IN) :: TP_stlevamf |
---|
468 | REAL(r_std), INTENT(IN) :: TP_stamflax |
---|
469 | REAL(r_std), INTENT(IN) :: TP_udlaimax |
---|
470 | REAL(r_std), INTENT(IN) :: TP_laicomp |
---|
471 | REAL(r_std), INTENT(IN) :: TP_adens !! Interplant competition parameter |
---|
472 | REAL(r_std), INTENT(IN) :: TP_bdens |
---|
473 | REAL(r_std), INTENT(IN) :: TP_tcxstop |
---|
474 | REAL(r_std), INTENT(IN) :: TP_tcmax |
---|
475 | REAL(r_std), INTENT(IN) :: TP_tcmin |
---|
476 | REAL(r_std), INTENT(IN) :: TP_dlaimax |
---|
477 | REAL(r_std), INTENT(IN) :: TP_dlaimin |
---|
478 | REAL(r_std), INTENT(IN) :: TP_pentlaimax |
---|
479 | REAL(r_std), INTENT(IN) :: TP_tigefeuil !! stem (structural part)/leaf proportion // SD |
---|
480 | |
---|
481 | REAL(r_std), INTENT(IN) :: TP_stlaxsen |
---|
482 | REAL(r_std), INTENT(IN) :: TP_stsenlan |
---|
483 | REAL(r_std), INTENT(IN) :: TP_stlevdrp |
---|
484 | REAL(r_std), INTENT(IN) :: TP_stflodrp |
---|
485 | REAL(r_std), INTENT(IN) :: TP_stdrpmat |
---|
486 | REAL(r_std), INTENT(IN) :: TP_stdrpdes |
---|
487 | REAL(r_std), INTENT(IN) :: TP_phyllotherme |
---|
488 | REAL(r_std), INTENT(IN) :: TP_lai0 |
---|
489 | REAL(r_std), INTENT(IN) :: TP_tustressmin |
---|
490 | |
---|
491 | ! STICS:: LAI SENESCENCE |
---|
492 | INTEGER(i_std), INTENT(IN) :: TP_nbfgellev |
---|
493 | INTEGER(i_std), INTENT(IN) :: TP_maxgs |
---|
494 | REAL(r_std), INTENT(IN) :: TP_ratiodurvieI |
---|
495 | REAL(r_std), INTENT(IN) :: TP_durvieF |
---|
496 | REAL(r_std), INTENT(IN) :: TP_ratiosen |
---|
497 | REAL(r_std), INTENT(IN) :: TP_tdmin |
---|
498 | ! STICS:: F_Humarec |
---|
499 | |
---|
500 | REAL(r_std), INTENT(IN) :: TP_sensrsec |
---|
501 | |
---|
502 | ! STICS:: GEL |
---|
503 | INTEGER(i_std), INTENT(IN) :: TP_codgellev |
---|
504 | INTEGER(i_std), INTENT(IN) :: TP_codgeljuv |
---|
505 | INTEGER(i_std), INTENT(IN) :: TP_codgelveg |
---|
506 | REAL(r_std), INTENT(IN) :: TP_tletale |
---|
507 | REAL(r_std), INTENT(IN) :: TP_tdebgel |
---|
508 | REAL(r_std), INTENT(IN) :: TP_tgellev10 |
---|
509 | REAL(r_std), INTENT(IN) :: TP_tgellev90 |
---|
510 | REAL(r_std), INTENT(IN) :: TP_tgeljuv10 |
---|
511 | REAL(r_std), INTENT(IN) :: TP_tgeljuv90 |
---|
512 | REAL(r_std), INTENT(IN) :: TP_tgelveg10 |
---|
513 | REAL(r_std), INTENT(IN) :: TP_tgelveg90 |
---|
514 | |
---|
515 | ! STICS:: Photoperiod |
---|
516 | |
---|
517 | REAL(r_std), INTENT(IN) :: TP_sensiphot |
---|
518 | REAL(r_std), INTENT(IN) :: TP_phosat |
---|
519 | REAL(r_std), INTENT(IN) :: TP_phobase |
---|
520 | INTEGER(i_std), INTENT(IN) :: codesla |
---|
521 | REAL(r_std), INTENT(IN) :: humrel |
---|
522 | ! 0.2 inout |
---|
523 | ! these variables should ba all saved in Stomate.f90 for historical interaction |
---|
524 | |
---|
525 | ! these variables are for laidev specifically |
---|
526 | real, intent(INOUT) :: nsendltams |
---|
527 | real, intent(INOUT) :: nsendltai |
---|
528 | real, intent(INOUT) :: nsenpfeuilverte |
---|
529 | real, intent(INOUT) :: nsendurvie |
---|
530 | real, intent(INOUT) :: nsenndurvie |
---|
531 | real, intent(INOUT) :: densiteequiv |
---|
532 | integer, intent(INOUT) :: nplt |
---|
533 | real, intent(INOUT) :: tursla |
---|
534 | real, intent(INOUT) :: sla |
---|
535 | real, intent(INOUT) :: pfeuilverte |
---|
536 | real, intent(INOUT) :: bsenlai |
---|
537 | |
---|
538 | ! variables are involved in DEVELOPMENT |
---|
539 | |
---|
540 | real, intent(INOUT) :: zrac |
---|
541 | integer, intent(INOUT) :: nrec |
---|
542 | integer, intent(INOUT) :: nlan |
---|
543 | real, intent(INOUT) :: tcult |
---|
544 | real, intent(INOUT) :: udevair |
---|
545 | real, intent(INOUT) :: udevcult |
---|
546 | integer, intent(INOUT) :: ndrp |
---|
547 | real, intent(INOUT) :: rfvi |
---|
548 | integer, intent(INOUT) :: nlev |
---|
549 | integer, intent(INOUT) :: nger |
---|
550 | logical, intent(INOUT) :: etatvernal |
---|
551 | real, intent(INOUT) :: caljvc |
---|
552 | real, intent(INOUT) :: rfpi |
---|
553 | real, intent(INOUT) :: upvt |
---|
554 | real, intent(INOUT) :: utp |
---|
555 | real, intent(INOUT) :: somcour |
---|
556 | real, intent(INOUT) :: somcourdrp |
---|
557 | real, intent(INOUT) :: somcourutp |
---|
558 | real, intent(INOUT) :: tdevelop |
---|
559 | real, intent(INOUT) :: somtemp |
---|
560 | real, intent(INOUT) :: somcourfauche |
---|
561 | real, intent(INOUT) :: stpltger |
---|
562 | real, intent(INOUT) :: R_stamflax |
---|
563 | real, intent(INOUT) :: R_stlaxsen |
---|
564 | real, intent(INOUT) :: R_stsenlan |
---|
565 | real, intent(INOUT) :: stlevflo |
---|
566 | integer, intent(INOUT) :: nflo |
---|
567 | real, intent(INOUT) :: R_stlevdrp |
---|
568 | real, intent(INOUT) :: R_stflodrp |
---|
569 | real, intent(INOUT) :: R_stdrpmat |
---|
570 | integer, intent(INOUT) :: nmat |
---|
571 | integer, intent(INOUT) :: nlax |
---|
572 | integer, intent(INOUT) :: nrecbutoir |
---|
573 | real, intent(INOUT) :: group |
---|
574 | integer, intent(INOUT) :: ndebdes |
---|
575 | real, intent(INOUT) :: R_stdrpdes |
---|
576 | real, intent(INOUT) :: densite |
---|
577 | real, intent(INOUT) :: densitelev |
---|
578 | real, intent(INOUT) :: coeflev |
---|
579 | real, intent(INOUT) :: densiteger |
---|
580 | real, intent(INOUT) :: somelong |
---|
581 | real, intent(INOUT) :: somger |
---|
582 | logical, intent(INOUT) :: humectation |
---|
583 | integer, intent(INOUT) :: nbjhumec |
---|
584 | real, intent(INOUT) :: somtemphumec |
---|
585 | real, intent(INOUT) :: stpltlev |
---|
586 | integer, intent(INOUT) :: namf |
---|
587 | real, intent(INOUT) :: stmatrec |
---|
588 | |
---|
589 | ! these variables are involved in Lai_calculation |
---|
590 | |
---|
591 | real, intent(INOUT) :: tustress |
---|
592 | real, intent(INOUT) :: slai |
---|
593 | real, intent(INOUT) :: somfeuille |
---|
594 | real, intent(INOUT) :: pdlai |
---|
595 | integer, intent(INOUT) :: nbfeuille |
---|
596 | real, intent(INOUT) :: reajust |
---|
597 | real, intent(INOUT) :: ulai |
---|
598 | real, intent(INOUT) :: pdulai |
---|
599 | real, intent(INOUT) :: efdensite |
---|
600 | real, intent(INOUT) :: tempeff |
---|
601 | integer, intent(INOUT) :: nstopfeuille |
---|
602 | real, intent(INOUT) :: deltai |
---|
603 | real, intent(INOUT) :: vmax |
---|
604 | integer, intent(INOUT) :: nsen |
---|
605 | real, intent(INOUT) :: laisen |
---|
606 | real, intent(INOUT) :: dltaisenat |
---|
607 | ! Xuhui 140321 |
---|
608 | INTEGER(i_std), intent(INOUT) :: doyhistst |
---|
609 | INTEGER(i_std), intent(INOUT) :: hist_sencour |
---|
610 | INTEGER(i_std), intent(INOUT) :: hist_latest |
---|
611 | REAL(r_std), DIMENSION(300,5), intent(INOUT) :: histgrowth |
---|
612 | !end histgrowth |
---|
613 | |
---|
614 | ! these variables are involved in the LAIsenescence |
---|
615 | |
---|
616 | integer, intent(INOUT) :: nsencour |
---|
617 | real, intent(INOUT) :: dltamsen |
---|
618 | real, intent(INOUT) :: dltaisen |
---|
619 | real, intent(INOUT) :: fgellev |
---|
620 | logical, intent(INOUT) :: gelee |
---|
621 | real, intent(INOUT) :: fstressgel |
---|
622 | real, intent(INOUT) :: pdlaisen |
---|
623 | real, intent(INOUT) :: R_stlevamf |
---|
624 | integer, intent(INOUT) :: dernier_n |
---|
625 | real, intent(INOUT) :: durvieI |
---|
626 | real, intent(INOUT) :: durvie |
---|
627 | integer, intent(INOUT) :: ndebsen |
---|
628 | real, intent(INOUT) :: somsenreste |
---|
629 | |
---|
630 | ! compartment senescence module |
---|
631 | !boxulai, boxndays, boxlai, boxlairem,boxtdev, boxbiom, boxbiomrem, boxdurage, boxsomsenbase |
---|
632 | integer(i_std), intent(IN) :: nbox |
---|
633 | real(r_std), dimension(nbox), intent(INOUT) :: boxulai |
---|
634 | integer(i_std), dimension(nbox), intent(INOUT) :: boxndays |
---|
635 | real(r_std), dimension(nbox), intent(INOUT) :: boxlai |
---|
636 | real(r_std), dimension(nbox), intent(INOUT) :: boxlairem |
---|
637 | real(r_std), dimension(nbox), intent(INOUT) :: boxtdev |
---|
638 | real(r_std), dimension(nbox), intent(INOUT) :: boxbiom |
---|
639 | real(r_std), dimension(nbox), intent(INOUT) :: boxbiomrem |
---|
640 | real(r_std), dimension(nbox), intent(INOUT) :: boxdurage |
---|
641 | real(r_std), dimension(nbox), intent(INOUT) :: boxsomsenbase |
---|
642 | |
---|
643 | |
---|
644 | ! these variables are involved in STRESS calculation |
---|
645 | |
---|
646 | real, intent(INOUT) :: shumrel |
---|
647 | real, intent(INOUT) :: swfac |
---|
648 | real, intent(INOUT) :: turfac |
---|
649 | real, intent(INOUT) :: senfac |
---|
650 | |
---|
651 | ! these variables are involved in CARBON ALLOCATION PROCESSES |
---|
652 | real, intent(INOUT) :: mafeuiljaune ! Dry matter of yellow leaves // t.ha-1 |
---|
653 | real, intent(INOUT) :: msneojaune ! Newly-formed senescent dry matter // t.ha-1 |
---|
654 | integer, intent(INOUT) :: gslen |
---|
655 | integer, intent(INOUT) :: drylen |
---|
656 | |
---|
657 | ! assignment |
---|
658 | nlevobs = 999 |
---|
659 | namfobs = 999 |
---|
660 | nfloobs = 999 |
---|
661 | nlanobs = 999 |
---|
662 | nlaxobs = 999 |
---|
663 | nmatobs = 999 |
---|
664 | nrecobs = 999 |
---|
665 | nsenobs = 999 |
---|
666 | ndrpobs = 999 |
---|
667 | |
---|
668 | P_codeplante = TP_codeplante |
---|
669 | P_stade0 = TP_stade0 |
---|
670 | P_iplt0 = TP_iplt0 |
---|
671 | P_iwater = TP_iwater |
---|
672 | P_codesimul = TP_codesimul |
---|
673 | P_codelaitr = TP_codelaitr |
---|
674 | P_slamax = TP_slamax |
---|
675 | P_slamin = TP_slamin |
---|
676 | P_codeperenne = TP_codeperenne |
---|
677 | P_codcueille = TP_codcueille |
---|
678 | P_codegdh = TP_codegdh |
---|
679 | P_codetemp = TP_codetemp |
---|
680 | P_coderetflo = TP_coderetflo |
---|
681 | P_codeinnact = TP_codeinnact |
---|
682 | P_codeh2oact = TP_codeh2oact |
---|
683 | P_stressdev = TP_stressdev |
---|
684 | P_innlai = TP_innlai |
---|
685 | P_innsenes = TP_innsenes |
---|
686 | P_codebfroid = TP_codebfroid |
---|
687 | P_codephot = TP_codephot |
---|
688 | P_codedormance = TP_codedormance |
---|
689 | P_codefauche = TP_codefauche |
---|
690 | P_codetempfauche = TP_codetempfauche |
---|
691 | P_codlainet = TP_codlainet |
---|
692 | P_codeindetermin = TP_codeindetermin |
---|
693 | P_codeinitprec = TP_codeinitprec |
---|
694 | P_culturean = TP_culturean |
---|
695 | P_jvc = TP_jvc |
---|
696 | P_tfroid = TP_tfroid |
---|
697 | P_ampfroid = TP_ampfroid |
---|
698 | P_jvcmini = TP_jvcmini |
---|
699 | P_tgmin = TP_tgmin |
---|
700 | P_stpltger = TP_stpltger |
---|
701 | P_profsem = TP_profsem |
---|
702 | P_propjgermin = TP_propjgermin |
---|
703 | P_tdmax = TP_tdmax |
---|
704 | P_nbjgerlim = TP_nbjgerlim |
---|
705 | P_densitesem = TP_densitesem |
---|
706 | P_vigueurbat = TP_vigueurbat |
---|
707 | P_codepluiepoquet = TP_codepluiepoquet |
---|
708 | P_codehypo = TP_codehypo |
---|
709 | P_elmax = TP_elmax |
---|
710 | P_belong = TP_belong |
---|
711 | P_celong = TP_celong |
---|
712 | P_nlevlim1 = TP_nlevlim1 |
---|
713 | P_nlevlim2 = TP_nlevlim2 |
---|
714 | P_codrecolte = TP_codrecolte |
---|
715 | P_variete = TP_variete |
---|
716 | P_codegermin = TP_codegermin |
---|
717 | |
---|
718 | codeulaivernal = T_codeulaivernal |
---|
719 | P_swfacmin = TP_swfacmin |
---|
720 | |
---|
721 | |
---|
722 | P_laiplantule = TP_laiplantule |
---|
723 | P_vlaimax = TP_vlaimax |
---|
724 | P_stlevamf = TP_stlevamf |
---|
725 | P_stamflax = TP_stamflax |
---|
726 | P_udlaimax = TP_udlaimax |
---|
727 | P_laicomp = TP_laicomp |
---|
728 | P_adens = TP_adens |
---|
729 | P_bdens = TP_bdens |
---|
730 | P_tcxstop = TP_tcxstop |
---|
731 | P_tcmax = TP_tcmax |
---|
732 | P_tcmin = TP_tcmin |
---|
733 | P_dlaimax = TP_dlaimax |
---|
734 | P_dlaimin = TP_dlaimin |
---|
735 | P_pentlaimax = TP_pentlaimax |
---|
736 | P_tigefeuil = TP_tigefeuil |
---|
737 | |
---|
738 | P_stlaxsen = TP_stlaxsen |
---|
739 | P_stsenlan = TP_stsenlan |
---|
740 | P_stlevdrp = TP_stlevdrp |
---|
741 | P_stflodrp = TP_stflodrp |
---|
742 | P_stdrpmat = TP_stdrpmat |
---|
743 | P_stdrpdes = TP_stdrpdes |
---|
744 | P_phyllotherme = TP_phyllotherme |
---|
745 | P_lai0 = TP_lai0 |
---|
746 | P_tustressmin = TP_tustressmin |
---|
747 | ! STICS:: SENESCENCE |
---|
748 | P_nbfgellev = TP_nbfgellev |
---|
749 | P_maxgs = TP_maxgs |
---|
750 | P_ratiodurvieI = TP_ratiodurvieI |
---|
751 | P_durvieF = TP_durvieF |
---|
752 | P_ratiosen = TP_ratiosen |
---|
753 | P_tdmin = TP_tdmin |
---|
754 | ! STICS:: F_hemarec |
---|
755 | P_sensrsec = TP_sensrsec |
---|
756 | ! STICS::GEL |
---|
757 | P_codgellev = TP_codgellev |
---|
758 | P_codgeljuv = TP_codgeljuv |
---|
759 | P_codgelveg = TP_codgelveg |
---|
760 | P_tletale = TP_tletale |
---|
761 | P_tdebgel = TP_tdebgel |
---|
762 | P_tgellev10 = TP_tgellev10 |
---|
763 | P_tgellev90 = TP_tgellev90 |
---|
764 | P_tgeljuv10 = TP_tgeljuv10 |
---|
765 | P_tgeljuv90 = TP_tgeljuv90 |
---|
766 | P_tgelveg10 = TP_tgelveg10 |
---|
767 | P_tgelveg90 = TP_tgelveg90 |
---|
768 | ! STICS:: Photoperiod |
---|
769 | P_sensiphot = TP_sensiphot |
---|
770 | P_phosat = TP_phosat |
---|
771 | P_phobase = TP_phobase |
---|
772 | |
---|
773 | P_codesla = codesla |
---|
774 | |
---|
775 | ! if (.NOT. in_cycle) then |
---|
776 | ! doyhistst = 0 |
---|
777 | ! hist_sencour = 0 |
---|
778 | ! hist_latest = 0 |
---|
779 | ! histgrowth(:,:) = 0. |
---|
780 | ! endif |
---|
781 | |
---|
782 | |
---|
783 | call laidev(n, & ! IN |
---|
784 | in_cycle, & ! inout |
---|
785 | f_crop_recycle, & ! INOUT |
---|
786 | f_sen_lai, & ! inout |
---|
787 | t2m_daily, & ! IN |
---|
788 | t2m_min_daily, & ! IN |
---|
789 | gdh_daily, & ! IN |
---|
790 | phoi, & ! IN |
---|
791 | onarretesomcourdrp, & ! IN |
---|
792 | stempdiag_cm_daily, & ! IN |
---|
793 | shumdiag_cm_day, & ! IN |
---|
794 | nlevobs, & ! IN |
---|
795 | namfobs, & ! IN |
---|
796 | nfloobs, & ! IN |
---|
797 | nlanobs, & ! IN |
---|
798 | nlaxobs, & ! IN |
---|
799 | nmatobs, & ! IN |
---|
800 | nrecobs, & ! IN |
---|
801 | nsenobs, & ! IN |
---|
802 | ndrpobs, & ! IN |
---|
803 | dltams, & ! IN |
---|
804 | eop, & ! IN |
---|
805 | masec, & ! IN |
---|
806 | masecveg, & ! IN |
---|
807 | nsendltams, & ! INOUT |
---|
808 | nsendltai, & |
---|
809 | nsenpfeuilverte, & |
---|
810 | nsendurvie, & |
---|
811 | nsenndurvie, & |
---|
812 | densiteequiv, & |
---|
813 | nplt, & |
---|
814 | tursla, & |
---|
815 | sla, & |
---|
816 | pfeuilverte, & |
---|
817 | bsenlai, & |
---|
818 | zrac, & |
---|
819 | nrec, & |
---|
820 | nlan, & |
---|
821 | tcult, & |
---|
822 | udevair, & |
---|
823 | udevcult, & |
---|
824 | ndrp, & |
---|
825 | rfvi, & |
---|
826 | nlev, & |
---|
827 | nger, & |
---|
828 | etatvernal, & |
---|
829 | caljvc, & |
---|
830 | rfpi, & |
---|
831 | upvt, & |
---|
832 | utp, & |
---|
833 | somcour, & |
---|
834 | somcourdrp, & |
---|
835 | somcourutp, & |
---|
836 | tdevelop, & |
---|
837 | somtemp, & |
---|
838 | somcourfauche, & |
---|
839 | stpltger, & |
---|
840 | R_stamflax, & |
---|
841 | R_stlaxsen, & |
---|
842 | R_stsenlan, & |
---|
843 | stlevflo, & |
---|
844 | nflo, & |
---|
845 | R_stlevdrp, & |
---|
846 | R_stflodrp, & |
---|
847 | R_stdrpmat, & |
---|
848 | nmat, & |
---|
849 | nlax, & |
---|
850 | nrecbutoir, & |
---|
851 | group, & |
---|
852 | ndebdes, & |
---|
853 | R_stdrpdes, & |
---|
854 | densite, & |
---|
855 | densitelev, & |
---|
856 | coeflev, & |
---|
857 | densiteger, & |
---|
858 | somelong, & |
---|
859 | somger, & |
---|
860 | humectation, & |
---|
861 | nbjhumec, & |
---|
862 | somtemphumec, & |
---|
863 | stpltlev, & |
---|
864 | namf, & |
---|
865 | stmatrec, & |
---|
866 | tustress, & |
---|
867 | slai, & |
---|
868 | somfeuille, & |
---|
869 | pdlai, & |
---|
870 | nbfeuille, & |
---|
871 | reajust, & |
---|
872 | ulai, & |
---|
873 | pdulai, & |
---|
874 | efdensite, & |
---|
875 | tempeff, & |
---|
876 | nstopfeuille, & |
---|
877 | deltai, & |
---|
878 | vmax, & |
---|
879 | nsen, & |
---|
880 | laisen, & |
---|
881 | dltaisenat, & |
---|
882 | nsencour, & |
---|
883 | dltamsen, & |
---|
884 | dltaisen, & |
---|
885 | fgellev, & |
---|
886 | gelee, & |
---|
887 | fstressgel, & |
---|
888 | pdlaisen, & |
---|
889 | R_stlevamf, & |
---|
890 | dernier_n, & |
---|
891 | durvieI, & |
---|
892 | durvie, & |
---|
893 | ndebsen, & |
---|
894 | somsenreste, & |
---|
895 | shumrel, & |
---|
896 | humrel, & |
---|
897 | swfac, & |
---|
898 | turfac, & |
---|
899 | senfac, & |
---|
900 | mafeuiljaune, & |
---|
901 | msneojaune, & |
---|
902 | gslen, & |
---|
903 | drylen, & |
---|
904 | vswc, & |
---|
905 | histgrowth, & |
---|
906 | hist_sencour, & |
---|
907 | hist_latest, & |
---|
908 | doyhistst, & |
---|
909 | nbox, boxulai, boxndays, boxlai, boxlairem,boxtdev, & |
---|
910 | boxbiom, boxbiomrem,boxdurage, boxsomsenbase) |
---|
911 | |
---|
912 | |
---|
913 | end subroutine driver_stics |
---|
914 | |
---|
915 | end module Stics |
---|
916 | |
---|
917 | |
---|