SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
pgd_teb_par.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 pgd_teb_par (DTCO, DGU, UG, U, USS, BDD, DTT, DTI, TG, &
7  hprogram,ogarden,ogreenroof,hbld_atype)
8 ! ##############################################################
9 !
10 !!**** *PGD_TEB_PAR* monitor for averaging and interpolations of cover fractions
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !! METHOD
16 !! ------
17 !!
18 !
19 !! EXTERNAL
20 !! --------
21 !!
22 !! IMPLICIT ARGUMENTS
23 !! ------------------
24 !!
25 !! REFERENCE
26 !! ---------
27 !!
28 !! AUTHOR
29 !! ------
30 !!
31 !! V. Masson Meteo-France
32 !!
33 !! MODIFICATION
34 !! ------------
35 !!
36 !! Original 10/12/97
37 !!
38 !! Modified 08/12/05, P. Le Moigne: user defined fields
39 !! G. Pigeon 09/2012: add ROUGH_WALL/ROUGH_ROOF for outdoor convection
40 !! V. Masson 08/2013: adds solar panels
41 !! V. Masson 10/2013: adds residential fraction
42 !!
43 !----------------------------------------------------------------------------
44 !
45 !* 0. DECLARATION
46 ! -----------
47 !
48 !
49 !
53 USE modd_surf_atm_n, ONLY : surf_atm_t
56 USE modd_data_teb_n, ONLY : data_teb_t
57 USE modd_data_isba_n, ONLY : data_isba_t
58 USE modd_teb_grid_n, ONLY : teb_grid_t
59 !
60 USE modd_surf_par, ONLY : xundef, nundef
61 !
62 USE modi_get_luout
63 USE modi_open_namelist
64 USE modi_close_namelist
65 USE modi_ini_var_from_data_0d
68 USE modi_read_csvdata_teb
69 USE modi_bldcode
70 !
71 USE mode_pos_surf
72 !
73 !
74 USE yomhook ,ONLY : lhook, dr_hook
75 USE parkind1 ,ONLY : jprb
76 !
77 USE modi_abor1_sfx
78 !
79 IMPLICIT NONE
80 !
81 !* 0.1 Declaration of arguments
82 ! ------------------------
83 !
84 !
85 TYPE(data_cover_t), INTENT(INOUT) :: dtco
86 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
87 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
88 TYPE(surf_atm_t), INTENT(INOUT) :: u
89 TYPE(surf_atm_sso_t), INTENT(INOUT) :: uss
90 TYPE(bld_desc_t), INTENT(INOUT) :: bdd
91 TYPE(data_teb_t), INTENT(INOUT) :: dtt
92 TYPE(data_isba_t), INTENT(INOUT) :: dti
93 TYPE(teb_grid_t), INTENT(INOUT) :: tg
94 !
95  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! Type of program
96 LOGICAL, INTENT(IN) :: ogarden ! T if urban green areas
97 LOGICAL, INTENT(IN) :: ogreenroof ! T if greenroofs option is activated
98  CHARACTER(LEN=3), INTENT(OUT) :: hbld_atype ! Type of building averaging
99 !
100 !
101 !* 0.2 Declaration of local variables
102 ! ------------------------------
103 !
104 INTEGER :: iluout ! output listing logical unit
105 INTEGER :: ilunam ! namelist file logical unit
106 LOGICAL :: gfound ! true if namelist is found
107 !
108 REAL, DIMENSION(TG%NDIM) :: zwork
109 REAL :: zunif ! temporary variable
110 !
111 !* 0.3 Declaration of namelists
112 ! ------------------------
113 !
114 INTEGER, PARAMETER :: nroof_max = 9
115 INTEGER, PARAMETER :: nroad_max = 9
116 INTEGER, PARAMETER :: nwall_max = 9
117 INTEGER :: npar_road_layer ! number of road layers
118 INTEGER :: npar_roof_layer ! number of roof layers
119 INTEGER :: npar_wall_layer ! number of wall layers
120 !
121 ! Geometric Parameters:
122 !
123 INTEGER :: nunif_bldtype
124  CHARACTER(LEN=28) :: cfnam_bldtype
125  CHARACTER(LEN=6) :: cftyp_bldtype
126 INTEGER :: nunif_bld_age
127  CHARACTER(LEN=28) :: cfnam_bld_age
128  CHARACTER(LEN=6) :: cftyp_bld_age
129  CHARACTER(LEN=28) :: ccsvdatafile
130 INTEGER :: nunif_usetype
131  CHARACTER(LEN=28) :: cfnam_usetype
132  CHARACTER(LEN=6) :: cftyp_usetype
133  CHARACTER(LEN=3) :: cbld_atype ! type of averaging for buildings
134 
135 !
136 REAL :: xunif_bld ! fraction of buildings (-)
137 REAL :: xunif_bld_height ! buildings height 'h' (m)
138 REAL :: xunif_wall_o_hor ! wall surf. / hor. surf. (-)
139 REAL :: xunif_z0_town ! roughness length for momentum (m)
140 REAL :: xunif_garden ! fraction of veg in the streets (-)
141 REAL :: xunif_greenroof ! fraction of greenroofs on roofs (-)
142 REAL :: xunif_road_dir ! road direction (deg from North, clockwise)
143  CHARACTER(LEN=28) :: cfnam_bld ! file name for BLD
144  CHARACTER(LEN=28) :: cfnam_bld_height ! file name for BLD_HEIGHT
145  CHARACTER(LEN=28) :: cfnam_wall_o_hor ! file name for WALL_O_HOR
146  CHARACTER(LEN=28) :: cfnam_z0_town ! file name for Z0_TOWN
147  CHARACTER(LEN=28) :: cfnam_garden ! file name for GARDEN
148  CHARACTER(LEN=28) :: cfnam_greenroof ! file name for GREENROOF
149  CHARACTER(LEN=28) :: cfnam_road_dir ! file name for ROAD_DIR
150  CHARACTER(LEN=6) :: cftyp_bld ! file type for BLD
151  CHARACTER(LEN=6) :: cftyp_bld_height ! file type for BLD_HEIGHT
152  CHARACTER(LEN=6) :: cftyp_wall_o_hor ! file type for WALL_O_HOR
153  CHARACTER(LEN=6) :: cftyp_z0_town ! file type for Z0_TOWN
154  CHARACTER(LEN=6) :: cftyp_garden ! file type for GARDEN
155  CHARACTER(LEN=6) :: cftyp_greenroof ! file type for GREENROOF
156  CHARACTER(LEN=6) :: cftyp_road_dir ! file type for ROAD_DIR
157 !
158 ! Roof parameters
159 !
160 REAL :: xunif_alb_roof ! roof albedo (-)
161 REAL :: xunif_emis_roof ! roof emissivity (-)
162  CHARACTER(LEN=28) :: cfnam_alb_roof ! file name for ALB_ROOF
163  CHARACTER(LEN=28) :: cfnam_emis_roof ! file name for EMIS_ROOF
164  CHARACTER(LEN=6) :: cftyp_alb_roof ! file name for ALB_ROOF
165  CHARACTER(LEN=6) :: cftyp_emis_roof ! file name for EMIS_ROOF
166 REAL, DIMENSION(NROOF_MAX) :: xunif_hc_roof ! roof layers heat capacity (J/K/m3)
167 REAL, DIMENSION(NROOF_MAX) :: xunif_tc_roof ! roof layers thermal conductivity (W/K/m)
168 REAL, DIMENSION(NROOF_MAX) :: xunif_d_roof ! depth of roof layers (m)
169  CHARACTER(LEN=28), DIMENSION(NROOF_MAX) :: cfnam_hc_roof ! file name for HC_ROOF
170  CHARACTER(LEN=28), DIMENSION(NROOF_MAX) :: cfnam_tc_roof ! file name for TC_ROOF
171  CHARACTER(LEN=28), DIMENSION(NROOF_MAX) :: cfnam_d_roof ! file name for D_ROOF
172  CHARACTER(LEN=6), DIMENSION(NROOF_MAX) :: cftyp_hc_roof ! file type for HC_ROOF
173  CHARACTER(LEN=6), DIMENSION(NROOF_MAX) :: cftyp_tc_roof ! file type for TC_ROOF
174  CHARACTER(LEN=6), DIMENSION(NROOF_MAX) :: cftyp_d_roof ! file type for D_ROOF
175 REAL :: xunif_rough_roof ! roof roughness coef
176  CHARACTER(LEN=28) :: cfnam_rough_roof ! file name for ROUGH_ROOF
177  CHARACTER(LEN=6) :: cftyp_rough_roof ! file type for ROUGH_ROOF
178 !
179 !
180 ! Road parameters
181 !
182 REAL :: xunif_alb_road ! road albedo (-)
183 REAL :: xunif_emis_road ! road emissivity (-)
184  CHARACTER(LEN=28) :: cfnam_alb_road ! file name for ALB_ROAD
185  CHARACTER(LEN=28) :: cfnam_emis_road ! file name for EMIS_ROAD
186  CHARACTER(LEN=6) :: cftyp_alb_road ! file type for ALB_ROAD
187  CHARACTER(LEN=6) :: cftyp_emis_road ! file type for EMIS_ROAD
188 REAL, DIMENSION(NROAD_MAX) :: xunif_hc_road ! road layers heat capacity (J/K/m3)
189 REAL, DIMENSION(NROAD_MAX) :: xunif_tc_road ! road layers thermal conductivity (W/K/m)
190 REAL, DIMENSION(NROAD_MAX) :: xunif_d_road ! depth of road layers (m)
191  CHARACTER(LEN=28), DIMENSION(NROAD_MAX) :: cfnam_hc_road ! file name for HC_ROAD
192  CHARACTER(LEN=28), DIMENSION(NROAD_MAX) :: cfnam_tc_road ! file name for TC_ROAD
193  CHARACTER(LEN=28), DIMENSION(NROAD_MAX) :: cfnam_d_road ! file name for D_ROAD
194  CHARACTER(LEN=6), DIMENSION(NROAD_MAX) :: cftyp_hc_road ! file type for HC_ROAD
195  CHARACTER(LEN=6), DIMENSION(NROAD_MAX) :: cftyp_tc_road ! file type for TC_ROAD
196  CHARACTER(LEN=6), DIMENSION(NROAD_MAX) :: cftyp_d_road ! file type for D_ROAD
197 !
198 ! Wall parameters
199 !
200 REAL :: xunif_alb_wall ! wall albedo (-)
201 REAL :: xunif_emis_wall ! wall emissivity (-)
202  CHARACTER(LEN=28) :: cfnam_alb_wall ! file name for ALB_WALL
203  CHARACTER(LEN=28) :: cfnam_emis_wall ! file name for EMIS_WALL
204  CHARACTER(LEN=6) :: cftyp_alb_wall ! file type for ALB_WALL
205  CHARACTER(LEN=6) :: cftyp_emis_wall ! file type for EMIS_WALL
206 REAL, DIMENSION(NWALL_MAX) :: xunif_hc_wall ! wall layers heat capacity (J/K/m3)
207 REAL, DIMENSION(NWALL_MAX) :: xunif_tc_wall ! wall layers thermal conductivity (W/K/m)
208 REAL, DIMENSION(NWALL_MAX) :: xunif_d_wall ! depth of wall layers (m)
209  CHARACTER(LEN=28), DIMENSION(NWALL_MAX) :: cfnam_hc_wall ! file name for HC_WALL
210  CHARACTER(LEN=28), DIMENSION(NWALL_MAX) :: cfnam_tc_wall ! file name for TC_WALL
211  CHARACTER(LEN=28), DIMENSION(NWALL_MAX) :: cfnam_d_wall ! file name for D_WALL
212  CHARACTER(LEN=6), DIMENSION(NWALL_MAX) :: cftyp_hc_wall ! file type for HC_WALL
213  CHARACTER(LEN=6), DIMENSION(NWALL_MAX) :: cftyp_tc_wall ! file type for TC_WALL
214  CHARACTER(LEN=6), DIMENSION(NWALL_MAX) :: cftyp_d_wall ! file type for D_WALL
215 REAL :: xunif_rough_wall ! wall roughness coef
216  CHARACTER(LEN=28) :: cfnam_rough_wall ! file name for ROUGH_WALL
217  CHARACTER(LEN=6) :: cftyp_rough_wall ! file type for ROUGH_WALL
218 REAL :: xunif_residential ! residential fraction
219  CHARACTER(LEN=28) :: cfnam_residential ! file name for RESIDENTIAL
220  CHARACTER(LEN=6) :: cftyp_residential ! file type for RESIDENTIAL
221 !
222 ! anthropogenic fluxes
223 !
224 REAL :: xunif_h_traffic ! anthropogenic sensible
225 ! ! heat fluxes due to traffic (W/m2)
226 REAL :: xunif_le_traffic ! anthropogenic latent
227 ! ! heat fluxes due to traffic (W/m2)
228 REAL :: xunif_h_industry ! anthropogenic sensible
229 ! ! heat fluxes due to factories (W/m2)
230 REAL :: xunif_le_industry ! anthropogenic latent
231 ! ! heat fluxes due to factories (W/m2)
232  CHARACTER(LEN=28) :: cfnam_h_traffic ! file name for H_TRAFFIC
233  CHARACTER(LEN=28) :: cfnam_le_traffic ! file name for LE_TRAFFIC
234  CHARACTER(LEN=28) :: cfnam_h_industry ! file name for H_INDUSTRY
235  CHARACTER(LEN=28) :: cfnam_le_industry ! file name for LE_INDUSTRY
236  CHARACTER(LEN=6) :: cftyp_h_traffic ! file type for H_TRAFFIC
237  CHARACTER(LEN=6) :: cftyp_le_traffic ! file type for LE_TRAFFIC
238  CHARACTER(LEN=6) :: cftyp_h_industry ! file type for H_INDUSTRY
239  CHARACTER(LEN=6) :: cftyp_le_industry ! file type for LE_INDUSTRY
240 !
241 ! Solar panels parameters
242 !
243 REAL :: xunif_emis_panel ! emissivity of solar panel (-)
244 REAL :: xunif_alb_panel ! albedo of solar panel (-)
245 REAL :: xunif_eff_panel ! efficiency of solar panel (-)
246 REAL :: xunif_frac_panel ! fraction of solar panel (-)
247  CHARACTER(LEN=28) :: cfnam_emis_panel ! file name for EMIS_PANEL
248  CHARACTER(LEN=28) :: cfnam_alb_panel ! file name for ALB_PANEL
249  CHARACTER(LEN=28) :: cfnam_eff_panel ! file name for EFF_PANEL
250  CHARACTER(LEN=28) :: cfnam_frac_panel ! file name for FRAC_PANEL
251  CHARACTER(LEN=6) :: cftyp_emis_panel ! file type for EMIS_PANEL
252  CHARACTER(LEN=6) :: cftyp_alb_panel ! file type for ALB_PANEL
253  CHARACTER(LEN=6) :: cftyp_eff_panel ! file type for EFF_PANEL
254  CHARACTER(LEN=6) :: cftyp_frac_panel ! file type for FRAC_PANEL
255 
256 REAL(KIND=JPRB) :: zhook_handle
257 !
258 
259 namelist/nam_data_teb/ npar_roof_layer, npar_road_layer, npar_wall_layer,&
260  cbld_atype, &
261  nunif_bldtype, cfnam_bldtype, cftyp_bldtype, &
262  nunif_bld_age, cfnam_bld_age, cftyp_bld_age, &
263  ccsvdatafile, &
264  nunif_usetype, cfnam_usetype, cftyp_usetype, &
265  xunif_alb_roof, &
266  xunif_emis_roof, xunif_hc_roof, xunif_tc_roof, &
267  xunif_d_roof, xunif_alb_road, xunif_emis_road, &
268  xunif_hc_road, xunif_tc_road, xunif_d_road, &
269  xunif_alb_wall, xunif_emis_wall, xunif_hc_wall, &
270  xunif_tc_wall, xunif_d_wall, &
271  xunif_z0_town, xunif_bld, xunif_bld_height, &
272  xunif_wall_o_hor, &
273  xunif_h_traffic, xunif_le_traffic, &
274  xunif_h_industry, xunif_le_industry, &
275  xunif_garden, xunif_greenroof, &
276  xunif_road_dir, &
277  cfnam_alb_roof, &
278  cfnam_emis_roof, cfnam_hc_roof, cfnam_tc_roof, &
279  cfnam_d_roof, cfnam_alb_road, cfnam_emis_road, &
280  cfnam_hc_road, cfnam_tc_road, cfnam_d_road, &
281  cfnam_alb_wall, cfnam_emis_wall, cfnam_hc_wall, &
282  cfnam_tc_wall, cfnam_d_wall, &
283  cfnam_z0_town, cfnam_bld, cfnam_bld_height, &
284  cfnam_wall_o_hor, &
285  cfnam_h_traffic, cfnam_le_traffic, &
286  cfnam_h_industry, cfnam_le_industry, &
287  cfnam_garden, cfnam_road_dir, cfnam_greenroof, &
288  cftyp_alb_roof, &
289  cftyp_emis_roof, cftyp_hc_roof, cftyp_tc_roof, &
290  cftyp_d_roof, cftyp_alb_road, cftyp_emis_road, &
291  cftyp_hc_road, cftyp_tc_road, cftyp_d_road, &
292  cftyp_alb_wall, cftyp_emis_wall, cftyp_hc_wall, &
293  cftyp_tc_wall, cftyp_d_wall, &
294  cftyp_z0_town, cftyp_bld, cftyp_bld_height, &
295  cftyp_wall_o_hor, &
296  cftyp_h_traffic, cftyp_le_traffic, &
297  cftyp_h_industry, cftyp_le_industry, &
298  cftyp_garden, cftyp_road_dir, cftyp_greenroof, &
299  xunif_rough_roof, cfnam_rough_roof, cftyp_rough_roof, &
300  xunif_rough_wall, cfnam_rough_wall, cftyp_rough_wall, &
301  xunif_residential,cfnam_residential,cftyp_residential,&
302  xunif_emis_panel, cfnam_emis_panel, cftyp_emis_panel, &
303  xunif_alb_panel, cfnam_alb_panel, cftyp_alb_panel, &
304  xunif_eff_panel, cfnam_eff_panel, cftyp_eff_panel, &
305  xunif_frac_panel, cfnam_frac_panel, cftyp_frac_panel
306 
307 !
308 !-------------------------------------------------------------------------------
309 !
310 !* 1. Initializations
311 ! ---------------
312 !
313 IF (lhook) CALL dr_hook('PGD_TEB_PAR',0,zhook_handle)
314 npar_roof_layer=0
315 npar_road_layer=0
316 npar_wall_layer=0
317  cbld_atype ='MAJ'
318 nunif_bldtype = nundef
319 nunif_bld_age = nundef
320 nunif_usetype = nundef
321 xunif_bld = xundef
322 xunif_bld_height = xundef
323 xunif_wall_o_hor = xundef
324 xunif_z0_town = xundef
325 xunif_alb_roof = xundef
326 xunif_emis_roof = xundef
327 xunif_hc_roof = xundef
328 xunif_tc_roof = xundef
329 xunif_d_roof = xundef
330 xunif_alb_road = xundef
331 xunif_emis_road = xundef
332 xunif_hc_road = xundef
333 xunif_tc_road = xundef
334 xunif_d_road = xundef
335 xunif_alb_wall = xundef
336 xunif_emis_wall = xundef
337 xunif_hc_wall = xundef
338 xunif_tc_wall = xundef
339 xunif_d_wall = xundef
340 xunif_h_traffic = xundef
341 xunif_le_traffic = xundef
342 xunif_h_industry = xundef
343 xunif_le_industry = xundef
344 xunif_garden = xundef
345 xunif_greenroof = xundef
346 xunif_road_dir = xundef
347 xunif_rough_roof = xundef
348 xunif_rough_wall = xundef
349 xunif_residential = xundef
350 xunif_emis_panel = xundef
351 xunif_alb_panel = xundef
352 xunif_eff_panel = xundef
353 xunif_frac_panel = xundef
354 
355  cfnam_bldtype = ' '
356  cfnam_bld_age = ' '
357  cfnam_usetype = ' '
358  ccsvdatafile =' '
359  cfnam_bld = ' '
360  cfnam_bld_height = ' '
361  cfnam_wall_o_hor = ' '
362  cfnam_z0_town = ' '
363 
364  cfnam_alb_roof(:) = ' '
365  cfnam_emis_roof(:) = ' '
366  cfnam_hc_roof(:) = ' '
367  cfnam_tc_roof(:) = ' '
368  cfnam_d_roof(:) = ' '
369  cfnam_rough_roof(:) = ' '
370  cfnam_rough_wall(:) = ' '
371  cfnam_residential(:)= ' '
372  cfnam_alb_road(:) = ' '
373  cfnam_emis_road(:) = ' '
374  cfnam_hc_road(:) = ' '
375  cfnam_tc_road(:) = ' '
376  cfnam_d_road(:) = ' '
377  cfnam_alb_wall(:) = ' '
378  cfnam_emis_wall(:) = ' '
379  cfnam_hc_wall(:) = ' '
380  cfnam_tc_wall(:) = ' '
381  cfnam_d_wall(:) = ' '
382 
383  cfnam_h_traffic = ' '
384  cfnam_le_traffic = ' '
385  cfnam_h_industry = ' '
386  cfnam_le_industry = ' '
387 
388  cfnam_garden = ' '
389  cfnam_greenroof = ' '
390  cfnam_road_dir = ' '
391 
392  cfnam_emis_panel = ' '
393  cfnam_alb_panel = ' '
394  cfnam_eff_panel = ' '
395  cfnam_frac_panel = ' '
396 
397  cftyp_bldtype = ' '
398  cftyp_bld_age = ' '
399  cftyp_usetype = ' '
400  cftyp_bld = ' '
401  cftyp_bld_height = ' '
402  cftyp_wall_o_hor = ' '
403  cftyp_z0_town = ' '
404  cftyp_alb_roof(:) = ' '
405  cftyp_emis_roof(:) = ' '
406  cftyp_hc_roof(:) = ' '
407  cftyp_tc_roof(:) = ' '
408  cftyp_d_roof(:) = ' '
409  cftyp_rough_roof(:) = ' '
410  cftyp_rough_wall(:) = ' '
411  cftyp_residential(:) = ' '
412  cftyp_alb_road(:) = ' '
413  cftyp_emis_road(:) = ' '
414  cftyp_hc_road(:) = ' '
415  cftyp_tc_road(:) = ' '
416  cftyp_d_road(:) = ' '
417  cftyp_alb_wall(:) = ' '
418  cftyp_emis_wall(:) = ' '
419  cftyp_hc_wall(:) = ' '
420  cftyp_tc_wall(:) = ' '
421  cftyp_d_wall(:) = ' '
422  cftyp_h_traffic = ' '
423  cftyp_le_traffic = ' '
424  cftyp_h_industry = ' '
425  cftyp_le_industry = ' '
426  cftyp_garden = ' '
427  cftyp_greenroof = ' '
428  cftyp_road_dir = ' '
429 !
430  cftyp_emis_panel = ' '
431  cftyp_alb_panel = ' '
432  cftyp_eff_panel = ' '
433  cftyp_frac_panel = ' '
434 !
435 !-------------------------------------------------------------------------------
436 !
437 !* 2. Input file for cover types
438 ! --------------------------
439 !
440  CALL get_luout(hprogram,iluout)
441  CALL open_namelist(hprogram,ilunam)
442 !
443  CALL posnam(ilunam,'NAM_DATA_TEB',gfound,iluout)
444 IF (gfound) READ(unit=ilunam,nml=nam_data_teb)
445 !
446  CALL close_namelist(hprogram,ilunam)
447 !
448  CALL test_nam_var_surf(iluout,'CBLD_ATYPE',cbld_atype,'ARI','MAJ')
449 !
450 dtt%NPAR_ROOF_LAYER = npar_roof_layer
451 dtt%NPAR_ROAD_LAYER = npar_road_layer
452 dtt%NPAR_WALL_LAYER = npar_wall_layer
453 !
454 hbld_atype = cbld_atype
455 !-------------------------------------------------------------------------------
456 !
457 !* coherence check
458 !
459 IF (( any(xunif_hc_road/=xundef) .OR. any(len_trim(cfnam_hc_road)>0) &
460  .OR. any(xunif_tc_road/=xundef) .OR. any(len_trim(cfnam_tc_road)>0) &
461  .OR. any(xunif_d_road /=xundef) .OR. any(len_trim(cfnam_d_road )>0) &
462  ) .AND. npar_road_layer<1 ) THEN
463  CALL abor1_sfx('In order to initialize road thermal quantities, please specify NPAR_ROAD_LAYER in namelist NAM_DATA_TEB')
464 END IF
465 !
466 IF (( any(xunif_hc_roof/=xundef) .OR. any(len_trim(cfnam_hc_roof)>0) &
467  .OR. any(xunif_tc_roof/=xundef) .OR. any(len_trim(cfnam_tc_roof)>0) &
468  .OR. any(xunif_d_roof /=xundef) .OR. any(len_trim(cfnam_d_roof )>0) &
469  ) .AND. npar_roof_layer<1 ) THEN
470  CALL abor1_sfx('In order to initialize ROOF thermal quantities, please specify NPAR_ROOF_LAYER in namelist NAM_DATA_TEB')
471 END IF
472 !
473 IF (( any(xunif_hc_wall/=xundef) .OR. any(len_trim(cfnam_hc_wall)>0) &
474  .OR. any(xunif_tc_wall/=xundef) .OR. any(len_trim(cfnam_tc_wall)>0) &
475  .OR. any(xunif_d_wall /=xundef) .OR. any(len_trim(cfnam_d_wall )>0) &
476  ) .AND. npar_wall_layer<1 ) THEN
477  CALL abor1_sfx('In order to initialize WALL thermal quantities, please specify NPAR_WALL_LAYER in namelist NAM_DATA_TEB')
478 END IF
479 !-------------------------------------------------------------------------------
480 ALLOCATE(dtt%NPAR_BLDTYPE (tg%NDIM))
481 ALLOCATE(dtt%NPAR_BLD_AGE (tg%NDIM))
482 ALLOCATE(dtt%NPAR_BLDCODE (tg%NDIM))
483 ALLOCATE(dtt%NPAR_USETYPE (tg%NDIM))
484 ALLOCATE(dtt%XPAR_Z0_TOWN (tg%NDIM))
485 ALLOCATE(dtt%XPAR_ALB_ROOF (tg%NDIM))
486 ALLOCATE(dtt%XPAR_EMIS_ROOF (tg%NDIM))
487 ALLOCATE(dtt%XPAR_ALB_ROAD (tg%NDIM))
488 ALLOCATE(dtt%XPAR_EMIS_ROAD (tg%NDIM))
489 ALLOCATE(dtt%XPAR_ALB_WALL (tg%NDIM))
490 ALLOCATE(dtt%XPAR_EMIS_WALL (tg%NDIM))
491 ALLOCATE(dtt%XPAR_BLD (tg%NDIM))
492 ALLOCATE(dtt%XPAR_BLD_HEIGHT (tg%NDIM))
493 ALLOCATE(dtt%XPAR_WALL_O_HOR (tg%NDIM))
494 ALLOCATE(dtt%XPAR_H_TRAFFIC (tg%NDIM))
495 ALLOCATE(dtt%XPAR_LE_TRAFFIC (tg%NDIM))
496 ALLOCATE(dtt%XPAR_H_INDUSTRY (tg%NDIM))
497 ALLOCATE(dtt%XPAR_LE_INDUSTRY (tg%NDIM))
498 ALLOCATE(dtt%XPAR_GARDEN (tg%NDIM))
499 ALLOCATE(dtt%XPAR_GREENROOF (tg%NDIM))
500 ALLOCATE(dtt%XPAR_ROAD_DIR (tg%NDIM))
501 !
502 ALLOCATE(dtt%XPAR_HC_ROOF (tg%NDIM,npar_roof_layer))
503 ALLOCATE(dtt%XPAR_TC_ROOF (tg%NDIM,npar_roof_layer))
504 ALLOCATE(dtt%XPAR_D_ROOF (tg%NDIM,npar_roof_layer))
505 ALLOCATE(dtt%XPAR_HC_ROAD (tg%NDIM,npar_road_layer))
506 ALLOCATE(dtt%XPAR_TC_ROAD (tg%NDIM,npar_road_layer))
507 ALLOCATE(dtt%XPAR_D_ROAD (tg%NDIM,npar_road_layer))
508 ALLOCATE(dtt%XPAR_HC_WALL (tg%NDIM,npar_wall_layer))
509 ALLOCATE(dtt%XPAR_TC_WALL (tg%NDIM,npar_wall_layer))
510 ALLOCATE(dtt%XPAR_D_WALL (tg%NDIM,npar_wall_layer))
511 ALLOCATE(dtt%XPAR_ROUGH_ROOF (tg%NDIM))
512 ALLOCATE(dtt%XPAR_ROUGH_WALL (tg%NDIM))
513 ALLOCATE(dtt%XPAR_RESIDENTIAL (tg%NDIM))
514 !
515 ALLOCATE(dtt%XPAR_EMIS_PANEL (tg%NDIM))
516 ALLOCATE(dtt%XPAR_ALB_PANEL (tg%NDIM))
517 ALLOCATE(dtt%XPAR_EFF_PANEL (tg%NDIM))
518 ALLOCATE(dtt%XPAR_FRAC_PANEL (tg%NDIM))
519 !
520 !-------------------------------------------------------------------------------
521 IF (nroof_max < npar_roof_layer) THEN
522  WRITE(iluout,*) '---------------------------------------------'
523  WRITE(iluout,*) 'Please update pgd_teb_par.f90 routine : '
524  WRITE(iluout,*) 'The maximum number of ROOF LAYER '
525  WRITE(iluout,*) 'in the declaration of the namelist variables '
526  WRITE(iluout,*) 'must be increased to : ', npar_roof_layer
527  WRITE(iluout,*) '---------------------------------------------'
528  CALL abor1_sfx('PGD_TEB_PAR: MAXIMUM NUMBER OF NROOF_LAYER MUST BE INCREASED')
529 ENDIF
530 !-------------------------------------------------------------------------------
531 IF (nroad_max < npar_road_layer) THEN
532  WRITE(iluout,*) '---------------------------------------------'
533  WRITE(iluout,*) 'Please update pgd_teb_par.f90 routine : '
534  WRITE(iluout,*) 'The maximum number of ROAD LAYER '
535  WRITE(iluout,*) 'in the declaration of the namelist variables '
536  WRITE(iluout,*) 'must be increased to : ', npar_road_layer
537  WRITE(iluout,*) '---------------------------------------------'
538  CALL abor1_sfx('PGD_TEB_PAR: MAXIMUM NUMBER OF NROAD_LAYER MUST BE INCREASED')
539 ENDIF
540 !-------------------------------------------------------------------------------
541 IF (nwall_max < npar_wall_layer) THEN
542  WRITE(iluout,*) '---------------------------------------------'
543  WRITE(iluout,*) 'Please update pgd_teb_par.f90 routine : '
544  WRITE(iluout,*) 'The maximum number of WALL LAYER '
545  WRITE(iluout,*) 'in the declaration of the namelist variables '
546  WRITE(iluout,*) 'must be increased to : ', npar_wall_layer
547  WRITE(iluout,*) '---------------------------------------------'
548  CALL abor1_sfx('PGD_TEB_PAR: MAXIMUM NUMBER OF NWALL_LAYER MUST BE INCREASED')
549 ENDIF
550 
551 !-------------------------------------------------------------------------------
552 !
553 !* 3. user defined fields are prescribed
554 ! ----------------------------------
555 !
556 !* building's type
557 zunif = xundef
558 IF (nunif_bldtype/=nundef) zunif=float(nunif_bldtype)
559  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
560  hprogram,'MAJ','BLDTYPE ','TWN', cfnam_bldtype,cftyp_bldtype,zunif,&
561  zwork(:),dtt%LDATA_BLDTYPE )
562 IF (.NOT. dtt%LDATA_BLDTYPE) THEN
563  DEALLOCATE(dtt%NPAR_BLDTYPE)
564 ELSE
565  dtt%NPAR_BLDTYPE = nint(zwork)
566 END IF
567 !
568 !* building's age
569 zunif = xundef
570 IF (nunif_bld_age/=nundef) zunif=float(nunif_bld_age)
571  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
572  hprogram,'ARI','BLD_AGE ','TWN', cfnam_bld_age,cftyp_bld_age,zunif,&
573  zwork(:),dtt%LDATA_BLD_AGE )
574 IF (.NOT. dtt%LDATA_BLD_AGE) THEN
575  DEALLOCATE(dtt%NPAR_BLD_AGE)
576 ELSE
577  dtt%NPAR_BLD_AGE = nint(zwork)
578 END IF
579 !
580 IF (dtt%LDATA_BLDTYPE .AND. .NOT. dtt%LDATA_BLD_AGE) THEN
581  WRITE(iluout,*) '---------------------------------------------'
582  WRITE(iluout,*) ' You chose to define building types : '
583  IF (nunif_bldtype/=nundef) THEN
584  WRITE(iluout,*) ' NUNIF_BLDTYPE=', nunif_bldtype
585  ELSE
586  WRITE(iluout,*) ' CFNAM_BLDTYPE =',cfnam_bldtype
587  WRITE(iluout,*) ' CFTYP_BLDTYPE =',cftyp_bldtype
588  END IF
589  WRITE(iluout,*) ' But '
590  WRITE(iluout,*) " You did not chose to define building's age"
591  WRITE(iluout,*) '- - - - - - - - - - - - - - - - - - - - - - -'
592  WRITE(iluout,*) ' Please define the construction date of the buildings. '
593  WRITE(iluout,*) ' To do so, use either :'
594  WRITE(iluout,*) ' NUNIF_BLD_AGE (to have a uniform construction date for all buildings'
595  WRITE(iluout,*) ' or CFNAM_BLD_AGE and CFTYP_BLD_AGE (to incorporate spatial data ) '
596  WRITE(iluout,*) '---------------------------------------------'
597  CALL abor1_sfx("PGD_TEB_PAR: Building's age data is missing")
598 END IF
599 !
600 !* building's use
601 zunif = xundef
602 IF (nunif_usetype/=nundef) zunif=float(nunif_usetype)
603  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
604  hprogram,'MAJ','USETYPE ','TWN', cfnam_usetype,cftyp_usetype,zunif,&
605  zwork(:),dtt%LDATA_USETYPE )
606 IF (.NOT. dtt%LDATA_USETYPE) THEN
607  DEALLOCATE(dtt%NPAR_USETYPE)
608 ELSE
609  dtt%NPAR_USETYPE = nint(zwork)
610 END IF
611 !
612 IF (dtt%LDATA_BLDTYPE .OR. dtt%LDATA_BLD_AGE .OR. dtt%LDATA_USETYPE) CALL read_csvdata_teb(bdd, &
613  hprogram,ccsvdatafile)
614 !
615 !* building's code
616 IF (ASSOCIATED(dtt%NPAR_BLDTYPE)) dtt%NPAR_BLDCODE(:) = bldcode(bdd, dtt%NPAR_BLDTYPE,dtt%NPAR_BLD_AGE)
617 !
618 !
619 !* other building parameters
620  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
621  hprogram,'ARI','BLD ','TWN', cfnam_bld,cftyp_bld,xunif_bld,dtt%XPAR_BLD,dtt%LDATA_BLD )
622 IF (.NOT.dtt%LDATA_BLD) DEALLOCATE(dtt%XPAR_BLD)
623 !
624  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
625  hprogram,'ARI','BLD_HEIGHT ','TWN',cfnam_bld_height,cftyp_bld_height,xunif_bld_height,&
626  dtt%XPAR_BLD_HEIGHT,dtt%LDATA_BLD_HEIGHT)
627 IF (.NOT.dtt%LDATA_BLD_HEIGHT) DEALLOCATE(dtt%XPAR_BLD_HEIGHT)
628 !
629  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
630  hprogram,'ARI','WALL_O_HOR ','TWN',cfnam_wall_o_hor,cftyp_wall_o_hor,xunif_wall_o_hor,&
631  dtt%XPAR_WALL_O_HOR,dtt%LDATA_WALL_O_HOR)
632 IF (.NOT.dtt%LDATA_WALL_O_HOR) DEALLOCATE(dtt%XPAR_WALL_O_HOR)
633 !
634  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
635  hprogram,'CDN','Z0_TOWN ','TWN',cfnam_z0_town,cftyp_z0_town,xunif_z0_town,&
636  dtt%XPAR_Z0_TOWN,dtt%LDATA_Z0_TOWN)
637 IF (.NOT.dtt%LDATA_Z0_TOWN) DEALLOCATE(dtt%XPAR_Z0_TOWN)
638 !
639  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
640  hprogram,cbld_atype,'ALB_ROOF ','TWN',cfnam_alb_roof,cftyp_alb_roof,xunif_alb_roof ,&
641  dtt%XPAR_ALB_ROOF,dtt%LDATA_ALB_ROOF)
642 IF (.NOT.dtt%LDATA_ALB_ROOF) DEALLOCATE(dtt%XPAR_ALB_ROOF)
643 !
644  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
645  hprogram,cbld_atype,'EMIS_ROOF ','TWN',cfnam_emis_roof,cftyp_emis_roof,xunif_emis_roof ,&
646  dtt%XPAR_EMIS_ROOF,dtt%LDATA_EMIS_ROOF)
647 IF (.NOT.dtt%LDATA_EMIS_ROOF) DEALLOCATE(dtt%XPAR_EMIS_ROOF)
648 !
649  CALL ini_var_from_data(dtco, dgu, ug, u, uss, dti, &
650  hprogram,cbld_atype,'HC_ROOF ','TWN',cfnam_hc_roof,cftyp_hc_roof, &
651  xunif_hc_roof,dtt%XPAR_HC_ROOF,dtt%LDATA_HC_ROOF )
652 IF (.NOT.dtt%LDATA_HC_ROOF) DEALLOCATE(dtt%XPAR_HC_ROOF)
653 !
654  CALL ini_var_from_data(dtco, dgu, ug, u, uss, dti, &
655  hprogram,cbld_atype,'TC_ROOF ','TWN',cfnam_tc_roof,cftyp_tc_roof, &
656  xunif_tc_roof ,dtt%XPAR_TC_ROOF, dtt%LDATA_TC_ROOF )
657 IF (.NOT.dtt%LDATA_TC_ROOF) DEALLOCATE(dtt%XPAR_TC_ROOF)
658 !
659  CALL ini_var_from_data(dtco, dgu, ug, u, uss, dti, &
660  hprogram,cbld_atype,'D_ROOF ','TWN',cfnam_d_roof,cftyp_d_roof, &
661  xunif_d_roof ,dtt%XPAR_D_ROOF , dtt%LDATA_D_ROOF )
662 IF (.NOT.dtt%LDATA_D_ROOF) DEALLOCATE(dtt%XPAR_D_ROOF)
663 !
664  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
665  hprogram,'ARI','ALB_ROAD ','TWN',cfnam_alb_road ,cftyp_alb_road ,xunif_alb_road ,&
666  dtt%XPAR_ALB_ROAD, dtt%LDATA_ALB_ROAD )
667 IF (.NOT.dtt%LDATA_ALB_ROAD) DEALLOCATE(dtt%XPAR_ALB_ROAD)
668 !
669  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
670  hprogram,'ARI','EMIS_ROAD ','TWN',cfnam_emis_road ,cftyp_emis_road ,xunif_emis_road ,&
671  dtt%XPAR_EMIS_ROAD, dtt%LDATA_EMIS_ROAD )
672 IF (.NOT.dtt%LDATA_EMIS_ROAD) DEALLOCATE(dtt%XPAR_EMIS_ROAD)
673 !
674  CALL ini_var_from_data(dtco, dgu, ug, u, uss, dti, &
675  hprogram,cbld_atype,'HC_ROAD ','TWN',cfnam_hc_road ,cftyp_hc_road , &
676  xunif_hc_road ,dtt%XPAR_HC_ROAD, dtt%LDATA_HC_ROAD )
677 IF (.NOT.dtt%LDATA_HC_ROAD) DEALLOCATE(dtt%XPAR_HC_ROAD)
678 !
679  CALL ini_var_from_data(dtco, dgu, ug, u, uss, dti, &
680  hprogram,cbld_atype,'TC_ROAD ','TWN',cfnam_tc_road ,cftyp_tc_road , &
681  xunif_tc_road ,dtt%XPAR_TC_ROAD, dtt%LDATA_TC_ROAD )
682 IF (.NOT.dtt%LDATA_TC_ROAD) DEALLOCATE(dtt%XPAR_TC_ROAD)
683 !
684  CALL ini_var_from_data(dtco, dgu, ug, u, uss, dti, &
685  hprogram,'ARI','D_ROAD ','TWN',cfnam_d_road ,cftyp_d_road , &
686  xunif_d_road ,dtt%XPAR_D_ROAD , dtt%LDATA_D_ROAD )
687 IF (.NOT.dtt%LDATA_D_ROAD) DEALLOCATE(dtt%XPAR_D_ROAD)
688 !
689  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
690  hprogram,cbld_atype,'ALB_WALL ','TWN',cfnam_alb_wall ,cftyp_alb_wall ,xunif_alb_wall ,&
691  dtt%XPAR_ALB_WALL, dtt%LDATA_ALB_WALL )
692 IF (.NOT.dtt%LDATA_ALB_WALL) DEALLOCATE(dtt%XPAR_ALB_WALL)
693 !
694  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
695  hprogram,cbld_atype,'EMIS_WALL ','TWN',cfnam_emis_wall ,cftyp_emis_wall ,xunif_emis_wall ,&
696  dtt%XPAR_EMIS_WALL, dtt%LDATA_EMIS_WALL )
697 IF (.NOT.dtt%LDATA_EMIS_WALL) DEALLOCATE(dtt%XPAR_EMIS_WALL)
698 !
699  CALL ini_var_from_data(dtco, dgu, ug, u, uss, dti, &
700  hprogram,cbld_atype,'HC_WALL ','TWN',cfnam_hc_wall ,cftyp_hc_wall , &
701  xunif_hc_wall ,dtt%XPAR_HC_WALL, dtt%LDATA_HC_WALL )
702 IF (.NOT.dtt%LDATA_HC_WALL) DEALLOCATE(dtt%XPAR_HC_WALL)
703 !
704  CALL ini_var_from_data(dtco, dgu, ug, u, uss, dti, &
705  hprogram,cbld_atype,'TC_WALL ','TWN',cfnam_tc_wall ,cftyp_tc_wall , &
706  xunif_tc_wall ,dtt%XPAR_TC_WALL, dtt%LDATA_TC_WALL )
707 IF (.NOT.dtt%LDATA_TC_WALL) DEALLOCATE(dtt%XPAR_TC_WALL)
708 !
709  CALL ini_var_from_data(dtco, dgu, ug, u, uss, dti, &
710  hprogram,cbld_atype,'D_WALL ','TWN',cfnam_d_wall ,cftyp_d_wall , &
711  xunif_d_wall ,dtt%XPAR_D_WALL , dtt%LDATA_D_WALL )
712 IF (.NOT.dtt%LDATA_D_WALL) DEALLOCATE(dtt%XPAR_D_WALL)
713 !
714  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
715  hprogram,'ARI','H_TRAFFIC ','TWN',cfnam_h_traffic ,cftyp_h_traffic ,xunif_h_traffic ,&
716  dtt%XPAR_H_TRAFFIC, dtt%LDATA_H_TRAFFIC )
717 IF (.NOT.dtt%LDATA_H_TRAFFIC) DEALLOCATE(dtt%XPAR_H_TRAFFIC)
718 !
719  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
720  hprogram,'ARI','LE_TRAFFIC ','TWN',cfnam_le_traffic ,cftyp_le_traffic ,xunif_le_traffic ,&
721  dtt%XPAR_LE_TRAFFIC, dtt%LDATA_LE_TRAFFIC )
722 IF (.NOT.dtt%LDATA_LE_TRAFFIC) DEALLOCATE(dtt%XPAR_LE_TRAFFIC)
723 !
724  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
725  hprogram,'ARI','H_INDUSTRY ','TWN',cfnam_h_industry ,cftyp_h_industry ,xunif_h_industry ,&
726  dtt%XPAR_H_INDUSTRY, dtt%LDATA_H_INDUSTRY )
727 IF (.NOT.dtt%LDATA_H_INDUSTRY) DEALLOCATE(dtt%XPAR_H_INDUSTRY)
728 !
729  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
730  hprogram,'ARI','LE_INDUSTRY','TWN',cfnam_le_industry,cftyp_le_industry,xunif_le_industry,&
731  dtt%XPAR_LE_INDUSTRY, dtt%LDATA_LE_INDUSTRY )
732 IF (.NOT.dtt%LDATA_LE_INDUSTRY) DEALLOCATE(dtt%XPAR_LE_INDUSTRY)
733 !
734  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
735  hprogram,cbld_atype,'ROUGH_ROOF','TWN',cfnam_rough_roof,cftyp_rough_roof,xunif_rough_roof ,&
736  dtt%XPAR_ROUGH_ROOF,dtt%LDATA_ROUGH_ROOF)
737 IF (.NOT.dtt%LDATA_ROUGH_ROOF) DEALLOCATE(dtt%XPAR_ROUGH_ROOF)
738 !
739  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
740  hprogram,cbld_atype,'ROUGH_WALL','TWN',cfnam_rough_wall,cftyp_rough_wall,xunif_rough_wall ,&
741  dtt%XPAR_ROUGH_WALL,dtt%LDATA_ROUGH_WALL)
742 IF (.NOT.dtt%LDATA_ROUGH_WALL) DEALLOCATE(dtt%XPAR_ROUGH_WALL)
743 !
744  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
745  hprogram,cbld_atype,'RESIDENTIAL','TWN',cfnam_residential,cftyp_residential,xunif_residential ,&
746  dtt%XPAR_RESIDENTIAL,dtt%LDATA_RESIDENTIAL)
747 IF (.NOT.dtt%LDATA_RESIDENTIAL) DEALLOCATE(dtt%XPAR_RESIDENTIAL)
748 !-------------------------------------------------------------------------------
749 !
750 !* coherence checks
751 !
752  CALL coherence_thermal_data('ROAD',dtt%LDATA_HC_ROAD,dtt%LDATA_TC_ROAD,dtt%LDATA_D_ROAD)
753  CALL coherence_thermal_data('ROOF',dtt%LDATA_HC_ROOF,dtt%LDATA_TC_ROOF,dtt%LDATA_D_ROOF)
754  CALL coherence_thermal_data('WALL',dtt%LDATA_HC_WALL,dtt%LDATA_TC_WALL,dtt%LDATA_D_WALL)
755 
756 !-------------------------------------------------------------------------------
757 !
758 !* road directions
759 !
760  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
761  hprogram,'ARI','ROAD_DIR ','TWN',cfnam_road_dir ,cftyp_road_dir ,xunif_road_dir ,&
762  dtt%XPAR_ROAD_DIR, dtt%LDATA_ROAD_DIR )
763 IF (.NOT.dtt%LDATA_ROAD_DIR) DEALLOCATE(dtt%XPAR_ROAD_DIR)
764 !
765 !-------------------------------------------------------------------------------
766 !
767 !* solar panels
768 !
769  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
770  hprogram,'ARI','EMIS_PANEL ','BLD',cfnam_emis_panel,cftyp_emis_panel,xunif_emis_panel,&
771  dtt%XPAR_EMIS_PANEL, dtt%LDATA_EMIS_PANEL )
772 IF (.NOT.dtt%LDATA_EMIS_PANEL) DEALLOCATE(dtt%XPAR_EMIS_PANEL)
773  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
774  hprogram,'ARI','ALB_PANEL ','BLD',cfnam_alb_panel ,cftyp_alb_panel ,xunif_alb_panel ,&
775  dtt%XPAR_ALB_PANEL , dtt%LDATA_ALB_PANEL )
776 IF (.NOT.dtt%LDATA_ALB_PANEL ) DEALLOCATE(dtt%XPAR_ALB_PANEL )
777  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
778  hprogram,'ARI','EFF_PANEL ','BLD',cfnam_eff_panel ,cftyp_eff_panel ,xunif_eff_panel ,&
779  dtt%XPAR_EFF_PANEL , dtt%LDATA_EFF_PANEL )
780 IF (.NOT.dtt%LDATA_EFF_PANEL ) DEALLOCATE(dtt%XPAR_EFF_PANEL )
781  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
782  hprogram,'ARI','FRAC_PANEL ','BLD',cfnam_frac_panel,cftyp_frac_panel,xunif_frac_panel,&
783  dtt%XPAR_FRAC_PANEL, dtt%LDATA_FRAC_PANEL )
784 IF (.NOT.dtt%LDATA_FRAC_PANEL) DEALLOCATE(dtt%XPAR_FRAC_PANEL)
785 !
786 !-------------------------------------------------------------------------------
787 !
788 !* greenroof fraction
789 !
790 IF (ogreenroof) THEN
791  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
792  hprogram,cbld_atype,'GREENROOF','BLD',cfnam_greenroof,cftyp_greenroof,xunif_greenroof ,&
793  dtt%XPAR_GREENROOF,dtt%LDATA_GREENROOF)
794  IF (.NOT.dtt%LDATA_GREENROOF) DEALLOCATE(dtt%XPAR_GREENROOF)
795 ELSE IF ( (xunif_greenroof/=0. .AND. xunif_greenroof/=xundef) .OR. len_trim(cfnam_greenroof)/=0) THEN
796  WRITE(iluout,*) '---------------------------------------------'
797  WRITE(iluout,*) ' You chose not to include greenroofs in urban areas : LGREENROOF=.FALSE. '
798  WRITE(iluout,*) ' But '
799  IF (xunif_greenroof/=0. .AND. xunif_greenroof/=xundef) THEN
800  WRITE(iluout,*) ' You also chose a greenroof fraction that is not zero : XUNIF_GREENROOF=',xunif_greenroof
801  ELSE
802  WRITE(iluout,*) ' You also chose a greenroof fraction that is not zero : CFNAM_GREENROOF=',cfnam_greenroof
803  END IF
804  WRITE(iluout,*) '- - - - - - - - - - - - - - - - - - - - - - -'
805  WRITE(iluout,*) ' Please choose either:'
806  WRITE(iluout,*) ' LGREENROOF=.TRUE. or set GREENROOF fraction to zero (XUNIF_GREENROOF=0.) in namelist PGD_TEB_PAR'
807  WRITE(iluout,*) '---------------------------------------------'
808  CALL abor1_sfx('PGD_TEB_PAR: GREENROOF flag and GREENROOF fraction not coherent')
809 END IF
810 !
811 !-------------------------------------------------------------------------------
812 !
813 !* gardens
814 !
815 IF (ogarden) THEN
816  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
817  hprogram,'ARI','GARDEN ','TWN',cfnam_garden ,cftyp_garden ,xunif_garden ,&
818  dtt%XPAR_GARDEN, dtt%LDATA_GARDEN )
819  IF (.NOT.dtt%LDATA_GARDEN) DEALLOCATE(dtt%XPAR_GARDEN)
820 ELSE IF ( (xunif_garden/=0. .AND. xunif_garden/=xundef) .OR. len_trim(cfnam_garden)/=0) THEN
821  WRITE(iluout,*) '---------------------------------------------'
822  WRITE(iluout,*) ' You chose not to include gardens in urban areas : LGARDEN=.FALSE. '
823  WRITE(iluout,*) ' But '
824  IF (xunif_garden/=0. .AND. xunif_garden/=xundef) THEN
825  WRITE(iluout,*) ' You also chose a garden fraction that is not zero : XUNIF_GARDEN=',xunif_garden
826  ELSE
827  WRITE(iluout,*) ' You also chose a garden fraction that is not zero : CFNAM_GARDEN=',cfnam_garden
828  END IF
829  WRITE(iluout,*) '- - - - - - - - - - - - - - - - - - - - - - -'
830  WRITE(iluout,*) ' Please choose either:'
831  WRITE(iluout,*) ' LGARDEN=.TRUE. or set GARDEN fraction to zero (XUNIF_GARDEN=0.) in namelist PGD_TEB_PAR'
832  WRITE(iluout,*) '- - - - - - - - - - - - - - - - - - - - - - -'
833  WRITE(iluout,*) ' Beware that in this case, it may be necessary to change the'
834  WRITE(iluout,*) ' road fraction if you want to keep the same canyon aspect ratio'
835  WRITE(iluout,*) '---------------------------------------------'
836  CALL abor1_sfx('PGD_TEB_PAR: GARDEN flag and GARDEN fraction not coherent')
837 END IF
838 !
839 !
840 !-------------------------------------------------------------------------------
841 IF (lhook) CALL dr_hook('PGD_TEB_PAR',1,zhook_handle)
842 !-------------------------------------------------------------------------------
843  CONTAINS
844 SUBROUTINE coherence_thermal_data(HTYPE,ODATA_HC,ODATA_TC,ODATA_D)
845  CHARACTER(LEN=4), INTENT(IN) :: htype
846 LOGICAL, INTENT(IN) :: odata_hc
847 LOGICAL, INTENT(IN) :: odata_tc
848 LOGICAL, INTENT(IN) :: odata_d
849 !
850 IF (odata_hc .OR. odata_tc .OR. odata_d) THEN
851  IF (.NOT. (odata_hc .AND. odata_tc .AND. odata_d)) THEN
852  WRITE(iluout,*) '*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*'
853  WRITE(iluout,*) 'When specifying data for thermal ',trim(htype),' characteristics,'
854  WRITE(iluout,*) 'All three parameters MUST be defined:'
855  WRITE(iluout,*) 'Heat capacity, Thermal conductivity and depths of layers'
856  WRITE(iluout,*) ' '
857  WRITE(iluout,*) 'In your case :'
858  IF (odata_hc) THEN
859  WRITE(iluout,*) 'Heat capacity is defined'
860  ELSE
861  WRITE(iluout,*) 'Heat capacity is NOT defined'
862  END IF
863  IF (odata_tc) THEN
864  WRITE(iluout,*) 'Thermal conductivity is defined'
865  ELSE
866  WRITE(iluout,*) 'Thermal conductivity is NOT defined'
867  END IF
868  IF (odata_d) THEN
869  WRITE(iluout,*) 'Depths of layers are defined'
870  ELSE
871  WRITE(iluout,*) 'Depths of layers are NOT defined'
872  END IF
873  WRITE(iluout,*) '*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*'
874  CALL abor1_sfx('Heat capacity, Thermal conductivity and depths of layers MUST all be defined for '//htype)
875  END IF
876 END IF
877 END SUBROUTINE coherence_thermal_data
878 !-------------------------------------------------------------------------------
879 !
880 END SUBROUTINE pgd_teb_par
subroutine coherence_thermal_data(HTYPE, ODATA_HC, ODATA_TC, ODATA_D)
integer function, dimension(size(ktype)) bldcode(BDD, KTYPE, KAGE)
Definition: bldcode.F90:5
subroutine pgd_teb_par(DTCO, DGU, UG, U, USS, BDD, DTT, DTI, TG, HPROGRAM, OGARDEN, OGREENROOF, HBLD_ATYPE)
Definition: pgd_teb_par.F90:6
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine read_csvdata_teb(BDD, HPROGRAM, HFILE)
subroutine close_namelist(HPROGRAM, KLUNAM)
subroutine ini_var_from_data_0d(DTCO, DGU, UG, U, USS, HPROGRAM, HATYPE, HNAME, HTYPE, HFNAM, HFTYP, PUNIF, PFIELD, OPRESENT)
subroutine posnam(KULNAM, HDNAML, OFOUND, KLUOUT)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine open_namelist(HPROGRAM, KLUNAM, HFILE)