source: branches/ORCHIDEE_EXT/ORCHIDEE/src_stomate/lpj_crown.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: 5.5 KB
Line 
1! $Header: /home/ssipsl/CVSREP/ORCHIDEE/src_stomate/lpj_crown.f90,v 1.12 2009/01/06 15:01:25 ssipsl Exp $
2! IPSL (2006)
3!  This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
4!-
5MODULE lpj_crown
6  !---------------------------------------------------------------------
7  !- calculate individual crown area from stem mass.
8  !- SZ, I've put the woodmass calculation out of this routine
9  !      because after the very first establishment, woodmass
10  !      could not be calculated here as veget_max = zero and
11  !      d_ind not known...
12  !---------------------------------------------------------------------
13  USE ioipsl
14  USE stomate_data
15  USE constantes
16  USE pft_parameters
17  !-
18  IMPLICIT NONE
19  !-
20  ! private & public routines
21  !-
22  PRIVATE
23  PUBLIC crown
24  !-
25CONTAINS
26  !-
27  !===
28  !-
29  SUBROUTINE crown &
30       &  (npts, PFTpresent, ind, biomass, woodmass_ind, veget_max, cn_ind, height)
31    !---------------------------------------------------------------------
32    ! 0 declarations
33    !-
34    ! 0.1 input
35    !-
36    ! Domain size
37    INTEGER(i_std),INTENT(in) :: npts
38    ! Is pft there
39    LOGICAL,DIMENSION(npts,nvm),INTENT(in) :: PFTpresent
40    ! density of individuals (1/(m**2 of ground))
41    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: ind
42    ! biomass (gC/(m**2 of ground))
43    REAL(r_std),DIMENSION(npts,nvm,nparts),INTENT(in) :: biomass
44    ! woodmass of the individual, needed to calculate crownarea in lpj_crownarea
45    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: woodmass_ind
46    !-
47    ! 0.2 modified fields
48    !-
49    ! "maximal" coverage fraction of a PFT (LAI -> infinity) on ground
50    !-
51    REAL(r_std),DIMENSION(npts,nvm),INTENT(inout) :: veget_max
52    !-
53    ! 0.3 output
54    !-
55    ! crown area (m**2) per ind.
56    !-
57    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: cn_ind
58    !-
59    ! height of vegetation (m)
60    !-
61    REAL(r_std),DIMENSION(npts,nvm),INTENT(inout) :: height
62    !-
63    ! 0.4 local
64    !-
65    ! wood mass of an individual
66    !-
67!!$    REAL(r_std),DIMENSION(npts) :: woodmass
68    !-
69    ! index
70    !-
71    INTEGER(i_std) :: j
72    !-
73    ! stem diameter
74    !-
75    REAL(r_std),DIMENSION(npts) :: dia
76    REAL(r_std),DIMENSION(nvm) :: height_presc_12
77    !---------------------------------------------------------------------
78    !-
79    ! 1 initializations
80    !-
81    ! 1.1 check if DGVM activated
82    !-
83    IF (.NOT.control%ok_dgvm .AND. lpj_gap_const_mort) THEN
84       STOP 'crown: not to be called with static vegetation.'
85    ENDIF
86    !-
87    ! 1.2 initialize output to zero
88    !-
89    cn_ind(:,:) = zero
90    ! no convertion, just cop
91    height_presc_12(1:nvm) = height_presc(1:nvm)
92    !-
93    ! 2 calculate (or prescribe) crown area
94    !-
95    DO j = 2,nvm
96       IF (tree(j)) THEN
97          !-----
98          !---- 2.1 trees
99          !-----
100          IF (natural(j)) THEN
101             !------ 2.1.1 natural
102             !WHERE (PFTpresent(:,j) .AND.ind(:,j).GT.min_stomate)
103             WHERE (PFTpresent(:,j) .AND.woodmass_ind(:,j).GT.min_stomate)
104!!$SZ note that woodmass_ind needs to be defined on the individual, hence
105!!$ biomass*veget_max/ind, not as stated here, correction MERGE
106!!$!-------- 2.1.1.1 calculate individual wood mass
107!!$          woodmass(:) = &
108!!$ &         (biomass(:,j,isapabove)+biomass(:,j,isapbelow) &
109!!$ &         +biomass(:,j,iheartabove)+biomass(:,j,iheartbelow))/ind(:,j)
110                !-------- 2.1.1.2 stem diameter (pipe model)
111!!$          dia(:) = (woodmass(:)/(pipe_density*pi/4.*pipe_tune2)) &
112                dia(:) = (woodmass_ind(:,j)/(pipe_density*pi/4.*pipe_tune2)) &
113                     &                **(1./(2.+pipe_tune3))
114                !-------- 2.1.1.3 height
115                height(:,j) = pipe_tune2*(dia(:)**pipe_tune3)
116!!$SZ: The constraint on height has nothing to do with LPJ (for that purpose there's dia_max
117!!$ cannot see why this is necessary - it also blurrs the output, hence I leave it commented
118!!$                WHERE (height(:,j) > height_presc_12(j))
119!!$                   dia(:) = (height_presc_12(j)/pipe_tune2)**(1./pipe_tune3)
120!!$                   height(:,j) = height_presc_12(j)
121!!$                ENDWHERE
122                !-------- 2.1.1.4 crown area: for large truncs, crown area cannot
123                !--------         exceed a certain value, prescribed through maxdia.
124                cn_ind(:,j) = pipe_tune1*MIN(dia(:),maxdia(j))**pipe_tune_exp_coeff
125             ENDWHERE
126          ELSE
127             !------ 2.1.2 tree is agricultural - stop
128             STOP 'crown: cannot treat agricultural trees.'
129          ENDIF
130       ELSE
131          !-----
132          !---- 2.2 grasses
133          !-----
134          WHERE (PFTpresent(:,j))
135             !------ 2.2.1 an "individual" is 1 m**2 of grass
136             cn_ind(:,j) = un
137          ENDWHERE
138       ENDIF
139       !---
140       !-- 2.3 recalculate vegetation cover if natural
141       !       ind and cn_ind are 0 if not present
142       !---
143!!$SZ: since now all state variables are defined on veget_max it is very
144!!$ dangerous to change this several times in stomate_lpj, as then GPP, turnover and allocated
145!!$ biomass are not defined on the same space! Hence, veget_max is now kept constant
146!!$ and updated at the end of stomate_lpj in lpj_cover.f90
147!!$ Eventually, this routine should only be called once at the beginning and the end of stomate_lpj
148!!$ or prefereably cn_ind made a saved state variable!
149!!$    IF (natural(j).AND.control%ok_dgvm) THEN
150!!$      veget_max(:,j) = ind(:,j) * cn_ind(:,j)
151!!$    ENDIF
152    ENDDO
153    !-------------------
154  END SUBROUTINE crown
155  !-
156  !===
157  !-
158END MODULE lpj_crown
Note: See TracBrowser for help on using the repository browser.