SURFEX v8.1
General documentation of Surfex
prep_teb_buffer.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_teb_buffer(HPROGRAM,HSURF,KLUOUT,PFIELD)
7 ! #################################################################################
8 !
9 !!**** *PREP_TEB_BUFFER* - prepares TEB field from operational BUFFER
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !!** METHOD
15 !! ------
16 !!
17 !! REFERENCE
18 !! ---------
19 !!
20 !!
21 !! AUTHOR
22 !! ------
23 !! S. Malardel
24 !!
25 !! MODIFICATIONS
26 !! -------------
27 !! Original 03/2005
28 !!------------------------------------------------------------------
29 !
30 
31 !
33 !
34 USE modi_prep_buffer_grid
37 !
38 USE modd_prep, ONLY : cinterp_type
39 USE modd_grid_buffer, ONLY : nni
40 USE modd_prep_teb, ONLY : xgrid_road, xgrid_wall, xgrid_roof, xgrid_floor, &
41  xti_bld, xti_road, xhui_bld, xti_bld_def
42 USE modd_surf_par, ONLY : xundef
43 !
44 !
45 USE yomhook ,ONLY : lhook, dr_hook
46 USE parkind1 ,ONLY : jprb
47 !
48 IMPLICIT NONE
49 !
50 !* 0.1 declarations of arguments
51 !
52  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
53  CHARACTER(LEN=7), INTENT(IN) :: HSURF ! type of field
54 INTEGER, INTENT(IN) :: KLUOUT ! logical unit of output listing
55 REAL,DIMENSION(:,:), POINTER :: PFIELD ! field to interpolate horizontally
56 !
57 !* 0.2 declarations of local variables
58 !
59 type(date_time) :: tztime_buf ! current date and time
60  CHARACTER(LEN=6) :: YINMODEL ! model from which BUFFER originates
61 REAL, DIMENSION(:), POINTER :: ZFIELD1D ! 1D field read
62 REAL, DIMENSION(:,:), POINTER :: ZFIELD ! field read
63 REAL, DIMENSION(:,:), POINTER :: ZD ! depth of field in the soil
64 REAL :: ZTI_BLD ! internal building temperature
65 REAL(KIND=JPRB) :: ZHOOK_HANDLE
66 !
67 !-------------------------------------------------------------------------------------
68 !
69 !* 1. Reading of grid
70 ! ---------------
71 !
72 IF (lhook) CALL dr_hook('PREP_TEB_BUFFER',0,zhook_handle)
73  CALL prep_buffer_grid(kluout,yinmodel,tztime_buf)
74 !
75 IF (hsurf=='T_FLOOR' .OR. hsurf=='T_WALL ' .OR. hsurf=='T_ROOF ' .OR. hsurf=='T_WIN2 ' .OR. hsurf=='TI_BLD ' .OR. &
76  hsurf=='T_WALLA' .OR. hsurf=='T_WALLB') THEN
77  zti_bld = xti_bld_def
78  IF (xti_bld/=xundef) zti_bld=xti_bld
79 ENDIF
80 !---------------------------------------------------------------------------------------
81 SELECT CASE(hsurf)
82 !---------------------------------------------------------------------------------------
83 !
84 !* 2. Orography
85 ! ---------
86 !
87  CASE('ZS ')
88  SELECT CASE (yinmodel)
89  CASE ('ALADIN')
90  CALL read_buffer_zs(kluout,yinmodel,zfield1d)
91  ALLOCATE(pfield(nni,1))
92  pfield(:,1) = zfield1d(:)
93  DEALLOCATE(zfield1d)
94  END SELECT
95 !
96 !* 3. Profile of temperatures in roads
97 ! --------------------------------
98 !
99  CASE('T_ROAD ')
100  !* reading of the profile and its depth definition
101  SELECT CASE(yinmodel)
102  CASE('ALADIN')
103  CALL read_buffer_tg(kluout,yinmodel,zfield,zd)
104  END SELECT
105  !* if deep road temperature is prescribed
106  IF (xti_road/=xundef) THEN
107  zfield(:,2:) = xti_road
108  END IF
109  CALL teb_profile_buffer(xgrid_road)
110 !
111 !* 3.bis Profile of temperatures in floors
112 ! --------------------------------
113 
114  CASE('T_FLOOR')
115  !* reading of the profile and its depth definition
116  SELECT CASE(yinmodel)
117  CASE('ALADIN')
118  CALL read_buffer_tf_teb(kluout,yinmodel,zti_bld,zfield,zd)
119  END SELECT
120  !* if deep road temperature is prescribed
121  IF (xti_road/=xundef) THEN
122  zfield(:,2:) = xti_road
123  END IF
124  CALL teb_profile_buffer(xgrid_floor)
125 
126 !* 4. Profile of temperatures in walls
127 ! --------------------------------
128 
129  CASE('T_WALLA','T_WALLB')
130  CALL read_buffer_t_teb(kluout,yinmodel,zti_bld,zfield,zd)
131  CALL teb_profile_buffer(xgrid_wall)
132 
133  CASE('T_WIN1 ')
134  SELECT CASE (yinmodel)
135  CASE ('ALADIN')
136  CALL read_buffer_ts(kluout,yinmodel,zfield1d)
137  ALLOCATE(pfield(nni,1))
138  pfield(:,1) = zfield1d(:)
139  DEALLOCATE(zfield1d)
140  END SELECT
141 
142 !* 5. Profile of temperatures in roofs
143 ! --------------------------------
144 
145  CASE('T_ROOF ')
146  CALL read_buffer_t_teb(kluout,yinmodel,zti_bld,zfield,zd)
147  CALL teb_profile_buffer(xgrid_roof)
148 
149 !* 5.bis Profile of temperatures in thermal mass
150 ! -----------------------------------------
151 !
152  CASE('T_MASS ')
153  ALLOCATE(pfield(nni,3))
154  pfield(:,:) = zti_bld
155  CALL teb_profile_buffer(xgrid_floor)
156 !
157 !* 6. Canyon air temperature
158 ! ----------------------
159 !
160  CASE('T_CAN ')
161  SELECT CASE (yinmodel)
162  CASE ('ALADIN')
163  CALL read_buffer_t2(kluout,yinmodel,zfield1d)
164  ALLOCATE(pfield(nni,1))
165  pfield(:,1) = zfield1d(:)
166  DEALLOCATE(zfield1d)
167  END SELECT
168 !
169 !* 7. Canyon air humidity
170 ! -------------------
171 !
172  CASE('Q_CAN ')
173  SELECT CASE (yinmodel)
174  CASE ('ALADIN')
175  ALLOCATE(pfield(nni,1))
176  pfield(:,1) = 0.01
177  END SELECT
178 
179 !
180 !* 9. Deep road temperature
181 ! ---------------------
182 
183  CASE('TI_ROAD')
184  IF (xti_road==xundef) THEN
185  CALL read_buffer_t2(kluout,yinmodel,zfield1d)
186  ALLOCATE(pfield(nni,1))
187  pfield(:,1) = zfield1d(:)
188  DEALLOCATE(zfield1d)
189  ELSE
190  ALLOCATE(pfield(nni,1))
191  pfield = xti_road
192  END IF
193 
194 
195 !* 9. Building temperatures/moisture
196 ! --------------------
197 
198  CASE('TI_BLD ')
199  ALLOCATE(pfield(nni,1))
200  pfield(:,:) = zti_bld
201 !
202  CASE('T_WIN2 ')
203  ALLOCATE(pfield(nni,1))
204  pfield(:,:) = zti_bld
205 
206  CASE('QI_BLD ')
207  ALLOCATE(pfield(nni,1))
208  pfield(:,1) = xundef
209 
210 !* 10. Other quantities (water reservoirs)
211 ! ----------------
212 
213  CASE DEFAULT
214  ALLOCATE(pfield(nni,1))
215  pfield = 0.
216 
217 END SELECT
218 !
219 !* 4. Interpolation method
220 ! --------------------
221 !
222 cinterp_type='BUFFER'
223 !
224 !-------------------------------------------------------------------------------------
225 !-------------------------------------------------------------------------------------
226 !
227 IF (lhook) CALL dr_hook('PREP_TEB_BUFFER',1,zhook_handle)
228 CONTAINS
229 !
230 !-------------------------------------------------------------------------------------
231 !-------------------------------------------------------------------------------------
232 SUBROUTINE teb_profile_buffer(PGRID)
233 !-------------------------------------------------------------------------------------
234 !
235 REAL, DIMENSION(:), INTENT(IN) :: PGRID ! destination grid
236 REAL(KIND=JPRB) :: ZHOOK_HANDLE
237 !
238 !-------------------------------------------------------------------------------------
239 !
240 !* interpolation on fine vertical grid
241 IF (lhook) CALL dr_hook('TEB_PROFILE_BUFFER',0,zhook_handle)
242 ALLOCATE(pfield(SIZE(zfield,1),SIZE(pgrid)))
243  CALL interp_grid(zd,zfield,pgrid,pfield)
244 !
245 !* end
246 DEALLOCATE(zfield)
247 DEALLOCATE(zd)
248 IF (lhook) CALL dr_hook('TEB_PROFILE_BUFFER',1,zhook_handle)
249 
250 END SUBROUTINE teb_profile_buffer
251 !
252 !-------------------------------------------------------------------------------------
253 END SUBROUTINE prep_teb_buffer
subroutine read_buffer_tg(KLUOUT, HINMODEL, PFIELD, PD)
subroutine read_buffer_t2(KLUOUT, HINMODEL, PFIELD)
subroutine prep_buffer_grid(KLUOUT, HINMODEL, TPTIME_BUF)
character(len=6) cinterp_type
Definition: modd_prep.F90:40
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
subroutine read_buffer_zs(KLUOUT, HINMODEL, PFIELD)
subroutine read_buffer_ts(KLUOUT, HINMODEL, PFIELD)
logical lhook
Definition: yomhook.F90:15
subroutine teb_profile_buffer(PGRID)
subroutine prep_teb_buffer(HPROGRAM, HSURF, KLUOUT, PFIELD)
subroutine read_buffer_t_teb(KLUOUT, HINMODEL, PTI, PFIELD, PD)
subroutine read_buffer_tf_teb(KLUOUT, HINMODEL, PTI, PFIELD, PD)