1 | ! ================================================================================================================================= |
---|
2 | ! MODULE : vertical_soil_var |
---|
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 |
---|
10 | !! |
---|
11 | !!\n DESCRIPTION: |
---|
12 | !! |
---|
13 | !! RECENT CHANGE(S): |
---|
14 | !! |
---|
15 | !! REFERENCE(S) : |
---|
16 | !! |
---|
17 | !! SVN : |
---|
18 | !! $HeadURL$ |
---|
19 | !! $Date$ |
---|
20 | !! $Revision$ |
---|
21 | !! \n |
---|
22 | !_ ================================================================================================================================ |
---|
23 | |
---|
24 | MODULE vertical_soil_var |
---|
25 | |
---|
26 | USE defprec |
---|
27 | |
---|
28 | IMPLICIT NONE |
---|
29 | PUBLIC |
---|
30 | |
---|
31 | !! Dimensioning parameters |
---|
32 | INTEGER(i_std), SAVE :: ngrnd !! Number of soil layer for thermo (unitless) |
---|
33 | !$OMP THREADPRIVATE(ngrnd) |
---|
34 | INTEGER(i_std), SAVE :: nbdl !! Number of diagnostic layers in the soil, not needed in CWRR (unitless) |
---|
35 | !$OMP THREADPRIVATE(nbdl) |
---|
36 | INTEGER(i_std), SAVE :: nslm !! Number of levels in CWRR (unitless) |
---|
37 | !$OMP THREADPRIVATE(nslm) |
---|
38 | REAL(r_std), SAVE :: zmaxh !! Maximum depth of soil reservoir in hydrol (m). Old name dpu_max or depth_Wmax |
---|
39 | !$OMP THREADPRIVATE(zmaxh) |
---|
40 | REAL(r_std), SAVE :: zmaxt !! Maximum depth of the soil thermodynamics (m) |
---|
41 | !$OMP THREADPRIVATE(zmaxt) |
---|
42 | |
---|
43 | !! Variables defining the vertical layering in soil moisture and temperature |
---|
44 | REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:) :: znt !! Depth of nodes for thermal (m) |
---|
45 | !$OMP THREADPRIVATE(znt) |
---|
46 | REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:) :: znh !! Depth of nodes for hydrology (m) |
---|
47 | !$OMP THREADPRIVATE(znh) |
---|
48 | REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:) :: dnh !! Distance between the current node and the one above for hydrology (m) |
---|
49 | !$OMP THREADPRIVATE(dnh) |
---|
50 | REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:) :: dlh !! Soil layer thickness for hydrology (m) |
---|
51 | !$OMP THREADPRIVATE(dlh) |
---|
52 | REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:) :: dlt !! Soil layer thickness for thermal (m) |
---|
53 | !$OMP THREADPRIVATE(dlt) |
---|
54 | REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:) :: zlh !! Depth of lower layer-interface for hydrology (m) |
---|
55 | !$OMP THREADPRIVATE(zlh) |
---|
56 | REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:) :: zlt !! Depth of lower layer-interface for thermal (m) |
---|
57 | !$OMP THREADPRIVATE(zlt) |
---|
58 | |
---|
59 | REAL(r_std),ALLOCATABLE, DIMENSION(:),SAVE :: diaglev !! The lower limit of the layer on which soil moisture |
---|
60 | !! (relative) and temperature are going to be diagnosed. |
---|
61 | !! These variables are made for transfering the information |
---|
62 | !! to the biogeophyical processes modelled in STOMATE. |
---|
63 | !$OMP THREADPRIVATE(diaglev) |
---|
64 | |
---|
65 | END MODULE vertical_soil_var |
---|