source: branches/publications/ORCHIDEE_GLUC_r6545/src_stomate/lpj_gap.f90 @ 6737

Last change on this file since 6737 was 4507, checked in by albert.jornet, 7 years ago

Merge: from revisions [4467:4491/trunk/ORCHIDEE]

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 15.2 KB
Line 
1! =================================================================================================================================
2! MODULE       : lpj_gap
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF       Simulate mortality of individuals and update biomass, litter and
10!! stand density of the PFT
11!!
12!!\n DESCRIPTION : Simulate mortality of individuals and update biomass, litter and
13!! stand density of the PFT. This module differs from lpj_kill.f90 in that this
14!! module kills individuals within a PFT and lpj_kill.f90 removes a PFT from a
15!! gridbox
16!!
17!! RECENT CHANGE(S): None
18!!
19!! REFERENCE(S) :
20!! - Sitch, S., B. Smith, et al. (2003), Evaluation of ecosystem dynamics,
21!!         plant geography and terrestrial carbon cycling in the LPJ dynamic
22!!         global vegetation model, Global Change Biology, 9, 161-185.\n
23!! - Waring, R. H. (1983). "Estimating forest growth and efficiency in relation
24!!         to canopy leaf area." Advances in Ecological Research 13: 327-354.\n
25!!
26!! SVN          :
27!! $HeadURL$
28!! $Date$
29!! $Revision$
30!! \n
31!_ ================================================================================================================================
32
33MODULE lpj_gap
34
35  ! modules used:
36  USE xios_orchidee
37  USE stomate_data
38  USE pft_parameters
39  USE ioipsl_para 
40  USE constantes
41
42  IMPLICIT NONE
43
44  ! private & public routines
45
46  PRIVATE
47  PUBLIC gap,gap_clear
48 
49  ! Variable declaration
50
51  LOGICAL, SAVE             :: firstcall_gap = .TRUE.                  !! first call flag
52!$OMP THREADPRIVATE(firstcall_gap)
53  REAL(r_std), PARAMETER    :: frost_damage_limit = -3 + ZeroCelsius   !! Spring frost-damage limitation (K)
54  REAL(r_std), PARAMETER    :: coldness_mort = 0.04                    !! Daily mortality induced by extreme coldness in winter
55CONTAINS
56
57
58!! ================================================================================================================================
59!! SUBROUTINE   : gap_clear
60!!
61!>\BRIEF        Set the firstcall_gap flag back to .TRUE. to prepare for the next simulation.
62!_ ================================================================================================================================
63 
64  SUBROUTINE gap_clear
65    firstcall_gap = .TRUE.
66  END SUBROUTINE gap_clear
67
68
69!! ================================================================================================================================
70!! SUBROUTINE   : gap
71!!
72!>\BRIEF        Simulate tree and grass mortality, transfer dead biomass to litter and update stand density
73!!
74!! DESCRIPTION  : Calculate mortality of trees and grasses, transfer the dead biomass to litter pool,
75!! and update biomass pool and number of individuals. To get tree mortality, it's possible to choose either a
76!! constant mortality rate; or to calculate the tree mortality rate based on it's growth efficiency, which is
77!! defined as this year's net biomass increment per leaf area.\n
78!!
79!! When using growth efficiency mortality, first calculate the net biomass increment for the last year, then
80!! calculate the growth efficiency and finally calculate the growth efficiency mortality.\n
81!!
82!! Eqation to calculate growth efficiency:
83!! \latexonly
84!!     \input{gap1.tex}
85!! \endlatexonly
86!! Where $greff$ is growth efficiency, $\Delta$ is net biomass increment,
87!! $C_{leaf} is last year's leaf biomass, and $SLA$ the specific leaf area.
88!!
89!!
90!! Eqation to calculate growth efficiency mortality:
91!! \latexonly
92!!     \input{gap2.tex}
93!! \endlatexonly
94!! Where $mort_{greff}$ is the growth efficiency mortality, $greff$ is growth 
95!! efficiency, $k_{mort1}$ is asymptotic maximum mortality rate.
96!!
97!! The name for variable ::availability is not well chosen. Actually the meaning of the variable is mortailty
98!! rate derived from growth efficiency related mortality. ?? Suggestion: change the name "availability" to
99!! "mortgref", which means "mortality caused by ".\n
100!!
101!! RECENT CHANGE(S): None
102!!
103!! MAIN OUTPUT VARIABLE(S): ::biomass; biomass, ::ind density of individuals, ::bm_to_litter biomass transfer
104!! to litter and ::mortality mortality (fraction of trees that is dying per time step)
105!!
106!! REFERENCE(S)   :
107!! - Sitch, S., B. Smith, et al. (2003), Evaluation of ecosystem dynamics,
108!!         plant geography and terrestrial carbon cycling in the LPJ dynamic
109!!         global vegetation model, Global Change Biology, 9, 161-185.
110!! - Waring, R. H. (1983). "Estimating forest growth and efficiency in relation
111!!         to canopy leaf area." Advances in Ecological Research 13: 327-354.
112!!
113!! FLOWCHART    : None
114!!\n
115!_ ================================================================================================================================
116 
117  SUBROUTINE gap (npts, dt, &
118       npp_longterm, turnover_longterm, lm_lastyearmax, &
119       PFTpresent, biomass, ind, bm_to_litter, mortality, t2m_min_daily, Tmin_spring_time, &
120       sla_calc)
121
122
123    !! 0. Variable and parameter declaration
124
125    !! 0.1 Input variables
126    INTEGER(i_std), INTENT(in)                              :: npts                    !! Domain size (-)
127    REAL(r_std), INTENT(in)                                 :: dt                      !! Time step (days)
128    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: npp_longterm            !! "Long term" (default 3-year) net primary
129                                                                                       !! productivity 
130                                                                                       !! @tex $(gC m^{-2} year^{-1})$ @endtex
131    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(in) :: turnover_longterm       !! "Long term" (default 3-year) turnover 
132                                                                                       !! rate @tex $(gC m^{-2} year^{-1})$ @endtex
133    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: lm_lastyearmax          !! Last year's maximum leaf mass, for each
134                                                                                       !! PFT @tex $(gC m^{-2})$ @endtex
135    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                :: PFTpresent              !! Is the pft present in the pixel
136    REAL(r_std), DIMENSION(npts), INTENT(in)                :: t2m_min_daily           !! Daily minimum 2 meter temperatures (K)
137    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: Tmin_spring_time        !! Number of days after begin_leaves (leaf onset)
138
139    !! 0.2 Output variables
140
141    REAL(r_std), DIMENSION(npts,nvm),INTENT(out)            :: mortality               !! Mortality (fraction of trees that is
142                                                                                       !! dying per time step)
143
144    !! 0.3 Modified variables   
145   
146    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(inout)  :: biomass       !! Biomass @tex $(gC m^{-2}) $@endtex
147    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                   :: ind           !! Number of individuals
148                                                                                       !! @tex $(m^{-2})$ @endtex
149    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(inout)  :: bm_to_litter  !! Biomass transfer to litter
150                                                                                       !! @tex $(gC m^{-2})$ @endtex 
151!gmjc
152    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: sla_calc
153!end gmjc
154    !! 0.4 Local variables
155
156    REAL(r_std), DIMENSION(npts)                            :: delta_biomass           !! Net biomass increase for the previous
157                                                                                       !! year @tex $(gC m^{-2} year^{-1})$ @endtex
158    REAL(r_std), DIMENSION(npts)                            :: dmortality              !! Dead biomass caused by mortality
159                                                                                       !! @tex $(gC m^{-2}) $@endtex
160    REAL(r_std), DIMENSION(npts)                            :: vigour                  !! Growth efficiency, an indicator of tree
161                                                                                       !! vitality, used to calculate mortality
162    REAL(r_std), DIMENSION(npts)                            :: availability            !! Mortality rate derived by growth
163                                                                                       !! efficiency @tex $(year^{-1})$ @endtex
164    INTEGER(i_std)                                          :: i, j,k,m                !! Indices
165
166!_ ================================================================================================================================
167
168    IF ( firstcall_gap ) THEN
169
170       firstcall_gap = .FALSE.
171
172    ENDIF
173
174    IF (printlev>=3) WRITE(numout,*) 'Entering gap',lpj_gap_const_mort
175
176    mortality(:,:) = zero
177
178    ! loop over #PFT
179    DO j = 2,nvm
180
181     IF (natural(j)) THEN
182 !! 1. Tree mortality
183
184       IF ( is_tree(j) ) THEN 
185
186          !! 1.1 Use growth efficiency or constant mortality?
187          IF ( .NOT.  lpj_gap_const_mort  ) THEN
188
189             !! 1.1.1 Estimate net biomass increment
190             !        To calculate growth efficiency mortality, first estimate net biomass increment by
191             !        subtracting turnover from last year's NPP.
192             WHERE ( PFTpresent(:,j) .AND. ( lm_lastyearmax(:,j) .GT. min_stomate ) )
193
194            !??! the following should be removed
195            ! note that npp_longterm is now actually longterm growth efficiency (NPP/LAI)
196            ! to be fair to deciduous trees
197            ! calculate net biomass increment
198             delta_biomass(:) = MAX( npp_longterm(:,j) - ( turnover_longterm(:,j,ileaf,icarbon) + &
199                  turnover_longterm(:,j,iroot,icarbon) + turnover_longterm(:,j,ifruit,icarbon) + & 
200                  turnover_longterm(:,j,isapabove,icarbon) + turnover_longterm(:,j,isapbelow,icarbon) ) ,zero)
201
202            !! 1.1.2 Calculate growth efficiency
203            !        Calculate growth efficiency by dividing net biomass increment by last year's
204            !        maximum LAI. (corresponding actually to the maximum LAI of the previous year)
205!JCMODIF
206!             vigour(:) = delta_biomass(:) / (lm_lastyearmax(:,j)*sla(j))
207             vigour(:) = delta_biomass(:) / (lm_lastyearmax(:,j)*sla_calc(:,j))
208!ENDJCMODIF
209
210             ELSEWHERE
211
212                vigour(:) = zero
213
214             ENDWHERE
215
216             !! 1.1.3 Calculate growth efficiency mortality rate
217             WHERE ( PFTpresent(:,j) )
218               
219                availability(:) = availability_fact(j) / ( un + ref_greff * vigour(:) )
220                ! Scale mortality by timesteps per year
221                mortality(:,j) = MAX(min_avail,availability(:))  * dt/one_year 
222
223             ENDWHERE
224
225          ELSE  ! .NOT. lpj_gap_const_mort
226
227             !! 1.2 Use constant mortality accounting for the residence time of each tree PFT
228             WHERE ( PFTpresent(:,j) )
229
230                mortality(:,j) = dt/(residence_time(j)*one_year)
231
232             ENDWHERE
233
234          ENDIF ! .NOT.  lpj_gap_const_mort
235
236          !! 1.3 Mortality in DGVM
237          !      If the long term NPP is zero, all trees are killed
238          !??! This is this only applied in the DGVM maybe in order to make the DGVM respond faster and thus make the vegetation dynamics more dynamic?
239          !??! the link here with lpj_kill.f90 is still not clear and so would leave to who especially working on this.
240          IF ( ok_dgvm ) THEN
241
242!             WHERE ( PFTpresent(:,j) .AND. ( npp_longterm(:,j) .LE. min_stomate ) )
243             WHERE ( PFTpresent(:,j) .AND. ( npp_longterm(:,j) .LT. (npp_longterm_init-un) ) )
244                mortality(:,j) = un
245
246             ENDWHERE
247
248          ENDIF
249
250          IF ( ok_dgvm .AND. (tmin_crit(j) .NE. undef) ) THEN
251             ! frost-sensitive PFTs
252             WHERE ( t2m_min_daily(:) .LT. tmin_crit(j) )
253                mortality(:,j) = MIN(un,(coldness_mort*(tmin_crit(j)-t2m_min_daily(:))+mortality(:,j) ) )
254             ENDWHERE
255          ENDIF
256
257          IF ( ok_dgvm .AND. leaf_tab(j)==1 .AND. pheno_type(j)==2) THEN
258              ! Treat the spring frost for broadleaf and summergreen vegetations
259              ! leaf_tab=broadleaf and pheno_typ=summergreen
260              DO i=1,npts
261                IF ( (Tmin_spring_time(i,j)>0) .AND. (Tmin_spring_time(i,j)<spring_days_max+1) ) THEN
262                   IF ( t2m_min_daily(i) .LT. frost_damage_limit ) THEN
263                      mortality(i,j) = MIN(un,(0.01*(frost_damage_limit-t2m_min_daily(i))* &
264                                       Tmin_spring_time(i,j)/spring_days_max+mortality(i,j) ) )
265                   END IF
266                END IF
267             END DO
268          ENDIF
269
270          !! 1.4 Update biomass and litter pools
271          !    Update biomass and litter pool after dying and transfer recently died biomass to litter
272         
273          DO m = 1,nelements
274             DO k = 1, nparts
275               
276                WHERE ( PFTpresent(:,j) )
277                   
278                   dmortality(:) =  mortality(:,j) * biomass(:,j,k,m)
279                   bm_to_litter(:,j,k,m) = bm_to_litter(:,j,k,m) + dmortality(:)
280                   biomass(:,j,k,m) = biomass(:,j,k,m) - dmortality(:)
281
282                ENDWHERE
283
284             ENDDO
285          END DO
286
287          !! 1.5 In case of dynamic vegetation, update tree individual density
288          IF ( ok_dgvm ) THEN
289
290             WHERE ( PFTpresent(:,j) )
291
292                ind(:,j) = ind(:,j) * ( un - mortality(:,j) )
293
294             ENDWHERE
295
296          ENDIF
297       ELSE 
298
299 !! 2. Grasses mortality
300
301          ! For grasses, if last year's NPP is very small (less than 10 gCm^{-2}year{-1})
302          ! the grasses completely die
303!          IF ( .NOT.ok_dgvm .AND. .NOT.lpj_gap_const_mort) THEN
304! JC comment: though natural(j) is defined before do we still need pasture here?
305!          IF ( ok_dgvm ) THEN
306          IF ( ok_dgvm .AND. natural(j) .AND. .NOT. pasture(j)) THEN
307
308!             WHERE ( PFTpresent(:,j) .AND. ( npp_longterm(:,j) .LE. min_stomate ) ) !npp_longterm_init ) )
309             WHERE ( PFTpresent(:,j) .AND. ( npp_longterm(:,j) .LT. (npp_longterm_init-un) ) )
310                mortality(:,j) = un
311
312             ENDWHERE
313
314          ENDIF
315
316             ! Update biomass and litter pools
317          DO m = 1,nelements
318             DO k = 1, nparts
319
320                WHERE ( PFTpresent(:,j) )
321
322                   dmortality(:) =  mortality(:,j) * biomass(:,j,k,m)
323
324                   bm_to_litter(:,j,k,m) = bm_to_litter(:,j,k,m) + dmortality(:)
325
326                   biomass(:,j,k,m) = biomass(:,j,k,m) - dmortality(:)
327
328                ENDWHERE
329
330             ENDDO
331          ENDDO
332
333          IF ( ok_dgvm ) THEN
334
335             WHERE ( PFTpresent(:,j) )
336
337                ind(:,j) = ind(:,j) * ( un - mortality(:,j) )
338 
339             ENDWHERE
340
341          ENDIF
342
343       ENDIF   !IF ( is_tree(j) )
344
345     ENDIF ! IF(natural(j))
346    ENDDO      !loop over pfts
347
348 !! 3. Write to history files
349
350    ! output in fraction of trees that dies/day.
351    mortality(:,:) = mortality(:,:) / dt
352
353    CALL xios_orchidee_send_field("mortality",mortality)
354
355    CALL histwrite_p (hist_id_stomate, 'MORTALITY', itime, &
356         mortality, npts*nvm, horipft_index)
357
358    IF (printlev>=4) WRITE(numout,*) 'Leaving gap'
359
360  END SUBROUTINE gap
361
362END MODULE lpj_gap
Note: See TracBrowser for help on using the repository browser.