SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
write_diag_pgd_tebn.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 write_diag_pgd_teb_n (DTCO, DGU, U, B, BOP, T, TOP, TPN, &
7  hprogram)
8 ! #########################################
9 !
10 !!**** *WRITE_DIAG_PGD_TEB_GARDEN_n* - writes the ISBA physiographic diagnostic fields
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !!** METHOD
16 !! ------
17 !!
18 !! EXTERNAL
19 !! --------
20 !!
21 !!
22 !! IMPLICIT ARGUMENTS
23 !! ------------------
24 !!
25 !! REFERENCE
26 !! ---------
27 !!
28 !!
29 !! AUTHOR
30 !! ------
31 !! V. Masson *Meteo France*
32 !!
33 !! MODIFICATIONS
34 !! -------------
35 !! Original 01/2004
36 !! Modified 10/2004 by P. Le Moigne: add XZ0REL, XVEGTYPE_PATCH
37 !! Modified 11/2005 by P. Le Moigne: limit length of VEGTYPE_PATCH field names
38 !-------------------------------------------------------------------------------
39 !
40 !* 0. DECLARATIONS
41 ! ------------
42 !
43 !
46 USE modd_surf_atm_n, ONLY : surf_atm_t
47 USE modd_bem_n, ONLY : bem_t
49 USE modd_teb_n, ONLY : teb_t
51 USE modd_teb_panel_n, ONLY : teb_panel_t
52 !
53 USE modd_surf_par, ONLY : xundef
54 
55 !
56 USE modd_io_surf_fa, ONLY : lfanocompact, lprep
57 !
58 USE modi_init_io_surf_n
60 USE modi_end_io_surf_n
61 !
62 !
63 USE yomhook ,ONLY : lhook, dr_hook
64 USE parkind1 ,ONLY : jprb
65 !
66 IMPLICIT NONE
67 !
68 !* 0.1 Declarations of arguments
69 ! -------------------------
70 !
71 !
72 TYPE(data_cover_t), INTENT(INOUT) :: dtco
73 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
74 TYPE(surf_atm_t), INTENT(INOUT) :: u
75 TYPE(bem_t), INTENT(INOUT) :: b
76 TYPE(bem_options_t), INTENT(INOUT) :: bop
77 TYPE(teb_t), INTENT(INOUT) :: t
78 TYPE(teb_options_t), INTENT(INOUT) :: top
79 TYPE(teb_panel_t), INTENT(INOUT) :: tpn
80 !
81  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling
82 !
83 !* 0.2 Declarations of local variables
84 ! -------------------------------
85 !
86 INTEGER :: iresp ! IRESP : return-code if a problem appears
87  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
88  CHARACTER(LEN=100):: ycomment ! Comment string
89 INTEGER :: jlayer ! loop counter on layers
90 !
91 REAL(KIND=JPRB) :: zhook_handle
92 !-------------------------------------------------------------------------------
93 !
94 ! Initialisation for IO
95 !
96 IF (lhook) CALL dr_hook('WRITE_DIAG_PGD_TEB_N',0,zhook_handle)
97  CALL init_io_surf_n(dtco, dgu, u, &
98  hprogram,'TOWN ','TEB ','WRITE')
99 !
100 !-------------------------------------------------------------------------------
101 !
102 ! Geometric parameters
103 !
104 yrecfm='BLD'
105 ycomment='building fraction (-)'
106  CALL write_surf(dgu, u, &
107  hprogram,yrecfm,t%CUR%XBLD(:),iresp,hcomment=ycomment)
108 !
109 yrecfm='WALL_O_HOR'
110 ycomment='Wall surface over plan area surface (-)'
111  CALL write_surf(dgu, u, &
112  hprogram,yrecfm,t%CUR%XWALL_O_HOR(:),iresp,hcomment=ycomment)
113 !
114 yrecfm='BLD_HEIGHT'
115 ycomment='Building Height (m)'
116  CALL write_surf(dgu, u, &
117  hprogram,yrecfm,t%CUR%XBLD_HEIGHT(:),iresp,hcomment=ycomment)
118 !
119 yrecfm='Z0_TOWN'
120 ycomment='Town roughness length (m)'
121  CALL write_surf(dgu, u, &
122  hprogram,yrecfm,t%CUR%XZ0_TOWN(:),iresp,hcomment=ycomment)
123 !
124 yrecfm='XROAD_DIR'
125 ycomment='Road direction'
126  CALL write_surf(dgu, u, &
127  hprogram,yrecfm,t%CUR%XROAD_DIR(:),iresp,hcomment=ycomment)
128 !
129 yrecfm='GARDEN_FRAC'
130 ycomment='Garden fraction (-)'
131  CALL write_surf(dgu, u, &
132  hprogram,yrecfm,t%CUR%XGARDEN(:),iresp,hcomment=ycomment)
133 !
134 yrecfm='GREENROOF_FRAC'
135 ycomment='Greenroof fraction (-)'
136  CALL write_surf(dgu, u, &
137  hprogram,yrecfm,t%CUR%XGREENROOF(:),iresp,hcomment=ycomment)
138  !
139 yrecfm='PANEL_FRAC'
140 ycomment='Solar Panel fraction (-)'
141  CALL write_surf(dgu, u, &
142  hprogram,yrecfm,tpn%XFRAC_PANEL(:),iresp,hcomment=ycomment)
143 !
144 !-------------------------------------------------------------------------------
145 !
146 ! Building parameters
147 !
148 yrecfm='ALB_ROOF'
149 ycomment='Roof Albedo'
150  CALL write_surf(dgu, u, &
151  hprogram,yrecfm,t%CUR%XALB_ROOF(:),iresp,hcomment=ycomment)
152 !
153 yrecfm='EMIS_ROOF'
154 ycomment='Roof Emissivity'
155  CALL write_surf(dgu, u, &
156  hprogram,yrecfm,t%CUR%XEMIS_ROOF(:),iresp,hcomment=ycomment)
157 !
158 DO jlayer=1,top%NROOF_LAYER
159  WRITE(yrecfm,fmt='(A,I1.1)') 'HC_ROOF',jlayer
160  ycomment='Roof Heat Capacity'
161  CALL write_surf(dgu, u, &
162  hprogram,yrecfm,t%CUR%XHC_ROOF(:,jlayer),iresp,hcomment=ycomment)
163 END DO
164 !
165 DO jlayer=1,top%NROOF_LAYER
166  WRITE(yrecfm,fmt='(A,I1.1)') 'TC_ROOF',jlayer
167  ycomment='Roof thermal conductivity'
168  CALL write_surf(dgu, u, &
169  hprogram,yrecfm,t%CUR%XTC_ROOF(:,jlayer),iresp,hcomment=ycomment)
170 END DO
171 !
172 DO jlayer=1,top%NROOF_LAYER
173  WRITE(yrecfm,fmt='(A,I1.1)') 'D_ROOF',jlayer
174  ycomment='Roof layer thickness'
175  CALL write_surf(dgu, u, &
176  hprogram,yrecfm,t%CUR%XD_ROOF(:,jlayer),iresp,hcomment=ycomment)
177 END DO
178 !
179 yrecfm='ROUGH_ROOF'
180 ycomment='Roof roughness'
181  CALL write_surf(dgu, u, &
182  hprogram,yrecfm,t%CUR%XROUGH_ROOF(:),iresp,hcomment=ycomment)
183 !
184 yrecfm='ALB_WALL'
185 ycomment='WALL Albedo'
186  CALL write_surf(dgu, u, &
187  hprogram,yrecfm,t%CUR%XALB_WALL(:),iresp,hcomment=ycomment)
188 !
189 yrecfm='EMIS_WALL'
190 ycomment='WALL Emissivity'
191  CALL write_surf(dgu, u, &
192  hprogram,yrecfm,t%CUR%XEMIS_WALL(:),iresp,hcomment=ycomment)
193 !
194 DO jlayer=1,top%NWALL_LAYER
195  WRITE(yrecfm,fmt='(A,I1.1)') 'HC_WALL',jlayer
196  ycomment='WALL Heat Capacity'
197  CALL write_surf(dgu, u, &
198  hprogram,yrecfm,t%CUR%XHC_WALL(:,jlayer),iresp,hcomment=ycomment)
199 END DO
200 !
201 DO jlayer=1,top%NWALL_LAYER
202  WRITE(yrecfm,fmt='(A,I1.1)') 'TC_WALL',jlayer
203  ycomment='WALL thermal conductivity'
204  CALL write_surf(dgu, u, &
205  hprogram,yrecfm,t%CUR%XTC_WALL(:,jlayer),iresp,hcomment=ycomment)
206 END DO
207 !
208 DO jlayer=1,top%NWALL_LAYER
209  WRITE(yrecfm,fmt='(A,I1.1)') 'D_WALL',jlayer
210  ycomment='WALL layer thickness'
211  CALL write_surf(dgu, u, &
212  hprogram,yrecfm,t%CUR%XD_WALL(:,jlayer),iresp,hcomment=ycomment)
213 END DO
214 !
215 yrecfm='ROUGH_WALL'
216 ycomment='Wall roughness'
217  CALL write_surf(dgu, u, &
218  hprogram,yrecfm,t%CUR%XROUGH_WALL(:),iresp,hcomment=ycomment)
219 !
220 !
221 yrecfm='RESIDENTIAL'
222 ycomment='Residential use fraction'
223  CALL write_surf(dgu, u, &
224  hprogram,yrecfm,t%CUR%XRESIDENTIAL(:),iresp,hcomment=ycomment)
225 !-------------------------------------------------------------------------------
226 !
227 ! Road parameters
228 !
229 yrecfm='ALB_ROAD'
230 ycomment='ROAD Albedo'
231  CALL write_surf(dgu, u, &
232  hprogram,yrecfm,t%CUR%XALB_ROAD(:),iresp,hcomment=ycomment)
233 !
234 yrecfm='EMIS_ROAD'
235 ycomment='ROAD Emissivity'
236  CALL write_surf(dgu, u, &
237  hprogram,yrecfm,t%CUR%XEMIS_ROAD(:),iresp,hcomment=ycomment)
238 !
239 DO jlayer=1,top%NROAD_LAYER
240  WRITE(yrecfm,fmt='(A,I1.1)') 'HC_ROAD',jlayer
241  ycomment='ROAD Heat Capacity'
242  CALL write_surf(dgu, u, &
243  hprogram,yrecfm,t%CUR%XHC_ROAD(:,jlayer),iresp,hcomment=ycomment)
244 END DO
245 !
246 DO jlayer=1,top%NROAD_LAYER
247  WRITE(yrecfm,fmt='(A,I1.1)') 'TC_ROAD',jlayer
248  ycomment='ROAD thermal conductivity'
249  CALL write_surf(dgu, u, &
250  hprogram,yrecfm,t%CUR%XTC_ROAD(:,jlayer),iresp,hcomment=ycomment)
251 END DO
252 !
253 DO jlayer=1,top%NROAD_LAYER
254  WRITE(yrecfm,fmt='(A,I1.1)') 'D_ROAD',jlayer
255  ycomment='ROAD layer thickness'
256  CALL write_surf(dgu, u, &
257  hprogram,yrecfm,t%CUR%XD_ROAD(:,jlayer),iresp,hcomment=ycomment)
258 END DO
259 !
260 !-------------------------------------------------------------------------------
261 !
262 ! Anthropogneic Fluxes
263 !
264 yrecfm='H_TRAFFIC'
265 ycomment='Traffic Heat Flux'
266  CALL write_surf(dgu, u, &
267  hprogram,yrecfm,t%CUR%XH_TRAFFIC(:),iresp,hcomment=ycomment)
268 !
269 yrecfm='LE_TRAFFIC'
270 ycomment='Traffic Latent Flux'
271  CALL write_surf(dgu, u, &
272  hprogram,yrecfm,t%CUR%XLE_TRAFFIC(:),iresp,hcomment=ycomment)
273 !
274 yrecfm='H_INDUSTRY'
275 ycomment='INDUSTRY Heat Flux'
276  CALL write_surf(dgu, u, &
277  hprogram,yrecfm,t%CUR%XH_INDUSTRY(:),iresp,hcomment=ycomment)
278 !
279 yrecfm='LE_INDUSTRY'
280 ycomment='INDUSTRY Latent Flux'
281  CALL write_surf(dgu, u, &
282  hprogram,yrecfm,t%CUR%XLE_INDUSTRY(:),iresp,hcomment=ycomment)
283 !
284 !-------------------------------------------------------------------------------
285 !
286 ! Building Energy Model parameters
287 !
288 IF (top%CBEM=='BEM') THEN
289  yrecfm='N_FLOOR'
290  ycomment='Number of floors'
291  CALL write_surf(dgu, u, &
292  hprogram,yrecfm,b%CUR%XN_FLOOR(:),iresp,hcomment=ycomment)
293 
294  DO jlayer=1,bop%NFLOOR_LAYER
295  WRITE(yrecfm,fmt='(A,I1.1)') 'HC_FLOOR',jlayer
296  ycomment='FLOOR Heat Capacity'
297  CALL write_surf(dgu, u, &
298  hprogram,yrecfm,b%CUR%XHC_FLOOR(:,jlayer),iresp,hcomment=ycomment)
299  END DO
300  !
301  DO jlayer=1,bop%NFLOOR_LAYER
302  WRITE(yrecfm,fmt='(A,I1.1)') 'TC_FLOOR',jlayer
303  ycomment='FLOOR thermal conductivity'
304  CALL write_surf(dgu, u, &
305  hprogram,yrecfm,b%CUR%XTC_FLOOR(:,jlayer),iresp,hcomment=ycomment)
306  END DO
307  !
308  DO jlayer=1,bop%NFLOOR_LAYER
309  WRITE(yrecfm,fmt='(A,I1.1)') 'D_FLOOR',jlayer
310  ycomment='FLOOR layer thickness'
311  CALL write_surf(dgu, u, &
312  hprogram,yrecfm,b%CUR%XD_FLOOR(:,jlayer),iresp,hcomment=ycomment)
313  END DO
314 ENDIF
315 !
316 !-------------------------------------------------------------------------------
317 !
318 ! End of IO
319 !
320  CALL end_io_surf_n(hprogram)
321 IF (lhook) CALL dr_hook('WRITE_DIAG_PGD_TEB_N',1,zhook_handle)
322 !
323 !
324 END SUBROUTINE write_diag_pgd_teb_n
subroutine init_io_surf_n(DTCO, DGU, U, HPROGRAM, HMASK, HSCHEME, HACTION)
subroutine end_io_surf_n(HPROGRAM)
Definition: end_io_surfn.F90:6
subroutine write_diag_pgd_teb_n(DTCO, DGU, U, B, BOP, T, TOP, TPN, HPROGRAM)