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

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

Move definition of building-surface properties from declaration block to an extra routine; avoid different type kinds

  • Property svn:keywords set to Id
File size: 552.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 3882 2019-04-10 11:08:06Z suehring $
30! Avoid different type kinds
31! Move definition of building-surface properties from declaration block
32! to an extra routine
33!
34! 3881 2019-04-10 09:31:22Z suehring
35! Revise determination of local ground-floor level height.
36! Make level 3 initalization conform with Palm-input-data standard
37! Move output of albedo and emissivity to radiation module
38!
39! 3832 2019-03-28 13:16:58Z raasch
40! instrumented with openmp directives
41!
42! 3824 2019-03-27 15:56:16Z pavelkrc
43! Remove unused imports
44!
45!
46! 3814 2019-03-26 08:40:31Z pavelkrc
47! unused subroutine commented out
48!
49! 3769 2019-02-28 10:16:49Z moh.hefny
50! removed unused variables
51!
52! 3767 2019-02-27 08:18:02Z raasch
53! unused variables removed from rrd-subroutines parameter list
54!
55! 3748 2019-02-18 10:38:31Z suehring
56! Revise conversion of waste-heat flux (do not divide by air density, will
57! be done in diffusion_s)
58!
59! 3745 2019-02-15 18:57:56Z suehring
60! - Remove internal flag indoor_model (is a global control parameter)
61! - add waste heat from buildings to the kinmatic heat flux
62! - consider waste heat in restart data
63! - remove unused USE statements
64!
65! 3744 2019-02-15 18:38:58Z suehring
66! fixed surface heat capacity in the building parameters
67! convert the file back to unix format
68!
69! 3730 2019-02-11 11:26:47Z moh.hefny
70! Formatting and clean-up (rvtils)
71!
72! 3710 2019-01-30 18:11:19Z suehring
73! Check if building type is set within a valid range.
74!
75! 3705 2019-01-29 19:56:39Z suehring
76! make nzb_wall public, required for virtual-measurements
77!
78! 3704 2019-01-29 19:51:41Z suehring
79! Some interface calls moved to module_interface + cleanup
80!
81! 3655 2019-01-07 16:51:22Z knoop
82! Implementation of the PALM module interface
83!
84! 3636 2018-12-19 13:48:34Z raasch
85! nopointer option removed
86!
87! 3614 2018-12-10 07:05:46Z raasch
88! unused variables removed
89!
90! 3607 2018-12-07 11:56:58Z suehring
91! Output of radiation-related quantities migrated to radiation_model_mod.
92!
93! 3597 2018-12-04 08:40:18Z maronga
94! Fixed calculation method of near surface air potential temperature at 10 cm
95! and moved to surface_layer_fluxes. Removed unnecessary _eb strings.
96!
97! 3524 2018-11-14 13:36:44Z raasch
98! bugfix concerning allocation of t_surf_wall_v
99!
100! 3502 2018-11-07 14:45:23Z suehring
101! Disable initialization of building roofs with ground-floor-level properties,
102! since this causes strong oscillations of surface temperature during the
103! spinup.
104!
105! 3469 2018-10-30 20:05:07Z kanani
106! Add missing PUBLIC variables for new indoor model
107!
108! 3449 2018-10-29 19:36:56Z suehring
109! Bugfix: Fix average arrays allocations in usm_3d_data_averaging (J.Resler)
110! Bugfix: Fix reading wall temperatures (J.Resler)
111! Bugfix: Fix treating of outputs for wall temperature and sky view factors (J.Resler)
112!
113!
114! 3435 2018-10-26 18:25:44Z gronemeier
115! Bugfix: allocate gamma_w_green_sat until nzt_wall+1
116!
117! 3418 2018-10-24 16:07:39Z kanani
118! (rvtils, srissman)
119! -Updated building databse, two green roof types (ind_green_type_roof)
120! -Latent heat flux for green walls and roofs, new output of latent heatflux
121!  and soil water content of green roof substrate
122! -t_surf changed to t_surf_wall
123! -Added namelist parameter usm_wall_mod for lower wall tendency
124!  of first two wall layers during spinup
125! -Window calculations deactivated during spinup
126!
127! 3382 2018-10-19 13:10:32Z knoop
128! Bugix: made array declaration Fortran Standard conform
129!
130! 3378 2018-10-19 12:34:59Z kanani
131! merge from radiation branch (r3362) into trunk
132! (moh.hefny):
133! - check the requested output variables if they are correct
134! - added unscheduled_radiation_calls switch to control force_radiation_call
135! - minor formate changes
136!
137! 3371 2018-10-18 13:40:12Z knoop
138! Set flag indicating that albedo at urban surfaces is already initialized
139!
140! 3347 2018-10-15 14:21:08Z suehring
141! Enable USM initialization with default building parameters in case no static
142! input file exist.
143!
144! 3343 2018-10-15 10:38:52Z suehring
145! Add output variables usm_rad_pc_inlw, usm_rad_pc_insw*
146!
147! 3274 2018-09-24 15:42:55Z knoop
148! Modularization of all bulk cloud physics code components
149!
150! 3248 2018-09-14 09:42:06Z sward
151! Minor formating changes
152!
153! 3246 2018-09-13 15:14:50Z sward
154! Added error handling for input namelist via parin_fail_message
155!
156! 3241 2018-09-12 15:02:00Z raasch
157! unused variables removed
158!
159! 3223 2018-08-30 13:48:17Z suehring
160! Bugfix for commit 3222
161!
162! 3222 2018-08-30 13:35:35Z suehring
163! Introduction of surface array for type and its name
164!
165! 3203 2018-08-23 10:48:36Z suehring
166! Revise bulk parameter for emissivity at ground-floor level
167!
168! 3196 2018-08-13 12:26:14Z maronga
169! Added maximum aerodynamic resistance of 300 for horiztonal surfaces.
170!
171! 3176 2018-07-26 17:12:48Z suehring
172! Bugfix, update virtual potential surface temparture, else heat fluxes on
173! roofs might become unphysical
174!
175! 3152 2018-07-19 13:26:52Z suehring
176! Initialize q_surface, which might be used in surface_layer_fluxes
177!
178! 3151 2018-07-19 08:45:38Z raasch
179! remaining preprocessor define strings __check removed
180!
181! 3136 2018-07-16 14:48:21Z suehring
182! Limit also roughness length for heat and moisture where necessary
183!
184! 3123 2018-07-12 16:21:53Z suehring
185! Correct working precision for INTEGER number
186!
187! 3115 2018-07-10 12:49:26Z suehring
188! Additional building type to represent bridges
189!
190! 3091 2018-06-28 16:20:35Z suehring
191! - Limit aerodynamic resistance at vertical walls.
192! - Add check for local roughness length not exceeding surface-layer height and
193!   limit roughness length where necessary.
194!
195! 3065 2018-06-12 07:03:02Z Giersch
196! Unused array dxdir was removed, dz was replaced by dzu to consider vertical
197! grid stretching
198!
199! 3049 2018-05-29 13:52:36Z Giersch
200! Error messages revised
201!
202! 3045 2018-05-28 07:55:41Z Giersch
203! Error message added
204!
205! 3029 2018-05-23 12:19:17Z raasch
206! bugfix: close unit 151 instead of 90
207!
208! 3014 2018-05-09 08:42:38Z maronga
209! Added pc_transpiration_rate
210!
211! 2977 2018-04-17 10:27:57Z kanani
212! Implement changes from branch radiation (r2948-2971) with minor modifications.
213! (moh.hefny):
214! Extended exn for all model domain height to avoid the need to get nzut.
215!
216! 2963 2018-04-12 14:47:44Z suehring
217! Introduce index for vegetation/wall, pavement/green-wall and water/window
218! surfaces, for clearer access of surface fraction, albedo, emissivity, etc. .
219!
220! 2943 2018-04-03 16:17:10Z suehring
221! Calculate exner function at all height levels and remove some un-used
222! variables.
223!
224! 2932 2018-03-26 09:39:22Z maronga
225! renamed urban_surface_par to urban_surface_parameters
226!
227! 2921 2018-03-22 15:05:23Z Giersch
228! The activation of spinup has been moved to parin
229!
230! 2920 2018-03-22 11:22:01Z kanani
231! Remove unused pcbl, npcbl from ONLY list
232! moh.hefny:
233! Fixed bugs introduced by new structures and by moving radiation interaction
234! into radiation_model_mod.f90.
235! Bugfix: usm data output 3D didn't respect directions
236!
237! 2906 2018-03-19 08:56:40Z Giersch
238! Local variable ids has to be initialized with a value of -1 in
239! usm_3d_data_averaging
240!
241! 2894 2018-03-15 09:17:58Z Giersch
242! Calculations of the index range of the subdomain on file which overlaps with
243! the current subdomain are already done in read_restart_data_mod,
244! usm_read/write_restart_data have been renamed to usm_r/wrd_local, variable
245! named found has been introduced for checking if restart data was found,
246! reading of restart strings has been moved completely to
247! read_restart_data_mod, usm_rrd_local is already inside the overlap loop
248! programmed in read_restart_data_mod, SAVE attribute added where necessary,
249! deallocation and allocation of some arrays have been changed to take care of
250! different restart files that can be opened (index i), the marker *** end usm
251! *** is not necessary anymore, strings and their respective lengths are
252! written out and read now in case of restart runs to get rid of prescribed
253! character lengths
254!
255! 2805 2018-02-14 17:00:09Z suehring
256! Initialization of resistances.
257!
258! 2797 2018-02-08 13:24:35Z suehring
259! Comment concerning output of ground-heat flux added.
260!
261! 2766 2018-01-22 17:17:47Z kanani
262! Removed redundant commas, added some blanks
263!
264! 2765 2018-01-22 11:34:58Z maronga
265! Major bugfix in calculation of f_shf. Adjustment of roughness lengths in
266! building_pars
267!
268! 2750 2018-01-15 16:26:51Z knoop
269! Move flag plant canopy to modules
270!
271! 2737 2018-01-11 14:58:11Z kanani
272! Removed unused variables t_surf_whole...
273!
274! 2735 2018-01-11 12:01:27Z suehring
275! resistances are saved in surface attributes
276!
277! 2723 2018-01-05 09:27:03Z maronga
278! Bugfix for spinups (end_time was increased twice in case of LSM + USM runs)
279!
280! 2720 2018-01-02 16:27:15Z kanani
281! Correction of comment
282!
283! 2718 2018-01-02 08:49:38Z maronga
284! Corrected "Former revisions" section
285!
286! 2705 2017-12-18 11:26:23Z maronga
287! Changes from last commit documented
288!
289! 2703 2017-12-15 20:12:38Z maronga
290! Workaround for calculation of r_a
291!
292! 2696 2017-12-14 17:12:51Z kanani
293! - Change in file header (GPL part)
294! - Bugfix in calculation of pt_surface and related fluxes. (BM)
295! - Do not write surface temperatures onto pt array as this might cause
296!   problems with nesting. (MS)
297! - Revised calculation of pt1 (now done in surface_layer_fluxes).
298!   Bugfix, f_shf_window and f_shf_green were not set at vertical surface
299!   elements. (MS)
300! - merged with branch ebsolver
301!   green building surfaces do not evaporate yet
302!   properties of green wall layers and window layers are taken from wall layers
303!   this input data is missing. (RvT)
304! - Merged with branch radiation (developed by Mohamed Salim)
305! - Revised initialization. (MS)
306! - Rename emiss_surf into emissivity, roughness_wall into z0, albedo_surf into
307!   albedo. (MS)
308! - Move first call of usm_radiatin from usm_init to init_3d_model
309! - fixed problem with near surface temperature
310! - added near surface temperature pt_10cm_h(m), pt_10cm_v(l)%t(m)
311! - does not work with temp profile including stability, ol
312!   pt_10cm = pt1 now
313! - merged with 2357 bugfix, error message for nopointer version
314! - added indoor model coupling with wall heat flux
315! - added green substrate/ dry vegetation layer for buildings
316! - merged with 2232 new surface-type structure
317! - added transmissivity of window tiles
318! - added MOSAIK tile approach for 3 different surfaces (RvT)
319!
320! 2583 2017-10-26 13:58:38Z knoop
321! Bugfix: reverted MPI_Win_allocate_cptr introduction in last commit
322!
323! 2582 2017-10-26 13:19:46Z hellstea
324! Workaround for gnufortran compiler added in usm_calc_svf. CALL MPI_Win_allocate is
325! replaced by CALL MPI_Win_allocate_cptr if defined ( __gnufortran ).
326!
327! 2544 2017-10-13 18:09:32Z maronga
328! Date and time quantities are now read from date_and_time_mod. Solar constant is
329! read from radiation_model_mod
330!
331! 2516 2017-10-04 11:03:04Z suehring
332! Remove tabs
333!
334! 2514 2017-10-04 09:52:37Z suehring
335! upper bounds of 3d output changed from nx+1,ny+1 to nx,ny
336! no output of ghost layer data
337!
338! 2350 2017-08-15 11:48:26Z kanani
339! Bugfix and error message for nopointer version.
340! Additional "! defined(__nopointer)" as workaround to enable compilation of
341! nopointer version.
342!
343! 2318 2017-07-20 17:27:44Z suehring
344! Get topography top index via Function call
345!
346! 2317 2017-07-20 17:27:19Z suehring
347! Bugfix: adjust output of shf. Added support for spinups
348!
349! 2287 2017-06-15 16:46:30Z suehring
350! Bugfix in determination topography-top index
351!
352! 2269 2017-06-09 11:57:32Z suehring
353! Enable restart runs with different number of PEs
354! Bugfixes nopointer branch
355!
356! 2258 2017-06-08 07:55:13Z suehring
357! Bugfix, add pre-preprocessor directives to enable non-parrallel mode
358!
359! 2233 2017-05-30 18:08:54Z suehring
360!
361! 2232 2017-05-30 17:47:52Z suehring
362! Adjustments according to new surface-type structure. Remove usm_wall_heat_flux;
363! insteat, heat fluxes are directly applied in diffusion_s.
364!
365! 2213 2017-04-24 15:10:35Z kanani
366! Removal of output quantities usm_lad and usm_canopy_hr
367!
368! 2209 2017-04-19 09:34:46Z kanani
369! cpp switch __mpi3 removed,
370! minor formatting,
371! small bugfix for division by zero (Krc)
372!
373! 2113 2017-01-12 13:40:46Z kanani
374! cpp switch __mpi3 added for MPI-3 standard code (Ketelsen)
375!
376! 2071 2016-11-17 11:22:14Z maronga
377! Small bugfix (Resler)
378!
379! 2031 2016-10-21 15:11:58Z knoop
380! renamed variable rho to rho_ocean
381!
382! 2024 2016-10-12 16:42:37Z kanani
383! Bugfixes in deallocation of array plantt and reading of csf/csfsurf,
384! optimization of MPI-RMA operations,
385! declaration of pcbl as integer,
386! renamed usm_radnet -> usm_rad_net, usm_canopy_khf -> usm_canopy_hr,
387! splitted arrays svf -> svf & csf, svfsurf -> svfsurf & csfsurf,
388! use of new control parameter varnamelength,
389! added output variables usm_rad_ressw, usm_rad_reslw,
390! minor formatting changes,
391! minor optimizations.
392!
393! 2011 2016-09-19 17:29:57Z kanani
394! Major reformatting according to PALM coding standard (comments, blanks,
395! alphabetical ordering, etc.),
396! removed debug_prints,
397! removed auxiliary SUBROUTINE get_usm_info, instead, USM flag urban_surface is
398! defined in MODULE control_parameters (modules.f90) to avoid circular
399! dependencies,
400! renamed canopy_heat_flux to pc_heating_rate, as meaning of quantity changed.
401!
402! 2007 2016-08-24 15:47:17Z kanani
403! Initial revision
404!
405!
406! Description:
407! ------------
408! 2016/6/9 - Initial version of the USM (Urban Surface Model)
409!            authors: Jaroslav Resler, Pavel Krc
410!                     (Czech Technical University in Prague and Institute of
411!                      Computer Science of the Czech Academy of Sciences, Prague)
412!            with contributions: Michal Belda, Nina Benesova, Ondrej Vlcek
413!            partly inspired by PALM LSM (B. Maronga)
414!            parameterizations of Ra checked with TUF3D (E. S. Krayenhoff)
415!> Module for Urban Surface Model (USM)
416!> The module includes:
417!>    1. radiation model with direct/diffuse radiation, shading, reflections
418!>       and integration with plant canopy
419!>    2. wall and wall surface model
420!>    3. surface layer energy balance
421!>    4. anthropogenic heat (only from transportation so far)
422!>    5. necessary auxiliary subroutines (reading inputs, writing outputs,
423!>       restart simulations, ...)
424!> It also make use of standard radiation and integrates it into
425!> urban surface model.
426!>
427!> Further work:
428!> -------------
429!> 1. Remove global arrays surfouts, surfoutl and only keep track of radiosity
430!>    from surfaces that are visible from local surfaces (i.e. there is a SVF
431!>    where target is local). To do that, radiosity will be exchanged after each
432!>    reflection step using MPI_Alltoall instead of current MPI_Allgather.
433!>
434!> 2. Temporarily large values of surface heat flux can be observed, up to
435!>    1.2 Km/s, which seem to be not realistic.
436!>
437!> @todo Output of _av variables in case of restarts
438!> @todo Revise flux conversion in energy-balance solver
439!> @todo Check optimizations for RMA operations
440!> @todo Alternatives for MPI_WIN_ALLOCATE? (causes problems with openmpi)
441!> @todo Check for load imbalances in CPU measures, e.g. for exchange_horiz_prog
442!>       factor 3 between min and max time
443!> @todo Check divisions in wtend (etc.) calculations for possible division
444!>       by zero, e.g. in case fraq(0,m) + fraq(1,m) = 0?!
445!> @todo Use unit 90 for OPEN/CLOSE of input files (FK)
446!> @todo Move plant canopy stuff into plant canopy code
447!------------------------------------------------------------------------------!
448 MODULE urban_surface_mod
449
450    USE arrays_3d,                                                             &
451        ONLY:  hyp, zu, pt, p, u, v, w, tend, exner, hyrho, prr, q, ql, vpt
452
453    USE calc_mean_profile_mod,                                                 &
454        ONLY:  calc_mean_profile
455
456    USE basic_constants_and_equations_mod,                                     &
457        ONLY:  c_p, g, kappa, pi, r_d, rho_l, l_v, sigma_sb
458
459    USE control_parameters,                                                    &
460        ONLY:  coupling_start_time, topography, dt_3d, humidity, indoor_model, &
461               intermediate_timestep_count, initializing_actions,              &
462               intermediate_timestep_count_max, simulated_time, end_time,      &
463               timestep_scheme, tsc, coupling_char, io_blocks, io_group,       &
464               message_string, time_since_reference_point, surface_pressure,   &
465               pt_surface, large_scale_forcing, lsf_surf, spinup,              &
466               spinup_pt_mean, spinup_time, time_do3d, dt_do3d,                &
467               average_count_3d, varnamelength, urban_surface, dz
468
469    USE bulk_cloud_model_mod,                                                  &
470        ONLY: bulk_cloud_model, precipitation
471               
472    USE cpulog,                                                                &
473        ONLY:  cpu_log, log_point, log_point_s
474
475    USE date_and_time_mod,                                                     &
476        ONLY:  time_utc_init
477
478    USE grid_variables,                                                        &
479        ONLY:  dx, dy, ddx, ddy, ddx2, ddy2
480
481    USE indices,                                                               &
482        ONLY:  nx, ny, nnx, nny, nnz, nxl, nxlg, nxr, nxrg, nyn, nyng, nys,    &
483               nysg, nzb, nzt, nbgp, wall_flags_0
484
485    USE, INTRINSIC :: iso_c_binding 
486
487    USE kinds
488             
489    USE pegrid
490       
491    USE radiation_model_mod,                                                   &
492        ONLY:  albedo_type, radiation_interaction,                             &
493               radiation, rad_sw_in, rad_lw_in, rad_sw_out, rad_lw_out,        &
494               force_radiation_call, iup_u, inorth_u, isouth_u, ieast_u,       &
495               iwest_u, iup_l, inorth_l, isouth_l, ieast_l, iwest_l, id,       &
496               iz, iy, ix,  nsurf, idsvf, ndsvf,                               &
497               idcsf, ndcsf, kdcsf, pct,                                       &
498               nz_urban_b, nz_urban_t, unscheduled_radiation_calls
499
500    USE statistics,                                                            &
501        ONLY:  hom, statistic_regions
502
503    USE surface_mod,                                                           &
504        ONLY:  get_topography_top_index_ji, get_topography_top_index,          &
505               ind_pav_green, ind_veg_wall, ind_wat_win, surf_usm_h,           &
506               surf_usm_v, surface_restore_elements
507
508
509    IMPLICIT NONE
510
511!
512!-- USM model constants
513
514    REAL(wp), PARAMETER ::                     &
515              b_ch               = 6.04_wp,    &  !< Clapp & Hornberger exponent
516              lambda_h_green_dry = 0.19_wp,    &  !< heat conductivity for dry soil   
517              lambda_h_green_sm  = 3.44_wp,    &  !< heat conductivity of the soil matrix
518              lambda_h_water     = 0.57_wp,    &  !< heat conductivity of water
519              psi_sat            = -0.388_wp,  &  !< soil matrix potential at saturation
520              rho_c_soil         = 2.19E6_wp,  &  !< volumetric heat capacity of soil
521              rho_c_water        = 4.20E6_wp      !< volumetric heat capacity of water
522!               m_max_depth        = 0.0002_wp     ! Maximum capacity of the water reservoir (m)
523
524!
525!-- Soil parameters I           alpha_vg,      l_vg_green,    n_vg, gamma_w_green_sat
526    REAL(wp), DIMENSION(0:3,1:7), PARAMETER :: soil_pars = RESHAPE( (/     &
527                                 3.83_wp,  1.250_wp, 1.38_wp,  6.94E-6_wp, &  !< soil 1
528                                 3.14_wp, -2.342_wp, 1.28_wp,  1.16E-6_wp, &  !< soil 2
529                                 0.83_wp, -0.588_wp, 1.25_wp,  0.26E-6_wp, &  !< soil 3
530                                 3.67_wp, -1.977_wp, 1.10_wp,  2.87E-6_wp, &  !< soil 4
531                                 2.65_wp,  2.500_wp, 1.10_wp,  1.74E-6_wp, &  !< soil 5
532                                 1.30_wp,  0.400_wp, 1.20_wp,  0.93E-6_wp, &  !< soil 6
533                                 0.00_wp,  0.00_wp,  0.00_wp,  0.57E-6_wp  &  !< soil 7
534                                 /), (/ 4, 7 /) )
535
536!
537!-- Soil parameters II              swc_sat,     fc,   wilt,    swc_res 
538    REAL(wp), DIMENSION(0:3,1:7), PARAMETER :: m_soil_pars = RESHAPE( (/ &
539                                 0.403_wp, 0.244_wp, 0.059_wp, 0.025_wp, &  !< soil 1
540                                 0.439_wp, 0.347_wp, 0.151_wp, 0.010_wp, &  !< soil 2
541                                 0.430_wp, 0.383_wp, 0.133_wp, 0.010_wp, &  !< soil 3
542                                 0.520_wp, 0.448_wp, 0.279_wp, 0.010_wp, &  !< soil 4
543                                 0.614_wp, 0.541_wp, 0.335_wp, 0.010_wp, &  !< soil 5
544                                 0.766_wp, 0.663_wp, 0.267_wp, 0.010_wp, &  !< soil 6
545                                 0.472_wp, 0.323_wp, 0.171_wp, 0.000_wp  &  !< soil 7
546                                 /), (/ 4, 7 /) )
547!
548!-- value 9999999.9_wp -> generic available or user-defined value must be set
549!-- otherwise -> no generic variable and user setting is optional
550    REAL(wp) :: alpha_vangenuchten = 9999999.9_wp,      &  !< NAMELIST alpha_vg
551                field_capacity = 9999999.9_wp,          &  !< NAMELIST fc
552                hydraulic_conductivity = 9999999.9_wp,  &  !< NAMELIST gamma_w_green_sat
553                l_vangenuchten = 9999999.9_wp,          &  !< NAMELIST l_vg
554                n_vangenuchten = 9999999.9_wp,          &  !< NAMELIST n_vg
555                residual_moisture = 9999999.9_wp,       &  !< NAMELIST m_res
556                saturation_moisture = 9999999.9_wp,     &  !< NAMELIST m_sat
557                wilting_point = 9999999.9_wp               !< NAMELIST m_wilt
558   
559!
560!-- configuration parameters (they can be setup in PALM config)
561    LOGICAL ::  usm_material_model = .TRUE.        !< flag parameter indicating wheather the  model of heat in materials is used
562    LOGICAL ::  usm_anthropogenic_heat = .FALSE.   !< flag parameter indicating wheather the anthropogenic heat sources
563                                                   !< (e.g.transportation) are used
564    LOGICAL ::  force_radiation_call_l = .FALSE.   !< flag parameter for unscheduled radiation model calls
565    LOGICAL ::  read_wall_temp_3d = .FALSE.
566    LOGICAL ::  usm_wall_mod = .FALSE.             !< reduces conductivity of the first 2 wall layers by factor 0.1
567
568
569    INTEGER(iwp) ::  building_type = 1               !< default building type (preleminary setting)
570    INTEGER(iwp) ::  land_category = 2               !< default category for land surface
571    INTEGER(iwp) ::  wall_category = 2               !< default category for wall surface over pedestrian zone
572    INTEGER(iwp) ::  pedestrian_category = 2         !< default category for wall surface in pedestrian zone
573    INTEGER(iwp) ::  roof_category = 2               !< default category for root surface
574    REAL(wp)     ::  roughness_concrete = 0.001_wp   !< roughness length of average concrete surface
575!
576!-- Indices of input attributes in building_pars for (above) ground floor level
577    INTEGER(iwp) ::  ind_alb_wall_agfl     = 38   !< index in input list for albedo_type of wall above ground floor level
578    INTEGER(iwp) ::  ind_alb_wall_gfl      = 66   !< index in input list for albedo_type of wall ground floor level
579    INTEGER(iwp) ::  ind_alb_wall_r        = 101  !< index in input list for albedo_type of wall roof
580    INTEGER(iwp) ::  ind_alb_green_agfl    = 39   !< index in input list for albedo_type of green above ground floor level
581    INTEGER(iwp) ::  ind_alb_green_gfl     = 78   !< index in input list for albedo_type of green ground floor level
582    INTEGER(iwp) ::  ind_alb_green_r       = 117  !< index in input list for albedo_type of green roof
583    INTEGER(iwp) ::  ind_alb_win_agfl      = 40   !< index in input list for albedo_type of window fraction above ground floor level
584    INTEGER(iwp) ::  ind_alb_win_gfl       = 77   !< index in input list for albedo_type of window fraction ground floor level
585    INTEGER(iwp) ::  ind_alb_win_r         = 115  !< index in input list for albedo_type of window fraction roof
586    INTEGER(iwp) ::  ind_c_surface         = 45   !< index in input list for heat capacity wall surface
587    INTEGER(iwp) ::  ind_c_surface_green   = 48   !< index in input list for heat capacity green surface
588    INTEGER(iwp) ::  ind_c_surface_win     = 47   !< index in input list for heat capacity window surface
589    INTEGER(iwp) ::  ind_emis_wall_agfl    = 14   !< index in input list for wall emissivity, above ground floor level
590    INTEGER(iwp) ::  ind_emis_wall_gfl     = 32   !< index in input list for wall emissivity, ground floor level
591    INTEGER(iwp) ::  ind_emis_wall_r       = 100  !< index in input list for wall emissivity, roof
592    INTEGER(iwp) ::  ind_emis_green_agfl   = 15   !< index in input list for green emissivity, above ground floor level
593    INTEGER(iwp) ::  ind_emis_green_gfl    = 34   !< index in input list for green emissivity, ground floor level
594    INTEGER(iwp) ::  ind_emis_green_r      = 116  !< index in input list for green emissivity, roof
595    INTEGER(iwp) ::  ind_emis_win_agfl     = 16   !< index in input list for window emissivity, above ground floor level
596    INTEGER(iwp) ::  ind_emis_win_gfl      = 33   !< index in input list for window emissivity, ground floor level
597    INTEGER(iwp) ::  ind_emis_win_r        = 113  !< index in input list for window emissivity, roof
598    INTEGER(iwp) ::  ind_gflh              = 20   !< index in input list for ground floor level height
599    INTEGER(iwp) ::  ind_green_frac_w_agfl = 2    !< index in input list for green fraction on wall, above ground floor level
600    INTEGER(iwp) ::  ind_green_frac_w_gfl  = 23   !< index in input list for green fraction on wall, ground floor level
601    INTEGER(iwp) ::  ind_green_frac_r_agfl = 3    !< index in input list for green fraction on roof, above ground floor level
602    INTEGER(iwp) ::  ind_green_frac_r_gfl  = 24   !< index in input list for green fraction on roof, ground floor level
603    INTEGER(iwp) ::  ind_hc1_agfl          = 6    !< index in input list for heat capacity at first wall layer,
604                                                  !< above ground floor level
605    INTEGER(iwp) ::  ind_hc1_gfl           = 26   !< index in input list for heat capacity at first wall layer, ground floor level
606    INTEGER(iwp) ::  ind_hc1_wall_r        = 94   !< index in input list for heat capacity at first wall layer, roof
607    INTEGER(iwp) ::  ind_hc1_win_agfl      = 83   !< index in input list for heat capacity at first window layer,
608                                                  !< above ground floor level
609    INTEGER(iwp) ::  ind_hc1_win_gfl       = 71   !< index in input list for heat capacity at first window layer,
610                                                  !< ground floor level
611    INTEGER(iwp) ::  ind_hc1_win_r         = 107  !< index in input list for heat capacity at first window layer, roof
612    INTEGER(iwp) ::  ind_hc2_agfl          = 7    !< index in input list for heat capacity at second wall layer,
613                                                  !< above ground floor level
614    INTEGER(iwp) ::  ind_hc2_gfl           = 27   !< index in input list for heat capacity at second wall layer, ground floor level
615    INTEGER(iwp) ::  ind_hc2_wall_r        = 95   !< index in input list for heat capacity at second wall layer, roof
616    INTEGER(iwp) ::  ind_hc2_win_agfl      = 84   !< index in input list for heat capacity at second window layer,
617                                                  !< above ground floor level
618    INTEGER(iwp) ::  ind_hc2_win_gfl       = 72   !< index in input list for heat capacity at second window layer,
619                                                  !< ground floor level
620    INTEGER(iwp) ::  ind_hc2_win_r         = 108  !< index in input list for heat capacity at second window layer, roof
621    INTEGER(iwp) ::  ind_hc3_agfl          = 8    !< index in input list for heat capacity at third wall layer,
622                                                  !< above ground floor level
623    INTEGER(iwp) ::  ind_hc3_gfl           = 28   !< index in input list for heat capacity at third wall layer, ground floor level
624    INTEGER(iwp) ::  ind_hc3_wall_r        = 96   !< index in input list for heat capacity at third wall layer, roof
625    INTEGER(iwp) ::  ind_hc3_win_agfl      = 85   !< index in input list for heat capacity at third window layer,
626                                                  !< above ground floor level
627    INTEGER(iwp) ::  ind_hc3_win_gfl       = 73   !< index in input list for heat capacity at third window layer,
628                                                  !< ground floor level
629    INTEGER(iwp) ::  ind_hc3_win_r         = 109  !< index in input list for heat capacity at third window layer, roof
630    INTEGER(iwp) ::  ind_indoor_target_temp_summer = 12
631    INTEGER(iwp) ::  ind_indoor_target_temp_winter = 13
632    INTEGER(iwp) ::  ind_lai_r_agfl        = 4    !< index in input list for LAI on roof, above ground floor level
633    INTEGER(iwp) ::  ind_lai_r_gfl         = 4  !< index in input list for LAI on roof, ground floor level
634    INTEGER(iwp) ::  ind_lai_w_agfl        = 5    !< index in input list for LAI on wall, above ground floor level
635    INTEGER(iwp) ::  ind_lai_w_gfl         = 25   !< index in input list for LAI on wall, ground floor level
636    INTEGER(iwp) ::  ind_lambda_surf       = 46   !< index in input list for thermal conductivity of wall surface
637    INTEGER(iwp) ::  ind_lambda_surf_green = 50   !< index in input list for thermal conductivity of green surface
638    INTEGER(iwp) ::  ind_lambda_surf_win   = 49   !< index in input list for thermal conductivity of window surface
639    INTEGER(iwp) ::  ind_tc1_agfl          = 9    !< index in input list for thermal conductivity at first wall layer,
640                                                  !< above ground floor level
641    INTEGER(iwp) ::  ind_tc1_gfl           = 29   !< index in input list for thermal conductivity at first wall layer,
642                                                  !< ground floor level
643    INTEGER(iwp) ::  ind_tc1_wall_r        = 97   !< index in input list for thermal conductivity at first wall layer, roof
644    INTEGER(iwp) ::  ind_tc1_win_agfl      = 86   !< index in input list for thermal conductivity at first window layer,
645                                                  !< above ground floor level
646    INTEGER(iwp) ::  ind_tc1_win_gfl       = 74   !< index in input list for thermal conductivity at first window layer,
647                                                  !< ground floor level
648    INTEGER(iwp) ::  ind_tc1_win_r         = 110  !< index in input list for thermal conductivity at first window layer, roof
649    INTEGER(iwp) ::  ind_tc2_agfl          = 10   !< index in input list for thermal conductivity at second wall layer,
650                                                  !< above ground floor level
651    INTEGER(iwp) ::  ind_tc2_gfl           = 30   !< index in input list for thermal conductivity at second wall layer,
652                                                  !< ground floor level
653    INTEGER(iwp) ::  ind_tc2_wall_r        = 98   !< index in input list for thermal conductivity at second wall layer, roof
654    INTEGER(iwp) ::  ind_tc2_win_agfl      = 87   !< index in input list for thermal conductivity at second window layer,
655                                                  !< above ground floor level
656    INTEGER(iwp) ::  ind_tc2_win_gfl       = 75   !< index in input list for thermal conductivity at second window layer,
657                                                  !< ground floor level
658    INTEGER(iwp) ::  ind_tc2_win_r         = 111  !< index in input list for thermal conductivity at second window layer,
659                                                  !< ground floor level
660    INTEGER(iwp) ::  ind_tc3_agfl          = 11   !< index in input list for thermal conductivity at third wall layer,
661                                                  !< above ground floor level
662    INTEGER(iwp) ::  ind_tc3_gfl           = 31   !< index in input list for thermal conductivity at third wall layer,
663                                                  !< ground floor level
664    INTEGER(iwp) ::  ind_tc3_wall_r        = 99   !< index in input list for thermal conductivity at third wall layer, roof
665    INTEGER(iwp) ::  ind_tc3_win_agfl      = 88   !< index in input list for thermal conductivity at third window layer,
666                                                  !< above ground floor level
667    INTEGER(iwp) ::  ind_tc3_win_gfl       = 76   !< index in input list for thermal conductivity at third window layer,
668                                                  !< ground floor level
669    INTEGER(iwp) ::  ind_tc3_win_r         = 112  !< index in input list for thermal conductivity at third window layer, roof
670    INTEGER(iwp) ::  ind_thick_1_agfl      = 41   !< index for wall layer thickness - 1st layer above ground floor level
671    INTEGER(iwp) ::  ind_thick_1_gfl       = 62   !< index for wall layer thickness - 1st layer ground floor level
672    INTEGER(iwp) ::  ind_thick_1_wall_r    = 90   !< index for wall layer thickness - 1st layer roof
673    INTEGER(iwp) ::  ind_thick_1_win_agfl  = 79   !< index for window layer thickness - 1st layer above ground floor level
674    INTEGER(iwp) ::  ind_thick_1_win_gfl   = 67   !< index for window layer thickness - 1st layer ground floor level
675    INTEGER(iwp) ::  ind_thick_1_win_r     = 103  !< index for window layer thickness - 1st layer roof
676    INTEGER(iwp) ::  ind_thick_2_agfl      = 42   !< index for wall layer thickness - 2nd layer above ground floor level
677    INTEGER(iwp) ::  ind_thick_2_gfl       = 63   !< index for wall layer thickness - 2nd layer ground floor level
678    INTEGER(iwp) ::  ind_thick_2_wall_r    = 91   !< index for wall layer thickness - 2nd layer roof
679    INTEGER(iwp) ::  ind_thick_2_win_agfl  = 80   !< index for window layer thickness - 2nd layer above ground floor level
680    INTEGER(iwp) ::  ind_thick_2_win_gfl   = 68   !< index for window layer thickness - 2nd layer ground floor level
681    INTEGER(iwp) ::  ind_thick_2_win_r     = 104  !< index for window layer thickness - 2nd layer roof
682    INTEGER(iwp) ::  ind_thick_3_agfl      = 43   !< index for wall layer thickness - 3rd layer above ground floor level
683    INTEGER(iwp) ::  ind_thick_3_gfl       = 64   !< index for wall layer thickness - 3rd layer ground floor level
684    INTEGER(iwp) ::  ind_thick_3_wall_r    = 92   !< index for wall layer thickness - 3rd layer roof
685    INTEGER(iwp) ::  ind_thick_3_win_agfl  = 81   !< index for window layer thickness - 3rd layer above ground floor level
686    INTEGER(iwp) ::  ind_thick_3_win_gfl   = 69   !< index for window layer thickness - 3rd layer ground floor level 
687    INTEGER(iwp) ::  ind_thick_3_win_r     = 105  !< index for window layer thickness - 3rd layer roof
688    INTEGER(iwp) ::  ind_thick_4_agfl      = 44   !< index for wall layer thickness - 4th layer above ground floor level
689    INTEGER(iwp) ::  ind_thick_4_gfl       = 65   !< index for wall layer thickness - 4th layer ground floor level
690    INTEGER(iwp) ::  ind_thick_4_wall_r    = 93   !< index for wall layer thickness - 4st layer roof
691    INTEGER(iwp) ::  ind_thick_4_win_agfl  = 82   !< index for window layer thickness - 4th layer above ground floor level
692    INTEGER(iwp) ::  ind_thick_4_win_gfl   = 70   !< index for window layer thickness - 4th layer ground floor level
693    INTEGER(iwp) ::  ind_thick_4_win_r     = 106  !< index for window layer thickness - 4th layer roof
694    INTEGER(iwp) ::  ind_trans_agfl        = 17   !< index in input list for window transmissivity, above ground floor level
695    INTEGER(iwp) ::  ind_trans_gfl         = 35   !< index in input list for window transmissivity, ground floor level
696    INTEGER(iwp) ::  ind_trans_r           = 114  !< index in input list for window transmissivity, roof
697    INTEGER(iwp) ::  ind_wall_frac_agfl    = 0    !< index in input list for wall fraction, above ground floor level
698    INTEGER(iwp) ::  ind_wall_frac_gfl     = 21   !< index in input list for wall fraction, ground floor level
699    INTEGER(iwp) ::  ind_wall_frac_r       = 89   !< index in input list for wall fraction, roof
700    INTEGER(iwp) ::  ind_win_frac_agfl     = 1    !< index in input list for window fraction, above ground floor level
701    INTEGER(iwp) ::  ind_win_frac_gfl      = 22   !< index in input list for window fraction, ground floor level
702    INTEGER(iwp) ::  ind_win_frac_r        = 102  !< index in input list for window fraction, roof
703    INTEGER(iwp) ::  ind_z0_agfl           = 18   !< index in input list for z0, above ground floor level
704    INTEGER(iwp) ::  ind_z0_gfl            = 36   !< index in input list for z0, ground floor level
705    INTEGER(iwp) ::  ind_z0qh_agfl         = 19   !< index in input list for z0h / z0q, above ground floor level
706    INTEGER(iwp) ::  ind_z0qh_gfl          = 37   !< index in input list for z0h / z0q, ground floor level
707    INTEGER(iwp) ::  ind_green_type_roof   = 118  !< index in input list for type of green roof
708
709
710    REAL(wp)  ::  roof_height_limit = 4.0_wp         !< height for distinguish between land surfaces and roofs
711    REAL(wp)  ::  ground_floor_level = 4.0_wp        !< default ground floor level
712
713
714    CHARACTER(37), DIMENSION(0:7), PARAMETER :: building_type_name = (/     &
715                                   'user-defined                         ', &  !< type 0
716                                   'residential - 1950                   ', &  !< type  1
717                                   'residential 1951 - 2000              ', &  !< type  2
718                                   'residential 2001 -                   ', &  !< type  3
719                                   'office - 1950                        ', &  !< type  4
720                                   'office 1951 - 2000                   ', &  !< type  5
721                                   'office 2001 -                        ', &  !< type  6
722                                   'bridges                              '  &  !< type  7
723                                                                     /)
724
725
726!
727!-- Building facade/wall/green/window properties (partly according to PIDS).
728!-- Initialization of building_pars is outsourced to usm_init_pars. This is
729!-- needed because of the huge number of attributes given in building_pars
730!-- (>700), while intel and gfortran compiler have hard limit of continuation
731!-- lines of 511.
732    REAL(wp), DIMENSION(0:133,1:7) ::  building_pars
733!
734!-- Type for surface temperatures at vertical walls. Is not necessary for horizontal walls.
735    TYPE t_surf_vertical
736       REAL(wp), DIMENSION(:), ALLOCATABLE         :: t
737    END TYPE t_surf_vertical
738!
739!-- Type for wall temperatures at vertical walls. Is not necessary for horizontal walls.
740    TYPE t_wall_vertical
741       REAL(wp), DIMENSION(:,:), ALLOCATABLE       :: t
742    END TYPE t_wall_vertical
743
744    TYPE surf_type_usm
745       REAL(wp), DIMENSION(:),   ALLOCATABLE ::  var_usm_1d  !< 1D prognostic variable
746       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  var_usm_2d  !< 2D prognostic variable
747    END TYPE surf_type_usm
748   
749    TYPE(surf_type_usm), POINTER  ::  m_liq_usm_h,        &  !< liquid water reservoir (m), horizontal surface elements
750                                      m_liq_usm_h_p          !< progn. liquid water reservoir (m), horizontal surface elements
751
752    TYPE(surf_type_usm), TARGET   ::  m_liq_usm_h_1,      &  !<
753                                      m_liq_usm_h_2          !<
754
755    TYPE(surf_type_usm), DIMENSION(:), POINTER  ::        &
756                                      m_liq_usm_v,        &  !< liquid water reservoir (m), vertical surface elements
757                                      m_liq_usm_v_p          !< progn. liquid water reservoir (m), vertical surface elements
758
759    TYPE(surf_type_usm), DIMENSION(0:3), TARGET   ::      &
760                                      m_liq_usm_v_1,      &  !<
761                                      m_liq_usm_v_2          !<
762
763    TYPE(surf_type_usm), TARGET ::  tm_liq_usm_h_m      !< liquid water reservoir tendency (m), horizontal surface elements
764    TYPE(surf_type_usm), DIMENSION(0:3), TARGET ::  tm_liq_usm_v_m      !< liquid water reservoir tendency (m),
765                                                                        !< vertical surface elements
766
767!
768!-- anthropogenic heat sources
769    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE        ::  aheat             !< daily average of anthropogenic heat (W/m2)
770    REAL(wp), DIMENSION(:,:), ALLOCATABLE          ::  aheatprof         !< diurnal profiles of anthropogenic heat
771                                                                         !< for particular layers
772    INTEGER(iwp)                                   ::  naheatlayers = 1  !< number of layers of anthropogenic heat
773
774!
775!-- wall surface model
776!-- wall surface model constants
777    INTEGER(iwp), PARAMETER                        :: nzb_wall = 0       !< inner side of the wall model (to be switched)
778    INTEGER(iwp), PARAMETER                        :: nzt_wall = 3       !< outer side of the wall model (to be switched)
779    INTEGER(iwp), PARAMETER                        :: nzw = 4            !< number of wall layers (fixed for now)
780
781    REAL(wp), DIMENSION(nzb_wall:nzt_wall)         :: zwn_default        = (/0.0242_wp, 0.0969_wp, 0.346_wp, 1.0_wp /)
782    REAL(wp), DIMENSION(nzb_wall:nzt_wall)         :: zwn_default_window = (/0.25_wp,   0.5_wp,    0.75_wp,  1.0_wp /)
783    REAL(wp), DIMENSION(nzb_wall:nzt_wall)         :: zwn_default_green  = (/0.25_wp,   0.5_wp,    0.75_wp,  1.0_wp /)
784                                                                         !< normalized soil, wall and roof, window and
785                                                                         !<green layer depths (m/m)
786
787    REAL(wp)                                       :: wall_inner_temperature   = 295.0_wp    !< temperature of the inner wall
788                                                                                             !< surface (~22 degrees C) (K)
789    REAL(wp)                                       :: roof_inner_temperature   = 295.0_wp    !< temperature of the inner roof
790                                                                                             !< surface (~22 degrees C) (K)
791    REAL(wp)                                       :: soil_inner_temperature   = 288.0_wp    !< temperature of the deep soil
792                                                                                             !< (~15 degrees C) (K)
793    REAL(wp)                                       :: window_inner_temperature = 295.0_wp    !< temperature of the inner window
794                                                                                             !< surface (~22 degrees C) (K)
795
796    REAL(wp)                                       :: m_total = 0.0_wp  !< weighted total water content of the soil (m3/m3)
797    INTEGER(iwp)                                   :: soil_type
798
799!
800!-- surface and material model variables for walls, ground, roofs
801    REAL(wp), DIMENSION(:), ALLOCATABLE            :: zwn                !< normalized wall layer depths (m)
802    REAL(wp), DIMENSION(:), ALLOCATABLE            :: zwn_window         !< normalized window layer depths (m)
803    REAL(wp), DIMENSION(:), ALLOCATABLE            :: zwn_green          !< normalized green layer depths (m)
804
805    REAL(wp), DIMENSION(:), POINTER                :: t_surf_wall_h
806    REAL(wp), DIMENSION(:), POINTER                :: t_surf_wall_h_p 
807    REAL(wp), DIMENSION(:), POINTER                :: t_surf_window_h
808    REAL(wp), DIMENSION(:), POINTER                :: t_surf_window_h_p 
809    REAL(wp), DIMENSION(:), POINTER                :: t_surf_green_h
810    REAL(wp), DIMENSION(:), POINTER                :: t_surf_green_h_p 
811
812    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_wall_h_1
813    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_wall_h_2
814    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_window_h_1
815    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_window_h_2
816    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_h_1
817    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_h_2
818
819    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_wall_v
820    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_wall_v_p
821    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_window_v
822    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_window_v_p
823    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_green_v
824    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_green_v_p
825
826    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_wall_v_1
827    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_wall_v_2
828    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_window_v_1
829    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_window_v_2
830    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_green_v_1
831    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_green_v_2
832
833!
834!-- Energy balance variables
835!-- parameters of the land, roof and wall surfaces
836
837    REAL(wp), DIMENSION(:,:), POINTER                :: t_wall_h, t_wall_h_p
838    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h_1, t_wall_h_2
839    REAL(wp), DIMENSION(:,:), POINTER                :: t_window_h, t_window_h_p
840    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_window_h_1, t_window_h_2
841    REAL(wp), DIMENSION(:,:), POINTER                :: t_green_h, t_green_h_p
842    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_green_h_1, t_green_h_2
843    REAL(wp), DIMENSION(:,:), POINTER                :: swc_h, rootfr_h, wilt_h, fc_h, swc_sat_h, swc_h_p, swc_res_h
844    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: swc_h_1, rootfr_h_1, &
845                                                        wilt_h_1, fc_h_1, swc_sat_h_1, swc_h_2, swc_res_h_1
846   
847
848    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: t_wall_v, t_wall_v_p
849    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v_1, t_wall_v_2
850    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: t_window_v, t_window_v_p
851    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_window_v_1, t_window_v_2
852    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: t_green_v, t_green_v_p
853    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v_1, t_green_v_2
854    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: swc_v, swc_v_p
855    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: swc_v_1, swc_v_2
856
857!
858!-- Surface and material parameters classes (surface_type)
859!-- albedo, emissivity, lambda_surf, roughness, thickness, volumetric heat capacity, thermal conductivity
860    INTEGER(iwp)                                   :: n_surface_types       !< number of the wall type categories
861    INTEGER(iwp), PARAMETER                        :: n_surface_params = 9  !< number of parameters for each type of the wall
862    INTEGER(iwp), PARAMETER                        :: ialbedo  = 1          !< albedo of the surface
863    INTEGER(iwp), PARAMETER                        :: iemiss   = 2          !< emissivity of the surface
864    INTEGER(iwp), PARAMETER                        :: ilambdas = 3          !< heat conductivity lambda S between surface
865                                                                            !< and material ( W m-2 K-1 )
866    INTEGER(iwp), PARAMETER                        :: irough   = 4          !< roughness length z0 for movements
867    INTEGER(iwp), PARAMETER                        :: iroughh  = 5          !< roughness length z0h for scalars
868                                                                            !< (heat, humidity,...)
869    INTEGER(iwp), PARAMETER                        :: icsurf   = 6          !< Surface skin layer heat capacity (J m-2 K-1 )
870    INTEGER(iwp), PARAMETER                        :: ithick   = 7          !< thickness of the surface (wall, roof, land)  ( m )
871    INTEGER(iwp), PARAMETER                        :: irhoC    = 8          !< volumetric heat capacity rho*C of
872                                                                            !< the material ( J m-3 K-1 )
873    INTEGER(iwp), PARAMETER                        :: ilambdah = 9          !< thermal conductivity lambda H
874                                                                            !< of the wall (W m-1 K-1 )
875    CHARACTER(12), DIMENSION(:), ALLOCATABLE       :: surface_type_names    !< names of wall types (used only for reports)
876    INTEGER(iwp), DIMENSION(:), ALLOCATABLE        :: surface_type_codes    !< codes of wall types
877    REAL(wp), DIMENSION(:,:), ALLOCATABLE          :: surface_params        !< parameters of wall types
878
879!
880!-- interfaces of subroutines accessed from outside of this module
881    INTERFACE usm_3d_data_averaging
882       MODULE PROCEDURE usm_3d_data_averaging
883    END INTERFACE usm_3d_data_averaging
884
885    INTERFACE usm_boundary_condition
886       MODULE PROCEDURE usm_boundary_condition
887    END INTERFACE usm_boundary_condition
888
889    INTERFACE usm_check_data_output
890       MODULE PROCEDURE usm_check_data_output
891    END INTERFACE usm_check_data_output
892   
893    INTERFACE usm_check_parameters
894       MODULE PROCEDURE usm_check_parameters
895    END INTERFACE usm_check_parameters
896   
897    INTERFACE usm_data_output_3d
898       MODULE PROCEDURE usm_data_output_3d
899    END INTERFACE usm_data_output_3d
900   
901    INTERFACE usm_define_netcdf_grid
902       MODULE PROCEDURE usm_define_netcdf_grid
903    END INTERFACE usm_define_netcdf_grid
904
905    INTERFACE usm_init
906       MODULE PROCEDURE usm_init
907    END INTERFACE usm_init
908
909    INTERFACE usm_init_arrays
910       MODULE PROCEDURE usm_init_arrays
911    END INTERFACE usm_init_arrays
912
913    INTERFACE usm_material_heat_model
914       MODULE PROCEDURE usm_material_heat_model
915    END INTERFACE usm_material_heat_model
916   
917    INTERFACE usm_green_heat_model
918       MODULE PROCEDURE usm_green_heat_model
919    END INTERFACE usm_green_heat_model
920   
921    INTERFACE usm_parin
922       MODULE PROCEDURE usm_parin
923    END INTERFACE usm_parin
924
925    INTERFACE usm_rrd_local 
926       MODULE PROCEDURE usm_rrd_local
927    END INTERFACE usm_rrd_local
928
929    INTERFACE usm_surface_energy_balance
930       MODULE PROCEDURE usm_surface_energy_balance
931    END INTERFACE usm_surface_energy_balance
932   
933    INTERFACE usm_swap_timelevel
934       MODULE PROCEDURE usm_swap_timelevel
935    END INTERFACE usm_swap_timelevel
936       
937    INTERFACE usm_wrd_local
938       MODULE PROCEDURE usm_wrd_local
939    END INTERFACE usm_wrd_local
940
941   
942    SAVE
943
944    PRIVATE 
945
946!
947!-- Public functions
948    PUBLIC usm_boundary_condition, usm_check_parameters, usm_init,               &
949           usm_rrd_local,                                                        & 
950           usm_surface_energy_balance, usm_material_heat_model,                  &
951           usm_swap_timelevel, usm_check_data_output, usm_3d_data_averaging,     &
952           usm_data_output_3d, usm_define_netcdf_grid, usm_parin,                &
953           usm_wrd_local, usm_init_arrays
954
955!
956!-- Public parameters, constants and initial values
957    PUBLIC usm_anthropogenic_heat, usm_material_model, usm_wall_mod, &
958           usm_green_heat_model, building_pars,                      &
959           nzb_wall, nzt_wall, t_wall_h, t_wall_v,                   &
960           t_window_h, t_window_v, building_type
961
962
963
964 CONTAINS
965
966!------------------------------------------------------------------------------!
967! Description:
968! ------------
969!> This subroutine creates the necessary indices of the urban surfaces
970!> and plant canopy and it allocates the needed arrays for USM
971!------------------------------------------------------------------------------!
972    SUBROUTINE usm_init_arrays
973   
974        IMPLICIT NONE
975       
976        INTEGER(iwp) ::  l
977
978        CALL location_message( 'initializing and allocating urban surfaces', .FALSE. )
979
980!
981!--     Allocate radiation arrays which are part of the new data type.
982!--     For horizontal surfaces.
983        ALLOCATE ( surf_usm_h%surfhf(1:surf_usm_h%ns)    )
984        ALLOCATE ( surf_usm_h%rad_net_l(1:surf_usm_h%ns) )
985!
986!--     For vertical surfaces
987        DO  l = 0, 3
988           ALLOCATE ( surf_usm_v(l)%surfhf(1:surf_usm_v(l)%ns)    )
989           ALLOCATE ( surf_usm_v(l)%rad_net_l(1:surf_usm_v(l)%ns) )
990        ENDDO
991
992!
993!--     Wall surface model
994!--     allocate arrays for wall surface model and define pointers
995!--     allocate array of wall types and wall parameters
996        ALLOCATE ( surf_usm_h%surface_types(1:surf_usm_h%ns)      )
997        ALLOCATE ( surf_usm_h%building_type(1:surf_usm_h%ns)      )
998        ALLOCATE ( surf_usm_h%building_type_name(1:surf_usm_h%ns) )
999        surf_usm_h%building_type      = 0
1000        surf_usm_h%building_type_name = 'none'
1001        DO  l = 0, 3
1002           ALLOCATE ( surf_usm_v(l)%surface_types(1:surf_usm_v(l)%ns)      )
1003           ALLOCATE ( surf_usm_v(l)%building_type(1:surf_usm_v(l)%ns)      )
1004           ALLOCATE ( surf_usm_v(l)%building_type_name(1:surf_usm_v(l)%ns) )
1005           surf_usm_v(l)%building_type      = 0
1006           surf_usm_v(l)%building_type_name = 'none'
1007        ENDDO
1008!
1009!--     Allocate albedo_type and albedo. Each surface element
1010!--     has 3 values, 0: wall fraction, 1: green fraction, 2: window fraction.
1011        ALLOCATE ( surf_usm_h%albedo_type(0:2,1:surf_usm_h%ns) )
1012        ALLOCATE ( surf_usm_h%albedo(0:2,1:surf_usm_h%ns)      )
1013        surf_usm_h%albedo_type = albedo_type
1014        DO  l = 0, 3
1015           ALLOCATE ( surf_usm_v(l)%albedo_type(0:2,1:surf_usm_v(l)%ns) )
1016           ALLOCATE ( surf_usm_v(l)%albedo(0:2,1:surf_usm_v(l)%ns)      )
1017           surf_usm_v(l)%albedo_type = albedo_type
1018        ENDDO       
1019
1020!
1021!--     Allocate indoor target temperature for summer and winter
1022        ALLOCATE ( surf_usm_h%target_temp_summer(1:surf_usm_h%ns) )
1023        ALLOCATE ( surf_usm_h%target_temp_winter(1:surf_usm_h%ns) )
1024        DO  l = 0, 3
1025           ALLOCATE ( surf_usm_v(l)%target_temp_summer(1:surf_usm_v(l)%ns) )
1026           ALLOCATE ( surf_usm_v(l)%target_temp_winter(1:surf_usm_v(l)%ns) )
1027        ENDDO
1028!
1029!--     In case the indoor model is applied, allocate memory for waste heat
1030!--     and indoor temperature.
1031        IF ( indoor_model )  THEN
1032           ALLOCATE ( surf_usm_h%waste_heat(1:surf_usm_h%ns) )
1033           surf_usm_h%waste_heat = 0.0_wp
1034           DO  l = 0, 3
1035              ALLOCATE ( surf_usm_v(l)%waste_heat(1:surf_usm_v(l)%ns) )
1036              surf_usm_v(l)%waste_heat = 0.0_wp
1037           ENDDO
1038        ENDIF
1039!
1040!--     Allocate flag indicating ground floor level surface elements
1041        ALLOCATE ( surf_usm_h%ground_level(1:surf_usm_h%ns) ) 
1042        DO  l = 0, 3
1043           ALLOCATE ( surf_usm_v(l)%ground_level(1:surf_usm_v(l)%ns) )
1044        ENDDO   
1045!
1046!--      Allocate arrays for relative surface fraction.
1047!--      0 - wall fraction, 1 - green fraction, 2 - window fraction
1048         ALLOCATE ( surf_usm_h%frac(0:2,1:surf_usm_h%ns) )
1049         surf_usm_h%frac = 0.0_wp
1050         DO  l = 0, 3
1051            ALLOCATE ( surf_usm_v(l)%frac(0:2,1:surf_usm_v(l)%ns) )
1052            surf_usm_v(l)%frac = 0.0_wp
1053         ENDDO
1054
1055!
1056!--     wall and roof surface parameters. First for horizontal surfaces
1057        ALLOCATE ( surf_usm_h%isroof_surf(1:surf_usm_h%ns)        )
1058        ALLOCATE ( surf_usm_h%lambda_surf(1:surf_usm_h%ns)        )
1059        ALLOCATE ( surf_usm_h%lambda_surf_window(1:surf_usm_h%ns) )
1060        ALLOCATE ( surf_usm_h%lambda_surf_green(1:surf_usm_h%ns)  )
1061        ALLOCATE ( surf_usm_h%c_surface(1:surf_usm_h%ns)          )
1062        ALLOCATE ( surf_usm_h%c_surface_window(1:surf_usm_h%ns)   )
1063        ALLOCATE ( surf_usm_h%c_surface_green(1:surf_usm_h%ns)    )
1064        ALLOCATE ( surf_usm_h%transmissivity(1:surf_usm_h%ns)     )
1065        ALLOCATE ( surf_usm_h%lai(1:surf_usm_h%ns)                )
1066        ALLOCATE ( surf_usm_h%emissivity(0:2,1:surf_usm_h%ns)     )
1067        ALLOCATE ( surf_usm_h%r_a(1:surf_usm_h%ns)                )
1068        ALLOCATE ( surf_usm_h%r_a_green(1:surf_usm_h%ns)          )
1069        ALLOCATE ( surf_usm_h%r_a_window(1:surf_usm_h%ns)         )
1070        ALLOCATE ( surf_usm_h%green_type_roof(1:surf_usm_h%ns)    )
1071        ALLOCATE ( surf_usm_h%r_s(1:surf_usm_h%ns)                )
1072       
1073!
1074!--     For vertical surfaces.
1075        DO  l = 0, 3
1076           ALLOCATE ( surf_usm_v(l)%lambda_surf(1:surf_usm_v(l)%ns)        )
1077           ALLOCATE ( surf_usm_v(l)%c_surface(1:surf_usm_v(l)%ns)          )
1078           ALLOCATE ( surf_usm_v(l)%lambda_surf_window(1:surf_usm_v(l)%ns) )
1079           ALLOCATE ( surf_usm_v(l)%c_surface_window(1:surf_usm_v(l)%ns)   )
1080           ALLOCATE ( surf_usm_v(l)%lambda_surf_green(1:surf_usm_v(l)%ns)  )
1081           ALLOCATE ( surf_usm_v(l)%c_surface_green(1:surf_usm_v(l)%ns)    )
1082           ALLOCATE ( surf_usm_v(l)%transmissivity(1:surf_usm_v(l)%ns)     )
1083           ALLOCATE ( surf_usm_v(l)%lai(1:surf_usm_v(l)%ns)                )
1084           ALLOCATE ( surf_usm_v(l)%emissivity(0:2,1:surf_usm_v(l)%ns)     )
1085           ALLOCATE ( surf_usm_v(l)%r_a(1:surf_usm_v(l)%ns)                )
1086           ALLOCATE ( surf_usm_v(l)%r_a_green(1:surf_usm_v(l)%ns)          )
1087           ALLOCATE ( surf_usm_v(l)%r_a_window(1:surf_usm_v(l)%ns)         )           
1088           ALLOCATE ( surf_usm_v(l)%r_s(1:surf_usm_v(l)%ns)                )
1089        ENDDO
1090
1091!       
1092!--     allocate wall and roof material parameters. First for horizontal surfaces
1093        ALLOCATE ( surf_usm_h%thickness_wall(1:surf_usm_h%ns)                    )
1094        ALLOCATE ( surf_usm_h%thickness_window(1:surf_usm_h%ns)                  )
1095        ALLOCATE ( surf_usm_h%thickness_green(1:surf_usm_h%ns)                   )
1096        ALLOCATE ( surf_usm_h%lambda_h(nzb_wall:nzt_wall,1:surf_usm_h%ns)        )
1097        ALLOCATE ( surf_usm_h%rho_c_wall(nzb_wall:nzt_wall,1:surf_usm_h%ns)      )
1098        ALLOCATE ( surf_usm_h%lambda_h_window(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1099        ALLOCATE ( surf_usm_h%rho_c_window(nzb_wall:nzt_wall,1:surf_usm_h%ns)    )
1100        ALLOCATE ( surf_usm_h%lambda_h_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)  )
1101        ALLOCATE ( surf_usm_h%rho_c_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)     )
1102
1103        ALLOCATE ( surf_usm_h%rho_c_total_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)    )
1104        ALLOCATE ( surf_usm_h%n_vg_green(1:surf_usm_h%ns)                             )
1105        ALLOCATE ( surf_usm_h%alpha_vg_green(1:surf_usm_h%ns)                         )
1106        ALLOCATE ( surf_usm_h%l_vg_green(1:surf_usm_h%ns)                             )
1107        ALLOCATE ( surf_usm_h%gamma_w_green_sat(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)  )
1108        ALLOCATE ( surf_usm_h%lambda_w_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)       )
1109        ALLOCATE ( surf_usm_h%gamma_w_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)        )
1110        ALLOCATE ( surf_usm_h%tswc_h_m(nzb_wall:nzt_wall,1:surf_usm_h%ns)             )
1111
1112!
1113!--     For vertical surfaces.
1114        DO  l = 0, 3
1115           ALLOCATE ( surf_usm_v(l)%thickness_wall(1:surf_usm_v(l)%ns)                    )
1116           ALLOCATE ( surf_usm_v(l)%thickness_window(1:surf_usm_v(l)%ns)                  )
1117           ALLOCATE ( surf_usm_v(l)%thickness_green(1:surf_usm_v(l)%ns)                   )
1118           ALLOCATE ( surf_usm_v(l)%lambda_h(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)        )
1119           ALLOCATE ( surf_usm_v(l)%rho_c_wall(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)      )
1120           ALLOCATE ( surf_usm_v(l)%lambda_h_window(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1121           ALLOCATE ( surf_usm_v(l)%rho_c_window(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)    )
1122           ALLOCATE ( surf_usm_v(l)%lambda_h_green(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)  )
1123           ALLOCATE ( surf_usm_v(l)%rho_c_green(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)     )
1124        ENDDO
1125
1126!
1127!--     allocate green wall and roof vegetation and soil parameters. First horizontal surfaces
1128        ALLOCATE ( surf_usm_h%g_d(1:surf_usm_h%ns)              )
1129        ALLOCATE ( surf_usm_h%c_liq(1:surf_usm_h%ns)            )
1130        ALLOCATE ( surf_usm_h%qsws_liq(1:surf_usm_h%ns)         )
1131        ALLOCATE ( surf_usm_h%qsws_veg(1:surf_usm_h%ns)         )
1132        ALLOCATE ( surf_usm_h%r_canopy(1:surf_usm_h%ns)         )
1133        ALLOCATE ( surf_usm_h%r_canopy_min(1:surf_usm_h%ns)     )
1134        ALLOCATE ( surf_usm_h%qsws_eb(1:surf_usm_h%ns)          )
1135        ALLOCATE ( surf_usm_h%pt_10cm(1:surf_usm_h%ns)          ) 
1136        ALLOCATE ( surf_usm_h%pt_2m(1:surf_usm_h%ns)            ) 
1137
1138!
1139!--     For vertical surfaces.
1140        DO  l = 0, 3
1141          ALLOCATE ( surf_usm_v(l)%g_d(1:surf_usm_v(l)%ns)              )
1142          ALLOCATE ( surf_usm_v(l)%c_liq(1:surf_usm_v(l)%ns)            )
1143          ALLOCATE ( surf_usm_v(l)%qsws_liq(1:surf_usm_v(l)%ns)         )
1144          ALLOCATE ( surf_usm_v(l)%qsws_veg(1:surf_usm_v(l)%ns)         )
1145          ALLOCATE ( surf_usm_v(l)%qsws_eb(1:surf_usm_v(l)%ns)          )
1146          ALLOCATE ( surf_usm_v(l)%r_canopy(1:surf_usm_v(l)%ns)         )
1147          ALLOCATE ( surf_usm_v(l)%r_canopy_min(1:surf_usm_v(l)%ns)     )
1148          ALLOCATE ( surf_usm_v(l)%pt_10cm(1:surf_usm_v(l)%ns)          )
1149        ENDDO
1150
1151!
1152!--     allocate wall and roof layers sizes. For horizontal surfaces.
1153        ALLOCATE ( zwn(nzb_wall:nzt_wall)                                        )
1154        ALLOCATE ( surf_usm_h%dz_wall(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)       )
1155        ALLOCATE ( zwn_window(nzb_wall:nzt_wall)                                 )
1156        ALLOCATE ( surf_usm_h%dz_window(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)     )
1157        ALLOCATE ( zwn_green(nzb_wall:nzt_wall)                                  )
1158        ALLOCATE ( surf_usm_h%dz_green(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)      )
1159        ALLOCATE ( surf_usm_h%ddz_wall(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)      )
1160        ALLOCATE ( surf_usm_h%dz_wall_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)    )
1161        ALLOCATE ( surf_usm_h%ddz_wall_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)   )
1162        ALLOCATE ( surf_usm_h%zw(nzb_wall:nzt_wall,1:surf_usm_h%ns)              )
1163        ALLOCATE ( surf_usm_h%ddz_window(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)    )
1164        ALLOCATE ( surf_usm_h%dz_window_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)  )
1165        ALLOCATE ( surf_usm_h%ddz_window_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1166        ALLOCATE ( surf_usm_h%zw_window(nzb_wall:nzt_wall,1:surf_usm_h%ns)       )
1167        ALLOCATE ( surf_usm_h%ddz_green(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)     )
1168        ALLOCATE ( surf_usm_h%dz_green_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)   )
1169        ALLOCATE ( surf_usm_h%ddz_green_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)  )
1170        ALLOCATE ( surf_usm_h%zw_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)        )
1171
1172!
1173!--     For vertical surfaces.
1174        DO  l = 0, 3
1175           ALLOCATE ( surf_usm_v(l)%dz_wall(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)       )
1176           ALLOCATE ( surf_usm_v(l)%dz_window(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)     )
1177           ALLOCATE ( surf_usm_v(l)%dz_green(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)      )
1178           ALLOCATE ( surf_usm_v(l)%ddz_wall(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)      )
1179           ALLOCATE ( surf_usm_v(l)%dz_wall_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)    )
1180           ALLOCATE ( surf_usm_v(l)%ddz_wall_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)   )
1181           ALLOCATE ( surf_usm_v(l)%zw(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)              )
1182           ALLOCATE ( surf_usm_v(l)%ddz_window(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)    )
1183           ALLOCATE ( surf_usm_v(l)%dz_window_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)  )
1184           ALLOCATE ( surf_usm_v(l)%ddz_window_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1185           ALLOCATE ( surf_usm_v(l)%zw_window(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)       )
1186           ALLOCATE ( surf_usm_v(l)%ddz_green(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)     )
1187           ALLOCATE ( surf_usm_v(l)%dz_green_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)   )
1188           ALLOCATE ( surf_usm_v(l)%ddz_green_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)  )
1189           ALLOCATE ( surf_usm_v(l)%zw_green(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)        )
1190        ENDDO
1191
1192!
1193!--     allocate wall and roof temperature arrays, for horizontal walls
1194!
1195!--     Allocate if required. Note, in case of restarts, some of these arrays
1196!--     might be already allocated.
1197        IF ( .NOT. ALLOCATED( t_surf_wall_h_1 ) )                              &
1198           ALLOCATE ( t_surf_wall_h_1(1:surf_usm_h%ns) )
1199        IF ( .NOT. ALLOCATED( t_surf_wall_h_2 ) )                              &
1200           ALLOCATE ( t_surf_wall_h_2(1:surf_usm_h%ns) )
1201        IF ( .NOT. ALLOCATED( t_wall_h_1 ) )                                   &           
1202           ALLOCATE ( t_wall_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1203        IF ( .NOT. ALLOCATED( t_wall_h_2 ) )                                   &           
1204           ALLOCATE ( t_wall_h_2(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )         
1205        IF ( .NOT. ALLOCATED( t_surf_window_h_1 ) )                            &
1206           ALLOCATE ( t_surf_window_h_1(1:surf_usm_h%ns) )
1207        IF ( .NOT. ALLOCATED( t_surf_window_h_2 ) )                            &
1208           ALLOCATE ( t_surf_window_h_2(1:surf_usm_h%ns) )
1209        IF ( .NOT. ALLOCATED( t_window_h_1 ) )                                 &           
1210           ALLOCATE ( t_window_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1211        IF ( .NOT. ALLOCATED( t_window_h_2 ) )                                 &           
1212           ALLOCATE ( t_window_h_2(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )         
1213        IF ( .NOT. ALLOCATED( t_surf_green_h_1 ) )                             &
1214           ALLOCATE ( t_surf_green_h_1(1:surf_usm_h%ns) )
1215        IF ( .NOT. ALLOCATED( t_surf_green_h_2 ) )                             &
1216           ALLOCATE ( t_surf_green_h_2(1:surf_usm_h%ns) )
1217        IF ( .NOT. ALLOCATED( t_green_h_1 ) )                                  &           
1218           ALLOCATE ( t_green_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1219        IF ( .NOT. ALLOCATED( t_green_h_2 ) )                                  &           
1220           ALLOCATE ( t_green_h_2(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )         
1221        IF ( .NOT. ALLOCATED( swc_h_1 ) )                                      &           
1222           ALLOCATE ( swc_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1223        IF ( .NOT. ALLOCATED( swc_sat_h_1 ) )                                  &           
1224           ALLOCATE ( swc_sat_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1225        IF ( .NOT. ALLOCATED( swc_res_h_1 ) )                                  &           
1226           ALLOCATE ( swc_res_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1227        IF ( .NOT. ALLOCATED( swc_h_2 ) )                                      &           
1228           ALLOCATE ( swc_h_2(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
1229        IF ( .NOT. ALLOCATED( rootfr_h_1 ) )                                   &           
1230           ALLOCATE ( rootfr_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1231        IF ( .NOT. ALLOCATED( wilt_h_1 ) )                                     &           
1232           ALLOCATE ( wilt_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1233        IF ( .NOT. ALLOCATED( fc_h_1 ) )                                       &           
1234           ALLOCATE ( fc_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1235
1236        IF ( .NOT. ALLOCATED( m_liq_usm_h_1%var_usm_1d ) )                     &
1237           ALLOCATE ( m_liq_usm_h_1%var_usm_1d(1:surf_usm_h%ns) )
1238        IF ( .NOT. ALLOCATED( m_liq_usm_h_2%var_usm_1d ) )                     &
1239           ALLOCATE ( m_liq_usm_h_2%var_usm_1d(1:surf_usm_h%ns) )
1240           
1241!           
1242!--     initial assignment of the pointers
1243        t_wall_h    => t_wall_h_1;   t_wall_h_p   => t_wall_h_2
1244        t_window_h  => t_window_h_1; t_window_h_p => t_window_h_2
1245        t_green_h   => t_green_h_1;  t_green_h_p  => t_green_h_2
1246        t_surf_wall_h   => t_surf_wall_h_1;   t_surf_wall_h_p   => t_surf_wall_h_2           
1247        t_surf_window_h => t_surf_window_h_1; t_surf_window_h_p => t_surf_window_h_2 
1248        t_surf_green_h  => t_surf_green_h_1;  t_surf_green_h_p  => t_surf_green_h_2           
1249        m_liq_usm_h     => m_liq_usm_h_1;     m_liq_usm_h_p     => m_liq_usm_h_2
1250        swc_h     => swc_h_1; swc_h_p => swc_h_2
1251        swc_sat_h => swc_sat_h_1
1252        swc_res_h => swc_res_h_1
1253        rootfr_h  => rootfr_h_1
1254        wilt_h    => wilt_h_1
1255        fc_h      => fc_h_1
1256
1257!
1258!--     allocate wall and roof temperature arrays, for vertical walls if required
1259!
1260!--     Allocate if required. Note, in case of restarts, some of these arrays
1261!--     might be already allocated.
1262        DO  l = 0, 3
1263           IF ( .NOT. ALLOCATED( t_surf_wall_v_1(l)%t ) )                      &
1264              ALLOCATE ( t_surf_wall_v_1(l)%t(1:surf_usm_v(l)%ns) )
1265           IF ( .NOT. ALLOCATED( t_surf_wall_v_2(l)%t ) )                      &
1266              ALLOCATE ( t_surf_wall_v_2(l)%t(1:surf_usm_v(l)%ns) )
1267           IF ( .NOT. ALLOCATED( t_wall_v_1(l)%t ) )                           &           
1268              ALLOCATE ( t_wall_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1269           IF ( .NOT. ALLOCATED( t_wall_v_2(l)%t ) )                           &           
1270              ALLOCATE ( t_wall_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1271           IF ( .NOT. ALLOCATED( t_surf_window_v_1(l)%t ) )                    &
1272              ALLOCATE ( t_surf_window_v_1(l)%t(1:surf_usm_v(l)%ns) )
1273           IF ( .NOT. ALLOCATED( t_surf_window_v_2(l)%t ) )                    &
1274              ALLOCATE ( t_surf_window_v_2(l)%t(1:surf_usm_v(l)%ns) )
1275           IF ( .NOT. ALLOCATED( t_window_v_1(l)%t ) )                         &           
1276              ALLOCATE ( t_window_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1277           IF ( .NOT. ALLOCATED( t_window_v_2(l)%t ) )                         &           
1278              ALLOCATE ( t_window_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1279           IF ( .NOT. ALLOCATED( t_surf_green_v_1(l)%t ) )                     &
1280              ALLOCATE ( t_surf_green_v_1(l)%t(1:surf_usm_v(l)%ns) )
1281           IF ( .NOT. ALLOCATED( t_surf_green_v_2(l)%t ) )                     &
1282              ALLOCATE ( t_surf_green_v_2(l)%t(1:surf_usm_v(l)%ns) )
1283           IF ( .NOT. ALLOCATED( t_green_v_1(l)%t ) )                          &           
1284              ALLOCATE ( t_green_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1285           IF ( .NOT. ALLOCATED( t_green_v_2(l)%t ) )                          &           
1286              ALLOCATE ( t_green_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1287           IF ( .NOT. ALLOCATED( m_liq_usm_v_1(l)%var_usm_1d ) )               &
1288              ALLOCATE ( m_liq_usm_v_1(l)%var_usm_1d(1:surf_usm_v(l)%ns) )
1289           IF ( .NOT. ALLOCATED( m_liq_usm_v_2(l)%var_usm_1d ) )               &
1290              ALLOCATE ( m_liq_usm_v_2(l)%var_usm_1d(1:surf_usm_v(l)%ns) )
1291           IF ( .NOT. ALLOCATED( swc_v_1(l)%t ) )                              &           
1292              ALLOCATE ( swc_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1293           IF ( .NOT. ALLOCATED( swc_v_2(l)%t ) )                              &           
1294              ALLOCATE ( swc_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1295        ENDDO
1296!
1297!--     initial assignment of the pointers
1298        t_wall_v        => t_wall_v_1;        t_wall_v_p        => t_wall_v_2
1299        t_surf_wall_v   => t_surf_wall_v_1;   t_surf_wall_v_p   => t_surf_wall_v_2
1300        t_window_v      => t_window_v_1;      t_window_v_p      => t_window_v_2
1301        t_green_v       => t_green_v_1;       t_green_v_p       => t_green_v_2
1302        t_surf_window_v => t_surf_window_v_1; t_surf_window_v_p => t_surf_window_v_2
1303        t_surf_green_v  => t_surf_green_v_1;  t_surf_green_v_p  => t_surf_green_v_2
1304        m_liq_usm_v     => m_liq_usm_v_1;     m_liq_usm_v_p     => m_liq_usm_v_2
1305        swc_v           => swc_v_1;           swc_v_p           => swc_v_2
1306
1307!
1308!--     Allocate intermediate timestep arrays. For horizontal surfaces.
1309        ALLOCATE ( surf_usm_h%tt_surface_wall_m(1:surf_usm_h%ns)               )
1310        ALLOCATE ( surf_usm_h%tt_wall_m(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)   )
1311        ALLOCATE ( surf_usm_h%tt_surface_window_m(1:surf_usm_h%ns)             )
1312        ALLOCATE ( surf_usm_h%tt_window_m(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
1313        ALLOCATE ( surf_usm_h%tt_green_m(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)  )
1314        ALLOCATE ( surf_usm_h%tt_surface_green_m(1:surf_usm_h%ns)              )
1315
1316!
1317!--    Allocate intermediate timestep arrays
1318!--    Horizontal surfaces
1319       ALLOCATE ( tm_liq_usm_h_m%var_usm_1d(1:surf_usm_h%ns)                   )
1320!
1321!--    Horizontal surfaces
1322       DO  l = 0, 3
1323          ALLOCATE ( tm_liq_usm_v_m(l)%var_usm_1d(1:surf_usm_v(l)%ns)          )
1324       ENDDO 
1325       
1326!
1327!--     Set inital values for prognostic quantities
1328        IF ( ALLOCATED( surf_usm_h%tt_surface_wall_m )   )  surf_usm_h%tt_surface_wall_m   = 0.0_wp
1329        IF ( ALLOCATED( surf_usm_h%tt_wall_m )           )  surf_usm_h%tt_wall_m           = 0.0_wp
1330        IF ( ALLOCATED( surf_usm_h%tt_surface_window_m ) )  surf_usm_h%tt_surface_window_m = 0.0_wp
1331        IF ( ALLOCATED( surf_usm_h%tt_window_m    )      )  surf_usm_h%tt_window_m         = 0.0_wp
1332        IF ( ALLOCATED( surf_usm_h%tt_green_m    )       )  surf_usm_h%tt_green_m          = 0.0_wp
1333        IF ( ALLOCATED( surf_usm_h%tt_surface_green_m )  )  surf_usm_h%tt_surface_green_m  = 0.0_wp
1334!
1335!--     Now, for vertical surfaces
1336        DO  l = 0, 3
1337           ALLOCATE ( surf_usm_v(l)%tt_surface_wall_m(1:surf_usm_v(l)%ns)               )
1338           ALLOCATE ( surf_usm_v(l)%tt_wall_m(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)   )
1339           IF ( ALLOCATED( surf_usm_v(l)%tt_surface_wall_m ) )  surf_usm_v(l)%tt_surface_wall_m = 0.0_wp
1340           IF ( ALLOCATED( surf_usm_v(l)%tt_wall_m    ) )  surf_usm_v(l)%tt_wall_m    = 0.0_wp
1341           ALLOCATE ( surf_usm_v(l)%tt_surface_window_m(1:surf_usm_v(l)%ns)             )
1342           ALLOCATE ( surf_usm_v(l)%tt_window_m(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
1343           IF ( ALLOCATED( surf_usm_v(l)%tt_surface_window_m ) )  surf_usm_v(l)%tt_surface_window_m = 0.0_wp
1344           IF ( ALLOCATED( surf_usm_v(l)%tt_window_m  ) )  surf_usm_v(l)%tt_window_m    = 0.0_wp
1345           ALLOCATE ( surf_usm_v(l)%tt_surface_green_m(1:surf_usm_v(l)%ns)              )
1346           IF ( ALLOCATED( surf_usm_v(l)%tt_surface_green_m ) )  surf_usm_v(l)%tt_surface_green_m = 0.0_wp
1347           ALLOCATE ( surf_usm_v(l)%tt_green_m(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)  )
1348           IF ( ALLOCATED( surf_usm_v(l)%tt_green_m   ) )  surf_usm_v(l)%tt_green_m    = 0.0_wp
1349        ENDDO
1350!
1351!--     allocate wall heat flux output array and set initial values. For horizontal surfaces
1352!        ALLOCATE ( surf_usm_h%wshf(1:surf_usm_h%ns)    )  !can be removed
1353        ALLOCATE ( surf_usm_h%wshf_eb(1:surf_usm_h%ns) )
1354        ALLOCATE ( surf_usm_h%wghf_eb(1:surf_usm_h%ns) )
1355        ALLOCATE ( surf_usm_h%wghf_eb_window(1:surf_usm_h%ns) )
1356        ALLOCATE ( surf_usm_h%wghf_eb_green(1:surf_usm_h%ns) )
1357        ALLOCATE ( surf_usm_h%iwghf_eb(1:surf_usm_h%ns) )
1358        ALLOCATE ( surf_usm_h%iwghf_eb_window(1:surf_usm_h%ns) )
1359        IF ( ALLOCATED( surf_usm_h%wshf    ) )  surf_usm_h%wshf    = 0.0_wp
1360        IF ( ALLOCATED( surf_usm_h%wshf_eb ) )  surf_usm_h%wshf_eb = 0.0_wp
1361        IF ( ALLOCATED( surf_usm_h%wghf_eb ) )  surf_usm_h%wghf_eb = 0.0_wp
1362        IF ( ALLOCATED( surf_usm_h%wghf_eb_window ) )  surf_usm_h%wghf_eb_window = 0.0_wp
1363        IF ( ALLOCATED( surf_usm_h%wghf_eb_green ) )  surf_usm_h%wghf_eb_green = 0.0_wp
1364        IF ( ALLOCATED( surf_usm_h%iwghf_eb ) )  surf_usm_h%iwghf_eb = 0.0_wp
1365        IF ( ALLOCATED( surf_usm_h%iwghf_eb_window ) )  surf_usm_h%iwghf_eb_window = 0.0_wp
1366!
1367!--     Now, for vertical surfaces
1368        DO  l = 0, 3
1369!           ALLOCATE ( surf_usm_v(l)%wshf(1:surf_usm_v(l)%ns)    )    ! can be removed
1370           ALLOCATE ( surf_usm_v(l)%wshf_eb(1:surf_usm_v(l)%ns) )
1371           ALLOCATE ( surf_usm_v(l)%wghf_eb(1:surf_usm_v(l)%ns) )
1372           ALLOCATE ( surf_usm_v(l)%wghf_eb_window(1:surf_usm_v(l)%ns) )
1373           ALLOCATE ( surf_usm_v(l)%wghf_eb_green(1:surf_usm_v(l)%ns) )
1374           ALLOCATE ( surf_usm_v(l)%iwghf_eb(1:surf_usm_v(l)%ns) )
1375           ALLOCATE ( surf_usm_v(l)%iwghf_eb_window(1:surf_usm_v(l)%ns) )
1376           IF ( ALLOCATED( surf_usm_v(l)%wshf    ) )  surf_usm_v(l)%wshf    = 0.0_wp
1377           IF ( ALLOCATED( surf_usm_v(l)%wshf_eb ) )  surf_usm_v(l)%wshf_eb = 0.0_wp
1378           IF ( ALLOCATED( surf_usm_v(l)%wghf_eb ) )  surf_usm_v(l)%wghf_eb = 0.0_wp
1379           IF ( ALLOCATED( surf_usm_v(l)%wghf_eb_window ) )  surf_usm_v(l)%wghf_eb_window = 0.0_wp
1380           IF ( ALLOCATED( surf_usm_v(l)%wghf_eb_green ) )  surf_usm_v(l)%wghf_eb_green = 0.0_wp
1381           IF ( ALLOCATED( surf_usm_v(l)%iwghf_eb ) )  surf_usm_v(l)%iwghf_eb = 0.0_wp
1382           IF ( ALLOCATED( surf_usm_v(l)%iwghf_eb_window ) )  surf_usm_v(l)%iwghf_eb_window = 0.0_wp
1383        ENDDO
1384
1385        CALL location_message( 'finished', .TRUE. )
1386       
1387    END SUBROUTINE usm_init_arrays
1388
1389
1390!------------------------------------------------------------------------------!
1391! Description:
1392! ------------
1393!> Sum up and time-average urban surface output quantities as well as allocate
1394!> the array necessary for storing the average.
1395!------------------------------------------------------------------------------!
1396    SUBROUTINE usm_3d_data_averaging( mode, variable )
1397
1398        IMPLICIT NONE
1399
1400        CHARACTER(LEN=*), INTENT(IN) ::  mode
1401        CHARACTER(LEN=*), INTENT(IN) :: variable
1402 
1403        INTEGER(iwp)                                       :: i, j, k, l, m, ids, idsint, iwl, istat  !< runnin indices
1404        CHARACTER(LEN=varnamelength)                       :: var                                     !< trimmed variable
1405        INTEGER(iwp), PARAMETER                            :: nd = 5                                  !< number of directions
1406        CHARACTER(LEN=6), DIMENSION(0:nd-1), PARAMETER     :: dirname = (/ '_roof ', '_south', '_north', '_west ', '_east ' /)
1407        INTEGER(iwp), DIMENSION(0:nd-1), PARAMETER         :: dirint = (/ iup_u, isouth_u, inorth_u, iwest_u, ieast_u /)
1408
1409        IF ( variable(1:4) == 'usm_' )  THEN  ! is such a check really rquired?
1410
1411!
1412!--     find the real name of the variable
1413        ids = -1
1414        l = -1
1415        var = TRIM(variable)
1416        DO i = 0, nd-1
1417            k = len(TRIM(var))
1418            j = len(TRIM(dirname(i)))
1419            IF ( TRIM(var(k-j+1:k)) == TRIM(dirname(i)) )  THEN
1420                ids = i
1421                idsint = dirint(ids)
1422                var = var(:k-j)
1423                EXIT
1424            ENDIF
1425        ENDDO
1426        l = idsint - 2  ! horisontal direction index - terible hack !
1427        IF ( l < 0 .OR. l > 3 ) THEN
1428           l = -1
1429        END IF
1430        IF ( ids == -1 )  THEN
1431            var = TRIM(variable)
1432        ENDIF
1433        IF ( var(1:11) == 'usm_t_wall_'  .AND.  len(TRIM(var)) >= 12 )  THEN
1434!
1435!--          wall layers
1436            READ(var(12:12), '(I1)', iostat=istat ) iwl
1437            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
1438                var = var(1:10)
1439            ELSE
1440!
1441!--             wrong wall layer index
1442                RETURN
1443            ENDIF
1444        ENDIF
1445        IF ( var(1:13) == 'usm_t_window_'  .AND.  len(TRIM(var)) >= 14 )  THEN
1446!
1447!--          wall layers
1448            READ(var(14:14), '(I1)', iostat=istat ) iwl
1449            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
1450                var = var(1:12)
1451            ELSE
1452!
1453!--             wrong window layer index
1454                RETURN
1455            ENDIF
1456        ENDIF
1457        IF ( var(1:12) == 'usm_t_green_'  .AND.  len(TRIM(var)) >= 13 )  THEN
1458!
1459!--          wall layers
1460            READ(var(13:13), '(I1)', iostat=istat ) iwl
1461            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
1462                var = var(1:11)
1463            ELSE
1464!
1465!--             wrong green layer index
1466                RETURN
1467            ENDIF
1468        ENDIF
1469        IF ( var(1:8) == 'usm_swc_'  .AND.  len(TRIM(var)) >= 9 )  THEN
1470!
1471!--          swc layers
1472            READ(var(9:9), '(I1)', iostat=istat ) iwl
1473            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
1474                var = var(1:7)
1475            ELSE
1476!
1477!--             wrong swc layer index
1478                RETURN
1479            ENDIF
1480        ENDIF
1481
1482        IF ( mode == 'allocate' )  THEN
1483           
1484           SELECT CASE ( TRIM( var ) )
1485
1486                CASE ( 'usm_wshf' )
1487!
1488!--                 array of sensible heat flux from surfaces
1489!--                 land surfaces
1490                    IF ( l == -1 ) THEN
1491                       IF ( .NOT.  ALLOCATED(surf_usm_h%wshf_eb_av) )  THEN
1492                          ALLOCATE ( surf_usm_h%wshf_eb_av(1:surf_usm_h%ns) )
1493                          surf_usm_h%wshf_eb_av = 0.0_wp
1494                       ENDIF
1495                    ELSE
1496                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%wshf_eb_av) )  THEN
1497                           ALLOCATE ( surf_usm_v(l)%wshf_eb_av(1:surf_usm_v(l)%ns) )
1498                           surf_usm_v(l)%wshf_eb_av = 0.0_wp
1499                       ENDIF
1500                    ENDIF
1501                   
1502                CASE ( 'usm_qsws' )
1503!
1504!--                 array of latent heat flux from surfaces
1505!--                 land surfaces
1506                    IF ( l == -1 .AND. .NOT.  ALLOCATED(surf_usm_h%qsws_eb_av) )  THEN
1507                        ALLOCATE ( surf_usm_h%qsws_eb_av(1:surf_usm_h%ns) )
1508                        surf_usm_h%qsws_eb_av = 0.0_wp
1509                    ELSE
1510                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%qsws_eb_av) )  THEN
1511                           ALLOCATE ( surf_usm_v(l)%qsws_eb_av(1:surf_usm_v(l)%ns) )
1512                           surf_usm_v(l)%qsws_eb_av = 0.0_wp
1513                       ENDIF
1514                    ENDIF
1515                   
1516                CASE ( 'usm_qsws_veg' )
1517!
1518!--                 array of latent heat flux from vegetation surfaces
1519!--                 land surfaces
1520                    IF ( l == -1 .AND. .NOT.  ALLOCATED(surf_usm_h%qsws_veg_av) )  THEN
1521                        ALLOCATE ( surf_usm_h%qsws_veg_av(1:surf_usm_h%ns) )
1522                        surf_usm_h%qsws_veg_av = 0.0_wp
1523                    ELSE
1524                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%qsws_veg_av) )  THEN
1525                           ALLOCATE ( surf_usm_v(l)%qsws_veg_av(1:surf_usm_v(l)%ns) )
1526                           surf_usm_v(l)%qsws_veg_av = 0.0_wp
1527                       ENDIF
1528                    ENDIF
1529                   
1530                CASE ( 'usm_qsws_liq' )
1531!
1532!--                 array of latent heat flux from surfaces with liquid
1533!--                 land surfaces
1534                    IF ( l == -1 .AND. .NOT.  ALLOCATED(surf_usm_h%qsws_liq_av) )  THEN
1535                        ALLOCATE ( surf_usm_h%qsws_liq_av(1:surf_usm_h%ns) )
1536                        surf_usm_h%qsws_liq_av = 0.0_wp
1537                    ELSE
1538                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%qsws_liq_av) )  THEN
1539                           ALLOCATE ( surf_usm_v(l)%qsws_liq_av(1:surf_usm_v(l)%ns) )
1540                           surf_usm_v(l)%qsws_liq_av = 0.0_wp
1541                       ENDIF
1542                    ENDIF
1543!
1544!--             Please note, the following output quantities belongs to the
1545!--             individual tile fractions - ground heat flux at wall-, window-,
1546!--             and green fraction. Aggregated ground-heat flux is treated
1547!--             accordingly in average_3d_data, sum_up_3d_data, etc..
1548                CASE ( 'usm_wghf' )
1549!
1550!--                 array of heat flux from ground (wall, roof, land)
1551                    IF ( l == -1 ) THEN
1552                       IF ( .NOT.  ALLOCATED(surf_usm_h%wghf_eb_av) )  THEN
1553                           ALLOCATE ( surf_usm_h%wghf_eb_av(1:surf_usm_h%ns) )
1554                           surf_usm_h%wghf_eb_av = 0.0_wp
1555                       ENDIF
1556                    ELSE
1557                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%wghf_eb_av) )  THEN
1558                           ALLOCATE ( surf_usm_v(l)%wghf_eb_av(1:surf_usm_v(l)%ns) )
1559                           surf_usm_v(l)%wghf_eb_av = 0.0_wp
1560                       ENDIF
1561                    ENDIF
1562
1563                CASE ( 'usm_wghf_window' )
1564!
1565!--                 array of heat flux from window ground (wall, roof, land)
1566                    IF ( l == -1 ) THEN
1567                       IF ( .NOT.  ALLOCATED(surf_usm_h%wghf_eb_window_av) )  THEN
1568                           ALLOCATE ( surf_usm_h%wghf_eb_window_av(1:surf_usm_h%ns) )
1569                           surf_usm_h%wghf_eb_window_av = 0.0_wp
1570                       ENDIF
1571                    ELSE
1572                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%wghf_eb_window_av) )  THEN
1573                           ALLOCATE ( surf_usm_v(l)%wghf_eb_window_av(1:surf_usm_v(l)%ns) )
1574                           surf_usm_v(l)%wghf_eb_window_av = 0.0_wp
1575                       ENDIF
1576                    ENDIF
1577
1578                CASE ( 'usm_wghf_green' )
1579!
1580!--                 array of heat flux from green ground (wall, roof, land)
1581                    IF ( l == -1 ) THEN
1582                       IF ( .NOT.  ALLOCATED(surf_usm_h%wghf_eb_green_av) )  THEN
1583                           ALLOCATE ( surf_usm_h%wghf_eb_green_av(1:surf_usm_h%ns) )
1584                           surf_usm_h%wghf_eb_green_av = 0.0_wp
1585                       ENDIF
1586                    ELSE
1587                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%wghf_eb_green_av) )  THEN
1588                           ALLOCATE ( surf_usm_v(l)%wghf_eb_green_av(1:surf_usm_v(l)%ns) )
1589                           surf_usm_v(l)%wghf_eb_green_av = 0.0_wp
1590                       ENDIF
1591                    ENDIF
1592
1593                CASE ( 'usm_iwghf' )
1594!
1595!--                 array of heat flux from indoor ground (wall, roof, land)
1596                    IF ( l == -1 ) THEN
1597                       IF ( .NOT.  ALLOCATED(surf_usm_h%iwghf_eb_av) )  THEN
1598                           ALLOCATE ( surf_usm_h%iwghf_eb_av(1:surf_usm_h%ns) )
1599                           surf_usm_h%iwghf_eb_av = 0.0_wp
1600                       ENDIF
1601                    ELSE
1602                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%iwghf_eb_av) )  THEN
1603                           ALLOCATE ( surf_usm_v(l)%iwghf_eb_av(1:surf_usm_v(l)%ns) )
1604                           surf_usm_v(l)%iwghf_eb_av = 0.0_wp
1605                       ENDIF
1606                    ENDIF
1607
1608                CASE ( 'usm_iwghf_window' )
1609!
1610!--                 array of heat flux from indoor window ground (wall, roof, land)
1611                    IF ( l == -1 ) THEN
1612                       IF ( .NOT.  ALLOCATED(surf_usm_h%iwghf_eb_window_av) )  THEN
1613                           ALLOCATE ( surf_usm_h%iwghf_eb_window_av(1:surf_usm_h%ns) )
1614                           surf_usm_h%iwghf_eb_window_av = 0.0_wp
1615                       ENDIF
1616                    ELSE
1617                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%iwghf_eb_window_av) )  THEN
1618                           ALLOCATE ( surf_usm_v(l)%iwghf_eb_window_av(1:surf_usm_v(l)%ns) )
1619                           surf_usm_v(l)%iwghf_eb_window_av = 0.0_wp
1620                       ENDIF
1621                    ENDIF
1622
1623                CASE ( 'usm_t_surf_wall' )
1624!
1625!--                 surface temperature for surfaces
1626                    IF ( l == -1 ) THEN
1627                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_surf_wall_av) )  THEN
1628                           ALLOCATE ( surf_usm_h%t_surf_wall_av(1:surf_usm_h%ns) )
1629                           surf_usm_h%t_surf_wall_av = 0.0_wp
1630                       ENDIF
1631                    ELSE
1632                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_surf_wall_av) )  THEN
1633                           ALLOCATE ( surf_usm_v(l)%t_surf_wall_av(1:surf_usm_v(l)%ns) )
1634                           surf_usm_v(l)%t_surf_wall_av = 0.0_wp
1635                       ENDIF
1636                    ENDIF
1637
1638                CASE ( 'usm_t_surf_window' )
1639!
1640!--                 surface temperature for window surfaces
1641                    IF ( l == -1 ) THEN
1642                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_surf_window_av) )  THEN
1643                           ALLOCATE ( surf_usm_h%t_surf_window_av(1:surf_usm_h%ns) )
1644                           surf_usm_h%t_surf_window_av = 0.0_wp
1645                       ENDIF
1646                    ELSE
1647                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_surf_window_av) )  THEN
1648                           ALLOCATE ( surf_usm_v(l)%t_surf_window_av(1:surf_usm_v(l)%ns) )
1649                           surf_usm_v(l)%t_surf_window_av = 0.0_wp
1650                       ENDIF
1651                    ENDIF
1652                   
1653                CASE ( 'usm_t_surf_green' )
1654!
1655!--                 surface temperature for green surfaces
1656                    IF ( l == -1 ) THEN
1657                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_surf_green_av) )  THEN
1658                           ALLOCATE ( surf_usm_h%t_surf_green_av(1:surf_usm_h%ns) )
1659                           surf_usm_h%t_surf_green_av = 0.0_wp
1660                       ENDIF
1661                    ELSE
1662                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_surf_green_av) )  THEN
1663                           ALLOCATE ( surf_usm_v(l)%t_surf_green_av(1:surf_usm_v(l)%ns) )
1664                           surf_usm_v(l)%t_surf_green_av = 0.0_wp
1665                       ENDIF
1666                    ENDIF
1667               
1668                CASE ( 'usm_theta_10cm' )
1669!
1670!--                 near surface (10cm) temperature for whole surfaces
1671                    IF ( l == -1 ) THEN
1672                       IF ( .NOT.  ALLOCATED(surf_usm_h%pt_10cm_av) )  THEN
1673                           ALLOCATE ( surf_usm_h%pt_10cm_av(1:surf_usm_h%ns) )
1674                           surf_usm_h%pt_10cm_av = 0.0_wp
1675                       ENDIF
1676                    ELSE
1677                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%pt_10cm_av) )  THEN
1678                           ALLOCATE ( surf_usm_v(l)%pt_10cm_av(1:surf_usm_v(l)%ns) )
1679                           surf_usm_v(l)%pt_10cm_av = 0.0_wp
1680                       ENDIF
1681                    ENDIF
1682                 
1683                CASE ( 'usm_t_wall' )
1684!
1685!--                 wall temperature for iwl layer of walls and land
1686                    IF ( l == -1 ) THEN
1687                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_wall_av) )  THEN
1688                           ALLOCATE ( surf_usm_h%t_wall_av(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1689                           surf_usm_h%t_wall_av = 0.0_wp
1690                       ENDIF
1691                    ELSE
1692                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_wall_av) )  THEN
1693                           ALLOCATE ( surf_usm_v(l)%t_wall_av(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1694                           surf_usm_v(l)%t_wall_av = 0.0_wp
1695                       ENDIF
1696                    ENDIF
1697
1698                CASE ( 'usm_t_window' )
1699!
1700!--                 window temperature for iwl layer of walls and land
1701                    IF ( l == -1 ) THEN
1702                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_window_av) )  THEN
1703                           ALLOCATE ( surf_usm_h%t_window_av(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1704                           surf_usm_h%t_window_av = 0.0_wp
1705                       ENDIF
1706                    ELSE
1707                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_window_av) )  THEN
1708                           ALLOCATE ( surf_usm_v(l)%t_window_av(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1709                           surf_usm_v(l)%t_window_av = 0.0_wp
1710                       ENDIF
1711                    ENDIF
1712
1713                CASE ( 'usm_t_green' )
1714!
1715!--                 green temperature for iwl layer of walls and land
1716                    IF ( l == -1 ) THEN
1717                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_green_av) )  THEN
1718                           ALLOCATE ( surf_usm_h%t_green_av(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1719                           surf_usm_h%t_green_av = 0.0_wp
1720                       ENDIF
1721                    ELSE
1722                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_green_av) )  THEN
1723                           ALLOCATE ( surf_usm_v(l)%t_green_av(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1724                           surf_usm_v(l)%t_green_av = 0.0_wp
1725                       ENDIF
1726                    ENDIF
1727                CASE ( 'usm_swc' )
1728!
1729!--                 soil water content for iwl layer of walls and land
1730                    IF ( l == -1 .AND. .NOT.  ALLOCATED(surf_usm_h%swc_av) )  THEN
1731                        ALLOCATE ( surf_usm_h%swc_av(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1732                        surf_usm_h%swc_av = 0.0_wp
1733                    ELSE
1734                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%swc_av) )  THEN
1735                           ALLOCATE ( surf_usm_v(l)%swc_av(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1736                           surf_usm_v(l)%swc_av = 0.0_wp
1737                       ENDIF
1738                    ENDIF
1739
1740               CASE DEFAULT
1741                   CONTINUE
1742
1743           END SELECT
1744
1745        ELSEIF ( mode == 'sum' )  THEN
1746           
1747           SELECT CASE ( TRIM( var ) )
1748
1749                CASE ( 'usm_wshf' )
1750!
1751!--                 array of sensible heat flux from surfaces (land, roof, wall)
1752                    IF ( l == -1 ) THEN
1753                       DO  m = 1, surf_usm_h%ns
1754                          surf_usm_h%wshf_eb_av(m) =                              &
1755                                             surf_usm_h%wshf_eb_av(m) +           &
1756                                             surf_usm_h%wshf_eb(m)
1757                       ENDDO
1758                    ELSE
1759                       DO  m = 1, surf_usm_v(l)%ns
1760                          surf_usm_v(l)%wshf_eb_av(m) =                        &
1761                                          surf_usm_v(l)%wshf_eb_av(m) +        &
1762                                          surf_usm_v(l)%wshf_eb(m)
1763                       ENDDO
1764                    ENDIF
1765                   
1766                CASE ( 'usm_qsws' )
1767!
1768!--                 array of latent heat flux from surfaces (land, roof, wall)
1769                    IF ( l == -1 ) THEN
1770                    DO  m = 1, surf_usm_h%ns
1771                       surf_usm_h%qsws_eb_av(m) =                              &
1772                                          surf_usm_h%qsws_eb_av(m) +           &
1773                                          surf_usm_h%qsws_eb(m)
1774                    ENDDO
1775                    ELSE
1776                       DO  m = 1, surf_usm_v(l)%ns
1777                          surf_usm_v(l)%qsws_eb_av(m) =                        &
1778                                          surf_usm_v(l)%qsws_eb_av(m) +        &
1779                                          surf_usm_v(l)%qsws_eb(m)
1780                       ENDDO
1781                    ENDIF
1782                   
1783                CASE ( 'usm_qsws_veg' )
1784!
1785!--                 array of latent heat flux from vegetation surfaces (land, roof, wall)
1786                    IF ( l == -1 ) THEN
1787                    DO  m = 1, surf_usm_h%ns
1788                       surf_usm_h%qsws_veg_av(m) =                              &
1789                                          surf_usm_h%qsws_veg_av(m) +           &
1790                                          surf_usm_h%qsws_veg(m)
1791                    ENDDO
1792                    ELSE
1793                       DO  m = 1, surf_usm_v(l)%ns
1794                          surf_usm_v(l)%qsws_veg_av(m) =                        &
1795                                          surf_usm_v(l)%qsws_veg_av(m) +        &
1796                                          surf_usm_v(l)%qsws_veg(m)
1797                       ENDDO
1798                    ENDIF
1799                   
1800                CASE ( 'usm_qsws_liq' )
1801!
1802!--                 array of latent heat flux from surfaces with liquid (land, roof, wall)
1803                    IF ( l == -1 ) THEN
1804                    DO  m = 1, surf_usm_h%ns
1805                       surf_usm_h%qsws_liq_av(m) =                              &
1806                                          surf_usm_h%qsws_liq_av(m) +           &
1807                                          surf_usm_h%qsws_liq(m)
1808                    ENDDO
1809                    ELSE
1810                       DO  m = 1, surf_usm_v(l)%ns
1811                          surf_usm_v(l)%qsws_liq_av(m) =                        &
1812                                          surf_usm_v(l)%qsws_liq_av(m) +        &
1813                                          surf_usm_v(l)%qsws_liq(m)
1814                       ENDDO
1815                    ENDIF
1816                   
1817                CASE ( 'usm_wghf' )
1818!
1819!--                 array of heat flux from ground (wall, roof, land)
1820                    IF ( l == -1 ) THEN
1821                       DO  m = 1, surf_usm_h%ns
1822                          surf_usm_h%wghf_eb_av(m) =                              &
1823                                             surf_usm_h%wghf_eb_av(m) +           &
1824                                             surf_usm_h%wghf_eb(m)
1825                       ENDDO
1826                    ELSE
1827                       DO  m = 1, surf_usm_v(l)%ns
1828                          surf_usm_v(l)%wghf_eb_av(m) =                        &
1829                                          surf_usm_v(l)%wghf_eb_av(m) +        &
1830                                          surf_usm_v(l)%wghf_eb(m)
1831                       ENDDO
1832                    ENDIF
1833                   
1834                CASE ( 'usm_wghf_window' )
1835!
1836!--                 array of heat flux from window ground (wall, roof, land)
1837                    IF ( l == -1 ) THEN
1838                       DO  m = 1, surf_usm_h%ns
1839                          surf_usm_h%wghf_eb_window_av(m) =                              &
1840                                             surf_usm_h%wghf_eb_window_av(m) +           &
1841                                             surf_usm_h%wghf_eb_window(m)
1842                       ENDDO
1843                    ELSE
1844                       DO  m = 1, surf_usm_v(l)%ns
1845                          surf_usm_v(l)%wghf_eb_window_av(m) =                        &
1846                                          surf_usm_v(l)%wghf_eb_window_av(m) +        &
1847                                          surf_usm_v(l)%wghf_eb_window(m)
1848                       ENDDO
1849                    ENDIF
1850
1851                CASE ( 'usm_wghf_green' )
1852!
1853!--                 array of heat flux from green ground (wall, roof, land)
1854                    IF ( l == -1 ) THEN
1855                       DO  m = 1, surf_usm_h%ns
1856                          surf_usm_h%wghf_eb_green_av(m) =                              &
1857                                             surf_usm_h%wghf_eb_green_av(m) +           &
1858                                             surf_usm_h%wghf_eb_green(m)
1859                       ENDDO
1860                    ELSE
1861                       DO  m = 1, surf_usm_v(l)%ns
1862                          surf_usm_v(l)%wghf_eb_green_av(m) =                        &
1863                                          surf_usm_v(l)%wghf_eb_green_av(m) +        &
1864                                          surf_usm_v(l)%wghf_eb_green(m)
1865                       ENDDO
1866                    ENDIF
1867                   
1868                CASE ( 'usm_iwghf' )
1869!
1870!--                 array of heat flux from indoor ground (wall, roof, land)
1871                    IF ( l == -1 ) THEN
1872                       DO  m = 1, surf_usm_h%ns
1873                          surf_usm_h%iwghf_eb_av(m) =                              &
1874                                             surf_usm_h%iwghf_eb_av(m) +           &
1875                                             surf_usm_h%iwghf_eb(m)
1876                       ENDDO
1877                    ELSE
1878                       DO  m = 1, surf_usm_v(l)%ns
1879                          surf_usm_v(l)%iwghf_eb_av(m) =                        &
1880                                          surf_usm_v(l)%iwghf_eb_av(m) +        &
1881                                          surf_usm_v(l)%iwghf_eb(m)
1882                       ENDDO
1883                    ENDIF
1884                   
1885                CASE ( 'usm_iwghf_window' )
1886!
1887!--                 array of heat flux from indoor window ground (wall, roof, land)
1888                    IF ( l == -1 ) THEN
1889                       DO  m = 1, surf_usm_h%ns
1890                          surf_usm_h%iwghf_eb_window_av(m) =                              &
1891                                             surf_usm_h%iwghf_eb_window_av(m) +           &
1892                                             surf_usm_h%iwghf_eb_window(m)
1893                       ENDDO
1894                    ELSE
1895                       DO  m = 1, surf_usm_v(l)%ns
1896                          surf_usm_v(l)%iwghf_eb_window_av(m) =                        &
1897                                          surf_usm_v(l)%iwghf_eb_window_av(m) +        &
1898                                          surf_usm_v(l)%iwghf_eb_window(m)
1899                       ENDDO
1900                    ENDIF
1901                   
1902                CASE ( 'usm_t_surf_wall' )
1903!
1904!--                 surface temperature for surfaces
1905                    IF ( l == -1 ) THEN
1906                       DO  m = 1, surf_usm_h%ns
1907                       surf_usm_h%t_surf_wall_av(m) =                               & 
1908                                          surf_usm_h%t_surf_wall_av(m) +            &
1909                                          t_surf_wall_h(m)
1910                       ENDDO
1911                    ELSE
1912                       DO  m = 1, surf_usm_v(l)%ns
1913                          surf_usm_v(l)%t_surf_wall_av(m) =                         &
1914                                          surf_usm_v(l)%t_surf_wall_av(m) +         &
1915                                          t_surf_wall_v(l)%t(m)
1916                       ENDDO
1917                    ENDIF
1918                   
1919                CASE ( 'usm_t_surf_window' )
1920!
1921!--                 surface temperature for window surfaces
1922                    IF ( l == -1 ) THEN
1923                       DO  m = 1, surf_usm_h%ns
1924                          surf_usm_h%t_surf_window_av(m) =                               &
1925                                             surf_usm_h%t_surf_window_av(m) +            &
1926                                             t_surf_window_h(m)
1927                       ENDDO
1928                    ELSE
1929                       DO  m = 1, surf_usm_v(l)%ns
1930                          surf_usm_v(l)%t_surf_window_av(m) =                         &
1931                                          surf_usm_v(l)%t_surf_window_av(m) +         &
1932                                          t_surf_window_v(l)%t(m)
1933                       ENDDO
1934                    ENDIF
1935                   
1936                CASE ( 'usm_t_surf_green' )
1937!
1938!--                 surface temperature for green surfaces
1939                    IF ( l == -1 ) THEN
1940                       DO  m = 1, surf_usm_h%ns
1941                          surf_usm_h%t_surf_green_av(m) =                               &
1942                                             surf_usm_h%t_surf_green_av(m) +            &
1943                                             t_surf_green_h(m)
1944                       ENDDO
1945                    ELSE
1946                       DO  m = 1, surf_usm_v(l)%ns
1947                          surf_usm_v(l)%t_surf_green_av(m) =                         &
1948                                          surf_usm_v(l)%t_surf_green_av(m) +         &
1949                                          t_surf_green_v(l)%t(m)
1950                       ENDDO
1951                    ENDIF
1952               
1953                CASE ( 'usm_theta_10cm' )
1954!
1955!--                 near surface temperature for whole surfaces
1956                    IF ( l == -1 ) THEN
1957                       DO  m = 1, surf_usm_h%ns
1958                          surf_usm_h%pt_10cm_av(m) =                               &
1959                                             surf_usm_h%pt_10cm_av(m) +            &
1960                                             surf_usm_h%pt_10cm(m)
1961                       ENDDO
1962                    ELSE
1963                       DO  m = 1, surf_usm_v(l)%ns
1964                          surf_usm_v(l)%pt_10cm_av(m) =                         &
1965                                          surf_usm_v(l)%pt_10cm_av(m) +         &
1966                                          surf_usm_v(l)%pt_10cm(m)
1967                       ENDDO
1968                    ENDIF
1969                   
1970                CASE ( 'usm_t_wall' )
1971!
1972!--                 wall temperature for  iwl layer of walls and land
1973                    IF ( l == -1 ) THEN
1974                       DO  m = 1, surf_usm_h%ns
1975                          surf_usm_h%t_wall_av(iwl,m) =                           &
1976                                             surf_usm_h%t_wall_av(iwl,m) +        &
1977                                             t_wall_h(iwl,m)
1978                       ENDDO
1979                    ELSE
1980                       DO  m = 1, surf_usm_v(l)%ns
1981                          surf_usm_v(l)%t_wall_av(iwl,m) =                     &
1982                                          surf_usm_v(l)%t_wall_av(iwl,m) +     &
1983                                          t_wall_v(l)%t(iwl,m)
1984                       ENDDO
1985                    ENDIF
1986                   
1987                CASE ( 'usm_t_window' )
1988!
1989!--                 window temperature for  iwl layer of walls and land
1990                    IF ( l == -1 ) THEN
1991                       DO  m = 1, surf_usm_h%ns
1992                          surf_usm_h%t_window_av(iwl,m) =                           &
1993                                             surf_usm_h%t_window_av(iwl,m) +        &
1994                                             t_window_h(iwl,m)
1995                       ENDDO
1996                    ELSE
1997                       DO  m = 1, surf_usm_v(l)%ns
1998                          surf_usm_v(l)%t_window_av(iwl,m) =                     &
1999                                          surf_usm_v(l)%t_window_av(iwl,m) +     &
2000                                          t_window_v(l)%t(iwl,m)
2001                       ENDDO
2002                    ENDIF
2003
2004                CASE ( 'usm_t_green' )
2005!
2006!--                 green temperature for  iwl layer of walls and land
2007                    IF ( l == -1 ) THEN
2008                       DO  m = 1, surf_usm_h%ns
2009                          surf_usm_h%t_green_av(iwl,m) =                           &
2010                                             surf_usm_h%t_green_av(iwl,m) +        &
2011                                             t_green_h(iwl,m)
2012                       ENDDO
2013                    ELSE
2014                       DO  m = 1, surf_usm_v(l)%ns
2015                          surf_usm_v(l)%t_green_av(iwl,m) =                     &
2016                                          surf_usm_v(l)%t_green_av(iwl,m) +     &
2017                                          t_green_v(l)%t(iwl,m)
2018                       ENDDO
2019                    ENDIF
2020
2021                CASE ( 'usm_swc' )
2022!
2023!--                 soil water content for  iwl layer of walls and land
2024                    IF ( l == -1 ) THEN
2025                    DO  m = 1, surf_usm_h%ns
2026                       surf_usm_h%swc_av(iwl,m) =                           &
2027                                          surf_usm_h%swc_av(iwl,m) +        &
2028                                          swc_h(iwl,m)
2029                    ENDDO
2030                    ELSE
2031                       DO  m = 1, surf_usm_v(l)%ns
2032                          surf_usm_v(l)%swc_av(iwl,m) =                     &
2033                                          surf_usm_v(l)%swc_av(iwl,m) +     &
2034                                          swc_v(l)%t(iwl,m)
2035                       ENDDO
2036                    ENDIF
2037
2038                CASE DEFAULT
2039                    CONTINUE
2040
2041           END SELECT
2042
2043        ELSEIF ( mode == 'average' )  THEN
2044           
2045           SELECT CASE ( TRIM( var ) )
2046
2047                CASE ( 'usm_wshf' )
2048!
2049!--                 array of sensible heat flux from surfaces (land, roof, wall)
2050                    IF ( l == -1 ) THEN
2051                       DO  m = 1, surf_usm_h%ns
2052                          surf_usm_h%wshf_eb_av(m) =                              &
2053                                             surf_usm_h%wshf_eb_av(m) /           &
2054                                             REAL( average_count_3d, kind=wp )
2055                       ENDDO
2056                    ELSE
2057                       DO  m = 1, surf_usm_v(l)%ns
2058                          surf_usm_v(l)%wshf_eb_av(m) =                        &
2059                                          surf_usm_v(l)%wshf_eb_av(m) /        &
2060                                          REAL( average_count_3d, kind=wp )
2061                       ENDDO
2062                    ENDIF
2063                   
2064                CASE ( 'usm_qsws' )
2065!
2066!--                 array of latent heat flux from surfaces (land, roof, wall)
2067                    IF ( l == -1 ) THEN
2068                    DO  m = 1, surf_usm_h%ns
2069                       surf_usm_h%qsws_eb_av(m) =                              &
2070                                          surf_usm_h%qsws_eb_av(m) /           &
2071                                          REAL( average_count_3d, kind=wp )
2072                    ENDDO
2073                    ELSE
2074                       DO  m = 1, surf_usm_v(l)%ns
2075                          surf_usm_v(l)%qsws_eb_av(m) =                        &
2076                                          surf_usm_v(l)%qsws_eb_av(m) /        &
2077                                          REAL( average_count_3d, kind=wp )
2078                       ENDDO
2079                    ENDIF
2080
2081                CASE ( 'usm_qsws_veg' )
2082!
2083!--                 array of latent heat flux from vegetation surfaces (land, roof, wall)
2084                    IF ( l == -1 ) THEN
2085                    DO  m = 1, surf_usm_h%ns
2086                       surf_usm_h%qsws_veg_av(m) =                              &
2087                                          surf_usm_h%qsws_veg_av(m) /           &
2088                                          REAL( average_count_3d, kind=wp )
2089                    ENDDO
2090                    ELSE
2091                       DO  m = 1, surf_usm_v(l)%ns
2092                          surf_usm_v(l)%qsws_veg_av(m) =                        &
2093                                          surf_usm_v(l)%qsws_veg_av(m) /        &
2094                                          REAL( average_count_3d, kind=wp )
2095                       ENDDO
2096                    ENDIF
2097                   
2098                CASE ( 'usm_qsws_liq' )
2099!
2100!--                 array of latent heat flux from surfaces with liquid (land, roof, wall)
2101                    IF ( l == -1 ) THEN
2102                    DO  m = 1, surf_usm_h%ns
2103                       surf_usm_h%qsws_liq_av(m) =                              &
2104                                          surf_usm_h%qsws_liq_av(m) /           &
2105                                          REAL( average_count_3d, kind=wp )
2106                    ENDDO
2107                    ELSE
2108                       DO  m = 1, surf_usm_v(l)%ns
2109                          surf_usm_v(l)%qsws_liq_av(m) =                        &
2110                                          surf_usm_v(l)%qsws_liq_av(m) /        &
2111                                          REAL( average_count_3d, kind=wp )
2112                       ENDDO
2113                    ENDIF
2114                   
2115                CASE ( 'usm_wghf' )
2116!
2117!--                 array of heat flux from ground (wall, roof, land)
2118                    IF ( l == -1 ) THEN
2119                       DO  m = 1, surf_usm_h%ns
2120                          surf_usm_h%wghf_eb_av(m) =                              &
2121                                             surf_usm_h%wghf_eb_av(m) /           &
2122                                             REAL( average_count_3d, kind=wp )
2123                       ENDDO
2124                    ELSE
2125                       DO  m = 1, surf_usm_v(l)%ns
2126                          surf_usm_v(l)%wghf_eb_av(m) =                        &
2127                                          surf_usm_v(l)%wghf_eb_av(m) /        &
2128                                          REAL( average_count_3d, kind=wp )
2129                       ENDDO
2130                    ENDIF
2131                   
2132                CASE ( 'usm_wghf_window' )
2133!
2134!--                 array of heat flux from window ground (wall, roof, land)
2135                    IF ( l == -1 ) THEN
2136                       DO  m = 1, surf_usm_h%ns
2137                          surf_usm_h%wghf_eb_window_av(m) =                              &
2138                                             surf_usm_h%wghf_eb_window_av(m) /           &
2139                                             REAL( average_count_3d, kind=wp )
2140                       ENDDO
2141                    ELSE
2142                       DO  m = 1, surf_usm_v(l)%ns
2143                          surf_usm_v(l)%wghf_eb_window_av(m) =                        &
2144                                          surf_usm_v(l)%wghf_eb_window_av(m) /        &
2145                                          REAL( average_count_3d, kind=wp )
2146                       ENDDO
2147                    ENDIF
2148
2149                CASE ( 'usm_wghf_green' )
2150!
2151!--                 array of heat flux from green ground (wall, roof, land)
2152                    IF ( l == -1 ) THEN
2153                       DO  m = 1, surf_usm_h%ns
2154                          surf_usm_h%wghf_eb_green_av(m) =                              &
2155                                             surf_usm_h%wghf_eb_green_av(m) /           &
2156                                             REAL( average_count_3d, kind=wp )
2157                       ENDDO
2158                    ELSE
2159                       DO  m = 1, surf_usm_v(l)%ns
2160                          surf_usm_v(l)%wghf_eb_green_av(m) =                        &
2161                                          surf_usm_v(l)%wghf_eb_green_av(m) /        &
2162                                          REAL( average_count_3d, kind=wp )
2163                       ENDDO
2164                    ENDIF
2165
2166                CASE ( 'usm_iwghf' )
2167!
2168!--                 array of heat flux from indoor ground (wall, roof, land)
2169                    IF ( l == -1 ) THEN
2170                       DO  m = 1, surf_usm_h%ns
2171                          surf_usm_h%iwghf_eb_av(m) =                              &
2172                                             surf_usm_h%iwghf_eb_av(m) /           &
2173                                             REAL( average_count_3d, kind=wp )
2174                       ENDDO
2175                    ELSE
2176                       DO  m = 1, surf_usm_v(l)%ns
2177                          surf_usm_v(l)%iwghf_eb_av(m) =                        &
2178                                          surf_usm_v(l)%iwghf_eb_av(m) /        &
2179                                          REAL( average_count_3d, kind=wp )
2180                       ENDDO
2181                    ENDIF
2182                   
2183                CASE ( 'usm_iwghf_window' )
2184!
2185!--                 array of heat flux from indoor window ground (wall, roof, land)
2186                    IF ( l == -1 ) THEN
2187                       DO  m = 1, surf_usm_h%ns
2188                          surf_usm_h%iwghf_eb_window_av(m) =                              &
2189                                             surf_usm_h%iwghf_eb_window_av(m) /           &
2190                                             REAL( average_count_3d, kind=wp )
2191                       ENDDO
2192                    ELSE
2193                       DO  m = 1, surf_usm_v(l)%ns
2194                          surf_usm_v(l)%iwghf_eb_window_av(m) =                        &
2195                                          surf_usm_v(l)%iwghf_eb_window_av(m) /        &
2196                                          REAL( average_count_3d, kind=wp )
2197                       ENDDO
2198                    ENDIF
2199                   
2200                CASE ( 'usm_t_surf_wall' )
2201!
2202!--                 surface temperature for surfaces
2203                    IF ( l == -1 ) THEN
2204                       DO  m = 1, surf_usm_h%ns
2205                       surf_usm_h%t_surf_wall_av(m) =                               & 
2206                                          surf_usm_h%t_surf_wall_av(m) /            &
2207                                             REAL( average_count_3d, kind=wp )
2208                       ENDDO
2209                    ELSE
2210                       DO  m = 1, surf_usm_v(l)%ns
2211                          surf_usm_v(l)%t_surf_wall_av(m) =                         &
2212                                          surf_usm_v(l)%t_surf_wall_av(m) /         &
2213                                          REAL( average_count_3d, kind=wp )
2214                       ENDDO
2215                    ENDIF
2216                   
2217                CASE ( 'usm_t_surf_window' )
2218!
2219!--                 surface temperature for window surfaces
2220                    IF ( l == -1 ) THEN
2221                       DO  m = 1, surf_usm_h%ns
2222                          surf_usm_h%t_surf_window_av(m) =                               &
2223                                             surf_usm_h%t_surf_window_av(m) /            &
2224                                             REAL( average_count_3d, kind=wp )
2225                       ENDDO
2226                    ELSE
2227                       DO  m = 1, surf_usm_v(l)%ns
2228                          surf_usm_v(l)%t_surf_window_av(m) =                         &
2229                                          surf_usm_v(l)%t_surf_window_av(m) /         &
2230                                          REAL( average_count_3d, kind=wp )
2231                       ENDDO
2232                    ENDIF
2233                   
2234                CASE ( 'usm_t_surf_green' )
2235!
2236!--                 surface temperature for green surfaces
2237                    IF ( l == -1 ) THEN
2238                       DO  m = 1, surf_usm_h%ns
2239                          surf_usm_h%t_surf_green_av(m) =                               &
2240                                             surf_usm_h%t_surf_green_av(m) /            &
2241                                             REAL( average_count_3d, kind=wp )
2242                       ENDDO
2243                    ELSE
2244                       DO  m = 1, surf_usm_v(l)%ns
2245                          surf_usm_v(l)%t_surf_green_av(m) =                         &
2246                                          surf_usm_v(l)%t_surf_green_av(m) /         &
2247                                          REAL( average_count_3d, kind=wp )
2248                       ENDDO
2249                    ENDIF
2250                   
2251                CASE ( 'usm_theta_10cm' )
2252!
2253!--                 near surface temperature for whole surfaces
2254                    IF ( l == -1 ) THEN
2255                       DO  m = 1, surf_usm_h%ns
2256                          surf_usm_h%pt_10cm_av(m) =                               &
2257                                             surf_usm_h%pt_10cm_av(m) /            &
2258                                             REAL( average_count_3d, kind=wp )
2259                       ENDDO
2260                    ELSE
2261                       DO  m = 1, surf_usm_v(l)%ns
2262                          surf_usm_v(l)%pt_10cm_av(m) =                         &
2263                                          surf_usm_v(l)%pt_10cm_av(m) /         &
2264                                          REAL( average_count_3d, kind=wp )
2265                       ENDDO
2266                    ENDIF
2267
2268                   
2269                CASE ( 'usm_t_wall' )
2270!
2271!--                 wall temperature for  iwl layer of walls and land
2272                    IF ( l == -1 ) THEN
2273                       DO  m = 1, surf_usm_h%ns
2274                          surf_usm_h%t_wall_av(iwl,m) =                           &
2275                                             surf_usm_h%t_wall_av(iwl,m) /        &
2276                                             REAL( average_count_3d, kind=wp )
2277                       ENDDO
2278                    ELSE
2279                       DO  m = 1, surf_usm_v(l)%ns
2280                          surf_usm_v(l)%t_wall_av(iwl,m) =                     &
2281                                          surf_usm_v(l)%t_wall_av(iwl,m) /     &
2282                                          REAL( average_count_3d, kind=wp )
2283                       ENDDO
2284                    ENDIF
2285
2286                CASE ( 'usm_t_window' )
2287!
2288!--                 window temperature for  iwl layer of walls and land
2289                    IF ( l == -1 ) THEN
2290                       DO  m = 1, surf_usm_h%ns
2291                          surf_usm_h%t_window_av(iwl,m) =                           &
2292                                             surf_usm_h%t_window_av(iwl,m) /        &
2293                                             REAL( average_count_3d, kind=wp )
2294                       ENDDO
2295                    ELSE
2296                       DO  m = 1, surf_usm_v(l)%ns
2297                          surf_usm_v(l)%t_window_av(iwl,m) =                     &
2298                                          surf_usm_v(l)%t_window_av(iwl,m) /     &
2299                                          REAL( average_count_3d, kind=wp )
2300                       ENDDO
2301                    ENDIF
2302
2303                CASE ( 'usm_t_green' )
2304!
2305!--                 green temperature for  iwl layer of walls and land
2306                    IF ( l == -1 ) THEN
2307                       DO  m = 1, surf_usm_h%ns
2308                          surf_usm_h%t_green_av(iwl,m) =                           &
2309                                             surf_usm_h%t_green_av(iwl,m) /        &
2310                                             REAL( average_count_3d, kind=wp )
2311                       ENDDO
2312                    ELSE
2313                       DO  m = 1, surf_usm_v(l)%ns
2314                          surf_usm_v(l)%t_green_av(iwl,m) =                     &
2315                                          surf_usm_v(l)%t_green_av(iwl,m) /     &
2316                                          REAL( average_count_3d, kind=wp )
2317                       ENDDO
2318                    ENDIF
2319                   
2320                CASE ( 'usm_swc' )
2321!
2322!--                 soil water content for  iwl layer of walls and land
2323                    IF ( l == -1 ) THEN
2324                    DO  m = 1, surf_usm_h%ns
2325                       surf_usm_h%swc_av(iwl,m) =                           &
2326                                          surf_usm_h%swc_av(iwl,m) /        &
2327                                          REAL( average_count_3d, kind=wp )
2328                    ENDDO
2329                    ELSE
2330                       DO  m = 1, surf_usm_v(l)%ns
2331                          surf_usm_v(l)%swc_av(iwl,m) =                     &
2332                                          surf_usm_v(l)%swc_av(iwl,m) /     &
2333                                          REAL( average_count_3d, kind=wp )
2334                       ENDDO
2335                    ENDIF
2336
2337
2338           END SELECT
2339
2340        ENDIF
2341
2342        ENDIF
2343
2344    END SUBROUTINE usm_3d_data_averaging
2345
2346
2347
2348!------------------------------------------------------------------------------!
2349! Description:
2350! ------------
2351!> Set internal Neumann boundary condition at outer soil grid points
2352!> for temperature and humidity.
2353!------------------------------------------------------------------------------!
2354 SUBROUTINE usm_boundary_condition
2355 
2356    IMPLICIT NONE
2357
2358    INTEGER(iwp) :: i      !< grid index x-direction
2359    INTEGER(iwp) :: ioff   !< offset index x-direction indicating location of soil grid point
2360    INTEGER(iwp) :: j      !< grid index y-direction
2361    INTEGER(iwp) :: joff   !< offset index x-direction indicating location of soil grid point
2362    INTEGER(iwp) :: k      !< grid index z-direction
2363    INTEGER(iwp) :: koff   !< offset index x-direction indicating location of soil grid point
2364    INTEGER(iwp) :: l      !< running index surface-orientation
2365    INTEGER(iwp) :: m      !< running index surface elements
2366
2367    koff = surf_usm_h%koff
2368    DO  m = 1, surf_usm_h%ns
2369       i = surf_usm_h%i(m)
2370       j = surf_usm_h%j(m)
2371       k = surf_usm_h%k(m)
2372       pt(k+koff,j,i) = pt(k,j,i)
2373    ENDDO
2374
2375    DO  l = 0, 3
2376       ioff = surf_usm_v(l)%ioff
2377       joff = surf_usm_v(l)%joff
2378       DO  m = 1, surf_usm_v(l)%ns
2379          i = surf_usm_v(l)%i(m)
2380          j = surf_usm_v(l)%j(m)
2381          k = surf_usm_v(l)%k(m)
2382          pt(k,j+joff,i+ioff) = pt(k,j,i)
2383       ENDDO
2384    ENDDO
2385
2386 END SUBROUTINE usm_boundary_condition
2387
2388
2389!------------------------------------------------------------------------------!
2390!
2391! Description:
2392! ------------
2393!> Subroutine checks variables and assigns units.
2394!> It is called out from subroutine check_parameters.
2395!------------------------------------------------------------------------------!
2396    SUBROUTINE usm_check_data_output( variable, unit )
2397
2398        IMPLICIT NONE
2399
2400        CHARACTER(LEN=*),INTENT(IN)    ::  variable   !<
2401        CHARACTER(LEN=*),INTENT(OUT)   ::  unit       !<
2402
2403        INTEGER(iwp)                                  :: i,j,l         !< index
2404        CHARACTER(LEN=2)                              :: ls
2405        CHARACTER(LEN=varnamelength)                  :: var           !< TRIM(variable)
2406        INTEGER(iwp), PARAMETER                       :: nl1 = 14      !< number of directional usm variables
2407        CHARACTER(LEN=varnamelength), DIMENSION(nl1)  :: varlist1 = &  !< list of directional usm variables
2408                  (/'usm_wshf                      ', &
2409                    'usm_wghf                      ', &
2410                    'usm_wghf_window               ', &
2411                    'usm_wghf_green                ', &
2412                    'usm_iwghf                     ', &
2413                    'usm_iwghf_window              ', &
2414                    'usm_surfz                     ', &
2415                    'usm_surfwintrans              ', &
2416                    'usm_surfcat                   ', &
2417                    'usm_t_surf_wall               ', &
2418                    'usm_t_surf_window             ', &
2419                    'usm_t_surf_green              ', &
2420                    'usm_t_green                   ', &
2421                    'usm_theta_10cm                '/)
2422
2423        INTEGER(iwp), PARAMETER                       :: nl2 = 3       !< number of directional layer usm variables
2424        CHARACTER(LEN=varnamelength), DIMENSION(nl2)  :: varlist2 = &  !< list of directional layer usm variables
2425                  (/'usm_t_wall                    ', &
2426                    'usm_t_window                  ', &
2427                    'usm_t_green                   '/)
2428
2429        INTEGER(iwp), PARAMETER                       :: nd = 5     !< number of directions
2430        CHARACTER(LEN=6), DIMENSION(nd), PARAMETER  :: dirname = &  !< direction names
2431                  (/'_roof ','_south','_north','_west ','_east '/)
2432        LOGICAL                                       :: lfound     !< flag if the variable is found
2433
2434
2435        lfound = .FALSE.
2436
2437        var = TRIM(variable)
2438
2439!
2440!--     check if variable exists
2441!--     directional variables
2442        DO i = 1, nl1
2443           DO j = 1, nd
2444              IF ( TRIM(var) == TRIM(varlist1(i))//TRIM(dirname(j)) ) THEN
2445                 lfound = .TRUE.
2446                 EXIT
2447              ENDIF
2448              IF ( lfound ) EXIT
2449           ENDDO
2450        ENDDO
2451        IF ( lfound ) GOTO 10
2452!
2453!--     directional layer variables
2454        DO i = 1, nl2
2455           DO j = 1, nd
2456              DO l = nzb_wall, nzt_wall
2457                 WRITE(ls,'(A1,I1)') '_',l
2458                 IF ( TRIM(var) == TRIM(varlist2(i))//TRIM(ls)//TRIM(dirname(j)) ) THEN
2459                    lfound = .TRUE.
2460                    EXIT
2461                 ENDIF
2462              ENDDO
2463              IF ( lfound ) EXIT
2464           ENDDO
2465        ENDDO
2466        IF ( .NOT.  lfound ) THEN
2467           unit = 'illegal'
2468           RETURN
2469        ENDIF
247010      CONTINUE
2471
2472        IF ( var(1:9)  == 'usm_wshf_'  .OR.  var(1:9) == 'usm_wghf_' .OR.                 &
2473             var(1:16) == 'usm_wghf_window_' .OR. var(1:15) == 'usm_wghf_green_' .OR.     &
2474             var(1:10) == 'usm_iwghf_' .OR. var(1:17) == 'usm_iwghf_window_'    .OR.      &
2475             var(1:17) == 'usm_surfwintrans_' .OR.                                        &
2476             var(1:9)  == 'usm_qsws_'  .OR.  var(1:13)  == 'usm_qsws_veg_'  .OR.          &
2477             var(1:13) == 'usm_qsws_liq_' ) THEN
2478            unit = 'W/m2'
2479        ELSE IF ( var(1:15) == 'usm_t_surf_wall'   .OR.  var(1:10) == 'usm_t_wall' .OR.   &
2480                  var(1:12) == 'usm_t_window' .OR. var(1:17) == 'usm_t_surf_window' .OR.  &
2481                  var(1:16) == 'usm_t_surf_green'  .OR.                                   &
2482                  var(1:11) == 'usm_t_green' .OR.  var(1:7) == 'usm_swc' .OR.             &
2483                  var(1:14) == 'usm_theta_10cm' )  THEN
2484            unit = 'K'
2485        ELSE IF ( var(1:9) == 'usm_surfz'  .OR.  var(1:11) == 'usm_surfcat' )  THEN
2486            unit = '1'
2487        ELSE
2488            unit = 'illegal'
2489        ENDIF
2490
2491    END SUBROUTINE usm_check_data_output
2492
2493
2494!------------------------------------------------------------------------------!
2495! Description:
2496! ------------
2497!> Check parameters routine for urban surface model
2498!------------------------------------------------------------------------------!
2499    SUBROUTINE usm_check_parameters
2500
2501       USE control_parameters,                                                 &
2502           ONLY:  bc_pt_b, bc_q_b, constant_flux_layer, large_scale_forcing,   &
2503                  lsf_surf, topography
2504
2505       USE netcdf_data_input_mod,                                             &
2506            ONLY:  building_type_f
2507
2508       IMPLICIT NONE
2509
2510       INTEGER(iwp) ::  i        !< running index, x-dimension
2511       INTEGER(iwp) ::  j        !< running index, y-dimension
2512
2513!
2514!--    Dirichlet boundary conditions are required as the surface fluxes are
2515!--    calculated from the temperature/humidity gradients in the urban surface
2516!--    model
2517       IF ( bc_pt_b == 'neumann'   .OR.   bc_q_b == 'neumann' )  THEN
2518          message_string = 'urban surface model requires setting of '//        &
2519                           'bc_pt_b = "dirichlet" and '//                      &
2520                           'bc_q_b  = "dirichlet"'
2521          CALL message( 'usm_check_parameters', 'PA0590', 1, 2, 0, 6, 0 )
2522       ENDIF
2523
2524       IF ( .NOT.  constant_flux_layer )  THEN
2525          message_string = 'urban surface model requires '//                   &
2526                           'constant_flux_layer = .T.'
2527          CALL message( 'usm_check_parameters', 'PA0084', 1, 2, 0, 6, 0 )
2528       ENDIF
2529
2530       IF (  .NOT.  radiation )  THEN
2531          message_string = 'urban surface model requires '//                   &
2532                           'the radiation model to be switched on'
2533          CALL message( 'usm_check_parameters', 'PA0084', 1, 2, 0, 6, 0 )
2534       ENDIF
2535!       
2536!--    Surface forcing has to be disabled for LSF in case of enabled
2537!--    urban surface module
2538       IF ( large_scale_forcing )  THEN
2539          lsf_surf = .FALSE.
2540       ENDIF
2541!
2542!--    Topography
2543       IF ( topography == 'flat' )  THEN
2544          message_string = 'topography /= "flat" is required '//               &
2545                           'when using the urban surface model'
2546          CALL message( 'usm_check_parameters', 'PA0592', 1, 2, 0, 6, 0 )
2547       ENDIF
2548!
2549!--    naheatlayers
2550       IF ( naheatlayers > nzt )  THEN
2551          message_string = 'number of anthropogenic heat layers '//            &
2552                           '"naheatlayers" can not be larger than'//           &
2553                           ' number of domain layers "nzt"'
2554          CALL message( 'usm_check_parameters', 'PA0593', 1, 2, 0, 6, 0 )
2555       ENDIF
2556!
2557!--    Check if building types are set within a valid range.
2558       IF ( building_type < LBOUND( building_pars, 2 )  .AND.                  &
2559            building_type > UBOUND( building_pars, 2 ) )  THEN
2560          WRITE( message_string, * ) 'building_type = ', building_type,        &
2561                                     ' is out of the valid range'
2562          CALL message( 'usm_check_parameters', 'PA0529', 2, 2, 0, 6, 0 )
2563       ENDIF
2564       IF ( building_type_f%from_file )  THEN
2565          DO  i = nxl, nxr
2566             DO  j = nys, nyn
2567                IF ( building_type_f%var(j,i) /= building_type_f%fill  .AND.   &
2568              ( building_type_f%var(j,i) < LBOUND( building_pars, 2 )  .OR.    &
2569                building_type_f%var(j,i) > UBOUND( building_pars, 2 ) ) )      &
2570                THEN
2571                   WRITE( message_string, * ) 'building_type = is out of ' //  &
2572                                        'the valid range at (j,i) = ', j, i
2573                   CALL message( 'usm_check_parameters', 'PA0529', 2, 2, 0, 6, 0 )
2574                ENDIF
2575             ENDDO
2576          ENDDO
2577       ENDIF
2578    END SUBROUTINE usm_check_parameters
2579
2580
2581!------------------------------------------------------------------------------!
2582!
2583! Description:
2584! ------------
2585!> Output of the 3D-arrays in netCDF and/or AVS format
2586!> for variables of urban_surface model.
2587!> It resorts the urban surface module output quantities from surf style
2588!> indexing into temporary 3D array with indices (i,j,k).
2589!> It is called from subroutine data_output_3d.
2590!------------------------------------------------------------------------------!
2591    SUBROUTINE usm_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
2592       
2593        IMPLICIT NONE
2594
2595        INTEGER(iwp), INTENT(IN)       ::  av        !< flag if averaged
2596        CHARACTER (len=*), INTENT(IN)  ::  variable  !< variable name
2597        INTEGER(iwp), INTENT(IN)       ::  nzb_do    !< lower limit of the data output (usually 0)
2598        INTEGER(iwp), INTENT(IN)       ::  nzt_do    !< vertical upper limit of the data output (usually nz_do3d)
2599        LOGICAL, INTENT(OUT)           ::  found     !<
2600        REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf   !< sp - it has to correspond to module data_output_3d
2601        REAL(sp), DIMENSION(nzb:nzt+1,nys:nyn,nxl:nxr)     ::  temp_pf    !< temp array for urban surface output procedure
2602       
2603        CHARACTER (len=varnamelength)                      :: var     !< trimmed variable name
2604        INTEGER(iwp), PARAMETER                            :: nd = 5  !< number of directions
2605        CHARACTER(len=6), DIMENSION(0:nd-1), PARAMETER     :: dirname = (/ '_roof ', '_south', '_north', '_west ', '_east ' /)
2606        INTEGER(iwp), DIMENSION(0:nd-1), PARAMETER         :: dirint =  (/    iup_u, isouth_u, inorth_u,  iwest_u,  ieast_u /)
2607        INTEGER(iwp), DIMENSION(0:nd-1), PARAMETER         :: diridx =  (/       -1,        1,        0,        3,        2 /)
2608                                                                      !< index for surf_*_v: 0:3 = (North, South, East, West)
2609        INTEGER(iwp)                   :: ids,idsint,idsidx
2610        INTEGER(iwp)                   :: i,j,k,iwl,istat, l, m  !< running indices
2611
2612        found = .TRUE.
2613        temp_pf = -1._wp
2614       
2615        ids = -1
2616        var = TRIM(variable)
2617        DO i = 0, nd-1
2618            k = len(TRIM(var))
2619            j = len(TRIM(dirname(i)))
2620            IF ( TRIM(var(k-j+1:k)) == TRIM(dirname(i)) )  THEN
2621                ids = i
2622                idsint = dirint(ids)
2623                idsidx = diridx(ids)
2624                var = var(:k-j)
2625                EXIT
2626            ENDIF
2627        ENDDO
2628        IF ( ids == -1 )  THEN
2629            var = TRIM(variable)
2630        ENDIF
2631        IF ( var(1:11) == 'usm_t_wall_'  .AND.  len(TRIM(var)) >= 12 )  THEN
2632!
2633!--         wall layers
2634            READ(var(12:12), '(I1)', iostat=istat ) iwl
2635            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
2636                var = var(1:10)
2637            ENDIF
2638        ENDIF
2639        IF ( var(1:13) == 'usm_t_window_'  .AND.  len(TRIM(var)) >= 14 )  THEN
2640!
2641!--         window layers
2642            READ(var(14:14), '(I1)', iostat=istat ) iwl
2643            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
2644                var = var(1:12)
2645            ENDIF
2646        ENDIF
2647        IF ( var(1:12) == 'usm_t_green_'  .AND.  len(TRIM(var)) >= 13 )  THEN
2648!
2649!--         green layers
2650            READ(var(13:13), '(I1)', iostat=istat ) iwl
2651            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
2652                var = var(1:11)
2653            ENDIF
2654        ENDIF
2655        IF ( var(1:8) == 'usm_swc_'  .AND.  len(TRIM(var)) >= 9 )  THEN
2656!
2657!--         green layers soil water content
2658            READ(var(9:9), '(I1)', iostat=istat ) iwl
2659            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
2660                var = var(1:7)
2661            ENDIF
2662        ENDIF
2663       
2664        SELECT CASE ( TRIM(var) )
2665
2666          CASE ( 'usm_surfz' )
2667!
2668!--           array of surface height (z)
2669              IF ( idsint == iup_u )  THEN
2670                 DO  m = 1, surf_usm_h%ns
2671                    i = surf_usm_h%i(m)
2672                    j = surf_usm_h%j(m)
2673                    k = surf_usm_h%k(m)
2674                    temp_pf(0,j,i) = MAX( temp_pf(0,j,i), REAL( k, KIND = sp) )
2675                 ENDDO
2676              ELSE
2677                 l = idsidx
2678                 DO  m = 1, surf_usm_v(l)%ns
2679                    i = surf_usm_v(l)%i(m)
2680                    j = surf_usm_v(l)%j(m)
2681                    k = surf_usm_v(l)%k(m)
2682                    temp_pf(0,j,i) = MAX( temp_pf(0,j,i), REAL( k, KIND = sp) + 1.0_sp )
2683                 ENDDO
2684              ENDIF
2685
2686          CASE ( 'usm_surfcat' )
2687!
2688!--           surface category
2689              IF ( idsint == iup_u )  THEN
2690                 DO  m = 1, surf_usm_h%ns
2691                    i = surf_usm_h%i(m)
2692                    j = surf_usm_h%j(m)
2693                    k = surf_usm_h%k(m)
2694                    temp_pf(k,j,i) = surf_usm_h%surface_types(m)
2695                 ENDDO
2696              ELSE
2697                 l = idsidx
2698                 DO  m = 1, surf_usm_v(l)%ns
2699                    i = surf_usm_v(l)%i(m)
2700                    j = surf_usm_v(l)%j(m)
2701                    k = surf_usm_v(l)%k(m)
2702                    temp_pf(k,j,i) = surf_usm_v(l)%surface_types(m)
2703                 ENDDO
2704              ENDIF
2705             
2706          CASE ( 'usm_surfwintrans' )
2707!
2708!--           transmissivity window tiles
2709              IF ( idsint == iup_u )  THEN
2710                 DO  m = 1, surf_usm_h%ns
2711                    i = surf_usm_h%i(m)
2712                    j = surf_usm_h%j(m)
2713                    k = surf_usm_h%k(m)
2714                    temp_pf(k,j,i) = surf_usm_h%transmissivity(m)
2715                 ENDDO
2716              ELSE
2717                 l = idsidx
2718                 DO  m = 1, surf_usm_v(l)%ns
2719                    i = surf_usm_v(l)%i(m)
2720                    j = surf_usm_v(l)%j(m)
2721                    k = surf_usm_v(l)%k(m)
2722                    temp_pf(k,j,i) = surf_usm_v(l)%transmissivity(m)
2723                 ENDDO
2724              ENDIF
2725
2726          CASE ( 'usm_wshf' )
2727!
2728!--           array of sensible heat flux from surfaces
2729              IF ( av == 0 )  THEN
2730                 IF ( idsint == iup_u )  THEN
2731                    DO  m = 1, surf_usm_h%ns
2732                       i = surf_usm_h%i(m)
2733                       j = surf_usm_h%j(m)
2734                       k = surf_usm_h%k(m)
2735                       temp_pf(k,j,i) = surf_usm_h%wshf_eb(m)
2736                    ENDDO
2737                 ELSE
2738                    l = idsidx
2739                    DO  m = 1, surf_usm_v(l)%ns
2740                       i = surf_usm_v(l)%i(m)
2741                       j = surf_usm_v(l)%j(m)
2742                       k = surf_usm_v(l)%k(m)
2743                       temp_pf(k,j,i) = surf_usm_v(l)%wshf_eb(m)
2744                    ENDDO
2745                 ENDIF
2746              ELSE
2747                 IF ( idsint == iup_u )  THEN
2748                    DO  m = 1, surf_usm_h%ns
2749                       i = surf_usm_h%i(m)
2750                       j = surf_usm_h%j(m)
2751                       k = surf_usm_h%k(m)
2752                       temp_pf(k,j,i) = surf_usm_h%wshf_eb_av(m)
2753                    ENDDO
2754                 ELSE
2755                    l = idsidx
2756                    DO  m = 1, surf_usm_v(l)%ns
2757                       i = surf_usm_v(l)%i(m)
2758                       j = surf_usm_v(l)%j(m)
2759                       k = surf_usm_v(l)%k(m)
2760                       temp_pf(k,j,i) = surf_usm_v(l)%wshf_eb_av(m)
2761                    ENDDO
2762                 ENDIF
2763              ENDIF
2764             
2765             
2766          CASE ( 'usm_qsws' )
2767!
2768!--           array of latent heat flux from surfaces
2769              IF ( av == 0 )  THEN
2770                 IF ( idsint == iup_u )  THEN
2771                    DO  m = 1, surf_usm_h%ns
2772                       i = surf_usm_h%i(m)
2773                       j = surf_usm_h%j(m)
2774                       k = surf_usm_h%k(m)
2775                       temp_pf(k,j,i) = surf_usm_h%qsws_eb(m)
2776                    ENDDO
2777                 ELSE
2778                    l = idsidx
2779                    DO  m = 1, surf_usm_v(l)%ns
2780                       i = surf_usm_v(l)%i(m)
2781                       j = surf_usm_v(l)%j(m)
2782                       k = surf_usm_v(l)%k(m)
2783                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_eb(m)
2784                    ENDDO
2785                 ENDIF
2786              ELSE
2787                 IF ( idsint == iup_u )  THEN
2788                    DO  m = 1, surf_usm_h%ns
2789                       i = surf_usm_h%i(m)
2790                       j = surf_usm_h%j(m)
2791                       k = surf_usm_h%k(m)
2792                       temp_pf(k,j,i) = surf_usm_h%qsws_eb_av(m)
2793                    ENDDO
2794                 ELSE
2795                    l = idsidx
2796                    DO  m = 1, surf_usm_v(l)%ns
2797                       i = surf_usm_v(l)%i(m)
2798                       j = surf_usm_v(l)%j(m)
2799                       k = surf_usm_v(l)%k(m)
2800                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_eb_av(m)
2801                    ENDDO
2802                 ENDIF
2803              ENDIF
2804             
2805          CASE ( 'usm_qsws_veg' )
2806!
2807!--           array of latent heat flux from vegetation surfaces
2808              IF ( av == 0 )  THEN
2809                 IF ( idsint == iup_u )  THEN
2810                    DO  m = 1, surf_usm_h%ns
2811                       i = surf_usm_h%i(m)
2812                       j = surf_usm_h%j(m)
2813                       k = surf_usm_h%k(m)
2814                       temp_pf(k,j,i) = surf_usm_h%qsws_veg(m)
2815                    ENDDO
2816                 ELSE
2817                    l = idsidx
2818                    DO  m = 1, surf_usm_v(l)%ns
2819                       i = surf_usm_v(l)%i(m)
2820                       j = surf_usm_v(l)%j(m)
2821                       k = surf_usm_v(l)%k(m)
2822                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_veg(m)
2823                    ENDDO
2824                 ENDIF
2825              ELSE
2826                 IF ( idsint == iup_u )  THEN
2827                    DO  m = 1, surf_usm_h%ns
2828                       i = surf_usm_h%i(m)
2829                       j = surf_usm_h%j(m)
2830                       k = surf_usm_h%k(m)
2831                       temp_pf(k,j,i) = surf_usm_h%qsws_veg_av(m)
2832                    ENDDO
2833                 ELSE
2834                    l = idsidx
2835                    DO  m = 1, surf_usm_v(l)%ns
2836                       i = surf_usm_v(l)%i(m)
2837                       j = surf_usm_v(l)%j(m)
2838                       k = surf_usm_v(l)%k(m)
2839                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_veg_av(m)
2840                    ENDDO
2841                 ENDIF
2842              ENDIF
2843             
2844          CASE ( 'usm_qsws_liq' )
2845!
2846!--           array of latent heat flux from surfaces with liquid
2847              IF ( av == 0 )  THEN
2848                 IF ( idsint == iup_u )  THEN
2849                    DO  m = 1, surf_usm_h%ns
2850                       i = surf_usm_h%i(m)
2851                       j = surf_usm_h%j(m)
2852                       k = surf_usm_h%k(m)
2853                       temp_pf(k,j,i) = surf_usm_h%qsws_liq(m)
2854                    ENDDO
2855                 ELSE
2856                    l = idsidx
2857                    DO  m = 1, surf_usm_v(l)%ns
2858                       i = surf_usm_v(l)%i(m)
2859                       j = surf_usm_v(l)%j(m)
2860                       k = surf_usm_v(l)%k(m)
2861                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_liq(m)
2862                    ENDDO
2863                 ENDIF
2864              ELSE
2865                 IF ( idsint == iup_u )  THEN
2866                    DO  m = 1, surf_usm_h%ns
2867                       i = surf_usm_h%i(m)
2868                       j = surf_usm_h%j(m)
2869                       k = surf_usm_h%k(m)
2870                       temp_pf(k,j,i) = surf_usm_h%qsws_liq_av(m)
2871                    ENDDO
2872                 ELSE
2873                    l = idsidx
2874                    DO  m = 1, surf_usm_v(l)%ns
2875                       i = surf_usm_v(l)%i(m)
2876                       j = surf_usm_v(l)%j(m)
2877                       k = surf_usm_v(l)%k(m)
2878                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_liq_av(m)
2879                    ENDDO
2880                 ENDIF
2881              ENDIF
2882
2883          CASE ( 'usm_wghf' )
2884!
2885!--           array of heat flux from ground (land, wall, roof)
2886              IF ( av == 0 )  THEN
2887                 IF ( idsint == iup_u )  THEN
2888                    DO  m = 1, surf_usm_h%ns
2889                       i = surf_usm_h%i(m)
2890                       j = surf_usm_h%j(m)
2891                       k = surf_usm_h%k(m)
2892                       temp_pf(k,j,i) = surf_usm_h%wghf_eb(m)
2893                    ENDDO
2894                 ELSE
2895                    l = idsidx
2896                    DO  m = 1, surf_usm_v(l)%ns
2897                       i = surf_usm_v(l)%i(m)
2898                       j = surf_usm_v(l)%j(m)
2899                       k = surf_usm_v(l)%k(m)
2900                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb(m)
2901                    ENDDO
2902                 ENDIF
2903              ELSE
2904                 IF ( idsint == iup_u )  THEN
2905                    DO  m = 1, surf_usm_h%ns
2906                       i = surf_usm_h%i(m)
2907                       j = surf_usm_h%j(m)
2908                       k = surf_usm_h%k(m)
2909                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_av(m)
2910                    ENDDO
2911                 ELSE
2912                    l = idsidx
2913                    DO  m = 1, surf_usm_v(l)%ns
2914                       i = surf_usm_v(l)%i(m)
2915                       j = surf_usm_v(l)%j(m)
2916                       k = surf_usm_v(l)%k(m)
2917                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_av(m)
2918                    ENDDO
2919                 ENDIF
2920              ENDIF
2921
2922          CASE ( 'usm_wghf_window' )
2923!
2924!--           array of heat flux from window ground (land, wall, roof)
2925              IF ( av == 0 )  THEN
2926                 IF ( idsint == iup_u )  THEN
2927                    DO  m = 1, surf_usm_h%ns
2928                       i = surf_usm_h%i(m)
2929                       j = surf_usm_h%j(m)
2930                       k = surf_usm_h%k(m)
2931                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_window(m)
2932                    ENDDO
2933                 ELSE
2934                    l = idsidx
2935                    DO  m = 1, surf_usm_v(l)%ns
2936                       i = surf_usm_v(l)%i(m)
2937                       j = surf_usm_v(l)%j(m)
2938                       k = surf_usm_v(l)%k(m)
2939                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_window(m)
2940                    ENDDO
2941                 ENDIF
2942              ELSE
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%wghf_eb_window_av(m)
2949                    ENDDO
2950                 ELSE
2951                    l = idsidx
2952                    DO  m = 1, surf_usm_v(l)%ns
2953                       i = surf_usm_v(l)%i(m)
2954                       j = surf_usm_v(l)%j(m)
2955                       k = surf_usm_v(l)%k(m)
2956                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_window_av(m)
2957                    ENDDO
2958                 ENDIF
2959              ENDIF
2960
2961          CASE ( 'usm_wghf_green' )
2962!
2963!--           array of heat flux from green ground (land, wall, roof)
2964              IF ( av == 0 )  THEN
2965                 IF ( idsint == iup_u )  THEN
2966                    DO  m = 1, surf_usm_h%ns
2967                       i = surf_usm_h%i(m)
2968                       j = surf_usm_h%j(m)
2969                       k = surf_usm_h%k(m)
2970                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_green(m)
2971                    ENDDO
2972                 ELSE
2973                    l = idsidx
2974                    DO  m = 1, surf_usm_v(l)%ns
2975                       i = surf_usm_v(l)%i(m)
2976                       j = surf_usm_v(l)%j(m)
2977                       k = surf_usm_v(l)%k(m)
2978                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_green(m)
2979                    ENDDO
2980                 ENDIF
2981              ELSE
2982                 IF ( idsint == iup_u )  THEN
2983                    DO  m = 1, surf_usm_h%ns
2984                       i = surf_usm_h%i(m)
2985                       j = surf_usm_h%j(m)
2986                       k = surf_usm_h%k(m)
2987                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_green_av(m)
2988                    ENDDO
2989                 ELSE
2990                    l = idsidx
2991                    DO  m = 1, surf_usm_v(l)%ns
2992                       i = surf_usm_v(l)%i(m)
2993                       j = surf_usm_v(l)%j(m)
2994                       k = surf_usm_v(l)%k(m)
2995                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_green_av(m)
2996                    ENDDO
2997                 ENDIF
2998              ENDIF
2999
3000          CASE ( 'usm_iwghf' )
3001!
3002!--           array of heat flux from indoor ground (land, wall, roof)
3003              IF ( av == 0 )  THEN
3004                 IF ( idsint == iup_u )  THEN
3005                    DO  m = 1, surf_usm_h%ns
3006                       i = surf_usm_h%i(m)
3007                       j = surf_usm_h%j(m)
3008                       k = surf_usm_h%k(m)
3009                       temp_pf(k,j,i) = surf_usm_h%iwghf_eb(m)
3010                    ENDDO
3011                 ELSE
3012                    l = idsidx
3013                    DO  m = 1, surf_usm_v(l)%ns
3014                       i = surf_usm_v(l)%i(m)
3015                       j = surf_usm_v(l)%j(m)
3016                       k = surf_usm_v(l)%k(m)
3017                       temp_pf(k,j,i) = surf_usm_v(l)%iwghf_eb(m)
3018                    ENDDO
3019                 ENDIF
3020              ELSE
3021                 IF ( idsint == iup_u )  THEN
3022                    DO  m = 1, surf_usm_h%ns
3023                       i = surf_usm_h%i(m)
3024                       j = surf_usm_h%j(m)
3025                       k = surf_usm_h%k(m)
3026                       temp_pf(k,j,i) = surf_usm_h%iwghf_eb_av(m)
3027                    ENDDO
3028                 ELSE
3029                    l = idsidx
3030                    DO  m = 1, surf_usm_v(l)%ns
3031                       i = surf_usm_v(l)%i(m)
3032                       j = surf_usm_v(l)%j(m)
3033                       k = surf_usm_v(l)%k(m)
3034                       temp_pf(k,j,i) = surf_usm_v(l)%iwghf_eb_av(m)
3035                    ENDDO
3036                 ENDIF
3037              ENDIF
3038
3039          CASE ( 'usm_iwghf_window' )
3040!
3041!--           array of heat flux from indoor window ground (land, wall, roof)
3042              IF ( av == 0 )  THEN
3043                 IF ( idsint == iup_u )  THEN
3044                    DO  m = 1, surf_usm_h%ns
3045                       i = surf_usm_h%i(m)
3046                       j = surf_usm_h%j(m)
3047                       k = surf_usm_h%k(m)
3048                       temp_pf(k,j,i) = surf_usm_h%iwghf_eb_window(m)
3049                    ENDDO
3050                 ELSE
3051                    l = idsidx
3052                    DO  m = 1, surf_usm_v(l)%ns
3053                       i = surf_usm_v(l)%i(m)
3054                       j = surf_usm_v(l)%j(m)
3055                       k = surf_usm_v(l)%k(m)
3056                       temp_pf(k,j,i) = surf_usm_v(l)%iwghf_eb_window(m)
3057                    ENDDO
3058                 ENDIF
3059              ELSE
3060                 IF ( idsint == iup_u )  THEN
3061                    DO  m = 1, surf_usm_h%ns
3062                       i = surf_usm_h%i(m)
3063                       j = surf_usm_h%j(m)
3064                       k = surf_usm_h%k(m)
3065                       temp_pf(k,j,i) = surf_usm_h%iwghf_eb_window_av(m)
3066                    ENDDO
3067                 ELSE
3068                    l = idsidx
3069                    DO  m = 1, surf_usm_v(l)%ns
3070                       i = surf_usm_v(l)%i(m)
3071                       j = surf_usm_v(l)%j(m)
3072                       k = surf_usm_v(l)%k(m)
3073                       temp_pf(k,j,i) = surf_usm_v(l)%iwghf_eb_window_av(m)
3074                    ENDDO
3075                 ENDIF
3076              ENDIF
3077             
3078          CASE ( 'usm_t_surf_wall' )
3079!
3080!--           surface temperature for surfaces
3081              IF ( av == 0 )  THEN
3082                 IF ( idsint == iup_u )  THEN
3083                    DO  m = 1, surf_usm_h%ns
3084                       i = surf_usm_h%i(m)
3085                       j = surf_usm_h%j(m)
3086                       k = surf_usm_h%k(m)
3087                       temp_pf(k,j,i) = t_surf_wall_h(m)
3088                    ENDDO
3089                 ELSE
3090                    l = idsidx
3091                    DO  m = 1, surf_usm_v(l)%ns
3092                       i = surf_usm_v(l)%i(m)
3093                       j = surf_usm_v(l)%j(m)
3094                       k = surf_usm_v(l)%k(m)
3095                       temp_pf(k,j,i) = t_surf_wall_v(l)%t(m)
3096                    ENDDO
3097                 ENDIF
3098              ELSE
3099                 IF ( idsint == iup_u )  THEN
3100                    DO  m = 1, surf_usm_h%ns
3101                       i = surf_usm_h%i(m)
3102                       j = surf_usm_h%j(m)
3103                       k = surf_usm_h%k(m)
3104                       temp_pf(k,j,i) = surf_usm_h%t_surf_wall_av(m)
3105                    ENDDO
3106                 ELSE
3107                    l = idsidx
3108                    DO  m = 1, surf_usm_v(l)%ns
3109                       i = surf_usm_v(l)%i(m)
3110                       j = surf_usm_v(l)%j(m)
3111                       k = surf_usm_v(l)%k(m)
3112                       temp_pf(k,j,i) = surf_usm_v(l)%t_surf_wall_av(m)
3113                    ENDDO
3114                 ENDIF
3115              ENDIF
3116             
3117          CASE ( 'usm_t_surf_window' )
3118!
3119!--           surface temperature for window surfaces
3120              IF ( av == 0 )  THEN
3121                 IF ( idsint == iup_u )  THEN
3122                    DO  m = 1, surf_usm_h%ns
3123                       i = surf_usm_h%i(m)
3124                       j = surf_usm_h%j(m)
3125                       k = surf_usm_h%k(m)
3126                       temp_pf(k,j,i) = t_surf_window_h(m)
3127                    ENDDO
3128                 ELSE
3129                    l = idsidx
3130                    DO  m = 1, surf_usm_v(l)%ns
3131                       i = surf_usm_v(l)%i(m)
3132                       j = surf_usm_v(l)%j(m)
3133                       k = surf_usm_v(l)%k(m)
3134                       temp_pf(k,j,i) = t_surf_window_v(l)%t(m)
3135                    ENDDO
3136                 ENDIF
3137
3138              ELSE
3139                 IF ( idsint == iup_u )  THEN
3140                    DO  m = 1, surf_usm_h%ns
3141                       i = surf_usm_h%i(m)
3142                       j = surf_usm_h%j(m)
3143                       k = surf_usm_h%k(m)
3144                       temp_pf(k,j,i) = surf_usm_h%t_surf_window_av(m)
3145                    ENDDO
3146                 ELSE
3147                    l = idsidx
3148                    DO  m = 1, surf_usm_v(l)%ns
3149                       i = surf_usm_v(l)%i(m)
3150                       j = surf_usm_v(l)%j(m)
3151                       k = surf_usm_v(l)%k(m)
3152                       temp_pf(k,j,i) = surf_usm_v(l)%t_surf_window_av(m)
3153                    ENDDO
3154
3155                 ENDIF
3156
3157              ENDIF
3158
3159          CASE ( 'usm_t_surf_green' )
3160!
3161!--           surface temperature for green surfaces
3162              IF ( av == 0 )  THEN
3163                 IF ( idsint == iup_u )  THEN
3164                    DO  m = 1, surf_usm_h%ns
3165                       i = surf_usm_h%i(m)
3166                       j = surf_usm_h%j(m)
3167                       k = surf_usm_h%k(m)
3168                       temp_pf(k,j,i) = t_surf_green_h(m)
3169                    ENDDO
3170                 ELSE
3171                    l = idsidx
3172                    DO  m = 1, surf_usm_v(l)%ns
3173                       i = surf_usm_v(l)%i(m)
3174                       j = surf_usm_v(l)%j(m)
3175                       k = surf_usm_v(l)%k(m)
3176                       temp_pf(k,j,i) = t_surf_green_v(l)%t(m)
3177                    ENDDO
3178                 ENDIF
3179
3180              ELSE
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%t_surf_green_av(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)%t_surf_green_av(m)
3195                    ENDDO
3196
3197                 ENDIF
3198
3199              ENDIF
3200
3201          CASE ( 'usm_theta_10cm' )
3202!
3203!--           near surface temperature for whole surfaces
3204              IF ( av == 0 )  THEN
3205                 IF ( idsint == iup_u )  THEN
3206                    DO  m = 1, surf_usm_h%ns
3207                       i = surf_usm_h%i(m)
3208                       j = surf_usm_h%j(m)
3209                       k = surf_usm_h%k(m)
3210                       temp_pf(k,j,i) = surf_usm_h%pt_10cm(m)
3211                    ENDDO
3212                 ELSE
3213                    l = idsidx
3214                    DO  m = 1, surf_usm_v(l)%ns
3215                       i = surf_usm_v(l)%i(m)
3216                       j = surf_usm_v(l)%j(m)
3217                       k = surf_usm_v(l)%k(m)
3218                       temp_pf(k,j,i) = surf_usm_v(l)%pt_10cm(m)
3219                    ENDDO
3220                 ENDIF
3221             
3222             
3223              ELSE
3224                 IF ( idsint == iup_u )  THEN
3225                    DO  m = 1, surf_usm_h%ns
3226                       i = surf_usm_h%i(m)
3227                       j = surf_usm_h%j(m)
3228                       k = surf_usm_h%k(m)
3229                       temp_pf(k,j,i) = surf_usm_h%pt_10cm_av(m)
3230                    ENDDO
3231                 ELSE
3232                    l = idsidx
3233                    DO  m = 1, surf_usm_v(l)%ns
3234                       i = surf_usm_v(l)%i(m)
3235                       j = surf_usm_v(l)%j(m)
3236                       k = surf_usm_v(l)%k(m)
3237                       temp_pf(k,j,i) = surf_usm_v(l)%pt_10cm_av(m)
3238                    ENDDO
3239
3240                  ENDIF
3241              ENDIF
3242             
3243          CASE ( 'usm_t_wall' )
3244!
3245!--           wall temperature for  iwl layer of walls and land
3246              IF ( av == 0 )  THEN
3247                 IF ( idsint == iup_u )  THEN
3248                    DO  m = 1, surf_usm_h%ns
3249                       i = surf_usm_h%i(m)
3250                       j = surf_usm_h%j(m)
3251                       k = surf_usm_h%k(m)
3252                       temp_pf(k,j,i) = t_wall_h(iwl,m)
3253                    ENDDO
3254                 ELSE
3255                    l = idsidx
3256                    DO  m = 1, surf_usm_v(l)%ns
3257                       i = surf_usm_v(l)%i(m)
3258                       j = surf_usm_v(l)%j(m)
3259                       k = surf_usm_v(l)%k(m)
3260                       temp_pf(k,j,i) = t_wall_v(l)%t(iwl,m)
3261                    ENDDO
3262                 ENDIF
3263              ELSE
3264                 IF ( idsint == iup_u )  THEN
3265                    DO  m = 1, surf_usm_h%ns
3266                       i = surf_usm_h%i(m)
3267                       j = surf_usm_h%j(m)
3268                       k = surf_usm_h%k(m)
3269                       temp_pf(k,j,i) = surf_usm_h%t_wall_av(iwl,m)
3270                    ENDDO
3271                 ELSE
3272                    l = idsidx
3273                    DO  m = 1, surf_usm_v(l)%ns
3274                       i = surf_usm_v(l)%i(m)
3275                       j = surf_usm_v(l)%j(m)
3276                       k = surf_usm_v(l)%k(m)
3277                       temp_pf(k,j,i) = surf_usm_v(l)%t_wall_av(iwl,m)
3278                    ENDDO
3279                 ENDIF
3280              ENDIF
3281             
3282          CASE ( 'usm_t_window' )
3283!
3284!--           window temperature for iwl layer of walls and land
3285              IF ( av == 0 )  THEN
3286                 IF ( idsint == iup_u )  THEN
3287                    DO  m = 1, surf_usm_h%ns
3288                       i = surf_usm_h%i(m)
3289                       j = surf_usm_h%j(m)
3290                       k = surf_usm_h%k(m)
3291                       temp_pf(k,j,i) = t_window_h(iwl,m)
3292                    ENDDO
3293                 ELSE
3294                    l = idsidx
3295                    DO  m = 1, surf_usm_v(l)%ns
3296                       i = surf_usm_v(l)%i(m)
3297                       j = surf_usm_v(l)%j(m)
3298                       k = surf_usm_v(l)%k(m)
3299                       temp_pf(k,j,i) = t_window_v(l)%t(iwl,m)
3300                    ENDDO
3301                 ENDIF
3302              ELSE
3303                 IF ( idsint == iup_u )  THEN
3304                    DO  m = 1, surf_usm_h%ns
3305                       i = surf_usm_h%i(m)
3306                       j = surf_usm_h%j(m)
3307                       k = surf_usm_h%k(m)
3308                       temp_pf(k,j,i) = surf_usm_h%t_window_av(iwl,m)
3309                    ENDDO
3310                 ELSE
3311                    l = idsidx
3312                    DO  m = 1, surf_usm_v(l)%ns
3313                       i = surf_usm_v(l)%i(m)
3314                       j = surf_usm_v(l)%j(m)
3315                       k = surf_usm_v(l)%k(m)
3316                       temp_pf(k,j,i) = surf_usm_v(l)%t_window_av(iwl,m)
3317                    ENDDO
3318                 ENDIF
3319              ENDIF
3320
3321          CASE ( 'usm_t_green' )
3322!
3323!--           green temperature for  iwl layer of walls and land
3324              IF ( av == 0 )  THEN
3325                 IF ( idsint == iup_u )  THEN
3326                    DO  m = 1, surf_usm_h%ns
3327                       i = surf_usm_h%i(m)
3328                       j = surf_usm_h%j(m)
3329                       k = surf_usm_h%k(m)
3330                       temp_pf(k,j,i) = t_green_h(iwl,m)
3331                    ENDDO
3332                 ELSE
3333                    l = idsidx
3334                    DO  m = 1, surf_usm_v(l)%ns
3335                       i = surf_usm_v(l)%i(m)
3336                       j = surf_usm_v(l)%j(m)
3337                       k = surf_usm_v(l)%k(m)
3338                       temp_pf(k,j,i) = t_green_v(l)%t(iwl,m)
3339                    ENDDO
3340                 ENDIF
3341              ELSE
3342                 IF ( idsint == iup_u )  THEN
3343                    DO  m = 1, surf_usm_h%ns
3344                       i = surf_usm_h%i(m)
3345                       j = surf_usm_h%j(m)
3346                       k = surf_usm_h%k(m)
3347                       temp_pf(k,j,i) = surf_usm_h%t_green_av(iwl,m)
3348                    ENDDO
3349                 ELSE
3350                    l = idsidx
3351                    DO  m = 1, surf_usm_v(l)%ns
3352                       i = surf_usm_v(l)%i(m)
3353                       j = surf_usm_v(l)%j(m)
3354                       k = surf_usm_v(l)%k(m)
3355                       temp_pf(k,j,i) = surf_usm_v(l)%t_green_av(iwl,m)
3356                    ENDDO
3357                 ENDIF
3358              ENDIF
3359             
3360              CASE ( 'usm_swc' )
3361!
3362!--           soil water content for  iwl layer of walls and land
3363              IF ( av == 0 )  THEN
3364                 IF ( idsint == iup_u )  THEN
3365                    DO  m = 1, surf_usm_h%ns
3366                       i = surf_usm_h%i(m)
3367                       j = surf_usm_h%j(m)
3368                       k = surf_usm_h%k(m)
3369                       temp_pf(k,j,i) = swc_h(iwl,m)
3370                    ENDDO
3371                 ELSE
3372                    l = idsidx
3373                    DO  m = 1, surf_usm_v(l)%ns
3374                       i = surf_usm_v(l)%i(m)
3375                       j = surf_usm_v(l)%j(m)
3376                       k = surf_usm_v(l)%k(m)
3377                       temp_pf(k,j,i) = swc_v(l)%t(iwl,m)
3378                    ENDDO
3379                 ENDIF
3380              ELSE
3381                 IF ( idsint == iup_u )  THEN
3382                    DO  m = 1, surf_usm_h%ns
3383                       i = surf_usm_h%i(m)
3384                       j = surf_usm_h%j(m)
3385                       k = surf_usm_h%k(m)
3386                       temp_pf(k,j,i) = surf_usm_h%swc_av(iwl,m)
3387                    ENDDO
3388                 ELSE
3389                    l = idsidx
3390                    DO  m = 1, surf_usm_v(l)%ns
3391                       i = surf_usm_v(l)%i(m)
3392                       j = surf_usm_v(l)%j(m)
3393                       k = surf_usm_v(l)%k(m)
3394                       temp_pf(k,j,i) = surf_usm_v(l)%swc_av(iwl,m)
3395                    ENDDO
3396                 ENDIF
3397              ENDIF
3398
3399             
3400          CASE DEFAULT
3401              found = .FALSE.
3402              RETURN
3403        END SELECT
3404
3405!
3406!--     Rearrange dimensions for NetCDF output
3407!--     FIXME: this may generate FPE overflow upon conversion from DP to SP
3408        DO  j = nys, nyn
3409            DO  i = nxl, nxr
3410                DO  k = nzb_do, nzt_do
3411                    local_pf(i,j,k) = temp_pf(k,j,i)
3412                ENDDO
3413            ENDDO
3414        ENDDO
3415       
3416    END SUBROUTINE usm_data_output_3d
3417   
3418
3419!------------------------------------------------------------------------------!
3420!
3421! Description:
3422! ------------
3423!> Soubroutine defines appropriate grid for netcdf variables.
3424!> It is called out from subroutine netcdf.
3425!------------------------------------------------------------------------------!
3426    SUBROUTINE usm_define_netcdf_grid( variable, found, grid_x, grid_y, grid_z )
3427   
3428        IMPLICIT NONE
3429
3430        CHARACTER (len=*), INTENT(IN)  ::  variable    !<
3431        LOGICAL, INTENT(OUT)           ::  found       !<
3432        CHARACTER (len=*), INTENT(OUT) ::  grid_x      !<
3433        CHARACTER (len=*), INTENT(OUT) ::  grid_y      !<
3434        CHARACTER (len=*), INTENT(OUT) ::  grid_z      !<
3435
3436        CHARACTER (len=varnamelength)  :: var
3437
3438        var = TRIM(variable)
3439        IF ( var(1:9) == 'usm_wshf_'  .OR.  var(1:9) == 'usm_wghf_'  .OR.                   &
3440             var(1:16) == 'usm_wghf_window_'  .OR. var(1:15) == 'usm_wghf_green_' .OR.      &
3441             var(1:10) == 'usm_iwghf_'  .OR. var(1:17) == 'usm_iwghf_window_' .OR.          &
3442             var(1:9) == 'usm_qsws_'  .OR.  var(1:13) == 'usm_qsws_veg_'  .OR.              &
3443             var(1:13) == 'usm_qsws_liq_' .OR.                                              &
3444             var(1:15) == 'usm_t_surf_wall'  .OR.  var(1:10) == 'usm_t_wall'  .OR.          &
3445             var(1:17) == 'usm_t_surf_window'  .OR.  var(1:12) == 'usm_t_window'  .OR.      &
3446             var(1:16) == 'usm_t_surf_green'  .OR. var(1:11) == 'usm_t_green' .OR.          &
3447             var(1:15) == 'usm_theta_10cm' .OR.                                             &
3448             var(1:9) == 'usm_surfz'  .OR.  var(1:11) == 'usm_surfcat'  .OR.                &
3449             var(1:16) == 'usm_surfwintrans'  .OR. var(1:7) == 'usm_swc' ) THEN
3450
3451            found = .TRUE.
3452            grid_x = 'x'
3453            grid_y = 'y'
3454            grid_z = 'zu'
3455        ELSE
3456            found  = .FALSE.
3457            grid_x = 'none'
3458            grid_y = 'none'
3459            grid_z = 'none'
3460        ENDIF
3461
3462    END SUBROUTINE usm_define_netcdf_grid
3463   
3464
3465!------------------------------------------------------------------------------!
3466! Description:
3467! ------------
3468!> Initialization of the wall surface model
3469!------------------------------------------------------------------------------!
3470    SUBROUTINE usm_init_material_model
3471
3472        IMPLICIT NONE
3473
3474        INTEGER(iwp) ::  k, l, m            !< running indices
3475       
3476        CALL location_message( '    initialization of wall surface model', .TRUE. )
3477
3478!
3479!--     Calculate wall grid spacings.
3480!--     Temperature is defined at the center of the wall layers,
3481!--     whereas gradients/fluxes are defined at the edges (_stag)     
3482!--     apply for all particular surface grids. First for horizontal surfaces
3483        DO  m = 1, surf_usm_h%ns
3484
3485           surf_usm_h%dz_wall(nzb_wall,m) = surf_usm_h%zw(nzb_wall,m)
3486           DO k = nzb_wall+1, nzt_wall
3487               surf_usm_h%dz_wall(k,m) = surf_usm_h%zw(k,m) -                  &
3488                                         surf_usm_h%zw(k-1,m)
3489           ENDDO
3490           surf_usm_h%dz_window(nzb_wall,m) = surf_usm_h%zw_window(nzb_wall,m)
3491           DO k = nzb_wall+1, nzt_wall
3492               surf_usm_h%dz_window(k,m) = surf_usm_h%zw_window(k,m) -         &
3493                                         surf_usm_h%zw_window(k-1,m)
3494           ENDDO
3495           
3496           surf_usm_h%dz_wall(nzt_wall+1,m) = surf_usm_h%dz_wall(nzt_wall,m)
3497
3498           DO k = nzb_wall, nzt_wall-1
3499               surf_usm_h%dz_wall_stag(k,m) = 0.5 * (                          &
3500                           surf_usm_h%dz_wall(k+1,m) + surf_usm_h%dz_wall(k,m) )
3501           ENDDO
3502           surf_usm_h%dz_wall_stag(nzt_wall,m) = surf_usm_h%dz_wall(nzt_wall,m)
3503           
3504           surf_usm_h%dz_window(nzt_wall+1,m) = surf_usm_h%dz_window(nzt_wall,m)
3505
3506           DO k = nzb_wall, nzt_wall-1
3507               surf_usm_h%dz_window_stag(k,m) = 0.5 * (                        &
3508                           surf_usm_h%dz_window(k+1,m) + surf_usm_h%dz_window(k,m) )
3509           ENDDO
3510           surf_usm_h%dz_window_stag(nzt_wall,m) = surf_usm_h%dz_window(nzt_wall,m)
3511
3512           IF (surf_usm_h%green_type_roof(m) == 2.0_wp ) THEN
3513!
3514!-- extensive green roof
3515!-- set ratio of substrate layer thickness, soil-type and LAI
3516              soil_type = 3
3517              surf_usm_h%lai(m) = 2.0_wp
3518             
3519              surf_usm_h%zw_green(nzb_wall,m)   = 0.05_wp
3520              surf_usm_h%zw_green(nzb_wall+1,m) = 0.10_wp
3521              surf_usm_h%zw_green(nzb_wall+2,m) = 0.15_wp
3522              surf_usm_h%zw_green(nzb_wall+3,m) = 0.20_wp
3523           ELSE
3524!
3525!-- intensiv green roof
3526!-- set ratio of substrate layer thickness, soil-type and LAI
3527              soil_type = 6
3528              surf_usm_h%lai(m) = 4.0_wp
3529             
3530              surf_usm_h%zw_green(nzb_wall,m)   = 0.05_wp
3531              surf_usm_h%zw_green(nzb_wall+1,m) = 0.10_wp
3532              surf_usm_h%zw_green(nzb_wall+2,m) = 0.40_wp
3533              surf_usm_h%zw_green(nzb_wall+3,m) = 0.80_wp
3534           ENDIF
3535           
3536           surf_usm_h%dz_green(nzb_wall,m) = surf_usm_h%zw_green(nzb_wall,m)
3537           DO k = nzb_wall+1, nzt_wall
3538               surf_usm_h%dz_green(k,m) = surf_usm_h%zw_green(k,m) -           &
3539                                         surf_usm_h%zw_green(k-1,m)
3540           ENDDO
3541           surf_usm_h%dz_green(nzt_wall+1,m) = surf_usm_h%dz_green(nzt_wall,m)
3542
3543           DO k = nzb_wall, nzt_wall-1
3544               surf_usm_h%dz_green_stag(k,m) = 0.5 * (                         &
3545                           surf_usm_h%dz_green(k+1,m) + surf_usm_h%dz_green(k,m) )
3546           ENDDO
3547           surf_usm_h%dz_green_stag(nzt_wall,m) = surf_usm_h%dz_green(nzt_wall,m)
3548           
3549          IF ( alpha_vangenuchten == 9999999.9_wp )  THEN
3550             alpha_vangenuchten = soil_pars(0,soil_type)
3551          ENDIF
3552
3553          IF ( l_vangenuchten == 9999999.9_wp )  THEN
3554             l_vangenuchten = soil_pars(1,soil_type)
3555          ENDIF
3556
3557          IF ( n_vangenuchten == 9999999.9_wp )  THEN
3558             n_vangenuchten = soil_pars(2,soil_type)           
3559          ENDIF
3560
3561          IF ( hydraulic_conductivity == 9999999.9_wp )  THEN
3562             hydraulic_conductivity = soil_pars(3,soil_type)           
3563          ENDIF
3564
3565          IF ( saturation_moisture == 9999999.9_wp )  THEN
3566             saturation_moisture = m_soil_pars(0,soil_type)           
3567          ENDIF
3568
3569          IF ( field_capacity == 9999999.9_wp )  THEN
3570             field_capacity = m_soil_pars(1,soil_type)           
3571          ENDIF
3572
3573          IF ( wilting_point == 9999999.9_wp )  THEN
3574             wilting_point = m_soil_pars(2,soil_type)           
3575          ENDIF
3576
3577          IF ( residual_moisture == 9999999.9_wp )  THEN
3578             residual_moisture = m_soil_pars(3,soil_type)       
3579          ENDIF
3580         
3581          DO k = nzb_wall, nzt_wall+1
3582             swc_h(k,m) = field_capacity
3583             rootfr_h(k,m) = 0.5_wp
3584             surf_usm_h%alpha_vg_green(m)      = alpha_vangenuchten
3585             surf_usm_h%l_vg_green(m)          = l_vangenuchten
3586             surf_usm_h%n_vg_green(m)          = n_vangenuchten 
3587             surf_usm_h%gamma_w_green_sat(k,m) = hydraulic_conductivity
3588             swc_sat_h(k,m)                    = saturation_moisture
3589             fc_h(k,m)                         = field_capacity
3590             wilt_h(k,m)                       = wilting_point
3591             swc_res_h(k,m)                    = residual_moisture
3592          ENDDO
3593
3594        ENDDO
3595
3596        surf_usm_h%ddz_wall        = 1.0_wp / surf_usm_h%dz_wall
3597        surf_usm_h%ddz_wall_stag   = 1.0_wp / surf_usm_h%dz_wall_stag
3598        surf_usm_h%ddz_window      = 1.0_wp / surf_usm_h%dz_window
3599        surf_usm_h%ddz_window_stag = 1.0_wp / surf_usm_h%dz_window_stag
3600        surf_usm_h%ddz_green       = 1.0_wp / surf_usm_h%dz_green
3601        surf_usm_h%ddz_green_stag  = 1.0_wp / surf_usm_h%dz_green_stag
3602!       
3603!--     For vertical surfaces
3604        DO  l = 0, 3
3605           DO  m = 1, surf_usm_v(l)%ns
3606              surf_usm_v(l)%dz_wall(nzb_wall,m) = surf_usm_v(l)%zw(nzb_wall,m)
3607              DO k = nzb_wall+1, nzt_wall
3608                  surf_usm_v(l)%dz_wall(k,m) = surf_usm_v(l)%zw(k,m) -         &
3609                                               surf_usm_v(l)%zw(k-1,m)
3610              ENDDO
3611              surf_usm_v(l)%dz_window(nzb_wall,m) = surf_usm_v(l)%zw_window(nzb_wall,m)
3612              DO k = nzb_wall+1, nzt_wall
3613                  surf_usm_v(l)%dz_window(k,m) = surf_usm_v(l)%zw_window(k,m) - &
3614                                               surf_usm_v(l)%zw_window(k-1,m)
3615              ENDDO
3616              surf_usm_v(l)%dz_green(nzb_wall,m) = surf_usm_v(l)%zw_green(nzb_wall,m)
3617              DO k = nzb_wall+1, nzt_wall
3618                  surf_usm_v(l)%dz_green(k,m) = surf_usm_v(l)%zw_green(k,m) - &
3619                                               surf_usm_v(l)%zw_green(k-1,m)
3620              ENDDO
3621           
3622              surf_usm_v(l)%dz_wall(nzt_wall+1,m) =                            &
3623                                              surf_usm_v(l)%dz_wall(nzt_wall,m)
3624
3625              DO k = nzb_wall, nzt_wall-1
3626                  surf_usm_v(l)%dz_wall_stag(k,m) = 0.5 * (                    &
3627                                                surf_usm_v(l)%dz_wall(k+1,m) + &
3628                                                surf_usm_v(l)%dz_wall(k,m) )
3629              ENDDO
3630              surf_usm_v(l)%dz_wall_stag(nzt_wall,m) =                         &
3631                                              surf_usm_v(l)%dz_wall(nzt_wall,m)
3632              surf_usm_v(l)%dz_window(nzt_wall+1,m) =                          &
3633                                              surf_usm_v(l)%dz_window(nzt_wall,m)
3634
3635              DO k = nzb_wall, nzt_wall-1
3636                  surf_usm_v(l)%dz_window_stag(k,m) = 0.5 * (                    &
3637                                                surf_usm_v(l)%dz_window(k+1,m) + &
3638                                                surf_usm_v(l)%dz_window(k,m) )
3639              ENDDO
3640              surf_usm_v(l)%dz_window_stag(nzt_wall,m) =                         &
3641                                              surf_usm_v(l)%dz_window(nzt_wall,m)
3642              surf_usm_v(l)%dz_green(nzt_wall+1,m) =                             &
3643                                              surf_usm_v(l)%dz_green(nzt_wall,m)
3644
3645              DO k = nzb_wall, nzt_wall-1
3646                  surf_usm_v(l)%dz_green_stag(k,m) = 0.5 * (                    &
3647                                                surf_usm_v(l)%dz_green(k+1,m) + &
3648                                                surf_usm_v(l)%dz_green(k,m) )
3649              ENDDO
3650              surf_usm_v(l)%dz_green_stag(nzt_wall,m) =                         &
3651                                              surf_usm_v(l)%dz_green(nzt_wall,m)
3652           ENDDO
3653           surf_usm_v(l)%ddz_wall        = 1.0_wp / surf_usm_v(l)%dz_wall
3654           surf_usm_v(l)%ddz_wall_stag   = 1.0_wp / surf_usm_v(l)%dz_wall_stag
3655           surf_usm_v(l)%ddz_window      = 1.0_wp / surf_usm_v(l)%dz_window
3656           surf_usm_v(l)%ddz_window_stag = 1.0_wp / surf_usm_v(l)%dz_window_stag
3657           surf_usm_v(l)%ddz_green       = 1.0_wp / surf_usm_v(l)%dz_green
3658           surf_usm_v(l)%ddz_green_stag  = 1.0_wp / surf_usm_v(l)%dz_green_stag
3659        ENDDO     
3660
3661       
3662        CALL location_message( '    wall structures filed out', .TRUE. )
3663
3664        CALL location_message( '    initialization of wall surface model finished', .TRUE. )
3665
3666    END SUBROUTINE usm_init_material_model
3667
3668 
3669!------------------------------------------------------------------------------!
3670! Description:
3671! ------------
3672!> Initialization of the urban surface model
3673!------------------------------------------------------------------------------!
3674    SUBROUTINE usm_init
3675
3676        USE arrays_3d,                                                         &
3677            ONLY:  zw
3678
3679        USE netcdf_data_input_mod,                                             &
3680            ONLY:  building_pars_f, building_type_f, terrain_height_f
3681   
3682        IMPLICIT NONE
3683
3684        INTEGER(iwp) ::  i                   !< loop index x-dirction
3685        INTEGER(iwp) ::  ind_alb_green       !< index in input list for green albedo
3686        INTEGER(iwp) ::  ind_alb_wall        !< index in input list for wall albedo
3687        INTEGER(iwp) ::  ind_alb_win         !< index in input list for window albedo
3688        INTEGER(iwp) ::  ind_emis_wall       !< index in input list for wall emissivity
3689        INTEGER(iwp) ::  ind_emis_green      !< index in input list for green emissivity
3690        INTEGER(iwp) ::  ind_emis_win        !< index in input list for window emissivity
3691        INTEGER(iwp) ::  ind_green_frac_w    !< index in input list for green fraction on wall
3692        INTEGER(iwp) ::  ind_green_frac_r    !< index in input list for green fraction on roof
3693        INTEGER(iwp) ::  ind_hc1             !< index in input list for heat capacity at first wall layer
3694        INTEGER(iwp) ::  ind_hc1_win         !< index in input list for heat capacity at first window layer
3695        INTEGER(iwp) ::  ind_hc2             !< index in input list for heat capacity at second wall layer
3696        INTEGER(iwp) ::  ind_hc2_win         !< index in input list for heat capacity at second window layer
3697        INTEGER(iwp) ::  ind_hc3             !< index in input list for heat capacity at third wall layer
3698        INTEGER(iwp) ::  ind_hc3_win         !< index in input list for heat capacity at third window layer
3699        INTEGER(iwp) ::  ind_lai_r           !< index in input list for LAI on roof
3700        INTEGER(iwp) ::  ind_lai_w           !< index in input list for LAI on wall
3701        INTEGER(iwp) ::  ind_tc1             !< index in input list for thermal conductivity at first wall layer
3702        INTEGER(iwp) ::  ind_tc1_win         !< index in input list for thermal conductivity at first window layer
3703        INTEGER(iwp) ::  ind_tc2             !< index in input list for thermal conductivity at second wall layer
3704        INTEGER(iwp) ::  ind_tc2_win         !< index in input list for thermal conductivity at second window layer
3705        INTEGER(iwp) ::  ind_tc3             !< index in input list for thermal conductivity at third wall layer
3706        INTEGER(iwp) ::  ind_tc3_win         !< index in input list for thermal conductivity at third window layer
3707        INTEGER(iwp) ::  ind_thick_1         !< index in input list for thickness of first wall layer
3708        INTEGER(iwp) ::  ind_thick_1_win     !< index in input list for thickness of first window layer
3709        INTEGER(iwp) ::  ind_thick_2         !< index in input list for thickness of second wall layer
3710        INTEGER(iwp) ::  ind_thick_2_win     !< index in input list for thickness of second window layer
3711        INTEGER(iwp) ::  ind_thick_3         !< index in input list for thickness of third wall layer
3712        INTEGER(iwp) ::  ind_thick_3_win     !< index in input list for thickness of third window layer
3713        INTEGER(iwp) ::  ind_thick_4         !< index in input list for thickness of fourth wall layer
3714        INTEGER(iwp) ::  ind_thick_4_win     !< index in input list for thickness of fourth window layer
3715        INTEGER(iwp) ::  ind_trans           !< index in input list for window transmissivity
3716        INTEGER(iwp) ::  ind_wall_frac       !< index in input list for wall fraction
3717        INTEGER(iwp) ::  ind_win_frac        !< index in input list for window fraction
3718        INTEGER(iwp) ::  ind_z0              !< index in input list for z0
3719        INTEGER(iwp) ::  ind_z0qh            !< index in input list for z0h / z0q
3720        INTEGER(iwp) ::  j                   !< loop index y-dirction
3721        INTEGER(iwp) ::  k                   !< loop index z-dirction
3722        INTEGER(iwp) ::  l                   !< loop index surface orientation
3723        INTEGER(iwp) ::  m                   !< loop index surface element
3724        INTEGER(iwp) ::  st                  !< dummy 
3725
3726        REAL(wp)     ::  c, tin, twin
3727        REAL(wp)     ::  ground_floor_level_l         !< local height of ground floor level
3728        REAL(wp)     ::  z_agl                        !< height above ground
3729
3730        CALL location_message( 'initializing urban surface model', .FALSE. )
3731
3732        CALL cpu_log( log_point_s(78), 'usm_init', 'start' )
3733!
3734!--     Initialize building-surface properties
3735        CALL usm_define_pars
3736!
3737!--     surface forcing have to be disabled for LSF
3738!--     in case of enabled urban surface module
3739        IF ( large_scale_forcing )  THEN
3740            lsf_surf = .FALSE.
3741        ENDIF
3742
3743!
3744!--     Flag surface elements belonging to the ground floor level. Therefore,
3745!--     use terrain height array from file, if available. This flag is later used
3746!--     to control initialization of surface attributes.
3747!--     Todo: for the moment disable initialization of building roofs with
3748!--     ground-floor-level properties.
3749        surf_usm_h%ground_level = .FALSE. 
3750
3751        DO  l = 0, 3
3752           surf_usm_v(l)%ground_level = .FALSE.
3753           DO  m = 1, surf_usm_v(l)%ns
3754              i = surf_usm_v(l)%i(m) + surf_usm_v(l)%ioff
3755              j = surf_usm_v(l)%j(m) + surf_usm_v(l)%joff
3756              k = surf_usm_v(l)%k(m)
3757!
3758!--           Determine local ground level. Level 1 - default value,
3759!--           level 2 - initialization according to building type,
3760!--           level 3 - initialization from value read from file.
3761              ground_floor_level_l = ground_floor_level
3762             
3763              IF ( building_type_f%from_file )  THEN
3764                  ground_floor_level_l =                                       &
3765                              building_pars(ind_gflh,building_type_f%var(j,i))
3766              ENDIF
3767             
3768              IF ( building_pars_f%from_file )  THEN
3769                 IF ( building_pars_f%pars_xy(ind_gflh,j,i) /=                 &
3770                      building_pars_f%fill )                                   &
3771                    ground_floor_level_l = building_pars_f%pars_xy(ind_gflh,j,i)
3772              ENDIF
3773!
3774!--           Determine height of surface element above ground level. Please
3775!--           note, height of surface element is determined with respect to
3776!--           its height above ground of the reference grid point in atmosphere,
3777!--           Therefore, substract the offset values when assessing the terrain
3778!--           height.
3779              IF ( terrain_height_f%from_file )  THEN
3780                 z_agl = zw(k) - terrain_height_f%var(j-surf_usm_v(l)%joff,    &
3781                                                      i-surf_usm_v(l)%ioff)
3782              ELSE
3783                 z_agl = zw(k)
3784              ENDIF
3785!
3786!--           Set flag for ground level
3787              IF ( z_agl <= ground_floor_level_l )                             &
3788                 surf_usm_v(l)%ground_level(m) = .TRUE.
3789
3790           ENDDO
3791        ENDDO
3792!
3793!--     Initialization of resistances.
3794        DO  m = 1, surf_usm_h%ns
3795           surf_usm_h%r_a(m)        = 50.0_wp
3796           surf_usm_h%r_a_green(m)  = 50.0_wp
3797           surf_usm_h%r_a_window(m) = 50.0_wp
3798        ENDDO
3799        DO  l = 0, 3
3800           DO  m = 1, surf_usm_v(l)%ns
3801              surf_usm_v(l)%r_a(m)        = 50.0_wp
3802              surf_usm_v(l)%r_a_green(m)  = 50.0_wp
3803              surf_usm_v(l)%r_a_window(m) = 50.0_wp
3804           ENDDO
3805        ENDDO
3806       
3807!
3808!--    Map values onto horizontal elemements
3809       DO  m = 1, surf_usm_h%ns
3810             surf_usm_h%r_canopy_min(m)     = 200.0_wp !< min_canopy_resistance
3811             surf_usm_h%g_d(m)              = 0.0_wp   !< canopy_resistance_coefficient
3812       ENDDO
3813!
3814!--    Map values onto vertical elements, even though this does not make
3815!--    much sense.
3816       DO  l = 0, 3
3817          DO  m = 1, surf_usm_v(l)%ns
3818                surf_usm_v(l)%r_canopy_min(m)     = 200.0_wp !< min_canopy_resistance
3819                surf_usm_v(l)%g_d(m)              = 0.0_wp   !< canopy_resistance_coefficient
3820          ENDDO
3821       ENDDO
3822
3823!
3824!--     Initialize urban-type surface attribute. According to initialization in
3825!--     land-surface model, follow a 3-level approach.
3826!--     Level 1 - initialization via default attributes
3827        DO  m = 1, surf_usm_h%ns
3828!
3829!--        Now, all horizontal surfaces are roof surfaces (?)
3830           surf_usm_h%isroof_surf(m)   = .TRUE.
3831           surf_usm_h%surface_types(m) = roof_category         !< default category for root surface
3832!
3833!--        In order to distinguish between ground floor level and
3834!--        above-ground-floor level surfaces, set input indices.
3835
3836           ind_green_frac_r = MERGE( ind_green_frac_r_gfl, ind_green_frac_r_agfl, &
3837                                     surf_usm_h%ground_level(m) )
3838           ind_lai_r        = MERGE( ind_lai_r_gfl,        ind_lai_r_agfl,        &
3839                                     surf_usm_h%ground_level(m) )
3840           ind_z0           = MERGE( ind_z0_gfl,           ind_z0_agfl,           &
3841                                     surf_usm_h%ground_level(m) )
3842           ind_z0qh         = MERGE( ind_z0qh_gfl,         ind_z0qh_agfl,         &
3843                                     surf_usm_h%ground_level(m) )
3844!
3845!--        Store building type and its name on each surface element
3846           surf_usm_h%building_type(m)      = building_type
3847           surf_usm_h%building_type_name(m) = building_type_name(building_type)
3848!
3849!--        Initialize relatvie wall- (0), green- (1) and window (2) fractions
3850           surf_usm_h%frac(ind_veg_wall,m)  = building_pars(ind_wall_frac_r,building_type)   
3851           surf_usm_h%frac(ind_pav_green,m) = building_pars(ind_green_frac_r,building_type) 
3852           surf_usm_h%frac(ind_wat_win,m)   = building_pars(ind_win_frac_r,building_type) 
3853           surf_usm_h%lai(m)                = building_pars(ind_lai_r,building_type) 
3854
3855           surf_usm_h%rho_c_wall(nzb_wall,m)   = building_pars(ind_hc1_wall_r,building_type) 
3856           surf_usm_h%rho_c_wall(nzb_wall+1,m) = building_pars(ind_hc1_wall_r,building_type)
3857           surf_usm_h%rho_c_wall(nzb_wall+2,m) = building_pars(ind_hc2_wall_r,building_type)
3858           surf_usm_h%rho_c_wall(nzb_wall+3,m) = building_pars(ind_hc3_wall_r,building_type)   
3859           surf_usm_h%lambda_h(nzb_wall,m)   = building_pars(ind_tc1_wall_r,building_type) 
3860           surf_usm_h%lambda_h(nzb_wall+1,m) = building_pars(ind_tc1_wall_r,building_type) 
3861           surf_usm_h%lambda_h(nzb_wall+2,m) = building_pars(ind_tc2_wall_r,building_type)
3862           surf_usm_h%lambda_h(nzb_wall+3,m) = building_pars(ind_tc3_wall_r,building_type)   
3863           surf_usm_h%rho_c_green(nzb_wall,m)   = rho_c_soil !building_pars(ind_hc1_wall_r,building_type) 
3864           surf_usm_h%rho_c_green(nzb_wall+1,m) = rho_c_soil !building_pars(ind_hc1_wall_r,building_type)
3865           surf_usm_h%rho_c_green(nzb_wall+2,m) = rho_c_soil !building_pars(ind_hc2_wall_r,building_type)
3866           surf_usm_h%rho_c_green(nzb_wall+3,m) = rho_c_soil !building_pars(ind_hc3_wall_r,building_type)   
3867           surf_usm_h%lambda_h_green(nzb_wall,m)   = lambda_h_green_sm !building_pars(ind_tc1_wall_r,building_type) 
3868           surf_usm_h%lambda_h_green(nzb_wall+1,m) = lambda_h_green_sm !building_pars(ind_tc1_wall_r,building_type)
3869           surf_usm_h%lambda_h_green(nzb_wall+2,m) = lambda_h_green_sm !building_pars(ind_tc2_wall_r,building_type)
3870           surf_usm_h%lambda_h_green(nzb_wall+3,m) = lambda_h_green_sm !building_pars(ind_tc3_wall_r,building_type)
3871           surf_usm_h%rho_c_window(nzb_wall,m)   = building_pars(ind_hc1_win_r,building_type) 
3872           surf_usm_h%rho_c_window(nzb_wall+1,m) = building_pars(ind_hc1_win_r,building_type)
3873           surf_usm_h%rho_c_window(nzb_wall+2,m) = building_pars(ind_hc2_win_r,building_type)
3874           surf_usm_h%rho_c_window(nzb_wall+3,m) = building_pars(ind_hc3_win_r,building_type)   
3875           surf_usm_h%lambda_h_window(nzb_wall,m)   = building_pars(ind_tc1_win_r,building_type) 
3876           surf_usm_h%lambda_h_window(nzb_wall+1,m) = building_pars(ind_tc1_win_r,building_type) 
3877           surf_usm_h%lambda_h_window(nzb_wall+2,m) = building_pars(ind_tc2_win_r,building_type)
3878           surf_usm_h%lambda_h_window(nzb_wall+3,m) = building_pars(ind_tc3_win_r,building_type)   
3879
3880           surf_usm_h%target_temp_summer(m)  = building_pars(ind_indoor_target_temp_summer,building_type)   
3881           surf_usm_h%target_temp_winter(m)  = building_pars(ind_indoor_target_temp_winter,building_type)   
3882!
3883!--        emissivity of wall-, green- and window fraction
3884           surf_usm_h%emissivity(ind_veg_wall,m)  = building_pars(ind_emis_wall_r,building_type)
3885           surf_usm_h%emissivity(ind_pav_green,m) = building_pars(ind_emis_green_r,building_type)
3886           surf_usm_h%emissivity(ind_wat_win,m)   = building_pars(ind_emis_win_r,building_type)
3887
3888           surf_usm_h%transmissivity(m)      = building_pars(ind_trans_r,building_type)
3889
3890           surf_usm_h%z0(m)                  = building_pars(ind_z0,building_type)
3891           surf_usm_h%z0h(m)                 = building_pars(ind_z0qh,building_type)
3892           surf_usm_h%z0q(m)                 = building_pars(ind_z0qh,building_type)
3893!
3894!--        albedo type for wall fraction, green fraction, window fraction
3895           surf_usm_h%albedo_type(ind_veg_wall,m)  = INT( building_pars(ind_alb_wall_r,building_type)  )
3896           surf_usm_h%albedo_type(ind_pav_green,m) = INT( building_pars(ind_alb_green_r,building_type) )
3897           surf_usm_h%albedo_type(ind_wat_win,m)   = INT( building_pars(ind_alb_win_r,building_type)   )
3898
3899           surf_usm_h%zw(nzb_wall,m)         = building_pars(ind_thick_1_wall_r,building_type)
3900           surf_usm_h%zw(nzb_wall+1,m)       = building_pars(ind_thick_2_wall_r,building_type)
3901           surf_usm_h%zw(nzb_wall+2,m)       = building_pars(ind_thick_3_wall_r,building_type)
3902           surf_usm_h%zw(nzb_wall+3,m)       = building_pars(ind_thick_4_wall_r,building_type)
3903           
3904           surf_usm_h%zw_green(nzb_wall,m)         = building_pars(ind_thick_1_wall_r,building_type)
3905           surf_usm_h%zw_green(nzb_wall+1,m)       = building_pars(ind_thick_2_wall_r,building_type)
3906           surf_usm_h%zw_green(nzb_wall+2,m)       = building_pars(ind_thick_3_wall_r,building_type)
3907           surf_usm_h%zw_green(nzb_wall+3,m)       = building_pars(ind_thick_4_wall_r,building_type)
3908           
3909           surf_usm_h%zw_window(nzb_wall,m)         = building_pars(ind_thick_1_win_r,building_type)
3910           surf_usm_h%zw_window(nzb_wall+1,m)       = building_pars(ind_thick_2_win_r,building_type)
3911           surf_usm_h%zw_window(nzb_wall+2,m)       = building_pars(ind_thick_3_win_r,building_type)
3912           surf_usm_h%zw_window(nzb_wall+3,m)       = building_pars(ind_thick_4_win_r,building_type)
3913
3914           surf_usm_h%c_surface(m)           = building_pars(ind_c_surface,building_type) 
3915           surf_usm_h%lambda_surf(m)         = building_pars(ind_lambda_surf,building_type) 
3916           surf_usm_h%c_surface_green(m)     = building_pars(ind_c_surface_green,building_type) 
3917           surf_usm_h%lambda_surf_green(m)   = building_pars(ind_lambda_surf_green,building_type) 
3918           surf_usm_h%c_surface_window(m)    = building_pars(ind_c_surface_win,building_type) 
3919           surf_usm_h%lambda_surf_window(m)  = building_pars(ind_lambda_surf_win,building_type) 
3920           
3921           surf_usm_h%green_type_roof(m)     = building_pars(ind_green_type_roof,building_type)
3922
3923        ENDDO
3924
3925        DO  l = 0, 3
3926           DO  m = 1, surf_usm_v(l)%ns
3927
3928              surf_usm_v(l)%surface_types(m) = wall_category         !< default category for root surface
3929!
3930!--           In order to distinguish between ground floor level and
3931!--           above-ground-floor level surfaces, set input indices.
3932              ind_alb_green    = MERGE( ind_alb_green_gfl,    ind_alb_green_agfl,    &
3933                                        surf_usm_v(l)%ground_level(m) )
3934              ind_alb_wall     = MERGE( ind_alb_wall_gfl,     ind_alb_wall_agfl,     &
3935                                        surf_usm_v(l)%ground_level(m) )
3936              ind_alb_win      = MERGE( ind_alb_win_gfl,      ind_alb_win_agfl,      &
3937                                        surf_usm_v(l)%ground_level(m) )
3938              ind_wall_frac    = MERGE( ind_wall_frac_gfl,    ind_wall_frac_agfl,    &
3939                                        surf_usm_v(l)%ground_level(m) )
3940              ind_win_frac     = MERGE( ind_win_frac_gfl,     ind_win_frac_agfl,     &
3941                                        surf_usm_v(l)%ground_level(m) )
3942              ind_green_frac_w = MERGE( ind_green_frac_w_gfl, ind_green_frac_w_agfl, &
3943                                        surf_usm_v(l)%ground_level(m) )
3944              ind_green_frac_r = MERGE( ind_green_frac_r_gfl, ind_green_frac_r_agfl, &
3945                                        surf_usm_v(l)%ground_level(m) )
3946              ind_lai_r        = MERGE( ind_lai_r_gfl,        ind_lai_r_agfl,        &
3947                                        surf_usm_v(l)%ground_level(m) )
3948              ind_lai_w        = MERGE( ind_lai_w_gfl,        ind_lai_w_agfl,        &
3949                                        surf_usm_v(l)%ground_level(m) )
3950              ind_hc1          = MERGE( ind_hc1_gfl,          ind_hc1_agfl,          &
3951                                        surf_usm_v(l)%ground_level(m) )
3952              ind_hc1_win      = MERGE( ind_hc1_win_gfl,      ind_hc1_win_agfl,      &
3953                                        surf_usm_v(l)%ground_level(m) )
3954              ind_hc2          = MERGE( ind_hc2_gfl,          ind_hc2_agfl,          &
3955                                        surf_usm_v(l)%ground_level(m) )
3956              ind_hc2_win      = MERGE( ind_hc2_win_gfl,      ind_hc2_win_agfl,      &
3957                                        surf_usm_v(l)%ground_level(m) )
3958              ind_hc3          = MERGE( ind_hc3_gfl,          ind_hc3_agfl,          &
3959                                        surf_usm_v(l)%ground_level(m) )
3960              ind_hc3_win      = MERGE( ind_hc3_win_gfl,      ind_hc3_win_agfl,      &
3961                                        surf_usm_v(l)%ground_level(m) )
3962              ind_tc1          = MERGE( ind_tc1_gfl,          ind_tc1_agfl,          &
3963                                        surf_usm_v(l)%ground_level(m) )
3964              ind_tc1_win      = MERGE( ind_tc1_win_gfl,      ind_tc1_win_agfl,      &
3965                                        surf_usm_v(l)%ground_level(m) )
3966              ind_tc2          = MERGE( ind_tc2_gfl,          ind_tc2_agfl,          &
3967                                        surf_usm_v(l)%ground_level(m) )
3968              ind_tc2_win      = MERGE( ind_tc2_win_gfl,      ind_tc2_win_agfl,      &
3969                                        surf_usm_v(l)%ground_level(m) )
3970              ind_tc3          = MERGE( ind_tc3_gfl,          ind_tc3_agfl,          &
3971                                        surf_usm_v(l)%ground_level(m) )
3972              ind_tc3_win      = MERGE( ind_tc3_win_gfl,      ind_tc3_win_agfl,      &
3973                                        surf_usm_v(l)%ground_level(m) )
3974              ind_thick_1      = MERGE( ind_thick_1_gfl,      ind_thick_1_agfl,      &
3975                                        surf_usm_v(l)%ground_level(m) )
3976              ind_thick_1_win  = MERGE( ind_thick_1_win_gfl,  ind_thick_1_win_agfl,  &
3977                                        surf_usm_v(l)%ground_level(m) )
3978              ind_thick_2      = MERGE( ind_thick_2_gfl,      ind_thick_2_agfl,      &
3979                                        surf_usm_v(l)%ground_level(m) )
3980              ind_thick_2_win  = MERGE( ind_thick_2_win_gfl,  ind_thick_2_win_agfl,  &
3981                                        surf_usm_v(l)%ground_level(m) )
3982              ind_thick_3      = MERGE( ind_thick_3_gfl,      ind_thick_3_agfl,      &
3983                                        surf_usm_v(l)%ground_level(m) )
3984              ind_thick_3_win  = MERGE( ind_thick_3_win_gfl,  ind_thick_3_win_agfl,  &
3985                                        surf_usm_v(l)%ground_level(m) )
3986              ind_thick_4      = MERGE( ind_thick_4_gfl,      ind_thick_4_agfl,      &
3987                                        surf_usm_v(l)%ground_level(m) )
3988              ind_thick_4_win  = MERGE( ind_thick_4_win_gfl,  ind_thick_4_win_agfl,  &
3989                                        surf_usm_v(l)%ground_level(m) )
3990              ind_emis_wall    = MERGE( ind_emis_wall_gfl,    ind_emis_wall_agfl,    &
3991                                        surf_usm_v(l)%ground_level(m) )
3992              ind_emis_green   = MERGE( ind_emis_green_gfl,   ind_emis_green_agfl,   &
3993                                        surf_usm_v(l)%ground_level(m) )
3994              ind_emis_win     = MERGE( ind_emis_win_gfl,     ind_emis_win_agfl,     &
3995                                        surf_usm_v(l)%ground_level(m) )
3996              ind_trans        = MERGE( ind_trans_gfl,       ind_trans_agfl,         &
3997                                        surf_usm_v(l)%ground_level(m) )
3998              ind_z0           = MERGE( ind_z0_gfl,           ind_z0_agfl,           &
3999                                        surf_usm_v(l)%ground_level(m) )
4000              ind_z0qh         = MERGE( ind_z0qh_gfl,         ind_z0qh_agfl,         &
4001                                        surf_usm_v(l)%ground_level(m) )
4002!
4003!--           Store building type and its name on each surface element
4004              surf_usm_v(l)%building_type(m)      = building_type
4005              surf_usm_v(l)%building_type_name(m) = building_type_name(building_type)
4006!
4007!--           Initialize relatvie wall- (0), green- (1) and window (2) fractions
4008              surf_usm_v(l)%frac(ind_veg_wall,m)   = building_pars(ind_wall_frac,building_type)   
4009              surf_usm_v(l)%frac(ind_pav_green,m)  = building_pars(ind_green_frac_w,building_type) 
4010              surf_usm_v(l)%frac(ind_wat_win,m)    = building_pars(ind_win_frac,building_type) 
4011              surf_usm_v(l)%lai(m)                 = building_pars(ind_lai_w,building_type) 
4012
4013              surf_usm_v(l)%rho_c_wall(nzb_wall,m)   = building_pars(ind_hc1,building_type) 
4014              surf_usm_v(l)%rho_c_wall(nzb_wall+1,m) = building_pars(ind_hc1,building_type)
4015              surf_usm_v(l)%rho_c_wall(nzb_wall+2,m) = building_pars(ind_hc2,building_type)
4016              surf_usm_v(l)%rho_c_wall(nzb_wall+3,m) = building_pars(ind_hc3,building_type)   
4017             
4018              surf_usm_v(l)%rho_c_green(nzb_wall,m)   = rho_c_soil !building_pars(ind_hc1,building_type) 
4019              surf_usm_v(l)%rho_c_green(nzb_wall+1,m) = rho_c_soil !building_pars(ind_hc1,building_type)
4020              surf_usm_v(l)%rho_c_green(nzb_wall+2,m) = rho_c_soil !building_pars(ind_hc2,building_type)
4021              surf_usm_v(l)%rho_c_green(nzb_wall+3,m) = rho_c_soil !building_pars(ind_hc3,building_type)   
4022             
4023              surf_usm_v(l)%rho_c_window(nzb_wall,m)   = building_pars(ind_hc1_win,building_type) 
4024              surf_usm_v(l)%rho_c_window(nzb_wall+1,m) = building_pars(ind_hc1_win,building_type)
4025              surf_usm_v(l)%rho_c_window(nzb_wall+2,m) = building_pars(ind_hc2_win,building_type)
4026              surf_usm_v(l)%rho_c_window(nzb_wall+3,m) = building_pars(ind_hc3_win,building_type)   
4027
4028              surf_usm_v(l)%lambda_h(nzb_wall,m)   = building_pars(ind_tc1,building_type) 
4029              surf_usm_v(l)%lambda_h(nzb_wall+1,m) = building_pars(ind_tc1,building_type) 
4030              surf_usm_v(l)%lambda_h(nzb_wall+2,m) = building_pars(ind_tc2,building_type)
4031              surf_usm_v(l)%lambda_h(nzb_wall+3,m) = building_pars(ind_tc3,building_type)   
4032             
4033              surf_usm_v(l)%lambda_h_green(nzb_wall,m)   = lambda_h_green_sm !building_pars(ind_tc1,building_type) 
4034              surf_usm_v(l)%lambda_h_green(nzb_wall+1,m) = lambda_h_green_sm !building_pars(ind_tc1,building_type)
4035              surf_usm_v(l)%lambda_h_green(nzb_wall+2,m) = lambda_h_green_sm !building_pars(ind_tc2,building_type)
4036              surf_usm_v(l)%lambda_h_green(nzb_wall+3,m) = lambda_h_green_sm !building_pars(ind_tc3,building_type)   
4037
4038              surf_usm_v(l)%lambda_h_window(nzb_wall,m)   = building_pars(ind_tc1_win,building_type) 
4039              surf_usm_v(l)%lambda_h_window(nzb_wall+1,m) = building_pars(ind_tc1_win,building_type) 
4040              surf_usm_v(l)%lambda_h_window(nzb_wall+2,m) = building_pars(ind_tc2_win,building_type)
4041              surf_usm_v(l)%lambda_h_window(nzb_wall+3,m) = building_pars(ind_tc3_win,building_type)   
4042
4043              surf_usm_v(l)%target_temp_summer(m)  = building_pars(ind_indoor_target_temp_summer,building_type)   
4044              surf_usm_v(l)%target_temp_winter(m)  = building_pars(ind_indoor_target_temp_winter,building_type)   
4045!
4046!--           emissivity of wall-, green- and window fraction
4047              surf_usm_v(l)%emissivity(ind_veg_wall,m)  = building_pars(ind_emis_wall,building_type)
4048              surf_usm_v(l)%emissivity(ind_pav_green,m) = building_pars(ind_emis_green,building_type)
4049              surf_usm_v(l)%emissivity(ind_wat_win,m)   = building_pars(ind_emis_win,building_type)
4050
4051              surf_usm_v(l)%transmissivity(m)      = building_pars(ind_trans,building_type)
4052
4053              surf_usm_v(l)%z0(m)                  = building_pars(ind_z0,building_type)
4054              surf_usm_v(l)%z0h(m)                 = building_pars(ind_z0qh,building_type)
4055              surf_usm_v(l)%z0q(m)                 = building_pars(ind_z0qh,building_type)
4056
4057              surf_usm_v(l)%albedo_type(ind_veg_wall,m)  = INT( building_pars(ind_alb_wall,building_type) )
4058              surf_usm_v(l)%albedo_type(ind_pav_green,m) = INT( building_pars(ind_alb_green,building_type) )
4059              surf_usm_v(l)%albedo_type(ind_wat_win,m)   = INT( building_pars(ind_alb_win,building_type) )
4060
4061              surf_usm_v(l)%zw(nzb_wall,m)         = building_pars(ind_thick_1,building_type)
4062              surf_usm_v(l)%zw(nzb_wall+1,m)       = building_pars(ind_thick_2,building_type)
4063              surf_usm_v(l)%zw(nzb_wall+2,m)       = building_pars(ind_thick_3,building_type)
4064              surf_usm_v(l)%zw(nzb_wall+3,m)       = building_pars(ind_thick_4,building_type)
4065             
4066              surf_usm_v(l)%zw_green(nzb_wall,m)         = building_pars(ind_thick_1,building_type)
4067              surf_usm_v(l)%zw_green(nzb_wall+1,m)       = building_pars(ind_thick_2,building_type)
4068              surf_usm_v(l)%zw_green(nzb_wall+2,m)       = building_pars(ind_thick_3,building_type)
4069              surf_usm_v(l)%zw_green(nzb_wall+3,m)       = building_pars(ind_thick_4,building_type)
4070
4071              surf_usm_v(l)%zw_window(nzb_wall,m)         = building_pars(ind_thick_1_win,building_type)
4072              surf_usm_v(l)%zw_window(nzb_wall+1,m)       = building_pars(ind_thick_2_win,building_type)
4073              surf_usm_v(l)%zw_window(nzb_wall+2,m)       = building_pars(ind_thick_3_win,building_type)
4074              surf_usm_v(l)%zw_window(nzb_wall+3,m)       = building_pars(ind_thick_4_win,building_type)
4075
4076              surf_usm_v(l)%c_surface(m)           = building_pars(ind_c_surface,building_type) 
4077              surf_usm_v(l)%lambda_surf(m)         = building_pars(ind_lambda_surf,building_type)
4078              surf_usm_v(l)%c_surface_green(m)     = building_pars(ind_c_surface_green,building_type) 
4079              surf_usm_v(l)%lambda_surf_green(m)   = building_pars(ind_lambda_surf_green,building_type)
4080              surf_usm_v(l)%c_surface_window(m)    = building_pars(ind_c_surface_win,building_type) 
4081              surf_usm_v(l)%lambda_surf_window(m)  = building_pars(ind_lambda_surf_win,building_type)
4082
4083           ENDDO
4084        ENDDO
4085!
4086!--     Level 2 - initialization via building type read from file
4087        IF ( building_type_f%from_file )  THEN
4088           DO  m = 1, surf_usm_h%ns
4089              i = surf_usm_h%i(m)
4090              j = surf_usm_h%j(m)
4091!
4092!--           For the moment, limit building type to 6 (to overcome errors in input file).
4093              st = building_type_f%var(j,i)
4094              IF ( st /= building_type_f%fill )  THEN
4095
4096!
4097!--              In order to distinguish between ground floor level and
4098!--              above-ground-floor level surfaces, set input indices.
4099
4100                 ind_green_frac_r = MERGE( ind_green_frac_r_gfl, ind_green_frac_r_agfl, &
4101                                           surf_usm_h%ground_level(m) )
4102                 ind_lai_r        = MERGE( ind_lai_r_gfl,        ind_lai_r_agfl,        &
4103                                           surf_usm_h%ground_level(m) )
4104                 ind_z0           = MERGE( ind_z0_gfl,           ind_z0_agfl,           &
4105                                           surf_usm_h%ground_level(m) )
4106                 ind_z0qh         = MERGE( ind_z0qh_gfl,         ind_z0qh_agfl,         &
4107                                           surf_usm_h%ground_level(m) )
4108!
4109!--              Store building type and its name on each surface element
4110                 surf_usm_h%building_type(m)      = st
4111                 surf_usm_h%building_type_name(m) = building_type_name(st)
4112!
4113!--              Initialize relatvie wall- (0), green- (1) and window (2) fractions
4114                 surf_usm_h%frac(ind_veg_wall,m)  = building_pars(ind_wall_frac_r,st)   
4115                 surf_usm_h%frac(ind_pav_green,m) = building_pars(ind_green_frac_r,st) 
4116                 surf_usm_h%frac(ind_wat_win,m)   = building_pars(ind_win_frac_r,st) 
4117                 surf_usm_h%lai(m)                = building_pars(ind_lai_r,st) 
4118
4119                 surf_usm_h%rho_c_wall(nzb_wall,m)   = building_pars(ind_hc1_wall_r,st) 
4120                 surf_usm_h%rho_c_wall(nzb_wall+1,m) = building_pars(ind_hc1_wall_r,st)
4121                 surf_usm_h%rho_c_wall(nzb_wall+2,m) = building_pars(ind_hc2_wall_r,st)
4122                 surf_usm_h%rho_c_wall(nzb_wall+3,m) = building_pars(ind_hc3_wall_r,st)   
4123                 surf_usm_h%lambda_h(nzb_wall,m)   = building_pars(ind_tc1_wall_r,st) 
4124                 surf_usm_h%lambda_h(nzb_wall+1,m) = building_pars(ind_tc1_wall_r,st) 
4125                 surf_usm_h%lambda_h(nzb_wall+2,m) = building_pars(ind_tc2_wall_r,st)
4126                 surf_usm_h%lambda_h(nzb_wall+3,m) = building_pars(ind_tc3_wall_r,st)   
4127                 
4128                 surf_usm_h%rho_c_green(nzb_wall,m)   = rho_c_soil !building_pars(ind_hc1_wall_r,st) 
4129                 surf_usm_h%rho_c_green(nzb_wall+1,m) = rho_c_soil !building_pars(ind_hc1_wall_r,st)
4130                 surf_usm_h%rho_c_green(nzb_wall+2,m) = rho_c_soil !building_pars(ind_hc2_wall_r,st)
4131                 surf_usm_h%rho_c_green(nzb_wall+3,m) = rho_c_soil !building_pars(ind_hc3_wall_r,st)   
4132                 surf_usm_h%lambda_h_green(nzb_wall,m)   = lambda_h_green_sm !building_pars(ind_tc1_wall_r,st) 
4133                 surf_usm_h%lambda_h_green(nzb_wall+1,m) = lambda_h_green_sm !building_pars(ind_tc1_wall_r,st)
4134                 surf_usm_h%lambda_h_green(nzb_wall+2,m) = lambda_h_green_sm !building_pars(ind_tc2_wall_r,st)
4135                 surf_usm_h%lambda_h_green(nzb_wall+3,m) = lambda_h_green_sm !building_pars(ind_tc3_wall_r,st)   
4136               
4137                 surf_usm_h%rho_c_window(nzb_wall,m)   = building_pars(ind_hc1_win_r,st) 
4138                 surf_usm_h%rho_c_window(nzb_wall+1,m) = building_pars(ind_hc1_win_r,st)
4139                 surf_usm_h%rho_c_window(nzb_wall+2,m) = building_pars(ind_hc2_win_r,st)
4140                 surf_usm_h%rho_c_window(nzb_wall+3,m) = building_pars(ind_hc3_win_r,st)   
4141                 surf_usm_h%lambda_h_window(nzb_wall,m)   = building_pars(ind_tc1_win_r,st) 
4142                 surf_usm_h%lambda_h_window(nzb_wall+1,m) = building_pars(ind_tc1_win_r,st) 
4143                 surf_usm_h%lambda_h_window(nzb_wall+2,m) = building_pars(ind_tc2_win_r,st)
4144                 surf_usm_h%lambda_h_window(nzb_wall+3,m) = building_pars(ind_tc3_win_r,st)   
4145
4146                 surf_usm_h%target_temp_summer(m)  = building_pars(ind_indoor_target_temp_summer,st)   
4147                 surf_usm_h%target_temp_winter(m)  = building_pars(ind_indoor_target_temp_winter,st)   
4148!
4149!--              emissivity of wall-, green- and window fraction
4150                 surf_usm_h%emissivity(ind_veg_wall,m)  = building_pars(ind_emis_wall_r,st)
4151                 surf_usm_h%emissivity(ind_pav_green,m) = building_pars(ind_emis_green_r,st)
4152                 surf_usm_h%emissivity(ind_wat_win,m)   = building_pars(ind_emis_win_r,st)
4153
4154                 surf_usm_h%transmissivity(m)      = building_pars(ind_trans_r,st)
4155
4156                 surf_usm_h%z0(m)                  = building_pars(ind_z0,st)
4157                 surf_usm_h%z0h(m)                 = building_pars(ind_z0qh,st)
4158                 surf_usm_h%z0q(m)                 = building_pars(ind_z0qh,st)
4159!
4160!--              albedo type for wall fraction, green fraction, window fraction
4161                 surf_usm_h%albedo_type(ind_veg_wall,m)  = INT( building_pars(ind_alb_wall_r,st) )
4162                 surf_usm_h%albedo_type(ind_pav_green,m) = INT( building_pars(ind_alb_green_r,st) )
4163                 surf_usm_h%albedo_type(ind_wat_win,m)   = INT( building_pars(ind_alb_win_r,st) )
4164
4165                 surf_usm_h%zw(nzb_wall,m)         = building_pars(ind_thick_1_wall_r,st)
4166                 surf_usm_h%zw(nzb_wall+1,m)       = building_pars(ind_thick_2_wall_r,st)
4167                 surf_usm_h%zw(nzb_wall+2,m)       = building_pars(ind_thick_3_wall_r,st)
4168                 surf_usm_h%zw(nzb_wall+3,m)       = building_pars(ind_thick_4_wall_r,st)
4169                 
4170                 surf_usm_h%zw_green(nzb_wall,m)         = building_pars(ind_thick_1_wall_r,st)
4171                 surf_usm_h%zw_green(nzb_wall+1,m)       = building_pars(ind_thick_2_wall_r,st)
4172                 surf_usm_h%zw_green(nzb_wall+2,m)       = building_pars(ind_thick_3_wall_r,st)
4173                 surf_usm_h%zw_green(nzb_wall+3,m)       = building_pars(ind_thick_4_wall_r,st)
4174
4175                 surf_usm_h%zw_window(nzb_wall,m)         = building_pars(ind_thick_1_win_r,st)
4176                 surf_usm_h%zw_window(nzb_wall+1,m)       = building_pars(ind_thick_2_win_r,st)
4177                 surf_usm_h%zw_window(nzb_wall+2,m)       = building_pars(ind_thick_3_win_r,st)
4178                 surf_usm_h%zw_window(nzb_wall+3,m)       = building_pars(ind_thick_4_win_r,st)
4179
4180                 surf_usm_h%c_surface(m)           = building_pars(ind_c_surface,st) 
4181                 surf_usm_h%lambda_surf(m)         = building_pars(ind_lambda_surf,st)
4182                 surf_usm_h%c_surface_green(m)     = building_pars(ind_c_surface_green,st) 
4183                 surf_usm_h%lambda_surf_green(m)   = building_pars(ind_lambda_surf_green,st)
4184                 surf_usm_h%c_surface_window(m)    = building_pars(ind_c_surface_win,st) 
4185                 surf_usm_h%lambda_surf_window(m)  = building_pars(ind_lambda_surf_win,st)
4186                 
4187                 surf_usm_h%green_type_roof(m)     = building_pars(ind_green_type_roof,st)
4188
4189              ENDIF
4190           ENDDO
4191
4192           DO  l = 0, 3
4193              DO  m = 1, surf_usm_v(l)%ns
4194                 i = surf_usm_v(l)%i(m) + surf_usm_v(l)%ioff
4195                 j = surf_usm_v(l)%j(m) + surf_usm_v(l)%joff
4196!
4197!--              For the moment, limit building type to 6 (to overcome errors in input file).
4198
4199                 st = building_type_f%var(j,i)
4200                 IF ( st /= building_type_f%fill )  THEN
4201
4202!
4203!--                 In order to distinguish between ground floor level and
4204!--                 above-ground-floor level surfaces, set input indices.
4205                    ind_alb_green    = MERGE( ind_alb_green_gfl,    ind_alb_green_agfl,    &
4206                                              surf_usm_v(l)%ground_level(m) )
4207                    ind_alb_wall     = MERGE( ind_alb_wall_gfl,     ind_alb_wall_agfl,     &
4208                                              surf_usm_v(l)%ground_level(m) )
4209                    ind_alb_win      = MERGE( ind_alb_win_gfl,      ind_alb_win_agfl,      &
4210                                              surf_usm_v(l)%ground_level(m) )
4211                    ind_wall_frac    = MERGE( ind_wall_frac_gfl,    ind_wall_frac_agfl,    &
4212                                              surf_usm_v(l)%ground_level(m) )
4213                    ind_win_frac     = MERGE( ind_win_frac_gfl,     ind_win_frac_agfl,     &
4214                                              surf_usm_v(l)%ground_level(m) )
4215                    ind_green_frac_w = MERGE( ind_green_frac_w_gfl, ind_green_frac_w_agfl, &
4216                                              surf_usm_v(l)%ground_level(m) )
4217                    ind_green_frac_r = MERGE( ind_green_frac_r_gfl, ind_green_frac_r_agfl, &
4218                                              surf_usm_v(l)%ground_level(m) )
4219                    ind_lai_r        = MERGE( ind_lai_r_gfl,        ind_lai_r_agfl,        &
4220                                              surf_usm_v(l)%ground_level(m) )
4221                    ind_lai_w        = MERGE( ind_lai_w_gfl,        ind_lai_w_agfl,        &
4222                                              surf_usm_v(l)%ground_level(m) )
4223                    ind_hc1          = MERGE( ind_hc1_gfl,          ind_hc1_agfl,          &
4224                                              surf_usm_v(l)%ground_level(m) )
4225                    ind_hc1_win      = MERGE( ind_hc1_win_gfl,      ind_hc1_win_agfl,      &
4226                                              surf_usm_v(l)%ground_level(m) )
4227                    ind_hc2          = MERGE( ind_hc2_gfl,          ind_hc2_agfl,          &
4228                                              surf_usm_v(l)%ground_level(m) )
4229                    ind_hc2_win      = MERGE( ind_hc2_win_gfl,      ind_hc2_win_agfl,      &
4230                                              surf_usm_v(l)%ground_level(m) )
4231                    ind_hc3          = MERGE( ind_hc3_gfl,          ind_hc3_agfl,          &
4232                                              surf_usm_v(l)%ground_level(m) )
4233                    ind_hc3_win      = MERGE( ind_hc3_win_gfl,      ind_hc3_win_agfl,      &
4234                                              surf_usm_v(l)%ground_level(m) )
4235                    ind_tc1          = MERGE( ind_tc1_gfl,          ind_tc1_agfl,          &
4236                                              surf_usm_v(l)%ground_level(m) )
4237                    ind_tc1_win      = MERGE( ind_tc1_win_gfl,      ind_tc1_win_agfl,      &
4238                                              surf_usm_v(l)%ground_level(m) )
4239                    ind_tc2          = MERGE( ind_tc2_gfl,          ind_tc2_agfl,          &
4240                                              surf_usm_v(l)%ground_level(m) )
4241                    ind_tc2_win      = MERGE( ind_tc2_win_gfl,      ind_tc2_win_agfl,      &
4242                                              surf_usm_v(l)%ground_level(m) )
4243                    ind_tc3          = MERGE( ind_tc3_gfl,          ind_tc3_agfl,          &
4244                                              surf_usm_v(l)%ground_level(m) )
4245                    ind_tc3_win      = MERGE( ind_tc3_win_gfl,      ind_tc3_win_agfl,      &
4246                                              surf_usm_v(l)%ground_level(m) )
4247                    ind_thick_1      = MERGE( ind_thick_1_gfl,      ind_thick_1_agfl,      &
4248                                              surf_usm_v(l)%ground_level(m) )
4249                    ind_thick_1_win  = MERGE( ind_thick_1_win_gfl,  ind_thick_1_win_agfl,  &
4250                                              surf_usm_v(l)%ground_level(m) )
4251                    ind_thick_2      = MERGE( ind_thick_2_gfl,      ind_thick_2_agfl,      &
4252                                              surf_usm_v(l)%ground_level(m) )
4253                    ind_thick_2_win  = MERGE( ind_thick_2_win_gfl,  ind_thick_2_win_agfl,  &
4254                                              surf_usm_v(l)%ground_level(m) )
4255                    ind_thick_3      = MERGE( ind_thick_3_gfl,      ind_thick_3_agfl,      &
4256                                              surf_usm_v(l)%ground_level(m) )
4257                    ind_thick_3_win  = MERGE( ind_thick_3_win_gfl,  ind_thick_3_win_agfl,  &
4258                                              surf_usm_v(l)%ground_level(m) )
4259                    ind_thick_4      = MERGE( ind_thick_4_gfl,      ind_thick_4_agfl,      &
4260                                              surf_usm_v(l)%ground_level(m) )
4261                    ind_thick_4_win  = MERGE( ind_thick_4_win_gfl,  ind_thick_4_win_agfl,  &
4262                                              surf_usm_v(l)%ground_level(m) )
4263                    ind_emis_wall    = MERGE( ind_emis_wall_gfl,    ind_emis_wall_agfl,    &
4264                                              surf_usm_v(l)%ground_level(m) )
4265                    ind_emis_green   = MERGE( ind_emis_green_gfl,   ind_emis_green_agfl,   &
4266                                              surf_usm_v(l)%ground_level(m) )
4267                    ind_emis_win     = MERGE( ind_emis_win_gfl,     ind_emis_win_agfl,     &
4268                                              surf_usm_v(l)%ground_level(m) )
4269                    ind_trans        = MERGE( ind_trans_gfl,       ind_trans_agfl,         &
4270                                            surf_usm_v(l)%ground_level(m) )
4271                    ind_z0           = MERGE( ind_z0_gfl,           ind_z0_agfl,           &
4272                                              surf_usm_v(l)%ground_level(m) )
4273                    ind_z0qh         = MERGE( ind_z0qh_gfl,         ind_z0qh_agfl,         &
4274                                              surf_usm_v(l)%ground_level(m) )
4275!
4276!--                 Store building type and its name on each surface element
4277                    surf_usm_v(l)%building_type(m)      = st
4278                    surf_usm_v(l)%building_type_name(m) = building_type_name(st)
4279!
4280!--                 Initialize relatvie wall- (0), green- (1) and window (2) fractions
4281                    surf_usm_v(l)%frac(ind_veg_wall,m)  = building_pars(ind_wall_frac,st)   
4282                    surf_usm_v(l)%frac(ind_pav_green,m) = building_pars(ind_green_frac_w,st) 
4283                    surf_usm_v(l)%frac(ind_wat_win,m)   = building_pars(ind_win_frac,st)   
4284                    surf_usm_v(l)%lai(m)                = building_pars(ind_lai_w,st) 
4285
4286                    surf_usm_v(l)%rho_c_wall(nzb_wall,m)   = building_pars(ind_hc1,st) 
4287                    surf_usm_v(l)%rho_c_wall(nzb_wall+1,m) = building_pars(ind_hc1,st)
4288                    surf_usm_v(l)%rho_c_wall(nzb_wall+2,m) = building_pars(ind_hc2,st)
4289                    surf_usm_v(l)%rho_c_wall(nzb_wall+3,m) = building_pars(ind_hc3,st)
4290                   
4291                    surf_usm_v(l)%rho_c_green(nzb_wall,m)   = rho_c_soil !building_pars(ind_hc1,st) 
4292                    surf_usm_v(l)%rho_c_green(nzb_wall+1,m) = rho_c_soil !building_pars(ind_hc1,st)
4293                    surf_usm_v(l)%rho_c_green(nzb_wall+2,m) = rho_c_soil !building_pars(ind_hc2,st)
4294                    surf_usm_v(l)%rho_c_green(nzb_wall+3,m) = rho_c_soil !building_pars(ind_hc3,st)
4295                   
4296                    surf_usm_v(l)%rho_c_window(nzb_wall,m)   = building_pars(ind_hc1_win,st) 
4297                    surf_usm_v(l)%rho_c_window(nzb_wall+1,m) = building_pars(ind_hc1_win,st)
4298                    surf_usm_v(l)%rho_c_window(nzb_wall+2,m) = building_pars(ind_hc2_win,st)
4299                    surf_usm_v(l)%rho_c_window(nzb_wall+3,m) = building_pars(ind_hc3_win,st)
4300
4301                    surf_usm_v(l)%lambda_h(nzb_wall,m)   = building_pars(ind_tc1,st) 
4302                    surf_usm_v(l)%lambda_h(nzb_wall+1,m) = building_pars(ind_tc1,st) 
4303                    surf_usm_v(l)%lambda_h(nzb_wall+2,m) = building_pars(ind_tc2,st)
4304                    surf_usm_v(l)%lambda_h(nzb_wall+3,m) = building_pars(ind_tc3,st) 
4305                   
4306                    surf_usm_v(l)%lambda_h_green(nzb_wall,m)   = lambda_h_green_sm !building_pars(ind_tc1,st) 
4307                    surf_usm_v(l)%lambda_h_green(nzb_wall+1,m) = lambda_h_green_sm !building_pars(ind_tc1,st)
4308                    surf_usm_v(l)%lambda_h_green(nzb_wall+2,m) = lambda_h_green_sm !building_pars(ind_tc2,st)
4309                    surf_usm_v(l)%lambda_h_green(nzb_wall+3,m) = lambda_h_green_sm !building_pars(ind_tc3,st)
4310                   
4311                    surf_usm_v(l)%lambda_h_window(nzb_wall,m)   = building_pars(ind_tc1_win,st) 
4312                    surf_usm_v(l)%lambda_h_window(nzb_wall+1,m) = building_pars(ind_tc1_win,st) 
4313                    surf_usm_v(l)%lambda_h_window(nzb_wall+2,m) = building_pars(ind_tc2_win,st)
4314                    surf_usm_v(l)%lambda_h_window(nzb_wall+3,m) = building_pars(ind_tc3_win,st) 
4315
4316                    surf_usm_v(l)%target_temp_summer(m)  = building_pars(ind_indoor_target_temp_summer,st)   
4317                    surf_usm_v(l)%target_temp_winter(m)  = building_pars(ind_indoor_target_temp_winter,st)   
4318!
4319!--                 emissivity of wall-, green- and window fraction
4320                    surf_usm_v(l)%emissivity(ind_veg_wall,m)  = building_pars(ind_emis_wall,st)
4321                    surf_usm_v(l)%emissivity(ind_pav_green,m) = building_pars(ind_emis_green,st)
4322                    surf_usm_v(l)%emissivity(ind_wat_win,m)   = building_pars(ind_emis_win,st)
4323
4324                    surf_usm_v(l)%transmissivity(m)      = building_pars(ind_trans,st)
4325
4326                    surf_usm_v(l)%z0(m)                  = building_pars(ind_z0,st)
4327                    surf_usm_v(l)%z0h(m)                 = building_pars(ind_z0qh,st)
4328                    surf_usm_v(l)%z0q(m)                 = building_pars(ind_z0qh,st)
4329
4330                    surf_usm_v(l)%albedo_type(ind_veg_wall,m)  = INT( building_pars(ind_alb_wall,st) )
4331                    surf_usm_v(l)%albedo_type(ind_pav_green,m) = INT( building_pars(ind_alb_green,st) )
4332                    surf_usm_v(l)%albedo_type(ind_wat_win,m)   = INT( building_pars(ind_alb_win,st) )
4333
4334                    surf_usm_v(l)%zw(nzb_wall,m)         = building_pars(ind_thick_1,st)
4335                    surf_usm_v(l)%zw(nzb_wall+1,m)       = building_pars(ind_thick_2,st)
4336                    surf_usm_v(l)%zw(nzb_wall+2,m)       = building_pars(ind_thick_3,st)
4337                    surf_usm_v(l)%zw(nzb_wall+3,m)       = building_pars(ind_thick_4,st)
4338                   
4339                    surf_usm_v(l)%zw_green(nzb_wall,m)         = building_pars(ind_thick_1,st)
4340                    surf_usm_v(l)%zw_green(nzb_wall+1,m)       = building_pars(ind_thick_2,st)
4341                    surf_usm_v(l)%zw_green(nzb_wall+2,m)       = building_pars(ind_thick_3,st)
4342                    surf_usm_v(l)%zw_green(nzb_wall+3,m)       = building_pars(ind_thick_4,st)
4343                   
4344                    surf_usm_v(l)%zw_window(nzb_wall,m)         = building_pars(ind_thick_1_win,st)
4345                    surf_usm_v(l)%zw_window(nzb_wall+1,m)       = building_pars(ind_thick_2_win,st)
4346                    surf_usm_v(l)%zw_window(nzb_wall+2,m)       = building_pars(ind_thick_3_win,st)
4347                    surf_usm_v(l)%zw_window(nzb_wall+3,m)       = building_pars(ind_thick_4_win,st)
4348
4349                    surf_usm_v(l)%c_surface(m)           = building_pars(ind_c_surface,st) 
4350                    surf_usm_v(l)%lambda_surf(m)         = building_pars(ind_lambda_surf,st) 
4351                    surf_usm_v(l)%c_surface_green(m)     = building_pars(ind_c_surface_green,st) 
4352                    surf_usm_v(l)%lambda_surf_green(m)   = building_pars(ind_lambda_surf_green,st) 
4353                    surf_usm_v(l)%c_surface_window(m)    = building_pars(ind_c_surface_win,st) 
4354                    surf_usm_v(l)%lambda_surf_window(m)  = building_pars(ind_lambda_surf_win,st) 
4355
4356
4357                 ENDIF
4358              ENDDO
4359           ENDDO
4360        ENDIF 
4361       
4362!
4363!--     Level 3 - initialization via building_pars read from file. Note, only
4364!--     variables that are also defined in the input-standard can be initialized
4365!--     via file. Other variables will be initialized on level 1 or 2.
4366        IF ( building_pars_f%from_file )  THEN
4367           DO  m = 1, surf_usm_h%ns
4368              i = surf_usm_h%i(m)
4369              j = surf_usm_h%j(m)
4370
4371!
4372!--           In order to distinguish between ground floor level and
4373!--           above-ground-floor level surfaces, set input indices.
4374              ind_wall_frac    = MERGE( ind_wall_frac_gfl,                     &
4375                                        ind_wall_frac_agfl,                    &
4376                                        surf_usm_h%ground_level(m) )
4377              ind_green_frac_r = MERGE( ind_green_frac_r_gfl,                  &
4378                                        ind_green_frac_r_agfl,                 &
4379                                        surf_usm_h%ground_level(m) )
4380              ind_win_frac     = MERGE( ind_win_frac_gfl,                      &
4381                                        ind_win_frac_agfl,                     &
4382                                        surf_usm_h%ground_level(m) )
4383              ind_lai_r        = MERGE( ind_lai_r_gfl,                         &
4384                                        ind_lai_r_agfl,                        &
4385                                        surf_usm_h%ground_level(m) )
4386              ind_z0           = MERGE( ind_z0_gfl,                            &
4387                                        ind_z0_agfl,                           &
4388                                        surf_usm_h%ground_level(m) )
4389              ind_z0qh         = MERGE( ind_z0qh_gfl,                          &
4390                                        ind_z0qh_agfl,                         &
4391                                        surf_usm_h%ground_level(m) )
4392              ind_hc1          = MERGE( ind_hc1_gfl,                           &
4393                                        ind_hc1_agfl,                          &
4394                                        surf_usm_h%ground_level(m) )
4395              ind_hc2          = MERGE( ind_hc2_gfl,                           &
4396                                        ind_hc2_agfl,                          &
4397                                        surf_usm_h%ground_level(m) )
4398              ind_hc3          = MERGE( ind_hc3_gfl,                           &
4399                                        ind_hc3_agfl,                          &
4400                                        surf_usm_h%ground_level(m) )
4401              ind_tc1          = MERGE( ind_tc1_gfl,                           &
4402                                        ind_tc1_agfl,                          &
4403                                        surf_usm_h%ground_level(m) )
4404              ind_tc2          = MERGE( ind_tc2_gfl,                           &
4405                                        ind_tc2_agfl,                          &
4406                                        surf_usm_h%ground_level(m) )
4407              ind_tc3          = MERGE( ind_tc3_gfl,                           &
4408                                        ind_tc3_agfl,                          &
4409                                        surf_usm_h%ground_level(m) )
4410              ind_emis_wall    = MERGE( ind_emis_wall_gfl,                     &
4411                                        ind_emis_wall_agfl,                    &
4412                                        surf_usm_h%ground_level(m) )
4413              ind_emis_green   = MERGE( ind_emis_green_gfl,                    &
4414                                        ind_emis_green_agfl,                   &
4415                                        surf_usm_h%ground_level(m) )
4416              ind_emis_win     = MERGE( ind_emis_win_gfl,                      &
4417                                        ind_emis_win_agfl,                     &
4418                                        surf_usm_h%ground_level(m) )
4419              ind_trans        = MERGE( ind_trans_gfl,                         &
4420                                        ind_trans_agfl,                        &
4421                                        surf_usm_h%ground_level(m) )
4422
4423!
4424!--           Initialize relatvie wall- (0), green- (1) and window (2) fractions
4425              IF ( building_pars_f%pars_xy(ind_wall_frac,j,i) /=               &
4426                   building_pars_f%fill )                                      &
4427                 surf_usm_h%frac(ind_veg_wall,m)  =                            &
4428                                    building_pars_f%pars_xy(ind_wall_frac,j,i)   
4429                 
4430              IF ( building_pars_f%pars_xy(ind_green_frac_r,j,i) /=            &         
4431                   building_pars_f%fill )                                      & 
4432                 surf_usm_h%frac(ind_pav_green,m) =                            &
4433                                    building_pars_f%pars_xy(ind_green_frac_r,j,i) 
4434                 
4435              IF ( building_pars_f%pars_xy(ind_win_frac,j,i) /=                &
4436                   building_pars_f%fill )                                      & 
4437                 surf_usm_h%frac(ind_wat_win,m)   =                            &
4438                                    building_pars_f%pars_xy(ind_win_frac,j,i)
4439 
4440              IF ( building_pars_f%pars_xy(ind_lai_r,j,i) /=                   &
4441                   building_pars_f%fill )                                      &
4442                 surf_usm_h%lai(m)  = building_pars_f%pars_xy(ind_lai_r,j,i)
4443
4444              IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=                     &
4445                   building_pars_f%fill )  THEN
4446                 surf_usm_h%rho_c_wall(nzb_wall,m)   =                         &
4447                                    building_pars_f%pars_xy(ind_hc1,j,i) 
4448                 surf_usm_h%rho_c_wall(nzb_wall+1,m) =                         &
4449                                    building_pars_f%pars_xy(ind_hc1,j,i)
4450              ENDIF
4451             
4452             
4453              IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=                     &
4454                   building_pars_f%fill )                                      &
4455                 surf_usm_h%rho_c_wall(nzb_wall+2,m) =                         &
4456                                    building_pars_f%pars_xy(ind_hc2,j,i)
4457                 
4458              IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=                     &
4459                   building_pars_f%fill )                                      &
4460                 surf_usm_h%rho_c_wall(nzb_wall+3,m) =                         &
4461                                    building_pars_f%pars_xy(ind_hc3,j,i)
4462                 
4463              IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=                     &
4464                   building_pars_f%fill )  THEN
4465                 surf_usm_h%rho_c_green(nzb_wall,m)   =                        &
4466                                    building_pars_f%pars_xy(ind_hc1,j,i) 
4467                 surf_usm_h%rho_c_green(nzb_wall+1,m) =                        &
4468                                    building_pars_f%pars_xy(ind_hc1,j,i)
4469              ENDIF
4470              IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=                     &
4471                   building_pars_f%fill )                                      &
4472                 surf_usm_h%rho_c_green(nzb_wall+2,m) =                        &
4473                                    building_pars_f%pars_xy(ind_hc2,j,i)
4474                 
4475              IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=                     &
4476                   building_pars_f%fill )                                      &
4477                 surf_usm_h%rho_c_green(nzb_wall+3,m) =                        &
4478                                    building_pars_f%pars_xy(ind_hc3,j,i)
4479                 
4480              IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=                     &
4481                   building_pars_f%fill )  THEN
4482                 surf_usm_h%rho_c_window(nzb_wall,m)   =                       &
4483                                    building_pars_f%pars_xy(ind_hc1,j,i) 
4484                 surf_usm_h%rho_c_window(nzb_wall+1,m) =                       &
4485                                    building_pars_f%pars_xy(ind_hc1,j,i)
4486              ENDIF
4487              IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=                     &
4488                   building_pars_f%fill )                                      &
4489                 surf_usm_h%rho_c_window(nzb_wall+2,m) =                       &
4490                                    building_pars_f%pars_xy(ind_hc2,j,i)
4491                 
4492              IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=                     &
4493                   building_pars_f%fill )                                      &
4494                 surf_usm_h%rho_c_window(nzb_wall+3,m) =                       &
4495                                    building_pars_f%pars_xy(ind_hc3,j,i)
4496
4497              IF ( building_pars_f%pars_xy(ind_tc1,j,i) /=                     &
4498                   building_pars_f%fill )  THEN
4499                 surf_usm_h%lambda_h(nzb_wall,m)   =                           &
4500                                    building_pars_f%pars_xy(ind_tc1,j,i)         
4501                 surf_usm_h%lambda_h(nzb_wall+1,m) =                           &
4502                                    building_pars_f%pars_xy(ind_tc1,j,i)       
4503              ENDIF
4504              IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=                     & 
4505                   building_pars_f%fill )                                      &
4506                 surf_usm_h%lambda_h(nzb_wall+2,m) =                           &
4507                                    building_pars_f%pars_xy(ind_tc2,j,i)
4508                 
4509              IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=                     &
4510                   building_pars_f%fill )                                      & 
4511                 surf_usm_h%lambda_h(nzb_wall+3,m) =                           &
4512                                    building_pars_f%pars_xy(ind_tc3,j,i)   
4513                 
4514              IF ( building_pars_f%pars_xy(ind_tc1,j,i) /=                     &
4515                   building_pars_f%fill )  THEN
4516                 surf_usm_h%lambda_h_green(nzb_wall,m)   =                     &
4517                                     building_pars_f%pars_xy(ind_tc1,j,i)         
4518                 surf_usm_h%lambda_h_green(nzb_wall+1,m) =                     &
4519                                     building_pars_f%pars_xy(ind_tc1,j,i)       
4520              ENDIF
4521              IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=                     & 
4522                   building_pars_f%fill )                                      &
4523                 surf_usm_h%lambda_h_green(nzb_wall+2,m) =                     &
4524                                    building_pars_f%pars_xy(ind_tc2,j,i)
4525                 
4526              IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=                     &       
4527                   building_pars_f%fill )                                      &
4528                 surf_usm_h%lambda_h_green(nzb_wall+3,m) =                     &
4529                                    building_pars_f%pars_xy(ind_tc3,j,i)   
4530                 
4531              IF ( building_pars_f%pars_xy(ind_tc1_win_r,j,i) /=               &
4532                   building_pars_f%fill )  THEN
4533                 surf_usm_h%lambda_h_window(nzb_wall,m)   =                    &
4534                                     building_pars_f%pars_xy(ind_tc1_win_r,j,i)         
4535                 surf_usm_h%lambda_h_window(nzb_wall+1,m) =                    &
4536                                     building_pars_f%pars_xy(ind_tc1_win_r,j,i)       
4537              ENDIF
4538              IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=                     &     
4539                   building_pars_f%fill )                                      &
4540                 surf_usm_h%lambda_h_window(nzb_wall+2,m) =                    &
4541                                     building_pars_f%pars_xy(ind_tc2,j,i)
4542                 
4543              IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=                     &   
4544                   building_pars_f%fill )                                      &
4545                 surf_usm_h%lambda_h_window(nzb_wall+3,m) =                    &
4546                                    building_pars_f%pars_xy(ind_tc3,j,i)   
4547
4548              IF ( building_pars_f%pars_xy(ind_indoor_target_temp_summer,j,i) /=&           
4549                   building_pars_f%fill )                                      & 
4550                 surf_usm_h%target_temp_summer(m)  =                           &
4551                      building_pars_f%pars_xy(ind_indoor_target_temp_summer,j,i)   
4552              IF ( building_pars_f%pars_xy(ind_indoor_target_temp_winter,j,i) /=&           
4553                   building_pars_f%fill )                                      & 
4554                 surf_usm_h%target_temp_winter(m)  =                           &
4555                      building_pars_f%pars_xy(ind_indoor_target_temp_winter,j,i)   
4556
4557              IF ( building_pars_f%pars_xy(ind_emis_wall,j,i) /=               &   
4558                   building_pars_f%fill )                                      &
4559                 surf_usm_h%emissivity(ind_veg_wall,m)  =                      &
4560                                    building_pars_f%pars_xy(ind_emis_wall,j,i)
4561                 
4562              IF ( building_pars_f%pars_xy(ind_emis_green,j,i) /=              &           
4563                   building_pars_f%fill )                                      &
4564                 surf_usm_h%emissivity(ind_pav_green,m) =                      &
4565                                     building_pars_f%pars_xy(ind_emis_green,j,i)
4566                 
4567              IF ( building_pars_f%pars_xy(ind_emis_win,j,i) /=                & 
4568                   building_pars_f%fill )                                      &
4569                 surf_usm_h%emissivity(ind_wat_win,m)   =                      &
4570                                     building_pars_f%pars_xy(ind_emis_win,j,i)
4571                 
4572              IF ( building_pars_f%pars_xy(ind_trans,j,i) /=                   &   
4573                   building_pars_f%fill )                                      &
4574                 surf_usm_h%transmissivity(m) =                                &
4575                                    building_pars_f%pars_xy(ind_trans,j,i)
4576
4577              IF ( building_pars_f%pars_xy(ind_z0,j,i) /=                      &         
4578                   building_pars_f%fill )                                      &
4579                 surf_usm_h%z0(m) = building_pars_f%pars_xy(ind_z0,j,i)
4580                 
4581              IF ( building_pars_f%pars_xy(ind_z0qh,j,i) /=                    &           
4582                   building_pars_f%fill )                                      &
4583                 surf_usm_h%z0h(m) = building_pars_f%pars_xy(ind_z0qh,j,i)
4584              IF ( building_pars_f%pars_xy(ind_z0qh,j,i) /=                    &           
4585                   building_pars_f%fill )                                      &
4586                 surf_usm_h%z0q(m) = building_pars_f%pars_xy(ind_z0qh,j,i)
4587
4588              IF ( building_pars_f%pars_xy(ind_alb_wall_agfl,j,i) /=           &         
4589                   building_pars_f%fill )                                      & 
4590                 surf_usm_h%albedo_type(ind_veg_wall,m)  =                     &
4591                                 building_pars_f%pars_xy(ind_alb_wall_agfl,j,i)
4592                 
4593              IF ( building_pars_f%pars_xy(ind_alb_green_agfl,j,i) /=          &           
4594                   building_pars_f%fill )                                      &
4595                 surf_usm_h%albedo_type(ind_pav_green,m) =                     &
4596                                building_pars_f%pars_xy(ind_alb_green_agfl,j,i)
4597              IF ( building_pars_f%pars_xy(ind_alb_win_agfl,j,i) /=            &         
4598                   building_pars_f%fill )                                      &
4599                 surf_usm_h%albedo_type(ind_wat_win,m)   =                     &
4600                                   building_pars_f%pars_xy(ind_alb_win_agfl,j,i)
4601
4602              IF ( building_pars_f%pars_xy(ind_thick_1_agfl,j,i) /=            &         
4603                   building_pars_f%fill )                                      & 
4604                 surf_usm_h%zw(nzb_wall,m) =                                   &
4605                                  building_pars_f%pars_xy(ind_thick_1_agfl,j,i)
4606                 
4607              IF ( building_pars_f%pars_xy(ind_thick_2_agfl,j,i) /=            &         
4608                   building_pars_f%fill )                                      &
4609                 surf_usm_h%zw(nzb_wall+1,m) =                                 &
4610                                  building_pars_f%pars_xy(ind_thick_2_agfl,j,i)
4611                 
4612              IF ( building_pars_f%pars_xy(ind_thick_3_agfl,j,i) /=            &         
4613                   building_pars_f%fill )                                      &
4614                 surf_usm_h%zw(nzb_wall+2,m) =                                 &
4615                                  building_pars_f%pars_xy(ind_thick_3_agfl,j,i)
4616                 
4617                 
4618              IF ( building_pars_f%pars_xy(ind_thick_4_agfl,j,i) /=            &         
4619                   building_pars_f%fill )                                      & 
4620                 surf_usm_h%zw(nzb_wall+3,m) =                                 &
4621                                  building_pars_f%pars_xy(ind_thick_4_agfl,j,i)
4622                 
4623              IF ( building_pars_f%pars_xy(ind_thick_1_agfl,j,i) /=            &           
4624                   building_pars_f%fill )                                      &
4625                 surf_usm_h%zw_green(nzb_wall,m) =                             &
4626                                  building_pars_f%pars_xy(ind_thick_1_agfl,j,i)
4627                 
4628              IF ( building_pars_f%pars_xy(ind_thick_2_agfl,j,i) /=            &         
4629                   building_pars_f%fill )                                      &
4630                 surf_usm_h%zw_green(nzb_wall+1,m) =                           &
4631                                   building_pars_f%pars_xy(ind_thick_2_agfl,j,i)
4632                 
4633              IF ( building_pars_f%pars_xy(ind_thick_3_agfl,j,i) /=            &         
4634                   building_pars_f%fill )                                      & 
4635                 surf_usm_h%zw_green(nzb_wall+2,m) =                           &
4636                                   building_pars_f%pars_xy(ind_thick_3_agfl,j,i)
4637                 
4638              IF ( building_pars_f%pars_xy(ind_thick_4_agfl,j,i) /=            &         
4639                   building_pars_f%fill )                                      &
4640                 surf_usm_h%zw_green(nzb_wall+3,m) =                           &
4641                                   building_pars_f%pars_xy(ind_thick_4_agfl,j,i)
4642
4643              IF ( building_pars_f%pars_xy(ind_c_surface,j,i) /=               &       
4644                   building_pars_f%fill )                                      & 
4645                 surf_usm_h%c_surface(m) =                                     &
4646                                    building_pars_f%pars_xy(ind_c_surface,j,i)
4647                 
4648              IF ( building_pars_f%pars_xy(ind_lambda_surf,j,i) /=             &       
4649                   building_pars_f%fill )                                      &
4650                 surf_usm_h%lambda_surf(m) =                                   &
4651                                    building_pars_f%pars_xy(ind_lambda_surf,j,i)
4652             
4653           ENDDO
4654
4655
4656
4657           DO  l = 0, 3
4658              DO  m = 1, surf_usm_v(l)%ns
4659                 i = surf_usm_v(l)%i(m) + surf_usm_v(l)%ioff
4660                 j = surf_usm_v(l)%j(m) + surf_usm_v(l)%joff
4661               
4662!
4663!--                 In order to distinguish between ground floor level and
4664!--                 above-ground-floor level surfaces, set input indices.
4665                    ind_wall_frac    = MERGE( ind_wall_frac_gfl,               &
4666                                              ind_wall_frac_agfl,              &
4667                                              surf_usm_v(l)%ground_level(m) )
4668                    ind_green_frac_w = MERGE( ind_green_frac_w_gfl,            &
4669                                              ind_green_frac_w_agfl,           &
4670                                              surf_usm_v(l)%ground_level(m) )
4671                    ind_win_frac     = MERGE( ind_win_frac_gfl,                &
4672                                              ind_win_frac_agfl,               &
4673                                              surf_usm_v(l)%ground_level(m) )
4674                    ind_lai_w        = MERGE( ind_lai_w_gfl,                   &
4675                                              ind_lai_w_agfl,                  &
4676                                              surf_usm_v(l)%ground_level(m) )
4677                    ind_z0           = MERGE( ind_z0_gfl,                      &
4678                                              ind_z0_agfl,                     &
4679                                              surf_usm_v(l)%ground_level(m) )
4680                    ind_z0qh         = MERGE( ind_z0qh_gfl,                    &
4681                                              ind_z0qh_agfl,                   &
4682                                              surf_usm_v(l)%ground_level(m) )
4683                    ind_hc1          = MERGE( ind_hc1_gfl,                     &
4684                                              ind_hc1_agfl,                    &
4685                                              surf_usm_v(l)%ground_level(m) )
4686                    ind_hc2          = MERGE( ind_hc2_gfl,                     &
4687                                              ind_hc2_agfl,                    &
4688                                              surf_usm_v(l)%ground_level(m) )
4689                    ind_hc3          = MERGE( ind_hc3_gfl,                     &
4690                                              ind_hc3_agfl,                    &
4691                                              surf_usm_v(l)%ground_level(m) )
4692                    ind_tc1          = MERGE( ind_tc1_gfl,                     &
4693                                              ind_tc1_agfl,                    &
4694                                              surf_usm_v(l)%ground_level(m) )
4695                    ind_tc2          = MERGE( ind_tc2_gfl,                     &
4696                                              ind_tc2_agfl,                    &
4697                                              surf_usm_v(l)%ground_level(m) )
4698                    ind_tc3          = MERGE( ind_tc3_gfl,                     &
4699                                              ind_tc3_agfl,                    &
4700                                              surf_usm_v(l)%ground_level(m) )
4701                    ind_emis_wall    = MERGE( ind_emis_wall_gfl,               &
4702                                              ind_emis_wall_agfl,              &
4703                                              surf_usm_v(l)%ground_level(m) )
4704                    ind_emis_green   = MERGE( ind_emis_green_gfl,              &
4705                                              ind_emis_green_agfl,             &
4706                                              surf_usm_v(l)%ground_level(m) )
4707                    ind_emis_win     = MERGE( ind_emis_win_gfl,                &
4708                                              ind_emis_win_agfl,               &
4709                                              surf_usm_v(l)%ground_level(m) )
4710                    ind_trans        = MERGE( ind_trans_gfl,                   &
4711                                              ind_trans_agfl,                  &
4712                                              surf_usm_v(l)%ground_level(m) )
4713                   
4714!                   
4715!--                 Initialize relatvie wall- (0), green- (1) and window (2) fractions
4716                    IF ( building_pars_f%pars_xy(ind_wall_frac,j,i) /=         &
4717                         building_pars_f%fill )                                &
4718                       surf_usm_v(l)%frac(ind_veg_wall,m)  =                   &
4719                                          building_pars_f%pars_xy(ind_wall_frac,j,i)   
4720                       
4721                    IF ( building_pars_f%pars_xy(ind_green_frac_w,j,i) /=      &         
4722                         building_pars_f%fill )                                & 
4723                       surf_usm_v(l)%frac(ind_pav_green,m) =                   &
4724                                  building_pars_f%pars_xy(ind_green_frac_w,j,i) 
4725                       
4726                    IF ( building_pars_f%pars_xy(ind_win_frac,j,i) /=          &
4727                         building_pars_f%fill )                                & 
4728                       surf_usm_v(l)%frac(ind_wat_win,m)   =                   &
4729                                       building_pars_f%pars_xy(ind_win_frac,j,i)
4730                   
4731                    IF ( building_pars_f%pars_xy(ind_lai_w,j,i) /=             &
4732                         building_pars_f%fill )                                &
4733                       surf_usm_v(l)%lai(m)  =                                 &
4734                                       building_pars_f%pars_xy(ind_lai_w,j,i)
4735                   
4736                    IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=               &
4737                         building_pars_f%fill )  THEN
4738                       surf_usm_v(l)%rho_c_wall(nzb_wall,m)   =                &
4739                                          building_pars_f%pars_xy(ind_hc1,j,i) 
4740                       surf_usm_v(l)%rho_c_wall(nzb_wall+1,m) =                &
4741                                          building_pars_f%pars_xy(ind_hc1,j,i)
4742                    ENDIF
4743                   
4744                   
4745                    IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=               &
4746                         building_pars_f%fill )                                &
4747                       surf_usm_v(l)%rho_c_wall(nzb_wall+2,m) =                &
4748                                          building_pars_f%pars_xy(ind_hc2,j,i)
4749                       
4750                    IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=               &         
4751                         building_pars_f%fill )                                &
4752                       surf_usm_v(l)%rho_c_wall(nzb_wall+3,m) =                &
4753                                          building_pars_f%pars_xy(ind_hc3,j,i)
4754                       
4755                    IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=               &
4756                         building_pars_f%fill )  THEN
4757                       surf_usm_v(l)%rho_c_green(nzb_wall,m)   =               &
4758                                          building_pars_f%pars_xy(ind_hc1,j,i) 
4759                       surf_usm_v(l)%rho_c_green(nzb_wall+1,m) =               &
4760                                          building_pars_f%pars_xy(ind_hc1,j,i)
4761                    ENDIF
4762                    IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=               &
4763                         building_pars_f%fill )                                &
4764                       surf_usm_v(l)%rho_c_green(nzb_wall+2,m) =               &
4765                                          building_pars_f%pars_xy(ind_hc2,j,i)
4766                       
4767                    IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=               &
4768                         building_pars_f%fill )                                &
4769                       surf_usm_v(l)%rho_c_green(nzb_wall+3,m) =               &
4770                                          building_pars_f%pars_xy(ind_hc3,j,i)
4771                       
4772                    IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=               &
4773                         building_pars_f%fill )  THEN
4774                       surf_usm_v(l)%rho_c_window(nzb_wall,m)   =              &
4775                                          building_pars_f%pars_xy(ind_hc1,j,i) 
4776                       surf_usm_v(l)%rho_c_window(nzb_wall+1,m) =              &
4777                                          building_pars_f%pars_xy(ind_hc1,j,i)
4778                    ENDIF
4779                    IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=               &
4780                         building_pars_f%fill )                                &
4781                       surf_usm_v(l)%rho_c_window(nzb_wall+2,m) =              &
4782                                          building_pars_f%pars_xy(ind_hc2,j,i)
4783                       
4784                    IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=               &
4785                         building_pars_f%fill )                                &
4786                       surf_usm_v(l)%rho_c_window(nzb_wall+3,m) =              &
4787                                          building_pars_f%pars_xy(ind_hc3,j,i)
4788                   
4789                    IF ( building_pars_f%pars_xy(ind_tc1,j,i) /=               &
4790                         building_pars_f%fill )  THEN
4791                       surf_usm_v(l)%lambda_h(nzb_wall,m)   =                  &
4792                                          building_pars_f%pars_xy(ind_tc1,j,i)   
4793                       surf_usm_v(l)%lambda_h(nzb_wall+1,m) =                  &
4794                                          building_pars_f%pars_xy(ind_tc1,j,i) 
4795                    ENDIF
4796                    IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=               & 
4797                         building_pars_f%fill )                                &
4798                       surf_usm_v(l)%lambda_h(nzb_wall+2,m) =                  &
4799                                          building_pars_f%pars_xy(ind_tc2,j,i)
4800                       
4801                    IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=               &
4802                         building_pars_f%fill )                                & 
4803                       surf_usm_v(l)%lambda_h(nzb_wall+3,m) =                  &
4804                                          building_pars_f%pars_xy(ind_tc3,j,i) 
4805                       
4806                    IF ( building_pars_f%pars_xy(ind_tc1,j,i) /=               &
4807                         building_pars_f%fill )  THEN
4808                       surf_usm_v(l)%lambda_h_green(nzb_wall,m)   =            &
4809                                           building_pars_f%pars_xy(ind_tc1,j,i)   
4810                       surf_usm_v(l)%lambda_h_green(nzb_wall+1,m) =            &
4811                                           building_pars_f%pars_xy(ind_tc1,j,i) 
4812                    ENDIF
4813                    IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=               & 
4814                         building_pars_f%fill )                                &
4815                       surf_usm_v(l)%lambda_h_green(nzb_wall+2,m) =            &
4816                                          building_pars_f%pars_xy(ind_tc2,j,i)
4817                       
4818                    IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=               &       
4819                         building_pars_f%fill )                                &
4820                       surf_usm_v(l)%lambda_h_green(nzb_wall+3,m) =            &
4821                                          building_pars_f%pars_xy(ind_tc3,j,i) 
4822                       
4823                    IF ( building_pars_f%pars_xy(ind_tc1_win_r,j,i) /=         &
4824                         building_pars_f%fill )  THEN
4825                       surf_usm_v(l)%lambda_h_window(nzb_wall,m)   =           &
4826                                     building_pars_f%pars_xy(ind_tc1_win_r,j,i)         
4827                       surf_usm_v(l)%lambda_h_window(nzb_wall+1,m) =           &
4828                                     building_pars_f%pars_xy(ind_tc1_win_r,j,i)       
4829                    ENDIF
4830                    IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=               &     
4831                         building_pars_f%fill )                                &
4832                       surf_usm_v(l)%lambda_h_window(nzb_wall+2,m) =           &
4833                                           building_pars_f%pars_xy(ind_tc2,j,i)
4834                       
4835                    IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=               &   
4836                         building_pars_f%fill )                                &
4837                       surf_usm_v(l)%lambda_h_window(nzb_wall+3,m) =           &
4838                                          building_pars_f%pars_xy(ind_tc3,j,i)   
4839                   
4840                    IF ( building_pars_f%pars_xy(ind_indoor_target_temp_summer,j,i) /=&           
4841                         building_pars_f%fill )                                & 
4842                       surf_usm_v(l)%target_temp_summer(m)  =                  &
4843                            building_pars_f%pars_xy(ind_indoor_target_temp_summer,j,i)   
4844                    IF ( building_pars_f%pars_xy(ind_indoor_target_temp_winter,j,i) /=&           
4845                         building_pars_f%fill )                                & 
4846                       surf_usm_v(l)%target_temp_winter(m)  =                  &
4847                            building_pars_f%pars_xy(ind_indoor_target_temp_winter,j,i)   
4848                   
4849                    IF ( building_pars_f%pars_xy(ind_emis_wall,j,i) /=         &   
4850                         building_pars_f%fill )                                &
4851                       surf_usm_v(l)%emissivity(ind_veg_wall,m)  =             &
4852                                      building_pars_f%pars_xy(ind_emis_wall,j,i)
4853                       
4854                    IF ( building_pars_f%pars_xy(ind_emis_green,j,i) /=        &           
4855                         building_pars_f%fill )                                &
4856                       surf_usm_v(l)%emissivity(ind_pav_green,m) =             &
4857                                      building_pars_f%pars_xy(ind_emis_green,j,i)
4858                       
4859                    IF ( building_pars_f%pars_xy(ind_emis_win,j,i) /=          & 
4860                         building_pars_f%fill )                                &
4861                       surf_usm_v(l)%emissivity(ind_wat_win,m)   =             &
4862                                      building_pars_f%pars_xy(ind_emis_win,j,i)
4863                       
4864                    IF ( building_pars_f%pars_xy(ind_trans,j,i) /=             &   
4865                         building_pars_f%fill )                                &
4866                       surf_usm_v(l)%transmissivity(m) =                       &
4867                                          building_pars_f%pars_xy(ind_trans,j,i)
4868                   
4869                    IF ( building_pars_f%pars_xy(ind_z0,j,i) /=                &         
4870                         building_pars_f%fill )                                &
4871                       surf_usm_v(l)%z0(m) = building_pars_f%pars_xy(ind_z0,j,i)
4872                       
4873                    IF ( building_pars_f%pars_xy(ind_z0qh,j,i) /=              &           
4874                         building_pars_f%fill )                                &
4875                       surf_usm_v(l)%z0h(m) =                                  &
4876                                       building_pars_f%pars_xy(ind_z0qh,j,i)
4877                    IF ( building_pars_f%pars_xy(ind_z0qh,j,i) /=              &           
4878                         building_pars_f%fill )                                &
4879                       surf_usm_v(l)%z0q(m) =                                  &
4880                                       building_pars_f%pars_xy(ind_z0qh,j,i)
4881                   
4882                    IF ( building_pars_f%pars_xy(ind_alb_wall_agfl,j,i) /=     &         
4883                         building_pars_f%fill )                                & 
4884                       surf_usm_v(l)%albedo_type(ind_veg_wall,m)  =            &
4885                                 building_pars_f%pars_xy(ind_alb_wall_agfl,j,i)
4886                       
4887                    IF ( building_pars_f%pars_xy(ind_alb_green_agfl,j,i) /=    &           
4888                         building_pars_f%fill )                                &
4889                       surf_usm_v(l)%albedo_type(ind_pav_green,m) =            &
4890                                 building_pars_f%pars_xy(ind_alb_green_agfl,j,i)
4891                    IF ( building_pars_f%pars_xy(ind_alb_win_agfl,j,i) /=      &         
4892                         building_pars_f%fill )                                &
4893                       surf_usm_v(l)%albedo_type(ind_wat_win,m)   =            &
4894                                   building_pars_f%pars_xy(ind_alb_win_agfl,j,i)
4895                   
4896                    IF ( building_pars_f%pars_xy(ind_thick_1_agfl,j,i) /=      &         
4897                         building_pars_f%fill )                                & 
4898                       surf_usm_v(l)%zw(nzb_wall,m) =                          &
4899                                   building_pars_f%pars_xy(ind_thick_1_agfl,j,i)
4900                       
4901                    IF ( building_pars_f%pars_xy(ind_thick_2_agfl,j,i) /=      &         
4902                         building_pars_f%fill )                                &
4903                       surf_usm_v(l)%zw(nzb_wall+1,m) =                        &
4904                                   building_pars_f%pars_xy(ind_thick_2_agfl,j,i)
4905                       
4906                    IF ( building_pars_f%pars_xy(ind_thick_3_agfl,j,i) /=      &         
4907                         building_pars_f%fill )                                &
4908                       surf_usm_v(l)%zw(nzb_wall+2,m) =                        &
4909                                   building_pars_f%pars_xy(ind_thick_3_agfl,j,i)
4910                       
4911                       
4912                    IF ( building_pars_f%pars_xy(ind_thick_4_agfl,j,i) /=      &         
4913                         building_pars_f%fill )                                & 
4914                       surf_usm_v(l)%zw(nzb_wall+3,m) =                        &
4915                                   building_pars_f%pars_xy(ind_thick_4_agfl,j,i)
4916                       
4917                    IF ( building_pars_f%pars_xy(ind_thick_1_agfl,j,i) /=      &           
4918                         building_pars_f%fill )                                &
4919                       surf_usm_v(l)%zw_green(nzb_wall,m) =                    &
4920                                   building_pars_f%pars_xy(ind_thick_1_agfl,j,i)
4921                       
4922                    IF ( building_pars_f%pars_xy(ind_thick_2_agfl,j,i) /=      &         
4923                         building_pars_f%fill )                                &
4924                       surf_usm_v(l)%zw_green(nzb_wall+1,m) =                  &
4925                                   building_pars_f%pars_xy(ind_thick_2_agfl,j,i)
4926                       
4927                    IF ( building_pars_f%pars_xy(ind_thick_3_agfl,j,i) /=      &         
4928                         building_pars_f%fill )                                & 
4929                       surf_usm_v(l)%zw_green(nzb_wall+2,m) =                  &
4930                                   building_pars_f%pars_xy(ind_thick_3_agfl,j,i)
4931                       
4932                    IF ( building_pars_f%pars_xy(ind_thick_4_agfl,j,i) /=      &         
4933                         building_pars_f%fill )                                &
4934                       surf_usm_v(l)%zw_green(nzb_wall+3,m) =                  &
4935                                   building_pars_f%pars_xy(ind_thick_4_agfl,j,i)
4936                   
4937                    IF ( building_pars_f%pars_xy(ind_c_surface,j,i) /=         &       
4938                         building_pars_f%fill )                                & 
4939                       surf_usm_v(l)%c_surface(m) =                            &
4940                                     building_pars_f%pars_xy(ind_c_surface,j,i)
4941                       
4942                    IF ( building_pars_f%pars_xy(ind_lambda_surf,j,i) /=       &       
4943                         building_pars_f%fill )                                &
4944                       surf_usm_v(l)%lambda_surf(m) =                          &
4945                                    building_pars_f%pars_xy(ind_lambda_surf,j,i)
4946                   
4947              ENDDO
4948           ENDDO
4949        ENDIF 
4950!       
4951!--     Read the surface_types array.
4952!--     Please note, here also initialization of surface attributes is done as
4953!--     long as _urbsurf and _surfpar files are available. Values from above
4954!--     will be overwritten. This might be removed later, but is still in the
4955!--     code to enable compatibility with older model version.
4956        CALL usm_read_urban_surface_types()
4957       
4958        CALL usm_init_material_model()
4959!       
4960!--     init anthropogenic sources of heat
4961        IF ( usm_anthropogenic_heat )  THEN
4962!
4963!--         init anthropogenic sources of heat (from transportation for now)
4964            CALL usm_read_anthropogenic_heat()
4965        ENDIF
4966
4967!
4968!--    Check for consistent initialization.
4969!--    Check if roughness length for momentum, or heat, exceed surface-layer
4970!--    height and decrease local roughness length where necessary.
4971       DO  m = 1, surf_usm_h%ns
4972          IF ( surf_usm_h%z0(m) >= surf_usm_h%z_mo(m) )  THEN
4973         
4974             surf_usm_h%z0(m) = 0.9_wp * surf_usm_h%z_mo(m)
4975             
4976             WRITE( message_string, * ) 'z0 exceeds surface-layer height ' //  &
4977                            'at horizontal urban surface and is ' //           &
4978                            'decreased appropriately at grid point (i,j) = ',  &
4979                            surf_usm_h%i(m), surf_usm_h%j(m)
4980             CALL message( 'urban_surface_model_mod', 'PA0503',                &
4981                            0, 0, 0, 6, 0 )
4982          ENDIF
4983          IF ( surf_usm_h%z0h(m) >= surf_usm_h%z_mo(m) )  THEN
4984         
4985             surf_usm_h%z0h(m) = 0.9_wp * surf_usm_h%z_mo(m)
4986             surf_usm_h%z0q(m) = 0.9_wp * surf_usm_h%z_mo(m)
4987             
4988             WRITE( message_string, * ) 'z0h exceeds surface-layer height ' // &
4989                            'at horizontal urban surface and is ' //           &
4990                            'decreased appropriately at grid point (i,j) = ',  &
4991                            surf_usm_h%i(m), surf_usm_h%j(m)
4992             CALL message( 'urban_surface_model_mod', 'PA0507',                &
4993                            0, 0, 0, 6, 0 )
4994          ENDIF         
4995       ENDDO
4996       
4997       DO  l = 0, 3
4998          DO  m = 1, surf_usm_v(l)%ns
4999             IF ( surf_usm_v(l)%z0(m) >= surf_usm_v(l)%z_mo(m) )  THEN
5000         
5001                surf_usm_v(l)%z0(m) = 0.9_wp * surf_usm_v(l)%z_mo(m)
5002             
5003                WRITE( message_string, * ) 'z0 exceeds surface-layer height '// &
5004                            'at vertical urban surface and is ' //              &
5005                            'decreased appropriately at grid point (i,j) = ',   &
5006                            surf_usm_v(l)%i(m)+surf_usm_v(l)%ioff,              &
5007                            surf_usm_v(l)%j(m)+surf_usm_v(l)%joff
5008                CALL message( 'urban_surface_model_mod', 'PA0503',              &
5009                            0, 0, 0, 6, 0 )
5010             ENDIF
5011             IF ( surf_usm_v(l)%z0h(m) >= surf_usm_v(l)%z_mo(m) )  THEN
5012         
5013                surf_usm_v(l)%z0h(m) = 0.9_wp * surf_usm_v(l)%z_mo(m)
5014                surf_usm_v(l)%z0q(m) = 0.9_wp * surf_usm_v(l)%z_mo(m)
5015             
5016                WRITE( message_string, * ) 'z0h exceeds surface-layer height '// &
5017                            'at vertical urban surface and is ' //               &
5018                            'decreased appropriately at grid point (i,j) = ',    &
5019                            surf_usm_v(l)%i(m)+surf_usm_v(l)%ioff,               &
5020                            surf_usm_v(l)%j(m)+surf_usm_v(l)%joff
5021                CALL message( 'urban_surface_model_mod', 'PA0507',               &
5022                            0, 0, 0, 6, 0 )
5023             ENDIF
5024          ENDDO
5025       ENDDO
5026
5027!
5028!--     Intitialization of the surface and wall/ground/roof temperature
5029!
5030!--     Initialization for restart runs
5031        IF ( TRIM( initializing_actions ) /= 'read_restart_data'  .AND.        &
5032             TRIM( initializing_actions ) /= 'cyclic_fill' )  THEN
5033
5034!
5035!--         At horizontal surfaces. Please note, t_surf_wall_h is defined on a
5036!--         different data type, but with the same dimension.
5037            DO  m = 1, surf_usm_h%ns
5038               i = surf_usm_h%i(m)           
5039               j = surf_usm_h%j(m)
5040               k = surf_usm_h%k(m)
5041
5042               t_surf_wall_h(m) = pt(k,j,i) * exner(k)
5043               t_surf_window_h(m) = pt(k,j,i) * exner(k)
5044               t_surf_green_h(m) = pt(k,j,i) * exner(k)
5045               surf_usm_h%pt_surface(m) = pt(k,j,i) * exner(k)
5046            ENDDO
5047!
5048!--         At vertical surfaces.
5049            DO  l = 0, 3
5050               DO  m = 1, surf_usm_v(l)%ns
5051                  i = surf_usm_v(l)%i(m)           
5052                  j = surf_usm_v(l)%j(m)
5053                  k = surf_usm_v(l)%k(m)
5054
5055                  t_surf_wall_v(l)%t(m) = pt(k,j,i) * exner(k)
5056                  t_surf_window_v(l)%t(m) = pt(k,j,i) * exner(k)
5057                  t_surf_green_v(l)%t(m) = pt(k,j,i) * exner(k)
5058                  surf_usm_v(l)%pt_surface(m) = pt(k,j,i) * exner(k)
5059               ENDDO
5060            ENDDO
5061
5062!
5063!--         For the sake of correct initialization, set also q_surface.
5064!--         Note, at urban surfaces q_surface is initialized with 0.
5065            IF ( humidity )  THEN
5066               DO  m = 1, surf_usm_h%ns
5067                  surf_usm_h%q_surface(m) = 0.0_wp
5068               ENDDO
5069               DO  l = 0, 3
5070                  DO  m = 1, surf_usm_v(l)%ns
5071                     surf_usm_v(l)%q_surface(m) = 0.0_wp
5072                  ENDDO
5073               ENDDO
5074            ENDIF
5075!
5076!--         initial values for t_wall
5077!--         outer value is set to surface temperature
5078!--         inner value is set to wall_inner_temperature
5079!--         and profile is logaritmic (linear in nz).
5080!--         Horizontal surfaces
5081            DO  m = 1, surf_usm_h%ns
5082!
5083!--            Roof
5084               IF ( surf_usm_h%isroof_surf(m) )  THEN
5085                   tin = roof_inner_temperature
5086                   twin = window_inner_temperature
5087!
5088!--            Normal land surface
5089               ELSE
5090                   tin = soil_inner_temperature
5091                   twin = window_inner_temperature
5092               ENDIF
5093
5094               DO k = nzb_wall, nzt_wall+1
5095                   c = REAL( k - nzb_wall, wp ) /                              &
5096                       REAL( nzt_wall + 1 - nzb_wall , wp )
5097
5098                   t_wall_h(k,m) = ( 1.0_wp - c ) * t_surf_wall_h(m) + c * tin
5099                   t_window_h(k,m) = ( 1.0_wp - c ) * t_surf_window_h(m) + c * twin
5100                   t_green_h(k,m) = t_surf_wall_h(m)
5101                   swc_h(k,m) = 0.5_wp
5102                   swc_sat_h(k,m) = 0.95_wp
5103                   swc_res_h(k,m) = 0.05_wp
5104                   rootfr_h(k,m) = 0.1_wp
5105                   wilt_h(k,m) = 0.1_wp
5106                   fc_h(k,m) = 0.9_wp
5107               ENDDO
5108            ENDDO
5109!
5110!--         Vertical surfaces
5111            DO  l = 0, 3
5112               DO  m = 1, surf_usm_v(l)%ns
5113!
5114!--               Inner wall
5115                  tin = wall_inner_temperature
5116                  twin = window_inner_temperature
5117
5118                  DO k = nzb_wall, nzt_wall+1
5119                     c = REAL( k - nzb_wall, wp ) /                            &
5120                         REAL( nzt_wall + 1 - nzb_wall , wp )
5121                     t_wall_v(l)%t(k,m) = ( 1.0_wp - c ) * t_surf_wall_v(l)%t(m) + c * tin
5122                     t_window_v(l)%t(k,m) = ( 1.0_wp - c ) * t_surf_window_v(l)%t(m) + c * twin
5123                     t_green_v(l)%t(k,m) = t_surf_wall_v(l)%t(m)
5124                     swc_v(l)%t(k,m) = 0.5_wp
5125                  ENDDO
5126               ENDDO
5127            ENDDO
5128        ENDIF
5129
5130!
5131!--     If specified, replace constant wall temperatures with fully 3D values from file
5132        IF ( read_wall_temp_3d )  CALL usm_read_wall_temperature()
5133
5134!--
5135!--     Possibly DO user-defined actions (e.g. define heterogeneous wall surface)
5136        CALL user_init_urban_surface
5137
5138!
5139!--     initialize prognostic values for the first timestep
5140        t_surf_wall_h_p = t_surf_wall_h
5141        t_surf_wall_v_p = t_surf_wall_v
5142        t_surf_window_h_p = t_surf_window_h
5143        t_surf_window_v_p = t_surf_window_v
5144        t_surf_green_h_p = t_surf_green_h
5145        t_surf_green_v_p = t_surf_green_v
5146
5147        t_wall_h_p = t_wall_h
5148        t_wall_v_p = t_wall_v
5149        t_window_h_p = t_window_h
5150        t_window_v_p = t_window_v
5151        t_green_h_p = t_green_h
5152        t_green_v_p = t_green_v
5153
5154!
5155!--     Adjust radiative fluxes for urban surface at model start
5156        !CALL radiation_interaction
5157!--     TODO: interaction should be called once before first output,
5158!--     that is not yet possible.
5159       
5160        m_liq_usm_h_p     = m_liq_usm_h
5161        m_liq_usm_v_p     = m_liq_usm_v
5162!
5163!--    Set initial values for prognostic quantities
5164!--    Horizontal surfaces
5165       tm_liq_usm_h_m%var_usm_1d  = 0.0_wp
5166       surf_usm_h%c_liq = 0.0_wp
5167
5168       surf_usm_h%qsws_liq  = 0.0_wp
5169       surf_usm_h%qsws_veg  = 0.0_wp
5170
5171!
5172!--    Do the same for vertical surfaces
5173       DO  l = 0, 3
5174          tm_liq_usm_v_m(l)%var_usm_1d  = 0.0_wp
5175          surf_usm_v(l)%c_liq = 0.0_wp
5176
5177          surf_usm_v(l)%qsws_liq  = 0.0_wp
5178          surf_usm_v(l)%qsws_veg  = 0.0_wp
5179       ENDDO
5180
5181!
5182!--    Set initial values for prognostic soil quantities
5183       IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
5184          m_liq_usm_h%var_usm_1d  = 0.0_wp
5185
5186          DO  l = 0, 3
5187             m_liq_usm_v(l)%var_usm_1d  = 0.0_wp
5188          ENDDO
5189       ENDIF
5190
5191        CALL cpu_log( log_point_s(78), 'usm_init', 'stop' )
5192
5193        CALL location_message( 'finished', .TRUE. )
5194
5195    END SUBROUTINE usm_init
5196
5197
5198!------------------------------------------------------------------------------!
5199! Description:
5200! ------------
5201!
5202!> Wall model as part of the urban surface model. The model predicts vertical
5203!> and horizontal wall / roof temperatures and window layer temperatures.
5204!> No window layer temperature calculactions during spinup to increase
5205!> possible timestep.
5206!------------------------------------------------------------------------------!
5207    SUBROUTINE usm_material_heat_model( spinup )
5208
5209
5210        IMPLICIT NONE
5211
5212        INTEGER(iwp) ::  i,j,k,l,kw, m                      !< running indices
5213
5214        REAL(wp), DIMENSION(nzb_wall:nzt_wall) :: wtend, wintend  !< tendency
5215        REAL(wp)     :: win_absorp  !< absorption coefficient from transmissivity
5216        REAL(wp), DIMENSION(nzb_wall:nzt_wall) :: wall_mod
5217
5218        LOGICAL      :: spinup  !< if true, no calculation of window temperatures
5219
5220        !$OMP PARALLEL PRIVATE (m, i, j, k, kw, wtend, wintend, win_absorp, wall_mod)
5221        wall_mod=1.0_wp
5222        IF (usm_wall_mod .AND. spinup) THEN
5223           DO  kw=nzb_wall,nzb_wall+1
5224               wall_mod(kw)=0.1_wp
5225           ENDDO
5226        ENDIF
5227
5228!
5229!--     For horizontal surfaces                                   
5230        !$OMP DO SCHEDULE (STATIC)
5231        DO  m = 1, surf_usm_h%ns
5232!
5233!--        Obtain indices
5234           i = surf_usm_h%i(m)           
5235           j = surf_usm_h%j(m)
5236           k = surf_usm_h%k(m)
5237!
5238!--        prognostic equation for ground/roof temperature t_wall_h
5239           wtend(:) = 0.0_wp
5240           wtend(nzb_wall) = (1.0_wp / surf_usm_h%rho_c_wall(nzb_wall,m)) *        &
5241                                       ( surf_usm_h%lambda_h(nzb_wall,m) * wall_mod(nzb_wall) *        &
5242                                         ( t_wall_h(nzb_wall+1,m)                  &
5243                                         - t_wall_h(nzb_wall,m) ) *                &
5244                                         surf_usm_h%ddz_wall(nzb_wall+1,m)         &
5245                                       + surf_usm_h%frac(ind_veg_wall,m)           &
5246                                         / (surf_usm_h%frac(ind_veg_wall,m)        &
5247                                           + surf_usm_h%frac(ind_pav_green,m) )    &
5248                                         * surf_usm_h%wghf_eb(m)                   &
5249                                       - surf_usm_h%frac(ind_pav_green,m)          &
5250                                          / (surf_usm_h%frac(ind_veg_wall,m)       &
5251                                            + surf_usm_h%frac(ind_pav_green,m) )   &
5252                                         * ( surf_usm_h%lambda_h_green(nzt_wall,m)* wall_mod(nzt_wall) &
5253                                           * surf_usm_h%ddz_green(nzt_wall,m)      &
5254                                           + surf_usm_h%lambda_h(nzb_wall,m) * wall_mod(nzb_wall)      &
5255                                           * surf_usm_h%ddz_wall(nzb_wall,m) )     &
5256                                         / ( surf_usm_h%ddz_green(nzt_wall,m)      &
5257                                           + surf_usm_h%ddz_wall(nzb_wall,m) )     &
5258                                         * ( t_wall_h(nzb_wall,m)                  &
5259                                           - t_green_h(nzt_wall,m) ) ) *           &
5260                                       surf_usm_h%ddz_wall_stag(nzb_wall,m)
5261!
5262!-- if indoor model ist used inner wall layer is calculated by using iwghf (indoor wall ground heat flux)
5263           IF ( indoor_model ) THEN
5264              DO  kw = nzb_wall+1, nzt_wall-1
5265                  wtend(kw) = (1.0_wp / surf_usm_h%rho_c_wall(kw,m))              &
5266                                 * (   surf_usm_h%lambda_h(kw,m) * wall_mod(kw)   &
5267                                    * ( t_wall_h(kw+1,m) - t_wall_h(kw,m) )       &
5268                                    * surf_usm_h%ddz_wall(kw+1,m)                 &
5269                                 - surf_usm_h%lambda_h(kw-1,m) * wall_mod(kw-1)   &
5270                                    * ( t_wall_h(kw,m) - t_wall_h(kw-1,m) )       &
5271                                    * surf_usm_h%ddz_wall(kw,m)                   &
5272                                   ) * surf_usm_h%ddz_wall_stag(kw,m)
5273              ENDDO
5274              wtend(nzt_wall) = (1.0_wp / surf_usm_h%rho_c_wall(nzt_wall,m)) *    &
5275                                         ( -surf_usm_h%lambda_h(nzt_wall-1,m) * wall_mod(nzt_wall-1) * &
5276                                           ( t_wall_h(nzt_wall,m)                 &
5277                                           - t_wall_h(nzt_wall-1,m) ) *           &
5278                                           surf_usm_h%ddz_wall(nzt_wall,m)        &
5279                                         + surf_usm_h%iwghf_eb(m) ) *             &
5280                                           surf_usm_h%ddz_wall_stag(nzt_wall,m)
5281           ELSE
5282              DO  kw = nzb_wall+1, nzt_wall
5283                  wtend(kw) = (1.0_wp / surf_usm_h%rho_c_wall(kw,m))              &
5284                                 * (   surf_usm_h%lambda_h(kw,m)  * wall_mod(kw)  &
5285                                    * ( t_wall_h(kw+1,m) - t_wall_h(kw,m) )       &
5286                                    * surf_usm_h%ddz_wall(kw+1,m)                 &
5287                                 - surf_usm_h%lambda_h(kw-1,m) * wall_mod(kw-1)   &
5288                                    * ( t_wall_h(kw,m) - t_wall_h(kw-1,m) )       &
5289                                    * surf_usm_h%ddz_wall(kw,m)                   &
5290                                   ) * surf_usm_h%ddz_wall_stag(kw,m)
5291              ENDDO
5292           ENDIF
5293
5294           t_wall_h_p(nzb_wall:nzt_wall,m) = t_wall_h(nzb_wall:nzt_wall,m)     &
5295                                 + dt_3d * ( tsc(2)                            &
5296                                 * wtend(nzb_wall:nzt_wall) + tsc(3)           &
5297                                 * surf_usm_h%tt_wall_m(nzb_wall:nzt_wall,m) )   
5298
5299!
5300!-- during spinup the tempeature inside window layers is not calculated to make larger timesteps possible
5301           IF ( .NOT. spinup) THEN
5302              win_absorp = -log(surf_usm_h%transmissivity(m)) / surf_usm_h%zw_window(nzt_wall,m)
5303!
5304!--           prognostic equation for ground/roof window temperature t_window_h
5305!--           takes absorption of shortwave radiation into account
5306              wintend(:) = 0.0_wp
5307              wintend(nzb_wall) = (1.0_wp / surf_usm_h%rho_c_window(nzb_wall,m)) *   &
5308                                         ( surf_usm_h%lambda_h_window(nzb_wall,m) *  &
5309                                           ( t_window_h(nzb_wall+1,m)                &
5310                                           - t_window_h(nzb_wall,m) ) *              &
5311                                           surf_usm_h%ddz_window(nzb_wall+1,m)       &
5312                                         + surf_usm_h%wghf_eb_window(m)              &
5313                                         + surf_usm_h%rad_sw_in(m)                   &
5314                                           * (1.0_wp - exp(-win_absorp               &
5315                                           * surf_usm_h%zw_window(nzb_wall,m) ) )    &
5316                                         ) * surf_usm_h%ddz_window_stag(nzb_wall,m)
5317   
5318              IF ( indoor_model ) THEN
5319                 DO  kw = nzb_wall+1, nzt_wall-1
5320                     wintend(kw) = (1.0_wp / surf_usm_h%rho_c_window(kw,m))          &
5321                                    * (   surf_usm_h%lambda_h_window(kw,m)           &
5322                                       * ( t_window_h(kw+1,m) - t_window_h(kw,m) )   &
5323                                       * surf_usm_h%ddz_window(kw+1,m)               &
5324                                    - surf_usm_h%lambda_h_window(kw-1,m)             &
5325                                       * ( t_window_h(kw,m) - t_window_h(kw-1,m) )   &
5326                                       * surf_usm_h%ddz_window(kw,m)                 &
5327                                    + surf_usm_h%rad_sw_in(m)                        &
5328                                       * (exp(-win_absorp                            &
5329                                           * surf_usm_h%zw_window(kw-1,m) )          &
5330                                           - exp(-win_absorp                         &
5331                                           * surf_usm_h%zw_window(kw,m) ) )          &
5332                                      ) * surf_usm_h%ddz_window_stag(kw,m)
5333   
5334                 ENDDO
5335                 wintend(nzt_wall) = (1.0_wp / surf_usm_h%rho_c_window(nzt_wall,m)) *       &
5336                                            ( -surf_usm_h%lambda_h_window(nzt_wall-1,m) *   &
5337                                              ( t_window_h(nzt_wall,m)                      &
5338                                              - t_window_h(nzt_wall-1,m) ) *                &
5339                                              surf_usm_h%ddz_window(nzt_wall,m)             &
5340                                            + surf_usm_h%iwghf_eb_window(m)                 &
5341                                            + surf_usm_h%rad_sw_in(m)                       &
5342                                              * (exp(-win_absorp                            &
5343                                              * surf_usm_h%zw_window(nzt_wall-1,m) )        &
5344                                              - exp(-win_absorp                             &
5345                                              * surf_usm_h%zw_window(nzt_wall,m) ) )        &
5346                                            ) * surf_usm_h%ddz_window_stag(nzt_wall,m)
5347              ELSE
5348                 DO  kw = nzb_wall+1, nzt_wall
5349                     wintend(kw) = (1.0_wp / surf_usm_h%rho_c_window(kw,m))          &
5350                                    * (   surf_usm_h%lambda_h_window(kw,m)           &
5351                                       * ( t_window_h(kw+1,m) - t_window_h(kw,m) )   &
5352                                       * surf_usm_h%ddz_window(kw+1,m)               &
5353                                    - surf_usm_h%lambda_h_window(kw-1,m)             &
5354                                       * ( t_window_h(kw,m) - t_window_h(kw-1,m) )   &
5355                                       * surf_usm_h%ddz_window(kw,m)                 &
5356                                    + surf_usm_h%rad_sw_in(m)                        &
5357                                       * (exp(-win_absorp                            &
5358                                           * surf_usm_h%zw_window(kw-1,m) )          &
5359                                           - exp(-win_absorp                         &
5360                                           * surf_usm_h%zw_window(kw,m) ) )          &
5361                                      ) * surf_usm_h%ddz_window_stag(kw,m)
5362   
5363                 ENDDO
5364              ENDIF
5365
5366              t_window_h_p(nzb_wall:nzt_wall,m) = t_window_h(nzb_wall:nzt_wall,m) &
5367                                 + dt_3d * ( tsc(2)                               &
5368                                 * wintend(nzb_wall:nzt_wall) + tsc(3)            &
5369                                 * surf_usm_h%tt_window_m(nzb_wall:nzt_wall,m) )   
5370
5371           ENDIF
5372
5373!
5374!--        calculate t_wall tendencies for the next Runge-Kutta step
5375           IF ( timestep_scheme(1:5) == 'runge' )  THEN
5376               IF ( intermediate_timestep_count == 1 )  THEN
5377                  DO  kw = nzb_wall, nzt_wall
5378                     surf_usm_h%tt_wall_m(kw,m) = wtend(kw)
5379                  ENDDO
5380               ELSEIF ( intermediate_timestep_count <                          &
5381                        intermediate_timestep_count_max )  THEN
5382                   DO  kw = nzb_wall, nzt_wall
5383                      surf_usm_h%tt_wall_m(kw,m) = -9.5625_wp * wtend(kw) +    &
5384                                         5.3125_wp * surf_usm_h%tt_wall_m(kw,m)
5385                   ENDDO
5386               ENDIF
5387           ENDIF
5388
5389           IF (.NOT. spinup) THEN
5390!
5391!--           calculate t_window tendencies for the next Runge-Kutta step
5392              IF ( timestep_scheme(1:5) == 'runge' )  THEN
5393                  IF ( intermediate_timestep_count == 1 )  THEN
5394                     DO  kw = nzb_wall, nzt_wall
5395                        surf_usm_h%tt_window_m(kw,m) = wintend(kw)
5396                     ENDDO
5397                  ELSEIF ( intermediate_timestep_count <                            &
5398                           intermediate_timestep_count_max )  THEN
5399                      DO  kw = nzb_wall, nzt_wall
5400                         surf_usm_h%tt_window_m(kw,m) = -9.5625_wp * wintend(kw) +  &
5401                                            5.3125_wp * surf_usm_h%tt_window_m(kw,m)
5402                      ENDDO
5403                  ENDIF
5404              ENDIF
5405           ENDIF
5406
5407        ENDDO
5408
5409!
5410!--     For vertical surfaces     
5411        !$OMP DO SCHEDULE (STATIC)
5412        DO  l = 0, 3                             
5413           DO  m = 1, surf_usm_v(l)%ns
5414!
5415!--           Obtain indices
5416              i = surf_usm_v(l)%i(m)           
5417              j = surf_usm_v(l)%j(m)
5418              k = surf_usm_v(l)%k(m)
5419!
5420!--           prognostic equation for wall temperature t_wall_v
5421              wtend(:) = 0.0_wp
5422
5423              wtend(nzb_wall) = (1.0_wp / surf_usm_v(l)%rho_c_wall(nzb_wall,m)) *    &
5424                                      ( surf_usm_v(l)%lambda_h(nzb_wall,m) * wall_mod(nzb_wall)  *      &
5425                                        ( t_wall_v(l)%t(nzb_wall+1,m)                &
5426                                        - t_wall_v(l)%t(nzb_wall,m) ) *              &
5427                                        surf_usm_v(l)%ddz_wall(nzb_wall+1,m)         &
5428                                      + surf_usm_v(l)%frac(ind_veg_wall,m)           &
5429                                        / (surf_usm_v(l)%frac(ind_veg_wall,m)        &
5430                                          + surf_usm_v(l)%frac(ind_pav_green,m) )    &
5431                                        * surf_usm_v(l)%wghf_eb(m)                   &
5432                                      - surf_usm_v(l)%frac(ind_pav_green,m)          &
5433                                        / (surf_usm_v(l)%frac(ind_veg_wall,m)        &
5434                                          + surf_usm_v(l)%frac(ind_pav_green,m) )    &
5435                                        * ( surf_usm_v(l)%lambda_h_green(nzt_wall,m)* wall_mod(nzt_wall) &
5436                                          * surf_usm_v(l)%ddz_green(nzt_wall,m)      &
5437                                          + surf_usm_v(l)%lambda_h(nzb_wall,m)* wall_mod(nzb_wall)       &
5438                                          * surf_usm_v(l)%ddz_wall(nzb_wall,m) )     &
5439                                        / ( surf_usm_v(l)%ddz_green(nzt_wall,m)      &
5440                                          + surf_usm_v(l)%ddz_wall(nzb_wall,m) )     &
5441                                        * ( t_wall_v(l)%t(nzb_wall,m)                &
5442                                          - t_green_v(l)%t(nzt_wall,m) ) ) *         &
5443                                        surf_usm_v(l)%ddz_wall_stag(nzb_wall,m)
5444
5445              IF ( indoor_model ) THEN
5446                 DO  kw = nzb_wall+1, nzt_wall-1
5447                     wtend(kw) = (1.0_wp / surf_usm_v(l)%rho_c_wall(kw,m))        &
5448                              * (   surf_usm_v(l)%lambda_h(kw,m)  * wall_mod(kw)  &
5449                                 * ( t_wall_v(l)%t(kw+1,m) - t_wall_v(l)%t(kw,m) )&
5450                                 * surf_usm_v(l)%ddz_wall(kw+1,m)                 &
5451                              - surf_usm_v(l)%lambda_h(kw-1,m)  * wall_mod(kw-1)  &
5452                                 * ( t_wall_v(l)%t(kw,m) - t_wall_v(l)%t(kw-1,m) )&
5453                                 * surf_usm_v(l)%ddz_wall(kw,m)                   &
5454                                 ) * surf_usm_v(l)%ddz_wall_stag(kw,m)
5455                 ENDDO
5456                 wtend(nzt_wall) = (1.0_wp / surf_usm_v(l)%rho_c_wall(nzt_wall,m)) * &
5457                                         ( -surf_usm_v(l)%lambda_h(nzt_wall-1,m) * wall_mod(nzt_wall-1)*    &
5458                                           ( t_wall_v(l)%t(nzt_wall,m)               &
5459                                           - t_wall_v(l)%t(nzt_wall-1,m) ) *         &
5460                                           surf_usm_v(l)%ddz_wall(nzt_wall,m)        &
5461                                         + surf_usm_v(l)%iwghf_eb(m) ) *             &
5462                                           surf_usm_v(l)%ddz_wall_stag(nzt_wall,m)
5463              ELSE
5464                 DO  kw = nzb_wall+1, nzt_wall
5465                     wtend(kw) = (1.0_wp / surf_usm_v(l)%rho_c_wall(kw,m))        &
5466                              * (   surf_usm_v(l)%lambda_h(kw,m) * wall_mod(kw)   &
5467                                 * ( t_wall_v(l)%t(kw+1,m) - t_wall_v(l)%t(kw,m) )&
5468                                 * surf_usm_v(l)%ddz_wall(kw+1,m)                 &
5469                              - surf_usm_v(l)%lambda_h(kw-1,m)  * wall_mod(kw-1)  &
5470                                 * ( t_wall_v(l)%t(kw,m) - t_wall_v(l)%t(kw-1,m) )&
5471                                 * surf_usm_v(l)%ddz_wall(kw,m)                   &
5472                                 ) * surf_usm_v(l)%ddz_wall_stag(kw,m)
5473                 ENDDO
5474              ENDIF
5475
5476              t_wall_v_p(l)%t(nzb_wall:nzt_wall,m) =                           &
5477                                   t_wall_v(l)%t(nzb_wall:nzt_wall,m)          &
5478                                 + dt_3d * ( tsc(2)                            &
5479                                 * wtend(nzb_wall:nzt_wall) + tsc(3)           &
5480                                 * surf_usm_v(l)%tt_wall_m(nzb_wall:nzt_wall,m) )   
5481
5482              IF (.NOT. spinup) THEN
5483                 win_absorp = -log(surf_usm_v(l)%transmissivity(m)) / surf_usm_v(l)%zw_window(nzt_wall,m)
5484!
5485!--              prognostic equation for window temperature t_window_v
5486                 wintend(:) = 0.0_wp
5487                 wintend(nzb_wall) = (1.0_wp / surf_usm_v(l)%rho_c_window(nzb_wall,m)) * &
5488                                         ( surf_usm_v(l)%lambda_h_window(nzb_wall,m) *   &
5489                                           ( t_window_v(l)%t(nzb_wall+1,m)               &
5490                                           - t_window_v(l)%t(nzb_wall,m) ) *             &
5491                                           surf_usm_v(l)%ddz_window(nzb_wall+1,m)        &
5492                                         + surf_usm_v(l)%wghf_eb_window(m)               &
5493                                         + surf_usm_v(l)%rad_sw_in(m)                    &
5494                                           * (1.0_wp - exp(-win_absorp                   &
5495                                           * surf_usm_v(l)%zw_window(nzb_wall,m) ) )     &
5496                                         ) * surf_usm_v(l)%ddz_window_stag(nzb_wall,m)
5497   
5498                 IF ( indoor_model ) THEN
5499                    DO  kw = nzb_wall+1, nzt_wall -1
5500                        wintend(kw) = (1.0_wp / surf_usm_v(l)%rho_c_window(kw,m))         &
5501                                 * (   surf_usm_v(l)%lambda_h_window(kw,m)                &
5502                                    * ( t_window_v(l)%t(kw+1,m) - t_window_v(l)%t(kw,m) ) &
5503                                    * surf_usm_v(l)%ddz_window(kw+1,m)                    &
5504                                 - surf_usm_v(l)%lambda_h_window(kw-1,m)                  &
5505                                    * ( t_window_v(l)%t(kw,m) - t_window_v(l)%t(kw-1,m) ) &
5506                                    * surf_usm_v(l)%ddz_window(kw,m)                      &
5507                                 + surf_usm_v(l)%rad_sw_in(m)                             &
5508                                    * (exp(-win_absorp                                    &
5509                                       * surf_usm_v(l)%zw_window(kw-1,m)       )          &
5510                                           - exp(-win_absorp                              &
5511                                           * surf_usm_v(l)%zw_window(kw,m) ) )            &
5512                                    ) * surf_usm_v(l)%ddz_window_stag(kw,m)
5513                     ENDDO
5514                     wintend(nzt_wall) = (1.0_wp / surf_usm_v(l)%rho_c_window(nzt_wall,m)) *  &
5515                                             ( -surf_usm_v(l)%lambda_h_window(nzt_wall-1,m) * &
5516                                               ( t_window_v(l)%t(nzt_wall,m)                  &
5517                                               - t_window_v(l)%t(nzt_wall-1,m) ) *            &
5518                                               surf_usm_v(l)%ddz_window(nzt_wall,m)           &
5519                                             + surf_usm_v(l)%iwghf_eb_window(m)               &
5520                                             + surf_usm_v(l)%rad_sw_in(m)                     &
5521                                               * (exp(-win_absorp                             &
5522                                             * surf_usm_v(l)%zw_window(nzt_wall-1,m) )        &
5523                                           - exp(-win_absorp                                  &
5524                                               * surf_usm_v(l)%zw_window(nzt_wall,m) ) )      &
5525                                             ) * surf_usm_v(l)%ddz_window_stag(nzt_wall,m)
5526                 ELSE
5527                    DO  kw = nzb_wall+1, nzt_wall
5528                        wintend(kw) = (1.0_wp / surf_usm_v(l)%rho_c_window(kw,m))         &
5529                                 * (   surf_usm_v(l)%lambda_h_window(kw,m)                &
5530                                    * ( t_window_v(l)%t(kw+1,m) - t_window_v(l)%t(kw,m) ) &
5531                                    * surf_usm_v(l)%ddz_window(kw+1,m)                    &
5532                                 - surf_usm_v(l)%lambda_h_window(kw-1,m)                  &
5533                                    * ( t_window_v(l)%t(kw,m) - t_window_v(l)%t(kw-1,m) ) &
5534                                    * surf_usm_v(l)%ddz_window(kw,m)                      &
5535                                 + surf_usm_v(l)%rad_sw_in(m)                             &
5536                                    * (exp(-win_absorp                                    &
5537                                       * surf_usm_v(l)%zw_window(kw-1,m)       )          &
5538                                           - exp(-win_absorp                              &
5539                                           * surf_usm_v(l)%zw_window(kw,m) ) )            &
5540                                    ) * surf_usm_v(l)%ddz_window_stag(kw,m)
5541                    ENDDO
5542                 ENDIF
5543   
5544                 t_window_v_p(l)%t(nzb_wall:nzt_wall,m) =                           &
5545                                      t_window_v(l)%t(nzb_wall:nzt_wall,m)          &
5546                                    + dt_3d * ( tsc(2)                              &
5547                                    * wintend(nzb_wall:nzt_wall) + tsc(3)           &
5548                                    * surf_usm_v(l)%tt_window_m(nzb_wall:nzt_wall,m) )   
5549              ENDIF
5550
5551!
5552!--           calculate t_wall tendencies for the next Runge-Kutta step
5553              IF ( timestep_scheme(1:5) == 'runge' )  THEN
5554                  IF ( intermediate_timestep_count == 1 )  THEN
5555                     DO  kw = nzb_wall, nzt_wall
5556                        surf_usm_v(l)%tt_wall_m(kw,m) = wtend(kw)
5557                     ENDDO
5558                  ELSEIF ( intermediate_timestep_count <                       &
5559                           intermediate_timestep_count_max )  THEN
5560                      DO  kw = nzb_wall, nzt_wall
5561                         surf_usm_v(l)%tt_wall_m(kw,m) =                       &
5562                                     - 9.5625_wp * wtend(kw) +                 &
5563                                       5.3125_wp * surf_usm_v(l)%tt_wall_m(kw,m)
5564                      ENDDO
5565                  ENDIF
5566              ENDIF
5567
5568
5569              IF (.NOT. spinup) THEN
5570!
5571!--              calculate t_window tendencies for the next Runge-Kutta step
5572                 IF ( timestep_scheme(1:5) == 'runge' )  THEN
5573                     IF ( intermediate_timestep_count == 1 )  THEN
5574                        DO  kw = nzb_wall, nzt_wall
5575                           surf_usm_v(l)%tt_window_m(kw,m) = wintend(kw)
5576                        ENDDO
5577                     ELSEIF ( intermediate_timestep_count <                       &
5578                              intermediate_timestep_count_max )  THEN
5579                         DO  kw = nzb_wall, nzt_wall
5580                            surf_usm_v(l)%tt_window_m(kw,m) =                     &
5581                                        - 9.5625_wp * wintend(kw) +               &
5582                                          5.3125_wp * surf_usm_v(l)%tt_window_m(kw,m)
5583                         ENDDO
5584                     ENDIF
5585                 ENDIF
5586              ENDIF
5587
5588           ENDDO
5589        ENDDO
5590        !$OMP END PARALLEL
5591
5592    END SUBROUTINE usm_material_heat_model
5593
5594!------------------------------------------------------------------------------!
5595! Description:
5596! ------------
5597!
5598!> Green and substrate model as part of the urban surface model. The model predicts ground
5599!> temperatures.
5600!------------------------------------------------------------------------------!
5601    SUBROUTINE usm_green_heat_model
5602
5603
5604        IMPLICIT NONE
5605
5606        INTEGER(iwp) ::  i,j,k,l,kw, m              !< running indices
5607
5608        REAL(wp)     :: ke, lambda_h_green_sat      !< heat conductivity for saturated soil
5609        REAL(wp)     :: h_vg                        !< Van Genuchten coef. h
5610        REAL(wp)     :: drho_l_lv                   !< frequently used parameter
5611
5612        REAL(wp), DIMENSION(nzb_wall:nzt_wall) :: gtend,tend  !< tendency
5613
5614        REAL(wp), DIMENSION(nzb_wall:nzt_wall) :: root_extr_green
5615
5616        REAL(wp), DIMENSION(nzb_wall:nzt_wall+1) :: lambda_green_temp  !< temp. lambda
5617        REAL(wp), DIMENSION(nzb_wall:nzt_wall+1) :: gamma_green_temp   !< temp. gamma
5618
5619        LOGICAL :: conserve_water_content = .true.
5620
5621
5622        drho_l_lv = 1.0_wp / (rho_l * l_v)
5623
5624!
5625!--     For horizontal surfaces                                   
5626        !$OMP PARALLEL PRIVATE (m, i, j, k, kw, lambda_h_green_sat, ke, lambda_green_temp, gtend,  &
5627        !$OMP&                  tend, h_vg, gamma_green_temp, m_total, root_extr_green)
5628        !$OMP DO SCHEDULE (STATIC)
5629        DO  m = 1, surf_usm_h%ns
5630
5631           IF (surf_usm_h%frac(ind_pav_green,m) > 0.0_wp) THEN
5632!
5633!--           Obtain indices
5634              i = surf_usm_h%i(m)           
5635              j = surf_usm_h%j(m)
5636              k = surf_usm_h%k(m)
5637   
5638              DO  kw = nzb_wall, nzt_wall
5639!
5640!--              Calculate volumetric heat capacity of the soil, taking
5641!--              into account water content
5642                 surf_usm_h%rho_c_total_green(kw,m) = (surf_usm_h%rho_c_green(kw,m) * (1.0_wp - swc_sat_h(kw,m)) &
5643                                      + rho_c_water * swc_h(kw,m))
5644     
5645!
5646!--              Calculate soil heat conductivity at the center of the soil
5647!--              layers
5648                 lambda_h_green_sat = lambda_h_green_sm ** (1.0_wp - swc_sat_h(kw,m)) *    &
5649                                lambda_h_water ** swc_h(kw,m)
5650     
5651                 ke = 1.0_wp + LOG10(MAX(0.1_wp,swc_h(kw,m)             &
5652                      / swc_sat_h(kw,m)))
5653     
5654                 lambda_green_temp(kw) = ke * (lambda_h_green_sat - lambda_h_green_dry) +    &
5655                                  lambda_h_green_dry
5656   
5657              ENDDO
5658              lambda_green_temp(nzt_wall+1) = lambda_green_temp(nzt_wall)
5659   
5660   
5661!
5662!--           Calculate soil heat conductivity (lambda_h) at the _stag level
5663!--           using linear interpolation. For pavement surface, the
5664!--           true pavement depth is considered
5665              DO  kw = nzb_wall, nzt_wall
5666                surf_usm_h%lambda_h_green(kw,m) = ( lambda_green_temp(kw+1) + lambda_green_temp(kw) )  &
5667                                      * 0.5_wp
5668              ENDDO
5669
5670              t_green_h(nzt_wall+1,m) = t_wall_h(nzb_wall,m)
5671!
5672!--        prognostic equation for ground/roof temperature t_green_h
5673              gtend(:) = 0.0_wp
5674              gtend(nzb_wall) = (1.0_wp / surf_usm_h%rho_c_total_green(nzb_wall,m)) *    &
5675                                         ( surf_usm_h%lambda_h_green(nzb_wall,m) * &
5676                                           ( t_green_h(nzb_wall+1,m)               &
5677                                           - t_green_h(nzb_wall,m) ) *             &
5678                                           surf_usm_h%ddz_green(nzb_wall+1,m)      &
5679                                         + surf_usm_h%wghf_eb_green(m) ) *         &
5680                                           surf_usm_h%ddz_green_stag(nzb_wall,m)
5681             
5682               DO  kw = nzb_wall+1, nzt_wall
5683                   gtend(kw) = (1.0_wp / surf_usm_h%rho_c_total_green(kw,m))       &
5684                                  * (   surf_usm_h%lambda_h_green(kw,m)            &
5685                                     * ( t_green_h(kw+1,m) - t_green_h(kw,m) )     &
5686                                     * surf_usm_h%ddz_green(kw+1,m)                &
5687                                  - surf_usm_h%lambda_h_green(kw-1,m)              &
5688                                     * ( t_green_h(kw,m) - t_green_h(kw-1,m) )     &
5689                                     * surf_usm_h%ddz_green(kw,m)                  &
5690                                    ) * surf_usm_h%ddz_green_stag(kw,m)
5691               ENDDO
5692   
5693              t_green_h_p(nzb_wall:nzt_wall,m) = t_green_h(nzb_wall:nzt_wall,m)    &
5694                                    + dt_3d * ( tsc(2)                             &
5695                                    * gtend(nzb_wall:nzt_wall) + tsc(3)            &
5696                                    * surf_usm_h%tt_green_m(nzb_wall:nzt_wall,m) )   
5697   
5698             
5699!
5700!--        calculate t_green tendencies for the next Runge-Kutta step
5701              IF ( timestep_scheme(1:5) == 'runge' )  THEN
5702                  IF ( intermediate_timestep_count == 1 )  THEN
5703                     DO  kw = nzb_wall, nzt_wall
5704                        surf_usm_h%tt_green_m(kw,m) = gtend(kw)
5705                     ENDDO
5706                  ELSEIF ( intermediate_timestep_count <                           &
5707                           intermediate_timestep_count_max )  THEN
5708                      DO  kw = nzb_wall, nzt_wall
5709                         surf_usm_h%tt_green_m(kw,m) = -9.5625_wp * gtend(kw) +    &
5710                                            5.3125_wp * surf_usm_h%tt_green_m(kw,m)
5711                      ENDDO
5712                  ENDIF
5713              ENDIF
5714
5715              DO  kw = nzb_wall, nzt_wall
5716
5717!
5718!--              Calculate soil diffusivity at the center of the soil layers
5719                 lambda_green_temp(kw) = (- b_ch * surf_usm_h%gamma_w_green_sat(kw,m) * psi_sat       &
5720                                   / swc_sat_h(kw,m) ) * ( MAX( swc_h(kw,m),    &
5721                                   wilt_h(kw,m) ) / swc_sat_h(kw,m) )**(        &
5722                                   b_ch + 2.0_wp )
5723
5724!
5725!--              Parametrization of Van Genuchten
5726                 IF ( soil_type /= 7 )  THEN
5727!
5728!--                 Calculate the hydraulic conductivity after Van Genuchten
5729!--                 (1980)
5730                    h_vg = ( ( (swc_res_h(kw,m) - swc_sat_h(kw,m)) / ( swc_res_h(kw,m) -    &
5731                               MAX( swc_h(kw,m), wilt_h(kw,m) ) ) )**(      &
5732                               surf_usm_h%n_vg_green(m) / (surf_usm_h%n_vg_green(m) - 1.0_wp ) ) - 1.0_wp  &
5733                           )**( 1.0_wp / surf_usm_h%n_vg_green(m) ) / surf_usm_h%alpha_vg_green(m)
5734
5735
5736                    gamma_green_temp(kw) = surf_usm_h%gamma_w_green_sat(kw,m) * ( ( (1.0_wp +         &
5737                                    ( surf_usm_h%alpha_vg_green(m) * h_vg )**surf_usm_h%n_vg_green(m))**(  &
5738                                    1.0_wp - 1.0_wp / surf_usm_h%n_vg_green(m) ) - (        &
5739                                    surf_usm_h%alpha_vg_green(m) * h_vg )**( surf_usm_h%n_vg_green(m)      &
5740                                    - 1.0_wp) )**2 )                         &
5741                                    / ( ( 1.0_wp + ( surf_usm_h%alpha_vg_green(m) * h_vg    &
5742                                    )**surf_usm_h%n_vg_green(m) )**( ( 1.0_wp  - 1.0_wp     &
5743                                    / surf_usm_h%n_vg_green(m) ) *( surf_usm_h%l_vg_green(m) + 2.0_wp) ) )
5744
5745!
5746!--              Parametrization of Clapp & Hornberger
5747                 ELSE
5748                    gamma_green_temp(kw) = surf_usm_h%gamma_w_green_sat(kw,m) * ( swc_h(kw,m)       &
5749                                    / swc_sat_h(kw,m) )**(2.0_wp * b_ch + 3.0_wp)
5750                 ENDIF
5751
5752              ENDDO
5753
5754!
5755!--           Prognostic equation for soil moisture content. Only performed,
5756!--           when humidity is enabled in the atmosphere
5757              IF ( humidity )  THEN
5758!
5759!--              Calculate soil diffusivity (lambda_w) at the _stag level
5760!--              using linear interpolation. To do: replace this with
5761!--              ECMWF-IFS Eq. 8.81
5762                 DO  kw = nzb_wall, nzt_wall-1
5763                   
5764                    surf_usm_h%lambda_w_green(kw,m) = ( lambda_green_temp(kw+1) + lambda_green_temp(kw) )  &
5765                                      * 0.5_wp
5766                    surf_usm_h%gamma_w_green(kw,m)  = ( gamma_green_temp(kw+1) + gamma_green_temp(kw) )    &
5767                                      * 0.5_wp
5768
5769                 ENDDO
5770
5771!
5772!--              In case of a closed bottom (= water content is conserved),
5773!--              set hydraulic conductivity to zero to that no water will be
5774!--              lost in the bottom layer.
5775                 IF ( conserve_water_content )  THEN
5776                    surf_usm_h%gamma_w_green(kw,m) = 0.0_wp
5777                 ELSE
5778                    surf_usm_h%gamma_w_green(kw,m) = gamma_green_temp(nzt_wall)
5779                 ENDIF     
5780
5781!--              The root extraction (= root_extr * qsws_veg / (rho_l     
5782!--              * l_v)) ensures the mass conservation for water. The         
5783!--              transpiration of plants equals the cumulative withdrawals by
5784!--              the roots in the soil. The scheme takes into account the
5785!--              availability of water in the soil layers as well as the root
5786!--              fraction in the respective layer. Layer with moisture below
5787!--              wilting point will not contribute, which reflects the
5788!--              preference of plants to take water from moister layers.
5789
5790!
5791!--              Calculate the root extraction (ECMWF 7.69, the sum of
5792!--              root_extr = 1). The energy balance solver guarantees a
5793!--              positive transpiration, so that there is no need for an
5794!--              additional check.
5795                 m_total = 0.0_wp
5796                 DO  kw = nzb_wall, nzt_wall
5797                     IF ( swc_h(kw,m) > wilt_h(kw,m) )  THEN
5798                        m_total = m_total + rootfr_h(kw,m) * swc_h(kw,m)
5799                     ENDIF
5800                 ENDDO 
5801
5802                 IF ( m_total > 0.0_wp )  THEN
5803                    DO  kw = nzb_wall, nzt_wall
5804                       IF ( swc_h(kw,m) > wilt_h(kw,m) )  THEN
5805                          root_extr_green(kw) = rootfr_h(kw,m) * swc_h(kw,m)      &
5806                                                          / m_total
5807                       ELSE
5808                          root_extr_green(kw) = 0.0_wp
5809                       ENDIF
5810                    ENDDO
5811                 ENDIF
5812
5813!
5814!--              Prognostic equation for soil water content m_soil.
5815                 tend(:) = 0.0_wp
5816
5817                 tend(nzb_wall) = ( surf_usm_h%lambda_w_green(nzb_wall,m) * (            &
5818                          swc_h(nzb_wall+1,m) - swc_h(nzb_wall,m) )    &
5819                          * surf_usm_h%ddz_green(nzb_wall+1,m) - surf_usm_h%gamma_w_green(nzb_wall,m) - ( &
5820                             root_extr_green(nzb_wall) * surf_usm_h%qsws_veg(m)          &
5821!                                + surf_usm_h%qsws_soil_green(m)
5822                                ) * drho_l_lv )             &
5823                               * surf_usm_h%ddz_green_stag(nzb_wall,m)
5824
5825                 DO  kw = nzb_wall+1, nzt_wall-1
5826                    tend(kw) = ( surf_usm_h%lambda_w_green(kw,m) * ( swc_h(kw+1,m)        &
5827                              - swc_h(kw,m) ) * surf_usm_h%ddz_green(kw+1,m)              &
5828                              - surf_usm_h%gamma_w_green(kw,m)                            &
5829                              - surf_usm_h%lambda_w_green(kw-1,m) * (swc_h(kw,m) -        &
5830                              swc_h(kw-1,m)) * surf_usm_h%ddz_green(kw,m)                 &
5831                              + surf_usm_h%gamma_w_green(kw-1,m) - (root_extr_green(kw)   &
5832                              * surf_usm_h%qsws_veg(m) * drho_l_lv)                       &
5833                              ) * surf_usm_h%ddz_green_stag(kw,m)
5834
5835                 ENDDO
5836                 tend(nzt_wall) = ( - surf_usm_h%gamma_w_green(nzt_wall,m)                  &
5837                                         - surf_usm_h%lambda_w_green(nzt_wall-1,m)          &
5838                                         * (swc_h(nzt_wall,m)             &
5839                                         - swc_h(nzt_wall-1,m))           &
5840                                         * surf_usm_h%ddz_green(nzt_wall,m)                 &
5841                                         + surf_usm_h%gamma_w_green(nzt_wall-1,m) - (       &
5842                                           root_extr_green(nzt_wall)               &
5843                                         * surf_usm_h%qsws_veg(m) * drho_l_lv  )   &
5844                                   ) * surf_usm_h%ddz_green_stag(nzt_wall,m)             
5845
5846                 swc_h_p(nzb_wall:nzt_wall,m) = swc_h(nzb_wall:nzt_wall,m)&
5847                                                 + dt_3d * ( tsc(2) * tend(:)   &
5848                                                 + tsc(3) * surf_usm_h%tswc_h_m(:,m) )   
5849 
5850!
5851!--              Account for dry soils (find a better solution here!)
5852                 DO  kw = nzb_wall, nzt_wall
5853                    IF ( swc_h_p(kw,m) < 0.0_wp )  swc_h_p(kw,m) = 0.0_wp
5854                 ENDDO
5855
5856!
5857!--              Calculate m_soil tendencies for the next Runge-Kutta step
5858                 IF ( timestep_scheme(1:5) == 'runge' )  THEN
5859                    IF ( intermediate_timestep_count == 1 )  THEN
5860                       DO  kw = nzb_wall, nzt_wall
5861                          surf_usm_h%tswc_h_m(kw,m) = tend(kw)
5862                       ENDDO
5863                    ELSEIF ( intermediate_timestep_count <                   &
5864                             intermediate_timestep_count_max )  THEN
5865                       DO  kw = nzb_wall, nzt_wall
5866                          surf_usm_h%tswc_h_m(kw,m) = -9.5625_wp * tend(kw) + 5.3125_wp&
5867                                   * surf_usm_h%tswc_h_m(kw,m)
5868                       ENDDO
5869                    ENDIF
5870                 ENDIF
5871              ENDIF
5872
5873           ENDIF
5874           
5875        ENDDO
5876        !$OMP END PARALLEL
5877
5878!
5879!--     For vertical surfaces     
5880        DO  l = 0, 3                             
5881           DO  m = 1, surf_usm_v(l)%ns
5882
5883              IF (surf_usm_v(l)%frac(ind_pav_green,m) > 0.0_wp) THEN
5884!
5885!-- no substrate layer for green walls / only groundbase green walls (ivy i.e.) -> green layers get same
5886!-- temperature as first wall layer
5887!-- there fore no temperature calculations for vertical green substrate layers now
5888
5889!
5890! !
5891! !--              Obtain indices
5892!                  i = surf_usm_v(l)%i(m)           
5893!                  j = surf_usm_v(l)%j(m)
5894!                  k = surf_usm_v(l)%k(m)
5895!   
5896!                  t_green_v(l)%t(nzt_wall+1,m) = t_wall_v(l)%t(nzb_wall,m)
5897! !
5898! !--              prognostic equation for green temperature t_green_v
5899!                  gtend(:) = 0.0_wp
5900!                  gtend(nzb_wall) = (1.0_wp / surf_usm_v(l)%rho_c_green(nzb_wall,m)) * &
5901!                                          ( surf_usm_v(l)%lambda_h_green(nzb_wall,m) * &
5902!                                            ( t_green_v(l)%t(nzb_wall+1,m)             &
5903!                                            - t_green_v(l)%t(nzb_wall,m) ) *           &
5904!                                            surf_usm_v(l)%ddz_green(nzb_wall+1,m)      &
5905!                                          + surf_usm_v(l)%wghf_eb(m) ) *               &
5906!                                            surf_usm_v(l)%ddz_green_stag(nzb_wall,m)
5907!               
5908!                  DO  kw = nzb_wall+1, nzt_wall
5909!                     gtend(kw) = (1.0_wp / surf_usm_v(l)%rho_c_green(kw,m))          &
5910!                               * (   surf_usm_v(l)%lambda_h_green(kw,m)              &
5911!                                 * ( t_green_v(l)%t(kw+1,m) - t_green_v(l)%t(kw,m) ) &
5912!                                 * surf_usm_v(l)%ddz_green(kw+1,m)                   &
5913!                               - surf_usm_v(l)%lambda_h(kw-1,m)                      &
5914!                                 * ( t_green_v(l)%t(kw,m) - t_green_v(l)%t(kw-1,m) ) &
5915!                                 * surf_usm_v(l)%ddz_green(kw,m) )                   &
5916!                               * surf_usm_v(l)%ddz_green_stag(kw,m)
5917!                  ENDDO
5918!   
5919!                  t_green_v_p(l)%t(nzb_wall:nzt_wall,m) =                              &
5920!                                       t_green_v(l)%t(nzb_wall:nzt_wall,m)             &
5921!                                     + dt_3d * ( tsc(2)                                &
5922!                                     * gtend(nzb_wall:nzt_wall) + tsc(3)               &
5923!                                     * surf_usm_v(l)%tt_green_m(nzb_wall:nzt_wall,m) )   
5924!   
5925! !
5926! !--              calculate t_green tendencies for the next Runge-Kutta step
5927!                  IF ( timestep_scheme(1:5) == 'runge' )  THEN
5928!                      IF ( intermediate_timestep_count == 1 )  THEN
5929!                         DO  kw = nzb_wall, nzt_wall
5930!                            surf_usm_v(l)%tt_green_m(kw,m) = gtend(kw)
5931!                         ENDDO
5932!                      ELSEIF ( intermediate_timestep_count <                           &
5933!                               intermediate_timestep_count_max )  THEN
5934!                          DO  kw = nzb_wall, nzt_wall
5935!                             surf_usm_v(l)%tt_green_m(kw,m) =                          &
5936!                                         - 9.5625_wp * gtend(kw) +                     &
5937!                                           5.3125_wp * surf_usm_v(l)%tt_green_m(kw,m)
5938!                          ENDDO
5939!                      ENDIF
5940!                  ENDIF
5941
5942                 DO  kw = nzb_wall, nzt_wall+1
5943                     t_green_v(l)%t(kw,m) = t_wall_v(l)%t(nzb_wall,m)
5944                 ENDDO
5945             
5946              ENDIF
5947
5948           ENDDO
5949        ENDDO
5950
5951    END SUBROUTINE usm_green_heat_model
5952
5953!------------------------------------------------------------------------------!
5954! Description:
5955! ------------
5956!> Parin for &usm_par for urban surface model
5957!------------------------------------------------------------------------------!
5958    SUBROUTINE usm_parin
5959
5960       IMPLICIT NONE
5961
5962       CHARACTER (LEN=80) ::  line  !< string containing current line of file PARIN
5963
5964       NAMELIST /urban_surface_par/                                            &
5965                           building_type,                                      &
5966                           land_category,                                      &
5967                           naheatlayers,                                       &
5968                           pedestrian_category,                                &
5969                           roughness_concrete,                                 &
5970                           read_wall_temp_3d,                                  &
5971                           roof_category,                                      &
5972                           urban_surface,                                      &
5973                           usm_anthropogenic_heat,                             &
5974                           usm_material_model,                                 &
5975                           wall_category,                                      &
5976                           wall_inner_temperature,                             &
5977                           roof_inner_temperature,                             &
5978                           soil_inner_temperature,                             &
5979                           window_inner_temperature,                           &
5980                           usm_wall_mod
5981
5982       NAMELIST /urban_surface_parameters/                                     &
5983                           building_type,                                      &
5984                           land_category,                                      &
5985                           naheatlayers,                                       &
5986                           pedestrian_category,                                &
5987                           roughness_concrete,                                 &
5988                           read_wall_temp_3d,                                  &
5989                           roof_category,                                      &
5990                           urban_surface,                                      &
5991                           usm_anthropogenic_heat,                             &
5992                           usm_material_model,                                 &
5993                           wall_category,                                      &
5994                           wall_inner_temperature,                             &
5995                           roof_inner_temperature,                             &
5996                           soil_inner_temperature,                             &
5997                           window_inner_temperature,                           &
5998                           usm_wall_mod
5999                           
6000 
6001!
6002!--    Try to find urban surface model package
6003       REWIND ( 11 )
6004       line = ' '
6005       DO WHILE ( INDEX( line, '&urban_surface_parameters' ) == 0 )
6006          READ ( 11, '(A)', END=12 )  line
6007       ENDDO
6008       BACKSPACE ( 11 )
6009
6010!
6011!--    Read user-defined namelist
6012       READ ( 11, urban_surface_parameters, ERR = 10 )
6013
6014!
6015!--    Set flag that indicates that the urban surface model is switched on
6016       urban_surface = .TRUE.
6017
6018       GOTO 14
6019
6020 10    BACKSPACE( 11 )
6021       READ( 11 , '(A)') line
6022       CALL parin_fail_message( 'urban_surface_parameters', line )
6023!
6024!--    Try to find old namelist
6025 12    REWIND ( 11 )
6026       line = ' '
6027       DO WHILE ( INDEX( line, '&urban_surface_par' ) == 0 )
6028          READ ( 11, '(A)', END=14 )  line
6029       ENDDO
6030       BACKSPACE ( 11 )
6031
6032!
6033!--    Read user-defined namelist
6034       READ ( 11, urban_surface_par, ERR = 13, END = 14 )
6035
6036       message_string = 'namelist urban_surface_par is deprecated and will be ' // &
6037                     'removed in near future. Please use namelist ' //   &
6038                     'urban_surface_parameters instead'
6039       CALL message( 'usm_parin', 'PA0487', 0, 1, 0, 6, 0 )
6040
6041!
6042!--    Set flag that indicates that the urban surface model is switched on
6043       urban_surface = .TRUE.
6044
6045       GOTO 14
6046
6047 13    BACKSPACE( 11 )
6048       READ( 11 , '(A)') line
6049       CALL parin_fail_message( 'urban_surface_par', line )
6050
6051
6052 14    CONTINUE
6053
6054
6055    END SUBROUTINE usm_parin
6056
6057 
6058!------------------------------------------------------------------------------!
6059! Description:
6060! ------------
6061!
6062!> This subroutine is part of the urban surface model.
6063!> It reads daily heat produced by anthropogenic sources
6064!> and the diurnal cycle of the heat.
6065!------------------------------------------------------------------------------!
6066    SUBROUTINE usm_read_anthropogenic_heat
6067   
6068        INTEGER(iwp)                  :: i,j,k,ii  !< running indices
6069        REAL(wp)                      :: heat      !< anthropogenic heat
6070
6071!
6072!--     allocation of array of sources of anthropogenic heat and their diural profile
6073        ALLOCATE( aheat(naheatlayers,nys:nyn,nxl:nxr) )
6074        ALLOCATE( aheatprof(naheatlayers,0:24) )
6075
6076!
6077!--     read daily amount of heat and its daily cycle
6078        aheat = 0.0_wp
6079        DO  ii = 0, io_blocks-1
6080            IF ( ii == io_group )  THEN
6081
6082!--             open anthropogenic heat file
6083                OPEN( 151, file='ANTHROPOGENIC_HEAT'//TRIM(coupling_char), action='read', &
6084                           status='old', form='formatted', err=11 )
6085                i = 0
6086                j = 0
6087                DO
6088                    READ( 151, *, err=12, end=13 )  i, j, k, heat
6089                    IF ( i >= nxl  .AND.  i <= nxr  .AND.  j >= nys  .AND.  j <= nyn )  THEN
6090                        IF ( k <= naheatlayers  .AND.  k > get_topography_top_index_ji( j, i, 's' ) )  THEN
6091!--                         write heat into the array
6092                            aheat(k,j,i) = heat
6093                        ENDIF
6094                    ENDIF
6095                    CYCLE
6096 12                 WRITE(message_string,'(a,2i4)') 'error in file ANTHROPOGENIC_HEAT'//TRIM(coupling_char)//' after line ',i,j
6097                    CALL message( 'usm_read_anthropogenic_heat', 'PA0515', 0, 1, 0, 6, 0 )
6098                ENDDO
6099 13             CLOSE(151)
6100                CYCLE
6101 11             message_string = 'file ANTHROPOGENIC_HEAT'//TRIM(coupling_char)//' does not exist'
6102                CALL message( 'usm_read_anthropogenic_heat', 'PA0516', 1, 2, 0, 6, 0 )
6103            ENDIF
6104           
6105#if defined( __parallel )
6106            CALL MPI_BARRIER( comm2d, ierr )
6107#endif
6108        ENDDO
6109       
6110!
6111!--     read diurnal profiles of heat sources
6112        aheatprof = 0.0_wp
6113        DO  ii = 0, io_blocks-1
6114            IF ( ii == io_group )  THEN
6115!
6116!--             open anthropogenic heat profile file
6117                OPEN( 151, file='ANTHROPOGENIC_HEAT_PROFILE'//TRIM(coupling_char), action='read', &
6118                           status='old', form='formatted', err=21 )
6119                i = 0
6120                DO
6121                    READ( 151, *, err=22, end=23 )  i, k, heat
6122                    IF ( i >= 0  .AND.  i <= 24  .AND.  k <= naheatlayers )  THEN
6123!--                     write heat into the array
6124                        aheatprof(k,i) = heat
6125                    ENDIF
6126                    CYCLE
6127 22                 WRITE(message_string,'(a,i4)') 'error in file ANTHROPOGENIC_HEAT_PROFILE'// &
6128                                                     TRIM(coupling_char)//' after line ',i
6129                    CALL message( 'usm_read_anthropogenic_heat', 'PA0517', 0, 1, 0, 6, 0 )
6130                ENDDO
6131                aheatprof(:,24) = aheatprof(:,0)
6132 23             CLOSE(151)
6133                CYCLE
6134 21             message_string = 'file ANTHROPOGENIC_HEAT_PROFILE'//TRIM(coupling_char)//' does not exist'
6135                CALL message( 'usm_read_anthropogenic_heat', 'PA0518', 1, 2, 0, 6, 0 )
6136            ENDIF
6137           
6138#if defined( __parallel )
6139            CALL MPI_BARRIER( comm2d, ierr )
6140#endif
6141        ENDDO
6142       
6143    END SUBROUTINE usm_read_anthropogenic_heat
6144   
6145
6146!------------------------------------------------------------------------------!
6147! Description:
6148! ------------
6149!> Soubroutine reads t_surf and t_wall data from restart files
6150!------------------------------------------------------------------------------!
6151    SUBROUTINE usm_rrd_local( k, nxlf, nxlc, nxl_on_file, nxrf, nxr_on_file, nynf, nyn_on_file,    &
6152                              nysf, nysc, nys_on_file, found )
6153
6154
6155       USE control_parameters,                                                 &
6156           ONLY: length, restart_string
6157           
6158       IMPLICIT NONE
6159
6160       INTEGER(iwp)       ::  k                 !< running index over previous input files covering current local domain
6161       INTEGER(iwp)       ::  l                 !< index variable for surface type
6162       INTEGER(iwp)       ::  ns_h_on_file_usm  !< number of horizontal surface elements (urban type) on file
6163       INTEGER(iwp)       ::  nxlc              !< index of left boundary on current subdomain
6164       INTEGER(iwp)       ::  nxlf              !< index of left boundary on former subdomain
6165       INTEGER(iwp)       ::  nxl_on_file       !< index of left boundary on former local domain
6166       INTEGER(iwp)       ::  nxrf              !< index of right boundary on former subdomain
6167       INTEGER(iwp)       ::  nxr_on_file       !< index of right boundary on former local domain
6168       INTEGER(iwp)       ::  nynf              !< index of north boundary on former subdomain
6169       INTEGER(iwp)       ::  nyn_on_file       !< index of north boundary on former local domain
6170       INTEGER(iwp)       ::  nysc              !< index of south boundary on current subdomain
6171       INTEGER(iwp)       ::  nysf              !< index of south boundary on former subdomain
6172       INTEGER(iwp)       ::  nys_on_file       !< index of south boundary on former local domain
6173       
6174       INTEGER(iwp)       ::  ns_v_on_file_usm(0:3)  !< number of vertical surface elements (urban type) on file
6175       
6176       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  start_index_on_file 
6177       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  end_index_on_file
6178
6179       LOGICAL, INTENT(OUT)  ::  found 
6180!!!    suehring: Why the SAVE attribute?       
6181       REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE   ::  tmp_surf_wall_h
6182       REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE   ::  tmp_surf_window_h
6183       REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE   ::  tmp_surf_green_h
6184       REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE   ::  tmp_surf_waste_h
6185       
6186       REAL(wp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  tmp_wall_h
6187       REAL(wp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  tmp_window_h
6188       REAL(wp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  tmp_green_h
6189       
6190       TYPE( t_surf_vertical ), DIMENSION(0:3), SAVE ::  tmp_surf_wall_v
6191       TYPE( t_surf_vertical ), DIMENSION(0:3), SAVE ::  tmp_surf_window_v
6192       TYPE( t_surf_vertical ), DIMENSION(0:3), SAVE ::  tmp_surf_green_v
6193       TYPE( t_surf_vertical ), DIMENSION(0:3), SAVE ::  tmp_surf_waste_v
6194       
6195       TYPE( t_wall_vertical ), DIMENSION(0:3), SAVE ::  tmp_wall_v
6196       TYPE( t_wall_vertical ), DIMENSION(0:3), SAVE ::  tmp_window_v
6197       TYPE( t_wall_vertical ), DIMENSION(0:3), SAVE ::  tmp_green_v
6198
6199
6200       found = .TRUE.
6201
6202
6203          SELECT CASE ( restart_string(1:length) ) 
6204
6205             CASE ( 'ns_h_on_file_usm') 
6206                IF ( k == 1 )  THEN
6207                   READ ( 13 ) ns_h_on_file_usm
6208               
6209                   IF ( ALLOCATED( tmp_surf_wall_h ) ) DEALLOCATE( tmp_surf_wall_h )
6210                   IF ( ALLOCATED( tmp_wall_h ) ) DEALLOCATE( tmp_wall_h ) 
6211                   IF ( ALLOCATED( tmp_surf_window_h ) )                       &
6212                      DEALLOCATE( tmp_surf_window_h ) 
6213                   IF ( ALLOCATED( tmp_window_h) ) DEALLOCATE( tmp_window_h ) 
6214                   IF ( ALLOCATED( tmp_surf_green_h) )                         &
6215                      DEALLOCATE( tmp_surf_green_h ) 
6216                   IF ( ALLOCATED( tmp_green_h) ) DEALLOCATE( tmp_green_h )
6217                   IF ( ALLOCATED( tmp_surf_waste_h) )                         &
6218                      DEALLOCATE( tmp_surf_waste_h )
6219 
6220!
6221!--                Allocate temporary arrays for reading data on file. Note,
6222!--                the size of allocated surface elements do not necessarily
6223!--                need  to match the size of present surface elements on
6224!--                current processor, as the number of processors between
6225!--                restarts can change.
6226                   ALLOCATE( tmp_surf_wall_h(1:ns_h_on_file_usm) )
6227                   ALLOCATE( tmp_wall_h(nzb_wall:nzt_wall+1,                   &
6228                                        1:ns_h_on_file_usm) )
6229                   ALLOCATE( tmp_surf_window_h(1:ns_h_on_file_usm) )
6230                   ALLOCATE( tmp_window_h(nzb_wall:nzt_wall+1,                 &
6231                                          1:ns_h_on_file_usm) )
6232                   ALLOCATE( tmp_surf_green_h(1:ns_h_on_file_usm) )
6233                   ALLOCATE( tmp_green_h(nzb_wall:nzt_wall+1,                  &
6234                                         1:ns_h_on_file_usm) )
6235                   ALLOCATE( tmp_surf_waste_h(1:ns_h_on_file_usm) )
6236
6237                ENDIF
6238
6239             CASE ( 'ns_v_on_file_usm')
6240                IF ( k == 1 )  THEN
6241                   READ ( 13 ) ns_v_on_file_usm 
6242
6243                   DO  l = 0, 3
6244                      IF ( ALLOCATED( tmp_surf_wall_v(l)%t ) )                 &
6245                         DEALLOCATE( tmp_surf_wall_v(l)%t )
6246                      IF ( ALLOCATED( tmp_wall_v(l)%t ) )                      &
6247                         DEALLOCATE( tmp_wall_v(l)%t )
6248                      IF ( ALLOCATED( tmp_surf_window_v(l)%t ) )               & 
6249                         DEALLOCATE( tmp_surf_window_v(l)%t )
6250                      IF ( ALLOCATED( tmp_window_v(l)%t ) )                    &
6251                         DEALLOCATE( tmp_window_v(l)%t )
6252                      IF ( ALLOCATED( tmp_surf_green_v(l)%t ) )                &
6253                         DEALLOCATE( tmp_surf_green_v(l)%t )
6254                      IF ( ALLOCATED( tmp_green_v(l)%t ) )                     &
6255                         DEALLOCATE( tmp_green_v(l)%t )
6256                      IF ( ALLOCATED( tmp_surf_waste_v(l)%t ) )                &
6257                         DEALLOCATE( tmp_surf_waste_v(l)%t )
6258                   ENDDO 
6259
6260!
6261!--                Allocate temporary arrays for reading data on file. Note,
6262!--                the size of allocated surface elements do not necessarily
6263!--                need to match the size of present surface elements on
6264!--                current processor, as the number of processors between
6265!--                restarts can change.
6266                   DO  l = 0, 3
6267                      ALLOCATE( tmp_surf_wall_v(l)%t(1:ns_v_on_file_usm(l)) )
6268                      ALLOCATE( tmp_wall_v(l)%t(nzb_wall:nzt_wall+1,           &
6269                                                1:ns_v_on_file_usm(l) ) )
6270                      ALLOCATE( tmp_surf_window_v(l)%t(1:ns_v_on_file_usm(l)) )
6271                      ALLOCATE( tmp_window_v(l)%t(nzb_wall:nzt_wall+1,         & 
6272                                                  1:ns_v_on_file_usm(l) ) )
6273                      ALLOCATE( tmp_surf_green_v(l)%t(1:ns_v_on_file_usm(l)) )
6274                      ALLOCATE( tmp_green_v(l)%t(nzb_wall:nzt_wall+1,          &
6275                                                 1:ns_v_on_file_usm(l) ) )
6276                      ALLOCATE( tmp_surf_waste_v(l)%t(1:ns_v_on_file_usm(l)) )
6277                   ENDDO
6278
6279                ENDIF   
6280         
6281             CASE ( 'usm_start_index_h', 'usm_start_index_v'  )   
6282                IF ( k == 1 )  THEN
6283
6284                   IF ( ALLOCATED( start_index_on_file ) )                     &
6285                      DEALLOCATE( start_index_on_file )
6286
6287                   ALLOCATE ( start_index_on_file(nys_on_file:nyn_on_file,     &
6288                                                  nxl_on_file:nxr_on_file) )
6289
6290                   READ ( 13 )  start_index_on_file
6291
6292                ENDIF
6293               
6294             CASE ( 'usm_end_index_h', 'usm_end_index_v' )   
6295                IF ( k == 1 )  THEN
6296
6297                   IF ( ALLOCATED( end_index_on_file ) )                       &
6298                      DEALLOCATE( end_index_on_file )
6299
6300                   ALLOCATE ( end_index_on_file(nys_on_file:nyn_on_file,       &
6301                                                nxl_on_file:nxr_on_file) )
6302
6303                   READ ( 13 )  end_index_on_file
6304
6305                ENDIF
6306         
6307             CASE ( 't_surf_wall_h' )
6308                IF ( k == 1 )  THEN
6309                   IF ( .NOT.  ALLOCATED( t_surf_wall_h_1 ) )                  &
6310                      ALLOCATE( t_surf_wall_h_1(1:surf_usm_h%ns) )
6311                   READ ( 13 )  tmp_surf_wall_h
6312                ENDIF             
6313                CALL surface_restore_elements(                                 &
6314                                        t_surf_wall_h_1, tmp_surf_wall_h,      &
6315                                        surf_usm_h%start_index,                &
6316                                        start_index_on_file,                   &
6317                                        end_index_on_file,                     &
6318                                        nxlc, nysc,                            &
6319                                        nxlf, nxrf, nysf, nynf,                &
6320                                        nys_on_file, nyn_on_file,              &
6321                                        nxl_on_file,nxr_on_file )
6322
6323             CASE ( 't_surf_wall_v(0)' )
6324                IF ( k == 1 )  THEN
6325                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(0)%t ) )             &
6326                      ALLOCATE( t_surf_wall_v_1(0)%t(1:surf_usm_v(0)%ns) )
6327                   READ ( 13 )  tmp_surf_wall_v(0)%t
6328                ENDIF
6329                CALL surface_restore_elements(                                 &
6330                                        t_surf_wall_v_1(0)%t, tmp_surf_wall_v(0)%t,      &
6331                                        surf_usm_v(0)%start_index,             & 
6332                                        start_index_on_file,                   &
6333                                        end_index_on_file,                     &
6334                                        nxlc, nysc,                            &
6335                                        nxlf, nxrf, nysf, nynf,                &
6336                                        nys_on_file, nyn_on_file,              &
6337                                        nxl_on_file,nxr_on_file )
6338                     
6339             CASE ( 't_surf_wall_v(1)' )
6340                IF ( k == 1 )  THEN
6341                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(1)%t ) )             &
6342                      ALLOCATE( t_surf_wall_v_1(1)%t(1:surf_usm_v(1)%ns) )
6343                   READ ( 13 )  tmp_surf_wall_v(1)%t
6344                ENDIF
6345                CALL surface_restore_elements(                                 &
6346                                        t_surf_wall_v_1(1)%t, tmp_surf_wall_v(1)%t,      &
6347                                        surf_usm_v(1)%start_index,             & 
6348                                        start_index_on_file,                   &
6349                                        end_index_on_file,                     &
6350                                        nxlc, nysc,                            &
6351                                        nxlf, nxrf, nysf, nynf,                &
6352                                        nys_on_file, nyn_on_file,              &
6353                                        nxl_on_file,nxr_on_file )
6354
6355             CASE ( 't_surf_wall_v(2)' )
6356                IF ( k == 1 )  THEN
6357                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(2)%t ) )             &
6358                      ALLOCATE( t_surf_wall_v_1(2)%t(1:surf_usm_v(2)%ns) )
6359                   READ ( 13 )  tmp_surf_wall_v(2)%t
6360                ENDIF
6361                CALL surface_restore_elements(                                 &
6362                                        t_surf_wall_v_1(2)%t, tmp_surf_wall_v(2)%t,      &
6363                                        surf_usm_v(2)%start_index,             & 
6364                                        start_index_on_file,                   &
6365                                        end_index_on_file,                     &
6366                                        nxlc, nysc,                            &
6367                                        nxlf, nxrf, nysf, nynf,                &
6368                                        nys_on_file, nyn_on_file,              &
6369                                        nxl_on_file,nxr_on_file )
6370                     
6371             CASE ( 't_surf_wall_v(3)' )
6372                IF ( k == 1 )  THEN
6373                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(3)%t ) )             &
6374                      ALLOCATE( t_surf_wall_v_1(3)%t(1:surf_usm_v(3)%ns) )
6375                   READ ( 13 )  tmp_surf_wall_v(3)%t
6376                ENDIF
6377                CALL surface_restore_elements(                                 &
6378                                        t_surf_wall_v_1(3)%t, tmp_surf_wall_v(3)%t,      &
6379                                        surf_usm_v(3)%start_index,             & 
6380                                        start_index_on_file,                   &
6381                                        end_index_on_file,                     &
6382                                        nxlc, nysc,                            &
6383                                        nxlf, nxrf, nysf, nynf,                &
6384                                        nys_on_file, nyn_on_file,              &
6385                                        nxl_on_file,nxr_on_file )
6386
6387             CASE ( 't_surf_green_h' )
6388                IF ( k == 1 )  THEN
6389                   IF ( .NOT.  ALLOCATED( t_surf_green_h_1 ) )                 &
6390                      ALLOCATE( t_surf_green_h_1(1:surf_usm_h%ns) )
6391                   READ ( 13 )  tmp_surf_green_h
6392                ENDIF
6393                CALL surface_restore_elements(                                 &
6394                                        t_surf_green_h_1, tmp_surf_green_h,    &
6395                                        surf_usm_h%start_index,                & 
6396                                        start_index_on_file,                   &
6397                                        end_index_on_file,                     &
6398                                        nxlc, nysc,                            &
6399                                        nxlf, nxrf, nysf, nynf,                &
6400                                        nys_on_file, nyn_on_file,              &
6401                                        nxl_on_file,nxr_on_file )
6402
6403             CASE ( 't_surf_green_v(0)' )
6404                IF ( k == 1 )  THEN
6405                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(0)%t ) )            &
6406                      ALLOCATE( t_surf_green_v_1(0)%t(1:surf_usm_v(0)%ns) )
6407                   READ ( 13 )  tmp_surf_green_v(0)%t
6408                ENDIF
6409                CALL surface_restore_elements(                                 &
6410                                        t_surf_green_v_1(0)%t,                 &
6411                                        tmp_surf_green_v(0)%t,                 &
6412                                        surf_usm_v(0)%start_index,             & 
6413                                        start_index_on_file,                   &
6414                                        end_index_on_file,                     &
6415                                        nxlc, nysc,                            &
6416                                        nxlf, nxrf, nysf, nynf,                &
6417                                        nys_on_file, nyn_on_file,              &
6418                                        nxl_on_file,nxr_on_file )
6419                   
6420             CASE ( 't_surf_green_v(1)' )
6421                IF ( k == 1 )  THEN
6422                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(1)%t ) )            &
6423                      ALLOCATE( t_surf_green_v_1(1)%t(1:surf_usm_v(1)%ns) )
6424                   READ ( 13 )  tmp_surf_green_v(1)%t
6425                ENDIF
6426                CALL surface_restore_elements(                                 &
6427                                        t_surf_green_v_1(1)%t,                 &
6428                                        tmp_surf_green_v(1)%t,                 &
6429                                        surf_usm_v(1)%start_index,             & 
6430                                        start_index_on_file,                   &
6431                                        end_index_on_file,                     &
6432                                        nxlc, nysc,                            &
6433                                        nxlf, nxrf, nysf, nynf,                &
6434                                        nys_on_file, nyn_on_file,              &
6435                                        nxl_on_file,nxr_on_file )
6436
6437             CASE ( 't_surf_green_v(2)' )
6438                IF ( k == 1 )  THEN
6439                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(2)%t ) )            &
6440                      ALLOCATE( t_surf_green_v_1(2)%t(1:surf_usm_v(2)%ns) )
6441                   READ ( 13 )  tmp_surf_green_v(2)%t
6442                ENDIF
6443                CALL surface_restore_elements(                                 &
6444                                        t_surf_green_v_1(2)%t,                 &
6445                                        tmp_surf_green_v(2)%t,                 &
6446                                        surf_usm_v(2)%start_index,             & 
6447                                        start_index_on_file,                   &
6448                                        end_index_on_file,                     &
6449                                        nxlc, nysc,                            &
6450                                        nxlf, nxrf, nysf, nynf,                &
6451                                        nys_on_file, nyn_on_file,              &
6452                                        nxl_on_file,nxr_on_file )
6453                   
6454             CASE ( 't_surf_green_v(3)' )
6455                IF ( k == 1 )  THEN
6456                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(3)%t ) )            &
6457                      ALLOCATE( t_surf_green_v_1(3)%t(1:surf_usm_v(3)%ns) )
6458                   READ ( 13 )  tmp_surf_green_v(3)%t
6459                ENDIF
6460                CALL surface_restore_elements(                                 &
6461                                        t_surf_green_v_1(3)%t,                 & 
6462                                        tmp_surf_green_v(3)%t,                 &
6463                                        surf_usm_v(3)%start_index,             & 
6464                                        start_index_on_file,                   &
6465                                        end_index_on_file,                     &
6466                                        nxlc, nysc,                            &
6467                                        nxlf, nxrf, nysf, nynf,                &
6468                                        nys_on_file, nyn_on_file,              &
6469                                        nxl_on_file,nxr_on_file )
6470
6471             CASE ( 't_surf_window_h' )
6472                IF ( k == 1 )  THEN
6473                   IF ( .NOT.  ALLOCATED( t_surf_window_h_1 ) )                &
6474                      ALLOCATE( t_surf_window_h_1(1:surf_usm_h%ns) )
6475                   READ ( 13 )  tmp_surf_window_h
6476                ENDIF
6477                CALL surface_restore_elements(                                 &
6478                                        t_surf_window_h_1,                     &
6479                                        tmp_surf_window_h,                     &
6480                                        surf_usm_h%start_index,                & 
6481                                        start_index_on_file,                   &
6482                                        end_index_on_file,                     &
6483                                        nxlc, nysc,                            &
6484                                        nxlf, nxrf, nysf, nynf,                &
6485                                        nys_on_file, nyn_on_file,              &
6486                                        nxl_on_file,nxr_on_file )
6487
6488             CASE ( 't_surf_window_v(0)' )
6489                IF ( k == 1 )  THEN
6490                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(0)%t ) )           &
6491                      ALLOCATE( t_surf_window_v_1(0)%t(1:surf_usm_v(0)%ns) )
6492                   READ ( 13 )  tmp_surf_window_v(0)%t
6493                ENDIF
6494                CALL surface_restore_elements(                                 &
6495                                        t_surf_window_v_1(0)%t,                &
6496                                        tmp_surf_window_v(0)%t,                &
6497                                        surf_usm_v(0)%start_index,             & 
6498                                        start_index_on_file,                   &
6499                                        end_index_on_file,                     &
6500                                        nxlc, nysc,                            &
6501                                        nxlf, nxrf, nysf, nynf,                &
6502                                        nys_on_file, nyn_on_file,              &
6503                                        nxl_on_file,nxr_on_file )
6504                   
6505             CASE ( 't_surf_window_v(1)' )
6506                IF ( k == 1 )  THEN
6507                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(1)%t ) )           &
6508                      ALLOCATE( t_surf_window_v_1(1)%t(1:surf_usm_v(1)%ns) )
6509                   READ ( 13 )  tmp_surf_window_v(1)%t
6510                ENDIF
6511                CALL surface_restore_elements(                                 &
6512                                        t_surf_window_v_1(1)%t,                &
6513                                        tmp_surf_window_v(1)%t,                &
6514                                        surf_usm_v(1)%start_index,             & 
6515                                        start_index_on_file,                   &
6516                                        end_index_on_file,                     &
6517                                        nxlc, nysc,                            &
6518                                        nxlf, nxrf, nysf, nynf,                &
6519                                        nys_on_file, nyn_on_file,              &
6520                                        nxl_on_file,nxr_on_file )
6521
6522             CASE ( 't_surf_window_v(2)' )
6523                IF ( k == 1 )  THEN
6524                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(2)%t ) )           &
6525                      ALLOCATE( t_surf_window_v_1(2)%t(1:surf_usm_v(2)%ns) )
6526                   READ ( 13 )  tmp_surf_window_v(2)%t
6527                ENDIF
6528                CALL surface_restore_elements(                                 &
6529                                        t_surf_window_v_1(2)%t,                & 
6530                                        tmp_surf_window_v(2)%t,                &
6531                                        surf_usm_v(2)%start_index,             & 
6532                                        start_index_on_file,                   &
6533                                        end_index_on_file,                     &
6534                                        nxlc, nysc,                            &
6535                                        nxlf, nxrf, nysf, nynf,                &
6536                                        nys_on_file, nyn_on_file,              &
6537                                        nxl_on_file,nxr_on_file )
6538                   
6539             CASE ( 't_surf_window_v(3)' )
6540                IF ( k == 1 )  THEN
6541                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(3)%t ) )           &
6542                      ALLOCATE( t_surf_window_v_1(3)%t(1:surf_usm_v(3)%ns) )
6543                   READ ( 13 )  tmp_surf_window_v(3)%t
6544                ENDIF
6545                CALL surface_restore_elements(                                 &
6546                                        t_surf_window_v_1(3)%t,                & 
6547                                        tmp_surf_window_v(3)%t,                &
6548                                        surf_usm_v(3)%start_index,             & 
6549                                        start_index_on_file,                   &
6550                                        end_index_on_file,                     &
6551                                        nxlc, nysc,                            &
6552                                        nxlf, nxrf, nysf, nynf,                &
6553                                        nys_on_file, nyn_on_file,              &
6554                                        nxl_on_file,nxr_on_file )
6555
6556             CASE ( 'waste_heat_h' )
6557                IF ( k == 1 )  THEN
6558                   IF ( .NOT.  ALLOCATED( surf_usm_h%waste_heat ) )            &
6559                      ALLOCATE( surf_usm_h%waste_heat(1:surf_usm_h%ns) )
6560                   READ ( 13 )  tmp_surf_waste_h
6561                ENDIF             
6562                CALL surface_restore_elements(                                 &
6563                                        surf_usm_h%waste_heat,                 &
6564                                        tmp_surf_waste_h,                      &
6565                                        surf_usm_h%start_index,                &
6566                                        start_index_on_file,                   &
6567                                        end_index_on_file,                     &
6568                                        nxlc, nysc,                            &
6569                                        nxlf, nxrf, nysf, nynf,                &
6570                                        nys_on_file, nyn_on_file,              &
6571                                        nxl_on_file,nxr_on_file )                 
6572                                       
6573             CASE ( 'waste_heat_v(0)' )
6574                IF ( k == 1 )  THEN
6575                   IF ( .NOT.  ALLOCATED( surf_usm_v(0)%waste_heat ) )         &
6576                      ALLOCATE( surf_usm_v(0)%waste_heat(1:surf_usm_v(0)%ns) )
6577                   READ ( 13 )  tmp_surf_waste_v(0)%t
6578                ENDIF
6579                CALL surface_restore_elements(                                 &
6580                                        surf_usm_v(0)%waste_heat,              &
6581                                        tmp_surf_waste_v(0)%t,                 &
6582                                        surf_usm_v(0)%start_index,             & 
6583                                        start_index_on_file,                   &
6584                                        end_index_on_file,                     &
6585                                        nxlc, nysc,                            &
6586                                        nxlf, nxrf, nysf, nynf,                &
6587                                        nys_on_file, nyn_on_file,              &
6588                                        nxl_on_file,nxr_on_file )
6589                     
6590             CASE ( 'waste_heat_v(1)' )
6591                IF ( k == 1 )  THEN
6592                   IF ( .NOT.  ALLOCATED( surf_usm_v(1)%waste_heat ) )         &
6593                      ALLOCATE( surf_usm_v(1)%waste_heat(1:surf_usm_v(1)%ns) )
6594                   READ ( 13 )  tmp_surf_waste_v(1)%t
6595                ENDIF
6596                CALL surface_restore_elements(                                 &
6597                                        surf_usm_v(1)%waste_heat,              &
6598                                        tmp_surf_waste_v(1)%t,                 &
6599                                        surf_usm_v(1)%start_index,             & 
6600                                        start_index_on_file,                   &
6601                                        end_index_on_file,                     &
6602                                        nxlc, nysc,                            &
6603                                        nxlf, nxrf, nysf, nynf,                &
6604                                        nys_on_file, nyn_on_file,              &
6605                                        nxl_on_file,nxr_on_file )
6606
6607             CASE ( 'waste_heat_v(2)' )
6608                IF ( k == 1 )  THEN
6609                   IF ( .NOT.  ALLOCATED( surf_usm_v(2)%waste_heat ) )         &
6610                      ALLOCATE( surf_usm_v(2)%waste_heat(1:surf_usm_v(2)%ns) )
6611                   READ ( 13 )  tmp_surf_waste_v(2)%t
6612                ENDIF
6613                CALL surface_restore_elements(                                 &
6614                                        surf_usm_v(2)%waste_heat,              &
6615                                        tmp_surf_waste_v(2)%t,                 &
6616                                        surf_usm_v(2)%start_index,             & 
6617                                        start_index_on_file,                   &
6618                                        end_index_on_file,                     &
6619                                        nxlc, nysc,                            &
6620                                        nxlf, nxrf, nysf, nynf,                &
6621                                        nys_on_file, nyn_on_file,              &
6622                                        nxl_on_file,nxr_on_file )
6623                     
6624             CASE ( 'waste_heat_v(3)' )
6625                IF ( k == 1 )  THEN
6626                   IF ( .NOT.  ALLOCATED( surf_usm_v(3)%waste_heat ) )         &
6627                      ALLOCATE( surf_usm_v(3)%waste_heat(1:surf_usm_v(3)%ns) )
6628                   READ ( 13 )  tmp_surf_waste_v(3)%t
6629                ENDIF
6630                CALL surface_restore_elements(                                 &
6631                                        surf_usm_v(3)%waste_heat,              &
6632                                        tmp_surf_waste_v(3)%t,                 &
6633                                        surf_usm_v(3)%start_index,             & 
6634                                        start_index_on_file,                   &
6635                                        end_index_on_file,                     &
6636                                        nxlc, nysc,                            &
6637                                        nxlf, nxrf, nysf, nynf,                &
6638                                        nys_on_file, nyn_on_file,              &
6639                                        nxl_on_file,nxr_on_file )
6640
6641             CASE ( 't_wall_h' )
6642                IF ( k == 1 )  THEN
6643                   IF ( .NOT.  ALLOCATED( t_wall_h_1 ) )                       &
6644                      ALLOCATE( t_wall_h_1(nzb_wall:nzt_wall+1,                &
6645                                           1:surf_usm_h%ns) )
6646                   READ ( 13 )  tmp_wall_h
6647                ENDIF
6648                CALL surface_restore_elements(                                 &
6649                                        t_wall_h_1, tmp_wall_h,                &
6650                                        surf_usm_h%start_index,                & 
6651                                        start_index_on_file,                   &
6652                                        end_index_on_file,                     &
6653                                        nxlc, nysc,                            &
6654                                        nxlf, nxrf, nysf, nynf,                &
6655                                        nys_on_file, nyn_on_file,              &
6656                                        nxl_on_file,nxr_on_file )
6657
6658             CASE ( 't_wall_v(0)' )
6659                IF ( k == 1 )  THEN
6660                   IF ( .NOT.  ALLOCATED( t_wall_v_1(0)%t ) )                  &
6661                      ALLOCATE( t_wall_v_1(0)%t(nzb_wall:nzt_wall+1,           &
6662                                                1:surf_usm_v(0)%ns) )
6663                   READ ( 13 )  tmp_wall_v(0)%t
6664                ENDIF
6665                CALL surface_restore_elements(                                 &
6666                                        t_wall_v_1(0)%t, tmp_wall_v(0)%t,      &
6667                                        surf_usm_v(0)%start_index,             & 
6668                                        start_index_on_file,                   &
6669                                        end_index_on_file,                     &
6670                                        nxlc, nysc,                            &
6671                                        nxlf, nxrf, nysf, nynf,                &
6672                                        nys_on_file, nyn_on_file,              &
6673                                        nxl_on_file,nxr_on_file )
6674
6675             CASE ( 't_wall_v(1)' )
6676                IF ( k == 1 )  THEN
6677                   IF ( .NOT.  ALLOCATED( t_wall_v_1(1)%t ) )                  &
6678                      ALLOCATE( t_wall_v_1(1)%t(nzb_wall:nzt_wall+1,           &
6679                                                1:surf_usm_v(1)%ns) )
6680                   READ ( 13 )  tmp_wall_v(1)%t
6681                ENDIF
6682                CALL surface_restore_elements(                                 &
6683                                        t_wall_v_1(1)%t, tmp_wall_v(1)%t,      &
6684                                        surf_usm_v(1)%start_index,             & 
6685                                        start_index_on_file,                   &
6686                                        end_index_on_file,                     &
6687                                        nxlc, nysc,                            &
6688                                        nxlf, nxrf, nysf, nynf,                &
6689                                        nys_on_file, nyn_on_file,              &
6690                                        nxl_on_file,nxr_on_file )
6691
6692             CASE ( 't_wall_v(2)' )
6693                IF ( k == 1 )  THEN
6694                   IF ( .NOT.  ALLOCATED( t_wall_v_1(2)%t ) )                  &
6695                      ALLOCATE( t_wall_v_1(2)%t(nzb_wall:nzt_wall+1,           &
6696                                                1:surf_usm_v(2)%ns) )
6697                   READ ( 13 )  tmp_wall_v(2)%t
6698                ENDIF
6699                CALL surface_restore_elements(                                 &
6700                                        t_wall_v_1(2)%t, tmp_wall_v(2)%t,      &
6701                                        surf_usm_v(2)%start_index,             & 
6702                                        start_index_on_file,                   &
6703                                        end_index_on_file ,                    &
6704                                        nxlc, nysc,                            &
6705                                        nxlf, nxrf, nysf, nynf,                &
6706                                        nys_on_file, nyn_on_file,              &
6707                                        nxl_on_file,nxr_on_file )
6708
6709             CASE ( 't_wall_v(3)' )
6710                IF ( k == 1 )  THEN
6711                   IF ( .NOT.  ALLOCATED( t_wall_v_1(3)%t ) )                  &
6712                      ALLOCATE( t_wall_v_1(3)%t(nzb_wall:nzt_wall+1,           &
6713                                                1:surf_usm_v(3)%ns) )
6714                   READ ( 13 )  tmp_wall_v(3)%t
6715                ENDIF
6716                CALL surface_restore_elements(                                 &
6717                                        t_wall_v_1(3)%t, tmp_wall_v(3)%t,      &
6718                                        surf_usm_v(3)%start_index,             &   
6719                                        start_index_on_file,                   &
6720                                        end_index_on_file,                     &
6721                                        nxlc, nysc,                            &
6722                                        nxlf, nxrf, nysf, nynf,                &
6723                                        nys_on_file, nyn_on_file,              &
6724                                        nxl_on_file,nxr_on_file )
6725
6726             CASE ( 't_green_h' )
6727                IF ( k == 1 )  THEN
6728                   IF ( .NOT.  ALLOCATED( t_green_h_1 ) )                      &
6729                      ALLOCATE( t_green_h_1(nzb_wall:nzt_wall+1,               &
6730                                            1:surf_usm_h%ns) )
6731                   READ ( 13 )  tmp_green_h
6732                ENDIF
6733                CALL surface_restore_elements(                                 &
6734                                        t_green_h_1, tmp_green_h,              &
6735                                        surf_usm_h%start_index,                & 
6736                                        start_index_on_file,                   &
6737                                        end_index_on_file,                     &
6738                                        nxlc, nysc,                            &
6739                                        nxlf, nxrf, nysf, nynf,                &
6740                                        nys_on_file, nyn_on_file,              &
6741                                        nxl_on_file,nxr_on_file )
6742
6743             CASE ( 't_green_v(0)' )
6744                IF ( k == 1 )  THEN
6745                   IF ( .NOT.  ALLOCATED( t_green_v_1(0)%t ) )                 &
6746                      ALLOCATE( t_green_v_1(0)%t(nzb_wall:nzt_wall+1,          &
6747                                                 1:surf_usm_v(0)%ns) )
6748                   READ ( 13 )  tmp_green_v(0)%t
6749                ENDIF
6750                CALL surface_restore_elements(                                 &
6751                                        t_green_v_1(0)%t, tmp_green_v(0)%t,    &
6752                                        surf_usm_v(0)%start_index,             & 
6753                                        start_index_on_file,                   &
6754                                        end_index_on_file,                     &
6755                                        nxlc, nysc,                            &
6756                                        nxlf, nxrf, nysf, nynf,                &
6757                                        nys_on_file, nyn_on_file,              &
6758                                        nxl_on_file,nxr_on_file )
6759
6760             CASE ( 't_green_v(1)' )
6761                IF ( k == 1 )  THEN
6762                   IF ( .NOT.  ALLOCATED( t_green_v_1(1)%t ) )                 &
6763                      ALLOCATE( t_green_v_1(1)%t(nzb_wall:nzt_wall+1,          &
6764                                                 1:surf_usm_v(1)%ns) )
6765                   READ ( 13 )  tmp_green_v(1)%t
6766                ENDIF
6767                CALL surface_restore_elements(                                 &
6768                                        t_green_v_1(1)%t, tmp_green_v(1)%t,    &
6769                                        surf_usm_v(1)%start_index,             & 
6770                                        start_index_on_file,                   &
6771                                        end_index_on_file,                     &
6772                                        nxlc, nysc,                            &
6773                                        nxlf, nxrf, nysf, nynf,                &
6774                                        nys_on_file, nyn_on_file,              &
6775                                        nxl_on_file,nxr_on_file )
6776
6777             CASE ( 't_green_v(2)' )
6778                IF ( k == 1 )  THEN
6779                   IF ( .NOT.  ALLOCATED( t_green_v_1(2)%t ) )                 &
6780                      ALLOCATE( t_green_v_1(2)%t(nzb_wall:nzt_wall+1,          &
6781                                                 1:surf_usm_v(2)%ns) )
6782                   READ ( 13 )  tmp_green_v(2)%t
6783                ENDIF
6784                CALL surface_restore_elements(                                 &
6785                                        t_green_v_1(2)%t, tmp_green_v(2)%t,    &
6786                                        surf_usm_v(2)%start_index,             & 
6787                                        start_index_on_file,                   &
6788                                        end_index_on_file ,                    &
6789                                        nxlc, nysc,                            &
6790                                        nxlf, nxrf, nysf, nynf,                &
6791                                        nys_on_file, nyn_on_file,              &
6792                                        nxl_on_file,nxr_on_file )
6793
6794             CASE ( 't_green_v(3)' )
6795                IF ( k == 1 )  THEN
6796                   IF ( .NOT.  ALLOCATED( t_green_v_1(3)%t ) )                 &
6797                      ALLOCATE( t_green_v_1(3)%t(nzb_wall:nzt_wall+1,          &
6798                                                 1:surf_usm_v(3)%ns) )
6799                   READ ( 13 )  tmp_green_v(3)%t
6800                ENDIF
6801                CALL surface_restore_elements(                                 &
6802                                        t_green_v_1(3)%t, tmp_green_v(3)%t,    &
6803                                        surf_usm_v(3)%start_index,             & 
6804                                        start_index_on_file,                   &
6805                                        end_index_on_file,                     &
6806                                        nxlc, nysc,                            &
6807                                        nxlf, nxrf, nysf, nynf,                &
6808                                        nys_on_file, nyn_on_file,              &
6809                                        nxl_on_file,nxr_on_file )
6810
6811             CASE ( 't_window_h' )
6812                IF ( k == 1 )  THEN
6813                   IF ( .NOT.  ALLOCATED( t_window_h_1 ) )                     &
6814                      ALLOCATE( t_window_h_1(nzb_wall:nzt_wall+1,              &
6815                                             1:surf_usm_h%ns) )
6816                   READ ( 13 )  tmp_window_h
6817                ENDIF
6818                CALL surface_restore_elements(                                 &
6819                                        t_window_h_1, tmp_window_h,            &
6820                                        surf_usm_h%start_index,                & 
6821                                        start_index_on_file,                   &
6822                                        end_index_on_file,                     &
6823                                        nxlc, nysc,                            &
6824                                        nxlf, nxrf, nysf, nynf,                &
6825                                        nys_on_file, nyn_on_file,              &
6826                                        nxl_on_file, nxr_on_file )
6827
6828             CASE ( 't_window_v(0)' )
6829                IF ( k == 1 )  THEN
6830                   IF ( .NOT.  ALLOCATED( t_window_v_1(0)%t ) )                &
6831                      ALLOCATE( t_window_v_1(0)%t(nzb_wall:nzt_wall+1,         &
6832                                                  1:surf_usm_v(0)%ns) )
6833                   READ ( 13 )  tmp_window_v(0)%t
6834                ENDIF
6835                CALL surface_restore_elements(                                 &
6836                                        t_window_v_1(0)%t,                     & 
6837                                        tmp_window_v(0)%t,                     &
6838                                        surf_usm_v(0)%start_index,             &
6839                                        start_index_on_file,                   &
6840                                        end_index_on_file,                     &
6841                                        nxlc, nysc,                            &
6842                                        nxlf, nxrf, nysf, nynf,                &
6843                                        nys_on_file, nyn_on_file,              &
6844                                        nxl_on_file,nxr_on_file )
6845
6846             CASE ( 't_window_v(1)' )
6847                IF ( k == 1 )  THEN
6848                   IF ( .NOT.  ALLOCATED( t_window_v_1(1)%t ) )                &
6849                      ALLOCATE( t_window_v_1(1)%t(nzb_wall:nzt_wall+1,         &
6850                                                  1:surf_usm_v(1)%ns) )
6851                   READ ( 13 )  tmp_window_v(1)%t
6852                ENDIF
6853                CALL surface_restore_elements(                                 &
6854                                        t_window_v_1(1)%t,                     & 
6855                                        tmp_window_v(1)%t,                     &
6856                                        surf_usm_v(1)%start_index,             & 
6857                                        start_index_on_file,                   &
6858                                        end_index_on_file,                     &
6859                                        nxlc, nysc,                            &
6860                                        nxlf, nxrf, nysf, nynf,                &
6861                                        nys_on_file, nyn_on_file,              &
6862                                        nxl_on_file,nxr_on_file )
6863
6864             CASE ( 't_window_v(2)' )
6865                IF ( k == 1 )  THEN
6866                   IF ( .NOT.  ALLOCATED( t_window_v_1(2)%t ) )                &
6867                      ALLOCATE( t_window_v_1(2)%t(nzb_wall:nzt_wall+1,         &
6868                                                  1:surf_usm_v(2)%ns) )
6869                   READ ( 13 )  tmp_window_v(2)%t
6870                ENDIF
6871                CALL surface_restore_elements(                                 &
6872                                        t_window_v_1(2)%t,                     & 
6873                                        tmp_window_v(2)%t,                     &
6874                                        surf_usm_v(2)%start_index,             & 
6875                                        start_index_on_file,                   &
6876                                        end_index_on_file ,                    &
6877                                        nxlc, nysc,                            &
6878                                        nxlf, nxrf, nysf, nynf,                &
6879                                        nys_on_file, nyn_on_file,              &
6880                                        nxl_on_file,nxr_on_file )
6881
6882             CASE ( 't_window_v(3)' )
6883                IF ( k == 1 )  THEN
6884                   IF ( .NOT.  ALLOCATED( t_window_v_1(3)%t ) )                &
6885                      ALLOCATE( t_window_v_1(3)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(3)%ns) )
6886                   READ ( 13 )  tmp_window_v(3)%t
6887                ENDIF
6888                CALL surface_restore_elements(                                 &
6889                                        t_window_v_1(3)%t,                     & 
6890                                        tmp_window_v(3)%t,                     &
6891                                        surf_usm_v(3)%start_index,             & 
6892                                        start_index_on_file,                   &
6893                                        end_index_on_file,                     &
6894                                        nxlc, nysc,                            &
6895                                        nxlf, nxrf, nysf, nynf,                &
6896                                        nys_on_file, nyn_on_file,              &
6897                                        nxl_on_file,nxr_on_file )
6898
6899             CASE DEFAULT
6900
6901                   found = .FALSE.
6902
6903          END SELECT
6904
6905       
6906    END SUBROUTINE usm_rrd_local
6907
6908   
6909!------------------------------------------------------------------------------!
6910! Description:
6911! ------------
6912!
6913!> This subroutine reads walls, roofs and land categories and it parameters
6914!> from input files.
6915!------------------------------------------------------------------------------!
6916    SUBROUTINE usm_read_urban_surface_types
6917   
6918        USE netcdf_data_input_mod,                                             &
6919            ONLY:  building_pars_f, building_type_f
6920
6921        IMPLICIT NONE
6922
6923        CHARACTER(12)                                         :: wtn
6924        INTEGER(iwp)                                          :: wtc
6925        REAL(wp), DIMENSION(n_surface_params)                 :: wtp
6926        LOGICAL                                               :: ascii_file = .FALSE.
6927        INTEGER(iwp), DIMENSION(0:17, nysg:nyng, nxlg:nxrg)   :: usm_par
6928        REAL(wp), DIMENSION(1:14, nysg:nyng, nxlg:nxrg)       :: usm_val
6929        INTEGER(iwp)                                          :: k, l, iw, jw, kw, it, ip, ii, ij, m
6930        INTEGER(iwp)                                          :: i, j
6931        INTEGER(iwp)                                          :: nz, roof, dirwe, dirsn
6932        INTEGER(iwp)                                          :: category
6933        INTEGER(iwp)                                          :: weheight1, wecat1, snheight1, sncat1
6934        INTEGER(iwp)                                          :: weheight2, wecat2, snheight2, sncat2
6935        INTEGER(iwp)                                          :: weheight3, wecat3, snheight3, sncat3
6936        REAL(wp)                                              :: height, albedo, thick
6937        REAL(wp)                                              :: wealbedo1, wethick1, snalbedo1, snthick1
6938        REAL(wp)                                              :: wealbedo2, wethick2, snalbedo2, snthick2
6939        REAL(wp)                                              :: wealbedo3, wethick3, snalbedo3, snthick3
6940
6941!
6942!--     If building_pars or building_type are already read from static input
6943!--     file, skip reading ASCII file.
6944        IF ( building_type_f%from_file  .OR.  building_pars_f%from_file )      &
6945           RETURN
6946!
6947!--     Check if ASCII input file exists. If not, return and initialize USM
6948!--     with default settings.
6949        INQUIRE( FILE = 'SURFACE_PARAMETERS' // coupling_char,                 &
6950                 EXIST = ascii_file )
6951                 
6952        IF ( .NOT. ascii_file )  RETURN
6953
6954!
6955!--     read categories of walls and their parameters
6956        DO  ii = 0, io_blocks-1
6957            IF ( ii == io_group )  THEN
6958!
6959!--             open urban surface file
6960                OPEN( 151, file='SURFACE_PARAMETERS'//coupling_char, action='read', &
6961                           status='old', form='formatted', err=15 )
6962!
6963!--             first test and get n_surface_types
6964                k = 0
6965                l = 0
6966                DO
6967                    l = l+1
6968                    READ( 151, *, err=11, end=12 )  wtc, wtp, wtn
6969                    k = k+1
6970                    CYCLE
6971 11                 CONTINUE
6972                ENDDO
6973 12             n_surface_types = k
6974                ALLOCATE( surface_type_names(n_surface_types) )
6975                ALLOCATE( surface_type_codes(n_surface_types) )
6976                ALLOCATE( surface_params(n_surface_params, n_surface_types) )
6977!
6978!--             real reading
6979                rewind( 151 )
6980                k = 0
6981                DO
6982                    READ( 151, *, err=13, end=14 )  wtc, wtp, wtn
6983                    k = k+1
6984                    surface_type_codes(k) = wtc
6985                    surface_params(:,k) = wtp
6986                    surface_type_names(k) = wtn
6987                    CYCLE
698813                  WRITE(6,'(i3,a,2i5)') myid, 'readparams2 error k=', k
6989                    FLUSH(6)
6990                    CONTINUE
6991                ENDDO
6992 14             CLOSE(151)
6993                CYCLE
6994 15             message_string = 'file SURFACE_PARAMETERS'//TRIM(coupling_char)//' does not exist'
6995                CALL message( 'usm_read_urban_surface_types', 'PA0513', 1, 2, 0, 6, 0 )
6996            ENDIF
6997        ENDDO
6998   
6999!
7000!--     read types of surfaces
7001        usm_par = 0
7002        DO  ii = 0, io_blocks-1
7003            IF ( ii == io_group )  THEN
7004
7005!
7006!--             open csv urban surface file
7007                OPEN( 151, file='URBAN_SURFACE'//TRIM(coupling_char), action='read', &
7008                      status='old', form='formatted', err=23 )
7009               
7010                l = 0
7011                DO
7012                    l = l+1
7013!
7014!--                 i, j, height, nz, roof, dirwe, dirsn, category, soilcat,
7015!--                 weheight1, wecat1, snheight1, sncat1, weheight2, wecat2, snheight2, sncat2,
7016!--                 weheight3, wecat3, snheight3, sncat3
7017                    READ( 151, *, err=21, end=25 )  i, j, height, nz, roof, dirwe, dirsn,            &
7018                                            category, albedo, thick,                                 &
7019                                            weheight1, wecat1, wealbedo1, wethick1,                  &
7020                                            weheight2, wecat2, wealbedo2, wethick2,                  &
7021                                            weheight3, wecat3, wealbedo3, wethick3,                  &
7022                                            snheight1, sncat1, snalbedo1, snthick1,                  &
7023                                            snheight2, sncat2, snalbedo2, snthick2,                  &
7024                                            snheight3, sncat3, snalbedo3, snthick3
7025
7026                    IF ( i >= nxlg  .AND.  i <= nxrg  .AND.  j >= nysg  .AND.  j <= nyng )  THEN
7027!
7028!--                     write integer variables into array
7029                        usm_par(:,j,i) = (/1, nz, roof, dirwe, dirsn, category,                      &
7030                                          weheight1, wecat1, weheight2, wecat2, weheight3, wecat3,   &
7031                                          snheight1, sncat1, snheight2, sncat2, snheight3, sncat3 /)
7032!
7033!--                     write real values into array
7034                        usm_val(:,j,i) = (/ albedo, thick,                                           &
7035                                           wealbedo1, wethick1, wealbedo2, wethick2,                 &
7036                                           wealbedo3, wethick3, snalbedo1, snthick1,                 &
7037                                           snalbedo2, snthick2, snalbedo3, snthick3 /)
7038                    ENDIF
7039                    CYCLE
7040 21                 WRITE (message_string, "(A,I5)") 'errors in file URBAN_SURFACE'//TRIM(coupling_char)//' on line ', l
7041                    CALL message( 'usm_read_urban_surface_types', 'PA0512', 0, 1, 0, 6, 0 )
7042                ENDDO
7043         
7044 23             message_string = 'file URBAN_SURFACE'//TRIM(coupling_char)//' does not exist'
7045                CALL message( 'usm_read_urban_surface_types', 'PA0514', 1, 2, 0, 6, 0 )
7046
7047 25             CLOSE( 151 )
7048
7049            ENDIF
7050#if defined( __parallel )
7051            CALL MPI_BARRIER( comm2d, ierr )
7052#endif
7053        ENDDO
7054       
7055!
7056!--     check completeness and formal correctness of the data
7057        DO i = nxlg, nxrg
7058            DO j = nysg, nyng
7059                IF ( usm_par(0,j,i) /= 0  .AND.  (        &  !< incomplete data,supply default values later
7060                     usm_par(1,j,i) < nzb  .OR.           &
7061                     usm_par(1,j,i) > nzt  .OR.           &  !< incorrect height (nz < nzb  .OR.  nz > nzt)
7062                     usm_par(2,j,i) < 0  .OR.             &
7063                     usm_par(2,j,i) > 1  .OR.             &  !< incorrect roof sign
7064                     usm_par(3,j,i) < nzb-nzt  .OR.       & 
7065                     usm_par(3,j,i) > nzt-nzb  .OR.       &  !< incorrect west-east wall direction sign
7066                     usm_par(4,j,i) < nzb-nzt  .OR.       &
7067                     usm_par(4,j,i) > nzt-nzb  .OR.       &  !< incorrect south-north wall direction sign
7068                     usm_par(6,j,i) < nzb  .OR.           & 
7069                     usm_par(6,j,i) > nzt  .OR.           &  !< incorrect pedestrian level height for west-east wall
7070                     usm_par(8,j,i) > nzt  .OR.           &
7071                     usm_par(10,j,i) > nzt  .OR.          &  !< incorrect wall or roof level height for west-east wall
7072                     usm_par(12,j,i) < nzb  .OR.          & 
7073                     usm_par(12,j,i) > nzt  .OR.          &  !< incorrect pedestrian level height for south-north wall
7074                     usm_par(14,j,i) > nzt  .OR.          &
7075                     usm_par(16,j,i) > nzt                &  !< incorrect wall or roof level height for south-north wall
7076                    ) )  THEN
7077!
7078!--                 incorrect input data
7079                    WRITE (message_string, "(A,2I5)") 'missing or incorrect data in file URBAN_SURFACE'// &
7080                                                       TRIM(coupling_char)//' for i,j=', i,j
7081                    CALL message( 'usm_read_urban_surface', 'PA0504', 1, 2, 0, 6, 0 )
7082                ENDIF
7083               
7084            ENDDO
7085        ENDDO
7086!       
7087!--     Assign the surface types to the respective data type.
7088!--     First, for horizontal upward-facing surfaces.
7089!--     Further, set flag indicating that albedo is initialized via ASCII
7090!--     format, else it would be overwritten in the radiation model.
7091        surf_usm_h%albedo_from_ascii = .TRUE.
7092        DO  m = 1, surf_usm_h%ns
7093           iw = surf_usm_h%i(m)
7094           jw = surf_usm_h%j(m)
7095           kw = surf_usm_h%k(m)
7096
7097           IF ( usm_par(5,jw,iw) == 0 )  THEN
7098
7099              IF ( zu(kw) >= roof_height_limit )  THEN
7100                 surf_usm_h%isroof_surf(m)   = .TRUE.
7101                 surf_usm_h%surface_types(m) = roof_category         !< default category for root surface
7102              ELSE
7103                 surf_usm_h%isroof_surf(m)   = .FALSE.
7104                 surf_usm_h%surface_types(m) = land_category         !< default category for land surface
7105              ENDIF
7106
7107              surf_usm_h%albedo(:,m)    = -1.0_wp
7108              surf_usm_h%thickness_wall(m) = -1.0_wp
7109              surf_usm_h%thickness_green(m) = -1.0_wp
7110              surf_usm_h%thickness_window(m) = -1.0_wp
7111           ELSE
7112              IF ( usm_par(2,jw,iw)==0 )  THEN
7113                 surf_usm_h%isroof_surf(m)    = .FALSE.
7114                 surf_usm_h%thickness_wall(m) = -1.0_wp
7115                 surf_usm_h%thickness_window(m) = -1.0_wp
7116                 surf_usm_h%thickness_green(m)  = -1.0_wp
7117              ELSE
7118                 surf_usm_h%isroof_surf(m)    = .TRUE.
7119                 surf_usm_h%thickness_wall(m) = usm_val(2,jw,iw)
7120                 surf_usm_h%thickness_window(m) = usm_val(2,jw,iw)
7121                 surf_usm_h%thickness_green(m)  = usm_val(2,jw,iw)
7122              ENDIF
7123              surf_usm_h%surface_types(m) = usm_par(5,jw,iw)
7124              surf_usm_h%albedo(:,m)   = usm_val(1,jw,iw)
7125              surf_usm_h%transmissivity(m)    = 0.0_wp
7126           ENDIF
7127!
7128!--        Find the type position
7129           it = surf_usm_h%surface_types(m)
7130           ip = -99999
7131           DO k = 1, n_surface_types
7132              IF ( surface_type_codes(k) == it )  THEN
7133                 ip = k
7134                 EXIT
7135              ENDIF
7136           ENDDO
7137           IF ( ip == -99999 )  THEN
7138!
7139!--           land/roof category not found
7140              WRITE (9,"(A,I5,A,3I5)") 'land/roof category ', it,     &
7141                                       ' not found  for i,j,k=', iw,jw,kw
7142              FLUSH(9)
7143              IF ( surf_usm_h%isroof_surf(m) ) THEN
7144                 category = roof_category
7145              ELSE
7146                 category = land_category
7147              ENDIF
7148              DO k = 1, n_surface_types
7149                 IF ( surface_type_codes(k) == roof_category ) THEN
7150                    ip = k
7151                    EXIT
7152                 ENDIF
7153              ENDDO
7154              IF ( ip == -99999 )  THEN
7155!
7156!--              default land/roof category not found
7157                 WRITE (9,"(A,I5,A,3I5)") 'Default land/roof category', category, ' not found!'
7158                 FLUSH(9)
7159                 ip = 1
7160              ENDIF
7161           ENDIF
7162!
7163!--        Albedo
7164           IF ( surf_usm_h%albedo(ind_veg_wall,m) < 0.0_wp )  THEN
7165              surf_usm_h%albedo(:,m) = surface_params(ialbedo,ip)
7166           ENDIF
7167!
7168!--        Albedo type is 0 (custom), others are replaced later
7169           surf_usm_h%albedo_type(:,m) = 0
7170!
7171!--        Transmissivity
7172           IF ( surf_usm_h%transmissivity(m) < 0.0_wp )  THEN
7173              surf_usm_h%transmissivity(m) = 0.0_wp
7174           ENDIF
7175!
7176!--        emissivity of the wall
7177           surf_usm_h%emissivity(:,m) = surface_params(iemiss,ip)
7178!           
7179!--        heat conductivity λS between air and wall ( W m−2 K−1 )
7180           surf_usm_h%lambda_surf(m) = surface_params(ilambdas,ip)
7181           surf_usm_h%lambda_surf_window(m) = surface_params(ilambdas,ip)
7182           surf_usm_h%lambda_surf_green(m)  = surface_params(ilambdas,ip)
7183!           
7184!--        roughness length for momentum, heat and humidity
7185           surf_usm_h%z0(m) = surface_params(irough,ip)
7186           surf_usm_h%z0h(m) = surface_params(iroughh,ip)
7187           surf_usm_h%z0q(m) = surface_params(iroughh,ip)
7188!
7189!--        Surface skin layer heat capacity (J m−2 K−1 )
7190           surf_usm_h%c_surface(m) = surface_params(icsurf,ip)
7191           surf_usm_h%c_surface_window(m) = surface_params(icsurf,ip)
7192           surf_usm_h%c_surface_green(m)  = surface_params(icsurf,ip)
7193!           
7194!--        wall material parameters:
7195!--        thickness of the wall (m)
7196!--        missing values are replaced by default value for category
7197           IF ( surf_usm_h%thickness_wall(m) <= 0.001_wp )  THEN
7198                surf_usm_h%thickness_wall(m) = surface_params(ithick,ip)
7199           ENDIF
7200           IF ( surf_usm_h%thickness_window(m) <= 0.001_wp )  THEN
7201                surf_usm_h%thickness_window(m) = surface_params(ithick,ip)
7202           ENDIF
7203           IF ( surf_usm_h%thickness_green(m) <= 0.001_wp )  THEN
7204                surf_usm_h%thickness_green(m) = surface_params(ithick,ip)
7205           ENDIF
7206!           
7207!--        volumetric heat capacity rho*C of the wall ( J m−3 K−1 )
7208           surf_usm_h%rho_c_wall(:,m) = surface_params(irhoC,ip)
7209           surf_usm_h%rho_c_window(:,m) = surface_params(irhoC,ip)
7210           surf_usm_h%rho_c_green(:,m)  = surface_params(irhoC,ip)
7211!           
7212!--        thermal conductivity λH of the wall (W m−1 K−1 )
7213           surf_usm_h%lambda_h(:,m) = surface_params(ilambdah,ip)
7214           surf_usm_h%lambda_h_window(:,m) = surface_params(ilambdah,ip)
7215           surf_usm_h%lambda_h_green(:,m)  = surface_params(ilambdah,ip)
7216
7217        ENDDO
7218!
7219!--     For vertical surface elements ( 0 -- northward-facing, 1 -- southward-facing,
7220!--     2 -- eastward-facing, 3 -- westward-facing )
7221        DO  l = 0, 3
7222!
7223!--        Set flag indicating that albedo is initialized via ASCII format.
7224!--        Else it would be overwritten in the radiation model.
7225           surf_usm_v(l)%albedo_from_ascii = .TRUE.
7226           DO  m = 1, surf_usm_v(l)%ns
7227              i  = surf_usm_v(l)%i(m)
7228              j  = surf_usm_v(l)%j(m)
7229              kw = surf_usm_v(l)%k(m)
7230             
7231              IF ( l == 3 )  THEN ! westward facing
7232                 iw = i
7233                 jw = j
7234                 ii = 6
7235                 ij = 3
7236              ELSEIF ( l == 2 )  THEN
7237                 iw = i-1
7238                 jw = j
7239                 ii = 6
7240                 ij = 3
7241              ELSEIF ( l == 1 )  THEN
7242                 iw = i
7243                 jw = j
7244                 ii = 12
7245                 ij = 9
7246              ELSEIF ( l == 0 )  THEN
7247                 iw = i
7248                 jw = j-1
7249                 ii = 12
7250                 ij = 9
7251              ENDIF
7252
7253              IF ( iw < 0 .OR. jw < 0 ) THEN
7254!
7255!--              wall on west or south border of the domain - assign default category
7256                 IF ( kw <= roof_height_limit ) THEN
7257                     surf_usm_v(l)%surface_types(m) = wall_category   !< default category for wall surface in wall zone
7258                 ELSE
7259                     surf_usm_v(l)%surface_types(m) = roof_category   !< default category for wall surface in roof zone
7260                 END IF
7261                 surf_usm_v(l)%albedo(:,m)         = -1.0_wp
7262                 surf_usm_v(l)%thickness_wall(m)   = -1.0_wp
7263                 surf_usm_v(l)%thickness_window(m) = -1.0_wp
7264                 surf_usm_v(l)%thickness_green(m)  = -1.0_wp
7265                 surf_usm_v(l)%transmissivity(m)   = -1.0_wp
7266              ELSE IF ( kw <= usm_par(ii,jw,iw) )  THEN
7267!
7268!--                 pedestrian zone
7269                 IF ( usm_par(ii+1,jw,iw) == 0 )  THEN
7270                     surf_usm_v(l)%surface_types(m)  = pedestrian_category   !< default category for wall surface in
7271                                                                             !<pedestrian zone
7272                     surf_usm_v(l)%albedo(:,m)         = -1.0_wp
7273                     surf_usm_v(l)%thickness_wall(m)   = -1.0_wp
7274                     surf_usm_v(l)%thickness_window(m) = -1.0_wp
7275                     surf_usm_v(l)%thickness_green(m)  = -1.0_wp
7276                     surf_usm_v(l)%transmissivity(m)   = -1.0_wp
7277                 ELSE
7278                     surf_usm_v(l)%surface_types(m)    = usm_par(ii+1,jw,iw)
7279                     surf_usm_v(l)%albedo(:,m)         = usm_val(ij,jw,iw)
7280                     surf_usm_v(l)%thickness_wall(m)   = usm_val(ij+1,jw,iw)
7281                     surf_usm_v(l)%thickness_window(m) = usm_val(ij+1,jw,iw)
7282                     surf_usm_v(l)%thickness_green(m)  = usm_val(ij+1,jw,iw)
7283                     surf_usm_v(l)%transmissivity(m)   = 0.0_wp
7284                 ENDIF
7285              ELSE IF ( kw <= usm_par(ii+2,jw,iw) )  THEN
7286!
7287!--              wall zone
7288                 IF ( usm_par(ii+3,jw,iw) == 0 )  THEN
7289                     surf_usm_v(l)%surface_types(m)    = wall_category         !< default category for wall surface
7290                     surf_usm_v(l)%albedo(:,m)         = -1.0_wp
7291                     surf_usm_v(l)%thickness_wall(m)   = -1.0_wp
7292                     surf_usm_v(l)%thickness_window(m) = -1.0_wp
7293                     surf_usm_v(l)%thickness_green(m)  = -1.0_wp
7294                     surf_usm_v(l)%transmissivity(m)   = -1.0_wp
7295                 ELSE
7296                     surf_usm_v(l)%surface_types(m)    = usm_par(ii+3,jw,iw)
7297                     surf_usm_v(l)%albedo(:,m)         = usm_val(ij+2,jw,iw)
7298                     surf_usm_v(l)%thickness_wall(m)   = usm_val(ij+3,jw,iw)
7299                     surf_usm_v(l)%thickness_window(m) = usm_val(ij+3,jw,iw)
7300                     surf_usm_v(l)%thickness_green(m)  = usm_val(ij+3,jw,iw)
7301                     surf_usm_v(l)%transmissivity(m)   = 0.0_wp
7302                 ENDIF
7303              ELSE IF ( kw <= usm_par(ii+4,jw,iw) )  THEN
7304!
7305!--              roof zone
7306                 IF ( usm_par(ii+5,jw,iw) == 0 )  THEN
7307                     surf_usm_v(l)%surface_types(m)    = roof_category         !< default category for roof surface
7308                     surf_usm_v(l)%albedo(:,m)         = -1.0_wp
7309                     surf_usm_v(l)%thickness_wall(m)   = -1.0_wp
7310                     surf_usm_v(l)%thickness_window(m) = -1.0_wp
7311                     surf_usm_v(l)%thickness_green(m)  = -1.0_wp
7312                     surf_usm_v(l)%transmissivity(m)   = -1.0_wp
7313                 ELSE
7314                     surf_usm_v(l)%surface_types(m)    = usm_par(ii+5,jw,iw)
7315                     surf_usm_v(l)%albedo(:,m)         = usm_val(ij+4,jw,iw)
7316                     surf_usm_v(l)%thickness_wall(m)   = usm_val(ij+5,jw,iw)
7317                     surf_usm_v(l)%thickness_window(m) = usm_val(ij+5,jw,iw)
7318                     surf_usm_v(l)%thickness_green(m)  = usm_val(ij+5,jw,iw)
7319                     surf_usm_v(l)%transmissivity(m)   = 0.0_wp
7320                 ENDIF
7321              ELSE
7322                 WRITE(9,*) 'Problem reading USM data:'
7323                 WRITE(9,*) l,i,j,kw,get_topography_top_index_ji( j, i, 's' )
7324                 WRITE(9,*) ii,iw,jw,kw,get_topography_top_index_ji( jw, iw, 's' )
7325                 WRITE(9,*) usm_par(ii,jw,iw),usm_par(ii+1,jw,iw)
7326                 WRITE(9,*) usm_par(ii+2,jw,iw),usm_par(ii+3,jw,iw)
7327                 WRITE(9,*) usm_par(ii+4,jw,iw),usm_par(ii+5,jw,iw)
7328                 WRITE(9,*) kw,roof_height_limit,wall_category,roof_category
7329                 FLUSH(9)
7330!
7331!--              supply the default category
7332                 IF ( kw <= roof_height_limit ) THEN
7333                     surf_usm_v(l)%surface_types(m) = wall_category   !< default category for wall surface in wall zone
7334                 ELSE
7335                     surf_usm_v(l)%surface_types(m) = roof_category   !< default category for wall surface in roof zone
7336                 END IF
7337                 surf_usm_v(l)%albedo(:,m)         = -1.0_wp
7338                 surf_usm_v(l)%thickness_wall(m)   = -1.0_wp
7339                 surf_usm_v(l)%thickness_window(m) = -1.0_wp
7340                 surf_usm_v(l)%thickness_green(m)  = -1.0_wp
7341                 surf_usm_v(l)%transmissivity(m)   = -1.0_wp
7342              ENDIF
7343!
7344!--           Find the type position
7345              it = surf_usm_v(l)%surface_types(m)
7346              ip = -99999
7347              DO k = 1, n_surface_types
7348                 IF ( surface_type_codes(k) == it )  THEN
7349                    ip = k
7350                    EXIT
7351                 ENDIF
7352              ENDDO
7353              IF ( ip == -99999 )  THEN
7354!
7355!--              wall category not found
7356                 WRITE (9, "(A,I7,A,3I5)") 'wall category ', it,  &
7357                                           ' not found  for i,j,k=', iw,jw,kw
7358                 FLUSH(9)
7359                 category = wall_category 
7360                 DO k = 1, n_surface_types
7361                    IF ( surface_type_codes(k) == category ) THEN
7362                       ip = k
7363                       EXIT
7364                    ENDIF
7365                 ENDDO
7366                 IF ( ip == -99999 )  THEN
7367!
7368!--                 default wall category not found
7369                    WRITE (9, "(A,I5,A,3I5)") 'Default wall category', category, ' not found!'
7370                    FLUSH(9)
7371                    ip = 1
7372                 ENDIF
7373              ENDIF
7374
7375!
7376!--           Albedo
7377              IF ( surf_usm_v(l)%albedo(ind_veg_wall,m) < 0.0_wp )  THEN
7378                 surf_usm_v(l)%albedo(:,m) = surface_params(ialbedo,ip)
7379              ENDIF
7380!--           Albedo type is 0 (custom), others are replaced later
7381              surf_usm_v(l)%albedo_type(:,m) = 0
7382!--           Transmissivity of the windows
7383              IF ( surf_usm_v(l)%transmissivity(m) < 0.0_wp )  THEN
7384                 surf_usm_v(l)%transmissivity(m) = 0.0_wp
7385              ENDIF
7386!
7387!--           emissivity of the wall
7388              surf_usm_v(l)%emissivity(:,m) = surface_params(iemiss,ip)
7389!           
7390!--           heat conductivity lambda S between air and wall ( W m-2 K-1 )
7391              surf_usm_v(l)%lambda_surf(m) = surface_params(ilambdas,ip)
7392              surf_usm_v(l)%lambda_surf_window(m) = surface_params(ilambdas,ip)
7393              surf_usm_v(l)%lambda_surf_green(m) = surface_params(ilambdas,ip)
7394!           
7395!--           roughness length
7396              surf_usm_v(l)%z0(m) = surface_params(irough,ip)
7397              surf_usm_v(l)%z0h(m) = surface_params(iroughh,ip)
7398              surf_usm_v(l)%z0q(m) = surface_params(iroughh,ip)
7399!           
7400!--           Surface skin layer heat capacity (J m-2 K-1 )
7401              surf_usm_v(l)%c_surface(m) = surface_params(icsurf,ip)
7402              surf_usm_v(l)%c_surface_window(m) = surface_params(icsurf,ip)
7403              surf_usm_v(l)%c_surface_green(m) = surface_params(icsurf,ip)
7404!           
7405!--           wall material parameters:
7406!--           thickness of the wall (m)
7407!--           missing values are replaced by default value for category
7408              IF ( surf_usm_v(l)%thickness_wall(m) <= 0.001_wp )  THEN
7409                   surf_usm_v(l)%thickness_wall(m) = surface_params(ithick,ip)
7410              ENDIF
7411              IF ( surf_usm_v(l)%thickness_window(m) <= 0.001_wp )  THEN
7412                   surf_usm_v(l)%thickness_window(m) = surface_params(ithick,ip)
7413              ENDIF
7414              IF ( surf_usm_v(l)%thickness_green(m) <= 0.001_wp )  THEN
7415                   surf_usm_v(l)%thickness_green(m) = surface_params(ithick,ip)
7416              ENDIF
7417!
7418!--           volumetric heat capacity rho*C of the wall ( J m-3 K-1 )
7419              surf_usm_v(l)%rho_c_wall(:,m) = surface_params(irhoC,ip)
7420              surf_usm_v(l)%rho_c_window(:,m) = surface_params(irhoC,ip)
7421              surf_usm_v(l)%rho_c_green(:,m) = surface_params(irhoC,ip)
7422!           
7423!--           thermal conductivity lambda H of the wall (W m-1 K-1 )
7424              surf_usm_v(l)%lambda_h(:,m) = surface_params(ilambdah,ip)
7425              surf_usm_v(l)%lambda_h_window(:,m) = surface_params(ilambdah,ip)
7426              surf_usm_v(l)%lambda_h_green(:,m) = surface_params(ilambdah,ip)
7427
7428           ENDDO
7429        ENDDO 
7430
7431!
7432!--     Initialize wall layer thicknesses. Please note, this will be removed
7433!--     after migration to Palm input data standard. 
7434        DO k = nzb_wall, nzt_wall
7435           zwn(k) = zwn_default(k)
7436           zwn_green(k) = zwn_default_green(k)
7437           zwn_window(k) = zwn_default_window(k)
7438        ENDDO
7439!
7440!--     apply for all particular surface grids. First for horizontal surfaces
7441        DO  m = 1, surf_usm_h%ns
7442           surf_usm_h%zw(:,m) = zwn(:) * surf_usm_h%thickness_wall(m)
7443           surf_usm_h%zw_green(:,m) = zwn_green(:) * surf_usm_h%thickness_green(m)
7444           surf_usm_h%zw_window(:,m) = zwn_window(:) * surf_usm_h%thickness_window(m)
7445        ENDDO
7446        DO  l = 0, 3
7447           DO  m = 1, surf_usm_v(l)%ns
7448              surf_usm_v(l)%zw(:,m) = zwn(:) * surf_usm_v(l)%thickness_wall(m)
7449              surf_usm_v(l)%zw_green(:,m) = zwn_green(:) * surf_usm_v(l)%thickness_green(m)
7450              surf_usm_v(l)%zw_window(:,m) = zwn_window(:) * surf_usm_v(l)%thickness_window(m)
7451           ENDDO
7452        ENDDO
7453
7454       
7455        WRITE(9,*) 'Urban surfaces read'
7456        FLUSH(9)
7457       
7458        CALL location_message( '    types and parameters of urban surfaces read', .TRUE. )
7459   
7460    END SUBROUTINE usm_read_urban_surface_types
7461
7462
7463!------------------------------------------------------------------------------!
7464! Description:
7465! ------------
7466!
7467!> This function advances through the list of local surfaces to find given
7468!> x, y, d, z coordinates
7469!------------------------------------------------------------------------------!
7470    PURE FUNCTION find_surface( x, y, z, d ) result(isurfl)
7471
7472        INTEGER(iwp), INTENT(in)                :: x, y, z, d
7473        INTEGER(iwp)                            :: isurfl
7474        INTEGER(iwp)                            :: isx, isy, isz
7475
7476        IF ( d == 0 ) THEN
7477           DO  isurfl = 1, surf_usm_h%ns
7478              isx = surf_usm_h%i(isurfl)
7479              isy = surf_usm_h%j(isurfl)
7480              isz = surf_usm_h%k(isurfl)
7481              IF ( isx==x .and. isy==y .and. isz==z )  RETURN
7482           ENDDO
7483        ELSE
7484           DO  isurfl = 1, surf_usm_v(d-1)%ns
7485              isx = surf_usm_v(d-1)%i(isurfl)
7486              isy = surf_usm_v(d-1)%j(isurfl)
7487              isz = surf_usm_v(d-1)%k(isurfl)
7488              IF ( isx==x .and. isy==y .and. isz==z )  RETURN
7489           ENDDO
7490        ENDIF
7491!
7492!--     coordinate not found
7493        isurfl = -1
7494
7495    END FUNCTION
7496
7497
7498!------------------------------------------------------------------------------!
7499! Description:
7500! ------------
7501!
7502!> This subroutine reads temperatures of respective material layers in walls,
7503!> roofs and ground from input files. Data in the input file must be in
7504!> standard order, i.e. horizontal surfaces first ordered by x, y and then
7505!> vertical surfaces ordered by x, y, direction, z
7506!------------------------------------------------------------------------------!
7507    SUBROUTINE usm_read_wall_temperature
7508
7509        INTEGER(iwp)                                          :: i, j, k, d, ii, iline  !> running indices
7510        INTEGER(iwp)                                          :: isurfl
7511        REAL(wp)                                              :: rtsurf
7512        REAL(wp), DIMENSION(nzb_wall:nzt_wall+1)              :: rtwall
7513
7514
7515        DO  ii = 0, io_blocks-1
7516            IF ( ii == io_group )  THEN
7517!
7518!--             open wall temperature file
7519                OPEN( 152, file='WALL_TEMPERATURE'//coupling_char, action='read', &
7520                           status='old', form='formatted', err=15 )
7521
7522                isurfl = 0
7523                iline = 1
7524                DO
7525                    rtwall = -9999.0_wp  !< for incomplete lines
7526                    READ( 152, *, err=13, end=14 )  i, j, k, d, rtsurf, rtwall
7527
7528                    IF ( nxl <= i .and. i <= nxr .and. &
7529                        nys <= j .and. j <= nyn)  THEN  !< local processor
7530!--                     identify surface id
7531                        isurfl = find_surface( i, j, k, d )
7532                        IF ( isurfl == -1 )  THEN
7533                            WRITE(message_string, '(a,4i5,a,i5,a)') 'Coordinates (xyzd) ', i, j, k, d, &
7534                                ' on line ', iline, &
7535                                ' in file WALL_TEMPERATURE are either not present or out of standard order of surfaces.'
7536                            CALL message( 'usm_read_wall_temperature', 'PA0521', 1, 2, 0, 6, 0 )
7537                        ENDIF
7538!
7539!--                     assign temperatures
7540                        IF ( d == 0 ) THEN
7541                           t_surf_wall_h(isurfl) = rtsurf
7542                           t_wall_h(:,isurfl) = rtwall(:)
7543                           t_window_h(:,isurfl) = rtwall(:)
7544                           t_green_h(:,isurfl) = rtwall(:)
7545                        ELSE
7546                           t_surf_wall_v(d-1)%t(isurfl) = rtsurf
7547                           t_wall_v(d-1)%t(:,isurfl) = rtwall(:)
7548                           t_window_v(d-1)%t(:,isurfl) = rtwall(:)
7549                           t_green_v(d-1)%t(:,isurfl) = rtwall(:)
7550                        ENDIF
7551                    ENDIF
7552
7553                    iline = iline + 1
7554                    CYCLE
7555 13                 WRITE(message_string, '(a,i5,a)') 'Error reading line ', iline, &
7556                        ' in file WALL_TEMPERATURE.'
7557                    CALL message( 'usm_read_wall_temperature', 'PA0522', 1, 2, 0, 6, 0 )
7558                ENDDO
7559 14             CLOSE(152)
7560                CYCLE
7561 15             message_string = 'file WALL_TEMPERATURE'//TRIM(coupling_char)//' does not exist'
7562                CALL message( 'usm_read_wall_temperature', 'PA0523', 1, 2, 0, 6, 0 )
7563            ENDIF
7564#if defined( __parallel )
7565            CALL MPI_BARRIER( comm2d, ierr )
7566#endif
7567        ENDDO
7568
7569        CALL location_message( '    wall layer temperatures read', .TRUE. )
7570
7571    END SUBROUTINE usm_read_wall_temperature
7572
7573
7574
7575!------------------------------------------------------------------------------!
7576! Description:
7577! ------------
7578!> Solver for the energy balance at the ground/roof/wall surface.
7579!> It follows basic ideas and structure of lsm_energy_balance
7580!> with many simplifications and adjustments.
7581!> TODO better description
7582!> No calculation of window surface temperatures during spinup to increase
7583!> maximum possible timstep
7584!------------------------------------------------------------------------------!
7585    SUBROUTINE usm_surface_energy_balance( spinup )
7586
7587
7588        IMPLICIT NONE
7589
7590        INTEGER(iwp)                          :: i, j, k, l, m   !< running indices
7591       
7592        INTEGER(iwp) ::  i_off     !< offset to determine index of surface element, seen from atmospheric grid point, for x
7593        INTEGER(iwp) ::  j_off     !< offset to determine index of surface element, seen from atmospheric grid point, for y
7594        INTEGER(iwp) ::  k_off     !< offset to determine index of surface element, seen from atmospheric grid point, for z
7595
7596        LOGICAL                               :: spinup             !true during spinup
7597       
7598        REAL(wp)                              :: stend_wall         !< surface tendency
7599       
7600        REAL(wp)                              :: stend_window       !< surface tendency
7601        REAL(wp)                              :: stend_green        !< surface tendency
7602        REAL(wp)                              :: coef_1             !< first coeficient for prognostic equation
7603        REAL(wp)                              :: coef_window_1      !< first coeficient for prognostic window equation
7604        REAL(wp)                              :: coef_green_1       !< first coeficient for prognostic green wall equation
7605        REAL(wp)                              :: coef_2             !< second  coeficient for prognostic equation
7606        REAL(wp)                              :: coef_window_2      !< second  coeficient for prognostic window equation
7607        REAL(wp)                              :: coef_green_2       !< second  coeficient for prognostic green wall equation
7608        REAL(wp)                              :: rho_cp             !< rho_wall_surface * c_p
7609        REAL(wp)                              :: f_shf              !< factor for shf_eb
7610        REAL(wp)                              :: f_shf_window       !< factor for shf_eb window
7611        REAL(wp)                              :: f_shf_green        !< factor for shf_eb green wall
7612        REAL(wp)                              :: lambda_surface     !< current value of lambda_surface (heat conductivity
7613                                                                    !<between air and wall)
7614        REAL(wp)                              :: lambda_surface_window  !< current value of lambda_surface (heat conductivity
7615                                                                        !< between air and window)
7616        REAL(wp)                              :: lambda_surface_green   !< current value of lambda_surface (heat conductivity
7617                                                                        !< between air and greeb wall)
7618       
7619        REAL(wp)                              :: dtime              !< simulated time of day (in UTC)
7620        INTEGER(iwp)                          :: dhour              !< simulated hour of day (in UTC)
7621        REAL(wp)                              :: acoef              !< actual coefficient of diurnal profile of anthropogenic heat
7622        REAL(wp) ::  f1,          &  !< resistance correction term 1
7623                     f2,          &  !< resistance correction term 2
7624                     f3,          &  !< resistance correction term 3
7625                     e,           &  !< water vapour pressure
7626                     e_s,         &  !< water vapour saturation pressure
7627                     e_s_dt,      &  !< derivate of e_s with respect to T
7628                     tend,        &  !< tendency
7629                     dq_s_dt,     &  !< derivate of q_s with respect to T
7630                     f_qsws,      &  !< factor for qsws
7631                     f_qsws_veg,  &  !< factor for qsws_veg
7632                     f_qsws_liq,  &  !< factor for qsws_liq
7633                     m_liq_max,   &  !< maxmimum value of the liq. water reservoir
7634                     qv1,         &  !< specific humidity at first grid level
7635                     m_max_depth = 0.0002_wp, &  !< Maximum capacity of the water reservoir (m)
7636                     rho_lv,      &  !< frequently used parameter for green layers
7637                     drho_l_lv,   &  !< frequently used parameter for green layers
7638                     q_s             !< saturation specific humidity
7639
7640!
7641!--     Index offset of surface element point with respect to adjoining
7642!--     atmospheric grid point
7643        k_off = surf_usm_h%koff
7644        j_off = surf_usm_h%joff
7645        i_off = surf_usm_h%ioff
7646       
7647!       
7648!--     First, treat horizontal surface elements
7649        !$OMP PARALLEL PRIVATE (m, i, j, k, lambda_surface, lambda_surface_window,                 &
7650        !$OMP&                  lambda_surface_green, qv1, rho_cp, rho_lv, drho_l_lv, f_shf,       &
7651        !$OMP&                  f_shf_window, f_shf_green, m_total, f1, f2, e_s, e, f3, f_qsws_veg,&
7652        !$OMP&                  q_s, f_qsws_liq, f_qsws, e_s_dt, dq_s_dt, coef_1, coef_window_1,   &
7653        !$OMP&                  coef_green_1, coef_2, coef_window_2, coef_green_2, stend_wall,     &
7654        !$OMP&                  stend_window, stend_green, tend, m_liq_max)
7655        !$OMP DO SCHEDULE (STATIC)
7656        DO  m = 1, surf_usm_h%ns
7657!
7658!--        Get indices of respective grid point
7659           i = surf_usm_h%i(m)
7660           j = surf_usm_h%j(m)
7661           k = surf_usm_h%k(m)
7662!
7663!--        TODO - how to calculate lambda_surface for horizontal surfaces
7664!--        (lambda_surface is set according to stratification in land surface model)
7665!--        MS: ???
7666           IF ( surf_usm_h%ol(m) >= 0.0_wp )  THEN
7667              lambda_surface = surf_usm_h%lambda_surf(m)
7668              lambda_surface_window = surf_usm_h%lambda_surf_window(m)
7669              lambda_surface_green = surf_usm_h%lambda_surf_green(m)
7670           ELSE
7671              lambda_surface = surf_usm_h%lambda_surf(m)
7672              lambda_surface_window = surf_usm_h%lambda_surf_window(m)
7673              lambda_surface_green = surf_usm_h%lambda_surf_green(m)
7674           ENDIF
7675
7676!            pt1  = pt(k,j,i)
7677           IF ( humidity )  THEN
7678              qv1 = q(k,j,i)
7679           ELSE
7680              qv1 = 0.0_wp
7681           ENDIF
7682!
7683!--        calculate rho * c_p coefficient at surface layer
7684           rho_cp  = c_p * hyp(k) / ( r_d * surf_usm_h%pt1(m) * exner(k) )
7685
7686           IF ( surf_usm_h%frac(ind_pav_green,m) > 0.0_wp )  THEN
7687!
7688!--           Calculate frequently used parameters
7689              rho_lv    = rho_cp / c_p * l_v
7690              drho_l_lv = 1.0_wp / (rho_l * l_v)
7691           ENDIF
7692
7693!
7694!--        Calculate aerodyamic resistance.
7695!--        Calculation for horizontal surfaces follows LSM formulation
7696!--        pt, us, ts are not available for the prognostic time step,
7697!--        data from the last time step is used here.
7698!
7699!--        Workaround: use single r_a as stability is only treated for the
7700!--        average temperature
7701           surf_usm_h%r_a(m) = ( surf_usm_h%pt1(m) - surf_usm_h%pt_surface(m) ) /&
7702                               ( surf_usm_h%ts(m) * surf_usm_h%us(m) + 1.0E-20_wp )   
7703           surf_usm_h%r_a_window(m) = surf_usm_h%r_a(m)
7704           surf_usm_h%r_a_green(m)  = surf_usm_h%r_a(m)
7705
7706!            r_a = ( surf_usm_h%pt1(m) - t_surf_h(m) / exner(k) ) /                              &
7707!                  ( surf_usm_h%ts(m) * surf_usm_h%us(m) + 1.0E-20_wp )
7708!            r_a_window = ( surf_usm_h%pt1(m) - t_surf_window_h(m) / exner(k) ) /                &
7709!                  ( surf_usm_h%ts(m) * surf_usm_h%us(m) + 1.0E-20_wp )
7710!            r_a_green = ( surf_usm_h%pt1(m) - t_surf_green_h(m) / exner(k) ) /                  &
7711!                  ( surf_usm_h%ts(m) * surf_usm_h%us(m) + 1.0E-20_wp )
7712               
7713!--        Make sure that the resistance does not drop to zero
7714           IF ( surf_usm_h%r_a(m)        < 1.0_wp )                            &
7715               surf_usm_h%r_a(m)        = 1.0_wp
7716           IF ( surf_usm_h%r_a_green(m)  < 1.0_wp )                            &
7717               surf_usm_h%r_a_green(m)  = 1.0_wp
7718           IF ( surf_usm_h%r_a_window(m) < 1.0_wp )                            &
7719               surf_usm_h%r_a_window(m) = 1.0_wp
7720             
7721!
7722!--        Make sure that the resistacne does not exceed a maxmium value in case
7723!--        of zero velocities
7724           IF ( surf_usm_h%r_a(m)        > 300.0_wp )                          &
7725               surf_usm_h%r_a(m)        = 300.0_wp
7726           IF ( surf_usm_h%r_a_green(m)  > 300.0_wp )                          &
7727               surf_usm_h%r_a_green(m)  = 300.0_wp
7728           IF ( surf_usm_h%r_a_window(m) > 300.0_wp )                          &
7729               surf_usm_h%r_a_window(m) = 300.0_wp               
7730               
7731!
7732!--        factor for shf_eb
7733           f_shf  = rho_cp / surf_usm_h%r_a(m)
7734           f_shf_window  = rho_cp / surf_usm_h%r_a_window(m)
7735           f_shf_green  = rho_cp / surf_usm_h%r_a_green(m)
7736       
7737
7738           IF ( surf_usm_h%frac(ind_pav_green,m) > 0.0_wp ) THEN
7739!--           Adapted from LSM:
7740!--           Second step: calculate canopy resistance r_canopy
7741!--           f1-f3 here are defined as 1/f1-f3 as in ECMWF documentation
7742 
7743!--           f1: correction for incoming shortwave radiation (stomata close at
7744!--           night)
7745              f1 = MIN( 1.0_wp, ( 0.004_wp * surf_usm_h%rad_sw_in(m) + 0.05_wp ) / &
7746                               (0.81_wp * (0.004_wp * surf_usm_h%rad_sw_in(m)      &
7747                                + 1.0_wp)) )
7748!
7749!--           f2: correction for soil moisture availability to plants (the
7750!--           integrated soil moisture must thus be considered here)
7751!--           f2 = 0 for very dry soils
7752              m_total = 0.0_wp
7753              DO  k = nzb_wall, nzt_wall+1
7754                  m_total = m_total + rootfr_h(nzb_wall,m)                              &
7755                            * MAX(swc_h(nzb_wall,m),wilt_h(nzb_wall,m))
7756              ENDDO 
7757   
7758              IF ( m_total > wilt_h(nzb_wall,m)  .AND.  m_total < fc_h(nzb_wall,m) )  THEN
7759                 f2 = ( m_total - wilt_h(nzb_wall,m) ) / (fc_h(nzb_wall,m) - wilt_h(nzb_wall,m) )
7760              ELSEIF ( m_total >= fc_h(nzb_wall,m) )  THEN
7761                 f2 = 1.0_wp
7762              ELSE
7763                 f2 = 1.0E-20_wp
7764              ENDIF
7765       
7766!
7767!--          Calculate water vapour pressure at saturation
7768              e_s = 0.01_wp * 610.78_wp * EXP( 17.269_wp * ( t_surf_green_h(m) &
7769                            - 273.16_wp ) / ( t_surf_green_h(m) - 35.86_wp ) )
7770!
7771!--           f3: correction for vapour pressure deficit
7772              IF ( surf_usm_h%g_d(m) /= 0.0_wp )  THEN
7773!
7774!--           Calculate vapour pressure
7775                 e  = qv1 * surface_pressure / ( qv1 + 0.622_wp )
7776                 f3 = EXP ( - surf_usm_h%g_d(m) * (e_s - e) )
7777              ELSE
7778                 f3 = 1.0_wp
7779              ENDIF
7780
7781!
7782!--           Calculate canopy resistance. In case that c_veg is 0 (bare soils),
7783!--           this calculation is obsolete, as r_canopy is not used below.
7784!--           To do: check for very dry soil -> r_canopy goes to infinity
7785              surf_usm_h%r_canopy(m) = surf_usm_h%r_canopy_min(m) /                   &
7786                              ( surf_usm_h%lai(m) * f1 * f2 * f3 + 1.0E-20_wp )
7787
7788!
7789!--           Calculate the maximum possible liquid water amount on plants and
7790!--           bare surface. For vegetated surfaces, a maximum depth of 0.2 mm is
7791!--           assumed, while paved surfaces might hold up 1 mm of water. The
7792!--           liquid water fraction for paved surfaces is calculated after
7793!--           Noilhan & Planton (1989), while the ECMWF formulation is used for
7794!--           vegetated surfaces and bare soils.
7795              m_liq_max = m_max_depth * ( surf_usm_h%lai(m) )
7796              surf_usm_h%c_liq(m) = MIN( 1.0_wp, ( m_liq_usm_h%var_usm_1d(m) / m_liq_max )**0.67 )
7797!
7798!--           Calculate saturation specific humidity
7799              q_s = 0.622_wp * e_s / ( surface_pressure - e_s )
7800!
7801!--           In case of dewfall, set evapotranspiration to zero
7802!--           All super-saturated water is then removed from the air
7803              IF ( humidity  .AND.  q_s <= qv1 )  THEN
7804                 surf_usm_h%r_canopy(m) = 0.0_wp
7805              ENDIF
7806
7807!
7808!--           Calculate coefficients for the total evapotranspiration
7809!--           In case of water surface, set vegetation and soil fluxes to zero.
7810!--           For pavements, only evaporation of liquid water is possible.
7811              f_qsws_veg  = rho_lv *                                           &
7812                                ( 1.0_wp        - surf_usm_h%c_liq(m)    ) /   &
7813                                ( surf_usm_h%r_a_green(m) + surf_usm_h%r_canopy(m) )
7814              f_qsws_liq  = rho_lv * surf_usm_h%c_liq(m)   /                   &
7815                                  surf_usm_h%r_a_green(m)
7816       
7817              f_qsws = f_qsws_veg + f_qsws_liq
7818!
7819!--           Calculate derivative of q_s for Taylor series expansion
7820              e_s_dt = e_s * ( 17.269_wp / ( t_surf_green_h(m) - 35.86_wp) -   &
7821                               17.269_wp*( t_surf_green_h(m) - 273.16_wp)      &
7822                              / ( t_surf_green_h(m) - 35.86_wp)**2 )
7823       
7824              dq_s_dt = 0.622_wp * e_s_dt / ( surface_pressure - e_s_dt )
7825           ENDIF
7826!
7827!--        add LW up so that it can be removed in prognostic equation
7828           surf_usm_h%rad_net_l(m) = surf_usm_h%rad_sw_in(m)  -                &
7829                                     surf_usm_h%rad_sw_out(m) +                &
7830                                     surf_usm_h%rad_lw_in(m)  -                &
7831                                     surf_usm_h%rad_lw_out(m)
7832!
7833!--     numerator of the prognostic equation
7834!--     Todo: Adjust to tile approach. So far, emissivity for wall (element 0)
7835!--     is used
7836           coef_1 = surf_usm_h%rad_net_l(m) +                                  & 
7837                 ( 3.0_wp + 1.0_wp ) * surf_usm_h%emissivity(ind_veg_wall,m) * &
7838                                       sigma_sb * t_surf_wall_h(m) ** 4 +      & 
7839                                       f_shf * surf_usm_h%pt1(m) +             &
7840                                       lambda_surface * t_wall_h(nzb_wall,m)
7841           IF ( ( .NOT. spinup ) .AND. (surf_usm_h%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
7842              coef_window_1 = surf_usm_h%rad_net_l(m) +                           & 
7843                      ( 3.0_wp + 1.0_wp ) * surf_usm_h%emissivity(ind_wat_win,m)  &
7844                                          * sigma_sb * t_surf_window_h(m) ** 4 +  & 
7845                                          f_shf_window * surf_usm_h%pt1(m) +      &
7846                                          lambda_surface_window * t_window_h(nzb_wall,m)
7847           ENDIF                 
7848           IF ( ( humidity ) .AND. ( surf_usm_h%frac(ind_pav_green,m) > 0.0_wp ) )  THEN
7849                    coef_green_1 = surf_usm_h%rad_net_l(m) +                                 & 
7850                   ( 3.0_wp + 1.0_wp ) * surf_usm_h%emissivity(ind_pav_green,m) * sigma_sb * &
7851                                       t_surf_green_h(m) ** 4 +                  & 
7852                                          f_shf_green * surf_usm_h%pt1(m) + f_qsws * ( qv1 - q_s    &
7853                                          + dq_s_dt * t_surf_green_h(m) )        &
7854                                          +lambda_surface_green * t_green_h(nzb_wall,m)
7855           ELSE
7856           coef_green_1 = surf_usm_h%rad_net_l(m) +                            & 
7857                 ( 3.0_wp + 1.0_wp ) * surf_usm_h%emissivity(ind_pav_green,m) *&
7858                                       sigma_sb * t_surf_green_h(m) ** 4 +     & 
7859                                       f_shf_green * surf_usm_h%pt1(m) +       &
7860                                       lambda_surface_green * t_green_h(nzb_wall,m)
7861          ENDIF
7862!
7863!--        denominator of the prognostic equation
7864           coef_2 = 4.0_wp * surf_usm_h%emissivity(ind_veg_wall,m) *           &
7865                             sigma_sb * t_surf_wall_h(m) ** 3                  &
7866                           + lambda_surface + f_shf / exner(k)
7867           IF ( ( .NOT. spinup ) .AND. ( surf_usm_h%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
7868              coef_window_2 = 4.0_wp * surf_usm_h%emissivity(ind_wat_win,m) *     &
7869                                sigma_sb * t_surf_window_h(m) ** 3                &
7870                              + lambda_surface_window + f_shf_window / exner(k)
7871           ENDIF
7872           IF ( ( humidity ) .AND. ( surf_usm_h%frac(ind_pav_green,m) > 0.0_wp ) )  THEN
7873              coef_green_2 = 4.0_wp * surf_usm_h%emissivity(ind_pav_green,m) * sigma_sb *    &
7874                                t_surf_green_h(m) ** 3 + f_qsws * dq_s_dt                    &
7875                              + lambda_surface_green + f_shf_green / exner(k)
7876           ELSE
7877           coef_green_2 = 4.0_wp * surf_usm_h%emissivity(ind_pav_green,m) * sigma_sb *    &
7878                             t_surf_green_h(m) ** 3                                       &
7879                           + lambda_surface_green + f_shf_green / exner(k)
7880           ENDIF
7881!
7882!--        implicit solution when the surface layer has no heat capacity,
7883!--        otherwise use RK3 scheme.
7884           t_surf_wall_h_p(m) = ( coef_1 * dt_3d * tsc(2) +                        &
7885                             surf_usm_h%c_surface(m) * t_surf_wall_h(m) ) /        & 
7886                           ( surf_usm_h%c_surface(m) + coef_2 * dt_3d * tsc(2) ) 
7887           IF ((.NOT. spinup).AND.(surf_usm_h%frac(ind_wat_win,m) > 0.0_wp)) THEN
7888              t_surf_window_h_p(m) = ( coef_window_1 * dt_3d * tsc(2) +                        &
7889                                surf_usm_h%c_surface_window(m) * t_surf_window_h(m) ) /        & 
7890                              ( surf_usm_h%c_surface_window(m) + coef_window_2 * dt_3d * tsc(2) )
7891           ENDIF
7892           t_surf_green_h_p(m) = ( coef_green_1 * dt_3d * tsc(2) +                        &
7893                             surf_usm_h%c_surface_green(m) * t_surf_green_h(m) ) /        & 
7894                           ( surf_usm_h%c_surface_green(m) + coef_green_2 * dt_3d * tsc(2) ) 
7895!
7896!--        add RK3 term
7897           t_surf_wall_h_p(m) = t_surf_wall_h_p(m) + dt_3d * tsc(3) *         &
7898                           surf_usm_h%tt_surface_wall_m(m)
7899
7900           t_surf_window_h_p(m) = t_surf_window_h_p(m) + dt_3d * tsc(3) *     &
7901                           surf_usm_h%tt_surface_window_m(m)
7902
7903           t_surf_green_h_p(m) = t_surf_green_h_p(m) + dt_3d * tsc(3) *       &
7904                           surf_usm_h%tt_surface_green_m(m)
7905!
7906!--        Store surface temperature on pt_surface. Further, in case humidity is used
7907!--        store also vpt_surface, which is, due to the lack of moisture on roofs simply
7908!--        assumed to be the surface temperature.
7909           surf_usm_h%pt_surface(m) = ( surf_usm_h%frac(ind_veg_wall,m) * t_surf_wall_h_p(m)   &
7910                               + surf_usm_h%frac(ind_wat_win,m) * t_surf_window_h_p(m)         &
7911                               + surf_usm_h%frac(ind_pav_green,m) * t_surf_green_h_p(m) )      &
7912                               / exner(k)
7913                               
7914           IF ( humidity )  surf_usm_h%vpt_surface(m) =                        &
7915                                                   surf_usm_h%pt_surface(m)
7916!
7917!--        calculate true tendency
7918           stend_wall = ( t_surf_wall_h_p(m) - t_surf_wall_h(m) - dt_3d * tsc(3) *              &
7919                     surf_usm_h%tt_surface_wall_m(m)) / ( dt_3d  * tsc(2) )
7920           stend_window = ( t_surf_window_h_p(m) - t_surf_window_h(m) - dt_3d * tsc(3) *        &
7921                     surf_usm_h%tt_surface_window_m(m)) / ( dt_3d  * tsc(2) )
7922           stend_green = ( t_surf_green_h_p(m) - t_surf_green_h(m) - dt_3d * tsc(3) *           &
7923                     surf_usm_h%tt_surface_green_m(m)) / ( dt_3d  * tsc(2) )
7924!
7925!--        calculate t_surf tendencies for the next Runge-Kutta step
7926           IF ( timestep_scheme(1:5) == 'runge' )  THEN
7927              IF ( intermediate_timestep_count == 1 )  THEN
7928                 surf_usm_h%tt_surface_wall_m(m) = stend_wall
7929                 surf_usm_h%tt_surface_window_m(m) = stend_window
7930                 surf_usm_h%tt_surface_green_m(m) = stend_green
7931              ELSEIF ( intermediate_timestep_count <                          &
7932                        intermediate_timestep_count_max )  THEN
7933                 surf_usm_h%tt_surface_wall_m(m) = -9.5625_wp * stend_wall +       &
7934                                     5.3125_wp * surf_usm_h%tt_surface_wall_m(m)
7935                 surf_usm_h%tt_surface_window_m(m) = -9.5625_wp * stend_window +   &
7936                                     5.3125_wp * surf_usm_h%tt_surface_window_m(m)
7937                 surf_usm_h%tt_surface_green_m(m) = -9.5625_wp * stend_green +     &
7938                                     5.3125_wp * surf_usm_h%tt_surface_green_m(m)
7939              ENDIF
7940           ENDIF
7941!
7942!--        in case of fast changes in the skin temperature, it is required to
7943!--        update the radiative fluxes in order to keep the solution stable
7944           IF ( ( ( ABS( t_surf_wall_h_p(m)   - t_surf_wall_h(m) )   > 1.0_wp )   .OR. &
7945                (   ABS( t_surf_green_h_p(m)  - t_surf_green_h(m) )  > 1.0_wp )   .OR. &
7946                (   ABS( t_surf_window_h_p(m) - t_surf_window_h(m) ) > 1.0_wp ) )      &
7947                   .AND.  unscheduled_radiation_calls  )  THEN
7948              force_radiation_call_l = .TRUE.
7949           ENDIF
7950!
7951!--        calculate fluxes
7952!--        rad_net_l is never used!
7953           surf_usm_h%rad_net_l(m) = surf_usm_h%rad_net_l(m) +                           &
7954                                     surf_usm_h%frac(ind_veg_wall,m) *                   &
7955                                     sigma_sb * surf_usm_h%emissivity(ind_veg_wall,m) *  &
7956                                     ( t_surf_wall_h_p(m)**4 - t_surf_wall_h(m)**4 )     &
7957                                    + surf_usm_h%frac(ind_wat_win,m) *                   &
7958                                     sigma_sb * surf_usm_h%emissivity(ind_wat_win,m) *   &
7959                                     ( t_surf_window_h_p(m)**4 - t_surf_window_h(m)**4 ) &
7960                                    + surf_usm_h%frac(ind_pav_green,m) *                 &
7961                                     sigma_sb * surf_usm_h%emissivity(ind_pav_green,m) * &
7962                                     ( t_surf_green_h_p(m)**4 - t_surf_green_h(m)**4 )
7963
7964           surf_usm_h%wghf_eb(m)   = lambda_surface *                                    &
7965                                      ( t_surf_wall_h_p(m) - t_wall_h(nzb_wall,m) )
7966           surf_usm_h%wghf_eb_green(m)  = lambda_surface_green *                         &
7967                                          ( t_surf_green_h_p(m) - t_green_h(nzb_wall,m) )
7968           surf_usm_h%wghf_eb_window(m) = lambda_surface_window *                        &
7969                                           ( t_surf_window_h_p(m) - t_window_h(nzb_wall,m) )
7970
7971!
7972!--        ground/wall/roof surface heat flux
7973           surf_usm_h%wshf_eb(m)   = - f_shf  * ( surf_usm_h%pt1(m) - t_surf_wall_h_p(m) / exner(k) ) *          &
7974                                       surf_usm_h%frac(ind_veg_wall,m)         &
7975                                     - f_shf_window  * ( surf_usm_h%pt1(m) - t_surf_window_h_p(m) / exner(k) ) * &
7976                                       surf_usm_h%frac(ind_wat_win,m)          &
7977                                     - f_shf_green  * ( surf_usm_h%pt1(m) - t_surf_green_h_p(m) / exner(k) ) *   &
7978                                       surf_usm_h%frac(ind_pav_green,m)
7979!           
7980!--        store kinematic surface heat fluxes for utilization in other processes
7981!--        diffusion_s, surface_layer_fluxes,...
7982           surf_usm_h%shf(m) = surf_usm_h%wshf_eb(m) / c_p
7983!
7984!--        If the indoor model is applied, further add waste heat from buildings to the
7985!--        kinematic flux.
7986           IF ( indoor_model )  THEN
7987              surf_usm_h%shf(m) = surf_usm_h%shf(m) + surf_usm_h%waste_heat(m) / c_p
7988           ENDIF
7989     
7990
7991           IF (surf_usm_h%frac(ind_pav_green,m) > 0.0_wp) THEN
7992
7993              IF ( humidity )  THEN
7994                 surf_usm_h%qsws_eb(m)  = - f_qsws * ( qv1 - q_s + dq_s_dt                  &
7995                                 * t_surf_green_h(m) - dq_s_dt *               &
7996                                   t_surf_green_h_p(m) )
7997       
7998                 surf_usm_h%qsws(m) = surf_usm_h%qsws_eb(m) / rho_lv
7999       
8000                 surf_usm_h%qsws_veg(m)  = - f_qsws_veg  * ( qv1 - q_s                      &
8001                                     + dq_s_dt * t_surf_green_h(m) - dq_s_dt   &
8002                                     * t_surf_green_h_p(m) )
8003       
8004                 surf_usm_h%qsws_liq(m)  = - f_qsws_liq  * ( qv1 - q_s                      &
8005                                     + dq_s_dt * t_surf_green_h(m) - dq_s_dt   &
8006                                     * t_surf_green_h_p(m) )
8007              ENDIF
8008 
8009!
8010!--           Calculate the true surface resistance
8011              IF ( .NOT.  humidity )  THEN
8012                 surf_usm_h%r_s(m) = 1.0E10_wp
8013              ELSE
8014                 surf_usm_h%r_s(m) = - rho_lv * ( qv1 - q_s + dq_s_dt                       &
8015                                 *  t_surf_green_h(m) - dq_s_dt *              &
8016                                   t_surf_green_h_p(m) ) /                     &
8017                                   (surf_usm_h%qsws(m) + 1.0E-20)  - surf_usm_h%r_a_green(m)
8018              ENDIF
8019 
8020!
8021!--           Calculate change in liquid water reservoir due to dew fall or
8022!--           evaporation of liquid water
8023              IF ( humidity )  THEN
8024!
8025!--              If precipitation is activated, add rain water to qsws_liq
8026!--              and qsws_soil according the the vegetation coverage.
8027!--              precipitation_rate is given in mm.
8028                 IF ( precipitation )  THEN
8029
8030!
8031!--                 Add precipitation to liquid water reservoir, if possible.
8032!--                 Otherwise, add the water to soil. In case of
8033!--                 pavements, the exceeding water amount is implicitely removed
8034!--                 as runoff as qsws_soil is then not used in the soil model
8035                    IF ( m_liq_usm_h%var_usm_1d(m) /= m_liq_max )  THEN
8036                       surf_usm_h%qsws_liq(m) = surf_usm_h%qsws_liq(m)                &
8037                                        + surf_usm_h%frac(ind_pav_green,m) * prr(k+k_off,j+j_off,i+i_off)&
8038                                        * hyrho(k+k_off)                              &
8039                                        * 0.001_wp * rho_l * l_v
8040                   ENDIF
8041
8042                 ENDIF
8043
8044!
8045!--              If the air is saturated, check the reservoir water level
8046                 IF ( surf_usm_h%qsws(m) < 0.0_wp )  THEN
8047!
8048!--                 Check if reservoir is full (avoid values > m_liq_max)
8049!--                 In that case, qsws_liq goes to qsws_soil. In this
8050!--                 case qsws_veg is zero anyway (because c_liq = 1),       
8051!--                 so that tend is zero and no further check is needed
8052                    IF ( m_liq_usm_h%var_usm_1d(m) == m_liq_max )  THEN
8053!                      surf_usm_h%qsws_soil(m) = surf_usm_h%qsws_soil(m) + surf_usm_h%qsws_liq(m)
8054                       surf_usm_h%qsws_liq(m)  = 0.0_wp
8055                    ENDIF
8056
8057!
8058!--                 In case qsws_veg becomes negative (unphysical behavior),
8059!--                 let the water enter the liquid water reservoir as dew on the
8060!--                 plant
8061                    IF ( surf_usm_h%qsws_veg(m) < 0.0_wp )  THEN
8062                       surf_usm_h%qsws_liq(m) = surf_usm_h%qsws_liq(m) + surf_usm_h%qsws_veg(m)
8063                       surf_usm_h%qsws_veg(m) = 0.0_wp
8064                    ENDIF
8065                 ENDIF                   
8066 
8067                 surf_usm_h%qsws(m) = surf_usm_h%qsws(m) / l_v
8068       
8069                 tend = - surf_usm_h%qsws_liq(m) * drho_l_lv
8070                 m_liq_usm_h_p%var_usm_1d(m) = m_liq_usm_h%var_usm_1d(m) + dt_3d *    &
8071                                               ( tsc(2) * tend +                      &
8072                                                 tsc(3) * tm_liq_usm_h_m%var_usm_1d(m) )
8073!
8074!--             Check if reservoir is overfull -> reduce to maximum
8075!--             (conservation of water is violated here)
8076                 m_liq_usm_h_p%var_usm_1d(m) = MIN( m_liq_usm_h_p%var_usm_1d(m),m_liq_max )
8077 
8078!
8079!--             Check if reservoir is empty (avoid values < 0.0)
8080!--             (conservation of water is violated here)
8081                 m_liq_usm_h_p%var_usm_1d(m) = MAX( m_liq_usm_h_p%var_usm_1d(m), 0.0_wp )
8082!
8083!--             Calculate m_liq tendencies for the next Runge-Kutta step
8084                 IF ( timestep_scheme(1:5) == 'runge' )  THEN
8085                    IF ( intermediate_timestep_count == 1 )  THEN
8086                       tm_liq_usm_h_m%var_usm_1d(m) = tend
8087                    ELSEIF ( intermediate_timestep_count <                            &
8088                             intermediate_timestep_count_max )  THEN
8089                       tm_liq_usm_h_m%var_usm_1d(m) = -9.5625_wp * tend +             &
8090                                                     5.3125_wp * tm_liq_usm_h_m%var_usm_1d(m)
8091                    ENDIF
8092                 ENDIF
8093 
8094              ENDIF
8095           ELSE
8096              surf_usm_h%r_s(m) = 1.0E10_wp
8097           ENDIF
8098 
8099       ENDDO
8100!
8101!--    Now, treat vertical surface elements
8102       !$OMP DO SCHEDULE (STATIC)
8103       DO  l = 0, 3
8104           DO  m = 1, surf_usm_v(l)%ns
8105!
8106!--          Get indices of respective grid point
8107              i = surf_usm_v(l)%i(m)
8108              j = surf_usm_v(l)%j(m)
8109              k = surf_usm_v(l)%k(m)
8110 
8111!
8112!--          TODO - how to calculate lambda_surface for horizontal (??? do you mean verical ???) surfaces
8113!--          (lambda_surface is set according to stratification in land surface model).
8114!--          Please note, for vertical surfaces no ol is defined, since
8115!--          stratification is not considered in this case.
8116              lambda_surface = surf_usm_v(l)%lambda_surf(m)
8117              lambda_surface_window = surf_usm_v(l)%lambda_surf_window(m)
8118              lambda_surface_green = surf_usm_v(l)%lambda_surf_green(m)
8119 
8120!            pt1  = pt(k,j,i)
8121              IF ( humidity )  THEN
8122                 qv1 = q(k,j,i)
8123              ELSE
8124                 qv1 = 0.0_wp
8125              ENDIF
8126!
8127!--          calculate rho * c_p coefficient at wall layer
8128              rho_cp  = c_p * hyp(k) / ( r_d * surf_usm_v(l)%pt1(m) * exner(k) )
8129             
8130              IF (surf_usm_v(l)%frac(1,m) > 0.0_wp )  THEN
8131!
8132!--            Calculate frequently used parameters
8133                 rho_lv    = rho_cp / c_p * l_v
8134                 drho_l_lv = 1.0_wp / (rho_l * l_v)
8135              ENDIF
8136 
8137!--          Calculation of r_a for vertical surfaces
8138!--
8139!--          heat transfer coefficient for forced convection along vertical walls
8140!--          follows formulation in TUF3d model (Krayenhoff & Voogt, 2006)
8141!--           
8142!--          H = httc (Tsfc - Tair)
8143!--          httc = rw * (11.8 + 4.2 * Ueff) - 4.0
8144!--           
8145!--                rw: wall patch roughness relative to 1.0 for concrete
8146!--                Ueff: effective wind speed
8147!--                - 4.0 is a reduction of Rowley et al (1930) formulation based on
8148!--                Cole and Sturrock (1977)
8149!--           
8150!--                Ucan: Canyon wind speed
8151!--                wstar: convective velocity
8152!--                Qs: surface heat flux
8153!--                zH: height of the convective layer
8154!--                wstar = (g/Tcan*Qs*zH)**(1./3.)
8155!--          Effective velocity components must always
8156!--          be defined at scalar grid point. The wall normal component is
8157!--          obtained by simple linear interpolation. ( An alternative would
8158!--          be an logarithmic interpolation. )
8159!--          Parameter roughness_concrete (default value = 0.001) is used
8160!--          to calculation of roughness relative to concrete
8161              surf_usm_v(l)%r_a(m) = rho_cp / ( surf_usm_v(l)%z0(m) /           &
8162                         roughness_concrete * ( 11.8_wp + 4.2_wp *              &
8163                         SQRT( MAX( ( ( u(k,j,i) + u(k,j,i+1) ) * 0.5_wp )**2 + &
8164                                    ( ( v(k,j,i) + v(k,j+1,i) ) * 0.5_wp )**2 + &
8165                                    ( ( w(k,j,i) + w(k-1,j,i) ) * 0.5_wp )**2,  &
8166                               0.01_wp ) )                                      &
8167                            )  - 4.0_wp  ) 
8168!
8169!--          Limit aerodynamic resistance
8170              IF ( surf_usm_v(l)%r_a(m) < 1.0_wp )  surf_usm_v(l)%r_a(m) = 1.0_wp   
8171             
8172                           
8173              f_shf         = rho_cp / surf_usm_v(l)%r_a(m)
8174              f_shf_window  = rho_cp / surf_usm_v(l)%r_a(m)
8175              f_shf_green   = rho_cp / surf_usm_v(l)%r_a(m)
8176 
8177
8178              IF ( surf_usm_v(l)%frac(1,m) > 0.0_wp ) THEN
8179!
8180!--             Adapted from LSM:
8181!--             Second step: calculate canopy resistance r_canopy
8182!--             f1-f3 here are defined as 1/f1-f3 as in ECMWF documentation
8183!--             f1: correction for incoming shortwave radiation (stomata close at
8184!--             night)
8185                 f1 = MIN( 1.0_wp, ( 0.004_wp * surf_usm_v(l)%rad_sw_in(m) + 0.05_wp ) / &
8186                                  (0.81_wp * (0.004_wp * surf_usm_v(l)%rad_sw_in(m)      &
8187                                   + 1.0_wp)) )
8188!
8189!--             f2: correction for soil moisture availability to plants (the
8190!--             integrated soil moisture must thus be considered here)
8191!--             f2 = 0 for very dry soils
8192 
8193                 f2=1.0_wp
8194 
8195!
8196!--              Calculate water vapour pressure at saturation
8197                 e_s = 0.01_wp * 610.78_wp * EXP( 17.269_wp * (  t_surf_green_v_p(l)%t(m) &
8198                               - 273.16_wp ) / (  t_surf_green_v_p(l)%t(m) - 35.86_wp ) )
8199!
8200!--              f3: correction for vapour pressure deficit
8201                 IF ( surf_usm_v(l)%g_d(m) /= 0.0_wp )  THEN
8202!
8203!--                 Calculate vapour pressure
8204                    e  = qv1 * surface_pressure / ( qv1 + 0.622_wp )
8205                    f3 = EXP ( - surf_usm_v(l)%g_d(m) * (e_s - e) )
8206                 ELSE
8207                    f3 = 1.0_wp
8208                 ENDIF
8209!
8210!--              Calculate canopy resistance. In case that c_veg is 0 (bare soils),
8211!--              this calculation is obsolete, as r_canopy is not used below.
8212!--              To do: check for very dry soil -> r_canopy goes to infinity
8213                 surf_usm_v(l)%r_canopy(m) = surf_usm_v(l)%r_canopy_min(m) /                  &
8214                                        ( surf_usm_v(l)%lai(m) * f1 * f2 * f3 + 1.0E-20_wp )
8215                               
8216!
8217!--              Calculate saturation specific humidity
8218                 q_s = 0.622_wp * e_s / ( surface_pressure - e_s )
8219!
8220!--              In case of dewfall, set evapotranspiration to zero
8221!--              All super-saturated water is then removed from the air
8222                 IF ( humidity  .AND.  q_s <= qv1 )  THEN
8223                    surf_usm_v(l)%r_canopy(m) = 0.0_wp
8224                 ENDIF
8225 
8226!
8227!--              Calculate coefficients for the total evapotranspiration
8228!--              In case of water surface, set vegetation and soil fluxes to zero.
8229!--              For pavements, only evaporation of liquid water is possible.
8230                 f_qsws_veg  = rho_lv *                                &
8231                                   ( 1.0_wp        - 0.0_wp ) / & !surf_usm_h%c_liq(m)    ) /   &
8232                                   ( surf_usm_v(l)%r_a(m) + surf_usm_v(l)%r_canopy(m) )
8233!                f_qsws_liq  = rho_lv * surf_usm_h%c_liq(m)   /             &
8234!                              surf_usm_h%r_a_green(m)
8235         
8236                 f_qsws = f_qsws_veg! + f_qsws_liq
8237!
8238!--              Calculate derivative of q_s for Taylor series expansion
8239                 e_s_dt = e_s * ( 17.269_wp / ( t_surf_green_v_p(l)%t(m) - 35.86_wp) -   &
8240                                  17.269_wp*( t_surf_green_v_p(l)%t(m) - 273.16_wp)      &
8241                                 / ( t_surf_green_v_p(l)%t(m) - 35.86_wp)**2 )
8242         
8243                 dq_s_dt = 0.622_wp * e_s_dt / ( surface_pressure - e_s_dt )
8244              ENDIF
8245
8246!
8247!--           add LW up so that it can be removed in prognostic equation
8248              surf_usm_v(l)%rad_net_l(m) = surf_usm_v(l)%rad_sw_in(m)  -        &
8249                                           surf_usm_v(l)%rad_sw_out(m) +        &
8250                                           surf_usm_v(l)%rad_lw_in(m)  -        &
8251                                           surf_usm_v(l)%rad_lw_out(m)
8252!
8253!--           numerator of the prognostic equation
8254              coef_1 = surf_usm_v(l)%rad_net_l(m) +                             & ! coef +1 corresponds to -lwout
8255                                                                                  ! included in calculation of radnet_l
8256              ( 3.0_wp + 1.0_wp ) * surf_usm_v(l)%emissivity(ind_veg_wall,m) *  &
8257                                      sigma_sb *  t_surf_wall_v(l)%t(m) ** 4 +  & 
8258                                      f_shf * surf_usm_v(l)%pt1(m) +            &
8259                                      lambda_surface * t_wall_v(l)%t(nzb_wall,m)
8260              IF ( ( .NOT. spinup ) .AND. ( surf_usm_v(l)%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
8261                 coef_window_1 = surf_usm_v(l)%rad_net_l(m) +                   & ! coef +1 corresponds to -lwout
8262                                                                                  ! included in calculation of radnet_l
8263                ( 3.0_wp + 1.0_wp ) * surf_usm_v(l)%emissivity(ind_wat_win,m) * &
8264                                      sigma_sb * t_surf_window_v(l)%t(m) ** 4 + & 
8265                                      f_shf * surf_usm_v(l)%pt1(m) +            &
8266                                      lambda_surface_window * t_window_v(l)%t(nzb_wall,m)
8267              ENDIF
8268              IF ( ( humidity ) .AND. ( surf_usm_v(l)%frac(ind_pav_green,m) > 0.0_wp ) )  THEN
8269                 coef_green_1 = surf_usm_v(l)%rad_net_l(m) +                      & ! coef +1 corresponds to -lwout
8270                                                                                    ! included in calculation of radnet_l
8271                 ( 3.0_wp + 1.0_wp ) * surf_usm_v(l)%emissivity(ind_pav_green,m) * sigma_sb *  &
8272                                      t_surf_green_v(l)%t(m) ** 4 +               & 
8273                                      f_shf * surf_usm_v(l)%pt1(m) +     f_qsws * ( qv1 - q_s  &
8274                                           + dq_s_dt * t_surf_green_v(l)%t(m) ) +              &
8275                                      lambda_surface_green * t_wall_v(l)%t(nzb_wall,m)
8276              ELSE
8277                coef_green_1 = surf_usm_v(l)%rad_net_l(m) +                       & ! coef +1 corresponds to -lwout included
8278                                                                                    ! in calculation of radnet_l
8279                ( 3.0_wp + 1.0_wp ) * surf_usm_v(l)%emissivity(ind_pav_green,m) * sigma_sb *  &
8280                                      t_surf_green_v(l)%t(m) ** 4 +               & 
8281                                      f_shf * surf_usm_v(l)%pt1(m) +              &
8282                                      lambda_surface_green * t_wall_v(l)%t(nzb_wall,m)
8283              ENDIF
8284                                     
8285!
8286!--           denominator of the prognostic equation
8287              coef_2 = 4.0_wp * surf_usm_v(l)%emissivity(ind_veg_wall,m) * sigma_sb *   &
8288                                 t_surf_wall_v(l)%t(m) ** 3                             &
8289                               + lambda_surface + f_shf / exner(k) 
8290              IF ( ( .NOT. spinup ) .AND. ( surf_usm_v(l)%frac(ind_wat_win,m) > 0.0_wp ) ) THEN             
8291                 coef_window_2 = 4.0_wp * surf_usm_v(l)%emissivity(ind_wat_win,m) * sigma_sb *       &
8292                                   t_surf_window_v(l)%t(m) ** 3                         &
8293                                 + lambda_surface_window + f_shf / exner(k)
8294              ENDIF
8295              IF ( ( humidity ) .AND. ( surf_usm_v(l)%frac(ind_pav_green,m) > 0.0_wp ) )  THEN
8296                  coef_green_2 = 4.0_wp * surf_usm_v(l)%emissivity(ind_pav_green,m) * sigma_sb *     &
8297                                   t_surf_green_v(l)%t(m) ** 3  + f_qsws * dq_s_dt      &
8298                                 + lambda_surface_green + f_shf / exner(k)
8299              ELSE
8300                 coef_green_2 = 4.0_wp * surf_usm_v(l)%emissivity(ind_pav_green,m) * sigma_sb *      &
8301                                   t_surf_green_v(l)%t(m) ** 3                          &
8302                                 + lambda_surface_green + f_shf / exner(k)
8303              ENDIF
8304!
8305!--           implicit solution when the surface layer has no heat capacity,
8306!--           otherwise use RK3 scheme.
8307              t_surf_wall_v_p(l)%t(m) = ( coef_1 * dt_3d * tsc(2) +                 &
8308                             surf_usm_v(l)%c_surface(m) * t_surf_wall_v(l)%t(m) ) / & 
8309                             ( surf_usm_v(l)%c_surface(m) + coef_2 * dt_3d * tsc(2) ) 
8310              IF ( ( .NOT. spinup ) .AND. ( surf_usm_v(l)%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
8311                 t_surf_window_v_p(l)%t(m) = ( coef_window_1 * dt_3d * tsc(2) +                 &
8312                                surf_usm_v(l)%c_surface_window(m) * t_surf_window_v(l)%t(m) ) / & 
8313                              ( surf_usm_v(l)%c_surface_window(m) + coef_window_2 * dt_3d * tsc(2) ) 
8314              ENDIF
8315              t_surf_green_v_p(l)%t(m) = ( coef_green_1 * dt_3d * tsc(2) +                 &
8316                             surf_usm_v(l)%c_surface_green(m) * t_surf_green_v(l)%t(m) ) / & 
8317                           ( surf_usm_v(l)%c_surface_green(m) + coef_green_2 * dt_3d * tsc(2) ) 
8318!
8319!--           add RK3 term
8320              t_surf_wall_v_p(l)%t(m) = t_surf_wall_v_p(l)%t(m) + dt_3d * tsc(3) *         &
8321                                surf_usm_v(l)%tt_surface_wall_m(m)
8322              t_surf_window_v_p(l)%t(m) = t_surf_window_v_p(l)%t(m) + dt_3d * tsc(3) *     &
8323                                surf_usm_v(l)%tt_surface_window_m(m)
8324              t_surf_green_v_p(l)%t(m) = t_surf_green_v_p(l)%t(m) + dt_3d * tsc(3) *       &
8325                                 surf_usm_v(l)%tt_surface_green_m(m)
8326!
8327!--           Store surface temperature. Further, in case humidity is used
8328!--           store also vpt_surface, which is, due to the lack of moisture on roofs simply
8329!--           assumed to be the surface temperature.     
8330              surf_usm_v(l)%pt_surface(m) =  ( surf_usm_v(l)%frac(ind_veg_wall,m) * t_surf_wall_v_p(l)%t(m)  &
8331                                      + surf_usm_v(l)%frac(ind_wat_win,m) * t_surf_window_v_p(l)%t(m)        &
8332                                      + surf_usm_v(l)%frac(ind_pav_green,m) * t_surf_green_v_p(l)%t(m) )     &
8333                                      / exner(k)
8334                                       
8335              IF ( humidity )  surf_usm_v(l)%vpt_surface(m) =                  &
8336                                                     surf_usm_v(l)%pt_surface(m)
8337!
8338!--           calculate true tendency
8339              stend_wall = ( t_surf_wall_v_p(l)%t(m) - t_surf_wall_v(l)%t(m) - dt_3d * tsc(3) *      &
8340                        surf_usm_v(l)%tt_surface_wall_m(m) ) / ( dt_3d  * tsc(2) )
8341              stend_window = ( t_surf_window_v_p(l)%t(m) - t_surf_window_v(l)%t(m) - dt_3d * tsc(3) *&
8342                        surf_usm_v(l)%tt_surface_window_m(m) ) / ( dt_3d  * tsc(2) )
8343              stend_green = ( t_surf_green_v_p(l)%t(m) - t_surf_green_v(l)%t(m) - dt_3d * tsc(3) *   &
8344                        surf_usm_v(l)%tt_surface_green_m(m) ) / ( dt_3d  * tsc(2) )
8345
8346!
8347!--           calculate t_surf_* tendencies for the next Runge-Kutta step
8348              IF ( timestep_scheme(1:5) == 'runge' )  THEN
8349                 IF ( intermediate_timestep_count == 1 )  THEN
8350                    surf_usm_v(l)%tt_surface_wall_m(m) = stend_wall
8351                    surf_usm_v(l)%tt_surface_window_m(m) = stend_window
8352                    surf_usm_v(l)%tt_surface_green_m(m) = stend_green
8353                 ELSEIF ( intermediate_timestep_count <                                 &
8354                          intermediate_timestep_count_max )  THEN
8355                    surf_usm_v(l)%tt_surface_wall_m(m) = -9.5625_wp * stend_wall +      &
8356                                     5.3125_wp * surf_usm_v(l)%tt_surface_wall_m(m)
8357                    surf_usm_v(l)%tt_surface_green_m(m) = -9.5625_wp * stend_green +    &
8358                                     5.3125_wp * surf_usm_v(l)%tt_surface_green_m(m)
8359                    surf_usm_v(l)%tt_surface_window_m(m) = -9.5625_wp * stend_window +  &
8360                                     5.3125_wp * surf_usm_v(l)%tt_surface_window_m(m)
8361                 ENDIF
8362              ENDIF
8363
8364!
8365!--           in case of fast changes in the skin temperature, it is required to
8366!--           update the radiative fluxes in order to keep the solution stable
8367 
8368              IF ( ( ( ABS( t_surf_wall_v_p(l)%t(m)   - t_surf_wall_v(l)%t(m) )   > 1.0_wp ) .OR. &
8369                   (   ABS( t_surf_green_v_p(l)%t(m)  - t_surf_green_v(l)%t(m) )  > 1.0_wp ) .OR. &
8370                   (   ABS( t_surf_window_v_p(l)%t(m) - t_surf_window_v(l)%t(m) ) > 1.0_wp ) )    &
8371                      .AND.  unscheduled_radiation_calls )  THEN
8372                 force_radiation_call_l = .TRUE.
8373              ENDIF
8374
8375!
8376!--           calculate fluxes
8377!--           prognostic rad_net_l is used just for output!           
8378              surf_usm_v(l)%rad_net_l(m) = surf_usm_v(l)%frac(ind_veg_wall,m) *                      &
8379                                           ( surf_usm_v(l)%rad_net_l(m) +                            &
8380                                           3.0_wp * sigma_sb *                                       &
8381                                           t_surf_wall_v(l)%t(m)**4 - 4.0_wp * sigma_sb *            &
8382                                           t_surf_wall_v(l)%t(m)**3 * t_surf_wall_v_p(l)%t(m) )      &
8383                                         + surf_usm_v(l)%frac(ind_wat_win,m) *                       &
8384                                           ( surf_usm_v(l)%rad_net_l(m) +                            &
8385                                           3.0_wp * sigma_sb *                                       &
8386                                           t_surf_window_v(l)%t(m)**4 - 4.0_wp * sigma_sb *          &
8387                                           t_surf_window_v(l)%t(m)**3 * t_surf_window_v_p(l)%t(m) )  &
8388                                         + surf_usm_v(l)%frac(ind_pav_green,m) *                     &
8389                                           ( surf_usm_v(l)%rad_net_l(m) +                            &
8390                                           3.0_wp * sigma_sb *                                       &
8391                                           t_surf_green_v(l)%t(m)**4 - 4.0_wp * sigma_sb *           &
8392                                           t_surf_green_v(l)%t(m)**3 * t_surf_green_v_p(l)%t(m) )
8393
8394              surf_usm_v(l)%wghf_eb_window(m) = lambda_surface_window * &
8395                                                ( t_surf_window_v_p(l)%t(m) - t_window_v(l)%t(nzb_wall,m) )
8396              surf_usm_v(l)%wghf_eb(m)   = lambda_surface *             &
8397                                                ( t_surf_wall_v_p(l)%t(m) - t_wall_v(l)%t(nzb_wall,m) )
8398              surf_usm_v(l)%wghf_eb_green(m)  = lambda_surface_green *  &
8399                                                ( t_surf_green_v_p(l)%t(m) - t_green_v(l)%t(nzb_wall,m) )
8400
8401!
8402!--           ground/wall/roof surface heat flux
8403              surf_usm_v(l)%wshf_eb(m)   =                                     &
8404                 - f_shf  * ( surf_usm_v(l)%pt1(m) -                           &
8405                 t_surf_wall_v_p(l)%t(m) / exner(k) ) * surf_usm_v(l)%frac(ind_veg_wall,m)       &
8406                 - f_shf_window  * ( surf_usm_v(l)%pt1(m) -                    &
8407                 t_surf_window_v_p(l)%t(m) / exner(k) ) * surf_usm_v(l)%frac(ind_wat_win,m)&
8408                 - f_shf_green  * ( surf_usm_v(l)%pt1(m) -                     &
8409                 t_surf_green_v_p(l)%t(m) / exner(k) ) * surf_usm_v(l)%frac(ind_pav_green,m)
8410
8411!           
8412!--           store kinematic surface heat fluxes for utilization in other processes
8413!--           diffusion_s, surface_layer_fluxes,...
8414              surf_usm_v(l)%shf(m) = surf_usm_v(l)%wshf_eb(m) / c_p
8415!
8416!--           If the indoor model is applied, further add waste heat from buildings to the
8417!--           kinematic flux.
8418              IF ( indoor_model )  THEN
8419                 surf_usm_v(l)%shf(m) = surf_usm_v(l)%shf(m) +                       &
8420                                        surf_usm_v(l)%waste_heat(m) / c_p
8421              ENDIF             
8422
8423              IF ( surf_usm_v(l)%frac(ind_pav_green,m) > 0.0_wp ) THEN
8424 
8425
8426                 IF ( humidity )  THEN
8427                    surf_usm_v(l)%qsws_eb(m)  = - f_qsws * ( qv1 - q_s + dq_s_dt       &
8428                                    * t_surf_green_v(l)%t(m) - dq_s_dt *               &
8429                                      t_surf_green_v_p(l)%t(m) )
8430         
8431                    surf_usm_v(l)%qsws(m) = surf_usm_v(l)%qsws_eb(m) / rho_lv
8432         
8433                    surf_usm_v(l)%qsws_veg(m)  = - f_qsws_veg  * ( qv1 - q_s           &
8434                                        + dq_s_dt * t_surf_green_v(l)%t(m) - dq_s_dt   &
8435                                        * t_surf_green_v_p(l)%t(m) )
8436         
8437!                    surf_usm_h%qsws_liq(m)  = - f_qsws_liq  * ( qv1 - q_s         &
8438!                                        + dq_s_dt * t_surf_green_h(m) - dq_s_dt   &
8439!                                        * t_surf_green_h_p(m) )
8440                 ENDIF
8441 
8442!
8443!--              Calculate the true surface resistance
8444                 IF ( .NOT.  humidity )  THEN
8445                    surf_usm_v(l)%r_s(m) = 1.0E10_wp
8446                 ELSE
8447                    surf_usm_v(l)%r_s(m) = - rho_lv * ( qv1 - q_s + dq_s_dt             &
8448                                    *  t_surf_green_v(l)%t(m) - dq_s_dt *               &
8449                                      t_surf_green_v_p(l)%t(m) ) /                      &
8450                                      (surf_usm_v(l)%qsws(m) + 1.0E-20)  - surf_usm_v(l)%r_a(m)
8451                 ENDIF
8452         
8453!
8454!--              Calculate change in liquid water reservoir due to dew fall or
8455!--              evaporation of liquid water
8456                 IF ( humidity )  THEN
8457!
8458!--                 If the air is saturated, check the reservoir water level
8459                    IF ( surf_usm_v(l)%qsws(m) < 0.0_wp )  THEN
8460       
8461!
8462!--                    In case qsws_veg becomes negative (unphysical behavior),
8463!--                    let the water enter the liquid water reservoir as dew on the
8464!--                    plant
8465                       IF ( surf_usm_v(l)%qsws_veg(m) < 0.0_wp )  THEN
8466          !                 surf_usm_h%qsws_liq(m) = surf_usm_h%qsws_liq(m) + surf_usm_h%qsws_veg(m)
8467                          surf_usm_v(l)%qsws_veg(m) = 0.0_wp
8468                       ENDIF
8469                    ENDIF
8470                 
8471                 ENDIF
8472              ELSE
8473                 surf_usm_v(l)%r_s(m) = 1.0E10_wp
8474              ENDIF
8475
8476           ENDDO
8477 
8478       ENDDO
8479       !$OMP END PARALLEL
8480
8481!
8482!--     Add-up anthropogenic heat, for now only at upward-facing surfaces
8483         IF ( usm_anthropogenic_heat  .AND.  &
8484              intermediate_timestep_count == intermediate_timestep_count_max )  THEN
8485!
8486!--        application of the additional anthropogenic heat sources
8487!--        we considere the traffic for now so all heat is absorbed
8488!--        to the first layer, generalization would be worth.
8489!--        calculation of actual profile coefficient
8490!--        ??? check time_since_reference_point ???
8491            dtime = mod(simulated_time + time_utc_init, 24.0_wp*3600.0_wp)
8492            dhour = INT(dtime/3600.0_wp)
8493
8494!--         TO_DO: activate, if testcase is available
8495!--         !$OMP PARALLEL DO PRIVATE (i, j, k, acoef, rho_cp)
8496!--         it may also improve performance to move get_topography_top_index_ji before the k-loop
8497            DO i = nxl, nxr
8498               DO j = nys, nyn
8499                  DO k = nz_urban_b, min(nz_urban_t,naheatlayers)
8500                     IF ( k > get_topography_top_index_ji( j, i, 's' ) ) THEN
8501!
8502!--                    increase of pt in box i,j,k in time dt_3d
8503!--                    given to anthropogenic heat aheat*acoef (W*m-2)
8504!--                    linear interpolation of coeficient
8505                        acoef = (REAL(dhour+1,wp)-dtime/3600.0_wp)*aheatprof(k,dhour) + &
8506                                (dtime/3600.0_wp-REAL(dhour,wp))*aheatprof(k,dhour+1)
8507                        IF ( aheat(k,j,i) > 0.0_wp )  THEN
8508!
8509!--                       calculate rho * c_p coefficient at layer k
8510                           rho_cp  = c_p * hyp(k) / ( r_d * pt(k+1,j,i) * exner(k) )
8511                           pt(k,j,i) = pt(k,j,i) + aheat(k,j,i)*acoef*dt_3d/(exner(k)*rho_cp*dz(1))
8512                        ENDIF
8513                     ENDIF
8514                  ENDDO
8515               ENDDO
8516            ENDDO
8517 
8518         ENDIF
8519!
8520!--     pt and shf are defined on nxlg:nxrg,nysg:nyng
8521!--     get the borders from neighbours
8522         CALL exchange_horiz( pt, nbgp )
8523!
8524!--     calculation of force_radiation_call:
8525!--     Make logical OR for all processes.
8526!--     Force radiation call if at least one processor forces it.
8527         IF ( intermediate_timestep_count == intermediate_timestep_count_max-1 )&
8528         THEN
8529#if defined( __parallel )
8530           IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
8531           CALL MPI_ALLREDUCE( force_radiation_call_l, force_radiation_call,    &
8532                               1, MPI_LOGICAL, MPI_LOR, comm2d, ierr )
8533#else
8534           force_radiation_call = force_radiation_call_l
8535#endif
8536           force_radiation_call_l = .FALSE.
8537         ENDIF
8538 
8539! !
8540! !-- Calculate surface specific humidity
8541!     IF ( humidity )  THEN
8542!        CALL calc_q_surface_usm
8543!     ENDIF
8544 
8545 
8546!     CONTAINS
8547! !------------------------------------------------------------------------------!
8548! ! Description:
8549! ! ------------
8550! !> Calculation of specific humidity of the skin layer (surface). It is assumend
8551! !> that the skin is always saturated.
8552! !------------------------------------------------------------------------------!
8553!        SUBROUTINE calc_q_surface_usm
8554!
8555!           IMPLICIT NONE
8556!
8557!           REAL(wp) :: resistance    !< aerodynamic and soil resistance term
8558!
8559!           DO  m = 1, surf_usm_h%ns
8560!
8561!              i   = surf_usm_h%i(m)           
8562!              j   = surf_usm_h%j(m)
8563!              k   = surf_usm_h%k(m)
8564!
8565!!
8566!!--          Calculate water vapour pressure at saturation
8567!              e_s = 0.01_wp * 610.78_wp * EXP( 17.269_wp *                  &
8568!                                     ( t_surf_green_h_p(m) - 273.16_wp ) /  &
8569!                                     ( t_surf_green_h_p(m) - 35.86_wp  )    &
8570!                                          )
8571!
8572!!
8573!!--          Calculate specific humidity at saturation
8574!              q_s = 0.622_wp * e_s / ( surface_pressure - e_s )
8575!
8576!!              surf_usm_h%r_a_green(m) = ( surf_usm_h%pt1(m) - t_surf_green_h(m) / exner(k) ) /  &
8577!!                    ( surf_usm_h%ts(m) * surf_usm_h%us(m) + 1.0E-10_wp )
8578!!                 
8579!! !--          make sure that the resistance does not drop to zero
8580!!              IF ( ABS(surf_usm_h%r_a_green(m)) < 1.0E-10_wp )  surf_usm_h%r_a_green(m) = 1.0E-10_wp
8581!
8582!              resistance = surf_usm_h%r_a_green(m) / ( surf_usm_h%r_a_green(m) + surf_usm_h%r_s(m) + 1E-5_wp )
8583!
8584!!
8585!!--          Calculate specific humidity at surface
8586!              IF ( bulk_cloud_model )  THEN
8587!                 q(k,j,i) = resistance * q_s +                   &
8588!                                            ( 1.0_wp - resistance ) *              &
8589!                                            ( q(k,j,i) - ql(k,j,i) )
8590!              ELSE
8591!                 q(k,j,i) = resistance * q_s +                   &
8592!                                            ( 1.0_wp - resistance ) *              &
8593!                                              q(k,j,i)
8594!              ENDIF
8595!
8596!!
8597!!--          Update virtual potential temperature
8598!              vpt(k,j,i) = pt(k,j,i) *         &
8599!                         ( 1.0_wp + 0.61_wp * q(k,j,i) )
8600!
8601!           ENDDO
8602!
8603!!
8604!!--       Now, treat vertical surface elements
8605!           DO  l = 0, 3
8606!              DO  m = 1, surf_usm_v(l)%ns
8607!!
8608!!--             Get indices of respective grid point
8609!                 i = surf_usm_v(l)%i(m)
8610!                 j = surf_usm_v(l)%j(m)
8611!                 k = surf_usm_v(l)%k(m)
8612!
8613!!
8614!!--             Calculate water vapour pressure at saturation
8615!                 e_s = 0.01_wp * 610.78_wp * EXP( 17.269_wp *                       &
8616!                                        ( t_surf_green_v_p(l)%t(m) - 273.16_wp ) /  &
8617!                                        ( t_surf_green_v_p(l)%t(m) - 35.86_wp  )    &
8618!                                             )
8619!
8620!!
8621!!--             Calculate specific humidity at saturation
8622!                 q_s = 0.622_wp * e_s / ( surface_pressure -e_s )
8623!
8624!!
8625!!--             Calculate specific humidity at surface
8626!                 IF ( bulk_cloud_model )  THEN
8627!                    q(k,j,i) = ( q(k,j,i) - ql(k,j,i) )
8628!                 ELSE
8629!                    q(k,j,i) = q(k,j,i)
8630!                 ENDIF
8631!!
8632!!--             Update virtual potential temperature
8633!                 vpt(k,j,i) = pt(k,j,i) *         &
8634!                            ( 1.0_wp + 0.61_wp * q(k,j,i) )
8635!
8636!              ENDDO
8637!
8638!           ENDDO
8639!
8640!        END SUBROUTINE calc_q_surface_usm
8641       
8642     END SUBROUTINE usm_surface_energy_balance
8643 
8644 
8645!------------------------------------------------------------------------------!
8646! Description:
8647! ------------
8648!> Swapping of timelevels for t_surf and t_wall
8649!> called out from subroutine swap_timelevel
8650!------------------------------------------------------------------------------!
8651     SUBROUTINE usm_swap_timelevel( mod_count )
8652 
8653        IMPLICIT NONE
8654 
8655        INTEGER(iwp), INTENT(IN) ::  mod_count
8656 
8657       
8658        SELECT CASE ( mod_count )
8659 
8660           CASE ( 0 )
8661!
8662!--          Horizontal surfaces
8663              t_surf_wall_h    => t_surf_wall_h_1;   t_surf_wall_h_p    => t_surf_wall_h_2
8664              t_wall_h         => t_wall_h_1;        t_wall_h_p         => t_wall_h_2
8665              t_surf_window_h  => t_surf_window_h_1; t_surf_window_h_p  => t_surf_window_h_2
8666              t_window_h       => t_window_h_1;      t_window_h_p       => t_window_h_2
8667              t_surf_green_h   => t_surf_green_h_1;  t_surf_green_h_p   => t_surf_green_h_2
8668              t_green_h        => t_green_h_1;       t_green_h_p        => t_green_h_2
8669!
8670!--          Vertical surfaces
8671              t_surf_wall_v    => t_surf_wall_v_1;   t_surf_wall_v_p    => t_surf_wall_v_2
8672              t_wall_v         => t_wall_v_1;        t_wall_v_p         => t_wall_v_2
8673              t_surf_window_v  => t_surf_window_v_1; t_surf_window_v_p  => t_surf_window_v_2
8674              t_window_v       => t_window_v_1;      t_window_v_p       => t_window_v_2
8675              t_surf_green_v   => t_surf_green_v_1;  t_surf_green_v_p   => t_surf_green_v_2
8676              t_green_v        => t_green_v_1;       t_green_v_p        => t_green_v_2
8677           CASE ( 1 )
8678!
8679!--          Horizontal surfaces
8680              t_surf_wall_h    => t_surf_wall_h_2;   t_surf_wall_h_p    => t_surf_wall_h_1
8681              t_wall_h         => t_wall_h_2;        t_wall_h_p         => t_wall_h_1
8682              t_surf_window_h  => t_surf_window_h_2; t_surf_window_h_p  => t_surf_window_h_1
8683              t_window_h       => t_window_h_2;      t_window_h_p       => t_window_h_1
8684              t_surf_green_h   => t_surf_green_h_2;  t_surf_green_h_p   => t_surf_green_h_1
8685              t_green_h        => t_green_h_2;       t_green_h_p        => t_green_h_1
8686!
8687!--          Vertical surfaces
8688              t_surf_wall_v    => t_surf_wall_v_2;   t_surf_wall_v_p    => t_surf_wall_v_1
8689              t_wall_v         => t_wall_v_2;        t_wall_v_p         => t_wall_v_1
8690              t_surf_window_v  => t_surf_window_v_2; t_surf_window_v_p  => t_surf_window_v_1
8691              t_window_v       => t_window_v_2;      t_window_v_p       => t_window_v_1
8692              t_surf_green_v   => t_surf_green_v_2;  t_surf_green_v_p   => t_surf_green_v_1
8693              t_green_v        => t_green_v_2;       t_green_v_p        => t_green_v_1
8694        END SELECT
8695         
8696     END SUBROUTINE usm_swap_timelevel
8697 
8698!------------------------------------------------------------------------------!
8699! Description:
8700! ------------
8701!> Subroutine writes t_surf and t_wall data into restart files
8702!------------------------------------------------------------------------------!
8703     SUBROUTINE usm_wrd_local
8704 
8705     
8706        IMPLICIT NONE
8707       
8708        CHARACTER(LEN=1) ::  dum     !< dummy string to create output-variable name 
8709        INTEGER(iwp)     ::  l       !< index surface type orientation
8710 
8711        CALL wrd_write_string( 'ns_h_on_file_usm' )
8712        WRITE ( 14 )  surf_usm_h%ns
8713 
8714        CALL wrd_write_string( 'ns_v_on_file_usm' )
8715        WRITE ( 14 )  surf_usm_v(0:3)%ns
8716 
8717        CALL wrd_write_string( 'usm_start_index_h' )
8718        WRITE ( 14 )  surf_usm_h%start_index
8719 
8720        CALL wrd_write_string( 'usm_end_index_h' )
8721        WRITE ( 14 )  surf_usm_h%end_index
8722 
8723        CALL wrd_write_string( 't_surf_wall_h' )
8724        WRITE ( 14 )  t_surf_wall_h
8725 
8726        CALL wrd_write_string( 't_surf_window_h' )
8727        WRITE ( 14 )  t_surf_window_h
8728 
8729        CALL wrd_write_string( 't_surf_green_h' )
8730        WRITE ( 14 )  t_surf_green_h
8731!
8732!--     Write restart data which is especially needed for the urban-surface
8733!--     model. In order to do not fill up the restart routines in
8734!--     surface_mod.
8735!--     Output of waste heat from indoor model. Restart data is required in
8736!--     this special case, because the indoor model where waste heat is
8737!--     computed is call each hour (current default), so that waste heat would
8738!--     have zero value until next call of indoor model.
8739        IF ( indoor_model )  THEN
8740           CALL wrd_write_string( 'waste_heat_h' )
8741           WRITE ( 14 )  surf_usm_h%waste_heat
8742        ENDIF   
8743           
8744        DO  l = 0, 3
8745 
8746           CALL wrd_write_string( 'usm_start_index_v' )
8747           WRITE ( 14 )  surf_usm_v(l)%start_index
8748 
8749           CALL wrd_write_string( 'usm_end_index_v' )
8750           WRITE ( 14 )  surf_usm_v(l)%end_index
8751 
8752           WRITE( dum, '(I1)')  l         
8753 
8754           CALL wrd_write_string( 't_surf_wall_v(' // dum // ')' )
8755           WRITE ( 14 )  t_surf_wall_v(l)%t
8756 
8757           CALL wrd_write_string( 't_surf_window_v(' // dum // ')' )
8758           WRITE ( 14 ) t_surf_window_v(l)%t     
8759 
8760           CALL wrd_write_string( 't_surf_green_v(' // dum // ')' )
8761           WRITE ( 14 ) t_surf_green_v(l)%t 
8762           
8763           IF ( indoor_model )  THEN
8764              CALL wrd_write_string( 'waste_heat_v(' // dum // ')' )
8765              WRITE ( 14 )  surf_usm_v(l)%waste_heat
8766           ENDIF
8767           
8768        ENDDO
8769 
8770        CALL wrd_write_string( 'usm_start_index_h' )
8771        WRITE ( 14 )  surf_usm_h%start_index
8772 
8773        CALL wrd_write_string( 'usm_end_index_h' )
8774        WRITE ( 14 )  surf_usm_h%end_index
8775 
8776        CALL wrd_write_string( 't_wall_h' )
8777        WRITE ( 14 )  t_wall_h
8778 
8779        CALL wrd_write_string( 't_window_h' )
8780        WRITE ( 14 )  t_window_h
8781 
8782        CALL wrd_write_string( 't_green_h' )
8783        WRITE ( 14 )  t_green_h
8784 
8785        DO  l = 0, 3
8786 
8787           CALL wrd_write_string( 'usm_start_index_v' )
8788           WRITE ( 14 )  surf_usm_v(l)%start_index
8789 
8790           CALL wrd_write_string( 'usm_end_index_v' )
8791           WRITE ( 14 )  surf_usm_v(l)%end_index
8792 
8793           WRITE( dum, '(I1)')  l     
8794 
8795           CALL wrd_write_string( 't_wall_v(' // dum // ')' )
8796           WRITE ( 14 )  t_wall_v(l)%t
8797 
8798           CALL wrd_write_string( 't_window_v(' // dum // ')' )
8799           WRITE ( 14 )  t_window_v(l)%t
8800 
8801           CALL wrd_write_string( 't_green_v(' // dum // ')' )
8802           WRITE ( 14 )  t_green_v(l)%t
8803       
8804        ENDDO
8805       
8806     END SUBROUTINE usm_wrd_local
8807     
8808     
8809!------------------------------------------------------------------------------!
8810! Description:
8811! ------------
8812!> Define building properties
8813!------------------------------------------------------------------------------!
8814     SUBROUTINE usm_define_pars     
8815!
8816!--     Define the building_pars
8817        building_pars(:,1) = (/   &
8818           0.7_wp,         &  !< parameter 0   - wall fraction above ground floor level
8819           0.3_wp,         &  !< parameter 1   - window fraction above ground floor level
8820           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
8821           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
8822           1.5_wp,         &  !< parameter 4   - LAI roof
8823           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
8824           2200000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
8825           1400000.0_wp,   &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
8826           1300000.0_wp,   &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
8827           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
8828           0.8_wp,         &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
8829           2.1_wp,         &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
8830           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
8831           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
8832           0.93_wp,        &  !< parameter 14  - wall emissivity above ground floor level
8833           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
8834           0.91_wp,        &  !< parameter 16  - window emissivity above ground floor level
8835           0.75_wp,        &  !< parameter 17  - window transmissivity above ground floor level
8836           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
8837           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
8838           4.0_wp,         &  !< parameter 20  - ground floor level height
8839           0.75_wp,        &  !< parameter 21  - wall fraction ground floor level
8840           0.25_wp,        &  !< parameter 22  - window fraction ground floor level
8841           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
8842           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
8843           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
8844           2200000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
8845           1400000.0_wp,   &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
8846           1300000.0_wp,   &  !< parameter 28  - heat capacity 4th wall layer ground floor level
8847           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
8848           0.8_wp,         &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
8849           2.1_wp,         &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
8850           0.93_wp,        &  !< parameter 32  - wall emissivity ground floor level
8851           0.91_wp,        &  !< parameter 33  - window emissivity ground floor level
8852           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
8853           0.75_wp,        &  !< parameter 35  - window transmissivity ground floor level
8854           0.01_wp,        &  !< parameter 36  - z0 roughness ground floor level
8855           0.001_wp,       &  !< parameter 37  - z0h/z0q roughness heat/humidity
8856           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
8857           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
8858           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
8859           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
8860           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
8861           0.39_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
8862           0.63_wp,        &  !< parameter 44  - 4th wall layer thickness above ground floor level
8863           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
8864           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
8865           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
8866           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
8867           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
8868           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
8869           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
8870           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
8871           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
8872           0.39_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
8873           0.63_wp,        &  !< parameter 55  - 4th wall layer thickness ground plate
8874           2200000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
8875           1400000.0_wp,   &  !< parameter 57  - heat capacity 3rd wall layer ground plate
8876           1300000.0_wp,   &  !< parameter 58  - heat capacity 4th wall layer ground plate
8877           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
8878           0.8_wp,         &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
8879           2.1_wp,         &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
8880           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
8881           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
8882           0.39_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
8883           0.63_wp,        &  !< parameter 65  - 4th wall layer thickness ground floor level
8884           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
8885           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
8886           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
8887           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
8888           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
8889           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
8890           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
8891           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
8892           0.57_wp,        &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
8893           0.57_wp,        &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
8894           0.57_wp,        &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
8895           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
8896           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
8897           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
8898           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
8899           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
8900           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
8901           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
8902           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
8903           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
8904           0.57_wp,        &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
8905           0.57_wp,        &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
8906           0.57_wp,        &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
8907           1.0_wp,         &  !< parameter 89  - wall fraction roof
8908           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
8909           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
8910           0.31_wp,        &  !< parameter 92  - 3rd wall layer thickness roof
8911           0.63_wp,        &  !< parameter 93  - 4th wall layer thickness roof
8912           2200000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
8913           1400000.0_wp,   &  !< parameter 95  - heat capacity 3rd wall layer roof
8914           1300000.0_wp,   &  !< parameter 96  - heat capacity 4th wall layer roof
8915           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
8916           0.8_wp,         &  !< parameter 98  - thermal conductivity 3rd wall layer roof
8917           2.1_wp,         &  !< parameter 99  - thermal conductivity 4th wall layer roof
8918           0.93_wp,        &  !< parameter 100 - wall emissivity roof
8919           27.0_wp,        &  !< parameter 101 - wall albedo roof
8920           0.0_wp,         &  !< parameter 102 - window fraction roof
8921           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
8922           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
8923           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
8924           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
8925           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
8926           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
8927           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
8928           0.57_wp,        &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
8929           0.57_wp,        &  !< parameter 111 - thermal conductivity 3rd window layer roof
8930           0.57_wp,        &  !< parameter 112 - thermal conductivity 4th window layer roof
8931           0.91_wp,        &  !< parameter 113 - window emissivity roof
8932           0.75_wp,        &  !< parameter 114 - window transmissivity roof
8933           27.0_wp,        &  !< parameter 115 - window albedo roof
8934           0.86_wp,        &  !< parameter 116 - green emissivity roof
8935           5.0_wp,         &  !< parameter 117 - green albedo roof
8936           0.0_wp,         &  !< parameter 118 - green type roof
8937           0.8_wp,         &  !< parameter 119 - shading factor
8938           0.76_wp,        &  !< parameter 120 - g-value windows
8939           5.0_wp,         &  !< parameter 121 - u-value windows
8940           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
8941           0.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
8942           0.0_wp,         &  !< parameter 124 - heat recovery efficiency
8943           3.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
8944           370000.0_wp,    &  !< parameter 126 - dynamic parameter innner heatstorage
8945           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
8946           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
8947           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
8948           3.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
8949           10.0_wp,        &  !< parameter 131 - basic internal heat gains without occupancy of the room
8950           3.0_wp,         &  !< parameter 132 - storey height
8951           0.2_wp          &  !< parameter 133 - ceiling construction height
8952                            /)
8953                           
8954        building_pars(:,2) = (/   &
8955           0.73_wp,        &  !< parameter 0   - wall fraction above ground floor level
8956           0.27_wp,        &  !< parameter 1   - window fraction above ground floor level
8957           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
8958           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
8959           1.5_wp,         &  !< parameter 4   - LAI roof
8960           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
8961           2000000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
8962           103000.0_wp,    &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
8963           900000.0_wp,    &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
8964           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
8965           0.38_wp,        &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
8966           0.04_wp,        &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
8967           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
8968           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
8969           0.92_wp,        &  !< parameter 14  - wall emissivity above ground floor level
8970           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
8971           0.87_wp,        &  !< parameter 16  - window emissivity above ground floor level
8972           0.7_wp,         &  !< parameter 17  - window transmissivity above ground floor level
8973           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
8974           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
8975           4.0_wp,         &  !< parameter 20  - ground floor level height
8976           0.78_wp,        &  !< parameter 21  - wall fraction ground floor level
8977           0.22_wp,        &  !< parameter 22  - window fraction ground floor level
8978           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
8979           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
8980           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
8981           2000000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
8982           103000.0_wp,    &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
8983           900000.0_wp,    &  !< parameter 28  - heat capacity 4th wall layer ground floor level
8984           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
8985           0.38_wp,        &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
8986           0.04_wp,        &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
8987           0.92_wp,        &  !< parameter 32  - wall emissivity ground floor level
8988           0.11_wp,        &  !< parameter 33  - window emissivity ground floor level
8989           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
8990           0.7_wp,         &  !< parameter 35  - window transmissivity ground floor level
8991           0.01_wp,        &  !< parameter 36  - z0 roughness ground floor level
8992           0.001_wp,       &  !< parameter 37  - z0h/z0q roughness heat/humidity
8993           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
8994           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
8995           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
8996           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
8997           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
8998           0.31_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
8999           0.43_wp,        &  !< parameter 44  - 4th wall layer thickness above ground floor level
9000           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9001           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9002           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9003           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9004           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9005           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9006           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9007           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
9008           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
9009           0.31_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
9010           0.42_wp,        &  !< parameter 55  - 4th wall layer thickness ground plate
9011           2000000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9012           103000.0_wp,    &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9013           900000.0_wp,    &  !< parameter 58  - heat capacity 4th wall layer ground plate
9014           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9015           0.38_wp,        &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9016           0.04_wp,        &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9017           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
9018           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
9019           0.31_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
9020           0.43_wp,        &  !< parameter 65  - 4th wall layer thickness ground floor level
9021           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9022           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9023           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9024           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9025           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9026           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9027           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9028           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9029           0.11_wp,        &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9030           0.11_wp,        &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9031           0.11_wp,        &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9032           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9033           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9034           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9035           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9036           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9037           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9038           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9039           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9040           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9041           0.11_wp,        &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9042           0.11_wp,        &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9043           0.11_wp,        &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9044           1.0_wp,         &  !< parameter 89  - wall fraction roof
9045           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9046           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9047           0.5_wp,         &  !< parameter 92  - 3rd wall layer thickness roof
9048           0.79_wp,        &  !< parameter 93  - 4th wall layer thickness roof
9049           2000000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9050           103000.0_wp,    &  !< parameter 95  - heat capacity 3rd wall layer roof
9051           900000.0_wp,    &  !< parameter 96  - heat capacity 4th wall layer roof
9052           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9053           0.38_wp,        &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9054           0.04_wp,        &  !< parameter 99  - thermal conductivity 4th wall layer roof
9055           0.93_wp,        &  !< parameter 100 - wall emissivity roof
9056           27.0_wp,        &  !< parameter 101 - wall albedo roof
9057           0.0_wp,         &  !< parameter 102 - window fraction roof
9058           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9059           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9060           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9061           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9062           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9063           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9064           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9065           0.11_wp,        &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9066           0.11_wp,        &  !< parameter 111 - thermal conductivity 3rd window layer roof
9067           0.11_wp,        &  !< parameter 112 - thermal conductivity 4th window layer roof
9068           0.87_wp,        &  !< parameter 113 - window emissivity roof
9069           0.7_wp,         &  !< parameter 114 - window transmissivity roof
9070           27.0_wp,        &  !< parameter 115 - window albedo roof
9071           0.86_wp,        &  !< parameter 116 - green emissivity roof
9072           5.0_wp,         &  !< parameter 117 - green albedo roof
9073           0.0_wp,         &  !< parameter 118 - green type roof
9074           0.8_wp,         &  !< parameter 119 - shading factor
9075           0.6_wp,         &  !< parameter 120 - g-value windows
9076           3.0_wp,         &  !< parameter 121 - u-value windows
9077           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9078           0.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9079           0.0_wp,         &  !< parameter 124 - heat recovery efficiency
9080           2.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9081           165000.0_wp,    &  !< parameter 126 - dynamic parameter innner heatstorage
9082           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9083           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9084           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9085           4.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9086           8.0_wp,         &  !< parameter 131 - basic internal heat gains without occupancy of the room
9087           3.0_wp,         &  !< parameter 132 - storey height
9088           0.2_wp          &  !< parameter 133 - ceiling construction height
9089                            /)
9090                           
9091        building_pars(:,3) = (/   &
9092           0.7_wp,         &  !< parameter 0   - wall fraction above ground floor level
9093           0.3_wp,         &  !< parameter 1   - window fraction above ground floor level
9094           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9095           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9096           1.5_wp,         &  !< parameter 4   - LAI roof
9097           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9098           2000000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9099           103000.0_wp,    &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9100           900000.0_wp,    &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9101           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9102           0.14_wp,        &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9103           0.035_wp,       &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9104           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9105           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9106           0.92_wp,        &  !< parameter 14  - wall emissivity above ground floor level
9107           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9108           0.8_wp,         &  !< parameter 16  - window emissivity above ground floor level
9109           0.6_wp,         &  !< parameter 17  - window transmissivity above ground floor level
9110           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9111           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9112           4.0_wp,         &  !< parameter 20  - ground floor level height
9113           0.75_wp,        &  !< parameter 21  - wall fraction ground floor level
9114           0.25_wp,        &  !< parameter 22  - window fraction ground floor level
9115           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9116           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9117           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9118           2000000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9119           103000.0_wp,    &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9120           900000.0_wp,    &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9121           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9122           0.14_wp,        &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9123           0.035_wp,       &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9124           0.92_wp,        &  !< parameter 32  - wall emissivity ground floor level
9125           0.8_wp,         &  !< parameter 33  - window emissivity ground floor level
9126           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9127           0.6_wp,         &  !< parameter 35  - window transmissivity ground floor level
9128           0.01_wp,        &  !< parameter 36  - z0 roughness ground floor level
9129           0.001_wp,       &  !< parameter 37  - z0h/z0q roughness heat/humidity
9130           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9131           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9132           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9133           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
9134           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9135           0.41_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9136           0.7_wp,         &  !< parameter 44  - 4th wall layer thickness above ground floor level
9137           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9138           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9139           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9140           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9141           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9142           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9143           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9144           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
9145           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
9146           0.41_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
9147           0.7_wp,         &  !< parameter 55  - 4th wall layer thickness ground plate
9148           2000000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9149           103000.0_wp,    &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9150           900000.0_wp,    &  !< parameter 58  - heat capacity 4th wall layer ground plate
9151           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9152           0.14_wp,        &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9153           0.035_wp,       &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9154           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
9155           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
9156           0.41_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
9157           0.7_wp,         &  !< parameter 65  - 4th wall layer thickness ground floor level
9158           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9159           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9160           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9161           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9162           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9163           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9164           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9165           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9166           0.037_wp,       &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9167           0.037_wp,       &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9168           0.037_wp,       &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9169           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9170           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9171           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9172           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9173           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9174           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9175           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9176           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9177           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9178           0.037_wp,       &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9179           0.037_wp,       &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9180           0.037_wp,       &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9181           1.0_wp,         &  !< parameter 89  - wall fraction roof
9182           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9183           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9184           0.41_wp,        &  !< parameter 92  - 3rd wall layer thickness roof
9185           0.7_wp,         &  !< parameter 93  - 4th wall layer thickness roof
9186           2000000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9187           103000.0_wp,    &  !< parameter 95  - heat capacity 3rd wall layer roof
9188           900000.0_wp,    &  !< parameter 96  - heat capacity 4th wall layer roof
9189           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9190           0.14_wp,        &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9191           0.035_wp,       &  !< parameter 99  - thermal conductivity 4th wall layer roof
9192           0.93_wp,        &  !< parameter 100 - wall emissivity roof
9193           27.0_wp,        &  !< parameter 101 - wall albedo roof
9194           0.0_wp,         &  !< parameter 102 - window fraction roof
9195           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9196           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9197           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9198           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9199           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9200           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9201           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9202           0.037_wp,       &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9203           0.037_wp,       &  !< parameter 111 - thermal conductivity 3rd window layer roof
9204           0.037_wp,       &  !< parameter 112 - thermal conductivity 4th window layer roof
9205           0.8_wp,         &  !< parameter 113 - window emissivity roof
9206           0.6_wp,         &  !< parameter 114 - window transmissivity roof
9207           27.0_wp,        &  !< parameter 115 - window albedo roof
9208           0.86_wp,        &  !< parameter 116 - green emissivity roof
9209           5.0_wp,         &  !< parameter 117 - green albedo roof
9210           0.0_wp,         &  !< parameter 118 - green type roof
9211           0.8_wp,         &  !< parameter 119 - shading factor
9212           0.5_wp,         &  !< parameter 120 - g-value windows
9213           0.6_wp,         &  !< parameter 121 - u-value windows
9214           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9215           0.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9216           0.8_wp,         &  !< parameter 124 - heat recovery efficiency
9217           2.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9218           80000.0_wp,     &  !< parameter 126 - dynamic parameter innner heatstorage
9219           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9220           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9221           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9222           3.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9223           8.0_wp,         &  !< parameter 131 - basic internal heat gains without occupancy of the room
9224           3.0_wp,         &  !< parameter 132 - storey height
9225           0.2_wp          &  !< parameter 133 - ceiling construction height
9226                            /)   
9227                           
9228        building_pars(:,4) = (/   &
9229           0.5_wp,         &  !< parameter 0   - wall fraction above ground floor level
9230           0.5_wp,         &  !< parameter 1   - window fraction above ground floor level
9231           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9232           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9233           1.5_wp,         &  !< parameter 4   - LAI roof
9234           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9235           2200000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9236           1400000.0_wp,   &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9237           1300000.0_wp,   &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9238           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9239           0.8_wp,         &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9240           2.1_wp,         &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9241           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9242           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9243           0.93_wp,        &  !< parameter 14  - wall emissivity above ground floor level
9244           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9245           0.91_wp,        &  !< parameter 16  - window emissivity above ground floor level
9246           0.75_wp,        &  !< parameter 17  - window transmissivity above ground floor level
9247           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9248           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9249           4.0_wp,         &  !< parameter 20  - ground floor level height
9250           0.55_wp,        &  !< parameter 21  - wall fraction ground floor level
9251           0.45_wp,        &  !< parameter 22  - window fraction ground floor level
9252           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9253           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9254           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9255           2200000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9256           1400000.0_wp,   &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9257           1300000.0_wp,   &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9258           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9259           0.8_wp,         &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9260           2.1_wp,         &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9261           0.93_wp,        &  !< parameter 32  - wall emissivity ground floor level
9262           0.91_wp,        &  !< parameter 33  - window emissivity ground floor level
9263           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9264           0.75_wp,        &  !< parameter 35  - window transmissivity ground floor level
9265           0.01_wp,        &  !< parameter 36  - z0 roughness ground floor level
9266           0.001_wp,       &  !< parameter 37  - z0h/z0q roughness heat/humidity
9267           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9268           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9269           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9270           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
9271           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9272           0.39_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9273           0.63_wp,        &  !< parameter 44  - 4th wall layer thickness above ground floor level
9274           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9275           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9276           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9277           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9278           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9279           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9280           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9281           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
9282           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
9283           0.39_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
9284           0.63_wp,        &  !< parameter 55  - 4th wall layer thickness ground plate
9285           2200000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9286           1400000.0_wp,   &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9287           1300000.0_wp,   &  !< parameter 58  - heat capacity 4th wall layer ground plate
9288           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9289           0.8_wp,         &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9290           2.1_wp,         &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9291           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
9292           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
9293           0.39_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
9294           0.63_wp,        &  !< parameter 65  - 4th wall layer thickness ground floor level
9295           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9296           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9297           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9298           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9299           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9300           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9301           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9302           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9303           0.57_wp,        &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9304           0.57_wp,        &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9305           0.57_wp,        &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9306           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9307           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9308           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9309           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9310           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9311           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9312           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9313           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9314           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9315           0.57_wp,        &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9316           0.57_wp,        &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9317           0.57_wp,        &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9318           1.0_wp,         &  !< parameter 89  - wall fraction roof
9319           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9320           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9321           0.39_wp,        &  !< parameter 92  - 3rd wall layer thickness roof
9322           0.63_wp,        &  !< parameter 93  - 4th wall layer thickness roof
9323           2200000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9324           1400000.0_wp,   &  !< parameter 95  - heat capacity 3rd wall layer roof
9325           1300000.0_wp,   &  !< parameter 96  - heat capacity 4th wall layer roof
9326           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9327           0.8_wp,         &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9328           2.1_wp,         &  !< parameter 99  - thermal conductivity 4th wall layer roof
9329           0.93_wp,        &  !< parameter 100 - wall emissivity roof
9330           27.0_wp,        &  !< parameter 101 - wall albedo roof
9331           0.0_wp,         &  !< parameter 102 - window fraction roof
9332           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9333           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9334           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9335           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9336           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9337           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9338           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9339           0.57_wp,        &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9340           0.57_wp,        &  !< parameter 111 - thermal conductivity 3rd window layer roof
9341           0.57_wp,        &  !< parameter 112 - thermal conductivity 4th window layer roof
9342           0.91_wp,        &  !< parameter 113 - window emissivity roof
9343           0.75_wp,        &  !< parameter 114 - window transmissivity roof
9344           27.0_wp,        &  !< parameter 115 - window albedo roof
9345           0.86_wp,        &  !< parameter 116 - green emissivity roof
9346           5.0_wp,         &  !< parameter 117 - green albedo roof
9347           0.0_wp,         &  !< parameter 118 - green type roof
9348           0.8_wp,         &  !< parameter 119 - shading factor
9349           0.76_wp,        &  !< parameter 120 - g-value windows
9350           5.0_wp,         &  !< parameter 121 - u-value windows
9351           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9352           1.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9353           0.0_wp,         &  !< parameter 124 - heat recovery efficiency
9354           3.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9355           370000.0_wp,    &  !< parameter 126 - dynamic parameter innner heatstorage
9356           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9357           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9358           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9359           3.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9360           10.0_wp,        &  !< parameter 131 - basic internal heat gains without occupancy of the room
9361           3.0_wp,         &  !< parameter 132 - storey height
9362           0.2_wp          &  !< parameter 133 - ceiling construction height
9363                            /)   
9364                           
9365        building_pars(:,5) = (/   &
9366           0.5_wp,         &  !< parameter 0   - wall fraction above ground floor level
9367           0.5_wp,         &  !< parameter 1   - window fraction above ground floor level
9368           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9369           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9370           1.5_wp,         &  !< parameter 4   - LAI roof
9371           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9372           2000000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9373           103000.0_wp,    &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9374           900000.0_wp,    &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9375           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9376           0.38_wp,        &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9377           0.04_wp,        &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9378           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9379           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9380           0.92_wp,        &  !< parameter 14  - wall emissivity above ground floor level
9381           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9382           0.87_wp,        &  !< parameter 16  - window emissivity above ground floor level
9383           0.7_wp,         &  !< parameter 17  - window transmissivity above ground floor level
9384           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9385           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9386           4.0_wp,         &  !< parameter 20  - ground floor level height
9387           0.55_wp,        &  !< parameter 21  - wall fraction ground floor level
9388           0.45_wp,        &  !< parameter 22  - window fraction ground floor level
9389           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9390           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9391           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9392           2000000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9393           103000.0_wp,    &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9394           900000.0_wp,    &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9395           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9396           0.38_wp,        &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9397           0.04_wp,        &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9398           0.92_wp,        &  !< parameter 32  - wall emissivity ground floor level
9399           0.87_wp,        &  !< parameter 33  - window emissivity ground floor level
9400           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9401           0.7_wp,         &  !< parameter 35  - window transmissivity ground floor level
9402           0.01_wp,        &  !< parameter 36  - z0 roughness ground floor level
9403           0.001_wp,       &  !< parameter 37  - z0h/z0q roughness heat/humidity
9404           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9405           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9406           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9407           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
9408           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9409           0.31_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9410           0.43_wp,        &  !< parameter 44  - 4th wall layer thickness above ground floor level
9411           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9412           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9413           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9414           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9415           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9416           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9417           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9418           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
9419           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
9420           0.31_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
9421           0.43_wp,        &  !< parameter 55  - 4th wall layer thickness ground plate
9422           2000000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9423           103000.0_wp,    &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9424           900000.0_wp,    &  !< parameter 58  - heat capacity 4th wall layer ground plate
9425           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9426           0.38_wp,        &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9427           0.04_wp,        &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9428           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
9429           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
9430           0.31_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
9431           0.43_wp,        &  !< parameter 65  - 4th wall layer thickness ground floor level
9432           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9433           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9434           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9435           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9436           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9437           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9438           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9439           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9440           0.11_wp,        &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9441           0.11_wp,        &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9442           0.11_wp,        &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9443           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9444           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9445           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9446           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9447           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9448           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9449           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9450           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9451           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9452           0.11_wp,        &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9453           0.11_wp,        &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9454           0.11_wp,        &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9455           1.0_wp,         &  !< parameter 89  - wall fraction roof
9456           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9457           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9458           0.31_wp,        &  !< parameter 92  - 3rd wall layer thickness roof
9459           0.43_wp,        &  !< parameter 93  - 4th wall layer thickness roof
9460           2000000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9461           103000.0_wp,    &  !< parameter 95  - heat capacity 3rd wall layer roof
9462           900000.0_wp,    &  !< parameter 96  - heat capacity 4th wall layer roof
9463           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9464           0.38_wp,        &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9465           0.04_wp,        &  !< parameter 99  - thermal conductivity 4th wall layer roof
9466           0.91_wp,        &  !< parameter 100 - wall emissivity roof
9467           27.0_wp,        &  !< parameter 101 - wall albedo roof
9468           0.0_wp,         &  !< parameter 102 - window fraction roof
9469           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9470           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9471           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9472           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9473           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9474           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9475           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9476           0.11_wp,        &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9477           0.11_wp,        &  !< parameter 111 - thermal conductivity 3rd window layer roof
9478           0.11_wp,        &  !< parameter 112 - thermal conductivity 4th window layer roof
9479           0.87_wp,        &  !< parameter 113 - window emissivity roof
9480           0.7_wp,         &  !< parameter 114 - window transmissivity roof
9481           27.0_wp,        &  !< parameter 115 - window albedo roof
9482           0.86_wp,        &  !< parameter 116 - green emissivity roof
9483           5.0_wp,         &  !< parameter 117 - green albedo roof
9484           0.0_wp,         &  !< parameter 118 - green type roof
9485           0.8_wp,         &  !< parameter 119 - shading factor
9486           0.6_wp,         &  !< parameter 120 - g-value windows
9487           3.0_wp,         &  !< parameter 121 - u-value windows
9488           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9489           1.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9490           0.65_wp,        &  !< parameter 124 - heat recovery efficiency
9491           2.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9492           165000.0_wp,    &  !< parameter 126 - dynamic parameter innner heatstorage
9493           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9494           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9495           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9496           7.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9497           20.0_wp,        &  !< parameter 131 - basic internal heat gains without occupancy of the room
9498           3.0_wp,         &  !< parameter 132 - storey height
9499           0.2_wp          &  !< parameter 133 - ceiling construction height
9500                            /)
9501                           
9502        building_pars(:,6) = (/   &
9503           0.425_wp,       &  !< parameter 0   - wall fraction above ground floor level
9504           0.575_wp,       &  !< parameter 1   - window fraction above ground floor level
9505           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9506           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9507           1.5_wp,         &  !< parameter 4   - LAI roof
9508           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9509           2000000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9510           103000.0_wp,    &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9511           900000.0_wp,    &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9512           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9513           0.14_wp,        &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9514           0.035_wp,       &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9515           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9516           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9517           0.92_wp,        &  !< parameter 14  - wall emissivity above ground floor level
9518           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9519           0.8_wp,         &  !< parameter 16  - window emissivity above ground floor level
9520           0.6_wp,         &  !< parameter 17  - window transmissivity above ground floor level
9521           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9522           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9523           4.0_wp,         &  !< parameter 20  - ground floor level height
9524           0.475_wp,       &  !< parameter 21  - wall fraction ground floor level
9525           0.525_wp,       &  !< parameter 22  - window fraction ground floor level
9526           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9527           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9528           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9529           2000000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9530           103000.0_wp,    &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9531           900000.0_wp,    &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9532           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9533           0.14_wp,        &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9534           0.035_wp,       &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9535           0.92_wp,        &  !< parameter 32  - wall emissivity ground floor level
9536           0.8_wp,         &  !< parameter 33  - window emissivity ground floor level
9537           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9538           0.6_wp,         &  !< parameter 35  - window transmissivity ground floor level
9539           0.01_wp,        &  !< parameter 36  - z0 roughness ground floor level
9540           0.001_wp,       &  !< parameter 37  - z0h/z0q roughness heat/humidity
9541           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9542           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9543           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9544           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
9545           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9546           0.41_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9547           0.7_wp,         &  !< parameter 44  - 4th wall layer thickness above ground floor level
9548           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9549           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9550           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9551           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9552           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9553           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9554           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9555           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
9556           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
9557           0.41_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
9558           0.7_wp,         &  !< parameter 55  - 4th wall layer thickness ground plate
9559           2000000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9560           103000.0_wp,    &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9561           900000.0_wp,    &  !< parameter 58  - heat capacity 4th wall layer ground plate
9562           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9563           0.14_wp,        &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9564           0.035_wp,       &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9565           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
9566           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
9567           0.41_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
9568           0.7_wp,         &  !< parameter 65  - 4th wall layer thickness ground floor level
9569           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9570           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9571           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9572           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9573           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9574           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9575           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9576           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9577           0.037_wp,       &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9578           0.037_wp,       &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9579           0.037_wp,       &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9580           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9581           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9582           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9583           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9584           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9585           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9586           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9587           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9588           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9589           0.037_wp,       &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9590           0.037_wp,       &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9591           0.037_wp,       &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9592           1.0_wp,         &  !< parameter 89  - wall fraction roof
9593           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9594           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9595           0.41_wp,        &  !< parameter 92  - 3rd wall layer thickness roof
9596           0.7_wp,         &  !< parameter 93  - 4th wall layer thickness roof
9597           2000000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9598           103000.0_wp,    &  !< parameter 95  - heat capacity 3rd wall layer roof
9599           900000.0_wp,    &  !< parameter 96  - heat capacity 4th wall layer roof
9600           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9601           0.14_wp,        &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9602           0.035_wp,       &  !< parameter 99  - thermal conductivity 4th wall layer roof
9603           0.91_wp,        &  !< parameter 100 - wall emissivity roof
9604           27.0_wp,        &  !< parameter 101 - wall albedo roof
9605           0.0_wp,         &  !< parameter 102 - window fraction roof
9606           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9607           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9608           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9609           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9610           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9611           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9612           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9613           0.037_wp,       &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9614           0.037_wp,       &  !< parameter 111 - thermal conductivity 3rd window layer roof
9615           0.037_wp,       &  !< parameter 112 - thermal conductivity 4th window layer roof
9616           0.8_wp,         &  !< parameter 113 - window emissivity roof
9617           0.6_wp,         &  !< parameter 114 - window transmissivity roof
9618           27.0_wp,        &  !< parameter 115 - window albedo roof
9619           0.86_wp,        &  !< parameter 116 - green emissivity roof
9620           5.0_wp,         &  !< parameter 117 - green albedo roof
9621           0.0_wp,         &  !< parameter 118 - green type roof
9622           0.8_wp,         &  !< parameter 119 - shading factor
9623           0.5_wp,         &  !< parameter 120 - g-value windows
9624           0.6_wp,         &  !< parameter 121 - u-value windows
9625           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9626           1.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9627           0.9_wp,         &  !< parameter 124 - heat recovery efficiency
9628           2.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9629           80000.0_wp,     &  !< parameter 126 - dynamic parameter innner heatstorage
9630           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9631           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9632           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9633           5.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9634           15.0_wp,        &  !< parameter 131 - basic internal heat gains without occupancy of the room
9635           3.0_wp,         &  !< parameter 132 - storey height
9636           0.2_wp          &  !< parameter 133 - ceiling construction height
9637                            /)
9638                           
9639        building_pars(:,7) = (/   &
9640           1.0_wp,         &  !< parameter 0   - wall fraction above ground floor level
9641           0.0_wp,         &  !< parameter 1   - window fraction above ground floor level
9642           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9643           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9644           1.5_wp,         &  !< parameter 4   - LAI roof
9645           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9646           1950400.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9647           1848000.0_wp,   &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9648           1848000.0_wp,   &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9649           0.7_wp,         &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9650           1.0_wp,         &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9651           1.0_wp,         &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9652           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9653           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9654           0.9_wp,         &  !< parameter 14  - wall emissivity above ground floor level
9655           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9656           0.8_wp,         &  !< parameter 16  - window emissivity above ground floor level
9657           0.6_wp,         &  !< parameter 17  - window transmissivity above ground floor level
9658           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9659           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9660           4.0_wp,         &  !< parameter 20  - ground floor level height
9661           1.0_wp,         &  !< parameter 21  - wall fraction ground floor level
9662           0.0_wp,         &  !< parameter 22  - window fraction ground floor level
9663           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9664           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9665           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9666           1950400.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9667           1848000.0_wp,   &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9668           1848000.0_wp,   &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9669           0.7_wp,         &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9670           1.0_wp,         &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9671           1.0_wp,         &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9672           0.9_wp,         &  !< parameter 32  - wall emissivity ground floor level
9673           0.8_wp,         &  !< parameter 33  - window emissivity ground floor level
9674           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9675           0.6_wp,         &  !< parameter 35  - window transmissivity ground floor level
9676           0.01_wp,        &  !< parameter 36  - z0 roughness ground floor level
9677           0.001_wp,       &  !< parameter 37  - z0h/z0q roughness heat/humidity
9678           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9679           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9680           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9681           0.29_wp,        &  !< parameter 41  - 1st wall layer thickness above ground floor level
9682           0.295_wp,       &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9683           0.695_wp,       &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9684           0.985_wp,       &  !< parameter 44  - 4th wall layer thickness above ground floor level
9685           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9686           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9687           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9688           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9689           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9690           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9691           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9692           0.29_wp,        &  !< parameter 52  - 1st wall layer thickness ground plate
9693           0.295_wp,       &  !< parameter 53  - 2nd wall layer thickness ground plate
9694           0.695_wp,       &  !< parameter 54  - 3rd wall layer thickness ground plate
9695           0.985_wp,       &  !< parameter 55  - 4th wall layer thickness ground plate
9696           1950400.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9697           1848000.0_wp,   &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9698           1848000.0_wp,   &  !< parameter 58  - heat capacity 4th wall layer ground plate
9699           0.7_wp,         &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9700           1.0_wp,         &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9701           1.0_wp,         &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9702           0.29_wp,        &  !< parameter 62  - 1st wall layer thickness ground floor level
9703           0.295_wp,       &  !< parameter 63  - 2nd wall layer thickness ground floor level
9704           0.695_wp,       &  !< parameter 64  - 3rd wall layer thickness ground floor level
9705           0.985_wp,       &  !< parameter 65  - 4th wall layer thickness ground floor level
9706           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9707           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9708           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9709           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9710           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9711           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9712           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9713           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9714           0.57_wp,        &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9715           0.57_wp,        &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9716           0.57_wp,        &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9717           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9718           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9719           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9720           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9721           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9722           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9723           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9724           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9725           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9726           0.57_wp,        &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9727           0.57_wp,        &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9728           0.57_wp,        &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9729           1.0_wp,         &  !< parameter 89  - wall fraction roof
9730           0.29_wp,        &  !< parameter 90  - 1st wall layer thickness roof
9731           0.295_wp,       &  !< parameter 91  - 2nd wall layer thickness roof
9732           0.695_wp,       &  !< parameter 92  - 3rd wall layer thickness roof
9733           0.985_wp,       &  !< parameter 93  - 4th wall layer thickness roof
9734           1950400.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9735           1848000.0_wp,   &  !< parameter 95  - heat capacity 3rd wall layer roof
9736           1848000.0_wp,   &  !< parameter 96  - heat capacity 4th wall layer roof
9737           0.7_wp,         &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9738           1.0_wp,         &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9739           1.0_wp,         &  !< parameter 99  - thermal conductivity 4th wall layer roof
9740           0.9_wp,         &  !< parameter 100 - wall emissivity roof
9741           27.0_wp,        &  !< parameter 101 - wall albedo roof
9742           0.0_wp,         &  !< parameter 102 - window fraction roof
9743           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9744           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9745           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9746           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9747           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9748           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9749           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9750           0.57_wp,        &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9751           0.57_wp,        &  !< parameter 111 - thermal conductivity 3rd window layer roof
9752           0.57_wp,        &  !< parameter 112 - thermal conductivity 4th window layer roof
9753           0.8_wp,         &  !< parameter 113 - window emissivity roof
9754           0.6_wp,         &  !< parameter 114 - window transmissivity roof
9755           27.0_wp,        &  !< parameter 115 - window albedo roof
9756           0.86_wp,        &  !< parameter 116 - green emissivity roof
9757           5.0_wp,         &  !< parameter 117 - green albedo roof
9758           0.0_wp,         &  !< parameter 118 - green type roof
9759           0.8_wp,         &  !< parameter 119 - shading factor
9760           100.0_wp,       &  !< parameter 120 - g-value windows
9761           100.0_wp,       &  !< parameter 121 - u-value windows
9762           20.0_wp,        &  !< parameter 122 - basical airflow without occupancy of the room
9763           20.0_wp,        &  !< parameter 123 - additional airflow depend of occupancy of the room
9764           0.0_wp,         &  !< parameter 124 - heat recovery efficiency
9765           1.0_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9766           1.0_wp,         &  !< parameter 126 - dynamic parameter innner heatstorage
9767           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9768           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9769           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9770           0.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9771           0.0_wp,         &  !< parameter 131 - basic internal heat gains without occupancy of the room
9772           3.0_wp,         &  !< parameter 132 - storey height
9773           0.2_wp          &  !< parameter 133 - ceiling construction height
9774                        /)
9775                       
9776     END SUBROUTINE usm_define_pars
9777 
9778   
9779  END MODULE urban_surface_mod
Note: See TracBrowser for help on using the repository browser.