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

Last change on this file since 3636 was 3636, checked in by raasch, 6 years ago

nopointer option removed

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