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

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

Merge with branch resler: biomet- output of bio_mrt added; plant_canopy - separate vertical dimension for 3D output (to save disk space); radiation - remove unused plant canopy variables; urban-surface model - do not add anthropogenic heat during wall spin-up

  • Property svn:keywords set to Id
File size: 548.1 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 4127 2019-07-30 14:47:10Z suehring $
30! Do not add anthopogenic energy during wall/soil spin-up
31! (merge from branch resler)
32!
33! 4077 2019-07-09 13:27:11Z gronemeier
34! Set roughness length z0 and z0h/q at ground-floor level to same value as
35! those above ground-floor level
36!
37! 4051 2019-06-24 13:58:30Z suehring
38! Remove work-around for green surface fraction on buildings
39! (do not set it zero)
40!
41! 4050 2019-06-24 13:57:27Z suehring
42! In order to avoid confusion with global control parameter, rename the
43! USM-internal flag spinup into during_spinup.
44!
45! 3987 2019-05-22 09:52:13Z kanani
46! Introduce alternative switch for debug output during timestepping
47!
48! 3943 2019-05-02 09:50:41Z maronga
49! Removed qsws_eb. Bugfix in calculation of qsws.
50!
51! 3933 2019-04-25 12:33:20Z kanani
52! Remove allocation of pt_2m, this is done in surface_mod now (surfaces%pt_2m)
53!
54! 3921 2019-04-18 14:21:10Z suehring
55! Undo accidentally commented initialization 
56!
57! 3918 2019-04-18 13:33:11Z suehring
58! Set green fraction to zero also at vertical surfaces
59!
60! 3914 2019-04-17 16:02:02Z suehring
61! In order to obtain correct surface temperature during spinup set window
62! fraction to zero (only during spinup) instead of just disabling
63! time-integration of window-surface temperature.
64!
65! 3901 2019-04-16 16:17:02Z suehring
66! Workaround - set green fraction to zero ( green-heat model crashes ).
67!
68! 3896 2019-04-15 10:10:17Z suehring
69!
70!
71! 3896 2019-04-15 10:10:17Z suehring
72! Bugfix, wrong index used for accessing building_pars from PIDS
73!
74! 3885 2019-04-11 11:29:34Z kanani
75! Changes related to global restructuring of location messages and introduction
76! of additional debug messages
77!
78! 3882 2019-04-10 11:08:06Z suehring
79! Avoid different type kinds
80! Move definition of building-surface properties from declaration block
81! to an extra routine
82!
83! 3881 2019-04-10 09:31:22Z suehring
84! Revise determination of local ground-floor level height.
85! Make level 3 initalization conform with Palm-input-data standard
86! Move output of albedo and emissivity to radiation module
87!
88! 3832 2019-03-28 13:16:58Z raasch
89! instrumented with openmp directives
90!
91! 3824 2019-03-27 15:56:16Z pavelkrc
92! Remove unused imports
93!
94!
95! 3814 2019-03-26 08:40:31Z pavelkrc
96! unused subroutine commented out
97!
98! 3769 2019-02-28 10:16:49Z moh.hefny
99! removed unused variables
100!
101! 3767 2019-02-27 08:18:02Z raasch
102! unused variables removed from rrd-subroutines parameter list
103!
104! 3748 2019-02-18 10:38:31Z suehring
105! Revise conversion of waste-heat flux (do not divide by air density, will
106! be done in diffusion_s)
107!
108! 3745 2019-02-15 18:57:56Z suehring
109! - Remove internal flag indoor_model (is a global control parameter)
110! - add waste heat from buildings to the kinmatic heat flux
111! - consider waste heat in restart data
112! - remove unused USE statements
113!
114! 3744 2019-02-15 18:38:58Z suehring
115! fixed surface heat capacity in the building parameters
116! convert the file back to unix format
117!
118! 3730 2019-02-11 11:26:47Z moh.hefny
119! Formatting and clean-up (rvtils)
120!
121! 3710 2019-01-30 18:11:19Z suehring
122! Check if building type is set within a valid range.
123!
124! 3705 2019-01-29 19:56:39Z suehring
125! make nzb_wall public, required for virtual-measurements
126!
127! 3704 2019-01-29 19:51:41Z suehring
128! Some interface calls moved to module_interface + cleanup
129!
130! 3655 2019-01-07 16:51:22Z knoop
131! Implementation of the PALM module interface
132!
133! 3636 2018-12-19 13:48:34Z raasch
134! nopointer option removed
135!
136! 3614 2018-12-10 07:05:46Z raasch
137! unused variables removed
138!
139! 3607 2018-12-07 11:56:58Z suehring
140! Output of radiation-related quantities migrated to radiation_model_mod.
141!
142! 3597 2018-12-04 08:40:18Z maronga
143! Fixed calculation method of near surface air potential temperature at 10 cm
144! and moved to surface_layer_fluxes. Removed unnecessary _eb strings.
145!
146! 3524 2018-11-14 13:36:44Z raasch
147! bugfix concerning allocation of t_surf_wall_v
148!
149! 3502 2018-11-07 14:45:23Z suehring
150! Disable initialization of building roofs with ground-floor-level properties,
151! since this causes strong oscillations of surface temperature during the
152! spinup.
153!
154! 3469 2018-10-30 20:05:07Z kanani
155! Add missing PUBLIC variables for new indoor model
156!
157! 3449 2018-10-29 19:36:56Z suehring
158! Bugfix: Fix average arrays allocations in usm_3d_data_averaging (J.Resler)
159! Bugfix: Fix reading wall temperatures (J.Resler)
160! Bugfix: Fix treating of outputs for wall temperature and sky view factors (J.Resler)
161!
162!
163! 3435 2018-10-26 18:25:44Z gronemeier
164! Bugfix: allocate gamma_w_green_sat until nzt_wall+1
165!
166! 3418 2018-10-24 16:07:39Z kanani
167! (rvtils, srissman)
168! -Updated building databse, two green roof types (ind_green_type_roof)
169! -Latent heat flux for green walls and roofs, new output of latent heatflux
170!  and soil water content of green roof substrate
171! -t_surf changed to t_surf_wall
172! -Added namelist parameter usm_wall_mod for lower wall tendency
173!  of first two wall layers during spinup
174! -Window calculations deactivated during spinup
175!
176! 3382 2018-10-19 13:10:32Z knoop
177! Bugix: made array declaration Fortran Standard conform
178!
179! 3378 2018-10-19 12:34:59Z kanani
180! merge from radiation branch (r3362) into trunk
181! (moh.hefny):
182! - check the requested output variables if they are correct
183! - added unscheduled_radiation_calls switch to control force_radiation_call
184! - minor formate changes
185!
186! 3371 2018-10-18 13:40:12Z knoop
187! Set flag indicating that albedo at urban surfaces is already initialized
188!
189! 3347 2018-10-15 14:21:08Z suehring
190! Enable USM initialization with default building parameters in case no static
191! input file exist.
192!
193! 3343 2018-10-15 10:38:52Z suehring
194! Add output variables usm_rad_pc_inlw, usm_rad_pc_insw*
195!
196! 3274 2018-09-24 15:42:55Z knoop
197! Modularization of all bulk cloud physics code components
198!
199! 3248 2018-09-14 09:42:06Z sward
200! Minor formating changes
201!
202! 3246 2018-09-13 15:14:50Z sward
203! Added error handling for input namelist via parin_fail_message
204!
205! 3241 2018-09-12 15:02:00Z raasch
206! unused variables removed
207!
208! 3223 2018-08-30 13:48:17Z suehring
209! Bugfix for commit 3222
210!
211! 3222 2018-08-30 13:35:35Z suehring
212! Introduction of surface array for type and its name
213!
214! 3203 2018-08-23 10:48:36Z suehring
215! Revise bulk parameter for emissivity at ground-floor level
216!
217! 3196 2018-08-13 12:26:14Z maronga
218! Added maximum aerodynamic resistance of 300 for horiztonal surfaces.
219!
220! 3176 2018-07-26 17:12:48Z suehring
221! Bugfix, update virtual potential surface temparture, else heat fluxes on
222! roofs might become unphysical
223!
224! 3152 2018-07-19 13:26:52Z suehring
225! Initialize q_surface, which might be used in surface_layer_fluxes
226!
227! 3151 2018-07-19 08:45:38Z raasch
228! remaining preprocessor define strings __check removed
229!
230! 3136 2018-07-16 14:48:21Z suehring
231! Limit also roughness length for heat and moisture where necessary
232!
233! 3123 2018-07-12 16:21:53Z suehring
234! Correct working precision for INTEGER number
235!
236! 3115 2018-07-10 12:49:26Z suehring
237! Additional building type to represent bridges
238!
239! 3091 2018-06-28 16:20:35Z suehring
240! - Limit aerodynamic resistance at vertical walls.
241! - Add check for local roughness length not exceeding surface-layer height and
242!   limit roughness length where necessary.
243!
244! 3065 2018-06-12 07:03:02Z Giersch
245! Unused array dxdir was removed, dz was replaced by dzu to consider vertical
246! grid stretching
247!
248! 3049 2018-05-29 13:52:36Z Giersch
249! Error messages revised
250!
251! 3045 2018-05-28 07:55:41Z Giersch
252! Error message added
253!
254! 3029 2018-05-23 12:19:17Z raasch
255! bugfix: close unit 151 instead of 90
256!
257! 3014 2018-05-09 08:42:38Z maronga
258! Added pc_transpiration_rate
259!
260! 2977 2018-04-17 10:27:57Z kanani
261! Implement changes from branch radiation (r2948-2971) with minor modifications.
262! (moh.hefny):
263! Extended exn for all model domain height to avoid the need to get nzut.
264!
265! 2963 2018-04-12 14:47:44Z suehring
266! Introduce index for vegetation/wall, pavement/green-wall and water/window
267! surfaces, for clearer access of surface fraction, albedo, emissivity, etc. .
268!
269! 2943 2018-04-03 16:17:10Z suehring
270! Calculate exner function at all height levels and remove some un-used
271! variables.
272!
273! 2932 2018-03-26 09:39:22Z maronga
274! renamed urban_surface_par to urban_surface_parameters
275!
276! 2921 2018-03-22 15:05:23Z Giersch
277! The activation of spinup has been moved to parin
278!
279! 2920 2018-03-22 11:22:01Z kanani
280! Remove unused pcbl, npcbl from ONLY list
281! moh.hefny:
282! Fixed bugs introduced by new structures and by moving radiation interaction
283! into radiation_model_mod.f90.
284! Bugfix: usm data output 3D didn't respect directions
285!
286! 2906 2018-03-19 08:56:40Z Giersch
287! Local variable ids has to be initialized with a value of -1 in
288! usm_3d_data_averaging
289!
290! 2894 2018-03-15 09:17:58Z Giersch
291! Calculations of the index range of the subdomain on file which overlaps with
292! the current subdomain are already done in read_restart_data_mod,
293! usm_read/write_restart_data have been renamed to usm_r/wrd_local, variable
294! named found has been introduced for checking if restart data was found,
295! reading of restart strings has been moved completely to
296! read_restart_data_mod, usm_rrd_local is already inside the overlap loop
297! programmed in read_restart_data_mod, SAVE attribute added where necessary,
298! deallocation and allocation of some arrays have been changed to take care of
299! different restart files that can be opened (index i), the marker *** end usm
300! *** is not necessary anymore, strings and their respective lengths are
301! written out and read now in case of restart runs to get rid of prescribed
302! character lengths
303!
304! 2805 2018-02-14 17:00:09Z suehring
305! Initialization of resistances.
306!
307! 2797 2018-02-08 13:24:35Z suehring
308! Comment concerning output of ground-heat flux added.
309!
310! 2766 2018-01-22 17:17:47Z kanani
311! Removed redundant commas, added some blanks
312!
313! 2765 2018-01-22 11:34:58Z maronga
314! Major bugfix in calculation of f_shf. Adjustment of roughness lengths in
315! building_pars
316!
317! 2750 2018-01-15 16:26:51Z knoop
318! Move flag plant canopy to modules
319!
320! 2737 2018-01-11 14:58:11Z kanani
321! Removed unused variables t_surf_whole...
322!
323! 2735 2018-01-11 12:01:27Z suehring
324! resistances are saved in surface attributes
325!
326! 2723 2018-01-05 09:27:03Z maronga
327! Bugfix for spinups (end_time was increased twice in case of LSM + USM runs)
328!
329! 2720 2018-01-02 16:27:15Z kanani
330! Correction of comment
331!
332! 2718 2018-01-02 08:49:38Z maronga
333! Corrected "Former revisions" section
334!
335! 2705 2017-12-18 11:26:23Z maronga
336! Changes from last commit documented
337!
338! 2703 2017-12-15 20:12:38Z maronga
339! Workaround for calculation of r_a
340!
341! 2696 2017-12-14 17:12:51Z kanani
342! - Change in file header (GPL part)
343! - Bugfix in calculation of pt_surface and related fluxes. (BM)
344! - Do not write surface temperatures onto pt array as this might cause
345!   problems with nesting. (MS)
346! - Revised calculation of pt1 (now done in surface_layer_fluxes).
347!   Bugfix, f_shf_window and f_shf_green were not set at vertical surface
348!   elements. (MS)
349! - merged with branch ebsolver
350!   green building surfaces do not evaporate yet
351!   properties of green wall layers and window layers are taken from wall layers
352!   this input data is missing. (RvT)
353! - Merged with branch radiation (developed by Mohamed Salim)
354! - Revised initialization. (MS)
355! - Rename emiss_surf into emissivity, roughness_wall into z0, albedo_surf into
356!   albedo. (MS)
357! - Move first call of usm_radiatin from usm_init to init_3d_model
358! - fixed problem with near surface temperature
359! - added near surface temperature pt_10cm_h(m), pt_10cm_v(l)%t(m)
360! - does not work with temp profile including stability, ol
361!   pt_10cm = pt1 now
362! - merged with 2357 bugfix, error message for nopointer version
363! - added indoor model coupling with wall heat flux
364! - added green substrate/ dry vegetation layer for buildings
365! - merged with 2232 new surface-type structure
366! - added transmissivity of window tiles
367! - added MOSAIK tile approach for 3 different surfaces (RvT)
368!
369! 2583 2017-10-26 13:58:38Z knoop
370! Bugfix: reverted MPI_Win_allocate_cptr introduction in last commit
371!
372! 2582 2017-10-26 13:19:46Z hellstea
373! Workaround for gnufortran compiler added in usm_calc_svf. CALL MPI_Win_allocate is
374! replaced by CALL MPI_Win_allocate_cptr if defined ( __gnufortran ).
375!
376! 2544 2017-10-13 18:09:32Z maronga
377! Date and time quantities are now read from date_and_time_mod. Solar constant is
378! read from radiation_model_mod
379!
380! 2516 2017-10-04 11:03:04Z suehring
381! Remove tabs
382!
383! 2514 2017-10-04 09:52:37Z suehring
384! upper bounds of 3d output changed from nx+1,ny+1 to nx,ny
385! no output of ghost layer data
386!
387! 2350 2017-08-15 11:48:26Z kanani
388! Bugfix and error message for nopointer version.
389! Additional "! defined(__nopointer)" as workaround to enable compilation of
390! nopointer version.
391!
392! 2318 2017-07-20 17:27:44Z suehring
393! Get topography top index via Function call
394!
395! 2317 2017-07-20 17:27:19Z suehring
396! Bugfix: adjust output of shf. Added support for spinups
397!
398! 2287 2017-06-15 16:46:30Z suehring
399! Bugfix in determination topography-top index
400!
401! 2269 2017-06-09 11:57:32Z suehring
402! Enable restart runs with different number of PEs
403! Bugfixes nopointer branch
404!
405! 2258 2017-06-08 07:55:13Z suehring
406! Bugfix, add pre-preprocessor directives to enable non-parrallel mode
407!
408! 2233 2017-05-30 18:08:54Z suehring
409!
410! 2232 2017-05-30 17:47:52Z suehring
411! Adjustments according to new surface-type structure. Remove usm_wall_heat_flux;
412! insteat, heat fluxes are directly applied in diffusion_s.
413!
414! 2213 2017-04-24 15:10:35Z kanani
415! Removal of output quantities usm_lad and usm_canopy_hr
416!
417! 2209 2017-04-19 09:34:46Z kanani
418! cpp switch __mpi3 removed,
419! minor formatting,
420! small bugfix for division by zero (Krc)
421!
422! 2113 2017-01-12 13:40:46Z kanani
423! cpp switch __mpi3 added for MPI-3 standard code (Ketelsen)
424!
425! 2071 2016-11-17 11:22:14Z maronga
426! Small bugfix (Resler)
427!
428! 2031 2016-10-21 15:11:58Z knoop
429! renamed variable rho to rho_ocean
430!
431! 2024 2016-10-12 16:42:37Z kanani
432! Bugfixes in deallocation of array plantt and reading of csf/csfsurf,
433! optimization of MPI-RMA operations,
434! declaration of pcbl as integer,
435! renamed usm_radnet -> usm_rad_net, usm_canopy_khf -> usm_canopy_hr,
436! splitted arrays svf -> svf & csf, svfsurf -> svfsurf & csfsurf,
437! use of new control parameter varnamelength,
438! added output variables usm_rad_ressw, usm_rad_reslw,
439! minor formatting changes,
440! minor optimizations.
441!
442! 2011 2016-09-19 17:29:57Z kanani
443! Major reformatting according to PALM coding standard (comments, blanks,
444! alphabetical ordering, etc.),
445! removed debug_prints,
446! removed auxiliary SUBROUTINE get_usm_info, instead, USM flag urban_surface is
447! defined in MODULE control_parameters (modules.f90) to avoid circular
448! dependencies,
449! renamed canopy_heat_flux to pc_heating_rate, as meaning of quantity changed.
450!
451! 2007 2016-08-24 15:47:17Z kanani
452! Initial revision
453!
454!
455! Description:
456! ------------
457! 2016/6/9 - Initial version of the USM (Urban Surface Model)
458!            authors: Jaroslav Resler, Pavel Krc
459!                     (Czech Technical University in Prague and Institute of
460!                      Computer Science of the Czech Academy of Sciences, Prague)
461!            with contributions: Michal Belda, Nina Benesova, Ondrej Vlcek
462!            partly inspired by PALM LSM (B. Maronga)
463!            parameterizations of Ra checked with TUF3D (E. S. Krayenhoff)
464!> Module for Urban Surface Model (USM)
465!> The module includes:
466!>    1. radiation model with direct/diffuse radiation, shading, reflections
467!>       and integration with plant canopy
468!>    2. wall and wall surface model
469!>    3. surface layer energy balance
470!>    4. anthropogenic heat (only from transportation so far)
471!>    5. necessary auxiliary subroutines (reading inputs, writing outputs,
472!>       restart simulations, ...)
473!> It also make use of standard radiation and integrates it into
474!> urban surface model.
475!>
476!> Further work:
477!> -------------
478!> 1. Remove global arrays surfouts, surfoutl and only keep track of radiosity
479!>    from surfaces that are visible from local surfaces (i.e. there is a SVF
480!>    where target is local). To do that, radiosity will be exchanged after each
481!>    reflection step using MPI_Alltoall instead of current MPI_Allgather.
482!>
483!> 2. Temporarily large values of surface heat flux can be observed, up to
484!>    1.2 Km/s, which seem to be not realistic.
485!>
486!> @todo Output of _av variables in case of restarts
487!> @todo Revise flux conversion in energy-balance solver
488!> @todo Check optimizations for RMA operations
489!> @todo Alternatives for MPI_WIN_ALLOCATE? (causes problems with openmpi)
490!> @todo Check for load imbalances in CPU measures, e.g. for exchange_horiz_prog
491!>       factor 3 between min and max time
492!> @todo Check divisions in wtend (etc.) calculations for possible division
493!>       by zero, e.g. in case fraq(0,m) + fraq(1,m) = 0?!
494!> @todo Use unit 90 for OPEN/CLOSE of input files (FK)
495!> @todo Move plant canopy stuff into plant canopy code
496!------------------------------------------------------------------------------!
497 MODULE urban_surface_mod
498
499    USE arrays_3d,                                                             &
500        ONLY:  hyp, zu, pt, p, u, v, w, tend, exner, hyrho, prr, q, ql, vpt
501
502    USE calc_mean_profile_mod,                                                 &
503        ONLY:  calc_mean_profile
504
505    USE basic_constants_and_equations_mod,                                     &
506        ONLY:  c_p, g, kappa, pi, r_d, rho_l, l_v, sigma_sb
507
508    USE control_parameters,                                                    &
509        ONLY:  coupling_start_time, topography,                                &
510               debug_output, debug_output_timestep, debug_string,              &
511               dt_3d, humidity, indoor_model,                                  &
512               intermediate_timestep_count, initializing_actions,              &
513               intermediate_timestep_count_max, simulated_time, end_time,      &
514               timestep_scheme, tsc, coupling_char, io_blocks, io_group,       &
515               message_string, time_since_reference_point, surface_pressure,   &
516               pt_surface, large_scale_forcing, lsf_surf,                      &
517               spinup_pt_mean, spinup_time, time_do3d, dt_do3d,                &
518               average_count_3d, varnamelength, urban_surface, dz
519
520    USE bulk_cloud_model_mod,                                                  &
521        ONLY: bulk_cloud_model, precipitation
522               
523    USE cpulog,                                                                &
524        ONLY:  cpu_log, log_point, log_point_s
525
526    USE date_and_time_mod,                                                     &
527        ONLY:  time_utc_init
528
529    USE grid_variables,                                                        &
530        ONLY:  dx, dy, ddx, ddy, ddx2, ddy2
531
532    USE indices,                                                               &
533        ONLY:  nx, ny, nnx, nny, nnz, nxl, nxlg, nxr, nxrg, nyn, nyng, nys,    &
534               nysg, nzb, nzt, nbgp, wall_flags_0
535
536    USE, INTRINSIC :: iso_c_binding 
537
538    USE kinds
539             
540    USE pegrid
541       
542    USE radiation_model_mod,                                                   &
543        ONLY:  albedo_type, radiation_interaction,                             &
544               radiation, rad_sw_in, rad_lw_in, rad_sw_out, rad_lw_out,        &
545               force_radiation_call, iup_u, inorth_u, isouth_u, ieast_u,       &
546               iwest_u, iup_l, inorth_l, isouth_l, ieast_l, iwest_l, id,       &
547               iz, iy, ix,  nsurf, idsvf, ndsvf,                               &
548               idcsf, ndcsf, kdcsf, pct,                                       &
549               nz_urban_b, nz_urban_t, unscheduled_radiation_calls
550
551    USE statistics,                                                            &
552        ONLY:  hom, statistic_regions
553
554    USE surface_mod,                                                           &
555        ONLY:  get_topography_top_index_ji, get_topography_top_index,          &
556               ind_pav_green, ind_veg_wall, ind_wat_win, surf_usm_h,           &
557               surf_usm_v, surface_restore_elements
558
559
560    IMPLICIT NONE
561
562!
563!-- USM model constants
564
565    REAL(wp), PARAMETER ::                     &
566              b_ch               = 6.04_wp,    &  !< Clapp & Hornberger exponent
567              lambda_h_green_dry = 0.19_wp,    &  !< heat conductivity for dry soil   
568              lambda_h_green_sm  = 3.44_wp,    &  !< heat conductivity of the soil matrix
569              lambda_h_water     = 0.57_wp,    &  !< heat conductivity of water
570              psi_sat            = -0.388_wp,  &  !< soil matrix potential at saturation
571              rho_c_soil         = 2.19E6_wp,  &  !< volumetric heat capacity of soil
572              rho_c_water        = 4.20E6_wp      !< volumetric heat capacity of water
573!               m_max_depth        = 0.0002_wp     ! Maximum capacity of the water reservoir (m)
574
575!
576!-- Soil parameters I           alpha_vg,      l_vg_green,    n_vg, gamma_w_green_sat
577    REAL(wp), DIMENSION(0:3,1:7), PARAMETER :: soil_pars = RESHAPE( (/     &
578                                 3.83_wp,  1.250_wp, 1.38_wp,  6.94E-6_wp, &  !< soil 1
579                                 3.14_wp, -2.342_wp, 1.28_wp,  1.16E-6_wp, &  !< soil 2
580                                 0.83_wp, -0.588_wp, 1.25_wp,  0.26E-6_wp, &  !< soil 3
581                                 3.67_wp, -1.977_wp, 1.10_wp,  2.87E-6_wp, &  !< soil 4
582                                 2.65_wp,  2.500_wp, 1.10_wp,  1.74E-6_wp, &  !< soil 5
583                                 1.30_wp,  0.400_wp, 1.20_wp,  0.93E-6_wp, &  !< soil 6
584                                 0.00_wp,  0.00_wp,  0.00_wp,  0.57E-6_wp  &  !< soil 7
585                                 /), (/ 4, 7 /) )
586
587!
588!-- Soil parameters II              swc_sat,     fc,   wilt,    swc_res 
589    REAL(wp), DIMENSION(0:3,1:7), PARAMETER :: m_soil_pars = RESHAPE( (/ &
590                                 0.403_wp, 0.244_wp, 0.059_wp, 0.025_wp, &  !< soil 1
591                                 0.439_wp, 0.347_wp, 0.151_wp, 0.010_wp, &  !< soil 2
592                                 0.430_wp, 0.383_wp, 0.133_wp, 0.010_wp, &  !< soil 3
593                                 0.520_wp, 0.448_wp, 0.279_wp, 0.010_wp, &  !< soil 4
594                                 0.614_wp, 0.541_wp, 0.335_wp, 0.010_wp, &  !< soil 5
595                                 0.766_wp, 0.663_wp, 0.267_wp, 0.010_wp, &  !< soil 6
596                                 0.472_wp, 0.323_wp, 0.171_wp, 0.000_wp  &  !< soil 7
597                                 /), (/ 4, 7 /) )
598!
599!-- value 9999999.9_wp -> generic available or user-defined value must be set
600!-- otherwise -> no generic variable and user setting is optional
601    REAL(wp) :: alpha_vangenuchten = 9999999.9_wp,      &  !< NAMELIST alpha_vg
602                field_capacity = 9999999.9_wp,          &  !< NAMELIST fc
603                hydraulic_conductivity = 9999999.9_wp,  &  !< NAMELIST gamma_w_green_sat
604                l_vangenuchten = 9999999.9_wp,          &  !< NAMELIST l_vg
605                n_vangenuchten = 9999999.9_wp,          &  !< NAMELIST n_vg
606                residual_moisture = 9999999.9_wp,       &  !< NAMELIST m_res
607                saturation_moisture = 9999999.9_wp,     &  !< NAMELIST m_sat
608                wilting_point = 9999999.9_wp               !< NAMELIST m_wilt
609   
610!
611!-- configuration parameters (they can be setup in PALM config)
612    LOGICAL ::  usm_material_model = .TRUE.        !< flag parameter indicating wheather the  model of heat in materials is used
613    LOGICAL ::  usm_anthropogenic_heat = .FALSE.   !< flag parameter indicating wheather the anthropogenic heat sources
614                                                   !< (e.g.transportation) are used
615    LOGICAL ::  force_radiation_call_l = .FALSE.   !< flag parameter for unscheduled radiation model calls
616    LOGICAL ::  read_wall_temp_3d = .FALSE.
617    LOGICAL ::  usm_wall_mod = .FALSE.             !< reduces conductivity of the first 2 wall layers by factor 0.1
618
619
620    INTEGER(iwp) ::  building_type = 1               !< default building type (preleminary setting)
621    INTEGER(iwp) ::  land_category = 2               !< default category for land surface
622    INTEGER(iwp) ::  wall_category = 2               !< default category for wall surface over pedestrian zone
623    INTEGER(iwp) ::  pedestrian_category = 2         !< default category for wall surface in pedestrian zone
624    INTEGER(iwp) ::  roof_category = 2               !< default category for root surface
625    REAL(wp)     ::  roughness_concrete = 0.001_wp   !< roughness length of average concrete surface
626!
627!-- Indices of input attributes in building_pars for (above) ground floor level
628    INTEGER(iwp) ::  ind_alb_wall_agfl     = 38   !< index in input list for albedo_type of wall above ground floor level
629    INTEGER(iwp) ::  ind_alb_wall_gfl      = 66   !< index in input list for albedo_type of wall ground floor level
630    INTEGER(iwp) ::  ind_alb_wall_r        = 101  !< index in input list for albedo_type of wall roof
631    INTEGER(iwp) ::  ind_alb_green_agfl    = 39   !< index in input list for albedo_type of green above ground floor level
632    INTEGER(iwp) ::  ind_alb_green_gfl     = 78   !< index in input list for albedo_type of green ground floor level
633    INTEGER(iwp) ::  ind_alb_green_r       = 117  !< index in input list for albedo_type of green roof
634    INTEGER(iwp) ::  ind_alb_win_agfl      = 40   !< index in input list for albedo_type of window fraction above ground floor level
635    INTEGER(iwp) ::  ind_alb_win_gfl       = 77   !< index in input list for albedo_type of window fraction ground floor level
636    INTEGER(iwp) ::  ind_alb_win_r         = 115  !< index in input list for albedo_type of window fraction roof
637    INTEGER(iwp) ::  ind_c_surface         = 45   !< index in input list for heat capacity wall surface
638    INTEGER(iwp) ::  ind_c_surface_green   = 48   !< index in input list for heat capacity green surface
639    INTEGER(iwp) ::  ind_c_surface_win     = 47   !< index in input list for heat capacity window surface
640    INTEGER(iwp) ::  ind_emis_wall_agfl    = 14   !< index in input list for wall emissivity, above ground floor level
641    INTEGER(iwp) ::  ind_emis_wall_gfl     = 32   !< index in input list for wall emissivity, ground floor level
642    INTEGER(iwp) ::  ind_emis_wall_r       = 100  !< index in input list for wall emissivity, roof
643    INTEGER(iwp) ::  ind_emis_green_agfl   = 15   !< index in input list for green emissivity, above ground floor level
644    INTEGER(iwp) ::  ind_emis_green_gfl    = 34   !< index in input list for green emissivity, ground floor level
645    INTEGER(iwp) ::  ind_emis_green_r      = 116  !< index in input list for green emissivity, roof
646    INTEGER(iwp) ::  ind_emis_win_agfl     = 16   !< index in input list for window emissivity, above ground floor level
647    INTEGER(iwp) ::  ind_emis_win_gfl      = 33   !< index in input list for window emissivity, ground floor level
648    INTEGER(iwp) ::  ind_emis_win_r        = 113  !< index in input list for window emissivity, roof
649    INTEGER(iwp) ::  ind_gflh              = 20   !< index in input list for ground floor level height
650    INTEGER(iwp) ::  ind_green_frac_w_agfl = 2    !< index in input list for green fraction on wall, above ground floor level
651    INTEGER(iwp) ::  ind_green_frac_w_gfl  = 23   !< index in input list for green fraction on wall, ground floor level
652    INTEGER(iwp) ::  ind_green_frac_r_agfl = 3    !< index in input list for green fraction on roof, above ground floor level
653    INTEGER(iwp) ::  ind_green_frac_r_gfl  = 24   !< index in input list for green fraction on roof, ground floor level
654    INTEGER(iwp) ::  ind_hc1_agfl          = 6    !< index in input list for heat capacity at first wall layer,
655                                                  !< above ground floor level
656    INTEGER(iwp) ::  ind_hc1_gfl           = 26   !< index in input list for heat capacity at first wall layer, ground floor level
657    INTEGER(iwp) ::  ind_hc1_wall_r        = 94   !< index in input list for heat capacity at first wall layer, roof
658    INTEGER(iwp) ::  ind_hc1_win_agfl      = 83   !< index in input list for heat capacity at first window layer,
659                                                  !< above ground floor level
660    INTEGER(iwp) ::  ind_hc1_win_gfl       = 71   !< index in input list for heat capacity at first window layer,
661                                                  !< ground floor level
662    INTEGER(iwp) ::  ind_hc1_win_r         = 107  !< index in input list for heat capacity at first window layer, roof
663    INTEGER(iwp) ::  ind_hc2_agfl          = 7    !< index in input list for heat capacity at second wall layer,
664                                                  !< above ground floor level
665    INTEGER(iwp) ::  ind_hc2_gfl           = 27   !< index in input list for heat capacity at second wall layer, ground floor level
666    INTEGER(iwp) ::  ind_hc2_wall_r        = 95   !< index in input list for heat capacity at second wall layer, roof
667    INTEGER(iwp) ::  ind_hc2_win_agfl      = 84   !< index in input list for heat capacity at second window layer,
668                                                  !< above ground floor level
669    INTEGER(iwp) ::  ind_hc2_win_gfl       = 72   !< index in input list for heat capacity at second window layer,
670                                                  !< ground floor level
671    INTEGER(iwp) ::  ind_hc2_win_r         = 108  !< index in input list for heat capacity at second window layer, roof
672    INTEGER(iwp) ::  ind_hc3_agfl          = 8    !< index in input list for heat capacity at third wall layer,
673                                                  !< above ground floor level
674    INTEGER(iwp) ::  ind_hc3_gfl           = 28   !< index in input list for heat capacity at third wall layer, ground floor level
675    INTEGER(iwp) ::  ind_hc3_wall_r        = 96   !< index in input list for heat capacity at third wall layer, roof
676    INTEGER(iwp) ::  ind_hc3_win_agfl      = 85   !< index in input list for heat capacity at third window layer,
677                                                  !< above ground floor level
678    INTEGER(iwp) ::  ind_hc3_win_gfl       = 73   !< index in input list for heat capacity at third window layer,
679                                                  !< ground floor level
680    INTEGER(iwp) ::  ind_hc3_win_r         = 109  !< index in input list for heat capacity at third window layer, roof
681    INTEGER(iwp) ::  ind_indoor_target_temp_summer = 12
682    INTEGER(iwp) ::  ind_indoor_target_temp_winter = 13
683    INTEGER(iwp) ::  ind_lai_r_agfl        = 4    !< index in input list for LAI on roof, above ground floor level
684    INTEGER(iwp) ::  ind_lai_r_gfl         = 4  !< index in input list for LAI on roof, ground floor level
685    INTEGER(iwp) ::  ind_lai_w_agfl        = 5    !< index in input list for LAI on wall, above ground floor level
686    INTEGER(iwp) ::  ind_lai_w_gfl         = 25   !< index in input list for LAI on wall, ground floor level
687    INTEGER(iwp) ::  ind_lambda_surf       = 46   !< index in input list for thermal conductivity of wall surface
688    INTEGER(iwp) ::  ind_lambda_surf_green = 50   !< index in input list for thermal conductivity of green surface
689    INTEGER(iwp) ::  ind_lambda_surf_win   = 49   !< index in input list for thermal conductivity of window surface
690    INTEGER(iwp) ::  ind_tc1_agfl          = 9    !< index in input list for thermal conductivity at first wall layer,
691                                                  !< above ground floor level
692    INTEGER(iwp) ::  ind_tc1_gfl           = 29   !< index in input list for thermal conductivity at first wall layer,
693                                                  !< ground floor level
694    INTEGER(iwp) ::  ind_tc1_wall_r        = 97   !< index in input list for thermal conductivity at first wall layer, roof
695    INTEGER(iwp) ::  ind_tc1_win_agfl      = 86   !< index in input list for thermal conductivity at first window layer,
696                                                  !< above ground floor level
697    INTEGER(iwp) ::  ind_tc1_win_gfl       = 74   !< index in input list for thermal conductivity at first window layer,
698                                                  !< ground floor level
699    INTEGER(iwp) ::  ind_tc1_win_r         = 110  !< index in input list for thermal conductivity at first window layer, roof
700    INTEGER(iwp) ::  ind_tc2_agfl          = 10   !< index in input list for thermal conductivity at second wall layer,
701                                                  !< above ground floor level
702    INTEGER(iwp) ::  ind_tc2_gfl           = 30   !< index in input list for thermal conductivity at second wall layer,
703                                                  !< ground floor level
704    INTEGER(iwp) ::  ind_tc2_wall_r        = 98   !< index in input list for thermal conductivity at second wall layer, roof
705    INTEGER(iwp) ::  ind_tc2_win_agfl      = 87   !< index in input list for thermal conductivity at second window layer,
706                                                  !< above ground floor level
707    INTEGER(iwp) ::  ind_tc2_win_gfl       = 75   !< index in input list for thermal conductivity at second window layer,
708                                                  !< ground floor level
709    INTEGER(iwp) ::  ind_tc2_win_r         = 111  !< index in input list for thermal conductivity at second window layer,
710                                                  !< ground floor level
711    INTEGER(iwp) ::  ind_tc3_agfl          = 11   !< index in input list for thermal conductivity at third wall layer,
712                                                  !< above ground floor level
713    INTEGER(iwp) ::  ind_tc3_gfl           = 31   !< index in input list for thermal conductivity at third wall layer,
714                                                  !< ground floor level
715    INTEGER(iwp) ::  ind_tc3_wall_r        = 99   !< index in input list for thermal conductivity at third wall layer, roof
716    INTEGER(iwp) ::  ind_tc3_win_agfl      = 88   !< index in input list for thermal conductivity at third window layer,
717                                                  !< above ground floor level
718    INTEGER(iwp) ::  ind_tc3_win_gfl       = 76   !< index in input list for thermal conductivity at third window layer,
719                                                  !< ground floor level
720    INTEGER(iwp) ::  ind_tc3_win_r         = 112  !< index in input list for thermal conductivity at third window layer, roof
721    INTEGER(iwp) ::  ind_thick_1_agfl      = 41   !< index for wall layer thickness - 1st layer above ground floor level
722    INTEGER(iwp) ::  ind_thick_1_gfl       = 62   !< index for wall layer thickness - 1st layer ground floor level
723    INTEGER(iwp) ::  ind_thick_1_wall_r    = 90   !< index for wall layer thickness - 1st layer roof
724    INTEGER(iwp) ::  ind_thick_1_win_agfl  = 79   !< index for window layer thickness - 1st layer above ground floor level
725    INTEGER(iwp) ::  ind_thick_1_win_gfl   = 67   !< index for window layer thickness - 1st layer ground floor level
726    INTEGER(iwp) ::  ind_thick_1_win_r     = 103  !< index for window layer thickness - 1st layer roof
727    INTEGER(iwp) ::  ind_thick_2_agfl      = 42   !< index for wall layer thickness - 2nd layer above ground floor level
728    INTEGER(iwp) ::  ind_thick_2_gfl       = 63   !< index for wall layer thickness - 2nd layer ground floor level
729    INTEGER(iwp) ::  ind_thick_2_wall_r    = 91   !< index for wall layer thickness - 2nd layer roof
730    INTEGER(iwp) ::  ind_thick_2_win_agfl  = 80   !< index for window layer thickness - 2nd layer above ground floor level
731    INTEGER(iwp) ::  ind_thick_2_win_gfl   = 68   !< index for window layer thickness - 2nd layer ground floor level
732    INTEGER(iwp) ::  ind_thick_2_win_r     = 104  !< index for window layer thickness - 2nd layer roof
733    INTEGER(iwp) ::  ind_thick_3_agfl      = 43   !< index for wall layer thickness - 3rd layer above ground floor level
734    INTEGER(iwp) ::  ind_thick_3_gfl       = 64   !< index for wall layer thickness - 3rd layer ground floor level
735    INTEGER(iwp) ::  ind_thick_3_wall_r    = 92   !< index for wall layer thickness - 3rd layer roof
736    INTEGER(iwp) ::  ind_thick_3_win_agfl  = 81   !< index for window layer thickness - 3rd layer above ground floor level
737    INTEGER(iwp) ::  ind_thick_3_win_gfl   = 69   !< index for window layer thickness - 3rd layer ground floor level 
738    INTEGER(iwp) ::  ind_thick_3_win_r     = 105  !< index for window layer thickness - 3rd layer roof
739    INTEGER(iwp) ::  ind_thick_4_agfl      = 44   !< index for wall layer thickness - 4th layer above ground floor level
740    INTEGER(iwp) ::  ind_thick_4_gfl       = 65   !< index for wall layer thickness - 4th layer ground floor level
741    INTEGER(iwp) ::  ind_thick_4_wall_r    = 93   !< index for wall layer thickness - 4st layer roof
742    INTEGER(iwp) ::  ind_thick_4_win_agfl  = 82   !< index for window layer thickness - 4th layer above ground floor level
743    INTEGER(iwp) ::  ind_thick_4_win_gfl   = 70   !< index for window layer thickness - 4th layer ground floor level
744    INTEGER(iwp) ::  ind_thick_4_win_r     = 106  !< index for window layer thickness - 4th layer roof
745    INTEGER(iwp) ::  ind_trans_agfl        = 17   !< index in input list for window transmissivity, above ground floor level
746    INTEGER(iwp) ::  ind_trans_gfl         = 35   !< index in input list for window transmissivity, ground floor level
747    INTEGER(iwp) ::  ind_trans_r           = 114  !< index in input list for window transmissivity, roof
748    INTEGER(iwp) ::  ind_wall_frac_agfl    = 0    !< index in input list for wall fraction, above ground floor level
749    INTEGER(iwp) ::  ind_wall_frac_gfl     = 21   !< index in input list for wall fraction, ground floor level
750    INTEGER(iwp) ::  ind_wall_frac_r       = 89   !< index in input list for wall fraction, roof
751    INTEGER(iwp) ::  ind_win_frac_agfl     = 1    !< index in input list for window fraction, above ground floor level
752    INTEGER(iwp) ::  ind_win_frac_gfl      = 22   !< index in input list for window fraction, ground floor level
753    INTEGER(iwp) ::  ind_win_frac_r        = 102  !< index in input list for window fraction, roof
754    INTEGER(iwp) ::  ind_z0_agfl           = 18   !< index in input list for z0, above ground floor level
755    INTEGER(iwp) ::  ind_z0_gfl            = 36   !< index in input list for z0, ground floor level
756    INTEGER(iwp) ::  ind_z0qh_agfl         = 19   !< index in input list for z0h / z0q, above ground floor level
757    INTEGER(iwp) ::  ind_z0qh_gfl          = 37   !< index in input list for z0h / z0q, ground floor level
758    INTEGER(iwp) ::  ind_green_type_roof   = 118  !< index in input list for type of green roof
759
760
761    REAL(wp)  ::  roof_height_limit = 4.0_wp         !< height for distinguish between land surfaces and roofs
762    REAL(wp)  ::  ground_floor_level = 4.0_wp        !< default ground floor level
763
764
765    CHARACTER(37), DIMENSION(0:7), PARAMETER :: building_type_name = (/     &
766                                   'user-defined                         ', &  !< type 0
767                                   'residential - 1950                   ', &  !< type  1
768                                   'residential 1951 - 2000              ', &  !< type  2
769                                   'residential 2001 -                   ', &  !< type  3
770                                   'office - 1950                        ', &  !< type  4
771                                   'office 1951 - 2000                   ', &  !< type  5
772                                   'office 2001 -                        ', &  !< type  6
773                                   'bridges                              '  &  !< type  7
774                                                                     /)
775
776
777!
778!-- Building facade/wall/green/window properties (partly according to PIDS).
779!-- Initialization of building_pars is outsourced to usm_init_pars. This is
780!-- needed because of the huge number of attributes given in building_pars
781!-- (>700), while intel and gfortran compiler have hard limit of continuation
782!-- lines of 511.
783    REAL(wp), DIMENSION(0:133,1:7) ::  building_pars
784!
785!-- Type for surface temperatures at vertical walls. Is not necessary for horizontal walls.
786    TYPE t_surf_vertical
787       REAL(wp), DIMENSION(:), ALLOCATABLE         :: t
788    END TYPE t_surf_vertical
789!
790!-- Type for wall temperatures at vertical walls. Is not necessary for horizontal walls.
791    TYPE t_wall_vertical
792       REAL(wp), DIMENSION(:,:), ALLOCATABLE       :: t
793    END TYPE t_wall_vertical
794
795    TYPE surf_type_usm
796       REAL(wp), DIMENSION(:),   ALLOCATABLE ::  var_usm_1d  !< 1D prognostic variable
797       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  var_usm_2d  !< 2D prognostic variable
798    END TYPE surf_type_usm
799   
800    TYPE(surf_type_usm), POINTER  ::  m_liq_usm_h,        &  !< liquid water reservoir (m), horizontal surface elements
801                                      m_liq_usm_h_p          !< progn. liquid water reservoir (m), horizontal surface elements
802
803    TYPE(surf_type_usm), TARGET   ::  m_liq_usm_h_1,      &  !<
804                                      m_liq_usm_h_2          !<
805
806    TYPE(surf_type_usm), DIMENSION(:), POINTER  ::        &
807                                      m_liq_usm_v,        &  !< liquid water reservoir (m), vertical surface elements
808                                      m_liq_usm_v_p          !< progn. liquid water reservoir (m), vertical surface elements
809
810    TYPE(surf_type_usm), DIMENSION(0:3), TARGET   ::      &
811                                      m_liq_usm_v_1,      &  !<
812                                      m_liq_usm_v_2          !<
813
814    TYPE(surf_type_usm), TARGET ::  tm_liq_usm_h_m      !< liquid water reservoir tendency (m), horizontal surface elements
815    TYPE(surf_type_usm), DIMENSION(0:3), TARGET ::  tm_liq_usm_v_m      !< liquid water reservoir tendency (m),
816                                                                        !< vertical surface elements
817
818!
819!-- anthropogenic heat sources
820    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE        ::  aheat             !< daily average of anthropogenic heat (W/m2)
821    REAL(wp), DIMENSION(:,:), ALLOCATABLE          ::  aheatprof         !< diurnal profiles of anthropogenic heat
822                                                                         !< for particular layers
823    INTEGER(iwp)                                   ::  naheatlayers = 1  !< number of layers of anthropogenic heat
824
825!
826!-- wall surface model
827!-- wall surface model constants
828    INTEGER(iwp), PARAMETER                        :: nzb_wall = 0       !< inner side of the wall model (to be switched)
829    INTEGER(iwp), PARAMETER                        :: nzt_wall = 3       !< outer side of the wall model (to be switched)
830    INTEGER(iwp), PARAMETER                        :: nzw = 4            !< number of wall layers (fixed for now)
831
832    REAL(wp), DIMENSION(nzb_wall:nzt_wall)         :: zwn_default        = (/0.0242_wp, 0.0969_wp, 0.346_wp, 1.0_wp /)
833    REAL(wp), DIMENSION(nzb_wall:nzt_wall)         :: zwn_default_window = (/0.25_wp,   0.5_wp,    0.75_wp,  1.0_wp /)
834    REAL(wp), DIMENSION(nzb_wall:nzt_wall)         :: zwn_default_green  = (/0.25_wp,   0.5_wp,    0.75_wp,  1.0_wp /)
835                                                                         !< normalized soil, wall and roof, window and
836                                                                         !<green layer depths (m/m)
837
838    REAL(wp)                                       :: wall_inner_temperature   = 295.0_wp    !< temperature of the inner wall
839                                                                                             !< surface (~22 degrees C) (K)
840    REAL(wp)                                       :: roof_inner_temperature   = 295.0_wp    !< temperature of the inner roof
841                                                                                             !< surface (~22 degrees C) (K)
842    REAL(wp)                                       :: soil_inner_temperature   = 288.0_wp    !< temperature of the deep soil
843                                                                                             !< (~15 degrees C) (K)
844    REAL(wp)                                       :: window_inner_temperature = 295.0_wp    !< temperature of the inner window
845                                                                                             !< surface (~22 degrees C) (K)
846
847    REAL(wp)                                       :: m_total = 0.0_wp  !< weighted total water content of the soil (m3/m3)
848    INTEGER(iwp)                                   :: soil_type
849
850!
851!-- surface and material model variables for walls, ground, roofs
852    REAL(wp), DIMENSION(:), ALLOCATABLE            :: zwn                !< normalized wall layer depths (m)
853    REAL(wp), DIMENSION(:), ALLOCATABLE            :: zwn_window         !< normalized window layer depths (m)
854    REAL(wp), DIMENSION(:), ALLOCATABLE            :: zwn_green          !< normalized green layer depths (m)
855
856    REAL(wp), DIMENSION(:), POINTER                :: t_surf_wall_h
857    REAL(wp), DIMENSION(:), POINTER                :: t_surf_wall_h_p 
858    REAL(wp), DIMENSION(:), POINTER                :: t_surf_window_h
859    REAL(wp), DIMENSION(:), POINTER                :: t_surf_window_h_p 
860    REAL(wp), DIMENSION(:), POINTER                :: t_surf_green_h
861    REAL(wp), DIMENSION(:), POINTER                :: t_surf_green_h_p 
862
863    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_wall_h_1
864    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_wall_h_2
865    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_window_h_1
866    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_window_h_2
867    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_h_1
868    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_h_2
869
870    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_wall_v
871    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_wall_v_p
872    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_window_v
873    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_window_v_p
874    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_green_v
875    TYPE(t_surf_vertical), DIMENSION(:), POINTER   ::  t_surf_green_v_p
876
877    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_wall_v_1
878    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_wall_v_2
879    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_window_v_1
880    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_window_v_2
881    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_green_v_1
882    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_green_v_2
883
884!
885!-- Energy balance variables
886!-- parameters of the land, roof and wall surfaces
887
888    REAL(wp), DIMENSION(:,:), POINTER                :: t_wall_h, t_wall_h_p
889    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h_1, t_wall_h_2
890    REAL(wp), DIMENSION(:,:), POINTER                :: t_window_h, t_window_h_p
891    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_window_h_1, t_window_h_2
892    REAL(wp), DIMENSION(:,:), POINTER                :: t_green_h, t_green_h_p
893    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_green_h_1, t_green_h_2
894    REAL(wp), DIMENSION(:,:), POINTER                :: swc_h, rootfr_h, wilt_h, fc_h, swc_sat_h, swc_h_p, swc_res_h
895    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: swc_h_1, rootfr_h_1, &
896                                                        wilt_h_1, fc_h_1, swc_sat_h_1, swc_h_2, swc_res_h_1
897   
898
899    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: t_wall_v, t_wall_v_p
900    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v_1, t_wall_v_2
901    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: t_window_v, t_window_v_p
902    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_window_v_1, t_window_v_2
903    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: t_green_v, t_green_v_p
904    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v_1, t_green_v_2
905    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: swc_v, swc_v_p
906    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: swc_v_1, swc_v_2
907
908!
909!-- Surface and material parameters classes (surface_type)
910!-- albedo, emissivity, lambda_surf, roughness, thickness, volumetric heat capacity, thermal conductivity
911    INTEGER(iwp)                                   :: n_surface_types       !< number of the wall type categories
912    INTEGER(iwp), PARAMETER                        :: n_surface_params = 9  !< number of parameters for each type of the wall
913    INTEGER(iwp), PARAMETER                        :: ialbedo  = 1          !< albedo of the surface
914    INTEGER(iwp), PARAMETER                        :: iemiss   = 2          !< emissivity of the surface
915    INTEGER(iwp), PARAMETER                        :: ilambdas = 3          !< heat conductivity lambda S between surface
916                                                                            !< and material ( W m-2 K-1 )
917    INTEGER(iwp), PARAMETER                        :: irough   = 4          !< roughness length z0 for movements
918    INTEGER(iwp), PARAMETER                        :: iroughh  = 5          !< roughness length z0h for scalars
919                                                                            !< (heat, humidity,...)
920    INTEGER(iwp), PARAMETER                        :: icsurf   = 6          !< Surface skin layer heat capacity (J m-2 K-1 )
921    INTEGER(iwp), PARAMETER                        :: ithick   = 7          !< thickness of the surface (wall, roof, land)  ( m )
922    INTEGER(iwp), PARAMETER                        :: irhoC    = 8          !< volumetric heat capacity rho*C of
923                                                                            !< the material ( J m-3 K-1 )
924    INTEGER(iwp), PARAMETER                        :: ilambdah = 9          !< thermal conductivity lambda H
925                                                                            !< of the wall (W m-1 K-1 )
926    CHARACTER(12), DIMENSION(:), ALLOCATABLE       :: surface_type_names    !< names of wall types (used only for reports)
927    INTEGER(iwp), DIMENSION(:), ALLOCATABLE        :: surface_type_codes    !< codes of wall types
928    REAL(wp), DIMENSION(:,:), ALLOCATABLE          :: surface_params        !< parameters of wall types
929
930!
931!-- interfaces of subroutines accessed from outside of this module
932    INTERFACE usm_3d_data_averaging
933       MODULE PROCEDURE usm_3d_data_averaging
934    END INTERFACE usm_3d_data_averaging
935
936    INTERFACE usm_boundary_condition
937       MODULE PROCEDURE usm_boundary_condition
938    END INTERFACE usm_boundary_condition
939
940    INTERFACE usm_check_data_output
941       MODULE PROCEDURE usm_check_data_output
942    END INTERFACE usm_check_data_output
943   
944    INTERFACE usm_check_parameters
945       MODULE PROCEDURE usm_check_parameters
946    END INTERFACE usm_check_parameters
947   
948    INTERFACE usm_data_output_3d
949       MODULE PROCEDURE usm_data_output_3d
950    END INTERFACE usm_data_output_3d
951   
952    INTERFACE usm_define_netcdf_grid
953       MODULE PROCEDURE usm_define_netcdf_grid
954    END INTERFACE usm_define_netcdf_grid
955
956    INTERFACE usm_init
957       MODULE PROCEDURE usm_init
958    END INTERFACE usm_init
959
960    INTERFACE usm_init_arrays
961       MODULE PROCEDURE usm_init_arrays
962    END INTERFACE usm_init_arrays
963
964    INTERFACE usm_material_heat_model
965       MODULE PROCEDURE usm_material_heat_model
966    END INTERFACE usm_material_heat_model
967   
968    INTERFACE usm_green_heat_model
969       MODULE PROCEDURE usm_green_heat_model
970    END INTERFACE usm_green_heat_model
971   
972    INTERFACE usm_parin
973       MODULE PROCEDURE usm_parin
974    END INTERFACE usm_parin
975
976    INTERFACE usm_rrd_local 
977       MODULE PROCEDURE usm_rrd_local
978    END INTERFACE usm_rrd_local
979
980    INTERFACE usm_surface_energy_balance
981       MODULE PROCEDURE usm_surface_energy_balance
982    END INTERFACE usm_surface_energy_balance
983   
984    INTERFACE usm_swap_timelevel
985       MODULE PROCEDURE usm_swap_timelevel
986    END INTERFACE usm_swap_timelevel
987       
988    INTERFACE usm_wrd_local
989       MODULE PROCEDURE usm_wrd_local
990    END INTERFACE usm_wrd_local
991
992   
993    SAVE
994
995    PRIVATE 
996
997!
998!-- Public functions
999    PUBLIC usm_boundary_condition, usm_check_parameters, usm_init,               &
1000           usm_rrd_local,                                                        & 
1001           usm_surface_energy_balance, usm_material_heat_model,                  &
1002           usm_swap_timelevel, usm_check_data_output, usm_3d_data_averaging,     &
1003           usm_data_output_3d, usm_define_netcdf_grid, usm_parin,                &
1004           usm_wrd_local, usm_init_arrays
1005
1006!
1007!-- Public parameters, constants and initial values
1008    PUBLIC usm_anthropogenic_heat, usm_material_model, usm_wall_mod, &
1009           usm_green_heat_model, building_pars,                      &
1010           nzb_wall, nzt_wall, t_wall_h, t_wall_v,                   &
1011           t_window_h, t_window_v, building_type
1012
1013
1014
1015 CONTAINS
1016
1017!------------------------------------------------------------------------------!
1018! Description:
1019! ------------
1020!> This subroutine creates the necessary indices of the urban surfaces
1021!> and plant canopy and it allocates the needed arrays for USM
1022!------------------------------------------------------------------------------!
1023    SUBROUTINE usm_init_arrays
1024   
1025        IMPLICIT NONE
1026       
1027        INTEGER(iwp) ::  l
1028
1029        IF ( debug_output )  CALL debug_message( 'usm_init_arrays', 'start' )
1030
1031!
1032!--     Allocate radiation arrays which are part of the new data type.
1033!--     For horizontal surfaces.
1034        ALLOCATE ( surf_usm_h%surfhf(1:surf_usm_h%ns)    )
1035        ALLOCATE ( surf_usm_h%rad_net_l(1:surf_usm_h%ns) )
1036!
1037!--     For vertical surfaces
1038        DO  l = 0, 3
1039           ALLOCATE ( surf_usm_v(l)%surfhf(1:surf_usm_v(l)%ns)    )
1040           ALLOCATE ( surf_usm_v(l)%rad_net_l(1:surf_usm_v(l)%ns) )
1041        ENDDO
1042
1043!
1044!--     Wall surface model
1045!--     allocate arrays for wall surface model and define pointers
1046!--     allocate array of wall types and wall parameters
1047        ALLOCATE ( surf_usm_h%surface_types(1:surf_usm_h%ns)      )
1048        ALLOCATE ( surf_usm_h%building_type(1:surf_usm_h%ns)      )
1049        ALLOCATE ( surf_usm_h%building_type_name(1:surf_usm_h%ns) )
1050        surf_usm_h%building_type      = 0
1051        surf_usm_h%building_type_name = 'none'
1052        DO  l = 0, 3
1053           ALLOCATE ( surf_usm_v(l)%surface_types(1:surf_usm_v(l)%ns)      )
1054           ALLOCATE ( surf_usm_v(l)%building_type(1:surf_usm_v(l)%ns)      )
1055           ALLOCATE ( surf_usm_v(l)%building_type_name(1:surf_usm_v(l)%ns) )
1056           surf_usm_v(l)%building_type      = 0
1057           surf_usm_v(l)%building_type_name = 'none'
1058        ENDDO
1059!
1060!--     Allocate albedo_type and albedo. Each surface element
1061!--     has 3 values, 0: wall fraction, 1: green fraction, 2: window fraction.
1062        ALLOCATE ( surf_usm_h%albedo_type(0:2,1:surf_usm_h%ns) )
1063        ALLOCATE ( surf_usm_h%albedo(0:2,1:surf_usm_h%ns)      )
1064        surf_usm_h%albedo_type = albedo_type
1065        DO  l = 0, 3
1066           ALLOCATE ( surf_usm_v(l)%albedo_type(0:2,1:surf_usm_v(l)%ns) )
1067           ALLOCATE ( surf_usm_v(l)%albedo(0:2,1:surf_usm_v(l)%ns)      )
1068           surf_usm_v(l)%albedo_type = albedo_type
1069        ENDDO       
1070
1071!
1072!--     Allocate indoor target temperature for summer and winter
1073        ALLOCATE ( surf_usm_h%target_temp_summer(1:surf_usm_h%ns) )
1074        ALLOCATE ( surf_usm_h%target_temp_winter(1:surf_usm_h%ns) )
1075        DO  l = 0, 3
1076           ALLOCATE ( surf_usm_v(l)%target_temp_summer(1:surf_usm_v(l)%ns) )
1077           ALLOCATE ( surf_usm_v(l)%target_temp_winter(1:surf_usm_v(l)%ns) )
1078        ENDDO
1079!
1080!--     In case the indoor model is applied, allocate memory for waste heat
1081!--     and indoor temperature.
1082        IF ( indoor_model )  THEN
1083           ALLOCATE ( surf_usm_h%waste_heat(1:surf_usm_h%ns) )
1084           surf_usm_h%waste_heat = 0.0_wp
1085           DO  l = 0, 3
1086              ALLOCATE ( surf_usm_v(l)%waste_heat(1:surf_usm_v(l)%ns) )
1087              surf_usm_v(l)%waste_heat = 0.0_wp
1088           ENDDO
1089        ENDIF
1090!
1091!--     Allocate flag indicating ground floor level surface elements
1092        ALLOCATE ( surf_usm_h%ground_level(1:surf_usm_h%ns) ) 
1093        DO  l = 0, 3
1094           ALLOCATE ( surf_usm_v(l)%ground_level(1:surf_usm_v(l)%ns) )
1095        ENDDO   
1096!
1097!--      Allocate arrays for relative surface fraction.
1098!--      0 - wall fraction, 1 - green fraction, 2 - window fraction
1099         ALLOCATE ( surf_usm_h%frac(0:2,1:surf_usm_h%ns) )
1100         surf_usm_h%frac = 0.0_wp
1101         DO  l = 0, 3
1102            ALLOCATE ( surf_usm_v(l)%frac(0:2,1:surf_usm_v(l)%ns) )
1103            surf_usm_v(l)%frac = 0.0_wp
1104         ENDDO
1105
1106!
1107!--     wall and roof surface parameters. First for horizontal surfaces
1108        ALLOCATE ( surf_usm_h%isroof_surf(1:surf_usm_h%ns)        )
1109        ALLOCATE ( surf_usm_h%lambda_surf(1:surf_usm_h%ns)        )
1110        ALLOCATE ( surf_usm_h%lambda_surf_window(1:surf_usm_h%ns) )
1111        ALLOCATE ( surf_usm_h%lambda_surf_green(1:surf_usm_h%ns)  )
1112        ALLOCATE ( surf_usm_h%c_surface(1:surf_usm_h%ns)          )
1113        ALLOCATE ( surf_usm_h%c_surface_window(1:surf_usm_h%ns)   )
1114        ALLOCATE ( surf_usm_h%c_surface_green(1:surf_usm_h%ns)    )
1115        ALLOCATE ( surf_usm_h%transmissivity(1:surf_usm_h%ns)     )
1116        ALLOCATE ( surf_usm_h%lai(1:surf_usm_h%ns)                )
1117        ALLOCATE ( surf_usm_h%emissivity(0:2,1:surf_usm_h%ns)     )
1118        ALLOCATE ( surf_usm_h%r_a(1:surf_usm_h%ns)                )
1119        ALLOCATE ( surf_usm_h%r_a_green(1:surf_usm_h%ns)          )
1120        ALLOCATE ( surf_usm_h%r_a_window(1:surf_usm_h%ns)         )
1121        ALLOCATE ( surf_usm_h%green_type_roof(1:surf_usm_h%ns)    )
1122        ALLOCATE ( surf_usm_h%r_s(1:surf_usm_h%ns)                )
1123       
1124!
1125!--     For vertical surfaces.
1126        DO  l = 0, 3
1127           ALLOCATE ( surf_usm_v(l)%lambda_surf(1:surf_usm_v(l)%ns)        )
1128           ALLOCATE ( surf_usm_v(l)%c_surface(1:surf_usm_v(l)%ns)          )
1129           ALLOCATE ( surf_usm_v(l)%lambda_surf_window(1:surf_usm_v(l)%ns) )
1130           ALLOCATE ( surf_usm_v(l)%c_surface_window(1:surf_usm_v(l)%ns)   )
1131           ALLOCATE ( surf_usm_v(l)%lambda_surf_green(1:surf_usm_v(l)%ns)  )
1132           ALLOCATE ( surf_usm_v(l)%c_surface_green(1:surf_usm_v(l)%ns)    )
1133           ALLOCATE ( surf_usm_v(l)%transmissivity(1:surf_usm_v(l)%ns)     )
1134           ALLOCATE ( surf_usm_v(l)%lai(1:surf_usm_v(l)%ns)                )
1135           ALLOCATE ( surf_usm_v(l)%emissivity(0:2,1:surf_usm_v(l)%ns)     )
1136           ALLOCATE ( surf_usm_v(l)%r_a(1:surf_usm_v(l)%ns)                )
1137           ALLOCATE ( surf_usm_v(l)%r_a_green(1:surf_usm_v(l)%ns)          )
1138           ALLOCATE ( surf_usm_v(l)%r_a_window(1:surf_usm_v(l)%ns)         )           
1139           ALLOCATE ( surf_usm_v(l)%r_s(1:surf_usm_v(l)%ns)                )
1140        ENDDO
1141
1142!       
1143!--     allocate wall and roof material parameters. First for horizontal surfaces
1144        ALLOCATE ( surf_usm_h%thickness_wall(1:surf_usm_h%ns)                    )
1145        ALLOCATE ( surf_usm_h%thickness_window(1:surf_usm_h%ns)                  )
1146        ALLOCATE ( surf_usm_h%thickness_green(1:surf_usm_h%ns)                   )
1147        ALLOCATE ( surf_usm_h%lambda_h(nzb_wall:nzt_wall,1:surf_usm_h%ns)        )
1148        ALLOCATE ( surf_usm_h%rho_c_wall(nzb_wall:nzt_wall,1:surf_usm_h%ns)      )
1149        ALLOCATE ( surf_usm_h%lambda_h_window(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1150        ALLOCATE ( surf_usm_h%rho_c_window(nzb_wall:nzt_wall,1:surf_usm_h%ns)    )
1151        ALLOCATE ( surf_usm_h%lambda_h_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)  )
1152        ALLOCATE ( surf_usm_h%rho_c_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)     )
1153
1154        ALLOCATE ( surf_usm_h%rho_c_total_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)    )
1155        ALLOCATE ( surf_usm_h%n_vg_green(1:surf_usm_h%ns)                             )
1156        ALLOCATE ( surf_usm_h%alpha_vg_green(1:surf_usm_h%ns)                         )
1157        ALLOCATE ( surf_usm_h%l_vg_green(1:surf_usm_h%ns)                             )
1158        ALLOCATE ( surf_usm_h%gamma_w_green_sat(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)  )
1159        ALLOCATE ( surf_usm_h%lambda_w_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)       )
1160        ALLOCATE ( surf_usm_h%gamma_w_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)        )
1161        ALLOCATE ( surf_usm_h%tswc_h_m(nzb_wall:nzt_wall,1:surf_usm_h%ns)             )
1162
1163!
1164!--     For vertical surfaces.
1165        DO  l = 0, 3
1166           ALLOCATE ( surf_usm_v(l)%thickness_wall(1:surf_usm_v(l)%ns)                    )
1167           ALLOCATE ( surf_usm_v(l)%thickness_window(1:surf_usm_v(l)%ns)                  )
1168           ALLOCATE ( surf_usm_v(l)%thickness_green(1:surf_usm_v(l)%ns)                   )
1169           ALLOCATE ( surf_usm_v(l)%lambda_h(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)        )
1170           ALLOCATE ( surf_usm_v(l)%rho_c_wall(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)      )
1171           ALLOCATE ( surf_usm_v(l)%lambda_h_window(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1172           ALLOCATE ( surf_usm_v(l)%rho_c_window(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)    )
1173           ALLOCATE ( surf_usm_v(l)%lambda_h_green(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)  )
1174           ALLOCATE ( surf_usm_v(l)%rho_c_green(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)     )
1175        ENDDO
1176
1177!
1178!--     allocate green wall and roof vegetation and soil parameters. First horizontal surfaces
1179        ALLOCATE ( surf_usm_h%g_d(1:surf_usm_h%ns)              )
1180        ALLOCATE ( surf_usm_h%c_liq(1:surf_usm_h%ns)            )
1181        ALLOCATE ( surf_usm_h%qsws_liq(1:surf_usm_h%ns)         )
1182        ALLOCATE ( surf_usm_h%qsws_veg(1:surf_usm_h%ns)         )
1183        ALLOCATE ( surf_usm_h%r_canopy(1:surf_usm_h%ns)         )
1184        ALLOCATE ( surf_usm_h%r_canopy_min(1:surf_usm_h%ns)     )
1185        ALLOCATE ( surf_usm_h%pt_10cm(1:surf_usm_h%ns)          ) 
1186
1187!
1188!--     For vertical surfaces.
1189        DO  l = 0, 3
1190          ALLOCATE ( surf_usm_v(l)%g_d(1:surf_usm_v(l)%ns)              )
1191          ALLOCATE ( surf_usm_v(l)%c_liq(1:surf_usm_v(l)%ns)            )
1192          ALLOCATE ( surf_usm_v(l)%qsws_liq(1:surf_usm_v(l)%ns)         )
1193          ALLOCATE ( surf_usm_v(l)%qsws_veg(1:surf_usm_v(l)%ns)         )
1194          ALLOCATE ( surf_usm_v(l)%r_canopy(1:surf_usm_v(l)%ns)         )
1195          ALLOCATE ( surf_usm_v(l)%r_canopy_min(1:surf_usm_v(l)%ns)     )
1196          ALLOCATE ( surf_usm_v(l)%pt_10cm(1:surf_usm_v(l)%ns)          )
1197        ENDDO
1198
1199!
1200!--     allocate wall and roof layers sizes. For horizontal surfaces.
1201        ALLOCATE ( zwn(nzb_wall:nzt_wall)                                        )
1202        ALLOCATE ( surf_usm_h%dz_wall(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)       )
1203        ALLOCATE ( zwn_window(nzb_wall:nzt_wall)                                 )
1204        ALLOCATE ( surf_usm_h%dz_window(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)     )
1205        ALLOCATE ( zwn_green(nzb_wall:nzt_wall)                                  )
1206        ALLOCATE ( surf_usm_h%dz_green(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)      )
1207        ALLOCATE ( surf_usm_h%ddz_wall(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)      )
1208        ALLOCATE ( surf_usm_h%dz_wall_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)    )
1209        ALLOCATE ( surf_usm_h%ddz_wall_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)   )
1210        ALLOCATE ( surf_usm_h%zw(nzb_wall:nzt_wall,1:surf_usm_h%ns)              )
1211        ALLOCATE ( surf_usm_h%ddz_window(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)    )
1212        ALLOCATE ( surf_usm_h%dz_window_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)  )
1213        ALLOCATE ( surf_usm_h%ddz_window_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1214        ALLOCATE ( surf_usm_h%zw_window(nzb_wall:nzt_wall,1:surf_usm_h%ns)       )
1215        ALLOCATE ( surf_usm_h%ddz_green(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)     )
1216        ALLOCATE ( surf_usm_h%dz_green_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)   )
1217        ALLOCATE ( surf_usm_h%ddz_green_stag(nzb_wall:nzt_wall,1:surf_usm_h%ns)  )
1218        ALLOCATE ( surf_usm_h%zw_green(nzb_wall:nzt_wall,1:surf_usm_h%ns)        )
1219
1220!
1221!--     For vertical surfaces.
1222        DO  l = 0, 3
1223           ALLOCATE ( surf_usm_v(l)%dz_wall(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)       )
1224           ALLOCATE ( surf_usm_v(l)%dz_window(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)     )
1225           ALLOCATE ( surf_usm_v(l)%dz_green(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)      )
1226           ALLOCATE ( surf_usm_v(l)%ddz_wall(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)      )
1227           ALLOCATE ( surf_usm_v(l)%dz_wall_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)    )
1228           ALLOCATE ( surf_usm_v(l)%ddz_wall_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)   )
1229           ALLOCATE ( surf_usm_v(l)%zw(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)              )
1230           ALLOCATE ( surf_usm_v(l)%ddz_window(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)    )
1231           ALLOCATE ( surf_usm_v(l)%dz_window_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)  )
1232           ALLOCATE ( surf_usm_v(l)%ddz_window_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1233           ALLOCATE ( surf_usm_v(l)%zw_window(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)       )
1234           ALLOCATE ( surf_usm_v(l)%ddz_green(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)     )
1235           ALLOCATE ( surf_usm_v(l)%dz_green_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)   )
1236           ALLOCATE ( surf_usm_v(l)%ddz_green_stag(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)  )
1237           ALLOCATE ( surf_usm_v(l)%zw_green(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns)        )
1238        ENDDO
1239
1240!
1241!--     allocate wall and roof temperature arrays, for horizontal walls
1242!
1243!--     Allocate if required. Note, in case of restarts, some of these arrays
1244!--     might be already allocated.
1245        IF ( .NOT. ALLOCATED( t_surf_wall_h_1 ) )                              &
1246           ALLOCATE ( t_surf_wall_h_1(1:surf_usm_h%ns) )
1247        IF ( .NOT. ALLOCATED( t_surf_wall_h_2 ) )                              &
1248           ALLOCATE ( t_surf_wall_h_2(1:surf_usm_h%ns) )
1249        IF ( .NOT. ALLOCATED( t_wall_h_1 ) )                                   &           
1250           ALLOCATE ( t_wall_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1251        IF ( .NOT. ALLOCATED( t_wall_h_2 ) )                                   &           
1252           ALLOCATE ( t_wall_h_2(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )         
1253        IF ( .NOT. ALLOCATED( t_surf_window_h_1 ) )                            &
1254           ALLOCATE ( t_surf_window_h_1(1:surf_usm_h%ns) )
1255        IF ( .NOT. ALLOCATED( t_surf_window_h_2 ) )                            &
1256           ALLOCATE ( t_surf_window_h_2(1:surf_usm_h%ns) )
1257        IF ( .NOT. ALLOCATED( t_window_h_1 ) )                                 &           
1258           ALLOCATE ( t_window_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1259        IF ( .NOT. ALLOCATED( t_window_h_2 ) )                                 &           
1260           ALLOCATE ( t_window_h_2(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )         
1261        IF ( .NOT. ALLOCATED( t_surf_green_h_1 ) )                             &
1262           ALLOCATE ( t_surf_green_h_1(1:surf_usm_h%ns) )
1263        IF ( .NOT. ALLOCATED( t_surf_green_h_2 ) )                             &
1264           ALLOCATE ( t_surf_green_h_2(1:surf_usm_h%ns) )
1265        IF ( .NOT. ALLOCATED( t_green_h_1 ) )                                  &           
1266           ALLOCATE ( t_green_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1267        IF ( .NOT. ALLOCATED( t_green_h_2 ) )                                  &           
1268           ALLOCATE ( t_green_h_2(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )         
1269        IF ( .NOT. ALLOCATED( swc_h_1 ) )                                      &           
1270           ALLOCATE ( swc_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1271        IF ( .NOT. ALLOCATED( swc_sat_h_1 ) )                                  &           
1272           ALLOCATE ( swc_sat_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1273        IF ( .NOT. ALLOCATED( swc_res_h_1 ) )                                  &           
1274           ALLOCATE ( swc_res_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1275        IF ( .NOT. ALLOCATED( swc_h_2 ) )                                      &           
1276           ALLOCATE ( swc_h_2(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
1277        IF ( .NOT. ALLOCATED( rootfr_h_1 ) )                                   &           
1278           ALLOCATE ( rootfr_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1279        IF ( .NOT. ALLOCATED( wilt_h_1 ) )                                     &           
1280           ALLOCATE ( wilt_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1281        IF ( .NOT. ALLOCATED( fc_h_1 ) )                                       &           
1282           ALLOCATE ( fc_h_1(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
1283
1284        IF ( .NOT. ALLOCATED( m_liq_usm_h_1%var_usm_1d ) )                     &
1285           ALLOCATE ( m_liq_usm_h_1%var_usm_1d(1:surf_usm_h%ns) )
1286        IF ( .NOT. ALLOCATED( m_liq_usm_h_2%var_usm_1d ) )                     &
1287           ALLOCATE ( m_liq_usm_h_2%var_usm_1d(1:surf_usm_h%ns) )
1288           
1289!           
1290!--     initial assignment of the pointers
1291        t_wall_h    => t_wall_h_1;   t_wall_h_p   => t_wall_h_2
1292        t_window_h  => t_window_h_1; t_window_h_p => t_window_h_2
1293        t_green_h   => t_green_h_1;  t_green_h_p  => t_green_h_2
1294        t_surf_wall_h   => t_surf_wall_h_1;   t_surf_wall_h_p   => t_surf_wall_h_2           
1295        t_surf_window_h => t_surf_window_h_1; t_surf_window_h_p => t_surf_window_h_2 
1296        t_surf_green_h  => t_surf_green_h_1;  t_surf_green_h_p  => t_surf_green_h_2           
1297        m_liq_usm_h     => m_liq_usm_h_1;     m_liq_usm_h_p     => m_liq_usm_h_2
1298        swc_h     => swc_h_1; swc_h_p => swc_h_2
1299        swc_sat_h => swc_sat_h_1
1300        swc_res_h => swc_res_h_1
1301        rootfr_h  => rootfr_h_1
1302        wilt_h    => wilt_h_1
1303        fc_h      => fc_h_1
1304
1305!
1306!--     allocate wall and roof temperature arrays, for vertical walls if required
1307!
1308!--     Allocate if required. Note, in case of restarts, some of these arrays
1309!--     might be already allocated.
1310        DO  l = 0, 3
1311           IF ( .NOT. ALLOCATED( t_surf_wall_v_1(l)%t ) )                      &
1312              ALLOCATE ( t_surf_wall_v_1(l)%t(1:surf_usm_v(l)%ns) )
1313           IF ( .NOT. ALLOCATED( t_surf_wall_v_2(l)%t ) )                      &
1314              ALLOCATE ( t_surf_wall_v_2(l)%t(1:surf_usm_v(l)%ns) )
1315           IF ( .NOT. ALLOCATED( t_wall_v_1(l)%t ) )                           &           
1316              ALLOCATE ( t_wall_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1317           IF ( .NOT. ALLOCATED( t_wall_v_2(l)%t ) )                           &           
1318              ALLOCATE ( t_wall_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1319           IF ( .NOT. ALLOCATED( t_surf_window_v_1(l)%t ) )                    &
1320              ALLOCATE ( t_surf_window_v_1(l)%t(1:surf_usm_v(l)%ns) )
1321           IF ( .NOT. ALLOCATED( t_surf_window_v_2(l)%t ) )                    &
1322              ALLOCATE ( t_surf_window_v_2(l)%t(1:surf_usm_v(l)%ns) )
1323           IF ( .NOT. ALLOCATED( t_window_v_1(l)%t ) )                         &           
1324              ALLOCATE ( t_window_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1325           IF ( .NOT. ALLOCATED( t_window_v_2(l)%t ) )                         &           
1326              ALLOCATE ( t_window_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1327           IF ( .NOT. ALLOCATED( t_surf_green_v_1(l)%t ) )                     &
1328              ALLOCATE ( t_surf_green_v_1(l)%t(1:surf_usm_v(l)%ns) )
1329           IF ( .NOT. ALLOCATED( t_surf_green_v_2(l)%t ) )                     &
1330              ALLOCATE ( t_surf_green_v_2(l)%t(1:surf_usm_v(l)%ns) )
1331           IF ( .NOT. ALLOCATED( t_green_v_1(l)%t ) )                          &           
1332              ALLOCATE ( t_green_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1333           IF ( .NOT. ALLOCATED( t_green_v_2(l)%t ) )                          &           
1334              ALLOCATE ( t_green_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1335           IF ( .NOT. ALLOCATED( m_liq_usm_v_1(l)%var_usm_1d ) )               &
1336              ALLOCATE ( m_liq_usm_v_1(l)%var_usm_1d(1:surf_usm_v(l)%ns) )
1337           IF ( .NOT. ALLOCATED( m_liq_usm_v_2(l)%var_usm_1d ) )               &
1338              ALLOCATE ( m_liq_usm_v_2(l)%var_usm_1d(1:surf_usm_v(l)%ns) )
1339           IF ( .NOT. ALLOCATED( swc_v_1(l)%t ) )                              &           
1340              ALLOCATE ( swc_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1341           IF ( .NOT. ALLOCATED( swc_v_2(l)%t ) )                              &           
1342              ALLOCATE ( swc_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
1343        ENDDO
1344!
1345!--     initial assignment of the pointers
1346        t_wall_v        => t_wall_v_1;        t_wall_v_p        => t_wall_v_2
1347        t_surf_wall_v   => t_surf_wall_v_1;   t_surf_wall_v_p   => t_surf_wall_v_2
1348        t_window_v      => t_window_v_1;      t_window_v_p      => t_window_v_2
1349        t_green_v       => t_green_v_1;       t_green_v_p       => t_green_v_2
1350        t_surf_window_v => t_surf_window_v_1; t_surf_window_v_p => t_surf_window_v_2
1351        t_surf_green_v  => t_surf_green_v_1;  t_surf_green_v_p  => t_surf_green_v_2
1352        m_liq_usm_v     => m_liq_usm_v_1;     m_liq_usm_v_p     => m_liq_usm_v_2
1353        swc_v           => swc_v_1;           swc_v_p           => swc_v_2
1354
1355!
1356!--     Allocate intermediate timestep arrays. For horizontal surfaces.
1357        ALLOCATE ( surf_usm_h%tt_surface_wall_m(1:surf_usm_h%ns)               )
1358        ALLOCATE ( surf_usm_h%tt_wall_m(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)   )
1359        ALLOCATE ( surf_usm_h%tt_surface_window_m(1:surf_usm_h%ns)             )
1360        ALLOCATE ( surf_usm_h%tt_window_m(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
1361        ALLOCATE ( surf_usm_h%tt_green_m(nzb_wall:nzt_wall+1,1:surf_usm_h%ns)  )
1362        ALLOCATE ( surf_usm_h%tt_surface_green_m(1:surf_usm_h%ns)              )
1363
1364!
1365!--    Allocate intermediate timestep arrays
1366!--    Horizontal surfaces
1367       ALLOCATE ( tm_liq_usm_h_m%var_usm_1d(1:surf_usm_h%ns)                   )
1368!
1369!--    Horizontal surfaces
1370       DO  l = 0, 3
1371          ALLOCATE ( tm_liq_usm_v_m(l)%var_usm_1d(1:surf_usm_v(l)%ns)          )
1372       ENDDO 
1373       
1374!
1375!--     Set inital values for prognostic quantities
1376        IF ( ALLOCATED( surf_usm_h%tt_surface_wall_m )   )  surf_usm_h%tt_surface_wall_m   = 0.0_wp
1377        IF ( ALLOCATED( surf_usm_h%tt_wall_m )           )  surf_usm_h%tt_wall_m           = 0.0_wp
1378        IF ( ALLOCATED( surf_usm_h%tt_surface_window_m ) )  surf_usm_h%tt_surface_window_m = 0.0_wp
1379        IF ( ALLOCATED( surf_usm_h%tt_window_m    )      )  surf_usm_h%tt_window_m         = 0.0_wp
1380        IF ( ALLOCATED( surf_usm_h%tt_green_m    )       )  surf_usm_h%tt_green_m          = 0.0_wp
1381        IF ( ALLOCATED( surf_usm_h%tt_surface_green_m )  )  surf_usm_h%tt_surface_green_m  = 0.0_wp
1382!
1383!--     Now, for vertical surfaces
1384        DO  l = 0, 3
1385           ALLOCATE ( surf_usm_v(l)%tt_surface_wall_m(1:surf_usm_v(l)%ns)               )
1386           ALLOCATE ( surf_usm_v(l)%tt_wall_m(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)   )
1387           IF ( ALLOCATED( surf_usm_v(l)%tt_surface_wall_m ) )  surf_usm_v(l)%tt_surface_wall_m = 0.0_wp
1388           IF ( ALLOCATED( surf_usm_v(l)%tt_wall_m    ) )  surf_usm_v(l)%tt_wall_m    = 0.0_wp
1389           ALLOCATE ( surf_usm_v(l)%tt_surface_window_m(1:surf_usm_v(l)%ns)             )
1390           ALLOCATE ( surf_usm_v(l)%tt_window_m(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
1391           IF ( ALLOCATED( surf_usm_v(l)%tt_surface_window_m ) )  surf_usm_v(l)%tt_surface_window_m = 0.0_wp
1392           IF ( ALLOCATED( surf_usm_v(l)%tt_window_m  ) )  surf_usm_v(l)%tt_window_m    = 0.0_wp
1393           ALLOCATE ( surf_usm_v(l)%tt_surface_green_m(1:surf_usm_v(l)%ns)              )
1394           IF ( ALLOCATED( surf_usm_v(l)%tt_surface_green_m ) )  surf_usm_v(l)%tt_surface_green_m = 0.0_wp
1395           ALLOCATE ( surf_usm_v(l)%tt_green_m(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns)  )
1396           IF ( ALLOCATED( surf_usm_v(l)%tt_green_m   ) )  surf_usm_v(l)%tt_green_m    = 0.0_wp
1397        ENDDO
1398!
1399!--     allocate wall heat flux output array and set initial values. For horizontal surfaces
1400!        ALLOCATE ( surf_usm_h%wshf(1:surf_usm_h%ns)    )  !can be removed
1401        ALLOCATE ( surf_usm_h%wshf_eb(1:surf_usm_h%ns) )
1402        ALLOCATE ( surf_usm_h%wghf_eb(1:surf_usm_h%ns) )
1403        ALLOCATE ( surf_usm_h%wghf_eb_window(1:surf_usm_h%ns) )
1404        ALLOCATE ( surf_usm_h%wghf_eb_green(1:surf_usm_h%ns) )
1405        ALLOCATE ( surf_usm_h%iwghf_eb(1:surf_usm_h%ns) )
1406        ALLOCATE ( surf_usm_h%iwghf_eb_window(1:surf_usm_h%ns) )
1407        IF ( ALLOCATED( surf_usm_h%wshf    ) )  surf_usm_h%wshf    = 0.0_wp
1408        IF ( ALLOCATED( surf_usm_h%wshf_eb ) )  surf_usm_h%wshf_eb = 0.0_wp
1409        IF ( ALLOCATED( surf_usm_h%wghf_eb ) )  surf_usm_h%wghf_eb = 0.0_wp
1410        IF ( ALLOCATED( surf_usm_h%wghf_eb_window ) )  surf_usm_h%wghf_eb_window = 0.0_wp
1411        IF ( ALLOCATED( surf_usm_h%wghf_eb_green ) )  surf_usm_h%wghf_eb_green = 0.0_wp
1412        IF ( ALLOCATED( surf_usm_h%iwghf_eb ) )  surf_usm_h%iwghf_eb = 0.0_wp
1413        IF ( ALLOCATED( surf_usm_h%iwghf_eb_window ) )  surf_usm_h%iwghf_eb_window = 0.0_wp
1414!
1415!--     Now, for vertical surfaces
1416        DO  l = 0, 3
1417!           ALLOCATE ( surf_usm_v(l)%wshf(1:surf_usm_v(l)%ns)    )    ! can be removed
1418           ALLOCATE ( surf_usm_v(l)%wshf_eb(1:surf_usm_v(l)%ns) )
1419           ALLOCATE ( surf_usm_v(l)%wghf_eb(1:surf_usm_v(l)%ns) )
1420           ALLOCATE ( surf_usm_v(l)%wghf_eb_window(1:surf_usm_v(l)%ns) )
1421           ALLOCATE ( surf_usm_v(l)%wghf_eb_green(1:surf_usm_v(l)%ns) )
1422           ALLOCATE ( surf_usm_v(l)%iwghf_eb(1:surf_usm_v(l)%ns) )
1423           ALLOCATE ( surf_usm_v(l)%iwghf_eb_window(1:surf_usm_v(l)%ns) )
1424           IF ( ALLOCATED( surf_usm_v(l)%wshf    ) )  surf_usm_v(l)%wshf    = 0.0_wp
1425           IF ( ALLOCATED( surf_usm_v(l)%wshf_eb ) )  surf_usm_v(l)%wshf_eb = 0.0_wp
1426           IF ( ALLOCATED( surf_usm_v(l)%wghf_eb ) )  surf_usm_v(l)%wghf_eb = 0.0_wp
1427           IF ( ALLOCATED( surf_usm_v(l)%wghf_eb_window ) )  surf_usm_v(l)%wghf_eb_window = 0.0_wp
1428           IF ( ALLOCATED( surf_usm_v(l)%wghf_eb_green ) )  surf_usm_v(l)%wghf_eb_green = 0.0_wp
1429           IF ( ALLOCATED( surf_usm_v(l)%iwghf_eb ) )  surf_usm_v(l)%iwghf_eb = 0.0_wp
1430           IF ( ALLOCATED( surf_usm_v(l)%iwghf_eb_window ) )  surf_usm_v(l)%iwghf_eb_window = 0.0_wp
1431        ENDDO
1432
1433        IF ( debug_output )  CALL debug_message( 'usm_init_arrays', 'end' )
1434       
1435    END SUBROUTINE usm_init_arrays
1436
1437
1438!------------------------------------------------------------------------------!
1439! Description:
1440! ------------
1441!> Sum up and time-average urban surface output quantities as well as allocate
1442!> the array necessary for storing the average.
1443!------------------------------------------------------------------------------!
1444    SUBROUTINE usm_3d_data_averaging( mode, variable )
1445
1446        IMPLICIT NONE
1447
1448        CHARACTER(LEN=*), INTENT(IN) ::  mode
1449        CHARACTER(LEN=*), INTENT(IN) :: variable
1450 
1451        INTEGER(iwp)                                       :: i, j, k, l, m, ids, idsint, iwl, istat  !< runnin indices
1452        CHARACTER(LEN=varnamelength)                       :: var                                     !< trimmed variable
1453        INTEGER(iwp), PARAMETER                            :: nd = 5                                  !< number of directions
1454        CHARACTER(LEN=6), DIMENSION(0:nd-1), PARAMETER     :: dirname = (/ '_roof ', '_south', '_north', '_west ', '_east ' /)
1455        INTEGER(iwp), DIMENSION(0:nd-1), PARAMETER         :: dirint = (/ iup_u, isouth_u, inorth_u, iwest_u, ieast_u /)
1456
1457        IF ( variable(1:4) == 'usm_' )  THEN  ! is such a check really rquired?
1458
1459!
1460!--     find the real name of the variable
1461        ids = -1
1462        l = -1
1463        var = TRIM(variable)
1464        DO i = 0, nd-1
1465            k = len(TRIM(var))
1466            j = len(TRIM(dirname(i)))
1467            IF ( TRIM(var(k-j+1:k)) == TRIM(dirname(i)) )  THEN
1468                ids = i
1469                idsint = dirint(ids)
1470                var = var(:k-j)
1471                EXIT
1472            ENDIF
1473        ENDDO
1474        l = idsint - 2  ! horisontal direction index - terible hack !
1475        IF ( l < 0 .OR. l > 3 ) THEN
1476           l = -1
1477        END IF
1478        IF ( ids == -1 )  THEN
1479            var = TRIM(variable)
1480        ENDIF
1481        IF ( var(1:11) == 'usm_t_wall_'  .AND.  len(TRIM(var)) >= 12 )  THEN
1482!
1483!--          wall layers
1484            READ(var(12:12), '(I1)', iostat=istat ) iwl
1485            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
1486                var = var(1:10)
1487            ELSE
1488!
1489!--             wrong wall layer index
1490                RETURN
1491            ENDIF
1492        ENDIF
1493        IF ( var(1:13) == 'usm_t_window_'  .AND.  len(TRIM(var)) >= 14 )  THEN
1494!
1495!--          wall layers
1496            READ(var(14:14), '(I1)', iostat=istat ) iwl
1497            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
1498                var = var(1:12)
1499            ELSE
1500!
1501!--             wrong window layer index
1502                RETURN
1503            ENDIF
1504        ENDIF
1505        IF ( var(1:12) == 'usm_t_green_'  .AND.  len(TRIM(var)) >= 13 )  THEN
1506!
1507!--          wall layers
1508            READ(var(13:13), '(I1)', iostat=istat ) iwl
1509            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
1510                var = var(1:11)
1511            ELSE
1512!
1513!--             wrong green layer index
1514                RETURN
1515            ENDIF
1516        ENDIF
1517        IF ( var(1:8) == 'usm_swc_'  .AND.  len(TRIM(var)) >= 9 )  THEN
1518!
1519!--          swc layers
1520            READ(var(9:9), '(I1)', iostat=istat ) iwl
1521            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
1522                var = var(1:7)
1523            ELSE
1524!
1525!--             wrong swc layer index
1526                RETURN
1527            ENDIF
1528        ENDIF
1529
1530        IF ( mode == 'allocate' )  THEN
1531           
1532           SELECT CASE ( TRIM( var ) )
1533
1534                CASE ( 'usm_wshf' )
1535!
1536!--                 array of sensible heat flux from surfaces
1537!--                 land surfaces
1538                    IF ( l == -1 ) THEN
1539                       IF ( .NOT.  ALLOCATED(surf_usm_h%wshf_eb_av) )  THEN
1540                          ALLOCATE ( surf_usm_h%wshf_eb_av(1:surf_usm_h%ns) )
1541                          surf_usm_h%wshf_eb_av = 0.0_wp
1542                       ENDIF
1543                    ELSE
1544                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%wshf_eb_av) )  THEN
1545                           ALLOCATE ( surf_usm_v(l)%wshf_eb_av(1:surf_usm_v(l)%ns) )
1546                           surf_usm_v(l)%wshf_eb_av = 0.0_wp
1547                       ENDIF
1548                    ENDIF
1549                   
1550                CASE ( 'usm_qsws' )
1551!
1552!--                 array of latent heat flux from surfaces
1553!--                 land surfaces
1554                    IF ( l == -1 .AND. .NOT.  ALLOCATED(surf_usm_h%qsws_av) )  THEN
1555                        ALLOCATE ( surf_usm_h%qsws_av(1:surf_usm_h%ns) )
1556                        surf_usm_h%qsws_av = 0.0_wp
1557                    ELSE
1558                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%qsws_av) )  THEN
1559                           ALLOCATE ( surf_usm_v(l)%qsws_av(1:surf_usm_v(l)%ns) )
1560                           surf_usm_v(l)%qsws_av = 0.0_wp
1561                       ENDIF
1562                    ENDIF
1563                   
1564                CASE ( 'usm_qsws_veg' )
1565!
1566!--                 array of latent heat flux from vegetation surfaces
1567!--                 land surfaces
1568                    IF ( l == -1 .AND. .NOT.  ALLOCATED(surf_usm_h%qsws_veg_av) )  THEN
1569                        ALLOCATE ( surf_usm_h%qsws_veg_av(1:surf_usm_h%ns) )
1570                        surf_usm_h%qsws_veg_av = 0.0_wp
1571                    ELSE
1572                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%qsws_veg_av) )  THEN
1573                           ALLOCATE ( surf_usm_v(l)%qsws_veg_av(1:surf_usm_v(l)%ns) )
1574                           surf_usm_v(l)%qsws_veg_av = 0.0_wp
1575                       ENDIF
1576                    ENDIF
1577                   
1578                CASE ( 'usm_qsws_liq' )
1579!
1580!--                 array of latent heat flux from surfaces with liquid
1581!--                 land surfaces
1582                    IF ( l == -1 .AND. .NOT.  ALLOCATED(surf_usm_h%qsws_liq_av) )  THEN
1583                        ALLOCATE ( surf_usm_h%qsws_liq_av(1:surf_usm_h%ns) )
1584                        surf_usm_h%qsws_liq_av = 0.0_wp
1585                    ELSE
1586                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%qsws_liq_av) )  THEN
1587                           ALLOCATE ( surf_usm_v(l)%qsws_liq_av(1:surf_usm_v(l)%ns) )
1588                           surf_usm_v(l)%qsws_liq_av = 0.0_wp
1589                       ENDIF
1590                    ENDIF
1591!
1592!--             Please note, the following output quantities belongs to the
1593!--             individual tile fractions - ground heat flux at wall-, window-,
1594!--             and green fraction. Aggregated ground-heat flux is treated
1595!--             accordingly in average_3d_data, sum_up_3d_data, etc..
1596                CASE ( 'usm_wghf' )
1597!
1598!--                 array of heat flux from ground (wall, roof, land)
1599                    IF ( l == -1 ) THEN
1600                       IF ( .NOT.  ALLOCATED(surf_usm_h%wghf_eb_av) )  THEN
1601                           ALLOCATE ( surf_usm_h%wghf_eb_av(1:surf_usm_h%ns) )
1602                           surf_usm_h%wghf_eb_av = 0.0_wp
1603                       ENDIF
1604                    ELSE
1605                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%wghf_eb_av) )  THEN
1606                           ALLOCATE ( surf_usm_v(l)%wghf_eb_av(1:surf_usm_v(l)%ns) )
1607                           surf_usm_v(l)%wghf_eb_av = 0.0_wp
1608                       ENDIF
1609                    ENDIF
1610
1611                CASE ( 'usm_wghf_window' )
1612!
1613!--                 array of heat flux from window ground (wall, roof, land)
1614                    IF ( l == -1 ) THEN
1615                       IF ( .NOT.  ALLOCATED(surf_usm_h%wghf_eb_window_av) )  THEN
1616                           ALLOCATE ( surf_usm_h%wghf_eb_window_av(1:surf_usm_h%ns) )
1617                           surf_usm_h%wghf_eb_window_av = 0.0_wp
1618                       ENDIF
1619                    ELSE
1620                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%wghf_eb_window_av) )  THEN
1621                           ALLOCATE ( surf_usm_v(l)%wghf_eb_window_av(1:surf_usm_v(l)%ns) )
1622                           surf_usm_v(l)%wghf_eb_window_av = 0.0_wp
1623                       ENDIF
1624                    ENDIF
1625
1626                CASE ( 'usm_wghf_green' )
1627!
1628!--                 array of heat flux from green ground (wall, roof, land)
1629                    IF ( l == -1 ) THEN
1630                       IF ( .NOT.  ALLOCATED(surf_usm_h%wghf_eb_green_av) )  THEN
1631                           ALLOCATE ( surf_usm_h%wghf_eb_green_av(1:surf_usm_h%ns) )
1632                           surf_usm_h%wghf_eb_green_av = 0.0_wp
1633                       ENDIF
1634                    ELSE
1635                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%wghf_eb_green_av) )  THEN
1636                           ALLOCATE ( surf_usm_v(l)%wghf_eb_green_av(1:surf_usm_v(l)%ns) )
1637                           surf_usm_v(l)%wghf_eb_green_av = 0.0_wp
1638                       ENDIF
1639                    ENDIF
1640
1641                CASE ( 'usm_iwghf' )
1642!
1643!--                 array of heat flux from indoor ground (wall, roof, land)
1644                    IF ( l == -1 ) THEN
1645                       IF ( .NOT.  ALLOCATED(surf_usm_h%iwghf_eb_av) )  THEN
1646                           ALLOCATE ( surf_usm_h%iwghf_eb_av(1:surf_usm_h%ns) )
1647                           surf_usm_h%iwghf_eb_av = 0.0_wp
1648                       ENDIF
1649                    ELSE
1650                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%iwghf_eb_av) )  THEN
1651                           ALLOCATE ( surf_usm_v(l)%iwghf_eb_av(1:surf_usm_v(l)%ns) )
1652                           surf_usm_v(l)%iwghf_eb_av = 0.0_wp
1653                       ENDIF
1654                    ENDIF
1655
1656                CASE ( 'usm_iwghf_window' )
1657!
1658!--                 array of heat flux from indoor window ground (wall, roof, land)
1659                    IF ( l == -1 ) THEN
1660                       IF ( .NOT.  ALLOCATED(surf_usm_h%iwghf_eb_window_av) )  THEN
1661                           ALLOCATE ( surf_usm_h%iwghf_eb_window_av(1:surf_usm_h%ns) )
1662                           surf_usm_h%iwghf_eb_window_av = 0.0_wp
1663                       ENDIF
1664                    ELSE
1665                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%iwghf_eb_window_av) )  THEN
1666                           ALLOCATE ( surf_usm_v(l)%iwghf_eb_window_av(1:surf_usm_v(l)%ns) )
1667                           surf_usm_v(l)%iwghf_eb_window_av = 0.0_wp
1668                       ENDIF
1669                    ENDIF
1670
1671                CASE ( 'usm_t_surf_wall' )
1672!
1673!--                 surface temperature for surfaces
1674                    IF ( l == -1 ) THEN
1675                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_surf_wall_av) )  THEN
1676                           ALLOCATE ( surf_usm_h%t_surf_wall_av(1:surf_usm_h%ns) )
1677                           surf_usm_h%t_surf_wall_av = 0.0_wp
1678                       ENDIF
1679                    ELSE
1680                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_surf_wall_av) )  THEN
1681                           ALLOCATE ( surf_usm_v(l)%t_surf_wall_av(1:surf_usm_v(l)%ns) )
1682                           surf_usm_v(l)%t_surf_wall_av = 0.0_wp
1683                       ENDIF
1684                    ENDIF
1685
1686                CASE ( 'usm_t_surf_window' )
1687!
1688!--                 surface temperature for window surfaces
1689                    IF ( l == -1 ) THEN
1690                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_surf_window_av) )  THEN
1691                           ALLOCATE ( surf_usm_h%t_surf_window_av(1:surf_usm_h%ns) )
1692                           surf_usm_h%t_surf_window_av = 0.0_wp
1693                       ENDIF
1694                    ELSE
1695                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_surf_window_av) )  THEN
1696                           ALLOCATE ( surf_usm_v(l)%t_surf_window_av(1:surf_usm_v(l)%ns) )
1697                           surf_usm_v(l)%t_surf_window_av = 0.0_wp
1698                       ENDIF
1699                    ENDIF
1700                   
1701                CASE ( 'usm_t_surf_green' )
1702!
1703!--                 surface temperature for green surfaces
1704                    IF ( l == -1 ) THEN
1705                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_surf_green_av) )  THEN
1706                           ALLOCATE ( surf_usm_h%t_surf_green_av(1:surf_usm_h%ns) )
1707                           surf_usm_h%t_surf_green_av = 0.0_wp
1708                       ENDIF
1709                    ELSE
1710                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_surf_green_av) )  THEN
1711                           ALLOCATE ( surf_usm_v(l)%t_surf_green_av(1:surf_usm_v(l)%ns) )
1712                           surf_usm_v(l)%t_surf_green_av = 0.0_wp
1713                       ENDIF
1714                    ENDIF
1715               
1716                CASE ( 'usm_theta_10cm' )
1717!
1718!--                 near surface (10cm) temperature for whole surfaces
1719                    IF ( l == -1 ) THEN
1720                       IF ( .NOT.  ALLOCATED(surf_usm_h%pt_10cm_av) )  THEN
1721                           ALLOCATE ( surf_usm_h%pt_10cm_av(1:surf_usm_h%ns) )
1722                           surf_usm_h%pt_10cm_av = 0.0_wp
1723                       ENDIF
1724                    ELSE
1725                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%pt_10cm_av) )  THEN
1726                           ALLOCATE ( surf_usm_v(l)%pt_10cm_av(1:surf_usm_v(l)%ns) )
1727                           surf_usm_v(l)%pt_10cm_av = 0.0_wp
1728                       ENDIF
1729                    ENDIF
1730                 
1731                CASE ( 'usm_t_wall' )
1732!
1733!--                 wall temperature for iwl layer of walls and land
1734                    IF ( l == -1 ) THEN
1735                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_wall_av) )  THEN
1736                           ALLOCATE ( surf_usm_h%t_wall_av(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1737                           surf_usm_h%t_wall_av = 0.0_wp
1738                       ENDIF
1739                    ELSE
1740                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_wall_av) )  THEN
1741                           ALLOCATE ( surf_usm_v(l)%t_wall_av(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1742                           surf_usm_v(l)%t_wall_av = 0.0_wp
1743                       ENDIF
1744                    ENDIF
1745
1746                CASE ( 'usm_t_window' )
1747!
1748!--                 window temperature for iwl layer of walls and land
1749                    IF ( l == -1 ) THEN
1750                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_window_av) )  THEN
1751                           ALLOCATE ( surf_usm_h%t_window_av(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1752                           surf_usm_h%t_window_av = 0.0_wp
1753                       ENDIF
1754                    ELSE
1755                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_window_av) )  THEN
1756                           ALLOCATE ( surf_usm_v(l)%t_window_av(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1757                           surf_usm_v(l)%t_window_av = 0.0_wp
1758                       ENDIF
1759                    ENDIF
1760
1761                CASE ( 'usm_t_green' )
1762!
1763!--                 green temperature for iwl layer of walls and land
1764                    IF ( l == -1 ) THEN
1765                       IF ( .NOT.  ALLOCATED(surf_usm_h%t_green_av) )  THEN
1766                           ALLOCATE ( surf_usm_h%t_green_av(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1767                           surf_usm_h%t_green_av = 0.0_wp
1768                       ENDIF
1769                    ELSE
1770                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_green_av) )  THEN
1771                           ALLOCATE ( surf_usm_v(l)%t_green_av(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1772                           surf_usm_v(l)%t_green_av = 0.0_wp
1773                       ENDIF
1774                    ENDIF
1775                CASE ( 'usm_swc' )
1776!
1777!--                 soil water content for iwl layer of walls and land
1778                    IF ( l == -1 .AND. .NOT.  ALLOCATED(surf_usm_h%swc_av) )  THEN
1779                        ALLOCATE ( surf_usm_h%swc_av(nzb_wall:nzt_wall,1:surf_usm_h%ns) )
1780                        surf_usm_h%swc_av = 0.0_wp
1781                    ELSE
1782                       IF ( .NOT.  ALLOCATED(surf_usm_v(l)%swc_av) )  THEN
1783                           ALLOCATE ( surf_usm_v(l)%swc_av(nzb_wall:nzt_wall,1:surf_usm_v(l)%ns) )
1784                           surf_usm_v(l)%swc_av = 0.0_wp
1785                       ENDIF
1786                    ENDIF
1787
1788               CASE DEFAULT
1789                   CONTINUE
1790
1791           END SELECT
1792
1793        ELSEIF ( mode == 'sum' )  THEN
1794           
1795           SELECT CASE ( TRIM( var ) )
1796
1797                CASE ( 'usm_wshf' )
1798!
1799!--                 array of sensible heat flux from surfaces (land, roof, wall)
1800                    IF ( l == -1 ) THEN
1801                       DO  m = 1, surf_usm_h%ns
1802                          surf_usm_h%wshf_eb_av(m) =                              &
1803                                             surf_usm_h%wshf_eb_av(m) +           &
1804                                             surf_usm_h%wshf_eb(m)
1805                       ENDDO
1806                    ELSE
1807                       DO  m = 1, surf_usm_v(l)%ns
1808                          surf_usm_v(l)%wshf_eb_av(m) =                        &
1809                                          surf_usm_v(l)%wshf_eb_av(m) +        &
1810                                          surf_usm_v(l)%wshf_eb(m)
1811                       ENDDO
1812                    ENDIF
1813                   
1814                CASE ( 'usm_qsws' )
1815!
1816!--                 array of latent heat flux from surfaces (land, roof, wall)
1817                    IF ( l == -1 ) THEN
1818                    DO  m = 1, surf_usm_h%ns
1819                       surf_usm_h%qsws_av(m) =                              &
1820                                          surf_usm_h%qsws_av(m) +           &
1821                                          surf_usm_h%qsws(m) * l_v
1822                    ENDDO
1823                    ELSE
1824                       DO  m = 1, surf_usm_v(l)%ns
1825                          surf_usm_v(l)%qsws_av(m) =                        &
1826                                          surf_usm_v(l)%qsws_av(m) +        &
1827                                          surf_usm_v(l)%qsws(m) * l_v
1828                       ENDDO
1829                    ENDIF
1830                   
1831                CASE ( 'usm_qsws_veg' )
1832!
1833!--                 array of latent heat flux from vegetation surfaces (land, roof, wall)
1834                    IF ( l == -1 ) THEN
1835                    DO  m = 1, surf_usm_h%ns
1836                       surf_usm_h%qsws_veg_av(m) =                              &
1837                                          surf_usm_h%qsws_veg_av(m) +           &
1838                                          surf_usm_h%qsws_veg(m)
1839                    ENDDO
1840                    ELSE
1841                       DO  m = 1, surf_usm_v(l)%ns
1842                          surf_usm_v(l)%qsws_veg_av(m) =                        &
1843                                          surf_usm_v(l)%qsws_veg_av(m) +        &
1844                                          surf_usm_v(l)%qsws_veg(m)
1845                       ENDDO
1846                    ENDIF
1847                   
1848                CASE ( 'usm_qsws_liq' )
1849!
1850!--                 array of latent heat flux from surfaces with liquid (land, roof, wall)
1851                    IF ( l == -1 ) THEN
1852                    DO  m = 1, surf_usm_h%ns
1853                       surf_usm_h%qsws_liq_av(m) =                              &
1854                                          surf_usm_h%qsws_liq_av(m) +           &
1855                                          surf_usm_h%qsws_liq(m)
1856                    ENDDO
1857                    ELSE
1858                       DO  m = 1, surf_usm_v(l)%ns
1859                          surf_usm_v(l)%qsws_liq_av(m) =                        &
1860                                          surf_usm_v(l)%qsws_liq_av(m) +        &
1861                                          surf_usm_v(l)%qsws_liq(m)
1862                       ENDDO
1863                    ENDIF
1864                   
1865                CASE ( 'usm_wghf' )
1866!
1867!--                 array of heat flux from ground (wall, roof, land)
1868                    IF ( l == -1 ) THEN
1869                       DO  m = 1, surf_usm_h%ns
1870                          surf_usm_h%wghf_eb_av(m) =                              &
1871                                             surf_usm_h%wghf_eb_av(m) +           &
1872                                             surf_usm_h%wghf_eb(m)
1873                       ENDDO
1874                    ELSE
1875                       DO  m = 1, surf_usm_v(l)%ns
1876                          surf_usm_v(l)%wghf_eb_av(m) =                        &
1877                                          surf_usm_v(l)%wghf_eb_av(m) +        &
1878                                          surf_usm_v(l)%wghf_eb(m)
1879                       ENDDO
1880                    ENDIF
1881                   
1882                CASE ( 'usm_wghf_window' )
1883!
1884!--                 array of heat flux from window ground (wall, roof, land)
1885                    IF ( l == -1 ) THEN
1886                       DO  m = 1, surf_usm_h%ns
1887                          surf_usm_h%wghf_eb_window_av(m) =                              &
1888                                             surf_usm_h%wghf_eb_window_av(m) +           &
1889                                             surf_usm_h%wghf_eb_window(m)
1890                       ENDDO
1891                    ELSE
1892                       DO  m = 1, surf_usm_v(l)%ns
1893                          surf_usm_v(l)%wghf_eb_window_av(m) =                        &
1894                                          surf_usm_v(l)%wghf_eb_window_av(m) +        &
1895                                          surf_usm_v(l)%wghf_eb_window(m)
1896                       ENDDO
1897                    ENDIF
1898
1899                CASE ( 'usm_wghf_green' )
1900!
1901!--                 array of heat flux from green ground (wall, roof, land)
1902                    IF ( l == -1 ) THEN
1903                       DO  m = 1, surf_usm_h%ns
1904                          surf_usm_h%wghf_eb_green_av(m) =                              &
1905                                             surf_usm_h%wghf_eb_green_av(m) +           &
1906                                             surf_usm_h%wghf_eb_green(m)
1907                       ENDDO
1908                    ELSE
1909                       DO  m = 1, surf_usm_v(l)%ns
1910                          surf_usm_v(l)%wghf_eb_green_av(m) =                        &
1911                                          surf_usm_v(l)%wghf_eb_green_av(m) +        &
1912                                          surf_usm_v(l)%wghf_eb_green(m)
1913                       ENDDO
1914                    ENDIF
1915                   
1916                CASE ( 'usm_iwghf' )
1917!
1918!--                 array of heat flux from indoor ground (wall, roof, land)
1919                    IF ( l == -1 ) THEN
1920                       DO  m = 1, surf_usm_h%ns
1921                          surf_usm_h%iwghf_eb_av(m) =                              &
1922                                             surf_usm_h%iwghf_eb_av(m) +           &
1923                                             surf_usm_h%iwghf_eb(m)
1924                       ENDDO
1925                    ELSE
1926                       DO  m = 1, surf_usm_v(l)%ns
1927                          surf_usm_v(l)%iwghf_eb_av(m) =                        &
1928                                          surf_usm_v(l)%iwghf_eb_av(m) +        &
1929                                          surf_usm_v(l)%iwghf_eb(m)
1930                       ENDDO
1931                    ENDIF
1932                   
1933                CASE ( 'usm_iwghf_window' )
1934!
1935!--                 array of heat flux from indoor window ground (wall, roof, land)
1936                    IF ( l == -1 ) THEN
1937                       DO  m = 1, surf_usm_h%ns
1938                          surf_usm_h%iwghf_eb_window_av(m) =                              &
1939                                             surf_usm_h%iwghf_eb_window_av(m) +           &
1940                                             surf_usm_h%iwghf_eb_window(m)
1941                       ENDDO
1942                    ELSE
1943                       DO  m = 1, surf_usm_v(l)%ns
1944                          surf_usm_v(l)%iwghf_eb_window_av(m) =                        &
1945                                          surf_usm_v(l)%iwghf_eb_window_av(m) +        &
1946                                          surf_usm_v(l)%iwghf_eb_window(m)
1947                       ENDDO
1948                    ENDIF
1949                   
1950                CASE ( 'usm_t_surf_wall' )
1951!
1952!--                 surface temperature for surfaces
1953                    IF ( l == -1 ) THEN
1954                       DO  m = 1, surf_usm_h%ns
1955                       surf_usm_h%t_surf_wall_av(m) =                               & 
1956                                          surf_usm_h%t_surf_wall_av(m) +            &
1957                                          t_surf_wall_h(m)
1958                       ENDDO
1959                    ELSE
1960                       DO  m = 1, surf_usm_v(l)%ns
1961                          surf_usm_v(l)%t_surf_wall_av(m) =                         &
1962                                          surf_usm_v(l)%t_surf_wall_av(m) +         &
1963                                          t_surf_wall_v(l)%t(m)
1964                       ENDDO
1965                    ENDIF
1966                   
1967                CASE ( 'usm_t_surf_window' )
1968!
1969!--                 surface temperature for window surfaces
1970                    IF ( l == -1 ) THEN
1971                       DO  m = 1, surf_usm_h%ns
1972                          surf_usm_h%t_surf_window_av(m) =                               &
1973                                             surf_usm_h%t_surf_window_av(m) +            &
1974                                             t_surf_window_h(m)
1975                       ENDDO
1976                    ELSE
1977                       DO  m = 1, surf_usm_v(l)%ns
1978                          surf_usm_v(l)%t_surf_window_av(m) =                         &
1979                                          surf_usm_v(l)%t_surf_window_av(m) +         &
1980                                          t_surf_window_v(l)%t(m)
1981                       ENDDO
1982                    ENDIF
1983                   
1984                CASE ( 'usm_t_surf_green' )
1985!
1986!--                 surface temperature for green surfaces
1987                    IF ( l == -1 ) THEN
1988                       DO  m = 1, surf_usm_h%ns
1989                          surf_usm_h%t_surf_green_av(m) =                               &
1990                                             surf_usm_h%t_surf_green_av(m) +            &
1991                                             t_surf_green_h(m)
1992                       ENDDO
1993                    ELSE
1994                       DO  m = 1, surf_usm_v(l)%ns
1995                          surf_usm_v(l)%t_surf_green_av(m) =                         &
1996                                          surf_usm_v(l)%t_surf_green_av(m) +         &
1997                                          t_surf_green_v(l)%t(m)
1998                       ENDDO
1999                    ENDIF
2000               
2001                CASE ( 'usm_theta_10cm' )
2002!
2003!--                 near surface temperature for whole surfaces
2004                    IF ( l == -1 ) THEN
2005                       DO  m = 1, surf_usm_h%ns
2006                          surf_usm_h%pt_10cm_av(m) =                               &
2007                                             surf_usm_h%pt_10cm_av(m) +            &
2008                                             surf_usm_h%pt_10cm(m)
2009                       ENDDO
2010                    ELSE
2011                       DO  m = 1, surf_usm_v(l)%ns
2012                          surf_usm_v(l)%pt_10cm_av(m) =                         &
2013                                          surf_usm_v(l)%pt_10cm_av(m) +         &
2014                                          surf_usm_v(l)%pt_10cm(m)
2015                       ENDDO
2016                    ENDIF
2017                   
2018                CASE ( 'usm_t_wall' )
2019!
2020!--                 wall temperature for  iwl layer of walls and land
2021                    IF ( l == -1 ) THEN
2022                       DO  m = 1, surf_usm_h%ns
2023                          surf_usm_h%t_wall_av(iwl,m) =                           &
2024                                             surf_usm_h%t_wall_av(iwl,m) +        &
2025                                             t_wall_h(iwl,m)
2026                       ENDDO
2027                    ELSE
2028                       DO  m = 1, surf_usm_v(l)%ns
2029                          surf_usm_v(l)%t_wall_av(iwl,m) =                     &
2030                                          surf_usm_v(l)%t_wall_av(iwl,m) +     &
2031                                          t_wall_v(l)%t(iwl,m)
2032                       ENDDO
2033                    ENDIF
2034                   
2035                CASE ( 'usm_t_window' )
2036!
2037!--                 window temperature for  iwl layer of walls and land
2038                    IF ( l == -1 ) THEN
2039                       DO  m = 1, surf_usm_h%ns
2040                          surf_usm_h%t_window_av(iwl,m) =                           &
2041                                             surf_usm_h%t_window_av(iwl,m) +        &
2042                                             t_window_h(iwl,m)
2043                       ENDDO
2044                    ELSE
2045                       DO  m = 1, surf_usm_v(l)%ns
2046                          surf_usm_v(l)%t_window_av(iwl,m) =                     &
2047                                          surf_usm_v(l)%t_window_av(iwl,m) +     &
2048                                          t_window_v(l)%t(iwl,m)
2049                       ENDDO
2050                    ENDIF
2051
2052                CASE ( 'usm_t_green' )
2053!
2054!--                 green temperature for  iwl layer of walls and land
2055                    IF ( l == -1 ) THEN
2056                       DO  m = 1, surf_usm_h%ns
2057                          surf_usm_h%t_green_av(iwl,m) =                           &
2058                                             surf_usm_h%t_green_av(iwl,m) +        &
2059                                             t_green_h(iwl,m)
2060                       ENDDO
2061                    ELSE
2062                       DO  m = 1, surf_usm_v(l)%ns
2063                          surf_usm_v(l)%t_green_av(iwl,m) =                     &
2064                                          surf_usm_v(l)%t_green_av(iwl,m) +     &
2065                                          t_green_v(l)%t(iwl,m)
2066                       ENDDO
2067                    ENDIF
2068
2069                CASE ( 'usm_swc' )
2070!
2071!--                 soil water content for  iwl layer of walls and land
2072                    IF ( l == -1 ) THEN
2073                    DO  m = 1, surf_usm_h%ns
2074                       surf_usm_h%swc_av(iwl,m) =                           &
2075                                          surf_usm_h%swc_av(iwl,m) +        &
2076                                          swc_h(iwl,m)
2077                    ENDDO
2078                    ELSE
2079                       DO  m = 1, surf_usm_v(l)%ns
2080                          surf_usm_v(l)%swc_av(iwl,m) =                     &
2081                                          surf_usm_v(l)%swc_av(iwl,m) +     &
2082                                          swc_v(l)%t(iwl,m)
2083                       ENDDO
2084                    ENDIF
2085
2086                CASE DEFAULT
2087                    CONTINUE
2088
2089           END SELECT
2090
2091        ELSEIF ( mode == 'average' )  THEN
2092           
2093           SELECT CASE ( TRIM( var ) )
2094
2095                CASE ( 'usm_wshf' )
2096!
2097!--                 array of sensible heat flux from surfaces (land, roof, wall)
2098                    IF ( l == -1 ) THEN
2099                       DO  m = 1, surf_usm_h%ns
2100                          surf_usm_h%wshf_eb_av(m) =                              &
2101                                             surf_usm_h%wshf_eb_av(m) /           &
2102                                             REAL( average_count_3d, kind=wp )
2103                       ENDDO
2104                    ELSE
2105                       DO  m = 1, surf_usm_v(l)%ns
2106                          surf_usm_v(l)%wshf_eb_av(m) =                        &
2107                                          surf_usm_v(l)%wshf_eb_av(m) /        &
2108                                          REAL( average_count_3d, kind=wp )
2109                       ENDDO
2110                    ENDIF
2111                   
2112                CASE ( 'usm_qsws' )
2113!
2114!--                 array of latent heat flux from surfaces (land, roof, wall)
2115                    IF ( l == -1 ) THEN
2116                    DO  m = 1, surf_usm_h%ns
2117                       surf_usm_h%qsws_av(m) =                              &
2118                                          surf_usm_h%qsws_av(m) /           &
2119                                          REAL( average_count_3d, kind=wp )
2120                    ENDDO
2121                    ELSE
2122                       DO  m = 1, surf_usm_v(l)%ns
2123                          surf_usm_v(l)%qsws_av(m) =                        &
2124                                          surf_usm_v(l)%qsws_av(m) /        &
2125                                          REAL( average_count_3d, kind=wp )
2126                       ENDDO
2127                    ENDIF
2128
2129                CASE ( 'usm_qsws_veg' )
2130!
2131!--                 array of latent heat flux from vegetation surfaces (land, roof, wall)
2132                    IF ( l == -1 ) THEN
2133                    DO  m = 1, surf_usm_h%ns
2134                       surf_usm_h%qsws_veg_av(m) =                              &
2135                                          surf_usm_h%qsws_veg_av(m) /           &
2136                                          REAL( average_count_3d, kind=wp )
2137                    ENDDO
2138                    ELSE
2139                       DO  m = 1, surf_usm_v(l)%ns
2140                          surf_usm_v(l)%qsws_veg_av(m) =                        &
2141                                          surf_usm_v(l)%qsws_veg_av(m) /        &
2142                                          REAL( average_count_3d, kind=wp )
2143                       ENDDO
2144                    ENDIF
2145                   
2146                CASE ( 'usm_qsws_liq' )
2147!
2148!--                 array of latent heat flux from surfaces with liquid (land, roof, wall)
2149                    IF ( l == -1 ) THEN
2150                    DO  m = 1, surf_usm_h%ns
2151                       surf_usm_h%qsws_liq_av(m) =                              &
2152                                          surf_usm_h%qsws_liq_av(m) /           &
2153                                          REAL( average_count_3d, kind=wp )
2154                    ENDDO
2155                    ELSE
2156                       DO  m = 1, surf_usm_v(l)%ns
2157                          surf_usm_v(l)%qsws_liq_av(m) =                        &
2158                                          surf_usm_v(l)%qsws_liq_av(m) /        &
2159                                          REAL( average_count_3d, kind=wp )
2160                       ENDDO
2161                    ENDIF
2162                   
2163                CASE ( 'usm_wghf' )
2164!
2165!--                 array of heat flux from ground (wall, roof, land)
2166                    IF ( l == -1 ) THEN
2167                       DO  m = 1, surf_usm_h%ns
2168                          surf_usm_h%wghf_eb_av(m) =                              &
2169                                             surf_usm_h%wghf_eb_av(m) /           &
2170                                             REAL( average_count_3d, kind=wp )
2171                       ENDDO
2172                    ELSE
2173                       DO  m = 1, surf_usm_v(l)%ns
2174                          surf_usm_v(l)%wghf_eb_av(m) =                        &
2175                                          surf_usm_v(l)%wghf_eb_av(m) /        &
2176                                          REAL( average_count_3d, kind=wp )
2177                       ENDDO
2178                    ENDIF
2179                   
2180                CASE ( 'usm_wghf_window' )
2181!
2182!--                 array of heat flux from window ground (wall, roof, land)
2183                    IF ( l == -1 ) THEN
2184                       DO  m = 1, surf_usm_h%ns
2185                          surf_usm_h%wghf_eb_window_av(m) =                              &
2186                                             surf_usm_h%wghf_eb_window_av(m) /           &
2187                                             REAL( average_count_3d, kind=wp )
2188                       ENDDO
2189                    ELSE
2190                       DO  m = 1, surf_usm_v(l)%ns
2191                          surf_usm_v(l)%wghf_eb_window_av(m) =                        &
2192                                          surf_usm_v(l)%wghf_eb_window_av(m) /        &
2193                                          REAL( average_count_3d, kind=wp )
2194                       ENDDO
2195                    ENDIF
2196
2197                CASE ( 'usm_wghf_green' )
2198!
2199!--                 array of heat flux from green ground (wall, roof, land)
2200                    IF ( l == -1 ) THEN
2201                       DO  m = 1, surf_usm_h%ns
2202                          surf_usm_h%wghf_eb_green_av(m) =                              &
2203                                             surf_usm_h%wghf_eb_green_av(m) /           &
2204                                             REAL( average_count_3d, kind=wp )
2205                       ENDDO
2206                    ELSE
2207                       DO  m = 1, surf_usm_v(l)%ns
2208                          surf_usm_v(l)%wghf_eb_green_av(m) =                        &
2209                                          surf_usm_v(l)%wghf_eb_green_av(m) /        &
2210                                          REAL( average_count_3d, kind=wp )
2211                       ENDDO
2212                    ENDIF
2213
2214                CASE ( 'usm_iwghf' )
2215!
2216!--                 array of heat flux from indoor ground (wall, roof, land)
2217                    IF ( l == -1 ) THEN
2218                       DO  m = 1, surf_usm_h%ns
2219                          surf_usm_h%iwghf_eb_av(m) =                              &
2220                                             surf_usm_h%iwghf_eb_av(m) /           &
2221                                             REAL( average_count_3d, kind=wp )
2222                       ENDDO
2223                    ELSE
2224                       DO  m = 1, surf_usm_v(l)%ns
2225                          surf_usm_v(l)%iwghf_eb_av(m) =                        &
2226                                          surf_usm_v(l)%iwghf_eb_av(m) /        &
2227                                          REAL( average_count_3d, kind=wp )
2228                       ENDDO
2229                    ENDIF
2230                   
2231                CASE ( 'usm_iwghf_window' )
2232!
2233!--                 array of heat flux from indoor window ground (wall, roof, land)
2234                    IF ( l == -1 ) THEN
2235                       DO  m = 1, surf_usm_h%ns
2236                          surf_usm_h%iwghf_eb_window_av(m) =                              &
2237                                             surf_usm_h%iwghf_eb_window_av(m) /           &
2238                                             REAL( average_count_3d, kind=wp )
2239                       ENDDO
2240                    ELSE
2241                       DO  m = 1, surf_usm_v(l)%ns
2242                          surf_usm_v(l)%iwghf_eb_window_av(m) =                        &
2243                                          surf_usm_v(l)%iwghf_eb_window_av(m) /        &
2244                                          REAL( average_count_3d, kind=wp )
2245                       ENDDO
2246                    ENDIF
2247                   
2248                CASE ( 'usm_t_surf_wall' )
2249!
2250!--                 surface temperature for surfaces
2251                    IF ( l == -1 ) THEN
2252                       DO  m = 1, surf_usm_h%ns
2253                       surf_usm_h%t_surf_wall_av(m) =                               & 
2254                                          surf_usm_h%t_surf_wall_av(m) /            &
2255                                             REAL( average_count_3d, kind=wp )
2256                       ENDDO
2257                    ELSE
2258                       DO  m = 1, surf_usm_v(l)%ns
2259                          surf_usm_v(l)%t_surf_wall_av(m) =                         &
2260                                          surf_usm_v(l)%t_surf_wall_av(m) /         &
2261                                          REAL( average_count_3d, kind=wp )
2262                       ENDDO
2263                    ENDIF
2264                   
2265                CASE ( 'usm_t_surf_window' )
2266!
2267!--                 surface temperature for window surfaces
2268                    IF ( l == -1 ) THEN
2269                       DO  m = 1, surf_usm_h%ns
2270                          surf_usm_h%t_surf_window_av(m) =                               &
2271                                             surf_usm_h%t_surf_window_av(m) /            &
2272                                             REAL( average_count_3d, kind=wp )
2273                       ENDDO
2274                    ELSE
2275                       DO  m = 1, surf_usm_v(l)%ns
2276                          surf_usm_v(l)%t_surf_window_av(m) =                         &
2277                                          surf_usm_v(l)%t_surf_window_av(m) /         &
2278                                          REAL( average_count_3d, kind=wp )
2279                       ENDDO
2280                    ENDIF
2281                   
2282                CASE ( 'usm_t_surf_green' )
2283!
2284!--                 surface temperature for green surfaces
2285                    IF ( l == -1 ) THEN
2286                       DO  m = 1, surf_usm_h%ns
2287                          surf_usm_h%t_surf_green_av(m) =                               &
2288                                             surf_usm_h%t_surf_green_av(m) /            &
2289                                             REAL( average_count_3d, kind=wp )
2290                       ENDDO
2291                    ELSE
2292                       DO  m = 1, surf_usm_v(l)%ns
2293                          surf_usm_v(l)%t_surf_green_av(m) =                         &
2294                                          surf_usm_v(l)%t_surf_green_av(m) /         &
2295                                          REAL( average_count_3d, kind=wp )
2296                       ENDDO
2297                    ENDIF
2298                   
2299                CASE ( 'usm_theta_10cm' )
2300!
2301!--                 near surface temperature for whole surfaces
2302                    IF ( l == -1 ) THEN
2303                       DO  m = 1, surf_usm_h%ns
2304                          surf_usm_h%pt_10cm_av(m) =                               &
2305                                             surf_usm_h%pt_10cm_av(m) /            &
2306                                             REAL( average_count_3d, kind=wp )
2307                       ENDDO
2308                    ELSE
2309                       DO  m = 1, surf_usm_v(l)%ns
2310                          surf_usm_v(l)%pt_10cm_av(m) =                         &
2311                                          surf_usm_v(l)%pt_10cm_av(m) /         &
2312                                          REAL( average_count_3d, kind=wp )
2313                       ENDDO
2314                    ENDIF
2315
2316                   
2317                CASE ( 'usm_t_wall' )
2318!
2319!--                 wall temperature for  iwl layer of walls and land
2320                    IF ( l == -1 ) THEN
2321                       DO  m = 1, surf_usm_h%ns
2322                          surf_usm_h%t_wall_av(iwl,m) =                           &
2323                                             surf_usm_h%t_wall_av(iwl,m) /        &
2324                                             REAL( average_count_3d, kind=wp )
2325                       ENDDO
2326                    ELSE
2327                       DO  m = 1, surf_usm_v(l)%ns
2328                          surf_usm_v(l)%t_wall_av(iwl,m) =                     &
2329                                          surf_usm_v(l)%t_wall_av(iwl,m) /     &
2330                                          REAL( average_count_3d, kind=wp )
2331                       ENDDO
2332                    ENDIF
2333
2334                CASE ( 'usm_t_window' )
2335!
2336!--                 window temperature for  iwl layer of walls and land
2337                    IF ( l == -1 ) THEN
2338                       DO  m = 1, surf_usm_h%ns
2339                          surf_usm_h%t_window_av(iwl,m) =                           &
2340                                             surf_usm_h%t_window_av(iwl,m) /        &
2341                                             REAL( average_count_3d, kind=wp )
2342                       ENDDO
2343                    ELSE
2344                       DO  m = 1, surf_usm_v(l)%ns
2345                          surf_usm_v(l)%t_window_av(iwl,m) =                     &
2346                                          surf_usm_v(l)%t_window_av(iwl,m) /     &
2347                                          REAL( average_count_3d, kind=wp )
2348                       ENDDO
2349                    ENDIF
2350
2351                CASE ( 'usm_t_green' )
2352!
2353!--                 green temperature for  iwl layer of walls and land
2354                    IF ( l == -1 ) THEN
2355                       DO  m = 1, surf_usm_h%ns
2356                          surf_usm_h%t_green_av(iwl,m) =                           &
2357                                             surf_usm_h%t_green_av(iwl,m) /        &
2358                                             REAL( average_count_3d, kind=wp )
2359                       ENDDO
2360                    ELSE
2361                       DO  m = 1, surf_usm_v(l)%ns
2362                          surf_usm_v(l)%t_green_av(iwl,m) =                     &
2363                                          surf_usm_v(l)%t_green_av(iwl,m) /     &
2364                                          REAL( average_count_3d, kind=wp )
2365                       ENDDO
2366                    ENDIF
2367                   
2368                CASE ( 'usm_swc' )
2369!
2370!--                 soil water content for  iwl layer of walls and land
2371                    IF ( l == -1 ) THEN
2372                    DO  m = 1, surf_usm_h%ns
2373                       surf_usm_h%swc_av(iwl,m) =                           &
2374                                          surf_usm_h%swc_av(iwl,m) /        &
2375                                          REAL( average_count_3d, kind=wp )
2376                    ENDDO
2377                    ELSE
2378                       DO  m = 1, surf_usm_v(l)%ns
2379                          surf_usm_v(l)%swc_av(iwl,m) =                     &
2380                                          surf_usm_v(l)%swc_av(iwl,m) /     &
2381                                          REAL( average_count_3d, kind=wp )
2382                       ENDDO
2383                    ENDIF
2384
2385
2386           END SELECT
2387
2388        ENDIF
2389
2390        ENDIF
2391
2392    END SUBROUTINE usm_3d_data_averaging
2393
2394
2395
2396!------------------------------------------------------------------------------!
2397! Description:
2398! ------------
2399!> Set internal Neumann boundary condition at outer soil grid points
2400!> for temperature and humidity.
2401!------------------------------------------------------------------------------!
2402 SUBROUTINE usm_boundary_condition
2403 
2404    IMPLICIT NONE
2405
2406    INTEGER(iwp) :: i      !< grid index x-direction
2407    INTEGER(iwp) :: ioff   !< offset index x-direction indicating location of soil grid point
2408    INTEGER(iwp) :: j      !< grid index y-direction
2409    INTEGER(iwp) :: joff   !< offset index x-direction indicating location of soil grid point
2410    INTEGER(iwp) :: k      !< grid index z-direction
2411    INTEGER(iwp) :: koff   !< offset index x-direction indicating location of soil grid point
2412    INTEGER(iwp) :: l      !< running index surface-orientation
2413    INTEGER(iwp) :: m      !< running index surface elements
2414
2415    koff = surf_usm_h%koff
2416    DO  m = 1, surf_usm_h%ns
2417       i = surf_usm_h%i(m)
2418       j = surf_usm_h%j(m)
2419       k = surf_usm_h%k(m)
2420       pt(k+koff,j,i) = pt(k,j,i)
2421    ENDDO
2422
2423    DO  l = 0, 3
2424       ioff = surf_usm_v(l)%ioff
2425       joff = surf_usm_v(l)%joff
2426       DO  m = 1, surf_usm_v(l)%ns
2427          i = surf_usm_v(l)%i(m)
2428          j = surf_usm_v(l)%j(m)
2429          k = surf_usm_v(l)%k(m)
2430          pt(k,j+joff,i+ioff) = pt(k,j,i)
2431       ENDDO
2432    ENDDO
2433
2434 END SUBROUTINE usm_boundary_condition
2435
2436
2437!------------------------------------------------------------------------------!
2438!
2439! Description:
2440! ------------
2441!> Subroutine checks variables and assigns units.
2442!> It is called out from subroutine check_parameters.
2443!------------------------------------------------------------------------------!
2444    SUBROUTINE usm_check_data_output( variable, unit )
2445
2446        IMPLICIT NONE
2447
2448        CHARACTER(LEN=*),INTENT(IN)    ::  variable   !<
2449        CHARACTER(LEN=*),INTENT(OUT)   ::  unit       !<
2450
2451        INTEGER(iwp)                                  :: i,j,l         !< index
2452        CHARACTER(LEN=2)                              :: ls
2453        CHARACTER(LEN=varnamelength)                  :: var           !< TRIM(variable)
2454        INTEGER(iwp), PARAMETER                       :: nl1 = 15      !< number of directional usm variables
2455        CHARACTER(LEN=varnamelength), DIMENSION(nl1)  :: varlist1 = &  !< list of directional usm variables
2456                  (/'usm_wshf                      ', &
2457                    'usm_wghf                      ', &
2458                    'usm_wghf_window               ', &
2459                    'usm_wghf_green                ', &
2460                    'usm_iwghf                     ', &
2461                    'usm_iwghf_window              ', &
2462                    'usm_surfz                     ', &
2463                    'usm_surfwintrans              ', &
2464                    'usm_surfcat                   ', &
2465                    'usm_t_surf_wall               ', &
2466                    'usm_t_surf_window             ', &
2467                    'usm_t_surf_green              ', &
2468                    'usm_t_green                   ', &
2469                    'usm_qsws                      ', &
2470                    'usm_theta_10cm                '/)
2471
2472        INTEGER(iwp), PARAMETER                       :: nl2 = 3       !< number of directional layer usm variables
2473        CHARACTER(LEN=varnamelength), DIMENSION(nl2)  :: varlist2 = &  !< list of directional layer usm variables
2474                  (/'usm_t_wall                    ', &
2475                    'usm_t_window                  ', &
2476                    'usm_t_green                   '/)
2477
2478        INTEGER(iwp), PARAMETER                       :: nd = 5     !< number of directions
2479        CHARACTER(LEN=6), DIMENSION(nd), PARAMETER  :: dirname = &  !< direction names
2480                  (/'_roof ','_south','_north','_west ','_east '/)
2481        LOGICAL                                       :: lfound     !< flag if the variable is found
2482
2483
2484        lfound = .FALSE.
2485
2486        var = TRIM(variable)
2487
2488!
2489!--     check if variable exists
2490!--     directional variables
2491        DO i = 1, nl1
2492           DO j = 1, nd
2493              IF ( TRIM(var) == TRIM(varlist1(i))//TRIM(dirname(j)) ) THEN
2494                 lfound = .TRUE.
2495                 EXIT
2496              ENDIF
2497              IF ( lfound ) EXIT
2498           ENDDO
2499        ENDDO
2500        IF ( lfound ) GOTO 10
2501!
2502!--     directional layer variables
2503        DO i = 1, nl2
2504           DO j = 1, nd
2505              DO l = nzb_wall, nzt_wall
2506                 WRITE(ls,'(A1,I1)') '_',l
2507                 IF ( TRIM(var) == TRIM(varlist2(i))//TRIM(ls)//TRIM(dirname(j)) ) THEN
2508                    lfound = .TRUE.
2509                    EXIT
2510                 ENDIF
2511              ENDDO
2512              IF ( lfound ) EXIT
2513           ENDDO
2514        ENDDO
2515        IF ( .NOT.  lfound ) THEN
2516           unit = 'illegal'
2517           RETURN
2518        ENDIF
251910      CONTINUE
2520
2521        IF ( var(1:9)  == 'usm_wshf_'  .OR.  var(1:9) == 'usm_wghf_' .OR.                 &
2522             var(1:16) == 'usm_wghf_window_' .OR. var(1:15) == 'usm_wghf_green_' .OR.     &
2523             var(1:10) == 'usm_iwghf_' .OR. var(1:17) == 'usm_iwghf_window_'    .OR.      &
2524             var(1:17) == 'usm_surfwintrans_' .OR.                                        &
2525             var(1:9)  == 'usm_qsws_'  .OR.  var(1:13)  == 'usm_qsws_veg_'  .OR.          &
2526             var(1:13) == 'usm_qsws_liq_' ) THEN
2527            unit = 'W/m2'
2528        ELSE IF ( var(1:15) == 'usm_t_surf_wall'   .OR.  var(1:10) == 'usm_t_wall' .OR.   &
2529                  var(1:12) == 'usm_t_window' .OR. var(1:17) == 'usm_t_surf_window' .OR.  &
2530                  var(1:16) == 'usm_t_surf_green'  .OR.                                   &
2531                  var(1:11) == 'usm_t_green' .OR.  var(1:7) == 'usm_swc' .OR.             &
2532                  var(1:14) == 'usm_theta_10cm' )  THEN
2533            unit = 'K'
2534        ELSE IF ( var(1:9) == 'usm_surfz'  .OR.  var(1:11) == 'usm_surfcat' )  THEN
2535            unit = '1'
2536        ELSE
2537            unit = 'illegal'
2538        ENDIF
2539
2540    END SUBROUTINE usm_check_data_output
2541
2542
2543!------------------------------------------------------------------------------!
2544! Description:
2545! ------------
2546!> Check parameters routine for urban surface model
2547!------------------------------------------------------------------------------!
2548    SUBROUTINE usm_check_parameters
2549
2550       USE control_parameters,                                                 &
2551           ONLY:  bc_pt_b, bc_q_b, constant_flux_layer, large_scale_forcing,   &
2552                  lsf_surf, topography
2553
2554       USE netcdf_data_input_mod,                                             &
2555            ONLY:  building_type_f
2556
2557       IMPLICIT NONE
2558
2559       INTEGER(iwp) ::  i        !< running index, x-dimension
2560       INTEGER(iwp) ::  j        !< running index, y-dimension
2561
2562!
2563!--    Dirichlet boundary conditions are required as the surface fluxes are
2564!--    calculated from the temperature/humidity gradients in the urban surface
2565!--    model
2566       IF ( bc_pt_b == 'neumann'   .OR.   bc_q_b == 'neumann' )  THEN
2567          message_string = 'urban surface model requires setting of '//        &
2568                           'bc_pt_b = "dirichlet" and '//                      &
2569                           'bc_q_b  = "dirichlet"'
2570          CALL message( 'usm_check_parameters', 'PA0590', 1, 2, 0, 6, 0 )
2571       ENDIF
2572
2573       IF ( .NOT.  constant_flux_layer )  THEN
2574          message_string = 'urban surface model requires '//                   &
2575                           'constant_flux_layer = .T.'
2576          CALL message( 'usm_check_parameters', 'PA0084', 1, 2, 0, 6, 0 )
2577       ENDIF
2578
2579       IF (  .NOT.  radiation )  THEN
2580          message_string = 'urban surface model requires '//                   &
2581                           'the radiation model to be switched on'
2582          CALL message( 'usm_check_parameters', 'PA0084', 1, 2, 0, 6, 0 )
2583       ENDIF
2584!       
2585!--    Surface forcing has to be disabled for LSF in case of enabled
2586!--    urban surface module
2587       IF ( large_scale_forcing )  THEN
2588          lsf_surf = .FALSE.
2589       ENDIF
2590!
2591!--    Topography
2592       IF ( topography == 'flat' )  THEN
2593          message_string = 'topography /= "flat" is required '//               &
2594                           'when using the urban surface model'
2595          CALL message( 'usm_check_parameters', 'PA0592', 1, 2, 0, 6, 0 )
2596       ENDIF
2597!
2598!--    naheatlayers
2599       IF ( naheatlayers > nzt )  THEN
2600          message_string = 'number of anthropogenic heat layers '//            &
2601                           '"naheatlayers" can not be larger than'//           &
2602                           ' number of domain layers "nzt"'
2603          CALL message( 'usm_check_parameters', 'PA0593', 1, 2, 0, 6, 0 )
2604       ENDIF
2605!
2606!--    Check if building types are set within a valid range.
2607       IF ( building_type < LBOUND( building_pars, 2 )  .AND.                  &
2608            building_type > UBOUND( building_pars, 2 ) )  THEN
2609          WRITE( message_string, * ) 'building_type = ', building_type,        &
2610                                     ' is out of the valid range'
2611          CALL message( 'usm_check_parameters', 'PA0529', 2, 2, 0, 6, 0 )
2612       ENDIF
2613       IF ( building_type_f%from_file )  THEN
2614          DO  i = nxl, nxr
2615             DO  j = nys, nyn
2616                IF ( building_type_f%var(j,i) /= building_type_f%fill  .AND.   &
2617              ( building_type_f%var(j,i) < LBOUND( building_pars, 2 )  .OR.    &
2618                building_type_f%var(j,i) > UBOUND( building_pars, 2 ) ) )      &
2619                THEN
2620                   WRITE( message_string, * ) 'building_type = is out of ' //  &
2621                                        'the valid range at (j,i) = ', j, i
2622                   CALL message( 'usm_check_parameters', 'PA0529', 2, 2, 0, 6, 0 )
2623                ENDIF
2624             ENDDO
2625          ENDDO
2626       ENDIF
2627    END SUBROUTINE usm_check_parameters
2628
2629
2630!------------------------------------------------------------------------------!
2631!
2632! Description:
2633! ------------
2634!> Output of the 3D-arrays in netCDF and/or AVS format
2635!> for variables of urban_surface model.
2636!> It resorts the urban surface module output quantities from surf style
2637!> indexing into temporary 3D array with indices (i,j,k).
2638!> It is called from subroutine data_output_3d.
2639!------------------------------------------------------------------------------!
2640    SUBROUTINE usm_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
2641       
2642        IMPLICIT NONE
2643
2644        INTEGER(iwp), INTENT(IN)       ::  av        !< flag if averaged
2645        CHARACTER (len=*), INTENT(IN)  ::  variable  !< variable name
2646        INTEGER(iwp), INTENT(IN)       ::  nzb_do    !< lower limit of the data output (usually 0)
2647        INTEGER(iwp), INTENT(IN)       ::  nzt_do    !< vertical upper limit of the data output (usually nz_do3d)
2648        LOGICAL, INTENT(OUT)           ::  found     !<
2649        REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf   !< sp - it has to correspond to module data_output_3d
2650        REAL(sp), DIMENSION(nzb:nzt+1,nys:nyn,nxl:nxr)     ::  temp_pf    !< temp array for urban surface output procedure
2651       
2652        CHARACTER (len=varnamelength)                      :: var     !< trimmed variable name
2653        INTEGER(iwp), PARAMETER                            :: nd = 5  !< number of directions
2654        CHARACTER(len=6), DIMENSION(0:nd-1), PARAMETER     :: dirname = (/ '_roof ', '_south', '_north', '_west ', '_east ' /)
2655        INTEGER(iwp), DIMENSION(0:nd-1), PARAMETER         :: dirint =  (/    iup_u, isouth_u, inorth_u,  iwest_u,  ieast_u /)
2656        INTEGER(iwp), DIMENSION(0:nd-1), PARAMETER         :: diridx =  (/       -1,        1,        0,        3,        2 /)
2657                                                                      !< index for surf_*_v: 0:3 = (North, South, East, West)
2658        INTEGER(iwp)                   :: ids,idsint,idsidx
2659        INTEGER(iwp)                   :: i,j,k,iwl,istat, l, m  !< running indices
2660
2661        found = .TRUE.
2662        temp_pf = -1._wp
2663       
2664        ids = -1
2665        var = TRIM(variable)
2666        DO i = 0, nd-1
2667            k = len(TRIM(var))
2668            j = len(TRIM(dirname(i)))
2669            IF ( TRIM(var(k-j+1:k)) == TRIM(dirname(i)) )  THEN
2670                ids = i
2671                idsint = dirint(ids)
2672                idsidx = diridx(ids)
2673                var = var(:k-j)
2674                EXIT
2675            ENDIF
2676        ENDDO
2677        IF ( ids == -1 )  THEN
2678            var = TRIM(variable)
2679        ENDIF
2680        IF ( var(1:11) == 'usm_t_wall_'  .AND.  len(TRIM(var)) >= 12 )  THEN
2681!
2682!--         wall layers
2683            READ(var(12:12), '(I1)', iostat=istat ) iwl
2684            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
2685                var = var(1:10)
2686            ENDIF
2687        ENDIF
2688        IF ( var(1:13) == 'usm_t_window_'  .AND.  len(TRIM(var)) >= 14 )  THEN
2689!
2690!--         window layers
2691            READ(var(14:14), '(I1)', iostat=istat ) iwl
2692            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
2693                var = var(1:12)
2694            ENDIF
2695        ENDIF
2696        IF ( var(1:12) == 'usm_t_green_'  .AND.  len(TRIM(var)) >= 13 )  THEN
2697!
2698!--         green layers
2699            READ(var(13:13), '(I1)', iostat=istat ) iwl
2700            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
2701                var = var(1:11)
2702            ENDIF
2703        ENDIF
2704        IF ( var(1:8) == 'usm_swc_'  .AND.  len(TRIM(var)) >= 9 )  THEN
2705!
2706!--         green layers soil water content
2707            READ(var(9:9), '(I1)', iostat=istat ) iwl
2708            IF ( istat == 0  .AND.  iwl >= nzb_wall  .AND.  iwl <= nzt_wall )  THEN
2709                var = var(1:7)
2710            ENDIF
2711        ENDIF
2712       
2713        SELECT CASE ( TRIM(var) )
2714
2715          CASE ( 'usm_surfz' )
2716!
2717!--           array of surface height (z)
2718              IF ( idsint == iup_u )  THEN
2719                 DO  m = 1, surf_usm_h%ns
2720                    i = surf_usm_h%i(m)
2721                    j = surf_usm_h%j(m)
2722                    k = surf_usm_h%k(m)
2723                    temp_pf(0,j,i) = MAX( temp_pf(0,j,i), REAL( k, KIND = sp) )
2724                 ENDDO
2725              ELSE
2726                 l = idsidx
2727                 DO  m = 1, surf_usm_v(l)%ns
2728                    i = surf_usm_v(l)%i(m)
2729                    j = surf_usm_v(l)%j(m)
2730                    k = surf_usm_v(l)%k(m)
2731                    temp_pf(0,j,i) = MAX( temp_pf(0,j,i), REAL( k, KIND = sp) + 1.0_sp )
2732                 ENDDO
2733              ENDIF
2734
2735          CASE ( 'usm_surfcat' )
2736!
2737!--           surface category
2738              IF ( idsint == iup_u )  THEN
2739                 DO  m = 1, surf_usm_h%ns
2740                    i = surf_usm_h%i(m)
2741                    j = surf_usm_h%j(m)
2742                    k = surf_usm_h%k(m)
2743                    temp_pf(k,j,i) = surf_usm_h%surface_types(m)
2744                 ENDDO
2745              ELSE
2746                 l = idsidx
2747                 DO  m = 1, surf_usm_v(l)%ns
2748                    i = surf_usm_v(l)%i(m)
2749                    j = surf_usm_v(l)%j(m)
2750                    k = surf_usm_v(l)%k(m)
2751                    temp_pf(k,j,i) = surf_usm_v(l)%surface_types(m)
2752                 ENDDO
2753              ENDIF
2754             
2755          CASE ( 'usm_surfwintrans' )
2756!
2757!--           transmissivity window tiles
2758              IF ( idsint == iup_u )  THEN
2759                 DO  m = 1, surf_usm_h%ns
2760                    i = surf_usm_h%i(m)
2761                    j = surf_usm_h%j(m)
2762                    k = surf_usm_h%k(m)
2763                    temp_pf(k,j,i) = surf_usm_h%transmissivity(m)
2764                 ENDDO
2765              ELSE
2766                 l = idsidx
2767                 DO  m = 1, surf_usm_v(l)%ns
2768                    i = surf_usm_v(l)%i(m)
2769                    j = surf_usm_v(l)%j(m)
2770                    k = surf_usm_v(l)%k(m)
2771                    temp_pf(k,j,i) = surf_usm_v(l)%transmissivity(m)
2772                 ENDDO
2773              ENDIF
2774
2775          CASE ( 'usm_wshf' )
2776!
2777!--           array of sensible heat flux from surfaces
2778              IF ( av == 0 )  THEN
2779                 IF ( idsint == iup_u )  THEN
2780                    DO  m = 1, surf_usm_h%ns
2781                       i = surf_usm_h%i(m)
2782                       j = surf_usm_h%j(m)
2783                       k = surf_usm_h%k(m)
2784                       temp_pf(k,j,i) = surf_usm_h%wshf_eb(m)
2785                    ENDDO
2786                 ELSE
2787                    l = idsidx
2788                    DO  m = 1, surf_usm_v(l)%ns
2789                       i = surf_usm_v(l)%i(m)
2790                       j = surf_usm_v(l)%j(m)
2791                       k = surf_usm_v(l)%k(m)
2792                       temp_pf(k,j,i) = surf_usm_v(l)%wshf_eb(m)
2793                    ENDDO
2794                 ENDIF
2795              ELSE
2796                 IF ( idsint == iup_u )  THEN
2797                    DO  m = 1, surf_usm_h%ns
2798                       i = surf_usm_h%i(m)
2799                       j = surf_usm_h%j(m)
2800                       k = surf_usm_h%k(m)
2801                       temp_pf(k,j,i) = surf_usm_h%wshf_eb_av(m)
2802                    ENDDO
2803                 ELSE
2804                    l = idsidx
2805                    DO  m = 1, surf_usm_v(l)%ns
2806                       i = surf_usm_v(l)%i(m)
2807                       j = surf_usm_v(l)%j(m)
2808                       k = surf_usm_v(l)%k(m)
2809                       temp_pf(k,j,i) = surf_usm_v(l)%wshf_eb_av(m)
2810                    ENDDO
2811                 ENDIF
2812              ENDIF
2813             
2814             
2815          CASE ( 'usm_qsws' )
2816!
2817!--           array of latent heat flux from surfaces
2818              IF ( av == 0 )  THEN
2819                 IF ( idsint == iup_u )  THEN
2820                    DO  m = 1, surf_usm_h%ns
2821                       i = surf_usm_h%i(m)
2822                       j = surf_usm_h%j(m)
2823                       k = surf_usm_h%k(m)
2824                       temp_pf(k,j,i) = surf_usm_h%qsws(m) * l_v
2825                    ENDDO
2826                 ELSE
2827                    l = idsidx
2828                    DO  m = 1, surf_usm_v(l)%ns
2829                       i = surf_usm_v(l)%i(m)
2830                       j = surf_usm_v(l)%j(m)
2831                       k = surf_usm_v(l)%k(m)
2832                       temp_pf(k,j,i) = surf_usm_v(l)%qsws(m) * l_v
2833                    ENDDO
2834                 ENDIF
2835              ELSE
2836                 IF ( idsint == iup_u )  THEN
2837                    DO  m = 1, surf_usm_h%ns
2838                       i = surf_usm_h%i(m)
2839                       j = surf_usm_h%j(m)
2840                       k = surf_usm_h%k(m)
2841                       temp_pf(k,j,i) = surf_usm_h%qsws_av(m)
2842                    ENDDO
2843                 ELSE
2844                    l = idsidx
2845                    DO  m = 1, surf_usm_v(l)%ns
2846                       i = surf_usm_v(l)%i(m)
2847                       j = surf_usm_v(l)%j(m)
2848                       k = surf_usm_v(l)%k(m)
2849                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_av(m)
2850                    ENDDO
2851                 ENDIF
2852              ENDIF
2853             
2854          CASE ( 'usm_qsws_veg' )
2855!
2856!--           array of latent heat flux from vegetation surfaces
2857              IF ( av == 0 )  THEN
2858                 IF ( idsint == iup_u )  THEN
2859                    DO  m = 1, surf_usm_h%ns
2860                       i = surf_usm_h%i(m)
2861                       j = surf_usm_h%j(m)
2862                       k = surf_usm_h%k(m)
2863                       temp_pf(k,j,i) = surf_usm_h%qsws_veg(m)
2864                    ENDDO
2865                 ELSE
2866                    l = idsidx
2867                    DO  m = 1, surf_usm_v(l)%ns
2868                       i = surf_usm_v(l)%i(m)
2869                       j = surf_usm_v(l)%j(m)
2870                       k = surf_usm_v(l)%k(m)
2871                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_veg(m)
2872                    ENDDO
2873                 ENDIF
2874              ELSE
2875                 IF ( idsint == iup_u )  THEN
2876                    DO  m = 1, surf_usm_h%ns
2877                       i = surf_usm_h%i(m)
2878                       j = surf_usm_h%j(m)
2879                       k = surf_usm_h%k(m)
2880                       temp_pf(k,j,i) = surf_usm_h%qsws_veg_av(m)
2881                    ENDDO
2882                 ELSE
2883                    l = idsidx
2884                    DO  m = 1, surf_usm_v(l)%ns
2885                       i = surf_usm_v(l)%i(m)
2886                       j = surf_usm_v(l)%j(m)
2887                       k = surf_usm_v(l)%k(m)
2888                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_veg_av(m)
2889                    ENDDO
2890                 ENDIF
2891              ENDIF
2892             
2893          CASE ( 'usm_qsws_liq' )
2894!
2895!--           array of latent heat flux from surfaces with liquid
2896              IF ( av == 0 )  THEN
2897                 IF ( idsint == iup_u )  THEN
2898                    DO  m = 1, surf_usm_h%ns
2899                       i = surf_usm_h%i(m)
2900                       j = surf_usm_h%j(m)
2901                       k = surf_usm_h%k(m)
2902                       temp_pf(k,j,i) = surf_usm_h%qsws_liq(m)
2903                    ENDDO
2904                 ELSE
2905                    l = idsidx
2906                    DO  m = 1, surf_usm_v(l)%ns
2907                       i = surf_usm_v(l)%i(m)
2908                       j = surf_usm_v(l)%j(m)
2909                       k = surf_usm_v(l)%k(m)
2910                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_liq(m)
2911                    ENDDO
2912                 ENDIF
2913              ELSE
2914                 IF ( idsint == iup_u )  THEN
2915                    DO  m = 1, surf_usm_h%ns
2916                       i = surf_usm_h%i(m)
2917                       j = surf_usm_h%j(m)
2918                       k = surf_usm_h%k(m)
2919                       temp_pf(k,j,i) = surf_usm_h%qsws_liq_av(m)
2920                    ENDDO
2921                 ELSE
2922                    l = idsidx
2923                    DO  m = 1, surf_usm_v(l)%ns
2924                       i = surf_usm_v(l)%i(m)
2925                       j = surf_usm_v(l)%j(m)
2926                       k = surf_usm_v(l)%k(m)
2927                       temp_pf(k,j,i) = surf_usm_v(l)%qsws_liq_av(m)
2928                    ENDDO
2929                 ENDIF
2930              ENDIF
2931
2932          CASE ( 'usm_wghf' )
2933!
2934!--           array of heat flux from ground (land, wall, roof)
2935              IF ( av == 0 )  THEN
2936                 IF ( idsint == iup_u )  THEN
2937                    DO  m = 1, surf_usm_h%ns
2938                       i = surf_usm_h%i(m)
2939                       j = surf_usm_h%j(m)
2940                       k = surf_usm_h%k(m)
2941                       temp_pf(k,j,i) = surf_usm_h%wghf_eb(m)
2942                    ENDDO
2943                 ELSE
2944                    l = idsidx
2945                    DO  m = 1, surf_usm_v(l)%ns
2946                       i = surf_usm_v(l)%i(m)
2947                       j = surf_usm_v(l)%j(m)
2948                       k = surf_usm_v(l)%k(m)
2949                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb(m)
2950                    ENDDO
2951                 ENDIF
2952              ELSE
2953                 IF ( idsint == iup_u )  THEN
2954                    DO  m = 1, surf_usm_h%ns
2955                       i = surf_usm_h%i(m)
2956                       j = surf_usm_h%j(m)
2957                       k = surf_usm_h%k(m)
2958                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_av(m)
2959                    ENDDO
2960                 ELSE
2961                    l = idsidx
2962                    DO  m = 1, surf_usm_v(l)%ns
2963                       i = surf_usm_v(l)%i(m)
2964                       j = surf_usm_v(l)%j(m)
2965                       k = surf_usm_v(l)%k(m)
2966                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_av(m)
2967                    ENDDO
2968                 ENDIF
2969              ENDIF
2970
2971          CASE ( 'usm_wghf_window' )
2972!
2973!--           array of heat flux from window ground (land, wall, roof)
2974              IF ( av == 0 )  THEN
2975                 IF ( idsint == iup_u )  THEN
2976                    DO  m = 1, surf_usm_h%ns
2977                       i = surf_usm_h%i(m)
2978                       j = surf_usm_h%j(m)
2979                       k = surf_usm_h%k(m)
2980                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_window(m)
2981                    ENDDO
2982                 ELSE
2983                    l = idsidx
2984                    DO  m = 1, surf_usm_v(l)%ns
2985                       i = surf_usm_v(l)%i(m)
2986                       j = surf_usm_v(l)%j(m)
2987                       k = surf_usm_v(l)%k(m)
2988                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_window(m)
2989                    ENDDO
2990                 ENDIF
2991              ELSE
2992                 IF ( idsint == iup_u )  THEN
2993                    DO  m = 1, surf_usm_h%ns
2994                       i = surf_usm_h%i(m)
2995                       j = surf_usm_h%j(m)
2996                       k = surf_usm_h%k(m)
2997                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_window_av(m)
2998                    ENDDO
2999                 ELSE
3000                    l = idsidx
3001                    DO  m = 1, surf_usm_v(l)%ns
3002                       i = surf_usm_v(l)%i(m)
3003                       j = surf_usm_v(l)%j(m)
3004                       k = surf_usm_v(l)%k(m)
3005                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_window_av(m)
3006                    ENDDO
3007                 ENDIF
3008              ENDIF
3009
3010          CASE ( 'usm_wghf_green' )
3011!
3012!--           array of heat flux from green ground (land, wall, roof)
3013              IF ( av == 0 )  THEN
3014                 IF ( idsint == iup_u )  THEN
3015                    DO  m = 1, surf_usm_h%ns
3016                       i = surf_usm_h%i(m)
3017                       j = surf_usm_h%j(m)
3018                       k = surf_usm_h%k(m)
3019                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_green(m)
3020                    ENDDO
3021                 ELSE
3022                    l = idsidx
3023                    DO  m = 1, surf_usm_v(l)%ns
3024                       i = surf_usm_v(l)%i(m)
3025                       j = surf_usm_v(l)%j(m)
3026                       k = surf_usm_v(l)%k(m)
3027                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_green(m)
3028                    ENDDO
3029                 ENDIF
3030              ELSE
3031                 IF ( idsint == iup_u )  THEN
3032                    DO  m = 1, surf_usm_h%ns
3033                       i = surf_usm_h%i(m)
3034                       j = surf_usm_h%j(m)
3035                       k = surf_usm_h%k(m)
3036                       temp_pf(k,j,i) = surf_usm_h%wghf_eb_green_av(m)
3037                    ENDDO
3038                 ELSE
3039                    l = idsidx
3040                    DO  m = 1, surf_usm_v(l)%ns
3041                       i = surf_usm_v(l)%i(m)
3042                       j = surf_usm_v(l)%j(m)
3043                       k = surf_usm_v(l)%k(m)
3044                       temp_pf(k,j,i) = surf_usm_v(l)%wghf_eb_green_av(m)
3045                    ENDDO
3046                 ENDIF
3047              ENDIF
3048
3049          CASE ( 'usm_iwghf' )
3050!
3051!--           array of heat flux from indoor ground (land, wall, roof)
3052              IF ( av == 0 )  THEN
3053                 IF ( idsint == iup_u )  THEN
3054                    DO  m = 1, surf_usm_h%ns
3055                       i = surf_usm_h%i(m)
3056                       j = surf_usm_h%j(m)
3057                       k = surf_usm_h%k(m)
3058                       temp_pf(k,j,i) = surf_usm_h%iwghf_eb(m)
3059                    ENDDO
3060                 ELSE
3061                    l = idsidx
3062                    DO  m = 1, surf_usm_v(l)%ns
3063                       i = surf_usm_v(l)%i(m)
3064                       j = surf_usm_v(l)%j(m)
3065                       k = surf_usm_v(l)%k(m)
3066                       temp_pf(k,j,i) = surf_usm_v(l)%iwghf_eb(m)
3067                    ENDDO
3068                 ENDIF
3069              ELSE
3070                 IF ( idsint == iup_u )  THEN
3071                    DO  m = 1, surf_usm_h%ns
3072                       i = surf_usm_h%i(m)
3073                       j = surf_usm_h%j(m)
3074                       k = surf_usm_h%k(m)
3075                       temp_pf(k,j,i) = surf_usm_h%iwghf_eb_av(m)
3076                    ENDDO
3077                 ELSE
3078                    l = idsidx
3079                    DO  m = 1, surf_usm_v(l)%ns
3080                       i = surf_usm_v(l)%i(m)
3081                       j = surf_usm_v(l)%j(m)
3082                       k = surf_usm_v(l)%k(m)
3083                       temp_pf(k,j,i) = surf_usm_v(l)%iwghf_eb_av(m)
3084                    ENDDO
3085                 ENDIF
3086              ENDIF
3087
3088          CASE ( 'usm_iwghf_window' )
3089!
3090!--           array of heat flux from indoor window ground (land, wall, roof)
3091              IF ( av == 0 )  THEN
3092                 IF ( idsint == iup_u )  THEN
3093                    DO  m = 1, surf_usm_h%ns
3094                       i = surf_usm_h%i(m)
3095                       j = surf_usm_h%j(m)
3096                       k = surf_usm_h%k(m)
3097                       temp_pf(k,j,i) = surf_usm_h%iwghf_eb_window(m)
3098                    ENDDO
3099                 ELSE
3100                    l = idsidx
3101                    DO  m = 1, surf_usm_v(l)%ns
3102                       i = surf_usm_v(l)%i(m)
3103                       j = surf_usm_v(l)%j(m)
3104                       k = surf_usm_v(l)%k(m)
3105                       temp_pf(k,j,i) = surf_usm_v(l)%iwghf_eb_window(m)
3106                    ENDDO
3107                 ENDIF
3108              ELSE
3109                 IF ( idsint == iup_u )  THEN
3110                    DO  m = 1, surf_usm_h%ns
3111                       i = surf_usm_h%i(m)
3112                       j = surf_usm_h%j(m)
3113                       k = surf_usm_h%k(m)
3114                       temp_pf(k,j,i) = surf_usm_h%iwghf_eb_window_av(m)
3115                    ENDDO
3116                 ELSE
3117                    l = idsidx
3118                    DO  m = 1, surf_usm_v(l)%ns
3119                       i = surf_usm_v(l)%i(m)
3120                       j = surf_usm_v(l)%j(m)
3121                       k = surf_usm_v(l)%k(m)
3122                       temp_pf(k,j,i) = surf_usm_v(l)%iwghf_eb_window_av(m)
3123                    ENDDO
3124                 ENDIF
3125              ENDIF
3126             
3127          CASE ( 'usm_t_surf_wall' )
3128!
3129!--           surface temperature for surfaces
3130              IF ( av == 0 )  THEN
3131                 IF ( idsint == iup_u )  THEN
3132                    DO  m = 1, surf_usm_h%ns
3133                       i = surf_usm_h%i(m)
3134                       j = surf_usm_h%j(m)
3135                       k = surf_usm_h%k(m)
3136                       temp_pf(k,j,i) = t_surf_wall_h(m)
3137                    ENDDO
3138                 ELSE
3139                    l = idsidx
3140                    DO  m = 1, surf_usm_v(l)%ns
3141                       i = surf_usm_v(l)%i(m)
3142                       j = surf_usm_v(l)%j(m)
3143                       k = surf_usm_v(l)%k(m)
3144                       temp_pf(k,j,i) = t_surf_wall_v(l)%t(m)
3145                    ENDDO
3146                 ENDIF
3147              ELSE
3148                 IF ( idsint == iup_u )  THEN
3149                    DO  m = 1, surf_usm_h%ns
3150                       i = surf_usm_h%i(m)
3151                       j = surf_usm_h%j(m)
3152                       k = surf_usm_h%k(m)
3153                       temp_pf(k,j,i) = surf_usm_h%t_surf_wall_av(m)
3154                    ENDDO
3155                 ELSE
3156                    l = idsidx
3157                    DO  m = 1, surf_usm_v(l)%ns
3158                       i = surf_usm_v(l)%i(m)
3159                       j = surf_usm_v(l)%j(m)
3160                       k = surf_usm_v(l)%k(m)
3161                       temp_pf(k,j,i) = surf_usm_v(l)%t_surf_wall_av(m)
3162                    ENDDO
3163                 ENDIF
3164              ENDIF
3165             
3166          CASE ( 'usm_t_surf_window' )
3167!
3168!--           surface temperature for window surfaces
3169              IF ( av == 0 )  THEN
3170                 IF ( idsint == iup_u )  THEN
3171                    DO  m = 1, surf_usm_h%ns
3172                       i = surf_usm_h%i(m)
3173                       j = surf_usm_h%j(m)
3174                       k = surf_usm_h%k(m)
3175                       temp_pf(k,j,i) = t_surf_window_h(m)
3176                    ENDDO
3177                 ELSE
3178                    l = idsidx
3179                    DO  m = 1, surf_usm_v(l)%ns
3180                       i = surf_usm_v(l)%i(m)
3181                       j = surf_usm_v(l)%j(m)
3182                       k = surf_usm_v(l)%k(m)
3183                       temp_pf(k,j,i) = t_surf_window_v(l)%t(m)
3184                    ENDDO
3185                 ENDIF
3186
3187              ELSE
3188                 IF ( idsint == iup_u )  THEN
3189                    DO  m = 1, surf_usm_h%ns
3190                       i = surf_usm_h%i(m)
3191                       j = surf_usm_h%j(m)
3192                       k = surf_usm_h%k(m)
3193                       temp_pf(k,j,i) = surf_usm_h%t_surf_window_av(m)
3194                    ENDDO
3195                 ELSE
3196                    l = idsidx
3197                    DO  m = 1, surf_usm_v(l)%ns
3198                       i = surf_usm_v(l)%i(m)
3199                       j = surf_usm_v(l)%j(m)
3200                       k = surf_usm_v(l)%k(m)
3201                       temp_pf(k,j,i) = surf_usm_v(l)%t_surf_window_av(m)
3202                    ENDDO
3203
3204                 ENDIF
3205
3206              ENDIF
3207
3208          CASE ( 'usm_t_surf_green' )
3209!
3210!--           surface temperature for green surfaces
3211              IF ( av == 0 )  THEN
3212                 IF ( idsint == iup_u )  THEN
3213                    DO  m = 1, surf_usm_h%ns
3214                       i = surf_usm_h%i(m)
3215                       j = surf_usm_h%j(m)
3216                       k = surf_usm_h%k(m)
3217                       temp_pf(k,j,i) = t_surf_green_h(m)
3218                    ENDDO
3219                 ELSE
3220                    l = idsidx
3221                    DO  m = 1, surf_usm_v(l)%ns
3222                       i = surf_usm_v(l)%i(m)
3223                       j = surf_usm_v(l)%j(m)
3224                       k = surf_usm_v(l)%k(m)
3225                       temp_pf(k,j,i) = t_surf_green_v(l)%t(m)
3226                    ENDDO
3227                 ENDIF
3228
3229              ELSE
3230                 IF ( idsint == iup_u )  THEN
3231                    DO  m = 1, surf_usm_h%ns
3232                       i = surf_usm_h%i(m)
3233                       j = surf_usm_h%j(m)
3234                       k = surf_usm_h%k(m)
3235                       temp_pf(k,j,i) = surf_usm_h%t_surf_green_av(m)
3236                    ENDDO
3237                 ELSE
3238                    l = idsidx
3239                    DO  m = 1, surf_usm_v(l)%ns
3240                       i = surf_usm_v(l)%i(m)
3241                       j = surf_usm_v(l)%j(m)
3242                       k = surf_usm_v(l)%k(m)
3243                       temp_pf(k,j,i) = surf_usm_v(l)%t_surf_green_av(m)
3244                    ENDDO
3245
3246                 ENDIF
3247
3248              ENDIF
3249
3250          CASE ( 'usm_theta_10cm' )
3251!
3252!--           near surface temperature for whole surfaces
3253              IF ( av == 0 )  THEN
3254                 IF ( idsint == iup_u )  THEN
3255                    DO  m = 1, surf_usm_h%ns
3256                       i = surf_usm_h%i(m)
3257                       j = surf_usm_h%j(m)
3258                       k = surf_usm_h%k(m)
3259                       temp_pf(k,j,i) = surf_usm_h%pt_10cm(m)
3260                    ENDDO
3261                 ELSE
3262                    l = idsidx
3263                    DO  m = 1, surf_usm_v(l)%ns
3264                       i = surf_usm_v(l)%i(m)
3265                       j = surf_usm_v(l)%j(m)
3266                       k = surf_usm_v(l)%k(m)
3267                       temp_pf(k,j,i) = surf_usm_v(l)%pt_10cm(m)
3268                    ENDDO
3269                 ENDIF
3270             
3271             
3272              ELSE
3273                 IF ( idsint == iup_u )  THEN
3274                    DO  m = 1, surf_usm_h%ns
3275                       i = surf_usm_h%i(m)
3276                       j = surf_usm_h%j(m)
3277                       k = surf_usm_h%k(m)
3278                       temp_pf(k,j,i) = surf_usm_h%pt_10cm_av(m)
3279                    ENDDO
3280                 ELSE
3281                    l = idsidx
3282                    DO  m = 1, surf_usm_v(l)%ns
3283                       i = surf_usm_v(l)%i(m)
3284                       j = surf_usm_v(l)%j(m)
3285                       k = surf_usm_v(l)%k(m)
3286                       temp_pf(k,j,i) = surf_usm_v(l)%pt_10cm_av(m)
3287                    ENDDO
3288
3289                  ENDIF
3290              ENDIF
3291             
3292          CASE ( 'usm_t_wall' )
3293!
3294!--           wall temperature for  iwl layer of walls and land
3295              IF ( av == 0 )  THEN
3296                 IF ( idsint == iup_u )  THEN
3297                    DO  m = 1, surf_usm_h%ns
3298                       i = surf_usm_h%i(m)
3299                       j = surf_usm_h%j(m)
3300                       k = surf_usm_h%k(m)
3301                       temp_pf(k,j,i) = t_wall_h(iwl,m)
3302                    ENDDO
3303                 ELSE
3304                    l = idsidx
3305                    DO  m = 1, surf_usm_v(l)%ns
3306                       i = surf_usm_v(l)%i(m)
3307                       j = surf_usm_v(l)%j(m)
3308                       k = surf_usm_v(l)%k(m)
3309                       temp_pf(k,j,i) = t_wall_v(l)%t(iwl,m)
3310                    ENDDO
3311                 ENDIF
3312              ELSE
3313                 IF ( idsint == iup_u )  THEN
3314                    DO  m = 1, surf_usm_h%ns
3315                       i = surf_usm_h%i(m)
3316                       j = surf_usm_h%j(m)
3317                       k = surf_usm_h%k(m)
3318                       temp_pf(k,j,i) = surf_usm_h%t_wall_av(iwl,m)
3319                    ENDDO
3320                 ELSE
3321                    l = idsidx
3322                    DO  m = 1, surf_usm_v(l)%ns
3323                       i = surf_usm_v(l)%i(m)
3324                       j = surf_usm_v(l)%j(m)
3325                       k = surf_usm_v(l)%k(m)
3326                       temp_pf(k,j,i) = surf_usm_v(l)%t_wall_av(iwl,m)
3327                    ENDDO
3328                 ENDIF
3329              ENDIF
3330             
3331          CASE ( 'usm_t_window' )
3332!
3333!--           window temperature for iwl layer of walls and land
3334              IF ( av == 0 )  THEN
3335                 IF ( idsint == iup_u )  THEN
3336                    DO  m = 1, surf_usm_h%ns
3337                       i = surf_usm_h%i(m)
3338                       j = surf_usm_h%j(m)
3339                       k = surf_usm_h%k(m)
3340                       temp_pf(k,j,i) = t_window_h(iwl,m)
3341                    ENDDO
3342                 ELSE
3343                    l = idsidx
3344                    DO  m = 1, surf_usm_v(l)%ns
3345                       i = surf_usm_v(l)%i(m)
3346                       j = surf_usm_v(l)%j(m)
3347                       k = surf_usm_v(l)%k(m)
3348                       temp_pf(k,j,i) = t_window_v(l)%t(iwl,m)
3349                    ENDDO
3350                 ENDIF
3351              ELSE
3352                 IF ( idsint == iup_u )  THEN
3353                    DO  m = 1, surf_usm_h%ns
3354                       i = surf_usm_h%i(m)
3355                       j = surf_usm_h%j(m)
3356                       k = surf_usm_h%k(m)
3357                       temp_pf(k,j,i) = surf_usm_h%t_window_av(iwl,m)
3358                    ENDDO
3359                 ELSE
3360                    l = idsidx
3361                    DO  m = 1, surf_usm_v(l)%ns
3362                       i = surf_usm_v(l)%i(m)
3363                       j = surf_usm_v(l)%j(m)
3364                       k = surf_usm_v(l)%k(m)
3365                       temp_pf(k,j,i) = surf_usm_v(l)%t_window_av(iwl,m)
3366                    ENDDO
3367                 ENDIF
3368              ENDIF
3369
3370          CASE ( 'usm_t_green' )
3371!
3372!--           green temperature for  iwl layer of walls and land
3373              IF ( av == 0 )  THEN
3374                 IF ( idsint == iup_u )  THEN
3375                    DO  m = 1, surf_usm_h%ns
3376                       i = surf_usm_h%i(m)
3377                       j = surf_usm_h%j(m)
3378                       k = surf_usm_h%k(m)
3379                       temp_pf(k,j,i) = t_green_h(iwl,m)
3380                    ENDDO
3381                 ELSE
3382                    l = idsidx
3383                    DO  m = 1, surf_usm_v(l)%ns
3384                       i = surf_usm_v(l)%i(m)
3385                       j = surf_usm_v(l)%j(m)
3386                       k = surf_usm_v(l)%k(m)
3387                       temp_pf(k,j,i) = t_green_v(l)%t(iwl,m)
3388                    ENDDO
3389                 ENDIF
3390              ELSE
3391                 IF ( idsint == iup_u )  THEN
3392                    DO  m = 1, surf_usm_h%ns
3393                       i = surf_usm_h%i(m)
3394                       j = surf_usm_h%j(m)
3395                       k = surf_usm_h%k(m)
3396                       temp_pf(k,j,i) = surf_usm_h%t_green_av(iwl,m)
3397                    ENDDO
3398                 ELSE
3399                    l = idsidx
3400                    DO  m = 1, surf_usm_v(l)%ns
3401                       i = surf_usm_v(l)%i(m)
3402                       j = surf_usm_v(l)%j(m)
3403                       k = surf_usm_v(l)%k(m)
3404                       temp_pf(k,j,i) = surf_usm_v(l)%t_green_av(iwl,m)
3405                    ENDDO
3406                 ENDIF
3407              ENDIF
3408             
3409              CASE ( 'usm_swc' )
3410!
3411!--           soil water content for  iwl layer of walls and land
3412              IF ( av == 0 )  THEN
3413                 IF ( idsint == iup_u )  THEN
3414                    DO  m = 1, surf_usm_h%ns
3415                       i = surf_usm_h%i(m)
3416                       j = surf_usm_h%j(m)
3417                       k = surf_usm_h%k(m)
3418                       temp_pf(k,j,i) = swc_h(iwl,m)
3419                    ENDDO
3420                 ELSE
3421                    l = idsidx
3422                    DO  m = 1, surf_usm_v(l)%ns
3423                       i = surf_usm_v(l)%i(m)
3424                       j = surf_usm_v(l)%j(m)
3425                       k = surf_usm_v(l)%k(m)
3426                       temp_pf(k,j,i) = swc_v(l)%t(iwl,m)
3427                    ENDDO
3428                 ENDIF
3429              ELSE
3430                 IF ( idsint == iup_u )  THEN
3431                    DO  m = 1, surf_usm_h%ns
3432                       i = surf_usm_h%i(m)
3433                       j = surf_usm_h%j(m)
3434                       k = surf_usm_h%k(m)
3435                       temp_pf(k,j,i) = surf_usm_h%swc_av(iwl,m)
3436                    ENDDO
3437                 ELSE
3438                    l = idsidx
3439                    DO  m = 1, surf_usm_v(l)%ns
3440                       i = surf_usm_v(l)%i(m)
3441                       j = surf_usm_v(l)%j(m)
3442                       k = surf_usm_v(l)%k(m)
3443                       temp_pf(k,j,i) = surf_usm_v(l)%swc_av(iwl,m)
3444                    ENDDO
3445                 ENDIF
3446              ENDIF
3447
3448             
3449          CASE DEFAULT
3450              found = .FALSE.
3451              RETURN
3452        END SELECT
3453
3454!
3455!--     Rearrange dimensions for NetCDF output
3456!--     FIXME: this may generate FPE overflow upon conversion from DP to SP
3457        DO  j = nys, nyn
3458            DO  i = nxl, nxr
3459                DO  k = nzb_do, nzt_do
3460                    local_pf(i,j,k) = temp_pf(k,j,i)
3461                ENDDO
3462            ENDDO
3463        ENDDO
3464       
3465    END SUBROUTINE usm_data_output_3d
3466   
3467
3468!------------------------------------------------------------------------------!
3469!
3470! Description:
3471! ------------
3472!> Soubroutine defines appropriate grid for netcdf variables.
3473!> It is called out from subroutine netcdf.
3474!------------------------------------------------------------------------------!
3475    SUBROUTINE usm_define_netcdf_grid( variable, found, grid_x, grid_y, grid_z )
3476   
3477        IMPLICIT NONE
3478
3479        CHARACTER (len=*), INTENT(IN)  ::  variable    !<
3480        LOGICAL, INTENT(OUT)           ::  found       !<
3481        CHARACTER (len=*), INTENT(OUT) ::  grid_x      !<
3482        CHARACTER (len=*), INTENT(OUT) ::  grid_y      !<
3483        CHARACTER (len=*), INTENT(OUT) ::  grid_z      !<
3484
3485        CHARACTER (len=varnamelength)  :: var
3486
3487        var = TRIM(variable)
3488        IF ( var(1:9) == 'usm_wshf_'  .OR.  var(1:9) == 'usm_wghf_'  .OR.                   &
3489             var(1:16) == 'usm_wghf_window_'  .OR. var(1:15) == 'usm_wghf_green_' .OR.      &
3490             var(1:10) == 'usm_iwghf_'  .OR. var(1:17) == 'usm_iwghf_window_' .OR.          &
3491             var(1:9) == 'usm_qsws_'  .OR.  var(1:13) == 'usm_qsws_veg_'  .OR.              &
3492             var(1:13) == 'usm_qsws_liq_' .OR.                                              &
3493             var(1:15) == 'usm_t_surf_wall'  .OR.  var(1:10) == 'usm_t_wall'  .OR.          &
3494             var(1:17) == 'usm_t_surf_window'  .OR.  var(1:12) == 'usm_t_window'  .OR.      &
3495             var(1:16) == 'usm_t_surf_green'  .OR. var(1:11) == 'usm_t_green' .OR.          &
3496             var(1:15) == 'usm_theta_10cm' .OR.                                             &
3497             var(1:9) == 'usm_surfz'  .OR.  var(1:11) == 'usm_surfcat'  .OR.                &
3498             var(1:16) == 'usm_surfwintrans'  .OR. var(1:7) == 'usm_swc' ) THEN
3499
3500            found = .TRUE.
3501            grid_x = 'x'
3502            grid_y = 'y'
3503            grid_z = 'zu'
3504        ELSE
3505            found  = .FALSE.
3506            grid_x = 'none'
3507            grid_y = 'none'
3508            grid_z = 'none'
3509        ENDIF
3510
3511    END SUBROUTINE usm_define_netcdf_grid
3512   
3513
3514!------------------------------------------------------------------------------!
3515! Description:
3516! ------------
3517!> Initialization of the wall surface model
3518!------------------------------------------------------------------------------!
3519    SUBROUTINE usm_init_material_model
3520
3521        IMPLICIT NONE
3522
3523        INTEGER(iwp) ::  k, l, m            !< running indices
3524       
3525        IF ( debug_output )  CALL debug_message( 'usm_init_material_model', 'start' )
3526
3527!
3528!--     Calculate wall grid spacings.
3529!--     Temperature is defined at the center of the wall layers,
3530!--     whereas gradients/fluxes are defined at the edges (_stag)     
3531!--     apply for all particular surface grids. First for horizontal surfaces
3532        DO  m = 1, surf_usm_h%ns
3533
3534           surf_usm_h%dz_wall(nzb_wall,m) = surf_usm_h%zw(nzb_wall,m)
3535           DO k = nzb_wall+1, nzt_wall
3536               surf_usm_h%dz_wall(k,m) = surf_usm_h%zw(k,m) -                  &
3537                                         surf_usm_h%zw(k-1,m)
3538           ENDDO
3539           surf_usm_h%dz_window(nzb_wall,m) = surf_usm_h%zw_window(nzb_wall,m)
3540           DO k = nzb_wall+1, nzt_wall
3541               surf_usm_h%dz_window(k,m) = surf_usm_h%zw_window(k,m) -         &
3542                                         surf_usm_h%zw_window(k-1,m)
3543           ENDDO
3544           
3545           surf_usm_h%dz_wall(nzt_wall+1,m) = surf_usm_h%dz_wall(nzt_wall,m)
3546
3547           DO k = nzb_wall, nzt_wall-1
3548               surf_usm_h%dz_wall_stag(k,m) = 0.5 * (                          &
3549                           surf_usm_h%dz_wall(k+1,m) + surf_usm_h%dz_wall(k,m) )
3550           ENDDO
3551           surf_usm_h%dz_wall_stag(nzt_wall,m) = surf_usm_h%dz_wall(nzt_wall,m)
3552           
3553           surf_usm_h%dz_window(nzt_wall+1,m) = surf_usm_h%dz_window(nzt_wall,m)
3554
3555           DO k = nzb_wall, nzt_wall-1
3556               surf_usm_h%dz_window_stag(k,m) = 0.5 * (                        &
3557                           surf_usm_h%dz_window(k+1,m) + surf_usm_h%dz_window(k,m) )
3558           ENDDO
3559           surf_usm_h%dz_window_stag(nzt_wall,m) = surf_usm_h%dz_window(nzt_wall,m)
3560
3561           IF (surf_usm_h%green_type_roof(m) == 2.0_wp ) THEN
3562!
3563!-- extensive green roof
3564!-- set ratio of substrate layer thickness, soil-type and LAI
3565              soil_type = 3
3566              surf_usm_h%lai(m) = 2.0_wp
3567             
3568              surf_usm_h%zw_green(nzb_wall,m)   = 0.05_wp
3569              surf_usm_h%zw_green(nzb_wall+1,m) = 0.10_wp
3570              surf_usm_h%zw_green(nzb_wall+2,m) = 0.15_wp
3571              surf_usm_h%zw_green(nzb_wall+3,m) = 0.20_wp
3572           ELSE
3573!
3574!-- intensiv green roof
3575!-- set ratio of substrate layer thickness, soil-type and LAI
3576              soil_type = 6
3577              surf_usm_h%lai(m) = 4.0_wp
3578             
3579              surf_usm_h%zw_green(nzb_wall,m)   = 0.05_wp
3580              surf_usm_h%zw_green(nzb_wall+1,m) = 0.10_wp
3581              surf_usm_h%zw_green(nzb_wall+2,m) = 0.40_wp
3582              surf_usm_h%zw_green(nzb_wall+3,m) = 0.80_wp
3583           ENDIF
3584           
3585           surf_usm_h%dz_green(nzb_wall,m) = surf_usm_h%zw_green(nzb_wall,m)
3586           DO k = nzb_wall+1, nzt_wall
3587               surf_usm_h%dz_green(k,m) = surf_usm_h%zw_green(k,m) -           &
3588                                         surf_usm_h%zw_green(k-1,m)
3589           ENDDO
3590           surf_usm_h%dz_green(nzt_wall+1,m) = surf_usm_h%dz_green(nzt_wall,m)
3591
3592           DO k = nzb_wall, nzt_wall-1
3593               surf_usm_h%dz_green_stag(k,m) = 0.5 * (                         &
3594                           surf_usm_h%dz_green(k+1,m) + surf_usm_h%dz_green(k,m) )
3595           ENDDO
3596           surf_usm_h%dz_green_stag(nzt_wall,m) = surf_usm_h%dz_green(nzt_wall,m)
3597           
3598          IF ( alpha_vangenuchten == 9999999.9_wp )  THEN
3599             alpha_vangenuchten = soil_pars(0,soil_type)
3600          ENDIF
3601
3602          IF ( l_vangenuchten == 9999999.9_wp )  THEN
3603             l_vangenuchten = soil_pars(1,soil_type)
3604          ENDIF
3605
3606          IF ( n_vangenuchten == 9999999.9_wp )  THEN
3607             n_vangenuchten = soil_pars(2,soil_type)           
3608          ENDIF
3609
3610          IF ( hydraulic_conductivity == 9999999.9_wp )  THEN
3611             hydraulic_conductivity = soil_pars(3,soil_type)           
3612          ENDIF
3613
3614          IF ( saturation_moisture == 9999999.9_wp )  THEN
3615             saturation_moisture = m_soil_pars(0,soil_type)           
3616          ENDIF
3617
3618          IF ( field_capacity == 9999999.9_wp )  THEN
3619             field_capacity = m_soil_pars(1,soil_type)           
3620          ENDIF
3621
3622          IF ( wilting_point == 9999999.9_wp )  THEN
3623             wilting_point = m_soil_pars(2,soil_type)           
3624          ENDIF
3625
3626          IF ( residual_moisture == 9999999.9_wp )  THEN
3627             residual_moisture = m_soil_pars(3,soil_type)       
3628          ENDIF
3629         
3630          DO k = nzb_wall, nzt_wall+1
3631             swc_h(k,m) = field_capacity
3632             rootfr_h(k,m) = 0.5_wp
3633             surf_usm_h%alpha_vg_green(m)      = alpha_vangenuchten
3634             surf_usm_h%l_vg_green(m)          = l_vangenuchten
3635             surf_usm_h%n_vg_green(m)          = n_vangenuchten 
3636             surf_usm_h%gamma_w_green_sat(k,m) = hydraulic_conductivity
3637             swc_sat_h(k,m)                    = saturation_moisture
3638             fc_h(k,m)                         = field_capacity
3639             wilt_h(k,m)                       = wilting_point
3640             swc_res_h(k,m)                    = residual_moisture
3641          ENDDO
3642
3643        ENDDO
3644
3645        surf_usm_h%ddz_wall        = 1.0_wp / surf_usm_h%dz_wall
3646        surf_usm_h%ddz_wall_stag   = 1.0_wp / surf_usm_h%dz_wall_stag
3647        surf_usm_h%ddz_window      = 1.0_wp / surf_usm_h%dz_window
3648        surf_usm_h%ddz_window_stag = 1.0_wp / surf_usm_h%dz_window_stag
3649        surf_usm_h%ddz_green       = 1.0_wp / surf_usm_h%dz_green
3650        surf_usm_h%ddz_green_stag  = 1.0_wp / surf_usm_h%dz_green_stag
3651!       
3652!--     For vertical surfaces
3653        DO  l = 0, 3
3654           DO  m = 1, surf_usm_v(l)%ns
3655              surf_usm_v(l)%dz_wall(nzb_wall,m) = surf_usm_v(l)%zw(nzb_wall,m)
3656              DO k = nzb_wall+1, nzt_wall
3657                  surf_usm_v(l)%dz_wall(k,m) = surf_usm_v(l)%zw(k,m) -         &
3658                                               surf_usm_v(l)%zw(k-1,m)
3659              ENDDO
3660              surf_usm_v(l)%dz_window(nzb_wall,m) = surf_usm_v(l)%zw_window(nzb_wall,m)
3661              DO k = nzb_wall+1, nzt_wall
3662                  surf_usm_v(l)%dz_window(k,m) = surf_usm_v(l)%zw_window(k,m) - &
3663                                               surf_usm_v(l)%zw_window(k-1,m)
3664              ENDDO
3665              surf_usm_v(l)%dz_green(nzb_wall,m) = surf_usm_v(l)%zw_green(nzb_wall,m)
3666              DO k = nzb_wall+1, nzt_wall
3667                  surf_usm_v(l)%dz_green(k,m) = surf_usm_v(l)%zw_green(k,m) - &
3668                                               surf_usm_v(l)%zw_green(k-1,m)
3669              ENDDO
3670           
3671              surf_usm_v(l)%dz_wall(nzt_wall+1,m) =                            &
3672                                              surf_usm_v(l)%dz_wall(nzt_wall,m)
3673
3674              DO k = nzb_wall, nzt_wall-1
3675                  surf_usm_v(l)%dz_wall_stag(k,m) = 0.5 * (                    &
3676                                                surf_usm_v(l)%dz_wall(k+1,m) + &
3677                                                surf_usm_v(l)%dz_wall(k,m) )
3678              ENDDO
3679              surf_usm_v(l)%dz_wall_stag(nzt_wall,m) =                         &
3680                                              surf_usm_v(l)%dz_wall(nzt_wall,m)
3681              surf_usm_v(l)%dz_window(nzt_wall+1,m) =                          &
3682                                              surf_usm_v(l)%dz_window(nzt_wall,m)
3683
3684              DO k = nzb_wall, nzt_wall-1
3685                  surf_usm_v(l)%dz_window_stag(k,m) = 0.5 * (                    &
3686                                                surf_usm_v(l)%dz_window(k+1,m) + &
3687                                                surf_usm_v(l)%dz_window(k,m) )
3688              ENDDO
3689              surf_usm_v(l)%dz_window_stag(nzt_wall,m) =                         &
3690                                              surf_usm_v(l)%dz_window(nzt_wall,m)
3691              surf_usm_v(l)%dz_green(nzt_wall+1,m) =                             &
3692                                              surf_usm_v(l)%dz_green(nzt_wall,m)
3693
3694              DO k = nzb_wall, nzt_wall-1
3695                  surf_usm_v(l)%dz_green_stag(k,m) = 0.5 * (                    &
3696                                                surf_usm_v(l)%dz_green(k+1,m) + &
3697                                                surf_usm_v(l)%dz_green(k,m) )
3698              ENDDO
3699              surf_usm_v(l)%dz_green_stag(nzt_wall,m) =                         &
3700                                              surf_usm_v(l)%dz_green(nzt_wall,m)
3701           ENDDO
3702           surf_usm_v(l)%ddz_wall        = 1.0_wp / surf_usm_v(l)%dz_wall
3703           surf_usm_v(l)%ddz_wall_stag   = 1.0_wp / surf_usm_v(l)%dz_wall_stag
3704           surf_usm_v(l)%ddz_window      = 1.0_wp / surf_usm_v(l)%dz_window
3705           surf_usm_v(l)%ddz_window_stag = 1.0_wp / surf_usm_v(l)%dz_window_stag
3706           surf_usm_v(l)%ddz_green       = 1.0_wp / surf_usm_v(l)%dz_green
3707           surf_usm_v(l)%ddz_green_stag  = 1.0_wp / surf_usm_v(l)%dz_green_stag
3708        ENDDO     
3709
3710       
3711        IF ( debug_output )  CALL debug_message( 'usm_init_material_model', 'end' )
3712
3713    END SUBROUTINE usm_init_material_model
3714
3715 
3716!------------------------------------------------------------------------------!
3717! Description:
3718! ------------
3719!> Initialization of the urban surface model
3720!------------------------------------------------------------------------------!
3721    SUBROUTINE usm_init
3722
3723        USE arrays_3d,                                                         &
3724            ONLY:  zw
3725
3726        USE netcdf_data_input_mod,                                             &
3727            ONLY:  building_pars_f, building_type_f, terrain_height_f
3728   
3729        IMPLICIT NONE
3730
3731        INTEGER(iwp) ::  i                   !< loop index x-dirction
3732        INTEGER(iwp) ::  ind_alb_green       !< index in input list for green albedo
3733        INTEGER(iwp) ::  ind_alb_wall        !< index in input list for wall albedo
3734        INTEGER(iwp) ::  ind_alb_win         !< index in input list for window albedo
3735        INTEGER(iwp) ::  ind_emis_wall       !< index in input list for wall emissivity
3736        INTEGER(iwp) ::  ind_emis_green      !< index in input list for green emissivity
3737        INTEGER(iwp) ::  ind_emis_win        !< index in input list for window emissivity
3738        INTEGER(iwp) ::  ind_green_frac_w    !< index in input list for green fraction on wall
3739        INTEGER(iwp) ::  ind_green_frac_r    !< index in input list for green fraction on roof
3740        INTEGER(iwp) ::  ind_hc1             !< index in input list for heat capacity at first wall layer
3741        INTEGER(iwp) ::  ind_hc1_win         !< index in input list for heat capacity at first window layer
3742        INTEGER(iwp) ::  ind_hc2             !< index in input list for heat capacity at second wall layer
3743        INTEGER(iwp) ::  ind_hc2_win         !< index in input list for heat capacity at second window layer
3744        INTEGER(iwp) ::  ind_hc3             !< index in input list for heat capacity at third wall layer
3745        INTEGER(iwp) ::  ind_hc3_win         !< index in input list for heat capacity at third window layer
3746        INTEGER(iwp) ::  ind_lai_r           !< index in input list for LAI on roof
3747        INTEGER(iwp) ::  ind_lai_w           !< index in input list for LAI on wall
3748        INTEGER(iwp) ::  ind_tc1             !< index in input list for thermal conductivity at first wall layer
3749        INTEGER(iwp) ::  ind_tc1_win         !< index in input list for thermal conductivity at first window layer
3750        INTEGER(iwp) ::  ind_tc2             !< index in input list for thermal conductivity at second wall layer
3751        INTEGER(iwp) ::  ind_tc2_win         !< index in input list for thermal conductivity at second window layer
3752        INTEGER(iwp) ::  ind_tc3             !< index in input list for thermal conductivity at third wall layer
3753        INTEGER(iwp) ::  ind_tc3_win         !< index in input list for thermal conductivity at third window layer
3754        INTEGER(iwp) ::  ind_thick_1         !< index in input list for thickness of first wall layer
3755        INTEGER(iwp) ::  ind_thick_1_win     !< index in input list for thickness of first window layer
3756        INTEGER(iwp) ::  ind_thick_2         !< index in input list for thickness of second wall layer
3757        INTEGER(iwp) ::  ind_thick_2_win     !< index in input list for thickness of second window layer
3758        INTEGER(iwp) ::  ind_thick_3         !< index in input list for thickness of third wall layer
3759        INTEGER(iwp) ::  ind_thick_3_win     !< index in input list for thickness of third window layer
3760        INTEGER(iwp) ::  ind_thick_4         !< index in input list for thickness of fourth wall layer
3761        INTEGER(iwp) ::  ind_thick_4_win     !< index in input list for thickness of fourth window layer
3762        INTEGER(iwp) ::  ind_trans           !< index in input list for window transmissivity
3763        INTEGER(iwp) ::  ind_wall_frac       !< index in input list for wall fraction
3764        INTEGER(iwp) ::  ind_win_frac        !< index in input list for window fraction
3765        INTEGER(iwp) ::  ind_z0              !< index in input list for z0
3766        INTEGER(iwp) ::  ind_z0qh            !< index in input list for z0h / z0q
3767        INTEGER(iwp) ::  j                   !< loop index y-dirction
3768        INTEGER(iwp) ::  k                   !< loop index z-dirction
3769        INTEGER(iwp) ::  l                   !< loop index surface orientation
3770        INTEGER(iwp) ::  m                   !< loop index surface element
3771        INTEGER(iwp) ::  st                  !< dummy 
3772
3773        REAL(wp)     ::  c, tin, twin
3774        REAL(wp)     ::  ground_floor_level_l         !< local height of ground floor level
3775        REAL(wp)     ::  z_agl                        !< height above ground
3776
3777        IF ( debug_output )  CALL debug_message( 'usm_init', 'start' )
3778
3779        CALL cpu_log( log_point_s(78), 'usm_init', 'start' )
3780!
3781!--     Initialize building-surface properties
3782        CALL usm_define_pars
3783!
3784!--     surface forcing have to be disabled for LSF
3785!--     in case of enabled urban surface module
3786        IF ( large_scale_forcing )  THEN
3787            lsf_surf = .FALSE.
3788        ENDIF
3789!
3790!--     Flag surface elements belonging to the ground floor level. Therefore,
3791!--     use terrain height array from file, if available. This flag is later used
3792!--     to control initialization of surface attributes.
3793!--     Todo: for the moment disable initialization of building roofs with
3794!--     ground-floor-level properties.
3795        surf_usm_h%ground_level = .FALSE. 
3796
3797        DO  l = 0, 3
3798           surf_usm_v(l)%ground_level = .FALSE.
3799           DO  m = 1, surf_usm_v(l)%ns
3800              i = surf_usm_v(l)%i(m) + surf_usm_v(l)%ioff
3801              j = surf_usm_v(l)%j(m) + surf_usm_v(l)%joff
3802              k = surf_usm_v(l)%k(m)
3803!
3804!--           Determine local ground level. Level 1 - default value,
3805!--           level 2 - initialization according to building type,
3806!--           level 3 - initialization from value read from file.
3807              ground_floor_level_l = ground_floor_level
3808             
3809              IF ( building_type_f%from_file )  THEN
3810                  ground_floor_level_l =                                       &
3811                              building_pars(ind_gflh,building_type_f%var(j,i))
3812              ENDIF
3813             
3814              IF ( building_pars_f%from_file )  THEN
3815                 IF ( building_pars_f%pars_xy(ind_gflh,j,i) /=                 &
3816                      building_pars_f%fill )                                   &
3817                    ground_floor_level_l = building_pars_f%pars_xy(ind_gflh,j,i)
3818              ENDIF
3819!
3820!--           Determine height of surface element above ground level. Please
3821!--           note, height of surface element is determined with respect to
3822!--           its height above ground of the reference grid point in atmosphere,
3823!--           Therefore, substract the offset values when assessing the terrain
3824!--           height.
3825              IF ( terrain_height_f%from_file )  THEN
3826                 z_agl = zw(k) - terrain_height_f%var(j-surf_usm_v(l)%joff,    &
3827                                                      i-surf_usm_v(l)%ioff)
3828              ELSE
3829                 z_agl = zw(k)
3830              ENDIF
3831!
3832!--           Set flag for ground level
3833              IF ( z_agl <= ground_floor_level_l )                             &
3834                 surf_usm_v(l)%ground_level(m) = .TRUE.
3835
3836           ENDDO
3837        ENDDO
3838!
3839!--     Initialization of resistances.
3840        DO  m = 1, surf_usm_h%ns
3841           surf_usm_h%r_a(m)        = 50.0_wp
3842           surf_usm_h%r_a_green(m)  = 50.0_wp
3843           surf_usm_h%r_a_window(m) = 50.0_wp
3844        ENDDO
3845        DO  l = 0, 3
3846           DO  m = 1, surf_usm_v(l)%ns
3847              surf_usm_v(l)%r_a(m)        = 50.0_wp
3848              surf_usm_v(l)%r_a_green(m)  = 50.0_wp
3849              surf_usm_v(l)%r_a_window(m) = 50.0_wp
3850           ENDDO
3851        ENDDO
3852       
3853!
3854!--    Map values onto horizontal elemements
3855       DO  m = 1, surf_usm_h%ns
3856             surf_usm_h%r_canopy_min(m)     = 200.0_wp !< min_canopy_resistance
3857             surf_usm_h%g_d(m)              = 0.0_wp   !< canopy_resistance_coefficient
3858       ENDDO
3859!
3860!--    Map values onto vertical elements, even though this does not make
3861!--    much sense.
3862       DO  l = 0, 3
3863          DO  m = 1, surf_usm_v(l)%ns
3864                surf_usm_v(l)%r_canopy_min(m)     = 200.0_wp !< min_canopy_resistance
3865                surf_usm_v(l)%g_d(m)              = 0.0_wp   !< canopy_resistance_coefficient
3866          ENDDO
3867       ENDDO
3868
3869!
3870!--     Initialize urban-type surface attribute. According to initialization in
3871!--     land-surface model, follow a 3-level approach.
3872!--     Level 1 - initialization via default attributes
3873        DO  m = 1, surf_usm_h%ns
3874!
3875!--        Now, all horizontal surfaces are roof surfaces (?)
3876           surf_usm_h%isroof_surf(m)   = .TRUE.
3877           surf_usm_h%surface_types(m) = roof_category         !< default category for root surface
3878!
3879!--        In order to distinguish between ground floor level and
3880!--        above-ground-floor level surfaces, set input indices.
3881
3882           ind_green_frac_r = MERGE( ind_green_frac_r_gfl, ind_green_frac_r_agfl, &
3883                                     surf_usm_h%ground_level(m) )
3884           ind_lai_r        = MERGE( ind_lai_r_gfl,        ind_lai_r_agfl,        &
3885                                     surf_usm_h%ground_level(m) )
3886           ind_z0           = MERGE( ind_z0_gfl,           ind_z0_agfl,           &
3887                                     surf_usm_h%ground_level(m) )
3888           ind_z0qh         = MERGE( ind_z0qh_gfl,         ind_z0qh_agfl,         &
3889                                     surf_usm_h%ground_level(m) )
3890!
3891!--        Store building type and its name on each surface element
3892           surf_usm_h%building_type(m)      = building_type
3893           surf_usm_h%building_type_name(m) = building_type_name(building_type)
3894!
3895!--        Initialize relatvie wall- (0), green- (1) and window (2) fractions
3896           surf_usm_h%frac(ind_veg_wall,m)  = building_pars(ind_wall_frac_r,building_type)   
3897           surf_usm_h%frac(ind_pav_green,m) = building_pars(ind_green_frac_r,building_type) 
3898           surf_usm_h%frac(ind_wat_win,m)   = building_pars(ind_win_frac_r,building_type) 
3899           surf_usm_h%lai(m)                = building_pars(ind_lai_r,building_type) 
3900
3901           surf_usm_h%rho_c_wall(nzb_wall,m)   = building_pars(ind_hc1_wall_r,building_type) 
3902           surf_usm_h%rho_c_wall(nzb_wall+1,m) = building_pars(ind_hc1_wall_r,building_type)
3903           surf_usm_h%rho_c_wall(nzb_wall+2,m) = building_pars(ind_hc2_wall_r,building_type)
3904           surf_usm_h%rho_c_wall(nzb_wall+3,m) = building_pars(ind_hc3_wall_r,building_type)   
3905           surf_usm_h%lambda_h(nzb_wall,m)   = building_pars(ind_tc1_wall_r,building_type) 
3906           surf_usm_h%lambda_h(nzb_wall+1,m) = building_pars(ind_tc1_wall_r,building_type) 
3907           surf_usm_h%lambda_h(nzb_wall+2,m) = building_pars(ind_tc2_wall_r,building_type)
3908           surf_usm_h%lambda_h(nzb_wall+3,m) = building_pars(ind_tc3_wall_r,building_type)   
3909           surf_usm_h%rho_c_green(nzb_wall,m)   = rho_c_soil !building_pars(ind_hc1_wall_r,building_type) 
3910           surf_usm_h%rho_c_green(nzb_wall+1,m) = rho_c_soil !building_pars(ind_hc1_wall_r,building_type)
3911           surf_usm_h%rho_c_green(nzb_wall+2,m) = rho_c_soil !building_pars(ind_hc2_wall_r,building_type)
3912           surf_usm_h%rho_c_green(nzb_wall+3,m) = rho_c_soil !building_pars(ind_hc3_wall_r,building_type)   
3913           surf_usm_h%lambda_h_green(nzb_wall,m)   = lambda_h_green_sm !building_pars(ind_tc1_wall_r,building_type) 
3914           surf_usm_h%lambda_h_green(nzb_wall+1,m) = lambda_h_green_sm !building_pars(ind_tc1_wall_r,building_type)
3915           surf_usm_h%lambda_h_green(nzb_wall+2,m) = lambda_h_green_sm !building_pars(ind_tc2_wall_r,building_type)
3916           surf_usm_h%lambda_h_green(nzb_wall+3,m) = lambda_h_green_sm !building_pars(ind_tc3_wall_r,building_type)
3917           surf_usm_h%rho_c_window(nzb_wall,m)   = building_pars(ind_hc1_win_r,building_type) 
3918           surf_usm_h%rho_c_window(nzb_wall+1,m) = building_pars(ind_hc1_win_r,building_type)
3919           surf_usm_h%rho_c_window(nzb_wall+2,m) = building_pars(ind_hc2_win_r,building_type)
3920           surf_usm_h%rho_c_window(nzb_wall+3,m) = building_pars(ind_hc3_win_r,building_type)   
3921           surf_usm_h%lambda_h_window(nzb_wall,m)   = building_pars(ind_tc1_win_r,building_type) 
3922           surf_usm_h%lambda_h_window(nzb_wall+1,m) = building_pars(ind_tc1_win_r,building_type) 
3923           surf_usm_h%lambda_h_window(nzb_wall+2,m) = building_pars(ind_tc2_win_r,building_type)
3924           surf_usm_h%lambda_h_window(nzb_wall+3,m) = building_pars(ind_tc3_win_r,building_type)   
3925
3926           surf_usm_h%target_temp_summer(m)  = building_pars(ind_indoor_target_temp_summer,building_type)   
3927           surf_usm_h%target_temp_winter(m)  = building_pars(ind_indoor_target_temp_winter,building_type)   
3928!
3929!--        emissivity of wall-, green- and window fraction
3930           surf_usm_h%emissivity(ind_veg_wall,m)  = building_pars(ind_emis_wall_r,building_type)
3931           surf_usm_h%emissivity(ind_pav_green,m) = building_pars(ind_emis_green_r,building_type)
3932           surf_usm_h%emissivity(ind_wat_win,m)   = building_pars(ind_emis_win_r,building_type)
3933
3934           surf_usm_h%transmissivity(m)      = building_pars(ind_trans_r,building_type)
3935
3936           surf_usm_h%z0(m)                  = building_pars(ind_z0,building_type)
3937           surf_usm_h%z0h(m)                 = building_pars(ind_z0qh,building_type)
3938           surf_usm_h%z0q(m)                 = building_pars(ind_z0qh,building_type)
3939!
3940!--        albedo type for wall fraction, green fraction, window fraction
3941           surf_usm_h%albedo_type(ind_veg_wall,m)  = INT( building_pars(ind_alb_wall_r,building_type)  )
3942           surf_usm_h%albedo_type(ind_pav_green,m) = INT( building_pars(ind_alb_green_r,building_type) )
3943           surf_usm_h%albedo_type(ind_wat_win,m)   = INT( building_pars(ind_alb_win_r,building_type)   )
3944
3945           surf_usm_h%zw(nzb_wall,m)         = building_pars(ind_thick_1_wall_r,building_type)
3946           surf_usm_h%zw(nzb_wall+1,m)       = building_pars(ind_thick_2_wall_r,building_type)
3947           surf_usm_h%zw(nzb_wall+2,m)       = building_pars(ind_thick_3_wall_r,building_type)
3948           surf_usm_h%zw(nzb_wall+3,m)       = building_pars(ind_thick_4_wall_r,building_type)
3949           
3950           surf_usm_h%zw_green(nzb_wall,m)         = building_pars(ind_thick_1_wall_r,building_type)
3951           surf_usm_h%zw_green(nzb_wall+1,m)       = building_pars(ind_thick_2_wall_r,building_type)
3952           surf_usm_h%zw_green(nzb_wall+2,m)       = building_pars(ind_thick_3_wall_r,building_type)
3953           surf_usm_h%zw_green(nzb_wall+3,m)       = building_pars(ind_thick_4_wall_r,building_type)
3954           
3955           surf_usm_h%zw_window(nzb_wall,m)         = building_pars(ind_thick_1_win_r,building_type)
3956           surf_usm_h%zw_window(nzb_wall+1,m)       = building_pars(ind_thick_2_win_r,building_type)
3957           surf_usm_h%zw_window(nzb_wall+2,m)       = building_pars(ind_thick_3_win_r,building_type)
3958           surf_usm_h%zw_window(nzb_wall+3,m)       = building_pars(ind_thick_4_win_r,building_type)
3959
3960           surf_usm_h%c_surface(m)           = building_pars(ind_c_surface,building_type) 
3961           surf_usm_h%lambda_surf(m)         = building_pars(ind_lambda_surf,building_type) 
3962           surf_usm_h%c_surface_green(m)     = building_pars(ind_c_surface_green,building_type) 
3963           surf_usm_h%lambda_surf_green(m)   = building_pars(ind_lambda_surf_green,building_type) 
3964           surf_usm_h%c_surface_window(m)    = building_pars(ind_c_surface_win,building_type) 
3965           surf_usm_h%lambda_surf_window(m)  = building_pars(ind_lambda_surf_win,building_type) 
3966           
3967           surf_usm_h%green_type_roof(m)     = building_pars(ind_green_type_roof,building_type)
3968
3969        ENDDO
3970
3971        DO  l = 0, 3
3972           DO  m = 1, surf_usm_v(l)%ns
3973
3974              surf_usm_v(l)%surface_types(m) = wall_category         !< default category for root surface
3975!
3976!--           In order to distinguish between ground floor level and
3977!--           above-ground-floor level surfaces, set input indices.
3978              ind_alb_green    = MERGE( ind_alb_green_gfl,    ind_alb_green_agfl,    &
3979                                        surf_usm_v(l)%ground_level(m) )
3980              ind_alb_wall     = MERGE( ind_alb_wall_gfl,     ind_alb_wall_agfl,     &
3981                                        surf_usm_v(l)%ground_level(m) )
3982              ind_alb_win      = MERGE( ind_alb_win_gfl,      ind_alb_win_agfl,      &
3983                                        surf_usm_v(l)%ground_level(m) )
3984              ind_wall_frac    = MERGE( ind_wall_frac_gfl,    ind_wall_frac_agfl,    &
3985                                        surf_usm_v(l)%ground_level(m) )
3986              ind_win_frac     = MERGE( ind_win_frac_gfl,     ind_win_frac_agfl,     &
3987                                        surf_usm_v(l)%ground_level(m) )
3988              ind_green_frac_w = MERGE( ind_green_frac_w_gfl, ind_green_frac_w_agfl, &
3989                                        surf_usm_v(l)%ground_level(m) )
3990              ind_green_frac_r = MERGE( ind_green_frac_r_gfl, ind_green_frac_r_agfl, &
3991                                        surf_usm_v(l)%ground_level(m) )
3992              ind_lai_r        = MERGE( ind_lai_r_gfl,        ind_lai_r_agfl,        &
3993                                        surf_usm_v(l)%ground_level(m) )
3994              ind_lai_w        = MERGE( ind_lai_w_gfl,        ind_lai_w_agfl,        &
3995                                        surf_usm_v(l)%ground_level(m) )
3996              ind_hc1          = MERGE( ind_hc1_gfl,          ind_hc1_agfl,          &
3997                                        surf_usm_v(l)%ground_level(m) )
3998              ind_hc1_win      = MERGE( ind_hc1_win_gfl,      ind_hc1_win_agfl,      &
3999                                        surf_usm_v(l)%ground_level(m) )
4000              ind_hc2          = MERGE( ind_hc2_gfl,          ind_hc2_agfl,          &
4001                                        surf_usm_v(l)%ground_level(m) )
4002              ind_hc2_win      = MERGE( ind_hc2_win_gfl,      ind_hc2_win_agfl,      &
4003                                        surf_usm_v(l)%ground_level(m) )
4004              ind_hc3          = MERGE( ind_hc3_gfl,          ind_hc3_agfl,          &
4005                                        surf_usm_v(l)%ground_level(m) )
4006              ind_hc3_win      = MERGE( ind_hc3_win_gfl,      ind_hc3_win_agfl,      &
4007                                        surf_usm_v(l)%ground_level(m) )
4008              ind_tc1          = MERGE( ind_tc1_gfl,          ind_tc1_agfl,          &
4009                                        surf_usm_v(l)%ground_level(m) )
4010              ind_tc1_win      = MERGE( ind_tc1_win_gfl,      ind_tc1_win_agfl,      &
4011                                        surf_usm_v(l)%ground_level(m) )
4012              ind_tc2          = MERGE( ind_tc2_gfl,          ind_tc2_agfl,          &
4013                                        surf_usm_v(l)%ground_level(m) )
4014              ind_tc2_win      = MERGE( ind_tc2_win_gfl,      ind_tc2_win_agfl,      &
4015                                        surf_usm_v(l)%ground_level(m) )
4016              ind_tc3          = MERGE( ind_tc3_gfl,          ind_tc3_agfl,          &
4017                                        surf_usm_v(l)%ground_level(m) )
4018              ind_tc3_win      = MERGE( ind_tc3_win_gfl,      ind_tc3_win_agfl,      &
4019                                        surf_usm_v(l)%ground_level(m) )
4020              ind_thick_1      = MERGE( ind_thick_1_gfl,      ind_thick_1_agfl,      &
4021                                        surf_usm_v(l)%ground_level(m) )
4022              ind_thick_1_win  = MERGE( ind_thick_1_win_gfl,  ind_thick_1_win_agfl,  &
4023                                        surf_usm_v(l)%ground_level(m) )
4024              ind_thick_2      = MERGE( ind_thick_2_gfl,      ind_thick_2_agfl,      &
4025                                        surf_usm_v(l)%ground_level(m) )
4026              ind_thick_2_win  = MERGE( ind_thick_2_win_gfl,  ind_thick_2_win_agfl,  &
4027                                        surf_usm_v(l)%ground_level(m) )
4028              ind_thick_3      = MERGE( ind_thick_3_gfl,      ind_thick_3_agfl,      &
4029                                        surf_usm_v(l)%ground_level(m) )
4030              ind_thick_3_win  = MERGE( ind_thick_3_win_gfl,  ind_thick_3_win_agfl,  &
4031                                        surf_usm_v(l)%ground_level(m) )
4032              ind_thick_4      = MERGE( ind_thick_4_gfl,      ind_thick_4_agfl,      &
4033                                        surf_usm_v(l)%ground_level(m) )
4034              ind_thick_4_win  = MERGE( ind_thick_4_win_gfl,  ind_thick_4_win_agfl,  &
4035                                        surf_usm_v(l)%ground_level(m) )
4036              ind_emis_wall    = MERGE( ind_emis_wall_gfl,    ind_emis_wall_agfl,    &
4037                                        surf_usm_v(l)%ground_level(m) )
4038              ind_emis_green   = MERGE( ind_emis_green_gfl,   ind_emis_green_agfl,   &
4039                                        surf_usm_v(l)%ground_level(m) )
4040              ind_emis_win     = MERGE( ind_emis_win_gfl,     ind_emis_win_agfl,     &
4041                                        surf_usm_v(l)%ground_level(m) )
4042              ind_trans        = MERGE( ind_trans_gfl,       ind_trans_agfl,         &
4043                                        surf_usm_v(l)%ground_level(m) )
4044              ind_z0           = MERGE( ind_z0_gfl,           ind_z0_agfl,           &
4045                                        surf_usm_v(l)%ground_level(m) )
4046              ind_z0qh         = MERGE( ind_z0qh_gfl,         ind_z0qh_agfl,         &
4047                                        surf_usm_v(l)%ground_level(m) )
4048!
4049!--           Store building type and its name on each surface element
4050              surf_usm_v(l)%building_type(m)      = building_type
4051              surf_usm_v(l)%building_type_name(m) = building_type_name(building_type)
4052!
4053!--           Initialize relatvie wall- (0), green- (1) and window (2) fractions
4054              surf_usm_v(l)%frac(ind_veg_wall,m)   = building_pars(ind_wall_frac,building_type)   
4055              surf_usm_v(l)%frac(ind_pav_green,m)  = building_pars(ind_green_frac_w,building_type) 
4056              surf_usm_v(l)%frac(ind_wat_win,m)    = building_pars(ind_win_frac,building_type) 
4057              surf_usm_v(l)%lai(m)                 = building_pars(ind_lai_w,building_type) 
4058
4059              surf_usm_v(l)%rho_c_wall(nzb_wall,m)   = building_pars(ind_hc1,building_type) 
4060              surf_usm_v(l)%rho_c_wall(nzb_wall+1,m) = building_pars(ind_hc1,building_type)
4061              surf_usm_v(l)%rho_c_wall(nzb_wall+2,m) = building_pars(ind_hc2,building_type)
4062              surf_usm_v(l)%rho_c_wall(nzb_wall+3,m) = building_pars(ind_hc3,building_type)   
4063             
4064              surf_usm_v(l)%rho_c_green(nzb_wall,m)   = rho_c_soil !building_pars(ind_hc1,building_type) 
4065              surf_usm_v(l)%rho_c_green(nzb_wall+1,m) = rho_c_soil !building_pars(ind_hc1,building_type)
4066              surf_usm_v(l)%rho_c_green(nzb_wall+2,m) = rho_c_soil !building_pars(ind_hc2,building_type)
4067              surf_usm_v(l)%rho_c_green(nzb_wall+3,m) = rho_c_soil !building_pars(ind_hc3,building_type)   
4068             
4069              surf_usm_v(l)%rho_c_window(nzb_wall,m)   = building_pars(ind_hc1_win,building_type) 
4070              surf_usm_v(l)%rho_c_window(nzb_wall+1,m) = building_pars(ind_hc1_win,building_type)
4071              surf_usm_v(l)%rho_c_window(nzb_wall+2,m) = building_pars(ind_hc2_win,building_type)
4072              surf_usm_v(l)%rho_c_window(nzb_wall+3,m) = building_pars(ind_hc3_win,building_type)   
4073
4074              surf_usm_v(l)%lambda_h(nzb_wall,m)   = building_pars(ind_tc1,building_type) 
4075              surf_usm_v(l)%lambda_h(nzb_wall+1,m) = building_pars(ind_tc1,building_type) 
4076              surf_usm_v(l)%lambda_h(nzb_wall+2,m) = building_pars(ind_tc2,building_type)
4077              surf_usm_v(l)%lambda_h(nzb_wall+3,m) = building_pars(ind_tc3,building_type)   
4078             
4079              surf_usm_v(l)%lambda_h_green(nzb_wall,m)   = lambda_h_green_sm !building_pars(ind_tc1,building_type) 
4080              surf_usm_v(l)%lambda_h_green(nzb_wall+1,m) = lambda_h_green_sm !building_pars(ind_tc1,building_type)
4081              surf_usm_v(l)%lambda_h_green(nzb_wall+2,m) = lambda_h_green_sm !building_pars(ind_tc2,building_type)
4082              surf_usm_v(l)%lambda_h_green(nzb_wall+3,m) = lambda_h_green_sm !building_pars(ind_tc3,building_type)   
4083
4084              surf_usm_v(l)%lambda_h_window(nzb_wall,m)   = building_pars(ind_tc1_win,building_type) 
4085              surf_usm_v(l)%lambda_h_window(nzb_wall+1,m) = building_pars(ind_tc1_win,building_type) 
4086              surf_usm_v(l)%lambda_h_window(nzb_wall+2,m) = building_pars(ind_tc2_win,building_type)
4087              surf_usm_v(l)%lambda_h_window(nzb_wall+3,m) = building_pars(ind_tc3_win,building_type)   
4088
4089              surf_usm_v(l)%target_temp_summer(m)  = building_pars(ind_indoor_target_temp_summer,building_type)   
4090              surf_usm_v(l)%target_temp_winter(m)  = building_pars(ind_indoor_target_temp_winter,building_type)   
4091!
4092!--           emissivity of wall-, green- and window fraction
4093              surf_usm_v(l)%emissivity(ind_veg_wall,m)  = building_pars(ind_emis_wall,building_type)
4094              surf_usm_v(l)%emissivity(ind_pav_green,m) = building_pars(ind_emis_green,building_type)
4095              surf_usm_v(l)%emissivity(ind_wat_win,m)   = building_pars(ind_emis_win,building_type)
4096
4097              surf_usm_v(l)%transmissivity(m)      = building_pars(ind_trans,building_type)
4098
4099              surf_usm_v(l)%z0(m)                  = building_pars(ind_z0,building_type)
4100              surf_usm_v(l)%z0h(m)                 = building_pars(ind_z0qh,building_type)
4101              surf_usm_v(l)%z0q(m)                 = building_pars(ind_z0qh,building_type)
4102
4103              surf_usm_v(l)%albedo_type(ind_veg_wall,m)  = INT( building_pars(ind_alb_wall,building_type) )
4104              surf_usm_v(l)%albedo_type(ind_pav_green,m) = INT( building_pars(ind_alb_green,building_type) )
4105              surf_usm_v(l)%albedo_type(ind_wat_win,m)   = INT( building_pars(ind_alb_win,building_type) )
4106
4107              surf_usm_v(l)%zw(nzb_wall,m)         = building_pars(ind_thick_1,building_type)
4108              surf_usm_v(l)%zw(nzb_wall+1,m)       = building_pars(ind_thick_2,building_type)
4109              surf_usm_v(l)%zw(nzb_wall+2,m)       = building_pars(ind_thick_3,building_type)
4110              surf_usm_v(l)%zw(nzb_wall+3,m)       = building_pars(ind_thick_4,building_type)
4111             
4112              surf_usm_v(l)%zw_green(nzb_wall,m)         = building_pars(ind_thick_1,building_type)
4113              surf_usm_v(l)%zw_green(nzb_wall+1,m)       = building_pars(ind_thick_2,building_type)
4114              surf_usm_v(l)%zw_green(nzb_wall+2,m)       = building_pars(ind_thick_3,building_type)
4115              surf_usm_v(l)%zw_green(nzb_wall+3,m)       = building_pars(ind_thick_4,building_type)
4116
4117              surf_usm_v(l)%zw_window(nzb_wall,m)         = building_pars(ind_thick_1_win,building_type)
4118              surf_usm_v(l)%zw_window(nzb_wall+1,m)       = building_pars(ind_thick_2_win,building_type)
4119              surf_usm_v(l)%zw_window(nzb_wall+2,m)       = building_pars(ind_thick_3_win,building_type)
4120              surf_usm_v(l)%zw_window(nzb_wall+3,m)       = building_pars(ind_thick_4_win,building_type)
4121
4122              surf_usm_v(l)%c_surface(m)           = building_pars(ind_c_surface,building_type) 
4123              surf_usm_v(l)%lambda_surf(m)         = building_pars(ind_lambda_surf,building_type)
4124              surf_usm_v(l)%c_surface_green(m)     = building_pars(ind_c_surface_green,building_type) 
4125              surf_usm_v(l)%lambda_surf_green(m)   = building_pars(ind_lambda_surf_green,building_type)
4126              surf_usm_v(l)%c_surface_window(m)    = building_pars(ind_c_surface_win,building_type) 
4127              surf_usm_v(l)%lambda_surf_window(m)  = building_pars(ind_lambda_surf_win,building_type)
4128
4129           ENDDO
4130        ENDDO
4131!
4132!--     Level 2 - initialization via building type read from file
4133        IF ( building_type_f%from_file )  THEN
4134           DO  m = 1, surf_usm_h%ns
4135              i = surf_usm_h%i(m)
4136              j = surf_usm_h%j(m)
4137!
4138!--           For the moment, limit building type to 6 (to overcome errors in input file).
4139              st = building_type_f%var(j,i)
4140              IF ( st /= building_type_f%fill )  THEN
4141
4142!
4143!--              In order to distinguish between ground floor level and
4144!--              above-ground-floor level surfaces, set input indices.
4145
4146                 ind_green_frac_r = MERGE( ind_green_frac_r_gfl, ind_green_frac_r_agfl, &
4147                                           surf_usm_h%ground_level(m) )
4148                 ind_lai_r        = MERGE( ind_lai_r_gfl,        ind_lai_r_agfl,        &
4149                                           surf_usm_h%ground_level(m) )
4150                 ind_z0           = MERGE( ind_z0_gfl,           ind_z0_agfl,           &
4151                                           surf_usm_h%ground_level(m) )
4152                 ind_z0qh         = MERGE( ind_z0qh_gfl,         ind_z0qh_agfl,         &
4153                                           surf_usm_h%ground_level(m) )
4154!
4155!--              Store building type and its name on each surface element
4156                 surf_usm_h%building_type(m)      = st
4157                 surf_usm_h%building_type_name(m) = building_type_name(st)
4158!
4159!--              Initialize relatvie wall- (0), green- (1) and window (2) fractions
4160                 surf_usm_h%frac(ind_veg_wall,m)  = building_pars(ind_wall_frac_r,st)   
4161                 surf_usm_h%frac(ind_pav_green,m) = building_pars(ind_green_frac_r,st) 
4162                 surf_usm_h%frac(ind_wat_win,m)   = building_pars(ind_win_frac_r,st) 
4163                 surf_usm_h%lai(m)                = building_pars(ind_lai_r,st) 
4164
4165                 surf_usm_h%rho_c_wall(nzb_wall,m)   = building_pars(ind_hc1_wall_r,st) 
4166                 surf_usm_h%rho_c_wall(nzb_wall+1,m) = building_pars(ind_hc1_wall_r,st)
4167                 surf_usm_h%rho_c_wall(nzb_wall+2,m) = building_pars(ind_hc2_wall_r,st)
4168                 surf_usm_h%rho_c_wall(nzb_wall+3,m) = building_pars(ind_hc3_wall_r,st)   
4169                 surf_usm_h%lambda_h(nzb_wall,m)   = building_pars(ind_tc1_wall_r,st) 
4170                 surf_usm_h%lambda_h(nzb_wall+1,m) = building_pars(ind_tc1_wall_r,st) 
4171                 surf_usm_h%lambda_h(nzb_wall+2,m) = building_pars(ind_tc2_wall_r,st)
4172                 surf_usm_h%lambda_h(nzb_wall+3,m) = building_pars(ind_tc3_wall_r,st)   
4173                 
4174                 surf_usm_h%rho_c_green(nzb_wall,m)   = rho_c_soil !building_pars(ind_hc1_wall_r,st) 
4175                 surf_usm_h%rho_c_green(nzb_wall+1,m) = rho_c_soil !building_pars(ind_hc1_wall_r,st)
4176                 surf_usm_h%rho_c_green(nzb_wall+2,m) = rho_c_soil !building_pars(ind_hc2_wall_r,st)
4177                 surf_usm_h%rho_c_green(nzb_wall+3,m) = rho_c_soil !building_pars(ind_hc3_wall_r,st)   
4178                 surf_usm_h%lambda_h_green(nzb_wall,m)   = lambda_h_green_sm !building_pars(ind_tc1_wall_r,st) 
4179                 surf_usm_h%lambda_h_green(nzb_wall+1,m) = lambda_h_green_sm !building_pars(ind_tc1_wall_r,st)
4180                 surf_usm_h%lambda_h_green(nzb_wall+2,m) = lambda_h_green_sm !building_pars(ind_tc2_wall_r,st)
4181                 surf_usm_h%lambda_h_green(nzb_wall+3,m) = lambda_h_green_sm !building_pars(ind_tc3_wall_r,st)   
4182               
4183                 surf_usm_h%rho_c_window(nzb_wall,m)   = building_pars(ind_hc1_win_r,st) 
4184                 surf_usm_h%rho_c_window(nzb_wall+1,m) = building_pars(ind_hc1_win_r,st)
4185                 surf_usm_h%rho_c_window(nzb_wall+2,m) = building_pars(ind_hc2_win_r,st)
4186                 surf_usm_h%rho_c_window(nzb_wall+3,m) = building_pars(ind_hc3_win_r,st)   
4187                 surf_usm_h%lambda_h_window(nzb_wall,m)   = building_pars(ind_tc1_win_r,st) 
4188                 surf_usm_h%lambda_h_window(nzb_wall+1,m) = building_pars(ind_tc1_win_r,st) 
4189                 surf_usm_h%lambda_h_window(nzb_wall+2,m) = building_pars(ind_tc2_win_r,st)
4190                 surf_usm_h%lambda_h_window(nzb_wall+3,m) = building_pars(ind_tc3_win_r,st)   
4191
4192                 surf_usm_h%target_temp_summer(m)  = building_pars(ind_indoor_target_temp_summer,st)   
4193                 surf_usm_h%target_temp_winter(m)  = building_pars(ind_indoor_target_temp_winter,st)   
4194!
4195!--              emissivity of wall-, green- and window fraction
4196                 surf_usm_h%emissivity(ind_veg_wall,m)  = building_pars(ind_emis_wall_r,st)
4197                 surf_usm_h%emissivity(ind_pav_green,m) = building_pars(ind_emis_green_r,st)
4198                 surf_usm_h%emissivity(ind_wat_win,m)   = building_pars(ind_emis_win_r,st)
4199
4200                 surf_usm_h%transmissivity(m)      = building_pars(ind_trans_r,st)
4201
4202                 surf_usm_h%z0(m)                  = building_pars(ind_z0,st)
4203                 surf_usm_h%z0h(m)                 = building_pars(ind_z0qh,st)
4204                 surf_usm_h%z0q(m)                 = building_pars(ind_z0qh,st)
4205!
4206!--              albedo type for wall fraction, green fraction, window fraction
4207                 surf_usm_h%albedo_type(ind_veg_wall,m)  = INT( building_pars(ind_alb_wall_r,st) )
4208                 surf_usm_h%albedo_type(ind_pav_green,m) = INT( building_pars(ind_alb_green_r,st) )
4209                 surf_usm_h%albedo_type(ind_wat_win,m)   = INT( building_pars(ind_alb_win_r,st) )
4210
4211                 surf_usm_h%zw(nzb_wall,m)         = building_pars(ind_thick_1_wall_r,st)
4212                 surf_usm_h%zw(nzb_wall+1,m)       = building_pars(ind_thick_2_wall_r,st)
4213                 surf_usm_h%zw(nzb_wall+2,m)       = building_pars(ind_thick_3_wall_r,st)
4214                 surf_usm_h%zw(nzb_wall+3,m)       = building_pars(ind_thick_4_wall_r,st)
4215                 
4216                 surf_usm_h%zw_green(nzb_wall,m)         = building_pars(ind_thick_1_wall_r,st)
4217                 surf_usm_h%zw_green(nzb_wall+1,m)       = building_pars(ind_thick_2_wall_r,st)
4218                 surf_usm_h%zw_green(nzb_wall+2,m)       = building_pars(ind_thick_3_wall_r,st)
4219                 surf_usm_h%zw_green(nzb_wall+3,m)       = building_pars(ind_thick_4_wall_r,st)
4220
4221                 surf_usm_h%zw_window(nzb_wall,m)         = building_pars(ind_thick_1_win_r,st)
4222                 surf_usm_h%zw_window(nzb_wall+1,m)       = building_pars(ind_thick_2_win_r,st)
4223                 surf_usm_h%zw_window(nzb_wall+2,m)       = building_pars(ind_thick_3_win_r,st)
4224                 surf_usm_h%zw_window(nzb_wall+3,m)       = building_pars(ind_thick_4_win_r,st)
4225
4226                 surf_usm_h%c_surface(m)           = building_pars(ind_c_surface,st) 
4227                 surf_usm_h%lambda_surf(m)         = building_pars(ind_lambda_surf,st)
4228                 surf_usm_h%c_surface_green(m)     = building_pars(ind_c_surface_green,st) 
4229                 surf_usm_h%lambda_surf_green(m)   = building_pars(ind_lambda_surf_green,st)
4230                 surf_usm_h%c_surface_window(m)    = building_pars(ind_c_surface_win,st) 
4231                 surf_usm_h%lambda_surf_window(m)  = building_pars(ind_lambda_surf_win,st)
4232                 
4233                 surf_usm_h%green_type_roof(m)     = building_pars(ind_green_type_roof,st)
4234
4235              ENDIF
4236           ENDDO
4237
4238           DO  l = 0, 3
4239              DO  m = 1, surf_usm_v(l)%ns
4240                 i = surf_usm_v(l)%i(m) + surf_usm_v(l)%ioff
4241                 j = surf_usm_v(l)%j(m) + surf_usm_v(l)%joff
4242!
4243!--              For the moment, limit building type to 6 (to overcome errors in input file).
4244
4245                 st = building_type_f%var(j,i)
4246                 IF ( st /= building_type_f%fill )  THEN
4247
4248!
4249!--                 In order to distinguish between ground floor level and
4250!--                 above-ground-floor level surfaces, set input indices.
4251                    ind_alb_green    = MERGE( ind_alb_green_gfl,    ind_alb_green_agfl,    &
4252                                              surf_usm_v(l)%ground_level(m) )
4253                    ind_alb_wall     = MERGE( ind_alb_wall_gfl,     ind_alb_wall_agfl,     &
4254                                              surf_usm_v(l)%ground_level(m) )
4255                    ind_alb_win      = MERGE( ind_alb_win_gfl,      ind_alb_win_agfl,      &
4256                                              surf_usm_v(l)%ground_level(m) )
4257                    ind_wall_frac    = MERGE( ind_wall_frac_gfl,    ind_wall_frac_agfl,    &
4258                                              surf_usm_v(l)%ground_level(m) )
4259                    ind_win_frac     = MERGE( ind_win_frac_gfl,     ind_win_frac_agfl,     &
4260                                              surf_usm_v(l)%ground_level(m) )
4261                    ind_green_frac_w = MERGE( ind_green_frac_w_gfl, ind_green_frac_w_agfl, &
4262                                              surf_usm_v(l)%ground_level(m) )
4263                    ind_green_frac_r = MERGE( ind_green_frac_r_gfl, ind_green_frac_r_agfl, &
4264                                              surf_usm_v(l)%ground_level(m) )
4265                    ind_lai_r        = MERGE( ind_lai_r_gfl,        ind_lai_r_agfl,        &
4266                                              surf_usm_v(l)%ground_level(m) )
4267                    ind_lai_w        = MERGE( ind_lai_w_gfl,        ind_lai_w_agfl,        &
4268                                              surf_usm_v(l)%ground_level(m) )
4269                    ind_hc1          = MERGE( ind_hc1_gfl,          ind_hc1_agfl,          &
4270                                              surf_usm_v(l)%ground_level(m) )
4271                    ind_hc1_win      = MERGE( ind_hc1_win_gfl,      ind_hc1_win_agfl,      &
4272                                              surf_usm_v(l)%ground_level(m) )
4273                    ind_hc2          = MERGE( ind_hc2_gfl,          ind_hc2_agfl,          &
4274                                              surf_usm_v(l)%ground_level(m) )
4275                    ind_hc2_win      = MERGE( ind_hc2_win_gfl,      ind_hc2_win_agfl,      &
4276                                              surf_usm_v(l)%ground_level(m) )
4277                    ind_hc3          = MERGE( ind_hc3_gfl,          ind_hc3_agfl,          &
4278                                              surf_usm_v(l)%ground_level(m) )
4279                    ind_hc3_win      = MERGE( ind_hc3_win_gfl,      ind_hc3_win_agfl,      &
4280                                              surf_usm_v(l)%ground_level(m) )
4281                    ind_tc1          = MERGE( ind_tc1_gfl,          ind_tc1_agfl,          &
4282                                              surf_usm_v(l)%ground_level(m) )
4283                    ind_tc1_win      = MERGE( ind_tc1_win_gfl,      ind_tc1_win_agfl,      &
4284                                              surf_usm_v(l)%ground_level(m) )
4285                    ind_tc2          = MERGE( ind_tc2_gfl,          ind_tc2_agfl,          &
4286                                              surf_usm_v(l)%ground_level(m) )
4287                    ind_tc2_win      = MERGE( ind_tc2_win_gfl,      ind_tc2_win_agfl,      &
4288                                              surf_usm_v(l)%ground_level(m) )
4289                    ind_tc3          = MERGE( ind_tc3_gfl,          ind_tc3_agfl,          &
4290                                              surf_usm_v(l)%ground_level(m) )
4291                    ind_tc3_win      = MERGE( ind_tc3_win_gfl,      ind_tc3_win_agfl,      &
4292                                              surf_usm_v(l)%ground_level(m) )
4293                    ind_thick_1      = MERGE( ind_thick_1_gfl,      ind_thick_1_agfl,      &
4294                                              surf_usm_v(l)%ground_level(m) )
4295                    ind_thick_1_win  = MERGE( ind_thick_1_win_gfl,  ind_thick_1_win_agfl,  &
4296                                              surf_usm_v(l)%ground_level(m) )
4297                    ind_thick_2      = MERGE( ind_thick_2_gfl,      ind_thick_2_agfl,      &
4298                                              surf_usm_v(l)%ground_level(m) )
4299                    ind_thick_2_win  = MERGE( ind_thick_2_win_gfl,  ind_thick_2_win_agfl,  &
4300                                              surf_usm_v(l)%ground_level(m) )
4301                    ind_thick_3      = MERGE( ind_thick_3_gfl,      ind_thick_3_agfl,      &
4302                                              surf_usm_v(l)%ground_level(m) )
4303                    ind_thick_3_win  = MERGE( ind_thick_3_win_gfl,  ind_thick_3_win_agfl,  &
4304                                              surf_usm_v(l)%ground_level(m) )
4305                    ind_thick_4      = MERGE( ind_thick_4_gfl,      ind_thick_4_agfl,      &
4306                                              surf_usm_v(l)%ground_level(m) )
4307                    ind_thick_4_win  = MERGE( ind_thick_4_win_gfl,  ind_thick_4_win_agfl,  &
4308                                              surf_usm_v(l)%ground_level(m) )
4309                    ind_emis_wall    = MERGE( ind_emis_wall_gfl,    ind_emis_wall_agfl,    &
4310                                              surf_usm_v(l)%ground_level(m) )
4311                    ind_emis_green   = MERGE( ind_emis_green_gfl,   ind_emis_green_agfl,   &
4312                                              surf_usm_v(l)%ground_level(m) )
4313                    ind_emis_win     = MERGE( ind_emis_win_gfl,     ind_emis_win_agfl,     &
4314                                              surf_usm_v(l)%ground_level(m) )
4315                    ind_trans        = MERGE( ind_trans_gfl,       ind_trans_agfl,         &
4316                                            surf_usm_v(l)%ground_level(m) )
4317                    ind_z0           = MERGE( ind_z0_gfl,           ind_z0_agfl,           &
4318                                              surf_usm_v(l)%ground_level(m) )
4319                    ind_z0qh         = MERGE( ind_z0qh_gfl,         ind_z0qh_agfl,         &
4320                                              surf_usm_v(l)%ground_level(m) )
4321!
4322!--                 Store building type and its name on each surface element
4323                    surf_usm_v(l)%building_type(m)      = st
4324                    surf_usm_v(l)%building_type_name(m) = building_type_name(st)
4325!
4326!--                 Initialize relatvie wall- (0), green- (1) and window (2) fractions
4327                    surf_usm_v(l)%frac(ind_veg_wall,m)  = building_pars(ind_wall_frac,st)   
4328                    surf_usm_v(l)%frac(ind_pav_green,m) = building_pars(ind_green_frac_w,st) 
4329                    surf_usm_v(l)%frac(ind_wat_win,m)   = building_pars(ind_win_frac,st)   
4330                    surf_usm_v(l)%lai(m)                = building_pars(ind_lai_w,st) 
4331
4332                    surf_usm_v(l)%rho_c_wall(nzb_wall,m)   = building_pars(ind_hc1,st) 
4333                    surf_usm_v(l)%rho_c_wall(nzb_wall+1,m) = building_pars(ind_hc1,st)
4334                    surf_usm_v(l)%rho_c_wall(nzb_wall+2,m) = building_pars(ind_hc2,st)
4335                    surf_usm_v(l)%rho_c_wall(nzb_wall+3,m) = building_pars(ind_hc3,st)
4336                   
4337                    surf_usm_v(l)%rho_c_green(nzb_wall,m)   = rho_c_soil !building_pars(ind_hc1,st) 
4338                    surf_usm_v(l)%rho_c_green(nzb_wall+1,m) = rho_c_soil !building_pars(ind_hc1,st)
4339                    surf_usm_v(l)%rho_c_green(nzb_wall+2,m) = rho_c_soil !building_pars(ind_hc2,st)
4340                    surf_usm_v(l)%rho_c_green(nzb_wall+3,m) = rho_c_soil !building_pars(ind_hc3,st)
4341                   
4342                    surf_usm_v(l)%rho_c_window(nzb_wall,m)   = building_pars(ind_hc1_win,st) 
4343                    surf_usm_v(l)%rho_c_window(nzb_wall+1,m) = building_pars(ind_hc1_win,st)
4344                    surf_usm_v(l)%rho_c_window(nzb_wall+2,m) = building_pars(ind_hc2_win,st)
4345                    surf_usm_v(l)%rho_c_window(nzb_wall+3,m) = building_pars(ind_hc3_win,st)
4346
4347                    surf_usm_v(l)%lambda_h(nzb_wall,m)   = building_pars(ind_tc1,st) 
4348                    surf_usm_v(l)%lambda_h(nzb_wall+1,m) = building_pars(ind_tc1,st) 
4349                    surf_usm_v(l)%lambda_h(nzb_wall+2,m) = building_pars(ind_tc2,st)
4350                    surf_usm_v(l)%lambda_h(nzb_wall+3,m) = building_pars(ind_tc3,st) 
4351                   
4352                    surf_usm_v(l)%lambda_h_green(nzb_wall,m)   = lambda_h_green_sm !building_pars(ind_tc1,st) 
4353                    surf_usm_v(l)%lambda_h_green(nzb_wall+1,m) = lambda_h_green_sm !building_pars(ind_tc1,st)
4354                    surf_usm_v(l)%lambda_h_green(nzb_wall+2,m) = lambda_h_green_sm !building_pars(ind_tc2,st)
4355                    surf_usm_v(l)%lambda_h_green(nzb_wall+3,m) = lambda_h_green_sm !building_pars(ind_tc3,st)
4356                   
4357                    surf_usm_v(l)%lambda_h_window(nzb_wall,m)   = building_pars(ind_tc1_win,st) 
4358                    surf_usm_v(l)%lambda_h_window(nzb_wall+1,m) = building_pars(ind_tc1_win,st) 
4359                    surf_usm_v(l)%lambda_h_window(nzb_wall+2,m) = building_pars(ind_tc2_win,st)
4360                    surf_usm_v(l)%lambda_h_window(nzb_wall+3,m) = building_pars(ind_tc3_win,st) 
4361
4362                    surf_usm_v(l)%target_temp_summer(m)  = building_pars(ind_indoor_target_temp_summer,st)   
4363                    surf_usm_v(l)%target_temp_winter(m)  = building_pars(ind_indoor_target_temp_winter,st)   
4364!
4365!--                 emissivity of wall-, green- and window fraction
4366                    surf_usm_v(l)%emissivity(ind_veg_wall,m)  = building_pars(ind_emis_wall,st)
4367                    surf_usm_v(l)%emissivity(ind_pav_green,m) = building_pars(ind_emis_green,st)
4368                    surf_usm_v(l)%emissivity(ind_wat_win,m)   = building_pars(ind_emis_win,st)
4369
4370                    surf_usm_v(l)%transmissivity(m)      = building_pars(ind_trans,st)
4371
4372                    surf_usm_v(l)%z0(m)                  = building_pars(ind_z0,st)
4373                    surf_usm_v(l)%z0h(m)                 = building_pars(ind_z0qh,st)
4374                    surf_usm_v(l)%z0q(m)                 = building_pars(ind_z0qh,st)
4375
4376                    surf_usm_v(l)%albedo_type(ind_veg_wall,m)  = INT( building_pars(ind_alb_wall,st) )
4377                    surf_usm_v(l)%albedo_type(ind_pav_green,m) = INT( building_pars(ind_alb_green,st) )
4378                    surf_usm_v(l)%albedo_type(ind_wat_win,m)   = INT( building_pars(ind_alb_win,st) )
4379
4380                    surf_usm_v(l)%zw(nzb_wall,m)         = building_pars(ind_thick_1,st)
4381                    surf_usm_v(l)%zw(nzb_wall+1,m)       = building_pars(ind_thick_2,st)
4382                    surf_usm_v(l)%zw(nzb_wall+2,m)       = building_pars(ind_thick_3,st)
4383                    surf_usm_v(l)%zw(nzb_wall+3,m)       = building_pars(ind_thick_4,st)
4384                   
4385                    surf_usm_v(l)%zw_green(nzb_wall,m)         = building_pars(ind_thick_1,st)
4386                    surf_usm_v(l)%zw_green(nzb_wall+1,m)       = building_pars(ind_thick_2,st)
4387                    surf_usm_v(l)%zw_green(nzb_wall+2,m)       = building_pars(ind_thick_3,st)
4388                    surf_usm_v(l)%zw_green(nzb_wall+3,m)       = building_pars(ind_thick_4,st)
4389                   
4390                    surf_usm_v(l)%zw_window(nzb_wall,m)         = building_pars(ind_thick_1_win,st)
4391                    surf_usm_v(l)%zw_window(nzb_wall+1,m)       = building_pars(ind_thick_2_win,st)
4392                    surf_usm_v(l)%zw_window(nzb_wall+2,m)       = building_pars(ind_thick_3_win,st)
4393                    surf_usm_v(l)%zw_window(nzb_wall+3,m)       = building_pars(ind_thick_4_win,st)
4394
4395                    surf_usm_v(l)%c_surface(m)           = building_pars(ind_c_surface,st) 
4396                    surf_usm_v(l)%lambda_surf(m)         = building_pars(ind_lambda_surf,st) 
4397                    surf_usm_v(l)%c_surface_green(m)     = building_pars(ind_c_surface_green,st) 
4398                    surf_usm_v(l)%lambda_surf_green(m)   = building_pars(ind_lambda_surf_green,st) 
4399                    surf_usm_v(l)%c_surface_window(m)    = building_pars(ind_c_surface_win,st) 
4400                    surf_usm_v(l)%lambda_surf_window(m)  = building_pars(ind_lambda_surf_win,st) 
4401
4402
4403                 ENDIF
4404              ENDDO
4405           ENDDO
4406        ENDIF 
4407       
4408!
4409!--     Level 3 - initialization via building_pars read from file. Note, only
4410!--     variables that are also defined in the input-standard can be initialized
4411!--     via file. Other variables will be initialized on level 1 or 2.
4412        IF ( building_pars_f%from_file )  THEN
4413           DO  m = 1, surf_usm_h%ns
4414              i = surf_usm_h%i(m)
4415              j = surf_usm_h%j(m)
4416
4417!
4418!--           In order to distinguish between ground floor level and
4419!--           above-ground-floor level surfaces, set input indices.
4420              ind_wall_frac    = MERGE( ind_wall_frac_gfl,                     &
4421                                        ind_wall_frac_agfl,                    &
4422                                        surf_usm_h%ground_level(m) )
4423              ind_green_frac_r = MERGE( ind_green_frac_r_gfl,                  &
4424                                        ind_green_frac_r_agfl,                 &
4425                                        surf_usm_h%ground_level(m) )
4426              ind_win_frac     = MERGE( ind_win_frac_gfl,                      &
4427                                        ind_win_frac_agfl,                     &
4428                                        surf_usm_h%ground_level(m) )
4429              ind_lai_r        = MERGE( ind_lai_r_gfl,                         &
4430                                        ind_lai_r_agfl,                        &
4431                                        surf_usm_h%ground_level(m) )
4432              ind_z0           = MERGE( ind_z0_gfl,                            &
4433                                        ind_z0_agfl,                           &
4434                                        surf_usm_h%ground_level(m) )
4435              ind_z0qh         = MERGE( ind_z0qh_gfl,                          &
4436                                        ind_z0qh_agfl,                         &
4437                                        surf_usm_h%ground_level(m) )
4438              ind_hc1          = MERGE( ind_hc1_gfl,                           &
4439                                        ind_hc1_agfl,                          &
4440                                        surf_usm_h%ground_level(m) )
4441              ind_hc2          = MERGE( ind_hc2_gfl,                           &
4442                                        ind_hc2_agfl,                          &
4443                                        surf_usm_h%ground_level(m) )
4444              ind_hc3          = MERGE( ind_hc3_gfl,                           &
4445                                        ind_hc3_agfl,                          &
4446                                        surf_usm_h%ground_level(m) )
4447              ind_tc1          = MERGE( ind_tc1_gfl,                           &
4448                                        ind_tc1_agfl,                          &
4449                                        surf_usm_h%ground_level(m) )
4450              ind_tc2          = MERGE( ind_tc2_gfl,                           &
4451                                        ind_tc2_agfl,                          &
4452                                        surf_usm_h%ground_level(m) )
4453              ind_tc3          = MERGE( ind_tc3_gfl,                           &
4454                                        ind_tc3_agfl,                          &
4455                                        surf_usm_h%ground_level(m) )
4456              ind_emis_wall    = MERGE( ind_emis_wall_gfl,                     &
4457                                        ind_emis_wall_agfl,                    &
4458                                        surf_usm_h%ground_level(m) )
4459              ind_emis_green   = MERGE( ind_emis_green_gfl,                    &
4460                                        ind_emis_green_agfl,                   &
4461                                        surf_usm_h%ground_level(m) )
4462              ind_emis_win     = MERGE( ind_emis_win_gfl,                      &
4463                                        ind_emis_win_agfl,                     &
4464                                        surf_usm_h%ground_level(m) )
4465              ind_trans        = MERGE( ind_trans_gfl,                         &
4466                                        ind_trans_agfl,                        &
4467                                        surf_usm_h%ground_level(m) )
4468
4469!
4470!--           Initialize relatvie wall- (0), green- (1) and window (2) fractions
4471              IF ( building_pars_f%pars_xy(ind_wall_frac,j,i) /=               &
4472                   building_pars_f%fill )                                      &
4473                 surf_usm_h%frac(ind_veg_wall,m)  =                            &
4474                                    building_pars_f%pars_xy(ind_wall_frac,j,i)   
4475                 
4476              IF ( building_pars_f%pars_xy(ind_green_frac_r,j,i) /=            &         
4477                   building_pars_f%fill )                                      & 
4478                 surf_usm_h%frac(ind_pav_green,m) =                            &
4479                                    building_pars_f%pars_xy(ind_green_frac_r,j,i) 
4480                 
4481              IF ( building_pars_f%pars_xy(ind_win_frac,j,i) /=                &
4482                   building_pars_f%fill )                                      & 
4483                 surf_usm_h%frac(ind_wat_win,m)   =                            &
4484                                    building_pars_f%pars_xy(ind_win_frac,j,i)
4485 
4486              IF ( building_pars_f%pars_xy(ind_lai_r,j,i) /=                   &
4487                   building_pars_f%fill )                                      &
4488                 surf_usm_h%lai(m)  = building_pars_f%pars_xy(ind_lai_r,j,i)
4489
4490              IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=                     &
4491                   building_pars_f%fill )  THEN
4492                 surf_usm_h%rho_c_wall(nzb_wall,m)   =                         &
4493                                    building_pars_f%pars_xy(ind_hc1,j,i) 
4494                 surf_usm_h%rho_c_wall(nzb_wall+1,m) =                         &
4495                                    building_pars_f%pars_xy(ind_hc1,j,i)
4496              ENDIF
4497             
4498             
4499              IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=                     &
4500                   building_pars_f%fill )                                      &
4501                 surf_usm_h%rho_c_wall(nzb_wall+2,m) =                         &
4502                                    building_pars_f%pars_xy(ind_hc2,j,i)
4503                 
4504              IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=                     &
4505                   building_pars_f%fill )                                      &
4506                 surf_usm_h%rho_c_wall(nzb_wall+3,m) =                         &
4507                                    building_pars_f%pars_xy(ind_hc3,j,i)
4508                 
4509              IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=                     &
4510                   building_pars_f%fill )  THEN
4511                 surf_usm_h%rho_c_green(nzb_wall,m)   =                        &
4512                                    building_pars_f%pars_xy(ind_hc1,j,i) 
4513                 surf_usm_h%rho_c_green(nzb_wall+1,m) =                        &
4514                                    building_pars_f%pars_xy(ind_hc1,j,i)
4515              ENDIF
4516              IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=                     &
4517                   building_pars_f%fill )                                      &
4518                 surf_usm_h%rho_c_green(nzb_wall+2,m) =                        &
4519                                    building_pars_f%pars_xy(ind_hc2,j,i)
4520                 
4521              IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=                     &
4522                   building_pars_f%fill )                                      &
4523                 surf_usm_h%rho_c_green(nzb_wall+3,m) =                        &
4524                                    building_pars_f%pars_xy(ind_hc3,j,i)
4525                 
4526              IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=                     &
4527                   building_pars_f%fill )  THEN
4528                 surf_usm_h%rho_c_window(nzb_wall,m)   =                       &
4529                                    building_pars_f%pars_xy(ind_hc1,j,i) 
4530                 surf_usm_h%rho_c_window(nzb_wall+1,m) =                       &
4531                                    building_pars_f%pars_xy(ind_hc1,j,i)
4532              ENDIF
4533              IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=                     &
4534                   building_pars_f%fill )                                      &
4535                 surf_usm_h%rho_c_window(nzb_wall+2,m) =                       &
4536                                    building_pars_f%pars_xy(ind_hc2,j,i)
4537                 
4538              IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=                     &
4539                   building_pars_f%fill )                                      &
4540                 surf_usm_h%rho_c_window(nzb_wall+3,m) =                       &
4541                                    building_pars_f%pars_xy(ind_hc3,j,i)
4542
4543              IF ( building_pars_f%pars_xy(ind_tc1,j,i) /=                     &
4544                   building_pars_f%fill )  THEN
4545                 surf_usm_h%lambda_h(nzb_wall,m)   =                           &
4546                                    building_pars_f%pars_xy(ind_tc1,j,i)         
4547                 surf_usm_h%lambda_h(nzb_wall+1,m) =                           &
4548                                    building_pars_f%pars_xy(ind_tc1,j,i)       
4549              ENDIF
4550              IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=                     & 
4551                   building_pars_f%fill )                                      &
4552                 surf_usm_h%lambda_h(nzb_wall+2,m) =                           &
4553                                    building_pars_f%pars_xy(ind_tc2,j,i)
4554                 
4555              IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=                     &
4556                   building_pars_f%fill )                                      & 
4557                 surf_usm_h%lambda_h(nzb_wall+3,m) =                           &
4558                                    building_pars_f%pars_xy(ind_tc3,j,i)   
4559                 
4560              IF ( building_pars_f%pars_xy(ind_tc1,j,i) /=                     &
4561                   building_pars_f%fill )  THEN
4562                 surf_usm_h%lambda_h_green(nzb_wall,m)   =                     &
4563                                     building_pars_f%pars_xy(ind_tc1,j,i)         
4564                 surf_usm_h%lambda_h_green(nzb_wall+1,m) =                     &
4565                                     building_pars_f%pars_xy(ind_tc1,j,i)       
4566              ENDIF
4567              IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=                     & 
4568                   building_pars_f%fill )                                      &
4569                 surf_usm_h%lambda_h_green(nzb_wall+2,m) =                     &
4570                                    building_pars_f%pars_xy(ind_tc2,j,i)
4571                 
4572              IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=                     &       
4573                   building_pars_f%fill )                                      &
4574                 surf_usm_h%lambda_h_green(nzb_wall+3,m) =                     &
4575                                    building_pars_f%pars_xy(ind_tc3,j,i)   
4576                 
4577              IF ( building_pars_f%pars_xy(ind_tc1,j,i) /=                     &
4578                   building_pars_f%fill )  THEN
4579                 surf_usm_h%lambda_h_window(nzb_wall,m)   =                    &
4580                                     building_pars_f%pars_xy(ind_tc1,j,i)         
4581                 surf_usm_h%lambda_h_window(nzb_wall+1,m) =                    &
4582                                     building_pars_f%pars_xy(ind_tc1,j,i)       
4583              ENDIF
4584              IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=                     &     
4585                   building_pars_f%fill )                                      &
4586                 surf_usm_h%lambda_h_window(nzb_wall+2,m) =                    &
4587                                     building_pars_f%pars_xy(ind_tc2,j,i)
4588                 
4589              IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=                     &   
4590                   building_pars_f%fill )                                      &
4591                 surf_usm_h%lambda_h_window(nzb_wall+3,m) =                    &
4592                                    building_pars_f%pars_xy(ind_tc3,j,i)   
4593
4594              IF ( building_pars_f%pars_xy(ind_indoor_target_temp_summer,j,i) /=&           
4595                   building_pars_f%fill )                                      & 
4596                 surf_usm_h%target_temp_summer(m)  =                           &
4597                      building_pars_f%pars_xy(ind_indoor_target_temp_summer,j,i)   
4598              IF ( building_pars_f%pars_xy(ind_indoor_target_temp_winter,j,i) /=&           
4599                   building_pars_f%fill )                                      & 
4600                 surf_usm_h%target_temp_winter(m)  =                           &
4601                      building_pars_f%pars_xy(ind_indoor_target_temp_winter,j,i)   
4602
4603              IF ( building_pars_f%pars_xy(ind_emis_wall,j,i) /=               &   
4604                   building_pars_f%fill )                                      &
4605                 surf_usm_h%emissivity(ind_veg_wall,m)  =                      &
4606                                    building_pars_f%pars_xy(ind_emis_wall,j,i)
4607                 
4608              IF ( building_pars_f%pars_xy(ind_emis_green,j,i) /=              &           
4609                   building_pars_f%fill )                                      &
4610                 surf_usm_h%emissivity(ind_pav_green,m) =                      &
4611                                     building_pars_f%pars_xy(ind_emis_green,j,i)
4612                 
4613              IF ( building_pars_f%pars_xy(ind_emis_win,j,i) /=                & 
4614                   building_pars_f%fill )                                      &
4615                 surf_usm_h%emissivity(ind_wat_win,m)   =                      &
4616                                     building_pars_f%pars_xy(ind_emis_win,j,i)
4617                 
4618              IF ( building_pars_f%pars_xy(ind_trans,j,i) /=                   &   
4619                   building_pars_f%fill )                                      &
4620                 surf_usm_h%transmissivity(m) =                                &
4621                                    building_pars_f%pars_xy(ind_trans,j,i)
4622
4623              IF ( building_pars_f%pars_xy(ind_z0,j,i) /=                      &         
4624                   building_pars_f%fill )                                      &
4625                 surf_usm_h%z0(m) = building_pars_f%pars_xy(ind_z0,j,i)
4626                 
4627              IF ( building_pars_f%pars_xy(ind_z0qh,j,i) /=                    &           
4628                   building_pars_f%fill )                                      &
4629                 surf_usm_h%z0h(m) = building_pars_f%pars_xy(ind_z0qh,j,i)
4630              IF ( building_pars_f%pars_xy(ind_z0qh,j,i) /=                    &           
4631                   building_pars_f%fill )                                      &
4632                 surf_usm_h%z0q(m) = building_pars_f%pars_xy(ind_z0qh,j,i)
4633
4634              IF ( building_pars_f%pars_xy(ind_alb_wall_agfl,j,i) /=           &         
4635                   building_pars_f%fill )                                      & 
4636                 surf_usm_h%albedo_type(ind_veg_wall,m)  =                     &
4637                                 building_pars_f%pars_xy(ind_alb_wall_agfl,j,i)
4638                 
4639              IF ( building_pars_f%pars_xy(ind_alb_green_agfl,j,i) /=          &           
4640                   building_pars_f%fill )                                      &
4641                 surf_usm_h%albedo_type(ind_pav_green,m) =                     &
4642                                building_pars_f%pars_xy(ind_alb_green_agfl,j,i)
4643              IF ( building_pars_f%pars_xy(ind_alb_win_agfl,j,i) /=            &         
4644                   building_pars_f%fill )                                      &
4645                 surf_usm_h%albedo_type(ind_wat_win,m)   =                     &
4646                                   building_pars_f%pars_xy(ind_alb_win_agfl,j,i)
4647
4648              IF ( building_pars_f%pars_xy(ind_thick_1_agfl,j,i) /=            &         
4649                   building_pars_f%fill )                                      & 
4650                 surf_usm_h%zw(nzb_wall,m) =                                   &
4651                                  building_pars_f%pars_xy(ind_thick_1_agfl,j,i)
4652                 
4653              IF ( building_pars_f%pars_xy(ind_thick_2_agfl,j,i) /=            &         
4654                   building_pars_f%fill )                                      &
4655                 surf_usm_h%zw(nzb_wall+1,m) =                                 &
4656                                  building_pars_f%pars_xy(ind_thick_2_agfl,j,i)
4657                 
4658              IF ( building_pars_f%pars_xy(ind_thick_3_agfl,j,i) /=            &         
4659                   building_pars_f%fill )                                      &
4660                 surf_usm_h%zw(nzb_wall+2,m) =                                 &
4661                                  building_pars_f%pars_xy(ind_thick_3_agfl,j,i)
4662                 
4663                 
4664              IF ( building_pars_f%pars_xy(ind_thick_4_agfl,j,i) /=            &         
4665                   building_pars_f%fill )                                      & 
4666                 surf_usm_h%zw(nzb_wall+3,m) =                                 &
4667                                  building_pars_f%pars_xy(ind_thick_4_agfl,j,i)
4668                 
4669              IF ( building_pars_f%pars_xy(ind_thick_1_agfl,j,i) /=            &           
4670                   building_pars_f%fill )                                      &
4671                 surf_usm_h%zw_green(nzb_wall,m) =                             &
4672                                  building_pars_f%pars_xy(ind_thick_1_agfl,j,i)
4673                 
4674              IF ( building_pars_f%pars_xy(ind_thick_2_agfl,j,i) /=            &         
4675                   building_pars_f%fill )                                      &
4676                 surf_usm_h%zw_green(nzb_wall+1,m) =                           &
4677                                   building_pars_f%pars_xy(ind_thick_2_agfl,j,i)
4678                 
4679              IF ( building_pars_f%pars_xy(ind_thick_3_agfl,j,i) /=            &         
4680                   building_pars_f%fill )                                      & 
4681                 surf_usm_h%zw_green(nzb_wall+2,m) =                           &
4682                                   building_pars_f%pars_xy(ind_thick_3_agfl,j,i)
4683                 
4684              IF ( building_pars_f%pars_xy(ind_thick_4_agfl,j,i) /=            &         
4685                   building_pars_f%fill )                                      &
4686                 surf_usm_h%zw_green(nzb_wall+3,m) =                           &
4687                                   building_pars_f%pars_xy(ind_thick_4_agfl,j,i)
4688
4689              IF ( building_pars_f%pars_xy(ind_c_surface,j,i) /=               &       
4690                   building_pars_f%fill )                                      & 
4691                 surf_usm_h%c_surface(m) =                                     &
4692                                    building_pars_f%pars_xy(ind_c_surface,j,i)
4693                 
4694              IF ( building_pars_f%pars_xy(ind_lambda_surf,j,i) /=             &       
4695                   building_pars_f%fill )                                      &
4696                 surf_usm_h%lambda_surf(m) =                                   &
4697                                    building_pars_f%pars_xy(ind_lambda_surf,j,i)
4698             
4699           ENDDO
4700
4701
4702
4703           DO  l = 0, 3
4704              DO  m = 1, surf_usm_v(l)%ns
4705                 i = surf_usm_v(l)%i(m) + surf_usm_v(l)%ioff
4706                 j = surf_usm_v(l)%j(m) + surf_usm_v(l)%joff
4707               
4708!
4709!--                 In order to distinguish between ground floor level and
4710!--                 above-ground-floor level surfaces, set input indices.
4711                    ind_wall_frac    = MERGE( ind_wall_frac_gfl,               &
4712                                              ind_wall_frac_agfl,              &
4713                                              surf_usm_v(l)%ground_level(m) )
4714                    ind_green_frac_w = MERGE( ind_green_frac_w_gfl,            &
4715                                              ind_green_frac_w_agfl,           &
4716                                              surf_usm_v(l)%ground_level(m) )
4717                    ind_win_frac     = MERGE( ind_win_frac_gfl,                &
4718                                              ind_win_frac_agfl,               &
4719                                              surf_usm_v(l)%ground_level(m) )
4720                    ind_lai_w        = MERGE( ind_lai_w_gfl,                   &
4721                                              ind_lai_w_agfl,                  &
4722                                              surf_usm_v(l)%ground_level(m) )
4723                    ind_z0           = MERGE( ind_z0_gfl,                      &
4724                                              ind_z0_agfl,                     &
4725                                              surf_usm_v(l)%ground_level(m) )
4726                    ind_z0qh         = MERGE( ind_z0qh_gfl,                    &
4727                                              ind_z0qh_agfl,                   &
4728                                              surf_usm_v(l)%ground_level(m) )
4729                    ind_hc1          = MERGE( ind_hc1_gfl,                     &
4730                                              ind_hc1_agfl,                    &
4731                                              surf_usm_v(l)%ground_level(m) )
4732                    ind_hc2          = MERGE( ind_hc2_gfl,                     &
4733                                              ind_hc2_agfl,                    &
4734                                              surf_usm_v(l)%ground_level(m) )
4735                    ind_hc3          = MERGE( ind_hc3_gfl,                     &
4736                                              ind_hc3_agfl,                    &
4737                                              surf_usm_v(l)%ground_level(m) )
4738                    ind_tc1          = MERGE( ind_tc1_gfl,                     &
4739                                              ind_tc1_agfl,                    &
4740                                              surf_usm_v(l)%ground_level(m) )
4741                    ind_tc2          = MERGE( ind_tc2_gfl,                     &
4742                                              ind_tc2_agfl,                    &
4743                                              surf_usm_v(l)%ground_level(m) )
4744                    ind_tc3          = MERGE( ind_tc3_gfl,                     &
4745                                              ind_tc3_agfl,                    &
4746                                              surf_usm_v(l)%ground_level(m) )
4747                    ind_emis_wall    = MERGE( ind_emis_wall_gfl,               &
4748                                              ind_emis_wall_agfl,              &
4749                                              surf_usm_v(l)%ground_level(m) )
4750                    ind_emis_green   = MERGE( ind_emis_green_gfl,              &
4751                                              ind_emis_green_agfl,             &
4752                                              surf_usm_v(l)%ground_level(m) )
4753                    ind_emis_win     = MERGE( ind_emis_win_gfl,                &
4754                                              ind_emis_win_agfl,               &
4755                                              surf_usm_v(l)%ground_level(m) )
4756                    ind_trans        = MERGE( ind_trans_gfl,                   &
4757                                              ind_trans_agfl,                  &
4758                                              surf_usm_v(l)%ground_level(m) )
4759                   
4760!                   
4761!--                 Initialize relatvie wall- (0), green- (1) and window (2) fractions
4762                    IF ( building_pars_f%pars_xy(ind_wall_frac,j,i) /=         &
4763                         building_pars_f%fill )                                &
4764                       surf_usm_v(l)%frac(ind_veg_wall,m)  =                   &
4765                                          building_pars_f%pars_xy(ind_wall_frac,j,i)   
4766                       
4767                    IF ( building_pars_f%pars_xy(ind_green_frac_w,j,i) /=      &         
4768                         building_pars_f%fill )                                & 
4769                       surf_usm_v(l)%frac(ind_pav_green,m) =                   &
4770                                  building_pars_f%pars_xy(ind_green_frac_w,j,i) 
4771                       
4772                    IF ( building_pars_f%pars_xy(ind_win_frac,j,i) /=          &
4773                         building_pars_f%fill )                                & 
4774                       surf_usm_v(l)%frac(ind_wat_win,m)   =                   &
4775                                       building_pars_f%pars_xy(ind_win_frac,j,i)
4776                   
4777                    IF ( building_pars_f%pars_xy(ind_lai_w,j,i) /=             &
4778                         building_pars_f%fill )                                &
4779                       surf_usm_v(l)%lai(m)  =                                 &
4780                                       building_pars_f%pars_xy(ind_lai_w,j,i)
4781                   
4782                    IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=               &
4783                         building_pars_f%fill )  THEN
4784                       surf_usm_v(l)%rho_c_wall(nzb_wall,m)   =                &
4785                                          building_pars_f%pars_xy(ind_hc1,j,i) 
4786                       surf_usm_v(l)%rho_c_wall(nzb_wall+1,m) =                &
4787                                          building_pars_f%pars_xy(ind_hc1,j,i)
4788                    ENDIF
4789                   
4790                   
4791                    IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=               &
4792                         building_pars_f%fill )                                &
4793                       surf_usm_v(l)%rho_c_wall(nzb_wall+2,m) =                &
4794                                          building_pars_f%pars_xy(ind_hc2,j,i)
4795                       
4796                    IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=               &         
4797                         building_pars_f%fill )                                &
4798                       surf_usm_v(l)%rho_c_wall(nzb_wall+3,m) =                &
4799                                          building_pars_f%pars_xy(ind_hc3,j,i)
4800                       
4801                    IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=               &
4802                         building_pars_f%fill )  THEN
4803                       surf_usm_v(l)%rho_c_green(nzb_wall,m)   =               &
4804                                          building_pars_f%pars_xy(ind_hc1,j,i) 
4805                       surf_usm_v(l)%rho_c_green(nzb_wall+1,m) =               &
4806                                          building_pars_f%pars_xy(ind_hc1,j,i)
4807                    ENDIF
4808                    IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=               &
4809                         building_pars_f%fill )                                &
4810                       surf_usm_v(l)%rho_c_green(nzb_wall+2,m) =               &
4811                                          building_pars_f%pars_xy(ind_hc2,j,i)
4812                       
4813                    IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=               &
4814                         building_pars_f%fill )                                &
4815                       surf_usm_v(l)%rho_c_green(nzb_wall+3,m) =               &
4816                                          building_pars_f%pars_xy(ind_hc3,j,i)
4817                       
4818                    IF ( building_pars_f%pars_xy(ind_hc1,j,i) /=               &
4819                         building_pars_f%fill )  THEN
4820                       surf_usm_v(l)%rho_c_window(nzb_wall,m)   =              &
4821                                          building_pars_f%pars_xy(ind_hc1,j,i) 
4822                       surf_usm_v(l)%rho_c_window(nzb_wall+1,m) =              &
4823                                          building_pars_f%pars_xy(ind_hc1,j,i)
4824                    ENDIF
4825                    IF ( building_pars_f%pars_xy(ind_hc2,j,i) /=               &
4826                         building_pars_f%fill )                                &
4827                       surf_usm_v(l)%rho_c_window(nzb_wall+2,m) =              &
4828                                          building_pars_f%pars_xy(ind_hc2,j,i)
4829                       
4830                    IF ( building_pars_f%pars_xy(ind_hc3,j,i) /=               &
4831                         building_pars_f%fill )                                &
4832                       surf_usm_v(l)%rho_c_window(nzb_wall+3,m) =              &
4833                                          building_pars_f%pars_xy(ind_hc3,j,i)
4834                   
4835                    IF ( building_pars_f%pars_xy(ind_tc1,j,i) /=               &
4836                         building_pars_f%fill )  THEN
4837                       surf_usm_v(l)%lambda_h(nzb_wall,m)   =                  &
4838                                          building_pars_f%pars_xy(ind_tc1,j,i)   
4839                       surf_usm_v(l)%lambda_h(nzb_wall+1,m) =                  &
4840                                          building_pars_f%pars_xy(ind_tc1,j,i) 
4841                    ENDIF
4842                    IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=               & 
4843                         building_pars_f%fill )                                &
4844                       surf_usm_v(l)%lambda_h(nzb_wall+2,m) =                  &
4845                                          building_pars_f%pars_xy(ind_tc2,j,i)
4846                       
4847                    IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=               &
4848                         building_pars_f%fill )                                & 
4849                       surf_usm_v(l)%lambda_h(nzb_wall+3,m) =                  &
4850                                          building_pars_f%pars_xy(ind_tc3,j,i) 
4851                       
4852                    IF ( building_pars_f%pars_xy(ind_tc1,j,i) /=               &
4853                         building_pars_f%fill )  THEN
4854                       surf_usm_v(l)%lambda_h_green(nzb_wall,m)   =            &
4855                                           building_pars_f%pars_xy(ind_tc1,j,i)   
4856                       surf_usm_v(l)%lambda_h_green(nzb_wall+1,m) =            &
4857                                           building_pars_f%pars_xy(ind_tc1,j,i) 
4858                    ENDIF
4859                    IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=               & 
4860                         building_pars_f%fill )                                &
4861                       surf_usm_v(l)%lambda_h_green(nzb_wall+2,m) =            &
4862                                          building_pars_f%pars_xy(ind_tc2,j,i)
4863                       
4864                    IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=               &       
4865                         building_pars_f%fill )                                &
4866                       surf_usm_v(l)%lambda_h_green(nzb_wall+3,m) =            &
4867                                          building_pars_f%pars_xy(ind_tc3,j,i) 
4868                       
4869                    IF ( building_pars_f%pars_xy(ind_tc1,j,i) /=         &
4870                         building_pars_f%fill )  THEN
4871                       surf_usm_v(l)%lambda_h_window(nzb_wall,m)   =           &
4872                                     building_pars_f%pars_xy(ind_tc1,j,i)         
4873                       surf_usm_v(l)%lambda_h_window(nzb_wall+1,m) =           &
4874                                     building_pars_f%pars_xy(ind_tc1,j,i)       
4875                    ENDIF
4876                    IF ( building_pars_f%pars_xy(ind_tc2,j,i) /=               &     
4877                         building_pars_f%fill )                                &
4878                       surf_usm_v(l)%lambda_h_window(nzb_wall+2,m) =           &
4879                                           building_pars_f%pars_xy(ind_tc2,j,i)
4880                       
4881                    IF ( building_pars_f%pars_xy(ind_tc3,j,i) /=               &   
4882                         building_pars_f%fill )                                &
4883                       surf_usm_v(l)%lambda_h_window(nzb_wall+3,m) =           &
4884                                          building_pars_f%pars_xy(ind_tc3,j,i)   
4885                   
4886                    IF ( building_pars_f%pars_xy(ind_indoor_target_temp_summer,j,i) /=&           
4887                         building_pars_f%fill )                                & 
4888                       surf_usm_v(l)%target_temp_summer(m)  =                  &
4889                            building_pars_f%pars_xy(ind_indoor_target_temp_summer,j,i)   
4890                    IF ( building_pars_f%pars_xy(ind_indoor_target_temp_winter,j,i) /=&           
4891                         building_pars_f%fill )                                & 
4892                       surf_usm_v(l)%target_temp_winter(m)  =                  &
4893                            building_pars_f%pars_xy(ind_indoor_target_temp_winter,j,i)   
4894                   
4895                    IF ( building_pars_f%pars_xy(ind_emis_wall,j,i) /=         &   
4896                         building_pars_f%fill )                                &
4897                       surf_usm_v(l)%emissivity(ind_veg_wall,m)  =             &
4898                                      building_pars_f%pars_xy(ind_emis_wall,j,i)
4899                       
4900                    IF ( building_pars_f%pars_xy(ind_emis_green,j,i) /=        &           
4901                         building_pars_f%fill )                                &
4902                       surf_usm_v(l)%emissivity(ind_pav_green,m) =             &
4903                                      building_pars_f%pars_xy(ind_emis_green,j,i)
4904                       
4905                    IF ( building_pars_f%pars_xy(ind_emis_win,j,i) /=          & 
4906                         building_pars_f%fill )                                &
4907                       surf_usm_v(l)%emissivity(ind_wat_win,m)   =             &
4908                                      building_pars_f%pars_xy(ind_emis_win,j,i)
4909                       
4910                    IF ( building_pars_f%pars_xy(ind_trans,j,i) /=             &   
4911                         building_pars_f%fill )                                &
4912                       surf_usm_v(l)%transmissivity(m) =                       &
4913                                          building_pars_f%pars_xy(ind_trans,j,i)
4914                   
4915                    IF ( building_pars_f%pars_xy(ind_z0,j,i) /=                &         
4916                         building_pars_f%fill )                                &
4917                       surf_usm_v(l)%z0(m) = building_pars_f%pars_xy(ind_z0,j,i)
4918                       
4919                    IF ( building_pars_f%pars_xy(ind_z0qh,j,i) /=              &           
4920                         building_pars_f%fill )                                &
4921                       surf_usm_v(l)%z0h(m) =                                  &
4922                                       building_pars_f%pars_xy(ind_z0qh,j,i)
4923                    IF ( building_pars_f%pars_xy(ind_z0qh,j,i) /=              &           
4924                         building_pars_f%fill )                                &
4925                       surf_usm_v(l)%z0q(m) =                                  &
4926                                       building_pars_f%pars_xy(ind_z0qh,j,i)
4927                   
4928                    IF ( building_pars_f%pars_xy(ind_alb_wall_agfl,j,i) /=     &         
4929                         building_pars_f%fill )                                & 
4930                       surf_usm_v(l)%albedo_type(ind_veg_wall,m)  =            &
4931                                 building_pars_f%pars_xy(ind_alb_wall_agfl,j,i)
4932                       
4933                    IF ( building_pars_f%pars_xy(ind_alb_green_agfl,j,i) /=    &           
4934                         building_pars_f%fill )                                &
4935                       surf_usm_v(l)%albedo_type(ind_pav_green,m) =            &
4936                                 building_pars_f%pars_xy(ind_alb_green_agfl,j,i)
4937                    IF ( building_pars_f%pars_xy(ind_alb_win_agfl,j,i) /=      &         
4938                         building_pars_f%fill )                                &
4939                       surf_usm_v(l)%albedo_type(ind_wat_win,m)   =            &
4940                                   building_pars_f%pars_xy(ind_alb_win_agfl,j,i)
4941                   
4942                    IF ( building_pars_f%pars_xy(ind_thick_1_agfl,j,i) /=      &         
4943                         building_pars_f%fill )                                & 
4944                       surf_usm_v(l)%zw(nzb_wall,m) =                          &
4945                                   building_pars_f%pars_xy(ind_thick_1_agfl,j,i)
4946                       
4947                    IF ( building_pars_f%pars_xy(ind_thick_2_agfl,j,i) /=      &         
4948                         building_pars_f%fill )                                &
4949                       surf_usm_v(l)%zw(nzb_wall+1,m) =                        &
4950                                   building_pars_f%pars_xy(ind_thick_2_agfl,j,i)
4951                       
4952                    IF ( building_pars_f%pars_xy(ind_thick_3_agfl,j,i) /=      &         
4953                         building_pars_f%fill )                                &
4954                       surf_usm_v(l)%zw(nzb_wall+2,m) =                        &
4955                                   building_pars_f%pars_xy(ind_thick_3_agfl,j,i)
4956                       
4957                       
4958                    IF ( building_pars_f%pars_xy(ind_thick_4_agfl,j,i) /=      &         
4959                         building_pars_f%fill )                                & 
4960                       surf_usm_v(l)%zw(nzb_wall+3,m) =                        &
4961                                   building_pars_f%pars_xy(ind_thick_4_agfl,j,i)
4962                       
4963                    IF ( building_pars_f%pars_xy(ind_thick_1_agfl,j,i) /=      &           
4964                         building_pars_f%fill )                                &
4965                       surf_usm_v(l)%zw_green(nzb_wall,m) =                    &
4966                                   building_pars_f%pars_xy(ind_thick_1_agfl,j,i)
4967                       
4968                    IF ( building_pars_f%pars_xy(ind_thick_2_agfl,j,i) /=      &         
4969                         building_pars_f%fill )                                &
4970                       surf_usm_v(l)%zw_green(nzb_wall+1,m) =                  &
4971                                   building_pars_f%pars_xy(ind_thick_2_agfl,j,i)
4972                       
4973                    IF ( building_pars_f%pars_xy(ind_thick_3_agfl,j,i) /=      &         
4974                         building_pars_f%fill )                                & 
4975                       surf_usm_v(l)%zw_green(nzb_wall+2,m) =                  &
4976                                   building_pars_f%pars_xy(ind_thick_3_agfl,j,i)
4977                       
4978                    IF ( building_pars_f%pars_xy(ind_thick_4_agfl,j,i) /=      &         
4979                         building_pars_f%fill )                                &
4980                       surf_usm_v(l)%zw_green(nzb_wall+3,m) =                  &
4981                                   building_pars_f%pars_xy(ind_thick_4_agfl,j,i)
4982                   
4983                    IF ( building_pars_f%pars_xy(ind_c_surface,j,i) /=         &       
4984                         building_pars_f%fill )                                & 
4985                       surf_usm_v(l)%c_surface(m) =                            &
4986                                     building_pars_f%pars_xy(ind_c_surface,j,i)
4987                       
4988                    IF ( building_pars_f%pars_xy(ind_lambda_surf,j,i) /=       &       
4989                         building_pars_f%fill )                                &
4990                       surf_usm_v(l)%lambda_surf(m) =                          &
4991                                    building_pars_f%pars_xy(ind_lambda_surf,j,i)
4992                   
4993              ENDDO
4994           ENDDO
4995        ENDIF 
4996!       
4997!--     Read the surface_types array.
4998!--     Please note, here also initialization of surface attributes is done as
4999!--     long as _urbsurf and _surfpar files are available. Values from above
5000!--     will be overwritten. This might be removed later, but is still in the
5001!--     code to enable compatibility with older model version.
5002        CALL usm_read_urban_surface_types()
5003       
5004        CALL usm_init_material_model()
5005!       
5006!--     init anthropogenic sources of heat
5007        IF ( usm_anthropogenic_heat )  THEN
5008!
5009!--         init anthropogenic sources of heat (from transportation for now)
5010            CALL usm_read_anthropogenic_heat()
5011        ENDIF
5012
5013!
5014!--    Check for consistent initialization.
5015!--    Check if roughness length for momentum, or heat, exceed surface-layer
5016!--    height and decrease local roughness length where necessary.
5017       DO  m = 1, surf_usm_h%ns
5018          IF ( surf_usm_h%z0(m) >= surf_usm_h%z_mo(m) )  THEN
5019         
5020             surf_usm_h%z0(m) = 0.9_wp * surf_usm_h%z_mo(m)
5021             
5022             WRITE( message_string, * ) 'z0 exceeds surface-layer height ' //  &
5023                            'at horizontal urban surface and is ' //           &
5024                            'decreased appropriately at grid point (i,j) = ',  &
5025                            surf_usm_h%i(m), surf_usm_h%j(m)
5026             CALL message( 'urban_surface_model_mod', 'PA0503',                &
5027                            0, 0, 0, 6, 0 )
5028          ENDIF
5029          IF ( surf_usm_h%z0h(m) >= surf_usm_h%z_mo(m) )  THEN
5030         
5031             surf_usm_h%z0h(m) = 0.9_wp * surf_usm_h%z_mo(m)
5032             surf_usm_h%z0q(m) = 0.9_wp * surf_usm_h%z_mo(m)
5033             
5034             WRITE( message_string, * ) 'z0h exceeds surface-layer height ' // &
5035                            'at horizontal urban surface and is ' //           &
5036                            'decreased appropriately at grid point (i,j) = ',  &
5037                            surf_usm_h%i(m), surf_usm_h%j(m)
5038             CALL message( 'urban_surface_model_mod', 'PA0507',                &
5039                            0, 0, 0, 6, 0 )
5040          ENDIF         
5041       ENDDO
5042       
5043       DO  l = 0, 3
5044          DO  m = 1, surf_usm_v(l)%ns
5045             IF ( surf_usm_v(l)%z0(m) >= surf_usm_v(l)%z_mo(m) )  THEN
5046         
5047                surf_usm_v(l)%z0(m) = 0.9_wp * surf_usm_v(l)%z_mo(m)
5048             
5049                WRITE( message_string, * ) 'z0 exceeds surface-layer height '// &
5050                            'at vertical urban surface and is ' //              &
5051                            'decreased appropriately at grid point (i,j) = ',   &
5052                            surf_usm_v(l)%i(m)+surf_usm_v(l)%ioff,              &
5053                            surf_usm_v(l)%j(m)+surf_usm_v(l)%joff
5054                CALL message( 'urban_surface_model_mod', 'PA0503',              &
5055                            0, 0, 0, 6, 0 )
5056             ENDIF
5057             IF ( surf_usm_v(l)%z0h(m) >= surf_usm_v(l)%z_mo(m) )  THEN
5058         
5059                surf_usm_v(l)%z0h(m) = 0.9_wp * surf_usm_v(l)%z_mo(m)
5060                surf_usm_v(l)%z0q(m) = 0.9_wp * surf_usm_v(l)%z_mo(m)
5061             
5062                WRITE( message_string, * ) 'z0h exceeds surface-layer height '// &
5063                            'at vertical urban surface and is ' //               &
5064                            'decreased appropriately at grid point (i,j) = ',    &
5065                            surf_usm_v(l)%i(m)+surf_usm_v(l)%ioff,               &
5066                            surf_usm_v(l)%j(m)+surf_usm_v(l)%joff
5067                CALL message( 'urban_surface_model_mod', 'PA0507',               &
5068                            0, 0, 0, 6, 0 )
5069             ENDIF
5070          ENDDO
5071       ENDDO
5072!
5073!--     Intitialization of the surface and wall/ground/roof temperature
5074!
5075!--     Initialization for restart runs
5076        IF ( TRIM( initializing_actions ) /= 'read_restart_data'  .AND.        &
5077             TRIM( initializing_actions ) /= 'cyclic_fill' )  THEN
5078
5079!
5080!--         At horizontal surfaces. Please note, t_surf_wall_h is defined on a
5081!--         different data type, but with the same dimension.
5082            DO  m = 1, surf_usm_h%ns
5083               i = surf_usm_h%i(m)           
5084               j = surf_usm_h%j(m)
5085               k = surf_usm_h%k(m)
5086
5087               t_surf_wall_h(m) = pt(k,j,i) * exner(k)
5088               t_surf_window_h(m) = pt(k,j,i) * exner(k)
5089               t_surf_green_h(m) = pt(k,j,i) * exner(k)
5090               surf_usm_h%pt_surface(m) = pt(k,j,i) * exner(k)
5091            ENDDO
5092!
5093!--         At vertical surfaces.
5094            DO  l = 0, 3
5095               DO  m = 1, surf_usm_v(l)%ns
5096                  i = surf_usm_v(l)%i(m)           
5097                  j = surf_usm_v(l)%j(m)
5098                  k = surf_usm_v(l)%k(m)
5099
5100                  t_surf_wall_v(l)%t(m) = pt(k,j,i) * exner(k)
5101                  t_surf_window_v(l)%t(m) = pt(k,j,i) * exner(k)
5102                  t_surf_green_v(l)%t(m) = pt(k,j,i) * exner(k)
5103                  surf_usm_v(l)%pt_surface(m) = pt(k,j,i) * exner(k)
5104               ENDDO
5105            ENDDO
5106
5107!
5108!--         For the sake of correct initialization, set also q_surface.
5109!--         Note, at urban surfaces q_surface is initialized with 0.
5110            IF ( humidity )  THEN
5111               DO  m = 1, surf_usm_h%ns
5112                  surf_usm_h%q_surface(m) = 0.0_wp
5113               ENDDO
5114               DO  l = 0, 3
5115                  DO  m = 1, surf_usm_v(l)%ns
5116                     surf_usm_v(l)%q_surface(m) = 0.0_wp
5117                  ENDDO
5118               ENDDO
5119            ENDIF
5120!
5121!--         initial values for t_wall
5122!--         outer value is set to surface temperature
5123!--         inner value is set to wall_inner_temperature
5124!--         and profile is logaritmic (linear in nz).
5125!--         Horizontal surfaces
5126            DO  m = 1, surf_usm_h%ns
5127!
5128!--            Roof
5129               IF ( surf_usm_h%isroof_surf(m) )  THEN
5130                   tin = roof_inner_temperature
5131                   twin = window_inner_temperature
5132!
5133!--            Normal land surface
5134               ELSE
5135                   tin = soil_inner_temperature
5136                   twin = window_inner_temperature
5137               ENDIF
5138
5139               DO k = nzb_wall, nzt_wall+1
5140                   c = REAL( k - nzb_wall, wp ) /                              &
5141                       REAL( nzt_wall + 1 - nzb_wall , wp )
5142
5143                   t_wall_h(k,m) = ( 1.0_wp - c ) * t_surf_wall_h(m) + c * tin
5144                   t_window_h(k,m) = ( 1.0_wp - c ) * t_surf_window_h(m) + c * twin
5145                   t_green_h(k,m) = t_surf_wall_h(m)
5146                   swc_h(k,m) = 0.5_wp
5147                   swc_sat_h(k,m) = 0.95_wp
5148                   swc_res_h(k,m) = 0.05_wp
5149                   rootfr_h(k,m) = 0.1_wp
5150                   wilt_h(k,m) = 0.1_wp
5151                   fc_h(k,m) = 0.9_wp
5152               ENDDO
5153            ENDDO
5154!
5155!--         Vertical surfaces
5156            DO  l = 0, 3
5157               DO  m = 1, surf_usm_v(l)%ns
5158!
5159!--               Inner wall
5160                  tin = wall_inner_temperature
5161                  twin = window_inner_temperature
5162
5163                  DO k = nzb_wall, nzt_wall+1
5164                     c = REAL( k - nzb_wall, wp ) /                            &
5165                         REAL( nzt_wall + 1 - nzb_wall , wp )
5166                     t_wall_v(l)%t(k,m) = ( 1.0_wp - c ) * t_surf_wall_v(l)%t(m) + c * tin
5167                     t_window_v(l)%t(k,m) = ( 1.0_wp - c ) * t_surf_window_v(l)%t(m) + c * twin
5168                     t_green_v(l)%t(k,m) = t_surf_wall_v(l)%t(m)
5169                     swc_v(l)%t(k,m) = 0.5_wp
5170                  ENDDO
5171               ENDDO
5172            ENDDO
5173        ENDIF
5174
5175!
5176!--     If specified, replace constant wall temperatures with fully 3D values from file
5177        IF ( read_wall_temp_3d )  CALL usm_read_wall_temperature()
5178
5179!--
5180!--     Possibly DO user-defined actions (e.g. define heterogeneous wall surface)
5181        CALL user_init_urban_surface
5182
5183!
5184!--     initialize prognostic values for the first timestep
5185        t_surf_wall_h_p = t_surf_wall_h
5186        t_surf_wall_v_p = t_surf_wall_v
5187        t_surf_window_h_p = t_surf_window_h
5188        t_surf_window_v_p = t_surf_window_v
5189        t_surf_green_h_p = t_surf_green_h
5190        t_surf_green_v_p = t_surf_green_v
5191
5192        t_wall_h_p = t_wall_h
5193        t_wall_v_p = t_wall_v
5194        t_window_h_p = t_window_h
5195        t_window_v_p = t_window_v
5196        t_green_h_p = t_green_h
5197        t_green_v_p = t_green_v
5198
5199!
5200!--     Adjust radiative fluxes for urban surface at model start
5201        !CALL radiation_interaction
5202!--     TODO: interaction should be called once before first output,
5203!--     that is not yet possible.
5204       
5205        m_liq_usm_h_p     = m_liq_usm_h
5206        m_liq_usm_v_p     = m_liq_usm_v
5207!
5208!--    Set initial values for prognostic quantities
5209!--    Horizontal surfaces
5210       tm_liq_usm_h_m%var_usm_1d  = 0.0_wp
5211       surf_usm_h%c_liq = 0.0_wp
5212
5213       surf_usm_h%qsws_liq  = 0.0_wp
5214       surf_usm_h%qsws_veg  = 0.0_wp
5215
5216!
5217!--    Do the same for vertical surfaces
5218       DO  l = 0, 3
5219          tm_liq_usm_v_m(l)%var_usm_1d  = 0.0_wp
5220          surf_usm_v(l)%c_liq = 0.0_wp
5221
5222          surf_usm_v(l)%qsws_liq  = 0.0_wp
5223          surf_usm_v(l)%qsws_veg  = 0.0_wp
5224       ENDDO
5225
5226!
5227!--    Set initial values for prognostic soil quantities
5228       IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
5229          m_liq_usm_h%var_usm_1d  = 0.0_wp
5230
5231          DO  l = 0, 3
5232             m_liq_usm_v(l)%var_usm_1d  = 0.0_wp
5233          ENDDO
5234       ENDIF
5235
5236        CALL cpu_log( log_point_s(78), 'usm_init', 'stop' )
5237
5238        IF ( debug_output )  CALL debug_message( 'usm_init', 'end' )
5239
5240    END SUBROUTINE usm_init
5241
5242
5243!------------------------------------------------------------------------------!
5244! Description:
5245! ------------
5246!
5247!> Wall model as part of the urban surface model. The model predicts vertical
5248!> and horizontal wall / roof temperatures and window layer temperatures.
5249!> No window layer temperature calculactions during spinup to increase
5250!> possible timestep.
5251!------------------------------------------------------------------------------!
5252    SUBROUTINE usm_material_heat_model( during_spinup )
5253
5254
5255        IMPLICIT NONE
5256
5257        INTEGER(iwp) ::  i,j,k,l,kw, m                      !< running indices
5258
5259        REAL(wp), DIMENSION(nzb_wall:nzt_wall) :: wtend, wintend  !< tendency
5260        REAL(wp)     :: win_absorp  !< absorption coefficient from transmissivity
5261        REAL(wp), DIMENSION(nzb_wall:nzt_wall) :: wall_mod
5262
5263        LOGICAL      :: during_spinup  !< if true, no calculation of window temperatures
5264
5265
5266        IF ( debug_output_timestep )  THEN
5267           WRITE( debug_string, * ) 'usm_material_heat_model | during_spinup: ',&
5268                                     during_spinup
5269           CALL debug_message( debug_string, 'start' )
5270        ENDIF
5271
5272        !$OMP PARALLEL PRIVATE (m, i, j, k, kw, wtend, wintend, win_absorp, wall_mod)
5273        wall_mod=1.0_wp
5274        IF ( usm_wall_mod  .AND.  during_spinup )  THEN
5275           DO  kw=nzb_wall,nzb_wall+1
5276               wall_mod(kw)=0.1_wp
5277           ENDDO
5278        ENDIF
5279
5280!
5281!--     For horizontal surfaces                                   
5282        !$OMP DO SCHEDULE (STATIC)
5283        DO  m = 1, surf_usm_h%ns
5284!
5285!--        Obtain indices
5286           i = surf_usm_h%i(m)           
5287           j = surf_usm_h%j(m)
5288           k = surf_usm_h%k(m)
5289!
5290!--        prognostic equation for ground/roof temperature t_wall_h
5291           wtend(:) = 0.0_wp
5292           wtend(nzb_wall) = (1.0_wp / surf_usm_h%rho_c_wall(nzb_wall,m)) *        &
5293                                       ( surf_usm_h%lambda_h(nzb_wall,m) * wall_mod(nzb_wall) *        &
5294                                         ( t_wall_h(nzb_wall+1,m)                  &
5295                                         - t_wall_h(nzb_wall,m) ) *                &
5296                                         surf_usm_h%ddz_wall(nzb_wall+1,m)         &
5297                                       + surf_usm_h%frac(ind_veg_wall,m)           &
5298                                         / (surf_usm_h%frac(ind_veg_wall,m)        &
5299                                           + surf_usm_h%frac(ind_pav_green,m) )    &
5300                                         * surf_usm_h%wghf_eb(m)                   &
5301                                       - surf_usm_h%frac(ind_pav_green,m)          &
5302                                          / (surf_usm_h%frac(ind_veg_wall,m)       &
5303                                            + surf_usm_h%frac(ind_pav_green,m) )   &
5304                                         * ( surf_usm_h%lambda_h_green(nzt_wall,m)* wall_mod(nzt_wall) &
5305                                           * surf_usm_h%ddz_green(nzt_wall,m)      &
5306                                           + surf_usm_h%lambda_h(nzb_wall,m) * wall_mod(nzb_wall)      &
5307                                           * surf_usm_h%ddz_wall(nzb_wall,m) )     &
5308                                         / ( surf_usm_h%ddz_green(nzt_wall,m)      &
5309                                           + surf_usm_h%ddz_wall(nzb_wall,m) )     &
5310                                         * ( t_wall_h(nzb_wall,m)                  &
5311                                           - t_green_h(nzt_wall,m) ) ) *           &
5312                                       surf_usm_h%ddz_wall_stag(nzb_wall,m)
5313!
5314!-- if indoor model ist used inner wall layer is calculated by using iwghf (indoor wall ground heat flux)
5315           IF ( indoor_model ) THEN
5316              DO  kw = nzb_wall+1, nzt_wall-1
5317                  wtend(kw) = (1.0_wp / surf_usm_h%rho_c_wall(kw,m))              &
5318                                 * (   surf_usm_h%lambda_h(kw,m) * wall_mod(kw)   &
5319                                    * ( t_wall_h(kw+1,m) - t_wall_h(kw,m) )       &
5320                                    * surf_usm_h%ddz_wall(kw+1,m)                 &
5321                                 - surf_usm_h%lambda_h(kw-1,m) * wall_mod(kw-1)   &
5322                                    * ( t_wall_h(kw,m) - t_wall_h(kw-1,m) )       &
5323                                    * surf_usm_h%ddz_wall(kw,m)                   &
5324                                   ) * surf_usm_h%ddz_wall_stag(kw,m)
5325              ENDDO
5326              wtend(nzt_wall) = (1.0_wp / surf_usm_h%rho_c_wall(nzt_wall,m)) *    &
5327                                         ( -surf_usm_h%lambda_h(nzt_wall-1,m) * wall_mod(nzt_wall-1) * &
5328                                           ( t_wall_h(nzt_wall,m)                 &
5329                                           - t_wall_h(nzt_wall-1,m) ) *           &
5330                                           surf_usm_h%ddz_wall(nzt_wall,m)        &
5331                                         + surf_usm_h%iwghf_eb(m) ) *             &
5332                                           surf_usm_h%ddz_wall_stag(nzt_wall,m)
5333           ELSE
5334              DO  kw = nzb_wall+1, nzt_wall
5335                  wtend(kw) = (1.0_wp / surf_usm_h%rho_c_wall(kw,m))              &
5336                                 * (   surf_usm_h%lambda_h(kw,m)  * wall_mod(kw)  &
5337                                    * ( t_wall_h(kw+1,m) - t_wall_h(kw,m) )       &
5338                                    * surf_usm_h%ddz_wall(kw+1,m)                 &
5339                                 - surf_usm_h%lambda_h(kw-1,m) * wall_mod(kw-1)   &
5340                                    * ( t_wall_h(kw,m) - t_wall_h(kw-1,m) )       &
5341                                    * surf_usm_h%ddz_wall(kw,m)                   &
5342                                   ) * surf_usm_h%ddz_wall_stag(kw,m)
5343              ENDDO
5344           ENDIF
5345
5346           t_wall_h_p(nzb_wall:nzt_wall,m) = t_wall_h(nzb_wall:nzt_wall,m)     &
5347                                 + dt_3d * ( tsc(2)                            &
5348                                 * wtend(nzb_wall:nzt_wall) + tsc(3)           &
5349                                 * surf_usm_h%tt_wall_m(nzb_wall:nzt_wall,m) )   
5350
5351!
5352!-- during spinup the tempeature inside window layers is not calculated to make larger timesteps possible
5353           IF ( .NOT. during_spinup ) THEN
5354              win_absorp = -log(surf_usm_h%transmissivity(m)) / surf_usm_h%zw_window(nzt_wall,m)
5355!
5356!--           prognostic equation for ground/roof window temperature t_window_h
5357!--           takes absorption of shortwave radiation into account
5358              wintend(:) = 0.0_wp
5359              wintend(nzb_wall) = (1.0_wp / surf_usm_h%rho_c_window(nzb_wall,m)) *   &
5360                                         ( surf_usm_h%lambda_h_window(nzb_wall,m) *  &
5361                                           ( t_window_h(nzb_wall+1,m)                &
5362                                           - t_window_h(nzb_wall,m) ) *              &
5363                                           surf_usm_h%ddz_window(nzb_wall+1,m)       &
5364                                         + surf_usm_h%wghf_eb_window(m)              &
5365                                         + surf_usm_h%rad_sw_in(m)                   &
5366                                           * (1.0_wp - exp(-win_absorp               &
5367                                           * surf_usm_h%zw_window(nzb_wall,m) ) )    &
5368                                         ) * surf_usm_h%ddz_window_stag(nzb_wall,m)
5369   
5370              IF ( indoor_model ) THEN
5371                 DO  kw = nzb_wall+1, nzt_wall-1
5372                     wintend(kw) = (1.0_wp / surf_usm_h%rho_c_window(kw,m))          &
5373                                    * (   surf_usm_h%lambda_h_window(kw,m)           &
5374                                       * ( t_window_h(kw+1,m) - t_window_h(kw,m) )   &
5375                                       * surf_usm_h%ddz_window(kw+1,m)               &
5376                                    - surf_usm_h%lambda_h_window(kw-1,m)             &
5377                                       * ( t_window_h(kw,m) - t_window_h(kw-1,m) )   &
5378                                       * surf_usm_h%ddz_window(kw,m)                 &
5379                                    + surf_usm_h%rad_sw_in(m)                        &
5380                                       * (exp(-win_absorp                            &
5381                                           * surf_usm_h%zw_window(kw-1,m) )          &
5382                                           - exp(-win_absorp                         &
5383                                           * surf_usm_h%zw_window(kw,m) ) )          &
5384                                      ) * surf_usm_h%ddz_window_stag(kw,m)
5385   
5386                 ENDDO
5387                 wintend(nzt_wall) = (1.0_wp / surf_usm_h%rho_c_window(nzt_wall,m)) *       &
5388                                            ( -surf_usm_h%lambda_h_window(nzt_wall-1,m) *   &
5389                                              ( t_window_h(nzt_wall,m)                      &
5390                                              - t_window_h(nzt_wall-1,m) ) *                &
5391                                              surf_usm_h%ddz_window(nzt_wall,m)             &
5392                                            + surf_usm_h%iwghf_eb_window(m)                 &
5393                                            + surf_usm_h%rad_sw_in(m)                       &
5394                                              * (exp(-win_absorp                            &
5395                                              * surf_usm_h%zw_window(nzt_wall-1,m) )        &
5396                                              - exp(-win_absorp                             &
5397                                              * surf_usm_h%zw_window(nzt_wall,m) ) )        &
5398                                            ) * surf_usm_h%ddz_window_stag(nzt_wall,m)
5399              ELSE
5400                 DO  kw = nzb_wall+1, nzt_wall
5401                     wintend(kw) = (1.0_wp / surf_usm_h%rho_c_window(kw,m))          &
5402                                    * (   surf_usm_h%lambda_h_window(kw,m)           &
5403                                       * ( t_window_h(kw+1,m) - t_window_h(kw,m) )   &
5404                                       * surf_usm_h%ddz_window(kw+1,m)               &
5405                                    - surf_usm_h%lambda_h_window(kw-1,m)             &
5406                                       * ( t_window_h(kw,m) - t_window_h(kw-1,m) )   &
5407                                       * surf_usm_h%ddz_window(kw,m)                 &
5408                                    + surf_usm_h%rad_sw_in(m)                        &
5409                                       * (exp(-win_absorp                            &
5410                                           * surf_usm_h%zw_window(kw-1,m) )          &
5411                                           - exp(-win_absorp                         &
5412                                           * surf_usm_h%zw_window(kw,m) ) )          &
5413                                      ) * surf_usm_h%ddz_window_stag(kw,m)
5414   
5415                 ENDDO
5416              ENDIF
5417
5418              t_window_h_p(nzb_wall:nzt_wall,m) = t_window_h(nzb_wall:nzt_wall,m) &
5419                                 + dt_3d * ( tsc(2)                               &
5420                                 * wintend(nzb_wall:nzt_wall) + tsc(3)            &
5421                                 * surf_usm_h%tt_window_m(nzb_wall:nzt_wall,m) )   
5422
5423           ENDIF
5424
5425!
5426!--        calculate t_wall tendencies for the next Runge-Kutta step
5427           IF ( timestep_scheme(1:5) == 'runge' )  THEN
5428               IF ( intermediate_timestep_count == 1 )  THEN
5429                  DO  kw = nzb_wall, nzt_wall
5430                     surf_usm_h%tt_wall_m(kw,m) = wtend(kw)
5431                  ENDDO
5432               ELSEIF ( intermediate_timestep_count <                          &
5433                        intermediate_timestep_count_max )  THEN
5434                   DO  kw = nzb_wall, nzt_wall
5435                      surf_usm_h%tt_wall_m(kw,m) = -9.5625_wp * wtend(kw) +    &
5436                                         5.3125_wp * surf_usm_h%tt_wall_m(kw,m)
5437                   ENDDO
5438               ENDIF
5439           ENDIF
5440
5441           IF ( .NOT. during_spinup )  THEN
5442!
5443!--           calculate t_window tendencies for the next Runge-Kutta step
5444              IF ( timestep_scheme(1:5) == 'runge' )  THEN
5445                  IF ( intermediate_timestep_count == 1 )  THEN
5446                     DO  kw = nzb_wall, nzt_wall
5447                        surf_usm_h%tt_window_m(kw,m) = wintend(kw)
5448                     ENDDO
5449                  ELSEIF ( intermediate_timestep_count <                            &
5450                           intermediate_timestep_count_max )  THEN
5451                      DO  kw = nzb_wall, nzt_wall
5452                         surf_usm_h%tt_window_m(kw,m) = -9.5625_wp * wintend(kw) +  &
5453                                            5.3125_wp * surf_usm_h%tt_window_m(kw,m)
5454                      ENDDO
5455                  ENDIF
5456              ENDIF
5457           ENDIF
5458
5459        ENDDO
5460
5461!
5462!--     For vertical surfaces     
5463        !$OMP DO SCHEDULE (STATIC)
5464        DO  l = 0, 3                             
5465           DO  m = 1, surf_usm_v(l)%ns
5466!
5467!--           Obtain indices
5468              i = surf_usm_v(l)%i(m)           
5469              j = surf_usm_v(l)%j(m)
5470              k = surf_usm_v(l)%k(m)
5471!
5472!--           prognostic equation for wall temperature t_wall_v
5473              wtend(:) = 0.0_wp
5474
5475              wtend(nzb_wall) = (1.0_wp / surf_usm_v(l)%rho_c_wall(nzb_wall,m)) *    &
5476                                      ( surf_usm_v(l)%lambda_h(nzb_wall,m) * wall_mod(nzb_wall)  *      &
5477                                        ( t_wall_v(l)%t(nzb_wall+1,m)                &
5478                                        - t_wall_v(l)%t(nzb_wall,m) ) *              &
5479                                        surf_usm_v(l)%ddz_wall(nzb_wall+1,m)         &
5480                                      + surf_usm_v(l)%frac(ind_veg_wall,m)           &
5481                                        / (surf_usm_v(l)%frac(ind_veg_wall,m)        &
5482                                          + surf_usm_v(l)%frac(ind_pav_green,m) )    &
5483                                        * surf_usm_v(l)%wghf_eb(m)                   &
5484                                      - surf_usm_v(l)%frac(ind_pav_green,m)          &
5485                                        / (surf_usm_v(l)%frac(ind_veg_wall,m)        &
5486                                          + surf_usm_v(l)%frac(ind_pav_green,m) )    &
5487                                        * ( surf_usm_v(l)%lambda_h_green(nzt_wall,m)* wall_mod(nzt_wall) &
5488                                          * surf_usm_v(l)%ddz_green(nzt_wall,m)      &
5489                                          + surf_usm_v(l)%lambda_h(nzb_wall,m)* wall_mod(nzb_wall)       &
5490                                          * surf_usm_v(l)%ddz_wall(nzb_wall,m) )     &
5491                                        / ( surf_usm_v(l)%ddz_green(nzt_wall,m)      &
5492                                          + surf_usm_v(l)%ddz_wall(nzb_wall,m) )     &
5493                                        * ( t_wall_v(l)%t(nzb_wall,m)                &
5494                                          - t_green_v(l)%t(nzt_wall,m) ) ) *         &
5495                                        surf_usm_v(l)%ddz_wall_stag(nzb_wall,m)
5496
5497              IF ( indoor_model ) THEN
5498                 DO  kw = nzb_wall+1, nzt_wall-1
5499                     wtend(kw) = (1.0_wp / surf_usm_v(l)%rho_c_wall(kw,m))        &
5500                              * (   surf_usm_v(l)%lambda_h(kw,m)  * wall_mod(kw)  &
5501                                 * ( t_wall_v(l)%t(kw+1,m) - t_wall_v(l)%t(kw,m) )&
5502                                 * surf_usm_v(l)%ddz_wall(kw+1,m)                 &
5503                              - surf_usm_v(l)%lambda_h(kw-1,m)  * wall_mod(kw-1)  &
5504                                 * ( t_wall_v(l)%t(kw,m) - t_wall_v(l)%t(kw-1,m) )&
5505                                 * surf_usm_v(l)%ddz_wall(kw,m)                   &
5506                                 ) * surf_usm_v(l)%ddz_wall_stag(kw,m)
5507                 ENDDO
5508                 wtend(nzt_wall) = (1.0_wp / surf_usm_v(l)%rho_c_wall(nzt_wall,m)) * &
5509                                         ( -surf_usm_v(l)%lambda_h(nzt_wall-1,m) * wall_mod(nzt_wall-1)*    &
5510                                           ( t_wall_v(l)%t(nzt_wall,m)               &
5511                                           - t_wall_v(l)%t(nzt_wall-1,m) ) *         &
5512                                           surf_usm_v(l)%ddz_wall(nzt_wall,m)        &
5513                                         + surf_usm_v(l)%iwghf_eb(m) ) *             &
5514                                           surf_usm_v(l)%ddz_wall_stag(nzt_wall,m)
5515              ELSE
5516                 DO  kw = nzb_wall+1, nzt_wall
5517                     wtend(kw) = (1.0_wp / surf_usm_v(l)%rho_c_wall(kw,m))        &
5518                              * (   surf_usm_v(l)%lambda_h(kw,m) * wall_mod(kw)   &
5519                                 * ( t_wall_v(l)%t(kw+1,m) - t_wall_v(l)%t(kw,m) )&
5520                                 * surf_usm_v(l)%ddz_wall(kw+1,m)                 &
5521                              - surf_usm_v(l)%lambda_h(kw-1,m)  * wall_mod(kw-1)  &
5522                                 * ( t_wall_v(l)%t(kw,m) - t_wall_v(l)%t(kw-1,m) )&
5523                                 * surf_usm_v(l)%ddz_wall(kw,m)                   &
5524                                 ) * surf_usm_v(l)%ddz_wall_stag(kw,m)
5525                 ENDDO
5526              ENDIF
5527
5528              t_wall_v_p(l)%t(nzb_wall:nzt_wall,m) =                           &
5529                                   t_wall_v(l)%t(nzb_wall:nzt_wall,m)          &
5530                                 + dt_3d * ( tsc(2)                            &
5531                                 * wtend(nzb_wall:nzt_wall) + tsc(3)           &
5532                                 * surf_usm_v(l)%tt_wall_m(nzb_wall:nzt_wall,m) )   
5533
5534              IF ( .NOT. during_spinup )  THEN
5535                 win_absorp = -log(surf_usm_v(l)%transmissivity(m)) / surf_usm_v(l)%zw_window(nzt_wall,m)
5536!
5537!--              prognostic equation for window temperature t_window_v
5538                 wintend(:) = 0.0_wp
5539                 wintend(nzb_wall) = (1.0_wp / surf_usm_v(l)%rho_c_window(nzb_wall,m)) * &
5540                                         ( surf_usm_v(l)%lambda_h_window(nzb_wall,m) *   &
5541                                           ( t_window_v(l)%t(nzb_wall+1,m)               &
5542                                           - t_window_v(l)%t(nzb_wall,m) ) *             &
5543                                           surf_usm_v(l)%ddz_window(nzb_wall+1,m)        &
5544                                         + surf_usm_v(l)%wghf_eb_window(m)               &
5545                                         + surf_usm_v(l)%rad_sw_in(m)                    &
5546                                           * (1.0_wp - exp(-win_absorp                   &
5547                                           * surf_usm_v(l)%zw_window(nzb_wall,m) ) )     &
5548                                         ) * surf_usm_v(l)%ddz_window_stag(nzb_wall,m)
5549   
5550                 IF ( indoor_model ) THEN
5551                    DO  kw = nzb_wall+1, nzt_wall -1
5552                        wintend(kw) = (1.0_wp / surf_usm_v(l)%rho_c_window(kw,m))         &
5553                                 * (   surf_usm_v(l)%lambda_h_window(kw,m)                &
5554                                    * ( t_window_v(l)%t(kw+1,m) - t_window_v(l)%t(kw,m) ) &
5555                                    * surf_usm_v(l)%ddz_window(kw+1,m)                    &
5556                                 - surf_usm_v(l)%lambda_h_window(kw-1,m)                  &
5557                                    * ( t_window_v(l)%t(kw,m) - t_window_v(l)%t(kw-1,m) ) &
5558                                    * surf_usm_v(l)%ddz_window(kw,m)                      &
5559                                 + surf_usm_v(l)%rad_sw_in(m)                             &
5560                                    * (exp(-win_absorp                                    &
5561                                       * surf_usm_v(l)%zw_window(kw-1,m)       )          &
5562                                           - exp(-win_absorp                              &
5563                                           * surf_usm_v(l)%zw_window(kw,m) ) )            &
5564                                    ) * surf_usm_v(l)%ddz_window_stag(kw,m)
5565                     ENDDO
5566                     wintend(nzt_wall) = (1.0_wp / surf_usm_v(l)%rho_c_window(nzt_wall,m)) *  &
5567                                             ( -surf_usm_v(l)%lambda_h_window(nzt_wall-1,m) * &
5568                                               ( t_window_v(l)%t(nzt_wall,m)                  &
5569                                               - t_window_v(l)%t(nzt_wall-1,m) ) *            &
5570                                               surf_usm_v(l)%ddz_window(nzt_wall,m)           &
5571                                             + surf_usm_v(l)%iwghf_eb_window(m)               &
5572                                             + surf_usm_v(l)%rad_sw_in(m)                     &
5573                                               * (exp(-win_absorp                             &
5574                                             * surf_usm_v(l)%zw_window(nzt_wall-1,m) )        &
5575                                           - exp(-win_absorp                                  &
5576                                               * surf_usm_v(l)%zw_window(nzt_wall,m) ) )      &
5577                                             ) * surf_usm_v(l)%ddz_window_stag(nzt_wall,m)
5578                 ELSE
5579                    DO  kw = nzb_wall+1, nzt_wall
5580                        wintend(kw) = (1.0_wp / surf_usm_v(l)%rho_c_window(kw,m))         &
5581                                 * (   surf_usm_v(l)%lambda_h_window(kw,m)                &
5582                                    * ( t_window_v(l)%t(kw+1,m) - t_window_v(l)%t(kw,m) ) &
5583                                    * surf_usm_v(l)%ddz_window(kw+1,m)                    &
5584                                 - surf_usm_v(l)%lambda_h_window(kw-1,m)                  &
5585                                    * ( t_window_v(l)%t(kw,m) - t_window_v(l)%t(kw-1,m) ) &
5586                                    * surf_usm_v(l)%ddz_window(kw,m)                      &
5587                                 + surf_usm_v(l)%rad_sw_in(m)                             &
5588                                    * (exp(-win_absorp                                    &
5589                                       * surf_usm_v(l)%zw_window(kw-1,m)       )          &
5590                                           - exp(-win_absorp                              &
5591                                           * surf_usm_v(l)%zw_window(kw,m) ) )            &
5592                                    ) * surf_usm_v(l)%ddz_window_stag(kw,m)
5593                    ENDDO
5594                 ENDIF
5595   
5596                 t_window_v_p(l)%t(nzb_wall:nzt_wall,m) =                           &
5597                                      t_window_v(l)%t(nzb_wall:nzt_wall,m)          &
5598                                    + dt_3d * ( tsc(2)                              &
5599                                    * wintend(nzb_wall:nzt_wall) + tsc(3)           &
5600                                    * surf_usm_v(l)%tt_window_m(nzb_wall:nzt_wall,m) )   
5601              ENDIF
5602
5603!
5604!--           calculate t_wall tendencies for the next Runge-Kutta step
5605              IF ( timestep_scheme(1:5) == 'runge' )  THEN
5606                  IF ( intermediate_timestep_count == 1 )  THEN
5607                     DO  kw = nzb_wall, nzt_wall
5608                        surf_usm_v(l)%tt_wall_m(kw,m) = wtend(kw)
5609                     ENDDO
5610                  ELSEIF ( intermediate_timestep_count <                       &
5611                           intermediate_timestep_count_max )  THEN
5612                      DO  kw = nzb_wall, nzt_wall
5613                         surf_usm_v(l)%tt_wall_m(kw,m) =                       &
5614                                     - 9.5625_wp * wtend(kw) +                 &
5615                                       5.3125_wp * surf_usm_v(l)%tt_wall_m(kw,m)
5616                      ENDDO
5617                  ENDIF
5618              ENDIF
5619
5620
5621              IF ( .NOT. during_spinup )  THEN
5622!
5623!--              calculate t_window tendencies for the next Runge-Kutta step
5624                 IF ( timestep_scheme(1:5) == 'runge' )  THEN
5625                     IF ( intermediate_timestep_count == 1 )  THEN
5626                        DO  kw = nzb_wall, nzt_wall
5627                           surf_usm_v(l)%tt_window_m(kw,m) = wintend(kw)
5628                        ENDDO
5629                     ELSEIF ( intermediate_timestep_count <                       &
5630                              intermediate_timestep_count_max )  THEN
5631                         DO  kw = nzb_wall, nzt_wall
5632                            surf_usm_v(l)%tt_window_m(kw,m) =                     &
5633                                        - 9.5625_wp * wintend(kw) +               &
5634                                          5.3125_wp * surf_usm_v(l)%tt_window_m(kw,m)
5635                         ENDDO
5636                     ENDIF
5637                 ENDIF
5638              ENDIF
5639
5640           ENDDO
5641        ENDDO
5642        !$OMP END PARALLEL
5643
5644        IF ( debug_output_timestep )  THEN
5645           WRITE( debug_string, * ) 'usm_material_heat_model | during_spinup: ',&
5646                                    during_spinup
5647           CALL debug_message( debug_string, 'end' )
5648        ENDIF
5649
5650    END SUBROUTINE usm_material_heat_model
5651
5652!------------------------------------------------------------------------------!
5653! Description:
5654! ------------
5655!
5656!> Green and substrate model as part of the urban surface model. The model predicts ground
5657!> temperatures.
5658!>
5659!> Important: gree-heat model crashes due to unknown reason. Green fraction
5660!> is thus set to zero (in favor of wall fraction).
5661!------------------------------------------------------------------------------!
5662    SUBROUTINE usm_green_heat_model
5663
5664
5665        IMPLICIT NONE
5666
5667        INTEGER(iwp) ::  i,j,k,l,kw, m              !< running indices
5668
5669        REAL(wp)     :: ke, lambda_h_green_sat      !< heat conductivity for saturated soil
5670        REAL(wp)     :: h_vg                        !< Van Genuchten coef. h
5671        REAL(wp)     :: drho_l_lv                   !< frequently used parameter
5672
5673        REAL(wp), DIMENSION(nzb_wall:nzt_wall) :: gtend,tend  !< tendency
5674
5675        REAL(wp), DIMENSION(nzb_wall:nzt_wall) :: root_extr_green
5676
5677        REAL(wp), DIMENSION(nzb_wall:nzt_wall+1) :: lambda_green_temp  !< temp. lambda
5678        REAL(wp), DIMENSION(nzb_wall:nzt_wall+1) :: gamma_green_temp   !< temp. gamma
5679
5680        LOGICAL :: conserve_water_content = .true.
5681
5682
5683        IF ( debug_output_timestep )  CALL debug_message( 'usm_green_heat_model', 'start' )
5684
5685        drho_l_lv = 1.0_wp / (rho_l * l_v)
5686
5687!
5688!--     For horizontal surfaces                                   
5689        !$OMP PARALLEL PRIVATE (m, i, j, k, kw, lambda_h_green_sat, ke, lambda_green_temp, gtend,  &
5690        !$OMP&                  tend, h_vg, gamma_green_temp, m_total, root_extr_green)
5691        !$OMP DO SCHEDULE (STATIC)
5692        DO  m = 1, surf_usm_h%ns
5693           IF (surf_usm_h%frac(ind_pav_green,m) > 0.0_wp) THEN
5694!
5695!--           Obtain indices
5696              i = surf_usm_h%i(m)           
5697              j = surf_usm_h%j(m)
5698              k = surf_usm_h%k(m)
5699   
5700              DO  kw = nzb_wall, nzt_wall
5701!
5702!--              Calculate volumetric heat capacity of the soil, taking
5703!--              into account water content
5704                 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)) &
5705                                      + rho_c_water * swc_h(kw,m))
5706     
5707!
5708!--              Calculate soil heat conductivity at the center of the soil
5709!--              layers
5710                 lambda_h_green_sat = lambda_h_green_sm ** (1.0_wp - swc_sat_h(kw,m)) *    &
5711                                lambda_h_water ** swc_h(kw,m)
5712     
5713                 ke = 1.0_wp + LOG10(MAX(0.1_wp,swc_h(kw,m)             &
5714                      / swc_sat_h(kw,m)))
5715     
5716                 lambda_green_temp(kw) = ke * (lambda_h_green_sat - lambda_h_green_dry) +    &
5717                                  lambda_h_green_dry
5718   
5719              ENDDO
5720              lambda_green_temp(nzt_wall+1) = lambda_green_temp(nzt_wall)
5721   
5722   
5723!
5724!--           Calculate soil heat conductivity (lambda_h) at the _stag level
5725!--           using linear interpolation. For pavement surface, the
5726!--           true pavement depth is considered
5727              DO  kw = nzb_wall, nzt_wall
5728                surf_usm_h%lambda_h_green(kw,m) = ( lambda_green_temp(kw+1) + lambda_green_temp(kw) )  &
5729                                      * 0.5_wp
5730              ENDDO
5731
5732              t_green_h(nzt_wall+1,m) = t_wall_h(nzb_wall,m)
5733!
5734!--        prognostic equation for ground/roof temperature t_green_h
5735              gtend(:) = 0.0_wp
5736              gtend(nzb_wall) = (1.0_wp / surf_usm_h%rho_c_total_green(nzb_wall,m)) *    &
5737                                         ( surf_usm_h%lambda_h_green(nzb_wall,m) * &
5738                                           ( t_green_h(nzb_wall+1,m)               &
5739                                           - t_green_h(nzb_wall,m) ) *             &
5740                                           surf_usm_h%ddz_green(nzb_wall+1,m)      &
5741                                         + surf_usm_h%wghf_eb_green(m) ) *         &
5742                                           surf_usm_h%ddz_green_stag(nzb_wall,m)
5743             
5744               DO  kw = nzb_wall+1, nzt_wall
5745                   gtend(kw) = (1.0_wp / surf_usm_h%rho_c_total_green(kw,m))       &
5746                                  * (   surf_usm_h%lambda_h_green(kw,m)            &
5747                                     * ( t_green_h(kw+1,m) - t_green_h(kw,m) )     &
5748                                     * surf_usm_h%ddz_green(kw+1,m)                &
5749                                  - surf_usm_h%lambda_h_green(kw-1,m)              &
5750                                     * ( t_green_h(kw,m) - t_green_h(kw-1,m) )     &
5751                                     * surf_usm_h%ddz_green(kw,m)                  &
5752                                    ) * surf_usm_h%ddz_green_stag(kw,m)
5753               ENDDO
5754   
5755              t_green_h_p(nzb_wall:nzt_wall,m) = t_green_h(nzb_wall:nzt_wall,m)    &
5756                                    + dt_3d * ( tsc(2)                             &
5757                                    * gtend(nzb_wall:nzt_wall) + tsc(3)            &
5758                                    * surf_usm_h%tt_green_m(nzb_wall:nzt_wall,m) )   
5759   
5760             
5761!
5762!--        calculate t_green tendencies for the next Runge-Kutta step
5763              IF ( timestep_scheme(1:5) == 'runge' )  THEN
5764                  IF ( intermediate_timestep_count == 1 )  THEN
5765                     DO  kw = nzb_wall, nzt_wall
5766                        surf_usm_h%tt_green_m(kw,m) = gtend(kw)
5767                     ENDDO
5768                  ELSEIF ( intermediate_timestep_count <                           &
5769                           intermediate_timestep_count_max )  THEN
5770                      DO  kw = nzb_wall, nzt_wall
5771                         surf_usm_h%tt_green_m(kw,m) = -9.5625_wp * gtend(kw) +    &
5772                                            5.3125_wp * surf_usm_h%tt_green_m(kw,m)
5773                      ENDDO
5774                  ENDIF
5775              ENDIF
5776
5777              DO  kw = nzb_wall, nzt_wall
5778
5779!
5780!--              Calculate soil diffusivity at the center of the soil layers
5781                 lambda_green_temp(kw) = (- b_ch * surf_usm_h%gamma_w_green_sat(kw,m) * psi_sat       &
5782                                   / swc_sat_h(kw,m) ) * ( MAX( swc_h(kw,m),    &
5783                                   wilt_h(kw,m) ) / swc_sat_h(kw,m) )**(        &
5784                                   b_ch + 2.0_wp )
5785
5786!
5787!--              Parametrization of Van Genuchten
5788                 IF ( soil_type /= 7 )  THEN
5789!
5790!--                 Calculate the hydraulic conductivity after Van Genuchten
5791!--                 (1980)
5792                    h_vg = ( ( (swc_res_h(kw,m) - swc_sat_h(kw,m)) / ( swc_res_h(kw,m) -    &
5793                               MAX( swc_h(kw,m), wilt_h(kw,m) ) ) )**(      &
5794                               surf_usm_h%n_vg_green(m) / (surf_usm_h%n_vg_green(m) - 1.0_wp ) ) - 1.0_wp  &
5795                           )**( 1.0_wp / surf_usm_h%n_vg_green(m) ) / surf_usm_h%alpha_vg_green(m)
5796
5797
5798                    gamma_green_temp(kw) = surf_usm_h%gamma_w_green_sat(kw,m) * ( ( (1.0_wp +         &
5799                                    ( surf_usm_h%alpha_vg_green(m) * h_vg )**surf_usm_h%n_vg_green(m))**(  &
5800                                    1.0_wp - 1.0_wp / surf_usm_h%n_vg_green(m) ) - (        &
5801                                    surf_usm_h%alpha_vg_green(m) * h_vg )**( surf_usm_h%n_vg_green(m)      &
5802                                    - 1.0_wp) )**2 )                         &
5803                                    / ( ( 1.0_wp + ( surf_usm_h%alpha_vg_green(m) * h_vg    &
5804                                    )**surf_usm_h%n_vg_green(m) )**( ( 1.0_wp  - 1.0_wp     &
5805                                    / surf_usm_h%n_vg_green(m) ) *( surf_usm_h%l_vg_green(m) + 2.0_wp) ) )
5806
5807!
5808!--              Parametrization of Clapp & Hornberger
5809                 ELSE
5810                    gamma_green_temp(kw) = surf_usm_h%gamma_w_green_sat(kw,m) * ( swc_h(kw,m)       &
5811                                    / swc_sat_h(kw,m) )**(2.0_wp * b_ch + 3.0_wp)
5812                 ENDIF
5813
5814              ENDDO
5815
5816!
5817!--           Prognostic equation for soil moisture content. Only performed,
5818!--           when humidity is enabled in the atmosphere
5819              IF ( humidity )  THEN
5820!
5821!--              Calculate soil diffusivity (lambda_w) at the _stag level
5822!--              using linear interpolation. To do: replace this with
5823!--              ECMWF-IFS Eq. 8.81
5824                 DO  kw = nzb_wall, nzt_wall-1
5825                   
5826                    surf_usm_h%lambda_w_green(kw,m) = ( lambda_green_temp(kw+1) + lambda_green_temp(kw) )  &
5827                                      * 0.5_wp
5828                    surf_usm_h%gamma_w_green(kw,m)  = ( gamma_green_temp(kw+1) + gamma_green_temp(kw) )    &
5829                                      * 0.5_wp
5830
5831                 ENDDO
5832
5833!
5834!--              In case of a closed bottom (= water content is conserved),
5835!--              set hydraulic conductivity to zero to that no water will be
5836!--              lost in the bottom layer.
5837                 IF ( conserve_water_content )  THEN
5838                    surf_usm_h%gamma_w_green(kw,m) = 0.0_wp
5839                 ELSE
5840                    surf_usm_h%gamma_w_green(kw,m) = gamma_green_temp(nzt_wall)
5841                 ENDIF     
5842
5843!--              The root extraction (= root_extr * qsws_veg / (rho_l     
5844!--              * l_v)) ensures the mass conservation for water. The         
5845!--              transpiration of plants equals the cumulative withdrawals by
5846!--              the roots in the soil. The scheme takes into account the
5847!--              availability of water in the soil layers as well as the root
5848!--              fraction in the respective layer. Layer with moisture below
5849!--              wilting point will not contribute, which reflects the
5850!--              preference of plants to take water from moister layers.
5851
5852!
5853!--              Calculate the root extraction (ECMWF 7.69, the sum of
5854!--              root_extr = 1). The energy balance solver guarantees a
5855!--              positive transpiration, so that there is no need for an
5856!--              additional check.
5857                 m_total = 0.0_wp
5858                 DO  kw = nzb_wall, nzt_wall
5859                     IF ( swc_h(kw,m) > wilt_h(kw,m) )  THEN
5860                        m_total = m_total + rootfr_h(kw,m) * swc_h(kw,m)
5861                     ENDIF
5862                 ENDDO 
5863
5864                 IF ( m_total > 0.0_wp )  THEN
5865                    DO  kw = nzb_wall, nzt_wall
5866                       IF ( swc_h(kw,m) > wilt_h(kw,m) )  THEN
5867                          root_extr_green(kw) = rootfr_h(kw,m) * swc_h(kw,m)      &
5868                                                          / m_total
5869                       ELSE
5870                          root_extr_green(kw) = 0.0_wp
5871                       ENDIF
5872                    ENDDO
5873                 ENDIF
5874
5875!
5876!--              Prognostic equation for soil water content m_soil.
5877                 tend(:) = 0.0_wp
5878
5879                 tend(nzb_wall) = ( surf_usm_h%lambda_w_green(nzb_wall,m) * (            &
5880                          swc_h(nzb_wall+1,m) - swc_h(nzb_wall,m) )    &
5881                          * surf_usm_h%ddz_green(nzb_wall+1,m) - surf_usm_h%gamma_w_green(nzb_wall,m) - ( &
5882                             root_extr_green(nzb_wall) * surf_usm_h%qsws_veg(m)          &
5883!                                + surf_usm_h%qsws_soil_green(m)
5884                                ) * drho_l_lv )             &
5885                               * surf_usm_h%ddz_green_stag(nzb_wall,m)
5886
5887                 DO  kw = nzb_wall+1, nzt_wall-1
5888                    tend(kw) = ( surf_usm_h%lambda_w_green(kw,m) * ( swc_h(kw+1,m)        &
5889                              - swc_h(kw,m) ) * surf_usm_h%ddz_green(kw+1,m)              &
5890                              - surf_usm_h%gamma_w_green(kw,m)                            &
5891                              - surf_usm_h%lambda_w_green(kw-1,m) * (swc_h(kw,m) -        &
5892                              swc_h(kw-1,m)) * surf_usm_h%ddz_green(kw,m)                 &
5893                              + surf_usm_h%gamma_w_green(kw-1,m) - (root_extr_green(kw)   &
5894                              * surf_usm_h%qsws_veg(m) * drho_l_lv)                       &
5895                              ) * surf_usm_h%ddz_green_stag(kw,m)
5896
5897                 ENDDO
5898                 tend(nzt_wall) = ( - surf_usm_h%gamma_w_green(nzt_wall,m)                  &
5899                                         - surf_usm_h%lambda_w_green(nzt_wall-1,m)          &
5900                                         * (swc_h(nzt_wall,m)             &
5901                                         - swc_h(nzt_wall-1,m))           &
5902                                         * surf_usm_h%ddz_green(nzt_wall,m)                 &
5903                                         + surf_usm_h%gamma_w_green(nzt_wall-1,m) - (       &
5904                                           root_extr_green(nzt_wall)               &
5905                                         * surf_usm_h%qsws_veg(m) * drho_l_lv  )   &
5906                                   ) * surf_usm_h%ddz_green_stag(nzt_wall,m)             
5907
5908                 swc_h_p(nzb_wall:nzt_wall,m) = swc_h(nzb_wall:nzt_wall,m)&
5909                                                 + dt_3d * ( tsc(2) * tend(:)   &
5910                                                 + tsc(3) * surf_usm_h%tswc_h_m(:,m) )   
5911 
5912!
5913!--              Account for dry soils (find a better solution here!)
5914                 DO  kw = nzb_wall, nzt_wall
5915                    IF ( swc_h_p(kw,m) < 0.0_wp )  swc_h_p(kw,m) = 0.0_wp
5916                 ENDDO
5917
5918!
5919!--              Calculate m_soil tendencies for the next Runge-Kutta step
5920                 IF ( timestep_scheme(1:5) == 'runge' )  THEN
5921                    IF ( intermediate_timestep_count == 1 )  THEN
5922                       DO  kw = nzb_wall, nzt_wall
5923                          surf_usm_h%tswc_h_m(kw,m) = tend(kw)
5924                       ENDDO
5925                    ELSEIF ( intermediate_timestep_count <                   &
5926                             intermediate_timestep_count_max )  THEN
5927                       DO  kw = nzb_wall, nzt_wall
5928                          surf_usm_h%tswc_h_m(kw,m) = -9.5625_wp * tend(kw) + 5.3125_wp&
5929                                   * surf_usm_h%tswc_h_m(kw,m)
5930                       ENDDO
5931                    ENDIF
5932                 ENDIF
5933              ENDIF
5934
5935           ENDIF
5936           
5937        ENDDO
5938        !$OMP END PARALLEL
5939
5940!
5941!--     For vertical surfaces     
5942        DO  l = 0, 3                             
5943           DO  m = 1, surf_usm_v(l)%ns
5944
5945              IF (surf_usm_v(l)%frac(ind_pav_green,m) > 0.0_wp) THEN
5946!
5947!-- no substrate layer for green walls / only groundbase green walls (ivy i.e.) -> green layers get same
5948!-- temperature as first wall layer
5949!-- there fore no temperature calculations for vertical green substrate layers now
5950
5951!
5952! !
5953! !--              Obtain indices
5954!                  i = surf_usm_v(l)%i(m)           
5955!                  j = surf_usm_v(l)%j(m)
5956!                  k = surf_usm_v(l)%k(m)
5957!   
5958!                  t_green_v(l)%t(nzt_wall+1,m) = t_wall_v(l)%t(nzb_wall,m)
5959! !
5960! !--              prognostic equation for green temperature t_green_v
5961!                  gtend(:) = 0.0_wp
5962!                  gtend(nzb_wall) = (1.0_wp / surf_usm_v(l)%rho_c_green(nzb_wall,m)) * &
5963!                                          ( surf_usm_v(l)%lambda_h_green(nzb_wall,m) * &
5964!                                            ( t_green_v(l)%t(nzb_wall+1,m)             &
5965!                                            - t_green_v(l)%t(nzb_wall,m) ) *           &
5966!                                            surf_usm_v(l)%ddz_green(nzb_wall+1,m)      &
5967!                                          + surf_usm_v(l)%wghf_eb(m) ) *               &
5968!                                            surf_usm_v(l)%ddz_green_stag(nzb_wall,m)
5969!               
5970!                  DO  kw = nzb_wall+1, nzt_wall
5971!                     gtend(kw) = (1.0_wp / surf_usm_v(l)%rho_c_green(kw,m))          &
5972!                               * (   surf_usm_v(l)%lambda_h_green(kw,m)              &
5973!                                 * ( t_green_v(l)%t(kw+1,m) - t_green_v(l)%t(kw,m) ) &
5974!                                 * surf_usm_v(l)%ddz_green(kw+1,m)                   &
5975!                               - surf_usm_v(l)%lambda_h(kw-1,m)                      &
5976!                                 * ( t_green_v(l)%t(kw,m) - t_green_v(l)%t(kw-1,m) ) &
5977!                                 * surf_usm_v(l)%ddz_green(kw,m) )                   &
5978!                               * surf_usm_v(l)%ddz_green_stag(kw,m)
5979!                  ENDDO
5980!   
5981!                  t_green_v_p(l)%t(nzb_wall:nzt_wall,m) =                              &
5982!                                       t_green_v(l)%t(nzb_wall:nzt_wall,m)             &
5983!                                     + dt_3d * ( tsc(2)                                &
5984!                                     * gtend(nzb_wall:nzt_wall) + tsc(3)               &
5985!                                     * surf_usm_v(l)%tt_green_m(nzb_wall:nzt_wall,m) )   
5986!   
5987! !
5988! !--              calculate t_green tendencies for the next Runge-Kutta step
5989!                  IF ( timestep_scheme(1:5) == 'runge' )  THEN
5990!                      IF ( intermediate_timestep_count == 1 )  THEN
5991!                         DO  kw = nzb_wall, nzt_wall
5992!                            surf_usm_v(l)%tt_green_m(kw,m) = gtend(kw)
5993!                         ENDDO
5994!                      ELSEIF ( intermediate_timestep_count <                           &
5995!                               intermediate_timestep_count_max )  THEN
5996!                          DO  kw = nzb_wall, nzt_wall
5997!                             surf_usm_v(l)%tt_green_m(kw,m) =                          &
5998!                                         - 9.5625_wp * gtend(kw) +                     &
5999!                                           5.3125_wp * surf_usm_v(l)%tt_green_m(kw,m)
6000!                          ENDDO
6001!                      ENDIF
6002!                  ENDIF
6003
6004                 DO  kw = nzb_wall, nzt_wall+1
6005                     t_green_v(l)%t(kw,m) = t_wall_v(l)%t(nzb_wall,m)
6006                 ENDDO
6007             
6008              ENDIF
6009
6010           ENDDO
6011        ENDDO
6012
6013        IF ( debug_output_timestep )  CALL debug_message( 'usm_green_heat_model', 'end' )
6014
6015    END SUBROUTINE usm_green_heat_model
6016
6017!------------------------------------------------------------------------------!
6018! Description:
6019! ------------
6020!> Parin for &usm_par for urban surface model
6021!------------------------------------------------------------------------------!
6022    SUBROUTINE usm_parin
6023
6024       IMPLICIT NONE
6025
6026       CHARACTER (LEN=80) ::  line  !< string containing current line of file PARIN
6027
6028       NAMELIST /urban_surface_par/                                            &
6029                           building_type,                                      &
6030                           land_category,                                      &
6031                           naheatlayers,                                       &
6032                           pedestrian_category,                                &
6033                           roughness_concrete,                                 &
6034                           read_wall_temp_3d,                                  &
6035                           roof_category,                                      &
6036                           urban_surface,                                      &
6037                           usm_anthropogenic_heat,                             &
6038                           usm_material_model,                                 &
6039                           wall_category,                                      &
6040                           wall_inner_temperature,                             &
6041                           roof_inner_temperature,                             &
6042                           soil_inner_temperature,                             &
6043                           window_inner_temperature,                           &
6044                           usm_wall_mod
6045
6046       NAMELIST /urban_surface_parameters/                                     &
6047                           building_type,                                      &
6048                           land_category,                                      &
6049                           naheatlayers,                                       &
6050                           pedestrian_category,                                &
6051                           roughness_concrete,                                 &
6052                           read_wall_temp_3d,                                  &
6053                           roof_category,                                      &
6054                           urban_surface,                                      &
6055                           usm_anthropogenic_heat,                             &
6056                           usm_material_model,                                 &
6057                           wall_category,                                      &
6058                           wall_inner_temperature,                             &
6059                           roof_inner_temperature,                             &
6060                           soil_inner_temperature,                             &
6061                           window_inner_temperature,                           &
6062                           usm_wall_mod
6063                           
6064 
6065!
6066!--    Try to find urban surface model package
6067       REWIND ( 11 )
6068       line = ' '
6069       DO WHILE ( INDEX( line, '&urban_surface_parameters' ) == 0 )
6070          READ ( 11, '(A)', END=12 )  line
6071       ENDDO
6072       BACKSPACE ( 11 )
6073
6074!
6075!--    Read user-defined namelist
6076       READ ( 11, urban_surface_parameters, ERR = 10 )
6077
6078!
6079!--    Set flag that indicates that the urban surface model is switched on
6080       urban_surface = .TRUE.
6081
6082       GOTO 14
6083
6084 10    BACKSPACE( 11 )
6085       READ( 11 , '(A)') line
6086       CALL parin_fail_message( 'urban_surface_parameters', line )
6087!
6088!--    Try to find old namelist
6089 12    REWIND ( 11 )
6090       line = ' '
6091       DO WHILE ( INDEX( line, '&urban_surface_par' ) == 0 )
6092          READ ( 11, '(A)', END=14 )  line
6093       ENDDO
6094       BACKSPACE ( 11 )
6095
6096!
6097!--    Read user-defined namelist
6098       READ ( 11, urban_surface_par, ERR = 13, END = 14 )
6099
6100       message_string = 'namelist urban_surface_par is deprecated and will be ' // &
6101                     'removed in near future. Please use namelist ' //   &
6102                     'urban_surface_parameters instead'
6103       CALL message( 'usm_parin', 'PA0487', 0, 1, 0, 6, 0 )
6104
6105!
6106!--    Set flag that indicates that the urban surface model is switched on
6107       urban_surface = .TRUE.
6108
6109       GOTO 14
6110
6111 13    BACKSPACE( 11 )
6112       READ( 11 , '(A)') line
6113       CALL parin_fail_message( 'urban_surface_par', line )
6114
6115
6116 14    CONTINUE
6117
6118
6119    END SUBROUTINE usm_parin
6120
6121 
6122!------------------------------------------------------------------------------!
6123! Description:
6124! ------------
6125!
6126!> This subroutine is part of the urban surface model.
6127!> It reads daily heat produced by anthropogenic sources
6128!> and the diurnal cycle of the heat.
6129!------------------------------------------------------------------------------!
6130    SUBROUTINE usm_read_anthropogenic_heat
6131   
6132        INTEGER(iwp)                  :: i,j,k,ii  !< running indices
6133        REAL(wp)                      :: heat      !< anthropogenic heat
6134
6135!
6136!--     allocation of array of sources of anthropogenic heat and their diural profile
6137        ALLOCATE( aheat(naheatlayers,nys:nyn,nxl:nxr) )
6138        ALLOCATE( aheatprof(naheatlayers,0:24) )
6139
6140!
6141!--     read daily amount of heat and its daily cycle
6142        aheat = 0.0_wp
6143        DO  ii = 0, io_blocks-1
6144            IF ( ii == io_group )  THEN
6145
6146!--             open anthropogenic heat file
6147                OPEN( 151, file='ANTHROPOGENIC_HEAT'//TRIM(coupling_char), action='read', &
6148                           status='old', form='formatted', err=11 )
6149                i = 0
6150                j = 0
6151                DO
6152                    READ( 151, *, err=12, end=13 )  i, j, k, heat
6153                    IF ( i >= nxl  .AND.  i <= nxr  .AND.  j >= nys  .AND.  j <= nyn )  THEN
6154                        IF ( k <= naheatlayers  .AND.  k > get_topography_top_index_ji( j, i, 's' ) )  THEN
6155!--                         write heat into the array
6156                            aheat(k,j,i) = heat
6157                        ENDIF
6158                    ENDIF
6159                    CYCLE
6160 12                 WRITE(message_string,'(a,2i4)') 'error in file ANTHROPOGENIC_HEAT'//TRIM(coupling_char)//' after line ',i,j
6161                    CALL message( 'usm_read_anthropogenic_heat', 'PA0515', 0, 1, 0, 6, 0 )
6162                ENDDO
6163 13             CLOSE(151)
6164                CYCLE
6165 11             message_string = 'file ANTHROPOGENIC_HEAT'//TRIM(coupling_char)//' does not exist'
6166                CALL message( 'usm_read_anthropogenic_heat', 'PA0516', 1, 2, 0, 6, 0 )
6167            ENDIF
6168           
6169#if defined( __parallel )
6170            CALL MPI_BARRIER( comm2d, ierr )
6171#endif
6172        ENDDO
6173       
6174!
6175!--     read diurnal profiles of heat sources
6176        aheatprof = 0.0_wp
6177        DO  ii = 0, io_blocks-1
6178            IF ( ii == io_group )  THEN
6179!
6180!--             open anthropogenic heat profile file
6181                OPEN( 151, file='ANTHROPOGENIC_HEAT_PROFILE'//TRIM(coupling_char), action='read', &
6182                           status='old', form='formatted', err=21 )
6183                i = 0
6184                DO
6185                    READ( 151, *, err=22, end=23 )  i, k, heat
6186                    IF ( i >= 0  .AND.  i <= 24  .AND.  k <= naheatlayers )  THEN
6187!--                     write heat into the array
6188                        aheatprof(k,i) = heat
6189                    ENDIF
6190                    CYCLE
6191 22                 WRITE(message_string,'(a,i4)') 'error in file ANTHROPOGENIC_HEAT_PROFILE'// &
6192                                                     TRIM(coupling_char)//' after line ',i
6193                    CALL message( 'usm_read_anthropogenic_heat', 'PA0517', 0, 1, 0, 6, 0 )
6194                ENDDO
6195                aheatprof(:,24) = aheatprof(:,0)
6196 23             CLOSE(151)
6197                CYCLE
6198 21             message_string = 'file ANTHROPOGENIC_HEAT_PROFILE'//TRIM(coupling_char)//' does not exist'
6199                CALL message( 'usm_read_anthropogenic_heat', 'PA0518', 1, 2, 0, 6, 0 )
6200            ENDIF
6201           
6202#if defined( __parallel )
6203            CALL MPI_BARRIER( comm2d, ierr )
6204#endif
6205        ENDDO
6206       
6207    END SUBROUTINE usm_read_anthropogenic_heat
6208   
6209
6210!------------------------------------------------------------------------------!
6211! Description:
6212! ------------
6213!> Soubroutine reads t_surf and t_wall data from restart files
6214!------------------------------------------------------------------------------!
6215    SUBROUTINE usm_rrd_local( k, nxlf, nxlc, nxl_on_file, nxrf, nxr_on_file, nynf, nyn_on_file,    &
6216                              nysf, nysc, nys_on_file, found )
6217
6218
6219       USE control_parameters,                                                 &
6220           ONLY: length, restart_string
6221           
6222       IMPLICIT NONE
6223
6224       INTEGER(iwp)       ::  k                 !< running index over previous input files covering current local domain
6225       INTEGER(iwp)       ::  l                 !< index variable for surface type
6226       INTEGER(iwp)       ::  ns_h_on_file_usm  !< number of horizontal surface elements (urban type) on file
6227       INTEGER(iwp)       ::  nxlc              !< index of left boundary on current subdomain
6228       INTEGER(iwp)       ::  nxlf              !< index of left boundary on former subdomain
6229       INTEGER(iwp)       ::  nxl_on_file       !< index of left boundary on former local domain
6230       INTEGER(iwp)       ::  nxrf              !< index of right boundary on former subdomain
6231       INTEGER(iwp)       ::  nxr_on_file       !< index of right boundary on former local domain
6232       INTEGER(iwp)       ::  nynf              !< index of north boundary on former subdomain
6233       INTEGER(iwp)       ::  nyn_on_file       !< index of north boundary on former local domain
6234       INTEGER(iwp)       ::  nysc              !< index of south boundary on current subdomain
6235       INTEGER(iwp)       ::  nysf              !< index of south boundary on former subdomain
6236       INTEGER(iwp)       ::  nys_on_file       !< index of south boundary on former local domain
6237       
6238       INTEGER(iwp)       ::  ns_v_on_file_usm(0:3)  !< number of vertical surface elements (urban type) on file
6239       
6240       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  start_index_on_file 
6241       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  end_index_on_file
6242
6243       LOGICAL, INTENT(OUT)  ::  found 
6244!!!    suehring: Why the SAVE attribute?       
6245       REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE   ::  tmp_surf_wall_h
6246       REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE   ::  tmp_surf_window_h
6247       REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE   ::  tmp_surf_green_h
6248       REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE   ::  tmp_surf_waste_h
6249       
6250       REAL(wp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  tmp_wall_h
6251       REAL(wp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  tmp_window_h
6252       REAL(wp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  tmp_green_h
6253       
6254       TYPE( t_surf_vertical ), DIMENSION(0:3), SAVE ::  tmp_surf_wall_v
6255       TYPE( t_surf_vertical ), DIMENSION(0:3), SAVE ::  tmp_surf_window_v
6256       TYPE( t_surf_vertical ), DIMENSION(0:3), SAVE ::  tmp_surf_green_v
6257       TYPE( t_surf_vertical ), DIMENSION(0:3), SAVE ::  tmp_surf_waste_v
6258       
6259       TYPE( t_wall_vertical ), DIMENSION(0:3), SAVE ::  tmp_wall_v
6260       TYPE( t_wall_vertical ), DIMENSION(0:3), SAVE ::  tmp_window_v
6261       TYPE( t_wall_vertical ), DIMENSION(0:3), SAVE ::  tmp_green_v
6262
6263
6264       found = .TRUE.
6265
6266
6267          SELECT CASE ( restart_string(1:length) ) 
6268
6269             CASE ( 'ns_h_on_file_usm') 
6270                IF ( k == 1 )  THEN
6271                   READ ( 13 ) ns_h_on_file_usm
6272               
6273                   IF ( ALLOCATED( tmp_surf_wall_h ) ) DEALLOCATE( tmp_surf_wall_h )
6274                   IF ( ALLOCATED( tmp_wall_h ) ) DEALLOCATE( tmp_wall_h ) 
6275                   IF ( ALLOCATED( tmp_surf_window_h ) )                       &
6276                      DEALLOCATE( tmp_surf_window_h ) 
6277                   IF ( ALLOCATED( tmp_window_h) ) DEALLOCATE( tmp_window_h ) 
6278                   IF ( ALLOCATED( tmp_surf_green_h) )                         &
6279                      DEALLOCATE( tmp_surf_green_h ) 
6280                   IF ( ALLOCATED( tmp_green_h) ) DEALLOCATE( tmp_green_h )
6281                   IF ( ALLOCATED( tmp_surf_waste_h) )                         &
6282                      DEALLOCATE( tmp_surf_waste_h )
6283 
6284!
6285!--                Allocate temporary arrays for reading data on file. Note,
6286!--                the size of allocated surface elements do not necessarily
6287!--                need  to match the size of present surface elements on
6288!--                current processor, as the number of processors between
6289!--                restarts can change.
6290                   ALLOCATE( tmp_surf_wall_h(1:ns_h_on_file_usm) )
6291                   ALLOCATE( tmp_wall_h(nzb_wall:nzt_wall+1,                   &
6292                                        1:ns_h_on_file_usm) )
6293                   ALLOCATE( tmp_surf_window_h(1:ns_h_on_file_usm) )
6294                   ALLOCATE( tmp_window_h(nzb_wall:nzt_wall+1,                 &
6295                                          1:ns_h_on_file_usm) )
6296                   ALLOCATE( tmp_surf_green_h(1:ns_h_on_file_usm) )
6297                   ALLOCATE( tmp_green_h(nzb_wall:nzt_wall+1,                  &
6298                                         1:ns_h_on_file_usm) )
6299                   ALLOCATE( tmp_surf_waste_h(1:ns_h_on_file_usm) )
6300
6301                ENDIF
6302
6303             CASE ( 'ns_v_on_file_usm')
6304                IF ( k == 1 )  THEN
6305                   READ ( 13 ) ns_v_on_file_usm 
6306
6307                   DO  l = 0, 3
6308                      IF ( ALLOCATED( tmp_surf_wall_v(l)%t ) )                 &
6309                         DEALLOCATE( tmp_surf_wall_v(l)%t )
6310                      IF ( ALLOCATED( tmp_wall_v(l)%t ) )                      &
6311                         DEALLOCATE( tmp_wall_v(l)%t )
6312                      IF ( ALLOCATED( tmp_surf_window_v(l)%t ) )               & 
6313                         DEALLOCATE( tmp_surf_window_v(l)%t )
6314                      IF ( ALLOCATED( tmp_window_v(l)%t ) )                    &
6315                         DEALLOCATE( tmp_window_v(l)%t )
6316                      IF ( ALLOCATED( tmp_surf_green_v(l)%t ) )                &
6317                         DEALLOCATE( tmp_surf_green_v(l)%t )
6318                      IF ( ALLOCATED( tmp_green_v(l)%t ) )                     &
6319                         DEALLOCATE( tmp_green_v(l)%t )
6320                      IF ( ALLOCATED( tmp_surf_waste_v(l)%t ) )                &
6321                         DEALLOCATE( tmp_surf_waste_v(l)%t )
6322                   ENDDO 
6323
6324!
6325!--                Allocate temporary arrays for reading data on file. Note,
6326!--                the size of allocated surface elements do not necessarily
6327!--                need to match the size of present surface elements on
6328!--                current processor, as the number of processors between
6329!--                restarts can change.
6330                   DO  l = 0, 3
6331                      ALLOCATE( tmp_surf_wall_v(l)%t(1:ns_v_on_file_usm(l)) )
6332                      ALLOCATE( tmp_wall_v(l)%t(nzb_wall:nzt_wall+1,           &
6333                                                1:ns_v_on_file_usm(l) ) )
6334                      ALLOCATE( tmp_surf_window_v(l)%t(1:ns_v_on_file_usm(l)) )
6335                      ALLOCATE( tmp_window_v(l)%t(nzb_wall:nzt_wall+1,         & 
6336                                                  1:ns_v_on_file_usm(l) ) )
6337                      ALLOCATE( tmp_surf_green_v(l)%t(1:ns_v_on_file_usm(l)) )
6338                      ALLOCATE( tmp_green_v(l)%t(nzb_wall:nzt_wall+1,          &
6339                                                 1:ns_v_on_file_usm(l) ) )
6340                      ALLOCATE( tmp_surf_waste_v(l)%t(1:ns_v_on_file_usm(l)) )
6341                   ENDDO
6342
6343                ENDIF   
6344         
6345             CASE ( 'usm_start_index_h', 'usm_start_index_v'  )   
6346                IF ( k == 1 )  THEN
6347
6348                   IF ( ALLOCATED( start_index_on_file ) )                     &
6349                      DEALLOCATE( start_index_on_file )
6350
6351                   ALLOCATE ( start_index_on_file(nys_on_file:nyn_on_file,     &
6352                                                  nxl_on_file:nxr_on_file) )
6353
6354                   READ ( 13 )  start_index_on_file
6355
6356                ENDIF
6357               
6358             CASE ( 'usm_end_index_h', 'usm_end_index_v' )   
6359                IF ( k == 1 )  THEN
6360
6361                   IF ( ALLOCATED( end_index_on_file ) )                       &
6362                      DEALLOCATE( end_index_on_file )
6363
6364                   ALLOCATE ( end_index_on_file(nys_on_file:nyn_on_file,       &
6365                                                nxl_on_file:nxr_on_file) )
6366
6367                   READ ( 13 )  end_index_on_file
6368
6369                ENDIF
6370         
6371             CASE ( 't_surf_wall_h' )
6372                IF ( k == 1 )  THEN
6373                   IF ( .NOT.  ALLOCATED( t_surf_wall_h_1 ) )                  &
6374                      ALLOCATE( t_surf_wall_h_1(1:surf_usm_h%ns) )
6375                   READ ( 13 )  tmp_surf_wall_h
6376                ENDIF             
6377                CALL surface_restore_elements(                                 &
6378                                        t_surf_wall_h_1, tmp_surf_wall_h,      &
6379                                        surf_usm_h%start_index,                &
6380                                        start_index_on_file,                   &
6381                                        end_index_on_file,                     &
6382                                        nxlc, nysc,                            &
6383                                        nxlf, nxrf, nysf, nynf,                &
6384                                        nys_on_file, nyn_on_file,              &
6385                                        nxl_on_file,nxr_on_file )
6386
6387             CASE ( 't_surf_wall_v(0)' )
6388                IF ( k == 1 )  THEN
6389                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(0)%t ) )             &
6390                      ALLOCATE( t_surf_wall_v_1(0)%t(1:surf_usm_v(0)%ns) )
6391                   READ ( 13 )  tmp_surf_wall_v(0)%t
6392                ENDIF
6393                CALL surface_restore_elements(                                 &
6394                                        t_surf_wall_v_1(0)%t, tmp_surf_wall_v(0)%t,      &
6395                                        surf_usm_v(0)%start_index,             & 
6396                                        start_index_on_file,                   &
6397                                        end_index_on_file,                     &
6398                                        nxlc, nysc,                            &
6399                                        nxlf, nxrf, nysf, nynf,                &
6400                                        nys_on_file, nyn_on_file,              &
6401                                        nxl_on_file,nxr_on_file )
6402                     
6403             CASE ( 't_surf_wall_v(1)' )
6404                IF ( k == 1 )  THEN
6405                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(1)%t ) )             &
6406                      ALLOCATE( t_surf_wall_v_1(1)%t(1:surf_usm_v(1)%ns) )
6407                   READ ( 13 )  tmp_surf_wall_v(1)%t
6408                ENDIF
6409                CALL surface_restore_elements(                                 &
6410                                        t_surf_wall_v_1(1)%t, tmp_surf_wall_v(1)%t,      &
6411                                        surf_usm_v(1)%start_index,             & 
6412                                        start_index_on_file,                   &
6413                                        end_index_on_file,                     &
6414                                        nxlc, nysc,                            &
6415                                        nxlf, nxrf, nysf, nynf,                &
6416                                        nys_on_file, nyn_on_file,              &
6417                                        nxl_on_file,nxr_on_file )
6418
6419             CASE ( 't_surf_wall_v(2)' )
6420                IF ( k == 1 )  THEN
6421                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(2)%t ) )             &
6422                      ALLOCATE( t_surf_wall_v_1(2)%t(1:surf_usm_v(2)%ns) )
6423                   READ ( 13 )  tmp_surf_wall_v(2)%t
6424                ENDIF
6425                CALL surface_restore_elements(                                 &
6426                                        t_surf_wall_v_1(2)%t, tmp_surf_wall_v(2)%t,      &
6427                                        surf_usm_v(2)%start_index,             & 
6428                                        start_index_on_file,                   &
6429                                        end_index_on_file,                     &
6430                                        nxlc, nysc,                            &
6431                                        nxlf, nxrf, nysf, nynf,                &
6432                                        nys_on_file, nyn_on_file,              &
6433                                        nxl_on_file,nxr_on_file )
6434                     
6435             CASE ( 't_surf_wall_v(3)' )
6436                IF ( k == 1 )  THEN
6437                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(3)%t ) )             &
6438                      ALLOCATE( t_surf_wall_v_1(3)%t(1:surf_usm_v(3)%ns) )
6439                   READ ( 13 )  tmp_surf_wall_v(3)%t
6440                ENDIF
6441                CALL surface_restore_elements(                                 &
6442                                        t_surf_wall_v_1(3)%t, tmp_surf_wall_v(3)%t,      &
6443                                        surf_usm_v(3)%start_index,             & 
6444                                        start_index_on_file,                   &
6445                                        end_index_on_file,                     &
6446                                        nxlc, nysc,                            &
6447                                        nxlf, nxrf, nysf, nynf,                &
6448                                        nys_on_file, nyn_on_file,              &
6449                                        nxl_on_file,nxr_on_file )
6450
6451             CASE ( 't_surf_green_h' )
6452                IF ( k == 1 )  THEN
6453                   IF ( .NOT.  ALLOCATED( t_surf_green_h_1 ) )                 &
6454                      ALLOCATE( t_surf_green_h_1(1:surf_usm_h%ns) )
6455                   READ ( 13 )  tmp_surf_green_h
6456                ENDIF
6457                CALL surface_restore_elements(                                 &
6458                                        t_surf_green_h_1, tmp_surf_green_h,    &
6459                                        surf_usm_h%start_index,                & 
6460                                        start_index_on_file,                   &
6461                                        end_index_on_file,                     &
6462                                        nxlc, nysc,                            &
6463                                        nxlf, nxrf, nysf, nynf,                &
6464                                        nys_on_file, nyn_on_file,              &
6465                                        nxl_on_file,nxr_on_file )
6466
6467             CASE ( 't_surf_green_v(0)' )
6468                IF ( k == 1 )  THEN
6469                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(0)%t ) )            &
6470                      ALLOCATE( t_surf_green_v_1(0)%t(1:surf_usm_v(0)%ns) )
6471                   READ ( 13 )  tmp_surf_green_v(0)%t
6472                ENDIF
6473                CALL surface_restore_elements(                                 &
6474                                        t_surf_green_v_1(0)%t,                 &
6475                                        tmp_surf_green_v(0)%t,                 &
6476                                        surf_usm_v(0)%start_index,             & 
6477                                        start_index_on_file,                   &
6478                                        end_index_on_file,                     &
6479                                        nxlc, nysc,                            &
6480                                        nxlf, nxrf, nysf, nynf,                &
6481                                        nys_on_file, nyn_on_file,              &
6482                                        nxl_on_file,nxr_on_file )
6483                   
6484             CASE ( 't_surf_green_v(1)' )
6485                IF ( k == 1 )  THEN
6486                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(1)%t ) )            &
6487                      ALLOCATE( t_surf_green_v_1(1)%t(1:surf_usm_v(1)%ns) )
6488                   READ ( 13 )  tmp_surf_green_v(1)%t
6489                ENDIF
6490                CALL surface_restore_elements(                                 &
6491                                        t_surf_green_v_1(1)%t,                 &
6492                                        tmp_surf_green_v(1)%t,                 &
6493                                        surf_usm_v(1)%start_index,             & 
6494                                        start_index_on_file,                   &
6495                                        end_index_on_file,                     &
6496                                        nxlc, nysc,                            &
6497                                        nxlf, nxrf, nysf, nynf,                &
6498                                        nys_on_file, nyn_on_file,              &
6499                                        nxl_on_file,nxr_on_file )
6500
6501             CASE ( 't_surf_green_v(2)' )
6502                IF ( k == 1 )  THEN
6503                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(2)%t ) )            &
6504                      ALLOCATE( t_surf_green_v_1(2)%t(1:surf_usm_v(2)%ns) )
6505                   READ ( 13 )  tmp_surf_green_v(2)%t
6506                ENDIF
6507                CALL surface_restore_elements(                                 &
6508                                        t_surf_green_v_1(2)%t,                 &
6509                                        tmp_surf_green_v(2)%t,                 &
6510                                        surf_usm_v(2)%start_index,             & 
6511                                        start_index_on_file,                   &
6512                                        end_index_on_file,                     &
6513                                        nxlc, nysc,                            &
6514                                        nxlf, nxrf, nysf, nynf,                &
6515                                        nys_on_file, nyn_on_file,              &
6516                                        nxl_on_file,nxr_on_file )
6517                   
6518             CASE ( 't_surf_green_v(3)' )
6519                IF ( k == 1 )  THEN
6520                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(3)%t ) )            &
6521                      ALLOCATE( t_surf_green_v_1(3)%t(1:surf_usm_v(3)%ns) )
6522                   READ ( 13 )  tmp_surf_green_v(3)%t
6523                ENDIF
6524                CALL surface_restore_elements(                                 &
6525                                        t_surf_green_v_1(3)%t,                 & 
6526                                        tmp_surf_green_v(3)%t,                 &
6527                                        surf_usm_v(3)%start_index,             & 
6528                                        start_index_on_file,                   &
6529                                        end_index_on_file,                     &
6530                                        nxlc, nysc,                            &
6531                                        nxlf, nxrf, nysf, nynf,                &
6532                                        nys_on_file, nyn_on_file,              &
6533                                        nxl_on_file,nxr_on_file )
6534
6535             CASE ( 't_surf_window_h' )
6536                IF ( k == 1 )  THEN
6537                   IF ( .NOT.  ALLOCATED( t_surf_window_h_1 ) )                &
6538                      ALLOCATE( t_surf_window_h_1(1:surf_usm_h%ns) )
6539                   READ ( 13 )  tmp_surf_window_h
6540                ENDIF
6541                CALL surface_restore_elements(                                 &
6542                                        t_surf_window_h_1,                     &
6543                                        tmp_surf_window_h,                     &
6544                                        surf_usm_h%start_index,                & 
6545                                        start_index_on_file,                   &
6546                                        end_index_on_file,                     &
6547                                        nxlc, nysc,                            &
6548                                        nxlf, nxrf, nysf, nynf,                &
6549                                        nys_on_file, nyn_on_file,              &
6550                                        nxl_on_file,nxr_on_file )
6551
6552             CASE ( 't_surf_window_v(0)' )
6553                IF ( k == 1 )  THEN
6554                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(0)%t ) )           &
6555                      ALLOCATE( t_surf_window_v_1(0)%t(1:surf_usm_v(0)%ns) )
6556                   READ ( 13 )  tmp_surf_window_v(0)%t
6557                ENDIF
6558                CALL surface_restore_elements(                                 &
6559                                        t_surf_window_v_1(0)%t,                &
6560                                        tmp_surf_window_v(0)%t,                &
6561                                        surf_usm_v(0)%start_index,             & 
6562                                        start_index_on_file,                   &
6563                                        end_index_on_file,                     &
6564                                        nxlc, nysc,                            &
6565                                        nxlf, nxrf, nysf, nynf,                &
6566                                        nys_on_file, nyn_on_file,              &
6567                                        nxl_on_file,nxr_on_file )
6568                   
6569             CASE ( 't_surf_window_v(1)' )
6570                IF ( k == 1 )  THEN
6571                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(1)%t ) )           &
6572                      ALLOCATE( t_surf_window_v_1(1)%t(1:surf_usm_v(1)%ns) )
6573                   READ ( 13 )  tmp_surf_window_v(1)%t
6574                ENDIF
6575                CALL surface_restore_elements(                                 &
6576                                        t_surf_window_v_1(1)%t,                &
6577                                        tmp_surf_window_v(1)%t,                &
6578                                        surf_usm_v(1)%start_index,             & 
6579                                        start_index_on_file,                   &
6580                                        end_index_on_file,                     &
6581                                        nxlc, nysc,                            &
6582                                        nxlf, nxrf, nysf, nynf,                &
6583                                        nys_on_file, nyn_on_file,              &
6584                                        nxl_on_file,nxr_on_file )
6585
6586             CASE ( 't_surf_window_v(2)' )
6587                IF ( k == 1 )  THEN
6588                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(2)%t ) )           &
6589                      ALLOCATE( t_surf_window_v_1(2)%t(1:surf_usm_v(2)%ns) )
6590                   READ ( 13 )  tmp_surf_window_v(2)%t
6591                ENDIF
6592                CALL surface_restore_elements(                                 &
6593                                        t_surf_window_v_1(2)%t,                & 
6594                                        tmp_surf_window_v(2)%t,                &
6595                                        surf_usm_v(2)%start_index,             & 
6596                                        start_index_on_file,                   &
6597                                        end_index_on_file,                     &
6598                                        nxlc, nysc,                            &
6599                                        nxlf, nxrf, nysf, nynf,                &
6600                                        nys_on_file, nyn_on_file,              &
6601                                        nxl_on_file,nxr_on_file )
6602                   
6603             CASE ( 't_surf_window_v(3)' )
6604                IF ( k == 1 )  THEN
6605                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(3)%t ) )           &
6606                      ALLOCATE( t_surf_window_v_1(3)%t(1:surf_usm_v(3)%ns) )
6607                   READ ( 13 )  tmp_surf_window_v(3)%t
6608                ENDIF
6609                CALL surface_restore_elements(                                 &
6610                                        t_surf_window_v_1(3)%t,                & 
6611                                        tmp_surf_window_v(3)%t,                &
6612                                        surf_usm_v(3)%start_index,             & 
6613                                        start_index_on_file,                   &
6614                                        end_index_on_file,                     &
6615                                        nxlc, nysc,                            &
6616                                        nxlf, nxrf, nysf, nynf,                &
6617                                        nys_on_file, nyn_on_file,              &
6618                                        nxl_on_file,nxr_on_file )
6619
6620             CASE ( 'waste_heat_h' )
6621                IF ( k == 1 )  THEN
6622                   IF ( .NOT.  ALLOCATED( surf_usm_h%waste_heat ) )            &
6623                      ALLOCATE( surf_usm_h%waste_heat(1:surf_usm_h%ns) )
6624                   READ ( 13 )  tmp_surf_waste_h
6625                ENDIF             
6626                CALL surface_restore_elements(                                 &
6627                                        surf_usm_h%waste_heat,                 &
6628                                        tmp_surf_waste_h,                      &
6629                                        surf_usm_h%start_index,                &
6630                                        start_index_on_file,                   &
6631                                        end_index_on_file,                     &
6632                                        nxlc, nysc,                            &
6633                                        nxlf, nxrf, nysf, nynf,                &
6634                                        nys_on_file, nyn_on_file,              &
6635                                        nxl_on_file,nxr_on_file )                 
6636                                       
6637             CASE ( 'waste_heat_v(0)' )
6638                IF ( k == 1 )  THEN
6639                   IF ( .NOT.  ALLOCATED( surf_usm_v(0)%waste_heat ) )         &
6640                      ALLOCATE( surf_usm_v(0)%waste_heat(1:surf_usm_v(0)%ns) )
6641                   READ ( 13 )  tmp_surf_waste_v(0)%t
6642                ENDIF
6643                CALL surface_restore_elements(                                 &
6644                                        surf_usm_v(0)%waste_heat,              &
6645                                        tmp_surf_waste_v(0)%t,                 &
6646                                        surf_usm_v(0)%start_index,             & 
6647                                        start_index_on_file,                   &
6648                                        end_index_on_file,                     &
6649                                        nxlc, nysc,                            &
6650                                        nxlf, nxrf, nysf, nynf,                &
6651                                        nys_on_file, nyn_on_file,              &
6652                                        nxl_on_file,nxr_on_file )
6653                     
6654             CASE ( 'waste_heat_v(1)' )
6655                IF ( k == 1 )  THEN
6656                   IF ( .NOT.  ALLOCATED( surf_usm_v(1)%waste_heat ) )         &
6657                      ALLOCATE( surf_usm_v(1)%waste_heat(1:surf_usm_v(1)%ns) )
6658                   READ ( 13 )  tmp_surf_waste_v(1)%t
6659                ENDIF
6660                CALL surface_restore_elements(                                 &
6661                                        surf_usm_v(1)%waste_heat,              &
6662                                        tmp_surf_waste_v(1)%t,                 &
6663                                        surf_usm_v(1)%start_index,             & 
6664                                        start_index_on_file,                   &
6665                                        end_index_on_file,                     &
6666                                        nxlc, nysc,                            &
6667                                        nxlf, nxrf, nysf, nynf,                &
6668                                        nys_on_file, nyn_on_file,              &
6669                                        nxl_on_file,nxr_on_file )
6670
6671             CASE ( 'waste_heat_v(2)' )
6672                IF ( k == 1 )  THEN
6673                   IF ( .NOT.  ALLOCATED( surf_usm_v(2)%waste_heat ) )         &
6674                      ALLOCATE( surf_usm_v(2)%waste_heat(1:surf_usm_v(2)%ns) )
6675                   READ ( 13 )  tmp_surf_waste_v(2)%t
6676                ENDIF
6677                CALL surface_restore_elements(                                 &
6678                                        surf_usm_v(2)%waste_heat,              &
6679                                        tmp_surf_waste_v(2)%t,                 &
6680                                        surf_usm_v(2)%start_index,             & 
6681                                        start_index_on_file,                   &
6682                                        end_index_on_file,                     &
6683                                        nxlc, nysc,                            &
6684                                        nxlf, nxrf, nysf, nynf,                &
6685                                        nys_on_file, nyn_on_file,              &
6686                                        nxl_on_file,nxr_on_file )
6687                     
6688             CASE ( 'waste_heat_v(3)' )
6689                IF ( k == 1 )  THEN
6690                   IF ( .NOT.  ALLOCATED( surf_usm_v(3)%waste_heat ) )         &
6691                      ALLOCATE( surf_usm_v(3)%waste_heat(1:surf_usm_v(3)%ns) )
6692                   READ ( 13 )  tmp_surf_waste_v(3)%t
6693                ENDIF
6694                CALL surface_restore_elements(                                 &
6695                                        surf_usm_v(3)%waste_heat,              &
6696                                        tmp_surf_waste_v(3)%t,                 &
6697                                        surf_usm_v(3)%start_index,             & 
6698                                        start_index_on_file,                   &
6699                                        end_index_on_file,                     &
6700                                        nxlc, nysc,                            &
6701                                        nxlf, nxrf, nysf, nynf,                &
6702                                        nys_on_file, nyn_on_file,              &
6703                                        nxl_on_file,nxr_on_file )
6704
6705             CASE ( 't_wall_h' )
6706                IF ( k == 1 )  THEN
6707                   IF ( .NOT.  ALLOCATED( t_wall_h_1 ) )                       &
6708                      ALLOCATE( t_wall_h_1(nzb_wall:nzt_wall+1,                &
6709                                           1:surf_usm_h%ns) )
6710                   READ ( 13 )  tmp_wall_h
6711                ENDIF
6712                CALL surface_restore_elements(                                 &
6713                                        t_wall_h_1, tmp_wall_h,                &
6714                                        surf_usm_h%start_index,                & 
6715                                        start_index_on_file,                   &
6716                                        end_index_on_file,                     &
6717                                        nxlc, nysc,                            &
6718                                        nxlf, nxrf, nysf, nynf,                &
6719                                        nys_on_file, nyn_on_file,              &
6720                                        nxl_on_file,nxr_on_file )
6721
6722             CASE ( 't_wall_v(0)' )
6723                IF ( k == 1 )  THEN
6724                   IF ( .NOT.  ALLOCATED( t_wall_v_1(0)%t ) )                  &
6725                      ALLOCATE( t_wall_v_1(0)%t(nzb_wall:nzt_wall+1,           &
6726                                                1:surf_usm_v(0)%ns) )
6727                   READ ( 13 )  tmp_wall_v(0)%t
6728                ENDIF
6729                CALL surface_restore_elements(                                 &
6730                                        t_wall_v_1(0)%t, tmp_wall_v(0)%t,      &
6731                                        surf_usm_v(0)%start_index,             & 
6732                                        start_index_on_file,                   &
6733                                        end_index_on_file,                     &
6734                                        nxlc, nysc,                            &
6735                                        nxlf, nxrf, nysf, nynf,                &
6736                                        nys_on_file, nyn_on_file,              &
6737                                        nxl_on_file,nxr_on_file )
6738
6739             CASE ( 't_wall_v(1)' )
6740                IF ( k == 1 )  THEN
6741                   IF ( .NOT.  ALLOCATED( t_wall_v_1(1)%t ) )                  &
6742                      ALLOCATE( t_wall_v_1(1)%t(nzb_wall:nzt_wall+1,           &
6743                                                1:surf_usm_v(1)%ns) )
6744                   READ ( 13 )  tmp_wall_v(1)%t
6745                ENDIF
6746                CALL surface_restore_elements(                                 &
6747                                        t_wall_v_1(1)%t, tmp_wall_v(1)%t,      &
6748                                        surf_usm_v(1)%start_index,             & 
6749                                        start_index_on_file,                   &
6750                                        end_index_on_file,                     &
6751                                        nxlc, nysc,                            &
6752                                        nxlf, nxrf, nysf, nynf,                &
6753                                        nys_on_file, nyn_on_file,              &
6754                                        nxl_on_file,nxr_on_file )
6755
6756             CASE ( 't_wall_v(2)' )
6757                IF ( k == 1 )  THEN
6758                   IF ( .NOT.  ALLOCATED( t_wall_v_1(2)%t ) )                  &
6759                      ALLOCATE( t_wall_v_1(2)%t(nzb_wall:nzt_wall+1,           &
6760                                                1:surf_usm_v(2)%ns) )
6761                   READ ( 13 )  tmp_wall_v(2)%t
6762                ENDIF
6763                CALL surface_restore_elements(                                 &
6764                                        t_wall_v_1(2)%t, tmp_wall_v(2)%t,      &
6765                                        surf_usm_v(2)%start_index,             & 
6766                                        start_index_on_file,                   &
6767                                        end_index_on_file ,                    &
6768                                        nxlc, nysc,                            &
6769                                        nxlf, nxrf, nysf, nynf,                &
6770                                        nys_on_file, nyn_on_file,              &
6771                                        nxl_on_file,nxr_on_file )
6772
6773             CASE ( 't_wall_v(3)' )
6774                IF ( k == 1 )  THEN
6775                   IF ( .NOT.  ALLOCATED( t_wall_v_1(3)%t ) )                  &
6776                      ALLOCATE( t_wall_v_1(3)%t(nzb_wall:nzt_wall+1,           &
6777                                                1:surf_usm_v(3)%ns) )
6778                   READ ( 13 )  tmp_wall_v(3)%t
6779                ENDIF
6780                CALL surface_restore_elements(                                 &
6781                                        t_wall_v_1(3)%t, tmp_wall_v(3)%t,      &
6782                                        surf_usm_v(3)%start_index,             &   
6783                                        start_index_on_file,                   &
6784                                        end_index_on_file,                     &
6785                                        nxlc, nysc,                            &
6786                                        nxlf, nxrf, nysf, nynf,                &
6787                                        nys_on_file, nyn_on_file,              &
6788                                        nxl_on_file,nxr_on_file )
6789
6790             CASE ( 't_green_h' )
6791                IF ( k == 1 )  THEN
6792                   IF ( .NOT.  ALLOCATED( t_green_h_1 ) )                      &
6793                      ALLOCATE( t_green_h_1(nzb_wall:nzt_wall+1,               &
6794                                            1:surf_usm_h%ns) )
6795                   READ ( 13 )  tmp_green_h
6796                ENDIF
6797                CALL surface_restore_elements(                                 &
6798                                        t_green_h_1, tmp_green_h,              &
6799                                        surf_usm_h%start_index,                & 
6800                                        start_index_on_file,                   &
6801                                        end_index_on_file,                     &
6802                                        nxlc, nysc,                            &
6803                                        nxlf, nxrf, nysf, nynf,                &
6804                                        nys_on_file, nyn_on_file,              &
6805                                        nxl_on_file,nxr_on_file )
6806
6807             CASE ( 't_green_v(0)' )
6808                IF ( k == 1 )  THEN
6809                   IF ( .NOT.  ALLOCATED( t_green_v_1(0)%t ) )                 &
6810                      ALLOCATE( t_green_v_1(0)%t(nzb_wall:nzt_wall+1,          &
6811                                                 1:surf_usm_v(0)%ns) )
6812                   READ ( 13 )  tmp_green_v(0)%t
6813                ENDIF
6814                CALL surface_restore_elements(                                 &
6815                                        t_green_v_1(0)%t, tmp_green_v(0)%t,    &
6816                                        surf_usm_v(0)%start_index,             & 
6817                                        start_index_on_file,                   &
6818                                        end_index_on_file,                     &
6819                                        nxlc, nysc,                            &
6820                                        nxlf, nxrf, nysf, nynf,                &
6821                                        nys_on_file, nyn_on_file,              &
6822                                        nxl_on_file,nxr_on_file )
6823
6824             CASE ( 't_green_v(1)' )
6825                IF ( k == 1 )  THEN
6826                   IF ( .NOT.  ALLOCATED( t_green_v_1(1)%t ) )                 &
6827                      ALLOCATE( t_green_v_1(1)%t(nzb_wall:nzt_wall+1,          &
6828                                                 1:surf_usm_v(1)%ns) )
6829                   READ ( 13 )  tmp_green_v(1)%t
6830                ENDIF
6831                CALL surface_restore_elements(                                 &
6832                                        t_green_v_1(1)%t, tmp_green_v(1)%t,    &
6833                                        surf_usm_v(1)%start_index,             & 
6834                                        start_index_on_file,                   &
6835                                        end_index_on_file,                     &
6836                                        nxlc, nysc,                            &
6837                                        nxlf, nxrf, nysf, nynf,                &
6838                                        nys_on_file, nyn_on_file,              &
6839                                        nxl_on_file,nxr_on_file )
6840
6841             CASE ( 't_green_v(2)' )
6842                IF ( k == 1 )  THEN
6843                   IF ( .NOT.  ALLOCATED( t_green_v_1(2)%t ) )                 &
6844                      ALLOCATE( t_green_v_1(2)%t(nzb_wall:nzt_wall+1,          &
6845                                                 1:surf_usm_v(2)%ns) )
6846                   READ ( 13 )  tmp_green_v(2)%t
6847                ENDIF
6848                CALL surface_restore_elements(                                 &
6849                                        t_green_v_1(2)%t, tmp_green_v(2)%t,    &
6850                                        surf_usm_v(2)%start_index,             & 
6851                                        start_index_on_file,                   &
6852                                        end_index_on_file ,                    &
6853                                        nxlc, nysc,                            &
6854                                        nxlf, nxrf, nysf, nynf,                &
6855                                        nys_on_file, nyn_on_file,              &
6856                                        nxl_on_file,nxr_on_file )
6857
6858             CASE ( 't_green_v(3)' )
6859                IF ( k == 1 )  THEN
6860                   IF ( .NOT.  ALLOCATED( t_green_v_1(3)%t ) )                 &
6861                      ALLOCATE( t_green_v_1(3)%t(nzb_wall:nzt_wall+1,          &
6862                                                 1:surf_usm_v(3)%ns) )
6863                   READ ( 13 )  tmp_green_v(3)%t
6864                ENDIF
6865                CALL surface_restore_elements(                                 &
6866                                        t_green_v_1(3)%t, tmp_green_v(3)%t,    &
6867                                        surf_usm_v(3)%start_index,             & 
6868                                        start_index_on_file,                   &
6869                                        end_index_on_file,                     &
6870                                        nxlc, nysc,                            &
6871                                        nxlf, nxrf, nysf, nynf,                &
6872                                        nys_on_file, nyn_on_file,              &
6873                                        nxl_on_file,nxr_on_file )
6874
6875             CASE ( 't_window_h' )
6876                IF ( k == 1 )  THEN
6877                   IF ( .NOT.  ALLOCATED( t_window_h_1 ) )                     &
6878                      ALLOCATE( t_window_h_1(nzb_wall:nzt_wall+1,              &
6879                                             1:surf_usm_h%ns) )
6880                   READ ( 13 )  tmp_window_h
6881                ENDIF
6882                CALL surface_restore_elements(                                 &
6883                                        t_window_h_1, tmp_window_h,            &
6884                                        surf_usm_h%start_index,                & 
6885                                        start_index_on_file,                   &
6886                                        end_index_on_file,                     &
6887                                        nxlc, nysc,                            &
6888                                        nxlf, nxrf, nysf, nynf,                &
6889                                        nys_on_file, nyn_on_file,              &
6890                                        nxl_on_file, nxr_on_file )
6891
6892             CASE ( 't_window_v(0)' )
6893                IF ( k == 1 )  THEN
6894                   IF ( .NOT.  ALLOCATED( t_window_v_1(0)%t ) )                &
6895                      ALLOCATE( t_window_v_1(0)%t(nzb_wall:nzt_wall+1,         &
6896                                                  1:surf_usm_v(0)%ns) )
6897                   READ ( 13 )  tmp_window_v(0)%t
6898                ENDIF
6899                CALL surface_restore_elements(                                 &
6900                                        t_window_v_1(0)%t,                     & 
6901                                        tmp_window_v(0)%t,                     &
6902                                        surf_usm_v(0)%start_index,             &
6903                                        start_index_on_file,                   &
6904                                        end_index_on_file,                     &
6905                                        nxlc, nysc,                            &
6906                                        nxlf, nxrf, nysf, nynf,                &
6907                                        nys_on_file, nyn_on_file,              &
6908                                        nxl_on_file,nxr_on_file )
6909
6910             CASE ( 't_window_v(1)' )
6911                IF ( k == 1 )  THEN
6912                   IF ( .NOT.  ALLOCATED( t_window_v_1(1)%t ) )                &
6913                      ALLOCATE( t_window_v_1(1)%t(nzb_wall:nzt_wall+1,         &
6914                                                  1:surf_usm_v(1)%ns) )
6915                   READ ( 13 )  tmp_window_v(1)%t
6916                ENDIF
6917                CALL surface_restore_elements(                                 &
6918                                        t_window_v_1(1)%t,                     & 
6919                                        tmp_window_v(1)%t,                     &
6920                                        surf_usm_v(1)%start_index,             & 
6921                                        start_index_on_file,                   &
6922                                        end_index_on_file,                     &
6923                                        nxlc, nysc,                            &
6924                                        nxlf, nxrf, nysf, nynf,                &
6925                                        nys_on_file, nyn_on_file,              &
6926                                        nxl_on_file,nxr_on_file )
6927
6928             CASE ( 't_window_v(2)' )
6929                IF ( k == 1 )  THEN
6930                   IF ( .NOT.  ALLOCATED( t_window_v_1(2)%t ) )                &
6931                      ALLOCATE( t_window_v_1(2)%t(nzb_wall:nzt_wall+1,         &
6932                                                  1:surf_usm_v(2)%ns) )
6933                   READ ( 13 )  tmp_window_v(2)%t
6934                ENDIF
6935                CALL surface_restore_elements(                                 &
6936                                        t_window_v_1(2)%t,                     & 
6937                                        tmp_window_v(2)%t,                     &
6938                                        surf_usm_v(2)%start_index,             & 
6939                                        start_index_on_file,                   &
6940                                        end_index_on_file ,                    &
6941                                        nxlc, nysc,                            &
6942                                        nxlf, nxrf, nysf, nynf,                &
6943                                        nys_on_file, nyn_on_file,              &
6944                                        nxl_on_file,nxr_on_file )
6945
6946             CASE ( 't_window_v(3)' )
6947                IF ( k == 1 )  THEN
6948                   IF ( .NOT.  ALLOCATED( t_window_v_1(3)%t ) )                &
6949                      ALLOCATE( t_window_v_1(3)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(3)%ns) )
6950                   READ ( 13 )  tmp_window_v(3)%t
6951                ENDIF
6952                CALL surface_restore_elements(                                 &
6953                                        t_window_v_1(3)%t,                     & 
6954                                        tmp_window_v(3)%t,                     &
6955                                        surf_usm_v(3)%start_index,             & 
6956                                        start_index_on_file,                   &
6957                                        end_index_on_file,                     &
6958                                        nxlc, nysc,                            &
6959                                        nxlf, nxrf, nysf, nynf,                &
6960                                        nys_on_file, nyn_on_file,              &
6961                                        nxl_on_file,nxr_on_file )
6962
6963             CASE DEFAULT
6964
6965                   found = .FALSE.
6966
6967          END SELECT
6968
6969       
6970    END SUBROUTINE usm_rrd_local
6971
6972   
6973!------------------------------------------------------------------------------!
6974! Description:
6975! ------------
6976!
6977!> This subroutine reads walls, roofs and land categories and it parameters
6978!> from input files.
6979!------------------------------------------------------------------------------!
6980    SUBROUTINE usm_read_urban_surface_types
6981   
6982        USE netcdf_data_input_mod,                                             &
6983            ONLY:  building_pars_f, building_type_f
6984
6985        IMPLICIT NONE
6986
6987        CHARACTER(12)                                         :: wtn
6988        INTEGER(iwp)                                          :: wtc
6989        REAL(wp), DIMENSION(n_surface_params)                 :: wtp
6990        LOGICAL                                               :: ascii_file = .FALSE.
6991        INTEGER(iwp), DIMENSION(0:17, nysg:nyng, nxlg:nxrg)   :: usm_par
6992        REAL(wp), DIMENSION(1:14, nysg:nyng, nxlg:nxrg)       :: usm_val
6993        INTEGER(iwp)                                          :: k, l, iw, jw, kw, it, ip, ii, ij, m
6994        INTEGER(iwp)                                          :: i, j
6995        INTEGER(iwp)                                          :: nz, roof, dirwe, dirsn
6996        INTEGER(iwp)                                          :: category
6997        INTEGER(iwp)                                          :: weheight1, wecat1, snheight1, sncat1
6998        INTEGER(iwp)                                          :: weheight2, wecat2, snheight2, sncat2
6999        INTEGER(iwp)                                          :: weheight3, wecat3, snheight3, sncat3
7000        REAL(wp)                                              :: height, albedo, thick
7001        REAL(wp)                                              :: wealbedo1, wethick1, snalbedo1, snthick1
7002        REAL(wp)                                              :: wealbedo2, wethick2, snalbedo2, snthick2
7003        REAL(wp)                                              :: wealbedo3, wethick3, snalbedo3, snthick3
7004
7005
7006        IF ( debug_output )  CALL debug_message( 'usm_read_urban_surface_types', 'start' )
7007!
7008!--     If building_pars or building_type are already read from static input
7009!--     file, skip reading ASCII file.
7010        IF ( building_type_f%from_file  .OR.  building_pars_f%from_file )      &
7011           RETURN
7012!
7013!--     Check if ASCII input file exists. If not, return and initialize USM
7014!--     with default settings.
7015        INQUIRE( FILE = 'SURFACE_PARAMETERS' // coupling_char,                 &
7016                 EXIST = ascii_file )
7017                 
7018        IF ( .NOT. ascii_file )  RETURN
7019
7020!
7021!--     read categories of walls and their parameters
7022        DO  ii = 0, io_blocks-1
7023            IF ( ii == io_group )  THEN
7024!
7025!--             open urban surface file
7026                OPEN( 151, file='SURFACE_PARAMETERS'//coupling_char, action='read', &
7027                           status='old', form='formatted', err=15 )
7028!
7029!--             first test and get n_surface_types
7030                k = 0
7031                l = 0
7032                DO
7033                    l = l+1
7034                    READ( 151, *, err=11, end=12 )  wtc, wtp, wtn
7035                    k = k+1
7036                    CYCLE
7037 11                 CONTINUE
7038                ENDDO
7039 12             n_surface_types = k
7040                ALLOCATE( surface_type_names(n_surface_types) )
7041                ALLOCATE( surface_type_codes(n_surface_types) )
7042                ALLOCATE( surface_params(n_surface_params, n_surface_types) )
7043!
7044!--             real reading
7045                rewind( 151 )
7046                k = 0
7047                DO
7048                    READ( 151, *, err=13, end=14 )  wtc, wtp, wtn
7049                    k = k+1
7050                    surface_type_codes(k) = wtc
7051                    surface_params(:,k) = wtp
7052                    surface_type_names(k) = wtn
7053                    CYCLE
705413                  WRITE(6,'(i3,a,2i5)') myid, 'readparams2 error k=', k
7055                    FLUSH(6)
7056                    CONTINUE
7057                ENDDO
7058 14             CLOSE(151)
7059                CYCLE
7060 15             message_string = 'file SURFACE_PARAMETERS'//TRIM(coupling_char)//' does not exist'
7061                CALL message( 'usm_read_urban_surface_types', 'PA0513', 1, 2, 0, 6, 0 )
7062            ENDIF
7063        ENDDO
7064   
7065!
7066!--     read types of surfaces
7067        usm_par = 0
7068        DO  ii = 0, io_blocks-1
7069            IF ( ii == io_group )  THEN
7070
7071!
7072!--             open csv urban surface file
7073                OPEN( 151, file='URBAN_SURFACE'//TRIM(coupling_char), action='read', &
7074                      status='old', form='formatted', err=23 )
7075               
7076                l = 0
7077                DO
7078                    l = l+1
7079!
7080!--                 i, j, height, nz, roof, dirwe, dirsn, category, soilcat,
7081!--                 weheight1, wecat1, snheight1, sncat1, weheight2, wecat2, snheight2, sncat2,
7082!--                 weheight3, wecat3, snheight3, sncat3
7083                    READ( 151, *, err=21, end=25 )  i, j, height, nz, roof, dirwe, dirsn,            &
7084                                            category, albedo, thick,                                 &
7085                                            weheight1, wecat1, wealbedo1, wethick1,                  &
7086                                            weheight2, wecat2, wealbedo2, wethick2,                  &
7087                                            weheight3, wecat3, wealbedo3, wethick3,                  &
7088                                            snheight1, sncat1, snalbedo1, snthick1,                  &
7089                                            snheight2, sncat2, snalbedo2, snthick2,                  &
7090                                            snheight3, sncat3, snalbedo3, snthick3
7091
7092                    IF ( i >= nxlg  .AND.  i <= nxrg  .AND.  j >= nysg  .AND.  j <= nyng )  THEN
7093!
7094!--                     write integer variables into array
7095                        usm_par(:,j,i) = (/1, nz, roof, dirwe, dirsn, category,                      &
7096                                          weheight1, wecat1, weheight2, wecat2, weheight3, wecat3,   &
7097                                          snheight1, sncat1, snheight2, sncat2, snheight3, sncat3 /)
7098!
7099!--                     write real values into array
7100                        usm_val(:,j,i) = (/ albedo, thick,                                           &
7101                                           wealbedo1, wethick1, wealbedo2, wethick2,                 &
7102                                           wealbedo3, wethick3, snalbedo1, snthick1,                 &
7103                                           snalbedo2, snthick2, snalbedo3, snthick3 /)
7104                    ENDIF
7105                    CYCLE
7106 21                 WRITE (message_string, "(A,I5)") 'errors in file URBAN_SURFACE'//TRIM(coupling_char)//' on line ', l
7107                    CALL message( 'usm_read_urban_surface_types', 'PA0512', 0, 1, 0, 6, 0 )
7108                ENDDO
7109         
7110 23             message_string = 'file URBAN_SURFACE'//TRIM(coupling_char)//' does not exist'
7111                CALL message( 'usm_read_urban_surface_types', 'PA0514', 1, 2, 0, 6, 0 )
7112
7113 25             CLOSE( 151 )
7114
7115            ENDIF
7116#if defined( __parallel )
7117            CALL MPI_BARRIER( comm2d, ierr )
7118#endif
7119        ENDDO
7120       
7121!
7122!--     check completeness and formal correctness of the data
7123        DO i = nxlg, nxrg
7124            DO j = nysg, nyng
7125                IF ( usm_par(0,j,i) /= 0  .AND.  (        &  !< incomplete data,supply default values later
7126                     usm_par(1,j,i) < nzb  .OR.           &
7127                     usm_par(1,j,i) > nzt  .OR.           &  !< incorrect height (nz < nzb  .OR.  nz > nzt)
7128                     usm_par(2,j,i) < 0  .OR.             &
7129                     usm_par(2,j,i) > 1  .OR.             &  !< incorrect roof sign
7130                     usm_par(3,j,i) < nzb-nzt  .OR.       & 
7131                     usm_par(3,j,i) > nzt-nzb  .OR.       &  !< incorrect west-east wall direction sign
7132                     usm_par(4,j,i) < nzb-nzt  .OR.       &
7133                     usm_par(4,j,i) > nzt-nzb  .OR.       &  !< incorrect south-north wall direction sign
7134                     usm_par(6,j,i) < nzb  .OR.           & 
7135                     usm_par(6,j,i) > nzt  .OR.           &  !< incorrect pedestrian level height for west-east wall
7136                     usm_par(8,j,i) > nzt  .OR.           &
7137                     usm_par(10,j,i) > nzt  .OR.          &  !< incorrect wall or roof level height for west-east wall
7138                     usm_par(12,j,i) < nzb  .OR.          & 
7139                     usm_par(12,j,i) > nzt  .OR.          &  !< incorrect pedestrian level height for south-north wall
7140                     usm_par(14,j,i) > nzt  .OR.          &
7141                     usm_par(16,j,i) > nzt                &  !< incorrect wall or roof level height for south-north wall
7142                    ) )  THEN
7143!
7144!--                 incorrect input data
7145                    WRITE (message_string, "(A,2I5)") 'missing or incorrect data in file URBAN_SURFACE'// &
7146                                                       TRIM(coupling_char)//' for i,j=', i,j
7147                    CALL message( 'usm_read_urban_surface', 'PA0504', 1, 2, 0, 6, 0 )
7148                ENDIF
7149               
7150            ENDDO
7151        ENDDO
7152!       
7153!--     Assign the surface types to the respective data type.
7154!--     First, for horizontal upward-facing surfaces.
7155!--     Further, set flag indicating that albedo is initialized via ASCII
7156!--     format, else it would be overwritten in the radiation model.
7157        surf_usm_h%albedo_from_ascii = .TRUE.
7158        DO  m = 1, surf_usm_h%ns
7159           iw = surf_usm_h%i(m)
7160           jw = surf_usm_h%j(m)
7161           kw = surf_usm_h%k(m)
7162
7163           IF ( usm_par(5,jw,iw) == 0 )  THEN
7164
7165              IF ( zu(kw) >= roof_height_limit )  THEN
7166                 surf_usm_h%isroof_surf(m)   = .TRUE.
7167                 surf_usm_h%surface_types(m) = roof_category         !< default category for root surface
7168              ELSE
7169                 surf_usm_h%isroof_surf(m)   = .FALSE.
7170                 surf_usm_h%surface_types(m) = land_category         !< default category for land surface
7171              ENDIF
7172
7173              surf_usm_h%albedo(:,m)    = -1.0_wp
7174              surf_usm_h%thickness_wall(m) = -1.0_wp
7175              surf_usm_h%thickness_green(m) = -1.0_wp
7176              surf_usm_h%thickness_window(m) = -1.0_wp
7177           ELSE
7178              IF ( usm_par(2,jw,iw)==0 )  THEN
7179                 surf_usm_h%isroof_surf(m)    = .FALSE.
7180                 surf_usm_h%thickness_wall(m) = -1.0_wp
7181                 surf_usm_h%thickness_window(m) = -1.0_wp
7182                 surf_usm_h%thickness_green(m)  = -1.0_wp
7183              ELSE
7184                 surf_usm_h%isroof_surf(m)    = .TRUE.
7185                 surf_usm_h%thickness_wall(m) = usm_val(2,jw,iw)
7186                 surf_usm_h%thickness_window(m) = usm_val(2,jw,iw)
7187                 surf_usm_h%thickness_green(m)  = usm_val(2,jw,iw)
7188              ENDIF
7189              surf_usm_h%surface_types(m) = usm_par(5,jw,iw)
7190              surf_usm_h%albedo(:,m)   = usm_val(1,jw,iw)
7191              surf_usm_h%transmissivity(m)    = 0.0_wp
7192           ENDIF
7193!
7194!--        Find the type position
7195           it = surf_usm_h%surface_types(m)
7196           ip = -99999
7197           DO k = 1, n_surface_types
7198              IF ( surface_type_codes(k) == it )  THEN
7199                 ip = k
7200                 EXIT
7201              ENDIF
7202           ENDDO
7203           IF ( ip == -99999 )  THEN
7204!
7205!--           land/roof category not found
7206              WRITE (9,"(A,I5,A,3I5)") 'land/roof category ', it,     &
7207                                       ' not found  for i,j,k=', iw,jw,kw
7208              FLUSH(9)
7209              IF ( surf_usm_h%isroof_surf(m) ) THEN
7210                 category = roof_category
7211              ELSE
7212                 category = land_category
7213              ENDIF
7214              DO k = 1, n_surface_types
7215                 IF ( surface_type_codes(k) == roof_category ) THEN
7216                    ip = k
7217                    EXIT
7218                 ENDIF
7219              ENDDO
7220              IF ( ip == -99999 )  THEN
7221!
7222!--              default land/roof category not found
7223                 WRITE (9,"(A,I5,A,3I5)") 'Default land/roof category', category, ' not found!'
7224                 FLUSH(9)
7225                 ip = 1
7226              ENDIF
7227           ENDIF
7228!
7229!--        Albedo
7230           IF ( surf_usm_h%albedo(ind_veg_wall,m) < 0.0_wp )  THEN
7231              surf_usm_h%albedo(:,m) = surface_params(ialbedo,ip)
7232           ENDIF
7233!
7234!--        Albedo type is 0 (custom), others are replaced later
7235           surf_usm_h%albedo_type(:,m) = 0
7236!
7237!--        Transmissivity
7238           IF ( surf_usm_h%transmissivity(m) < 0.0_wp )  THEN
7239              surf_usm_h%transmissivity(m) = 0.0_wp
7240           ENDIF
7241!
7242!--        emissivity of the wall
7243           surf_usm_h%emissivity(:,m) = surface_params(iemiss,ip)
7244!           
7245!--        heat conductivity λS between air and wall ( W m−2 K−1 )
7246           surf_usm_h%lambda_surf(m) = surface_params(ilambdas,ip)
7247           surf_usm_h%lambda_surf_window(m) = surface_params(ilambdas,ip)
7248           surf_usm_h%lambda_surf_green(m)  = surface_params(ilambdas,ip)
7249!           
7250!--        roughness length for momentum, heat and humidity
7251           surf_usm_h%z0(m) = surface_params(irough,ip)
7252           surf_usm_h%z0h(m) = surface_params(iroughh,ip)
7253           surf_usm_h%z0q(m) = surface_params(iroughh,ip)
7254!
7255!--        Surface skin layer heat capacity (J m−2 K−1 )
7256           surf_usm_h%c_surface(m) = surface_params(icsurf,ip)
7257           surf_usm_h%c_surface_window(m) = surface_params(icsurf,ip)
7258           surf_usm_h%c_surface_green(m)  = surface_params(icsurf,ip)
7259!           
7260!--        wall material parameters:
7261!--        thickness of the wall (m)
7262!--        missing values are replaced by default value for category
7263           IF ( surf_usm_h%thickness_wall(m) <= 0.001_wp )  THEN
7264                surf_usm_h%thickness_wall(m) = surface_params(ithick,ip)
7265           ENDIF
7266           IF ( surf_usm_h%thickness_window(m) <= 0.001_wp )  THEN
7267                surf_usm_h%thickness_window(m) = surface_params(ithick,ip)
7268           ENDIF
7269           IF ( surf_usm_h%thickness_green(m) <= 0.001_wp )  THEN
7270                surf_usm_h%thickness_green(m) = surface_params(ithick,ip)
7271           ENDIF
7272!           
7273!--        volumetric heat capacity rho*C of the wall ( J m−3 K−1 )
7274           surf_usm_h%rho_c_wall(:,m) = surface_params(irhoC,ip)
7275           surf_usm_h%rho_c_window(:,m) = surface_params(irhoC,ip)
7276           surf_usm_h%rho_c_green(:,m)  = surface_params(irhoC,ip)
7277!           
7278!--        thermal conductivity λH of the wall (W m−1 K−1 )
7279           surf_usm_h%lambda_h(:,m) = surface_params(ilambdah,ip)
7280           surf_usm_h%lambda_h_window(:,m) = surface_params(ilambdah,ip)
7281           surf_usm_h%lambda_h_green(:,m)  = surface_params(ilambdah,ip)
7282
7283        ENDDO
7284!
7285!--     For vertical surface elements ( 0 -- northward-facing, 1 -- southward-facing,
7286!--     2 -- eastward-facing, 3 -- westward-facing )
7287        DO  l = 0, 3
7288!
7289!--        Set flag indicating that albedo is initialized via ASCII format.
7290!--        Else it would be overwritten in the radiation model.
7291           surf_usm_v(l)%albedo_from_ascii = .TRUE.
7292           DO  m = 1, surf_usm_v(l)%ns
7293              i  = surf_usm_v(l)%i(m)
7294              j  = surf_usm_v(l)%j(m)
7295              kw = surf_usm_v(l)%k(m)
7296             
7297              IF ( l == 3 )  THEN ! westward facing
7298                 iw = i
7299                 jw = j
7300                 ii = 6
7301                 ij = 3
7302              ELSEIF ( l == 2 )  THEN
7303                 iw = i-1
7304                 jw = j
7305                 ii = 6
7306                 ij = 3
7307              ELSEIF ( l == 1 )  THEN
7308                 iw = i
7309                 jw = j
7310                 ii = 12
7311                 ij = 9
7312              ELSEIF ( l == 0 )  THEN
7313                 iw = i
7314                 jw = j-1
7315                 ii = 12
7316                 ij = 9
7317              ENDIF
7318
7319              IF ( iw < 0 .OR. jw < 0 ) THEN
7320!
7321!--              wall on west or south border of the domain - assign default category
7322                 IF ( kw <= roof_height_limit ) THEN
7323                     surf_usm_v(l)%surface_types(m) = wall_category   !< default category for wall surface in wall zone
7324                 ELSE
7325                     surf_usm_v(l)%surface_types(m) = roof_category   !< default category for wall surface in roof zone
7326                 END IF
7327                 surf_usm_v(l)%albedo(:,m)         = -1.0_wp
7328                 surf_usm_v(l)%thickness_wall(m)   = -1.0_wp
7329                 surf_usm_v(l)%thickness_window(m) = -1.0_wp
7330                 surf_usm_v(l)%thickness_green(m)  = -1.0_wp
7331                 surf_usm_v(l)%transmissivity(m)   = -1.0_wp
7332              ELSE IF ( kw <= usm_par(ii,jw,iw) )  THEN
7333!
7334!--                 pedestrian zone
7335                 IF ( usm_par(ii+1,jw,iw) == 0 )  THEN
7336                     surf_usm_v(l)%surface_types(m)  = pedestrian_category   !< default category for wall surface in
7337                                                                             !<pedestrian zone
7338                     surf_usm_v(l)%albedo(:,m)         = -1.0_wp
7339                     surf_usm_v(l)%thickness_wall(m)   = -1.0_wp
7340                     surf_usm_v(l)%thickness_window(m) = -1.0_wp
7341                     surf_usm_v(l)%thickness_green(m)  = -1.0_wp
7342                     surf_usm_v(l)%transmissivity(m)   = -1.0_wp
7343                 ELSE
7344                     surf_usm_v(l)%surface_types(m)    = usm_par(ii+1,jw,iw)
7345                     surf_usm_v(l)%albedo(:,m)         = usm_val(ij,jw,iw)
7346                     surf_usm_v(l)%thickness_wall(m)   = usm_val(ij+1,jw,iw)
7347                     surf_usm_v(l)%thickness_window(m) = usm_val(ij+1,jw,iw)
7348                     surf_usm_v(l)%thickness_green(m)  = usm_val(ij+1,jw,iw)
7349                     surf_usm_v(l)%transmissivity(m)   = 0.0_wp
7350                 ENDIF
7351              ELSE IF ( kw <= usm_par(ii+2,jw,iw) )  THEN
7352!
7353!--              wall zone
7354                 IF ( usm_par(ii+3,jw,iw) == 0 )  THEN
7355                     surf_usm_v(l)%surface_types(m)    = wall_category         !< default category for wall surface
7356                     surf_usm_v(l)%albedo(:,m)         = -1.0_wp
7357                     surf_usm_v(l)%thickness_wall(m)   = -1.0_wp
7358                     surf_usm_v(l)%thickness_window(m) = -1.0_wp
7359                     surf_usm_v(l)%thickness_green(m)  = -1.0_wp
7360                     surf_usm_v(l)%transmissivity(m)   = -1.0_wp
7361                 ELSE
7362                     surf_usm_v(l)%surface_types(m)    = usm_par(ii+3,jw,iw)
7363                     surf_usm_v(l)%albedo(:,m)         = usm_val(ij+2,jw,iw)
7364                     surf_usm_v(l)%thickness_wall(m)   = usm_val(ij+3,jw,iw)
7365                     surf_usm_v(l)%thickness_window(m) = usm_val(ij+3,jw,iw)
7366                     surf_usm_v(l)%thickness_green(m)  = usm_val(ij+3,jw,iw)
7367                     surf_usm_v(l)%transmissivity(m)   = 0.0_wp
7368                 ENDIF
7369              ELSE IF ( kw <= usm_par(ii+4,jw,iw) )  THEN
7370!
7371!--              roof zone
7372                 IF ( usm_par(ii+5,jw,iw) == 0 )  THEN
7373                     surf_usm_v(l)%surface_types(m)    = roof_category         !< default category for roof surface
7374                     surf_usm_v(l)%albedo(:,m)         = -1.0_wp
7375                     surf_usm_v(l)%thickness_wall(m)   = -1.0_wp
7376                     surf_usm_v(l)%thickness_window(m) = -1.0_wp
7377                     surf_usm_v(l)%thickness_green(m)  = -1.0_wp
7378                     surf_usm_v(l)%transmissivity(m)   = -1.0_wp
7379                 ELSE
7380                     surf_usm_v(l)%surface_types(m)    = usm_par(ii+5,jw,iw)
7381                     surf_usm_v(l)%albedo(:,m)         = usm_val(ij+4,jw,iw)
7382                     surf_usm_v(l)%thickness_wall(m)   = usm_val(ij+5,jw,iw)
7383                     surf_usm_v(l)%thickness_window(m) = usm_val(ij+5,jw,iw)
7384                     surf_usm_v(l)%thickness_green(m)  = usm_val(ij+5,jw,iw)
7385                     surf_usm_v(l)%transmissivity(m)   = 0.0_wp
7386                 ENDIF
7387              ELSE
7388                 WRITE(9,*) 'Problem reading USM data:'
7389                 WRITE(9,*) l,i,j,kw,get_topography_top_index_ji( j, i, 's' )
7390                 WRITE(9,*) ii,iw,jw,kw,get_topography_top_index_ji( jw, iw, 's' )
7391                 WRITE(9,*) usm_par(ii,jw,iw),usm_par(ii+1,jw,iw)
7392                 WRITE(9,*) usm_par(ii+2,jw,iw),usm_par(ii+3,jw,iw)
7393                 WRITE(9,*) usm_par(ii+4,jw,iw),usm_par(ii+5,jw,iw)
7394                 WRITE(9,*) kw,roof_height_limit,wall_category,roof_category
7395                 FLUSH(9)
7396!
7397!--              supply the default category
7398                 IF ( kw <= roof_height_limit ) THEN
7399                     surf_usm_v(l)%surface_types(m) = wall_category   !< default category for wall surface in wall zone
7400                 ELSE
7401                     surf_usm_v(l)%surface_types(m) = roof_category   !< default category for wall surface in roof zone
7402                 END IF
7403                 surf_usm_v(l)%albedo(:,m)         = -1.0_wp
7404                 surf_usm_v(l)%thickness_wall(m)   = -1.0_wp
7405                 surf_usm_v(l)%thickness_window(m) = -1.0_wp
7406                 surf_usm_v(l)%thickness_green(m)  = -1.0_wp
7407                 surf_usm_v(l)%transmissivity(m)   = -1.0_wp
7408              ENDIF
7409!
7410!--           Find the type position
7411              it = surf_usm_v(l)%surface_types(m)
7412              ip = -99999
7413              DO k = 1, n_surface_types
7414                 IF ( surface_type_codes(k) == it )  THEN
7415                    ip = k
7416                    EXIT
7417                 ENDIF
7418              ENDDO
7419              IF ( ip == -99999 )  THEN
7420!
7421!--              wall category not found
7422                 WRITE (9, "(A,I7,A,3I5)") 'wall category ', it,  &
7423                                           ' not found  for i,j,k=', iw,jw,kw
7424                 FLUSH(9)
7425                 category = wall_category 
7426                 DO k = 1, n_surface_types
7427                    IF ( surface_type_codes(k) == category ) THEN
7428                       ip = k
7429                       EXIT
7430                    ENDIF
7431                 ENDDO
7432                 IF ( ip == -99999 )  THEN
7433!
7434!--                 default wall category not found
7435                    WRITE (9, "(A,I5,A,3I5)") 'Default wall category', category, ' not found!'
7436                    FLUSH(9)
7437                    ip = 1
7438                 ENDIF
7439              ENDIF
7440
7441!
7442!--           Albedo
7443              IF ( surf_usm_v(l)%albedo(ind_veg_wall,m) < 0.0_wp )  THEN
7444                 surf_usm_v(l)%albedo(:,m) = surface_params(ialbedo,ip)
7445              ENDIF
7446!--           Albedo type is 0 (custom), others are replaced later
7447              surf_usm_v(l)%albedo_type(:,m) = 0
7448!--           Transmissivity of the windows
7449              IF ( surf_usm_v(l)%transmissivity(m) < 0.0_wp )  THEN
7450                 surf_usm_v(l)%transmissivity(m) = 0.0_wp
7451              ENDIF
7452!
7453!--           emissivity of the wall
7454              surf_usm_v(l)%emissivity(:,m) = surface_params(iemiss,ip)
7455!           
7456!--           heat conductivity lambda S between air and wall ( W m-2 K-1 )
7457              surf_usm_v(l)%lambda_surf(m) = surface_params(ilambdas,ip)
7458              surf_usm_v(l)%lambda_surf_window(m) = surface_params(ilambdas,ip)
7459              surf_usm_v(l)%lambda_surf_green(m) = surface_params(ilambdas,ip)
7460!           
7461!--           roughness length
7462              surf_usm_v(l)%z0(m) = surface_params(irough,ip)
7463              surf_usm_v(l)%z0h(m) = surface_params(iroughh,ip)
7464              surf_usm_v(l)%z0q(m) = surface_params(iroughh,ip)
7465!           
7466!--           Surface skin layer heat capacity (J m-2 K-1 )
7467              surf_usm_v(l)%c_surface(m) = surface_params(icsurf,ip)
7468              surf_usm_v(l)%c_surface_window(m) = surface_params(icsurf,ip)
7469              surf_usm_v(l)%c_surface_green(m) = surface_params(icsurf,ip)
7470!           
7471!--           wall material parameters:
7472!--           thickness of the wall (m)
7473!--           missing values are replaced by default value for category
7474              IF ( surf_usm_v(l)%thickness_wall(m) <= 0.001_wp )  THEN
7475                   surf_usm_v(l)%thickness_wall(m) = surface_params(ithick,ip)
7476              ENDIF
7477              IF ( surf_usm_v(l)%thickness_window(m) <= 0.001_wp )  THEN
7478                   surf_usm_v(l)%thickness_window(m) = surface_params(ithick,ip)
7479              ENDIF
7480              IF ( surf_usm_v(l)%thickness_green(m) <= 0.001_wp )  THEN
7481                   surf_usm_v(l)%thickness_green(m) = surface_params(ithick,ip)
7482              ENDIF
7483!
7484!--           volumetric heat capacity rho*C of the wall ( J m-3 K-1 )
7485              surf_usm_v(l)%rho_c_wall(:,m) = surface_params(irhoC,ip)
7486              surf_usm_v(l)%rho_c_window(:,m) = surface_params(irhoC,ip)
7487              surf_usm_v(l)%rho_c_green(:,m) = surface_params(irhoC,ip)
7488!           
7489!--           thermal conductivity lambda H of the wall (W m-1 K-1 )
7490              surf_usm_v(l)%lambda_h(:,m) = surface_params(ilambdah,ip)
7491              surf_usm_v(l)%lambda_h_window(:,m) = surface_params(ilambdah,ip)
7492              surf_usm_v(l)%lambda_h_green(:,m) = surface_params(ilambdah,ip)
7493
7494           ENDDO
7495        ENDDO 
7496
7497!
7498!--     Initialize wall layer thicknesses. Please note, this will be removed
7499!--     after migration to Palm input data standard. 
7500        DO k = nzb_wall, nzt_wall
7501           zwn(k) = zwn_default(k)
7502           zwn_green(k) = zwn_default_green(k)
7503           zwn_window(k) = zwn_default_window(k)
7504        ENDDO
7505!
7506!--     apply for all particular surface grids. First for horizontal surfaces
7507        DO  m = 1, surf_usm_h%ns
7508           surf_usm_h%zw(:,m) = zwn(:) * surf_usm_h%thickness_wall(m)
7509           surf_usm_h%zw_green(:,m) = zwn_green(:) * surf_usm_h%thickness_green(m)
7510           surf_usm_h%zw_window(:,m) = zwn_window(:) * surf_usm_h%thickness_window(m)
7511        ENDDO
7512        DO  l = 0, 3
7513           DO  m = 1, surf_usm_v(l)%ns
7514              surf_usm_v(l)%zw(:,m) = zwn(:) * surf_usm_v(l)%thickness_wall(m)
7515              surf_usm_v(l)%zw_green(:,m) = zwn_green(:) * surf_usm_v(l)%thickness_green(m)
7516              surf_usm_v(l)%zw_window(:,m) = zwn_window(:) * surf_usm_v(l)%thickness_window(m)
7517           ENDDO
7518        ENDDO
7519
7520        IF ( debug_output )  CALL debug_message( 'usm_read_urban_surface_types', 'end' )
7521   
7522    END SUBROUTINE usm_read_urban_surface_types
7523
7524
7525!------------------------------------------------------------------------------!
7526! Description:
7527! ------------
7528!
7529!> This function advances through the list of local surfaces to find given
7530!> x, y, d, z coordinates
7531!------------------------------------------------------------------------------!
7532    PURE FUNCTION find_surface( x, y, z, d ) result(isurfl)
7533
7534        INTEGER(iwp), INTENT(in)                :: x, y, z, d
7535        INTEGER(iwp)                            :: isurfl
7536        INTEGER(iwp)                            :: isx, isy, isz
7537
7538        IF ( d == 0 ) THEN
7539           DO  isurfl = 1, surf_usm_h%ns
7540              isx = surf_usm_h%i(isurfl)
7541              isy = surf_usm_h%j(isurfl)
7542              isz = surf_usm_h%k(isurfl)
7543              IF ( isx==x .and. isy==y .and. isz==z )  RETURN
7544           ENDDO
7545        ELSE
7546           DO  isurfl = 1, surf_usm_v(d-1)%ns
7547              isx = surf_usm_v(d-1)%i(isurfl)
7548              isy = surf_usm_v(d-1)%j(isurfl)
7549              isz = surf_usm_v(d-1)%k(isurfl)
7550              IF ( isx==x .and. isy==y .and. isz==z )  RETURN
7551           ENDDO
7552        ENDIF
7553!
7554!--     coordinate not found
7555        isurfl = -1
7556
7557    END FUNCTION
7558
7559
7560!------------------------------------------------------------------------------!
7561! Description:
7562! ------------
7563!
7564!> This subroutine reads temperatures of respective material layers in walls,
7565!> roofs and ground from input files. Data in the input file must be in
7566!> standard order, i.e. horizontal surfaces first ordered by x, y and then
7567!> vertical surfaces ordered by x, y, direction, z
7568!------------------------------------------------------------------------------!
7569    SUBROUTINE usm_read_wall_temperature
7570
7571        INTEGER(iwp)                                          :: i, j, k, d, ii, iline  !> running indices
7572        INTEGER(iwp)                                          :: isurfl
7573        REAL(wp)                                              :: rtsurf
7574        REAL(wp), DIMENSION(nzb_wall:nzt_wall+1)              :: rtwall
7575
7576
7577        IF ( debug_output )  CALL debug_message( 'usm_read_wall_temperature', 'start' )
7578
7579        DO  ii = 0, io_blocks-1
7580            IF ( ii == io_group )  THEN
7581!
7582!--             open wall temperature file
7583                OPEN( 152, file='WALL_TEMPERATURE'//coupling_char, action='read', &
7584                           status='old', form='formatted', err=15 )
7585
7586                isurfl = 0
7587                iline = 1
7588                DO
7589                    rtwall = -9999.0_wp  !< for incomplete lines
7590                    READ( 152, *, err=13, end=14 )  i, j, k, d, rtsurf, rtwall
7591
7592                    IF ( nxl <= i .and. i <= nxr .and. &
7593                        nys <= j .and. j <= nyn)  THEN  !< local processor
7594!--                     identify surface id
7595                        isurfl = find_surface( i, j, k, d )
7596                        IF ( isurfl == -1 )  THEN
7597                            WRITE(message_string, '(a,4i5,a,i5,a)') 'Coordinates (xyzd) ', i, j, k, d, &
7598                                ' on line ', iline, &
7599                                ' in file WALL_TEMPERATURE are either not present or out of standard order of surfaces.'
7600                            CALL message( 'usm_read_wall_temperature', 'PA0521', 1, 2, 0, 6, 0 )
7601                        ENDIF
7602!
7603!--                     assign temperatures
7604                        IF ( d == 0 ) THEN
7605                           t_surf_wall_h(isurfl) = rtsurf
7606                           t_wall_h(:,isurfl) = rtwall(:)
7607                           t_window_h(:,isurfl) = rtwall(:)
7608                           t_green_h(:,isurfl) = rtwall(:)
7609                        ELSE
7610                           t_surf_wall_v(d-1)%t(isurfl) = rtsurf
7611                           t_wall_v(d-1)%t(:,isurfl) = rtwall(:)
7612                           t_window_v(d-1)%t(:,isurfl) = rtwall(:)
7613                           t_green_v(d-1)%t(:,isurfl) = rtwall(:)
7614                        ENDIF
7615                    ENDIF
7616
7617                    iline = iline + 1
7618                    CYCLE
7619 13                 WRITE(message_string, '(a,i5,a)') 'Error reading line ', iline, &
7620                        ' in file WALL_TEMPERATURE.'
7621                    CALL message( 'usm_read_wall_temperature', 'PA0522', 1, 2, 0, 6, 0 )
7622                ENDDO
7623 14             CLOSE(152)
7624                CYCLE
7625 15             message_string = 'file WALL_TEMPERATURE'//TRIM(coupling_char)//' does not exist'
7626                CALL message( 'usm_read_wall_temperature', 'PA0523', 1, 2, 0, 6, 0 )
7627            ENDIF
7628#if defined( __parallel )
7629            CALL MPI_BARRIER( comm2d, ierr )
7630#endif
7631        ENDDO
7632
7633        IF ( debug_output )  CALL debug_message( 'usm_read_wall_temperature', 'end' )
7634
7635    END SUBROUTINE usm_read_wall_temperature
7636
7637
7638
7639!------------------------------------------------------------------------------!
7640! Description:
7641! ------------
7642!> Solver for the energy balance at the ground/roof/wall surface.
7643!> It follows basic ideas and structure of lsm_energy_balance
7644!> with many simplifications and adjustments.
7645!> TODO better description
7646!> No calculation of window surface temperatures during spinup to increase
7647!> maximum possible timstep
7648!------------------------------------------------------------------------------!
7649    SUBROUTINE usm_surface_energy_balance( during_spinup )
7650
7651
7652        IMPLICIT NONE
7653
7654        INTEGER(iwp)                          :: i, j, k, l, m   !< running indices
7655       
7656        INTEGER(iwp) ::  i_off     !< offset to determine index of surface element, seen from atmospheric grid point, for x
7657        INTEGER(iwp) ::  j_off     !< offset to determine index of surface element, seen from atmospheric grid point, for y
7658        INTEGER(iwp) ::  k_off     !< offset to determine index of surface element, seen from atmospheric grid point, for z
7659
7660        LOGICAL                               :: during_spinup      !< flag indicating soil/wall spinup phase
7661       
7662        REAL(wp)                              :: frac_win           !< window fraction, used to restore original values during spinup
7663        REAL(wp)                              :: frac_green         !< green fraction, used to restore original values during spinup
7664        REAL(wp)                              :: frac_wall          !< wall fraction, used to restore original values during spinup
7665        REAL(wp)                              :: stend_wall         !< surface tendency
7666       
7667        REAL(wp)                              :: stend_window       !< surface tendency
7668        REAL(wp)                              :: stend_green        !< surface tendency
7669        REAL(wp)                              :: coef_1             !< first coeficient for prognostic equation
7670        REAL(wp)                              :: coef_window_1      !< first coeficient for prognostic window equation
7671        REAL(wp)                              :: coef_green_1       !< first coeficient for prognostic green wall equation
7672        REAL(wp)                              :: coef_2             !< second  coeficient for prognostic equation
7673        REAL(wp)                              :: coef_window_2      !< second  coeficient for prognostic window equation
7674        REAL(wp)                              :: coef_green_2       !< second  coeficient for prognostic green wall equation
7675        REAL(wp)                              :: rho_cp             !< rho_wall_surface * c_p
7676        REAL(wp)                              :: f_shf              !< factor for shf_eb
7677        REAL(wp)                              :: f_shf_window       !< factor for shf_eb window
7678        REAL(wp)                              :: f_shf_green        !< factor for shf_eb green wall
7679        REAL(wp)                              :: lambda_surface     !< current value of lambda_surface (heat conductivity
7680                                                                    !<between air and wall)
7681        REAL(wp)                              :: lambda_surface_window  !< current value of lambda_surface (heat conductivity
7682                                                                        !< between air and window)
7683        REAL(wp)                              :: lambda_surface_green   !< current value of lambda_surface (heat conductivity
7684                                                                        !< between air and greeb wall)
7685       
7686        REAL(wp)                              :: dtime              !< simulated time of day (in UTC)
7687        INTEGER(iwp)                          :: dhour              !< simulated hour of day (in UTC)
7688        REAL(wp)                              :: acoef              !< actual coefficient of diurnal profile of anthropogenic heat
7689        REAL(wp) ::  f1,          &  !< resistance correction term 1
7690                     f2,          &  !< resistance correction term 2
7691                     f3,          &  !< resistance correction term 3
7692                     e,           &  !< water vapour pressure
7693                     e_s,         &  !< water vapour saturation pressure
7694                     e_s_dt,      &  !< derivate of e_s with respect to T
7695                     tend,        &  !< tendency
7696                     dq_s_dt,     &  !< derivate of q_s with respect to T
7697                     f_qsws,      &  !< factor for qsws
7698                     f_qsws_veg,  &  !< factor for qsws_veg
7699                     f_qsws_liq,  &  !< factor for qsws_liq
7700                     m_liq_max,   &  !< maxmimum value of the liq. water reservoir
7701                     qv1,         &  !< specific humidity at first grid level
7702                     m_max_depth = 0.0002_wp, &  !< Maximum capacity of the water reservoir (m)
7703                     rho_lv,      &  !< frequently used parameter for green layers
7704                     drho_l_lv,   &  !< frequently used parameter for green layers
7705                     q_s             !< saturation specific humidity
7706
7707
7708        IF ( debug_output_timestep )  THEN
7709           WRITE( debug_string, * ) 'usm_surface_energy_balance | during_spinup: ',&
7710                                    during_spinup
7711           CALL debug_message( debug_string, 'start' )
7712        ENDIF
7713!
7714!--     Index offset of surface element point with respect to adjoining
7715!--     atmospheric grid point
7716        k_off = surf_usm_h%koff
7717        j_off = surf_usm_h%joff
7718        i_off = surf_usm_h%ioff
7719       
7720!       
7721!--     First, treat horizontal surface elements
7722        !$OMP PARALLEL PRIVATE (m, i, j, k, lambda_surface, lambda_surface_window,                 &
7723        !$OMP&                  lambda_surface_green, qv1, rho_cp, rho_lv, drho_l_lv, f_shf,       &
7724        !$OMP&                  f_shf_window, f_shf_green, m_total, f1, f2, e_s, e, f3, f_qsws_veg,&
7725        !$OMP&                  q_s, f_qsws_liq, f_qsws, e_s_dt, dq_s_dt, coef_1, coef_window_1,   &
7726        !$OMP&                  coef_green_1, coef_2, coef_window_2, coef_green_2, stend_wall,     &
7727        !$OMP&                  stend_window, stend_green, tend, m_liq_max)
7728        !$OMP DO SCHEDULE (STATIC)
7729        DO  m = 1, surf_usm_h%ns
7730!
7731!--       During spinup set green and window fraction to zero and restore
7732!--       at the end of the loop.
7733!--       Note, this is a temporary fix and need to be removed later. 
7734           IF ( during_spinup )  THEN
7735              frac_win   = surf_usm_h%frac(ind_wat_win,m)
7736              frac_wall  = surf_usm_h%frac(ind_veg_wall,m)
7737              frac_green = surf_usm_h%frac(ind_pav_green,m)
7738              surf_usm_h%frac(ind_wat_win,m)   = 0.0_wp
7739              surf_usm_h%frac(ind_veg_wall,m)  = 1.0_wp
7740              surf_usm_h%frac(ind_pav_green,m) = 0.0_wp
7741           ENDIF
7742!
7743!--        Get indices of respective grid point
7744           i = surf_usm_h%i(m)
7745           j = surf_usm_h%j(m)
7746           k = surf_usm_h%k(m)
7747!
7748!--        TODO - how to calculate lambda_surface for horizontal surfaces
7749!--        (lambda_surface is set according to stratification in land surface model)
7750!--        MS: ???
7751           IF ( surf_usm_h%ol(m) >= 0.0_wp )  THEN
7752              lambda_surface = surf_usm_h%lambda_surf(m)
7753              lambda_surface_window = surf_usm_h%lambda_surf_window(m)
7754              lambda_surface_green = surf_usm_h%lambda_surf_green(m)
7755           ELSE
7756              lambda_surface = surf_usm_h%lambda_surf(m)
7757              lambda_surface_window = surf_usm_h%lambda_surf_window(m)
7758              lambda_surface_green = surf_usm_h%lambda_surf_green(m)
7759           ENDIF
7760
7761!            pt1  = pt(k,j,i)
7762           IF ( humidity )  THEN
7763              qv1 = q(k,j,i)
7764           ELSE
7765              qv1 = 0.0_wp
7766           ENDIF
7767!
7768!--        calculate rho * c_p coefficient at surface layer
7769           rho_cp  = c_p * hyp(k) / ( r_d * surf_usm_h%pt1(m) * exner(k) )
7770
7771           IF ( surf_usm_h%frac(ind_pav_green,m) > 0.0_wp )  THEN
7772!
7773!--           Calculate frequently used parameters
7774              rho_lv    = rho_cp / c_p * l_v
7775              drho_l_lv = 1.0_wp / (rho_l * l_v)
7776           ENDIF
7777
7778!
7779!--        Calculate aerodyamic resistance.
7780!--        Calculation for horizontal surfaces follows LSM formulation
7781!--        pt, us, ts are not available for the prognostic time step,
7782!--        data from the last time step is used here.
7783!
7784!--        Workaround: use single r_a as stability is only treated for the
7785!--        average temperature
7786           surf_usm_h%r_a(m) = ( surf_usm_h%pt1(m) - surf_usm_h%pt_surface(m) ) /&
7787                               ( surf_usm_h%ts(m) * surf_usm_h%us(m) + 1.0E-20_wp )   
7788           surf_usm_h%r_a_window(m) = surf_usm_h%r_a(m)
7789           surf_usm_h%r_a_green(m)  = surf_usm_h%r_a(m)
7790
7791!            r_a = ( surf_usm_h%pt1(m) - t_surf_h(m) / exner(k) ) /                              &
7792!                  ( surf_usm_h%ts(m) * surf_usm_h%us(m) + 1.0E-20_wp )
7793!            r_a_window = ( surf_usm_h%pt1(m) - t_surf_window_h(m) / exner(k) ) /                &
7794!                  ( surf_usm_h%ts(m) * surf_usm_h%us(m) + 1.0E-20_wp )
7795!            r_a_green = ( surf_usm_h%pt1(m) - t_surf_green_h(m) / exner(k) ) /                  &
7796!                  ( surf_usm_h%ts(m) * surf_usm_h%us(m) + 1.0E-20_wp )
7797               
7798!--        Make sure that the resistance does not drop to zero
7799           IF ( surf_usm_h%r_a(m)        < 1.0_wp )                            &
7800               surf_usm_h%r_a(m)        = 1.0_wp
7801           IF ( surf_usm_h%r_a_green(m)  < 1.0_wp )                            &
7802               surf_usm_h%r_a_green(m)  = 1.0_wp
7803           IF ( surf_usm_h%r_a_window(m) < 1.0_wp )                            &
7804               surf_usm_h%r_a_window(m) = 1.0_wp
7805             
7806!
7807!--        Make sure that the resistacne does not exceed a maxmium value in case
7808!--        of zero velocities
7809           IF ( surf_usm_h%r_a(m)        > 300.0_wp )                          &
7810               surf_usm_h%r_a(m)        = 300.0_wp
7811           IF ( surf_usm_h%r_a_green(m)  > 300.0_wp )                          &
7812               surf_usm_h%r_a_green(m)  = 300.0_wp
7813           IF ( surf_usm_h%r_a_window(m) > 300.0_wp )                          &
7814               surf_usm_h%r_a_window(m) = 300.0_wp               
7815               
7816!
7817!--        factor for shf_eb
7818           f_shf  = rho_cp / surf_usm_h%r_a(m)
7819           f_shf_window  = rho_cp / surf_usm_h%r_a_window(m)
7820           f_shf_green  = rho_cp / surf_usm_h%r_a_green(m)
7821       
7822
7823           IF ( surf_usm_h%frac(ind_pav_green,m) > 0.0_wp ) THEN
7824!--           Adapted from LSM:
7825!--           Second step: calculate canopy resistance r_canopy
7826!--           f1-f3 here are defined as 1/f1-f3 as in ECMWF documentation
7827 
7828!--           f1: correction for incoming shortwave radiation (stomata close at
7829!--           night)
7830              f1 = MIN( 1.0_wp, ( 0.004_wp * surf_usm_h%rad_sw_in(m) + 0.05_wp ) / &
7831                               (0.81_wp * (0.004_wp * surf_usm_h%rad_sw_in(m)      &
7832                                + 1.0_wp)) )
7833!
7834!--           f2: correction for soil moisture availability to plants (the
7835!--           integrated soil moisture must thus be considered here)
7836!--           f2 = 0 for very dry soils
7837              m_total = 0.0_wp
7838              DO  k = nzb_wall, nzt_wall+1
7839                  m_total = m_total + rootfr_h(nzb_wall,m)                              &
7840                            * MAX(swc_h(nzb_wall,m),wilt_h(nzb_wall,m))
7841              ENDDO 
7842   
7843              IF ( m_total > wilt_h(nzb_wall,m)  .AND.  m_total < fc_h(nzb_wall,m) )  THEN
7844                 f2 = ( m_total - wilt_h(nzb_wall,m) ) / (fc_h(nzb_wall,m) - wilt_h(nzb_wall,m) )
7845              ELSEIF ( m_total >= fc_h(nzb_wall,m) )  THEN
7846                 f2 = 1.0_wp
7847              ELSE
7848                 f2 = 1.0E-20_wp
7849              ENDIF
7850       
7851!
7852!--          Calculate water vapour pressure at saturation
7853              e_s = 0.01_wp * 610.78_wp * EXP( 17.269_wp * ( t_surf_green_h(m) &
7854                            - 273.16_wp ) / ( t_surf_green_h(m) - 35.86_wp ) )
7855!
7856!--           f3: correction for vapour pressure deficit
7857              IF ( surf_usm_h%g_d(m) /= 0.0_wp )  THEN
7858!
7859!--           Calculate vapour pressure
7860                 e  = qv1 * surface_pressure / ( qv1 + 0.622_wp )
7861                 f3 = EXP ( - surf_usm_h%g_d(m) * (e_s - e) )
7862              ELSE
7863                 f3 = 1.0_wp
7864              ENDIF
7865
7866!
7867!--           Calculate canopy resistance. In case that c_veg is 0 (bare soils),
7868!--           this calculation is obsolete, as r_canopy is not used below.
7869!--           To do: check for very dry soil -> r_canopy goes to infinity
7870              surf_usm_h%r_canopy(m) = surf_usm_h%r_canopy_min(m) /                   &
7871                              ( surf_usm_h%lai(m) * f1 * f2 * f3 + 1.0E-20_wp )
7872
7873!
7874!--           Calculate the maximum possible liquid water amount on plants and
7875!--           bare surface. For vegetated surfaces, a maximum depth of 0.2 mm is
7876!--           assumed, while paved surfaces might hold up 1 mm of water. The
7877!--           liquid water fraction for paved surfaces is calculated after
7878!--           Noilhan & Planton (1989), while the ECMWF formulation is used for
7879!--           vegetated surfaces and bare soils.
7880              m_liq_max = m_max_depth * ( surf_usm_h%lai(m) )
7881              surf_usm_h%c_liq(m) = MIN( 1.0_wp, ( m_liq_usm_h%var_usm_1d(m) / m_liq_max )**0.67 )
7882!
7883!--           Calculate saturation specific humidity
7884              q_s = 0.622_wp * e_s / ( surface_pressure - e_s )
7885!
7886!--           In case of dewfall, set evapotranspiration to zero
7887!--           All super-saturated water is then removed from the air
7888              IF ( humidity  .AND.  q_s <= qv1 )  THEN
7889                 surf_usm_h%r_canopy(m) = 0.0_wp
7890              ENDIF
7891
7892!
7893!--           Calculate coefficients for the total evapotranspiration
7894!--           In case of water surface, set vegetation and soil fluxes to zero.
7895!--           For pavements, only evaporation of liquid water is possible.
7896              f_qsws_veg  = rho_lv *                                           &
7897                                ( 1.0_wp        - surf_usm_h%c_liq(m)    ) /   &
7898                                ( surf_usm_h%r_a_green(m) + surf_usm_h%r_canopy(m) )
7899              f_qsws_liq  = rho_lv * surf_usm_h%c_liq(m)   /                   &
7900                                  surf_usm_h%r_a_green(m)
7901       
7902              f_qsws = f_qsws_veg + f_qsws_liq
7903!
7904!--           Calculate derivative of q_s for Taylor series expansion
7905              e_s_dt = e_s * ( 17.269_wp / ( t_surf_green_h(m) - 35.86_wp) -   &
7906                               17.269_wp*( t_surf_green_h(m) - 273.16_wp)      &
7907                              / ( t_surf_green_h(m) - 35.86_wp)**2 )
7908       
7909              dq_s_dt = 0.622_wp * e_s_dt / ( surface_pressure - e_s_dt )
7910           ENDIF
7911!
7912!--        add LW up so that it can be removed in prognostic equation
7913           surf_usm_h%rad_net_l(m) = surf_usm_h%rad_sw_in(m)  -                &
7914                                     surf_usm_h%rad_sw_out(m) +                &
7915                                     surf_usm_h%rad_lw_in(m)  -                &
7916                                     surf_usm_h%rad_lw_out(m)
7917!
7918!--     numerator of the prognostic equation
7919!--     Todo: Adjust to tile approach. So far, emissivity for wall (element 0)
7920!--     is used
7921           coef_1 = surf_usm_h%rad_net_l(m) +                                  & 
7922                 ( 3.0_wp + 1.0_wp ) * surf_usm_h%emissivity(ind_veg_wall,m) * &
7923                                       sigma_sb * t_surf_wall_h(m) ** 4 +      & 
7924                                       f_shf * surf_usm_h%pt1(m) +             &
7925                                       lambda_surface * t_wall_h(nzb_wall,m)
7926           IF ( ( .NOT. during_spinup ) .AND. (surf_usm_h%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
7927              coef_window_1 = surf_usm_h%rad_net_l(m) +                           & 
7928                      ( 3.0_wp + 1.0_wp ) * surf_usm_h%emissivity(ind_wat_win,m)  &
7929                                          * sigma_sb * t_surf_window_h(m) ** 4 +  & 
7930                                          f_shf_window * surf_usm_h%pt1(m) +      &
7931                                          lambda_surface_window * t_window_h(nzb_wall,m)
7932           ENDIF                 
7933           IF ( ( humidity ) .AND. ( surf_usm_h%frac(ind_pav_green,m) > 0.0_wp ) )  THEN
7934                    coef_green_1 = surf_usm_h%rad_net_l(m) +                                 & 
7935                   ( 3.0_wp + 1.0_wp ) * surf_usm_h%emissivity(ind_pav_green,m) * sigma_sb * &
7936                                       t_surf_green_h(m) ** 4 +                  & 
7937                                          f_shf_green * surf_usm_h%pt1(m) + f_qsws * ( qv1 - q_s    &
7938                                          + dq_s_dt * t_surf_green_h(m) )        &
7939                                          +lambda_surface_green * t_green_h(nzb_wall,m)
7940           ELSE
7941           coef_green_1 = surf_usm_h%rad_net_l(m) +                            & 
7942                 ( 3.0_wp + 1.0_wp ) * surf_usm_h%emissivity(ind_pav_green,m) *&
7943                                       sigma_sb * t_surf_green_h(m) ** 4 +     & 
7944                                       f_shf_green * surf_usm_h%pt1(m) +       &
7945                                       lambda_surface_green * t_green_h(nzb_wall,m)
7946          ENDIF
7947!
7948!--        denominator of the prognostic equation
7949           coef_2 = 4.0_wp * surf_usm_h%emissivity(ind_veg_wall,m) *           &
7950                             sigma_sb * t_surf_wall_h(m) ** 3                  &
7951                           + lambda_surface + f_shf / exner(k)
7952           IF ( ( .NOT. during_spinup ) .AND. ( surf_usm_h%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
7953              coef_window_2 = 4.0_wp * surf_usm_h%emissivity(ind_wat_win,m) *     &
7954                                sigma_sb * t_surf_window_h(m) ** 3                &
7955                              + lambda_surface_window + f_shf_window / exner(k)
7956           ENDIF
7957           IF ( ( humidity ) .AND. ( surf_usm_h%frac(ind_pav_green,m) > 0.0_wp ) )  THEN
7958              coef_green_2 = 4.0_wp * surf_usm_h%emissivity(ind_pav_green,m) * sigma_sb *    &
7959                                t_surf_green_h(m) ** 3 + f_qsws * dq_s_dt                    &
7960                              + lambda_surface_green + f_shf_green / exner(k)
7961           ELSE
7962           coef_green_2 = 4.0_wp * surf_usm_h%emissivity(ind_pav_green,m) * sigma_sb *    &
7963                             t_surf_green_h(m) ** 3                                       &
7964                           + lambda_surface_green + f_shf_green / exner(k)
7965           ENDIF
7966!
7967!--        implicit solution when the surface layer has no heat capacity,
7968!--        otherwise use RK3 scheme.
7969           t_surf_wall_h_p(m) = ( coef_1 * dt_3d * tsc(2) +                        &
7970                             surf_usm_h%c_surface(m) * t_surf_wall_h(m) ) /        & 
7971                           ( surf_usm_h%c_surface(m) + coef_2 * dt_3d * tsc(2) ) 
7972           IF (( .NOT. during_spinup ) .AND. (surf_usm_h%frac(ind_wat_win,m) > 0.0_wp)) THEN
7973              t_surf_window_h_p(m) = ( coef_window_1 * dt_3d * tsc(2) +                        &
7974                                surf_usm_h%c_surface_window(m) * t_surf_window_h(m) ) /        & 
7975                              ( surf_usm_h%c_surface_window(m) + coef_window_2 * dt_3d * tsc(2) )
7976           ENDIF
7977           t_surf_green_h_p(m) = ( coef_green_1 * dt_3d * tsc(2) +                        &
7978                             surf_usm_h%c_surface_green(m) * t_surf_green_h(m) ) /        & 
7979                           ( surf_usm_h%c_surface_green(m) + coef_green_2 * dt_3d * tsc(2) ) 
7980!
7981!--        add RK3 term
7982           t_surf_wall_h_p(m) = t_surf_wall_h_p(m) + dt_3d * tsc(3) *         &
7983                           surf_usm_h%tt_surface_wall_m(m)
7984
7985           t_surf_window_h_p(m) = t_surf_window_h_p(m) + dt_3d * tsc(3) *     &
7986                           surf_usm_h%tt_surface_window_m(m)
7987
7988           t_surf_green_h_p(m) = t_surf_green_h_p(m) + dt_3d * tsc(3) *       &
7989                           surf_usm_h%tt_surface_green_m(m)
7990!
7991!--        Store surface temperature on pt_surface. Further, in case humidity is used
7992!--        store also vpt_surface, which is, due to the lack of moisture on roofs simply
7993!--        assumed to be the surface temperature.
7994           surf_usm_h%pt_surface(m) = ( surf_usm_h%frac(ind_veg_wall,m) * t_surf_wall_h_p(m)   &
7995                               + surf_usm_h%frac(ind_wat_win,m) * t_surf_window_h_p(m)         &
7996                               + surf_usm_h%frac(ind_pav_green,m) * t_surf_green_h_p(m) )      &
7997                               / exner(k)
7998                               
7999           IF ( humidity )  surf_usm_h%vpt_surface(m) =                        &
8000                                                   surf_usm_h%pt_surface(m)
8001!
8002!--        calculate true tendency
8003           stend_wall = ( t_surf_wall_h_p(m) - t_surf_wall_h(m) - dt_3d * tsc(3) *              &
8004                     surf_usm_h%tt_surface_wall_m(m)) / ( dt_3d  * tsc(2) )
8005           stend_window = ( t_surf_window_h_p(m) - t_surf_window_h(m) - dt_3d * tsc(3) *        &
8006                     surf_usm_h%tt_surface_window_m(m)) / ( dt_3d  * tsc(2) )
8007           stend_green = ( t_surf_green_h_p(m) - t_surf_green_h(m) - dt_3d * tsc(3) *           &
8008                     surf_usm_h%tt_surface_green_m(m)) / ( dt_3d  * tsc(2) )
8009!
8010!--        calculate t_surf tendencies for the next Runge-Kutta step
8011           IF ( timestep_scheme(1:5) == 'runge' )  THEN
8012              IF ( intermediate_timestep_count == 1 )  THEN
8013                 surf_usm_h%tt_surface_wall_m(m) = stend_wall
8014                 surf_usm_h%tt_surface_window_m(m) = stend_window
8015                 surf_usm_h%tt_surface_green_m(m) = stend_green
8016              ELSEIF ( intermediate_timestep_count <                          &
8017                        intermediate_timestep_count_max )  THEN
8018                 surf_usm_h%tt_surface_wall_m(m) = -9.5625_wp * stend_wall +       &
8019                                     5.3125_wp * surf_usm_h%tt_surface_wall_m(m)
8020                 surf_usm_h%tt_surface_window_m(m) = -9.5625_wp * stend_window +   &
8021                                     5.3125_wp * surf_usm_h%tt_surface_window_m(m)
8022                 surf_usm_h%tt_surface_green_m(m) = -9.5625_wp * stend_green +     &
8023                                     5.3125_wp * surf_usm_h%tt_surface_green_m(m)
8024              ENDIF
8025           ENDIF
8026!
8027!--        in case of fast changes in the skin temperature, it is required to
8028!--        update the radiative fluxes in order to keep the solution stable
8029           IF ( ( ( ABS( t_surf_wall_h_p(m)   - t_surf_wall_h(m) )   > 1.0_wp )   .OR. &
8030                (   ABS( t_surf_green_h_p(m)  - t_surf_green_h(m) )  > 1.0_wp )   .OR. &
8031                (   ABS( t_surf_window_h_p(m) - t_surf_window_h(m) ) > 1.0_wp ) )      &
8032                   .AND.  unscheduled_radiation_calls  )  THEN
8033              force_radiation_call_l = .TRUE.
8034           ENDIF
8035!
8036!--        calculate fluxes
8037!--        rad_net_l is never used!
8038           surf_usm_h%rad_net_l(m) = surf_usm_h%rad_net_l(m) +                           &
8039                                     surf_usm_h%frac(ind_veg_wall,m) *                   &
8040                                     sigma_sb * surf_usm_h%emissivity(ind_veg_wall,m) *  &
8041                                     ( t_surf_wall_h_p(m)**4 - t_surf_wall_h(m)**4 )     &
8042                                    + surf_usm_h%frac(ind_wat_win,m) *                   &
8043                                     sigma_sb * surf_usm_h%emissivity(ind_wat_win,m) *   &
8044                                     ( t_surf_window_h_p(m)**4 - t_surf_window_h(m)**4 ) &
8045                                    + surf_usm_h%frac(ind_pav_green,m) *                 &
8046                                     sigma_sb * surf_usm_h%emissivity(ind_pav_green,m) * &
8047                                     ( t_surf_green_h_p(m)**4 - t_surf_green_h(m)**4 )
8048
8049           surf_usm_h%wghf_eb(m)   = lambda_surface *                                    &
8050                                      ( t_surf_wall_h_p(m) - t_wall_h(nzb_wall,m) )
8051           surf_usm_h%wghf_eb_green(m)  = lambda_surface_green *                         &
8052                                          ( t_surf_green_h_p(m) - t_green_h(nzb_wall,m) )
8053           surf_usm_h%wghf_eb_window(m) = lambda_surface_window *                        &
8054                                           ( t_surf_window_h_p(m) - t_window_h(nzb_wall,m) )
8055
8056!
8057!--        ground/wall/roof surface heat flux
8058           surf_usm_h%wshf_eb(m)   = - f_shf  * ( surf_usm_h%pt1(m) - t_surf_wall_h_p(m) / exner(k) ) *          &
8059                                       surf_usm_h%frac(ind_veg_wall,m)         &
8060                                     - f_shf_window  * ( surf_usm_h%pt1(m) - t_surf_window_h_p(m) / exner(k) ) * &
8061                                       surf_usm_h%frac(ind_wat_win,m)          &
8062                                     - f_shf_green  * ( surf_usm_h%pt1(m) - t_surf_green_h_p(m) / exner(k) ) *   &
8063                                       surf_usm_h%frac(ind_pav_green,m)
8064!           
8065!--        store kinematic surface heat fluxes for utilization in other processes
8066!--        diffusion_s, surface_layer_fluxes,...
8067           surf_usm_h%shf(m) = surf_usm_h%wshf_eb(m) / c_p
8068!
8069!--        If the indoor model is applied, further add waste heat from buildings to the
8070!--        kinematic flux.
8071           IF ( indoor_model )  THEN
8072              surf_usm_h%shf(m) = surf_usm_h%shf(m) + surf_usm_h%waste_heat(m) / c_p
8073           ENDIF
8074     
8075
8076           IF (surf_usm_h%frac(ind_pav_green,m) > 0.0_wp) THEN
8077             
8078           
8079              IF ( humidity )  THEN
8080                 surf_usm_h%qsws(m)  = - f_qsws * ( qv1 - q_s + dq_s_dt                     &
8081                                 * t_surf_green_h(m) - dq_s_dt *               &
8082                                   t_surf_green_h_p(m) )
8083       
8084                 surf_usm_h%qsws_veg(m)  = - f_qsws_veg  * ( qv1 - q_s                      &
8085                                     + dq_s_dt * t_surf_green_h(m) - dq_s_dt   &
8086                                     * t_surf_green_h_p(m) )
8087       
8088                 surf_usm_h%qsws_liq(m)  = - f_qsws_liq  * ( qv1 - q_s                      &
8089                                     + dq_s_dt * t_surf_green_h(m) - dq_s_dt   &
8090                                     * t_surf_green_h_p(m) )
8091                                     
8092              ENDIF
8093 
8094!
8095!--           Calculate the true surface resistance
8096              IF ( .NOT.  humidity )  THEN
8097                 surf_usm_h%r_s(m) = 1.0E10_wp
8098              ELSE
8099                 surf_usm_h%r_s(m) = - rho_lv * ( qv1 - q_s + dq_s_dt                       &
8100                                 *  t_surf_green_h(m) - dq_s_dt *              &
8101                                   t_surf_green_h_p(m) ) /                     &
8102                                   (surf_usm_h%qsws(m) + 1.0E-20)  - surf_usm_h%r_a_green(m)
8103              ENDIF
8104 
8105!
8106!--           Calculate change in liquid water reservoir due to dew fall or
8107!--           evaporation of liquid water
8108              IF ( humidity )  THEN
8109!
8110!--              If precipitation is activated, add rain water to qsws_liq
8111!--              and qsws_soil according the the vegetation coverage.
8112!--              precipitation_rate is given in mm.
8113                 IF ( precipitation )  THEN
8114
8115!
8116!--                 Add precipitation to liquid water reservoir, if possible.
8117!--                 Otherwise, add the water to soil. In case of
8118!--                 pavements, the exceeding water amount is implicitely removed
8119!--                 as runoff as qsws_soil is then not used in the soil model
8120                    IF ( m_liq_usm_h%var_usm_1d(m) /= m_liq_max )  THEN
8121                       surf_usm_h%qsws_liq(m) = surf_usm_h%qsws_liq(m)                &
8122                                        + surf_usm_h%frac(ind_pav_green,m) * prr(k+k_off,j+j_off,i+i_off)&
8123                                        * hyrho(k+k_off)                              &
8124                                        * 0.001_wp * rho_l * l_v
8125                   ENDIF
8126
8127                 ENDIF
8128
8129!
8130!--              If the air is saturated, check the reservoir water level
8131                 IF ( surf_usm_h%qsws(m) < 0.0_wp )  THEN
8132!
8133!--                 Check if reservoir is full (avoid values > m_liq_max)
8134!--                 In that case, qsws_liq goes to qsws_soil. In this
8135!--                 case qsws_veg is zero anyway (because c_liq = 1),       
8136!--                 so that tend is zero and no further check is needed
8137                    IF ( m_liq_usm_h%var_usm_1d(m) == m_liq_max )  THEN
8138!                      surf_usm_h%qsws_soil(m) = surf_usm_h%qsws_soil(m) + surf_usm_h%qsws_liq(m)
8139                       surf_usm_h%qsws_liq(m)  = 0.0_wp
8140                    ENDIF
8141
8142!
8143!--                 In case qsws_veg becomes negative (unphysical behavior),
8144!--                 let the water enter the liquid water reservoir as dew on the
8145!--                 plant
8146                    IF ( surf_usm_h%qsws_veg(m) < 0.0_wp )  THEN
8147                       surf_usm_h%qsws_liq(m) = surf_usm_h%qsws_liq(m) + surf_usm_h%qsws_veg(m)
8148                       surf_usm_h%qsws_veg(m) = 0.0_wp
8149                    ENDIF
8150                 ENDIF                   
8151 
8152                 surf_usm_h%qsws(m) = surf_usm_h%qsws(m) / l_v
8153       
8154                 tend = - surf_usm_h%qsws_liq(m) * drho_l_lv
8155                 m_liq_usm_h_p%var_usm_1d(m) = m_liq_usm_h%var_usm_1d(m) + dt_3d *    &
8156                                               ( tsc(2) * tend +                      &
8157                                                 tsc(3) * tm_liq_usm_h_m%var_usm_1d(m) )
8158!
8159!--             Check if reservoir is overfull -> reduce to maximum
8160!--             (conservation of water is violated here)
8161                 m_liq_usm_h_p%var_usm_1d(m) = MIN( m_liq_usm_h_p%var_usm_1d(m),m_liq_max )
8162 
8163!
8164!--             Check if reservoir is empty (avoid values < 0.0)
8165!--             (conservation of water is violated here)
8166                 m_liq_usm_h_p%var_usm_1d(m) = MAX( m_liq_usm_h_p%var_usm_1d(m), 0.0_wp )
8167!
8168!--             Calculate m_liq tendencies for the next Runge-Kutta step
8169                 IF ( timestep_scheme(1:5) == 'runge' )  THEN
8170                    IF ( intermediate_timestep_count == 1 )  THEN
8171                       tm_liq_usm_h_m%var_usm_1d(m) = tend
8172                    ELSEIF ( intermediate_timestep_count <                            &
8173                             intermediate_timestep_count_max )  THEN
8174                       tm_liq_usm_h_m%var_usm_1d(m) = -9.5625_wp * tend +             &
8175                                                     5.3125_wp * tm_liq_usm_h_m%var_usm_1d(m)
8176                    ENDIF
8177                 ENDIF
8178 
8179              ENDIF
8180           ELSE
8181              surf_usm_h%r_s(m) = 1.0E10_wp
8182           ENDIF
8183!
8184!--        During spinup green and window fraction are set to zero. Here, the original
8185!--        values are restored.
8186           IF ( during_spinup )  THEN
8187              surf_usm_h%frac(ind_wat_win,m)   = frac_win
8188              surf_usm_h%frac(ind_veg_wall,m)  = frac_wall
8189              surf_usm_h%frac(ind_pav_green,m) = frac_green
8190           ENDIF
8191 
8192       ENDDO
8193!
8194!--    Now, treat vertical surface elements
8195       !$OMP DO SCHEDULE (STATIC)
8196       DO  l = 0, 3
8197           DO  m = 1, surf_usm_v(l)%ns
8198!
8199!--           During spinup set green and window fraction to zero and restore
8200!--           at the end of the loop.
8201!--           Note, this is a temporary fix and need to be removed later.
8202              IF ( during_spinup )  THEN
8203                 frac_win   = surf_usm_v(l)%frac(ind_wat_win,m)
8204                 frac_wall  = surf_usm_v(l)%frac(ind_veg_wall,m)
8205                 frac_green = surf_usm_v(l)%frac(ind_pav_green,m)
8206                 surf_usm_v(l)%frac(ind_wat_win,m)   = 0.0_wp
8207                 surf_usm_v(l)%frac(ind_veg_wall,m)  = 1.0_wp
8208                 surf_usm_v(l)%frac(ind_pav_green,m) = 0.0_wp
8209              ENDIF
8210!
8211!--          Get indices of respective grid point
8212              i = surf_usm_v(l)%i(m)
8213              j = surf_usm_v(l)%j(m)
8214              k = surf_usm_v(l)%k(m)
8215 
8216!
8217!--          TODO - how to calculate lambda_surface for horizontal (??? do you mean verical ???) surfaces
8218!--          (lambda_surface is set according to stratification in land surface model).
8219!--          Please note, for vertical surfaces no ol is defined, since
8220!--          stratification is not considered in this case.
8221              lambda_surface = surf_usm_v(l)%lambda_surf(m)
8222              lambda_surface_window = surf_usm_v(l)%lambda_surf_window(m)
8223              lambda_surface_green = surf_usm_v(l)%lambda_surf_green(m)
8224 
8225!            pt1  = pt(k,j,i)
8226              IF ( humidity )  THEN
8227                 qv1 = q(k,j,i)
8228              ELSE
8229                 qv1 = 0.0_wp
8230              ENDIF
8231!
8232!--          calculate rho * c_p coefficient at wall layer
8233              rho_cp  = c_p * hyp(k) / ( r_d * surf_usm_v(l)%pt1(m) * exner(k) )
8234             
8235              IF (surf_usm_v(l)%frac(1,m) > 0.0_wp )  THEN
8236!
8237!--            Calculate frequently used parameters
8238                 rho_lv    = rho_cp / c_p * l_v
8239                 drho_l_lv = 1.0_wp / (rho_l * l_v)
8240              ENDIF
8241 
8242!--          Calculation of r_a for vertical surfaces
8243!--
8244!--          heat transfer coefficient for forced convection along vertical walls
8245!--          follows formulation in TUF3d model (Krayenhoff & Voogt, 2006)
8246!--           
8247!--          H = httc (Tsfc - Tair)
8248!--          httc = rw * (11.8 + 4.2 * Ueff) - 4.0
8249!--           
8250!--                rw: wall patch roughness relative to 1.0 for concrete
8251!--                Ueff: effective wind speed
8252!--                - 4.0 is a reduction of Rowley et al (1930) formulation based on
8253!--                Cole and Sturrock (1977)
8254!--           
8255!--                Ucan: Canyon wind speed
8256!--                wstar: convective velocity
8257!--                Qs: surface heat flux
8258!--                zH: height of the convective layer
8259!--                wstar = (g/Tcan*Qs*zH)**(1./3.)
8260!--          Effective velocity components must always
8261!--          be defined at scalar grid point. The wall normal component is
8262!--          obtained by simple linear interpolation. ( An alternative would
8263!--          be an logarithmic interpolation. )
8264!--          Parameter roughness_concrete (default value = 0.001) is used
8265!--          to calculation of roughness relative to concrete
8266              surf_usm_v(l)%r_a(m) = rho_cp / ( surf_usm_v(l)%z0(m) /           &
8267                         roughness_concrete * ( 11.8_wp + 4.2_wp *              &
8268                         SQRT( MAX( ( ( u(k,j,i) + u(k,j,i+1) ) * 0.5_wp )**2 + &
8269                                    ( ( v(k,j,i) + v(k,j+1,i) ) * 0.5_wp )**2 + &
8270                                    ( ( w(k,j,i) + w(k-1,j,i) ) * 0.5_wp )**2,  &
8271                               0.01_wp ) )                                      &
8272                            )  - 4.0_wp  ) 
8273!
8274!--          Limit aerodynamic resistance
8275              IF ( surf_usm_v(l)%r_a(m) < 1.0_wp )  surf_usm_v(l)%r_a(m) = 1.0_wp   
8276             
8277                           
8278              f_shf         = rho_cp / surf_usm_v(l)%r_a(m)
8279              f_shf_window  = rho_cp / surf_usm_v(l)%r_a(m)
8280              f_shf_green   = rho_cp / surf_usm_v(l)%r_a(m)
8281 
8282
8283              IF ( surf_usm_v(l)%frac(1,m) > 0.0_wp ) THEN
8284!
8285!--             Adapted from LSM:
8286!--             Second step: calculate canopy resistance r_canopy
8287!--             f1-f3 here are defined as 1/f1-f3 as in ECMWF documentation
8288!--             f1: correction for incoming shortwave radiation (stomata close at
8289!--             night)
8290                 f1 = MIN( 1.0_wp, ( 0.004_wp * surf_usm_v(l)%rad_sw_in(m) + 0.05_wp ) / &
8291                                  (0.81_wp * (0.004_wp * surf_usm_v(l)%rad_sw_in(m)      &
8292                                   + 1.0_wp)) )
8293!
8294!--             f2: correction for soil moisture availability to plants (the
8295!--             integrated soil moisture must thus be considered here)
8296!--             f2 = 0 for very dry soils
8297 
8298                 f2=1.0_wp
8299 
8300!
8301!--              Calculate water vapour pressure at saturation
8302                 e_s = 0.01_wp * 610.78_wp * EXP( 17.269_wp * (  t_surf_green_v_p(l)%t(m) &
8303                               - 273.16_wp ) / (  t_surf_green_v_p(l)%t(m) - 35.86_wp ) )
8304!
8305!--              f3: correction for vapour pressure deficit
8306                 IF ( surf_usm_v(l)%g_d(m) /= 0.0_wp )  THEN
8307!
8308!--                 Calculate vapour pressure
8309                    e  = qv1 * surface_pressure / ( qv1 + 0.622_wp )
8310                    f3 = EXP ( - surf_usm_v(l)%g_d(m) * (e_s - e) )
8311                 ELSE
8312                    f3 = 1.0_wp
8313                 ENDIF
8314!
8315!--              Calculate canopy resistance. In case that c_veg is 0 (bare soils),
8316!--              this calculation is obsolete, as r_canopy is not used below.
8317!--              To do: check for very dry soil -> r_canopy goes to infinity
8318                 surf_usm_v(l)%r_canopy(m) = surf_usm_v(l)%r_canopy_min(m) /                  &
8319                                        ( surf_usm_v(l)%lai(m) * f1 * f2 * f3 + 1.0E-20_wp )
8320                               
8321!
8322!--              Calculate saturation specific humidity
8323                 q_s = 0.622_wp * e_s / ( surface_pressure - e_s )
8324!
8325!--              In case of dewfall, set evapotranspiration to zero
8326!--              All super-saturated water is then removed from the air
8327                 IF ( humidity  .AND.  q_s <= qv1 )  THEN
8328                    surf_usm_v(l)%r_canopy(m) = 0.0_wp
8329                 ENDIF
8330 
8331!
8332!--              Calculate coefficients for the total evapotranspiration
8333!--              In case of water surface, set vegetation and soil fluxes to zero.
8334!--              For pavements, only evaporation of liquid water is possible.
8335                 f_qsws_veg  = rho_lv *                                &
8336                                   ( 1.0_wp        - 0.0_wp ) / & !surf_usm_h%c_liq(m)    ) /   &
8337                                   ( surf_usm_v(l)%r_a(m) + surf_usm_v(l)%r_canopy(m) )
8338!                f_qsws_liq  = rho_lv * surf_usm_h%c_liq(m)   /             &
8339!                              surf_usm_h%r_a_green(m)
8340         
8341                 f_qsws = f_qsws_veg! + f_qsws_liq
8342!
8343!--              Calculate derivative of q_s for Taylor series expansion
8344                 e_s_dt = e_s * ( 17.269_wp / ( t_surf_green_v_p(l)%t(m) - 35.86_wp) -   &
8345                                  17.269_wp*( t_surf_green_v_p(l)%t(m) - 273.16_wp)      &
8346                                 / ( t_surf_green_v_p(l)%t(m) - 35.86_wp)**2 )
8347         
8348                 dq_s_dt = 0.622_wp * e_s_dt / ( surface_pressure - e_s_dt )
8349              ENDIF
8350
8351!
8352!--           add LW up so that it can be removed in prognostic equation
8353              surf_usm_v(l)%rad_net_l(m) = surf_usm_v(l)%rad_sw_in(m)  -        &
8354                                           surf_usm_v(l)%rad_sw_out(m) +        &
8355                                           surf_usm_v(l)%rad_lw_in(m)  -        &
8356                                           surf_usm_v(l)%rad_lw_out(m)
8357!
8358!--           numerator of the prognostic equation
8359              coef_1 = surf_usm_v(l)%rad_net_l(m) +                             & ! coef +1 corresponds to -lwout
8360                                                                                  ! included in calculation of radnet_l
8361              ( 3.0_wp + 1.0_wp ) * surf_usm_v(l)%emissivity(ind_veg_wall,m) *  &
8362                                      sigma_sb *  t_surf_wall_v(l)%t(m) ** 4 +  & 
8363                                      f_shf * surf_usm_v(l)%pt1(m) +            &
8364                                      lambda_surface * t_wall_v(l)%t(nzb_wall,m)
8365              IF ( ( .NOT. during_spinup ) .AND. ( surf_usm_v(l)%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
8366                 coef_window_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_wat_win,m) * &
8369                                      sigma_sb * t_surf_window_v(l)%t(m) ** 4 + & 
8370                                      f_shf * surf_usm_v(l)%pt1(m) +            &
8371                                      lambda_surface_window * t_window_v(l)%t(nzb_wall,m)
8372              ENDIF
8373              IF ( ( humidity ) .AND. ( surf_usm_v(l)%frac(ind_pav_green,m) > 0.0_wp ) )  THEN
8374                 coef_green_1 = surf_usm_v(l)%rad_net_l(m) +                      & ! coef +1 corresponds to -lwout
8375                                                                                    ! included 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) +     f_qsws * ( qv1 - q_s  &
8379                                           + dq_s_dt * t_surf_green_v(l)%t(m) ) +              &
8380                                      lambda_surface_green * t_wall_v(l)%t(nzb_wall,m)
8381              ELSE
8382                coef_green_1 = surf_usm_v(l)%rad_net_l(m) +                       & ! coef +1 corresponds to -lwout included
8383                                                                                    ! in calculation of radnet_l
8384                ( 3.0_wp + 1.0_wp ) * surf_usm_v(l)%emissivity(ind_pav_green,m) * sigma_sb *  &
8385                                      t_surf_green_v(l)%t(m) ** 4 +               & 
8386                                      f_shf * surf_usm_v(l)%pt1(m) +              &
8387                                      lambda_surface_green * t_wall_v(l)%t(nzb_wall,m)
8388              ENDIF
8389                                     
8390!
8391!--           denominator of the prognostic equation
8392              coef_2 = 4.0_wp * surf_usm_v(l)%emissivity(ind_veg_wall,m) * sigma_sb *   &
8393                                 t_surf_wall_v(l)%t(m) ** 3                             &
8394                               + lambda_surface + f_shf / exner(k) 
8395              IF ( ( .NOT. during_spinup ) .AND. ( surf_usm_v(l)%frac(ind_wat_win,m) > 0.0_wp ) ) THEN             
8396                 coef_window_2 = 4.0_wp * surf_usm_v(l)%emissivity(ind_wat_win,m) * sigma_sb *       &
8397                                   t_surf_window_v(l)%t(m) ** 3                         &
8398                                 + lambda_surface_window + f_shf / exner(k)
8399              ENDIF
8400              IF ( ( humidity ) .AND. ( surf_usm_v(l)%frac(ind_pav_green,m) > 0.0_wp ) )  THEN
8401                  coef_green_2 = 4.0_wp * surf_usm_v(l)%emissivity(ind_pav_green,m) * sigma_sb *     &
8402                                   t_surf_green_v(l)%t(m) ** 3  + f_qsws * dq_s_dt      &
8403                                 + lambda_surface_green + f_shf / exner(k)
8404              ELSE
8405                 coef_green_2 = 4.0_wp * surf_usm_v(l)%emissivity(ind_pav_green,m) * sigma_sb *      &
8406                                   t_surf_green_v(l)%t(m) ** 3                          &
8407                                 + lambda_surface_green + f_shf / exner(k)
8408              ENDIF
8409!
8410!--           implicit solution when the surface layer has no heat capacity,
8411!--           otherwise use RK3 scheme.
8412              t_surf_wall_v_p(l)%t(m) = ( coef_1 * dt_3d * tsc(2) +                 &
8413                             surf_usm_v(l)%c_surface(m) * t_surf_wall_v(l)%t(m) ) / & 
8414                             ( surf_usm_v(l)%c_surface(m) + coef_2 * dt_3d * tsc(2) ) 
8415              IF ( ( .NOT. during_spinup ) .AND. ( surf_usm_v(l)%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
8416                 t_surf_window_v_p(l)%t(m) = ( coef_window_1 * dt_3d * tsc(2) +                 &
8417                                surf_usm_v(l)%c_surface_window(m) * t_surf_window_v(l)%t(m) ) / & 
8418                              ( surf_usm_v(l)%c_surface_window(m) + coef_window_2 * dt_3d * tsc(2) ) 
8419              ENDIF
8420              t_surf_green_v_p(l)%t(m) = ( coef_green_1 * dt_3d * tsc(2) +                 &
8421                             surf_usm_v(l)%c_surface_green(m) * t_surf_green_v(l)%t(m) ) / & 
8422                           ( surf_usm_v(l)%c_surface_green(m) + coef_green_2 * dt_3d * tsc(2) ) 
8423!
8424!--           add RK3 term
8425              t_surf_wall_v_p(l)%t(m) = t_surf_wall_v_p(l)%t(m) + dt_3d * tsc(3) *         &
8426                                surf_usm_v(l)%tt_surface_wall_m(m)
8427              t_surf_window_v_p(l)%t(m) = t_surf_window_v_p(l)%t(m) + dt_3d * tsc(3) *     &
8428                                surf_usm_v(l)%tt_surface_window_m(m)
8429              t_surf_green_v_p(l)%t(m) = t_surf_green_v_p(l)%t(m) + dt_3d * tsc(3) *       &
8430                                 surf_usm_v(l)%tt_surface_green_m(m)
8431!
8432!--           Store surface temperature. Further, in case humidity is used
8433!--           store also vpt_surface, which is, due to the lack of moisture on roofs simply
8434!--           assumed to be the surface temperature.     
8435              surf_usm_v(l)%pt_surface(m) =  ( surf_usm_v(l)%frac(ind_veg_wall,m) * t_surf_wall_v_p(l)%t(m)  &
8436                                      + surf_usm_v(l)%frac(ind_wat_win,m) * t_surf_window_v_p(l)%t(m)        &
8437                                      + surf_usm_v(l)%frac(ind_pav_green,m) * t_surf_green_v_p(l)%t(m) )     &
8438                                      / exner(k)
8439                                       
8440              IF ( humidity )  surf_usm_v(l)%vpt_surface(m) =                  &
8441                                                     surf_usm_v(l)%pt_surface(m)
8442!
8443!--           calculate true tendency
8444              stend_wall = ( t_surf_wall_v_p(l)%t(m) - t_surf_wall_v(l)%t(m) - dt_3d * tsc(3) *      &
8445                        surf_usm_v(l)%tt_surface_wall_m(m) ) / ( dt_3d  * tsc(2) )
8446              stend_window = ( t_surf_window_v_p(l)%t(m) - t_surf_window_v(l)%t(m) - dt_3d * tsc(3) *&
8447                        surf_usm_v(l)%tt_surface_window_m(m) ) / ( dt_3d  * tsc(2) )
8448              stend_green = ( t_surf_green_v_p(l)%t(m) - t_surf_green_v(l)%t(m) - dt_3d * tsc(3) *   &
8449                        surf_usm_v(l)%tt_surface_green_m(m) ) / ( dt_3d  * tsc(2) )
8450
8451!
8452!--           calculate t_surf_* tendencies for the next Runge-Kutta step
8453              IF ( timestep_scheme(1:5) == 'runge' )  THEN
8454                 IF ( intermediate_timestep_count == 1 )  THEN
8455                    surf_usm_v(l)%tt_surface_wall_m(m) = stend_wall
8456                    surf_usm_v(l)%tt_surface_window_m(m) = stend_window
8457                    surf_usm_v(l)%tt_surface_green_m(m) = stend_green
8458                 ELSEIF ( intermediate_timestep_count <                                 &
8459                          intermediate_timestep_count_max )  THEN
8460                    surf_usm_v(l)%tt_surface_wall_m(m) = -9.5625_wp * stend_wall +      &
8461                                     5.3125_wp * surf_usm_v(l)%tt_surface_wall_m(m)
8462                    surf_usm_v(l)%tt_surface_green_m(m) = -9.5625_wp * stend_green +    &
8463                                     5.3125_wp * surf_usm_v(l)%tt_surface_green_m(m)
8464                    surf_usm_v(l)%tt_surface_window_m(m) = -9.5625_wp * stend_window +  &
8465                                     5.3125_wp * surf_usm_v(l)%tt_surface_window_m(m)
8466                 ENDIF
8467              ENDIF
8468
8469!
8470!--           in case of fast changes in the skin temperature, it is required to
8471!--           update the radiative fluxes in order to keep the solution stable
8472 
8473              IF ( ( ( ABS( t_surf_wall_v_p(l)%t(m)   - t_surf_wall_v(l)%t(m) )   > 1.0_wp ) .OR. &
8474                   (   ABS( t_surf_green_v_p(l)%t(m)  - t_surf_green_v(l)%t(m) )  > 1.0_wp ) .OR. &
8475                   (   ABS( t_surf_window_v_p(l)%t(m) - t_surf_window_v(l)%t(m) ) > 1.0_wp ) )    &
8476                      .AND.  unscheduled_radiation_calls )  THEN
8477                 force_radiation_call_l = .TRUE.
8478              ENDIF
8479
8480!
8481!--           calculate fluxes
8482!--           prognostic rad_net_l is used just for output!           
8483              surf_usm_v(l)%rad_net_l(m) = surf_usm_v(l)%frac(ind_veg_wall,m) *                      &
8484                                           ( surf_usm_v(l)%rad_net_l(m) +                            &
8485                                           3.0_wp * sigma_sb *                                       &
8486                                           t_surf_wall_v(l)%t(m)**4 - 4.0_wp * sigma_sb *            &
8487                                           t_surf_wall_v(l)%t(m)**3 * t_surf_wall_v_p(l)%t(m) )      &
8488                                         + surf_usm_v(l)%frac(ind_wat_win,m) *                       &
8489                                           ( surf_usm_v(l)%rad_net_l(m) +                            &
8490                                           3.0_wp * sigma_sb *                                       &
8491                                           t_surf_window_v(l)%t(m)**4 - 4.0_wp * sigma_sb *          &
8492                                           t_surf_window_v(l)%t(m)**3 * t_surf_window_v_p(l)%t(m) )  &
8493                                         + surf_usm_v(l)%frac(ind_pav_green,m) *                     &
8494                                           ( surf_usm_v(l)%rad_net_l(m) +                            &
8495                                           3.0_wp * sigma_sb *                                       &
8496                                           t_surf_green_v(l)%t(m)**4 - 4.0_wp * sigma_sb *           &
8497                                           t_surf_green_v(l)%t(m)**3 * t_surf_green_v_p(l)%t(m) )
8498
8499              surf_usm_v(l)%wghf_eb_window(m) = lambda_surface_window * &
8500                                                ( t_surf_window_v_p(l)%t(m) - t_window_v(l)%t(nzb_wall,m) )
8501              surf_usm_v(l)%wghf_eb(m)   = lambda_surface *             &
8502                                                ( t_surf_wall_v_p(l)%t(m) - t_wall_v(l)%t(nzb_wall,m) )
8503              surf_usm_v(l)%wghf_eb_green(m)  = lambda_surface_green *  &
8504                                                ( t_surf_green_v_p(l)%t(m) - t_green_v(l)%t(nzb_wall,m) )
8505
8506!
8507!--           ground/wall/roof surface heat flux
8508              surf_usm_v(l)%wshf_eb(m)   =                                     &
8509                 - f_shf  * ( surf_usm_v(l)%pt1(m) -                           &
8510                 t_surf_wall_v_p(l)%t(m) / exner(k) ) * surf_usm_v(l)%frac(ind_veg_wall,m)       &
8511                 - f_shf_window  * ( surf_usm_v(l)%pt1(m) -                    &
8512                 t_surf_window_v_p(l)%t(m) / exner(k) ) * surf_usm_v(l)%frac(ind_wat_win,m)&
8513                 - f_shf_green  * ( surf_usm_v(l)%pt1(m) -                     &
8514                 t_surf_green_v_p(l)%t(m) / exner(k) ) * surf_usm_v(l)%frac(ind_pav_green,m)
8515
8516!           
8517!--           store kinematic surface heat fluxes for utilization in other processes
8518!--           diffusion_s, surface_layer_fluxes,...
8519              surf_usm_v(l)%shf(m) = surf_usm_v(l)%wshf_eb(m) / c_p
8520!
8521!--           If the indoor model is applied, further add waste heat from buildings to the
8522!--           kinematic flux.
8523              IF ( indoor_model )  THEN
8524                 surf_usm_v(l)%shf(m) = surf_usm_v(l)%shf(m) +                       &
8525                                        surf_usm_v(l)%waste_heat(m) / c_p
8526              ENDIF             
8527
8528              IF ( surf_usm_v(l)%frac(ind_pav_green,m) > 0.0_wp ) THEN
8529 
8530
8531                 IF ( humidity )  THEN
8532                    surf_usm_v(l)%qsws(m)  = - f_qsws * ( qv1 - q_s + dq_s_dt          &
8533                                    * t_surf_green_v(l)%t(m) - dq_s_dt *               &
8534                                      t_surf_green_v_p(l)%t(m) )
8535         
8536                    surf_usm_v(l)%qsws(m) = surf_usm_v(l)%qsws(m) / l_v
8537         
8538                    surf_usm_v(l)%qsws_veg(m)  = - f_qsws_veg  * ( qv1 - q_s           &
8539                                        + dq_s_dt * t_surf_green_v(l)%t(m) - dq_s_dt   &
8540                                        * t_surf_green_v_p(l)%t(m) )
8541         
8542!                    surf_usm_h%qsws_liq(m)  = - f_qsws_liq  * ( qv1 - q_s         &
8543!                                        + dq_s_dt * t_surf_green_h(m) - dq_s_dt   &
8544!                                        * t_surf_green_h_p(m) )
8545                 ENDIF
8546 
8547!
8548!--              Calculate the true surface resistance
8549                 IF ( .NOT.  humidity )  THEN
8550                    surf_usm_v(l)%r_s(m) = 1.0E10_wp
8551                 ELSE
8552                    surf_usm_v(l)%r_s(m) = - rho_lv * ( qv1 - q_s + dq_s_dt             &
8553                                    *  t_surf_green_v(l)%t(m) - dq_s_dt *               &
8554                                      t_surf_green_v_p(l)%t(m) ) /                      &
8555                                      (surf_usm_v(l)%qsws(m) + 1.0E-20)  - surf_usm_v(l)%r_a(m)
8556                 ENDIF
8557         
8558!
8559!--              Calculate change in liquid water reservoir due to dew fall or
8560!--              evaporation of liquid water
8561                 IF ( humidity )  THEN
8562!
8563!--                 If the air is saturated, check the reservoir water level
8564                    IF ( surf_usm_v(l)%qsws(m) < 0.0_wp )  THEN
8565       
8566!
8567!--                    In case qsws_veg becomes negative (unphysical behavior),
8568!--                    let the water enter the liquid water reservoir as dew on the
8569!--                    plant
8570                       IF ( surf_usm_v(l)%qsws_veg(m) < 0.0_wp )  THEN
8571          !                 surf_usm_h%qsws_liq(m) = surf_usm_h%qsws_liq(m) + surf_usm_h%qsws_veg(m)
8572                          surf_usm_v(l)%qsws_veg(m) = 0.0_wp
8573                       ENDIF
8574                    ENDIF
8575                 
8576                 ENDIF
8577              ELSE
8578                 surf_usm_v(l)%r_s(m) = 1.0E10_wp
8579              ENDIF
8580!
8581!--           During spinup green and window fraction are set to zero. Here, the original
8582!--           values are restored.
8583              IF ( during_spinup )  THEN
8584                 surf_usm_v(l)%frac(ind_wat_win,m)   = frac_win
8585                 surf_usm_v(l)%frac(ind_veg_wall,m)  = frac_wall
8586                 surf_usm_v(l)%frac(ind_pav_green,m) = frac_green
8587              ENDIF
8588
8589           ENDDO
8590 
8591       ENDDO
8592       !$OMP END PARALLEL
8593
8594!
8595!--     Add-up anthropogenic heat, for now only at upward-facing surfaces
8596         IF ( usm_anthropogenic_heat  .AND.  .NOT. during_spinup  .AND. &
8597              intermediate_timestep_count == intermediate_timestep_count_max )  THEN
8598!
8599!--        application of the additional anthropogenic heat sources
8600!--        we considere the traffic for now so all heat is absorbed
8601!--        to the first layer, generalization would be worth.
8602!--        calculation of actual profile coefficient
8603!--        ??? check time_since_reference_point ???
8604            dtime = mod(simulated_time + time_utc_init, 24.0_wp*3600.0_wp)
8605            dhour = INT(dtime/3600.0_wp)
8606
8607!--         TO_DO: activate, if testcase is available
8608!--         !$OMP PARALLEL DO PRIVATE (i, j, k, acoef, rho_cp)
8609!--         it may also improve performance to move get_topography_top_index_ji before the k-loop
8610            DO i = nxl, nxr
8611               DO j = nys, nyn
8612                  DO k = nz_urban_b, min(nz_urban_t,naheatlayers)
8613                     IF ( k > get_topography_top_index_ji( j, i, 's' ) ) THEN
8614!
8615!--                    increase of pt in box i,j,k in time dt_3d
8616!--                    given to anthropogenic heat aheat*acoef (W*m-2)
8617!--                    linear interpolation of coeficient
8618                        acoef = (REAL(dhour+1,wp)-dtime/3600.0_wp)*aheatprof(k,dhour) + &
8619                                (dtime/3600.0_wp-REAL(dhour,wp))*aheatprof(k,dhour+1)
8620                        IF ( aheat(k,j,i) > 0.0_wp )  THEN
8621!
8622!--                       calculate rho * c_p coefficient at layer k
8623                           rho_cp  = c_p * hyp(k) / ( r_d * pt(k+1,j,i) * exner(k) )
8624                           pt(k,j,i) = pt(k,j,i) + aheat(k,j,i)*acoef*dt_3d/(exner(k)*rho_cp*dz(1))
8625                        ENDIF
8626                     ENDIF
8627                  ENDDO
8628               ENDDO
8629            ENDDO
8630 
8631         ENDIF
8632!
8633!--     pt and shf are defined on nxlg:nxrg,nysg:nyng
8634!--     get the borders from neighbours
8635         CALL exchange_horiz( pt, nbgp )
8636!
8637!--     calculation of force_radiation_call:
8638!--     Make logical OR for all processes.
8639!--     Force radiation call if at least one processor forces it.
8640         IF ( intermediate_timestep_count == intermediate_timestep_count_max-1 )&
8641         THEN
8642#if defined( __parallel )
8643           IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
8644           CALL MPI_ALLREDUCE( force_radiation_call_l, force_radiation_call,    &
8645                               1, MPI_LOGICAL, MPI_LOR, comm2d, ierr )
8646#else
8647           force_radiation_call = force_radiation_call_l
8648#endif
8649           force_radiation_call_l = .FALSE.
8650         ENDIF
8651 
8652! !
8653! !-- Calculate surface specific humidity
8654!     IF ( humidity )  THEN
8655!        CALL calc_q_surface_usm
8656!     ENDIF
8657 
8658 
8659!     CONTAINS
8660! !------------------------------------------------------------------------------!
8661! ! Description:
8662! ! ------------
8663! !> Calculation of specific humidity of the skin layer (surface). It is assumend
8664! !> that the skin is always saturated.
8665! !------------------------------------------------------------------------------!
8666!        SUBROUTINE calc_q_surface_usm
8667!
8668!           IMPLICIT NONE
8669!
8670!           REAL(wp) :: resistance    !< aerodynamic and soil resistance term
8671!
8672!           DO  m = 1, surf_usm_h%ns
8673!
8674!              i   = surf_usm_h%i(m)           
8675!              j   = surf_usm_h%j(m)
8676!              k   = surf_usm_h%k(m)
8677!
8678!!
8679!!--          Calculate water vapour pressure at saturation
8680!              e_s = 0.01_wp * 610.78_wp * EXP( 17.269_wp *                  &
8681!                                     ( t_surf_green_h_p(m) - 273.16_wp ) /  &
8682!                                     ( t_surf_green_h_p(m) - 35.86_wp  )    &
8683!                                          )
8684!
8685!!
8686!!--          Calculate specific humidity at saturation
8687!              q_s = 0.622_wp * e_s / ( surface_pressure - e_s )
8688!
8689!!              surf_usm_h%r_a_green(m) = ( surf_usm_h%pt1(m) - t_surf_green_h(m) / exner(k) ) /  &
8690!!                    ( surf_usm_h%ts(m) * surf_usm_h%us(m) + 1.0E-10_wp )
8691!!                 
8692!! !--          make sure that the resistance does not drop to zero
8693!!              IF ( ABS(surf_usm_h%r_a_green(m)) < 1.0E-10_wp )  surf_usm_h%r_a_green(m) = 1.0E-10_wp
8694!
8695!              resistance = surf_usm_h%r_a_green(m) / ( surf_usm_h%r_a_green(m) + surf_usm_h%r_s(m) + 1E-5_wp )
8696!
8697!!
8698!!--          Calculate specific humidity at surface
8699!              IF ( bulk_cloud_model )  THEN
8700!                 q(k,j,i) = resistance * q_s +                   &
8701!                                            ( 1.0_wp - resistance ) *              &
8702!                                            ( q(k,j,i) - ql(k,j,i) )
8703!              ELSE
8704!                 q(k,j,i) = resistance * q_s +                   &
8705!                                            ( 1.0_wp - resistance ) *              &
8706!                                              q(k,j,i)
8707!              ENDIF
8708!
8709!!
8710!!--          Update virtual potential temperature
8711!              vpt(k,j,i) = pt(k,j,i) *         &
8712!                         ( 1.0_wp + 0.61_wp * q(k,j,i) )
8713!
8714!           ENDDO
8715!
8716!!
8717!!--       Now, treat vertical surface elements
8718!           DO  l = 0, 3
8719!              DO  m = 1, surf_usm_v(l)%ns
8720!!
8721!!--             Get indices of respective grid point
8722!                 i = surf_usm_v(l)%i(m)
8723!                 j = surf_usm_v(l)%j(m)
8724!                 k = surf_usm_v(l)%k(m)
8725!
8726!!
8727!!--             Calculate water vapour pressure at saturation
8728!                 e_s = 0.01_wp * 610.78_wp * EXP( 17.269_wp *                       &
8729!                                        ( t_surf_green_v_p(l)%t(m) - 273.16_wp ) /  &
8730!                                        ( t_surf_green_v_p(l)%t(m) - 35.86_wp  )    &
8731!                                             )
8732!
8733!!
8734!!--             Calculate specific humidity at saturation
8735!                 q_s = 0.622_wp * e_s / ( surface_pressure -e_s )
8736!
8737!!
8738!!--             Calculate specific humidity at surface
8739!                 IF ( bulk_cloud_model )  THEN
8740!                    q(k,j,i) = ( q(k,j,i) - ql(k,j,i) )
8741!                 ELSE
8742!                    q(k,j,i) = q(k,j,i)
8743!                 ENDIF
8744!!
8745!!--             Update virtual potential temperature
8746!                 vpt(k,j,i) = pt(k,j,i) *         &
8747!                            ( 1.0_wp + 0.61_wp * q(k,j,i) )
8748!
8749!              ENDDO
8750!
8751!           ENDDO
8752!
8753!        END SUBROUTINE calc_q_surface_usm
8754
8755        IF ( debug_output_timestep )  THEN
8756           WRITE( debug_string, * ) 'usm_surface_energy_balance | during_spinup: ',&
8757                                    during_spinup
8758           CALL debug_message( debug_string, 'end' )
8759        ENDIF
8760
8761     END SUBROUTINE usm_surface_energy_balance
8762 
8763 
8764!------------------------------------------------------------------------------!
8765! Description:
8766! ------------
8767!> Swapping of timelevels for t_surf and t_wall
8768!> called out from subroutine swap_timelevel
8769!------------------------------------------------------------------------------!
8770     SUBROUTINE usm_swap_timelevel( mod_count )
8771 
8772        IMPLICIT NONE
8773 
8774        INTEGER(iwp), INTENT(IN) ::  mod_count
8775 
8776       
8777        SELECT CASE ( mod_count )
8778 
8779           CASE ( 0 )
8780!
8781!--          Horizontal surfaces
8782              t_surf_wall_h    => t_surf_wall_h_1;   t_surf_wall_h_p    => t_surf_wall_h_2
8783              t_wall_h         => t_wall_h_1;        t_wall_h_p         => t_wall_h_2
8784              t_surf_window_h  => t_surf_window_h_1; t_surf_window_h_p  => t_surf_window_h_2
8785              t_window_h       => t_window_h_1;      t_window_h_p       => t_window_h_2
8786              t_surf_green_h   => t_surf_green_h_1;  t_surf_green_h_p   => t_surf_green_h_2
8787              t_green_h        => t_green_h_1;       t_green_h_p        => t_green_h_2
8788!
8789!--          Vertical surfaces
8790              t_surf_wall_v    => t_surf_wall_v_1;   t_surf_wall_v_p    => t_surf_wall_v_2
8791              t_wall_v         => t_wall_v_1;        t_wall_v_p         => t_wall_v_2
8792              t_surf_window_v  => t_surf_window_v_1; t_surf_window_v_p  => t_surf_window_v_2
8793              t_window_v       => t_window_v_1;      t_window_v_p       => t_window_v_2
8794              t_surf_green_v   => t_surf_green_v_1;  t_surf_green_v_p   => t_surf_green_v_2
8795              t_green_v        => t_green_v_1;       t_green_v_p        => t_green_v_2
8796           CASE ( 1 )
8797!
8798!--          Horizontal surfaces
8799              t_surf_wall_h    => t_surf_wall_h_2;   t_surf_wall_h_p    => t_surf_wall_h_1
8800              t_wall_h         => t_wall_h_2;        t_wall_h_p         => t_wall_h_1
8801              t_surf_window_h  => t_surf_window_h_2; t_surf_window_h_p  => t_surf_window_h_1
8802              t_window_h       => t_window_h_2;      t_window_h_p       => t_window_h_1
8803              t_surf_green_h   => t_surf_green_h_2;  t_surf_green_h_p   => t_surf_green_h_1
8804              t_green_h        => t_green_h_2;       t_green_h_p        => t_green_h_1
8805!
8806!--          Vertical surfaces
8807              t_surf_wall_v    => t_surf_wall_v_2;   t_surf_wall_v_p    => t_surf_wall_v_1
8808              t_wall_v         => t_wall_v_2;        t_wall_v_p         => t_wall_v_1
8809              t_surf_window_v  => t_surf_window_v_2; t_surf_window_v_p  => t_surf_window_v_1
8810              t_window_v       => t_window_v_2;      t_window_v_p       => t_window_v_1
8811              t_surf_green_v   => t_surf_green_v_2;  t_surf_green_v_p   => t_surf_green_v_1
8812              t_green_v        => t_green_v_2;       t_green_v_p        => t_green_v_1
8813        END SELECT
8814         
8815     END SUBROUTINE usm_swap_timelevel
8816 
8817!------------------------------------------------------------------------------!
8818! Description:
8819! ------------
8820!> Subroutine writes t_surf and t_wall data into restart files
8821!------------------------------------------------------------------------------!
8822     SUBROUTINE usm_wrd_local
8823 
8824     
8825        IMPLICIT NONE
8826       
8827        CHARACTER(LEN=1) ::  dum     !< dummy string to create output-variable name 
8828        INTEGER(iwp)     ::  l       !< index surface type orientation
8829 
8830        CALL wrd_write_string( 'ns_h_on_file_usm' )
8831        WRITE ( 14 )  surf_usm_h%ns
8832 
8833        CALL wrd_write_string( 'ns_v_on_file_usm' )
8834        WRITE ( 14 )  surf_usm_v(0:3)%ns
8835 
8836        CALL wrd_write_string( 'usm_start_index_h' )
8837        WRITE ( 14 )  surf_usm_h%start_index
8838 
8839        CALL wrd_write_string( 'usm_end_index_h' )
8840        WRITE ( 14 )  surf_usm_h%end_index
8841 
8842        CALL wrd_write_string( 't_surf_wall_h' )
8843        WRITE ( 14 )  t_surf_wall_h
8844 
8845        CALL wrd_write_string( 't_surf_window_h' )
8846        WRITE ( 14 )  t_surf_window_h
8847 
8848        CALL wrd_write_string( 't_surf_green_h' )
8849        WRITE ( 14 )  t_surf_green_h
8850!
8851!--     Write restart data which is especially needed for the urban-surface
8852!--     model. In order to do not fill up the restart routines in
8853!--     surface_mod.
8854!--     Output of waste heat from indoor model. Restart data is required in
8855!--     this special case, because the indoor model where waste heat is
8856!--     computed is call each hour (current default), so that waste heat would
8857!--     have zero value until next call of indoor model.
8858        IF ( indoor_model )  THEN
8859           CALL wrd_write_string( 'waste_heat_h' )
8860           WRITE ( 14 )  surf_usm_h%waste_heat
8861        ENDIF   
8862           
8863        DO  l = 0, 3
8864 
8865           CALL wrd_write_string( 'usm_start_index_v' )
8866           WRITE ( 14 )  surf_usm_v(l)%start_index
8867 
8868           CALL wrd_write_string( 'usm_end_index_v' )
8869           WRITE ( 14 )  surf_usm_v(l)%end_index
8870 
8871           WRITE( dum, '(I1)')  l         
8872 
8873           CALL wrd_write_string( 't_surf_wall_v(' // dum // ')' )
8874           WRITE ( 14 )  t_surf_wall_v(l)%t
8875 
8876           CALL wrd_write_string( 't_surf_window_v(' // dum // ')' )
8877           WRITE ( 14 ) t_surf_window_v(l)%t     
8878 
8879           CALL wrd_write_string( 't_surf_green_v(' // dum // ')' )
8880           WRITE ( 14 ) t_surf_green_v(l)%t 
8881           
8882           IF ( indoor_model )  THEN
8883              CALL wrd_write_string( 'waste_heat_v(' // dum // ')' )
8884              WRITE ( 14 )  surf_usm_v(l)%waste_heat
8885           ENDIF
8886           
8887        ENDDO
8888 
8889        CALL wrd_write_string( 'usm_start_index_h' )
8890        WRITE ( 14 )  surf_usm_h%start_index
8891 
8892        CALL wrd_write_string( 'usm_end_index_h' )
8893        WRITE ( 14 )  surf_usm_h%end_index
8894 
8895        CALL wrd_write_string( 't_wall_h' )
8896        WRITE ( 14 )  t_wall_h
8897 
8898        CALL wrd_write_string( 't_window_h' )
8899        WRITE ( 14 )  t_window_h
8900 
8901        CALL wrd_write_string( 't_green_h' )
8902        WRITE ( 14 )  t_green_h
8903 
8904        DO  l = 0, 3
8905 
8906           CALL wrd_write_string( 'usm_start_index_v' )
8907           WRITE ( 14 )  surf_usm_v(l)%start_index
8908 
8909           CALL wrd_write_string( 'usm_end_index_v' )
8910           WRITE ( 14 )  surf_usm_v(l)%end_index
8911 
8912           WRITE( dum, '(I1)')  l     
8913 
8914           CALL wrd_write_string( 't_wall_v(' // dum // ')' )
8915           WRITE ( 14 )  t_wall_v(l)%t
8916 
8917           CALL wrd_write_string( 't_window_v(' // dum // ')' )
8918           WRITE ( 14 )  t_window_v(l)%t
8919 
8920           CALL wrd_write_string( 't_green_v(' // dum // ')' )
8921           WRITE ( 14 )  t_green_v(l)%t
8922       
8923        ENDDO
8924       
8925     END SUBROUTINE usm_wrd_local
8926     
8927     
8928!------------------------------------------------------------------------------!
8929! Description:
8930! ------------
8931!> Define building properties
8932!------------------------------------------------------------------------------!
8933     SUBROUTINE usm_define_pars     
8934!
8935!--     Define the building_pars
8936        building_pars(:,1) = (/   &
8937           0.7_wp,         &  !< parameter 0   - wall fraction above ground floor level
8938           0.3_wp,         &  !< parameter 1   - window fraction above ground floor level
8939           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
8940           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
8941           1.5_wp,         &  !< parameter 4   - LAI roof
8942           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
8943           2200000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
8944           1400000.0_wp,   &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
8945           1300000.0_wp,   &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
8946           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
8947           0.8_wp,         &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
8948           2.1_wp,         &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
8949           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
8950           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
8951           0.93_wp,        &  !< parameter 14  - wall emissivity above ground floor level
8952           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
8953           0.91_wp,        &  !< parameter 16  - window emissivity above ground floor level
8954           0.75_wp,        &  !< parameter 17  - window transmissivity above ground floor level
8955           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
8956           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
8957           4.0_wp,         &  !< parameter 20  - ground floor level height
8958           0.75_wp,        &  !< parameter 21  - wall fraction ground floor level
8959           0.25_wp,        &  !< parameter 22  - window fraction ground floor level
8960           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
8961           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
8962           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
8963           2200000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
8964           1400000.0_wp,   &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
8965           1300000.0_wp,   &  !< parameter 28  - heat capacity 4th wall layer ground floor level
8966           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
8967           0.8_wp,         &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
8968           2.1_wp,         &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
8969           0.93_wp,        &  !< parameter 32  - wall emissivity ground floor level
8970           0.91_wp,        &  !< parameter 33  - window emissivity ground floor level
8971           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
8972           0.75_wp,        &  !< parameter 35  - window transmissivity ground floor level
8973           0.001_wp,       &  !< parameter 36  - z0 roughness ground floor level
8974           0.0001_wp,      &  !< parameter 37  - z0h/z0q roughness heat/humidity
8975           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
8976           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
8977           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
8978           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
8979           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
8980           0.39_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
8981           0.63_wp,        &  !< parameter 44  - 4th wall layer thickness above ground floor level
8982           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
8983           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
8984           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
8985           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
8986           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
8987           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
8988           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
8989           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
8990           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
8991           0.39_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
8992           0.63_wp,        &  !< parameter 55  - 4th wall layer thickness ground plate
8993           2200000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
8994           1400000.0_wp,   &  !< parameter 57  - heat capacity 3rd wall layer ground plate
8995           1300000.0_wp,   &  !< parameter 58  - heat capacity 4th wall layer ground plate
8996           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
8997           0.8_wp,         &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
8998           2.1_wp,         &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
8999           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
9000           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
9001           0.39_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
9002           0.63_wp,        &  !< parameter 65  - 4th wall layer thickness ground floor level
9003           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9004           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9005           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9006           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9007           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9008           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9009           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9010           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9011           0.57_wp,        &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9012           0.57_wp,        &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9013           0.57_wp,        &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9014           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9015           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9016           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9017           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9018           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9019           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9020           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9021           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9022           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9023           0.57_wp,        &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9024           0.57_wp,        &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9025           0.57_wp,        &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9026           1.0_wp,         &  !< parameter 89  - wall fraction roof
9027           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9028           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9029           0.31_wp,        &  !< parameter 92  - 3rd wall layer thickness roof
9030           0.63_wp,        &  !< parameter 93  - 4th wall layer thickness roof
9031           2200000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9032           1400000.0_wp,   &  !< parameter 95  - heat capacity 3rd wall layer roof
9033           1300000.0_wp,   &  !< parameter 96  - heat capacity 4th wall layer roof
9034           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9035           0.8_wp,         &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9036           2.1_wp,         &  !< parameter 99  - thermal conductivity 4th wall layer roof
9037           0.93_wp,        &  !< parameter 100 - wall emissivity roof
9038           27.0_wp,        &  !< parameter 101 - wall albedo roof
9039           0.0_wp,         &  !< parameter 102 - window fraction roof
9040           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9041           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9042           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9043           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9044           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9045           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9046           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9047           0.57_wp,        &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9048           0.57_wp,        &  !< parameter 111 - thermal conductivity 3rd window layer roof
9049           0.57_wp,        &  !< parameter 112 - thermal conductivity 4th window layer roof
9050           0.91_wp,        &  !< parameter 113 - window emissivity roof
9051           0.75_wp,        &  !< parameter 114 - window transmissivity roof
9052           27.0_wp,        &  !< parameter 115 - window albedo roof
9053           0.86_wp,        &  !< parameter 116 - green emissivity roof
9054           5.0_wp,         &  !< parameter 117 - green albedo roof
9055           0.0_wp,         &  !< parameter 118 - green type roof
9056           0.8_wp,         &  !< parameter 119 - shading factor
9057           0.76_wp,        &  !< parameter 120 - g-value windows
9058           5.0_wp,         &  !< parameter 121 - u-value windows
9059           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9060           0.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9061           0.0_wp,         &  !< parameter 124 - heat recovery efficiency
9062           3.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9063           370000.0_wp,    &  !< parameter 126 - dynamic parameter innner heatstorage
9064           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9065           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9066           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9067           3.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9068           10.0_wp,        &  !< parameter 131 - basic internal heat gains without occupancy of the room
9069           3.0_wp,         &  !< parameter 132 - storey height
9070           0.2_wp          &  !< parameter 133 - ceiling construction height
9071                            /)
9072                           
9073        building_pars(:,2) = (/   &
9074           0.73_wp,        &  !< parameter 0   - wall fraction above ground floor level
9075           0.27_wp,        &  !< parameter 1   - window fraction above ground floor level
9076           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9077           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9078           1.5_wp,         &  !< parameter 4   - LAI roof
9079           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9080           2000000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9081           103000.0_wp,    &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9082           900000.0_wp,    &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9083           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9084           0.38_wp,        &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9085           0.04_wp,        &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9086           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9087           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9088           0.92_wp,        &  !< parameter 14  - wall emissivity above ground floor level
9089           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9090           0.87_wp,        &  !< parameter 16  - window emissivity above ground floor level
9091           0.7_wp,         &  !< parameter 17  - window transmissivity above ground floor level
9092           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9093           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9094           4.0_wp,         &  !< parameter 20  - ground floor level height
9095           0.78_wp,        &  !< parameter 21  - wall fraction ground floor level
9096           0.22_wp,        &  !< parameter 22  - window fraction ground floor level
9097           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9098           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9099           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9100           2000000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9101           103000.0_wp,    &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9102           900000.0_wp,    &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9103           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9104           0.38_wp,        &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9105           0.04_wp,        &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9106           0.92_wp,        &  !< parameter 32  - wall emissivity ground floor level
9107           0.11_wp,        &  !< parameter 33  - window emissivity ground floor level
9108           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9109           0.7_wp,         &  !< parameter 35  - window transmissivity ground floor level
9110           0.001_wp,       &  !< parameter 36  - z0 roughness ground floor level
9111           0.0001_wp,      &  !< parameter 37  - z0h/z0q roughness heat/humidity
9112           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9113           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9114           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9115           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
9116           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9117           0.31_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9118           0.43_wp,        &  !< parameter 44  - 4th wall layer thickness above ground floor level
9119           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9120           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9121           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9122           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9123           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9124           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9125           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9126           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
9127           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
9128           0.31_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
9129           0.42_wp,        &  !< parameter 55  - 4th wall layer thickness ground plate
9130           2000000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9131           103000.0_wp,    &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9132           900000.0_wp,    &  !< parameter 58  - heat capacity 4th wall layer ground plate
9133           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9134           0.38_wp,        &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9135           0.04_wp,        &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9136           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
9137           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
9138           0.31_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
9139           0.43_wp,        &  !< parameter 65  - 4th wall layer thickness ground floor level
9140           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9141           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9142           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9143           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9144           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9145           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9146           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9147           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9148           0.11_wp,        &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9149           0.11_wp,        &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9150           0.11_wp,        &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9151           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9152           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9153           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9154           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9155           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9156           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9157           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9158           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9159           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9160           0.11_wp,        &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9161           0.11_wp,        &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9162           0.11_wp,        &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9163           1.0_wp,         &  !< parameter 89  - wall fraction roof
9164           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9165           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9166           0.5_wp,         &  !< parameter 92  - 3rd wall layer thickness roof
9167           0.79_wp,        &  !< parameter 93  - 4th wall layer thickness roof
9168           2000000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9169           103000.0_wp,    &  !< parameter 95  - heat capacity 3rd wall layer roof
9170           900000.0_wp,    &  !< parameter 96  - heat capacity 4th wall layer roof
9171           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9172           0.38_wp,        &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9173           0.04_wp,        &  !< parameter 99  - thermal conductivity 4th wall layer roof
9174           0.93_wp,        &  !< parameter 100 - wall emissivity roof
9175           27.0_wp,        &  !< parameter 101 - wall albedo roof
9176           0.0_wp,         &  !< parameter 102 - window fraction roof
9177           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9178           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9179           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9180           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9181           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9182           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9183           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9184           0.11_wp,        &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9185           0.11_wp,        &  !< parameter 111 - thermal conductivity 3rd window layer roof
9186           0.11_wp,        &  !< parameter 112 - thermal conductivity 4th window layer roof
9187           0.87_wp,        &  !< parameter 113 - window emissivity roof
9188           0.7_wp,         &  !< parameter 114 - window transmissivity roof
9189           27.0_wp,        &  !< parameter 115 - window albedo roof
9190           0.86_wp,        &  !< parameter 116 - green emissivity roof
9191           5.0_wp,         &  !< parameter 117 - green albedo roof
9192           0.0_wp,         &  !< parameter 118 - green type roof
9193           0.8_wp,         &  !< parameter 119 - shading factor
9194           0.6_wp,         &  !< parameter 120 - g-value windows
9195           3.0_wp,         &  !< parameter 121 - u-value windows
9196           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9197           0.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9198           0.0_wp,         &  !< parameter 124 - heat recovery efficiency
9199           2.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9200           165000.0_wp,    &  !< parameter 126 - dynamic parameter innner heatstorage
9201           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9202           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9203           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9204           4.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9205           8.0_wp,         &  !< parameter 131 - basic internal heat gains without occupancy of the room
9206           3.0_wp,         &  !< parameter 132 - storey height
9207           0.2_wp          &  !< parameter 133 - ceiling construction height
9208                            /)
9209                           
9210        building_pars(:,3) = (/   &
9211           0.7_wp,         &  !< parameter 0   - wall fraction above ground floor level
9212           0.3_wp,         &  !< parameter 1   - window fraction above ground floor level
9213           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9214           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9215           1.5_wp,         &  !< parameter 4   - LAI roof
9216           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9217           2000000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9218           103000.0_wp,    &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9219           900000.0_wp,    &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9220           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9221           0.14_wp,        &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9222           0.035_wp,       &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9223           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9224           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9225           0.92_wp,        &  !< parameter 14  - wall emissivity above ground floor level
9226           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9227           0.8_wp,         &  !< parameter 16  - window emissivity above ground floor level
9228           0.6_wp,         &  !< parameter 17  - window transmissivity above ground floor level
9229           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9230           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9231           4.0_wp,         &  !< parameter 20  - ground floor level height
9232           0.75_wp,        &  !< parameter 21  - wall fraction ground floor level
9233           0.25_wp,        &  !< parameter 22  - window fraction ground floor level
9234           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9235           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9236           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9237           2000000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9238           103000.0_wp,    &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9239           900000.0_wp,    &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9240           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9241           0.14_wp,        &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9242           0.035_wp,       &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9243           0.92_wp,        &  !< parameter 32  - wall emissivity ground floor level
9244           0.8_wp,         &  !< parameter 33  - window emissivity ground floor level
9245           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9246           0.6_wp,         &  !< parameter 35  - window transmissivity ground floor level
9247           0.001_wp,       &  !< parameter 36  - z0 roughness ground floor level
9248           0.0001_wp,      &  !< parameter 37  - z0h/z0q roughness heat/humidity
9249           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9250           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9251           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9252           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
9253           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9254           0.41_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9255           0.7_wp,         &  !< parameter 44  - 4th wall layer thickness above ground floor level
9256           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9257           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9258           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9259           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9260           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9261           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9262           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9263           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
9264           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
9265           0.41_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
9266           0.7_wp,         &  !< parameter 55  - 4th wall layer thickness ground plate
9267           2000000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9268           103000.0_wp,    &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9269           900000.0_wp,    &  !< parameter 58  - heat capacity 4th wall layer ground plate
9270           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9271           0.14_wp,        &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9272           0.035_wp,       &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9273           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
9274           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
9275           0.41_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
9276           0.7_wp,         &  !< parameter 65  - 4th wall layer thickness ground floor level
9277           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9278           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9279           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9280           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9281           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9282           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9283           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9284           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9285           0.037_wp,       &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9286           0.037_wp,       &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9287           0.037_wp,       &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9288           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9289           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9290           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9291           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9292           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9293           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9294           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9295           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9296           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9297           0.037_wp,       &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9298           0.037_wp,       &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9299           0.037_wp,       &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9300           1.0_wp,         &  !< parameter 89  - wall fraction roof
9301           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9302           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9303           0.41_wp,        &  !< parameter 92  - 3rd wall layer thickness roof
9304           0.7_wp,         &  !< parameter 93  - 4th wall layer thickness roof
9305           2000000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9306           103000.0_wp,    &  !< parameter 95  - heat capacity 3rd wall layer roof
9307           900000.0_wp,    &  !< parameter 96  - heat capacity 4th wall layer roof
9308           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9309           0.14_wp,        &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9310           0.035_wp,       &  !< parameter 99  - thermal conductivity 4th wall layer roof
9311           0.93_wp,        &  !< parameter 100 - wall emissivity roof
9312           27.0_wp,        &  !< parameter 101 - wall albedo roof
9313           0.0_wp,         &  !< parameter 102 - window fraction roof
9314           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9315           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9316           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9317           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9318           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9319           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9320           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9321           0.037_wp,       &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9322           0.037_wp,       &  !< parameter 111 - thermal conductivity 3rd window layer roof
9323           0.037_wp,       &  !< parameter 112 - thermal conductivity 4th window layer roof
9324           0.8_wp,         &  !< parameter 113 - window emissivity roof
9325           0.6_wp,         &  !< parameter 114 - window transmissivity roof
9326           27.0_wp,        &  !< parameter 115 - window albedo roof
9327           0.86_wp,        &  !< parameter 116 - green emissivity roof
9328           5.0_wp,         &  !< parameter 117 - green albedo roof
9329           0.0_wp,         &  !< parameter 118 - green type roof
9330           0.8_wp,         &  !< parameter 119 - shading factor
9331           0.5_wp,         &  !< parameter 120 - g-value windows
9332           0.6_wp,         &  !< parameter 121 - u-value windows
9333           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9334           0.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9335           0.8_wp,         &  !< parameter 124 - heat recovery efficiency
9336           2.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9337           80000.0_wp,     &  !< parameter 126 - dynamic parameter innner heatstorage
9338           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9339           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9340           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9341           3.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9342           8.0_wp,         &  !< parameter 131 - basic internal heat gains without occupancy of the room
9343           3.0_wp,         &  !< parameter 132 - storey height
9344           0.2_wp          &  !< parameter 133 - ceiling construction height
9345                            /)   
9346                           
9347        building_pars(:,4) = (/   &
9348           0.5_wp,         &  !< parameter 0   - wall fraction above ground floor level
9349           0.5_wp,         &  !< parameter 1   - window fraction above ground floor level
9350           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9351           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9352           1.5_wp,         &  !< parameter 4   - LAI roof
9353           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9354           2200000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9355           1400000.0_wp,   &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9356           1300000.0_wp,   &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9357           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9358           0.8_wp,         &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9359           2.1_wp,         &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9360           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9361           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9362           0.93_wp,        &  !< parameter 14  - wall emissivity above ground floor level
9363           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9364           0.91_wp,        &  !< parameter 16  - window emissivity above ground floor level
9365           0.75_wp,        &  !< parameter 17  - window transmissivity above ground floor level
9366           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9367           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9368           4.0_wp,         &  !< parameter 20  - ground floor level height
9369           0.55_wp,        &  !< parameter 21  - wall fraction ground floor level
9370           0.45_wp,        &  !< parameter 22  - window fraction ground floor level
9371           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9372           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9373           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9374           2200000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9375           1400000.0_wp,   &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9376           1300000.0_wp,   &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9377           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9378           0.8_wp,         &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9379           2.1_wp,         &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9380           0.93_wp,        &  !< parameter 32  - wall emissivity ground floor level
9381           0.91_wp,        &  !< parameter 33  - window emissivity ground floor level
9382           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9383           0.75_wp,        &  !< parameter 35  - window transmissivity ground floor level
9384           0.001_wp,       &  !< parameter 36  - z0 roughness ground floor level
9385           0.0001_wp,      &  !< parameter 37  - z0h/z0q roughness heat/humidity
9386           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9387           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9388           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9389           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
9390           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9391           0.39_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9392           0.63_wp,        &  !< parameter 44  - 4th wall layer thickness above ground floor level
9393           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9394           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9395           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9396           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9397           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9398           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9399           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9400           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
9401           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
9402           0.39_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
9403           0.63_wp,        &  !< parameter 55  - 4th wall layer thickness ground plate
9404           2200000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9405           1400000.0_wp,   &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9406           1300000.0_wp,   &  !< parameter 58  - heat capacity 4th wall layer ground plate
9407           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9408           0.8_wp,         &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9409           2.1_wp,         &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9410           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
9411           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
9412           0.39_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
9413           0.63_wp,        &  !< parameter 65  - 4th wall layer thickness ground floor level
9414           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9415           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9416           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9417           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9418           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9419           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9420           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9421           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9422           0.57_wp,        &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9423           0.57_wp,        &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9424           0.57_wp,        &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9425           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9426           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9427           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9428           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9429           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9430           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9431           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9432           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9433           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9434           0.57_wp,        &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9435           0.57_wp,        &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9436           0.57_wp,        &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9437           1.0_wp,         &  !< parameter 89  - wall fraction roof
9438           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9439           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9440           0.39_wp,        &  !< parameter 92  - 3rd wall layer thickness roof
9441           0.63_wp,        &  !< parameter 93  - 4th wall layer thickness roof
9442           2200000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9443           1400000.0_wp,   &  !< parameter 95  - heat capacity 3rd wall layer roof
9444           1300000.0_wp,   &  !< parameter 96  - heat capacity 4th wall layer roof
9445           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9446           0.8_wp,         &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9447           2.1_wp,         &  !< parameter 99  - thermal conductivity 4th wall layer roof
9448           0.93_wp,        &  !< parameter 100 - wall emissivity roof
9449           27.0_wp,        &  !< parameter 101 - wall albedo roof
9450           0.0_wp,         &  !< parameter 102 - window fraction roof
9451           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9452           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9453           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9454           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9455           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9456           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9457           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9458           0.57_wp,        &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9459           0.57_wp,        &  !< parameter 111 - thermal conductivity 3rd window layer roof
9460           0.57_wp,        &  !< parameter 112 - thermal conductivity 4th window layer roof
9461           0.91_wp,        &  !< parameter 113 - window emissivity roof
9462           0.75_wp,        &  !< parameter 114 - window transmissivity roof
9463           27.0_wp,        &  !< parameter 115 - window albedo roof
9464           0.86_wp,        &  !< parameter 116 - green emissivity roof
9465           5.0_wp,         &  !< parameter 117 - green albedo roof
9466           0.0_wp,         &  !< parameter 118 - green type roof
9467           0.8_wp,         &  !< parameter 119 - shading factor
9468           0.76_wp,        &  !< parameter 120 - g-value windows
9469           5.0_wp,         &  !< parameter 121 - u-value windows
9470           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9471           1.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9472           0.0_wp,         &  !< parameter 124 - heat recovery efficiency
9473           3.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9474           370000.0_wp,    &  !< parameter 126 - dynamic parameter innner heatstorage
9475           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9476           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9477           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9478           3.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9479           10.0_wp,        &  !< parameter 131 - basic internal heat gains without occupancy of the room
9480           3.0_wp,         &  !< parameter 132 - storey height
9481           0.2_wp          &  !< parameter 133 - ceiling construction height
9482                            /)   
9483                           
9484        building_pars(:,5) = (/   &
9485           0.5_wp,         &  !< parameter 0   - wall fraction above ground floor level
9486           0.5_wp,         &  !< parameter 1   - window fraction above ground floor level
9487           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9488           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9489           1.5_wp,         &  !< parameter 4   - LAI roof
9490           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9491           2000000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9492           103000.0_wp,    &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9493           900000.0_wp,    &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9494           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9495           0.38_wp,        &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9496           0.04_wp,        &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9497           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9498           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9499           0.92_wp,        &  !< parameter 14  - wall emissivity above ground floor level
9500           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9501           0.87_wp,        &  !< parameter 16  - window emissivity above ground floor level
9502           0.7_wp,         &  !< parameter 17  - window transmissivity above ground floor level
9503           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9504           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9505           4.0_wp,         &  !< parameter 20  - ground floor level height
9506           0.55_wp,        &  !< parameter 21  - wall fraction ground floor level
9507           0.45_wp,        &  !< parameter 22  - window fraction ground floor level
9508           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9509           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9510           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9511           2000000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9512           103000.0_wp,    &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9513           900000.0_wp,    &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9514           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9515           0.38_wp,        &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9516           0.04_wp,        &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9517           0.92_wp,        &  !< parameter 32  - wall emissivity ground floor level
9518           0.87_wp,        &  !< parameter 33  - window emissivity ground floor level
9519           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9520           0.7_wp,         &  !< parameter 35  - window transmissivity ground floor level
9521           0.001_wp,       &  !< parameter 36  - z0 roughness ground floor level
9522           0.0001_wp,      &  !< parameter 37  - z0h/z0q roughness heat/humidity
9523           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9524           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9525           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9526           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
9527           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9528           0.31_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9529           0.43_wp,        &  !< parameter 44  - 4th wall layer thickness above ground floor level
9530           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9531           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9532           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9533           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9534           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9535           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9536           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9537           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
9538           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
9539           0.31_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
9540           0.43_wp,        &  !< parameter 55  - 4th wall layer thickness ground plate
9541           2000000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9542           103000.0_wp,    &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9543           900000.0_wp,    &  !< parameter 58  - heat capacity 4th wall layer ground plate
9544           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9545           0.38_wp,        &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9546           0.04_wp,        &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9547           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
9548           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
9549           0.31_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
9550           0.43_wp,        &  !< parameter 65  - 4th wall layer thickness ground floor level
9551           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9552           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9553           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9554           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9555           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9556           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9557           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9558           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9559           0.11_wp,        &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9560           0.11_wp,        &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9561           0.11_wp,        &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9562           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9563           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9564           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9565           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9566           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9567           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9568           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9569           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9570           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9571           0.11_wp,        &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9572           0.11_wp,        &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9573           0.11_wp,        &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9574           1.0_wp,         &  !< parameter 89  - wall fraction roof
9575           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9576           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9577           0.31_wp,        &  !< parameter 92  - 3rd wall layer thickness roof
9578           0.43_wp,        &  !< parameter 93  - 4th wall layer thickness roof
9579           2000000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9580           103000.0_wp,    &  !< parameter 95  - heat capacity 3rd wall layer roof
9581           900000.0_wp,    &  !< parameter 96  - heat capacity 4th wall layer roof
9582           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9583           0.38_wp,        &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9584           0.04_wp,        &  !< parameter 99  - thermal conductivity 4th wall layer roof
9585           0.91_wp,        &  !< parameter 100 - wall emissivity roof
9586           27.0_wp,        &  !< parameter 101 - wall albedo roof
9587           0.0_wp,         &  !< parameter 102 - window fraction roof
9588           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9589           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9590           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9591           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9592           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9593           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9594           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9595           0.11_wp,        &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9596           0.11_wp,        &  !< parameter 111 - thermal conductivity 3rd window layer roof
9597           0.11_wp,        &  !< parameter 112 - thermal conductivity 4th window layer roof
9598           0.87_wp,        &  !< parameter 113 - window emissivity roof
9599           0.7_wp,         &  !< parameter 114 - window transmissivity roof
9600           27.0_wp,        &  !< parameter 115 - window albedo roof
9601           0.86_wp,        &  !< parameter 116 - green emissivity roof
9602           5.0_wp,         &  !< parameter 117 - green albedo roof
9603           0.0_wp,         &  !< parameter 118 - green type roof
9604           0.8_wp,         &  !< parameter 119 - shading factor
9605           0.6_wp,         &  !< parameter 120 - g-value windows
9606           3.0_wp,         &  !< parameter 121 - u-value windows
9607           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9608           1.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9609           0.65_wp,        &  !< parameter 124 - heat recovery efficiency
9610           2.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9611           165000.0_wp,    &  !< parameter 126 - dynamic parameter innner heatstorage
9612           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9613           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9614           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9615           7.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9616           20.0_wp,        &  !< parameter 131 - basic internal heat gains without occupancy of the room
9617           3.0_wp,         &  !< parameter 132 - storey height
9618           0.2_wp          &  !< parameter 133 - ceiling construction height
9619                            /)
9620                           
9621        building_pars(:,6) = (/   &
9622           0.425_wp,       &  !< parameter 0   - wall fraction above ground floor level
9623           0.575_wp,       &  !< parameter 1   - window fraction above ground floor level
9624           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9625           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9626           1.5_wp,         &  !< parameter 4   - LAI roof
9627           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9628           2000000.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9629           103000.0_wp,    &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9630           900000.0_wp,    &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9631           0.35_wp,        &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9632           0.14_wp,        &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9633           0.035_wp,       &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9634           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9635           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9636           0.92_wp,        &  !< parameter 14  - wall emissivity above ground floor level
9637           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9638           0.8_wp,         &  !< parameter 16  - window emissivity above ground floor level
9639           0.6_wp,         &  !< parameter 17  - window transmissivity above ground floor level
9640           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9641           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9642           4.0_wp,         &  !< parameter 20  - ground floor level height
9643           0.475_wp,       &  !< parameter 21  - wall fraction ground floor level
9644           0.525_wp,       &  !< parameter 22  - window fraction ground floor level
9645           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9646           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9647           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9648           2000000.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9649           103000.0_wp,    &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9650           900000.0_wp,    &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9651           0.35_wp,        &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9652           0.14_wp,        &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9653           0.035_wp,       &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9654           0.92_wp,        &  !< parameter 32  - wall emissivity ground floor level
9655           0.8_wp,         &  !< parameter 33  - window emissivity ground floor level
9656           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9657           0.6_wp,         &  !< parameter 35  - window transmissivity ground floor level
9658           0.001_wp,       &  !< parameter 36  - z0 roughness ground floor level
9659           0.0001_wp,      &  !< parameter 37  - z0h/z0q roughness heat/humidity
9660           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9661           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9662           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9663           0.005_wp,       &  !< parameter 41  - 1st wall layer thickness above ground floor level
9664           0.01_wp,        &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9665           0.41_wp,        &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9666           0.7_wp,         &  !< parameter 44  - 4th wall layer thickness above ground floor level
9667           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9668           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9669           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9670           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9671           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9672           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9673           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9674           0.005_wp,       &  !< parameter 52  - 1st wall layer thickness ground plate
9675           0.01_wp,        &  !< parameter 53  - 2nd wall layer thickness ground plate
9676           0.41_wp,        &  !< parameter 54  - 3rd wall layer thickness ground plate
9677           0.7_wp,         &  !< parameter 55  - 4th wall layer thickness ground plate
9678           2000000.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9679           103000.0_wp,    &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9680           900000.0_wp,    &  !< parameter 58  - heat capacity 4th wall layer ground plate
9681           0.35_wp,        &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9682           0.14_wp,        &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9683           0.035_wp,       &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9684           0.005_wp,       &  !< parameter 62  - 1st wall layer thickness ground floor level
9685           0.01_wp,        &  !< parameter 63  - 2nd wall layer thickness ground floor level
9686           0.41_wp,        &  !< parameter 64  - 3rd wall layer thickness ground floor level
9687           0.7_wp,         &  !< parameter 65  - 4th wall layer thickness ground floor level
9688           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9689           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9690           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9691           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9692           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9693           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9694           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9695           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9696           0.037_wp,       &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9697           0.037_wp,       &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9698           0.037_wp,       &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9699           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9700           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9701           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9702           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9703           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9704           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9705           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9706           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9707           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9708           0.037_wp,       &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9709           0.037_wp,       &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9710           0.037_wp,       &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9711           1.0_wp,         &  !< parameter 89  - wall fraction roof
9712           0.005_wp,       &  !< parameter 90  - 1st wall layer thickness roof
9713           0.01_wp,        &  !< parameter 91  - 2nd wall layer thickness roof
9714           0.41_wp,        &  !< parameter 92  - 3rd wall layer thickness roof
9715           0.7_wp,         &  !< parameter 93  - 4th wall layer thickness roof
9716           2000000.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9717           103000.0_wp,    &  !< parameter 95  - heat capacity 3rd wall layer roof
9718           900000.0_wp,    &  !< parameter 96  - heat capacity 4th wall layer roof
9719           0.35_wp,        &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9720           0.14_wp,        &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9721           0.035_wp,       &  !< parameter 99  - thermal conductivity 4th wall layer roof
9722           0.91_wp,        &  !< parameter 100 - wall emissivity roof
9723           27.0_wp,        &  !< parameter 101 - wall albedo roof
9724           0.0_wp,         &  !< parameter 102 - window fraction roof
9725           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9726           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9727           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9728           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9729           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9730           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9731           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9732           0.037_wp,       &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9733           0.037_wp,       &  !< parameter 111 - thermal conductivity 3rd window layer roof
9734           0.037_wp,       &  !< parameter 112 - thermal conductivity 4th window layer roof
9735           0.8_wp,         &  !< parameter 113 - window emissivity roof
9736           0.6_wp,         &  !< parameter 114 - window transmissivity roof
9737           27.0_wp,        &  !< parameter 115 - window albedo roof
9738           0.86_wp,        &  !< parameter 116 - green emissivity roof
9739           5.0_wp,         &  !< parameter 117 - green albedo roof
9740           0.0_wp,         &  !< parameter 118 - green type roof
9741           0.8_wp,         &  !< parameter 119 - shading factor
9742           0.5_wp,         &  !< parameter 120 - g-value windows
9743           0.6_wp,         &  !< parameter 121 - u-value windows
9744           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
9745           1.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
9746           0.9_wp,         &  !< parameter 124 - heat recovery efficiency
9747           2.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9748           80000.0_wp,     &  !< parameter 126 - dynamic parameter innner heatstorage
9749           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9750           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9751           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9752           5.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9753           15.0_wp,        &  !< parameter 131 - basic internal heat gains without occupancy of the room
9754           3.0_wp,         &  !< parameter 132 - storey height
9755           0.2_wp          &  !< parameter 133 - ceiling construction height
9756                            /)
9757                           
9758        building_pars(:,7) = (/   &
9759           1.0_wp,         &  !< parameter 0   - wall fraction above ground floor level
9760           0.0_wp,         &  !< parameter 1   - window fraction above ground floor level
9761           0.0_wp,         &  !< parameter 2   - green fraction above ground floor level
9762           0.0_wp,         &  !< parameter 3   - green fraction roof above ground floor level
9763           1.5_wp,         &  !< parameter 4   - LAI roof
9764           1.5_wp,         &  !< parameter 5   - LAI on wall above ground floor level
9765           1950400.0_wp,   &  !< parameter 6   - heat capacity 1st/2nd wall layer above ground floor level
9766           1848000.0_wp,   &  !< parameter 7   - heat capacity 3rd wall layer above ground floor level
9767           1848000.0_wp,   &  !< parameter 8   - heat capacity 4th wall layer above ground floor level
9768           0.7_wp,         &  !< parameter 9   - thermal conductivity 1st/2nd wall layer above ground floor level
9769           1.0_wp,         &  !< parameter 10  - thermal conductivity 3rd wall layer above ground floor level
9770           1.0_wp,         &  !< parameter 11  - thermal conductivity 4th wall layer above ground floor level
9771           299.15_wp,      &  !< parameter 12  - indoor target summer temperature
9772           293.15_wp,      &  !< parameter 13  - indoor target winter temperature
9773           0.9_wp,         &  !< parameter 14  - wall emissivity above ground floor level
9774           0.86_wp,        &  !< parameter 15  - green emissivity above ground floor level
9775           0.8_wp,         &  !< parameter 16  - window emissivity above ground floor level
9776           0.6_wp,         &  !< parameter 17  - window transmissivity above ground floor level
9777           0.001_wp,       &  !< parameter 18  - z0 roughness above ground floor level
9778           0.0001_wp,      &  !< parameter 19  - z0h/z0g roughness heat/humidity above ground floor level
9779           4.0_wp,         &  !< parameter 20  - ground floor level height
9780           1.0_wp,         &  !< parameter 21  - wall fraction ground floor level
9781           0.0_wp,         &  !< parameter 22  - window fraction ground floor level
9782           0.0_wp,         &  !< parameter 23  - green fraction ground floor level
9783           0.0_wp,         &  !< parameter 24  - green fraction roof ground floor level
9784           1.5_wp,         &  !< parameter 25  - LAI on wall ground floor level
9785           1950400.0_wp,   &  !< parameter 26  - heat capacity 1st/2nd wall layer ground floor level
9786           1848000.0_wp,   &  !< parameter 27  - heat capacity 3rd wall layer ground floor level
9787           1848000.0_wp,   &  !< parameter 28  - heat capacity 4th wall layer ground floor level
9788           0.7_wp,         &  !< parameter 29  - thermal conductivity 1st/2nd wall layer ground floor level
9789           1.0_wp,         &  !< parameter 30  - thermal conductivity 3rd wall layer ground floor level
9790           1.0_wp,         &  !< parameter 31  - thermal conductivity 4th wall layer ground floor level
9791           0.9_wp,         &  !< parameter 32  - wall emissivity ground floor level
9792           0.8_wp,         &  !< parameter 33  - window emissivity ground floor level
9793           0.86_wp,        &  !< parameter 34  - green emissivity ground floor level
9794           0.6_wp,         &  !< parameter 35  - window transmissivity ground floor level
9795           0.001_wp,       &  !< parameter 36  - z0 roughness ground floor level
9796           0.0001_wp,      &  !< parameter 37  - z0h/z0q roughness heat/humidity
9797           27.0_wp,        &  !< parameter 38  - wall albedo above ground floor level
9798           5.0_wp,         &  !< parameter 39  - green albedo above ground floor level
9799           27.0_wp,        &  !< parameter 40  - window albedo above ground floor level
9800           0.29_wp,        &  !< parameter 41  - 1st wall layer thickness above ground floor level
9801           0.295_wp,       &  !< parameter 42  - 2nd wall layer thickness above ground floor level
9802           0.695_wp,       &  !< parameter 43  - 3rd wall layer thickness above ground floor level
9803           0.985_wp,       &  !< parameter 44  - 4th wall layer thickness above ground floor level
9804           20000.0_wp,     &  !< parameter 45  - heat capacity wall surface
9805           23.0_wp,        &  !< parameter 46  - thermal conductivity of wall surface
9806           20000.0_wp,     &  !< parameter 47  - heat capacity of window surface
9807           20000.0_wp,     &  !< parameter 48  - heat capacity of green surface
9808           23.0_wp,        &  !< parameter 49  - thermal conductivity of window surface
9809           10.0_wp,        &  !< parameter 50  - thermal conductivty of green surface
9810           1.0_wp,         &  !< parameter 51  - wall fraction ground plate
9811           0.29_wp,        &  !< parameter 52  - 1st wall layer thickness ground plate
9812           0.295_wp,       &  !< parameter 53  - 2nd wall layer thickness ground plate
9813           0.695_wp,       &  !< parameter 54  - 3rd wall layer thickness ground plate
9814           0.985_wp,       &  !< parameter 55  - 4th wall layer thickness ground plate
9815           1950400.0_wp,   &  !< parameter 56  - heat capacity 1st/2nd wall layer ground plate
9816           1848000.0_wp,   &  !< parameter 57  - heat capacity 3rd wall layer ground plate
9817           1848000.0_wp,   &  !< parameter 58  - heat capacity 4th wall layer ground plate
9818           0.7_wp,         &  !< parameter 59  - thermal conductivity 1st/2nd wall layer ground plate
9819           1.0_wp,         &  !< parameter 60  - thermal conductivity 3rd wall layer ground plate
9820           1.0_wp,         &  !< parameter 61  - thermal conductivity 4th wall layer ground plate
9821           0.29_wp,        &  !< parameter 62  - 1st wall layer thickness ground floor level
9822           0.295_wp,       &  !< parameter 63  - 2nd wall layer thickness ground floor level
9823           0.695_wp,       &  !< parameter 64  - 3rd wall layer thickness ground floor level
9824           0.985_wp,       &  !< parameter 65  - 4th wall layer thickness ground floor level
9825           27.0_wp,        &  !< parameter 66  - wall albedo ground floor level
9826           0.003_wp,       &  !< parameter 67  - 1st window layer thickness ground floor level
9827           0.006_wp,       &  !< parameter 68  - 2nd window layer thickness ground floor level
9828           0.012_wp,       &  !< parameter 69  - 3rd window layer thickness ground floor level
9829           0.018_wp,       &  !< parameter 70  - 4th window layer thickness ground floor level
9830           1736000.0_wp,   &  !< parameter 71  - heat capacity 1st/2nd window layer ground floor level
9831           1736000.0_wp,   &  !< parameter 72  - heat capacity 3rd window layer ground floor level
9832           1736000.0_wp,   &  !< parameter 73  - heat capacity 4th window layer ground floor level
9833           0.57_wp,        &  !< parameter 74  - thermal conductivity 1st/2nd window layer ground floor level
9834           0.57_wp,        &  !< parameter 75  - thermal conductivity 3rd window layer ground floor level
9835           0.57_wp,        &  !< parameter 76  - thermal conductivity 4th window layer ground floor level
9836           27.0_wp,        &  !< parameter 77  - window albedo ground floor level
9837           5.0_wp,         &  !< parameter 78  - green albedo ground floor level
9838           0.003_wp,       &  !< parameter 79  - 1st window layer thickness above ground floor level
9839           0.006_wp,       &  !< parameter 80  - 2nd thickness window layer above ground floor level
9840           0.012_wp,       &  !< parameter 81  - 3rd window layer thickness above ground floor level
9841           0.018_wp,       &  !< parameter 82  - 4th window layer thickness above ground floor level
9842           1736000.0_wp,   &  !< parameter 83  - heat capacity 1st/2nd window layer above ground floor level
9843           1736000.0_wp,   &  !< parameter 84  - heat capacity 3rd window layer above ground floor level
9844           1736000.0_wp,   &  !< parameter 85  - heat capacity 4th window layer above ground floor level
9845           0.57_wp,        &  !< parameter 86  - thermal conductivity 1st/2nd window layer above ground floor level
9846           0.57_wp,        &  !< parameter 87  - thermal conductivity 3rd window layer above ground floor level
9847           0.57_wp,        &  !< parameter 88  - thermal conductivity 4th window layer above ground floor level
9848           1.0_wp,         &  !< parameter 89  - wall fraction roof
9849           0.29_wp,        &  !< parameter 90  - 1st wall layer thickness roof
9850           0.295_wp,       &  !< parameter 91  - 2nd wall layer thickness roof
9851           0.695_wp,       &  !< parameter 92  - 3rd wall layer thickness roof
9852           0.985_wp,       &  !< parameter 93  - 4th wall layer thickness roof
9853           1950400.0_wp,   &  !< parameter 94  - heat capacity 1st/2nd wall layer roof
9854           1848000.0_wp,   &  !< parameter 95  - heat capacity 3rd wall layer roof
9855           1848000.0_wp,   &  !< parameter 96  - heat capacity 4th wall layer roof
9856           0.7_wp,         &  !< parameter 97  - thermal conductivity 1st/2nd wall layer roof
9857           1.0_wp,         &  !< parameter 98  - thermal conductivity 3rd wall layer roof
9858           1.0_wp,         &  !< parameter 99  - thermal conductivity 4th wall layer roof
9859           0.9_wp,         &  !< parameter 100 - wall emissivity roof
9860           27.0_wp,        &  !< parameter 101 - wall albedo roof
9861           0.0_wp,         &  !< parameter 102 - window fraction roof
9862           0.003_wp,       &  !< parameter 103 - window 1st layer thickness roof
9863           0.006_wp,       &  !< parameter 104 - window 2nd layer thickness roof
9864           0.012_wp,       &  !< parameter 105 - window 3rd layer thickness roof
9865           0.018_wp,       &  !< parameter 106 - window 4th layer thickness roof
9866           1736000.0_wp,   &  !< parameter 107 - heat capacity 1st/2nd window layer roof
9867           1736000.0_wp,   &  !< parameter 108 - heat capacity 3rd window layer roof
9868           1736000.0_wp,   &  !< parameter 109 - heat capacity 4th window layer roof
9869           0.57_wp,        &  !< parameter 110 - thermal conductivity 1st/2nd window layer roof
9870           0.57_wp,        &  !< parameter 111 - thermal conductivity 3rd window layer roof
9871           0.57_wp,        &  !< parameter 112 - thermal conductivity 4th window layer roof
9872           0.8_wp,         &  !< parameter 113 - window emissivity roof
9873           0.6_wp,         &  !< parameter 114 - window transmissivity roof
9874           27.0_wp,        &  !< parameter 115 - window albedo roof
9875           0.86_wp,        &  !< parameter 116 - green emissivity roof
9876           5.0_wp,         &  !< parameter 117 - green albedo roof
9877           0.0_wp,         &  !< parameter 118 - green type roof
9878           0.8_wp,         &  !< parameter 119 - shading factor
9879           100.0_wp,       &  !< parameter 120 - g-value windows
9880           100.0_wp,       &  !< parameter 121 - u-value windows
9881           20.0_wp,        &  !< parameter 122 - basical airflow without occupancy of the room
9882           20.0_wp,        &  !< parameter 123 - additional airflow depend of occupancy of the room
9883           0.0_wp,         &  !< parameter 124 - heat recovery efficiency
9884           1.0_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
9885           1.0_wp,         &  !< parameter 126 - dynamic parameter innner heatstorage
9886           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
9887           100000.0_wp,    &  !< parameter 128 - maximal heating capacity
9888           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
9889           0.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
9890           0.0_wp,         &  !< parameter 131 - basic internal heat gains without occupancy of the room
9891           3.0_wp,         &  !< parameter 132 - storey height
9892           0.2_wp          &  !< parameter 133 - ceiling construction height
9893                        /)
9894                       
9895     END SUBROUTINE usm_define_pars
9896 
9897   
9898  END MODULE urban_surface_mod
Note: See TracBrowser for help on using the repository browser.