source: branches/publications/ORCHIDEE_2.2_r7266/ORCHIDEE/src_stomate/lpj_gap.f90 @ 7541

Last change on this file since 7541 was 7541, checked in by fabienne.maignan, 2 years ago
  1. Zhang publication on coupling factor
File size: 14.7 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: svn://forge.ipsl.jussieu.fr/orchidee/branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate/lpj_gap.f90 $
28!! $Date: 2017-06-28 16:04:50 +0200 (Wed, 28 Jun 2017) $
29!! $Revision: 4470 $
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, t2m_min_daily, Tmin_spring_time, &
120       biomass, ind, bm_to_litter, mortality )
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
152    !! 0.4 Local variables
153
154    REAL(r_std), DIMENSION(npts)                            :: delta_biomass           !! Net biomass increase for the previous
155                                                                                       !! year @tex $(gC m^{-2} year^{-1})$ @endtex
156    REAL(r_std), DIMENSION(npts)                            :: dmortality              !! Dead biomass caused by mortality
157                                                                                       !! @tex $(gC m^{-2}) $@endtex
158    REAL(r_std), DIMENSION(npts)                            :: vigour                  !! Growth efficiency, an indicator of tree
159                                                                                       !! vitality, used to calculate mortality
160    REAL(r_std), DIMENSION(npts)                            :: availability            !! Mortality rate derived by growth
161                                                                                       !! efficiency @tex $(year^{-1})$ @endtex
162    INTEGER(i_std)                                          :: i, j,k,m                !! Indices
163
164!_ ================================================================================================================================
165
166    IF ( firstcall_gap ) THEN
167
168       firstcall_gap = .FALSE.
169
170    ENDIF
171
172    IF (printlev>=3) WRITE(numout,*) 'Entering gap',lpj_gap_const_mort
173
174    mortality(:,:) = zero
175
176    ! loop over #PFT
177    DO j = 2,nvm
178
179 !! 1. Tree mortality
180
181       IF ( is_tree(j) ) THEN 
182
183          !! 1.1 Use growth efficiency or constant mortality?
184          IF ( .NOT.  lpj_gap_const_mort  ) THEN
185
186             !! 1.1.1 Estimate net biomass increment
187             !        To calculate growth efficiency mortality, first estimate net biomass increment by
188             !        subtracting turnover from last year's NPP.
189             WHERE ( PFTpresent(:,j) .AND. ( lm_lastyearmax(:,j) .GT. min_stomate ) )
190
191            !??! the following should be removed
192            ! note that npp_longterm is now actually longterm growth efficiency (NPP/LAI)
193            ! to be fair to deciduous trees
194            ! calculate net biomass increment
195             delta_biomass(:) = MAX( npp_longterm(:,j) - ( turnover_longterm(:,j,ileaf,icarbon) + &
196                  turnover_longterm(:,j,iroot,icarbon) + turnover_longterm(:,j,ifruit,icarbon) + & 
197                  turnover_longterm(:,j,isapabove,icarbon) + turnover_longterm(:,j,isapbelow,icarbon) ) ,zero)
198
199            !! 1.1.2 Calculate growth efficiency
200            !        Calculate growth efficiency by dividing net biomass increment by last year's
201            !        maximum LAI. (corresponding actually to the maximum LAI of the previous year)
202             vigour(:) = delta_biomass(:) / (lm_lastyearmax(:,j)*sla(j))
203
204             ELSEWHERE
205
206                vigour(:) = zero
207
208             ENDWHERE
209
210             !! 1.1.3 Calculate growth efficiency mortality rate
211             WHERE ( PFTpresent(:,j) )
212               
213                availability(:) = availability_fact(j) / ( un + ref_greff * vigour(:) )
214                ! Scale mortality by timesteps per year
215                mortality(:,j) = MAX(min_avail,availability(:))  * dt/one_year 
216
217             ENDWHERE
218
219          ELSE  ! .NOT. lpj_gap_const_mort
220
221             !! 1.2 Use constant mortality accounting for the residence time of each tree PFT
222             WHERE ( PFTpresent(:,j) )
223
224                mortality(:,j) = dt/(residence_time(j)*one_year)
225
226             ENDWHERE
227
228          ENDIF ! .NOT.  lpj_gap_const_mort
229
230          !! 1.3 Mortality in DGVM
231          !      If the long term NPP is zero, all trees are killed
232          !??! 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?
233          !??! the link here with lpj_kill.f90 is still not clear and so would leave to who especially working on this.
234          IF ( ok_dgvm ) THEN
235
236             WHERE ( PFTpresent(:,j) .AND. ( npp_longterm(:,j) .LE. min_stomate ) )
237
238                mortality(:,j) = un
239
240             ENDWHERE
241
242          ENDIF
243
244          IF ( ok_dgvm .AND. (tmin_crit(j) .NE. undef) ) THEN
245             ! frost-sensitive PFTs
246             WHERE ( t2m_min_daily(:) .LT. tmin_crit(j) )
247                mortality(:,j) = MIN(un,(coldness_mort*(tmin_crit(j)-t2m_min_daily(:))+mortality(:,j) ) )
248             ENDWHERE
249          ENDIF
250
251          IF ( ok_dgvm .AND. leaf_tab(j)==1 .AND. pheno_type(j)==2) THEN
252             ! Treat the spring frost for broadleaf and summergreen vegetations
253             ! leaf_tab=broadleaf and pheno_typ=summergreen
254             DO i=1,npts
255                IF ( (Tmin_spring_time(i,j)>0) .AND. (Tmin_spring_time(i,j)<spring_days_max+1) ) THEN
256                   IF ( t2m_min_daily(i) .LT. frost_damage_limit ) THEN
257                      mortality(i,j) = MIN(un,(0.01*(frost_damage_limit-t2m_min_daily(i))* &
258                           Tmin_spring_time(i,j)/spring_days_max+mortality(i,j) ) )
259                   END IF
260                END IF
261             END DO
262          END IF
263       
264
265          !! 1.4 Update biomass and litter pools
266          !    Update biomass and litter pool after dying and transfer recently died biomass to litter
267         
268          DO m = 1,nelements
269             DO k = 1, nparts
270               
271                WHERE ( PFTpresent(:,j) )
272                   
273                   dmortality(:) =  mortality(:,j) * biomass(:,j,k,m)
274                   bm_to_litter(:,j,k,m) = bm_to_litter(:,j,k,m) + dmortality(:)
275                   biomass(:,j,k,m) = biomass(:,j,k,m) - dmortality(:)
276
277                ENDWHERE
278
279             ENDDO
280          END DO
281
282          !! 1.5 In case of dynamic vegetation, update tree individual density
283          IF ( ok_dgvm ) THEN
284
285             WHERE ( PFTpresent(:,j) )
286
287                ind(:,j) = ind(:,j) * ( un - mortality(:,j) )
288
289             ENDWHERE
290
291          ENDIF
292       ELSE 
293
294 !! 2. Grasses mortality
295
296          ! For grasses, if last year's NPP is very small (less than 10 gCm^{-2}year{-1})
297          ! the grasses completely die
298          IF ( .NOT.ok_dgvm .AND. .NOT.lpj_gap_const_mort) THEN
299
300             WHERE ( PFTpresent(:,j) .AND. ( npp_longterm(:,j) .LE. npp_longterm_init ) )
301
302                mortality(:,j) = un
303
304             ENDWHERE
305
306             ! Update biomass and litter pools
307             DO m = 1,nelements
308                DO k = 1, nparts
309
310                   WHERE ( PFTpresent(:,j) )
311                     
312                      dmortality(:) =  mortality(:,j) * biomass(:,j,k,m)
313                     
314                      bm_to_litter(:,j,k,m) = bm_to_litter(:,j,k,m) + dmortality(:)
315                     
316                      biomass(:,j,k,m) = biomass(:,j,k,m) - dmortality(:)
317                     
318                   ENDWHERE
319
320                ENDDO
321             END DO
322             
323          ENDIF
324
325       ENDIF   !IF ( is_tree(j) )
326
327    ENDDO      !loop over pfts
328
329 !! 3. Write to history files
330
331    ! output in fraction of trees that dies/day.
332    mortality(:,:) = mortality(:,:) / dt
333
334    CALL xios_orchidee_send_field("mortality",mortality)
335
336    CALL histwrite_p (hist_id_stomate, 'MORTALITY', itime, &
337         mortality, npts*nvm, horipft_index)
338
339    IF (printlev>=4) WRITE(numout,*) 'Leaving gap'
340
341  END SUBROUTINE gap
342
343END MODULE lpj_gap
Note: See TracBrowser for help on using the repository browser.