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

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

add missing files for ORCHIDEE-GMv3.2

File size: 16.0 KB
Line 
1! ******************************************************** c
2! * - derniere modif le 28/06/01                         * c
3! * - version 3.3 18/03/98                               * c
4! * - dernière modif le 22/5/98  paramétrage de P_irmax    * c
5! * - derniere modif le 17/11/00     magrain constant    * c
6! * - derniere modif le 08/04/01     GEL                 * c
7! * - derniere modif le 02/05        sucre,huile         * c
8! * - derniere modif dr 25/10/05 pb proteines            * c
9! ******************************************************** c
10!> Calculation of the number and filling of organs for harvest in the case of plants with determinate growth.
11!> - Stics book paragraphe 4,1, page 74-76
12!>
13!> In the case of plants with determinate growth, the hypothesis is made that the number and filling of organs for harvest do not depend on the other
14!! organs’ growth requirements. The number of grains is fixed during a phase of variable duration (nbjgrain in days), which precedes the onset of filling (IDRP).
15!! This number depends on the mean growth rate of the canopy during this period (vitmoy in gm-2d-1), which in turns depends on dynamics specific to the
16!! particular species.
17!>
18!> The number of grains per m2 (nbgrains) is defined at the IDRP stage. It depends on the growth variable (vitmoy in g m-2) that integrates the effect of the
19!! prevailing stresses during the period preceding the IDRP stage, on two species-dependent parameters cgrain (in g-1 m2) and nbgrmin (grains m-2) and a
20!! genetic-dependent parameter nbgrmax (grains m-2).  The last two parameters define the limits of variation of nbgrains.
21!! After the IDRP stage, the grain number can be reduced in the event of frost and the daily proportion of grains affected is (1-fgelflo), whatever their
22!! state of growth. The corresponding weight (pgraingel in gm-2) is deducted from the grain weight, using the elementary current grain weight (pgrain in g).
23!>
24!> The quantity of dry matter accumulated in grains is calculated by applying a progressive "harvest index" to the dry weight of the plant.
25!! This ircarb index increases linearly with time (vitircarb in g grain g biomass 1 d-1), from the IDRP stage to the IMAT stage and the final harvest index
26!! is restricted to the irmax parameter. Yet this dynamics may not be the actual grain filling dynamics since threshold translocation temperatures defining
27!! the thermal stress ftempremp (tminremp and tmaxremp) may stop the carbon filling of harvested organs.
28!! Consequently the grain filling is calculated daily (dltags in t ha-1) to allow the effect of the thermal stress and then accumulated within the
29!! mafruit (in t ha-1) variable. The mass of each grain is then calculated as the ratio of the mass to the number of grains, although this cannot exceed
30!! the genetic pgrainmaxi limit.
31!-----------------------------------------------------------------------------------------------
32!subroutine grain(n,ndrp,nrec,nlev,nrecbutoir,P_nbjgrain,dltams,P_cgrain,P_cgrainv0, & ! IN
33!                 P_nbgrmin,P_nbgrmax,P_codazofruit,P_codeinnact,inns,fgelflo,P_codeir,  & ! IN
34!                 P_vitircarb,P_irmax,P_vitircarbT,somcourdrp,nmat,masec,P_codetremp,  & ! IN
35!                 tcultmin,tcultmax,P_tminremp,P_tmaxremp,P_pgrainmaxi,              & ! IN
36!                 ircarb,nbgrains,pgrain,CNgrain,vitmoy,nbgraingel,pgraingel,  & ! INOUT
37!                 dltags,ftempremp,magrain,nbj0remp,pdsfruittot)                 ! INOUT
38
39
40subroutine grain(n,vday_counter, dltams, nflo, ndrp,nrec,nlev,nrecbutoir, & ! IN
41                 somcourdrp,nmat,masec, pdmasec, tcultmin, tcultmax,  & ! IN
42                 v_dltams, fgelflo, pdircarb, ircarb, nbgrains, pgrain, vitmoy,nbgraingel,pgraingel,  & ! INOUT
43                 dltags,ftempremp,magrain, pdmagrain, nbj0remp,pdsfruittot, deltgrain, & ! INOUT
44                 P_nbjgrain, P_codeplante, P_codgelflo, P_tgelflo10, P_tgelflo90, P_cgrain, P_cgrainv0, &
45                 P_nbgrmax, P_nbgrmin, P_codazofruit, P_codeinnact, P_codeir, P_vitircarb, P_irmax, P_vitircarbT, &
46                 P_codetremp, P_tminremp, P_tmaxremp, P_pgrainmaxi)                 ! IN, parameter
47
48  !USE Messages
49  USE constantes
50  USE Divers_gel
51
52
53  implicit none
54
55!: Arguments
56
57  integer, intent(IN)    :: n     ! date // actually stomate slow step 
58  integer, intent(IN)    :: vday_counter ! day_counter but not be reinitilized 
59  real,    intent(IN)    :: dltams !//unit with t ha-1 j-1
60  integer, intent(IN)    :: nflo 
61  integer, intent(IN)    :: ndrp 
62  integer, intent(IN)    :: nrec 
63  integer, intent(IN)    :: nlev 
64  integer, intent(IN)    :: nrecbutoir 
65  integer, intent(IN)    :: P_nbjgrain  !> // PARAMETER // Period to compute NBGRAIN // days // PARPLT // 1
66  character, intent(IN)  :: P_codeplante ! //parameter
67  integer,     intent(IN)   :: P_codgelflo  !
68  real,     intent(IN)   :: P_tgelflo10 !
69  real,     intent(IN)   :: P_tgelflo90  !
70  !real,    intent(IN)    :: dltams(ndrp) ! ndrp-P_nbjgrain+1 to ndrp    // OUTPUT // Growth rate of the plant  // t ha-1.j-1
71  real,    intent(IN)    :: P_cgrain  !> // PARAMETER // slope of the relationship between grain number and growth rate  // grains gMS -1 jour // PARPLT // 1
72  real,    intent(IN)    :: P_cgrainv0  !> // PARAMETER // number of grains produced when growth rate is zero // grains m-2 // PARPLT // 1
73  real,    intent(IN)    :: P_nbgrmin  !> // PARAMETER // Minimum number of grain // grains m-2  // PARPLT // 1
74  real,    intent(IN)    :: P_nbgrmax  !> // PARAMETER // Maximum number of grain // grains m-2 // PARPLT // 1
75  integer, intent(IN)    :: P_codazofruit  !> // PARAMETER // option of activation of the direct effect of the nitrogen plant status upon the fruit/grain number // code 1/2 // PARPLT // 0
76  integer, intent(IN)    :: P_codeinnact  !> // PARAMETER // code activating  nitrogen stress effect on the crop: yes (1), no (2) // code 1/2 // PARAM // 0
77  !!real,    intent(IN)    :: inns   !> // OUTPUT // Index of nitrogen stress active on growth in biomass // P_innmin to 1
78  integer, intent(IN)    :: P_codeir  !> // PARAMETER // option of computing the ratio grain weight/total biomass: proportional to time(1), proportional to sum temperatures (2) // code 1/2 // PARPLT // 0
79  real,    intent(IN)    :: P_vitircarb  !> // PARAMETER // Rate of increase of the carbon harvest index // g grain g plant -1 day-1 // PARPLT // 1
80  real,    intent(IN)    :: P_irmax  !> // PARAMETER // Maximum harvest index // SD // PARPLT // 1
81  real,    intent(IN)    :: P_vitircarbT  !> // PARAMETER // Heat rate of increase of the carbon harvest index  // g grain g plant-1 degree.day-1 // PARPLT // 1
82  real,    intent(IN)    :: somcourdrp 
83  integer, intent(IN)    :: nmat 
84
85  !real,    intent(IN)    :: masec(0:1)  ! n-1 (0) & n (1)    // OUTPUT // Aboveground dry matter  // t.ha-1
86  real,    intent(IN)    :: masec  ! // Aboveground dry matter  // t.ha-1
87  real,    intent(IN)    :: pdmasec  ! // Aboveground dry matter of previous day  // t.ha-1
88
89  integer, intent(IN)    :: P_codetremp  !> // PARAMETER // option of heat effect on grain filling: yes (2), no (1) // code 1/2 // PARPLT // 0
90  real,    intent(IN)    :: tcultmin 
91  real,    intent(IN)    :: tcultmax   !> // OUTPUT // Crop surface temperature (daily maximum) // degree C
92  real,    intent(IN)    :: P_tminremp  !> // PARAMETER // Minimal temperature for grain filling // degree C // PARPLT // 1
93  real,    intent(IN)    :: P_tmaxremp  !> // PARAMETER // maximal temperature for grain filling // degree C // PARPLT // 1
94  real,    intent(IN)    :: P_pgrainmaxi  !> // PARAMETER // Maximum weight of one grain (at 0% water content) // g // PARPLT // 1
95  !
96
97  !! INOUT
98  real, dimension(0:vlength-1),  intent(INOUT) :: v_dltams   !biomass increment during a time period before ndrp, the length is according to P_nbjgrain 
99  real,    intent(INOUT) :: fgelflo   !> // Frost index on the number of fruits // 0-1
100  !real,    intent(INOUT) :: ircarb(0:1)   ! n-1 (0) & n (1)    // OUTPUT // Carbon harvest index // g  grain g plant-1
101  real,    intent(INOUT) :: pdircarb   !ircarb of previous day     // OUTPUT // Carbon harvest index // g  grain g plant-1
102  real,    intent(INOUT) :: ircarb   ! // Carbon harvest index // g  grain g plant-1
103
104  real,    intent(INOUT) :: nbgrains ! grains per square meter grains m-2
105  real,    intent(INOUT) :: pgrain ! weight per grain // unit in g m-2
106  !real,    intent(INOUT) :: CNgrain   !> // OUTPUT // Nitrogen concentration of grains  // %
107  real,    intent(INOUT) :: vitmoy   !> // OUTPUT // mean growth rate of the canopy (dans le livre c'est en g mais ca colle pas)  // g.m-2.d-1
108  real,    intent(INOUT) :: nbgraingel 
109  real,    intent(INOUT) :: pgraingel 
110  real,    intent(INOUT) :: dltags   !> // OUTPUT // Growth rate of the grains  // t ha-1.j-1
111  real,    intent(INOUT) :: ftempremp 
112  !real,    intent(INOUT) :: magrain(0:1)  ! n-1 (0) & n (1)! dry matter of the grain
113  real,    intent(INOUT) :: magrain  ! accumulated dry matter of the grain // unit is in g m-2
114  real,    intent(INOUT) :: pdmagrain  ! dry matter of the grain of the previous day // unit is in g m-2
115   
116  integer, intent(INOUT) :: nbj0remp   !> // OUTPUT // Number of shrivelling days //
117  real,    intent(INOUT) :: pdsfruittot 
118 
119  !! output
120  real,    intent(OUT) :: deltgrain 
121  !
122!:! Variables locales
123  integer :: ng 
124  real    :: tefficace 
125
126     
127
128
129      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
130      !>> PART ONE     
131      ! Here, we preparing the dltams for period: ndrp-P_nbjgrain+1 to ndrp
132     
133      v_dltams(MOD(vday_counter, P_nbjgrain)) = dltams 
134   
135      !>> PART TWO
136      ! Here, we calculate the gel effects on grain production
137
138      if (P_codeplante /= 'snu') then
139         if (nflo > 0 .and. nmat == 0) then  ! from flowering to mature
140           fgelflo = GEL(P_codgelflo,tcultmin,P_tgelflo90,P_tgelflo10)
141         else
142           fgelflo = 1.0
143           !if (fgelflo < 1.) gelee = .TRUE.
144         endif
145         !if (gelee .eqv. .TRUE.) nbjgel = nbjgel + 1
146      endif
147
148
149      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
150      !>> PART THREE
151      ! Here, we calculate the grain production
152
153      if (ndrp == 0 .or. (nrec > 0 .and. n > nrec)) then
154        !ircarb(1) = 0.0
155        ircarb = 0.0
156        return
157      endif
158     
159
160      !: Attention incohérence entre tsol qui interdit la levée et tair qui amène à drp
161      ! in case of the following situation, the simulation is wrong.
162      if (ndrp > 0 .and. nlev == 0) then
163        !call EnvoyerMsgHistorique(51)
164        !call EnvoyerMsgHistorique(52)
165        stop
166      endif
167
168      !: Modif NB - 20/08/97
169      !- Si la date de récolte butoir intervient avant le début remplissage,
170      !- pas de grain.
171      if (ndrp == nrecbutoir) then
172        nbgrains = 0.0 ! number of grains
173        pgrain   = 0.0 ! weight per grain
174        !CNgrain  = 0.0
175        return
176      endif
177   
178     
179      !: Calcul du nombre de grain
180      if (n == ndrp) then
181     
182        !: Calcul de la vitesse de croissance moyenne P_nbjgrain avant ndrp
183        !- NB - 08/04 : nbgrains remplacé par nbgrainpot
184        vitmoy = 0.0
185        ng = ndrp - P_nbjgrain + 1
186        !
187        !vitmoy = SUM(dltams(ng:ndrp))
188        vitmoy = SUM(v_dltams(1:P_nbjgrain))
189        vitmoy = vitmoy / P_nbjgrain * 100    ! unit in g m-2 d-1
190
191        !: nbgrains devient variétal avec P_nbgrmax
192        nbgrains = ((P_cgrain * vitmoy) + P_cgrainv0) * P_nbgrmax
193
194
195
196        !: Seuillage de nbgrains
197        nbgrains = max(nbgrains, P_nbgrmin)
198        nbgrains = min(nbgrains, P_nbgrmax)
199
200
201        !: Option P_codazofruit, addressing the direct effects of nitrogen on grain
202        if (P_codazofruit == 2 .and. P_codeinnact == 1) then
203          nbgrains = nbgrains * inns ! inns is a constance
204        endif
205      else
206        !: Dégats de GEL
207        if (fgelflo < 1.0) then
208          nbgraingel = nbgrains * (1.0 - fgelflo)
209        else
210          nbgraingel = 0.0
211        endif
212        pgraingel = (pgrain * nbgraingel) + pgraingel
213        nbgrains = nbgrains - nbgraingel
214
215
216        !: vitmoy est en g m-2 day-1
217        if (P_codeir == 1) then
218          ircarb = P_vitircarb * (n - ndrp + 1)
219          ircarb = min(ircarb, P_irmax)
220          !ircarb(1) = P_vitircarb * (n - ndrp + 1)
221          !ircarb(1) = min(ircarb(1), P_irmax)
222        endif
223
224        if (P_codeir == 2) then
225          ircarb = P_vitircarbT * somcourdrp
226          !ircarb(1) = P_vitircarbT * somcourdrp
227        endif
228
229
230        !: domi - 29/10/05: irazo deplacé dans Ngrain sinon on a pas la valeur
231        !-                  de qnplante qui est calculée dans stressn
232
233
234        if (nmat == 0 .or. n == nmat) then
235          !: Vitesse de remplissage du grain unit in t/ha
236          dltags = ircarb * masec      &
237                 - pdircarb * pdmasec
238
239          !dltags = ircarb(1) * masec(1)      &
240          !       - ircarb(0) * masec(0)
241          !: Effet température
242          ftempremp = 1.0
243          if (P_codetremp == 1) then
244            !: NB - Ajout d'un compteur jours sans remplissage
245
246            !: pour les mini
247            tefficace = tcultmin
248           
249            if (tefficace <= P_tminremp) then
250              magrain = pdmagrain
251              !magrain(1) = magrain(0)
252              ftempremp = 0.0
253              dltags = 0.0
254              nbj0remp = nbj0remp + 1
255            endif
256
257            !: pour les maxi
258            tefficace = tcultmax
259            if (tefficace >= P_tmaxremp) then
260              magrain = pdmagrain
261              !magrain(1) = magrain(0)
262              ftempremp = 0.0
263              dltags = 0.0
264              nbj0remp = nbj0remp + 1
265            endif
266          endif
267   
268          !: Le carbone des grains
269          !- NB - le 23/05 : suppression des grains gelés
270          !- NB - passage par dltags pour echaudage actif - le 11/01/02
271          !-- magrain(1) = ircarb(1)*masec(n)*100 - pgraingel
272
273          !- DR et AIG, on a trouvé un bug :
274          !- On enlevait chaque jour le cumul du poids de grain gelé
275          !- au lieu du poids de grain gelé du jour et ce meme apres
276          !- que le gel soit fini d'ou diminution
277          !- notable du rdt (dixit aig)
278          magrain = pdmagrain + (dltags * 100) - (pgrain * nbgraingel)
279          !magrain(1) = magrain(0) + (dltags * 100) - (pgrain * nbgraingel)
280          magrain = max(magrain, 0.0)
281          !magrain(1) = max(magrain(1), 0.0)
282          if (magrain > P_pgrainmaxi * nbgrains) then
283          !if (magrain(1) > P_pgrainmaxi * nbgrains) then
284            magrain = P_pgrainmaxi * nbgrains
285            !magrain(1) = P_pgrainmaxi * nbgrains
286            dltags = 0.0
287          endif
288          if (nbgrains > 0.0) then
289            pgrain = magrain / nbgrains
290            !pgrain = magrain(1) / nbgrains
291          else
292            pgrain = 0.0
293          endif
294          ! les calculs d'azote dans les grains ont ete deplacé dans Ngrain
295        endif
296
297        !: Entre maturité et récolte
298        !- DR - 050506 : Dans le cas où on repousse la recolte,
299        !-               on doit pourvoir garder masec.
300        !-- if (nrec == 0 .and. nmat > 0) then
301        if ((nrec == 0 .or. nrec == -999) .and. nmat > 0) then
302           magrain = pdmagrain
303           !magrain(1) = magrain(0)
304        endif
305       
306        if (nmat > 0 .and. nrec > 0 .and. n < nrec) magrain = pdmagrain
307   
308        if (n == nrec) magrain = pdmagrain
309       
310       
311       
312        pdsfruittot = magrain
313        !pdsfruittot = magrain(1)
314
315      endif
316
317      ! transfication between dry matter and carbon
318      ! according to PC GBC (2007)
319     
320      ! transfer dry matter of grain to carbon
321
322      magrain = magrain
323     
324      deltgrain = magrain - pdmagrain ! this is the deltgrain
325
326 
327      pdircarb = ircarb 
328      pdmagrain = magrain   ! get the pdmagrain       
329      !
330       
331return
332end
333 
334 
Note: See TracBrowser for help on using the repository browser.