source: branches/ORCHIDEE_2_2/ORCHIDEE/src_parameters/vertical_soil_var.f90 @ 7442

Last change on this file since 7442 was 4631, checked in by josefine.ghattas, 7 years ago

Since the homogenization of the soil discretization, dimension nbdl is not needed as it it the same as nslm. Here remove all usage of nbdl and replace by nslm. No change in results. See ticket #195

  • Property svn:keywords set to Date Revision HeadURL
File size: 2.7 KB
Line 
1! =================================================================================================================================
2! MODULE       : vertical_soil_var
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       
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
24MODULE 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      :: nslm      !! Number of levels in CWRR (unitless)
35!$OMP THREADPRIVATE(nslm)
36  REAL(r_std), SAVE         :: zmaxh     !! Maximum depth of soil reservoir in hydrol (m). Old name dpu_max or depth_Wmax
37!$OMP THREADPRIVATE(zmaxh)
38  REAL(r_std), SAVE         :: zmaxt     !! Maximum depth of the soil thermodynamics (m)
39!$OMP THREADPRIVATE(zmaxt)
40
41  !! Variables defining the vertical layering in soil moisture and temperature
42  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:) :: znt          !! Depth of nodes for thermal (m)
43!$OMP THREADPRIVATE(znt)
44  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:) :: znh          !! Depth of nodes for hydrology (m)
45!$OMP THREADPRIVATE(znh)
46  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:) :: dnh          !! Distance between the current node and the one above for hydrology (m)
47!$OMP THREADPRIVATE(dnh)
48  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:) :: dlh          !! Soil layer thickness for hydrology (m)
49!$OMP THREADPRIVATE(dlh)
50  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:) :: dlt          !! Soil layer thickness for thermal (m)
51!$OMP THREADPRIVATE(dlt)
52  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:) :: zlh          !! Depth of lower layer-interface for hydrology (m)
53!$OMP THREADPRIVATE(zlh)
54  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:) :: zlt          !! Depth of lower layer-interface for thermal (m)
55!$OMP THREADPRIVATE(zlt)
56
57  REAL(r_std),ALLOCATABLE, DIMENSION(:),SAVE :: diaglev        !! The lower limit of the layer on which soil moisture
58                                                               !! (relative) and temperature are going to be diagnosed.
59                                                               !! These variables are made for transfering the information
60                                                               !! to the biogeophyical processes modelled in STOMATE.
61!$OMP THREADPRIVATE(diaglev)
62
63END MODULE vertical_soil_var
Note: See TracBrowser for help on using the repository browser.