source: palm/trunk/SOURCE/urban_surface_mod.f90 @ 3607

Last change on this file since 3607 was 3607, checked in by suehring, 6 years ago

Output of radiation-related quantities migrated from urban_surface_model_mod to radiation_model_mod

  • Property svn:keywords set to Id
File size: 511.7 KB
Line 
1!> @file urban_surface_mod.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 2015-2018 Czech Technical University in Prague
18! Copyright 2015-2018 Institute of Computer Science of the
19!                     Czech Academy of Sciences, Prague
20! Copyright 1997-2018 Leibniz Universitaet Hannover
21!------------------------------------------------------------------------------!
22!
23! Current revisions:
24! ------------------
25!
26!
27! Former revisions:
28! -----------------
29! $Id: urban_surface_mod.f90 3607 2018-12-07 11:56:58Z suehring $
30! Output of radiation-related quantities migrated to radiation_model_mod.
31!
32! 3597 2018-12-04 08:40:18Z maronga
33! Fixed calculation method of near surface air potential temperature at 10 cm
34! and moved to surface_layer_fluxes. Removed unnecessary _eb strings.
35!
36! 3524 2018-11-14 13:36:44Z raasch
37! bugfix concerning allocation of t_surf_wall_v
38!
39! 3502 2018-11-07 14:45:23Z suehring
40! Disable initialization of building roofs with ground-floor-level properties,
41! since this causes strong oscillations of surface temperature during the
42! spinup.
43!
44! 3469 2018-10-30 20:05:07Z kanani
45! Add missing PUBLIC variables for new indoor model
46!
47! 3449 2018-10-29 19:36:56Z suehring
48! Bugfix: Fix average arrays allocations in usm_average_3d_data (J.Resler)
49! Bugfix: Fix reading wall temperatures (J.Resler)
50! Bugfix: Fix treating of outputs for wall temperature and sky view factors (J.Resler)
51!
52!
53! 3435 2018-10-26 18:25:44Z gronemeier
54! Bugfix: allocate gamma_w_green_sat until nzt_wall+1
55!
56! 3418 2018-10-24 16:07:39Z kanani
57! (rvtils, srissman)
58! -Updated building databse, two green roof types (ind_green_type_roof)
59! -Latent heat flux for green walls and roofs, new output of latent heatflux
60!  and soil water content of green roof substrate
61! -t_surf changed to t_surf_wall
62! -Added namelist parameter usm_wall_mod for lower wall tendency
63!  of first two wall layers during spinup
64! -Window calculations deactivated during spinup
65!
66! 3382 2018-10-19 13:10:32Z knoop
67! Bugix: made array declaration Fortran Standard conform
68!
69! 3378 2018-10-19 12:34:59Z kanani
70! merge from radiation branch (r3362) into trunk
71! (moh.hefny):
72! - check the requested output variables if they are correct
73! - added unscheduled_radiation_calls switch to control force_radiation_call
74! - minor formate changes
75!
76! 3371 2018-10-18 13:40:12Z knoop
77! Set flag indicating that albedo at urban surfaces is already initialized
78!
79! 3347 2018-10-15 14:21:08Z suehring
80! Enable USM initialization with default building parameters in case no static
81! input file exist.
82!
83! 3343 2018-10-15 10:38:52Z suehring
84! Add output variables usm_rad_pc_inlw, usm_rad_pc_insw*
85!
86! 3274 2018-09-24 15:42:55Z knoop
87! Modularization of all bulk cloud physics code components
88!
89! 3248 2018-09-14 09:42:06Z sward
90! Minor formating changes
91!
92! 3246 2018-09-13 15:14:50Z sward
93! Added error handling for input namelist via parin_fail_message
94!
95! 3241 2018-09-12 15:02:00Z raasch
96! unused variables removed
97!
98! 3223 2018-08-30 13:48:17Z suehring
99! Bugfix for commit 3222
100!
101! 3222 2018-08-30 13:35:35Z suehring
102! Introduction of surface array for type and its name
103!
104! 3203 2018-08-23 10:48:36Z suehring
105! Revise bulk parameter for emissivity at ground-floor level
106!
107! 3196 2018-08-13 12:26:14Z maronga
108! Added maximum aerodynamic resistance of 300 for horiztonal surfaces.
109!
110! 3176 2018-07-26 17:12:48Z suehring
111! Bugfix, update virtual potential surface temparture, else heat fluxes on
112! roofs might become unphysical
113!
114! 3152 2018-07-19 13:26:52Z suehring
115! Initialize q_surface, which might be used in surface_layer_fluxes
116!
117! 3151 2018-07-19 08:45:38Z raasch
118! remaining preprocessor define strings __check removed
119!
120! 3136 2018-07-16 14:48:21Z suehring
121! Limit also roughness length for heat and moisture where necessary
122!
123! 3123 2018-07-12 16:21:53Z suehring
124! Correct working precision for INTEGER number
125!
126! 3115 2018-07-10 12:49:26Z suehring
127! Additional building type to represent bridges
128!
129! 3091 2018-06-28 16:20:35Z suehring
130! - Limit aerodynamic resistance at vertical walls.
131! - Add check for local roughness length not exceeding surface-layer height and
132!   limit roughness length where necessary.
133!
134! 3065 2018-06-12 07:03:02Z Giersch
135! Unused array dxdir was removed, dz was replaced by dzu to consider vertical
136! grid stretching
137!
138! 3049 2018-05-29 13:52:36Z Giersch
139! Error messages revised
140!
141! 3045 2018-05-28 07:55:41Z Giersch
142! Error message added
143!
144! 3029 2018-05-23 12:19:17Z raasch
145! bugfix: close unit 151 instead of 90
146!
147! 3014 2018-05-09 08:42:38Z maronga
148! Added pc_transpiration_rate
149!
150! 2977 2018-04-17 10:27:57Z kanani
151! Implement changes from branch radiation (r2948-2971) with minor modifications.
152! (moh.hefny):
153! Extended exn for all model domain height to avoid the need to get nzut.
154!
155! 2963 2018-04-12 14:47:44Z suehring
156! Introduce index for vegetation/wall, pavement/green-wall and water/window
157! surfaces, for clearer access of surface fraction, albedo, emissivity, etc. .
158!
159! 2943 2018-04-03 16:17:10Z suehring
160! Calculate exner function at all height levels and remove some un-used
161! variables.
162!
163! 2932 2018-03-26 09:39:22Z maronga
164! renamed urban_surface_par to urban_surface_parameters
165!
166! 2921 2018-03-22 15:05:23Z Giersch
167! The activation of spinup has been moved to parin
168!
169! 2920 2018-03-22 11:22:01Z kanani
170! Remove unused pcbl, npcbl from ONLY list
171! moh.hefny:
172! Fixed bugs introduced by new structures and by moving radiation interaction
173! into radiation_model_mod.f90.
174! Bugfix: usm data output 3D didn't respect directions
175!
176! 2906 2018-03-19 08:56:40Z Giersch
177! Local variable ids has to be initialized with a value of -1 in
178! usm_average_3d_data
179!
180! 2894 2018-03-15 09:17:58Z Giersch
181! Calculations of the index range of the subdomain on file which overlaps with
182! the current subdomain are already done in read_restart_data_mod,
183! usm_read/write_restart_data have been renamed to usm_r/wrd_local, variable
184! named found has been introduced for checking if restart data was found,
185! reading of restart strings has been moved completely to
186! read_restart_data_mod, usm_rrd_local is already inside the overlap loop
187! programmed in read_restart_data_mod, SAVE attribute added where necessary,
188! deallocation and allocation of some arrays have been changed to take care of
189! different restart files that can be opened (index i), the marker *** end usm
190! *** is not necessary anymore, strings and their respective lengths are
191! written out and read now in case of restart runs to get rid of prescribed
192! character lengths
193!
194! 2805 2018-02-14 17:00:09Z suehring
195! Initialization of resistances.
196!
197! 2797 2018-02-08 13:24:35Z suehring
198! Comment concerning output of ground-heat flux added.
199!
200! 2766 2018-01-22 17:17:47Z kanani
201! Removed redundant commas, added some blanks
202!
203! 2765 2018-01-22 11:34:58Z maronga
204! Major bugfix in calculation of f_shf. Adjustment of roughness lengths in
205! building_pars
206!
207! 2750 2018-01-15 16:26:51Z knoop
208! Move flag plant canopy to modules
209!
210! 2737 2018-01-11 14:58:11Z kanani
211! Removed unused variables t_surf_whole...
212!
213! 2735 2018-01-11 12:01:27Z suehring
214! resistances are saved in surface attributes
215!
216! 2723 2018-01-05 09:27:03Z maronga
217! Bugfix for spinups (end_time was increased twice in case of LSM + USM runs)
218!
219! 2720 2018-01-02 16:27:15Z kanani
220! Correction of comment
221!
222! 2718 2018-01-02 08:49:38Z maronga
223! Corrected "Former revisions" section
224!
225! 2705 2017-12-18 11:26:23Z maronga
226! Changes from last commit documented
227!
228! 2703 2017-12-15 20:12:38Z maronga
229! Workaround for calculation of r_a
230!
231! 2696 2017-12-14 17:12:51Z kanani
232! - Change in file header (GPL part)
233! - Bugfix in calculation of pt_surface and related fluxes. (BM)
234! - Do not write surface temperatures onto pt array as this might cause
235!   problems with nesting. (MS)
236! - Revised calculation of pt1 (now done in surface_layer_fluxes).
237!   Bugfix, f_shf_window and f_shf_green were not set at vertical surface
238!   elements. (MS)
239! - merged with branch ebsolver
240!   green building surfaces do not evaporate yet
241!   properties of green wall layers and window layers are taken from wall layers
242!   this input data is missing. (RvT)
243! - Merged with branch radiation (developed by Mohamed Salim)
244! - Revised initialization. (MS)
245! - Rename emiss_surf into emissivity, roughness_wall into z0, albedo_surf into
246!   albedo. (MS)
247! - Move first call of usm_radiatin from usm_init to init_3d_model
248! - fixed problem with near surface temperature
249! - added near surface temperature pt_10cm_h(m), pt_10cm_v(l)%t(m)
250! - does not work with temp profile including stability, ol
251!   pt_10cm = pt1 now
252! - merged with 2357 bugfix, error message for nopointer version
253! - added indoor model coupling with wall heat flux
254! - added green substrate/ dry vegetation layer for buildings
255! - merged with 2232 new surface-type structure
256! - added transmissivity of window tiles
257! - added MOSAIK tile approach for 3 different surfaces (RvT)
258!
259! 2583 2017-10-26 13:58:38Z knoop
260! Bugfix: reverted MPI_Win_allocate_cptr introduction in last commit
261!
262! 2582 2017-10-26 13:19:46Z hellstea
263! Workaround for gnufortran compiler added in usm_calc_svf. CALL MPI_Win_allocate is
264! replaced by CALL MPI_Win_allocate_cptr if defined ( __gnufortran ).
265!
266! 2544 2017-10-13 18:09:32Z maronga
267! Date and time quantities are now read from date_and_time_mod. Solar constant is
268! read from radiation_model_mod
269!
270! 2516 2017-10-04 11:03:04Z suehring
271! Remove tabs
272!
273! 2514 2017-10-04 09:52:37Z suehring
274! upper bounds of 3d output changed from nx+1,ny+1 to nx,ny
275! no output of ghost layer data
276!
277! 2350 2017-08-15 11:48:26Z kanani
278! Bugfix and error message for nopointer version.
279! Additional "! defined(__nopointer)" as workaround to enable compilation of
280! nopointer version.
281!
282! 2318 2017-07-20 17:27:44Z suehring
283! Get topography top index via Function call
284!
285! 2317 2017-07-20 17:27:19Z suehring
286! Bugfix: adjust output of shf. Added support for spinups
287!
288! 2287 2017-06-15 16:46:30Z suehring
289! Bugfix in determination topography-top index
290!
291! 2269 2017-06-09 11:57:32Z suehring
292! Enable restart runs with different number of PEs
293! Bugfixes nopointer branch
294!
295! 2258 2017-06-08 07:55:13Z suehring
296! Bugfix, add pre-preprocessor directives to enable non-parrallel mode
297!
298! 2233 2017-05-30 18:08:54Z suehring
299!
300! 2232 2017-05-30 17:47:52Z suehring
301! Adjustments according to new surface-type structure. Remove usm_wall_heat_flux;
302! insteat, heat fluxes are directly applied in diffusion_s.
303!
304! 2213 2017-04-24 15:10:35Z kanani
305! Removal of output quantities usm_lad and usm_canopy_hr
306!
307! 2209 2017-04-19 09:34:46Z kanani
308! cpp switch __mpi3 removed,
309! minor formatting,
310! small bugfix for division by zero (Krc)
311!
312! 2113 2017-01-12 13:40:46Z kanani
313! cpp switch __mpi3 added for MPI-3 standard code (Ketelsen)
314!
315! 2071 2016-11-17 11:22:14Z maronga
316! Small bugfix (Resler)
317!
318! 2031 2016-10-21 15:11:58Z knoop
319! renamed variable rho to rho_ocean
320!
321! 2024 2016-10-12 16:42:37Z kanani
322! Bugfixes in deallocation of array plantt and reading of csf/csfsurf,
323! optimization of MPI-RMA operations,
324! declaration of pcbl as integer,
325! renamed usm_radnet -> usm_rad_net, usm_canopy_khf -> usm_canopy_hr,
326! splitted arrays svf -> svf & csf, svfsurf -> svfsurf & csfsurf,
327! use of new control parameter varnamelength,
328! added output variables usm_rad_ressw, usm_rad_reslw,
329! minor formatting changes,
330! minor optimizations.
331!
332! 2011 2016-09-19 17:29:57Z kanani
333! Major reformatting according to PALM coding standard (comments, blanks,
334! alphabetical ordering, etc.),
335! removed debug_prints,
336! removed auxiliary SUBROUTINE get_usm_info, instead, USM flag urban_surface is
337! defined in MODULE control_parameters (modules.f90) to avoid circular
338! dependencies,
339! renamed canopy_heat_flux to pc_heating_rate, as meaning of quantity changed.
340!
341! 2007 2016-08-24 15:47:17Z kanani
342! Initial revision
343!
344!
345! Description:
346! ------------
347! 2016/6/9 - Initial version of the USM (Urban Surface Model)
348!            authors: Jaroslav Resler, Pavel Krc
349!                     (Czech Technical University in Prague and Institute of
350!                      Computer Science of the Czech Academy of Sciences, Prague)
351!            with contributions: Michal Belda, Nina Benesova, Ondrej Vlcek
352!            partly inspired by PALM LSM (B. Maronga)
353!            parameterizations of Ra checked with TUF3D (E. S. Krayenhoff)
354!> Module for Urban Surface Model (USM)
355!> The module includes:
356!>    1. radiation model with direct/diffuse radiation, shading, reflections
357!>       and integration with plant canopy
358!>    2. wall and wall surface model
359!>    3. surface layer energy balance
360!>    4. anthropogenic heat (only from transportation so far)
361!>    5. necessary auxiliary subroutines (reading inputs, writing outputs,
362!>       restart simulations, ...)
363!> It also make use of standard radiation and integrates it into
364!> urban surface model.
365!>
366!> Further work:
367!> -------------
368!> 1. Remove global arrays surfouts, surfoutl and only keep track of radiosity
369!>    from surfaces that are visible from local surfaces (i.e. there is a SVF
370!>    where target is local). To do that, radiosity will be exchanged after each
371!>    reflection step using MPI_Alltoall instead of current MPI_Allgather.
372!>
373!> 2. Temporarily large values of surface heat flux can be observed, up to
374!>    1.2 Km/s, which seem to be not realistic.
375!>
376!> @todo Output of _av variables in case of restarts
377!> @todo Revise flux conversion in energy-balance solver
378!> @todo Bugfixing in nopointer branch
379!> @todo Check optimizations for RMA operations
380!> @todo Alternatives for MPI_WIN_ALLOCATE? (causes problems with openmpi)
381!> @todo Check for load imbalances in CPU measures, e.g. for exchange_horiz_prog
382!>       factor 3 between min and max time
383!> @todo Move setting of flag indoor_model to indoor_model_mod once available
384!> @todo Check divisions in wtend (etc.) calculations for possible division
385!>       by zero, e.g. in case fraq(0,m) + fraq(1,m) = 0?!
386!> @todo Use unit 90 for OPEN/CLOSE of input files (FK)
387!> @todo Move plant canopy stuff into plant canopy code
388!------------------------------------------------------------------------------!
389 MODULE urban_surface_mod
390
391    USE arrays_3d,                                                             &
392#if ! defined( __nopointer )
393        ONLY:  hyp, zu, pt, p, u, v, w, tend, exner, hyrho, prr, q, ql, vpt
394#else
395        ONLY:  hyp,     pt,    u, v, w, tend, exner, hyrho, prr, q, ql, vpt
396#endif
397    USE calc_mean_profile_mod,                                                 &
398        ONLY:  calc_mean_profile
399
400    USE basic_constants_and_equations_mod,                                     &
401        ONLY:  c_p, g, kappa, pi, r_d, rho_l, l_v
402
403    USE control_parameters,                                                    &
404        ONLY:  coupling_start_time, topography, dt_3d, humidity,               &
405               intermediate_timestep_count, initializing_actions,              &
406               intermediate_timestep_count_max, simulated_time, end_time,      &
407               timestep_scheme, tsc, coupling_char, io_blocks, io_group,       &
408               message_string, time_since_reference_point, surface_pressure,   &
409               pt_surface, large_scale_forcing, lsf_surf, spinup,              &
410               spinup_pt_mean, spinup_time, time_do3d, dt_do3d,                &
411               average_count_3d, varnamelength, urban_surface,                 &
412               plant_canopy, dz
413
414    USE bulk_cloud_model_mod,                                                  &
415        ONLY: bulk_cloud_model, precipitation
416               
417    USE cpulog,                                                                &
418        ONLY:  cpu_log, log_point, log_point_s
419
420    USE date_and_time_mod,                                                     &
421        ONLY:  time_utc_init
422
423    USE grid_variables,                                                        &
424        ONLY:  dx, dy, ddx, ddy, ddx2, ddy2
425
426    USE indices,                                                               &
427        ONLY:  nx, ny, nnx, nny, nnz, nxl, nxlg, nxr, nxrg, nyn, nyng, nys,    &
428               nysg, nzb, nzt, nbgp, wall_flags_0
429
430    USE, INTRINSIC :: iso_c_binding 
431
432    USE kinds
433             
434    USE pegrid
435   
436    USE plant_canopy_model_mod,                                                &
437        ONLY:  pc_heating_rate, pc_transpiration_rate, pc_latent_rate
438   
439    USE radiation_model_mod,                                                   &
440        ONLY:  albedo_type, radiation_interaction, calc_zenith, zenith,        &
441               radiation, rad_sw_in, rad_lw_in, rad_sw_out, rad_lw_out,        &
442               sigma_sb, sun_direction, sun_dir_lat, sun_dir_lon,              &
443               force_radiation_call, iup_u, inorth_u, isouth_u, ieast_u,       &
444               iwest_u, iup_l, inorth_l, isouth_l, ieast_l, iwest_l, id,       &
445               iz, iy, ix,  nsurf, idsvf, ndsvf,                               &
446               idcsf, ndcsf, kdcsf, pct,                                       &
447               nzub, nzut, unscheduled_radiation_calls
448
449    USE statistics,                                                            &
450        ONLY:  hom, statistic_regions
451
452    USE surface_mod,                                                           &
453        ONLY:  get_topography_top_index_ji, get_topography_top_index,          &
454               ind_pav_green, ind_veg_wall, ind_wat_win, surf_usm_h,           &
455               surf_usm_v, surface_restore_elements
456
457
458    IMPLICIT NONE
459
460!
461!-- USM model constants
462
463    REAL(wp), PARAMETER ::                     &
464              b_ch               = 6.04_wp,    & ! Clapp & Hornberger exponent
465              lambda_h_green_dry = 0.19_wp,    & ! heat conductivity for dry soil   
466              lambda_h_green_sm  = 3.44_wp,    & ! heat conductivity of the soil matrix
467              lambda_h_water     = 0.57_wp,    & ! heat conductivity of water
468              psi_sat            = -0.388_wp,  & ! soil matrix potential at saturation
469              rho_c_soil         = 2.19E6_wp,  & ! volumetric heat capacity of soil
470              rho_c_water        = 4.20E6_wp !,  & ! volumetric heat capacity of water
471!               m_max_depth        = 0.0002_wp     ! Maximum capacity of the water reservoir (m)
472
473!
474!-- Soil parameters I           alpha_vg,      l_vg_green,    n_vg, gamma_w_green_sat
475    REAL(wp), DIMENSION(0:3,1:7), PARAMETER :: soil_pars = RESHAPE( (/     &
476                                 3.83_wp,  1.250_wp, 1.38_wp,  6.94E-6_wp, & ! 1
477                                 3.14_wp, -2.342_wp, 1.28_wp,  1.16E-6_wp, & ! 2
478                                 0.83_wp, -0.588_wp, 1.25_wp,  0.26E-6_wp, & ! 3
479                                 3.67_wp, -1.977_wp, 1.10_wp,  2.87E-6_wp, & ! 4
480                                 2.65_wp,  2.500_wp, 1.10_wp,  1.74E-6_wp, & ! 5
481                                 1.30_wp,  0.400_wp, 1.20_wp,  0.93E-6_wp, & ! 6
482                                 0.00_wp,  0.00_wp,  0.00_wp,  0.57E-6_wp  & ! 7
483                                 /), (/ 4, 7 /) )
484
485!
486!-- Soil parameters II              swc_sat,     fc,   wilt,    swc_res 
487    REAL(wp), DIMENSION(0:3,1:7), PARAMETER :: m_soil_pars = RESHAPE( (/ &
488                                 0.403_wp, 0.244_wp, 0.059_wp, 0.025_wp, & ! 1
489                                 0.439_wp, 0.347_wp, 0.151_wp, 0.010_wp, & ! 2
490                                 0.430_wp, 0.383_wp, 0.133_wp, 0.010_wp, & ! 3
491                                 0.520_wp, 0.448_wp, 0.279_wp, 0.010_wp, & ! 4
492                                 0.614_wp, 0.541_wp, 0.335_wp, 0.010_wp, & ! 5
493                                 0.766_wp, 0.663_wp, 0.267_wp, 0.010_wp, & ! 6
494                                 0.472_wp, 0.323_wp, 0.171_wp, 0.000_wp  & ! 7
495                                 /), (/ 4, 7 /) )
496                               
497    !   value 9999999.9_wp -> generic available or user-defined value must be set
498!   otherwise -> no generic variable and user setting is optional
499    REAL(wp) :: alpha_vangenuchten = 9999999.9_wp,      & !< NAMELIST alpha_vg
500                field_capacity = 9999999.9_wp,          & !< NAMELIST fc
501                hydraulic_conductivity = 9999999.9_wp,  & !< NAMELIST gamma_w_green_sat
502                lambda_h_green_sat = 0.0_wp,            & !< heat conductivity for saturated soil
503                l_vangenuchten = 9999999.9_wp,          & !< NAMELIST l_vg
504                n_vangenuchten = 9999999.9_wp,          & !< NAMELIST n_vg
505                residual_moisture = 9999999.9_wp,       & !< NAMELIST m_res
506                saturation_moisture = 9999999.9_wp,     & !< NAMELIST m_sat
507                wilting_point = 9999999.9_wp!,           & !< NAMELIST m_wilt
508   
509
510!-- configuration parameters (they can be setup in PALM config)
511    LOGICAL ::  usm_material_model = .TRUE.        !< flag parameter indicating wheather the  model of heat in materials is used
512    LOGICAL ::  usm_anthropogenic_heat = .FALSE.   !< flag parameter indicating wheather the anthropogenic heat sources (e.g.transportation) are used
513    LOGICAL ::  force_radiation_call_l = .FALSE.   !< flag parameter for unscheduled radiation model calls
514    LOGICAL ::  indoor_model = .FALSE.             !< whether to use the indoor model
515    LOGICAL ::  read_wall_temp_3d = .FALSE.
516    LOGICAL ::  usm_wall_mod = .FALSE.             !< reduces conductivity of the first 2 wall layers by factor 0.1
517
518
519    INTEGER(iwp) ::  building_type = 1               !< default building type (preleminary setting)
520    INTEGER(iwp) ::  land_category = 2               !< default category for land surface
521    INTEGER(iwp) ::  wall_category = 2               !< default category for wall surface over pedestrian zone
522    INTEGER(iwp) ::  pedestrian_category = 2         !< default category for wall surface in pedestrian zone
523    INTEGER(iwp) ::  roof_category = 2               !< default category for root surface
524    REAL(wp)     ::  roughness_concrete = 0.001_wp   !< roughness length of average concrete surface
525!
526!-- Indices of input attributes for (above) ground floor level
527    INTEGER(iwp) ::  ind_alb_wall_agfl     = 65  !< index in input list for albedo_type of wall above ground floor level
528    INTEGER(iwp) ::  ind_alb_wall_gfl      = 32  !< index in input list for albedo_type of wall ground floor level
529    INTEGER(iwp) ::  ind_alb_wall_r        = 96  !< index in input list for albedo_type of wall roof
530    INTEGER(iwp) ::  ind_alb_green_agfl    = 83  !< index in input list for albedo_type of green above ground floor level
531    INTEGER(iwp) ::  ind_alb_green_gfl     = 50  !< index in input list for albedo_type of green ground floor level
532    INTEGER(iwp) ::  ind_alb_green_r       = 115 !< index in input list for albedo_type of green roof
533    INTEGER(iwp) ::  ind_alb_win_agfl      = 79  !< index in input list for albedo_type of window fraction above ground floor level
534    INTEGER(iwp) ::  ind_alb_win_gfl       = 46  !< index in input list for albedo_type of window fraction ground floor level
535    INTEGER(iwp) ::  ind_alb_win_r         = 110 !< index in input list for albedo_type of window fraction roof
536    INTEGER(iwp) ::  ind_emis_wall_agfl    = 64  !< index in input list for wall emissivity, above ground floor level
537    INTEGER(iwp) ::  ind_emis_wall_gfl     = 31  !< index in input list for wall emissivity, ground floor level
538    INTEGER(iwp) ::  ind_emis_wall_r       = 95  !< index in input list for wall emissivity, roof
539    INTEGER(iwp) ::  ind_emis_green_agfl   = 82  !< index in input list for green emissivity, above ground floor level
540    INTEGER(iwp) ::  ind_emis_green_gfl    = 49  !< index in input list for green emissivity, ground floor level
541    INTEGER(iwp) ::  ind_emis_green_r      = 114 !< index in input list for green emissivity, roof
542    INTEGER(iwp) ::  ind_emis_win_agfl     = 77  !< index in input list for window emissivity, above ground floor level
543    INTEGER(iwp) ::  ind_emis_win_gfl      = 44  !< index in input list for window emissivity, ground floor level
544    INTEGER(iwp) ::  ind_emis_win_r        = 108 !< index in input list for window emissivity, roof
545    INTEGER(iwp) ::  ind_green_frac_w_agfl = 80  !< index in input list for green fraction on wall, above ground floor level
546    INTEGER(iwp) ::  ind_green_frac_w_gfl  = 47  !< index in input list for green fraction on wall, ground floor level
547    INTEGER(iwp) ::  ind_green_frac_r_agfl = 112 !< index in input list for green fraction on roof, above ground floor level
548    INTEGER(iwp) ::  ind_green_frac_r_gfl  = 111 !< index in input list for green fraction on roof, ground floor level
549    INTEGER(iwp) ::  ind_hc1_agfl          = 58  !< index in input list for heat capacity at first wall layer, above ground floor level
550    INTEGER(iwp) ::  ind_hc1_gfl           = 25  !< index in input list for heat capacity at first wall layer, ground floor level
551    INTEGER(iwp) ::  ind_hc1_wall_r        = 89  !< index in input list for heat capacity at first wall layer, roof
552    INTEGER(iwp) ::  ind_hc1_win_agfl      = 71  !< index in input list for heat capacity at first window layer, above ground floor level
553    INTEGER(iwp) ::  ind_hc1_win_gfl       = 38  !< index in input list for heat capacity at first window layer, ground floor level
554    INTEGER(iwp) ::  ind_hc1_win_r         = 102 !< index in input list for heat capacity at first window layer, roof
555    INTEGER(iwp) ::  ind_hc2_agfl          = 59  !< index in input list for heat capacity at second wall layer, above ground floor level
556    INTEGER(iwp) ::  ind_hc2_gfl           = 26  !< index in input list for heat capacity at second wall layer, ground floor level
557    INTEGER(iwp) ::  ind_hc2_wall_r        = 90  !< index in input list for heat capacity at second wall layer, roof
558    INTEGER(iwp) ::  ind_hc2_win_agfl      = 72  !< index in input list for heat capacity at second window layer, above ground floor level
559    INTEGER(iwp) ::  ind_hc2_win_gfl       = 39  !< index in input list for heat capacity at second window layer, ground floor level
560    INTEGER(iwp) ::  ind_hc2_win_r         = 103 !< index in input list for heat capacity at second window layer, roof
561    INTEGER(iwp) ::  ind_hc3_agfl          = 60  !< index in input list for heat capacity at third wall layer, above ground floor level
562    INTEGER(iwp) ::  ind_hc3_gfl           = 27  !< index in input list for heat capacity at third wall layer, ground floor level
563    INTEGER(iwp) ::  ind_hc3_wall_r        = 91  !< index in input list for heat capacity at third wall layer, roof
564    INTEGER(iwp) ::  ind_hc3_win_agfl      = 73  !< index in input list for heat capacity at third window layer, above ground floor level
565    INTEGER(iwp) ::  ind_hc3_win_gfl       = 40  !< index in input list for heat capacity at third window layer, ground floor level
566    INTEGER(iwp) ::  ind_hc3_win_r         = 104 !< index in input list for heat capacity at third window layer, roof
567    INTEGER(iwp) ::  ind_gflh              = 17  !< index in input list for ground floor level height
568    INTEGER(iwp) ::  ind_lai_r_agfl        = 113 !< index in input list for LAI on roof, above ground floor level
569    INTEGER(iwp) ::  ind_lai_r_gfl         = 113  !< index in input list for LAI on roof, ground floor level
570    INTEGER(iwp) ::  ind_lai_w_agfl        = 81  !< index in input list for LAI on wall, above ground floor level
571    INTEGER(iwp) ::  ind_lai_w_gfl         = 48  !< index in input list for LAI on wall, ground floor level
572    INTEGER(iwp) ::  ind_tc1_agfl          = 61  !< index in input list for thermal conductivity at first wall layer, above ground floor level
573    INTEGER(iwp) ::  ind_tc1_gfl           = 28  !< index in input list for thermal conductivity at first wall layer, ground floor level
574    INTEGER(iwp) ::  ind_tc1_wall_r        = 92  !< index in input list for thermal conductivity at first wall layer, roof
575    INTEGER(iwp) ::  ind_tc1_win_agfl      = 74  !< index in input list for thermal conductivity at first window layer, above ground floor level
576    INTEGER(iwp) ::  ind_tc1_win_gfl       = 41  !< index in input list for thermal conductivity at first window layer, ground floor level
577    INTEGER(iwp) ::  ind_tc1_win_r         = 105 !< index in input list for thermal conductivity at first window layer, roof
578    INTEGER(iwp) ::  ind_tc2_agfl          = 62  !< index in input list for thermal conductivity at second wall layer, above ground floor level
579    INTEGER(iwp) ::  ind_tc2_gfl           = 29  !< index in input list for thermal conductivity at second wall layer, ground floor level
580    INTEGER(iwp) ::  ind_tc2_wall_r        = 93  !< index in input list for thermal conductivity at second wall layer, roof
581    INTEGER(iwp) ::  ind_tc2_win_agfl      = 75  !< index in input list for thermal conductivity at second window layer, above ground floor level
582    INTEGER(iwp) ::  ind_tc2_win_gfl       = 42  !< index in input list for thermal conductivity at second window layer, ground floor level
583    INTEGER(iwp) ::  ind_tc2_win_r         = 106 !< index in input list for thermal conductivity at second window layer, ground floor level
584    INTEGER(iwp) ::  ind_tc3_agfl          = 63  !< index in input list for thermal conductivity at third wall layer, above ground floor level
585    INTEGER(iwp) ::  ind_tc3_gfl           = 30  !< index in input list for thermal conductivity at third wall layer, ground floor level
586    INTEGER(iwp) ::  ind_tc3_wall_r        = 94  !< index in input list for thermal conductivity at third wall layer, roof
587    INTEGER(iwp) ::  ind_tc3_win_agfl      = 76  !< index in input list for thermal conductivity at third window layer, above ground floor level
588    INTEGER(iwp) ::  ind_tc3_win_gfl       = 43  !< index in input list for thermal conductivity at third window layer, ground floor level
589    INTEGER(iwp) ::  ind_tc3_win_r         = 107 !< index in input list for thermal conductivity at third window layer, roof
590    INTEGER(iwp) ::  ind_thick_1_agfl      = 54  !< index for wall layer thickness - 1st layer above ground floor level
591    INTEGER(iwp) ::  ind_thick_1_gfl       = 21  !< index for wall layer thickness - 1st layer ground floor level
592    INTEGER(iwp) ::  ind_thick_1_wall_r    = 85  !< index for wall layer thickness - 1st layer roof
593    INTEGER(iwp) ::  ind_thick_1_win_agfl  = 67  !< index for window layer thickness - 1st layer above ground floor level
594    INTEGER(iwp) ::  ind_thick_1_win_gfl   = 34  !< index for window layer thickness - 1st layer ground floor level
595    INTEGER(iwp) ::  ind_thick_1_win_r     = 98  !< index for window layer thickness - 1st layer roof
596    INTEGER(iwp) ::  ind_thick_2_agfl      = 55  !< index for wall layer thickness - 2nd layer above ground floor level
597    INTEGER(iwp) ::  ind_thick_2_gfl       = 22  !< index for wall layer thickness - 2nd layer ground floor level
598    INTEGER(iwp) ::  ind_thick_2_wall_r    = 86  !< index for wall layer thickness - 2nd layer roof
599    INTEGER(iwp) ::  ind_thick_2_win_agfl  = 68  !< index for window layer thickness - 2nd layer above ground floor level
600    INTEGER(iwp) ::  ind_thick_2_win_gfl   = 35  !< index for window layer thickness - 2nd layer ground floor level
601    INTEGER(iwp) ::  ind_thick_2_win_r     = 99  !< index for window layer thickness - 2nd layer roof
602    INTEGER(iwp) ::  ind_thick_3_agfl      = 56  !< index for wall layer thickness - 3rd layer above ground floor level
603    INTEGER(iwp) ::  ind_thick_3_gfl       = 23  !< index for wall layer thickness - 3rd layer ground floor level
604    INTEGER(iwp) ::  ind_thick_3_wall_r    = 87  !< index for wall layer thickness - 3rd layer roof
605    INTEGER(iwp) ::  ind_thick_3_win_agfl  = 69  !< index for window layer thickness - 3rd layer above ground floor level
606    INTEGER(iwp) ::  ind_thick_3_win_gfl   = 36  !< index for window layer thickness - 3rd layer ground floor level 
607    INTEGER(iwp) ::  ind_thick_3_win_r     = 100 !< index for window layer thickness - 3rd layer roof
608    INTEGER(iwp) ::  ind_thick_4_agfl      = 57  !< index for wall layer thickness - 4th layer above ground floor level
609    INTEGER(iwp) ::  ind_thick_4_gfl       = 24  !< index for wall layer thickness - 4th layer ground floor level
610    INTEGER(iwp) ::  ind_thick_4_wall_r    = 88  !< index for wall layer thickness - 4st layer roof
611    INTEGER(iwp) ::  ind_thick_4_win_agfl  = 70  !< index for window layer thickness - 4th layer above ground floor level
612    INTEGER(iwp) ::  ind_thick_4_win_gfl   = 37  !< index for window layer thickness - 4th layer ground floor level
613    INTEGER(iwp) ::  ind_thick_4_win_r     = 101 !< index for window layer thickness - 4th layer roof
614    INTEGER(iwp) ::  ind_trans_agfl        = 78  !< index in input list for window transmissivity, above ground floor level
615    INTEGER(iwp) ::  ind_trans_gfl         = 45  !< index in input list for window transmissivity, ground floor level
616    INTEGER(iwp) ::  ind_trans_r           = 109 !< index in input list for window transmissivity, roof
617    INTEGER(iwp) ::  ind_wall_frac_agfl    = 53  !< index in input list for wall fraction, above ground floor level
618    INTEGER(iwp) ::  ind_wall_frac_gfl     = 20  !< index in input list for wall fraction, ground floor level
619    INTEGER(iwp) ::  ind_wall_frac_r       = 84  !< index in input list for wall fraction, roof
620    INTEGER(iwp) ::  ind_win_frac_agfl     = 66  !< index in input list for window fraction, above ground floor level
621    INTEGER(iwp) ::  ind_win_frac_gfl      = 33  !< index in input list for window fraction, ground floor level
622    INTEGER(iwp) ::  ind_win_frac_r        = 97  !< index in input list for window fraction, roof
623    INTEGER(iwp) ::  ind_z0_agfl           = 51  !< index in input list for z0, above ground floor level
624    INTEGER(iwp) ::  ind_z0_gfl            = 18  !< index in input list for z0, ground floor level
625    INTEGER(iwp) ::  ind_z0qh_agfl         = 52  !< index in input list for z0h / z0q, above ground floor level
626    INTEGER(iwp) ::  ind_z0qh_gfl          = 19  !< index in input list for z0h / z0q, ground floor level
627    INTEGER(iwp) ::  ind_green_type_roof   = 116 !< index in input list for type of green roof
628
629
630    REAL(wp)  ::  roof_height_limit = 4.0_wp          !< height for distinguish between land surfaces and roofs
631    REAL(wp)  ::  ground_floor_level = 4.0_wp        !< default ground floor level
632
633
634    CHARACTER(37), DIMENSION(0:7), PARAMETER :: building_type_name = (/     &
635                                   'user-defined                         ', & !  0
636                                   'residential - 1950                   ', & !  1
637                                   'residential 1951 - 2000              ', & !  2
638                                   'residential 2001 -                   ', & !  3
639                                   'office - 1950                        ', & !  4
640                                   'office 1951 - 2000                   ', & !  5
641                                   'office 2001 -                        ', & !  6
642                                   'bridges                              '  & !  7
643                                                                     /)
644!
645!-- building parameters, 6 different types
646!-- Parameter for urban surface model
647!-- 0 - heat capacity wall surface, 1 - heat capacity of window surface, 2 - heat capacity of green surface
648!-- 3 - thermal conductivity of wall surface, 4 - thermal conductivity of window surface,
649!-- 5 - thermal conductivty of green surface, 6 - wall fraction ground plate,
650!-- 7 - 1st wall layer thickness ground plate, 8 - 2nd wall layer thickness ground plate
651!-- 9 - 3rd wall layer thickness ground plate, 10 - 4th wall layer thickness ground plate,
652!-- 11 - heat capacity 1st/2nd wall layer ground plate, 12 - heat capacity 3rd wall layer ground plate
653!-- 13 - heat capacity 4th wall layer ground plate, 14 - thermal conductivity 1st/2nd wall layer ground plate,
654!-- 15 - thermal conductivity 3rd wall layer ground plate, 16 - thermal conductivity 4th wall layer ground plate
655!-- 17 - ground floor level height, 18 - z0 roughness ground floor level, 19 - z0h/z0g roughness heaat/humidity,
656!-- 20 - wall fraction ground floor level, 21 - 1st wall layer thickness ground floor level,
657!-- 22 - 2nd wall layer thickness ground floor level, 23 - 3rd wall layer thickness ground floor level,
658!-- 24 - 4th wall layer thickness ground floor level, 25 - heat capacity 1st/2nd wall layer ground floor level,
659!-- 26 - heat capacity 3rd wall layer ground floor level, 27 - heat capacity 4th wall layer ground floor level,
660!-- 28 - thermal conductivity 1st/2nd wall layer ground floor level,
661!-- 29 - thermal conductivity 3rd wall layer ground floor level, 30 - thermal conductivity 4th wall layer ground floor level
662!-- 31 - wall emissivity ground floor level, 32 - wall albedo ground floor level, 33 - window fraction ground floor level,
663!-- 34 - 1st window layer thickness ground floor level, 35 - 2nd window layer thickness ground floor level,
664!-- 36 - 3rd window layer thickness ground floor level, 37 - 4th window layer thickness ground floor level,
665!-- 38 - heat capacity 1st/2nd window layer ground floor level, 39 - heat capacity 3rd window layer ground floor level,
666!-- 40 - heat capacity 4th window layer ground floor level,
667!-- 41 - thermal conductivity 1st/2nd window layer ground floor level,
668!-- 42 - thermal conductivity 3rd window layer ground floor level,
669!-- 43 - thermal conductivity 4th window layer ground floor level, 44 - window emissivity ground floor level,
670!-- 45 - window transmissivity ground floor level, 46 - window albedo ground floor level,
671!-- 47 - green fraction ground floor level, 48 - LAI on wall ground floor level, 49 - green emissivity ground floor level,
672!-- 50 - green albedo ground floor level, 51 - z0 roughness above ground floor level,
673!-- 52 - z0h/z0g roughness heat/humidity above ground floor level, 53 - wall fraction above ground floor level
674!-- 54 - 1st wall layer thickness above ground floor level, 55 - 2nd wall layer thickness above ground floor level
675!-- 56 - 3rd wall layer thickness above ground floor level, 57 - 4th wall layer thickness above ground floor level
676!-- 58 - heat capacity 1st/2nd wall layer above ground floor level,
677!-- 59 - heat capacity 3rd wall layer above ground floor level,
678!-- 60 - heat capacity 4th wall layer above ground floor level,
679!-- 61 - thermal conductivity 1st/2nd wall layer above ground floor level,
680!-- 62 - thermal conductivity 3rd wall layer above ground floor level,
681!-- 63 - thermal conductivity 4th wall layer above ground floor level,
682!-- 64 - wall emissivity above ground floor level, 65 - wall albedo above ground floor level,
683!-- 66 - window fraction above ground floor level, 67 - 1st window layer thickness above ground floor level,
684!-- 68 - 2nd thickness window layer above ground floor level, 69 - 3rd window layer thickness above ground floor level,
685!-- 70 - 4th window layer thickness above ground floor level,
686!-- 71 - heat capacity 1st/2nd window layer above ground floor level,
687!-- 72 - heat capacity 3rd window layer above ground floor level,
688!-- 73 - heat capacity 4th window layer above ground floor level,
689!-- 74 - conductivity 1st/2nd window layer above ground floor level,
690!-- 75 - thermal conductivity 3rd window layer above ground floor level,
691!-- 76 - thermal conductivity 4th window layer above ground floor level, 77 - window emissivity above ground floor level,
692!-- 78 - window transmissivity above ground floor level, 79 - window albedo above ground floor level,
693!-- 80 - green fraction above ground floor level, 81 - LAI on wall above ground floor level,
694!-- 82 - green emissivity above ground floor level, 83 - green albedo above ground floor level,
695!-- 84 - wall fraction roof, 85 - 1st wall layer thickness roof, 86 - 2nd wall layer thickness roof,
696!-- 87 - 3rd wall layer thickness roof, 88 - 4th wall layer thickness roof,
697!-- 89 - heat capacity 1st/2nd wall layer roof, 90 - heat capacity 3rd wall layer roof,
698!-- 91 - heat capacity 4th wall layer roof, 92 - thermal conductivity 1st/2nd wall layer roof,
699!-- 93 - thermal conductivity 3rd wall layer roof, 94 - thermal conductivity 4th wall layer roof,
700!-- 95 - wall emissivity roof, 96 - wall albedo roof, 97 - window fraction roof,
701!-- 98 - window 1st layer thickness roof, 99 - window 2nd layer thickness roof, 100 - window 3rd layer thickness roof,
702!-- 101 - window 4th layer thickness, 102 - heat capacity 1st/2nd window layer roof,
703!-- 103 - heat capacity 3rd window layer roof, 104 - heat capacity 4th window layer roof,
704!-- 105 - thermal conductivity 1st/2nd window layer roof, 106 - thermal conductivity 3rd window layer roof,
705!-- 107 - thermal conductivity 4th window layer roof, 108 - window emissivity roof, 109 - window transmissivity roof,
706!-- 110 - window albedo roof, 111 - green fraction roof ground floor level,
707!-- 112 - green fraction roof above ground floor level, 113 - LAI roof, 114 - green emissivity roof,
708!-- 115 - green albedo roof, 116 - green type roof,
709!-- Parameter for indoor model
710!-- 117 - indoor target summer temperature, 118 - indoor target winter temperature,
711!-- 119 - shading factor, 120 - g-value windows, 121 - u-value windows, 122 - basical airflow without occupancy of the room,
712!-- 123 - additional airflow depend of occupancy of the room, 124 - heat recovery efficiency,
713!-- 125 - dynamic parameter specific effective surface, 126 - dynamic parameter innner heatstorage,
714!-- 127 - ratio internal surface/floor area, 128 - maximal heating capacity, 129 - maximal cooling capacity,
715!-- 130 - additional internal heat gains dependent on occupancy of the room,
716!-- 131 - basic internal heat gains without occupancy of the room, 132 - storey height, 133 - ceiling construction height
717
718
719    REAL(wp), DIMENSION(0:133,1:7), PARAMETER :: building_pars = RESHAPE( (/   &
720        10.0_wp, 10.0_wp, 20000.0_wp, 23.0_wp, 23.0_wp, 10.0_wp,               & !parameter 0-5
721        1.0_wp, 0.005_wp, 0.01_wp, 0.39_wp, 0.63_wp, 2200000.0_wp,             & !parameter 6-11
722        1400000.0_wp, 1300000.0_wp, 0.35_wp, 0.8_wp, 2.1_wp, 4.0_wp,           & !parameter 12-17
723        0.01_wp, 0.001_wp, 0.75_wp,                                            & !parameter 18-20
724        0.005_wp, 0.01_wp, 0.39_wp, 0.63_wp, 2200000.0_wp,                     & !parameter 21-25
725        1400000.0_wp, 1300000.0_wp, 0.35_wp,                                   & !parameter 26-28                     
726        0.8_wp, 2.1_wp, 0.93_wp,                                               & !parameter 29-31       
727        27.0_wp, 0.25_wp, 0.003_wp, 0.006_wp, 0.012_wp, 0.018_wp,              & !parameter 32-37
728        1736000.0_wp, 1736000.0_wp, 1736000.0_wp,                              & !parameter 38-40
729        0.57_wp, 0.57_wp, 0.57_wp, 0.91_wp,                                    & !parameter 41-44
730        0.75_wp, 27.0_wp, 0.0_wp, 1.5_wp, 0.86_wp,                             & !parameter 45-49
731        5.0_wp, 0.001_wp, 0.0001_wp, 0.7_wp, 0.005_wp,                        & !parameter 50-54
732        0.01_wp, 0.39_wp, 0.63_wp, 2200000.0_wp,                               & !parameter 55-58
733        1400000.0_wp, 1300000.0_wp, 0.35_wp, 0.8_wp,                           & !parameter 59-62
734        2.1_wp, 0.93_wp, 27.0_wp, 0.3_wp,                                      & !parameter 63-66
735        0.003_wp, 0.006_wp, 0.012_wp, 0.018_wp,                                & !parameter 67-70
736        1736000.0_wp, 1736000.0_wp, 1736000.0_wp,                              & !parameter 71-73
737        0.57_wp, 0.57_wp, 0.57_wp, 0.91_wp, 0.75_wp,                           & !parameter 74-78
738        27.0_wp, 0.0_wp, 1.5_wp, 0.86_wp, 5.0_wp, 1.0_wp,                      & !parameter 79-84
739        0.005_wp, 0.01_wp, 0.31_wp, 0.63_wp, 2200000.0_wp, 1400000.0_wp,       & !parameter 85-90
740        1300000.0_wp, 0.35_wp, 0.8_wp, 2.1_wp, 0.93_wp, 27.0_wp, 0.0_wp,       & !parameter 91-97
741        0.003_wp, 0.006_wp, 0.012_wp, 0.018_wp, 1736000.0_wp,                  & !parameter 98-102
742        1736000.0_wp, 1736000.0_wp, 0.57_wp, 0.57_wp, 0.57_wp,                 & !parameter 103-107
743        0.91_wp, 0.75_wp, 27.0_wp, 0.0_wp, 0.0_wp, 1.5_wp,                     & !parameter 108-113
744        0.86_wp, 5.0_wp, 0.0_wp,                                              & !parameter 114-116
745        299.15_wp, 293.15_wp, 0.8_wp, 0.76_wp, 5.0_wp,                         & !parameter 117-121
746        0.1_wp, 0.5_wp, 0.0_wp, 3.5_wp, 370000.0_wp, 4.5_wp,                   & !parameter 122-127
747        100000.0_wp, 0.0_wp, 3.0_wp, 10.0_wp, 3.0_wp, 0.2_wp,                  & !parameter 128-133- end of type 1
748        10.0_wp, 10.0_wp, 20000.0_wp, 23.0_wp, 23.0_wp, 10.0_wp,               & !parameter 0-5
749        1.0_wp, 0.005_wp, 0.01_wp, 0.31_wp, 0.42_wp, 2000000.0_wp,             & !parameter 6-11
750        103000.0_wp, 900000.0_wp, 0.35_wp, 0.38_wp, 0.04_wp, 4.0_wp,           & !parameter 12-17
751        0.01_wp, 0.001_wp, 0.78_wp,                                            & !parameter 18-20
752        0.005_wp, 0.01_wp, 0.31_wp, 0.43_wp, 2000000.0_wp,                     & !parameter 21-25
753        103000.0_wp, 900000.0_wp, 0.35_wp,                                     & !parameter 26-28                     
754        0.38_wp, 0.04_wp, 0.92_wp,                                             & !parameter 29-31       
755        27.0_wp, 0.22_wp, 0.003_wp, 0.006_wp, 0.012_wp, 0.018_wp,              & !parameter 32-37
756        1736000.0_wp, 1736000.0_wp, 1736000.0_wp,                              & !parameter 38-40
757        0.11_wp, 0.11_wp, 0.11_wp, 0.11_wp,                                    & !parameter 41-44
758        0.7_wp, 27.0_wp, 0.0_wp, 1.5_wp, 0.86_wp,                              & !parameter 45-49
759        5.0_wp, 0.001_wp, 0.0001_wp, 0.73_wp, 0.005_wp,                       & !parameter 50-54
760        0.01_wp, 0.31_wp, 0.43_wp, 2000000.0_wp,                               & !parameter 55-58
761        103000.0_wp, 900000.0_wp, 0.35_wp, 0.38_wp,                            & !parameter 59-62
762        0.04_wp, 0.92_wp, 27.0_wp, 0.27_wp,                                    & !parameter 63-66
763        0.003_wp, 0.006_wp, 0.012_wp, 0.018_wp,                                & !parameter 67-70
764        1736000.0_wp, 1736000.0_wp, 1736000.0_wp,                              & !parameter 71-73
765        0.11_wp, 0.11_wp, 0.11_wp, 0.87_wp, 0.7_wp,                            & !parameter 74-78
766        27.0_wp, 0.0_wp, 1.5_wp, 0.86_wp, 5.0_wp, 1.0_wp,                      & !parameter 79-84
767        0.005_wp, 0.01_wp, 0.5_wp, 0.79_wp, 2000000.0_wp, 103000.0_wp,         & !parameter 85-90
768        900000.0_wp, 0.35_wp, 0.38_wp, 0.04_wp, 0.93_wp, 27.0_wp, 0.0_wp,      & !parameter 91-97
769        0.003_wp, 0.006_wp, 0.012_wp, 0.018_wp, 1736000.0_wp,                  & !parameter 98-102
770        1736000.0_wp, 1736000.0_wp, 0.11_wp, 0.11_wp, 0.11_wp,                 & !parameter 103-107
771        0.87_wp, 0.7_wp, 27.0_wp, 0.0_wp, 0.0_wp, 1.5_wp,                      & !parameter 108-113
772        0.86_wp, 5.0_wp, 0.0_wp,                                              & !parameter 114-116
773        299.15_wp, 293.15_wp, 0.8_wp, 0.6_wp, 3.0_wp,                          & !parameter 117-121
774        0.1_wp, 0.5_wp, 0.0_wp, 2.5_wp, 165000.0_wp, 4.5_wp,                   & !parameter 122-127
775        100000.0_wp, 0.0_wp, 4.0_wp, 8.0_wp, 3.0_wp, 0.2_wp,                   & !parameter 128-133- end of type 2
776        10.0_wp, 10.0_wp, 20000.0_wp, 23.0_wp, 23.0_wp, 10.0_wp,               & !parameter 0-5
777        1.0_wp, 0.005_wp, 0.01_wp, 0.41_wp, 0.7_wp, 2000000.0_wp,              & !parameter 6-11
778        103000.0_wp, 900000.0_wp, 0.35_wp, 0.14_wp, 0.035_wp, 4.0_wp,          & !parameter 12-17
779        0.01_wp, 0.001_wp, 0.75_wp,                                            & !parameter 18-20
780        0.005_wp, 0.01_wp, 0.41_wp, 0.7_wp, 2000000.0_wp,                      & !parameter 21-25
781        103000.0_wp, 900000.0_wp, 0.35_wp,                                     & !parameter 26-28                     
782        0.14_wp, 0.035_wp, 0.92_wp,                                            & !parameter 29-31       
783        27.0_wp, 0.25_wp, 0.003_wp, 0.006_wp, 0.012_wp, 0.018_wp,              & !parameter 32-37
784        1736000.0_wp, 1736000.0_wp, 1736000.0_wp,                              & !parameter 38-40
785        0.037_wp, 0.037_wp, 0.037_wp, 0.8_wp,                                     & !parameter 41-44
786        0.6_wp, 27.0_wp, 0.0_wp, 1.5_wp, 0.86_wp,                              & !parameter 45-49
787        5.0_wp, 0.001_wp, 0.0001_wp, 0.7_wp, 0.005_wp,                        & !parameter 50-54
788        0.01_wp, 0.41_wp, 0.7_wp, 2000000.0_wp,                                & !parameter 55-58
789        103000.0_wp, 900000.0_wp, 0.35_wp, 0.14_wp,                            & !parameter 59-62
790        0.035_wp, 0.92_wp, 27.0_wp, 0.3_wp,                                    & !parameter 63-66
791        0.003_wp, 0.006_wp, 0.012_wp, 0.018_wp,                                & !parameter 67-70
792        1736000.0_wp, 1736000.0_wp, 1736000.0_wp,                              & !parameter 71-73
793        0.037_wp, 0.037_wp, 0.037_wp, 0.8_wp, 0.6_wp,                             & !parameter 74-78
794        27.0_wp, 0.0_wp, 1.5_wp, 0.86_wp, 5.0_wp, 1.0_wp,                      & !parameter 79-84
795        0.005_wp, 0.01_wp, 0.41_wp, 0.7_wp, 2000000.0_wp, 103000.0_wp,         & !parameter 85-90
796        900000.0_wp, 0.35_wp, 0.14_wp, 0.035_wp, 0.93_wp, 27.0_wp, 0.0_wp,     & !parameter 91-97
797        0.003_wp, 0.006_wp, 0.012_wp, 0.018_wp, 1736000.0_wp,                  & !parameter 98-102
798        1736000.0_wp, 1736000.0_wp, 0.037_wp, 0.037_wp, 0.037_wp,                 & !parameter 103-107
799        0.8_wp, 0.6_wp, 27.0_wp, 0.0_wp, 0.0_wp, 1.5_wp,                       & !parameter 108-113
800        0.86_wp, 5.0_wp, 0.0_wp,                                              & !parameter 114-116
801        299.15_wp, 293.15_wp, 0.8_wp, 0.5_wp, 0.6_wp,                          & !parameter 117-121
802        0.1_wp, 0.5_wp, 0.8_wp, 2.5_wp, 80000.0_wp, 4.5_wp,                    & !parameter 122-127
803        100000.0_wp, 0.0_wp, 3.0_wp, 8.0_wp, 3.0_wp, 0.2_wp,                   & !parameter 128-133- end of type 3
804        10.0_wp, 10.0_wp, 20000.0_wp, 23.0_wp, 23.0_wp, 10.0_wp,               & !parameter 0-5
805        1.0_wp, 0.005_wp, 0.01_wp, 0.39_wp, 0.63_wp, 2200000.0_wp,             & !parameter 6-11
806        1400000.0_wp, 1300000.0_wp, 0.35_wp, 0.8_wp, 2.1_wp, 4.0_wp,           & !parameter 12-17
807        0.01_wp, 0.001_wp, 0.55_wp,                                            & !parameter 18-20
808        0.005_wp, 0.01_wp, 0.39_wp, 0.63_wp, 2200000.0_wp,                     & !parameter 21-25
809        1400000.0_wp, 1300000.0_wp, 0.35_wp,                                   & !parameter 26-28                     
810        0.8_wp, 2.1_wp, 0.93_wp,                                               & !parameter 29-31       
811        27.0_wp, 0.45_wp, 0.003_wp, 0.006_wp, 0.012_wp, 0.018_wp,              & !parameter 32-37
812        1736000.0_wp, 1736000.0_wp, 1736000.0_wp,                              & !parameter 38-40
813        0.57_wp, 0.57_wp, 0.57_wp, 0.91_wp,                                    & !parameter 41-44
814        0.75_wp, 27.0_wp, 0.0_wp, 1.5_wp, 0.86_wp,                             & !parameter 45-49
815        5.0_wp, 0.001_wp, 0.0001_wp, 0.5_wp, 0.005_wp,                        & !parameter 50-54
816        0.01_wp, 0.39_wp, 0.63_wp, 2200000.0_wp,                               & !parameter 55-58
817        1400000.0_wp, 1300000.0_wp, 0.35_wp, 0.8_wp,                           & !parameter 59-62
818        2.1_wp, 0.93_wp, 27.0_wp, 0.5_wp,                                      & !parameter 63-66
819        0.003_wp, 0.006_wp, 0.012_wp, 0.018_wp,                                & !parameter 67-70
820        1736000.0_wp, 1736000.0_wp, 1736000.0_wp,                              & !parameter 71-73
821        0.57_wp, 0.57_wp, 0.57_wp, 0.91_wp, 0.75_wp,                           & !parameter 74-78
822        27.0_wp, 0.0_wp, 1.5_wp, 0.86_wp, 5.0_wp, 1.0_wp,                      & !parameter 79-84
823        0.005_wp, 0.01_wp, 0.39_wp, 0.63_wp, 2200000.0_wp, 1400000.0_wp,       & !parameter 85-90
824        1300000.0_wp, 0.35_wp, 0.8_wp, 2.1_wp, 0.93_wp, 27.0_wp, 0.0_wp,       & !parameter 91-97
825        0.003_wp, 0.006_wp, 0.012_wp, 0.018_wp, 1736000.0_wp,                  & !parameter 98-102
826        1736000.0_wp, 1736000.0_wp, 0.57_wp, 0.57_wp, 0.57_wp,                 & !parameter 103-107
827        0.91_wp, 0.75_wp, 27.0_wp, 0.0_wp, 0.0_wp, 1.5_wp,                     & !parameter 108-113
828        0.86_wp, 5.0_wp, 0.0_wp,                                              & !parameter 114-116
829        299.15_wp, 293.15_wp, 0.8_wp, 0.76_wp, 5.0_wp,                         & !parameter 117-121
830        0.1_wp, 1.5_wp, 0.0_wp, 3.5_wp, 370000.0_wp, 4.5_wp,                   & !parameter 122-127
831        100000.0_wp, 0.0_wp, 3.0_wp, 10.0_wp, 3.0_wp, 0.2_wp,                  & !parameter 128-133- end of type 4
832        10.0_wp, 10.0_wp, 20000.0_wp, 23.0_wp, 23.0_wp, 10.0_wp,               & !parameter 0-5
833        1.0_wp, 0.005_wp, 0.01_wp, 0.31_wp, 0.43_wp, 2000000.0_wp,             & !parameter 6-11
834        103000.0_wp, 900000.0_wp, 0.35_wp, 0.38_wp, 0.04_wp, 4.0_wp,           & !parameter 12-17
835        0.01_wp, 0.001_wp, 0.55_wp,                                            & !parameter 18-20
836        0.005_wp, 0.01_wp, 0.31_wp, 0.43_wp, 2000000.0_wp,                     & !parameter 21-25
837        103000.0_wp, 900000.0_wp, 0.35_wp,                                     & !parameter 26-28                     
838        0.38_wp, 0.04_wp, 0.92_wp,                                             & !parameter 29-31       
839        27.0_wp, 0.45_wp, 0.003_wp, 0.006_wp, 0.012_wp, 0.018_wp,              & !parameter 32-37
840        1736000.0_wp, 1736000.0_wp, 1736000.0_wp,                              & !parameter 38-40
841        0.11_wp, 0.11_wp, 0.11_wp, 0.87_wp,                                    & !parameter 41-44
842        0.7_wp, 27.0_wp, 0.0_wp, 1.5_wp, 0.86_wp,                              & !parameter 45-49
843        5.0_wp, 0.001_wp, 0.0001_wp, 0.5_wp, 0.005_wp,                        & !parameter 50-54
844        0.01_wp, 0.31_wp, 0.43_wp, 2000000.0_wp,                               & !parameter 55-58
845        103000.0_wp, 900000.0_wp, 0.35_wp, 0.38_wp,                            & !parameter 59-62
846        0.04_wp, 0.92_wp, 27.0_wp, 0.5_wp,                                     & !parameter 63-66
847        0.003_wp, 0.006_wp, 0.012_wp, 0.018_wp,                                & !parameter 67-70
848        1736000.0_wp, 1736000.0_wp, 1736000.0_wp,                              & !parameter 71-73
849        0.11_wp, 0.11_wp, 0.11_wp, 0.87_wp, 0.7_wp,                            & !parameter 74-78
850        27.0_wp, 0.0_wp, 1.5_wp, 0.86_wp, 5.0_wp, 1.0_wp,                      & !parameter 79-84
851        0.005_wp, 0.01_wp, 0.31_wp, 0.43_wp, 2000000.0_wp, 103000.0_wp,        & !parameter 85-90
852        900000.0_wp, 0.35_wp, 0.38_wp, 0.04_wp, 0.91_wp, 27.0_wp, 0.0_wp,      & !parameter 91-97
853        0.003_wp, 0.006_wp, 0.012_wp, 0.018_wp, 1736000.0_wp,                  & !parameter 98-102
854        1736000.0_wp, 1736000.0_wp, 0.11_wp, 0.11_wp, 0.11_wp,                 & !parameter 103-107
855        0.87_wp, 0.7_wp, 27.0_wp, 0.0_wp, 0.0_wp, 1.5_wp,                      & !parameter 108-113
856        0.86_wp, 5.0_wp, 0.0_wp,                                              & !parameter 114-116
857        299.15_wp, 293.15_wp, 0.8_wp, 0.6_wp, 3.0_wp,                          & !parameter 117-121
858        0.1_wp, 1.5_wp, 0.65_wp, 2.5_wp, 165000.0_wp, 4.5_wp,                  & !parameter 122-127
859        100000.0_wp, 0.0_wp, 7.0_wp, 20.0_wp, 3.0_wp, 0.2_wp,                  & !parameter 128-133- end of type 5
860        10.0_wp, 10.0_wp, 20000.0_wp, 23.0_wp, 23.0_wp, 10.0_wp,               & !parameter 0-5
861        1.0_wp, 0.005_wp, 0.01_wp, 0.41_wp, 0.7_wp, 2000000.0_wp,              & !parameter 6-11
862        103000.0_wp, 900000.0_wp, 0.35_wp, 0.14_wp, 0.035_wp, 4.0_wp,          & !parameter 12-17
863        0.01_wp, 0.001_wp, 0.475_wp,                                           & !parameter 18-20
864        0.005_wp, 0.01_wp, 0.41_wp, 0.7_wp, 2000000.0_wp,                      & !parameter 21-25
865        103000.0_wp, 900000.0_wp, 0.35_wp,                                     & !parameter 26-28                     
866        0.14_wp, 0.035_wp, 0.92_wp,                                            & !parameter 29-31       
867        27.0_wp, 0.525_wp, 0.003_wp, 0.006_wp, 0.012_wp, 0.018_wp,             & !parameter 32-37
868        1736000.0_wp, 1736000.0_wp, 1736000.0_wp,                              & !parameter 38-40
869        0.037_wp, 0.037_wp, 0.037_wp, 0.8_wp,                                     & !parameter 41-44
870        0.6_wp, 27.0_wp, 0.0_wp, 1.5_wp, 0.86_wp,                              & !parameter 45-49
871        5.0_wp, 0.001_wp, 0.0001_wp, 0.425_wp, 0.005_wp,                      & !parameter 50-54
872        0.01_wp, 0.41_wp, 0.7_wp, 2000000.0_wp,                                & !parameter 55-58
873        103000.0_wp, 900000.0_wp, 0.35_wp, 0.14_wp,                            & !parameter 59-62
874        0.035_wp, 0.92_wp, 27.0_wp, 0.575_wp,                                  & !parameter 63-66
875        0.003_wp, 0.006_wp, 0.012_wp, 0.018_wp,                                & !parameter 67-70
876        1736000.0_wp, 1736000.0_wp, 1736000.0_wp,                              & !parameter 71-73
877        0.037_wp, 0.037_wp, 0.037_wp, 0.8_wp, 0.6_wp,                             & !parameter 74-78
878        27.0_wp, 0.0_wp, 1.5_wp, 0.86_wp, 5.0_wp, 1.0_wp,                      & !parameter 79-84
879        0.005_wp, 0.01_wp, 0.41_wp, 0.7_wp, 2000000.0_wp, 103000.0_wp,         & !parameter 85-90
880        900000.0_wp, 0.35_wp, 0.14_wp, 0.035_wp, 0.91_wp, 27.0_wp, 0.0_wp,     & !parameter 91-97
881        0.003_wp, 0.006_wp, 0.012_wp, 0.018_wp, 1736000.0_wp,                  & !parameter 98-102
882        1736000.0_wp, 1736000.0_wp, 0.037_wp, 0.037_wp, 0.037_wp,                 & !parameter 103-107
883        0.8_wp, 0.6_wp, 27.0_wp, 0.0_wp, 0.0_wp, 1.5_wp,                       & !parameter 108-113
884        0.86_wp, 5.0_wp, 0.0_wp,                                              & !parameter 114-116
885        299.15_wp, 293.15_wp, 0.8_wp, 0.5_wp, 0.6_wp,                          & !parameter 117-121
886        0.1_wp, 1.5_wp, 0.9_wp, 2.5_wp, 80000.0_wp, 4.5_wp,                    & !parameter 122-127
887        100000.0_wp, 0.0_wp, 5.0_wp, 15.0_wp, 3.0_wp, 0.2_wp,                  & !parameter 128-133- end of type 6   
888        10.0_wp, 10.0_wp, 20000.0_wp, 23.0_wp, 23.0_wp, 10.0_wp,               & !parameter 0-5
889        1.0_wp, 0.29_wp, 0.295_wp, 0.695_wp, 0.985_wp, 1950400.0_wp,           & !parameter 6-11
890        1848000.0_wp, 1848000.0_wp, 0.7_wp, 1.0_wp, 1.0_wp, 4.0_wp,            & !parameter 12-17
891        0.01_wp, 0.001_wp, 1.0_wp,                                             & !parameter 18-20
892        0.29_wp, 0.295_wp, 0.695_wp, 0.985_wp, 1950400.0_wp,                   & !parameter 21-25
893        1848000.0_wp, 1848000.0_wp, 0.7_wp,                                    & !parameter 26-28                     
894        1.0_wp, 1.0_wp, 0.9_wp,                                                & !parameter 29-31       
895        27.0_wp, 0.0_wp, 0.003_wp, 0.006_wp, 0.012_wp, 0.018_wp,               & !parameter 32-37
896        1736000.0_wp, 1736000.0_wp, 1736000.0_wp,                              & !parameter 38-40
897        0.57_wp, 0.57_wp, 0.57_wp, 0.8_wp,                                     & !parameter 41-44
898        0.6_wp, 27.0_wp, 0.0_wp, 1.5_wp, 0.86_wp,                              & !parameter 45-49
899        5.0_wp, 0.001_wp, 0.0001_wp, 1.0_wp, 0.29_wp,                         & !parameter 50-54
900        0.295_wp, 0.695_wp, 0.985_wp, 1950400.0_wp,                            & !parameter 55-58
901        1848000.0_wp, 1848000.0_wp, 0.7_wp, 1.0_wp,                            & !parameter 59-62
902        1.0_wp, 0.9_wp, 27.0_wp, 0.0_wp,                                       & !parameter 63-66
903        0.003_wp, 0.006_wp, 0.012_wp, 0.018_wp,                                & !parameter 67-70
904        1736000.0_wp, 1736000.0_wp, 1736000.0_wp,                              & !parameter 71-73
905        0.57_wp, 0.57_wp, 0.57_wp, 0.8_wp, 0.6_wp,                             & !parameter 74-78
906        27.0_wp, 0.0_wp, 1.5_wp, 0.86_wp, 5.0_wp, 1.0_wp,                      & !parameter 79-84
907        0.29_wp, 0.295_wp, 0.695_wp, 0.985_wp, 1950400.0_wp, 1848000.0_wp,     & !parameter 85-90
908        1848000.0_wp, 0.7_wp, 1.0_wp, 1.0_wp, 0.9_wp, 27.0_wp, 0.0_wp,         & !parameter 91-97
909        0.003_wp, 0.006_wp, 0.012_wp, 0.018_wp, 1736000.0_wp,                  & !parameter 98-102
910        1736000.0_wp, 1736000.0_wp, 0.57_wp, 0.57_wp, 0.57_wp,                 & !parameter 103-107
911        0.8_wp, 0.6_wp, 27.0_wp, 0.0_wp, 0.0_wp, 1.5_wp,                       & !parameter 108-113
912        0.86_wp, 5.0_wp, 0.0_wp,                                              & !parameter 114-116
913        299.15_wp, 293.15_wp, 0.8_wp, 100.0_wp, 100.0_wp,                      & !parameter 117-121
914        20.0_wp, 20.0_wp, 0.0_wp, 1.0_wp, 1.0_wp, 4.5_wp,                      & !parameter 122-127
915        100000.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 3.0_wp, 0.2_wp                    & !parameter 128-133- end of type 7 (bridge)
916                                                                       /),     &
917                                                               (/134, 7/) )
918
919!
920!-- Type for surface temperatures at vertical walls. Is not necessary for horizontal walls.
921    TYPE t_surf_vertical
922       REAL(wp), DIMENSION(:), ALLOCATABLE         :: t
923    END TYPE t_surf_vertical
924!
925!-- Type for wall temperatures at vertical walls. Is not necessary for horizontal walls.
926    TYPE t_wall_vertical
927       REAL(wp), DIMENSION(:,:), ALLOCATABLE       :: t
928    END TYPE t_wall_vertical
929
930    TYPE surf_type_usm
931       REAL(wp), DIMENSION(:),   ALLOCATABLE ::  var_usm_1d !< 1D prognostic variable
932       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  var_usm_2d !< 2D prognostic variable
933    END TYPE surf_type_usm
934   
935#if defined( __nopointer )
936    TYPE(surf_type_usm), TARGET   ::  m_liq_usm_h,        & !< liquid water reservoir (m), horizontal surface elements
937                                      m_liq_usm_h_p         !< progn. liquid water reservoir (m), horizontal surface elements
938
939    TYPE(surf_type_usm), DIMENSION(0:3), TARGET   ::  &
940                                      m_liq_usm_v,        & !< liquid water reservoir (m), vertical surface elements
941                                      m_liq_usm_v_p         !< progn. liquid water reservoir (m), vertical surface elements
942#else
943    TYPE(surf_type_usm), POINTER  ::  m_liq_usm_h,        & !< liquid water reservoir (m), horizontal surface elements
944                                      m_liq_usm_h_p         !< progn. liquid water reservoir (m), horizontal surface elements
945
946    TYPE(surf_type_usm), TARGET   ::  m_liq_usm_h_1,      & !<
947                                      m_liq_usm_h_2         !<
948
949    TYPE(surf_type_usm), DIMENSION(:), POINTER  ::    &
950                                      m_liq_usm_v,        & !< liquid water reservoir (m), vertical surface elements
951                                      m_liq_usm_v_p         !< progn. liquid water reservoir (m), vertical surface elements
952
953    TYPE(surf_type_usm), DIMENSION(0:3), TARGET   ::  &
954                                      m_liq_usm_v_1,      & !<
955                                      m_liq_usm_v_2         !<
956#endif
957
958    TYPE(surf_type_usm), TARGET ::  tm_liq_usm_h_m      !< liquid water reservoir tendency (m), horizontal surface elements
959    TYPE(surf_type_usm), DIMENSION(0:3), TARGET ::  tm_liq_usm_v_m      !< liquid water reservoir tendency (m), vertical surface elements
960
961
962!-- arrays for time averages
963!-- Attention: the variable rad_net_av is also used in the 3d field variable in radiation_model_mod.f90. It may be better to rename it
964    REAL(wp), DIMENSION(:), ALLOCATABLE            ::  wghf_eb_av       !< average of wghf_eb
965    REAL(wp), DIMENSION(:), ALLOCATABLE            ::  wshf_eb_av       !< average of wshf_eb
966    REAL(wp), DIMENSION(:,:), ALLOCATABLE          ::  t_wall_av        !< Average of t_wall
967    REAL(wp), DIMENSION(:), ALLOCATABLE            ::  wghf_eb_green_av !< average of wghf_eb_green
968    REAL(wp), DIMENSION(:,:), ALLOCATABLE          ::  t_green_av       !< Average of t_green
969    REAL(wp), DIMENSION(:), ALLOCATABLE            ::  wghf_eb_window_av !< average of wghf_eb_window
970    REAL(wp), DIMENSION(:,:), ALLOCATABLE          ::  t_window_av      !< Average of t_window
971    REAL(wp), DIMENSION(:), ALLOCATABLE            ::  qsws_eb_av       !< average of qsws_eb
972    REAL(wp), DIMENSION(:), ALLOCATABLE            ::  qsws_veg_av   !< average of qsws_veg
973    REAL(wp), DIMENSION(:), ALLOCATABLE            ::  qsws_liq_av   !< average of qsws_liq
974    REAL(wp), DIMENSION(:,:), ALLOCATABLE          ::  swc_av        !< Average of swc
975   
976
977!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
978!-- anthropogenic heat sources
979!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
980    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE        ::  aheat             !< daily average of anthropogenic heat (W/m2)
981    REAL(wp), DIMENSION(:,:), ALLOCATABLE          ::  aheatprof         !< diurnal profiles of anthropogenic heat for particular layers
982    INTEGER(iwp)                                   ::  naheatlayers = 1  !< number of layers of anthropogenic heat
983
984!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
985!-- wall surface model
986!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
987!-- wall surface model constants
988    INTEGER(iwp), PARAMETER                        :: nzb_wall = 0       !< inner side of the wall model (to be switched)
989    INTEGER(iwp), PARAMETER                        :: nzt_wall = 3       !< outer side of the wall model (to be switched)
990    INTEGER(iwp), PARAMETER                        :: nzw = 4            !< number of wall layers (fixed for now)
991
992    REAL(wp), DIMENSION(nzb_wall:nzt_wall)         :: zwn_default = (/0.0242_wp, 0.0969_wp, 0.346_wp, 1.0_wp /)
993                                                                         !< normalized soil, wall and roof layer depths (m/m)
994!    REAL(wp), DIMENSION(nzb_wall:nzt_wall)         :: zwn_default = (/0.33_wp, 0.66_wp, 1.0_wp /)
995    REAL(wp), DIMENSION(nzb_wall:nzt_wall)         :: zwn_default_window = (/0.25_wp, 0.5_wp, 0.75_wp, 1.0_wp /)
996!    REAL(wp), DIMENSION(nzb_wall:nzt_wall)         :: zwn_default_window = (/0.33_wp, 0.66_wp, 1.0_wp /)
997!    REAL(wp), DIMENSION(nzb_wall:nzt_wall)         :: zwn_default_window = (/0.0242_wp, 0.0969_wp, 0.346_wp, 1.0_wp /)
998                                                                         !< normalized window layer depths (m/m)
999!    REAL(wp), DIMENSION(nzb_wall:nzt_wall)         :: zwn_default_green = (/0.0242_wp, 0.0969_wp, 0.346_wp, 1.0_wp /)
1000                                                                         !< normalized green layer depths (m/m)
1001    REAL(wp), DIMENSION(nzb_wall:nzt_wall)         :: zwn_default_green = (/0.25_wp, 0.5_wp, 0.75_wp, 1.0_wp /)
1002!    REAL(wp), DIMENSION(nzb_wall:nzt_wall)         :: zwn_default_green = (/0.33_wp, 0.66_wp, 1.0_wp /)
1003
1004
1005    REAL(wp)                                       :: wall_inner_temperature = 295.0_wp    !< temperature of the inner wall surface (~22 degrees C) (K)
1006    REAL(wp)                                       :: roof_inner_temperature = 295.0_wp    !< temperature of the inner roof surface (~22 degrees C) (K)
1007    REAL(wp)                                       :: soil_inner_temperature = 288.0_wp    !< temperature of the deep soil (~15 degrees C) (K)
1008    REAL(wp)                                       :: window_inner_temperature = 295.0_wp  !< temperature of the inner window surface (~22 degrees C) (K)
1009
1010    REAL(wp)                                       ::   m_total = 0.0_wp !< weighted total water content of the soil (m3/m3)
1011    INTEGER(iwp)                                   ::   soil_type
1012   
1013!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1014!-- surface and material model variables for walls, ground, roofs
1015!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1016    REAL(wp), DIMENSION(:), ALLOCATABLE            :: zwn                !< normalized wall layer depths (m)
1017    REAL(wp), DIMENSION(:), ALLOCATABLE            :: zwn_window         !< normalized window layer depths (m)
1018    REAL(wp), DIMENSION(:), ALLOCATABLE            :: zwn_green          !< normalized green layer depths (m)
1019
1020#if defined( __nopointer )
1021    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_wall_h           !< wall surface temperature (K) at horizontal walls
1022    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_wall_h_p         !< progn. wall surface temperature (K) at horizontal walls
1023    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_window_h    !< window surface temperature (K) at horizontal walls
1024    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_window_h_p  !< progn. window surface temperature (K) at horizontal walls
1025    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_h     !< green surface temperature (K) at horizontal walls
1026    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_h_p   !< progn. green surface temperature (K) at horizontal walls
1027    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_wall_v
1028    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_wall_v_p
1029    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_window_v
1030    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_window_v_p
1031    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_green_v
1032    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_green_v_p
1033#else
1034    REAL(wp), DIMENSION(:), POINTER                :: t_surf_wall_h
1035    REAL(wp), DIMENSION(:), POINTER                :: t_surf_wall_h_p 
1036    REAL(wp), DIMENSION(:), POINTER                :: t_surf_window_h
1037    REAL(wp), DIMENSION(:), POINTER                :: t_surf_window_h_p 
1038    REAL(wp), DIMENSION(:), POINTER                :: t_surf_green_h
1039    REAL(wp), DIMENSION(:), POINTER                :: t_surf_green_h_p 
1040
1041    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_wall_h_1
1042    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_wall_h_2
1043    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_window_h_1
1044    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_window_h_2
1045    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_h_1
1046    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_h_2
1047
1048    TYPE(t_surf_vertical), DIMENSION(:), POINTER ::  t_surf_wall_v
1049    TYPE(t_surf_vertical), DIMENSION(:), POINTER ::  t_surf_wall_v_p
1050    TYPE(t_surf_vertical), DIMENSION(:), POINTER ::  t_surf_window_v
1051    TYPE(t_surf_vertical), DIMENSION(:), POINTER ::  t_surf_window_v_p
1052    TYPE(t_surf_vertical), DIMENSION(:), POINTER ::  t_surf_green_v
1053    TYPE(t_surf_vertical), DIMENSION(:), POINTER ::  t_surf_green_v_p
1054
1055    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_wall_v_1
1056    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_wall_v_2
1057    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_window_v_1
1058    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_window_v_2
1059    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_green_v_1
1060    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_green_v_2
1061   
1062#endif
1063    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_wall_av          !< average of wall surface temperature (K)
1064    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_window_av   !< average of window surface temperature (K)
1065    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_av    !< average of green wall surface temperature (K)
1066
1067!-- Temporal tendencies for time stepping           
1068    REAL(wp), DIMENSION(:), ALLOCATABLE            :: tt_surface_wall_m       !< surface temperature tendency of wall (K)
1069    REAL(wp), DIMENSION(:), ALLOCATABLE            :: tt_surface_window_m !< surface temperature tendency of window (K)
1070    REAL(wp), DIMENSION(:), ALLOCATABLE            :: tt_surface_green_m !< surface temperature tendency of green wall (K)
1071
1072!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1073!-- Energy balance variables
1074!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1075!-- parameters of the land, roof and wall surfaces
1076
1077#if defined( __nopointer )
1078    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h             !< Wall temperature (K)
1079    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h_av          !< Average of t_wall
1080    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h_p           !< Prog. wall temperature (K)
1081    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_window_h           !< Window temperature (K)
1082    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_window_h_av        !< Average of t_window
1083    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_window_h_p         !< Prog. window temperature (K)
1084    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_green_h            !< Green temperature (K)
1085    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_green_h_av         !< Average of t_green
1086    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_green_h_p          !< Prog. green temperature (K)
1087    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: swc_h              !< soil water content green building layer
1088    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: swc_h_av              !< avg of soil water content green building layer
1089    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: swc_h_p              !< Prog. soil water content green building layer
1090    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: swc_sat_h          !< soil water content green building layer at saturation
1091    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: swc_res_h          !< soil water content green building layer residual
1092    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: rootfr_h           !< root fraction green green building layer
1093    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: wilt_h             !< wilting point green building layer
1094    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: fc_h               !< field capacity green building layer
1095
1096
1097    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v             !< Wall temperature (K)
1098    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v_av          !< Average of t_wall
1099    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v_p           !< Prog. wall temperature (K)
1100    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_window_v           !< Window temperature (K)
1101    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_window_v_av        !< Average of t_window
1102    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_window_v_p         !< Prog. window temperature (K)
1103    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v            !< Green temperature (K)
1104    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v_av         !< Average of t_green
1105    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v_p          !< Prog. green temperature (K)
1106    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: swc_v             !< Wall swc
1107    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: swc_v_av          !< Average of swc
1108    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: swc_v_p           !< Prog. swc
1109   
1110#else
1111    REAL(wp), DIMENSION(:,:), POINTER                :: t_wall_h, t_wall_h_p
1112    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h_av, t_wall_h_1, t_wall_h_2
1113    REAL(wp), DIMENSION(:,:), POINTER                :: t_window_h, t_window_h_p
1114    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_window_h_av, t_window_h_1, t_window_h_2
1115    REAL(wp), DIMENSION(:,:), POINTER                :: t_green_h, t_green_h_p
1116    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_green_h_av, t_green_h_1, t_green_h_2
1117    REAL(wp), DIMENSION(:,:), POINTER                :: swc_h, rootfr_h, wilt_h, fc_h, swc_sat_h, swc_h_p, swc_res_h
1118    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: swc_h_1, rootfr_h_1, &
1119                                                        wilt_h_1, fc_h_1, swc_sat_h_1, swc_h_2, swc_res_h_1
1120   
1121
1122    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: t_wall_v, t_wall_v_p
1123    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v_av, t_wall_v_1, t_wall_v_2
1124    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: t_window_v, t_window_v_p
1125    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_window_v_av, t_window_v_1, t_window_v_2
1126    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: t_green_v, t_green_v_p
1127    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v_av, t_green_v_1, t_green_v_2
1128    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: swc_v, swc_v_p
1129    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: swc_v_av, swc_v_1, swc_v_2
1130#endif
1131
1132!-- Wall temporal tendencies for time stepping
1133    REAL(wp), DIMENSION(:,:), ALLOCATABLE          :: tt_wall_m          !< t_wall prognostic array
1134    REAL(wp), DIMENSION(:,:), ALLOCATABLE          :: tt_window_m        !< t_window prognostic array
1135    REAL(wp), DIMENSION(:,:), ALLOCATABLE          :: tt_green_m         !< t_green prognostic array
1136
1137!-- Surface and material parameters classes (surface_type)
1138!-- albedo, emissivity, lambda_surf, roughness, thickness, volumetric heat capacity, thermal conductivity
1139    INTEGER(iwp)                                   :: n_surface_types      !< number of the wall type categories
1140    INTEGER(iwp), PARAMETER                        :: n_surface_params = 9 !< number of parameters for each type of the wall
1141    INTEGER(iwp), PARAMETER                        :: ialbedo  = 1         !< albedo of the surface
1142    INTEGER(iwp), PARAMETER                        :: iemiss   = 2         !< emissivity of the surface
1143    INTEGER(iwp), PARAMETER                        :: ilambdas = 3         !< heat conductivity lambda S between surface and material ( W m-2 K-1 )
1144    INTEGER(iwp), PARAMETER                        :: irough   = 4         !< roughness length z0 for movements
1145    INTEGER(iwp), PARAMETER                        :: iroughh  = 5         !< roughness length z0h for scalars (heat, humidity,...)
1146    INTEGER(iwp), PARAMETER                        :: icsurf   = 6         !< Surface skin layer heat capacity (J m-2 K-1 )
1147    INTEGER(iwp), PARAMETER                        :: ithick   = 7         !< thickness of the surface (wall, roof, land)  ( m )
1148    INTEGER(iwp), PARAMETER                        :: irhoC    = 8         !< volumetric heat capacity rho*C of the material ( J m-3 K-1 )
1149    INTEGER(iwp), PARAMETER                        :: ilambdah = 9         !< thermal conductivity lambda H of the wall (W m-1 K-1 )
1150    CHARACTER(12), DIMENSION(:), ALLOCATABLE       :: surface_type_names   !< names of wall types (used only for reports)
1151    INTEGER(iwp), DIMENSION(:), ALLOCATABLE        :: surface_type_codes   !< codes of wall types
1152    REAL(wp), DIMENSION(:,:), ALLOCATABLE          :: surface_params       !< parameters of wall types
1153
1154   
1155!-- interfaces of subroutines accessed from outside of this module
1156    INTERFACE usm_boundary_condition
1157       MODULE PROCEDURE usm_boundary_condition
1158    END INTERFACE usm_boundary_condition
1159
1160    INTERFACE usm_check_data_output
1161       MODULE PROCEDURE usm_check_data_output
1162    END INTERFACE usm_check_data_output
1163   
1164    INTERFACE usm_check_parameters
1165       MODULE PROCEDURE usm_check_parameters
1166    END INTERFACE usm_check_parameters
1167   
1168    INTERFACE usm_data_output_3d
1169       MODULE PROCEDURE usm_data_output_3d
1170    END INTERFACE usm_data_output_3d
1171   
1172    INTERFACE usm_define_netcdf_grid
1173       MODULE PROCEDURE usm_define_netcdf_grid
1174    END INTERFACE usm_define_netcdf_grid
1175
1176    INTERFACE usm_init_urban_surface
1177       MODULE PROCEDURE usm_init_urban_surface
1178    END INTERFACE usm_init_urban_surface
1179
1180    INTERFACE usm_material_heat_model
1181       MODULE PROCEDURE usm_material_heat_model
1182    END INTERFACE usm_material_heat_model
1183   
1184    INTERFACE usm_green_heat_model
1185       MODULE PROCEDURE usm_green_heat_model
1186    END INTERFACE usm_green_heat_model
1187   
1188    INTERFACE usm_parin
1189       MODULE PROCEDURE usm_parin
1190    END INTERFACE usm_parin
1191
1192    INTERFACE usm_rrd_local 
1193       MODULE PROCEDURE usm_rrd_local
1194    END INTERFACE usm_rrd_local
1195
1196    INTERFACE usm_surface_energy_balance
1197       MODULE PROCEDURE usm_surface_energy_balance
1198    END INTERFACE usm_surface_energy_balance
1199   
1200    INTERFACE usm_swap_timelevel
1201       MODULE PROCEDURE usm_swap_timelevel
1202    END INTERFACE usm_swap_timelevel
1203       
1204    INTERFACE usm_wrd_local
1205       MODULE PROCEDURE usm_wrd_local
1206    END INTERFACE usm_wrd_local
1207
1208    INTERFACE usm_allocate_surface
1209       MODULE PROCEDURE usm_allocate_surface
1210    END INTERFACE usm_allocate_surface
1211
1212    INTERFACE usm_average_3d_data
1213       MODULE PROCEDURE usm_average_3d_data
1214    END INTERFACE usm_average_3d_data
1215
1216   
1217    SAVE
1218
1219    PRIVATE 
1220   
1221!-- Public functions
1222    PUBLIC usm_boundary_condition, usm_check_parameters, usm_init_urban_surface,&
1223           usm_rrd_local,                                                      & 
1224           usm_surface_energy_balance, usm_material_heat_model,                &
1225           usm_swap_timelevel, usm_check_data_output, usm_average_3d_data,     &
1226           usm_data_output_3d, usm_define_netcdf_grid, usm_parin,              &
1227           usm_wrd_local, usm_allocate_surface
1228
1229!-- Public parameters, constants and initial values
1230    PUBLIC usm_anthropogenic_heat, usm_material_model, usm_wall_mod,           &
1231           usm_green_heat_model, building_pars,  &
1232           nzt_wall, t_wall_h, t_wall_v,         &
1233           t_window_h, t_window_v, building_type
1234
1235
1236
1237 CONTAINS
1238
1239!------------------------------------------------------------------------------!
1240! Description:
1241! ------------
1242!> This subroutine creates the necessary indices of the urban surfaces
1243!> and plant canopy and it allocates the needed arrays for USM
1244!------------------------------------------------------------------------------!
1245    SUBROUTINE usm_allocate_surface
1246   
1247        IMPLICIT NONE
1248       
1249        INTEGER(iwp) ::  l
1250
1251!
1252!--     Allocate radiation arrays which are part of the new data type.
1253!--     For horizontal surfaces.
1254        ALLOCATE( surf_usm_h%surfhf(1:surf_usm_h%ns)    )
1255        ALLOCATE( surf_usm_h%rad_net_l(1:surf_usm_h%ns) )
1256!
1257!--     For vertical surfaces
1258        DO  l = 0, 3
1259           ALLOCATE( surf_usm_v(l)%surfhf(1:surf_usm_v(l)%ns)    )
1260           ALLOCATE( surf_usm_v(l)%rad_net_l(1:surf_usm_v(l)%ns) )
1261        ENDDO
1262
1263!--     Wall surface model
1264!--     allocate arrays for wall surface model and define pointers
1265       
1266!--     allocate array of wall types and wall parameters
1267        ALLOCATE ( surf_usm_h%surface_types(1:surf_usm_h%ns)      )
1268        ALLOCATE ( surf_usm_h%building_type(1:surf_usm_h%ns)      )
1269        ALLOCATE ( surf_usm_h%building_type_name(1:surf_usm_h%ns) )
1270        surf_usm_h%building_type      = 0
1271        surf_usm_h%building_type_name = 'none'
1272        DO  l = 0, 3
1273           ALLOCATE( surf_usm_v(l)%surface_types(1:surf_usm_v(l)%ns) )
1274           ALLOCATE ( surf_usm_v(l)%building_type(1:surf_usm_v(l)%ns)      )
1275           ALLOCATE ( surf_usm_v(l)%building_type_name(1:surf_usm_v(l)%ns) )
1276           surf_usm_v(l)%building_type      = 0
1277           surf_usm_v(l)%building_type_name = 'none'
1278        ENDDO
1279!
1280!--     Allocate albedo_type and albedo. Each surface element
1281!--     has 3 values, 0: wall fraction, 1: green fraction, 2: window fraction.
1282        ALLOCATE( surf_usm_h%albedo_type(0:2,1:surf_usm_h%ns) )
1283        ALLOCATE( surf_usm_h%albedo(0:2,1:surf_usm_h%ns)      )
1284        surf_usm_h%albedo_type = albedo_type
1285        DO  l = 0, 3
1286           ALLOCATE( surf_usm_v(l)%albedo_type(0:2,1:surf_usm_v(l)%ns) )
1287           ALLOCATE( surf_usm_v(l)%albedo(0:2,1:surf_usm_v(l)%ns)      )
1288           surf_usm_v(l)%albedo_type = albedo_type
1289        ENDDO       
1290
1291
1292!
1293!--     Allocate indoor target temperature for summer and winter
1294        ALLOCATE( surf_usm_h%target_temp_summer(1:surf_usm_h%ns) )
1295        ALLOCATE( surf_usm_h%target_temp_winter(1:surf_usm_h%ns) )
1296        DO  l = 0, 3
1297           ALLOCATE( surf_usm_v(l)%target_temp_summer(1:surf_usm_v(l)%ns) )
1298           ALLOCATE( surf_usm_v(l)%target_temp_winter(1:surf_usm_v(l)%ns) )
1299        ENDDO   
1300!
1301!--     Allocate flag indicating ground floor level surface elements
1302        ALLOCATE ( surf_usm_h%ground_level(1:surf_usm_h%ns) ) 
1303        DO  l = 0, 3
1304           ALLOCATE( surf_usm_v(l)%ground_level(1:surf_usm_v(l)%ns) )
1305        ENDDO   
1306!
1307!--      Allocate arrays for relative surface fraction.
1308!--      0 - wall fraction, 1 - green fraction, 2 - window fraction
1309         ALLOCATE( surf_usm_h%frac(0:2,1:surf_usm_h%ns) )
1310         surf_usm_h%frac = 0.0_wp
1311         DO  l = 0, 3
1312            ALLOCATE( surf_usm_v(l)%frac(0:2,1:surf_usm_v(l)%ns) )
1313            surf_usm_v(l)%frac = 0.0_wp
1314         ENDDO
1315       
1316!--     wall and roof surface parameters. First for horizontal surfaces
1317        ALLOCATE ( surf_usm_h%isroof_surf(1:surf_usm_h%ns)        )
1318        ALLOCATE ( surf_usm_h%lambda_surf(1:surf_usm_h%ns)        )
1319        ALLOCATE ( surf_usm_h%lambda_surf_window(1:surf_usm_h%ns) )
1320        ALLOCATE ( surf_usm_h%lambda_surf_green(1:surf_usm_h%ns)  )
1321        ALLOCATE ( surf_usm_h%c_surface(1:surf_usm_h%ns)          )
1322        ALLOCATE ( surf_usm_h%c_surface_window(1:surf_usm_h%ns)   )
1323        ALLOCATE ( surf_usm_h%c_surface_green(1:surf_usm_h%ns)    )
1324        ALLOCATE ( surf_usm_h%transmissivity(1:surf_usm_h%ns)     )
1325        ALLOCATE ( surf_usm_h%lai(1:surf_usm_h%ns)                )
1326        ALLOCATE ( surf_usm_h%emissivity(0:2,1:surf_usm_h%ns)     )
1327        ALLOCATE ( surf_usm_h%r_a(1:surf_usm_h%ns)                )
1328        ALLOCATE ( surf_usm_h%r_a_green(1:surf_usm_h%ns)          )
1329        ALLOCATE ( surf_usm_h%r_a_window(1:surf_usm_h%ns)         )
1330        ALLOCATE ( surf_usm_h%green_type_roof(1:surf_usm_h%ns)    )
1331        ALLOCATE ( surf_usm_h%r_s(1:surf_usm_h%ns)                )
1332       
1333!
1334!--     For vertical surfaces.
1335        DO  l = 0, 3
1336           ALLOCATE ( surf_usm_v(l)%lambda_surf(1:surf_usm_v(l)%ns)     )
1337           ALLOCATE ( surf_usm_v(l)%c_surface(1:surf_usm_v(l)%ns)       )
1338           ALLOCATE ( surf_usm_v(l)%lambda_surf_window(1:surf_usm_v(l)%ns) )
1339           ALLOCATE ( surf_usm_v(l)%c_surface_window(1:surf_usm_v(l)%ns)   )
1340           ALLOCATE ( surf_usm_v(l)%lambda_surf_green(1:surf_usm_v(l)%ns)  )
1341           ALLOCATE ( surf_usm_v(l)%c_surface_green(1:surf_usm_v(l)%ns)    )
1342           ALLOCATE ( surf_usm_v(l)%transmissivity(1:surf_usm_v(l)%ns)  )
1343           ALLOCATE ( surf_usm_v(l)%lai(1:surf_usm_v(l)%ns)             )
1344           ALLOCATE ( surf_usm_v(l)%emissivity(0:2,1:surf_usm_v(l)%ns)  )
1345           ALLOCATE ( surf_usm_v(l)%r_a(1:surf_usm_v(l)%ns)             )
1346           ALLOCATE ( surf_usm_v(l)%r_a_green(1:surf_usm_v(l)%ns)       )
1347           ALLOCATE ( surf_usm_v(l)%r_a_window(1:surf_usm_v(l)%ns)      )           
1348           ALLOCATE ( surf_usm_v(l)%r_s(1:surf_usm_v(l)%ns)                )
1349        ENDDO
1350
1351!       
1352!--     allocate wall and roof material parameters. First for horizontal surfaces
1353        ALLOCATE ( surf_usm_h%thickness_wall(1:surf_usm_h%ns)               )
1354        ALLOCATE ( surf_usm_h%thickness_window(1:surf_usm_h%ns)                  )
1355        ALLOCATE ( surf_usm_h%thickness_green(1:surf_usm_h%ns)                   )
1356        ALLOCATE ( surf_usm_h%lambda_h(nzb_wall:nzt_wall,1:surf_usm_h%ns)   )
1357        ALLOCATE ( surf_usm_h%rho_c_wall(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1358        ALLOCATE ( surf_usm_h%lambda_h_window(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1359        ALLOCATE ( surf_usm_h%rho_c_window(nzb_wall:nzt_wall,1:surf_usm_h%ns)    )
1360        ALLOCATE ( surf_usm_h%lambda_h_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)  )
1361        ALLOCATE ( surf_usm_h%rho_c_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)     )
1362
1363        ALLOCATE ( surf_usm_h%rho_c_total_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)     )
1364        ALLOCATE ( surf_usm_h%n_vg_green(1:surf_usm_h%ns)     )
1365        ALLOCATE ( surf_usm_h%alpha_vg_green(1:surf_usm_h%ns)     )
1366        ALLOCATE ( surf_usm_h%l_vg_green(1:surf_usm_h%ns)     )
1367        ALLOCATE ( surf_usm_h%gamma_w_green_sat(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)     )
1368        ALLOCATE ( surf_usm_h%lambda_w_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)     )
1369        ALLOCATE ( surf_usm_h%gamma_w_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)     )
1370        ALLOCATE ( surf_usm_h%tswc_h_m(nzb_wall:nzt_wall,1:surf_usm_h%ns)     )
1371
1372!
1373!--     For vertical surfaces.
1374        DO  l = 0, 3
1375           ALLOCATE ( surf_usm_v(l)%thickness_wall(1:surf_usm_v(l)%ns)               )
1376           ALLOCATE ( surf_usm_v(l)%thickness_window(1:surf_usm_v(l)%ns)                  )
1377           ALLOCATE ( surf_usm_v(l)%thickness_green(1:surf_usm_v(l)%ns)                   )
1378           ALLOCATE ( surf_usm_v(l)%lambda_h(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)   )
1379           ALLOCATE ( surf_usm_v(l)%rho_c_wall(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1380           ALLOCATE ( surf_usm_v(l)%lambda_h_window(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1381           ALLOCATE ( surf_usm_v(l)%rho_c_window(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)    )
1382           ALLOCATE ( surf_usm_v(l)%lambda_h_green(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)  )
1383           ALLOCATE ( surf_usm_v(l)%rho_c_green(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)     )
1384        ENDDO
1385
1386!
1387!--     allocate green wall and roof vegetation and soil parameters. First horizontal surfaces
1388        ALLOCATE ( surf_usm_h%g_d(1:surf_usm_h%ns)              )
1389        ALLOCATE ( surf_usm_h%c_liq(1:surf_usm_h%ns)            )
1390        ALLOCATE ( surf_usm_h%qsws_liq(1:surf_usm_h%ns)         )
1391        ALLOCATE ( surf_usm_h%qsws_veg(1:surf_usm_h%ns)         )
1392        ALLOCATE ( surf_usm_h%r_canopy(1:surf_usm_h%ns)         )
1393        ALLOCATE ( surf_usm_h%r_canopy_min(1:surf_usm_h%ns)     )
1394        ALLOCATE ( surf_usm_h%qsws_eb(1:surf_usm_h%ns)          )
1395        ALLOCATE ( surf_usm_h%pt_10cm(1:surf_usm_h%ns)          ) 
1396        ALLOCATE ( surf_usm_h%pt_2m(1:surf_usm_h%ns)            ) 
1397
1398!
1399!--     For vertical surfaces.
1400        DO  l = 0, 3
1401          ALLOCATE ( surf_usm_v(l)%g_d(1:surf_usm_v(l)%ns)              )
1402          ALLOCATE ( surf_usm_v(l)%c_liq(1:surf_usm_v(l)%ns)            )
1403          ALLOCATE ( surf_usm_v(l)%qsws_liq(1:surf_usm_v(l)%ns)         )
1404          ALLOCATE ( surf_usm_v(l)%qsws_veg(1:surf_usm_v(l)%ns)         )
1405          ALLOCATE ( surf_usm_v(l)%qsws_eb(1:surf_usm_v(l)%ns)          )
1406          ALLOCATE ( surf_usm_v(l)%r_canopy(1:surf_usm_v(l)%ns)         )
1407          ALLOCATE ( surf_usm_v(l)%r_canopy_min(1:surf_usm_v(l)%ns)     )
1408          ALLOCATE ( surf_usm_v(l)%pt_10cm(1:surf_usm_v(l)%ns)     )
1409        ENDDO
1410       
1411!--     allocate wall and roof layers sizes. For horizontal surfaces.
1412        ALLOCATE ( zwn(nzb_wall:nzt_wall) )
1413        ALLOCATE ( surf_usm_h%dz_wall(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)     )
1414        ALLOCATE ( zwn_window(nzb_wall:nzt_wall) )
1415        ALLOCATE ( surf_usm_h%dz_window(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)     )
1416        ALLOCATE ( zwn_green(nzb_wall:nzt_wall) )
1417        ALLOCATE ( surf_usm_h%dz_green(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)      )
1418        ALLOCATE ( surf_usm_h%ddz_wall(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)    )
1419        ALLOCATE ( surf_usm_h%dz_wall_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)  )
1420        ALLOCATE ( surf_usm_h%ddz_wall_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1421        ALLOCATE ( surf_usm_h%zw(nzb_wall:nzt_wall,1:surf_usm_h%ns)            )
1422        ALLOCATE ( surf_usm_h%ddz_window(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)    )
1423        ALLOCATE ( surf_usm_h%dz_window_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)  )
1424        ALLOCATE ( surf_usm_h%ddz_window_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1425        ALLOCATE ( surf_usm_h%zw_window(nzb_wall:nzt_wall,1:surf_usm_h%ns)       )
1426        ALLOCATE ( surf_usm_h%ddz_green(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)     )
1427        ALLOCATE ( surf_usm_h%dz_green_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)   )
1428        ALLOCATE ( surf_usm_h%ddz_green_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)  )
1429        ALLOCATE ( surf_usm_h%zw_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)        )
1430!
1431!--     For vertical surfaces.
1432        DO  l = 0, 3
1433           ALLOCATE ( surf_usm_v(l)%dz_wall(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)     )
1434           ALLOCATE ( surf_usm_v(l)%dz_window(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)     )
1435           ALLOCATE ( surf_usm_v(l)%dz_green(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)      )
1436           ALLOCATE ( surf_usm_v(l)%ddz_wall(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)    )
1437           ALLOCATE ( surf_usm_v(l)%dz_wall_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)  )
1438           ALLOCATE ( surf_usm_v(l)%ddz_wall_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1439           ALLOCATE ( surf_usm_v(l)%zw(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)            )
1440           ALLOCATE ( surf_usm_v(l)%ddz_window(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)    )
1441           ALLOCATE ( surf_usm_v(l)%dz_window_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)  )
1442           ALLOCATE ( surf_usm_v(l)%ddz_window_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1443           ALLOCATE ( surf_usm_v(l)%zw_window(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)       )
1444           ALLOCATE ( surf_usm_v(l)%ddz_green(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)     )
1445           ALLOCATE ( surf_usm_v(l)%dz_green_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)   )
1446           ALLOCATE ( surf_usm_v(l)%ddz_green_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)  )
1447           ALLOCATE ( surf_usm_v(l)%zw_green(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)        )
1448        ENDDO
1449
1450!--     allocate wall and roof temperature arrays, for horizontal walls
1451#if defined( __nopointer )
1452        IF ( .NOT. ALLOCATED( t_surf_wall_h ) )                                     &
1453           ALLOCATE ( t_surf_wall_h(1:surf_usm_h%ns) )
1454        IF ( .NOT. ALLOCATED( t_surf_wall_h_p ) )                                   &
1455           ALLOCATE ( t_surf_wall_h_p(1:surf_usm_h%ns) )
1456        IF ( .NOT. ALLOCATED( t_wall_h ) )                                     &           
1457           ALLOCATE ( t_wall_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1458        IF ( .NOT. ALLOCATED( t_wall_h_p ) )                                   &           
1459           ALLOCATE ( t_wall_h_p(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1460        IF ( .NOT. ALLOCATED( t_surf_window_h ) )                              &
1461           ALLOCATE ( t_surf_window_h(1:surf_usm_h%ns) )
1462        IF ( .NOT. ALLOCATED( t_surf_window_h_p ) )                            &
1463           ALLOCATE ( t_surf_window_h_p(1:surf_usm_h%ns) )
1464        IF ( .NOT. ALLOCATED( t_window_h ) )                                   &           
1465           ALLOCATE ( t_window_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1466        IF ( .NOT. ALLOCATED( t_window_h_p ) )                                 &           
1467           ALLOCATE ( t_window_h_p(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1468        IF ( .NOT. ALLOCATED( t_surf_green_h ) )                               &
1469           ALLOCATE ( t_surf_green_h(1:surf_usm_h%ns) )
1470        IF ( .NOT. ALLOCATED( t_surf_green_h_p ) )                             &
1471           ALLOCATE ( t_surf_green_h_p(1:surf_usm_h%ns) )           
1472        IF ( .NOT. ALLOCATED( t_green_h ) )                                    &           
1473           ALLOCATE ( t_green_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1474        IF ( .NOT. ALLOCATED( t_green_h_p ) )                                  &           
1475           ALLOCATE ( t_green_h_p(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1476        IF ( .NOT. ALLOCATED( swc_h ) )                                    &           
1477           ALLOCATE ( swc_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
1478        IF ( .NOT. ALLOCATED( swc_sat_h ) )                                    &           
1479           ALLOCATE ( swc_sat_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
1480        IF ( .NOT. ALLOCATED( swc_res_h ) )                                    &           
1481           ALLOCATE ( swc_res_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
1482        IF ( .NOT. ALLOCATED( rootfr_h ) )                                    &           
1483           ALLOCATE ( rootfr_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
1484        IF ( .NOT. ALLOCATED( wilt_h ) )                                    &           
1485           ALLOCATE ( wilt_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
1486        IF ( .NOT. ALLOCATED( fc_h ) )                                    &           
1487           ALLOCATE ( fc_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1488
1489       IF ( .NOT. ALLOCATED( m_liq_usm_h%var_usm_1d ) )                            &
1490          ALLOCATE ( m_liq_usm_h%var_usm_1d(1:surf_usm_h%ns) )
1491
1492!--    Horizontal surfaces
1493       ALLOCATE ( m_liq_usm_h_p%var_usm_1d(1:surf_usm_h%ns)                      )
1494!
1495!--    Vertical surfaces
1496       DO  l = 0, 3
1497          ALLOCATE ( m_liq_usm_v_p(l)%var_usm_1d(1:surf_usm_v(l)%ns)                      )
1498       ENDDO
1499         
1500#else
1501!
1502!--     Allocate if required. Note, in case of restarts, some of these arrays
1503!--     might be already allocated.
1504        IF ( .NOT. ALLOCATED( t_surf_wall_h_1 ) )                                   &
1505           ALLOCATE ( t_surf_wall_h_1(1:surf_usm_h%ns) )
1506        IF ( .NOT. ALLOCATED( t_surf_wall_h_2 ) )                                   &
1507           ALLOCATE ( t_surf_wall_h_2(1:surf_usm_h%ns) )
1508        IF ( .NOT. ALLOCATED( t_wall_h_1 ) )                                   &           
1509           ALLOCATE ( t_wall_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1510        IF ( .NOT. ALLOCATED( t_wall_h_2 ) )                                   &           
1511           ALLOCATE ( t_wall_h_2(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )         
1512        IF ( .NOT. ALLOCATED( t_surf_window_h_1 ) )                            &
1513           ALLOCATE ( t_surf_window_h_1(1:surf_usm_h%ns) )
1514        IF ( .NOT. ALLOCATED( t_surf_window_h_2 ) )                            &
1515           ALLOCATE ( t_surf_window_h_2(1:surf_usm_h%ns) )
1516        IF ( .NOT. ALLOCATED( t_window_h_1 ) )                                 &           
1517           ALLOCATE ( t_window_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1518        IF ( .NOT. ALLOCATED( t_window_h_2 ) )                                 &           
1519           ALLOCATE ( t_window_h_2(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )         
1520        IF ( .NOT. ALLOCATED( t_surf_green_h_1 ) )                             &
1521           ALLOCATE ( t_surf_green_h_1(1:surf_usm_h%ns) )
1522        IF ( .NOT. ALLOCATED( t_surf_green_h_2 ) )                             &
1523           ALLOCATE ( t_surf_green_h_2(1:surf_usm_h%ns) )
1524        IF ( .NOT. ALLOCATED( t_green_h_1 ) )                                  &           
1525           ALLOCATE ( t_green_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1526        IF ( .NOT. ALLOCATED( t_green_h_2 ) )                                  &           
1527           ALLOCATE ( t_green_h_2(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )         
1528        IF ( .NOT. ALLOCATED( swc_h_1 ) )                                  &           
1529           ALLOCATE ( swc_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1530        IF ( .NOT. ALLOCATED( swc_sat_h_1 ) )                                  &           
1531           ALLOCATE ( swc_sat_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1532        IF ( .NOT. ALLOCATED( swc_res_h_1 ) )                                  &           
1533           ALLOCATE ( swc_res_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1534        IF ( .NOT. ALLOCATED( swc_h_2 ) )                                  &           
1535           ALLOCATE ( swc_h_2(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
1536        IF ( .NOT. ALLOCATED( rootfr_h_1 ) )                                  &           
1537           ALLOCATE ( rootfr_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1538        IF ( .NOT. ALLOCATED( wilt_h_1 ) )                                  &           
1539           ALLOCATE ( wilt_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1540        IF ( .NOT. ALLOCATED( fc_h_1 ) )                                  &           
1541           ALLOCATE ( fc_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1542
1543        IF ( .NOT. ALLOCATED( m_liq_usm_h_1%var_usm_1d ) )                         &
1544           ALLOCATE ( m_liq_usm_h_1%var_usm_1d(1:surf_usm_h%ns) )
1545        IF ( .NOT. ALLOCATED( m_liq_usm_h_2%var_usm_1d ) )                         &
1546           ALLOCATE ( m_liq_usm_h_2%var_usm_1d(1:surf_usm_h%ns) )
1547           
1548!           
1549!--     initial assignment of the pointers
1550        t_wall_h    => t_wall_h_1;    t_wall_h_p    => t_wall_h_2
1551        t_window_h    => t_window_h_1;    t_window_h_p    => t_window_h_2
1552        t_green_h    => t_green_h_1;    t_green_h_p    => t_green_h_2
1553        t_surf_wall_h => t_surf_wall_h_1; t_surf_wall_h_p => t_surf_wall_h_2           
1554        t_surf_window_h => t_surf_window_h_1; t_surf_window_h_p => t_surf_window_h_2 
1555        t_surf_green_h => t_surf_green_h_1; t_surf_green_h_p => t_surf_green_h_2           
1556        m_liq_usm_h     => m_liq_usm_h_1;     m_liq_usm_h_p     => m_liq_usm_h_2
1557        swc_h       => swc_h_1; swc_h_p     => swc_h_2
1558        swc_sat_h    => swc_sat_h_1
1559        swc_res_h    => swc_res_h_1
1560        rootfr_h       => rootfr_h_1
1561        wilt_h       => wilt_h_1
1562        fc_h       => fc_h_1
1563 
1564#endif
1565
1566!--     allocate wall and roof temperature arrays, for vertical walls if required
1567#if defined( __nopointer )
1568        DO  l = 0, 3
1569           IF ( .NOT. ALLOCATED( t_surf_wall_v(l)%t ) )                             &
1570              ALLOCATE ( t_surf_wall_v(l)%t(1:surf_usm_v(l)%ns) )
1571           IF ( .NOT. ALLOCATED( t_surf_wall_v_p(l)%t ) )                           &
1572              ALLOCATE ( t_surf_wall_v_p(l)%t(1:surf_usm_v(l)%ns) )
1573           IF ( .NOT. ALLOCATED( t_wall_v(l)%t ) )                             &
1574              ALLOCATE ( t_wall_v(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
1575           IF ( .NOT. ALLOCATED( t_wall_v_p(l)%t ) )                           &                 
1576              ALLOCATE ( t_wall_v_p(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
1577           IF ( .NOT. ALLOCATED( t_surf_window_v(l)%t ) )                      &
1578              ALLOCATE ( t_surf_window_v(l)%t(1:surf_usm_v(l)%ns) )
1579           IF ( .NOT. ALLOCATED( t_surf_window_v_p(l)%t ) )                    &
1580              ALLOCATE ( t_surf_window_v_p(l)%t(1:surf_usm_v(l)%ns) )
1581           IF ( .NOT. ALLOCATED( t_window_v(l)%t ) )                           &
1582              ALLOCATE ( t_window_v(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
1583           IF ( .NOT. ALLOCATED( t_window_v_p(l)%t ) )                         &                 
1584              ALLOCATE ( t_window_v_p(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
1585           IF ( .NOT. ALLOCATED( t_green_v(l)%t ) )                            &
1586              ALLOCATE ( t_green_v(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
1587           IF ( .NOT. ALLOCATED( t_green_v_p(l)%t ) )                          &                 
1588              ALLOCATE ( t_green_v_p(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
1589           IF ( .NOT. ALLOCATED( t_surf_green_v(l)%t ) )                       &
1590              ALLOCATE ( t_surf_green_v(l)%t(1:surf_usm_v(l)%ns) )
1591           IF ( .NOT. ALLOCATED( t_surf_green_v_p(l)%t ) )                     &
1592              ALLOCATE ( t_surf_green_v_p(l)%t(1:surf_usm_v(l)%ns) )
1593           IF ( .NOT. ALLOCATED( m_liq_usm_v(l)%var_usm_1d ) )                 &
1594             ALLOCATE ( m_liq_usm_v(l)%var_usm_1d(1:surf_usm_v(l)%ns) )
1595           IF ( .NOT. ALLOCATED( swc_v(l)%t ) )                             &
1596              ALLOCATE ( swc_v(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
1597           IF ( .NOT. ALLOCATED( swc_v_p(l)%t ) )                           &                 
1598              ALLOCATE ( swc_v_p(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
1599        ENDDO
1600#else
1601!
1602!--     Allocate if required. Note, in case of restarts, some of these arrays
1603!--     might be already allocated.
1604        DO  l = 0, 3
1605           IF ( .NOT. ALLOCATED( t_surf_wall_v_1(l)%t ) )                           &
1606              ALLOCATE ( t_surf_wall_v_1(l)%t(1:surf_usm_v(l)%ns) )
1607           IF ( .NOT. ALLOCATED( t_surf_wall_v_2(l)%t ) )                           &
1608              ALLOCATE ( t_surf_wall_v_2(l)%t(1:surf_usm_v(l)%ns) )
1609           IF ( .NOT. ALLOCATED( t_wall_v_1(l)%t ) )                           &           
1610              ALLOCATE ( t_wall_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1611           IF ( .NOT. ALLOCATED( t_wall_v_2(l)%t ) )                           &           
1612              ALLOCATE ( t_wall_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1613           IF ( .NOT. ALLOCATED( t_surf_window_v_1(l)%t ) )                    &
1614              ALLOCATE ( t_surf_window_v_1(l)%t(1:surf_usm_v(l)%ns) )
1615           IF ( .NOT. ALLOCATED( t_surf_window_v_2(l)%t ) )                    &
1616              ALLOCATE ( t_surf_window_v_2(l)%t(1:surf_usm_v(l)%ns) )
1617           IF ( .NOT. ALLOCATED( t_window_v_1(l)%t ) )                         &           
1618              ALLOCATE ( t_window_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1619           IF ( .NOT. ALLOCATED( t_window_v_2(l)%t ) )                         &           
1620              ALLOCATE ( t_window_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1621           IF ( .NOT. ALLOCATED( t_surf_green_v_1(l)%t ) )                     &
1622              ALLOCATE ( t_surf_green_v_1(l)%t(1:surf_usm_v(l)%ns) )
1623           IF ( .NOT. ALLOCATED( t_surf_green_v_2(l)%t ) )                     &
1624              ALLOCATE ( t_surf_green_v_2(l)%t(1:surf_usm_v(l)%ns) )
1625           IF ( .NOT. ALLOCATED( t_green_v_1(l)%t ) )                          &           
1626              ALLOCATE ( t_green_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1627           IF ( .NOT. ALLOCATED( t_green_v_2(l)%t ) )                          &           
1628              ALLOCATE ( t_green_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1629           IF ( .NOT. ALLOCATED( m_liq_usm_v_1(l)%var_usm_1d ) )              &
1630              ALLOCATE ( m_liq_usm_v_1(l)%var_usm_1d(1:surf_usm_v(l)%ns) )
1631           IF ( .NOT. ALLOCATED( m_liq_usm_v_2(l)%var_usm_1d ) )              &
1632              ALLOCATE ( m_liq_usm_v_2(l)%var_usm_1d(1:surf_usm_v(l)%ns) )
1633           IF ( .NOT. ALLOCATED( swc_v_1(l)%t ) )                           &           
1634              ALLOCATE ( swc_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1635           IF ( .NOT. ALLOCATED( swc_v_2(l)%t ) )                           &           
1636              ALLOCATE ( swc_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1637        ENDDO
1638!
1639!--     initial assignment of the pointers
1640        t_wall_v    => t_wall_v_1;    t_wall_v_p    => t_wall_v_2
1641        t_surf_wall_v => t_surf_wall_v_1; t_surf_wall_v_p => t_surf_wall_v_2
1642        t_window_v    => t_window_v_1;    t_window_v_p    => t_window_v_2
1643        t_green_v    => t_green_v_1;    t_green_v_p    => t_green_v_2
1644        t_surf_window_v => t_surf_window_v_1; t_surf_window_v_p => t_surf_window_v_2
1645        t_surf_green_v => t_surf_green_v_1; t_surf_green_v_p => t_surf_green_v_2
1646        m_liq_usm_v     => m_liq_usm_v_1;     m_liq_usm_v_p     => m_liq_usm_v_2
1647        swc_v    => swc_v_1;    swc_v_p    => swc_v_2
1648
1649#endif
1650!
1651!--     Allocate intermediate timestep arrays. For horizontal surfaces.
1652        ALLOCATE ( surf_usm_h%tt_surface_wall_m(1:surf_usm_h%ns)                  )
1653        ALLOCATE ( surf_usm_h%tt_wall_m(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
1654        ALLOCATE ( surf_usm_h%tt_surface_window_m(1:surf_usm_h%ns)             )
1655        ALLOCATE ( surf_usm_h%tt_window_m(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
1656        ALLOCATE ( surf_usm_h%tt_green_m(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)  )
1657        ALLOCATE ( surf_usm_h%tt_surface_green_m(1:surf_usm_h%ns)              )
1658
1659!
1660!--    Allocate intermediate timestep arrays
1661!--    Horizontal surfaces
1662       ALLOCATE ( tm_liq_usm_h_m%var_usm_1d(1:surf_usm_h%ns)                   )
1663!
1664!--    Horizontal surfaces
1665       DO  l = 0, 3
1666          ALLOCATE ( tm_liq_usm_v_m(l)%var_usm_1d(1:surf_usm_v(l)%ns)          )
1667       ENDDO 
1668       
1669!
1670!--     Set inital values for prognostic quantities
1671        IF ( ALLOCATED( surf_usm_h%tt_surface_wall_m ) )  surf_usm_h%tt_surface_wall_m = 0.0_wp
1672        IF ( ALLOCATED( surf_usm_h%tt_wall_m    ) )  surf_usm_h%tt_wall_m    = 0.0_wp
1673        IF ( ALLOCATED( surf_usm_h%tt_surface_window_m ) )  surf_usm_h%tt_surface_window_m = 0.0_wp
1674        IF ( ALLOCATED( surf_usm_h%tt_window_m    )      )  surf_usm_h%tt_window_m         = 0.0_wp
1675        IF ( ALLOCATED( surf_usm_h%tt_green_m    )       )  surf_usm_h%tt_green_m          = 0.0_wp
1676        IF ( ALLOCATED( surf_usm_h%tt_surface_green_m )  )  surf_usm_h%tt_surface_green_m  = 0.0_wp
1677!
1678!--     Now, for vertical surfaces
1679        DO  l = 0, 3
1680           ALLOCATE ( surf_usm_v(l)%tt_surface_wall_m(1:surf_usm_v(l)%ns)                  )
1681           ALLOCATE ( surf_usm_v(l)%tt_wall_m(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
1682           IF ( ALLOCATED( surf_usm_v(l)%tt_surface_wall_m ) )  surf_usm_v(l)%tt_surface_wall_m = 0.0_wp
1683           IF ( ALLOCATED( surf_usm_v(l)%tt_wall_m    ) )  surf_usm_v(l)%tt_wall_m    = 0.0_wp
1684           ALLOCATE ( surf_usm_v(l)%tt_surface_window_m(1:surf_usm_v(l)%ns)             )
1685           ALLOCATE ( surf_usm_v(l)%tt_window_m(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
1686           IF ( ALLOCATED( surf_usm_v(l)%tt_surface_window_m ) )  surf_usm_v(l)%tt_surface_window_m = 0.0_wp
1687           IF ( ALLOCATED( surf_usm_v(l)%tt_window_m  ) )  surf_usm_v(l)%tt_window_m    = 0.0_wp
1688           ALLOCATE ( surf_usm_v(l)%tt_surface_green_m(1:surf_usm_v(l)%ns)              )
1689           IF ( ALLOCATED( surf_usm_v(l)%tt_surface_green_m ) )  surf_usm_v(l)%tt_surface_green_m = 0.0_wp
1690           ALLOCATE ( surf_usm_v(l)%tt_green_m(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)  )
1691           IF ( ALLOCATED( surf_usm_v(l)%tt_green_m   ) )  surf_usm_v(l)%tt_green_m    = 0.0_wp
1692        ENDDO
1693
1694!--     allocate wall heat flux output array and set initial values. For horizontal surfaces
1695!         ALLOCATE ( surf_usm_h%wshf(1:surf_usm_h%ns)    )  !can be removed
1696        ALLOCATE ( surf_usm_h%wshf_eb(1:surf_usm_h%ns) )
1697        ALLOCATE ( surf_usm_h%wghf_eb(1:surf_usm_h%ns) )
1698        ALLOCATE ( surf_usm_h%wghf_eb_window(1:surf_usm_h%ns) )
1699        ALLOCATE ( surf_usm_h%wghf_eb_green(1:surf_usm_h%ns) )
1700        ALLOCATE ( surf_usm_h%iwghf_eb(1:surf_usm_h%ns) )
1701        ALLOCATE ( surf_usm_h%iwghf_eb_window(1:surf_usm_h%ns) )
1702        IF ( ALLOCATED( surf_usm_h%wshf    ) )  surf_usm_h%wshf    = 0.0_wp
1703        IF ( ALLOCATED( surf_usm_h%wshf_eb ) )  surf_usm_h%wshf_eb = 0.0_wp
1704        IF ( ALLOCATED( surf_usm_h%wghf_eb ) )  surf_usm_h%wghf_eb = 0.0_wp
1705        IF ( ALLOCATED( surf_usm_h%wghf_eb_window ) )  surf_usm_h%wghf_eb_window = 0.0_wp
1706        IF ( ALLOCATED( surf_usm_h%wghf_eb_green ) )  surf_usm_h%wghf_eb_green = 0.0_wp
1707        IF ( ALLOCATED( surf_usm_h%iwghf_eb ) )  surf_usm_h%iwghf_eb = 0.0_wp
1708        IF ( ALLOCATED( surf_usm_h%iwghf_eb_window ) )  surf_usm_h%iwghf_eb_window = 0.0_wp
1709!
1710!--     Now, for vertical surfaces
1711        DO  l = 0, 3
1712!            ALLOCATE ( surf_usm_v(l)%wshf(1:surf_usm_v(l)%ns)    )    ! can be removed
1713           ALLOCATE ( surf_usm_v(l)%wshf_eb(1:surf_usm_v(l)%ns) )
1714           ALLOCATE ( surf_usm_v(l)%wghf_eb(1:surf_usm_v(l)%ns) )
1715           ALLOCATE ( surf_usm_v(l)%wghf_eb_window(1:surf_usm_v(l)%ns) )
1716           ALLOCATE ( surf_usm_v(l)%wghf_eb_green(1:surf_usm_v(l)%ns) )
1717           ALLOCATE ( surf_usm_v(l)%iwghf_eb(1:surf_usm_v(l)%ns) )
1718           ALLOCATE ( surf_usm_v(l)%iwghf_eb_window(1:surf_usm_v(l)%ns) )
1719           IF ( ALLOCATED( surf_usm_v(l)%wshf    ) )  surf_usm_v(l)%wshf    = 0.0_wp
1720           IF ( ALLOCATED( surf_usm_v(l)%wshf_eb ) )  surf_usm_v(l)%wshf_eb = 0.0_wp
1721           IF ( ALLOCATED( surf_usm_v(l)%wghf_eb ) )  surf_usm_v(l)%wghf_eb = 0.0_wp
1722           IF ( ALLOCATED( surf_usm_v(l)%wghf_eb_window ) )  surf_usm_v(l)%wghf_eb_window = 0.0_wp
1723           IF ( ALLOCATED( surf_usm_v(l)%wghf_eb_green ) )  surf_usm_v(l)%wghf_eb_green = 0.0_wp
1724           IF ( ALLOCATED( surf_usm_v(l)%iwghf_eb ) )  surf_usm_v(l)%iwghf_eb = 0.0_wp
1725           IF ( ALLOCATED( surf_usm_v(l)%iwghf_eb_window ) )  surf_usm_v(l)%iwghf_eb_window = 0.0_wp
1726        ENDDO
1727       
1728    END SUBROUTINE usm_allocate_surface
1729
1730
1731!------------------------------------------------------------------------------!
1732! Description:
1733! ------------
1734!> Sum up and time-average urban surface output quantities as well as allocate
1735!> the array necessary for storing the average.
1736!------------------------------------------------------------------------------!
1737    SUBROUTINE usm_average_3d_data( mode, variable )
1738
1739        IMPLICIT NONE
1740
1741        CHARACTER(LEN=*), INTENT(IN) ::  mode
1742        CHARACTER(LEN=*), INTENT(IN) :: variable
1743 
1744        INTEGER(iwp)                                       :: i, j, k, l, m, ids, idsint, iwl, istat
1745        CHARACTER(LEN=varnamelength)                       :: var
1746        INTEGER(iwp), PARAMETER                            :: nd = 5
1747        CHARACTER(LEN=6), DIMENSION(0:nd-1), PARAMETER     :: dirname = (/ '_roof ', '_south', '_north', '_west ', '_east ' /)
1748        INTEGER(iwp), DIMENSION(0:nd-1), PARAMETER         :: dirint = (/ iup_u, isouth_u, inorth_u, iwest_u, ieast_u /)
1749
1750!--     find the real name of the variable
1751        ids = -1
1752        l = -1
1753        var = TRIM(variable)
1754        DO i = 0, nd-1
1755            k = len(TRIM(var))
1756            j = len(TRIM(dirname(i)))
1757            IF ( TRIM(var(k-j+1:k)) == TRIM(dirname(i)) )  THEN
1758                ids = i
1759                idsint = dirint(ids)
1760                var = var(:k-j)
1761                EXIT
1762            ENDIF
1763        ENDDO
1764        l = idsint - 2  ! horisontal direction index - terible hack !
1765        IF ( l < 0 .OR. l > 3 ) THEN
1766           l = -1
1767        END IF
1768        IF ( ids == -1 )  THEN
1769            var = TRIM(variable)
1770        ENDIF
1771        IF ( var(1:11) == 'usm_t_wall_'  .AND.  len(TRIM(var)) >= 12 )  THEN
1772!--          wall layers
1773            READ(var(12:12), '(I1)', iostat=istat ) iwl
1774            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
1775                var = var(1:10)
1776            ELSE
1777!--             wrong wall layer index
1778                RETURN
1779            ENDIF
1780        ENDIF
1781        IF ( var(1:13) == 'usm_t_window_'  .AND.  len(TRIM(var)) >= 14 )  THEN
1782!--          wall layers
1783            READ(var(14:14), '(I1)', iostat=istat ) iwl
1784            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
1785                var = var(1:12)
1786            ELSE
1787!--             wrong window layer index
1788                RETURN
1789            ENDIF
1790        ENDIF
1791        IF ( var(1:12) == 'usm_t_green_'  .AND.  len(TRIM(var)) >= 13 )  THEN
1792!--          wall layers
1793            READ(var(13:13), '(I1)', iostat=istat ) iwl
1794            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
1795                var = var(1:11)
1796            ELSE
1797!--             wrong green layer index
1798                RETURN
1799            ENDIF
1800        ENDIF
1801        IF ( var(1:8) == 'usm_swc_'  .AND.  len(TRIM(var)) >= 9 )  THEN
1802!--          swc layers
1803            READ(var(9:9), '(I1)', iostat=istat ) iwl
1804            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
1805                var = var(1:7)
1806            ELSE
1807!--             wrong swc layer index
1808                RETURN
1809            ENDIF
1810        ENDIF
1811
1812        IF ( mode == 'allocate' )  THEN
1813           
1814           SELECT CASE ( TRIM( var ) )
1815
1816                CASE ( 'usm_wshf' )
1817!--                 array of sensible heat flux from surfaces
1818!--                 land surfaces
1819                    IF ( l == -1 ) THEN
1820                       IF ( .NOT.  ALLOCATED(surf_usm_h%wshf_eb_av) )  THEN
1821                          ALLOCATE( surf_usm_h%wshf_eb_av(1:surf_usm_h%ns) )
1822                          surf_usm_h%wshf_eb_av = 0.0_wp
1823                       ENDIF
1824                    ELSE
1825                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%wshf_eb_av) )  THEN
1826                           ALLOCATE( surf_usm_v(l)%wshf_eb_av(1:surf_usm_v(l)%ns) )
1827                           surf_usm_v(l)%wshf_eb_av = 0.0_wp
1828                       ENDIF
1829                    ENDIF
1830                   
1831                CASE ( 'usm_qsws' )
1832!--                 array of latent heat flux from surfaces
1833!--                 land surfaces
1834                    IF ( l == -1 .AND. .NOT.  ALLOCATED(surf_usm_h%qsws_eb_av) )  THEN
1835                        ALLOCATE( surf_usm_h%qsws_eb_av(1:surf_usm_h%ns) )
1836                        surf_usm_h%qsws_eb_av = 0.0_wp
1837                    ELSE
1838                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%qsws_eb_av) )  THEN
1839                           ALLOCATE( surf_usm_v(l)%qsws_eb_av(1:surf_usm_v(l)%ns) )
1840                           surf_usm_v(l)%qsws_eb_av = 0.0_wp
1841                       ENDIF
1842                    ENDIF
1843                   
1844                CASE ( 'usm_qsws_veg' )
1845!--                 array of latent heat flux from vegetation surfaces
1846!--                 land surfaces
1847                    IF ( l == -1 .AND. .NOT.  ALLOCATED(surf_usm_h%qsws_veg_av) )  THEN
1848                        ALLOCATE( surf_usm_h%qsws_veg_av(1:surf_usm_h%ns) )
1849                        surf_usm_h%qsws_veg_av = 0.0_wp
1850                    ELSE
1851                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%qsws_veg_av) )  THEN
1852                           ALLOCATE( surf_usm_v(l)%qsws_veg_av(1:surf_usm_v(l)%ns) )
1853                           surf_usm_v(l)%qsws_veg_av = 0.0_wp
1854                       ENDIF
1855                    ENDIF
1856                   
1857                CASE ( 'usm_qsws_liq' )
1858!--                 array of latent heat flux from surfaces with liquid
1859!--                 land surfaces
1860                    IF ( l == -1 .AND. .NOT.  ALLOCATED(surf_usm_h%qsws_liq_av) )  THEN
1861                        ALLOCATE( surf_usm_h%qsws_liq_av(1:surf_usm_h%ns) )
1862                        surf_usm_h%qsws_liq_av = 0.0_wp
1863                    ELSE
1864                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%qsws_liq_av) )  THEN
1865                           ALLOCATE( surf_usm_v(l)%qsws_liq_av(1:surf_usm_v(l)%ns) )
1866                           surf_usm_v(l)%qsws_liq_av = 0.0_wp
1867                       ENDIF
1868                    ENDIF
1869!
1870!--             Please note, the following output quantities belongs to the
1871!--             individual tile fractions - ground heat flux at wall-, window-,
1872!--             and green fraction. Aggregated ground-heat flux is treated
1873!--             accordingly in average_3d_data, sum_up_3d_data, etc..
1874                CASE ( 'usm_wghf' )
1875!--                 array of heat flux from ground (wall, roof, land)
1876                    IF ( l == -1 ) THEN
1877                       IF ( .NOT.  ALLOCATED(surf_usm_h%wghf_eb_av) )  THEN
1878                           ALLOCATE( surf_usm_h%wghf_eb_av(1:surf_usm_h%ns) )
1879                           surf_usm_h%wghf_eb_av = 0.0_wp
1880                       ENDIF
1881                    ELSE
1882                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%wghf_eb_av) )  THEN
1883                           ALLOCATE( surf_usm_v(l)%wghf_eb_av(1:surf_usm_v(l)%ns) )
1884                           surf_usm_v(l)%wghf_eb_av = 0.0_wp
1885                       ENDIF
1886                    ENDIF
1887
1888                CASE ( 'usm_wghf_window' )
1889!--                 array of heat flux from window ground (wall, roof, land)
1890                    IF ( l == -1 ) THEN
1891                       IF ( .NOT.  ALLOCATED(surf_usm_h%wghf_eb_window_av) )  THEN
1892                           ALLOCATE( surf_usm_h%wghf_eb_window_av(1:surf_usm_h%ns) )
1893                           surf_usm_h%wghf_eb_window_av = 0.0_wp
1894                       ENDIF
1895                    ELSE
1896                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%wghf_eb_window_av) )  THEN
1897                           ALLOCATE( surf_usm_v(l)%wghf_eb_window_av(1:surf_usm_v(l)%ns) )
1898                           surf_usm_v(l)%wghf_eb_window_av = 0.0_wp
1899                       ENDIF
1900                    ENDIF
1901
1902                CASE ( 'usm_wghf_green' )
1903!--                 array of heat flux from green ground (wall, roof, land)
1904                    IF ( l == -1 ) THEN
1905                       IF ( .NOT.  ALLOCATED(surf_usm_h%wghf_eb_green_av) )  THEN
1906                           ALLOCATE( surf_usm_h%wghf_eb_green_av(1:surf_usm_h%ns) )
1907                           surf_usm_h%wghf_eb_green_av = 0.0_wp
1908                       ENDIF
1909                    ELSE
1910                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%wghf_eb_green_av) )  THEN
1911                           ALLOCATE( surf_usm_v(l)%wghf_eb_green_av(1:surf_usm_v(l)%ns) )
1912                           surf_usm_v(l)%wghf_eb_green_av = 0.0_wp
1913                       ENDIF
1914                    ENDIF
1915
1916                CASE ( 'usm_iwghf' )
1917!--                 array of heat flux from indoor ground (wall, roof, land)
1918                    IF ( l == -1 ) THEN
1919                       IF ( .NOT.  ALLOCATED(surf_usm_h%iwghf_eb_av) )  THEN
1920                           ALLOCATE( surf_usm_h%iwghf_eb_av(1:surf_usm_h%ns) )
1921                           surf_usm_h%iwghf_eb_av = 0.0_wp
1922                       ENDIF
1923                    ELSE
1924                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%iwghf_eb_av) )  THEN
1925                           ALLOCATE( surf_usm_v(l)%iwghf_eb_av(1:surf_usm_v(l)%ns) )
1926                           surf_usm_v(l)%iwghf_eb_av = 0.0_wp
1927                       ENDIF
1928                    ENDIF
1929
1930                CASE ( 'usm_iwghf_window' )
1931!--                 array of heat flux from indoor window ground (wall, roof, land)
1932                    IF ( l == -1 ) THEN
1933                       IF ( .NOT.  ALLOCATED(surf_usm_h%iwghf_eb_window_av) )  THEN
1934                           ALLOCATE( surf_usm_h%iwghf_eb_window_av(1:surf_usm_h%ns) )
1935                           surf_usm_h%iwghf_eb_window_av = 0.0_wp
1936                       ENDIF
1937                    ELSE
1938                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%iwghf_eb_window_av) )  THEN
1939                           ALLOCATE( surf_usm_v(l)%iwghf_eb_window_av(1:surf_usm_v(l)%ns) )
1940                           surf_usm_v(l)%iwghf_eb_window_av = 0.0_wp
1941                       ENDIF
1942                    ENDIF
1943
1944                CASE ( 'usm_t_surf_wall' )
1945!--                 surface temperature for surfaces
1946                    IF ( l == -1 ) THEN
1947                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_surf_wall_av) )  THEN
1948                           ALLOCATE( surf_usm_h%t_surf_wall_av(1:surf_usm_h%ns) )
1949                           surf_usm_h%t_surf_wall_av = 0.0_wp
1950                       ENDIF
1951                    ELSE
1952                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_surf_wall_av) )  THEN
1953                           ALLOCATE( surf_usm_v(l)%t_surf_wall_av(1:surf_usm_v(l)%ns) )
1954                           surf_usm_v(l)%t_surf_wall_av = 0.0_wp
1955                       ENDIF
1956                    ENDIF
1957
1958                CASE ( 'usm_t_surf_window' )
1959!--                 surface temperature for window surfaces
1960                    IF ( l == -1 ) THEN
1961                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_surf_window_av) )  THEN
1962                           ALLOCATE( surf_usm_h%t_surf_window_av(1:surf_usm_h%ns) )
1963                           surf_usm_h%t_surf_window_av = 0.0_wp
1964                       ENDIF
1965                    ELSE
1966                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_surf_window_av) )  THEN
1967                           ALLOCATE( surf_usm_v(l)%t_surf_window_av(1:surf_usm_v(l)%ns) )
1968                           surf_usm_v(l)%t_surf_window_av = 0.0_wp
1969                       ENDIF
1970                    ENDIF
1971                   
1972                CASE ( 'usm_t_surf_green' )
1973!--                 surface temperature for green surfaces
1974                    IF ( l == -1 ) THEN
1975                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_surf_green_av) )  THEN
1976                           ALLOCATE( surf_usm_h%t_surf_green_av(1:surf_usm_h%ns) )
1977                           surf_usm_h%t_surf_green_av = 0.0_wp
1978                       ENDIF
1979                    ELSE
1980                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_surf_green_av) )  THEN
1981                           ALLOCATE( surf_usm_v(l)%t_surf_green_av(1:surf_usm_v(l)%ns) )
1982                           surf_usm_v(l)%t_surf_green_av = 0.0_wp
1983                       ENDIF
1984                    ENDIF
1985               
1986                CASE ( 'usm_theta_10cm' )
1987!--                 near surface (10cm) temperature for whole surfaces
1988                    IF ( l == -1 ) THEN
1989                       IF ( .NOT.  ALLOCATED(surf_usm_h%pt_10cm_av) )  THEN
1990                           ALLOCATE( surf_usm_h%pt_10cm_av(1:surf_usm_h%ns) )
1991                           surf_usm_h%pt_10cm_av = 0.0_wp
1992                       ENDIF
1993                    ELSE
1994                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%pt_10cm_av) )  THEN
1995                           ALLOCATE( surf_usm_v(l)%pt_10cm_av(1:surf_usm_v(l)%ns) )
1996                           surf_usm_v(l)%pt_10cm_av = 0.0_wp
1997                       ENDIF
1998                    ENDIF
1999                 
2000                CASE ( 'usm_t_wall' )
2001!--                 wall temperature for iwl layer of walls and land
2002                    IF ( l == -1 ) THEN
2003                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_wall_av) )  THEN
2004                           ALLOCATE( surf_usm_h%t_wall_av(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
2005                           surf_usm_h%t_wall_av = 0.0_wp
2006                       ENDIF
2007                    ELSE
2008                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_wall_av) )  THEN
2009                           ALLOCATE( surf_usm_v(l)%t_wall_av(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
2010                           surf_usm_v(l)%t_wall_av = 0.0_wp
2011                       ENDIF
2012                    ENDIF
2013
2014                CASE ( 'usm_t_window' )
2015!--                 window temperature for iwl layer of walls and land
2016                    IF ( l == -1 ) THEN
2017                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_window_av) )  THEN
2018                           ALLOCATE( surf_usm_h%t_window_av(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
2019                           surf_usm_h%t_window_av = 0.0_wp
2020                       ENDIF
2021                    ELSE
2022                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_window_av) )  THEN
2023                           ALLOCATE( surf_usm_v(l)%t_window_av(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
2024                           surf_usm_v(l)%t_window_av = 0.0_wp
2025                       ENDIF
2026                    ENDIF
2027
2028                CASE ( 'usm_t_green' )
2029!--                 green temperature for iwl layer of walls and land
2030                    IF ( l == -1 ) THEN
2031                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_green_av) )  THEN
2032                           ALLOCATE( surf_usm_h%t_green_av(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
2033                           surf_usm_h%t_green_av = 0.0_wp
2034                       ENDIF
2035                    ELSE
2036                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_green_av) )  THEN
2037                           ALLOCATE( surf_usm_v(l)%t_green_av(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
2038                           surf_usm_v(l)%t_green_av = 0.0_wp
2039                       ENDIF
2040                    ENDIF
2041                CASE ( 'usm_swc' )
2042!--                 soil water content for iwl layer of walls and land
2043                    IF ( l == -1 .AND. .NOT.  ALLOCATED(surf_usm_h%swc_av) )  THEN
2044                        ALLOCATE( surf_usm_h%swc_av(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
2045                        surf_usm_h%swc_av = 0.0_wp
2046                    ELSE
2047                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%swc_av) )  THEN
2048                           ALLOCATE( surf_usm_v(l)%swc_av(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
2049                           surf_usm_v(l)%swc_av = 0.0_wp
2050                       ENDIF
2051                    ENDIF
2052
2053               CASE DEFAULT
2054                   CONTINUE
2055
2056           END SELECT
2057
2058        ELSEIF ( mode == 'sum' )  THEN
2059           
2060           SELECT CASE ( TRIM( var ) )
2061
2062                CASE ( 'usm_wshf' )
2063!--                 array of sensible heat flux from surfaces (land, roof, wall)
2064                    IF ( l == -1 ) THEN
2065                       DO  m = 1, surf_usm_h%ns
2066                          surf_usm_h%wshf_eb_av(m) =                              &
2067                                             surf_usm_h%wshf_eb_av(m) +           &
2068                                             surf_usm_h%wshf_eb(m)
2069                       ENDDO
2070                    ELSE
2071                       DO  m = 1, surf_usm_v(l)%ns
2072                          surf_usm_v(l)%wshf_eb_av(m) =                        &
2073                                          surf_usm_v(l)%wshf_eb_av(m) +        &
2074                                          surf_usm_v(l)%wshf_eb(m)
2075                       ENDDO
2076                    ENDIF
2077                   
2078                CASE ( 'usm_qsws' )
2079!--                 array of latent heat flux from surfaces (land, roof, wall)
2080                    IF ( l == -1 ) THEN
2081                    DO  m = 1, surf_usm_h%ns
2082                       surf_usm_h%qsws_eb_av(m) =                              &
2083                                          surf_usm_h%qsws_eb_av(m) +           &
2084                                          surf_usm_h%qsws_eb(m)
2085                    ENDDO
2086                    ELSE
2087                       DO  m = 1, surf_usm_v(l)%ns
2088                          surf_usm_v(l)%qsws_eb_av(m) =                        &
2089                                          surf_usm_v(l)%qsws_eb_av(m) +        &
2090                                          surf_usm_v(l)%qsws_eb(m)
2091                       ENDDO
2092                    ENDIF
2093                   
2094                CASE ( 'usm_qsws_veg' )
2095!--                 array of latent heat flux from vegetation surfaces (land, roof, wall)
2096                    IF ( l == -1 ) THEN
2097                    DO  m = 1, surf_usm_h%ns
2098                       surf_usm_h%qsws_veg_av(m) =                              &
2099                                          surf_usm_h%qsws_veg_av(m) +           &
2100                                          surf_usm_h%qsws_veg(m)
2101                    ENDDO
2102                    ELSE
2103                       DO  m = 1, surf_usm_v(l)%ns
2104                          surf_usm_v(l)%qsws_veg_av(m) =                        &
2105                                          surf_usm_v(l)%qsws_veg_av(m) +        &
2106                                          surf_usm_v(l)%qsws_veg(m)
2107                       ENDDO
2108                    ENDIF
2109                   
2110                CASE ( 'usm_qsws_liq' )
2111!--                 array of latent heat flux from surfaces with liquid (land, roof, wall)
2112                    IF ( l == -1 ) THEN
2113                    DO  m = 1, surf_usm_h%ns
2114                       surf_usm_h%qsws_liq_av(m) =                              &
2115                                          surf_usm_h%qsws_liq_av(m) +           &
2116                                          surf_usm_h%qsws_liq(m)
2117                    ENDDO
2118                    ELSE
2119                       DO  m = 1, surf_usm_v(l)%ns
2120                          surf_usm_v(l)%qsws_liq_av(m) =                        &
2121                                          surf_usm_v(l)%qsws_liq_av(m) +        &
2122                                          surf_usm_v(l)%qsws_liq(m)
2123                       ENDDO
2124                    ENDIF
2125                   
2126                CASE ( 'usm_wghf' )
2127!--                 array of heat flux from ground (wall, roof, land)
2128                    IF ( l == -1 ) THEN
2129                       DO  m = 1, surf_usm_h%ns
2130                          surf_usm_h%wghf_eb_av(m) =                              &
2131                                             surf_usm_h%wghf_eb_av(m) +           &
2132                                             surf_usm_h%wghf_eb(m)
2133                       ENDDO
2134                    ELSE
2135                       DO  m = 1, surf_usm_v(l)%ns
2136                          surf_usm_v(l)%wghf_eb_av(m) =                        &
2137                                          surf_usm_v(l)%wghf_eb_av(m) +        &
2138                                          surf_usm_v(l)%wghf_eb(m)
2139                       ENDDO
2140                    ENDIF
2141                   
2142                CASE ( 'usm_wghf_window' )
2143!--                 array of heat flux from window ground (wall, roof, land)
2144                    IF ( l == -1 ) THEN
2145                       DO  m = 1, surf_usm_h%ns
2146                          surf_usm_h%wghf_eb_window_av(m) =                              &
2147                                             surf_usm_h%wghf_eb_window_av(m) +           &
2148                                             surf_usm_h%wghf_eb_window(m)
2149                       ENDDO
2150                    ELSE
2151                       DO  m = 1, surf_usm_v(l)%ns
2152                          surf_usm_v(l)%wghf_eb_window_av(m) =                        &
2153                                          surf_usm_v(l)%wghf_eb_window_av(m) +        &
2154                                          surf_usm_v(l)%wghf_eb_window(m)
2155                       ENDDO
2156                    ENDIF
2157
2158                CASE ( 'usm_wghf_green' )
2159!--                 array of heat flux from green ground (wall, roof, land)
2160                    IF ( l == -1 ) THEN
2161                       DO  m = 1, surf_usm_h%ns
2162                          surf_usm_h%wghf_eb_green_av(m) =                              &
2163                                             surf_usm_h%wghf_eb_green_av(m) +           &
2164                                             surf_usm_h%wghf_eb_green(m)
2165                       ENDDO
2166                    ELSE
2167                       DO  m = 1, surf_usm_v(l)%ns
2168                          surf_usm_v(l)%wghf_eb_green_av(m) =                        &
2169                                          surf_usm_v(l)%wghf_eb_green_av(m) +        &
2170                                          surf_usm_v(l)%wghf_eb_green(m)
2171                       ENDDO
2172                    ENDIF
2173                   
2174                CASE ( 'usm_iwghf' )
2175!--                 array of heat flux from indoor ground (wall, roof, land)
2176                    IF ( l == -1 ) THEN
2177                       DO  m = 1, surf_usm_h%ns
2178                          surf_usm_h%iwghf_eb_av(m) =                              &
2179                                             surf_usm_h%iwghf_eb_av(m) +           &
2180                                             surf_usm_h%iwghf_eb(m)
2181                       ENDDO
2182                    ELSE
2183                       DO  m = 1, surf_usm_v(l)%ns
2184                          surf_usm_v(l)%iwghf_eb_av(m) =                        &
2185                                          surf_usm_v(l)%iwghf_eb_av(m) +        &
2186                                          surf_usm_v(l)%iwghf_eb(m)
2187                       ENDDO
2188                    ENDIF
2189                   
2190                CASE ( 'usm_iwghf_window' )
2191!--                 array of heat flux from indoor window ground (wall, roof, land)
2192                    IF ( l == -1 ) THEN
2193                       DO  m = 1, surf_usm_h%ns
2194                          surf_usm_h%iwghf_eb_window_av(m) =                              &
2195                                             surf_usm_h%iwghf_eb_window_av(m) +           &
2196                                             surf_usm_h%iwghf_eb_window(m)
2197                       ENDDO
2198                    ELSE
2199                       DO  m = 1, surf_usm_v(l)%ns
2200                          surf_usm_v(l)%iwghf_eb_window_av(m) =                        &
2201                                          surf_usm_v(l)%iwghf_eb_window_av(m) +        &
2202                                          surf_usm_v(l)%iwghf_eb_window(m)
2203                       ENDDO
2204                    ENDIF
2205                   
2206                CASE ( 'usm_t_surf_wall' )
2207!--                 surface temperature for surfaces
2208                    IF ( l == -1 ) THEN
2209                       DO  m = 1, surf_usm_h%ns
2210                       surf_usm_h%t_surf_wall_av(m) =                               & 
2211                                          surf_usm_h%t_surf_wall_av(m) +            &
2212                                          t_surf_wall_h(m)
2213                       ENDDO
2214                    ELSE
2215                       DO  m = 1, surf_usm_v(l)%ns
2216                          surf_usm_v(l)%t_surf_wall_av(m) =                         &
2217                                          surf_usm_v(l)%t_surf_wall_av(m) +         &
2218                                          t_surf_wall_v(l)%t(m)
2219                       ENDDO
2220                    ENDIF
2221                   
2222                CASE ( 'usm_t_surf_window' )
2223!--                 surface temperature for window surfaces
2224                    IF ( l == -1 ) THEN
2225                       DO  m = 1, surf_usm_h%ns
2226                          surf_usm_h%t_surf_window_av(m) =                               &
2227                                             surf_usm_h%t_surf_window_av(m) +            &
2228                                             t_surf_window_h(m)
2229                       ENDDO
2230                    ELSE
2231                       DO  m = 1, surf_usm_v(l)%ns
2232                          surf_usm_v(l)%t_surf_window_av(m) =                         &
2233                                          surf_usm_v(l)%t_surf_window_av(m) +         &
2234                                          t_surf_window_v(l)%t(m)
2235                       ENDDO
2236                    ENDIF
2237                   
2238                CASE ( 'usm_t_surf_green' )
2239!--                 surface temperature for green surfaces
2240                    IF ( l == -1 ) THEN
2241                       DO  m = 1, surf_usm_h%ns
2242                          surf_usm_h%t_surf_green_av(m) =                               &
2243                                             surf_usm_h%t_surf_green_av(m) +            &
2244                                             t_surf_green_h(m)
2245                       ENDDO
2246                    ELSE
2247                       DO  m = 1, surf_usm_v(l)%ns
2248                          surf_usm_v(l)%t_surf_green_av(m) =                         &
2249                                          surf_usm_v(l)%t_surf_green_av(m) +         &
2250                                          t_surf_green_v(l)%t(m)
2251                       ENDDO
2252                    ENDIF
2253               
2254                CASE ( 'usm_theta_10cm' )
2255!--                 near surface temperature for whole surfaces
2256                    IF ( l == -1 ) THEN
2257                       DO  m = 1, surf_usm_h%ns
2258                          surf_usm_h%pt_10cm_av(m) =                               &
2259                                             surf_usm_h%pt_10cm_av(m) +            &
2260                                             surf_usm_h%pt_10cm(m)
2261                       ENDDO
2262                    ELSE
2263                       DO  m = 1, surf_usm_v(l)%ns
2264                          surf_usm_v(l)%pt_10cm_av(m) =                         &
2265                                          surf_usm_v(l)%pt_10cm_av(m) +         &
2266                                          surf_usm_v(l)%pt_10cm(m)
2267                       ENDDO
2268                    ENDIF
2269                   
2270                CASE ( 'usm_t_wall' )
2271!--                 wall temperature for  iwl layer of walls and land
2272                    IF ( l == -1 ) THEN
2273                       DO  m = 1, surf_usm_h%ns
2274                          surf_usm_h%t_wall_av(iwl,m) =                           &
2275                                             surf_usm_h%t_wall_av(iwl,m) +        &
2276                                             t_wall_h(iwl,m)
2277                       ENDDO
2278                    ELSE
2279                       DO  m = 1, surf_usm_v(l)%ns
2280                          surf_usm_v(l)%t_wall_av(iwl,m) =                     &
2281                                          surf_usm_v(l)%t_wall_av(iwl,m) +     &
2282                                          t_wall_v(l)%t(iwl,m)
2283                       ENDDO
2284                    ENDIF
2285                   
2286                CASE ( 'usm_t_window' )
2287!--                 window temperature for  iwl layer of walls and land
2288                    IF ( l == -1 ) THEN
2289                       DO  m = 1, surf_usm_h%ns
2290                          surf_usm_h%t_window_av(iwl,m) =                           &
2291                                             surf_usm_h%t_window_av(iwl,m) +        &
2292                                             t_window_h(iwl,m)
2293                       ENDDO
2294                    ELSE
2295                       DO  m = 1, surf_usm_v(l)%ns
2296                          surf_usm_v(l)%t_window_av(iwl,m) =                     &
2297                                          surf_usm_v(l)%t_window_av(iwl,m) +     &
2298                                          t_window_v(l)%t(iwl,m)
2299                       ENDDO
2300                    ENDIF
2301
2302                CASE ( 'usm_t_green' )
2303!--                 green temperature for  iwl layer of walls and land
2304                    IF ( l == -1 ) THEN
2305                       DO  m = 1, surf_usm_h%ns
2306                          surf_usm_h%t_green_av(iwl,m) =                           &
2307                                             surf_usm_h%t_green_av(iwl,m) +        &
2308                                             t_green_h(iwl,m)
2309                       ENDDO
2310                    ELSE
2311                       DO  m = 1, surf_usm_v(l)%ns
2312                          surf_usm_v(l)%t_green_av(iwl,m) =                     &
2313                                          surf_usm_v(l)%t_green_av(iwl,m) +     &
2314                                          t_green_v(l)%t(iwl,m)
2315                       ENDDO
2316                    ENDIF
2317
2318                CASE ( 'usm_swc' )
2319!--                 soil water content for  iwl layer of walls and land
2320                    IF ( l == -1 ) THEN
2321                    DO  m = 1, surf_usm_h%ns
2322                       surf_usm_h%swc_av(iwl,m) =                           &
2323                                          surf_usm_h%swc_av(iwl,m) +        &
2324                                          swc_h(iwl,m)
2325                    ENDDO
2326                    ELSE
2327                       DO  m = 1, surf_usm_v(l)%ns
2328                          surf_usm_v(l)%swc_av(iwl,m) =                     &
2329                                          surf_usm_v(l)%swc_av(iwl,m) +     &
2330                                          swc_v(l)%t(iwl,m)
2331                       ENDDO
2332                    ENDIF
2333
2334                CASE DEFAULT
2335                    CONTINUE
2336
2337           END SELECT
2338
2339        ELSEIF ( mode == 'average' )  THEN
2340           
2341           SELECT CASE ( TRIM( var ) )
2342
2343                CASE ( 'usm_wshf' )
2344!--                 array of sensible heat flux from surfaces (land, roof, wall)
2345                    IF ( l == -1 ) THEN
2346                       DO  m = 1, surf_usm_h%ns
2347                          surf_usm_h%wshf_eb_av(m) =                              &
2348                                             surf_usm_h%wshf_eb_av(m) /           &
2349                                             REAL( average_count_3d, kind=wp )
2350                       ENDDO
2351                    ELSE
2352                       DO  m = 1, surf_usm_v(l)%ns
2353                          surf_usm_v(l)%wshf_eb_av(m) =                        &
2354                                          surf_usm_v(l)%wshf_eb_av(m) /        &
2355                                          REAL( average_count_3d, kind=wp )
2356                       ENDDO
2357                    ENDIF
2358                   
2359                CASE ( 'usm_qsws' )
2360!--                 array of latent heat flux from surfaces (land, roof, wall)
2361                    IF ( l == -1 ) THEN
2362                    DO  m = 1, surf_usm_h%ns
2363                       surf_usm_h%qsws_eb_av(m) =                              &
2364                                          surf_usm_h%qsws_eb_av(m) /           &
2365                                          REAL( average_count_3d, kind=wp )
2366                    ENDDO
2367                    ELSE
2368                       DO  m = 1, surf_usm_v(l)%ns
2369                          surf_usm_v(l)%qsws_eb_av(m) =                        &
2370                                          surf_usm_v(l)%qsws_eb_av(m) /        &
2371                                          REAL( average_count_3d, kind=wp )
2372                       ENDDO
2373                    ENDIF
2374
2375                CASE ( 'usm_qsws_veg' )
2376!--                 array of latent heat flux from vegetation surfaces (land, roof, wall)
2377                    IF ( l == -1 ) THEN
2378                    DO  m = 1, surf_usm_h%ns
2379                       surf_usm_h%qsws_veg_av(m) =                              &
2380                                          surf_usm_h%qsws_veg_av(m) /           &
2381                                          REAL( average_count_3d, kind=wp )
2382                    ENDDO
2383                    ELSE
2384                       DO  m = 1, surf_usm_v(l)%ns
2385                          surf_usm_v(l)%qsws_veg_av(m) =                        &
2386                                          surf_usm_v(l)%qsws_veg_av(m) /        &
2387                                          REAL( average_count_3d, kind=wp )
2388                       ENDDO
2389                    ENDIF
2390                   
2391                CASE ( 'usm_qsws_liq' )
2392!--                 array of latent heat flux from surfaces with liquid (land, roof, wall)
2393                    IF ( l == -1 ) THEN
2394                    DO  m = 1, surf_usm_h%ns
2395                       surf_usm_h%qsws_liq_av(m) =                              &
2396                                          surf_usm_h%qsws_liq_av(m) /           &
2397                                          REAL( average_count_3d, kind=wp )
2398                    ENDDO
2399                    ELSE
2400                       DO  m = 1, surf_usm_v(l)%ns
2401                          surf_usm_v(l)%qsws_liq_av(m) =                        &
2402                                          surf_usm_v(l)%qsws_liq_av(m) /        &
2403                                          REAL( average_count_3d, kind=wp )
2404                       ENDDO
2405                    ENDIF
2406                   
2407                CASE ( 'usm_wghf' )
2408!--                 array of heat flux from ground (wall, roof, land)
2409                    IF ( l == -1 ) THEN
2410                       DO  m = 1, surf_usm_h%ns
2411                          surf_usm_h%wghf_eb_av(m) =                              &
2412                                             surf_usm_h%wghf_eb_av(m) /           &
2413                                             REAL( average_count_3d, kind=wp )
2414                       ENDDO
2415                    ELSE
2416                       DO  m = 1, surf_usm_v(l)%ns
2417                          surf_usm_v(l)%wghf_eb_av(m) =                        &
2418                                          surf_usm_v(l)%wghf_eb_av(m) /        &
2419                                          REAL( average_count_3d, kind=wp )
2420                       ENDDO
2421                    ENDIF
2422                   
2423                CASE ( 'usm_wghf_window' )
2424!--                 array of heat flux from window ground (wall, roof, land)
2425                    IF ( l == -1 ) THEN
2426                       DO  m = 1, surf_usm_h%ns
2427                          surf_usm_h%wghf_eb_window_av(m) =                              &
2428                                             surf_usm_h%wghf_eb_window_av(m) /           &
2429                                             REAL( average_count_3d, kind=wp )
2430                       ENDDO
2431                    ELSE
2432                       DO  m = 1, surf_usm_v(l)%ns
2433                          surf_usm_v(l)%wghf_eb_window_av(m) =                        &
2434                                          surf_usm_v(l)%wghf_eb_window_av(m) /        &
2435                                          REAL( average_count_3d, kind=wp )
2436                       ENDDO
2437                    ENDIF
2438
2439                CASE ( 'usm_wghf_green' )
2440!--                 array of heat flux from green ground (wall, roof, land)
2441                    IF ( l == -1 ) THEN
2442                       DO  m = 1, surf_usm_h%ns
2443                          surf_usm_h%wghf_eb_green_av(m) =                              &
2444                                             surf_usm_h%wghf_eb_green_av(m) /           &
2445                                             REAL( average_count_3d, kind=wp )
2446                       ENDDO
2447                    ELSE
2448                       DO  m = 1, surf_usm_v(l)%ns
2449                          surf_usm_v(l)%wghf_eb_green_av(m) =                        &
2450                                          surf_usm_v(l)%wghf_eb_green_av(m) /        &
2451                                          REAL( average_count_3d, kind=wp )
2452                       ENDDO
2453                    ENDIF
2454
2455                CASE ( 'usm_iwghf' )
2456!--                 array of heat flux from indoor ground (wall, roof, land)
2457                    IF ( l == -1 ) THEN
2458                       DO  m = 1, surf_usm_h%ns
2459                          surf_usm_h%iwghf_eb_av(m) =                              &
2460                                             surf_usm_h%iwghf_eb_av(m) /           &
2461                                             REAL( average_count_3d, kind=wp )
2462                       ENDDO
2463                    ELSE
2464                       DO  m = 1, surf_usm_v(l)%ns
2465                          surf_usm_v(l)%iwghf_eb_av(m) =                        &
2466                                          surf_usm_v(l)%iwghf_eb_av(m) /        &
2467                                          REAL( average_count_3d, kind=wp )
2468                       ENDDO
2469                    ENDIF
2470                   
2471                CASE ( 'usm_iwghf_window' )
2472!--                 array of heat flux from indoor window ground (wall, roof, land)
2473                    IF ( l == -1 ) THEN
2474                       DO  m = 1, surf_usm_h%ns
2475                          surf_usm_h%iwghf_eb_window_av(m) =                              &
2476                                             surf_usm_h%iwghf_eb_window_av(m) /           &
2477                                             REAL( average_count_3d, kind=wp )
2478                       ENDDO
2479                    ELSE
2480                       DO  m = 1, surf_usm_v(l)%ns
2481                          surf_usm_v(l)%iwghf_eb_window_av(m) =                        &
2482                                          surf_usm_v(l)%iwghf_eb_window_av(m) /        &
2483                                          REAL( average_count_3d, kind=wp )
2484                       ENDDO
2485                    ENDIF
2486                   
2487                CASE ( 'usm_t_surf_wall' )
2488!--                 surface temperature for surfaces
2489                    IF ( l == -1 ) THEN
2490                       DO  m = 1, surf_usm_h%ns
2491                       surf_usm_h%t_surf_wall_av(m) =                               & 
2492                                          surf_usm_h%t_surf_wall_av(m) /            &
2493                                             REAL( average_count_3d, kind=wp )
2494                       ENDDO
2495                    ELSE
2496                       DO  m = 1, surf_usm_v(l)%ns
2497                          surf_usm_v(l)%t_surf_wall_av(m) =                         &
2498                                          surf_usm_v(l)%t_surf_wall_av(m) /         &
2499                                          REAL( average_count_3d, kind=wp )
2500                       ENDDO
2501                    ENDIF
2502                   
2503                CASE ( 'usm_t_surf_window' )
2504!--                 surface temperature for window surfaces
2505                    IF ( l == -1 ) THEN
2506                       DO  m = 1, surf_usm_h%ns
2507                          surf_usm_h%t_surf_window_av(m) =                               &
2508                                             surf_usm_h%t_surf_window_av(m) /            &
2509                                             REAL( average_count_3d, kind=wp )
2510                       ENDDO
2511                    ELSE
2512                       DO  m = 1, surf_usm_v(l)%ns
2513                          surf_usm_v(l)%t_surf_window_av(m) =                         &
2514                                          surf_usm_v(l)%t_surf_window_av(m) /         &
2515                                          REAL( average_count_3d, kind=wp )
2516                       ENDDO
2517                    ENDIF
2518                   
2519                CASE ( 'usm_t_surf_green' )
2520!--                 surface temperature for green surfaces
2521                    IF ( l == -1 ) THEN
2522                       DO  m = 1, surf_usm_h%ns
2523                          surf_usm_h%t_surf_green_av(m) =                               &
2524                                             surf_usm_h%t_surf_green_av(m) /            &
2525                                             REAL( average_count_3d, kind=wp )
2526                       ENDDO
2527                    ELSE
2528                       DO  m = 1, surf_usm_v(l)%ns
2529                          surf_usm_v(l)%t_surf_green_av(m) =                         &
2530                                          surf_usm_v(l)%t_surf_green_av(m) /         &
2531                                          REAL( average_count_3d, kind=wp )
2532                       ENDDO
2533                    ENDIF
2534                   
2535                CASE ( 'usm_theta_10cm' )
2536!--                 near surface temperature for whole surfaces
2537                    IF ( l == -1 ) THEN
2538                       DO  m = 1, surf_usm_h%ns
2539                          surf_usm_h%pt_10cm_av(m) =                               &
2540                                             surf_usm_h%pt_10cm_av(m) /            &
2541                                             REAL( average_count_3d, kind=wp )
2542                       ENDDO
2543                    ELSE
2544                       DO  m = 1, surf_usm_v(l)%ns
2545                          surf_usm_v(l)%pt_10cm_av(m) =                         &
2546                                          surf_usm_v(l)%pt_10cm_av(m) /         &
2547                                          REAL( average_count_3d, kind=wp )
2548                       ENDDO
2549                    ENDIF
2550
2551                   
2552                CASE ( 'usm_t_wall' )
2553!--                 wall temperature for  iwl layer of walls and land
2554                    IF ( l == -1 ) THEN
2555                       DO  m = 1, surf_usm_h%ns
2556                          surf_usm_h%t_wall_av(iwl,m) =                           &
2557                                             surf_usm_h%t_wall_av(iwl,m) /        &
2558                                             REAL( average_count_3d, kind=wp )
2559                       ENDDO
2560                    ELSE
2561                       DO  m = 1, surf_usm_v(l)%ns
2562                          surf_usm_v(l)%t_wall_av(iwl,m) =                     &
2563                                          surf_usm_v(l)%t_wall_av(iwl,m) /     &
2564                                          REAL( average_count_3d, kind=wp )
2565                       ENDDO
2566                    ENDIF
2567
2568                CASE ( 'usm_t_window' )
2569!--                 window temperature for  iwl layer of walls and land
2570                    IF ( l == -1 ) THEN
2571                       DO  m = 1, surf_usm_h%ns
2572                          surf_usm_h%t_window_av(iwl,m) =                           &
2573                                             surf_usm_h%t_window_av(iwl,m) /        &
2574                                             REAL( average_count_3d, kind=wp )
2575                       ENDDO
2576                    ELSE
2577                       DO  m = 1, surf_usm_v(l)%ns
2578                          surf_usm_v(l)%t_window_av(iwl,m) =                     &
2579                                          surf_usm_v(l)%t_window_av(iwl,m) /     &
2580                                          REAL( average_count_3d, kind=wp )
2581                       ENDDO
2582                    ENDIF
2583
2584                CASE ( 'usm_t_green' )
2585!--                 green temperature for  iwl layer of walls and land
2586                    IF ( l == -1 ) THEN
2587                       DO  m = 1, surf_usm_h%ns
2588                          surf_usm_h%t_green_av(iwl,m) =                           &
2589                                             surf_usm_h%t_green_av(iwl,m) /        &
2590                                             REAL( average_count_3d, kind=wp )
2591                       ENDDO
2592                    ELSE
2593                       DO  m = 1, surf_usm_v(l)%ns
2594                          surf_usm_v(l)%t_green_av(iwl,m) =                     &
2595                                          surf_usm_v(l)%t_green_av(iwl,m) /     &
2596                                          REAL( average_count_3d, kind=wp )
2597                       ENDDO
2598                    ENDIF
2599                   
2600                CASE ( 'usm_swc' )
2601!--                 soil water content for  iwl layer of walls and land
2602                    IF ( l == -1 ) THEN
2603                    DO  m = 1, surf_usm_h%ns
2604                       surf_usm_h%swc_av(iwl,m) =                           &
2605                                          surf_usm_h%swc_av(iwl,m) /        &
2606                                          REAL( average_count_3d, kind=wp )
2607                    ENDDO
2608                    ELSE
2609                       DO  m = 1, surf_usm_v(l)%ns
2610                          surf_usm_v(l)%swc_av(iwl,m) =                     &
2611                                          surf_usm_v(l)%swc_av(iwl,m) /     &
2612                                          REAL( average_count_3d, kind=wp )
2613                       ENDDO
2614                    ENDIF
2615
2616
2617           END SELECT
2618
2619        ENDIF
2620
2621    END SUBROUTINE usm_average_3d_data
2622
2623
2624
2625!------------------------------------------------------------------------------!
2626! Description:
2627! ------------
2628!> Set internal Neumann boundary condition at outer soil grid points
2629!> for temperature and humidity.
2630!------------------------------------------------------------------------------!
2631 SUBROUTINE usm_boundary_condition
2632 
2633    IMPLICIT NONE
2634
2635    INTEGER(iwp) :: i      !< grid index x-direction
2636    INTEGER(iwp) :: ioff   !< offset index x-direction indicating location of soil grid point
2637    INTEGER(iwp) :: j      !< grid index y-direction
2638    INTEGER(iwp) :: joff   !< offset index x-direction indicating location of soil grid point
2639    INTEGER(iwp) :: k      !< grid index z-direction
2640    INTEGER(iwp) :: koff   !< offset index x-direction indicating location of soil grid point
2641    INTEGER(iwp) :: l      !< running index surface-orientation
2642    INTEGER(iwp) :: m      !< running index surface elements
2643
2644    koff = surf_usm_h%koff
2645    DO  m = 1, surf_usm_h%ns
2646       i = surf_usm_h%i(m)
2647       j = surf_usm_h%j(m)
2648       k = surf_usm_h%k(m)
2649       pt(k+koff,j,i) = pt(k,j,i)
2650    ENDDO
2651
2652    DO  l = 0, 3
2653       ioff = surf_usm_v(l)%ioff
2654       joff = surf_usm_v(l)%joff
2655       DO  m = 1, surf_usm_v(l)%ns
2656          i = surf_usm_v(l)%i(m)
2657          j = surf_usm_v(l)%j(m)
2658          k = surf_usm_v(l)%k(m)
2659          pt(k,j+joff,i+ioff) = pt(k,j,i)
2660       ENDDO
2661    ENDDO
2662
2663 END SUBROUTINE usm_boundary_condition
2664
2665
2666!------------------------------------------------------------------------------!
2667!
2668! Description:
2669! ------------
2670!> Subroutine checks variables and assigns units.
2671!> It is called out from subroutine check_parameters.
2672!------------------------------------------------------------------------------!
2673    SUBROUTINE usm_check_data_output( variable, unit )
2674
2675        IMPLICIT NONE
2676
2677        CHARACTER(LEN=*),INTENT(IN)    ::  variable   !<
2678        CHARACTER(LEN=*),INTENT(OUT)   ::  unit       !<
2679
2680        INTEGER(iwp)                                  :: i,j,l        !< index
2681        CHARACTER(LEN=2)                              :: ls
2682        CHARACTER(LEN=varnamelength)                  :: var          !< TRIM(variable)
2683        INTEGER(iwp), PARAMETER                       :: nl1 = 16     !< number of directional usm variables
2684        CHARACTER(LEN=varnamelength), DIMENSION(nl1)  :: varlist1 = & !< list of directional usm variables
2685                  (/'usm_wshf                      ', &
2686                    'usm_wghf                      ', &
2687                    'usm_wghf_window               ', &
2688                    'usm_wghf_green                ', &
2689                    'usm_iwghf                     ', &
2690                    'usm_iwghf_window              ', &
2691                    'usm_surfz                     ', &
2692                    'usm_surfwintrans              ', &
2693                    'usm_surfcat                   ', &
2694                    'usm_surfalb                   ', &
2695                    'usm_surfemis                  ', &
2696                    'usm_t_surf_wall               ', &
2697                    'usm_t_surf_window             ', &
2698                    'usm_t_surf_green              ', &
2699                    'usm_t_green                   ', &
2700                    'usm_theta_10cm                '/)
2701
2702        INTEGER(iwp), PARAMETER                       :: nl2 = 3      !< number of directional layer usm variables
2703        CHARACTER(LEN=varnamelength), DIMENSION(nl2)  :: varlist2 = & !< list of directional layer usm variables
2704                  (/'usm_t_wall                    ', &
2705                    'usm_t_window                  ', &
2706                    'usm_t_green                   '/)
2707
2708        INTEGER(iwp), PARAMETER                       :: nd = 5     !< number of directions
2709        CHARACTER(LEN=6), DIMENSION(nd), PARAMETER  :: dirname = &  !< direction names
2710                  (/'_roof ','_south','_north','_west ','_east '/)
2711        LOGICAL                                       :: lfound     !< flag if the variable is found
2712
2713
2714        lfound = .FALSE.
2715
2716        var = TRIM(variable)
2717
2718!--     check if variable exists
2719!       directional variables
2720        DO i = 1, nl1
2721           DO j = 1, nd
2722              IF ( TRIM(var) == TRIM(varlist1(i))//TRIM(dirname(j)) ) THEN
2723                 lfound = .TRUE.
2724                 EXIT
2725              ENDIF
2726              IF ( lfound ) EXIT
2727           ENDDO
2728        ENDDO
2729        IF ( lfound ) GOTO 10
2730!       directional layer variables
2731        DO i = 1, nl2
2732           DO j = 1, nd
2733              DO l = nzb_wall, nzt_wall
2734                 WRITE(ls,'(A1,I1)') '_',l
2735                 IF ( TRIM(var) == TRIM(varlist2(i))//TRIM(ls)//TRIM(dirname(j)) ) THEN
2736                    lfound = .TRUE.
2737                    EXIT
2738                 ENDIF
2739              ENDDO
2740              IF ( lfound ) EXIT
2741           ENDDO
2742        ENDDO
2743        IF ( .NOT.  lfound ) THEN
2744           unit = 'illegal'
2745           RETURN
2746        ENDIF
274710      CONTINUE
2748
2749        IF ( var(1:9)  == 'usm_wshf_'  .OR.  var(1:9) == 'usm_wghf_' .OR.                 &
2750             var(1:16) == 'usm_wghf_window_' .OR. var(1:15) == 'usm_wghf_green_' .OR.     &
2751             var(1:10) == 'usm_iwghf_' .OR. var(1:17) == 'usm_iwghf_window_'    .OR.      &
2752             var(1:17) == 'usm_surfwintrans_' .OR.                                        &
2753             var(1:9)  == 'usm_qsws_'  .OR.  var(1:13)  == 'usm_qsws_veg_'  .OR.          &
2754             var(1:13) == 'usm_qsws_liq_' ) THEN
2755            unit = 'W/m2'
2756        ELSE IF ( var(1:15) == 'usm_t_surf_wall'   .OR.  var(1:10) == 'usm_t_wall' .OR.   &
2757                  var(1:12) == 'usm_t_window' .OR. var(1:17) == 'usm_t_surf_window' .OR.  &
2758                  var(1:16) == 'usm_t_surf_green'  .OR.                                   &
2759                  var(1:11) == 'usm_t_green' .OR.  var(1:7) == 'usm_swc' .OR.             &
2760                  var(1:14) == 'usm_theta_10cm' )  THEN
2761            unit = 'K'
2762        ELSE IF ( var(1:9) == 'usm_surfz'  .OR.  var(1:11) == 'usm_surfcat'  .OR.         &
2763                  var(1:11) == 'usm_surfalb'  .OR.  var(1:12) == 'usm_surfemis'  )  THEN
2764            unit = '1'
2765        ELSE
2766            unit = 'illegal'
2767        ENDIF
2768
2769    END SUBROUTINE usm_check_data_output
2770
2771
2772!------------------------------------------------------------------------------!
2773! Description:
2774! ------------
2775!> Check parameters routine for urban surface model
2776!------------------------------------------------------------------------------!
2777    SUBROUTINE usm_check_parameters
2778   
2779       USE control_parameters,                                                 &
2780           ONLY:  bc_pt_b, bc_q_b, constant_flux_layer, large_scale_forcing,   &
2781                  lsf_surf, topography
2782
2783!
2784!--    Dirichlet boundary conditions are required as the surface fluxes are
2785!--    calculated from the temperature/humidity gradients in the urban surface
2786!--    model
2787       IF ( bc_pt_b == 'neumann'   .OR.   bc_q_b == 'neumann' )  THEN
2788          message_string = 'urban surface model requires setting of '//        &
2789                           'bc_pt_b = "dirichlet" and '//                      &
2790                           'bc_q_b  = "dirichlet"'
2791          CALL message( 'usm_check_parameters', 'PA0590', 1, 2, 0, 6, 0 )
2792       ENDIF
2793
2794       IF ( .NOT.  constant_flux_layer )  THEN
2795          message_string = 'urban surface model requires '//                   &
2796                           'constant_flux_layer = .T.'
2797          CALL message( 'usm_check_parameters', 'PA0084', 1, 2, 0, 6, 0 )
2798       ENDIF
2799
2800       IF (  .NOT.  radiation )  THEN
2801          message_string = 'urban surface model requires '//                   &
2802                           'the radiation model to be switched on'
2803          CALL message( 'usm_check_parameters', 'PA0084', 1, 2, 0, 6, 0 )
2804       ENDIF
2805!       
2806!--    Surface forcing has to be disabled for LSF in case of enabled
2807!--    urban surface module
2808       IF ( large_scale_forcing )  THEN
2809          lsf_surf = .FALSE.
2810       ENDIF
2811!
2812!--    Topography
2813       IF ( topography == 'flat' )  THEN
2814          message_string = 'topography /= "flat" is required '//               &
2815                           'when using the urban surface model'
2816          CALL message( 'check_parameters', 'PA0592', 1, 2, 0, 6, 0 )
2817       ENDIF
2818!
2819!--    naheatlayers
2820       IF ( naheatlayers > nzt )  THEN
2821          message_string = 'number of anthropogenic heat layers '//            &
2822                           '"naheatlayers" can not be larger than'//           &
2823                           ' number of domain layers "nzt"'
2824          CALL message( 'check_parameters', 'PA0593', 1, 2, 0, 6, 0 )
2825       ENDIF
2826
2827    END SUBROUTINE usm_check_parameters
2828
2829
2830!------------------------------------------------------------------------------!
2831!
2832! Description:
2833! ------------
2834!> Output of the 3D-arrays in netCDF and/or AVS format
2835!> for variables of urban_surface model.
2836!> It resorts the urban surface module output quantities from surf style
2837!> indexing into temporary 3D array with indices (i,j,k).
2838!> It is called from subroutine data_output_3d.
2839!------------------------------------------------------------------------------!
2840    SUBROUTINE usm_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
2841       
2842        IMPLICIT NONE
2843
2844        INTEGER(iwp), INTENT(IN)       ::  av        !<
2845        CHARACTER (len=*), INTENT(IN)  ::  variable  !<
2846        INTEGER(iwp), INTENT(IN)       ::  nzb_do    !< lower limit of the data output (usually 0)
2847        INTEGER(iwp), INTENT(IN)       ::  nzt_do    !< vertical upper limit of the data output (usually nz_do3d)
2848        LOGICAL, INTENT(OUT)           ::  found     !<
2849        REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf   !< sp - it has to correspond to module data_output_3d
2850        REAL(wp), DIMENSION(nzb:nzt+1,nys:nyn,nxl:nxr)     ::  temp_pf    !< temp array for urban surface output procedure
2851       
2852        CHARACTER (len=varnamelength)                          :: var, surfid
2853        INTEGER(iwp), PARAMETER                                :: nd = 5
2854        CHARACTER(len=6), DIMENSION(0:nd-1), PARAMETER         :: dirname = (/ '_roof ', '_south', '_north', '_west ', '_east ' /)
2855        INTEGER(iwp), DIMENSION(0:nd-1), PARAMETER             :: dirint =  (/    iup_u, isouth_u, inorth_u,  iwest_u,  ieast_u /)
2856        INTEGER(iwp), DIMENSION(0:nd-1), PARAMETER             :: diridx =  (/       -1,        1,        0,        3,        2 /)
2857                                                                     !< index for surf_*_v: 0:3 = (North, South, East, West)
2858        INTEGER(iwp)                                           :: ids,idsint,idsidx,isurf,isvf,isurfs,isurflt,ipcgb
2859        INTEGER(iwp)                                           :: is,js,ks,i,j,k,iwl,istat, l, m
2860
2861        found = .TRUE.
2862        temp_pf = -1._wp
2863       
2864        ids = -1
2865        var = TRIM(variable)
2866        DO i = 0, nd-1
2867            k = len(TRIM(var))
2868            j = len(TRIM(dirname(i)))
2869            IF ( TRIM(var(k-j+1:k)) == TRIM(dirname(i)) )  THEN
2870                ids = i
2871                idsint = dirint(ids)
2872                idsidx = diridx(ids)
2873                var = var(:k-j)
2874                EXIT
2875            ENDIF
2876        ENDDO
2877        IF ( ids == -1 )  THEN
2878            var = TRIM(variable)
2879        ENDIF
2880        IF ( var(1:11) == 'usm_t_wall_'  .AND.  len(TRIM(var)) >= 12 )  THEN
2881!--         wall layers
2882            READ(var(12:12), '(I1)', iostat=istat ) iwl
2883            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
2884                var = var(1:10)
2885            ENDIF
2886        ENDIF
2887        IF ( var(1:13) == 'usm_t_window_'  .AND.  len(TRIM(var)) >= 14 )  THEN
2888!--         window layers
2889            READ(var(14:14), '(I1)', iostat=istat ) iwl
2890            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
2891                var = var(1:12)
2892            ENDIF
2893        ENDIF
2894        IF ( var(1:12) == 'usm_t_green_'  .AND.  len(TRIM(var)) >= 13 )  THEN
2895!--         green layers
2896            READ(var(13:13), '(I1)', iostat=istat ) iwl
2897            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
2898                var = var(1:11)
2899            ENDIF
2900        ENDIF
2901        IF ( var(1:8) == 'usm_swc_'  .AND.  len(TRIM(var)) >= 9 )  THEN
2902!--         green layers soil water content
2903            READ(var(9:9), '(I1)', iostat=istat ) iwl
2904            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
2905                var = var(1:7)
2906            ENDIF
2907        ENDIF
2908       
2909        SELECT CASE ( TRIM(var) )
2910
2911          CASE ( 'usm_surfz' )
2912!--           array of surface height (z)
2913              IF ( idsint == iup_u )  THEN
2914                 DO  m = 1, surf_usm_h%ns
2915                    i = surf_usm_h%i(m)
2916                    j = surf_usm_h%j(m)
2917                    k = surf_usm_h%k(m)
2918                    temp_pf(0,j,i) = MAX( temp_pf(0,j,i), REAL( k, kind=wp) )
2919                 ENDDO
2920              ELSE
2921                 l = idsidx
2922                 DO  m = 1, surf_usm_v(l)%ns
2923                    i = surf_usm_v(l)%i(m)
2924                    j = surf_usm_v(l)%j(m)
2925                    k = surf_usm_v(l)%k(m)
2926                    temp_pf(0,j,i) = MAX( temp_pf(0,j,i), REAL( k, kind=wp) + 1.0_wp )
2927                 ENDDO
2928              ENDIF
2929
2930          CASE ( 'usm_surfcat' )
2931!--           surface category
2932              IF ( idsint == iup_u )  THEN
2933                 DO  m = 1, surf_usm_h%ns
2934                    i = surf_usm_h%i(m)
2935                    j = surf_usm_h%j(m)
2936                    k = surf_usm_h%k(m)
2937                    temp_pf(k,j,i) = surf_usm_h%surface_types(m)
2938                 ENDDO
2939              ELSE
2940                 l = idsidx
2941                 DO  m = 1, surf_usm_v(l)%ns
2942                    i = surf_usm_v(l)%i(m)
2943                    j = surf_usm_v(l)%j(m)
2944                    k = surf_usm_v(l)%k(m)
2945                    temp_pf(k,j,i) = surf_usm_v(l)%surface_types(m)
2946                 ENDDO
2947              ENDIF
2948             
2949          CASE ( 'usm_surfalb' )
2950!--           surface albedo, weighted average
2951              IF ( idsint == iup_u )  THEN
2952                 DO  m = 1, surf_usm_h%ns
2953                    i = surf_usm_h%i(m)
2954                    j = surf_usm_h%j(m)
2955                    k = surf_usm_h%k(m)
2956                    temp_pf(k,j,i) = surf_usm_h%frac(ind_veg_wall,m)     *     &
2957                                     surf_usm_h%albedo(ind_veg_wall,m)  +      &
2958                                     surf_usm_h%frac(ind_pav_green,m)    *     &
2959                                     surf_usm_h%albedo(ind_pav_green,m) +      &
2960                                     surf_usm_h%frac(ind_wat_win,m)      *     &
2961                                     surf_usm_h%albedo(ind_wat_win,m)
2962                 ENDDO
2963              ELSE
2964                 l = idsidx
2965                 DO  m = 1, surf_usm_v(l)%ns
2966                    i = surf_usm_v(l)%i(m)
2967                    j = surf_usm_v(l)%j(m)
2968                    k = surf_usm_v(l)%k(m)
2969                    temp_pf(k,j,i) = surf_usm_v(l)%frac(ind_veg_wall,m)     *  &
2970                                     surf_usm_v(l)%albedo(ind_veg_wall,m)  +   &
2971                                     surf_usm_v(l)%frac(ind_pav_green,m)    *  &
2972                                     surf_usm_v(l)%albedo(ind_pav_green,m) +   &
2973                                     surf_usm_v(l)%frac(ind_wat_win,m)      *  &
2974                                     surf_usm_v(l)%albedo(ind_wat_win,m)
2975                 ENDDO
2976              ENDIF
2977             
2978          CASE ( 'usm_surfemis' )
2979!--           surface emissivity, weighted average
2980              IF ( idsint == iup_u )  THEN
2981                 DO  m = 1, surf_usm_h%ns
2982                    i = surf_usm_h%i(m)
2983                    j = surf_usm_h%j(m)
2984                    k = surf_usm_h%k(m)
2985                    temp_pf(k,j,i) =  surf_usm_h%frac(ind_veg_wall,m)      *   &
2986                                      surf_usm_h%emissivity(ind_veg_wall,m)  + &
2987                                      surf_usm_h%frac(ind_pav_green,m)     *   &
2988                                      surf_usm_h%emissivity(ind_pav_green,m) + &
2989                                      surf_usm_h%frac(ind_wat_win,m)       *   &
2990                                      surf_usm_h%emissivity(ind_wat_win,m)
2991                 ENDDO
2992              ELSE
2993                 l = idsidx
2994                 DO  m = 1, surf_usm_v(l)%ns
2995                    i = surf_usm_v(l)%i(m)
2996                    j = surf_usm_v(l)%j(m)
2997                    k = surf_usm_v(l)%k(m)
2998                    temp_pf(k,j,i) = surf_usm_v(l)%frac(ind_veg_wall,m)       *&
2999                                     surf_usm_v(l)%emissivity(ind_veg_wall,m) +&
3000                                     surf_usm_v(l)%frac(ind_pav_green,m)      *&
3001                                     surf_usm_v(l)%emissivity(ind_pav_green,m)+&
3002                                     surf_usm_v(l)%frac(ind_wat_win,m)        *&
3003                                     surf_usm_v(l)%emissivity(ind_wat_win,m)
3004                 ENDDO
3005              ENDIF
3006
3007          CASE ( 'usm_surfwintrans' )
3008!--           transmissivity window tiles
3009              IF ( idsint == iup_u )  THEN
3010                 DO  m = 1, surf_usm_h%ns
3011                    i = surf_usm_h%i(m)
3012                    j = surf_usm_h%j(m)
3013                    k = surf_usm_h%k(m)
3014                    temp_pf(k,j,i) = surf_usm_h%transmissivity(m)
3015                 ENDDO
3016              ELSE
3017                 l = idsidx
3018                 DO  m = 1, surf_usm_v(l)%ns
3019                    i = surf_usm_v(l)%i(m)
3020                    j = surf_usm_v(l)%j(m)
3021                    k = surf_usm_v(l)%k(m)
3022                    temp_pf(k,j,i) = surf_usm_v(l)%transmissivity(m)
3023                 ENDDO
3024              ENDIF
3025
3026          CASE ( 'usm_wshf' )
3027!--           array of sensible heat flux from surfaces
3028              IF ( av == 0 )  THEN
3029                 IF ( idsint == iup_u )  THEN
3030                    DO  m = 1, surf_usm_h%ns
3031                       i = surf_usm_h%i(m)
3032                       j = surf_usm_h%j(m)
3033                       k = surf_usm_h%k(m)
3034                       temp_pf(k,j,i) = surf_usm_h%wshf_eb(m)
3035                    ENDDO
3036                 ELSE
3037                    l = idsidx
3038                    DO  m = 1, surf_usm_v(l)%ns
3039                       i = surf_usm_v(l)%i(m)
3040                       j = surf_usm_v(l)%j(m)
3041                       k = surf_usm_v(l)%k(m)
3042                       temp_pf(k,j,i) = surf_usm_v(l)%wshf_eb(m)
3043                    ENDDO
3044                 ENDIF
3045              ELSE
3046                 IF ( idsint == iup_u )  THEN
3047                    DO  m = 1, surf_usm_h%ns
3048                       i = surf_usm_h%i(m)
3049                       j = surf_usm_h%j(m)
3050                       k = surf_usm_h%k(m)
3051                       temp_pf(k,j,i) = surf_usm_h%wshf_eb_av(m)
3052                    ENDDO
3053                 ELSE
3054                    l = idsidx
3055                    DO  m = 1, surf_usm_v(l)%ns
3056                       i = surf_usm_v(l)%i(m)
3057                       j = surf_usm_v(l)%j(m)
3058                       k = surf_usm_v(l)%k(m)
3059                       temp_pf(k,j,i) = surf_usm_v(l)%wshf_eb_av(m)
3060                    ENDDO
3061                 ENDIF
3062              ENDIF
3063             
3064             
3065          CASE ( 'usm_qsws' )
3066!--           array of latent heat flux from surfaces
3067              IF ( av == 0 )  THEN
3068                 IF ( idsint == iup_u )  THEN
3069                    DO  m = 1, surf_usm_h%ns
3070                       i = surf_usm_h%i(m)
3071                       j = surf_usm_h%j(m)
3072                       k = surf_usm_h%k(m)
3073                       temp_pf(k,j,i) = surf_usm_h%qsws_eb(m)
3074                    ENDDO
3075                 ELSE
3076                    l = idsidx
3077                    DO  m = 1, surf_usm_v(l)%ns
3078                       i = surf_usm_v(l)%i(m)
3079                       j = surf_usm_v(l)%j(m)
3080                       k = surf_usm_v(l)%k(m)
3081                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_eb(m)
3082                    ENDDO
3083                 ENDIF
3084              ELSE
3085                 IF ( idsint == iup_u )  THEN
3086                    DO  m = 1, surf_usm_h%ns
3087                       i = surf_usm_h%i(m)
3088                       j = surf_usm_h%j(m)
3089                       k = surf_usm_h%k(m)
3090                       temp_pf(k,j,i) = surf_usm_h%qsws_eb_av(m)
3091                    ENDDO
3092                 ELSE
3093                    l = idsidx
3094                    DO  m = 1, surf_usm_v(l)%ns
3095                       i = surf_usm_v(l)%i(m)
3096                       j = surf_usm_v(l)%j(m)
3097                       k = surf_usm_v(l)%k(m)
3098                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_eb_av(m)
3099                    ENDDO
3100                 ENDIF
3101              ENDIF
3102             
3103          CASE ( 'usm_qsws_veg' )
3104!--           array of latent heat flux from vegetation surfaces
3105              IF ( av == 0 )  THEN
3106                 IF ( idsint == iup_u )  THEN
3107                    DO  m = 1, surf_usm_h%ns
3108                       i = surf_usm_h%i(m)
3109                       j = surf_usm_h%j(m)
3110                       k = surf_usm_h%k(m)
3111                       temp_pf(k,j,i) = surf_usm_h%qsws_veg(m)
3112                    ENDDO
3113                 ELSE
3114                    l = idsidx
3115                    DO  m = 1, surf_usm_v(l)%ns
3116                       i = surf_usm_v(l)%i(m)
3117                       j = surf_usm_v(l)%j(m)
3118                       k = surf_usm_v(l)%k(m)
3119                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_veg(m)
3120                    ENDDO
3121                 ENDIF
3122              ELSE
3123                 IF ( idsint == iup_u )  THEN
3124                    DO  m = 1, surf_usm_h%ns
3125                       i = surf_usm_h%i(m)
3126                       j = surf_usm_h%j(m)
3127                       k = surf_usm_h%k(m)
3128                       temp_pf(k,j,i) = surf_usm_h%qsws_veg_av(m)
3129                    ENDDO
3130                 ELSE
3131                    l = idsidx
3132                    DO  m = 1, surf_usm_v(l)%ns
3133                       i = surf_usm_v(l)%i(m)
3134                       j = surf_usm_v(l)%j(m)
3135                       k = surf_usm_v(l)%k(m)
3136                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_veg_av(m)
3137                    ENDDO
3138                 ENDIF
3139              ENDIF
3140             
3141          CASE ( 'usm_qsws_liq' )
3142!--           array of latent heat flux from surfaces with liquid
3143              IF ( av == 0 )  THEN
3144                 IF ( idsint == iup_u )  THEN
3145                    DO  m = 1, surf_usm_h%ns
3146                       i = surf_usm_h%i(m)
3147                       j = surf_usm_h%j(m)
3148                       k = surf_usm_h%k(m)
3149                       temp_pf(k,j,i) = surf_usm_h%qsws_liq(m)
3150                    ENDDO
3151                 ELSE
3152                    l = idsidx
3153                    DO  m = 1, surf_usm_v(l)%ns
3154                       i = surf_usm_v(l)%i(m)
3155                       j = surf_usm_v(l)%j(m)
3156                       k = surf_usm_v(l)%k(m)
3157                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_liq(m)
3158                    ENDDO
3159                 ENDIF
3160              ELSE
3161                 IF ( idsint == iup_u )  THEN
3162                    DO  m = 1, surf_usm_h%ns
3163                       i = surf_usm_h%i(m)
3164                       j = surf_usm_h%j(m)
3165                       k = surf_usm_h%k(m)
3166                       temp_pf(k,j,i) = surf_usm_h%qsws_liq_av(m)
3167                    ENDDO
3168                 ELSE
3169                    l = idsidx
3170                    DO  m = 1, surf_usm_v(l)%ns
3171                       i = surf_usm_v(l)%i(m)
3172                       j = surf_usm_v(l)%j(m)
3173                       k = surf_usm_v(l)%k(m)
3174                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_liq_av(m)
3175                    ENDDO
3176                 ENDIF
3177              ENDIF
3178
3179          CASE ( 'usm_wghf' )
3180!--           array of heat flux from ground (land, wall, roof)
3181              IF ( av == 0 )  THEN
3182                 IF ( idsint == iup_u )  THEN
3183                    DO  m = 1, surf_usm_h%ns
3184                       i = surf_usm_h%i(m)
3185                       j = surf_usm_h%j(m)
3186                       k = surf_usm_h%k(m)
3187                       temp_pf(k,j,i) = surf_usm_h%wghf_eb(m)
3188                    ENDDO
3189                 ELSE
3190                    l = idsidx
3191                    DO  m = 1, surf_usm_v(l)%ns
3192                       i = surf_usm_v(l)%i(m)
3193                       j = surf_usm_v(l)%j(m)
3194                       k = surf_usm_v(l)%k(m)
3195                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb(m)
3196                    ENDDO
3197                 ENDIF
3198              ELSE
3199                 IF ( idsint == iup_u )  THEN
3200                    DO  m = 1, surf_usm_h%ns
3201                       i = surf_usm_h%i(m)
3202                       j = surf_usm_h%j(m)
3203                       k = surf_usm_h%k(m)
3204                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_av(m)
3205                    ENDDO
3206                 ELSE
3207                    l = idsidx
3208                    DO  m = 1, surf_usm_v(l)%ns
3209                       i = surf_usm_v(l)%i(m)
3210                       j = surf_usm_v(l)%j(m)
3211                       k = surf_usm_v(l)%k(m)
3212                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_av(m)
3213                    ENDDO
3214                 ENDIF
3215              ENDIF
3216
3217          CASE ( 'usm_wghf_window' )
3218!--           array of heat flux from window ground (land, wall, roof)
3219
3220              IF ( av == 0 )  THEN
3221                 IF ( idsint == iup_u )  THEN
3222                    DO  m = 1, surf_usm_h%ns
3223                       i = surf_usm_h%i(m)
3224                       j = surf_usm_h%j(m)
3225                       k = surf_usm_h%k(m)
3226                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_window(m)
3227                    ENDDO
3228                 ELSE
3229                    l = idsidx
3230                    DO  m = 1, surf_usm_v(l)%ns
3231                       i = surf_usm_v(l)%i(m)
3232                       j = surf_usm_v(l)%j(m)
3233                       k = surf_usm_v(l)%k(m)
3234                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_window(m)
3235                    ENDDO
3236                 ENDIF
3237              ELSE
3238                 IF ( idsint == iup_u )  THEN
3239                    DO  m = 1, surf_usm_h%ns
3240                       i = surf_usm_h%i(m)
3241                       j = surf_usm_h%j(m)
3242                       k = surf_usm_h%k(m)
3243                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_window_av(m)
3244                    ENDDO
3245                 ELSE
3246                    l = idsidx
3247                    DO  m = 1, surf_usm_v(l)%ns
3248                       i = surf_usm_v(l)%i(m)
3249                       j = surf_usm_v(l)%j(m)
3250                       k = surf_usm_v(l)%k(m)
3251                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_window_av(m)
3252                    ENDDO
3253                 ENDIF
3254              ENDIF
3255
3256          CASE ( 'usm_wghf_green' )
3257!--           array of heat flux from green ground (land, wall, roof)
3258
3259              IF ( av == 0 )  THEN
3260                 IF ( idsint == iup_u )  THEN
3261                    DO  m = 1, surf_usm_h%ns
3262                       i = surf_usm_h%i(m)
3263                       j = surf_usm_h%j(m)
3264                       k = surf_usm_h%k(m)
3265                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_green(m)
3266                    ENDDO
3267                 ELSE
3268                    l = idsidx
3269                    DO  m = 1, surf_usm_v(l)%ns
3270                       i = surf_usm_v(l)%i(m)
3271                       j = surf_usm_v(l)%j(m)
3272                       k = surf_usm_v(l)%k(m)
3273                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_green(m)
3274                    ENDDO
3275                 ENDIF
3276              ELSE
3277                 IF ( idsint == iup_u )  THEN
3278                    DO  m = 1, surf_usm_h%ns
3279                       i = surf_usm_h%i(m)
3280                       j = surf_usm_h%j(m)
3281                       k = surf_usm_h%k(m)
3282                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_green_av(m)
3283                    ENDDO
3284                 ELSE
3285                    l = idsidx
3286                    DO  m = 1, surf_usm_v(l)%ns
3287                       i = surf_usm_v(l)%i(m)
3288                       j = surf_usm_v(l)%j(m)
3289                       k = surf_usm_v(l)%k(m)
3290                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_green_av(m)
3291                    ENDDO
3292                 ENDIF
3293              ENDIF
3294
3295          CASE ( 'usm_iwghf' )
3296!--           array of heat flux from indoor ground (land, wall, roof)
3297              IF ( av == 0 )  THEN
3298                 IF ( idsint == iup_u )  THEN
3299                    DO  m = 1, surf_usm_h%ns
3300                       i = surf_usm_h%i(m)
3301                       j = surf_usm_h%j(m)
3302                       k = surf_usm_h%k(m)
3303                       temp_pf(k,j,i) = surf_usm_h%iwghf_eb(m)
3304                    ENDDO
3305                 ELSE
3306                    l = idsidx
3307                    DO  m = 1, surf_usm_v(l)%ns
3308                       i = surf_usm_v(l)%i(m)
3309                       j = surf_usm_v(l)%j(m)
3310                       k = surf_usm_v(l)%k(m)
3311                       temp_pf(k,j,i) = surf_usm_v(l)%iwghf_eb(m)
3312                    ENDDO
3313                 ENDIF
3314              ELSE
3315                 IF ( idsint == iup_u )  THEN
3316                    DO  m = 1, surf_usm_h%ns
3317                       i = surf_usm_h%i(m)
3318                       j = surf_usm_h%j(m)
3319                       k = surf_usm_h%k(m)
3320                       temp_pf(k,j,i) = surf_usm_h%iwghf_eb_av(m)
3321                    ENDDO
3322                 ELSE
3323                    l = idsidx
3324                    DO  m = 1, surf_usm_v(l)%ns
3325                       i = surf_usm_v(l)%i(m)
3326                       j = surf_usm_v(l)%j(m)
3327                       k = surf_usm_v(l)%k(m)
3328                       temp_pf(k,j,i) = surf_usm_v(l)%iwghf_eb_av(m)
3329                    ENDDO
3330                 ENDIF
3331              ENDIF
3332
3333          CASE ( 'usm_iwghf_window' )
3334!--           array of heat flux from indoor window ground (land, wall, roof)
3335
3336              IF ( av == 0 )  THEN
3337                 IF ( idsint == iup_u )  THEN
3338                    DO  m = 1, surf_usm_h%ns
3339                       i = surf_usm_h%i(m)
3340                       j = surf_usm_h%j(m)
3341                       k = surf_usm_h%k(m)
3342                       temp_pf(k,j,i) = surf_usm_h%iwghf_eb_window(m)
3343                    ENDDO
3344                 ELSE
3345                    l = idsidx
3346                    DO  m = 1, surf_usm_v(l)%ns
3347                       i = surf_usm_v(l)%i(m)
3348                       j = surf_usm_v(l)%j(m)
3349                       k = surf_usm_v(l)%k(m)
3350                       temp_pf(k,j,i) = surf_usm_v(l)%iwghf_eb_window(m)
3351                    ENDDO
3352                 ENDIF
3353              ELSE
3354                 IF ( idsint == iup_u )  THEN
3355                    DO  m = 1, surf_usm_h%ns
3356                       i = surf_usm_h%i(m)
3357                       j = surf_usm_h%j(m)
3358                       k = surf_usm_h%k(m)
3359                       temp_pf(k,j,i) = surf_usm_h%iwghf_eb_window_av(m)
3360                    ENDDO
3361                 ELSE
3362                    l = idsidx
3363                    DO  m = 1, surf_usm_v(l)%ns
3364                       i = surf_usm_v(l)%i(m)
3365                       j = surf_usm_v(l)%j(m)
3366                       k = surf_usm_v(l)%k(m)
3367                       temp_pf(k,j,i) = surf_usm_v(l)%iwghf_eb_window_av(m)
3368                    ENDDO
3369                 ENDIF
3370              ENDIF
3371             
3372          CASE ( 'usm_t_surf_wall' )
3373!--           surface temperature for surfaces
3374              IF ( av == 0 )  THEN
3375                 IF ( idsint == iup_u )  THEN
3376                    DO  m = 1, surf_usm_h%ns
3377                       i = surf_usm_h%i(m)
3378                       j = surf_usm_h%j(m)
3379                       k = surf_usm_h%k(m)
3380                       temp_pf(k,j,i) = t_surf_wall_h(m)
3381                    ENDDO
3382                 ELSE
3383                    l = idsidx
3384                    DO  m = 1, surf_usm_v(l)%ns
3385                       i = surf_usm_v(l)%i(m)
3386                       j = surf_usm_v(l)%j(m)
3387                       k = surf_usm_v(l)%k(m)
3388                       temp_pf(k,j,i) = t_surf_wall_v(l)%t(m)
3389                    ENDDO
3390                 ENDIF
3391              ELSE
3392                 IF ( idsint == iup_u )  THEN
3393                    DO  m = 1, surf_usm_h%ns
3394                       i = surf_usm_h%i(m)
3395                       j = surf_usm_h%j(m)
3396                       k = surf_usm_h%k(m)
3397                       temp_pf(k,j,i) = surf_usm_h%t_surf_wall_av(m)
3398                    ENDDO
3399                 ELSE
3400                    l = idsidx
3401                    DO  m = 1, surf_usm_v(l)%ns
3402                       i = surf_usm_v(l)%i(m)
3403                       j = surf_usm_v(l)%j(m)
3404                       k = surf_usm_v(l)%k(m)
3405                       temp_pf(k,j,i) = surf_usm_v(l)%t_surf_wall_av(m)
3406                    ENDDO
3407                 ENDIF
3408              ENDIF
3409             
3410          CASE ( 'usm_t_surf_window' )
3411!--           surface temperature for window surfaces
3412
3413              IF ( av == 0 )  THEN
3414                 IF ( idsint == iup_u )  THEN
3415                    DO  m = 1, surf_usm_h%ns
3416                       i = surf_usm_h%i(m)
3417                       j = surf_usm_h%j(m)
3418                       k = surf_usm_h%k(m)
3419                       temp_pf(k,j,i) = t_surf_window_h(m)
3420                    ENDDO
3421