1 | ! ================================================================================================================================= |
---|
2 | ! MODULE : structures |
---|
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 Contains structures and types used throughout the code |
---|
10 | !! |
---|
11 | !!\n DESCRIPTION: In this module, structural types should be declared. There are |
---|
12 | !! also routines for allocating and deallocating the memory in structures, |
---|
13 | !! if necessary. |
---|
14 | !! |
---|
15 | !! RECENT CHANGE(S): |
---|
16 | !! |
---|
17 | !! REFERENCE(S) : |
---|
18 | !! |
---|
19 | !! SVN : |
---|
20 | !! $HeadURL: $ |
---|
21 | !! $Date: 2013-09-25 17:38:26 +0200 (Wed, 25 Sep 2013) $ |
---|
22 | !! $Revision: 1480 $ |
---|
23 | !! \n |
---|
24 | !_ ================================================================================================================================ |
---|
25 | |
---|
26 | MODULE structures |
---|
27 | |
---|
28 | USE defprec |
---|
29 | USE constantes |
---|
30 | USE pft_parameters |
---|
31 | !- |
---|
32 | IMPLICIT NONE |
---|
33 | !- |
---|
34 | |
---|
35 | ! The purpose of this structure is to contain all |
---|
36 | ! the information needed to fit the effective LAI |
---|
37 | ! as a function of the solar angle. Doing this |
---|
38 | ! as a structure means that we can change which |
---|
39 | ! function we fit to more easily. We will have |
---|
40 | ! to allocate this for every grid cell, PFT, and |
---|
41 | ! level. |
---|
42 | INTEGER,PARAMETER :: nparams_laieff = 5 ! The number of parameters in the structure below |
---|
43 | TYPE laieff_type |
---|
44 | REAL(r_std) :: a,b,c,d,e !! We do a polynomial fit, a+b*x+c*x**2+d*x**3+e*x**4 |
---|
45 | END type laieff_type |
---|
46 | |
---|
47 | |
---|
48 | CONTAINS |
---|
49 | |
---|
50 | !! ============================================================================================================================== |
---|
51 | !! SUBROUTINE : laieff_type_init |
---|
52 | !! |
---|
53 | !>\BRIEF Set the values for all the parameters of this type to zero. |
---|
54 | !! |
---|
55 | !! DESCRIPTION : |
---|
56 | !! |
---|
57 | !! RECENT CHANGE(S): None |
---|
58 | !! |
---|
59 | !! MAIN OUTPUT VARIABLE(S): ::laieff_type |
---|
60 | !! |
---|
61 | !! REFERENCE(S) : |
---|
62 | !! |
---|
63 | !! FLOWCHART : None |
---|
64 | !! \n |
---|
65 | !! |
---|
66 | !! |
---|
67 | !! |
---|
68 | !_ ================================================================================================================================ |
---|
69 | |
---|
70 | SUBROUTINE laieff_type_init(npts, nlevels_loc, laieff_fit) |
---|
71 | |
---|
72 | !! 0. Variable and parameter declaration |
---|
73 | |
---|
74 | !! 0.1 Input variables |
---|
75 | INTEGER(i_std), INTENT(in) :: npts !! Domain size - Number of land pixels (unitless) |
---|
76 | INTEGER(i_std), INTENT(in) :: nlevels_loc !! The number of vertical levels in the canopy (unitless) |
---|
77 | !! 0.2 Output variables |
---|
78 | |
---|
79 | !! 0.3 Modified variables |
---|
80 | TYPE(laieff_type),DIMENSION (:,:,:),INTENT(inout) :: laieff_fit !! Fitted parameters for the effective LAI |
---|
81 | |
---|
82 | !! 0.4 Local variables |
---|
83 | |
---|
84 | INTEGER :: ipts,ivm,ilevel |
---|
85 | |
---|
86 | !_ ================================================================================================================================ |
---|
87 | |
---|
88 | DO ipts=1,npts |
---|
89 | DO ivm=1,nvm |
---|
90 | DO ilevel=1,nlevels_loc |
---|
91 | laieff_fit(ipts,ivm,ilevel)%a=zero |
---|
92 | laieff_fit(ipts,ivm,ilevel)%b=zero |
---|
93 | laieff_fit(ipts,ivm,ilevel)%c=zero |
---|
94 | laieff_fit(ipts,ivm,ilevel)%d=zero |
---|
95 | laieff_fit(ipts,ivm,ilevel)%e=zero |
---|
96 | ENDDO |
---|
97 | ENDDO |
---|
98 | ENDDO |
---|
99 | |
---|
100 | |
---|
101 | END SUBROUTINE laieff_type_init |
---|
102 | |
---|
103 | |
---|
104 | |
---|
105 | END MODULE structures |
---|