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

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

document last commit

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