SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
prep_ver_teb_greenroof.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_greenroof (TGR, TGRO, TGRP, TOP)
7 ! #################################################################################
8 !
9 !!**** *PREP_VER_TEB_GREENROOF* - 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 + A.Lemonsu & C.deMunck
24 !!
25 !! MODIFICATIONS
26 !! -------------
27 !! Original 01/2004
28 !! Modified by B. Decharme (01/2009), Optional Arpege deep soil temperature initialization
29 !!------------------------------------------------------------------
30 !
31 
32 !
33 !
38 !
39 USE modd_isba_par, ONLY : xwgmin
40 USE modd_surf_par, ONLY : xundef
41 USE modd_prep, ONLY : xzs_ls, xt_clim_grad
42 USE modd_csts, ONLY : xtt, xday, xlmtt, xrholw
43 !
44 USE mode_thermos
45 USE modi_prep_ver_snow
46 !
47 !
48 USE yomhook ,ONLY : lhook, dr_hook
49 USE parkind1 ,ONLY : jprb
50 !
51 IMPLICIT NONE
52 !
53 !* 0.1 declarations of arguments
54 !
55 !
56 !* 0.2 declarations of local variables
57 !
58 !
59 TYPE(teb_greenroof_t), INTENT(INOUT) :: tgr
60 TYPE(teb_greenroof_options_t), INTENT(INOUT) :: tgro
61 TYPE(teb_greenroof_pgd_t), INTENT(INOUT) :: tgrp
62 TYPE(teb_options_t), INTENT(INOUT) :: top
63 !
64 INTEGER :: jl ! loop counter on layers
65 INTEGER :: iwork ! Work integer
66 !
67 REAL, DIMENSION(:), ALLOCATABLE :: zwgtot ! total water content
68 REAL, DIMENSION(:), ALLOCATABLE :: zdw ! variation of water in soil
69 REAL, DIMENSION(:), ALLOCATABLE :: zzsfreeze ! altitude where soil temperature equals XTT
70 INTEGER :: ideep_soil! layer corresponding to deep soil temperature
71 !
72 REAL, DIMENSION(:,:), ALLOCATABLE :: zwgi_clim_grad ! ice content vertical gradient
73 !
74 REAL, DIMENSION(:,:), ALLOCATABLE :: ztg_ls! temperature on initial orography
75 !
76 REAL :: zgradx = 5.e-4 ! slope of ice content gradient
77 REAL :: zh0 = 5.e-1 ! constant used to define ice content gradient
78 REAL(KIND=JPRB) :: zhook_handle
79 !-------------------------------------------------------------------------------------
80 !
81 !* 1.0 Ice content climatologic gradient
82 !
83 IF (lhook) CALL dr_hook('PREP_VER_TEB_GREENROOF',0,zhook_handle)
84 ALLOCATE(zwgi_clim_grad(SIZE(tgr%CUR%XWG,1),SIZE(tgr%CUR%XWG,2)))
85 !
86 zwgi_clim_grad(:,:) = zgradx * exp( - tgrp%XDG(:,:) / zh0 )
87 !-------------------------------------------------------------------------------------
88 !
89 !* 1.1 Temperature profile
90 !
91 ALLOCATE(ztg_ls(SIZE(tgr%CUR%XTG,1),SIZE(tgr%CUR%XTG,2)))
92 ztg_ls(:,:) = tgr%CUR%XTG(:,:)
93 !
94  DO jl=1,SIZE(tgr%CUR%XTG,2)
95  WHERE(tgr%CUR%XTG(:,jl)/=xundef) &
96  tgr%CUR%XTG(:,jl) = tgr%CUR%XTG(:,jl) + xt_clim_grad * (top%XZS - xzs_ls)
97  END DO
98 !
99 !-------------------------------------------------------------------------------------
100 !
101 !* 1.2 Water and ice in the soil
102 !
103 ALLOCATE(zzsfreeze(SIZE(tgr%CUR%XWG,1)))
104 ALLOCATE(zwgtot(SIZE(tgr%CUR%XWG,1)))
105 ALLOCATE(zdw(SIZE(tgr%CUR%XWG,1)))
106 !
107 !* general case
108 !
109 iwork=SIZE(tgr%CUR%XTG,2)
110 !
111  !
112  DO jl=1,iwork
113  !
114  zdw(:) = 0.
115  ! altitude where deep soil freezes (diurnal surface response is not treated)
116  zzsfreeze(:) = top%XZS + (xtt - tgr%CUR%XTG(:,jl)) / xt_clim_grad
117  !
118  WHERE(tgr%CUR%XTG(:,jl)/=xundef)
119  !
120  WHERE (ztg_ls(:,jl) < xtt)
121  !
122  WHERE (top%XZS <= xzs_ls)
123  !
124  WHERE (top%XZS > zzsfreeze)
125  zdw(:) = zwgi_clim_grad(:,jl) * (top%XZS - xzs_ls)
126  ELSEWHERE
127  zdw(:) = zwgi_clim_grad(:,jl) * (zzsfreeze - xzs_ls) + zgradx * (top%XZS - zzsfreeze)
128  ENDWHERE
129  !
130  ELSEWHERE
131  !
132  zdw(:) = zwgi_clim_grad(:,jl) * (top%XZS - xzs_ls)
133  !
134  ENDWHERE
135  !
136  ELSEWHERE
137  !
138  WHERE (top%XZS <= xzs_ls)
139  !
140  zdw(:) = zgradx * (top%XZS - xzs_ls)
141  !
142  ELSEWHERE
143  !
144  zdw(:) = zwgi_clim_grad(:,jl) * (top%XZS - zzsfreeze)
145  !
146  END WHERE
147  !
148  END WHERE
149  !
150  zwgtot(:) = xundef
151  !
152  WHERE(tgr%CUR%XWG(:,jl)/=xundef)
153  zwgtot(:) = tgr%CUR%XWG(:,jl) + tgr%CUR%XWGI(:,jl)
154  ENDWHERE
155  !
156  WHERE(tgr%CUR%XWG(:,jl)/=xundef)
157  tgr%CUR%XWGI(:,jl) = tgr%CUR%XWGI(:,jl) + zdw(:)
158  tgr%CUR%XWG (:,jl) = tgr%CUR%XWG (:,jl) - zdw(:)
159  ENDWHERE
160  !
161  WHERE (tgr%CUR%XWGI(:,jl) < 0..AND.tgr%CUR%XWGI(:,jl)/=xundef)
162  tgr%CUR%XWGI(:,jl) = 0.
163  tgr%CUR%XWG (:,jl) = zwgtot(:)
164  END WHERE
165  !
166  WHERE (tgr%CUR%XWG(:,jl) < xwgmin.AND.tgr%CUR%XWG(:,jl)/=xundef)
167  tgr%CUR%XWG (:,jl) = xwgmin
168  tgr%CUR%XWGI(:,jl) = zwgtot(:) - xwgmin
169  END WHERE
170  !
171  WHERE(tgr%CUR%XWGI(:,jl) > 0..AND.tgr%CUR%XWGI(:,jl)/=xundef)
172  tgr%CUR%XTG(:,jl) = min(xtt,tgr%CUR%XTG(:,jl))
173  ELSEWHERE
174  tgr%CUR%XTG(:,jl) = max(xtt,tgr%CUR%XTG(:,jl))
175  ENDWHERE
176  !
177  ENDWHERE
178  !
179  END DO
180  !
181 !
182 !
183 DEALLOCATE(zzsfreeze )
184 DEALLOCATE(zwgi_clim_grad)
185 DEALLOCATE(zwgtot )
186 DEALLOCATE(zdw )
187 !
188 !* masks where fields are not defined
189 WHERE (tgr%CUR%XTG(:,1:SIZE(tgr%CUR%XWG,2)) == xundef)
190  tgr%CUR%XWG (:,:) = xundef
191  tgr%CUR%XWGI(:,:) = xundef
192 END WHERE
193 !
194 !-------------------------------------------------------------------------------------
195 !
196 ideep_soil = tgro%NLAYER_GR
197  CALL prep_ver_snow(tgr%CUR%TSNOW,xzs_ls,top%XZS,spread(ztg_ls,3,1),spread(tgr%CUR%XTG,3,1),ideep_soil)
198 !
199 !-------------------------------------------------------------------------------------
200 !
201 !* 2. Deallocation of large-scale orography
202 !
203 DEALLOCATE(ztg_ls)
204 IF (lhook) CALL dr_hook('PREP_VER_TEB_GREENROOF',1,zhook_handle)
205 !-------------------------------------------------------------------------------------
206 !
207 END SUBROUTINE prep_ver_teb_greenroof
subroutine prep_ver_snow(TPSNOW, PZS_LS, PZS, PTG_LS, PTG, KDEEP_SOIL)
subroutine prep_ver_teb_greenroof(TGR, TGRO, TGRP, TOP)