source: branches/ORCHIDEE_EXT/ORCHIDEE/src_stomate/lpj_kill.f90 @ 64

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

Import first version of ORCHIDEE_EXT

File size: 6.0 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, &
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*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    ! conversion of biomass to litter (gC/(m**2 of ground)) / day
75    REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)    :: bm_to_litter
76
77    ! 0.3 local
78
79    ! indices
80    INTEGER(i_std)                                             :: j,m
81    ! bookkeeping
82    LOGICAL, DIMENSION(npts)                                  :: was_killed
83
84    ! =========================================================================
85
86    IF (bavard.GE.3) WRITE(numout,*) 'Entering kill'
87
88    DO j = 2,nvm
89
90       was_killed(:) = .FALSE.
91
92       ! only kill natural PFTs
93
94       IF ( natural(j) ) THEN
95
96          ! kill present plants if number of individuals or last year's leaf
97          ! mass is close to zero.
98          ! the "was_killed" business is necessary for a more efficient code on the VPP
99
100          WHERE ( PFTpresent(:,j) .AND. &
101               ( ( ind(:,j) .LT. min_stomate ) .OR. &
102               ( lm_lastyearmax(:,j) .LT. min_stomate ) ) )
103
104             was_killed(:) = .TRUE.
105
106          ENDWHERE
107
108          IF ( ANY( was_killed(:) ) ) THEN
109
110             WHERE ( was_killed(:) )
111
112                ind(:,j) = 0.0
113
114                bm_to_litter(:,j,ileaf) = bm_to_litter(:,j,ileaf) + biomass(:,j,ileaf)
115                bm_to_litter(:,j,isapabove) = bm_to_litter(:,j,isapabove) + biomass(:,j,isapabove)
116                bm_to_litter(:,j,isapbelow) = bm_to_litter(:,j,isapbelow) + biomass(:,j,isapbelow)
117                bm_to_litter(:,j,iheartabove) = bm_to_litter(:,j,iheartabove) + &
118                     biomass(:,j,iheartabove)
119                bm_to_litter(:,j,iheartbelow) = bm_to_litter(:,j,iheartbelow) + &
120                     biomass(:,j,iheartbelow)
121                bm_to_litter(:,j,iroot) = bm_to_litter(:,j,iroot) + biomass(:,j,iroot)
122                bm_to_litter(:,j,ifruit) = bm_to_litter(:,j,ifruit) + biomass(:,j,ifruit)
123                bm_to_litter(:,j,icarbres) = bm_to_litter(:,j,icarbres) + biomass(:,j,icarbres)
124
125                biomass(:,j,ileaf) = 0.0
126                biomass(:,j,isapabove) = 0.0
127                biomass(:,j,isapbelow) = 0.0
128                biomass(:,j,iheartabove) = 0.0
129                biomass(:,j,iheartbelow) = 0.0
130                biomass(:,j,iroot) = 0.0
131                biomass(:,j,ifruit) = 0.0
132                biomass(:,j,icarbres) = 0.0
133
134                PFTpresent(:,j) = .FALSE.
135
136                cn_ind(:,j) = 0.0
137
138                senescence(:,j) = .FALSE.
139
140
141                age(:,j) = 0.0
142
143                when_growthinit(:,j) = undef
144
145                everywhere(:,j) = 0.0
146
147                veget(:,j) = 0.0
148
149                veget_max(:,j) = 0.0
150
151                RIP_time(:,j) = 0.0
152
153             ENDWHERE   ! number of individuals very low
154
155             DO m = 1, nleafages
156
157                WHERE ( was_killed(:) )
158
159                   leaf_age(:,j,m) = 0.0 
160                   leaf_frac(:,j,m) = 0.0 
161
162                ENDWHERE
163
164             ENDDO
165
166             IF ( bavard .GE. 2 ) THEN
167
168                WRITE(numout,*) 'kill: eliminated ',PFT_name(j)
169                WRITE(numout,*) '  at ',COUNT( was_killed(:) ),' points after '//whichroutine
170
171             ENDIF
172
173          ENDIF     ! PFT must be killed at at least one place
174
175       ENDIF       ! PFT is natural
176
177    ENDDO         ! loop over PFTs
178
179    IF (bavard.GE.4) WRITE(numout,*) 'Leaving kill'
180
181  END SUBROUTINE kill
182
183END MODULE lpj_kill
Note: See TracBrowser for help on using the repository browser.