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