source: tags/ORCHIDEE_4_1/ORCHIDEE/src_stomate/stomate_stand_structure.f90 @ 7761

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

Correction of crown diameters and crown volume. Avoids the situatiuon were the sum of the crown volumes exceeds the entire canopy space. Contributes to ticket #791

File size: 6.2 KB
Line 
1! =================================================================================================================================
2! MODULE       : stomate_stand_structure
3!
4! CONTACT      : orchidee-help _at_ ipsl.jussieu.fr
5!
6! LICENCE      : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF         Initialize and update density, crown area.
10!!
11!!\n DESCRIPTION: None
12!!
13!! RECENT CHANGE(S): None
14!!
15!! REFERENCE(S) :
16!!
17!! SVN          :
18!! $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/branches/ORCHIDEE-DOFOCO/ORCHIDEE/src_stomate/stomate_prescribe.f90 $
19!! $Date: 2013-01-04 16:50:56 +0100 (Fri, 04 Jan 2013) $
20!! $Revision: 1126 $
21!! \n
22!_ ================================================================================================================================
23
24MODULE stomate_stand_structure
25
26  ! modules used:
27
28  USE xios_orchidee
29  USE ioipsl_para
30  USE stomate_data
31  USE pft_parameters
32  USE constantes
33  USE function_library, ONLY:wood_to_height, wood_to_dia, &
34                             wood_to_cv, wood_to_cn_dia
35
36  IMPLICIT NONE
37
38  ! private & public routines
39
40  PRIVATE
41  PUBLIC stand_structure_clear, derive_biomass_quantities
42
43  ! first call
44  LOGICAL, SAVE                                    :: firstcall = .TRUE.
45!$OMP THREADPRIVATE(firstcall)
46CONTAINS
47
48! =================================================================================================================================
49!! SUBROUTINE   : stand_structure_clear
50!!
51!>\BRIEF        : Set the firstcall flag back to .TRUE. to prepare for the next simulation.
52!_=================================================================================================================================
53
54  SUBROUTINE stand_structure_clear
55    firstcall=.TRUE.
56  END SUBROUTINE stand_structure_clear
57
58
59!! ================================================================================================================================
60!! SUBROUTINE   :derive_biomass_quantities
61!!
62!>\BRIEF        Use the basal areabiomass and number density to derive various
63!!              distributions of the trees in a single grid point for
64!!              all vegetation types
65!!
66!! DESCRIPTION  : I have chosen to do this for a single grid point instead of
67!!                the whole map or a single grid point and single PFT because
68!!                of the compromise between speed (subroutine overhead) and
69!!                flexibility
70!!
71!! RECENT CHANGE(S) : None
72!!
73!! MAIN OUTPUT VARIABLE(S): ::height_dist, ::diameter_dist, ::cn_area_dist, ::cn_vol_dist
74!!
75!! REFERENCE(S) :
76!!
77!! FLOWCHART : None
78!! \n
79!_ ================================================================================================================================
80
81  SUBROUTINE derive_biomass_quantities(npts, nvm, ncirc, circ_class_n, &
82       circ_class_biomass, values)
83
84  !! 0 Variable and parameter declaration
85 
86    !! 0.1 Input variables
87    INTEGER,INTENT(IN)                                      :: npts               !! Number of pixels
88    INTEGER,INTENT(IN)                                      :: nvm                !! Number of PFT types
89    INTEGER,INTENT(IN)                                      :: ncirc              !! Number of circumference classes
90    REAL(r_std), DIMENSION(:,:,:,:,:), INTENT(IN)           :: circ_class_biomass !! Biomass of the componets of the model 
91                                                                                  !! tree within a circumference
92                                                                                  !! class @tex $(gC ind^{-1})$ @endtex
93    REAL(r_std), DIMENSION(:,:,:), INTENT(IN)               :: circ_class_n       !! Number of trees within each circumference
94                                                                                  !! class @tex $(m^{-2})$ @endtex
95
96    !! 0.2 Output variables
97
98    REAL(r_std),DIMENSION(:,:,:,:),INTENT(OUT)              :: values             !! An array which holds data for
99                                                                                  !! various canopy parameters
100
101
102    !! 0.3 Modified variables
103
104    !! 0.4 Local variables
105
106    INTEGER(i_std)                                          :: ipts, ivm, icir, &
107                                                                       idist_type !! index (unitless)
108!_ ================================================================================================================================
109
110    IF (printlev.GE.3) WRITE(numout,*) 'Entering derive_biomass_quantities'
111
112    ! zero everything
113    values(:,:,:,:)=zero
114
115    DO ipts=1,npts
116       DO ivm=1,nvm
117
118          IF (.NOT. is_tree(ivm)) CYCLE
119
120          ! compute the new mean values
121
122          ! for the stem height (aboveground only)
123          values(ipts,ivm,:,iheight) = &
124               wood_to_height(circ_class_biomass(ipts,ivm,:,:,icarbon),ivm)
125         
126          ! for the stem diameter
127          values(ipts,ivm,:,idiameter) = &
128               wood_to_dia(circ_class_biomass(ipts,ivm,:,:,icarbon),ivm)
129         
130          ! vertical and horizontal crown diameter
131          CALL wood_to_cn_dia(circ_class_biomass(ipts,ivm,:,:,icarbon), &
132               circ_class_n(ipts,ivm,:),ivm,values(ipts,ivm,:,icndiahor), &
133               values(ipts,ivm,:,icndiaver))
134         
135          ! for the crown area
136          values(ipts,ivm,:,icnarea) = &
137               pi/4*values(ipts,ivm,:,icndiahor)**2
138         
139          ! for the crown volume
140          values(ipts,ivm,:,icnvol) = &
141               wood_to_cv(circ_class_biomass(ipts,ivm,:,:,icarbon),&
142               circ_class_n(ipts,ivm,:),ivm)
143
144       ENDDO ! loop over PFT
145
146    ENDDO ! loop over points
147
148    ! Output tree and crown properties
149    ! CCDIAMETER and CCHEIGHT are written in stomate_growth_fun_all
150    ! at the same time as some tree ring width variables. They could
151    ! as well be written here.
152    CALL xios_orchidee_send_field("CCDIAHOR",values(:,:,:,icndiahor))
153    CALL xios_orchidee_send_field("CCDIAVER",values(:,:,:,icndiaver))
154    CALL xios_orchidee_send_field("CCCROWN",values(:,:,:,icnarea))
155    CALL xios_orchidee_send_field("CCCROWNVOL",values(:,:,:,icnvol))
156
157    IF (printlev.GE.3) WRITE(numout,*) 'Leaving derive_biomass_quantities'
158
159 END SUBROUTINE derive_biomass_quantities
160
161
162END MODULE stomate_stand_structure
163
164
165
Note: See TracBrowser for help on using the repository browser.