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

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

Undo accidentally commented initialization

  • Property svn:keywords set to Id
File size: 557.6 KB
Line 
1!> @file urban_surface_mod.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 2015-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 3921 2019-04-18 14:21:10Z suehring $
30! Undo accidentally commented initialization 
31!
32! 3918 2019-04-18 13:33:11Z suehring
33! Set green fraction to zero also at vertical surfaces
34!
35! 3914 2019-04-17 16:02:02Z suehring
36! In order to obtain correct surface temperature during spinup set window
37! fraction to zero (only during spinup) instead of just disabling
38! time-integration of window-surface temperature.
39!
40! 3901 2019-04-16 16:17:02Z suehring
41! Workaround - set green fraction to zero ( green-heat model crashes ).
42!
43! 3896 2019-04-15 10:10:17Z suehring
44!
45!
46! 3896 2019-04-15 10:10:17Z suehring
47! Bugfix, wrong index used for accessing building_pars from PIDS
48!
49! 3885 2019-04-11 11:29:34Z kanani
50! Changes related to global restructuring of location messages and introduction
51! of additional debug messages
52!
53! 3882 2019-04-10 11:08:06Z suehring
54! Avoid different type kinds
55! Move definition of building-surface properties from declaration block
56! to an extra routine
57!
58! 3881 2019-04-10 09:31:22Z suehring
59! Revise determination of local ground-floor level height.
60! Make level 3 initalization conform with Palm-input-data standard
61! Move output of albedo and emissivity to radiation module
62!
63! 3832 2019-03-28 13:16:58Z raasch
64! instrumented with openmp directives
65!
66! 3824 2019-03-27 15:56:16Z pavelkrc
67! Remove unused imports
68!
69!
70! 3814 2019-03-26 08:40:31Z pavelkrc
71! unused subroutine commented out
72!
73! 3769 2019-02-28 10:16:49Z moh.hefny
74! removed unused variables
75!
76! 3767 2019-02-27 08:18:02Z raasch
77! unused variables removed from rrd-subroutines parameter list
78!
79! 3748 2019-02-18 10:38:31Z suehring
80! Revise conversion of waste-heat flux (do not divide by air density, will
81! be done in diffusion_s)
82!
83! 3745 2019-02-15 18:57:56Z suehring
84! - Remove internal flag indoor_model (is a global control parameter)
85! - add waste heat from buildings to the kinmatic heat flux
86! - consider waste heat in restart data
87! - remove unused USE statements
88!
89! 3744 2019-02-15 18:38:58Z suehring
90! fixed surface heat capacity in the building parameters
91! convert the file back to unix format
92!
93! 3730 2019-02-11 11:26:47Z moh.hefny
94! Formatting and clean-up (rvtils)
95!
96! 3710 2019-01-30 18:11:19Z suehring
97! Check if building type is set within a valid range.
98!
99! 3705 2019-01-29 19:56:39Z suehring
100! make nzb_wall public, required for virtual-measurements
101!
102! 3704 2019-01-29 19:51:41Z suehring
103! Some interface calls moved to module_interface + cleanup
104!
105! 3655 2019-01-07 16:51:22Z knoop
106! Implementation of the PALM module interface
107!
108! 3636 2018-12-19 13:48:34Z raasch
109! nopointer option removed
110!
111! 3614 2018-12-10 07:05:46Z raasch
112! unused variables removed
113!
114! 3607 2018-12-07 11:56:58Z suehring
115! Output of radiation-related quantities migrated to radiation_model_mod.
116!
117! 3597 2018-12-04 08:40:18Z maronga
118! Fixed calculation method of near surface air potential temperature at 10 cm
119! and moved to surface_layer_fluxes. Removed unnecessary _eb strings.
120!
121! 3524 2018-11-14 13:36:44Z raasch
122! bugfix concerning allocation of t_surf_wall_v
123!
124! 3502 2018-11-07 14:45:23Z suehring
125! Disable initialization of building roofs with ground-floor-level properties,
126! since this causes strong oscillations of surface temperature during the
127! spinup.
128!
129! 3469 2018-10-30 20:05:07Z kanani
130! Add missing PUBLIC variables for new indoor model
131!
132! 3449 2018-10-29 19:36:56Z suehring
133! Bugfix: Fix average arrays allocations in usm_3d_data_averaging (J.Resler)
134! Bugfix: Fix reading wall temperatures (J.Resler)
135! Bugfix: Fix treating of outputs for wall temperature and sky view factors (J.Resler)
136!
137!
138! 3435 2018-10-26 18:25:44Z gronemeier
139! Bugfix: allocate gamma_w_green_sat until nzt_wall+1
140!
141! 3418 2018-10-24 16:07:39Z kanani
142! (rvtils, srissman)
143! -Updated building databse, two green roof types (ind_green_type_roof)
144! -Latent heat flux for green walls and roofs, new output of latent heatflux
145!  and soil water content of green roof substrate
146! -t_surf changed to t_surf_wall
147! -Added namelist parameter usm_wall_mod for lower wall tendency
148!  of first two wall layers during spinup
149! -Window calculations deactivated during spinup
150!
151! 3382 2018-10-19 13:10:32Z knoop
152! Bugix: made array declaration Fortran Standard conform
153!
154! 3378 2018-10-19 12:34:59Z kanani
155! merge from radiation branch (r3362) into trunk
156! (moh.hefny):
157! - check the requested output variables if they are correct
158! - added unscheduled_radiation_calls switch to control force_radiation_call
159! - minor formate changes
160!
161! 3371 2018-10-18 13:40:12Z knoop
162! Set flag indicating that albedo at urban surfaces is already initialized
163!
164! 3347 2018-10-15 14:21:08Z suehring
165! Enable USM initialization with default building parameters in case no static
166! input file exist.
167!
168! 3343 2018-10-15 10:38:52Z suehring
169! Add output variables usm_rad_pc_inlw, usm_rad_pc_insw*
170!
171! 3274 2018-09-24 15:42:55Z knoop
172! Modularization of all bulk cloud physics code components
173!
174! 3248 2018-09-14 09:42:06Z sward
175! Minor formating changes
176!
177! 3246 2018-09-13 15:14:50Z sward
178! Added error handling for input namelist via parin_fail_message
179!
180! 3241 2018-09-12 15:02:00Z raasch
181! unused variables removed
182!
183! 3223 2018-08-30 13:48:17Z suehring
184! Bugfix for commit 3222
185!
186! 3222 2018-08-30 13:35:35Z suehring
187! Introduction of surface array for type and its name
188!
189! 3203 2018-08-23 10:48:36Z suehring
190! Revise bulk parameter for emissivity at ground-floor level
191!
192! 3196 2018-08-13 12:26:14Z maronga
193! Added maximum aerodynamic resistance of 300 for horiztonal surfaces.
194!
195! 3176 2018-07-26 17:12:48Z suehring
196! Bugfix, update virtual potential surface temparture, else heat fluxes on
197! roofs might become unphysical
198!
199! 3152 2018-07-19 13:26:52Z suehring
200! Initialize q_surface, which might be used in surface_layer_fluxes
201!
202! 3151 2018-07-19 08:45:38Z raasch
203! remaining preprocessor define strings __check removed
204!
205! 3136 2018-07-16 14:48:21Z suehring
206! Limit also roughness length for heat and moisture where necessary
207!
208! 3123 2018-07-12 16:21:53Z suehring
209! Correct working precision for INTEGER number
210!
211! 3115 2018-07-10 12:49:26Z suehring
212! Additional building type to represent bridges
213!
214! 3091 2018-06-28 16:20:35Z suehring
215! - Limit aerodynamic resistance at vertical walls.
216! - Add check for local roughness length not exceeding surface-layer height and
217!   limit roughness length where necessary.
218!
219! 3065 2018-06-12 07:03:02Z Giersch
220! Unused array dxdir was removed, dz was replaced by dzu to consider vertical
221! grid stretching
222!
223! 3049 2018-05-29 13:52:36Z Giersch
224! Error messages revised
225!
226! 3045 2018-05-28 07:55:41Z Giersch
227! Error message added
228!
229! 3029 2018-05-23 12:19:17Z raasch
230! bugfix: close unit 151 instead of 90
231!
232! 3014 2018-05-09 08:42:38Z maronga
233! Added pc_transpiration_rate
234!
235! 2977 2018-04-17 10:27:57Z kanani
236! Implement changes from branch radiation (r2948-2971) with minor modifications.
237! (moh.hefny):
238! Extended exn for all model domain height to avoid the need to get nzut.
239!
240! 2963 2018-04-12 14:47:44Z suehring
241! Introduce index for vegetation/wall, pavement/green-wall and water/window
242! surfaces, for clearer access of surface fraction, albedo, emissivity, etc. .
243!
244! 2943 2018-04-03 16:17:10Z suehring
245! Calculate exner function at all height levels and remove some un-used
246! variables.
247!
248! 2932 2018-03-26 09:39:22Z maronga
249! renamed urban_surface_par to urban_surface_parameters
250!
251! 2921 2018-03-22 15:05:23Z Giersch
252! The activation of spinup has been moved to parin
253!
254! 2920 2018-03-22 11:22:01Z kanani
255! Remove unused pcbl, npcbl from ONLY list
256! moh.hefny:
257! Fixed bugs introduced by new structures and by moving radiation interaction
258! into radiation_model_mod.f90.
259! Bugfix: usm data output 3D didn't respect directions
260!
261! 2906 2018-03-19 08:56:40Z Giersch
262! Local variable ids has to be initialized with a value of -1 in
263! usm_3d_data_averaging
264!
265! 2894 2018-03-15 09:17:58Z Giersch
266! Calculations of the index range of the subdomain on file which overlaps with
267! the current subdomain are already done in read_restart_data_mod,
268! usm_read/write_restart_data have been renamed to usm_r/wrd_local, variable
269! named found has been introduced for checking if restart data was found,
270! reading of restart strings has been moved completely to
271! read_restart_data_mod, usm_rrd_local is already inside the overlap loop
272! programmed in read_restart_data_mod, SAVE attribute added where necessary,
273! deallocation and allocation of some arrays have been changed to take care of
274! different restart files that can be opened (index i), the marker *** end usm
275! *** is not necessary anymore, strings and their respective lengths are
276! written out and read now in case of restart runs to get rid of prescribed
277! character lengths
278!
279! 2805 2018-02-14 17:00:09Z suehring
280! Initialization of resistances.
281!
282! 2797 2018-02-08 13:24:35Z suehring
283! Comment concerning output of ground-heat flux added.
284!
285! 2766 2018-01-22 17:17:47Z kanani
286! Removed redundant commas, added some blanks
287!
288! 2765 2018-01-22 11:34:58Z maronga
289! Major bugfix in calculation of f_shf. Adjustment of roughness lengths in
290! building_pars
291!
292! 2750 2018-01-15 16:26:51Z knoop
293! Move flag plant canopy to modules
294!
295! 2737 2018-01-11 14:58:11Z kanani
296! Removed unused variables t_surf_whole...
297!
298! 2735 2018-01-11 12:01:27Z suehring
299! resistances are saved in surface attributes
300!
301! 2723 2018-01-05 09:27:03Z maronga
302! Bugfix for spinups (end_time was increased twice in case of LSM + USM runs)
303!
304! 2720 2018-01-02 16:27:15Z kanani
305! Correction of comment
306!
307! 2718 2018-01-02 08:49:38Z maronga
308! Corrected "Former revisions" section
309!
310! 2705 2017-12-18 11:26:23Z maronga
311! Changes from last commit documented
312!
313! 2703 2017-12-15 20:12:38Z maronga
314! Workaround for calculation of r_a
315!
316! 2696 2017-12-14 17:12:51Z kanani
317! - Change in file header (GPL part)
318! - Bugfix in calculation of pt_surface and related fluxes. (BM)
319! - Do not write surface temperatures onto pt array as this might cause
320!   problems with nesting. (MS)
321! - Revised calculation of pt1 (now done in surface_layer_fluxes).
322!   Bugfix, f_shf_window and f_shf_green were not set at vertical surface
323!   elements. (MS)
324! - merged with branch ebsolver
325!   green building surfaces do not evaporate yet
326!   properties of green wall layers and window layers are taken from wall layers
327!   this input data is missing. (RvT)
328! - Merged with branch radiation (developed by Mohamed Salim)
329! - Revised initialization. (MS)
330! - Rename emiss_surf into emissivity, roughness_wall into z0, albedo_surf into
331!   albedo. (MS)
332! - Move first call of usm_radiatin from usm_init to init_3d_model
333! - fixed problem with near surface temperature
334! - added near surface temperature pt_10cm_h(m), pt_10cm_v(l)%t(m)
335! - does not work with temp profile including stability, ol
336!   pt_10cm = pt1 now
337! - merged with 2357 bugfix, error message for nopointer version
338! - added indoor model coupling with wall heat flux
339! - added green substrate/ dry vegetation layer for buildings
340! - merged with 2232 new surface-type structure
341! - added transmissivity of window tiles
342! - added MOSAIK tile approach for 3 different surfaces (RvT)
343!
344! 2583 2017-10-26 13:58:38Z knoop
345! Bugfix: reverted MPI_Win_allocate_cptr introduction in last commit
346!
347! 2582 2017-10-26 13:19:46Z hellstea
348! Workaround for gnufortran compiler added in usm_calc_svf. CALL MPI_Win_allocate is
349! replaced by CALL MPI_Win_allocate_cptr if defined ( __gnufortran ).
350!
351! 2544 2017-10-13 18:09:32Z maronga
352! Date and time quantities are now read from date_and_time_mod. Solar constant is
353! read from radiation_model_mod
354!
355! 2516 2017-10-04 11:03:04Z suehring
356! Remove tabs
357!
358! 2514 2017-10-04 09:52:37Z suehring
359! upper bounds of 3d output changed from nx+1,ny+1 to nx,ny
360! no output of ghost layer data
361!
362! 2350 2017-08-15 11:48:26Z kanani
363! Bugfix and error message for nopointer version.
364! Additional "! defined(__nopointer)" as workaround to enable compilation of
365! nopointer version.
366!
367! 2318 2017-07-20 17:27:44Z suehring
368! Get topography top index via Function call
369!
370! 2317 2017-07-20 17:27:19Z suehring
371! Bugfix: adjust output of shf. Added support for spinups
372!
373! 2287 2017-06-15 16:46:30Z suehring
374! Bugfix in determination topography-top index
375!
376! 2269 2017-06-09 11:57:32Z suehring
377! Enable restart runs with different number of PEs
378! Bugfixes nopointer branch
379!
380! 2258 2017-06-08 07:55:13Z suehring
381! Bugfix, add pre-preprocessor directives to enable non-parrallel mode
382!
383! 2233 2017-05-30 18:08:54Z suehring
384!
385! 2232 2017-05-30 17:47:52Z suehring
386! Adjustments according to new surface-type structure. Remove usm_wall_heat_flux;
387! insteat, heat fluxes are directly applied in diffusion_s.
388!
389! 2213 2017-04-24 15:10:35Z kanani
390! Removal of output quantities usm_lad and usm_canopy_hr
391!
392! 2209 2017-04-19 09:34:46Z kanani
393! cpp switch __mpi3 removed,
394! minor formatting,
395! small bugfix for division by zero (Krc)
396!
397! 2113 2017-01-12 13:40:46Z kanani
398! cpp switch __mpi3 added for MPI-3 standard code (Ketelsen)
399!
400! 2071 2016-11-17 11:22:14Z maronga
401! Small bugfix (Resler)
402!
403! 2031 2016-10-21 15:11:58Z knoop
404! renamed variable rho to rho_ocean
405!
406! 2024 2016-10-12 16:42:37Z kanani
407! Bugfixes in deallocation of array plantt and reading of csf/csfsurf,
408! optimization of MPI-RMA operations,
409! declaration of pcbl as integer,
410! renamed usm_radnet -> usm_rad_net, usm_canopy_khf -> usm_canopy_hr,
411! splitted arrays svf -> svf & csf, svfsurf -> svfsurf & csfsurf,
412! use of new control parameter varnamelength,
413! added output variables usm_rad_ressw, usm_rad_reslw,
414! minor formatting changes,
415! minor optimizations.
416!
417! 2011 2016-09-19 17:29:57Z kanani
418! Major reformatting according to PALM coding standard (comments, blanks,
419! alphabetical ordering, etc.),
420! removed debug_prints,
421! removed auxiliary SUBROUTINE get_usm_info, instead, USM flag urban_surface is
422! defined in MODULE control_parameters (modules.f90) to avoid circular
423! dependencies,
424! renamed canopy_heat_flux to pc_heating_rate, as meaning of quantity changed.
425!
426! 2007 2016-08-24 15:47:17Z kanani
427! Initial revision
428!
429!
430! Description:
431! ------------
432! 2016/6/9 - Initial version of the USM (Urban Surface Model)
433!            authors: Jaroslav Resler, Pavel Krc
434!                     (Czech Technical University in Prague and Institute of
435!                      Computer Science of the Czech Academy of Sciences, Prague)
436!            with contributions: Michal Belda, Nina Benesova, Ondrej Vlcek
437!            partly inspired by PALM LSM (B. Maronga)
438!            parameterizations of Ra checked with TUF3D (E. S. Krayenhoff)
439!> Module for Urban Surface Model (USM)
440!> The module includes:
441!>    1. radiation model with direct/diffuse radiation, shading, reflections
442!>       and integration with plant canopy
443!>    2. wall and wall surface model
444!>    3. surface layer energy balance
445!>    4. anthropogenic heat (only from transportation so far)
446!>    5. necessary auxiliary subroutines (reading inputs, writing outputs,
447!>       restart simulations, ...)
448!> It also make use of standard radiation and integrates it into
449!> urban surface model.
450!>
451!> Further work:
452!> -------------
453!> 1. Remove global arrays surfouts, surfoutl and only keep track of radiosity
454!>    from surfaces that are visible from local surfaces (i.e. there is a SVF
455!>    where target is local). To do that, radiosity will be exchanged after each
456!>    reflection step using MPI_Alltoall instead of current MPI_Allgather.
457!>
458!> 2. Temporarily large values of surface heat flux can be observed, up to
459!>    1.2 Km/s, which seem to be not realistic.
460!>
461!> @todo Output of _av variables in case of restarts
462!> @todo Revise flux conversion in energy-balance solver
463!> @todo Check optimizations for RMA operations
464!> @todo Alternatives for MPI_WIN_ALLOCATE? (causes problems with openmpi)
465!> @todo Check for load imbalances in CPU measures, e.g. for exchange_horiz_prog
466!>       factor 3 between min and max time
467!> @todo Check divisions in wtend (etc.) calculations for possible division
468!>       by zero, e.g. in case fraq(0,m) + fraq(1,m) = 0?!
469!> @todo Use unit 90 for OPEN/CLOSE of input files (FK)
470!> @todo Move plant canopy stuff into plant canopy code
471!------------------------------------------------------------------------------!
472 MODULE urban_surface_mod
473
474    USE arrays_3d,                                                             &
475        ONLY:  hyp, zu, pt, p, u, v, w, tend, exner, hyrho, prr, q, ql, vpt
476
477    USE calc_mean_profile_mod,                                                 &
478        ONLY:  calc_mean_profile
479
480    USE basic_constants_and_equations_mod,                                     &
481        ONLY:  c_p, g, kappa, pi, r_d, rho_l, l_v, sigma_sb
482
483    USE control_parameters,                                                    &
484        ONLY:  coupling_start_time, topography,                                &
485               debug_output, debug_string,                                     &
486               dt_3d, humidity, indoor_model,                                  &
487               intermediate_timestep_count, initializing_actions,              &
488               intermediate_timestep_count_max, simulated_time, end_time,      &
489               timestep_scheme, tsc, coupling_char, io_blocks, io_group,       &
490               message_string, time_since_reference_point, surface_pressure,   &
491               pt_surface, large_scale_forcing, lsf_surf, spinup,              &
492               spinup_pt_mean, spinup_time, time_do3d, dt_do3d,                &
493               average_count_3d, varnamelength, urban_surface, dz
494
495    USE bulk_cloud_model_mod,                                                  &
496        ONLY: bulk_cloud_model, precipitation
497               
498    USE cpulog,                                                                &
499        ONLY:  cpu_log, log_point, log_point_s
500
501    USE date_and_time_mod,                                                     &
502        ONLY:  time_utc_init
503
504    USE grid_variables,                                                        &
505        ONLY:  dx, dy, ddx, ddy, ddx2, ddy2
506
507    USE indices,                                                               &
508        ONLY:  nx, ny, nnx, nny, nnz, nxl, nxlg, nxr, nxrg, nyn, nyng, nys,    &
509               nysg, nzb, nzt, nbgp, wall_flags_0
510
511    USE, INTRINSIC :: iso_c_binding 
512
513    USE kinds
514             
515    USE pegrid
516       
517    USE radiation_model_mod,                                                   &
518        ONLY:  albedo_type, radiation_interaction,                             &
519               radiation, rad_sw_in, rad_lw_in, rad_sw_out, rad_lw_out,        &
520               force_radiation_call, iup_u, inorth_u, isouth_u, ieast_u,       &
521               iwest_u, iup_l, inorth_l, isouth_l, ieast_l, iwest_l, id,       &
522               iz, iy, ix,  nsurf, idsvf, ndsvf,                               &
523               idcsf, ndcsf, kdcsf, pct,                                       &
524               nz_urban_b, nz_urban_t, unscheduled_radiation_calls
525
526    USE statistics,                                                            &
527        ONLY:  hom, statistic_regions
528
529    USE surface_mod,                                                           &
530        ONLY:  get_topography_top_index_ji, get_topography_top_index,          &
531               ind_pav_green, ind_veg_wall, ind_wat_win, surf_usm_h,           &
532               surf_usm_v, surface_restore_elements
533
534
535    IMPLICIT NONE
536
537!
538!-- USM model constants
539
540    REAL(wp), PARAMETER ::                     &
541              b_ch               = 6.04_wp,    &  !< Clapp & Hornberger exponent
542              lambda_h_green_dry = 0.19_wp,    &  !< heat conductivity for dry soil   
543              lambda_h_green_sm  = 3.44_wp,    &  !< heat conductivity of the soil matrix
544              lambda_h_water     = 0.57_wp,    &  !< heat conductivity of water
545              psi_sat            = -0.388_wp,  &  !< soil matrix potential at saturation
546              rho_c_soil         = 2.19E6_wp,  &  !< volumetric heat capacity of soil
547              rho_c_water        = 4.20E6_wp      !< volumetric heat capacity of water
548!               m_max_depth        = 0.0002_wp     ! Maximum capacity of the water reservoir (m)
549
550!
551!-- Soil parameters I           alpha_vg,      l_vg_green,    n_vg, gamma_w_green_sat
552    REAL(wp), DIMENSION(0:3,1:7), PARAMETER :: soil_pars = RESHAPE( (/     &
553                                 3.83_wp,  1.250_wp, 1.38_wp,  6.94E-6_wp, &  !< soil 1
554                                 3.14_wp, -2.342_wp, 1.28_wp,  1.16E-6_wp, &  !< soil 2
555                                 0.83_wp, -0.588_wp, 1.25_wp,  0.26E-6_wp, &  !< soil 3
556                                 3.67_wp, -1.977_wp, 1.10_wp,  2.87E-6_wp, &  !< soil 4
557                                 2.65_wp,  2.500_wp, 1.10_wp,  1.74E-6_wp, &  !< soil 5
558                                 1.30_wp,  0.400_wp, 1.20_wp,  0.93E-6_wp, &  !< soil 6
559                                 0.00_wp,  0.00_wp,  0.00_wp,  0.57E-6_wp  &  !< soil 7
560                                 /), (/ 4, 7 /) )
561
562!
563!-- Soil parameters II              swc_sat,     fc,   wilt,    swc_res 
564    REAL(wp), DIMENSION(0:3,1:7), PARAMETER :: m_soil_pars = RESHAPE( (/ &
565                                 0.403_wp, 0.244_wp, 0.059_wp, 0.025_wp, &  !< soil 1
566                                 0.439_wp, 0.347_wp, 0.151_wp, 0.010_wp, &  !< soil 2
567                                 0.430_wp, 0.383_wp, 0.133_wp, 0.010_wp, &  !< soil 3
568                                 0.520_wp, 0.448_wp, 0.279_wp, 0.010_wp, &  !< soil 4
569                                 0.614_wp, 0.541_wp, 0.335_wp, 0.010_wp, &  !< soil 5
570                                 0.766_wp, 0.663_wp, 0.267_wp, 0.010_wp, &  !< soil 6
571                                 0.472_wp, 0.323_wp, 0.171_wp, 0.000_wp  &  !< soil 7
572                                 /), (/ 4, 7 /) )
573!
574!-- value 9999999.9_wp -> generic available or user-defined value must be set
575!-- otherwise -> no generic variable and user setting is optional
576    REAL(wp) :: alpha_vangenuchten = 9999999.9_wp,      &  !< NAMELIST alpha_vg
577                field_capacity = 9999999.9_wp,          &  !< NAMELIST fc
578                hydraulic_conductivity = 9999999.9_wp,  &  !< NAMELIST gamma_w_green_sat
579                l_vangenuchten = 9999999.9_wp,          &  !< NAMELIST l_vg
580                n_vangenuchten = 9999999.9_wp,          &  !< NAMELIST n_vg
581                residual_moisture = 9999999.9_wp,       &  !< NAMELIST m_res
582                saturation_moisture = 9999999.9_wp,     &  !< NAMELIST m_sat
583                wilting_point = 9999999.9_wp               !< NAMELIST m_wilt
584   
585!
586!-- configuration parameters (they can be setup in PALM config)
587    LOGICAL ::  usm_material_model = .TRUE.        !< flag parameter indicating wheather the  model of heat in materials is used
588    LOGICAL ::  usm_anthropogenic_heat = .FALSE.   !< flag parameter indicating wheather the anthropogenic heat sources
589                                                   !< (e.g.transportation) are used
590    LOGICAL ::  force_radiation_call_l = .FALSE.   !< flag parameter for unscheduled radiation model calls
591    LOGICAL ::  read_wall_temp_3d = .FALSE.
592    LOGICAL ::  usm_wall_mod = .FALSE.             !< reduces conductivity of the first 2 wall layers by factor 0.1
593
594
595    INTEGER(iwp) ::  building_type = 1               !< default building type (preleminary setting)
596    INTEGER(iwp) ::  land_category = 2               !< default category for land surface
597    INTEGER(iwp) ::  wall_category = 2               !< default category for wall surface over pedestrian zone
598    INTEGER(iwp) ::  pedestrian_category = 2         !< default category for wall surface in pedestrian zone
599    INTEGER(iwp) ::  roof_category = 2               !< default category for root surface
600    REAL(wp)     ::  roughness_concrete = 0.001_wp   !< roughness length of average concrete surface
601!
602!-- Indices of input attributes in building_pars for (above) ground floor level
603    INTEGER(iwp) ::  ind_alb_wall_agfl     = 38   !< index in input list for albedo_type of wall above ground floor level
604    INTEGER(iwp) ::  ind_alb_wall_gfl      = 66   !< index in input list for albedo_type of wall ground floor level
605    INTEGER(iwp) ::  ind_alb_wall_r        = 101  !< index in input list for albedo_type of wall roof
606    INTEGER(iwp) ::  ind_alb_green_agfl    = 39   !< index in input list for albedo_type of green above ground floor level
607    INTEGER(iwp) ::  ind_alb_green_gfl     = 78   !< index in input list for albedo_type of green ground floor level
608    INTEGER(iwp) ::  ind_alb_green_r       = 117  !< index in input list for albedo_type of green roof
609    INTEGER(iwp) ::  ind_alb_win_agfl      = 40   !< index in input list for albedo_type of window fraction above ground floor level
610    INTEGER(iwp) ::  ind_alb_win_gfl       = 77   !< index in input list for albedo_type of window fraction ground floor level
611    INTEGER(iwp) ::  ind_alb_win_r         = 115  !< index in input list for albedo_type of window fraction roof
612    INTEGER(iwp) ::  ind_c_surface         = 45   !< index in input list for heat capacity wall surface
613    INTEGER(iwp) ::  ind_c_surface_green   = 48   !< index in input list for heat capacity green surface
614    INTEGER(iwp) ::  ind_c_surface_win     = 47   !< index in input list for heat capacity window surface
615    INTEGER(iwp) ::  ind_emis_wall_agfl    = 14   !< index in input list for wall emissivity, above ground floor level
616    INTEGER(iwp) ::  ind_emis_wall_gfl     = 32   !< index in input list for wall emissivity, ground floor level
617    INTEGER(iwp) ::  ind_emis_wall_r       = 100  !< index in input list for wall emissivity, roof
618    INTEGER(iwp) ::  ind_emis_green_agfl   = 15   !< index in input list for green emissivity, above ground floor level
619    INTEGER(iwp) ::  ind_emis_green_gfl    = 34   !< index in input list for green emissivity, ground floor level
620    INTEGER(iwp) ::  ind_emis_green_r      = 116  !< index in input list for green emissivity, roof
621    INTEGER(iwp) ::  ind_emis_win_agfl     = 16   !< index in input list for window emissivity, above ground floor level
622    INTEGER(iwp) ::  ind_emis_win_gfl      = 33   !< index in input list for window emissivity, ground floor level
623    INTEGER(iwp) ::  ind_emis_win_r        = 113  !< index in input list for window emissivity, roof
624    INTEGER(iwp) ::  ind_gflh              = 20   !< index in input list for ground floor level height
625    INTEGER(iwp) ::  ind_green_frac_w_agfl = 2    !< index in input list for green fraction on wall, above ground floor level
626    INTEGER(iwp) ::  ind_green_frac_w_gfl  = 23   !< index in input list for green fraction on wall, ground floor level
627    INTEGER(iwp) ::  ind_green_frac_r_agfl = 3    !< index in input list for green fraction on roof, above ground floor level
628    INTEGER(iwp) ::  ind_green_frac_r_gfl  = 24   !< index in input list for green fraction on roof, ground floor level
629    INTEGER(iwp) ::  ind_hc1_agfl          = 6    !< index in input list for heat capacity at first wall layer,
630                                                  !< above ground floor level
631    INTEGER(iwp) ::  ind_hc1_gfl           = 26   !< index in input list for heat capacity at first wall layer, ground floor level
632    INTEGER(iwp) ::  ind_hc1_wall_r        = 94   !< index in input list for heat capacity at first wall layer, roof
633    INTEGER(iwp) ::  ind_hc1_win_agfl      = 83   !< index in input list for heat capacity at first window layer,
634                                                  !< above ground floor level
635    INTEGER(iwp) ::  ind_hc1_win_gfl       = 71   !< index in input list for heat capacity at first window layer,
636                                                  !< ground floor level
637    INTEGER(iwp) ::  ind_hc1_win_r         = 107  !< index in input list for heat capacity at first window layer, roof
638    INTEGER(iwp) ::  ind_hc2_agfl          = 7    !< index in input list for heat capacity at second wall layer,
639                                                  !< above ground floor level
640    INTEGER(iwp) ::  ind_hc2_gfl           = 27   !< index in input list for heat capacity at second wall layer, ground floor level
641    INTEGER(iwp) ::  ind_hc2_wall_r        = 95   !< index in input list for heat capacity at second wall layer, roof
642    INTEGER(iwp) ::  ind_hc2_win_agfl      = 84   !< index in input list for heat capacity at second window layer,
643                                                  !< above ground floor level
644    INTEGER(iwp) ::  ind_hc2_win_gfl       = 72   !< index in input list for heat capacity at second window layer,
645                                                  !< ground floor level
646    INTEGER(iwp) ::  ind_hc2_win_r         = 108  !< index in input list for heat capacity at second window layer, roof
647    INTEGER(iwp) ::  ind_hc3_agfl          = 8    !< index in input list for heat capacity at third wall layer,
648                                                  !< above ground floor level
649    INTEGER(iwp) ::  ind_hc3_gfl           = 28   !< index in input list for heat capacity at third wall layer, ground floor level
650    INTEGER(iwp) ::  ind_hc3_wall_r        = 96   !< index in input list for heat capacity at third wall layer, roof
651    INTEGER(iwp) ::  ind_hc3_win_agfl      = 85   !< index in input list for heat capacity at third window layer,
652                                                  !< above ground floor level
653    INTEGER(iwp) ::  ind_hc3_win_gfl       = 73   !< index in input list for heat capacity at third window layer,
654                                                  !< ground floor level
655    INTEGER(iwp) ::  ind_hc3_win_r         = 109  !< index in input list for heat capacity at third window layer, roof
656    INTEGER(iwp) ::  ind_indoor_target_temp_summer = 12
657    INTEGER(iwp) ::  ind_indoor_target_temp_winter = 13
658    INTEGER(iwp) ::  ind_lai_r_agfl        = 4    !< index in input list for LAI on roof, above ground floor level
659    INTEGER(iwp) ::  ind_lai_r_gfl         = 4  !< index in input list for LAI on roof, ground floor level
660    INTEGER(iwp) ::  ind_lai_w_agfl        = 5    !< index in input list for LAI on wall, above ground floor level
661    INTEGER(iwp) ::  ind_lai_w_gfl         = 25   !< index in input list for LAI on wall, ground floor level
662    INTEGER(iwp) ::  ind_lambda_surf       = 46   !< index in input list for thermal conductivity of wall surface
663    INTEGER(iwp) ::  ind_lambda_surf_green = 50   !< index in input list for thermal conductivity of green surface
664    INTEGER(iwp) ::  ind_lambda_surf_win   = 49   !< index in input list for thermal conductivity of window surface
665    INTEGER(iwp) ::  ind_tc1_agfl          = 9    !< index in input list for thermal conductivity at first wall layer,
666                                                  !< above ground floor level
667    INTEGER(iwp) ::  ind_tc1_gfl           = 29   !< index in input list for thermal conductivity at first wall layer,
668                                                  !< ground floor level
669    INTEGER(iwp) ::  ind_tc1_wall_r        = 97   !< index in input list for thermal conductivity at first wall layer, roof
670    INTEGER(iwp) ::  ind_tc1_win_agfl      = 86   !< index in input list for thermal conductivity at first window layer,
671                                                  !< above ground floor level
672    INTEGER(iwp) ::  ind_tc1_win_gfl       = 74   !< index in input list for thermal conductivity at first window layer,
673                                                  !< ground floor level
674    INTEGER(iwp) ::  ind_tc1_win_r         = 110  !< index in input list for thermal conductivity at first window layer, roof
675    INTEGER(iwp) ::  ind_tc2_agfl          = 10   !< index in input list for thermal conductivity at second wall layer,
676                                                  !< above ground floor level
677    INTEGER(iwp) ::  ind_tc2_gfl           = 30   !< index in input list for thermal conductivity at second wall layer,
678                                                  !< ground floor level
679    INTEGER(iwp) ::  ind_tc2_wall_r        = 98   !< index in input list for thermal conductivity at second wall layer, roof
680    INTEGER(iwp) ::  ind_tc2_win_agfl      = 87   !< index in input list for thermal conductivity at second window layer,
681                                                  !< above ground floor level
682    INTEGER(iwp) ::  ind_tc2_win_gfl       = 75   !< index in input list for thermal conductivity at second window layer,
683                                                  !< ground floor level
684    INTEGER(iwp) ::  ind_tc2_win_r         = 111  !< index in input list for thermal conductivity at second window layer,
685                                                  !< ground floor level
686    INTEGER(iwp) ::  ind_tc3_agfl          = 11   !< index in input list for thermal conductivity at third wall layer,
687                                                  !< above ground floor level
688    INTEGER(iwp) ::  ind_tc3_gfl           = 31   !< index in input list for thermal conductivity at third wall layer,
689                                                  !< ground floor level
690    INTEGER(iwp) ::  ind_tc3_wall_r        = 99   !< index in input list for thermal conductivity at third wall layer, roof
691    INTEGER(iwp) ::  ind_tc3_win_agfl      = 88   !< index in input list for thermal conductivity at third window layer,
692                                                  !< above ground floor level
693    INTEGER(iwp) ::  ind_tc3_win_gfl       = 76   !< index in input list for thermal conductivity at third window layer,
694                                                  !< ground floor level
695    INTEGER(iwp) ::  ind_tc3_win_r         = 112  !< index in input list for thermal conductivity at third window layer, roof
696    INTEGER(iwp) ::  ind_thick_1_agfl      = 41   !< index for wall layer thickness - 1st layer above ground floor level
697    INTEGER(iwp) ::  ind_thick_1_gfl       = 62   !< index for wall layer thickness - 1st layer ground floor level
698    INTEGER(iwp) ::  ind_thick_1_wall_r    = 90   !< index for wall layer thickness - 1st layer roof
699    INTEGER(iwp) ::  ind_thick_1_win_agfl  = 79   !< index for window layer thickness - 1st layer above ground floor level
700    INTEGER(iwp) ::  ind_thick_1_win_gfl   = 67   !< index for window layer thickness - 1st layer ground floor level
701    INTEGER(iwp) ::  ind_thick_1_win_r     = 103  !< index for window layer thickness - 1st layer roof
702    INTEGER(iwp) ::  ind_thick_2_agfl      = 42   !< index for wall layer thickness - 2nd layer above ground floor level
703    INTEGER(iwp) ::  ind_thick_2_gfl       = 63   !< index for wall layer thickness - 2nd layer ground floor level
704    INTEGER(iwp) ::  ind_thick_2_wall_r    = 91   !< index for wall layer thickness - 2nd layer roof
705    INTEGER(iwp) ::  ind_thick_2_win_agfl  = 80   !< index for window layer thickness - 2nd layer above ground floor level
706    INTEGER(iwp) ::  ind_thick_2_win_gfl   = 68   !< index for window layer thickness - 2nd layer ground floor level
707    INTEGER(iwp) ::  ind_thick_2_win_r     = 104  !< index for window layer thickness - 2nd layer roof
708    INTEGER(iwp) ::  ind_thick_3_agfl      = 43   !< index for wall layer thickness - 3rd layer above ground floor level
709    INTEGER(iwp) ::  ind_thick_3_gfl       = 64   !< index for wall layer thickness - 3rd layer ground floor level
710    INTEGER(iwp) ::  ind_thick_3_wall_r    = 92   !< index for wall layer thickness - 3rd layer roof
711    INTEGER(iwp) ::  ind_thick_3_win_agfl  = 81   !< index for window layer thickness - 3rd layer above ground floor level
712    INTEGER(iwp) ::  ind_thick_3_win_gfl   = 69   !< index for window layer thickness - 3rd layer ground floor level 
713    INTEGER(iwp) ::  ind_thick_3_win_r     = 105  !< index for window layer thickness - 3rd layer roof
714    INTEGER(iwp) ::  ind_thick_4_agfl      = 44   !< index for wall layer thickness - 4th layer above ground floor level
715    INTEGER(iwp) ::  ind_thick_4_gfl       = 65   !< index for wall layer thickness - 4th layer ground floor level
716    INTEGER(iwp) ::  ind_thick_4_wall_r    = 93   !< index for wall layer thickness - 4st layer roof
717    INTEGER(iwp) ::  ind_thick_4_win_agfl  = 82   !< index for window layer thickness - 4th layer above ground floor level
718    INTEGER(iwp) ::  ind_thick_4_win_gfl   = 70   !< index for window layer thickness - 4th layer ground floor level
719    INTEGER(iwp) ::  ind_thick_4_win_r     = 106  !< index for window layer thickness - 4th layer roof
720    INTEGER(iwp) ::  ind_trans_agfl        = 17   !< index in input list for window transmissivity, above ground floor level
721    INTEGER(iwp) ::  ind_trans_gfl         = 35   !< index in input list for window transmissivity, ground floor level
722    INTEGER(iwp) ::  ind_trans_r           = 114  !< index in input list for window transmissivity, roof
723    INTEGER(iwp) ::  ind_wall_frac_agfl    = 0    !< index in input list for wall fraction, above ground floor level
724    INTEGER(iwp) ::  ind_wall_frac_gfl     = 21   !< index in input list for wall fraction, ground floor level
725    INTEGER(iwp) ::  ind_wall_frac_r       = 89   !< index in input list for wall fraction, roof
726    INTEGER(iwp) ::  ind_win_frac_agfl     = 1    !< index in input list for window fraction, above ground floor level
727    INTEGER(iwp) ::  ind_win_frac_gfl      = 22   !< index in input list for window fraction, ground floor level
728    INTEGER(iwp) ::  ind_win_frac_r        = 102  !< index in input list for window fraction, roof
729    INTEGER(iwp) ::  ind_z0_agfl           = 18   !< index in input list for z0, above ground floor level
730    INTEGER(iwp) ::  ind_z0_gfl            = 36   !< index in input list for z0, ground floor level
731    INTEGER(iwp) ::  ind_z0qh_agfl         = 19   !< index in input list for z0h / z0q, above ground floor level
732    INTEGER(iwp) ::  ind_z0qh_gfl          = 37   !< index in input list for z0h / z0q, ground floor level
733    INTEGER(iwp) ::  ind_green_type_roof   = 118  !< index in input list for type of green roof
734
735
736    REAL(wp)  ::  roof_height_limit = 4.0_wp         !< height for distinguish between land surfaces and roofs
737    REAL(wp)  ::  ground_floor_level = 4.0_wp        !< default ground floor level
738
739
740    CHARACTER(37), DIMENSION(0:7), PARAMETER :: building_type_name = (/     &
741                                   'user-defined                         ', &  !< type 0
742                                   'residential - 1950                   ', &  !< type  1
743                                   'residential 1951 - 2000              ', &  !< type  2
744                                   'residential 2001 -                   ', &  !< type  3
745                                   'office - 1950                        ', &  !< type  4
746                                   'office 1951 - 2000                   ', &  !< type  5
747                                   'office 2001 -                        ', &  !< type  6
748                                   'bridges                              '  &  !< type  7
749                                                                     /)
750
751
752!
753!-- Building facade/wall/green/window properties (partly according to PIDS).
754!-- Initialization of building_pars is outsourced to usm_init_pars. This is
755!-- needed because of the huge number of attributes given in building_pars
756!-- (>700), while intel and gfortran compiler have hard limit of continuation
757!-- lines of 511.
758    REAL(wp), DIMENSION(0:133,1:7) ::  building_pars
759!
760!-- Type for surface temperatures at vertical walls. Is not necessary for horizontal walls.
761    TYPE t_surf_vertical
762       REAL(wp), DIMENSION(:), ALLOCATABLE         :: t
763    END TYPE t_surf_vertical
764!
765!-- Type for wall temperatures at vertical walls. Is not necessary for horizontal walls.
766    TYPE t_wall_vertical
767       REAL(wp), DIMENSION(:,:), ALLOCATABLE       :: t
768    END TYPE t_wall_vertical
769
770    TYPE surf_type_usm
771       REAL(wp), DIMENSION(:),   ALLOCATABLE ::  var_usm_1d  !< 1D prognostic variable
772       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  var_usm_2d  !< 2D prognostic variable
773    END TYPE surf_type_usm
774   
775    TYPE(surf_type_usm), POINTER  ::  m_liq_usm_h,        &  !< liquid water reservoir (m), horizontal surface elements
776                                      m_liq_usm_h_p          !< progn. liquid water reservoir (m), horizontal surface elements
777
778    TYPE(surf_type_usm), TARGET   ::  m_liq_usm_h_1,      &  !<
779                                      m_liq_usm_h_2          !<
780
781    TYPE(surf_type_usm), DIMENSION(:), POINTER  ::        &
782                                      m_liq_usm_v,        &  !< liquid water reservoir (m), vertical surface elements
783                                      m_liq_usm_v_p          !< progn. liquid water reservoir (m), vertical surface elements
784
785    TYPE(surf_type_usm), DIMENSION(0:3), TARGET   ::      &
786                                      m_liq_usm_v_1,      &  !<
787                                      m_liq_usm_v_2          !<
788
789    TYPE(surf_type_usm), TARGET ::  tm_liq_usm_h_m      !< liquid water reservoir tendency (m), horizontal surface elements
790    TYPE(surf_type_usm), DIMENSION(0:3), TARGET ::  tm_liq_usm_v_m      !< liquid water reservoir tendency (m),
791                                                                        !< vertical surface elements
792
793!
794!-- anthropogenic heat sources
795    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE        ::  aheat             !< daily average of anthropogenic heat (W/m2)
796    REAL(wp), DIMENSION(:,:), ALLOCATABLE          ::  aheatprof         !< diurnal profiles of anthropogenic heat
797                                                                         !< for particular layers
798    INTEGER(iwp)                                   ::  naheatlayers = 1  !< number of layers of anthropogenic heat
799
800!
801!-- wall surface model
802!-- wall surface model constants
803    INTEGER(iwp), PARAMETER                        :: nzb_wall = 0       !< inner side of the wall model (to be switched)
804    INTEGER(iwp), PARAMETER                        :: nzt_wall = 3       !< outer side of the wall model (to be switched)
805    INTEGER(iwp), PARAMETER                        :: nzw = 4            !< number of wall layers (fixed for now)
806
807    REAL(wp), DIMENSION(nzb_wall:nzt_wall)         :: zwn_default        = (/0.0242_wp, 0.0969_wp, 0.346_wp, 1.0_wp /)
808    REAL(wp), DIMENSION(nzb_wall:nzt_wall)         :: zwn_default_window = (/0.25_wp,   0.5_wp,    0.75_wp,  1.0_wp /)
809    REAL(wp), DIMENSION(nzb_wall:nzt_wall)         :: zwn_default_green  = (/0.25_wp,   0.5_wp,    0.75_wp,  1.0_wp /)
810                                                                         !< normalized soil, wall and roof, window and
811                                                                         !<green layer depths (m/m)
812
813    REAL(wp)                                       :: wall_inner_temperature   = 295.0_wp    !< temperature of the inner wall
814                                                                                             !< surface (~22 degrees C) (K)
815    REAL(wp)                                       :: roof_inner_temperature   = 295.0_wp    !< temperature of the inner roof
816                                                                                             !< surface (~22 degrees C) (K)
817    REAL(wp)                                       :: soil_inner_temperature   = 288.0_wp    !< temperature of the deep soil
818                                                                                             !< (~15 degrees C) (K)
819    REAL(wp)                                       :: window_inner_temperature = 295.0_wp    !< temperature of the inner window
820                                                                                             !< surface (~22 degrees C) (K)
821
822    REAL(wp)                                       :: m_total = 0.0_wp  !< weighted total water content of the soil (m3/m3)
823    INTEGER(iwp)                                   :: soil_type
824
825!
826!-- surface and material model variables for walls, ground, roofs
827    REAL(wp), DIMENSION(:), ALLOCATABLE            :: zwn                !< normalized wall layer depths (m)
828    REAL(wp), DIMENSION(:), ALLOCATABLE            :: zwn_window         !< normalized window layer depths (m)
829    REAL(wp), DIMENSION(:), ALLOCATABLE            :: zwn_green          !< normalized green layer depths (m)
830
831    REAL(wp), DIMENSION(:), POINTER                :: t_surf_wall_h
832    REAL(wp), DIMENSION(:), POINTER                :: t_surf_wall_h_p 
833    REAL(wp), DIMENSION(:), POINTER                :: t_surf_window_h
834    REAL(wp), DIMENSION(:), POINTER                :: t_surf_window_h_p 
835    REAL(wp), DIMENSION(:), POINTER                :: t_surf_green_h
836    REAL(wp), DIMENSION(:), POINTER                :: t_surf_green_h_p 
837
838    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_wall_h_1
839    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_wall_h_2
840    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_window_h_1
841    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_window_h_2
842    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_h_1
843    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_h_2
844
845    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_wall_v
846    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_wall_v_p
847    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_window_v
848    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_window_v_p
849    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_green_v
850    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_green_v_p
851
852    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_wall_v_1
853    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_wall_v_2
854    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_window_v_1
855    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_window_v_2
856    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_green_v_1
857    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_green_v_2
858
859!
860!-- Energy balance variables
861!-- parameters of the land, roof and wall surfaces
862
863    REAL(wp), DIMENSION(:,:), POINTER                :: t_wall_h, t_wall_h_p
864    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h_1, t_wall_h_2
865    REAL(wp), DIMENSION(:,:), POINTER                :: t_window_h, t_window_h_p
866    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_window_h_1, t_window_h_2
867    REAL(wp), DIMENSION(:,:), POINTER                :: t_green_h, t_green_h_p
868    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_green_h_1, t_green_h_2
869    REAL(wp), DIMENSION(:,:), POINTER                :: swc_h, rootfr_h, wilt_h, fc_h, swc_sat_h, swc_h_p, swc_res_h
870    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: swc_h_1, rootfr_h_1, &
871                                                        wilt_h_1, fc_h_1, swc_sat_h_1, swc_h_2, swc_res_h_1
872   
873
874    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: t_wall_v, t_wall_v_p
875    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v_1, t_wall_v_2
876    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: t_window_v, t_window_v_p
877    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_window_v_1, t_window_v_2
878    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: t_green_v, t_green_v_p
879    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v_1, t_green_v_2
880    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: swc_v, swc_v_p
881    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: swc_v_1, swc_v_2
882
883!
884!-- Surface and material parameters classes (surface_type)
885!-- albedo, emissivity, lambda_surf, roughness, thickness, volumetric heat capacity, thermal conductivity
886    INTEGER(iwp)                                   :: n_surface_types       !< number of the wall type categories
887    INTEGER(iwp), PARAMETER                        :: n_surface_params = 9  !< number of parameters for each type of the wall
888    INTEGER(iwp), PARAMETER                        :: ialbedo  = 1          !< albedo of the surface
889    INTEGER(iwp), PARAMETER                        :: iemiss   = 2          !< emissivity of the surface
890    INTEGER(iwp), PARAMETER                        :: ilambdas = 3          !< heat conductivity lambda S between surface
891                                                                            !< and material ( W m-2 K-1 )
892    INTEGER(iwp), PARAMETER                        :: irough   = 4          !< roughness length z0 for movements
893    INTEGER(iwp), PARAMETER                        :: iroughh  = 5          !< roughness length z0h for scalars
894                                                                            !< (heat, humidity,...)
895    INTEGER(iwp), PARAMETER                        :: icsurf   = 6          !< Surface skin layer heat capacity (J m-2 K-1 )
896    INTEGER(iwp), PARAMETER                        :: ithick   = 7          !< thickness of the surface (wall, roof, land)  ( m )
897    INTEGER(iwp), PARAMETER                        :: irhoC    = 8          !< volumetric heat capacity rho*C of
898                                                                            !< the material ( J m-3 K-1 )
899    INTEGER(iwp), PARAMETER                        :: ilambdah = 9          !< thermal conductivity lambda H
900                                                                            !< of the wall (W m-1 K-1 )
901    CHARACTER(12), DIMENSION(:), ALLOCATABLE       :: surface_type_names    !< names of wall types (used only for reports)
902    INTEGER(iwp), DIMENSION(:), ALLOCATABLE        :: surface_type_codes    !< codes of wall types
903    REAL(wp), DIMENSION(:,:), ALLOCATABLE          :: surface_params        !< parameters of wall types
904
905!
906!-- interfaces of subroutines accessed from outside of this module
907    INTERFACE usm_3d_data_averaging
908       MODULE PROCEDURE usm_3d_data_averaging
909    END INTERFACE usm_3d_data_averaging
910
911    INTERFACE usm_boundary_condition
912       MODULE PROCEDURE usm_boundary_condition
913    END INTERFACE usm_boundary_condition
914
915    INTERFACE usm_check_data_output
916       MODULE PROCEDURE usm_check_data_output
917    END INTERFACE usm_check_data_output
918   
919    INTERFACE usm_check_parameters
920       MODULE PROCEDURE usm_check_parameters
921    END INTERFACE usm_check_parameters
922   
923    INTERFACE usm_data_output_3d
924       MODULE PROCEDURE usm_data_output_3d
925    END INTERFACE usm_data_output_3d
926   
927    INTERFACE usm_define_netcdf_grid
928       MODULE PROCEDURE usm_define_netcdf_grid
929    END INTERFACE usm_define_netcdf_grid
930
931    INTERFACE usm_init
932       MODULE PROCEDURE usm_init
933    END INTERFACE usm_init
934
935    INTERFACE usm_init_arrays
936       MODULE PROCEDURE usm_init_arrays
937    END INTERFACE usm_init_arrays
938
939    INTERFACE usm_material_heat_model
940       MODULE PROCEDURE usm_material_heat_model
941    END INTERFACE usm_material_heat_model
942   
943    INTERFACE usm_green_heat_model
944       MODULE PROCEDURE usm_green_heat_model
945    END INTERFACE usm_green_heat_model
946   
947    INTERFACE usm_parin
948       MODULE PROCEDURE usm_parin
949    END INTERFACE usm_parin
950
951    INTERFACE usm_rrd_local 
952       MODULE PROCEDURE usm_rrd_local
953    END INTERFACE usm_rrd_local
954
955    INTERFACE usm_surface_energy_balance
956       MODULE PROCEDURE usm_surface_energy_balance
957    END INTERFACE usm_surface_energy_balance
958   
959    INTERFACE usm_swap_timelevel
960       MODULE PROCEDURE usm_swap_timelevel
961    END INTERFACE usm_swap_timelevel
962       
963    INTERFACE usm_wrd_local
964       MODULE PROCEDURE usm_wrd_local
965    END INTERFACE usm_wrd_local
966
967   
968    SAVE
969
970    PRIVATE 
971
972!
973!-- Public functions
974    PUBLIC usm_boundary_condition, usm_check_parameters, usm_init,               &
975           usm_rrd_local,                                                        & 
976           usm_surface_energy_balance, usm_material_heat_model,                  &
977           usm_swap_timelevel, usm_check_data_output, usm_3d_data_averaging,     &
978           usm_data_output_3d, usm_define_netcdf_grid, usm_parin,                &
979           usm_wrd_local, usm_init_arrays
980
981!
982!-- Public parameters, constants and initial values
983    PUBLIC usm_anthropogenic_heat, usm_material_model, usm_wall_mod, &
984           usm_green_heat_model, building_pars,                      &
985           nzb_wall, nzt_wall, t_wall_h, t_wall_v,                   &
986           t_window_h, t_window_v, building_type
987
988
989
990 CONTAINS
991
992!------------------------------------------------------------------------------!
993! Description:
994! ------------
995!> This subroutine creates the necessary indices of the urban surfaces
996!> and plant canopy and it allocates the needed arrays for USM
997!------------------------------------------------------------------------------!
998    SUBROUTINE usm_init_arrays
999   
1000        IMPLICIT NONE
1001       
1002        INTEGER(iwp) ::  l
1003
1004        IF ( debug_output )  CALL debug_message( 'usm_init_arrays', 'start' )
1005
1006!
1007!--     Allocate radiation arrays which are part of the new data type.
1008!--     For horizontal surfaces.
1009        ALLOCATE ( surf_usm_h%surfhf(1:surf_usm_h%ns)    )
1010        ALLOCATE ( surf_usm_h%rad_net_l(1:surf_usm_h%ns) )
1011!
1012!--     For vertical surfaces
1013        DO  l = 0, 3
1014           ALLOCATE ( surf_usm_v(l)%surfhf(1:surf_usm_v(l)%ns)    )
1015           ALLOCATE ( surf_usm_v(l)%rad_net_l(1:surf_usm_v(l)%ns) )
1016        ENDDO
1017
1018!
1019!--     Wall surface model
1020!--     allocate arrays for wall surface model and define pointers
1021!--     allocate array of wall types and wall parameters
1022        ALLOCATE ( surf_usm_h%surface_types(1:surf_usm_h%ns)      )
1023        ALLOCATE ( surf_usm_h%building_type(1:surf_usm_h%ns)      )
1024        ALLOCATE ( surf_usm_h%building_type_name(1:surf_usm_h%ns) )
1025        surf_usm_h%building_type      = 0
1026        surf_usm_h%building_type_name = 'none'
1027        DO  l = 0, 3
1028           ALLOCATE ( surf_usm_v(l)%surface_types(1:surf_usm_v(l)%ns)      )
1029           ALLOCATE ( surf_usm_v(l)%building_type(1:surf_usm_v(l)%ns)      )
1030           ALLOCATE ( surf_usm_v(l)%building_type_name(1:surf_usm_v(l)%ns) )
1031           surf_usm_v(l)%building_type      = 0
1032           surf_usm_v(l)%building_type_name = 'none'
1033        ENDDO
1034!
1035!--     Allocate albedo_type and albedo. Each surface element
1036!--     has 3 values, 0: wall fraction, 1: green fraction, 2: window fraction.
1037        ALLOCATE ( surf_usm_h%albedo_type(0:2,1:surf_usm_h%ns) )
1038        ALLOCATE ( surf_usm_h%albedo(0:2,1:surf_usm_h%ns)      )
1039        surf_usm_h%albedo_type = albedo_type
1040        DO  l = 0, 3
1041           ALLOCATE ( surf_usm_v(l)%albedo_type(0:2,1:surf_usm_v(l)%ns) )
1042           ALLOCATE ( surf_usm_v(l)%albedo(0:2,1:surf_usm_v(l)%ns)      )
1043           surf_usm_v(l)%albedo_type = albedo_type
1044        ENDDO       
1045
1046!
1047!--     Allocate indoor target temperature for summer and winter
1048        ALLOCATE ( surf_usm_h%target_temp_summer(1:surf_usm_h%ns) )
1049        ALLOCATE ( surf_usm_h%target_temp_winter(1:surf_usm_h%ns) )
1050        DO  l = 0, 3
1051           ALLOCATE ( surf_usm_v(l)%target_temp_summer(1:surf_usm_v(l)%ns) )
1052           ALLOCATE ( surf_usm_v(l)%target_temp_winter(1:surf_usm_v(l)%ns) )
1053        ENDDO
1054!
1055!--     In case the indoor model is applied, allocate memory for waste heat
1056!--     and indoor temperature.
1057        IF ( indoor_model )  THEN
1058           ALLOCATE ( surf_usm_h%waste_heat(1:surf_usm_h%ns) )
1059           surf_usm_h%waste_heat = 0.0_wp
1060           DO  l = 0, 3
1061              ALLOCATE ( surf_usm_v(l)%waste_heat(1:surf_usm_v(l)%ns) )
1062              surf_usm_v(l)%waste_heat = 0.0_wp
1063           ENDDO
1064        ENDIF
1065!
1066!--     Allocate flag indicating ground floor level surface elements
1067        ALLOCATE ( surf_usm_h%ground_level(1:surf_usm_h%ns) ) 
1068        DO  l = 0, 3
1069           ALLOCATE ( surf_usm_v(l)%ground_level(1:surf_usm_v(l)%ns) )
1070        ENDDO   
1071!
1072!--      Allocate arrays for relative surface fraction.
1073!--      0 - wall fraction, 1 - green fraction, 2 - window fraction
1074         ALLOCATE ( surf_usm_h%frac(0:2,1:surf_usm_h%ns) )
1075         surf_usm_h%frac = 0.0_wp
1076         DO  l = 0, 3
1077            ALLOCATE ( surf_usm_v(l)%frac(0:2,1:surf_usm_v(l)%ns) )
1078            surf_usm_v(l)%frac = 0.0_wp
1079         ENDDO
1080
1081!
1082!--     wall and roof surface parameters. First for horizontal surfaces
1083        ALLOCATE ( surf_usm_h%isroof_surf(1:surf_usm_h%ns)        )
1084        ALLOCATE ( surf_usm_h%lambda_surf(1:surf_usm_h%ns)        )
1085        ALLOCATE ( surf_usm_h%lambda_surf_window(1:surf_usm_h%ns) )
1086        ALLOCATE ( surf_usm_h%lambda_surf_green(1:surf_usm_h%ns)  )
1087        ALLOCATE ( surf_usm_h%c_surface(1:surf_usm_h%ns)          )
1088        ALLOCATE ( surf_usm_h%c_surface_window(1:surf_usm_h%ns)   )
1089        ALLOCATE ( surf_usm_h%c_surface_green(1:surf_usm_h%ns)    )
1090        ALLOCATE ( surf_usm_h%transmissivity(1:surf_usm_h%ns)     )
1091        ALLOCATE ( surf_usm_h%lai(1:surf_usm_h%ns)                )
1092        ALLOCATE ( surf_usm_h%emissivity(0:2,1:surf_usm_h%ns)     )
1093        ALLOCATE ( surf_usm_h%r_a(1:surf_usm_h%ns)                )
1094        ALLOCATE ( surf_usm_h%r_a_green(1:surf_usm_h%ns)          )
1095        ALLOCATE ( surf_usm_h%r_a_window(1:surf_usm_h%ns)         )
1096        ALLOCATE ( surf_usm_h%green_type_roof(1:surf_usm_h%ns)    )
1097        ALLOCATE ( surf_usm_h%r_s(1:surf_usm_h%ns)                )
1098       
1099!
1100!--     For vertical surfaces.
1101        DO  l = 0, 3
1102           ALLOCATE ( surf_usm_v(l)%lambda_surf(1:surf_usm_v(l)%ns)        )
1103           ALLOCATE ( surf_usm_v(l)%c_surface(1:surf_usm_v(l)%ns)          )
1104           ALLOCATE ( surf_usm_v(l)%lambda_surf_window(1:surf_usm_v(l)%ns) )
1105           ALLOCATE ( surf_usm_v(l)%c_surface_window(1:surf_usm_v(l)%ns)   )
1106           ALLOCATE ( surf_usm_v(l)%lambda_surf_green(1:surf_usm_v(l)%ns)  )
1107           ALLOCATE ( surf_usm_v(l)%c_surface_green(1:surf_usm_v(l)%ns)    )
1108           ALLOCATE ( surf_usm_v(l)%transmissivity(1:surf_usm_v(l)%ns)     )
1109           ALLOCATE ( surf_usm_v(l)%lai(1:surf_usm_v(l)%ns)                )
1110           ALLOCATE ( surf_usm_v(l)%emissivity(0:2,1:surf_usm_v(l)%ns)     )
1111           ALLOCATE ( surf_usm_v(l)%r_a(1:surf_usm_v(l)%ns)                )
1112           ALLOCATE ( surf_usm_v(l)%r_a_green(1:surf_usm_v(l)%ns)          )
1113           ALLOCATE ( surf_usm_v(l)%r_a_window(1:surf_usm_v(l)%ns)         )           
1114           ALLOCATE ( surf_usm_v(l)%r_s(1:surf_usm_v(l)%ns)                )
1115        ENDDO
1116
1117!       
1118!--     allocate wall and roof material parameters. First for horizontal surfaces
1119        ALLOCATE ( surf_usm_h%thickness_wall(1:surf_usm_h%ns)                    )
1120        ALLOCATE ( surf_usm_h%thickness_window(1:surf_usm_h%ns)                  )
1121        ALLOCATE ( surf_usm_h%thickness_green(1:surf_usm_h%ns)                   )
1122        ALLOCATE ( surf_usm_h%lambda_h(nzb_wall:nzt_wall,1:surf_usm_h%ns)        )
1123        ALLOCATE ( surf_usm_h%rho_c_wall(nzb_wall:nzt_wall,1:surf_usm_h%ns)      )
1124        ALLOCATE ( surf_usm_h%lambda_h_window(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1125        ALLOCATE ( surf_usm_h%rho_c_window(nzb_wall:nzt_wall,1:surf_usm_h%ns)    )
1126        ALLOCATE ( surf_usm_h%lambda_h_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)  )
1127        ALLOCATE ( surf_usm_h%rho_c_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)     )
1128
1129        ALLOCATE ( surf_usm_h%rho_c_total_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)    )
1130        ALLOCATE ( surf_usm_h%n_vg_green(1:surf_usm_h%ns)                             )
1131        ALLOCATE ( surf_usm_h%alpha_vg_green(1:surf_usm_h%ns)                         )
1132        ALLOCATE ( surf_usm_h%l_vg_green(1:surf_usm_h%ns)                             )
1133        ALLOCATE ( surf_usm_h%gamma_w_green_sat(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)  )
1134        ALLOCATE ( surf_usm_h%lambda_w_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)       )
1135        ALLOCATE ( surf_usm_h%gamma_w_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)        )
1136        ALLOCATE ( surf_usm_h%tswc_h_m(nzb_wall:nzt_wall,1:surf_usm_h%ns)             )
1137
1138!
1139!--     For vertical surfaces.
1140        DO  l = 0, 3
1141           ALLOCATE ( surf_usm_v(l)%thickness_wall(1:surf_usm_v(l)%ns)                    )
1142           ALLOCATE ( surf_usm_v(l)%thickness_window(1:surf_usm_v(l)%ns)                  )
1143           ALLOCATE ( surf_usm_v(l)%thickness_green(1:surf_usm_v(l)%ns)                   )
1144           ALLOCATE ( surf_usm_v(l)%lambda_h(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)        )
1145           ALLOCATE ( surf_usm_v(l)%rho_c_wall(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)      )
1146           ALLOCATE ( surf_usm_v(l)%lambda_h_window(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1147           ALLOCATE ( surf_usm_v(l)%rho_c_window(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)    )
1148           ALLOCATE ( surf_usm_v(l)%lambda_h_green(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)  )
1149           ALLOCATE ( surf_usm_v(l)%rho_c_green(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)     )
1150        ENDDO
1151
1152!
1153!--     allocate green wall and roof vegetation and soil parameters. First horizontal surfaces
1154        ALLOCATE ( surf_usm_h%g_d(1:surf_usm_h%ns)              )
1155        ALLOCATE ( surf_usm_h%c_liq(1:surf_usm_h%ns)            )
1156        ALLOCATE ( surf_usm_h%qsws_liq(1:surf_usm_h%ns)         )
1157        ALLOCATE ( surf_usm_h%qsws_veg(1:surf_usm_h%ns)         )
1158        ALLOCATE ( surf_usm_h%r_canopy(1:surf_usm_h%ns)         )
1159        ALLOCATE ( surf_usm_h%r_canopy_min(1:surf_usm_h%ns)     )
1160        ALLOCATE ( surf_usm_h%qsws_eb(1:surf_usm_h%ns)          )
1161        ALLOCATE ( surf_usm_h%pt_10cm(1:surf_usm_h%ns)          ) 
1162        ALLOCATE ( surf_usm_h%pt_2m(1:surf_usm_h%ns)            ) 
1163
1164!
1165!--     For vertical surfaces.
1166        DO  l = 0, 3
1167          ALLOCATE ( surf_usm_v(l)%g_d(1:surf_usm_v(l)%ns)              )
1168          ALLOCATE ( surf_usm_v(l)%c_liq(1:surf_usm_v(l)%ns)            )
1169          ALLOCATE ( surf_usm_v(l)%qsws_liq(1:surf_usm_v(l)%ns)         )
1170          ALLOCATE ( surf_usm_v(l)%qsws_veg(1:surf_usm_v(l)%ns)         )
1171          ALLOCATE ( surf_usm_v(l)%qsws_eb(1:surf_usm_v(l)%ns)          )
1172          ALLOCATE ( surf_usm_v(l)%r_canopy(1:surf_usm_v(l)%ns)         )
1173          ALLOCATE ( surf_usm_v(l)%r_canopy_min(1:surf_usm_v(l)%ns)     )
1174          ALLOCATE ( surf_usm_v(l)%pt_10cm(1:surf_usm_v(l)%ns)          )
1175        ENDDO
1176
1177!
1178!--     allocate wall and roof layers sizes. For horizontal surfaces.
1179        ALLOCATE ( zwn(nzb_wall:nzt_wall)                                        )
1180        ALLOCATE ( surf_usm_h%dz_wall(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)       )
1181        ALLOCATE ( zwn_window(nzb_wall:nzt_wall)                                 )
1182        ALLOCATE ( surf_usm_h%dz_window(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)     )
1183        ALLOCATE ( zwn_green(nzb_wall:nzt_wall)                                  )
1184        ALLOCATE ( surf_usm_h%dz_green(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)      )
1185        ALLOCATE ( surf_usm_h%ddz_wall(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)      )
1186        ALLOCATE ( surf_usm_h%dz_wall_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)    )
1187        ALLOCATE ( surf_usm_h%ddz_wall_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)   )
1188        ALLOCATE ( surf_usm_h%zw(nzb_wall:nzt_wall,1:surf_usm_h%ns)              )
1189        ALLOCATE ( surf_usm_h%ddz_window(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)    )
1190        ALLOCATE ( surf_usm_h%dz_window_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)  )
1191        ALLOCATE ( surf_usm_h%ddz_window_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1192        ALLOCATE ( surf_usm_h%zw_window(nzb_wall:nzt_wall,1:surf_usm_h%ns)       )
1193        ALLOCATE ( surf_usm_h%ddz_green(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)     )
1194        ALLOCATE ( surf_usm_h%dz_green_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)   )
1195        ALLOCATE ( surf_usm_h%ddz_green_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)  )
1196        ALLOCATE ( surf_usm_h%zw_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)        )
1197
1198!
1199!--     For vertical surfaces.
1200        DO  l = 0, 3
1201           ALLOCATE ( surf_usm_v(l)%dz_wall(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)       )
1202           ALLOCATE ( surf_usm_v(l)%dz_window(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)     )
1203           ALLOCATE ( surf_usm_v(l)%dz_green(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)      )
1204           ALLOCATE ( surf_usm_v(l)%ddz_wall(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)      )
1205           ALLOCATE ( surf_usm_v(l)%dz_wall_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)    )
1206           ALLOCATE ( surf_usm_v(l)%ddz_wall_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)   )
1207           ALLOCATE ( surf_usm_v(l)%zw(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)              )
1208           ALLOCATE ( surf_usm_v(l)%ddz_window(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)    )
1209           ALLOCATE ( surf_usm_v(l)%dz_window_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)  )
1210           ALLOCATE ( surf_usm_v(l)%ddz_window_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1211           ALLOCATE ( surf_usm_v(l)%zw_window(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)       )
1212           ALLOCATE ( surf_usm_v(l)%ddz_green(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)     )
1213           ALLOCATE ( surf_usm_v(l)%dz_green_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)   )
1214           ALLOCATE ( surf_usm_v(l)%ddz_green_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)  )
1215           ALLOCATE ( surf_usm_v(l)%zw_green(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)        )
1216        ENDDO
1217
1218!
1219!--     allocate wall and roof temperature arrays, for horizontal walls
1220!
1221!--     Allocate if required. Note, in case of restarts, some of these arrays
1222!--     might be already allocated.
1223        IF ( .NOT. ALLOCATED( t_surf_wall_h_1 ) )                              &
1224           ALLOCATE ( t_surf_wall_h_1(1:surf_usm_h%ns) )
1225        IF ( .NOT. ALLOCATED( t_surf_wall_h_2 ) )                              &
1226           ALLOCATE ( t_surf_wall_h_2(1:surf_usm_h%ns) )
1227        IF ( .NOT. ALLOCATED( t_wall_h_1 ) )                                   &           
1228           ALLOCATE ( t_wall_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1229        IF ( .NOT. ALLOCATED( t_wall_h_2 ) )                                   &           
1230           ALLOCATE ( t_wall_h_2(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )         
1231        IF ( .NOT. ALLOCATED( t_surf_window_h_1 ) )                            &
1232           ALLOCATE ( t_surf_window_h_1(1:surf_usm_h%ns) )
1233        IF ( .NOT. ALLOCATED( t_surf_window_h_2 ) )                            &
1234           ALLOCATE ( t_surf_window_h_2(1:surf_usm_h%ns) )
1235        IF ( .NOT. ALLOCATED( t_window_h_1 ) )                                 &           
1236           ALLOCATE ( t_window_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1237        IF ( .NOT. ALLOCATED( t_window_h_2 ) )                                 &           
1238           ALLOCATE ( t_window_h_2(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )         
1239        IF ( .NOT. ALLOCATED( t_surf_green_h_1 ) )                             &
1240           ALLOCATE ( t_surf_green_h_1(1:surf_usm_h%ns) )
1241        IF ( .NOT. ALLOCATED( t_surf_green_h_2 ) )                             &
1242           ALLOCATE ( t_surf_green_h_2(1:surf_usm_h%ns) )
1243        IF ( .NOT. ALLOCATED( t_green_h_1 ) )                                  &           
1244           ALLOCATE ( t_green_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1245        IF ( .NOT. ALLOCATED( t_green_h_2 ) )                                  &           
1246           ALLOCATE ( t_green_h_2(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )         
1247        IF ( .NOT. ALLOCATED( swc_h_1 ) )                                      &           
1248           ALLOCATE ( swc_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1249        IF ( .NOT. ALLOCATED( swc_sat_h_1 ) )                                  &           
1250           ALLOCATE ( swc_sat_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1251        IF ( .NOT. ALLOCATED( swc_res_h_1 ) )                                  &           
1252           ALLOCATE ( swc_res_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1253        IF ( .NOT. ALLOCATED( swc_h_2 ) )                                      &           
1254           ALLOCATE ( swc_h_2(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
1255        IF ( .NOT. ALLOCATED( rootfr_h_1 ) )                                   &           
1256           ALLOCATE ( rootfr_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1257        IF ( .NOT. ALLOCATED( wilt_h_1 ) )                                     &           
1258           ALLOCATE ( wilt_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1259        IF ( .NOT. ALLOCATED( fc_h_1 ) )                                       &           
1260           ALLOCATE ( fc_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1261
1262        IF ( .NOT. ALLOCATED( m_liq_usm_h_1%var_usm_1d ) )                     &
1263           ALLOCATE ( m_liq_usm_h_1%var_usm_1d(1:surf_usm_h%ns) )
1264        IF ( .NOT. ALLOCATED( m_liq_usm_h_2%var_usm_1d ) )                     &
1265           ALLOCATE ( m_liq_usm_h_2%var_usm_1d(1:surf_usm_h%ns) )
1266           
1267!           
1268!--     initial assignment of the pointers
1269        t_wall_h    => t_wall_h_1;   t_wall_h_p   => t_wall_h_2
1270        t_window_h  => t_window_h_1; t_window_h_p => t_window_h_2
1271        t_green_h   => t_green_h_1;  t_green_h_p  => t_green_h_2
1272        t_surf_wall_h   => t_surf_wall_h_1;   t_surf_wall_h_p   => t_surf_wall_h_2           
1273        t_surf_window_h => t_surf_window_h_1; t_surf_window_h_p => t_surf_window_h_2 
1274        t_surf_green_h  => t_surf_green_h_1;  t_surf_green_h_p  => t_surf_green_h_2           
1275        m_liq_usm_h     => m_liq_usm_h_1;     m_liq_usm_h_p     => m_liq_usm_h_2
1276        swc_h     => swc_h_1; swc_h_p => swc_h_2
1277        swc_sat_h => swc_sat_h_1
1278        swc_res_h => swc_res_h_1
1279        rootfr_h  => rootfr_h_1
1280        wilt_h    => wilt_h_1
1281        fc_h      => fc_h_1
1282
1283!
1284!--     allocate wall and roof temperature arrays, for vertical walls if required
1285!
1286!--     Allocate if required. Note, in case of restarts, some of these arrays
1287!--     might be already allocated.
1288        DO  l = 0, 3
1289           IF ( .NOT. ALLOCATED( t_surf_wall_v_1(l)%t ) )                      &
1290              ALLOCATE ( t_surf_wall_v_1(l)%t(1:surf_usm_v(l)%ns) )
1291           IF ( .NOT. ALLOCATED( t_surf_wall_v_2(l)%t ) )                      &
1292              ALLOCATE ( t_surf_wall_v_2(l)%t(1:surf_usm_v(l)%ns) )
1293           IF ( .NOT. ALLOCATED( t_wall_v_1(l)%t ) )                           &           
1294              ALLOCATE ( t_wall_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1295           IF ( .NOT. ALLOCATED( t_wall_v_2(l)%t ) )                           &           
1296              ALLOCATE ( t_wall_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1297           IF ( .NOT. ALLOCATED( t_surf_window_v_1(l)%t ) )                    &
1298              ALLOCATE ( t_surf_window_v_1(l)%t(1:surf_usm_v(l)%ns) )
1299           IF ( .NOT. ALLOCATED( t_surf_window_v_2(l)%t ) )                    &
1300              ALLOCATE ( t_surf_window_v_2(l)%t(1:surf_usm_v(l)%ns) )
1301           IF ( .NOT. ALLOCATED( t_window_v_1(l)%t ) )                         &           
1302              ALLOCATE ( t_window_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1303           IF ( .NOT. ALLOCATED( t_window_v_2(l)%t ) )                         &           
1304              ALLOCATE ( t_window_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1305           IF ( .NOT. ALLOCATED( t_surf_green_v_1(l)%t ) )                     &
1306              ALLOCATE ( t_surf_green_v_1(l)%t(1:surf_usm_v(l)%ns) )
1307           IF ( .NOT. ALLOCATED( t_surf_green_v_2(l)%t ) )                     &
1308              ALLOCATE ( t_surf_green_v_2(l)%t(1:surf_usm_v(l)%ns) )
1309           IF ( .NOT. ALLOCATED( t_green_v_1(l)%t ) )                          &           
1310              ALLOCATE ( t_green_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1311           IF ( .NOT. ALLOCATED( t_green_v_2(l)%t ) )                          &           
1312              ALLOCATE ( t_green_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1313           IF ( .NOT. ALLOCATED( m_liq_usm_v_1(l)%var_usm_1d ) )               &
1314              ALLOCATE ( m_liq_usm_v_1(l)%var_usm_1d(1:surf_usm_v(l)%ns) )
1315           IF ( .NOT. ALLOCATED( m_liq_usm_v_2(l)%var_usm_1d ) )               &
1316              ALLOCATE ( m_liq_usm_v_2(l)%var_usm_1d(1:surf_usm_v(l)%ns) )
1317           IF ( .NOT. ALLOCATED( swc_v_1(l)%t ) )                              &           
1318              ALLOCATE ( swc_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1319           IF ( .NOT. ALLOCATED( swc_v_2(l)%t ) )                              &           
1320              ALLOCATE ( swc_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1321        ENDDO
1322!
1323!--     initial assignment of the pointers
1324        t_wall_v        => t_wall_v_1;        t_wall_v_p        => t_wall_v_2
1325        t_surf_wall_v   => t_surf_wall_v_1;   t_surf_wall_v_p   => t_surf_wall_v_2
1326        t_window_v      => t_window_v_1;      t_window_v_p      => t_window_v_2
1327        t_green_v       => t_green_v_1;       t_green_v_p       => t_green_v_2
1328        t_surf_window_v => t_surf_window_v_1; t_surf_window_v_p => t_surf_window_v_2
1329        t_surf_green_v  => t_surf_green_v_1;  t_surf_green_v_p  => t_surf_green_v_2
1330        m_liq_usm_v     => m_liq_usm_v_1;     m_liq_usm_v_p     => m_liq_usm_v_2
1331        swc_v           => swc_v_1;           swc_v_p           => swc_v_2
1332
1333!
1334!--     Allocate intermediate timestep arrays. For horizontal surfaces.
1335        ALLOCATE ( surf_usm_h%tt_surface_wall_m(1:surf_usm_h%ns)               )
1336        ALLOCATE ( surf_usm_h%tt_wall_m(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)   )
1337        ALLOCATE ( surf_usm_h%tt_surface_window_m(1:surf_usm_h%ns)             )
1338        ALLOCATE ( surf_usm_h%tt_window_m(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
1339        ALLOCATE ( surf_usm_h%tt_green_m(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)  )
1340        ALLOCATE ( surf_usm_h%tt_surface_green_m(1:surf_usm_h%ns)              )
1341
1342!
1343!--    Allocate intermediate timestep arrays
1344!--    Horizontal surfaces
1345       ALLOCATE ( tm_liq_usm_h_m%var_usm_1d(1:surf_usm_h%ns)                   )
1346!
1347!--    Horizontal surfaces
1348       DO  l = 0, 3
1349          ALLOCATE ( tm_liq_usm_v_m(l)%var_usm_1d(1:surf_usm_v(l)%ns)          )
1350       ENDDO 
1351       
1352!
1353!--     Set inital values for prognostic quantities
1354        IF ( ALLOCATED( surf_usm_h%tt_surface_wall_m )   )  surf_usm_h%tt_surface_wall_m   = 0.0_wp
1355        IF ( ALLOCATED( surf_usm_h%tt_wall_m )           )  surf_usm_h%tt_wall_m           = 0.0_wp
1356        IF ( ALLOCATED( surf_usm_h%tt_surface_window_m ) )  surf_usm_h%tt_surface_window_m = 0.0_wp
1357        IF ( ALLOCATED( surf_usm_h%tt_window_m    )      )  surf_usm_h%tt_window_m         = 0.0_wp
1358        IF ( ALLOCATED( surf_usm_h%tt_green_m    )       )  surf_usm_h%tt_green_m          = 0.0_wp
1359        IF ( ALLOCATED( surf_usm_h%tt_surface_green_m )  )  surf_usm_h%tt_surface_green_m  = 0.0_wp
1360!
1361!--     Now, for vertical surfaces
1362        DO  l = 0, 3
1363           ALLOCATE ( surf_usm_v(l)%tt_surface_wall_m(1:surf_usm_v(l)%ns)               )
1364           ALLOCATE ( surf_usm_v(l)%tt_wall_m(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)   )
1365           IF ( ALLOCATED( surf_usm_v(l)%tt_surface_wall_m ) )  surf_usm_v(l)%tt_surface_wall_m = 0.0_wp
1366           IF ( ALLOCATED( surf_usm_v(l)%tt_wall_m    ) )  surf_usm_v(l)%tt_wall_m    = 0.0_wp
1367           ALLOCATE ( surf_usm_v(l)%tt_surface_window_m(1:surf_usm_v(l)%ns)             )
1368           ALLOCATE ( surf_usm_v(l)%tt_window_m(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
1369           IF ( ALLOCATED( surf_usm_v(l)%tt_surface_window_m ) )  surf_usm_v(l)%tt_surface_window_m = 0.0_wp
1370           IF ( ALLOCATED( surf_usm_v(l)%tt_window_m  ) )  surf_usm_v(l)%tt_window_m    = 0.0_wp
1371           ALLOCATE ( surf_usm_v(l)%tt_surface_green_m(1:surf_usm_v(l)%ns)              )
1372           IF ( ALLOCATED( surf_usm_v(l)%tt_surface_green_m ) )  surf_usm_v(l)%tt_surface_green_m = 0.0_wp
1373           ALLOCATE ( surf_usm_v(l)%tt_green_m(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)  )
1374           IF ( ALLOCATED( surf_usm_v(l)%tt_green_m   ) )  surf_usm_v(l)%tt_green_m    = 0.0_wp
1375        ENDDO
1376!
1377!--     allocate wall heat flux output array and set initial values. For horizontal surfaces
1378!        ALLOCATE ( surf_usm_h%wshf(1:surf_usm_h%ns)    )  !can be removed
1379        ALLOCATE ( surf_usm_h%wshf_eb(1:surf_usm_h%ns) )
1380        ALLOCATE ( surf_usm_h%wghf_eb(1:surf_usm_h%ns) )
1381        ALLOCATE ( surf_usm_h%wghf_eb_window(1:surf_usm_h%ns) )
1382        ALLOCATE ( surf_usm_h%wghf_eb_green(1:surf_usm_h%ns) )
1383        ALLOCATE ( surf_usm_h%iwghf_eb(1:surf_usm_h%ns) )
1384        ALLOCATE ( surf_usm_h%iwghf_eb_window(1:surf_usm_h%ns) )
1385        IF ( ALLOCATED( surf_usm_h%wshf    ) )  surf_usm_h%wshf    = 0.0_wp
1386        IF ( ALLOCATED( surf_usm_h%wshf_eb ) )  surf_usm_h%wshf_eb = 0.0_wp
1387        IF ( ALLOCATED( surf_usm_h%wghf_eb ) )  surf_usm_h%wghf_eb = 0.0_wp
1388        IF ( ALLOCATED( surf_usm_h%wghf_eb_window ) )  surf_usm_h%wghf_eb_window = 0.0_wp
1389        IF ( ALLOCATED( surf_usm_h%wghf_eb_green ) )  surf_usm_h%wghf_eb_green = 0.0_wp
1390        IF ( ALLOCATED( surf_usm_h%iwghf_eb ) )  surf_usm_h%iwghf_eb = 0.0_wp
1391        IF ( ALLOCATED( surf_usm_h%iwghf_eb_window ) )  surf_usm_h%iwghf_eb_window = 0.0_wp
1392!
1393!--     Now, for vertical surfaces
1394        DO  l = 0, 3
1395!           ALLOCATE ( surf_usm_v(l)%wshf(1:surf_usm_v(l)%ns)    )    ! can be removed
1396           ALLOCATE ( surf_usm_v(l)%wshf_eb(1:surf_usm_v(l)%ns) )
1397           ALLOCATE ( surf_usm_v(l)%wghf_eb(1:surf_usm_v(l)%ns) )
1398           ALLOCATE ( surf_usm_v(l)%wghf_eb_window(1:surf_usm_v(l)%ns) )
1399           ALLOCATE ( surf_usm_v(l)%wghf_eb_green(1:surf_usm_v(l)%ns) )
1400           ALLOCATE ( surf_usm_v(l)%iwghf_eb(1:surf_usm_v(l)%ns) )
1401           ALLOCATE ( surf_usm_v(l)%iwghf_eb_window(1:surf_usm_v(l)%ns) )
1402           IF ( ALLOCATED( surf_usm_v(l)%wshf    ) )  surf_usm_v(l)%wshf    = 0.0_wp
1403           IF ( ALLOCATED( surf_usm_v(l)%wshf_eb ) )  surf_usm_v(l)%wshf_eb = 0.0_wp
1404           IF ( ALLOCATED( surf_usm_v(l)%wghf_eb ) )  surf_usm_v(l)%wghf_eb = 0.0_wp
1405           IF ( ALLOCATED( surf_usm_v(l)%wghf_eb_window ) )  surf_usm_v(l)%wghf_eb_window = 0.0_wp
1406           IF ( ALLOCATED( surf_usm_v(l)%wghf_eb_green ) )  surf_usm_v(l)%wghf_eb_green = 0.0_wp
1407           IF ( ALLOCATED( surf_usm_v(l)%iwghf_eb ) )  surf_usm_v(l)%iwghf_eb = 0.0_wp
1408           IF ( ALLOCATED( surf_usm_v(l)%iwghf_eb_window ) )  surf_usm_v(l)%iwghf_eb_window = 0.0_wp
1409        ENDDO
1410
1411        IF ( debug_output )  CALL debug_message( 'usm_init_arrays', 'end' )
1412       
1413    END SUBROUTINE usm_init_arrays
1414
1415
1416!------------------------------------------------------------------------------!
1417! Description:
1418! ------------
1419!> Sum up and time-average urban surface output quantities as well as allocate
1420!> the array necessary for storing the average.
1421!------------------------------------------------------------------------------!
1422    SUBROUTINE usm_3d_data_averaging( mode, variable )
1423
1424        IMPLICIT NONE
1425
1426        CHARACTER(LEN=*), INTENT(IN) ::  mode
1427        CHARACTER(LEN=*), INTENT(IN) :: variable
1428 
1429        INTEGER(iwp)                                       :: i, j, k, l, m, ids, idsint, iwl, istat  !< runnin indices
1430        CHARACTER(LEN=varnamelength)                       :: var                                     !< trimmed variable
1431        INTEGER(iwp), PARAMETER                            :: nd = 5                                  !< number of directions
1432        CHARACTER(LEN=6), DIMENSION(0:nd-1), PARAMETER     :: dirname = (/ '_roof ', '_south', '_north', '_west ', '_east ' /)
1433        INTEGER(iwp), DIMENSION(0:nd-1), PARAMETER         :: dirint = (/ iup_u, isouth_u, inorth_u, iwest_u, ieast_u /)
1434
1435        IF ( variable(1:4) == 'usm_' )  THEN  ! is such a check really rquired?
1436
1437!
1438!--     find the real name of the variable
1439        ids = -1
1440        l = -1
1441        var = TRIM(variable)
1442        DO i = 0, nd-1
1443            k = len(TRIM(var))
1444            j = len(TRIM(dirname(i)))
1445            IF ( TRIM(var(k-j+1:k)) == TRIM(dirname(i)) )  THEN
1446                ids = i
1447                idsint = dirint(ids)
1448                var = var(:k-j)
1449                EXIT
1450            ENDIF
1451        ENDDO
1452        l = idsint - 2  ! horisontal direction index - terible hack !
1453        IF ( l < 0 .OR. l > 3 ) THEN
1454           l = -1
1455        END IF
1456        IF ( ids == -1 )  THEN
1457            var = TRIM(variable)
1458        ENDIF
1459        IF ( var(1:11) == 'usm_t_wall_'  .AND.  len(TRIM(var)) >= 12 )  THEN
1460!
1461!--          wall layers
1462            READ(var(12:12), '(I1)', iostat=istat ) iwl
1463            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
1464                var = var(1:10)
1465            ELSE
1466!
1467!--             wrong wall layer index
1468                RETURN
1469            ENDIF
1470        ENDIF
1471        IF ( var(1:13) == 'usm_t_window_'  .AND.  len(TRIM(var)) >= 14 )  THEN
1472!
1473!--          wall layers
1474            READ(var(14:14), '(I1)', iostat=istat ) iwl
1475            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
1476                var = var(1:12)
1477            ELSE
1478!
1479!--             wrong window layer index
1480                RETURN
1481            ENDIF
1482        ENDIF
1483        IF ( var(1:12) == 'usm_t_green_'  .AND.  len(TRIM(var)) >= 13 )  THEN
1484!
1485!--          wall layers
1486            READ(var(13:13), '(I1)', iostat=istat ) iwl
1487            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
1488                var = var(1:11)
1489            ELSE
1490!
1491!--             wrong green layer index
1492                RETURN
1493            ENDIF
1494        ENDIF
1495        IF ( var(1:8) == 'usm_swc_'  .AND.  len(TRIM(var)) >= 9 )  THEN
1496!
1497!--          swc layers
1498            READ(var(9:9), '(I1)', iostat=istat ) iwl
1499            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
1500                var = var(1:7)
1501            ELSE
1502!
1503!--             wrong swc layer index
1504                RETURN
1505            ENDIF
1506        ENDIF
1507
1508        IF ( mode == 'allocate' )  THEN
1509           
1510           SELECT CASE ( TRIM( var ) )
1511
1512                CASE ( 'usm_wshf' )
1513!
1514!--                 array of sensible heat flux from surfaces
1515!--                 land surfaces
1516                    IF ( l == -1 ) THEN
1517                       IF ( .NOT.  ALLOCATED(surf_usm_h%wshf_eb_av) )  THEN
1518                          ALLOCATE ( surf_usm_h%wshf_eb_av(1:surf_usm_h%ns) )
1519                          surf_usm_h%wshf_eb_av = 0.0_wp
1520                       ENDIF
1521                    ELSE
1522                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%wshf_eb_av) )  THEN
1523                           ALLOCATE ( surf_usm_v(l)%wshf_eb_av(1:surf_usm_v(l)%ns) )
1524                           surf_usm_v(l)%wshf_eb_av = 0.0_wp
1525                       ENDIF
1526                    ENDIF
1527                   
1528                CASE ( 'usm_qsws' )
1529!
1530!--                 array of latent heat flux from surfaces
1531!--                 land surfaces
1532                    IF ( l == -1 .AND. .NOT.  ALLOCATED(surf_usm_h%qsws_eb_av) )  THEN
1533                        ALLOCATE ( surf_usm_h%qsws_eb_av(1:surf_usm_h%ns) )
1534                        surf_usm_h%qsws_eb_av = 0.0_wp
1535                    ELSE
1536                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%qsws_eb_av) )  THEN
1537                           ALLOCATE ( surf_usm_v(l)%qsws_eb_av(1:surf_usm_v(l)%ns) )
1538                           surf_usm_v(l)%qsws_eb_av = 0.0_wp
1539                       ENDIF
1540                    ENDIF
1541                   
1542                CASE ( 'usm_qsws_veg' )
1543!
1544!--                 array of latent heat flux from vegetation surfaces
1545!--                 land surfaces
1546                    IF ( l == -1 .AND. .NOT.  ALLOCATED(surf_usm_h%qsws_veg_av) )  THEN
1547                        ALLOCATE ( surf_usm_h%qsws_veg_av(1:surf_usm_h%ns) )
1548                        surf_usm_h%qsws_veg_av = 0.0_wp
1549                    ELSE
1550                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%qsws_veg_av) )  THEN
1551                           ALLOCATE ( surf_usm_v(l)%qsws_veg_av(1:surf_usm_v(l)%ns) )
1552                           surf_usm_v(l)%qsws_veg_av = 0.0_wp
1553                       ENDIF
1554                    ENDIF
1555                   
1556                CASE ( 'usm_qsws_liq' )
1557!
1558!--                 array of latent heat flux from surfaces with liquid
1559!--                 land surfaces
1560                    IF ( l == -1 .AND. .NOT.  ALLOCATED(surf_usm_h%qsws_liq_av) )  THEN
1561                        ALLOCATE ( surf_usm_h%qsws_liq_av(1:surf_usm_h%ns) )
1562                        surf_usm_h%qsws_liq_av = 0.0_wp
1563                    ELSE
1564                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%qsws_liq_av) )  THEN
1565                           ALLOCATE ( surf_usm_v(l)%qsws_liq_av(1:surf_usm_v(l)%ns) )
1566                           surf_usm_v(l)%qsws_liq_av = 0.0_wp
1567                       ENDIF
1568                    ENDIF
1569!
1570!--             Please note, the following output quantities belongs to the
1571!--             individual tile fractions - ground heat flux at wall-, window-,
1572!--             and green fraction. Aggregated ground-heat flux is treated
1573!--             accordingly in average_3d_data, sum_up_3d_data, etc..
1574                CASE ( 'usm_wghf' )
1575!
1576!--                 array of heat flux from ground (wall, roof, land)
1577                    IF ( l == -1 ) THEN
1578                       IF ( .NOT.  ALLOCATED(surf_usm_h%wghf_eb_av) )  THEN
1579                           ALLOCATE ( surf_usm_h%wghf_eb_av(1:surf_usm_h%ns) )
1580                           surf_usm_h%wghf_eb_av = 0.0_wp
1581                       ENDIF
1582                    ELSE
1583                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%wghf_eb_av) )  THEN
1584                           ALLOCATE ( surf_usm_v(l)%wghf_eb_av(1:surf_usm_v(l)%ns) )
1585                           surf_usm_v(l)%wghf_eb_av = 0.0_wp
1586                       ENDIF
1587                    ENDIF
1588
1589                CASE ( 'usm_wghf_window' )
1590!
1591!--                 array of heat flux from window ground (wall, roof, land)
1592                    IF ( l == -1 ) THEN
1593                       IF ( .NOT.  ALLOCATED(surf_usm_h%wghf_eb_window_av) )  THEN
1594                           ALLOCATE ( surf_usm_h%wghf_eb_window_av(1:surf_usm_h%ns) )
1595                           surf_usm_h%wghf_eb_window_av = 0.0_wp
1596                       ENDIF
1597                    ELSE
1598                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%wghf_eb_window_av) )  THEN
1599                           ALLOCATE ( surf_usm_v(l)%wghf_eb_window_av(1:surf_usm_v(l)%ns) )
1600                           surf_usm_v(l)%wghf_eb_window_av = 0.0_wp
1601                       ENDIF
1602                    ENDIF
1603
1604                CASE ( 'usm_wghf_green' )
1605!
1606!--                 array of heat flux from green ground (wall, roof, land)
1607                    IF ( l == -1 ) THEN
1608                       IF ( .NOT.  ALLOCATED(surf_usm_h%wghf_eb_green_av) )  THEN
1609                           ALLOCATE ( surf_usm_h%wghf_eb_green_av(1:surf_usm_h%ns) )
1610                           surf_usm_h%wghf_eb_green_av = 0.0_wp
1611                       ENDIF
1612                    ELSE
1613                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%wghf_eb_green_av) )  THEN
1614                           ALLOCATE ( surf_usm_v(l)%wghf_eb_green_av(1:surf_usm_v(l)%ns) )
1615                           surf_usm_v(l)%wghf_eb_green_av = 0.0_wp
1616                       ENDIF
1617                    ENDIF
1618
1619                CASE ( 'usm_iwghf' )
1620!
1621!--                 array of heat flux from indoor ground (wall, roof, land)
1622                    IF ( l == -1 ) THEN
1623                       IF ( .NOT.  ALLOCATED(surf_usm_h%iwghf_eb_av) )  THEN
1624                           ALLOCATE ( surf_usm_h%iwghf_eb_av(1:surf_usm_h%ns) )
1625                           surf_usm_h%iwghf_eb_av = 0.0_wp
1626                       ENDIF
1627                    ELSE
1628                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%iwghf_eb_av) )  THEN
1629                           ALLOCATE ( surf_usm_v(l)%iwghf_eb_av(1:surf_usm_v(l)%ns) )
1630                           surf_usm_v(l)%iwghf_eb_av = 0.0_wp
1631                       ENDIF
1632                    ENDIF
1633
1634                CASE ( 'usm_iwghf_window' )
1635!
1636!--                 array of heat flux from indoor window ground (wall, roof, land)
1637                    IF ( l == -1 ) THEN
1638                       IF ( .NOT.  ALLOCATED(surf_usm_h%iwghf_eb_window_av) )  THEN
1639                           ALLOCATE ( surf_usm_h%iwghf_eb_window_av(1:surf_usm_h%ns) )
1640                           surf_usm_h%iwghf_eb_window_av = 0.0_wp
1641                       ENDIF
1642                    ELSE
1643                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%iwghf_eb_window_av) )  THEN
1644                           ALLOCATE ( surf_usm_v(l)%iwghf_eb_window_av(1:surf_usm_v(l)%ns) )
1645                           surf_usm_v(l)%iwghf_eb_window_av = 0.0_wp
1646                       ENDIF
1647                    ENDIF
1648
1649                CASE ( 'usm_t_surf_wall' )
1650!
1651!--                 surface temperature for surfaces
1652                    IF ( l == -1 ) THEN
1653                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_surf_wall_av) )  THEN
1654                           ALLOCATE ( surf_usm_h%t_surf_wall_av(1:surf_usm_h%ns) )
1655                           surf_usm_h%t_surf_wall_av = 0.0_wp
1656                       ENDIF
1657                    ELSE
1658                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_surf_wall_av) )  THEN
1659                           ALLOCATE ( surf_usm_v(l)%t_surf_wall_av(1:surf_usm_v(l)%ns) )
1660                           surf_usm_v(l)%t_surf_wall_av = 0.0_wp
1661                       ENDIF
1662                    ENDIF
1663
1664                CASE ( 'usm_t_surf_window' )
1665!
1666!--                 surface temperature for window surfaces
1667                    IF ( l == -1 ) THEN
1668                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_surf_window_av) )  THEN
1669                           ALLOCATE ( surf_usm_h%t_surf_window_av(1:surf_usm_h%ns) )
1670                           surf_usm_h%t_surf_window_av = 0.0_wp
1671                       ENDIF
1672                    ELSE
1673                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_surf_window_av) )  THEN
1674                           ALLOCATE ( surf_usm_v(l)%t_surf_window_av(1:surf_usm_v(l)%ns) )
1675                           surf_usm_v(l)%t_surf_window_av = 0.0_wp
1676                       ENDIF
1677                    ENDIF
1678                   
1679                CASE ( 'usm_t_surf_green' )
1680!
1681!--                 surface temperature for green surfaces
1682                    IF ( l == -1 ) THEN
1683                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_surf_green_av) )  THEN
1684                           ALLOCATE ( surf_usm_h%t_surf_green_av(1:surf_usm_h%ns) )
1685                           surf_usm_h%t_surf_green_av = 0.0_wp
1686                       ENDIF
1687                    ELSE
1688                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_surf_green_av) )  THEN
1689                           ALLOCATE ( surf_usm_v(l)%t_surf_green_av(1:surf_usm_v(l)%ns) )
1690                           surf_usm_v(l)%t_surf_green_av = 0.0_wp
1691                       ENDIF
1692                    ENDIF
1693               
1694                CASE ( 'usm_theta_10cm' )
1695!
1696!--                 near surface (10cm) temperature for whole surfaces
1697                    IF ( l == -1 ) THEN
1698                       IF ( .NOT.  ALLOCATED(surf_usm_h%pt_10cm_av) )  THEN
1699                           ALLOCATE ( surf_usm_h%pt_10cm_av(1:surf_usm_h%ns) )
1700                           surf_usm_h%pt_10cm_av = 0.0_wp
1701                       ENDIF
1702                    ELSE
1703                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%pt_10cm_av) )  THEN
1704                           ALLOCATE ( surf_usm_v(l)%pt_10cm_av(1:surf_usm_v(l)%ns) )
1705                           surf_usm_v(l)%pt_10cm_av = 0.0_wp
1706                       ENDIF
1707                    ENDIF
1708                 
1709                CASE ( 'usm_t_wall' )
1710!
1711!--                 wall temperature for iwl layer of walls and land
1712                    IF ( l == -1 ) THEN
1713                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_wall_av) )  THEN
1714                           ALLOCATE ( surf_usm_h%t_wall_av(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1715                           surf_usm_h%t_wall_av = 0.0_wp
1716                       ENDIF
1717                    ELSE
1718                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_wall_av) )  THEN
1719                           ALLOCATE ( surf_usm_v(l)%t_wall_av(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1720                           surf_usm_v(l)%t_wall_av = 0.0_wp
1721                       ENDIF
1722                    ENDIF
1723
1724                CASE ( 'usm_t_window' )
1725!
1726!--                 window temperature for iwl layer of walls and land
1727                    IF ( l == -1 ) THEN
1728                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_window_av) )  THEN
1729                           ALLOCATE ( surf_usm_h%t_window_av(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1730                           surf_usm_h%t_window_av = 0.0_wp
1731                       ENDIF
1732                    ELSE
1733                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_window_av) )  THEN
1734                           ALLOCATE ( surf_usm_v(l)%t_window_av(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1735                           surf_usm_v(l)%t_window_av = 0.0_wp
1736                       ENDIF
1737                    ENDIF
1738
1739                CASE ( 'usm_t_green' )
1740!
1741!--                 green temperature for iwl layer of walls and land
1742                    IF ( l == -1 ) THEN
1743                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_green_av) )  THEN
1744                           ALLOCATE ( surf_usm_h%t_green_av(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1745                           surf_usm_h%t_green_av = 0.0_wp
1746                       ENDIF
1747                    ELSE
1748                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_green_av) )  THEN
1749                           ALLOCATE ( surf_usm_v(l)%t_green_av(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1750                           surf_usm_v(l)%t_green_av = 0.0_wp
1751                       ENDIF
1752                    ENDIF
1753                CASE ( 'usm_swc' )
1754!
1755!--                 soil water content for iwl layer of walls and land
1756                    IF ( l == -1 .AND. .NOT.  ALLOCATED(surf_usm_h%swc_av) )  THEN
1757                        ALLOCATE ( surf_usm_h%swc_av(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1758                        surf_usm_h%swc_av = 0.0_wp
1759                    ELSE
1760                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%swc_av) )  THEN
1761                           ALLOCATE ( surf_usm_v(l)%swc_av(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1762                           surf_usm_v(l)%swc_av = 0.0_wp
1763                       ENDIF
1764                    ENDIF
1765
1766               CASE DEFAULT
1767                   CONTINUE
1768
1769           END SELECT
1770
1771        ELSEIF ( mode == 'sum' )  THEN
1772           
1773           SELECT CASE ( TRIM( var ) )
1774
1775                CASE ( 'usm_wshf' )
1776!
1777!--                 array of sensible heat flux from surfaces (land, roof, wall)
1778                    IF ( l == -1 ) THEN
1779                       DO  m = 1, surf_usm_h%ns
1780                          surf_usm_h%wshf_eb_av(m) =                              &
1781                                             surf_usm_h%wshf_eb_av(m) +           &
1782                                             surf_usm_h%wshf_eb(m)
1783                       ENDDO
1784                    ELSE
1785                       DO  m = 1, surf_usm_v(l)%ns
1786                          surf_usm_v(l)%wshf_eb_av(m) =                        &
1787                                          surf_usm_v(l)%wshf_eb_av(m) +        &
1788                                          surf_usm_v(l)%wshf_eb(m)
1789                       ENDDO
1790                    ENDIF
1791                   
1792                CASE ( 'usm_qsws' )
1793!
1794!--                 array of latent heat flux from surfaces (land, roof, wall)
1795                    IF ( l == -1 ) THEN
1796                    DO  m = 1, surf_usm_h%ns
1797                       surf_usm_h%qsws_eb_av(m) =                              &
1798                                          surf_usm_h%qsws_eb_av(m) +           &
1799                                          surf_usm_h%qsws_eb(m)
1800                    ENDDO
1801                    ELSE
1802                       DO  m = 1, surf_usm_v(l)%ns
1803                          surf_usm_v(l)%qsws_eb_av(m) =                        &
1804                                          surf_usm_v(l)%qsws_eb_av(m) +        &
1805                                          surf_usm_v(l)%qsws_eb(m)
1806                       ENDDO
1807                    ENDIF
1808                   
1809                CASE ( 'usm_qsws_veg' )
1810!
1811!--                 array of latent heat flux from vegetation surfaces (land, roof, wall)
1812                    IF ( l == -1 ) THEN
1813                    DO  m = 1, surf_usm_h%ns
1814                       surf_usm_h%qsws_veg_av(m) =                              &
1815                                          surf_usm_h%qsws_veg_av(m) +           &
1816                                          surf_usm_h%qsws_veg(m)
1817                    ENDDO
1818                    ELSE
1819                       DO  m = 1, surf_usm_v(l)%ns
1820                          surf_usm_v(l)%qsws_veg_av(m) =                        &
1821                                          surf_usm_v(l)%qsws_veg_av(m) +        &
1822                                          surf_usm_v(l)%qsws_veg(m)
1823                       ENDDO
1824                    ENDIF
1825                   
1826                CASE ( 'usm_qsws_liq' )
1827!
1828!--                 array of latent heat flux from surfaces with liquid (land, roof, wall)
1829                    IF ( l == -1 ) THEN
1830                    DO  m = 1, surf_usm_h%ns
1831                       surf_usm_h%qsws_liq_av(m) =                              &
1832                                          surf_usm_h%qsws_liq_av(m) +           &
1833                                          surf_usm_h%qsws_liq(m)
1834                    ENDDO
1835                    ELSE
1836                       DO  m = 1, surf_usm_v(l)%ns
1837                          surf_usm_v(l)%qsws_liq_av(m) =                        &
1838                                          surf_usm_v(l)%qsws_liq_av(m) +        &
1839                                          surf_usm_v(l)%qsws_liq(m)
1840                       ENDDO
1841                    ENDIF
1842                   
1843                CASE ( 'usm_wghf' )
1844!
1845!--                 array of heat flux from ground (wall, roof, land)
1846                    IF ( l == -1 ) THEN
1847                       DO  m = 1, surf_usm_h%ns
1848                          surf_usm_h%wghf_eb_av(m) =                              &
1849                                             surf_usm_h%wghf_eb_av(m) +           &
1850                                             surf_usm_h%wghf_eb(m)
1851                       ENDDO
1852                    ELSE
1853                       DO  m = 1, surf_usm_v(l)%ns
1854                          surf_usm_v(l)%wghf_eb_av(m) =                        &
1855                                          surf_usm_v(l)%wghf_eb_av(m) +        &
1856                                          surf_usm_v(l)%wghf_eb(m)
1857                       ENDDO
1858                    ENDIF
1859                   
1860                CASE ( 'usm_wghf_window' )
1861!
1862!--                 array of heat flux from window ground (wall, roof, land)
1863                    IF ( l == -1 ) THEN
1864                       DO  m = 1, surf_usm_h%ns
1865                          surf_usm_h%wghf_eb_window_av(m) =                              &
1866                                             surf_usm_h%wghf_eb_window_av(m) +           &
1867                                             surf_usm_h%wghf_eb_window(m)
1868                       ENDDO
1869                    ELSE
1870                       DO  m = 1, surf_usm_v(l)%ns
1871                          surf_usm_v(l)%wghf_eb_window_av(m) =                        &
1872                                          surf_usm_v(l)%wghf_eb_window_av(m) +        &
1873                                          surf_usm_v(l)%wghf_eb_window(m)
1874                       ENDDO
1875                    ENDIF
1876
1877                CASE ( 'usm_wghf_green' )
1878!
1879!--                 array of heat flux from green ground (wall, roof, land)
1880                    IF ( l == -1 ) THEN
1881                       DO  m = 1, surf_usm_h%ns
1882                          surf_usm_h%wghf_eb_green_av(m) =                              &
1883                                             surf_usm_h%wghf_eb_green_av(m) +           &
1884                                             surf_usm_h%wghf_eb_green(m)
1885                       ENDDO
1886                    ELSE
1887                       DO  m = 1, surf_usm_v(l)%ns
1888                          surf_usm_v(l)%wghf_eb_green_av(m) =                        &
1889                                          surf_usm_v(l)%wghf_eb_green_av(m) +        &
1890                                          surf_usm_v(l)%wghf_eb_green(m)
1891                       ENDDO
1892                    ENDIF
1893                   
1894                CASE ( 'usm_iwghf' )
1895!
1896!--                 array of heat flux from indoor ground (wall, roof, land)
1897                    IF ( l == -1 ) THEN
1898                       DO  m = 1, surf_usm_h%ns
1899                          surf_usm_h%iwghf_eb_av(m) =                              &
1900                                             surf_usm_h%iwghf_eb_av(m) +           &
1901                                             surf_usm_h%iwghf_eb(m)
1902                       ENDDO
1903                    ELSE
1904                       DO  m = 1, surf_usm_v(l)%ns
1905                          surf_usm_v(l)%iwghf_eb_av(m) =                        &
1906                                          surf_usm_v(l)%iwghf_eb_av(m) +        &
1907                                          surf_usm_v(l)%iwghf_eb(m)
1908                       ENDDO
1909                    ENDIF
1910                   
1911                CASE ( 'usm_iwghf_window' )
1912!
1913!--                 array of heat flux from indoor window ground (wall, roof, land)
1914                    IF ( l == -1 ) THEN
1915                       DO  m = 1, surf_usm_h%ns
1916                          surf_usm_h%iwghf_eb_window_av(m) =                              &
1917                                             surf_usm_h%iwghf_eb_window_av(m) +           &
1918                                             surf_usm_h%iwghf_eb_window(m)
1919                       ENDDO
1920                    ELSE
1921                       DO  m = 1, surf_usm_v(l)%ns
1922                          surf_usm_v(l)%iwghf_eb_window_av(m) =                        &
1923                                          surf_usm_v(l)%iwghf_eb_window_av(m) +        &
1924                                          surf_usm_v(l)%iwghf_eb_window(m)
1925                       ENDDO
1926                    ENDIF
1927                   
1928                CASE ( 'usm_t_surf_wall' )
1929!
1930!--                 surface temperature for surfaces
1931                    IF ( l == -1 ) THEN
1932                       DO  m = 1, surf_usm_h%ns
1933                       surf_usm_h%t_surf_wall_av(m) =                               & 
1934                                          surf_usm_h%t_surf_wall_av(m) +            &
1935                                          t_surf_wall_h(m)
1936                       ENDDO
1937                    ELSE
1938                       DO  m = 1, surf_usm_v(l)%ns
1939                          surf_usm_v(l)%t_surf_wall_av(m) =                         &
1940                                          surf_usm_v(l)%t_surf_wall_av(m) +         &
1941                                          t_surf_wall_v(l)%t(m)
1942                       ENDDO
1943                    ENDIF
1944                   
1945                CASE ( 'usm_t_surf_window' )
1946!
1947!--                 surface temperature for window surfaces
1948                    IF ( l == -1 ) THEN
1949                       DO  m = 1, surf_usm_h%ns
1950                          surf_usm_h%t_surf_window_av(m) =                               &
1951                                             surf_usm_h%t_surf_window_av(m) +            &
1952                                             t_surf_window_h(m)
1953                       ENDDO
1954                    ELSE
1955                       DO  m = 1, surf_usm_v(l)%ns
1956                          surf_usm_v(l)%t_surf_window_av(m) =                         &
1957                                          surf_usm_v(l)%t_surf_window_av(m) +         &
1958                                          t_surf_window_v(l)%t(m)
1959                       ENDDO
1960                    ENDIF
1961                   
1962                CASE ( 'usm_t_surf_green' )
1963!
1964!--                 surface temperature for green surfaces
1965                    IF ( l == -1 ) THEN
1966                       DO  m = 1, surf_usm_h%ns
1967                          surf_usm_h%t_surf_green_av(m) =                               &
1968                                             surf_usm_h%t_surf_green_av(m) +            &
1969                                             t_surf_green_h(m)
1970                       ENDDO
1971                    ELSE
1972                       DO  m = 1, surf_usm_v(l)%ns
1973                          surf_usm_v(l)%t_surf_green_av(m) =                         &
1974                                          surf_usm_v(l)%t_surf_green_av(m) +         &
1975                                          t_surf_green_v(l)%t(m)
1976                       ENDDO
1977                    ENDIF
1978               
1979                CASE ( 'usm_theta_10cm' )
1980!
1981!--                 near surface temperature for whole surfaces
1982                    IF ( l == -1 ) THEN
1983                       DO  m = 1, surf_usm_h%ns
1984                          surf_usm_h%pt_10cm_av(m) =                               &
1985                                             surf_usm_h%pt_10cm_av(m) +            &
1986                                             surf_usm_h%pt_10cm(m)
1987                       ENDDO
1988                    ELSE
1989                       DO  m = 1, surf_usm_v(l)%ns
1990                          surf_usm_v(l)%pt_10cm_av(m) =                         &
1991                                          surf_usm_v(l)%pt_10cm_av(m) +         &
1992                                          surf_usm_v(l)%pt_10cm(m)
1993                       ENDDO
1994                    ENDIF
1995                   
1996                CASE ( 'usm_t_wall' )
1997!
1998!--                 wall temperature for  iwl layer of walls and land
1999                    IF ( l == -1 ) THEN
2000                       DO  m = 1, surf_usm_h%ns
2001                          surf_usm_h%t_wall_av(iwl,m) =                           &
2002                                             surf_usm_h%t_wall_av(iwl,m) +        &
2003                                             t_wall_h(iwl,m)
2004                       ENDDO
2005                    ELSE
2006                       DO  m = 1, surf_usm_v(l)%ns
2007                          surf_usm_v(l)%t_wall_av(iwl,m) =                     &
2008                                          surf_usm_v(l)%t_wall_av(iwl,m) +     &
2009                                          t_wall_v(l)%t(iwl,m)
2010                       ENDDO
2011                    ENDIF
2012                   
2013                CASE ( 'usm_t_window' )
2014!
2015!--                 window temperature for  iwl layer of walls and land
2016                    IF ( l == -1 ) THEN
2017                       DO  m = 1, surf_usm_h%ns
2018                          surf_usm_h%t_window_av(iwl,m) =                           &
2019                                             surf_usm_h%t_window_av(iwl,m) +        &
2020                                             t_window_h(iwl,m)
2021                       ENDDO
2022                    ELSE
2023                       DO  m = 1, surf_usm_v(l)%ns
2024                          surf_usm_v(l)%t_window_av(iwl,m) =                     &
2025                                          surf_usm_v(l)%t_window_av(iwl,m) +     &
2026                                          t_window_v(l)%t(iwl,m)
2027                       ENDDO
2028                    ENDIF
2029
2030                CASE ( 'usm_t_green' )
2031!
2032!--                 green temperature for  iwl layer of walls and land
2033                    IF ( l == -1 ) THEN
2034                       DO  m = 1, surf_usm_h%ns
2035                          surf_usm_h%t_green_av(iwl,m) =                           &
2036                                             surf_usm_h%t_green_av(iwl,m) +        &
2037                                             t_green_h(iwl,m)
2038                       ENDDO
2039                    ELSE
2040                       DO  m = 1, surf_usm_v(l)%ns
2041                          surf_usm_v(l)%t_green_av(iwl,m) =                     &
2042                                          surf_usm_v(l)%t_green_av(iwl,m) +     &
2043                                          t_green_v(l)%t(iwl,m)
2044                       ENDDO
2045                    ENDIF
2046
2047                CASE ( 'usm_swc' )
2048!
2049!--                 soil water content for  iwl layer of walls and land
2050                    IF ( l == -1 ) THEN
2051                    DO  m = 1, surf_usm_h%ns
2052                       surf_usm_h%swc_av(iwl,m) =                           &
2053                                          surf_usm_h%swc_av(iwl,m) +        &
2054                                          swc_h(iwl,m)
2055                    ENDDO
2056                    ELSE
2057                       DO  m = 1, surf_usm_v(l)%ns
2058                          surf_usm_v(l)%swc_av(iwl,m) =                     &
2059                                          surf_usm_v(l)%swc_av(iwl,m) +     &
2060                                          swc_v(l)%t(iwl,m)
2061                       ENDDO
2062                    ENDIF
2063
2064                CASE DEFAULT
2065                    CONTINUE
2066
2067           END SELECT
2068
2069        ELSEIF ( mode == 'average' )  THEN
2070           
2071           SELECT CASE ( TRIM( var ) )
2072
2073                CASE ( 'usm_wshf' )
2074!
2075!--                 array of sensible heat flux from surfaces (land, roof, wall)
2076                    IF ( l == -1 ) THEN
2077                       DO  m = 1, surf_usm_h%ns
2078                          surf_usm_h%wshf_eb_av(m) =                              &
2079                                             surf_usm_h%wshf_eb_av(m) /           &
2080                                             REAL( average_count_3d, kind=wp )
2081                       ENDDO
2082                    ELSE
2083                       DO  m = 1, surf_usm_v(l)%ns
2084                          surf_usm_v(l)%wshf_eb_av(m) =                        &
2085                                          surf_usm_v(l)%wshf_eb_av(m) /        &
2086                                          REAL( average_count_3d, kind=wp )
2087                       ENDDO
2088                    ENDIF
2089                   
2090                CASE ( 'usm_qsws' )
2091!
2092!--                 array of latent heat flux from surfaces (land, roof, wall)
2093                    IF ( l == -1 ) THEN
2094                    DO  m = 1, surf_usm_h%ns
2095                       surf_usm_h%qsws_eb_av(m) =                              &
2096                                          surf_usm_h%qsws_eb_av(m) /           &
2097                                          REAL( average_count_3d, kind=wp )
2098                    ENDDO
2099                    ELSE
2100                       DO  m = 1, surf_usm_v(l)%ns
2101                          surf_usm_v(l)%qsws_eb_av(m) =                        &
2102                                          surf_usm_v(l)%qsws_eb_av(m) /        &
2103                                          REAL( average_count_3d, kind=wp )
2104                       ENDDO
2105                    ENDIF
2106
2107                CASE ( 'usm_qsws_veg' )
2108!
2109!--                 array of latent heat flux from vegetation surfaces (land, roof, wall)
2110                    IF ( l == -1 ) THEN
2111                    DO  m = 1, surf_usm_h%ns
2112                       surf_usm_h%qsws_veg_av(m) =                              &
2113                                          surf_usm_h%qsws_veg_av(m) /           &
2114                                          REAL( average_count_3d, kind=wp )
2115                    ENDDO
2116                    ELSE
2117                       DO  m = 1, surf_usm_v(l)%ns
2118                          surf_usm_v(l)%qsws_veg_av(m) =                        &
2119                                          surf_usm_v(l)%qsws_veg_av(m) /        &
2120                                          REAL( average_count_3d, kind=wp )
2121                       ENDDO
2122                    ENDIF
2123                   
2124                CASE ( 'usm_qsws_liq' )
2125!
2126!--                 array of latent heat flux from surfaces with liquid (land, roof, wall)
2127                    IF ( l == -1 ) THEN
2128                    DO  m = 1, surf_usm_h%ns
2129                       surf_usm_h%qsws_liq_av(m) =                              &
2130                                          surf_usm_h%qsws_liq_av(m) /           &
2131                                          REAL( average_count_3d, kind=wp )
2132                    ENDDO
2133                    ELSE
2134                       DO  m = 1, surf_usm_v(l)%ns
2135                          surf_usm_v(l)%qsws_liq_av(m) =                        &
2136                                          surf_usm_v(l)%qsws_liq_av(m) /        &
2137                                          REAL( average_count_3d, kind=wp )
2138                       ENDDO
2139                    ENDIF
2140                   
2141                CASE ( 'usm_wghf' )
2142!
2143!--                 array of heat flux from ground (wall, roof, land)
2144                    IF ( l == -1 ) THEN
2145                       DO  m = 1, surf_usm_h%ns
2146                          surf_usm_h%wghf_eb_av(m) =                              &
2147                                             surf_usm_h%wghf_eb_av(m) /           &
2148                                             REAL( average_count_3d, kind=wp )
2149                       ENDDO
2150                    ELSE
2151                       DO  m = 1, surf_usm_v(l)%ns
2152                          surf_usm_v(l)%wghf_eb_av(m) =                        &
2153                                          surf_usm_v(l)%wghf_eb_av(m) /        &
2154                                          REAL( average_count_3d, kind=wp )
2155                       ENDDO
2156                    ENDIF
2157                   
2158                CASE ( 'usm_wghf_window' )
2159!
2160!--                 array of heat flux from window ground (wall, roof, land)
2161                    IF ( l == -1 ) THEN
2162                       DO  m = 1, surf_usm_h%ns
2163                          surf_usm_h%wghf_eb_window_av(m) =                              &
2164                                             surf_usm_h%wghf_eb_window_av(m) /           &
2165                                             REAL( average_count_3d, kind=wp )
2166                       ENDDO
2167                    ELSE
2168                       DO  m = 1, surf_usm_v(l)%ns
2169                          surf_usm_v(l)%wghf_eb_window_av(m) =                        &
2170                                          surf_usm_v(l)%wghf_eb_window_av(m) /        &
2171                                          REAL( average_count_3d, kind=wp )
2172                       ENDDO
2173                    ENDIF
2174
2175                CASE ( 'usm_wghf_green' )
2176!
2177!--                 array of heat flux from green ground (wall, roof, land)
2178                    IF ( l == -1 ) THEN
2179                       DO  m = 1, surf_usm_h%ns
2180                          surf_usm_h%wghf_eb_green_av(m) =                              &
2181                                             surf_usm_h%wghf_eb_green_av(m) /           &
2182                                             REAL( average_count_3d, kind=wp )
2183                       ENDDO
2184                    ELSE
2185                       DO  m = 1, surf_usm_v(l)%ns
2186                          surf_usm_v(l)%wghf_eb_green_av(m) =                        &
2187                                          surf_usm_v(l)%wghf_eb_green_av(m) /        &
2188                                          REAL( average_count_3d, kind=wp )
2189                       ENDDO
2190                    ENDIF
2191
2192                CASE ( 'usm_iwghf' )
2193!
2194!--                 array of heat flux from indoor ground (wall, roof, land)
2195                    IF ( l == -1 ) THEN
2196                       DO  m = 1, surf_usm_h%ns
2197                          surf_usm_h%iwghf_eb_av(m) =                              &
2198                                             surf_usm_h%iwghf_eb_av(m) /           &
2199                                             REAL( average_count_3d, kind=wp )
2200                       ENDDO
2201                    ELSE
2202                       DO  m = 1, surf_usm_v(l)%ns
2203                          surf_usm_v(l)%iwghf_eb_av(m) =                        &
2204                                          surf_usm_v(l)%iwghf_eb_av(m) /        &
2205                                          REAL( average_count_3d, kind=wp )
2206                       ENDDO
2207                    ENDIF
2208                   
2209                CASE ( 'usm_iwghf_window' )
2210!
2211!--                 array of heat flux from indoor window ground (wall, roof, land)
2212                    IF ( l == -1 ) THEN
2213                       DO  m = 1, surf_usm_h%ns
2214                          surf_usm_h%iwghf_eb_window_av(m) =                              &
2215                                             surf_usm_h%iwghf_eb_window_av(m) /           &
2216                                             REAL( average_count_3d, kind=wp )
2217                       ENDDO
2218                    ELSE
2219                       DO  m = 1, surf_usm_v(l)%ns
2220                          surf_usm_v(l)%iwghf_eb_window_av(m) =                        &
2221                                          surf_usm_v(l)%iwghf_eb_window_av(m) /        &
2222                                          REAL( average_count_3d, kind=wp )
2223                       ENDDO
2224                    ENDIF
2225                   
2226                CASE ( 'usm_t_surf_wall' )
2227!
2228!--                 surface temperature for surfaces
2229                    IF ( l == -1 ) THEN
2230                       DO  m = 1, surf_usm_h%ns
2231                       surf_usm_h%t_surf_wall_av(m) =                               & 
2232                                          surf_usm_h%t_surf_wall_av(m) /            &
2233                                             REAL( average_count_3d, kind=wp )
2234                       ENDDO
2235                    ELSE
2236                       DO  m = 1, surf_usm_v(l)%ns
2237                          surf_usm_v(l)%t_surf_wall_av(m) =                         &
2238                                          surf_usm_v(l)%t_surf_wall_av(m) /         &
2239                                          REAL( average_count_3d, kind=wp )
2240                       ENDDO
2241                    ENDIF
2242                   
2243                CASE ( 'usm_t_surf_window' )
2244!
2245!--                 surface temperature for window surfaces
2246                    IF ( l == -1 ) THEN
2247                       DO  m = 1, surf_usm_h%ns
2248                          surf_usm_h%t_surf_window_av(m) =                               &
2249                                             surf_usm_h%t_surf_window_av(m) /            &
2250                                             REAL( average_count_3d, kind=wp )
2251                       ENDDO
2252                    ELSE
2253                       DO  m = 1, surf_usm_v(l)%ns
2254                          surf_usm_v(l)%t_surf_window_av(m) =                         &
2255                                          surf_usm_v(l)%t_surf_window_av(m) /         &
2256                                          REAL( average_count_3d, kind=wp )
2257                       ENDDO
2258                    ENDIF
2259                   
2260                CASE ( 'usm_t_surf_green' )
2261!
2262!--                 surface temperature for green surfaces
2263                    IF ( l == -1 ) THEN
2264                       DO  m = 1, surf_usm_h%ns
2265                          surf_usm_h%t_surf_green_av(m) =                               &
2266                                             surf_usm_h%t_surf_green_av(m) /            &
2267                                             REAL( average_count_3d, kind=wp )
2268                       ENDDO
2269                    ELSE
2270                       DO  m = 1, surf_usm_v(l)%ns
2271                          surf_usm_v(l)%t_surf_green_av(m) =                         &
2272                                          surf_usm_v(l)%t_surf_green_av(m) /         &
2273                                          REAL( average_count_3d, kind=wp )
2274                       ENDDO
2275                    ENDIF
2276                   
2277                CASE ( 'usm_theta_10cm' )
2278!
2279!--                 near surface temperature for whole surfaces
2280                    IF ( l == -1 ) THEN
2281                       DO  m = 1, surf_usm_h%ns
2282                          surf_usm_h%pt_10cm_av(m) =                               &
2283                                             surf_usm_h%pt_10cm_av(m) /            &
2284                                             REAL( average_count_3d, kind=wp )
2285                       ENDDO
2286                    ELSE
2287                       DO  m = 1, surf_usm_v(l)%ns
2288                          surf_usm_v(l)%pt_10cm_av(m) =                         &
2289                                          surf_usm_v(l)%pt_10cm_av(m) /         &
2290                                          REAL( average_count_3d, kind=wp )
2291                       ENDDO
2292                    ENDIF
2293
2294                   
2295                CASE ( 'usm_t_wall' )
2296!
2297!--                 wall temperature for  iwl layer of walls and land
2298                    IF ( l == -1 ) THEN
2299                       DO  m = 1, surf_usm_h%ns
2300                          surf_usm_h%t_wall_av(iwl,m) =                           &
2301                                             surf_usm_h%t_wall_av(iwl,m) /        &
2302                                             REAL( average_count_3d, kind=wp )
2303                       ENDDO
2304                    ELSE
2305                       DO  m = 1, surf_usm_v(l)%ns
2306                          surf_usm_v(l)%t_wall_av(iwl,m) =                     &
2307                                          surf_usm_v(l)%t_wall_av(iwl,m) /     &
2308                                          REAL( average_count_3d, kind=wp )
2309                       ENDDO
2310                    ENDIF
2311
2312                CASE ( 'usm_t_window' )
2313!
2314!--                 window temperature for  iwl layer of walls and land
2315                    IF ( l == -1 ) THEN
2316                       DO  m = 1, surf_usm_h%ns
2317                          surf_usm_h%t_window_av(iwl,m) =                           &
2318                                             surf_usm_h%t_window_av(iwl,m) /        &
2319                                             REAL( average_count_3d, kind=wp )
2320                       ENDDO
2321                    ELSE
2322                       DO  m = 1, surf_usm_v(l)%ns
2323                          surf_usm_v(l)%t_window_av(iwl,m) =                     &
2324                                          surf_usm_v(l)%t_window_av(iwl,m) /     &
2325                                          REAL( average_count_3d, kind=wp )
2326                       ENDDO
2327                    ENDIF
2328
2329                CASE ( 'usm_t_green' )
2330!
2331!--                 green temperature for  iwl layer of walls and land
2332                    IF ( l == -1 ) THEN
2333                       DO  m = 1, surf_usm_h%ns
2334                          surf_usm_h%t_green_av(iwl,m) =                           &
2335                                             surf_usm_h%t_green_av(iwl,m) /        &
2336                                             REAL( average_count_3d, kind=wp )
2337                       ENDDO
2338                    ELSE
2339                       DO  m = 1, surf_usm_v(l)%ns
2340                          surf_usm_v(l)%t_green_av(iwl,m) =                     &
2341                                          surf_usm_v(l)%t_green_av(iwl,m) /     &
2342                                          REAL( average_count_3d, kind=wp )
2343                       ENDDO
2344                    ENDIF
2345                   
2346                CASE ( 'usm_swc' )
2347!
2348!--                 soil water content for  iwl layer of walls and land
2349                    IF ( l == -1 ) THEN
2350                    DO  m = 1, surf_usm_h%ns
2351                       surf_usm_h%swc_av(iwl,m) =                           &
2352                                          surf_usm_h%swc_av(iwl,m) /        &
2353                                          REAL( average_count_3d, kind=wp )
2354                    ENDDO
2355                    ELSE
2356                       DO  m = 1, surf_usm_v(l)%ns
2357                          surf_usm_v(l)%swc_av(iwl,m) =                     &
2358                                          surf_usm_v(l)%swc_av(iwl,m) /     &
2359                                          REAL( average_count_3d, kind=wp )
2360                       ENDDO
2361                    ENDIF
2362
2363
2364           END SELECT
2365
2366        ENDIF
2367
2368        ENDIF
2369
2370    END SUBROUTINE usm_3d_data_averaging
2371
2372
2373
2374!------------------------------------------------------------------------------!
2375! Description:
2376! ------------
2377!> Set internal Neumann boundary condition at outer soil grid points
2378!> for temperature and humidity.
2379!------------------------------------------------------------------------------!
2380 SUBROUTINE usm_boundary_condition
2381 
2382    IMPLICIT NONE
2383
2384    INTEGER(iwp) :: i      !< grid index x-direction
2385    INTEGER(iwp) :: ioff   !< offset index x-direction indicating location of soil grid point
2386    INTEGER(iwp) :: j      !< grid index y-direction
2387    INTEGER(iwp) :: joff   !< offset index x-direction indicating location of soil grid point
2388    INTEGER(iwp) :: k      !< grid index z-direction
2389    INTEGER(iwp) :: koff   !< offset index x-direction indicating location of soil grid point
2390    INTEGER(iwp) :: l      !< running index surface-orientation
2391    INTEGER(iwp) :: m      !< running index surface elements
2392
2393    koff = surf_usm_h%koff
2394    DO  m = 1, surf_usm_h%ns
2395       i = surf_usm_h%i(m)
2396       j = surf_usm_h%j(m)
2397       k = surf_usm_h%k(m)
2398       pt(k+koff,j,i) = pt(k,j,i)
2399    ENDDO
2400
2401    DO  l = 0, 3
2402       ioff = surf_usm_v(l)%ioff
2403       joff = surf_usm_v(l)%joff
2404       DO  m = 1, surf_usm_v(l)%ns
2405          i = surf_usm_v(l)%i(m)
2406          j = surf_usm_v(l)%j(m)
2407          k = surf_usm_v(l)%k(m)
2408          pt(k,j+joff,i+ioff) = pt(k,j,i)
2409       ENDDO
2410    ENDDO
2411
2412 END SUBROUTINE usm_boundary_condition
2413
2414
2415!------------------------------------------------------------------------------!
2416!
2417! Description:
2418! ------------
2419!> Subroutine checks variables and assigns units.
2420!> It is called out from subroutine check_parameters.
2421!------------------------------------------------------------------------------!
2422    SUBROUTINE usm_check_data_output( variable, unit )
2423
2424        IMPLICIT NONE
2425
2426        CHARACTER(LEN=*),INTENT(IN)    ::  variable   !<
2427        CHARACTER(LEN=*),INTENT(OUT)   ::  unit       !<
2428
2429        INTEGER(iwp)                                  :: i,j,l         !< index
2430        CHARACTER(LEN=2)                              :: ls
2431        CHARACTER(LEN=varnamelength)                  :: var           !< TRIM(variable)
2432        INTEGER(iwp), PARAMETER                       :: nl1 = 14      !< number of directional usm variables
2433        CHARACTER(LEN=varnamelength), DIMENSION(nl1)  :: varlist1 = &  !< list of directional usm variables
2434                  (/'usm_wshf                      ', &
2435                    'usm_wghf                      ', &
2436                    'usm_wghf_window               ', &
2437                    'usm_wghf_green                ', &
2438                    'usm_iwghf                     ', &
2439                    'usm_iwghf_window              ', &
2440                    'usm_surfz                     ', &
2441                    'usm_surfwintrans              ', &
2442                    'usm_surfcat                   ', &
2443                    'usm_t_surf_wall               ', &
2444                    'usm_t_surf_window             ', &
2445                    'usm_t_surf_green              ', &
2446                    'usm_t_green                   ', &
2447                    'usm_theta_10cm                '/)
2448
2449        INTEGER(iwp), PARAMETER                       :: nl2 = 3       !< number of directional layer usm variables
2450        CHARACTER(LEN=varnamelength), DIMENSION(nl2)  :: varlist2 = &  !< list of directional layer usm variables
2451                  (/'usm_t_wall                    ', &
2452                    'usm_t_window                  ', &
2453                    'usm_t_green                   '/)
2454
2455        INTEGER(iwp), PARAMETER                       :: nd = 5     !< number of directions
2456        CHARACTER(LEN=6), DIMENSION(nd), PARAMETER  :: dirname = &  !< direction names
2457                  (/'_roof ','_south','_north','_west ','_east '/)
2458        LOGICAL                                       :: lfound     !< flag if the variable is found
2459
2460
2461        lfound = .FALSE.
2462
2463        var = TRIM(variable)
2464
2465!
2466!--     check if variable exists
2467!--     directional variables
2468        DO i = 1, nl1
2469           DO j = 1, nd
2470              IF ( TRIM(var) == TRIM(varlist1(i))//TRIM(dirname(j)) ) THEN
2471                 lfound = .TRUE.
2472                 EXIT
2473              ENDIF
2474              IF ( lfound ) EXIT
2475           ENDDO
2476        ENDDO
2477        IF ( lfound ) GOTO 10
2478!
2479!--     directional layer variables
2480        DO i = 1, nl2
2481           DO j = 1, nd
2482              DO l = nzb_wall, nzt_wall
2483                 WRITE(ls,'(A1,I1)') '_',l
2484                 IF ( TRIM(var) == TRIM(varlist2(i))//TRIM(ls)//TRIM(dirname(j)) ) THEN
2485                    lfound = .TRUE.
2486                    EXIT
2487                 ENDIF
2488              ENDDO
2489              IF ( lfound ) EXIT
2490           ENDDO
2491        ENDDO
2492        IF ( .NOT.  lfound ) THEN
2493           unit = 'illegal'
2494           RETURN
2495        ENDIF
249610      CONTINUE
2497
2498        IF ( var(1:9)  == 'usm_wshf_'  .OR.  var(1:9) == 'usm_wghf_' .OR.                 &
2499             var(1:16) == 'usm_wghf_window_' .OR. var(1:15) == 'usm_wghf_green_' .OR.     &
2500             var(1:10) == 'usm_iwghf_' .OR. var(1:17) == 'usm_iwghf_window_'    .OR.      &
2501             var(1:17) == 'usm_surfwintrans_' .OR.                                        &
2502             var(1:9)  == 'usm_qsws_'  .OR.  var(1:13)  == 'usm_qsws_veg_'  .OR.          &
2503             var(1:13) == 'usm_qsws_liq_' ) THEN
2504            unit = 'W/m2'
2505        ELSE IF ( var(1:15) == 'usm_t_surf_wall'   .OR.  var(1:10) == 'usm_t_wall' .OR.   &
2506                  var(1:12) == 'usm_t_window' .OR. var(1:17) == 'usm_t_surf_window' .OR.  &
2507                  var(1:16) == 'usm_t_surf_green'  .OR.                                   &
2508                  var(1:11) == 'usm_t_green' .OR.  var(1:7) == 'usm_swc' .OR.             &
2509                  var(1:14) == 'usm_theta_10cm' )  THEN
2510            unit = 'K'
2511        ELSE IF ( var(1:9) == 'usm_surfz'  .OR.  var(1:11) == 'usm_surfcat' )  THEN
2512            unit = '1'
2513        ELSE
2514            unit = 'illegal'
2515        ENDIF
2516
2517    END SUBROUTINE usm_check_data_output
2518
2519
2520!------------------------------------------------------------------------------!
2521! Description:
2522! ------------
2523!> Check parameters routine for urban surface model
2524!------------------------------------------------------------------------------!
2525    SUBROUTINE usm_check_parameters
2526
2527       USE control_parameters,                                                 &
2528           ONLY:  bc_pt_b, bc_q_b, constant_flux_layer, large_scale_forcing,   &
2529                  lsf_surf, topography
2530
2531       USE netcdf_data_input_mod,                                             &
2532            ONLY:  building_type_f
2533
2534       IMPLICIT NONE
2535
2536       INTEGER(iwp) ::  i        !< running index, x-dimension
2537       INTEGER(iwp) ::  j        !< running index, y-dimension
2538
2539!
2540!--    Dirichlet boundary conditions are required as the surface fluxes are
2541!--    calculated from the temperature/humidity gradients in the urban surface
2542!--    model
2543       IF ( bc_pt_b == 'neumann'   .OR.   bc_q_b == 'neumann' )  THEN
2544          message_string = 'urban surface model requires setting of '//        &
2545                           'bc_pt_b = "dirichlet" and '//                      &
2546                           'bc_q_b  = "dirichlet"'
2547          CALL message( 'usm_check_parameters', 'PA0590', 1, 2, 0, 6, 0 )
2548       ENDIF
2549
2550       IF ( .NOT.  constant_flux_layer )  THEN
2551          message_string = 'urban surface model requires '//                   &
2552                           'constant_flux_layer = .T.'
2553          CALL message( 'usm_check_parameters', 'PA0084', 1, 2, 0, 6, 0 )
2554       ENDIF
2555
2556       IF (  .NOT.  radiation )  THEN
2557          message_string = 'urban surface model requires '//                   &
2558                           'the radiation model to be switched on'
2559          CALL message( 'usm_check_parameters', 'PA0084', 1, 2, 0, 6, 0 )
2560       ENDIF
2561!       
2562!--    Surface forcing has to be disabled for LSF in case of enabled
2563!--    urban surface module
2564       IF ( large_scale_forcing )  THEN
2565          lsf_surf = .FALSE.
2566       ENDIF
2567!
2568!--    Topography
2569       IF ( topography == 'flat' )  THEN
2570          message_string = 'topography /= "flat" is required '//               &
2571                           'when using the urban surface model'
2572          CALL message( 'usm_check_parameters', 'PA0592', 1, 2, 0, 6, 0 )
2573       ENDIF
2574!
2575!--    naheatlayers
2576       IF ( naheatlayers > nzt )  THEN
2577          message_string = 'number of anthropogenic heat layers '//            &
2578                           '"naheatlayers" can not be larger than'//           &
2579                           ' number of domain layers "nzt"'
2580          CALL message( 'usm_check_parameters', 'PA0593', 1, 2, 0, 6, 0 )
2581       ENDIF
2582!
2583!--    Check if building types are set within a valid range.
2584       IF ( building_type < LBOUND( building_pars, 2 )  .AND.                  &
2585            building_type > UBOUND( building_pars, 2 ) )  THEN
2586          WRITE( message_string, * ) 'building_type = ', building_type,        &
2587                                     ' is out of the valid range'
2588          CALL message( 'usm_check_parameters', 'PA0529', 2, 2, 0, 6, 0 )
2589       ENDIF
2590       IF ( building_type_f%from_file )  THEN
2591          DO  i = nxl, nxr
2592             DO  j = nys, nyn
2593                IF ( building_type_f%var(j,i) /= building_type_f%fill  .AND.   &
2594              ( building_type_f%var(j,i) < LBOUND( building_pars, 2 )  .OR.    &
2595                building_type_f%var(j,i) > UBOUND( building_pars, 2 ) ) )      &
2596                THEN
2597                   WRITE( message_string, * ) 'building_type = is out of ' //  &
2598                                        'the valid range at (j,i) = ', j, i
2599                   CALL message( 'usm_check_parameters', 'PA0529', 2, 2, 0, 6, 0 )
2600                ENDIF
2601             ENDDO
2602          ENDDO
2603       ENDIF
2604    END SUBROUTINE usm_check_parameters
2605
2606
2607!------------------------------------------------------------------------------!
2608!
2609! Description:
2610! ------------
2611!> Output of the 3D-arrays in netCDF and/or AVS format
2612!> for variables of urban_surface model.
2613!> It resorts the urban surface module output quantities from surf style
2614!> indexing into temporary 3D array with indices (i,j,k).
2615!> It is called from subroutine data_output_3d.
2616!------------------------------------------------------------------------------!
2617    SUBROUTINE usm_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
2618       
2619        IMPLICIT NONE
2620
2621        INTEGER(iwp), INTENT(IN)       ::  av        !< flag if averaged
2622        CHARACTER (len=*), INTENT(IN)  ::  variable  !< variable name
2623        INTEGER(iwp), INTENT(IN)       ::  nzb_do    !< lower limit of the data output (usually 0)
2624        INTEGER(iwp), INTENT(IN)       ::  nzt_do    !< vertical upper limit of the data output (usually nz_do3d)
2625        LOGICAL, INTENT(OUT)           ::  found     !<
2626        REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf   !< sp - it has to correspond to module data_output_3d
2627        REAL(sp), DIMENSION(nzb:nzt+1,nys:nyn,nxl:nxr)     ::  temp_pf    !< temp array for urban surface output procedure
2628       
2629        CHARACTER (len=varnamelength)                      :: var     !< trimmed variable name
2630        INTEGER(iwp), PARAMETER                            :: nd = 5  !< number of directions
2631        CHARACTER(len=6), DIMENSION(0:nd-1), PARAMETER     :: dirname = (/ '_roof ', '_south', '_north', '_west ', '_east ' /)
2632        INTEGER(iwp), DIMENSION(0:nd-1), PARAMETER         :: dirint =  (/    iup_u, isouth_u, inorth_u,  iwest_u,  ieast_u /)
2633        INTEGER(iwp), DIMENSION(0:nd-1), PARAMETER         :: diridx =  (/       -1,        1,        0,        3,        2 /)
2634                                                                      !< index for surf_*_v: 0:3 = (North, South, East, West)
2635        INTEGER(iwp)                   :: ids,idsint,idsidx
2636        INTEGER(iwp)                   :: i,j,k,iwl,istat, l, m  !< running indices
2637
2638        found = .TRUE.
2639        temp_pf = -1._wp
2640       
2641        ids = -1
2642        var = TRIM(variable)
2643        DO i = 0, nd-1
2644            k = len(TRIM(var))
2645            j = len(TRIM(dirname(i)))
2646            IF ( TRIM(var(k-j+1:k)) == TRIM(dirname(i)) )  THEN
2647                ids = i
2648                idsint = dirint(ids)
2649                idsidx = diridx(ids)
2650                var = var(:k-j)
2651                EXIT
2652            ENDIF
2653        ENDDO
2654        IF ( ids == -1 )  THEN
2655            var = TRIM(variable)
2656        ENDIF
2657        IF ( var(1:11) == 'usm_t_wall_'  .AND.  len(TRIM(var)) >= 12 )  THEN
2658!
2659!--         wall layers
2660            READ(var(12:12), '(I1)', iostat=istat ) iwl
2661            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
2662                var = var(1:10)
2663            ENDIF
2664        ENDIF
2665        IF ( var(1:13) == 'usm_t_window_'  .AND.  len(TRIM(var)) >= 14 )  THEN
2666!
2667!--         window layers
2668            READ(var(14:14), '(I1)', iostat=istat ) iwl
2669            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
2670                var = var(1:12)
2671            ENDIF
2672        ENDIF
2673        IF ( var(1:12) == 'usm_t_green_'  .AND.  len(TRIM(var)) >= 13 )  THEN
2674!
2675!--         green layers
2676            READ(var(13:13), '(I1)', iostat=istat ) iwl
2677            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
2678                var = var(1:11)
2679            ENDIF
2680        ENDIF
2681        IF ( var(1:8) == 'usm_swc_'  .AND.  len(TRIM(var)) >= 9 )  THEN
2682!
2683!--         green layers soil water content
2684            READ(var(9:9), '(I1)', iostat=istat ) iwl
2685            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
2686                var = var(1:7)
2687            ENDIF
2688        ENDIF
2689       
2690        SELECT CASE ( TRIM(var) )
2691
2692          CASE ( 'usm_surfz' )
2693!
2694!--           array of surface height (z)
2695              IF ( idsint == iup_u )  THEN
2696                 DO  m = 1, surf_usm_h%ns
2697                    i = surf_usm_h%i(m)
2698                    j = surf_usm_h%j(m)
2699                    k = surf_usm_h%k(m)
2700                    temp_pf(0,j,i) = MAX( temp_pf(0,j,i), REAL( k, KIND = sp) )
2701                 ENDDO
2702              ELSE
2703                 l = idsidx
2704                 DO  m = 1, surf_usm_v(l)%ns
2705                    i = surf_usm_v(l)%i(m)
2706                    j = surf_usm_v(l)%j(m)
2707                    k = surf_usm_v(l)%k(m)
2708                    temp_pf(0,j,i) = MAX( temp_pf(0,j,i), REAL( k, KIND = sp) + 1.0_sp )
2709                 ENDDO
2710              ENDIF
2711
2712          CASE ( 'usm_surfcat' )
2713!
2714!--           surface category
2715              IF ( idsint == iup_u )  THEN
2716                 DO  m = 1, surf_usm_h%ns
2717                    i = surf_usm_h%i(m)
2718                    j = surf_usm_h%j(m)
2719                    k = surf_usm_h%k(m)
2720                    temp_pf(k,j,i) = surf_usm_h%surface_types(m)
2721                 ENDDO
2722              ELSE
2723                 l = idsidx
2724                 DO  m = 1, surf_usm_v(l)%ns
2725                    i = surf_usm_v(l)%i(m)
2726                    j = surf_usm_v(l)%j(m)
2727                    k = surf_usm_v(l)%k(m)
2728                    temp_pf(k,j,i) = surf_usm_v(l)%surface_types(m)
2729                 ENDDO
2730              ENDIF
2731             
2732          CASE ( 'usm_surfwintrans' )
2733!
2734!--           transmissivity window tiles
2735              IF ( idsint == iup_u )  THEN
2736                 DO  m = 1, surf_usm_h%ns
2737                    i = surf_usm_h%i(m)
2738                    j = surf_usm_h%j(m)
2739                    k = surf_usm_h%k(m)
2740                    temp_pf(k,j,i) = surf_usm_h%transmissivity(m)
2741                 ENDDO
2742              ELSE
2743                 l = idsidx
2744                 DO  m = 1, surf_usm_v(l)%ns
2745                    i = surf_usm_v(l)%i(m)
2746                    j = surf_usm_v(l)%j(m)
2747                    k = surf_usm_v(l)%k(m)
2748                    temp_pf(k,j,i) = surf_usm_v(l)%transmissivity(m)
2749                 ENDDO
2750              ENDIF
2751
2752          CASE ( 'usm_wshf' )
2753!
2754!--           array of sensible heat flux from surfaces
2755              IF ( av == 0 )  THEN
2756                 IF ( idsint == iup_u )  THEN
2757                    DO  m = 1, surf_usm_h%ns
2758                       i = surf_usm_h%i(m)
2759                       j = surf_usm_h%j(m)
2760                       k = surf_usm_h%k(m)
2761                       temp_pf(k,j,i) = surf_usm_h%wshf_eb(m)
2762                    ENDDO
2763                 ELSE
2764                    l = idsidx
2765                    DO  m = 1, surf_usm_v(l)%ns
2766                       i = surf_usm_v(l)%i(m)
2767                       j = surf_usm_v(l)%j(m)
2768                       k = surf_usm_v(l)%k(m)
2769                       temp_pf(k,j,i) = surf_usm_v(l)%wshf_eb(m)
2770                    ENDDO
2771                 ENDIF
2772              ELSE
2773                 IF ( idsint == iup_u )  THEN
2774                    DO  m = 1, surf_usm_h%ns
2775                       i = surf_usm_h%i(m)
2776                       j = surf_usm_h%j(m)
2777                       k = surf_usm_h%k(m)
2778                       temp_pf(k,j,i) = surf_usm_h%wshf_eb_av(m)
2779                    ENDDO
2780                 ELSE
2781                    l = idsidx
2782                    DO  m = 1, surf_usm_v(l)%ns
2783                       i = surf_usm_v(l)%i(m)
2784                       j = surf_usm_v(l)%j(m)
2785                       k = surf_usm_v(l)%k(m)
2786                       temp_pf(k,j,i) = surf_usm_v(l)%wshf_eb_av(m)
2787                    ENDDO
2788                 ENDIF
2789              ENDIF
2790             
2791             
2792          CASE ( 'usm_qsws' )
2793!
2794!--           array of latent heat flux from surfaces
2795              IF ( av == 0 )  THEN
2796                 IF ( idsint == iup_u )  THEN
2797                    DO  m = 1, surf_usm_h%ns
2798                       i = surf_usm_h%i(m)
2799                       j = surf_usm_h%j(m)
2800                       k = surf_usm_h%k(m)
2801                       temp_pf(k,j,i) = surf_usm_h%qsws_eb(m)
2802                    ENDDO
2803                 ELSE
2804                    l = idsidx
2805                    DO  m = 1, surf_usm_v(l)%ns
2806                       i = surf_usm_v(l)%i(m)
2807                       j = surf_usm_v(l)%j(m)
2808                       k = surf_usm_v(l)%k(m)
2809                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_eb(m)
2810                    ENDDO
2811                 ENDIF
2812              ELSE
2813                 IF ( idsint == iup_u )  THEN
2814                    DO  m = 1, surf_usm_h%ns
2815                       i = surf_usm_h%i(m)
2816                       j = surf_usm_h%j(m)
2817                       k = surf_usm_h%k(m)
2818                       temp_pf(k,j,i) = surf_usm_h%qsws_eb_av(m)
2819                    ENDDO
2820                 ELSE
2821                    l = idsidx
2822                    DO  m = 1, surf_usm_v(l)%ns
2823                       i = surf_usm_v(l)%i(m)
2824                       j = surf_usm_v(l)%j(m)
2825                       k = surf_usm_v(l)%k(m)
2826                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_eb_av(m)
2827                    ENDDO
2828                 ENDIF
2829              ENDIF
2830             
2831          CASE ( 'usm_qsws_veg' )
2832!
2833!--           array of latent heat flux from vegetation surfaces
2834              IF ( av == 0 )  THEN
2835                 IF ( idsint == iup_u )  THEN
2836                    DO  m = 1, surf_usm_h%ns
2837                       i = surf_usm_h%i(m)
2838                       j = surf_usm_h%j(m)
2839                       k = surf_usm_h%k(m)
2840                       temp_pf(k,j,i) = surf_usm_h%qsws_veg(m)
2841                    ENDDO
2842                 ELSE
2843                    l = idsidx
2844                    DO  m = 1, surf_usm_v(l)%ns
2845                       i = surf_usm_v(l)%i(m)
2846                       j = surf_usm_v(l)%j(m)
2847                       k = surf_usm_v(l)%k(m)
2848                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_veg(m)
2849                    ENDDO
2850                 ENDIF
2851              ELSE
2852                 IF ( idsint == iup_u )  THEN
2853                    DO  m = 1, surf_usm_h%ns
2854                       i = surf_usm_h%i(m)
2855                       j = surf_usm_h%j(m)
2856                       k = surf_usm_h%k(m)
2857                       temp_pf(k,j,i) = surf_usm_h%qsws_veg_av(m)
2858                    ENDDO
2859                 ELSE
2860                    l = idsidx
2861                    DO  m = 1, surf_usm_v(l)%ns
2862                       i = surf_usm_v(l)%i(m)
2863                       j = surf_usm_v(l)%j(m)
2864                       k = surf_usm_v(l)%k(m)
2865                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_veg_av(m)
2866                    ENDDO
2867                 ENDIF
2868              ENDIF
2869             
2870          CASE ( 'usm_qsws_liq' )
2871!
2872!--           array of latent heat flux from surfaces with liquid
2873              IF ( av == 0 )  THEN
2874                 IF ( idsint == iup_u )  THEN
2875                    DO  m = 1, surf_usm_h%ns
2876                       i = surf_usm_h%i(m)
2877                       j = surf_usm_h%j(m)
2878                       k = surf_usm_h%k(m)
2879                       temp_pf(k,j,i) = surf_usm_h%qsws_liq(m)
2880                    ENDDO
2881                 ELSE
2882                    l = idsidx
2883                    DO  m = 1, surf_usm_v(l)%ns
2884                       i = surf_usm_v(l)%i(m)
2885                       j = surf_usm_v(l)%j(m)
2886                       k = surf_usm_v(l)%k(m)
2887                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_liq(m)
2888                    ENDDO
2889                 ENDIF
2890              ELSE
2891                 IF ( idsint == iup_u )  THEN
2892                    DO  m = 1, surf_usm_h%ns
2893                       i = surf_usm_h%i(m)
2894                       j = surf_usm_h%j(m)
2895                       k = surf_usm_h%k(m)
2896                       temp_pf(k,j,i) = surf_usm_h%qsws_liq_av(m)
2897                    ENDDO
2898                 ELSE
2899                    l = idsidx
2900                    DO  m = 1, surf_usm_v(l)%ns
2901                       i = surf_usm_v(l)%i(m)
2902                       j = surf_usm_v(l)%j(m)
2903                       k = surf_usm_v(l)%k(m)
2904                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_liq_av(m)
2905                    ENDDO
2906                 ENDIF
2907              ENDIF
2908
2909          CASE ( 'usm_wghf' )
2910!
2911!--           array of heat flux from ground (land, wall, roof)
2912              IF ( av == 0 )  THEN
2913                 IF ( idsint == iup_u )  THEN
2914                    DO  m = 1, surf_usm_h%ns
2915                       i = surf_usm_h%i(m)
2916                       j = surf_usm_h%j(m)
2917                       k = surf_usm_h%k(m)
2918                       temp_pf(k,j,i) = surf_usm_h%wghf_eb(m)
2919                    ENDDO
2920                 ELSE
2921                    l = idsidx
2922                    DO  m = 1, surf_usm_v(l)%ns
2923                       i = surf_usm_v(l)%i(m)
2924                       j = surf_usm_v(l)%j(m)
2925                       k = surf_usm_v(l)%k(m)
2926                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb(m)
2927                    ENDDO
2928                 ENDIF
2929              ELSE
2930                 IF ( idsint == iup_u )  THEN
2931                    DO  m = 1, surf_usm_h%ns
2932                       i = surf_usm_h%i(m)
2933                       j = surf_usm_h%j(m)
2934                       k = surf_usm_h%k(m)
2935                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_av(m)
2936                    ENDDO
2937                 ELSE
2938                    l = idsidx
2939                    DO  m = 1, surf_usm_v(l)%ns
2940                       i = surf_usm_v(l)%i(m)
2941                       j = surf_usm_v(l)%j(m)
2942                       k = surf_usm_v(l)%k(m)
2943                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_av(m)
2944                    ENDDO
2945                 ENDIF
2946              ENDIF
2947
2948          CASE ( 'usm_wghf_window' )
2949!
2950!--           array of heat flux from window ground (land, wall, roof)
2951              IF ( av == 0 )  THEN
2952                 IF ( idsint == iup_u )  THEN
2953                    DO  m = 1, surf_usm_h%ns
2954                       i = surf_usm_h%i(m)
2955                       j = surf_usm_h%j(m)
2956                       k = surf_usm_h%k(m)
2957                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_window(m)
2958                    ENDDO
2959                 ELSE
2960                    l = idsidx
2961                    DO  m = 1, surf_usm_v(l)%ns
2962                       i = surf_usm_v(l)%i(m)
2963                       j = surf_usm_v(l)%j(m)
2964                       k = surf_usm_v(l)%k(m)
2965                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_window(m)
2966                    ENDDO
2967                 ENDIF
2968              ELSE
2969                 IF ( idsint == iup_u )  THEN
2970                    DO  m = 1, surf_usm_h%ns
2971                       i = surf_usm_h%i(m)
2972                       j = surf_usm_h%j(m)
2973                       k = surf_usm_h%k(m)
2974                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_window_av(m)
2975                    ENDDO
2976                 ELSE
2977                    l = idsidx
2978                    DO  m = 1, surf_usm_v(l)%ns
2979                       i = surf_usm_v(l)%i(m)
2980                       j = surf_usm_v(l)%j(m)
2981                       k = surf_usm_v(l)%k(m)
2982                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_window_av(m)
2983                    ENDDO
2984                 ENDIF
2985              ENDIF
2986
2987          CASE ( 'usm_wghf_green' )
2988!
2989!--           array of heat flux from green ground (land, wall, roof)
2990              IF ( av == 0 )  THEN
2991                 IF ( idsint == iup_u )  THEN
2992                    DO  m = 1, surf_usm_h%ns
2993                       i = surf_usm_h%i(m)
2994                       j = surf_usm_h%j(m)
2995                       k = surf_usm_h%k(m)
2996                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_green(m)
2997                    ENDDO
2998                 ELSE
2999                    l = idsidx
3000                    DO  m = 1, surf_usm_v(l)%ns
3001                       i = surf_usm_v(l)%i(m)
3002                       j = surf_usm_v(l)%j(m)
3003                       k = surf_usm_v(l)%k(m)
3004                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_green(m)
3005                    ENDDO
3006                 ENDIF
3007              ELSE
3008                 IF ( idsint == iup_u )  THEN
3009                    DO  m = 1, surf_usm_h%ns
3010                       i = surf_usm_h%i(m)
3011                       j = surf_usm_h%j(m)
3012                       k = surf_usm_h%k(m)
3013                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_green_av(m)
3014                    ENDDO
3015                 ELSE
3016                    l = idsidx
3017                    DO  m = 1, surf_usm_v(l)%ns
3018                       i = surf_usm_v(l)%i(m)
3019                       j = surf_usm_v(l)%j(m)
3020                       k = surf_usm_v(l)%k(m)
3021                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_green_av(m)
3022                    ENDDO
3023                 ENDIF
3024              ENDIF
3025
3026          CASE ( 'usm_iwghf' )
3027!
3028!--           array of heat flux from indoor ground (land, wall, roof)
3029              IF ( av == 0 )  THEN
3030                 IF ( idsint == iup_u )  THEN
3031                    DO  m = 1, surf_usm_h%ns
3032                       i = surf_usm_h%i(m)
3033                       j = surf_usm_h%j(m)
3034                       k = surf_usm_h%k(m)
3035                       temp_pf(k,j,i) = surf_usm_h%iwghf_eb(m)
3036                    ENDDO
3037                 ELSE
3038                    l = idsidx
3039                    DO  m = 1, surf_usm_v(l)%ns
3040                       i = surf_usm_v(l)%i(m)
3041                       j = surf_usm_v(l)%j(m)
3042                       k = surf_usm_v(l)%k(m)
3043                       temp_pf(k,j,i) = surf_usm_v(l)%iwghf_eb(m)
3044                    ENDDO
3045                 ENDIF
3046              ELSE
3047                 IF ( idsint == iup_u )  THEN
3048                    DO  m = 1, surf_usm_h%ns
3049                       i = surf_usm_h%i(m)
3050                       j = surf_usm_h%j(m)
3051                       k = surf_usm_h%k(m)
3052                       temp_pf(k,j,i) = surf_usm_h%iwghf_eb_av(m)
3053                    ENDDO
3054                 ELSE
3055                    l = idsidx
3056                    DO  m = 1, surf_usm_v(l)%ns
3057                       i = surf_usm_v(l)%i(m)
3058                       j = surf_usm_v(l)%j(m)
3059                       k = surf_usm_v(l)%k(m)
3060                       temp_pf(k,j,i) = surf_usm_v(l)%iwghf_eb_av(m)
3061                    ENDDO
3062                 ENDIF
3063              ENDIF
3064
3065          CASE ( 'usm_iwghf_window' )
3066!
3067!--           array of heat flux from indoor window ground (land, wall, roof)
3068              IF ( av == 0 )  THEN
3069                 IF ( idsint == iup_u )  THEN
3070                    DO  m = 1, surf_usm_h%ns
3071                       i = surf_usm_h%i(m)
3072                       j = surf_usm_h%j(m)
3073                       k = surf_usm_h%k(m)
3074                       temp_pf(k,j,i) = surf_usm_h%iwghf_eb_window(m)
3075                    ENDDO
3076                 ELSE
3077                    l = idsidx
3078                    DO  m = 1, surf_usm_v(l)%ns
3079                       i = surf_usm_v(l)%i(m)
3080                       j = surf_usm_v(l)%j(m)
3081                       k = surf_usm_v(l)%k(m)
3082                       temp_pf(k,j,i) = surf_usm_v(l)%iwghf_eb_window(m)
3083                    ENDDO
3084                 ENDIF
3085              ELSE
3086                 IF ( idsint == iup_u )  THEN
3087                    DO  m = 1, surf_usm_h%ns
3088                       i = surf_usm_h%i(m)
3089                       j = surf_usm_h%j(m)
3090                       k = surf_usm_h%k(m)
3091                       temp_pf(k,j,i) = surf_usm_h%iwghf_eb_window_av(m)
3092                    ENDDO
3093                 ELSE
3094                    l = idsidx
3095                    DO  m = 1, surf_usm_v(l)%ns
3096                       i = surf_usm_v(l)%i(m)
3097                       j = surf_usm_v(l)%j(m)
3098                       k = surf_usm_v(l)%k(m)
3099                       temp_pf(k,j,i) = surf_usm_v(l)%iwghf_eb_window_av(m)
3100                    ENDDO
3101                 ENDIF
3102              ENDIF
3103             
3104          CASE ( 'usm_t_surf_wall' )
3105!
3106!--           surface temperature for surfaces
3107              IF ( av == 0 )  THEN
3108                 IF ( idsint == iup_u )  THEN
3109                    DO  m = 1, surf_usm_h%ns
3110                       i = surf_usm_h%i(m)
3111                       j = surf_usm_h%j(m)
3112                       k = surf_usm_h%k(m)
3113                       temp_pf(k,j,i) = t_surf_wall_h(m)
3114                    ENDDO
3115                 ELSE
3116                    l = idsidx
3117                    DO  m = 1, surf_usm_v(l)%ns
3118                       i = surf_usm_v(l)%i(m)
3119                       j = surf_usm_v(l)%j(m)
3120                       k = surf_usm_v(l)%k(m)
3121                       temp_pf(k,j,i) = t_surf_wall_v(l)%t(m)
3122                    ENDDO
3123                 ENDIF
3124              ELSE
3125                 IF ( idsint == iup_u )  THEN
3126                    DO  m = 1, surf_usm_h%ns
3127                       i = surf_usm_h%i(m)
3128                       j = surf_usm_h%j(m)
3129                       k = surf_usm_h%k(m)
3130                       temp_pf(k,j,i) = surf_usm_h%t_surf_wall_av(m)
3131                    ENDDO
3132                 ELSE
3133                    l = idsidx
3134                    DO  m = 1, surf_usm_v(l)%ns
3135                       i = surf_usm_v(l)%i(m)
3136                       j = surf_usm_v(l)%j(m)
3137                       k = surf_usm_v(l)%k(m)
3138                       temp_pf(k,j,i) = surf_usm_v(l)%t_surf_wall_av(m)
3139                    ENDDO
3140                 ENDIF
3141              ENDIF
3142             
3143          CASE ( 'usm_t_surf_window' )
3144!
3145!--           surface temperature for window surfaces
3146              IF ( av == 0 )  THEN
3147                 IF ( idsint == iup_u )  THEN
3148                    DO  m = 1, surf_usm_h%ns
3149                       i = surf_usm_h%i(m)
3150                       j = surf_usm_h%j(m)
3151                       k = surf_usm_h%k(m)
3152                       temp_pf(k,j,i) = t_surf_window_h(m)
3153                    ENDDO
3154                 ELSE
3155                    l = idsidx
3156                    DO  m = 1, surf_usm_v(l)%ns
3157                       i = surf_usm_v(l)%i(m)
3158                       j = surf_usm_v(l)%j(m)
3159                       k = surf_usm_v(l)%k(m)
3160                       temp_pf(k,j,i) = t_surf_window_v(l)%t(m)
3161                    ENDDO
3162                 ENDIF
3163
3164              ELSE
3165                 IF ( idsint == iup_u )  THEN
3166                    DO  m = 1, surf_usm_h%ns
3167                       i = surf_usm_h%i(m)
3168                       j = surf_usm_h%j(m)
3169                       k = surf_usm_h%k(m)
3170                       temp_pf(k,j,i) = surf_usm_h%t_surf_window_av(m)
3171                    ENDDO
3172                 ELSE
3173                    l = idsidx
3174                    DO  m = 1, surf_usm_v(l)%ns
3175                       i = surf_usm_v(l)%i(m)
3176                       j = surf_usm_v(l)%j(m)
3177                       k = surf_usm_v(l)%k(m)
3178                       temp_pf(k,j,i) = surf_usm_v(l)%t_surf_window_av(m)
3179                    ENDDO
3180
3181                 ENDIF
3182
3183              ENDIF
3184
3185          CASE ( 'usm_t_surf_green' )
3186!
3187!--           surface temperature for green surfaces
3188              IF ( av == 0 )  THEN
3189                 IF ( idsint == iup_u )  THEN
3190                    DO  m = 1, surf_usm_h%ns
3191                       i = surf_usm_h%i(m)
3192                       j = surf_usm_h%j(m)
3193                       k = surf_usm_h%k(m)
3194                       temp_pf(k,j,i) = t_surf_green_h(m)
3195                    ENDDO
3196                 ELSE
3197                    l = idsidx
3198                    DO  m = 1, surf_usm_v(l)%ns
3199                       i = surf_usm_v(l)%i(m)
3200                       j = surf_usm_v(l)%j(m)
3201                       k = surf_usm_v(l)%k(m)
3202                       temp_pf(k,j,i) = t_surf_green_v(l)%t(m)
3203                    ENDDO
3204                 ENDIF
3205
3206              ELSE
3207                 IF ( idsint == iup_u )  THEN
3208                    DO  m = 1, surf_usm_h%ns
3209                       i = surf_usm_h%i(m)
3210                       j = surf_usm_h%j(m)
3211                       k = surf_usm_h%k(m)
3212                       temp_pf(k,j,i) = surf_usm_h%t_surf_green_av(m)
3213                    ENDDO
3214                 ELSE
3215                    l = idsidx
3216                    DO  m = 1, surf_usm_v(l)%ns
3217                       i = surf_usm_v(l)%i(m)
3218                       j = surf_usm_v(l)%j(m)
3219                       k = surf_usm_v(l)%k(m)
3220                       temp_pf(k,j,i) = surf_usm_v(l)%t_surf_green_av(m)
3221                    ENDDO
3222
3223                 ENDIF
3224
3225              ENDIF
3226
3227          CASE ( 'usm_theta_10cm' )
3228!
3229!--           near surface temperature for whole surfaces
3230              IF ( av == 0 )  THEN
3231                 IF ( idsint == iup_u )  THEN
3232                    DO  m = 1, surf_usm_h%ns
3233                       i = surf_usm_h%i(m)
3234                       j = surf_usm_h%j(m)
3235                       k = surf_usm_h%k(m)
3236                       temp_pf(k,j,i) = surf_usm_h%pt_10cm(m)
3237                    ENDDO
3238                 ELSE
3239                    l = idsidx
3240                    DO  m = 1, surf_usm_v(l)%ns
3241                       i = surf_usm_v(l)%i(m)
3242                       j = surf_usm_v(l)%j(m)
3243                       k = surf_usm_v(l)%k(m)
3244                       temp_pf(k,j,i) = surf_usm_v(l)%pt_10cm(m)
3245                    ENDDO
3246                 ENDIF
3247             
3248             
3249              ELSE
3250                 IF ( idsint == iup_u )  THEN
3251                    DO  m = 1, surf_usm_h%ns
3252                       i = surf_usm_h%i(m)
3253                       j = surf_usm_h%j(m)
3254                       k = surf_usm_h%k(m)
3255                       temp_pf(k,j,i) = surf_usm_h%pt_10cm_av(m)
3256                    ENDDO
3257                 ELSE
3258                    l = idsidx
3259                    DO  m = 1, surf_usm_v(l)%ns
3260                       i = surf_usm_v(l)%i(m)
3261                       j = surf_usm_v(l)%j(m)
3262                       k = surf_usm_v(l)%k(m)
3263                       temp_pf(k,j,i) = surf_usm_v(l)%pt_10cm_av(m)
3264                    ENDDO
3265
3266                  ENDIF
3267              ENDIF
3268             
3269          CASE ( 'usm_t_wall' )
3270!
3271!--           wall temperature for  iwl layer of walls and land
3272              IF ( av == 0 )  THEN
3273                 IF ( idsint == iup_u )  THEN
3274                    DO  m = 1, surf_usm_h%ns
3275                       i = surf_usm_h%i(m)
3276                       j = surf_usm_h%j(m)
3277                       k = surf_usm_h%k(m)
3278                       temp_pf(k,j,i) = t_wall_h(iwl,m)
3279                    ENDDO
3280                 ELSE
3281                    l = idsidx
3282                    DO  m = 1, surf_usm_v(l)%ns
3283                       i = surf_usm_v(l)%i(m)
3284                       j = surf_usm_v(l)%j(m)
3285                       k = surf_usm_v(l)%k(m)
3286                       temp_pf(k,j,i) = t_wall_v(l)%t(iwl,m)
3287                    ENDDO
3288                 ENDIF
3289              ELSE
3290                 IF ( idsint == iup_u )  THEN
3291                    DO  m = 1, surf_usm_h%ns
3292                       i = surf_usm_h%i(m)
3293                       j = surf_usm_h%j(m)
3294                       k = surf_usm_h%k(m)
3295                       temp_pf(k,j,i) = surf_usm_h%t_wall_av(iwl,m)
3296                    ENDDO
3297                 ELSE
3298                    l = idsidx
3299                    DO  m = 1, surf_usm_v(l)%ns
3300                       i = surf_usm_v(l)%i(m)
3301                       j = surf_usm_v(l)%j(m)
3302                       k = surf_usm_v(l)%k(m)
3303                       temp_pf(k,j,i) = surf_usm_v(l)%t_wall_av(iwl,m)
3304                    ENDDO
3305                 ENDIF
3306              ENDIF
3307             
3308          CASE ( 'usm_t_window' )
3309!
3310!--           window temperature for iwl layer of walls and land
3311              IF ( av == 0 )  THEN
3312                 IF ( idsint == iup_u )  THEN
3313                    DO  m = 1, surf_usm_h%ns
3314                       i = surf_usm_h%i(m)
3315                       j = surf_usm_h%j(m)
3316                       k = surf_usm_h%k(m)
3317                       temp_pf(k,j,i) = t_window_h(iwl,m)
3318                    ENDDO
3319                 ELSE
3320                    l = idsidx
3321                    DO  m = 1, surf_usm_v(l)%ns
3322                       i = surf_usm_v(l)%i(m)
3323                       j = surf_usm_v(l)%j(m)
3324                       k = surf_usm_v(l)%k(m)
3325                       temp_pf(k,j,i) = t_window_v(l)%t(iwl,m)
3326                    ENDDO
3327                 ENDIF
3328              ELSE
3329                 IF ( idsint == iup_u )  THEN
3330                    DO  m = 1, surf_usm_h%ns
3331                       i = surf_usm_h%i(m)
3332                       j = surf_usm_h%j(m)
3333                       k = surf_usm_h%k(m)
3334                       temp_pf(k,j,i) = surf_usm_h%t_window_av(iwl,m)
3335                    ENDDO
3336                 ELSE
3337                    l = idsidx
3338                    DO  m = 1, surf_usm_v(l)%ns
3339                       i = surf_usm_v(l)%i(m)
3340                       j = surf_usm_v(l)%j(m)
3341                       k = surf_usm_v(l)%k(m)
3342                       temp_pf(k,j,i) = surf_usm_v(l)%t_window_av(iwl,m)
3343                    ENDDO
3344                 ENDIF
3345              ENDIF
3346
3347          CASE ( 'usm_t_green' )
3348!
3349!--           green temperature for  iwl layer of walls and land
3350              IF ( av == 0 )  THEN
3351                 IF ( idsint == iup_u )  THEN
3352                    DO  m = 1, surf_usm_h%ns
3353                       i = surf_usm_h%i(m)
3354                       j = surf_usm_h%j(m)
3355                       k = surf_usm_h%k(m)
3356                       temp_pf(k,j,i) = t_green_h(iwl,m)
3357                    ENDDO
3358                 ELSE
3359                    l = idsidx
3360                    DO  m = 1, surf_usm_v(l)%ns
3361                       i = surf_usm_v(l)%i(m)
3362                       j = surf_usm_v(l)%j(m)
3363                       k = surf_usm_v(l)%k(m)
3364                       temp_pf(k,j,i) = t_green_v(l)%t(iwl,m)
3365                    ENDDO
3366                 ENDIF
3367              ELSE
3368                 IF ( idsint == iup_u )  THEN
3369                    DO  m = 1, surf_usm_h%ns
3370                       i = surf_usm_h%i(m)
3371                       j = surf_usm_h%j(m)
3372                       k = surf_usm_h%k(m)
3373                       temp_pf(k,j,i) = surf_usm_h%t_green_av(iwl,m)
3374                    ENDDO
3375                 ELSE
3376                    l = idsidx
3377                    DO  m = 1, surf_usm_v(l)%ns
3378                       i = surf_usm_v(l)%i(m)
3379                       j = surf_usm_v(l)%j(m)
3380                       k = surf_usm_v(l)%k(m)
3381                       temp_pf(k,j,i) = surf_usm_v(l)%t_green_av(iwl,m)
3382                    ENDDO
3383                 ENDIF
3384              ENDIF
3385             
3386              CASE ( 'usm_swc' )
3387!
3388!--           soil water content for  iwl layer of walls and land
3389              IF ( av == 0 )  THEN
3390                 IF ( idsint == iup_u )  THEN
3391                    DO  m = 1, surf_usm_h%ns
3392                       i = surf_usm_h%i(m)
3393                       j = surf_usm_h%j(m)
3394                       k = surf_usm_h%k(m)
3395                       temp_pf(k,j,i) = swc_h(iwl,m)
3396                    ENDDO
3397                 ELSE
3398                    l = idsidx
3399                    DO  m = 1, surf_usm_v(l)%ns
3400                       i = surf_usm_v(l)%i(m)
3401                       j = surf_usm_v(l)%j(m)
3402                       k = surf_usm_v(l)%k(m)
3403                       temp_pf(k,j,i) = swc_v(l)%t(iwl,m)
3404                    ENDDO
3405                 ENDIF
3406              ELSE
3407                 IF ( idsint == iup_u )  THEN
3408                    DO  m = 1, surf_usm_h%ns
3409                       i = surf_usm_h%i(m)
3410                       j = surf_usm_h%j(m)
3411                       k = surf_usm_h%k(m)
3412                       temp_pf(k,j,i) = surf_usm_h%swc_av(iwl,m)
3413                    ENDDO
3414                 ELSE
3415                    l = idsidx
3416                    DO  m = 1, surf_usm_v(l)%ns
3417                       i = surf_usm_v(l)%i(m)
3418                       j = surf_usm_v(l)%j(m)
3419                       k = surf_usm_v(l)%k(m)
3420                       temp_pf(k,j,i) = surf_usm_v(l)%swc_av(iwl,m)
3421                    ENDDO
3422                 ENDIF
3423              ENDIF
3424
3425             
3426          CASE DEFAULT
3427              found = .FALSE.
3428              RETURN
3429        END SELECT
3430
3431!
3432!--     Rearrange dimensions for NetCDF output
3433!--     FIXME: this may generate FPE overflow upon conversion from DP to SP
3434        DO  j = nys, nyn
3435            DO  i = nxl, nxr
3436                DO  k = nzb_do, nzt_do
3437                    local_pf(i,j,k) = temp_pf(k,j,i)
3438                ENDDO
3439            ENDDO
3440        ENDDO
3441       
3442    END SUBROUTINE usm_data_output_3d
3443   
3444
3445!------------------------------------------------------------------------------!
3446!
3447! Description:
3448! ------------
3449!> Soubroutine defines appropriate grid for netcdf variables.
3450!> It is called out from subroutine netcdf.
3451!------------------------------------------------------------------------------!
3452    SUBROUTINE usm_define_netcdf_grid( variable, found, grid_x, grid_y, grid_z )
3453   
3454        IMPLICIT NONE
3455
3456        CHARACTER (len=*), INTENT(IN)  ::  variable    !<
3457        LOGICAL, INTENT(OUT)           ::  found       !<
3458        CHARACTER (len=*), INTENT(OUT) ::  grid_x      !<
3459        CHARACTER (len=*), INTENT(OUT) ::  grid_y      !<
3460        CHARACTER (len=*), INTENT(OUT) ::  grid_z      !<
3461
3462        CHARACTER (len=varnamelength)  :: var
3463
3464        var = TRIM(variable)
3465        IF ( var(1:9) == 'usm_wshf_'  .OR.  var(1:9) == 'usm_wghf_'  .OR.                   &
3466             var(1:16) == 'usm_wghf_window_'  .OR. var(1:15) == 'usm_wghf_green_' .OR.      &
3467             var(1:10) == 'usm_iwghf_'  .OR. var(1:17) == 'usm_iwghf_window_' .OR.          &
3468             var(1:9) == 'usm_qsws_'  .OR.  var(1:13) == 'usm_qsws_veg_'  .OR.              &
3469             var(1:13) == 'usm_qsws_liq_' .OR.                                              &
3470             var(1:15) == 'usm_t_surf_wall'  .OR.  var(1:10) == 'usm_t_wall'  .OR.          &
3471             var(1:17) == 'usm_t_surf_window'  .OR.  var(1:12) == 'usm_t_window'  .OR.      &
3472             var(1:16) == 'usm_t_surf_green'  .OR. var(1:11) == 'usm_t_green' .OR.          &
3473             var(1:15) == 'usm_theta_10cm' .OR.                                             &
3474             var(1:9) == 'usm_surfz'  .OR.  var(1:11) == 'usm_surfcat'  .OR.                &
3475             var(1:16) == 'usm_surfwintrans'  .OR. var(1:7) == 'usm_swc' ) THEN
3476
3477            found = .TRUE.
3478            grid_x = 'x'
3479            grid_y = 'y'
3480            grid_z = 'zu'
3481        ELSE
3482            found  = .FALSE.
3483            grid_x = 'none'
3484            grid_y = 'none'
3485            grid_z = 'none'
3486        ENDIF
3487
3488    END SUBROUTINE usm_define_netcdf_grid
3489   
3490
3491!------------------------------------------------------------------------------!
3492! Description:
3493! ------------
3494!> Initialization of the wall surface model
3495!------------------------------------------------------------------------------!
3496    SUBROUTINE usm_init_material_model
3497
3498        IMPLICIT NONE
3499
3500        INTEGER(iwp) ::  k, l, m            !< running indices
3501       
3502        IF ( debug_output )  CALL debug_message( 'usm_init_material_model', 'start' )
3503
3504!
3505!--     Calculate wall grid spacings.
3506!--     Temperature is defined at the center of the wall layers,
3507!--     whereas gradients/fluxes are defined at the edges (_stag)     
3508!--     apply for all particular surface grids. First for horizontal surfaces
3509        DO  m = 1, surf_usm_h%ns
3510
3511           surf_usm_h%dz_wall(nzb_wall,m) = surf_usm_h%zw(nzb_wall,m)
3512           DO k = nzb_wall+1, nzt_wall
3513               surf_usm_h%dz_wall(k,m) = surf_usm_h%zw(k,m) -                  &
3514                                         surf_usm_h%zw(k-1,m)
3515           ENDDO
3516           surf_usm_h%dz_window(nzb_wall,m) = surf_usm_h%zw_window(nzb_wall,m)
3517           DO k = nzb_wall+1, nzt_wall
3518               surf_usm_h%dz_window(k,m) = surf_usm_h%zw_window(k,m) -         &
3519                                         surf_usm_h%zw_window(k-1,m)
3520           ENDDO
3521           
3522           surf_usm_h%dz_wall(nzt_wall+1,m) = surf_usm_h%dz_wall(nzt_wall,m)
3523
3524           DO k = nzb_wall, nzt_wall-1
3525               surf_usm_h%dz_wall_stag(k,m) = 0.5 * (                          &
3526                           surf_usm_h%dz_wall(k+1,m) + surf_usm_h%dz_wall(k,m) )
3527           ENDDO
3528           surf_usm_h%dz_wall_stag(nzt_wall,m) = surf_usm_h%dz_wall(nzt_wall,m)
3529           
3530           surf_usm_h%dz_window(nzt_wall+1,m) = surf_usm_h%dz_window(nzt_wall,m)
3531
3532           DO k = nzb_wall, nzt_wall-1
3533               surf_usm_h%dz_window_stag(k,m) = 0.5 * (                        &
3534                           surf_usm_h%dz_window(k+1,m) + surf_usm_h%dz_window(k,m) )
3535           ENDDO
3536           surf_usm_h%dz_window_stag(nzt_wall,m) = surf_usm_h%dz_window(nzt_wall,m)
3537
3538           IF (surf_usm_h%green_type_roof(m) == 2.0_wp ) THEN
3539!
3540!-- extensive green roof
3541!-- set ratio of substrate layer thickness, soil-type and LAI
3542              soil_type = 3
3543              surf_usm_h%lai(m) = 2.0_wp
3544             
3545              surf_usm_h%zw_green(nzb_wall,m)   = 0.05_wp
3546              surf_usm_h%zw_green(nzb_wall+1,m) = 0.10_wp
3547              surf_usm_h%zw_green(nzb_wall+2,m) = 0.15_wp
3548              surf_usm_h%zw_green(nzb_wall+3,m) = 0.20_wp
3549           ELSE
3550!
3551!-- intensiv green roof
3552!-- set ratio of substrate layer thickness, soil-type and LAI
3553              soil_type = 6
3554              surf_usm_h%lai(m) = 4.0_wp
3555             
3556              surf_usm_h%zw_green(nzb_wall,m)   = 0.05_wp
3557              surf_usm_h%zw_green(nzb_wall+1,m) = 0.10_wp
3558              surf_usm_h%zw_green(nzb_wall+2,m) = 0.40_wp
3559              surf_usm_h%zw_green(nzb_wall+3,m) = 0.80_wp
3560           ENDIF
3561           
3562           surf_usm_h%dz_green(nzb_wall,m) = surf_usm_h%zw_green(nzb_wall,m)
3563           DO k = nzb_wall+1, nzt_wall
3564               surf_usm_h%dz_green(k,m) = surf_usm_h%zw_green(k,m) -           &
3565                                         surf_usm_h%zw_green(k-1,m)
3566           ENDDO
3567           surf_usm_h%dz_green(nzt_wall+1,m) = surf_usm_h%dz_green(nzt_wall,m)
3568
3569           DO k = nzb_wall, nzt_wall-1
3570               surf_usm_h%dz_green_stag(k,m) = 0.5 * (                         &
3571                           surf_usm_h%dz_green(k+1,m) + surf_usm_h%dz_green(k,m) )
3572           ENDDO
3573           surf_usm_h%dz_green_stag(nzt_wall,m) = surf_usm_h%dz_green(nzt_wall,m)
3574           
3575          IF ( alpha_vangenuchten == 9999999.9_wp )  THEN
3576             alpha_vangenuchten = soil_pars(0,soil_type)
3577          ENDIF
3578
3579          IF ( l_vangenuchten == 9999999.9_wp )  THEN
3580             l_vangenuchten = soil_pars(1,soil_type)
3581          ENDIF
3582
3583          IF ( n_vangenuchten == 9999999.9_wp )  THEN
3584             n_vangenuchten = soil_pars(2,soil_type)           
3585          ENDIF
3586
3587          IF ( hydraulic_conductivity == 9999999.9_wp )  THEN
3588             hydraulic_conductivity = soil_pars(3,soil_type)           
3589          ENDIF
3590
3591          IF ( saturation_moisture == 9999999.9_wp )  THEN
3592             saturation_moisture = m_soil_pars(0,soil_type)           
3593          ENDIF
3594
3595          IF ( field_capacity == 9999999.9_wp )  THEN
3596             field_capacity = m_soil_pars(1,soil_type)           
3597          ENDIF
3598
3599          IF ( wilting_point == 9999999.9_wp )  THEN
3600             wilting_point = m_soil_pars(2,soil_type)           
3601          ENDIF
3602
3603          IF ( residual_moisture == 9999999.9_wp )  THEN
3604             residual_moisture = m_soil_pars(3,soil_type)       
3605          ENDIF
3606         
3607          DO k = nzb_wall, nzt_wall+1
3608             swc_h(k,m) = field_capacity
3609             rootfr_h(k,m) = 0.5_wp
3610             surf_usm_h%alpha_vg_green(m)      = alpha_vangenuchten
3611             surf_usm_h%l_vg_green(m)          = l_vangenuchten
3612             surf_usm_h%n_vg_green(m)          = n_vangenuchten 
3613             surf_usm_h%gamma_w_green_sat(k,m) = hydraulic_conductivity
3614             swc_sat_h(k,m)                    = saturation_moisture
3615             fc_h(k,m)                         = field_capacity
3616             wilt_h(k,m)                       = wilting_point
3617             swc_res_h(k,m)                    = residual_moisture
3618          ENDDO
3619
3620        ENDDO
3621
3622        surf_usm_h%ddz_wall        = 1.0_wp / surf_usm_h%dz_wall
3623        surf_usm_h%ddz_wall_stag   = 1.0_wp / surf_usm_h%dz_wall_stag
3624        surf_usm_h%ddz_window      = 1.0_wp / surf_usm_h%dz_window
3625        surf_usm_h%ddz_window_stag = 1.0_wp / surf_usm_h%dz_window_stag
3626        surf_usm_h%ddz_green       = 1.0_wp / surf_usm_h%dz_green
3627        surf_usm_h%ddz_green_stag  = 1.0_wp / surf_usm_h%dz_green_stag
3628!       
3629!--     For vertical surfaces
3630        DO  l = 0, 3
3631           DO  m = 1, surf_usm_v(l)%ns
3632              surf_usm_v(l)%dz_wall(nzb_wall,m) = surf_usm_v(l)%zw(nzb_wall,m)
3633              DO k = nzb_wall+1, nzt_wall
3634                  surf_usm_v(l)%dz_wall(k,m) = surf_usm_v(l)%zw(k,m) -         &
3635                                               surf_usm_v(l)%zw(k-1,m)
3636              ENDDO
3637              surf_usm_v(l)%dz_window(nzb_wall,m) = surf_usm_v(l)%zw_window(nzb_wall,m)
3638              DO k = nzb_wall+1, nzt_wall
3639                  surf_usm_v(l)%dz_window(k,m) = surf_usm_v(l)%zw_window(k,m) - &
3640                                               surf_usm_v(l)%zw_window(k-1,m)
3641              ENDDO
3642              surf_usm_v(l)%dz_green(nzb_wall,m) = surf_usm_v(l)%zw_green(nzb_wall,m)
3643              DO k = nzb_wall+1, nzt_wall
3644                  surf_usm_v(l)%dz_green(k,m) = surf_usm_v(l)%zw_green(k,m) - &
3645                                               surf_usm_v(l)%zw_green(k-1,m)
3646              ENDDO
3647           
3648              surf_usm_v(l)%dz_wall(nzt_wall+1,m) =                            &
3649                                              surf_usm_v(l)%dz_wall(nzt_wall,m)
3650
3651              DO k = nzb_wall, nzt_wall-1
3652                  surf_usm_v(l)%dz_wall_stag(k,m) = 0.5 * (                    &
3653                                                surf_usm_v(l)%dz_wall(k+1,m) + &
3654                                                surf_usm_v(l)%dz_wall(k,m) )
3655              ENDDO
3656              surf_usm_v(l)%dz_wall_stag(nzt_wall,m) =                         &
3657                                              surf_usm_v(l)%dz_wall(nzt_wall,m)
3658              surf_usm_v(l)%dz_window(nzt_wall+1,m) =                          &
3659                                              surf_usm_v(l)%dz_window(nzt_wall,m)
3660
3661              DO k = nzb_wall, nzt_wall-1
3662                  surf_usm_v(l)%dz_window_stag(k,m) = 0.5 * (                    &
3663                                                surf_usm_v(l)%dz_window(k+1,m) + &
3664                                                surf_usm_v(l)%dz_window(k,m) )
3665              ENDDO
3666              surf_usm_v(l)%dz_window_stag(nzt_wall,m) =                         &
3667                                              surf_usm_v(l)%dz_window(nzt_wall,m)
3668              surf_usm_v(l)%dz_green(nzt_wall+1,m) =                             &
3669                                              surf_usm_v(l)%dz_green(nzt_wall,m)
3670
3671              DO k = nzb_wall, nzt_wall-1
3672                  surf_usm_v(l)%dz_green_stag(k,m) = 0.5 * (                    &
3673                                                surf_usm_v(l)%dz_green(k+1,m) + &
3674                                                surf_usm_v(l)%dz_green(k,m) )
3675              ENDDO
3676              surf_usm_v(l)%dz_green_stag(nzt_wall,m) =                         &
3677                                              surf_usm_v(l)%dz_green(nzt_wall,m)
3678           ENDDO
3679           surf_usm_v(l)%ddz_wall        = 1.0_wp / surf_usm_v(l)%dz_wall
3680           surf_usm_v(l)%ddz_wall_stag   = 1.0_wp / surf_usm_v(l)%dz_wall_stag
3681           surf_usm_v(l)%ddz_window      = 1.0_wp / surf_usm_v(l)%dz_window
3682           surf_usm_v(l)%ddz_window_stag = 1.0_wp / surf_usm_v(l)%dz_window_stag
3683           surf_usm_v(l)%ddz_green       = 1.0_wp / surf_usm_v(l)%dz_green
3684           surf_usm_v(l)%ddz_green_stag  = 1.0_wp / surf_usm_v(l)%dz_green_stag
3685        ENDDO     
3686
3687       
3688        IF ( debug_output )  CALL debug_message( 'usm_init_material_model', 'end' )
3689
3690    END SUBROUTINE usm_init_material_model
3691
3692 
3693!------------------------------------------------------------------------------!
3694! Description:
3695! ------------
3696!> Initialization of the urban surface model
3697!------------------------------------------------------------------------------!
3698    SUBROUTINE usm_init
3699
3700        USE arrays_3d,                                                         &
3701            ONLY:  zw
3702
3703        USE netcdf_data_input_mod,                                             &
3704            ONLY:  building_pars_f, building_type_f, terrain_height_f
3705   
3706        IMPLICIT NONE
3707
3708        INTEGER(iwp) ::  i                   !< loop index x-dirction
3709        INTEGER(iwp) ::  ind_alb_green       !< index in input list for green albedo
3710        INTEGER(iwp) ::  ind_alb_wall        !< index in input list for wall albedo
3711        INTEGER(iwp) ::  ind_alb_win         !< index in input list for window albedo
3712        INTEGER(iwp) ::  ind_emis_wall       !< index in input list for wall emissivity
3713        INTEGER(iwp) ::  ind_emis_green      !< index in input list for green emissivity
3714        INTEGER(iwp) ::  ind_emis_win        !< index in input list for window emissivity
3715        INTEGER(iwp) ::  ind_green_frac_w    !< index in input list for green fraction on wall
3716        INTEGER(iwp) ::  ind_green_frac_r    !< index in input list for green fraction on roof
3717        INTEGER(iwp) ::  ind_hc1             !< index in input list for heat capacity at first wall layer
3718        INTEGER(iwp) ::  ind_hc1_win         !< index in input list for heat capacity at first window layer
3719        INTEGER(iwp) ::  ind_hc2             !< index in input list for heat capacity at second wall layer
3720        INTEGER(iwp) ::  ind_hc2_win         !< index in input list for heat capacity at second window layer
3721        INTEGER(iwp) ::  ind_hc3             !< index in input list for heat capacity at third wall layer
3722        INTEGER(iwp) ::  ind_hc3_win         !< index in input list for heat capacity at third window layer
3723        INTEGER(iwp) ::  ind_lai_r           !< index in input list for LAI on roof
3724        INTEGER(iwp) ::  ind_lai_w           !< index in input list for LAI on wall
3725        INTEGER(iwp) ::  ind_tc1             !< index in input list for thermal conductivity at first wall layer
3726        INTEGER(iwp) ::  ind_tc1_win         !< index in input list for thermal conductivity at first window layer
3727        INTEGER(iwp) ::  ind_tc2             !< index in input list for thermal conductivity at second wall layer
3728        INTEGER(iwp) ::  ind_tc2_win         !< index in input list for thermal conductivity at second window layer
3729        INTEGER(iwp) ::  ind_tc3             !< index in input list for thermal conductivity at third wall layer
3730        INTEGER(iwp) ::  ind_tc3_win         !< index in input list for thermal conductivity at third window layer
3731        INTEGER(iwp) ::  ind_thick_1         !< index in input list for thickness of first wall layer
3732        INTEGER(iwp) ::  ind_thick_1_win     !< index in input list for thickness of first window layer
3733        INTEGER(iwp) ::  ind_thick_2         !< index in input list for thickness of second wall layer
3734        INTEGER(iwp) ::  ind_thick_2_win     !< index in input list for thickness of second window layer
3735        INTEGER(iwp) ::  ind_thick_3         !< index in input list for thickness of third wall layer
3736        INTEGER(iwp) ::  ind_thick_3_win     !< index in input list for thickness of third window layer
3737        INTEGER(iwp) ::  ind_thick_4         !< index in input list for thickness of fourth wall layer
3738        INTEGER(iwp) ::  ind_thick_4_win     !< index in input list for thickness of fourth window layer
3739        INTEGER(iwp) ::  ind_trans           !< index in input list for window transmissivity
3740        INTEGER(iwp) ::  ind_wall_frac       !< index in input list for wall fraction
3741        INTEGER(iwp) ::  ind_win_frac        !< index in input list for window fraction
3742        INTEGER(iwp) ::  ind_z0              !< index in input list for z0
3743        INTEGER(iwp) ::  ind_z0qh            !< index in input list for z0h / z0q
3744        INTEGER(iwp) ::  j                   !< loop index y-dirction
3745        INTEGER(iwp) ::  k                   !< loop index z-dirction
3746        INTEGER(iwp) ::  l                   !< loop index surface orientation
3747        INTEGER(iwp) ::  m                   !< loop index surface element
3748        INTEGER(iwp) ::  st                  !< dummy 
3749
3750        REAL(wp)     ::  c, tin, twin
3751        REAL(wp)     ::  ground_floor_level_l         !< local height of ground floor level
3752        REAL(wp)     ::  z_agl                        !< height above ground
3753
3754        IF ( debug_output )  CALL debug_message( 'usm_init', 'start' )
3755
3756        CALL cpu_log( log_point_s(78), 'usm_init', 'start' )
3757!
3758!--     Initialize building-surface properties
3759        CALL usm_define_pars
3760!
3761!--     surface forcing have to be disabled for LSF
3762!--     in case of enabled urban surface module
3763        IF ( large_scale_forcing )  THEN
3764            lsf_surf = .FALSE.
3765        ENDIF
3766!
3767!--     Flag surface elements belonging to the ground floor level. Therefore,
3768!--     use terrain height array from file, if available. This flag is later used
3769!--     to control initialization of surface attributes.
3770!--     Todo: for the moment disable initialization of building roofs with
3771!--     ground-floor-level properties.
3772        surf_usm_h%ground_level = .FALSE. 
3773
3774        DO  l = 0, 3
3775           surf_usm_v(l)%ground_level = .FALSE.
3776           DO  m = 1, surf_usm_v(l)%ns
3777              i = surf_usm_v(l)%i(m) + surf_usm_v(l)%ioff
3778              j = surf_usm_v(l)%j(m) + surf_usm_v(l)%joff
3779              k = surf_usm_v(l)%k(m)
3780!
3781!--           Determine local ground level. Level 1 - default value,
3782!--           level 2 - initialization according to building type,
3783!--           level 3 - initialization from value read from file.
3784              ground_floor_level_l = ground_floor_level
3785             
3786              IF ( building_type_f%from_file )  THEN
3787                  ground_floor_level_l =                                       &
3788                              building_pars(ind_gflh,building_type_f%var(j,i))
3789              ENDIF
3790             
3791              IF ( building_pars_f%from_file )  THEN
3792                 IF ( building_pars_f%pars_xy(ind_gflh,j,i) /=                 &
3793                      building_pars_f%fill )                                   &
3794                    ground_floor_level_l = building_pars_f%pars_xy(ind_gflh,j,i)
3795              ENDIF
3796!
3797!--           Determine height of surface element above ground level. Please
3798!--           note, height of surface element is determined with respect to
3799!--           its height above ground of the reference grid point in atmosphere,
3800!--           Therefore, substract the offset values when assessing the terrain
3801!--           height.
3802              IF ( terrain_height_f%from_file )  THEN
3803                 z_agl = zw(k) - terrain_height_f%var(j-surf_usm_v(l)%joff,    &
3804                                                      i-surf_usm_v(l)%ioff)
3805              ELSE
3806                 z_agl = zw(k)
3807              ENDIF
3808!
3809!--           Set flag for ground level
3810              IF ( z_agl <= ground_floor_level_l )                             &
3811                 surf_usm_v(l)%ground_level(m) = .TRUE.
3812
3813           ENDDO
3814        ENDDO
3815!
3816!--     Initialization of resistances.
3817        DO  m = 1, surf_usm_h%ns
3818           surf_usm_h%r_a(m)        = 50.0_wp
3819           surf_usm_h%r_a_green(m)  = 50.0_wp
3820           surf_usm_h%r_a_window(m) = 50.0_wp
3821        ENDDO
3822        DO  l = 0, 3
3823           DO  m = 1, surf_usm_v(l)%ns
3824              surf_usm_v(l)%r_a(m)        = 50.0_wp
3825              surf_usm_v(l)%r_a_green(m)  = 50.0_wp
3826              surf_usm_v(l)%r_a_window(m) = 50.0_wp
3827           ENDDO
3828        ENDDO
3829       
3830!
3831!--    Map values onto horizontal elemements
3832       DO  m = 1, surf_usm_h%ns
3833             surf_usm_h%r_canopy_min(m)     = 200.0_wp !< min_canopy_resistance
3834             surf_usm_h%g_d(m)              = 0.0_wp   !< canopy_resistance_coefficient
3835       ENDDO
3836!
3837!--    Map values onto vertical elements, even though this does not make
3838!--    much sense.
3839       DO  l = 0, 3
3840          DO  m = 1, surf_usm_v(l)%ns
3841                surf_usm_v(l)%r_canopy_min(m)     = 200.0_wp !< min_canopy_resistance
3842                surf_usm_v(l)%g_d(m)              = 0.0_wp   !< canopy_resistance_coefficient
3843          ENDDO
3844       ENDDO
3845
3846!
3847!--     Initialize urban-type surface attribute. According to initialization in
3848!--     land-surface model, follow a 3-level approach.
3849!--     Level 1 - initialization via default attributes
3850        DO  m = 1, surf_usm_h%ns
3851!
3852!--        Now, all horizontal surfaces are roof surfaces (?)
3853           surf_usm_h%isroof_surf(m)   = .TRUE.
3854           surf_usm_h%surface_types(m) = roof_category         !< default category for root surface
3855!
3856!--        In order to distinguish between ground floor level and
3857!--        above-ground-floor level surfaces, set input indices.
3858
3859           ind_green_frac_r = MERGE( ind_green_frac_r_gfl, ind_green_frac_r_agfl, &
3860                                     surf_usm_h%ground_level(m) )
3861           ind_lai_r        = MERGE( ind_lai_r_gfl,        ind_lai_r_agfl,        &
3862                                     surf_usm_h%ground_level(m) )
3863           ind_z0           = MERGE( ind_z0_gfl,           ind_z0_agfl,           &
3864                                     surf_usm_h%ground_level(m) )
3865           ind_z0qh         = MERGE( ind_z0qh_gfl,         ind_z0qh_agfl,         &
3866                                     surf_usm_h%ground_level(m) )
3867!
3868!--        Store building type and its name on each surface element
3869           surf_usm_h%building_type(m)      = building_type
3870           surf_usm_h%building_type_name(m) = building_type_name(building_type)
3871!
3872!--        Initialize relatvie wall- (0), green- (1) and window (2) fractions
3873           surf_usm_h%frac(ind_veg_wall,m)  = building_pars(ind_wall_frac_r,building_type)   
3874           surf_usm_h%frac(ind_pav_green,m) = building_pars(ind_green_frac_r,building_type) 
3875           surf_usm_h%frac(ind_wat_win,m)   = building_pars(ind_win_frac_r,building_type) 
3876           surf_usm_h%lai(m)                = building_pars(ind_lai_r,building_type) 
3877
3878           surf_usm_h%rho_c_wall(nzb_wall,m)   = building_pars(ind_hc1_wall_r,building_type) 
3879           surf_usm_h%rho_c_wall(nzb_wall+1,m) = building_pars(ind_hc1_wall_r,building_type)
3880           surf_usm_h%rho_c_wall(nzb_wall+2,m) = building_pars(ind_hc2_wall_r,building_type)
3881           surf_usm_h%rho_c_wall(nzb_wall+3,m) = building_pars(ind_hc3_wall_r,building_type)   
3882           surf_usm_h%lambda_h(nzb_wall,m)   = building_pars(ind_tc1_wall_r,building_type) 
3883           surf_usm_h%lambda_h(nzb_wall+1,m) = building_pars(ind_tc1_wall_r,building_type) 
3884           surf_usm_h%lambda_h(nzb_wall+2,m) = building_pars(ind_tc2_wall_r,building_type)
3885           surf_usm_h%lambda_h(nzb_wall+3,m) = building_pars(ind_tc3_wall_r,building_type)   
3886           surf_usm_h%rho_c_green(nzb_wall,m)   = rho_c_soil !building_pars(ind_hc1_wall_r,building_type) 
3887           surf_usm_h%rho_c_green(nzb_wall+1,m) = rho_c_soil !building_pars(ind_hc1_wall_r,building_type)
3888           surf_usm_h%rho_c_green(nzb_wall+2,m) = rho_c_soil !building_pars(ind_hc2_wall_r,building_type)
3889           surf_usm_h%rho_c_green(nzb_wall+3,m) = rho_c_soil !building_pars(ind_hc3_wall_r,building_type)   
3890           surf_usm_h%lambda_h_green(nzb_wall,m)   = lambda_h_green_sm !building_pars(ind_tc1_wall_r,building_type) 
3891           surf_usm_h%lambda_h_green(nzb_wall+1,m) = lambda_h_green_sm !building_pars(ind_tc1_wall_r,building_type)
3892           surf_usm_h%lambda_h_green(nzb_wall+2,m) = lambda_h_green_sm !building_pars(ind_tc2_wall_r,building_type)
3893           surf_usm_h%lambda_h_green(nzb_wall+3,m) = lambda_h_green_sm !building_pars(ind_tc3_wall_r,building_type)
3894           surf_usm_h%rho_c_window(nzb_wall,m)   = building_pars(ind_hc1_win_r,building_type) 
3895           surf_usm_h%rho_c_window(nzb_wall+1,m) = building_pars(ind_hc1_win_r,building_type)
3896           surf_usm_h%rho_c_window(nzb_wall+2,m) = building_pars(ind_hc2_win_r,building_type)
3897           surf_usm_h%rho_c_window(nzb_wall+3,m) = building_pars(ind_hc3_win_r,building_type)   
3898           surf_usm_h%lambda_h_window(nzb_wall,m)   = building_pars(ind_tc1_win_r,building_type) 
3899           surf_usm_h%lambda_h_window(nzb_wall+1,m) = building_pars(ind_tc1_win_r,building_type) 
3900           surf_usm_h%lambda_h_window(nzb_wall+2,m) = building_pars(ind_tc2_win_r,building_type)
3901           surf_usm_h%lambda_h_window(nzb_wall+3,m) = building_pars(ind_tc3_win_r,building_type)   
3902
3903           surf_usm_h%target_temp_summer(m)  = building_pars(ind_indoor_target_temp_summer,building_type)   
3904           surf_usm_h%target_temp_winter(m)  = building_pars(ind_indoor_target_temp_winter,building_type)   
3905!
3906!--        emissivity of wall-, green- and window fraction
3907           surf_usm_h%emissivity(ind_veg_wall,m)  = building_pars(ind_emis_wall_r,building_type)
3908           surf_usm_h%emissivity(ind_pav_green,m) = building_pars(ind_emis_green_r,building_type)
3909           surf_usm_h%emissivity(ind_wat_win,m)   = building_pars(ind_emis_win_r,building_type)
3910
3911           surf_usm_h%transmissivity(m)      = building_pars(ind_trans_r,building_type)
3912
3913           surf_usm_h%z0(m)                  = building_pars(ind_z0,building_type)
3914           surf_usm_h%z0h(m)                 = building_pars(ind_z0qh,building_type)
3915           surf_usm_h%z0q(m)                 = building_pars(ind_z0qh,building_type)
3916!
3917!--        albedo type for wall fraction, green fraction, window fraction
3918           surf_usm_h%albedo_type(ind_veg_wall,m)  = INT( building_pars(ind_alb_wall_r,building_type)  )
3919           surf_usm_h%albedo_type(ind_pav_green,m) = INT( building_pars(ind_alb_green_r,building_type) )
3920           surf_usm_h%albedo_type(ind_wat_win,m)   = INT( building_pars(ind_alb_win_r,building_type)   )
3921
3922           surf_usm_h%zw(nzb_wall,m)         = building_pars(ind_thick_1_wall_r,building_type)
3923           surf_usm_h%zw(nzb_wall+1,m)       = building_pars(ind_thick_2_wall_r,building_type)
3924           surf_usm_h%zw(nzb_wall+2,m)       = building_pars(ind_thick_3_wall_r,building_type)
3925           surf_usm_h%zw(nzb_wall+3,m)       = building_pars(ind_thick_4_wall_r,building_type)
3926           
3927           surf_usm_h%zw_green(nzb_wall,m)         = building_pars(ind_thick_1_wall_r,building_type)
3928           surf_usm_h%zw_green(nzb_wall+1,m)       = building_pars(ind_thick_2_wall_r,building_type)
3929           surf_usm_h%zw_green(nzb_wall+2,m)       = building_pars(ind_thick_3_wall_r,building_type)
3930           surf_usm_h%zw_green(nzb_wall+3,m)       = building_pars(ind_thick_4_wall_r,building_type)
3931           
3932           surf_usm_h%zw_window(nzb_wall,m)         = building_pars(ind_thick_1_win_r,building_type)
3933           surf_usm_h%zw_window(nzb_wall+1,m)       = building_pars(ind_thick_2_win_r,building_type)
3934           surf_usm_h%zw_window(nzb_wall+2,m)       = building_pars(ind_thick_3_win_r,building_type)
3935           surf_usm_h%zw_window(nzb_wall+3,m)       = building_pars(ind_thick_4_win_r,building_type)
3936
3937           surf_usm_h%c_surface(m)           = building_pars(ind_c_surface,building_type) 
3938           surf_usm_h%lambda_surf(m)         = building_pars(ind_lambda_surf,building_type) 
3939           surf_usm_h%c_surface_green(m)     = building_pars(ind_c_surface_green,building_type) 
3940           surf_usm_h%lambda_surf_green(m)   = building_pars(ind_lambda_surf_green,building_type) 
3941           surf_usm_h%c_surface_window(m)    = building_pars(ind_c_surface_win,building_type) 
3942           surf_usm_h%lambda_surf_window(m)  = building_pars(ind_lambda_surf_win,building_type) 
3943           
3944           surf_usm_h%green_type_roof(m)     = building_pars(ind_green_type_roof,building_type)
3945
3946        ENDDO
3947
3948        DO  l = 0, 3
3949           DO  m = 1, surf_usm_v(l)%ns
3950
3951              surf_usm_v(l)%surface_types(m) = wall_category         !< default category for root surface
3952!
3953!--           In order to distinguish between ground floor level and
3954!--           above-ground-floor level surfaces, set input indices.
3955              ind_alb_green    = MERGE( ind_alb_green_gfl,    ind_alb_green_agfl,    &
3956                                        surf_usm_v(l)%ground_level(m) )
3957              ind_alb_wall     = MERGE( ind_alb_wall_gfl,     ind_alb_wall_agfl,     &
3958                                        surf_usm_v(l)%ground_level(m) )
3959              ind_alb_win      = MERGE( ind_alb_win_gfl,      ind_alb_win_agfl,      &
3960                                        surf_usm_v(l)%ground_level(m) )
3961              ind_wall_frac    = MERGE( ind_wall_frac_gfl,    ind_wall_frac_agfl,    &
3962                                        surf_usm_v(l)%ground_level(m) )
3963              ind_win_frac     = MERGE( ind_win_frac_gfl,     ind_win_frac_agfl,     &
3964                                        surf_usm_v(l)%ground_level(m) )
3965              ind_green_frac_w = MERGE( ind_green_frac_w_gfl, ind_green_frac_w_agfl, &
3966                                        surf_usm_v(l)%ground_level(m) )
3967              ind_green_frac_r = MERGE( ind_green_frac_r_gfl, ind_green_frac_r_agfl, &
3968                                        surf_usm_v(l)%ground_level(m) )
3969              ind_lai_r        = MERGE( ind_lai_r_gfl,        ind_lai_r_agfl,        &
3970                                        surf_usm_v(l)%ground_level(m) )
3971              ind_lai_w        = MERGE( ind_lai_w_gfl,        ind_lai_w_agfl,        &
3972                                        surf_usm_v(l)%ground_level(m) )
3973              ind_hc1          = MERGE( ind_hc1_gfl,          ind_hc1_agfl,          &
3974                                        surf_usm_v(l)%ground_level(m) )
3975              ind_hc1_win      = MERGE( ind_hc1_win_gfl,      ind_hc1_win_agfl,      &
3976                                        surf_usm_v(l)%ground_level(m) )
3977              ind_hc2          = MERGE( ind_hc2_gfl,          ind_hc2_agfl,          &
3978                                        surf_usm_v(l)%ground_level(m) )
3979              ind_hc2_win      = MERGE( ind_hc2_win_gfl,      ind_hc2_win_agfl,      &
3980                                        surf_usm_v(l)%ground_level(m) )
3981              ind_hc3          = MERGE( ind_hc3_gfl,          ind_hc3_agfl,          &
3982                                        surf_usm_v(l)%ground_level(m) )
3983              ind_hc3_win      = MERGE( ind_hc3_win_gfl,      ind_hc3_win_agfl,      &
3984                                        surf_usm_v(l)%ground_level(m) )
3985              ind_tc1          = MERGE( ind_tc1_gfl,          ind_tc1_agfl,          &
3986                                        surf_usm_v(l)%ground_level(m) )
3987              ind_tc1_win      = MERGE( ind_tc1_win_gfl,      ind_tc1_win_agfl,      &
3988                                        surf_usm_v(l)%ground_level(m) )
3989              ind_tc2          = MERGE( ind_tc2_gfl,          ind_tc2_agfl,          &
3990                                        surf_usm_v(l)%ground_level(m) )
3991              ind_tc2_win      = MERGE( ind_tc2_win_gfl,      ind_tc2_win_agfl,      &
3992                                        surf_usm_v(l)%ground_level(m) )
3993              ind_tc3          = MERGE( ind_tc3_gfl,          ind_tc3_agfl,          &
3994                                        surf_usm_v(l)%ground_level(m) )
3995              ind_tc3_win      = MERGE( ind_tc3_win_gfl,      ind_tc3_win_agfl,      &
3996                                        surf_usm_v(l)%ground_level(m) )
3997              ind_thick_1      = MERGE( ind_thick_1_gfl,      ind_thick_1_agfl,      &
3998                                        surf_usm_v(l)%ground_level(m) )
3999              ind_thick_1_win  = MERGE( ind_thick_1_win_gfl,  ind_thick_1_win_agfl,  &
4000                                        surf_usm_v(l)%ground_level(m) )
4001              ind_thick_2      = MERGE( ind_thick_2_gfl,      ind_thick_2_agfl,      &
4002                                        surf_usm_v(l)%ground_level(m) )
4003              ind_thick_2_win  = MERGE( ind_thick_2_win_gfl,  ind_thick_2_win_agfl,  &
4004                                        surf_usm_v(l)%ground_level(m) )
4005              ind_thick_3      = MERGE( ind_thick_3_gfl,      ind_thick_3_agfl,      &
4006                                        surf_usm_v(l)%ground_level(m) )
4007              ind_thick_3_win  = MERGE( ind_thick_3_win_gfl,  ind_thick_3_win_agfl,  &
4008                                        surf_usm_v(l)%ground_level(m) )
4009              ind_thick_4      = MERGE( ind_thick_4_gfl,      ind_thick_4_agfl,      &
4010                                        surf_usm_v(l)%ground_level(m) )
4011              ind_thick_4_win  = MERGE( ind_thick_4_win_gfl,  ind_thick_4_win_agfl,  &
4012                                        surf_usm_v(l)%ground_level(m) )
4013              ind_emis_wall    = MERGE( ind_emis_wall_gfl,    ind_emis_wall_agfl,    &
4014                                        surf_usm_v(l)%ground_level(m) )
4015              ind_emis_green   = MERGE( ind_emis_green_gfl,   ind_emis_green_agfl,   &
4016                                        surf_usm_v(l)%ground_level(m) )
4017              ind_emis_win     = MERGE( ind_emis_win_gfl,     ind_emis_win_agfl,     &
4018                                        surf_usm_v(l)%ground_level(m) )
4019              ind_trans        = MERGE( ind_trans_gfl,       ind_trans_agfl,         &
4020                                        surf_usm_v(l)%ground_level(m) )
4021              ind_z0           = MERGE( ind_z0_gfl,           ind_z0_agfl,           &
4022                                        surf_usm_v(l)%ground_level(m) )
4023              ind_z0qh         = MERGE( ind_z0qh_gfl,         ind_z0qh_agfl,         &
4024                                        surf_usm_v(l)%ground_level(m) )
4025!
4026!--           Store building type and its name on each surface element
4027              surf_usm_v(l)%building_type(m)      = building_type
4028              surf_usm_v(l)%building_type_name(m) = building_type_name(building_type)
4029!
4030!--           Initialize relatvie wall- (0), green- (1) and window (2) fractions
4031              surf_usm_v(l)%frac(ind_veg_wall,m)   = building_pars(ind_wall_frac,building_type)   
4032              surf_usm_v(l)%frac(ind_pav_green,m)  = building_pars(ind_green_frac_w,building_type) 
4033              surf_usm_v(l)%frac(ind_wat_win,m)    = building_pars(ind_win_frac,building_type) 
4034              surf_usm_v(l)%lai(m)                 = building_pars(ind_lai_w,building_type) 
4035
4036              surf_usm_v(l)%rho_c_wall(nzb_wall,m)   = building_pars(ind_hc1,building_type) 
4037              surf_usm_v(l)%rho_c_wall(nzb_wall+1,m) = building_pars(ind_hc1,building_type)
4038              surf_usm_v(l)%rho_c_wall(nzb_wall+2,m) = building_pars(ind_hc2,building_type)
4039              surf_usm_v(l)%rho_c_wall(nzb_wall+3,m) = building_pars(ind_hc3,building_type)   
4040             
4041              surf_usm_v(l)%rho_c_green(nzb_wall,m)   = rho_c_soil !building_pars(ind_hc1,building_type) 
4042              surf_usm_v(l)%rho_c_green(nzb_wall+1,m) = rho_c_soil !building_pars(ind_hc1,building_type)
4043              surf_usm_v(l)%rho_c_green(nzb_wall+2,m) = rho_c_soil !building_pars(ind_hc2,building_type)
4044              surf_usm_v(l)%rho_c_green(nzb_wall+3,m) = rho_c_soil !building_pars(ind_hc3,building_type)   
4045             
4046              surf_usm_v(l)%rho_c_window(nzb_wall,m)   = building_pars(ind_hc1_win,building_type) 
4047              surf_usm_v(l)%rho_c_window(nzb_wall+1,m) = building_pars(ind_hc1_win,building_type)
4048              surf_usm_v(l)%rho_c_window(nzb_wall+2,m) = building_pars(ind_hc2_win,building_type)
4049              surf_usm_v(l)%rho_c_window(nzb_wall+3,m) = building_pars(ind_hc3_win,building_type)   
4050
4051              surf_usm_v(l)%lambda_h(nzb_wall,m)   = building_pars(ind_tc1,building_type) 
4052              surf_usm_v(l)%lambda_h(nzb_wall+1,m) = building_pars(ind_tc1,building_type) 
4053              surf_usm_v(l)%lambda_h(nzb_wall+2,m) = building_pars(ind_tc2,building_type)
4054              surf_usm_v(l)%lambda_h(nzb_wall+3,m) = building_pars(ind_tc3,building_type)   
4055             
4056              surf_usm_v(l)%lambda_h_green(nzb_wall,m)   = lambda_h_green_sm !building_pars(ind_tc1,building_type) 
4057              surf_usm_v(l)%lambda_h_green(nzb_wall+1,m) = lambda_h_green_sm !building_pars(ind_tc1,building_type)
4058              surf_usm_v(l)%lambda_h_green(nzb_wall+2,m) = lambda_h_green_sm !building_pars(ind_tc2,building_type)
4059              surf_usm_v(l)%lambda_h_green(nzb_wall+3,m) = lambda_h_green_sm !building_pars(ind_tc3,building_type)   
4060
4061              surf_usm_v(l)%lambda_h_window(nzb_wall,m)   = building_pars(ind_tc1_win,building_type) 
4062              surf_usm_v(l)%lambda_h_window(nzb_wall+1,m) = building_pars(ind_tc1_win,building_type) 
4063              surf_usm_v(l)%lambda_h_window(nzb_wall+2,m) = building_pars(ind_tc2_win,building_type)
4064              surf_usm_v(l)%lambda_h_window(nzb_wall+3,m) = building_pars(ind_tc3_win,building_type)   
4065
4066              surf_usm_v(l)%target_temp_summer(m)  = building_pars(ind_indoor_target_temp_summer,building_type)   
4067              surf_usm_v(l)%target_temp_winter(m)  = building_pars(ind_indoor_target_temp_winter,building_type)   
4068!
4069!--           emissivity of wall-, green- and window fraction
4070              surf_usm_v(l)%emissivity(ind_veg_wall,m)  = building_pars(ind_emis_wall,building_type)
4071              surf_usm_v(l)%emissivity(ind_pav_green,m) = building_pars(ind_emis_green,building_type)
4072              surf_usm_v(l)%emissivity(ind_wat_win,m)   = building_pars(ind_emis_win,building_type)
4073
4074              surf_usm_v(l)%transmissivity(m)      = building_pars(ind_trans,building_type)
4075
4076              surf_usm_v(l)%z0(m)                  = building_pars(ind_z0,building_type)
4077              surf_usm_v(l)%z0h(m)                 = building_pars(ind_z0qh,building_type)
4078              surf_usm_v(l)%z0q(m)                 = building_pars(ind_z0qh,building_type)
4079
4080              surf_usm_v(l)%albedo_type(ind_veg_wall,m)  = INT( building_pars(ind_alb_wall,building_type) )
4081              surf_usm_v(l)%albedo_type(ind_pav_green,m) = INT( building_pars(ind_alb_green,building_type) )
4082              surf_usm_v(l)%albedo_type(ind_wat_win,m)   = INT( building_pars(ind_alb_win,building_type) )
4083
4084              surf_usm_v(l)%zw(nzb_wall,m)         = building_pars(ind_thick_1,building_type)
4085              surf_usm_v(l)%zw(nzb_wall+1,m)       = building_pars(ind_thick_2,building_type)
4086              surf_usm_v(l)%zw(nzb_wall+2,m)       = building_pars(ind_thick_3,building_type)
4087              surf_usm_v(l)%zw(nzb_wall+3,m)       = building_pars(ind_thick_4,building_type)
4088             
4089              surf_usm_v(l)%zw_green(nzb_wall,m)         = building_pars(ind_thick_1,building_type)
4090              surf_usm_v(l)%zw_green(nzb_wall+1,m)       = building_pars(ind_thick_2,building_type)
4091              surf_usm_v(l)%zw_green(nzb_wall+2,m)       = building_pars(ind_thick_3,building_type)
4092              surf_usm_v(l)%zw_green(nzb_wall+3,m)       = building_pars(ind_thick_4,building_type)
4093
4094              surf_usm_v(l)%zw_window(nzb_wall,m)         = building_pars(ind_thick_1_win,building_type)
4095              surf_usm_v(l)%zw_window(nzb_wall+1,m)       = building_pars(ind_thick_2_win,building_type)
4096              surf_usm_v(l)%zw_window(nzb_wall+2,m)       = building_pars(ind_thick_3_win,building_type)
4097              surf_usm_v(l)%zw_window(nzb_wall+3,m)       = building_pars(ind_thick_4_win,building_type)
4098
4099              surf_usm_v(l)%c_surface(m)           = building_pars(ind_c_surface,building_type) 
4100              surf_usm_v(l)%lambda_surf(m)         = building_pars(ind_lambda_surf,building_type)
4101              surf_usm_v(l)%c_surface_green(m)     = building_pars(ind_c_surface_green,building_type) 
4102              surf_usm_v(l)%lambda_surf_green(m)   = building_pars(ind_lambda_surf_green,building_type)
4103              surf_usm_v(l)%c_surface_window(m)    = building_pars(ind_c_surface_win,building_type) 
4104              surf_usm_v(l)%lambda_surf_window(m)  = building_pars(ind_lambda_surf_win,building_type)
4105
4106           ENDDO
4107        ENDDO
4108!
4109!--     Level 2 - initialization via building type read from file
4110        IF ( building_type_f%from_file )  THEN
4111           DO  m = 1, surf_usm_h%ns
4112              i = surf_usm_h%i(m)
4113              j = surf_usm_h%j(m)
4114!
4115!--           For the moment, limit building type to 6 (to overcome errors in input file).
4116              st = building_type_f%var(j,i)
4117              IF ( st /= building_type_f%fill )  THEN
4118
4119!
4120!--              In order to distinguish between ground floor level and
4121!--              above-ground-floor level surfaces, set input indices.
4122
4123                 ind_green_frac_r = MERGE( ind_green_frac_r_gfl, ind_green_frac_r_agfl, &
4124                                           surf_usm_h%ground_level(m) )
4125                 ind_lai_r        = MERGE( ind_lai_r_gfl,        ind_lai_r_agfl,        &
4126                                           surf_usm_h%ground_level(m) )
4127                 ind_z0           = MERGE( ind_z0_gfl,           ind_z0_agfl,           &
4128                                           surf_usm_h%ground_level(m) )
4129                 ind_z0qh         = MERGE( ind_z0qh_gfl,         ind_z0qh_agfl,         &
4130                                           surf_usm_h%ground_level(m) )
4131!
4132!--              Store building type and its name on each surface element
4133                 surf_usm_h%building_type(m)      = st
4134                 surf_usm_h%building_type_name(m) = building_type_name(st)
4135!
4136!--              Initialize relatvie wall- (0), green- (1) and window (2) fractions
4137                 surf_usm_h%frac(ind_veg_wall,m)  = building_pars(ind_wall_frac_r,st)   
4138                 surf_usm_h%frac(ind_pav_green,m) = building_pars(ind_green_frac_r,st) 
4139                 surf_usm_h%frac(ind_wat_win,m)   = building_pars(ind_win_frac_r,st) 
4140                 surf_usm_h%lai(m)                = building_pars(ind_lai_r,st) 
4141
4142                 surf_usm_h%rho_c_wall(nzb_wall,m)   = building_pars(ind_hc1_wall_r,st) 
4143                 surf_usm_h%rho_c_wall(nzb_wall+1,m) = building_pars(ind_hc1_wall_r,st)
4144                 surf_usm_h%rho_c_wall(nzb_wall+2,m) = building_pars(ind_hc2_wall_r,st)
4145                 surf_usm_h%rho_c_wall(nzb_wall+3,m) = building_pars(ind_hc3_wall_r,st)   
4146                 surf_usm_h%lambda_h(nzb_wall,m)   = building_pars(ind_tc1_wall_r,st) 
4147                 surf_usm_h%lambda_h(nzb_wall+1,m) = building_pars(ind_tc1_wall_r,st) 
4148                 surf_usm_h%lambda_h(nzb_wall+2,m) = building_pars(ind_tc2_wall_r,st)
4149                 surf_usm_h%lambda_h(nzb_wall+3,m) = building_pars(ind_tc3_wall_r,st)   
4150                 
4151                 surf_usm_h%rho_c_green(nzb_wall,m)   = rho_c_soil !building_pars(ind_hc1_wall_r,st) 
4152                 surf_usm_h%rho_c_green(nzb_wall+1,m) = rho_c_soil !building_pars(ind_hc1_wall_r,st)
4153                 surf_usm_h%rho_c_green(nzb_wall+2,m) = rho_c_soil !building_pars(ind_hc2_wall_r,st)
4154                 surf_usm_h%rho_c_green(nzb_wall+3,m) = rho_c_soil !building_pars(ind_hc3_wall_r,st)   
4155                 surf_usm_h%lambda_h_green(nzb_wall,m)   = lambda_h_green_sm !building_pars(ind_tc1_wall_r,st) 
4156                 surf_usm_h%lambda_h_green(nzb_wall+1,m) = lambda_h_green_sm !building_pars(ind_tc1_wall_r,st)
4157                 surf_usm_h%lambda_h_green(nzb_wall+2,m) = lambda_h_green_sm !building_pars(ind_tc2_wall_r,st)
4158                 surf_usm_h%lambda_h_green(nzb_wall+3,m) = lambda_h_green_sm !building_pars(ind_tc3_wall_r,st)   
4159               
4160                 surf_usm_h%rho_c_window(nzb_wall,m)   = building_pars(ind_hc1_win_r,st) 
4161                 surf_usm_h%rho_c_window(nzb_wall+1,m) = building_pars(ind_hc1_win_r,st)
4162                 surf_usm_h%rho_c_window(nzb_wall+2,m) = building_pars(ind_hc2_win_r,st)
4163                 surf_usm_h%rho_c_window(nzb_wall+3,m) = building_pars(ind_hc3_win_r,st)   
4164                 surf_usm_h%lambda_h_window(nzb_wall,m)   = building_pars(ind_tc1_win_r,st) 
4165                 surf_usm_h%lambda_h_window(nzb_wall+1,m) = building_pars(ind_tc1_win_r,st) 
4166                 surf_usm_h%lambda_h_window(nzb_wall+2,m) = building_pars(ind_tc2_win_r,st)
4167                 surf_usm_h%lambda_h_window(nzb_wall+3,m) = building_pars(ind_tc3_win_r,st)   
4168
4169                 surf_usm_h%target_temp_summer(m)  = building_pars(ind_indoor_target_temp_summer,st)   
4170                 surf_usm_h%target_temp_winter(m)  = building_pars(ind_indoor_target_temp_winter,st)   
4171!
4172!--              emissivity of wall-, green- and window fraction
4173                 surf_usm_h%emissivity(ind_veg_wall,m)  = building_pars(ind_emis_wall_r,st)
4174                 surf_usm_h%emissivity(ind_pav_green,m) = building_pars(ind_emis_green_r,st)
4175                 surf_usm_h%emissivity(ind_wat_win,m)   = building_pars(ind_emis_win_r,st)
4176
4177                 surf_usm_h%transmissivity(m)      = building_pars(ind_trans_r,st)
4178
4179                 surf_usm_h%z0(m)                  = building_pars(ind_z0,st)
4180                 surf_usm_h%z0h(m)                 = building_pars(ind_z0qh,st)
4181                 surf_usm_h%z0q(m)                 = building_pars(ind_z0qh,st)
4182!
4183!--              albedo type for wall fraction, green fraction, window fraction
4184                 surf_usm_h%albedo_type(ind_veg_wall,m)  = INT( building_pars(ind_alb_wall_r,st) )
4185                 surf_usm_h%albedo_type(ind_pav_green,m) = INT( building_pars(ind_alb_green_r,st) )
4186                 surf_usm_h%albedo_type(ind_wat_win,m)   = INT( building_pars(ind_alb_win_r,st) )
4187
4188                 surf_usm_h%zw(nzb_wall,m)         = building_pars(ind_thick_1_wall_r,st)
4189                 surf_usm_h%zw(nzb_wall+1,m)       = building_pars(ind_thick_2_wall_r,st)
4190                 surf_usm_h%zw(nzb_wall+2,m)       = building_pars(ind_thick_3_wall_r,st)
4191                 surf_usm_h%zw(nzb_wall+3,m)       = building_pars(ind_thick_4_wall_r,st)
4192                 
4193                 surf_usm_h%zw_green(nzb_wall,m)         = building_pars(ind_thick_1_wall_r,st)
4194                 surf_usm_h%zw_green(nzb_wall+1,m)       = building_pars(ind_thick_2_wall_r,st)
4195                 surf_usm_h%zw_green(nzb_wall+2,m)       = building_pars(ind_thick_3_wall_r,st)
4196                 surf_usm_h%zw_green(nzb_wall+3,m)       = building_pars(ind_thick_4_wall_r,st)
4197
4198                 surf_usm_h%zw_window(nzb_wall,m)         = building_pars(ind_thick_1_win_r,st)
4199                 surf_usm_h%zw_window(nzb_wall+1,m)       = building_pars(ind_thick_2_win_r,st)
4200                 surf_usm_h%zw_window(nzb_wall+2,m)       = building_pars(ind_thick_3_win_r,st)
4201                 surf_usm_h%zw_window(nzb_wall+3,m)       = building_pars(ind_thick_4_win_r,st)
4202
4203                 surf_usm_h%c_surface(m)           = building_pars(ind_c_surface,st) 
4204                 surf_usm_h%lambda_surf(m)         = building_pars(ind_lambda_surf,st)
4205                 surf_usm_h%c_surface_green(m)     = building_pars(ind_c_surface_green,st) 
4206                 surf_usm_h%lambda_surf_green(m)   = building_pars(ind_lambda_surf_green,st)
4207                 surf_usm_h%c_surface_window(m)    = building_pars(ind_c_surface_win,st) 
4208                 surf_usm_h%lambda_surf_window(m)  = building_pars(ind_lambda_surf_win,st)
4209                 
4210                 surf_usm_h%green_type_roof(m)     = building_pars(ind_green_type_roof,st)
4211
4212              ENDIF
4213           ENDDO
4214
4215           DO  l = 0, 3
4216              DO  m = 1, surf_usm_v(l)%ns
4217                 i = surf_usm_v(l)%i(m) + surf_usm_v(l)%ioff
4218                 j = surf_usm_v(l)%j(m) + surf_usm_v(l)%joff
4219!
4220!--              For the moment, limit building type to 6 (to overcome errors in input file).
4221
4222                 st = building_type_f%var(j,i)
4223                 IF ( st /= building_type_f%fill )  THEN
4224
4225!
4226!--                 In order to distinguish between ground floor level and
4227!--                 above-ground-floor level surfaces, set input indices.
4228                    ind_alb_green    = MERGE( ind_alb_green_gfl,    ind_alb_green_agfl,    &
4229                                              surf_usm_v(l)%ground_level(m) )
4230                    ind_alb_wall     = MERGE( ind_alb_wall_gfl,     ind_alb_wall_agfl,     &
4231                                              surf_usm_v(l)%ground_level(m) )
4232                    ind_alb_win      = MERGE( ind_alb_win_gfl,      ind_alb_win_agfl,      &
4233                                              surf_usm_v(l)%ground_level(m) )
4234                    ind_wall_frac    = MERGE( ind_wall_frac_gfl,    ind_wall_frac_agfl,    &
4235                                              surf_usm_v(l)%ground_level(m) )
4236                    ind_win_frac     = MERGE( ind_win_frac_gfl,     ind_win_frac_agfl,     &
4237                                              surf_usm_v(l)%ground_level(m) )
4238                    ind_green_frac_w = MERGE( ind_green_frac_w_gfl, ind_green_frac_w_agfl, &
4239                                              surf_usm_v(l)%ground_level(m) )
4240                    ind_green_frac_r = MERGE( ind_green_frac_r_gfl, ind_green_frac_r_agfl, &
4241                                              surf_usm_v(l)%ground_level(m) )
4242                    ind_lai_r        = MERGE( ind_lai_r_gfl,        ind_lai_r_agfl,        &
4243                                              surf_usm_v(l)%ground_level(m) )
4244                    ind_lai_w        = MERGE( ind_lai_w_gfl,        ind_lai_w_agfl,        &
4245                                              surf_usm_v(l)%ground_level(m) )
4246                    ind_hc1          = MERGE( ind_hc1_gfl,          ind_hc1_agfl,          &
4247                                              surf_usm_v(l)%ground_level(m) )
4248                    ind_hc1_win      = MERGE( ind_hc1_win_gfl,      ind_hc1_win_agfl,      &
4249                                              surf_usm_v(l)%ground_level(m) )
4250                    ind_hc2          = MERGE( ind_hc2_gfl,          ind_hc2_agfl,          &
4251                                              surf_usm_v(l)%ground_level(m) )
4252                    ind_hc2_win      = MERGE( ind_hc2_win_gfl,      ind_hc2_win_agfl,      &
4253                                              surf_usm_v(l)%ground_level(m) )
4254                    ind_hc3          = MERGE( ind_hc3_gfl,          ind_hc3_agfl,          &
4255                                              surf_usm_v(l)%ground_level(m) )
4256                    ind_hc3_win      = MERGE( ind_hc3_win_gfl,      ind_hc3_win_agfl,      &
4257                                              surf_usm_v(l)%ground_level(m) )
4258                    ind_tc1          = MERGE( ind_tc1_gfl,          ind_tc1_agfl,          &
4259                                              surf_usm_v(l)%ground_level(m) )
4260                    ind_tc1_win      = MERGE( ind_tc1_win_gfl,      ind_tc1_win_agfl,      &
4261                                              surf_usm_v(l)%ground_level(m) )
4262                    ind_tc2          = MERGE( ind_tc2_gfl,          ind_tc2_agfl,          &
4263                                              surf_usm_v(l)%ground_level(m) )
4264                    ind_tc2_win      = MERGE( ind_tc2_win_gfl,      ind_tc2_win_agfl,      &
4265                                              surf_usm_v(l)%ground_level(m) )
4266                    ind_tc3          = MERGE( ind_tc3_gfl,          ind_tc3_agfl,          &
4267                                              surf_usm_v(l)%ground_level(m) )
4268                    ind_tc3_win      = MERGE( ind_tc3_win_gfl,      ind_tc3_win_agfl,      &
4269                                              surf_usm_v(l)%ground_level(m) )
4270                    ind_thick_1      = MERGE( ind_thick_1_gfl,      ind_thick_1_agfl,      &
4271                                              surf_usm_v(l)%ground_level(m) )
4272                    ind_thick_1_win  = MERGE( ind_thick_1_win_gfl,  ind_thick_1_win_agfl,  &
4273                                              surf_usm_v(l)%ground_level(m) )
4274                    ind_thick_2      = MERGE( ind_thick_2_gfl,      ind_thick_2_agfl,      &
4275                                              surf_usm_v(l)%ground_level(m) )
4276                    ind_thick_2_win  = MERGE( ind_thick_2_win_gfl,  ind_thick_2_win_agfl,  &
4277                                              surf_usm_v(l)%ground_level(m) )
4278                    ind_thick_3      = MERGE( ind_thick_3_gfl,      ind_thick_3_agfl,      &
4279                                              surf_usm_v(l)%ground_level(m) )
4280                    ind_thick_3_win  = MERGE( ind_thick_3_win_gfl,  ind_thick_3_win_agfl,  &
4281                                              surf_usm_v(l)%ground_level(m) )
4282                    ind_thick_4      = MERGE( ind_thick_4_gfl,      ind_thick_4_agfl,      &
4283                                              surf_usm_v(l)%ground_level(m) )
4284                    ind_thick_4_win  = MERGE( ind_thick_4_win_gfl,  ind_thick_4_win_agfl,  &
4285                                              surf_usm_v(l)%ground_level(m) )
4286                    ind_emis_wall    = MERGE( ind_emis_wall_gfl,    ind_emis_wall_agfl,    &
4287                                              surf_usm_v(l)%ground_level(m) )
4288                    ind_emis_green   = MERGE( ind_emis_green_gfl,   ind_emis_green_agfl,   &
4289                                              surf_usm_v(l)%ground_level(m) )
4290                    ind_emis_win     = MERGE( ind_emis_win_gfl,     ind_emis_win_agfl,     &
4291                                              surf_usm_v(l)%ground_level(m) )
4292                    ind_trans        = MERGE( ind_trans_gfl,       ind_trans_agfl,         &
4293                                            surf_usm_v(l)%ground_level(m) )
4294                    ind_z0           = MERGE( ind_z0_gfl,           ind_z0_agfl,           &
4295                                              surf_usm_v(l)%ground_level(m) )
4296                    ind_z0qh         = MERGE( ind_z0qh_gfl,         ind_z0qh_agfl,         &
4297                                              surf_usm_v(l)%ground_level(m) )
4298!
4299!--                 Store building type and its name on each surface element
4300                    surf_usm_v(l)%building_type(m)      = st
4301                    surf_usm_v(l)%building_type_name(m) = building_type_name(st)
4302!
4303!--                 Initialize relatvie wall- (0), green- (1) and window (2) fractions
4304                    surf_usm_v(l)%frac(ind_veg_wall,m)  = building_pars(ind_wall_frac,st)   
4305                    surf_usm_v(l)%frac(ind_pav_green,m) = building_pars(ind_green_frac_w,st) 
4306                    surf_usm_v(l)%frac(ind_wat_win,m)   = building_pars(ind_win_frac,st)   
4307                    surf_usm_v(l)%lai(m)                = building_pars(ind_lai_w,st) 
4308
4309                    surf_usm_v(l)%rho_c_wall(nzb_wall,m)   = building_pars(ind_hc1,st) 
4310                    surf_usm_v(l)%rho_c_wall(nzb_wall+1,m) = building_pars(ind_hc1,st)
4311                    surf_usm_v(l)%rho_c_wall(nzb_wall+2,m) = building_pars(ind_hc2,st)
4312                    surf_usm_v(l)%rho_c_wall(nzb_wall+3,m) = building_pars(ind_hc3,st)
4313                   
4314                    surf_usm_v(l)%rho_c_green(nzb_wall,m)   = rho_c_soil !building_pars(ind_hc1,st) 
4315                    surf_usm_v(l)%rho_c_green(nzb_wall+1,m) = rho_c_soil !building_pars(ind_hc1,st)
4316                    surf_usm_v(l)%rho_c_green(nzb_wall+2,m) = rho_c_soil !building_pars(ind_hc2,st)
4317                    surf_usm_v(l)%rho_c_green(nzb_wall+3,m) = rho_c_soil !building_pars(ind_hc3,st)
4318                   
4319                    surf_usm_v(l)%rho_c_window(nzb_wall,m)   = building_pars(ind_hc1_win,st) 
4320                    surf_usm_v(l)%rho_c_window(nzb_wall+1,m) = building_pars(ind_hc1_win,st)
4321                    surf_usm_v(l)%rho_c_window(nzb_wall+2,m) = building_pars(ind_hc2_win,st)
4322                    surf_usm_v(l)%rho_c_window(nzb_wall+3,m) = building_pars(ind_hc3_win,st)
4323
4324                    surf_usm_v(l)%lambda_h(nzb_wall,m)   = building_pars(ind_tc1,st) 
4325                    surf_usm_v(l)%lambda_h(nzb_wall+1,m) = building_pars(ind_tc1,st) 
4326                    surf_usm_v(l)%lambda_h(nzb_wall+2,m) = building_pars(ind_tc2,st)
4327                    surf_usm_v(l)%lambda_h(nzb_wall+3,m) = building_pars(ind_tc3,st) 
4328                   
4329                    surf_usm_v(l)%lambda_h_green(nzb_wall,m)   = lambda_h_green_sm !building_pars(ind_tc1,st) 
4330                    surf_usm_v(l)%lambda_h_green(nzb_wall+1,m) = lambda_h_green_sm !building_pars(ind_tc1,st)
4331                    surf_usm_v(l)%lambda_h_green(nzb_wall+2,m) = lambda_h_green_sm !building_pars(ind_tc2,st)
4332                    surf_usm_v(l)%lambda_h_green(nzb_wall+3,m) = lambda_h_green_sm !building_pars(ind_tc3,st)
4333                   
4334                    surf_usm_v(l)%lambda_h_window(nzb_wall,m)   = building_pars(ind_tc1_win,st) 
4335                    surf_usm_v(l)%lambda_h_window(nzb_wall+1,m) = building_pars(ind_tc1_win,st) 
4336                    surf_usm_v(l)%lambda_h_window(nzb_wall+2,m) = building_pars(ind_tc2_win,st)
4337                    surf_usm_v(l)%lambda_h_window(nzb_wall+3,m) = building_pars(ind_tc3_win,st) 
4338
4339                    surf_usm_v(l)%target_temp_summer(m)  = building_pars(ind_indoor_target_temp_summer,st)   
4340                    surf_usm_v(l)%target_temp_winter(m)  = building_pars(ind_indoor_target_temp_winter,st)   
4341!
4342!--                 emissivity of wall-, green- and window fraction
4343                    surf_usm_v(l)%emissivity(ind_veg_wall,m)  = building_pars(ind_emis_wall,st)
4344                    surf_usm_v(l)%emissivity(ind_pav_green,m) = building_pars(ind_emis_green,st)
4345                    surf_usm_v(l)%emissivity(ind_wat_win,m)   = building_pars(ind_emis_win,st)
4346
4347                    surf_usm_v(l)%transmissivity(m)      = building_pars(ind_trans,st)
4348
4349                    surf_usm_v(l)%z0(m)                  = building_pars(ind_z0,st)
4350                    surf_usm_v(l)%z0h(m)                 = building_pars(ind_z0qh,st)
4351                    surf_usm_v(l)%z0q(m)                 = building_pars(ind_z0qh,st)
4352
4353                    surf_usm_v(l)%albedo_type(ind_veg_wall,m)  = INT( building_pars(ind_alb_wall,st) )
4354                    surf_usm_v(l)%albedo_type(ind_pav_green,m) = INT( building_pars(ind_alb_green,st) )
4355                    surf_usm_v(l)%albedo_type(ind_wat_win,m)   = INT( building_pars(ind_alb_win,st) )
4356
4357                    surf_usm_v(l)%zw(nzb_wall,m)         = building_pars(ind_thick_1,st)
4358                    surf_usm_v(l)%zw(nzb_wall+1,m)       = building_pars(ind_thick_2,st)
4359                    surf_usm_v(l)%zw(nzb_wall+2,m)       = building_pars(ind_thick_3,st)
4360                    surf_usm_v(l)%zw(nzb_wall+3,m)       = building_pars(ind_thick_4,st)
4361                   
4362                    surf_usm_v(l)%zw_green(nzb_wall,m)         = building_pars(ind_thick_1,st)
4363                    surf_usm_v(l)%zw_green(nzb_wall+1,m)       = building_pars(ind_thick_2,st)
4364                    surf_usm_v(l)%zw_green(nzb_wall+2,m)       = building_pars(ind_thick_3,st)
4365                    surf_usm_v(l)%zw_green(nzb_wall+3,m)       = building_pars(ind_thick_4,st)
4366                   
4367                    surf_usm_v(l)%zw_window(nzb_wall,m)         = building_pars(ind_thick_1_win,st)
4368                    surf_usm_v(l)%zw_window(nzb_wall+1,m)       = building_pars(ind_thick_2_win,st)
4369                    surf_usm_v(l)%zw_window(nzb_wall+2,m)       = building_pars(ind_thick_3_win,st)
4370                    surf_usm_v(l)%zw_window(nzb_wall+3,m)       = building_pars(ind_thick_4_win,st)
4371
4372                    surf_usm_v(l)%c_surface(m)           = building_pars(ind_c_surface,st) 
4373                    surf_usm_v(l)%lambda_surf(m)         = building_pars(ind_lambda_surf,st) 
4374                    surf_usm_v(l)%c_surface_green(m)     = building_pars(ind_c_surface_green,st) 
4375                    surf_usm_v(l)%lambda_surf_green(m)   = building_pars(ind_lambda_surf_green,st) 
4376                    surf_usm_v(l)%c_surface_window(m)    = building_pars(ind_c_surface_win,st) 
4377                    surf_usm_v(l)%lambda_surf_window(m)  = building_pars(ind_lambda_surf_win,st) 
4378
4379
4380                 ENDIF
4381              ENDDO
4382           ENDDO
4383        ENDIF 
4384       
4385!
4386!--     Level 3 - initialization via building_pars read from file. Note, only
4387!--     variables that are also defined in the input-standard can be initialized
4388!--     via file. Other variables will be initialized on level 1 or 2.
4389        IF ( building_pars_f%from_file )  THEN
4390           DO  m = 1, surf_usm_h%ns
4391              i = surf_usm_h%i(m)
4392              j = surf_usm_h%j(m)
4393
4394!
4395!--           In order to distinguish between ground floor level and
4396!--           above-ground-floor level surfaces, set input indices.
4397              ind_wall_frac    = MERGE( ind_wall_frac_gfl,                     &
4398                                        ind_wall_frac_agfl,                    &
4399                                        surf_usm_h%ground_level(m) )
4400              ind_green_frac_r = MERGE( ind_green_frac_r_gfl,                  &
4401                                        ind_green_frac_r_agfl,                 &
4402                                        surf_usm_h%ground_level(m) )
4403              ind_win_frac     = MERGE( ind_win_frac_gfl,                      &
4404                                        ind_win_frac_agfl,                     &
4405                                        surf_usm_h%ground_level(m) )
4406              ind_lai_r        = MERGE( ind_lai_r_gfl,                         &
4407                                        ind_lai_r_agfl,                        &
4408                                        surf_usm_h%ground_level(m) )
4409              ind_z0           = MERGE( ind_z0_gfl,                            &
4410                                        ind_z0_agfl,                           &
4411                                        surf_usm_h%ground_level(m) )
4412              ind_z0qh         = MERGE( ind_z0qh_gfl,                          &
4413                                        ind_z0qh_agfl,                         &
4414                                        surf_usm_h%ground_level(m) )
4415              ind_hc1          = MERGE( ind_hc1_gfl,                           &
4416                                        ind_hc1_agfl,                          &
4417                                        surf_usm_h%ground_level(m) )
4418              ind_hc2          = MERGE( ind_hc2_gfl,                           &
4419                                        ind_hc2_agfl,                          &
4420                                        surf_usm_h%ground_level(m) )
4421              ind_hc3          = MERGE( ind_hc3_gfl,                           &
4422                                        ind_hc3_agfl,                          &
4423                                        surf_usm_h%ground_level(m) )
4424              ind_tc1          = MERGE( ind_tc1_gfl,                           &
4425                                        ind_tc1_agfl,                          &
4426                                        surf_usm_h%ground_level(m) )
4427              ind_tc2          = MERGE( ind_tc2_gfl,                           &
4428                                        ind_tc2_agfl,                          &
4429                                        surf_usm_h%ground_level(m) )
4430              ind_tc3          = MERGE( ind_tc3_gfl,                           &
4431                                        ind_tc3_agfl,                          &
4432                                        surf_usm_h%ground_level(m) )
4433              ind_emis_wall    = MERGE( ind_emis_wall_gfl,                     &
4434                                        ind_emis_wall_agfl,                    &
4435                                        surf_usm_h%ground_level(m) )
4436              ind_emis_green   = MERGE( ind_emis_green_gfl,                    &
4437                                        ind_emis_green_agfl,                   &
4438                                        surf_usm_h%ground_level(m) )
4439              ind_emis_win     = MERGE( ind_emis_win_gfl,                      &
4440                                        ind_emis_win_agfl,                     &
4441                                        surf_usm_h%ground_level(m) )
4442              ind_trans        = MERGE( ind_trans_gfl,                         &
4443                                        ind_trans_agfl,                        &
4444                                        surf_usm_h%ground_level(m) )
4445
4446!
4447!--           Initialize relatvie wall- (0), green- (1) and window (2) fractions
4448              IF ( building_pars_f%pars_xy(ind_wall_frac,j,i) /=               &
4449                   building_pars_f%fill )                                      &
4450                 surf_usm_h%frac(ind_veg_wall,m)  =                            &
4451                                    building_pars_f%pars_xy(ind_wall_frac,j,i)   
4452                 
4453              IF ( building_pars_f%pars_xy(ind_green_frac_r,j,i) /=            &         
4454                   building_pars_f%fill )                                      & 
4455                 surf_usm_h%frac(ind_pav_green,m) =                            &
4456                                    building_pars_f%pars_xy(ind_green_frac_r,j,i) 
4457                 
4458              IF ( building_pars_f%pars_xy(ind_win_frac,j,i) /=                &
4459                   building_pars_f%fill )                                      & 
4460                 surf_usm_h%frac(ind_wat_win,m)   =                            &
4461                                    building_pars_f%pars_xy(ind_win_frac,j,i)
4462 
4463              IF ( building_pars_f%pars_xy(ind_lai_r,j,i) /=                   &
4464                   building_pars_f%fill )                                      &
4465                 surf_usm_h%lai(m)  = building_pars_f%pars_xy(ind_lai_r,j,i)
4466
4467              IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=                     &
4468                   building_pars_f%fill )  THEN
4469                 surf_usm_h%rho_c_wall(nzb_wall,m)   =                         &
4470                                    building_pars_f%pars_xy(ind_hc1,j,i) 
4471                 surf_usm_h%rho_c_wall(nzb_wall+1,m) =                         &
4472                                    building_pars_f%pars_xy(ind_hc1,j,i)
4473              ENDIF
4474             
4475             
4476              IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=                     &
4477                   building_pars_f%fill )                                      &
4478                 surf_usm_h%rho_c_wall(nzb_wall+2,m) =                         &
4479                                    building_pars_f%pars_xy(ind_hc2,j,i)
4480                 
4481              IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=                     &
4482                   building_pars_f%fill )                                      &
4483                 surf_usm_h%rho_c_wall(nzb_wall+3,m) =                         &
4484                                    building_pars_f%pars_xy(ind_hc3,j,i)
4485                 
4486              IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=                     &
4487                   building_pars_f%fill )  THEN
4488                 surf_usm_h%rho_c_green(nzb_wall,m)   =                        &
4489                                    building_pars_f%pars_xy(ind_hc1,j,i) 
4490                 surf_usm_h%rho_c_green(nzb_wall+1,m) =                        &
4491                                    building_pars_f%pars_xy(ind_hc1,j,i)
4492              ENDIF
4493              IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=                     &
4494                   building_pars_f%fill )                                      &
4495                 surf_usm_h%rho_c_green(nzb_wall+2,m) =                        &
4496                                    building_pars_f%pars_xy(ind_hc2,j,i)
4497                 
4498              IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=                     &
4499                   building_pars_f%fill )                                      &
4500                 surf_usm_h%rho_c_green(nzb_wall+3,m) =                        &
4501                                    building_pars_f%pars_xy(ind_hc3,j,i)
4502                 
4503              IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=                     &
4504                   building_pars_f%fill )  THEN
4505                 surf_usm_h%rho_c_window(nzb_wall,m)   =                       &
4506                                    building_pars_f%pars_xy(ind_hc1,j,i) 
4507                 surf_usm_h%rho_c_window(nzb_wall+1,m) =                       &
4508                                    building_pars_f%pars_xy(ind_hc1,j,i)
4509              ENDIF
4510              IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=                     &
4511                   building_pars_f%fill )                                      &
4512                 surf_usm_h%rho_c_window(nzb_wall+2,m) =                       &
4513                                    building_pars_f%pars_xy(ind_hc2,j,i)
4514                 
4515              IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=                     &
4516                   building_pars_f%fill )                                      &
4517                 surf_usm_h%rho_c_window(nzb_wall+3,m) =                       &
4518                                    building_pars_f%pars_xy(ind_hc3,j,i)
4519
4520              IF ( building_pars_f%pars_xy(ind_tc1,j,i) /=                     &
4521                   building_pars_f%fill )  THEN
4522                 surf_usm_h%lambda_h(nzb_wall,m)   =                           &
4523                                    building_pars_f%pars_xy(ind_tc1,j,i)         
4524                 surf_usm_h%lambda_h(nzb_wall+1,m) =                           &
4525                                    building_pars_f%pars_xy(ind_tc1,j,i)       
4526              ENDIF
4527              IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=                     & 
4528                   building_pars_f%fill )                                      &
4529                 surf_usm_h%lambda_h(nzb_wall+2,m) =                           &
4530                                    building_pars_f%pars_xy(ind_tc2,j,i)
4531                 
4532              IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=                     &
4533                   building_pars_f%fill )                                      & 
4534                 surf_usm_h%lambda_h(nzb_wall+3,m) =                           &
4535                                    building_pars_f%pars_xy(ind_tc3,j,i)   
4536                 
4537              IF ( building_pars_f%pars_xy(ind_tc1,j,i) /=                     &
4538                   building_pars_f%fill )  THEN
4539                 surf_usm_h%lambda_h_green(nzb_wall,m)   =                     &
4540                                     building_pars_f%pars_xy(ind_tc1,j,i)         
4541                 surf_usm_h%lambda_h_green(nzb_wall+1,m) =                     &
4542                                     building_pars_f%pars_xy(ind_tc1,j,i)       
4543              ENDIF
4544              IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=                     & 
4545                   building_pars_f%fill )                                      &
4546                 surf_usm_h%lambda_h_green(nzb_wall+2,m) =                     &
4547                                    building_pars_f%pars_xy(ind_tc2,j,i)
4548                 
4549              IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=                     &       
4550                   building_pars_f%fill )                                      &
4551                 surf_usm_h%lambda_h_green(nzb_wall+3,m) =                     &
4552                                    building_pars_f%pars_xy(ind_tc3,j,i)   
4553                 
4554              IF ( building_pars_f%pars_xy(ind_tc1,j,i) /=                     &
4555                   building_pars_f%fill )  THEN
4556                 surf_usm_h%lambda_h_window(nzb_wall,m)   =                    &
4557                                     building_pars_f%pars_xy(ind_tc1,j,i)         
4558                 surf_usm_h%lambda_h_window(nzb_wall+1,m) =                    &
4559                                     building_pars_f%pars_xy(ind_tc1,j,i)       
4560              ENDIF
4561              IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=                     &     
4562                   building_pars_f%fill )                                      &
4563                 surf_usm_h%lambda_h_window(nzb_wall+2,m) =                    &
4564                                     building_pars_f%pars_xy(ind_tc2,j,i)
4565                 
4566              IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=                     &   
4567                   building_pars_f%fill )                                      &
4568                 surf_usm_h%lambda_h_window(nzb_wall+3,m) =                    &
4569                                    building_pars_f%pars_xy(ind_tc3,j,i)   
4570
4571              IF ( building_pars_f%pars_xy(ind_indoor_target_temp_summer,j,i) /=&           
4572                   building_pars_f%fill )                                      & 
4573                 surf_usm_h%target_temp_summer(m)  =                           &
4574                      building_pars_f%pars_xy(ind_indoor_target_temp_summer,j,i)   
4575              IF ( building_pars_f%pars_xy(ind_indoor_target_temp_winter,j,i) /=&           
4576                   building_pars_f%fill )                                      & 
4577                 surf_usm_h%target_temp_winter(m)  =                           &
4578                      building_pars_f%pars_xy(ind_indoor_target_temp_winter,j,i)   
4579
4580              IF ( building_pars_f%pars_xy(ind_emis_wall,j,i) /=               &   
4581                   building_pars_f%fill )                                      &
4582                 surf_usm_h%emissivity(ind_veg_wall,m)  =                      &
4583                                    building_pars_f%pars_xy(ind_emis_wall,j,i)
4584                 
4585              IF ( building_pars_f%pars_xy(ind_emis_green,j,i) /=              &           
4586                   building_pars_f%fill )                                      &
4587                 surf_usm_h%emissivity(ind_pav_green,m) =                      &
4588                                     building_pars_f%pars_xy(ind_emis_green,j,i)
4589                 
4590              IF ( building_pars_f%pars_xy(ind_emis_win,j,i) /=                & 
4591                   building_pars_f%fill )                                      &
4592                 surf_usm_h%emissivity(ind_wat_win,m)   =                      &
4593                                     building_pars_f%pars_xy(ind_emis_win,j,i)
4594                 
4595              IF ( building_pars_f%pars_xy(ind_trans,j,i) /=                   &   
4596                   building_pars_f%fill )                                      &
4597                 surf_usm_h%transmissivity(m) =                                &
4598                                    building_pars_f%pars_xy(ind_trans,j,i)
4599
4600              IF ( building_pars_f%pars_xy(ind_z0,j,i) /=                      &         
4601                   building_pars_f%fill )                                      &
4602                 surf_usm_h%z0(m) = building_pars_f%pars_xy(ind_z0,j,i)
4603                 
4604              IF ( building_pars_f%pars_xy(ind_z0qh,j,i) /=                    &           
4605                   building_pars_f%fill )                                      &
4606                 surf_usm_h%z0h(m) = building_pars_f%pars_xy(ind_z0qh,j,i)
4607              IF ( building_pars_f%pars_xy(ind_z0qh,j,i) /=                    &           
4608                   building_pars_f%fill )                                      &
4609                 surf_usm_h%z0q(m) = building_pars_f%pars_xy(ind_z0qh,j,i)
4610
4611              IF ( building_pars_f%pars_xy(ind_alb_wall_agfl,j,i) /=           &         
4612                   building_pars_f%fill )                                      & 
4613                 surf_usm_h%albedo_type(ind_veg_wall,m)  =                     &
4614                                 building_pars_f%pars_xy(ind_alb_wall_agfl,j,i)
4615                 
4616              IF ( building_pars_f%pars_xy(ind_alb_green_agfl,j,i) /=          &           
4617                   building_pars_f%fill )                                      &
4618                 surf_usm_h%albedo_type(ind_pav_green,m) =                     &
4619                                building_pars_f%pars_xy(ind_alb_green_agfl,j,i)
4620              IF ( building_pars_f%pars_xy(ind_alb_win_agfl,j,i) /=            &         
4621                   building_pars_f%fill )                                      &
4622                 surf_usm_h%albedo_type(ind_wat_win,m)   =                     &
4623                                   building_pars_f%pars_xy(ind_alb_win_agfl,j,i)
4624
4625              IF ( building_pars_f%pars_xy(ind_thick_1_agfl,j,i) /=            &         
4626                   building_pars_f%fill )                                      & 
4627                 surf_usm_h%zw(nzb_wall,m) =                                   &
4628                                  building_pars_f%pars_xy(ind_thick_1_agfl,j,i)
4629                 
4630              IF ( building_pars_f%pars_xy(ind_thick_2_agfl,j,i) /=            &         
4631                   building_pars_f%fill )                                      &
4632                 surf_usm_h%zw(nzb_wall+1,m) =                                 &
4633                                  building_pars_f%pars_xy(ind_thick_2_agfl,j,i)
4634                 
4635              IF ( building_pars_f%pars_xy(ind_thick_3_agfl,j,i) /=            &         
4636                   building_pars_f%fill )                                      &
4637                 surf_usm_h%zw(nzb_wall+2,m) =                                 &
4638                                  building_pars_f%pars_xy(ind_thick_3_agfl,j,i)
4639                 
4640                 
4641              IF ( building_pars_f%pars_xy(ind_thick_4_agfl,j,i) /=            &         
4642                   building_pars_f%fill )                                      & 
4643                 surf_usm_h%zw(nzb_wall+3,m) =                                 &
4644                                  building_pars_f%pars_xy(ind_thick_4_agfl,j,i)
4645                 
4646              IF ( building_pars_f%pars_xy(ind_thick_1_agfl,j,i) /=            &           
4647                   building_pars_f%fill )                                      &
4648                 surf_usm_h%zw_green(nzb_wall,m) =                             &
4649                                  building_pars_f%pars_xy(ind_thick_1_agfl,j,i)
4650                 
4651              IF ( building_pars_f%pars_xy(ind_thick_2_agfl,j,i) /=            &         
4652                   building_pars_f%fill )                                      &
4653                 surf_usm_h%zw_green(nzb_wall+1,m) =                           &
4654                                   building_pars_f%pars_xy(ind_thick_2_agfl,j,i)
4655                 
4656              IF ( building_pars_f%pars_xy(ind_thick_3_agfl,j,i) /=            &         
4657                   building_pars_f%fill )                                      & 
4658                 surf_usm_h%zw_green(nzb_wall+2,m) =                           &
4659                                   building_pars_f%pars_xy(ind_thick_3_agfl,j,i)
4660                 
4661              IF ( building_pars_f%pars_xy(ind_thick_4_agfl,j,i) /=            &         
4662                   building_pars_f%fill )                                      &
4663                 surf_usm_h%zw_green(nzb_wall+3,m) =                           &
4664                                   building_pars_f%pars_xy(ind_thick_4_agfl,j,i)
4665
4666              IF ( building_pars_f%pars_xy(ind_c_surface,j,i) /=               &       
4667                   building_pars_f%fill )                                      & 
4668                 surf_usm_h%c_surface(m) =                                     &
4669                                    building_pars_f%pars_xy(ind_c_surface,j,i)
4670                 
4671              IF ( building_pars_f%pars_xy(ind_lambda_surf,j,i) /=             &       
4672                   building_pars_f%fill )                                      &
4673                 surf_usm_h%lambda_surf(m) =                                   &
4674                                    building_pars_f%pars_xy(ind_lambda_surf,j,i)
4675             
4676           ENDDO
4677
4678
4679
4680           DO  l = 0, 3
4681              DO  m = 1, surf_usm_v(l)%ns
4682                 i = surf_usm_v(l)%i(m) + surf_usm_v(l)%ioff
4683                 j = surf_usm_v(l)%j(m) + surf_usm_v(l)%joff
4684               
4685!
4686!--                 In order to distinguish between ground floor level and
4687!--                 above-ground-floor level surfaces, set input indices.
4688                    ind_wall_frac    = MERGE( ind_wall_frac_gfl,               &
4689                                              ind_wall_frac_agfl,              &
4690                                              surf_usm_v(l)%ground_level(m) )
4691                    ind_green_frac_w = MERGE( ind_green_frac_w_gfl,            &
4692                                              ind_green_frac_w_agfl,           &
4693                                              surf_usm_v(l)%ground_level(m) )
4694                    ind_win_frac     = MERGE( ind_win_frac_gfl,                &
4695                                              ind_win_frac_agfl,               &
4696                                              surf_usm_v(l)%ground_level(m) )
4697                    ind_lai_w        = MERGE( ind_lai_w_gfl,                   &
4698                                              ind_lai_w_agfl,                  &
4699                                              surf_usm_v(l)%ground_level(m) )
4700                    ind_z0           = MERGE( ind_z0_gfl,                      &
4701                                              ind_z0_agfl,                     &
4702                                              surf_usm_v(l)%ground_level(m) )
4703                    ind_z0qh         = MERGE( ind_z0qh_gfl,                    &
4704                                              ind_z0qh_agfl,                   &
4705                                              surf_usm_v(l)%ground_level(m) )
4706                    ind_hc1          = MERGE( ind_hc1_gfl,                     &
4707                                              ind_hc1_agfl,                    &
4708                                              surf_usm_v(l)%ground_level(m) )
4709                    ind_hc2          = MERGE( ind_hc2_gfl,                     &
4710                                              ind_hc2_agfl,                    &
4711                                              surf_usm_v(l)%ground_level(m) )
4712                    ind_hc3          = MERGE( ind_hc3_gfl,                     &
4713                                              ind_hc3_agfl,                    &
4714                                              surf_usm_v(l)%ground_level(m) )
4715                    ind_tc1          = MERGE( ind_tc1_gfl,                     &
4716                                              ind_tc1_agfl,                    &
4717                                              surf_usm_v(l)%ground_level(m) )
4718                    ind_tc2          = MERGE( ind_tc2_gfl,                     &
4719                                              ind_tc2_agfl,                    &
4720                                              surf_usm_v(l)%ground_level(m) )
4721                    ind_tc3          = MERGE( ind_tc3_gfl,                     &
4722                                              ind_tc3_agfl,                    &
4723                                              surf_usm_v(l)%ground_level(m) )
4724                    ind_emis_wall    = MERGE( ind_emis_wall_gfl,               &
4725                                              ind_emis_wall_agfl,              &
4726                                              surf_usm_v(l)%ground_level(m) )
4727                    ind_emis_green   = MERGE( ind_emis_green_gfl,              &
4728                                              ind_emis_green_agfl,             &
4729                                              surf_usm_v(l)%ground_level(m) )
4730                    ind_emis_win     = MERGE( ind_emis_win_gfl,                &
4731                                              ind_emis_win_agfl,               &
4732                                              surf_usm_v(l)%ground_level(m) )
4733                    ind_trans        = MERGE( ind_trans_gfl,                   &
4734                                              ind_trans_agfl,                  &
4735                                              surf_usm_v(l)%ground_level(m) )
4736                   
4737!                   
4738!--                 Initialize relatvie wall- (0), green- (1) and window (2) fractions
4739                    IF ( building_pars_f%pars_xy(ind_wall_frac,j,i) /=         &
4740                         building_pars_f%fill )                                &
4741                       surf_usm_v(l)%frac(ind_veg_wall,m)  =                   &
4742                                          building_pars_f%pars_xy(ind_wall_frac,j,i)   
4743                       
4744                    IF ( building_pars_f%pars_xy(ind_green_frac_w,j,i) /=      &         
4745                         building_pars_f%fill )                                & 
4746                       surf_usm_v(l)%frac(ind_pav_green,m) =                   &
4747                                  building_pars_f%pars_xy(ind_green_frac_w,j,i) 
4748                       
4749                    IF ( building_pars_f%pars_xy(ind_win_frac,j,i) /=          &
4750                         building_pars_f%fill )                                & 
4751                       surf_usm_v(l)%frac(ind_wat_win,m)   =                   &
4752                                       building_pars_f%pars_xy(ind_win_frac,j,i)
4753                   
4754                    IF ( building_pars_f%pars_xy(ind_lai_w,j,i) /=             &
4755                         building_pars_f%fill )                                &
4756                       surf_usm_v(l)%lai(m)  =                                 &
4757                                       building_pars_f%pars_xy(ind_lai_w,j,i)
4758                   
4759                    IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=               &
4760                         building_pars_f%fill )  THEN
4761                       surf_usm_v(l)%rho_c_wall(nzb_wall,m)   =                &
4762                                          building_pars_f%pars_xy(ind_hc1,j,i) 
4763                       surf_usm_v(l)%rho_c_wall(nzb_wall+1,m) =                &
4764                                          building_pars_f%pars_xy(ind_hc1,j,i)
4765                    ENDIF
4766                   
4767                   
4768                    IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=               &
4769                         building_pars_f%fill )                                &
4770                       surf_usm_v(l)%rho_c_wall(nzb_wall+2,m) =                &
4771                                          building_pars_f%pars_xy(ind_hc2,j,i)
4772                       
4773                    IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=               &         
4774                         building_pars_f%fill )                                &
4775                       surf_usm_v(l)%rho_c_wall(nzb_wall+3,m) =                &
4776                                          building_pars_f%pars_xy(ind_hc3,j,i)
4777                       
4778                    IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=               &
4779                         building_pars_f%fill )  THEN
4780                       surf_usm_v(l)%rho_c_green(nzb_wall,m)   =               &
4781                                          building_pars_f%pars_xy(ind_hc1,j,i) 
4782                       surf_usm_v(l)%rho_c_green(nzb_wall+1,m) =               &
4783                                          building_pars_f%pars_xy(ind_hc1,j,i)
4784                    ENDIF
4785                    IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=               &
4786                         building_pars_f%fill )                                &
4787                       surf_usm_v(l)%rho_c_green(nzb_wall+2,m) =               &
4788                                          building_pars_f%pars_xy(ind_hc2,j,i)
4789                       
4790                    IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=               &
4791                         building_pars_f%fill )                                &
4792                       surf_usm_v(l)%rho_c_green(nzb_wall+3,m) =               &
4793                                          building_pars_f%pars_xy(ind_hc3,j,i)
4794                       
4795                    IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=               &
4796                         building_pars_f%fill )  THEN
4797                       surf_usm_v(l)%rho_c_window(nzb_wall,m)   =              &
4798                                          building_pars_f%pars_xy(ind_hc1,j,i) 
4799                       surf_usm_v(l)%rho_c_window(nzb_wall+1,m) =              &
4800                                          building_pars_f%pars_xy(ind_hc1,j,i)
4801                    ENDIF
4802                    IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=               &
4803                         building_pars_f%fill )                                &
4804                       surf_usm_v(l)%rho_c_window(nzb_wall+2,m) =              &
4805                                          building_pars_f%pars_xy(ind_hc2,j,i)
4806                       
4807                    IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=               &
4808                         building_pars_f%fill )                                &
4809                       surf_usm_v(l)%rho_c_window(nzb_wall+3,m) =              &
4810                                          building_pars_f%pars_xy(ind_hc3,j,i)
4811                   
4812                    IF ( building_pars_f%pars_xy(ind_tc1,j,i) /=               &
4813                         building_pars_f%fill )  THEN
4814                       surf_usm_v(l)%lambda_h(nzb_wall,m)   =                  &
4815                                          building_pars_f%pars_xy(ind_tc1,j,i)   
4816                       surf_usm_v(l)%lambda_h(nzb_wall+1,m) =                  &
4817                                          building_pars_f%pars_xy(ind_tc1,j,i) 
4818                    ENDIF
4819                    IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=               & 
4820                         building_pars_f%fill )                                &
4821                       surf_usm_v(l)%lambda_h(nzb_wall+2,m) =                  &
4822                                          building_pars_f%pars_xy(ind_tc2,j,i)
4823                       
4824                    IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=               &
4825                         building_pars_f%fill )                                & 
4826                       surf_usm_v(l)%lambda_h(nzb_wall+3,m) =                  &
4827                                          building_pars_f%pars_xy(ind_tc3,j,i) 
4828                       
4829                    IF ( building_pars_f%pars_xy(ind_tc1,j,i) /=               &
4830                         building_pars_f%fill )  THEN
4831                       surf_usm_v(l)%lambda_h_green(nzb_wall,m)   =            &
4832                                           building_pars_f%pars_xy(ind_tc1,j,i)   
4833                       surf_usm_v(l)%lambda_h_green(nzb_wall+1,m) =            &
4834                                           building_pars_f%pars_xy(ind_tc1,j,i) 
4835                    ENDIF
4836                    IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=               & 
4837                         building_pars_f%fill )                                &
4838                       surf_usm_v(l)%lambda_h_green(nzb_wall+2,m) =            &
4839                                          building_pars_f%pars_xy(ind_tc2,j,i)
4840                       
4841                    IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=               &       
4842                         building_pars_f%fill )                                &
4843                       surf_usm_v(l)%lambda_h_green(nzb_wall+3,m) =            &
4844                                          building_pars_f%pars_xy(ind_tc3,j,i) 
4845                       
4846                    IF ( building_pars_f%pars_xy(ind_tc1,j,i) /=         &
4847                         building_pars_f%fill )  THEN
4848                       surf_usm_v(l)%lambda_h_window(nzb_wall,m)   =           &
4849                                     building_pars_f%pars_xy(ind_tc1,j,i)         
4850                       surf_usm_v(l)%lambda_h_window(nzb_wall+1,m) =           &
4851                                     building_pars_f%pars_xy(ind_tc1,j,i)       
4852                    ENDIF
4853                    IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=               &     
4854                         building_pars_f%fill )                                &
4855                       surf_usm_v(l)%lambda_h_window(nzb_wall+2,m) =           &
4856                                           building_pars_f%pars_xy(ind_tc2,j,i)
4857                       
4858                    IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=               &   
4859                         building_pars_f%fill )                                &
4860                       surf_usm_v(l)%lambda_h_window(nzb_wall+3,m) =           &
4861                                          building_pars_f%pars_xy(ind_tc3,j,i)   
4862                   
4863                    IF ( building_pars_f%pars_xy(ind_indoor_target_temp_summer,j,i) /=&           
4864                         building_pars_f%fill )                                & 
4865                       surf_usm_v(l)%target_temp_summer(m)  =                  &
4866                            building_pars_f%pars_xy(ind_indoor_target_temp_summer,j,i)   
4867                    IF ( building_pars_f%pars_xy(ind_indoor_target_temp_winter,j,i) /=&           
4868                         building_pars_f%fill )                                & 
4869                       surf_usm_v(l)%target_temp_winter(m)  =                  &
4870                            building_pars_f%pars_xy(ind_indoor_target_temp_winter,j,i)   
4871                   
4872                    IF ( building_pars_f%pars_xy(ind_emis_wall,j,i) /=         &   
4873                         building_pars_f%fill )                                &
4874                       surf_usm_v(l)%emissivity(ind_veg_wall,m)  =             &
4875                                      building_pars_f%pars_xy(ind_emis_wall,j,i)
4876                       
4877                    IF ( building_pars_f%pars_xy(ind_emis_green,j,i) /=        &           
4878                         building_pars_f%fill )                                &
4879                       surf_usm_v(l)%emissivity(ind_pav_green,m) =             &
4880                                      building_pars_f%pars_xy(ind_emis_green,j,i)
4881                       
4882                    IF ( building_pars_f%pars_xy(ind_emis_win,j,i) /=          & 
4883                         building_pars_f%fill )                                &
4884                       surf_usm_v(l)%emissivity(ind_wat_win,m)   =             &
4885                                      building_pars_f%pars_xy(ind_emis_win,j,i)
4886                       
4887                    IF ( building_pars_f%pars_xy(ind_trans,j,i) /=             &   
4888                         building_pars_f%fill )                                &
4889                       surf_usm_v(l)%transmissivity(m) =                       &
4890                                          building_pars_f%pars_xy(ind_trans,j,i)
4891                   
4892                    IF ( building_pars_f%pars_xy(ind_z0,j,i) /=                &         
4893                         building_pars_f%fill )                                &
4894                       surf_usm_v(l)%z0(m) = building_pars_f%pars_xy(ind_z0,j,i)
4895                       
4896                    IF ( building_pars_f%pars_xy(ind_z0qh,j,i) /=              &           
4897                         building_pars_f%fill )                                &
4898                       surf_usm_v(l)%z0h(m) =                                  &
4899                                       building_pars_f%pars_xy(ind_z0qh,j,i)
4900                    IF ( building_pars_f%pars_xy(ind_z0qh,j,i) /=              &           
4901                         building_pars_f%fill )                                &
4902                       surf_usm_v(l)%z0q(m) =                                  &
4903                                       building_pars_f%pars_xy(ind_z0qh,j,i)
4904                   
4905                    IF ( building_pars_f%pars_xy(ind_alb_wall_agfl,j,i) /=     &         
4906                         building_pars_f%fill )                                & 
4907                       surf_usm_v(l)%albedo_type(ind_veg_wall,m)  =            &
4908                                 building_pars_f%pars_xy(ind_alb_wall_agfl,j,i)
4909                       
4910                    IF ( building_pars_f%pars_xy(ind_alb_green_agfl,j,i) /=    &           
4911                         building_pars_f%fill )                                &
4912                       surf_usm_v(l)%albedo_type(ind_pav_green,m) =            &
4913                                 building_pars_f%pars_xy(ind_alb_green_agfl,j,i)
4914                    IF ( building_pars_f%pars_xy(ind_alb_win_agfl,j,i) /=      &         
4915                         building_pars_f%fill )                                &
4916                       surf_usm_v(l)%albedo_type(ind_wat_win,m)   =            &
4917                                   building_pars_f%pars_xy(ind_alb_win_agfl,j,i)
4918                   
4919                    IF ( building_pars_f%pars_xy(ind_thick_1_agfl,j,i) /=      &         
4920                         building_pars_f%fill )                                & 
4921                       surf_usm_v(l)%zw(nzb_wall,m) =                          &
4922                                   building_pars_f%pars_xy(ind_thick_1_agfl,j,i)
4923                       
4924                    IF ( building_pars_f%pars_xy(ind_thick_2_agfl,j,i) /=      &         
4925                         building_pars_f%fill )                                &
4926                       surf_usm_v(l)%zw(nzb_wall+1,m) =                        &
4927                                   building_pars_f%pars_xy(ind_thick_2_agfl,j,i)
4928                       
4929                    IF ( building_pars_f%pars_xy(ind_thick_3_agfl,j,i) /=      &         
4930                         building_pars_f%fill )                                &
4931                       surf_usm_v(l)%zw(nzb_wall+2,m) =                        &
4932                                   building_pars_f%pars_xy(ind_thick_3_agfl,j,i)
4933                       
4934                       
4935                    IF ( building_pars_f%pars_xy(ind_thick_4_agfl,j,i) /=      &         
4936                         building_pars_f%fill )                                & 
4937                       surf_usm_v(l)%zw(nzb_wall+3,m) =                        &
4938                                   building_pars_f%pars_xy(ind_thick_4_agfl,j,i)
4939                       
4940                    IF ( building_pars_f%pars_xy(ind_thick_1_agfl,j,i) /=      &           
4941                         building_pars_f%fill )                                &
4942                       surf_usm_v(l)%zw_green(nzb_wall,m) =                    &
4943                                   building_pars_f%pars_xy(ind_thick_1_agfl,j,i)
4944                       
4945                    IF ( building_pars_f%pars_xy(ind_thick_2_agfl,j,i) /=      &         
4946                         building_pars_f%fill )                                &
4947                       surf_usm_v(l)%zw_green(nzb_wall+1,m) =                  &
4948                                   building_pars_f%pars_xy(ind_thick_2_agfl,j,i)
4949                       
4950                    IF ( building_pars_f%pars_xy(ind_thick_3_agfl,j,i) /=      &         
4951                         building_pars_f%fill )                                & 
4952                       surf_usm_v(l)%zw_green(nzb_wall+2,m) =                  &
4953                                   building_pars_f%pars_xy(ind_thick_3_agfl,j,i)
4954                       
4955                    IF ( building_pars_f%pars_xy(ind_thick_4_agfl,j,i) /=      &         
4956                         building_pars_f%fill )                                &
4957                       surf_usm_v(l)%zw_green(nzb_wall+3,m) =                  &
4958                                   building_pars_f%pars_xy(ind_thick_4_agfl,j,i)
4959                   
4960                    IF ( building_pars_f%pars_xy(ind_c_surface,j,i) /=         &       
4961                         building_pars_f%fill )                                & 
4962                       surf_usm_v(l)%c_surface(m) =                            &
4963                                     building_pars_f%pars_xy(ind_c_surface,j,i)
4964                       
4965                    IF ( building_pars_f%pars_xy(ind_lambda_surf,j,i) /=       &       
4966                         building_pars_f%fill )                                &
4967                       surf_usm_v(l)%lambda_surf(m) =                          &
4968                                    building_pars_f%pars_xy(ind_lambda_surf,j,i)
4969                   
4970              ENDDO
4971           ENDDO
4972        ENDIF 
4973!       
4974!--     Read the surface_types array.
4975!--     Please note, here also initialization of surface attributes is done as
4976!--     long as _urbsurf and _surfpar files are available. Values from above
4977!--     will be overwritten. This might be removed later, but is still in the
4978!--     code to enable compatibility with older model version.
4979        CALL usm_read_urban_surface_types()
4980       
4981        CALL usm_init_material_model()
4982!       
4983!--     init anthropogenic sources of heat
4984        IF ( usm_anthropogenic_heat )  THEN
4985!
4986!--         init anthropogenic sources of heat (from transportation for now)
4987            CALL usm_read_anthropogenic_heat()
4988        ENDIF
4989
4990!
4991!--    Check for consistent initialization.
4992!--    Check if roughness length for momentum, or heat, exceed surface-layer
4993!--    height and decrease local roughness length where necessary.
4994       DO  m = 1, surf_usm_h%ns
4995          IF ( surf_usm_h%z0(m) >= surf_usm_h%z_mo(m) )  THEN
4996         
4997             surf_usm_h%z0(m) = 0.9_wp * surf_usm_h%z_mo(m)
4998             
4999             WRITE( message_string, * ) 'z0 exceeds surface-layer height ' //  &
5000                            'at horizontal urban surface and is ' //           &
5001                            'decreased appropriately at grid point (i,j) = ',  &
5002                            surf_usm_h%i(m), surf_usm_h%j(m)
5003             CALL message( 'urban_surface_model_mod', 'PA0503',                &
5004                            0, 0, 0, 6, 0 )
5005          ENDIF
5006          IF ( surf_usm_h%z0h(m) >= surf_usm_h%z_mo(m) )  THEN
5007         
5008             surf_usm_h%z0h(m) = 0.9_wp * surf_usm_h%z_mo(m)
5009             surf_usm_h%z0q(m) = 0.9_wp * surf_usm_h%z_mo(m)
5010             
5011             WRITE( message_string, * ) 'z0h exceeds surface-layer height ' // &
5012                            'at horizontal urban surface and is ' //           &
5013                            'decreased appropriately at grid point (i,j) = ',  &
5014                            surf_usm_h%i(m), surf_usm_h%j(m)
5015             CALL message( 'urban_surface_model_mod', 'PA0507',                &
5016                            0, 0, 0, 6, 0 )
5017          ENDIF         
5018       ENDDO
5019       
5020       DO  l = 0, 3
5021          DO  m = 1, surf_usm_v(l)%ns
5022             IF ( surf_usm_v(l)%z0(m) >= surf_usm_v(l)%z_mo(m) )  THEN
5023         
5024                surf_usm_v(l)%z0(m) = 0.9_wp * surf_usm_v(l)%z_mo(m)
5025             
5026                WRITE( message_string, * ) 'z0 exceeds surface-layer height '// &
5027                            'at vertical urban surface and is ' //              &
5028                            'decreased appropriately at grid point (i,j) = ',   &
5029                            surf_usm_v(l)%i(m)+surf_usm_v(l)%ioff,              &
5030                            surf_usm_v(l)%j(m)+surf_usm_v(l)%joff
5031                CALL message( 'urban_surface_model_mod', 'PA0503',              &
5032                            0, 0, 0, 6, 0 )
5033             ENDIF
5034             IF ( surf_usm_v(l)%z0h(m) >= surf_usm_v(l)%z_mo(m) )  THEN
5035         
5036                surf_usm_v(l)%z0h(m) = 0.9_wp * surf_usm_v(l)%z_mo(m)
5037                surf_usm_v(l)%z0q(m) = 0.9_wp * surf_usm_v(l)%z_mo(m)
5038             
5039                WRITE( message_string, * ) 'z0h exceeds surface-layer height '// &
5040                            'at vertical urban surface and is ' //               &
5041                            'decreased appropriately at grid point (i,j) = ',    &
5042                            surf_usm_v(l)%i(m)+surf_usm_v(l)%ioff,               &
5043                            surf_usm_v(l)%j(m)+surf_usm_v(l)%joff
5044                CALL message( 'urban_surface_model_mod', 'PA0507',               &
5045                            0, 0, 0, 6, 0 )
5046             ENDIF
5047          ENDDO
5048       ENDDO
5049!
5050!--    Just a work-around: Set green fraction on roof to zero (in favor of
5051!--    wall fraction). The green-heat model crashes due to some unknown reason.
5052!--    To be removed later. 
5053       DO  m = 1, surf_usm_h%ns
5054          IF ( surf_usm_h%frac(ind_pav_green,m) > 0.0_wp )  THEN
5055             surf_usm_h%frac(ind_veg_wall,m)  = surf_usm_h%frac(ind_veg_wall,m)&
5056                                              + surf_usm_h%frac(ind_pav_green,m)
5057             surf_usm_h%frac(ind_pav_green,m) = 0.0_wp
5058          ENDIF
5059       ENDDO
5060       DO  l = 0, 3
5061          DO  m = 1, surf_usm_v(l)%ns
5062             IF ( surf_usm_v(l)%frac(ind_pav_green,m) > 0.0_wp )  THEN
5063                surf_usm_v(l)%frac(ind_veg_wall,m)  =                          &
5064                                             surf_usm_v(l)%frac(ind_veg_wall,m)&
5065                                           + surf_usm_v(l)%frac(ind_pav_green,m)
5066                surf_usm_v(l)%frac(ind_pav_green,m) = 0.0_wp
5067             ENDIF
5068          ENDDO
5069       ENDDO
5070
5071!
5072!--     Intitialization of the surface and wall/ground/roof temperature
5073!
5074!--     Initialization for restart runs
5075        IF ( TRIM( initializing_actions ) /= 'read_restart_data'  .AND.        &
5076             TRIM( initializing_actions ) /= 'cyclic_fill' )  THEN
5077
5078!
5079!--         At horizontal surfaces. Please note, t_surf_wall_h is defined on a
5080!--         different data type, but with the same dimension.
5081            DO  m = 1, surf_usm_h%ns
5082               i = surf_usm_h%i(m)           
5083               j = surf_usm_h%j(m)
5084               k = surf_usm_h%k(m)
5085
5086               t_surf_wall_h(m) = pt(k,j,i) * exner(k)
5087               t_surf_window_h(m) = pt(k,j,i) * exner(k)
5088               t_surf_green_h(m) = pt(k,j,i) * exner(k)
5089               surf_usm_h%pt_surface(m) = pt(k,j,i) * exner(k)
5090            ENDDO
5091!
5092!--         At vertical surfaces.
5093            DO  l = 0, 3
5094               DO  m = 1, surf_usm_v(l)%ns
5095                  i = surf_usm_v(l)%i(m)           
5096                  j = surf_usm_v(l)%j(m)
5097                  k = surf_usm_v(l)%k(m)
5098
5099                  t_surf_wall_v(l)%t(m) = pt(k,j,i) * exner(k)
5100                  t_surf_window_v(l)%t(m) = pt(k,j,i) * exner(k)
5101                  t_surf_green_v(l)%t(m) = pt(k,j,i) * exner(k)
5102                  surf_usm_v(l)%pt_surface(m) = pt(k,j,i) * exner(k)
5103               ENDDO
5104            ENDDO
5105
5106!
5107!--         For the sake of correct initialization, set also q_surface.
5108!--         Note, at urban surfaces q_surface is initialized with 0.
5109            IF ( humidity )  THEN
5110               DO  m = 1, surf_usm_h%ns
5111                  surf_usm_h%q_surface(m) = 0.0_wp
5112               ENDDO
5113               DO  l = 0, 3
5114                  DO  m = 1, surf_usm_v(l)%ns
5115                     surf_usm_v(l)%q_surface(m) = 0.0_wp
5116                  ENDDO
5117               ENDDO
5118            ENDIF
5119!
5120!--         initial values for t_wall
5121!--         outer value is set to surface temperature
5122!--         inner value is set to wall_inner_temperature
5123!--         and profile is logaritmic (linear in nz).
5124!--         Horizontal surfaces
5125            DO  m = 1, surf_usm_h%ns
5126!
5127!--            Roof
5128               IF ( surf_usm_h%isroof_surf(m) )  THEN
5129                   tin = roof_inner_temperature
5130                   twin = window_inner_temperature
5131!
5132!--            Normal land surface
5133               ELSE
5134                   tin = soil_inner_temperature
5135                   twin = window_inner_temperature
5136               ENDIF
5137
5138               DO k = nzb_wall, nzt_wall+1
5139                   c = REAL( k - nzb_wall, wp ) /                              &
5140                       REAL( nzt_wall + 1 - nzb_wall , wp )
5141
5142                   t_wall_h(k,m) = ( 1.0_wp - c ) * t_surf_wall_h(m) + c * tin
5143                   t_window_h(k,m) = ( 1.0_wp - c ) * t_surf_window_h(m) + c * twin
5144                   t_green_h(k,m) = t_surf_wall_h(m)
5145                   swc_h(k,m) = 0.5_wp
5146                   swc_sat_h(k,m) = 0.95_wp
5147                   swc_res_h(k,m) = 0.05_wp
5148                   rootfr_h(k,m) = 0.1_wp
5149                   wilt_h(k,m) = 0.1_wp
5150                   fc_h(k,m) = 0.9_wp
5151               ENDDO
5152            ENDDO
5153!
5154!--         Vertical surfaces
5155            DO  l = 0, 3
5156               DO  m = 1, surf_usm_v(l)%ns
5157!
5158!--               Inner wall
5159                  tin = wall_inner_temperature
5160                  twin = window_inner_temperature
5161
5162                  DO k = nzb_wall, nzt_wall+1
5163                     c = REAL( k - nzb_wall, wp ) /                            &
5164                         REAL( nzt_wall + 1 - nzb_wall , wp )
5165                     t_wall_v(l)%t(k,m) = ( 1.0_wp - c ) * t_surf_wall_v(l)%t(m) + c * tin
5166                     t_window_v(l)%t(k,m) = ( 1.0_wp - c ) * t_surf_window_v(l)%t(m) + c * twin
5167                     t_green_v(l)%t(k,m) = t_surf_wall_v(l)%t(m)
5168                     swc_v(l)%t(k,m) = 0.5_wp
5169                  ENDDO
5170               ENDDO
5171            ENDDO
5172        ENDIF
5173
5174!
5175!--     If specified, replace constant wall temperatures with fully 3D values from file
5176        IF ( read_wall_temp_3d )  CALL usm_read_wall_temperature()
5177
5178!--
5179!--     Possibly DO user-defined actions (e.g. define heterogeneous wall surface)
5180        CALL user_init_urban_surface
5181
5182!
5183!--     initialize prognostic values for the first timestep
5184        t_surf_wall_h_p = t_surf_wall_h
5185        t_surf_wall_v_p = t_surf_wall_v
5186        t_surf_window_h_p = t_surf_window_h
5187        t_surf_window_v_p = t_surf_window_v
5188        t_surf_green_h_p = t_surf_green_h
5189        t_surf_green_v_p = t_surf_green_v
5190
5191        t_wall_h_p = t_wall_h
5192        t_wall_v_p = t_wall_v
5193        t_window_h_p = t_window_h
5194        t_window_v_p = t_window_v
5195        t_green_h_p = t_green_h
5196        t_green_v_p = t_green_v
5197
5198!
5199!--     Adjust radiative fluxes for urban surface at model start
5200        !CALL radiation_interaction
5201!--     TODO: interaction should be called once before first output,
5202!--     that is not yet possible.
5203       
5204        m_liq_usm_h_p     = m_liq_usm_h
5205        m_liq_usm_v_p     = m_liq_usm_v
5206!
5207!--    Set initial values for prognostic quantities
5208!--    Horizontal surfaces
5209       tm_liq_usm_h_m%var_usm_1d  = 0.0_wp
5210       surf_usm_h%c_liq = 0.0_wp
5211
5212       surf_usm_h%qsws_liq  = 0.0_wp
5213       surf_usm_h%qsws_veg  = 0.0_wp
5214
5215!
5216!--    Do the same for vertical surfaces
5217       DO  l = 0, 3
5218          tm_liq_usm_v_m(l)%var_usm_1d  = 0.0_wp
5219          surf_usm_v(l)%c_liq = 0.0_wp
5220
5221          surf_usm_v(l)%qsws_liq  = 0.0_wp
5222          surf_usm_v(l)%qsws_veg  = 0.0_wp
5223       ENDDO
5224
5225!
5226!--    Set initial values for prognostic soil quantities
5227       IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
5228          m_liq_usm_h%var_usm_1d  = 0.0_wp
5229
5230          DO  l = 0, 3
5231             m_liq_usm_v(l)%var_usm_1d  = 0.0_wp
5232          ENDDO
5233       ENDIF
5234
5235        CALL cpu_log( log_point_s(78), 'usm_init', 'stop' )
5236
5237        IF ( debug_output )  CALL debug_message( 'usm_init', 'end' )
5238
5239    END SUBROUTINE usm_init
5240
5241
5242!------------------------------------------------------------------------------!
5243! Description:
5244! ------------
5245!
5246!> Wall model as part of the urban surface model. The model predicts vertical
5247!> and horizontal wall / roof temperatures and window layer temperatures.
5248!> No window layer temperature calculactions during spinup to increase
5249!> possible timestep.
5250!------------------------------------------------------------------------------!
5251    SUBROUTINE usm_material_heat_model( spinup )
5252
5253
5254        IMPLICIT NONE
5255
5256        INTEGER(iwp) ::  i,j,k,l,kw, m                      !< running indices
5257
5258        REAL(wp), DIMENSION(nzb_wall:nzt_wall) :: wtend, wintend  !< tendency
5259        REAL(wp)     :: win_absorp  !< absorption coefficient from transmissivity
5260        REAL(wp), DIMENSION(nzb_wall:nzt_wall) :: wall_mod
5261
5262        LOGICAL      :: spinup  !< if true, no calculation of window temperatures
5263
5264
5265        IF ( debug_output )  THEN
5266           WRITE( debug_string, * ) 'usm_material_heat_model | spinup: ', spinup
5267           CALL debug_message( debug_string, 'start' )
5268        ENDIF
5269
5270        !$OMP PARALLEL PRIVATE (m, i, j, k, kw, wtend, wintend, win_absorp, wall_mod)
5271        wall_mod=1.0_wp
5272        IF (usm_wall_mod .AND. spinup) THEN
5273           DO  kw=nzb_wall,nzb_wall+1
5274               wall_mod(kw)=0.1_wp
5275           ENDDO
5276        ENDIF
5277
5278!
5279!--     For horizontal surfaces                                   
5280        !$OMP DO SCHEDULE (STATIC)
5281        DO  m = 1, surf_usm_h%ns
5282!
5283!--        Obtain indices
5284           i = surf_usm_h%i(m)           
5285           j = surf_usm_h%j(m)
5286           k = surf_usm_h%k(m)
5287!
5288!--        prognostic equation for ground/roof temperature t_wall_h
5289           wtend(:) = 0.0_wp
5290           wtend(nzb_wall) = (1.0_wp / surf_usm_h%rho_c_wall(nzb_wall,m)) *        &
5291                                       ( surf_usm_h%lambda_h(nzb_wall,m) * wall_mod(nzb_wall) *        &
5292                                         ( t_wall_h(nzb_wall+1,m)                  &
5293                                         - t_wall_h(nzb_wall,m) ) *                &
5294                                         surf_usm_h%ddz_wall(nzb_wall+1,m)         &
5295                                       + surf_usm_h%frac(ind_veg_wall,m)           &
5296                                         / (surf_usm_h%frac(ind_veg_wall,m)        &
5297                                           + surf_usm_h%frac(ind_pav_green,m) )    &
5298                                         * surf_usm_h%wghf_eb(m)                   &
5299                                       - surf_usm_h%frac(ind_pav_green,m)          &
5300                                          / (surf_usm_h%frac(ind_veg_wall,m)       &
5301                                            + surf_usm_h%frac(ind_pav_green,m) )   &
5302                                         * ( surf_usm_h%lambda_h_green(nzt_wall,m)* wall_mod(nzt_wall) &
5303                                           * surf_usm_h%ddz_green(nzt_wall,m)      &
5304                                           + surf_usm_h%lambda_h(nzb_wall,m) * wall_mod(nzb_wall)      &
5305                                           * surf_usm_h%ddz_wall(nzb_wall,m) )     &
5306                                         / ( surf_usm_h%ddz_green(nzt_wall,m)      &
5307                                           + surf_usm_h%ddz_wall(nzb_wall,m) )     &
5308                                         * ( t_wall_h(nzb_wall,m)                  &
5309                                           - t_green_h(nzt_wall,m) ) ) *           &
5310                                       surf_usm_h%ddz_wall_stag(nzb_wall,m)
5311!
5312!-- if indoor model ist used inner wall layer is calculated by using iwghf (indoor wall ground heat flux)
5313           IF ( indoor_model ) THEN
5314              DO  kw = nzb_wall+1, nzt_wall-1
5315                  wtend(kw) = (1.0_wp / surf_usm_h%rho_c_wall(kw,m))              &
5316                                 * (   surf_usm_h%lambda_h(kw,m) * wall_mod(kw)   &
5317                                    * ( t_wall_h(kw+1,m) - t_wall_h(kw,m) )       &
5318                                    * surf_usm_h%ddz_wall(kw+1,m)                 &
5319                                 - surf_usm_h%lambda_h(kw-1,m) * wall_mod(kw-1)   &
5320                                    * ( t_wall_h(kw,m) - t_wall_h(kw-1,m) )       &
5321                                    * surf_usm_h%ddz_wall(kw,m)                   &
5322                                   ) * surf_usm_h%ddz_wall_stag(kw,m)
5323              ENDDO
5324              wtend(nzt_wall) = (1.0_wp / surf_usm_h%rho_c_wall(nzt_wall,m)) *    &
5325                                         ( -surf_usm_h%lambda_h(nzt_wall-1,m) * wall_mod(nzt_wall-1) * &
5326                                           ( t_wall_h(nzt_wall,m)                 &
5327                                           - t_wall_h(nzt_wall-1,m) ) *           &
5328                                           surf_usm_h%ddz_wall(nzt_wall,m)        &
5329                                         + surf_usm_h%iwghf_eb(m) ) *             &
5330                                           surf_usm_h%ddz_wall_stag(nzt_wall,m)
5331           ELSE
5332              DO  kw = nzb_wall+1, nzt_wall
5333                  wtend(kw) = (1.0_wp / surf_usm_h%rho_c_wall(kw,m))              &
5334                                 * (   surf_usm_h%lambda_h(kw,m)  * wall_mod(kw)  &
5335                                    * ( t_wall_h(kw+1,m) - t_wall_h(kw,m) )       &
5336                                    * surf_usm_h%ddz_wall(kw+1,m)                 &
5337                                 - surf_usm_h%lambda_h(kw-1,m) * wall_mod(kw-1)   &
5338                                    * ( t_wall_h(kw,m) - t_wall_h(kw-1,m) )       &
5339                                    * surf_usm_h%ddz_wall(kw,m)                   &
5340                                   ) * surf_usm_h%ddz_wall_stag(kw,m)
5341              ENDDO
5342           ENDIF
5343
5344           t_wall_h_p(nzb_wall:nzt_wall,m) = t_wall_h(nzb_wall:nzt_wall,m)     &
5345                                 + dt_3d * ( tsc(2)                            &
5346                                 * wtend(nzb_wall:nzt_wall) + tsc(3)           &
5347                                 * surf_usm_h%tt_wall_m(nzb_wall:nzt_wall,m) )   
5348
5349!
5350!-- during spinup the tempeature inside window layers is not calculated to make larger timesteps possible
5351           IF ( .NOT. spinup) THEN
5352              win_absorp = -log(surf_usm_h%transmissivity(m)) / surf_usm_h%zw_window(nzt_wall,m)
5353!
5354!--           prognostic equation for ground/roof window temperature t_window_h
5355!--           takes absorption of shortwave radiation into account
5356              wintend(:) = 0.0_wp
5357              wintend(nzb_wall) = (1.0_wp / surf_usm_h%rho_c_window(nzb_wall,m)) *   &
5358                                         ( surf_usm_h%lambda_h_window(nzb_wall,m) *  &
5359                                           ( t_window_h(nzb_wall+1,m)                &
5360                                           - t_window_h(nzb_wall,m) ) *              &
5361                                           surf_usm_h%ddz_window(nzb_wall+1,m)       &
5362                                         + surf_usm_h%wghf_eb_window(m)              &
5363                                         + surf_usm_h%rad_sw_in(m)                   &
5364                                           * (1.0_wp - exp(-win_absorp               &
5365                                           * surf_usm_h%zw_window(nzb_wall,m) ) )    &
5366                                         ) * surf_usm_h%ddz_window_stag(nzb_wall,m)
5367   
5368              IF ( indoor_model ) THEN
5369                 DO  kw = nzb_wall+1, nzt_wall-1
5370                     wintend(kw) = (1.0_wp / surf_usm_h%rho_c_window(kw,m))          &
5371                                    * (   surf_usm_h%lambda_h_window(kw,m)           &
5372                                       * ( t_window_h(kw+1,m) - t_window_h(kw,m) )   &
5373                                       * surf_usm_h%ddz_window(kw+1,m)               &
5374                                    - surf_usm_h%lambda_h_window(kw-1,m)             &
5375                                       * ( t_window_h(kw,m) - t_window_h(kw-1,m) )   &
5376                                       * surf_usm_h%ddz_window(kw,m)                 &
5377                                    + surf_usm_h%rad_sw_in(m)                        &
5378                                       * (exp(-win_absorp                            &
5379                                           * surf_usm_h%zw_window(kw-1,m) )          &
5380                                           - exp(-win_absorp                         &
5381                                           * surf_usm_h%zw_window(kw,m) ) )          &
5382                                      ) * surf_usm_h%ddz_window_stag(kw,m)
5383   
5384                 ENDDO
5385                 wintend(nzt_wall) = (1.0_wp / surf_usm_h%rho_c_window(nzt_wall,m)) *       &
5386                                            ( -surf_usm_h%lambda_h_window(nzt_wall-1,m) *   &
5387                                              ( t_window_h(nzt_wall,m)                      &
5388                                              - t_window_h(nzt_wall-1,m) ) *                &
5389                                              surf_usm_h%ddz_window(nzt_wall,m)             &
5390                                            + surf_usm_h%iwghf_eb_window(m)                 &
5391                                            + surf_usm_h%rad_sw_in(m)                       &
5392                                              * (exp(-win_absorp                            &
5393                                              * surf_usm_h%zw_window(nzt_wall-1,m) )        &
5394                                              - exp(-win_absorp                             &
5395                                              * surf_usm_h%zw_window(nzt_wall,m) ) )        &
5396                                            ) * surf_usm_h%ddz_window_stag(nzt_wall,m)
5397              ELSE
5398                 DO  kw = nzb_wall+1, nzt_wall
5399                     wintend(kw) = (1.0_wp / surf_usm_h%rho_c_window(kw,m))          &
5400                                    * (   surf_usm_h%lambda_h_window(kw,m)           &
5401                                       * ( t_window_h(kw+1,m) - t_window_h(kw,m) )   &
5402                                       * surf_usm_h%ddz_window(kw+1,m)               &
5403                                    - surf_usm_h%lambda_h_window(kw-1,m)             &
5404                                       * ( t_window_h(kw,m) - t_window_h(kw-1,m) )   &
5405                                       * surf_usm_h%ddz_window(kw,m)                 &
5406                                    + surf_usm_h%rad_sw_in(m)                        &
5407                                       * (exp(-win_absorp                            &
5408                                           * surf_usm_h%zw_window(kw-1,m) )          &
5409                                           - exp(-win_absorp                         &
5410                                           * surf_usm_h%zw_window(kw,m) ) )          &
5411                                      ) * surf_usm_h%ddz_window_stag(kw,m)
5412   
5413                 ENDDO
5414              ENDIF
5415
5416              t_window_h_p(nzb_wall:nzt_wall,m) = t_window_h(nzb_wall:nzt_wall,m) &
5417                                 + dt_3d * ( tsc(2)                               &
5418                                 * wintend(nzb_wall:nzt_wall) + tsc(3)            &
5419                                 * surf_usm_h%tt_window_m(nzb_wall:nzt_wall,m) )   
5420
5421           ENDIF
5422
5423!
5424!--        calculate t_wall tendencies for the next Runge-Kutta step
5425           IF ( timestep_scheme(1:5) == 'runge' )  THEN
5426               IF ( intermediate_timestep_count == 1 )  THEN
5427                  DO  kw = nzb_wall, nzt_wall
5428                     surf_usm_h%tt_wall_m(kw,m) = wtend(kw)
5429                  ENDDO
5430               ELSEIF ( intermediate_timestep_count <                          &
5431                        intermediate_timestep_count_max )  THEN
5432                   DO  kw = nzb_wall, nzt_wall
5433                      surf_usm_h%tt_wall_m(kw,m) = -9.5625_wp * wtend(kw) +    &
5434                                         5.3125_wp * surf_usm_h%tt_wall_m(kw,m)
5435                   ENDDO
5436               ENDIF
5437           ENDIF
5438
5439           IF (.NOT. spinup) THEN
5440!
5441!--           calculate t_window tendencies for the next Runge-Kutta step
5442              IF ( timestep_scheme(1:5) == 'runge' )  THEN
5443                  IF ( intermediate_timestep_count == 1 )  THEN
5444                     DO  kw = nzb_wall, nzt_wall
5445                        surf_usm_h%tt_window_m(kw,m) = wintend(kw)
5446                     ENDDO
5447                  ELSEIF ( intermediate_timestep_count <                            &
5448                           intermediate_timestep_count_max )  THEN
5449                      DO  kw = nzb_wall, nzt_wall
5450                         surf_usm_h%tt_window_m(kw,m) = -9.5625_wp * wintend(kw) +  &
5451                                            5.3125_wp * surf_usm_h%tt_window_m(kw,m)
5452                      ENDDO
5453                  ENDIF
5454              ENDIF
5455           ENDIF
5456
5457        ENDDO
5458
5459!
5460!--     For vertical surfaces     
5461        !$OMP DO SCHEDULE (STATIC)
5462        DO  l = 0, 3                             
5463           DO  m = 1, surf_usm_v(l)%ns
5464!
5465!--           Obtain indices
5466              i = surf_usm_v(l)%i(m)           
5467              j = surf_usm_v(l)%j(m)
5468              k = surf_usm_v(l)%k(m)
5469!
5470!--           prognostic equation for wall temperature t_wall_v
5471              wtend(:) = 0.0_wp
5472
5473              wtend(nzb_wall) = (1.0_wp / surf_usm_v(l)%rho_c_wall(nzb_wall,m)) *    &
5474                                      ( surf_usm_v(l)%lambda_h(nzb_wall,m) * wall_mod(nzb_wall)  *      &
5475                                        ( t_wall_v(l)%t(nzb_wall+1,m)                &
5476                                        - t_wall_v(l)%t(nzb_wall,m) ) *              &
5477                                        surf_usm_v(l)%ddz_wall(nzb_wall+1,m)         &
5478                                      + surf_usm_v(l)%frac(ind_veg_wall,m)           &
5479                                        / (surf_usm_v(l)%frac(ind_veg_wall,m)        &
5480                                          + surf_usm_v(l)%frac(ind_pav_green,m) )    &
5481                                        * surf_usm_v(l)%wghf_eb(m)                   &
5482                                      - surf_usm_v(l)%frac(ind_pav_green,m)          &
5483                                        / (surf_usm_v(l)%frac(ind_veg_wall,m)        &
5484                                          + surf_usm_v(l)%frac(ind_pav_green,m) )    &
5485                                        * ( surf_usm_v(l)%lambda_h_green(nzt_wall,m)* wall_mod(nzt_wall) &
5486                                          * surf_usm_v(l)%ddz_green(nzt_wall,m)      &
5487                                          + surf_usm_v(l)%lambda_h(nzb_wall,m)* wall_mod(nzb_wall)       &
5488                                          * surf_usm_v(l)%ddz_wall(nzb_wall,m) )     &
5489                                        / ( surf_usm_v(l)%ddz_green(nzt_wall,m)      &
5490                                          + surf_usm_v(l)%ddz_wall(nzb_wall,m) )     &
5491                                        * ( t_wall_v(l)%t(nzb_wall,m)                &
5492                                          - t_green_v(l)%t(nzt_wall,m) ) ) *         &
5493                                        surf_usm_v(l)%ddz_wall_stag(nzb_wall,m)
5494
5495              IF ( indoor_model ) THEN
5496                 DO  kw = nzb_wall+1, nzt_wall-1
5497                     wtend(kw) = (1.0_wp / surf_usm_v(l)%rho_c_wall(kw,m))        &
5498                              * (   surf_usm_v(l)%lambda_h(kw,m)  * wall_mod(kw)  &
5499                                 * ( t_wall_v(l)%t(kw+1,m) - t_wall_v(l)%t(kw,m) )&
5500                                 * surf_usm_v(l)%ddz_wall(kw+1,m)                 &
5501                              - surf_usm_v(l)%lambda_h(kw-1,m)  * wall_mod(kw-1)  &
5502                                 * ( t_wall_v(l)%t(kw,m) - t_wall_v(l)%t(kw-1,m) )&
5503                                 * surf_usm_v(l)%ddz_wall(kw,m)                   &
5504                                 ) * surf_usm_v(l)%ddz_wall_stag(kw,m)
5505                 ENDDO
5506                 wtend(nzt_wall) = (1.0_wp / surf_usm_v(l)%rho_c_wall(nzt_wall,m)) * &
5507                                         ( -surf_usm_v(l)%lambda_h(nzt_wall-1,m) * wall_mod(nzt_wall-1)*    &
5508                                           ( t_wall_v(l)%t(nzt_wall,m)               &
5509                                           - t_wall_v(l)%t(nzt_wall-1,m) ) *         &
5510                                           surf_usm_v(l)%ddz_wall(nzt_wall,m)        &
5511                                         + surf_usm_v(l)%iwghf_eb(m) ) *             &
5512                                           surf_usm_v(l)%ddz_wall_stag(nzt_wall,m)
5513              ELSE
5514                 DO  kw = nzb_wall+1, nzt_wall
5515                     wtend(kw) = (1.0_wp / surf_usm_v(l)%rho_c_wall(kw,m))        &
5516                              * (   surf_usm_v(l)%lambda_h(kw,m) * wall_mod(kw)   &
5517                                 * ( t_wall_v(l)%t(kw+1,m) - t_wall_v(l)%t(kw,m) )&
5518                                 * surf_usm_v(l)%ddz_wall(kw+1,m)                 &
5519                              - surf_usm_v(l)%lambda_h(kw-1,m)  * wall_mod(kw-1)  &
5520                                 * ( t_wall_v(l)%t(kw,m) - t_wall_v(l)%t(kw-1,m) )&
5521                                 * surf_usm_v(l)%ddz_wall(kw,m)                   &
5522                                 ) * surf_usm_v(l)%ddz_wall_stag(kw,m)
5523                 ENDDO
5524              ENDIF
5525
5526              t_wall_v_p(l)%t(nzb_wall:nzt_wall,m) =                           &
5527                                   t_wall_v(l)%t(nzb_wall:nzt_wall,m)          &
5528                                 + dt_3d * ( tsc(2)                            &
5529                                 * wtend(nzb_wall:nzt_wall) + tsc(3)           &
5530                                 * surf_usm_v(l)%tt_wall_m(nzb_wall:nzt_wall,m) )   
5531
5532              IF (.NOT. spinup) THEN
5533                 win_absorp = -log(surf_usm_v(l)%transmissivity(m)) / surf_usm_v(l)%zw_window(nzt_wall,m)
5534!
5535!--              prognostic equation for window temperature t_window_v
5536                 wintend(:) = 0.0_wp
5537                 wintend(nzb_wall) = (1.0_wp / surf_usm_v(l)%rho_c_window(nzb_wall,m)) * &
5538                                         ( surf_usm_v(l)%lambda_h_window(nzb_wall,m) *   &
5539                                           ( t_window_v(l)%t(nzb_wall+1,m)               &
5540                                           - t_window_v(l)%t(nzb_wall,m) ) *             &
5541                                           surf_usm_v(l)%ddz_window(nzb_wall+1,m)        &
5542                                         + surf_usm_v(l)%wghf_eb_window(m)               &
5543                                         + surf_usm_v(l)%rad_sw_in(m)                    &
5544                                           * (1.0_wp - exp(-win_absorp                   &
5545                                           * surf_usm_v(l)%zw_window(nzb_wall,m) ) )     &
5546                                         ) * surf_usm_v(l)%ddz_window_stag(nzb_wall,m)
5547   
5548                 IF ( indoor_model ) THEN
5549                    DO  kw = nzb_wall+1, nzt_wall -1
5550                        wintend(kw) = (1.0_wp / surf_usm_v(l)%rho_c_window(kw,m))         &
5551                                 * (   surf_usm_v(l)%lambda_h_window(kw,m)                &
5552                                    * ( t_window_v(l)%t(kw+1,m) - t_window_v(l)%t(kw,m) ) &
5553                                    * surf_usm_v(l)%ddz_window(kw+1,m)                    &
5554                                 - surf_usm_v(l)%lambda_h_window(kw-1,m)                  &
5555                                    * ( t_window_v(l)%t(kw,m) - t_window_v(l)%t(kw-1,m) ) &
5556                                    * surf_usm_v(l)%ddz_window(kw,m)                      &
5557                                 + surf_usm_v(l)%rad_sw_in(m)                             &
5558                                    * (exp(-win_absorp                                    &
5559                                       * surf_usm_v(l)%zw_window(kw-1,m)       )          &
5560                                           - exp(-win_absorp                              &
5561                                           * surf_usm_v(l)%zw_window(kw,m) ) )            &
5562                                    ) * surf_usm_v(l)%ddz_window_stag(kw,m)
5563                     ENDDO
5564                     wintend(nzt_wall) = (1.0_wp / surf_usm_v(l)%rho_c_window(nzt_wall,m)) *  &
5565                                             ( -surf_usm_v(l)%lambda_h_window(nzt_wall-1,m) * &
5566                                               ( t_window_v(l)%t(nzt_wall,m)                  &
5567                                               - t_window_v(l)%t(nzt_wall-1,m) ) *            &
5568                                               surf_usm_v(l)%ddz_window(nzt_wall,m)           &
5569                                             + surf_usm_v(l)%iwghf_eb_window(m)               &
5570                                             + surf_usm_v(l)%rad_sw_in(m)                     &
5571                                               * (exp(-win_absorp                             &
5572                                             * surf_usm_v(l)%zw_window(nzt_wall-1,m) )        &
5573                                           - exp(-win_absorp                                  &
5574                                               * surf_usm_v(l)%zw_window(nzt_wall,m) ) )      &
5575                                             ) * surf_usm_v(l)%ddz_window_stag(nzt_wall,m)
5576                 ELSE
5577                    DO  kw = nzb_wall+1, nzt_wall
5578                        wintend(kw) = (1.0_wp / surf_usm_v(l)%rho_c_window(kw,m))         &
5579                                 * (   surf_usm_v(l)%lambda_h_window(kw,m)                &
5580                                    * ( t_window_v(l)%t(kw+1,m) - t_window_v(l)%t(kw,m) ) &
5581                                    * surf_usm_v(l)%ddz_window(kw+1,m)                    &
5582                                 - surf_usm_v(l)%lambda_h_window(kw-1,m)                  &
5583                                    * ( t_window_v(l)%t(kw,m) - t_window_v(l)%t(kw-1,m) ) &
5584                                    * surf_usm_v(l)%ddz_window(kw,m)                      &
5585                                 + surf_usm_v(l)%rad_sw_in(m)                             &
5586                                    * (exp(-win_absorp                                    &
5587                                       * surf_usm_v(l)%zw_window(kw-1,m)       )          &
5588                                           - exp(-win_absorp                              &
5589                                           * surf_usm_v(l)%zw_window(kw,m) ) )            &
5590                                    ) * surf_usm_v(l)%ddz_window_stag(kw,m)
5591                    ENDDO
5592                 ENDIF
5593   
5594                 t_window_v_p(l)%t(nzb_wall:nzt_wall,m) =                           &
5595                                      t_window_v(l)%t(nzb_wall:nzt_wall,m)          &
5596                                    + dt_3d * ( tsc(2)                              &
5597                                    * wintend(nzb_wall:nzt_wall) + tsc(3)           &
5598                                    * surf_usm_v(l)%tt_window_m(nzb_wall:nzt_wall,m) )   
5599              ENDIF
5600
5601!
5602!--           calculate t_wall tendencies for the next Runge-Kutta step
5603              IF ( timestep_scheme(1:5) == 'runge' )  THEN
5604                  IF ( intermediate_timestep_count == 1 )  THEN
5605                     DO  kw = nzb_wall, nzt_wall
5606                        surf_usm_v(l)%tt_wall_m(kw,m) = wtend(kw)
5607                     ENDDO
5608                  ELSEIF ( intermediate_timestep_count <                       &
5609                           intermediate_timestep_count_max )  THEN
5610                      DO  kw = nzb_wall, nzt_wall
5611                         surf_usm_v(l)%tt_wall_m(kw,m) =                       &
5612                                     - 9.5625_wp * wtend(kw) +                 &
5613                                       5.3125_wp * surf_usm_v(l)%tt_wall_m(kw,m)
5614                      ENDDO
5615                  ENDIF
5616              ENDIF
5617
5618
5619              IF (.NOT. spinup) THEN
5620!
5621!--              calculate t_window tendencies for the next Runge-Kutta step
5622                 IF ( timestep_scheme(1:5) == 'runge' )  THEN
5623                     IF ( intermediate_timestep_count == 1 )  THEN
5624                        DO  kw = nzb_wall, nzt_wall
5625                           surf_usm_v(l)%tt_window_m(kw,m) = wintend(kw)
5626                        ENDDO
5627                     ELSEIF ( intermediate_timestep_count <                       &
5628                              intermediate_timestep_count_max )  THEN
5629                         DO  kw = nzb_wall, nzt_wall
5630                            surf_usm_v(l)%tt_window_m(kw,m) =                     &
5631                                        - 9.5625_wp * wintend(kw) +               &
5632                                          5.3125_wp * surf_usm_v(l)%tt_window_m(kw,m)
5633                         ENDDO
5634                     ENDIF
5635                 ENDIF
5636              ENDIF
5637
5638           ENDDO
5639        ENDDO
5640        !$OMP END PARALLEL
5641
5642        IF ( debug_output )  THEN
5643           WRITE( debug_string, * ) 'usm_material_heat_model | spinup: ', spinup
5644           CALL debug_message( debug_string, 'end' )
5645        ENDIF
5646
5647    END SUBROUTINE usm_material_heat_model
5648
5649!------------------------------------------------------------------------------!
5650! Description:
5651! ------------
5652!
5653!> Green and substrate model as part of the urban surface model. The model predicts ground
5654!> temperatures.
5655!>
5656!> Important: gree-heat model crashes due to unknown reason. Green fraction
5657!> is thus set to zero (in favor of wall fraction).
5658!------------------------------------------------------------------------------!
5659    SUBROUTINE usm_green_heat_model
5660
5661
5662        IMPLICIT NONE
5663
5664        INTEGER(iwp) ::  i,j,k,l,kw, m              !< running indices
5665
5666        REAL(wp)     :: ke, lambda_h_green_sat      !< heat conductivity for saturated soil
5667        REAL(wp)     :: h_vg                        !< Van Genuchten coef. h
5668        REAL(wp)     :: drho_l_lv                   !< frequently used parameter
5669
5670        REAL(wp), DIMENSION(nzb_wall:nzt_wall) :: gtend,tend  !< tendency
5671
5672        REAL(wp), DIMENSION(nzb_wall:nzt_wall) :: root_extr_green
5673
5674        REAL(wp), DIMENSION(nzb_wall:nzt_wall+1) :: lambda_green_temp  !< temp. lambda
5675        REAL(wp), DIMENSION(nzb_wall:nzt_wall+1) :: gamma_green_temp   !< temp. gamma
5676
5677        LOGICAL :: conserve_water_content = .true.
5678
5679
5680        IF ( debug_output )  CALL debug_message( 'usm_green_heat_model', 'start' )
5681
5682        drho_l_lv = 1.0_wp / (rho_l * l_v)
5683
5684!
5685!--     For horizontal surfaces                                   
5686        !$OMP PARALLEL PRIVATE (m, i, j, k, kw, lambda_h_green_sat, ke, lambda_green_temp, gtend,  &
5687        !$OMP&                  tend, h_vg, gamma_green_temp, m_total, root_extr_green)
5688        !$OMP DO SCHEDULE (STATIC)
5689        DO  m = 1, surf_usm_h%ns
5690           IF (surf_usm_h%frac(ind_pav_green,m) > 0.0_wp) THEN
5691!
5692!--           Obtain indices
5693              i = surf_usm_h%i(m)           
5694              j = surf_usm_h%j(m)
5695              k = surf_usm_h%k(m)
5696   
5697              DO  kw = nzb_wall, nzt_wall
5698!
5699!--              Calculate volumetric heat capacity of the soil, taking
5700!--              into account water content
5701                 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)) &
5702                                      + rho_c_water * swc_h(kw,m))
5703     
5704!
5705!--              Calculate soil heat conductivity at the center of the soil
5706!--              layers
5707                 lambda_h_green_sat = lambda_h_green_sm ** (1.0_wp - swc_sat_h(kw,m)) *    &
5708                                lambda_h_water ** swc_h(kw,m)
5709     
5710                 ke = 1.0_wp + LOG10(MAX(0.1_wp,swc_h(kw,m)             &
5711                      / swc_sat_h(kw,m)))
5712     
5713                 lambda_green_temp(kw) = ke * (lambda_h_green_sat - lambda_h_green_dry) +    &
5714                                  lambda_h_green_dry
5715   
5716              ENDDO
5717              lambda_green_temp(nzt_wall+1) = lambda_green_temp(nzt_wall)
5718   
5719   
5720!
5721!--           Calculate soil heat conductivity (lambda_h) at the _stag level
5722!--           using linear interpolation. For pavement surface, the
5723!--           true pavement depth is considered
5724              DO  kw = nzb_wall, nzt_wall
5725                surf_usm_h%lambda_h_green(kw,m) = ( lambda_green_temp(kw+1) + lambda_green_temp(kw) )  &
5726                                      * 0.5_wp
5727              ENDDO
5728
5729              t_green_h(nzt_wall+1,m) = t_wall_h(nzb_wall,m)
5730!
5731!--        prognostic equation for ground/roof temperature t_green_h
5732              gtend(:) = 0.0_wp
5733              gtend(nzb_wall) = (1.0_wp / surf_usm_h%rho_c_total_green(nzb_wall,m)) *    &
5734                                         ( surf_usm_h%lambda_h_green(nzb_wall,m) * &
5735                                           ( t_green_h(nzb_wall+1,m)               &
5736                                           - t_green_h(nzb_wall,m) ) *             &
5737                                           surf_usm_h%ddz_green(nzb_wall+1,m)      &
5738                                         + surf_usm_h%wghf_eb_green(m) ) *         &
5739                                           surf_usm_h%ddz_green_stag(nzb_wall,m)
5740             
5741               DO  kw = nzb_wall+1, nzt_wall
5742                   gtend(kw) = (1.0_wp / surf_usm_h%rho_c_total_green(kw,m))       &
5743                                  * (   surf_usm_h%lambda_h_green(kw,m)            &
5744                                     * ( t_green_h(kw+1,m) - t_green_h(kw,m) )     &
5745                                     * surf_usm_h%ddz_green(kw+1,m)                &
5746                                  - surf_usm_h%lambda_h_green(kw-1,m)              &
5747                                     * ( t_green_h(kw,m) - t_green_h(kw-1,m) )     &
5748                                     * surf_usm_h%ddz_green(kw,m)                  &
5749                                    ) * surf_usm_h%ddz_green_stag(kw,m)
5750               ENDDO
5751   
5752              t_green_h_p(nzb_wall:nzt_wall,m) = t_green_h(nzb_wall:nzt_wall,m)    &
5753                                    + dt_3d * ( tsc(2)                             &
5754                                    * gtend(nzb_wall:nzt_wall) + tsc(3)            &
5755                                    * surf_usm_h%tt_green_m(nzb_wall:nzt_wall,m) )   
5756   
5757             
5758!
5759!--        calculate t_green tendencies for the next Runge-Kutta step
5760              IF ( timestep_scheme(1:5) == 'runge' )  THEN
5761                  IF ( intermediate_timestep_count == 1 )  THEN
5762                     DO  kw = nzb_wall, nzt_wall
5763                        surf_usm_h%tt_green_m(kw,m) = gtend(kw)
5764                     ENDDO
5765                  ELSEIF ( intermediate_timestep_count <                           &
5766                           intermediate_timestep_count_max )  THEN
5767                      DO  kw = nzb_wall, nzt_wall
5768                         surf_usm_h%tt_green_m(kw,m) = -9.5625_wp * gtend(kw) +    &
5769                                            5.3125_wp * surf_usm_h%tt_green_m(kw,m)
5770                      ENDDO
5771                  ENDIF
5772              ENDIF
5773
5774              DO  kw = nzb_wall, nzt_wall
5775
5776!
5777!--              Calculate soil diffusivity at the center of the soil layers
5778                 lambda_green_temp(kw) = (- b_ch * surf_usm_h%gamma_w_green_sat(kw,m) * psi_sat       &
5779                                   / swc_sat_h(kw,m) ) * ( MAX( swc_h(kw,m),    &
5780                                   wilt_h(kw,m) ) / swc_sat_h(kw,m) )**(        &
5781                                   b_ch + 2.0_wp )
5782
5783!
5784!--              Parametrization of Van Genuchten
5785                 IF ( soil_type /= 7 )  THEN
5786!
5787!--                 Calculate the hydraulic conductivity after Van Genuchten
5788!--                 (1980)
5789                    h_vg = ( ( (swc_res_h(kw,m) - swc_sat_h(kw,m)) / ( swc_res_h(kw,m) -    &
5790                               MAX( swc_h(kw,m), wilt_h(kw,m) ) ) )**(      &
5791                               surf_usm_h%n_vg_green(m) / (surf_usm_h%n_vg_green(m) - 1.0_wp ) ) - 1.0_wp  &
5792                           )**( 1.0_wp / surf_usm_h%n_vg_green(m) ) / surf_usm_h%alpha_vg_green(m)
5793
5794
5795                    gamma_green_temp(kw) = surf_usm_h%gamma_w_green_sat(kw,m) * ( ( (1.0_wp +         &
5796                                    ( surf_usm_h%alpha_vg_green(m) * h_vg )**surf_usm_h%n_vg_green(m))**(  &
5797                                    1.0_wp - 1.0_wp / surf_usm_h%n_vg_green(m) ) - (        &
5798                                    surf_usm_h%alpha_vg_green(m) * h_vg )**( surf_usm_h%n_vg_green(m)      &
5799                                    - 1.0_wp) )**2 )                         &
5800                                    / ( ( 1.0_wp + ( surf_usm_h%alpha_vg_green(m) * h_vg    &
5801                                    )**surf_usm_h%n_vg_green(m) )**( ( 1.0_wp  - 1.0_wp     &
5802                                    / surf_usm_h%n_vg_green(m) ) *( surf_usm_h%l_vg_green(m) + 2.0_wp) ) )
5803
5804!
5805!--              Parametrization of Clapp & Hornberger
5806                 ELSE
5807                    gamma_green_temp(kw) = surf_usm_h%gamma_w_green_sat(kw,m) * ( swc_h(kw,m)       &
5808                                    / swc_sat_h(kw,m) )**(2.0_wp * b_ch + 3.0_wp)
5809                 ENDIF
5810
5811              ENDDO
5812
5813!
5814!--           Prognostic equation for soil moisture content. Only performed,
5815!--           when humidity is enabled in the atmosphere
5816              IF ( humidity )  THEN
5817!
5818!--              Calculate soil diffusivity (lambda_w) at the _stag level
5819!--              using linear interpolation. To do: replace this with
5820!--              ECMWF-IFS Eq. 8.81
5821                 DO  kw = nzb_wall, nzt_wall-1
5822                   
5823                    surf_usm_h%lambda_w_green(kw,m) = ( lambda_green_temp(kw+1) + lambda_green_temp(kw) )  &
5824                                      * 0.5_wp
5825                    surf_usm_h%gamma_w_green(kw,m)  = ( gamma_green_temp(kw+1) + gamma_green_temp(kw) )    &
5826                                      * 0.5_wp
5827
5828                 ENDDO
5829
5830!
5831!--              In case of a closed bottom (= water content is conserved),
5832!--              set hydraulic conductivity to zero to that no water will be
5833!--              lost in the bottom layer.
5834                 IF ( conserve_water_content )  THEN
5835                    surf_usm_h%gamma_w_green(kw,m) = 0.0_wp
5836                 ELSE
5837                    surf_usm_h%gamma_w_green(kw,m) = gamma_green_temp(nzt_wall)
5838                 ENDIF     
5839
5840!--              The root extraction (= root_extr * qsws_veg / (rho_l     
5841!--              * l_v)) ensures the mass conservation for water. The         
5842!--              transpiration of plants equals the cumulative withdrawals by
5843!--              the roots in the soil. The scheme takes into account the
5844!--              availability of water in the soil layers as well as the root
5845!--              fraction in the respective layer. Layer with moisture below
5846!--              wilting point will not contribute, which reflects the
5847!--              preference of plants to take water from moister layers.
5848
5849!
5850!--              Calculate the root extraction (ECMWF 7.69, the sum of
5851!--              root_extr = 1). The energy balance solver guarantees a
5852!--              positive transpiration, so that there is no need for an
5853!--              additional check.
5854                 m_total = 0.0_wp
5855                 DO  kw = nzb_wall, nzt_wall
5856                     IF ( swc_h(kw,m) > wilt_h(kw,m) )  THEN
5857                        m_total = m_total + rootfr_h(kw,m) * swc_h(kw,m)
5858                     ENDIF
5859                 ENDDO 
5860
5861                 IF ( m_total > 0.0_wp )  THEN
5862                    DO  kw = nzb_wall, nzt_wall
5863                       IF ( swc_h(kw,m) > wilt_h(kw,m) )  THEN
5864                          root_extr_green(kw) = rootfr_h(kw,m) * swc_h(kw,m)      &
5865                                                          / m_total
5866                       ELSE
5867                          root_extr_green(kw) = 0.0_wp
5868                       ENDIF
5869                    ENDDO
5870                 ENDIF
5871
5872!
5873!--              Prognostic equation for soil water content m_soil.
5874                 tend(:) = 0.0_wp
5875
5876                 tend(nzb_wall) = ( surf_usm_h%lambda_w_green(nzb_wall,m) * (            &
5877                          swc_h(nzb_wall+1,m) - swc_h(nzb_wall,m) )    &
5878                          * surf_usm_h%ddz_green(nzb_wall+1,m) - surf_usm_h%gamma_w_green(nzb_wall,m) - ( &
5879                             root_extr_green(nzb_wall) * surf_usm_h%qsws_veg(m)          &
5880!                                + surf_usm_h%qsws_soil_green(m)
5881                                ) * drho_l_lv )             &
5882                               * surf_usm_h%ddz_green_stag(nzb_wall,m)
5883
5884                 DO  kw = nzb_wall+1, nzt_wall-1
5885                    tend(kw) = ( surf_usm_h%lambda_w_green(kw,m) * ( swc_h(kw+1,m)        &
5886                              - swc_h(kw,m) ) * surf_usm_h%ddz_green(kw+1,m)              &
5887                              - surf_usm_h%gamma_w_green(kw,m)                            &
5888                              - surf_usm_h%lambda_w_green(kw-1,m) * (swc_h(kw,m) -        &
5889                              swc_h(kw-1,m)) * surf_usm_h%ddz_green(kw,m)                 &
5890                              + surf_usm_h%gamma_w_green(kw-1,m) - (root_extr_green(kw)   &
5891                              * surf_usm_h%qsws_veg(m) * drho_l_lv)                       &
5892                              ) * surf_usm_h%ddz_green_stag(kw,m)
5893
5894                 ENDDO
5895                 tend(nzt_wall) = ( - surf_usm_h%gamma_w_green(nzt_wall,m)                  &
5896                                         - surf_usm_h%lambda_w_green(nzt_wall-1,m)          &
5897                                         * (swc_h(nzt_wall,m)             &
5898                                         - swc_h(nzt_wall-1,m))           &
5899                                         * surf_usm_h%ddz_green(nzt_wall,m)                 &
5900                                         + surf_usm_h%gamma_w_green(nzt_wall-1,m) - (       &
5901                                           root_extr_green(nzt_wall)               &
5902                                         * surf_usm_h%qsws_veg(m) * drho_l_lv  )   &
5903                                   ) * surf_usm_h%ddz_green_stag(nzt_wall,m)             
5904
5905                 swc_h_p(nzb_wall:nzt_wall,m) = swc_h(nzb_wall:nzt_wall,m)&
5906                                                 + dt_3d * ( tsc(2) * tend(:)   &
5907                                                 + tsc(3) * surf_usm_h%tswc_h_m(:,m) )   
5908 
5909!
5910!--              Account for dry soils (find a better solution here!)
5911                 DO  kw = nzb_wall, nzt_wall
5912                    IF ( swc_h_p(kw,m) < 0.0_wp )  swc_h_p(kw,m) = 0.0_wp
5913                 ENDDO
5914
5915!
5916!--              Calculate m_soil tendencies for the next Runge-Kutta step
5917                 IF ( timestep_scheme(1:5) == 'runge' )  THEN
5918                    IF ( intermediate_timestep_count == 1 )  THEN
5919                       DO  kw = nzb_wall, nzt_wall
5920                          surf_usm_h%tswc_h_m(kw,m) = tend(kw)
5921                       ENDDO
5922                    ELSEIF ( intermediate_timestep_count <                   &
5923                             intermediate_timestep_count_max )  THEN
5924                       DO  kw = nzb_wall, nzt_wall
5925                          surf_usm_h%tswc_h_m(kw,m) = -9.5625_wp * tend(kw) + 5.3125_wp&
5926                                   * surf_usm_h%tswc_h_m(kw,m)
5927                       ENDDO
5928                    ENDIF
5929                 ENDIF
5930              ENDIF
5931
5932           ENDIF
5933           
5934        ENDDO
5935        !$OMP END PARALLEL
5936
5937!
5938!--     For vertical surfaces     
5939        DO  l = 0, 3                             
5940           DO  m = 1, surf_usm_v(l)%ns
5941
5942              IF (surf_usm_v(l)%frac(ind_pav_green,m) > 0.0_wp) THEN
5943!
5944!-- no substrate layer for green walls / only groundbase green walls (ivy i.e.) -> green layers get same
5945!-- temperature as first wall layer
5946!-- there fore no temperature calculations for vertical green substrate layers now
5947
5948!
5949! !
5950! !--              Obtain indices
5951!                  i = surf_usm_v(l)%i(m)           
5952!                  j = surf_usm_v(l)%j(m)
5953!                  k = surf_usm_v(l)%k(m)
5954!   
5955!                  t_green_v(l)%t(nzt_wall+1,m) = t_wall_v(l)%t(nzb_wall,m)
5956! !
5957! !--              prognostic equation for green temperature t_green_v
5958!                  gtend(:) = 0.0_wp
5959!                  gtend(nzb_wall) = (1.0_wp / surf_usm_v(l)%rho_c_green(nzb_wall,m)) * &
5960!                                          ( surf_usm_v(l)%lambda_h_green(nzb_wall,m) * &
5961!                                            ( t_green_v(l)%t(nzb_wall+1,m)             &
5962!                                            - t_green_v(l)%t(nzb_wall,m) ) *           &
5963!                                            surf_usm_v(l)%ddz_green(nzb_wall+1,m)      &
5964!                                          + surf_usm_v(l)%wghf_eb(m) ) *               &
5965!                                            surf_usm_v(l)%ddz_green_stag(nzb_wall,m)
5966!               
5967!                  DO  kw = nzb_wall+1, nzt_wall
5968!                     gtend(kw) = (1.0_wp / surf_usm_v(l)%rho_c_green(kw,m))          &
5969!                               * (   surf_usm_v(l)%lambda_h_green(kw,m)              &
5970!                                 * ( t_green_v(l)%t(kw+1,m) - t_green_v(l)%t(kw,m) ) &
5971!                                 * surf_usm_v(l)%ddz_green(kw+1,m)                   &
5972!                               - surf_usm_v(l)%lambda_h(kw-1,m)                      &
5973!                                 * ( t_green_v(l)%t(kw,m) - t_green_v(l)%t(kw-1,m) ) &
5974!                                 * surf_usm_v(l)%ddz_green(kw,m) )                   &
5975!                               * surf_usm_v(l)%ddz_green_stag(kw,m)
5976!                  ENDDO
5977!   
5978!                  t_green_v_p(l)%t(nzb_wall:nzt_wall,m) =                              &
5979!                                       t_green_v(l)%t(nzb_wall:nzt_wall,m)             &
5980!                                     + dt_3d * ( tsc(2)                                &
5981!                                     * gtend(nzb_wall:nzt_wall) + tsc(3)               &
5982!                                     * surf_usm_v(l)%tt_green_m(nzb_wall:nzt_wall,m) )   
5983!   
5984! !
5985! !--              calculate t_green tendencies for the next Runge-Kutta step
5986!                  IF ( timestep_scheme(1:5) == 'runge' )  THEN
5987!                      IF ( intermediate_timestep_count == 1 )  THEN
5988!                         DO  kw = nzb_wall, nzt_wall
5989!                            surf_usm_v(l)%tt_green_m(kw,m) = gtend(kw)
5990!                         ENDDO
5991!                      ELSEIF ( intermediate_timestep_count <                           &
5992!                               intermediate_timestep_count_max )  THEN
5993!                          DO  kw = nzb_wall, nzt_wall
5994!                             surf_usm_v(l)%tt_green_m(kw,m) =                          &
5995!                                         - 9.5625_wp * gtend(kw) +                     &
5996!                                           5.3125_wp * surf_usm_v(l)%tt_green_m(kw,m)
5997!                          ENDDO
5998!                      ENDIF
5999!                  ENDIF
6000
6001                 DO  kw = nzb_wall, nzt_wall+1
6002                     t_green_v(l)%t(kw,m) = t_wall_v(l)%t(nzb_wall,m)
6003                 ENDDO
6004             
6005              ENDIF
6006
6007           ENDDO
6008        ENDDO
6009
6010        IF ( debug_output )  CALL debug_message( 'usm_green_heat_model', 'end' )
6011
6012    END SUBROUTINE usm_green_heat_model
6013
6014!------------------------------------------------------------------------------!
6015! Description:
6016! ------------
6017!> Parin for &usm_par for urban surface model
6018!------------------------------------------------------------------------------!
6019    SUBROUTINE usm_parin
6020
6021       IMPLICIT NONE
6022
6023       CHARACTER (LEN=80) ::  line  !< string containing current line of file PARIN
6024
6025       NAMELIST /urban_surface_par/                                            &
6026                           building_type,                                      &
6027                           land_category,                                      &
6028                           naheatlayers,                                       &
6029                           pedestrian_category,                                &
6030                           roughness_concrete,                                 &
6031                           read_wall_temp_3d,                                  &
6032                           roof_category,                                      &
6033                           urban_surface,                                      &
6034                           usm_anthropogenic_heat,                             &
6035                           usm_material_model,                                 &
6036                           wall_category,                                      &
6037                           wall_inner_temperature,                             &
6038                           roof_inner_temperature,                             &
6039                           soil_inner_temperature,                             &
6040                           window_inner_temperature,                           &
6041                           usm_wall_mod
6042
6043       NAMELIST /urban_surface_parameters/                                     &
6044                           building_type,                                      &
6045                           land_category,                                      &
6046                           naheatlayers,                                       &
6047                           pedestrian_category,                                &
6048                           roughness_concrete,                                 &
6049                           read_wall_temp_3d,                                  &
6050                           roof_category,                                      &
6051                           urban_surface,                                      &
6052                           usm_anthropogenic_heat,                             &
6053                           usm_material_model,                                 &
6054                           wall_category,                                      &
6055                           wall_inner_temperature,                             &
6056                           roof_inner_temperature,                             &
6057                           soil_inner_temperature,                             &
6058                           window_inner_temperature,                           &
6059                           usm_wall_mod
6060                           
6061 
6062!
6063!--    Try to find urban surface model package
6064       REWIND ( 11 )
6065       line = ' '
6066       DO WHILE ( INDEX( line, '&urban_surface_parameters' ) == 0 )
6067          READ ( 11, '(A)', END=12 )  line
6068       ENDDO
6069       BACKSPACE ( 11 )
6070
6071!
6072!--    Read user-defined namelist
6073       READ ( 11, urban_surface_parameters, ERR = 10 )
6074
6075!
6076!--    Set flag that indicates that the urban surface model is switched on
6077       urban_surface = .TRUE.
6078
6079       GOTO 14
6080
6081 10    BACKSPACE( 11 )
6082       READ( 11 , '(A)') line
6083       CALL parin_fail_message( 'urban_surface_parameters', line )
6084!
6085!--    Try to find old namelist
6086 12    REWIND ( 11 )
6087       line = ' '
6088       DO WHILE ( INDEX( line, '&urban_surface_par' ) == 0 )
6089          READ ( 11, '(A)', END=14 )  line
6090       ENDDO
6091       BACKSPACE ( 11 )
6092
6093!
6094!--    Read user-defined namelist
6095       READ ( 11, urban_surface_par, ERR = 13, END = 14 )
6096
6097       message_string = 'namelist urban_surface_par is deprecated and will be ' // &
6098                     'removed in near future. Please use namelist ' //   &
6099                     'urban_surface_parameters instead'
6100       CALL message( 'usm_parin', 'PA0487', 0, 1, 0, 6, 0 )
6101
6102!
6103!--    Set flag that indicates that the urban surface model is switched on
6104       urban_surface = .TRUE.
6105
6106       GOTO 14
6107
6108 13    BACKSPACE( 11 )
6109       READ( 11 , '(A)') line
6110       CALL parin_fail_message( 'urban_surface_par', line )
6111
6112
6113 14    CONTINUE
6114
6115
6116    END SUBROUTINE usm_parin
6117
6118 
6119!------------------------------------------------------------------------------!
6120! Description:
6121! ------------
6122!
6123!> This subroutine is part of the urban surface model.
6124!> It reads daily heat produced by anthropogenic sources
6125!> and the diurnal cycle of the heat.
6126!------------------------------------------------------------------------------!
6127    SUBROUTINE usm_read_anthropogenic_heat
6128   
6129        INTEGER(iwp)                  :: i,j,k,ii  !< running indices
6130        REAL(wp)                      :: heat      !< anthropogenic heat
6131
6132!
6133!--     allocation of array of sources of anthropogenic heat and their diural profile
6134        ALLOCATE( aheat(naheatlayers,nys:nyn,nxl:nxr) )
6135        ALLOCATE( aheatprof(naheatlayers,0:24) )
6136
6137!
6138!--     read daily amount of heat and its daily cycle
6139        aheat = 0.0_wp
6140        DO  ii = 0, io_blocks-1
6141            IF ( ii == io_group )  THEN
6142
6143!--             open anthropogenic heat file
6144                OPEN( 151, file='ANTHROPOGENIC_HEAT'//TRIM(coupling_char), action='read', &
6145                           status='old', form='formatted', err=11 )
6146                i = 0
6147                j = 0
6148                DO
6149                    READ( 151, *, err=12, end=13 )  i, j, k, heat
6150                    IF ( i >= nxl  .AND.  i <= nxr  .AND.  j >= nys  .AND.  j <= nyn )  THEN
6151                        IF ( k <= naheatlayers  .AND.  k > get_topography_top_index_ji( j, i, 's' ) )  THEN
6152!--                         write heat into the array
6153                            aheat(k,j,i) = heat
6154                        ENDIF
6155                    ENDIF
6156                    CYCLE
6157 12                 WRITE(message_string,'(a,2i4)') 'error in file ANTHROPOGENIC_HEAT'//TRIM(coupling_char)//' after line ',i,j
6158                    CALL message( 'usm_read_anthropogenic_heat', 'PA0515', 0, 1, 0, 6, 0 )
6159                ENDDO
6160 13             CLOSE(151)
6161                CYCLE
6162 11             message_string = 'file ANTHROPOGENIC_HEAT'//TRIM(coupling_char)//' does not exist'
6163                CALL message( 'usm_read_anthropogenic_heat', 'PA0516', 1, 2, 0, 6, 0 )
6164            ENDIF
6165           
6166#if defined( __parallel )
6167            CALL MPI_BARRIER( comm2d, ierr )
6168#endif
6169        ENDDO
6170       
6171!
6172!--     read diurnal profiles of heat sources
6173        aheatprof = 0.0_wp
6174        DO  ii = 0, io_blocks-1
6175            IF ( ii == io_group )  THEN
6176!
6177!--             open anthropogenic heat profile file
6178                OPEN( 151, file='ANTHROPOGENIC_HEAT_PROFILE'//TRIM(coupling_char), action='read', &
6179                           status='old', form='formatted', err=21 )
6180                i = 0
6181                DO
6182                    READ( 151, *, err=22, end=23 )  i, k, heat
6183                    IF ( i >= 0  .AND.  i <= 24  .AND.  k <= naheatlayers )  THEN
6184!--                     write heat into the array
6185                        aheatprof(k,i) = heat
6186                    ENDIF
6187                    CYCLE
6188 22                 WRITE(message_string,'(a,i4)') 'error in file ANTHROPOGENIC_HEAT_PROFILE'// &
6189                                                     TRIM(coupling_char)//' after line ',i
6190                    CALL message( 'usm_read_anthropogenic_heat', 'PA0517', 0, 1, 0, 6, 0 )
6191                ENDDO
6192                aheatprof(:,24) = aheatprof(:,0)
6193 23             CLOSE(151)
6194                CYCLE
6195 21             message_string = 'file ANTHROPOGENIC_HEAT_PROFILE'//TRIM(coupling_char)//' does not exist'
6196                CALL message( 'usm_read_anthropogenic_heat', 'PA0518', 1, 2, 0, 6, 0 )
6197            ENDIF
6198           
6199#if defined( __parallel )
6200            CALL MPI_BARRIER( comm2d, ierr )
6201#endif
6202        ENDDO
6203       
6204    END SUBROUTINE usm_read_anthropogenic_heat
6205   
6206
6207!------------------------------------------------------------------------------!
6208! Description:
6209! ------------
6210!> Soubroutine reads t_surf and t_wall data from restart files
6211!------------------------------------------------------------------------------!
6212    SUBROUTINE usm_rrd_local( k, nxlf, nxlc, nxl_on_file, nxrf, nxr_on_file, nynf, nyn_on_file,    &
6213                              nysf, nysc, nys_on_file, found )
6214
6215
6216       USE control_parameters,                                                 &
6217           ONLY: length, restart_string
6218           
6219       IMPLICIT NONE
6220
6221       INTEGER(iwp)       ::  k                 !< running index over previous input files covering current local domain
6222       INTEGER(iwp)       ::  l                 !< index variable for surface type
6223       INTEGER(iwp)       ::  ns_h_on_file_usm  !< number of horizontal surface elements (urban type) on file
6224       INTEGER(iwp)       ::  nxlc              !< index of left boundary on current subdomain
6225       INTEGER(iwp)       ::  nxlf              !< index of left boundary on former subdomain
6226       INTEGER(iwp)       ::  nxl_on_file       !< index of left boundary on former local domain
6227       INTEGER(iwp)       ::  nxrf              !< index of right boundary on former subdomain
6228       INTEGER(iwp)       ::  nxr_on_file       !< index of right boundary on former local domain
6229       INTEGER(iwp)       ::  nynf              !< index of north boundary on former subdomain
6230       INTEGER(iwp)       ::  nyn_on_file       !< index of north boundary on former local domain
6231       INTEGER(iwp)       ::  nysc              !< index of south boundary on current subdomain
6232       INTEGER(iwp)       ::  nysf              !< index of south boundary on former subdomain
6233       INTEGER(iwp)       ::  nys_on_file       !< index of south boundary on former local domain
6234       
6235       INTEGER(iwp)       ::  ns_v_on_file_usm(0:3)  !< number of vertical surface elements (urban type) on file
6236       
6237       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  start_index_on_file 
6238       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  end_index_on_file
6239
6240       LOGICAL, INTENT(OUT)  ::  found 
6241!!!    suehring: Why the SAVE attribute?       
6242       REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE   ::  tmp_surf_wall_h
6243       REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE   ::  tmp_surf_window_h
6244       REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE   ::  tmp_surf_green_h
6245       REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE   ::  tmp_surf_waste_h
6246       
6247       REAL(wp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  tmp_wall_h
6248       REAL(wp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  tmp_window_h
6249       REAL(wp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  tmp_green_h
6250       
6251       TYPE( t_surf_vertical ), DIMENSION(0:3), SAVE ::  tmp_surf_wall_v
6252       TYPE( t_surf_vertical ), DIMENSION(0:3), SAVE ::  tmp_surf_window_v
6253       TYPE( t_surf_vertical ), DIMENSION(0:3), SAVE ::  tmp_surf_green_v
6254       TYPE( t_surf_vertical ), DIMENSION(0:3), SAVE ::  tmp_surf_waste_v
6255       
6256       TYPE( t_wall_vertical ), DIMENSION(0:3), SAVE ::  tmp_wall_v
6257       TYPE( t_wall_vertical ), DIMENSION(0:3), SAVE ::  tmp_window_v
6258       TYPE( t_wall_vertical ), DIMENSION(0:3), SAVE ::  tmp_green_v
6259
6260
6261       found = .TRUE.
6262
6263
6264          SELECT CASE ( restart_string(1:length) ) 
6265
6266             CASE ( 'ns_h_on_file_usm') 
6267                IF ( k == 1 )  THEN
6268                   READ ( 13 ) ns_h_on_file_usm
6269               
6270                   IF ( ALLOCATED( tmp_surf_wall_h ) ) DEALLOCATE( tmp_surf_wall_h )
6271                   IF ( ALLOCATED( tmp_wall_h ) ) DEALLOCATE( tmp_wall_h ) 
6272                   IF ( ALLOCATED( tmp_surf_window_h ) )                       &
6273                      DEALLOCATE( tmp_surf_window_h ) 
6274                   IF ( ALLOCATED( tmp_window_h) ) DEALLOCATE( tmp_window_h ) 
6275                   IF ( ALLOCATED( tmp_surf_green_h) )                         &
6276                      DEALLOCATE( tmp_surf_green_h ) 
6277                   IF ( ALLOCATED( tmp_green_h) ) DEALLOCATE( tmp_green_h )
6278                   IF ( ALLOCATED( tmp_surf_waste_h) )                         &
6279                      DEALLOCATE( tmp_surf_waste_h )
6280 
6281!
6282!--                Allocate temporary arrays for reading data on file. Note,
6283!--                the size of allocated surface elements do not necessarily
6284!--                need  to match the size of present surface elements on
6285!--                current processor, as the number of processors between
6286!--                restarts can change.
6287                   ALLOCATE( tmp_surf_wall_h(1:ns_h_on_file_usm) )
6288                   ALLOCATE( tmp_wall_h(nzb_wall:nzt_wall+1,                   &
6289                                        1:ns_h_on_file_usm) )
6290                   ALLOCATE( tmp_surf_window_h(1:ns_h_on_file_usm) )
6291                   ALLOCATE( tmp_window_h(nzb_wall:nzt_wall+1,                 &
6292                                          1:ns_h_on_file_usm) )
6293                   ALLOCATE( tmp_surf_green_h(1:ns_h_on_file_usm) )
6294                   ALLOCATE( tmp_green_h(nzb_wall:nzt_wall+1,                  &
6295                                         1:ns_h_on_file_usm) )
6296                   ALLOCATE( tmp_surf_waste_h(1:ns_h_on_file_usm) )
6297
6298                ENDIF
6299
6300             CASE ( 'ns_v_on_file_usm')
6301                IF ( k == 1 )  THEN
6302                   READ ( 13 ) ns_v_on_file_usm 
6303
6304                   DO  l = 0, 3
6305                      IF ( ALLOCATED( tmp_surf_wall_v(l)%t ) )                 &
6306                         DEALLOCATE( tmp_surf_wall_v(l)%t )
6307                      IF ( ALLOCATED( tmp_wall_v(l)%t ) )                      &
6308                         DEALLOCATE( tmp_wall_v(l)%t )
6309                      IF ( ALLOCATED( tmp_surf_window_v(l)%t ) )               & 
6310                         DEALLOCATE( tmp_surf_window_v(l)%t )
6311                      IF ( ALLOCATED( tmp_window_v(l)%t ) )                    &
6312                         DEALLOCATE( tmp_window_v(l)%t )
6313                      IF ( ALLOCATED( tmp_surf_green_v(l)%t ) )                &
6314                         DEALLOCATE( tmp_surf_green_v(l)%t )
6315                      IF ( ALLOCATED( tmp_green_v(l)%t ) )                     &
6316                         DEALLOCATE( tmp_green_v(l)%t )
6317                      IF ( ALLOCATED( tmp_surf_waste_v(l)%t ) )                &
6318                         DEALLOCATE( tmp_surf_waste_v(l)%t )
6319                   ENDDO 
6320
6321!
6322!--                Allocate temporary arrays for reading data on file. Note,
6323!--                the size of allocated surface elements do not necessarily
6324!--                need to match the size of present surface elements on
6325!--                current processor, as the number of processors between
6326!--                restarts can change.
6327                   DO  l = 0, 3
6328                      ALLOCATE( tmp_surf_wall_v(l)%t(1:ns_v_on_file_usm(l)) )
6329                      ALLOCATE( tmp_wall_v(l)%t(nzb_wall:nzt_wall+1,           &
6330                                                1:ns_v_on_file_usm(l) ) )
6331                      ALLOCATE( tmp_surf_window_v(l)%t(1:ns_v_on_file_usm(l)) )
6332                      ALLOCATE( tmp_window_v(l)%t(nzb_wall:nzt_wall+1,         & 
6333                                                  1:ns_v_on_file_usm(l) ) )
6334                      ALLOCATE( tmp_surf_green_v(l)%t(1:ns_v_on_file_usm(l)) )
6335                      ALLOCATE( tmp_green_v(l)%t(nzb_wall:nzt_wall+1,          &
6336                                                 1:ns_v_on_file_usm(l) ) )
6337                      ALLOCATE( tmp_surf_waste_v(l)%t(1:ns_v_on_file_usm(l)) )
6338                   ENDDO
6339
6340                ENDIF   
6341         
6342             CASE ( 'usm_start_index_h', 'usm_start_index_v'  )   
6343                IF ( k == 1 )  THEN
6344
6345                   IF ( ALLOCATED( start_index_on_file ) )                     &
6346                      DEALLOCATE( start_index_on_file )
6347
6348                   ALLOCATE ( start_index_on_file(nys_on_file:nyn_on_file,     &
6349                                                  nxl_on_file:nxr_on_file) )
6350
6351                   READ ( 13 )  start_index_on_file
6352
6353                ENDIF
6354               
6355             CASE ( 'usm_end_index_h', 'usm_end_index_v' )   
6356                IF ( k == 1 )  THEN
6357
6358                   IF ( ALLOCATED( end_index_on_file ) )                       &
6359                      DEALLOCATE( end_index_on_file )
6360
6361                   ALLOCATE ( end_index_on_file(nys_on_file:nyn_on_file,       &
6362                                                nxl_on_file:nxr_on_file) )
6363
6364                   READ ( 13 )  end_index_on_file
6365
6366                ENDIF
6367         
6368             CASE ( 't_surf_wall_h' )
6369                IF ( k == 1 )  THEN
6370                   IF ( .NOT.  ALLOCATED( t_surf_wall_h_1 ) )                  &
6371                      ALLOCATE( t_surf_wall_h_1(1:surf_usm_h%ns) )
6372                   READ ( 13 )  tmp_surf_wall_h
6373                ENDIF             
6374                CALL surface_restore_elements(                                 &
6375                                        t_surf_wall_h_1, tmp_surf_wall_h,      &
6376                                        surf_usm_h%start_index,                &
6377                                        start_index_on_file,                   &
6378                                        end_index_on_file,                     &
6379                                        nxlc, nysc,                            &
6380                                        nxlf, nxrf, nysf, nynf,                &
6381                                        nys_on_file, nyn_on_file,              &
6382                                        nxl_on_file,nxr_on_file )
6383
6384             CASE ( 't_surf_wall_v(0)' )
6385                IF ( k == 1 )  THEN
6386                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(0)%t ) )             &
6387                      ALLOCATE( t_surf_wall_v_1(0)%t(1:surf_usm_v(0)%ns) )
6388                   READ ( 13 )  tmp_surf_wall_v(0)%t
6389                ENDIF
6390                CALL surface_restore_elements(                                 &
6391                                        t_surf_wall_v_1(0)%t, tmp_surf_wall_v(0)%t,      &
6392                                        surf_usm_v(0)%start_index,             & 
6393                                        start_index_on_file,                   &
6394                                        end_index_on_file,                     &
6395                                        nxlc, nysc,                            &
6396                                        nxlf, nxrf, nysf, nynf,                &
6397                                        nys_on_file, nyn_on_file,              &
6398                                        nxl_on_file,nxr_on_file )
6399                     
6400             CASE ( 't_surf_wall_v(1)' )
6401                IF ( k == 1 )  THEN
6402                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(1)%t ) )             &
6403                      ALLOCATE( t_surf_wall_v_1(1)%t(1:surf_usm_v(1)%ns) )
6404                   READ ( 13 )  tmp_surf_wall_v(1)%t
6405                ENDIF
6406                CALL surface_restore_elements(                                 &
6407                                        t_surf_wall_v_1(1)%t, tmp_surf_wall_v(1)%t,      &
6408                                        surf_usm_v(1)%start_index,             & 
6409                                        start_index_on_file,                   &
6410                                        end_index_on_file,                     &
6411                                        nxlc, nysc,                            &
6412                                        nxlf, nxrf, nysf, nynf,                &
6413                                        nys_on_file, nyn_on_file,              &
6414                                        nxl_on_file,nxr_on_file )
6415
6416             CASE ( 't_surf_wall_v(2)' )
6417                IF ( k == 1 )  THEN
6418                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(2)%t ) )             &
6419                      ALLOCATE( t_surf_wall_v_1(2)%t(1:surf_usm_v(2)%ns) )
6420                   READ ( 13 )  tmp_surf_wall_v(2)%t
6421                ENDIF
6422                CALL surface_restore_elements(                                 &
6423                                        t_surf_wall_v_1(2)%t, tmp_surf_wall_v(2)%t,      &
6424                                        surf_usm_v(2)%start_index,             & 
6425                                        start_index_on_file,                   &
6426                                        end_index_on_file,                     &
6427                                        nxlc, nysc,                            &
6428                                        nxlf, nxrf, nysf, nynf,                &
6429                                        nys_on_file, nyn_on_file,              &
6430                                        nxl_on_file,nxr_on_file )
6431                     
6432             CASE ( 't_surf_wall_v(3)' )
6433                IF ( k == 1 )  THEN
6434                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(3)%t ) )             &
6435                      ALLOCATE( t_surf_wall_v_1(3)%t(1:surf_usm_v(3)%ns) )
6436                   READ ( 13 )  tmp_surf_wall_v(3)%t
6437                ENDIF
6438                CALL surface_restore_elements(                                 &
6439                                        t_surf_wall_v_1(3)%t, tmp_surf_wall_v(3)%t,      &
6440                                        surf_usm_v(3)%start_index,             & 
6441                                        start_index_on_file,                   &
6442                                        end_index_on_file,                     &
6443                                        nxlc, nysc,                            &
6444                                        nxlf, nxrf, nysf, nynf,                &
6445                                        nys_on_file, nyn_on_file,              &
6446                                        nxl_on_file,nxr_on_file )
6447
6448             CASE ( 't_surf_green_h' )
6449                IF ( k == 1 )  THEN
6450                   IF ( .NOT.  ALLOCATED( t_surf_green_h_1 ) )                 &
6451                      ALLOCATE( t_surf_green_h_1(1:surf_usm_h%ns) )
6452                   READ ( 13 )  tmp_surf_green_h
6453                ENDIF
6454                CALL surface_restore_elements(                                 &
6455                                        t_surf_green_h_1, tmp_surf_green_h,    &
6456                                        surf_usm_h%start_index,                & 
6457                                        start_index_on_file,                   &
6458                                        end_index_on_file,                     &
6459                                        nxlc, nysc,                            &
6460                                        nxlf, nxrf, nysf, nynf,                &
6461                                        nys_on_file, nyn_on_file,              &
6462                                        nxl_on_file,nxr_on_file )
6463
6464             CASE ( 't_surf_green_v(0)' )
6465                IF ( k == 1 )  THEN
6466                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(0)%t ) )            &
6467                      ALLOCATE( t_surf_green_v_1(0)%t(1:surf_usm_v(0)%ns) )
6468                   READ ( 13 )  tmp_surf_green_v(0)%t
6469                ENDIF
6470                CALL surface_restore_elements(                                 &
6471                                        t_surf_green_v_1(0)%t,                 &
6472                                        tmp_surf_green_v(0)%t,                 &
6473                                        surf_usm_v(0)%start_index,             & 
6474                                        start_index_on_file,                   &
6475                                        end_index_on_file,                     &
6476                                        nxlc, nysc,                            &
6477                                        nxlf, nxrf, nysf, nynf,                &
6478                                        nys_on_file, nyn_on_file,              &
6479                                        nxl_on_file,nxr_on_file )
6480                   
6481             CASE ( 't_surf_green_v(1)' )
6482                IF ( k == 1 )  THEN
6483                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(1)%t ) )            &
6484                      ALLOCATE( t_surf_green_v_1(1)%t(1:surf_usm_v(1)%ns) )
6485                   READ ( 13 )  tmp_surf_green_v(1)%t
6486                ENDIF
6487                CALL surface_restore_elements(                                 &
6488                                        t_surf_green_v_1(1)%t,                 &
6489                                        tmp_surf_green_v(1)%t,                 &
6490                                        surf_usm_v(1)%start_index,             & 
6491                                        start_index_on_file,                   &
6492                                        end_index_on_file,                     &
6493                                        nxlc, nysc,                            &
6494                                        nxlf, nxrf, nysf, nynf,                &
6495                                        nys_on_file, nyn_on_file,              &
6496                                        nxl_on_file,nxr_on_file )
6497
6498             CASE ( 't_surf_green_v(2)' )
6499                IF ( k == 1 )  THEN
6500                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(2)%t ) )            &
6501                      ALLOCATE( t_surf_green_v_1(2)%t(1:surf_usm_v(2)%ns) )
6502                   READ ( 13 )  tmp_surf_green_v(2)%t
6503                ENDIF
6504                CALL surface_restore_elements(                                 &
6505                                        t_surf_green_v_1(2)%t,                 &
6506                                        tmp_surf_green_v(2)%t,                 &
6507                                        surf_usm_v(2)%start_index,             & 
6508                                        start_index_on_file,                   &
6509                                        end_index_on_file,                     &
6510                                        nxlc, nysc,                            &
6511                                        nxlf, nxrf, nysf, nynf,                &
6512                                        nys_on_file, nyn_on_file,              &
6513                                        nxl_on_file,nxr_on_file )
6514                   
6515             CASE ( 't_surf_green_v(3)' )
6516                IF ( k == 1 )  THEN
6517                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(3)%t ) )            &
6518                      ALLOCATE( t_surf_green_v_1(3)%t(1:surf_usm_v(3)%ns) )
6519                   READ ( 13 )  tmp_surf_green_v(3)%t
6520                ENDIF
6521                CALL surface_restore_elements(                                 &
6522                                        t_surf_green_v_1(3)%t,                 & 
6523                                        tmp_surf_green_v(3)%t,                 &
6524                                        surf_usm_v(3)%start_index,             & 
6525                                        start_index_on_file,                   &
6526                                        end_index_on_file,                     &
6527                                        nxlc, nysc,                            &
6528                                        nxlf, nxrf, nysf, nynf,                &
6529                                        nys_on_file, nyn_on_file,              &
6530                                        nxl_on_file,nxr_on_file )
6531
6532             CASE ( 't_surf_window_h' )
6533                IF ( k == 1 )  THEN
6534                   IF ( .NOT.  ALLOCATED( t_surf_window_h_1 ) )                &
6535                      ALLOCATE( t_surf_window_h_1(1:surf_usm_h%ns) )
6536                   READ ( 13 )  tmp_surf_window_h
6537                ENDIF
6538                CALL surface_restore_elements(                                 &
6539                                        t_surf_window_h_1,                     &
6540                                        tmp_surf_window_h,                     &
6541                                        surf_usm_h%start_index,                & 
6542                                        start_index_on_file,                   &
6543                                        end_index_on_file,                     &
6544                                        nxlc, nysc,                            &
6545                                        nxlf, nxrf, nysf, nynf,                &
6546                                        nys_on_file, nyn_on_file,              &
6547                                        nxl_on_file,nxr_on_file )
6548
6549             CASE ( 't_surf_window_v(0)' )
6550                IF ( k == 1 )  THEN
6551                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(0)%t ) )           &
6552                      ALLOCATE( t_surf_window_v_1(0)%t(1:surf_usm_v(0)%ns) )
6553                   READ ( 13 )  tmp_surf_window_v(0)%t
6554                ENDIF
6555                CALL surface_restore_elements(                                 &
6556                                        t_surf_window_v_1(0)%t,                &
6557                                        tmp_surf_window_v(0)%t,                &
6558                                        surf_usm_v(0)%start_index,             & 
6559                                        start_index_on_file,                   &
6560                                        end_index_on_file,                     &
6561                                        nxlc, nysc,                            &
6562                                        nxlf, nxrf, nysf, nynf,                &
6563                                        nys_on_file, nyn_on_file,              &
6564                                        nxl_on_file,nxr_on_file )
6565                   
6566             CASE ( 't_surf_window_v(1)' )
6567                IF ( k == 1 )  THEN
6568                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(1)%t ) )           &
6569                      ALLOCATE( t_surf_window_v_1(1)%t(1:surf_usm_v(1)%ns) )
6570                   READ ( 13 )  tmp_surf_window_v(1)%t
6571                ENDIF
6572                CALL surface_restore_elements(                                 &
6573                                        t_surf_window_v_1(1)%t,                &
6574                                        tmp_surf_window_v(1)%t,                &
6575                                        surf_usm_v(1)%start_index,             & 
6576                                        start_index_on_file,                   &
6577                                        end_index_on_file,                     &
6578                                        nxlc, nysc,                            &
6579                                        nxlf, nxrf, nysf, nynf,                &
6580                                        nys_on_file, nyn_on_file,              &
6581                                        nxl_on_file,nxr_on_file )
6582
6583             CASE ( 't_surf_window_v(2)' )
6584                IF ( k == 1 )  THEN
6585                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(2)%t ) )           &
6586                      ALLOCATE( t_surf_window_v_1(2)%t(1:surf_usm_v(2)%ns) )
6587                   READ ( 13 )  tmp_surf_window_v(2)%t
6588                ENDIF
6589                CALL surface_restore_elements(                                 &
6590                                        t_surf_window_v_1(2)%t,                & 
6591                                        tmp_surf_window_v(2)%t,                &
6592                                        surf_usm_v(2)%start_index,             & 
6593                                        start_index_on_file,                   &
6594                                        end_index_on_file,                     &
6595                                        nxlc, nysc,                            &
6596                                        nxlf, nxrf, nysf, nynf,                &
6597                                        nys_on_file, nyn_on_file,              &
6598                                        nxl_on_file,nxr_on_file )
6599                   
6600             CASE ( 't_surf_window_v(3)' )
6601                IF ( k == 1 )  THEN
6602                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(3)%t ) )           &
6603                      ALLOCATE( t_surf_window_v_1(3)%t(1:surf_usm_v(3)%ns) )
6604                   READ ( 13 )  tmp_surf_window_v(3)%t
6605                ENDIF
6606                CALL surface_restore_elements(                                 &
6607                                        t_surf_window_v_1(3)%t,                & 
6608                                        tmp_surf_window_v(3)%t,                &
6609                                        surf_usm_v(3)%start_index,             & 
6610                                        start_index_on_file,                   &
6611                                        end_index_on_file,                     &
6612                                        nxlc, nysc,                            &
6613                                        nxlf, nxrf, nysf, nynf,                &
6614                                        nys_on_file, nyn_on_file,              &
6615                                        nxl_on_file,nxr_on_file )
6616
6617             CASE ( 'waste_heat_h' )
6618                IF ( k == 1 )  THEN
6619                   IF ( .NOT.  ALLOCATED( surf_usm_h%waste_heat ) )            &
6620                      ALLOCATE( surf_usm_h%waste_heat(1:surf_usm_h%ns) )
6621                   READ ( 13 )  tmp_surf_waste_h
6622                ENDIF             
6623                CALL surface_restore_elements(                                 &
6624                                        surf_usm_h%waste_heat,                 &
6625                                        tmp_surf_waste_h,                      &
6626                                        surf_usm_h%start_index,                &
6627                                        start_index_on_file,                   &
6628                                        end_index_on_file,                     &
6629                                        nxlc, nysc,                            &
6630                                        nxlf, nxrf, nysf, nynf,                &
6631                                        nys_on_file, nyn_on_file,              &
6632                                        nxl_on_file,nxr_on_file )                 
6633                                       
6634             CASE ( 'waste_heat_v(0)' )
6635                IF ( k == 1 )  THEN
6636                   IF ( .NOT.  ALLOCATED( surf_usm_v(0)%waste_heat ) )         &
6637                      ALLOCATE( surf_usm_v(0)%waste_heat(1:surf_usm_v(0)%ns) )
6638                   READ ( 13 )  tmp_surf_waste_v(0)%t
6639                ENDIF
6640                CALL surface_restore_elements(                                 &
6641                                        surf_usm_v(0)%waste_heat,              &
6642                                        tmp_surf_waste_v(0)%t,                 &
6643                                        surf_usm_v(0)%start_index,             & 
6644                                        start_index_on_file,                   &
6645                                        end_index_on_file,                     &
6646                                        nxlc, nysc,                            &
6647                                        nxlf, nxrf, nysf, nynf,                &
6648                                        nys_on_file, nyn_on_file,              &
6649                                        nxl_on_file,nxr_on_file )
6650                     
6651             CASE ( 'waste_heat_v(1)' )
6652                IF ( k == 1 )  THEN
6653                   IF ( .NOT.  ALLOCATED( surf_usm_v(1)%waste_heat ) )         &
6654                      ALLOCATE( surf_usm_v(1)%waste_heat(1:surf_usm_v(1)%ns) )
6655                   READ ( 13 )  tmp_surf_waste_v(1)%t
6656                ENDIF
6657                CALL surface_restore_elements(                                 &
6658                                        surf_usm_v(1)%waste_heat,              &
6659                                        tmp_surf_waste_v(1)%t,                 &
6660                                        surf_usm_v(1)%start_index,             & 
6661                                        start_index_on_file,                   &
6662                                        end_index_on_file,                     &
6663                                        nxlc, nysc,                            &
6664                                        nxlf, nxrf, nysf, nynf,                &
6665                                        nys_on_file, nyn_on_file,              &
6666                                        nxl_on_file,nxr_on_file )
6667
6668             CASE ( 'waste_heat_v(2)' )
6669                IF ( k == 1 )  THEN
6670                   IF ( .NOT.  ALLOCATED( surf_usm_v(2)%waste_heat ) )         &
6671                      ALLOCATE( surf_usm_v(2)%waste_heat(1:surf_usm_v(2)%ns) )
6672                   READ ( 13 )  tmp_surf_waste_v(2)%t
6673                ENDIF
6674                CALL surface_restore_elements(                                 &
6675                                        surf_usm_v(2)%waste_heat,              &
6676                                        tmp_surf_waste_v(2)%t,                 &
6677                                        surf_usm_v(2)%start_index,             & 
6678                                        start_index_on_file,                   &
6679                                        end_index_on_file,                     &
6680                                        nxlc, nysc,                            &
6681                                        nxlf, nxrf, nysf, nynf,                &
6682                                        nys_on_file, nyn_on_file,              &
6683                                        nxl_on_file,nxr_on_file )
6684                     
6685             CASE ( 'waste_heat_v(3)' )
6686                IF ( k == 1 )  THEN
6687                   IF ( .NOT.  ALLOCATED( surf_usm_v(3)%waste_heat ) )         &
6688                      ALLOCATE( surf_usm_v(3)%waste_heat(1:surf_usm_v(3)%ns) )
6689                   READ ( 13 )  tmp_surf_waste_v(3)%t
6690                ENDIF
6691                CALL surface_restore_elements(                                 &
6692                                        surf_usm_v(3)%waste_heat,              &
6693                                        tmp_surf_waste_v(3)%t,                 &
6694                                        surf_usm_v(3)%start_index,             & 
6695                                        start_index_on_file,                   &
6696                                        end_index_on_file,                     &
6697                                        nxlc, nysc,                            &
6698                                        nxlf, nxrf, nysf, nynf,                &
6699                                        nys_on_file, nyn_on_file,              &
6700                                        nxl_on_file,nxr_on_file )
6701
6702             CASE ( 't_wall_h' )
6703                IF ( k == 1 )  THEN
6704                   IF ( .NOT.  ALLOCATED( t_wall_h_1 ) )                       &
6705                      ALLOCATE( t_wall_h_1(nzb_wall:nzt_wall+1,                &
6706                                           1:surf_usm_h%ns) )
6707                   READ ( 13 )  tmp_wall_h
6708                ENDIF
6709                CALL surface_restore_elements(                                 &
6710                                        t_wall_h_1, tmp_wall_h,                &
6711                                        surf_usm_h%start_index,                & 
6712                                        start_index_on_file,                   &
6713                                        end_index_on_file,                     &
6714                                        nxlc, nysc,                            &
6715                                        nxlf, nxrf, nysf, nynf,                &
6716                                        nys_on_file, nyn_on_file,              &
6717                                        nxl_on_file,nxr_on_file )
6718
6719             CASE ( 't_wall_v(0)' )
6720                IF ( k == 1 )  THEN
6721                   IF ( .NOT.  ALLOCATED( t_wall_v_1(0)%t ) )                  &
6722                      ALLOCATE( t_wall_v_1(0)%t(nzb_wall:nzt_wall+1,           &
6723                                                1:surf_usm_v(0)%ns) )
6724                   READ ( 13 )  tmp_wall_v(0)%t
6725                ENDIF
6726                CALL surface_restore_elements(                                 &
6727                                        t_wall_v_1(0)%t, tmp_wall_v(0)%t,      &
6728                                        surf_usm_v(0)%start_index,             & 
6729                                        start_index_on_file,                   &
6730                                        end_index_on_file,                     &
6731                                        nxlc, nysc,                            &
6732                                        nxlf, nxrf, nysf, nynf,                &
6733                                        nys_on_file, nyn_on_file,              &
6734                                        nxl_on_file,nxr_on_file )
6735
6736             CASE ( 't_wall_v(1)' )
6737                IF ( k == 1 )  THEN
6738                   IF ( .NOT.  ALLOCATED( t_wall_v_1(1)%t ) )                  &
6739                      ALLOCATE( t_wall_v_1(1)%t(nzb_wall:nzt_wall+1,           &
6740                                                1:surf_usm_v(1)%ns) )
6741                   READ ( 13 )  tmp_wall_v(1)%t
6742                ENDIF
6743                CALL surface_restore_elements(                                 &
6744                                        t_wall_v_1(1)%t, tmp_wall_v(1)%t,      &
6745                                        surf_usm_v(1)%start_index,             & 
6746                                        start_index_on_file,                   &
6747                                        end_index_on_file,                     &
6748                                        nxlc, nysc,                            &
6749                                        nxlf, nxrf, nysf, nynf,                &
6750                                        nys_on_file, nyn_on_file,              &
6751                                        nxl_on_file,nxr_on_file )
6752
6753             CASE ( 't_wall_v(2)' )
6754                IF ( k == 1 )  THEN
6755                   IF ( .NOT.  ALLOCATED( t_wall_v_1(2)%t ) )                  &
6756                      ALLOCATE( t_wall_v_1(2)%t(nzb_wall:nzt_wall+1,           &
6757                                                1:surf_usm_v(2)%ns) )
6758                   READ ( 13 )  tmp_wall_v(2)%t
6759                ENDIF
6760                CALL surface_restore_elements(                                 &
6761                                        t_wall_v_1(2)%t, tmp_wall_v(2)%t,      &
6762                                        surf_usm_v(2)%start_index,             & 
6763                                        start_index_on_file,                   &
6764                                        end_index_on_file ,                    &
6765                                        nxlc, nysc,                            &
6766                                        nxlf, nxrf, nysf, nynf,                &
6767                                        nys_on_file, nyn_on_file,              &
6768                                        nxl_on_file,nxr_on_file )
6769
6770             CASE ( 't_wall_v(3)' )
6771                IF ( k == 1 )  THEN
6772                   IF ( .NOT.  ALLOCATED( t_wall_v_1(3)%t ) )                  &
6773                      ALLOCATE( t_wall_v_1(3)%t(nzb_wall:nzt_wall+1,           &
6774                                                1:surf_usm_v(3)%ns) )
6775                   READ ( 13 )  tmp_wall_v(3)%t
6776                ENDIF
6777                CALL surface_restore_elements(                                 &
6778                                        t_wall_v_1(3)%t, tmp_wall_v(3)%t,      &
6779                                        surf_usm_v(3)%start_index,             &   
6780                                        start_index_on_file,                   &
6781                                        end_index_on_file,                     &
6782                                        nxlc, nysc,                            &
6783                                        nxlf, nxrf, nysf, nynf,                &
6784                                        nys_on_file, nyn_on_file,              &
6785                                        nxl_on_file,nxr_on_file )
6786
6787             CASE ( 't_green_h' )
6788                IF ( k == 1 )  THEN
6789                   IF ( .NOT.  ALLOCATED( t_green_h_1 ) )                      &
6790                      ALLOCATE( t_green_h_1(nzb_wall:nzt_wall+1,               &
6791                                            1:surf_usm_h%ns) )
6792                   READ ( 13 )  tmp_green_h
6793                ENDIF
6794                CALL surface_restore_elements(                                 &
6795                                        t_green_h_1, tmp_green_h,              &
6796                                        surf_usm_h%start_index,                & 
6797                                        start_index_on_file,                   &
6798                                        end_index_on_file,                     &
6799                                        nxlc, nysc,                            &
6800                                        nxlf, nxrf, nysf, nynf,                &
6801                                        nys_on_file, nyn_on_file,              &
6802                                        nxl_on_file,nxr_on_file )
6803
6804             CASE ( 't_green_v(0)' )
6805                IF ( k == 1 )  THEN
6806                   IF ( .NOT.  ALLOCATED( t_green_v_1(0)%t ) )                 &
6807                      ALLOCATE( t_green_v_1(0)%t(nzb_wall:nzt_wall+1,          &
6808                                                 1:surf_usm_v(0)%ns) )
6809                   READ ( 13 )  tmp_green_v(0)%t
6810                ENDIF
6811                CALL surface_restore_elements(                                 &
6812                                        t_green_v_1(0)%t, tmp_green_v(0)%t,    &
6813                                        surf_usm_v(0)%start_index,             & 
6814                                        start_index_on_file,                   &
6815                                        end_index_on_file,                     &
6816                                        nxlc, nysc,                            &
6817                                        nxlf, nxrf, nysf, nynf,                &
6818                                        nys_on_file, nyn_on_file,              &
6819                                        nxl_on_file,nxr_on_file )
6820
6821             CASE ( 't_green_v(1)' )
6822                IF ( k == 1 )  THEN
6823                   IF ( .NOT.  ALLOCATED( t_green_v_1(1)%t ) )                 &
6824                      ALLOCATE( t_green_v_1(1)%t(nzb_wall:nzt_wall+1,          &
6825                                                 1:surf_usm_v(1)%ns) )
6826                   READ ( 13 )  tmp_green_v(1)%t
6827                ENDIF
6828                CALL surface_restore_elements(                                 &
6829                                        t_green_v_1(1)%t, tmp_green_v(1)%t,    &
6830                                        surf_usm_v(1)%start_index,             & 
6831                                        start_index_on_file,                   &
6832                                        end_index_on_file,                     &
6833                                        nxlc, nysc,                            &
6834                                        nxlf, nxrf, nysf, nynf,                &
6835                                        nys_on_file, nyn_on_file,              &
6836                                        nxl_on_file,nxr_on_file )
6837
6838             CASE ( 't_green_v(2)' )
6839                IF ( k == 1 )  THEN
6840                   IF ( .NOT.  ALLOCATED( t_green_v_1(2)%t ) )                 &
6841                      ALLOCATE( t_green_v_1(2)%t(nzb_wall:nzt_wall+1,          &
6842                                                 1:surf_usm_v(2)%ns) )
6843                   READ ( 13 )  tmp_green_v(2)%t
6844                ENDIF
6845                CALL surface_restore_elements(                                 &
6846                                        t_green_v_1(2)%t, tmp_green_v(2)%t,    &
6847                                        surf_usm_v(2)%start_index,             & 
6848                                        start_index_on_file,                   &
6849                                        end_index_on_file ,                    &
6850                                        nxlc, nysc,                            &
6851                                        nxlf, nxrf, nysf, nynf,                &
6852                                        nys_on_file, nyn_on_file,              &
6853                                        nxl_on_file,nxr_on_file )
6854
6855             CASE ( 't_green_v(3)' )
6856                IF ( k == 1 )  THEN
6857                   IF ( .NOT.  ALLOCATED( t_green_v_1(3)%t ) )                 &
6858                      ALLOCATE( t_green_v_1(3)%t(nzb_wall:nzt_wall+1,          &
6859                                                 1:surf_usm_v(3)%ns) )
6860                   READ ( 13 )  tmp_green_v(3)%t
6861                ENDIF
6862                CALL surface_restore_elements(                                 &
6863                                        t_green_v_1(3)%t, tmp_green_v(3)%t,    &
6864                                        surf_usm_v(3)%start_index,             & 
6865                                        start_index_on_file,                   &
6866                                        end_index_on_file,                     &
6867                                        nxlc, nysc,                            &
6868                                        nxlf, nxrf, nysf, nynf,                &
6869                                        nys_on_file, nyn_on_file,              &
6870                                        nxl_on_file,nxr_on_file )
6871
6872             CASE ( 't_window_h' )
6873                IF ( k == 1 )  THEN
6874                   IF ( .NOT.  ALLOCATED( t_window_h_1 ) )                     &
6875                      ALLOCATE( t_window_h_1(nzb_wall:nzt_wall+1,              &
6876                                             1:surf_usm_h%ns) )
6877                   READ ( 13 )  tmp_window_h
6878                ENDIF
6879                CALL surface_restore_elements(                                 &
6880                                        t_window_h_1, tmp_window_h,            &
6881                                        surf_usm_h%start_index,                & 
6882                                        start_index_on_file,                   &
6883                                        end_index_on_file,                     &
6884                                        nxlc, nysc,                            &
6885                                        nxlf, nxrf, nysf, nynf,                &
6886                                        nys_on_file, nyn_on_file,              &
6887                                        nxl_on_file, nxr_on_file )
6888
6889             CASE ( 't_window_v(0)' )
6890                IF ( k == 1 )  THEN
6891                   IF ( .NOT.  ALLOCATED( t_window_v_1(0)%t ) )                &
6892                      ALLOCATE( t_window_v_1(0)%t(nzb_wall:nzt_wall+1,         &
6893                                                  1:surf_usm_v(0)%ns) )
6894                   READ ( 13 )  tmp_window_v(0)%t
6895                ENDIF
6896                CALL surface_restore_elements(                                 &
6897                                        t_window_v_1(0)%t,                     & 
6898                                        tmp_window_v(0)%t,                     &
6899                                        surf_usm_v(0)%start_index,             &
6900                                        start_index_on_file,                   &
6901                                        end_index_on_file,                     &
6902                                        nxlc, nysc,                            &
6903                                        nxlf, nxrf, nysf, nynf,                &
6904                                        nys_on_file, nyn_on_file,              &
6905                                        nxl_on_file,nxr_on_file )
6906
6907             CASE ( 't_window_v(1)' )
6908                IF ( k == 1 )  THEN
6909                   IF ( .NOT.  ALLOCATED( t_window_v_1(1)%t ) )                &
6910                      ALLOCATE( t_window_v_1(1)%t(nzb_wall:nzt_wall+1,         &
6911                                                  1:surf_usm_v(1)%ns) )
6912                   READ ( 13 )  tmp_window_v(1)%t
6913                ENDIF
6914                CALL surface_restore_elements(                                 &
6915                                        t_window_v_1(1)%t,                     & 
6916                                        tmp_window_v(1)%t,                     &
6917                                        surf_usm_v(1)%start_index,             & 
6918                                        start_index_on_file,                   &
6919                                        end_index_on_file,                     &
6920                                        nxlc, nysc,                            &
6921                                        nxlf, nxrf, nysf, nynf,                &
6922                                        nys_on_file, nyn_on_file,              &
6923                                        nxl_on_file,nxr_on_file )
6924
6925             CASE ( 't_window_v(2)' )
6926                IF ( k == 1 )  THEN
6927                   IF ( .NOT.  ALLOCATED( t_window_v_1(2)%t ) )                &
6928                      ALLOCATE( t_window_v_1(2)%t(nzb_wall:nzt_wall+1,         &
6929                                                  1:surf_usm_v(2)%ns) )
6930                   READ ( 13 )  tmp_window_v(2)%t
6931                ENDIF
6932                CALL surface_restore_elements(                                 &
6933                                        t_window_v_1(2)%t,                     & 
6934                                        tmp_window_v(2)%t,                     &
6935                                        surf_usm_v(2)%start_index,             & 
6936                                        start_index_on_file,                   &
6937                                        end_index_on_file ,                    &
6938                                        nxlc, nysc,                            &
6939                                        nxlf, nxrf, nysf, nynf,                &
6940                                        nys_on_file, nyn_on_file,              &
6941                                        nxl_on_file,nxr_on_file )
6942
6943             CASE ( 't_window_v(3)' )
6944                IF ( k == 1 )  THEN
6945                   IF ( .NOT.  ALLOCATED( t_window_v_1(3)%t ) )                &
6946                      ALLOCATE( t_window_v_1(3)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(3)%ns) )
6947                   READ ( 13 )  tmp_window_v(3)%t
6948                ENDIF
6949                CALL surface_restore_elements(                                 &
6950                                        t_window_v_1(3)%t,                     & 
6951                                        tmp_window_v(3)%t,                     &
6952                                        surf_usm_v(3)%start_index,             & 
6953                                        start_index_on_file,                   &
6954                                        end_index_on_file,                     &
6955                                        nxlc, nysc,                            &
6956                                        nxlf, nxrf, nysf, nynf,                &
6957                                        nys_on_file, nyn_on_file,              &
6958                                        nxl_on_file,nxr_on_file )
6959
6960             CASE DEFAULT
6961
6962                   found = .FALSE.
6963
6964          END SELECT
6965
6966       
6967    END SUBROUTINE usm_rrd_local
6968
6969   
6970!------------------------------------------------------------------------------!
6971! Description:
6972! ------------
6973!
6974!> This subroutine reads walls, roofs and land categories and it parameters
6975!> from input files.
6976!------------------------------------------------------------------------------!
6977    SUBROUTINE usm_read_urban_surface_types
6978   
6979        USE netcdf_data_input_mod,                                             &
6980            ONLY:  building_pars_f, building_type_f
6981
6982        IMPLICIT NONE
6983
6984        CHARACTER(12)                                         :: wtn
6985        INTEGER(iwp)                                          :: wtc
6986        REAL(wp), DIMENSION(n_surface_params)                 :: wtp
6987        LOGICAL                                               :: ascii_file = .FALSE.
6988        INTEGER(iwp), DIMENSION(0:17, nysg:nyng, nxlg:nxrg)   :: usm_par
6989        REAL(wp), DIMENSION(1:14, nysg:nyng, nxlg:nxrg)       :: usm_val
6990        INTEGER(iwp)                                          :: k, l, iw, jw, kw, it, ip, ii, ij, m
6991        INTEGER(iwp)                                          :: i, j
6992        INTEGER(iwp)                                          :: nz, roof, dirwe, dirsn
6993        INTEGER(iwp)                                          :: category
6994        INTEGER(iwp)                                          :: weheight1, wecat1, snheight1, sncat1
6995        INTEGER(iwp)                                          :: weheight2, wecat2, snheight2, sncat2
6996        INTEGER(iwp)                                          :: weheight3, wecat3, snheight3, sncat3
6997        REAL(wp)                                              :: height, albedo, thick
6998        REAL(wp)                                              :: wealbedo1, wethick1, snalbedo1, snthick1
6999        REAL(wp)                                              :: wealbedo2, wethick2, snalbedo2, snthick2
7000        REAL(wp)                                              :: wealbedo3, wethick3, snalbedo3, snthick3
7001
7002
7003        IF ( debug_output )  CALL debug_message( 'usm_read_urban_surface_types', 'start' )
7004!
7005!--     If building_pars or building_type are already read from static input
7006!--     file, skip reading ASCII file.
7007        IF ( building_type_f%from_file  .OR.  building_pars_f%from_file )      &
7008           RETURN
7009!
7010!--     Check if ASCII input file exists. If not, return and initialize USM
7011!--     with default settings.
7012        INQUIRE( FILE = 'SURFACE_PARAMETERS' // coupling_char,                 &
7013                 EXIST = ascii_file )
7014                 
7015        IF ( .NOT. ascii_file )  RETURN
7016
7017!
7018!--     read categories of walls and their parameters
7019        DO  ii = 0, io_blocks-1
7020            IF ( ii == io_group )  THEN
7021!
7022!--             open urban surface file
7023                OPEN( 151, file='SURFACE_PARAMETERS'//coupling_char, action='read', &
7024                           status='old', form='formatted', err=15 )
7025!
7026!--             first test and get n_surface_types
7027                k = 0
7028                l = 0
7029                DO
7030                    l = l+1
7031                    READ( 151, *, err=11, end=12 )  wtc, wtp, wtn
7032                    k = k+1
7033                    CYCLE
7034 11                 CONTINUE
7035                ENDDO
7036 12             n_surface_types = k
7037                ALLOCATE( surface_type_names(n_surface_types) )
7038                ALLOCATE( surface_type_codes(n_surface_types) )
7039                ALLOCATE( surface_params(n_surface_params, n_surface_types) )
7040!
7041!--             real reading
7042                rewind( 151 )
7043                k = 0
7044                DO
7045                    READ( 151, *, err=13, end=14 )  wtc, wtp, wtn
7046                    k = k+1
7047                    surface_type_codes(k) = wtc
7048                    surface_params(:,k) = wtp
7049                    surface_type_names(k) = wtn
7050                    CYCLE
705113                  WRITE(6,'(i3,a,2i5)') myid, 'readparams2 error k=', k
7052                    FLUSH(6)
7053                    CONTINUE
7054                ENDDO
7055 14             CLOSE(151)
7056                CYCLE
7057 15             message_string = 'file SURFACE_PARAMETERS'//TRIM(coupling_char)//' does not exist'
7058                CALL message( 'usm_read_urban_surface_types', 'PA0513', 1, 2, 0, 6, 0 )
7059            ENDIF
7060        ENDDO
7061   
7062!
7063!--     read types of surfaces
7064        usm_par = 0
7065        DO  ii = 0, io_blocks-1
7066            IF ( ii == io_group )  THEN
7067
7068!
7069!--             open csv urban surface file
7070                OPEN( 151, file='URBAN_SURFACE'//TRIM(coupling_char), action='read', &
7071                      status='old', form='formatted', err=23 )
7072               
7073                l = 0
7074                DO
7075                    l = l+1
7076!
7077!--                 i, j, height, nz, roof, dirwe, dirsn, category, soilcat,
7078!--                 weheight1, wecat1, snheight1, sncat1, weheight2, wecat2, snheight2, sncat2,
7079!--                 weheight3, wecat3, snheight3, sncat3
7080                    READ( 151, *, err=21, end=25 )  i, j, height, nz, roof, dirwe, dirsn,            &
7081                                            category, albedo, thick,                                 &
7082                                            weheight1, wecat1, wealbedo1, wethick1,                  &
7083                                            weheight2, wecat2, wealbedo2, wethick2,                  &
7084                                            weheight3, wecat3, wealbedo3, wethick3,                  &
7085                                            snheight1, sncat1, snalbedo1, snthick1,                  &
7086                                            snheight2, sncat2, snalbedo2, snthick2,                  &
7087                                            snheight3, sncat3, snalbedo3, snthick3
7088
7089                    IF ( i >= nxlg  .AND.  i <= nxrg  .AND.  j >= nysg  .AND.  j <= nyng )  THEN
7090!
7091!--                     write integer variables into array
7092                        usm_par(:,j,i) = (/1, nz, roof, dirwe, dirsn, category,                      &
7093                                          weheight1, wecat1, weheight2, wecat2, weheight3, wecat3,   &
7094                                          snheight1, sncat1, snheight2, sncat2, snheight3, sncat3 /)
7095!
7096!--                     write real values into array
7097                        usm_val(:,j,i) = (/ albedo, thick,                                           &
7098                                           wealbedo1, wethick1, wealbedo2, wethick2,                 &
7099                                           wealbedo3, wethick3, snalbedo1, snthick1,                 &
7100                                           snalbedo2, snthick2, snalbedo3, snthick3 /)
7101                    ENDIF
7102                    CYCLE
7103 21                 WRITE (message_string, "(A,I5)") 'errors in file URBAN_SURFACE'//TRIM(coupling_char)//' on line ', l
7104                    CALL message( 'usm_read_urban_surface_types', 'PA0512', 0, 1, 0, 6, 0 )
7105                ENDDO
7106         
7107 23             message_string = 'file URBAN_SURFACE'//TRIM(coupling_char)//' does not exist'
7108                CALL message( 'usm_read_urban_surface_types', 'PA0514', 1, 2, 0, 6, 0 )
7109
7110 25             CLOSE( 151 )
7111
7112            ENDIF
7113#if defined( __parallel )
7114            CALL MPI_BARRIER( comm2d, ierr )
7115#endif
7116        ENDDO
7117       
7118!
7119!--     check completeness and formal correctness of the data
7120        DO i = nxlg, nxrg
7121            DO j = nysg, nyng
7122                IF ( usm_par(0,j,i) /= 0  .AND.  (        &  !< incomplete data,supply default values later
7123                     usm_par(1,j,i) < nzb  .OR.           &
7124                     usm_par(1,j,i) > nzt  .OR.           &  !< incorrect height (nz < nzb  .OR.  nz > nzt)
7125                     usm_par(2,j,i) < 0  .OR.             &
7126                     usm_par(2,j,i) > 1  .OR.             &  !< incorrect roof sign
7127                     usm_par(3,j,i) < nzb-nzt  .OR.       & 
7128                     usm_par(3,j,i) > nzt-nzb  .OR.       &  !< incorrect west-east wall direction sign
7129                     usm_par(4,j,i) < nzb-nzt  .OR.       &
7130                     usm_par(4,j,i) > nzt-nzb  .OR.       &  !< incorrect south-north wall direction sign
7131                     usm_par(6,j,i) < nzb  .OR.           & 
7132                     usm_par(6,j,i) > nzt  .OR.           &  !< incorrect pedestrian level height for west-east wall
7133                     usm_par(8,j,i) > nzt  .OR.           &
7134                     usm_par(10,j,i) > nzt  .OR.          &  !< incorrect wall or roof level height for west-east wall
7135                     usm_par(12,j,i) < nzb  .OR.          & 
7136                     usm_par(12,j,i) > nzt  .OR.          &  !< incorrect pedestrian level height for south-north wall
7137                     usm_par(14,j,i) > nzt  .OR.          &
7138                     usm_par(16,j,i) > nzt                &  !< incorrect wall or roof level height for south-north wall
7139                    ) )  THEN
7140!
7141!--                 incorrect input data
7142                    WRITE (message_string, "(A,2I5)") 'missing or incorrect data in file URBAN_SURFACE'// &
7143                                                       TRIM(coupling_char)//' for i,j=', i,j
7144                    CALL message( 'usm_read_urban_surface', 'PA0504', 1, 2, 0, 6, 0 )
7145                ENDIF
7146               
7147            ENDDO
7148        ENDDO
7149!       
7150!--     Assign the surface types to the respective data type.
7151!--     First, for horizontal upward-facing surfaces.
7152!--     Further, set flag indicating that albedo is initialized via ASCII
7153!--     format, else it would be overwritten in the radiation model.
7154        surf_usm_h%albedo_from_ascii = .TRUE.
7155        DO  m = 1, surf_usm_h%ns
7156           iw = surf_usm_h%i(m)
7157           jw = surf_usm_h%j(m)
7158           kw = surf_usm_h%k(m)
7159
7160           IF ( usm_par(5,jw,iw) == 0 )  THEN
7161
7162              IF ( zu(kw) >= roof_height_limit )  THEN
7163                 surf_usm_h%isroof_surf(m)   = .TRUE.
7164                 surf_usm_h%surface_types(m) = roof_category         !< default category for root surface
7165              ELSE
7166                 surf_usm_h%isroof_surf(m)   = .FALSE.
7167                 surf_usm_h%surface_types(m) = land_category         !< default category for land surface
7168              ENDIF
7169
7170              surf_usm_h%albedo(:,m)    = -1.0_wp
7171              surf_usm_h%thickness_wall(m) = -1.0_wp
7172              surf_usm_h%thickness_green(m) = -1.0_wp
7173              surf_usm_h%thickness_window(m) = -1.0_wp
7174           ELSE
7175              IF ( usm_par(2,jw,iw)==0 )  THEN
7176                 surf_usm_h%isroof_surf(m)    = .FALSE.
7177                 surf_usm_h%thickness_wall(m) = -1.0_wp
7178                 surf_usm_h%thickness_window(m) = -1.0_wp
7179                 surf_usm_h%thickness_green(m)  = -1.0_wp
7180              ELSE
7181                 surf_usm_h%isroof_surf(m)    = .TRUE.
7182                 surf_usm_h%thickness_wall(m) = usm_val(2,jw,iw)
7183                 surf_usm_h%thickness_window(m) = usm_val(2,jw,iw)
7184                 surf_usm_h%thickness_green(m)  = usm_val(2,jw,iw)
7185              ENDIF
7186              surf_usm_h%surface_types(m) = usm_par(5,jw,iw)
7187              surf_usm_h%albedo(:,m)   = usm_val(1,jw,iw)
7188              surf_usm_h%transmissivity(m)    = 0.0_wp
7189           ENDIF
7190!
7191!--        Find the type position
7192           it = surf_usm_h%surface_types(m)
7193           ip = -99999
7194           DO k = 1, n_surface_types
7195              IF ( surface_type_codes(k) == it )  THEN
7196                 ip = k
7197                 EXIT
7198              ENDIF
7199           ENDDO
7200           IF ( ip == -99999 )  THEN
7201!
7202!--           land/roof category not found
7203              WRITE (9,"(A,I5,A,3I5)") 'land/roof category ', it,     &
7204                                       ' not found  for i,j,k=', iw,jw,kw
7205              FLUSH(9)
7206              IF ( surf_usm_h%isroof_surf(m) ) THEN
7207                 category = roof_category
7208              ELSE
7209                 category = land_category
7210              ENDIF
7211              DO k = 1, n_surface_types
7212                 IF ( surface_type_codes(k) == roof_category ) THEN
7213                    ip = k
7214                    EXIT
7215                 ENDIF
7216              ENDDO
7217              IF ( ip == -99999 )  THEN
7218!
7219!--              default land/roof category not found
7220                 WRITE (9,"(A,I5,A,3I5)") 'Default land/roof category', category, ' not found!'
7221                 FLUSH(9)
7222                 ip = 1
7223              ENDIF
7224           ENDIF
7225!
7226!--        Albedo
7227           IF ( surf_usm_h%albedo(ind_veg_wall,m) < 0.0_wp )  THEN
7228              surf_usm_h%albedo(:,m) = surface_params(ialbedo,ip)
7229           ENDIF
7230!
7231!--        Albedo type is 0 (custom), others are replaced later
7232           surf_usm_h%albedo_type(:,m) = 0
7233!
7234!--        Transmissivity
7235           IF ( surf_usm_h%transmissivity(m) < 0.0_wp )  THEN
7236              surf_usm_h%transmissivity(m) = 0.0_wp
7237           ENDIF
7238!
7239!--        emissivity of the wall
7240           surf_usm_h%emissivity(:,m) = surface_params(iemiss,ip)
7241!           
7242!--        heat conductivity λS between air and wall ( W m−2 K−1 )
7243           surf_usm_h%lambda_surf(m) = surface_params(ilambdas,ip)
7244           surf_usm_h%lambda_surf_window(m) = surface_params(ilambdas,ip)
7245           surf_usm_h%lambda_surf_green(m)  = surface_params(ilambdas,ip)
7246!           
7247!--        roughness length for momentum, heat and humidity
7248           surf_usm_h%z0(m) = surface_params(irough,ip)
7249           surf_usm_h%z0h(m) = surface_params(iroughh,ip)
7250           surf_usm_h%z0q(m) = surface_params(iroughh,ip)
7251!
7252!--        Surface skin layer heat capacity (J m−2 K−1 )
7253           surf_usm_h%c_surface(m) = surface_params(icsurf,ip)
7254           surf_usm_h%c_surface_window(m) = surface_params(icsurf,ip)
7255           surf_usm_h%c_surface_green(m)  = surface_params(icsurf,ip)
7256!           
7257!--        wall material parameters:
7258!--        thickness of the wall (m)
7259!--        missing values are replaced by default value for category
7260           IF ( surf_usm_h%thickness_wall(m) <= 0.001_wp )  THEN
7261                surf_usm_h%thickness_wall(m) = surface_params(ithick,ip)
7262           ENDIF
7263           IF ( surf_usm_h%thickness_window(m) <= 0.001_wp )  THEN
7264                surf_usm_h%thickness_window(m) = surface_params(ithick,ip)
7265           ENDIF
7266           IF ( surf_usm_h%thickness_green(m) <= 0.001_wp )  THEN
7267                surf_usm_h%thickness_green(m) = surface_params(ithick,ip)
7268           ENDIF
7269!           
7270!--        volumetric heat capacity rho*C of the wall ( J m−3 K−1 )
7271           surf_usm_h%rho_c_wall(:,m) = surface_params(irhoC,ip)
7272           surf_usm_h%rho_c_window(:,m) = surface_params(irhoC,ip)
7273           surf_usm_h%rho_c_green(:,m)  = surface_params(irhoC,ip)
7274!           
7275!--        thermal conductivity λH of the wall (W m−1 K−1 )
7276           surf_usm_h%lambda_h(:,m) = surface_params(ilambdah,ip)
7277           surf_usm_h%lambda_h_window(:,m) = surface_params(ilambdah,ip)
7278           surf_usm_h%lambda_h_green(:,m)  = surface_params(ilambdah,ip)
7279
7280        ENDDO
7281!
7282!--     For vertical surface elements ( 0 -- northward-facing, 1 -- southward-facing,
7283!--     2 -- eastward-facing, 3 -- westward-facing )
7284        DO  l = 0, 3
7285!
7286!--        Set flag indicating that albedo is initialized via ASCII format.
7287!--        Else it would be overwritten in the radiation model.
7288           surf_usm_v(l)%albedo_from_ascii = .TRUE.
7289           DO  m = 1, surf_usm_v(l)%ns
7290              i  = surf_usm_v(l)%i(m)
7291              j  = surf_usm_v(l)%j(m)
7292              kw = surf_usm_v(l)%k(m)
7293             
7294              IF ( l == 3 )  THEN ! westward facing
7295                 iw = i
7296                 jw = j
7297                 ii = 6
7298                 ij = 3
7299              ELSEIF ( l == 2 )  THEN
7300                 iw = i-1
7301                 jw = j
7302                 ii = 6
7303                 ij = 3
7304              ELSEIF ( l == 1 )  THEN
7305                 iw = i
7306                 jw = j
7307                 ii = 12
7308                 ij = 9
7309              ELSEIF ( l == 0 )  THEN
7310                 iw = i
7311                 jw = j-1
7312                 ii = 12
7313                 ij = 9
7314              ENDIF
7315
7316              IF ( iw < 0 .OR. jw < 0 ) THEN
7317!
7318!--              wall on west or south border of the domain - assign default category
7319                 IF ( kw <= roof_height_limit ) THEN
7320                     surf_usm_v(l)%surface_types(m) = wall_category   !< default category for wall surface in wall zone
7321                 ELSE
7322                     surf_usm_v(l)%surface_types(m) = roof_category   !< default category for wall surface in roof zone
7323                 END IF
7324                 surf_usm_v(l)%albedo(:,m)         = -1.0_wp
7325                 surf_usm_v(l)%thickness_wall(m)   = -1.0_wp
7326                 surf_usm_v(l)%thickness_window(m) = -1.0_wp
7327                 surf_usm_v(l)%thickness_green(m)  = -1.0_wp
7328                 surf_usm_v(l)%transmissivity(m)   = -1.0_wp
7329              ELSE IF ( kw <= usm_par(ii,jw,iw) )  THEN
7330!
7331!--                 pedestrian zone
7332                 IF ( usm_par(ii+1,jw,iw) == 0 )  THEN
7333                     surf_usm_v(l)%surface_types(m)  = pedestrian_category   !< default category for wall surface in
7334                                                                             !<pedestrian zone
7335                     surf_usm_v(l)%albedo(:,m)         = -1.0_wp
7336                     surf_usm_v(l)%thickness_wall(m)   = -1.0_wp
7337                     surf_usm_v(l)%thickness_window(m) = -1.0_wp
7338                     surf_usm_v(l)%thickness_green(m)  = -1.0_wp
7339                     surf_usm_v(l)%transmissivity(m)   = -1.0_wp
7340                 ELSE
7341                     surf_usm_v(l)%surface_types(m)    = usm_par(ii+1,jw,iw)
7342                     surf_usm_v(l)%albedo(:,m)         = usm_val(ij,jw,iw)
7343                     surf_usm_v(l)%thickness_wall(m)   = usm_val(ij+1,jw,iw)
7344                     surf_usm_v(l)%thickness_window(m) = usm_val(ij+1,jw,iw)
7345                     surf_usm_v(l)%thickness_green(m)  = usm_val(ij+1,jw,iw)
7346                     surf_usm_v(l)%transmissivity(m)   = 0.0_wp
7347                 ENDIF
7348              ELSE IF ( kw <= usm_par(ii+2,jw,iw) )  THEN
7349!
7350!--              wall zone
7351                 IF ( usm_par(ii+3,jw,iw) == 0 )  THEN
7352                     surf_usm_v(l)%surface_types(m)    = wall_category         !< default category for wall surface
7353                     surf_usm_v(l)%albedo(:,m)         = -1.0_wp
7354                     surf_usm_v(l)%thickness_wall(m)   = -1.0_wp
7355                     surf_usm_v(l)%thickness_window(m) = -1.0_wp
7356                     surf_usm_v(l)%thickness_green(m)  = -1.0_wp
7357                     surf_usm_v(l)%transmissivity(m)   = -1.0_wp
7358                 ELSE
7359                     surf_usm_v(l)%surface_types(m)    = usm_par(ii+3,jw,iw)
7360                     surf_usm_v(l)%albedo(:,m)         = usm_val(ij+2,jw,iw)
7361                     surf_usm_v(l)%thickness_wall(m)   = usm_val(ij+3,jw,iw)
7362                     surf_usm_v(l)%thickness_window(m) = usm_val(ij+3,jw,iw)
7363                     surf_usm_v(l)%thickness_green(m)  = usm_val(ij+3,jw,iw)
7364                     surf_usm_v(l)%transmissivity(m)   = 0.0_wp
7365                 ENDIF
7366              ELSE IF ( kw <= usm_par(ii+4,jw,iw) )  THEN
7367!
7368!--              roof zone
7369                 IF ( usm_par(ii+5,jw,iw) == 0 )  THEN
7370                     surf_usm_v(l)%surface_types(m)    = roof_category         !< default category for roof surface
7371                     surf_usm_v(l)%albedo(:,m)         = -1.0_wp
7372                     surf_usm_v(l)%thickness_wall(m)   = -1.0_wp
7373                     surf_usm_v(l)%thickness_window(m) = -1.0_wp
7374                     surf_usm_v(l)%thickness_green(m)  = -1.0_wp
7375                     surf_usm_v(l)%transmissivity(m)   = -1.0_wp
7376                 ELSE
7377                     surf_usm_v(l)%surface_types(m)    = usm_par(ii+5,jw,iw)
7378                     surf_usm_v(l)%albedo(:,m)         = usm_val(ij+4,jw,iw)
7379                     surf_usm_v(l)%thickness_wall(m)   = usm_val(ij+5,jw,iw)
7380                     surf_usm_v(l)%thickness_window(m) = usm_val(ij+5,jw,iw)
7381                     surf_usm_v(l)%thickness_green(m)  = usm_val(ij+5,jw,iw)
7382                     surf_usm_v(l)%transmissivity(m)   = 0.0_wp
7383                 ENDIF
7384              ELSE
7385                 WRITE(9,*) 'Problem reading USM data:'
7386                 WRITE(9,*) l,i,j,kw,get_topography_top_index_ji( j, i, 's' )
7387                 WRITE(9,*) ii,iw,jw,kw,get_topography_top_index_ji( jw, iw, 's' )
7388                 WRITE(9,*) usm_par(ii,jw,iw),usm_par(ii+1,jw,iw)
7389                 WRITE(9,*) usm_par(ii+2,jw,iw),usm_par(ii+3,jw,iw)
7390                 WRITE(9,*) usm_par(ii+4,jw,iw),usm_par(ii+5,jw,iw)
7391                 WRITE(9,*) kw,roof_height_limit,wall_category,roof_category
7392                 FLUSH(9)
7393!
7394!--              supply the default category
7395                 IF ( kw <= roof_height_limit ) THEN
7396                     surf_usm_v(l)%surface_types(m) = wall_category   !< default category for wall surface in wall zone
7397                 ELSE
7398                     surf_usm_v(l)%surface_types(m) = roof_category   !< default category for wall surface in roof zone
7399                 END IF
7400                 surf_usm_v(l)%albedo(:,m)         = -1.0_wp
7401                 surf_usm_v(l)%thickness_wall(m)   = -1.0_wp
7402                 surf_usm_v(l)%thickness_window(m) = -1.0_wp
7403                 surf_usm_v(l)%thickness_green(m)  = -1.0_wp
7404                 surf_usm_v(l)%transmissivity(m)   = -1.0_wp
7405              ENDIF
7406!
7407!--           Find the type position
7408              it = surf_usm_v(l)%surface_types(m)
7409              ip = -99999
7410              DO k = 1, n_surface_types
7411                 IF ( surface_type_codes(k) == it )  THEN
7412                    ip = k
7413                    EXIT
7414                 ENDIF
7415              ENDDO
7416              IF ( ip == -99999 )  THEN
7417!
7418!--              wall category not found
7419                 WRITE (9, "(A,I7,A,3I5)") 'wall category ', it,  &
7420                                           ' not found  for i,j,k=', iw,jw,kw
7421                 FLUSH(9)
7422                 category = wall_category 
7423                 DO k = 1, n_surface_types
7424                    IF ( surface_type_codes(k) == category ) THEN
7425                       ip = k
7426                       EXIT
7427                    ENDIF
7428                 ENDDO
7429                 IF ( ip == -99999 )  THEN
7430!
7431!--                 default wall category not found
7432                    WRITE (9, "(A,I5,A,3I5)") 'Default wall category', category, ' not found!'
7433                    FLUSH(9)
7434                    ip = 1
7435                 ENDIF
7436              ENDIF
7437
7438!
7439!--           Albedo
7440              IF ( surf_usm_v(l)%albedo(ind_veg_wall,m) < 0.0_wp )  THEN
7441                 surf_usm_v(l)%albedo(:,m) = surface_params(ialbedo,ip)
7442              ENDIF
7443!--           Albedo type is 0 (custom), others are replaced later
7444              surf_usm_v(l)%albedo_type(:,m) = 0
7445!--           Transmissivity of the windows
7446              IF ( surf_usm_v(l)%transmissivity(m) < 0.0_wp )  THEN
7447                 surf_usm_v(l)%transmissivity(m) = 0.0_wp
7448              ENDIF
7449!
7450!--           emissivity of the wall
7451              surf_usm_v(l)%emissivity(:,m) = surface_params(iemiss,ip)
7452!           
7453!--           heat conductivity lambda S between air and wall ( W m-2 K-1 )
7454              surf_usm_v(l)%lambda_surf(m) = surface_params(ilambdas,ip)
7455              surf_usm_v(l)%lambda_surf_window(m) = surface_params(ilambdas,ip)
7456              surf_usm_v(l)%lambda_surf_green(m) = surface_params(ilambdas,ip)
7457!           
7458!--           roughness length
7459              surf_usm_v(l)%z0(m) = surface_params(irough,ip)
7460              surf_usm_v(l)%z0h(m) = surface_params(iroughh,ip)
7461              surf_usm_v(l)%z0q(m) = surface_params(iroughh,ip)
7462!           
7463!--           Surface skin layer heat capacity (J m-2 K-1 )
7464              surf_usm_v(l)%c_surface(m) = surface_params(icsurf,ip)
7465              surf_usm_v(l)%c_surface_window(m) = surface_params(icsurf,ip)
7466              surf_usm_v(l)%c_surface_green(m) = surface_params(icsurf,ip)
7467!           
7468!--           wall material parameters:
7469!--           thickness of the wall (m)
7470!--           missing values are replaced by default value for category
7471              IF ( surf_usm_v(l)%thickness_wall(m) <= 0.001_wp )  THEN
7472                   surf_usm_v(l)%thickness_wall(m) = surface_params(ithick,ip)
7473              ENDIF
7474              IF ( surf_usm_v(l)%thickness_window(m) <= 0.001_wp )  THEN
7475                   surf_usm_v(l)%thickness_window(m) = surface_params(ithick,ip)
7476              ENDIF
7477              IF ( surf_usm_v(l)%thickness_green(m) <= 0.001_wp )  THEN
7478                   surf_usm_v(l)%thickness_green(m) = surface_params(ithick,ip)
7479              ENDIF
7480!
7481!--           volumetric heat capacity rho*C of the wall ( J m-3 K-1 )
7482              surf_usm_v(l)%rho_c_wall(:,m) = surface_params(irhoC,ip)
7483              surf_usm_v(l)%rho_c_window(:,m) = surface_params(irhoC,ip)
7484              surf_usm_v(l)%rho_c_green(:,m) = surface_params(irhoC,ip)
7485!           
7486!--           thermal conductivity lambda H of the wall (W m-1 K-1 )
7487              surf_usm_v(l)%lambda_h(:,m) = surface_params(ilambdah,ip)
7488              surf_usm_v(l)%lambda_h_window(:,m) = surface_params(ilambdah,ip)
7489              surf_usm_v(l)%lambda_h_green(:,m) = surface_params(ilambdah,ip)
7490
7491           ENDDO
7492        ENDDO 
7493
7494!
7495!--     Initialize wall layer thicknesses. Please note, this will be removed
7496!--     after migration to Palm input data standard. 
7497        DO k = nzb_wall, nzt_wall
7498           zwn(k) = zwn_default(k)
7499           zwn_green(k) = zwn_default_green(k)
7500           zwn_window(k) = zwn_default_window(k)
7501        ENDDO
7502!
7503!--     apply for all particular surface grids. First for horizontal surfaces
7504        DO  m = 1, surf_usm_h%ns
7505           surf_usm_h%zw(:,m) = zwn(:) * surf_usm_h%thickness_wall(m)
7506           surf_usm_h%zw_green(:,m) = zwn_green(:) * surf_usm_h%thickness_green(m)
7507           surf_usm_h%zw_window(:,m) = zwn_window(:) * surf_usm_h%thickness_window(m)
7508        ENDDO
7509        DO  l = 0, 3
7510           DO  m = 1, surf_usm_v(l)%ns
7511              surf_usm_v(l)%zw(:,m) = zwn(:) * surf_usm_v(l)%thickness_wall(m)
7512              surf_usm_v(l)%zw_green(:,m) = zwn_green(:) * surf_usm_v(l)%thickness_green(m)
7513              surf_usm_v(l)%zw_window(:,m) = zwn_window(:) * surf_usm_v(l)%thickness_window(m)
7514           ENDDO
7515        ENDDO
7516
7517        IF ( debug_output )  CALL debug_message( 'usm_read_urban_surface_types', 'end' )
7518   
7519    END SUBROUTINE usm_read_urban_surface_types
7520
7521
7522!------------------------------------------------------------------------------!
7523! Description:
7524! ------------
7525!
7526!> This function advances through the list of local surfaces to find given
7527!> x, y, d, z coordinates
7528!------------------------------------------------------------------------------!
7529    PURE FUNCTION find_surface( x, y, z, d ) result(isurfl)
7530
7531        INTEGER(iwp), INTENT(in)                :: x, y, z, d
7532        INTEGER(iwp)                            :: isurfl
7533        INTEGER(iwp)                            :: isx, isy, isz
7534
7535        IF ( d == 0 ) THEN
7536           DO  isurfl = 1, surf_usm_h%ns
7537              isx = surf_usm_h%i(isurfl)
7538              isy = surf_usm_h%j(isurfl)
7539              isz = surf_usm_h%k(isurfl)
7540              IF ( isx==x .and. isy==y .and. isz==z )  RETURN
7541           ENDDO
7542        ELSE
7543           DO  isurfl = 1, surf_usm_v(d-1)%ns
7544              isx = surf_usm_v(d-1)%i(isurfl)
7545              isy = surf_usm_v(d-1)%j(isurfl)
7546              isz = surf_usm_v(d-1)%k(isurfl)
7547              IF ( isx==x .and. isy==y .and. isz==z )  RETURN
7548           ENDDO
7549        ENDIF
7550!
7551!--     coordinate not found
7552        isurfl = -1
7553
7554    END FUNCTION
7555
7556
7557!------------------------------------------------------------------------------!
7558! Description:
7559! ------------
7560!
7561!> This subroutine reads temperatures of respective material layers in walls,
7562!> roofs and ground from input files. Data in the input file must be in
7563!> standard order, i.e. horizontal surfaces first ordered by x, y and then
7564!> vertical surfaces ordered by x, y, direction, z
7565!------------------------------------------------------------------------------!
7566    SUBROUTINE usm_read_wall_temperature
7567
7568        INTEGER(iwp)                                          :: i, j, k, d, ii, iline  !> running indices
7569        INTEGER(iwp)                                          :: isurfl
7570        REAL(wp)                                              :: rtsurf
7571        REAL(wp), DIMENSION(nzb_wall:nzt_wall+1)              :: rtwall
7572
7573
7574        IF ( debug_output )  CALL debug_message( 'usm_read_wall_temperature', 'start' )
7575
7576        DO  ii = 0, io_blocks-1
7577            IF ( ii == io_group )  THEN
7578!
7579!--             open wall temperature file
7580                OPEN( 152, file='WALL_TEMPERATURE'//coupling_char, action='read', &
7581                           status='old', form='formatted', err=15 )
7582
7583                isurfl = 0
7584                iline = 1
7585                DO
7586                    rtwall = -9999.0_wp  !< for incomplete lines
7587                    READ( 152, *, err=13, end=14 )  i, j, k, d, rtsurf, rtwall
7588
7589                    IF ( nxl <= i .and. i <= nxr .and. &
7590                        nys <= j .and. j <= nyn)  THEN  !< local processor
7591!--                     identify surface id
7592                        isurfl = find_surface( i, j, k, d )
7593                        IF ( isurfl == -1 )  THEN
7594                            WRITE(message_string, '(a,4i5,a,i5,a)') 'Coordinates (xyzd) ', i, j, k, d, &
7595                                ' on line ', iline, &
7596                                ' in file WALL_TEMPERATURE are either not present or out of standard order of surfaces.'
7597                            CALL message( 'usm_read_wall_temperature', 'PA0521', 1, 2, 0, 6, 0 )
7598                        ENDIF
7599!
7600!--                     assign temperatures
7601                        IF ( d == 0 ) THEN
7602                           t_surf_wall_h(isurfl) = rtsurf
7603                           t_wall_h(:,isurfl) = rtwall(:)
7604                           t_window_h(:,isurfl) = rtwall(:)
7605                           t_green_h(:,isurfl) = rtwall(:)
7606                        ELSE
7607                           t_surf_wall_v(d-1)%t(isurfl) = rtsurf
7608                           t_wall_v(d-1)%t(:,isurfl) = rtwall(:)
7609                           t_window_v(d-1)%t(:,isurfl) = rtwall(:)
7610                           t_green_v(d-1)%t(:,isurfl) = rtwall(:)
7611                        ENDIF
7612                    ENDIF
7613
7614                    iline = iline + 1
7615                    CYCLE
7616 13                 WRITE(message_string, '(a,i5,a)') 'Error reading line ', iline, &
7617                        ' in file WALL_TEMPERATURE.'
7618                    CALL message( 'usm_read_wall_temperature', 'PA0522', 1, 2, 0, 6, 0 )
7619                ENDDO
7620 14             CLOSE(152)
7621                CYCLE
7622 15             message_string = 'file WALL_TEMPERATURE'//TRIM(coupling_char)//' does not exist'
7623                CALL message( 'usm_read_wall_temperature', 'PA0523', 1, 2, 0, 6, 0 )
7624            ENDIF
7625#if defined( __parallel )
7626            CALL MPI_BARRIER( comm2d, ierr )
7627#endif
7628        ENDDO
7629
7630        IF ( debug_output )  CALL debug_message( 'usm_read_wall_temperature', 'end' )
7631
7632    END SUBROUTINE usm_read_wall_temperature
7633
7634
7635
7636!------------------------------------------------------------------------------!
7637! Description:
7638! ------------
7639!> Solver for the energy balance at the ground/roof/wall surface.
7640!> It follows basic ideas and structure of lsm_energy_balance
7641!> with many simplifications and adjustments.
7642!> TODO better description
7643!> No calculation of window surface temperatures during spinup to increase
7644!> maximum possible timstep
7645!------------------------------------------------------------------------------!
7646    SUBROUTINE usm_surface_energy_balance( spinup )
7647
7648
7649        IMPLICIT NONE
7650
7651        INTEGER(iwp)                          :: i, j, k, l, m   !< running indices
7652       
7653        INTEGER(iwp) ::  i_off     !< offset to determine index of surface element, seen from atmospheric grid point, for x
7654        INTEGER(iwp) ::  j_off     !< offset to determine index of surface element, seen from atmospheric grid point, for y
7655        INTEGER(iwp) ::  k_off     !< offset to determine index of surface element, seen from atmospheric grid point, for z
7656
7657        LOGICAL                               :: spinup             !true during spinup
7658       
7659        REAL(wp)                              :: frac_win           !< window fraction, used to restore original values during spinup
7660        REAL(wp)                              :: frac_green         !< green fraction, used to restore original values during spinup
7661        REAL(wp)                              :: frac_wall          !< wall fraction, used to restore original values during spinup
7662        REAL(wp)                              :: stend_wall         !< surface tendency
7663       
7664        REAL(wp)                              :: stend_window       !< surface tendency
7665        REAL(wp)                              :: stend_green        !< surface tendency
7666        REAL(wp)                              :: coef_1             !< first coeficient for prognostic equation
7667        REAL(wp)                              :: coef_window_1      !< first coeficient for prognostic window equation
7668        REAL(wp)                              :: coef_green_1       !< first coeficient for prognostic green wall equation
7669        REAL(wp)                              :: coef_2             !< second  coeficient for prognostic equation
7670        REAL(wp)                              :: coef_window_2      !< second  coeficient for prognostic window equation
7671        REAL(wp)                              :: coef_green_2       !< second  coeficient for prognostic green wall equation
7672        REAL(wp)                              :: rho_cp             !< rho_wall_surface * c_p
7673        REAL(wp)                              :: f_shf              !< factor for shf_eb
7674        REAL(wp)                              :: f_shf_window       !< factor for shf_eb window
7675        REAL(wp)                              :: f_shf_green        !< factor for shf_eb green wall
7676        REAL(wp)                              :: lambda_surface     !< current value of lambda_surface (heat conductivity
7677                                                                    !<between air and wall)
7678        REAL(wp)                              :: lambda_surface_window  !< current value of lambda_surface (heat conductivity
7679                                                                        !< between air and window)
7680        REAL(wp)                              :: lambda_surface_green   !< current value of lambda_surface (heat conductivity
7681                                                                        !< between air and greeb wall)
7682       
7683        REAL(wp)                              :: dtime              !< simulated time of day (in UTC)
7684        INTEGER(iwp)                          :: dhour              !< simulated hour of day (in UTC)
7685        REAL(wp)                              :: acoef              !< actual coefficient of diurnal profile of anthropogenic heat
7686        REAL(wp) ::  f1,          &  !< resistance correction term 1
7687                     f2,          &  !< resistance correction term 2
7688                     f3,          &  !< resistance correction term 3
7689                     e,           &  !< water vapour pressure
7690                     e_s,         &  !< water vapour saturation pressure
7691                     e_s_dt,      &  !< derivate of e_s with respect to T
7692                     tend,        &  !< tendency
7693                     dq_s_dt,     &  !< derivate of q_s with respect to T
7694                     f_qsws,      &  !< factor for qsws
7695                     f_qsws_veg,  &  !< factor for qsws_veg
7696                     f_qsws_liq,  &  !< factor for qsws_liq
7697                     m_liq_max,   &  !< maxmimum value of the liq. water reservoir
7698                     qv1,         &  !< specific humidity at first grid level
7699                     m_max_depth = 0.0002_wp, &  !< Maximum capacity of the water reservoir (m)
7700                     rho_lv,      &  !< frequently used parameter for green layers
7701                     drho_l_lv,   &  !< frequently used parameter for green layers
7702                     q_s             !< saturation specific humidity
7703
7704
7705        IF ( debug_output )  THEN
7706           WRITE( debug_string, * ) 'usm_surface_energy_balance | spinup: ', spinup
7707           CALL debug_message( debug_string, 'start' )
7708        ENDIF
7709!
7710!--     Index offset of surface element point with respect to adjoining
7711!--     atmospheric grid point
7712        k_off = surf_usm_h%koff
7713        j_off = surf_usm_h%joff
7714        i_off = surf_usm_h%ioff
7715       
7716!       
7717!--     First, treat horizontal surface elements
7718        !$OMP PARALLEL PRIVATE (m, i, j, k, lambda_surface, lambda_surface_window,                 &
7719        !$OMP&                  lambda_surface_green, qv1, rho_cp, rho_lv, drho_l_lv, f_shf,       &
7720        !$OMP&                  f_shf_window, f_shf_green, m_total, f1, f2, e_s, e, f3, f_qsws_veg,&
7721        !$OMP&                  q_s, f_qsws_liq, f_qsws, e_s_dt, dq_s_dt, coef_1, coef_window_1,   &
7722        !$OMP&                  coef_green_1, coef_2, coef_window_2, coef_green_2, stend_wall,     &
7723        !$OMP&                  stend_window, stend_green, tend, m_liq_max)
7724        !$OMP DO SCHEDULE (STATIC)
7725        DO  m = 1, surf_usm_h%ns
7726!
7727!--       During spinup set green and window fraction to zero and restore
7728!--       at the end of the loop.
7729!--       Note, this is a temporary fix and need to be removed later. 
7730           IF ( spinup )  THEN
7731              frac_win   = surf_usm_h%frac(ind_wat_win,m)
7732              frac_wall  = surf_usm_h%frac(ind_veg_wall,m)
7733              frac_green = surf_usm_h%frac(ind_pav_green,m)
7734              surf_usm_h%frac(ind_wat_win,m)   = 0.0_wp
7735              surf_usm_h%frac(ind_veg_wall,m)  = 1.0_wp
7736              surf_usm_h%frac(ind_pav_green,m) = 0.0_wp
7737           ENDIF
7738!
7739!--        Get indices of respective grid point
7740           i = surf_usm_h%i(m)
7741           j = surf_usm_h%j(m)
7742           k = surf_usm_h%k(m)
7743!
7744!--        TODO - how to calculate lambda_surface for horizontal surfaces
7745!--        (lambda_surface is set according to stratification in land surface model)
7746!--        MS: ???
7747           IF ( surf_usm_h%ol(m) >= 0.0_wp )  THEN
7748              lambda_surface = surf_usm_h%lambda_surf(m)
7749              lambda_surface_window = surf_usm_h%lambda_surf_window(m)
7750              lambda_surface_green = surf_usm_h%lambda_surf_green(m)
7751           ELSE
7752              lambda_surface = surf_usm_h%lambda_surf(m)
7753              lambda_surface_window = surf_usm_h%lambda_surf_window(m)
7754              lambda_surface_green = surf_usm_h%lambda_surf_green(m)
7755           ENDIF
7756
7757!            pt1  = pt(k,j,i)
7758           IF ( humidity )  THEN
7759              qv1 = q(k,j,i)
7760           ELSE
7761              qv1 = 0.0_wp
7762           ENDIF
7763!
7764!--        calculate rho * c_p coefficient at surface layer
7765           rho_cp  = c_p * hyp(k) / ( r_d * surf_usm_h%pt1(m) * exner(k) )
7766
7767           IF ( surf_usm_h%frac(ind_pav_green,m) > 0.0_wp )  THEN
7768!
7769!--           Calculate frequently used parameters
7770              rho_lv    = rho_cp / c_p * l_v
7771              drho_l_lv = 1.0_wp / (rho_l * l_v)
7772           ENDIF
7773
7774!
7775!--        Calculate aerodyamic resistance.
7776!--        Calculation for horizontal surfaces follows LSM formulation
7777!--        pt, us, ts are not available for the prognostic time step,
7778!--        data from the last time step is used here.
7779!
7780!--        Workaround: use single r_a as stability is only treated for the
7781!--        average temperature
7782           surf_usm_h%r_a(m) = ( surf_usm_h%pt1(m) - surf_usm_h%pt_surface(m) ) /&
7783                               ( surf_usm_h%ts(m) * surf_usm_h%us(m) + 1.0E-20_wp )   
7784           surf_usm_h%r_a_window(m) = surf_usm_h%r_a(m)
7785           surf_usm_h%r_a_green(m)  = surf_usm_h%r_a(m)
7786
7787!            r_a = ( surf_usm_h%pt1(m) - t_surf_h(m) / exner(k) ) /                              &
7788!                  ( surf_usm_h%ts(m) * surf_usm_h%us(m) + 1.0E-20_wp )
7789!            r_a_window = ( surf_usm_h%pt1(m) - t_surf_window_h(m) / exner(k) ) /                &
7790!                  ( surf_usm_h%ts(m) * surf_usm_h%us(m) + 1.0E-20_wp )
7791!            r_a_green = ( surf_usm_h%pt1(m) - t_surf_green_h(m) / exner(k) ) /                  &
7792!                  ( surf_usm_h%ts(m) * surf_usm_h%us(m) + 1.0E-20_wp )
7793               
7794!--        Make sure that the resistance does not drop to zero
7795           IF ( surf_usm_h%r_a(m)        < 1.0_wp )                            &
7796               surf_usm_h%r_a(m)        = 1.0_wp
7797           IF ( surf_usm_h%r_a_green(m)  < 1.0_wp )                            &
7798               surf_usm_h%r_a_green(m)  = 1.0_wp
7799           IF ( surf_usm_h%r_a_window(m) < 1.0_wp )                            &
7800               surf_usm_h%r_a_window(m) = 1.0_wp
7801             
7802!
7803!--        Make sure that the resistacne does not exceed a maxmium value in case
7804!--        of zero velocities
7805           IF ( surf_usm_h%r_a(m)        > 300.0_wp )                          &
7806               surf_usm_h%r_a(m)        = 300.0_wp
7807           IF ( surf_usm_h%r_a_green(m)  > 300.0_wp )                          &
7808               surf_usm_h%r_a_green(m)  = 300.0_wp
7809           IF ( surf_usm_h%r_a_window(m) > 300.0_wp )                          &
7810               surf_usm_h%r_a_window(m) = 300.0_wp               
7811               
7812!
7813!--        factor for shf_eb
7814           f_shf  = rho_cp / surf_usm_h%r_a(m)
7815           f_shf_window  = rho_cp / surf_usm_h%r_a_window(m)
7816           f_shf_green  = rho_cp / surf_usm_h%r_a_green(m)
7817       
7818
7819           IF ( surf_usm_h%frac(ind_pav_green,m) > 0.0_wp ) THEN
7820!--           Adapted from LSM:
7821!--           Second step: calculate canopy resistance r_canopy
7822!--           f1-f3 here are defined as 1/f1-f3 as in ECMWF documentation
7823 
7824!--           f1: correction for incoming shortwave radiation (stomata close at
7825!--           night)
7826              f1 = MIN( 1.0_wp, ( 0.004_wp * surf_usm_h%rad_sw_in(m) + 0.05_wp ) / &
7827                               (0.81_wp * (0.004_wp * surf_usm_h%rad_sw_in(m)      &
7828                                + 1.0_wp)) )
7829!
7830!--           f2: correction for soil moisture availability to plants (the
7831!--           integrated soil moisture must thus be considered here)
7832!--           f2 = 0 for very dry soils
7833              m_total = 0.0_wp
7834              DO  k = nzb_wall, nzt_wall+1
7835                  m_total = m_total + rootfr_h(nzb_wall,m)                              &
7836                            * MAX(swc_h(nzb_wall,m),wilt_h(nzb_wall,m))
7837              ENDDO 
7838   
7839              IF ( m_total > wilt_h(nzb_wall,m)  .AND.  m_total < fc_h(nzb_wall,m) )  THEN
7840                 f2 = ( m_total - wilt_h(nzb_wall,m) ) / (fc_h(nzb_wall,m) - wilt_h(nzb_wall,m) )
7841              ELSEIF ( m_total >= fc_h(nzb_wall,m) )  THEN
7842                 f2 = 1.0_wp
7843              ELSE
7844                 f2 = 1.0E-20_wp
7845              ENDIF
7846       
7847!
7848!--          Calculate water vapour pressure at saturation
7849              e_s = 0.01_wp * 610.78_wp * EXP( 17.269_wp * ( t_surf_green_h(m) &
7850                            - 273.16_wp ) / ( t_surf_green_h(m) - 35.86_wp ) )
7851!
7852!--           f3: correction for vapour pressure deficit
7853              IF ( surf_usm_h%g_d(m) /= 0.0_wp )  THEN
7854!
7855!--           Calculate vapour pressure
7856                 e  = qv1 * surface_pressure / ( qv1 + 0.622_wp )
7857                 f3 = EXP ( - surf_usm_h%g_d(m) * (e_s - e) )
7858              ELSE
7859                 f3 = 1.0_wp
7860              ENDIF
7861
7862!
7863!--           Calculate canopy resistance. In case that c_veg is 0 (bare soils),
7864!--           this calculation is obsolete, as r_canopy is not used below.
7865!--           To do: check for very dry soil -> r_canopy goes to infinity
7866              surf_usm_h%r_canopy(m) = surf_usm_h%r_canopy_min(m) /                   &
7867                              ( surf_usm_h%lai(m) * f1 * f2 * f3 + 1.0E-20_wp )
7868
7869!
7870!--           Calculate the maximum possible liquid water amount on plants and
7871!--           bare surface. For vegetated surfaces, a maximum depth of 0.2 mm is
7872!--           assumed, while paved surfaces might hold up 1 mm of water. The
7873!--           liquid water fraction for paved surfaces is calculated after
7874!--           Noilhan & Planton (1989), while the ECMWF formulation is used for
7875!--           vegetated surfaces and bare soils.
7876              m_liq_max = m_max_depth * ( surf_usm_h%lai(m) )
7877              surf_usm_h%c_liq(m) = MIN( 1.0_wp, ( m_liq_usm_h%var_usm_1d(m) / m_liq_max )**0.67 )
7878!
7879!--           Calculate saturation specific humidity
7880              q_s = 0.622_wp * e_s / ( surface_pressure - e_s )
7881!
7882!--           In case of dewfall, set evapotranspiration to zero
7883!--           All super-saturated water is then removed from the air
7884              IF ( humidity  .AND.  q_s <= qv1 )  THEN
7885                 surf_usm_h%r_canopy(m) = 0.0_wp
7886              ENDIF
7887
7888!
7889!--           Calculate coefficients for the total evapotranspiration
7890!--           In case of water surface, set vegetation and soil fluxes to zero.
7891!--           For pavements, only evaporation of liquid water is possible.
7892              f_qsws_veg  = rho_lv *                                           &
7893                                ( 1.0_wp        - surf_usm_h%c_liq(m)    ) /   &
7894                                ( surf_usm_h%r_a_green(m) + surf_usm_h%r_canopy(m) )
7895              f_qsws_liq  = rho_lv * surf_usm_h%c_liq(m)   /                   &
7896                                  surf_usm_h%r_a_green(m)
7897       
7898              f_qsws = f_qsws_veg + f_qsws_liq
7899!
7900!--           Calculate derivative of q_s for Taylor series expansion
7901              e_s_dt = e_s * ( 17.269_wp / ( t_surf_green_h(m) - 35.86_wp) -   &
7902                               17.269_wp*( t_surf_green_h(m) - 273.16_wp)      &
7903                              / ( t_surf_green_h(m) - 35.86_wp)**2 )
7904       
7905              dq_s_dt = 0.622_wp * e_s_dt / ( surface_pressure - e_s_dt )
7906           ENDIF
7907!
7908!--        add LW up so that it can be removed in prognostic equation
7909           surf_usm_h%rad_net_l(m) = surf_usm_h%rad_sw_in(m)  -                &
7910                                     surf_usm_h%rad_sw_out(m) +                &
7911                                     surf_usm_h%rad_lw_in(m)  -                &
7912                                     surf_usm_h%rad_lw_out(m)
7913!
7914!--     numerator of the prognostic equation
7915!--     Todo: Adjust to tile approach. So far, emissivity for wall (element 0)
7916!--     is used
7917           coef_1 = surf_usm_h%rad_net_l(m) +                                  & 
7918                 ( 3.0_wp + 1.0_wp ) * surf_usm_h%emissivity(ind_veg_wall,m) * &
7919                                       sigma_sb * t_surf_wall_h(m) ** 4 +      & 
7920                                       f_shf * surf_usm_h%pt1(m) +             &
7921                                       lambda_surface * t_wall_h(nzb_wall,m)
7922           IF ( ( .NOT. spinup ) .AND. (surf_usm_h%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
7923              coef_window_1 = surf_usm_h%rad_net_l(m) +                           & 
7924                      ( 3.0_wp + 1.0_wp ) * surf_usm_h%emissivity(ind_wat_win,m)  &
7925                                          * sigma_sb * t_surf_window_h(m) ** 4 +  & 
7926                                          f_shf_window * surf_usm_h%pt1(m) +      &
7927                                          lambda_surface_window * t_window_h(nzb_wall,m)
7928           ENDIF                 
7929           IF ( ( humidity ) .AND. ( surf_usm_h%frac(ind_pav_green,m) > 0.0_wp ) )  THEN
7930                    coef_green_1 = surf_usm_h%rad_net_l(m) +                                 & 
7931                   ( 3.0_wp + 1.0_wp ) * surf_usm_h%emissivity(ind_pav_green,m) * sigma_sb * &
7932                                       t_surf_green_h(m) ** 4 +                  & 
7933                                          f_shf_green * surf_usm_h%pt1(m) + f_qsws * ( qv1 - q_s    &
7934                                          + dq_s_dt * t_surf_green_h(m) )        &
7935                                          +lambda_surface_green * t_green_h(nzb_wall,m)
7936           ELSE
7937           coef_green_1 = surf_usm_h%rad_net_l(m) +                            & 
7938                 ( 3.0_wp + 1.0_wp ) * surf_usm_h%emissivity(ind_pav_green,m) *&
7939                                       sigma_sb * t_surf_green_h(m) ** 4 +     & 
7940                                       f_shf_green * surf_usm_h%pt1(m) +       &
7941                                       lambda_surface_green * t_green_h(nzb_wall,m)
7942          ENDIF
7943!
7944!--        denominator of the prognostic equation
7945           coef_2 = 4.0_wp * surf_usm_h%emissivity(ind_veg_wall,m) *           &
7946                             sigma_sb * t_surf_wall_h(m) ** 3                  &
7947                           + lambda_surface + f_shf / exner(k)
7948           IF ( ( .NOT. spinup ) .AND. ( surf_usm_h%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
7949              coef_window_2 = 4.0_wp * surf_usm_h%emissivity(ind_wat_win,m) *     &
7950                                sigma_sb * t_surf_window_h(m) ** 3                &
7951                              + lambda_surface_window + f_shf_window / exner(k)
7952           ENDIF
7953           IF ( ( humidity ) .AND. ( surf_usm_h%frac(ind_pav_green,m) > 0.0_wp ) )  THEN
7954              coef_green_2 = 4.0_wp * surf_usm_h%emissivity(ind_pav_green,m) * sigma_sb *    &
7955                                t_surf_green_h(m) ** 3 + f_qsws * dq_s_dt                    &
7956                              + lambda_surface_green + f_shf_green / exner(k)
7957           ELSE
7958           coef_green_2 = 4.0_wp * surf_usm_h%emissivity(ind_pav_green,m) * sigma_sb *    &
7959                             t_surf_green_h(m) ** 3                                       &
7960                           + lambda_surface_green + f_shf_green / exner(k)
7961           ENDIF
7962!
7963!--        implicit solution when the surface layer has no heat capacity,
7964!--        otherwise use RK3 scheme.
7965           t_surf_wall_h_p(m) = ( coef_1 * dt_3d * tsc(2) +                        &
7966                             surf_usm_h%c_surface(m) * t_surf_wall_h(m) ) /        & 
7967                           ( surf_usm_h%c_surface(m) + coef_2 * dt_3d * tsc(2) ) 
7968           IF ((.NOT. spinup).AND.(surf_usm_h%frac(ind_wat_win,m) > 0.0_wp)) THEN
7969              t_surf_window_h_p(m) = ( coef_window_1 * dt_3d * tsc(2) +                        &
7970                                surf_usm_h%c_surface_window(m) * t_surf_window_h(m) ) /        & 
7971                              ( surf_usm_h%c_surface_window(m) + coef_window_2 * dt_3d * tsc(2) )
7972           ENDIF
7973           t_surf_green_h_p(m) = ( coef_green_1 * dt_3d * tsc(2) +                        &
7974                             surf_usm_h%c_surface_green(m) * t_surf_green_h(m) ) /        & 
7975                           ( surf_usm_h%c_surface_green(m) + coef_green_2 * dt_3d * tsc(2) ) 
7976!
7977!--        add RK3 term
7978           t_surf_wall_h_p(m) = t_surf_wall_h_p(m) + dt_3d * tsc(3) *         &
7979                           surf_usm_h%tt_surface_wall_m(m)
7980
7981           t_surf_window_h_p(m) = t_surf_window_h_p(m) + dt_3d * tsc(3) *     &
7982                           surf_usm_h%tt_surface_window_m(m)
7983
7984           t_surf_green_h_p(m) = t_surf_green_h_p(m) + dt_3d * tsc(3) *       &
7985                           surf_usm_h%tt_surface_green_m(m)
7986!
7987!--        Store surface temperature on pt_surface. Further, in case humidity is used
7988!--        store also vpt_surface, which is, due to the lack of moisture on roofs simply
7989!--        assumed to be the surface temperature.
7990           surf_usm_h%pt_surface(m) = ( surf_usm_h%frac(ind_veg_wall,m) * t_surf_wall_h_p(m)   &
7991                               + surf_usm_h%frac(ind_wat_win,m) * t_surf_window_h_p(m)         &
7992                               + surf_usm_h%frac(ind_pav_green,m) * t_surf_green_h_p(m) )      &
7993                               / exner(k)
7994                               
7995           IF ( humidity )  surf_usm_h%vpt_surface(m) =                        &
7996                                                   surf_usm_h%pt_surface(m)
7997!
7998!--        calculate true tendency
7999           stend_wall = ( t_surf_wall_h_p(m) - t_surf_wall_h(m) - dt_3d * tsc(3) *              &
8000                     surf_usm_h%tt_surface_wall_m(m)) / ( dt_3d  * tsc(2) )
8001           stend_window = ( t_surf_window_h_p(m) - t_surf_window_h(m) - dt_3d * tsc(3) *        &
8002                     surf_usm_h%tt_surface_window_m(m)) / ( dt_3d  * tsc(2) )
8003           stend_green = ( t_surf_green_h_p(m) - t_surf_green_h(m) - dt_3d * tsc(3) *           &
8004                     surf_usm_h%tt_surface_green_m(m)) / ( dt_3d  * tsc(2) )
8005!
8006!--        calculate t_surf tendencies for the next Runge-Kutta step
8007           IF ( timestep_scheme(1:5) == 'runge' )  THEN
8008              IF ( intermediate_timestep_count == 1 )  THEN
8009                 surf_usm_h%tt_surface_wall_m(m) = stend_wall
8010                 surf_usm_h%tt_surface_window_m(m) = stend_window
8011                 surf_usm_h%tt_surface_green_m(m) = stend_green
8012              ELSEIF ( intermediate_timestep_count <                          &
8013                        intermediate_timestep_count_max )  THEN
8014                 surf_usm_h%tt_surface_wall_m(m) = -9.5625_wp * stend_wall +       &
8015                                     5.3125_wp * surf_usm_h%tt_surface_wall_m(m)
8016                 surf_usm_h%tt_surface_window_m(m) = -9.5625_wp * stend_window +   &
8017                                     5.3125_wp * surf_usm_h%tt_surface_window_m(m)
8018                 surf_usm_h%tt_surface_green_m(m) = -9.5625_wp * stend_green +     &
8019                                     5.3125_wp * surf_usm_h%tt_surface_green_m(m)
8020              ENDIF
8021           ENDIF
8022!
8023!--        in case of fast changes in the skin temperature, it is required to
8024!--        update the radiative fluxes in order to keep the solution stable
8025           IF ( ( ( ABS( t_surf_wall_h_p(m)   - t_surf_wall_h(m) )   > 1.0_wp )   .OR. &
8026                (   ABS( t_surf_green_h_p(m)  - t_surf_green_h(m) )  > 1.0_wp )   .OR. &
8027                (   ABS( t_surf_window_h_p(m) - t_surf_window_h(m) ) > 1.0_wp ) )      &
8028                   .AND.  unscheduled_radiation_calls  )  THEN
8029              force_radiation_call_l = .TRUE.
8030           ENDIF
8031!
8032!--        calculate fluxes
8033!--        rad_net_l is never used!
8034           surf_usm_h%rad_net_l(m) = surf_usm_h%rad_net_l(m) +                           &
8035                                     surf_usm_h%frac(ind_veg_wall,m) *                   &
8036                                     sigma_sb * surf_usm_h%emissivity(ind_veg_wall,m) *  &
8037                                     ( t_surf_wall_h_p(m)**4 - t_surf_wall_h(m)**4 )     &
8038                                    + surf_usm_h%frac(ind_wat_win,m) *                   &
8039                                     sigma_sb * surf_usm_h%emissivity(ind_wat_win,m) *   &
8040                                     ( t_surf_window_h_p(m)**4 - t_surf_window_h(m)**4 ) &
8041                                    + surf_usm_h%frac(ind_pav_green,m) *                 &
8042                                     sigma_sb * surf_usm_h%emissivity(ind_pav_green,m) * &
8043                                     ( t_surf_green_h_p(m)**4 - t_surf_green_h(m)**4 )
8044
8045           surf_usm_h%wghf_eb(m)   = lambda_surface *                                    &
8046                                      ( t_surf_wall_h_p(m) - t_wall_h(nzb_wall,m) )
8047           surf_usm_h%wghf_eb_green(m)  = lambda_surface_green *                         &
8048                                          ( t_surf_green_h_p(m) - t_green_h(nzb_wall,m) )
8049           surf_usm_h%wghf_eb_window(m) = lambda_surface_window *                        &
8050                                           ( t_surf_window_h_p(m) - t_window_h(nzb_wall,m) )
8051
8052!
8053!--        ground/wall/roof surface heat flux
8054           surf_usm_h%wshf_eb(m)   = - f_shf  * ( surf_usm_h%pt1(m) - t_surf_wall_h_p(m) / exner(k) ) *          &
8055                                       surf_usm_h%frac(ind_veg_wall,m)         &
8056                                     - f_shf_window  * ( surf_usm_h%pt1(m) - t_surf_window_h_p(m) / exner(k) ) * &
8057                                       surf_usm_h%frac(ind_wat_win,m)          &
8058                                     - f_shf_green  * ( surf_usm_h%pt1(m) - t_surf_green_h_p(m) / exner(k) ) *   &
8059                                       surf_usm_h%frac(ind_pav_green,m)
8060!           
8061!--        store kinematic surface heat fluxes for utilization in other processes
8062!--        diffusion_s, surface_layer_fluxes,...
8063           surf_usm_h%shf(m) = surf_usm_h%wshf_eb(m) / c_p
8064!
8065!--        If the indoor model is applied, further add waste heat from buildings to the
8066!--        kinematic flux.
8067           IF ( indoor_model )  THEN
8068              surf_usm_h%shf(m) = surf_usm_h%shf(m) + surf_usm_h%waste_heat(m) / c_p
8069           ENDIF
8070     
8071
8072           IF (surf_usm_h%frac(ind_pav_green,m) > 0.0_wp) THEN
8073
8074              IF ( humidity )  THEN
8075                 surf_usm_h%qsws_eb(m)  = - f_qsws * ( qv1 - q_s + dq_s_dt                  &
8076                                 * t_surf_green_h(m) - dq_s_dt *               &
8077                                   t_surf_green_h_p(m) )
8078       
8079                 surf_usm_h%qsws(m) = surf_usm_h%qsws_eb(m) / rho_lv
8080       
8081                 surf_usm_h%qsws_veg(m)  = - f_qsws_veg  * ( qv1 - q_s                      &
8082                                     + dq_s_dt * t_surf_green_h(m) - dq_s_dt   &
8083                                     * t_surf_green_h_p(m) )
8084       
8085                 surf_usm_h%qsws_liq(m)  = - f_qsws_liq  * ( qv1 - q_s                      &
8086                                     + dq_s_dt * t_surf_green_h(m) - dq_s_dt   &
8087                                     * t_surf_green_h_p(m) )
8088              ENDIF
8089 
8090!
8091!--           Calculate the true surface resistance
8092              IF ( .NOT.  humidity )  THEN
8093                 surf_usm_h%r_s(m) = 1.0E10_wp
8094              ELSE
8095                 surf_usm_h%r_s(m) = - rho_lv * ( qv1 - q_s + dq_s_dt                       &
8096                                 *  t_surf_green_h(m) - dq_s_dt *              &
8097                                   t_surf_green_h_p(m) ) /                     &
8098                                   (surf_usm_h%qsws(m) + 1.0E-20)  - surf_usm_h%r_a_green(m)
8099              ENDIF
8100 
8101!
8102!--           Calculate change in liquid water reservoir due to dew fall or
8103!--           evaporation of liquid water
8104              IF ( humidity )  THEN
8105!
8106!--              If precipitation is activated, add rain water to qsws_liq
8107!--              and qsws_soil according the the vegetation coverage.
8108!--              precipitation_rate is given in mm.
8109                 IF ( precipitation )  THEN
8110
8111!
8112!--                 Add precipitation to liquid water reservoir, if possible.
8113!--                 Otherwise, add the water to soil. In case of
8114!--                 pavements, the exceeding water amount is implicitely removed
8115!--                 as runoff as qsws_soil is then not used in the soil model
8116                    IF ( m_liq_usm_h%var_usm_1d(m) /= m_liq_max )  THEN
8117                       surf_usm_h%qsws_liq(m) = surf_usm_h%qsws_liq(m)                &
8118                                        + surf_usm_h%frac(ind_pav_green,m) * prr(k+k_off,j+j_off,i+i_off)&
8119                                        * hyrho(k+k_off)                              &
8120                                        * 0.001_wp * rho_l * l_v
8121                   ENDIF
8122
8123                 ENDIF
8124
8125!
8126!--              If the air is saturated, check the reservoir water level
8127                 IF ( surf_usm_h%qsws(m) < 0.0_wp )  THEN
8128!
8129!--                 Check if reservoir is full (avoid values > m_liq_max)
8130!--                 In that case, qsws_liq goes to qsws_soil. In this
8131!--                 case qsws_veg is zero anyway (because c_liq = 1),       
8132!--                 so that tend is zero and no further check is needed
8133                    IF ( m_liq_usm_h%var_usm_1d(m) == m_liq_max )  THEN
8134!                      surf_usm_h%qsws_soil(m) = surf_usm_h%qsws_soil(m) + surf_usm_h%qsws_liq(m)
8135                       surf_usm_h%qsws_liq(m)  = 0.0_wp
8136                    ENDIF
8137
8138!
8139!--                 In case qsws_veg becomes negative (unphysical behavior),
8140!--                 let the water enter the liquid water reservoir as dew on the
8141!--                 plant
8142                    IF ( surf_usm_h%qsws_veg(m) < 0.0_wp )  THEN
8143                       surf_usm_h%qsws_liq(m) = surf_usm_h%qsws_liq(m) + surf_usm_h%qsws_veg(m)
8144                       surf_usm_h%qsws_veg(m) = 0.0_wp
8145                    ENDIF
8146                 ENDIF                   
8147 
8148                 surf_usm_h%qsws(m) = surf_usm_h%qsws(m) / l_v
8149       
8150                 tend = - surf_usm_h%qsws_liq(m) * drho_l_lv
8151                 m_liq_usm_h_p%var_usm_1d(m) = m_liq_usm_h%var_usm_1d(m) + dt_3d *    &
8152                                               ( tsc(2) * tend +                      &
8153                                                 tsc(3) * tm_liq_usm_h_m%var_usm_1d(m) )
8154!
8155!--             Check if reservoir is overfull -> reduce to maximum
8156!--             (conservation of water is violated here)
8157                 m_liq_usm_h_p%var_usm_1d(m) = MIN( m_liq_usm_h_p%var_usm_1d(m),m_liq_max )
8158 
8159!
8160!--             Check if reservoir is empty (avoid values < 0.0)
8161!--             (conservation of water is violated here)
8162                 m_liq_usm_h_p%var_usm_1d(m) = MAX( m_liq_usm_h_p%var_usm_1d(m), 0.0_wp )
8163!
8164!--             Calculate m_liq tendencies for the next Runge-Kutta step
8165                 IF ( timestep_scheme(1:5) == 'runge' )  THEN
8166                    IF ( intermediate_timestep_count == 1 )  THEN
8167                       tm_liq_usm_h_m%var_usm_1d(m) = tend
8168                    ELSEIF ( intermediate_timestep_count <                            &
8169                             intermediate_timestep_count_max )  THEN
8170                       tm_liq_usm_h_m%var_usm_1d(m) = -9.5625_wp * tend +             &
8171                                                     5.3125_wp * tm_liq_usm_h_m%var_usm_1d(m)
8172                    ENDIF
8173                 ENDIF
8174 
8175              ENDIF
8176           ELSE
8177              surf_usm_h%r_s(m) = 1.0E10_wp
8178           ENDIF
8179!
8180!--        During spinup green and window fraction are set to zero. Here, the original
8181!--        values are restored.
8182           IF ( spinup )  THEN
8183              surf_usm_h%frac(ind_wat_win,m)   = frac_win
8184              surf_usm_h%frac(ind_veg_wall,m)  = frac_wall
8185              surf_usm_h%frac(ind_pav_green,m) = frac_green
8186           ENDIF
8187 
8188       ENDDO
8189!
8190!--    Now, treat vertical surface elements
8191       !$OMP DO SCHEDULE (STATIC)
8192       DO  l = 0, 3
8193           DO  m = 1, surf_usm_v(l)%ns
8194!
8195!--           During spinup set green and window fraction to zero and restore
8196!--           at the end of the loop.
8197!--           Note, this is a temporary fix and need to be removed later.
8198              IF ( spinup )  THEN
8199                 frac_win   = surf_usm_v(l)%frac(ind_wat_win,m)
8200                 frac_wall  = surf_usm_v(l)%frac(ind_veg_wall,m)
8201                 frac_green = surf_usm_v(l)%frac(ind_pav_green,m)
8202                 surf_usm_v(l)%frac(ind_wat_win,m)   = 0.0_wp
8203                 surf_usm_v(l)%frac(ind_veg_wall,m)  = 1.0_wp
8204                 surf_usm_v(l)%frac(ind_pav_green,m) = 0.0_wp
8205              ENDIF
8206!
8207!--          Get indices of respective grid point
8208              i = surf_usm_v(l)%i(m)
8209              j = surf_usm_v(l)%j(m)
8210              k = surf_usm_v(l)%k(m)
8211 
8212!
8213!--          TODO - how to calculate lambda_surface for horizontal (??? do you mean verical ???) surfaces
8214!--          (lambda_surface is set according to stratification in land surface model).
8215!--          Please note, for vertical surfaces no ol is defined, since
8216!--          stratification is not considered in this case.
8217              lambda_surface = surf_usm_v(l)%lambda_surf(m)
8218              lambda_surface_window = surf_usm_v(l)%lambda_surf_window(m)
8219              lambda_surface_green = surf_usm_v(l)%lambda_surf_green(m)
8220 
8221!            pt1  = pt(k,j,i)
8222              IF ( humidity )  THEN
8223                 qv1 = q(k,j,i)
8224              ELSE
8225                 qv1 = 0.0_wp
8226              ENDIF
8227!
8228!--          calculate rho * c_p coefficient at wall layer
8229              rho_cp  = c_p * hyp(k) / ( r_d * surf_usm_v(l)%pt1(m) * exner(k) )
8230             
8231              IF (surf_usm_v(l)%frac(1,m) > 0.0_wp )  THEN
8232!
8233!--            Calculate frequently used parameters
8234                 rho_lv    = rho_cp / c_p * l_v
8235                 drho_l_lv = 1.0_wp / (rho_l * l_v)
8236              ENDIF
8237 
8238!--          Calculation of r_a for vertical surfaces
8239!--
8240!--          heat transfer coefficient for forced convection along vertical walls
8241!--          follows formulation in TUF3d model (Krayenhoff & Voogt, 2006)
8242!--           
8243!--          H = httc (Tsfc - Tair)
8244!--          httc = rw * (11.8 + 4.2 * Ueff) - 4.0
8245!--           
8246!--                rw: wall patch roughness relative to 1.0 for concrete
8247!--                Ueff: effective wind speed
8248!--                - 4.0 is a reduction of Rowley et al (1930) formulation based on
8249!--                Cole and Sturrock (1977)
8250!--           
8251!--                Ucan: Canyon wind speed
8252!--                wstar: convective velocity
8253!--                Qs: surface heat flux
8254!--                zH: height of the convective layer
8255!--                wstar = (g/Tcan*Qs*zH)**(1./3.)
8256!--          Effective velocity components must always
8257!--          be defined at scalar grid point. The wall normal component is
8258!--          obtained by simple linear interpolation. ( An alternative would
8259!--          be an logarithmic interpolation. )
8260!--          Parameter roughness_concrete (default value = 0.001) is used
8261!--          to calculation of roughness relative to concrete
8262              surf_usm_v(l)%r_a(m) = rho_cp / ( surf_usm_v(l)%z0(m) /           &
8263                         roughness_concrete * ( 11.8_wp + 4.2_wp *              &
8264                         SQRT( MAX( ( ( u(k,j,i) + u(k,j,i+1) ) * 0.5_wp )**2 + &
8265                                    ( ( v(k,j,i) + v(k,j+1,i) ) * 0.5_wp )**2 + &
8266                                    ( ( w(k,j,i) + w(k-1,j,i) ) * 0.5_wp )**2,  &
8267                               0.01_wp ) )                                      &
8268                            )  - 4.0_wp  ) 
8269!
8270!--          Limit aerodynamic resistance
8271              IF ( surf_usm_v(l)%r_a(m) < 1.0_wp )  surf_usm_v(l)%r_a(m) = 1.0_wp   
8272             
8273                           
8274              f_shf         = rho_cp / surf_usm_v(l)%r_a(m)
8275              f_shf_window  = rho_cp / surf_usm_v(l)%r_a(m)
8276              f_shf_green   = rho_cp / surf_usm_v(l)%r_a(m)
8277 
8278
8279              IF ( surf_usm_v(l)%frac(1,m) > 0.0_wp ) THEN
8280!
8281!--             Adapted from LSM:
8282!--             Second step: calculate canopy resistance r_canopy
8283!--             f1-f3 here are defined as 1/f1-f3 as in ECMWF documentation
8284!--             f1: correction for incoming shortwave radiation (stomata close at
8285!--             night)
8286                 f1 = MIN( 1.0_wp, ( 0.004_wp * surf_usm_v(l)%rad_sw_in(m) + 0.05_wp ) / &
8287                                  (0.81_wp * (0.004_wp * surf_usm_v(l)%rad_sw_in(m)      &
8288                                   + 1.0_wp)) )
8289!
8290!--             f2: correction for soil moisture availability to plants (the
8291!--             integrated soil moisture must thus be considered here)
8292!--             f2 = 0 for very dry soils
8293 
8294                 f2=1.0_wp
8295 
8296!
8297!--              Calculate water vapour pressure at saturation
8298                 e_s = 0.01_wp * 610.78_wp * EXP( 17.269_wp * (  t_surf_green_v_p(l)%t(m) &
8299                               - 273.16_wp ) / (  t_surf_green_v_p(l)%t(m) - 35.86_wp ) )
8300!
8301!--              f3: correction for vapour pressure deficit
8302                 IF ( surf_usm_v(l)%g_d(m) /= 0.0_wp )  THEN
8303!
8304!--                 Calculate vapour pressure
8305                    e  = qv1 * surface_pressure / ( qv1 + 0.622_wp )
8306                    f3 = EXP ( - surf_usm_v(l)%g_d(m) * (e_s - e) )
8307                 ELSE
8308                    f3 = 1.0_wp
8309                 ENDIF
8310!
8311!--              Calculate canopy resistance. In case that c_veg is 0 (bare soils),
8312!--              this calculation is obsolete, as r_canopy is not used below.
8313!--              To do: check for very dry soil -> r_canopy goes to infinity
8314                 surf_usm_v(l)%r_canopy(m) = surf_usm_v(l)%r_canopy_min(m) /                  &
8315                                        ( surf_usm_v(l)%lai(m) * f1 * f2 * f3 + 1.0E-20_wp )
8316                               
8317!
8318!--              Calculate saturation specific humidity
8319                 q_s = 0.622_wp * e_s / ( surface_pressure - e_s )
8320!
8321!--              In case of dewfall, set evapotranspiration to zero
8322!--              All super-saturated water is then removed from the air
8323                 IF ( humidity  .AND.  q_s <= qv1 )  THEN
8324                    surf_usm_v(l)%r_canopy(m) = 0.0_wp
8325                 ENDIF
8326 
8327!
8328!--              Calculate coefficients for the total evapotranspiration
8329!--              In case of water surface, set vegetation and soil fluxes to zero.
8330!--              For pavements, only evaporation of liquid water is possible.
8331                 f_qsws_veg  = rho_lv *                                &
8332                                   ( 1.0_wp        - 0.0_wp ) / & !surf_usm_h%c_liq(m)    ) /   &
8333                                   ( surf_usm_v(l)%r_a(m) + surf_usm_v(l)%r_canopy(m) )
8334!                f_qsws_liq  = rho_lv * surf_usm_h%c_liq(m)   /             &
8335!                              surf_usm_h%r_a_green(m)
8336         
8337                 f_qsws = f_qsws_veg! + f_qsws_liq
8338!
8339!--              Calculate derivative of q_s for Taylor series expansion
8340                 e_s_dt = e_s * ( 17.269_wp / ( t_surf_green_v_p(l)%t(m) - 35.86_wp) -   &
8341                                  17.269_wp*( t_surf_green_v_p(l)%t(m) - 273.16_wp)      &
8342                                 / ( t_surf_green_v_p(l)%t(m) - 35.86_wp)**2 )
8343         
8344                 dq_s_dt = 0.622_wp * e_s_dt / ( surface_pressure - e_s_dt )
8345              ENDIF
8346
8347!
8348!--           add LW up so that it can be removed in prognostic equation
8349              surf_usm_v(l)%rad_net_l(m) = surf_usm_v(l)%rad_sw_in(m)  -        &
8350                                           surf_usm_v(l)%rad_sw_out(m) +        &
8351                                           surf_usm_v(l)%rad_lw_in(m)  -        &
8352                                           surf_usm_v(l)%rad_lw_out(m)
8353!
8354!--           numerator of the prognostic equation
8355              coef_1 = surf_usm_v(l)%rad_net_l(m) +                             & ! coef +1 corresponds to -lwout
8356                                                                                  ! included in calculation of radnet_l
8357              ( 3.0_wp + 1.0_wp ) * surf_usm_v(l)%emissivity(ind_veg_wall,m) *  &
8358                                      sigma_sb *  t_surf_wall_v(l)%t(m) ** 4 +  & 
8359                                      f_shf * surf_usm_v(l)%pt1(m) +            &
8360                                      lambda_surface * t_wall_v(l)%t(nzb_wall,m)
8361              IF ( ( .NOT. spinup ) .AND. ( surf_usm_v(l)%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
8362                 coef_window_1 = surf_usm_v(l)%rad_net_l(m) +                   & ! coef +1 corresponds to -lwout
8363                                                                                  ! included in calculation of radnet_l
8364                ( 3.0_wp + 1.0_wp ) * surf_usm_v(l)%emissivity(ind_wat_win,m) * &
8365                                      sigma_sb * t_surf_window_v(l)%t(m) ** 4 + & 
8366                                      f_shf * surf_usm_v(l)%pt1(m) +            &
8367                                      lambda_surface_window * t_window_v(l)%t(nzb_wall,m)
8368              ENDIF
8369              IF ( ( humidity ) .AND. ( surf_usm_v(l)%frac(ind_pav_green,m) > 0.0_wp ) )  THEN
8370                 coef_green_1 = surf_usm_v(l)%rad_net_l(m) +                      & ! coef +1 corresponds to -lwout
8371                                                                                    ! included in calculation of radnet_l
8372                 ( 3.0_wp + 1.0_wp ) * surf_usm_v(l)%emissivity(ind_pav_green,m) * sigma_sb *  &
8373                                      t_surf_green_v(l)%t(m) ** 4 +               & 
8374                                      f_shf * surf_usm_v(l)%pt1(m) +     f_qsws * ( qv1 - q_s  &
8375                                           + dq_s_dt * t_surf_green_v(l)%t(m) ) +              &
8376                                      lambda_surface_green * t_wall_v(l)%t(nzb_wall,m)
8377              ELSE
8378                coef_green_1 = surf_usm_v(l)%rad_net_l(m) +                       & ! coef +1 corresponds to -lwout included
8379                                                                                    ! in calculation of radnet_l
8380                ( 3.0_wp + 1.0_wp ) * surf_usm_v(l)%emissivity(ind_pav_green,m) * sigma_sb *  &
8381                                      t_surf_green_v(l)%t(m) ** 4 +               & 
8382                                      f_shf * surf_usm_v(l)%pt1(m) +              &
8383                                      lambda_surface_green * t_wall_v(l)%t(nzb_wall,m)
8384              ENDIF
8385                                     
8386!
8387!--           denominator of the prognostic equation
8388              coef_2 = 4.0_wp * surf_usm_v(l)%emissivity(ind_veg_wall,m) * sigma_sb *   &
8389                                 t_surf_wall_v(l)%t(m) ** 3                             &
8390                               + lambda_surface + f_shf / exner(k) 
8391              IF ( ( .NOT. spinup ) .AND. ( surf_usm_v(l)%frac(ind_wat_win,m) > 0.0_wp ) ) THEN             
8392                 coef_window_2 = 4.0_wp * surf_usm_v(l)%emissivity(ind_wat_win,m) * sigma_sb *       &
8393                                   t_surf_window_v(l)%t(m) ** 3                         &
8394                                 + lambda_surface_window + f_shf / exner(k)
8395              ENDIF
8396              IF ( ( humidity ) .AND. ( surf_usm_v(l)%frac(ind_pav_green,m) > 0.0_wp ) )  THEN
8397                  coef_green_2 = 4.0_wp * surf_usm_v(l)%emissivity(ind_pav_green,m) * sigma_sb *     &
8398                                   t_surf_green_v(l)%t(m) ** 3  + f_qsws * dq_s_dt      &
8399                                 + lambda_surface_green + f_shf / exner(k)
8400              ELSE
8401                 coef_green_2 = 4.0_wp * surf_usm_v(l)%emissivity(ind_pav_green,m) * sigma_sb *      &
8402                                   t_surf_green_v(l)%t(m) ** 3                          &
8403                                 + lambda_surface_green + f_shf / exner(k)
8404              ENDIF
8405!
8406!--           implicit solution when the surface layer has no heat capacity,
8407!--           otherwise use RK3 scheme.
8408              t_surf_wall_v_p(l)%t(m) = ( coef_1 * dt_3d * tsc(2) +                 &
8409                             surf_usm_v(l)%c_surface(m) * t_surf_wall_v(l)%t(m) ) / & 
8410                             ( surf_usm_v(l)%c_surface(m) + coef_2 * dt_3d * tsc(2) ) 
8411              IF ( ( .NOT. spinup ) .AND. ( surf_usm_v(l)%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
8412                 t_surf_window_v_p(l)%t(m) = ( coef_window_1 * dt_3d * tsc(2) +                 &
8413                                surf_usm_v(l)%c_surface_window(m) * t_surf_window_v(l)%t(m) ) / & 
8414                              ( surf_usm_v(l)%c_surface_window(m) + coef_window_2 * dt_3d * tsc(2) ) 
8415              ENDIF
8416              t_surf_green_v_p(l)%t(m) = ( coef_green_1 * dt_3d * tsc(2) +                 &
8417                             surf_usm_v(l)%c_surface_green(m) * t_surf_green_v(l)%t(m) ) / & 
8418                           ( surf_usm_v(l)%c_surface_green(m) + coef_green_2 * dt_3d * tsc(2) ) 
8419!
8420!--           add RK3 term
8421              t_surf_wall_v_p(l)%t(m) = t_surf_wall_v_p(l)%t(m) + dt_3d * tsc(3) *         &
8422                                surf_usm_v(l)%tt_surface_wall_m(m)
8423              t_surf_window_v_p(l)%t(m) = t_surf_window_v_p(l)%t(m) + dt_3d * tsc(3) *     &
8424                                surf_usm_v(l)%tt_surface_window_m(m)
8425              t_surf_green_v_p(l)%t(m) = t_surf_green_v_p(l)%t(m) + dt_3d * tsc(3) *       &
8426                                 surf_usm_v(l)%tt_surface_green_m(m)
8427!
8428!--           Store surface temperature. Further, in case humidity is used
8429!--           store also vpt_surface, which is, due to the lack of moisture on roofs simply
8430!--           assumed to be the surface temperature.     
8431              surf_usm_v(l)%pt_surface(m) =  ( surf_usm_v(l)%frac(ind_veg_wall,m) * t_surf_wall_v_p(l)%t(m)  &
8432                                      + surf_usm_v(l)%frac(ind_wat_win,m) * t_surf_window_v_p(l)%t(m)        &
8433                                      + surf_usm_v(l)%frac(ind_pav_green,m) * t_surf_green_v_p(l)%t(m) )     &
8434                                      / exner(k)
8435                                       
8436              IF ( humidity )  surf_usm_v(l)%vpt_surface(m) =                  &
8437                                                     surf_usm_v(l)%pt_surface(m)
8438!
8439!--           calculate true tendency
8440              stend_wall = ( t_surf_wall_v_p(l)%t(m) - t_surf_wall_v(l)%t(m) - dt_3d * tsc(3) *      &
8441                        surf_usm_v(l)%tt_surface_wall_m(m) ) / ( dt_3d  * tsc(2) )
8442              stend_window = ( t_surf_window_v_p(l)%t(m) - t_surf_window_v(l)%t(m) - dt_3d * tsc(3) *&
8443                        surf_usm_v(l)%tt_surface_window_m(m) ) / ( dt_3d  * tsc(2) )
8444              stend_green = ( t_surf_green_v_p(l)%t(m) - t_surf_green_v(l)%t(m) - dt_3d * tsc(3) *   &
8445                        surf_usm_v(l)%tt_surface_green_m(m) ) / ( dt_3d  * tsc(2) )
8446
8447!
8448!--           calculate t_surf_* tendencies for the next Runge-Kutta step
8449              IF ( timestep_scheme(1:5) == 'runge' )  THEN
8450                 IF ( intermediate_timestep_count == 1 )  THEN
8451                    surf_usm_v(l)%tt_surface_wall_m(m) = stend_wall
8452                    surf_usm_v(l)%tt_surface_window_m(m) = stend_window
8453                    surf_usm_v(l)%tt_surface_green_m(m) = stend_green
8454                 ELSEIF ( intermediate_timestep_count <                                 &
8455                          intermediate_timestep_count_max )  THEN
8456                    surf_usm_v(l)%tt_surface_wall_m(m) = -9.5625_wp * stend_wall +      &
8457                                     5.3125_wp * surf_usm_v(l)%tt_surface_wall_m(m)
8458                    surf_usm_v(l)%tt_surface_green_m(m) = -9.5625_wp * stend_green +    &
8459                                     5.3125_wp * surf_usm_v(l)%tt_surface_green_m(m)
8460                    surf_usm_v(l)%tt_surface_window_m(m) = -9.5625_wp * stend_window +  &
8461                                     5.3125_wp * surf_usm_v(l)%tt_surface_window_m(m)
8462                 ENDIF
8463              ENDIF
8464
8465!
8466!--           in case of fast changes in the skin temperature, it is required to
8467!--           update the radiative fluxes in order to keep the solution stable
8468 
8469              IF ( ( ( ABS( t_surf_wall_v_p(l)%t(m)   - t_surf_wall_v(l)%t(m) )   > 1.0_wp ) .OR. &
8470                   (   ABS( t_surf_green_v_p(l)%t(m)  - t_surf_green_v(l)%t(m) )  > 1.0_wp ) .OR. &
8471                   (   ABS( t_surf_window_v_p(l)%t(m) - t_surf_window_v(l)%t(m) ) > 1.0_wp ) )    &
8472                      .AND.  unscheduled_radiation_calls )  THEN
8473                 force_radiation_call_l = .TRUE.
8474              ENDIF
8475
8476!
8477!--           calculate fluxes
8478!--           prognostic rad_net_l is used just for output!           
8479              surf_usm_v(l)%rad_net_l(m) = surf_usm_v(l)%frac(ind_veg_wall,m) *                      &
8480                                           ( surf_usm_v(l)%rad_net_l(m) +                            &
8481                                           3.0_wp * sigma_sb *                                       &
8482                                           t_surf_wall_v(l)%t(m)**4 - 4.0_wp * sigma_sb *            &
8483                                           t_surf_wall_v(l)%t(m)**3 * t_surf_wall_v_p(l)%t(m) )      &
8484                                         + surf_usm_v(l)%frac(ind_wat_win,m) *                       &
8485                                           ( surf_usm_v(l)%rad_net_l(m) +                            &
8486                                           3.0_wp * sigma_sb *                                       &
8487                                           t_surf_window_v(l)%t(m)**4 - 4.0_wp * sigma_sb *          &
8488                                           t_surf_window_v(l)%t(m)**3 * t_surf_window_v_p(l)%t(m) )  &
8489                                         + surf_usm_v(l)%frac(ind_pav_green,m) *                     &
8490                                           ( surf_usm_v(l)%rad_net_l(m) +                            &
8491                                           3.0_wp * sigma_sb *                                       &
8492                                           t_surf_green_v(l)%t(m)**4 - 4.0_wp * sigma_sb *           &
8493                                           t_surf_green_v(l)%t(m)**3 * t_surf_green_v_p(l)%t(m) )
8494
8495              surf_usm_v(l)%wghf_eb_window(m) = lambda_surface_window * &
8496                                                ( t_surf_window_v_p(l)%t(m) - t_window_v(l)%t(nzb_wall,m) )
8497              surf_usm_v(l)%wghf_eb(m)   = lambda_surface *             &
8498                                                ( t_surf_wall_v_p(l)%t(m) - t_wall_v(l)%t(nzb_wall,m) )
8499              surf_usm_v(l)%wghf_eb_green(m)  = lambda_surface_green *  &
8500                                                ( t_surf_green_v_p(l)%t(m) - t_green_v(l)%t(nzb_wall,m) )
8501
8502!
8503!--           ground/wall/roof surface heat flux
8504              surf_usm_v(l)%wshf_eb(m)   =                                     &
8505                 - f_shf  * ( surf_usm_v(l)%pt1(m) -                           &
8506                 t_surf_wall_v_p(l)%t(m) / exner(k) ) * surf_usm_v(l)%frac(ind_veg_wall,m)       &
8507                 - f_shf_window  * ( surf_usm_v(l)%pt1(m) -                    &
8508                 t_surf_window_v_p(l)%t(m) / exner(k) ) * surf_usm_v(l)%frac(ind_wat_win,m)&
8509                 - f_shf_green  * ( surf_usm_v(l)%pt1(m) -                     &
8510                 t_surf_green_v_p(l)%t(m) / exner(k) ) * surf_usm_v(l)%frac(ind_pav_green,m)
8511
8512!           
8513!--           store kinematic surface heat fluxes for utilization in other processes
8514!--           diffusion_s, surface_layer_fluxes,...
8515              surf_usm_v(l)%shf(m) = surf_usm_v(l)%wshf_eb(m) / c_p
8516!
8517!--           If the indoor model is applied, further add waste heat from buildings to the
8518!--           kinematic flux.
8519              IF ( indoor_model )  THEN
8520                 surf_usm_v(l)%shf(m) = surf_usm_v(l)%shf(m) +                       &
8521                                        surf_usm_v(l)%waste_heat(m) / c_p
8522              ENDIF             
8523
8524              IF ( surf_usm_v(l)%frac(ind_pav_green,m) > 0.0_wp ) THEN
8525 
8526
8527                 IF ( humidity )  THEN
8528                    surf_usm_v(l)%qsws_eb(m)  = - f_qsws * ( qv1 - q_s + dq_s_dt       &
8529                                    * t_surf_green_v(l)%t(m) - dq_s_dt *               &
8530                                      t_surf_green_v_p(l)%t(m) )
8531         
8532                    surf_usm_v(l)%qsws(m) = surf_usm_v(l)%qsws_eb(m) / rho_lv
8533         
8534                    surf_usm_v(l)%qsws_veg(m)  = - f_qsws_veg  * ( qv1 - q_s           &
8535                                        + dq_s_dt * t_surf_green_v(l)%t(m) - dq_s_dt   &
8536                                        * t_surf_green_v_p(l)%t(m) )
8537         
8538!                    surf_usm_h%qsws_liq(m)  = - f_qsws_liq  * ( qv1 - q_s         &
8539!                                        + dq_s_dt * t_surf_green_h(m) - dq_s_dt   &
8540!                                        * t_surf_green_h_p(m) )
8541                 ENDIF
8542 
8543!
8544!--              Calculate the true surface resistance
8545                 IF ( .NOT.  humidity )  THEN
8546                    surf_usm_v(l)%r_s(m) = 1.0E10_wp
8547                 ELSE
8548                    surf_usm_v(l)%r_s(m) = - rho_lv * ( qv1 - q_s + dq_s_dt             &
8549                                    *  t_surf_green_v(l)%t(m) - dq_s_dt *               &
8550                                      t_surf_green_v_p(l)%t(m) ) /                      &
8551                                      (surf_usm_v(l)%qsws(m) + 1.0E-20)  - surf_usm_v(l)%r_a(m)
8552                 ENDIF
8553         
8554!
8555!--              Calculate change in liquid water reservoir due to dew fall or
8556!--              evaporation of liquid water
8557                 IF ( humidity )  THEN
8558!
8559!--                 If the air is saturated, check the reservoir water level
8560                    IF ( surf_usm_v(l)%qsws(m) < 0.0_wp )  THEN
8561       
8562!
8563!--                    In case qsws_veg becomes negative (unphysical behavior),
8564!--                    let the water enter the liquid water reservoir as dew on the
8565!--                    plant
8566                       IF ( surf_usm_v(l)%qsws_veg(m) < 0.0_wp )  THEN
8567          !                 surf_usm_h%qsws_liq(m) = surf_usm_h%qsws_liq(m) + surf_usm_h%qsws_veg(m)
8568                          surf_usm_v(l)%qsws_veg(m) = 0.0_wp
8569                       ENDIF
8570                    ENDIF
8571                 
8572                 ENDIF
8573              ELSE
8574                 surf_usm_v(l)%r_s(m) = 1.0E10_wp
8575              ENDIF
8576!
8577!--           During spinup green and window fraction are set to zero. Here, the original
8578!--           values are restored.
8579              IF ( spinup )  THEN
8580                 surf_usm_v(l)%frac(ind_wat_win,m)   = frac_win
8581                 surf_usm_v(l)%frac(ind_veg_wall,m)  = frac_wall
8582                 surf_usm_v(l)%frac(ind_pav_green,m) = frac_green
8583              ENDIF
8584
8585           ENDDO
8586 
8587       ENDDO
8588       !$OMP END PARALLEL
8589
8590!
8591!--     Add-up anthropogenic heat, for now only at upward-facing surfaces
8592         IF ( usm_anthropogenic_heat  .AND.  &
8593              intermediate_timestep_count == intermediate_timestep_count_max )  THEN
8594!
8595!--        application of the additional anthropogenic heat sources
8596!--        we considere the traffic for now so all heat is absorbed
8597!--        to the first layer, generalization would be worth.
8598!--        calculation of actual profile coefficient
8599!--        ??? check time_since_reference_point ???
8600            dtime = mod(simulated_time + time_utc_init, 24.0_wp*3600.0_wp)
8601            dhour = INT(dtime/3600.0_wp)
8602
8603!--         TO_DO: activate, if testcase is available
8604!--         !$OMP PARALLEL DO PRIVATE (i, j, k, acoef, rho_cp)
8605!--         it may also improve performance to move get_topography_top_index_ji before the k-loop
8606            DO i = nxl, nxr
8607               DO j = nys, nyn
8608                  DO k = nz_urban_b, min(nz_urban_t,naheatlayers)
8609                     IF ( k > get_topography_top_index_ji( j, i, 's' ) ) THEN
8610!
8611!--                    increase of pt in box i,j,k in time dt_3d
8612!--                    given to anthropogenic heat aheat*acoef (W*m-2)
8613!--                    linear interpolation of coeficient
8614                        acoef = (REAL(dhour+1,wp)-dtime/3600.0_wp)*aheatprof(k,dhour) + &
8615                                (dtime/3600.0_wp-REAL(dhour,wp))*aheatprof(k,dhour+1)
8616                        IF ( aheat(k,j,i) > 0.0_wp )  THEN
8617!
8618!--                       calculate rho * c_p coefficient at layer k
8619                           rho_cp  = c_p * hyp(k) / ( r_d * pt(k+1,j,i) * exner(k) )
8620                           pt(k,j,i) = pt(k,j,i) + aheat(k,j,i)*acoef*dt_3d/(exner(k)*rho_cp*dz(1))
8621                        ENDIF
8622                     ENDIF
8623                  ENDDO
8624               ENDDO
8625            ENDDO
8626 
8627         ENDIF
8628!
8629!--     pt and shf are defined on nxlg:nxrg,nysg:nyng
8630!--     get the borders from neighbours
8631         CALL exchange_horiz( pt, nbgp )
8632!
8633!--     calculation of force_radiation_call:
8634!--     Make logical OR for all processes.
8635!--     Force radiation call if at least one processor forces it.
8636         IF ( intermediate_timestep_count == intermediate_timestep_count_max-1 )&
8637         THEN
8638#if defined( __parallel )
8639           IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
8640           CALL MPI_ALLREDUCE( force_radiation_call_l, force_radiation_call,    &
8641                               1, MPI_LOGICAL, MPI_LOR, comm2d, ierr )
8642#else
8643           force_radiation_call = force_radiation_call_l
8644#endif
8645           force_radiation_call_l = .FALSE.
8646         ENDIF
8647 
8648! !
8649! !-- Calculate surface specific humidity
8650!     IF ( humidity )  THEN
8651!        CALL calc_q_surface_usm
8652!     ENDIF
8653 
8654 
8655!     CONTAINS
8656! !------------------------------------------------------------------------------!
8657! ! Description:
8658! ! ------------
8659! !> Calculation of specific humidity of the skin layer (surface). It is assumend
8660! !> that the skin is always saturated.
8661! !------------------------------------------------------------------------------!
8662!        SUBROUTINE calc_q_surface_usm
8663!
8664!           IMPLICIT NONE
8665!
8666!           REAL(wp) :: resistance    !< aerodynamic and soil resistance term
8667!
8668!           DO  m = 1, surf_usm_h%ns
8669!
8670!              i   = surf_usm_h%i(m)           
8671!              j   = surf_usm_h%j(m)
8672!              k   = surf_usm_h%k(m)
8673!
8674!!
8675!!--          Calculate water vapour pressure at saturation
8676!              e_s = 0.01_wp * 610.78_wp * EXP( 17.269_wp *                  &
8677!                                     ( t_surf_green_h_p(m) - 273.16_wp ) /  &
8678!                                     ( t_surf_green_h_p(m) - 35.86_wp  )    &
8679!                                          )
8680!
8681!!
8682!!--          Calculate specific humidity at saturation
8683!              q_s = 0.622_wp * e_s / ( surface_pressure - e_s )
8684!
8685!!              surf_usm_h%r_a_green(m) = ( surf_usm_h%pt1(m) - t_surf_green_h(m) / exner(k) ) /  &
8686!!                    ( surf_usm_h%ts(m) * surf_usm_h%us(m) + 1.0E-10_wp )
8687!!                 
8688!! !--          make sure that the resistance does not drop to zero
8689!!              IF ( ABS(surf_usm_h%r_a_green(m)) < 1.0E-10_wp )  surf_usm_h%r_a_green(m) = 1.0E-10_wp
8690!
8691!              resistance = surf_usm_h%r_a_green(m) / ( surf_usm_h%r_a_green(m) + surf_usm_h%r_s(m) + 1E-5_wp )
8692!
8693!!
8694!!--          Calculate specific humidity at surface
8695!              IF ( bulk_cloud_model )  THEN
8696!                 q(k,j,i) = resistance * q_s +                   &
8697!                                            ( 1.0_wp - resistance ) *              &
8698!                                            ( q(k,j,i) - ql(k,j,i) )
8699!              ELSE
8700!                 q(k,j,i) = resistance * q_s +                   &
8701!                                            ( 1.0_wp - resistance ) *              &
8702!                                              q(k,j,i)
8703!              ENDIF
8704!
8705!!
8706!!--          Update virtual potential temperature
8707!              vpt(k,j,i) = pt(k,j,i) *         &
8708!                         ( 1.0_wp + 0.61_wp * q(k,j,i) )
8709!
8710!           ENDDO
8711!
8712!!
8713!!--       Now, treat vertical surface elements
8714!           DO  l = 0, 3
8715!              DO  m = 1, surf_usm_v(l)%ns
8716!!
8717!!--             Get indices of respective grid point
8718!                 i = surf_usm_v(l)%i(m)
8719!                 j = surf_usm_v(l)%j(m)
8720!                 k = surf_usm_v(l)%k(m)
8721!
8722!!
8723!!--             Calculate water vapour pressure at saturation
8724!                 e_s = 0.01_wp * 610.78_wp * EXP( 17.269_wp *                       &
8725!                                        ( t_surf_green_v_p(l)%t(m) - 273.16_wp ) /  &
8726!                                        ( t_surf_green_v_p(l)%t(m) - 35.86_wp  )    &
8727!                                             )
8728!
8729!!
8730!!--             Calculate specific humidity at saturation
8731!                 q_s = 0.622_wp * e_s / ( surface_pressure -e_s )
8732!
8733!!
8734!!--             Calculate specific humidity at surface
8735!                 IF ( bulk_cloud_model )  THEN
8736!                    q(k,j,i) = ( q(k,j,i) - ql(k,j,i) )
8737!                 ELSE
8738!                    q(k,j,i) = q(k,j,i)
8739!                 ENDIF
8740!!
8741!!--             Update virtual potential temperature
8742!                 vpt(k,j,i) = pt(k,j,i) *         &
8743!                            ( 1.0_wp + 0.61_wp * q(k,j,i) )
8744!
8745!              ENDDO
8746!
8747!           ENDDO
8748!
8749!        END SUBROUTINE calc_q_surface_usm
8750
8751        IF ( debug_output )  THEN
8752           WRITE( debug_string, * ) 'usm_surface_energy_balance | spinup: ', spinup
8753           CALL debug_message( debug_string, 'end' )
8754        ENDIF
8755
8756     END SUBROUTINE usm_surface_energy_balance
8757 
8758 
8759!------------------------------------------------------------------------------!
8760! Description:
8761! ------------
8762!> Swapping of timelevels for t_surf and t_wall
8763!> called out from subroutine swap_timelevel
8764!------------------------------------------------------------------------------!
8765     SUBROUTINE usm_swap_timelevel( mod_count )
8766 
8767        IMPLICIT NONE
8768 
8769        INTEGER(iwp), INTENT(IN) ::  mod_count
8770 
8771       
8772        SELECT CASE ( mod_count )
8773 
8774           CASE ( 0 )
8775!
8776!--          Horizontal surfaces
8777              t_surf_wall_h    => t_surf_wall_h_1;   t_surf_wall_h_p    => t_surf_wall_h_2
8778              t_wall_h         => t_wall_h_1;        t_wall_h_p         => t_wall_h_2
8779              t_surf_window_h  => t_surf_window_h_1; t_surf_window_h_p  => t_surf_window_h_2
8780              t_window_h       => t_window_h_1;      t_window_h_p       => t_window_h_2
8781              t_surf_green_h   => t_surf_green_h_1;  t_surf_green_h_p   => t_surf_green_h_2
8782              t_green_h        => t_green_h_1;       t_green_h_p        => t_green_h_2
8783!
8784!--          Vertical surfaces
8785              t_surf_wall_v    => t_surf_wall_v_1;   t_surf_wall_v_p    => t_surf_wall_v_2
8786              t_wall_v         => t_wall_v_1;        t_wall_v_p         => t_wall_v_2
8787              t_surf_window_v  => t_surf_window_v_1; t_surf_window_v_p  => t_surf_window_v_2
8788              t_window_v       => t_window_v_1;      t_window_v_p       => t_window_v_2
8789              t_surf_green_v   => t_surf_green_v_1;  t_surf_green_v_p   => t_surf_green_v_2
8790              t_green_v        => t_green_v_1;       t_green_v_p        => t_green_v_2
8791           CASE ( 1 )
8792!
8793!--          Horizontal surfaces
8794              t_surf_wall_h    => t_surf_wall_h_2;   t_surf_wall_h_p    => t_surf_wall_h_1
8795              t_wall_h         => t_wall_h_2;        t_wall_h_p         => t_wall_h_1
8796              t_surf_window_h  => t_surf_window_h_2; t_surf_window_h_p  => t_surf_window_h_1
8797              t_window_h       => t_window_h_2;      t_window_h_p       => t_window_h_1
8798              t_surf_green_h   => t_surf_green_h_2;  t_surf_green_h_p   => t_surf_green_h_1
8799              t_green_h        => t_green_h_2;       t_green_h_p        => t_green_h_1
8800!
8801!--          Vertical surfaces
8802              t_surf_wall_v    => t_surf_wall_v_2;   t_surf_wall_v_p    => t_surf_wall_v_1
8803              t_wall_v         => t_wall_v_2;        t_wall_v_p         => t_wall_v_1
8804              t_surf_window_v  => t_surf_window_v_2; t_surf_window_v_p  => t_surf_window_v_1
8805              t_window_v       => t_window_v_2;      t_window_v_p       => t_window_v_1
8806              t_surf_green_v   => t_surf_green_v_2;  t_surf_green_v_p   => t_surf_green_v_1
8807              t_green_v        => t_green_v_2;       t_green_v_p        => t_green_v_1
8808        END SELECT
8809         
8810     END SUBROUTINE usm_swap_timelevel
8811 
8812!------------------------------------------------------------------------------!
8813! Description:
8814! ------------
8815!> Subroutine writes t_surf and t_wall data into restart files
8816!------------------------------------------------------------------------------!
8817     SUBROUTINE usm_wrd_local
8818 
8819     
8820        IMPLICIT NONE
8821       
8822        CHARACTER(LEN=1) ::  dum     !< dummy string to create output-variable name 
8823        INTEGER(iwp)     ::  l       !< index surface type orientation
8824 
8825        CALL wrd_write_string( 'ns_h_on_file_usm' )
8826        WRITE ( 14 )  surf_usm_h%ns
8827 
8828        CALL wrd_write_string( 'ns_v_on_file_usm' )
8829        WRITE ( 14 )  surf_usm_v(0:3)%ns
8830 
8831        CALL wrd_write_string( 'usm_start_index_h' )
8832        WRITE ( 14 )  surf_usm_h%start_index
8833 
8834        CALL wrd_write_string( 'usm_end_index_h' )
8835        WRITE ( 14 )  surf_usm_h%end_index
8836 
8837        CALL wrd_write_string( 't_surf_wall_h' )
8838        WRITE ( 14 )  t_surf_wall_h
8839 
8840        CALL wrd_write_string( 't_surf_window_h' )
8841        WRITE ( 14 )  t_surf_window_h
8842 
8843        CALL wrd_write_string( 't_surf_green_h' )
8844        WRITE ( 14 )  t_surf_green_h
8845!
8846!--     Write restart data which is especially needed for the urban-surface
8847!--     model. In order to do not fill up the restart routines in
8848!--     surface_mod.
8849!--     Output of waste heat from indoor model. Restart data is required in
8850!--     this special case, because the indoor model where waste heat is
8851!--     computed is call each hour (current default), so that waste heat would
8852!--     have zero value until next call of indoor model.
8853        IF ( indoor_model )  THEN
8854           CALL wrd_write_string( 'waste_heat_h' )
8855           WRITE ( 14 )  surf_usm_h%waste_heat
8856        ENDIF   
8857           
8858        DO  l = 0, 3
8859 
8860           CALL wrd_write_string( 'usm_start_index_v' )
8861           WRITE ( 14 )  surf_usm_v(l)%start_index
8862 
8863           CALL wrd_write_string( 'usm_end_index_v' )
8864           WRITE ( 14 )  surf_usm_v(l)%end_index
8865 
8866           WRITE( dum, '(I1)')  l         
8867 
8868           CALL wrd_write_string( 't_surf_wall_v(' // dum // ')' )
8869           WRITE ( 14 )  t_surf_wall_v(l)%t
8870 
8871           CALL wrd_write_string( 't_surf_window_v(' // dum // ')' )
8872           WRITE ( 14 ) t_surf_window_v(l)%t     
8873 
8874           CALL wrd_write_string( 't_surf_green_v(' // dum // ')' )
8875           WRITE ( 14 ) t_surf_green_v(l)%t 
8876           
8877           IF ( indoor_model )  THEN
8878              CALL wrd_write_string( 'waste_heat_v(' // dum // ')' )
8879              WRITE ( 14 )  surf_usm_v(l)%waste_heat
8880           ENDIF
8881           
8882        ENDDO
8883 
8884        CALL wrd_write_string( 'usm_start_index_h' )
8885        WRITE ( 14 )  surf_usm_h%start_index
8886 
8887        CALL wrd_write_string( 'usm_end_index_h' )
8888        WRITE ( 14 )  surf_usm_h%end_index
8889 
8890        CALL wrd_write_string( 't_wall_h' )
8891        WRITE ( 14 )  t_wall_h
8892 
8893        CALL wrd_write_string( 't_window_h' )
8894        WRITE ( 14 )  t_window_h
8895 
8896        CALL wrd_write_string( 't_green_h' )
8897        WRITE ( 14 )  t_green_h
8898 
8899        DO  l = 0, 3
8900 
8901           CALL wrd_write_string( 'usm_start_index_v' )
8902           WRITE ( 14 )  surf_usm_v(l)%start_index
8903 
8904           CALL wrd_write_string( 'usm_end_index_v' )
8905           WRITE ( 14 )  surf_usm_v(l)%end_index
8906 
8907           WRITE( dum, '(I1)')  l     
8908 
8909           CALL wrd_write_string( 't_wall_v(' // dum // ')' )
8910           WRITE ( 14 )  t_wall_v(l)%t
8911 
8912           CALL wrd_write_string( 't_window_v(' // dum // ')' )
8913           WRITE ( 14 )  t_window_v(l)%t
8914 
8915           CALL wrd_write_string( 't_green_v(' // dum // ')' )
8916           WRITE ( 14 )  t_green_v(l)%t
8917       
8918        ENDDO
8919       
8920     END SUBROUTINE usm_wrd_local
8921     
8922     
8923!------------------------------------------------------------------------------!
8924! Description:
8925! ------------
8926!> Define building properties
8927!------------------------------------------------------------------------------!
8928     SUBROUTINE usm_define_pars     
8929!
8930!--     Define the building_pars
8931        building_pars(:,1) = (/   &
8932           0.7_wp,         &  !< parameter 0   - wall fraction above ground floor level
8933           0.3_wp,         &  !< parameter 1   - window fraction above ground floor level
8934           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
8935           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
8936           1.5_wp,         &  !< parameter 4   - LAI roof
8937           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
8938           2200000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
8939           1400000.0_wp,   &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
8940           1300000.0_wp,   &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
8941           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
8942           0.8_wp,         &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
8943           2.1_wp,         &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
8944           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
8945           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
8946           0.93_wp,        &  !< parameter 14  - wall emissivity above ground floor level
8947           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
8948           0.91_wp,        &  !< parameter 16  - window emissivity above ground floor level
8949           0.75_wp,        &  !< parameter 17  - window transmissivity above ground floor level
8950           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
8951           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
8952           4.0_wp,         &  !< parameter 20  - ground floor level height
8953           0.75_wp,        &  !< parameter 21  - wall fraction ground floor level
8954           0.25_wp,        &  !< parameter 22  - window fraction ground floor level
8955           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
8956           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
8957           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
8958           2200000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
8959           1400000.0_wp,   &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
8960           1300000.0_wp,   &  !< parameter 28  - heat capacity 4th wall layer ground floor level
8961           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
8962           0.8_wp,         &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
8963           2.1_wp,         &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
8964           0.93_wp,        &  !< parameter 32  - wall emissivity ground floor level
8965           0.91_wp,        &  !< parameter 33  - window emissivity ground floor level
8966           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
8967           0.75_wp,        &  !< parameter 35  - window transmissivity ground floor level
8968           0.01_wp,        &  !< parameter 36  - z0 roughness ground floor level
8969           0.001_wp,       &  !< parameter 37  - z0h/z0q roughness heat/humidity
8970           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
8971           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
8972           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
8973           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
8974           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
8975           0.39_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
8976           0.63_wp,        &  !< parameter 44  - 4th wall layer thickness above ground floor level
8977           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
8978           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
8979           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
8980           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
8981           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
8982           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
8983           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
8984           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
8985           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
8986           0.39_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
8987           0.63_wp,        &  !< parameter 55  - 4th wall layer thickness ground plate
8988           2200000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
8989           1400000.0_wp,   &  !< parameter 57  - heat capacity 3rd wall layer ground plate
8990           1300000.0_wp,   &  !< parameter 58  - heat capacity 4th wall layer ground plate
8991           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
8992           0.8_wp,         &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
8993           2.1_wp,         &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
8994           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
8995           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
8996           0.39_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
8997           0.63_wp,        &  !< parameter 65  - 4th wall layer thickness ground floor level
8998           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
8999           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9000           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9001           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9002           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9003           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9004           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9005           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9006           0.57_wp,        &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9007           0.57_wp,        &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9008           0.57_wp,        &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9009           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9010           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9011           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9012           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9013           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9014           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9015           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9016           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9017           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9018           0.57_wp,        &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9019           0.57_wp,        &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9020           0.57_wp,        &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9021           1.0_wp,         &  !< parameter 89  - wall fraction roof
9022           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9023           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9024           0.31_wp,        &  !< parameter 92  - 3rd wall layer thickness roof
9025           0.63_wp,        &  !< parameter 93  - 4th wall layer thickness roof
9026           2200000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9027           1400000.0_wp,   &  !< parameter 95  - heat capacity 3rd wall layer roof
9028           1300000.0_wp,   &  !< parameter 96  - heat capacity 4th wall layer roof
9029           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9030           0.8_wp,         &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9031           2.1_wp,         &  !< parameter 99  - thermal conductivity 4th wall layer roof
9032           0.93_wp,        &  !< parameter 100 - wall emissivity roof
9033           27.0_wp,        &  !< parameter 101 - wall albedo roof
9034           0.0_wp,         &  !< parameter 102 - window fraction roof
9035           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9036           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9037           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9038           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9039           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9040           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9041           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9042           0.57_wp,        &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9043           0.57_wp,        &  !< parameter 111 - thermal conductivity 3rd window layer roof
9044           0.57_wp,        &  !< parameter 112 - thermal conductivity 4th window layer roof
9045           0.91_wp,        &  !< parameter 113 - window emissivity roof
9046           0.75_wp,        &  !< parameter 114 - window transmissivity roof
9047           27.0_wp,        &  !< parameter 115 - window albedo roof
9048           0.86_wp,        &  !< parameter 116 - green emissivity roof
9049           5.0_wp,         &  !< parameter 117 - green albedo roof
9050           0.0_wp,         &  !< parameter 118 - green type roof
9051           0.8_wp,         &  !< parameter 119 - shading factor
9052           0.76_wp,        &  !< parameter 120 - g-value windows
9053           5.0_wp,         &  !< parameter 121 - u-value windows
9054           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9055           0.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9056           0.0_wp,         &  !< parameter 124 - heat recovery efficiency
9057           3.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9058           370000.0_wp,    &  !< parameter 126 - dynamic parameter innner heatstorage
9059           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9060           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9061           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9062           3.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9063           10.0_wp,        &  !< parameter 131 - basic internal heat gains without occupancy of the room
9064           3.0_wp,         &  !< parameter 132 - storey height
9065           0.2_wp          &  !< parameter 133 - ceiling construction height
9066                            /)
9067                           
9068        building_pars(:,2) = (/   &
9069           0.73_wp,        &  !< parameter 0   - wall fraction above ground floor level
9070           0.27_wp,        &  !< parameter 1   - window fraction above ground floor level
9071           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9072           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9073           1.5_wp,         &  !< parameter 4   - LAI roof
9074           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9075           2000000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9076           103000.0_wp,    &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9077           900000.0_wp,    &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9078           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9079           0.38_wp,        &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9080           0.04_wp,        &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9081           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9082           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9083           0.92_wp,        &  !< parameter 14  - wall emissivity above ground floor level
9084           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9085           0.87_wp,        &  !< parameter 16  - window emissivity above ground floor level
9086           0.7_wp,         &  !< parameter 17  - window transmissivity above ground floor level
9087           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9088           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9089           4.0_wp,         &  !< parameter 20  - ground floor level height
9090           0.78_wp,        &  !< parameter 21  - wall fraction ground floor level
9091           0.22_wp,        &  !< parameter 22  - window fraction ground floor level
9092           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9093           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9094           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9095           2000000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9096           103000.0_wp,    &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9097           900000.0_wp,    &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9098           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9099           0.38_wp,        &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9100           0.04_wp,        &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9101           0.92_wp,        &  !< parameter 32  - wall emissivity ground floor level
9102           0.11_wp,        &  !< parameter 33  - window emissivity ground floor level
9103           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9104           0.7_wp,         &  !< parameter 35  - window transmissivity ground floor level
9105           0.01_wp,        &  !< parameter 36  - z0 roughness ground floor level
9106           0.001_wp,       &  !< parameter 37  - z0h/z0q roughness heat/humidity
9107           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9108           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9109           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9110           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
9111           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9112           0.31_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9113           0.43_wp,        &  !< parameter 44  - 4th wall layer thickness above ground floor level
9114           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9115           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9116           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9117           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9118           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9119           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9120           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9121           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
9122           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
9123           0.31_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
9124           0.42_wp,        &  !< parameter 55  - 4th wall layer thickness ground plate
9125           2000000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9126           103000.0_wp,    &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9127           900000.0_wp,    &  !< parameter 58  - heat capacity 4th wall layer ground plate
9128           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9129           0.38_wp,        &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9130           0.04_wp,        &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9131           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
9132           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
9133           0.31_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
9134           0.43_wp,        &  !< parameter 65  - 4th wall layer thickness ground floor level
9135           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9136           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9137           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9138           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9139           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9140           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9141           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9142           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9143           0.11_wp,        &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9144           0.11_wp,        &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9145           0.11_wp,        &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9146           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9147           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9148           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9149           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9150           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9151           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9152           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9153           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9154           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9155           0.11_wp,        &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9156           0.11_wp,        &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9157           0.11_wp,        &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9158           1.0_wp,         &  !< parameter 89  - wall fraction roof
9159           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9160           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9161           0.5_wp,         &  !< parameter 92  - 3rd wall layer thickness roof
9162           0.79_wp,        &  !< parameter 93  - 4th wall layer thickness roof
9163           2000000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9164           103000.0_wp,    &  !< parameter 95  - heat capacity 3rd wall layer roof
9165           900000.0_wp,    &  !< parameter 96  - heat capacity 4th wall layer roof
9166           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9167           0.38_wp,        &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9168           0.04_wp,        &  !< parameter 99  - thermal conductivity 4th wall layer roof
9169           0.93_wp,        &  !< parameter 100 - wall emissivity roof
9170           27.0_wp,        &  !< parameter 101 - wall albedo roof
9171           0.0_wp,         &  !< parameter 102 - window fraction roof
9172           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9173           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9174           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9175           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9176           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9177           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9178           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9179           0.11_wp,        &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9180           0.11_wp,        &  !< parameter 111 - thermal conductivity 3rd window layer roof
9181           0.11_wp,        &  !< parameter 112 - thermal conductivity 4th window layer roof
9182           0.87_wp,        &  !< parameter 113 - window emissivity roof
9183           0.7_wp,         &  !< parameter 114 - window transmissivity roof
9184           27.0_wp,        &  !< parameter 115 - window albedo roof
9185           0.86_wp,        &  !< parameter 116 - green emissivity roof
9186           5.0_wp,         &  !< parameter 117 - green albedo roof
9187           0.0_wp,         &  !< parameter 118 - green type roof
9188           0.8_wp,         &  !< parameter 119 - shading factor
9189           0.6_wp,         &  !< parameter 120 - g-value windows
9190           3.0_wp,         &  !< parameter 121 - u-value windows
9191           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9192           0.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9193           0.0_wp,         &  !< parameter 124 - heat recovery efficiency
9194           2.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9195           165000.0_wp,    &  !< parameter 126 - dynamic parameter innner heatstorage
9196           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9197           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9198           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9199           4.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9200           8.0_wp,         &  !< parameter 131 - basic internal heat gains without occupancy of the room
9201           3.0_wp,         &  !< parameter 132 - storey height
9202           0.2_wp          &  !< parameter 133 - ceiling construction height
9203                            /)
9204                           
9205        building_pars(:,3) = (/   &
9206           0.7_wp,         &  !< parameter 0   - wall fraction above ground floor level
9207           0.3_wp,         &  !< parameter 1   - window fraction above ground floor level
9208           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9209           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9210           1.5_wp,         &  !< parameter 4   - LAI roof
9211           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9212           2000000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9213           103000.0_wp,    &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9214           900000.0_wp,    &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9215           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9216           0.14_wp,        &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9217           0.035_wp,       &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9218           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9219           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9220           0.92_wp,        &  !< parameter 14  - wall emissivity above ground floor level
9221           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9222           0.8_wp,         &  !< parameter 16  - window emissivity above ground floor level
9223           0.6_wp,         &  !< parameter 17  - window transmissivity above ground floor level
9224           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9225           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9226           4.0_wp,         &  !< parameter 20  - ground floor level height
9227           0.75_wp,        &  !< parameter 21  - wall fraction ground floor level
9228           0.25_wp,        &  !< parameter 22  - window fraction ground floor level
9229           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9230           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9231           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9232           2000000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9233           103000.0_wp,    &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9234           900000.0_wp,    &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9235           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9236           0.14_wp,        &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9237           0.035_wp,       &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9238           0.92_wp,        &  !< parameter 32  - wall emissivity ground floor level
9239           0.8_wp,         &  !< parameter 33  - window emissivity ground floor level
9240           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9241           0.6_wp,         &  !< parameter 35  - window transmissivity ground floor level
9242           0.01_wp,        &  !< parameter 36  - z0 roughness ground floor level
9243           0.001_wp,       &  !< parameter 37  - z0h/z0q roughness heat/humidity
9244           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9245           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9246           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9247           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
9248           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9249           0.41_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9250           0.7_wp,         &  !< parameter 44  - 4th wall layer thickness above ground floor level
9251           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9252           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9253           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9254           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9255           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9256           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9257           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9258           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
9259           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
9260           0.41_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
9261           0.7_wp,         &  !< parameter 55  - 4th wall layer thickness ground plate
9262           2000000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9263           103000.0_wp,    &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9264           900000.0_wp,    &  !< parameter 58  - heat capacity 4th wall layer ground plate
9265           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9266           0.14_wp,        &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9267           0.035_wp,       &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9268           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
9269           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
9270           0.41_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
9271           0.7_wp,         &  !< parameter 65  - 4th wall layer thickness ground floor level
9272           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9273           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9274           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9275           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9276           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9277           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9278           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9279           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9280           0.037_wp,       &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9281           0.037_wp,       &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9282           0.037_wp,       &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9283           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9284           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9285           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9286           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9287           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9288           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9289           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9290           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9291           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9292           0.037_wp,       &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9293           0.037_wp,       &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9294           0.037_wp,       &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9295           1.0_wp,         &  !< parameter 89  - wall fraction roof
9296           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9297           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9298           0.41_wp,        &  !< parameter 92  - 3rd wall layer thickness roof
9299           0.7_wp,         &  !< parameter 93  - 4th wall layer thickness roof
9300           2000000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9301           103000.0_wp,    &  !< parameter 95  - heat capacity 3rd wall layer roof
9302           900000.0_wp,    &  !< parameter 96  - heat capacity 4th wall layer roof
9303           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9304           0.14_wp,        &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9305           0.035_wp,       &  !< parameter 99  - thermal conductivity 4th wall layer roof
9306           0.93_wp,        &  !< parameter 100 - wall emissivity roof
9307           27.0_wp,        &  !< parameter 101 - wall albedo roof
9308           0.0_wp,         &  !< parameter 102 - window fraction roof
9309           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9310           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9311           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9312           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9313           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9314           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9315           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9316           0.037_wp,       &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9317           0.037_wp,       &  !< parameter 111 - thermal conductivity 3rd window layer roof
9318           0.037_wp,       &  !< parameter 112 - thermal conductivity 4th window layer roof
9319           0.8_wp,         &  !< parameter 113 - window emissivity roof
9320           0.6_wp,         &  !< parameter 114 - window transmissivity roof
9321           27.0_wp,        &  !< parameter 115 - window albedo roof
9322           0.86_wp,        &  !< parameter 116 - green emissivity roof
9323           5.0_wp,         &  !< parameter 117 - green albedo roof
9324           0.0_wp,         &  !< parameter 118 - green type roof
9325           0.8_wp,         &  !< parameter 119 - shading factor
9326           0.5_wp,         &  !< parameter 120 - g-value windows
9327           0.6_wp,         &  !< parameter 121 - u-value windows
9328           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9329           0.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9330           0.8_wp,         &  !< parameter 124 - heat recovery efficiency
9331           2.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9332           80000.0_wp,     &  !< parameter 126 - dynamic parameter innner heatstorage
9333           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9334           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9335           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9336           3.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9337           8.0_wp,         &  !< parameter 131 - basic internal heat gains without occupancy of the room
9338           3.0_wp,         &  !< parameter 132 - storey height
9339           0.2_wp          &  !< parameter 133 - ceiling construction height
9340                            /)   
9341                           
9342        building_pars(:,4) = (/   &
9343           0.5_wp,         &  !< parameter 0   - wall fraction above ground floor level
9344           0.5_wp,         &  !< parameter 1   - window fraction above ground floor level
9345           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9346           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9347           1.5_wp,         &  !< parameter 4   - LAI roof
9348           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9349           2200000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9350           1400000.0_wp,   &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9351           1300000.0_wp,   &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9352           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9353           0.8_wp,         &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9354           2.1_wp,         &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9355           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9356           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9357           0.93_wp,        &  !< parameter 14  - wall emissivity above ground floor level
9358           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9359           0.91_wp,        &  !< parameter 16  - window emissivity above ground floor level
9360           0.75_wp,        &  !< parameter 17  - window transmissivity above ground floor level
9361           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9362           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9363           4.0_wp,         &  !< parameter 20  - ground floor level height
9364           0.55_wp,        &  !< parameter 21  - wall fraction ground floor level
9365           0.45_wp,        &  !< parameter 22  - window fraction ground floor level
9366           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9367           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9368           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9369           2200000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9370           1400000.0_wp,   &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9371           1300000.0_wp,   &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9372           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9373           0.8_wp,         &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9374           2.1_wp,         &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9375           0.93_wp,        &  !< parameter 32  - wall emissivity ground floor level
9376           0.91_wp,        &  !< parameter 33  - window emissivity ground floor level
9377           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9378           0.75_wp,        &  !< parameter 35  - window transmissivity ground floor level
9379           0.01_wp,        &  !< parameter 36  - z0 roughness ground floor level
9380           0.001_wp,       &  !< parameter 37  - z0h/z0q roughness heat/humidity
9381           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9382           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9383           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9384           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
9385           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9386           0.39_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9387           0.63_wp,        &  !< parameter 44  - 4th wall layer thickness above ground floor level
9388           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9389           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9390           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9391           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9392           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9393           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9394           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9395           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
9396           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
9397           0.39_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
9398           0.63_wp,        &  !< parameter 55  - 4th wall layer thickness ground plate
9399           2200000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9400           1400000.0_wp,   &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9401           1300000.0_wp,   &  !< parameter 58  - heat capacity 4th wall layer ground plate
9402           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9403           0.8_wp,         &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9404           2.1_wp,         &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9405           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
9406           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
9407           0.39_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
9408           0.63_wp,        &  !< parameter 65  - 4th wall layer thickness ground floor level
9409           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9410           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9411           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9412           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9413           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9414           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9415           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9416           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9417           0.57_wp,        &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9418           0.57_wp,        &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9419           0.57_wp,        &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9420           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9421           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9422           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9423           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9424           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9425           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9426           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9427           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9428           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9429           0.57_wp,        &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9430           0.57_wp,        &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9431           0.57_wp,        &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9432           1.0_wp,         &  !< parameter 89  - wall fraction roof
9433           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9434           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9435           0.39_wp,        &  !< parameter 92  - 3rd wall layer thickness roof
9436           0.63_wp,        &  !< parameter 93  - 4th wall layer thickness roof
9437           2200000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9438           1400000.0_wp,   &  !< parameter 95  - heat capacity 3rd wall layer roof
9439           1300000.0_wp,   &  !< parameter 96  - heat capacity 4th wall layer roof
9440           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9441           0.8_wp,         &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9442           2.1_wp,         &  !< parameter 99  - thermal conductivity 4th wall layer roof
9443           0.93_wp,        &  !< parameter 100 - wall emissivity roof
9444           27.0_wp,        &  !< parameter 101 - wall albedo roof
9445           0.0_wp,         &  !< parameter 102 - window fraction roof
9446           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9447           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9448           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9449           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9450           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9451           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9452           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9453           0.57_wp,        &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9454           0.57_wp,        &  !< parameter 111 - thermal conductivity 3rd window layer roof
9455           0.57_wp,        &  !< parameter 112 - thermal conductivity 4th window layer roof
9456           0.91_wp,        &  !< parameter 113 - window emissivity roof
9457           0.75_wp,        &  !< parameter 114 - window transmissivity roof
9458           27.0_wp,        &  !< parameter 115 - window albedo roof
9459           0.86_wp,        &  !< parameter 116 - green emissivity roof
9460           5.0_wp,         &  !< parameter 117 - green albedo roof
9461           0.0_wp,         &  !< parameter 118 - green type roof
9462           0.8_wp,         &  !< parameter 119 - shading factor
9463           0.76_wp,        &  !< parameter 120 - g-value windows
9464           5.0_wp,         &  !< parameter 121 - u-value windows
9465           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9466           1.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9467           0.0_wp,         &  !< parameter 124 - heat recovery efficiency
9468           3.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9469           370000.0_wp,    &  !< parameter 126 - dynamic parameter innner heatstorage
9470           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9471           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9472           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9473           3.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9474           10.0_wp,        &  !< parameter 131 - basic internal heat gains without occupancy of the room
9475           3.0_wp,         &  !< parameter 132 - storey height
9476           0.2_wp          &  !< parameter 133 - ceiling construction height
9477                            /)   
9478                           
9479        building_pars(:,5) = (/   &
9480           0.5_wp,         &  !< parameter 0   - wall fraction above ground floor level
9481           0.5_wp,         &  !< parameter 1   - window fraction above ground floor level
9482           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9483           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9484           1.5_wp,         &  !< parameter 4   - LAI roof
9485           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9486           2000000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9487           103000.0_wp,    &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9488           900000.0_wp,    &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9489           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9490           0.38_wp,        &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9491           0.04_wp,        &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9492           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9493           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9494           0.92_wp,        &  !< parameter 14  - wall emissivity above ground floor level
9495           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9496           0.87_wp,        &  !< parameter 16  - window emissivity above ground floor level
9497           0.7_wp,         &  !< parameter 17  - window transmissivity above ground floor level
9498           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9499           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9500           4.0_wp,         &  !< parameter 20  - ground floor level height
9501           0.55_wp,        &  !< parameter 21  - wall fraction ground floor level
9502           0.45_wp,        &  !< parameter 22  - window fraction ground floor level
9503           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9504           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9505           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9506           2000000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9507           103000.0_wp,    &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9508           900000.0_wp,    &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9509           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9510           0.38_wp,        &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9511           0.04_wp,        &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9512           0.92_wp,        &  !< parameter 32  - wall emissivity ground floor level
9513           0.87_wp,        &  !< parameter 33  - window emissivity ground floor level
9514           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9515           0.7_wp,         &  !< parameter 35  - window transmissivity ground floor level
9516           0.01_wp,        &  !< parameter 36  - z0 roughness ground floor level
9517           0.001_wp,       &  !< parameter 37  - z0h/z0q roughness heat/humidity
9518           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9519           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9520           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9521           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
9522           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9523           0.31_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9524           0.43_wp,        &  !< parameter 44  - 4th wall layer thickness above ground floor level
9525           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9526           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9527           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9528           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9529           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9530           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9531           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9532           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
9533           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
9534           0.31_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
9535           0.43_wp,        &  !< parameter 55  - 4th wall layer thickness ground plate
9536           2000000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9537           103000.0_wp,    &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9538           900000.0_wp,    &  !< parameter 58  - heat capacity 4th wall layer ground plate
9539           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9540           0.38_wp,        &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9541           0.04_wp,        &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9542           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
9543           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
9544           0.31_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
9545           0.43_wp,        &  !< parameter 65  - 4th wall layer thickness ground floor level
9546           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9547           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9548           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9549           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9550           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9551           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9552           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9553           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9554           0.11_wp,        &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9555           0.11_wp,        &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9556           0.11_wp,        &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9557           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9558           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9559           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9560           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9561           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9562           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9563           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9564           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9565           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9566           0.11_wp,        &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9567           0.11_wp,        &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9568           0.11_wp,        &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9569           1.0_wp,         &  !< parameter 89  - wall fraction roof
9570           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9571           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9572           0.31_wp,        &  !< parameter 92  - 3rd wall layer thickness roof
9573           0.43_wp,        &  !< parameter 93  - 4th wall layer thickness roof
9574           2000000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9575           103000.0_wp,    &  !< parameter 95  - heat capacity 3rd wall layer roof
9576           900000.0_wp,    &  !< parameter 96  - heat capacity 4th wall layer roof
9577           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9578           0.38_wp,        &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9579           0.04_wp,        &  !< parameter 99  - thermal conductivity 4th wall layer roof
9580           0.91_wp,        &  !< parameter 100 - wall emissivity roof
9581           27.0_wp,        &  !< parameter 101 - wall albedo roof
9582           0.0_wp,         &  !< parameter 102 - window fraction roof
9583           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9584           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9585           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9586           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9587           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9588           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9589           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9590           0.11_wp,        &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9591           0.11_wp,        &  !< parameter 111 - thermal conductivity 3rd window layer roof
9592           0.11_wp,        &  !< parameter 112 - thermal conductivity 4th window layer roof
9593           0.87_wp,        &  !< parameter 113 - window emissivity roof
9594           0.7_wp,         &  !< parameter 114 - window transmissivity roof
9595           27.0_wp,        &  !< parameter 115 - window albedo roof
9596           0.86_wp,        &  !< parameter 116 - green emissivity roof
9597           5.0_wp,         &  !< parameter 117 - green albedo roof
9598           0.0_wp,         &  !< parameter 118 - green type roof
9599           0.8_wp,         &  !< parameter 119 - shading factor
9600           0.6_wp,         &  !< parameter 120 - g-value windows
9601           3.0_wp,         &  !< parameter 121 - u-value windows
9602           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9603           1.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9604           0.65_wp,        &  !< parameter 124 - heat recovery efficiency
9605           2.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9606           165000.0_wp,    &  !< parameter 126 - dynamic parameter innner heatstorage
9607           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9608           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9609           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9610           7.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9611           20.0_wp,        &  !< parameter 131 - basic internal heat gains without occupancy of the room
9612           3.0_wp,         &  !< parameter 132 - storey height
9613           0.2_wp          &  !< parameter 133 - ceiling construction height
9614                            /)
9615                           
9616        building_pars(:,6) = (/   &
9617           0.425_wp,       &  !< parameter 0   - wall fraction above ground floor level
9618           0.575_wp,       &  !< parameter 1   - window fraction above ground floor level
9619           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9620           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9621           1.5_wp,         &  !< parameter 4   - LAI roof
9622           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9623           2000000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9624           103000.0_wp,    &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9625           900000.0_wp,    &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9626           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9627           0.14_wp,        &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9628           0.035_wp,       &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9629           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9630           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9631           0.92_wp,        &  !< parameter 14  - wall emissivity above ground floor level
9632           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9633           0.8_wp,         &  !< parameter 16  - window emissivity above ground floor level
9634           0.6_wp,         &  !< parameter 17  - window transmissivity above ground floor level
9635           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9636           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9637           4.0_wp,         &  !< parameter 20  - ground floor level height
9638           0.475_wp,       &  !< parameter 21  - wall fraction ground floor level
9639           0.525_wp,       &  !< parameter 22  - window fraction ground floor level
9640           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9641           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9642           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9643           2000000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9644           103000.0_wp,    &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9645           900000.0_wp,    &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9646           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9647           0.14_wp,        &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9648           0.035_wp,       &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9649           0.92_wp,        &  !< parameter 32  - wall emissivity ground floor level
9650           0.8_wp,         &  !< parameter 33  - window emissivity ground floor level
9651           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9652           0.6_wp,         &  !< parameter 35  - window transmissivity ground floor level
9653           0.01_wp,        &  !< parameter 36  - z0 roughness ground floor level
9654           0.001_wp,       &  !< parameter 37  - z0h/z0q roughness heat/humidity
9655           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9656           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9657           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9658           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
9659           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9660           0.41_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9661           0.7_wp,         &  !< parameter 44  - 4th wall layer thickness above ground floor level
9662           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9663           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9664           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9665           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9666           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9667           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9668           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9669           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
9670           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
9671           0.41_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
9672           0.7_wp,         &  !< parameter 55  - 4th wall layer thickness ground plate
9673           2000000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9674           103000.0_wp,    &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9675           900000.0_wp,    &  !< parameter 58  - heat capacity 4th wall layer ground plate
9676           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9677           0.14_wp,        &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9678           0.035_wp,       &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9679           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
9680           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
9681           0.41_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
9682           0.7_wp,         &  !< parameter 65  - 4th wall layer thickness ground floor level
9683           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9684           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9685           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9686           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9687           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9688           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9689           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9690           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9691           0.037_wp,       &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9692           0.037_wp,       &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9693           0.037_wp,       &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9694           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9695           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9696           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9697           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9698           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9699           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9700           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9701           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9702           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9703           0.037_wp,       &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9704           0.037_wp,       &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9705           0.037_wp,       &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9706           1.0_wp,         &  !< parameter 89  - wall fraction roof
9707           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9708           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9709           0.41_wp,        &  !< parameter 92  - 3rd wall layer thickness roof
9710           0.7_wp,         &  !< parameter 93  - 4th wall layer thickness roof
9711           2000000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9712           103000.0_wp,    &  !< parameter 95  - heat capacity 3rd wall layer roof
9713           900000.0_wp,    &  !< parameter 96  - heat capacity 4th wall layer roof
9714           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9715           0.14_wp,        &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9716           0.035_wp,       &  !< parameter 99  - thermal conductivity 4th wall layer roof
9717           0.91_wp,        &  !< parameter 100 - wall emissivity roof
9718           27.0_wp,        &  !< parameter 101 - wall albedo roof
9719           0.0_wp,         &  !< parameter 102 - window fraction roof
9720           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9721           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9722           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9723           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9724           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9725           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9726           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9727           0.037_wp,       &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9728           0.037_wp,       &  !< parameter 111 - thermal conductivity 3rd window layer roof
9729           0.037_wp,       &  !< parameter 112 - thermal conductivity 4th window layer roof
9730           0.8_wp,         &  !< parameter 113 - window emissivity roof
9731           0.6_wp,         &  !< parameter 114 - window transmissivity roof
9732           27.0_wp,        &  !< parameter 115 - window albedo roof
9733           0.86_wp,        &  !< parameter 116 - green emissivity roof
9734           5.0_wp,         &  !< parameter 117 - green albedo roof
9735           0.0_wp,         &  !< parameter 118 - green type roof
9736           0.8_wp,         &  !< parameter 119 - shading factor
9737           0.5_wp,         &  !< parameter 120 - g-value windows
9738           0.6_wp,         &  !< parameter 121 - u-value windows
9739           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9740           1.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9741           0.9_wp,         &  !< parameter 124 - heat recovery efficiency
9742           2.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9743           80000.0_wp,     &  !< parameter 126 - dynamic parameter innner heatstorage
9744           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9745           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9746           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9747           5.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9748           15.0_wp,        &  !< parameter 131 - basic internal heat gains without occupancy of the room
9749           3.0_wp,         &  !< parameter 132 - storey height
9750           0.2_wp          &  !< parameter 133 - ceiling construction height
9751                            /)
9752                           
9753        building_pars(:,7) = (/   &
9754           1.0_wp,         &  !< parameter 0   - wall fraction above ground floor level
9755           0.0_wp,         &  !< parameter 1   - window fraction above ground floor level
9756           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9757           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9758           1.5_wp,         &  !< parameter 4   - LAI roof
9759           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9760           1950400.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9761           1848000.0_wp,   &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9762           1848000.0_wp,   &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9763           0.7_wp,         &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9764           1.0_wp,         &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9765           1.0_wp,         &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9766           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9767           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9768           0.9_wp,         &  !< parameter 14  - wall emissivity above ground floor level
9769           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9770           0.8_wp,         &  !< parameter 16  - window emissivity above ground floor level
9771           0.6_wp,         &  !< parameter 17  - window transmissivity above ground floor level
9772           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9773           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9774           4.0_wp,         &  !< parameter 20  - ground floor level height
9775           1.0_wp,         &  !< parameter 21  - wall fraction ground floor level
9776           0.0_wp,         &  !< parameter 22  - window fraction ground floor level
9777           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9778           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9779           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9780           1950400.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9781           1848000.0_wp,   &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9782           1848000.0_wp,   &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9783           0.7_wp,         &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9784           1.0_wp,         &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9785           1.0_wp,         &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9786           0.9_wp,         &  !< parameter 32  - wall emissivity ground floor level
9787           0.8_wp,         &  !< parameter 33  - window emissivity ground floor level
9788           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9789           0.6_wp,         &  !< parameter 35  - window transmissivity ground floor level
9790           0.01_wp,        &  !< parameter 36  - z0 roughness ground floor level
9791           0.001_wp,       &  !< parameter 37  - z0h/z0q roughness heat/humidity
9792           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9793           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9794           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9795           0.29_wp,        &  !< parameter 41  - 1st wall layer thickness above ground floor level
9796           0.295_wp,       &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9797           0.695_wp,       &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9798           0.985_wp,       &  !< parameter 44  - 4th wall layer thickness above ground floor level
9799           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9800           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9801           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9802           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9803           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9804           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9805           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9806           0.29_wp,        &  !< parameter 52  - 1st wall layer thickness ground plate
9807           0.295_wp,       &  !< parameter 53  - 2nd wall layer thickness ground plate
9808           0.695_wp,       &  !< parameter 54  - 3rd wall layer thickness ground plate
9809           0.985_wp,       &  !< parameter 55  - 4th wall layer thickness ground plate
9810           1950400.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9811           1848000.0_wp,   &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9812           1848000.0_wp,   &  !< parameter 58  - heat capacity 4th wall layer ground plate
9813           0.7_wp,         &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9814           1.0_wp,         &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9815           1.0_wp,         &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9816           0.29_wp,        &  !< parameter 62  - 1st wall layer thickness ground floor level
9817           0.295_wp,       &  !< parameter 63  - 2nd wall layer thickness ground floor level
9818           0.695_wp,       &  !< parameter 64  - 3rd wall layer thickness ground floor level
9819           0.985_wp,       &  !< parameter 65  - 4th wall layer thickness ground floor level
9820           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9821           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9822           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9823           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9824           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9825           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9826           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9827           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9828           0.57_wp,        &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9829           0.57_wp,        &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9830           0.57_wp,        &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9831           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9832           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9833           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9834           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9835           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9836           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9837           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9838           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9839           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9840           0.57_wp,        &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9841           0.57_wp,        &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9842           0.57_wp,        &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9843           1.0_wp,         &  !< parameter 89  - wall fraction roof
9844           0.29_wp,        &  !< parameter 90  - 1st wall layer thickness roof
9845           0.295_wp,       &  !< parameter 91  - 2nd wall layer thickness roof
9846           0.695_wp,       &  !< parameter 92  - 3rd wall layer thickness roof
9847           0.985_wp,       &  !< parameter 93  - 4th wall layer thickness roof
9848           1950400.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9849           1848000.0_wp,   &  !< parameter 95  - heat capacity 3rd wall layer roof
9850           1848000.0_wp,   &  !< parameter 96  - heat capacity 4th wall layer roof
9851           0.7_wp,         &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9852           1.0_wp,         &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9853           1.0_wp,         &  !< parameter 99  - thermal conductivity 4th wall layer roof
9854           0.9_wp,         &  !< parameter 100 - wall emissivity roof
9855           27.0_wp,        &  !< parameter 101 - wall albedo roof
9856           0.0_wp,         &  !< parameter 102 - window fraction roof
9857           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9858           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9859           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9860           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9861           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9862           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9863           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9864           0.57_wp,        &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9865           0.57_wp,        &  !< parameter 111 - thermal conductivity 3rd window layer roof
9866           0.57_wp,        &  !< parameter 112 - thermal conductivity 4th window layer roof
9867           0.8_wp,         &  !< parameter 113 - window emissivity roof
9868           0.6_wp,         &  !< parameter 114 - window transmissivity roof
9869           27.0_wp,        &  !< parameter 115 - window albedo roof
9870           0.86_wp,        &  !< parameter 116 - green emissivity roof
9871           5.0_wp,         &  !< parameter 117 - green albedo roof
9872           0.0_wp,         &  !< parameter 118 - green type roof
9873           0.8_wp,         &  !< parameter 119 - shading factor
9874           100.0_wp,       &  !< parameter 120 - g-value windows
9875           100.0_wp,       &  !< parameter 121 - u-value windows
9876           20.0_wp,        &  !< parameter 122 - basical airflow without occupancy of the room
9877           20.0_wp,        &  !< parameter 123 - additional airflow depend of occupancy of the room
9878           0.0_wp,         &  !< parameter 124 - heat recovery efficiency
9879           1.0_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9880           1.0_wp,         &  !< parameter 126 - dynamic parameter innner heatstorage
9881           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9882           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9883           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9884           0.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9885           0.0_wp,         &  !< parameter 131 - basic internal heat gains without occupancy of the room
9886           3.0_wp,         &  !< parameter 132 - storey height
9887           0.2_wp          &  !< parameter 133 - ceiling construction height
9888                        /)
9889                       
9890     END SUBROUTINE usm_define_pars
9891 
9892   
9893  END MODULE urban_surface_mod
Note: See TracBrowser for help on using the repository browser.