source: branches/ORCHIDEE_EXT/ORCHIDEE/src_stomate/lpj_gap.f90 @ 257

Last change on this file since 257 was 257, checked in by didier.solyga, 13 years ago

Externalized version merged with the trunk

File size: 8.0 KB
Line 
1! gap routine - place for new plants
2!
3! Death rate of trees is estimated by evaluating their vigour (based on npp).
4! For large availabilities, lifetime is 50 years (!?).
5! Age of stands is not considered, although availability death rate should probably
6! depend on age.
7!
8! $Header: /home/ssipsl/CVSREP/ORCHIDEE/src_stomate/lpj_gap.f90,v 1.10 2009/01/06 15:01:25 ssipsl Exp $
9! IPSL (2006)
10!  This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
11!
12MODULE lpj_gap
13
14  ! modules used:
15
16  USE ioipsl
17  USE stomate_data
18  USE pft_parameters
19  USE parallel
20  USE constantes
21
22  IMPLICIT NONE
23
24  ! private & public routines
25
26  PRIVATE
27  PUBLIC gap,gap_clear
28
29  ! first call
30  LOGICAL, SAVE                                           :: firstcall = .TRUE.
31
32CONTAINS
33
34
35  SUBROUTINE gap_clear
36    firstcall = .TRUE.
37  END SUBROUTINE gap_clear
38
39  SUBROUTINE gap (npts, dt, &
40       npp_longterm, turnover_longterm, lm_lastyearmax, &
41       PFTpresent, biomass, ind, bm_to_litter, mortality)
42
43    !
44    ! 0 declarations
45    !
46
47    ! 0.1 input
48
49    ! Domain size
50    INTEGER(i_std), INTENT(in)                                     :: npts
51    ! Time step (days)
52    REAL(r_std), INTENT(in)                                  :: dt
53    ! "long term" net primary productivity (gC/(m**2 of ground)/year)
54    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: npp_longterm
55    ! "long term" turnover rate (gC/(m**2 of ground)/year)
56    REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(in)     :: turnover_longterm
57    ! last year's maximum leaf mass, for each PFT (gC/(m**2 of ground))
58    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: lm_lastyearmax
59
60    ! 0.2 modified fields
61
62    ! Is pft there
63    LOGICAL, DIMENSION(npts,nvm), INTENT(in)            :: PFTpresent
64    ! biomass (gC/(m**2 of ground))
65    REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)  :: biomass
66    ! Number of individuals / (m**2 of ground)
67    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)         :: ind
68    ! biomass taken away (gC/(m**2 of ground))
69    REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)  :: bm_to_litter
70    ! mortality (fraction of trees that is dying per time step), per day in history file
71    REAL(r_std), DIMENSION(npts,nvm),INTENT(out)             :: mortality
72
73    ! 0.3 local
74
75    ! biomass increase
76    REAL(r_std), DIMENSION(npts)                             :: delta_biomass
77    ! biomass increase
78    REAL(r_std), DIMENSION(npts)                             :: dmortality
79    ! vigour
80    REAL(r_std), DIMENSION(npts)                             :: vigour
81    ! natural availability, based on vigour
82    REAL(r_std), DIMENSION(npts)                             :: availability
83    ! indices
84    INTEGER(i_std)                                           :: j,k,m
85    REAL(r_std) :: ref_greff
86
87    ! =========================================================================
88
89    IF ( firstcall ) THEN
90
91       firstcall = .FALSE.
92
93    ENDIF
94
95    IF (bavard.GE.3) WRITE(numout,*) 'Entering gap',lpj_gap_const_mort
96
97    mortality(:,:) = zero
98
99    ref_greff =  0.035
100
101    DO j = 2,nvm
102
103       ! only trees
104
105       IF ( tree(j) ) THEN
106
107          !
108          ! 1 determine availability
109          !
110
111          IF ( .NOT.  lpj_gap_const_mort  ) THEN
112
113             !
114             ! 1.1 original formulation: mortality depends on vigour
115             !
116
117             WHERE ( PFTpresent(:,j) .AND. ( lm_lastyearmax(:,j) .GT. min_stomate ) )
118
119!SZ 080806, changed to LPJ formulation according to Smith et al., 2001
120
121                ! how much did the tree grow per year?
122
123!!$                delta_biomass(:) = &
124!!$                     MAX( npp_longterm(:,j) - ( turnover_longterm(:,j,ileaf) + &
125!!$                     turnover_longterm(:,j,iroot) + turnover_longterm(:,j,ifruit) ), &
126!!$                     0._r_std )
127
128            ! note that npp_longterm is now actually longterm growth efficiency (NPP/LAI)
129            ! to be fair to deciduous trees
130             delta_biomass(:) = MAX( npp_longterm(:,j) - ( turnover_longterm(:,j,ileaf) + &
131                  turnover_longterm(:,j,iroot) + turnover_longterm(:,j,ifruit) + & 
132                  turnover_longterm(:,j,isapabove) + turnover_longterm(:,j,isapbelow) ) ,zero)
133
134                ! scale this to the leaf surface of the tree
135!!$                vigour(:) = delta_biomass(:) / (lm_lastyearmax(:,j)*sla(j)) / vigour_coeff
136             vigour(:) = delta_biomass(:) / (lm_lastyearmax(:,j)*sla(j))
137
138             ELSEWHERE
139
140                vigour(:) = 0.0
141
142             ENDWHERE
143
144             WHERE ( PFTpresent(:,j) )
145
146                ! note that availability is never above 0.02, i.e. lifetime of 50 years when very
147                ! low vigour.
148
149!SZ 080806, changed to LPJ formulation according to Smith et al., 2001
150! tuned maximal mortality to 0.05 to get realistic range of avergage age to get ~100 years at GREFF=100
151! for the range of modelled annual NPP
152!!$                availability(:) = min_avail / ( 1.+vigour(:)/vigour_ref )
153                availability(:) = 0.1 / ( 1.+ref_greff*vigour(:) )
154
155                ! Mortality (fraction per time step).
156                ! In the original DGVM, mortality was set to zero if there was strong fire
157                ! perturbation.
158                ! This has been de-activated since the npp is not influenced by fire,
159                ! as opposed to the original DGVM. Instead, mortality is simply
160                ! equal to the availability, modulated by the time step.
161                ! Exact formulation: mor = 1. - ( 1. - availability ) ** (dt/one_year)
162                ! approximation ok as availability < 0.02 << 1
163
164                mortality(:,j) = MAX(min_avail,availability(:))  * dt/one_year 
165!!$                mortality(:,j) = availability(:) * dt/one_year
166
167             ENDWHERE
168
169          ELSE
170
171             !
172             ! 1.2 Alternative version: Constant mortality
173             !
174
175             WHERE ( PFTpresent(:,j) )
176
177                mortality(:,j) = dt/(residence_time(j)*one_year)
178
179             ENDWHERE
180
181          ENDIF
182
183          !
184          ! 2 Special for the DGVM:
185          !   mortality is one if npp is zero or negative.
186          !
187
188          IF ( control%ok_dgvm ) THEN
189
190             WHERE ( PFTpresent(:,j) .AND. ( npp_longterm(:,j) .LE. min_stomate ) )
191
192                mortality(:,j) = 1.
193
194             ENDWHERE
195
196          ENDIF
197
198          !
199          ! 3 update biomass, create litter
200          !
201
202          DO k = 1, nparts
203
204             WHERE ( PFTpresent(:,j) )
205
206                dmortality(:) =  mortality(:,j) * biomass(:,j,k)
207                bm_to_litter(:,j,k) = bm_to_litter(:,j,k) + dmortality(:)
208               
209                biomass(:,j,k) = biomass(:,j,k) - dmortality(:)
210
211             ENDWHERE
212
213          ENDDO
214
215          !
216          ! 4 update number of individuals
217          !
218
219!SZ 080806, allow changing density in static case when mortality is dynamic
220          IF ( control%ok_dgvm .OR. .NOT.lpj_gap_const_mort) THEN
221
222             WHERE ( PFTpresent(:,j) )
223
224                ind(:,j) = ind(:,j) * ( un - mortality(:,j) )
225
226             ENDWHERE
227
228          ENDIF
229
230       ELSE
231
232          IF ( .NOT.control%ok_dgvm .AND. .NOT.lpj_gap_const_mort) THEN
233
234             WHERE ( PFTpresent(:,j) .AND. ( npp_longterm(:,j) .LE. 10. ) )
235
236                mortality(:,j) = 1.
237
238             ENDWHERE
239             DO k = 1, nparts
240
241                WHERE ( PFTpresent(:,j) )
242
243                   dmortality(:) =  mortality(:,j) * biomass(:,j,k)
244                   
245                   bm_to_litter(:,j,k) = bm_to_litter(:,j,k) + dmortality(:)
246                   
247                   biomass(:,j,k) = biomass(:,j,k) - dmortality(:)
248
249                ENDWHERE
250             ENDDO
251             
252          ENDIF
253
254       ENDIF       ! only trees
255
256    ENDDO         ! loop over pfts
257
258    !
259    ! 5 history
260    !
261
262    ! output in fraction of trees that dies/day.
263    ! exact formulation: 1. - ( 1. - mortality ) ** (1./dt)
264    mortality = mortality / dt
265
266    CALL histwrite (hist_id_stomate, 'MORTALITY', itime, &
267         mortality, npts*nvm, horipft_index)
268
269    IF (bavard.GE.4) WRITE(numout,*) 'Leaving gap'
270
271  END SUBROUTINE gap
272
273END MODULE lpj_gap
Note: See TracBrowser for help on using the repository browser.