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