SURFEX v8.1
General documentation of Surfex
tebgrid.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #########
6  SUBROUTINE tebgrid3( PSOILDEPTH, PD_G, PD_G1 )
7 
8 ! ##########################################################################
9 !
10 !!**** *TEBGRID*
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 ! Calculates the soil grid configuration using a simple
16 ! geometric relation for all sub-surface layers.
17 ! This algorithm assumes the total soil depth > 0 m
18 !
19 !
20 !!** METHOD
21 !! ------
22 !
23 ! Direct calculation
24 !
25 !! EXTERNAL
26 !! --------
27 !
28 ! None
29 !!
30 !! IMPLICIT ARGUMENTS
31 !! ------------------
32 !!
33 !! REFERENCE
34 !! ---------
35 !!
36 !! Noilhan and Planton (1989)
37 !! Belair (1995)
38 !! Boone (2000)
39 !! Boone et al. (2000)
40 !! Habets et al. (2003)
41 !!
42 !! AUTHOR
43 !! ------
44 !! A. Boone * Meteo-France *
45 !!
46 !! MODIFICATIONS
47 !! -------------
48 !! Original 12/04/03
49 !! B. Decharme 12/10 uppermost soil layer set to 1cm
50 !-------------------------------------------------------------------------------
51 !
52 !* 0. DECLARATIONS
53 ! ------------
54 !
55 !
56 USE yomhook ,ONLY : lhook, dr_hook
57 USE parkind1 ,ONLY : jprb
58 !
59 IMPLICIT NONE
60 !
61 !* 0.1 declarations of arguments
62 !
63 !
64 REAL, INTENT(IN) :: PSOILDEPTH ! total soil depth (m)
65 !
66 REAL, DIMENSION(:), INTENT(OUT) :: PD_G ! depth of base of soil layers (m)
67 REAL, OPTIONAL, INTENT(IN) :: PD_G1 ! depth of first layer
68 !
69 !
70 !* 0.2 declarations of local variables
71 !
72 INTEGER :: JJ, JI, JNLVL
73 !
74 !
75 REAL, PARAMETER :: ZGRIDFACTOR = 3.0 ! soil depth factor
76 ! ! of increase with depth
77 ! ! for all *sub-surface*
78 ! ! layers. Note, uppermost
79 ! ! layer fixed by other
80 ! ! constraints. (-)
81 !
82 REAL :: ZD_G1 = 0.01 ! uppermost soil layer
83 ! ! thickness/depth (m)
84 ! ! Can not be too thin as
85 ! ! then definition of soil
86 ! ! properties (i.e. phyiscal
87 ! ! representation of) and
88 ! ! accuarcy of
89 ! ! numerical solution come
90 ! ! into question. If it is too
91 ! ! thick, then resolution of
92 ! ! diurnal cycle not as valid.
93 ! ! Also chosen to comply with
94 ! ! remotely sensed soil moisture.
95 REAL(KIND=JPRB) :: ZHOOK_HANDLE
96 !-------------------------------------------------------------------------------
97 ! 0. Initialization
98 ! --------------
99 !
100 jnlvl = SIZE(pd_g)
101 !
102 IF (PRESENT(pd_g1)) zd_g1 = pd_g1
103 !
104 IF (psoildepth < jnlvl*zd_g1) THEN
105  !
106  !* 3. In the LIMIT For extremely thin soils
107  ! ------------------------------------------
108  ! This should be a RARE occurance, but
109  ! accounted for none-the-less ...:
110  ! hold the ratio between all layer
111  ! thicknesses constant.
112  DO jj = 1,jnlvl
113  pd_g(jj) = jj*psoildepth/jnlvl
114  ENDDO
115  !
116 ELSE
117  !
118  pd_g(1) = zd_g1
119  pd_g(jnlvl) = psoildepth
120  !
121  DO jj=jnlvl-1,2,-1
122  !* 1. Assign soil layer depths
123  ! ------------------------
124  ! using a geometric relation
125  ! for layers 2...N
126  ! This is GENERAL rule.
127  ! Note that the first soil layer
128  ! is FIXED except for VERY thin
129  ! soils (see #3 below).
130  pd_g(jj) = pd_g(jj+1)/zgridfactor
131  !* 2. When the soil is sufficiently thin
132  ! ------------------------------------------
133  ! We recalculate layer depths such
134  ! that all layer thicknesses are >= ZD_G1
135  ! We favor keeping a minimum grid thickness
136  ! OVER maintaining geometric relation
137  ! for increasingly thin soils. This means
138  ! that uppermost soil moisture is readily
139  ! comparable (i.e. for same layer thickness)
140  ! EVERYWHERE except for most thin soils (below).
141  pd_g(jj) = max(pd_g(jj), jj*zd_g1)
142  !
143  ENDDO
144  !
145 ENDIF
146 !
147 !-------------------------------------------------------------------------------
148 !
149 END SUBROUTINE tebgrid3
integer, parameter jprb
Definition: parkind1.F90:32
subroutine tebgrid3(PSOILDEPTH, PD_G, PD_G1)
Definition: tebgrid.F90:7
logical lhook
Definition: yomhook.F90:15