source: tags/ORCHIDEE_1_9_5_2/ORCHIDEE/src_stomate/lpj_crown.f90 @ 404

Last change on this file since 404 was 186, checked in by martial.mancip, 13 years ago

First steps to DGVM for Merge version. This won't compile. I lock the trunk. Martial.

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