1 | ! ================================================================================================================================= |
---|
2 | ! MODULE : stomate_lai |
---|
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 Calculate lai |
---|
10 | !! |
---|
11 | !! \n DESCRIPTION : Calculate lai |
---|
12 | !! |
---|
13 | !! REFERENCE(S) : |
---|
14 | !! |
---|
15 | !! SVN : |
---|
16 | !! $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/branches/ORCHIDEE-MICT/ORCHIDEE/src_stomate/lpj_crown.f90 $ |
---|
17 | !! $Date: 2015-11-16 14:26:03 +0100 (Mon, 16 Nov 2015) $ |
---|
18 | !! $Revision: 3026 $ |
---|
19 | !! \n |
---|
20 | !_ ================================================================================================================================ |
---|
21 | |
---|
22 | MODULE stomate_lai |
---|
23 | |
---|
24 | ! USE ioipsl_para |
---|
25 | ! USE stomate_data |
---|
26 | ! USE constantes |
---|
27 | USE constantes_var |
---|
28 | ! USE pft_parameters |
---|
29 | |
---|
30 | IMPLICIT NONE |
---|
31 | |
---|
32 | ! private & public routines |
---|
33 | |
---|
34 | PRIVATE |
---|
35 | PUBLIC setlai |
---|
36 | |
---|
37 | CONTAINS |
---|
38 | |
---|
39 | !! ================================================================================================================================ |
---|
40 | !! SUBROUTINE : setlai |
---|
41 | !! |
---|
42 | !>\BRIEF Routine to force the lai in STOMATE. The code in this routine |
---|
43 | !! simply CALCULATES lai and is therefore not functional. The routine should be |
---|
44 | !! rewritten if one wants to force lai. |
---|
45 | !! |
---|
46 | !! DESCRIPTION : None |
---|
47 | !! |
---|
48 | !! RECENT CHANGE(S) : None |
---|
49 | !! |
---|
50 | !! MAIN OUTPUT VARIABLE(S): ::lai |
---|
51 | !! |
---|
52 | !! REFERENCE(S) : None |
---|
53 | !! |
---|
54 | !! FLOWCHART : None |
---|
55 | !! \n |
---|
56 | !_ ================================================================================================================================ |
---|
57 | |
---|
58 | SUBROUTINE setlai(biomass,sla_calc,lai) |
---|
59 | |
---|
60 | !! 0 Variable and parameter declaration |
---|
61 | |
---|
62 | !! 0.1 Input variables |
---|
63 | |
---|
64 | REAL(r_std),DIMENSION(:,:,:,:),INTENT(in) :: biomass !! biomass |
---|
65 | REAL(r_std),DIMENSION(:,:),INTENT(in) :: sla_calc !! sla_calc |
---|
66 | |
---|
67 | !! 0.2 Output variables |
---|
68 | |
---|
69 | REAL(r_std),DIMENSION(:,:),INTENT(out) :: lai !! PFT leaf area index @tex $(m^{2} m^{-2})$ @endtex |
---|
70 | |
---|
71 | !! 0.3 Modified variables |
---|
72 | |
---|
73 | !! 0.4 Local variables |
---|
74 | |
---|
75 | INTEGER(i_std) :: j !! index (unitless) |
---|
76 | !_ ================================================================================================================================ |
---|
77 | |
---|
78 | !! 1. Set lai for bare soil to zero |
---|
79 | |
---|
80 | lai(:,ibare_sechiba) = zero |
---|
81 | |
---|
82 | !! 2. Multiply foliage biomass by sla to calculate lai for all PFTs and pixels |
---|
83 | |
---|
84 | DO j=2,SIZE(biomass,DIM=2) |
---|
85 | lai(:,j) = biomass(:,j,ileaf,icarbon)*sla_calc(:,j) |
---|
86 | ENDDO |
---|
87 | |
---|
88 | END SUBROUTINE setlai |
---|
89 | |
---|
90 | |
---|
91 | END MODULE stomate_lai |
---|