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

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

changes from last commit documented

  • Property svn:keywords set to Id
File size: 557.4 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 4051 2019-06-24 13:58:30Z suehring $
30! Remove work-around for green surface fraction on buildings
31! (do not set it zero)
32!
33! 4050 2019-06-24 13:57:27Z suehring
34! In order to avoid confusion with global control parameter, rename the
35! USM-internal flag spinup into during_spinup.
36!
37! 3987 2019-05-22 09:52:13Z kanani
38! Introduce alternative switch for debug output during timestepping
39!
40! 3943 2019-05-02 09:50:41Z maronga
41! Removed qsws_eb. Bugfix in calculation of qsws.
42!
43! 3933 2019-04-25 12:33:20Z kanani
44! Remove allocation of pt_2m, this is done in surface_mod now (surfaces%pt_2m)
45!
46! 3921 2019-04-18 14:21:10Z suehring
47! Undo accidentally commented initialization 
48!
49! 3918 2019-04-18 13:33:11Z suehring
50! Set green fraction to zero also at vertical surfaces
51!
52! 3914 2019-04-17 16:02:02Z suehring
53! In order to obtain correct surface temperature during spinup set window
54! fraction to zero (only during spinup) instead of just disabling
55! time-integration of window-surface temperature.
56!
57! 3901 2019-04-16 16:17:02Z suehring
58! Workaround - set green fraction to zero ( green-heat model crashes ).
59!
60! 3896 2019-04-15 10:10:17Z suehring
61!
62!
63! 3896 2019-04-15 10:10:17Z suehring
64! Bugfix, wrong index used for accessing building_pars from PIDS
65!
66! 3885 2019-04-11 11:29:34Z kanani
67! Changes related to global restructuring of location messages and introduction
68! of additional debug messages
69!
70! 3882 2019-04-10 11:08:06Z suehring
71! Avoid different type kinds
72! Move definition of building-surface properties from declaration block
73! to an extra routine
74!
75! 3881 2019-04-10 09:31:22Z suehring
76! Revise determination of local ground-floor level height.
77! Make level 3 initalization conform with Palm-input-data standard
78! Move output of albedo and emissivity to radiation module
79!
80! 3832 2019-03-28 13:16:58Z raasch
81! instrumented with openmp directives
82!
83! 3824 2019-03-27 15:56:16Z pavelkrc
84! Remove unused imports
85!
86!
87! 3814 2019-03-26 08:40:31Z pavelkrc
88! unused subroutine commented out
89!
90! 3769 2019-02-28 10:16:49Z moh.hefny
91! removed unused variables
92!
93! 3767 2019-02-27 08:18:02Z raasch
94! unused variables removed from rrd-subroutines parameter list
95!
96! 3748 2019-02-18 10:38:31Z suehring
97! Revise conversion of waste-heat flux (do not divide by air density, will
98! be done in diffusion_s)
99!
100! 3745 2019-02-15 18:57:56Z suehring
101! - Remove internal flag indoor_model (is a global control parameter)
102! - add waste heat from buildings to the kinmatic heat flux
103! - consider waste heat in restart data
104! - remove unused USE statements
105!
106! 3744 2019-02-15 18:38:58Z suehring
107! fixed surface heat capacity in the building parameters
108! convert the file back to unix format
109!
110! 3730 2019-02-11 11:26:47Z moh.hefny
111! Formatting and clean-up (rvtils)
112!
113! 3710 2019-01-30 18:11:19Z suehring
114! Check if building type is set within a valid range.
115!
116! 3705 2019-01-29 19:56:39Z suehring
117! make nzb_wall public, required for virtual-measurements
118!
119! 3704 2019-01-29 19:51:41Z suehring
120! Some interface calls moved to module_interface + cleanup
121!
122! 3655 2019-01-07 16:51:22Z knoop
123! Implementation of the PALM module interface
124!
125! 3636 2018-12-19 13:48:34Z raasch
126! nopointer option removed
127!
128! 3614 2018-12-10 07:05:46Z raasch
129! unused variables removed
130!
131! 3607 2018-12-07 11:56:58Z suehring
132! Output of radiation-related quantities migrated to radiation_model_mod.
133!
134! 3597 2018-12-04 08:40:18Z maronga
135! Fixed calculation method of near surface air potential temperature at 10 cm
136! and moved to surface_layer_fluxes. Removed unnecessary _eb strings.
137!
138! 3524 2018-11-14 13:36:44Z raasch
139! bugfix concerning allocation of t_surf_wall_v
140!
141! 3502 2018-11-07 14:45:23Z suehring
142! Disable initialization of building roofs with ground-floor-level properties,
143! since this causes strong oscillations of surface temperature during the
144! spinup.
145!
146! 3469 2018-10-30 20:05:07Z kanani
147! Add missing PUBLIC variables for new indoor model
148!
149! 3449 2018-10-29 19:36:56Z suehring
150! Bugfix: Fix average arrays allocations in usm_3d_data_averaging (J.Resler)
151! Bugfix: Fix reading wall temperatures (J.Resler)
152! Bugfix: Fix treating of outputs for wall temperature and sky view factors (J.Resler)
153!
154!
155! 3435 2018-10-26 18:25:44Z gronemeier
156! Bugfix: allocate gamma_w_green_sat until nzt_wall+1
157!
158! 3418 2018-10-24 16:07:39Z kanani
159! (rvtils, srissman)
160! -Updated building databse, two green roof types (ind_green_type_roof)
161! -Latent heat flux for green walls and roofs, new output of latent heatflux
162!  and soil water content of green roof substrate
163! -t_surf changed to t_surf_wall
164! -Added namelist parameter usm_wall_mod for lower wall tendency
165!  of first two wall layers during spinup
166! -Window calculations deactivated during spinup
167!
168! 3382 2018-10-19 13:10:32Z knoop
169! Bugix: made array declaration Fortran Standard conform
170!
171! 3378 2018-10-19 12:34:59Z kanani
172! merge from radiation branch (r3362) into trunk
173! (moh.hefny):
174! - check the requested output variables if they are correct
175! - added unscheduled_radiation_calls switch to control force_radiation_call
176! - minor formate changes
177!
178! 3371 2018-10-18 13:40:12Z knoop
179! Set flag indicating that albedo at urban surfaces is already initialized
180!
181! 3347 2018-10-15 14:21:08Z suehring
182! Enable USM initialization with default building parameters in case no static
183! input file exist.
184!
185! 3343 2018-10-15 10:38:52Z suehring
186! Add output variables usm_rad_pc_inlw, usm_rad_pc_insw*
187!
188! 3274 2018-09-24 15:42:55Z knoop
189! Modularization of all bulk cloud physics code components
190!
191! 3248 2018-09-14 09:42:06Z sward
192! Minor formating changes
193!
194! 3246 2018-09-13 15:14:50Z sward
195! Added error handling for input namelist via parin_fail_message
196!
197! 3241 2018-09-12 15:02:00Z raasch
198! unused variables removed
199!
200! 3223 2018-08-30 13:48:17Z suehring
201! Bugfix for commit 3222
202!
203! 3222 2018-08-30 13:35:35Z suehring
204! Introduction of surface array for type and its name
205!
206! 3203 2018-08-23 10:48:36Z suehring
207! Revise bulk parameter for emissivity at ground-floor level
208!
209! 3196 2018-08-13 12:26:14Z maronga
210! Added maximum aerodynamic resistance of 300 for horiztonal surfaces.
211!
212! 3176 2018-07-26 17:12:48Z suehring
213! Bugfix, update virtual potential surface temparture, else heat fluxes on
214! roofs might become unphysical
215!
216! 3152 2018-07-19 13:26:52Z suehring
217! Initialize q_surface, which might be used in surface_layer_fluxes
218!
219! 3151 2018-07-19 08:45:38Z raasch
220! remaining preprocessor define strings __check removed
221!
222! 3136 2018-07-16 14:48:21Z suehring
223! Limit also roughness length for heat and moisture where necessary
224!
225! 3123 2018-07-12 16:21:53Z suehring
226! Correct working precision for INTEGER number
227!
228! 3115 2018-07-10 12:49:26Z suehring
229! Additional building type to represent bridges
230!
231! 3091 2018-06-28 16:20:35Z suehring
232! - Limit aerodynamic resistance at vertical walls.
233! - Add check for local roughness length not exceeding surface-layer height and
234!   limit roughness length where necessary.
235!
236! 3065 2018-06-12 07:03:02Z Giersch
237! Unused array dxdir was removed, dz was replaced by dzu to consider vertical
238! grid stretching
239!
240! 3049 2018-05-29 13:52:36Z Giersch
241! Error messages revised
242!
243! 3045 2018-05-28 07:55:41Z Giersch
244! Error message added
245!
246! 3029 2018-05-23 12:19:17Z raasch
247! bugfix: close unit 151 instead of 90
248!
249! 3014 2018-05-09 08:42:38Z maronga
250! Added pc_transpiration_rate
251!
252! 2977 2018-04-17 10:27:57Z kanani
253! Implement changes from branch radiation (r2948-2971) with minor modifications.
254! (moh.hefny):
255! Extended exn for all model domain height to avoid the need to get nzut.
256!
257! 2963 2018-04-12 14:47:44Z suehring
258! Introduce index for vegetation/wall, pavement/green-wall and water/window
259! surfaces, for clearer access of surface fraction, albedo, emissivity, etc. .
260!
261! 2943 2018-04-03 16:17:10Z suehring
262! Calculate exner function at all height levels and remove some un-used
263! variables.
264!
265! 2932 2018-03-26 09:39:22Z maronga
266! renamed urban_surface_par to urban_surface_parameters
267!
268! 2921 2018-03-22 15:05:23Z Giersch
269! The activation of spinup has been moved to parin
270!
271! 2920 2018-03-22 11:22:01Z kanani
272! Remove unused pcbl, npcbl from ONLY list
273! moh.hefny:
274! Fixed bugs introduced by new structures and by moving radiation interaction
275! into radiation_model_mod.f90.
276! Bugfix: usm data output 3D didn't respect directions
277!
278! 2906 2018-03-19 08:56:40Z Giersch
279! Local variable ids has to be initialized with a value of -1 in
280! usm_3d_data_averaging
281!
282! 2894 2018-03-15 09:17:58Z Giersch
283! Calculations of the index range of the subdomain on file which overlaps with
284! the current subdomain are already done in read_restart_data_mod,
285! usm_read/write_restart_data have been renamed to usm_r/wrd_local, variable
286! named found has been introduced for checking if restart data was found,
287! reading of restart strings has been moved completely to
288! read_restart_data_mod, usm_rrd_local is already inside the overlap loop
289! programmed in read_restart_data_mod, SAVE attribute added where necessary,
290! deallocation and allocation of some arrays have been changed to take care of
291! different restart files that can be opened (index i), the marker *** end usm
292! *** is not necessary anymore, strings and their respective lengths are
293! written out and read now in case of restart runs to get rid of prescribed
294! character lengths
295!
296! 2805 2018-02-14 17:00:09Z suehring
297! Initialization of resistances.
298!
299! 2797 2018-02-08 13:24:35Z suehring
300! Comment concerning output of ground-heat flux added.
301!
302! 2766 2018-01-22 17:17:47Z kanani
303! Removed redundant commas, added some blanks
304!
305! 2765 2018-01-22 11:34:58Z maronga
306! Major bugfix in calculation of f_shf. Adjustment of roughness lengths in
307! building_pars
308!
309! 2750 2018-01-15 16:26:51Z knoop
310! Move flag plant canopy to modules
311!
312! 2737 2018-01-11 14:58:11Z kanani
313! Removed unused variables t_surf_whole...
314!
315! 2735 2018-01-11 12:01:27Z suehring
316! resistances are saved in surface attributes
317!
318! 2723 2018-01-05 09:27:03Z maronga
319! Bugfix for spinups (end_time was increased twice in case of LSM + USM runs)
320!
321! 2720 2018-01-02 16:27:15Z kanani
322! Correction of comment
323!
324! 2718 2018-01-02 08:49:38Z maronga
325! Corrected "Former revisions" section
326!
327! 2705 2017-12-18 11:26:23Z maronga
328! Changes from last commit documented
329!
330! 2703 2017-12-15 20:12:38Z maronga
331! Workaround for calculation of r_a
332!
333! 2696 2017-12-14 17:12:51Z kanani
334! - Change in file header (GPL part)
335! - Bugfix in calculation of pt_surface and related fluxes. (BM)
336! - Do not write surface temperatures onto pt array as this might cause
337!   problems with nesting. (MS)
338! - Revised calculation of pt1 (now done in surface_layer_fluxes).
339!   Bugfix, f_shf_window and f_shf_green were not set at vertical surface
340!   elements. (MS)
341! - merged with branch ebsolver
342!   green building surfaces do not evaporate yet
343!   properties of green wall layers and window layers are taken from wall layers
344!   this input data is missing. (RvT)
345! - Merged with branch radiation (developed by Mohamed Salim)
346! - Revised initialization. (MS)
347! - Rename emiss_surf into emissivity, roughness_wall into z0, albedo_surf into
348!   albedo. (MS)
349! - Move first call of usm_radiatin from usm_init to init_3d_model
350! - fixed problem with near surface temperature
351! - added near surface temperature pt_10cm_h(m), pt_10cm_v(l)%t(m)
352! - does not work with temp profile including stability, ol
353!   pt_10cm = pt1 now
354! - merged with 2357 bugfix, error message for nopointer version
355! - added indoor model coupling with wall heat flux
356! - added green substrate/ dry vegetation layer for buildings
357! - merged with 2232 new surface-type structure
358! - added transmissivity of window tiles
359! - added MOSAIK tile approach for 3 different surfaces (RvT)
360!
361! 2583 2017-10-26 13:58:38Z knoop
362! Bugfix: reverted MPI_Win_allocate_cptr introduction in last commit
363!
364! 2582 2017-10-26 13:19:46Z hellstea
365! Workaround for gnufortran compiler added in usm_calc_svf. CALL MPI_Win_allocate is
366! replaced by CALL MPI_Win_allocate_cptr if defined ( __gnufortran ).
367!
368! 2544 2017-10-13 18:09:32Z maronga
369! Date and time quantities are now read from date_and_time_mod. Solar constant is
370! read from radiation_model_mod
371!
372! 2516 2017-10-04 11:03:04Z suehring
373! Remove tabs
374!
375! 2514 2017-10-04 09:52:37Z suehring
376! upper bounds of 3d output changed from nx+1,ny+1 to nx,ny
377! no output of ghost layer data
378!
379! 2350 2017-08-15 11:48:26Z kanani
380! Bugfix and error message for nopointer version.
381! Additional "! defined(__nopointer)" as workaround to enable compilation of
382! nopointer version.
383!
384! 2318 2017-07-20 17:27:44Z suehring
385! Get topography top index via Function call
386!
387! 2317 2017-07-20 17:27:19Z suehring
388! Bugfix: adjust output of shf. Added support for spinups
389!
390! 2287 2017-06-15 16:46:30Z suehring
391! Bugfix in determination topography-top index
392!
393! 2269 2017-06-09 11:57:32Z suehring
394! Enable restart runs with different number of PEs
395! Bugfixes nopointer branch
396!
397! 2258 2017-06-08 07:55:13Z suehring
398! Bugfix, add pre-preprocessor directives to enable non-parrallel mode
399!
400! 2233 2017-05-30 18:08:54Z suehring
401!
402! 2232 2017-05-30 17:47:52Z suehring
403! Adjustments according to new surface-type structure. Remove usm_wall_heat_flux;
404! insteat, heat fluxes are directly applied in diffusion_s.
405!
406! 2213 2017-04-24 15:10:35Z kanani
407! Removal of output quantities usm_lad and usm_canopy_hr
408!
409! 2209 2017-04-19 09:34:46Z kanani
410! cpp switch __mpi3 removed,
411! minor formatting,
412! small bugfix for division by zero (Krc)
413!
414! 2113 2017-01-12 13:40:46Z kanani
415! cpp switch __mpi3 added for MPI-3 standard code (Ketelsen)
416!
417! 2071 2016-11-17 11:22:14Z maronga
418! Small bugfix (Resler)
419!
420! 2031 2016-10-21 15:11:58Z knoop
421! renamed variable rho to rho_ocean
422!
423! 2024 2016-10-12 16:42:37Z kanani
424! Bugfixes in deallocation of array plantt and reading of csf/csfsurf,
425! optimization of MPI-RMA operations,
426! declaration of pcbl as integer,
427! renamed usm_radnet -> usm_rad_net, usm_canopy_khf -> usm_canopy_hr,
428! splitted arrays svf -> svf & csf, svfsurf -> svfsurf & csfsurf,
429! use of new control parameter varnamelength,
430! added output variables usm_rad_ressw, usm_rad_reslw,
431! minor formatting changes,
432! minor optimizations.
433!
434! 2011 2016-09-19 17:29:57Z kanani
435! Major reformatting according to PALM coding standard (comments, blanks,
436! alphabetical ordering, etc.),
437! removed debug_prints,
438! removed auxiliary SUBROUTINE get_usm_info, instead, USM flag urban_surface is
439! defined in MODULE control_parameters (modules.f90) to avoid circular
440! dependencies,
441! renamed canopy_heat_flux to pc_heating_rate, as meaning of quantity changed.
442!
443! 2007 2016-08-24 15:47:17Z kanani
444! Initial revision
445!
446!
447! Description:
448! ------------
449! 2016/6/9 - Initial version of the USM (Urban Surface Model)
450!            authors: Jaroslav Resler, Pavel Krc
451!                     (Czech Technical University in Prague and Institute of
452!                      Computer Science of the Czech Academy of Sciences, Prague)
453!            with contributions: Michal Belda, Nina Benesova, Ondrej Vlcek
454!            partly inspired by PALM LSM (B. Maronga)
455!            parameterizations of Ra checked with TUF3D (E. S. Krayenhoff)
456!> Module for Urban Surface Model (USM)
457!> The module includes:
458!>    1. radiation model with direct/diffuse radiation, shading, reflections
459!>       and integration with plant canopy
460!>    2. wall and wall surface model
461!>    3. surface layer energy balance
462!>    4. anthropogenic heat (only from transportation so far)
463!>    5. necessary auxiliary subroutines (reading inputs, writing outputs,
464!>       restart simulations, ...)
465!> It also make use of standard radiation and integrates it into
466!> urban surface model.
467!>
468!> Further work:
469!> -------------
470!> 1. Remove global arrays surfouts, surfoutl and only keep track of radiosity
471!>    from surfaces that are visible from local surfaces (i.e. there is a SVF
472!>    where target is local). To do that, radiosity will be exchanged after each
473!>    reflection step using MPI_Alltoall instead of current MPI_Allgather.
474!>
475!> 2. Temporarily large values of surface heat flux can be observed, up to
476!>    1.2 Km/s, which seem to be not realistic.
477!>
478!> @todo Output of _av variables in case of restarts
479!> @todo Revise flux conversion in energy-balance solver
480!> @todo Check optimizations for RMA operations
481!> @todo Alternatives for MPI_WIN_ALLOCATE? (causes problems with openmpi)
482!> @todo Check for load imbalances in CPU measures, e.g. for exchange_horiz_prog
483!>       factor 3 between min and max time
484!> @todo Check divisions in wtend (etc.) calculations for possible division
485!>       by zero, e.g. in case fraq(0,m) + fraq(1,m) = 0?!
486!> @todo Use unit 90 for OPEN/CLOSE of input files (FK)
487!> @todo Move plant canopy stuff into plant canopy code
488!------------------------------------------------------------------------------!
489 MODULE urban_surface_mod
490
491    USE arrays_3d,                                                             &
492        ONLY:  hyp, zu, pt, p, u, v, w, tend, exner, hyrho, prr, q, ql, vpt
493
494    USE calc_mean_profile_mod,                                                 &
495        ONLY:  calc_mean_profile
496
497    USE basic_constants_and_equations_mod,                                     &
498        ONLY:  c_p, g, kappa, pi, r_d, rho_l, l_v, sigma_sb
499
500    USE control_parameters,                                                    &
501        ONLY:  coupling_start_time, topography,                                &
502               debug_output, debug_output_timestep, debug_string,              &
503               dt_3d, humidity, indoor_model,                                  &
504               intermediate_timestep_count, initializing_actions,              &
505               intermediate_timestep_count_max, simulated_time, end_time,      &
506               timestep_scheme, tsc, coupling_char, io_blocks, io_group,       &
507               message_string, time_since_reference_point, surface_pressure,   &
508               pt_surface, large_scale_forcing, lsf_surf,                      &
509               spinup_pt_mean, spinup_time, time_do3d, dt_do3d,                &
510               average_count_3d, varnamelength, urban_surface, dz
511
512    USE bulk_cloud_model_mod,                                                  &
513        ONLY: bulk_cloud_model, precipitation
514               
515    USE cpulog,                                                                &
516        ONLY:  cpu_log, log_point, log_point_s
517
518    USE date_and_time_mod,                                                     &
519        ONLY:  time_utc_init
520
521    USE grid_variables,                                                        &
522        ONLY:  dx, dy, ddx, ddy, ddx2, ddy2
523
524    USE indices,                                                               &
525        ONLY:  nx, ny, nnx, nny, nnz, nxl, nxlg, nxr, nxrg, nyn, nyng, nys,    &
526               nysg, nzb, nzt, nbgp, wall_flags_0
527
528    USE, INTRINSIC :: iso_c_binding 
529
530    USE kinds
531             
532    USE pegrid
533       
534    USE radiation_model_mod,                                                   &
535        ONLY:  albedo_type, radiation_interaction,                             &
536               radiation, rad_sw_in, rad_lw_in, rad_sw_out, rad_lw_out,        &
537               force_radiation_call, iup_u, inorth_u, isouth_u, ieast_u,       &
538               iwest_u, iup_l, inorth_l, isouth_l, ieast_l, iwest_l, id,       &
539               iz, iy, ix,  nsurf, idsvf, ndsvf,                               &
540               idcsf, ndcsf, kdcsf, pct,                                       &
541               nz_urban_b, nz_urban_t, unscheduled_radiation_calls
542
543    USE statistics,                                                            &
544        ONLY:  hom, statistic_regions
545
546    USE surface_mod,                                                           &
547        ONLY:  get_topography_top_index_ji, get_topography_top_index,          &
548               ind_pav_green, ind_veg_wall, ind_wat_win, surf_usm_h,           &
549               surf_usm_v, surface_restore_elements
550
551
552    IMPLICIT NONE
553
554!
555!-- USM model constants
556
557    REAL(wp), PARAMETER ::                     &
558              b_ch               = 6.04_wp,    &  !< Clapp & Hornberger exponent
559              lambda_h_green_dry = 0.19_wp,    &  !< heat conductivity for dry soil   
560              lambda_h_green_sm  = 3.44_wp,    &  !< heat conductivity of the soil matrix
561              lambda_h_water     = 0.57_wp,    &  !< heat conductivity of water
562              psi_sat            = -0.388_wp,  &  !< soil matrix potential at saturation
563              rho_c_soil         = 2.19E6_wp,  &  !< volumetric heat capacity of soil
564              rho_c_water        = 4.20E6_wp      !< volumetric heat capacity of water
565!               m_max_depth        = 0.0002_wp     ! Maximum capacity of the water reservoir (m)
566
567!
568!-- Soil parameters I           alpha_vg,      l_vg_green,    n_vg, gamma_w_green_sat
569    REAL(wp), DIMENSION(0:3,1:7), PARAMETER :: soil_pars = RESHAPE( (/     &
570                                 3.83_wp,  1.250_wp, 1.38_wp,  6.94E-6_wp, &  !< soil 1
571                                 3.14_wp, -2.342_wp, 1.28_wp,  1.16E-6_wp, &  !< soil 2
572                                 0.83_wp, -0.588_wp, 1.25_wp,  0.26E-6_wp, &  !< soil 3
573                                 3.67_wp, -1.977_wp, 1.10_wp,  2.87E-6_wp, &  !< soil 4
574                                 2.65_wp,  2.500_wp, 1.10_wp,  1.74E-6_wp, &  !< soil 5
575                                 1.30_wp,  0.400_wp, 1.20_wp,  0.93E-6_wp, &  !< soil 6
576                                 0.00_wp,  0.00_wp,  0.00_wp,  0.57E-6_wp  &  !< soil 7
577                                 /), (/ 4, 7 /) )
578
579!
580!-- Soil parameters II              swc_sat,     fc,   wilt,    swc_res 
581    REAL(wp), DIMENSION(0:3,1:7), PARAMETER :: m_soil_pars = RESHAPE( (/ &
582                                 0.403_wp, 0.244_wp, 0.059_wp, 0.025_wp, &  !< soil 1
583                                 0.439_wp, 0.347_wp, 0.151_wp, 0.010_wp, &  !< soil 2
584                                 0.430_wp, 0.383_wp, 0.133_wp, 0.010_wp, &  !< soil 3
585                                 0.520_wp, 0.448_wp, 0.279_wp, 0.010_wp, &  !< soil 4
586                                 0.614_wp, 0.541_wp, 0.335_wp, 0.010_wp, &  !< soil 5
587                                 0.766_wp, 0.663_wp, 0.267_wp, 0.010_wp, &  !< soil 6
588                                 0.472_wp, 0.323_wp, 0.171_wp, 0.000_wp  &  !< soil 7
589                                 /), (/ 4, 7 /) )
590!
591!-- value 9999999.9_wp -> generic available or user-defined value must be set
592!-- otherwise -> no generic variable and user setting is optional
593    REAL(wp) :: alpha_vangenuchten = 9999999.9_wp,      &  !< NAMELIST alpha_vg
594                field_capacity = 9999999.9_wp,          &  !< NAMELIST fc
595                hydraulic_conductivity = 9999999.9_wp,  &  !< NAMELIST gamma_w_green_sat
596                l_vangenuchten = 9999999.9_wp,          &  !< NAMELIST l_vg
597                n_vangenuchten = 9999999.9_wp,          &  !< NAMELIST n_vg
598                residual_moisture = 9999999.9_wp,       &  !< NAMELIST m_res
599                saturation_moisture = 9999999.9_wp,     &  !< NAMELIST m_sat
600                wilting_point = 9999999.9_wp               !< NAMELIST m_wilt
601   
602!
603!-- configuration parameters (they can be setup in PALM config)
604    LOGICAL ::  usm_material_model = .TRUE.        !< flag parameter indicating wheather the  model of heat in materials is used
605    LOGICAL ::  usm_anthropogenic_heat = .FALSE.   !< flag parameter indicating wheather the anthropogenic heat sources
606                                                   !< (e.g.transportation) are used
607    LOGICAL ::  force_radiation_call_l = .FALSE.   !< flag parameter for unscheduled radiation model calls
608    LOGICAL ::  read_wall_temp_3d = .FALSE.
609    LOGICAL ::  usm_wall_mod = .FALSE.             !< reduces conductivity of the first 2 wall layers by factor 0.1
610
611
612    INTEGER(iwp) ::  building_type = 1               !< default building type (preleminary setting)
613    INTEGER(iwp) ::  land_category = 2               !< default category for land surface
614    INTEGER(iwp) ::  wall_category = 2               !< default category for wall surface over pedestrian zone
615    INTEGER(iwp) ::  pedestrian_category = 2         !< default category for wall surface in pedestrian zone
616    INTEGER(iwp) ::  roof_category = 2               !< default category for root surface
617    REAL(wp)     ::  roughness_concrete = 0.001_wp   !< roughness length of average concrete surface
618!
619!-- Indices of input attributes in building_pars for (above) ground floor level
620    INTEGER(iwp) ::  ind_alb_wall_agfl     = 38   !< index in input list for albedo_type of wall above ground floor level
621    INTEGER(iwp) ::  ind_alb_wall_gfl      = 66   !< index in input list for albedo_type of wall ground floor level
622    INTEGER(iwp) ::  ind_alb_wall_r        = 101  !< index in input list for albedo_type of wall roof
623    INTEGER(iwp) ::  ind_alb_green_agfl    = 39   !< index in input list for albedo_type of green above ground floor level
624    INTEGER(iwp) ::  ind_alb_green_gfl     = 78   !< index in input list for albedo_type of green ground floor level
625    INTEGER(iwp) ::  ind_alb_green_r       = 117  !< index in input list for albedo_type of green roof
626    INTEGER(iwp) ::  ind_alb_win_agfl      = 40   !< index in input list for albedo_type of window fraction above ground floor level
627    INTEGER(iwp) ::  ind_alb_win_gfl       = 77   !< index in input list for albedo_type of window fraction ground floor level
628    INTEGER(iwp) ::  ind_alb_win_r         = 115  !< index in input list for albedo_type of window fraction roof
629    INTEGER(iwp) ::  ind_c_surface         = 45   !< index in input list for heat capacity wall surface
630    INTEGER(iwp) ::  ind_c_surface_green   = 48   !< index in input list for heat capacity green surface
631    INTEGER(iwp) ::  ind_c_surface_win     = 47   !< index in input list for heat capacity window surface
632    INTEGER(iwp) ::  ind_emis_wall_agfl    = 14   !< index in input list for wall emissivity, above ground floor level
633    INTEGER(iwp) ::  ind_emis_wall_gfl     = 32   !< index in input list for wall emissivity, ground floor level
634    INTEGER(iwp) ::  ind_emis_wall_r       = 100  !< index in input list for wall emissivity, roof
635    INTEGER(iwp) ::  ind_emis_green_agfl   = 15   !< index in input list for green emissivity, above ground floor level
636    INTEGER(iwp) ::  ind_emis_green_gfl    = 34   !< index in input list for green emissivity, ground floor level
637    INTEGER(iwp) ::  ind_emis_green_r      = 116  !< index in input list for green emissivity, roof
638    INTEGER(iwp) ::  ind_emis_win_agfl     = 16   !< index in input list for window emissivity, above ground floor level
639    INTEGER(iwp) ::  ind_emis_win_gfl      = 33   !< index in input list for window emissivity, ground floor level
640    INTEGER(iwp) ::  ind_emis_win_r        = 113  !< index in input list for window emissivity, roof
641    INTEGER(iwp) ::  ind_gflh              = 20   !< index in input list for ground floor level height
642    INTEGER(iwp) ::  ind_green_frac_w_agfl = 2    !< index in input list for green fraction on wall, above ground floor level
643    INTEGER(iwp) ::  ind_green_frac_w_gfl  = 23   !< index in input list for green fraction on wall, ground floor level
644    INTEGER(iwp) ::  ind_green_frac_r_agfl = 3    !< index in input list for green fraction on roof, above ground floor level
645    INTEGER(iwp) ::  ind_green_frac_r_gfl  = 24   !< index in input list for green fraction on roof, ground floor level
646    INTEGER(iwp) ::  ind_hc1_agfl          = 6    !< index in input list for heat capacity at first wall layer,
647                                                  !< above ground floor level
648    INTEGER(iwp) ::  ind_hc1_gfl           = 26   !< index in input list for heat capacity at first wall layer, ground floor level
649    INTEGER(iwp) ::  ind_hc1_wall_r        = 94   !< index in input list for heat capacity at first wall layer, roof
650    INTEGER(iwp) ::  ind_hc1_win_agfl      = 83   !< index in input list for heat capacity at first window layer,
651                                                  !< above ground floor level
652    INTEGER(iwp) ::  ind_hc1_win_gfl       = 71   !< index in input list for heat capacity at first window layer,
653                                                  !< ground floor level
654    INTEGER(iwp) ::  ind_hc1_win_r         = 107  !< index in input list for heat capacity at first window layer, roof
655    INTEGER(iwp) ::  ind_hc2_agfl          = 7    !< index in input list for heat capacity at second wall layer,
656                                                  !< above ground floor level
657    INTEGER(iwp) ::  ind_hc2_gfl           = 27   !< index in input list for heat capacity at second wall layer, ground floor level
658    INTEGER(iwp) ::  ind_hc2_wall_r        = 95   !< index in input list for heat capacity at second wall layer, roof
659    INTEGER(iwp) ::  ind_hc2_win_agfl      = 84   !< index in input list for heat capacity at second window layer,
660                                                  !< above ground floor level
661    INTEGER(iwp) ::  ind_hc2_win_gfl       = 72   !< index in input list for heat capacity at second window layer,
662                                                  !< ground floor level
663    INTEGER(iwp) ::  ind_hc2_win_r         = 108  !< index in input list for heat capacity at second window layer, roof
664    INTEGER(iwp) ::  ind_hc3_agfl          = 8    !< index in input list for heat capacity at third wall layer,
665                                                  !< above ground floor level
666    INTEGER(iwp) ::  ind_hc3_gfl           = 28   !< index in input list for heat capacity at third wall layer, ground floor level
667    INTEGER(iwp) ::  ind_hc3_wall_r        = 96   !< index in input list for heat capacity at third wall layer, roof
668    INTEGER(iwp) ::  ind_hc3_win_agfl      = 85   !< index in input list for heat capacity at third window layer,
669                                                  !< above ground floor level
670    INTEGER(iwp) ::  ind_hc3_win_gfl       = 73   !< index in input list for heat capacity at third window layer,
671                                                  !< ground floor level
672    INTEGER(iwp) ::  ind_hc3_win_r         = 109  !< index in input list for heat capacity at third window layer, roof
673    INTEGER(iwp) ::  ind_indoor_target_temp_summer = 12
674    INTEGER(iwp) ::  ind_indoor_target_temp_winter = 13
675    INTEGER(iwp) ::  ind_lai_r_agfl        = 4    !< index in input list for LAI on roof, above ground floor level
676    INTEGER(iwp) ::  ind_lai_r_gfl         = 4  !< index in input list for LAI on roof, ground floor level
677    INTEGER(iwp) ::  ind_lai_w_agfl        = 5    !< index in input list for LAI on wall, above ground floor level
678    INTEGER(iwp) ::  ind_lai_w_gfl         = 25   !< index in input list for LAI on wall, ground floor level
679    INTEGER(iwp) ::  ind_lambda_surf       = 46   !< index in input list for thermal conductivity of wall surface
680    INTEGER(iwp) ::  ind_lambda_surf_green = 50   !< index in input list for thermal conductivity of green surface
681    INTEGER(iwp) ::  ind_lambda_surf_win   = 49   !< index in input list for thermal conductivity of window surface
682    INTEGER(iwp) ::  ind_tc1_agfl          = 9    !< index in input list for thermal conductivity at first wall layer,
683                                                  !< above ground floor level
684    INTEGER(iwp) ::  ind_tc1_gfl           = 29   !< index in input list for thermal conductivity at first wall layer,
685                                                  !< ground floor level
686    INTEGER(iwp) ::  ind_tc1_wall_r        = 97   !< index in input list for thermal conductivity at first wall layer, roof
687    INTEGER(iwp) ::  ind_tc1_win_agfl      = 86   !< index in input list for thermal conductivity at first window layer,
688                                                  !< above ground floor level
689    INTEGER(iwp) ::  ind_tc1_win_gfl       = 74   !< index in input list for thermal conductivity at first window layer,
690                                                  !< ground floor level
691    INTEGER(iwp) ::  ind_tc1_win_r         = 110  !< index in input list for thermal conductivity at first window layer, roof
692    INTEGER(iwp) ::  ind_tc2_agfl          = 10   !< index in input list for thermal conductivity at second wall layer,
693                                                  !< above ground floor level
694    INTEGER(iwp) ::  ind_tc2_gfl           = 30   !< index in input list for thermal conductivity at second wall layer,
695                                                  !< ground floor level
696    INTEGER(iwp) ::  ind_tc2_wall_r        = 98   !< index in input list for thermal conductivity at second wall layer, roof
697    INTEGER(iwp) ::  ind_tc2_win_agfl      = 87   !< index in input list for thermal conductivity at second window layer,
698                                                  !< above ground floor level
699    INTEGER(iwp) ::  ind_tc2_win_gfl       = 75   !< index in input list for thermal conductivity at second window layer,
700                                                  !< ground floor level
701    INTEGER(iwp) ::  ind_tc2_win_r         = 111  !< index in input list for thermal conductivity at second window layer,
702                                                  !< ground floor level
703    INTEGER(iwp) ::  ind_tc3_agfl          = 11   !< index in input list for thermal conductivity at third wall layer,
704                                                  !< above ground floor level
705    INTEGER(iwp) ::  ind_tc3_gfl           = 31   !< index in input list for thermal conductivity at third wall layer,
706                                                  !< ground floor level
707    INTEGER(iwp) ::  ind_tc3_wall_r        = 99   !< index in input list for thermal conductivity at third wall layer, roof
708    INTEGER(iwp) ::  ind_tc3_win_agfl      = 88   !< index in input list for thermal conductivity at third window layer,
709                                                  !< above ground floor level
710    INTEGER(iwp) ::  ind_tc3_win_gfl       = 76   !< index in input list for thermal conductivity at third window layer,
711                                                  !< ground floor level
712    INTEGER(iwp) ::  ind_tc3_win_r         = 112  !< index in input list for thermal conductivity at third window layer, roof
713    INTEGER(iwp) ::  ind_thick_1_agfl      = 41   !< index for wall layer thickness - 1st layer above ground floor level
714    INTEGER(iwp) ::  ind_thick_1_gfl       = 62   !< index for wall layer thickness - 1st layer ground floor level
715    INTEGER(iwp) ::  ind_thick_1_wall_r    = 90   !< index for wall layer thickness - 1st layer roof
716    INTEGER(iwp) ::  ind_thick_1_win_agfl  = 79   !< index for window layer thickness - 1st layer above ground floor level
717    INTEGER(iwp) ::  ind_thick_1_win_gfl   = 67   !< index for window layer thickness - 1st layer ground floor level
718    INTEGER(iwp) ::  ind_thick_1_win_r     = 103  !< index for window layer thickness - 1st layer roof
719    INTEGER(iwp) ::  ind_thick_2_agfl      = 42   !< index for wall layer thickness - 2nd layer above ground floor level
720    INTEGER(iwp) ::  ind_thick_2_gfl       = 63   !< index for wall layer thickness - 2nd layer ground floor level
721    INTEGER(iwp) ::  ind_thick_2_wall_r    = 91   !< index for wall layer thickness - 2nd layer roof
722    INTEGER(iwp) ::  ind_thick_2_win_agfl  = 80   !< index for window layer thickness - 2nd layer above ground floor level
723    INTEGER(iwp) ::  ind_thick_2_win_gfl   = 68   !< index for window layer thickness - 2nd layer ground floor level
724    INTEGER(iwp) ::  ind_thick_2_win_r     = 104  !< index for window layer thickness - 2nd layer roof
725    INTEGER(iwp) ::  ind_thick_3_agfl      = 43   !< index for wall layer thickness - 3rd layer above ground floor level
726    INTEGER(iwp) ::  ind_thick_3_gfl       = 64   !< index for wall layer thickness - 3rd layer ground floor level
727    INTEGER(iwp) ::  ind_thick_3_wall_r    = 92   !< index for wall layer thickness - 3rd layer roof
728    INTEGER(iwp) ::  ind_thick_3_win_agfl  = 81   !< index for window layer thickness - 3rd layer above ground floor level
729    INTEGER(iwp) ::  ind_thick_3_win_gfl   = 69   !< index for window layer thickness - 3rd layer ground floor level 
730    INTEGER(iwp) ::  ind_thick_3_win_r     = 105  !< index for window layer thickness - 3rd layer roof
731    INTEGER(iwp) ::  ind_thick_4_agfl      = 44   !< index for wall layer thickness - 4th layer above ground floor level
732    INTEGER(iwp) ::  ind_thick_4_gfl       = 65   !< index for wall layer thickness - 4th layer ground floor level
733    INTEGER(iwp) ::  ind_thick_4_wall_r    = 93   !< index for wall layer thickness - 4st layer roof
734    INTEGER(iwp) ::  ind_thick_4_win_agfl  = 82   !< index for window layer thickness - 4th layer above ground floor level
735    INTEGER(iwp) ::  ind_thick_4_win_gfl   = 70   !< index for window layer thickness - 4th layer ground floor level
736    INTEGER(iwp) ::  ind_thick_4_win_r     = 106  !< index for window layer thickness - 4th layer roof
737    INTEGER(iwp) ::  ind_trans_agfl        = 17   !< index in input list for window transmissivity, above ground floor level
738    INTEGER(iwp) ::  ind_trans_gfl         = 35   !< index in input list for window transmissivity, ground floor level
739    INTEGER(iwp) ::  ind_trans_r           = 114  !< index in input list for window transmissivity, roof
740    INTEGER(iwp) ::  ind_wall_frac_agfl    = 0    !< index in input list for wall fraction, above ground floor level
741    INTEGER(iwp) ::  ind_wall_frac_gfl     = 21   !< index in input list for wall fraction, ground floor level
742    INTEGER(iwp) ::  ind_wall_frac_r       = 89   !< index in input list for wall fraction, roof
743    INTEGER(iwp) ::  ind_win_frac_agfl     = 1    !< index in input list for window fraction, above ground floor level
744    INTEGER(iwp) ::  ind_win_frac_gfl      = 22   !< index in input list for window fraction, ground floor level
745    INTEGER(iwp) ::  ind_win_frac_r        = 102  !< index in input list for window fraction, roof
746    INTEGER(iwp) ::  ind_z0_agfl           = 18   !< index in input list for z0, above ground floor level
747    INTEGER(iwp) ::  ind_z0_gfl            = 36   !< index in input list for z0, ground floor level
748    INTEGER(iwp) ::  ind_z0qh_agfl         = 19   !< index in input list for z0h / z0q, above ground floor level
749    INTEGER(iwp) ::  ind_z0qh_gfl          = 37   !< index in input list for z0h / z0q, ground floor level
750    INTEGER(iwp) ::  ind_green_type_roof   = 118  !< index in input list for type of green roof
751
752
753    REAL(wp)  ::  roof_height_limit = 4.0_wp         !< height for distinguish between land surfaces and roofs
754    REAL(wp)  ::  ground_floor_level = 4.0_wp        !< default ground floor level
755
756
757    CHARACTER(37), DIMENSION(0:7), PARAMETER :: building_type_name = (/     &
758                                   'user-defined                         ', &  !< type 0
759                                   'residential - 1950                   ', &  !< type  1
760                                   'residential 1951 - 2000              ', &  !< type  2
761                                   'residential 2001 -                   ', &  !< type  3
762                                   'office - 1950                        ', &  !< type  4
763                                   'office 1951 - 2000                   ', &  !< type  5
764                                   'office 2001 -                        ', &  !< type  6
765                                   'bridges                              '  &  !< type  7
766                                                                     /)
767
768
769!
770!-- Building facade/wall/green/window properties (partly according to PIDS).
771!-- Initialization of building_pars is outsourced to usm_init_pars. This is
772!-- needed because of the huge number of attributes given in building_pars
773!-- (>700), while intel and gfortran compiler have hard limit of continuation
774!-- lines of 511.
775    REAL(wp), DIMENSION(0:133,1:7) ::  building_pars
776!
777!-- Type for surface temperatures at vertical walls. Is not necessary for horizontal walls.
778    TYPE t_surf_vertical
779       REAL(wp), DIMENSION(:), ALLOCATABLE         :: t
780    END TYPE t_surf_vertical
781!
782!-- Type for wall temperatures at vertical walls. Is not necessary for horizontal walls.
783    TYPE t_wall_vertical
784       REAL(wp), DIMENSION(:,:), ALLOCATABLE       :: t
785    END TYPE t_wall_vertical
786
787    TYPE surf_type_usm
788       REAL(wp), DIMENSION(:),   ALLOCATABLE ::  var_usm_1d  !< 1D prognostic variable
789       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  var_usm_2d  !< 2D prognostic variable
790    END TYPE surf_type_usm
791   
792    TYPE(surf_type_usm), POINTER  ::  m_liq_usm_h,        &  !< liquid water reservoir (m), horizontal surface elements
793                                      m_liq_usm_h_p          !< progn. liquid water reservoir (m), horizontal surface elements
794
795    TYPE(surf_type_usm), TARGET   ::  m_liq_usm_h_1,      &  !<
796                                      m_liq_usm_h_2          !<
797
798    TYPE(surf_type_usm), DIMENSION(:), POINTER  ::        &
799                                      m_liq_usm_v,        &  !< liquid water reservoir (m), vertical surface elements
800                                      m_liq_usm_v_p          !< progn. liquid water reservoir (m), vertical surface elements
801
802    TYPE(surf_type_usm), DIMENSION(0:3), TARGET   ::      &
803                                      m_liq_usm_v_1,      &  !<
804                                      m_liq_usm_v_2          !<
805
806    TYPE(surf_type_usm), TARGET ::  tm_liq_usm_h_m      !< liquid water reservoir tendency (m), horizontal surface elements
807    TYPE(surf_type_usm), DIMENSION(0:3), TARGET ::  tm_liq_usm_v_m      !< liquid water reservoir tendency (m),
808                                                                        !< vertical surface elements
809
810!
811!-- anthropogenic heat sources
812    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE        ::  aheat             !< daily average of anthropogenic heat (W/m2)
813    REAL(wp), DIMENSION(:,:), ALLOCATABLE          ::  aheatprof         !< diurnal profiles of anthropogenic heat
814                                                                         !< for particular layers
815    INTEGER(iwp)                                   ::  naheatlayers = 1  !< number of layers of anthropogenic heat
816
817!
818!-- wall surface model
819!-- wall surface model constants
820    INTEGER(iwp), PARAMETER                        :: nzb_wall = 0       !< inner side of the wall model (to be switched)
821    INTEGER(iwp), PARAMETER                        :: nzt_wall = 3       !< outer side of the wall model (to be switched)
822    INTEGER(iwp), PARAMETER                        :: nzw = 4            !< number of wall layers (fixed for now)
823
824    REAL(wp), DIMENSION(nzb_wall:nzt_wall)         :: zwn_default        = (/0.0242_wp, 0.0969_wp, 0.346_wp, 1.0_wp /)
825    REAL(wp), DIMENSION(nzb_wall:nzt_wall)         :: zwn_default_window = (/0.25_wp,   0.5_wp,    0.75_wp,  1.0_wp /)
826    REAL(wp), DIMENSION(nzb_wall:nzt_wall)         :: zwn_default_green  = (/0.25_wp,   0.5_wp,    0.75_wp,  1.0_wp /)
827                                                                         !< normalized soil, wall and roof, window and
828                                                                         !<green layer depths (m/m)
829
830    REAL(wp)                                       :: wall_inner_temperature   = 295.0_wp    !< temperature of the inner wall
831                                                                                             !< surface (~22 degrees C) (K)
832    REAL(wp)                                       :: roof_inner_temperature   = 295.0_wp    !< temperature of the inner roof
833                                                                                             !< surface (~22 degrees C) (K)
834    REAL(wp)                                       :: soil_inner_temperature   = 288.0_wp    !< temperature of the deep soil
835                                                                                             !< (~15 degrees C) (K)
836    REAL(wp)                                       :: window_inner_temperature = 295.0_wp    !< temperature of the inner window
837                                                                                             !< surface (~22 degrees C) (K)
838
839    REAL(wp)                                       :: m_total = 0.0_wp  !< weighted total water content of the soil (m3/m3)
840    INTEGER(iwp)                                   :: soil_type
841
842!
843!-- surface and material model variables for walls, ground, roofs
844    REAL(wp), DIMENSION(:), ALLOCATABLE            :: zwn                !< normalized wall layer depths (m)
845    REAL(wp), DIMENSION(:), ALLOCATABLE            :: zwn_window         !< normalized window layer depths (m)
846    REAL(wp), DIMENSION(:), ALLOCATABLE            :: zwn_green          !< normalized green layer depths (m)
847
848    REAL(wp), DIMENSION(:), POINTER                :: t_surf_wall_h
849    REAL(wp), DIMENSION(:), POINTER                :: t_surf_wall_h_p 
850    REAL(wp), DIMENSION(:), POINTER                :: t_surf_window_h
851    REAL(wp), DIMENSION(:), POINTER                :: t_surf_window_h_p 
852    REAL(wp), DIMENSION(:), POINTER                :: t_surf_green_h
853    REAL(wp), DIMENSION(:), POINTER                :: t_surf_green_h_p 
854
855    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_wall_h_1
856    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_wall_h_2
857    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_window_h_1
858    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_window_h_2
859    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_h_1
860    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_h_2
861
862    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_wall_v
863    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_wall_v_p
864    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_window_v
865    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_window_v_p
866    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_green_v
867    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_green_v_p
868
869    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_wall_v_1
870    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_wall_v_2
871    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_window_v_1
872    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_window_v_2
873    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_green_v_1
874    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_green_v_2
875
876!
877!-- Energy balance variables
878!-- parameters of the land, roof and wall surfaces
879
880    REAL(wp), DIMENSION(:,:), POINTER                :: t_wall_h, t_wall_h_p
881    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h_1, t_wall_h_2
882    REAL(wp), DIMENSION(:,:), POINTER                :: t_window_h, t_window_h_p
883    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_window_h_1, t_window_h_2
884    REAL(wp), DIMENSION(:,:), POINTER                :: t_green_h, t_green_h_p
885    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_green_h_1, t_green_h_2
886    REAL(wp), DIMENSION(:,:), POINTER                :: swc_h, rootfr_h, wilt_h, fc_h, swc_sat_h, swc_h_p, swc_res_h
887    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: swc_h_1, rootfr_h_1, &
888                                                        wilt_h_1, fc_h_1, swc_sat_h_1, swc_h_2, swc_res_h_1
889   
890
891    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: t_wall_v, t_wall_v_p
892    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v_1, t_wall_v_2
893    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: t_window_v, t_window_v_p
894    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_window_v_1, t_window_v_2
895    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: t_green_v, t_green_v_p
896    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v_1, t_green_v_2
897    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: swc_v, swc_v_p
898    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: swc_v_1, swc_v_2
899
900!
901!-- Surface and material parameters classes (surface_type)
902!-- albedo, emissivity, lambda_surf, roughness, thickness, volumetric heat capacity, thermal conductivity
903    INTEGER(iwp)                                   :: n_surface_types       !< number of the wall type categories
904    INTEGER(iwp), PARAMETER                        :: n_surface_params = 9  !< number of parameters for each type of the wall
905    INTEGER(iwp), PARAMETER                        :: ialbedo  = 1          !< albedo of the surface
906    INTEGER(iwp), PARAMETER                        :: iemiss   = 2          !< emissivity of the surface
907    INTEGER(iwp), PARAMETER                        :: ilambdas = 3          !< heat conductivity lambda S between surface
908                                                                            !< and material ( W m-2 K-1 )
909    INTEGER(iwp), PARAMETER                        :: irough   = 4          !< roughness length z0 for movements
910    INTEGER(iwp), PARAMETER                        :: iroughh  = 5          !< roughness length z0h for scalars
911                                                                            !< (heat, humidity,...)
912    INTEGER(iwp), PARAMETER                        :: icsurf   = 6          !< Surface skin layer heat capacity (J m-2 K-1 )
913    INTEGER(iwp), PARAMETER                        :: ithick   = 7          !< thickness of the surface (wall, roof, land)  ( m )
914    INTEGER(iwp), PARAMETER                        :: irhoC    = 8          !< volumetric heat capacity rho*C of
915                                                                            !< the material ( J m-3 K-1 )
916    INTEGER(iwp), PARAMETER                        :: ilambdah = 9          !< thermal conductivity lambda H
917                                                                            !< of the wall (W m-1 K-1 )
918    CHARACTER(12), DIMENSION(:), ALLOCATABLE       :: surface_type_names    !< names of wall types (used only for reports)
919    INTEGER(iwp), DIMENSION(:), ALLOCATABLE        :: surface_type_codes    !< codes of wall types
920    REAL(wp), DIMENSION(:,:), ALLOCATABLE          :: surface_params        !< parameters of wall types
921
922!
923!-- interfaces of subroutines accessed from outside of this module
924    INTERFACE usm_3d_data_averaging
925       MODULE PROCEDURE usm_3d_data_averaging
926    END INTERFACE usm_3d_data_averaging
927
928    INTERFACE usm_boundary_condition
929       MODULE PROCEDURE usm_boundary_condition
930    END INTERFACE usm_boundary_condition
931
932    INTERFACE usm_check_data_output
933       MODULE PROCEDURE usm_check_data_output
934    END INTERFACE usm_check_data_output
935   
936    INTERFACE usm_check_parameters
937       MODULE PROCEDURE usm_check_parameters
938    END INTERFACE usm_check_parameters
939   
940    INTERFACE usm_data_output_3d
941       MODULE PROCEDURE usm_data_output_3d
942    END INTERFACE usm_data_output_3d
943   
944    INTERFACE usm_define_netcdf_grid
945       MODULE PROCEDURE usm_define_netcdf_grid
946    END INTERFACE usm_define_netcdf_grid
947
948    INTERFACE usm_init
949       MODULE PROCEDURE usm_init
950    END INTERFACE usm_init
951
952    INTERFACE usm_init_arrays
953       MODULE PROCEDURE usm_init_arrays
954    END INTERFACE usm_init_arrays
955
956    INTERFACE usm_material_heat_model
957       MODULE PROCEDURE usm_material_heat_model
958    END INTERFACE usm_material_heat_model
959   
960    INTERFACE usm_green_heat_model
961       MODULE PROCEDURE usm_green_heat_model
962    END INTERFACE usm_green_heat_model
963   
964    INTERFACE usm_parin
965       MODULE PROCEDURE usm_parin
966    END INTERFACE usm_parin
967
968    INTERFACE usm_rrd_local 
969       MODULE PROCEDURE usm_rrd_local
970    END INTERFACE usm_rrd_local
971
972    INTERFACE usm_surface_energy_balance
973       MODULE PROCEDURE usm_surface_energy_balance
974    END INTERFACE usm_surface_energy_balance
975   
976    INTERFACE usm_swap_timelevel
977       MODULE PROCEDURE usm_swap_timelevel
978    END INTERFACE usm_swap_timelevel
979       
980    INTERFACE usm_wrd_local
981       MODULE PROCEDURE usm_wrd_local
982    END INTERFACE usm_wrd_local
983
984   
985    SAVE
986
987    PRIVATE 
988
989!
990!-- Public functions
991    PUBLIC usm_boundary_condition, usm_check_parameters, usm_init,               &
992           usm_rrd_local,                                                        & 
993           usm_surface_energy_balance, usm_material_heat_model,                  &
994           usm_swap_timelevel, usm_check_data_output, usm_3d_data_averaging,     &
995           usm_data_output_3d, usm_define_netcdf_grid, usm_parin,                &
996           usm_wrd_local, usm_init_arrays
997
998!
999!-- Public parameters, constants and initial values
1000    PUBLIC usm_anthropogenic_heat, usm_material_model, usm_wall_mod, &
1001           usm_green_heat_model, building_pars,                      &
1002           nzb_wall, nzt_wall, t_wall_h, t_wall_v,                   &
1003           t_window_h, t_window_v, building_type
1004
1005
1006
1007 CONTAINS
1008
1009!------------------------------------------------------------------------------!
1010! Description:
1011! ------------
1012!> This subroutine creates the necessary indices of the urban surfaces
1013!> and plant canopy and it allocates the needed arrays for USM
1014!------------------------------------------------------------------------------!
1015    SUBROUTINE usm_init_arrays
1016   
1017        IMPLICIT NONE
1018       
1019        INTEGER(iwp) ::  l
1020
1021        IF ( debug_output )  CALL debug_message( 'usm_init_arrays', 'start' )
1022
1023!
1024!--     Allocate radiation arrays which are part of the new data type.
1025!--     For horizontal surfaces.
1026        ALLOCATE ( surf_usm_h%surfhf(1:surf_usm_h%ns)    )
1027        ALLOCATE ( surf_usm_h%rad_net_l(1:surf_usm_h%ns) )
1028!
1029!--     For vertical surfaces
1030        DO  l = 0, 3
1031           ALLOCATE ( surf_usm_v(l)%surfhf(1:surf_usm_v(l)%ns)    )
1032           ALLOCATE ( surf_usm_v(l)%rad_net_l(1:surf_usm_v(l)%ns) )
1033        ENDDO
1034
1035!
1036!--     Wall surface model
1037!--     allocate arrays for wall surface model and define pointers
1038!--     allocate array of wall types and wall parameters
1039        ALLOCATE ( surf_usm_h%surface_types(1:surf_usm_h%ns)      )
1040        ALLOCATE ( surf_usm_h%building_type(1:surf_usm_h%ns)      )
1041        ALLOCATE ( surf_usm_h%building_type_name(1:surf_usm_h%ns) )
1042        surf_usm_h%building_type      = 0
1043        surf_usm_h%building_type_name = 'none'
1044        DO  l = 0, 3
1045           ALLOCATE ( surf_usm_v(l)%surface_types(1:surf_usm_v(l)%ns)      )
1046           ALLOCATE ( surf_usm_v(l)%building_type(1:surf_usm_v(l)%ns)      )
1047           ALLOCATE ( surf_usm_v(l)%building_type_name(1:surf_usm_v(l)%ns) )
1048           surf_usm_v(l)%building_type      = 0
1049           surf_usm_v(l)%building_type_name = 'none'
1050        ENDDO
1051!
1052!--     Allocate albedo_type and albedo. Each surface element
1053!--     has 3 values, 0: wall fraction, 1: green fraction, 2: window fraction.
1054        ALLOCATE ( surf_usm_h%albedo_type(0:2,1:surf_usm_h%ns) )
1055        ALLOCATE ( surf_usm_h%albedo(0:2,1:surf_usm_h%ns)      )
1056        surf_usm_h%albedo_type = albedo_type
1057        DO  l = 0, 3
1058           ALLOCATE ( surf_usm_v(l)%albedo_type(0:2,1:surf_usm_v(l)%ns) )
1059           ALLOCATE ( surf_usm_v(l)%albedo(0:2,1:surf_usm_v(l)%ns)      )
1060           surf_usm_v(l)%albedo_type = albedo_type
1061        ENDDO       
1062
1063!
1064!--     Allocate indoor target temperature for summer and winter
1065        ALLOCATE ( surf_usm_h%target_temp_summer(1:surf_usm_h%ns) )
1066        ALLOCATE ( surf_usm_h%target_temp_winter(1:surf_usm_h%ns) )
1067        DO  l = 0, 3
1068           ALLOCATE ( surf_usm_v(l)%target_temp_summer(1:surf_usm_v(l)%ns) )
1069           ALLOCATE ( surf_usm_v(l)%target_temp_winter(1:surf_usm_v(l)%ns) )
1070        ENDDO
1071!
1072!--     In case the indoor model is applied, allocate memory for waste heat
1073!--     and indoor temperature.
1074        IF ( indoor_model )  THEN
1075           ALLOCATE ( surf_usm_h%waste_heat(1:surf_usm_h%ns) )
1076           surf_usm_h%waste_heat = 0.0_wp
1077           DO  l = 0, 3
1078              ALLOCATE ( surf_usm_v(l)%waste_heat(1:surf_usm_v(l)%ns) )
1079              surf_usm_v(l)%waste_heat = 0.0_wp
1080           ENDDO
1081        ENDIF
1082!
1083!--     Allocate flag indicating ground floor level surface elements
1084        ALLOCATE ( surf_usm_h%ground_level(1:surf_usm_h%ns) ) 
1085        DO  l = 0, 3
1086           ALLOCATE ( surf_usm_v(l)%ground_level(1:surf_usm_v(l)%ns) )
1087        ENDDO   
1088!
1089!--      Allocate arrays for relative surface fraction.
1090!--      0 - wall fraction, 1 - green fraction, 2 - window fraction
1091         ALLOCATE ( surf_usm_h%frac(0:2,1:surf_usm_h%ns) )
1092         surf_usm_h%frac = 0.0_wp
1093         DO  l = 0, 3
1094            ALLOCATE ( surf_usm_v(l)%frac(0:2,1:surf_usm_v(l)%ns) )
1095            surf_usm_v(l)%frac = 0.0_wp
1096         ENDDO
1097
1098!
1099!--     wall and roof surface parameters. First for horizontal surfaces
1100        ALLOCATE ( surf_usm_h%isroof_surf(1:surf_usm_h%ns)        )
1101        ALLOCATE ( surf_usm_h%lambda_surf(1:surf_usm_h%ns)        )
1102        ALLOCATE ( surf_usm_h%lambda_surf_window(1:surf_usm_h%ns) )
1103        ALLOCATE ( surf_usm_h%lambda_surf_green(1:surf_usm_h%ns)  )
1104        ALLOCATE ( surf_usm_h%c_surface(1:surf_usm_h%ns)          )
1105        ALLOCATE ( surf_usm_h%c_surface_window(1:surf_usm_h%ns)   )
1106        ALLOCATE ( surf_usm_h%c_surface_green(1:surf_usm_h%ns)    )
1107        ALLOCATE ( surf_usm_h%transmissivity(1:surf_usm_h%ns)     )
1108        ALLOCATE ( surf_usm_h%lai(1:surf_usm_h%ns)                )
1109        ALLOCATE ( surf_usm_h%emissivity(0:2,1:surf_usm_h%ns)     )
1110        ALLOCATE ( surf_usm_h%r_a(1:surf_usm_h%ns)                )
1111        ALLOCATE ( surf_usm_h%r_a_green(1:surf_usm_h%ns)          )
1112        ALLOCATE ( surf_usm_h%r_a_window(1:surf_usm_h%ns)         )
1113        ALLOCATE ( surf_usm_h%green_type_roof(1:surf_usm_h%ns)    )
1114        ALLOCATE ( surf_usm_h%r_s(1:surf_usm_h%ns)                )
1115       
1116!
1117!--     For vertical surfaces.
1118        DO  l = 0, 3
1119           ALLOCATE ( surf_usm_v(l)%lambda_surf(1:surf_usm_v(l)%ns)        )
1120           ALLOCATE ( surf_usm_v(l)%c_surface(1:surf_usm_v(l)%ns)          )
1121           ALLOCATE ( surf_usm_v(l)%lambda_surf_window(1:surf_usm_v(l)%ns) )
1122           ALLOCATE ( surf_usm_v(l)%c_surface_window(1:surf_usm_v(l)%ns)   )
1123           ALLOCATE ( surf_usm_v(l)%lambda_surf_green(1:surf_usm_v(l)%ns)  )
1124           ALLOCATE ( surf_usm_v(l)%c_surface_green(1:surf_usm_v(l)%ns)    )
1125           ALLOCATE ( surf_usm_v(l)%transmissivity(1:surf_usm_v(l)%ns)     )
1126           ALLOCATE ( surf_usm_v(l)%lai(1:surf_usm_v(l)%ns)                )
1127           ALLOCATE ( surf_usm_v(l)%emissivity(0:2,1:surf_usm_v(l)%ns)     )
1128           ALLOCATE ( surf_usm_v(l)%r_a(1:surf_usm_v(l)%ns)                )
1129           ALLOCATE ( surf_usm_v(l)%r_a_green(1:surf_usm_v(l)%ns)          )
1130           ALLOCATE ( surf_usm_v(l)%r_a_window(1:surf_usm_v(l)%ns)         )           
1131           ALLOCATE ( surf_usm_v(l)%r_s(1:surf_usm_v(l)%ns)                )
1132        ENDDO
1133
1134!       
1135!--     allocate wall and roof material parameters. First for horizontal surfaces
1136        ALLOCATE ( surf_usm_h%thickness_wall(1:surf_usm_h%ns)                    )
1137        ALLOCATE ( surf_usm_h%thickness_window(1:surf_usm_h%ns)                  )
1138        ALLOCATE ( surf_usm_h%thickness_green(1:surf_usm_h%ns)                   )
1139        ALLOCATE ( surf_usm_h%lambda_h(nzb_wall:nzt_wall,1:surf_usm_h%ns)        )
1140        ALLOCATE ( surf_usm_h%rho_c_wall(nzb_wall:nzt_wall,1:surf_usm_h%ns)      )
1141        ALLOCATE ( surf_usm_h%lambda_h_window(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1142        ALLOCATE ( surf_usm_h%rho_c_window(nzb_wall:nzt_wall,1:surf_usm_h%ns)    )
1143        ALLOCATE ( surf_usm_h%lambda_h_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)  )
1144        ALLOCATE ( surf_usm_h%rho_c_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)     )
1145
1146        ALLOCATE ( surf_usm_h%rho_c_total_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)    )
1147        ALLOCATE ( surf_usm_h%n_vg_green(1:surf_usm_h%ns)                             )
1148        ALLOCATE ( surf_usm_h%alpha_vg_green(1:surf_usm_h%ns)                         )
1149        ALLOCATE ( surf_usm_h%l_vg_green(1:surf_usm_h%ns)                             )
1150        ALLOCATE ( surf_usm_h%gamma_w_green_sat(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)  )
1151        ALLOCATE ( surf_usm_h%lambda_w_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)       )
1152        ALLOCATE ( surf_usm_h%gamma_w_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)        )
1153        ALLOCATE ( surf_usm_h%tswc_h_m(nzb_wall:nzt_wall,1:surf_usm_h%ns)             )
1154
1155!
1156!--     For vertical surfaces.
1157        DO  l = 0, 3
1158           ALLOCATE ( surf_usm_v(l)%thickness_wall(1:surf_usm_v(l)%ns)                    )
1159           ALLOCATE ( surf_usm_v(l)%thickness_window(1:surf_usm_v(l)%ns)                  )
1160           ALLOCATE ( surf_usm_v(l)%thickness_green(1:surf_usm_v(l)%ns)                   )
1161           ALLOCATE ( surf_usm_v(l)%lambda_h(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)        )
1162           ALLOCATE ( surf_usm_v(l)%rho_c_wall(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)      )
1163           ALLOCATE ( surf_usm_v(l)%lambda_h_window(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1164           ALLOCATE ( surf_usm_v(l)%rho_c_window(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)    )
1165           ALLOCATE ( surf_usm_v(l)%lambda_h_green(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)  )
1166           ALLOCATE ( surf_usm_v(l)%rho_c_green(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)     )
1167        ENDDO
1168
1169!
1170!--     allocate green wall and roof vegetation and soil parameters. First horizontal surfaces
1171        ALLOCATE ( surf_usm_h%g_d(1:surf_usm_h%ns)              )
1172        ALLOCATE ( surf_usm_h%c_liq(1:surf_usm_h%ns)            )
1173        ALLOCATE ( surf_usm_h%qsws_liq(1:surf_usm_h%ns)         )
1174        ALLOCATE ( surf_usm_h%qsws_veg(1:surf_usm_h%ns)         )
1175        ALLOCATE ( surf_usm_h%r_canopy(1:surf_usm_h%ns)         )
1176        ALLOCATE ( surf_usm_h%r_canopy_min(1:surf_usm_h%ns)     )
1177        ALLOCATE ( surf_usm_h%pt_10cm(1:surf_usm_h%ns)          ) 
1178
1179!
1180!--     For vertical surfaces.
1181        DO  l = 0, 3
1182          ALLOCATE ( surf_usm_v(l)%g_d(1:surf_usm_v(l)%ns)              )
1183          ALLOCATE ( surf_usm_v(l)%c_liq(1:surf_usm_v(l)%ns)            )
1184          ALLOCATE ( surf_usm_v(l)%qsws_liq(1:surf_usm_v(l)%ns)         )
1185          ALLOCATE ( surf_usm_v(l)%qsws_veg(1:surf_usm_v(l)%ns)         )
1186          ALLOCATE ( surf_usm_v(l)%r_canopy(1:surf_usm_v(l)%ns)         )
1187          ALLOCATE ( surf_usm_v(l)%r_canopy_min(1:surf_usm_v(l)%ns)     )
1188          ALLOCATE ( surf_usm_v(l)%pt_10cm(1:surf_usm_v(l)%ns)          )
1189        ENDDO
1190
1191!
1192!--     allocate wall and roof layers sizes. For horizontal surfaces.
1193        ALLOCATE ( zwn(nzb_wall:nzt_wall)                                        )
1194        ALLOCATE ( surf_usm_h%dz_wall(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)       )
1195        ALLOCATE ( zwn_window(nzb_wall:nzt_wall)                                 )
1196        ALLOCATE ( surf_usm_h%dz_window(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)     )
1197        ALLOCATE ( zwn_green(nzb_wall:nzt_wall)                                  )
1198        ALLOCATE ( surf_usm_h%dz_green(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)      )
1199        ALLOCATE ( surf_usm_h%ddz_wall(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)      )
1200        ALLOCATE ( surf_usm_h%dz_wall_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)    )
1201        ALLOCATE ( surf_usm_h%ddz_wall_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)   )
1202        ALLOCATE ( surf_usm_h%zw(nzb_wall:nzt_wall,1:surf_usm_h%ns)              )
1203        ALLOCATE ( surf_usm_h%ddz_window(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)    )
1204        ALLOCATE ( surf_usm_h%dz_window_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)  )
1205        ALLOCATE ( surf_usm_h%ddz_window_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1206        ALLOCATE ( surf_usm_h%zw_window(nzb_wall:nzt_wall,1:surf_usm_h%ns)       )
1207        ALLOCATE ( surf_usm_h%ddz_green(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)     )
1208        ALLOCATE ( surf_usm_h%dz_green_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)   )
1209        ALLOCATE ( surf_usm_h%ddz_green_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)  )
1210        ALLOCATE ( surf_usm_h%zw_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)        )
1211
1212!
1213!--     For vertical surfaces.
1214        DO  l = 0, 3
1215           ALLOCATE ( surf_usm_v(l)%dz_wall(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)       )
1216           ALLOCATE ( surf_usm_v(l)%dz_window(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)     )
1217           ALLOCATE ( surf_usm_v(l)%dz_green(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)      )
1218           ALLOCATE ( surf_usm_v(l)%ddz_wall(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)      )
1219           ALLOCATE ( surf_usm_v(l)%dz_wall_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)    )
1220           ALLOCATE ( surf_usm_v(l)%ddz_wall_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)   )
1221           ALLOCATE ( surf_usm_v(l)%zw(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)              )
1222           ALLOCATE ( surf_usm_v(l)%ddz_window(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)    )
1223           ALLOCATE ( surf_usm_v(l)%dz_window_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)  )
1224           ALLOCATE ( surf_usm_v(l)%ddz_window_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1225           ALLOCATE ( surf_usm_v(l)%zw_window(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)       )
1226           ALLOCATE ( surf_usm_v(l)%ddz_green(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)     )
1227           ALLOCATE ( surf_usm_v(l)%dz_green_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)   )
1228           ALLOCATE ( surf_usm_v(l)%ddz_green_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)  )
1229           ALLOCATE ( surf_usm_v(l)%zw_green(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)        )
1230        ENDDO
1231
1232!
1233!--     allocate wall and roof temperature arrays, for horizontal walls
1234!
1235!--     Allocate if required. Note, in case of restarts, some of these arrays
1236!--     might be already allocated.
1237        IF ( .NOT. ALLOCATED( t_surf_wall_h_1 ) )                              &
1238           ALLOCATE ( t_surf_wall_h_1(1:surf_usm_h%ns) )
1239        IF ( .NOT. ALLOCATED( t_surf_wall_h_2 ) )                              &
1240           ALLOCATE ( t_surf_wall_h_2(1:surf_usm_h%ns) )
1241        IF ( .NOT. ALLOCATED( t_wall_h_1 ) )                                   &           
1242           ALLOCATE ( t_wall_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1243        IF ( .NOT. ALLOCATED( t_wall_h_2 ) )                                   &           
1244           ALLOCATE ( t_wall_h_2(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )         
1245        IF ( .NOT. ALLOCATED( t_surf_window_h_1 ) )                            &
1246           ALLOCATE ( t_surf_window_h_1(1:surf_usm_h%ns) )
1247        IF ( .NOT. ALLOCATED( t_surf_window_h_2 ) )                            &
1248           ALLOCATE ( t_surf_window_h_2(1:surf_usm_h%ns) )
1249        IF ( .NOT. ALLOCATED( t_window_h_1 ) )                                 &           
1250           ALLOCATE ( t_window_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1251        IF ( .NOT. ALLOCATED( t_window_h_2 ) )                                 &           
1252           ALLOCATE ( t_window_h_2(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )         
1253        IF ( .NOT. ALLOCATED( t_surf_green_h_1 ) )                             &
1254           ALLOCATE ( t_surf_green_h_1(1:surf_usm_h%ns) )
1255        IF ( .NOT. ALLOCATED( t_surf_green_h_2 ) )                             &
1256           ALLOCATE ( t_surf_green_h_2(1:surf_usm_h%ns) )
1257        IF ( .NOT. ALLOCATED( t_green_h_1 ) )                                  &           
1258           ALLOCATE ( t_green_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1259        IF ( .NOT. ALLOCATED( t_green_h_2 ) )                                  &           
1260           ALLOCATE ( t_green_h_2(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )         
1261        IF ( .NOT. ALLOCATED( swc_h_1 ) )                                      &           
1262           ALLOCATE ( swc_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1263        IF ( .NOT. ALLOCATED( swc_sat_h_1 ) )                                  &           
1264           ALLOCATE ( swc_sat_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1265        IF ( .NOT. ALLOCATED( swc_res_h_1 ) )                                  &           
1266           ALLOCATE ( swc_res_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1267        IF ( .NOT. ALLOCATED( swc_h_2 ) )                                      &           
1268           ALLOCATE ( swc_h_2(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
1269        IF ( .NOT. ALLOCATED( rootfr_h_1 ) )                                   &           
1270           ALLOCATE ( rootfr_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1271        IF ( .NOT. ALLOCATED( wilt_h_1 ) )                                     &           
1272           ALLOCATE ( wilt_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1273        IF ( .NOT. ALLOCATED( fc_h_1 ) )                                       &           
1274           ALLOCATE ( fc_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1275
1276        IF ( .NOT. ALLOCATED( m_liq_usm_h_1%var_usm_1d ) )                     &
1277           ALLOCATE ( m_liq_usm_h_1%var_usm_1d(1:surf_usm_h%ns) )
1278        IF ( .NOT. ALLOCATED( m_liq_usm_h_2%var_usm_1d ) )                     &
1279           ALLOCATE ( m_liq_usm_h_2%var_usm_1d(1:surf_usm_h%ns) )
1280           
1281!           
1282!--     initial assignment of the pointers
1283        t_wall_h    => t_wall_h_1;   t_wall_h_p   => t_wall_h_2
1284        t_window_h  => t_window_h_1; t_window_h_p => t_window_h_2
1285        t_green_h   => t_green_h_1;  t_green_h_p  => t_green_h_2
1286        t_surf_wall_h   => t_surf_wall_h_1;   t_surf_wall_h_p   => t_surf_wall_h_2           
1287        t_surf_window_h => t_surf_window_h_1; t_surf_window_h_p => t_surf_window_h_2 
1288        t_surf_green_h  => t_surf_green_h_1;  t_surf_green_h_p  => t_surf_green_h_2           
1289        m_liq_usm_h     => m_liq_usm_h_1;     m_liq_usm_h_p     => m_liq_usm_h_2
1290        swc_h     => swc_h_1; swc_h_p => swc_h_2
1291        swc_sat_h => swc_sat_h_1
1292        swc_res_h => swc_res_h_1
1293        rootfr_h  => rootfr_h_1
1294        wilt_h    => wilt_h_1
1295        fc_h      => fc_h_1
1296
1297!
1298!--     allocate wall and roof temperature arrays, for vertical walls if required
1299!
1300!--     Allocate if required. Note, in case of restarts, some of these arrays
1301!--     might be already allocated.
1302        DO  l = 0, 3
1303           IF ( .NOT. ALLOCATED( t_surf_wall_v_1(l)%t ) )                      &
1304              ALLOCATE ( t_surf_wall_v_1(l)%t(1:surf_usm_v(l)%ns) )
1305           IF ( .NOT. ALLOCATED( t_surf_wall_v_2(l)%t ) )                      &
1306              ALLOCATE ( t_surf_wall_v_2(l)%t(1:surf_usm_v(l)%ns) )
1307           IF ( .NOT. ALLOCATED( t_wall_v_1(l)%t ) )                           &           
1308              ALLOCATE ( t_wall_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1309           IF ( .NOT. ALLOCATED( t_wall_v_2(l)%t ) )                           &           
1310              ALLOCATE ( t_wall_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1311           IF ( .NOT. ALLOCATED( t_surf_window_v_1(l)%t ) )                    &
1312              ALLOCATE ( t_surf_window_v_1(l)%t(1:surf_usm_v(l)%ns) )
1313           IF ( .NOT. ALLOCATED( t_surf_window_v_2(l)%t ) )                    &
1314              ALLOCATE ( t_surf_window_v_2(l)%t(1:surf_usm_v(l)%ns) )
1315           IF ( .NOT. ALLOCATED( t_window_v_1(l)%t ) )                         &           
1316              ALLOCATE ( t_window_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1317           IF ( .NOT. ALLOCATED( t_window_v_2(l)%t ) )                         &           
1318              ALLOCATE ( t_window_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1319           IF ( .NOT. ALLOCATED( t_surf_green_v_1(l)%t ) )                     &
1320              ALLOCATE ( t_surf_green_v_1(l)%t(1:surf_usm_v(l)%ns) )
1321           IF ( .NOT. ALLOCATED( t_surf_green_v_2(l)%t ) )                     &
1322              ALLOCATE ( t_surf_green_v_2(l)%t(1:surf_usm_v(l)%ns) )
1323           IF ( .NOT. ALLOCATED( t_green_v_1(l)%t ) )                          &           
1324              ALLOCATE ( t_green_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1325           IF ( .NOT. ALLOCATED( t_green_v_2(l)%t ) )                          &           
1326              ALLOCATE ( t_green_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1327           IF ( .NOT. ALLOCATED( m_liq_usm_v_1(l)%var_usm_1d ) )               &
1328              ALLOCATE ( m_liq_usm_v_1(l)%var_usm_1d(1:surf_usm_v(l)%ns) )
1329           IF ( .NOT. ALLOCATED( m_liq_usm_v_2(l)%var_usm_1d ) )               &
1330              ALLOCATE ( m_liq_usm_v_2(l)%var_usm_1d(1:surf_usm_v(l)%ns) )
1331           IF ( .NOT. ALLOCATED( swc_v_1(l)%t ) )                              &           
1332              ALLOCATE ( swc_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1333           IF ( .NOT. ALLOCATED( swc_v_2(l)%t ) )                              &           
1334              ALLOCATE ( swc_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1335        ENDDO
1336!
1337!--     initial assignment of the pointers
1338        t_wall_v        => t_wall_v_1;        t_wall_v_p        => t_wall_v_2
1339        t_surf_wall_v   => t_surf_wall_v_1;   t_surf_wall_v_p   => t_surf_wall_v_2
1340        t_window_v      => t_window_v_1;      t_window_v_p      => t_window_v_2
1341        t_green_v       => t_green_v_1;       t_green_v_p       => t_green_v_2
1342        t_surf_window_v => t_surf_window_v_1; t_surf_window_v_p => t_surf_window_v_2
1343        t_surf_green_v  => t_surf_green_v_1;  t_surf_green_v_p  => t_surf_green_v_2
1344        m_liq_usm_v     => m_liq_usm_v_1;     m_liq_usm_v_p     => m_liq_usm_v_2
1345        swc_v           => swc_v_1;           swc_v_p           => swc_v_2
1346
1347!
1348!--     Allocate intermediate timestep arrays. For horizontal surfaces.
1349        ALLOCATE ( surf_usm_h%tt_surface_wall_m(1:surf_usm_h%ns)               )
1350        ALLOCATE ( surf_usm_h%tt_wall_m(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)   )
1351        ALLOCATE ( surf_usm_h%tt_surface_window_m(1:surf_usm_h%ns)             )
1352        ALLOCATE ( surf_usm_h%tt_window_m(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
1353        ALLOCATE ( surf_usm_h%tt_green_m(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)  )
1354        ALLOCATE ( surf_usm_h%tt_surface_green_m(1:surf_usm_h%ns)              )
1355
1356!
1357!--    Allocate intermediate timestep arrays
1358!--    Horizontal surfaces
1359       ALLOCATE ( tm_liq_usm_h_m%var_usm_1d(1:surf_usm_h%ns)                   )
1360!
1361!--    Horizontal surfaces
1362       DO  l = 0, 3
1363          ALLOCATE ( tm_liq_usm_v_m(l)%var_usm_1d(1:surf_usm_v(l)%ns)          )
1364       ENDDO 
1365       
1366!
1367!--     Set inital values for prognostic quantities
1368        IF ( ALLOCATED( surf_usm_h%tt_surface_wall_m )   )  surf_usm_h%tt_surface_wall_m   = 0.0_wp
1369        IF ( ALLOCATED( surf_usm_h%tt_wall_m )           )  surf_usm_h%tt_wall_m           = 0.0_wp
1370        IF ( ALLOCATED( surf_usm_h%tt_surface_window_m ) )  surf_usm_h%tt_surface_window_m = 0.0_wp
1371        IF ( ALLOCATED( surf_usm_h%tt_window_m    )      )  surf_usm_h%tt_window_m         = 0.0_wp
1372        IF ( ALLOCATED( surf_usm_h%tt_green_m    )       )  surf_usm_h%tt_green_m          = 0.0_wp
1373        IF ( ALLOCATED( surf_usm_h%tt_surface_green_m )  )  surf_usm_h%tt_surface_green_m  = 0.0_wp
1374!
1375!--     Now, for vertical surfaces
1376        DO  l = 0, 3
1377           ALLOCATE ( surf_usm_v(l)%tt_surface_wall_m(1:surf_usm_v(l)%ns)               )
1378           ALLOCATE ( surf_usm_v(l)%tt_wall_m(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)   )
1379           IF ( ALLOCATED( surf_usm_v(l)%tt_surface_wall_m ) )  surf_usm_v(l)%tt_surface_wall_m = 0.0_wp
1380           IF ( ALLOCATED( surf_usm_v(l)%tt_wall_m    ) )  surf_usm_v(l)%tt_wall_m    = 0.0_wp
1381           ALLOCATE ( surf_usm_v(l)%tt_surface_window_m(1:surf_usm_v(l)%ns)             )
1382           ALLOCATE ( surf_usm_v(l)%tt_window_m(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
1383           IF ( ALLOCATED( surf_usm_v(l)%tt_surface_window_m ) )  surf_usm_v(l)%tt_surface_window_m = 0.0_wp
1384           IF ( ALLOCATED( surf_usm_v(l)%tt_window_m  ) )  surf_usm_v(l)%tt_window_m    = 0.0_wp
1385           ALLOCATE ( surf_usm_v(l)%tt_surface_green_m(1:surf_usm_v(l)%ns)              )
1386           IF ( ALLOCATED( surf_usm_v(l)%tt_surface_green_m ) )  surf_usm_v(l)%tt_surface_green_m = 0.0_wp
1387           ALLOCATE ( surf_usm_v(l)%tt_green_m(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)  )
1388           IF ( ALLOCATED( surf_usm_v(l)%tt_green_m   ) )  surf_usm_v(l)%tt_green_m    = 0.0_wp
1389        ENDDO
1390!
1391!--     allocate wall heat flux output array and set initial values. For horizontal surfaces
1392!        ALLOCATE ( surf_usm_h%wshf(1:surf_usm_h%ns)    )  !can be removed
1393        ALLOCATE ( surf_usm_h%wshf_eb(1:surf_usm_h%ns) )
1394        ALLOCATE ( surf_usm_h%wghf_eb(1:surf_usm_h%ns) )
1395        ALLOCATE ( surf_usm_h%wghf_eb_window(1:surf_usm_h%ns) )
1396        ALLOCATE ( surf_usm_h%wghf_eb_green(1:surf_usm_h%ns) )
1397        ALLOCATE ( surf_usm_h%iwghf_eb(1:surf_usm_h%ns) )
1398        ALLOCATE ( surf_usm_h%iwghf_eb_window(1:surf_usm_h%ns) )
1399        IF ( ALLOCATED( surf_usm_h%wshf    ) )  surf_usm_h%wshf    = 0.0_wp
1400        IF ( ALLOCATED( surf_usm_h%wshf_eb ) )  surf_usm_h%wshf_eb = 0.0_wp
1401        IF ( ALLOCATED( surf_usm_h%wghf_eb ) )  surf_usm_h%wghf_eb = 0.0_wp
1402        IF ( ALLOCATED( surf_usm_h%wghf_eb_window ) )  surf_usm_h%wghf_eb_window = 0.0_wp
1403        IF ( ALLOCATED( surf_usm_h%wghf_eb_green ) )  surf_usm_h%wghf_eb_green = 0.0_wp
1404        IF ( ALLOCATED( surf_usm_h%iwghf_eb ) )  surf_usm_h%iwghf_eb = 0.0_wp
1405        IF ( ALLOCATED( surf_usm_h%iwghf_eb_window ) )  surf_usm_h%iwghf_eb_window = 0.0_wp
1406!
1407!--     Now, for vertical surfaces
1408        DO  l = 0, 3
1409!           ALLOCATE ( surf_usm_v(l)%wshf(1:surf_usm_v(l)%ns)    )    ! can be removed
1410           ALLOCATE ( surf_usm_v(l)%wshf_eb(1:surf_usm_v(l)%ns) )
1411           ALLOCATE ( surf_usm_v(l)%wghf_eb(1:surf_usm_v(l)%ns) )
1412           ALLOCATE ( surf_usm_v(l)%wghf_eb_window(1:surf_usm_v(l)%ns) )
1413           ALLOCATE ( surf_usm_v(l)%wghf_eb_green(1:surf_usm_v(l)%ns) )
1414           ALLOCATE ( surf_usm_v(l)%iwghf_eb(1:surf_usm_v(l)%ns) )
1415           ALLOCATE ( surf_usm_v(l)%iwghf_eb_window(1:surf_usm_v(l)%ns) )
1416           IF ( ALLOCATED( surf_usm_v(l)%wshf    ) )  surf_usm_v(l)%wshf    = 0.0_wp
1417           IF ( ALLOCATED( surf_usm_v(l)%wshf_eb ) )  surf_usm_v(l)%wshf_eb = 0.0_wp
1418           IF ( ALLOCATED( surf_usm_v(l)%wghf_eb ) )  surf_usm_v(l)%wghf_eb = 0.0_wp
1419           IF ( ALLOCATED( surf_usm_v(l)%wghf_eb_window ) )  surf_usm_v(l)%wghf_eb_window = 0.0_wp
1420           IF ( ALLOCATED( surf_usm_v(l)%wghf_eb_green ) )  surf_usm_v(l)%wghf_eb_green = 0.0_wp
1421           IF ( ALLOCATED( surf_usm_v(l)%iwghf_eb ) )  surf_usm_v(l)%iwghf_eb = 0.0_wp
1422           IF ( ALLOCATED( surf_usm_v(l)%iwghf_eb_window ) )  surf_usm_v(l)%iwghf_eb_window = 0.0_wp
1423        ENDDO
1424
1425        IF ( debug_output )  CALL debug_message( 'usm_init_arrays', 'end' )
1426       
1427    END SUBROUTINE usm_init_arrays
1428
1429
1430!------------------------------------------------------------------------------!
1431! Description:
1432! ------------
1433!> Sum up and time-average urban surface output quantities as well as allocate
1434!> the array necessary for storing the average.
1435!------------------------------------------------------------------------------!
1436    SUBROUTINE usm_3d_data_averaging( mode, variable )
1437
1438        IMPLICIT NONE
1439
1440        CHARACTER(LEN=*), INTENT(IN) ::  mode
1441        CHARACTER(LEN=*), INTENT(IN) :: variable
1442 
1443        INTEGER(iwp)                                       :: i, j, k, l, m, ids, idsint, iwl, istat  !< runnin indices
1444        CHARACTER(LEN=varnamelength)                       :: var                                     !< trimmed variable
1445        INTEGER(iwp), PARAMETER                            :: nd = 5                                  !< number of directions
1446        CHARACTER(LEN=6), DIMENSION(0:nd-1), PARAMETER     :: dirname = (/ '_roof ', '_south', '_north', '_west ', '_east ' /)
1447        INTEGER(iwp), DIMENSION(0:nd-1), PARAMETER         :: dirint = (/ iup_u, isouth_u, inorth_u, iwest_u, ieast_u /)
1448
1449        IF ( variable(1:4) == 'usm_' )  THEN  ! is such a check really rquired?
1450
1451!
1452!--     find the real name of the variable
1453        ids = -1
1454        l = -1
1455        var = TRIM(variable)
1456        DO i = 0, nd-1
1457            k = len(TRIM(var))
1458            j = len(TRIM(dirname(i)))
1459            IF ( TRIM(var(k-j+1:k)) == TRIM(dirname(i)) )  THEN
1460                ids = i
1461                idsint = dirint(ids)
1462                var = var(:k-j)
1463                EXIT
1464            ENDIF
1465        ENDDO
1466        l = idsint - 2  ! horisontal direction index - terible hack !
1467        IF ( l < 0 .OR. l > 3 ) THEN
1468           l = -1
1469        END IF
1470        IF ( ids == -1 )  THEN
1471            var = TRIM(variable)
1472        ENDIF
1473        IF ( var(1:11) == 'usm_t_wall_'  .AND.  len(TRIM(var)) >= 12 )  THEN
1474!
1475!--          wall layers
1476            READ(var(12:12), '(I1)', iostat=istat ) iwl
1477            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
1478                var = var(1:10)
1479            ELSE
1480!
1481!--             wrong wall layer index
1482                RETURN
1483            ENDIF
1484        ENDIF
1485        IF ( var(1:13) == 'usm_t_window_'  .AND.  len(TRIM(var)) >= 14 )  THEN
1486!
1487!--          wall layers
1488            READ(var(14:14), '(I1)', iostat=istat ) iwl
1489            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
1490                var = var(1:12)
1491            ELSE
1492!
1493!--             wrong window layer index
1494                RETURN
1495            ENDIF
1496        ENDIF
1497        IF ( var(1:12) == 'usm_t_green_'  .AND.  len(TRIM(var)) >= 13 )  THEN
1498!
1499!--          wall layers
1500            READ(var(13:13), '(I1)', iostat=istat ) iwl
1501            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
1502                var = var(1:11)
1503            ELSE
1504!
1505!--             wrong green layer index
1506                RETURN
1507            ENDIF
1508        ENDIF
1509        IF ( var(1:8) == 'usm_swc_'  .AND.  len(TRIM(var)) >= 9 )  THEN
1510!
1511!--          swc layers
1512            READ(var(9:9), '(I1)', iostat=istat ) iwl
1513            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
1514                var = var(1:7)
1515            ELSE
1516!
1517!--             wrong swc layer index
1518                RETURN
1519            ENDIF
1520        ENDIF
1521
1522        IF ( mode == 'allocate' )  THEN
1523           
1524           SELECT CASE ( TRIM( var ) )
1525
1526                CASE ( 'usm_wshf' )
1527!
1528!--                 array of sensible heat flux from surfaces
1529!--                 land surfaces
1530                    IF ( l == -1 ) THEN
1531                       IF ( .NOT.  ALLOCATED(surf_usm_h%wshf_eb_av) )  THEN
1532                          ALLOCATE ( surf_usm_h%wshf_eb_av(1:surf_usm_h%ns) )
1533                          surf_usm_h%wshf_eb_av = 0.0_wp
1534                       ENDIF
1535                    ELSE
1536                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%wshf_eb_av) )  THEN
1537                           ALLOCATE ( surf_usm_v(l)%wshf_eb_av(1:surf_usm_v(l)%ns) )
1538                           surf_usm_v(l)%wshf_eb_av = 0.0_wp
1539                       ENDIF
1540                    ENDIF
1541                   
1542                CASE ( 'usm_qsws' )
1543!
1544!--                 array of latent heat flux from surfaces
1545!--                 land surfaces
1546                    IF ( l == -1 .AND. .NOT.  ALLOCATED(surf_usm_h%qsws_av) )  THEN
1547                        ALLOCATE ( surf_usm_h%qsws_av(1:surf_usm_h%ns) )
1548                        surf_usm_h%qsws_av = 0.0_wp
1549                    ELSE
1550                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%qsws_av) )  THEN
1551                           ALLOCATE ( surf_usm_v(l)%qsws_av(1:surf_usm_v(l)%ns) )
1552                           surf_usm_v(l)%qsws_av = 0.0_wp
1553                       ENDIF
1554                    ENDIF
1555                   
1556                CASE ( 'usm_qsws_veg' )
1557!
1558!--                 array of latent heat flux from vegetation surfaces
1559!--                 land surfaces
1560                    IF ( l == -1 .AND. .NOT.  ALLOCATED(surf_usm_h%qsws_veg_av) )  THEN
1561                        ALLOCATE ( surf_usm_h%qsws_veg_av(1:surf_usm_h%ns) )
1562                        surf_usm_h%qsws_veg_av = 0.0_wp
1563                    ELSE
1564                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%qsws_veg_av) )  THEN
1565                           ALLOCATE ( surf_usm_v(l)%qsws_veg_av(1:surf_usm_v(l)%ns) )
1566                           surf_usm_v(l)%qsws_veg_av = 0.0_wp
1567                       ENDIF
1568                    ENDIF
1569                   
1570                CASE ( 'usm_qsws_liq' )
1571!
1572!--                 array of latent heat flux from surfaces with liquid
1573!--                 land surfaces
1574                    IF ( l == -1 .AND. .NOT.  ALLOCATED(surf_usm_h%qsws_liq_av) )  THEN
1575                        ALLOCATE ( surf_usm_h%qsws_liq_av(1:surf_usm_h%ns) )
1576                        surf_usm_h%qsws_liq_av = 0.0_wp
1577                    ELSE
1578                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%qsws_liq_av) )  THEN
1579                           ALLOCATE ( surf_usm_v(l)%qsws_liq_av(1:surf_usm_v(l)%ns) )
1580                           surf_usm_v(l)%qsws_liq_av = 0.0_wp
1581                       ENDIF
1582                    ENDIF
1583!
1584!--             Please note, the following output quantities belongs to the
1585!--             individual tile fractions - ground heat flux at wall-, window-,
1586!--             and green fraction. Aggregated ground-heat flux is treated
1587!--             accordingly in average_3d_data, sum_up_3d_data, etc..
1588                CASE ( 'usm_wghf' )
1589!
1590!--                 array of heat flux from ground (wall, roof, land)
1591                    IF ( l == -1 ) THEN
1592                       IF ( .NOT.  ALLOCATED(surf_usm_h%wghf_eb_av) )  THEN
1593                           ALLOCATE ( surf_usm_h%wghf_eb_av(1:surf_usm_h%ns) )
1594                           surf_usm_h%wghf_eb_av = 0.0_wp
1595                       ENDIF
1596                    ELSE
1597                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%wghf_eb_av) )  THEN
1598                           ALLOCATE ( surf_usm_v(l)%wghf_eb_av(1:surf_usm_v(l)%ns) )
1599                           surf_usm_v(l)%wghf_eb_av = 0.0_wp
1600                       ENDIF
1601                    ENDIF
1602
1603                CASE ( 'usm_wghf_window' )
1604!
1605!--                 array of heat flux from window ground (wall, roof, land)
1606                    IF ( l == -1 ) THEN
1607                       IF ( .NOT.  ALLOCATED(surf_usm_h%wghf_eb_window_av) )  THEN
1608                           ALLOCATE ( surf_usm_h%wghf_eb_window_av(1:surf_usm_h%ns) )
1609                           surf_usm_h%wghf_eb_window_av = 0.0_wp
1610                       ENDIF
1611                    ELSE
1612                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%wghf_eb_window_av) )  THEN
1613                           ALLOCATE ( surf_usm_v(l)%wghf_eb_window_av(1:surf_usm_v(l)%ns) )
1614                           surf_usm_v(l)%wghf_eb_window_av = 0.0_wp
1615                       ENDIF
1616                    ENDIF
1617
1618                CASE ( 'usm_wghf_green' )
1619!
1620!--                 array of heat flux from green ground (wall, roof, land)
1621                    IF ( l == -1 ) THEN
1622                       IF ( .NOT.  ALLOCATED(surf_usm_h%wghf_eb_green_av) )  THEN
1623                           ALLOCATE ( surf_usm_h%wghf_eb_green_av(1:surf_usm_h%ns) )
1624                           surf_usm_h%wghf_eb_green_av = 0.0_wp
1625                       ENDIF
1626                    ELSE
1627                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%wghf_eb_green_av) )  THEN
1628                           ALLOCATE ( surf_usm_v(l)%wghf_eb_green_av(1:surf_usm_v(l)%ns) )
1629                           surf_usm_v(l)%wghf_eb_green_av = 0.0_wp
1630                       ENDIF
1631                    ENDIF
1632
1633                CASE ( 'usm_iwghf' )
1634!
1635!--                 array of heat flux from indoor ground (wall, roof, land)
1636                    IF ( l == -1 ) THEN
1637                       IF ( .NOT.  ALLOCATED(surf_usm_h%iwghf_eb_av) )  THEN
1638                           ALLOCATE ( surf_usm_h%iwghf_eb_av(1:surf_usm_h%ns) )
1639                           surf_usm_h%iwghf_eb_av = 0.0_wp
1640                       ENDIF
1641                    ELSE
1642                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%iwghf_eb_av) )  THEN
1643                           ALLOCATE ( surf_usm_v(l)%iwghf_eb_av(1:surf_usm_v(l)%ns) )
1644                           surf_usm_v(l)%iwghf_eb_av = 0.0_wp
1645                       ENDIF
1646                    ENDIF
1647
1648                CASE ( 'usm_iwghf_window' )
1649!
1650!--                 array of heat flux from indoor window ground (wall, roof, land)
1651                    IF ( l == -1 ) THEN
1652                       IF ( .NOT.  ALLOCATED(surf_usm_h%iwghf_eb_window_av) )  THEN
1653                           ALLOCATE ( surf_usm_h%iwghf_eb_window_av(1:surf_usm_h%ns) )
1654                           surf_usm_h%iwghf_eb_window_av = 0.0_wp
1655                       ENDIF
1656                    ELSE
1657                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%iwghf_eb_window_av) )  THEN
1658                           ALLOCATE ( surf_usm_v(l)%iwghf_eb_window_av(1:surf_usm_v(l)%ns) )
1659                           surf_usm_v(l)%iwghf_eb_window_av = 0.0_wp
1660                       ENDIF
1661                    ENDIF
1662
1663                CASE ( 'usm_t_surf_wall' )
1664!
1665!--                 surface temperature for surfaces
1666                    IF ( l == -1 ) THEN
1667                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_surf_wall_av) )  THEN
1668                           ALLOCATE ( surf_usm_h%t_surf_wall_av(1:surf_usm_h%ns) )
1669                           surf_usm_h%t_surf_wall_av = 0.0_wp
1670                       ENDIF
1671                    ELSE
1672                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_surf_wall_av) )  THEN
1673                           ALLOCATE ( surf_usm_v(l)%t_surf_wall_av(1:surf_usm_v(l)%ns) )
1674                           surf_usm_v(l)%t_surf_wall_av = 0.0_wp
1675                       ENDIF
1676                    ENDIF
1677
1678                CASE ( 'usm_t_surf_window' )
1679!
1680!--                 surface temperature for window surfaces
1681                    IF ( l == -1 ) THEN
1682                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_surf_window_av) )  THEN
1683                           ALLOCATE ( surf_usm_h%t_surf_window_av(1:surf_usm_h%ns) )
1684                           surf_usm_h%t_surf_window_av = 0.0_wp
1685                       ENDIF
1686                    ELSE
1687                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_surf_window_av) )  THEN
1688                           ALLOCATE ( surf_usm_v(l)%t_surf_window_av(1:surf_usm_v(l)%ns) )
1689                           surf_usm_v(l)%t_surf_window_av = 0.0_wp
1690                       ENDIF
1691                    ENDIF
1692                   
1693                CASE ( 'usm_t_surf_green' )
1694!
1695!--                 surface temperature for green surfaces
1696                    IF ( l == -1 ) THEN
1697                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_surf_green_av) )  THEN
1698                           ALLOCATE ( surf_usm_h%t_surf_green_av(1:surf_usm_h%ns) )
1699                           surf_usm_h%t_surf_green_av = 0.0_wp
1700                       ENDIF
1701                    ELSE
1702                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_surf_green_av) )  THEN
1703                           ALLOCATE ( surf_usm_v(l)%t_surf_green_av(1:surf_usm_v(l)%ns) )
1704                           surf_usm_v(l)%t_surf_green_av = 0.0_wp
1705                       ENDIF
1706                    ENDIF
1707               
1708                CASE ( 'usm_theta_10cm' )
1709!
1710!--                 near surface (10cm) temperature for whole surfaces
1711                    IF ( l == -1 ) THEN
1712                       IF ( .NOT.  ALLOCATED(surf_usm_h%pt_10cm_av) )  THEN
1713                           ALLOCATE ( surf_usm_h%pt_10cm_av(1:surf_usm_h%ns) )
1714                           surf_usm_h%pt_10cm_av = 0.0_wp
1715                       ENDIF
1716                    ELSE
1717                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%pt_10cm_av) )  THEN
1718                           ALLOCATE ( surf_usm_v(l)%pt_10cm_av(1:surf_usm_v(l)%ns) )
1719                           surf_usm_v(l)%pt_10cm_av = 0.0_wp
1720                       ENDIF
1721                    ENDIF
1722                 
1723                CASE ( 'usm_t_wall' )
1724!
1725!--                 wall temperature for iwl layer of walls and land
1726                    IF ( l == -1 ) THEN
1727                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_wall_av) )  THEN
1728                           ALLOCATE ( surf_usm_h%t_wall_av(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1729                           surf_usm_h%t_wall_av = 0.0_wp
1730                       ENDIF
1731                    ELSE
1732                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_wall_av) )  THEN
1733                           ALLOCATE ( surf_usm_v(l)%t_wall_av(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1734                           surf_usm_v(l)%t_wall_av = 0.0_wp
1735                       ENDIF
1736                    ENDIF
1737
1738                CASE ( 'usm_t_window' )
1739!
1740!--                 window temperature for iwl layer of walls and land
1741                    IF ( l == -1 ) THEN
1742                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_window_av) )  THEN
1743                           ALLOCATE ( surf_usm_h%t_window_av(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1744                           surf_usm_h%t_window_av = 0.0_wp
1745                       ENDIF
1746                    ELSE
1747                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_window_av) )  THEN
1748                           ALLOCATE ( surf_usm_v(l)%t_window_av(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1749                           surf_usm_v(l)%t_window_av = 0.0_wp
1750                       ENDIF
1751                    ENDIF
1752
1753                CASE ( 'usm_t_green' )
1754!
1755!--                 green temperature for iwl layer of walls and land
1756                    IF ( l == -1 ) THEN
1757                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_green_av) )  THEN
1758                           ALLOCATE ( surf_usm_h%t_green_av(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1759                           surf_usm_h%t_green_av = 0.0_wp
1760                       ENDIF
1761                    ELSE
1762                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_green_av) )  THEN
1763                           ALLOCATE ( surf_usm_v(l)%t_green_av(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1764                           surf_usm_v(l)%t_green_av = 0.0_wp
1765                       ENDIF
1766                    ENDIF
1767                CASE ( 'usm_swc' )
1768!
1769!--                 soil water content for iwl layer of walls and land
1770                    IF ( l == -1 .AND. .NOT.  ALLOCATED(surf_usm_h%swc_av) )  THEN
1771                        ALLOCATE ( surf_usm_h%swc_av(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1772                        surf_usm_h%swc_av = 0.0_wp
1773                    ELSE
1774                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%swc_av) )  THEN
1775                           ALLOCATE ( surf_usm_v(l)%swc_av(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1776                           surf_usm_v(l)%swc_av = 0.0_wp
1777                       ENDIF
1778                    ENDIF
1779
1780               CASE DEFAULT
1781                   CONTINUE
1782
1783           END SELECT
1784
1785        ELSEIF ( mode == 'sum' )  THEN
1786           
1787           SELECT CASE ( TRIM( var ) )
1788
1789                CASE ( 'usm_wshf' )
1790!
1791!--                 array of sensible heat flux from surfaces (land, roof, wall)
1792                    IF ( l == -1 ) THEN
1793                       DO  m = 1, surf_usm_h%ns
1794                          surf_usm_h%wshf_eb_av(m) =                              &
1795                                             surf_usm_h%wshf_eb_av(m) +           &
1796                                             surf_usm_h%wshf_eb(m)
1797                       ENDDO
1798                    ELSE
1799                       DO  m = 1, surf_usm_v(l)%ns
1800                          surf_usm_v(l)%wshf_eb_av(m) =                        &
1801                                          surf_usm_v(l)%wshf_eb_av(m) +        &
1802                                          surf_usm_v(l)%wshf_eb(m)
1803                       ENDDO
1804                    ENDIF
1805                   
1806                CASE ( 'usm_qsws' )
1807!
1808!--                 array of latent heat flux from surfaces (land, roof, wall)
1809                    IF ( l == -1 ) THEN
1810                    DO  m = 1, surf_usm_h%ns
1811                       surf_usm_h%qsws_av(m) =                              &
1812                                          surf_usm_h%qsws_av(m) +           &
1813                                          surf_usm_h%qsws(m) * l_v
1814                    ENDDO
1815                    ELSE
1816                       DO  m = 1, surf_usm_v(l)%ns
1817                          surf_usm_v(l)%qsws_av(m) =                        &
1818                                          surf_usm_v(l)%qsws_av(m) +        &
1819                                          surf_usm_v(l)%qsws(m) * l_v
1820                       ENDDO
1821                    ENDIF
1822                   
1823                CASE ( 'usm_qsws_veg' )
1824!
1825!--                 array of latent heat flux from vegetation surfaces (land, roof, wall)
1826                    IF ( l == -1 ) THEN
1827                    DO  m = 1, surf_usm_h%ns
1828                       surf_usm_h%qsws_veg_av(m) =                              &
1829                                          surf_usm_h%qsws_veg_av(m) +           &
1830                                          surf_usm_h%qsws_veg(m)
1831                    ENDDO
1832                    ELSE
1833                       DO  m = 1, surf_usm_v(l)%ns
1834                          surf_usm_v(l)%qsws_veg_av(m) =                        &
1835                                          surf_usm_v(l)%qsws_veg_av(m) +        &
1836                                          surf_usm_v(l)%qsws_veg(m)
1837                       ENDDO
1838                    ENDIF
1839                   
1840                CASE ( 'usm_qsws_liq' )
1841!
1842!--                 array of latent heat flux from surfaces with liquid (land, roof, wall)
1843                    IF ( l == -1 ) THEN
1844                    DO  m = 1, surf_usm_h%ns
1845                       surf_usm_h%qsws_liq_av(m) =                              &
1846                                          surf_usm_h%qsws_liq_av(m) +           &
1847                                          surf_usm_h%qsws_liq(m)
1848                    ENDDO
1849                    ELSE
1850                       DO  m = 1, surf_usm_v(l)%ns
1851                          surf_usm_v(l)%qsws_liq_av(m) =                        &
1852                                          surf_usm_v(l)%qsws_liq_av(m) +        &
1853                                          surf_usm_v(l)%qsws_liq(m)
1854                       ENDDO
1855                    ENDIF
1856                   
1857                CASE ( 'usm_wghf' )
1858!
1859!--                 array of heat flux from ground (wall, roof, land)
1860                    IF ( l == -1 ) THEN
1861                       DO  m = 1, surf_usm_h%ns
1862                          surf_usm_h%wghf_eb_av(m) =                              &
1863                                             surf_usm_h%wghf_eb_av(m) +           &
1864                                             surf_usm_h%wghf_eb(m)
1865                       ENDDO
1866                    ELSE
1867                       DO  m = 1, surf_usm_v(l)%ns
1868                          surf_usm_v(l)%wghf_eb_av(m) =                        &
1869                                          surf_usm_v(l)%wghf_eb_av(m) +        &
1870                                          surf_usm_v(l)%wghf_eb(m)
1871                       ENDDO
1872                    ENDIF
1873                   
1874                CASE ( 'usm_wghf_window' )
1875!
1876!--                 array of heat flux from window ground (wall, roof, land)
1877                    IF ( l == -1 ) THEN
1878                       DO  m = 1, surf_usm_h%ns
1879                          surf_usm_h%wghf_eb_window_av(m) =                              &
1880                                             surf_usm_h%wghf_eb_window_av(m) +           &
1881                                             surf_usm_h%wghf_eb_window(m)
1882                       ENDDO
1883                    ELSE
1884                       DO  m = 1, surf_usm_v(l)%ns
1885                          surf_usm_v(l)%wghf_eb_window_av(m) =                        &
1886                                          surf_usm_v(l)%wghf_eb_window_av(m) +        &
1887                                          surf_usm_v(l)%wghf_eb_window(m)
1888                       ENDDO
1889                    ENDIF
1890
1891                CASE ( 'usm_wghf_green' )
1892!
1893!--                 array of heat flux from green ground (wall, roof, land)
1894                    IF ( l == -1 ) THEN
1895                       DO  m = 1, surf_usm_h%ns
1896                          surf_usm_h%wghf_eb_green_av(m) =                              &
1897                                             surf_usm_h%wghf_eb_green_av(m) +           &
1898                                             surf_usm_h%wghf_eb_green(m)
1899                       ENDDO
1900                    ELSE
1901                       DO  m = 1, surf_usm_v(l)%ns
1902                          surf_usm_v(l)%wghf_eb_green_av(m) =                        &
1903                                          surf_usm_v(l)%wghf_eb_green_av(m) +        &
1904                                          surf_usm_v(l)%wghf_eb_green(m)
1905                       ENDDO
1906                    ENDIF
1907                   
1908                CASE ( 'usm_iwghf' )
1909!
1910!--                 array of heat flux from indoor ground (wall, roof, land)
1911                    IF ( l == -1 ) THEN
1912                       DO  m = 1, surf_usm_h%ns
1913                          surf_usm_h%iwghf_eb_av(m) =                              &
1914                                             surf_usm_h%iwghf_eb_av(m) +           &
1915                                             surf_usm_h%iwghf_eb(m)
1916                       ENDDO
1917                    ELSE
1918                       DO  m = 1, surf_usm_v(l)%ns
1919                          surf_usm_v(l)%iwghf_eb_av(m) =                        &
1920                                          surf_usm_v(l)%iwghf_eb_av(m) +        &
1921                                          surf_usm_v(l)%iwghf_eb(m)
1922                       ENDDO
1923                    ENDIF
1924                   
1925                CASE ( 'usm_iwghf_window' )
1926!
1927!--                 array of heat flux from indoor window ground (wall, roof, land)
1928                    IF ( l == -1 ) THEN
1929                       DO  m = 1, surf_usm_h%ns
1930                          surf_usm_h%iwghf_eb_window_av(m) =                              &
1931                                             surf_usm_h%iwghf_eb_window_av(m) +           &
1932                                             surf_usm_h%iwghf_eb_window(m)
1933                       ENDDO
1934                    ELSE
1935                       DO  m = 1, surf_usm_v(l)%ns
1936                          surf_usm_v(l)%iwghf_eb_window_av(m) =                        &
1937                                          surf_usm_v(l)%iwghf_eb_window_av(m) +        &
1938                                          surf_usm_v(l)%iwghf_eb_window(m)
1939                       ENDDO
1940                    ENDIF
1941                   
1942                CASE ( 'usm_t_surf_wall' )
1943!
1944!--                 surface temperature for surfaces
1945                    IF ( l == -1 ) THEN
1946                       DO  m = 1, surf_usm_h%ns
1947                       surf_usm_h%t_surf_wall_av(m) =                               & 
1948                                          surf_usm_h%t_surf_wall_av(m) +            &
1949                                          t_surf_wall_h(m)
1950                       ENDDO
1951                    ELSE
1952                       DO  m = 1, surf_usm_v(l)%ns
1953                          surf_usm_v(l)%t_surf_wall_av(m) =                         &
1954                                          surf_usm_v(l)%t_surf_wall_av(m) +         &
1955                                          t_surf_wall_v(l)%t(m)
1956                       ENDDO
1957                    ENDIF
1958                   
1959                CASE ( 'usm_t_surf_window' )
1960!
1961!--                 surface temperature for window surfaces
1962                    IF ( l == -1 ) THEN
1963                       DO  m = 1, surf_usm_h%ns
1964                          surf_usm_h%t_surf_window_av(m) =                               &
1965                                             surf_usm_h%t_surf_window_av(m) +            &
1966                                             t_surf_window_h(m)
1967                       ENDDO
1968                    ELSE
1969                       DO  m = 1, surf_usm_v(l)%ns
1970                          surf_usm_v(l)%t_surf_window_av(m) =                         &
1971                                          surf_usm_v(l)%t_surf_window_av(m) +         &
1972                                          t_surf_window_v(l)%t(m)
1973                       ENDDO
1974                    ENDIF
1975                   
1976                CASE ( 'usm_t_surf_green' )
1977!
1978!--                 surface temperature for green surfaces
1979                    IF ( l == -1 ) THEN
1980                       DO  m = 1, surf_usm_h%ns
1981                          surf_usm_h%t_surf_green_av(m) =                               &
1982                                             surf_usm_h%t_surf_green_av(m) +            &
1983                                             t_surf_green_h(m)
1984                       ENDDO
1985                    ELSE
1986                       DO  m = 1, surf_usm_v(l)%ns
1987                          surf_usm_v(l)%t_surf_green_av(m) =                         &
1988                                          surf_usm_v(l)%t_surf_green_av(m) +         &
1989                                          t_surf_green_v(l)%t(m)
1990                       ENDDO
1991                    ENDIF
1992               
1993                CASE ( 'usm_theta_10cm' )
1994!
1995!--                 near surface temperature for whole surfaces
1996                    IF ( l == -1 ) THEN
1997                       DO  m = 1, surf_usm_h%ns
1998                          surf_usm_h%pt_10cm_av(m) =                               &
1999                                             surf_usm_h%pt_10cm_av(m) +            &
2000                                             surf_usm_h%pt_10cm(m)
2001                       ENDDO
2002                    ELSE
2003                       DO  m = 1, surf_usm_v(l)%ns
2004                          surf_usm_v(l)%pt_10cm_av(m) =                         &
2005                                          surf_usm_v(l)%pt_10cm_av(m) +         &
2006                                          surf_usm_v(l)%pt_10cm(m)
2007                       ENDDO
2008                    ENDIF
2009                   
2010                CASE ( 'usm_t_wall' )
2011!
2012!--                 wall temperature for  iwl layer of walls and land
2013                    IF ( l == -1 ) THEN
2014                       DO  m = 1, surf_usm_h%ns
2015                          surf_usm_h%t_wall_av(iwl,m) =                           &
2016                                             surf_usm_h%t_wall_av(iwl,m) +        &
2017                                             t_wall_h(iwl,m)
2018                       ENDDO
2019                    ELSE
2020                       DO  m = 1, surf_usm_v(l)%ns
2021                          surf_usm_v(l)%t_wall_av(iwl,m) =                     &
2022                                          surf_usm_v(l)%t_wall_av(iwl,m) +     &
2023                                          t_wall_v(l)%t(iwl,m)
2024                       ENDDO
2025                    ENDIF
2026                   
2027                CASE ( 'usm_t_window' )
2028!
2029!--                 window temperature for  iwl layer of walls and land
2030                    IF ( l == -1 ) THEN
2031                       DO  m = 1, surf_usm_h%ns
2032                          surf_usm_h%t_window_av(iwl,m) =                           &
2033                                             surf_usm_h%t_window_av(iwl,m) +        &
2034                                             t_window_h(iwl,m)
2035                       ENDDO
2036                    ELSE
2037                       DO  m = 1, surf_usm_v(l)%ns
2038                          surf_usm_v(l)%t_window_av(iwl,m) =                     &
2039                                          surf_usm_v(l)%t_window_av(iwl,m) +     &
2040                                          t_window_v(l)%t(iwl,m)
2041                       ENDDO
2042                    ENDIF
2043
2044                CASE ( 'usm_t_green' )
2045!
2046!--                 green temperature for  iwl layer of walls and land
2047                    IF ( l == -1 ) THEN
2048                       DO  m = 1, surf_usm_h%ns
2049                          surf_usm_h%t_green_av(iwl,m) =                           &
2050                                             surf_usm_h%t_green_av(iwl,m) +        &
2051                                             t_green_h(iwl,m)
2052                       ENDDO
2053                    ELSE
2054                       DO  m = 1, surf_usm_v(l)%ns
2055                          surf_usm_v(l)%t_green_av(iwl,m) =                     &
2056                                          surf_usm_v(l)%t_green_av(iwl,m) +     &
2057                                          t_green_v(l)%t(iwl,m)
2058                       ENDDO
2059                    ENDIF
2060
2061                CASE ( 'usm_swc' )
2062!
2063!--                 soil water content for  iwl layer of walls and land
2064                    IF ( l == -1 ) THEN
2065                    DO  m = 1, surf_usm_h%ns
2066                       surf_usm_h%swc_av(iwl,m) =                           &
2067                                          surf_usm_h%swc_av(iwl,m) +        &
2068                                          swc_h(iwl,m)
2069                    ENDDO
2070                    ELSE
2071                       DO  m = 1, surf_usm_v(l)%ns
2072                          surf_usm_v(l)%swc_av(iwl,m) =                     &
2073                                          surf_usm_v(l)%swc_av(iwl,m) +     &
2074                                          swc_v(l)%t(iwl,m)
2075                       ENDDO
2076                    ENDIF
2077
2078                CASE DEFAULT
2079                    CONTINUE
2080
2081           END SELECT
2082
2083        ELSEIF ( mode == 'average' )  THEN
2084           
2085           SELECT CASE ( TRIM( var ) )
2086
2087                CASE ( 'usm_wshf' )
2088!
2089!--                 array of sensible heat flux from surfaces (land, roof, wall)
2090                    IF ( l == -1 ) THEN
2091                       DO  m = 1, surf_usm_h%ns
2092                          surf_usm_h%wshf_eb_av(m) =                              &
2093                                             surf_usm_h%wshf_eb_av(m) /           &
2094                                             REAL( average_count_3d, kind=wp )
2095                       ENDDO
2096                    ELSE
2097                       DO  m = 1, surf_usm_v(l)%ns
2098                          surf_usm_v(l)%wshf_eb_av(m) =                        &
2099                                          surf_usm_v(l)%wshf_eb_av(m) /        &
2100                                          REAL( average_count_3d, kind=wp )
2101                       ENDDO
2102                    ENDIF
2103                   
2104                CASE ( 'usm_qsws' )
2105!
2106!--                 array of latent heat flux from surfaces (land, roof, wall)
2107                    IF ( l == -1 ) THEN
2108                    DO  m = 1, surf_usm_h%ns
2109                       surf_usm_h%qsws_av(m) =                              &
2110                                          surf_usm_h%qsws_av(m) /           &
2111                                          REAL( average_count_3d, kind=wp )
2112                    ENDDO
2113                    ELSE
2114                       DO  m = 1, surf_usm_v(l)%ns
2115                          surf_usm_v(l)%qsws_av(m) =                        &
2116                                          surf_usm_v(l)%qsws_av(m) /        &
2117                                          REAL( average_count_3d, kind=wp )
2118                       ENDDO
2119                    ENDIF
2120
2121                CASE ( 'usm_qsws_veg' )
2122!
2123!--                 array of latent heat flux from vegetation surfaces (land, roof, wall)
2124                    IF ( l == -1 ) THEN
2125                    DO  m = 1, surf_usm_h%ns
2126                       surf_usm_h%qsws_veg_av(m) =                              &
2127                                          surf_usm_h%qsws_veg_av(m) /           &
2128                                          REAL( average_count_3d, kind=wp )
2129                    ENDDO
2130                    ELSE
2131                       DO  m = 1, surf_usm_v(l)%ns
2132                          surf_usm_v(l)%qsws_veg_av(m) =                        &
2133                                          surf_usm_v(l)%qsws_veg_av(m) /        &
2134                                          REAL( average_count_3d, kind=wp )
2135                       ENDDO
2136                    ENDIF
2137                   
2138                CASE ( 'usm_qsws_liq' )
2139!
2140!--                 array of latent heat flux from surfaces with liquid (land, roof, wall)
2141                    IF ( l == -1 ) THEN
2142                    DO  m = 1, surf_usm_h%ns
2143                       surf_usm_h%qsws_liq_av(m) =                              &
2144                                          surf_usm_h%qsws_liq_av(m) /           &
2145                                          REAL( average_count_3d, kind=wp )
2146                    ENDDO
2147                    ELSE
2148                       DO  m = 1, surf_usm_v(l)%ns
2149                          surf_usm_v(l)%qsws_liq_av(m) =                        &
2150                                          surf_usm_v(l)%qsws_liq_av(m) /        &
2151                                          REAL( average_count_3d, kind=wp )
2152                       ENDDO
2153                    ENDIF
2154                   
2155                CASE ( 'usm_wghf' )
2156!
2157!--                 array of heat flux from ground (wall, roof, land)
2158                    IF ( l == -1 ) THEN
2159                       DO  m = 1, surf_usm_h%ns
2160                          surf_usm_h%wghf_eb_av(m) =                              &
2161                                             surf_usm_h%wghf_eb_av(m) /           &
2162                                             REAL( average_count_3d, kind=wp )
2163                       ENDDO
2164                    ELSE
2165                       DO  m = 1, surf_usm_v(l)%ns
2166                          surf_usm_v(l)%wghf_eb_av(m) =                        &
2167                                          surf_usm_v(l)%wghf_eb_av(m) /        &
2168                                          REAL( average_count_3d, kind=wp )
2169                       ENDDO
2170                    ENDIF
2171                   
2172                CASE ( 'usm_wghf_window' )
2173!
2174!--                 array of heat flux from window ground (wall, roof, land)
2175                    IF ( l == -1 ) THEN
2176                       DO  m = 1, surf_usm_h%ns
2177                          surf_usm_h%wghf_eb_window_av(m) =                              &
2178                                             surf_usm_h%wghf_eb_window_av(m) /           &
2179                                             REAL( average_count_3d, kind=wp )
2180                       ENDDO
2181                    ELSE
2182                       DO  m = 1, surf_usm_v(l)%ns
2183                          surf_usm_v(l)%wghf_eb_window_av(m) =                        &
2184                                          surf_usm_v(l)%wghf_eb_window_av(m) /        &
2185                                          REAL( average_count_3d, kind=wp )
2186                       ENDDO
2187                    ENDIF
2188
2189                CASE ( 'usm_wghf_green' )
2190!
2191!--                 array of heat flux from green ground (wall, roof, land)
2192                    IF ( l == -1 ) THEN
2193                       DO  m = 1, surf_usm_h%ns
2194                          surf_usm_h%wghf_eb_green_av(m) =                              &
2195                                             surf_usm_h%wghf_eb_green_av(m) /           &
2196                                             REAL( average_count_3d, kind=wp )
2197                       ENDDO
2198                    ELSE
2199                       DO  m = 1, surf_usm_v(l)%ns
2200                          surf_usm_v(l)%wghf_eb_green_av(m) =                        &
2201                                          surf_usm_v(l)%wghf_eb_green_av(m) /        &
2202                                          REAL( average_count_3d, kind=wp )
2203                       ENDDO
2204                    ENDIF
2205
2206                CASE ( 'usm_iwghf' )
2207!
2208!--                 array of heat flux from indoor ground (wall, roof, land)
2209                    IF ( l == -1 ) THEN
2210                       DO  m = 1, surf_usm_h%ns
2211                          surf_usm_h%iwghf_eb_av(m) =                              &
2212                                             surf_usm_h%iwghf_eb_av(m) /           &
2213                                             REAL( average_count_3d, kind=wp )
2214                       ENDDO
2215                    ELSE
2216                       DO  m = 1, surf_usm_v(l)%ns
2217                          surf_usm_v(l)%iwghf_eb_av(m) =                        &
2218                                          surf_usm_v(l)%iwghf_eb_av(m) /        &
2219                                          REAL( average_count_3d, kind=wp )
2220                       ENDDO
2221                    ENDIF
2222                   
2223                CASE ( 'usm_iwghf_window' )
2224!
2225!--                 array of heat flux from indoor window ground (wall, roof, land)
2226                    IF ( l == -1 ) THEN
2227                       DO  m = 1, surf_usm_h%ns
2228                          surf_usm_h%iwghf_eb_window_av(m) =                              &
2229                                             surf_usm_h%iwghf_eb_window_av(m) /           &
2230                                             REAL( average_count_3d, kind=wp )
2231                       ENDDO
2232                    ELSE
2233                       DO  m = 1, surf_usm_v(l)%ns
2234                          surf_usm_v(l)%iwghf_eb_window_av(m) =                        &
2235                                          surf_usm_v(l)%iwghf_eb_window_av(m) /        &
2236                                          REAL( average_count_3d, kind=wp )
2237                       ENDDO
2238                    ENDIF
2239                   
2240                CASE ( 'usm_t_surf_wall' )
2241!
2242!--                 surface temperature for surfaces
2243                    IF ( l == -1 ) THEN
2244                       DO  m = 1, surf_usm_h%ns
2245                       surf_usm_h%t_surf_wall_av(m) =                               & 
2246                                          surf_usm_h%t_surf_wall_av(m) /            &
2247                                             REAL( average_count_3d, kind=wp )
2248                       ENDDO
2249                    ELSE
2250                       DO  m = 1, surf_usm_v(l)%ns
2251                          surf_usm_v(l)%t_surf_wall_av(m) =                         &
2252                                          surf_usm_v(l)%t_surf_wall_av(m) /         &
2253                                          REAL( average_count_3d, kind=wp )
2254                       ENDDO
2255                    ENDIF
2256                   
2257                CASE ( 'usm_t_surf_window' )
2258!
2259!--                 surface temperature for window surfaces
2260                    IF ( l == -1 ) THEN
2261                       DO  m = 1, surf_usm_h%ns
2262                          surf_usm_h%t_surf_window_av(m) =                               &
2263                                             surf_usm_h%t_surf_window_av(m) /            &
2264                                             REAL( average_count_3d, kind=wp )
2265                       ENDDO
2266                    ELSE
2267                       DO  m = 1, surf_usm_v(l)%ns
2268                          surf_usm_v(l)%t_surf_window_av(m) =                         &
2269                                          surf_usm_v(l)%t_surf_window_av(m) /         &
2270                                          REAL( average_count_3d, kind=wp )
2271                       ENDDO
2272                    ENDIF
2273                   
2274                CASE ( 'usm_t_surf_green' )
2275!
2276!--                 surface temperature for green surfaces
2277                    IF ( l == -1 ) THEN
2278                       DO  m = 1, surf_usm_h%ns
2279                          surf_usm_h%t_surf_green_av(m) =                               &
2280                                             surf_usm_h%t_surf_green_av(m) /            &
2281                                             REAL( average_count_3d, kind=wp )
2282                       ENDDO
2283                    ELSE
2284                       DO  m = 1, surf_usm_v(l)%ns
2285                          surf_usm_v(l)%t_surf_green_av(m) =                         &
2286                                          surf_usm_v(l)%t_surf_green_av(m) /         &
2287                                          REAL( average_count_3d, kind=wp )
2288                       ENDDO
2289                    ENDIF
2290                   
2291                CASE ( 'usm_theta_10cm' )
2292!
2293!--                 near surface temperature for whole surfaces
2294                    IF ( l == -1 ) THEN
2295                       DO  m = 1, surf_usm_h%ns
2296                          surf_usm_h%pt_10cm_av(m) =                               &
2297                                             surf_usm_h%pt_10cm_av(m) /            &
2298                                             REAL( average_count_3d, kind=wp )
2299                       ENDDO
2300                    ELSE
2301                       DO  m = 1, surf_usm_v(l)%ns
2302                          surf_usm_v(l)%pt_10cm_av(m) =                         &
2303                                          surf_usm_v(l)%pt_10cm_av(m) /         &
2304                                          REAL( average_count_3d, kind=wp )
2305                       ENDDO
2306                    ENDIF
2307
2308                   
2309                CASE ( 'usm_t_wall' )
2310!
2311!--                 wall temperature for  iwl layer of walls and land
2312                    IF ( l == -1 ) THEN
2313                       DO  m = 1, surf_usm_h%ns
2314                          surf_usm_h%t_wall_av(iwl,m) =                           &
2315                                             surf_usm_h%t_wall_av(iwl,m) /        &
2316                                             REAL( average_count_3d, kind=wp )
2317                       ENDDO
2318                    ELSE
2319                       DO  m = 1, surf_usm_v(l)%ns
2320                          surf_usm_v(l)%t_wall_av(iwl,m) =                     &
2321                                          surf_usm_v(l)%t_wall_av(iwl,m) /     &
2322                                          REAL( average_count_3d, kind=wp )
2323                       ENDDO
2324                    ENDIF
2325
2326                CASE ( 'usm_t_window' )
2327!
2328!--                 window temperature for  iwl layer of walls and land
2329                    IF ( l == -1 ) THEN
2330                       DO  m = 1, surf_usm_h%ns
2331                          surf_usm_h%t_window_av(iwl,m) =                           &
2332                                             surf_usm_h%t_window_av(iwl,m) /        &
2333                                             REAL( average_count_3d, kind=wp )
2334                       ENDDO
2335                    ELSE
2336                       DO  m = 1, surf_usm_v(l)%ns
2337                          surf_usm_v(l)%t_window_av(iwl,m) =                     &
2338                                          surf_usm_v(l)%t_window_av(iwl,m) /     &
2339                                          REAL( average_count_3d, kind=wp )
2340                       ENDDO
2341                    ENDIF
2342
2343                CASE ( 'usm_t_green' )
2344!
2345!--                 green temperature for  iwl layer of walls and land
2346                    IF ( l == -1 ) THEN
2347                       DO  m = 1, surf_usm_h%ns
2348                          surf_usm_h%t_green_av(iwl,m) =                           &
2349                                             surf_usm_h%t_green_av(iwl,m) /        &
2350                                             REAL( average_count_3d, kind=wp )
2351                       ENDDO
2352                    ELSE
2353                       DO  m = 1, surf_usm_v(l)%ns
2354                          surf_usm_v(l)%t_green_av(iwl,m) =                     &
2355                                          surf_usm_v(l)%t_green_av(iwl,m) /     &
2356                                          REAL( average_count_3d, kind=wp )
2357                       ENDDO
2358                    ENDIF
2359                   
2360                CASE ( 'usm_swc' )
2361!
2362!--                 soil water content for  iwl layer of walls and land
2363                    IF ( l == -1 ) THEN
2364                    DO  m = 1, surf_usm_h%ns
2365                       surf_usm_h%swc_av(iwl,m) =                           &
2366                                          surf_usm_h%swc_av(iwl,m) /        &
2367                                          REAL( average_count_3d, kind=wp )
2368                    ENDDO
2369                    ELSE
2370                       DO  m = 1, surf_usm_v(l)%ns
2371                          surf_usm_v(l)%swc_av(iwl,m) =                     &
2372                                          surf_usm_v(l)%swc_av(iwl,m) /     &
2373                                          REAL( average_count_3d, kind=wp )
2374                       ENDDO
2375                    ENDIF
2376
2377
2378           END SELECT
2379
2380        ENDIF
2381
2382        ENDIF
2383
2384    END SUBROUTINE usm_3d_data_averaging
2385
2386
2387
2388!------------------------------------------------------------------------------!
2389! Description:
2390! ------------
2391!> Set internal Neumann boundary condition at outer soil grid points
2392!> for temperature and humidity.
2393!------------------------------------------------------------------------------!
2394 SUBROUTINE usm_boundary_condition
2395 
2396    IMPLICIT NONE
2397
2398    INTEGER(iwp) :: i      !< grid index x-direction
2399    INTEGER(iwp) :: ioff   !< offset index x-direction indicating location of soil grid point
2400    INTEGER(iwp) :: j      !< grid index y-direction
2401    INTEGER(iwp) :: joff   !< offset index x-direction indicating location of soil grid point
2402    INTEGER(iwp) :: k      !< grid index z-direction
2403    INTEGER(iwp) :: koff   !< offset index x-direction indicating location of soil grid point
2404    INTEGER(iwp) :: l      !< running index surface-orientation
2405    INTEGER(iwp) :: m      !< running index surface elements
2406
2407    koff = surf_usm_h%koff
2408    DO  m = 1, surf_usm_h%ns
2409       i = surf_usm_h%i(m)
2410       j = surf_usm_h%j(m)
2411       k = surf_usm_h%k(m)
2412       pt(k+koff,j,i) = pt(k,j,i)
2413    ENDDO
2414
2415    DO  l = 0, 3
2416       ioff = surf_usm_v(l)%ioff
2417       joff = surf_usm_v(l)%joff
2418       DO  m = 1, surf_usm_v(l)%ns
2419          i = surf_usm_v(l)%i(m)
2420          j = surf_usm_v(l)%j(m)
2421          k = surf_usm_v(l)%k(m)
2422          pt(k,j+joff,i+ioff) = pt(k,j,i)
2423       ENDDO
2424    ENDDO
2425
2426 END SUBROUTINE usm_boundary_condition
2427
2428
2429!------------------------------------------------------------------------------!
2430!
2431! Description:
2432! ------------
2433!> Subroutine checks variables and assigns units.
2434!> It is called out from subroutine check_parameters.
2435!------------------------------------------------------------------------------!
2436    SUBROUTINE usm_check_data_output( variable, unit )
2437
2438        IMPLICIT NONE
2439
2440        CHARACTER(LEN=*),INTENT(IN)    ::  variable   !<
2441        CHARACTER(LEN=*),INTENT(OUT)   ::  unit       !<
2442
2443        INTEGER(iwp)                                  :: i,j,l         !< index
2444        CHARACTER(LEN=2)                              :: ls
2445        CHARACTER(LEN=varnamelength)                  :: var           !< TRIM(variable)
2446        INTEGER(iwp), PARAMETER                       :: nl1 = 15      !< number of directional usm variables
2447        CHARACTER(LEN=varnamelength), DIMENSION(nl1)  :: varlist1 = &  !< list of directional usm variables
2448                  (/'usm_wshf                      ', &
2449                    'usm_wghf                      ', &
2450                    'usm_wghf_window               ', &
2451                    'usm_wghf_green                ', &
2452                    'usm_iwghf                     ', &
2453                    'usm_iwghf_window              ', &
2454                    'usm_surfz                     ', &
2455                    'usm_surfwintrans              ', &
2456                    'usm_surfcat                   ', &
2457                    'usm_t_surf_wall               ', &
2458                    'usm_t_surf_window             ', &
2459                    'usm_t_surf_green              ', &
2460                    'usm_t_green                   ', &
2461                    'usm_qsws                      ', &
2462                    'usm_theta_10cm                '/)
2463
2464        INTEGER(iwp), PARAMETER                       :: nl2 = 3       !< number of directional layer usm variables
2465        CHARACTER(LEN=varnamelength), DIMENSION(nl2)  :: varlist2 = &  !< list of directional layer usm variables
2466                  (/'usm_t_wall                    ', &
2467                    'usm_t_window                  ', &
2468                    'usm_t_green                   '/)
2469
2470        INTEGER(iwp), PARAMETER                       :: nd = 5     !< number of directions
2471        CHARACTER(LEN=6), DIMENSION(nd), PARAMETER  :: dirname = &  !< direction names
2472                  (/'_roof ','_south','_north','_west ','_east '/)
2473        LOGICAL                                       :: lfound     !< flag if the variable is found
2474
2475
2476        lfound = .FALSE.
2477
2478        var = TRIM(variable)
2479
2480!
2481!--     check if variable exists
2482!--     directional variables
2483        DO i = 1, nl1
2484           DO j = 1, nd
2485              IF ( TRIM(var) == TRIM(varlist1(i))//TRIM(dirname(j)) ) THEN
2486                 lfound = .TRUE.
2487                 EXIT
2488              ENDIF
2489              IF ( lfound ) EXIT
2490           ENDDO
2491        ENDDO
2492        IF ( lfound ) GOTO 10
2493!
2494!--     directional layer variables
2495        DO i = 1, nl2
2496           DO j = 1, nd
2497              DO l = nzb_wall, nzt_wall
2498                 WRITE(ls,'(A1,I1)') '_',l
2499                 IF ( TRIM(var) == TRIM(varlist2(i))//TRIM(ls)//TRIM(dirname(j)) ) THEN
2500                    lfound = .TRUE.
2501                    EXIT
2502                 ENDIF
2503              ENDDO
2504              IF ( lfound ) EXIT
2505           ENDDO
2506        ENDDO
2507        IF ( .NOT.  lfound ) THEN
2508           unit = 'illegal'
2509           RETURN
2510        ENDIF
251110      CONTINUE
2512
2513        IF ( var(1:9)  == 'usm_wshf_'  .OR.  var(1:9) == 'usm_wghf_' .OR.                 &
2514             var(1:16) == 'usm_wghf_window_' .OR. var(1:15) == 'usm_wghf_green_' .OR.     &
2515             var(1:10) == 'usm_iwghf_' .OR. var(1:17) == 'usm_iwghf_window_'    .OR.      &
2516             var(1:17) == 'usm_surfwintrans_' .OR.                                        &
2517             var(1:9)  == 'usm_qsws_'  .OR.  var(1:13)  == 'usm_qsws_veg_'  .OR.          &
2518             var(1:13) == 'usm_qsws_liq_' ) THEN
2519            unit = 'W/m2'
2520        ELSE IF ( var(1:15) == 'usm_t_surf_wall'   .OR.  var(1:10) == 'usm_t_wall' .OR.   &
2521                  var(1:12) == 'usm_t_window' .OR. var(1:17) == 'usm_t_surf_window' .OR.  &
2522                  var(1:16) == 'usm_t_surf_green'  .OR.                                   &
2523                  var(1:11) == 'usm_t_green' .OR.  var(1:7) == 'usm_swc' .OR.             &
2524                  var(1:14) == 'usm_theta_10cm' )  THEN
2525            unit = 'K'
2526        ELSE IF ( var(1:9) == 'usm_surfz'  .OR.  var(1:11) == 'usm_surfcat' )  THEN
2527            unit = '1'
2528        ELSE
2529            unit = 'illegal'
2530        ENDIF
2531
2532    END SUBROUTINE usm_check_data_output
2533
2534
2535!------------------------------------------------------------------------------!
2536! Description:
2537! ------------
2538!> Check parameters routine for urban surface model
2539!------------------------------------------------------------------------------!
2540    SUBROUTINE usm_check_parameters
2541
2542       USE control_parameters,                                                 &
2543           ONLY:  bc_pt_b, bc_q_b, constant_flux_layer, large_scale_forcing,   &
2544                  lsf_surf, topography
2545
2546       USE netcdf_data_input_mod,                                             &
2547            ONLY:  building_type_f
2548
2549       IMPLICIT NONE
2550
2551       INTEGER(iwp) ::  i        !< running index, x-dimension
2552       INTEGER(iwp) ::  j        !< running index, y-dimension
2553
2554!
2555!--    Dirichlet boundary conditions are required as the surface fluxes are
2556!--    calculated from the temperature/humidity gradients in the urban surface
2557!--    model
2558       IF ( bc_pt_b == 'neumann'   .OR.   bc_q_b == 'neumann' )  THEN
2559          message_string = 'urban surface model requires setting of '//        &
2560                           'bc_pt_b = "dirichlet" and '//                      &
2561                           'bc_q_b  = "dirichlet"'
2562          CALL message( 'usm_check_parameters', 'PA0590', 1, 2, 0, 6, 0 )
2563       ENDIF
2564
2565       IF ( .NOT.  constant_flux_layer )  THEN
2566          message_string = 'urban surface model requires '//                   &
2567                           'constant_flux_layer = .T.'
2568          CALL message( 'usm_check_parameters', 'PA0084', 1, 2, 0, 6, 0 )
2569       ENDIF
2570
2571       IF (  .NOT.  radiation )  THEN
2572          message_string = 'urban surface model requires '//                   &
2573                           'the radiation model to be switched on'
2574          CALL message( 'usm_check_parameters', 'PA0084', 1, 2, 0, 6, 0 )
2575       ENDIF
2576!       
2577!--    Surface forcing has to be disabled for LSF in case of enabled
2578!--    urban surface module
2579       IF ( large_scale_forcing )  THEN
2580          lsf_surf = .FALSE.
2581       ENDIF
2582!
2583!--    Topography
2584       IF ( topography == 'flat' )  THEN
2585          message_string = 'topography /= "flat" is required '//               &
2586                           'when using the urban surface model'
2587          CALL message( 'usm_check_parameters', 'PA0592', 1, 2, 0, 6, 0 )
2588       ENDIF
2589!
2590!--    naheatlayers
2591       IF ( naheatlayers > nzt )  THEN
2592          message_string = 'number of anthropogenic heat layers '//            &
2593                           '"naheatlayers" can not be larger than'//           &
2594                           ' number of domain layers "nzt"'
2595          CALL message( 'usm_check_parameters', 'PA0593', 1, 2, 0, 6, 0 )
2596       ENDIF
2597!
2598!--    Check if building types are set within a valid range.
2599       IF ( building_type < LBOUND( building_pars, 2 )  .AND.                  &
2600            building_type > UBOUND( building_pars, 2 ) )  THEN
2601          WRITE( message_string, * ) 'building_type = ', building_type,        &
2602                                     ' is out of the valid range'
2603          CALL message( 'usm_check_parameters', 'PA0529', 2, 2, 0, 6, 0 )
2604       ENDIF
2605       IF ( building_type_f%from_file )  THEN
2606          DO  i = nxl, nxr
2607             DO  j = nys, nyn
2608                IF ( building_type_f%var(j,i) /= building_type_f%fill  .AND.   &
2609              ( building_type_f%var(j,i) < LBOUND( building_pars, 2 )  .OR.    &
2610                building_type_f%var(j,i) > UBOUND( building_pars, 2 ) ) )      &
2611                THEN
2612                   WRITE( message_string, * ) 'building_type = is out of ' //  &
2613                                        'the valid range at (j,i) = ', j, i
2614                   CALL message( 'usm_check_parameters', 'PA0529', 2, 2, 0, 6, 0 )
2615                ENDIF
2616             ENDDO
2617          ENDDO
2618       ENDIF
2619    END SUBROUTINE usm_check_parameters
2620
2621
2622!------------------------------------------------------------------------------!
2623!
2624! Description:
2625! ------------
2626!> Output of the 3D-arrays in netCDF and/or AVS format
2627!> for variables of urban_surface model.
2628!> It resorts the urban surface module output quantities from surf style
2629!> indexing into temporary 3D array with indices (i,j,k).
2630!> It is called from subroutine data_output_3d.
2631!------------------------------------------------------------------------------!
2632    SUBROUTINE usm_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
2633       
2634        IMPLICIT NONE
2635
2636        INTEGER(iwp), INTENT(IN)       ::  av        !< flag if averaged
2637        CHARACTER (len=*), INTENT(IN)  ::  variable  !< variable name
2638        INTEGER(iwp), INTENT(IN)       ::  nzb_do    !< lower limit of the data output (usually 0)
2639        INTEGER(iwp), INTENT(IN)       ::  nzt_do    !< vertical upper limit of the data output (usually nz_do3d)
2640        LOGICAL, INTENT(OUT)           ::  found     !<
2641        REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf   !< sp - it has to correspond to module data_output_3d
2642        REAL(sp), DIMENSION(nzb:nzt+1,nys:nyn,nxl:nxr)     ::  temp_pf    !< temp array for urban surface output procedure
2643       
2644        CHARACTER (len=varnamelength)                      :: var     !< trimmed variable name
2645        INTEGER(iwp), PARAMETER                            :: nd = 5  !< number of directions
2646        CHARACTER(len=6), DIMENSION(0:nd-1), PARAMETER     :: dirname = (/ '_roof ', '_south', '_north', '_west ', '_east ' /)
2647        INTEGER(iwp), DIMENSION(0:nd-1), PARAMETER         :: dirint =  (/    iup_u, isouth_u, inorth_u,  iwest_u,  ieast_u /)
2648        INTEGER(iwp), DIMENSION(0:nd-1), PARAMETER         :: diridx =  (/       -1,        1,        0,        3,        2 /)
2649                                                                      !< index for surf_*_v: 0:3 = (North, South, East, West)
2650        INTEGER(iwp)                   :: ids,idsint,idsidx
2651        INTEGER(iwp)                   :: i,j,k,iwl,istat, l, m  !< running indices
2652
2653        found = .TRUE.
2654        temp_pf = -1._wp
2655       
2656        ids = -1
2657        var = TRIM(variable)
2658        DO i = 0, nd-1
2659            k = len(TRIM(var))
2660            j = len(TRIM(dirname(i)))
2661            IF ( TRIM(var(k-j+1:k)) == TRIM(dirname(i)) )  THEN
2662                ids = i
2663                idsint = dirint(ids)
2664                idsidx = diridx(ids)
2665                var = var(:k-j)
2666                EXIT
2667            ENDIF
2668        ENDDO
2669        IF ( ids == -1 )  THEN
2670            var = TRIM(variable)
2671        ENDIF
2672        IF ( var(1:11) == 'usm_t_wall_'  .AND.  len(TRIM(var)) >= 12 )  THEN
2673!
2674!--         wall layers
2675            READ(var(12:12), '(I1)', iostat=istat ) iwl
2676            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
2677                var = var(1:10)
2678            ENDIF
2679        ENDIF
2680        IF ( var(1:13) == 'usm_t_window_'  .AND.  len(TRIM(var)) >= 14 )  THEN
2681!
2682!--         window layers
2683            READ(var(14:14), '(I1)', iostat=istat ) iwl
2684            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
2685                var = var(1:12)
2686            ENDIF
2687        ENDIF
2688        IF ( var(1:12) == 'usm_t_green_'  .AND.  len(TRIM(var)) >= 13 )  THEN
2689!
2690!--         green layers
2691            READ(var(13:13), '(I1)', iostat=istat ) iwl
2692            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
2693                var = var(1:11)
2694            ENDIF
2695        ENDIF
2696        IF ( var(1:8) == 'usm_swc_'  .AND.  len(TRIM(var)) >= 9 )  THEN
2697!
2698!--         green layers soil water content
2699            READ(var(9:9), '(I1)', iostat=istat ) iwl
2700            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
2701                var = var(1:7)
2702            ENDIF
2703        ENDIF
2704       
2705        SELECT CASE ( TRIM(var) )
2706
2707          CASE ( 'usm_surfz' )
2708!
2709!--           array of surface height (z)
2710              IF ( idsint == iup_u )  THEN
2711                 DO  m = 1, surf_usm_h%ns
2712                    i = surf_usm_h%i(m)
2713                    j = surf_usm_h%j(m)
2714                    k = surf_usm_h%k(m)
2715                    temp_pf(0,j,i) = MAX( temp_pf(0,j,i), REAL( k, KIND = sp) )
2716                 ENDDO
2717              ELSE
2718                 l = idsidx
2719                 DO  m = 1, surf_usm_v(l)%ns
2720                    i = surf_usm_v(l)%i(m)
2721                    j = surf_usm_v(l)%j(m)
2722                    k = surf_usm_v(l)%k(m)
2723                    temp_pf(0,j,i) = MAX( temp_pf(0,j,i), REAL( k, KIND = sp) + 1.0_sp )
2724                 ENDDO
2725              ENDIF
2726
2727          CASE ( 'usm_surfcat' )
2728!
2729!--           surface category
2730              IF ( idsint == iup_u )  THEN
2731                 DO  m = 1, surf_usm_h%ns
2732                    i = surf_usm_h%i(m)
2733                    j = surf_usm_h%j(m)
2734                    k = surf_usm_h%k(m)
2735                    temp_pf(k,j,i) = surf_usm_h%surface_types(m)
2736                 ENDDO
2737              ELSE
2738                 l = idsidx
2739                 DO  m = 1, surf_usm_v(l)%ns
2740                    i = surf_usm_v(l)%i(m)
2741                    j = surf_usm_v(l)%j(m)
2742                    k = surf_usm_v(l)%k(m)
2743                    temp_pf(k,j,i) = surf_usm_v(l)%surface_types(m)
2744                 ENDDO
2745              ENDIF
2746             
2747          CASE ( 'usm_surfwintrans' )
2748!
2749!--           transmissivity window tiles
2750              IF ( idsint == iup_u )  THEN
2751                 DO  m = 1, surf_usm_h%ns
2752                    i = surf_usm_h%i(m)
2753                    j = surf_usm_h%j(m)
2754                    k = surf_usm_h%k(m)
2755                    temp_pf(k,j,i) = surf_usm_h%transmissivity(m)
2756                 ENDDO
2757              ELSE
2758                 l = idsidx
2759                 DO  m = 1, surf_usm_v(l)%ns
2760                    i = surf_usm_v(l)%i(m)
2761                    j = surf_usm_v(l)%j(m)
2762                    k = surf_usm_v(l)%k(m)
2763                    temp_pf(k,j,i) = surf_usm_v(l)%transmissivity(m)
2764                 ENDDO
2765              ENDIF
2766
2767          CASE ( 'usm_wshf' )
2768!
2769!--           array of sensible heat flux from surfaces
2770              IF ( av == 0 )  THEN
2771                 IF ( idsint == iup_u )  THEN
2772                    DO  m = 1, surf_usm_h%ns
2773                       i = surf_usm_h%i(m)
2774                       j = surf_usm_h%j(m)
2775                       k = surf_usm_h%k(m)
2776                       temp_pf(k,j,i) = surf_usm_h%wshf_eb(m)
2777                    ENDDO
2778                 ELSE
2779                    l = idsidx
2780                    DO  m = 1, surf_usm_v(l)%ns
2781                       i = surf_usm_v(l)%i(m)
2782                       j = surf_usm_v(l)%j(m)
2783                       k = surf_usm_v(l)%k(m)
2784                       temp_pf(k,j,i) = surf_usm_v(l)%wshf_eb(m)
2785                    ENDDO
2786                 ENDIF
2787              ELSE
2788                 IF ( idsint == iup_u )  THEN
2789                    DO  m = 1, surf_usm_h%ns
2790                       i = surf_usm_h%i(m)
2791                       j = surf_usm_h%j(m)
2792                       k = surf_usm_h%k(m)
2793                       temp_pf(k,j,i) = surf_usm_h%wshf_eb_av(m)
2794                    ENDDO
2795                 ELSE
2796                    l = idsidx
2797                    DO  m = 1, surf_usm_v(l)%ns
2798                       i = surf_usm_v(l)%i(m)
2799                       j = surf_usm_v(l)%j(m)
2800                       k = surf_usm_v(l)%k(m)
2801                       temp_pf(k,j,i) = surf_usm_v(l)%wshf_eb_av(m)
2802                    ENDDO
2803                 ENDIF
2804              ENDIF
2805             
2806             
2807          CASE ( 'usm_qsws' )
2808!
2809!--           array of latent heat flux from surfaces
2810              IF ( av == 0 )  THEN
2811                 IF ( idsint == iup_u )  THEN
2812                    DO  m = 1, surf_usm_h%ns
2813                       i = surf_usm_h%i(m)
2814                       j = surf_usm_h%j(m)
2815                       k = surf_usm_h%k(m)
2816                       temp_pf(k,j,i) = surf_usm_h%qsws(m) * l_v
2817                    ENDDO
2818                 ELSE
2819                    l = idsidx
2820                    DO  m = 1, surf_usm_v(l)%ns
2821                       i = surf_usm_v(l)%i(m)
2822                       j = surf_usm_v(l)%j(m)
2823                       k = surf_usm_v(l)%k(m)
2824                       temp_pf(k,j,i) = surf_usm_v(l)%qsws(m) * l_v
2825                    ENDDO
2826                 ENDIF
2827              ELSE
2828                 IF ( idsint == iup_u )  THEN
2829                    DO  m = 1, surf_usm_h%ns
2830                       i = surf_usm_h%i(m)
2831                       j = surf_usm_h%j(m)
2832                       k = surf_usm_h%k(m)
2833                       temp_pf(k,j,i) = surf_usm_h%qsws_av(m)
2834                    ENDDO
2835                 ELSE
2836                    l = idsidx
2837                    DO  m = 1, surf_usm_v(l)%ns
2838                       i = surf_usm_v(l)%i(m)
2839                       j = surf_usm_v(l)%j(m)
2840                       k = surf_usm_v(l)%k(m)
2841                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_av(m)
2842                    ENDDO
2843                 ENDIF
2844              ENDIF
2845             
2846          CASE ( 'usm_qsws_veg' )
2847!
2848!--           array of latent heat flux from vegetation surfaces
2849              IF ( av == 0 )  THEN
2850                 IF ( idsint == iup_u )  THEN
2851                    DO  m = 1, surf_usm_h%ns
2852                       i = surf_usm_h%i(m)
2853                       j = surf_usm_h%j(m)
2854                       k = surf_usm_h%k(m)
2855                       temp_pf(k,j,i) = surf_usm_h%qsws_veg(m)
2856                    ENDDO
2857                 ELSE
2858                    l = idsidx
2859                    DO  m = 1, surf_usm_v(l)%ns
2860                       i = surf_usm_v(l)%i(m)
2861                       j = surf_usm_v(l)%j(m)
2862                       k = surf_usm_v(l)%k(m)
2863                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_veg(m)
2864                    ENDDO
2865                 ENDIF
2866              ELSE
2867                 IF ( idsint == iup_u )  THEN
2868                    DO  m = 1, surf_usm_h%ns
2869                       i = surf_usm_h%i(m)
2870                       j = surf_usm_h%j(m)
2871                       k = surf_usm_h%k(m)
2872                       temp_pf(k,j,i) = surf_usm_h%qsws_veg_av(m)
2873                    ENDDO
2874                 ELSE
2875                    l = idsidx
2876                    DO  m = 1, surf_usm_v(l)%ns
2877                       i = surf_usm_v(l)%i(m)
2878                       j = surf_usm_v(l)%j(m)
2879                       k = surf_usm_v(l)%k(m)
2880                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_veg_av(m)
2881                    ENDDO
2882                 ENDIF
2883              ENDIF
2884             
2885          CASE ( 'usm_qsws_liq' )
2886!
2887!--           array of latent heat flux from surfaces with liquid
2888              IF ( av == 0 )  THEN
2889                 IF ( idsint == iup_u )  THEN
2890                    DO  m = 1, surf_usm_h%ns
2891                       i = surf_usm_h%i(m)
2892                       j = surf_usm_h%j(m)
2893                       k = surf_usm_h%k(m)
2894                       temp_pf(k,j,i) = surf_usm_h%qsws_liq(m)
2895                    ENDDO
2896                 ELSE
2897                    l = idsidx
2898                    DO  m = 1, surf_usm_v(l)%ns
2899                       i = surf_usm_v(l)%i(m)
2900                       j = surf_usm_v(l)%j(m)
2901                       k = surf_usm_v(l)%k(m)
2902                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_liq(m)
2903                    ENDDO
2904                 ENDIF
2905              ELSE
2906                 IF ( idsint == iup_u )  THEN
2907                    DO  m = 1, surf_usm_h%ns
2908                       i = surf_usm_h%i(m)
2909                       j = surf_usm_h%j(m)
2910                       k = surf_usm_h%k(m)
2911                       temp_pf(k,j,i) = surf_usm_h%qsws_liq_av(m)
2912                    ENDDO
2913                 ELSE
2914                    l = idsidx
2915                    DO  m = 1, surf_usm_v(l)%ns
2916                       i = surf_usm_v(l)%i(m)
2917                       j = surf_usm_v(l)%j(m)
2918                       k = surf_usm_v(l)%k(m)
2919                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_liq_av(m)
2920                    ENDDO
2921                 ENDIF
2922              ENDIF
2923
2924          CASE ( 'usm_wghf' )
2925!
2926!--           array of heat flux from ground (land, wall, roof)
2927              IF ( av == 0 )  THEN
2928                 IF ( idsint == iup_u )  THEN
2929                    DO  m = 1, surf_usm_h%ns
2930                       i = surf_usm_h%i(m)
2931                       j = surf_usm_h%j(m)
2932                       k = surf_usm_h%k(m)
2933                       temp_pf(k,j,i) = surf_usm_h%wghf_eb(m)
2934                    ENDDO
2935                 ELSE
2936                    l = idsidx
2937                    DO  m = 1, surf_usm_v(l)%ns
2938                       i = surf_usm_v(l)%i(m)
2939                       j = surf_usm_v(l)%j(m)
2940                       k = surf_usm_v(l)%k(m)
2941                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb(m)
2942                    ENDDO
2943                 ENDIF
2944              ELSE
2945                 IF ( idsint == iup_u )  THEN
2946                    DO  m = 1, surf_usm_h%ns
2947                       i = surf_usm_h%i(m)
2948                       j = surf_usm_h%j(m)
2949                       k = surf_usm_h%k(m)
2950                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_av(m)
2951                    ENDDO
2952                 ELSE
2953                    l = idsidx
2954                    DO  m = 1, surf_usm_v(l)%ns
2955                       i = surf_usm_v(l)%i(m)
2956                       j = surf_usm_v(l)%j(m)
2957                       k = surf_usm_v(l)%k(m)
2958                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_av(m)
2959                    ENDDO
2960                 ENDIF
2961              ENDIF
2962
2963          CASE ( 'usm_wghf_window' )
2964!
2965!--           array of heat flux from window ground (land, wall, roof)
2966              IF ( av == 0 )  THEN
2967                 IF ( idsint == iup_u )  THEN
2968                    DO  m = 1, surf_usm_h%ns
2969                       i = surf_usm_h%i(m)
2970                       j = surf_usm_h%j(m)
2971                       k = surf_usm_h%k(m)
2972                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_window(m)
2973                    ENDDO
2974                 ELSE
2975                    l = idsidx
2976                    DO  m = 1, surf_usm_v(l)%ns
2977                       i = surf_usm_v(l)%i(m)
2978                       j = surf_usm_v(l)%j(m)
2979                       k = surf_usm_v(l)%k(m)
2980                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_window(m)
2981                    ENDDO
2982                 ENDIF
2983              ELSE
2984                 IF ( idsint == iup_u )  THEN
2985                    DO  m = 1, surf_usm_h%ns
2986                       i = surf_usm_h%i(m)
2987                       j = surf_usm_h%j(m)
2988                       k = surf_usm_h%k(m)
2989                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_window_av(m)
2990                    ENDDO
2991                 ELSE
2992                    l = idsidx
2993                    DO  m = 1, surf_usm_v(l)%ns
2994                       i = surf_usm_v(l)%i(m)
2995                       j = surf_usm_v(l)%j(m)
2996                       k = surf_usm_v(l)%k(m)
2997                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_window_av(m)
2998                    ENDDO
2999                 ENDIF
3000              ENDIF
3001
3002          CASE ( 'usm_wghf_green' )
3003!
3004!--           array of heat flux from green ground (land, wall, roof)
3005              IF ( av == 0 )  THEN
3006                 IF ( idsint == iup_u )  THEN
3007                    DO  m = 1, surf_usm_h%ns
3008                       i = surf_usm_h%i(m)
3009                       j = surf_usm_h%j(m)
3010                       k = surf_usm_h%k(m)
3011                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_green(m)
3012                    ENDDO
3013                 ELSE
3014                    l = idsidx
3015                    DO  m = 1, surf_usm_v(l)%ns
3016                       i = surf_usm_v(l)%i(m)
3017                       j = surf_usm_v(l)%j(m)
3018                       k = surf_usm_v(l)%k(m)
3019                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_green(m)
3020                    ENDDO
3021                 ENDIF
3022              ELSE
3023                 IF ( idsint == iup_u )  THEN
3024                    DO  m = 1, surf_usm_h%ns
3025                       i = surf_usm_h%i(m)
3026                       j = surf_usm_h%j(m)
3027                       k = surf_usm_h%k(m)
3028                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_green_av(m)
3029                    ENDDO
3030                 ELSE
3031                    l = idsidx
3032                    DO  m = 1, surf_usm_v(l)%ns
3033                       i = surf_usm_v(l)%i(m)
3034                       j = surf_usm_v(l)%j(m)
3035                       k = surf_usm_v(l)%k(m)
3036                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_green_av(m)
3037                    ENDDO
3038                 ENDIF
3039              ENDIF
3040
3041          CASE ( 'usm_iwghf' )
3042!
3043!--           array of heat flux from indoor ground (land, wall, roof)
3044              IF ( av == 0 )  THEN
3045                 IF ( idsint == iup_u )  THEN
3046                    DO  m = 1, surf_usm_h%ns
3047                       i = surf_usm_h%i(m)
3048                       j = surf_usm_h%j(m)
3049                       k = surf_usm_h%k(m)
3050                       temp_pf(k,j,i) = surf_usm_h%iwghf_eb(m)
3051                    ENDDO
3052                 ELSE
3053                    l = idsidx
3054                    DO  m = 1, surf_usm_v(l)%ns
3055                       i = surf_usm_v(l)%i(m)
3056                       j = surf_usm_v(l)%j(m)
3057                       k = surf_usm_v(l)%k(m)
3058                       temp_pf(k,j,i) = surf_usm_v(l)%iwghf_eb(m)
3059                    ENDDO
3060                 ENDIF
3061              ELSE
3062                 IF ( idsint == iup_u )  THEN
3063                    DO  m = 1, surf_usm_h%ns
3064                       i = surf_usm_h%i(m)
3065                       j = surf_usm_h%j(m)
3066                       k = surf_usm_h%k(m)
3067                       temp_pf(k,j,i) = surf_usm_h%iwghf_eb_av(m)
3068                    ENDDO
3069                 ELSE
3070                    l = idsidx
3071                    DO  m = 1, surf_usm_v(l)%ns
3072                       i = surf_usm_v(l)%i(m)
3073                       j = surf_usm_v(l)%j(m)
3074                       k = surf_usm_v(l)%k(m)
3075                       temp_pf(k,j,i) = surf_usm_v(l)%iwghf_eb_av(m)
3076                    ENDDO
3077                 ENDIF
3078              ENDIF
3079
3080          CASE ( 'usm_iwghf_window' )
3081!
3082!--           array of heat flux from indoor window ground (land, wall, roof)
3083              IF ( av == 0 )  THEN
3084                 IF ( idsint == iup_u )  THEN
3085                    DO  m = 1, surf_usm_h%ns
3086                       i = surf_usm_h%i(m)
3087                       j = surf_usm_h%j(m)
3088                       k = surf_usm_h%k(m)
3089                       temp_pf(k,j,i) = surf_usm_h%iwghf_eb_window(m)
3090                    ENDDO
3091                 ELSE
3092                    l = idsidx
3093                    DO  m = 1, surf_usm_v(l)%ns
3094                       i = surf_usm_v(l)%i(m)
3095                       j = surf_usm_v(l)%j(m)
3096                       k = surf_usm_v(l)%k(m)
3097                       temp_pf(k,j,i) = surf_usm_v(l)%iwghf_eb_window(m)
3098                    ENDDO
3099                 ENDIF
3100              ELSE
3101                 IF ( idsint == iup_u )  THEN
3102                    DO  m = 1, surf_usm_h%ns
3103                       i = surf_usm_h%i(m)
3104                       j = surf_usm_h%j(m)
3105                       k = surf_usm_h%k(m)
3106                       temp_pf(k,j,i) = surf_usm_h%iwghf_eb_window_av(m)
3107                    ENDDO
3108                 ELSE
3109                    l = idsidx
3110                    DO  m = 1, surf_usm_v(l)%ns
3111                       i = surf_usm_v(l)%i(m)
3112                       j = surf_usm_v(l)%j(m)
3113                       k = surf_usm_v(l)%k(m)
3114                       temp_pf(k,j,i) = surf_usm_v(l)%iwghf_eb_window_av(m)
3115                    ENDDO
3116                 ENDIF
3117              ENDIF
3118             
3119          CASE ( 'usm_t_surf_wall' )
3120!
3121!--           surface temperature for surfaces
3122              IF ( av == 0 )  THEN
3123                 IF ( idsint == iup_u )  THEN
3124                    DO  m = 1, surf_usm_h%ns
3125                       i = surf_usm_h%i(m)
3126                       j = surf_usm_h%j(m)
3127                       k = surf_usm_h%k(m)
3128                       temp_pf(k,j,i) = t_surf_wall_h(m)
3129                    ENDDO
3130                 ELSE
3131                    l = idsidx
3132                    DO  m = 1, surf_usm_v(l)%ns
3133                       i = surf_usm_v(l)%i(m)
3134                       j = surf_usm_v(l)%j(m)
3135                       k = surf_usm_v(l)%k(m)
3136                       temp_pf(k,j,i) = t_surf_wall_v(l)%t(m)
3137                    ENDDO
3138                 ENDIF
3139              ELSE
3140                 IF ( idsint == iup_u )  THEN
3141                    DO  m = 1, surf_usm_h%ns
3142                       i = surf_usm_h%i(m)
3143                       j = surf_usm_h%j(m)
3144                       k = surf_usm_h%k(m)
3145                       temp_pf(k,j,i) = surf_usm_h%t_surf_wall_av(m)
3146                    ENDDO
3147                 ELSE
3148                    l = idsidx
3149                    DO  m = 1, surf_usm_v(l)%ns
3150                       i = surf_usm_v(l)%i(m)
3151                       j = surf_usm_v(l)%j(m)
3152                       k = surf_usm_v(l)%k(m)
3153                       temp_pf(k,j,i) = surf_usm_v(l)%t_surf_wall_av(m)
3154                    ENDDO
3155                 ENDIF
3156              ENDIF
3157             
3158          CASE ( 'usm_t_surf_window' )
3159!
3160!--           surface temperature for window surfaces
3161              IF ( av == 0 )  THEN
3162                 IF ( idsint == iup_u )  THEN
3163                    DO  m = 1, surf_usm_h%ns
3164                       i = surf_usm_h%i(m)
3165                       j = surf_usm_h%j(m)
3166                       k = surf_usm_h%k(m)
3167                       temp_pf(k,j,i) = t_surf_window_h(m)
3168                    ENDDO
3169                 ELSE
3170                    l = idsidx
3171                    DO  m = 1, surf_usm_v(l)%ns
3172                       i = surf_usm_v(l)%i(m)
3173                       j = surf_usm_v(l)%j(m)
3174                       k = surf_usm_v(l)%k(m)
3175                       temp_pf(k,j,i) = t_surf_window_v(l)%t(m)
3176                    ENDDO
3177                 ENDIF
3178
3179              ELSE
3180                 IF ( idsint == iup_u )  THEN
3181                    DO  m = 1, surf_usm_h%ns
3182                       i = surf_usm_h%i(m)
3183                       j = surf_usm_h%j(m)
3184                       k = surf_usm_h%k(m)
3185                       temp_pf(k,j,i) = surf_usm_h%t_surf_window_av(m)
3186                    ENDDO
3187                 ELSE
3188                    l = idsidx
3189                    DO  m = 1, surf_usm_v(l)%ns
3190                       i = surf_usm_v(l)%i(m)
3191                       j = surf_usm_v(l)%j(m)
3192                       k = surf_usm_v(l)%k(m)
3193                       temp_pf(k,j,i) = surf_usm_v(l)%t_surf_window_av(m)
3194                    ENDDO
3195
3196                 ENDIF
3197
3198              ENDIF
3199
3200          CASE ( 'usm_t_surf_green' )
3201!
3202!--           surface temperature for green surfaces
3203              IF ( av == 0 )  THEN
3204                 IF ( idsint == iup_u )  THEN
3205                    DO  m = 1, surf_usm_h%ns
3206                       i = surf_usm_h%i(m)
3207                       j = surf_usm_h%j(m)
3208                       k = surf_usm_h%k(m)
3209                       temp_pf(k,j,i) = t_surf_green_h(m)
3210                    ENDDO
3211                 ELSE
3212                    l = idsidx
3213                    DO  m = 1, surf_usm_v(l)%ns
3214                       i = surf_usm_v(l)%i(m)
3215                       j = surf_usm_v(l)%j(m)
3216                       k = surf_usm_v(l)%k(m)
3217                       temp_pf(k,j,i) = t_surf_green_v(l)%t(m)
3218                    ENDDO
3219                 ENDIF
3220
3221              ELSE
3222                 IF ( idsint == iup_u )  THEN
3223                    DO  m = 1, surf_usm_h%ns
3224                       i = surf_usm_h%i(m)
3225                       j = surf_usm_h%j(m)
3226                       k = surf_usm_h%k(m)
3227                       temp_pf(k,j,i) = surf_usm_h%t_surf_green_av(m)
3228                    ENDDO
3229                 ELSE
3230                    l = idsidx
3231                    DO  m = 1, surf_usm_v(l)%ns
3232                       i = surf_usm_v(l)%i(m)
3233                       j = surf_usm_v(l)%j(m)
3234                       k = surf_usm_v(l)%k(m)
3235                       temp_pf(k,j,i) = surf_usm_v(l)%t_surf_green_av(m)
3236                    ENDDO
3237
3238                 ENDIF
3239
3240              ENDIF
3241
3242          CASE ( 'usm_theta_10cm' )
3243!
3244!--           near surface temperature for whole surfaces
3245              IF ( av == 0 )  THEN
3246                 IF ( idsint == iup_u )  THEN
3247                    DO  m = 1, surf_usm_h%ns
3248                       i = surf_usm_h%i(m)
3249                       j = surf_usm_h%j(m)
3250                       k = surf_usm_h%k(m)
3251                       temp_pf(k,j,i) = surf_usm_h%pt_10cm(m)
3252                    ENDDO
3253                 ELSE
3254                    l = idsidx
3255                    DO  m = 1, surf_usm_v(l)%ns
3256                       i = surf_usm_v(l)%i(m)
3257                       j = surf_usm_v(l)%j(m)
3258                       k = surf_usm_v(l)%k(m)
3259                       temp_pf(k,j,i) = surf_usm_v(l)%pt_10cm(m)
3260                    ENDDO
3261                 ENDIF
3262             
3263             
3264              ELSE
3265                 IF ( idsint == iup_u )  THEN
3266                    DO  m = 1, surf_usm_h%ns
3267                       i = surf_usm_h%i(m)
3268                       j = surf_usm_h%j(m)
3269                       k = surf_usm_h%k(m)
3270                       temp_pf(k,j,i) = surf_usm_h%pt_10cm_av(m)
3271                    ENDDO
3272                 ELSE
3273                    l = idsidx
3274                    DO  m = 1, surf_usm_v(l)%ns
3275                       i = surf_usm_v(l)%i(m)
3276                       j = surf_usm_v(l)%j(m)
3277                       k = surf_usm_v(l)%k(m)
3278                       temp_pf(k,j,i) = surf_usm_v(l)%pt_10cm_av(m)
3279                    ENDDO
3280
3281                  ENDIF
3282              ENDIF
3283             
3284          CASE ( 'usm_t_wall' )
3285!
3286!--           wall temperature for  iwl layer of walls and land
3287              IF ( av == 0 )  THEN
3288                 IF ( idsint == iup_u )  THEN
3289                    DO  m = 1, surf_usm_h%ns
3290                       i = surf_usm_h%i(m)
3291                       j = surf_usm_h%j(m)
3292                       k = surf_usm_h%k(m)
3293                       temp_pf(k,j,i) = t_wall_h(iwl,m)
3294                    ENDDO
3295                 ELSE
3296                    l = idsidx
3297                    DO  m = 1, surf_usm_v(l)%ns
3298                       i = surf_usm_v(l)%i(m)
3299                       j = surf_usm_v(l)%j(m)
3300                       k = surf_usm_v(l)%k(m)
3301                       temp_pf(k,j,i) = t_wall_v(l)%t(iwl,m)
3302                    ENDDO
3303                 ENDIF
3304              ELSE
3305                 IF ( idsint == iup_u )  THEN
3306                    DO  m = 1, surf_usm_h%ns
3307                       i = surf_usm_h%i(m)
3308                       j = surf_usm_h%j(m)
3309                       k = surf_usm_h%k(m)
3310                       temp_pf(k,j,i) = surf_usm_h%t_wall_av(iwl,m)
3311                    ENDDO
3312                 ELSE
3313                    l = idsidx
3314                    DO  m = 1, surf_usm_v(l)%ns
3315                       i = surf_usm_v(l)%i(m)
3316                       j = surf_usm_v(l)%j(m)
3317                       k = surf_usm_v(l)%k(m)
3318                       temp_pf(k,j,i) = surf_usm_v(l)%t_wall_av(iwl,m)
3319                    ENDDO
3320                 ENDIF
3321              ENDIF
3322             
3323          CASE ( 'usm_t_window' )
3324!
3325!--           window temperature for iwl layer of walls and land
3326              IF ( av == 0 )  THEN
3327                 IF ( idsint == iup_u )  THEN
3328                    DO  m = 1, surf_usm_h%ns
3329                       i = surf_usm_h%i(m)
3330                       j = surf_usm_h%j(m)
3331                       k = surf_usm_h%k(m)
3332                       temp_pf(k,j,i) = t_window_h(iwl,m)
3333                    ENDDO
3334                 ELSE
3335                    l = idsidx
3336                    DO  m = 1, surf_usm_v(l)%ns
3337                       i = surf_usm_v(l)%i(m)
3338                       j = surf_usm_v(l)%j(m)
3339                       k = surf_usm_v(l)%k(m)
3340                       temp_pf(k,j,i) = t_window_v(l)%t(iwl,m)
3341                    ENDDO
3342                 ENDIF
3343              ELSE
3344                 IF ( idsint == iup_u )  THEN
3345                    DO  m = 1, surf_usm_h%ns
3346                       i = surf_usm_h%i(m)
3347                       j = surf_usm_h%j(m)
3348                       k = surf_usm_h%k(m)
3349                       temp_pf(k,j,i) = surf_usm_h%t_window_av(iwl,m)
3350                    ENDDO
3351                 ELSE
3352                    l = idsidx
3353                    DO  m = 1, surf_usm_v(l)%ns
3354                       i = surf_usm_v(l)%i(m)
3355                       j = surf_usm_v(l)%j(m)
3356                       k = surf_usm_v(l)%k(m)
3357                       temp_pf(k,j,i) = surf_usm_v(l)%t_window_av(iwl,m)
3358                    ENDDO
3359                 ENDIF
3360              ENDIF
3361
3362          CASE ( 'usm_t_green' )
3363!
3364!--           green temperature for  iwl layer of walls and land
3365              IF ( av == 0 )  THEN
3366                 IF ( idsint == iup_u )  THEN
3367                    DO  m = 1, surf_usm_h%ns
3368                       i = surf_usm_h%i(m)
3369                       j = surf_usm_h%j(m)
3370                       k = surf_usm_h%k(m)
3371                       temp_pf(k,j,i) = t_green_h(iwl,m)
3372                    ENDDO
3373                 ELSE
3374                    l = idsidx
3375                    DO  m = 1, surf_usm_v(l)%ns
3376                       i = surf_usm_v(l)%i(m)
3377                       j = surf_usm_v(l)%j(m)
3378                       k = surf_usm_v(l)%k(m)
3379                       temp_pf(k,j,i) = t_green_v(l)%t(iwl,m)
3380                    ENDDO
3381                 ENDIF
3382              ELSE
3383                 IF ( idsint == iup_u )  THEN
3384                    DO  m = 1, surf_usm_h%ns
3385                       i = surf_usm_h%i(m)
3386                       j = surf_usm_h%j(m)
3387                       k = surf_usm_h%k(m)
3388                       temp_pf(k,j,i) = surf_usm_h%t_green_av(iwl,m)
3389                    ENDDO
3390                 ELSE
3391                    l = idsidx
3392                    DO  m = 1, surf_usm_v(l)%ns
3393                       i = surf_usm_v(l)%i(m)
3394                       j = surf_usm_v(l)%j(m)
3395                       k = surf_usm_v(l)%k(m)
3396                       temp_pf(k,j,i) = surf_usm_v(l)%t_green_av(iwl,m)
3397                    ENDDO
3398                 ENDIF
3399              ENDIF
3400             
3401              CASE ( 'usm_swc' )
3402!
3403!--           soil water content for  iwl layer of walls and land
3404              IF ( av == 0 )  THEN
3405                 IF ( idsint == iup_u )  THEN
3406                    DO  m = 1, surf_usm_h%ns
3407                       i = surf_usm_h%i(m)
3408                       j = surf_usm_h%j(m)
3409                       k = surf_usm_h%k(m)
3410                       temp_pf(k,j,i) = swc_h(iwl,m)
3411                    ENDDO
3412                 ELSE
3413                    l = idsidx
3414                    DO  m = 1, surf_usm_v(l)%ns
3415                       i = surf_usm_v(l)%i(m)
3416                       j = surf_usm_v(l)%j(m)
3417                       k = surf_usm_v(l)%k(m)
3418                       temp_pf(k,j,i) = swc_v(l)%t(iwl,m)
3419                    ENDDO
3420                 ENDIF
3421              ELSE
3422                 IF ( idsint == iup_u )  THEN
3423                    DO  m = 1, surf_usm_h%ns
3424                       i = surf_usm_h%i(m)
3425                       j = surf_usm_h%j(m)
3426                       k = surf_usm_h%k(m)
3427                       temp_pf(k,j,i) = surf_usm_h%swc_av(iwl,m)
3428                    ENDDO
3429                 ELSE
3430                    l = idsidx
3431                    DO  m = 1, surf_usm_v(l)%ns
3432                       i = surf_usm_v(l)%i(m)
3433                       j = surf_usm_v(l)%j(m)
3434                       k = surf_usm_v(l)%k(m)
3435                       temp_pf(k,j,i) = surf_usm_v(l)%swc_av(iwl,m)
3436                    ENDDO
3437                 ENDIF
3438              ENDIF
3439
3440             
3441          CASE DEFAULT
3442              found = .FALSE.
3443              RETURN
3444        END SELECT
3445
3446!
3447!--     Rearrange dimensions for NetCDF output
3448!--     FIXME: this may generate FPE overflow upon conversion from DP to SP
3449        DO  j = nys, nyn
3450            DO  i = nxl, nxr
3451                DO  k = nzb_do, nzt_do
3452                    local_pf(i,j,k) = temp_pf(k,j,i)
3453                ENDDO
3454            ENDDO
3455        ENDDO
3456       
3457    END SUBROUTINE usm_data_output_3d
3458   
3459
3460!------------------------------------------------------------------------------!
3461!
3462! Description:
3463! ------------
3464!> Soubroutine defines appropriate grid for netcdf variables.
3465!> It is called out from subroutine netcdf.
3466!------------------------------------------------------------------------------!
3467    SUBROUTINE usm_define_netcdf_grid( variable, found, grid_x, grid_y, grid_z )
3468   
3469        IMPLICIT NONE
3470
3471        CHARACTER (len=*), INTENT(IN)  ::  variable    !<
3472        LOGICAL, INTENT(OUT)           ::  found       !<
3473        CHARACTER (len=*), INTENT(OUT) ::  grid_x      !<
3474        CHARACTER (len=*), INTENT(OUT) ::  grid_y      !<
3475        CHARACTER (len=*), INTENT(OUT) ::  grid_z      !<
3476
3477        CHARACTER (len=varnamelength)  :: var
3478
3479        var = TRIM(variable)
3480        IF ( var(1:9) == 'usm_wshf_'  .OR.  var(1:9) == 'usm_wghf_'  .OR.                   &
3481             var(1:16) == 'usm_wghf_window_'  .OR. var(1:15) == 'usm_wghf_green_' .OR.      &
3482             var(1:10) == 'usm_iwghf_'  .OR. var(1:17) == 'usm_iwghf_window_' .OR.          &
3483             var(1:9) == 'usm_qsws_'  .OR.  var(1:13) == 'usm_qsws_veg_'  .OR.              &
3484             var(1:13) == 'usm_qsws_liq_' .OR.                                              &
3485             var(1:15) == 'usm_t_surf_wall'  .OR.  var(1:10) == 'usm_t_wall'  .OR.          &
3486             var(1:17) == 'usm_t_surf_window'  .OR.  var(1:12) == 'usm_t_window'  .OR.      &
3487             var(1:16) == 'usm_t_surf_green'  .OR. var(1:11) == 'usm_t_green' .OR.          &
3488             var(1:15) == 'usm_theta_10cm' .OR.                                             &
3489             var(1:9) == 'usm_surfz'  .OR.  var(1:11) == 'usm_surfcat'  .OR.                &
3490             var(1:16) == 'usm_surfwintrans'  .OR. var(1:7) == 'usm_swc' ) THEN
3491
3492            found = .TRUE.
3493            grid_x = 'x'
3494            grid_y = 'y'
3495            grid_z = 'zu'
3496        ELSE
3497            found  = .FALSE.
3498            grid_x = 'none'
3499            grid_y = 'none'
3500            grid_z = 'none'
3501        ENDIF
3502
3503    END SUBROUTINE usm_define_netcdf_grid
3504   
3505
3506!------------------------------------------------------------------------------!
3507! Description:
3508! ------------
3509!> Initialization of the wall surface model
3510!------------------------------------------------------------------------------!
3511    SUBROUTINE usm_init_material_model
3512
3513        IMPLICIT NONE
3514
3515        INTEGER(iwp) ::  k, l, m            !< running indices
3516       
3517        IF ( debug_output )  CALL debug_message( 'usm_init_material_model', 'start' )
3518
3519!
3520!--     Calculate wall grid spacings.
3521!--     Temperature is defined at the center of the wall layers,
3522!--     whereas gradients/fluxes are defined at the edges (_stag)     
3523!--     apply for all particular surface grids. First for horizontal surfaces
3524        DO  m = 1, surf_usm_h%ns
3525
3526           surf_usm_h%dz_wall(nzb_wall,m) = surf_usm_h%zw(nzb_wall,m)
3527           DO k = nzb_wall+1, nzt_wall
3528               surf_usm_h%dz_wall(k,m) = surf_usm_h%zw(k,m) -                  &
3529                                         surf_usm_h%zw(k-1,m)
3530           ENDDO
3531           surf_usm_h%dz_window(nzb_wall,m) = surf_usm_h%zw_window(nzb_wall,m)
3532           DO k = nzb_wall+1, nzt_wall
3533               surf_usm_h%dz_window(k,m) = surf_usm_h%zw_window(k,m) -         &
3534                                         surf_usm_h%zw_window(k-1,m)
3535           ENDDO
3536           
3537           surf_usm_h%dz_wall(nzt_wall+1,m) = surf_usm_h%dz_wall(nzt_wall,m)
3538
3539           DO k = nzb_wall, nzt_wall-1
3540               surf_usm_h%dz_wall_stag(k,m) = 0.5 * (                          &
3541                           surf_usm_h%dz_wall(k+1,m) + surf_usm_h%dz_wall(k,m) )
3542           ENDDO
3543           surf_usm_h%dz_wall_stag(nzt_wall,m) = surf_usm_h%dz_wall(nzt_wall,m)
3544           
3545           surf_usm_h%dz_window(nzt_wall+1,m) = surf_usm_h%dz_window(nzt_wall,m)
3546
3547           DO k = nzb_wall, nzt_wall-1
3548               surf_usm_h%dz_window_stag(k,m) = 0.5 * (                        &
3549                           surf_usm_h%dz_window(k+1,m) + surf_usm_h%dz_window(k,m) )
3550           ENDDO
3551           surf_usm_h%dz_window_stag(nzt_wall,m) = surf_usm_h%dz_window(nzt_wall,m)
3552
3553           IF (surf_usm_h%green_type_roof(m) == 2.0_wp ) THEN
3554!
3555!-- extensive green roof
3556!-- set ratio of substrate layer thickness, soil-type and LAI
3557              soil_type = 3
3558              surf_usm_h%lai(m) = 2.0_wp
3559             
3560              surf_usm_h%zw_green(nzb_wall,m)   = 0.05_wp
3561              surf_usm_h%zw_green(nzb_wall+1,m) = 0.10_wp
3562              surf_usm_h%zw_green(nzb_wall+2,m) = 0.15_wp
3563              surf_usm_h%zw_green(nzb_wall+3,m) = 0.20_wp
3564           ELSE
3565!
3566!-- intensiv green roof
3567!-- set ratio of substrate layer thickness, soil-type and LAI
3568              soil_type = 6
3569              surf_usm_h%lai(m) = 4.0_wp
3570             
3571              surf_usm_h%zw_green(nzb_wall,m)   = 0.05_wp
3572              surf_usm_h%zw_green(nzb_wall+1,m) = 0.10_wp
3573              surf_usm_h%zw_green(nzb_wall+2,m) = 0.40_wp
3574              surf_usm_h%zw_green(nzb_wall+3,m) = 0.80_wp
3575           ENDIF
3576           
3577           surf_usm_h%dz_green(nzb_wall,m) = surf_usm_h%zw_green(nzb_wall,m)
3578           DO k = nzb_wall+1, nzt_wall
3579               surf_usm_h%dz_green(k,m) = surf_usm_h%zw_green(k,m) -           &
3580                                         surf_usm_h%zw_green(k-1,m)
3581           ENDDO
3582           surf_usm_h%dz_green(nzt_wall+1,m) = surf_usm_h%dz_green(nzt_wall,m)
3583
3584           DO k = nzb_wall, nzt_wall-1
3585               surf_usm_h%dz_green_stag(k,m) = 0.5 * (                         &
3586                           surf_usm_h%dz_green(k+1,m) + surf_usm_h%dz_green(k,m) )
3587           ENDDO
3588           surf_usm_h%dz_green_stag(nzt_wall,m) = surf_usm_h%dz_green(nzt_wall,m)
3589           
3590          IF ( alpha_vangenuchten == 9999999.9_wp )  THEN
3591             alpha_vangenuchten = soil_pars(0,soil_type)
3592          ENDIF
3593
3594          IF ( l_vangenuchten == 9999999.9_wp )  THEN
3595             l_vangenuchten = soil_pars(1,soil_type)
3596          ENDIF
3597
3598          IF ( n_vangenuchten == 9999999.9_wp )  THEN
3599             n_vangenuchten = soil_pars(2,soil_type)           
3600          ENDIF
3601
3602          IF ( hydraulic_conductivity == 9999999.9_wp )  THEN
3603             hydraulic_conductivity = soil_pars(3,soil_type)           
3604          ENDIF
3605
3606          IF ( saturation_moisture == 9999999.9_wp )  THEN
3607             saturation_moisture = m_soil_pars(0,soil_type)           
3608          ENDIF
3609
3610          IF ( field_capacity == 9999999.9_wp )  THEN
3611             field_capacity = m_soil_pars(1,soil_type)           
3612          ENDIF
3613
3614          IF ( wilting_point == 9999999.9_wp )  THEN
3615             wilting_point = m_soil_pars(2,soil_type)           
3616          ENDIF
3617
3618          IF ( residual_moisture == 9999999.9_wp )  THEN
3619             residual_moisture = m_soil_pars(3,soil_type)       
3620          ENDIF
3621         
3622          DO k = nzb_wall, nzt_wall+1
3623             swc_h(k,m) = field_capacity
3624             rootfr_h(k,m) = 0.5_wp
3625             surf_usm_h%alpha_vg_green(m)      = alpha_vangenuchten
3626             surf_usm_h%l_vg_green(m)          = l_vangenuchten
3627             surf_usm_h%n_vg_green(m)          = n_vangenuchten 
3628             surf_usm_h%gamma_w_green_sat(k,m) = hydraulic_conductivity
3629             swc_sat_h(k,m)                    = saturation_moisture
3630             fc_h(k,m)                         = field_capacity
3631             wilt_h(k,m)                       = wilting_point
3632             swc_res_h(k,m)                    = residual_moisture
3633          ENDDO
3634
3635        ENDDO
3636
3637        surf_usm_h%ddz_wall        = 1.0_wp / surf_usm_h%dz_wall
3638        surf_usm_h%ddz_wall_stag   = 1.0_wp / surf_usm_h%dz_wall_stag
3639        surf_usm_h%ddz_window      = 1.0_wp / surf_usm_h%dz_window
3640        surf_usm_h%ddz_window_stag = 1.0_wp / surf_usm_h%dz_window_stag
3641        surf_usm_h%ddz_green       = 1.0_wp / surf_usm_h%dz_green
3642        surf_usm_h%ddz_green_stag  = 1.0_wp / surf_usm_h%dz_green_stag
3643!       
3644!--     For vertical surfaces
3645        DO  l = 0, 3
3646           DO  m = 1, surf_usm_v(l)%ns
3647              surf_usm_v(l)%dz_wall(nzb_wall,m) = surf_usm_v(l)%zw(nzb_wall,m)
3648              DO k = nzb_wall+1, nzt_wall
3649                  surf_usm_v(l)%dz_wall(k,m) = surf_usm_v(l)%zw(k,m) -         &
3650                                               surf_usm_v(l)%zw(k-1,m)
3651              ENDDO
3652              surf_usm_v(l)%dz_window(nzb_wall,m) = surf_usm_v(l)%zw_window(nzb_wall,m)
3653              DO k = nzb_wall+1, nzt_wall
3654                  surf_usm_v(l)%dz_window(k,m) = surf_usm_v(l)%zw_window(k,m) - &
3655                                               surf_usm_v(l)%zw_window(k-1,m)
3656              ENDDO
3657              surf_usm_v(l)%dz_green(nzb_wall,m) = surf_usm_v(l)%zw_green(nzb_wall,m)
3658              DO k = nzb_wall+1, nzt_wall
3659                  surf_usm_v(l)%dz_green(k,m) = surf_usm_v(l)%zw_green(k,m) - &
3660                                               surf_usm_v(l)%zw_green(k-1,m)
3661              ENDDO
3662           
3663              surf_usm_v(l)%dz_wall(nzt_wall+1,m) =                            &
3664                                              surf_usm_v(l)%dz_wall(nzt_wall,m)
3665
3666              DO k = nzb_wall, nzt_wall-1
3667                  surf_usm_v(l)%dz_wall_stag(k,m) = 0.5 * (                    &
3668                                                surf_usm_v(l)%dz_wall(k+1,m) + &
3669                                                surf_usm_v(l)%dz_wall(k,m) )
3670              ENDDO
3671              surf_usm_v(l)%dz_wall_stag(nzt_wall,m) =                         &
3672                                              surf_usm_v(l)%dz_wall(nzt_wall,m)
3673              surf_usm_v(l)%dz_window(nzt_wall+1,m) =                          &
3674                                              surf_usm_v(l)%dz_window(nzt_wall,m)
3675
3676              DO k = nzb_wall, nzt_wall-1
3677                  surf_usm_v(l)%dz_window_stag(k,m) = 0.5 * (                    &
3678                                                surf_usm_v(l)%dz_window(k+1,m) + &
3679                                                surf_usm_v(l)%dz_window(k,m) )
3680              ENDDO
3681              surf_usm_v(l)%dz_window_stag(nzt_wall,m) =                         &
3682                                              surf_usm_v(l)%dz_window(nzt_wall,m)
3683              surf_usm_v(l)%dz_green(nzt_wall+1,m) =                             &
3684                                              surf_usm_v(l)%dz_green(nzt_wall,m)
3685
3686              DO k = nzb_wall, nzt_wall-1
3687                  surf_usm_v(l)%dz_green_stag(k,m) = 0.5 * (                    &
3688                                                surf_usm_v(l)%dz_green(k+1,m) + &
3689                                                surf_usm_v(l)%dz_green(k,m) )
3690              ENDDO
3691              surf_usm_v(l)%dz_green_stag(nzt_wall,m) =                         &
3692                                              surf_usm_v(l)%dz_green(nzt_wall,m)
3693           ENDDO
3694           surf_usm_v(l)%ddz_wall        = 1.0_wp / surf_usm_v(l)%dz_wall
3695           surf_usm_v(l)%ddz_wall_stag   = 1.0_wp / surf_usm_v(l)%dz_wall_stag
3696           surf_usm_v(l)%ddz_window      = 1.0_wp / surf_usm_v(l)%dz_window
3697           surf_usm_v(l)%ddz_window_stag = 1.0_wp / surf_usm_v(l)%dz_window_stag
3698           surf_usm_v(l)%ddz_green       = 1.0_wp / surf_usm_v(l)%dz_green
3699           surf_usm_v(l)%ddz_green_stag  = 1.0_wp / surf_usm_v(l)%dz_green_stag
3700        ENDDO     
3701
3702       
3703        IF ( debug_output )  CALL debug_message( 'usm_init_material_model', 'end' )
3704
3705    END SUBROUTINE usm_init_material_model
3706
3707 
3708!------------------------------------------------------------------------------!
3709! Description:
3710! ------------
3711!> Initialization of the urban surface model
3712!------------------------------------------------------------------------------!
3713    SUBROUTINE usm_init
3714
3715        USE arrays_3d,                                                         &
3716            ONLY:  zw
3717
3718        USE netcdf_data_input_mod,                                             &
3719            ONLY:  building_pars_f, building_type_f, terrain_height_f
3720   
3721        IMPLICIT NONE
3722
3723        INTEGER(iwp) ::  i                   !< loop index x-dirction
3724        INTEGER(iwp) ::  ind_alb_green       !< index in input list for green albedo
3725        INTEGER(iwp) ::  ind_alb_wall        !< index in input list for wall albedo
3726        INTEGER(iwp) ::  ind_alb_win         !< index in input list for window albedo
3727        INTEGER(iwp) ::  ind_emis_wall       !< index in input list for wall emissivity
3728        INTEGER(iwp) ::  ind_emis_green      !< index in input list for green emissivity
3729        INTEGER(iwp) ::  ind_emis_win        !< index in input list for window emissivity
3730        INTEGER(iwp) ::  ind_green_frac_w    !< index in input list for green fraction on wall
3731        INTEGER(iwp) ::  ind_green_frac_r    !< index in input list for green fraction on roof
3732        INTEGER(iwp) ::  ind_hc1             !< index in input list for heat capacity at first wall layer
3733        INTEGER(iwp) ::  ind_hc1_win         !< index in input list for heat capacity at first window layer
3734        INTEGER(iwp) ::  ind_hc2             !< index in input list for heat capacity at second wall layer
3735        INTEGER(iwp) ::  ind_hc2_win         !< index in input list for heat capacity at second window layer
3736        INTEGER(iwp) ::  ind_hc3             !< index in input list for heat capacity at third wall layer
3737        INTEGER(iwp) ::  ind_hc3_win         !< index in input list for heat capacity at third window layer
3738        INTEGER(iwp) ::  ind_lai_r           !< index in input list for LAI on roof
3739        INTEGER(iwp) ::  ind_lai_w           !< index in input list for LAI on wall
3740        INTEGER(iwp) ::  ind_tc1             !< index in input list for thermal conductivity at first wall layer
3741        INTEGER(iwp) ::  ind_tc1_win         !< index in input list for thermal conductivity at first window layer
3742        INTEGER(iwp) ::  ind_tc2             !< index in input list for thermal conductivity at second wall layer
3743        INTEGER(iwp) ::  ind_tc2_win         !< index in input list for thermal conductivity at second window layer
3744        INTEGER(iwp) ::  ind_tc3             !< index in input list for thermal conductivity at third wall layer
3745        INTEGER(iwp) ::  ind_tc3_win         !< index in input list for thermal conductivity at third window layer
3746        INTEGER(iwp) ::  ind_thick_1         !< index in input list for thickness of first wall layer
3747        INTEGER(iwp) ::  ind_thick_1_win     !< index in input list for thickness of first window layer
3748        INTEGER(iwp) ::  ind_thick_2         !< index in input list for thickness of second wall layer
3749        INTEGER(iwp) ::  ind_thick_2_win     !< index in input list for thickness of second window layer
3750        INTEGER(iwp) ::  ind_thick_3         !< index in input list for thickness of third wall layer
3751        INTEGER(iwp) ::  ind_thick_3_win     !< index in input list for thickness of third window layer
3752        INTEGER(iwp) ::  ind_thick_4         !< index in input list for thickness of fourth wall layer
3753        INTEGER(iwp) ::  ind_thick_4_win     !< index in input list for thickness of fourth window layer
3754        INTEGER(iwp) ::  ind_trans           !< index in input list for window transmissivity
3755        INTEGER(iwp) ::  ind_wall_frac       !< index in input list for wall fraction
3756        INTEGER(iwp) ::  ind_win_frac        !< index in input list for window fraction
3757        INTEGER(iwp) ::  ind_z0              !< index in input list for z0
3758        INTEGER(iwp) ::  ind_z0qh            !< index in input list for z0h / z0q
3759        INTEGER(iwp) ::  j                   !< loop index y-dirction
3760        INTEGER(iwp) ::  k                   !< loop index z-dirction
3761        INTEGER(iwp) ::  l                   !< loop index surface orientation
3762        INTEGER(iwp) ::  m                   !< loop index surface element
3763        INTEGER(iwp) ::  st                  !< dummy 
3764
3765        REAL(wp)     ::  c, tin, twin
3766        REAL(wp)     ::  ground_floor_level_l         !< local height of ground floor level
3767        REAL(wp)     ::  z_agl                        !< height above ground
3768
3769        IF ( debug_output )  CALL debug_message( 'usm_init', 'start' )
3770
3771        CALL cpu_log( log_point_s(78), 'usm_init', 'start' )
3772!
3773!--     Initialize building-surface properties
3774        CALL usm_define_pars
3775!
3776!--     surface forcing have to be disabled for LSF
3777!--     in case of enabled urban surface module
3778        IF ( large_scale_forcing )  THEN
3779            lsf_surf = .FALSE.
3780        ENDIF
3781!
3782!--     Flag surface elements belonging to the ground floor level. Therefore,
3783!--     use terrain height array from file, if available. This flag is later used
3784!--     to control initialization of surface attributes.
3785!--     Todo: for the moment disable initialization of building roofs with
3786!--     ground-floor-level properties.
3787        surf_usm_h%ground_level = .FALSE. 
3788
3789        DO  l = 0, 3
3790           surf_usm_v(l)%ground_level = .FALSE.
3791           DO  m = 1, surf_usm_v(l)%ns
3792              i = surf_usm_v(l)%i(m) + surf_usm_v(l)%ioff
3793              j = surf_usm_v(l)%j(m) + surf_usm_v(l)%joff
3794              k = surf_usm_v(l)%k(m)
3795!
3796!--           Determine local ground level. Level 1 - default value,
3797!--           level 2 - initialization according to building type,
3798!--           level 3 - initialization from value read from file.
3799              ground_floor_level_l = ground_floor_level
3800             
3801              IF ( building_type_f%from_file )  THEN
3802                  ground_floor_level_l =                                       &
3803                              building_pars(ind_gflh,building_type_f%var(j,i))
3804              ENDIF
3805             
3806              IF ( building_pars_f%from_file )  THEN
3807                 IF ( building_pars_f%pars_xy(ind_gflh,j,i) /=                 &
3808                      building_pars_f%fill )                                   &
3809                    ground_floor_level_l = building_pars_f%pars_xy(ind_gflh,j,i)
3810              ENDIF
3811!
3812!--           Determine height of surface element above ground level. Please
3813!--           note, height of surface element is determined with respect to
3814!--           its height above ground of the reference grid point in atmosphere,
3815!--           Therefore, substract the offset values when assessing the terrain
3816!--           height.
3817              IF ( terrain_height_f%from_file )  THEN
3818                 z_agl = zw(k) - terrain_height_f%var(j-surf_usm_v(l)%joff,    &
3819                                                      i-surf_usm_v(l)%ioff)
3820              ELSE
3821                 z_agl = zw(k)
3822              ENDIF
3823!
3824!--           Set flag for ground level
3825              IF ( z_agl <= ground_floor_level_l )                             &
3826                 surf_usm_v(l)%ground_level(m) = .TRUE.
3827
3828           ENDDO
3829        ENDDO
3830!
3831!--     Initialization of resistances.
3832        DO  m = 1, surf_usm_h%ns
3833           surf_usm_h%r_a(m)        = 50.0_wp
3834           surf_usm_h%r_a_green(m)  = 50.0_wp
3835           surf_usm_h%r_a_window(m) = 50.0_wp
3836        ENDDO
3837        DO  l = 0, 3
3838           DO  m = 1, surf_usm_v(l)%ns
3839              surf_usm_v(l)%r_a(m)        = 50.0_wp
3840              surf_usm_v(l)%r_a_green(m)  = 50.0_wp
3841              surf_usm_v(l)%r_a_window(m) = 50.0_wp
3842           ENDDO
3843        ENDDO
3844       
3845!
3846!--    Map values onto horizontal elemements
3847       DO  m = 1, surf_usm_h%ns
3848             surf_usm_h%r_canopy_min(m)     = 200.0_wp !< min_canopy_resistance
3849             surf_usm_h%g_d(m)              = 0.0_wp   !< canopy_resistance_coefficient
3850       ENDDO
3851!
3852!--    Map values onto vertical elements, even though this does not make
3853!--    much sense.
3854       DO  l = 0, 3
3855          DO  m = 1, surf_usm_v(l)%ns
3856                surf_usm_v(l)%r_canopy_min(m)     = 200.0_wp !< min_canopy_resistance
3857                surf_usm_v(l)%g_d(m)              = 0.0_wp   !< canopy_resistance_coefficient
3858          ENDDO
3859       ENDDO
3860
3861!
3862!--     Initialize urban-type surface attribute. According to initialization in
3863!--     land-surface model, follow a 3-level approach.
3864!--     Level 1 - initialization via default attributes
3865        DO  m = 1, surf_usm_h%ns
3866!
3867!--        Now, all horizontal surfaces are roof surfaces (?)
3868           surf_usm_h%isroof_surf(m)   = .TRUE.
3869           surf_usm_h%surface_types(m) = roof_category         !< default category for root surface
3870!
3871!--        In order to distinguish between ground floor level and
3872!--        above-ground-floor level surfaces, set input indices.
3873
3874           ind_green_frac_r = MERGE( ind_green_frac_r_gfl, ind_green_frac_r_agfl, &
3875                                     surf_usm_h%ground_level(m) )
3876           ind_lai_r        = MERGE( ind_lai_r_gfl,        ind_lai_r_agfl,        &
3877                                     surf_usm_h%ground_level(m) )
3878           ind_z0           = MERGE( ind_z0_gfl,           ind_z0_agfl,           &
3879                                     surf_usm_h%ground_level(m) )
3880           ind_z0qh         = MERGE( ind_z0qh_gfl,         ind_z0qh_agfl,         &
3881                                     surf_usm_h%ground_level(m) )
3882!
3883!--        Store building type and its name on each surface element
3884           surf_usm_h%building_type(m)      = building_type
3885           surf_usm_h%building_type_name(m) = building_type_name(building_type)
3886!
3887!--        Initialize relatvie wall- (0), green- (1) and window (2) fractions
3888           surf_usm_h%frac(ind_veg_wall,m)  = building_pars(ind_wall_frac_r,building_type)   
3889           surf_usm_h%frac(ind_pav_green,m) = building_pars(ind_green_frac_r,building_type) 
3890           surf_usm_h%frac(ind_wat_win,m)   = building_pars(ind_win_frac_r,building_type) 
3891           surf_usm_h%lai(m)                = building_pars(ind_lai_r,building_type) 
3892
3893           surf_usm_h%rho_c_wall(nzb_wall,m)   = building_pars(ind_hc1_wall_r,building_type) 
3894           surf_usm_h%rho_c_wall(nzb_wall+1,m) = building_pars(ind_hc1_wall_r,building_type)
3895           surf_usm_h%rho_c_wall(nzb_wall+2,m) = building_pars(ind_hc2_wall_r,building_type)
3896           surf_usm_h%rho_c_wall(nzb_wall+3,m) = building_pars(ind_hc3_wall_r,building_type)   
3897           surf_usm_h%lambda_h(nzb_wall,m)   = building_pars(ind_tc1_wall_r,building_type) 
3898           surf_usm_h%lambda_h(nzb_wall+1,m) = building_pars(ind_tc1_wall_r,building_type) 
3899           surf_usm_h%lambda_h(nzb_wall+2,m) = building_pars(ind_tc2_wall_r,building_type)
3900           surf_usm_h%lambda_h(nzb_wall+3,m) = building_pars(ind_tc3_wall_r,building_type)   
3901           surf_usm_h%rho_c_green(nzb_wall,m)   = rho_c_soil !building_pars(ind_hc1_wall_r,building_type) 
3902           surf_usm_h%rho_c_green(nzb_wall+1,m) = rho_c_soil !building_pars(ind_hc1_wall_r,building_type)
3903           surf_usm_h%rho_c_green(nzb_wall+2,m) = rho_c_soil !building_pars(ind_hc2_wall_r,building_type)
3904           surf_usm_h%rho_c_green(nzb_wall+3,m) = rho_c_soil !building_pars(ind_hc3_wall_r,building_type)   
3905           surf_usm_h%lambda_h_green(nzb_wall,m)   = lambda_h_green_sm !building_pars(ind_tc1_wall_r,building_type) 
3906           surf_usm_h%lambda_h_green(nzb_wall+1,m) = lambda_h_green_sm !building_pars(ind_tc1_wall_r,building_type)
3907           surf_usm_h%lambda_h_green(nzb_wall+2,m) = lambda_h_green_sm !building_pars(ind_tc2_wall_r,building_type)
3908           surf_usm_h%lambda_h_green(nzb_wall+3,m) = lambda_h_green_sm !building_pars(ind_tc3_wall_r,building_type)
3909           surf_usm_h%rho_c_window(nzb_wall,m)   = building_pars(ind_hc1_win_r,building_type) 
3910           surf_usm_h%rho_c_window(nzb_wall+1,m) = building_pars(ind_hc1_win_r,building_type)
3911           surf_usm_h%rho_c_window(nzb_wall+2,m) = building_pars(ind_hc2_win_r,building_type)
3912           surf_usm_h%rho_c_window(nzb_wall+3,m) = building_pars(ind_hc3_win_r,building_type)   
3913           surf_usm_h%lambda_h_window(nzb_wall,m)   = building_pars(ind_tc1_win_r,building_type) 
3914           surf_usm_h%lambda_h_window(nzb_wall+1,m) = building_pars(ind_tc1_win_r,building_type) 
3915           surf_usm_h%lambda_h_window(nzb_wall+2,m) = building_pars(ind_tc2_win_r,building_type)
3916           surf_usm_h%lambda_h_window(nzb_wall+3,m) = building_pars(ind_tc3_win_r,building_type)   
3917
3918           surf_usm_h%target_temp_summer(m)  = building_pars(ind_indoor_target_temp_summer,building_type)   
3919           surf_usm_h%target_temp_winter(m)  = building_pars(ind_indoor_target_temp_winter,building_type)   
3920!
3921!--        emissivity of wall-, green- and window fraction
3922           surf_usm_h%emissivity(ind_veg_wall,m)  = building_pars(ind_emis_wall_r,building_type)
3923           surf_usm_h%emissivity(ind_pav_green,m) = building_pars(ind_emis_green_r,building_type)
3924           surf_usm_h%emissivity(ind_wat_win,m)   = building_pars(ind_emis_win_r,building_type)
3925
3926           surf_usm_h%transmissivity(m)      = building_pars(ind_trans_r,building_type)
3927
3928           surf_usm_h%z0(m)                  = building_pars(ind_z0,building_type)
3929           surf_usm_h%z0h(m)                 = building_pars(ind_z0qh,building_type)
3930           surf_usm_h%z0q(m)                 = building_pars(ind_z0qh,building_type)
3931!
3932!--        albedo type for wall fraction, green fraction, window fraction
3933           surf_usm_h%albedo_type(ind_veg_wall,m)  = INT( building_pars(ind_alb_wall_r,building_type)  )
3934           surf_usm_h%albedo_type(ind_pav_green,m) = INT( building_pars(ind_alb_green_r,building_type) )
3935           surf_usm_h%albedo_type(ind_wat_win,m)   = INT( building_pars(ind_alb_win_r,building_type)   )
3936
3937           surf_usm_h%zw(nzb_wall,m)         = building_pars(ind_thick_1_wall_r,building_type)
3938           surf_usm_h%zw(nzb_wall+1,m)       = building_pars(ind_thick_2_wall_r,building_type)
3939           surf_usm_h%zw(nzb_wall+2,m)       = building_pars(ind_thick_3_wall_r,building_type)
3940           surf_usm_h%zw(nzb_wall+3,m)       = building_pars(ind_thick_4_wall_r,building_type)
3941           
3942           surf_usm_h%zw_green(nzb_wall,m)         = building_pars(ind_thick_1_wall_r,building_type)
3943           surf_usm_h%zw_green(nzb_wall+1,m)       = building_pars(ind_thick_2_wall_r,building_type)
3944           surf_usm_h%zw_green(nzb_wall+2,m)       = building_pars(ind_thick_3_wall_r,building_type)
3945           surf_usm_h%zw_green(nzb_wall+3,m)       = building_pars(ind_thick_4_wall_r,building_type)
3946           
3947           surf_usm_h%zw_window(nzb_wall,m)         = building_pars(ind_thick_1_win_r,building_type)
3948           surf_usm_h%zw_window(nzb_wall+1,m)       = building_pars(ind_thick_2_win_r,building_type)
3949           surf_usm_h%zw_window(nzb_wall+2,m)       = building_pars(ind_thick_3_win_r,building_type)
3950           surf_usm_h%zw_window(nzb_wall+3,m)       = building_pars(ind_thick_4_win_r,building_type)
3951
3952           surf_usm_h%c_surface(m)           = building_pars(ind_c_surface,building_type) 
3953           surf_usm_h%lambda_surf(m)         = building_pars(ind_lambda_surf,building_type) 
3954           surf_usm_h%c_surface_green(m)     = building_pars(ind_c_surface_green,building_type) 
3955           surf_usm_h%lambda_surf_green(m)   = building_pars(ind_lambda_surf_green,building_type) 
3956           surf_usm_h%c_surface_window(m)    = building_pars(ind_c_surface_win,building_type) 
3957           surf_usm_h%lambda_surf_window(m)  = building_pars(ind_lambda_surf_win,building_type) 
3958           
3959           surf_usm_h%green_type_roof(m)     = building_pars(ind_green_type_roof,building_type)
3960
3961        ENDDO
3962
3963        DO  l = 0, 3
3964           DO  m = 1, surf_usm_v(l)%ns
3965
3966              surf_usm_v(l)%surface_types(m) = wall_category         !< default category for root surface
3967!
3968!--           In order to distinguish between ground floor level and
3969!--           above-ground-floor level surfaces, set input indices.
3970              ind_alb_green    = MERGE( ind_alb_green_gfl,    ind_alb_green_agfl,    &
3971                                        surf_usm_v(l)%ground_level(m) )
3972              ind_alb_wall     = MERGE( ind_alb_wall_gfl,     ind_alb_wall_agfl,     &
3973                                        surf_usm_v(l)%ground_level(m) )
3974              ind_alb_win      = MERGE( ind_alb_win_gfl,      ind_alb_win_agfl,      &
3975                                        surf_usm_v(l)%ground_level(m) )
3976              ind_wall_frac    = MERGE( ind_wall_frac_gfl,    ind_wall_frac_agfl,    &
3977                                        surf_usm_v(l)%ground_level(m) )
3978              ind_win_frac     = MERGE( ind_win_frac_gfl,     ind_win_frac_agfl,     &
3979                                        surf_usm_v(l)%ground_level(m) )
3980              ind_green_frac_w = MERGE( ind_green_frac_w_gfl, ind_green_frac_w_agfl, &
3981                                        surf_usm_v(l)%ground_level(m) )
3982              ind_green_frac_r = MERGE( ind_green_frac_r_gfl, ind_green_frac_r_agfl, &
3983                                        surf_usm_v(l)%ground_level(m) )
3984              ind_lai_r        = MERGE( ind_lai_r_gfl,        ind_lai_r_agfl,        &
3985                                        surf_usm_v(l)%ground_level(m) )
3986              ind_lai_w        = MERGE( ind_lai_w_gfl,        ind_lai_w_agfl,        &
3987                                        surf_usm_v(l)%ground_level(m) )
3988              ind_hc1          = MERGE( ind_hc1_gfl,          ind_hc1_agfl,          &
3989                                        surf_usm_v(l)%ground_level(m) )
3990              ind_hc1_win      = MERGE( ind_hc1_win_gfl,      ind_hc1_win_agfl,      &
3991                                        surf_usm_v(l)%ground_level(m) )
3992              ind_hc2          = MERGE( ind_hc2_gfl,          ind_hc2_agfl,          &
3993                                        surf_usm_v(l)%ground_level(m) )
3994              ind_hc2_win      = MERGE( ind_hc2_win_gfl,      ind_hc2_win_agfl,      &
3995                                        surf_usm_v(l)%ground_level(m) )
3996              ind_hc3          = MERGE( ind_hc3_gfl,          ind_hc3_agfl,          &
3997                                        surf_usm_v(l)%ground_level(m) )
3998              ind_hc3_win      = MERGE( ind_hc3_win_gfl,      ind_hc3_win_agfl,      &
3999                                        surf_usm_v(l)%ground_level(m) )
4000              ind_tc1          = MERGE( ind_tc1_gfl,          ind_tc1_agfl,          &
4001                                        surf_usm_v(l)%ground_level(m) )
4002              ind_tc1_win      = MERGE( ind_tc1_win_gfl,      ind_tc1_win_agfl,      &
4003                                        surf_usm_v(l)%ground_level(m) )
4004              ind_tc2          = MERGE( ind_tc2_gfl,          ind_tc2_agfl,          &
4005                                        surf_usm_v(l)%ground_level(m) )
4006              ind_tc2_win      = MERGE( ind_tc2_win_gfl,      ind_tc2_win_agfl,      &
4007                                        surf_usm_v(l)%ground_level(m) )
4008              ind_tc3          = MERGE( ind_tc3_gfl,          ind_tc3_agfl,          &
4009                                        surf_usm_v(l)%ground_level(m) )
4010              ind_tc3_win      = MERGE( ind_tc3_win_gfl,      ind_tc3_win_agfl,      &
4011                                        surf_usm_v(l)%ground_level(m) )
4012              ind_thick_1      = MERGE( ind_thick_1_gfl,      ind_thick_1_agfl,      &
4013                                        surf_usm_v(l)%ground_level(m) )
4014              ind_thick_1_win  = MERGE( ind_thick_1_win_gfl,  ind_thick_1_win_agfl,  &
4015                                        surf_usm_v(l)%ground_level(m) )
4016              ind_thick_2      = MERGE( ind_thick_2_gfl,      ind_thick_2_agfl,      &
4017                                        surf_usm_v(l)%ground_level(m) )
4018              ind_thick_2_win  = MERGE( ind_thick_2_win_gfl,  ind_thick_2_win_agfl,  &
4019                                        surf_usm_v(l)%ground_level(m) )
4020              ind_thick_3      = MERGE( ind_thick_3_gfl,      ind_thick_3_agfl,      &
4021                                        surf_usm_v(l)%ground_level(m) )
4022              ind_thick_3_win  = MERGE( ind_thick_3_win_gfl,  ind_thick_3_win_agfl,  &
4023                                        surf_usm_v(l)%ground_level(m) )
4024              ind_thick_4      = MERGE( ind_thick_4_gfl,      ind_thick_4_agfl,      &
4025                                        surf_usm_v(l)%ground_level(m) )
4026              ind_thick_4_win  = MERGE( ind_thick_4_win_gfl,  ind_thick_4_win_agfl,  &
4027                                        surf_usm_v(l)%ground_level(m) )
4028              ind_emis_wall    = MERGE( ind_emis_wall_gfl,    ind_emis_wall_agfl,    &
4029                                        surf_usm_v(l)%ground_level(m) )
4030              ind_emis_green   = MERGE( ind_emis_green_gfl,   ind_emis_green_agfl,   &
4031                                        surf_usm_v(l)%ground_level(m) )
4032              ind_emis_win     = MERGE( ind_emis_win_gfl,     ind_emis_win_agfl,     &
4033                                        surf_usm_v(l)%ground_level(m) )
4034              ind_trans        = MERGE( ind_trans_gfl,       ind_trans_agfl,         &
4035                                        surf_usm_v(l)%ground_level(m) )
4036              ind_z0           = MERGE( ind_z0_gfl,           ind_z0_agfl,           &
4037                                        surf_usm_v(l)%ground_level(m) )
4038              ind_z0qh         = MERGE( ind_z0qh_gfl,         ind_z0qh_agfl,         &
4039                                        surf_usm_v(l)%ground_level(m) )
4040!
4041!--           Store building type and its name on each surface element
4042              surf_usm_v(l)%building_type(m)      = building_type
4043              surf_usm_v(l)%building_type_name(m) = building_type_name(building_type)
4044!
4045!--           Initialize relatvie wall- (0), green- (1) and window (2) fractions
4046              surf_usm_v(l)%frac(ind_veg_wall,m)   = building_pars(ind_wall_frac,building_type)   
4047              surf_usm_v(l)%frac(ind_pav_green,m)  = building_pars(ind_green_frac_w,building_type) 
4048              surf_usm_v(l)%frac(ind_wat_win,m)    = building_pars(ind_win_frac,building_type) 
4049              surf_usm_v(l)%lai(m)                 = building_pars(ind_lai_w,building_type) 
4050
4051              surf_usm_v(l)%rho_c_wall(nzb_wall,m)   = building_pars(ind_hc1,building_type) 
4052              surf_usm_v(l)%rho_c_wall(nzb_wall+1,m) = building_pars(ind_hc1,building_type)
4053              surf_usm_v(l)%rho_c_wall(nzb_wall+2,m) = building_pars(ind_hc2,building_type)
4054              surf_usm_v(l)%rho_c_wall(nzb_wall+3,m) = building_pars(ind_hc3,building_type)   
4055             
4056              surf_usm_v(l)%rho_c_green(nzb_wall,m)   = rho_c_soil !building_pars(ind_hc1,building_type) 
4057              surf_usm_v(l)%rho_c_green(nzb_wall+1,m) = rho_c_soil !building_pars(ind_hc1,building_type)
4058              surf_usm_v(l)%rho_c_green(nzb_wall+2,m) = rho_c_soil !building_pars(ind_hc2,building_type)
4059              surf_usm_v(l)%rho_c_green(nzb_wall+3,m) = rho_c_soil !building_pars(ind_hc3,building_type)   
4060             
4061              surf_usm_v(l)%rho_c_window(nzb_wall,m)   = building_pars(ind_hc1_win,building_type) 
4062              surf_usm_v(l)%rho_c_window(nzb_wall+1,m) = building_pars(ind_hc1_win,building_type)
4063              surf_usm_v(l)%rho_c_window(nzb_wall+2,m) = building_pars(ind_hc2_win,building_type)
4064              surf_usm_v(l)%rho_c_window(nzb_wall+3,m) = building_pars(ind_hc3_win,building_type)   
4065
4066              surf_usm_v(l)%lambda_h(nzb_wall,m)   = building_pars(ind_tc1,building_type) 
4067              surf_usm_v(l)%lambda_h(nzb_wall+1,m) = building_pars(ind_tc1,building_type) 
4068              surf_usm_v(l)%lambda_h(nzb_wall+2,m) = building_pars(ind_tc2,building_type)
4069              surf_usm_v(l)%lambda_h(nzb_wall+3,m) = building_pars(ind_tc3,building_type)   
4070             
4071              surf_usm_v(l)%lambda_h_green(nzb_wall,m)   = lambda_h_green_sm !building_pars(ind_tc1,building_type) 
4072              surf_usm_v(l)%lambda_h_green(nzb_wall+1,m) = lambda_h_green_sm !building_pars(ind_tc1,building_type)
4073              surf_usm_v(l)%lambda_h_green(nzb_wall+2,m) = lambda_h_green_sm !building_pars(ind_tc2,building_type)
4074              surf_usm_v(l)%lambda_h_green(nzb_wall+3,m) = lambda_h_green_sm !building_pars(ind_tc3,building_type)   
4075
4076              surf_usm_v(l)%lambda_h_window(nzb_wall,m)   = building_pars(ind_tc1_win,building_type) 
4077              surf_usm_v(l)%lambda_h_window(nzb_wall+1,m) = building_pars(ind_tc1_win,building_type) 
4078              surf_usm_v(l)%lambda_h_window(nzb_wall+2,m) = building_pars(ind_tc2_win,building_type)
4079              surf_usm_v(l)%lambda_h_window(nzb_wall+3,m) = building_pars(ind_tc3_win,building_type)   
4080
4081              surf_usm_v(l)%target_temp_summer(m)  = building_pars(ind_indoor_target_temp_summer,building_type)   
4082              surf_usm_v(l)%target_temp_winter(m)  = building_pars(ind_indoor_target_temp_winter,building_type)   
4083!
4084!--           emissivity of wall-, green- and window fraction
4085              surf_usm_v(l)%emissivity(ind_veg_wall,m)  = building_pars(ind_emis_wall,building_type)
4086              surf_usm_v(l)%emissivity(ind_pav_green,m) = building_pars(ind_emis_green,building_type)
4087              surf_usm_v(l)%emissivity(ind_wat_win,m)   = building_pars(ind_emis_win,building_type)
4088
4089              surf_usm_v(l)%transmissivity(m)      = building_pars(ind_trans,building_type)
4090
4091              surf_usm_v(l)%z0(m)                  = building_pars(ind_z0,building_type)
4092              surf_usm_v(l)%z0h(m)                 = building_pars(ind_z0qh,building_type)
4093              surf_usm_v(l)%z0q(m)                 = building_pars(ind_z0qh,building_type)
4094
4095              surf_usm_v(l)%albedo_type(ind_veg_wall,m)  = INT( building_pars(ind_alb_wall,building_type) )
4096              surf_usm_v(l)%albedo_type(ind_pav_green,m) = INT( building_pars(ind_alb_green,building_type) )
4097              surf_usm_v(l)%albedo_type(ind_wat_win,m)   = INT( building_pars(ind_alb_win,building_type) )
4098
4099              surf_usm_v(l)%zw(nzb_wall,m)         = building_pars(ind_thick_1,building_type)
4100              surf_usm_v(l)%zw(nzb_wall+1,m)       = building_pars(ind_thick_2,building_type)
4101              surf_usm_v(l)%zw(nzb_wall+2,m)       = building_pars(ind_thick_3,building_type)
4102              surf_usm_v(l)%zw(nzb_wall+3,m)       = building_pars(ind_thick_4,building_type)
4103             
4104              surf_usm_v(l)%zw_green(nzb_wall,m)         = building_pars(ind_thick_1,building_type)
4105              surf_usm_v(l)%zw_green(nzb_wall+1,m)       = building_pars(ind_thick_2,building_type)
4106              surf_usm_v(l)%zw_green(nzb_wall+2,m)       = building_pars(ind_thick_3,building_type)
4107              surf_usm_v(l)%zw_green(nzb_wall+3,m)       = building_pars(ind_thick_4,building_type)
4108
4109              surf_usm_v(l)%zw_window(nzb_wall,m)         = building_pars(ind_thick_1_win,building_type)
4110              surf_usm_v(l)%zw_window(nzb_wall+1,m)       = building_pars(ind_thick_2_win,building_type)
4111              surf_usm_v(l)%zw_window(nzb_wall+2,m)       = building_pars(ind_thick_3_win,building_type)
4112              surf_usm_v(l)%zw_window(nzb_wall+3,m)       = building_pars(ind_thick_4_win,building_type)
4113
4114              surf_usm_v(l)%c_surface(m)           = building_pars(ind_c_surface,building_type) 
4115              surf_usm_v(l)%lambda_surf(m)         = building_pars(ind_lambda_surf,building_type)
4116              surf_usm_v(l)%c_surface_green(m)     = building_pars(ind_c_surface_green,building_type) 
4117              surf_usm_v(l)%lambda_surf_green(m)   = building_pars(ind_lambda_surf_green,building_type)
4118              surf_usm_v(l)%c_surface_window(m)    = building_pars(ind_c_surface_win,building_type) 
4119              surf_usm_v(l)%lambda_surf_window(m)  = building_pars(ind_lambda_surf_win,building_type)
4120
4121           ENDDO
4122        ENDDO
4123!
4124!--     Level 2 - initialization via building type read from file
4125        IF ( building_type_f%from_file )  THEN
4126           DO  m = 1, surf_usm_h%ns
4127              i = surf_usm_h%i(m)
4128              j = surf_usm_h%j(m)
4129!
4130!--           For the moment, limit building type to 6 (to overcome errors in input file).
4131              st = building_type_f%var(j,i)
4132              IF ( st /= building_type_f%fill )  THEN
4133
4134!
4135!--              In order to distinguish between ground floor level and
4136!--              above-ground-floor level surfaces, set input indices.
4137
4138                 ind_green_frac_r = MERGE( ind_green_frac_r_gfl, ind_green_frac_r_agfl, &
4139                                           surf_usm_h%ground_level(m) )
4140                 ind_lai_r        = MERGE( ind_lai_r_gfl,        ind_lai_r_agfl,        &
4141                                           surf_usm_h%ground_level(m) )
4142                 ind_z0           = MERGE( ind_z0_gfl,           ind_z0_agfl,           &
4143                                           surf_usm_h%ground_level(m) )
4144                 ind_z0qh         = MERGE( ind_z0qh_gfl,         ind_z0qh_agfl,         &
4145                                           surf_usm_h%ground_level(m) )
4146!
4147!--              Store building type and its name on each surface element
4148                 surf_usm_h%building_type(m)      = st
4149                 surf_usm_h%building_type_name(m) = building_type_name(st)
4150!
4151!--              Initialize relatvie wall- (0), green- (1) and window (2) fractions
4152                 surf_usm_h%frac(ind_veg_wall,m)  = building_pars(ind_wall_frac_r,st)   
4153                 surf_usm_h%frac(ind_pav_green,m) = building_pars(ind_green_frac_r,st) 
4154                 surf_usm_h%frac(ind_wat_win,m)   = building_pars(ind_win_frac_r,st) 
4155                 surf_usm_h%lai(m)                = building_pars(ind_lai_r,st) 
4156
4157                 surf_usm_h%rho_c_wall(nzb_wall,m)   = building_pars(ind_hc1_wall_r,st) 
4158                 surf_usm_h%rho_c_wall(nzb_wall+1,m) = building_pars(ind_hc1_wall_r,st)
4159                 surf_usm_h%rho_c_wall(nzb_wall+2,m) = building_pars(ind_hc2_wall_r,st)
4160                 surf_usm_h%rho_c_wall(nzb_wall+3,m) = building_pars(ind_hc3_wall_r,st)   
4161                 surf_usm_h%lambda_h(nzb_wall,m)   = building_pars(ind_tc1_wall_r,st) 
4162                 surf_usm_h%lambda_h(nzb_wall+1,m) = building_pars(ind_tc1_wall_r,st) 
4163                 surf_usm_h%lambda_h(nzb_wall+2,m) = building_pars(ind_tc2_wall_r,st)
4164                 surf_usm_h%lambda_h(nzb_wall+3,m) = building_pars(ind_tc3_wall_r,st)   
4165                 
4166                 surf_usm_h%rho_c_green(nzb_wall,m)   = rho_c_soil !building_pars(ind_hc1_wall_r,st) 
4167                 surf_usm_h%rho_c_green(nzb_wall+1,m) = rho_c_soil !building_pars(ind_hc1_wall_r,st)
4168                 surf_usm_h%rho_c_green(nzb_wall+2,m) = rho_c_soil !building_pars(ind_hc2_wall_r,st)
4169                 surf_usm_h%rho_c_green(nzb_wall+3,m) = rho_c_soil !building_pars(ind_hc3_wall_r,st)   
4170                 surf_usm_h%lambda_h_green(nzb_wall,m)   = lambda_h_green_sm !building_pars(ind_tc1_wall_r,st) 
4171                 surf_usm_h%lambda_h_green(nzb_wall+1,m) = lambda_h_green_sm !building_pars(ind_tc1_wall_r,st)
4172                 surf_usm_h%lambda_h_green(nzb_wall+2,m) = lambda_h_green_sm !building_pars(ind_tc2_wall_r,st)
4173                 surf_usm_h%lambda_h_green(nzb_wall+3,m) = lambda_h_green_sm !building_pars(ind_tc3_wall_r,st)   
4174               
4175                 surf_usm_h%rho_c_window(nzb_wall,m)   = building_pars(ind_hc1_win_r,st) 
4176                 surf_usm_h%rho_c_window(nzb_wall+1,m) = building_pars(ind_hc1_win_r,st)
4177                 surf_usm_h%rho_c_window(nzb_wall+2,m) = building_pars(ind_hc2_win_r,st)
4178                 surf_usm_h%rho_c_window(nzb_wall+3,m) = building_pars(ind_hc3_win_r,st)   
4179                 surf_usm_h%lambda_h_window(nzb_wall,m)   = building_pars(ind_tc1_win_r,st) 
4180                 surf_usm_h%lambda_h_window(nzb_wall+1,m) = building_pars(ind_tc1_win_r,st) 
4181                 surf_usm_h%lambda_h_window(nzb_wall+2,m) = building_pars(ind_tc2_win_r,st)
4182                 surf_usm_h%lambda_h_window(nzb_wall+3,m) = building_pars(ind_tc3_win_r,st)   
4183
4184                 surf_usm_h%target_temp_summer(m)  = building_pars(ind_indoor_target_temp_summer,st)   
4185                 surf_usm_h%target_temp_winter(m)  = building_pars(ind_indoor_target_temp_winter,st)   
4186!
4187!--              emissivity of wall-, green- and window fraction
4188                 surf_usm_h%emissivity(ind_veg_wall,m)  = building_pars(ind_emis_wall_r,st)
4189                 surf_usm_h%emissivity(ind_pav_green,m) = building_pars(ind_emis_green_r,st)
4190                 surf_usm_h%emissivity(ind_wat_win,m)   = building_pars(ind_emis_win_r,st)
4191
4192                 surf_usm_h%transmissivity(m)      = building_pars(ind_trans_r,st)
4193
4194                 surf_usm_h%z0(m)                  = building_pars(ind_z0,st)
4195                 surf_usm_h%z0h(m)                 = building_pars(ind_z0qh,st)
4196                 surf_usm_h%z0q(m)                 = building_pars(ind_z0qh,st)
4197!
4198!--              albedo type for wall fraction, green fraction, window fraction
4199                 surf_usm_h%albedo_type(ind_veg_wall,m)  = INT( building_pars(ind_alb_wall_r,st) )
4200                 surf_usm_h%albedo_type(ind_pav_green,m) = INT( building_pars(ind_alb_green_r,st) )
4201                 surf_usm_h%albedo_type(ind_wat_win,m)   = INT( building_pars(ind_alb_win_r,st) )
4202
4203                 surf_usm_h%zw(nzb_wall,m)         = building_pars(ind_thick_1_wall_r,st)
4204                 surf_usm_h%zw(nzb_wall+1,m)       = building_pars(ind_thick_2_wall_r,st)
4205                 surf_usm_h%zw(nzb_wall+2,m)       = building_pars(ind_thick_3_wall_r,st)
4206                 surf_usm_h%zw(nzb_wall+3,m)       = building_pars(ind_thick_4_wall_r,st)
4207                 
4208                 surf_usm_h%zw_green(nzb_wall,m)         = building_pars(ind_thick_1_wall_r,st)
4209                 surf_usm_h%zw_green(nzb_wall+1,m)       = building_pars(ind_thick_2_wall_r,st)
4210                 surf_usm_h%zw_green(nzb_wall+2,m)       = building_pars(ind_thick_3_wall_r,st)
4211                 surf_usm_h%zw_green(nzb_wall+3,m)       = building_pars(ind_thick_4_wall_r,st)
4212
4213                 surf_usm_h%zw_window(nzb_wall,m)         = building_pars(ind_thick_1_win_r,st)
4214                 surf_usm_h%zw_window(nzb_wall+1,m)       = building_pars(ind_thick_2_win_r,st)
4215                 surf_usm_h%zw_window(nzb_wall+2,m)       = building_pars(ind_thick_3_win_r,st)
4216                 surf_usm_h%zw_window(nzb_wall+3,m)       = building_pars(ind_thick_4_win_r,st)
4217
4218                 surf_usm_h%c_surface(m)           = building_pars(ind_c_surface,st) 
4219                 surf_usm_h%lambda_surf(m)         = building_pars(ind_lambda_surf,st)
4220                 surf_usm_h%c_surface_green(m)     = building_pars(ind_c_surface_green,st) 
4221                 surf_usm_h%lambda_surf_green(m)   = building_pars(ind_lambda_surf_green,st)
4222                 surf_usm_h%c_surface_window(m)    = building_pars(ind_c_surface_win,st) 
4223                 surf_usm_h%lambda_surf_window(m)  = building_pars(ind_lambda_surf_win,st)
4224                 
4225                 surf_usm_h%green_type_roof(m)     = building_pars(ind_green_type_roof,st)
4226
4227              ENDIF
4228           ENDDO
4229
4230           DO  l = 0, 3
4231              DO  m = 1, surf_usm_v(l)%ns
4232                 i = surf_usm_v(l)%i(m) + surf_usm_v(l)%ioff
4233                 j = surf_usm_v(l)%j(m) + surf_usm_v(l)%joff
4234!
4235!--              For the moment, limit building type to 6 (to overcome errors in input file).
4236
4237                 st = building_type_f%var(j,i)
4238                 IF ( st /= building_type_f%fill )  THEN
4239
4240!
4241!--                 In order to distinguish between ground floor level and
4242!--                 above-ground-floor level surfaces, set input indices.
4243                    ind_alb_green    = MERGE( ind_alb_green_gfl,    ind_alb_green_agfl,    &
4244                                              surf_usm_v(l)%ground_level(m) )
4245                    ind_alb_wall     = MERGE( ind_alb_wall_gfl,     ind_alb_wall_agfl,     &
4246                                              surf_usm_v(l)%ground_level(m) )
4247                    ind_alb_win      = MERGE( ind_alb_win_gfl,      ind_alb_win_agfl,      &
4248                                              surf_usm_v(l)%ground_level(m) )
4249                    ind_wall_frac    = MERGE( ind_wall_frac_gfl,    ind_wall_frac_agfl,    &
4250                                              surf_usm_v(l)%ground_level(m) )
4251                    ind_win_frac     = MERGE( ind_win_frac_gfl,     ind_win_frac_agfl,     &
4252                                              surf_usm_v(l)%ground_level(m) )
4253                    ind_green_frac_w = MERGE( ind_green_frac_w_gfl, ind_green_frac_w_agfl, &
4254                                              surf_usm_v(l)%ground_level(m) )
4255                    ind_green_frac_r = MERGE( ind_green_frac_r_gfl, ind_green_frac_r_agfl, &
4256                                              surf_usm_v(l)%ground_level(m) )
4257                    ind_lai_r        = MERGE( ind_lai_r_gfl,        ind_lai_r_agfl,        &
4258                                              surf_usm_v(l)%ground_level(m) )
4259                    ind_lai_w        = MERGE( ind_lai_w_gfl,        ind_lai_w_agfl,        &
4260                                              surf_usm_v(l)%ground_level(m) )
4261                    ind_hc1          = MERGE( ind_hc1_gfl,          ind_hc1_agfl,          &
4262                                              surf_usm_v(l)%ground_level(m) )
4263                    ind_hc1_win      = MERGE( ind_hc1_win_gfl,      ind_hc1_win_agfl,      &
4264                                              surf_usm_v(l)%ground_level(m) )
4265                    ind_hc2          = MERGE( ind_hc2_gfl,          ind_hc2_agfl,          &
4266                                              surf_usm_v(l)%ground_level(m) )
4267                    ind_hc2_win      = MERGE( ind_hc2_win_gfl,      ind_hc2_win_agfl,      &
4268                                              surf_usm_v(l)%ground_level(m) )
4269                    ind_hc3          = MERGE( ind_hc3_gfl,          ind_hc3_agfl,          &
4270                                              surf_usm_v(l)%ground_level(m) )
4271                    ind_hc3_win      = MERGE( ind_hc3_win_gfl,      ind_hc3_win_agfl,      &
4272                                              surf_usm_v(l)%ground_level(m) )
4273                    ind_tc1          = MERGE( ind_tc1_gfl,          ind_tc1_agfl,          &
4274                                              surf_usm_v(l)%ground_level(m) )
4275                    ind_tc1_win      = MERGE( ind_tc1_win_gfl,      ind_tc1_win_agfl,      &
4276                                              surf_usm_v(l)%ground_level(m) )
4277                    ind_tc2          = MERGE( ind_tc2_gfl,          ind_tc2_agfl,          &
4278                                              surf_usm_v(l)%ground_level(m) )
4279                    ind_tc2_win      = MERGE( ind_tc2_win_gfl,      ind_tc2_win_agfl,      &
4280                                              surf_usm_v(l)%ground_level(m) )
4281                    ind_tc3          = MERGE( ind_tc3_gfl,          ind_tc3_agfl,          &
4282                                              surf_usm_v(l)%ground_level(m) )
4283                    ind_tc3_win      = MERGE( ind_tc3_win_gfl,      ind_tc3_win_agfl,      &
4284                                              surf_usm_v(l)%ground_level(m) )
4285                    ind_thick_1      = MERGE( ind_thick_1_gfl,      ind_thick_1_agfl,      &
4286                                              surf_usm_v(l)%ground_level(m) )
4287                    ind_thick_1_win  = MERGE( ind_thick_1_win_gfl,  ind_thick_1_win_agfl,  &
4288                                              surf_usm_v(l)%ground_level(m) )
4289                    ind_thick_2      = MERGE( ind_thick_2_gfl,      ind_thick_2_agfl,      &
4290                                              surf_usm_v(l)%ground_level(m) )
4291                    ind_thick_2_win  = MERGE( ind_thick_2_win_gfl,  ind_thick_2_win_agfl,  &
4292                                              surf_usm_v(l)%ground_level(m) )
4293                    ind_thick_3      = MERGE( ind_thick_3_gfl,      ind_thick_3_agfl,      &
4294                                              surf_usm_v(l)%ground_level(m) )
4295                    ind_thick_3_win  = MERGE( ind_thick_3_win_gfl,  ind_thick_3_win_agfl,  &
4296                                              surf_usm_v(l)%ground_level(m) )
4297                    ind_thick_4      = MERGE( ind_thick_4_gfl,      ind_thick_4_agfl,      &
4298                                              surf_usm_v(l)%ground_level(m) )
4299                    ind_thick_4_win  = MERGE( ind_thick_4_win_gfl,  ind_thick_4_win_agfl,  &
4300                                              surf_usm_v(l)%ground_level(m) )
4301                    ind_emis_wall    = MERGE( ind_emis_wall_gfl,    ind_emis_wall_agfl,    &
4302                                              surf_usm_v(l)%ground_level(m) )
4303                    ind_emis_green   = MERGE( ind_emis_green_gfl,   ind_emis_green_agfl,   &
4304                                              surf_usm_v(l)%ground_level(m) )
4305                    ind_emis_win     = MERGE( ind_emis_win_gfl,     ind_emis_win_agfl,     &
4306                                              surf_usm_v(l)%ground_level(m) )
4307                    ind_trans        = MERGE( ind_trans_gfl,       ind_trans_agfl,         &
4308                                            surf_usm_v(l)%ground_level(m) )
4309                    ind_z0           = MERGE( ind_z0_gfl,           ind_z0_agfl,           &
4310                                              surf_usm_v(l)%ground_level(m) )
4311                    ind_z0qh         = MERGE( ind_z0qh_gfl,         ind_z0qh_agfl,         &
4312                                              surf_usm_v(l)%ground_level(m) )
4313!
4314!--                 Store building type and its name on each surface element
4315                    surf_usm_v(l)%building_type(m)      = st
4316                    surf_usm_v(l)%building_type_name(m) = building_type_name(st)
4317!
4318!--                 Initialize relatvie wall- (0), green- (1) and window (2) fractions
4319                    surf_usm_v(l)%frac(ind_veg_wall,m)  = building_pars(ind_wall_frac,st)   
4320                    surf_usm_v(l)%frac(ind_pav_green,m) = building_pars(ind_green_frac_w,st) 
4321                    surf_usm_v(l)%frac(ind_wat_win,m)   = building_pars(ind_win_frac,st)   
4322                    surf_usm_v(l)%lai(m)                = building_pars(ind_lai_w,st) 
4323
4324                    surf_usm_v(l)%rho_c_wall(nzb_wall,m)   = building_pars(ind_hc1,st) 
4325                    surf_usm_v(l)%rho_c_wall(nzb_wall+1,m) = building_pars(ind_hc1,st)
4326                    surf_usm_v(l)%rho_c_wall(nzb_wall+2,m) = building_pars(ind_hc2,st)
4327                    surf_usm_v(l)%rho_c_wall(nzb_wall+3,m) = building_pars(ind_hc3,st)
4328                   
4329                    surf_usm_v(l)%rho_c_green(nzb_wall,m)   = rho_c_soil !building_pars(ind_hc1,st) 
4330                    surf_usm_v(l)%rho_c_green(nzb_wall+1,m) = rho_c_soil !building_pars(ind_hc1,st)
4331                    surf_usm_v(l)%rho_c_green(nzb_wall+2,m) = rho_c_soil !building_pars(ind_hc2,st)
4332                    surf_usm_v(l)%rho_c_green(nzb_wall+3,m) = rho_c_soil !building_pars(ind_hc3,st)
4333                   
4334                    surf_usm_v(l)%rho_c_window(nzb_wall,m)   = building_pars(ind_hc1_win,st) 
4335                    surf_usm_v(l)%rho_c_window(nzb_wall+1,m) = building_pars(ind_hc1_win,st)
4336                    surf_usm_v(l)%rho_c_window(nzb_wall+2,m) = building_pars(ind_hc2_win,st)
4337                    surf_usm_v(l)%rho_c_window(nzb_wall+3,m) = building_pars(ind_hc3_win,st)
4338
4339                    surf_usm_v(l)%lambda_h(nzb_wall,m)   = building_pars(ind_tc1,st) 
4340                    surf_usm_v(l)%lambda_h(nzb_wall+1,m) = building_pars(ind_tc1,st) 
4341                    surf_usm_v(l)%lambda_h(nzb_wall+2,m) = building_pars(ind_tc2,st)
4342                    surf_usm_v(l)%lambda_h(nzb_wall+3,m) = building_pars(ind_tc3,st) 
4343                   
4344                    surf_usm_v(l)%lambda_h_green(nzb_wall,m)   = lambda_h_green_sm !building_pars(ind_tc1,st) 
4345                    surf_usm_v(l)%lambda_h_green(nzb_wall+1,m) = lambda_h_green_sm !building_pars(ind_tc1,st)
4346                    surf_usm_v(l)%lambda_h_green(nzb_wall+2,m) = lambda_h_green_sm !building_pars(ind_tc2,st)
4347                    surf_usm_v(l)%lambda_h_green(nzb_wall+3,m) = lambda_h_green_sm !building_pars(ind_tc3,st)
4348                   
4349                    surf_usm_v(l)%lambda_h_window(nzb_wall,m)   = building_pars(ind_tc1_win,st) 
4350                    surf_usm_v(l)%lambda_h_window(nzb_wall+1,m) = building_pars(ind_tc1_win,st) 
4351                    surf_usm_v(l)%lambda_h_window(nzb_wall+2,m) = building_pars(ind_tc2_win,st)
4352                    surf_usm_v(l)%lambda_h_window(nzb_wall+3,m) = building_pars(ind_tc3_win,st) 
4353
4354                    surf_usm_v(l)%target_temp_summer(m)  = building_pars(ind_indoor_target_temp_summer,st)   
4355                    surf_usm_v(l)%target_temp_winter(m)  = building_pars(ind_indoor_target_temp_winter,st)   
4356!
4357!--                 emissivity of wall-, green- and window fraction
4358                    surf_usm_v(l)%emissivity(ind_veg_wall,m)  = building_pars(ind_emis_wall,st)
4359                    surf_usm_v(l)%emissivity(ind_pav_green,m) = building_pars(ind_emis_green,st)
4360                    surf_usm_v(l)%emissivity(ind_wat_win,m)   = building_pars(ind_emis_win,st)
4361
4362                    surf_usm_v(l)%transmissivity(m)      = building_pars(ind_trans,st)
4363
4364                    surf_usm_v(l)%z0(m)                  = building_pars(ind_z0,st)
4365                    surf_usm_v(l)%z0h(m)                 = building_pars(ind_z0qh,st)
4366                    surf_usm_v(l)%z0q(m)                 = building_pars(ind_z0qh,st)
4367
4368                    surf_usm_v(l)%albedo_type(ind_veg_wall,m)  = INT( building_pars(ind_alb_wall,st) )
4369                    surf_usm_v(l)%albedo_type(ind_pav_green,m) = INT( building_pars(ind_alb_green,st) )
4370                    surf_usm_v(l)%albedo_type(ind_wat_win,m)   = INT( building_pars(ind_alb_win,st) )
4371
4372                    surf_usm_v(l)%zw(nzb_wall,m)         = building_pars(ind_thick_1,st)
4373                    surf_usm_v(l)%zw(nzb_wall+1,m)       = building_pars(ind_thick_2,st)
4374                    surf_usm_v(l)%zw(nzb_wall+2,m)       = building_pars(ind_thick_3,st)
4375                    surf_usm_v(l)%zw(nzb_wall+3,m)       = building_pars(ind_thick_4,st)
4376                   
4377                    surf_usm_v(l)%zw_green(nzb_wall,m)         = building_pars(ind_thick_1,st)
4378                    surf_usm_v(l)%zw_green(nzb_wall+1,m)       = building_pars(ind_thick_2,st)
4379                    surf_usm_v(l)%zw_green(nzb_wall+2,m)       = building_pars(ind_thick_3,st)
4380                    surf_usm_v(l)%zw_green(nzb_wall+3,m)       = building_pars(ind_thick_4,st)
4381                   
4382                    surf_usm_v(l)%zw_window(nzb_wall,m)         = building_pars(ind_thick_1_win,st)
4383                    surf_usm_v(l)%zw_window(nzb_wall+1,m)       = building_pars(ind_thick_2_win,st)
4384                    surf_usm_v(l)%zw_window(nzb_wall+2,m)       = building_pars(ind_thick_3_win,st)
4385                    surf_usm_v(l)%zw_window(nzb_wall+3,m)       = building_pars(ind_thick_4_win,st)
4386
4387                    surf_usm_v(l)%c_surface(m)           = building_pars(ind_c_surface,st) 
4388                    surf_usm_v(l)%lambda_surf(m)         = building_pars(ind_lambda_surf,st) 
4389                    surf_usm_v(l)%c_surface_green(m)     = building_pars(ind_c_surface_green,st) 
4390                    surf_usm_v(l)%lambda_surf_green(m)   = building_pars(ind_lambda_surf_green,st) 
4391                    surf_usm_v(l)%c_surface_window(m)    = building_pars(ind_c_surface_win,st) 
4392                    surf_usm_v(l)%lambda_surf_window(m)  = building_pars(ind_lambda_surf_win,st) 
4393
4394
4395                 ENDIF
4396              ENDDO
4397           ENDDO
4398        ENDIF 
4399       
4400!
4401!--     Level 3 - initialization via building_pars read from file. Note, only
4402!--     variables that are also defined in the input-standard can be initialized
4403!--     via file. Other variables will be initialized on level 1 or 2.
4404        IF ( building_pars_f%from_file )  THEN
4405           DO  m = 1, surf_usm_h%ns
4406              i = surf_usm_h%i(m)
4407              j = surf_usm_h%j(m)
4408
4409!
4410!--           In order to distinguish between ground floor level and
4411!--           above-ground-floor level surfaces, set input indices.
4412              ind_wall_frac    = MERGE( ind_wall_frac_gfl,                     &
4413                                        ind_wall_frac_agfl,                    &
4414                                        surf_usm_h%ground_level(m) )
4415              ind_green_frac_r = MERGE( ind_green_frac_r_gfl,                  &
4416                                        ind_green_frac_r_agfl,                 &
4417                                        surf_usm_h%ground_level(m) )
4418              ind_win_frac     = MERGE( ind_win_frac_gfl,                      &
4419                                        ind_win_frac_agfl,                     &
4420                                        surf_usm_h%ground_level(m) )
4421              ind_lai_r        = MERGE( ind_lai_r_gfl,                         &
4422                                        ind_lai_r_agfl,                        &
4423                                        surf_usm_h%ground_level(m) )
4424              ind_z0           = MERGE( ind_z0_gfl,                            &
4425                                        ind_z0_agfl,                           &
4426                                        surf_usm_h%ground_level(m) )
4427              ind_z0qh         = MERGE( ind_z0qh_gfl,                          &
4428                                        ind_z0qh_agfl,                         &
4429                                        surf_usm_h%ground_level(m) )
4430              ind_hc1          = MERGE( ind_hc1_gfl,                           &
4431                                        ind_hc1_agfl,                          &
4432                                        surf_usm_h%ground_level(m) )
4433              ind_hc2          = MERGE( ind_hc2_gfl,                           &
4434                                        ind_hc2_agfl,                          &
4435                                        surf_usm_h%ground_level(m) )
4436              ind_hc3          = MERGE( ind_hc3_gfl,                           &
4437                                        ind_hc3_agfl,                          &
4438                                        surf_usm_h%ground_level(m) )
4439              ind_tc1          = MERGE( ind_tc1_gfl,                           &
4440                                        ind_tc1_agfl,                          &
4441                                        surf_usm_h%ground_level(m) )
4442              ind_tc2          = MERGE( ind_tc2_gfl,                           &
4443                                        ind_tc2_agfl,                          &
4444                                        surf_usm_h%ground_level(m) )
4445              ind_tc3          = MERGE( ind_tc3_gfl,                           &
4446                                        ind_tc3_agfl,                          &
4447                                        surf_usm_h%ground_level(m) )
4448              ind_emis_wall    = MERGE( ind_emis_wall_gfl,                     &
4449                                        ind_emis_wall_agfl,                    &
4450                                        surf_usm_h%ground_level(m) )
4451              ind_emis_green   = MERGE( ind_emis_green_gfl,                    &
4452                                        ind_emis_green_agfl,                   &
4453                                        surf_usm_h%ground_level(m) )
4454              ind_emis_win     = MERGE( ind_emis_win_gfl,                      &
4455                                        ind_emis_win_agfl,                     &
4456                                        surf_usm_h%ground_level(m) )
4457              ind_trans        = MERGE( ind_trans_gfl,                         &
4458                                        ind_trans_agfl,                        &
4459                                        surf_usm_h%ground_level(m) )
4460
4461!
4462!--           Initialize relatvie wall- (0), green- (1) and window (2) fractions
4463              IF ( building_pars_f%pars_xy(ind_wall_frac,j,i) /=               &
4464                   building_pars_f%fill )                                      &
4465                 surf_usm_h%frac(ind_veg_wall,m)  =                            &
4466                                    building_pars_f%pars_xy(ind_wall_frac,j,i)   
4467                 
4468              IF ( building_pars_f%pars_xy(ind_green_frac_r,j,i) /=            &         
4469                   building_pars_f%fill )                                      & 
4470                 surf_usm_h%frac(ind_pav_green,m) =                            &
4471                                    building_pars_f%pars_xy(ind_green_frac_r,j,i) 
4472                 
4473              IF ( building_pars_f%pars_xy(ind_win_frac,j,i) /=                &
4474                   building_pars_f%fill )                                      & 
4475                 surf_usm_h%frac(ind_wat_win,m)   =                            &
4476                                    building_pars_f%pars_xy(ind_win_frac,j,i)
4477 
4478              IF ( building_pars_f%pars_xy(ind_lai_r,j,i) /=                   &
4479                   building_pars_f%fill )                                      &
4480                 surf_usm_h%lai(m)  = building_pars_f%pars_xy(ind_lai_r,j,i)
4481
4482              IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=                     &
4483                   building_pars_f%fill )  THEN
4484                 surf_usm_h%rho_c_wall(nzb_wall,m)   =                         &
4485                                    building_pars_f%pars_xy(ind_hc1,j,i) 
4486                 surf_usm_h%rho_c_wall(nzb_wall+1,m) =                         &
4487                                    building_pars_f%pars_xy(ind_hc1,j,i)
4488              ENDIF
4489             
4490             
4491              IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=                     &
4492                   building_pars_f%fill )                                      &
4493                 surf_usm_h%rho_c_wall(nzb_wall+2,m) =                         &
4494                                    building_pars_f%pars_xy(ind_hc2,j,i)
4495                 
4496              IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=                     &
4497                   building_pars_f%fill )                                      &
4498                 surf_usm_h%rho_c_wall(nzb_wall+3,m) =                         &
4499                                    building_pars_f%pars_xy(ind_hc3,j,i)
4500                 
4501              IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=                     &
4502                   building_pars_f%fill )  THEN
4503                 surf_usm_h%rho_c_green(nzb_wall,m)   =                        &
4504                                    building_pars_f%pars_xy(ind_hc1,j,i) 
4505                 surf_usm_h%rho_c_green(nzb_wall+1,m) =                        &
4506                                    building_pars_f%pars_xy(ind_hc1,j,i)
4507              ENDIF
4508              IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=                     &
4509                   building_pars_f%fill )                                      &
4510                 surf_usm_h%rho_c_green(nzb_wall+2,m) =                        &
4511                                    building_pars_f%pars_xy(ind_hc2,j,i)
4512                 
4513              IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=                     &
4514                   building_pars_f%fill )                                      &
4515                 surf_usm_h%rho_c_green(nzb_wall+3,m) =                        &
4516                                    building_pars_f%pars_xy(ind_hc3,j,i)
4517                 
4518              IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=                     &
4519                   building_pars_f%fill )  THEN
4520                 surf_usm_h%rho_c_window(nzb_wall,m)   =                       &
4521                                    building_pars_f%pars_xy(ind_hc1,j,i) 
4522                 surf_usm_h%rho_c_window(nzb_wall+1,m) =                       &
4523                                    building_pars_f%pars_xy(ind_hc1,j,i)
4524              ENDIF
4525              IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=                     &
4526                   building_pars_f%fill )                                      &
4527                 surf_usm_h%rho_c_window(nzb_wall+2,m) =                       &
4528                                    building_pars_f%pars_xy(ind_hc2,j,i)
4529                 
4530              IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=                     &
4531                   building_pars_f%fill )                                      &
4532                 surf_usm_h%rho_c_window(nzb_wall+3,m) =                       &
4533                                    building_pars_f%pars_xy(ind_hc3,j,i)
4534
4535              IF ( building_pars_f%pars_xy(ind_tc1,j,i) /=                     &
4536                   building_pars_f%fill )  THEN
4537                 surf_usm_h%lambda_h(nzb_wall,m)   =                           &
4538                                    building_pars_f%pars_xy(ind_tc1,j,i)         
4539                 surf_usm_h%lambda_h(nzb_wall+1,m) =                           &
4540                                    building_pars_f%pars_xy(ind_tc1,j,i)       
4541              ENDIF
4542              IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=                     & 
4543                   building_pars_f%fill )                                      &
4544                 surf_usm_h%lambda_h(nzb_wall+2,m) =                           &
4545                                    building_pars_f%pars_xy(ind_tc2,j,i)
4546                 
4547              IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=                     &
4548                   building_pars_f%fill )                                      & 
4549                 surf_usm_h%lambda_h(nzb_wall+3,m) =                           &
4550                                    building_pars_f%pars_xy(ind_tc3,j,i)   
4551                 
4552              IF ( building_pars_f%pars_xy(ind_tc1,j,i) /=                     &
4553                   building_pars_f%fill )  THEN
4554                 surf_usm_h%lambda_h_green(nzb_wall,m)   =                     &
4555                                     building_pars_f%pars_xy(ind_tc1,j,i)         
4556                 surf_usm_h%lambda_h_green(nzb_wall+1,m) =                     &
4557                                     building_pars_f%pars_xy(ind_tc1,j,i)       
4558              ENDIF
4559              IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=                     & 
4560                   building_pars_f%fill )                                      &
4561                 surf_usm_h%lambda_h_green(nzb_wall+2,m) =                     &
4562                                    building_pars_f%pars_xy(ind_tc2,j,i)
4563                 
4564              IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=                     &       
4565                   building_pars_f%fill )                                      &
4566                 surf_usm_h%lambda_h_green(nzb_wall+3,m) =                     &
4567                                    building_pars_f%pars_xy(ind_tc3,j,i)   
4568                 
4569              IF ( building_pars_f%pars_xy(ind_tc1,j,i) /=                     &
4570                   building_pars_f%fill )  THEN
4571                 surf_usm_h%lambda_h_window(nzb_wall,m)   =                    &
4572                                     building_pars_f%pars_xy(ind_tc1,j,i)         
4573                 surf_usm_h%lambda_h_window(nzb_wall+1,m) =                    &
4574                                     building_pars_f%pars_xy(ind_tc1,j,i)       
4575              ENDIF
4576              IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=                     &     
4577                   building_pars_f%fill )                                      &
4578                 surf_usm_h%lambda_h_window(nzb_wall+2,m) =                    &
4579                                     building_pars_f%pars_xy(ind_tc2,j,i)
4580                 
4581              IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=                     &   
4582                   building_pars_f%fill )                                      &
4583                 surf_usm_h%lambda_h_window(nzb_wall+3,m) =                    &
4584                                    building_pars_f%pars_xy(ind_tc3,j,i)   
4585
4586              IF ( building_pars_f%pars_xy(ind_indoor_target_temp_summer,j,i) /=&           
4587                   building_pars_f%fill )                                      & 
4588                 surf_usm_h%target_temp_summer(m)  =                           &
4589                      building_pars_f%pars_xy(ind_indoor_target_temp_summer,j,i)   
4590              IF ( building_pars_f%pars_xy(ind_indoor_target_temp_winter,j,i) /=&           
4591                   building_pars_f%fill )                                      & 
4592                 surf_usm_h%target_temp_winter(m)  =                           &
4593                      building_pars_f%pars_xy(ind_indoor_target_temp_winter,j,i)   
4594
4595              IF ( building_pars_f%pars_xy(ind_emis_wall,j,i) /=               &   
4596                   building_pars_f%fill )                                      &
4597                 surf_usm_h%emissivity(ind_veg_wall,m)  =                      &
4598                                    building_pars_f%pars_xy(ind_emis_wall,j,i)
4599                 
4600              IF ( building_pars_f%pars_xy(ind_emis_green,j,i) /=              &           
4601                   building_pars_f%fill )                                      &
4602                 surf_usm_h%emissivity(ind_pav_green,m) =                      &
4603                                     building_pars_f%pars_xy(ind_emis_green,j,i)
4604                 
4605              IF ( building_pars_f%pars_xy(ind_emis_win,j,i) /=                & 
4606                   building_pars_f%fill )                                      &
4607                 surf_usm_h%emissivity(ind_wat_win,m)   =                      &
4608                                     building_pars_f%pars_xy(ind_emis_win,j,i)
4609                 
4610              IF ( building_pars_f%pars_xy(ind_trans,j,i) /=                   &   
4611                   building_pars_f%fill )                                      &
4612                 surf_usm_h%transmissivity(m) =                                &
4613                                    building_pars_f%pars_xy(ind_trans,j,i)
4614
4615              IF ( building_pars_f%pars_xy(ind_z0,j,i) /=                      &         
4616                   building_pars_f%fill )                                      &
4617                 surf_usm_h%z0(m) = building_pars_f%pars_xy(ind_z0,j,i)
4618                 
4619              IF ( building_pars_f%pars_xy(ind_z0qh,j,i) /=                    &           
4620                   building_pars_f%fill )                                      &
4621                 surf_usm_h%z0h(m) = building_pars_f%pars_xy(ind_z0qh,j,i)
4622              IF ( building_pars_f%pars_xy(ind_z0qh,j,i) /=                    &           
4623                   building_pars_f%fill )                                      &
4624                 surf_usm_h%z0q(m) = building_pars_f%pars_xy(ind_z0qh,j,i)
4625
4626              IF ( building_pars_f%pars_xy(ind_alb_wall_agfl,j,i) /=           &         
4627                   building_pars_f%fill )                                      & 
4628                 surf_usm_h%albedo_type(ind_veg_wall,m)  =                     &
4629                                 building_pars_f%pars_xy(ind_alb_wall_agfl,j,i)
4630                 
4631              IF ( building_pars_f%pars_xy(ind_alb_green_agfl,j,i) /=          &           
4632                   building_pars_f%fill )                                      &
4633                 surf_usm_h%albedo_type(ind_pav_green,m) =                     &
4634                                building_pars_f%pars_xy(ind_alb_green_agfl,j,i)
4635              IF ( building_pars_f%pars_xy(ind_alb_win_agfl,j,i) /=            &         
4636                   building_pars_f%fill )                                      &
4637                 surf_usm_h%albedo_type(ind_wat_win,m)   =                     &
4638                                   building_pars_f%pars_xy(ind_alb_win_agfl,j,i)
4639
4640              IF ( building_pars_f%pars_xy(ind_thick_1_agfl,j,i) /=            &         
4641                   building_pars_f%fill )                                      & 
4642                 surf_usm_h%zw(nzb_wall,m) =                                   &
4643                                  building_pars_f%pars_xy(ind_thick_1_agfl,j,i)
4644                 
4645              IF ( building_pars_f%pars_xy(ind_thick_2_agfl,j,i) /=            &         
4646                   building_pars_f%fill )                                      &
4647                 surf_usm_h%zw(nzb_wall+1,m) =                                 &
4648                                  building_pars_f%pars_xy(ind_thick_2_agfl,j,i)
4649                 
4650              IF ( building_pars_f%pars_xy(ind_thick_3_agfl,j,i) /=            &         
4651                   building_pars_f%fill )                                      &
4652                 surf_usm_h%zw(nzb_wall+2,m) =                                 &
4653                                  building_pars_f%pars_xy(ind_thick_3_agfl,j,i)
4654                 
4655                 
4656              IF ( building_pars_f%pars_xy(ind_thick_4_agfl,j,i) /=            &         
4657                   building_pars_f%fill )                                      & 
4658                 surf_usm_h%zw(nzb_wall+3,m) =                                 &
4659                                  building_pars_f%pars_xy(ind_thick_4_agfl,j,i)
4660                 
4661              IF ( building_pars_f%pars_xy(ind_thick_1_agfl,j,i) /=            &           
4662                   building_pars_f%fill )                                      &
4663                 surf_usm_h%zw_green(nzb_wall,m) =                             &
4664                                  building_pars_f%pars_xy(ind_thick_1_agfl,j,i)
4665                 
4666              IF ( building_pars_f%pars_xy(ind_thick_2_agfl,j,i) /=            &         
4667                   building_pars_f%fill )                                      &
4668                 surf_usm_h%zw_green(nzb_wall+1,m) =                           &
4669                                   building_pars_f%pars_xy(ind_thick_2_agfl,j,i)
4670                 
4671              IF ( building_pars_f%pars_xy(ind_thick_3_agfl,j,i) /=            &         
4672                   building_pars_f%fill )                                      & 
4673                 surf_usm_h%zw_green(nzb_wall+2,m) =                           &
4674                                   building_pars_f%pars_xy(ind_thick_3_agfl,j,i)
4675                 
4676              IF ( building_pars_f%pars_xy(ind_thick_4_agfl,j,i) /=            &         
4677                   building_pars_f%fill )                                      &
4678                 surf_usm_h%zw_green(nzb_wall+3,m) =                           &
4679                                   building_pars_f%pars_xy(ind_thick_4_agfl,j,i)
4680
4681              IF ( building_pars_f%pars_xy(ind_c_surface,j,i) /=               &       
4682                   building_pars_f%fill )                                      & 
4683                 surf_usm_h%c_surface(m) =                                     &
4684                                    building_pars_f%pars_xy(ind_c_surface,j,i)
4685                 
4686              IF ( building_pars_f%pars_xy(ind_lambda_surf,j,i) /=             &       
4687                   building_pars_f%fill )                                      &
4688                 surf_usm_h%lambda_surf(m) =                                   &
4689                                    building_pars_f%pars_xy(ind_lambda_surf,j,i)
4690             
4691           ENDDO
4692
4693
4694
4695           DO  l = 0, 3
4696              DO  m = 1, surf_usm_v(l)%ns
4697                 i = surf_usm_v(l)%i(m) + surf_usm_v(l)%ioff
4698                 j = surf_usm_v(l)%j(m) + surf_usm_v(l)%joff
4699               
4700!
4701!--                 In order to distinguish between ground floor level and
4702!--                 above-ground-floor level surfaces, set input indices.
4703                    ind_wall_frac    = MERGE( ind_wall_frac_gfl,               &
4704                                              ind_wall_frac_agfl,              &
4705                                              surf_usm_v(l)%ground_level(m) )
4706                    ind_green_frac_w = MERGE( ind_green_frac_w_gfl,            &
4707                                              ind_green_frac_w_agfl,           &
4708                                              surf_usm_v(l)%ground_level(m) )
4709                    ind_win_frac     = MERGE( ind_win_frac_gfl,                &
4710                                              ind_win_frac_agfl,               &
4711                                              surf_usm_v(l)%ground_level(m) )
4712                    ind_lai_w        = MERGE( ind_lai_w_gfl,                   &
4713                                              ind_lai_w_agfl,                  &
4714                                              surf_usm_v(l)%ground_level(m) )
4715                    ind_z0           = MERGE( ind_z0_gfl,                      &
4716                                              ind_z0_agfl,                     &
4717                                              surf_usm_v(l)%ground_level(m) )
4718                    ind_z0qh         = MERGE( ind_z0qh_gfl,                    &
4719                                              ind_z0qh_agfl,                   &
4720                                              surf_usm_v(l)%ground_level(m) )
4721                    ind_hc1          = MERGE( ind_hc1_gfl,                     &
4722                                              ind_hc1_agfl,                    &
4723                                              surf_usm_v(l)%ground_level(m) )
4724                    ind_hc2          = MERGE( ind_hc2_gfl,                     &
4725                                              ind_hc2_agfl,                    &
4726                                              surf_usm_v(l)%ground_level(m) )
4727                    ind_hc3          = MERGE( ind_hc3_gfl,                     &
4728                                              ind_hc3_agfl,                    &
4729                                              surf_usm_v(l)%ground_level(m) )
4730                    ind_tc1          = MERGE( ind_tc1_gfl,                     &
4731                                              ind_tc1_agfl,                    &
4732                                              surf_usm_v(l)%ground_level(m) )
4733                    ind_tc2          = MERGE( ind_tc2_gfl,                     &
4734                                              ind_tc2_agfl,                    &
4735                                              surf_usm_v(l)%ground_level(m) )
4736                    ind_tc3          = MERGE( ind_tc3_gfl,                     &
4737                                              ind_tc3_agfl,                    &
4738                                              surf_usm_v(l)%ground_level(m) )
4739                    ind_emis_wall    = MERGE( ind_emis_wall_gfl,               &
4740                                              ind_emis_wall_agfl,              &
4741                                              surf_usm_v(l)%ground_level(m) )
4742                    ind_emis_green   = MERGE( ind_emis_green_gfl,              &
4743                                              ind_emis_green_agfl,             &
4744                                              surf_usm_v(l)%ground_level(m) )
4745                    ind_emis_win     = MERGE( ind_emis_win_gfl,                &
4746                                              ind_emis_win_agfl,               &
4747                                              surf_usm_v(l)%ground_level(m) )
4748                    ind_trans        = MERGE( ind_trans_gfl,                   &
4749                                              ind_trans_agfl,                  &
4750                                              surf_usm_v(l)%ground_level(m) )
4751                   
4752!                   
4753!--                 Initialize relatvie wall- (0), green- (1) and window (2) fractions
4754                    IF ( building_pars_f%pars_xy(ind_wall_frac,j,i) /=         &
4755                         building_pars_f%fill )                                &
4756                       surf_usm_v(l)%frac(ind_veg_wall,m)  =                   &
4757                                          building_pars_f%pars_xy(ind_wall_frac,j,i)   
4758                       
4759                    IF ( building_pars_f%pars_xy(ind_green_frac_w,j,i) /=      &         
4760                         building_pars_f%fill )                                & 
4761                       surf_usm_v(l)%frac(ind_pav_green,m) =                   &
4762                                  building_pars_f%pars_xy(ind_green_frac_w,j,i) 
4763                       
4764                    IF ( building_pars_f%pars_xy(ind_win_frac,j,i) /=          &
4765                         building_pars_f%fill )                                & 
4766                       surf_usm_v(l)%frac(ind_wat_win,m)   =                   &
4767                                       building_pars_f%pars_xy(ind_win_frac,j,i)
4768                   
4769                    IF ( building_pars_f%pars_xy(ind_lai_w,j,i) /=             &
4770                         building_pars_f%fill )                                &
4771                       surf_usm_v(l)%lai(m)  =                                 &
4772                                       building_pars_f%pars_xy(ind_lai_w,j,i)
4773                   
4774                    IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=               &
4775                         building_pars_f%fill )  THEN
4776                       surf_usm_v(l)%rho_c_wall(nzb_wall,m)   =                &
4777                                          building_pars_f%pars_xy(ind_hc1,j,i) 
4778                       surf_usm_v(l)%rho_c_wall(nzb_wall+1,m) =                &
4779                                          building_pars_f%pars_xy(ind_hc1,j,i)
4780                    ENDIF
4781                   
4782                   
4783                    IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=               &
4784                         building_pars_f%fill )                                &
4785                       surf_usm_v(l)%rho_c_wall(nzb_wall+2,m) =                &
4786                                          building_pars_f%pars_xy(ind_hc2,j,i)
4787                       
4788                    IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=               &         
4789                         building_pars_f%fill )                                &
4790                       surf_usm_v(l)%rho_c_wall(nzb_wall+3,m) =                &
4791                                          building_pars_f%pars_xy(ind_hc3,j,i)
4792                       
4793                    IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=               &
4794                         building_pars_f%fill )  THEN
4795                       surf_usm_v(l)%rho_c_green(nzb_wall,m)   =               &
4796                                          building_pars_f%pars_xy(ind_hc1,j,i) 
4797                       surf_usm_v(l)%rho_c_green(nzb_wall+1,m) =               &
4798                                          building_pars_f%pars_xy(ind_hc1,j,i)
4799                    ENDIF
4800                    IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=               &
4801                         building_pars_f%fill )                                &
4802                       surf_usm_v(l)%rho_c_green(nzb_wall+2,m) =               &
4803                                          building_pars_f%pars_xy(ind_hc2,j,i)
4804                       
4805                    IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=               &
4806                         building_pars_f%fill )                                &
4807                       surf_usm_v(l)%rho_c_green(nzb_wall+3,m) =               &
4808                                          building_pars_f%pars_xy(ind_hc3,j,i)
4809                       
4810                    IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=               &
4811                         building_pars_f%fill )  THEN
4812                       surf_usm_v(l)%rho_c_window(nzb_wall,m)   =              &
4813                                          building_pars_f%pars_xy(ind_hc1,j,i) 
4814                       surf_usm_v(l)%rho_c_window(nzb_wall+1,m) =              &
4815                                          building_pars_f%pars_xy(ind_hc1,j,i)
4816                    ENDIF
4817                    IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=               &
4818                         building_pars_f%fill )                                &
4819                       surf_usm_v(l)%rho_c_window(nzb_wall+2,m) =              &
4820                                          building_pars_f%pars_xy(ind_hc2,j,i)
4821                       
4822                    IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=               &
4823                         building_pars_f%fill )                                &
4824                       surf_usm_v(l)%rho_c_window(nzb_wall+3,m) =              &
4825                                          building_pars_f%pars_xy(ind_hc3,j,i)
4826                   
4827                    IF ( building_pars_f%pars_xy(ind_tc1,j,i) /=               &
4828                         building_pars_f%fill )  THEN
4829                       surf_usm_v(l)%lambda_h(nzb_wall,m)   =                  &
4830                                          building_pars_f%pars_xy(ind_tc1,j,i)   
4831                       surf_usm_v(l)%lambda_h(nzb_wall+1,m) =                  &
4832                                          building_pars_f%pars_xy(ind_tc1,j,i) 
4833                    ENDIF
4834                    IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=               & 
4835                         building_pars_f%fill )                                &
4836                       surf_usm_v(l)%lambda_h(nzb_wall+2,m) =                  &
4837                                          building_pars_f%pars_xy(ind_tc2,j,i)
4838                       
4839                    IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=               &
4840                         building_pars_f%fill )                                & 
4841                       surf_usm_v(l)%lambda_h(nzb_wall+3,m) =                  &
4842                                          building_pars_f%pars_xy(ind_tc3,j,i) 
4843                       
4844                    IF ( building_pars_f%pars_xy(ind_tc1,j,i) /=               &
4845                         building_pars_f%fill )  THEN
4846                       surf_usm_v(l)%lambda_h_green(nzb_wall,m)   =            &
4847                                           building_pars_f%pars_xy(ind_tc1,j,i)   
4848                       surf_usm_v(l)%lambda_h_green(nzb_wall+1,m) =            &
4849                                           building_pars_f%pars_xy(ind_tc1,j,i) 
4850                    ENDIF
4851                    IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=               & 
4852                         building_pars_f%fill )                                &
4853                       surf_usm_v(l)%lambda_h_green(nzb_wall+2,m) =            &
4854                                          building_pars_f%pars_xy(ind_tc2,j,i)
4855                       
4856                    IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=               &       
4857                         building_pars_f%fill )                                &
4858                       surf_usm_v(l)%lambda_h_green(nzb_wall+3,m) =            &
4859                                          building_pars_f%pars_xy(ind_tc3,j,i) 
4860                       
4861                    IF ( building_pars_f%pars_xy(ind_tc1,j,i) /=         &
4862                         building_pars_f%fill )  THEN
4863                       surf_usm_v(l)%lambda_h_window(nzb_wall,m)   =           &
4864                                     building_pars_f%pars_xy(ind_tc1,j,i)         
4865                       surf_usm_v(l)%lambda_h_window(nzb_wall+1,m) =           &
4866                                     building_pars_f%pars_xy(ind_tc1,j,i)       
4867                    ENDIF
4868                    IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=               &     
4869                         building_pars_f%fill )                                &
4870                       surf_usm_v(l)%lambda_h_window(nzb_wall+2,m) =           &
4871                                           building_pars_f%pars_xy(ind_tc2,j,i)
4872                       
4873                    IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=               &   
4874                         building_pars_f%fill )                                &
4875                       surf_usm_v(l)%lambda_h_window(nzb_wall+3,m) =           &
4876                                          building_pars_f%pars_xy(ind_tc3,j,i)   
4877                   
4878                    IF ( building_pars_f%pars_xy(ind_indoor_target_temp_summer,j,i) /=&           
4879                         building_pars_f%fill )                                & 
4880                       surf_usm_v(l)%target_temp_summer(m)  =                  &
4881                            building_pars_f%pars_xy(ind_indoor_target_temp_summer,j,i)   
4882                    IF ( building_pars_f%pars_xy(ind_indoor_target_temp_winter,j,i) /=&           
4883                         building_pars_f%fill )                                & 
4884                       surf_usm_v(l)%target_temp_winter(m)  =                  &
4885                            building_pars_f%pars_xy(ind_indoor_target_temp_winter,j,i)   
4886                   
4887                    IF ( building_pars_f%pars_xy(ind_emis_wall,j,i) /=         &   
4888                         building_pars_f%fill )                                &
4889                       surf_usm_v(l)%emissivity(ind_veg_wall,m)  =             &
4890                                      building_pars_f%pars_xy(ind_emis_wall,j,i)
4891                       
4892                    IF ( building_pars_f%pars_xy(ind_emis_green,j,i) /=        &           
4893                         building_pars_f%fill )                                &
4894                       surf_usm_v(l)%emissivity(ind_pav_green,m) =             &
4895                                      building_pars_f%pars_xy(ind_emis_green,j,i)
4896                       
4897                    IF ( building_pars_f%pars_xy(ind_emis_win,j,i) /=          & 
4898                         building_pars_f%fill )                                &
4899                       surf_usm_v(l)%emissivity(ind_wat_win,m)   =             &
4900                                      building_pars_f%pars_xy(ind_emis_win,j,i)
4901                       
4902                    IF ( building_pars_f%pars_xy(ind_trans,j,i) /=             &   
4903                         building_pars_f%fill )                                &
4904                       surf_usm_v(l)%transmissivity(m) =                       &
4905                                          building_pars_f%pars_xy(ind_trans,j,i)
4906                   
4907                    IF ( building_pars_f%pars_xy(ind_z0,j,i) /=                &         
4908                         building_pars_f%fill )                                &
4909                       surf_usm_v(l)%z0(m) = building_pars_f%pars_xy(ind_z0,j,i)
4910                       
4911                    IF ( building_pars_f%pars_xy(ind_z0qh,j,i) /=              &           
4912                         building_pars_f%fill )                                &
4913                       surf_usm_v(l)%z0h(m) =                                  &
4914                                       building_pars_f%pars_xy(ind_z0qh,j,i)
4915                    IF ( building_pars_f%pars_xy(ind_z0qh,j,i) /=              &           
4916                         building_pars_f%fill )                                &
4917                       surf_usm_v(l)%z0q(m) =                                  &
4918                                       building_pars_f%pars_xy(ind_z0qh,j,i)
4919                   
4920                    IF ( building_pars_f%pars_xy(ind_alb_wall_agfl,j,i) /=     &         
4921                         building_pars_f%fill )                                & 
4922                       surf_usm_v(l)%albedo_type(ind_veg_wall,m)  =            &
4923                                 building_pars_f%pars_xy(ind_alb_wall_agfl,j,i)
4924                       
4925                    IF ( building_pars_f%pars_xy(ind_alb_green_agfl,j,i) /=    &           
4926                         building_pars_f%fill )                                &
4927                       surf_usm_v(l)%albedo_type(ind_pav_green,m) =            &
4928                                 building_pars_f%pars_xy(ind_alb_green_agfl,j,i)
4929                    IF ( building_pars_f%pars_xy(ind_alb_win_agfl,j,i) /=      &         
4930                         building_pars_f%fill )                                &
4931                       surf_usm_v(l)%albedo_type(ind_wat_win,m)   =            &
4932                                   building_pars_f%pars_xy(ind_alb_win_agfl,j,i)
4933                   
4934                    IF ( building_pars_f%pars_xy(ind_thick_1_agfl,j,i) /=      &         
4935                         building_pars_f%fill )                                & 
4936                       surf_usm_v(l)%zw(nzb_wall,m) =                          &
4937                                   building_pars_f%pars_xy(ind_thick_1_agfl,j,i)
4938                       
4939                    IF ( building_pars_f%pars_xy(ind_thick_2_agfl,j,i) /=      &         
4940                         building_pars_f%fill )                                &
4941                       surf_usm_v(l)%zw(nzb_wall+1,m) =                        &
4942                                   building_pars_f%pars_xy(ind_thick_2_agfl,j,i)
4943                       
4944                    IF ( building_pars_f%pars_xy(ind_thick_3_agfl,j,i) /=      &         
4945                         building_pars_f%fill )                                &
4946                       surf_usm_v(l)%zw(nzb_wall+2,m) =                        &
4947                                   building_pars_f%pars_xy(ind_thick_3_agfl,j,i)
4948                       
4949                       
4950                    IF ( building_pars_f%pars_xy(ind_thick_4_agfl,j,i) /=      &         
4951                         building_pars_f%fill )                                & 
4952                       surf_usm_v(l)%zw(nzb_wall+3,m) =                        &
4953                                   building_pars_f%pars_xy(ind_thick_4_agfl,j,i)
4954                       
4955                    IF ( building_pars_f%pars_xy(ind_thick_1_agfl,j,i) /=      &           
4956                         building_pars_f%fill )                                &
4957                       surf_usm_v(l)%zw_green(nzb_wall,m) =                    &
4958                                   building_pars_f%pars_xy(ind_thick_1_agfl,j,i)
4959                       
4960                    IF ( building_pars_f%pars_xy(ind_thick_2_agfl,j,i) /=      &         
4961                         building_pars_f%fill )                                &
4962                       surf_usm_v(l)%zw_green(nzb_wall+1,m) =                  &
4963                                   building_pars_f%pars_xy(ind_thick_2_agfl,j,i)
4964                       
4965                    IF ( building_pars_f%pars_xy(ind_thick_3_agfl,j,i) /=      &         
4966                         building_pars_f%fill )                                & 
4967                       surf_usm_v(l)%zw_green(nzb_wall+2,m) =                  &
4968                                   building_pars_f%pars_xy(ind_thick_3_agfl,j,i)
4969                       
4970                    IF ( building_pars_f%pars_xy(ind_thick_4_agfl,j,i) /=      &         
4971                         building_pars_f%fill )                                &
4972                       surf_usm_v(l)%zw_green(nzb_wall+3,m) =                  &
4973                                   building_pars_f%pars_xy(ind_thick_4_agfl,j,i)
4974                   
4975                    IF ( building_pars_f%pars_xy(ind_c_surface,j,i) /=         &       
4976                         building_pars_f%fill )                                & 
4977                       surf_usm_v(l)%c_surface(m) =                            &
4978                                     building_pars_f%pars_xy(ind_c_surface,j,i)
4979                       
4980                    IF ( building_pars_f%pars_xy(ind_lambda_surf,j,i) /=       &       
4981                         building_pars_f%fill )                                &
4982                       surf_usm_v(l)%lambda_surf(m) =                          &
4983                                    building_pars_f%pars_xy(ind_lambda_surf,j,i)
4984                   
4985              ENDDO
4986           ENDDO
4987        ENDIF 
4988!       
4989!--     Read the surface_types array.
4990!--     Please note, here also initialization of surface attributes is done as
4991!--     long as _urbsurf and _surfpar files are available. Values from above
4992!--     will be overwritten. This might be removed later, but is still in the
4993!--     code to enable compatibility with older model version.
4994        CALL usm_read_urban_surface_types()
4995       
4996        CALL usm_init_material_model()
4997!       
4998!--     init anthropogenic sources of heat
4999        IF ( usm_anthropogenic_heat )  THEN
5000!
5001!--         init anthropogenic sources of heat (from transportation for now)
5002            CALL usm_read_anthropogenic_heat()
5003        ENDIF
5004
5005!
5006!--    Check for consistent initialization.
5007!--    Check if roughness length for momentum, or heat, exceed surface-layer
5008!--    height and decrease local roughness length where necessary.
5009       DO  m = 1, surf_usm_h%ns
5010          IF ( surf_usm_h%z0(m) >= surf_usm_h%z_mo(m) )  THEN
5011         
5012             surf_usm_h%z0(m) = 0.9_wp * surf_usm_h%z_mo(m)
5013             
5014             WRITE( message_string, * ) 'z0 exceeds surface-layer height ' //  &
5015                            'at horizontal urban surface and is ' //           &
5016                            'decreased appropriately at grid point (i,j) = ',  &
5017                            surf_usm_h%i(m), surf_usm_h%j(m)
5018             CALL message( 'urban_surface_model_mod', 'PA0503',                &
5019                            0, 0, 0, 6, 0 )
5020          ENDIF
5021          IF ( surf_usm_h%z0h(m) >= surf_usm_h%z_mo(m) )  THEN
5022         
5023             surf_usm_h%z0h(m) = 0.9_wp * surf_usm_h%z_mo(m)
5024             surf_usm_h%z0q(m) = 0.9_wp * surf_usm_h%z_mo(m)
5025             
5026             WRITE( message_string, * ) 'z0h exceeds surface-layer height ' // &
5027                            'at horizontal urban surface and is ' //           &
5028                            'decreased appropriately at grid point (i,j) = ',  &
5029                            surf_usm_h%i(m), surf_usm_h%j(m)
5030             CALL message( 'urban_surface_model_mod', 'PA0507',                &
5031                            0, 0, 0, 6, 0 )
5032          ENDIF         
5033       ENDDO
5034       
5035       DO  l = 0, 3
5036          DO  m = 1, surf_usm_v(l)%ns
5037             IF ( surf_usm_v(l)%z0(m) >= surf_usm_v(l)%z_mo(m) )  THEN
5038         
5039                surf_usm_v(l)%z0(m) = 0.9_wp * surf_usm_v(l)%z_mo(m)
5040             
5041                WRITE( message_string, * ) 'z0 exceeds surface-layer height '// &
5042                            'at vertical urban surface and is ' //              &
5043                            'decreased appropriately at grid point (i,j) = ',   &
5044                            surf_usm_v(l)%i(m)+surf_usm_v(l)%ioff,              &
5045                            surf_usm_v(l)%j(m)+surf_usm_v(l)%joff
5046                CALL message( 'urban_surface_model_mod', 'PA0503',              &
5047                            0, 0, 0, 6, 0 )
5048             ENDIF
5049             IF ( surf_usm_v(l)%z0h(m) >= surf_usm_v(l)%z_mo(m) )  THEN
5050         
5051                surf_usm_v(l)%z0h(m) = 0.9_wp * surf_usm_v(l)%z_mo(m)
5052                surf_usm_v(l)%z0q(m) = 0.9_wp * surf_usm_v(l)%z_mo(m)
5053             
5054                WRITE( message_string, * ) 'z0h exceeds surface-layer height '// &
5055                            'at vertical urban surface and is ' //               &
5056                            'decreased appropriately at grid point (i,j) = ',    &
5057                            surf_usm_v(l)%i(m)+surf_usm_v(l)%ioff,               &
5058                            surf_usm_v(l)%j(m)+surf_usm_v(l)%joff
5059                CALL message( 'urban_surface_model_mod', 'PA0507',               &
5060                            0, 0, 0, 6, 0 )
5061             ENDIF
5062          ENDDO
5063       ENDDO
5064!
5065!--     Intitialization of the surface and wall/ground/roof temperature
5066!
5067!--     Initialization for restart runs
5068        IF ( TRIM( initializing_actions ) /= 'read_restart_data'  .AND.        &
5069             TRIM( initializing_actions ) /= 'cyclic_fill' )  THEN
5070
5071!
5072!--         At horizontal surfaces. Please note, t_surf_wall_h is defined on a
5073!--         different data type, but with the same dimension.
5074            DO  m = 1, surf_usm_h%ns
5075               i = surf_usm_h%i(m)           
5076               j = surf_usm_h%j(m)
5077               k = surf_usm_h%k(m)
5078
5079               t_surf_wall_h(m) = pt(k,j,i) * exner(k)
5080               t_surf_window_h(m) = pt(k,j,i) * exner(k)
5081               t_surf_green_h(m) = pt(k,j,i) * exner(k)
5082               surf_usm_h%pt_surface(m) = pt(k,j,i) * exner(k)
5083            ENDDO
5084!
5085!--         At vertical surfaces.
5086            DO  l = 0, 3
5087               DO  m = 1, surf_usm_v(l)%ns
5088                  i = surf_usm_v(l)%i(m)           
5089                  j = surf_usm_v(l)%j(m)
5090                  k = surf_usm_v(l)%k(m)
5091
5092                  t_surf_wall_v(l)%t(m) = pt(k,j,i) * exner(k)
5093                  t_surf_window_v(l)%t(m) = pt(k,j,i) * exner(k)
5094                  t_surf_green_v(l)%t(m) = pt(k,j,i) * exner(k)
5095                  surf_usm_v(l)%pt_surface(m) = pt(k,j,i) * exner(k)
5096               ENDDO
5097            ENDDO
5098
5099!
5100!--         For the sake of correct initialization, set also q_surface.
5101!--         Note, at urban surfaces q_surface is initialized with 0.
5102            IF ( humidity )  THEN
5103               DO  m = 1, surf_usm_h%ns
5104                  surf_usm_h%q_surface(m) = 0.0_wp
5105               ENDDO
5106               DO  l = 0, 3
5107                  DO  m = 1, surf_usm_v(l)%ns
5108                     surf_usm_v(l)%q_surface(m) = 0.0_wp
5109                  ENDDO
5110               ENDDO
5111            ENDIF
5112!
5113!--         initial values for t_wall
5114!--         outer value is set to surface temperature
5115!--         inner value is set to wall_inner_temperature
5116!--         and profile is logaritmic (linear in nz).
5117!--         Horizontal surfaces
5118            DO  m = 1, surf_usm_h%ns
5119!
5120!--            Roof
5121               IF ( surf_usm_h%isroof_surf(m) )  THEN
5122                   tin = roof_inner_temperature
5123                   twin = window_inner_temperature
5124!
5125!--            Normal land surface
5126               ELSE
5127                   tin = soil_inner_temperature
5128                   twin = window_inner_temperature
5129               ENDIF
5130
5131               DO k = nzb_wall, nzt_wall+1
5132                   c = REAL( k - nzb_wall, wp ) /                              &
5133                       REAL( nzt_wall + 1 - nzb_wall , wp )
5134
5135                   t_wall_h(k,m) = ( 1.0_wp - c ) * t_surf_wall_h(m) + c * tin
5136                   t_window_h(k,m) = ( 1.0_wp - c ) * t_surf_window_h(m) + c * twin
5137                   t_green_h(k,m) = t_surf_wall_h(m)
5138                   swc_h(k,m) = 0.5_wp
5139                   swc_sat_h(k,m) = 0.95_wp
5140                   swc_res_h(k,m) = 0.05_wp
5141                   rootfr_h(k,m) = 0.1_wp
5142                   wilt_h(k,m) = 0.1_wp
5143                   fc_h(k,m) = 0.9_wp
5144               ENDDO
5145            ENDDO
5146!
5147!--         Vertical surfaces
5148            DO  l = 0, 3
5149               DO  m = 1, surf_usm_v(l)%ns
5150!
5151!--               Inner wall
5152                  tin = wall_inner_temperature
5153                  twin = window_inner_temperature
5154
5155                  DO k = nzb_wall, nzt_wall+1
5156                     c = REAL( k - nzb_wall, wp ) /                            &
5157                         REAL( nzt_wall + 1 - nzb_wall , wp )
5158                     t_wall_v(l)%t(k,m) = ( 1.0_wp - c ) * t_surf_wall_v(l)%t(m) + c * tin
5159                     t_window_v(l)%t(k,m) = ( 1.0_wp - c ) * t_surf_window_v(l)%t(m) + c * twin
5160                     t_green_v(l)%t(k,m) = t_surf_wall_v(l)%t(m)
5161                     swc_v(l)%t(k,m) = 0.5_wp
5162                  ENDDO
5163               ENDDO
5164            ENDDO
5165        ENDIF
5166
5167!
5168!--     If specified, replace constant wall temperatures with fully 3D values from file
5169        IF ( read_wall_temp_3d )  CALL usm_read_wall_temperature()
5170
5171!--
5172!--     Possibly DO user-defined actions (e.g. define heterogeneous wall surface)
5173        CALL user_init_urban_surface
5174
5175!
5176!--     initialize prognostic values for the first timestep
5177        t_surf_wall_h_p = t_surf_wall_h
5178        t_surf_wall_v_p = t_surf_wall_v
5179        t_surf_window_h_p = t_surf_window_h
5180        t_surf_window_v_p = t_surf_window_v
5181        t_surf_green_h_p = t_surf_green_h
5182        t_surf_green_v_p = t_surf_green_v
5183
5184        t_wall_h_p = t_wall_h
5185        t_wall_v_p = t_wall_v
5186        t_window_h_p = t_window_h
5187        t_window_v_p = t_window_v
5188        t_green_h_p = t_green_h
5189        t_green_v_p = t_green_v
5190
5191!
5192!--     Adjust radiative fluxes for urban surface at model start
5193        !CALL radiation_interaction
5194!--     TODO: interaction should be called once before first output,
5195!--     that is not yet possible.
5196       
5197        m_liq_usm_h_p     = m_liq_usm_h
5198        m_liq_usm_v_p     = m_liq_usm_v
5199!
5200!--    Set initial values for prognostic quantities
5201!--    Horizontal surfaces
5202       tm_liq_usm_h_m%var_usm_1d  = 0.0_wp
5203       surf_usm_h%c_liq = 0.0_wp
5204
5205       surf_usm_h%qsws_liq  = 0.0_wp
5206       surf_usm_h%qsws_veg  = 0.0_wp
5207
5208!
5209!--    Do the same for vertical surfaces
5210       DO  l = 0, 3
5211          tm_liq_usm_v_m(l)%var_usm_1d  = 0.0_wp
5212          surf_usm_v(l)%c_liq = 0.0_wp
5213
5214          surf_usm_v(l)%qsws_liq  = 0.0_wp
5215          surf_usm_v(l)%qsws_veg  = 0.0_wp
5216       ENDDO
5217
5218!
5219!--    Set initial values for prognostic soil quantities
5220       IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
5221          m_liq_usm_h%var_usm_1d  = 0.0_wp
5222
5223          DO  l = 0, 3
5224             m_liq_usm_v(l)%var_usm_1d  = 0.0_wp
5225          ENDDO
5226       ENDIF
5227
5228        CALL cpu_log( log_point_s(78), 'usm_init', 'stop' )
5229
5230        IF ( debug_output )  CALL debug_message( 'usm_init', 'end' )
5231
5232    END SUBROUTINE usm_init
5233
5234
5235!------------------------------------------------------------------------------!
5236! Description:
5237! ------------
5238!
5239!> Wall model as part of the urban surface model. The model predicts vertical
5240!> and horizontal wall / roof temperatures and window layer temperatures.
5241!> No window layer temperature calculactions during spinup to increase
5242!> possible timestep.
5243!------------------------------------------------------------------------------!
5244    SUBROUTINE usm_material_heat_model( during_spinup )
5245
5246
5247        IMPLICIT NONE
5248
5249        INTEGER(iwp) ::  i,j,k,l,kw, m                      !< running indices
5250
5251        REAL(wp), DIMENSION(nzb_wall:nzt_wall) :: wtend, wintend  !< tendency
5252        REAL(wp)     :: win_absorp  !< absorption coefficient from transmissivity
5253        REAL(wp), DIMENSION(nzb_wall:nzt_wall) :: wall_mod
5254
5255        LOGICAL      :: during_spinup  !< if true, no calculation of window temperatures
5256
5257
5258        IF ( debug_output_timestep )  THEN
5259           WRITE( debug_string, * ) 'usm_material_heat_model | during_spinup: ',&
5260                                     during_spinup
5261           CALL debug_message( debug_string, 'start' )
5262        ENDIF
5263
5264        !$OMP PARALLEL PRIVATE (m, i, j, k, kw, wtend, wintend, win_absorp, wall_mod)
5265        wall_mod=1.0_wp
5266        IF ( usm_wall_mod  .AND.  during_spinup )  THEN
5267           DO  kw=nzb_wall,nzb_wall+1
5268               wall_mod(kw)=0.1_wp
5269           ENDDO
5270        ENDIF
5271
5272!
5273!--     For horizontal surfaces                                   
5274        !$OMP DO SCHEDULE (STATIC)
5275        DO  m = 1, surf_usm_h%ns
5276!
5277!--        Obtain indices
5278           i = surf_usm_h%i(m)           
5279           j = surf_usm_h%j(m)
5280           k = surf_usm_h%k(m)
5281!
5282!--        prognostic equation for ground/roof temperature t_wall_h
5283           wtend(:) = 0.0_wp
5284           wtend(nzb_wall) = (1.0_wp / surf_usm_h%rho_c_wall(nzb_wall,m)) *        &
5285                                       ( surf_usm_h%lambda_h(nzb_wall,m) * wall_mod(nzb_wall) *        &
5286                                         ( t_wall_h(nzb_wall+1,m)                  &
5287                                         - t_wall_h(nzb_wall,m) ) *                &
5288                                         surf_usm_h%ddz_wall(nzb_wall+1,m)         &
5289                                       + surf_usm_h%frac(ind_veg_wall,m)           &
5290                                         / (surf_usm_h%frac(ind_veg_wall,m)        &
5291                                           + surf_usm_h%frac(ind_pav_green,m) )    &
5292                                         * surf_usm_h%wghf_eb(m)                   &
5293                                       - surf_usm_h%frac(ind_pav_green,m)          &
5294                                          / (surf_usm_h%frac(ind_veg_wall,m)       &
5295                                            + surf_usm_h%frac(ind_pav_green,m) )   &
5296                                         * ( surf_usm_h%lambda_h_green(nzt_wall,m)* wall_mod(nzt_wall) &
5297                                           * surf_usm_h%ddz_green(nzt_wall,m)      &
5298                                           + surf_usm_h%lambda_h(nzb_wall,m) * wall_mod(nzb_wall)      &
5299                                           * surf_usm_h%ddz_wall(nzb_wall,m) )     &
5300                                         / ( surf_usm_h%ddz_green(nzt_wall,m)      &
5301                                           + surf_usm_h%ddz_wall(nzb_wall,m) )     &
5302                                         * ( t_wall_h(nzb_wall,m)                  &
5303                                           - t_green_h(nzt_wall,m) ) ) *           &
5304                                       surf_usm_h%ddz_wall_stag(nzb_wall,m)
5305!
5306!-- if indoor model ist used inner wall layer is calculated by using iwghf (indoor wall ground heat flux)
5307           IF ( indoor_model ) THEN
5308              DO  kw = nzb_wall+1, nzt_wall-1
5309                  wtend(kw) = (1.0_wp / surf_usm_h%rho_c_wall(kw,m))              &
5310                                 * (   surf_usm_h%lambda_h(kw,m) * wall_mod(kw)   &
5311                                    * ( t_wall_h(kw+1,m) - t_wall_h(kw,m) )       &
5312                                    * surf_usm_h%ddz_wall(kw+1,m)                 &
5313                                 - surf_usm_h%lambda_h(kw-1,m) * wall_mod(kw-1)   &
5314                                    * ( t_wall_h(kw,m) - t_wall_h(kw-1,m) )       &
5315                                    * surf_usm_h%ddz_wall(kw,m)                   &
5316                                   ) * surf_usm_h%ddz_wall_stag(kw,m)
5317              ENDDO
5318              wtend(nzt_wall) = (1.0_wp / surf_usm_h%rho_c_wall(nzt_wall,m)) *    &
5319                                         ( -surf_usm_h%lambda_h(nzt_wall-1,m) * wall_mod(nzt_wall-1) * &
5320                                           ( t_wall_h(nzt_wall,m)                 &
5321                                           - t_wall_h(nzt_wall-1,m) ) *           &
5322                                           surf_usm_h%ddz_wall(nzt_wall,m)        &
5323                                         + surf_usm_h%iwghf_eb(m) ) *             &
5324                                           surf_usm_h%ddz_wall_stag(nzt_wall,m)
5325           ELSE
5326              DO  kw = nzb_wall+1, nzt_wall
5327                  wtend(kw) = (1.0_wp / surf_usm_h%rho_c_wall(kw,m))              &
5328                                 * (   surf_usm_h%lambda_h(kw,m)  * wall_mod(kw)  &
5329                                    * ( t_wall_h(kw+1,m) - t_wall_h(kw,m) )       &
5330                                    * surf_usm_h%ddz_wall(kw+1,m)                 &
5331                                 - surf_usm_h%lambda_h(kw-1,m) * wall_mod(kw-1)   &
5332                                    * ( t_wall_h(kw,m) - t_wall_h(kw-1,m) )       &
5333                                    * surf_usm_h%ddz_wall(kw,m)                   &
5334                                   ) * surf_usm_h%ddz_wall_stag(kw,m)
5335              ENDDO
5336           ENDIF
5337
5338           t_wall_h_p(nzb_wall:nzt_wall,m) = t_wall_h(nzb_wall:nzt_wall,m)     &
5339                                 + dt_3d * ( tsc(2)                            &
5340                                 * wtend(nzb_wall:nzt_wall) + tsc(3)           &
5341                                 * surf_usm_h%tt_wall_m(nzb_wall:nzt_wall,m) )   
5342
5343!
5344!-- during spinup the tempeature inside window layers is not calculated to make larger timesteps possible
5345           IF ( .NOT. during_spinup ) THEN
5346              win_absorp = -log(surf_usm_h%transmissivity(m)) / surf_usm_h%zw_window(nzt_wall,m)
5347!
5348!--           prognostic equation for ground/roof window temperature t_window_h
5349!--           takes absorption of shortwave radiation into account
5350              wintend(:) = 0.0_wp
5351              wintend(nzb_wall) = (1.0_wp / surf_usm_h%rho_c_window(nzb_wall,m)) *   &
5352                                         ( surf_usm_h%lambda_h_window(nzb_wall,m) *  &
5353                                           ( t_window_h(nzb_wall+1,m)                &
5354                                           - t_window_h(nzb_wall,m) ) *              &
5355                                           surf_usm_h%ddz_window(nzb_wall+1,m)       &
5356                                         + surf_usm_h%wghf_eb_window(m)              &
5357                                         + surf_usm_h%rad_sw_in(m)                   &
5358                                           * (1.0_wp - exp(-win_absorp               &
5359                                           * surf_usm_h%zw_window(nzb_wall,m) ) )    &
5360                                         ) * surf_usm_h%ddz_window_stag(nzb_wall,m)
5361   
5362              IF ( indoor_model ) THEN
5363                 DO  kw = nzb_wall+1, nzt_wall-1
5364                     wintend(kw) = (1.0_wp / surf_usm_h%rho_c_window(kw,m))          &
5365                                    * (   surf_usm_h%lambda_h_window(kw,m)           &
5366                                       * ( t_window_h(kw+1,m) - t_window_h(kw,m) )   &
5367                                       * surf_usm_h%ddz_window(kw+1,m)               &
5368                                    - surf_usm_h%lambda_h_window(kw-1,m)             &
5369                                       * ( t_window_h(kw,m) - t_window_h(kw-1,m) )   &
5370                                       * surf_usm_h%ddz_window(kw,m)                 &
5371                                    + surf_usm_h%rad_sw_in(m)                        &
5372                                       * (exp(-win_absorp                            &
5373                                           * surf_usm_h%zw_window(kw-1,m) )          &
5374                                           - exp(-win_absorp                         &
5375                                           * surf_usm_h%zw_window(kw,m) ) )          &
5376                                      ) * surf_usm_h%ddz_window_stag(kw,m)
5377   
5378                 ENDDO
5379                 wintend(nzt_wall) = (1.0_wp / surf_usm_h%rho_c_window(nzt_wall,m)) *       &
5380                                            ( -surf_usm_h%lambda_h_window(nzt_wall-1,m) *   &
5381                                              ( t_window_h(nzt_wall,m)                      &
5382                                              - t_window_h(nzt_wall-1,m) ) *                &
5383                                              surf_usm_h%ddz_window(nzt_wall,m)             &
5384                                            + surf_usm_h%iwghf_eb_window(m)                 &
5385                                            + surf_usm_h%rad_sw_in(m)                       &
5386                                              * (exp(-win_absorp                            &
5387                                              * surf_usm_h%zw_window(nzt_wall-1,m) )        &
5388                                              - exp(-win_absorp                             &
5389                                              * surf_usm_h%zw_window(nzt_wall,m) ) )        &
5390                                            ) * surf_usm_h%ddz_window_stag(nzt_wall,m)
5391              ELSE
5392                 DO  kw = nzb_wall+1, nzt_wall
5393                     wintend(kw) = (1.0_wp / surf_usm_h%rho_c_window(kw,m))          &
5394                                    * (   surf_usm_h%lambda_h_window(kw,m)           &
5395                                       * ( t_window_h(kw+1,m) - t_window_h(kw,m) )   &
5396                                       * surf_usm_h%ddz_window(kw+1,m)               &
5397                                    - surf_usm_h%lambda_h_window(kw-1,m)             &
5398                                       * ( t_window_h(kw,m) - t_window_h(kw-1,m) )   &
5399                                       * surf_usm_h%ddz_window(kw,m)                 &
5400                                    + surf_usm_h%rad_sw_in(m)                        &
5401                                       * (exp(-win_absorp                            &
5402                                           * surf_usm_h%zw_window(kw-1,m) )          &
5403                                           - exp(-win_absorp                         &
5404                                           * surf_usm_h%zw_window(kw,m) ) )          &
5405                                      ) * surf_usm_h%ddz_window_stag(kw,m)
5406   
5407                 ENDDO
5408              ENDIF
5409
5410              t_window_h_p(nzb_wall:nzt_wall,m) = t_window_h(nzb_wall:nzt_wall,m) &
5411                                 + dt_3d * ( tsc(2)                               &
5412                                 * wintend(nzb_wall:nzt_wall) + tsc(3)            &
5413                                 * surf_usm_h%tt_window_m(nzb_wall:nzt_wall,m) )   
5414
5415           ENDIF
5416
5417!
5418!--        calculate t_wall tendencies for the next Runge-Kutta step
5419           IF ( timestep_scheme(1:5) == 'runge' )  THEN
5420               IF ( intermediate_timestep_count == 1 )  THEN
5421                  DO  kw = nzb_wall, nzt_wall
5422                     surf_usm_h%tt_wall_m(kw,m) = wtend(kw)
5423                  ENDDO
5424               ELSEIF ( intermediate_timestep_count <                          &
5425                        intermediate_timestep_count_max )  THEN
5426                   DO  kw = nzb_wall, nzt_wall
5427                      surf_usm_h%tt_wall_m(kw,m) = -9.5625_wp * wtend(kw) +    &
5428                                         5.3125_wp * surf_usm_h%tt_wall_m(kw,m)
5429                   ENDDO
5430               ENDIF
5431           ENDIF
5432
5433           IF ( .NOT. during_spinup )  THEN
5434!
5435!--           calculate t_window tendencies for the next Runge-Kutta step
5436              IF ( timestep_scheme(1:5) == 'runge' )  THEN
5437                  IF ( intermediate_timestep_count == 1 )  THEN
5438                     DO  kw = nzb_wall, nzt_wall
5439                        surf_usm_h%tt_window_m(kw,m) = wintend(kw)
5440                     ENDDO
5441                  ELSEIF ( intermediate_timestep_count <                            &
5442                           intermediate_timestep_count_max )  THEN
5443                      DO  kw = nzb_wall, nzt_wall
5444                         surf_usm_h%tt_window_m(kw,m) = -9.5625_wp * wintend(kw) +  &
5445                                            5.3125_wp * surf_usm_h%tt_window_m(kw,m)
5446                      ENDDO
5447                  ENDIF
5448              ENDIF
5449           ENDIF
5450
5451        ENDDO
5452
5453!
5454!--     For vertical surfaces     
5455        !$OMP DO SCHEDULE (STATIC)
5456        DO  l = 0, 3                             
5457           DO  m = 1, surf_usm_v(l)%ns
5458!
5459!--           Obtain indices
5460              i = surf_usm_v(l)%i(m)           
5461              j = surf_usm_v(l)%j(m)
5462              k = surf_usm_v(l)%k(m)
5463!
5464!--           prognostic equation for wall temperature t_wall_v
5465              wtend(:) = 0.0_wp
5466
5467              wtend(nzb_wall) = (1.0_wp / surf_usm_v(l)%rho_c_wall(nzb_wall,m)) *    &
5468                                      ( surf_usm_v(l)%lambda_h(nzb_wall,m) * wall_mod(nzb_wall)  *      &
5469                                        ( t_wall_v(l)%t(nzb_wall+1,m)                &
5470                                        - t_wall_v(l)%t(nzb_wall,m) ) *              &
5471                                        surf_usm_v(l)%ddz_wall(nzb_wall+1,m)         &
5472                                      + surf_usm_v(l)%frac(ind_veg_wall,m)           &
5473                                        / (surf_usm_v(l)%frac(ind_veg_wall,m)        &
5474                                          + surf_usm_v(l)%frac(ind_pav_green,m) )    &
5475                                        * surf_usm_v(l)%wghf_eb(m)                   &
5476                                      - surf_usm_v(l)%frac(ind_pav_green,m)          &
5477                                        / (surf_usm_v(l)%frac(ind_veg_wall,m)        &
5478                                          + surf_usm_v(l)%frac(ind_pav_green,m) )    &
5479                                        * ( surf_usm_v(l)%lambda_h_green(nzt_wall,m)* wall_mod(nzt_wall) &
5480                                          * surf_usm_v(l)%ddz_green(nzt_wall,m)      &
5481                                          + surf_usm_v(l)%lambda_h(nzb_wall,m)* wall_mod(nzb_wall)       &
5482                                          * surf_usm_v(l)%ddz_wall(nzb_wall,m) )     &
5483                                        / ( surf_usm_v(l)%ddz_green(nzt_wall,m)      &
5484                                          + surf_usm_v(l)%ddz_wall(nzb_wall,m) )     &
5485                                        * ( t_wall_v(l)%t(nzb_wall,m)                &
5486                                          - t_green_v(l)%t(nzt_wall,m) ) ) *         &
5487                                        surf_usm_v(l)%ddz_wall_stag(nzb_wall,m)
5488
5489              IF ( indoor_model ) THEN
5490                 DO  kw = nzb_wall+1, nzt_wall-1
5491                     wtend(kw) = (1.0_wp / surf_usm_v(l)%rho_c_wall(kw,m))        &
5492                              * (   surf_usm_v(l)%lambda_h(kw,m)  * wall_mod(kw)  &
5493                                 * ( t_wall_v(l)%t(kw+1,m) - t_wall_v(l)%t(kw,m) )&
5494                                 * surf_usm_v(l)%ddz_wall(kw+1,m)                 &
5495                              - surf_usm_v(l)%lambda_h(kw-1,m)  * wall_mod(kw-1)  &
5496                                 * ( t_wall_v(l)%t(kw,m) - t_wall_v(l)%t(kw-1,m) )&
5497                                 * surf_usm_v(l)%ddz_wall(kw,m)                   &
5498                                 ) * surf_usm_v(l)%ddz_wall_stag(kw,m)
5499                 ENDDO
5500                 wtend(nzt_wall) = (1.0_wp / surf_usm_v(l)%rho_c_wall(nzt_wall,m)) * &
5501                                         ( -surf_usm_v(l)%lambda_h(nzt_wall-1,m) * wall_mod(nzt_wall-1)*    &
5502                                           ( t_wall_v(l)%t(nzt_wall,m)               &
5503                                           - t_wall_v(l)%t(nzt_wall-1,m) ) *         &
5504                                           surf_usm_v(l)%ddz_wall(nzt_wall,m)        &
5505                                         + surf_usm_v(l)%iwghf_eb(m) ) *             &
5506                                           surf_usm_v(l)%ddz_wall_stag(nzt_wall,m)
5507              ELSE
5508                 DO  kw = nzb_wall+1, nzt_wall
5509                     wtend(kw) = (1.0_wp / surf_usm_v(l)%rho_c_wall(kw,m))        &
5510                              * (   surf_usm_v(l)%lambda_h(kw,m) * wall_mod(kw)   &
5511                                 * ( t_wall_v(l)%t(kw+1,m) - t_wall_v(l)%t(kw,m) )&
5512                                 * surf_usm_v(l)%ddz_wall(kw+1,m)                 &
5513                              - surf_usm_v(l)%lambda_h(kw-1,m)  * wall_mod(kw-1)  &
5514                                 * ( t_wall_v(l)%t(kw,m) - t_wall_v(l)%t(kw-1,m) )&
5515                                 * surf_usm_v(l)%ddz_wall(kw,m)                   &
5516                                 ) * surf_usm_v(l)%ddz_wall_stag(kw,m)
5517                 ENDDO
5518              ENDIF
5519
5520              t_wall_v_p(l)%t(nzb_wall:nzt_wall,m) =                           &
5521                                   t_wall_v(l)%t(nzb_wall:nzt_wall,m)          &
5522                                 + dt_3d * ( tsc(2)                            &
5523                                 * wtend(nzb_wall:nzt_wall) + tsc(3)           &
5524                                 * surf_usm_v(l)%tt_wall_m(nzb_wall:nzt_wall,m) )   
5525
5526              IF ( .NOT. during_spinup )  THEN
5527                 win_absorp = -log(surf_usm_v(l)%transmissivity(m)) / surf_usm_v(l)%zw_window(nzt_wall,m)
5528!
5529!--              prognostic equation for window temperature t_window_v
5530                 wintend(:) = 0.0_wp
5531                 wintend(nzb_wall) = (1.0_wp / surf_usm_v(l)%rho_c_window(nzb_wall,m)) * &
5532                                         ( surf_usm_v(l)%lambda_h_window(nzb_wall,m) *   &
5533                                           ( t_window_v(l)%t(nzb_wall+1,m)               &
5534                                           - t_window_v(l)%t(nzb_wall,m) ) *             &
5535                                           surf_usm_v(l)%ddz_window(nzb_wall+1,m)        &
5536                                         + surf_usm_v(l)%wghf_eb_window(m)               &
5537                                         + surf_usm_v(l)%rad_sw_in(m)                    &
5538                                           * (1.0_wp - exp(-win_absorp                   &
5539                                           * surf_usm_v(l)%zw_window(nzb_wall,m) ) )     &
5540                                         ) * surf_usm_v(l)%ddz_window_stag(nzb_wall,m)
5541   
5542                 IF ( indoor_model ) THEN
5543                    DO  kw = nzb_wall+1, nzt_wall -1
5544                        wintend(kw) = (1.0_wp / surf_usm_v(l)%rho_c_window(kw,m))         &
5545                                 * (   surf_usm_v(l)%lambda_h_window(kw,m)                &
5546                                    * ( t_window_v(l)%t(kw+1,m) - t_window_v(l)%t(kw,m) ) &
5547                                    * surf_usm_v(l)%ddz_window(kw+1,m)                    &
5548                                 - surf_usm_v(l)%lambda_h_window(kw-1,m)                  &
5549                                    * ( t_window_v(l)%t(kw,m) - t_window_v(l)%t(kw-1,m) ) &
5550                                    * surf_usm_v(l)%ddz_window(kw,m)                      &
5551                                 + surf_usm_v(l)%rad_sw_in(m)                             &
5552                                    * (exp(-win_absorp                                    &
5553                                       * surf_usm_v(l)%zw_window(kw-1,m)       )          &
5554                                           - exp(-win_absorp                              &
5555                                           * surf_usm_v(l)%zw_window(kw,m) ) )            &
5556                                    ) * surf_usm_v(l)%ddz_window_stag(kw,m)
5557                     ENDDO
5558                     wintend(nzt_wall) = (1.0_wp / surf_usm_v(l)%rho_c_window(nzt_wall,m)) *  &
5559                                             ( -surf_usm_v(l)%lambda_h_window(nzt_wall-1,m) * &
5560                                               ( t_window_v(l)%t(nzt_wall,m)                  &
5561                                               - t_window_v(l)%t(nzt_wall-1,m) ) *            &
5562                                               surf_usm_v(l)%ddz_window(nzt_wall,m)           &
5563                                             + surf_usm_v(l)%iwghf_eb_window(m)               &
5564                                             + surf_usm_v(l)%rad_sw_in(m)                     &
5565                                               * (exp(-win_absorp                             &
5566                                             * surf_usm_v(l)%zw_window(nzt_wall-1,m) )        &
5567                                           - exp(-win_absorp                                  &
5568                                               * surf_usm_v(l)%zw_window(nzt_wall,m) ) )      &
5569                                             ) * surf_usm_v(l)%ddz_window_stag(nzt_wall,m)
5570                 ELSE
5571                    DO  kw = nzb_wall+1, nzt_wall
5572                        wintend(kw) = (1.0_wp / surf_usm_v(l)%rho_c_window(kw,m))         &
5573                                 * (   surf_usm_v(l)%lambda_h_window(kw,m)                &
5574                                    * ( t_window_v(l)%t(kw+1,m) - t_window_v(l)%t(kw,m) ) &
5575                                    * surf_usm_v(l)%ddz_window(kw+1,m)                    &
5576                                 - surf_usm_v(l)%lambda_h_window(kw-1,m)                  &
5577                                    * ( t_window_v(l)%t(kw,m) - t_window_v(l)%t(kw-1,m) ) &
5578                                    * surf_usm_v(l)%ddz_window(kw,m)                      &
5579                                 + surf_usm_v(l)%rad_sw_in(m)                             &
5580                                    * (exp(-win_absorp                                    &
5581                                       * surf_usm_v(l)%zw_window(kw-1,m)       )          &
5582                                           - exp(-win_absorp                              &
5583                                           * surf_usm_v(l)%zw_window(kw,m) ) )            &
5584                                    ) * surf_usm_v(l)%ddz_window_stag(kw,m)
5585                    ENDDO
5586                 ENDIF
5587   
5588                 t_window_v_p(l)%t(nzb_wall:nzt_wall,m) =                           &
5589                                      t_window_v(l)%t(nzb_wall:nzt_wall,m)          &
5590                                    + dt_3d * ( tsc(2)                              &
5591                                    * wintend(nzb_wall:nzt_wall) + tsc(3)           &
5592                                    * surf_usm_v(l)%tt_window_m(nzb_wall:nzt_wall,m) )   
5593              ENDIF
5594
5595!
5596!--           calculate t_wall tendencies for the next Runge-Kutta step
5597              IF ( timestep_scheme(1:5) == 'runge' )  THEN
5598                  IF ( intermediate_timestep_count == 1 )  THEN
5599                     DO  kw = nzb_wall, nzt_wall
5600                        surf_usm_v(l)%tt_wall_m(kw,m) = wtend(kw)
5601                     ENDDO
5602                  ELSEIF ( intermediate_timestep_count <                       &
5603                           intermediate_timestep_count_max )  THEN
5604                      DO  kw = nzb_wall, nzt_wall
5605                         surf_usm_v(l)%tt_wall_m(kw,m) =                       &
5606                                     - 9.5625_wp * wtend(kw) +                 &
5607                                       5.3125_wp * surf_usm_v(l)%tt_wall_m(kw,m)
5608                      ENDDO
5609                  ENDIF
5610              ENDIF
5611
5612
5613              IF ( .NOT. during_spinup )  THEN
5614!
5615!--              calculate t_window tendencies for the next Runge-Kutta step
5616                 IF ( timestep_scheme(1:5) == 'runge' )  THEN
5617                     IF ( intermediate_timestep_count == 1 )  THEN
5618                        DO  kw = nzb_wall, nzt_wall
5619                           surf_usm_v(l)%tt_window_m(kw,m) = wintend(kw)
5620                        ENDDO
5621                     ELSEIF ( intermediate_timestep_count <                       &
5622                              intermediate_timestep_count_max )  THEN
5623                         DO  kw = nzb_wall, nzt_wall
5624                            surf_usm_v(l)%tt_window_m(kw,m) =                     &
5625                                        - 9.5625_wp * wintend(kw) +               &
5626                                          5.3125_wp * surf_usm_v(l)%tt_window_m(kw,m)
5627                         ENDDO
5628                     ENDIF
5629                 ENDIF
5630              ENDIF
5631
5632           ENDDO
5633        ENDDO
5634        !$OMP END PARALLEL
5635
5636        IF ( debug_output_timestep )  THEN
5637           WRITE( debug_string, * ) 'usm_material_heat_model | during_spinup: ',&
5638                                    during_spinup
5639           CALL debug_message( debug_string, 'end' )
5640        ENDIF
5641
5642    END SUBROUTINE usm_material_heat_model
5643
5644!------------------------------------------------------------------------------!
5645! Description:
5646! ------------
5647!
5648!> Green and substrate model as part of the urban surface model. The model predicts ground
5649!> temperatures.
5650!>
5651!> Important: gree-heat model crashes due to unknown reason. Green fraction
5652!> is thus set to zero (in favor of wall fraction).
5653!------------------------------------------------------------------------------!
5654    SUBROUTINE usm_green_heat_model
5655
5656
5657        IMPLICIT NONE
5658
5659        INTEGER(iwp) ::  i,j,k,l,kw, m              !< running indices
5660
5661        REAL(wp)     :: ke, lambda_h_green_sat      !< heat conductivity for saturated soil
5662        REAL(wp)     :: h_vg                        !< Van Genuchten coef. h
5663        REAL(wp)     :: drho_l_lv                   !< frequently used parameter
5664
5665        REAL(wp), DIMENSION(nzb_wall:nzt_wall) :: gtend,tend  !< tendency
5666
5667        REAL(wp), DIMENSION(nzb_wall:nzt_wall) :: root_extr_green
5668
5669        REAL(wp), DIMENSION(nzb_wall:nzt_wall+1) :: lambda_green_temp  !< temp. lambda
5670        REAL(wp), DIMENSION(nzb_wall:nzt_wall+1) :: gamma_green_temp   !< temp. gamma
5671
5672        LOGICAL :: conserve_water_content = .true.
5673
5674
5675        IF ( debug_output_timestep )  CALL debug_message( 'usm_green_heat_model', 'start' )
5676
5677        drho_l_lv = 1.0_wp / (rho_l * l_v)
5678
5679!
5680!--     For horizontal surfaces                                   
5681        !$OMP PARALLEL PRIVATE (m, i, j, k, kw, lambda_h_green_sat, ke, lambda_green_temp, gtend,  &
5682        !$OMP&                  tend, h_vg, gamma_green_temp, m_total, root_extr_green)
5683        !$OMP DO SCHEDULE (STATIC)
5684        DO  m = 1, surf_usm_h%ns
5685           IF (surf_usm_h%frac(ind_pav_green,m) > 0.0_wp) THEN
5686!
5687!--           Obtain indices
5688              i = surf_usm_h%i(m)           
5689              j = surf_usm_h%j(m)
5690              k = surf_usm_h%k(m)
5691   
5692              DO  kw = nzb_wall, nzt_wall
5693!
5694!--              Calculate volumetric heat capacity of the soil, taking
5695!--              into account water content
5696                 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)) &
5697                                      + rho_c_water * swc_h(kw,m))
5698     
5699!
5700!--              Calculate soil heat conductivity at the center of the soil
5701!--              layers
5702                 lambda_h_green_sat = lambda_h_green_sm ** (1.0_wp - swc_sat_h(kw,m)) *    &
5703                                lambda_h_water ** swc_h(kw,m)
5704     
5705                 ke = 1.0_wp + LOG10(MAX(0.1_wp,swc_h(kw,m)             &
5706                      / swc_sat_h(kw,m)))
5707     
5708                 lambda_green_temp(kw) = ke * (lambda_h_green_sat - lambda_h_green_dry) +    &
5709                                  lambda_h_green_dry
5710   
5711              ENDDO
5712              lambda_green_temp(nzt_wall+1) = lambda_green_temp(nzt_wall)
5713   
5714   
5715!
5716!--           Calculate soil heat conductivity (lambda_h) at the _stag level
5717!--           using linear interpolation. For pavement surface, the
5718!--           true pavement depth is considered
5719              DO  kw = nzb_wall, nzt_wall
5720                surf_usm_h%lambda_h_green(kw,m) = ( lambda_green_temp(kw+1) + lambda_green_temp(kw) )  &
5721                                      * 0.5_wp
5722              ENDDO
5723
5724              t_green_h(nzt_wall+1,m) = t_wall_h(nzb_wall,m)
5725!
5726!--        prognostic equation for ground/roof temperature t_green_h
5727              gtend(:) = 0.0_wp
5728              gtend(nzb_wall) = (1.0_wp / surf_usm_h%rho_c_total_green(nzb_wall,m)) *    &
5729                                         ( surf_usm_h%lambda_h_green(nzb_wall,m) * &
5730                                           ( t_green_h(nzb_wall+1,m)               &
5731                                           - t_green_h(nzb_wall,m) ) *             &
5732                                           surf_usm_h%ddz_green(nzb_wall+1,m)      &
5733                                         + surf_usm_h%wghf_eb_green(m) ) *         &
5734                                           surf_usm_h%ddz_green_stag(nzb_wall,m)
5735             
5736               DO  kw = nzb_wall+1, nzt_wall
5737                   gtend(kw) = (1.0_wp / surf_usm_h%rho_c_total_green(kw,m))       &
5738                                  * (   surf_usm_h%lambda_h_green(kw,m)            &
5739                                     * ( t_green_h(kw+1,m) - t_green_h(kw,m) )     &
5740                                     * surf_usm_h%ddz_green(kw+1,m)                &
5741                                  - surf_usm_h%lambda_h_green(kw-1,m)              &
5742                                     * ( t_green_h(kw,m) - t_green_h(kw-1,m) )     &
5743                                     * surf_usm_h%ddz_green(kw,m)                  &
5744                                    ) * surf_usm_h%ddz_green_stag(kw,m)
5745               ENDDO
5746   
5747              t_green_h_p(nzb_wall:nzt_wall,m) = t_green_h(nzb_wall:nzt_wall,m)    &
5748                                    + dt_3d * ( tsc(2)                             &
5749                                    * gtend(nzb_wall:nzt_wall) + tsc(3)            &
5750                                    * surf_usm_h%tt_green_m(nzb_wall:nzt_wall,m) )   
5751   
5752             
5753!
5754!--        calculate t_green tendencies for the next Runge-Kutta step
5755              IF ( timestep_scheme(1:5) == 'runge' )  THEN
5756                  IF ( intermediate_timestep_count == 1 )  THEN
5757                     DO  kw = nzb_wall, nzt_wall
5758                        surf_usm_h%tt_green_m(kw,m) = gtend(kw)
5759                     ENDDO
5760                  ELSEIF ( intermediate_timestep_count <                           &
5761                           intermediate_timestep_count_max )  THEN
5762                      DO  kw = nzb_wall, nzt_wall
5763                         surf_usm_h%tt_green_m(kw,m) = -9.5625_wp * gtend(kw) +    &
5764                                            5.3125_wp * surf_usm_h%tt_green_m(kw,m)
5765                      ENDDO
5766                  ENDIF
5767              ENDIF
5768
5769              DO  kw = nzb_wall, nzt_wall
5770
5771!
5772!--              Calculate soil diffusivity at the center of the soil layers
5773                 lambda_green_temp(kw) = (- b_ch * surf_usm_h%gamma_w_green_sat(kw,m) * psi_sat       &
5774                                   / swc_sat_h(kw,m) ) * ( MAX( swc_h(kw,m),    &
5775                                   wilt_h(kw,m) ) / swc_sat_h(kw,m) )**(        &
5776                                   b_ch + 2.0_wp )
5777
5778!
5779!--              Parametrization of Van Genuchten
5780                 IF ( soil_type /= 7 )  THEN
5781!
5782!--                 Calculate the hydraulic conductivity after Van Genuchten
5783!--                 (1980)
5784                    h_vg = ( ( (swc_res_h(kw,m) - swc_sat_h(kw,m)) / ( swc_res_h(kw,m) -    &
5785                               MAX( swc_h(kw,m), wilt_h(kw,m) ) ) )**(      &
5786                               surf_usm_h%n_vg_green(m) / (surf_usm_h%n_vg_green(m) - 1.0_wp ) ) - 1.0_wp  &
5787                           )**( 1.0_wp / surf_usm_h%n_vg_green(m) ) / surf_usm_h%alpha_vg_green(m)
5788
5789
5790                    gamma_green_temp(kw) = surf_usm_h%gamma_w_green_sat(kw,m) * ( ( (1.0_wp +         &
5791                                    ( surf_usm_h%alpha_vg_green(m) * h_vg )**surf_usm_h%n_vg_green(m))**(  &
5792                                    1.0_wp - 1.0_wp / surf_usm_h%n_vg_green(m) ) - (        &
5793                                    surf_usm_h%alpha_vg_green(m) * h_vg )**( surf_usm_h%n_vg_green(m)      &
5794                                    - 1.0_wp) )**2 )                         &
5795                                    / ( ( 1.0_wp + ( surf_usm_h%alpha_vg_green(m) * h_vg    &
5796                                    )**surf_usm_h%n_vg_green(m) )**( ( 1.0_wp  - 1.0_wp     &
5797                                    / surf_usm_h%n_vg_green(m) ) *( surf_usm_h%l_vg_green(m) + 2.0_wp) ) )
5798
5799!
5800!--              Parametrization of Clapp & Hornberger
5801                 ELSE
5802                    gamma_green_temp(kw) = surf_usm_h%gamma_w_green_sat(kw,m) * ( swc_h(kw,m)       &
5803                                    / swc_sat_h(kw,m) )**(2.0_wp * b_ch + 3.0_wp)
5804                 ENDIF
5805
5806              ENDDO
5807
5808!
5809!--           Prognostic equation for soil moisture content. Only performed,
5810!--           when humidity is enabled in the atmosphere
5811              IF ( humidity )  THEN
5812!
5813!--              Calculate soil diffusivity (lambda_w) at the _stag level
5814!--              using linear interpolation. To do: replace this with
5815!--              ECMWF-IFS Eq. 8.81
5816                 DO  kw = nzb_wall, nzt_wall-1
5817                   
5818                    surf_usm_h%lambda_w_green(kw,m) = ( lambda_green_temp(kw+1) + lambda_green_temp(kw) )  &
5819                                      * 0.5_wp
5820                    surf_usm_h%gamma_w_green(kw,m)  = ( gamma_green_temp(kw+1) + gamma_green_temp(kw) )    &
5821                                      * 0.5_wp
5822
5823                 ENDDO
5824
5825!
5826!--              In case of a closed bottom (= water content is conserved),
5827!--              set hydraulic conductivity to zero to that no water will be
5828!--              lost in the bottom layer.
5829                 IF ( conserve_water_content )  THEN
5830                    surf_usm_h%gamma_w_green(kw,m) = 0.0_wp
5831                 ELSE
5832                    surf_usm_h%gamma_w_green(kw,m) = gamma_green_temp(nzt_wall)
5833                 ENDIF     
5834
5835!--              The root extraction (= root_extr * qsws_veg / (rho_l     
5836!--              * l_v)) ensures the mass conservation for water. The         
5837!--              transpiration of plants equals the cumulative withdrawals by
5838!--              the roots in the soil. The scheme takes into account the
5839!--              availability of water in the soil layers as well as the root
5840!--              fraction in the respective layer. Layer with moisture below
5841!--              wilting point will not contribute, which reflects the
5842!--              preference of plants to take water from moister layers.
5843
5844!
5845!--              Calculate the root extraction (ECMWF 7.69, the sum of
5846!--              root_extr = 1). The energy balance solver guarantees a
5847!--              positive transpiration, so that there is no need for an
5848!--              additional check.
5849                 m_total = 0.0_wp
5850                 DO  kw = nzb_wall, nzt_wall
5851                     IF ( swc_h(kw,m) > wilt_h(kw,m) )  THEN
5852                        m_total = m_total + rootfr_h(kw,m) * swc_h(kw,m)
5853                     ENDIF
5854                 ENDDO 
5855
5856                 IF ( m_total > 0.0_wp )  THEN
5857                    DO  kw = nzb_wall, nzt_wall
5858                       IF ( swc_h(kw,m) > wilt_h(kw,m) )  THEN
5859                          root_extr_green(kw) = rootfr_h(kw,m) * swc_h(kw,m)      &
5860                                                          / m_total
5861                       ELSE
5862                          root_extr_green(kw) = 0.0_wp
5863                       ENDIF
5864                    ENDDO
5865                 ENDIF
5866
5867!
5868!--              Prognostic equation for soil water content m_soil.
5869                 tend(:) = 0.0_wp
5870
5871                 tend(nzb_wall) = ( surf_usm_h%lambda_w_green(nzb_wall,m) * (            &
5872                          swc_h(nzb_wall+1,m) - swc_h(nzb_wall,m) )    &
5873                          * surf_usm_h%ddz_green(nzb_wall+1,m) - surf_usm_h%gamma_w_green(nzb_wall,m) - ( &
5874                             root_extr_green(nzb_wall) * surf_usm_h%qsws_veg(m)          &
5875!                                + surf_usm_h%qsws_soil_green(m)
5876                                ) * drho_l_lv )             &
5877                               * surf_usm_h%ddz_green_stag(nzb_wall,m)
5878
5879                 DO  kw = nzb_wall+1, nzt_wall-1
5880                    tend(kw) = ( surf_usm_h%lambda_w_green(kw,m) * ( swc_h(kw+1,m)        &
5881                              - swc_h(kw,m) ) * surf_usm_h%ddz_green(kw+1,m)              &
5882                              - surf_usm_h%gamma_w_green(kw,m)                            &
5883                              - surf_usm_h%lambda_w_green(kw-1,m) * (swc_h(kw,m) -        &
5884                              swc_h(kw-1,m)) * surf_usm_h%ddz_green(kw,m)                 &
5885                              + surf_usm_h%gamma_w_green(kw-1,m) - (root_extr_green(kw)   &
5886                              * surf_usm_h%qsws_veg(m) * drho_l_lv)                       &
5887                              ) * surf_usm_h%ddz_green_stag(kw,m)
5888
5889                 ENDDO
5890                 tend(nzt_wall) = ( - surf_usm_h%gamma_w_green(nzt_wall,m)                  &
5891                                         - surf_usm_h%lambda_w_green(nzt_wall-1,m)          &
5892                                         * (swc_h(nzt_wall,m)             &
5893                                         - swc_h(nzt_wall-1,m))           &
5894                                         * surf_usm_h%ddz_green(nzt_wall,m)                 &
5895                                         + surf_usm_h%gamma_w_green(nzt_wall-1,m) - (       &
5896                                           root_extr_green(nzt_wall)               &
5897                                         * surf_usm_h%qsws_veg(m) * drho_l_lv  )   &
5898                                   ) * surf_usm_h%ddz_green_stag(nzt_wall,m)             
5899
5900                 swc_h_p(nzb_wall:nzt_wall,m) = swc_h(nzb_wall:nzt_wall,m)&
5901                                                 + dt_3d * ( tsc(2) * tend(:)   &
5902                                                 + tsc(3) * surf_usm_h%tswc_h_m(:,m) )   
5903 
5904!
5905!--              Account for dry soils (find a better solution here!)
5906                 DO  kw = nzb_wall, nzt_wall
5907                    IF ( swc_h_p(kw,m) < 0.0_wp )  swc_h_p(kw,m) = 0.0_wp
5908                 ENDDO
5909
5910!
5911!--              Calculate m_soil tendencies for the next Runge-Kutta step
5912                 IF ( timestep_scheme(1:5) == 'runge' )  THEN
5913                    IF ( intermediate_timestep_count == 1 )  THEN
5914                       DO  kw = nzb_wall, nzt_wall
5915                          surf_usm_h%tswc_h_m(kw,m) = tend(kw)
5916                       ENDDO
5917                    ELSEIF ( intermediate_timestep_count <                   &
5918                             intermediate_timestep_count_max )  THEN
5919                       DO  kw = nzb_wall, nzt_wall
5920                          surf_usm_h%tswc_h_m(kw,m) = -9.5625_wp * tend(kw) + 5.3125_wp&
5921                                   * surf_usm_h%tswc_h_m(kw,m)
5922                       ENDDO
5923                    ENDIF
5924                 ENDIF
5925              ENDIF
5926
5927           ENDIF
5928           
5929        ENDDO
5930        !$OMP END PARALLEL
5931
5932!
5933!--     For vertical surfaces     
5934        DO  l = 0, 3                             
5935           DO  m = 1, surf_usm_v(l)%ns
5936
5937              IF (surf_usm_v(l)%frac(ind_pav_green,m) > 0.0_wp) THEN
5938!
5939!-- no substrate layer for green walls / only groundbase green walls (ivy i.e.) -> green layers get same
5940!-- temperature as first wall layer
5941!-- there fore no temperature calculations for vertical green substrate layers now
5942
5943!
5944! !
5945! !--              Obtain indices
5946!                  i = surf_usm_v(l)%i(m)           
5947!                  j = surf_usm_v(l)%j(m)
5948!                  k = surf_usm_v(l)%k(m)
5949!   
5950!                  t_green_v(l)%t(nzt_wall+1,m) = t_wall_v(l)%t(nzb_wall,m)
5951! !
5952! !--              prognostic equation for green temperature t_green_v
5953!                  gtend(:) = 0.0_wp
5954!                  gtend(nzb_wall) = (1.0_wp / surf_usm_v(l)%rho_c_green(nzb_wall,m)) * &
5955!                                          ( surf_usm_v(l)%lambda_h_green(nzb_wall,m) * &
5956!                                            ( t_green_v(l)%t(nzb_wall+1,m)             &
5957!                                            - t_green_v(l)%t(nzb_wall,m) ) *           &
5958!                                            surf_usm_v(l)%ddz_green(nzb_wall+1,m)      &
5959!                                          + surf_usm_v(l)%wghf_eb(m) ) *               &
5960!                                            surf_usm_v(l)%ddz_green_stag(nzb_wall,m)
5961!               
5962!                  DO  kw = nzb_wall+1, nzt_wall
5963!                     gtend(kw) = (1.0_wp / surf_usm_v(l)%rho_c_green(kw,m))          &
5964!                               * (   surf_usm_v(l)%lambda_h_green(kw,m)              &
5965!                                 * ( t_green_v(l)%t(kw+1,m) - t_green_v(l)%t(kw,m) ) &
5966!                                 * surf_usm_v(l)%ddz_green(kw+1,m)                   &
5967!                               - surf_usm_v(l)%lambda_h(kw-1,m)                      &
5968!                                 * ( t_green_v(l)%t(kw,m) - t_green_v(l)%t(kw-1,m) ) &
5969!                                 * surf_usm_v(l)%ddz_green(kw,m) )                   &
5970!                               * surf_usm_v(l)%ddz_green_stag(kw,m)
5971!                  ENDDO
5972!   
5973!                  t_green_v_p(l)%t(nzb_wall:nzt_wall,m) =                              &
5974!                                       t_green_v(l)%t(nzb_wall:nzt_wall,m)             &
5975!                                     + dt_3d * ( tsc(2)                                &
5976!                                     * gtend(nzb_wall:nzt_wall) + tsc(3)               &
5977!                                     * surf_usm_v(l)%tt_green_m(nzb_wall:nzt_wall,m) )   
5978!   
5979! !
5980! !--              calculate t_green tendencies for the next Runge-Kutta step
5981!                  IF ( timestep_scheme(1:5) == 'runge' )  THEN
5982!                      IF ( intermediate_timestep_count == 1 )  THEN
5983!                         DO  kw = nzb_wall, nzt_wall
5984!                            surf_usm_v(l)%tt_green_m(kw,m) = gtend(kw)
5985!                         ENDDO
5986!                      ELSEIF ( intermediate_timestep_count <                           &
5987!                               intermediate_timestep_count_max )  THEN
5988!                          DO  kw = nzb_wall, nzt_wall
5989!                             surf_usm_v(l)%tt_green_m(kw,m) =                          &
5990!                                         - 9.5625_wp * gtend(kw) +                     &
5991!                                           5.3125_wp * surf_usm_v(l)%tt_green_m(kw,m)
5992!                          ENDDO
5993!                      ENDIF
5994!                  ENDIF
5995
5996                 DO  kw = nzb_wall, nzt_wall+1
5997                     t_green_v(l)%t(kw,m) = t_wall_v(l)%t(nzb_wall,m)
5998                 ENDDO
5999             
6000              ENDIF
6001
6002           ENDDO
6003        ENDDO
6004
6005        IF ( debug_output_timestep )  CALL debug_message( 'usm_green_heat_model', 'end' )
6006
6007    END SUBROUTINE usm_green_heat_model
6008
6009!------------------------------------------------------------------------------!
6010! Description:
6011! ------------
6012!> Parin for &usm_par for urban surface model
6013!------------------------------------------------------------------------------!
6014    SUBROUTINE usm_parin
6015
6016       IMPLICIT NONE
6017
6018       CHARACTER (LEN=80) ::  line  !< string containing current line of file PARIN
6019
6020       NAMELIST /urban_surface_par/                                            &
6021                           building_type,                                      &
6022                           land_category,                                      &
6023                           naheatlayers,                                       &
6024                           pedestrian_category,                                &
6025                           roughness_concrete,                                 &
6026                           read_wall_temp_3d,                                  &
6027                           roof_category,                                      &
6028                           urban_surface,                                      &
6029                           usm_anthropogenic_heat,                             &
6030                           usm_material_model,                                 &
6031                           wall_category,                                      &
6032                           wall_inner_temperature,                             &
6033                           roof_inner_temperature,                             &
6034                           soil_inner_temperature,                             &
6035                           window_inner_temperature,                           &
6036                           usm_wall_mod
6037
6038       NAMELIST /urban_surface_parameters/                                     &
6039                           building_type,                                      &
6040                           land_category,                                      &
6041                           naheatlayers,                                       &
6042                           pedestrian_category,                                &
6043                           roughness_concrete,                                 &
6044                           read_wall_temp_3d,                                  &
6045                           roof_category,                                      &
6046                           urban_surface,                                      &
6047                           usm_anthropogenic_heat,                             &
6048                           usm_material_model,                                 &
6049                           wall_category,                                      &
6050                           wall_inner_temperature,                             &
6051                           roof_inner_temperature,                             &
6052                           soil_inner_temperature,                             &
6053                           window_inner_temperature,                           &
6054                           usm_wall_mod
6055                           
6056 
6057!
6058!--    Try to find urban surface model package
6059       REWIND ( 11 )
6060       line = ' '
6061       DO WHILE ( INDEX( line, '&urban_surface_parameters' ) == 0 )
6062          READ ( 11, '(A)', END=12 )  line
6063       ENDDO
6064       BACKSPACE ( 11 )
6065
6066!
6067!--    Read user-defined namelist
6068       READ ( 11, urban_surface_parameters, ERR = 10 )
6069
6070!
6071!--    Set flag that indicates that the urban surface model is switched on
6072       urban_surface = .TRUE.
6073
6074       GOTO 14
6075
6076 10    BACKSPACE( 11 )
6077       READ( 11 , '(A)') line
6078       CALL parin_fail_message( 'urban_surface_parameters', line )
6079!
6080!--    Try to find old namelist
6081 12    REWIND ( 11 )
6082       line = ' '
6083       DO WHILE ( INDEX( line, '&urban_surface_par' ) == 0 )
6084          READ ( 11, '(A)', END=14 )  line
6085       ENDDO
6086       BACKSPACE ( 11 )
6087
6088!
6089!--    Read user-defined namelist
6090       READ ( 11, urban_surface_par, ERR = 13, END = 14 )
6091
6092       message_string = 'namelist urban_surface_par is deprecated and will be ' // &
6093                     'removed in near future. Please use namelist ' //   &
6094                     'urban_surface_parameters instead'
6095       CALL message( 'usm_parin', 'PA0487', 0, 1, 0, 6, 0 )
6096
6097!
6098!--    Set flag that indicates that the urban surface model is switched on
6099       urban_surface = .TRUE.
6100
6101       GOTO 14
6102
6103 13    BACKSPACE( 11 )
6104       READ( 11 , '(A)') line
6105       CALL parin_fail_message( 'urban_surface_par', line )
6106
6107
6108 14    CONTINUE
6109
6110
6111    END SUBROUTINE usm_parin
6112
6113 
6114!------------------------------------------------------------------------------!
6115! Description:
6116! ------------
6117!
6118!> This subroutine is part of the urban surface model.
6119!> It reads daily heat produced by anthropogenic sources
6120!> and the diurnal cycle of the heat.
6121!------------------------------------------------------------------------------!
6122    SUBROUTINE usm_read_anthropogenic_heat
6123   
6124        INTEGER(iwp)                  :: i,j,k,ii  !< running indices
6125        REAL(wp)                      :: heat      !< anthropogenic heat
6126
6127!
6128!--     allocation of array of sources of anthropogenic heat and their diural profile
6129        ALLOCATE( aheat(naheatlayers,nys:nyn,nxl:nxr) )
6130        ALLOCATE( aheatprof(naheatlayers,0:24) )
6131
6132!
6133!--     read daily amount of heat and its daily cycle
6134        aheat = 0.0_wp
6135        DO  ii = 0, io_blocks-1
6136            IF ( ii == io_group )  THEN
6137
6138!--             open anthropogenic heat file
6139                OPEN( 151, file='ANTHROPOGENIC_HEAT'//TRIM(coupling_char), action='read', &
6140                           status='old', form='formatted', err=11 )
6141                i = 0
6142                j = 0
6143                DO
6144                    READ( 151, *, err=12, end=13 )  i, j, k, heat
6145                    IF ( i >= nxl  .AND.  i <= nxr  .AND.  j >= nys  .AND.  j <= nyn )  THEN
6146                        IF ( k <= naheatlayers  .AND.  k > get_topography_top_index_ji( j, i, 's' ) )  THEN
6147!--                         write heat into the array
6148                            aheat(k,j,i) = heat
6149                        ENDIF
6150                    ENDIF
6151                    CYCLE
6152 12                 WRITE(message_string,'(a,2i4)') 'error in file ANTHROPOGENIC_HEAT'//TRIM(coupling_char)//' after line ',i,j
6153                    CALL message( 'usm_read_anthropogenic_heat', 'PA0515', 0, 1, 0, 6, 0 )
6154                ENDDO
6155 13             CLOSE(151)
6156                CYCLE
6157 11             message_string = 'file ANTHROPOGENIC_HEAT'//TRIM(coupling_char)//' does not exist'
6158                CALL message( 'usm_read_anthropogenic_heat', 'PA0516', 1, 2, 0, 6, 0 )
6159            ENDIF
6160           
6161#if defined( __parallel )
6162            CALL MPI_BARRIER( comm2d, ierr )
6163#endif
6164        ENDDO
6165       
6166!
6167!--     read diurnal profiles of heat sources
6168        aheatprof = 0.0_wp
6169        DO  ii = 0, io_blocks-1
6170            IF ( ii == io_group )  THEN
6171!
6172!--             open anthropogenic heat profile file
6173                OPEN( 151, file='ANTHROPOGENIC_HEAT_PROFILE'//TRIM(coupling_char), action='read', &
6174                           status='old', form='formatted', err=21 )
6175                i = 0
6176                DO
6177                    READ( 151, *, err=22, end=23 )  i, k, heat
6178                    IF ( i >= 0  .AND.  i <= 24  .AND.  k <= naheatlayers )  THEN
6179!--                     write heat into the array
6180                        aheatprof(k,i) = heat
6181                    ENDIF
6182                    CYCLE
6183 22                 WRITE(message_string,'(a,i4)') 'error in file ANTHROPOGENIC_HEAT_PROFILE'// &
6184                                                     TRIM(coupling_char)//' after line ',i
6185                    CALL message( 'usm_read_anthropogenic_heat', 'PA0517', 0, 1, 0, 6, 0 )
6186                ENDDO
6187                aheatprof(:,24) = aheatprof(:,0)
6188 23             CLOSE(151)
6189                CYCLE
6190 21             message_string = 'file ANTHROPOGENIC_HEAT_PROFILE'//TRIM(coupling_char)//' does not exist'
6191                CALL message( 'usm_read_anthropogenic_heat', 'PA0518', 1, 2, 0, 6, 0 )
6192            ENDIF
6193           
6194#if defined( __parallel )
6195            CALL MPI_BARRIER( comm2d, ierr )
6196#endif
6197        ENDDO
6198       
6199    END SUBROUTINE usm_read_anthropogenic_heat
6200   
6201
6202!------------------------------------------------------------------------------!
6203! Description:
6204! ------------
6205!> Soubroutine reads t_surf and t_wall data from restart files
6206!------------------------------------------------------------------------------!
6207    SUBROUTINE usm_rrd_local( k, nxlf, nxlc, nxl_on_file, nxrf, nxr_on_file, nynf, nyn_on_file,    &
6208                              nysf, nysc, nys_on_file, found )
6209
6210
6211       USE control_parameters,                                                 &
6212           ONLY: length, restart_string
6213           
6214       IMPLICIT NONE
6215
6216       INTEGER(iwp)       ::  k                 !< running index over previous input files covering current local domain
6217       INTEGER(iwp)       ::  l                 !< index variable for surface type
6218       INTEGER(iwp)       ::  ns_h_on_file_usm  !< number of horizontal surface elements (urban type) on file
6219       INTEGER(iwp)       ::  nxlc              !< index of left boundary on current subdomain
6220       INTEGER(iwp)       ::  nxlf              !< index of left boundary on former subdomain
6221       INTEGER(iwp)       ::  nxl_on_file       !< index of left boundary on former local domain
6222       INTEGER(iwp)       ::  nxrf              !< index of right boundary on former subdomain
6223       INTEGER(iwp)       ::  nxr_on_file       !< index of right boundary on former local domain
6224       INTEGER(iwp)       ::  nynf              !< index of north boundary on former subdomain
6225       INTEGER(iwp)       ::  nyn_on_file       !< index of north boundary on former local domain
6226       INTEGER(iwp)       ::  nysc              !< index of south boundary on current subdomain
6227       INTEGER(iwp)       ::  nysf              !< index of south boundary on former subdomain
6228       INTEGER(iwp)       ::  nys_on_file       !< index of south boundary on former local domain
6229       
6230       INTEGER(iwp)       ::  ns_v_on_file_usm(0:3)  !< number of vertical surface elements (urban type) on file
6231       
6232       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  start_index_on_file 
6233       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  end_index_on_file
6234
6235       LOGICAL, INTENT(OUT)  ::  found 
6236!!!    suehring: Why the SAVE attribute?       
6237       REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE   ::  tmp_surf_wall_h
6238       REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE   ::  tmp_surf_window_h
6239       REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE   ::  tmp_surf_green_h
6240       REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE   ::  tmp_surf_waste_h
6241       
6242       REAL(wp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  tmp_wall_h
6243       REAL(wp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  tmp_window_h
6244       REAL(wp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  tmp_green_h
6245       
6246       TYPE( t_surf_vertical ), DIMENSION(0:3), SAVE ::  tmp_surf_wall_v
6247       TYPE( t_surf_vertical ), DIMENSION(0:3), SAVE ::  tmp_surf_window_v
6248       TYPE( t_surf_vertical ), DIMENSION(0:3), SAVE ::  tmp_surf_green_v
6249       TYPE( t_surf_vertical ), DIMENSION(0:3), SAVE ::  tmp_surf_waste_v
6250       
6251       TYPE( t_wall_vertical ), DIMENSION(0:3), SAVE ::  tmp_wall_v
6252       TYPE( t_wall_vertical ), DIMENSION(0:3), SAVE ::  tmp_window_v
6253       TYPE( t_wall_vertical ), DIMENSION(0:3), SAVE ::  tmp_green_v
6254
6255
6256       found = .TRUE.
6257
6258
6259          SELECT CASE ( restart_string(1:length) ) 
6260
6261             CASE ( 'ns_h_on_file_usm') 
6262                IF ( k == 1 )  THEN
6263                   READ ( 13 ) ns_h_on_file_usm
6264               
6265                   IF ( ALLOCATED( tmp_surf_wall_h ) ) DEALLOCATE( tmp_surf_wall_h )
6266                   IF ( ALLOCATED( tmp_wall_h ) ) DEALLOCATE( tmp_wall_h ) 
6267                   IF ( ALLOCATED( tmp_surf_window_h ) )                       &
6268                      DEALLOCATE( tmp_surf_window_h ) 
6269                   IF ( ALLOCATED( tmp_window_h) ) DEALLOCATE( tmp_window_h ) 
6270                   IF ( ALLOCATED( tmp_surf_green_h) )                         &
6271                      DEALLOCATE( tmp_surf_green_h ) 
6272                   IF ( ALLOCATED( tmp_green_h) ) DEALLOCATE( tmp_green_h )
6273                   IF ( ALLOCATED( tmp_surf_waste_h) )                         &
6274                      DEALLOCATE( tmp_surf_waste_h )
6275 
6276!
6277!--                Allocate temporary arrays for reading data on file. Note,
6278!--                the size of allocated surface elements do not necessarily
6279!--                need  to match the size of present surface elements on
6280!--                current processor, as the number of processors between
6281!--                restarts can change.
6282                   ALLOCATE( tmp_surf_wall_h(1:ns_h_on_file_usm) )
6283                   ALLOCATE( tmp_wall_h(nzb_wall:nzt_wall+1,                   &
6284                                        1:ns_h_on_file_usm) )
6285                   ALLOCATE( tmp_surf_window_h(1:ns_h_on_file_usm) )
6286                   ALLOCATE( tmp_window_h(nzb_wall:nzt_wall+1,                 &
6287                                          1:ns_h_on_file_usm) )
6288                   ALLOCATE( tmp_surf_green_h(1:ns_h_on_file_usm) )
6289                   ALLOCATE( tmp_green_h(nzb_wall:nzt_wall+1,                  &
6290                                         1:ns_h_on_file_usm) )
6291                   ALLOCATE( tmp_surf_waste_h(1:ns_h_on_file_usm) )
6292
6293                ENDIF
6294
6295             CASE ( 'ns_v_on_file_usm')
6296                IF ( k == 1 )  THEN
6297                   READ ( 13 ) ns_v_on_file_usm 
6298
6299                   DO  l = 0, 3
6300                      IF ( ALLOCATED( tmp_surf_wall_v(l)%t ) )                 &
6301                         DEALLOCATE( tmp_surf_wall_v(l)%t )
6302                      IF ( ALLOCATED( tmp_wall_v(l)%t ) )                      &
6303                         DEALLOCATE( tmp_wall_v(l)%t )
6304                      IF ( ALLOCATED( tmp_surf_window_v(l)%t ) )               & 
6305                         DEALLOCATE( tmp_surf_window_v(l)%t )
6306                      IF ( ALLOCATED( tmp_window_v(l)%t ) )                    &
6307                         DEALLOCATE( tmp_window_v(l)%t )
6308                      IF ( ALLOCATED( tmp_surf_green_v(l)%t ) )                &
6309                         DEALLOCATE( tmp_surf_green_v(l)%t )
6310                      IF ( ALLOCATED( tmp_green_v(l)%t ) )                     &
6311                         DEALLOCATE( tmp_green_v(l)%t )
6312                      IF ( ALLOCATED( tmp_surf_waste_v(l)%t ) )                &
6313                         DEALLOCATE( tmp_surf_waste_v(l)%t )
6314                   ENDDO 
6315
6316!
6317!--                Allocate temporary arrays for reading data on file. Note,
6318!--                the size of allocated surface elements do not necessarily
6319!--                need to match the size of present surface elements on
6320!--                current processor, as the number of processors between
6321!--                restarts can change.
6322                   DO  l = 0, 3
6323                      ALLOCATE( tmp_surf_wall_v(l)%t(1:ns_v_on_file_usm(l)) )
6324                      ALLOCATE( tmp_wall_v(l)%t(nzb_wall:nzt_wall+1,           &
6325                                                1:ns_v_on_file_usm(l) ) )
6326                      ALLOCATE( tmp_surf_window_v(l)%t(1:ns_v_on_file_usm(l)) )
6327                      ALLOCATE( tmp_window_v(l)%t(nzb_wall:nzt_wall+1,         & 
6328                                                  1:ns_v_on_file_usm(l) ) )
6329                      ALLOCATE( tmp_surf_green_v(l)%t(1:ns_v_on_file_usm(l)) )
6330                      ALLOCATE( tmp_green_v(l)%t(nzb_wall:nzt_wall+1,          &
6331                                                 1:ns_v_on_file_usm(l) ) )
6332                      ALLOCATE( tmp_surf_waste_v(l)%t(1:ns_v_on_file_usm(l)) )
6333                   ENDDO
6334
6335                ENDIF   
6336         
6337             CASE ( 'usm_start_index_h', 'usm_start_index_v'  )   
6338                IF ( k == 1 )  THEN
6339
6340                   IF ( ALLOCATED( start_index_on_file ) )                     &
6341                      DEALLOCATE( start_index_on_file )
6342
6343                   ALLOCATE ( start_index_on_file(nys_on_file:nyn_on_file,     &
6344                                                  nxl_on_file:nxr_on_file) )
6345
6346                   READ ( 13 )  start_index_on_file
6347
6348                ENDIF
6349               
6350             CASE ( 'usm_end_index_h', 'usm_end_index_v' )   
6351                IF ( k == 1 )  THEN
6352
6353                   IF ( ALLOCATED( end_index_on_file ) )                       &
6354                      DEALLOCATE( end_index_on_file )
6355
6356                   ALLOCATE ( end_index_on_file(nys_on_file:nyn_on_file,       &
6357                                                nxl_on_file:nxr_on_file) )
6358
6359                   READ ( 13 )  end_index_on_file
6360
6361                ENDIF
6362         
6363             CASE ( 't_surf_wall_h' )
6364                IF ( k == 1 )  THEN
6365                   IF ( .NOT.  ALLOCATED( t_surf_wall_h_1 ) )                  &
6366                      ALLOCATE( t_surf_wall_h_1(1:surf_usm_h%ns) )
6367                   READ ( 13 )  tmp_surf_wall_h
6368                ENDIF             
6369                CALL surface_restore_elements(                                 &
6370                                        t_surf_wall_h_1, tmp_surf_wall_h,      &
6371                                        surf_usm_h%start_index,                &
6372                                        start_index_on_file,                   &
6373                                        end_index_on_file,                     &
6374                                        nxlc, nysc,                            &
6375                                        nxlf, nxrf, nysf, nynf,                &
6376                                        nys_on_file, nyn_on_file,              &
6377                                        nxl_on_file,nxr_on_file )
6378
6379             CASE ( 't_surf_wall_v(0)' )
6380                IF ( k == 1 )  THEN
6381                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(0)%t ) )             &
6382                      ALLOCATE( t_surf_wall_v_1(0)%t(1:surf_usm_v(0)%ns) )
6383                   READ ( 13 )  tmp_surf_wall_v(0)%t
6384                ENDIF
6385                CALL surface_restore_elements(                                 &
6386                                        t_surf_wall_v_1(0)%t, tmp_surf_wall_v(0)%t,      &
6387                                        surf_usm_v(0)%start_index,             & 
6388                                        start_index_on_file,                   &
6389                                        end_index_on_file,                     &
6390                                        nxlc, nysc,                            &
6391                                        nxlf, nxrf, nysf, nynf,                &
6392                                        nys_on_file, nyn_on_file,              &
6393                                        nxl_on_file,nxr_on_file )
6394                     
6395             CASE ( 't_surf_wall_v(1)' )
6396                IF ( k == 1 )  THEN
6397                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(1)%t ) )             &
6398                      ALLOCATE( t_surf_wall_v_1(1)%t(1:surf_usm_v(1)%ns) )
6399                   READ ( 13 )  tmp_surf_wall_v(1)%t
6400                ENDIF
6401                CALL surface_restore_elements(                                 &
6402                                        t_surf_wall_v_1(1)%t, tmp_surf_wall_v(1)%t,      &
6403                                        surf_usm_v(1)%start_index,             & 
6404                                        start_index_on_file,                   &
6405                                        end_index_on_file,                     &
6406                                        nxlc, nysc,                            &
6407                                        nxlf, nxrf, nysf, nynf,                &
6408                                        nys_on_file, nyn_on_file,              &
6409                                        nxl_on_file,nxr_on_file )
6410
6411             CASE ( 't_surf_wall_v(2)' )
6412                IF ( k == 1 )  THEN
6413                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(2)%t ) )             &
6414                      ALLOCATE( t_surf_wall_v_1(2)%t(1:surf_usm_v(2)%ns) )
6415                   READ ( 13 )  tmp_surf_wall_v(2)%t
6416                ENDIF
6417                CALL surface_restore_elements(                                 &
6418                                        t_surf_wall_v_1(2)%t, tmp_surf_wall_v(2)%t,      &
6419                                        surf_usm_v(2)%start_index,             & 
6420                                        start_index_on_file,                   &
6421                                        end_index_on_file,                     &
6422                                        nxlc, nysc,                            &
6423                                        nxlf, nxrf, nysf, nynf,                &
6424                                        nys_on_file, nyn_on_file,              &
6425                                        nxl_on_file,nxr_on_file )
6426                     
6427             CASE ( 't_surf_wall_v(3)' )
6428                IF ( k == 1 )  THEN
6429                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(3)%t ) )             &
6430                      ALLOCATE( t_surf_wall_v_1(3)%t(1:surf_usm_v(3)%ns) )
6431                   READ ( 13 )  tmp_surf_wall_v(3)%t
6432                ENDIF
6433                CALL surface_restore_elements(                                 &
6434                                        t_surf_wall_v_1(3)%t, tmp_surf_wall_v(3)%t,      &
6435                                        surf_usm_v(3)%start_index,             & 
6436                                        start_index_on_file,                   &
6437                                        end_index_on_file,                     &
6438                                        nxlc, nysc,                            &
6439                                        nxlf, nxrf, nysf, nynf,                &
6440                                        nys_on_file, nyn_on_file,              &
6441                                        nxl_on_file,nxr_on_file )
6442
6443             CASE ( 't_surf_green_h' )
6444                IF ( k == 1 )  THEN
6445                   IF ( .NOT.  ALLOCATED( t_surf_green_h_1 ) )                 &
6446                      ALLOCATE( t_surf_green_h_1(1:surf_usm_h%ns) )
6447                   READ ( 13 )  tmp_surf_green_h
6448                ENDIF
6449                CALL surface_restore_elements(                                 &
6450                                        t_surf_green_h_1, tmp_surf_green_h,    &
6451                                        surf_usm_h%start_index,                & 
6452                                        start_index_on_file,                   &
6453                                        end_index_on_file,                     &
6454                                        nxlc, nysc,                            &
6455                                        nxlf, nxrf, nysf, nynf,                &
6456                                        nys_on_file, nyn_on_file,              &
6457                                        nxl_on_file,nxr_on_file )
6458
6459             CASE ( 't_surf_green_v(0)' )
6460                IF ( k == 1 )  THEN
6461                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(0)%t ) )            &
6462                      ALLOCATE( t_surf_green_v_1(0)%t(1:surf_usm_v(0)%ns) )
6463                   READ ( 13 )  tmp_surf_green_v(0)%t
6464                ENDIF
6465                CALL surface_restore_elements(                                 &
6466                                        t_surf_green_v_1(0)%t,                 &
6467                                        tmp_surf_green_v(0)%t,                 &
6468                                        surf_usm_v(0)%start_index,             & 
6469                                        start_index_on_file,                   &
6470                                        end_index_on_file,                     &
6471                                        nxlc, nysc,                            &
6472                                        nxlf, nxrf, nysf, nynf,                &
6473                                        nys_on_file, nyn_on_file,              &
6474                                        nxl_on_file,nxr_on_file )
6475                   
6476             CASE ( 't_surf_green_v(1)' )
6477                IF ( k == 1 )  THEN
6478                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(1)%t ) )            &
6479                      ALLOCATE( t_surf_green_v_1(1)%t(1:surf_usm_v(1)%ns) )
6480                   READ ( 13 )  tmp_surf_green_v(1)%t
6481                ENDIF
6482                CALL surface_restore_elements(                                 &
6483                                        t_surf_green_v_1(1)%t,                 &
6484                                        tmp_surf_green_v(1)%t,                 &
6485                                        surf_usm_v(1)%start_index,             & 
6486                                        start_index_on_file,                   &
6487                                        end_index_on_file,                     &
6488                                        nxlc, nysc,                            &
6489                                        nxlf, nxrf, nysf, nynf,                &
6490                                        nys_on_file, nyn_on_file,              &
6491                                        nxl_on_file,nxr_on_file )
6492
6493             CASE ( 't_surf_green_v(2)' )
6494                IF ( k == 1 )  THEN
6495                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(2)%t ) )            &
6496                      ALLOCATE( t_surf_green_v_1(2)%t(1:surf_usm_v(2)%ns) )
6497                   READ ( 13 )  tmp_surf_green_v(2)%t
6498                ENDIF
6499                CALL surface_restore_elements(                                 &
6500                                        t_surf_green_v_1(2)%t,                 &
6501                                        tmp_surf_green_v(2)%t,                 &
6502                                        surf_usm_v(2)%start_index,             & 
6503                                        start_index_on_file,                   &
6504                                        end_index_on_file,                     &
6505                                        nxlc, nysc,                            &
6506                                        nxlf, nxrf, nysf, nynf,                &
6507                                        nys_on_file, nyn_on_file,              &
6508                                        nxl_on_file,nxr_on_file )
6509                   
6510             CASE ( 't_surf_green_v(3)' )
6511                IF ( k == 1 )  THEN
6512                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(3)%t ) )            &
6513                      ALLOCATE( t_surf_green_v_1(3)%t(1:surf_usm_v(3)%ns) )
6514                   READ ( 13 )  tmp_surf_green_v(3)%t
6515                ENDIF
6516                CALL surface_restore_elements(                                 &
6517                                        t_surf_green_v_1(3)%t,                 & 
6518                                        tmp_surf_green_v(3)%t,                 &
6519                                        surf_usm_v(3)%start_index,             & 
6520                                        start_index_on_file,                   &
6521                                        end_index_on_file,                     &
6522                                        nxlc, nysc,                            &
6523                                        nxlf, nxrf, nysf, nynf,                &
6524                                        nys_on_file, nyn_on_file,              &
6525                                        nxl_on_file,nxr_on_file )
6526
6527             CASE ( 't_surf_window_h' )
6528                IF ( k == 1 )  THEN
6529                   IF ( .NOT.  ALLOCATED( t_surf_window_h_1 ) )                &
6530                      ALLOCATE( t_surf_window_h_1(1:surf_usm_h%ns) )
6531                   READ ( 13 )  tmp_surf_window_h
6532                ENDIF
6533                CALL surface_restore_elements(                                 &
6534                                        t_surf_window_h_1,                     &
6535                                        tmp_surf_window_h,                     &
6536                                        surf_usm_h%start_index,                & 
6537                                        start_index_on_file,                   &
6538                                        end_index_on_file,                     &
6539                                        nxlc, nysc,                            &
6540                                        nxlf, nxrf, nysf, nynf,                &
6541                                        nys_on_file, nyn_on_file,              &
6542                                        nxl_on_file,nxr_on_file )
6543
6544             CASE ( 't_surf_window_v(0)' )
6545                IF ( k == 1 )  THEN
6546                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(0)%t ) )           &
6547                      ALLOCATE( t_surf_window_v_1(0)%t(1:surf_usm_v(0)%ns) )
6548                   READ ( 13 )  tmp_surf_window_v(0)%t
6549                ENDIF
6550                CALL surface_restore_elements(                                 &
6551                                        t_surf_window_v_1(0)%t,                &
6552                                        tmp_surf_window_v(0)%t,                &
6553                                        surf_usm_v(0)%start_index,             & 
6554                                        start_index_on_file,                   &
6555                                        end_index_on_file,                     &
6556                                        nxlc, nysc,                            &
6557                                        nxlf, nxrf, nysf, nynf,                &
6558                                        nys_on_file, nyn_on_file,              &
6559                                        nxl_on_file,nxr_on_file )
6560                   
6561             CASE ( 't_surf_window_v(1)' )
6562                IF ( k == 1 )  THEN
6563                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(1)%t ) )           &
6564                      ALLOCATE( t_surf_window_v_1(1)%t(1:surf_usm_v(1)%ns) )
6565                   READ ( 13 )  tmp_surf_window_v(1)%t
6566                ENDIF
6567                CALL surface_restore_elements(                                 &
6568                                        t_surf_window_v_1(1)%t,                &
6569                                        tmp_surf_window_v(1)%t,                &
6570                                        surf_usm_v(1)%start_index,             & 
6571                                        start_index_on_file,                   &
6572                                        end_index_on_file,                     &
6573                                        nxlc, nysc,                            &
6574                                        nxlf, nxrf, nysf, nynf,                &
6575                                        nys_on_file, nyn_on_file,              &
6576                                        nxl_on_file,nxr_on_file )
6577
6578             CASE ( 't_surf_window_v(2)' )
6579                IF ( k == 1 )  THEN
6580                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(2)%t ) )           &
6581                      ALLOCATE( t_surf_window_v_1(2)%t(1:surf_usm_v(2)%ns) )
6582                   READ ( 13 )  tmp_surf_window_v(2)%t
6583                ENDIF
6584                CALL surface_restore_elements(                                 &
6585                                        t_surf_window_v_1(2)%t,                & 
6586                                        tmp_surf_window_v(2)%t,                &
6587                                        surf_usm_v(2)%start_index,             & 
6588                                        start_index_on_file,                   &
6589                                        end_index_on_file,                     &
6590                                        nxlc, nysc,                            &
6591                                        nxlf, nxrf, nysf, nynf,                &
6592                                        nys_on_file, nyn_on_file,              &
6593                                        nxl_on_file,nxr_on_file )
6594                   
6595             CASE ( 't_surf_window_v(3)' )
6596                IF ( k == 1 )  THEN
6597                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(3)%t ) )           &
6598                      ALLOCATE( t_surf_window_v_1(3)%t(1:surf_usm_v(3)%ns) )
6599                   READ ( 13 )  tmp_surf_window_v(3)%t
6600                ENDIF
6601                CALL surface_restore_elements(                                 &
6602                                        t_surf_window_v_1(3)%t,                & 
6603                                        tmp_surf_window_v(3)%t,                &
6604                                        surf_usm_v(3)%start_index,             & 
6605                                        start_index_on_file,                   &
6606                                        end_index_on_file,                     &
6607                                        nxlc, nysc,                            &
6608                                        nxlf, nxrf, nysf, nynf,                &
6609                                        nys_on_file, nyn_on_file,              &
6610                                        nxl_on_file,nxr_on_file )
6611
6612             CASE ( 'waste_heat_h' )
6613                IF ( k == 1 )  THEN
6614                   IF ( .NOT.  ALLOCATED( surf_usm_h%waste_heat ) )            &
6615                      ALLOCATE( surf_usm_h%waste_heat(1:surf_usm_h%ns) )
6616                   READ ( 13 )  tmp_surf_waste_h
6617                ENDIF             
6618                CALL surface_restore_elements(                                 &
6619                                        surf_usm_h%waste_heat,                 &
6620                                        tmp_surf_waste_h,                      &
6621                                        surf_usm_h%start_index,                &
6622                                        start_index_on_file,                   &
6623                                        end_index_on_file,                     &
6624                                        nxlc, nysc,                            &
6625                                        nxlf, nxrf, nysf, nynf,                &
6626                                        nys_on_file, nyn_on_file,              &
6627                                        nxl_on_file,nxr_on_file )                 
6628                                       
6629             CASE ( 'waste_heat_v(0)' )
6630                IF ( k == 1 )  THEN
6631                   IF ( .NOT.  ALLOCATED( surf_usm_v(0)%waste_heat ) )         &
6632                      ALLOCATE( surf_usm_v(0)%waste_heat(1:surf_usm_v(0)%ns) )
6633                   READ ( 13 )  tmp_surf_waste_v(0)%t
6634                ENDIF
6635                CALL surface_restore_elements(                                 &
6636                                        surf_usm_v(0)%waste_heat,              &
6637                                        tmp_surf_waste_v(0)%t,                 &
6638                                        surf_usm_v(0)%start_index,             & 
6639                                        start_index_on_file,                   &
6640                                        end_index_on_file,                     &
6641                                        nxlc, nysc,                            &
6642                                        nxlf, nxrf, nysf, nynf,                &
6643                                        nys_on_file, nyn_on_file,              &
6644                                        nxl_on_file,nxr_on_file )
6645                     
6646             CASE ( 'waste_heat_v(1)' )
6647                IF ( k == 1 )  THEN
6648                   IF ( .NOT.  ALLOCATED( surf_usm_v(1)%waste_heat ) )         &
6649                      ALLOCATE( surf_usm_v(1)%waste_heat(1:surf_usm_v(1)%ns) )
6650                   READ ( 13 )  tmp_surf_waste_v(1)%t
6651                ENDIF
6652                CALL surface_restore_elements(                                 &
6653                                        surf_usm_v(1)%waste_heat,              &
6654                                        tmp_surf_waste_v(1)%t,                 &
6655                                        surf_usm_v(1)%start_index,             & 
6656                                        start_index_on_file,                   &
6657                                        end_index_on_file,                     &
6658                                        nxlc, nysc,                            &
6659                                        nxlf, nxrf, nysf, nynf,                &
6660                                        nys_on_file, nyn_on_file,              &
6661                                        nxl_on_file,nxr_on_file )
6662
6663             CASE ( 'waste_heat_v(2)' )
6664                IF ( k == 1 )  THEN
6665                   IF ( .NOT.  ALLOCATED( surf_usm_v(2)%waste_heat ) )         &
6666                      ALLOCATE( surf_usm_v(2)%waste_heat(1:surf_usm_v(2)%ns) )
6667                   READ ( 13 )  tmp_surf_waste_v(2)%t
6668                ENDIF
6669                CALL surface_restore_elements(                                 &
6670                                        surf_usm_v(2)%waste_heat,              &
6671                                        tmp_surf_waste_v(2)%t,                 &
6672                                        surf_usm_v(2)%start_index,             & 
6673                                        start_index_on_file,                   &
6674                                        end_index_on_file,                     &
6675                                        nxlc, nysc,                            &
6676                                        nxlf, nxrf, nysf, nynf,                &
6677                                        nys_on_file, nyn_on_file,              &
6678                                        nxl_on_file,nxr_on_file )
6679                     
6680             CASE ( 'waste_heat_v(3)' )
6681                IF ( k == 1 )  THEN
6682                   IF ( .NOT.  ALLOCATED( surf_usm_v(3)%waste_heat ) )         &
6683                      ALLOCATE( surf_usm_v(3)%waste_heat(1:surf_usm_v(3)%ns) )
6684                   READ ( 13 )  tmp_surf_waste_v(3)%t
6685                ENDIF
6686                CALL surface_restore_elements(                                 &
6687                                        surf_usm_v(3)%waste_heat,              &
6688                                        tmp_surf_waste_v(3)%t,                 &
6689                                        surf_usm_v(3)%start_index,             & 
6690                                        start_index_on_file,                   &
6691                                        end_index_on_file,                     &
6692                                        nxlc, nysc,                            &
6693                                        nxlf, nxrf, nysf, nynf,                &
6694                                        nys_on_file, nyn_on_file,              &
6695                                        nxl_on_file,nxr_on_file )
6696
6697             CASE ( 't_wall_h' )
6698                IF ( k == 1 )  THEN
6699                   IF ( .NOT.  ALLOCATED( t_wall_h_1 ) )                       &
6700                      ALLOCATE( t_wall_h_1(nzb_wall:nzt_wall+1,                &
6701                                           1:surf_usm_h%ns) )
6702                   READ ( 13 )  tmp_wall_h
6703                ENDIF
6704                CALL surface_restore_elements(                                 &
6705                                        t_wall_h_1, tmp_wall_h,                &
6706                                        surf_usm_h%start_index,                & 
6707                                        start_index_on_file,                   &
6708                                        end_index_on_file,                     &
6709                                        nxlc, nysc,                            &
6710                                        nxlf, nxrf, nysf, nynf,                &
6711                                        nys_on_file, nyn_on_file,              &
6712                                        nxl_on_file,nxr_on_file )
6713
6714             CASE ( 't_wall_v(0)' )
6715                IF ( k == 1 )  THEN
6716                   IF ( .NOT.  ALLOCATED( t_wall_v_1(0)%t ) )                  &
6717                      ALLOCATE( t_wall_v_1(0)%t(nzb_wall:nzt_wall+1,           &
6718                                                1:surf_usm_v(0)%ns) )
6719                   READ ( 13 )  tmp_wall_v(0)%t
6720                ENDIF
6721                CALL surface_restore_elements(                                 &
6722                                        t_wall_v_1(0)%t, tmp_wall_v(0)%t,      &
6723                                        surf_usm_v(0)%start_index,             & 
6724                                        start_index_on_file,                   &
6725                                        end_index_on_file,                     &
6726                                        nxlc, nysc,                            &
6727                                        nxlf, nxrf, nysf, nynf,                &
6728                                        nys_on_file, nyn_on_file,              &
6729                                        nxl_on_file,nxr_on_file )
6730
6731             CASE ( 't_wall_v(1)' )
6732                IF ( k == 1 )  THEN
6733                   IF ( .NOT.  ALLOCATED( t_wall_v_1(1)%t ) )                  &
6734                      ALLOCATE( t_wall_v_1(1)%t(nzb_wall:nzt_wall+1,           &
6735                                                1:surf_usm_v(1)%ns) )
6736                   READ ( 13 )  tmp_wall_v(1)%t
6737                ENDIF
6738                CALL surface_restore_elements(                                 &
6739                                        t_wall_v_1(1)%t, tmp_wall_v(1)%t,      &
6740                                        surf_usm_v(1)%start_index,             & 
6741                                        start_index_on_file,                   &
6742                                        end_index_on_file,                     &
6743                                        nxlc, nysc,                            &
6744                                        nxlf, nxrf, nysf, nynf,                &
6745                                        nys_on_file, nyn_on_file,              &
6746                                        nxl_on_file,nxr_on_file )
6747
6748             CASE ( 't_wall_v(2)' )
6749                IF ( k == 1 )  THEN
6750                   IF ( .NOT.  ALLOCATED( t_wall_v_1(2)%t ) )                  &
6751                      ALLOCATE( t_wall_v_1(2)%t(nzb_wall:nzt_wall+1,           &
6752                                                1:surf_usm_v(2)%ns) )
6753                   READ ( 13 )  tmp_wall_v(2)%t
6754                ENDIF
6755                CALL surface_restore_elements(                                 &
6756                                        t_wall_v_1(2)%t, tmp_wall_v(2)%t,      &
6757                                        surf_usm_v(2)%start_index,             & 
6758                                        start_index_on_file,                   &
6759                                        end_index_on_file ,                    &
6760                                        nxlc, nysc,                            &
6761                                        nxlf, nxrf, nysf, nynf,                &
6762                                        nys_on_file, nyn_on_file,              &
6763                                        nxl_on_file,nxr_on_file )
6764
6765             CASE ( 't_wall_v(3)' )
6766                IF ( k == 1 )  THEN
6767                   IF ( .NOT.  ALLOCATED( t_wall_v_1(3)%t ) )                  &
6768                      ALLOCATE( t_wall_v_1(3)%t(nzb_wall:nzt_wall+1,           &
6769                                                1:surf_usm_v(3)%ns) )
6770                   READ ( 13 )  tmp_wall_v(3)%t
6771                ENDIF
6772                CALL surface_restore_elements(                                 &
6773                                        t_wall_v_1(3)%t, tmp_wall_v(3)%t,      &
6774                                        surf_usm_v(3)%start_index,             &   
6775                                        start_index_on_file,                   &
6776                                        end_index_on_file,                     &
6777                                        nxlc, nysc,                            &
6778                                        nxlf, nxrf, nysf, nynf,                &
6779                                        nys_on_file, nyn_on_file,              &
6780                                        nxl_on_file,nxr_on_file )
6781
6782             CASE ( 't_green_h' )
6783                IF ( k == 1 )  THEN
6784                   IF ( .NOT.  ALLOCATED( t_green_h_1 ) )                      &
6785                      ALLOCATE( t_green_h_1(nzb_wall:nzt_wall+1,               &
6786                                            1:surf_usm_h%ns) )
6787                   READ ( 13 )  tmp_green_h
6788                ENDIF
6789                CALL surface_restore_elements(                                 &
6790                                        t_green_h_1, tmp_green_h,              &
6791                                        surf_usm_h%start_index,                & 
6792                                        start_index_on_file,                   &
6793                                        end_index_on_file,                     &
6794                                        nxlc, nysc,                            &
6795                                        nxlf, nxrf, nysf, nynf,                &
6796                                        nys_on_file, nyn_on_file,              &
6797                                        nxl_on_file,nxr_on_file )
6798
6799             CASE ( 't_green_v(0)' )
6800                IF ( k == 1 )  THEN
6801                   IF ( .NOT.  ALLOCATED( t_green_v_1(0)%t ) )                 &
6802                      ALLOCATE( t_green_v_1(0)%t(nzb_wall:nzt_wall+1,          &
6803                                                 1:surf_usm_v(0)%ns) )
6804                   READ ( 13 )  tmp_green_v(0)%t
6805                ENDIF
6806                CALL surface_restore_elements(                                 &
6807                                        t_green_v_1(0)%t, tmp_green_v(0)%t,    &
6808                                        surf_usm_v(0)%start_index,             & 
6809                                        start_index_on_file,                   &
6810                                        end_index_on_file,                     &
6811                                        nxlc, nysc,                            &
6812                                        nxlf, nxrf, nysf, nynf,                &
6813                                        nys_on_file, nyn_on_file,              &
6814                                        nxl_on_file,nxr_on_file )
6815
6816             CASE ( 't_green_v(1)' )
6817                IF ( k == 1 )  THEN
6818                   IF ( .NOT.  ALLOCATED( t_green_v_1(1)%t ) )                 &
6819                      ALLOCATE( t_green_v_1(1)%t(nzb_wall:nzt_wall+1,          &
6820                                                 1:surf_usm_v(1)%ns) )
6821                   READ ( 13 )  tmp_green_v(1)%t
6822                ENDIF
6823                CALL surface_restore_elements(                                 &
6824                                        t_green_v_1(1)%t, tmp_green_v(1)%t,    &
6825                                        surf_usm_v(1)%start_index,             & 
6826                                        start_index_on_file,                   &
6827                                        end_index_on_file,                     &
6828                                        nxlc, nysc,                            &
6829                                        nxlf, nxrf, nysf, nynf,                &
6830                                        nys_on_file, nyn_on_file,              &
6831                                        nxl_on_file,nxr_on_file )
6832
6833             CASE ( 't_green_v(2)' )
6834                IF ( k == 1 )  THEN
6835                   IF ( .NOT.  ALLOCATED( t_green_v_1(2)%t ) )                 &
6836                      ALLOCATE( t_green_v_1(2)%t(nzb_wall:nzt_wall+1,          &
6837                                                 1:surf_usm_v(2)%ns) )
6838                   READ ( 13 )  tmp_green_v(2)%t
6839                ENDIF
6840                CALL surface_restore_elements(                                 &
6841                                        t_green_v_1(2)%t, tmp_green_v(2)%t,    &
6842                                        surf_usm_v(2)%start_index,             & 
6843                                        start_index_on_file,                   &
6844                                        end_index_on_file ,                    &
6845                                        nxlc, nysc,                            &
6846                                        nxlf, nxrf, nysf, nynf,                &
6847                                        nys_on_file, nyn_on_file,              &
6848                                        nxl_on_file,nxr_on_file )
6849
6850             CASE ( 't_green_v(3)' )
6851                IF ( k == 1 )  THEN
6852                   IF ( .NOT.  ALLOCATED( t_green_v_1(3)%t ) )                 &
6853                      ALLOCATE( t_green_v_1(3)%t(nzb_wall:nzt_wall+1,          &
6854                                                 1:surf_usm_v(3)%ns) )
6855                   READ ( 13 )  tmp_green_v(3)%t
6856                ENDIF
6857                CALL surface_restore_elements(                                 &
6858                                        t_green_v_1(3)%t, tmp_green_v(3)%t,    &
6859                                        surf_usm_v(3)%start_index,             & 
6860                                        start_index_on_file,                   &
6861                                        end_index_on_file,                     &
6862                                        nxlc, nysc,                            &
6863                                        nxlf, nxrf, nysf, nynf,                &
6864                                        nys_on_file, nyn_on_file,              &
6865                                        nxl_on_file,nxr_on_file )
6866
6867             CASE ( 't_window_h' )
6868                IF ( k == 1 )  THEN
6869                   IF ( .NOT.  ALLOCATED( t_window_h_1 ) )                     &
6870                      ALLOCATE( t_window_h_1(nzb_wall:nzt_wall+1,              &
6871                                             1:surf_usm_h%ns) )
6872                   READ ( 13 )  tmp_window_h
6873                ENDIF
6874                CALL surface_restore_elements(                                 &
6875                                        t_window_h_1, tmp_window_h,            &
6876                                        surf_usm_h%start_index,                & 
6877                                        start_index_on_file,                   &
6878                                        end_index_on_file,                     &
6879                                        nxlc, nysc,                            &
6880                                        nxlf, nxrf, nysf, nynf,                &
6881                                        nys_on_file, nyn_on_file,              &
6882                                        nxl_on_file, nxr_on_file )
6883
6884             CASE ( 't_window_v(0)' )
6885                IF ( k == 1 )  THEN
6886                   IF ( .NOT.  ALLOCATED( t_window_v_1(0)%t ) )                &
6887                      ALLOCATE( t_window_v_1(0)%t(nzb_wall:nzt_wall+1,         &
6888                                                  1:surf_usm_v(0)%ns) )
6889                   READ ( 13 )  tmp_window_v(0)%t
6890                ENDIF
6891                CALL surface_restore_elements(                                 &
6892                                        t_window_v_1(0)%t,                     & 
6893                                        tmp_window_v(0)%t,                     &
6894                                        surf_usm_v(0)%start_index,             &
6895                                        start_index_on_file,                   &
6896                                        end_index_on_file,                     &
6897                                        nxlc, nysc,                            &
6898                                        nxlf, nxrf, nysf, nynf,                &
6899                                        nys_on_file, nyn_on_file,              &
6900                                        nxl_on_file,nxr_on_file )
6901
6902             CASE ( 't_window_v(1)' )
6903                IF ( k == 1 )  THEN
6904                   IF ( .NOT.  ALLOCATED( t_window_v_1(1)%t ) )                &
6905                      ALLOCATE( t_window_v_1(1)%t(nzb_wall:nzt_wall+1,         &
6906                                                  1:surf_usm_v(1)%ns) )
6907                   READ ( 13 )  tmp_window_v(1)%t
6908                ENDIF
6909                CALL surface_restore_elements(                                 &
6910                                        t_window_v_1(1)%t,                     & 
6911                                        tmp_window_v(1)%t,                     &
6912                                        surf_usm_v(1)%start_index,             & 
6913                                        start_index_on_file,                   &
6914                                        end_index_on_file,                     &
6915                                        nxlc, nysc,                            &
6916                                        nxlf, nxrf, nysf, nynf,                &
6917                                        nys_on_file, nyn_on_file,              &
6918                                        nxl_on_file,nxr_on_file )
6919
6920             CASE ( 't_window_v(2)' )
6921                IF ( k == 1 )  THEN
6922                   IF ( .NOT.  ALLOCATED( t_window_v_1(2)%t ) )                &
6923                      ALLOCATE( t_window_v_1(2)%t(nzb_wall:nzt_wall+1,         &
6924                                                  1:surf_usm_v(2)%ns) )
6925                   READ ( 13 )  tmp_window_v(2)%t
6926                ENDIF
6927                CALL surface_restore_elements(                                 &
6928                                        t_window_v_1(2)%t,                     & 
6929                                        tmp_window_v(2)%t,                     &
6930                                        surf_usm_v(2)%start_index,             & 
6931                                        start_index_on_file,                   &
6932                                        end_index_on_file ,                    &
6933                                        nxlc, nysc,                            &
6934                                        nxlf, nxrf, nysf, nynf,                &
6935                                        nys_on_file, nyn_on_file,              &
6936                                        nxl_on_file,nxr_on_file )
6937
6938             CASE ( 't_window_v(3)' )
6939                IF ( k == 1 )  THEN
6940                   IF ( .NOT.  ALLOCATED( t_window_v_1(3)%t ) )                &
6941                      ALLOCATE( t_window_v_1(3)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(3)%ns) )
6942                   READ ( 13 )  tmp_window_v(3)%t
6943                ENDIF
6944                CALL surface_restore_elements(                                 &
6945                                        t_window_v_1(3)%t,                     & 
6946                                        tmp_window_v(3)%t,                     &
6947                                        surf_usm_v(3)%start_index,             & 
6948                                        start_index_on_file,                   &
6949                                        end_index_on_file,                     &
6950                                        nxlc, nysc,                            &
6951                                        nxlf, nxrf, nysf, nynf,                &
6952                                        nys_on_file, nyn_on_file,              &
6953                                        nxl_on_file,nxr_on_file )
6954
6955             CASE DEFAULT
6956
6957                   found = .FALSE.
6958
6959          END SELECT
6960
6961       
6962    END SUBROUTINE usm_rrd_local
6963
6964   
6965!------------------------------------------------------------------------------!
6966! Description:
6967! ------------
6968!
6969!> This subroutine reads walls, roofs and land categories and it parameters
6970!> from input files.
6971!------------------------------------------------------------------------------!
6972    SUBROUTINE usm_read_urban_surface_types
6973   
6974        USE netcdf_data_input_mod,                                             &
6975            ONLY:  building_pars_f, building_type_f
6976
6977        IMPLICIT NONE
6978
6979        CHARACTER(12)                                         :: wtn
6980        INTEGER(iwp)                                          :: wtc
6981        REAL(wp), DIMENSION(n_surface_params)                 :: wtp
6982        LOGICAL                                               :: ascii_file = .FALSE.
6983        INTEGER(iwp), DIMENSION(0:17, nysg:nyng, nxlg:nxrg)   :: usm_par
6984        REAL(wp), DIMENSION(1:14, nysg:nyng, nxlg:nxrg)       :: usm_val
6985        INTEGER(iwp)                                          :: k, l, iw, jw, kw, it, ip, ii, ij, m
6986        INTEGER(iwp)                                          :: i, j
6987        INTEGER(iwp)                                          :: nz, roof, dirwe, dirsn
6988        INTEGER(iwp)                                          :: category
6989        INTEGER(iwp)                                          :: weheight1, wecat1, snheight1, sncat1
6990        INTEGER(iwp)                                          :: weheight2, wecat2, snheight2, sncat2
6991        INTEGER(iwp)                                          :: weheight3, wecat3, snheight3, sncat3
6992        REAL(wp)                                              :: height, albedo, thick
6993        REAL(wp)                                              :: wealbedo1, wethick1, snalbedo1, snthick1
6994        REAL(wp)                                              :: wealbedo2, wethick2, snalbedo2, snthick2
6995        REAL(wp)                                              :: wealbedo3, wethick3, snalbedo3, snthick3
6996
6997
6998        IF ( debug_output )  CALL debug_message( 'usm_read_urban_surface_types', 'start' )
6999!
7000!--     If building_pars or building_type are already read from static input
7001!--     file, skip reading ASCII file.
7002        IF ( building_type_f%from_file  .OR.  building_pars_f%from_file )      &
7003           RETURN
7004!
7005!--     Check if ASCII input file exists. If not, return and initialize USM
7006!--     with default settings.
7007        INQUIRE( FILE = 'SURFACE_PARAMETERS' // coupling_char,                 &
7008                 EXIST = ascii_file )
7009                 
7010        IF ( .NOT. ascii_file )  RETURN
7011
7012!
7013!--     read categories of walls and their parameters
7014        DO  ii = 0, io_blocks-1
7015            IF ( ii == io_group )  THEN
7016!
7017!--             open urban surface file
7018                OPEN( 151, file='SURFACE_PARAMETERS'//coupling_char, action='read', &
7019                           status='old', form='formatted', err=15 )
7020!
7021!--             first test and get n_surface_types
7022                k = 0
7023                l = 0
7024                DO
7025                    l = l+1
7026                    READ( 151, *, err=11, end=12 )  wtc, wtp, wtn
7027                    k = k+1
7028                    CYCLE
7029 11                 CONTINUE
7030                ENDDO
7031 12             n_surface_types = k
7032                ALLOCATE( surface_type_names(n_surface_types) )
7033                ALLOCATE( surface_type_codes(n_surface_types) )
7034                ALLOCATE( surface_params(n_surface_params, n_surface_types) )
7035!
7036!--             real reading
7037                rewind( 151 )
7038                k = 0
7039                DO
7040                    READ( 151, *, err=13, end=14 )  wtc, wtp, wtn
7041                    k = k+1
7042                    surface_type_codes(k) = wtc
7043                    surface_params(:,k) = wtp
7044                    surface_type_names(k) = wtn
7045                    CYCLE
704613                  WRITE(6,'(i3,a,2i5)') myid, 'readparams2 error k=', k
7047                    FLUSH(6)
7048                    CONTINUE
7049                ENDDO
7050 14             CLOSE(151)
7051                CYCLE
7052 15             message_string = 'file SURFACE_PARAMETERS'//TRIM(coupling_char)//' does not exist'
7053                CALL message( 'usm_read_urban_surface_types', 'PA0513', 1, 2, 0, 6, 0 )
7054            ENDIF
7055        ENDDO
7056   
7057!
7058!--     read types of surfaces
7059        usm_par = 0
7060        DO  ii = 0, io_blocks-1
7061            IF ( ii == io_group )  THEN
7062
7063!
7064!--             open csv urban surface file
7065                OPEN( 151, file='URBAN_SURFACE'//TRIM(coupling_char), action='read', &
7066                      status='old', form='formatted', err=23 )
7067               
7068                l = 0
7069                DO
7070                    l = l+1
7071!
7072!--                 i, j, height, nz, roof, dirwe, dirsn, category, soilcat,
7073!--                 weheight1, wecat1, snheight1, sncat1, weheight2, wecat2, snheight2, sncat2,
7074!--                 weheight3, wecat3, snheight3, sncat3
7075                    READ( 151, *, err=21, end=25 )  i, j, height, nz, roof, dirwe, dirsn,            &
7076                                            category, albedo, thick,                                 &
7077                                            weheight1, wecat1, wealbedo1, wethick1,                  &
7078                                            weheight2, wecat2, wealbedo2, wethick2,                  &
7079                                            weheight3, wecat3, wealbedo3, wethick3,                  &
7080                                            snheight1, sncat1, snalbedo1, snthick1,                  &
7081                                            snheight2, sncat2, snalbedo2, snthick2,                  &
7082                                            snheight3, sncat3, snalbedo3, snthick3
7083
7084                    IF ( i >= nxlg  .AND.  i <= nxrg  .AND.  j >= nysg  .AND.  j <= nyng )  THEN
7085!
7086!--                     write integer variables into array
7087                        usm_par(:,j,i) = (/1, nz, roof, dirwe, dirsn, category,                      &
7088                                          weheight1, wecat1, weheight2, wecat2, weheight3, wecat3,   &
7089                                          snheight1, sncat1, snheight2, sncat2, snheight3, sncat3 /)
7090!
7091!--                     write real values into array
7092                        usm_val(:,j,i) = (/ albedo, thick,                                           &
7093                                           wealbedo1, wethick1, wealbedo2, wethick2,                 &
7094                                           wealbedo3, wethick3, snalbedo1, snthick1,                 &
7095                                           snalbedo2, snthick2, snalbedo3, snthick3 /)
7096                    ENDIF
7097                    CYCLE
7098 21                 WRITE (message_string, "(A,I5)") 'errors in file URBAN_SURFACE'//TRIM(coupling_char)//' on line ', l
7099                    CALL message( 'usm_read_urban_surface_types', 'PA0512', 0, 1, 0, 6, 0 )
7100                ENDDO
7101         
7102 23             message_string = 'file URBAN_SURFACE'//TRIM(coupling_char)//' does not exist'
7103                CALL message( 'usm_read_urban_surface_types', 'PA0514', 1, 2, 0, 6, 0 )
7104
7105 25             CLOSE( 151 )
7106
7107            ENDIF
7108#if defined( __parallel )
7109            CALL MPI_BARRIER( comm2d, ierr )
7110#endif
7111        ENDDO
7112       
7113!
7114!--     check completeness and formal correctness of the data
7115        DO i = nxlg, nxrg
7116            DO j = nysg, nyng
7117                IF ( usm_par(0,j,i) /= 0  .AND.  (        &  !< incomplete data,supply default values later
7118                     usm_par(1,j,i) < nzb  .OR.           &
7119                     usm_par(1,j,i) > nzt  .OR.           &  !< incorrect height (nz < nzb  .OR.  nz > nzt)
7120                     usm_par(2,j,i) < 0  .OR.             &
7121                     usm_par(2,j,i) > 1  .OR.             &  !< incorrect roof sign
7122                     usm_par(3,j,i) < nzb-nzt  .OR.       & 
7123                     usm_par(3,j,i) > nzt-nzb  .OR.       &  !< incorrect west-east wall direction sign
7124                     usm_par(4,j,i) < nzb-nzt  .OR.       &
7125                     usm_par(4,j,i) > nzt-nzb  .OR.       &  !< incorrect south-north wall direction sign
7126                     usm_par(6,j,i) < nzb  .OR.           & 
7127                     usm_par(6,j,i) > nzt  .OR.           &  !< incorrect pedestrian level height for west-east wall
7128                     usm_par(8,j,i) > nzt  .OR.           &
7129                     usm_par(10,j,i) > nzt  .OR.          &  !< incorrect wall or roof level height for west-east wall
7130                     usm_par(12,j,i) < nzb  .OR.          & 
7131                     usm_par(12,j,i) > nzt  .OR.          &  !< incorrect pedestrian level height for south-north wall
7132                     usm_par(14,j,i) > nzt  .OR.          &
7133                     usm_par(16,j,i) > nzt                &  !< incorrect wall or roof level height for south-north wall
7134                    ) )  THEN
7135!
7136!--                 incorrect input data
7137                    WRITE (message_string, "(A,2I5)") 'missing or incorrect data in file URBAN_SURFACE'// &
7138                                                       TRIM(coupling_char)//' for i,j=', i,j
7139                    CALL message( 'usm_read_urban_surface', 'PA0504', 1, 2, 0, 6, 0 )
7140                ENDIF
7141               
7142            ENDDO
7143        ENDDO
7144!       
7145!--     Assign the surface types to the respective data type.
7146!--     First, for horizontal upward-facing surfaces.
7147!--     Further, set flag indicating that albedo is initialized via ASCII
7148!--     format, else it would be overwritten in the radiation model.
7149        surf_usm_h%albedo_from_ascii = .TRUE.
7150        DO  m = 1, surf_usm_h%ns
7151           iw = surf_usm_h%i(m)
7152           jw = surf_usm_h%j(m)
7153           kw = surf_usm_h%k(m)
7154
7155           IF ( usm_par(5,jw,iw) == 0 )  THEN
7156
7157              IF ( zu(kw) >= roof_height_limit )  THEN
7158                 surf_usm_h%isroof_surf(m)   = .TRUE.
7159                 surf_usm_h%surface_types(m) = roof_category         !< default category for root surface
7160              ELSE
7161                 surf_usm_h%isroof_surf(m)   = .FALSE.
7162                 surf_usm_h%surface_types(m) = land_category         !< default category for land surface
7163              ENDIF
7164
7165              surf_usm_h%albedo(:,m)    = -1.0_wp
7166              surf_usm_h%thickness_wall(m) = -1.0_wp
7167              surf_usm_h%thickness_green(m) = -1.0_wp
7168              surf_usm_h%thickness_window(m) = -1.0_wp
7169           ELSE
7170              IF ( usm_par(2,jw,iw)==0 )  THEN
7171                 surf_usm_h%isroof_surf(m)    = .FALSE.
7172                 surf_usm_h%thickness_wall(m) = -1.0_wp
7173                 surf_usm_h%thickness_window(m) = -1.0_wp
7174                 surf_usm_h%thickness_green(m)  = -1.0_wp
7175              ELSE
7176                 surf_usm_h%isroof_surf(m)    = .TRUE.
7177                 surf_usm_h%thickness_wall(m) = usm_val(2,jw,iw)
7178                 surf_usm_h%thickness_window(m) = usm_val(2,jw,iw)
7179                 surf_usm_h%thickness_green(m)  = usm_val(2,jw,iw)
7180              ENDIF
7181              surf_usm_h%surface_types(m) = usm_par(5,jw,iw)
7182              surf_usm_h%albedo(:,m)   = usm_val(1,jw,iw)
7183              surf_usm_h%transmissivity(m)    = 0.0_wp
7184           ENDIF
7185!
7186!--        Find the type position
7187           it = surf_usm_h%surface_types(m)
7188           ip = -99999
7189           DO k = 1, n_surface_types
7190              IF ( surface_type_codes(k) == it )  THEN
7191                 ip = k
7192                 EXIT
7193              ENDIF
7194           ENDDO
7195           IF ( ip == -99999 )  THEN
7196!
7197!--           land/roof category not found
7198              WRITE (9,"(A,I5,A,3I5)") 'land/roof category ', it,     &
7199                                       ' not found  for i,j,k=', iw,jw,kw
7200              FLUSH(9)
7201              IF ( surf_usm_h%isroof_surf(m) ) THEN
7202                 category = roof_category
7203              ELSE
7204                 category = land_category
7205              ENDIF
7206              DO k = 1, n_surface_types
7207                 IF ( surface_type_codes(k) == roof_category ) THEN
7208                    ip = k
7209                    EXIT
7210                 ENDIF
7211              ENDDO
7212              IF ( ip == -99999 )  THEN
7213!
7214!--              default land/roof category not found
7215                 WRITE (9,"(A,I5,A,3I5)") 'Default land/roof category', category, ' not found!'
7216                 FLUSH(9)
7217                 ip = 1
7218              ENDIF
7219           ENDIF
7220!
7221!--        Albedo
7222           IF ( surf_usm_h%albedo(ind_veg_wall,m) < 0.0_wp )  THEN
7223              surf_usm_h%albedo(:,m) = surface_params(ialbedo,ip)
7224           ENDIF
7225!
7226!--        Albedo type is 0 (custom), others are replaced later
7227           surf_usm_h%albedo_type(:,m) = 0
7228!
7229!--        Transmissivity
7230           IF ( surf_usm_h%transmissivity(m) < 0.0_wp )  THEN
7231              surf_usm_h%transmissivity(m) = 0.0_wp
7232           ENDIF
7233!
7234!--        emissivity of the wall
7235           surf_usm_h%emissivity(:,m) = surface_params(iemiss,ip)
7236!           
7237!--        heat conductivity λS between air and wall ( W m−2 K−1 )
7238           surf_usm_h%lambda_surf(m) = surface_params(ilambdas,ip)
7239           surf_usm_h%lambda_surf_window(m) = surface_params(ilambdas,ip)
7240           surf_usm_h%lambda_surf_green(m)  = surface_params(ilambdas,ip)
7241!           
7242!--        roughness length for momentum, heat and humidity
7243           surf_usm_h%z0(m) = surface_params(irough,ip)
7244           surf_usm_h%z0h(m) = surface_params(iroughh,ip)
7245           surf_usm_h%z0q(m) = surface_params(iroughh,ip)
7246!
7247!--        Surface skin layer heat capacity (J m−2 K−1 )
7248           surf_usm_h%c_surface(m) = surface_params(icsurf,ip)
7249           surf_usm_h%c_surface_window(m) = surface_params(icsurf,ip)
7250           surf_usm_h%c_surface_green(m)  = surface_params(icsurf,ip)
7251!           
7252!--        wall material parameters:
7253!--        thickness of the wall (m)
7254!--        missing values are replaced by default value for category
7255           IF ( surf_usm_h%thickness_wall(m) <= 0.001_wp )  THEN
7256                surf_usm_h%thickness_wall(m) = surface_params(ithick,ip)
7257           ENDIF
7258           IF ( surf_usm_h%thickness_window(m) <= 0.001_wp )  THEN
7259                surf_usm_h%thickness_window(m) = surface_params(ithick,ip)
7260           ENDIF
7261           IF ( surf_usm_h%thickness_green(m) <= 0.001_wp )  THEN
7262                surf_usm_h%thickness_green(m) = surface_params(ithick,ip)
7263           ENDIF
7264!           
7265!--        volumetric heat capacity rho*C of the wall ( J m−3 K−1 )
7266           surf_usm_h%rho_c_wall(:,m) = surface_params(irhoC,ip)
7267           surf_usm_h%rho_c_window(:,m) = surface_params(irhoC,ip)
7268           surf_usm_h%rho_c_green(:,m)  = surface_params(irhoC,ip)
7269!           
7270!--        thermal conductivity λH of the wall (W m−1 K−1 )
7271           surf_usm_h%lambda_h(:,m) = surface_params(ilambdah,ip)
7272           surf_usm_h%lambda_h_window(:,m) = surface_params(ilambdah,ip)
7273           surf_usm_h%lambda_h_green(:,m)  = surface_params(ilambdah,ip)
7274
7275        ENDDO
7276!
7277!--     For vertical surface elements ( 0 -- northward-facing, 1 -- southward-facing,
7278!--     2 -- eastward-facing, 3 -- westward-facing )
7279        DO  l = 0, 3
7280!
7281!--        Set flag indicating that albedo is initialized via ASCII format.
7282!--        Else it would be overwritten in the radiation model.
7283           surf_usm_v(l)%albedo_from_ascii = .TRUE.
7284           DO  m = 1, surf_usm_v(l)%ns
7285              i  = surf_usm_v(l)%i(m)
7286              j  = surf_usm_v(l)%j(m)
7287              kw = surf_usm_v(l)%k(m)
7288             
7289              IF ( l == 3 )  THEN ! westward facing
7290                 iw = i
7291                 jw = j
7292                 ii = 6
7293                 ij = 3
7294              ELSEIF ( l == 2 )  THEN
7295                 iw = i-1
7296                 jw = j
7297                 ii = 6
7298                 ij = 3
7299              ELSEIF ( l == 1 )  THEN
7300                 iw = i
7301                 jw = j
7302                 ii = 12
7303                 ij = 9
7304              ELSEIF ( l == 0 )  THEN
7305                 iw = i
7306                 jw = j-1
7307                 ii = 12
7308                 ij = 9
7309              ENDIF
7310
7311              IF ( iw < 0 .OR. jw < 0 ) THEN
7312!
7313!--              wall on west or south border of the domain - assign default category
7314                 IF ( kw <= roof_height_limit ) THEN
7315                     surf_usm_v(l)%surface_types(m) = wall_category   !< default category for wall surface in wall zone
7316                 ELSE
7317                     surf_usm_v(l)%surface_types(m) = roof_category   !< default category for wall surface in roof zone
7318                 END IF
7319                 surf_usm_v(l)%albedo(:,m)         = -1.0_wp
7320                 surf_usm_v(l)%thickness_wall(m)   = -1.0_wp
7321                 surf_usm_v(l)%thickness_window(m) = -1.0_wp
7322                 surf_usm_v(l)%thickness_green(m)  = -1.0_wp
7323                 surf_usm_v(l)%transmissivity(m)   = -1.0_wp
7324              ELSE IF ( kw <= usm_par(ii,jw,iw) )  THEN
7325!
7326!--                 pedestrian zone
7327                 IF ( usm_par(ii+1,jw,iw) == 0 )  THEN
7328                     surf_usm_v(l)%surface_types(m)  = pedestrian_category   !< default category for wall surface in
7329                                                                             !<pedestrian zone
7330                     surf_usm_v(l)%albedo(:,m)         = -1.0_wp
7331                     surf_usm_v(l)%thickness_wall(m)   = -1.0_wp
7332                     surf_usm_v(l)%thickness_window(m) = -1.0_wp
7333                     surf_usm_v(l)%thickness_green(m)  = -1.0_wp
7334                     surf_usm_v(l)%transmissivity(m)   = -1.0_wp
7335                 ELSE
7336                     surf_usm_v(l)%surface_types(m)    = usm_par(ii+1,jw,iw)
7337                     surf_usm_v(l)%albedo(:,m)         = usm_val(ij,jw,iw)
7338                     surf_usm_v(l)%thickness_wall(m)   = usm_val(ij+1,jw,iw)
7339                     surf_usm_v(l)%thickness_window(m) = usm_val(ij+1,jw,iw)
7340                     surf_usm_v(l)%thickness_green(m)  = usm_val(ij+1,jw,iw)
7341                     surf_usm_v(l)%transmissivity(m)   = 0.0_wp
7342                 ENDIF
7343              ELSE IF ( kw <= usm_par(ii+2,jw,iw) )  THEN
7344!
7345!--              wall zone
7346                 IF ( usm_par(ii+3,jw,iw) == 0 )  THEN
7347                     surf_usm_v(l)%surface_types(m)    = wall_category         !< default category for wall surface
7348                     surf_usm_v(l)%albedo(:,m)         = -1.0_wp
7349                     surf_usm_v(l)%thickness_wall(m)   = -1.0_wp
7350                     surf_usm_v(l)%thickness_window(m) = -1.0_wp
7351                     surf_usm_v(l)%thickness_green(m)  = -1.0_wp
7352                     surf_usm_v(l)%transmissivity(m)   = -1.0_wp
7353                 ELSE
7354                     surf_usm_v(l)%surface_types(m)    = usm_par(ii+3,jw,iw)
7355                     surf_usm_v(l)%albedo(:,m)         = usm_val(ij+2,jw,iw)
7356                     surf_usm_v(l)%thickness_wall(m)   = usm_val(ij+3,jw,iw)
7357                     surf_usm_v(l)%thickness_window(m) = usm_val(ij+3,jw,iw)
7358                     surf_usm_v(l)%thickness_green(m)  = usm_val(ij+3,jw,iw)
7359                     surf_usm_v(l)%transmissivity(m)   = 0.0_wp
7360                 ENDIF
7361              ELSE IF ( kw <= usm_par(ii+4,jw,iw) )  THEN
7362!
7363!--              roof zone
7364                 IF ( usm_par(ii+5,jw,iw) == 0 )  THEN
7365                     surf_usm_v(l)%surface_types(m)    = roof_category         !< default category for roof surface
7366                     surf_usm_v(l)%albedo(:,m)         = -1.0_wp
7367                     surf_usm_v(l)%thickness_wall(m)   = -1.0_wp
7368                     surf_usm_v(l)%thickness_window(m) = -1.0_wp
7369                     surf_usm_v(l)%thickness_green(m)  = -1.0_wp
7370                     surf_usm_v(l)%transmissivity(m)   = -1.0_wp
7371                 ELSE
7372                     surf_usm_v(l)%surface_types(m)    = usm_par(ii+5,jw,iw)
7373                     surf_usm_v(l)%albedo(:,m)         = usm_val(ij+4,jw,iw)
7374                     surf_usm_v(l)%thickness_wall(m)   = usm_val(ij+5,jw,iw)
7375                     surf_usm_v(l)%thickness_window(m) = usm_val(ij+5,jw,iw)
7376                     surf_usm_v(l)%thickness_green(m)  = usm_val(ij+5,jw,iw)
7377                     surf_usm_v(l)%transmissivity(m)   = 0.0_wp
7378                 ENDIF
7379              ELSE
7380                 WRITE(9,*) 'Problem reading USM data:'
7381                 WRITE(9,*) l,i,j,kw,get_topography_top_index_ji( j, i, 's' )
7382                 WRITE(9,*) ii,iw,jw,kw,get_topography_top_index_ji( jw, iw, 's' )
7383                 WRITE(9,*) usm_par(ii,jw,iw),usm_par(ii+1,jw,iw)
7384                 WRITE(9,*) usm_par(ii+2,jw,iw),usm_par(ii+3,jw,iw)
7385                 WRITE(9,*) usm_par(ii+4,jw,iw),usm_par(ii+5,jw,iw)
7386                 WRITE(9,*) kw,roof_height_limit,wall_category,roof_category
7387                 FLUSH(9)
7388!
7389!--              supply the default category
7390                 IF ( kw <= roof_height_limit ) THEN
7391                     surf_usm_v(l)%surface_types(m) = wall_category   !< default category for wall surface in wall zone
7392                 ELSE
7393                     surf_usm_v(l)%surface_types(m) = roof_category   !< default category for wall surface in roof zone
7394                 END IF
7395                 surf_usm_v(l)%albedo(:,m)         = -1.0_wp
7396                 surf_usm_v(l)%thickness_wall(m)   = -1.0_wp
7397                 surf_usm_v(l)%thickness_window(m) = -1.0_wp
7398                 surf_usm_v(l)%thickness_green(m)  = -1.0_wp
7399                 surf_usm_v(l)%transmissivity(m)   = -1.0_wp
7400              ENDIF
7401!
7402!--           Find the type position
7403              it = surf_usm_v(l)%surface_types(m)
7404              ip = -99999
7405              DO k = 1, n_surface_types
7406                 IF ( surface_type_codes(k) == it )  THEN
7407                    ip = k
7408                    EXIT
7409                 ENDIF
7410              ENDDO
7411              IF ( ip == -99999 )  THEN
7412!
7413!--              wall category not found
7414                 WRITE (9, "(A,I7,A,3I5)") 'wall category ', it,  &
7415                                           ' not found  for i,j,k=', iw,jw,kw
7416                 FLUSH(9)
7417                 category = wall_category 
7418                 DO k = 1, n_surface_types
7419                    IF ( surface_type_codes(k) == category ) THEN
7420                       ip = k
7421                       EXIT
7422                    ENDIF
7423                 ENDDO
7424                 IF ( ip == -99999 )  THEN
7425!
7426!--                 default wall category not found
7427                    WRITE (9, "(A,I5,A,3I5)") 'Default wall category', category, ' not found!'
7428                    FLUSH(9)
7429                    ip = 1
7430                 ENDIF
7431              ENDIF
7432
7433!
7434!--           Albedo
7435              IF ( surf_usm_v(l)%albedo(ind_veg_wall,m) < 0.0_wp )  THEN
7436                 surf_usm_v(l)%albedo(:,m) = surface_params(ialbedo,ip)
7437              ENDIF
7438!--           Albedo type is 0 (custom), others are replaced later
7439              surf_usm_v(l)%albedo_type(:,m) = 0
7440!--           Transmissivity of the windows
7441              IF ( surf_usm_v(l)%transmissivity(m) < 0.0_wp )  THEN
7442                 surf_usm_v(l)%transmissivity(m) = 0.0_wp
7443              ENDIF
7444!
7445!--           emissivity of the wall
7446              surf_usm_v(l)%emissivity(:,m) = surface_params(iemiss,ip)
7447!           
7448!--           heat conductivity lambda S between air and wall ( W m-2 K-1 )
7449              surf_usm_v(l)%lambda_surf(m) = surface_params(ilambdas,ip)
7450              surf_usm_v(l)%lambda_surf_window(m) = surface_params(ilambdas,ip)
7451              surf_usm_v(l)%lambda_surf_green(m) = surface_params(ilambdas,ip)
7452!           
7453!--           roughness length
7454              surf_usm_v(l)%z0(m) = surface_params(irough,ip)
7455              surf_usm_v(l)%z0h(m) = surface_params(iroughh,ip)
7456              surf_usm_v(l)%z0q(m) = surface_params(iroughh,ip)
7457!           
7458!--           Surface skin layer heat capacity (J m-2 K-1 )
7459              surf_usm_v(l)%c_surface(m) = surface_params(icsurf,ip)
7460              surf_usm_v(l)%c_surface_window(m) = surface_params(icsurf,ip)
7461              surf_usm_v(l)%c_surface_green(m) = surface_params(icsurf,ip)
7462!           
7463!--           wall material parameters:
7464!--           thickness of the wall (m)
7465!--           missing values are replaced by default value for category
7466              IF ( surf_usm_v(l)%thickness_wall(m) <= 0.001_wp )  THEN
7467                   surf_usm_v(l)%thickness_wall(m) = surface_params(ithick,ip)
7468              ENDIF
7469              IF ( surf_usm_v(l)%thickness_window(m) <= 0.001_wp )  THEN
7470                   surf_usm_v(l)%thickness_window(m) = surface_params(ithick,ip)
7471              ENDIF
7472              IF ( surf_usm_v(l)%thickness_green(m) <= 0.001_wp )  THEN
7473                   surf_usm_v(l)%thickness_green(m) = surface_params(ithick,ip)
7474              ENDIF
7475!
7476!--           volumetric heat capacity rho*C of the wall ( J m-3 K-1 )
7477              surf_usm_v(l)%rho_c_wall(:,m) = surface_params(irhoC,ip)
7478              surf_usm_v(l)%rho_c_window(:,m) = surface_params(irhoC,ip)
7479              surf_usm_v(l)%rho_c_green(:,m) = surface_params(irhoC,ip)
7480!           
7481!--           thermal conductivity lambda H of the wall (W m-1 K-1 )
7482              surf_usm_v(l)%lambda_h(:,m) = surface_params(ilambdah,ip)
7483              surf_usm_v(l)%lambda_h_window(:,m) = surface_params(ilambdah,ip)
7484              surf_usm_v(l)%lambda_h_green(:,m) = surface_params(ilambdah,ip)
7485
7486           ENDDO
7487        ENDDO 
7488
7489!
7490!--     Initialize wall layer thicknesses. Please note, this will be removed
7491!--     after migration to Palm input data standard. 
7492        DO k = nzb_wall, nzt_wall
7493           zwn(k) = zwn_default(k)
7494           zwn_green(k) = zwn_default_green(k)
7495           zwn_window(k) = zwn_default_window(k)
7496        ENDDO
7497!
7498!--     apply for all particular surface grids. First for horizontal surfaces
7499        DO  m = 1, surf_usm_h%ns
7500           surf_usm_h%zw(:,m) = zwn(:) * surf_usm_h%thickness_wall(m)
7501           surf_usm_h%zw_green(:,m) = zwn_green(:) * surf_usm_h%thickness_green(m)
7502           surf_usm_h%zw_window(:,m) = zwn_window(:) * surf_usm_h%thickness_window(m)
7503        ENDDO
7504        DO  l = 0, 3
7505           DO  m = 1, surf_usm_v(l)%ns
7506              surf_usm_v(l)%zw(:,m) = zwn(:) * surf_usm_v(l)%thickness_wall(m)
7507              surf_usm_v(l)%zw_green(:,m) = zwn_green(:) * surf_usm_v(l)%thickness_green(m)
7508              surf_usm_v(l)%zw_window(:,m) = zwn_window(:) * surf_usm_v(l)%thickness_window(m)
7509           ENDDO
7510        ENDDO
7511
7512        IF ( debug_output )  CALL debug_message( 'usm_read_urban_surface_types', 'end' )
7513   
7514    END SUBROUTINE usm_read_urban_surface_types
7515
7516
7517!------------------------------------------------------------------------------!
7518! Description:
7519! ------------
7520!
7521!> This function advances through the list of local surfaces to find given
7522!> x, y, d, z coordinates
7523!------------------------------------------------------------------------------!
7524    PURE FUNCTION find_surface( x, y, z, d ) result(isurfl)
7525
7526        INTEGER(iwp), INTENT(in)                :: x, y, z, d
7527        INTEGER(iwp)                            :: isurfl
7528        INTEGER(iwp)                            :: isx, isy, isz
7529
7530        IF ( d == 0 ) THEN
7531           DO  isurfl = 1, surf_usm_h%ns
7532              isx = surf_usm_h%i(isurfl)
7533              isy = surf_usm_h%j(isurfl)
7534              isz = surf_usm_h%k(isurfl)
7535              IF ( isx==x .and. isy==y .and. isz==z )  RETURN
7536           ENDDO
7537        ELSE
7538           DO  isurfl = 1, surf_usm_v(d-1)%ns
7539              isx = surf_usm_v(d-1)%i(isurfl)
7540              isy = surf_usm_v(d-1)%j(isurfl)
7541              isz = surf_usm_v(d-1)%k(isurfl)
7542              IF ( isx==x .and. isy==y .and. isz==z )  RETURN
7543           ENDDO
7544        ENDIF
7545!
7546!--     coordinate not found
7547        isurfl = -1
7548
7549    END FUNCTION
7550
7551
7552!------------------------------------------------------------------------------!
7553! Description:
7554! ------------
7555!
7556!> This subroutine reads temperatures of respective material layers in walls,
7557!> roofs and ground from input files. Data in the input file must be in
7558!> standard order, i.e. horizontal surfaces first ordered by x, y and then
7559!> vertical surfaces ordered by x, y, direction, z
7560!------------------------------------------------------------------------------!
7561    SUBROUTINE usm_read_wall_temperature
7562
7563        INTEGER(iwp)                                          :: i, j, k, d, ii, iline  !> running indices
7564        INTEGER(iwp)                                          :: isurfl
7565        REAL(wp)                                              :: rtsurf
7566        REAL(wp), DIMENSION(nzb_wall:nzt_wall+1)              :: rtwall
7567
7568
7569        IF ( debug_output )  CALL debug_message( 'usm_read_wall_temperature', 'start' )
7570
7571        DO  ii = 0, io_blocks-1
7572            IF ( ii == io_group )  THEN
7573!
7574!--             open wall temperature file
7575                OPEN( 152, file='WALL_TEMPERATURE'//coupling_char, action='read', &
7576                           status='old', form='formatted', err=15 )
7577
7578                isurfl = 0
7579                iline = 1
7580                DO
7581                    rtwall = -9999.0_wp  !< for incomplete lines
7582                    READ( 152, *, err=13, end=14 )  i, j, k, d, rtsurf, rtwall
7583
7584                    IF ( nxl <= i .and. i <= nxr .and. &
7585                        nys <= j .and. j <= nyn)  THEN  !< local processor
7586!--                     identify surface id
7587                        isurfl = find_surface( i, j, k, d )
7588                        IF ( isurfl == -1 )  THEN
7589                            WRITE(message_string, '(a,4i5,a,i5,a)') 'Coordinates (xyzd) ', i, j, k, d, &
7590                                ' on line ', iline, &
7591                                ' in file WALL_TEMPERATURE are either not present or out of standard order of surfaces.'
7592                            CALL message( 'usm_read_wall_temperature', 'PA0521', 1, 2, 0, 6, 0 )
7593                        ENDIF
7594!
7595!--                     assign temperatures
7596                        IF ( d == 0 ) THEN
7597                           t_surf_wall_h(isurfl) = rtsurf
7598                           t_wall_h(:,isurfl) = rtwall(:)
7599                           t_window_h(:,isurfl) = rtwall(:)
7600                           t_green_h(:,isurfl) = rtwall(:)
7601                        ELSE
7602                           t_surf_wall_v(d-1)%t(isurfl) = rtsurf
7603                           t_wall_v(d-1)%t(:,isurfl) = rtwall(:)
7604                           t_window_v(d-1)%t(:,isurfl) = rtwall(:)
7605                           t_green_v(d-1)%t(:,isurfl) = rtwall(:)
7606                        ENDIF
7607                    ENDIF
7608
7609                    iline = iline + 1
7610                    CYCLE
7611 13                 WRITE(message_string, '(a,i5,a)') 'Error reading line ', iline, &
7612                        ' in file WALL_TEMPERATURE.'
7613                    CALL message( 'usm_read_wall_temperature', 'PA0522', 1, 2, 0, 6, 0 )
7614                ENDDO
7615 14             CLOSE(152)
7616                CYCLE
7617 15             message_string = 'file WALL_TEMPERATURE'//TRIM(coupling_char)//' does not exist'
7618                CALL message( 'usm_read_wall_temperature', 'PA0523', 1, 2, 0, 6, 0 )
7619            ENDIF
7620#if defined( __parallel )
7621            CALL MPI_BARRIER( comm2d, ierr )
7622#endif
7623        ENDDO
7624
7625        IF ( debug_output )  CALL debug_message( 'usm_read_wall_temperature', 'end' )
7626
7627    END SUBROUTINE usm_read_wall_temperature
7628
7629
7630
7631!------------------------------------------------------------------------------!
7632! Description:
7633! ------------
7634!> Solver for the energy balance at the ground/roof/wall surface.
7635!> It follows basic ideas and structure of lsm_energy_balance
7636!> with many simplifications and adjustments.
7637!> TODO better description
7638!> No calculation of window surface temperatures during spinup to increase
7639!> maximum possible timstep
7640!------------------------------------------------------------------------------!
7641    SUBROUTINE usm_surface_energy_balance( during_spinup )
7642
7643
7644        IMPLICIT NONE
7645
7646        INTEGER(iwp)                          :: i, j, k, l, m   !< running indices
7647       
7648        INTEGER(iwp) ::  i_off     !< offset to determine index of surface element, seen from atmospheric grid point, for x
7649        INTEGER(iwp) ::  j_off     !< offset to determine index of surface element, seen from atmospheric grid point, for y
7650        INTEGER(iwp) ::  k_off     !< offset to determine index of surface element, seen from atmospheric grid point, for z
7651
7652        LOGICAL                               :: during_spinup      !< flag indicating soil/wall spinup phase
7653       
7654        REAL(wp)                              :: frac_win           !< window fraction, used to restore original values during spinup
7655        REAL(wp)                              :: frac_green         !< green fraction, used to restore original values during spinup
7656        REAL(wp)                              :: frac_wall          !< wall fraction, used to restore original values during spinup
7657        REAL(wp)                              :: stend_wall         !< surface tendency
7658       
7659        REAL(wp)                              :: stend_window       !< surface tendency
7660        REAL(wp)                              :: stend_green        !< surface tendency
7661        REAL(wp)                              :: coef_1             !< first coeficient for prognostic equation
7662        REAL(wp)                              :: coef_window_1      !< first coeficient for prognostic window equation
7663        REAL(wp)                              :: coef_green_1       !< first coeficient for prognostic green wall equation
7664        REAL(wp)                              :: coef_2             !< second  coeficient for prognostic equation
7665        REAL(wp)                              :: coef_window_2      !< second  coeficient for prognostic window equation
7666        REAL(wp)                              :: coef_green_2       !< second  coeficient for prognostic green wall equation
7667        REAL(wp)                              :: rho_cp             !< rho_wall_surface * c_p
7668        REAL(wp)                              :: f_shf              !< factor for shf_eb
7669        REAL(wp)                              :: f_shf_window       !< factor for shf_eb window
7670        REAL(wp)                              :: f_shf_green        !< factor for shf_eb green wall
7671        REAL(wp)                              :: lambda_surface     !< current value of lambda_surface (heat conductivity
7672                                                                    !<between air and wall)
7673        REAL(wp)                              :: lambda_surface_window  !< current value of lambda_surface (heat conductivity
7674                                                                        !< between air and window)
7675        REAL(wp)                              :: lambda_surface_green   !< current value of lambda_surface (heat conductivity
7676                                                                        !< between air and greeb wall)
7677       
7678        REAL(wp)                              :: dtime              !< simulated time of day (in UTC)
7679        INTEGER(iwp)                          :: dhour              !< simulated hour of day (in UTC)
7680        REAL(wp)                              :: acoef              !< actual coefficient of diurnal profile of anthropogenic heat
7681        REAL(wp) ::  f1,          &  !< resistance correction term 1
7682                     f2,          &  !< resistance correction term 2
7683                     f3,          &  !< resistance correction term 3
7684                     e,           &  !< water vapour pressure
7685                     e_s,         &  !< water vapour saturation pressure
7686                     e_s_dt,      &  !< derivate of e_s with respect to T
7687                     tend,        &  !< tendency
7688                     dq_s_dt,     &  !< derivate of q_s with respect to T
7689                     f_qsws,      &  !< factor for qsws
7690                     f_qsws_veg,  &  !< factor for qsws_veg
7691                     f_qsws_liq,  &  !< factor for qsws_liq
7692                     m_liq_max,   &  !< maxmimum value of the liq. water reservoir
7693                     qv1,         &  !< specific humidity at first grid level
7694                     m_max_depth = 0.0002_wp, &  !< Maximum capacity of the water reservoir (m)
7695                     rho_lv,      &  !< frequently used parameter for green layers
7696                     drho_l_lv,   &  !< frequently used parameter for green layers
7697                     q_s             !< saturation specific humidity
7698
7699
7700        IF ( debug_output_timestep )  THEN
7701           WRITE( debug_string, * ) 'usm_surface_energy_balance | during_spinup: ',&
7702                                    during_spinup
7703           CALL debug_message( debug_string, 'start' )
7704        ENDIF
7705!
7706!--     Index offset of surface element point with respect to adjoining
7707!--     atmospheric grid point
7708        k_off = surf_usm_h%koff
7709        j_off = surf_usm_h%joff
7710        i_off = surf_usm_h%ioff
7711       
7712!       
7713!--     First, treat horizontal surface elements
7714        !$OMP PARALLEL PRIVATE (m, i, j, k, lambda_surface, lambda_surface_window,                 &
7715        !$OMP&                  lambda_surface_green, qv1, rho_cp, rho_lv, drho_l_lv, f_shf,       &
7716        !$OMP&                  f_shf_window, f_shf_green, m_total, f1, f2, e_s, e, f3, f_qsws_veg,&
7717        !$OMP&                  q_s, f_qsws_liq, f_qsws, e_s_dt, dq_s_dt, coef_1, coef_window_1,   &
7718        !$OMP&                  coef_green_1, coef_2, coef_window_2, coef_green_2, stend_wall,     &
7719        !$OMP&                  stend_window, stend_green, tend, m_liq_max)
7720        !$OMP DO SCHEDULE (STATIC)
7721        DO  m = 1, surf_usm_h%ns
7722!
7723!--       During spinup set green and window fraction to zero and restore
7724!--       at the end of the loop.
7725!--       Note, this is a temporary fix and need to be removed later. 
7726           IF ( during_spinup )  THEN
7727              frac_win   = surf_usm_h%frac(ind_wat_win,m)
7728              frac_wall  = surf_usm_h%frac(ind_veg_wall,m)
7729              frac_green = surf_usm_h%frac(ind_pav_green,m)
7730              surf_usm_h%frac(ind_wat_win,m)   = 0.0_wp
7731              surf_usm_h%frac(ind_veg_wall,m)  = 1.0_wp
7732              surf_usm_h%frac(ind_pav_green,m) = 0.0_wp
7733           ENDIF
7734!
7735!--        Get indices of respective grid point
7736           i = surf_usm_h%i(m)
7737           j = surf_usm_h%j(m)
7738           k = surf_usm_h%k(m)
7739!
7740!--        TODO - how to calculate lambda_surface for horizontal surfaces
7741!--        (lambda_surface is set according to stratification in land surface model)
7742!--        MS: ???
7743           IF ( surf_usm_h%ol(m) >= 0.0_wp )  THEN
7744              lambda_surface = surf_usm_h%lambda_surf(m)
7745              lambda_surface_window = surf_usm_h%lambda_surf_window(m)
7746              lambda_surface_green = surf_usm_h%lambda_surf_green(m)
7747           ELSE
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           ENDIF
7752
7753!            pt1  = pt(k,j,i)
7754           IF ( humidity )  THEN
7755              qv1 = q(k,j,i)
7756           ELSE
7757              qv1 = 0.0_wp
7758           ENDIF
7759!
7760!--        calculate rho * c_p coefficient at surface layer
7761           rho_cp  = c_p * hyp(k) / ( r_d * surf_usm_h%pt1(m) * exner(k) )
7762
7763           IF ( surf_usm_h%frac(ind_pav_green,m) > 0.0_wp )  THEN
7764!
7765!--           Calculate frequently used parameters
7766              rho_lv    = rho_cp / c_p * l_v
7767              drho_l_lv = 1.0_wp / (rho_l * l_v)
7768           ENDIF
7769
7770!
7771!--        Calculate aerodyamic resistance.
7772!--        Calculation for horizontal surfaces follows LSM formulation
7773!--        pt, us, ts are not available for the prognostic time step,
7774!--        data from the last time step is used here.
7775!
7776!--        Workaround: use single r_a as stability is only treated for the
7777!--        average temperature
7778           surf_usm_h%r_a(m) = ( surf_usm_h%pt1(m) - surf_usm_h%pt_surface(m) ) /&
7779                               ( surf_usm_h%ts(m) * surf_usm_h%us(m) + 1.0E-20_wp )   
7780           surf_usm_h%r_a_window(m) = surf_usm_h%r_a(m)
7781           surf_usm_h%r_a_green(m)  = surf_usm_h%r_a(m)
7782
7783!            r_a = ( surf_usm_h%pt1(m) - t_surf_h(m) / exner(k) ) /                              &
7784!                  ( surf_usm_h%ts(m) * surf_usm_h%us(m) + 1.0E-20_wp )
7785!            r_a_window = ( surf_usm_h%pt1(m) - t_surf_window_h(m) / exner(k) ) /                &
7786!                  ( surf_usm_h%ts(m) * surf_usm_h%us(m) + 1.0E-20_wp )
7787!            r_a_green = ( surf_usm_h%pt1(m) - t_surf_green_h(m) / exner(k) ) /                  &
7788!                  ( surf_usm_h%ts(m) * surf_usm_h%us(m) + 1.0E-20_wp )
7789               
7790!--        Make sure that the resistance does not drop to zero
7791           IF ( surf_usm_h%r_a(m)        < 1.0_wp )                            &
7792               surf_usm_h%r_a(m)        = 1.0_wp
7793           IF ( surf_usm_h%r_a_green(m)  < 1.0_wp )                            &
7794               surf_usm_h%r_a_green(m)  = 1.0_wp
7795           IF ( surf_usm_h%r_a_window(m) < 1.0_wp )                            &
7796               surf_usm_h%r_a_window(m) = 1.0_wp
7797             
7798!
7799!--        Make sure that the resistacne does not exceed a maxmium value in case
7800!--        of zero velocities
7801           IF ( surf_usm_h%r_a(m)        > 300.0_wp )                          &
7802               surf_usm_h%r_a(m)        = 300.0_wp
7803           IF ( surf_usm_h%r_a_green(m)  > 300.0_wp )                          &
7804               surf_usm_h%r_a_green(m)  = 300.0_wp
7805           IF ( surf_usm_h%r_a_window(m) > 300.0_wp )                          &
7806               surf_usm_h%r_a_window(m) = 300.0_wp               
7807               
7808!
7809!--        factor for shf_eb
7810           f_shf  = rho_cp / surf_usm_h%r_a(m)
7811           f_shf_window  = rho_cp / surf_usm_h%r_a_window(m)
7812           f_shf_green  = rho_cp / surf_usm_h%r_a_green(m)
7813       
7814
7815           IF ( surf_usm_h%frac(ind_pav_green,m) > 0.0_wp ) THEN
7816!--           Adapted from LSM:
7817!--           Second step: calculate canopy resistance r_canopy
7818!--           f1-f3 here are defined as 1/f1-f3 as in ECMWF documentation
7819 
7820!--           f1: correction for incoming shortwave radiation (stomata close at
7821!--           night)
7822              f1 = MIN( 1.0_wp, ( 0.004_wp * surf_usm_h%rad_sw_in(m) + 0.05_wp ) / &
7823                               (0.81_wp * (0.004_wp * surf_usm_h%rad_sw_in(m)      &
7824                                + 1.0_wp)) )
7825!
7826!--           f2: correction for soil moisture availability to plants (the
7827!--           integrated soil moisture must thus be considered here)
7828!--           f2 = 0 for very dry soils
7829              m_total = 0.0_wp
7830              DO  k = nzb_wall, nzt_wall+1
7831                  m_total = m_total + rootfr_h(nzb_wall,m)                              &
7832                            * MAX(swc_h(nzb_wall,m),wilt_h(nzb_wall,m))
7833              ENDDO 
7834   
7835              IF ( m_total > wilt_h(nzb_wall,m)  .AND.  m_total < fc_h(nzb_wall,m) )  THEN
7836                 f2 = ( m_total - wilt_h(nzb_wall,m) ) / (fc_h(nzb_wall,m) - wilt_h(nzb_wall,m) )
7837              ELSEIF ( m_total >= fc_h(nzb_wall,m) )  THEN
7838                 f2 = 1.0_wp
7839              ELSE
7840                 f2 = 1.0E-20_wp
7841              ENDIF
7842       
7843!
7844!--          Calculate water vapour pressure at saturation
7845              e_s = 0.01_wp * 610.78_wp * EXP( 17.269_wp * ( t_surf_green_h(m) &
7846                            - 273.16_wp ) / ( t_surf_green_h(m) - 35.86_wp ) )
7847!
7848!--           f3: correction for vapour pressure deficit
7849              IF ( surf_usm_h%g_d(m) /= 0.0_wp )  THEN
7850!
7851!--           Calculate vapour pressure
7852                 e  = qv1 * surface_pressure / ( qv1 + 0.622_wp )
7853                 f3 = EXP ( - surf_usm_h%g_d(m) * (e_s - e) )
7854              ELSE
7855                 f3 = 1.0_wp
7856              ENDIF
7857
7858!
7859!--           Calculate canopy resistance. In case that c_veg is 0 (bare soils),
7860!--           this calculation is obsolete, as r_canopy is not used below.
7861!--           To do: check for very dry soil -> r_canopy goes to infinity
7862              surf_usm_h%r_canopy(m) = surf_usm_h%r_canopy_min(m) /                   &
7863                              ( surf_usm_h%lai(m) * f1 * f2 * f3 + 1.0E-20_wp )
7864
7865!
7866!--           Calculate the maximum possible liquid water amount on plants and
7867!--           bare surface. For vegetated surfaces, a maximum depth of 0.2 mm is
7868!--           assumed, while paved surfaces might hold up 1 mm of water. The
7869!--           liquid water fraction for paved surfaces is calculated after
7870!--           Noilhan & Planton (1989), while the ECMWF formulation is used for
7871!--           vegetated surfaces and bare soils.
7872              m_liq_max = m_max_depth * ( surf_usm_h%lai(m) )
7873              surf_usm_h%c_liq(m) = MIN( 1.0_wp, ( m_liq_usm_h%var_usm_1d(m) / m_liq_max )**0.67 )
7874!
7875!--           Calculate saturation specific humidity
7876              q_s = 0.622_wp * e_s / ( surface_pressure - e_s )
7877!
7878!--           In case of dewfall, set evapotranspiration to zero
7879!--           All super-saturated water is then removed from the air
7880              IF ( humidity  .AND.  q_s <= qv1 )  THEN
7881                 surf_usm_h%r_canopy(m) = 0.0_wp
7882              ENDIF
7883
7884!
7885!--           Calculate coefficients for the total evapotranspiration
7886!--           In case of water surface, set vegetation and soil fluxes to zero.
7887!--           For pavements, only evaporation of liquid water is possible.
7888              f_qsws_veg  = rho_lv *                                           &
7889                                ( 1.0_wp        - surf_usm_h%c_liq(m)    ) /   &
7890                                ( surf_usm_h%r_a_green(m) + surf_usm_h%r_canopy(m) )
7891              f_qsws_liq  = rho_lv * surf_usm_h%c_liq(m)   /                   &
7892                                  surf_usm_h%r_a_green(m)
7893       
7894              f_qsws = f_qsws_veg + f_qsws_liq
7895!
7896!--           Calculate derivative of q_s for Taylor series expansion
7897              e_s_dt = e_s * ( 17.269_wp / ( t_surf_green_h(m) - 35.86_wp) -   &
7898                               17.269_wp*( t_surf_green_h(m) - 273.16_wp)      &
7899                              / ( t_surf_green_h(m) - 35.86_wp)**2 )
7900       
7901              dq_s_dt = 0.622_wp * e_s_dt / ( surface_pressure - e_s_dt )
7902           ENDIF
7903!
7904!--        add LW up so that it can be removed in prognostic equation
7905           surf_usm_h%rad_net_l(m) = surf_usm_h%rad_sw_in(m)  -                &
7906                                     surf_usm_h%rad_sw_out(m) +                &
7907                                     surf_usm_h%rad_lw_in(m)  -                &
7908                                     surf_usm_h%rad_lw_out(m)
7909!
7910!--     numerator of the prognostic equation
7911!--     Todo: Adjust to tile approach. So far, emissivity for wall (element 0)
7912!--     is used
7913           coef_1 = surf_usm_h%rad_net_l(m) +                                  & 
7914                 ( 3.0_wp + 1.0_wp ) * surf_usm_h%emissivity(ind_veg_wall,m) * &
7915                                       sigma_sb * t_surf_wall_h(m) ** 4 +      & 
7916                                       f_shf * surf_usm_h%pt1(m) +             &
7917                                       lambda_surface * t_wall_h(nzb_wall,m)
7918           IF ( ( .NOT. during_spinup ) .AND. (surf_usm_h%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
7919              coef_window_1 = surf_usm_h%rad_net_l(m) +                           & 
7920                      ( 3.0_wp + 1.0_wp ) * surf_usm_h%emissivity(ind_wat_win,m)  &
7921                                          * sigma_sb * t_surf_window_h(m) ** 4 +  & 
7922                                          f_shf_window * surf_usm_h%pt1(m) +      &
7923                                          lambda_surface_window * t_window_h(nzb_wall,m)
7924           ENDIF                 
7925           IF ( ( humidity ) .AND. ( surf_usm_h%frac(ind_pav_green,m) > 0.0_wp ) )  THEN
7926                    coef_green_1 = surf_usm_h%rad_net_l(m) +                                 & 
7927                   ( 3.0_wp + 1.0_wp ) * surf_usm_h%emissivity(ind_pav_green,m) * sigma_sb * &
7928                                       t_surf_green_h(m) ** 4 +                  & 
7929                                          f_shf_green * surf_usm_h%pt1(m) + f_qsws * ( qv1 - q_s    &
7930                                          + dq_s_dt * t_surf_green_h(m) )        &
7931                                          +lambda_surface_green * t_green_h(nzb_wall,m)
7932           ELSE
7933           coef_green_1 = surf_usm_h%rad_net_l(m) +                            & 
7934                 ( 3.0_wp + 1.0_wp ) * surf_usm_h%emissivity(ind_pav_green,m) *&
7935                                       sigma_sb * t_surf_green_h(m) ** 4 +     & 
7936                                       f_shf_green * surf_usm_h%pt1(m) +       &
7937                                       lambda_surface_green * t_green_h(nzb_wall,m)
7938          ENDIF
7939!
7940!--        denominator of the prognostic equation
7941           coef_2 = 4.0_wp * surf_usm_h%emissivity(ind_veg_wall,m) *           &
7942                             sigma_sb * t_surf_wall_h(m) ** 3                  &
7943                           + lambda_surface + f_shf / exner(k)
7944           IF ( ( .NOT. during_spinup ) .AND. ( surf_usm_h%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
7945              coef_window_2 = 4.0_wp * surf_usm_h%emissivity(ind_wat_win,m) *     &
7946                                sigma_sb * t_surf_window_h(m) ** 3                &
7947                              + lambda_surface_window + f_shf_window / exner(k)
7948           ENDIF
7949           IF ( ( humidity ) .AND. ( surf_usm_h%frac(ind_pav_green,m) > 0.0_wp ) )  THEN
7950              coef_green_2 = 4.0_wp * surf_usm_h%emissivity(ind_pav_green,m) * sigma_sb *    &
7951                                t_surf_green_h(m) ** 3 + f_qsws * dq_s_dt                    &
7952                              + lambda_surface_green + f_shf_green / exner(k)
7953           ELSE
7954           coef_green_2 = 4.0_wp * surf_usm_h%emissivity(ind_pav_green,m) * sigma_sb *    &
7955                             t_surf_green_h(m) ** 3                                       &
7956                           + lambda_surface_green + f_shf_green / exner(k)
7957           ENDIF
7958!
7959!--        implicit solution when the surface layer has no heat capacity,
7960!--        otherwise use RK3 scheme.
7961           t_surf_wall_h_p(m) = ( coef_1 * dt_3d * tsc(2) +                        &
7962                             surf_usm_h%c_surface(m) * t_surf_wall_h(m) ) /        & 
7963                           ( surf_usm_h%c_surface(m) + coef_2 * dt_3d * tsc(2) ) 
7964           IF (( .NOT. during_spinup ) .AND. (surf_usm_h%frac(ind_wat_win,m) > 0.0_wp)) THEN
7965              t_surf_window_h_p(m) = ( coef_window_1 * dt_3d * tsc(2) +                        &
7966                                surf_usm_h%c_surface_window(m) * t_surf_window_h(m) ) /        & 
7967                              ( surf_usm_h%c_surface_window(m) + coef_window_2 * dt_3d * tsc(2) )
7968           ENDIF
7969           t_surf_green_h_p(m) = ( coef_green_1 * dt_3d * tsc(2) +                        &
7970                             surf_usm_h%c_surface_green(m) * t_surf_green_h(m) ) /        & 
7971                           ( surf_usm_h%c_surface_green(m) + coef_green_2 * dt_3d * tsc(2) ) 
7972!
7973!--        add RK3 term
7974           t_surf_wall_h_p(m) = t_surf_wall_h_p(m) + dt_3d * tsc(3) *         &
7975                           surf_usm_h%tt_surface_wall_m(m)
7976
7977           t_surf_window_h_p(m) = t_surf_window_h_p(m) + dt_3d * tsc(3) *     &
7978                           surf_usm_h%tt_surface_window_m(m)
7979
7980           t_surf_green_h_p(m) = t_surf_green_h_p(m) + dt_3d * tsc(3) *       &
7981                           surf_usm_h%tt_surface_green_m(m)
7982!
7983!--        Store surface temperature on pt_surface. Further, in case humidity is used
7984!--        store also vpt_surface, which is, due to the lack of moisture on roofs simply
7985!--        assumed to be the surface temperature.
7986           surf_usm_h%pt_surface(m) = ( surf_usm_h%frac(ind_veg_wall,m) * t_surf_wall_h_p(m)   &
7987                               + surf_usm_h%frac(ind_wat_win,m) * t_surf_window_h_p(m)         &
7988                               + surf_usm_h%frac(ind_pav_green,m) * t_surf_green_h_p(m) )      &
7989                               / exner(k)
7990                               
7991           IF ( humidity )  surf_usm_h%vpt_surface(m) =                        &
7992                                                   surf_usm_h%pt_surface(m)
7993!
7994!--        calculate true tendency
7995           stend_wall = ( t_surf_wall_h_p(m) - t_surf_wall_h(m) - dt_3d * tsc(3) *              &
7996                     surf_usm_h%tt_surface_wall_m(m)) / ( dt_3d  * tsc(2) )
7997           stend_window = ( t_surf_window_h_p(m) - t_surf_window_h(m) - dt_3d * tsc(3) *        &
7998                     surf_usm_h%tt_surface_window_m(m)) / ( dt_3d  * tsc(2) )
7999           stend_green = ( t_surf_green_h_p(m) - t_surf_green_h(m) - dt_3d * tsc(3) *           &
8000                     surf_usm_h%tt_surface_green_m(m)) / ( dt_3d  * tsc(2) )
8001!
8002!--        calculate t_surf tendencies for the next Runge-Kutta step
8003           IF ( timestep_scheme(1:5) == 'runge' )  THEN
8004              IF ( intermediate_timestep_count == 1 )  THEN
8005                 surf_usm_h%tt_surface_wall_m(m) = stend_wall
8006                 surf_usm_h%tt_surface_window_m(m) = stend_window
8007                 surf_usm_h%tt_surface_green_m(m) = stend_green
8008              ELSEIF ( intermediate_timestep_count <                          &
8009                        intermediate_timestep_count_max )  THEN
8010                 surf_usm_h%tt_surface_wall_m(m) = -9.5625_wp * stend_wall +       &
8011                                     5.3125_wp * surf_usm_h%tt_surface_wall_m(m)
8012                 surf_usm_h%tt_surface_window_m(m) = -9.5625_wp * stend_window +   &
8013                                     5.3125_wp * surf_usm_h%tt_surface_window_m(m)
8014                 surf_usm_h%tt_surface_green_m(m) = -9.5625_wp * stend_green +     &
8015                                     5.3125_wp * surf_usm_h%tt_surface_green_m(m)
8016              ENDIF
8017           ENDIF
8018!
8019!--        in case of fast changes in the skin temperature, it is required to
8020!--        update the radiative fluxes in order to keep the solution stable
8021           IF ( ( ( ABS( t_surf_wall_h_p(m)   - t_surf_wall_h(m) )   > 1.0_wp )   .OR. &
8022                (   ABS( t_surf_green_h_p(m)  - t_surf_green_h(m) )  > 1.0_wp )   .OR. &
8023                (   ABS( t_surf_window_h_p(m) - t_surf_window_h(m) ) > 1.0_wp ) )      &
8024                   .AND.  unscheduled_radiation_calls  )  THEN
8025              force_radiation_call_l = .TRUE.
8026           ENDIF
8027!
8028!--        calculate fluxes
8029!--        rad_net_l is never used!
8030           surf_usm_h%rad_net_l(m) = surf_usm_h%rad_net_l(m) +                           &
8031                                     surf_usm_h%frac(ind_veg_wall,m) *                   &
8032                                     sigma_sb * surf_usm_h%emissivity(ind_veg_wall,m) *  &
8033                                     ( t_surf_wall_h_p(m)**4 - t_surf_wall_h(m)**4 )     &
8034                                    + surf_usm_h%frac(ind_wat_win,m) *                   &
8035                                     sigma_sb * surf_usm_h%emissivity(ind_wat_win,m) *   &
8036                                     ( t_surf_window_h_p(m)**4 - t_surf_window_h(m)**4 ) &
8037                                    + surf_usm_h%frac(ind_pav_green,m) *                 &
8038                                     sigma_sb * surf_usm_h%emissivity(ind_pav_green,m) * &
8039                                     ( t_surf_green_h_p(m)**4 - t_surf_green_h(m)**4 )
8040
8041           surf_usm_h%wghf_eb(m)   = lambda_surface *                                    &
8042                                      ( t_surf_wall_h_p(m) - t_wall_h(nzb_wall,m) )
8043           surf_usm_h%wghf_eb_green(m)  = lambda_surface_green *                         &
8044                                          ( t_surf_green_h_p(m) - t_green_h(nzb_wall,m) )
8045           surf_usm_h%wghf_eb_window(m) = lambda_surface_window *                        &
8046                                           ( t_surf_window_h_p(m) - t_window_h(nzb_wall,m) )
8047
8048!
8049!--        ground/wall/roof surface heat flux
8050           surf_usm_h%wshf_eb(m)   = - f_shf  * ( surf_usm_h%pt1(m) - t_surf_wall_h_p(m) / exner(k) ) *          &
8051                                       surf_usm_h%frac(ind_veg_wall,m)         &
8052                                     - f_shf_window  * ( surf_usm_h%pt1(m) - t_surf_window_h_p(m) / exner(k) ) * &
8053                                       surf_usm_h%frac(ind_wat_win,m)          &
8054                                     - f_shf_green  * ( surf_usm_h%pt1(m) - t_surf_green_h_p(m) / exner(k) ) *   &
8055                                       surf_usm_h%frac(ind_pav_green,m)
8056!           
8057!--        store kinematic surface heat fluxes for utilization in other processes
8058!--        diffusion_s, surface_layer_fluxes,...
8059           surf_usm_h%shf(m) = surf_usm_h%wshf_eb(m) / c_p
8060!
8061!--        If the indoor model is applied, further add waste heat from buildings to the
8062!--        kinematic flux.
8063           IF ( indoor_model )  THEN
8064              surf_usm_h%shf(m) = surf_usm_h%shf(m) + surf_usm_h%waste_heat(m) / c_p
8065           ENDIF
8066     
8067
8068           IF (surf_usm_h%frac(ind_pav_green,m) > 0.0_wp) THEN
8069             
8070           
8071              IF ( humidity )  THEN
8072                 surf_usm_h%qsws(m)  = - f_qsws * ( qv1 - q_s + dq_s_dt                     &
8073                                 * t_surf_green_h(m) - dq_s_dt *               &
8074                                   t_surf_green_h_p(m) )
8075       
8076                 surf_usm_h%qsws_veg(m)  = - f_qsws_veg  * ( qv1 - q_s                      &
8077                                     + dq_s_dt * t_surf_green_h(m) - dq_s_dt   &
8078                                     * t_surf_green_h_p(m) )
8079       
8080                 surf_usm_h%qsws_liq(m)  = - f_qsws_liq  * ( qv1 - q_s                      &
8081                                     + dq_s_dt * t_surf_green_h(m) - dq_s_dt   &
8082                                     * t_surf_green_h_p(m) )
8083                                     
8084              ENDIF
8085 
8086!
8087!--           Calculate the true surface resistance
8088              IF ( .NOT.  humidity )  THEN
8089                 surf_usm_h%r_s(m) = 1.0E10_wp
8090              ELSE
8091                 surf_usm_h%r_s(m) = - rho_lv * ( qv1 - q_s + dq_s_dt                       &
8092                                 *  t_surf_green_h(m) - dq_s_dt *              &
8093                                   t_surf_green_h_p(m) ) /                     &
8094                                   (surf_usm_h%qsws(m) + 1.0E-20)  - surf_usm_h%r_a_green(m)
8095              ENDIF
8096 
8097!
8098!--           Calculate change in liquid water reservoir due to dew fall or
8099!--           evaporation of liquid water
8100              IF ( humidity )  THEN
8101!
8102!--              If precipitation is activated, add rain water to qsws_liq
8103!--              and qsws_soil according the the vegetation coverage.
8104!--              precipitation_rate is given in mm.
8105                 IF ( precipitation )  THEN
8106
8107!
8108!--                 Add precipitation to liquid water reservoir, if possible.
8109!--                 Otherwise, add the water to soil. In case of
8110!--                 pavements, the exceeding water amount is implicitely removed
8111!--                 as runoff as qsws_soil is then not used in the soil model
8112                    IF ( m_liq_usm_h%var_usm_1d(m) /= m_liq_max )  THEN
8113                       surf_usm_h%qsws_liq(m) = surf_usm_h%qsws_liq(m)                &
8114                                        + surf_usm_h%frac(ind_pav_green,m) * prr(k+k_off,j+j_off,i+i_off)&
8115                                        * hyrho(k+k_off)                              &
8116                                        * 0.001_wp * rho_l * l_v
8117                   ENDIF
8118
8119                 ENDIF
8120
8121!
8122!--              If the air is saturated, check the reservoir water level
8123                 IF ( surf_usm_h%qsws(m) < 0.0_wp )  THEN
8124!
8125!--                 Check if reservoir is full (avoid values > m_liq_max)
8126!--                 In that case, qsws_liq goes to qsws_soil. In this
8127!--                 case qsws_veg is zero anyway (because c_liq = 1),       
8128!--                 so that tend is zero and no further check is needed
8129                    IF ( m_liq_usm_h%var_usm_1d(m) == m_liq_max )  THEN
8130!                      surf_usm_h%qsws_soil(m) = surf_usm_h%qsws_soil(m) + surf_usm_h%qsws_liq(m)
8131                       surf_usm_h%qsws_liq(m)  = 0.0_wp
8132                    ENDIF
8133
8134!
8135!--                 In case qsws_veg becomes negative (unphysical behavior),
8136!--                 let the water enter the liquid water reservoir as dew on the
8137!--                 plant
8138                    IF ( surf_usm_h%qsws_veg(m) < 0.0_wp )  THEN
8139                       surf_usm_h%qsws_liq(m) = surf_usm_h%qsws_liq(m) + surf_usm_h%qsws_veg(m)
8140                       surf_usm_h%qsws_veg(m) = 0.0_wp
8141                    ENDIF
8142                 ENDIF                   
8143 
8144                 surf_usm_h%qsws(m) = surf_usm_h%qsws(m) / l_v
8145       
8146                 tend = - surf_usm_h%qsws_liq(m) * drho_l_lv
8147                 m_liq_usm_h_p%var_usm_1d(m) = m_liq_usm_h%var_usm_1d(m) + dt_3d *    &
8148                                               ( tsc(2) * tend +                      &
8149                                                 tsc(3) * tm_liq_usm_h_m%var_usm_1d(m) )
8150!
8151!--             Check if reservoir is overfull -> reduce to maximum
8152!--             (conservation of water is violated here)
8153                 m_liq_usm_h_p%var_usm_1d(m) = MIN( m_liq_usm_h_p%var_usm_1d(m),m_liq_max )
8154 
8155!
8156!--             Check if reservoir is empty (avoid values < 0.0)
8157!--             (conservation of water is violated here)
8158                 m_liq_usm_h_p%var_usm_1d(m) = MAX( m_liq_usm_h_p%var_usm_1d(m), 0.0_wp )
8159!
8160!--             Calculate m_liq tendencies for the next Runge-Kutta step
8161                 IF ( timestep_scheme(1:5) == 'runge' )  THEN
8162                    IF ( intermediate_timestep_count == 1 )  THEN
8163                       tm_liq_usm_h_m%var_usm_1d(m) = tend
8164                    ELSEIF ( intermediate_timestep_count <                            &
8165                             intermediate_timestep_count_max )  THEN
8166                       tm_liq_usm_h_m%var_usm_1d(m) = -9.5625_wp * tend +             &
8167                                                     5.3125_wp * tm_liq_usm_h_m%var_usm_1d(m)
8168                    ENDIF
8169                 ENDIF
8170 
8171              ENDIF
8172           ELSE
8173              surf_usm_h%r_s(m) = 1.0E10_wp
8174           ENDIF
8175!
8176!--        During spinup green and window fraction are set to zero. Here, the original
8177!--        values are restored.
8178           IF ( during_spinup )  THEN
8179              surf_usm_h%frac(ind_wat_win,m)   = frac_win
8180              surf_usm_h%frac(ind_veg_wall,m)  = frac_wall
8181              surf_usm_h%frac(ind_pav_green,m) = frac_green
8182           ENDIF
8183 
8184       ENDDO
8185!
8186!--    Now, treat vertical surface elements
8187       !$OMP DO SCHEDULE (STATIC)
8188       DO  l = 0, 3
8189           DO  m = 1, surf_usm_v(l)%ns
8190!
8191!--           During spinup set green and window fraction to zero and restore
8192!--           at the end of the loop.
8193!--           Note, this is a temporary fix and need to be removed later.
8194              IF ( during_spinup )  THEN
8195                 frac_win   = surf_usm_v(l)%frac(ind_wat_win,m)
8196                 frac_wall  = surf_usm_v(l)%frac(ind_veg_wall,m)
8197                 frac_green = surf_usm_v(l)%frac(ind_pav_green,m)
8198                 surf_usm_v(l)%frac(ind_wat_win,m)   = 0.0_wp
8199                 surf_usm_v(l)%frac(ind_veg_wall,m)  = 1.0_wp
8200                 surf_usm_v(l)%frac(ind_pav_green,m) = 0.0_wp
8201              ENDIF
8202!
8203!--          Get indices of respective grid point
8204              i = surf_usm_v(l)%i(m)
8205              j = surf_usm_v(l)%j(m)
8206              k = surf_usm_v(l)%k(m)
8207 
8208!
8209!--          TODO - how to calculate lambda_surface for horizontal (??? do you mean verical ???) surfaces
8210!--          (lambda_surface is set according to stratification in land surface model).
8211!--          Please note, for vertical surfaces no ol is defined, since
8212!--          stratification is not considered in this case.
8213              lambda_surface = surf_usm_v(l)%lambda_surf(m)
8214              lambda_surface_window = surf_usm_v(l)%lambda_surf_window(m)
8215              lambda_surface_green = surf_usm_v(l)%lambda_surf_green(m)
8216 
8217!            pt1  = pt(k,j,i)
8218              IF ( humidity )  THEN
8219                 qv1 = q(k,j,i)
8220              ELSE
8221                 qv1 = 0.0_wp
8222              ENDIF
8223!
8224!--          calculate rho * c_p coefficient at wall layer
8225              rho_cp  = c_p * hyp(k) / ( r_d * surf_usm_v(l)%pt1(m) * exner(k) )
8226             
8227              IF (surf_usm_v(l)%frac(1,m) > 0.0_wp )  THEN
8228!
8229!--            Calculate frequently used parameters
8230                 rho_lv    = rho_cp / c_p * l_v
8231                 drho_l_lv = 1.0_wp / (rho_l * l_v)
8232              ENDIF
8233 
8234!--          Calculation of r_a for vertical surfaces
8235!--
8236!--          heat transfer coefficient for forced convection along vertical walls
8237!--          follows formulation in TUF3d model (Krayenhoff & Voogt, 2006)
8238!--           
8239!--          H = httc (Tsfc - Tair)
8240!--          httc = rw * (11.8 + 4.2 * Ueff) - 4.0
8241!--           
8242!--                rw: wall patch roughness relative to 1.0 for concrete
8243!--                Ueff: effective wind speed
8244!--                - 4.0 is a reduction of Rowley et al (1930) formulation based on
8245!--                Cole and Sturrock (1977)
8246!--           
8247!--                Ucan: Canyon wind speed
8248!--                wstar: convective velocity
8249!--                Qs: surface heat flux
8250!--                zH: height of the convective layer
8251!--                wstar = (g/Tcan*Qs*zH)**(1./3.)
8252!--          Effective velocity components must always
8253!--          be defined at scalar grid point. The wall normal component is
8254!--          obtained by simple linear interpolation. ( An alternative would
8255!--          be an logarithmic interpolation. )
8256!--          Parameter roughness_concrete (default value = 0.001) is used
8257!--          to calculation of roughness relative to concrete
8258              surf_usm_v(l)%r_a(m) = rho_cp / ( surf_usm_v(l)%z0(m) /           &
8259                         roughness_concrete * ( 11.8_wp + 4.2_wp *              &
8260                         SQRT( MAX( ( ( u(k,j,i) + u(k,j,i+1) ) * 0.5_wp )**2 + &
8261                                    ( ( v(k,j,i) + v(k,j+1,i) ) * 0.5_wp )**2 + &
8262                                    ( ( w(k,j,i) + w(k-1,j,i) ) * 0.5_wp )**2,  &
8263                               0.01_wp ) )                                      &
8264                            )  - 4.0_wp  ) 
8265!
8266!--          Limit aerodynamic resistance
8267              IF ( surf_usm_v(l)%r_a(m) < 1.0_wp )  surf_usm_v(l)%r_a(m) = 1.0_wp   
8268             
8269                           
8270              f_shf         = rho_cp / surf_usm_v(l)%r_a(m)
8271              f_shf_window  = rho_cp / surf_usm_v(l)%r_a(m)
8272              f_shf_green   = rho_cp / surf_usm_v(l)%r_a(m)
8273 
8274
8275              IF ( surf_usm_v(l)%frac(1,m) > 0.0_wp ) THEN
8276!
8277!--             Adapted from LSM:
8278!--             Second step: calculate canopy resistance r_canopy
8279!--             f1-f3 here are defined as 1/f1-f3 as in ECMWF documentation
8280!--             f1: correction for incoming shortwave radiation (stomata close at
8281!--             night)
8282                 f1 = MIN( 1.0_wp, ( 0.004_wp * surf_usm_v(l)%rad_sw_in(m) + 0.05_wp ) / &
8283                                  (0.81_wp * (0.004_wp * surf_usm_v(l)%rad_sw_in(m)      &
8284                                   + 1.0_wp)) )
8285!
8286!--             f2: correction for soil moisture availability to plants (the
8287!--             integrated soil moisture must thus be considered here)
8288!--             f2 = 0 for very dry soils
8289 
8290                 f2=1.0_wp
8291 
8292!
8293!--              Calculate water vapour pressure at saturation
8294                 e_s = 0.01_wp * 610.78_wp * EXP( 17.269_wp * (  t_surf_green_v_p(l)%t(m) &
8295                               - 273.16_wp ) / (  t_surf_green_v_p(l)%t(m) - 35.86_wp ) )
8296!
8297!--              f3: correction for vapour pressure deficit
8298                 IF ( surf_usm_v(l)%g_d(m) /= 0.0_wp )  THEN
8299!
8300!--                 Calculate vapour pressure
8301                    e  = qv1 * surface_pressure / ( qv1 + 0.622_wp )
8302                    f3 = EXP ( - surf_usm_v(l)%g_d(m) * (e_s - e) )
8303                 ELSE
8304                    f3 = 1.0_wp
8305                 ENDIF
8306!
8307!--              Calculate canopy resistance. In case that c_veg is 0 (bare soils),
8308!--              this calculation is obsolete, as r_canopy is not used below.
8309!--              To do: check for very dry soil -> r_canopy goes to infinity
8310                 surf_usm_v(l)%r_canopy(m) = surf_usm_v(l)%r_canopy_min(m) /                  &
8311                                        ( surf_usm_v(l)%lai(m) * f1 * f2 * f3 + 1.0E-20_wp )
8312                               
8313!
8314!--              Calculate saturation specific humidity
8315                 q_s = 0.622_wp * e_s / ( surface_pressure - e_s )
8316!
8317!--              In case of dewfall, set evapotranspiration to zero
8318!--              All super-saturated water is then removed from the air
8319                 IF ( humidity  .AND.  q_s <= qv1 )  THEN
8320                    surf_usm_v(l)%r_canopy(m) = 0.0_wp
8321                 ENDIF
8322 
8323!
8324!--              Calculate coefficients for the total evapotranspiration
8325!--              In case of water surface, set vegetation and soil fluxes to zero.
8326!--              For pavements, only evaporation of liquid water is possible.
8327                 f_qsws_veg  = rho_lv *                                &
8328                                   ( 1.0_wp        - 0.0_wp ) / & !surf_usm_h%c_liq(m)    ) /   &
8329                                   ( surf_usm_v(l)%r_a(m) + surf_usm_v(l)%r_canopy(m) )
8330!                f_qsws_liq  = rho_lv * surf_usm_h%c_liq(m)   /             &
8331!                              surf_usm_h%r_a_green(m)
8332         
8333                 f_qsws = f_qsws_veg! + f_qsws_liq
8334!
8335!--              Calculate derivative of q_s for Taylor series expansion
8336                 e_s_dt = e_s * ( 17.269_wp / ( t_surf_green_v_p(l)%t(m) - 35.86_wp) -   &
8337                                  17.269_wp*( t_surf_green_v_p(l)%t(m) - 273.16_wp)      &
8338                                 / ( t_surf_green_v_p(l)%t(m) - 35.86_wp)**2 )
8339         
8340                 dq_s_dt = 0.622_wp * e_s_dt / ( surface_pressure - e_s_dt )
8341              ENDIF
8342
8343!
8344!--           add LW up so that it can be removed in prognostic equation
8345              surf_usm_v(l)%rad_net_l(m) = surf_usm_v(l)%rad_sw_in(m)  -        &
8346                                           surf_usm_v(l)%rad_sw_out(m) +        &
8347                                           surf_usm_v(l)%rad_lw_in(m)  -        &
8348                                           surf_usm_v(l)%rad_lw_out(m)
8349!
8350!--           numerator of the prognostic equation
8351              coef_1 = surf_usm_v(l)%rad_net_l(m) +                             & ! coef +1 corresponds to -lwout
8352                                                                                  ! included in calculation of radnet_l
8353              ( 3.0_wp + 1.0_wp ) * surf_usm_v(l)%emissivity(ind_veg_wall,m) *  &
8354                                      sigma_sb *  t_surf_wall_v(l)%t(m) ** 4 +  & 
8355                                      f_shf * surf_usm_v(l)%pt1(m) +            &
8356                                      lambda_surface * t_wall_v(l)%t(nzb_wall,m)
8357              IF ( ( .NOT. during_spinup ) .AND. ( surf_usm_v(l)%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
8358                 coef_window_1 = surf_usm_v(l)%rad_net_l(m) +                   & ! coef +1 corresponds to -lwout
8359                                                                                  ! included in calculation of radnet_l
8360                ( 3.0_wp + 1.0_wp ) * surf_usm_v(l)%emissivity(ind_wat_win,m) * &
8361                                      sigma_sb * t_surf_window_v(l)%t(m) ** 4 + & 
8362                                      f_shf * surf_usm_v(l)%pt1(m) +            &
8363                                      lambda_surface_window * t_window_v(l)%t(nzb_wall,m)
8364              ENDIF
8365              IF ( ( humidity ) .AND. ( surf_usm_v(l)%frac(ind_pav_green,m) > 0.0_wp ) )  THEN
8366                 coef_green_1 = surf_usm_v(l)%rad_net_l(m) +                      & ! coef +1 corresponds to -lwout
8367                                                                                    ! included in calculation of radnet_l
8368                 ( 3.0_wp + 1.0_wp ) * surf_usm_v(l)%emissivity(ind_pav_green,m) * sigma_sb *  &
8369                                      t_surf_green_v(l)%t(m) ** 4 +               & 
8370                                      f_shf * surf_usm_v(l)%pt1(m) +     f_qsws * ( qv1 - q_s  &
8371                                           + dq_s_dt * t_surf_green_v(l)%t(m) ) +              &
8372                                      lambda_surface_green * t_wall_v(l)%t(nzb_wall,m)
8373              ELSE
8374                coef_green_1 = surf_usm_v(l)%rad_net_l(m) +                       & ! coef +1 corresponds to -lwout included
8375                                                                                    ! in calculation of radnet_l
8376                ( 3.0_wp + 1.0_wp ) * surf_usm_v(l)%emissivity(ind_pav_green,m) * sigma_sb *  &
8377                                      t_surf_green_v(l)%t(m) ** 4 +               & 
8378                                      f_shf * surf_usm_v(l)%pt1(m) +              &
8379                                      lambda_surface_green * t_wall_v(l)%t(nzb_wall,m)
8380              ENDIF
8381                                     
8382!
8383!--           denominator of the prognostic equation
8384              coef_2 = 4.0_wp * surf_usm_v(l)%emissivity(ind_veg_wall,m) * sigma_sb *   &
8385                                 t_surf_wall_v(l)%t(m) ** 3                             &
8386                               + lambda_surface + f_shf / exner(k) 
8387              IF ( ( .NOT. during_spinup ) .AND. ( surf_usm_v(l)%frac(ind_wat_win,m) > 0.0_wp ) ) THEN             
8388                 coef_window_2 = 4.0_wp * surf_usm_v(l)%emissivity(ind_wat_win,m) * sigma_sb *       &
8389                                   t_surf_window_v(l)%t(m) ** 3                         &
8390                                 + lambda_surface_window + f_shf / exner(k)
8391              ENDIF
8392              IF ( ( humidity ) .AND. ( surf_usm_v(l)%frac(ind_pav_green,m) > 0.0_wp ) )  THEN
8393                  coef_green_2 = 4.0_wp * surf_usm_v(l)%emissivity(ind_pav_green,m) * sigma_sb *     &
8394                                   t_surf_green_v(l)%t(m) ** 3  + f_qsws * dq_s_dt      &
8395                                 + lambda_surface_green + f_shf / exner(k)
8396              ELSE
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                          &
8399                                 + lambda_surface_green + f_shf / exner(k)
8400              ENDIF
8401!
8402!--           implicit solution when the surface layer has no heat capacity,
8403!--           otherwise use RK3 scheme.
8404              t_surf_wall_v_p(l)%t(m) = ( coef_1 * dt_3d * tsc(2) +                 &
8405                             surf_usm_v(l)%c_surface(m) * t_surf_wall_v(l)%t(m) ) / & 
8406                             ( surf_usm_v(l)%c_surface(m) + coef_2 * dt_3d * tsc(2) ) 
8407              IF ( ( .NOT. during_spinup ) .AND. ( surf_usm_v(l)%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
8408                 t_surf_window_v_p(l)%t(m) = ( coef_window_1 * dt_3d * tsc(2) +                 &
8409                                surf_usm_v(l)%c_surface_window(m) * t_surf_window_v(l)%t(m) ) / & 
8410                              ( surf_usm_v(l)%c_surface_window(m) + coef_window_2 * dt_3d * tsc(2) ) 
8411              ENDIF
8412              t_surf_green_v_p(l)%t(m) = ( coef_green_1 * dt_3d * tsc(2) +                 &
8413                             surf_usm_v(l)%c_surface_green(m) * t_surf_green_v(l)%t(m) ) / & 
8414                           ( surf_usm_v(l)%c_surface_green(m) + coef_green_2 * dt_3d * tsc(2) ) 
8415!
8416!--           add RK3 term
8417              t_surf_wall_v_p(l)%t(m) = t_surf_wall_v_p(l)%t(m) + dt_3d * tsc(3) *         &
8418                                surf_usm_v(l)%tt_surface_wall_m(m)
8419              t_surf_window_v_p(l)%t(m) = t_surf_window_v_p(l)%t(m) + dt_3d * tsc(3) *     &
8420                                surf_usm_v(l)%tt_surface_window_m(m)
8421              t_surf_green_v_p(l)%t(m) = t_surf_green_v_p(l)%t(m) + dt_3d * tsc(3) *       &
8422                                 surf_usm_v(l)%tt_surface_green_m(m)
8423!
8424!--           Store surface temperature. Further, in case humidity is used
8425!--           store also vpt_surface, which is, due to the lack of moisture on roofs simply
8426!--           assumed to be the surface temperature.     
8427              surf_usm_v(l)%pt_surface(m) =  ( surf_usm_v(l)%frac(ind_veg_wall,m) * t_surf_wall_v_p(l)%t(m)  &
8428                                      + surf_usm_v(l)%frac(ind_wat_win,m) * t_surf_window_v_p(l)%t(m)        &
8429                                      + surf_usm_v(l)%frac(ind_pav_green,m) * t_surf_green_v_p(l)%t(m) )     &
8430                                      / exner(k)
8431                                       
8432              IF ( humidity )  surf_usm_v(l)%vpt_surface(m) =                  &
8433                                                     surf_usm_v(l)%pt_surface(m)
8434!
8435!--           calculate true tendency
8436              stend_wall = ( t_surf_wall_v_p(l)%t(m) - t_surf_wall_v(l)%t(m) - dt_3d * tsc(3) *      &
8437                        surf_usm_v(l)%tt_surface_wall_m(m) ) / ( dt_3d  * tsc(2) )
8438              stend_window = ( t_surf_window_v_p(l)%t(m) - t_surf_window_v(l)%t(m) - dt_3d * tsc(3) *&
8439                        surf_usm_v(l)%tt_surface_window_m(m) ) / ( dt_3d  * tsc(2) )
8440              stend_green = ( t_surf_green_v_p(l)%t(m) - t_surf_green_v(l)%t(m) - dt_3d * tsc(3) *   &
8441                        surf_usm_v(l)%tt_surface_green_m(m) ) / ( dt_3d  * tsc(2) )
8442
8443!
8444!--           calculate t_surf_* tendencies for the next Runge-Kutta step
8445              IF ( timestep_scheme(1:5) == 'runge' )  THEN
8446                 IF ( intermediate_timestep_count == 1 )  THEN
8447                    surf_usm_v(l)%tt_surface_wall_m(m) = stend_wall
8448                    surf_usm_v(l)%tt_surface_window_m(m) = stend_window
8449                    surf_usm_v(l)%tt_surface_green_m(m) = stend_green
8450                 ELSEIF ( intermediate_timestep_count <                                 &
8451                          intermediate_timestep_count_max )  THEN
8452                    surf_usm_v(l)%tt_surface_wall_m(m) = -9.5625_wp * stend_wall +      &
8453                                     5.3125_wp * surf_usm_v(l)%tt_surface_wall_m(m)
8454                    surf_usm_v(l)%tt_surface_green_m(m) = -9.5625_wp * stend_green +    &
8455                                     5.3125_wp * surf_usm_v(l)%tt_surface_green_m(m)
8456                    surf_usm_v(l)%tt_surface_window_m(m) = -9.5625_wp * stend_window +  &
8457                                     5.3125_wp * surf_usm_v(l)%tt_surface_window_m(m)
8458                 ENDIF
8459              ENDIF
8460
8461!
8462!--           in case of fast changes in the skin temperature, it is required to
8463!--           update the radiative fluxes in order to keep the solution stable
8464 
8465              IF ( ( ( ABS( t_surf_wall_v_p(l)%t(m)   - t_surf_wall_v(l)%t(m) )   > 1.0_wp ) .OR. &
8466                   (   ABS( t_surf_green_v_p(l)%t(m)  - t_surf_green_v(l)%t(m) )  > 1.0_wp ) .OR. &
8467                   (   ABS( t_surf_window_v_p(l)%t(m) - t_surf_window_v(l)%t(m) ) > 1.0_wp ) )    &
8468                      .AND.  unscheduled_radiation_calls )  THEN
8469                 force_radiation_call_l = .TRUE.
8470              ENDIF
8471
8472!
8473!--           calculate fluxes
8474!--           prognostic rad_net_l is used just for output!           
8475              surf_usm_v(l)%rad_net_l(m) = surf_usm_v(l)%frac(ind_veg_wall,m) *                      &
8476                                           ( surf_usm_v(l)%rad_net_l(m) +                            &
8477                                           3.0_wp * sigma_sb *                                       &
8478                                           t_surf_wall_v(l)%t(m)**4 - 4.0_wp * sigma_sb *            &
8479                                           t_surf_wall_v(l)%t(m)**3 * t_surf_wall_v_p(l)%t(m) )      &
8480                                         + surf_usm_v(l)%frac(ind_wat_win,m) *                       &
8481                                           ( surf_usm_v(l)%rad_net_l(m) +                            &
8482                                           3.0_wp * sigma_sb *                                       &
8483                                           t_surf_window_v(l)%t(m)**4 - 4.0_wp * sigma_sb *          &
8484                                           t_surf_window_v(l)%t(m)**3 * t_surf_window_v_p(l)%t(m) )  &
8485                                         + surf_usm_v(l)%frac(ind_pav_green,m) *                     &
8486                                           ( surf_usm_v(l)%rad_net_l(m) +                            &
8487                                           3.0_wp * sigma_sb *                                       &
8488                                           t_surf_green_v(l)%t(m)**4 - 4.0_wp * sigma_sb *           &
8489                                           t_surf_green_v(l)%t(m)**3 * t_surf_green_v_p(l)%t(m) )
8490
8491              surf_usm_v(l)%wghf_eb_window(m) = lambda_surface_window * &
8492                                                ( t_surf_window_v_p(l)%t(m) - t_window_v(l)%t(nzb_wall,m) )
8493              surf_usm_v(l)%wghf_eb(m)   = lambda_surface *             &
8494                                                ( t_surf_wall_v_p(l)%t(m) - t_wall_v(l)%t(nzb_wall,m) )
8495              surf_usm_v(l)%wghf_eb_green(m)  = lambda_surface_green *  &
8496                                                ( t_surf_green_v_p(l)%t(m) - t_green_v(l)%t(nzb_wall,m) )
8497
8498!
8499!--           ground/wall/roof surface heat flux
8500              surf_usm_v(l)%wshf_eb(m)   =                                     &
8501                 - f_shf  * ( surf_usm_v(l)%pt1(m) -                           &
8502                 t_surf_wall_v_p(l)%t(m) / exner(k) ) * surf_usm_v(l)%frac(ind_veg_wall,m)       &
8503                 - f_shf_window  * ( surf_usm_v(l)%pt1(m) -                    &
8504                 t_surf_window_v_p(l)%t(m) / exner(k) ) * surf_usm_v(l)%frac(ind_wat_win,m)&
8505                 - f_shf_green  * ( surf_usm_v(l)%pt1(m) -                     &
8506                 t_surf_green_v_p(l)%t(m) / exner(k) ) * surf_usm_v(l)%frac(ind_pav_green,m)
8507
8508!           
8509!--           store kinematic surface heat fluxes for utilization in other processes
8510!--           diffusion_s, surface_layer_fluxes,...
8511              surf_usm_v(l)%shf(m) = surf_usm_v(l)%wshf_eb(m) / c_p
8512!
8513!--           If the indoor model is applied, further add waste heat from buildings to the
8514!--           kinematic flux.
8515              IF ( indoor_model )  THEN
8516                 surf_usm_v(l)%shf(m) = surf_usm_v(l)%shf(m) +                       &
8517                                        surf_usm_v(l)%waste_heat(m) / c_p
8518              ENDIF             
8519
8520              IF ( surf_usm_v(l)%frac(ind_pav_green,m) > 0.0_wp ) THEN
8521 
8522
8523                 IF ( humidity )  THEN
8524                    surf_usm_v(l)%qsws(m)  = - f_qsws * ( qv1 - q_s + dq_s_dt          &
8525                                    * t_surf_green_v(l)%t(m) - dq_s_dt *               &
8526                                      t_surf_green_v_p(l)%t(m) )
8527         
8528                    surf_usm_v(l)%qsws(m) = surf_usm_v(l)%qsws(m) / l_v
8529         
8530                    surf_usm_v(l)%qsws_veg(m)  = - f_qsws_veg  * ( qv1 - q_s           &
8531                                        + dq_s_dt * t_surf_green_v(l)%t(m) - dq_s_dt   &
8532                                        * t_surf_green_v_p(l)%t(m) )
8533         
8534!                    surf_usm_h%qsws_liq(m)  = - f_qsws_liq  * ( qv1 - q_s         &
8535!                                        + dq_s_dt * t_surf_green_h(m) - dq_s_dt   &
8536!                                        * t_surf_green_h_p(m) )
8537                 ENDIF
8538 
8539!
8540!--              Calculate the true surface resistance
8541                 IF ( .NOT.  humidity )  THEN
8542                    surf_usm_v(l)%r_s(m) = 1.0E10_wp
8543                 ELSE
8544                    surf_usm_v(l)%r_s(m) = - rho_lv * ( qv1 - q_s + dq_s_dt             &
8545                                    *  t_surf_green_v(l)%t(m) - dq_s_dt *               &
8546                                      t_surf_green_v_p(l)%t(m) ) /                      &
8547                                      (surf_usm_v(l)%qsws(m) + 1.0E-20)  - surf_usm_v(l)%r_a(m)
8548                 ENDIF
8549         
8550!
8551!--              Calculate change in liquid water reservoir due to dew fall or
8552!--              evaporation of liquid water
8553                 IF ( humidity )  THEN
8554!
8555!--                 If the air is saturated, check the reservoir water level
8556                    IF ( surf_usm_v(l)%qsws(m) < 0.0_wp )  THEN
8557       
8558!
8559!--                    In case qsws_veg becomes negative (unphysical behavior),
8560!--                    let the water enter the liquid water reservoir as dew on the
8561!--                    plant
8562                       IF ( surf_usm_v(l)%qsws_veg(m) < 0.0_wp )  THEN
8563          !                 surf_usm_h%qsws_liq(m) = surf_usm_h%qsws_liq(m) + surf_usm_h%qsws_veg(m)
8564                          surf_usm_v(l)%qsws_veg(m) = 0.0_wp
8565                       ENDIF
8566                    ENDIF
8567                 
8568                 ENDIF
8569              ELSE
8570                 surf_usm_v(l)%r_s(m) = 1.0E10_wp
8571              ENDIF
8572!
8573!--           During spinup green and window fraction are set to zero. Here, the original
8574!--           values are restored.
8575              IF ( during_spinup )  THEN
8576                 surf_usm_v(l)%frac(ind_wat_win,m)   = frac_win
8577                 surf_usm_v(l)%frac(ind_veg_wall,m)  = frac_wall
8578                 surf_usm_v(l)%frac(ind_pav_green,m) = frac_green
8579              ENDIF
8580
8581           ENDDO
8582 
8583       ENDDO
8584       !$OMP END PARALLEL
8585
8586!
8587!--     Add-up anthropogenic heat, for now only at upward-facing surfaces
8588         IF ( usm_anthropogenic_heat  .AND.  &
8589              intermediate_timestep_count == intermediate_timestep_count_max )  THEN
8590!
8591!--        application of the additional anthropogenic heat sources
8592!--        we considere the traffic for now so all heat is absorbed
8593!--        to the first layer, generalization would be worth.
8594!--        calculation of actual profile coefficient
8595!--        ??? check time_since_reference_point ???
8596            dtime = mod(simulated_time + time_utc_init, 24.0_wp*3600.0_wp)
8597            dhour = INT(dtime/3600.0_wp)
8598
8599!--         TO_DO: activate, if testcase is available
8600!--         !$OMP PARALLEL DO PRIVATE (i, j, k, acoef, rho_cp)
8601!--         it may also improve performance to move get_topography_top_index_ji before the k-loop
8602            DO i = nxl, nxr
8603               DO j = nys, nyn
8604                  DO k = nz_urban_b, min(nz_urban_t,naheatlayers)
8605                     IF ( k > get_topography_top_index_ji( j, i, 's' ) ) THEN
8606!
8607!--                    increase of pt in box i,j,k in time dt_3d
8608!--                    given to anthropogenic heat aheat*acoef (W*m-2)
8609!--                    linear interpolation of coeficient
8610                        acoef = (REAL(dhour+1,wp)-dtime/3600.0_wp)*aheatprof(k,dhour) + &
8611                                (dtime/3600.0_wp-REAL(dhour,wp))*aheatprof(k,dhour+1)
8612                        IF ( aheat(k,j,i) > 0.0_wp )  THEN
8613!
8614!--                       calculate rho * c_p coefficient at layer k
8615                           rho_cp  = c_p * hyp(k) / ( r_d * pt(k+1,j,i) * exner(k) )
8616                           pt(k,j,i) = pt(k,j,i) + aheat(k,j,i)*acoef*dt_3d/(exner(k)*rho_cp*dz(1))
8617                        ENDIF
8618                     ENDIF
8619                  ENDDO
8620               ENDDO
8621            ENDDO
8622 
8623         ENDIF
8624!
8625!--     pt and shf are defined on nxlg:nxrg,nysg:nyng
8626!--     get the borders from neighbours
8627         CALL exchange_horiz( pt, nbgp )
8628!
8629!--     calculation of force_radiation_call:
8630!--     Make logical OR for all processes.
8631!--     Force radiation call if at least one processor forces it.
8632         IF ( intermediate_timestep_count == intermediate_timestep_count_max-1 )&
8633         THEN
8634#if defined( __parallel )
8635           IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
8636           CALL MPI_ALLREDUCE( force_radiation_call_l, force_radiation_call,    &
8637                               1, MPI_LOGICAL, MPI_LOR, comm2d, ierr )
8638#else
8639           force_radiation_call = force_radiation_call_l
8640#endif
8641           force_radiation_call_l = .FALSE.
8642         ENDIF
8643 
8644! !
8645! !-- Calculate surface specific humidity
8646!     IF ( humidity )  THEN
8647!        CALL calc_q_surface_usm
8648!     ENDIF
8649 
8650 
8651!     CONTAINS
8652! !------------------------------------------------------------------------------!
8653! ! Description:
8654! ! ------------
8655! !> Calculation of specific humidity of the skin layer (surface). It is assumend
8656! !> that the skin is always saturated.
8657! !------------------------------------------------------------------------------!
8658!        SUBROUTINE calc_q_surface_usm
8659!
8660!           IMPLICIT NONE
8661!
8662!           REAL(wp) :: resistance    !< aerodynamic and soil resistance term
8663!
8664!           DO  m = 1, surf_usm_h%ns
8665!
8666!              i   = surf_usm_h%i(m)           
8667!              j   = surf_usm_h%j(m)
8668!              k   = surf_usm_h%k(m)
8669!
8670!!
8671!!--          Calculate water vapour pressure at saturation
8672!              e_s = 0.01_wp * 610.78_wp * EXP( 17.269_wp *                  &
8673!                                     ( t_surf_green_h_p(m) - 273.16_wp ) /  &
8674!                                     ( t_surf_green_h_p(m) - 35.86_wp  )    &
8675!                                          )
8676!
8677!!
8678!!--          Calculate specific humidity at saturation
8679!              q_s = 0.622_wp * e_s / ( surface_pressure - e_s )
8680!
8681!!              surf_usm_h%r_a_green(m) = ( surf_usm_h%pt1(m) - t_surf_green_h(m) / exner(k) ) /  &
8682!!                    ( surf_usm_h%ts(m) * surf_usm_h%us(m) + 1.0E-10_wp )
8683!!                 
8684!! !--          make sure that the resistance does not drop to zero
8685!!              IF ( ABS(surf_usm_h%r_a_green(m)) < 1.0E-10_wp )  surf_usm_h%r_a_green(m) = 1.0E-10_wp
8686!
8687!              resistance = surf_usm_h%r_a_green(m) / ( surf_usm_h%r_a_green(m) + surf_usm_h%r_s(m) + 1E-5_wp )
8688!
8689!!
8690!!--          Calculate specific humidity at surface
8691!              IF ( bulk_cloud_model )  THEN
8692!                 q(k,j,i) = resistance * q_s +                   &
8693!                                            ( 1.0_wp - resistance ) *              &
8694!                                            ( q(k,j,i) - ql(k,j,i) )
8695!              ELSE
8696!                 q(k,j,i) = resistance * q_s +                   &
8697!                                            ( 1.0_wp - resistance ) *              &
8698!                                              q(k,j,i)
8699!              ENDIF
8700!
8701!!
8702!!--          Update virtual potential temperature
8703!              vpt(k,j,i) = pt(k,j,i) *         &
8704!                         ( 1.0_wp + 0.61_wp * q(k,j,i) )
8705!
8706!           ENDDO
8707!
8708!!
8709!!--       Now, treat vertical surface elements
8710!           DO  l = 0, 3
8711!              DO  m = 1, surf_usm_v(l)%ns
8712!!
8713!!--             Get indices of respective grid point
8714!                 i = surf_usm_v(l)%i(m)
8715!                 j = surf_usm_v(l)%j(m)
8716!                 k = surf_usm_v(l)%k(m)
8717!
8718!!
8719!!--             Calculate water vapour pressure at saturation
8720!                 e_s = 0.01_wp * 610.78_wp * EXP( 17.269_wp *                       &
8721!                                        ( t_surf_green_v_p(l)%t(m) - 273.16_wp ) /  &
8722!                                        ( t_surf_green_v_p(l)%t(m) - 35.86_wp  )    &
8723!                                             )
8724!
8725!!
8726!!--             Calculate specific humidity at saturation
8727!                 q_s = 0.622_wp * e_s / ( surface_pressure -e_s )
8728!
8729!!
8730!!--             Calculate specific humidity at surface
8731!                 IF ( bulk_cloud_model )  THEN
8732!                    q(k,j,i) = ( q(k,j,i) - ql(k,j,i) )
8733!                 ELSE
8734!                    q(k,j,i) = q(k,j,i)
8735!                 ENDIF
8736!!
8737!!--             Update virtual potential temperature
8738!                 vpt(k,j,i) = pt(k,j,i) *         &
8739!                            ( 1.0_wp + 0.61_wp * q(k,j,i) )
8740!
8741!              ENDDO
8742!
8743!           ENDDO
8744!
8745!        END SUBROUTINE calc_q_surface_usm
8746
8747        IF ( debug_output_timestep )  THEN
8748           WRITE( debug_string, * ) 'usm_surface_energy_balance | during_spinup: ',&
8749                                    during_spinup
8750           CALL debug_message( debug_string, 'end' )
8751        ENDIF
8752
8753     END SUBROUTINE usm_surface_energy_balance
8754 
8755 
8756!------------------------------------------------------------------------------!
8757! Description:
8758! ------------
8759!> Swapping of timelevels for t_surf and t_wall
8760!> called out from subroutine swap_timelevel
8761!------------------------------------------------------------------------------!
8762     SUBROUTINE usm_swap_timelevel( mod_count )
8763 
8764        IMPLICIT NONE
8765 
8766        INTEGER(iwp), INTENT(IN) ::  mod_count
8767 
8768       
8769        SELECT CASE ( mod_count )
8770 
8771           CASE ( 0 )
8772!
8773!--          Horizontal surfaces
8774              t_surf_wall_h    => t_surf_wall_h_1;   t_surf_wall_h_p    => t_surf_wall_h_2
8775              t_wall_h         => t_wall_h_1;        t_wall_h_p         => t_wall_h_2
8776              t_surf_window_h  => t_surf_window_h_1; t_surf_window_h_p  => t_surf_window_h_2
8777              t_window_h       => t_window_h_1;      t_window_h_p       => t_window_h_2
8778              t_surf_green_h   => t_surf_green_h_1;  t_surf_green_h_p   => t_surf_green_h_2
8779              t_green_h        => t_green_h_1;       t_green_h_p        => t_green_h_2
8780!
8781!--          Vertical surfaces
8782              t_surf_wall_v    => t_surf_wall_v_1;   t_surf_wall_v_p    => t_surf_wall_v_2
8783              t_wall_v         => t_wall_v_1;        t_wall_v_p         => t_wall_v_2
8784              t_surf_window_v  => t_surf_window_v_1; t_surf_window_v_p  => t_surf_window_v_2
8785              t_window_v       => t_window_v_1;      t_window_v_p       => t_window_v_2
8786              t_surf_green_v   => t_surf_green_v_1;  t_surf_green_v_p   => t_surf_green_v_2
8787              t_green_v        => t_green_v_1;       t_green_v_p        => t_green_v_2
8788           CASE ( 1 )
8789!
8790!--          Horizontal surfaces
8791              t_surf_wall_h    => t_surf_wall_h_2;   t_surf_wall_h_p    => t_surf_wall_h_1
8792              t_wall_h         => t_wall_h_2;        t_wall_h_p         => t_wall_h_1
8793              t_surf_window_h  => t_surf_window_h_2; t_surf_window_h_p  => t_surf_window_h_1
8794              t_window_h       => t_window_h_2;      t_window_h_p       => t_window_h_1
8795              t_surf_green_h   => t_surf_green_h_2;  t_surf_green_h_p   => t_surf_green_h_1
8796              t_green_h        => t_green_h_2;       t_green_h_p        => t_green_h_1
8797!
8798!--          Vertical surfaces
8799              t_surf_wall_v    => t_surf_wall_v_2;   t_surf_wall_v_p    => t_surf_wall_v_1
8800              t_wall_v         => t_wall_v_2;        t_wall_v_p         => t_wall_v_1
8801              t_surf_window_v  => t_surf_window_v_2; t_surf_window_v_p  => t_surf_window_v_1
8802              t_window_v       => t_window_v_2;      t_window_v_p       => t_window_v_1
8803              t_surf_green_v   => t_surf_green_v_2;  t_surf_green_v_p   => t_surf_green_v_1
8804              t_green_v        => t_green_v_2;       t_green_v_p        => t_green_v_1
8805        END SELECT
8806         
8807     END SUBROUTINE usm_swap_timelevel
8808 
8809!------------------------------------------------------------------------------!
8810! Description:
8811! ------------
8812!> Subroutine writes t_surf and t_wall data into restart files
8813!------------------------------------------------------------------------------!
8814     SUBROUTINE usm_wrd_local
8815 
8816     
8817        IMPLICIT NONE
8818       
8819        CHARACTER(LEN=1) ::  dum     !< dummy string to create output-variable name 
8820        INTEGER(iwp)     ::  l       !< index surface type orientation
8821 
8822        CALL wrd_write_string( 'ns_h_on_file_usm' )
8823        WRITE ( 14 )  surf_usm_h%ns
8824 
8825        CALL wrd_write_string( 'ns_v_on_file_usm' )
8826        WRITE ( 14 )  surf_usm_v(0:3)%ns
8827 
8828        CALL wrd_write_string( 'usm_start_index_h' )
8829        WRITE ( 14 )  surf_usm_h%start_index
8830 
8831        CALL wrd_write_string( 'usm_end_index_h' )
8832        WRITE ( 14 )  surf_usm_h%end_index
8833 
8834        CALL wrd_write_string( 't_surf_wall_h' )
8835        WRITE ( 14 )  t_surf_wall_h
8836 
8837        CALL wrd_write_string( 't_surf_window_h' )
8838        WRITE ( 14 )  t_surf_window_h
8839 
8840        CALL wrd_write_string( 't_surf_green_h' )
8841        WRITE ( 14 )  t_surf_green_h
8842!
8843!--     Write restart data which is especially needed for the urban-surface
8844!--     model. In order to do not fill up the restart routines in
8845!--     surface_mod.
8846!--     Output of waste heat from indoor model. Restart data is required in
8847!--     this special case, because the indoor model where waste heat is
8848!--     computed is call each hour (current default), so that waste heat would
8849!--     have zero value until next call of indoor model.
8850        IF ( indoor_model )  THEN
8851           CALL wrd_write_string( 'waste_heat_h' )
8852           WRITE ( 14 )  surf_usm_h%waste_heat
8853        ENDIF   
8854           
8855        DO  l = 0, 3
8856 
8857           CALL wrd_write_string( 'usm_start_index_v' )
8858           WRITE ( 14 )  surf_usm_v(l)%start_index
8859 
8860           CALL wrd_write_string( 'usm_end_index_v' )
8861           WRITE ( 14 )  surf_usm_v(l)%end_index
8862 
8863           WRITE( dum, '(I1)')  l         
8864 
8865           CALL wrd_write_string( 't_surf_wall_v(' // dum // ')' )
8866           WRITE ( 14 )  t_surf_wall_v(l)%t
8867 
8868           CALL wrd_write_string( 't_surf_window_v(' // dum // ')' )
8869           WRITE ( 14 ) t_surf_window_v(l)%t     
8870 
8871           CALL wrd_write_string( 't_surf_green_v(' // dum // ')' )
8872           WRITE ( 14 ) t_surf_green_v(l)%t 
8873           
8874           IF ( indoor_model )  THEN
8875              CALL wrd_write_string( 'waste_heat_v(' // dum // ')' )
8876              WRITE ( 14 )  surf_usm_v(l)%waste_heat
8877           ENDIF
8878           
8879        ENDDO
8880 
8881        CALL wrd_write_string( 'usm_start_index_h' )
8882        WRITE ( 14 )  surf_usm_h%start_index
8883 
8884        CALL wrd_write_string( 'usm_end_index_h' )
8885        WRITE ( 14 )  surf_usm_h%end_index
8886 
8887        CALL wrd_write_string( 't_wall_h' )
8888        WRITE ( 14 )  t_wall_h
8889 
8890        CALL wrd_write_string( 't_window_h' )
8891        WRITE ( 14 )  t_window_h
8892 
8893        CALL wrd_write_string( 't_green_h' )
8894        WRITE ( 14 )  t_green_h
8895 
8896        DO  l = 0, 3
8897 
8898           CALL wrd_write_string( 'usm_start_index_v' )
8899           WRITE ( 14 )  surf_usm_v(l)%start_index
8900 
8901           CALL wrd_write_string( 'usm_end_index_v' )
8902           WRITE ( 14 )  surf_usm_v(l)%end_index
8903 
8904           WRITE( dum, '(I1)')  l     
8905 
8906           CALL wrd_write_string( 't_wall_v(' // dum // ')' )
8907           WRITE ( 14 )  t_wall_v(l)%t
8908 
8909           CALL wrd_write_string( 't_window_v(' // dum // ')' )
8910           WRITE ( 14 )  t_window_v(l)%t
8911 
8912           CALL wrd_write_string( 't_green_v(' // dum // ')' )
8913           WRITE ( 14 )  t_green_v(l)%t
8914       
8915        ENDDO
8916       
8917     END SUBROUTINE usm_wrd_local
8918     
8919     
8920!------------------------------------------------------------------------------!
8921! Description:
8922! ------------
8923!> Define building properties
8924!------------------------------------------------------------------------------!
8925     SUBROUTINE usm_define_pars     
8926!
8927!--     Define the building_pars
8928        building_pars(:,1) = (/   &
8929           0.7_wp,         &  !< parameter 0   - wall fraction above ground floor level
8930           0.3_wp,         &  !< parameter 1   - window fraction above ground floor level
8931           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
8932           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
8933           1.5_wp,         &  !< parameter 4   - LAI roof
8934           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
8935           2200000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
8936           1400000.0_wp,   &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
8937           1300000.0_wp,   &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
8938           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
8939           0.8_wp,         &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
8940           2.1_wp,         &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
8941           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
8942           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
8943           0.93_wp,        &  !< parameter 14  - wall emissivity above ground floor level
8944           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
8945           0.91_wp,        &  !< parameter 16  - window emissivity above ground floor level
8946           0.75_wp,        &  !< parameter 17  - window transmissivity above ground floor level
8947           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
8948           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
8949           4.0_wp,         &  !< parameter 20  - ground floor level height
8950           0.75_wp,        &  !< parameter 21  - wall fraction ground floor level
8951           0.25_wp,        &  !< parameter 22  - window fraction ground floor level
8952           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
8953           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
8954           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
8955           2200000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
8956           1400000.0_wp,   &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
8957           1300000.0_wp,   &  !< parameter 28  - heat capacity 4th wall layer ground floor level
8958           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
8959           0.8_wp,         &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
8960           2.1_wp,         &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
8961           0.93_wp,        &  !< parameter 32  - wall emissivity ground floor level
8962           0.91_wp,        &  !< parameter 33  - window emissivity ground floor level
8963           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
8964           0.75_wp,        &  !< parameter 35  - window transmissivity ground floor level
8965           0.01_wp,        &  !< parameter 36  - z0 roughness ground floor level
8966           0.001_wp,       &  !< parameter 37  - z0h/z0q roughness heat/humidity
8967           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
8968           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
8969           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
8970           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
8971           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
8972           0.39_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
8973           0.63_wp,        &  !< parameter 44  - 4th wall layer thickness above ground floor level
8974           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
8975           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
8976           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
8977           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
8978           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
8979           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
8980           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
8981           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
8982           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
8983           0.39_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
8984           0.63_wp,        &  !< parameter 55  - 4th wall layer thickness ground plate
8985           2200000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
8986           1400000.0_wp,   &  !< parameter 57  - heat capacity 3rd wall layer ground plate
8987           1300000.0_wp,   &  !< parameter 58  - heat capacity 4th wall layer ground plate
8988           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
8989           0.8_wp,         &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
8990           2.1_wp,         &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
8991           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
8992           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
8993           0.39_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
8994           0.63_wp,        &  !< parameter 65  - 4th wall layer thickness ground floor level
8995           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
8996           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
8997           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
8998           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
8999           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9000           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9001           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9002           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9003           0.57_wp,        &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9004           0.57_wp,        &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9005           0.57_wp,        &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9006           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9007           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9008           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9009           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9010           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9011           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9012           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9013           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9014           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9015           0.57_wp,        &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9016           0.57_wp,        &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9017           0.57_wp,        &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9018           1.0_wp,         &  !< parameter 89  - wall fraction roof
9019           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9020           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9021           0.31_wp,        &  !< parameter 92  - 3rd wall layer thickness roof
9022           0.63_wp,        &  !< parameter 93  - 4th wall layer thickness roof
9023           2200000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9024           1400000.0_wp,   &  !< parameter 95  - heat capacity 3rd wall layer roof
9025           1300000.0_wp,   &  !< parameter 96  - heat capacity 4th wall layer roof
9026           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9027           0.8_wp,         &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9028           2.1_wp,         &  !< parameter 99  - thermal conductivity 4th wall layer roof
9029           0.93_wp,        &  !< parameter 100 - wall emissivity roof
9030           27.0_wp,        &  !< parameter 101 - wall albedo roof
9031           0.0_wp,         &  !< parameter 102 - window fraction roof
9032           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9033           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9034           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9035           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9036           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9037           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9038           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9039           0.57_wp,        &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9040           0.57_wp,        &  !< parameter 111 - thermal conductivity 3rd window layer roof
9041           0.57_wp,        &  !< parameter 112 - thermal conductivity 4th window layer roof
9042           0.91_wp,        &  !< parameter 113 - window emissivity roof
9043           0.75_wp,        &  !< parameter 114 - window transmissivity roof
9044           27.0_wp,        &  !< parameter 115 - window albedo roof
9045           0.86_wp,        &  !< parameter 116 - green emissivity roof
9046           5.0_wp,         &  !< parameter 117 - green albedo roof
9047           0.0_wp,         &  !< parameter 118 - green type roof
9048           0.8_wp,         &  !< parameter 119 - shading factor
9049           0.76_wp,        &  !< parameter 120 - g-value windows
9050           5.0_wp,         &  !< parameter 121 - u-value windows
9051           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9052           0.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9053           0.0_wp,         &  !< parameter 124 - heat recovery efficiency
9054           3.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9055           370000.0_wp,    &  !< parameter 126 - dynamic parameter innner heatstorage
9056           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9057           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9058           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9059           3.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9060           10.0_wp,        &  !< parameter 131 - basic internal heat gains without occupancy of the room
9061           3.0_wp,         &  !< parameter 132 - storey height
9062           0.2_wp          &  !< parameter 133 - ceiling construction height
9063                            /)
9064                           
9065        building_pars(:,2) = (/   &
9066           0.73_wp,        &  !< parameter 0   - wall fraction above ground floor level
9067           0.27_wp,        &  !< parameter 1   - window fraction above ground floor level
9068           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9069           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9070           1.5_wp,         &  !< parameter 4   - LAI roof
9071           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9072           2000000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9073           103000.0_wp,    &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9074           900000.0_wp,    &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9075           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9076           0.38_wp,        &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9077           0.04_wp,        &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9078           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9079           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9080           0.92_wp,        &  !< parameter 14  - wall emissivity above ground floor level
9081           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9082           0.87_wp,        &  !< parameter 16  - window emissivity above ground floor level
9083           0.7_wp,         &  !< parameter 17  - window transmissivity above ground floor level
9084           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9085           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9086           4.0_wp,         &  !< parameter 20  - ground floor level height
9087           0.78_wp,        &  !< parameter 21  - wall fraction ground floor level
9088           0.22_wp,        &  !< parameter 22  - window fraction ground floor level
9089           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9090           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9091           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9092           2000000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9093           103000.0_wp,    &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9094           900000.0_wp,    &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9095           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9096           0.38_wp,        &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9097           0.04_wp,        &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9098           0.92_wp,        &  !< parameter 32  - wall emissivity ground floor level
9099           0.11_wp,        &  !< parameter 33  - window emissivity ground floor level
9100           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9101           0.7_wp,         &  !< parameter 35  - window transmissivity ground floor level
9102           0.01_wp,        &  !< parameter 36  - z0 roughness ground floor level
9103           0.001_wp,       &  !< parameter 37  - z0h/z0q roughness heat/humidity
9104           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9105           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9106           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9107           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
9108           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9109           0.31_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9110           0.43_wp,        &  !< parameter 44  - 4th wall layer thickness above ground floor level
9111           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9112           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9113           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9114           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9115           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9116           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9117           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9118           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
9119           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
9120           0.31_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
9121           0.42_wp,        &  !< parameter 55  - 4th wall layer thickness ground plate
9122           2000000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9123           103000.0_wp,    &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9124           900000.0_wp,    &  !< parameter 58  - heat capacity 4th wall layer ground plate
9125           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9126           0.38_wp,        &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9127           0.04_wp,        &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9128           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
9129           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
9130           0.31_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
9131           0.43_wp,        &  !< parameter 65  - 4th wall layer thickness ground floor level
9132           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9133           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9134           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9135           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9136           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9137           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9138           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9139           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9140           0.11_wp,        &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9141           0.11_wp,        &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9142           0.11_wp,        &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9143           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9144           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9145           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9146           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9147           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9148           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9149           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9150           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9151           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9152           0.11_wp,        &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9153           0.11_wp,        &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9154           0.11_wp,        &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9155           1.0_wp,         &  !< parameter 89  - wall fraction roof
9156           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9157           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9158           0.5_wp,         &  !< parameter 92  - 3rd wall layer thickness roof
9159           0.79_wp,        &  !< parameter 93  - 4th wall layer thickness roof
9160           2000000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9161           103000.0_wp,    &  !< parameter 95  - heat capacity 3rd wall layer roof
9162           900000.0_wp,    &  !< parameter 96  - heat capacity 4th wall layer roof
9163           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9164           0.38_wp,        &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9165           0.04_wp,        &  !< parameter 99  - thermal conductivity 4th wall layer roof
9166           0.93_wp,        &  !< parameter 100 - wall emissivity roof
9167           27.0_wp,        &  !< parameter 101 - wall albedo roof
9168           0.0_wp,         &  !< parameter 102 - window fraction roof
9169           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9170           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9171           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9172           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9173           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9174           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9175           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9176           0.11_wp,        &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9177           0.11_wp,        &  !< parameter 111 - thermal conductivity 3rd window layer roof
9178           0.11_wp,        &  !< parameter 112 - thermal conductivity 4th window layer roof
9179           0.87_wp,        &  !< parameter 113 - window emissivity roof
9180           0.7_wp,         &  !< parameter 114 - window transmissivity roof
9181           27.0_wp,        &  !< parameter 115 - window albedo roof
9182           0.86_wp,        &  !< parameter 116 - green emissivity roof
9183           5.0_wp,         &  !< parameter 117 - green albedo roof
9184           0.0_wp,         &  !< parameter 118 - green type roof
9185           0.8_wp,         &  !< parameter 119 - shading factor
9186           0.6_wp,         &  !< parameter 120 - g-value windows
9187           3.0_wp,         &  !< parameter 121 - u-value windows
9188           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9189           0.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9190           0.0_wp,         &  !< parameter 124 - heat recovery efficiency
9191           2.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9192           165000.0_wp,    &  !< parameter 126 - dynamic parameter innner heatstorage
9193           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9194           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9195           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9196           4.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9197           8.0_wp,         &  !< parameter 131 - basic internal heat gains without occupancy of the room
9198           3.0_wp,         &  !< parameter 132 - storey height
9199           0.2_wp          &  !< parameter 133 - ceiling construction height
9200                            /)
9201                           
9202        building_pars(:,3) = (/   &
9203           0.7_wp,         &  !< parameter 0   - wall fraction above ground floor level
9204           0.3_wp,         &  !< parameter 1   - window fraction above ground floor level
9205           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9206           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9207           1.5_wp,         &  !< parameter 4   - LAI roof
9208           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9209           2000000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9210           103000.0_wp,    &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9211           900000.0_wp,    &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9212           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9213           0.14_wp,        &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9214           0.035_wp,       &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9215           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9216           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9217           0.92_wp,        &  !< parameter 14  - wall emissivity above ground floor level
9218           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9219           0.8_wp,         &  !< parameter 16  - window emissivity above ground floor level
9220           0.6_wp,         &  !< parameter 17  - window transmissivity above ground floor level
9221           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9222           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9223           4.0_wp,         &  !< parameter 20  - ground floor level height
9224           0.75_wp,        &  !< parameter 21  - wall fraction ground floor level
9225           0.25_wp,        &  !< parameter 22  - window fraction ground floor level
9226           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9227           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9228           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9229           2000000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9230           103000.0_wp,    &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9231           900000.0_wp,    &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9232           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9233           0.14_wp,        &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9234           0.035_wp,       &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9235           0.92_wp,        &  !< parameter 32  - wall emissivity ground floor level
9236           0.8_wp,         &  !< parameter 33  - window emissivity ground floor level
9237           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9238           0.6_wp,         &  !< parameter 35  - window transmissivity ground floor level
9239           0.01_wp,        &  !< parameter 36  - z0 roughness ground floor level
9240           0.001_wp,       &  !< parameter 37  - z0h/z0q roughness heat/humidity
9241           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9242           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9243           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9244           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
9245           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9246           0.41_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9247           0.7_wp,         &  !< parameter 44  - 4th wall layer thickness above ground floor level
9248           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9249           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9250           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9251           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9252           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9253           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9254           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9255           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
9256           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
9257           0.41_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
9258           0.7_wp,         &  !< parameter 55  - 4th wall layer thickness ground plate
9259           2000000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9260           103000.0_wp,    &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9261           900000.0_wp,    &  !< parameter 58  - heat capacity 4th wall layer ground plate
9262           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9263           0.14_wp,        &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9264           0.035_wp,       &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9265           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
9266           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
9267           0.41_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
9268           0.7_wp,         &  !< parameter 65  - 4th wall layer thickness ground floor level
9269           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9270           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9271           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9272           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9273           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9274           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9275           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9276           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9277           0.037_wp,       &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9278           0.037_wp,       &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9279           0.037_wp,       &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9280           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9281           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9282           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9283           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9284           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9285           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9286           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9287           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9288           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9289           0.037_wp,       &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9290           0.037_wp,       &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9291           0.037_wp,       &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9292           1.0_wp,         &  !< parameter 89  - wall fraction roof
9293           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9294           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9295           0.41_wp,        &  !< parameter 92  - 3rd wall layer thickness roof
9296           0.7_wp,         &  !< parameter 93  - 4th wall layer thickness roof
9297           2000000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9298           103000.0_wp,    &  !< parameter 95  - heat capacity 3rd wall layer roof
9299           900000.0_wp,    &  !< parameter 96  - heat capacity 4th wall layer roof
9300           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9301           0.14_wp,        &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9302           0.035_wp,       &  !< parameter 99  - thermal conductivity 4th wall layer roof
9303           0.93_wp,        &  !< parameter 100 - wall emissivity roof
9304           27.0_wp,        &  !< parameter 101 - wall albedo roof
9305           0.0_wp,         &  !< parameter 102 - window fraction roof
9306           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9307           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9308           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9309           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9310           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9311           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9312           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9313           0.037_wp,       &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9314           0.037_wp,       &  !< parameter 111 - thermal conductivity 3rd window layer roof
9315           0.037_wp,       &  !< parameter 112 - thermal conductivity 4th window layer roof
9316           0.8_wp,         &  !< parameter 113 - window emissivity roof
9317           0.6_wp,         &  !< parameter 114 - window transmissivity roof
9318           27.0_wp,        &  !< parameter 115 - window albedo roof
9319           0.86_wp,        &  !< parameter 116 - green emissivity roof
9320           5.0_wp,         &  !< parameter 117 - green albedo roof
9321           0.0_wp,         &  !< parameter 118 - green type roof
9322           0.8_wp,         &  !< parameter 119 - shading factor
9323           0.5_wp,         &  !< parameter 120 - g-value windows
9324           0.6_wp,         &  !< parameter 121 - u-value windows
9325           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9326           0.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9327           0.8_wp,         &  !< parameter 124 - heat recovery efficiency
9328           2.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9329           80000.0_wp,     &  !< parameter 126 - dynamic parameter innner heatstorage
9330           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9331           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9332           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9333           3.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9334           8.0_wp,         &  !< parameter 131 - basic internal heat gains without occupancy of the room
9335           3.0_wp,         &  !< parameter 132 - storey height
9336           0.2_wp          &  !< parameter 133 - ceiling construction height
9337                            /)   
9338                           
9339        building_pars(:,4) = (/   &
9340           0.5_wp,         &  !< parameter 0   - wall fraction above ground floor level
9341           0.5_wp,         &  !< parameter 1   - window fraction above ground floor level
9342           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9343           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9344           1.5_wp,         &  !< parameter 4   - LAI roof
9345           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9346           2200000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9347           1400000.0_wp,   &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9348           1300000.0_wp,   &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9349           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9350           0.8_wp,         &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9351           2.1_wp,         &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9352           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9353           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9354           0.93_wp,        &  !< parameter 14  - wall emissivity above ground floor level
9355           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9356           0.91_wp,        &  !< parameter 16  - window emissivity above ground floor level
9357           0.75_wp,        &  !< parameter 17  - window transmissivity above ground floor level
9358           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9359           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9360           4.0_wp,         &  !< parameter 20  - ground floor level height
9361           0.55_wp,        &  !< parameter 21  - wall fraction ground floor level
9362           0.45_wp,        &  !< parameter 22  - window fraction ground floor level
9363           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9364           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9365           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9366           2200000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9367           1400000.0_wp,   &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9368           1300000.0_wp,   &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9369           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9370           0.8_wp,         &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9371           2.1_wp,         &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9372           0.93_wp,        &  !< parameter 32  - wall emissivity ground floor level
9373           0.91_wp,        &  !< parameter 33  - window emissivity ground floor level
9374           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9375           0.75_wp,        &  !< parameter 35  - window transmissivity ground floor level
9376           0.01_wp,        &  !< parameter 36  - z0 roughness ground floor level
9377           0.001_wp,       &  !< parameter 37  - z0h/z0q roughness heat/humidity
9378           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9379           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9380           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9381           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
9382           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9383           0.39_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9384           0.63_wp,        &  !< parameter 44  - 4th wall layer thickness above ground floor level
9385           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9386           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9387           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9388           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9389           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9390           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9391           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9392           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
9393           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
9394           0.39_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
9395           0.63_wp,        &  !< parameter 55  - 4th wall layer thickness ground plate
9396           2200000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9397           1400000.0_wp,   &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9398           1300000.0_wp,   &  !< parameter 58  - heat capacity 4th wall layer ground plate
9399           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9400           0.8_wp,         &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9401           2.1_wp,         &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9402           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
9403           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
9404           0.39_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
9405           0.63_wp,        &  !< parameter 65  - 4th wall layer thickness ground floor level
9406           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9407           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9408           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9409           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9410           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9411           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9412           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9413           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9414           0.57_wp,        &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9415           0.57_wp,        &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9416           0.57_wp,        &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9417           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9418           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9419           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9420           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9421           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9422           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9423           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9424           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9425           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9426           0.57_wp,        &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9427           0.57_wp,        &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9428           0.57_wp,        &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9429           1.0_wp,         &  !< parameter 89  - wall fraction roof
9430           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9431           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9432           0.39_wp,        &  !< parameter 92  - 3rd wall layer thickness roof
9433           0.63_wp,        &  !< parameter 93  - 4th wall layer thickness roof
9434           2200000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9435           1400000.0_wp,   &  !< parameter 95  - heat capacity 3rd wall layer roof
9436           1300000.0_wp,   &  !< parameter 96  - heat capacity 4th wall layer roof
9437           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9438           0.8_wp,         &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9439           2.1_wp,         &  !< parameter 99  - thermal conductivity 4th wall layer roof
9440           0.93_wp,        &  !< parameter 100 - wall emissivity roof
9441           27.0_wp,        &  !< parameter 101 - wall albedo roof
9442           0.0_wp,         &  !< parameter 102 - window fraction roof
9443           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9444           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9445           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9446           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9447           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9448           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9449           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9450           0.57_wp,        &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9451           0.57_wp,        &  !< parameter 111 - thermal conductivity 3rd window layer roof
9452           0.57_wp,        &  !< parameter 112 - thermal conductivity 4th window layer roof
9453           0.91_wp,        &  !< parameter 113 - window emissivity roof
9454           0.75_wp,        &  !< parameter 114 - window transmissivity roof
9455           27.0_wp,        &  !< parameter 115 - window albedo roof
9456           0.86_wp,        &  !< parameter 116 - green emissivity roof
9457           5.0_wp,         &  !< parameter 117 - green albedo roof
9458           0.0_wp,         &  !< parameter 118 - green type roof
9459           0.8_wp,         &  !< parameter 119 - shading factor
9460           0.76_wp,        &  !< parameter 120 - g-value windows
9461           5.0_wp,         &  !< parameter 121 - u-value windows
9462           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9463           1.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9464           0.0_wp,         &  !< parameter 124 - heat recovery efficiency
9465           3.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9466           370000.0_wp,    &  !< parameter 126 - dynamic parameter innner heatstorage
9467           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9468           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9469           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9470           3.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9471           10.0_wp,        &  !< parameter 131 - basic internal heat gains without occupancy of the room
9472           3.0_wp,         &  !< parameter 132 - storey height
9473           0.2_wp          &  !< parameter 133 - ceiling construction height
9474                            /)   
9475                           
9476        building_pars(:,5) = (/   &
9477           0.5_wp,         &  !< parameter 0   - wall fraction above ground floor level
9478           0.5_wp,         &  !< parameter 1   - window fraction above ground floor level
9479           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9480           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9481           1.5_wp,         &  !< parameter 4   - LAI roof
9482           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9483           2000000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9484           103000.0_wp,    &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9485           900000.0_wp,    &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9486           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9487           0.38_wp,        &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9488           0.04_wp,        &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9489           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9490           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9491           0.92_wp,        &  !< parameter 14  - wall emissivity above ground floor level
9492           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9493           0.87_wp,        &  !< parameter 16  - window emissivity above ground floor level
9494           0.7_wp,         &  !< parameter 17  - window transmissivity above ground floor level
9495           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9496           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9497           4.0_wp,         &  !< parameter 20  - ground floor level height
9498           0.55_wp,        &  !< parameter 21  - wall fraction ground floor level
9499           0.45_wp,        &  !< parameter 22  - window fraction ground floor level
9500           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9501           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9502           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9503           2000000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9504           103000.0_wp,    &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9505           900000.0_wp,    &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9506           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9507           0.38_wp,        &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9508           0.04_wp,        &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9509           0.92_wp,        &  !< parameter 32  - wall emissivity ground floor level
9510           0.87_wp,        &  !< parameter 33  - window emissivity ground floor level
9511           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9512           0.7_wp,         &  !< parameter 35  - window transmissivity ground floor level
9513           0.01_wp,        &  !< parameter 36  - z0 roughness ground floor level
9514           0.001_wp,       &  !< parameter 37  - z0h/z0q roughness heat/humidity
9515           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9516           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9517           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9518           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
9519           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9520           0.31_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9521           0.43_wp,        &  !< parameter 44  - 4th wall layer thickness above ground floor level
9522           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9523           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9524           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9525           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9526           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9527           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9528           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9529           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
9530           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
9531           0.31_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
9532           0.43_wp,        &  !< parameter 55  - 4th wall layer thickness ground plate
9533           2000000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9534           103000.0_wp,    &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9535           900000.0_wp,    &  !< parameter 58  - heat capacity 4th wall layer ground plate
9536           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9537           0.38_wp,        &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9538           0.04_wp,        &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9539           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
9540           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
9541           0.31_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
9542           0.43_wp,        &  !< parameter 65  - 4th wall layer thickness ground floor level
9543           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9544           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9545           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9546           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9547           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9548           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9549           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9550           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9551           0.11_wp,        &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9552           0.11_wp,        &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9553           0.11_wp,        &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9554           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9555           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9556           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9557           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9558           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9559           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9560           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9561           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9562           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9563           0.11_wp,        &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9564           0.11_wp,        &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9565           0.11_wp,        &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9566           1.0_wp,         &  !< parameter 89  - wall fraction roof
9567           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9568           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9569           0.31_wp,        &  !< parameter 92  - 3rd wall layer thickness roof
9570           0.43_wp,        &  !< parameter 93  - 4th wall layer thickness roof
9571           2000000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9572           103000.0_wp,    &  !< parameter 95  - heat capacity 3rd wall layer roof
9573           900000.0_wp,    &  !< parameter 96  - heat capacity 4th wall layer roof
9574           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9575           0.38_wp,        &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9576           0.04_wp,        &  !< parameter 99  - thermal conductivity 4th wall layer roof
9577           0.91_wp,        &  !< parameter 100 - wall emissivity roof
9578           27.0_wp,        &  !< parameter 101 - wall albedo roof
9579           0.0_wp,         &  !< parameter 102 - window fraction roof
9580           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9581           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9582           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9583           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9584           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9585           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9586           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9587           0.11_wp,        &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9588           0.11_wp,        &  !< parameter 111 - thermal conductivity 3rd window layer roof
9589           0.11_wp,        &  !< parameter 112 - thermal conductivity 4th window layer roof
9590           0.87_wp,        &  !< parameter 113 - window emissivity roof
9591           0.7_wp,         &  !< parameter 114 - window transmissivity roof
9592           27.0_wp,        &  !< parameter 115 - window albedo roof
9593           0.86_wp,        &  !< parameter 116 - green emissivity roof
9594           5.0_wp,         &  !< parameter 117 - green albedo roof
9595           0.0_wp,         &  !< parameter 118 - green type roof
9596           0.8_wp,         &  !< parameter 119 - shading factor
9597           0.6_wp,         &  !< parameter 120 - g-value windows
9598           3.0_wp,         &  !< parameter 121 - u-value windows
9599           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9600           1.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9601           0.65_wp,        &  !< parameter 124 - heat recovery efficiency
9602           2.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9603           165000.0_wp,    &  !< parameter 126 - dynamic parameter innner heatstorage
9604           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9605           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9606           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9607           7.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9608           20.0_wp,        &  !< parameter 131 - basic internal heat gains without occupancy of the room
9609           3.0_wp,         &  !< parameter 132 - storey height
9610           0.2_wp          &  !< parameter 133 - ceiling construction height
9611                            /)
9612                           
9613        building_pars(:,6) = (/   &
9614           0.425_wp,       &  !< parameter 0   - wall fraction above ground floor level
9615           0.575_wp,       &  !< parameter 1   - window fraction above ground floor level
9616           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9617           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9618           1.5_wp,         &  !< parameter 4   - LAI roof
9619           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9620           2000000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9621           103000.0_wp,    &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9622           900000.0_wp,    &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9623           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9624           0.14_wp,        &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9625           0.035_wp,       &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9626           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9627           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9628           0.92_wp,        &  !< parameter 14  - wall emissivity above ground floor level
9629           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9630           0.8_wp,         &  !< parameter 16  - window emissivity above ground floor level
9631           0.6_wp,         &  !< parameter 17  - window transmissivity above ground floor level
9632           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9633           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9634           4.0_wp,         &  !< parameter 20  - ground floor level height
9635           0.475_wp,       &  !< parameter 21  - wall fraction ground floor level
9636           0.525_wp,       &  !< parameter 22  - window fraction ground floor level
9637           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9638           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9639           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9640           2000000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9641           103000.0_wp,    &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9642           900000.0_wp,    &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9643           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9644           0.14_wp,        &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9645           0.035_wp,       &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9646           0.92_wp,        &  !< parameter 32  - wall emissivity ground floor level
9647           0.8_wp,         &  !< parameter 33  - window emissivity ground floor level
9648           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9649           0.6_wp,         &  !< parameter 35  - window transmissivity ground floor level
9650           0.01_wp,        &  !< parameter 36  - z0 roughness ground floor level
9651           0.001_wp,       &  !< parameter 37  - z0h/z0q roughness heat/humidity
9652           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9653           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9654           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9655           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
9656           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9657           0.41_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9658           0.7_wp,         &  !< parameter 44  - 4th wall layer thickness above ground floor level
9659           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9660           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9661           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9662           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9663           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9664           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9665           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9666           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
9667           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
9668           0.41_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
9669           0.7_wp,         &  !< parameter 55  - 4th wall layer thickness ground plate
9670           2000000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9671           103000.0_wp,    &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9672           900000.0_wp,    &  !< parameter 58  - heat capacity 4th wall layer ground plate
9673           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9674           0.14_wp,        &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9675           0.035_wp,       &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9676           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
9677           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
9678           0.41_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
9679           0.7_wp,         &  !< parameter 65  - 4th wall layer thickness ground floor level
9680           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9681           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9682           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9683           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9684           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9685           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9686           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9687           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9688           0.037_wp,       &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9689           0.037_wp,       &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9690           0.037_wp,       &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9691           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9692           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9693           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9694           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9695           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9696           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9697           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9698           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9699           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9700           0.037_wp,       &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9701           0.037_wp,       &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9702           0.037_wp,       &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9703           1.0_wp,         &  !< parameter 89  - wall fraction roof
9704           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9705           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9706           0.41_wp,        &  !< parameter 92  - 3rd wall layer thickness roof
9707           0.7_wp,         &  !< parameter 93  - 4th wall layer thickness roof
9708           2000000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9709           103000.0_wp,    &  !< parameter 95  - heat capacity 3rd wall layer roof
9710           900000.0_wp,    &  !< parameter 96  - heat capacity 4th wall layer roof
9711           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9712           0.14_wp,        &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9713           0.035_wp,       &  !< parameter 99  - thermal conductivity 4th wall layer roof
9714           0.91_wp,        &  !< parameter 100 - wall emissivity roof
9715           27.0_wp,        &  !< parameter 101 - wall albedo roof
9716           0.0_wp,         &  !< parameter 102 - window fraction roof
9717           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9718           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9719           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9720           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9721           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9722           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9723           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9724           0.037_wp,       &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9725           0.037_wp,       &  !< parameter 111 - thermal conductivity 3rd window layer roof
9726           0.037_wp,       &  !< parameter 112 - thermal conductivity 4th window layer roof
9727           0.8_wp,         &  !< parameter 113 - window emissivity roof
9728           0.6_wp,         &  !< parameter 114 - window transmissivity roof
9729           27.0_wp,        &  !< parameter 115 - window albedo roof
9730           0.86_wp,        &  !< parameter 116 - green emissivity roof
9731           5.0_wp,         &  !< parameter 117 - green albedo roof
9732           0.0_wp,         &  !< parameter 118 - green type roof
9733           0.8_wp,         &  !< parameter 119 - shading factor
9734           0.5_wp,         &  !< parameter 120 - g-value windows
9735           0.6_wp,         &  !< parameter 121 - u-value windows
9736           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9737           1.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9738           0.9_wp,         &  !< parameter 124 - heat recovery efficiency
9739           2.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9740           80000.0_wp,     &  !< parameter 126 - dynamic parameter innner heatstorage
9741           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9742           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9743           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9744           5.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9745           15.0_wp,        &  !< parameter 131 - basic internal heat gains without occupancy of the room
9746           3.0_wp,         &  !< parameter 132 - storey height
9747           0.2_wp          &  !< parameter 133 - ceiling construction height
9748                            /)
9749                           
9750        building_pars(:,7) = (/   &
9751           1.0_wp,         &  !< parameter 0   - wall fraction above ground floor level
9752           0.0_wp,         &  !< parameter 1   - window fraction above ground floor level
9753           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9754           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9755           1.5_wp,         &  !< parameter 4   - LAI roof
9756           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9757           1950400.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9758           1848000.0_wp,   &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9759           1848000.0_wp,   &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9760           0.7_wp,         &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9761           1.0_wp,         &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9762           1.0_wp,         &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9763           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9764           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9765           0.9_wp,         &  !< parameter 14  - wall emissivity above ground floor level
9766           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9767           0.8_wp,         &  !< parameter 16  - window emissivity above ground floor level
9768           0.6_wp,         &  !< parameter 17  - window transmissivity above ground floor level
9769           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9770           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9771           4.0_wp,         &  !< parameter 20  - ground floor level height
9772           1.0_wp,         &  !< parameter 21  - wall fraction ground floor level
9773           0.0_wp,         &  !< parameter 22  - window fraction ground floor level
9774           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9775           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9776           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9777           1950400.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9778           1848000.0_wp,   &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9779           1848000.0_wp,   &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9780           0.7_wp,         &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9781           1.0_wp,         &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9782           1.0_wp,         &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9783           0.9_wp,         &  !< parameter 32  - wall emissivity ground floor level
9784           0.8_wp,         &  !< parameter 33  - window emissivity ground floor level
9785           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9786           0.6_wp,         &  !< parameter 35  - window transmissivity ground floor level
9787           0.01_wp,        &  !< parameter 36  - z0 roughness ground floor level
9788           0.001_wp,       &  !< parameter 37  - z0h/z0q roughness heat/humidity
9789           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9790           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9791           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9792           0.29_wp,        &  !< parameter 41  - 1st wall layer thickness above ground floor level
9793           0.295_wp,       &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9794           0.695_wp,       &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9795           0.985_wp,       &  !< parameter 44  - 4th wall layer thickness above ground floor level
9796           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9797           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9798           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9799           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9800           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9801           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9802           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9803           0.29_wp,        &  !< parameter 52  - 1st wall layer thickness ground plate
9804           0.295_wp,       &  !< parameter 53  - 2nd wall layer thickness ground plate
9805           0.695_wp,       &  !< parameter 54  - 3rd wall layer thickness ground plate
9806           0.985_wp,       &  !< parameter 55  - 4th wall layer thickness ground plate
9807           1950400.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9808           1848000.0_wp,   &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9809           1848000.0_wp,   &  !< parameter 58  - heat capacity 4th wall layer ground plate
9810           0.7_wp,         &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9811           1.0_wp,         &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9812           1.0_wp,         &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9813           0.29_wp,        &  !< parameter 62  - 1st wall layer thickness ground floor level
9814           0.295_wp,       &  !< parameter 63  - 2nd wall layer thickness ground floor level
9815           0.695_wp,       &  !< parameter 64  - 3rd wall layer thickness ground floor level
9816           0.985_wp,       &  !< parameter 65  - 4th wall layer thickness ground floor level
9817           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9818           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9819           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9820           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9821           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9822           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9823           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9824           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9825           0.57_wp,        &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9826           0.57_wp,        &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9827           0.57_wp,        &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9828           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9829           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9830           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9831           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9832           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9833           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9834           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9835           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9836           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9837           0.57_wp,        &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9838           0.57_wp,        &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9839           0.57_wp,        &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9840           1.0_wp,         &  !< parameter 89  - wall fraction roof
9841           0.29_wp,        &  !< parameter 90  - 1st wall layer thickness roof
9842           0.295_wp,       &  !< parameter 91  - 2nd wall layer thickness roof
9843           0.695_wp,       &  !< parameter 92  - 3rd wall layer thickness roof
9844           0.985_wp,       &  !< parameter 93  - 4th wall layer thickness roof
9845           1950400.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9846           1848000.0_wp,   &  !< parameter 95  - heat capacity 3rd wall layer roof
9847           1848000.0_wp,   &  !< parameter 96  - heat capacity 4th wall layer roof
9848           0.7_wp,         &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9849           1.0_wp,         &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9850           1.0_wp,         &  !< parameter 99  - thermal conductivity 4th wall layer roof
9851           0.9_wp,         &  !< parameter 100 - wall emissivity roof
9852           27.0_wp,        &  !< parameter 101 - wall albedo roof
9853           0.0_wp,         &  !< parameter 102 - window fraction roof
9854           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9855           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9856           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9857           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9858           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9859           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9860           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9861           0.57_wp,        &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9862           0.57_wp,        &  !< parameter 111 - thermal conductivity 3rd window layer roof
9863           0.57_wp,        &  !< parameter 112 - thermal conductivity 4th window layer roof
9864           0.8_wp,         &  !< parameter 113 - window emissivity roof
9865           0.6_wp,         &  !< parameter 114 - window transmissivity roof
9866           27.0_wp,        &  !< parameter 115 - window albedo roof
9867           0.86_wp,        &  !< parameter 116 - green emissivity roof
9868           5.0_wp,         &  !< parameter 117 - green albedo roof
9869           0.0_wp,         &  !< parameter 118 - green type roof
9870           0.8_wp,         &  !< parameter 119 - shading factor
9871           100.0_wp,       &  !< parameter 120 - g-value windows
9872           100.0_wp,       &  !< parameter 121 - u-value windows
9873           20.0_wp,        &  !< parameter 122 - basical airflow without occupancy of the room
9874           20.0_wp,        &  !< parameter 123 - additional airflow depend of occupancy of the room
9875           0.0_wp,         &  !< parameter 124 - heat recovery efficiency
9876           1.0_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9877           1.0_wp,         &  !< parameter 126 - dynamic parameter innner heatstorage
9878           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9879           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9880           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9881           0.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9882           0.0_wp,         &  !< parameter 131 - basic internal heat gains without occupancy of the room
9883           3.0_wp,         &  !< parameter 132 - storey height
9884           0.2_wp          &  !< parameter 133 - ceiling construction height
9885                        /)
9886                       
9887     END SUBROUTINE usm_define_pars
9888 
9889   
9890  END MODULE urban_surface_mod
Note: See TracBrowser for help on using the repository browser.