source: tags/ORCHIDEE_4_1/ORCHIDEE/src_stomate/lpj_crown.f90 @ 7852

Last change on this file since 7852 was 7273, checked in by sebastiaan.luyssaert, 3 years ago

Contributes to tickets #633 and #653. Adding a period for unmanaged forest to decay after reaching the min density. Made crown dimensions PFT-dependent

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 9.2 KB
Line 
1! =================================================================================================================================
2! MODULE       : lpj_crown
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2006)
7!                This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF       Calculate individual crown area from stem mass
10!!
11!! \n DESCRIPTION : Calculating crown area of individual tree by diameter and tree height
12!!
13!! REFERENCE(S) :
14!! - Smith, B., I. C. Prentice, et al. (2001), Representation of vegetation
15!!  dynamics in the modelling of terrestrial ecosystems: comparing two
16!!  contrasting approaches within European climate space,
17!!  Global Ecology and Biogeography, 10, 621-637.
18!!
19!! SVN          :
20!! $HeadURL$
21!! $Date$
22!! $Revision$
23!! \n
24!_ ================================================================================================================================
25
26MODULE lpj_crown
27
28  USE ioipsl_para
29  USE stomate_data
30  USE constantes
31  USE pft_parameters
32 
33  IMPLICIT NONE
34 
35  ! private & public routines
36
37  PRIVATE
38  PUBLIC crown
39 
40CONTAINS
41 
42 
43!! ================================================================================================================================
44!! SUBROUTINE    : lpj_crown
45!!
46!>\BRIEF         Calculate individual crown area from stem mass
47!!
48!! DESCRIPTION   : Calculating crown area of individual tree by diameter and tree height
49!! which are also calculated internally within this program from stem mass and allometory.
50!! Calculations for diameter, height and crown area originate from eqns 1, 2, and 3 in
51!! Appendix B, Smith et al. (2001) following Huang et al. 1992 and Zeide 1993.
52!! \latexonly
53!!  \input{lpj_crown1.tex}
54!!  \input{lpj_crown2.tex}
55!!  \input{lpj_crown3.tex}
56!! \endlatexonly
57!! \n
58!! where \f$k_{allom1}(=100.)\f$, \f$k_{allom2}(=40.)\f$, \f$k_{allom3}(=0.85)\f$ and \f$k_{rp}(=1.6)\f$ are
59!! constants, \f$WD\f$ is wood density (\f$=2 \times 10^5\f$ gC m\f$^3\f$) and \f$CA_{max}\f$ is maximum
60!! crown area (\f$=27.3\f$ m\f$^2\f$).
61!!
62!! RECENT CHANGE(S) : None
63!!
64!! MAIN OUTPUT VARIABLE(S) : ::cn_ind (crown area per individual, @tex $m^2 $ @endtex) and ::height (m)
65!!
66!! REFERENCE(S)   :
67!! - Huang, S., Titus, S.J. and Wiens, D.P. (1992) Comparison of nonlinear height–diameter functions for major
68!! Alberta tree species. Canadian Journal of Forest Research, 22, 1297–1304.\n
69!! - Zeide, B. (1993) Primary unit of the tree crown. Ecology, 74, 1598–1602.\n
70!! - Smith, B., I. C. Prentice, et al. (2001), Representation of vegetation dynamics in the modelling of
71!! terrestrial ecosystems: comparing two contrasting approaches within European climate space,
72!! Global Ecology and Biogeography, 10, 621-637.\n
73!!
74!! FLOWCHART : None
75!! \n
76!_ ================================================================================================================================
77
78  SUBROUTINE crown &
79       &  (npts, PFTpresent, ind, biomass, woodmass_ind, veget_cov_max, cn_ind, height)
80
81  !! 0. Variable and parameter declaration
82
83    !! 0.1 Input variables
84
85    INTEGER(i_std),INTENT(in)                         :: npts              !! Domain size (unitless)
86    LOGICAL,DIMENSION(npts,nvm),INTENT(in)            :: PFTpresent        !! Is pft there (unitless)
87    REAL(r_std),DIMENSION(npts,nvm),INTENT(in)        :: ind               !! [DISPENSABLE] Density of individuals
88                                                                           !! @tex $(m^{-2})$ @endtex
89    REAL(r_std),DIMENSION(npts,nvm,nparts,nelements),INTENT(in) :: biomass !! [DISPENSABLE] Biomass @tex $(gC.m^{-2})$ @endtex
90    REAL(r_std),DIMENSION(npts,nvm),INTENT(in)        :: woodmass_ind      !! Woodmass of the individual, needed to calculate
91                                                                           !! crownarea in lpj_crown (gC)
92
93    !! 0.2 Output variables
94 
95    REAL(r_std),DIMENSION(npts,nvm),INTENT(out)       :: cn_ind            !! Crown area per individual @tex $(m^{2})$ @endtex   
96
97    !! 0.3 Modified variables
98
99    REAL(r_std),DIMENSION(npts,nvm),INTENT(inout)     :: veget_cov_max    !! [DISPENSABLE] "Maximal" coverage fraction of a PFT
100                                                                          !! infinity) on ground (unitless)
101    REAL(r_std),DIMENSION(npts,nvm),INTENT(inout)     :: height           !! Height of vegetation (m)           
102
103    !! 0.4 Local variables
104       
105!   REAL(r_std),DIMENSION(npts)                       :: woodmass        !! Wood mass of an individual (gC)
106    INTEGER(i_std)                                    :: j               !! Index
107    REAL(r_std),DIMENSION(npts)                       :: dia             !! Stem diameter (m)
108    REAL(r_std),DIMENSION(nvm)                        :: height_presc_12 !! [DISPENSABLE] Prescribed height of each pfts (m)
109
110!_ ================================================================================================================================
111   
112  !! 1. Initializations
113   
114    !! 1.1 Check if DGVM is activated
115    IF (.NOT.ok_dgvm .AND. lpj_gap_const_mort) THEN
116       CALL ipslerr_p(3,'crown','Coherence error','crown cannot be called with static vegetation.','')
117    ENDIF
118   
119    !! 1.2 Initialize output to zero
120    cn_ind(:,:) = zero
121
122    !! 1.3 Copy prescribed height to new variable**3 !![DISPENSABLE]
123    height_presc_12(1:nvm) = height_presc(1:nvm)     !![DISPENSABLE]
124   
125  !! 2. Calculate (or prescribe) crown area
126   
127    DO j = 2,nvm ! loop over PFTs
128       IF (is_tree(j)) THEN
129         
130          !! 2.1 Trees
131          IF (natural(j)) THEN
132
133             !! 2.1.1 Natural trees
134             !WHERE (PFTpresent(:,j) .AND.ind(:,j).GT.min_stomate)
135             WHERE (PFTpresent(:,j) .AND.woodmass_ind(:,j).GT.min_stomate)
136
137                !! 2.1.1.1 Calculate individual wood mass**2
138
139                !! S. Zaehle note that woodmass_ind needs to be defined on the individual, hence
140                !! biomass*veget_cov_max/ind, not as stated here, correction MERGE
141                !!         woodmass(:) = &
142                !! &         (biomass(:,j,isapabove,icarbon) + biomass(:,j,isapbelow,icarbon) &
143                !! &         +biomass(:,j,iheartabove,icarbon) + biomass(:,j,iheartbelow,icarbon))/ind(:,j)
144         
145                !! 2.1.1.2 Stem diameter from pipe model
146                !          Stem diameter (pipe model) is calculated by allometory (eqn 1, Appdx B, Smith et al. (2001))
147                !!!$          dia(:) = (woodmass(:)/(pipe_density*pi/4.*pipe_tune2)) &
148                dia(:) = (woodmass_ind(:,j)/(pipe_density(j)*pi/4.*pipe_tune2)) &
149                 &       **(1./(2.+pipe_tune3))
150
151                !! 2.1.1.3 Individual tree height from pipe model
152                !          Individual tree height (eqn 2, Appdx B, Smith et al. (2001))
153                height(:,j) = pipe_tune2*(dia(:)**pipe_tune3)
154
155                !!!$S. Zaehle : The constraint on height has nothing to do with LPJ (for that purpose there's dia_max
156                !!!$ cannot see why this is necessary - it also blurrs the output, hence I leave it commented
157                !!!$ WHERE (height(:,j) > height_presc_12(j))
158                !!!$    dia(:) = (height_presc_12(j)/pipe_tune2)**(1./pipe_tune3)
159                !!!$    height(:,j) = height_presc_12(j)
160                !!!$ ENDWHERE
161
162                !! 2.1.1.4 Crown area of individual tree 
163                !          Calculate crown area, truncate crown area for trunks with large diameters
164                ! crown area cannot exceed a certain value, prescribed through maxdia
165                ! (eqn 3, Appdx B, Smith et al. (2001))
166
167                !+++HACK+++
168                ! Calculation of crown area has been changed
169                ! Use the function wood_to_diahor
170                ! ORIGINAL line of code : cn_ind(:,j) = pipe_tune1*MIN(dia(:),maxdia(j))**pipe_tune_exp_coeff
171                ! Quick fix to make the model compile
172                cn_ind(:,j) = crown_vertohor_dia(j)*crown_to_height(j)*height(:,j)
173                !++++++++++
174
175             ENDWHERE
176          ELSE
177
178             !! 2.1.2 Agricultural tree
179             !        To be developped if needed
180             CALL ipslerr_p(3,'crown','Cannot treat agricultural trees.','','')
181          ENDIF
182       ELSE
183         
184       !! 2.2 Grasses
185         
186          WHERE (PFTpresent(:,j))
187
188             !! 2.2.1 Crown area of grass
189             !        An "individual" is 1 m^2 of grass
190             cn_ind(:,j) = un
191          ENDWHERE
192       ENDIF
193       
194       !! 2.3 Recalculate vegetation cover
195       
196       !!!$S. Zaehle : since now all state variables are defined on veget_cov_max it is very
197       !!!$ dangerous to change this several times in stomate_lpj, as then GPP, turnover and allocated
198       !!!$ biomass are not defined on the same space! Hence, veget_cov_max is now kept constant
199       !!!$ and updated at the end of stomate_lpj in lpj_cover.f90
200       !!!$ Eventually, this routine should only be called once at the beginning and the end of stomate_lpj
201       !!!$ or prefereably cn_ind made a saved state variable!
202       !!!$ IF (natural(j).AND.ok_dgvm) THEN
203       !!!$   veget_cov_max(:,j) = ind(:,j) * cn_ind(:,j)
204       !!!$ ENDIF
205
206    ENDDO ! loop over PFTs
207
208  END SUBROUTINE crown
209
210END MODULE lpj_crown
Note: See TracBrowser for help on using the repository browser.