SURFEX v8.1
General documentation of Surfex
prep_ver_teb_veg.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 prep_ver_teb_veg (P, PEK, IO, PZS)
7 ! #################################################################################
8 !
9 !!**** *PREP_VER_TEB_GARDEN* - change in ISBA fields due to altitude change
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !!** METHOD
15 !! ------
16 !!
17 !! REFERENCE
18 !! ---------
19 !!
20 !!
21 !! AUTHOR
22 !! ------
23 !! V. Masson
24 !!
25 !! MODIFICATIONS
26 !! -------------
27 !! Original 01/2004
28 !! Modified by B. Decharme (01/2009), Optional Arpege deep soil temperature initialization
29 !!------------------------------------------------------------------
30 !
31 USE modd_isba_n, ONLY : isba_pe_t, isba_p_t
33 !
34 USE modd_isba_par, ONLY : xwgmin
35 USE modd_surf_par, ONLY : xundef
36 USE modd_prep, ONLY : xzs_ls, xt_clim_grad
37 USE modd_csts, ONLY : xtt, xday, xlmtt, xrholw
38 !
39 USE mode_thermos
40 USE modi_prep_ver_snow
41 !
42 !
43 USE yomhook ,ONLY : lhook, dr_hook
44 USE parkind1 ,ONLY : jprb
45 !
46 IMPLICIT NONE
47 !
48 !* 0.1 declarations of arguments
49 !
50 !
51 !* 0.2 declarations of local variables
52 !
53 !
54 TYPE(isba_p_t), INTENT(INOUT) :: P
55 TYPE(isba_pe_t), INTENT(INOUT) :: PEK
56 TYPE(isba_options_t), INTENT(INOUT) :: IO
57 REAL, DIMENSION(:), INTENT(IN) :: PZS
58 !
59 INTEGER :: JL ! loop counter on layers
60 INTEGER :: IWORK ! Work integer
61 !
62 REAL, DIMENSION(:), ALLOCATABLE :: ZWGTOT ! total water content
63 REAL, DIMENSION(:), ALLOCATABLE :: ZDW ! variation of water in soil
64 REAL, DIMENSION(:), ALLOCATABLE :: ZZSFREEZE ! altitude where soil temperature equals XTT
65 INTEGER :: IDEEP_SOIL! layer corresponding to deep soil temperature
66 !
67 REAL, DIMENSION(:,:), ALLOCATABLE :: ZWGI_CLIM_GRAD ! ice content vertical gradient
68 !
69 REAL, DIMENSION(:,:), ALLOCATABLE :: ZTG_LS! temperature on initial orography
70 !
71 REAL :: ZGRADX = 5.e-4 ! slope of ice content gradient
72 REAL :: ZH0 = 5.e-1 ! constant used to define ice content gradient
73 REAL(KIND=JPRB) :: ZHOOK_HANDLE
74 !-------------------------------------------------------------------------------------
75 !
76 !* 1.0 Ice content climatologic gradient
77 !
78 IF (lhook) CALL dr_hook('PREP_VER_TEB_VEG',0,zhook_handle)
79 ALLOCATE(zwgi_clim_grad(SIZE(pek%XWG,1),SIZE(pek%XWG,2)))
80 !
81 zwgi_clim_grad(:,:) = zgradx * exp( - p%XDG(:,:) / zh0 )
82 !-------------------------------------------------------------------------------------
83 !
84 !* 1.1 Temperature profile
85 !
86 ALLOCATE(ztg_ls(SIZE(pek%XTG,1),SIZE(pek%XTG,2)))
87 ztg_ls(:,:) = pek%XTG(:,:)
88 !
89 DO jl=1,SIZE(pek%XTG,2)
90  WHERE(pek%XTG(:,jl)/=xundef) &
91  pek%XTG(:,jl) = pek%XTG(:,jl) + xt_clim_grad * (pzs - xzs_ls)
92 END DO
93 !
94 !-------------------------------------------------------------------------------------
95 !
96 !* 1.2 Water and ice in the soil
97 !
98 ALLOCATE(zzsfreeze(SIZE(pek%XWG,1)))
99 ALLOCATE(zwgtot(SIZE(pek%XWG,1)))
100 ALLOCATE(zdw(SIZE(pek%XWG,1)))
101 !
102 !* general case
103 !
104 iwork=SIZE(pek%XTG,2)
105 !
106 DO jl=1,iwork
107  !
108  zdw(:) = 0.
109  ! altitude where deep soil freezes (diurnal surface response is not treated)
110  zzsfreeze(:) = pzs + (xtt - pek%XTG(:,jl)) / xt_clim_grad
111  !
112  WHERE(pek%XTG(:,jl)/=xundef)
113  !
114  WHERE (ztg_ls(:,jl) < xtt)
115  !
116  WHERE (pzs <= xzs_ls)
117  !
118  WHERE (pzs > zzsfreeze)
119  zdw(:) = zwgi_clim_grad(:,jl) * (pzs - xzs_ls)
120  ELSEWHERE
121  zdw(:) = zwgi_clim_grad(:,jl) * (zzsfreeze - xzs_ls) + zgradx * (pzs - zzsfreeze)
122  ENDWHERE
123  !
124  ELSEWHERE
125  !
126  zdw(:) = zwgi_clim_grad(:,jl) * (pzs - xzs_ls)
127  !
128  ENDWHERE
129  !
130  ELSEWHERE
131  !
132  WHERE (pzs <= xzs_ls)
133  !
134  zdw(:) = zgradx * (pzs - xzs_ls)
135  !
136  ELSEWHERE
137  !
138  zdw(:) = zwgi_clim_grad(:,jl) * (pzs - zzsfreeze)
139  !
140  END WHERE
141  !
142  END WHERE
143  !
144  zwgtot(:) = xundef
145  !
146  WHERE(pek%XWG(:,jl)/=xundef)
147  zwgtot(:) = pek%XWG(:,jl) + pek%XWGI(:,jl)
148  ENDWHERE
149  !
150  WHERE(pek%XWG(:,jl)/=xundef)
151  pek%XWGI(:,jl) = pek%XWGI(:,jl) + zdw(:)
152  pek%XWG (:,jl) = pek%XWG (:,jl) - zdw(:)
153  ENDWHERE
154  !
155  WHERE (pek%XWGI(:,jl) < 0..AND.pek%XWGI(:,jl)/=xundef)
156  pek%XWGI(:,jl) = 0.
157  pek%XWG (:,jl) = zwgtot(:)
158  END WHERE
159  !
160  WHERE (pek%XWG(:,jl) < xwgmin.AND.pek%XWG(:,jl)/=xundef)
161  pek%XWG (:,jl) = xwgmin
162  pek%XWGI(:,jl) = zwgtot(:) - xwgmin
163  END WHERE
164  !
165  WHERE(pek%XWGI(:,jl) > 0..AND.pek%XWGI(:,jl)/=xundef)
166  pek%XTG(:,jl) = min(xtt,pek%XTG(:,jl))
167  ELSEWHERE
168  pek%XTG(:,jl) = max(xtt,pek%XTG(:,jl))
169  ENDWHERE
170  !
171  ENDWHERE
172  !
173 END DO
174 !
175 !* limits in force-restore case
176 !
177 IF (io%CISBA=='3-L') THEN
178  WHERE (pek%XWGI(:,3) /= xundef)
179  pek%XWG (:,3) = pek%XWG(:,3)+pek%XWGI(:,3)
180  pek%XWGI(:,3) = 0.
181  pek%XTG (:,3) = ztg_ls(:,3)
182  END WHERE
183 END IF
184 !
185 DEALLOCATE(zzsfreeze)
186 DEALLOCATE(zwgi_clim_grad)
187 DEALLOCATE(zwgtot )
188 DEALLOCATE(zdw )
189 !
190 !* masks where fields are not defined
191 WHERE (pek%XTG(:,1:SIZE(pek%XWG,2)) == xundef)
192  pek%XWG (:,:) = xundef
193  pek%XWGI(:,:) = xundef
194 END WHERE
195 !
196 !-------------------------------------------------------------------------------------
197 !
198 !* 1.4 Snow variables
199 !
200 !* vertical shift
201 IF (io%CISBA=='DIF') THEN
202  ideep_soil = io%NGROUND_LAYER
203 ELSE
204  ideep_soil = 2
205 END IF
206  CALL prep_ver_snow(pek%TSNOW,xzs_ls,pzs,ztg_ls,pek%XTG,ideep_soil)
207 !
208 !-------------------------------------------------------------------------------------
209 !
210 !* 2. Deallocation of large-scale orography
211 !
212 DEALLOCATE(ztg_ls)
213 IF (lhook) CALL dr_hook('PREP_VER_TEB_VEG',1,zhook_handle)
214 !-------------------------------------------------------------------------------------
215 !
216 END SUBROUTINE prep_ver_teb_veg
subroutine prep_ver_snow(TPSNOW, PZS_LS, PZS, PTG_LS, PTG, KDEEP_SOIL)
real, dimension(:), allocatable xzs_ls
Definition: modd_prep.F90:45
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
real, save xday
Definition: modd_csts.F90:45
logical lhook
Definition: yomhook.F90:15
subroutine prep_ver_teb_veg(P, PEK, IO, PZS)
real, parameter xt_clim_grad
Definition: modd_prep.F90:53
real, save xrholw
Definition: modd_csts.F90:64
real, save xtt
Definition: modd_csts.F90:66
real, save xlmtt
Definition: modd_csts.F90:72