Branches/Assimilation/Implementation: diff_ORCHIDEE_for_RESHAPE-ORCHIDEE_1_9_5_2.diff

File diff_ORCHIDEE_for_RESHAPE-ORCHIDEE_1_9_5_2.diff, 297.8 KB (added by mmaipsl, 11 years ago)

Liste des différences entre le modèle TAG 1.9.5.2 et le modèle pour l'assimilation

Line 
1diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_parameters/constantes_soil.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_parameters/constantes_soil.f90
2152,155d151
3< !-
4< ! Check the water balance
5<   LOGICAL, SAVE                    :: check_waterbal=.FALSE.
6<
7diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_sechiba/condveg.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_sechiba/condveg.f90
810c10
9< !< $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/tags/ORCHIDEE_1_9_5_2/ORCHIDEE/src_sechiba/condveg.f90 $
10---
11> !< $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/trunk/ORCHIDEE/src_sechiba/condveg.f90 $
1269,77d68
13< ! List of subroutines for initialization :
14< !- condveg_init
15< !- condveg_clear
16< !- condveg_var_init
17< !- condveg_snow
18< !- condveg_soilalb
19< !- condveg_z0logz
20< !- condveg_z0cdrag
21< !- condveg_albcalc
22881d871
23<   ok_interpol=.FALSE.
24diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_sechiba/diffuco.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_sechiba/diffuco.f90
257c7
26< !< $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/tags/ORCHIDEE_1_9_5_2/ORCHIDEE/src_sechiba/diffuco.f90 $
27---
28> !< $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/trunk/ORCHIDEE/src_sechiba/diffuco.f90 $
2936a37
30>   CHARACTER(LEN=80)                                 :: var_name                  !! To store variables names for I/O
3148,50d48
32< ! List of subroutines for initialization :
33< !- diffuco_init
34< !- diffuco_clear
3575,76c73,74
36< !     & zlev, z0, roughheight, temp_sol, temp_air, rau, tq_cdrag, qsurf, qair, pb, &
37<      & zlev, z0, roughheight, temp_sol, temp_air, rau, tq_cdrag, qsurf, qair, q2m, t2m, pb, &
38---
39> !     & zlev, z0, roughheight, temp_sol, temp_air, rau, q_cdrag, qsurf, qair, pb, &
40>      & zlev, z0, roughheight, temp_sol, temp_air, rau, q_cdrag, qsurf, qair, q2m, t2m, pb, &
41126c124
42<     REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: tq_cdrag          !! Surface drag ! Aerodynamic conductance
43---
44>     REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: q_cdrag          !! Surface drag ! Aerodynamic conductance
45144d141
46<     CHARACTER(LEN=80)                                 :: var_name   !! To store variables names for I/O
47152,153c149,150
48<         !Config Def  = TRUE if tq_cdrag on initialization is non zero
49<         !Config Help = Set to .TRUE. if you want tq_cdrag coming from GCM.
50---
51>         !Config Def  = TRUE if q_cdrag on initialization is non zero
52>         !Config Help = Set to .TRUE. if you want q_cdrag coming from GCM.
53155c152
54<         IF ( ABS(MAXVAL(tq_cdrag)) .LE. EPSILON(tq_cdrag)) THEN
55---
56>         IF ( ABS(MAXVAL(q_cdrag)) .LE. EPSILON(q_cdrag)) THEN
57160c157
58< !MM tq_cdrag is always 0 on initialization ??
59---
60> !MM q_cdrag is always 0 on initialization ??
61168c165
62<         CALL diffuco_init(kjit, ldrestart_read, kjpindex, index, rest_id, tq_cdrag)
63---
64>         CALL diffuco_init(kjit, ldrestart_read, kjpindex, index, rest_id, q_cdrag)
65207c204
66<            CALL restput_p (rest_id, var_name, nbp_glo, 1, 1, kjit, tq_cdrag, 'scatter',  nbp_glo, index_g)
67---
68>            CALL restput_p (rest_id, var_name, nbp_glo, 1, 1, kjit, q_cdrag, 'scatter',  nbp_glo, index_g)
69221c218
70<             &             qsurf, qair, tq_cdrag)
71---
72>             &             qsurf, qair, q_cdrag)
73223c220
74<     CALL diffuco_raerod (kjpindex, u, v, tq_cdrag, raero)
75---
76>     CALL diffuco_raerod (kjpindex, u, v, q_cdrag, raero)
77235c232
78<     CALL diffuco_snow (kjpindex, dtradia, qair, qsatt, rau, u, v, tq_cdrag, &
79---
80>     CALL diffuco_snow (kjpindex, dtradia, qair, qsatt, rau, u, v, q_cdrag, &
81243c240
82<     !CALL diffuco_inter (kjpindex, dtradia, qair, qsatt, rau, u, v, tq_cdrag, veget, &
83---
84>     !CALL diffuco_inter (kjpindex, dtradia, qair, qsatt, rau, u, v, q_cdrag, veget, &
85245c242
86<     CALL diffuco_inter (kjpindex, dtradia, qair, qsatt, rau, u, v, tq_cdrag, veget, &
87---
88>     CALL diffuco_inter (kjpindex, dtradia, qair, qsatt, rau, u, v, q_cdrag, veget, &
89251c248
90<     CALL diffuco_bare (kjpindex, dtradia, u, v, tq_cdrag, rsol, evap_bare_lim, evapot, humrel, veget, vbeta4)
91---
92>     CALL diffuco_bare (kjpindex, dtradia, u, v, q_cdrag, rsol, evap_bare_lim, evapot, humrel, veget, vbeta4)
93261c258
94<       !CALL diffuco_trans_co2 (kjpindex, dtradia, swdown, temp_air, pb, qair, rau, u, v, tq_cdrag, humrel, &
95---
96>       !CALL diffuco_trans_co2 (kjpindex, dtradia, swdown, temp_air, pb, qair, rau, u, v, q_cdrag, humrel, &
97265c262
98<       CALL diffuco_trans_co2 (kjpindex, dtradia, swdown, temp_air, pb, qair, q2m, t2m, rau, u, v, tq_cdrag, humrel, &
99---
100>       CALL diffuco_trans_co2 (kjpindex, dtradia, swdown, temp_air, pb, qair, q2m, t2m, rau, u, v, q_cdrag, humrel, &
101272c269
102<       !CALL diffuco_trans (kjpindex, dtradia, swnet, temp_air, pb, qair, rau, u, v, tq_cdrag, humrel, &
103---
104>       !CALL diffuco_trans (kjpindex, dtradia, swnet, temp_air, pb, qair, rau, u, v, q_cdrag, humrel, &
105275c272
106<       CALL diffuco_trans (kjpindex, dtradia, swnet, temp_air, pb, qair, rau, u, v, tq_cdrag, humrel, &
107---
108>       CALL diffuco_trans (kjpindex, dtradia, swnet, temp_air, pb, qair, rau, u, v, q_cdrag, humrel, &
109285c282
110<     CALL diffuco_comb (kjpindex, dtradia, humrel, rau, u, v, tq_cdrag, pb, qair, temp_sol, temp_air, snow, &
111---
112>     CALL diffuco_comb (kjpindex, dtradia, humrel, rau, u, v, q_cdrag, pb, qair, temp_sol, temp_air, snow, &
113292c289
114<        CALL histwrite(hist_id, 'cdrag', kjit, tq_cdrag, kjpindex, index)
115---
116>        CALL histwrite(hist_id, 'cdrag', kjit, q_cdrag, kjpindex, index)
117301c298
118<           CALL histwrite(hist2_id, 'cdrag', kjit, tq_cdrag, kjpindex, index)
119---
120>           CALL histwrite(hist2_id, 'cdrag', kjit, q_cdrag, kjpindex, index)
121336d332
122<     CHARACTER(LEN=80)               :: var_name           !! To store variables names for I/O
123492,493d487
124<       IF (ALLOCATED (qsatt)) DEALLOCATE (qsatt)
125<       IF (ALLOCATED (wind)) DEALLOCATE (wind)
126diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_sechiba/enerbil.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_sechiba/enerbil.f90
1277c7
128< !< $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/tags/ORCHIDEE_1_9_5_2/ORCHIDEE/src_sechiba/enerbil.f90 $
129---
130> !< $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/trunk/ORCHIDEE/src_sechiba/enerbil.f90 $
13138a39,40
132>   CHARACTER(LEN=80), SAVE                    :: var_name                !! To store variables names for I/O
133>
13456,60d57
135< ! List of subroutines for initialization :
136< !- enerbil_init
137< !- enerbil_clear
138< !- enerbil_var_init
139< !- enerbil_t2mdiag
14082c79
141<      & cimean, ccanopy, emis, soilflx, soilcap, tq_cdrag, humrel, fluxsens, fluxlat, &
142---
143>      & cimean, ccanopy, emis, soilflx, soilcap, q_cdrag, humrel, fluxsens, fluxlat, &
144118c115
145<     REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: tq_cdrag          !! This is the cdrag without the wind multiplied
146---
147>     REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: q_cdrag          !! This is the cdrag without the wind multiplied
148146,147d142
149<     CHARACTER(LEN=80)                :: var_name                !! To store variables names for I/O
150<
151218c213
152<        & epot_air, petAcoef, petBcoef, qair, peqAcoef, peqBcoef, soilflx, rau, u, v, tq_cdrag, vbeta,&
153---
154>        & epot_air, petAcoef, petBcoef, qair, peqAcoef, peqBcoef, soilflx, rau, u, v, q_cdrag, vbeta,&
155226c221
156<     CALL enerbil_flux (kjpindex, dtradia, emis, temp_sol, rau, u, v, tq_cdrag, vbeta, valpha, vbeta1, &
157---
158>     CALL enerbil_flux (kjpindex, dtradia, emis, temp_sol, rau, u, v, q_cdrag, vbeta, valpha, vbeta1, &
159236c231
160<        & ccanopy, rau, u, v, tq_cdrag, qair_new, humrel, vevapsno, vevapnu , vevapwet, transpir, gpp, evapot)
161---
162>        & ccanopy, rau, u, v, q_cdrag, qair_new, humrel, vevapsno, vevapnu , vevapwet, transpir, gpp, evapot)
163303d297
164<     CHARACTER(LEN=80)                :: var_name                !! To store variables names for I/O
165diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_sechiba/hydrolc.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_sechiba/hydrolc.f90
1667c7
167< !< $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/tags/ORCHIDEE_1_9_5_2/ORCHIDEE/src_sechiba/hydrolc.f90 $
168---
169> !< $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/trunk/ORCHIDEE/src_sechiba/hydrolc.f90 $
17040c40
171<   LOGICAL, SAVE                                     :: l_first_hydrolc=.TRUE. !! Initialisation has to be done one time
172---
173>   LOGICAL, SAVE                                     :: l_first_hydrol=.TRUE. !! Initialisation has to be done one time
17441a42
175>   LOGICAL, SAVE                                     :: check_waterbal=.FALSE. !! The check the water balance
17643a45,46
177>   CHARACTER(LEN=80) , SAVE                          :: var_name         !! To store variables names for I/O
178>
17983c86
180<   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: runoff_veg           !! Ruissellement
181---
182>   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: runoff           !! Ruissellement
18389,90d91
184<   REAL(r_std), SAVE, DIMENSION(nvm)              :: throughfall_by_pft
185<
18692,103d92
187< ! List of subroutines for initialization :
188< !- hydrolc_init
189< !- hydrolc_clear
190< !- hydrolc_var_init
191< !- hydrolc_snow
192< !- hydrolc_canop
193< !- hydrolc_vegupd
194< !- hydrolc_soil
195< !- hydrolc_waterbal
196< !- hydrolc_alma
197< !- hydrolc_hdiff
198<
199121c110
200<      & temp_sol_new, runoff, drainage, frac_nobio, totfrac_nobio, vevapwet, veget, veget_max,&
201---
202>      & temp_sol_new, run_off_tot, drainage, frac_nobio, totfrac_nobio, vevapwet, veget, veget_max,&
203166c155
204<     REAL(r_std),DIMENSION (kjpindex), INTENT (inout)     :: runoff   !! Complete runoff
205---
206>     REAL(r_std),DIMENSION (kjpindex), INTENT (inout)     :: run_off_tot   !! Complete runoff
207183,184d171
208<     CHARACTER(LEN=80)                                  :: var_name !! To store variables names for I/O
209<
210189c176
211<     IF (l_first_hydrolc) THEN
212---
213>     IF (l_first_hydrol) THEN
214191c178
215<         IF (long_print) WRITE (numout,*) ' l_first_hydrolc : call hydrolc_init '
216---
217>         IF (long_print) WRITE (numout,*) ' l_first_hydrol : call hydrolc_init '
218203c190
219<                 & runoff, drainage)
220---
221>                 & run_off_tot, drainage)
222289c276
223<          & gqsb, bqsb, dsg, dss, rsol, drysoil_frac, hdry, dsp, runoff_veg, runoff, drainage, humrel, vegstress, &
224---
225>          & gqsb, bqsb, dsg, dss, rsol, drysoil_frac, hdry, dsp, runoff, run_off_tot, drainage, humrel, vegstress, &
226303c290
227<             & runoff, drainage )
228---
229>             & run_off_tot, drainage )
230317c304
231<        CALL histwrite(hist_id, 'runoff', kjit, runoff, kjpindex, index)
232---
233>        CALL histwrite(hist_id, 'runoff', kjit, run_off_tot, kjpindex, index)
234339c326
235<        histvar(:)=runoff(:)/one_day
236---
237>        histvar(:)=run_off_tot(:)/one_day
238342c329
239<        histvar(:)=(runoff(:)+drainage(:))/one_day
240---
241>        histvar(:)=(run_off_tot(:)+drainage(:))/one_day
242351c338
243<        CALL histwrite(hist_id, 'Qs', kjit, runoff, kjpindex, index)
244---
245>        CALL histwrite(hist_id, 'Qs', kjit, run_off_tot, kjpindex, index)
246373c360
247<           CALL histwrite(hist2_id, 'runoff', kjit, runoff, kjpindex, index)
248---
249>           CALL histwrite(hist2_id, 'runoff', kjit, run_off_tot, kjpindex, index)
250392c379
251<           histvar(:)=(runoff(:)+drainage(:))/one_day
252---
253>           histvar(:)=(run_off_tot(:)+drainage(:))/one_day
254398c385
255<           CALL histwrite(hist2_id, 'Qs', kjit, runoff, kjpindex, index)
256---
257>           CALL histwrite(hist2_id, 'Qs', kjit, run_off_tot, kjpindex, index)
258455d441
259<     CHARACTER(LEN=80)                                  :: var_name !! To store variables names for I/O
260458,459c444,445
261<     IF (l_first_hydrolc) THEN
262<         l_first_hydrolc=.FALSE.
263---
264>     IF (l_first_hydrol) THEN
265>         l_first_hydrol=.FALSE.
266461c447
267<         WRITE (numout,*) ' l_first_hydrolc false . we stop '
268---
269>         WRITE (numout,*) ' l_first_hydrol false . we stop '
270607c593
271<     ALLOCATE (runoff_veg(kjpindex,nvm),stat=ier)
272---
273>     ALLOCATE (runoff(kjpindex,nvm),stat=ier)
274609c595
275<         WRITE (numout,*) ' error in runoff_veg allocation. We stop. We need kjpindex words = ',kjpindex*nvm
276---
277>         WRITE (numout,*) ' error in runoff allocation. We stop. We need kjpindex words = ',kjpindex*nvm
278612c598
279<     runoff_veg(:,:) = zero
280---
281>     runoff(:,:) = zero
282977,986d962
283<     !Config  Key  = PERCENT_THROUGHFALL_PFT
284<     !Config  Desc = Percent by PFT of precip that is not intercepted by the canopy
285<     !Config  Def  = 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30.
286<     !Config  Help = During one rainfall event, PERCENT_THROUGHFALL_PFT% of the incident rainfall
287<     !Config         will get directly to the ground without being intercepted, for each PFT.
288<       
289<     throughfall_by_pft = (/ 30., 30., 30., 30., 30., 30., 30., 30., 30., 30., 30., 30., 30. /)
290<     CALL getin_p('PERCENT_THROUGHFALL_PFT',throughfall_by_pft)
291<     throughfall_by_pft = throughfall_by_pft / 100.
292<     !
293995c971
294<     l_first_hydrolc=.TRUE.
295---
296>     l_first_hydrol=.TRUE.
2971015c991
298<     IF (ALLOCATED  (runoff_veg)) DEALLOCATE (runoff_veg)
299---
300>     IF (ALLOCATED  (runoff)) DEALLOCATE (runoff)
3011482a1459,1474
302>     LOGICAL, SAVE                                  :: firstcall=.TRUE.
303>     REAL(r_std), SAVE, DIMENSION(nvm)              :: throughfall_by_pft
304>
305>     IF ( firstcall ) THEN
306>        !Config  Key  = PERCENT_THROUGHFALL_PFT
307>        !Config  Desc = Percent by PFT of precip that is not intercepted by the canopy
308>        !Config  Def  = 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30.
309>        !Config  Help = During one rainfall event, PERCENT_THROUGHFALL_PFT% of the incident rainfall
310>        !Config         will get directly to the ground without being intercepted, for each PFT.
311>       
312>        throughfall_by_pft = (/ 30., 30., 30., 30., 30., 30., 30., 30., 30., 30., 30., 30., 30. /)
313>        CALL getin_p('PERCENT_THROUGHFALL_PFT',throughfall_by_pft)
314>        throughfall_by_pft = throughfall_by_pft / 100.
315>
316>        firstcall=.FALSE.
317>     ENDIF
3181690c1682
319<        & gqsb, bqsb, dsg, dss, rsol, drysoil_frac, hdry, dsp, runoff_veg, run_off_tot, drainage, humrel, vegstress, &
320---
321>        & gqsb, bqsb, dsg, dss, rsol, drysoil_frac, hdry, dsp, runoff, run_off_tot, drainage, humrel, vegstress, &
3221714c1706
323<     REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(out)       :: runoff_veg           !! Ruissellement
324---
325>     REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(out)       :: runoff           !! Ruissellement
3261833c1825
327<     runoff_veg(:,:) = zero
328---
329>     runoff(:,:) = zero
3301841c1833
331<         runoff_veg(ji,jv) = MAX(gqsb(ji,jv) + bqsb(ji,jv) - mx_eau_var(ji), zero)
332---
333>         runoff(ji,jv) = MAX(gqsb(ji,jv) + bqsb(ji,jv) - mx_eau_var(ji), zero)
3341946c1938
335<       !      WRITE (numout,*) 'runoff_veg = ',runoff_veg(ji,jv)
336---
337>       !      WRITE (numout,*) 'runoff = ',runoff(ji,jv)
3382079c2071
339<             runoff_veg(ji,jv) = runoff_veg(ji,jv) + &
340---
341>             runoff(ji,jv) = runoff(ji,jv) + &
3422116c2108
343<         run_off_tot(ji) = run_off_tot(ji) + (runoff_veg(ji,jv)*veget(ji,jv))
344---
345>         run_off_tot(ji) = run_off_tot(ji) + (runoff(ji,jv)*veget(ji,jv))
3462526c2518
347<     LOGICAL, SAVE                                       :: firstcall_hdiff=.TRUE.
348---
349>     LOGICAL, SAVE                                       :: firstcall=.TRUE.
3502528c2520
351<     IF ( firstcall_hdiff ) THEN
352---
353>     IF ( firstcall ) THEN
3542543c2535
355<       firstcall_hdiff = .FALSE.
356---
357>       firstcall = .FALSE.
358diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_sechiba/hydrol.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_sechiba/hydrol.f90
3597c7
360< !< $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/tags/ORCHIDEE_1_9_5_2/ORCHIDEE/src_sechiba/hydrol.f90 $
361---
362> !< $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/trunk/ORCHIDEE/src_sechiba/hydrol.f90 $
36341a42
364>   LOGICAL, SAVE                                     :: check_waterbal=.TRUE. !! The check the water balance
36544a46
366>   CHARACTER(LEN=80) , SAVE                          :: var_name         !! To store variables names for I/O
36793c95
368<   REAL(r_std), SAVE, DIMENSION (nslm+1,nstm)         :: zh               !!
369---
370>   REAL(r_std), SAVE, DIMENSION (nslm+1,nstm)         :: zz               !!
371164,165d165
372<   REAL(r_std), SAVE, DIMENSION(nvm)                 :: throughfall_by_pft
373<     
374167,181d166
375< ! List of subroutines for initialization :
376< !- hydrol_init
377< !- hydrol_clear
378< !- hydrol_var_init
379< !- hydrol_snow
380< !- hydrol_canop
381< !- hydrol_vegupd
382< !- hydrol_soil
383< !- hydrol_soil_tridiag
384< !- hydrol_soil_setup
385< !- hydrol_split_soil
386< !- hydrol_diag_soil
387< !- hydrol_waterbal
388< !- hydrol_alma
389<
390203c188
391<        & humrel, vegstress, drysoil_frac, evapot, evapot_corr, evap_bare_lim, &
392---
393>        & humrel, vegstress, drysoil_frac, evapot, evapot_penm, evap_bare_lim, &
394236c221
395<     REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: evapot_corr      !! Soil Potential Evaporation Correction
396---
397>     REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: evapot_penm      !! Soil Potential Evaporation Correction
398264d248
399<     CHARACTER(LEN=80)                                 :: var_name  !! To store variables names for I/O
400371c355
401<          & evapot_corr, runoff, drainage, returnflow, irrigation, &
402---
403>          & evapot_penm, runoff, drainage, returnflow, irrigation, &
404509d492
405<     CHARACTER(LEN=80)                                  :: var_name  !! To store variables names for I/O
4061253,1261d1235
407<     !Config  Key  = PERCENT_THROUGHFALL_PFT
408<     !Config  Desc = Percent by PFT of precip that is not intercepted by the canopy
409<     !Config  Def  = 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30.
410<     !Config  Help = During one rainfall event, PERCENT_THROUGHFALL_PFT% of the incident rainfall
411<     !Config         will get directly to the ground without being intercepted, for each PFT.
412<     
413<     throughfall_by_pft = (/ 30., 30., 30., 30., 30., 30., 30., 30., 30., 30., 30., 30., 30. /)
414<     CALL getin_p('PERCENT_THROUGHFALL_PFT',throughfall_by_pft)
415<     throughfall_by_pft = throughfall_by_pft / 100.
4161418c1392
417<        zh(1,jst) = zero
418---
419>        zz(1,jst) = zero
4201421,1423c1395,1397
421<           zh(jsl,jst) = dpu(jst)* mille*((2**(jsl-1))-1)/ ((2**(nslm-1))-1)
422<           dz(jsl,jst) = zh(jsl,jst)-zh(jsl-1,jst)
423<           !          WRITE(numout,*) 'jsl, zz,dz',jsl, dpu(jst),zh(jsl,jst),dz(jsl,jst)
424---
425>           zz(jsl,jst) = dpu(jst)* mille*((2**(jsl-1))-1)/ ((2**(nslm-1))-1)
426>           dz(jsl,jst) = zz(jsl,jst)-zz(jsl-1,jst)
427>           !          WRITE(numout,*) 'jsl, zz,dz',jsl, dpu(jst),zz(jsl,jst),dz(jsl,jst)
4281425c1399
429<        zh(nslm+1,jst) = zh(nslm,jst)
430---
431>        zz(nslm+1,jst) = zz(nslm,jst)
4321630c1604
433< !!$          diaglev(jsl) = zh(jsl,1) + dz(jsl+1,1)/deux
434---
435> !!$          diaglev(jsl) = zz(jsl,1) + dz(jsl+1,1)/deux
4361632c1606
437< !!$       diaglev(nbdl) = zh(nbdl,1)
438---
439> !!$       diaglev(nbdl) = zz(nbdl,1)
4401920a1895,1911
441>     LOGICAL, SAVE                                  :: firstcall=.TRUE.
442>     REAL(r_std), SAVE, DIMENSION(nvm)              :: throughfall_by_pft
443>
444>     IF ( firstcall ) THEN
445>        !Config  Key  = PERCENT_THROUGHFALL_PFT
446>        !Config  Desc = Percent by PFT of precip that is not intercepted by the canopy
447>        !Config  Def  = 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30.
448>        !Config  Help = During one rainfall event, PERCENT_THROUGHFALL_PFT% of the incident rainfall
449>        !Config         will get directly to the ground without being intercepted, for each PFT.
450>       
451>        throughfall_by_pft = (/ 30., 30., 30., 30., 30., 30., 30., 30., 30., 30., 30., 30., 30. /)
452>        CALL getin_p('PERCENT_THROUGHFALL_PFT',throughfall_by_pft)
453>        throughfall_by_pft = throughfall_by_pft / 100.
454>
455>        firstcall=.FALSE.
456>     ENDIF
457>
4582356c2347
459<           dpue = zh(nslme(ji,jst),jst) + dz(nslme(ji,jst)+1,jst) / deux
460---
461>           dpue = zz(nslme(ji,jst),jst) + dz(nslme(ji,jst)+1,jst) / deux
4622744c2735
463<              dpue = zh(nslme(ji,jst),jst) + dz(nslme(ji,jst)+1,jst) / deux
464---
465>              dpue = zz(nslme(ji,jst),jst) + dz(nslme(ji,jst)+1,jst) / deux
4662793c2784
467<           dpue = zh(nslme(ji,jst),jst) + dz(nslme(ji,jst)+1,jst) / deux
468---
469>           dpue = zz(nslme(ji,jst),jst) + dz(nslme(ji,jst)+1,jst) / deux
4702963c2954
471<                   & /(un-EXP(-humcste(jv)*zh(nslm,jst)/mille))
472---
473>                   & /(un-EXP(-humcste(jv)*zz(nslm,jst)/mille))
4742976c2967
475<                      & (EXP(-humcste(jv)*zh(jsl,jst)/mille)) * &
476---
477>                      & (EXP(-humcste(jv)*zz(jsl,jst)/mille)) * &
4782980c2971
479<                      & -EXP(-humcste(jv)*zh(nslm,jst)/mille))
480---
481>                      & -EXP(-humcste(jv)*zz(nslm,jst)/mille))
4822993c2984
483<                   & EXP(-humcste(jv)*zh(nslm,jst)/mille) / &
484---
485>                   & EXP(-humcste(jv)*zz(nslm,jst)/mille) / &
4862995c2986
487<                   & -EXP(-humcste(jv)*zh(nslm,jst)/mille))
488---
489>                   & -EXP(-humcste(jv)*zz(nslm,jst)/mille))
490diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_sechiba/routing.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_sechiba/routing.f90
49121c21
492< !! @Version : $Revision: 390 $, $Date: 2011-08-09 10:45:55 +0200 (mar. 09 août 2011) $
493---
494> !! @Version : $Revision: 274 $, $Date: 2011-06-21 15:18:18 +0200 (mar. 21 juin 2011) $
49523,24c23,24
496< !< $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/tags/ORCHIDEE_1_9_5_2/ORCHIDEE/src_sechiba/routing.f90 $
497< !< $Date: 2011-08-09 10:45:55 +0200 (mar. 09 août 2011) $
498---
499> !< $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/trunk/ORCHIDEE/src_sechiba/routing.f90 $
500> !< $Date: 2011-06-21 15:18:18 +0200 (mar. 21 juin 2011) $
50126c26
502< !< $Revision: 390 $
503---
504> !< $Revision: 274 $
50552a53
506>   LOGICAL, SAVE                                     :: check_waterbal=.FALSE. !! The check the water balance
507141,163d141
508< ! List of subroutines for initialization :
509< !- routing_init
510< !- routing_clear
511< !- routing_diagnostic_p
512< !- routing_diagnostic
513< !- routing_basins_p
514< !- routing_basins
515< !- routing_getgrid
516< !- routing_sortcoord
517< !- routing_findbasins
518< !- routing_simplify
519< !- routing_cutbasin
520< !- routing_hierarchy
521< !- routing_findrout
522< !- routing_globalize
523< !- routing_linkup
524< !- routing_fetch
525< !- routing_truncate
526< !- routing_killbas
527< !- routing_names
528< !- routing_irrigmap
529< !- routing_waterbal
530<
531167c145
532<   SUBROUTINE routing_main(kjit, kjpindex, dtradia, ldrestart_read, ldrestart_write, index, &
533---
534>   SUBROUTINE routing_main(kjit, nbpt, dtradia, ldrestart_read, ldrestart_write, index, &
535187c165
536<     INTEGER(i_std), INTENT(in)    :: kjpindex                !! Domain size
537---
538>     INTEGER(i_std), INTENT(in)    :: nbpt                !! Domain size
539193,199c171,177
540<     INTEGER(i_std), INTENT(in)    :: index(kjpindex)         ! Indeces of the points on the map
541<     REAL(r_std), INTENT(in)       :: lalo(kjpindex,2)        ! Vector of latitude and longitudes (beware of the order !)
542<     INTEGER(i_std), INTENT(in)    :: neighbours(kjpindex,8)  ! Vector of neighbours for each grid point (1=N, 2=E, 3=S, 4=W)
543<     REAL(r_std), INTENT(in)       :: resolution(kjpindex,2)  ! The size in km of each grid-box in X and Y
544<     REAL(r_std), INTENT(in)       :: contfrac(kjpindex)      ! Fraction of land in each grid box
545<     REAL(r_std), INTENT(in)       :: totfrac_nobio(kjpindex) ! Total fraction of continental ice+lakes+...
546<     REAL(r_std), INTENT(in)       :: veget_max(kjpindex,nvm) ! Maximum vegetation fraction. We want to have the
547---
548>     INTEGER(i_std), INTENT(in)    :: index(nbpt)         ! Indeces of the points on the map
549>     REAL(r_std), INTENT(in)       :: lalo(nbpt,2)        ! Vector of latitude and longitudes (beware of the order !)
550>     INTEGER(i_std), INTENT(in)    :: neighbours(nbpt,8)  ! Vector of neighbours for each grid point (1=N, 2=E, 3=S, 4=W)
551>     REAL(r_std), INTENT(in)       :: resolution(nbpt,2)  ! The size in km of each grid-box in X and Y
552>     REAL(r_std), INTENT(in)       :: contfrac(nbpt)      ! Fraction of land in each grid box
553>     REAL(r_std), INTENT(in)       :: totfrac_nobio(nbpt) ! Total fraction of continental ice+lakes+...
554>     REAL(r_std), INTENT(in)       :: veget_max(nbpt,nvm) ! Maximum vegetation fraction. We want to have the
555201,211c179,189
556<     REAL(r_std), INTENT(in)       :: runoff(kjpindex)        ! grid-point runoff
557<     REAL(r_std), INTENT(in)       :: drainage(kjpindex)      ! grid-point drainage
558<     REAL(r_std), INTENT(in)       :: evapot(kjpindex)        ! Potential evaporation
559<     REAL(r_std), INTENT(in)       :: precip_rain(kjpindex)   ! Rainfall needed for the irrigation formula
560<     REAL(r_std), INTENT(in)       :: humrel(kjpindex,nvm)    ! Soil moisture stress
561<     REAL(r_std), INTENT(in)       :: stempdiag(kjpindex,nbdl)! Temperature profile in soil
562<     !
563<     REAL(r_std), INTENT(out)      :: returnflow(kjpindex)    ! The water flow which returns to the grid box (kg/m^2 per dt)
564<     REAL(r_std), INTENT(out)      :: irrigation(kjpindex)    ! Irrigation flux (kg/m^2 per dt)
565<     REAL(r_std), INTENT(out)      :: riverflow(kjpindex)     ! Outflow of the major rivers
566<     REAL(r_std), INTENT(out)      :: coastalflow(kjpindex)   ! Outflow on coastal points by small basins   
567---
568>     REAL(r_std), INTENT(in)       :: runoff(nbpt)        ! grid-point runoff
569>     REAL(r_std), INTENT(in)       :: drainage(nbpt)      ! grid-point drainage
570>     REAL(r_std), INTENT(in)       :: evapot(nbpt)        ! Potential evaporation
571>     REAL(r_std), INTENT(in)       :: precip_rain(nbpt)   ! Rainfall needed for the irrigation formula
572>     REAL(r_std), INTENT(in)       :: humrel(nbpt,nvm)    ! Soil moisture stress
573>     REAL(r_std), INTENT(in)       :: stempdiag(nbpt,nbdl)! Temperature profile in soil
574>     !
575>     REAL(r_std), INTENT(out)      :: returnflow(nbpt)    ! The water flow which returns to the grid box (kg/m^2 per dt)
576>     REAL(r_std), INTENT(out)      :: irrigation(nbpt)    ! Irrigation flux (kg/m^2 per dt)
577>     REAL(r_std), INTENT(out)      :: riverflow(nbpt)     ! Outflow of the major rivers
578>     REAL(r_std), INTENT(out)      :: coastalflow(nbpt)   ! Outflow on coastal points by small basins   
579217c195
580<     REAL(r_std), DIMENSION(kjpindex)  :: return_lakes
581---
582>     REAL(r_std), DIMENSION(nbpt)  :: return_lakes
583228c206
584<        CALL routing_init (kjit, kjpindex, index, dtradia, returnflow, irrigation, &
585---
586>        CALL routing_init (kjit, nbpt, index, dtradia, returnflow, irrigation, &
587240c218
588<           CALL routing_basins_p(kjpindex, lalo, neighbours, resolution, contfrac)
589---
590>           CALL routing_basins_p(nbpt, lalo, neighbours, resolution, contfrac)
591260c238
592<              CALL routing_irrigmap(kjpindex, index, lalo, neighbours, resolution, &
593---
594>              CALL routing_irrigmap(nbpt, index, lalo, neighbours, resolution, &
595268c246
596<        CALL routing_diagnostic_p(kjpindex, index, resolution, contfrac, hist_id, hist2_id)
597---
598>        CALL routing_diagnostic_p(nbpt, index, resolution, contfrac, hist_id, hist2_id)
599293c271
600<        DO ig=1,kjpindex
601---
602>        DO ig=1,nbpt
603308c286
604<           CALL routing_waterbal(kjpindex, .TRUE., runoff_mean, drainage_mean, returnflow_mean, &
605---
606>           CALL routing_waterbal(nbpt, .TRUE., runoff_mean, drainage_mean, returnflow_mean, &
607314c292
608<        DO ig=1,kjpindex
609---
610>        DO ig=1,nbpt
611320c298
612<        CALL routing_flow(kjpindex, dt_routing, runoff_mean, drainage_mean, &
613---
614>        CALL routing_flow(nbpt, dt_routing, runoff_mean, drainage_mean, &
615325c303
616<        CALL routing_lake(kjpindex, dt_routing, lakeinflow_mean, humrel_mean, return_lakes)
617---
618>        CALL routing_lake(nbpt, dt_routing, lakeinflow_mean, humrel_mean, return_lakes)
619332c310
620<           CALL routing_waterbal(kjpindex, .FALSE., runoff_mean, drainage_mean, returnflow_mean, &
621---
622>           CALL routing_waterbal(nbpt, .FALSE., runoff_mean, drainage_mean, returnflow_mean, &
623454,455c432,433
624<        CALL histwrite(hist_id, 'riversret', kjit, returnflow, kjpindex, index)
625<        CALL histwrite(hist_id, 'hydrographs', kjit, hydrographs, kjpindex, index)
626---
627>        CALL histwrite(hist_id, 'riversret', kjit, returnflow, nbpt, index)
628>        CALL histwrite(hist_id, 'hydrographs', kjit, hydrographs, nbpt, index)
629457,460c435,438
630<        CALL histwrite(hist_id, 'fastr', kjit, fast_diag, kjpindex, index)
631<        CALL histwrite(hist_id, 'slowr', kjit, slow_diag, kjpindex, index)
632<        CALL histwrite(hist_id, 'streamr', kjit, stream_diag, kjpindex, index)
633<        CALL histwrite(hist_id, 'lakevol', kjit, lake_diag, kjpindex, index)
634---
635>        CALL histwrite(hist_id, 'fastr', kjit, fast_diag, nbpt, index)
636>        CALL histwrite(hist_id, 'slowr', kjit, slow_diag, nbpt, index)
637>        CALL histwrite(hist_id, 'streamr', kjit, stream_diag, nbpt, index)
638>        CALL histwrite(hist_id, 'lakevol', kjit, lake_diag, nbpt, index)
639462c440
640<        CALL histwrite(hist_id, 'irrigation', kjit, irrigation, kjpindex, index)
641---
642>        CALL histwrite(hist_id, 'irrigation', kjit, irrigation, nbpt, index)
643464c442
644<        CALL histwrite(hist_id, 'netirrig', kjit, irrig_netereq, kjpindex, index)
645---
646>        CALL histwrite(hist_id, 'netirrig', kjit, irrig_netereq, nbpt, index)
647468c446
648<        CALL histwrite(hist_id, 'dis', kjit, hydrographs, kjpindex, index)
649---
650>        CALL histwrite(hist_id, 'dis', kjit, hydrographs, nbpt, index)
651474,475c452,453
652<           CALL histwrite(hist2_id, 'riversret', kjit, returnflow, kjpindex, index)
653<           CALL histwrite(hist2_id, 'hydrographs', kjit, hydrographs, kjpindex, index)
654---
655>           CALL histwrite(hist2_id, 'riversret', kjit, returnflow, nbpt, index)
656>           CALL histwrite(hist2_id, 'hydrographs', kjit, hydrographs, nbpt, index)
657477,480c455,458
658<           CALL histwrite(hist2_id, 'fastr', kjit, fast_diag, kjpindex, index)
659<           CALL histwrite(hist2_id, 'slowr', kjit, slow_diag, kjpindex, index)
660<           CALL histwrite(hist2_id, 'streamr', kjit, stream_diag, kjpindex, index)
661<           CALL histwrite(hist2_id, 'lakevol', kjit, lake_diag, kjpindex, index)
662---
663>           CALL histwrite(hist2_id, 'fastr', kjit, fast_diag, nbpt, index)
664>           CALL histwrite(hist2_id, 'slowr', kjit, slow_diag, nbpt, index)
665>           CALL histwrite(hist2_id, 'streamr', kjit, stream_diag, nbpt, index)
666>           CALL histwrite(hist2_id, 'lakevol', kjit, lake_diag, nbpt, index)
667482c460
668<           CALL histwrite(hist2_id, 'irrigation', kjit, irrigation, kjpindex, index)
669---
670>           CALL histwrite(hist2_id, 'irrigation', kjit, irrigation, nbpt, index)
671484c462
672<           CALL histwrite(hist2_id, 'netirrig', kjit, irrig_netereq, kjpindex, index)
673---
674>           CALL histwrite(hist2_id, 'netirrig', kjit, irrig_netereq, nbpt, index)
675488c466
676<           CALL histwrite(hist2_id, 'dis', kjit, hydrographs, kjpindex, index)
677---
678>           CALL histwrite(hist2_id, 'dis', kjit, hydrographs, nbpt, index)
679diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_sechiba/sechiba.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_sechiba/sechiba.f90
6808c8
681< !< $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/tags/ORCHIDEE_1_9_5_2/ORCHIDEE/src_sechiba/sechiba.f90 $
682---
683> !< $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/trunk/ORCHIDEE/src_sechiba/sechiba.f90 $
68489d88
685<   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)    :: t2mdiag_min    !! 2 meter temperature min over time step
686134a134
687>   CHARACTER(LEN=80) , SAVE                             :: var_name                !! To store variables names for I/O
688138,139d137
689<   LOGICAL, SAVE                                   :: ldforcing_write  !! Logical for _forcing_ file to write
690<   LOGICAL, SAVE                                   :: ldcarbon_write   !! Logical for _carbon_forcing_ file to w
691145,148d142
692< ! List of subroutines for initialization :
693< !- sechiba_init
694< !- sechiba_clear
695<
696267d260
697<     CHARACTER(LEN=80)                                  :: var_name         !! To store variables names for I/O
698318,320c311
699<        !
700<        ldforcing_write=control%ok_co2
701<        ldcarbon_write=control%ok_stomate
702---
703>
704325c316
705<             ldrestart_read, ldrestart_write, ldforcing_write, ldcarbon_write, &
706---
707>             ldrestart_read, ldrestart_write, control%ok_co2, control%ok_stomate, &
708327c318
709<             t2mdiag, t2mdiag_min, temp_sol, stempdiag, &
710---
711>             t2mdiag, t2mdiag, temp_sol, stempdiag, &
712516d506
713<     t2mdiag_min = t2mdiag
714578c568
715<          ldrestart_read, ldrestart_write, ldforcing_write, ldcarbon_write, &
716---
717>          ldrestart_read, myfalse, control%ok_co2, control%ok_stomate, &
718580c570
719<          t2mdiag, t2mdiag_min, temp_sol, stempdiag, &
720---
721>          t2mdiag, t2mdiag, temp_sol, stempdiag, &
722770c760
723<        t2mdiag_min = t2mdiag
724---
725>
726827c817
727<             ldrestart_read, ldrestart_write, ldforcing_write, ldcarbon_write, &
728---
729>             ldrestart_read, ldrestart_write, control%ok_co2, control%ok_stomate, &
730829c819
731<             t2mdiag, t2mdiag_min, temp_sol, stempdiag, &
732---
733>             t2mdiag, t2mdiag, temp_sol, stempdiag, &
734877d866
735<     CHARACTER(LEN=80)                             :: var_name         !! To store variables names for I/O
7361168,1173d1156
737<     ALLOCATE (t2mdiag_min(kjpindex),stat=ier)
738<     IF (ier.NE.0) THEN
739<        WRITE (numout,*) ' error in t2mdiag_min allocation. We stop. We need kjpindex words = ',kjpindex
740<        STOP 'sechiba_init'
741<     END IF
742<
7431434d1416
744<     IF ( ALLOCATED (albedo)) DEALLOCATE (albedo)
7451441d1422
746<     IF ( ALLOCATED (t2mdiag_min)) DEALLOCATE (t2mdiag_min)
7471447,1448d1427
748<     IF ( ALLOCATED (z0)) DEALLOCATE (z0)
749<     IF ( ALLOCATED (emis)) DEALLOCATE (emis)
750diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_sechiba/sechiba_io_p.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_sechiba/sechiba_io_p.f90
75114c14
752< !< $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/tags/ORCHIDEE_1_9_5_2/ORCHIDEE/src_sechiba/sechiba_io_p.f90 $
753---
754> !< $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/trunk/ORCHIDEE/src_sechiba/sechiba_io_p.f90 $
75546,47d45
756< ! List of subroutines for initialization :
757< !- ok_var
758diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_sechiba/slowproc.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_sechiba/slowproc.f90
7594c4
760< !< $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/tags/ORCHIDEE_1_9_5_2/ORCHIDEE/src_sechiba/slowproc.f90 $
761---
762> !< $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/trunk/ORCHIDEE/src_sechiba/slowproc.f90 $
76368,70c68,70
764<   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: veget_max_new          !! next year fraction of vegetation type
765<   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: frac_nobio_new     !! next year fraction of ice+lakes+cities+...
766<   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: totfrac_nobio_new  !! next year total fraction of ice+lakes+cities+...
767---
768>   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: veget_nextyear          !! next year fraction of vegetation type
769>   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: frac_nobio_nextyear     !! next year fraction of ice+lakes+cities+...
770>   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: totfrac_nobio_nextyear  !! next year total fraction of ice+lakes+cities+...
77173,87d72
772< ! List of subroutines for initialization :
773< !- slowproc_init
774< !- slowproc_clear
775< !- slowproc_derivvar
776< !- slowproc_veget
777< !- slowproc_lai
778< !- slowproc_interlai_OLD
779< !- slowproc_interlai_NEW
780< !- slowproc_update
781< !- slowproc_interpol_OLD
782< !- slowproc_interpol_NEW
783< !- slowproc_interpol_OLD_g
784< !- slowproc_interpol_NEW_g
785< !- slowproc_nearest
786< !- slowproc_soilt
78791,92c76,77
788<        index, indexveg, lalo, neighbours, resolution, contfrac, soiltype, &
789<        t2m, t2mdiag, temp_sol, stempdiag, &
790---
791>        IndexLand, indexveg, lalo, neighbours, resolution, contfrac, soiltype, &
792>        t2m, t2m_min, temp_sol, stempdiag, &
793118c103
794<     INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)    :: index         !! Indeces of the points on the map
795---
796>     INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)    :: IndexLand         !! Indeces of the points on the map
797126c111
798<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)        :: t2mdiag          !! min. 2 m air temp. during forcing time step (K)
799---
800>     REAL(r_std), DIMENSION(kjpindex), INTENT(in)        :: t2m_min          !! min. 2 m air temp. during forcing time step (K)
801179c164
802<        CALL slowproc_init (kjit, ldrestart_read, dtradia, date0, kjpindex, index, lalo, neighbours, resolution, contfrac, &
803---
804>        CALL slowproc_init (kjit, ldrestart_read, dtradia, date0, kjpindex, IndexLand, lalo, neighbours, resolution, contfrac, &
805198d182
806<
807204,205c188,189
808<                index, lalo, neighbours, resolution, contfrac, totfrac_nobio, clayfraction, &
809<                t2m, t2mdiag, temp_sol, stempdiag, &
810---
811>                IndexLand, lalo, neighbours, resolution, contfrac, totfrac_nobio, clayfraction, &
812>                t2m, t2m_min, temp_sol, stempdiag, &
813210c194
814<                veget_max_new, totfrac_nobio_new, &
815---
816>                veget_nextyear, totfrac_nobio_nextyear, &
817300,301c284,285
818<                index, lalo, neighbours, resolution, contfrac, totfrac_nobio, clayfraction, &
819<                t2m, t2mdiag, temp_sol, stempdiag, &
820---
821>                IndexLand, lalo, neighbours, resolution, contfrac, totfrac_nobio, clayfraction, &
822>                t2m, t2m_min, temp_sol, stempdiag, &
823306c290
824<                veget_max_new, totfrac_nobio_new, &
825---
826>                veget_nextyear, totfrac_nobio_nextyear, &
827371c355
828<                &               veget_max, frac_nobio, veget_max_new, frac_nobio_new, veget_year)
829---
830>                &               veget_max, frac_nobio, veget_nextyear, frac_nobio_nextyear, veget_year)
831374,375c358,359
832<              WHERE(veget_max_new(:,:).LT.veget(:,:))
833<                 veget(:,:) = veget_max_new(:,:)
834---
835>              WHERE(veget_nextyear(:,:).LT.veget(:,:))
836>                 veget(:,:) = veget_nextyear(:,:)
837379c363
838<                 totfrac_nobio_new(:) = totfrac_nobio_new(:) + frac_nobio_new(:,j)
839---
840>                 totfrac_nobio_nextyear(:) = totfrac_nobio_nextyear(:) + frac_nobio_nextyear(:,j)
841398,399c382,383
842<             index, lalo, neighbours, resolution, contfrac, totfrac_nobio, clayfraction, &
843<             t2m, t2mdiag, temp_sol, stempdiag, &
844---
845>             IndexLand, lalo, neighbours, resolution, contfrac, totfrac_nobio, clayfraction, &
846>             t2m, t2m_min, temp_sol, stempdiag, &
847404c388
848<             veget_max_new, totfrac_nobio_new, &
849---
850>             veget_nextyear, totfrac_nobio_nextyear, &
851448,449c432,433
852<              veget_max(:,:)=veget_max_new(:,:)
853<              frac_nobio(:,:)=frac_nobio_new(:,:)
854---
855>              veget_max(:,:)=veget_nextyear(:,:)
856>              frac_nobio(:,:)=frac_nobio_nextyear(:,:)
857465c449
858<              frac_nobio(:,:)=frac_nobio_new(:,:)
859---
860>              frac_nobio(:,:)=frac_nobio_nextyear(:,:)
861552c536
862<     ALLOCATE(veget_max_new(kjpindex, nvm), STAT=ier)
863---
864>     ALLOCATE(veget_nextyear(kjpindex, nvm), STAT=ier)
865554c538
866<       WRITE(numout,*) "ERROR IN ALLOCATION of veget_max_new : ",ier
867---
868>       WRITE(numout,*) "ERROR IN ALLOCATION of veget_nextyear : ",ier
869557,558c541,542
870<     veget_max_new(:,1) = un
871<     veget_max_new(:,2:nvm) = zero
872---
873>     veget_nextyear(:,1) = un
874>     veget_nextyear(:,2:nvm) = zero
875561c545
876<     ALLOCATE(frac_nobio_new(kjpindex, nnobio), STAT=ier)
877---
878>     ALLOCATE(frac_nobio_nextyear(kjpindex, nnobio), STAT=ier)
879563c547
880<       PRINT *,"ERROR IN ALLOCATION of frac_nobio_new : ",ier
881---
882>       PRINT *,"ERROR IN ALLOCATION of frac_nobio_nextyear : ",ier
883566c550
884<     frac_nobio_new(:,:) = zero
885---
886>     frac_nobio_nextyear(:,:) = zero
887569c553
888<     ALLOCATE(totfrac_nobio_new(kjpindex), STAT=ier)
889---
890>     ALLOCATE(totfrac_nobio_nextyear(kjpindex), STAT=ier)
891571c555
892<       PRINT *,"ERROR IN ALLOCATION of totfrac_nobio_new : ",ier
893---
894>       PRINT *,"ERROR IN ALLOCATION of totfrac_nobio_nextyear : ",ier
895575c559
896<     totfrac_nobio_new(:) = nnobio*un
897---
898>     totfrac_nobio_nextyear(:) = nnobio*un
8991036c1020
900<                &               veget_max_new, frac_nobio_new, veget_max, frac_nobio, veget_year, init=.TRUE.)
901---
902>                &               veget_nextyear, frac_nobio_nextyear, veget_max, frac_nobio, veget_year, init=.TRUE.)
9031224,1226c1208,1210
904<     IF (ALLOCATED (veget_max_new)) DEALLOCATE (veget_max_new)
905<     IF (ALLOCATED (frac_nobio_new)) DEALLOCATE (frac_nobio_new)
906<     IF (ALLOCATED (totfrac_nobio_new)) DEALLOCATE (totfrac_nobio_new)
907---
908>     IF (ALLOCATED (veget_nextyear)) DEALLOCATE (veget_nextyear)
909>     IF (ALLOCATED (frac_nobio_nextyear)) DEALLOCATE (frac_nobio_nextyear)
910>     IF (ALLOCATED (totfrac_nobio_nextyear)) DEALLOCATE (totfrac_nobio_nextyear)
911diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_sechiba/thermosoil.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_sechiba/thermosoil.f90
9127c7
913< !< $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/tags/ORCHIDEE_1_9_5_2/ORCHIDEE/src_sechiba/thermosoil.f90 $
914---
915> !< $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/trunk/ORCHIDEE/src_sechiba/thermosoil.f90 $
91638a39
917>   CHARACTER(LEN=80) , SAVE                  :: var_name                  !! To store variables names for I/O
91874,82d74
919< ! List of subroutines for initialization :
920< !- thermosoil_init
921< !- thermosoil_clear
922< !- fz
923< !- thermosoil_var_init
924< !- thermosoil_coef
925< !- thermosoil_diaglev
926< !- thermosoil_humlev
927< !- thermosoil_energy
928121d112
929<     CHARACTER(LEN=80)                :: var_name                  !! To store variables names for I/O
930354d344
931<     CHARACTER(LEN=80)                :: var_name                  !! To store variables names for I/O
932diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_sechiba/watchout.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_sechiba/watchout.f90
9338,9d7
934<   IMPLICIT NONE
935<
93651,56d48
937< ! List of subroutines for initialization :
938< !- watchout_init
939< !- watchout_write_p
940< !- watchout_write
941< !- watchout_close
942<
943diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/lpj_constraints.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/lpj_constraints.f90
94423c23
945<   LOGICAL, SAVE                                    :: firstcall_constraints = .TRUE.
946---
947>   LOGICAL, SAVE                                    :: firstcall = .TRUE.
94825,27d24
949< ! List of subroutines for initialization :
950< !- constraints_clear
951<
95231c28
953<     firstcall_constraints = .TRUE.
954---
955>     firstcall = .TRUE.
95634c31
957<   SUBROUTINE constraints_main (kjpindex, dt_days, &
958---
959>   SUBROUTINE constraints (npts, dt, &
96045c42
961<     INTEGER(i_std), INTENT(in)                              :: kjpindex
962---
963>     INTEGER(i_std), INTENT(in)                              :: npts
96447c44
965<     REAL(r_std), INTENT(in)                           :: dt_days
966---
967>     REAL(r_std), INTENT(in)                           :: dt
96849c46
969<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)          :: t2m_month
970---
971>     REAL(r_std), DIMENSION(npts), INTENT(in)          :: t2m_month
97251c48
973<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)          :: t2m_min_daily
974---
975>     REAL(r_std), DIMENSION(npts), INTENT(in)          :: t2m_min_daily
97653c50
977<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)     :: when_growthinit
978---
979>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)     :: when_growthinit
98058c55
981<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)  :: adapted
982---
983>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)  :: adapted
98460c57
985<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)  :: regenerate
986---
987>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)  :: regenerate
98865c62
989<     REAL(r_std), SAVE                                 :: tau_adapt
990---
991>     REAL(r_std)                                       :: tau_adapt
99267c64
993<     REAL(r_std), SAVE                                 :: tau_regenerate
994---
995>     REAL(r_std)                                       :: tau_regenerate
99679,80d75
997<     IF ( firstcall_constraints ) THEN
998<
99989a85,86
1000>     IF ( firstcall ) THEN
1001>
100298,99c95,96
1003<        firstcall_constraints = .FALSE.
1004<        RETURN
1005---
1006>        firstcall = .FALSE.
1007>
1008141c138
1009<              adapted(:,j) = un - ( un - adapted(:,j) ) * (tau_adapt- dt_days)/tau_adapt
1010---
1011>              adapted(:,j) = un - ( un - adapted(:,j) ) * (tau_adapt- dt)/tau_adapt
1012179c176
1013<              regenerate(:,j) = regenerate(:,j) * (tau_regenerate-dt_days)/tau_regenerate
1014---
1015>              regenerate(:,j) = regenerate(:,j) * (tau_regenerate-dt)/tau_regenerate
1016205c202
1017<          adapted, kjpindex*nvm, horipft_index)
1018---
1019>          adapted, npts*nvm, horipft_index)
1020207c204
1021<          regenerate, kjpindex*nvm, horipft_index)
1022---
1023>          regenerate, npts*nvm, horipft_index)
1024211c208
1025<   END SUBROUTINE constraints_main
1026---
1027>   END SUBROUTINE constraints
1028diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/lpj_cover.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/lpj_cover.f90
102924c24
1030<   SUBROUTINE cover (kjpindex, cn_ind, ind, biomass, &
1031---
1032>   SUBROUTINE cover (npts, cn_ind, ind, biomass, &
103334c34
1034<     INTEGER(i_std), INTENT(in)                                   :: kjpindex
1035---
1036>     INTEGER(i_std), INTENT(in)                                   :: npts
103736c36
1038<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)          :: cn_ind
1039---
1040>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)          :: cn_ind
104138c38
1042<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)          :: ind
1043---
1044>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)          :: ind
104540c40
1046<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)          :: veget_max_old
1047---
1048>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)          :: veget_max_old
104944c44
1050<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)   :: biomass
1051---
1052>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)   :: biomass
105346c46
1054<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)       :: veget_max
1055---
1056>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)       :: veget_max
105748c48
1058<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)          :: turnover_daily
1059---
1060>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)          :: turnover_daily
106150c50
1062<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)          :: bm_to_litter
1063---
1064>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)          :: bm_to_litter
106555c55
1066<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)       :: veget
1067---
1068>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)       :: veget
106957c57
1070<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)         :: lai
1071---
1072>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)         :: lai
107360c60
1074<     REAL(r_std),DIMENSION(kjpindex,nlitt,nvm,nlevs), INTENT(inout)         :: litter
1075---
1076>     REAL(r_std),DIMENSION(npts,nlitt,nvm,nlevs), INTENT(inout)         :: litter
107762c62
1078<     REAL(r_std),DIMENSION(kjpindex,ncarb,nvm), INTENT(inout)               :: carbon
1079---
1080>     REAL(r_std),DIMENSION(npts,ncarb,nvm), INTENT(inout)               :: carbon
108170c70
1082<     REAL(r_std),DIMENSION(kjpindex,nlitt,nlevs)                            :: dilu_lit
1083---
1084>     REAL(r_std),DIMENSION(npts,nlitt,nlevs)                            :: dilu_lit
108572c72
1086<     REAL(r_std),DIMENSION(kjpindex,ncarb)                                  :: dilu_soil_carbon
1087---
1088>     REAL(r_std),DIMENSION(npts,ncarb)                                  :: dilu_soil_carbon
108978,79c78,79
1090<     REAL(r_std), DIMENSION(kjpindex)                                       :: frac_nat,sum_vegettree,sum_vegetgrass
1091<     REAL(r_std), DIMENSION(kjpindex)                                       :: sum_veget_natveg
1092---
1093>     REAL(r_std), DIMENSION(npts)                                       :: frac_nat,sum_vegettree,sum_vegetgrass
1094>     REAL(r_std), DIMENSION(npts)                                       :: sum_veget_natveg
1095114c114
1096<        DO i = 1, kjpindex
1097---
1098>        DO i = 1, npts
1099135c135
1100<        DO i = 1, kjpindex         
1101---
1102>        DO i = 1, npts         
1103195c195
1104<        DO i = 1, kjpindex
1105---
1106>        DO i = 1, npts
1107237c237
1108<        DO i = 1,kjpindex
1109---
1110>        DO i = 1,npts
1111diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/lpj_crown.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/lpj_crown.f90
111229c29
1113<        &  (kjpindex, PFTpresent, ind, biomass, woodmass_ind, veget_max, cn_ind, height)
1114---
1115>        &  (npts, PFTpresent, ind, biomass, woodmass_ind, veget_max, cn_ind, height)
111636c36
1117<     INTEGER(i_std),INTENT(in) :: kjpindex
1118---
1119>     INTEGER(i_std),INTENT(in) :: npts
112038c38
1121<     LOGICAL,DIMENSION(kjpindex,nvm),INTENT(in) :: PFTpresent
1122---
1123>     LOGICAL,DIMENSION(npts,nvm),INTENT(in) :: PFTpresent
112440c40
1125<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: ind
1126---
1127>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: ind
112842c42
1129<     REAL(r_std),DIMENSION(kjpindex,nvm,nparts),INTENT(in) :: biomass
1130---
1131>     REAL(r_std),DIMENSION(npts,nvm,nparts),INTENT(in) :: biomass
113244c44
1133<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: woodmass_ind
1134---
1135>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: woodmass_ind
113650c50
1137<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(inout) :: veget_max
1138---
1139>     REAL(r_std),DIMENSION(npts,nvm),INTENT(inout) :: veget_max
114056c56
1141<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: cn_ind
1142---
1143>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: cn_ind
114460c60
1145<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(inout) :: height
1146---
1147>     REAL(r_std),DIMENSION(npts,nvm),INTENT(inout) :: height
114866c66
1149< !!$    REAL(r_std),DIMENSION(kjpindex) :: woodmass
1150---
1151> !!$    REAL(r_std),DIMENSION(npts) :: woodmass
115274c74
1153<     REAL(r_std),DIMENSION(kjpindex) :: dia
1154---
1155>     REAL(r_std),DIMENSION(npts) :: dia
1156diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/lpj_establish.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/lpj_establish.f90
115721c21
1158<   PUBLIC establish_main,establish_clear
1159---
1160>   PUBLIC establish,establish_clear
116124c24
1162<   LOGICAL, SAVE                                              :: firstcall_establish = .TRUE.
1163---
1164>   LOGICAL, SAVE                                              :: firstcall = .TRUE.
116526,28d25
1166< ! List of subroutines for initialization :
1167< !- establish_clear
1168<
116932c29
1170<     firstcall_establish = .TRUE.
1171---
1172>     firstcall = .TRUE.
117335c32
1174<   SUBROUTINE establish_main (kjpindex, dt_days, PFTpresent, regenerate, &
1175---
1176>   SUBROUTINE establish (npts, dt, PFTpresent, regenerate, &
117737c34
1178<        precip_lastyear, gdd0_lastyear, lm_lastyearmax, &
1179---
1180>        precip_annual, gdd0, lm_lastyearmax, &
118140c37
1182<        ind, biomass, age, everywhere, co2_to_bm_dgvm,veget_max, woodmass_ind)
1183---
1184>        ind, biomass, age, everywhere, co2_to_bm,veget_max, woodmass_ind)
118548c45
1186<     INTEGER(i_std), INTENT(in)                                  :: kjpindex
1187---
1188>     INTEGER(i_std), INTENT(in)                                  :: npts
118950c47
1190<     REAL(r_std), INTENT(in)                                     :: dt_days
1191---
1192>     REAL(r_std), INTENT(in)                                     :: dt
119352c49
1194<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(in)                  :: PFTpresent
1195---
1196>     LOGICAL, DIMENSION(npts,nvm), INTENT(in)                  :: PFTpresent
119754c51
1198<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: regenerate
1199---
1200>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: regenerate
120156c53
1202<     INTEGER(i_std), DIMENSION(kjpindex,8), INTENT(in)               :: neighbours
1203---
1204>     INTEGER(i_std), DIMENSION(npts,8), INTENT(in)               :: neighbours
120558c55
1206<     REAL(r_std), DIMENSION(kjpindex,2), INTENT(in)                  :: resolution
1207---
1208>     REAL(r_std), DIMENSION(npts,2), INTENT(in)                  :: resolution
120961c58
1210<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(in)                  :: need_adjacent
1211---
1212>     LOGICAL, DIMENSION(npts,nvm), INTENT(in)                  :: need_adjacent
121363c60
1214<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: herbivores
1215---
1216>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: herbivores
121765c62
1218<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                    :: precip_lastyear
1219---
1220>     REAL(r_std), DIMENSION(npts), INTENT(in)                    :: precip_annual
122167c64
1222<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                    :: gdd0_lastyear
1223---
1224>     REAL(r_std), DIMENSION(npts), INTENT(in)                    :: gdd0
122569c66
1226<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: lm_lastyearmax
1227---
1228>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: lm_lastyearmax
122971c68
1230<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: cn_ind
1231---
1232>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: cn_ind
123373c70
1234<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: lai
1235---
1236>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: lai
123775c72
1238<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                    :: avail_tree
1239---
1240>     REAL(r_std), DIMENSION(npts), INTENT(in)                    :: avail_tree
124177c74
1242<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                    :: avail_grass
1243---
1244>     REAL(r_std), DIMENSION(npts), INTENT(in)                    :: avail_grass
124579c76
1246<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)                :: npp_longterm
1247---
1248>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                :: npp_longterm
124981c78
1250<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)            :: veget_max
1251---
1252>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: veget_max
125386c83
1254<     REAL(r_std), DIMENSION(kjpindex,nvm,nleafages), INTENT(inout)  :: leaf_age
1255---
1256>     REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)  :: leaf_age
125788c85
1258<     REAL(r_std), DIMENSION(kjpindex,nvm,nleafages), INTENT(inout)  :: leaf_frac
1259---
1260>     REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)  :: leaf_frac
126190c87
1262<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)            :: ind
1263---
1264>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: ind
126592c89
1266<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)     :: biomass
1267---
1268>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)     :: biomass
126994c91
1270<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)            :: age
1271---
1272>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: age
127396c93
1274<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)            :: everywhere
1275---
1276>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: everywhere
127799c96
1278<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)                 :: co2_to_bm_dgvm
1279---
1280>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                 :: co2_to_bm
1281101c98
1282<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)                 :: woodmass_ind
1283---
1284>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                 :: woodmass_ind
1285106c103
1286<     REAL(r_std), SAVE                                           :: tau_eatup
1287---
1288>     REAL(r_std)                                                 :: tau_eatup
1289108c105
1290<     REAL(r_std), DIMENSION(kjpindex,nvm)                            :: fpc_nat
1291---
1292>     REAL(r_std), DIMENSION(npts,nvm)                           :: fpc_nat
1293110c107
1294<     REAL(r_std), DIMENSION(kjpindex)                                :: estab_rate_max_climate_tree
1295---
1296>     REAL(r_std), DIMENSION(npts)                                :: estab_rate_max_climate_tree
1297112c109
1298<     REAL(r_std), DIMENSION(kjpindex)                                :: estab_rate_max_climate_grass
1299---
1300>     REAL(r_std), DIMENSION(npts)                                :: estab_rate_max_climate_grass
1301114c111
1302<     REAL(r_std), DIMENSION(kjpindex)                                :: estab_rate_max_tree
1303---
1304>     REAL(r_std), DIMENSION(npts)                                :: estab_rate_max_tree
1305116c113
1306<     REAL(r_std), DIMENSION(kjpindex)                                :: estab_rate_max_grass
1307---
1308>     REAL(r_std), DIMENSION(npts)                                :: estab_rate_max_grass
1309118c115
1310<     REAL(r_std), DIMENSION(kjpindex)                                :: sumfpc
1311---
1312>     REAL(r_std), DIMENSION(npts)                                :: sumfpc
1313120c117
1314<     REAL(r_std), DIMENSION(kjpindex)                                :: fracnat
1315---
1316>     REAL(r_std), DIMENSION(npts)                                :: fracnat
1317122c119
1318<     REAL(r_std), DIMENSION(kjpindex)                                :: sumfpc_wood
1319---
1320>     REAL(r_std), DIMENSION(npts)                                :: sumfpc_wood
1321124c121
1322<     REAL(r_std), DIMENSION(kjpindex)                                :: spacefight_tree
1323---
1324>     REAL(r_std), DIMENSION(npts)                                :: spacefight_tree
1325126c123
1326<     REAL(r_std), DIMENSION(kjpindex)                                :: spacefight_grass
1327---
1328>     REAL(r_std), DIMENSION(npts)                                :: spacefight_grass
1329128c125
1330<     REAL(r_std), DIMENSION(kjpindex,nvm)                           :: d_ind
1331---
1332>     REAL(r_std), DIMENSION(npts,nvm)                           :: d_ind
1333130c127
1334<     REAL(r_std), DIMENSION(kjpindex)                                :: bm_new
1335---
1336>     REAL(r_std), DIMENSION(npts)                                :: bm_new
1337132c129
1338<     REAL(r_std), DIMENSION(kjpindex)                                :: dia
1339---
1340>     REAL(r_std), DIMENSION(npts)                                :: dia
1341134c131
1342<     REAL(r_std), DIMENSION(kjpindex)                                :: b1
1343---
1344>     REAL(r_std), DIMENSION(npts)                                :: b1
1345136c133
1346<     REAL(r_std), DIMENSION(kjpindex)                                :: sm2
1347---
1348>     REAL(r_std), DIMENSION(npts)                                :: sm2
1349138c135
1350<     REAL(r_std), DIMENSION(kjpindex)                                :: woodmass
1351---
1352>     REAL(r_std), DIMENSION(npts)                                :: woodmass
1353140c137
1354<     REAL(r_std), DIMENSION(kjpindex)                                :: leaf_mass_young
1355---
1356>     REAL(r_std), DIMENSION(npts)                                :: leaf_mass_young
1357142c139
1358<     REAL(r_std), DIMENSION(kjpindex)                                :: sm_at
1359---
1360>     REAL(r_std), DIMENSION(npts)                                :: sm_at
1361144c141
1362<     REAL(r_std), DIMENSION(kjpindex)                                :: factor
1363---
1364>     REAL(r_std), DIMENSION(npts)                                :: factor
1365146c143
1366<     REAL(r_std), DIMENSION(kjpindex)                                :: total_bm_c
1367---
1368>     REAL(r_std), DIMENSION(npts)                                :: total_bm_c
1369148c145
1370<     REAL(r_std), DIMENSION(kjpindex)                                :: total_bm_sapl
1371---
1372>     REAL(r_std), DIMENSION(npts)                                :: total_bm_sapl
1373153c150
1374<     !LOGICAL, DIMENSION(kjpindex)                                   :: many_new
1375---
1376>     !LOGICAL, DIMENSION(npts)                                   :: many_new
1377156c153
1378<     REAL(r_std), DIMENSION(kjpindex)                                 :: vn
1379---
1380>     REAL(r_std), DIMENSION(npts)                                 :: vn
1381158c155
1382<     REAL(r_std), DIMENSION(kjpindex)                                 :: lai_ind
1383---
1384>     REAL(r_std), DIMENSION(npts)                                 :: lai_ind
1385167,168d163
1386<     IF ( firstcall_establish ) THEN
1387<
1388173a169,170
1389>     IF ( firstcall ) THEN
1390>
1391179,180c176,177
1392<        firstcall_establish = .FALSE.
1393<        RETURN
1394---
1395>        firstcall = .FALSE.
1396>
1397284c281
1398<        WHERE ( ( precip_lastyear(:) .GE. precip_crit ) .AND. ( gdd0_lastyear(:) .GE. gdd_crit ) )
1399---
1400>        WHERE ( ( precip_annual(:) .GE. precip_crit ) .AND. ( gdd0(:) .GE. gdd_crit ) )
1401364c361
1402<                 DO i = 1, kjpindex
1403---
1404>                 DO i = 1, npts
1405392c389
1406<                            everywhere(i,j) + migrate(j) * dt_days/one_year * &
1407---
1408>                            everywhere(i,j) + migrate(j) * dt/one_year * &
1409401c398
1410<                               everywhere(i,j) + migrate(j) * dt_days/one_year * &
1411---
1412>                               everywhere(i,j) + migrate(j) * dt/one_year * &
1413430c427
1414<                         avail_tree(:) * dt_days/one_year
1415---
1416>                         avail_tree(:) * dt/one_year
1417442c439
1418<                         MAX(min_stomate,npp_longterm(:,j)*lm_lastyearmax(:,j)*sla(j)/factor(:)) * fracnat(:) * dt_days/one_year
1419---
1420>                         MAX(min_stomate,npp_longterm(:,j)*lm_lastyearmax(:,j)*sla(j)/factor(:)) * fracnat(:) * dt/one_year
1421488c485
1422<                 d_ind(:,j) = MAX( 0.0, estab_rate_max_tree(:) * dt_days/one_year)
1423---
1424>                 d_ind(:,j) = MAX( 0.0, estab_rate_max_tree(:) * dt/one_year)
1425494c491
1426<              !d_ind(:,j) = 0.1 !MAX( 0.0, estab_rate_max_tree(:) * dt_days/one_year)
1427---
1428>              !d_ind(:,j) = 0.1 !MAX( 0.0, estab_rate_max_tree(:) * dt/one_year)
1429509c506
1430<                 d_ind(:,j) = MAX(0.0 , (1.0-fpc_nat(:,j)) * dt_days/one_year )
1431---
1432>                 d_ind(:,j) = MAX(0.0 , (1.0-fpc_nat(:,j)) * dt/one_year )
1433601c598
1434<                 DO i=1,kjpindex
1435---
1436>                 DO i=1,npts
1437633c630
1438<              DO i=1,kjpindex
1439---
1440>              DO i=1,npts
1441683c680
1442<                 co2_to_bm_dgvm(:,j) = co2_to_bm_dgvm(:,j) + bm_new(:) / dt_days
1443---
1444>                 co2_to_bm(:,j) = co2_to_bm(:,j) + bm_new(:) / dt
1445693c690
1446<                 co2_to_bm_dgvm(:,j) = co2_to_bm_dgvm(:,j) + bm_new(:) / dt_days
1447---
1448>                 co2_to_bm(:,j) = co2_to_bm(:,j) + bm_new(:) / dt
1449782,804d778
1450< !!$             sm2(:) = 0.0
1451< !!$             WHERE ( d_ind(:,j) .GT. 0.0 )
1452< !!$
1453< !!$                ! ratio of above / total sap parts
1454< !!$                sm_at(:) = biomass(:,j,isapabove) / &
1455< !!$                     ( biomass(:,j,isapabove) + biomass(:,j,isapbelow) )
1456< !!$
1457< !!$                ! woodmass of an individual
1458< !!$
1459< !!$                woodmass(:) = &
1460< !!$                     ( biomass(:,j,isapabove) + biomass(:,j,isapbelow) + &
1461< !!$                     biomass(:,j,iheartabove) + biomass(:,j,iheartbelow) ) / ind(:,j)
1462< !!$
1463< !!$                ! crown area (m**2) depends on stem diameter (pipe model)
1464< !!$                dia(:) = ( woodmass(:) / ( pipe_density * pi/4. * pipe_tune2 ) ) &
1465< !!$                     ** ( 1. / ( 2. + pipe_tune3 ) )
1466< !!$
1467< !!$                b1(:) = pipe_k1 / ( sla(j) * pipe_density*pipe_tune2 * dia(:)**pipe_tune3 ) * &
1468< !!$                     ind(:,j)
1469< !!$                sm2(:) = lm_lastyearmax(:,j) / b1(:)
1470< !!$
1471< !!$             ENDWHERE
1472<
1473809a784,786
1474>                sm_at(:) = biomass(:,j,isapabove) / &
1475>                     ( biomass(:,j,isapabove) + biomass(:,j,isapbelow) )
1476>   
1477830c807
1478<     d_ind = d_ind / dt_days
1479---
1480>     d_ind = d_ind / dt
1481832,834c809,811
1482<     CALL histwrite (hist_id_stomate, 'IND_ESTAB', itime, d_ind, kjpindex*nvm, horipft_index)
1483<     CALL histwrite (hist_id_stomate, 'ESTABTREE', itime, estab_rate_max_tree, kjpindex, hori_index)
1484<     CALL histwrite (hist_id_stomate, 'ESTABGRASS', itime, estab_rate_max_grass, kjpindex, hori_index)
1485---
1486>     CALL histwrite (hist_id_stomate, 'IND_ESTAB', itime, d_ind, npts*nvm, horipft_index)
1487>     CALL histwrite (hist_id_stomate, 'ESTABTREE', itime, estab_rate_max_tree, npts, hori_index)
1488>     CALL histwrite (hist_id_stomate, 'ESTABGRASS', itime, estab_rate_max_grass, npts, hori_index)
1489838c815
1490<   END SUBROUTINE establish_main
1491---
1492>   END SUBROUTINE establish
1493diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/lpj_fire.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/lpj_fire.f90
149426c26
1495<   PUBLIC fire_main,fire_clear
1496---
1497>   PUBLIC fire,fire_clear
149829c29
1499<   LOGICAL, SAVE                                                   :: firstcall_fire = .TRUE.
1500---
1501>   LOGICAL, SAVE                                                   :: firstcall = .TRUE.
150234,36d33
1503< ! List of subroutines for initialization :
1504< !- fire_clear
1505<
150640c37
1507<     firstcall_fire = .TRUE.
1508---
1509>     firstcall = .TRUE.
151043c40
1511<   SUBROUTINE fire_main (kjpindex, dt_days, litterpart, &
1512---
1513>   SUBROUTINE fire (npts, dt, litterpart, &
151456c53
1515<     INTEGER(i_std), INTENT(in)                                             :: kjpindex
1516---
1517>     INTEGER(i_std), INTENT(in)                                             :: npts
151858c55
1519<     REAL(r_std), INTENT(in)                                          :: dt_days
1520---
1521>     REAL(r_std), INTENT(in)                                          :: dt
152260c57
1523<     REAL(r_std), DIMENSION(kjpindex,nvm,nlitt), INTENT(in)              :: litterpart
1524---
1525>     REAL(r_std), DIMENSION(npts,nvm,nlitt), INTENT(in)              :: litterpart
152662c59
1527<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                         :: litterhum_daily
1528---
1529>     REAL(r_std), DIMENSION(npts), INTENT(in)                         :: litterhum_daily
153064c61
1531<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                         :: t2m_daily
1532---
1533>     REAL(r_std), DIMENSION(npts), INTENT(in)                         :: t2m_daily
153467c64
1535<     REAL(r_std), DIMENSION(kjpindex,nvm,nlevs), INTENT(in)         :: lignin_struc
1536---
1537>     REAL(r_std), DIMENSION(npts,nvm,nlevs), INTENT(in)         :: lignin_struc
153872c69
1539<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)            :: fireindex
1540---
1541>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: fireindex
154274c71
1543<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)            :: firelitter
1544---
1545>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: firelitter
154676c73
1547<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)          :: biomass
1548---
1549>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)          :: biomass
155078c75
1551<     REAl(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)                 :: ind
1552---
1553>     REAl(r_std), DIMENSION(npts,nvm), INTENT(inout)                 :: ind
155480c77
1555<     REAL(r_std), DIMENSION(kjpindex,nlitt,nvm,nlevs), INTENT(inout):: litter
1556---
1557>     REAL(r_std), DIMENSION(npts,nlitt,nvm,nlevs), INTENT(inout):: litter
155883c80
1559<     REAL(r_std), DIMENSION(kjpindex,nvm,nlitt), INTENT(inout)           :: dead_leaves
1560---
1561>     REAL(r_std), DIMENSION(npts,nvm,nlitt), INTENT(inout)           :: dead_leaves
156285c82
1563<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)          :: bm_to_litter
1564---
1565>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)          :: bm_to_litter
156687c84
1567<     REAL(r_std), DIMENSION(kjpindex), INTENT(inout)                      :: black_carbon
1568---
1569>     REAL(r_std), DIMENSION(npts), INTENT(inout)                      :: black_carbon
157094c91
1571<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)                        :: co2_fire
1572---
1573>     REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                        :: co2_fire
1574105c102
1575<     REAL(r_std), DIMENSION(kjpindex)                                     :: fire_disturb
1576---
1577>     REAL(r_std), DIMENSION(npts)                                     :: fire_disturb
1578107c104
1579<     REAL(r_std), DIMENSION(kjpindex,nvm)                                :: firedeath
1580---
1581>     REAL(r_std), DIMENSION(npts,nvm)                                :: firedeath
1582112c109
1583<     REAL(r_std), DIMENSION(kjpindex)                                     :: moistlimit
1584---
1585>     REAL(r_std), DIMENSION(npts)                                     :: moistlimit
1586114c111
1587<     REAL(r_std), DIMENSION(kjpindex)                                     :: litter_above
1588---
1589>     REAL(r_std), DIMENSION(npts)                                     :: litter_above
1590116c113
1591<     REAL(r_std), DIMENSION(kjpindex,nvm)                           :: fireindex_daily
1592---
1593>     REAL(r_std), DIMENSION(npts,nvm)                           :: fireindex_daily
1594118c115
1595<     REAL(r_std), DIMENSION(kjpindex, nvm)                          :: firefrac
1596---
1597>     REAL(r_std), DIMENSION(npts, nvm)                          :: firefrac
1598120c117
1599<     REAL(r_std), DIMENSION(kjpindex)                                     :: struc_residual
1600---
1601>     REAL(r_std), DIMENSION(npts)                                     :: struc_residual
1602122c119
1603<     REAL(r_std), DIMENSION(kjpindex)                                     :: residue
1604---
1605>     REAL(r_std), DIMENSION(npts)                                     :: residue
1606124c121
1607<     REAL(r_std), DIMENSION(kjpindex)                                     :: bcfrac
1608---
1609>     REAL(r_std), DIMENSION(npts)                                     :: bcfrac
1610126c123
1611<     REAL(r_std), DIMENSION(kjpindex)                                     :: x
1612---
1613>     REAL(r_std), DIMENSION(npts)                                     :: x
1614128c125
1615<     REAL(r_std), DIMENSION(kjpindex)                                     :: aff
1616---
1617>     REAL(r_std), DIMENSION(npts)                                     :: aff
1618140c137
1619<     IF ( firstcall_fire ) THEN
1620---
1621>     IF ( firstcall ) THEN
1622177c174
1623<        firstcall_fire = .FALSE.
1624---
1625>        firstcall = .FALSE.
1626189d185
1627<        RETURN
1628243c239
1629<           ! with larger dt_days, one misses dry days with very high fireindex ( strongly
1630---
1631>           ! with larger dt, one misses dry days with very high fireindex ( strongly
1632259c255
1633<        fireindex(:,j) = ((tau_fire - dt_days) * fireindex(:,j) + (dt_days) * fireindex_daily(:,j)) / tau_fire
1634---
1635>        fireindex(:,j) = ((tau_fire - dt) * fireindex(:,j) + (dt) * fireindex_daily(:,j)) / tau_fire
1636267c263
1637<             ( ( tau_fire-dt_days ) * firelitter(:,j) + dt_days * litter_above(:) ) / tau_fire
1638---
1639>             ( ( tau_fire-dt ) * firelitter(:,j) + dt * litter_above(:) ) / tau_fire
1640283c279
1641<        aff(:) = firefrac_func (kjpindex, fireindex(:,j))
1642---
1643>        aff(:) = firefrac_func (npts, fireindex(:,j))
1644289c285
1645<        ! If annual firefrac<<1, then firefrac_daily = firefrac * dt_days/one_year
1646---
1647>        ! If annual firefrac<<1, then firefrac_daily = firefrac * dt/one_year
1648294c290
1649<              firefrac(:,j) = un - ( un - aff(:) ) ** (dt_days/one_year)
1650---
1651>              firefrac(:,j) = un - ( un - aff(:) ) ** (dt/one_year)
1652296c292
1653<              firefrac(:,j) = aff(:) * dt_days/one_year
1654---
1655>              firefrac(:,j) = aff(:) * dt/one_year
1656310c306
1657<        firefrac(:,j) = MAX( 0.001_r_std * dt_days/one_year, firefrac(:,j) )
1658---
1659>        firefrac(:,j) = MAX( 0.001_r_std * dt/one_year, firefrac(:,j) )
1660370c366
1661<              co2_fire(:,j) =  co2_fire(:,j)+ biomass(:,j,k) * fire_disturb(:) * co2frac(k) / dt_days
1662---
1663>              co2_fire(:,j) =  co2_fire(:,j)+ biomass(:,j,k) * fire_disturb(:) * co2frac(k) / dt
1664430,431c426,427
1665<           ! exact formulation: 1. - (1.-fire_disturb(:)) ** (1./dt_days)
1666<           firedeath(:,j) = fire_disturb(:) / dt_days
1667---
1668>           ! exact formulation: 1. - (1.-fire_disturb(:)) ** (1./dt)
1669>           firedeath(:,j) = fire_disturb(:) / dt
1670453c449
1671<             firefrac(:,j) / dt_days
1672---
1673>             firefrac(:,j) / dt
1674473c469
1675<             ( un - struc_residual(:) )/ dt_days
1676---
1677>             ( un - struc_residual(:) )/ dt
1678527c523
1679<     firefrac(:,:) = firefrac(:,:) / dt_days
1680---
1681>     firefrac(:,:) = firefrac(:,:) / dt
1682530c526
1683<          firefrac(:,:), kjpindex*nvm, horipft_index)
1684---
1685>          firefrac(:,:), npts*nvm, horipft_index)
1686532c528
1687<          firedeath(:,:), kjpindex*nvm, horipft_index)
1688---
1689>          firedeath(:,:), npts*nvm, horipft_index)
1690536c532
1691<   END SUBROUTINE fire_main
1692---
1693>   END SUBROUTINE fire
1694538c534
1695<   FUNCTION firefrac_func (kjpindex, x) RESULT (firefrac_result)
1696---
1697>   FUNCTION firefrac_func (npts, x) RESULT (firefrac_result)
1698547c543
1699<     INTEGER(i_std), INTENT(in)                                             :: kjpindex
1700---
1701>     INTEGER(i_std), INTENT(in)                                             :: npts
1702549c545
1703<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                         :: x
1704---
1705>     REAL(r_std), DIMENSION(npts), INTENT(in)                         :: x
1706554c550
1707<     REAL(r_std), DIMENSION(kjpindex)                                     :: firefrac_result
1708---
1709>     REAL(r_std), DIMENSION(npts)                                     :: firefrac_result
1710559c555
1711<     REAL(r_std), DIMENSION(kjpindex)                                     :: xm1
1712---
1713>     REAL(r_std), DIMENSION(npts)                                     :: xm1
1714diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/lpj_gap.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/lpj_gap.f90
171526c26
1716<   PUBLIC gap_main,gap_clear
1717---
1718>   PUBLIC gap,gap_clear
171929c29
1720<   LOGICAL, SAVE                                           :: firstcall_gap = .TRUE.
1721---
1722>   LOGICAL, SAVE                                           :: firstcall = .TRUE.
172332,33c32
1724< ! List of subroutines for initialization :
1725< !- gap_clear
1726---
1727>
172836c35
1729<     firstcall_gap = .TRUE.
1730---
1731>     firstcall = .TRUE.
173239c38
1733<   SUBROUTINE gap_main (kjpindex, dt_days, &
1734---
1735>   SUBROUTINE gap (npts, dt, &
173650c49
1737<     INTEGER(i_std), INTENT(in)                                     :: kjpindex
1738---
1739>     INTEGER(i_std), INTENT(in)                                     :: npts
174052c51
1741<     REAL(r_std), INTENT(in)                                  :: dt_days
1742---
1743>     REAL(r_std), INTENT(in)                                  :: dt
174454c53
1745<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)            :: npp_longterm
1746---
1747>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: npp_longterm
174856c55
1749<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(in)     :: turnover_longterm
1750---
1751>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(in)     :: turnover_longterm
175258c57
1753<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)            :: lm_lastyearmax
1754---
1755>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: lm_lastyearmax
175663c62
1757<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(in)            :: PFTpresent
1758---
1759>     LOGICAL, DIMENSION(npts,nvm), INTENT(in)            :: PFTpresent
176065c64
1761<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)  :: biomass
1762---
1763>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)  :: biomass
176467c66
1765<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)         :: ind
1766---
1767>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)         :: ind
176869c68
1769<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)  :: bm_to_litter
1770---
1771>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)  :: bm_to_litter
177271c70
1773<     REAL(r_std), DIMENSION(kjpindex,nvm),INTENT(out)             :: mortality
1774---
1775>     REAL(r_std), DIMENSION(npts,nvm),INTENT(out)             :: mortality
177676c75
1777<     REAL(r_std), DIMENSION(kjpindex)                             :: delta_biomass
1778---
1779>     REAL(r_std), DIMENSION(npts)                             :: delta_biomass
178078c77
1781<     REAL(r_std), DIMENSION(kjpindex)                             :: dmortality
1782---
1783>     REAL(r_std), DIMENSION(npts)                             :: dmortality
178480c79
1785<     REAL(r_std), DIMENSION(kjpindex)                             :: vigour
1786---
1787>     REAL(r_std), DIMENSION(npts)                             :: vigour
178882c81
1789<     REAL(r_std), DIMENSION(kjpindex)                             :: availability
1790---
1791>     REAL(r_std), DIMENSION(npts)                             :: availability
179289c88,90
1793<     IF ( firstcall_gap ) THEN
1794---
1795>     IF ( firstcall ) THEN
1796>
1797>        firstcall = .FALSE.
179891,92d91
1799<        firstcall_gap = .FALSE.
1800<        RETURN
1801161c160
1802<                 ! Exact formulation: mor = 1. - ( 1. - availability ) ** (dt_days/one_year)
1803---
1804>                 ! Exact formulation: mor = 1. - ( 1. - availability ) ** (dt/one_year)
1805164,165c163,164
1806<                 mortality(:,j) = MAX(min_avail,availability(:))  * dt_days/one_year 
1807< !!$                mortality(:,j) = availability(:) * dt_days/one_year
1808---
1809>                 mortality(:,j) = MAX(min_avail,availability(:))  * dt/one_year 
1810> !!$                mortality(:,j) = availability(:) * dt/one_year
1811177c176
1812<                 mortality(:,j) = dt_days/(residence_time(j)*one_year)
1813---
1814>                 mortality(:,j) = dt/(residence_time(j)*one_year)
1815262,263c261,262
1816<     ! exact formulation: 1. - ( 1. - mortality ) ** (1./dt_days)
1817<     mortality = mortality / dt_days
1818---
1819>     ! exact formulation: 1. - ( 1. - mortality ) ** (1./dt)
1820>     mortality = mortality / dt
1821266c265
1822<          mortality, kjpindex*nvm, horipft_index)
1823---
1824>          mortality, npts*nvm, horipft_index)
1825270c269
1826<   END SUBROUTINE gap_main
1827---
1828>   END SUBROUTINE gap
1829diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/lpj_kill.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/lpj_kill.f90
183024c24
1831<   SUBROUTINE kill (kjpindex, whichroutine, lm_lastyearmax, &
1832---
1833>   SUBROUTINE kill (npts, whichroutine, lm_lastyearmax, &
183436c36
1835<     INTEGER(i_std), INTENT(in)                                       :: kjpindex
1836---
1837>     INTEGER(i_std), INTENT(in)                                       :: npts
183840c40
1839<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)              :: lm_lastyearmax
1840---
1841>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)              :: lm_lastyearmax
184245c45
1843<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)           :: ind
1844---
1845>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: ind
184647c47
1847<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(inout)              :: PFTpresent
1848---
1849>     LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: PFTpresent
185049c49
1851<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)           :: cn_ind
1852---
1853>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: cn_ind
185451c51
1855<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)    :: biomass
1856---
1857>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)    :: biomass
185853c53
1859<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(inout)              :: senescence
1860---
1861>     LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: senescence
186255c55
1863<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)           :: RIP_time
1864---
1865>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: RIP_time
186657c57
1867<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)           :: lai
1868---
1869>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)           :: lai
187059c59
1871<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)           :: age
1872---
1873>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: age
187461c61
1875<     REAL(r_std), DIMENSION(kjpindex,nvm,nleafages), INTENT(inout) :: leaf_age
1876---
1877>     REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout) :: leaf_age
187863c63
1879<     REAL(r_std), DIMENSION(kjpindex,nvm,nleafages), INTENT(inout) :: leaf_frac
1880---
1881>     REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout) :: leaf_frac
188265c65
1883<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)           :: when_growthinit
1884---
1885>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: when_growthinit
188667c67
1887<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)           :: everywhere
1888---
1889>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: everywhere
189070c70
1891<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)           :: veget
1892---
1893>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: veget
189472c72
1895<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)           :: veget_max
1896---
1897>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: veget_max
189874c74
1899<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)           :: npp_longterm
1900---
1901>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: npp_longterm
190276c76
1903<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)    :: bm_to_litter
1904---
1905>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)    :: bm_to_litter
190683c83
1907<     LOGICAL, DIMENSION(kjpindex)                                  :: was_killed
1908---
1909>     LOGICAL, DIMENSION(npts)                                  :: was_killed
1910diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/lpj_light.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/lpj_light.f90
191144c44
1912<   PUBLIC light_main, light_clear
1913---
1914>   PUBLIC light, light_clear
191547c47
1916<   LOGICAL, SAVE                                            :: firstcall_light = .TRUE.
1917---
1918>   LOGICAL, SAVE                                            :: firstcall = .TRUE.
191950,51d49
1920< ! List of subroutines for initialization :
1921< !- light_clear
192254c52
1923<     firstcall_light=.TRUE.
1924---
1925>     firstcall=.TRUE.
192657c55
1927<   SUBROUTINE light_main (kjpindex, dt_days, &
1928---
1929>   SUBROUTINE light (npts, dt, &
193068c66
1931<     INTEGER(i_std), INTENT(in)                                      :: kjpindex
1932---
1933>     INTEGER(i_std), INTENT(in)                                      :: npts
193470c68
1935<     REAL(r_std), INTENT(in)                                   :: dt_days
1936---
1937>     REAL(r_std), INTENT(in)                                   :: dt
193872c70
1939<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(in)                :: PFTpresent
1940---
1941>     LOGICAL, DIMENSION(npts,nvm), INTENT(in)                :: PFTpresent
194274c72
1943<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)             :: cn_ind
1944---
1945>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: cn_ind
194676c74
1947<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)             :: lai
1948---
1949>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: lai
195078c76
1951<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)             :: maxfpc_lastyear
1952---
1953>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: maxfpc_lastyear
195480c78
1955<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)             :: lm_lastyearmax
1956---
1957>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: lm_lastyearmax
195882c80
1959<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)             :: veget_max
1960---
1961>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: veget_max
196284c82
1963<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)             :: fpc_max
1964---
1965>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: fpc_max
196689c87
1967<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)          :: ind
1968---
1969>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)          :: ind
197091c89
1971<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)   :: biomass
1972---
1973>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)   :: biomass
197493c91
1975<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)          :: veget_lastlight
1976---
1977>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)          :: veget_lastlight
197895c93
1979<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)   :: bm_to_litter
1980---
1981>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)   :: bm_to_litter
198297c95
1983<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)          :: mortality
1984---
1985>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)          :: mortality
1986111c109
1987<     REAL(r_std), DIMENSION(kjpindex)                              :: sumfpc
1988---
1989>     REAL(r_std), DIMENSION(npts)                              :: sumfpc
1990113c111
1991<     REAL(r_std), DIMENSION(kjpindex)                              :: fracnat
1992---
1993>     REAL(r_std), DIMENSION(npts)                              :: fracnat
1994125c123
1995<     REAL(r_std), DIMENSION(kjpindex,nvm)                         :: fpc_nat
1996---
1997>     REAL(r_std), DIMENSION(npts,nvm)                         :: fpc_nat
1998133c131
1999<     REAL(r_std), DIMENSION(kjpindex)                              :: fpc_real
2000---
2001>     REAL(r_std), DIMENSION(npts)                              :: fpc_real
2002135c133
2003<     REAL(r_std), DIMENSION(kjpindex)                              :: lai_ind
2004---
2005>     REAL(r_std), DIMENSION(npts)                              :: lai_ind
2006141c139
2007<     REAL(r_std), DIMENSION(kjpindex,nvm)                         :: light_death
2008---
2009>     REAL(r_std), DIMENSION(npts,nvm)                         :: light_death
2010153c151
2011<     IF ( firstcall_light ) THEN
2012---
2013>     IF ( firstcall ) THEN
2014173,174c171,172
2015<        firstcall_light = .FALSE.
2016<        RETURN
2017---
2018>        firstcall = .FALSE.
2019>
2020207c205
2021<                 !          DO i = 1, kjpindex
2022---
2023>                 !          DO i = 1, npts
2024246c244
2025< !!$                   DO i = 1, kjpindex
2026---
2027> !!$                   DO i = 1, npts
2028284c282
2029<        DO i = 1, kjpindex ! SZ why this loop and not a vector statement ?
2030---
2031>        DO i = 1, npts ! SZ why this loop and not a vector statement ?
2032503,504c501,502
2033<                    ! exact formulation: light_death(i,j) = un - survive(j) / dt_days
2034<                    light_death(i,j) = ( un - survive(j) ) / dt_days
2035---
2036>                    ! exact formulation: light_death(i,j) = un - survive(j) / dt
2037>                    light_death(i,j) = ( un - survive(j) ) / dt
2038530c528
2039<                 DO i = 1, kjpindex
2040---
2041>                 DO i = 1, npts
2042552c550
2043<                 DO i = 1, kjpindex
2044---
2045>                 DO i = 1, npts
2046619c617
2047<        light_death(:,:)=light_death(:,:)/dt_days
2048---
2049>        light_death(:,:)=light_death(:,:)/dt
2050628c626
2051<          light_death, kjpindex*nvm, horipft_index)
2052---
2053>          light_death, npts*nvm, horipft_index)
2054632c630
2055<   END SUBROUTINE light_main
2056---
2057>   END SUBROUTINE light
2058diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/lpj_pftinout.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/lpj_pftinout.f90
205923c23
2060<   LOGICAL, SAVE                                             :: firstcall_pftinout = .TRUE.
2061---
2062>   LOGICAL, SAVE                                             :: firstcall = .TRUE.
206326,27c26
2064< ! List of subroutines for initialization :
2065< !- pftinout_clear
2066---
2067>
206830c29
2069<     firstcall_pftinout = .TRUE.
2070---
2071>     firstcall = .TRUE.
207233c32
2073<   SUBROUTINE pftinout_main (kjpindex, dt_days, adapted, regenerate, &
2074---
2075>   SUBROUTINE pftinout (npts, dt, adapted, regenerate, &
207637c36
2077<        co2_to_bm_dgvm, &
2078---
2079>        co2_to_bm, &
208047c46
2081<     INTEGER(i_std), INTENT(in)                                       :: kjpindex
2082---
2083>     INTEGER(i_std), INTENT(in)                                       :: npts
208449c48
2085<     REAL(r_std), INTENT(in)                                    :: dt_days
2086---
2087>     REAL(r_std), INTENT(in)                                    :: dt
208851c50
2089<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)              :: adapted
2090---
2091>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)              :: adapted
209253c52
2093<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)              :: regenerate
2094---
2095>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)              :: regenerate
209655c54
2097<     INTEGER(i_std), DIMENSION(kjpindex,8), INTENT(in)              :: neighbours
2098---
2099>     INTEGER(i_std), DIMENSION(npts,8), INTENT(in)              :: neighbours
210058c57
2101<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)           :: veget
2102---
2103>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: veget
210460c59
2105<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)           :: veget_max
2106---
2107>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: veget_max
210865c64
2109<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)    :: biomass
2110---
2111>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)    :: biomass
211267c66
2113<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)           :: ind
2114---
2115>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: ind
211669c68
2117<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)              :: cn_ind
2118---
2119>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)              :: cn_ind
212071c70
2121<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)           :: age
2122---
2123>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: age
212473c72
2125<     REAL(r_std), DIMENSION(kjpindex,nvm,nleafages), INTENT(inout) :: leaf_frac
2126---
2127>     REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout) :: leaf_frac
212875c74
2129<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)           :: npp_longterm
2130---
2131>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: npp_longterm
213277c76
2133<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)           :: lm_lastyearmax
2134---
2135>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: lm_lastyearmax
213680c79
2137<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(inout)              :: senescence
2138---
2139>     LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: senescence
214082c81
2141<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(inout)              :: PFTpresent
2142---
2143>     LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: PFTpresent
214484c83
2145<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)           :: everywhere
2146---
2147>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: everywhere
214886c85
2149<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)           :: when_growthinit
2150---
2151>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: when_growthinit
215289c88
2153<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(inout)              :: need_adjacent
2154---
2155>     LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: need_adjacent
215691c90
2157<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)           :: RIP_time
2158---
2159>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: RIP_time
216094c93
2161<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)                :: co2_to_bm_dgvm
2162---
2163>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                :: co2_to_bm
216499c98
2165<     REAL(r_std), DIMENSION(kjpindex), INTENT(out)                  :: avail_tree
2166---
2167>     REAL(r_std), DIMENSION(npts), INTENT(out)                  :: avail_tree
2168101c100
2169<     REAL(r_std), DIMENSION(kjpindex), INTENT(out)                  :: avail_grass
2170---
2171>     REAL(r_std), DIMENSION(npts), INTENT(out)                  :: avail_grass
2172108c107
2173<     REAL(r_std), DIMENSION(kjpindex)                               :: avail
2174---
2175>     REAL(r_std), DIMENSION(npts)                               :: avail
2176112c111
2177<     REAL(r_std), DIMENSION(kjpindex)                               :: sumfrac_wood
2178---
2179>     REAL(r_std), DIMENSION(npts)                               :: sumfrac_wood
2180114c113
2181<     INTEGER(i_std), DIMENSION(kjpindex)                            :: n_present
2182---
2183>     INTEGER(i_std), DIMENSION(npts)                            :: n_present
2184116c115
2185<     LOGICAL, DIMENSION(kjpindex)                                  :: can_introduce
2186---
2187>     LOGICAL, DIMENSION(npts)                                  :: can_introduce
2188118c117
2189<     REAL(r_std), DIMENSION(kjpindex)                               :: fracnat
2190---
2191>     REAL(r_std), DIMENSION(npts)                               :: fracnat
2192128c127
2193<     IF ( firstcall_pftinout ) THEN
2194---
2195>     IF ( firstcall ) THEN
2196132,133c131,132
2197<        firstcall_pftinout = .FALSE.
2198<        RETURN
2199---
2200>        firstcall = .FALSE.
2201>
2202177c176
2203<     RIP_time = RIP_time + dt_days / one_year
2204---
2205>     RIP_time = RIP_time + dt / one_year
2206204c203
2207<              DO i = 1, kjpindex
2208---
2209>              DO i = 1, npts
2210215c214
2211<                    co2_to_bm_dgvm(i,j) =  co2_to_bm_dgvm(i,j) +SUM( biomass(i,j,:) ) / dt_days
2212---
2213>                    co2_to_bm(i,j) =  co2_to_bm(i,j) +SUM( biomass(i,j,:) ) / dt
2214280c279
2215<           DO i = 1, kjpindex
2216---
2217>           DO i = 1, npts
2218367c366
2219<              ind(:,j) = ind_0 * (dt_days/one_year) * avail(:)
2220---
2221>              ind(:,j) = ind_0 * (dt/one_year) * avail(:)
2222391,392c390,391
2223<              co2_to_bm_dgvm(:,j) = &
2224<                   co2_to_bm_dgvm(:,j) / dt_days * &
2225---
2226>              co2_to_bm(:,j) = &
2227>                   co2_to_bm(:,j) / dt * &
2228453c452
2229<   END SUBROUTINE pftinout_main
2230---
2231>   END SUBROUTINE pftinout
2232diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/stomate_alloc.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/stomate_alloc.f90
223330c30
2234<   LOGICAL, SAVE                                             :: firstcall_alloc = .TRUE.
2235---
2236>   LOGICAL, SAVE                                             :: firstcall = .TRUE.
223732,34d31
2238< ! List of subroutines for initialization :
2239< !- alloc_clear
2240<
224136c33
2242<     firstcall_alloc = .TRUE.
2243---
2244>     firstcall = .TRUE.
224539c36
2246<   SUBROUTINE alloc_main (kjpindex, dt_days, &
2247---
2248>   SUBROUTINE alloc (npts, dt, &
224951c48
2250<     INTEGER(i_std), INTENT(in)                                       :: kjpindex
2251---
2252>     INTEGER(i_std), INTENT(in)                                       :: npts
225353c50
2254<     REAL(r_std), INTENT(in)                                    :: dt_days
2255---
2256>     REAL(r_std), INTENT(in)                                    :: dt
225755c52
2258<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)              :: lai
2259---
2260>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)              :: lai
226157c54
2262<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)              :: veget_max
2263---
2264>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)              :: veget_max
226559c56
2266<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(in)                 :: senescence
2267---
2268>     LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: senescence
226961c58
2270<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)              :: when_growthinit
2271---
2272>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)              :: when_growthinit
227363c60
2274<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)              :: moiavail_week
2275---
2276>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)              :: moiavail_week
227765c62
2278<     REAL(r_std), DIMENSION(kjpindex,nbdl), INTENT(in)              :: tsoil_month
2279---
2280>     REAL(r_std), DIMENSION(npts,nbdl), INTENT(in)              :: tsoil_month
228167c64
2282<     REAL(r_std), DIMENSION(kjpindex,nbdl), INTENT(in)              :: soilhum_month
2283---
2284>     REAL(r_std), DIMENSION(npts,nbdl), INTENT(in)              :: soilhum_month
228569c66
2286<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)              :: age
2287---
2288>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)              :: age
228974c71
2290<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)    :: biomass
2291---
2292>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)    :: biomass
229376c73
2294<     REAL(r_std), DIMENSION(kjpindex,nvm,nleafages), INTENT(inout) :: leaf_age
2295---
2296>     REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout) :: leaf_age
229778c75
2298<     REAL(r_std), DIMENSION(kjpindex,nvm,nleafages), INTENT(inout) :: leaf_frac
2299---
2300>     REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout) :: leaf_frac
230185c82
2302<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)             :: rprof
2303---
2304>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)             :: rprof
230587c84
2306<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(out)      :: f_alloc
2307---
2308>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(out)      :: f_alloc
2309116c113
2310<     REAL(r_std), DIMENSION(kjpindex)                               :: limit_L
2311---
2312>     REAL(r_std), DIMENSION(npts)                               :: limit_L
2313118c115
2314<     REAL(r_std), DIMENSION(kjpindex)                               :: limit_N
2315---
2316>     REAL(r_std), DIMENSION(npts)                               :: limit_N
2317120c117
2318<     REAL(r_std), DIMENSION(kjpindex)                               :: limit_N_temp
2319---
2320>     REAL(r_std), DIMENSION(npts)                               :: limit_N_temp
2321122c119
2322<     REAL(r_std), DIMENSION(kjpindex)                               :: limit_N_hum
2323---
2324>     REAL(r_std), DIMENSION(npts)                               :: limit_N_hum
2325124c121
2326<     REAL(r_std), DIMENSION(kjpindex)                               :: limit_W
2327---
2328>     REAL(r_std), DIMENSION(npts)                               :: limit_W
2329126c123
2330<     REAL(r_std), DIMENSION(kjpindex)                               :: limit_WorN
2331---
2332>     REAL(r_std), DIMENSION(npts)                               :: limit_WorN
2333128c125
2334<     REAL(r_std), DIMENSION(kjpindex)                               :: limit
2335---
2336>     REAL(r_std), DIMENSION(npts)                               :: limit
2337132c129
2338<     REAL(r_std), DIMENSION(kjpindex)                               :: t_nitrogen
2339---
2340>     REAL(r_std), DIMENSION(npts)                               :: t_nitrogen
2341134c131
2342<     REAL(r_std), DIMENSION(kjpindex)                               :: h_nitrogen
2343---
2344>     REAL(r_std), DIMENSION(npts)                               :: h_nitrogen
2345136c133
2346<     REAL(r_std), DIMENSION(kjpindex)                               :: rpc
2347---
2348>     REAL(r_std), DIMENSION(npts)                               :: rpc
2349138c135
2350<     REAL(r_std), DIMENSION(kjpindex)                               :: LtoLSR
2351---
2352>     REAL(r_std), DIMENSION(npts)                               :: LtoLSR
2353140c137
2354<     REAL(r_std), DIMENSION(kjpindex)                               :: StoLSR
2355---
2356>     REAL(r_std), DIMENSION(npts)                               :: StoLSR
2357142c139
2358<     REAL(r_std), DIMENSION(kjpindex)                               :: RtoLSR
2359---
2360>     REAL(r_std), DIMENSION(npts)                               :: RtoLSR
2361144c141
2362<     REAL(r_std), DIMENSION(kjpindex)                               :: carb_rescale
2363---
2364>     REAL(r_std), DIMENSION(npts)                               :: carb_rescale
2365146c143
2366<     REAL(r_std), DIMENSION(kjpindex)                               :: use_reserve
2367---
2368>     REAL(r_std), DIMENSION(npts)                               :: use_reserve
2369148c145
2370<     REAL(r_std), DIMENSION(kjpindex)                               :: transloc_leaf
2371---
2372>     REAL(r_std), DIMENSION(npts)                               :: transloc_leaf
2373150c147
2374<     REAL(r_std), DIMENSION(kjpindex)                               :: leaf_mass_young
2375---
2376>     REAL(r_std), DIMENSION(npts)                               :: leaf_mass_young
2377152c149
2378<     REAL(r_std), DIMENSION(kjpindex,nvm)                          :: lm_old
2379---
2380>     REAL(r_std), DIMENSION(npts,nvm)                          :: lm_old
2381156c153
2382<     REAL(r_std), DIMENSION(kjpindex,nvm)                          :: lai_around
2383---
2384>     REAL(r_std), DIMENSION(npts,nvm)                          :: lai_around
2385158c155
2386<     REAL(r_std), DIMENSION(kjpindex,nvm)                          :: veget_max_nat
2387---
2388>     REAL(r_std), DIMENSION(npts,nvm)                          :: veget_max_nat
2389160c157
2390<     REAL(r_std), DIMENSION(kjpindex)                               :: natveg_tot
2391---
2392>     REAL(r_std), DIMENSION(npts)                               :: natveg_tot
2393162c159
2394<     REAL(r_std), DIMENSION(kjpindex)                               :: lai_nat
2395---
2396>     REAL(r_std), DIMENSION(npts)                               :: lai_nat
2397164c161
2398<     REAL(r_std), DIMENSION(kjpindex)                               :: zdiff_min
2399---
2400>     REAL(r_std), DIMENSION(npts)                               :: zdiff_min
2401166c163,165
2402<     REAL(r_std), DIMENSION(kjpindex)                               :: alloc_sap_above
2403---
2404>     REAL(r_std), DIMENSION(npts)                               :: alloc_sap_above
2405>     ! soil levels (m)
2406>     REAL(r_std), SAVE, DIMENSION(0:nbdl)                       :: z_soil
2407182c181,186
2408<     IF ( firstcall_alloc ) THEN
2409---
2410>     IF ( firstcall ) THEN
2411>
2412>        ! 1.1.1 soil levels
2413>
2414>        z_soil(0) = zero
2415>        z_soil(1:nbdl) = diaglev(1:nbdl)
2416184c188
2417<        ! 1.1.1 info about flags and parameters.
2418---
2419>        ! 1.1.2 info about flags and parameters.
2420213,214c217
2421<        firstcall_alloc = .FALSE.
2422<        RETURN
2423---
2424>        firstcall = .FALSE.
2425342c345
2426<                2._r_std * dt_days/tau_leafinit * lai_happy(j)/ sla(j) )
2427---
2428>                2._r_std * dt/tau_leafinit * lai_happy(j)/ sla(j) )
2429414,415c417,418
2430<        ! we could have alloc_sap_above(kjpindex,nvm) but we have only
2431<        ! alloc_sap_above(kjpindex) as we make a loop over j=2,nvm
2432---
2433>        ! we could have alloc_sap_above(npts,nvm) but we have only
2434>        ! alloc_sap_above(npts) as we make a loop over j=2,nvm
2435511c514
2436<        DO i = 1, kjpindex
2437---
2438>        DO i = 1, npts
2439567c570
2440<   END SUBROUTINE alloc_main
2441---
2442>   END SUBROUTINE alloc
2443diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/stomate_assimtemp.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/stomate_assimtemp.f90
244423c23
2445<   SUBROUTINE assim_temp (kjpindex, tlong_ref, t2m_month, t_photo_min, t_photo_opt, t_photo_max)
2446---
2447>   SUBROUTINE assim_temp (npts, tlong_ref, t2m_month, t_photo_min, t_photo_opt, t_photo_max)
244832c32
2449<     INTEGER(i_std), INTENT(in)                                        :: kjpindex
2450---
2451>     INTEGER(i_std), INTENT(in)                                        :: npts
245234c34
2453<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                    :: tlong_ref
2454---
2455>     REAL(r_std), DIMENSION(npts), INTENT(in)                    :: tlong_ref
245636c36
2457<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                    :: t2m_month
2458---
2459>     REAL(r_std), DIMENSION(npts), INTENT(in)                    :: t2m_month
246040c40
2461<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)              :: t_photo_min
2462---
2463>     REAL(r_std), DIMENSION(npts,nvm), INTENT(out)              :: t_photo_min
246442c42
2465<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)              :: t_photo_opt
2466---
2467>     REAL(r_std), DIMENSION(npts,nvm), INTENT(out)              :: t_photo_opt
246844c44
2469<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)              :: t_photo_max
2470---
2471>     REAL(r_std), DIMENSION(npts,nvm), INTENT(out)              :: t_photo_max
247248c48
2473<     REAL(r_std), DIMENSION(kjpindex)                                :: tl
2474---
2475>     REAL(r_std), DIMENSION(npts)                                :: tl
2476diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/stomate_constants.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/stomate_constants.f90
2477491a492
2478>   CALL getin_p("residence_time", residence_time)
2479772a774
2480>   CALL getin_p("tphoto_min_c_tab", tphoto_min_c_tab)
2481diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/stomate_data.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/stomate_data.f90
248226c26
2483<   SUBROUTINE data (kjpindex, lalo)
2484---
2485>   SUBROUTINE data (npts, lalo)
248635c35
2487<     INTEGER(i_std), INTENT(in)                               :: kjpindex
2488---
2489>     INTEGER(i_std), INTENT(in)                               :: npts
249037c37
2491<     REAL(r_std),DIMENSION (kjpindex,2), INTENT (in)        :: lalo
2492---
2493>     REAL(r_std),DIMENSION (npts,2), INTENT (in)        :: lalo
2494diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/stomate.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/stomate.f90
249535d34
2496<
249739,46d37
2498<   ! soil levels (m)
2499<   REAL(r_std),DIMENSION(0:nbdl)                   :: z_soil
2500<   ! root depth. This will, one day, be a prognostic variable.
2501<   ! It will be calculated by
2502<   ! STOMATE (save in restart file & give to hydrology module!),
2503<   ! probably somewhere
2504<   ! in the allocation routine. For the moment, it is prescribed.
2505<   REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)            :: rprof
250656c47
2507<   REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: moiavail_daily
2508---
2509>   REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: humrel_daily
251084c75
2511<   REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: moiavail_month
2512---
2513>   REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: humrel_month
251486c77
2515<   REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: moiavail_week
2516---
2517>   REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: humrel_week
2518108c99
2519<   REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: maxmoiavail_lastyear
2520---
2521>   REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: maxhumrel_lastyear
2522110c101
2523<   REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: maxmoiavail_thisyear
2524---
2525>   REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: maxhumrel_thisyear
2526112c103
2527<   REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: minmoiavail_lastyear
2528---
2529>   REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: minhumrel_lastyear
2530114c105
2531<   REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: minmoiavail_thisyear
2532---
2533>   REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: minhumrel_thisyear
2534268c259
2535<   REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)   :: moiavail_daily_fm
2536---
2537>   REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)   :: humrel_daily_fm
2538280c271
2539<   PUBLIC clay_fm, moiavail_daily_fm, litterhum_daily_fm, t2m_daily_fm, t2m_min_daily_fm, tsurf_daily_fm, tsoil_daily_fm, &
2540---
2541>   PUBLIC clay_fm, humrel_daily_fm, litterhum_daily_fm, t2m_daily_fm, t2m_min_daily_fm, tsurf_daily_fm, tsoil_daily_fm, &
2542284c275
2543<   REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)   :: moiavail_daily_fm_g
2544---
2545>   REAL(r_std),ALLOCATABLE,DIMENSION(:,:,:)   :: humrel_daily_fm_g
2546333,338d323
2547< ! List of subroutines for initialization :
2548< !- stomate_init
2549< !- stomate_clear
2550< !- stomate_var_init
2551< !- init_forcing
2552< !- forcing_zero
2553345,346c330,331
2554<        &  index, lalo, neighbours, resolution, contfrac, totfrac_nobio, clayfraction, &
2555<        &  t2mdiag, t2mdiag_min, temp_sol, stempdiag, &
2556---
2557>        &  index, lalo, neighbours, resolution, contfrac, totfrac_nobio, clay, &
2558>        &  t2m, t2m_min, temp_sol, stempdiag, &
2559406c391
2560<     REAL(r_std),DIMENSION(kjpindex),INTENT(in)       :: clayfraction
2561---
2562>     REAL(r_std),DIMENSION(kjpindex),INTENT(in)       :: clay
2563410c395
2564<     REAL(r_std),DIMENSION(kjpindex),INTENT(in)       :: t2mdiag
2565---
2566>     REAL(r_std),DIMENSION(kjpindex),INTENT(in)       :: t2m
2567412c397
2568<     REAL(r_std),DIMENSION(kjpindex),INTENT(in)       :: t2mdiag_min
2569---
2570>     REAL(r_std),DIMENSION(kjpindex),INTENT(in)       :: t2m_min
2571480a466,467
2572>     ! soil level used for LAI
2573>     INTEGER(i_std),SAVE                          :: lcanop
2574561c548,555
2575<     !
2576---
2577>     ! soil levels (m)
2578>     REAL(r_std),DIMENSION(0:nbdl)                   :: z_soil
2579>     ! root depth. This will, one day, be a prognostic variable.
2580>     ! It will be calculated by
2581>     ! STOMATE (save in restart file & give to hydrology module!),
2582>     ! probably somewhere
2583>     ! in the allocation routine. For the moment, it is prescribed.
2584>     REAL(r_std),DIMENSION(kjpindex,nvm)            :: rprof
2585579d572
2586<
2587581,589d573
2588<     !-
2589<     ! 1 do initialisation
2590<     !-
2591<     IF (l_first_stomate) THEN
2592<
2593<        IF (long_print) THEN
2594<           WRITE (numout,*) ' l_first_stomate : call stomate_init'
2595<        ENDIF
2596<
2597593,594d576
2598<       ! 1.0.0 soil levels
2599<
2600600c582,589
2601<
2602---
2603>     !-
2604>     ! 1 do initialisation
2605>     !-
2606>     resp_growth=zero
2607>     IF (l_first_stomate) THEN
2608>        IF (long_print) THEN
2609>           WRITE (numout,*) ' l_first_stomate : call stomate_init'
2610>        ENDIF
2611627c616
2612<             &         moiavail_daily, litterhum_daily, &
2613---
2614>             &         humrel_daily, litterhum_daily, &
2615631c620
2616<             &         moiavail_month, moiavail_week, &
2617---
2618>             &         humrel_month, humrel_week, &
2619634,635c623,624
2620<             &         maxmoiavail_lastyear, maxmoiavail_thisyear, &
2621<             &         minmoiavail_lastyear, minmoiavail_thisyear, &
2622---
2623>             &         maxhumrel_lastyear, maxhumrel_thisyear, &
2624>             &         minhumrel_lastyear, minhumrel_thisyear, &
2625738,739c727,728
2626<                   &      SIZE(clayfraction)*KIND(clayfraction) &
2627<                   &           +SIZE(moiavail_daily)*KIND(moiavail_daily) &
2628---
2629>                   &      SIZE(clay)*KIND(clay) &
2630>                   &           +SIZE(humrel_daily)*KIND(humrel_daily) &
2631978,1059d966
2632<
2633<        resp_growth=zero
2634<        !
2635<        CALL maint_respiration_main &
2636<             &  (kjpindex,dtradia,lai,t2mdiag,tlong_ref,stempdiag,height,veget_cov_max, &
2637<             &   rprof,biomass,resp_maint_part_radia)
2638<       
2639<        CALL littercalc_main (kjpindex, dtradia/one_day, &
2640<             turnover_littercalc, bm_to_littercalc, &
2641<             veget_cov_max, temp_sol, stempdiag, shumdiag, litterhumdiag, &
2642<             litterpart, litter, dead_leaves, lignin_struc, &
2643<             deadleaf_cover, resp_hetero_litter, &
2644<             soilcarbon_input_inst, control_temp_inst, control_moist_inst)
2645<        resp_hetero_litter=resp_hetero_litter*dtradia/one_day
2646<
2647<        CALL soilcarbon_main (kjpindex, dtradia/one_day, clayfraction, &
2648<             soilcarbon_input_inst, control_temp_inst, control_moist_inst, &
2649<             carbon, resp_hetero_soil)
2650<        resp_hetero_soil=resp_hetero_soil*dtradia/one_day
2651<        resp_hetero_radia = resp_hetero_litter+resp_hetero_soil
2652<        resp_hetero_d = resp_hetero_d + resp_hetero_radia
2653<
2654<        CALL season_main &
2655<             &          (kjpindex, dt_days, EndOfYear, &
2656<             &           veget_cov, veget_cov_max, &
2657<             &           moiavail_daily, t2m_daily, tsoil_daily, soilhum_daily, &
2658<             &           precip_daily, npp_daily, biomass, &
2659<             &           turnover_daily, gpp_daily, when_growthinit, &
2660<             &           maxmoiavail_lastyear, maxmoiavail_thisyear, &
2661<             &           minmoiavail_lastyear, minmoiavail_thisyear, &
2662<             &           maxgppweek_lastyear, maxgppweek_thisyear, &
2663<             &           gdd0_lastyear, gdd0_thisyear, &
2664<             &           precip_lastyear, precip_thisyear, &
2665<             &           lm_lastyearmax, lm_thisyearmax, &
2666<             &           maxfpc_lastyear, maxfpc_thisyear, &
2667<             &           moiavail_month, moiavail_week, t2m_longterm, &
2668<             &           tlong_ref, t2m_month, t2m_week, tsoil_month, soilhum_month, &
2669<             &           npp_longterm, turnover_longterm, gpp_week, &
2670<             &           gdd_m5_dormance, gdd_midwinter, ncd_dormance, ngd_minus5, &
2671<             &           time_lowgpp, time_hum_min, hum_min_dormance, herbivores)
2672<
2673<
2674<        IF (control%ok_stomate) THEN
2675<           
2676<           ! 6.3.1  call stomate
2677<           
2678<           CALL StomateLpj_main &
2679<                &            (kjpindex, dt_days, EndOfYear, EndOfMonth, &
2680<                &             neighbours, resolution, &
2681<                &             clayfraction, herbivores, &
2682<                &             tsurf_daily, tsoil_daily, t2m_daily, t2m_min_daily, &
2683<                &             litterhum_daily, soilhum_daily, &
2684<                &             maxmoiavail_lastyear, minmoiavail_lastyear, &
2685<                &             gdd0_lastyear, precip_lastyear, &
2686<                &             moiavail_month, moiavail_week, tlong_ref, t2m_month, t2m_week, &
2687<                &             tsoil_month, soilhum_month, &
2688<                &             gdd_m5_dormance, gdd_midwinter, ncd_dormance, ngd_minus5, &
2689<                &             turnover_longterm, gpp_daily, time_lowgpp, &
2690<                &             time_hum_min, maxfpc_lastyear, resp_maint_part,&
2691<                &             PFTpresent, age, fireindex, firelitter, &
2692<                &             leaf_age, leaf_frac, biomass, ind, adapted, regenerate, &
2693<                &             senescence, when_growthinit, litterpart, litter, &
2694<                &             dead_leaves, carbon, black_carbon, lignin_struc, &
2695<                &             veget_cov_max, veget_cov, npp_longterm, lm_lastyearmax, &
2696<                &             veget_lastlight, everywhere, need_adjacent, RIP_time, &
2697<                &             lai, rprof,npp_daily, turnover_daily, turnover_time,&
2698<                &             control_moist_inst, control_temp_inst, soilcarbon_input_inst, &
2699<                &             co2_to_bm_dgvm, co2_fire, &
2700<                &             resp_hetero_d, resp_maint_d, resp_growth_d, &
2701<                &             height, deadleaf_cover, vcmax, vjmax, &
2702<                &             t_photo_min, t_photo_opt, t_photo_max,bm_to_litter,&
2703<                &             prod10, prod100, flux10, flux100, veget_cov_max_new,&
2704<                &             convflux, cflux_prod10, cflux_prod100, harvest_above, carb_mass_total, lcchange,&
2705<                &             fpc_max)
2706<
2707<           resp_maint(:,:) = resp_maint_radia(:,:)*veget_cov_max(:,:)
2708<           resp_maint(:,ibare_sechiba) = zero
2709<           resp_growth(:,:)= resp_growth_d(:,:)*veget_cov_max(:,:)*dtradia/one_day
2710<           !
2711<           resp_hetero(:,:) = resp_hetero_radia(:,:)*veget_cov_max(:,:)
2712<           
2713<        ENDIF
27141069,1071d975
2715<
2716<     ! store time step in common value
2717<     itime = kjit
27181087c991
2719<             &          moiavail_daily, litterhum_daily, &
2720---
2721>             &          humrel_daily, litterhum_daily, &
27221091c995
2723<             &          moiavail_month, moiavail_week, &
2724---
2725>             &          humrel_month, humrel_week, &
27261094,1095c998,999
2727<             &          maxmoiavail_lastyear, maxmoiavail_thisyear, &
2728<             &          minmoiavail_lastyear, minmoiavail_thisyear, &
2729---
2730>             &          maxhumrel_lastyear, maxhumrel_thisyear, &
2731>             &          minhumrel_lastyear, minhumrel_thisyear, &
27321154c1058
2733<           CALL gather(clayfraction,clay_g)
2734---
2735>           CALL gather(clay,clay_g)
27361291c1195
2737<          &                   do_slow, humrel, moiavail_daily)
2738---
2739>          &                   do_slow, humrel, humrel_daily)
27401295c1199
2741<          &                   do_slow, t2mdiag, t2m_daily)
2742---
2743>          &                   do_slow, t2m, t2m_daily)
27441310c1214
2745<     t2m_min_daily(:) = MIN( t2mdiag_min(:), t2m_min_daily(:) )
2746---
2747>     t2m_min_daily(:) = MIN( t2m_min(:), t2m_min_daily(:) )
27481318,1319c1222,1223
2749<     CALL maint_respiration_main &
2750<          &  (kjpindex,dtradia,lai,t2mdiag,tlong_ref,stempdiag,height,veget_cov_max, &
2751---
2752>     CALL maint_respiration &
2753>          &  (kjpindex,dtradia,lai,t2m,tlong_ref,stempdiag,height,veget_cov_max, &
27541340c1244
2755<     CALL littercalc_main (kjpindex, dtradia/one_day, &
2756---
2757>     CALL littercalc (kjpindex, dtradia/one_day, &
27581354c1258
2759<     CALL soilcarbon_main (kjpindex, dtradia/one_day, clayfraction, &
2760---
2761>     CALL soilcarbon (kjpindex, dtradia/one_day, clay, &
27621389c1293
2763<        CALL season_main &
2764---
2765>        CALL season &
27661392c1296
2767<             &           moiavail_daily, t2m_daily, tsoil_daily, soilhum_daily, &
2768---
2769>             &           humrel_daily, t2m_daily, tsoil_daily, soilhum_daily, &
27701395,1396c1299,1300
2771<             &           maxmoiavail_lastyear, maxmoiavail_thisyear, &
2772<             &           minmoiavail_lastyear, minmoiavail_thisyear, &
2773---
2774>             &           maxhumrel_lastyear, maxhumrel_thisyear, &
2775>             &           minhumrel_lastyear, minhumrel_thisyear, &
27761402c1306
2777<             &           moiavail_month, moiavail_week, t2m_longterm, &
2778---
2779>             &           humrel_month, humrel_week, t2m_longterm, &
27801414c1318
2781<           CALL StomateLpj_main &
2782---
2783>           CALL StomateLpj &
27841417c1321
2785<                &             clayfraction, herbivores, &
2786---
2787>                &             clay, herbivores, &
27881420c1324
2789<                &             maxmoiavail_lastyear, minmoiavail_lastyear, &
2790---
2791>                &             maxhumrel_lastyear, minhumrel_lastyear, &
27921422c1326
2793<                &             moiavail_month, moiavail_week, tlong_ref, t2m_month, t2m_week, &
2794---
2795>                &             humrel_month, humrel_week, tlong_ref, t2m_month, t2m_week, &
27961552c1456
2797<           moiavail_daily(:,ibare_sechiba) = humrel(:,ibare_sechiba)   
2798---
2799>           humrel_daily(:,ibare_sechiba) = humrel(:,ibare_sechiba)   
28001563,1565c1467,1469
2801<              clay_fm(:,iisf) = (xn*clay_fm(:,iisf)+clayfraction(:))/(xn+1.)
2802<              moiavail_daily_fm(:,:,iisf) = &
2803<                   &                (xn*moiavail_daily_fm(:,:,iisf) + moiavail_daily(:,:))/(xn+1.)
2804---
2805>              clay_fm(:,iisf) = (xn*clay_fm(:,iisf)+clay(:))/(xn+1.)
2806>              humrel_daily_fm(:,:,iisf) = &
2807>                   &                (xn*humrel_daily_fm(:,:,iisf) + humrel_daily(:,:))/(xn+1.)
28081589,1590c1493,1494
2809<              clay_fm(:,iisf) = clayfraction(:)
2810<              moiavail_daily_fm(:,:,iisf) = moiavail_daily(:,:)
2811---
2812>              clay_fm(:,iisf) = clay(:)
2813>              humrel_daily_fm(:,:,iisf) = humrel_daily(:,:)
28141727c1631
2815<        moiavail_daily(:,:) = zero
2816---
2817>        humrel_daily(:,:) = zero
28181768,1774d1671
2819<     ELSE
2820<        co2_flux(:,:) = zero
2821<        fco2_lu(:) = zero
2822<     
2823<        resp_maint(:,:)  = zero
2824<        resp_hetero(:,:) = zero
2825<        resp_growth(:,:) = zero
28261889,1890d1785
2827<     ALLOCATE(rprof(kjpindex,nvm),stat=ier)
2828<     l_error = .FALSE.
28291901c1796
2830<     ALLOCATE(moiavail_daily(kjpindex,nvm),stat=ier)
2831---
2832>     ALLOCATE(humrel_daily(kjpindex,nvm),stat=ier)
28331925c1820
2834<     ALLOCATE(moiavail_month(kjpindex,nvm),stat=ier)
2835---
2836>     ALLOCATE(humrel_month(kjpindex,nvm),stat=ier)
28371927c1822
2838<     ALLOCATE(moiavail_week(kjpindex,nvm),stat=ier)
2839---
2840>     ALLOCATE(humrel_week(kjpindex,nvm),stat=ier)
28411945c1840
2842<     ALLOCATE(maxmoiavail_lastyear(kjpindex,nvm),stat=ier)
2843---
2844>     ALLOCATE(maxhumrel_lastyear(kjpindex,nvm),stat=ier)
28451947c1842
2846<     ALLOCATE(maxmoiavail_thisyear(kjpindex,nvm),stat=ier)
2847---
2848>     ALLOCATE(maxhumrel_thisyear(kjpindex,nvm),stat=ier)
28491949c1844
2850<     ALLOCATE(minmoiavail_lastyear(kjpindex,nvm),stat=ier)
2851---
2852>     ALLOCATE(minhumrel_lastyear(kjpindex,nvm),stat=ier)
28531951c1846
2854<     ALLOCATE(minmoiavail_thisyear(kjpindex,nvm),stat=ier)
2855---
2856>     ALLOCATE(minhumrel_thisyear(kjpindex,nvm),stat=ier)
28572189c2084
2858<     !Config  Desc = Harvest model for agricol PFTs.
2859---
2860>     !Config  Desc = Harvert model for agricol PFTs.
28612229d2123
2862<     IF (ALLOCATED(rprof)) DEALLOCATE(rprof)
28632235c2129
2864<     IF (ALLOCATED(moiavail_daily)) DEALLOCATE(moiavail_daily)
2865---
2866>     IF (ALLOCATED(humrel_daily)) DEALLOCATE(humrel_daily)
28672247,2248c2141,2142
2868<     IF (ALLOCATED(moiavail_month)) DEALLOCATE(moiavail_month)
2869<     IF (ALLOCATED(moiavail_week)) DEALLOCATE(moiavail_week)
2870---
2871>     IF (ALLOCATED(humrel_month)) DEALLOCATE(humrel_month)
2872>     IF (ALLOCATED(humrel_week)) DEALLOCATE(humrel_week)
28732257,2260c2151,2154
2874<     IF (ALLOCATED(maxmoiavail_lastyear)) DEALLOCATE(maxmoiavail_lastyear)
2875<     IF (ALLOCATED(maxmoiavail_thisyear)) DEALLOCATE(maxmoiavail_thisyear)
2876<     IF (ALLOCATED(minmoiavail_lastyear)) DEALLOCATE(minmoiavail_lastyear)
2877<     IF (ALLOCATED(minmoiavail_thisyear)) DEALLOCATE(minmoiavail_thisyear)
2878---
2879>     IF (ALLOCATED(maxhumrel_lastyear)) DEALLOCATE(maxhumrel_lastyear)
2880>     IF (ALLOCATED(maxhumrel_thisyear)) DEALLOCATE(maxhumrel_thisyear)
2881>     IF (ALLOCATED(minhumrel_lastyear)) DEALLOCATE(minhumrel_lastyear)
2882>     IF (ALLOCATED(minhumrel_thisyear)) DEALLOCATE(minhumrel_thisyear)
28832318c2212
2884<     IF (ALLOCATED(moiavail_daily_fm)) DEALLOCATE(moiavail_daily_fm)
2885---
2886>     IF (ALLOCATED(humrel_daily_fm)) DEALLOCATE(humrel_daily_fm)
28872333c2227
2888<        IF (ALLOCATED(moiavail_daily_fm_g)) DEALLOCATE(moiavail_daily_fm_g)
2889---
2890>        IF (ALLOCATED(humrel_daily_fm_g)) DEALLOCATE(humrel_daily_fm_g)
28912366d2259
2892<     IF ( ALLOCATED (carb_mass_total)) DEALLOCATE (carb_mass_total)
28932381,2382d2273
2894<     CALL maint_respiration_clear
2895<     CALL StomateLpj_clear
28962517c2408
2897<        &  (kjpindex, n_dim2, dt_tot, dt_days, ldmean, field_in, field_out)
2898---
2899>        &  (npts, n_dim2, dt_tot, dt, ldmean, field_in, field_out)
29002525c2416
2901<     INTEGER(i_std),INTENT(in)                       :: kjpindex
2902---
2903>     INTEGER(i_std),INTENT(in)                       :: npts
29042531c2422
2905<     REAL(r_std),INTENT(in)                           :: dt_days
2906---
2907>     REAL(r_std),INTENT(in)                           :: dt
29082535c2426
2909<     REAL(r_std),DIMENSION(kjpindex,n_dim2),INTENT(in)    :: field_in
2910---
2911>     REAL(r_std),DIMENSION(npts,n_dim2),INTENT(in)    :: field_in
29122540c2431
2913<     REAL(r_std),DIMENSION(kjpindex,n_dim2),INTENT(inout) :: field_out
2914---
2915>     REAL(r_std),DIMENSION(npts,n_dim2),INTENT(inout) :: field_out
29162545c2436
2917<     field_out(:,:) = field_out(:,:)+field_in(:,:)*dt_days
2918---
2919>     field_out(:,:) = field_out(:,:)+field_in(:,:)*dt
29202568c2459
2921<     ALLOCATE(moiavail_daily_fm(kjpindex,nvm,nsfm),stat=ier)
2922---
2923>     ALLOCATE(humrel_daily_fm(kjpindex,nvm,nsfm),stat=ier)
29242606c2497
2925<        ALLOCATE(moiavail_daily_fm_g(nbp_glo,nvm,nsfm),stat=ier)
2926---
2927>        ALLOCATE(humrel_daily_fm_g(nbp_glo,nvm,nsfm),stat=ier)
29282636c2527
2929<        ALLOCATE(moiavail_daily_fm_g(0,nvm,nsfm),stat=ier)
2930---
2931>        ALLOCATE(humrel_daily_fm_g(0,nvm,nsfm),stat=ier)
29322664c2555
2933<     moiavail_daily_fm(:,:,:) = zero
2934---
2935>     humrel_daily_fm(:,:,:) = zero
29362715c2606
2937<     CALL gather(moiavail_daily_fm,moiavail_daily_fm_g)
2938---
2939>     CALL gather(humrel_daily_fm,humrel_daily_fm_g)
29402740c2631
2941<              count_force(1:ndim) = SHAPE(moiavail_daily_fm_g)
2942---
2943>              count_force(1:ndim) = SHAPE(humrel_daily_fm_g)
29442744c2635
2945<                   &            moiavail_daily_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
2946---
2947>                   &            humrel_daily_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
29482867c2758
2949<           moiavail_daily_fm(:,:,iisf) = zero
2950---
2951>           humrel_daily_fm(:,:,iisf) = zero
29522925c2816
2953<              count_force(1:ndim) = SHAPE(moiavail_daily_fm_g)
2954---
2955>              count_force(1:ndim) = SHAPE(humrel_daily_fm_g)
29562930c2821
2957<                   &            moiavail_daily_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
2958---
2959>                   &            humrel_daily_fm_g(:,:,ifirst(iblocks):ilast(iblocks)), &
29603063c2954
2961<     CALL scatter(moiavail_daily_fm_g,moiavail_daily_fm)
2962---
2963>     CALL scatter(humrel_daily_fm_g,humrel_daily_fm)
29643080c2971
2965<   SUBROUTINE setlai(kjpindex,lai)
2966---
2967>   SUBROUTINE setlai(npts,lai)
29683091c2982
2969<     INTEGER(i_std),INTENT(in)                    :: kjpindex
2970---
2971>     INTEGER(i_std),INTENT(in)                    :: npts
29723093c2984
2973<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out)  :: lai
2974---
2975>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out)  :: lai
2976diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/stomate_io.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/stomate_io.f90
297723c23
2978<   LOGICAL,SAVE :: firstcall_io = .TRUE.
2979---
2980>   LOGICAL,SAVE :: firstcall = .TRUE.
298134c34
2982<        & (kjpindex, index, lalo, resolution, day_counter, dt_days, date, &
2983---
2984>        & (npts, index, lalo, resolution, day_counter, dt_days, date, &
298567c67
2986<     INTEGER(i_std),INTENT(in) :: kjpindex
2987---
2988>     INTEGER(i_std),INTENT(in) :: npts
298969c69
2990<     INTEGER(i_std),DIMENSION(kjpindex),INTENT(in) :: index
2991---
2992>     INTEGER(i_std),DIMENSION(npts),INTENT(in) :: index
299371c71
2994<     REAL(r_std),DIMENSION(kjpindex,2),INTENT(in) :: lalo
2995---
2996>     REAL(r_std),DIMENSION(npts,2),INTENT(in) :: lalo
299773c73
2998<     REAL(r_std),DIMENSION(kjpindex,2),INTENT(in) :: resolution
2999---
3000>     REAL(r_std),DIMENSION(npts,2),INTENT(in) :: resolution
300184c84
3002<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: ind
3003---
3004>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: ind
300586c86
3006<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: adapted
3007---
3008>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: adapted
300988c88
3010<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: regenerate
3011---
3012>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: regenerate
301390c90
3014<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: moiavail_daily
3015---
3016>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: moiavail_daily
301792c92
3018<     REAL(r_std),DIMENSION(kjpindex),INTENT(out)      :: litterhum_daily
3019---
3020>     REAL(r_std),DIMENSION(npts),INTENT(out)      :: litterhum_daily
302194c94
3022<     REAL(r_std),DIMENSION(kjpindex),INTENT(out)      :: t2m_daily
3023---
3024>     REAL(r_std),DIMENSION(npts),INTENT(out)      :: t2m_daily
302596c96
3026<     REAL(r_std),DIMENSION(kjpindex),INTENT(out)      :: t2m_min_daily
3027---
3028>     REAL(r_std),DIMENSION(npts),INTENT(out)      :: t2m_min_daily
302998c98
3030<     REAL(r_std),DIMENSION(kjpindex),INTENT(out)      :: tsurf_daily
3031---
3032>     REAL(r_std),DIMENSION(npts),INTENT(out)      :: tsurf_daily
3033100c100
3034<     REAL(r_std),DIMENSION(kjpindex,nbdl),INTENT(out) :: tsoil_daily
3035---
3036>     REAL(r_std),DIMENSION(npts,nbdl),INTENT(out) :: tsoil_daily
3037102c102
3038<     REAL(r_std),DIMENSION(kjpindex,nbdl),INTENT(out) :: soilhum_daily
3039---
3040>     REAL(r_std),DIMENSION(npts,nbdl),INTENT(out) :: soilhum_daily
3041104c104
3042<     REAL(r_std),DIMENSION(kjpindex),INTENT(out)      :: precip_daily
3043---
3044>     REAL(r_std),DIMENSION(npts),INTENT(out)      :: precip_daily
3045106c106
3046<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: gpp_daily
3047---
3048>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: gpp_daily
3049108c108
3050<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: npp_daily
3051---
3052>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: npp_daily
3053110c110
3054<     REAL(r_std),DIMENSION(kjpindex,nvm,nparts),INTENT(out) :: turnover_daily
3055---
3056>     REAL(r_std),DIMENSION(npts,nvm,nparts),INTENT(out) :: turnover_daily
3057112c112
3058<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: moiavail_month
3059---
3060>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: moiavail_month
3061114c114
3062<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: moiavail_week
3063---
3064>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: moiavail_week
3065116c116
3066<     REAL(r_std),DIMENSION(kjpindex),INTENT(out)      :: t2m_longterm
3067---
3068>     REAL(r_std),DIMENSION(npts),INTENT(out)      :: t2m_longterm
3069118c118
3070<     REAL(r_std),DIMENSION(kjpindex),INTENT(out)      :: t2m_month
3071---
3072>     REAL(r_std),DIMENSION(npts),INTENT(out)      :: t2m_month
3073120c120
3074<     REAL(r_std),DIMENSION(kjpindex),INTENT(out)      :: t2m_week
3075---
3076>     REAL(r_std),DIMENSION(npts),INTENT(out)      :: t2m_week
3077122c122
3078<     REAL(r_std),DIMENSION(kjpindex,nbdl),INTENT(out) :: tsoil_month
3079---
3080>     REAL(r_std),DIMENSION(npts,nbdl),INTENT(out) :: tsoil_month
3081124c124
3082<     REAL(r_std),DIMENSION(kjpindex,nbdl),INTENT(out) :: soilhum_month
3083---
3084>     REAL(r_std),DIMENSION(npts,nbdl),INTENT(out) :: soilhum_month
3085126c126
3086<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: fireindex
3087---
3088>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: fireindex
3089128c128
3090<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: firelitter
3091---
3092>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: firelitter
3093130c130
3094<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: maxmoiavail_lastyear
3095---
3096>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: maxmoiavail_lastyear
3097132c132
3098<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: maxmoiavail_thisyear
3099---
3100>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: maxmoiavail_thisyear
3101134c134
3102<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: minmoiavail_lastyear
3103---
3104>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: minmoiavail_lastyear
3105136c136
3106<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: minmoiavail_thisyear
3107---
3108>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: minmoiavail_thisyear
3109138c138
3110<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: maxgppweek_lastyear
3111---
3112>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: maxgppweek_lastyear
3113140c140
3114<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: maxgppweek_thisyear
3115---
3116>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: maxgppweek_thisyear
3117142c142
3118<     REAL(r_std),DIMENSION(kjpindex),INTENT(out)      :: gdd0_lastyear
3119---
3120>     REAL(r_std),DIMENSION(npts),INTENT(out)      :: gdd0_lastyear
3121144c144
3122<     REAL(r_std),DIMENSION(kjpindex),INTENT(out)      :: gdd0_thisyear
3123---
3124>     REAL(r_std),DIMENSION(npts),INTENT(out)      :: gdd0_thisyear
3125146c146
3126<     REAL(r_std),DIMENSION(kjpindex),INTENT(out)      :: precip_lastyear
3127---
3128>     REAL(r_std),DIMENSION(npts),INTENT(out)      :: precip_lastyear
3129148c148
3130<     REAL(r_std),DIMENSION(kjpindex),INTENT(out)      :: precip_thisyear
3131---
3132>     REAL(r_std),DIMENSION(npts),INTENT(out)      :: precip_thisyear
3133150c150
3134<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: gdd_m5_dormance
3135---
3136>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: gdd_m5_dormance
3137152c152
3138<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: gdd_midwinter
3139---
3140>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: gdd_midwinter
3141154c154
3142<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: ncd_dormance
3143---
3144>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: ncd_dormance
3145156c156
3146<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: ngd_minus5
3147---
3148>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: ngd_minus5
3149158c158
3150<     LOGICAL,DIMENSION(kjpindex,nvm),INTENT(out)    :: PFTpresent
3151---
3152>     LOGICAL,DIMENSION(npts,nvm),INTENT(out)    :: PFTpresent
3153160c160
3154<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: npp_longterm
3155---
3156>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: npp_longterm
3157162c162
3158<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: lm_lastyearmax
3159---
3160>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: lm_lastyearmax
3161164c164
3162<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: lm_thisyearmax
3163---
3164>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: lm_thisyearmax
3165166c166
3166<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: maxfpc_lastyear
3167---
3168>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: maxfpc_lastyear
3169169c169
3170<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: maxfpc_thisyear
3171---
3172>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: maxfpc_thisyear
3173171c171
3174<     REAL(r_std),DIMENSION(kjpindex,nvm,nparts),INTENT(out) :: turnover_longterm
3175---
3176>     REAL(r_std),DIMENSION(npts,nvm,nparts),INTENT(out) :: turnover_longterm
3177173c173
3178<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: gpp_week
3179---
3180>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: gpp_week
3181175c175
3182<     REAL(r_std),DIMENSION(kjpindex,nvm,nparts),INTENT(out) :: biomass
3183---
3184>     REAL(r_std),DIMENSION(npts,nvm,nparts),INTENT(out) :: biomass
3185177c177
3186<     REAL(r_std),DIMENSION(kjpindex,nvm,nparts),INTENT(out) :: resp_maint_part
3187---
3188>     REAL(r_std),DIMENSION(npts,nvm,nparts),INTENT(out) :: resp_maint_part
3189179c179
3190<     REAL(r_std),DIMENSION(kjpindex,nvm,nleafages),INTENT(out) :: leaf_age
3191---
3192>     REAL(r_std),DIMENSION(npts,nvm,nleafages),INTENT(out) :: leaf_age
3193181c181
3194<     REAL(r_std),DIMENSION(kjpindex,nvm,nleafages),INTENT(out) :: leaf_frac
3195---
3196>     REAL(r_std),DIMENSION(npts,nvm,nleafages),INTENT(out) :: leaf_frac
3197184c184
3198<     LOGICAL,DIMENSION(kjpindex,nvm),INTENT(out) :: senescence
3199---
3200>     LOGICAL,DIMENSION(npts,nvm),INTENT(out) :: senescence
3201186c186
3202<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: when_growthinit
3203---
3204>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: when_growthinit
3205188c188
3206<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: age
3207---
3208>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: age
3209190c190
3210<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: resp_hetero
3211---
3212>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: resp_hetero
3213192c192
3214<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: resp_maint
3215---
3216>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: resp_maint
3217194c194
3218<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: resp_growth
3219---
3220>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: resp_growth
3221197c197
3222<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: co2_fire
3223---
3224>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: co2_fire
3225199c199
3226<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: co2_to_bm_dgvm
3227---
3228>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: co2_to_bm_dgvm
3229201c201
3230<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: veget_lastlight
3231---
3232>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: veget_lastlight
3233204c204
3234<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: everywhere
3235---
3236>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: everywhere
3237207c207
3238<     LOGICAL,DIMENSION(kjpindex,nvm),INTENT(out) :: need_adjacent
3239---
3240>     LOGICAL,DIMENSION(npts,nvm),INTENT(out) :: need_adjacent
3241209c209
3242<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: RIP_time
3243---
3244>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: RIP_time
3245211c211
3246<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: time_lowgpp
3247---
3248>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: time_lowgpp
3249213c213
3250<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: time_hum_min
3251---
3252>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: time_hum_min
3253215c215
3254<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: hum_min_dormance
3255---
3256>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: hum_min_dormance
3257218c218
3258<     REAL(r_std),DIMENSION(kjpindex,nvm,nlitt),INTENT(out) :: litterpart
3259---
3260>     REAL(r_std),DIMENSION(npts,nvm,nlitt),INTENT(out) :: litterpart
3261221c221
3262<     REAL(r_std),DIMENSION(kjpindex,nlitt,nvm,nlevs),INTENT(out):: litter
3263---
3264>     REAL(r_std),DIMENSION(npts,nlitt,nvm,nlevs),INTENT(out):: litter
3265224c224
3266<     REAL(r_std),DIMENSION(kjpindex,nvm,nlitt),INTENT(out) :: dead_leaves
3267---
3268>     REAL(r_std),DIMENSION(npts,nvm,nlitt),INTENT(out) :: dead_leaves
3269226c226
3270<     REAL(r_std),DIMENSION(kjpindex,ncarb,nvm),INTENT(out) :: carbon
3271---
3272>     REAL(r_std),DIMENSION(npts,ncarb,nvm),INTENT(out) :: carbon
3273228c228
3274<     REAL(r_std),DIMENSION(kjpindex),INTENT(out)                 :: black_carbon
3275---
3276>     REAL(r_std),DIMENSION(npts),INTENT(out)                 :: black_carbon
3277230,231c230,231
3278<     REAL(r_std),DIMENSION(kjpindex,nvm,nlevs),INTENT(out) :: lignin_struc
3279<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: turnover_time
3280---
3281>     REAL(r_std),DIMENSION(npts,nvm,nlevs),INTENT(out) :: lignin_struc
3282>     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: turnover_time
3283236c236
3284<     REAL(r_std),DIMENSION(kjpindex),INTENT(inout) :: tlong_ref
3285---
3286>     REAL(r_std),DIMENSION(npts),INTENT(inout) :: tlong_ref
3287243c243
3288<     REAL(r_std),DIMENSION(kjpindex,nvm) :: PFTpresent_real
3289---
3290>     REAL(r_std),DIMENSION(npts,nvm) :: PFTpresent_real
3291246c246
3292<     REAL(r_std),DIMENSION(kjpindex,nvm) :: senescence_real
3293---
3294>     REAL(r_std),DIMENSION(npts,nvm) :: senescence_real
3295249c249
3296<     REAL(r_std),DIMENSION(kjpindex,nvm) :: need_adjacent_real
3297---
3298>     REAL(r_std),DIMENSION(npts,nvm) :: need_adjacent_real
3299263c263
3300<     REAL(r_std),DIMENSION(kjpindex) :: tref
3301---
3302>     REAL(r_std),DIMENSION(npts) :: tref
3303268,269c268,269
3304<     REAL(r_std),DIMENSION(kjpindex,0:10),INTENT(out)                           :: prod10
3305<     REAL(r_std),DIMENSION(kjpindex,0:100),INTENT(out)                          :: prod100
3306---
3307>     REAL(r_std),DIMENSION(npts,0:10),INTENT(out)                           :: prod10
3308>     REAL(r_std),DIMENSION(npts,0:100),INTENT(out)                          :: prod100
3309271,277c271,277
3310<     REAL(r_std),DIMENSION(kjpindex,10),INTENT(out)                           :: flux10
3311<     REAL(r_std),DIMENSION(kjpindex,100),INTENT(out)                          :: flux100
3312<     REAL(r_std), DIMENSION(kjpindex), INTENT(out)                            :: convflux
3313<     REAL(r_std), DIMENSION(kjpindex), INTENT(out)                            :: cflux_prod10
3314<     REAL(r_std), DIMENSION(kjpindex), INTENT(out)                            :: cflux_prod100
3315<     REAL(r_std),DIMENSION(kjpindex,nvm,nparts),INTENT(out)                   :: bm_to_litter
3316<     REAL(r_std),DIMENSION(kjpindex),INTENT(out)                              :: carb_mass_total
3317---
3318>     REAL(r_std),DIMENSION(npts,10),INTENT(out)                           :: flux10
3319>     REAL(r_std),DIMENSION(npts,100),INTENT(out)                          :: flux100
3320>     REAL(r_std), DIMENSION(npts), INTENT(out)                            :: convflux
3321>     REAL(r_std), DIMENSION(npts), INTENT(out)                            :: cflux_prod10
3322>     REAL(r_std), DIMENSION(npts), INTENT(out)                            :: cflux_prod100
3323>     REAL(r_std),DIMENSION(npts,nvm,nparts),INTENT(out)                   :: bm_to_litter
3324>     REAL(r_std),DIMENSION(npts),INTENT(out)                              :: carb_mass_total
3325287c287
3326<     CALL get_reftemp( kjpindex, lalo, resolution, tref )
3327---
3328>     CALL get_reftemp( npts, lalo, resolution, tref )
3329957c957
3330<        & (kjpindex, index, day_counter, dt_days, date, &
3331---
3332>        & (npts, index, day_counter, dt_days, date, &
3333990c990
3334<     INTEGER(i_std),INTENT(in) :: kjpindex
3335---
3336>     INTEGER(i_std),INTENT(in) :: npts
3337992c992
3338<     INTEGER(i_std),DIMENSION(kjpindex),INTENT(in) :: index
3339---
3340>     INTEGER(i_std),DIMENSION(npts),INTENT(in) :: index
33411000c1000
3342<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: ind
3343---
3344>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: ind
33451002c1002
3346<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: adapted
3347---
3348>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: adapted
33491004c1004
3350<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: regenerate
3351---
3352>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: regenerate
33531006c1006
3354<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: moiavail_daily
3355---
3356>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: moiavail_daily
33571008c1008
3358<     REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: litterhum_daily
3359---
3360>     REAL(r_std),DIMENSION(npts),INTENT(in) :: litterhum_daily
33611010c1010
3362<     REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: t2m_daily
3363---
3364>     REAL(r_std),DIMENSION(npts),INTENT(in) :: t2m_daily
33651012c1012
3366<     REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: t2m_min_daily
3367---
3368>     REAL(r_std),DIMENSION(npts),INTENT(in) :: t2m_min_daily
33691014c1014
3370<     REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: tsurf_daily
3371---
3372>     REAL(r_std),DIMENSION(npts),INTENT(in) :: tsurf_daily
33731016c1016
3374<     REAL(r_std),DIMENSION(kjpindex,nbdl),INTENT(in) :: tsoil_daily
3375---
3376>     REAL(r_std),DIMENSION(npts,nbdl),INTENT(in) :: tsoil_daily
33771018c1018
3378<     REAL(r_std),DIMENSION(kjpindex,nbdl),INTENT(in) :: soilhum_daily
3379---
3380>     REAL(r_std),DIMENSION(npts,nbdl),INTENT(in) :: soilhum_daily
33811020c1020
3382<     REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: precip_daily
3383---
3384>     REAL(r_std),DIMENSION(npts),INTENT(in) :: precip_daily
33851022c1022
3386<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: gpp_daily
3387---
3388>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: gpp_daily
33891024c1024
3390<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: npp_daily
3391---
3392>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: npp_daily
33931026c1026
3394<     REAL(r_std),DIMENSION(kjpindex,nvm,nparts),INTENT(in) :: turnover_daily
3395---
3396>     REAL(r_std),DIMENSION(npts,nvm,nparts),INTENT(in) :: turnover_daily
33971028c1028
3398<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: moiavail_month
3399---
3400>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: moiavail_month
34011030c1030
3402<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: moiavail_week
3403---
3404>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: moiavail_week
34051032c1032
3406<     REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: t2m_longterm
3407---
3408>     REAL(r_std),DIMENSION(npts),INTENT(in) :: t2m_longterm
34091034c1034
3410<     REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: tlong_ref
3411---
3412>     REAL(r_std),DIMENSION(npts),INTENT(in) :: tlong_ref
34131036c1036
3414<     REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: t2m_month
3415---
3416>     REAL(r_std),DIMENSION(npts),INTENT(in) :: t2m_month
34171038c1038
3418<     REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: t2m_week
3419---
3420>     REAL(r_std),DIMENSION(npts),INTENT(in) :: t2m_week
34211040c1040
3422<     REAL(r_std),DIMENSION(kjpindex,nbdl),INTENT(in) :: tsoil_month
3423---
3424>     REAL(r_std),DIMENSION(npts,nbdl),INTENT(in) :: tsoil_month
34251042c1042
3426<     REAL(r_std),DIMENSION(kjpindex,nbdl),INTENT(in) :: soilhum_month
3427---
3428>     REAL(r_std),DIMENSION(npts,nbdl),INTENT(in) :: soilhum_month
34291044c1044
3430<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: fireindex
3431---
3432>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: fireindex
34331046c1046
3434<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: firelitter
3435---
3436>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: firelitter
34371048c1048
3438<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: maxmoiavail_lastyear
3439---
3440>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: maxmoiavail_lastyear
34411050c1050
3442<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: maxmoiavail_thisyear
3443---
3444>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: maxmoiavail_thisyear
34451052c1052
3446<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: minmoiavail_lastyear
3447---
3448>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: minmoiavail_lastyear
34491054c1054
3450<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: minmoiavail_thisyear
3451---
3452>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: minmoiavail_thisyear
34531056c1056
3454<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: maxgppweek_lastyear
3455---
3456>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: maxgppweek_lastyear
34571058c1058
3458<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: maxgppweek_thisyear
3459---
3460>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: maxgppweek_thisyear
34611060c1060
3462<     REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: gdd0_lastyear
3463---
3464>     REAL(r_std),DIMENSION(npts),INTENT(in) :: gdd0_lastyear
34651062c1062
3466<     REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: gdd0_thisyear
3467---
3468>     REAL(r_std),DIMENSION(npts),INTENT(in) :: gdd0_thisyear
34691064c1064
3470<     REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: precip_lastyear
3471---
3472>     REAL(r_std),DIMENSION(npts),INTENT(in) :: precip_lastyear
34731066c1066
3474<     REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: precip_thisyear
3475---
3476>     REAL(r_std),DIMENSION(npts),INTENT(in) :: precip_thisyear
34771068c1068
3478<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: gdd_m5_dormance
3479---
3480>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: gdd_m5_dormance
34811070c1070
3482<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: gdd_midwinter
3483---
3484>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: gdd_midwinter
34851072c1072
3486<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: ncd_dormance
3487---
3488>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: ncd_dormance
34891074c1074
3490<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: ngd_minus5
3491---
3492>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: ngd_minus5
34931076c1076
3494<     LOGICAL,DIMENSION(kjpindex,nvm),INTENT(in) :: PFTpresent
3495---
3496>     LOGICAL,DIMENSION(npts,nvm),INTENT(in) :: PFTpresent
34971078c1078
3498<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: npp_longterm
3499---
3500>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: npp_longterm
35011080c1080
3502<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: lm_lastyearmax
3503---
3504>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: lm_lastyearmax
35051082c1082
3506<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: lm_thisyearmax
3507---
3508>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: lm_thisyearmax
35091084c1084
3510<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: maxfpc_lastyear
3511---
3512>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: maxfpc_lastyear
35131087c1087
3514<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: maxfpc_thisyear
3515---
3516>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: maxfpc_thisyear
35171089c1089
3518<     REAL(r_std),DIMENSION(kjpindex,nvm,nparts),INTENT(in) :: turnover_longterm
3519---
3520>     REAL(r_std),DIMENSION(npts,nvm,nparts),INTENT(in) :: turnover_longterm
35211091c1091
3522<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: gpp_week
3523---
3524>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: gpp_week
35251093c1093
3526<     REAL(r_std),DIMENSION(kjpindex,nvm,nparts),INTENT(in) :: biomass
3527---
3528>     REAL(r_std),DIMENSION(npts,nvm,nparts),INTENT(in) :: biomass
35291095c1095
3530<     REAL(r_std),DIMENSION(kjpindex,nvm,nparts),INTENT(in) :: resp_maint_part
3531---
3532>     REAL(r_std),DIMENSION(npts,nvm,nparts),INTENT(in) :: resp_maint_part
35331097c1097
3534<     REAL(r_std),DIMENSION(kjpindex,nvm,nleafages),INTENT(in) :: leaf_age
3535---
3536>     REAL(r_std),DIMENSION(npts,nvm,nleafages),INTENT(in) :: leaf_age
35371099c1099
3538<     REAL(r_std),DIMENSION(kjpindex,nvm,nleafages),INTENT(in) :: leaf_frac
3539---
3540>     REAL(r_std),DIMENSION(npts,nvm,nleafages),INTENT(in) :: leaf_frac
35411102c1102
3542<     LOGICAL,DIMENSION(kjpindex,nvm),INTENT(in) :: senescence
3543---
3544>     LOGICAL,DIMENSION(npts,nvm),INTENT(in) :: senescence
35451104c1104
3546<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: when_growthinit
3547---
3548>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: when_growthinit
35491106c1106
3550<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: age
3551---
3552>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: age
35531108c1108
3554<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: resp_hetero
3555---
3556>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: resp_hetero
35571110c1110
3558<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: resp_maint
3559---
3560>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: resp_maint
35611112c1112
3562<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: resp_growth
3563---
3564>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: resp_growth
35651115c1115
3566<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: co2_fire
3567---
3568>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: co2_fire
35691117c1117
3570<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: co2_to_bm_dgvm
3571---
3572>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: co2_to_bm_dgvm
35731119c1119
3574<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: veget_lastlight
3575---
3576>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: veget_lastlight
35771122c1122
3578<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: everywhere
3579---
3580>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: everywhere
35811125c1125
3582<     LOGICAL,DIMENSION(kjpindex,nvm),INTENT(in) :: need_adjacent
3583---
3584>     LOGICAL,DIMENSION(npts,nvm),INTENT(in) :: need_adjacent
35851127c1127
3586<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: RIP_time
3587---
3588>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: RIP_time
35891129c1129
3590<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: time_lowgpp
3591---
3592>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: time_lowgpp
35931131c1131
3594<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: time_hum_min
3595---
3596>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: time_hum_min
35971133c1133
3598<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: hum_min_dormance
3599---
3600>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: hum_min_dormance
36011135c1135
3602<     REAL(r_std),DIMENSION(kjpindex,nvm,nlitt),INTENT(in) :: litterpart
3603---
3604>     REAL(r_std),DIMENSION(npts,nvm,nlitt),INTENT(in) :: litterpart
36051137c1137
3606<     REAL(r_std),DIMENSION(kjpindex,nlitt,nvm,nlevs),INTENT(in) :: litter
3607---
3608>     REAL(r_std),DIMENSION(npts,nlitt,nvm,nlevs),INTENT(in) :: litter
36091140c1140
3610<     REAL(r_std),DIMENSION(kjpindex,nvm,nlitt),INTENT(in) :: dead_leaves
3611---
3612>     REAL(r_std),DIMENSION(npts,nvm,nlitt),INTENT(in) :: dead_leaves
36131142c1142
3614<     REAL(r_std),DIMENSION(kjpindex,ncarb,nvm),INTENT(in) :: carbon
3615---
3616>     REAL(r_std),DIMENSION(npts,ncarb,nvm),INTENT(in) :: carbon
36171144c1144
3618<     REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: black_carbon
3619---
3620>     REAL(r_std),DIMENSION(npts),INTENT(in) :: black_carbon
36211146c1146
3622<     REAL(r_std),DIMENSION(kjpindex,nvm,nlevs),INTENT(in) :: lignin_struc
3623---
3624>     REAL(r_std),DIMENSION(npts,nvm,nlevs),INTENT(in) :: lignin_struc
36251148c1148
3626<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: turnover_time
3627---
3628>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: turnover_time
36291155c1155
3630<     REAL(r_std),DIMENSION(kjpindex,nvm) :: PFTpresent_real
3631---
3632>     REAL(r_std),DIMENSION(npts,nvm) :: PFTpresent_real
36331158c1158
3634<     REAL(r_std),DIMENSION(kjpindex,nvm) :: senescence_real
3635---
3636>     REAL(r_std),DIMENSION(npts,nvm) :: senescence_real
36371161c1161
3638<     REAL(r_std),DIMENSION(kjpindex,nvm) :: need_adjacent_real
3639---
3640>     REAL(r_std),DIMENSION(npts,nvm) :: need_adjacent_real
36411178,1179c1178,1179
3642<     REAL(r_std),DIMENSION(kjpindex,0:10),INTENT(in)                           :: prod10
3643<     REAL(r_std),DIMENSION(kjpindex,0:100),INTENT(in)                          :: prod100
3644---
3645>     REAL(r_std),DIMENSION(npts,0:10),INTENT(in)                           :: prod10
3646>     REAL(r_std),DIMENSION(npts,0:100),INTENT(in)                          :: prod100
36471181,1187c1181,1187
3648<     REAL(r_std),DIMENSION(kjpindex,10),INTENT(in)                           :: flux10
3649<     REAL(r_std),DIMENSION(kjpindex,100),INTENT(in)                          :: flux100
3650<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                            :: convflux
3651<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                            :: cflux_prod10
3652<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                            :: cflux_prod100
3653<     REAL(r_std),DIMENSION(kjpindex,nvm,nparts),INTENT(in)                   :: bm_to_litter
3654<     REAL(r_std),DIMENSION(kjpindex),INTENT(in)                              :: carb_mass_total
3655---
3656>     REAL(r_std),DIMENSION(npts,10),INTENT(in)                           :: flux10
3657>     REAL(r_std),DIMENSION(npts,100),INTENT(in)                          :: flux100
3658>     REAL(r_std), DIMENSION(npts), INTENT(in)                            :: convflux
3659>     REAL(r_std), DIMENSION(npts), INTENT(in)                            :: cflux_prod10
3660>     REAL(r_std), DIMENSION(npts), INTENT(in)                            :: cflux_prod100
3661>     REAL(r_std),DIMENSION(npts,nvm,nparts),INTENT(in)                   :: bm_to_litter
3662>     REAL(r_std),DIMENSION(npts),INTENT(in)                              :: carb_mass_total
36631662c1662
3664<   SUBROUTINE readbc (kjpindex, lalo, resolution, tref)
3665---
3666>   SUBROUTINE readbc (npts, lalo, resolution, tref)
36671668c1668
3668<     INTEGER(i_std),INTENT(in) :: kjpindex
3669---
3670>     INTEGER(i_std),INTENT(in) :: npts
36711670c1670
3672<     REAL(r_std),DIMENSION (kjpindex,2),INTENT(in) :: lalo
3673---
3674>     REAL(r_std),DIMENSION (npts,2),INTENT(in) :: lalo
36751672c1672
3676<     REAL(r_std),DIMENSION (kjpindex,2),INTENT(in) :: resolution
3677---
3678>     REAL(r_std),DIMENSION (npts,2),INTENT(in) :: resolution
36791677c1677
3680<     REAL(r_std),DIMENSION(kjpindex),INTENT(inout) :: tref
3681---
3682>     REAL(r_std),DIMENSION(npts),INTENT(inout) :: tref
36831684c1684
3684<        CALL get_reftemp (kjpindex, lalo, resolution, tref)
3685---
3686>        CALL get_reftemp (npts, lalo, resolution, tref)
36871693c1693
3688<     firstcall_io=.TRUE.
3689---
3690>     firstcall=.TRUE.
36911700c1700
3692<   SUBROUTINE get_reftemp (kjpindex, lalo, resolution, tref_out)
3693---
3694>   SUBROUTINE get_reftemp (npts, lalo, resolution, tref_out)
36951715c1715
3696<     INTEGER(i_std),INTENT(in) :: kjpindex
3697---
3698>     INTEGER(i_std),INTENT(in) :: npts
36991717c1717
3700<     REAL(r_std),DIMENSION (kjpindex,2),INTENT(in) :: lalo
3701---
3702>     REAL(r_std),DIMENSION (npts,2),INTENT(in) :: lalo
37031719c1719
3704<     REAL(r_std),DIMENSION (kjpindex,2),INTENT(in) :: resolution
3705---
3706>     REAL(r_std),DIMENSION (npts,2),INTENT(in) :: resolution
37071724c1724
3708<     REAL(r_std), DIMENSION(kjpindex),INTENT(out) :: tref_out
3709---
3710>     REAL(r_std), DIMENSION(npts),INTENT(out) :: tref_out
37111732c1732
3712<     REAL(r_std) :: lev(1), date, dt_days, coslat
3713---
3714>     REAL(r_std) :: lev(1), date, dt, coslat
37151751c1751
3716<     IF (firstcall_io) THEN
3717---
3718>     IF (firstcall) THEN
37191755c1755
3720<        firstcall_io = .FALSE.
3721---
3722>        firstcall = .FALSE.
37231759c1759
3724<        ALLOCATE( trefe(kjpindex) )
3725---
3726>        ALLOCATE( trefe(npts) )
37271798c1798
3728<             &                                   lon_rel, lat_rel, lev, tml, itau, date, dt_days, fid)
3729---
3730>             &                                   lon_rel, lat_rel, lev, tml, itau, date, dt, fid)
37311803c1803
3732<        CALL bcast(dt_days)
3733---
3734>        CALL bcast(dt)
37351870c1870
3736<        DO ib=1,kjpindex
3737---
3738>        DO ib=1,npts
3739diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/stomate_lcchange.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/stomate_lcchange.f90
374032c32
3741<   SUBROUTINE lcchange_main ( kjpindex, dt_days, veget_max, veget_max_new,&
3742---
3743>   SUBROUTINE lcchange_main ( npts, dt_days, veget_max, veget_max_new,&
374434c34
3745<        co2_to_bm_dgvm, bm_to_litter, turnover_daily, cn_ind,flux10,flux100, &
3746---
3747>        co2_to_bm, bm_to_litter, turnover_daily, bm_sapl, tree, cn_ind,flux10,flux100, &
374848c48
3749<     INTEGER, INTENT(in)                                            :: kjpindex
3750---
3751>     INTEGER, INTENT(in)                                            :: npts
375254c54,59
3753<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(INOUT)                 :: veget_max_new
3754---
3755>     REAL(r_std), DIMENSION(npts,nvm), INTENT(INOUT)                 :: veget_max_new
3756>     ! biomass of sapling (gC/individu)
3757>     REAL(r_std) , DIMENSION (nvm, nparts), INTENT(in)              :: bm_sapl
3758>
3759>     ! is pft a tree
3760>     LOGICAL, DIMENSION(nvm), INTENT(in)                           :: tree
376160c65
3762<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)                    :: veget
3763---
3764>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                    :: veget
376563c68
3766<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)                    :: veget_max
3767---
3768>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                    :: veget_max
376966c71
3770<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)             :: biomass
3771---
3772>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)             :: biomass
377369c74
3774<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)                    :: ind
3775---
3776>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                    :: ind
377772c77
3778<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)                    :: age
3779---
3780>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                    :: age
378176c81
3782<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(inout)                       :: senescence
3783---
3784>     LOGICAL, DIMENSION(npts,nvm), INTENT(inout)                       :: senescence
378579c84
3786<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(inout)                       :: PFTpresent
3787---
3788>     LOGICAL, DIMENSION(npts,nvm), INTENT(inout)                       :: PFTpresent
378982c87
3790<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)                    :: everywhere
3791---
3792>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                    :: everywhere
379385c90
3794<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)                    :: when_growthinit
3795---
3796>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                    :: when_growthinit
379790c95
3798<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)                       :: co2_to_bm_dgvm
3799---
3800>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                       :: co2_to_bm
380193c98
3802<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)           :: bm_to_litter
3803---
3804>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)           :: bm_to_litter
380596c101
3806<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)                   :: cn_ind
3807---
3808>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                   :: cn_ind
3809100,101c105,106
3810<     REAL(r_std), DIMENSION(kjpindex,0:10), INTENT(inout)                     :: prod10
3811<     REAL(r_std), DIMENSION(kjpindex,0:100), INTENT(inout)                    :: prod100
3812---
3813>     REAL(r_std), DIMENSION(npts,0:10), INTENT(inout)                     :: prod10
3814>     REAL(r_std), DIMENSION(npts,0:100), INTENT(inout)                    :: prod100
3815104,105c109,110
3816<     REAL(r_std), DIMENSION(kjpindex,10), INTENT(inout)                     :: flux10
3817<     REAL(r_std), DIMENSION(kjpindex,100), INTENT(inout)                    :: flux100
3818---
3819>     REAL(r_std), DIMENSION(npts,10), INTENT(inout)                     :: flux10
3820>     REAL(r_std), DIMENSION(npts,100), INTENT(inout)                    :: flux100
3821108c113
3822<     REAL(r_std), DIMENSION(kjpindex,nvm,nleafages), INTENT(inout)         :: leaf_frac
3823---
3824>     REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)         :: leaf_frac
3825111c116
3826<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)                   :: lm_lastyearmax
3827---
3828>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                   :: lm_lastyearmax
3829114c119
3830<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)                    :: npp_longterm
3831---
3832>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                    :: npp_longterm
3833117c122
3834<     REAL(r_std),DIMENSION(kjpindex,nlitt,nvm,nlevs), INTENT(inout)         :: litter
3835---
3836>     REAL(r_std),DIMENSION(npts,nlitt,nvm,nlevs), INTENT(inout)         :: litter
3837119c124
3838<     REAL(r_std),DIMENSION(kjpindex,ncarb,nvm), INTENT(inout)               :: carbon
3839---
3840>     REAL(r_std),DIMENSION(npts,ncarb,nvm), INTENT(inout)               :: carbon
3841124c129
3842<     REAL(r_std), DIMENSION(kjpindex), INTENT(out)                          :: convflux
3843---
3844>     REAL(r_std), DIMENSION(npts), INTENT(out)                          :: convflux
3845127c132
3846<     REAL(r_std), DIMENSION(kjpindex), INTENT(out)                          :: cflux_prod10, cflux_prod100
3847---
3848>     REAL(r_std), DIMENSION(npts), INTENT(out)                          :: cflux_prod10, cflux_prod100
3849130c135
3850< !!$    REAL(r_std), DIMENSION(kjpindex), INTENT(out)                          :: prod10_total, prod100_total
3851---
3852> !!$    REAL(r_std), DIMENSION(npts), INTENT(out)                          :: prod10_total, prod100_total
3853133c138
3854< !!$    REAL(r_std), DIMENSION(kjpindex), INTENT(out)                          :: cflux_prod_total
3855---
3856> !!$    REAL(r_std), DIMENSION(npts), INTENT(out)                          :: cflux_prod_total
3857136c141
3858<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)               :: turnover_daily
3859---
3860>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)               :: turnover_daily
3861146c151
3862<     REAL(r_std),DIMENSION(kjpindex,nparts)                                 :: biomass_loss
3863---
3864>     REAL(r_std),DIMENSION(npts,nparts)                                 :: biomass_loss
3865149c154
3866<     REAL(r_std),DIMENSION(kjpindex,nlitt,nlevs)                            :: dilu_lit
3867---
3868>     REAL(r_std),DIMENSION(npts,nlitt,nlevs)                            :: dilu_lit
3869151c156
3870<     REAL(r_std),DIMENSION(kjpindex,ncarb)                                  :: dilu_soil_carbon
3871---
3872>     REAL(r_std),DIMENSION(npts,ncarb)                                  :: dilu_soil_carbon
3873158c163
3874<     REAL(r_std),DIMENSION(kjpindex,nvm)                                    :: delta_ind
3875---
3876>     REAL(r_std),DIMENSION(npts,nvm)                                    :: delta_ind
3877178c183
3878<     DO i = 1, kjpindex 
3879---
3880>     DO i = 1, npts 
3881231c236
3882<                 co2_to_bm_dgvm(i,j) = co2_to_bm_dgvm(i,j)+  (bm_new* dt_days) / (one_year * veget_max_new(i,j))
3883---
3884>                 co2_to_bm(i,j) = co2_to_bm(i,j)+  (bm_new* dt_days) / (one_year * veget_max_new(i,j))
3885323c328
3886<     ENDDO  ! End loop on kjpindex
3887---
3888>     ENDDO  ! End loop on npts
3889diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/stomate_litter.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/stomate_litter.f90
389021c21
3891<   PUBLIC littercalc_main,littercalc_clear, deadleaf
3892---
3893>   PUBLIC littercalc,littercalc_clear, deadleaf
389424c24
3895<   LOGICAL, SAVE                                                     :: firstcall_litter = .TRUE.
3896---
3897>   LOGICAL, SAVE                                                     :: firstcall = .TRUE.
389827,29d26
3899< ! List of subroutines for initialization :
3900< !- littercalc_clear
3901< !- deadleaf
390232c29
3903<     firstcall_litter =.TRUE.
3904---
3905>     firstcall =.TRUE.
390636,38c33,35
3907<   SUBROUTINE littercalc_main (kjpindex, dt_days, &
3908<        turnover_littercalc, bm_to_litter, &
3909<        veget_max, tsurf_daily, tsoil_daily, shumdiag, litterhumdiag, &
3910---
3911>   SUBROUTINE littercalc (npts, dt, &
3912>        turnover, bm_to_litter, &
3913>        veget_max, tsurf, tsoil, soilhum, litterhum, &
391450c47
3915<     INTEGER(i_std), INTENT(in)                                               :: kjpindex
3916---
3917>     INTEGER(i_std), INTENT(in)                                               :: npts
391852c49
3919<     REAL(r_std), INTENT(in)                                            :: dt_days
3920---
3921>     REAL(r_std), INTENT(in)                                            :: dt
392254c51
3923<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(in)               :: turnover_littercalc
3924---
3925>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(in)               :: turnover
392656c53
3927<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(in)               :: bm_to_litter
3928---
3929>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(in)               :: bm_to_litter
393058c55
3931<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)                  :: veget_max
3932---
3933>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in)                  :: veget_max
393460c57
3935<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                           :: tsurf_daily
3936---
3937>     REAL(r_std), DIMENSION(npts), INTENT(in)                           :: tsurf
393862c59
3939<     REAL(r_std), DIMENSION(kjpindex,nbdl), INTENT(in)                      :: tsoil_daily
3940---
3941>     REAL(r_std), DIMENSION(npts,nbdl), INTENT(in)                      :: tsoil
394264c61
3943<     REAL(r_std), DIMENSION(kjpindex,nbdl), INTENT(in)                      :: shumdiag
3944---
3945>     REAL(r_std), DIMENSION(npts,nbdl), INTENT(in)                      :: soilhum
394666c63
3947<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                           :: litterhumdiag
3948---
3949>     REAL(r_std), DIMENSION(npts), INTENT(in)                           :: litterhum
395071c68
3951<     REAL(r_std), DIMENSION(kjpindex,nvm,nlitt), INTENT(inout)             :: litterpart
3952---
3953>     REAL(r_std), DIMENSION(npts,nvm,nlitt), INTENT(inout)             :: litterpart
395473c70
3955<     REAL(r_std), DIMENSION(kjpindex,nlitt,nvm,nlevs), INTENT(inout)  :: litter
3956---
3957>     REAL(r_std), DIMENSION(npts,nlitt,nvm,nlevs), INTENT(inout)  :: litter
395876c73
3959<     REAL(r_std), DIMENSION(kjpindex,nvm,nlitt), INTENT(inout)             :: dead_leaves
3960---
3961>     REAL(r_std), DIMENSION(npts,nvm,nlitt), INTENT(inout)             :: dead_leaves
396278c75
3963<     REAL(r_std), DIMENSION(kjpindex,nvm,nlevs), INTENT(inout)        :: lignin_struc
3964---
3965>     REAL(r_std), DIMENSION(npts,nvm,nlevs), INTENT(inout)        :: lignin_struc
396683c80
3967<     REAL(r_std), DIMENSION(kjpindex), INTENT(out)                          :: deadleaf_cover
3968---
3969>     REAL(r_std), DIMENSION(npts), INTENT(out)                          :: deadleaf_cover
397085c82
3971<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)                :: resp_hetero_litter
3972---
3973>     REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                :: resp_hetero_litter
397488c85
3975<     REAL(r_std), DIMENSION(kjpindex,ncarb,nvm), INTENT(out)          :: soilcarbon_input
3976---
3977>     REAL(r_std), DIMENSION(npts,ncarb,nvm), INTENT(out)          :: soilcarbon_input
397890c87
3979<     REAL(r_std), DIMENSION(kjpindex,nlevs), INTENT(out)                    :: control_temp
3980---
3981>     REAL(r_std), DIMENSION(npts,nlevs), INTENT(out)                    :: control_temp
398292c89
3983<     REAL(r_std), DIMENSION(kjpindex,nlevs), INTENT(out)                    :: control_moist
3984---
3985>     REAL(r_std), DIMENSION(npts,nlevs), INTENT(out)                    :: control_moist
3986101a99,100
3987>     ! soil levels (m)
3988>     REAL(r_std), SAVE, DIMENSION(0:nbdl)                               :: z_soil
3989105c104
3990<     REAL(r_std), DIMENSION(kjpindex)                                       :: rpc
3991---
3992>     REAL(r_std), DIMENSION(npts)                                       :: rpc
3993112c111
3994<     REAL(r_std), DIMENSION(kjpindex)                                       :: tsoil_decomp
3995---
3996>     REAL(r_std), DIMENSION(npts)                                       :: tsoil_decomp
3997114c113
3998<     REAL(r_std), DIMENSION(kjpindex)                                       :: soilhum_decomp
3999---
4000>     REAL(r_std), DIMENSION(npts)                                       :: soilhum_decomp
4001116c115
4002<     REAL(r_std), DIMENSION(kjpindex)                                       :: fd
4003---
4004>     REAL(r_std), DIMENSION(npts)                                       :: fd
4005118c117
4006<     REAL(r_std), DIMENSION(kjpindex)                                       :: qd
4007---
4008>     REAL(r_std), DIMENSION(npts)                                       :: qd
4009120c119
4010<     REAL(r_std), DIMENSION(kjpindex,nvm,nlevs)                       :: old_struc
4011---
4012>     REAL(r_std), DIMENSION(npts,nvm,nlevs)                       :: old_struc
4013123c122
4014<     REAL(r_std), DIMENSION(kjpindex,nvm,nlitt,nlevs)                      :: litter_inc_PFT
4015---
4016>     REAL(r_std), DIMENSION(npts,nvm,nlitt,nlevs)                      :: litter_inc_PFT
4017125c124
4018<     REAL(r_std), DIMENSION(kjpindex,nlitt,nvm,nlevs)                 :: litter_inc
4019---
4020>     REAL(r_std), DIMENSION(npts,nlitt,nvm,nlevs)                 :: litter_inc
4021127c126
4022<     REAL(r_std), DIMENSION(kjpindex,nvm,nlevs)                       :: lignin_struc_inc
4023---
4024>     REAL(r_std), DIMENSION(npts,nvm,nlevs)                       :: lignin_struc_inc
4025129c128
4026<     REAL(r_std), DIMENSION(kjpindex,nvm,nlitt)                            :: litter_pft
4027---
4028>     REAL(r_std), DIMENSION(npts,nvm,nlitt)                            :: litter_pft
4029131c130
4030<     REAL(r_std), DIMENSION(kjpindex)                                       :: zdiff_min
4031---
4032>     REAL(r_std), DIMENSION(npts)                                       :: zdiff_min
4033148c147
4034<     IF ( firstcall_litter ) THEN
4035---
4036>     IF ( firstcall ) THEN
4037209a209,215
4038>        ! 1.2 soil levels
4039>        !
4040>
4041>        z_soil(0) = zero
4042>        z_soil(1:nbdl) = diaglev(1:nbdl)
4043>
4044>        !
4045269,270c275,276
4046<        firstcall_litter = .FALSE.
4047<        RETURN
4048---
4049>        firstcall = .FALSE.
4050>
4051333,337c339,343
4052<                litterfrac(ileaf,k) * turnover_littercalc(:,j,ileaf) + &
4053<                litterfrac(isapabove,k) * turnover_littercalc(:,j,isapabove) + &
4054<                litterfrac(iheartabove,k) * turnover_littercalc(:,j,iheartabove) + &
4055<                litterfrac(ifruit,k) * turnover_littercalc(:,j,ifruit) + &
4056<                litterfrac(icarbres,k) * turnover_littercalc(:,j,icarbres)
4057---
4058>                litterfrac(ileaf,k) * turnover(:,j,ileaf) + &
4059>                litterfrac(isapabove,k) * turnover(:,j,isapabove) + &
4060>                litterfrac(iheartabove,k) * turnover(:,j,iheartabove) + &
4061>                litterfrac(ifruit,k) * turnover(:,j,ifruit) + &
4062>                litterfrac(icarbres,k) * turnover(:,j,icarbres)
4063343,345c349,351
4064<                litterfrac(isapbelow,k) * turnover_littercalc(:,j,isapbelow) + &
4065<                litterfrac(iheartbelow,k) * turnover_littercalc(:,j,iheartbelow) + &
4066<                litterfrac(iroot,k) * turnover_littercalc(:,j,iroot)
4067---
4068>                litterfrac(isapbelow,k) * turnover(:,j,isapbelow) + &
4069>                litterfrac(iheartbelow,k) * turnover(:,j,iheartbelow) + &
4070>                litterfrac(iroot,k) * turnover(:,j,iroot)
4071356c362
4072<                litterfrac(ileaf,k) * ( bm_to_litter(:,j,ileaf) + turnover_littercalc(:,j,ileaf) )
4073---
4074>                litterfrac(ileaf,k) * ( bm_to_litter(:,j,ileaf) + turnover(:,j,ileaf) )
4075369,373c375,379
4076<                   LC(ileaf) * turnover_littercalc(:,j,ileaf) + &
4077<                   LC(isapabove) * turnover_littercalc(:,j,isapabove) + &
4078<                   LC(iheartabove) * turnover_littercalc(:,j,iheartabove) + &
4079<                   LC(ifruit) * turnover_littercalc(:,j,ifruit) + &
4080<                   LC(icarbres) * turnover_littercalc(:,j,icarbres)
4081---
4082>                   LC(ileaf) * turnover(:,j,ileaf) + &
4083>                   LC(isapabove) * turnover(:,j,isapabove) + &
4084>                   LC(iheartabove) * turnover(:,j,iheartabove) + &
4085>                   LC(ifruit) * turnover(:,j,ifruit) + &
4086>                   LC(icarbres) * turnover(:,j,icarbres)
4087380,382c386,388
4088<                   LC(isapbelow)*turnover_littercalc(:,j,isapbelow) + &
4089<                   LC(iheartbelow)*turnover_littercalc(:,j,iheartbelow) + &
4090<                   LC(iroot)*turnover_littercalc(:,j,iroot)
4091---
4092>                   LC(isapbelow)*turnover(:,j,isapbelow) + &
4093>                   LC(iheartbelow)*turnover(:,j,iheartbelow) + &
4094>                   LC(iroot)*turnover(:,j,iroot)
4095454c460
4096<     control_temp(:,iabove) = control_temp_func (kjpindex, tsurf_daily)
4097---
4098>     control_temp(:,iabove) = control_temp_func (npts, tsurf)
4099471c477
4100<             tsoil_decomp(:) + tsoil_daily(:,l) * rpc(:) * &
4101---
4102>             tsoil_decomp(:) + tsoil(:,l) * rpc(:) * &
4103476c482
4104<     control_temp(:,ibelow) = control_temp_func (kjpindex, tsoil_decomp)
4105---
4106>     control_temp(:,ibelow) = control_temp_func (npts, tsoil_decomp)
4107486c492
4108<     control_moist(:,iabove) = control_moist_func (kjpindex, litterhumdiag)
4109---
4110>     control_moist(:,iabove) = control_moist_func (npts, litterhum)
4111503c509
4112<             soilhum_decomp(:) + shumdiag(:,l) * rpc(:) * &
4113---
4114>             soilhum_decomp(:) + soilhum(:,l) * rpc(:) * &
4115508c514
4116<     control_moist(:,ibelow) = control_moist_func (kjpindex, soilhum_decomp)
4117---
4118>     control_moist(:,ibelow) = control_moist_func (npts, soilhum_decomp)
4119523c529
4120<           fd(:) = dt_days/litter_tau(istructural) * &
4121---
4122>           fd(:) = dt/litter_tau(istructural) * &
4123541c547
4124<                frac_soil(istructural,iactive,l) * qd(:) * ( 1. - lignin_struc(:,m,l) ) / dt_days
4125---
4126>                frac_soil(istructural,iactive,l) * qd(:) * ( 1. - lignin_struc(:,m,l) ) / dt
4127545c551
4128<                ( 1. - lignin_struc(:,m,l) ) / dt_days
4129---
4130>                ( 1. - lignin_struc(:,m,l) ) / dt
4131551c557
4132<                frac_soil(istructural,islow,l) * qd(:) * lignin_struc(:,m,l) / dt_days
4133---
4134>                frac_soil(istructural,islow,l) * qd(:) * lignin_struc(:,m,l) / dt
4135554c560
4136<                ( 1. - frac_soil(istructural,islow,l) ) * qd(:) * lignin_struc(:,m,l) / dt_days
4137---
4138>                ( 1. - frac_soil(istructural,islow,l) ) * qd(:) * lignin_struc(:,m,l) / dt
4139562c568
4140<           fd(:) = dt_days/litter_tau(imetabolic) * control_temp(:,l) * control_moist(:,l)
4141---
4142>           fd(:) = dt/litter_tau(imetabolic) * control_temp(:,l) * control_moist(:,l)
4143578c584
4144<                frac_soil(imetabolic,iactive,l) * qd(:) / dt_days
4145---
4146>                frac_soil(imetabolic,iactive,l) * qd(:) / dt
4147581c587
4148<                ( 1. - frac_soil(imetabolic,iactive,l) ) * qd(:) / dt_days
4149---
4150>                ( 1. - frac_soil(imetabolic,iactive,l) ) * qd(:) / dt
4151590c596
4152<     CALL deadleaf (kjpindex, veget_max, dead_leaves, deadleaf_cover)
4153---
4154>     CALL deadleaf (npts, veget_max, dead_leaves, deadleaf_cover)
4155594c600
4156<   END SUBROUTINE littercalc_main
4157---
4158>   END SUBROUTINE littercalc
4159596c602
4160<   SUBROUTINE deadleaf (kjpindex, veget_max, dead_leaves, deadleaf_cover)
4161---
4162>   SUBROUTINE deadleaf (npts, veget_max, dead_leaves, deadleaf_cover)
4163605c611
4164<     INTEGER(i_std), INTENT(in)                                               :: kjpindex
4165---
4166>     INTEGER(i_std), INTENT(in)                                               :: npts
4167608c614
4168<     REAL(r_std), DIMENSION(kjpindex,nvm,nlitt), INTENT(in)                :: dead_leaves
4169---
4170>     REAL(r_std), DIMENSION(npts,nvm,nlitt), INTENT(in)                :: dead_leaves
4171610c616
4172<     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)                 :: veget_max
4173---
4174>     REAL(r_std),DIMENSION(npts,nvm),INTENT(in)                 :: veget_max
4175613c619
4176<     REAL(r_std), DIMENSION(kjpindex), INTENT(out)                          :: deadleaf_cover
4177---
4178>     REAL(r_std), DIMENSION(npts), INTENT(out)                          :: deadleaf_cover
4179618c624
4180<     REAL(r_std), DIMENSION(kjpindex)                                       :: dead_lai
4181---
4182>     REAL(r_std), DIMENSION(npts)                                       :: dead_lai
4183643c649
4184<   FUNCTION control_moist_func (kjpindex, moist_in) RESULT (moistfunc_result)
4185---
4186>   FUNCTION control_moist_func (npts, moist_in) RESULT (moistfunc_result)
4187652c658
4188<     INTEGER(i_std), INTENT(in)                                               :: kjpindex
4189---
4190>     INTEGER(i_std), INTENT(in)                                               :: npts
4191654c660
4192<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                           :: moist_in
4193---
4194>     REAL(r_std), DIMENSION(npts), INTENT(in)                           :: moist_in
4195659c665
4196<     REAL(r_std), DIMENSION(kjpindex)                                       :: moistfunc_result
4197---
4198>     REAL(r_std), DIMENSION(npts)                                       :: moistfunc_result
4199666c672
4200<   FUNCTION control_temp_func (kjpindex, temp_in) RESULT (tempfunc_result)
4201---
4202>   FUNCTION control_temp_func (npts, temp_in) RESULT (tempfunc_result)
4203675c681
4204<     INTEGER(i_std), INTENT(in)                                               :: kjpindex
4205---
4206>     INTEGER(i_std), INTENT(in)                                               :: npts
4207677c683
4208<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                           :: temp_in
4209---
4210>     REAL(r_std), DIMENSION(npts), INTENT(in)                           :: temp_in
4211682c688
4212<     REAL(r_std), DIMENSION(kjpindex)                                       :: tempfunc_result
4213---
4214>     REAL(r_std), DIMENSION(npts)                                       :: tempfunc_result
4215diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/stomate_lpj.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/stomate_lpj.f90
421647,55c47
4217<   PUBLIC StomateLpj_main,StomateLpj_clear
4218<
4219<   ! crown area of individuals (m**2)
4220<   REAL(r_std), ALLOCATABLE, DIMENSION(:,:)                 :: cn_ind
4221<   ! woodmass of individuals (gC)
4222<   REAL(r_std), ALLOCATABLE, DIMENSION(:,:)                 :: woodmass_ind
4223<   ! "maximal" coverage fraction of a PFT (LAI -> infinity) on ground
4224<   REAL(r_std), ALLOCATABLE, DIMENSION(:,:)                 :: veget_max_old
4225<
4226---
4227>   PUBLIC StomateLpj,StomateLpj_clear
422858c50
4229<   LOGICAL, SAVE                                           :: firstcall_lpj = .TRUE.
4230---
4231>   LOGICAL, SAVE                                           :: firstcall = .TRUE.
423261,62d52
4233< ! List of subroutines for initialization :
4234< !- StomateLpj_clear
423566,69d55
4236<     IF (ALLOCATED(cn_ind)) DEALLOCATE(cn_ind)
4237<     IF (ALLOCATED(woodmass_ind)) DEALLOCATE(woodmass_ind)
4238<     IF (ALLOCATED(veget_max_old)) DEALLOCATE(veget_max_old)
4239<
424082d67
4241<
424285c70
4243<   SUBROUTINE StomateLpj_main (kjpindex, dt_days, EndOfYear, EndOfMonth, &
4244---
4245>   SUBROUTINE StomateLpj (npts, dt_days, EndOfYear, EndOfMonth, &
424687c72
4247<        clayfraction, herbivores, &
4248---
4249>        clay, herbivores, &
4250105c90
4251<        co2_to_bm_dgvm, co2_fire, resp_hetero, resp_maint, resp_growth, &
4252---
4253>        co2_to_bm, co2_fire, resp_hetero, resp_maint, resp_growth, &
4254119c104
4255<     INTEGER(i_std), INTENT(in)                                           :: kjpindex
4256---
4257>     INTEGER(i_std), INTENT(in)                                           :: npts
4258123c108
4259<     INTEGER(i_std), DIMENSION(kjpindex,8), INTENT(in)                 :: neighbours
4260---
4261>     INTEGER(i_std), DIMENSION(npts,8), INTENT(in)                 :: neighbours
4262125c110
4263<     REAL(r_std), DIMENSION(kjpindex,2), INTENT(in)                     :: resolution
4264---
4265>     REAL(r_std), DIMENSION(npts,2), INTENT(in)                     :: resolution
4266127c112
4267<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                       :: clayfraction
4268---
4269>     REAL(r_std), DIMENSION(npts), INTENT(in)                       :: clay
4270129c114
4271<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)                  :: herbivores
4272---
4273>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                  :: herbivores
4274131c116
4275<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                       :: tsurf_daily
4276---
4277>     REAL(r_std), DIMENSION(npts), INTENT(in)                       :: tsurf_daily
4278133c118
4279<     REAL(r_std), DIMENSION(kjpindex,nbdl), INTENT(in)                  :: tsoil_daily
4280---
4281>     REAL(r_std), DIMENSION(npts,nbdl), INTENT(in)                  :: tsoil_daily
4282135c120
4283<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                       :: t2m_daily
4284---
4285>     REAL(r_std), DIMENSION(npts), INTENT(in)                       :: t2m_daily
4286137c122
4287<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                       :: t2m_min_daily
4288---
4289>     REAL(r_std), DIMENSION(npts), INTENT(in)                       :: t2m_min_daily
4290139c124
4291<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                       :: litterhum_daily
4292---
4293>     REAL(r_std), DIMENSION(npts), INTENT(in)                       :: litterhum_daily
4294141c126
4295<     REAL(r_std), DIMENSION(kjpindex,nbdl), INTENT(in)                  :: soilhum_daily
4296---
4297>     REAL(r_std), DIMENSION(npts,nbdl), INTENT(in)                  :: soilhum_daily
4298143c128
4299<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)                  :: maxmoiavail_lastyear
4300---
4301>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                  :: maxmoiavail_lastyear
4302145c130
4303<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)                  :: minmoiavail_lastyear
4304---
4305>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                  :: minmoiavail_lastyear
4306147c132
4307<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                       :: gdd0_lastyear
4308---
4309>     REAL(r_std), DIMENSION(npts), INTENT(in)                       :: gdd0_lastyear
4310149c134
4311<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                       :: precip_lastyear
4312---
4313>     REAL(r_std), DIMENSION(npts), INTENT(in)                       :: precip_lastyear
4314151c136
4315<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)                  :: moiavail_month
4316---
4317>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                  :: moiavail_month
4318153c138
4319<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)                  :: moiavail_week
4320---
4321>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                  :: moiavail_week
4322155c140
4323<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                       :: tlong_ref
4324---
4325>     REAL(r_std), DIMENSION(npts), INTENT(in)                       :: tlong_ref
4326157c142
4327<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                       :: t2m_month
4328---
4329>     REAL(r_std), DIMENSION(npts), INTENT(in)                       :: t2m_month
4330159c144
4331<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                       :: t2m_week
4332---
4333>     REAL(r_std), DIMENSION(npts), INTENT(in)                       :: t2m_week
4334161c146
4335<     REAL(r_std), DIMENSION(kjpindex,nbdl), INTENT(in)                  :: tsoil_month
4336---
4337>     REAL(r_std), DIMENSION(npts,nbdl), INTENT(in)                  :: tsoil_month
4338163c148
4339<     REAL(r_std), DIMENSION(kjpindex,nbdl), INTENT(in)                  :: soilhum_month
4340---
4341>     REAL(r_std), DIMENSION(npts,nbdl), INTENT(in)                  :: soilhum_month
4342165c150
4343<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)                   :: gdd_m5_dormance
4344---
4345>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                   :: gdd_m5_dormance
4346167c152
4347<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)                   :: gdd_midwinter
4348---
4349>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                   :: gdd_midwinter
4350169c154
4351<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)                  :: ncd_dormance
4352---
4353>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                  :: ncd_dormance
4354171c156
4355<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)                  :: ngd_minus5
4356---
4357>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                  :: ngd_minus5
4358173c158
4359<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(in)           :: turnover_longterm
4360---
4361>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(in)           :: turnover_longterm
4362175c160
4363<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)                  :: gpp_daily
4364---
4365>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                  :: gpp_daily
4366177c162
4367<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)                  :: time_lowgpp
4368---
4369>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                  :: time_lowgpp
4370179c164
4371<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)                  :: time_hum_min
4372---
4373>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                  :: time_hum_min
4374181c166
4375<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)                  :: maxfpc_lastyear
4376---
4377>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                  :: maxfpc_lastyear
4378183c168
4379<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(in)             :: resp_maint_part
4380---
4381>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(in)             :: resp_maint_part
4382185c170
4383<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)                  :: fpc_max
4384---
4385>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                  :: fpc_max
4386190c175
4387<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(inout)                  :: PFTpresent
4388---
4389>     LOGICAL, DIMENSION(npts,nvm), INTENT(inout)                  :: PFTpresent
4390192c177
4391<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)               :: age
4392---
4393>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)               :: age
4394194c179
4395<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)          :: fireindex
4396---
4397>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)          :: fireindex
4398196c181
4399<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)          :: firelitter
4400---
4401>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)          :: firelitter
4402198c183
4403<     REAL(r_std), DIMENSION(kjpindex,nvm,nleafages), INTENT(inout)     :: leaf_age
4404---
4405>     REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)     :: leaf_age
4406200c185
4407<     REAL(r_std), DIMENSION(kjpindex,nvm,nleafages), INTENT(inout)     :: leaf_frac
4408---
4409>     REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)     :: leaf_frac
4410202c187
4411<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)        :: biomass
4412---
4413>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)        :: biomass
4414204c189
4415<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)               :: ind
4416---
4417>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)               :: ind
4418206c191
4419<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)               :: adapted
4420---
4421>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)               :: adapted
4422208c193
4423<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)               :: regenerate
4424---
4425>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)               :: regenerate
4426210c195
4427<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(inout)                  :: senescence
4428---
4429>     LOGICAL, DIMENSION(npts,nvm), INTENT(inout)                  :: senescence
4430212c197
4431<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)               :: when_growthinit
4432---
4433>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)               :: when_growthinit
4434214c199
4435<     REAL(r_std), DIMENSION(kjpindex,nvm,nlitt), INTENT(inout)         :: litterpart
4436---
4437>     REAL(r_std), DIMENSION(npts,nvm,nlitt), INTENT(inout)         :: litterpart
4438216c201
4439<     REAL(r_std), DIMENSION(kjpindex,nlitt,nvm,nlevs), INTENT(inout)  :: litter
4440---
4441>     REAL(r_std), DIMENSION(npts,nlitt,nvm,nlevs), INTENT(inout)  :: litter
4442219c204
4443<     REAL(r_std), DIMENSION(kjpindex,nvm,nlitt), INTENT(inout)         :: dead_leaves
4444---
4445>     REAL(r_std), DIMENSION(npts,nvm,nlitt), INTENT(inout)         :: dead_leaves
4446221c206
4447<     REAL(r_std), DIMENSION(kjpindex,ncarb,nvm), INTENT(inout)    :: carbon
4448---
4449>     REAL(r_std), DIMENSION(npts,ncarb,nvm), INTENT(inout)    :: carbon
4450223c208
4451<     REAL(r_std), DIMENSION(kjpindex), INTENT(inout)                    :: black_carbon
4452---
4453>     REAL(r_std), DIMENSION(npts), INTENT(inout)                    :: black_carbon
4454226c211
4455<     REAL(r_std), DIMENSION(kjpindex,nvm,nlevs), INTENT(inout)    :: lignin_struc
4456---
4457>     REAL(r_std), DIMENSION(npts,nvm,nlevs), INTENT(inout)    :: lignin_struc
4458228c213
4459<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)               :: veget_max
4460---
4461>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)               :: veget_max
4462230c215
4463<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)               :: veget
4464---
4465>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)               :: veget
4466232c217
4467<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)               :: npp_longterm
4468---
4469>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)               :: npp_longterm
4470234c219
4471<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)               :: lm_lastyearmax
4472---
4473>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)               :: lm_lastyearmax
4474236c221
4475<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)               :: veget_lastlight
4476---
4477>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)               :: veget_lastlight
4478238c223
4479<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)               :: everywhere
4480---
4481>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)               :: everywhere
4482241c226
4483<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(inout)                  :: need_adjacent
4484---
4485>     LOGICAL, DIMENSION(npts,nvm), INTENT(inout)                  :: need_adjacent
4486243c228
4487<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)               :: RIP_time
4488---
4489>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)               :: RIP_time
4490245c230
4491<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)          :: turnover_time
4492---
4493>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)          :: turnover_time
4494250c235
4495<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)                 :: lai
4496---
4497>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                 :: lai
4498254c239
4499<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)                 :: rprof
4500---
4501>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                 :: rprof
4502256c241
4503<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)                 :: npp_daily
4504---
4505>     REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                 :: npp_daily
4506258c243
4507<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(out)          :: turnover_daily
4508---
4509>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(out)          :: turnover_daily
4510260c245
4511<     REAL(r_std), DIMENSION(kjpindex,nlevs), INTENT(inout)                :: control_moist
4512---
4513>     REAL(r_std), DIMENSION(npts,nlevs), INTENT(inout)                :: control_moist
4514262c247
4515<     REAL(r_std), DIMENSION(kjpindex,nlevs), INTENT(inout)                :: control_temp
4516---
4517>     REAL(r_std), DIMENSION(npts,nlevs), INTENT(inout)                :: control_temp
4518265c250
4519<     REAL(r_std), DIMENSION(kjpindex,ncarb,nvm), INTENT(inout)      :: soilcarbon_input
4520---
4521>     REAL(r_std), DIMENSION(npts,ncarb,nvm), INTENT(inout)      :: soilcarbon_input
4522267c252,253
4523<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)                      :: co2_to_bm_dgvm
4524---
4525>     !NV devient 2D
4526>     REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                      :: co2_to_bm
4527271c257
4528<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)                      :: co2_fire
4529---
4530>     REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                      :: co2_fire
4531273c259
4532<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)            :: resp_hetero
4533---
4534>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: resp_hetero
4535275c261
4536<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)                 :: resp_maint
4537---
4538>     REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                 :: resp_maint
4539277c263
4540<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)                 :: resp_growth
4541---
4542>     REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                 :: resp_growth
4543279c265
4544<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)                 :: height
4545---
4546>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                 :: height
4547281c267
4548<     REAL(r_std), DIMENSION(kjpindex), INTENT(inout)                      :: deadleaf_cover
4549---
4550>     REAL(r_std), DIMENSION(npts), INTENT(inout)                      :: deadleaf_cover
4551283c269
4552<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)                 :: vcmax
4553---
4554>     REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                 :: vcmax
4555285c271
4556<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)                 :: vjmax
4557---
4558>     REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                 :: vjmax
4559287c273
4560<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)                 :: t_photo_min
4561---
4562>     REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                 :: t_photo_min
4563289c275
4564<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)                 :: t_photo_opt
4565---
4566>     REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                 :: t_photo_opt
4567291c277
4568<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)                 :: t_photo_max
4569---
4570>     REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                 :: t_photo_max
4571293c279
4572<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(out)          :: bm_to_litter
4573---
4574>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(out)          :: bm_to_litter
4575296c282
4576<     REAL(r_std), DIMENSION(kjpindex,nvm),INTENT(inout)                 :: veget_max_new
4577---
4578>     REAL(r_std), DIMENSION(npts,nvm),INTENT(inout)                 :: veget_max_new
4579300,301c286,287
4580<     REAL(r_std),DIMENSION(kjpindex,0:10), INTENT(inout)                        :: prod10
4581<     REAL(r_std),DIMENSION(kjpindex,0:100), INTENT(inout)                       :: prod100
4582---
4583>     REAL(r_std),DIMENSION(npts,0:10), INTENT(inout)                        :: prod10
4584>     REAL(r_std),DIMENSION(npts,0:100), INTENT(inout)                       :: prod100
4585303,304c289,290
4586<     REAL(r_std),DIMENSION(kjpindex,10), INTENT(inout)                       :: flux10
4587<     REAL(r_std),DIMENSION(kjpindex,100), INTENT(inout)                      :: flux100
4588---
4589>     REAL(r_std),DIMENSION(npts,10), INTENT(inout)                       :: flux10
4590>     REAL(r_std),DIMENSION(npts,100), INTENT(inout)                      :: flux100
4591306c292
4592<     REAL(r_std),DIMENSION(kjpindex), INTENT(inout)                          :: convflux
4593---
4594>     REAL(r_std),DIMENSION(npts), INTENT(inout)                          :: convflux
4595308c294
4596<     REAL(r_std),DIMENSION(kjpindex), INTENT(inout)                          :: cflux_prod10, cflux_prod100
4597---
4598>     REAL(r_std),DIMENSION(npts), INTENT(inout)                          :: cflux_prod10, cflux_prod100
4599310c296
4600<     REAL(r_std), DIMENSION(kjpindex), INTENT(inout)                       :: harvest_above
4601---
4602>     REAL(r_std), DIMENSION(npts), INTENT(inout)                       :: harvest_above
4603312c298
4604<     REAL(r_std), DIMENSION(kjpindex), INTENT(inout)                       :: carb_mass_total
4605---
4606>     REAL(r_std), DIMENSION(npts), INTENT(inout)                       :: carb_mass_total
4607327c313
4608<     REAL(r_std), DIMENSION(kjpindex,nvm)                                   :: tot_bm_to_litter
4609---
4610>     REAL(r_std), DIMENSION(npts,nvm)                                   :: tot_bm_to_litter
4611329c315
4612<     REAL(r_std), DIMENSION(kjpindex,nvm)                                   :: tot_live_biomass
4613---
4614>     REAL(r_std), DIMENSION(npts,nvm)                                   :: tot_live_biomass
4615331c317
4616<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts)                            :: bm_alloc
4617---
4618>     REAL(r_std), DIMENSION(npts,nvm,nparts)                            :: bm_alloc
4619333c319
4620<     REAL(r_std), DIMENSION(kjpindex,nvm)                                   :: tot_turnover
4621---
4622>     REAL(r_std), DIMENSION(npts,nvm)                                   :: tot_turnover
4623335c321
4624<     REAL(r_std), DIMENSION(kjpindex,nvm)                                   :: tot_litter_soil_carb
4625---
4626>     REAL(r_std), DIMENSION(npts,nvm)                                   :: tot_litter_soil_carb
4627337c323
4628<     REAL(r_std), DIMENSION(kjpindex,nvm)                                   :: tot_litter_carb
4629---
4630>     REAL(r_std), DIMENSION(npts,nvm)                                   :: tot_litter_carb
4631339c325
4632<     REAL(r_std), DIMENSION(kjpindex,nvm)                                   :: tot_soil_carb
4633---
4634>     REAL(r_std), DIMENSION(npts,nvm)                                   :: tot_soil_carb
4635341c327,331
4636<     REAL(r_std), DIMENSION(kjpindex)                                      :: carb_mass_variation
4637---
4638>     REAL(r_std), DIMENSION(npts)                                      :: carb_mass_variation
4639>     ! crown area of individuals (m**2)
4640>     REAL(r_std), DIMENSION(npts,nvm)                               :: cn_ind
4641>     ! woodmass of individuals (gC)
4642>     REAL(r_std), DIMENSION(npts,nvm)                               :: woodmass_ind
4643343c333
4644<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts)                        :: f_alloc
4645---
4646>     REAL(r_std), DIMENSION(npts,nvm,nparts)                        :: f_alloc
4647345c335
4648<     REAL(r_std), DIMENSION(kjpindex)                                   :: avail_tree
4649---
4650>     REAL(r_std), DIMENSION(npts)                                   :: avail_tree
4651347c337
4652<     REAL(r_std), DIMENSION(kjpindex)                                   :: avail_grass
4653---
4654>     REAL(r_std), DIMENSION(npts)                                   :: avail_grass
4655352c342
4656<     REAL(r_std),DIMENSION(kjpindex)                                   :: prod10_total, prod100_total
4657---
4658>     REAL(r_std),DIMENSION(npts)                                   :: prod10_total, prod100_total
4659354c344,347
4660<     REAL(r_std),DIMENSION(kjpindex)                                       :: cflux_prod_total
4661---
4662>     REAL(r_std),DIMENSION(npts)                                       :: cflux_prod_total
4663>
4664>     ! "maximal" coverage fraction of a PFT (LAI -> infinity) on ground
4665>     REAL(r_std),DIMENSION(npts,nvm)                                :: veget_max_old
4666357c350
4667<     REAL(r_std), DIMENSION(kjpindex,nvm)                               :: mortality
4668---
4669>     REAL(r_std), DIMENSION(npts,nvm)                               :: mortality
4670359c352
4671<     REAL(r_std), DIMENSION(kjpindex)                                   :: vartmp
4672---
4673>     REAL(r_std), DIMENSION(npts)                                   :: vartmp
4674361c354
4675<     REAL(r_std), DIMENSION(kjpindex,nvm)                          :: histvar
4676---
4677>     REAL(r_std), DIMENSION(npts,nvm)                          :: histvar
4678367,494d359
4679<     IF ( firstcall_lpj ) THEN
4680< !.OR. .NOT. firstcall_lpj  ????
4681<        !
4682<        ! 0 Allocation
4683<        !
4684<
4685<
4686<        ALLOCATE(cn_ind(kjpindex,nvm))
4687<        ALLOCATE(woodmass_ind(kjpindex,nvm))
4688<        ALLOCATE(veget_max_old(kjpindex,nvm))
4689<
4690< !!$       IF ( control%ok_dgvm .OR. .NOT.lpj_gap_const_mort) THEN
4691< !!$
4692< !!$          CALL crown (kjpindex,  PFTpresent, &
4693< !!$               ind, biomass, woodmass_ind, &
4694< !!$               veget_max, cn_ind, height)
4695< !!$
4696< !!$       ENDIF
4697< !!$
4698< !!$       CALL prescribe (kjpindex, &
4699< !!$            veget_max, PFTpresent, everywhere, when_growthinit, &
4700< !!$            biomass, leaf_frac, ind, cn_ind)
4701< !!$       
4702<        CALL constraints_main (kjpindex, dt_days, &
4703<             t2m_month, t2m_min_daily,when_growthinit, &
4704<             adapted, regenerate)
4705<
4706<        IF ( control%ok_dgvm ) THEN
4707<
4708<           CALL pftinout_main (kjpindex, dt_days, adapted, regenerate, &
4709<                neighbours, veget, veget_max, &
4710<                biomass, ind, cn_ind, age, leaf_frac, npp_longterm, lm_lastyearmax, senescence, &
4711<                PFTpresent, everywhere, when_growthinit, need_adjacent, RIP_time, &
4712<                co2_to_bm_dgvm, &
4713<                avail_tree, avail_grass)
4714<
4715< !!$          CALL kill (kjpindex, 'pftinout  ', lm_lastyearmax, &
4716< !!$               ind, PFTpresent, cn_ind, biomass, senescence, RIP_time, &
4717< !!$               lai, age, leaf_age, leaf_frac, npp_longterm, &
4718< !!$               when_growthinit, everywhere, veget, veget_max, bm_to_litter)
4719< !!$
4720<        ENDIF
4721<
4722<        CALL phenology_main (kjpindex, dt_days, PFTpresent, &
4723<             veget_max, &
4724<             tlong_ref, t2m_month, t2m_week, gpp_daily, &
4725<             maxmoiavail_lastyear, minmoiavail_lastyear, &
4726<             moiavail_month, moiavail_week, &
4727<             gdd_m5_dormance, gdd_midwinter, ncd_dormance, ngd_minus5, &
4728<             senescence, time_lowgpp, time_hum_min, &
4729<             biomass, leaf_frac, leaf_age, &
4730<             when_growthinit, co2_to_bm_dgvm, lai)
4731<
4732<        CALL alloc_main (kjpindex, dt_days, &
4733<             lai, veget_max, senescence, when_growthinit, &
4734<             moiavail_week, tsoil_month, soilhum_month, &
4735<             biomass, age, leaf_age, leaf_frac, rprof, f_alloc)
4736<
4737<        CALL npp_calc_main (kjpindex, dt_days, &
4738<             PFTpresent, &
4739<             tlong_ref, t2m_daily, tsoil_daily, lai, rprof, &
4740<             gpp_daily, f_alloc, bm_alloc, resp_maint_part,&
4741<             biomass, leaf_age, leaf_frac, age, &
4742<             resp_maint, resp_growth, npp_daily)
4743<
4744<        CALL fire_main (kjpindex, dt_days, litterpart, &
4745<             litterhum_daily, t2m_daily, lignin_struc, &
4746<             fireindex, firelitter, biomass, ind, &
4747<             litter, dead_leaves, bm_to_litter, black_carbon, &
4748<             co2_fire)
4749<       
4750<        CALL gap_main (kjpindex, dt_days, &
4751<             npp_longterm, turnover_longterm, lm_lastyearmax, &
4752<             PFTpresent, biomass, ind, bm_to_litter, mortality)
4753<
4754<
4755<        CALL vmax (kjpindex, dt_days, &
4756<             leaf_age, leaf_frac, &
4757<             vcmax, vjmax)
4758<
4759< !!$       CALL assim_temp (kjpindex, tlong_ref, t2m_month, &
4760< !!$            t_photo_min, t_photo_opt, t_photo_max)
4761< !!$
4762<        CALL turn_main (kjpindex, dt_days, PFTpresent, &
4763<             herbivores, &
4764<             maxmoiavail_lastyear, minmoiavail_lastyear, &
4765<             moiavail_week,  moiavail_month,tlong_ref, t2m_month, t2m_week, veget_max, &
4766<             leaf_age, leaf_frac, age, lai, biomass, &
4767<             turnover_daily, senescence,turnover_time)
4768<
4769<        IF ( control%ok_dgvm ) THEN
4770<
4771<           CALL light_main (kjpindex, dt_days, &
4772<                veget_max, fpc_max, PFTpresent, cn_ind, lai, maxfpc_lastyear, &
4773<                lm_lastyearmax, ind, biomass, veget_lastlight, bm_to_litter, mortality)
4774<           
4775<        ENDIF
4776<       
4777<        IF ( control%ok_dgvm .OR. .NOT.lpj_gap_const_mort ) THEN
4778<
4779<           CALL establish_main (kjpindex, dt_days, PFTpresent, regenerate, &
4780<                neighbours, resolution, need_adjacent, herbivores, &
4781<                precip_lastyear, gdd0_lastyear, lm_lastyearmax, &
4782<                cn_ind, lai, avail_tree, avail_grass, npp_longterm, &
4783<                leaf_age, leaf_frac, &
4784<                ind, biomass, age, everywhere, co2_to_bm_dgvm, veget_max, woodmass_ind)
4785<
4786<        ENDIF
4787<
4788< !!$       CALL cover (kjpindex, cn_ind, ind, biomass, &
4789< !!$            veget_max, veget_max_old, veget, &
4790< !!$            lai, litter, carbon, turnover_daily, bm_to_litter)
4791< !!$       
4792< !!$       IF (lcchange) THEN
4793< !!$          CALL lcchange_main (kjpindex, dt_days, veget_max, veget_max_new, &
4794< !!$               biomass, ind, age, PFTpresent, senescence, when_growthinit, &
4795< !!$               everywhere, veget, &
4796< !!$               co2_to_bm_dgvm, bm_to_litter, turnover_daily, cn_ind,flux10,flux100, &
4797< !!$               prod10,prod100,convflux,cflux_prod10,cflux_prod100,leaf_frac,&
4798< !!$               npp_longterm, lm_lastyearmax, litter, carbon)
4799< !!$       ENDIF
4800<
4801<
4802<        firstcall_lpj=.FALSE.
4803<        RETURN
4804<
4805<     ENDIF
4806<
4807502c367
4808<     co2_to_bm_dgvm(:,:) = zero
4809---
4810>     co2_to_bm(:,:) = zero
4811541c406
4812<        CALL crown (kjpindex,  PFTpresent, &
4813---
4814>        CALL crown (npts,  PFTpresent, &
4815555c420
4816<     CALL prescribe (kjpindex, &
4817---
4818>     CALL prescribe (npts, &
4819565c430
4820<     CALL constraints_main (kjpindex, dt_days, &
4821---
4822>     CALL constraints (npts, dt_days, &
4823579c444
4824<        CALL pftinout_main (kjpindex, dt_days, adapted, regenerate, &
4825---
4826>        CALL pftinout (npts, dt_days, adapted, regenerate, &
4827583c448
4828<             co2_to_bm_dgvm, &
4829---
4830>             co2_to_bm, &
4831592c457
4832<        CALL kill (kjpindex, 'pftinout  ', lm_lastyearmax, &
4833---
4834>        CALL kill (npts, 'pftinout  ', lm_lastyearmax, &
4835618c483
4836<        CALL crown (kjpindex, PFTpresent, &
4837---
4838>        CALL crown (npts, PFTpresent, &
4839627,628c492,493
4840<     CALL histwrite (hist_id_stomate, 'WHEN_GROWTHINIT', itime, when_growthinit, kjpindex*nvm, horipft_index)
4841<     CALL histwrite (hist_id_stomate, 'TIME_LOWGPP', itime, time_lowgpp, kjpindex*nvm, horipft_index)
4842---
4843>     CALL histwrite (hist_id_stomate, 'WHEN_GROWTHINIT', itime, when_growthinit, npts*nvm, horipft_index)
4844>     CALL histwrite (hist_id_stomate, 'TIME_LOWGPP', itime, time_lowgpp, npts*nvm, horipft_index)
4845635c500
4846<     CALL histwrite (hist_id_stomate, 'PFTPRESENT', itime, histvar, kjpindex*nvm, horipft_index)
4847---
4848>     CALL histwrite (hist_id_stomate, 'PFTPRESENT', itime, histvar, npts*nvm, horipft_index)
4849642c507
4850<     CALL histwrite (hist_id_stomate, 'GDD_MIDWINTER', itime, histvar, kjpindex*nvm, horipft_index)
4851---
4852>     CALL histwrite (hist_id_stomate, 'GDD_MIDWINTER', itime, histvar, npts*nvm, horipft_index)
4853649c514
4854<     CALL histwrite (hist_id_stomate, 'NCD_DORMANCE', itime, histvar, kjpindex*nvm, horipft_index)
4855---
4856>     CALL histwrite (hist_id_stomate, 'NCD_DORMANCE', itime, histvar, npts*nvm, horipft_index)
4857651c516
4858<     CALL phenology_main (kjpindex, dt_days, PFTpresent, &
4859---
4860>     CALL phenology (npts, dt_days, PFTpresent, &
4861659c524
4862<          when_growthinit, co2_to_bm_dgvm, lai)
4863---
4864>          when_growthinit, co2_to_bm, lai)
4865665c530
4866<     CALL alloc_main (kjpindex, dt_days, &
4867---
4868>     CALL alloc (npts, dt_days, &
4869674c539
4870<     CALL npp_calc_main (kjpindex, dt_days, &
4871---
4872>     CALL npp_calc (npts, dt_days, &
4873682c547
4874<        CALL kill (kjpindex, 'npp       ', lm_lastyearmax,  &
4875---
4876>        CALL kill (npts, 'npp       ', lm_lastyearmax,  &
4877703c568
4878<        CALL crown (kjpindex, PFTpresent, &
4879---
4880>        CALL crown (npts, PFTpresent, &
4881713c578
4882<     CALL fire_main (kjpindex, dt_days, litterpart, &
4883---
4884>     CALL fire (npts, dt_days, litterpart, &
4885723c588
4886<        CALL kill (kjpindex, 'fire      ', lm_lastyearmax, &
4887---
4888>        CALL kill (npts, 'fire      ', lm_lastyearmax, &
4889734c599
4890<     CALL gap_main (kjpindex, dt_days, &
4891---
4892>     CALL gap (npts, dt_days, &
4893742c607
4894<        CALL kill (kjpindex, 'gap       ', lm_lastyearmax, &
4895---
4896>        CALL kill (npts, 'gap       ', lm_lastyearmax, &
4897753c618
4898<     CALL vmax (kjpindex, dt_days, &
4899---
4900>     CALL vmax (npts, dt_days, &
4901757c622
4902<     CALL assim_temp (kjpindex, tlong_ref, t2m_month, &
4903---
4904>     CALL assim_temp (npts, tlong_ref, t2m_month, &
4905764c629
4906<     CALL turn_main (kjpindex, dt_days, PFTpresent, &
4907---
4908>     CALL turn (npts, dt_days, PFTpresent, &
4909781c646
4910<        CALL light_main (kjpindex, dt_days, &
4911---
4912>        CALL light (npts, dt_days, &
4913789c654
4914<        CALL kill (kjpindex, 'light     ', lm_lastyearmax, &
4915---
4916>        CALL kill (npts, 'light     ', lm_lastyearmax, &
4917806c671
4918<        CALL establish_main (kjpindex, dt_days, PFTpresent, regenerate, &
4919---
4920>        CALL establish (npts, dt_days, PFTpresent, regenerate, &
4921811c676
4922<             ind, biomass, age, everywhere, co2_to_bm_dgvm, veget_max, woodmass_ind)
4923---
4924>             ind, biomass, age, everywhere, co2_to_bm, veget_max, woodmass_ind)
4925817c682
4926<        CALL crown (kjpindex, PFTpresent, &
4927---
4928>        CALL crown (npts, PFTpresent, &
4929827c692
4930<     CALL cover (kjpindex, cn_ind, ind, biomass, &
4931---
4932>     CALL cover (npts, cn_ind, ind, biomass, &
4933839c704
4934<        CALL harvest(kjpindex, dt_days, veget_max, veget, &
4935---
4936>        CALL harvest(npts, dt_days, veget_max, veget, &
4937849c714
4938<           CALL lcchange_main (kjpindex, dt_days, veget_max, veget_max_new, &
4939---
4940>           CALL lcchange_main (npts, dt_days, veget_max, veget_max_new, &
4941852c717
4942<                co2_to_bm_dgvm, bm_to_litter, turnover_daily, cn_ind,flux10,flux100, &
4943---
4944>                co2_to_bm, bm_to_litter, turnover_daily, bm_sapl, tree, cn_ind,flux10,flux100, &
4945906c771
4946<          resolution(:,1), kjpindex, hori_index)
4947---
4948>          resolution(:,1), npts, hori_index)
4949908c773
4950<          resolution(:,2), kjpindex, hori_index)
4951---
4952>          resolution(:,2), npts, hori_index)
4953910c775
4954<          contfrac(:), kjpindex, hori_index)
4955---
4956>          contfrac(:), npts, hori_index)
4957913c778
4958<          litter(:,istructural,:,iabove), kjpindex*nvm, horipft_index)
4959---
4960>          litter(:,istructural,:,iabove), npts*nvm, horipft_index)
4961915c780
4962<          litter(:,imetabolic,:,iabove), kjpindex*nvm, horipft_index)
4963---
4964>          litter(:,imetabolic,:,iabove), npts*nvm, horipft_index)
4965917c782
4966<          litter(:,istructural,:,ibelow), kjpindex*nvm, horipft_index)
4967---
4968>          litter(:,istructural,:,ibelow), npts*nvm, horipft_index)
4969919c784
4970<          litter(:,imetabolic,:,ibelow), kjpindex*nvm, horipft_index)
4971---
4972>          litter(:,imetabolic,:,ibelow), npts*nvm, horipft_index)
4973922c787
4974<          deadleaf_cover, kjpindex, hori_index)
4975---
4976>          deadleaf_cover, npts, hori_index)
4977925c790
4978<          tot_litter_soil_carb, kjpindex*nvm, horipft_index)
4979---
4980>          tot_litter_soil_carb, npts*nvm, horipft_index)
4981927c792
4982<          carbon(:,iactive,:), kjpindex*nvm, horipft_index)
4983---
4984>          carbon(:,iactive,:), npts*nvm, horipft_index)
4985929c794
4986<          carbon(:,islow,:), kjpindex*nvm, horipft_index)
4987---
4988>          carbon(:,islow,:), npts*nvm, horipft_index)
4989931c796
4990<          carbon(:,ipassive,:), kjpindex*nvm, horipft_index)
4991---
4992>          carbon(:,ipassive,:), npts*nvm, horipft_index)
4993934c799
4994<          t2m_month, kjpindex, hori_index)
4995---
4996>          t2m_month, npts, hori_index)
4997936c801
4998<          t2m_week, kjpindex, hori_index)
4999---
5000>          t2m_week, npts, hori_index)
5001939c804
5002<          resp_hetero(:,:), kjpindex*nvm, horipft_index)
5003---
5004>          resp_hetero(:,:), npts*nvm, horipft_index)
5005942c807
5006<          black_carbon, kjpindex, hori_index)
5007---
5008>          black_carbon, npts, hori_index)
5009945c810
5010<          fireindex(:,:), kjpindex*nvm, horipft_index)
5011---
5012>          fireindex(:,:), npts*nvm, horipft_index)
5013947c812
5014<          litterhum_daily, kjpindex, hori_index)
5015---
5016>          litterhum_daily, npts, hori_index)
5017949c814
5018<          co2_fire, kjpindex*nvm, horipft_index)
5019---
5020>          co2_fire, npts*nvm, horipft_index)
5021951c816
5022<          co2_to_bm_dgvm, kjpindex*nvm, horipft_index)
5023---
5024>          co2_to_bm, npts*nvm, horipft_index)
5025954c819
5026<          convflux, kjpindex, hori_index)
5027---
5028>          convflux, npts, hori_index)
5029956c821
5030<          cflux_prod10, kjpindex, hori_index)
5031---
5032>          cflux_prod10, npts, hori_index)
5033958c823
5034<          cflux_prod100, kjpindex, hori_index)
5035---
5036>          cflux_prod100, npts, hori_index)
5037960c825
5038<          harvest_above, kjpindex, hori_index)
5039---
5040>          harvest_above, npts, hori_index)
5041965c830
5042<          lai, kjpindex*nvm, horipft_index)
5043---
5044>          lai, npts*nvm, horipft_index)
5045967c832
5046<          veget, kjpindex*nvm, horipft_index)
5047---
5048>          veget, npts*nvm, horipft_index)
5049969c834
5050<          veget_max, kjpindex*nvm, horipft_index)
5051---
5052>          veget_max, npts*nvm, horipft_index)
5053971c836
5054<          npp_daily, kjpindex*nvm, horipft_index)
5055---
5056>          npp_daily, npts*nvm, horipft_index)
5057973c838
5058<          gpp_daily, kjpindex*nvm, horipft_index)
5059---
5060>          gpp_daily, npts*nvm, horipft_index)
5061975c840
5062<          ind, kjpindex*nvm, horipft_index)
5063---
5064>          ind, npts*nvm, horipft_index)
5065977c842
5066<          cn_ind, kjpindex*nvm, horipft_index)
5067---
5068>          cn_ind, npts*nvm, horipft_index)
5069979c844
5070<          woodmass_ind, kjpindex*nvm, horipft_index)
5071---
5072>          woodmass_ind, npts*nvm, horipft_index)
5073981c846
5074<          tot_live_biomass, kjpindex*nvm, horipft_index)
5075---
5076>          tot_live_biomass, npts*nvm, horipft_index)
5077983c848
5078<          biomass(:,:,ileaf), kjpindex*nvm, horipft_index)
5079---
5080>          biomass(:,:,ileaf), npts*nvm, horipft_index)
5081985c850
5082<          biomass(:,:,isapabove), kjpindex*nvm, horipft_index)
5083---
5084>          biomass(:,:,isapabove), npts*nvm, horipft_index)
5085987c852
5086<          biomass(:,:,isapbelow), kjpindex*nvm, horipft_index)
5087---
5088>          biomass(:,:,isapbelow), npts*nvm, horipft_index)
5089989c854
5090<          biomass(:,:,iheartabove), kjpindex*nvm, horipft_index)
5091---
5092>          biomass(:,:,iheartabove), npts*nvm, horipft_index)
5093991c856
5094<          biomass(:,:,iheartbelow), kjpindex*nvm, horipft_index)
5095---
5096>          biomass(:,:,iheartbelow), npts*nvm, horipft_index)
5097993c858
5098<          biomass(:,:,iroot), kjpindex*nvm, horipft_index)
5099---
5100>          biomass(:,:,iroot), npts*nvm, horipft_index)
5101995c860
5102<          biomass(:,:,ifruit), kjpindex*nvm, horipft_index)
5103---
5104>          biomass(:,:,ifruit), npts*nvm, horipft_index)
5105997c862
5106<          biomass(:,:,icarbres), kjpindex*nvm, horipft_index)
5107---
5108>          biomass(:,:,icarbres), npts*nvm, horipft_index)
5109999c864
5110<          tot_turnover, kjpindex*nvm, horipft_index)
5111---
5112>          tot_turnover, npts*nvm, horipft_index)
51131001c866
5114<          turnover_daily(:,:,ileaf), kjpindex*nvm, horipft_index)
5115---
5116>          turnover_daily(:,:,ileaf), npts*nvm, horipft_index)
51171003c868
5118<          turnover_daily(:,:,isapabove), kjpindex*nvm, horipft_index)
5119---
5120>          turnover_daily(:,:,isapabove), npts*nvm, horipft_index)
51211005c870
5122<          turnover_daily(:,:,iroot), kjpindex*nvm, horipft_index)
5123---
5124>          turnover_daily(:,:,iroot), npts*nvm, horipft_index)
51251007c872
5126<          turnover_daily(:,:,ifruit), kjpindex*nvm, horipft_index)
5127---
5128>          turnover_daily(:,:,ifruit), npts*nvm, horipft_index)
51291009c874
5130<          tot_bm_to_litter, kjpindex*nvm, horipft_index)
5131---
5132>          tot_bm_to_litter, npts*nvm, horipft_index)
51331011c876
5134<          bm_to_litter(:,:,ileaf), kjpindex*nvm, horipft_index)
5135---
5136>          bm_to_litter(:,:,ileaf), npts*nvm, horipft_index)
51371013c878
5138<          bm_to_litter(:,:,isapabove), kjpindex*nvm, horipft_index)
5139---
5140>          bm_to_litter(:,:,isapabove), npts*nvm, horipft_index)
51411015c880
5142<          bm_to_litter(:,:,isapbelow), kjpindex*nvm, horipft_index)
5143---
5144>          bm_to_litter(:,:,isapbelow), npts*nvm, horipft_index)
51451017c882
5146<          bm_to_litter(:,:,iheartabove), kjpindex*nvm, horipft_index)
5147---
5148>          bm_to_litter(:,:,iheartabove), npts*nvm, horipft_index)
51491019c884
5150<          bm_to_litter(:,:,iheartbelow), kjpindex*nvm, horipft_index)
5151---
5152>          bm_to_litter(:,:,iheartbelow), npts*nvm, horipft_index)
51531021c886
5154<          bm_to_litter(:,:,iroot), kjpindex*nvm, horipft_index)
5155---
5156>          bm_to_litter(:,:,iroot), npts*nvm, horipft_index)
51571023c888
5158<          bm_to_litter(:,:,ifruit), kjpindex*nvm, horipft_index)
5159---
5160>          bm_to_litter(:,:,ifruit), npts*nvm, horipft_index)
51611025c890
5162<          bm_to_litter(:,:,icarbres), kjpindex*nvm, horipft_index)
5163---
5164>          bm_to_litter(:,:,icarbres), npts*nvm, horipft_index)
51651027c892
5166<          resp_maint, kjpindex*nvm, horipft_index)
5167---
5168>          resp_maint, npts*nvm, horipft_index)
51691029c894
5170<          resp_growth, kjpindex*nvm, horipft_index)
5171---
5172>          resp_growth, npts*nvm, horipft_index)
51731031c896
5174<          age, kjpindex*nvm, horipft_index)
5175---
5176>          age, npts*nvm, horipft_index)
51771033c898
5178<          height, kjpindex*nvm, horipft_index)
5179---
5180>          height, npts*nvm, horipft_index)
51811035c900
5182<          moiavail_week, kjpindex*nvm, horipft_index)
5183---
5184>          moiavail_week, npts*nvm, horipft_index)
51851037c902
5186<          vcmax, kjpindex*nvm, horipft_index)
5187---
5188>          vcmax, npts*nvm, horipft_index)
51891039c904
5190<          turnover_time, kjpindex*nvm, horipft_index)
5191---
5192>          turnover_time, npts*nvm, horipft_index)
51931042c907
5194<          prod10, kjpindex*11, horip11_index)
5195---
5196>          prod10, npts*11, horip11_index)
51971044c909
5198<          prod100, kjpindex*101, horip101_index)
5199---
5200>          prod100, npts*101, horip101_index)
52011046c911
5202<          flux10, kjpindex*10, horip10_index)
5203---
5204>          flux10, npts*10, horip10_index)
52051048c913
5206<          flux100, kjpindex*100, horip100_index)
5207---
5208>          flux100, npts*100, horip100_index)
52091053c918
5210<             vartmp, kjpindex, hori_index)
5211---
5212>             vartmp, npts, hori_index)
52131056c921
5214<             vartmp, kjpindex, hori_index)
5215---
5216>             vartmp, npts, hori_index)
52171059c924
5218<             vartmp, kjpindex, hori_index)
5219---
5220>             vartmp, npts, hori_index)
52211062c927
5222<             vartmp, kjpindex, hori_index)
5223---
5224>             vartmp, npts, hori_index)
52251065c930
5226<             vartmp, kjpindex, hori_index)
5227---
5228>             vartmp, npts, hori_index)
52291069c934
5230<             vartmp, kjpindex, hori_index)
5231---
5232>             vartmp, npts, hori_index)
52331072c937
5234<             vartmp, kjpindex, hori_index)
5235---
5236>             vartmp, npts, hori_index)
52371075c940
5238<             vartmp, kjpindex, hori_index)
5239---
5240>             vartmp, npts, hori_index)
52411078c943
5242<             vartmp, kjpindex, hori_index)
5243---
5244>             vartmp, npts, hori_index)
52451081c946
5246<             vartmp, kjpindex, hori_index)
5247---
5248>             vartmp, npts, hori_index)
52491084c949
5250<             vartmp, kjpindex, hori_index)
5251---
5252>             vartmp, npts, hori_index)
52531087c952
5254<             vartmp, kjpindex, hori_index)
5255---
5256>             vartmp, npts, hori_index)
52571090c955
5258<             vartmp, kjpindex, hori_index)
5259---
5260>             vartmp, npts, hori_index)
52611094c959
5262<             vartmp, kjpindex, hori_index)
5263---
5264>             vartmp, npts, hori_index)
52651097c962
5266<             vartmp, kjpindex, hori_index)
5267---
5268>             vartmp, npts, hori_index)
52691100c965
5270<             vartmp, kjpindex, hori_index)
5271---
5272>             vartmp, npts, hori_index)
52731103c968
5274<             vartmp, kjpindex, hori_index)
5275---
5276>             vartmp, npts, hori_index)
52771106c971
5278<             vartmp, kjpindex, hori_index)
5279---
5280>             vartmp, npts, hori_index)
52811110c975
5282<             vartmp, kjpindex, hori_index)
5283---
5284>             vartmp, npts, hori_index)
52851113c978
5286<             vartmp, kjpindex, hori_index)
5287---
5288>             vartmp, npts, hori_index)
52891116c981
5290<             vartmp, kjpindex, hori_index)
5291---
5292>             vartmp, npts, hori_index)
52931119c984
5294<             vartmp, kjpindex, hori_index)
5295---
5296>             vartmp, npts, hori_index)
52971122c987
5298<             vartmp, kjpindex, hori_index)
5299---
5300>             vartmp, npts, hori_index)
53011125c990
5302<             vartmp, kjpindex, hori_index)
5303---
5304>             vartmp, npts, hori_index)
53051128c993
5306<             vartmp, kjpindex, hori_index)
5307---
5308>             vartmp, npts, hori_index)
53091133c998
5310<             histvar, kjpindex*nvm, horipft_index)
5311---
5312>             histvar, npts*nvm, horipft_index)
53131136c1001
5314<             vartmp, kjpindex, hori_index)
5315---
5316>             vartmp, npts, hori_index)
53171139c1004
5318<             vartmp, kjpindex, hori_index)
5319---
5320>             vartmp, npts, hori_index)
53211142c1007
5322<             vartmp, kjpindex, hori_index)
5323---
5324>             vartmp, npts, hori_index)
53251145c1010
5326<             vartmp, kjpindex, hori_index)
5327---
5328>             vartmp, npts, hori_index)
53291148c1013
5330<             vartmp, kjpindex, hori_index)
5331---
5332>             vartmp, npts, hori_index)
53331151c1016
5334<             vartmp, kjpindex, hori_index)
5335---
5336>             vartmp, npts, hori_index)
53371154c1019
5338<             vartmp, kjpindex, hori_index)
5339---
5340>             vartmp, npts, hori_index)
53411157c1022
5342<             vartmp, kjpindex, hori_index)
5343---
5344>             vartmp, npts, hori_index)
53451160c1025
5346<             vartmp, kjpindex, hori_index)
5347---
5348>             vartmp, npts, hori_index)
53491163c1028
5350<             resolution(:,1), kjpindex, hori_index)
5351---
5352>             resolution(:,1), npts, hori_index)
53531165c1030
5354<             resolution(:,2), kjpindex, hori_index)
5355---
5356>             resolution(:,2), npts, hori_index)
53571167c1032
5358<             contfrac(:), kjpindex, hori_index)
5359---
5360>             contfrac(:), npts, hori_index)
53611173c1038
5362<   END SUBROUTINE StomateLpj_main
5363---
5364>   END SUBROUTINE StomateLpj
53651175c1040
5366<   SUBROUTINE harvest(kjpindex, dt_days, veget_max, veget, &
5367---
5368>   SUBROUTINE harvest(npts, dt_days, veget_max, veget, &
53691181c1046
5370<     INTEGER, INTENT(in)                                            :: kjpindex
5371---
5372>     INTEGER, INTENT(in)                                            :: npts
53731187c1052
5374<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)                 :: veget_max
5375---
5376>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                 :: veget_max
53771192c1057
5378<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)                    :: veget
5379---
5380>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                    :: veget
53811195c1060
5382<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)           :: bm_to_litter
5383---
5384>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)           :: bm_to_litter
53851198c1063
5386<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)          :: turnover_daily
5387---
5388>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)          :: turnover_daily
53891200c1065
5390<     REAL(r_std), DIMENSION(kjpindex), INTENT(inout)                       :: harvest_above
5391---
5392>     REAL(r_std), DIMENSION(npts), INTENT(inout)                       :: harvest_above
53931211c1076
5394<     DO i = 1, kjpindex
5395---
5396>     DO i = 1, npts
5397diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/stomate_npp.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/stomate_npp.f90
539824c24
5399<   PUBLIC npp_calc_main,npp_calc_clear
5400---
5401>   PUBLIC npp_calc,npp_calc_clear
540227c27
5403<   LOGICAL, SAVE                                              :: firstcall_npp = .TRUE.
5404---
5405>   LOGICAL, SAVE                                              :: firstcall = .TRUE.
540630,31d29
5407< ! List of subroutines for initialization :
5408< !- npp_calc_clear
540934c32
5410<     firstcall_npp=.TRUE.
5411---
5412>     firstcall=.TRUE.
541337c35
5414<   SUBROUTINE npp_calc_main (kjpindex, dt_days, &
5415---
5416>   SUBROUTINE npp_calc (npts, dt, &
541739c37
5418<        tlong_ref, t2m_daily, tsoil_daily, lai, rprof, &
5419---
5420>        tlong_ref, t2m, tsoil, lai, rprof, &
542142c40
5422<        resp_maint, resp_growth, npp_daily)
5423---
5424>        resp_maint, resp_growth, npp)
542551c49
5426<     INTEGER(i_std), INTENT(in)                                        :: kjpindex
5427---
5428>     INTEGER(i_std), INTENT(in)                                        :: npts
542953c51
5430<     REAL(r_std), INTENT(in)                                     :: dt_days
5431---
5432>     REAL(r_std), INTENT(in)                                     :: dt
543355c53
5434<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(in)                  :: PFTpresent
5435---
5436>     LOGICAL, DIMENSION(npts,nvm), INTENT(in)                  :: PFTpresent
543757c55
5438<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                    :: tlong_ref
5439---
5440>     REAL(r_std), DIMENSION(npts), INTENT(in)                    :: tlong_ref
544159c57
5442<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                    :: t2m_daily
5443---
5444>     REAL(r_std), DIMENSION(npts), INTENT(in)                    :: t2m
544561c59
5446<     REAL(r_std), DIMENSION(kjpindex,nbdl), INTENT(in)               :: tsoil_daily
5447---
5448>     REAL(r_std), DIMENSION(npts,nbdl), INTENT(in)               :: tsoil
544963c61
5450<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: lai
5451---
5452>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: lai
545365c63
5454<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: rprof
5455---
5456>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: rprof
545767c65
5458<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: gpp
5459---
5460>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: gpp
546169c67
5462<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(in)        :: f_alloc
5463---
5464>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(in)        :: f_alloc
546571c69
5466<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(in)             :: resp_maint_part
5467---
5468>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(in)             :: resp_maint_part
546976c74
5470<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)     :: biomass
5471---
5472>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)     :: biomass
547378c76
5474<     REAL(r_std), DIMENSION(kjpindex,nvm,nleafages), INTENT(inout)  :: leaf_age
5475---
5476>     REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)  :: leaf_age
547780c78
5478<     REAL(r_std), DIMENSION(kjpindex,nvm,nleafages), INTENT(inout)  :: leaf_frac
5479---
5480>     REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)  :: leaf_frac
548182c80
5482<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)            :: age
5483---
5484>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: age
548587c85
5486<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)              :: resp_maint
5487---
5488>     REAL(r_std), DIMENSION(npts,nvm), INTENT(out)              :: resp_maint
548989c87
5490<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)              :: resp_growth
5491---
5492>     REAL(r_std), DIMENSION(npts,nvm), INTENT(out)              :: resp_growth
549391c89
5494<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)              :: npp_daily
5495---
5496>     REAL(r_std), DIMENSION(npts,nvm), INTENT(out)              :: npp
549793c91
5498<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(out)       :: bm_alloc
5499---
5500>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(out)       :: bm_alloc
550198a97,98
5502>     ! soil levels (m)
5503>     REAL(r_std), SAVE, DIMENSION(0:nbdl)                        :: z_soil
5504100c100
5505<     REAL(r_std), DIMENSION(kjpindex,nvm)                           :: t_root
5506---
5507>     REAL(r_std), DIMENSION(npts,nvm)                           :: t_root
5508102c102
5509<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts)                    :: coeff_maint
5510---
5511>     REAL(r_std), DIMENSION(npts,nvm,nparts)                    :: coeff_maint
5512104c104
5513<     REAL(r_std), DIMENSION(kjpindex,nparts)                         :: t_maint
5514---
5515>     REAL(r_std), DIMENSION(npts,nparts)                         :: t_maint
5516106c106
5517<     REAL(r_std), DIMENSION(kjpindex)                                :: rpc
5518---
5519>     REAL(r_std), DIMENSION(npts)                                :: rpc
5520108c108
5521<     REAL(r_std), DIMENSION(kjpindex)                                :: tl
5522---
5523>     REAL(r_std), DIMENSION(npts)                                :: tl
5524110c110
5525<     REAL(r_std), DIMENSION(kjpindex)                                :: slope
5526---
5527>     REAL(r_std), DIMENSION(npts)                                :: slope
5528112c112
5529<     REAL(r_std), DIMENSION(kjpindex,nparts)                         :: resp_growth_part
5530---
5531>     REAL(r_std), DIMENSION(npts,nparts)                         :: resp_growth_part
5532114c114
5533<     REAL(r_std), DIMENSION(kjpindex,nvm)                           :: bm_alloc_tot
5534---
5535>     REAL(r_std), DIMENSION(npts,nvm)                           :: bm_alloc_tot
5536116c116
5537<     REAL(r_std), DIMENSION(kjpindex)                                :: bm_add
5538---
5539>     REAL(r_std), DIMENSION(npts)                                :: bm_add
5540118c118
5541<     REAL(r_std), DIMENSION(kjpindex)                                :: bm_new
5542---
5543>     REAL(r_std), DIMENSION(npts)                                :: bm_new
5544120c120
5545<     REAL(r_std), DIMENSION(kjpindex,nvm)                           :: leaf_mass_young
5546---
5547>     REAL(r_std), DIMENSION(npts,nvm)                           :: leaf_mass_young
5548122c122
5549<     REAL(r_std), DIMENSION(kjpindex,nvm)                           :: lm_old
5550---
5551>     REAL(r_std), DIMENSION(npts,nvm)                           :: lm_old
5552124c124
5553<     REAL(r_std), DIMENSION(kjpindex,nvm)                           :: bm_create
5554---
5555>     REAL(r_std), DIMENSION(npts,nvm)                           :: bm_create
5556126c126
5557<     REAL(r_std), DIMENSION(kjpindex)                                :: bm_tax_max
5558---
5559>     REAL(r_std), DIMENSION(npts)                                :: bm_tax_max
5560128c128
5561<     REAL(r_std), DIMENSION(kjpindex)                                :: bm_pump
5562---
5563>     REAL(r_std), DIMENSION(npts)                                :: bm_pump
5564143c143,148
5565<     IF ( firstcall_npp ) THEN
5566---
5567>     IF ( firstcall ) THEN
5568>
5569>        ! 1.1.1 soil levels
5570>
5571>        z_soil(0) = zero
5572>        z_soil(1:nbdl) = diaglev(1:nbdl)
5573152,153c157,158
5574<        firstcall_npp = .FALSE.
5575<        RETURN
5576---
5577>        firstcall = .FALSE.
5578>
5579163c168
5580<     npp_daily(:,:) = zero
5581---
5582>     npp(:,:) = zero
5583182c187
5584<                t_root(:,j) + tsoil_daily(:,l) * rpc(:) * &
5585---
5586>                t_root(:,j) + tsoil(:,l) * rpc(:) * &
5587193c198
5588<     bm_alloc_tot(:,:) = gpp(:,:) * dt_days
5589---
5590>     bm_alloc_tot(:,:) = gpp(:,:) * dt
5591207,209c212,214
5592<        t_maint(:,ileaf) = t2m_daily(:)
5593<        t_maint(:,isapabove) = t2m_daily(:)
5594<        t_maint(:,ifruit) = t2m_daily(:)
5595---
5596>        t_maint(:,ileaf) = t2m(:)
5597>        t_maint(:,isapabove) = t2m(:)
5598>        t_maint(:,ifruit) = t2m(:)
5599219c224
5600<        t_maint(:,iheartabove) = t2m_daily(:)
5601---
5602>        t_maint(:,iheartabove) = t2m(:)
5603224c229
5604<           t_maint(:,icarbres) = t2m_daily(:)
5605---
5606>           t_maint(:,icarbres) = t2m(:)
5607284c289
5608<        DO i = 1, kjpindex
5609---
5610>        DO i = 1, npts
5611287c292
5612<                ( ( resp_maint(i,j) * dt_days ) .LT. bm_tax_max(i) ) ) THEN
5613---
5614>                ( ( resp_maint(i,j) * dt ) .LT. bm_tax_max(i) ) ) THEN
5615289c294
5616<              bm_alloc_tot(i,j) = bm_alloc_tot(i,j) - resp_maint(i,j) * dt_days
5617---
5618>              bm_alloc_tot(i,j) = bm_alloc_tot(i,j) - resp_maint(i,j) * dt
5619298c303
5620<              bm_pump(i) = resp_maint(i,j) * dt_days - bm_tax_max(i)
5621---
5622>              bm_pump(i) = resp_maint(i,j) * dt - bm_tax_max(i)
5623332c337
5624<        resp_growth_part(:,:) = frac_growthresp * bm_alloc(:,j,:) / dt_days
5625---
5626>        resp_growth_part(:,:) = frac_growthresp * bm_alloc(:,j,:) / dt
5627377c382
5628<              resp_maint(:,j) = resp_maint(:,j) - bm_create(:,j) / dt_days
5629---
5630>              resp_maint(:,j) = resp_maint(:,j) - bm_create(:,j) / dt
5631390c395
5632<        npp_daily(:,j) = gpp(:,j) - resp_growth(:,j) - resp_maint(:,j)
5633---
5634>        npp(:,j) = gpp(:,j) - resp_growth(:,j) - resp_maint(:,j)
5635455c460
5636<        age(:,:) = age(:,:) + dt_days/one_year
5637---
5638>        age(:,:) = age(:,:) + dt/one_year
5639498c503
5640<          bm_alloc(:,:,ileaf), kjpindex*nvm, horipft_index)
5641---
5642>          bm_alloc(:,:,ileaf), npts*nvm, horipft_index)
5643500c505
5644<          bm_alloc(:,:,isapabove), kjpindex*nvm, horipft_index)
5645---
5646>          bm_alloc(:,:,isapabove), npts*nvm, horipft_index)
5647502c507
5648<          bm_alloc(:,:,isapbelow), kjpindex*nvm, horipft_index)
5649---
5650>          bm_alloc(:,:,isapbelow), npts*nvm, horipft_index)
5651504c509
5652<          bm_alloc(:,:,iroot), kjpindex*nvm, horipft_index)
5653---
5654>          bm_alloc(:,:,iroot), npts*nvm, horipft_index)
5655506c511
5656<          bm_alloc(:,:,ifruit), kjpindex*nvm, horipft_index)
5657---
5658>          bm_alloc(:,:,ifruit), npts*nvm, horipft_index)
5659508c513
5660<          bm_alloc(:,:,icarbres), kjpindex*nvm, horipft_index)
5661---
5662>          bm_alloc(:,:,icarbres), npts*nvm, horipft_index)
5663512c517
5664<   END SUBROUTINE npp_calc_main
5665---
5666>   END SUBROUTINE npp_calc
5667diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/stomate_phenology.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/stomate_phenology.f90
566820c20
5669<   PUBLIC phenology_main,phenology_clear
5670---
5671>   PUBLIC phenology,phenology_clear
567223c23
5673<   LOGICAL, SAVE                                              :: firstcall_phenology = .TRUE.
5674---
5675>   LOGICAL, SAVE                                              :: firstcall = .TRUE.
567629,31d28
5677<   REAL(r_std), PARAMETER                                   :: moiavail_always_tree = un
5678<   REAL(r_std), PARAMETER                                   :: moiavail_always_grass = 0.6
5679<
568033,34d29
5681< ! List of subroutines for initialization :
5682< !- phenology_clear
568337c32
5684<     firstcall_phenology=.TRUE.
5685---
5686>     firstcall=.TRUE.
568744c39
5688<   SUBROUTINE phenology_main (kjpindex, dt_days, PFTpresent, &
5689---
5690>   SUBROUTINE phenology (npts, dt, PFTpresent, &
569152c47
5692<        when_growthinit, co2_to_bm_dgvm, lai)
5693---
5694>        when_growthinit, co2_to_bm, lai)
569561c56
5696<     INTEGER(i_std), INTENT(in)                                        :: kjpindex
5697---
5698>     INTEGER(i_std), INTENT(in)                                        :: npts
569963c58
5700<     REAL(r_std), INTENT(in)                                     :: dt_days
5701---
5702>     REAL(r_std), INTENT(in)                                     :: dt
570365c60
5704<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(in)                  :: PFTpresent
5705---
5706>     LOGICAL, DIMENSION(npts,nvm), INTENT(in)                  :: PFTpresent
570767c62
5708<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: veget_max
5709---
5710>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: veget_max
571169c64
5712<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                    :: tlong_ref
5713---
5714>     REAL(r_std), DIMENSION(npts), INTENT(in)                    :: tlong_ref
571571c66
5716<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                    :: t2m_month
5717---
5718>     REAL(r_std), DIMENSION(npts), INTENT(in)                    :: t2m_month
571973c68
5720<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                    :: t2m_week
5721---
5722>     REAL(r_std), DIMENSION(npts), INTENT(in)                    :: t2m_week
572375c70
5724<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: gpp
5725---
5726>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: gpp
572777c72
5728<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: maxmoiavail_lastyear
5729---
5730>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: maxmoiavail_lastyear
573179c74
5732<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: minmoiavail_lastyear
5733---
5734>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: minmoiavail_lastyear
573581c76
5736<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: moiavail_month
5737---
5738>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: moiavail_month
573983c78
5740<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: moiavail_week
5741---
5742>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: moiavail_week
574385c80
5744<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: gdd_m5_dormance
5745---
5746>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: gdd_m5_dormance
574787c82
5748<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)               :: gdd_midwinter
5749---
5750>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)               :: gdd_midwinter
575189c84
5752<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: ncd_dormance
5753---
5754>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: ncd_dormance
575591c86
5756<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: ngd_minus5
5757---
5758>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: ngd_minus5
575993c88
5760<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(in)                  :: senescence
5761---
5762>     LOGICAL, DIMENSION(npts,nvm), INTENT(in)                  :: senescence
576395c90
5764<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: time_lowgpp
5765---
5766>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: time_lowgpp
576797c92
5768<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: time_hum_min
5769---
5770>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: time_hum_min
5771102c97
5772<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)     :: biomass
5773---
5774>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)     :: biomass
5775104c99
5776<     REAL(r_std), DIMENSION(kjpindex,nvm,nleafages), INTENT(inout)  :: leaf_frac
5777---
5778>     REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)  :: leaf_frac
5779106c101
5780<     REAL(r_std), DIMENSION(kjpindex,nvm,nleafages), INTENT(inout)  :: leaf_age
5781---
5782>     REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)  :: leaf_age
5783108c103
5784<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)            :: when_growthinit
5785---
5786>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: when_growthinit
5787111c106
5788<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)                 :: co2_to_bm_dgvm
5789---
5790>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                 :: co2_to_bm
5791116c111
5792<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)              :: lai
5793---
5794>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)              :: lai
5795125c120
5796<     LOGICAL, DIMENSION(kjpindex,nvm)                              :: allow_initpheno
5797---
5798>     LOGICAL, DIMENSION(npts,nvm)                              :: allow_initpheno
5799127c122
5800<     REAL(r_std), DIMENSION(kjpindex)                                :: bm_wanted
5801---
5802>     REAL(r_std), DIMENSION(npts)                                :: bm_wanted
5803129c124
5804<     REAL(r_std), DIMENSION(kjpindex)                                :: bm_use
5805---
5806>     REAL(r_std), DIMENSION(npts)                                :: bm_use
5807131c126
5808<     REAL(r_std), DIMENSION(kjpindex)                                :: lm_min
5809---
5810>     REAL(r_std), DIMENSION(npts)                                :: lm_min
5811133c128
5812<     LOGICAL(r_std), DIMENSION(kjpindex)                             :: age_reset
5813---
5814>     LOGICAL(r_std), DIMENSION(npts)                             :: age_reset
5815137c132
5816<     LOGICAL, DIMENSION(kjpindex,nvm)                              :: begin_leaves
5817---
5818>     LOGICAL, DIMENSION(npts,nvm)                              :: begin_leaves
5819139c134
5820<     REAL(r_std), DIMENSION(kjpindex,nvm)                          :: histvar
5821---
5822>     REAL(r_std), DIMENSION(npts,nvm)                          :: histvar
5823149c144
5824<     IF ( firstcall_phenology ) THEN
5825---
5826>     IF ( firstcall ) THEN
5827159c154
5828<        firstcall_phenology = .FALSE.
5829---
5830>        firstcall = .FALSE.
5831161d155
5832<        RETURN
5833191c185
5834<     CALL histwrite (hist_id_stomate, 'ALLOW_INITPHENO', itime, histvar, kjpindex*nvm, horipft_index)
5835---
5836>     CALL histwrite (hist_id_stomate, 'ALLOW_INITPHENO', itime, histvar, npts*nvm, horipft_index)
5837198c192
5838<     when_growthinit(:,:) = when_growthinit(:,:) + dt_days
5839---
5840>     when_growthinit(:,:) = when_growthinit(:,:) + dt
5841215c209
5842<           CALL pheno_hum (kjpindex, j, PFTpresent, allow_initpheno, &
5843---
5844>           CALL pheno_hum (npts, j, PFTpresent, allow_initpheno, &
5845222c216
5846<           CALL pheno_moi (kjpindex, j, PFTpresent, allow_initpheno, &
5847---
5848>           CALL pheno_moi (npts, j, PFTpresent, allow_initpheno, &
5849230c224
5850<           CALL pheno_ncdgdd (kjpindex, j, PFTpresent, allow_initpheno, &
5851---
5852>           CALL pheno_ncdgdd (npts, j, PFTpresent, allow_initpheno, &
5853236c230
5854<           CALL pheno_ngd (kjpindex, j, PFTpresent, allow_initpheno, ngd_minus5, &
5855---
5856>           CALL pheno_ngd (npts, j, PFTpresent, allow_initpheno, ngd_minus5, &
5857241c235
5858<           CALL pheno_humgdd (kjpindex, j, PFTpresent, allow_initpheno, gdd_m5_dormance, &
5859---
5860>           CALL pheno_humgdd (npts, j, PFTpresent, allow_initpheno, gdd_m5_dormance, &
5861249c243
5862<           CALL pheno_moigdd (kjpindex, j, PFTpresent, allow_initpheno, gdd_m5_dormance, &
5863---
5864>           CALL pheno_moigdd (npts, j, PFTpresent, allow_initpheno, gdd_m5_dormance, &
5865275c269
5866<     CALL histwrite (hist_id_stomate, 'BEGIN_LEAVES', itime, histvar, kjpindex*nvm, horipft_index)
5867---
5868>     CALL histwrite (hist_id_stomate, 'BEGIN_LEAVES', itime, histvar, npts*nvm, horipft_index)
5869286c280
5870<        DO i = 1, kjpindex
5871---
5872>        DO i = 1, npts
5873307c301
5874<                    co2_to_bm_dgvm(i,j) = co2_to_bm_dgvm(i,j) + ( bm_wanted(i) - biomass(i,j,icarbres) ) / dt_days
5875---
5876>                    co2_to_bm(i,j) = co2_to_bm(i,j) + ( bm_wanted(i) - biomass(i,j,icarbres) ) / dt
5877377c371
5878<   END SUBROUTINE phenology_main
5879---
5880>   END SUBROUTINE phenology
5881386c380
5882<   SUBROUTINE pheno_hum (kjpindex, j, PFTpresent, allow_initpheno, &
5883---
5884>   SUBROUTINE pheno_hum (npts, j, PFTpresent, allow_initpheno, &
5885398c392
5886<     INTEGER(i_std), INTENT(in)                                     :: kjpindex
5887---
5888>     INTEGER(i_std), INTENT(in)                                     :: npts
5889402c396
5890<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(in)               :: PFTpresent
5891---
5892>     LOGICAL, DIMENSION(npts,nvm), INTENT(in)               :: PFTpresent
5893404c398
5894<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(in)               :: allow_initpheno
5895---
5896>     LOGICAL, DIMENSION(npts,nvm), INTENT(in)               :: allow_initpheno
5897406c400
5898<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)            :: moiavail_month
5899---
5900>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: moiavail_month
5901408c402
5902<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)            :: moiavail_week
5903---
5904>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: moiavail_week
5905410c404
5906<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)            :: maxmoiavail_lastyear
5907---
5908>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: maxmoiavail_lastyear
5909412c406
5910<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)            :: minmoiavail_lastyear
5911---
5912>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: minmoiavail_lastyear
5913417c411
5914<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(inout)              :: begin_leaves
5915---
5916>     LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves
5917421a416,417
5918>     REAL(r_std), PARAMETER                                   :: moiavail_always_tree = un
5919>     REAL(r_std), PARAMETER                                   :: moiavail_always_grass = 0.6
5920424c420
5921<     REAL(r_std), DIMENSION(kjpindex)                             :: availability_crit
5922---
5923>     REAL(r_std), DIMENSION(npts)                             :: availability_crit
5924484c480
5925<     DO i = 1, kjpindex
5926---
5927>     DO i = 1, npts
5928519c515
5929<   SUBROUTINE pheno_moi (kjpindex, j, PFTpresent, allow_initpheno, &
5930---
5931>   SUBROUTINE pheno_moi (npts, j, PFTpresent, allow_initpheno, &
5932531c527
5933<     INTEGER(i_std), INTENT(in)                                     :: kjpindex
5934---
5935>     INTEGER(i_std), INTENT(in)                                     :: npts
5936535c531
5937<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(in)               :: PFTpresent
5938---
5939>     LOGICAL, DIMENSION(npts,nvm), INTENT(in)               :: PFTpresent
5940537c533
5941<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(in)               :: allow_initpheno
5942---
5943>     LOGICAL, DIMENSION(npts,nvm), INTENT(in)               :: allow_initpheno
5944539c535
5945<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)            :: time_hum_min
5946---
5947>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: time_hum_min
5948541c537
5949<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)            :: moiavail_month
5950---
5951>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: moiavail_month
5952543c539
5953<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)            :: moiavail_week
5954---
5955>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: moiavail_week
5956548c544
5957<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(inout)              :: begin_leaves
5958---
5959>     LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves
5960616c612
5961<     DO i = 1, kjpindex
5962---
5963>     DO i = 1, npts
5964647c643
5965<   SUBROUTINE pheno_humgdd (kjpindex, j, PFTpresent, allow_initpheno, gdd, &
5966---
5967>   SUBROUTINE pheno_humgdd (npts, j, PFTpresent, allow_initpheno, gdd, &
5968660c656
5969<     INTEGER(i_std), INTENT(in)                                     :: kjpindex
5970---
5971>     INTEGER(i_std), INTENT(in)                                     :: npts
5972664c660
5973<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(in)               :: PFTpresent
5974---
5975>     LOGICAL, DIMENSION(npts,nvm), INTENT(in)               :: PFTpresent
5976666c662
5977<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(in)               :: allow_initpheno
5978---
5979>     LOGICAL, DIMENSION(npts,nvm), INTENT(in)               :: allow_initpheno
5980668c664
5981<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)            :: gdd
5982---
5983>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: gdd
5984670c666
5985<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)            :: maxmoiavail_lastyear
5986---
5987>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: maxmoiavail_lastyear
5988672c668
5989<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)            :: minmoiavail_lastyear
5990---
5991>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: minmoiavail_lastyear
5992674c670
5993<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                 :: tlong_ref
5994---
5995>     REAL(r_std), DIMENSION(npts), INTENT(in)                 :: tlong_ref
5996676c672
5997<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                 :: t2m_month
5998---
5999>     REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_month
6000678c674
6001<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                 :: t2m_week
6002---
6003>     REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_week
6004680c676
6005<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)            :: moiavail_week
6006---
6007>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: moiavail_week
6008682c678
6009<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)            :: moiavail_month
6010---
6011>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: moiavail_month
6012687c683
6013<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(inout)              :: begin_leaves
6014---
6015>     LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves
6016699c695
6017<     REAL(r_std), DIMENSION(kjpindex)                             :: moiavail_crit
6018---
6019>     REAL(r_std), DIMENSION(npts)                             :: moiavail_crit
6020701c697
6021<     REAL(r_std), DIMENSION(kjpindex)                             :: tl
6022---
6023>     REAL(r_std), DIMENSION(npts)                             :: tl
6024703c699
6025<     REAL(r_std), DIMENSION(kjpindex)                             :: gdd_crit
6026---
6027>     REAL(r_std), DIMENSION(npts)                             :: gdd_crit
6028774c770
6029<     DO i = 1, kjpindex
6030---
6031>     DO i = 1, npts
6032813c809
6033<   SUBROUTINE pheno_moigdd (kjpindex, j, PFTpresent, allow_initpheno, gdd, &
6034---
6035>   SUBROUTINE pheno_moigdd (npts, j, PFTpresent, allow_initpheno, gdd, &
6036826c822
6037<     INTEGER(i_std), INTENT(in)                                     :: kjpindex
6038---
6039>     INTEGER(i_std), INTENT(in)                                     :: npts
6040830c826
6041<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(in)               :: PFTpresent
6042---
6043>     LOGICAL, DIMENSION(npts,nvm), INTENT(in)               :: PFTpresent
6044832c828
6045<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(in)               :: allow_initpheno
6046---
6047>     LOGICAL, DIMENSION(npts,nvm), INTENT(in)               :: allow_initpheno
6048834c830
6049<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)            :: gdd
6050---
6051>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: gdd
6052836c832
6053<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)            :: time_hum_min
6054---
6055>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: time_hum_min
6056838c834
6057<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                 :: tlong_ref
6058---
6059>     REAL(r_std), DIMENSION(npts), INTENT(in)                 :: tlong_ref
6060840c836
6061<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                 :: t2m_month
6062---
6063>     REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_month
6064842c838
6065<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                 :: t2m_week
6066---
6067>     REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_week
6068844c840
6069<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)            :: moiavail_week
6070---
6071>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: moiavail_week
6072846c842
6073<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)            :: moiavail_month
6074---
6075>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: moiavail_month
6076851c847
6077<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(inout)              :: begin_leaves
6078---
6079>     LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves
6080863c859
6081<     REAL(r_std), DIMENSION(kjpindex)                             :: tl
6082---
6083>     REAL(r_std), DIMENSION(npts)                             :: tl
6084865c861
6085<     REAL(r_std), DIMENSION(kjpindex)                             :: gdd_crit
6086---
6087>     REAL(r_std), DIMENSION(npts)                             :: gdd_crit
6088936c932
6089<     DO i = 1, kjpindex
6090---
6091>     DO i = 1, npts
6092973c969
6093<   SUBROUTINE pheno_ncdgdd (kjpindex, j, PFTpresent, allow_initpheno, &
6094---
6095>   SUBROUTINE pheno_ncdgdd (npts, j, PFTpresent, allow_initpheno, &
6096984c980
6097<     INTEGER(i_std), INTENT(in)                                     :: kjpindex
6098---
6099>     INTEGER(i_std), INTENT(in)                                     :: npts
6100988c984
6101<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(in)               :: PFTpresent
6102---
6103>     LOGICAL, DIMENSION(npts,nvm), INTENT(in)               :: PFTpresent
6104990c986
6105<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(in)               :: allow_initpheno
6106---
6107>     LOGICAL, DIMENSION(npts,nvm), INTENT(in)               :: allow_initpheno
6108992c988
6109<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)            :: ncd_dormance
6110---
6111>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: ncd_dormance
6112994c990
6113<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)            :: gdd_midwinter
6114---
6115>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: gdd_midwinter
6116996c992
6117<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                 :: t2m_month
6118---
6119>     REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_month
6120998c994
6121<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                 :: t2m_week
6122---
6123>     REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_week
61241003c999
6125<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(inout)              :: begin_leaves
6126---
6127>     LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves
61281042c1038
6129<     DO i = 1, kjpindex
6130---
6131>     DO i = 1, npts
61321074c1070
6133<   SUBROUTINE pheno_ngd (kjpindex, j, PFTpresent, allow_initpheno, ngd, &
6134---
6135>   SUBROUTINE pheno_ngd (npts, j, PFTpresent, allow_initpheno, ngd, &
61361084c1080
6137<     INTEGER(i_std), INTENT(in)                                     :: kjpindex
6138---
6139>     INTEGER(i_std), INTENT(in)                                     :: npts
61401088c1084
6141<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(in)               :: PFTpresent
6142---
6143>     LOGICAL, DIMENSION(npts,nvm), INTENT(in)               :: PFTpresent
61441090c1086
6145<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(in)               :: allow_initpheno
6146---
6147>     LOGICAL, DIMENSION(npts,nvm), INTENT(in)               :: allow_initpheno
61481092c1088
6149<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)            :: ngd
6150---
6151>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: ngd
61521094c1090
6153<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                 :: t2m_month
6154---
6155>     REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_month
61561096c1092
6157<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                 :: t2m_week
6158---
6159>     REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_week
61601101c1097
6161<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(inout)              :: begin_leaves
6162---
6163>     LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves
61641138c1134
6165<     DO i = 1, kjpindex
6166---
6167>     DO i = 1, npts
6168diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/stomate_prescribe.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/stomate_prescribe.f90
616929c29
6170<     LOGICAL, SAVE                                              :: firstcall_prescribe = .TRUE.
6171---
6172>     LOGICAL, SAVE                                              :: firstcall = .TRUE.
617332,35d31
6174< ! List of subroutines for initialization :
6175< !- prescribe_clear
6176<
6177< !???- prescribe => utilité de l'appel de prescribe dans stomate_init_main ??
617838c34
6179<     firstcall_prescribe=.TRUE.
6180---
6181>     firstcall=.TRUE.
618241c37
6183<  SUBROUTINE prescribe (kjpindex, &
6184---
6185>  SUBROUTINE prescribe (npts, &
618652c48
6187<     INTEGER(i_std), INTENT(in)                                        :: kjpindex
6188---
6189>     INTEGER(i_std), INTENT(in)                                        :: npts
619057c53
6191<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: veget_max
6192---
6193>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: veget_max
619459c55
6195<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(inout)               :: PFTpresent
6196---
6197>     LOGICAL, DIMENSION(npts,nvm), INTENT(inout)               :: PFTpresent
619861c57
6199<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)            :: everywhere
6200---
6201>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: everywhere
620263c59
6203<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)            :: when_growthinit
6204---
6205>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: when_growthinit
620665c61
6207<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)     :: biomass
6208---
6209>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)     :: biomass
621067c63
6211<     REAL(r_std), DIMENSION(kjpindex,nvm,nleafages), INTENT(inout)  :: leaf_frac
6212---
6213>     REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)  :: leaf_frac
621469c65
6215<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)            :: ind
6216---
6217>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: ind
621871c67
6219<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)            :: cn_ind
6220---
6221>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: cn_ind
622281c77
6223<     REAL(r_std), DIMENSION(kjpindex)                                :: dia
6224---
6225>     REAL(r_std), DIMENSION(npts)                                :: dia
622683c79
6227<     REAL(r_std), DIMENSION(kjpindex)                                :: woodmass
6228---
6229>     REAL(r_std), DIMENSION(npts)                                :: woodmass
623085c81
6231<     REAL(r_std), DIMENSION(kjpindex)                                :: woodmass_ind
6232---
6233>     REAL(r_std), DIMENSION(npts)                                :: woodmass_ind
6234111c107
6235<           DO i = 1, kjpindex
6236---
6237>           DO i = 1, npts
6238210c206
6239<     IF ( firstcall_prescribe ) THEN
6240---
6241>     IF ( firstcall ) THEN
6242221c217
6243<         DO i = 1, kjpindex
6244---
6245>         DO i = 1, npts
6246293c289
6247<       firstcall_prescribe = .FALSE.
6248---
6249>       firstcall = .FALSE.
6250diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/stomate_resp.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/stomate_resp.f90
625116c16
6252<   PUBLIC maint_respiration_main,maint_respiration_clear
6253---
6254>   PUBLIC maint_respiration,maint_respiration_clear
625519c19
6256<   LOGICAL, SAVE                                              :: firstcall_resp = .TRUE.
6257---
6258>   LOGICAL, SAVE                                              :: firstcall = .TRUE.
625922,23d21
6260< ! List of subroutines for initialization :
6261< !- maint_respiration_clear
626226c24
6263<     firstcall_resp=.TRUE.
6264---
6265>     firstcall=.TRUE.
626629c27
6267<   SUBROUTINE maint_respiration_main ( kjpindex,dt_days,lai, t2m_daily,tlong_ref,stempdiag,height,veget_max,&
6268---
6269>   SUBROUTINE maint_respiration ( npts,dt,lai, t2m,tlong_ref,stempdiag,height,veget_max,&
627039c37
6271<     INTEGER(i_std), INTENT(in)                                        :: kjpindex
6272---
6273>     INTEGER(i_std), INTENT(in)                                        :: npts
627441c39
6275<     REAL(r_std), INTENT(in)                                     :: dt_days
6276---
6277>     REAL(r_std), INTENT(in)                                     :: dt
627843c41
6279<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                    :: t2m_daily
6280---
6281>     REAL(r_std), DIMENSION(npts), INTENT(in)                    :: t2m
628245c43
6283<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                    :: tlong_ref
6284---
6285>     REAL(r_std), DIMENSION(npts), INTENT(in)                    :: tlong_ref
628647c45
6287<     REAL(r_std),DIMENSION (kjpindex,nbdl), INTENT (in)              :: stempdiag
6288---
6289>     REAL(r_std),DIMENSION (npts,nbdl), INTENT (in)              :: stempdiag
629049c47
6291<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: height
6292---
6293>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: height
629451c49
6295<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: veget_max
6296---
6297>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: veget_max
629853c51
6299<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: rprof
6300---
6301>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: rprof
630255c53
6303<     REAL(r_std),DIMENSION(kjpindex,nvm,nparts),INTENT(in)          :: biomass
6304---
6305>     REAL(r_std),DIMENSION(npts,nvm,nparts),INTENT(in)          :: biomass
630662c60
6307<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(out)             :: resp_maint_part_radia
6308---
6309>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(out)             :: resp_maint_part_radia
631066c64,66
6311<     REAL(r_std), DIMENSION(kjpindex,nvm)                           :: lai
6312---
6313>     REAL(r_std), DIMENSION(npts,nvm)                           :: lai
6314>     ! soil levels (m)
6315>     REAL(r_std), SAVE, DIMENSION(0:nbdl)                        :: z_soil
631668c68
6317<     REAL(r_std), DIMENSION(kjpindex,nvm)                           :: t_root
6318---
6319>     REAL(r_std), DIMENSION(npts,nvm)                           :: t_root
632070c70
6321<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts)                    :: coeff_maint
6322---
6323>     REAL(r_std), DIMENSION(npts,nvm,nparts)                    :: coeff_maint
632472c72
6325<     REAL(r_std), DIMENSION(kjpindex,nparts)                         :: t_maint
6326---
6327>     REAL(r_std), DIMENSION(npts,nparts)                         :: t_maint
632874c74
6329<     REAL(r_std), DIMENSION(kjpindex)                                :: rpc
6330---
6331>     REAL(r_std), DIMENSION(npts)                                :: rpc
633276c76
6333<     REAL(r_std), DIMENSION(kjpindex,nparts)                         :: t_maint_radia
6334---
6335>     REAL(r_std), DIMENSION(npts,nparts)                         :: t_maint_radia
633678c78
6337<     REAL(r_std), DIMENSION(kjpindex)                                :: tl
6338---
6339>     REAL(r_std), DIMENSION(npts)                                :: tl
634080c80
6341<     REAL(r_std), DIMENSION(kjpindex)                                :: slope
6342---
6343>     REAL(r_std), DIMENSION(npts)                                :: slope
634492c92
6345<     IF ( firstcall_resp ) THEN
6346---
6347>     IF ( firstcall ) THEN
634895a96,98
6349>        z_soil(0) = zero
6350>        z_soil(1:nbdl) = diaglev(1:nbdl)
6351>
6352100,101c103,104
6353<        firstcall_resp = .FALSE.
6354<        RETURN
6355---
6356>        firstcall = .FALSE.
6357>
6358138,140c141,143
6359<        t_maint_radia(:,ileaf) = t2m_daily(:)
6360<        t_maint_radia(:,isapabove) = t2m_daily(:)
6361<        t_maint_radia(:,ifruit) = t2m_daily(:)
6362---
6363>        t_maint_radia(:,ileaf) = t2m(:)
6364>        t_maint_radia(:,isapabove) = t2m(:)
6365>        t_maint_radia(:,ifruit) = t2m(:)
6366150c153
6367<        t_maint_radia(:,iheartabove) = t2m_daily(:)
6368---
6369>        t_maint_radia(:,iheartabove) = t2m(:)
6370155c158
6371<           t_maint_radia(:,icarbres) = t2m_daily(:)
6372---
6373>           t_maint_radia(:,icarbres) = t2m(:)
6374171c174
6375<                MAX( (coeff_maint_zero(j,k)*dt_days/one_day) * &
6376---
6377>                MAX( (coeff_maint_zero(j,k)*dt/one_day) * &
6378203c206
6379<              DO i = 1, kjpindex
6380---
6381>              DO i = 1, npts
6382237c240
6383<   END SUBROUTINE maint_respiration_main
6384---
6385>   END SUBROUTINE maint_respiration
6386diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/stomate_season.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/stomate_season.f90
638721c21
6388<   PUBLIC season_main,season_clear
6389---
6390>   PUBLIC season,season_clear
639124c24
6392<   LOGICAL, SAVE                                          :: firstcall_season = .TRUE.
6393---
6394>   LOGICAL, SAVE                                          :: firstcall = .TRUE.
639527,28c27
6396< ! List of subroutines for initialization :
6397< !- season_clear
6398---
6399>
640031c30
6401<     firstcall_season=.TRUE.
6402---
6403>     firstcall=.TRUE.
640434c33
6405<   SUBROUTINE season_main (kjpindex, dt_days, EndOfYear, veget, veget_max, &
6406---
6407>   SUBROUTINE season (npts, dt, EndOfYear, veget, veget_max, &
640857c56
6409<     INTEGER(i_std), INTENT(in)                                    :: kjpindex
6410---
6411>     INTEGER(i_std), INTENT(in)                                    :: npts
641259c58
6413<     REAL(r_std), INTENT(in)                                 :: dt_days
6414---
6415>     REAL(r_std), INTENT(in)                                 :: dt
641663c62
6417<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)           :: veget
6418---
6419>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)           :: veget
642066c65
6421<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)           :: veget_max
6422---
6423>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)           :: veget_max
642468c67
6425<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)           :: moiavail_daily
6426---
6427>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)           :: moiavail_daily
642870c69
6429<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                :: t2m_daily
6430---
6431>     REAL(r_std), DIMENSION(npts), INTENT(in)                :: t2m_daily
643272c71
6433<     REAL(r_std), DIMENSION(kjpindex,nbdl), INTENT(in)           :: tsoil_daily
6434---
6435>     REAL(r_std), DIMENSION(npts,nbdl), INTENT(in)           :: tsoil_daily
643674c73
6437<     REAL(r_std), DIMENSION(kjpindex,nbdl), INTENT(in)           :: soilhum_daily
6438---
6439>     REAL(r_std), DIMENSION(npts,nbdl), INTENT(in)           :: soilhum_daily
644076c75
6441<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                :: precip_daily
6442---
6443>     REAL(r_std), DIMENSION(npts), INTENT(in)                :: precip_daily
644478c77
6445<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)           :: npp_daily
6446---
6447>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)           :: npp_daily
644880c79
6449<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(in)    :: biomass
6450---
6451>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(in)    :: biomass
645282c81
6453<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(in)    :: turnover_daily
6454---
6455>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(in)    :: turnover_daily
645684c83
6457<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)           :: gpp_daily
6458---
6459>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)           :: gpp_daily
646086c85
6461<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)           :: when_growthinit
6462---
6463>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)           :: when_growthinit
646491c90
6465<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)        :: maxmoiavail_lastyear
6466---
6467>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: maxmoiavail_lastyear
646893c92
6469<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)        :: maxmoiavail_thisyear
6470---
6471>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: maxmoiavail_thisyear
647295c94
6473<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)        :: minmoiavail_lastyear
6474---
6475>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: minmoiavail_lastyear
647697c96
6477<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)        :: minmoiavail_thisyear
6478---
6479>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: minmoiavail_thisyear
648099c98
6481<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)        :: maxgppweek_lastyear
6482---
6483>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: maxgppweek_lastyear
6484101c100
6485<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)        :: maxgppweek_thisyear
6486---
6487>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: maxgppweek_thisyear
6488103c102
6489<     REAL(r_std), DIMENSION(kjpindex), INTENT(inout)             :: gdd0_lastyear
6490---
6491>     REAL(r_std), DIMENSION(npts), INTENT(inout)             :: gdd0_lastyear
6492105c104
6493<     REAL(r_std), DIMENSION(kjpindex), INTENT(inout)             :: gdd0_thisyear
6494---
6495>     REAL(r_std), DIMENSION(npts), INTENT(inout)             :: gdd0_thisyear
6496107c106
6497<     REAL(r_std), DIMENSION(kjpindex), INTENT(inout)             :: precip_lastyear
6498---
6499>     REAL(r_std), DIMENSION(npts), INTENT(inout)             :: precip_lastyear
6500109c108
6501<     REAL(r_std), DIMENSION(kjpindex), INTENT(inout)             :: precip_thisyear
6502---
6503>     REAL(r_std), DIMENSION(npts), INTENT(inout)             :: precip_thisyear
6504111c110
6505<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)        :: lm_lastyearmax
6506---
6507>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: lm_lastyearmax
6508113c112
6509<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)        :: lm_thisyearmax
6510---
6511>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: lm_thisyearmax
6512115c114
6513<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)        :: maxfpc_lastyear
6514---
6515>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: maxfpc_lastyear
6516117c116
6517<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)        :: maxfpc_thisyear
6518---
6519>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: maxfpc_thisyear
6520119c118
6521<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)        :: moiavail_month
6522---
6523>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: moiavail_month
6524121c120
6525<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)        :: moiavail_week
6526---
6527>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: moiavail_week
6528123c122
6529<     REAL(r_std), DIMENSION(kjpindex), INTENT(inout)             :: t2m_longterm
6530---
6531>     REAL(r_std), DIMENSION(npts), INTENT(inout)             :: t2m_longterm
6532125c124
6533<     REAL(r_std), DIMENSION(kjpindex), INTENT(inout)             :: tlong_ref
6534---
6535>     REAL(r_std), DIMENSION(npts), INTENT(inout)             :: tlong_ref
6536127c126
6537<     REAL(r_std), DIMENSION(kjpindex), INTENT(inout)             :: t2m_month
6538---
6539>     REAL(r_std), DIMENSION(npts), INTENT(inout)             :: t2m_month
6540129c128
6541<     REAL(r_std), DIMENSION(kjpindex), INTENT(inout)             :: t2m_week
6542---
6543>     REAL(r_std), DIMENSION(npts), INTENT(inout)             :: t2m_week
6544131c130
6545<     REAL(r_std), DIMENSION(kjpindex,nbdl), INTENT(inout)        :: tsoil_month
6546---
6547>     REAL(r_std), DIMENSION(npts,nbdl), INTENT(inout)        :: tsoil_month
6548133c132
6549<     REAL(r_std), DIMENSION(kjpindex,nbdl), INTENT(inout)        :: soilhum_month
6550---
6551>     REAL(r_std), DIMENSION(npts,nbdl), INTENT(inout)        :: soilhum_month
6552135c134
6553<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)        :: npp_longterm
6554---
6555>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: npp_longterm
6556137c136
6557<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout) :: turnover_longterm
6558---
6559>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout) :: turnover_longterm
6560139c138
6561<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)        :: gpp_week
6562---
6563>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: gpp_week
6564141c140
6565<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)        :: gdd_m5_dormance
6566---
6567>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: gdd_m5_dormance
6568143c142
6569<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)        :: gdd_midwinter
6570---
6571>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: gdd_midwinter
6572145c144
6573<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)        :: ncd_dormance
6574---
6575>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: ncd_dormance
6576147c146
6577<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)        :: ngd_minus5
6578---
6579>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: ngd_minus5
6580149c148
6581<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)        :: time_lowgpp
6582---
6583>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: time_lowgpp
6584151c150
6585<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)        :: time_hum_min
6586---
6587>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: time_hum_min
6588153c152
6589<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)        :: hum_min_dormance
6590---
6591>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: hum_min_dormance
6592158c157
6593<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)          :: herbivores
6594---
6595>     REAL(r_std), DIMENSION(npts,nvm), INTENT(out)          :: herbivores
6596178c177
6597<     REAL(r_std), PARAMETER                                  :: leaf_frac_season=.33
6598---
6599>     REAL(r_std), PARAMETER                                  :: leaf_frac=.33
6600180c179
6601<     REAL(r_std), DIMENSION(kjpindex)                            :: sumfpc_nat
6602---
6603>     REAL(r_std), DIMENSION(npts)                            :: sumfpc_nat
6604182c181
6605<     REAL(r_std), DIMENSION(kjpindex)                            :: weighttot
6606---
6607>     REAL(r_std), DIMENSION(npts)                            :: weighttot
6608184c183
6609<     REAL(r_std), DIMENSION(kjpindex)                            :: nlflong_nat
6610---
6611>     REAL(r_std), DIMENSION(npts)                            :: nlflong_nat
6612186c185
6613<     REAL(r_std), DIMENSION(kjpindex)                            :: green_age
6614---
6615>     REAL(r_std), DIMENSION(npts)                            :: green_age
6616188c187
6617<     REAL(r_std), DIMENSION(kjpindex)                            :: consumption
6618---
6619>     REAL(r_std), DIMENSION(npts)                            :: consumption
6620190c189
6621<     REAL(r_std), DIMENSION(kjpindex)                            :: fracnat
6622---
6623>     REAL(r_std), DIMENSION(npts)                            :: fracnat
6624201c200
6625<     IF ( firstcall_season ) THEN
6626---
6627>     IF ( firstcall ) THEN
6628217c216
6629<           WRITE(numout,*) '   > for herbivores, suppose that ',leaf_frac_season*100., &
6630---
6631>           WRITE(numout,*) '   > for herbivores, suppose that ',leaf_frac*100., &
6632356,357c355,356
6633<        firstcall_season = .FALSE.
6634<        RETURN
6635---
6636>        firstcall = .FALSE.
6637>
6638368,369c367,368
6639<     moiavail_month = ( moiavail_month * ( pheno_crit%tau_hum_month - dt_days ) + &
6640<          moiavail_daily * dt_days ) / pheno_crit%tau_hum_month
6641---
6642>     moiavail_month = ( moiavail_month * ( pheno_crit%tau_hum_month - dt ) + &
6643>          moiavail_daily * dt ) / pheno_crit%tau_hum_month
6644381,382c380,381
6645<     moiavail_week = ( moiavail_week * ( pheno_crit%tau_hum_week - dt_days ) + &
6646<          moiavail_daily * dt_days ) / pheno_crit%tau_hum_week
6647---
6648>     moiavail_week = ( moiavail_week * ( pheno_crit%tau_hum_week - dt ) + &
6649>          moiavail_daily * dt ) / pheno_crit%tau_hum_week
6650398,399c397,398
6651<     t2m_longterm = ( t2m_longterm * ( pheno_crit%tau_longterm - dt_days ) + &
6652<          t2m_daily * dt_days ) / pheno_crit%tau_longterm
6653---
6654>     t2m_longterm = ( t2m_longterm * ( pheno_crit%tau_longterm - dt ) + &
6655>          t2m_daily * dt ) / pheno_crit%tau_longterm
6656406c405
6657<          t2m_longterm, kjpindex, hori_index)
6658---
6659>          t2m_longterm, npts, hori_index)
6660423,424c422,423
6661<     t2m_month = ( t2m_month * ( pheno_crit%tau_t2m_month - dt_days ) + &
6662<          t2m_daily * dt_days ) / pheno_crit%tau_t2m_month
6663---
6664>     t2m_month = ( t2m_month * ( pheno_crit%tau_t2m_month - dt ) + &
6665>          t2m_daily * dt ) / pheno_crit%tau_t2m_month
6666434,435c433,434
6667<     t2m_week = ( t2m_week * ( pheno_crit%tau_t2m_week - dt_days ) + &
6668<          t2m_daily * dt_days ) / pheno_crit%tau_t2m_week
6669---
6670>     t2m_week = ( t2m_week * ( pheno_crit%tau_t2m_week - dt ) + &
6671>          t2m_daily * dt ) / pheno_crit%tau_t2m_week
6672445,446c444,445
6673<     tsoil_month = ( tsoil_month * ( pheno_crit%tau_tsoil_month - dt_days ) + &
6674<          tsoil_daily(:,:) * dt_days ) / pheno_crit%tau_tsoil_month
6675---
6676>     tsoil_month = ( tsoil_month * ( pheno_crit%tau_tsoil_month - dt ) + &
6677>          tsoil_daily(:,:) * dt ) / pheno_crit%tau_tsoil_month
6678456,457c455,456
6679<     soilhum_month = ( soilhum_month * ( pheno_crit%tau_soilhum_month - dt_days ) + &
6680<          soilhum_daily * dt_days ) / pheno_crit%tau_soilhum_month
6681---
6682>     soilhum_month = ( soilhum_month * ( pheno_crit%tau_soilhum_month - dt ) + &
6683>          soilhum_daily * dt ) / pheno_crit%tau_soilhum_month
6684481c480
6685<           time_lowgpp(:,j) = time_lowgpp(:,j) + dt_days
6686---
6687>           time_lowgpp(:,j) = time_lowgpp(:,j) + dt
6688529c528
6689<                   dt_days * ( t2m_daily(:) - (ZeroCelsius-5.) )
6690---
6691>                   dt * ( t2m_daily(:) - (ZeroCelsius-5.) )
6692534c533
6693<                   ( pheno_crit%tau_gdd - dt_days ) / pheno_crit%tau_gdd
6694---
6695>                   ( pheno_crit%tau_gdd - dt ) / pheno_crit%tau_gdd
6696589c588
6697<                   dt_days * ( t2m_daily(:) - ( pheno_crit%ncdgdd_temp(j)+ZeroCelsius ) )
6698---
6699>                   dt * ( t2m_daily(:) - ( pheno_crit%ncdgdd_temp(j)+ZeroCelsius ) )
6700632c631
6701<              ncd_dormance(:,j) = MIN( ncd_dormance(:,j) + dt_days, ncd_max )
6702---
6703>              ncd_dormance(:,j) = MIN( ncd_dormance(:,j) + dt, ncd_max )
6704660c659
6705<           ngd_minus5(:,j) = ngd_minus5(:,j) + dt_days
6706---
6707>           ngd_minus5(:,j) = ngd_minus5(:,j) + dt
6708663c662
6709<        ngd_minus5(:,j) = ngd_minus5(:,j) * ( pheno_crit%tau_ngd - dt_days ) / pheno_crit%tau_ngd
6710---
6711>        ngd_minus5(:,j) = ngd_minus5(:,j) * ( pheno_crit%tau_ngd - dt ) / pheno_crit%tau_ngd
6712712c711
6713<              time_hum_min(:,j) = time_hum_min(:,j) + dt_days
6714---
6715>              time_hum_min(:,j) = time_hum_min(:,j) + dt
6716735,736c734,735
6717<     npp_longterm = ( npp_longterm * ( pheno_crit%tau_longterm - dt_days ) + &
6718<          (npp_daily*one_year) * dt_days                          ) / &
6719---
6720>     npp_longterm = ( npp_longterm * ( pheno_crit%tau_longterm - dt ) + &
6721>          (npp_daily*one_year) * dt                          ) / &
6722749,750c748,749
6723<     turnover_longterm = ( turnover_longterm * ( pheno_crit%tau_longterm - dt_days ) + &
6724<          (turnover_daily*one_year) * dt_days                          ) / &
6725---
6726>     turnover_longterm = ( turnover_longterm * ( pheno_crit%tau_longterm - dt ) + &
6727>          (turnover_daily*one_year) * dt                          ) / &
6728767,768c766,767
6729<        gpp_week = ( gpp_week * ( pheno_crit%tau_gpp_week - dt_days ) + &
6730<             gpp_daily * dt_days ) / pheno_crit%tau_gpp_week
6731---
6732>        gpp_week = ( gpp_week * ( pheno_crit%tau_gpp_week - dt ) + &
6733>             gpp_daily * dt ) / pheno_crit%tau_gpp_week
6734807c806
6735<        gdd0_thisyear = gdd0_thisyear + dt_days * ( t2m_daily - ZeroCelsius )
6736---
6737>        gdd0_thisyear = gdd0_thisyear + dt * ( t2m_daily - ZeroCelsius )
6738814c813
6739<     precip_thisyear = precip_thisyear + dt_days * precip_daily
6740---
6741>     precip_thisyear = precip_thisyear + dt * precip_daily
6742840,841c839,840
6743<                    maxfpc_lastyear(:,j) = ( maxfpc_lastyear(:,j) * ( one_year/leaflife_tab(j)- dt_days ) + &
6744<                         veget(:,j) / fracnat(:) * dt_days ) / (one_year/leaflife_tab(j))
6745---
6746>                    maxfpc_lastyear(:,j) = ( maxfpc_lastyear(:,j) * ( one_year/leaflife_tab(j)- dt ) + &
6747>                         veget(:,j) / fracnat(:) * dt ) / (one_year/leaflife_tab(j))
6748849,850c848,849
6749< !!$                lm_lastyearmax(:,j) = ( lm_lastyearmax(:,j) * ( one_year/leaflife_tab(j)- dt_days ) + &
6750< !!$                     biomass(:,j,ileaf) * dt_days ) / (one_year/leaflife_tab(j))
6751---
6752> !!$                lm_lastyearmax(:,j) = ( lm_lastyearmax(:,j) * ( one_year/leaflife_tab(j)- dt ) + &
6753> !!$                     biomass(:,j,ileaf) * dt ) / (one_year/leaflife_tab(j))
6754855,856c854,855
6755<                    lm_thisyearmax(:,j) = ( lm_thisyearmax(:,j) * ( one_year/leaflife_tab(j)- dt_days ) + &
6756<                         biomass(:,j,ileaf) * dt_days ) / (one_year/leaflife_tab(j))
6757---
6758>                    lm_thisyearmax(:,j) = ( lm_thisyearmax(:,j) * ( one_year/leaflife_tab(j)- dt ) + &
6759>                         biomass(:,j,ileaf) * dt ) / (one_year/leaflife_tab(j))
6760996c995
6761<           nlflong_nat(:) = nlflong_nat(:) + npp_longterm(:,j) * leaf_frac_season
6762---
6763>           nlflong_nat(:) = nlflong_nat(:) + npp_longterm(:,j) * leaf_frac
67641041c1040
6765<   END SUBROUTINE season_main
6766---
6767>   END SUBROUTINE season
6768diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/stomate_soilcarbon.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/stomate_soilcarbon.f90
676921c21
6770<   PUBLIC soilcarbon_main,soilcarbon_clear
6771---
6772>   PUBLIC soilcarbon,soilcarbon_clear
677324c24
6774<   LOGICAL, SAVE                                                     :: firstcall_soilcarbon = .TRUE.
6775---
6776>   LOGICAL, SAVE                                                     :: firstcall = .TRUE.
677727,28c27
6778< ! List of subroutines for initialization :
6779< !- soilcarbon_clear
6780---
6781>
678231c30
6783<     firstcall_soilcarbon=.TRUE.
6784---
6785>     firstcall=.TRUE.
678634c33
6787<   SUBROUTINE soilcarbon_main (kjpindex, dt_days, clayfraction, &
6788---
6789>   SUBROUTINE soilcarbon (npts, dt, clay, &
679046c45
6791<     INTEGER(i_std), INTENT(in)                                               :: kjpindex
6792---
6793>     INTEGER(i_std), INTENT(in)                                               :: npts
679448c47
6795<     REAL(r_std), INTENT(in)                                            :: dt_days
6796---
6797>     REAL(r_std), INTENT(in)                                            :: dt
679850c49
6799<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                           :: clayfraction
6800---
6801>     REAL(r_std), DIMENSION(npts), INTENT(in)                           :: clay
680253c52
6803<     REAL(r_std), DIMENSION(kjpindex,ncarb,nvm), INTENT(in)           :: soilcarbon_input
6804---
6805>     REAL(r_std), DIMENSION(npts,ncarb,nvm), INTENT(in)           :: soilcarbon_input
680655c54
6807<     REAL(r_std), DIMENSION(kjpindex,nlevs), INTENT(in)                     :: control_temp
6808---
6809>     REAL(r_std), DIMENSION(npts,nlevs), INTENT(in)                     :: control_temp
681057c56
6811<     REAL(r_std), DIMENSION(kjpindex,nlevs), INTENT(in)                     :: control_moist
6812---
6813>     REAL(r_std), DIMENSION(npts,nlevs), INTENT(in)                     :: control_moist
681462c61
6815<     REAL(r_std), DIMENSION(kjpindex,ncarb,nvm), INTENT(inout)        :: carbon
6816---
6817>     REAL(r_std), DIMENSION(npts,ncarb,nvm), INTENT(inout)        :: carbon
681867c66
6819<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)                :: resp_hetero_soil
6820---
6821>     REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                :: resp_hetero_soil
682274c73
6823<     REAL(r_std), DIMENSION(kjpindex,ncarb,ncarb)                           :: frac_carb
6824---
6825>     REAL(r_std), DIMENSION(npts,ncarb,ncarb)                           :: frac_carb
682676c75
6827<     REAL(r_std), DIMENSION(kjpindex,ncarb)                                 :: frac_resp
6828---
6829>     REAL(r_std), DIMENSION(npts,ncarb)                                 :: frac_resp
683078c77
6831<     REAL(r_std), DIMENSION(kjpindex,ncarb)                                 :: fluxtot
6832---
6833>     REAL(r_std), DIMENSION(npts,ncarb)                                 :: fluxtot
683480c79
6835<     REAL(r_std), DIMENSION(kjpindex,ncarb,ncarb)                           :: flux
6836---
6837>     REAL(r_std), DIMENSION(npts,ncarb,ncarb)                           :: flux
683894,95d92
6839<     IF ( firstcall_soilcarbon ) THEN
6840<
6841100c97,121
6842<        ! 1.1.1 residence times in carbon pools (days)
6843---
6844>     ! 1.1.1 flux fractions between carbon pools: depend on clay content, recalculated
6845>     !       each time
6846>
6847>     ! 1.1.1.1 from active pool: depends on clay content
6848>
6849>     frac_carb(:,iactive,iactive) = zero
6850>     frac_carb(:,iactive,ipassive) = 0.004
6851>     frac_carb(:,iactive,islow) = un - (.85-.68*clay(:)) - frac_carb(:,iactive,ipassive)
6852>
6853>     ! 1.1.1.2 from slow pool
6854>
6855>     frac_carb(:,islow,islow) = .0
6856>     frac_carb(:,islow,iactive) = .42
6857>     frac_carb(:,islow,ipassive) = .03
6858>
6859>     ! 1.1.1.3 from passive pool
6860>
6861>     frac_carb(:,ipassive,ipassive) = .0
6862>     frac_carb(:,ipassive,iactive) = .45
6863>     frac_carb(:,ipassive,islow) = .0
6864>
6865>
6866>     IF ( firstcall ) THEN
6867>
6868>        ! 1.1.2 residence times in carbon pools (days)
6869107c128
6870<        ! 1.1.2 messages
6871---
6872>        ! 1.2 messages
6873123c144
6874<        firstcall_soilcarbon = .FALSE.
6875---
6876>        firstcall = .FALSE.
6877125d145
6878<        RETURN
6879128,148d147
6880<     ! 1.1.3 flux fractions between carbon pools: depend on clay content, recalculated
6881<     !       each time
6882<
6883<     ! 1.1.3.1 from active pool: depends on clay content
6884<
6885<     frac_carb(:,iactive,iactive) = zero
6886<     frac_carb(:,iactive,ipassive) = 0.004
6887<     frac_carb(:,iactive,islow) = un - (.85-.68*clayfraction(:)) - frac_carb(:,iactive,ipassive)
6888<
6889<     ! 1.1.3.2 from slow pool
6890<
6891<     frac_carb(:,islow,islow) = .0
6892<     frac_carb(:,islow,iactive) = .42
6893<     frac_carb(:,islow,ipassive) = .03
6894<
6895<     ! 1.1.3.3 from passive pool
6896<
6897<     frac_carb(:,ipassive,ipassive) = .0
6898<     frac_carb(:,ipassive,iactive) = .45
6899<     frac_carb(:,ipassive,islow) = .0
6900<
6901150c149
6902<     ! 1.2 set output to zero
6903---
6904>     ! 1.3 set output to zero
6905159c158
6906<     carbon(:,:,:) = carbon(:,:,:) + soilcarbon_input(:,:,:) * dt_days
6907---
6908>     carbon(:,:,:) = carbon(:,:,:) + soilcarbon_input(:,:,:) * dt
6909188c187
6910<              fluxtot(:,k) = dt_days/carbon_tau(k) * carbon(:,k,m) * &
6911---
6912>              fluxtot(:,k) = dt/carbon_tau(k) * carbon(:,k,m) * &
6913191c190
6914<              fluxtot(:,k) = dt_days/carbon_tau(k) * carbon(:,k,m) * &
6915---
6916>              fluxtot(:,k) = dt/carbon_tau(k) * carbon(:,k,m) * &
6917194c193
6918<              fluxtot(:,k) = dt_days/carbon_tau(k) * carbon(:,k,m) * &
6919---
6920>              fluxtot(:,k) = dt/carbon_tau(k) * carbon(:,k,m) * &
6921199c198
6922<              fluxtot(:,k) = fluxtot(:,k) * ( un - .75 * clayfraction(:) )
6923---
6924>              fluxtot(:,k) = fluxtot(:,k) * ( un - .75 * clay(:) )
6925216c215
6926<        !       resp_hetero_soil(:,m) = SUM( frac_resp(:,:) * fluxtot(:,:), DIM=2 ) / dt_days
6927---
6928>        !       resp_hetero_soil(:,m) = SUM( frac_resp(:,:) * fluxtot(:,:), DIM=2 ) / dt
6929221c220
6930<             frac_resp(:,ipassive) * fluxtot(:,ipassive)  ) / dt_days
6931---
6932>             frac_resp(:,ipassive) * fluxtot(:,ipassive)  ) / dt
6933236c235
6934<   END SUBROUTINE soilcarbon_main
6935---
6936>   END SUBROUTINE soilcarbon
6937diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/stomate_turnover.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/stomate_turnover.f90
693824c24
6939<   PUBLIC turn_main, turn_clear
6940---
6941>   PUBLIC turn, turn_clear
694227c27
6943<   LOGICAL, SAVE                                              :: firstcall_turnover = .TRUE.
6944---
6945>   LOGICAL, SAVE                                              :: firstcall = .TRUE.
694630,31d29
6947< ! List of subroutines for initialization :
6948< !- turn_clear
694934c32
6950<     firstcall_turnover=.TRUE.
6951---
6952>     firstcall=.TRUE.
695337c35
6954<   SUBROUTINE turn_main (kjpindex, dt_days, PFTpresent, &
6955---
6956>   SUBROUTINE turn (npts, dt, PFTpresent, &
695742c40
6958<        turnover_daily, senescence,turnover_time)
6959---
6960>        turnover, senescence,turnover_time)
696151c49
6962<     INTEGER(i_std), INTENT(in)                                        :: kjpindex
6963---
6964>     INTEGER(i_std), INTENT(in)                                        :: npts
696553c51
6966<     REAL(r_std), INTENT(in)                                     :: dt_days
6967---
6968>     REAL(r_std), INTENT(in)                                     :: dt
696955c53
6970<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(in)                  :: PFTpresent
6971---
6972>     LOGICAL, DIMENSION(npts,nvm), INTENT(in)                  :: PFTpresent
697357c55
6974<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: herbivores
6975---
6976>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: herbivores
697759c57
6978<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: maxmoiavail_lastyear
6979---
6980>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: maxmoiavail_lastyear
698161c59
6982<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: minmoiavail_lastyear
6983---
6984>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: minmoiavail_lastyear
698563c61
6986<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: moiavail_week
6987---
6988>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: moiavail_week
698965c63
6990<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: moiavail_month
6991---
6992>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: moiavail_month
699367c65
6994<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                    :: tlong_ref
6995---
6996>     REAL(r_std), DIMENSION(npts), INTENT(in)                    :: tlong_ref
699769c67
6998<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                    :: t2m_month
6999---
7000>     REAL(r_std), DIMENSION(npts), INTENT(in)                    :: t2m_month
700171c69
7002<     REAL(r_std), DIMENSION(kjpindex), INTENT(in)                    :: t2m_week
7003---
7004>     REAL(r_std), DIMENSION(npts), INTENT(in)                    :: t2m_week
700573c71
7006<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)               :: veget_max
7007---
7008>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: veget_max
700978c76
7010<     REAL(r_std), DIMENSION(kjpindex,nvm,nleafages), INTENT(inout)  :: leaf_age
7011---
7012>     REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)  :: leaf_age
701380c78
7014<     REAL(r_std), DIMENSION(kjpindex,nvm,nleafages), INTENT(inout)  :: leaf_frac
7015---
7016>     REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)  :: leaf_frac
701782c80
7018<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)            :: age
7019---
7020>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: age
702184c82
7022<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)            :: lai
7023---
7024>     REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: lai
702586c84
7026<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(inout)     :: biomass
7027---
7028>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)     :: biomass
702988c86
7030<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(inout)            :: turnover_time
7031---
7032>     REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: turnover_time
703393c91
7034<     REAL(r_std), DIMENSION(kjpindex,nvm,nparts), INTENT(out)       :: turnover_daily
7035---
7036>     REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(out)       :: turnover
703796c94
7038<     LOGICAL, DIMENSION(kjpindex,nvm), INTENT(out)                 :: senescence
7039---
7040>     LOGICAL, DIMENSION(npts,nvm), INTENT(out)                 :: senescence
7041103c101
7042<     REAL(r_std), DIMENSION(kjpindex,nvm)                           :: leaf_meanage
7043---
7044>     REAL(r_std), DIMENSION(npts,nvm)                           :: leaf_meanage
7045105c103
7046<     REAL(r_std), DIMENSION(kjpindex)                                :: dturnover
7047---
7048>     REAL(r_std), DIMENSION(npts)                                :: dturnover
7049107c105
7050<     REAL(r_std), DIMENSION(kjpindex)                                :: moiavail_crit
7051---
7052>     REAL(r_std), DIMENSION(npts)                                :: moiavail_crit
7053109c107
7054<     REAL(r_std), DIMENSION(kjpindex)                                :: tl
7055---
7056>     REAL(r_std), DIMENSION(npts)                                :: tl
7057111c109
7058<     REAL(r_std), DIMENSION(kjpindex)                                :: t_crit
7059---
7060>     REAL(r_std), DIMENSION(npts)                                :: t_crit
7061113c111
7062<     LOGICAL, DIMENSION(kjpindex)                                   :: shed_rest
7063---
7064>     LOGICAL, DIMENSION(npts)                                   :: shed_rest
7065115c113
7066<     REAL(r_std), DIMENSION(kjpindex)                                :: sapconv
7067---
7068>     REAL(r_std), DIMENSION(npts)                                :: sapconv
7069117c115
7070<     REAL(r_std), DIMENSION(kjpindex)                                :: hw_old
7071---
7072>     REAL(r_std), DIMENSION(npts)                                :: hw_old
7073119c117
7074<     REAL(r_std), DIMENSION(kjpindex)                                :: hw_new
7075---
7076>     REAL(r_std), DIMENSION(npts)                                :: hw_new
7077121c119
7078<     REAL(r_std), DIMENSION(kjpindex)                                :: lm_old
7079---
7080>     REAL(r_std), DIMENSION(npts)                                :: lm_old
7081123c121
7082<     REAL(r_std), DIMENSION(kjpindex,nleafages)                      :: delta_lm
7083---
7084>     REAL(r_std), DIMENSION(npts,nleafages)                      :: delta_lm
7085125c123
7086<     REAL(r_std), DIMENSION(kjpindex)                                :: turnover_rate
7087---
7088>     REAL(r_std), DIMENSION(npts)                                :: turnover_rate
7089127c125
7090<     REAL(r_std), DIMENSION(kjpindex,nvm)                           :: leaf_age_crit
7091---
7092>     REAL(r_std), DIMENSION(npts,nvm)                           :: leaf_age_crit
7093129c127
7094<     REAL(r_std), DIMENSION(kjpindex,nvm)                           :: new_turnover_time
7095---
7096>     REAL(r_std), DIMENSION(npts,nvm)                           :: new_turnover_time
7097141c139
7098<     IF ( firstcall_turnover ) THEN
7099---
7100>     IF ( firstcall ) THEN
7101147,148c145,146
7102<        firstcall_turnover = .FALSE.
7103<        RETURN
7104---
7105>        firstcall = .FALSE.
7106>
7107160c158
7108<     turnover_daily(:,:,:) = zero
7109---
7110>     turnover(:,:,:) = zero
7111278c276
7112<              turnover_time(:,j)=(turnover_time(:,j)*10./dt_days+new_turnover_time(:,j))/(10./dt_days+1.)
7113---
7114>              turnover_time(:,j)=(turnover_time(:,j)*10./dt+new_turnover_time(:,j))/(10./dt+1.)
7115305,306c303,304
7116<              turnover_daily(:,j,ileaf) = biomass(:,j,ileaf) * dt_days / pheno_crit%leaffall(j)
7117<              turnover_daily(:,j,iroot) = biomass(:,j,iroot) * dt_days / pheno_crit%leaffall(j)
7118---
7119>              turnover(:,j,ileaf) = biomass(:,j,ileaf) * dt / pheno_crit%leaffall(j)
7120>              turnover(:,j,iroot) = biomass(:,j,iroot) * dt / pheno_crit%leaffall(j)
7121308,309c306,307
7122<              biomass(:,j,ileaf) = biomass(:,j,ileaf) - turnover_daily(:,j,ileaf)
7123<              biomass(:,j,iroot) = biomass(:,j,iroot) - turnover_daily(:,j,iroot)
7124---
7125>              biomass(:,j,ileaf) = biomass(:,j,ileaf) - turnover(:,j,ileaf)
7126>              biomass(:,j,iroot) = biomass(:,j,iroot) - turnover(:,j,iroot)
7127317,320c315,318
7128<              turnover_daily(:,j,ileaf) = biomass(:,j,ileaf) * dt_days / turnover_time(:,j)
7129<              turnover_daily(:,j,isapabove) = biomass(:,j,isapabove) * dt_days / turnover_time(:,j)
7130<              turnover_daily(:,j,iroot) = biomass(:,j,iroot) * dt_days / turnover_time(:,j)
7131<              turnover_daily(:,j,ifruit) = biomass(:,j,ifruit) * dt_days / turnover_time(:,j)
7132---
7133>              turnover(:,j,ileaf) = biomass(:,j,ileaf) * dt / turnover_time(:,j)
7134>              turnover(:,j,isapabove) = biomass(:,j,isapabove) * dt / turnover_time(:,j)
7135>              turnover(:,j,iroot) = biomass(:,j,iroot) * dt / turnover_time(:,j)
7136>              turnover(:,j,ifruit) = biomass(:,j,ifruit) * dt / turnover_time(:,j)
7137322,330c320,328
7138<              turnover_daily(:,j,ileaf)=zero
7139<              turnover_daily(:,j,isapabove) =zero
7140<              turnover_daily(:,j,iroot) = zero
7141<              turnover_daily(:,j,ifruit) =zero
7142<           ENDWHERE
7143<           biomass(:,j,ileaf) = biomass(:,j,ileaf) - turnover_daily(:,j,ileaf)
7144<           biomass(:,j,isapabove) = biomass(:,j,isapabove) - turnover_daily(:,j,isapabove)
7145<           biomass(:,j,iroot) = biomass(:,j,iroot) - turnover_daily(:,j,iroot)
7146<           biomass(:,j,ifruit) = biomass(:,j,ifruit) - turnover_daily(:,j,ifruit)
7147---
7148>              turnover(:,j,ileaf)=zero
7149>              turnover(:,j,isapabove) =zero
7150>              turnover(:,j,iroot) = zero
7151>              turnover(:,j,ifruit) =zero
7152>           ENDWHERE
7153>           biomass(:,j,ileaf) = biomass(:,j,ileaf) - turnover(:,j,ileaf)
7154>           biomass(:,j,isapabove) = biomass(:,j,isapabove) - turnover(:,j,isapabove)
7155>           biomass(:,j,iroot) = biomass(:,j,iroot) - turnover(:,j,iroot)
7156>           biomass(:,j,ifruit) = biomass(:,j,ifruit) - turnover(:,j,ifruit)
7157371c369
7158<                      MIN( 0.99_r_std, dt_days / ( leaf_age_crit(:,j) * &
7159---
7160>                      MIN( 0.99_r_std, dt / ( leaf_age_crit(:,j) * &
7161375c373
7162<                 turnover_daily(:,j,ileaf) = turnover_daily(:,j,ileaf) + dturnover(:)
7163---
7164>                 turnover(:,j,ileaf) = turnover(:,j,ileaf) + dturnover(:)
7165382c380
7166<                 turnover_daily(:,j,iroot) = turnover_daily(:,j,iroot) + dturnover(:)
7167---
7168>                 turnover(:,j,iroot) = turnover(:,j,iroot) + dturnover(:)
7169386c384
7170<                 turnover_daily(:,j,ifruit) = turnover_daily(:,j,ifruit) + dturnover(:)
7171---
7172>                 turnover(:,j,ifruit) = turnover(:,j,ifruit) + dturnover(:)
7173416c414
7174<                      MIN( 0.99_r_std, dt_days / ( leaf_age_crit(:,j) * &
7175---
7176>                      MIN( 0.99_r_std, dt / ( leaf_age_crit(:,j) * &
7177420c418
7178<                 turnover_daily(:,j,ileaf) = turnover_daily(:,j,ileaf) + dturnover(:)
7179---
7180>                 turnover(:,j,ileaf) = turnover(:,j,ileaf) + dturnover(:)
7181427c425
7182<                 turnover_daily(:,j,isapabove) = turnover_daily(:,j,isapabove) + dturnover(:)
7183---
7184>                 turnover(:,j,isapabove) = turnover(:,j,isapabove) + dturnover(:)
7185431c429
7186<                 turnover_daily(:,j,iroot) = turnover_daily(:,j,iroot) + dturnover(:)
7187---
7188>                 turnover(:,j,iroot) = turnover(:,j,iroot) + dturnover(:)
7189435c433
7190<                 turnover_daily(:,j,ifruit) = turnover_daily(:,j,ifruit) + dturnover(:)
7191---
7192>                 turnover(:,j,ifruit) = turnover(:,j,ifruit) + dturnover(:)
7193497,499c495,497
7194<              turnover_daily(:,j,ileaf) = turnover_daily(:,j,ileaf) + biomass(:,j,ileaf)
7195<              turnover_daily(:,j,iroot) = turnover_daily(:,j,iroot) + biomass(:,j,iroot)
7196<              turnover_daily(:,j,ifruit) = turnover_daily(:,j,ifruit) + biomass(:,j,ifruit)
7197---
7198>              turnover(:,j,ileaf) = turnover(:,j,ileaf) + biomass(:,j,ileaf)
7199>              turnover(:,j,iroot) = turnover(:,j,iroot) + biomass(:,j,iroot)
7200>              turnover(:,j,ifruit) = turnover(:,j,ifruit) + biomass(:,j,ifruit)
7201527,530c525,528
7202<              turnover_daily(:,j,ileaf) = turnover_daily(:,j,ileaf) + biomass(:,j,ileaf)
7203<              turnover_daily(:,j,isapabove) = turnover_daily(:,j,isapabove) + biomass(:,j,isapabove)
7204<              turnover_daily(:,j,iroot) = turnover_daily(:,j,iroot) + biomass(:,j,iroot)
7205<              turnover_daily(:,j,ifruit) = turnover_daily(:,j,ifruit) + biomass(:,j,ifruit)
7206---
7207>              turnover(:,j,ileaf) = turnover(:,j,ileaf) + biomass(:,j,ileaf)
7208>              turnover(:,j,isapabove) = turnover(:,j,isapabove) + biomass(:,j,isapabove)
7209>              turnover(:,j,iroot) = turnover(:,j,iroot) + biomass(:,j,iroot)
7210>              turnover(:,j,ifruit) = turnover(:,j,ifruit) + biomass(:,j,ifruit)
7211582,583c580,581
7212<                    dturnover(:) = biomass(:,j,ileaf) * dt_days / herbivores(:,j)
7213<                    turnover_daily(:,j,ileaf) = turnover_daily(:,j,ileaf) + dturnover(:)
7214---
7215>                    dturnover(:) = biomass(:,j,ileaf) * dt / herbivores(:,j)
7216>                    turnover(:,j,ileaf) = turnover(:,j,ileaf) + dturnover(:)
7217586,587c584,585
7218<                    dturnover(:) = biomass(:,j,ifruit) * dt_days / herbivores(:,j)
7219<                    turnover_daily(:,j,ifruit) = turnover_daily(:,j,ifruit) + dturnover(:)
7220---
7221>                    dturnover(:) = biomass(:,j,ifruit) * dt / herbivores(:,j)
7222>                    turnover(:,j,ifruit) = turnover(:,j,ifruit) + dturnover(:)
7223599,600c597,598
7224<                    dturnover(:) = biomass(:,j,ileaf) * dt_days / herbivores(:,j)
7225<                    turnover_daily(:,j,ileaf) = turnover_daily(:,j,ileaf) + dturnover(:)
7226---
7227>                    dturnover(:) = biomass(:,j,ileaf) * dt / herbivores(:,j)
7228>                    turnover(:,j,ileaf) = turnover(:,j,ileaf) + dturnover(:)
7229603,604c601,602
7230<                    dturnover(:) = biomass(:,j,isapabove) * dt_days / herbivores(:,j)
7231<                    turnover_daily(:,j,isapabove) = turnover_daily(:,j,isapabove) + dturnover(:)
7232---
7233>                    dturnover(:) = biomass(:,j,isapabove) * dt / herbivores(:,j)
7234>                    turnover(:,j,isapabove) = turnover(:,j,isapabove) + dturnover(:)
7235607,608c605,606
7236<                    dturnover(:) = biomass(:,j,ifruit) * dt_days / herbivores(:,j)
7237<                    turnover_daily(:,j,ifruit) = turnover_daily(:,j,ifruit) + dturnover(:)
7238---
7239>                    dturnover(:) = biomass(:,j,ifruit) * dt / herbivores(:,j)
7240>                    turnover(:,j,ifruit) = turnover(:,j,ifruit) + dturnover(:)
7241629,630c627,628
7242<           dturnover(:) = biomass(:,j,ifruit) * dt_days / tau_fruit(j)
7243<           turnover_daily(:,j,ifruit) = turnover_daily(:,j,ifruit) + dturnover(:)
7244---
7245>           dturnover(:) = biomass(:,j,ifruit) * dt / tau_fruit(j)
7246>           turnover(:,j,ifruit) = turnover(:,j,ifruit) + dturnover(:)
7247632,633c630,631
7248< !!$        turnover_daily(:,j,ifruit) = biomass(:,j,ifruit) * dt_days / tau_fruit(j)
7249< !!$        biomass(:,j,ifruit) = biomass(:,j,ifruit) - turnover_daily(:,j,ifruit)
7250---
7251> !!$        turnover(:,j,ifruit) = biomass(:,j,ifruit) * dt / tau_fruit(j)
7252> !!$        biomass(:,j,ifruit) = biomass(:,j,ifruit) - turnover(:,j,ifruit)
7253660c658
7254<           sapconv(:) = biomass(:,j,isapabove) * dt_days / tau_sap(j)
7255---
7256>           sapconv(:) = biomass(:,j,isapabove) * dt / tau_sap(j)
7257666c664
7258<           sapconv(:) = biomass(:,j,isapbelow) * dt_days / tau_sap(j)
7259---
7260>           sapconv(:) = biomass(:,j,isapbelow) * dt / tau_sap(j)
7261699c697
7262<          leaf_meanage, kjpindex*nvm, horipft_index)
7263---
7264>          leaf_meanage, npts*nvm, horipft_index)
7265701c699
7266<          herbivores, kjpindex*nvm, horipft_index)
7267---
7268>          herbivores, npts*nvm, horipft_index)
7269705c703
7270<   END SUBROUTINE turn_main
7271---
7272>   END SUBROUTINE turn
7273diff -w --ignore-all-space --ignore-case --recursive --exclude='cvs_diff*' --exclude='*.flc' --exclude='*.bak' --exclude='*.svn*' --exclude='*.lst' --exclude='i.*.L' --exclude='*~' --exclude=Entries --exclude=Tag --exclude=CVS --exclude Makefile /login/IPSL_CODE/AssimilBranche/modeles/ORCHIDEE/src_stomate/stomate_vmax.f90 /login/IPSL_CODE/ORCHIDEE_1_9_5_2/modeles/ORCHIDEE/src_stomate/stomate_vmax.f90
727423c23
7275<   LOGICAL, SAVE                                              :: firstcall_vmax = .TRUE.
7276---
7277>   LOGICAL, SAVE                                              :: firstcall = .TRUE.
727828c28
7279<     firstcall_vmax=.TRUE.
7280---
7281>     firstcall=.TRUE.
728231c31
7283<   SUBROUTINE vmax (kjpindex, dt_days, &
7284---
7285>   SUBROUTINE vmax (npts, dt, &
728642c42
7287<     INTEGER(i_std), INTENT(in)                                        :: kjpindex
7288---
7289>     INTEGER(i_std), INTENT(in)                                        :: npts
729044c44
7291<     REAL(r_std), INTENT(in)                                     :: dt_days
7292---
7293>     REAL(r_std), INTENT(in)                                     :: dt
729449c49
7295<     REAL(r_std), DIMENSION(kjpindex,nvm,nleafages), INTENT(inout)  :: leaf_age
7296---
7297>     REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)  :: leaf_age
729851c51
7299<     REAL(r_std), DIMENSION(kjpindex,nvm,nleafages), INTENT(inout)  :: leaf_frac
7300---
7301>     REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)  :: leaf_frac
730256c56
7303<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)              :: vcmax
7304---
7305>     REAL(r_std), DIMENSION(npts,nvm), INTENT(out)              :: vcmax
730658c58
7307<     REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(out)              :: vjmax
7308---
7309>     REAL(r_std), DIMENSION(npts,nvm), INTENT(out)              :: vjmax
731071c71
7311<     REAL(r_std), DIMENSION(kjpindex)                                :: leaf_efficiency
7312---
7313>     REAL(r_std), DIMENSION(npts)                                :: leaf_efficiency
731473c73
7315<     REAL(r_std), DIMENSION(kjpindex,nvm,nleafages)                 :: d_leaf_frac
7316---
7317>     REAL(r_std), DIMENSION(npts,nvm,nleafages)                 :: d_leaf_frac
731875c75
7319<     REAL(r_std), DIMENSION(kjpindex,nleafages)                      :: leaf_age_new
7320---
7321>     REAL(r_std), DIMENSION(npts,nleafages)                      :: leaf_age_new
732277c77
7323<     REAL(r_std), DIMENSION(kjpindex)                                :: sumfrac
7324---
7325>     REAL(r_std), DIMENSION(npts)                                :: sumfrac
732679c79
7327<     REAL(r_std), DIMENSION(kjpindex)                                :: rel_age
7328---
7329>     REAL(r_std), DIMENSION(npts)                                :: rel_age
733095c95
7331<     IF ( firstcall_vmax ) THEN
7332---
7333>     IF ( firstcall ) THEN
7334104c104
7335<        firstcall_vmax = .FALSE.
7336---
7337>        firstcall = .FALSE.
7338128c128
7339<              leaf_age(:,j,m) = leaf_age(:,j,m) + dt_days
7340---
7341>              leaf_age(:,j,m) = leaf_age(:,j,m) + dt
7342150c150
7343<           d_leaf_frac(:,j,m) = leaf_frac(:,j,m-1) * dt_days/leaf_timecst(j)
7344---
7345>           d_leaf_frac(:,j,m) = leaf_frac(:,j,m-1) * dt/leaf_timecst(j)