SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
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 tebgrid( 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, DIMENSION(:), 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, 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 IF (lhook) CALL dr_hook('TEBGRID',0,zhook_handle)
101 jnlvl = SIZE(pd_g,2)
102 !
103 IF (present(pd_g1)) zd_g1 = pd_g1
104 !-------------------------------------------------------------------------------
105 !
106 !* 1. Assign soil layer depths
107 ! ------------------------
108 ! using a geometric relation
109 ! for layers 2...N
110 ! This is GENERAL rule.
111 ! Note that the first soil layer
112 ! is FIXED except for VERY thin
113 ! soils (see #3 below).
114 !
115 pd_g(:,1) = zd_g1
116 pd_g(:,jnlvl) = psoildepth(:)
117 !
118 DO jj=jnlvl-1,2,-1
119  pd_g(:,jj) = pd_g(:,jj+1)/zgridfactor
120 ENDDO
121 !
122 !-------------------------------------------------------------------------------
123 !
124 !* 2. When the soil is sufficiently thin
125 ! ------------------------------------------
126 ! We recalculate layer depths such
127 ! that all layer thicknesses are >= ZD_G1
128 ! We favor keeping a minimum grid thickness
129 ! OVER maintaining geometric relation
130 ! for increasingly thin soils. This means
131 ! that uppermost soil moisture is readily
132 ! comparable (i.e. for same layer thickness)
133 ! EVERYWHERE except for most thin soils (below).
134 !
135 DO jj=1,jnlvl
136  pd_g(:,jj) = max(pd_g(:,jj), jj*zd_g1)
137 ENDDO
138 !
139 !-------------------------------------------------------------------------------
140 !
141 !* 3. In the LIMIT For extremely thin soils
142 ! ------------------------------------------
143 ! This should be a RARE occurance, but
144 ! accounted for none-the-less ...:
145 ! hold the ratio between all layer
146 ! thicknesses constant.
147 !
148 DO jj=1,jnlvl
149  WHERE(psoildepth(:) < jnlvl*zd_g1)
150  pd_g(:,jj) = jj*psoildepth/jnlvl
151  END WHERE
152 ENDDO
153 IF (lhook) CALL dr_hook('TEBGRID',1,zhook_handle)
154 !
155 !-------------------------------------------------------------------------------
156 !
157 END SUBROUTINE tebgrid
subroutine tebgrid(PSOILDEPTH, PD_G, PD_G1)
Definition: tebgrid.F90:6