SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
pgd_bem_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_bem_par (DTCO, DGU, UG, U, USS, DTB, DTI, TG, &
7  hprogram,oautosize)
8 ! ##########################################
9 !
10 !!**** *PGD_BEM_PAR* monitor for averaging and interpolations of BEM input data
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 !! G. Pigeon Meteo-France
32 !!
33 !! MODIFICATION
34 !! ------------
35 !!
36 !! Original 08/2011
37 !! G. Pigeon 09/2012, NPAR_FLOOR_LAYER default to 1
38 !!
39 !!
40 !----------------------------------------------------------------------------
41 !
42 !* 0. DECLARATION
43 ! -----------
44 !
45 !
49 USE modd_surf_atm_n, ONLY : surf_atm_t
51 USE modd_data_bem_n, ONLY : data_bem_t
52 USE modd_data_isba_n, ONLY : data_isba_t
53 USE modd_teb_grid_n, ONLY : teb_grid_t
54 !
55 USE modd_surf_par, ONLY : xundef
56 !
57 USE yomhook ,ONLY : lhook, dr_hook
58 USE parkind1 ,ONLY : jprb
59 !
60 USE modi_get_luout
61 USE modi_open_namelist
62 USE modi_close_namelist
64 USE modi_ini_var_from_data_0d
66 USE modi_abor1_sfx
67 !
68 USE mode_pos_surf
69 !
70 IMPLICIT NONE
71 !
72 !* 0.1 Declaration of arguments
73 ! ------------------------
74 !
75 !
76 TYPE(data_cover_t), INTENT(INOUT) :: dtco
77 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
78 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
79 TYPE(surf_atm_t), INTENT(INOUT) :: u
80 TYPE(surf_atm_sso_t), INTENT(INOUT) :: uss
81 TYPE(data_bem_t), INTENT(INOUT) :: dtb
82 TYPE(data_isba_t), INTENT(INOUT) :: dti
83 TYPE(teb_grid_t), INTENT(INOUT) :: tg
84 !
85  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! Type of program
86 LOGICAL, INTENT(IN) :: oautosize ! T for automatic determination
87 ! ! of HVAC systems charcateristics
88 !
89 !
90 !* 0.2 Declaration of local variables
91 ! ------------------------------
92 !
93 INTEGER :: iluout ! output listing logical unit
94 INTEGER :: ilunam ! namelist file logical unit
95 LOGICAL :: gfound ! true if namelist is found
96 INTEGER :: jlayer ! loop counter on layers
97 !
98 !
99 !* 0.3 Declaration of namelists
100 ! ------------------------
101 !
102 ! bem options
103 !
104 INTEGER, PARAMETER :: nfloor_max = 9
105 INTEGER :: npar_floor_layer ! number of floor layers
106 !
107 REAL :: xunif_shade !
108  CHARACTER(LEN=28) :: cfnam_shade !
109  CHARACTER(LEN=6) :: cftyp_shade !
110 REAL :: xunif_natvent !
111  CHARACTER(LEN=28) :: cfnam_natvent !
112  CHARACTER(LEN=6) :: cftyp_natvent !
113 !
114 ! Floor parameters
115 !
116 REAL, DIMENSION(NFLOOR_MAX) :: xunif_hc_floor ! floor layers heat capacity (J/K/m3)
117 REAL, DIMENSION(NFLOOR_MAX) :: xunif_tc_floor ! floor layers thermal conduc (W/K/m)
118 REAL, DIMENSION(NFLOOR_MAX) :: xunif_d_floor ! depth of floor layers (m)
119 REAL :: xunif_floor_height ! building floor height [m]
120  CHARACTER(LEN=28), DIMENSION(NFLOOR_MAX):: cfnam_hc_floor ! file name for HC_FLOOR
121  CHARACTER(LEN=28), DIMENSION(NFLOOR_MAX):: cfnam_tc_floor ! file name for TC_FLOOR
122  CHARACTER(LEN=28), DIMENSION(NFLOOR_MAX):: cfnam_d_floor ! file name for D_FLOOR
123  CHARACTER(LEN=28) :: cfnam_floor_height ! file name for FLOOR_HEIGHT
124  CHARACTER(LEN=6), DIMENSION(NFLOOR_MAX):: cftyp_hc_floor ! file type for HC_FLOOR
125  CHARACTER(LEN=6), DIMENSION(NFLOOR_MAX):: cftyp_tc_floor ! file type for TC_FLOOR
126  CHARACTER(LEN=6), DIMENSION(NFLOOR_MAX):: cftyp_d_floor ! file type for D_FLOOR
127  CHARACTER(LEN=6) :: cftyp_floor_height ! file type for FLOOR_HEIGHT
128 !
129 ! AC systems parameters
130 !
131 REAL :: xunif_tcool_target !cooling setpoint
132 REAL :: xunif_theat_target !heating setpoint
133 REAL :: xunif_f_waste_can ! fraction of waste heat into the canyon
134 REAL :: xunif_eff_heat ! efficiency of the heating system
135 REAL :: xunif_hr_target ! Relative humidity setpoint
136 REAL :: xunif_cap_sys_heat ! Capacity of the heating system
137 REAL :: xunif_cap_sys_rat ! Rated capacity of the cooling system
138 REAL :: xunif_t_adp ! Apparatus dewpoint temperature of the
139 REAL :: xunif_m_sys_rat ! Rated HVAC mass flow rate
140 REAL :: xunif_cop_rat ! Rated COP of the cooling system
141 REAL :: xunif_f_water_cond ! fraction of evaporation of condensers
142  CHARACTER(LEN=28) :: cfnam_tcool_target ! file name for TCOOL_TARGET
143  CHARACTER(LEN=28) :: cfnam_theat_target ! file name for THEAT_TARGET
144  CHARACTER(LEN=28) :: cfnam_f_waste_can ! file name for F_WASTE_CAN
145  CHARACTER(LEN=28) :: cfnam_eff_heat ! file name for EFF_HEAT
146  CHARACTER(LEN=28) :: cfnam_hr_target ! Relative humidity setpoint
147  CHARACTER(LEN=28) :: cfnam_cap_sys_heat ! Capacity of the heating system
148  CHARACTER(LEN=28) :: cfnam_cap_sys_rat ! Rated capacity of the cooling system
149  CHARACTER(LEN=28) :: cfnam_t_adp ! Apparatus dewpoint temperature of the
150  CHARACTER(LEN=28) :: cfnam_m_sys_rat ! Rated HVAC mass flow rate
151  CHARACTER(LEN=28) :: cfnam_cop_rat ! Rated COP of the cooling system
152  CHARACTER(LEN=28) :: cfnam_f_water_cond ! fraction of evaporation of condensers
153  CHARACTER(LEN=6) :: cftyp_tcool_target ! file type for TCOOL_TARGET
154  CHARACTER(LEN=6) :: cftyp_theat_target ! file type for THEAT_TARGET
155  CHARACTER(LEN=6) :: cftyp_f_waste_can ! file type for F_WASTE_CAN
156  CHARACTER(LEN=6) :: cftyp_eff_heat ! file type for EFF_HEAT
157  CHARACTER(LEN=6) :: cftyp_hr_target ! Relative humidity setpoint
158  CHARACTER(LEN=6) :: cftyp_cap_sys_heat ! Capacity of the heating system
159  CHARACTER(LEN=6) :: cftyp_cap_sys_rat ! Rated capacity of the cooling system
160  CHARACTER(LEN=6) :: cftyp_t_adp ! Apparatus dewpoint temperature of the
161  CHARACTER(LEN=6) :: cftyp_m_sys_rat ! Rated HVAC mass flow rate
162  CHARACTER(LEN=6) :: cftyp_cop_rat ! Rated COP of the cooling system
163  CHARACTER(LEN=6) :: cftyp_f_water_cond ! fraction of evaporation of condensers
164 !
165 ! Internal heat gains
166 REAL :: xunif_qin ! internal heat gains [W m-2(floor)]
167 REAL :: xunif_qin_frad ! radiant fraction of int heat gains
168 REAL :: xunif_qin_flat ! Latent franction of internal heat gains
169  CHARACTER(LEN=28) :: cfnam_qin ! file name for QIN
170  CHARACTER(LEN=28) :: cfnam_qin_frad ! file name for QIN_FRAD
171  CHARACTER(LEN=28) :: cfnam_qin_flat ! Latent franction of internal heat gains
172  CHARACTER(LEN=6) :: cftyp_qin ! file type for QIN
173  CHARACTER(LEN=6) :: cftyp_qin_frad ! file type for QIN_FRAD
174  CHARACTER(LEN=6) :: cftyp_qin_flat ! Latent franction of internal heat gains
175 !
176 ! window parameters
177 REAL :: xunif_gr ! glazing ratio
178 REAL :: xunif_shgc ! solar transmitance of windows
179 REAL :: xunif_shgc_sh ! solar transmitance of windows + shading
180 REAL :: xunif_u_win ! glazing thermal resistance[K m W-2]
181  CHARACTER(LEN=28) :: cfnam_gr ! file name for GR
182  CHARACTER(LEN=28) :: cfnam_shgc ! file name for SHGC
183  CHARACTER(LEN=28) :: cfnam_shgc_sh ! file name for SHGC_SH
184  CHARACTER(LEN=28) :: cfnam_u_win ! file name for U_WIN
185  CHARACTER(LEN=6) :: cftyp_gr ! file type for GR
186  CHARACTER(LEN=6) :: cftyp_shgc ! file type for SHGC
187  CHARACTER(LEN=6) :: cftyp_shgc_sh ! file type for SHGC
188  CHARACTER(LEN=6) :: cftyp_u_win ! file type for U_WIN
189 !
190 ! air renewal
191 REAL :: xunif_inf ! infiltration/ventilation flow rate [AC/H]
192 REAL :: xunif_v_vent ! Ventilation flow rate [AC/H]
193  CHARACTER(LEN=28) :: cfnam_inf ! file name for INF
194  CHARACTER(LEN=28) :: cfnam_v_vent ! Ventilation flow rate [AC/H]
195  CHARACTER(LEN=6) :: cftyp_inf ! file type for INF
196  CHARACTER(LEN=6) :: cftyp_v_vent ! Ventilation flow rate [AC/H]
197 !
198 ! parameters for autosize calculation of the AC systems
199 REAL :: xunif_t_size_max !
200 REAL :: xunif_t_size_min !
201  CHARACTER(LEN=28) :: cfnam_t_size_max !
202  CHARACTER(LEN=28) :: cfnam_t_size_min !
203  CHARACTER(LEN=6) :: cftyp_t_size_max !
204  CHARACTER(LEN=6) :: cftyp_t_size_min !
205 !
206 REAL, DIMENSION(TG%NDIM) :: zwork
207 REAL(KIND=JPRB) :: zhook_handle
208 !
209 namelist/nam_data_bem/ npar_floor_layer, &
210  xunif_hc_floor, xunif_tc_floor, xunif_d_floor, &
211  xunif_floor_height, &
212  xunif_tcool_target, xunif_theat_target, &
213  xunif_f_waste_can, xunif_eff_heat, &
214  xunif_f_water_cond, xunif_hr_target, &
215  xunif_qin, xunif_qin_frad, xunif_qin_flat, &
216  xunif_shgc, xunif_u_win, xunif_gr,xunif_shgc_sh,&
217  xunif_inf, xunif_v_vent, &
218  xunif_cap_sys_heat, &
219  xunif_cap_sys_rat, xunif_t_adp, xunif_m_sys_rat,&
220  xunif_cop_rat, xunif_t_size_max, &
221  xunif_t_size_min, &
222  xunif_shade, cfnam_shade, cftyp_shade, &
223  xunif_natvent, cfnam_natvent, cftyp_natvent, &
224  cfnam_hc_floor, cfnam_tc_floor, cfnam_d_floor, &
225  cfnam_floor_height, &
226  cfnam_tcool_target, cfnam_theat_target, &
227  cfnam_f_waste_can, cfnam_eff_heat, &
228  cfnam_f_water_cond, cfnam_hr_target, &
229  cfnam_qin, cfnam_qin_frad, cfnam_qin_flat, &
230  cfnam_shgc, cfnam_u_win, cfnam_gr, &
231  cfnam_shgc_sh, cfnam_inf, cfnam_v_vent, &
232  cfnam_cap_sys_heat, &
233  cfnam_cap_sys_rat, cfnam_t_adp, cfnam_m_sys_rat,&
234  cfnam_cop_rat, cfnam_t_size_max, &
235  cfnam_t_size_min, &
236  cftyp_hc_floor, cftyp_tc_floor, cftyp_d_floor, &
237  cftyp_floor_height, &
238  cftyp_tcool_target, cftyp_theat_target, &
239  cftyp_f_waste_can, cftyp_eff_heat, &
240  cftyp_f_water_cond, cftyp_hr_target, &
241  cftyp_qin, cftyp_qin_frad, cftyp_qin_flat, &
242  cftyp_shgc, cftyp_u_win, cftyp_gr, &
243  cftyp_shgc_sh, cftyp_inf, cftyp_v_vent, &
244  cftyp_cap_sys_heat, &
245  cftyp_cap_sys_rat, cftyp_t_adp, cftyp_m_sys_rat,&
246  cftyp_cop_rat, cftyp_t_size_max, &
247  cftyp_t_size_min
248 !-------------------------------------------------------------------------------
249 IF (lhook) CALL dr_hook('PGD_BEM_PAR',0,zhook_handle)
250 !
251 !* 1. Initializations
252 ! ---------------
253 !
254 npar_floor_layer = 1
255 xunif_shade = xundef
256 xunif_natvent = xundef
257 xunif_hc_floor = xundef
258 xunif_tc_floor = xundef
259 xunif_d_floor = xundef
260 xunif_tcool_target = xundef
261 xunif_theat_target = xundef
262 xunif_f_waste_can = xundef
263 xunif_eff_heat = xundef
264 xunif_qin = xundef
265 xunif_qin_frad = xundef
266 xunif_shgc = xundef
267 xunif_u_win = xundef
268 xunif_gr = xundef
269 xunif_shgc_sh = xundef
270 xunif_floor_height = xundef
271 xunif_inf = xundef
272 xunif_f_water_cond = xundef
273 xunif_qin_flat = xundef
274 xunif_hr_target = xundef
275 xunif_v_vent = xundef
276 xunif_cap_sys_heat = xundef
277 xunif_cap_sys_rat = xundef
278 xunif_t_adp = xundef
279 xunif_m_sys_rat = xundef
280 xunif_cop_rat = xundef
281 xunif_t_size_max = xundef
282 xunif_t_size_min = xundef
283 !
284  cfnam_shade = ' '
285  cfnam_natvent = ' '
286  cfnam_hc_floor(:) = ' '
287  cfnam_tc_floor(:) = ' '
288  cfnam_d_floor(:) = ' '
289  cfnam_tcool_target = ' '
290  cfnam_theat_target = ' '
291  cfnam_f_waste_can = ' '
292  cfnam_eff_heat = ' '
293  cfnam_qin = ' '
294  cfnam_qin_frad = ' '
295  cfnam_shgc = ' '
296  cfnam_u_win = ' '
297  cfnam_gr = ' '
298  cfnam_shgc_sh = ' '
299  cfnam_floor_height = ' '
300  cfnam_inf = ' '
301  cfnam_f_water_cond = ' '
302  cfnam_qin_flat = ' '
303  cfnam_hr_target = ' '
304  cfnam_v_vent = ' '
305  cfnam_cap_sys_heat = ' '
306  cfnam_cap_sys_rat = ' '
307  cfnam_t_adp = ' '
308  cfnam_m_sys_rat = ' '
309  cfnam_cop_rat = ' '
310  cfnam_t_size_max = ' '
311  cfnam_t_size_min = ' '
312 !
313  cftyp_shade = ' '
314  cftyp_natvent = ' '
315  cftyp_hc_floor(:) = ' '
316  cftyp_tc_floor(:) = ' '
317  cftyp_d_floor(:) = ' '
318  cftyp_tcool_target = ' '
319  cftyp_theat_target = ' '
320  cftyp_f_waste_can = ' '
321  cftyp_eff_heat = ' '
322  cftyp_qin = ' '
323  cftyp_qin_frad = ' '
324  cftyp_shgc = ' '
325  cftyp_u_win = ' '
326  cftyp_gr = ' '
327  cftyp_shgc_sh = ' '
328  cftyp_floor_height = ' '
329  cftyp_inf = ' '
330  cftyp_f_water_cond = ' '
331  cftyp_qin_flat = ' '
332  cftyp_hr_target = ' '
333  cftyp_v_vent = ' '
334  cftyp_cap_sys_heat = ' '
335  cftyp_cap_sys_rat = ' '
336  cftyp_t_adp = ' '
337  cftyp_m_sys_rat = ' '
338  cftyp_cop_rat = ' '
339  cftyp_t_size_max = ' '
340  cftyp_t_size_min = ' '
341 !
342 !-------------------------------------------------------------------------------
343 !
344 !* 2. Input file for cover types
345 ! --------------------------
346 !
347  CALL get_luout(hprogram,iluout)
348  CALL open_namelist(hprogram,ilunam)
349 !
350  CALL posnam(ilunam,'NAM_DATA_BEM',gfound,iluout)
351 IF (gfound) READ(unit=ilunam,nml=nam_data_bem)
352 !
353  CALL close_namelist(hprogram,ilunam)
354 !
355 !-------------------------------------------------------------------------------
356 !
357 dtb%NPAR_FLOOR_LAYER = npar_floor_layer
358 !
359 !-------------------------------------------------------------------------------
360 !
361 !* coherence check
362 !
363 IF (( any(xunif_hc_floor/=xundef) .OR. any(len_trim(cfnam_hc_floor)>0) &
364  .OR. any(xunif_tc_floor/=xundef) .OR. any(len_trim(cfnam_tc_floor)>0) &
365  .OR. any(xunif_d_floor /=xundef) .OR. any(len_trim(cfnam_d_floor )>0) &
366  ) .AND. npar_floor_layer<1 ) THEN
367  CALL abor1_sfx('In order to initialize FLOOR thermal quantities, please specify NPAR_FLOOR_LAYER in namelist NAM_DATA_BEM')
368 END IF
369 !
370 !-------------------------------------------------------------------------------
371 !
372 ALLOCATE(dtb%XPAR_HC_FLOOR (tg%NDIM,npar_floor_layer))
373 ALLOCATE(dtb%XPAR_TC_FLOOR (tg%NDIM,npar_floor_layer))
374 ALLOCATE(dtb%XPAR_D_FLOOR (tg%NDIM,npar_floor_layer))
375 !
376 ALLOCATE(dtb%XPAR_TCOOL_TARGET (tg%NDIM))
377 ALLOCATE(dtb%XPAR_THEAT_TARGET (tg%NDIM))
378 ALLOCATE(dtb%XPAR_F_WASTE_CAN (tg%NDIM))
379 ALLOCATE(dtb%XPAR_EFF_HEAT (tg%NDIM))
380 ALLOCATE(dtb%XPAR_QIN (tg%NDIM))
381 ALLOCATE(dtb%XPAR_QIN_FRAD (tg%NDIM))
382 ALLOCATE(dtb%XPAR_SHGC (tg%NDIM))
383 ALLOCATE(dtb%XPAR_U_WIN (tg%NDIM))
384 ALLOCATE(dtb%XPAR_GR (tg%NDIM))
385 ALLOCATE(dtb%XPAR_SHGC_SH (tg%NDIM))
386 ALLOCATE(dtb%XPAR_FLOOR_HEIGHT (tg%NDIM))
387 ALLOCATE(dtb%XPAR_INF (tg%NDIM))
388 !
389 ALLOCATE(dtb%XPAR_F_WATER_COND (tg%NDIM))
390 ALLOCATE(dtb%XPAR_QIN_FLAT (tg%NDIM))
391 ALLOCATE(dtb%XPAR_HR_TARGET (tg%NDIM))
392 ALLOCATE(dtb%XPAR_V_VENT (tg%NDIM))
393 ALLOCATE(dtb%XPAR_CAP_SYS_HEAT (tg%NDIM))
394 ALLOCATE(dtb%XPAR_CAP_SYS_RAT (tg%NDIM))
395 ALLOCATE(dtb%XPAR_T_ADP (tg%NDIM))
396 ALLOCATE(dtb%XPAR_M_SYS_RAT (tg%NDIM))
397 ALLOCATE(dtb%XPAR_COP_RAT (tg%NDIM))
398 ALLOCATE(dtb%XPAR_T_SIZE_MAX (tg%NDIM))
399 ALLOCATE(dtb%XPAR_T_SIZE_MIN (tg%NDIM))
400 !
401 ALLOCATE(dtb%XPAR_SHADE (tg%NDIM))
402 ALLOCATE(dtb%XPAR_NATVENT (tg%NDIM))
403 !
404 !-------------------------------------------------------------------------------
405 IF (nfloor_max < npar_floor_layer) THEN
406  WRITE(iluout,*) '---------------------------------------------'
407  WRITE(iluout,*) 'Please update pgd_bem_par.F90 routine : '
408  WRITE(iluout,*) 'The maximum number of FLOOR LAYER '
409  WRITE(iluout,*) 'in the declaration of the namelist variables '
410  WRITE(iluout,*) 'must be increased to : ', npar_floor_layer
411  WRITE(iluout,*) '---------------------------------------------'
412  CALL abor1_sfx('PGD_BEM_PAR: MAXIMUM NUMBER OF NPAR_FLOOR_LAYER MUST BE INCREASED')
413 END IF
414 !-------------------------------------------------------------------------------
415 !
416 !* 3. user defined fields are prescribed
417 ! ----------------------------------
418 !
419 !
420  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
421  hprogram,'MAJ','SHADE ','TWN', cfnam_shade, cftyp_shade, xunif_shade, &
422  dtb%XPAR_SHADE, dtb%LDATA_SHADE )
423 IF (.NOT.dtb%LDATA_SHADE) DEALLOCATE(dtb%XPAR_SHADE)
424 !
425  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
426  hprogram,'MAJ','NATVENT ','TWN', cfnam_natvent, cftyp_natvent, xunif_natvent, &
427  dtb%XPAR_NATVENT, dtb%LDATA_NATVENT )
428 IF (.NOT.dtb%LDATA_NATVENT) DEALLOCATE(dtb%XPAR_NATVENT)
429 !
430  CALL ini_var_from_data(dtco, dgu, ug, u, uss, dti, &
431  hprogram,'INV','HC_FLOOR ','TWN',cfnam_hc_floor,cftyp_hc_floor, &
432  xunif_hc_floor,dtb%XPAR_HC_FLOOR,dtb%LDATA_HC_FLOOR )
433 IF (.NOT.dtb%LDATA_HC_FLOOR) DEALLOCATE(dtb%XPAR_HC_FLOOR)
434 !
435  CALL ini_var_from_data(dtco, dgu, ug, u, uss, dti, &
436  hprogram,'ARI','TC_FLOOR ','TWN',cfnam_tc_floor,cftyp_tc_floor, &
437  xunif_tc_floor ,dtb%XPAR_TC_FLOOR, dtb%LDATA_TC_FLOOR )
438 IF (.NOT.dtb%LDATA_TC_FLOOR) DEALLOCATE(dtb%XPAR_TC_FLOOR)
439 !
440  CALL ini_var_from_data(dtco, dgu, ug, u, uss, dti, &
441  hprogram,'ARI','D_FLOOR ','TWN',cfnam_d_floor,cftyp_d_floor, &
442  xunif_d_floor ,dtb%XPAR_D_FLOOR , dtb%LDATA_D_FLOOR )
443 IF (.NOT.dtb%LDATA_D_FLOOR) DEALLOCATE(dtb%XPAR_D_FLOOR)
444 !
445  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
446  hprogram,'ARI','TCOOL_TARGET','TWN',cfnam_tcool_target, cftyp_tcool_target, xunif_tcool_target, &
447  dtb%XPAR_TCOOL_TARGET, dtb%LDATA_TCOOL_TARGET)
448 IF (.NOT.dtb%LDATA_TCOOL_TARGET) DEALLOCATE(dtb%XPAR_TCOOL_TARGET)
449 !
450  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
451  hprogram,'ARI','THEAT_TARGET','TWN',cfnam_theat_target, cftyp_theat_target, xunif_theat_target, &
452  dtb%XPAR_THEAT_TARGET, dtb%LDATA_THEAT_TARGET)
453 IF (.NOT.dtb%LDATA_THEAT_TARGET) DEALLOCATE(dtb%XPAR_THEAT_TARGET)
454 !
455  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
456  hprogram,'ARI','F_WASTE_CAN','TWN',cfnam_f_waste_can, cftyp_f_waste_can, xunif_f_waste_can, &
457  dtb%XPAR_F_WASTE_CAN, dtb%LDATA_F_WASTE_CAN)
458 IF (.NOT.dtb%LDATA_F_WASTE_CAN) DEALLOCATE(dtb%XPAR_F_WASTE_CAN)
459 !
460  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
461  hprogram,'ARI','EFF_HEAT','TWN',cfnam_eff_heat, cftyp_eff_heat, xunif_eff_heat, &
462  dtb%XPAR_EFF_HEAT, dtb%LDATA_EFF_HEAT)
463 IF (.NOT.dtb%LDATA_EFF_HEAT) DEALLOCATE(dtb%XPAR_EFF_HEAT)
464 !
465  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
466  hprogram,'ARI','QIN','TWN',cfnam_qin, cftyp_qin, xunif_qin, dtb%XPAR_QIN, dtb%LDATA_QIN)
467 IF (.NOT.dtb%LDATA_QIN) DEALLOCATE(dtb%XPAR_QIN)
468 !
469  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
470  hprogram,'ARI','QIN_FRAD','TWN',cfnam_qin_frad, cftyp_qin_frad, xunif_qin_frad, &
471  dtb%XPAR_QIN_FRAD, dtb%LDATA_QIN_FRAD)
472 IF (.NOT.dtb%LDATA_QIN_FRAD) DEALLOCATE(dtb%XPAR_QIN_FRAD)
473 !
474  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
475  hprogram,'ARI','SHGC','TWN',cfnam_shgc, cftyp_shgc, xunif_shgc, dtb%XPAR_SHGC, dtb%LDATA_SHGC)
476 IF (.NOT.dtb%LDATA_SHGC) DEALLOCATE(dtb%XPAR_SHGC)
477 !
478  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
479  hprogram,'ARI','U_WIN','TWN',cfnam_u_win, cftyp_u_win, xunif_u_win, dtb%XPAR_U_WIN, dtb%LDATA_U_WIN)
480 IF (.NOT.dtb%LDATA_U_WIN) DEALLOCATE(dtb%XPAR_U_WIN)
481 !
482  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
483  hprogram,'ARI','GR','TWN',cfnam_gr, cftyp_gr, xunif_gr, dtb%XPAR_GR, dtb%LDATA_GR)
484 IF (.NOT.dtb%LDATA_GR) DEALLOCATE(dtb%XPAR_GR)
485 !
486  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
487  hprogram,'ARI','SHGC_SH','TWN',cfnam_shgc_sh, cftyp_shgc_sh, xunif_shgc_sh, &
488  dtb%XPAR_SHGC_SH, dtb%LDATA_SHGC_SH)
489 IF (.NOT.dtb%LDATA_SHGC_SH) DEALLOCATE(dtb%XPAR_SHGC_SH)
490 !
491  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
492  hprogram,'ARI','FLOOR_HEIGHT','TWN',cfnam_floor_height, cftyp_floor_height, xunif_floor_height, &
493  dtb%XPAR_FLOOR_HEIGHT, dtb%LDATA_FLOOR_HEIGHT)
494 IF (.NOT.dtb%LDATA_FLOOR_HEIGHT) DEALLOCATE(dtb%XPAR_FLOOR_HEIGHT)
495 !
496  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
497  hprogram,'ARI','INF','TWN',cfnam_inf, cftyp_inf, xunif_inf, dtb%XPAR_INF, dtb%LDATA_INF)
498 IF (.NOT.dtb%LDATA_INF) DEALLOCATE(dtb%XPAR_INF)
499 !
500  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
501  hprogram,'ARI','F_WATER_COND','TWN',cfnam_f_water_cond, cftyp_f_water_cond, xunif_f_water_cond, &
502  dtb%XPAR_F_WATER_COND, dtb%LDATA_F_WATER_COND)
503 IF (.NOT.dtb%LDATA_F_WATER_COND) DEALLOCATE(dtb%XPAR_F_WATER_COND)
504 !
505  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
506  hprogram,'ARI','QIN_FLAT','TWN',cfnam_qin_flat, cftyp_qin_flat, xunif_qin_flat, &
507  dtb%XPAR_QIN_FLAT, dtb%LDATA_QIN_FLAT)
508 IF (.NOT.dtb%LDATA_QIN_FLAT) DEALLOCATE(dtb%XPAR_QIN_FLAT)
509 !
510  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
511  hprogram,'ARI','HR_TARGET','TWN',cfnam_hr_target, cftyp_hr_target, xunif_hr_target, &
512  dtb%XPAR_HR_TARGET, dtb%LDATA_HR_TARGET)
513 IF (.NOT.dtb%LDATA_HR_TARGET) DEALLOCATE(dtb%XPAR_HR_TARGET)
514 !
515  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
516  hprogram,'ARI','V_VENT','TWN',cfnam_v_vent, cftyp_v_vent, &
517  xunif_v_vent, dtb%XPAR_V_VENT, dtb%LDATA_V_VENT)
518 IF (.NOT.dtb%LDATA_V_VENT) DEALLOCATE(dtb%XPAR_V_VENT)
519 !
520 !
521  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
522  hprogram,'ARI','T_SIZE_MAX','TWN',cfnam_t_size_max, cftyp_t_size_max, xunif_t_size_max, &
523  dtb%XPAR_T_SIZE_MAX, dtb%LDATA_T_SIZE_MAX)
524 IF (.NOT.dtb%LDATA_T_SIZE_MAX) DEALLOCATE(dtb%XPAR_T_SIZE_MAX)
525 !
526  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
527  hprogram,'ARI','T_SIZE_MIN','TWN',cfnam_t_size_min, cftyp_t_size_min, xunif_t_size_min, &
528  dtb%XPAR_T_SIZE_MIN, dtb%LDATA_T_SIZE_MIN)
529 IF (.NOT.dtb%LDATA_T_SIZE_MIN) DEALLOCATE(dtb%XPAR_T_SIZE_MIN)
530 !
531  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
532  hprogram,'ARI','CAP_SYS_HEAT','TWN',cfnam_cap_sys_heat, cftyp_cap_sys_heat, xunif_cap_sys_heat, &
533  dtb%XPAR_CAP_SYS_HEAT, dtb%LDATA_CAP_SYS_HEAT)
534 IF (.NOT.dtb%LDATA_CAP_SYS_HEAT) DEALLOCATE(dtb%XPAR_CAP_SYS_HEAT)
535 !
536  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
537  hprogram,'ARI','CAP_SYS_RAT','TWN',cfnam_cap_sys_rat, cftyp_cap_sys_rat, xunif_cap_sys_rat, &
538  dtb%XPAR_CAP_SYS_RAT, dtb%LDATA_CAP_SYS_RAT)
539 IF (.NOT.dtb%LDATA_CAP_SYS_RAT) DEALLOCATE(dtb%XPAR_CAP_SYS_RAT)
540 !
541  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
542  hprogram,'ARI','M_SYS_RAT','TWN',cfnam_m_sys_rat, cftyp_m_sys_rat, xunif_m_sys_rat, &
543  dtb%XPAR_M_SYS_RAT, dtb%LDATA_M_SYS_RAT)
544 IF (.NOT.dtb%LDATA_M_SYS_RAT) DEALLOCATE(dtb%XPAR_M_SYS_RAT)
545  !
546 IF (oautosize) THEN
547  IF (dtb%LDATA_CAP_SYS_HEAT .OR. dtb%LDATA_CAP_SYS_RAT .OR. dtb%LDATA_M_SYS_RAT) THEN
548  WRITE(iluout,*) '==> You choose LAUTOSIZE=T <=='
549  WRITE(iluout,*) 'Therefore HVAC systems characteristics will be computed automatically'
550  IF (dtb%LDATA_CAP_SYS_HEAT) THEN
551  WRITE(iluout,*) 'Data you provided for CAP_SYS_HEAT are then discarded.'
552  DEALLOCATE(dtb%XPAR_CAP_SYS_HEAT)
553  END IF
554  IF (dtb%LDATA_CAP_SYS_RAT ) THEN
555  WRITE(iluout,*) 'Data you provided for CAP_SYS_RAT are then discarded.'
556  DEALLOCATE(dtb%XPAR_CAP_SYS_RAT)
557  END IF
558  IF (dtb%LDATA_M_SYS_RAT ) THEN
559  WRITE(iluout,*) 'Data you provided for M_SYS_RAT are then discarded.'
560  DEALLOCATE(dtb%XPAR_M_SYS_RAT)
561  END IF
562  END IF
563  dtb%LDATA_CAP_SYS_HEAT = .false.
564  dtb%LDATA_CAP_SYS_RAT = .false.
565  dtb%LDATA_M_SYS_RAT = .false.
566 ELSE
567  IF (dtb%LDATA_T_SIZE_MAX .OR. dtb%LDATA_T_SIZE_MAX) THEN
568  WRITE(iluout,*) '==> You choose LAUTOSIZE=F <=='
569  WRITE(iluout,*) 'Therefore HVAC systems characteristics are specified'
570  WRITE(iluout,*) 'and you do not need the minimal and maximum temperatures'
571  WRITE(iluout,*) 'that would be used if you have chosen an automatic calibration.'
572  IF (dtb%LDATA_T_SIZE_MAX) THEN
573  WRITE(iluout,*) 'Data you provided for T_SIZE_MAX are then discarded.'
574  DEALLOCATE(dtb%XPAR_T_SIZE_MAX)
575  END IF
576  IF (dtb%LDATA_T_SIZE_MIN) THEN
577  WRITE(iluout,*) 'Data you provided for T_SIZE_MIN are then discarded.'
578  DEALLOCATE(dtb%XPAR_T_SIZE_MIN)
579  END IF
580  END IF
581  dtb%LDATA_T_SIZE_MAX = .false.
582  dtb%LDATA_T_SIZE_MIN = .false.
583 END IF
584 !
585  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
586  hprogram,'ARI','T_ADP','TWN',cfnam_t_adp, cftyp_t_adp, xunif_t_adp, dtb%XPAR_T_ADP, dtb%LDATA_T_ADP)
587 IF (.NOT.dtb%LDATA_T_ADP) DEALLOCATE(dtb%XPAR_T_ADP)
588 !
589  CALL ini_var_from_data_0d(dtco, dgu, ug, u, uss, &
590  hprogram,'ARI','COP_RAT','TWN',cfnam_cop_rat, cftyp_cop_rat, xunif_cop_rat, &
591  dtb%XPAR_COP_RAT, dtb%LDATA_COP_RAT)
592 IF (.NOT.dtb%LDATA_COP_RAT) DEALLOCATE(dtb%XPAR_COP_RAT)
593 
594 !-------------------------------------------------------------------------------
595 !
596 !* coherence checks
597 !
598  CALL coherence_thermal_data_fl('FLOOR',dtb%LDATA_HC_FLOOR,dtb%LDATA_TC_FLOOR,dtb%LDATA_D_FLOOR)
599 !
600 !-------------------------------------------------------------------------------
601 IF (lhook) CALL dr_hook('PGD_BEM_PAR',1,zhook_handle)
602 !-------------------------------------------------------------------------------
603  CONTAINS
604 SUBROUTINE coherence_thermal_data_fl(HTYPE,ODATA_HC,ODATA_TC,ODATA_D)
605  CHARACTER(LEN=5), INTENT(IN) :: htype
606 LOGICAL, INTENT(IN) :: odata_hc
607 LOGICAL, INTENT(IN) :: odata_tc
608 LOGICAL, INTENT(IN) :: odata_d
609 !
610 IF (odata_hc .OR. odata_tc .OR. odata_d) THEN
611  IF (.NOT. (odata_hc .AND. odata_tc .AND. odata_d)) THEN
612  WRITE(iluout,*) '*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*'
613  WRITE(iluout,*) 'When specifying data for thermal ',trim(htype),' characteristics,'
614  WRITE(iluout,*) 'All three parameters MUST be defined:'
615  WRITE(iluout,*) 'Heat capacity, Thermal conductivity and depths of layers'
616  WRITE(iluout,*) ' '
617  WRITE(iluout,*) 'In your case :'
618  IF (odata_hc) THEN
619  WRITE(iluout,*) 'Heat capacity is defined'
620  ELSE
621  WRITE(iluout,*) 'Heat capacity is NOT defined'
622  END IF
623  IF (odata_tc) THEN
624  WRITE(iluout,*) 'Thermal conductivity is defined'
625  ELSE
626  WRITE(iluout,*) 'Thermal conductivity is NOT defined'
627  END IF
628  IF (odata_d) THEN
629  WRITE(iluout,*) 'Depths of layers are defined'
630  ELSE
631  WRITE(iluout,*) 'Depths of layers are NOT defined'
632  END IF
633  WRITE(iluout,*) '*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*'
634  CALL abor1_sfx('Heat capacity, Thermal conductivity and depths of layers MUST all be defined for '//htype)
635  END IF
636 END IF
637 END SUBROUTINE coherence_thermal_data_fl
638 !-------------------------------------------------------------------------------
639 !
640 !-------------------------------------------------------------------------------
641 !
642 END SUBROUTINE pgd_bem_par
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine pgd_bem_par(DTCO, DGU, UG, U, USS, DTB, DTI, TG, HPROGRAM, OAUTOSIZE)
Definition: pgd_bem_par.F90:6
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 coherence_thermal_data_fl(HTYPE, ODATA_HC, ODATA_TC, ODATA_D)
subroutine open_namelist(HPROGRAM, KLUNAM, HFILE)