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

Last change on this file since 3418 was 3418, checked in by kanani, 5 years ago

Add green facades, update building data base, fix for thin walls in spinup

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