SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_csvdata_teb.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 read_csvdata_teb (BDD, &
7  hprogram,hfile)
8 ! #########################
9 !
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !! METHOD
15 !! ------
16 !!
17 !!
18 !! EXTERNAL
19 !! --------
20 !!
21 !! IMPLICIT ARGUMENTS
22 !! ------------------
23 !!
24 !! REFERENCE
25 !! ---------
26 !!
27 !! AUTHOR
28 !! ------
29 !!
30 !! V. Masson Meteo-France
31 !!
32 !! MODIFICATION
33 !! ------------
34 !!
35 !! Original 05/2012
36 !
37 !----------------------------------------------------------------------------
38 !
39 !* 0. DECLARATION
40 ! -----------
41 !
42 !
44 !
45 USE modd_csts, ONLY : xtt
46 USE modd_surf_par, ONLY : xundef
47 !
48 !
49 USE modi_open_namelist
50 USE modi_close_namelist
51 !
52 USE modi_get_luout
53 USE modi_abor1_sfx
54 !
55 !
56 USE yomhook ,ONLY : lhook, dr_hook
57 USE parkind1 ,ONLY : jprb
58 !
59 IMPLICIT NONE
60 !
61 !* 0.1 Declaration of arguments
62 ! ------------------------
63 !
64 !
65 TYPE(bld_desc_t), INTENT(INOUT) :: bdd
66 !
67  CHARACTER(LEN=6), INTENT(IN) :: hprogram
68  CHARACTER(LEN=28), INTENT(IN) :: hfile ! file to read
69 !
70 !
71 !* 0.2 Declaration of local variables
72 ! ------------------------------
73 !
74 INTEGER :: ilunam ! logical unit of the file
75 INTEGER :: iluout ! logical unit of the output listing file
76  CHARACTER(LEN=400) :: ystring
77  CHARACTER(LEN=80) :: ystring1, ystring2, ystring3, ystring4, &
78  ystring5, ystring6, ystring7, ystring8, ystring9
79  CHARACTER(LEN=30), DIMENSION(:), ALLOCATABLE :: yuse_name ! building's use name
80  CHARACTER(LEN=30), DIMENSION(:), ALLOCATABLE :: ybld_name ! building name
81  CHARACTER(LEN=30), DIMENSION(:), ALLOCATABLE :: ylayer ! name of layer
82 INTEGER :: i1
83 INTEGER :: i2
84 INTEGER :: jbld ! loop counter on buildings
85 INTEGER :: jage ! loop counter on building's ages
86 INTEGER :: juse ! loop counter on building's uses
87 INTEGER :: jlayer ! loop counter on layers
88 INTEGER :: iindex ! index in descriptive data arrays
89 !
90 INTEGER :: iall_hyp ! number of hypotheses for equipment
91 INTEGER :: ihyp ! kept hypothese for equipment
92 INTEGER :: ires ! index for residential use
93  CHARACTER(LEN=10) :: ytype_of_data ! 'STRUCTURE', 'EQUIPMENT'
94 !
95 REAL(KIND=JPRB) :: zhook_handle
96 !
97 !-------------------------------------------------------------------------------
98 !-------------------------------------------------------------------------------
99 !
100 IF (lhook) CALL dr_hook('READ_CSVDATA_TEB',0,zhook_handle)
101 !
102 !-------------------------------------------------------------------------------
103 IF (len_trim(hfile)==0) THEN
104  IF (lhook) CALL dr_hook('READ_CSVDATA_TEB',1,zhook_handle)
105  RETURN
106 END IF
107 !
108  CALL get_luout(hprogram,iluout)
109 !
110 !-------------------------------------------------------------------------------
111 !
112 !* 1. Opens the file
113 ! --------------------
114 !
115  CALL open_namelist(hprogram,ilunam,hfile)
116 !
117 !-------------------------------------------------------------------------------
118 !
119 !* 2.1 Reads the number of building types and of construction dates
120 ! ------------------------------------------------------------
121 !
122  CALL read_conf_in_csvfile("Nb de types de batiments",bdd%NDESC_BLD)
123  CALL read_conf_in_csvfile("Nb de plages de dates",bdd%NDESC_AGE)
124  CALL read_conf_in_csvfile("Nb de types d_usages",bdd%NDESC_USE)
125 !
126 bdd%NDESC_CODE = bdd%NDESC_BLD * bdd%NDESC_AGE
127 !
128 !* 2.2 Reads the number of layers for description of the surfaces
129 ! ----------------------------------------------------------
130 !
131  CALL read_conf_in_csvfile("Nb de couches MUR",bdd%NDESC_WALL_LAYER)
132  CALL read_conf_in_csvfile("Nb de couches TOITURE",bdd%NDESC_ROOF_LAYER)
133  CALL read_conf_in_csvfile("Nb de couches PLANCHER",bdd%NDESC_FLOOR_LAYER)
134 !
135 !-------------------------------------------------------------------------------
136 !
137 !* 3. Reads the codes of the building construction (or renovation) dates
138 ! ------------------------------------------------------------------
139 !
140 ALLOCATE(bdd%NDESC_AGE_LIST(bdd%NDESC_AGE))
141 ALLOCATE(bdd%NDESC_AGE_DATE(bdd%NDESC_AGE))
142 !
143 DO
144  ystring1=' '
145  ystring2=' '
146  ystring3=' '
147  ystring4=' '
148  ystring5=' '
149  ystring6=' '
150 !* reads the record
151  READ(ilunam,end=98,fmt='(A400)') ystring
152 !* analyses if the record has been written in French convention
153  CALL french_to_english(ystring)
154 !* reads the string
155  IF (len_trim(ystring)>0) &
156  READ(ystring,fmt=*) ystring1, ystring2, ystring3, ystring4, ystring5, ystring6
157  IF (ystring1=='DATE' .AND. ystring2(4:)=='plage de date') THEN
158  READ(ystring,fmt=*) ystring1, ystring2, bdd%NDESC_AGE_LIST(:)
159  END IF
160  IF (ystring1=='DATE' .AND. ystring2(:)=='Date maximum') THEN
161  READ(ystring,fmt=*) ystring1, ystring2, bdd%NDESC_AGE_DATE(:)
162  END IF
163 END DO
164 !
165 98 CONTINUE
166 rewind(ilunam)
167 !
168 !
169 !
170 !-------------------------------------------------------------------------------
171 !
172 !* 3. Reads the codes of the building and building's use types
173 ! --------------------------------------------------------
174 !
175 ALLOCATE(ybld_name(bdd%NDESC_BLD))
176 ALLOCATE(yuse_name(bdd%NDESC_USE))
177 !
178 ALLOCATE(bdd%NDESC_BLD_LIST(bdd%NDESC_BLD))
179 ALLOCATE(bdd%NDESC_CODE_LIST(bdd%NDESC_CODE))
180 ALLOCATE(bdd%NDESC_USE_LIST(bdd%NDESC_USE))
181 !
182 DO
183  ystring1=' '
184  ystring2=' '
185  ystring3=' '
186  ystring4=' '
187  ystring5=' '
188  ystring6=' '
189 !* reads the record
190  READ(ilunam,end=99,fmt='(A400)') ystring
191 !* analyses if the record has been written in French convention
192  CALL french_to_english(ystring)
193 !* reads the string
194  IF (len_trim(ystring)>0) &
195  READ(ystring,fmt=*) ystring1, ystring2, ystring3, ystring4, ystring5, ystring6
196 
197  IF (ystring1=='TYPES USAGES' .AND. ystring4=='TYPES BATIMENTS') THEN
198  ! reads both use and building types
199  DO jbld=1,max(bdd%NDESC_BLD,bdd%NDESC_USE)
200  READ(ilunam,fmt='(A400)') ystring
201  CALL french_to_english(ystring)
202  READ(ystring,fmt=*) ystring1, i1, ystring3, ystring4, i2, ystring6
203  ! updates building types
204  IF (jbld<=bdd%NDESC_BLD) THEN
205  ybld_name(jbld) = ystring4
206  bdd%NDESC_BLD_LIST(jbld) = i2
207  DO jage=1,bdd%NDESC_AGE
208  iindex = (jbld-1)*bdd%NDESC_AGE + jage
209  bdd%NDESC_CODE_LIST(iindex) = bld_code(bdd%NDESC_BLD_LIST(jbld),bdd%NDESC_AGE_LIST(jage))
210  END DO
211  END IF
212  ! updates building's use types
213  IF (jbld<=bdd%NDESC_USE) THEN
214  yuse_name(jbld) = ystring1
215  bdd%NDESC_USE_LIST(jbld) = i1
216  END IF
217  END DO
218  EXIT
219  END IF
220 END DO
221 !
222 99 CONTINUE
223 rewind(ilunam)
224 !
225 !------------------------------------------------------------------------------
226 !
227 !* 4. town parameters depending on building structure descriptions
228 ! ------------------------------------------------------------------
229 !
230 ytype_of_data = 'STRUCTURE'
231 !
232 !* radiative properties
233 !
234 ALLOCATE(bdd%XDESC_ALB_ROOF(bdd%NDESC_CODE))
235  CALL read_in_csvfile('TOITURE',ybld_name,"Exterieur",'Albedo',bdd%XDESC_ALB_ROOF)
236 
237 ALLOCATE(bdd%XDESC_ALB_WALL(bdd%NDESC_CODE))
238  CALL read_in_csvfile('MUR',ybld_name,"Couche 1 (Ext)",'Albedo',bdd%XDESC_ALB_WALL)
239 
240 ALLOCATE(bdd%XDESC_EMIS_ROOF(bdd%NDESC_CODE))
241  CALL read_in_csvfile('TOITURE',ybld_name,"Exterieur",'Emissivite',bdd%XDESC_EMIS_ROOF)
242 
243 ALLOCATE(bdd%XDESC_EMIS_WALL(bdd%NDESC_CODE))
244  CALL read_in_csvfile('MUR',ybld_name,"Couche 1 (Ext)",'Emissivite',bdd%XDESC_EMIS_WALL)
245 !
246 !* thermal properties for roof
247 !
248 ALLOCATE(ylayer(bdd%NDESC_ROOF_LAYER))
249 DO jlayer=1,bdd%NDESC_ROOF_LAYER
250  IF (jlayer==1) THEN
251  WRITE(ylayer(jlayer),fmt='(A)') 'Exterieur '
252  ELSEIF (jlayer==bdd%NDESC_ROOF_LAYER) THEN
253  WRITE(ylayer(jlayer),fmt='(A)') 'Interieur '
254  ELSE
255  WRITE(ylayer(jlayer),fmt='(A)') 'Milieu '
256  END IF
257 END DO
258 !
259 ALLOCATE(bdd%XDESC_HC_ROOF(bdd%NDESC_CODE,bdd%NDESC_ROOF_LAYER))
260 ALLOCATE(bdd%XDESC_TC_ROOF(bdd%NDESC_CODE,bdd%NDESC_ROOF_LAYER))
261 ALLOCATE(bdd%XDESC_D_ROOF (bdd%NDESC_CODE,bdd%NDESC_ROOF_LAYER))
262 DO jlayer=1,bdd%NDESC_ROOF_LAYER
263  CALL read_in_csvfile('TOITURE',ybld_name,ylayer(jlayer),'Chaleur specifique C',bdd%XDESC_HC_ROOF(:,jlayer))
264  CALL read_in_csvfile('TOITURE',ybld_name,ylayer(jlayer),'Conductivite',bdd%XDESC_TC_ROOF(:,jlayer))
265  CALL read_in_csvfile('TOITURE',ybld_name,ylayer(jlayer),'Epaisseur d',bdd%XDESC_D_ROOF(:,jlayer))
266 END DO
267 !* transformation from kJ.m-3.K-1 to J.m-3.K-1
268 bdd%XDESC_HC_ROOF = bdd%XDESC_HC_ROOF * 1000.
269 DEALLOCATE(ylayer)
270 !
271 !* thermal properties for wall
272 !
273 ALLOCATE(ylayer(bdd%NDESC_WALL_LAYER))
274 DO jlayer=1,bdd%NDESC_WALL_LAYER
275  IF (jlayer==1) THEN
276  WRITE(ylayer(jlayer),fmt='(A,I1,A)') 'Couche ',jlayer,' (Ext)'
277  ELSEIF (jlayer==bdd%NDESC_WALL_LAYER) THEN
278  WRITE(ylayer(jlayer),fmt='(A,I1,A)') 'Couche ',jlayer,' (Int)'
279  ELSE
280  WRITE(ylayer(jlayer),fmt='(A,I1,A)') 'Couche ',jlayer,' (Milieu)'
281  END IF
282 END DO
283 !
284 ALLOCATE(bdd%XDESC_HC_WALL(bdd%NDESC_CODE,bdd%NDESC_WALL_LAYER))
285 ALLOCATE(bdd%XDESC_TC_WALL(bdd%NDESC_CODE,bdd%NDESC_WALL_LAYER))
286 ALLOCATE(bdd%XDESC_D_WALL (bdd%NDESC_CODE,bdd%NDESC_WALL_LAYER))
287 DO jlayer=1,bdd%NDESC_WALL_LAYER
288  CALL read_in_csvfile('MUR',ybld_name,ylayer(jlayer),'Chaleur specifique C',bdd%XDESC_HC_WALL(:,jlayer))
289  CALL read_in_csvfile('MUR',ybld_name,ylayer(jlayer),'Conductivite',bdd%XDESC_TC_WALL(:,jlayer))
290  CALL read_in_csvfile('MUR',ybld_name,ylayer(jlayer),'Epaisseur d',bdd%XDESC_D_WALL(:,jlayer))
291 END DO
292 !* transformation from kJ.m-3.K-1 to J.m-3.K-1
293 bdd%XDESC_HC_WALL = bdd%XDESC_HC_WALL * 1000.
294 DEALLOCATE(ylayer)
295 !
296 !
297 !* thermal properties for floor
298 !
299 ALLOCATE(ylayer(bdd%NDESC_FLOOR_LAYER))
300 DO jlayer=1,bdd%NDESC_FLOOR_LAYER
301  IF (jlayer==1) THEN
302  WRITE(ylayer(jlayer),fmt='(A)') 'Superieur '
303  ELSEIF (jlayer==bdd%NDESC_FLOOR_LAYER) THEN
304  WRITE(ylayer(jlayer),fmt='(A)') 'Inferieur '
305  ELSE
306  WRITE(ylayer(jlayer),fmt='(A)') 'Milieu '
307  END IF
308 END DO
309 !
310 ALLOCATE(bdd%XDESC_HC_FLOOR(bdd%NDESC_CODE,bdd%NDESC_FLOOR_LAYER))
311 ALLOCATE(bdd%XDESC_TC_FLOOR(bdd%NDESC_CODE,bdd%NDESC_FLOOR_LAYER))
312 ALLOCATE(bdd%XDESC_D_FLOOR (bdd%NDESC_CODE,bdd%NDESC_FLOOR_LAYER))
313 DO jlayer=1,bdd%NDESC_FLOOR_LAYER
314  CALL read_in_csvfile('PLANCHER',ybld_name,ylayer(jlayer),'Chaleur specifique C',bdd%XDESC_HC_FLOOR(:,jlayer))
315  CALL read_in_csvfile('PLANCHER',ybld_name,ylayer(jlayer),'Conductivite',bdd%XDESC_TC_FLOOR(:,jlayer))
316  CALL read_in_csvfile('PLANCHER',ybld_name,ylayer(jlayer),'Epaisseur d',bdd%XDESC_D_FLOOR(:,jlayer))
317 END DO
318 !* transformation from kJ.m-3.K-1 to J.m-3.K-1
319 bdd%XDESC_HC_FLOOR = bdd%XDESC_HC_FLOOR * 1000.
320 DEALLOCATE(ylayer)
321 !
322 !* windows
323 ! -------
324 !
325 ALLOCATE(bdd%XDESC_SHGC(bdd%NDESC_CODE))
326  CALL read_in_csvfile('ENVELOPPE',ybld_name,"Vitrage",'Facteur solaire m',bdd%XDESC_SHGC)
327 
328 ALLOCATE(bdd%XDESC_U_WIN(bdd%NDESC_CODE))
329  CALL read_in_csvfile('ENVELOPPE',ybld_name,"Vitrage",'U-factor',bdd%XDESC_U_WIN)
330 
331 ALLOCATE(bdd%XDESC_GR(bdd%NDESC_CODE))
332  CALL read_in_csvfile('ENVELOPPE',ybld_name,"Vitrage",'Surface fenetre /surface facade',bdd%XDESC_GR)
333 !
334 !------------------------------------------------------------------------------
335 !
336 !* 5. town parameters depending on building equipment descriptions
337 ! ------------------------------------------------------------------
338 !
339 ytype_of_data = 'EQUIPMENT'
340 !
341  CALL read_conf_in_csvfile("Nb d_hypotheses",iall_hyp)
342 !
343 !* Air conditionning systems
344 !
345  CALL read_hyp_in_csvfile("Climatisation","Taux de rejets en toitures",ihyp)
346 ALLOCATE(bdd%XDESC_F_WASTE_CAN(bdd%NDESC_CODE))
347  CALL read_in_csvfile('EQUIPEMENT',ybld_name,"Climatisation",'Taux de rejets en toitures',bdd%XDESC_F_WASTE_CAN)
348 bdd%XDESC_F_WASTE_CAN = bdd%XDESC_F_WASTE_CAN / 100. ! % => fraction
349 !
350  CALL read_hyp_in_csvfile("Climatisation","Taux de rejets secs",ihyp)
351 ALLOCATE(bdd%XDESC_F_WATER_COND(bdd%NDESC_CODE))
352  CALL read_in_csvfile('EQUIPEMENT',ybld_name,"Climatisation",'Taux de rejets secs',bdd%XDESC_F_WATER_COND)
353 bdd%XDESC_F_WATER_COND = 1. - bdd%XDESC_F_WATER_COND / 100. ! % => fraction and dry waste => humid waste
354 !
355  CALL read_hyp_in_csvfile("Climatisation","Performance (COP)",ihyp)
356 ALLOCATE(bdd%XDESC_COP_RAT(bdd%NDESC_CODE))
357  CALL read_in_csvfile('EQUIPEMENT',ybld_name,"Climatisation",'Performance (COP)',bdd%XDESC_COP_RAT)
358 !
359 !
360 !* Heating systems
361 !
362 !CALL READ_HYP_IN_CSVFILE("Chauffage","Efficacite energetique",IHYP)
363 ALLOCATE(bdd%XDESC_EFF_HEAT(bdd%NDESC_CODE))
364 !CALL READ_IN_CSVFILE('EQUIPEMENT',YBLD_NAME,"Chauffage",'Efficacite energetique',XDESC_EFF_HEAT)
365 bdd%XDESC_EFF_HEAT = 0.9
366 !
367 !
368 !* Sanitary ventilation
369  CALL read_hyp_in_csvfile("Infiltration","Taux de renouvellement d_air",ihyp)
370 ALLOCATE(bdd%XDESC_INF(bdd%NDESC_CODE))
371  CALL read_in_csvfile('EQUIPEMENT',ybld_name,"Infiltration","Taux de renouvellement d_air",bdd%XDESC_INF)
372 !
373  CALL read_hyp_in_csvfile("Ventilation Mecanique Controlee","Taux de renouvellement d_air",ihyp)
374 ALLOCATE(bdd%XDESC_V_VENT(bdd%NDESC_CODE))
375  CALL read_in_csvfile('EQUIPEMENT',ybld_name,"Ventilation Mecanique Controlee","Taux de renouvellement d_air",bdd%XDESC_V_VENT)
376 !
377 !* Greenroof fraction
378  CALL read_hyp_in_csvfile("Toits vegetalises","Implantation",ihyp)
379 ALLOCATE(bdd%XDESC_GREENROOF(bdd%NDESC_CODE))
380  CALL read_in_csvfile('EQUIPEMENT',ybld_name,"Toits vegetalises","Implantation",bdd%XDESC_GREENROOF)
381 !
382 !* solar panels
383  CALL read_hyp_in_csvfile("Panneau solaire","Emissivite",ihyp)
384 ALLOCATE(bdd%XDESC_EMIS_PANEL(bdd%NDESC_CODE))
385  CALL read_in_csvfile('EQUIPEMENT',ybld_name,"Panneau solaire","Emissivite",bdd%XDESC_EMIS_PANEL)
386 !
387  CALL read_hyp_in_csvfile("Panneau solaire","Coefficient d_absorption",ihyp)
388 ALLOCATE(bdd%XDESC_ALB_PANEL(bdd%NDESC_CODE))
389  CALL read_in_csvfile('EQUIPEMENT',ybld_name,"Panneau solaire","Coefficient d_absorption",bdd%XDESC_ALB_PANEL)
390 bdd%XDESC_ALB_PANEL = 1. - bdd%XDESC_ALB_PANEL ! absorption ==> albedo
391 !
392  CALL read_hyp_in_csvfile("Panneau solaire","Rendement",ihyp)
393 ALLOCATE(bdd%XDESC_EFF_PANEL(bdd%NDESC_CODE))
394  CALL read_in_csvfile('EQUIPEMENT',ybld_name,"Panneau solaire","Rendement",bdd%XDESC_EFF_PANEL)
395 bdd%XDESC_EFF_PANEL = bdd%XDESC_EFF_PANEL /100. ! % ==> fraction
396 !
397  CALL read_hyp_in_csvfile("Panneau solaire","Surface des panneaux / surface du toit",ihyp)
398 ALLOCATE(bdd%XDESC_FRAC_PANEL(bdd%NDESC_CODE))
399  CALL read_in_csvfile('EQUIPEMENT',ybld_name,"Panneau solaire","Surface des panneaux / surface du toit",bdd%XDESC_FRAC_PANEL)
400 bdd%XDESC_FRAC_PANEL = bdd%XDESC_FRAC_PANEL/100. ! % ==> fraction
401 
402 !-------------------------------------------------------------------------------
403 
404 !------------------------------------------------------------------------------
405 !
406 !* 7. town parameters depending on building's use descriptions
407 ! --------------------------------------------------------------
408 !
409 !
410 ytype_of_data = 'USE'
411 !
412 !* Temperature target for air conditionning
413  CALL read_hyp_in_csvfile("Climatisation","Temp. de consigne",ihyp)
414 ALLOCATE(bdd%XDESC_TCOOL_TARGET(bdd%NDESC_USE))
415  CALL read_in_csvfile('USAGE',yuse_name,"Climatisation","Temp. de consigne",bdd%XDESC_TCOOL_TARGET)
416 bdd%XDESC_TCOOL_TARGET = bdd%XDESC_TCOOL_TARGET + xtt ! C => K
417 !
418 !* Temperature target for domestic heating
419  CALL read_hyp_in_csvfile("Chauffage","Temp. de consigne",ihyp)
420 ALLOCATE(bdd%XDESC_THEAT_TARGET(bdd%NDESC_USE))
421  CALL read_in_csvfile('USAGE',yuse_name,"Chauffage","Temp. de consigne",bdd%XDESC_THEAT_TARGET)
422 bdd%XDESC_THEAT_TARGET = bdd%XDESC_THEAT_TARGET + xtt ! C => K
423 !
424 !* Internal gains
425  CALL read_hyp_in_csvfile("Apports internes","Flux",ihyp)
426 ALLOCATE(bdd%XDESC_QIN(bdd%NDESC_USE))
427  CALL read_in_csvfile('USAGE',yuse_name,"Apports internes","Flux",bdd%XDESC_QIN)
428 !
429 !* Latent fraction for internal gains
430  CALL read_hyp_in_csvfile("Apports internes","Fraction latente",ihyp)
431 ALLOCATE(bdd%XDESC_QIN_FLAT(bdd%NDESC_USE))
432  CALL read_in_csvfile('USAGE',yuse_name,"Apports internes","Fraction latente",bdd%XDESC_QIN_FLAT)
433 bdd%XDESC_QIN_FLAT = bdd%XDESC_QIN_FLAT / 100. ! % => fraction
434 !
435 !* Solar protections
436  CALL read_hyp_in_csvfile("Protection solaire","Facteur solaire m",ihyp)
437 ALLOCATE(bdd%XDESC_SHGC_SH(bdd%NDESC_USE))
438  CALL read_in_csvfile('USAGE',yuse_name,"Protection solaire","Facteur solaire m",bdd%XDESC_SHGC_SH)
439 !
440  CALL read_hyp_in_csvfile("Protection solaire","Active",ihyp)
441 ALLOCATE(bdd%XDESC_SHADE(bdd%NDESC_USE))
442  CALL read_in_csvfile('USAGE',yuse_name,"Protection solaire","Active",bdd%XDESC_SHADE)
443 !
444 !* Extra Natural ventilation (windows open or extra mechanical ventilation)
445  CALL read_hyp_in_csvfile("Sur-ventilation","Type d_ouverture",ihyp)
446 ALLOCATE(bdd%XDESC_NATVENT(bdd%NDESC_USE))
447  CALL read_in_csvfile('USAGE',yuse_name,"Sur-ventilation","Type d_ouverture",bdd%XDESC_NATVENT)
448 !
449 !* fraction of residential use for the buildings
450 ALLOCATE(bdd%XDESC_RESIDENTIAL(bdd%NDESC_USE))
451  CALL read_conf_in_csvfile("Residentiel",ires)
452 bdd%XDESC_RESIDENTIAL(:) = 0.
453 DO juse=1,bdd%NDESC_USE
454  IF (juse==ires) bdd%XDESC_RESIDENTIAL(juse) = 1.
455 END DO
456 
457 !------------------------------------------------------------------------------
458 !
459 !* 8. town parameters depending on urban structure
460 ! --------------------------------------------------
461 !
462 bdd%NDESC_ROAD_LAYER = 3
463 !
464 ALLOCATE(bdd%XDESC_ALB_ROAD(bdd%NDESC_CODE))
465 bdd%XDESC_ALB_ROAD = 0.08
466 ALLOCATE(bdd%XDESC_EMIS_ROAD(bdd%NDESC_CODE))
467 bdd%XDESC_EMIS_ROAD = 0.94
468 ALLOCATE(bdd%XDESC_HC_ROAD(bdd%NDESC_CODE,bdd%NDESC_ROAD_LAYER))
469 bdd%XDESC_HC_ROAD(:,1) = 1940000.
470 bdd%XDESC_HC_ROAD(:,2:) = 1280000.
471 ALLOCATE(bdd%XDESC_TC_ROAD(bdd%NDESC_CODE,bdd%NDESC_ROAD_LAYER))
472 bdd%XDESC_TC_ROAD(:,1) = 0.74
473 bdd%XDESC_TC_ROAD(:,2:) = 0.25
474 ALLOCATE(bdd%XDESC_D_ROAD(bdd%NDESC_CODE,bdd%NDESC_ROAD_LAYER))
475 bdd%XDESC_D_ROAD(:,1) = 0.05
476 bdd%XDESC_D_ROAD(:,2) = 0.1
477 bdd%XDESC_D_ROAD(:,3:) = 1.
478 !
479 !-------------------------------------------------------------------------------
480 !
481  CALL close_namelist(hprogram,ilunam)
482 !
483 IF (lhook) CALL dr_hook('READ_CSVDATA_TEB',1,zhook_handle)
484 !-------------------------------------------------------------------------------
485  CONTAINS
486 !-------------------------------------------------------------------------------
487 !
488 FUNCTION bld_code(KBLD,KAGE)
489 INTEGER, INTENT(IN) :: kbld ! building type number
490 INTEGER, INTENT(IN) :: kage ! building construction period number
491 INTEGER :: bld_code ! building code combining type and age
492 bld_code = 100*kbld+kage
493 END FUNCTION bld_code
494 !
495 !-------------------------------------------------------------------------------
496 !
497 !-------------------------------------------------------------------------------
498 !
499 SUBROUTINE read_conf_in_csvfile(HCODE1,KDATA)
500 
501  CHARACTER(LEN=*), INTENT(IN) :: hcode1
502 INTEGER, INTENT(OUT):: kdata
503  CHARACTER(LEN=80) :: yerror
504 !
505 rewind(ilunam)
506 DO
507  ystring1 = ''
508  ystring2 = ''
509 !* reads the record
510  READ(ilunam,end=101,fmt='(A400)') ystring
511 !* analyses if the record has been written in French convention
512  CALL french_to_english(ystring)
513 !* reads the string
514  IF (len_trim(ystring)>0) &
515  READ(ystring,fmt=*) ystring1, ystring2
516 
517  IF (trim(ystring1)==trim(hcode1)) THEN
518  READ(ystring,*) ystring1, kdata
519  rewind(ilunam)
520  RETURN
521  END IF
522 END DO
523 !
524 101 CONTINUE
525  yerror=trim(hcode1)//' not found in file : '//trim(hfile)
526  CALL abor1_sfx(yerror)
527 !
528 END SUBROUTINE read_conf_in_csvfile
529 !
530 SUBROUTINE read_hyp_in_csvfile(HCODE1,HCODE2,KDATA)
531 
532  CHARACTER(LEN=*), INTENT(IN) :: hcode1
533  CHARACTER(LEN=*), INTENT(IN) :: hcode2
534 INTEGER, INTENT(OUT):: kdata
535  CHARACTER(LEN=80) :: yerror
536 LOGICAL :: gcode2
537 !
538 rewind(ilunam)
539 DO
540  ystring1 = ''
541  ystring2 = ''
542 !* reads the record
543  READ(ilunam,end=101,fmt='(A400)') ystring
544 !* analyses if the record has been written in French convention
545  CALL french_to_english(ystring)
546 !* reads the string
547  IF (len_trim(ystring)>0) &
548  READ(ystring,fmt=*) ystring1, ystring2
549 
550  gcode2 = trim(ystring2)==trim(hcode2)
551  IF (trim(ystring1)==trim(hcode1) .AND. gcode2) THEN
552  READ(ystring,*) ystring1, ystring2, kdata
553  rewind(ilunam)
554  RETURN
555  END IF
556 END DO
557 !
558 101 CONTINUE
559  yerror=trim(hcode1)//' '//trim(hcode2)//' not found in file : '//trim(hfile)
560  CALL abor1_sfx(yerror)
561 !
562 END SUBROUTINE read_hyp_in_csvfile
563 !
564 SUBROUTINE read_in_csvfile(HCODE_ELEMENT,HCODE_TYPE,HCODE_ELEMENT2,HCODE_PARAM,PDATA)
565 !
566  CHARACTER(LEN=*), INTENT(IN) :: hcode_element ! type of element
567  CHARACTER(LEN=*), DIMENSION(:), INTENT(IN) :: hcode_type ! building type or
568  ! building's use type
569  CHARACTER(LEN=*), INTENT(IN) :: hcode_element2 ! description of element
570  CHARACTER(LEN=*), INTENT(IN) :: hcode_param ! name of Parameter
571 REAL, DIMENSION(:), INTENT(OUT):: pdata ! data read in the csv file
572 !
573 REAL, DIMENSION(:), ALLOCATABLE :: zdata ! data array read in the file
574 LOGICAL, DIMENSION(SIZE(HCODE_TYPE)) :: ginitialized ! Flag to know if parameter
575 ! ! has been initialized correctly
576 LOGICAL :: gfound ! correct record has been found
577  CHARACTER(LEN=80) :: ytype ! type of building or building's use
578 ! ! in the csv file record
579  CHARACTER(LEN=100) :: yerror ! Character string for error message
580 INTEGER :: in1 ! number of building type or use
581 INTEGER :: in2 ! number of construction dates
582 !
583 IF (ytype_of_data=='STRUCTURE') THEN
584  ALLOCATE(zdata(bdd%NDESC_AGE))
585  in1=bdd%NDESC_BLD
586  in2=bdd%NDESC_AGE
587 ELSE IF (ytype_of_data=='EQUIPMENT') THEN
588  ALLOCATE(zdata(iall_hyp))
589  in1=bdd%NDESC_BLD
590  in2=bdd%NDESC_AGE
591 ELSE IF (ytype_of_data=='USE') THEN
592  ALLOCATE(zdata(iall_hyp))
593  in1=bdd%NDESC_USE
594  in2=1
595 END IF
596 !
597 pdata = xundef
598 ginitialized(:)=.false.
599 DO
600  ystring1=' '
601  ystring2=' '
602  ystring3=' '
603  ystring4=' '
604  ystring5=' '
605  ystring6=' '
606  ystring7=' '
607  ystring8=' '
608 !* reads the record
609  READ(ilunam,end=100,fmt='(A400)') ystring
610 !* analyses if the record has been written in French convention
611  CALL french_to_english(ystring)
612 !* reads the string
613  IF (len_trim(ystring)>0) &
614  READ(ystring,fmt=*) ystring1, ystring2, ystring3, ystring4, ystring5, ystring6, ystring7
615  !
616  IF (ytype_of_data=='EQUIPMENT' .OR. ytype_of_data=='USE') THEN
617  gfound = trim(ystring1)==trim(hcode_element) .AND. trim(ystring6)==trim(hcode_element2) &
618  .AND. trim(ystring7)==trim(hcode_param)
619  ELSE IF (ytype_of_data=='STRUCTURE') THEN
620  gfound = trim(ystring1)==trim(hcode_element) .AND. trim(ystring4)==trim(hcode_element2) &
621  .AND. trim(ystring5)==trim(hcode_param)
622  ELSE
623  gfound = .false.
624  END IF
625 
626  IF (gfound) THEN
627 !* reads the data in the record
628  IF (ytype_of_data=='EQUIPMENT' .OR. ytype_of_data=='USE') THEN
629  READ(ystring,fmt=*) ystring1, ystring2, ystring3, ystring4, ystring5, &
630  ystring6, ystring7, ystring8, ystring9, zdata(:)
631  ELSE IF (ytype_of_data=='STRUCTURE') THEN
632  READ(ystring,fmt=*) ystring1, ystring2, ystring3, ystring4, ystring5, &
633  ystring6, ystring7, zdata(:)
634  END IF
635 !* in case of EQUIPMENT or USE data, one keeps the chosen hypothesis
636  IF (ytype_of_data=='EQUIPMENT' .OR. ytype_of_data=='USE') zdata(:) = zdata(ihyp)
637 !* one finds for which building type or building's use type the data is for
638  IF (ytype_of_data=='EQUIPMENT') ytype = ystring2
639  IF (ytype_of_data=='STRUCTURE') ytype = ystring2
640  IF (ytype_of_data=='USE ') ytype = ystring4
641  !
642  DO jbld=1,in1
643  IF (trim(hcode_type(jbld))==trim(ytype) .OR. trim(ytype)=='Tous batiments') THEN
644 !* one affects the data for this type of building for each construction dates
645  DO jage=1,in2
646  iindex = (jbld-1)*in2 + jage
647  pdata(iindex) = zdata(min(jage,SIZE(zdata)))
648  END DO
649  ginitialized(jbld) = .true.
650  END IF
651  END DO
652  END IF
653  IF (all(ginitialized)) EXIT
654 END DO
655 !
656 100 CONTINUE
657 rewind(ilunam)
658 DEALLOCATE(zdata)
659 !
660 !* one checks if the data is available for all building's types
661 IF (any(.NOT. ginitialized)) THEN
662  WRITE(iluout,*) '*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*'
663  WRITE(iluout,*) 'While reading the csv data file for building parameters specification'
664  WRITE(iluout,*) '(file ',trim(hfile),')'
665  WRITE(iluout,*) 'The field corresponding to the following '
666  WRITE(iluout,*) 'identifiers:',trim(hcode_element),' ',trim(hcode_element2),' ',trim(hcode_param)
667  WRITE(iluout,*) 'has not been completely initialized.'
668  WRITE(iluout,*) 'The data for the following building types were not found:'
669  IF (ytype_of_data=='USE') THEN
670  DO jbld=1,in1
671  IF (.NOT. ginitialized(jbld)) WRITE(iluout,*) '"',trim(yuse_name(jbld)),'"'
672  END DO
673  ELSE
674  DO jbld=1,in1
675  IF (.NOT. ginitialized(jbld)) WRITE(iluout,*) '"',trim(ybld_name(jbld)),'"'
676  END DO
677  END IF
678  WRITE(iluout,*) '*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*'
679 
680  yerror='Initialization not complete for: '//trim(hcode_element)//' '//trim(hcode_element2)//' '//trim(hcode_param)
681  CALL abor1_sfx(yerror)
682 END IF
683 !
684 END SUBROUTINE read_in_csvfile
685 !-------------------------------------------------------------------------------
686 !-------------------------------------------------------------------------------
687 SUBROUTINE french_to_english(HSTRING)
688  CHARACTER(LEN=400), INTENT(INOUT) :: hstring ! csv record
689 INTEGER :: jl
690 LOGICAL :: gfrench
691 !
692 gfrench = .false.
693 !* analyses if the record has been written in French convention
694 ! French convention (separator is ; decimal symbol is ,)
695 ! or English convention (separator is , decimal symbol is .)
696 DO jl=1,400
697  IF (hstring(jl:jl)==';') gfrench=.true.
698 END DO
699 !
700 ! If French convention is used in the file, transforms it in English convention
701 IF (gfrench) THEN
702  DO jl=1,400
703  IF (hstring(jl:jl)==',') hstring(jl:jl)='.'
704  IF (hstring(jl:jl)==';') hstring(jl:jl)=','
705  END DO
706 END IF
707 !
708 END SUBROUTINE french_to_english
709 !-------------------------------------------------------------------------------
710 !
711 END SUBROUTINE read_csvdata_teb
subroutine french_to_english(HSTRING)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine read_hyp_in_csvfile(HCODE1, HCODE2, KDATA)
subroutine read_csvdata_teb(BDD, HPROGRAM, HFILE)
subroutine read_in_csvfile(HCODE_ELEMENT, HCODE_TYPE, HCODE_ELEMENT2, HCODE_PARAM, PDATA)
subroutine close_namelist(HPROGRAM, KLUNAM)
integer function bld_code(KBLD, KAGE)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine read_conf_in_csvfile(HCODE1, KDATA)
subroutine open_namelist(HPROGRAM, KLUNAM, HFILE)