SURFEX v8.1
General documentation of Surfex
prep_teb_grib.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_grib(HPROGRAM,HSURF,HFILE,KLUOUT,PFIELD)
7 ! #################################################################################
8 !
9 !!**** *PREP_TEB_GRIB* - prepares TEB field from operational GRIB
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 !!------------------------------------------------------------------
29 !
30 !
32 !
35 !
37 USE modd_prep_teb, ONLY : xgrid_road, xgrid_wall, xgrid_roof, xgrid_floor, &
38  xti_bld, xti_road, xhui_bld, xti_bld_def, &
39  xhui_bld_def
40 USE modd_surf_par, ONLY : xundef
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  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
51  CHARACTER(LEN=7), INTENT(IN) :: HSURF ! type of field
52  CHARACTER(LEN=28), INTENT(IN) :: HFILE ! name of file
53 INTEGER, INTENT(IN) :: KLUOUT ! logical unit of output listing
54 REAL,DIMENSION(:,:), POINTER :: PFIELD ! field to interpolate horizontally
55 !
56 !* 0.2 declarations of local variables
57 !
58 REAL, DIMENSION(:) , POINTER :: ZMASK => null() ! Land mask
59 REAL, DIMENSION(:), POINTER :: ZFIELD1D => null() ! 1D field read
60 REAL, DIMENSION(:,:), POINTER :: ZFIELD => null() ! field read
61 REAL, DIMENSION(:,:), POINTER :: ZD => null() ! depth of field in the soil
62 REAL :: ZTI_BLD !indoor air temperature
63 !REAL(KIND=JPRB) :: ZHOOK_HANDLE
64 !
65 !-------------------------------------------------------------------------------------
66 !
67 !* 1. Reading of grid
68 ! ---------------
69 !
70 !IF (LHOOK) CALL DR_HOOK('PREP_TEB_GRIB',0,ZHOOK_HANDLE)
71 !
72 IF (trim(hfile).NE.cgrib_file) cgrib_file=""
73 !
74  CALL read_grib_land_mask(hfile,kluout,cinmodel,zmask)
75 !
76 IF (hsurf=='T_FLOOR' .OR. hsurf(1:6)=='T_WALL' .OR. hsurf=='T_ROOF' .OR. &
77  hsurf=='T_WIN2' .OR. hsurf=='TI_BLD' .OR. hsurf=='T_MASS') THEN
78  zti_bld = xti_bld_def
79  IF (xti_bld/=xundef) zti_bld=xti_bld
80 ENDIF
81 !
82 !---------------------------------------------------------------------------------------
83 SELECT CASE(hsurf)
84 !---------------------------------------------------------------------------------------
85 !
86 !* 2. Orography
87 ! ---------
88 !
89  CASE('ZS ')
90  SELECT CASE (cinmodel)
91  CASE ('ECMWF ','ARPEGE','ALADIN','MOCAGE','HIRLAM')
92  CALL read_grib_zs_land(hfile,kluout,cinmodel,zmask,zfield1d)
93  ALLOCATE(pfield(SIZE(zfield1d),1))
94  pfield(:,1) = zfield1d(:)
95  DEALLOCATE(zfield1d)
96  END SELECT
97 !
98 !* 3. Profile of temperatures in roads
99 ! --------------------------------
100 !
101  CASE('T_ROAD')
102  !* reading of the profile and its depth definition
103  SELECT CASE(cinmodel)
104  CASE('ECMWF ')
105  CALL read_grib_tg_ecmwf(hfile,kluout,cinmodel,zmask,zfield,zd)
106  CASE('ARPEGE','ALADIN','MOCAGE')
107  CALL read_grib_tg_meteo_france(hfile,kluout,cinmodel,zmask,zfield,zd)
108  CASE('HIRLAM')
109  CALL read_grib_tg_hirlam(hfile,kluout,cinmodel,zmask,zfield,zd)
110  END SELECT
111  !* if deep road temperature is prescribed
112  IF (xti_road/=xundef) THEN
113  zfield(:,2:) = xti_road
114  END IF
115  CALL teb_profile_grib(xgrid_road)
116 !
117 !* 3.bis Profile of temperatures in floors
118 ! --------------------------------
119 
120  CASE('T_FLOOR')
121  !* reading of the profile and its depth definition
122  SELECT CASE(cinmodel)
123  CASE('ECMWF ','ARPEGE','ALADIN','MOCAGE','HIRLAM')
124  CALL read_grib_tf_teb(hfile,kluout,cinmodel,zti_bld,zmask,zfield,zd)
125  END SELECT
126  !* if deep road temperature is prescribed
127  IF (xti_road/=xundef) THEN
128  zfield(:,2:) = xti_road
129  END IF
130  CALL teb_profile_grib(xgrid_floor)
131 !
132 !* 4. Profile of temperatures in walls
133 ! --------------------------------
134 
135  CASE('T_WALLA','T_WALLB')
136  CALL read_grib_t_teb(hfile,kluout,cinmodel,zti_bld,zmask,zfield,zd)
137  CALL teb_profile_grib(xgrid_wall)
138 
139  CASE('T_WIN1')
140  SELECT CASE (cinmodel)
141  CASE ('ECMWF ','ARPEGE','ALADIN','MOCAGE','HIRLAM')
142  CALL read_grib_ts(hfile,kluout,cinmodel,zmask,zfield1d)
143  ALLOCATE(pfield(nni,1))
144  pfield(:,1) = zfield1d(:)
145  DEALLOCATE(zfield1d)
146  END SELECT
147 !
148 !* 5. Profile of temperatures in roofs
149 ! --------------------------------
150 !
151  CASE('T_ROOF')
152  CALL read_grib_t_teb(hfile,kluout,cinmodel,zti_bld,zmask,zfield,zd)
153  CALL teb_profile_grib(xgrid_roof)
154 !
155 !* 5.bis Profile of temperatures in thermal mass
156 ! -----------------------------------------
157 !
158  CASE('T_MASS')
159  ALLOCATE(pfield(nni,3))
160  pfield(:,:) = zti_bld
161 !
162 !* 6. Canyon air temperature
163 ! ----------------------
164 !
165  CASE('T_CAN ')
166  SELECT CASE (cinmodel)
167  CASE ('ECMWF ','ARPEGE','ALADIN','MOCAGE','HIRLAM')
168  CALL read_grib_t2_land(hfile,kluout,cinmodel,zmask,zfield1d)
169  ALLOCATE(pfield(SIZE(zfield1d),1))
170  pfield(:,1) = zfield1d(:)
171  DEALLOCATE(zfield1d)
172  END SELECT
173 !
174 !* 7. Canyon air humidity
175 ! -------------------
176 !
177  CASE('Q_CAN ')
178  SELECT CASE (cinmodel)
179  CASE ('ECMWF ','ARPEGE','ALADIN','MOCAGE','HIRLAM')
180  ALLOCATE(pfield(nni,1))
181  pfield(:,1) = 0.01
182  END SELECT
183 
184 !
185 !* 9. Deep road temperature
186 ! ---------------------
187 
188  CASE('TI_ROAD')
189  IF (xti_road==xundef) THEN
190  CALL read_grib_t2_land(hfile,kluout,cinmodel,zmask,zfield1d)
191  ALLOCATE(pfield(SIZE(zfield1d),1))
192  pfield(:,1) = zfield1d(:)
193  DEALLOCATE(zfield1d)
194  ELSE
195  ALLOCATE(pfield(nni,1))
196  pfield = xti_road
197  END IF
198 
199 
200 !* 9. Building temperatures/moisture
201 ! --------------------
202 
203  CASE('TI_BLD ')
204  ALLOCATE(pfield(nni,1))
205  pfield = zti_bld
206 
207  CASE('T_WIN2')
208  ALLOCATE(pfield(nni,1))
209  pfield = zti_bld
210 
211  CASE('QI_BLD ')
212  ALLOCATE(pfield(nni,1))
213  pfield(:,1) = xundef
214 
215 !* 10. Other quantities (water reservoirs)
216 ! ----------------
217 
218  CASE DEFAULT
219  ALLOCATE(pfield(nni,1))
220  pfield = 0.
221 
222 END SELECT
223 !
224 DEALLOCATE(zmask)
225 !
226 !* 4. Interpolation method
227 ! --------------------
228 !
229 !-------------------------------------------------------------------------------------
230 !-------------------------------------------------------------------------------------
231 !
232 !IF (LHOOK) CALL DR_HOOK('PREP_TEB_GRIB',1,ZHOOK_HANDLE)
233 CONTAINS
234 !
235 !-------------------------------------------------------------------------------------
236 !-------------------------------------------------------------------------------------
237 SUBROUTINE teb_profile_grib(PGRID)
238 !-------------------------------------------------------------------------------------
239 !
240 REAL, DIMENSION(:), INTENT(IN) :: PGRID ! destination grid
241 !REAL(KIND=JPRB) :: ZHOOK_HANDLE
242 !
243 !
244 !-------------------------------------------------------------------------------------
245 !
246 !* interpolation on fine vertical grid
247 !IF (LHOOK) CALL DR_HOOK('TEB_PROFILE_GRIB',0,ZHOOK_HANDLE)
248 ALLOCATE(pfield(SIZE(zfield,1),SIZE(pgrid)))
249  CALL interp_grid(zd,zfield,pgrid,pfield)
250 !
251 !* end
252 DEALLOCATE(zfield)
253 DEALLOCATE(zd)
254 !IF (LHOOK) CALL DR_HOOK('TEB_PROFILE_GRIB',1,ZHOOK_HANDLE)
255 
256 END SUBROUTINE teb_profile_grib
257 !
258 !-------------------------------------------------------------------------------------
259 END SUBROUTINE prep_teb_grib
static const char * trim(const char *name, int *n)
Definition: drhook.c:2383
character(len=28) cgrib_file
subroutine read_grib_t_teb(HGRIB, KLUOUT, HINMODEL, PTI, PMASK, PT, PD)
subroutine read_grib_tf_teb(HGRIB, KLUOUT, HINMODEL, PTI, PMASK, PTF, PD)
subroutine read_grib_tg_meteo_france(HGRIB, KLUOUT, HINMODEL, PMASK, PTG, PDT)
subroutine read_grib_zs_land(HGRIB, KLUOUT, HINMODEL, PMASK, PZSL)
subroutine read_grib_ts(HGRIB, KLUOUT, HINMODEL, PMASK, PTS)
real, parameter xundef
subroutine teb_profile_grib(PGRID)
character(len=6) cinmodel
subroutine read_grib_tg_hirlam(HGRIB, KLUOUT, HINMODEL, PMASK, PTG, PDT)
subroutine read_grib_t2_land(HGRIB, KLUOUT, HINMODEL, PMASK, ZFIELD)
subroutine prep_teb_grib(HPROGRAM, HSURF, HFILE, KLUOUT, PFIELD)
subroutine read_grib_land_mask(HGRIB, KLUOUT, HINMODEL, PMASK)
subroutine read_grib_tg_ecmwf(HGRIB, KLUOUT, HINMODEL, PMASK, PTG, PD)