source: branches/ORCHIDEE_EXT/ORCHIDEE/src_stomate/lpj_kill.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: 7.2 KB
Line 
1! kills pfts that obviously fare badly
2!
3! $Header: /home/ssipsl/CVSREP/ORCHIDEE/src_stomate/lpj_kill.f90,v 1.8 2009/01/06 15:01:25 ssipsl Exp $
4! IPSL (2006)
5!  This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
6!
7MODULE lpj_kill
8
9  ! modules used:
10
11  USE ioipsl
12  USE stomate_data
13  USE pft_parameters
14  USE constantes
15
16  IMPLICIT NONE
17
18  ! private & public routines
19
20  PRIVATE
21  PUBLIC kill
22
23CONTAINS
24
25  SUBROUTINE kill (npts, whichroutine, lm_lastyearmax, &
26       ind, PFTpresent, cn_ind, biomass, senescence, RIP_time, &
27       lai, age, leaf_age, leaf_frac, npp_longterm, &
28       when_growthinit, everywhere, veget, veget_max, bm_to_litter)
29
30    !
31    ! 0 declarations
32    !
33
34    ! 0.1 input
35
36    ! Domain size
37    INTEGER(i_std), INTENT(in)                                       :: npts
38    ! message
39    CHARACTER(LEN=10), INTENT(in)                                  :: whichroutine
40    ! last year's maximum leaf mass, for each PFT (gC/(m**2 of ground))
41    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)              :: lm_lastyearmax
42
43    ! 0.2 modified fields
44
45    ! Number of individuals / m**2
46    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: ind
47    ! Is pft there
48    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: PFTpresent
49    ! crown area of individuals (m**2)
50    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: cn_ind
51    ! biomass (gC/(m**2 of ground))
52    REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)    :: biomass
53    ! is the plant senescent? (only for deciduous trees - carbohydrate reserve)
54    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: senescence
55    ! How much time ago was the PFT eliminated for the last time (y)
56    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: RIP_time
57    ! leaf area index OF AN INDIVIDUAL PLANT
58    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)           :: lai
59    ! mean age (years)
60    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: age
61    ! leaf age (days)
62    REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout) :: leaf_age
63    ! fraction of leaves in leaf age class
64    REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout) :: leaf_frac
65    ! how many days ago was the beginning of the growing season
66    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: when_growthinit
67    ! is the PFT everywhere in the grid box or very localized (after its introduction)
68    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: everywhere
69    ! fractional coverage on ground, taking into
70    !   account LAI (=grid-scale fpc)
71    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: veget
72    ! "maximal" coverage fraction of a PFT (LAI -> infinity) on ground
73    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: veget_max
74    ! "long term" net primary productivity (gC/(m**2 of ground)/year)
75    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)           :: npp_longterm 
76    ! conversion of biomass to litter (gC/(m**2 of ground)) / day
77    REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)    :: bm_to_litter
78
79    ! 0.3 local
80
81    ! indices
82    INTEGER(i_std)                                             :: j,m
83    ! bookkeeping
84    LOGICAL, DIMENSION(npts)                                  :: was_killed
85
86    ! =========================================================================
87
88    IF (bavard.GE.3) WRITE(numout,*) 'Entering kill'
89
90    DO j = 2,nvm
91
92       was_killed(:) = .FALSE.
93
94       ! only kill natural PFTs
95
96       IF ( natural(j) ) THEN
97
98          ! kill present plants if number of individuals or last year's leaf
99          ! mass is close to zero.
100          ! the "was_killed" business is necessary for a more efficient code on the VPP
101
102          IF ( control%ok_dgvm ) THEN
103             WHERE ( PFTpresent(:,j) .AND. &
104                  ( ( ind(:,j) .LT. min_stomate ) .OR. &
105                  ( lm_lastyearmax(:,j) .LT. min_stomate ) ) )
106             
107             was_killed(:) = .TRUE.
108             
109             ENDWHERE
110         
111          ELSE
112             WHERE ( PFTpresent(:,j) .AND. & 
113                  (biomass(:,j,icarbres) .LE.zero .OR. & 
114                  biomass(:,j,iroot).LT.-min_stomate .OR. biomass(:,j,ileaf).LT.-min_stomate ).AND. & 
115                  ind(:,j).GT. zero)
116
117                was_killed(:) = .TRUE.
118
119             ENDWHERE
120
121             IF(.NOT.tree(j).AND..NOT.lpj_gap_const_mort)THEN
122                WHERE ( was_killed(:) )
123
124                   npp_longterm(:,j)=500.
125
126                ENDWHERE
127             ENDIF
128
129          ENDIF
130
131          IF ( ANY( was_killed(:) ) ) THEN
132
133             WHERE ( was_killed(:) )
134
135                bm_to_litter(:,j,ileaf) = bm_to_litter(:,j,ileaf) + biomass(:,j,ileaf)
136                bm_to_litter(:,j,isapabove) = bm_to_litter(:,j,isapabove) + biomass(:,j,isapabove)
137                bm_to_litter(:,j,isapbelow) = bm_to_litter(:,j,isapbelow) + biomass(:,j,isapbelow)
138                bm_to_litter(:,j,iheartabove) = bm_to_litter(:,j,iheartabove) + &
139                     biomass(:,j,iheartabove)
140                bm_to_litter(:,j,iheartbelow) = bm_to_litter(:,j,iheartbelow) + &
141                     biomass(:,j,iheartbelow)
142                bm_to_litter(:,j,iroot) = bm_to_litter(:,j,iroot) + biomass(:,j,iroot)
143                bm_to_litter(:,j,ifruit) = bm_to_litter(:,j,ifruit) + biomass(:,j,ifruit)
144                bm_to_litter(:,j,icarbres) = bm_to_litter(:,j,icarbres) + biomass(:,j,icarbres)
145
146                biomass(:,j,ileaf) = zero
147                biomass(:,j,isapabove) = zero
148                biomass(:,j,isapbelow) = zero
149                biomass(:,j,iheartabove) = zero
150                biomass(:,j,iheartbelow) = zero
151                biomass(:,j,iroot) = zero
152                biomass(:,j,ifruit) = zero
153                biomass(:,j,icarbres) = zero
154
155             ENDWHERE   ! number of individuals very low
156
157             IF (control%ok_dgvm) THEN
158
159                WHERE ( was_killed(:) )
160                   PFTpresent(:,j) = .FALSE.
161
162                   veget_max(:,j) = zero
163                   
164                   RIP_time(:,j) = zero
165
166                ENDWHERE  ! number of individuals very low
167
168             ENDIF
169
170             WHERE ( was_killed(:) )
171
172                ind(:,j) = zero
173
174                cn_ind(:,j) = zero
175
176                senescence(:,j) = .FALSE.
177
178                age(:,j) = zero
179
180                ! SZ: why undef ??? this causes a delay in reestablishment
181                !when_growthinit(:,j) = undef
182                when_growthinit(:,j) = large_value 
183
184                everywhere(:,j) = zero
185
186                veget(:,j) = zero
187
188             ENDWHERE   ! number of individuals very low
189
190             DO m = 1, nleafages
191
192                WHERE ( was_killed(:) )
193
194                   leaf_age(:,j,m) = zero 
195                   leaf_frac(:,j,m) = zero 
196
197                ENDWHERE
198
199             ENDDO
200
201             IF ( bavard .GE. 2 ) THEN
202
203                WRITE(numout,*) 'kill: eliminated ',PFT_name(j)
204                WRITE(numout,*) '  at ',COUNT( was_killed(:) ),' points after '//whichroutine
205
206             ENDIF
207
208          ENDIF     ! PFT must be killed at at least one place
209
210       ENDIF       ! PFT is natural
211
212    ENDDO         ! loop over PFTs
213
214    IF (bavard.GE.4) WRITE(numout,*) 'Leaving kill'
215
216  END SUBROUTINE kill
217
218END MODULE lpj_kill
Note: See TracBrowser for help on using the repository browser.