SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
writesurf_pgd_teb_parn.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 writesurf_pgd_teb_par_n (BDD, DTB, DTGD, DTGR, DTT, DGU, U, TGDO, TGDP, TGRO, TIR, TOP, &
7  hprogram)
8 ! ################################################
9 !
10 !!**** *WRITESURF_PGD_TEB_PAR_n* - reads ISBA physiographic fields
11 !!
12 !!
13 !! PURPOSE
14 !! -------
15 !!
16 !!** METHOD
17 !! ------
18 !!
19 !! EXTERNAL
20 !! --------
21 !!
22 !!
23 !! IMPLICIT ARGUMENTS
24 !! ------------------
25 !!
26 !! REFERENCE
27 !! ---------
28 !!
29 !!
30 !! AUTHOR
31 !! ------
32 !! V. Masson *Meteo France*
33 !!
34 !! MODIFICATIONS
35 !! -------------
36 !! Original 05/2005
37 !! V. Masson 08/2013 add solar panels
38 !-------------------------------------------------------------------------------
39 !
40 !* 0. DECLARATIONS
41 ! ------------
42 !
43 !
44 !
45 !
46 
47 !
48 !
50 USE modd_data_bem_n, ONLY : data_bem_t
53 USE modd_data_teb_n, ONLY : data_teb_t
55 USE modd_surf_atm_n, ONLY : surf_atm_t
59 USE modd_teb_irrig_n, ONLY : teb_irrig_t
61 !
63 USE modi_write_bld_description_n
64 USE modi_writesurf_pgd_teb_irrig_n
65 !
66 !
67 USE yomhook ,ONLY : lhook, dr_hook
68 USE parkind1 ,ONLY : jprb
69 !
70 IMPLICIT NONE
71 !
72 !* 0.1 Declarations of arguments
73 ! -------------------------
74 !
75 !
76 TYPE(bld_desc_t), INTENT(INOUT) :: bdd
77 TYPE(data_bem_t), INTENT(INOUT) :: dtb
78 TYPE(data_teb_garden_t), INTENT(INOUT) :: dtgd
79 TYPE(data_teb_greenroof_t), INTENT(INOUT) :: dtgr
80 TYPE(data_teb_t), INTENT(INOUT) :: dtt
81 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
82 TYPE(surf_atm_t), INTENT(INOUT) :: u
83 TYPE(teb_garden_options_t), INTENT(INOUT) :: tgdo
84 TYPE(teb_garden_pgd_t), INTENT(INOUT) :: tgdp
85 TYPE(teb_greenroof_options_t), INTENT(INOUT) :: tgro
86 TYPE(teb_irrig_t), INTENT(INOUT) :: tir
87 TYPE(teb_options_t), INTENT(INOUT) :: top
88 !
89  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling
90 !
91 !* 0.2 Declarations of local variables
92 ! -------------------------------
93 !
94 INTEGER :: iresp ! IRESP : return-code if a problem appears
95  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
96  CHARACTER(LEN=100):: ycomment ! Comment string
97 INTEGER :: jlayer ! loop index
98 INTEGER :: jtime ! loop index
99 REAL, DIMENSION(:), ALLOCATABLE :: zwork
100 REAL(KIND=JPRB) :: zhook_handle
101 !
102 !-------------------------------------------------------------------------------
103 !
104 IF (lhook) CALL dr_hook('WRITESURF_PGD_TEB_PAR_N',0,zhook_handle)
105 yrecfm='L_BLDTYPE'
106 ycomment=yrecfm
107  CALL write_surf(dgu, u, &
108  hprogram,yrecfm,dtt%LDATA_BLDTYPE,iresp,hcomment=ycomment)
109 IF (dtt%LDATA_BLDTYPE) THEN
110  yrecfm='D_BLDTYPE'
111  ycomment='X_Y_'//yrecfm//' (m)'
112  ALLOCATE(zwork(SIZE(dtt%NPAR_BLDTYPE)))
113  zwork=float(dtt%NPAR_BLDTYPE(:))
114  CALL write_surf(dgu, u, &
115  hprogram,yrecfm,zwork,iresp,ycomment)
116  DEALLOCATE(zwork)
117 ENDIF
118 !
119 yrecfm='L_BLD_AGE'
120 ycomment=yrecfm
121  CALL write_surf(dgu, u, &
122  hprogram,yrecfm,dtt%LDATA_BLD_AGE,iresp,hcomment=ycomment)
123 IF (dtt%LDATA_BLD_AGE) THEN
124  yrecfm='D_BLD_AGE'
125  ycomment='X_Y_'//yrecfm//' (m)'
126  ALLOCATE(zwork(SIZE(dtt%NPAR_BLD_AGE)))
127  zwork=float(dtt%NPAR_BLD_AGE(:))
128  CALL write_surf(dgu, u, &
129  hprogram,yrecfm,zwork,iresp,ycomment)
130  DEALLOCATE(zwork)
131 ENDIF
132 !
133 yrecfm='L_USETYPE'
134 ycomment=yrecfm
135  CALL write_surf(dgu, u, &
136  hprogram,yrecfm,dtt%LDATA_USETYPE,iresp,hcomment=ycomment)
137 IF (dtt%LDATA_USETYPE) THEN
138  yrecfm='D_USETYPE'
139  ycomment='X_Y_'//yrecfm//' (m)'
140  ALLOCATE(zwork(SIZE(dtt%NPAR_USETYPE)))
141  zwork=float(dtt%NPAR_USETYPE(:))
142  CALL write_surf(dgu, u, &
143  hprogram,yrecfm,zwork,iresp,ycomment)
144  DEALLOCATE(zwork)
145 ENDIF
146 !
147 IF (dtt%LDATA_BLDTYPE .OR. dtt%LDATA_BLD_AGE .OR. dtt%LDATA_USETYPE) CALL write_bld_description_n(dgu, u, &
148  bdd, &
149  hprogram)
150 !
151 yrecfm='L_Z0_TOWN'
152 ycomment=yrecfm
153  CALL write_surf(dgu, u, &
154  hprogram,yrecfm,dtt%LDATA_Z0_TOWN,iresp,hcomment=ycomment)
155 IF (dtt%LDATA_Z0_TOWN) THEN
156  yrecfm='D_Z0_TOWN'
157  ycomment='X_Y_'//yrecfm//' (m)'
158  CALL write_surf(dgu, u, &
159  hprogram,yrecfm,dtt%XPAR_Z0_TOWN,iresp,ycomment)
160 ENDIF
161 !
162 yrecfm='L_BLD'
163 ycomment=yrecfm
164  CALL write_surf(dgu, u, &
165  hprogram,yrecfm,dtt%LDATA_BLD,iresp,hcomment=ycomment)
166 IF (dtt%LDATA_BLD) THEN
167  yrecfm='D_BLD'
168  ycomment='X_Y_'//yrecfm//' (-)'
169  CALL write_surf(dgu, u, &
170  hprogram,yrecfm,dtt%XPAR_BLD,iresp,ycomment)
171 ENDIF
172 !
173 yrecfm='L_GARDEN'
174 ycomment=yrecfm
175  CALL write_surf(dgu, u, &
176  hprogram,yrecfm,dtt%LDATA_GARDEN,iresp,hcomment=ycomment)
177 IF (dtt%LDATA_GARDEN) THEN
178  yrecfm='D_GARDEN'
179  ycomment='X_Y_'//yrecfm//' (-)'
180  CALL write_surf(dgu, u, &
181  hprogram,yrecfm,dtt%XPAR_GARDEN,iresp,ycomment)
182 ENDIF
183 !
184 yrecfm='L_GREENROOF'
185 ycomment=yrecfm
186  CALL write_surf(dgu, u, &
187  hprogram,yrecfm,dtt%LDATA_GREENROOF,iresp,hcomment=ycomment)
188 IF (dtt%LDATA_GREENROOF) THEN
189  yrecfm='D_GREENROOF'
190  ycomment='X_Y_'//yrecfm//' (-)'
191  CALL write_surf(dgu, u, &
192  hprogram,yrecfm,dtt%XPAR_GREENROOF,iresp,ycomment)
193 ENDIF
194 !
195 yrecfm='L_ROAD_DIR'
196 ycomment=yrecfm
197  CALL write_surf(dgu, u, &
198  hprogram,yrecfm,dtt%LDATA_ROAD_DIR,iresp,hcomment=ycomment)
199 IF (dtt%LDATA_ROAD_DIR) THEN
200  yrecfm='D_ROAD_DIR'
201  ycomment='X_Y_'//yrecfm//' (-)'
202  CALL write_surf(dgu, u, &
203  hprogram,yrecfm,dtt%XPAR_ROAD_DIR,iresp,ycomment)
204 ENDIF
205 !
206 yrecfm='L_ALB_ROOF'
207 ycomment=yrecfm
208  CALL write_surf(dgu, u, &
209  hprogram,yrecfm,dtt%LDATA_ALB_ROOF,iresp,hcomment=ycomment)
210 IF (dtt%LDATA_ALB_ROOF) THEN
211  yrecfm='D_ALB_ROOF'
212  ycomment='X_Y_'//yrecfm//' (-)'
213  CALL write_surf(dgu, u, &
214  hprogram,yrecfm,dtt%XPAR_ALB_ROOF,iresp,ycomment)
215 ENDIF
216 !
217 yrecfm='L_EMIS_ROOF'
218 ycomment=yrecfm
219  CALL write_surf(dgu, u, &
220  hprogram,yrecfm,dtt%LDATA_EMIS_ROOF,iresp,hcomment=ycomment)
221 IF (dtt%LDATA_EMIS_ROOF) THEN
222  yrecfm='D_EMI_ROOF'
223  ycomment='X_Y_'//yrecfm//' (-)'
224  CALL write_surf(dgu, u, &
225  hprogram,yrecfm,dtt%XPAR_EMIS_ROOF,iresp,ycomment)
226 ENDIF
227 !
228 IF (dtt%LDATA_HC_ROOF) THEN
229  ycomment='Number of specified Roof thermal layers'
230  CALL write_surf(dgu, u, &
231  hprogram,'PAR_RF_LAYER',dtt%NPAR_ROOF_LAYER,iresp,ycomment)
232 END IF
233 !
234 yrecfm='L_HC_ROOF'
235 ycomment=yrecfm
236  CALL write_surf(dgu, u, &
237  hprogram,yrecfm,dtt%LDATA_HC_ROOF,iresp,hcomment=ycomment)
238 IF (dtt%LDATA_HC_ROOF) THEN
239  DO jlayer=1,dtt%NPAR_ROOF_LAYER
240  WRITE(yrecfm,fmt='(A9,I1.1)') 'D_HC_ROOF',jlayer
241  ycomment='X_Y_'//yrecfm//' (J/K/m3)'
242  CALL write_surf(dgu, u, &
243  hprogram,yrecfm,dtt%XPAR_HC_ROOF(:,jlayer),iresp,ycomment)
244  END DO
245 ENDIF
246 !
247 yrecfm='L_TC_ROOF'
248 ycomment=yrecfm
249  CALL write_surf(dgu, u, &
250  hprogram,yrecfm,dtt%LDATA_TC_ROOF,iresp,hcomment=ycomment)
251 IF (dtt%LDATA_TC_ROOF) THEN
252  DO jlayer=1,dtt%NPAR_ROOF_LAYER
253  WRITE(yrecfm,fmt='(A9,I1.1)') 'D_TC_ROOF',jlayer
254  ycomment='X_Y_'//yrecfm//' (W/K/m)'
255  CALL write_surf(dgu, u, &
256  hprogram,yrecfm,dtt%XPAR_TC_ROOF(:,jlayer),iresp,ycomment)
257  END DO
258 ENDIF
259 !
260 yrecfm='L_D_ROOF'
261 ycomment=yrecfm
262  CALL write_surf(dgu, u, &
263  hprogram,yrecfm,dtt%LDATA_D_ROOF,iresp,hcomment=ycomment)
264 IF (dtt%LDATA_D_ROOF) THEN
265  DO jlayer=1,dtt%NPAR_ROOF_LAYER
266  WRITE(yrecfm,fmt='(A8,I1.1)') 'D_D_ROOF',jlayer
267  ycomment='X_Y_'//yrecfm//' (m)'
268  CALL write_surf(dgu, u, &
269  hprogram,yrecfm,dtt%XPAR_D_ROOF(:,jlayer),iresp,ycomment)
270  END DO
271 ENDIF
272 !
273 yrecfm='L_ALB_ROAD'
274 ycomment=yrecfm
275  CALL write_surf(dgu, u, &
276  hprogram,yrecfm,dtt%LDATA_ALB_ROAD,iresp,hcomment=ycomment)
277 IF (dtt%LDATA_ALB_ROAD) THEN
278  yrecfm='D_ALB_ROAD'
279  ycomment='X_Y_'//yrecfm//' (-)'
280  CALL write_surf(dgu, u, &
281  hprogram,yrecfm,dtt%XPAR_ALB_ROAD,iresp,ycomment)
282 ENDIF
283 !
284 yrecfm='L_EMIS_ROAD'
285 ycomment=yrecfm
286  CALL write_surf(dgu, u, &
287  hprogram,yrecfm,dtt%LDATA_EMIS_ROAD,iresp,hcomment=ycomment)
288 IF (dtt%LDATA_EMIS_ROAD) THEN
289  yrecfm='D_EMI_ROAD'
290  ycomment='X_Y_'//yrecfm//' (-)'
291  CALL write_surf(dgu, u, &
292  hprogram,yrecfm,dtt%XPAR_EMIS_ROAD,iresp,ycomment)
293 ENDIF
294 !
295 IF (dtt%LDATA_HC_ROAD) THEN
296  ycomment='Number of specified Road thermal layers'
297  CALL write_surf(dgu, u, &
298  hprogram,'PAR_RD_LAYER',dtt%NPAR_ROAD_LAYER,iresp,ycomment)
299 END IF
300 !
301 yrecfm='L_HC_ROAD'
302 ycomment=yrecfm
303  CALL write_surf(dgu, u, &
304  hprogram,yrecfm,dtt%LDATA_HC_ROAD,iresp,hcomment=ycomment)
305 IF (dtt%LDATA_HC_ROAD) THEN
306  DO jlayer=1,dtt%NPAR_ROAD_LAYER
307  WRITE(yrecfm,fmt='(A9,I1.1)') 'D_HC_ROAD',jlayer
308  ycomment='X_Y_'//yrecfm//' (J/K/m3)'
309  CALL write_surf(dgu, u, &
310  hprogram,yrecfm,dtt%XPAR_HC_ROAD(:,jlayer),iresp,ycomment)
311  END DO
312 ENDIF
313 !
314 yrecfm='L_TC_ROAD'
315 ycomment=yrecfm
316  CALL write_surf(dgu, u, &
317  hprogram,yrecfm,dtt%LDATA_TC_ROAD,iresp,hcomment=ycomment)
318 IF (dtt%LDATA_TC_ROAD) THEN
319  DO jlayer=1,dtt%NPAR_ROAD_LAYER
320  WRITE(yrecfm,fmt='(A9,I1.1)') 'D_TC_ROAD',jlayer
321  ycomment='X_Y_'//yrecfm//' (W/K/m)'
322  CALL write_surf(dgu, u, &
323  hprogram,yrecfm,dtt%XPAR_TC_ROAD(:,jlayer),iresp,ycomment)
324  END DO
325 ENDIF
326 !
327 yrecfm='L_D_ROAD'
328 ycomment=yrecfm
329  CALL write_surf(dgu, u, &
330  hprogram,yrecfm,dtt%LDATA_D_ROAD,iresp,hcomment=ycomment)
331 IF (dtt%LDATA_D_ROAD) THEN
332  DO jlayer=1,dtt%NPAR_ROAD_LAYER
333  WRITE(yrecfm,fmt='(A8,I1.1)') 'D_D_ROAD',jlayer
334  ycomment='X_Y_'//yrecfm//' (m)'
335  CALL write_surf(dgu, u, &
336  hprogram,yrecfm,dtt%XPAR_D_ROAD(:,jlayer),iresp,ycomment)
337  END DO
338 ENDIF
339 !
340 yrecfm='L_ALB_WALL'
341 ycomment=yrecfm
342  CALL write_surf(dgu, u, &
343  hprogram,yrecfm,dtt%LDATA_ALB_WALL,iresp,hcomment=ycomment)
344 IF (dtt%LDATA_ALB_WALL) THEN
345  yrecfm='D_ALB_WALL'
346  ycomment='X_Y_'//yrecfm//' (-)'
347  CALL write_surf(dgu, u, &
348  hprogram,yrecfm,dtt%XPAR_ALB_WALL,iresp,ycomment)
349 ENDIF
350 !
351 yrecfm='L_EMIS_WALL'
352 ycomment=yrecfm
353  CALL write_surf(dgu, u, &
354  hprogram,yrecfm,dtt%LDATA_EMIS_WALL,iresp,hcomment=ycomment)
355 IF (dtt%LDATA_EMIS_WALL) THEN
356  yrecfm='D_EMI_WALL'
357  ycomment='X_Y_'//yrecfm//' (-)'
358  CALL write_surf(dgu, u, &
359  hprogram,yrecfm,dtt%XPAR_EMIS_WALL,iresp,ycomment)
360 ENDIF
361 !
362 !
363 IF (dtt%LDATA_HC_WALL) THEN
364  ycomment='Number of specified Wall thermal layers'
365  CALL write_surf(dgu, u, &
366  hprogram,'PAR_WL_LAYER',dtt%NPAR_WALL_LAYER,iresp,ycomment)
367 END IF
368 !
369 yrecfm='L_HC_WALL'
370 ycomment=yrecfm
371  CALL write_surf(dgu, u, &
372  hprogram,yrecfm,dtt%LDATA_HC_WALL,iresp,hcomment=ycomment)
373 IF (dtt%LDATA_HC_WALL) THEN
374  DO jlayer=1,dtt%NPAR_WALL_LAYER
375  WRITE(yrecfm,fmt='(A9,I1.1)') 'D_HC_WALL',jlayer
376  ycomment='X_Y_'//yrecfm//' (J/K/m3)'
377  CALL write_surf(dgu, u, &
378  hprogram,yrecfm,dtt%XPAR_HC_WALL(:,jlayer),iresp,ycomment)
379  END DO
380 ENDIF
381 !
382 yrecfm='L_TC_WALL'
383 ycomment=yrecfm
384  CALL write_surf(dgu, u, &
385  hprogram,yrecfm,dtt%LDATA_TC_WALL,iresp,hcomment=ycomment)
386 IF (dtt%LDATA_TC_WALL) THEN
387  DO jlayer=1,dtt%NPAR_WALL_LAYER
388  WRITE(yrecfm,fmt='(A9,I1.1)') 'D_TC_WALL',jlayer
389  ycomment='X_Y_'//yrecfm//' (W/K/m)'
390  CALL write_surf(dgu, u, &
391  hprogram,yrecfm,dtt%XPAR_TC_WALL(:,jlayer),iresp,ycomment)
392  END DO
393 ENDIF
394 !
395 yrecfm='L_D_WALL'
396 ycomment=yrecfm
397  CALL write_surf(dgu, u, &
398  hprogram,yrecfm,dtt%LDATA_D_WALL,iresp,hcomment=ycomment)
399 IF (dtt%LDATA_D_WALL) THEN
400  DO jlayer=1,dtt%NPAR_WALL_LAYER
401  WRITE(yrecfm,fmt='(A8,I1.1)') 'D_D_WALL',jlayer
402  ycomment='X_Y_'//yrecfm//' (m)'
403  CALL write_surf(dgu, u, &
404  hprogram,yrecfm,dtt%XPAR_D_WALL(:,jlayer),iresp,ycomment)
405  END DO
406 ENDIF
407 !
408 yrecfm='L_BLD_HEIGHT'
409 ycomment=yrecfm
410  CALL write_surf(dgu, u, &
411  hprogram,yrecfm,dtt%LDATA_BLD_HEIGHT,iresp,hcomment=ycomment)
412 IF (dtt%LDATA_BLD_HEIGHT) THEN
413  yrecfm='D_BLD_HEIG'
414  ycomment='X_Y_'//yrecfm//' (m)'
415  CALL write_surf(dgu, u, &
416  hprogram,yrecfm,dtt%XPAR_BLD_HEIGHT,iresp,ycomment)
417 ENDIF
418 !
419 yrecfm='L_WALL_O_HOR'
420 ycomment=yrecfm
421  CALL write_surf(dgu, u, &
422  hprogram,yrecfm,dtt%LDATA_WALL_O_HOR,iresp,hcomment=ycomment)
423 IF (dtt%LDATA_WALL_O_HOR) THEN
424  yrecfm='D_WALL_O_H'
425  ycomment='X_Y_'//yrecfm//' (-)'
426  CALL write_surf(dgu, u, &
427  hprogram,yrecfm,dtt%XPAR_WALL_O_HOR,iresp,ycomment)
428 ENDIF
429 !
430 yrecfm='L_H_TRAF'
431 ycomment=yrecfm
432  CALL write_surf(dgu, u, &
433  hprogram,yrecfm,dtt%LDATA_H_TRAFFIC,iresp,hcomment=ycomment)
434 IF (dtt%LDATA_H_TRAFFIC) THEN
435  yrecfm='D_H_TRAF'
436  ycomment='X_Y_'//yrecfm//' (W/m2)'
437  CALL write_surf(dgu, u, &
438  hprogram,yrecfm,dtt%XPAR_H_TRAFFIC,iresp,ycomment)
439 ENDIF
440 !
441 yrecfm='L_LE_TRAF'
442 ycomment=yrecfm
443  CALL write_surf(dgu, u, &
444  hprogram,yrecfm,dtt%LDATA_LE_TRAFFIC,iresp,hcomment=ycomment)
445 IF (dtt%LDATA_LE_TRAFFIC) THEN
446  yrecfm='D_LE_TRAF'
447  ycomment='X_Y_'//yrecfm//' (W/m2)'
448  CALL write_surf(dgu, u, &
449  hprogram,yrecfm,dtt%XPAR_LE_TRAFFIC,iresp,ycomment)
450 ENDIF
451 !
452 yrecfm='L_H_IND'
453 ycomment=yrecfm
454  CALL write_surf(dgu, u, &
455  hprogram,yrecfm,dtt%LDATA_H_INDUSTRY,iresp,hcomment=ycomment)
456 IF (dtt%LDATA_H_INDUSTRY) THEN
457  yrecfm='D_H_IND'
458  ycomment='X_Y_'//yrecfm//' (W/m2)'
459  CALL write_surf(dgu, u, &
460  hprogram,yrecfm,dtt%XPAR_H_INDUSTRY,iresp,ycomment)
461 ENDIF
462 !
463 yrecfm='L_LE_IND'
464 ycomment=yrecfm
465  CALL write_surf(dgu, u, &
466  hprogram,yrecfm,dtt%LDATA_LE_INDUSTRY,iresp,hcomment=ycomment)
467 IF (dtt%LDATA_LE_INDUSTRY) THEN
468  yrecfm='D_LE_IND'
469  ycomment='X_Y_'//yrecfm//' (W/m2)'
470  CALL write_surf(dgu, u, &
471  hprogram,yrecfm,dtt%XPAR_LE_INDUSTRY,iresp,ycomment)
472 ENDIF
473 !
474 yrecfm='L_ROUGH_ROOF'
475 ycomment=yrecfm
476  CALL write_surf(dgu, u, &
477  hprogram,yrecfm,dtt%LDATA_ROUGH_ROOF,iresp,hcomment=ycomment)
478 IF (dtt%LDATA_ROUGH_ROOF) THEN
479  yrecfm='D_ROUGH_ROOF'
480  ycomment='X_Y_'//yrecfm//' (-)'
481  CALL write_surf(dgu, u, &
482  hprogram,yrecfm,dtt%XPAR_ROUGH_ROOF,iresp,ycomment)
483 ENDIF
484 !
485 yrecfm='L_ROUGH_WALL'
486 ycomment=yrecfm
487  CALL write_surf(dgu, u, &
488  hprogram,yrecfm,dtt%LDATA_ROUGH_WALL,iresp,hcomment=ycomment)
489 IF (dtt%LDATA_ROUGH_WALL) THEN
490  yrecfm='D_ROUGH_WALL'
491  ycomment='X_Y_'//yrecfm//' (-)'
492  CALL write_surf(dgu, u, &
493  hprogram,yrecfm,dtt%XPAR_ROUGH_WALL,iresp,ycomment)
494 endif!
495 !
496 yrecfm='L_F_RESIDENT'
497 ycomment=yrecfm
498  CALL write_surf(dgu, u, &
499  hprogram,yrecfm,dtt%LDATA_RESIDENTIAL,iresp,hcomment=ycomment)
500 IF (dtt%LDATA_RESIDENTIAL) THEN
501  yrecfm='D_F_RESIDENT'
502  ycomment='X_Y_'//yrecfm//' (-)'
503  CALL write_surf(dgu, u, &
504  hprogram,yrecfm,dtt%XPAR_RESIDENTIAL,iresp,ycomment)
505 ENDIF
506 !
507 !* solar panels
508 !
509 yrecfm='L_EMIS_PANEL'
510 ycomment=yrecfm
511  CALL write_surf(dgu, u, &
512  hprogram,yrecfm,dtt%LDATA_EMIS_PANEL,iresp,hcomment=ycomment)
513 IF (dtt%LDATA_EMIS_PANEL) THEN
514  yrecfm='D_EMIS_PANEL'
515  ycomment='X_Y_'//yrecfm//' (-)'
516  CALL write_surf(dgu, u, &
517  hprogram,yrecfm,dtt%XPAR_EMIS_PANEL,iresp,ycomment)
518 ENDIF
519 !
520 yrecfm='L_ALB_PANEL'
521 ycomment=yrecfm
522  CALL write_surf(dgu, u, &
523  hprogram,yrecfm,dtt%LDATA_ALB_PANEL,iresp,hcomment=ycomment)
524 IF (dtt%LDATA_ALB_PANEL) THEN
525  yrecfm='D_ALB_PANEL'
526  ycomment='X_Y_'//yrecfm//' (-)'
527  CALL write_surf(dgu, u, &
528  hprogram,yrecfm,dtt%XPAR_ALB_PANEL,iresp,ycomment)
529 ENDIF
530 !
531 yrecfm='L_EFF_PANEL'
532 ycomment=yrecfm
533  CALL write_surf(dgu, u, &
534  hprogram,yrecfm,dtt%LDATA_EFF_PANEL,iresp,hcomment=ycomment)
535 IF (dtt%LDATA_EFF_PANEL) THEN
536  yrecfm='D_EFF_PANEL'
537  ycomment='X_Y_'//yrecfm//' (-)'
538  CALL write_surf(dgu, u, &
539  hprogram,yrecfm,dtt%XPAR_EFF_PANEL,iresp,ycomment)
540 ENDIF
541 !
542 yrecfm='L_FRAC_PANEL'
543 ycomment=yrecfm
544  CALL write_surf(dgu, u, &
545  hprogram,yrecfm,dtt%LDATA_FRAC_PANEL,iresp,hcomment=ycomment)
546 IF (dtt%LDATA_FRAC_PANEL) THEN
547  yrecfm='D_FRAC_PANEL'
548  ycomment='X_Y_'//yrecfm//' (-)'
549  CALL write_surf(dgu, u, &
550  hprogram,yrecfm,dtt%XPAR_FRAC_PANEL,iresp,ycomment)
551 ENDIF
552 !
553 !* Building Energy Model
554 !
555 IF (top%CBEM .EQ. 'BEM') THEN
556  !
557  IF (dtb%LDATA_HC_FLOOR) THEN
558  ycomment='Number of specified Floor thermal layers'
559  CALL write_surf(dgu, u, &
560  hprogram,'PAR_FL_LAYER',dtb%NPAR_FLOOR_LAYER,iresp,ycomment)
561  END IF
562  !
563  yrecfm='L_HC_FLOOR'
564  ycomment=yrecfm
565  CALL write_surf(dgu, u, &
566  hprogram,yrecfm,dtb%LDATA_HC_FLOOR,iresp,hcomment=ycomment)
567  IF (dtb%LDATA_HC_FLOOR) THEN
568  DO jlayer=1,dtb%NPAR_FLOOR_LAYER
569  WRITE(yrecfm,fmt='(A10,I1.1)') 'D_HC_FLOOR',jlayer
570  ycomment='X_Y_'//yrecfm//' (J/K/m3)'
571  CALL write_surf(dgu, u, &
572  hprogram,yrecfm,dtb%XPAR_HC_FLOOR(:,jlayer),iresp,ycomment)
573  END DO
574  ENDIF
575  !
576  yrecfm='L_TC_FLOOR'
577  ycomment=yrecfm
578  CALL write_surf(dgu, u, &
579  hprogram,yrecfm,dtb%LDATA_TC_FLOOR,iresp,hcomment=ycomment)
580  IF (dtb%LDATA_TC_FLOOR) THEN
581  DO jlayer=1,dtb%NPAR_FLOOR_LAYER
582  WRITE(yrecfm,fmt='(A10,I1.1)') 'D_TC_FLOOR',jlayer
583  ycomment='X_Y_'//yrecfm//' (W/K/m)'
584  CALL write_surf(dgu, u, &
585  hprogram,yrecfm,dtb%XPAR_TC_FLOOR(:,jlayer),iresp,ycomment)
586  END DO
587  ENDIF
588  !
589  yrecfm='L_D_FLOOR'
590  ycomment=yrecfm
591  CALL write_surf(dgu, u, &
592  hprogram,yrecfm,dtb%LDATA_D_FLOOR,iresp,hcomment=ycomment)
593  IF (dtb%LDATA_D_FLOOR) THEN
594  DO jlayer=1,dtb%NPAR_FLOOR_LAYER
595  WRITE(yrecfm,fmt='(A9,I1.1)') 'D_D_FLOOR',jlayer
596  ycomment='X_Y_'//yrecfm//' (m)'
597  CALL write_surf(dgu, u, &
598  hprogram,yrecfm,dtb%XPAR_D_FLOOR(:,jlayer),iresp,ycomment)
599  END DO
600  ENDIF
601  !
602  yrecfm='L_TCOOL_TARG'
603  ycomment=yrecfm
604  CALL write_surf(dgu, u, &
605  hprogram,yrecfm,dtb%LDATA_TCOOL_TARGET,iresp,hcomment=ycomment)
606  IF (dtb%LDATA_TCOOL_TARGET) THEN
607  yrecfm='D_TCOOL_TARG'
608  ycomment='X_Y_'//yrecfm//' (K)'
609  CALL write_surf(dgu, u, &
610  hprogram,yrecfm,dtb%XPAR_TCOOL_TARGET,iresp,ycomment)
611  ENDIF
612  !
613  yrecfm='L_THEAT_TARG'
614  ycomment=yrecfm
615  CALL write_surf(dgu, u, &
616  hprogram,yrecfm,dtb%LDATA_THEAT_TARGET,iresp,hcomment=ycomment)
617  IF (dtb%LDATA_THEAT_TARGET) THEN
618  yrecfm='D_THEAT_TARG'
619  ycomment='X_Y_'//yrecfm//' (K)'
620  CALL write_surf(dgu, u, &
621  hprogram,yrecfm,dtb%XPAR_THEAT_TARGET,iresp,ycomment)
622  ENDIF
623  !
624  yrecfm='L_F_WAST_CAN'
625  ycomment=yrecfm
626  CALL write_surf(dgu, u, &
627  hprogram,yrecfm,dtb%LDATA_F_WASTE_CAN,iresp,hcomment=ycomment)
628  IF (dtb%LDATA_F_WASTE_CAN) THEN
629  yrecfm='D_F_WAST_CAN'
630  ycomment='X_Y_'//yrecfm//' (-)'
631  CALL write_surf(dgu, u, &
632  hprogram,yrecfm,dtb%XPAR_F_WASTE_CAN,iresp,ycomment)
633  ENDIF
634  !
635  yrecfm='L_EFF_HEAT'
636  ycomment=yrecfm
637  CALL write_surf(dgu, u, &
638  hprogram,yrecfm,dtb%LDATA_EFF_HEAT,iresp,hcomment=ycomment)
639  IF (dtb%LDATA_EFF_HEAT) THEN
640  yrecfm='D_EFF_HEAT'
641  ycomment='X_Y_'//yrecfm//' (-)'
642  CALL write_surf(dgu, u, &
643  hprogram,yrecfm,dtb%XPAR_EFF_HEAT,iresp,ycomment)
644  ENDIF
645  !
646  yrecfm='L_QIN'
647  ycomment=yrecfm
648  CALL write_surf(dgu, u, &
649  hprogram,yrecfm,dtb%LDATA_QIN,iresp,hcomment=ycomment)
650  IF (dtb%LDATA_QIN) THEN
651  yrecfm='D_QIN'
652  ycomment='X_Y_'//yrecfm//' (K)'
653  CALL write_surf(dgu, u, &
654  hprogram,yrecfm,dtb%XPAR_QIN,iresp,ycomment)
655  ENDIF
656  !
657  yrecfm='L_QIN_FRAD'
658  ycomment=yrecfm
659  CALL write_surf(dgu, u, &
660  hprogram,yrecfm,dtb%LDATA_QIN_FRAD,iresp,hcomment=ycomment)
661  IF (dtb%LDATA_QIN_FRAD) THEN
662  yrecfm='D_QIN_FRAD'
663  ycomment='X_Y_'//yrecfm//' (K)'
664  CALL write_surf(dgu, u, &
665  hprogram,yrecfm,dtb%XPAR_QIN_FRAD,iresp,ycomment)
666  ENDIF
667  !
668  yrecfm='L_SHGC'
669  ycomment=yrecfm
670  CALL write_surf(dgu, u, &
671  hprogram,yrecfm,dtb%LDATA_SHGC,iresp,hcomment=ycomment)
672  IF (dtb%LDATA_SHGC) THEN
673  yrecfm='D_SHGC'
674  ycomment='X_Y_'//yrecfm//' (-)'
675  CALL write_surf(dgu, u, &
676  hprogram,yrecfm,dtb%XPAR_SHGC,iresp,ycomment)
677  ENDIF
678  !
679  yrecfm='L_U_WIN'
680  ycomment=yrecfm
681  CALL write_surf(dgu, u, &
682  hprogram,yrecfm,dtb%LDATA_U_WIN,iresp,hcomment=ycomment)
683  IF (dtb%LDATA_U_WIN) THEN
684  yrecfm='D_U_WIN'
685  ycomment='X_Y_'//yrecfm//' (W m-2 K-1)'
686  CALL write_surf(dgu, u, &
687  hprogram,yrecfm,dtb%XPAR_U_WIN,iresp,ycomment)
688  ENDIF
689  !
690  yrecfm='L_GR'
691  ycomment=yrecfm
692  CALL write_surf(dgu, u, &
693  hprogram,yrecfm,dtb%LDATA_GR,iresp,hcomment=ycomment)
694  IF (dtb%LDATA_GR) THEN
695  yrecfm='D_GR'
696  ycomment='X_Y_'//yrecfm//' (-)'
697  CALL write_surf(dgu, u, &
698  hprogram,yrecfm,dtb%XPAR_GR,iresp,ycomment)
699  ENDIF
700  !
701  yrecfm='L_SHGC_SH'
702  ycomment=yrecfm
703  CALL write_surf(dgu, u, &
704  hprogram,yrecfm,dtb%LDATA_SHGC_SH,iresp,hcomment=ycomment)
705  IF (dtb%LDATA_SHGC_SH) THEN
706  yrecfm='D_SHGC_SH'
707  ycomment='X_Y_'//yrecfm//' (-)'
708  CALL write_surf(dgu, u, &
709  hprogram,yrecfm,dtb%XPAR_SHGC_SH,iresp,ycomment)
710  ENDIF
711  !
712  yrecfm='L_FLOOR_HEIG'
713  ycomment=yrecfm
714  CALL write_surf(dgu, u, &
715  hprogram,yrecfm,dtb%LDATA_FLOOR_HEIGHT,iresp,hcomment=ycomment)
716  IF (dtb%LDATA_FLOOR_HEIGHT) THEN
717  yrecfm='D_FLOOR_HEIG'
718  ycomment='X_Y_'//yrecfm//' (m)'
719  CALL write_surf(dgu, u, &
720  hprogram,yrecfm,dtb%XPAR_FLOOR_HEIGHT,iresp,ycomment)
721  ENDIF
722  !
723  yrecfm='L_INF'
724  ycomment=yrecfm
725  CALL write_surf(dgu, u, &
726  hprogram,yrecfm,dtb%LDATA_INF,iresp,hcomment=ycomment)
727  IF (dtb%LDATA_INF) THEN
728  yrecfm='D_INF'
729  ycomment='X_Y_'//yrecfm//' (ACH)'
730  CALL write_surf(dgu, u, &
731  hprogram,yrecfm,dtb%XPAR_INF,iresp,ycomment)
732  ENDIF
733  !
734  yrecfm='L_QIN_FLAT'
735  ycomment=yrecfm
736  CALL write_surf(dgu, u, &
737  hprogram,yrecfm,dtb%LDATA_QIN_FLAT,iresp,hcomment=ycomment)
738  IF (dtb%LDATA_QIN_FLAT) THEN
739  yrecfm='D_QIN_FLAT'
740  ycomment='X_Y_'//yrecfm//' (-)'
741  CALL write_surf(dgu, u, &
742  hprogram,yrecfm,dtb%XPAR_QIN_FLAT,iresp,ycomment)
743  ENDIF
744  !
745  yrecfm='L_HR_TARGET'
746  ycomment=yrecfm
747  CALL write_surf(dgu, u, &
748  hprogram,yrecfm,dtb%LDATA_HR_TARGET,iresp,hcomment=ycomment)
749  IF (dtb%LDATA_HR_TARGET) THEN
750  yrecfm='D_HR_TARGET'
751  ycomment='X_Y_'//yrecfm//' (-)'
752  CALL write_surf(dgu, u, &
753  hprogram,yrecfm,dtb%XPAR_HR_TARGET,iresp,ycomment)
754  ENDIF
755  !
756  yrecfm='L_V_VENT'
757  ycomment=yrecfm
758  CALL write_surf(dgu, u, &
759  hprogram,yrecfm,dtb%LDATA_V_VENT,iresp,hcomment=ycomment)
760  IF (dtb%LDATA_V_VENT) THEN
761  yrecfm='D_V_VENT'
762  ycomment='X_Y_'//yrecfm//' (ACH)'
763  CALL write_surf(dgu, u, &
764  hprogram,yrecfm,dtb%XPAR_V_VENT,iresp,ycomment)
765  ENDIF
766  !
767  yrecfm='L_CAP_SYS_HE'
768  ycomment=yrecfm
769  CALL write_surf(dgu, u, &
770  hprogram,yrecfm,dtb%LDATA_CAP_SYS_HEAT,iresp,hcomment=ycomment)
771  IF (dtb%LDATA_CAP_SYS_HEAT) THEN
772  yrecfm='D_CAP_SYS_HE'
773  ycomment='X_Y_'//yrecfm//' (W m-2)'
774  CALL write_surf(dgu, u, &
775  hprogram,yrecfm,dtb%XPAR_CAP_SYS_HEAT,iresp,ycomment)
776  ENDIF
777  !
778  yrecfm='L_CAP_SYS_RA'
779  ycomment=yrecfm
780  CALL write_surf(dgu, u, &
781  hprogram,yrecfm,dtb%LDATA_CAP_SYS_RAT,iresp,hcomment=ycomment)
782  IF (dtb%LDATA_CAP_SYS_RAT) THEN
783  yrecfm='D_CAP_SYS_RA'
784  ycomment='X_Y_'//yrecfm//' (W m-2)'
785  CALL write_surf(dgu, u, &
786  hprogram,yrecfm,dtb%XPAR_CAP_SYS_RAT,iresp,ycomment)
787  ENDIF
788  !
789  yrecfm='L_T_ADP'
790  ycomment=yrecfm
791  CALL write_surf(dgu, u, &
792  hprogram,yrecfm,dtb%LDATA_T_ADP,iresp,hcomment=ycomment)
793  IF (dtb%LDATA_T_ADP) THEN
794  yrecfm='D_T_ADP'
795  ycomment='X_Y_'//yrecfm//' (K)'
796  CALL write_surf(dgu, u, &
797  hprogram,yrecfm,dtb%XPAR_T_ADP,iresp,ycomment)
798  ENDIF
799  !
800  yrecfm='L_M_SYS_RAT'
801  ycomment=yrecfm
802  CALL write_surf(dgu, u, &
803  hprogram,yrecfm,dtb%LDATA_M_SYS_RAT,iresp,hcomment=ycomment)
804  IF (dtb%LDATA_M_SYS_RAT) THEN
805  yrecfm='D_M_SYS_RAT'
806  ycomment='X_Y_'//yrecfm//' (kg s-1 m-)'
807  CALL write_surf(dgu, u, &
808  hprogram,yrecfm,dtb%XPAR_M_SYS_RAT,iresp,ycomment)
809  ENDIF
810  !
811  yrecfm='L_COP_RAT'
812  ycomment=yrecfm
813  CALL write_surf(dgu, u, &
814  hprogram,yrecfm,dtb%LDATA_COP_RAT,iresp,hcomment=ycomment)
815  IF (dtb%LDATA_COP_RAT) THEN
816  yrecfm='D_COP_RAT'
817  ycomment='X_Y_'//yrecfm//' (-)'
818  CALL write_surf(dgu, u, &
819  hprogram,yrecfm,dtb%XPAR_COP_RAT,iresp,ycomment)
820  ENDIF
821  !
822  yrecfm='L_T_SIZE_MAX'
823  ycomment=yrecfm
824  CALL write_surf(dgu, u, &
825  hprogram,yrecfm,dtb%LDATA_T_SIZE_MAX,iresp,hcomment=ycomment)
826  IF (dtb%LDATA_T_SIZE_MAX) THEN
827  yrecfm='D_T_SIZE_MAX'
828  ycomment='X_Y_'//yrecfm//' (K)'
829  CALL write_surf(dgu, u, &
830  hprogram,yrecfm,dtb%XPAR_T_SIZE_MAX,iresp,ycomment)
831  ENDIF
832  !
833  yrecfm='L_T_SIZE_MIN'
834  ycomment=yrecfm
835  CALL write_surf(dgu, u, &
836  hprogram,yrecfm,dtb%LDATA_T_SIZE_MIN,iresp,hcomment=ycomment)
837  IF (dtb%LDATA_T_SIZE_MIN) THEN
838  yrecfm='D_T_SIZE_MIN'
839  ycomment='X_Y_'//yrecfm//' (K)'
840  CALL write_surf(dgu, u, &
841  hprogram,yrecfm,dtb%XPAR_T_SIZE_MIN,iresp,ycomment)
842  ENDIF
843  !
844  yrecfm='L_FWAT_COND'
845  ycomment=yrecfm
846  CALL write_surf(dgu, u, &
847  hprogram,yrecfm,dtb%LDATA_F_WATER_COND,iresp,hcomment=ycomment)
848  IF (dtb%LDATA_F_WATER_COND) THEN
849  yrecfm='D_FWAT_COND'
850  ycomment='X_Y_'//yrecfm//' (-)'
851  CALL write_surf(dgu, u, &
852  hprogram,yrecfm,dtb%XPAR_F_WATER_COND,iresp,ycomment)
853  ENDIF
854  !
855  yrecfm='L_SHADE'
856  ycomment=yrecfm
857  CALL write_surf(dgu, u, &
858  hprogram,yrecfm,dtb%LDATA_SHADE,iresp,hcomment=ycomment)
859  IF (dtb%LDATA_SHADE) THEN
860  yrecfm='D_SHADE'
861  ycomment='X_Y_'//yrecfm//' (-)'
862  CALL write_surf(dgu, u, &
863  hprogram,yrecfm,dtb%XPAR_SHADE,iresp,ycomment)
864  ENDIF
865  !
866  yrecfm='L_NATVENT'
867  ycomment=yrecfm
868  CALL write_surf(dgu, u, &
869  hprogram,yrecfm,dtb%LDATA_NATVENT,iresp,hcomment=ycomment)
870  IF (dtb%LDATA_NATVENT) THEN
871  yrecfm='D_NATVENT'
872  ycomment='X_Y_'//yrecfm//' (-)'
873  CALL write_surf(dgu, u, &
874  hprogram,yrecfm,dtb%XPAR_NATVENT,iresp,ycomment)
875  ENDIF
876  !
877 ENDIF
878 !
879 ! Flag for data for gardens
880 yrecfm='PAR_GARDEN'
881 ycomment='FLAG FOR SPECIFIED GARDEN PARAMETERS'
882  CALL write_surf(dgu, u, &
883  hprogram,yrecfm,tgdo%LPAR_GARDEN,iresp,hcomment=ycomment)
884 !
885 IF (top%LGARDEN .AND. tgdo%LPAR_GARDEN) THEN
886 !
887  yrecfm='GD_NTIME'
888  ycomment=yrecfm
889  CALL write_surf(dgu, u, &
890  hprogram,yrecfm,dtgd%NTIME,iresp,hcomment=ycomment)
891 !
892 ! Type of high vegetation
893  yrecfm='D_TYPE_HVEG'
894  ycomment='X_Y_TYPE_HVEG'
895  CALL write_surf(dgu, u, &
896  hprogram,yrecfm,tgdp%CTYPE_HVEG,iresp,hcomment=ycomment)
897 !
898 ! Type of low vegetation
899  yrecfm='D_TYPE_LVEG'
900  ycomment='X_Y_TYPE_LVEG'
901  CALL write_surf(dgu, u, &
902  hprogram,yrecfm,tgdp%CTYPE_LVEG,iresp,hcomment=ycomment)
903 !
904 ! Type of bare soil (no vegetation)
905  yrecfm='D_TYPE_NVEG'
906  ycomment='X_Y_TYPE_NVEG'
907  CALL write_surf(dgu, u, &
908  hprogram,yrecfm,tgdp%CTYPE_NVEG,iresp,hcomment=ycomment)
909 !
910 ! Fraction of high vegetation
911  yrecfm='D_FRAC_HVEG'
912  ycomment='X_Y_D_FRAC_HVEG'
913  CALL write_surf(dgu, u, &
914  hprogram,yrecfm,dtgd%XDATA_FRAC_HVEG(:),iresp,hcomment=ycomment)
915 !
916 ! Fraction of low vegetation
917  yrecfm='D_FRAC_LVEG'
918  ycomment='X_Y_D_FRAC_LVEG'
919  CALL write_surf(dgu, u, &
920  hprogram,yrecfm,dtgd%XDATA_FRAC_LVEG(:),iresp,hcomment=ycomment)
921 !
922 ! Fraction of bare soil
923  yrecfm='D_FRAC_NVEG'
924  ycomment='X_Y_D_FRAC_NVEG'
925  CALL write_surf(dgu, u, &
926  hprogram,yrecfm,dtgd%XDATA_FRAC_NVEG(:),iresp,hcomment=ycomment)
927 !
928 ! LAI of high vegetation
929  DO jtime=1,dtgd%NTIME
930  WRITE(yrecfm,fmt='(A10,I2.2)') 'D_LAI_HVEG',jtime
931  ycomment='X_Y_D_LAI_HVEG'
932  CALL write_surf(dgu, u, &
933  hprogram,yrecfm,dtgd%XDATA_LAI_HVEG(:,jtime),iresp,hcomment=ycomment)
934  END DO
935 !
936 ! LAI of low vegetation
937  DO jtime=1,dtgd%NTIME
938  WRITE(yrecfm,fmt='(A10,I2.2)') 'D_LAI_LVEG',jtime
939  ycomment='X_Y_D_LAI_LVEG'
940  CALL write_surf(dgu, u, &
941  hprogram,yrecfm,dtgd%XDATA_LAI_LVEG(:,jtime),iresp,hcomment=ycomment)
942  END DO
943 !
944 ! Height of trees
945  yrecfm='D_H_HVEG'
946  ycomment='X_Y_DATA_H_HVEG'
947  CALL write_surf(dgu, u, &
948  hprogram,yrecfm,dtgd%XDATA_H_HVEG(:),iresp,hcomment=ycomment)
949 !
950 ENDIF
951 !
952 IF (top%LGREENROOF .AND. tgro%LPAR_GREENROOF) THEN
953 !
954 ! Type of green roof
955  yrecfm='D_TYPE_GR'
956  ycomment='X_Y_TYPE_GR'
957  CALL write_surf(dgu, u, &
958  hprogram,yrecfm,tgro%CTYP_GR,iresp,hcomment=ycomment)
959 !
960 ! Fraction of OM in green roof layer
961  DO jlayer=1,tgro%NLAYER_GR
962  WRITE(yrecfm,fmt='(A7,I2.2)') 'D_OM_GR',jlayer
963  ycomment='X_Y_D_OM_GR'
964  CALL write_surf(dgu, u, &
965  hprogram,yrecfm,dtgr%XPAR_OM_GR(:,jlayer),iresp,hcomment=ycomment)
966  END DO
967 !
968 ! Fraction of CLAY in the non-OM part of the green roof layer
969  DO jlayer=1,tgro%NLAYER_GR
970  WRITE(yrecfm,fmt='(A9,I2.2)') 'D_CLAY_GR',jlayer
971  ycomment='X_Y_D_CLAY_GR'
972  CALL write_surf(dgu, u, &
973  hprogram,yrecfm,dtgr%XPAR_CLAY_GR(:,jlayer),iresp,hcomment=ycomment)
974  END DO
975 !
976 ! Fraction of SAND in the non-OM part of the green roof layer
977  DO jlayer=1,tgro%NLAYER_GR
978  WRITE(yrecfm,fmt='(A9,I2.2)') 'D_SAND_GR',jlayer
979  ycomment='X_Y_D_SAND_GR'
980  CALL write_surf(dgu, u, &
981  hprogram,yrecfm,dtgr%XPAR_SAND_GR(:,jlayer),iresp,hcomment=ycomment)
982  END DO
983 !
984 ! LAI of green roof vegetation
985  DO jtime=1,tgro%NTIME_GR
986  WRITE(yrecfm,fmt='(A8,I2.2)') 'D_LAI_GR',jtime
987  ycomment='X_Y_D_LAI_GR'
988  CALL write_surf(dgu, u, &
989  hprogram,yrecfm,dtgr%XPAR_LAI_GR(:,jtime),iresp,hcomment=ycomment)
990  END DO
991 !
992 ENDIF
993 !-------------------------------------------------------------------------------
994 !
995 !* Irrigation of gardens or greenroofs
996 ! -----------------------------------
997 !
998  CALL writesurf_pgd_teb_irrig_n(dgu, u, &
999  tir, &
1000  hprogram)
1001 !
1002 IF (lhook) CALL dr_hook('WRITESURF_PGD_TEB_PAR_N',1,zhook_handle)
1003 !
1004 !
1005 !-------------------------------------------------------------------------------
1006 !
1007 END SUBROUTINE writesurf_pgd_teb_par_n
subroutine write_bld_description_n(DGU, U, BDD, HPROGRAM)
subroutine writesurf_pgd_teb_par_n(BDD, DTB, DTGD, DTGR, DTT, DGU, U, TGDO, TGDP, TGRO, TIR, TOP, HPROGRAM)
subroutine writesurf_pgd_teb_irrig_n(DGU, U, TIR, HPROGRAM)