source: palm/trunk/SOURCE/indoor_model_mod.f90 @ 4750

Last change on this file since 4750 was 4750, checked in by suehring, 4 years ago

Indoor-model new: Namelist parameter added to switch-off/on the indoor model during wall/soil spinup; bugfixes concerning indoor model: bugfix in window-wall treatment during spinup - in the urban-surface model the window fraction is set to zero during spinup, so it is done here also; bugfix in wall treatment - inner wall temperature was too low due to wrong weighting of wall/green/window fractions; Revision of 10-cm temperature at vertical walls - assume grid-cell temperature rather than employ MOST; call hourly-based indoor model only once per hour during spinup, not every timestep; add missing dependency in Makefile; urban-surface model: bugfix in openmp directive

  • Property svn:keywords set to Id
File size: 110.9 KB
Line 
1!> @file indoor_model_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 terms of the GNU General
6! Public License as published by the Free Software Foundation, either version 3 of the License, or
7! (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
11! Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with PALM. If not, see
14! <http://www.gnu.org/licenses/>.
15!
16! Copyright 2018-2020 Leibniz Universitaet Hannover
17! Copyright 2018-2020 Hochschule Offenburg
18!--------------------------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: indoor_model_mod.f90 4750 2020-10-16 14:27:48Z suehring $
27! - Namelist parameter added to switch-off/on the indoor model during wall/soil spinup
28! - Bugfix in window-wall treatment during spinup - in the urban-surface model the window fraction
29!   is set to zero during spinup, so it is done here also
30! - Bugfix in wall treatment - inner wall temperature was too low due to wrong weighting of
31!   wall/green/window fractions
32!
33! 4730 2020-10-07 10:48:51Z suehring
34! Bugfix - avoid divisions by zero
35!
36! 4709 2020-09-28 19:20:00Z maronga
37! Bugfix: avoid division by zero in case of zero window fraction (now also for vertical walls).
38! Reactivated waste heat.
39!
40! 4704 2020-09-28 10:13:03Z maronga
41! Bugfix: avoid division by zero in case of zero window fraction
42!
43! 4702 2020-09-27 18:39:00Z maronga
44! Removed unused variable indoor_wall_window_temperature
45!
46! 4701 2020-09-27 11:02:15Z maronga
47! Heat transfer for wall and windows back to USM separated into q_wall and q_win (instead q_wall_win).
48! Heat flow direction revised (heat flow positive from outside to inside).
49! New variable indoor_wall_temperature (for q_wall).
50! Removed unused quantity q_trans.
51!
52! 4698 2020-09-25 08:37:55Z maronga
53! Fixed faulty characters
54!
55! 4687 2020-09-21 19:40:16Z maronga
56! Bugfix: values of theta_m_t_prev were not stored for individual surfaces and thus re-used by all
57! surfaces and buildings, which led to excessive indoor temperatures
58!
59! 4681 2020-09-16 10:23:06Z pavelkrc
60! Bugfix for implementation of downward surfaces
61!
62! 4671 2020-09-09 20:27:58Z pavelkrc
63! Implementation of downward facing USM and LSM surfaces
64!
65! 4646 2020-08-24 16:02:40Z raasch
66! file re-formatted to follow the PALM coding standard
67!
68! 4481 2020-03-31 18:55:54Z maronga
69! Change order of dimension in surface array %frac to allow for better vectorization.
70!
71! 4441 2020-03-04 19:20:35Z suehring
72! Major bugfix in calculation of energy demand - floor-area-per-facade was wrongly calculated
73! leading to unrealistically high energy demands and thus to unreallistically high waste-heat
74! fluxes.
75!
76! 4346 2019-12-18 11:55:56Z motisi
77! Introduction of wall_flags_total_0, which currently sets bits based on static topography
78! information used in wall_flags_static_0
79!
80! 4329 2019-12-10 15:46:36Z motisi
81! Renamed wall_flags_0 to wall_flags_static_0
82!
83! 4310 2019-11-26 19:01:28Z suehring
84! Remove dt_indoor from namelist input. The indoor model is an hourly-based model, calling it
85! more/less often lead to inaccurate results.
86!
87! 4299 2019-11-22 10:13:38Z suehring
88! Output of indoor temperature revised (to avoid non-defined values within buildings)
89!
90! 4267 2019-10-16 18:58:49Z suehring
91! Bugfix in initialization, some indices to access building_pars where wrong.
92! Introduction of seasonal parameters.
93!
94! 4246 2019-09-30 09:27:52Z pavelkrc
95!
96!
97! 4242 2019-09-27 12:59:10Z suehring
98! Bugfix in array index
99!
100! 4238 2019-09-25 16:06:01Z suehring
101! - Bugfix in determination of minimum facade height and in location message
102! - Bugfix, avoid division by zero
103! - Some optimization
104!
105! 4227 2019-09-10 18:04:34Z gronemeier
106! implement new palm_date_time_mod
107!
108! 4217 2019-09-04 09:47:05Z scharf
109! Corrected "Former revisions" section
110!
111! 4209 2019-09-02 12:00:03Z suehring
112! - Bugfix in initialization of indoor temperature
113! - Prescibe default indoor temperature in case it is not given in the namelist input
114!
115! 4182 2019-08-21 14:37:54Z scharf
116! Corrected "Former revisions" section
117!
118! 4148 2019-08-08 11:26:00Z suehring
119! Bugfix in case of non grid-resolved buildings. Further, vertical grid spacing is now considered at
120! the correct level.
121! - change calculation of a_m and c_m
122! - change calculation of u-values (use h_es in building array)
123! - rename h_tr_... to  h_t_...
124!          h_tr_em  to  h_t_wm
125!          h_tr_op  to  h_t_wall
126!          h_tr_w   to  h_t_es
127! - rename h_ve     to  h_v
128! - rename h_is     to  h_ms
129! - inserted net_floor_area
130! - inserted params_waste_heat_h, params_waste_heat_c from building database
131!   in building array
132! - change calculation of q_waste_heat
133! - bugfix in averaging mean indoor temperature
134!
135! 3759 2019-02-21 15:53:45Z suehring
136! - Calculation of total building volume
137! - Several bugfixes
138! - Calculation of building height revised
139!
140! 3745 2019-02-15 18:57:56Z suehring
141! - remove building_type from module
142! - initialize parameters for each building individually instead of a bulk initializaion with
143!   identical building type for all
144! - output revised
145! - add missing _wp
146! - some restructuring of variables in building data structure
147!
148! 3744 2019-02-15 18:38:58Z suehring
149! Some interface calls moved to module_interface + cleanup
150!
151! 3469 2018-10-30 20:05:07Z kanani
152! Initial revision (tlang, suehring, kanani, srissman)!
153!
154! Authors:
155! --------
156! @author Tobias Lang
157! @author Jens Pfafferott
158! @author Farah Kanani-Suehring
159! @author Matthias Suehring
160! @author Sascha Rissmann
161! @author Bjoern Maronga
162!
163!
164! Description:
165! ------------
166!> Module for Indoor Climate Model (ICM)
167!> The module is based on the DIN EN ISO 13790 with simplified hour-based procedure.
168!> This model is a equivalent circuit diagram of a three-point RC-model (5R1C).
169!> This module differs between indoor-air temperature an average temperature of indoor surfaces which make it prossible to determine
170!> thermal comfort
171!> the heat transfer between indoor and outdoor is simplified
172
173!> @todo Many statement comments that are given as doxygen comments need to be changed to normal comments
174!> @todo Replace window_area_per_facade by %frac(1,m) for window
175!> @todo emissivity change for window blinds if solar_protection_on=1
176
177!> @note Do we allow use of integer flags, or only logical flags? (concerns e.g. cooling_on, heating_on)
178!> @note How to write indoor temperature output to pt array?
179!>
180!> @bug  Calculation of iwghf_eb and iwghf_eb_window is faulty
181!--------------------------------------------------------------------------------------------------!
182 MODULE indoor_model_mod
183
184    USE arrays_3d,                                                                                 &
185        ONLY:  ddzw,                                                                               &
186               dzw,                                                                                &
187               pt
188
189    USE control_parameters,                                                                        &
190        ONLY:  initializing_actions
191
192    USE kinds
193
194    USE netcdf_data_input_mod,                                                                     &
195        ONLY:  building_id_f, building_type_f
196
197    USE palm_date_time_mod,                                                                        &
198        ONLY:  get_date_time, northward_equinox, seconds_per_hour, southward_equinox
199
200    USE surface_mod,                                                                               &
201        ONLY:  surf_usm_h, surf_usm_v
202
203
204    IMPLICIT NONE
205
206!
207!-- Define data structure for buidlings.
208    TYPE build
209
210       INTEGER(iwp) ::  id                                !< building ID
211       INTEGER(iwp) ::  kb_max                            !< highest vertical index of a building
212       INTEGER(iwp) ::  kb_min                            !< lowest vertical index of a building
213       INTEGER(iwp) ::  num_facades_per_building_h = 0    !< total number of horizontal facades elements
214       INTEGER(iwp) ::  num_facades_per_building_h_l = 0  !< number of horizontal facade elements on local subdomain
215       INTEGER(iwp) ::  num_facades_per_building_v = 0    !< total number of vertical facades elements
216       INTEGER(iwp) ::  num_facades_per_building_v_l = 0  !< number of vertical facade elements on local subdomain
217       INTEGER(iwp) ::  ventilation_int_loads             !< [-] allocation of activity in the building
218
219       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  l_h            !< index array linking surface-element orientation index
220                                                                  !< for horizontal surfaces with building
221       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  l_v            !< index array linking surface-element orientation index
222                                                                  !< for vertical surfaces with building
223       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  m_h            !< index array linking surface-element index for
224                                                                  !< horizontal surfaces with building
225       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  m_v            !< index array linking surface-element index for
226                                                                  !< vertical surfaces with building
227       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facade_h   !< number of horizontal facade elements per buidling
228                                                                  !< and height level
229       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facade_v   !< number of vertical facades elements per buidling
230                                                                  !< and height level
231
232
233       LOGICAL ::  on_pe = .FALSE.   !< flag indicating whether a building with certain ID is on local subdomain
234
235       REAL(wp) ::  air_change_high       !< [1/h] air changes per time_utc_hour
236       REAL(wp) ::  air_change_low        !< [1/h] air changes per time_utc_hour
237       REAL(wp) ::  area_facade           !< [m2] area of total facade
238       REAL(wp) ::  building_height       !< building height
239       REAL(wp) ::  eta_ve                !< [-] heat recovery efficiency
240       REAL(wp) ::  factor_a              !< [-] Dynamic parameters specific effective surface according to Table 12; 2.5
241                                          !< (very light, light and medium), 3.0 (heavy), 3.5 (very heavy)
242       REAL(wp) ::  factor_c              !< [J/(m2 K)] Dynamic parameters inner heatstorage according to Table 12; 80000
243                                          !< (very light), 110000 (light), 165000 (medium), 260000 (heavy), 370000 (very heavy)
244       REAL(wp) ::  f_c_win               !< [-] shading factor
245       REAL(wp) ::  fapf                  !< [m2/m2] floor area per facade
246       REAL(wp) ::  g_value_win           !< [-] SHGC factor
247       REAL(wp) ::  h_es                  !< [W/(m2 K)] surface-related heat transfer coefficient between extern and surface
248       REAL(wp) ::  height_cei_con        !< [m] ceiling construction heigth
249       REAL(wp) ::  height_storey         !< [m] storey heigth
250       REAL(wp) ::  params_waste_heat_c   !< [-] anthropogenic heat outputs for cooling e.g. 1.33 for KKM with COP = 3
251       REAL(wp) ::  params_waste_heat_h   !< [-] anthropogenic heat outputs for heating e.g. 1 - 0.9 = 0.1 for combustion with
252                                          !< eta = 0.9 or -2 for WP with COP = 3
253       REAL(wp) ::  phi_c_max             !< [W] Max. Cooling capacity (negative)
254       REAL(wp) ::  phi_h_max             !< [W] Max. Heating capacity (positive)
255       REAL(wp) ::  q_c_max               !< [W/m2] Max. Cooling heat flux per netto floor area (negative)
256       REAL(wp) ::  q_h_max               !< [W/m2] Max. Heating heat flux per netto floor area (positive)
257       REAL(wp) ::  qint_high             !< [W/m2] internal heat gains, option Database qint_0-23
258       REAL(wp) ::  qint_low              !< [W/m2] internal heat gains, option Database qint_0-23
259       REAL(wp) ::  lambda_at             !< [-] ratio internal surface/floor area chap. 7.2.2.2.
260       REAL(wp) ::  lambda_layer3         !< [W/(m*K)] Thermal conductivity of the inner layer
261       REAL(wp) ::  net_floor_area        !< [m2] netto ground area
262       REAL(wp) ::  s_layer3              !< [m] half thickness of the inner layer (layer_3)
263       REAL(wp) ::  theta_int_c_set       !< [degree_C] Max. Setpoint temperature (summer)
264       REAL(wp) ::  theta_int_h_set       !< [degree_C] Max. Setpoint temperature (winter)
265       REAL(wp) ::  u_value_win           !< [W/(m2*K)] transmittance
266       REAL(wp) ::  vol_tot               !< [m3] total building volume
267
268       REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in       !< mean building indoor temperature, height dependent
269       REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in_l     !< mean building indoor temperature on local subdomain, height dependent
270       REAL(wp), DIMENSION(:), ALLOCATABLE ::  theta_m_t_prev_h !< [degree_C] value of theta_m_t from previous time step (horizontal)
271       REAL(wp), DIMENSION(:), ALLOCATABLE ::  theta_m_t_prev_v !< [degree_C] value of theta_m_t from previous time step (vertical)
272       REAL(wp), DIMENSION(:), ALLOCATABLE ::  volume     !< total building volume, height dependent
273       REAL(wp), DIMENSION(:), ALLOCATABLE ::  vol_frac   !< fraction of local on total building volume, height dependent
274       REAL(wp), DIMENSION(:), ALLOCATABLE ::  vpf        !< building volume volume per facade element, height dependent
275
276    END TYPE build
277
278    TYPE(build), DIMENSION(:), ALLOCATABLE ::  buildings   !< building array
279
280    INTEGER(iwp) ::  cooling_on              !< Indoor cooling flag (0=off, 1=on)
281    INTEGER(iwp) ::  heating_on              !< Indoor heating flag (0=off, 1=on)
282    INTEGER(iwp) ::  num_build               !< total number of buildings in domain
283    INTEGER(iwp) ::  solar_protection_off    !< Solar protection off
284    INTEGER(iwp) ::  solar_protection_on     !< Solar protection on
285
286    LOGICAL ::  indoor_during_spinup = .FALSE.      !< namelist parameter used to switch-off/on the indoor model during spinup
287!
288!-- Declare all global variables within the module
289
290    REAL(wp), PARAMETER ::  dt_indoor = 3600.0_wp                  !< [s] time interval for indoor-model application, fixed to
291                                                                   !< 3600.0 due to model requirements
292    REAL(wp), PARAMETER ::  h_is                     = 3.45_wp     !< [W/(m2 K)] surface-related heat transfer coefficient between
293                                                                   !< surface and air (chap. 7.2.2.2)
294    REAL(wp), PARAMETER ::  h_ms                     = 9.1_wp      !< [W/(m2 K)] surface-related heat transfer coefficient between
295                                                                   !< component and surface (chap. 12.2.2)
296    REAL(wp), PARAMETER ::  params_f_f               = 0.3_wp      !< [-] frame ratio chap. 8.3.2.1.1 for buildings with mostly
297                                                                   !< cooling 2.0_wp
298    REAL(wp), PARAMETER ::  params_f_w               = 0.9_wp      !< [-] correction factor (fuer nicht senkrechten Stahlungseinfall
299                                                                   !< DIN 4108-2 chap.8, (hier konstant, keine WinkelabhÀngigkeit)
300    REAL(wp), PARAMETER ::  params_f_win             = 0.5_wp      !< [-] proportion of window area, Database A_win aus
301                                                                   !< Datenbank 27 window_area_per_facade_percent
302    REAL(wp), PARAMETER ::  params_solar_protection  = 300.0_wp    !< [W/m2] chap. G.5.3.1 sun protection closed, if the radiation
303                                                                   !< on facade exceeds this value
304
305    REAL(wp) ::  a_m                                 !< [m2] the effective mass-related area
306    REAL(wp) ::  air_change                          !< [1/h] Airflow
307    REAL(wp) ::  c_m                                 !< [J/K] internal heat storage capacity
308    REAL(wp) ::  facade_element_area                 !< [m2_facade] building surface facade
309    REAL(wp) ::  floor_area_per_facade               !< [m2/m2] floor area per facade area
310    REAL(wp) ::  h_t_1                               !< [W/K] Heat transfer coefficient auxiliary variable 1
311    REAL(wp) ::  h_t_2                               !< [W/K] Heat transfer coefficient auxiliary variable 2
312    REAL(wp) ::  h_t_3                               !< [W/K] Heat transfer coefficient auxiliary variable 3
313    REAL(wp) ::  h_t_es                              !< [W/K] heat transfer coefficient of doors, windows, curtain walls and
314                                                     !< glazed walls (assumption: thermal mass=0)
315    REAL(wp) ::  h_t_is                              !< [W/K] thermal coupling conductance (Thermischer Kopplungsleitwert)
316    REAL(wp) ::  h_t_ms                              !< [W/K] Heat transfer conductance term (got with h_t_wm the thermal mass)
317    REAL(wp) ::  h_t_wall                            !< [W/K] heat transfer coefficient of opaque components (assumption: got all
318                                                     !< thermal mass) contains of h_t_wm and h_t_ms
319    REAL(wp) ::  h_t_wm                              !< [W/K] Heat transfer coefficient of the emmision (got with h_t_ms the
320                                                     !< thermal mass)
321    REAL(wp) ::  h_v                                 !< [W/K] heat transfer of ventilation
322    REAL(wp) ::  indoor_volume_per_facade            !< [m3] indoor air volume per facade element
323    REAL(wp) ::  initial_indoor_temperature = 293.15 !< [K] initial indoor temperature (namelist parameter)
324    REAL(wp) ::  net_sw_in                           !< [W/m2] net short-wave radiation
325    REAL(wp) ::  phi_hc_nd                           !< [W] heating demand and/or cooling demand
326    REAL(wp) ::  phi_hc_nd_10                        !< [W] heating demand and/or cooling demand for heating or cooling
327    REAL(wp) ::  phi_hc_nd_ac                        !< [W] actual heating demand and/or cooling demand
328    REAL(wp) ::  phi_hc_nd_un                        !< [W] unlimited heating demand and/or cooling demand which is necessary to
329                                                     !< reach the demanded required temperature (heating is positive,
330                                                     !< cooling is negative)
331    REAL(wp) ::  phi_ia                              !< [W] internal air load = internal loads * 0.5, Eq. (C.1)
332    REAL(wp) ::  phi_m                               !< [W] mass specific thermal load (internal and external)
333    REAL(wp) ::  phi_mtot                            !< [W] total mass specific thermal load (internal and external)
334    REAL(wp) ::  phi_sol                             !< [W] solar loads
335    REAL(wp) ::  phi_st                              !< [W] mass specific thermal load implied non thermal mass
336    REAL(wp) ::  q_wall                              !< [W/m2]heat flux from indoor into wall
337    REAL(wp) ::  q_win                               !< [W/m2]heat flux from indoor into window
338    REAL(wp) ::  q_waste_heat                        !< [W/m2]waste heat, sum of waste heat over the roof to Palm
339
340    REAL(wp) ::  q_c_m                               !< [W] Energy of thermal storage mass specific thermal load for internal
341                                                     !< and external heatsources (for energy bilanz)
342    REAL(wp) ::  q_c_st                              !< [W] Energy of thermal storage mass specific thermal load implied non
343                                                     !< thermal mass (for energy bilanz)
344    REAL(wp) ::  q_int                               !< [W] Energy of internal air load (for energy bilanz)
345    REAL(wp) ::  q_sol                               !< [W] Energy of solar (for energy bilanz)
346    REAL(wp) ::  q_vent                              !< [W] Energy of ventilation (for energy bilanz)
347
348    REAL(wp) ::  schedule_d                          !< [-] activation for internal loads (low or high + low)
349    REAL(wp) ::  skip_time_do_indoor = 0.0_wp        !< [s] Indoor model is not called before this time
350    REAL(wp) ::  theta_air                           !< [degree_C] air temperature of the RC-node
351    REAL(wp) ::  theta_air_0                         !< [degree_C] air temperature of the RC-node in equilibrium
352    REAL(wp) ::  theta_air_10                        !< [degree_C] air temperature of the RC-node from a heating capacity
353                                                     !< of 10 W/m2
354    REAL(wp) ::  theta_air_ac                        !< [degree_C] actual room temperature after heating/cooling
355    REAL(wp) ::  theta_air_set                       !< [degree_C] Setpoint_temperature for the room
356    REAL(wp) ::  theta_m                             !< [degree_C} inner temperature of the RC-node
357    REAL(wp) ::  theta_m_t                           !< [degree_C] (Fictive) component temperature during timestep
358    REAL(wp) ::  theta_op                            !< [degree_C] operative temperature
359    REAL(wp) ::  theta_s                             !< [degree_C] surface temperature of the RC-node
360    REAL(wp) ::  time_indoor = 0.0_wp                !< [s] time since last call of indoor model
361    REAL(wp) ::  total_area                          !< [m2] area of all surfaces pointing to zone
362    REAL(wp) ::  window_area_per_facade              !< [m2] window area per facade element
363
364!
365!-- Definition of seasonal parameters, summer and winter, for different building types
366    REAL(wp), DIMENSION(0:1,1:7) ::  summer_pars = RESHAPE( (/                & ! building_type 1
367                                          0.5_wp,                             & ! basical airflow without occupancy of the room
368                                          2.0_wp,                             & ! additional airflow depend of occupancy of the room
369                                          0.5_wp,                             & ! building_type 2: basical airflow without occupancy
370                                                                                ! of the room
371                                          2.0_wp,                             & ! additional airflow depend of occupancy of the room
372                                          0.8_wp,                             & ! building_type 3: basical airflow without occupancy
373                                                                                ! of the room
374                                          2.0_wp,                             & ! additional airflow depend of occupancy of the room
375                                          0.1_wp,                             & ! building_type 4: basical airflow without occupancy
376                                                                                ! of the room
377                                          1.5_wp,                             & ! additional airflow depend of occupancy of the room
378                                          0.1_wp,                             & ! building_type 5: basical airflow without occupancy
379                                                                                ! of the room
380                                          1.5_wp,                             & ! additional airflow depend of occupancy of the room
381                                          0.1_wp,                             & ! building_type 6: basical airflow without occupancy
382                                                                                ! of the room
383                                          1.5_wp,                             & ! additional airflow depend of occupancy of the room
384                                          0.1_wp,                             & ! building_type 7: basical airflow without occupancy
385                                                                                ! of the room
386                                          1.5_wp                              & ! additional airflow depend of occupancy of the room
387                                                           /), (/ 2, 7 /) )
388
389    REAL(wp), DIMENSION(0:1,1:7) ::  winter_pars = RESHAPE( (/                & ! building_type 1
390                                          0.1_wp,                             & ! basical airflow without occupancy of the room
391                                          0.5_wp,                             & ! additional airflow depend of occupancy of the room
392                                          0.1_wp,                             & ! building_type 2: basical airflow without occupancy
393                                                                                ! of the room
394                                          0.5_wp,                             & ! additional airflow depend of occupancy of the room
395                                          0.1_wp,                             & ! building_type 3: basical airflow without occupancy
396                                                                                ! of the room
397                                          0.5_wp,                             & ! additional airflow depend of occupancy of the room
398                                          0.1_wp,                             & ! building_type 4: basical airflow without occupancy
399                                                                                ! of the room
400                                          1.5_wp,                             & ! additional airflow depend of occupancy of the room
401                                          0.1_wp,                             & ! building_type 5: basical airflow without occupancy
402                                                                                ! of the room
403                                          1.5_wp,                             & ! additional airflow depend of occupancy of the room
404                                          0.1_wp,                             & ! building_type 6: basical airflow without occupancy
405                                                                                ! of the room
406                                          1.5_wp,                             & ! additional airflow depend of occupancy of the room
407                                          0.1_wp,                             & ! building_type 7: basical airflow without occupancy
408                                                                                ! of the room
409                                          1.5_wp                              & ! additional airflow depend of occupancy of the room
410                                                           /), (/ 2, 7 /) )
411
412    SAVE
413
414
415    PRIVATE
416
417!
418!-- Add INTERFACES that must be available to other modules
419    PUBLIC im_init, im_main_heatcool, im_parin, im_define_netcdf_grid, im_check_data_output,       &
420           im_data_output_3d, im_check_parameters
421
422
423!
424!-- Add VARIABLES that must be available to other modules
425    PUBLIC dt_indoor,                                                                              &
426           indoor_during_spinup,                                                                   &
427           skip_time_do_indoor,                                                                    &
428           time_indoor
429
430!
431!-- PALM interfaces:
432!-- Data output checks for 2D/3D data to be done in check_parameters
433     INTERFACE im_check_data_output
434        MODULE PROCEDURE im_check_data_output
435     END INTERFACE im_check_data_output
436!
437!-- Input parameter checks to be done in check_parameters
438     INTERFACE im_check_parameters
439        MODULE PROCEDURE im_check_parameters
440     END INTERFACE im_check_parameters
441!
442!-- Data output of 3D data
443     INTERFACE im_data_output_3d
444        MODULE PROCEDURE im_data_output_3d
445     END INTERFACE im_data_output_3d
446
447!
448!-- Definition of data output quantities
449     INTERFACE im_define_netcdf_grid
450        MODULE PROCEDURE im_define_netcdf_grid
451     END INTERFACE im_define_netcdf_grid
452!
453! !
454! !-- Output of information to the header file
455!     INTERFACE im_header
456!        MODULE PROCEDURE im_header
457!     END INTERFACE im_header
458!
459!-- Calculations for indoor temperatures
460    INTERFACE im_calc_temperatures
461       MODULE PROCEDURE im_calc_temperatures
462    END INTERFACE im_calc_temperatures
463!
464!-- Initialization actions
465    INTERFACE im_init
466       MODULE PROCEDURE im_init
467    END INTERFACE im_init
468!
469!-- Main part of indoor model
470    INTERFACE im_main_heatcool
471       MODULE PROCEDURE im_main_heatcool
472    END INTERFACE im_main_heatcool
473!
474!-- Reading of NAMELIST parameters
475    INTERFACE im_parin
476       MODULE PROCEDURE im_parin
477    END INTERFACE im_parin
478
479 CONTAINS
480
481!--------------------------------------------------------------------------------------------------!
482! Description:
483! ------------
484!< Calculation of the air temperatures and mean radiation temperature.
485!< This is basis for the operative temperature.
486!< Based on a Crank-Nicholson scheme with a timestep of a hour.
487!--------------------------------------------------------------------------------------------------!
488 SUBROUTINE im_calc_temperatures ( i, j, k, indoor_wall_temperature,  &
489                                   near_facade_temperature, phi_hc_nd_dummy, theta_m_t_prev )
490
491    INTEGER(iwp) ::  i
492    INTEGER(iwp) ::  j
493    INTEGER(iwp) ::  k
494
495    REAL(wp) ::  indoor_wall_temperature   !< temperature of innermost wall layer evtl in im_calc_temperatures einfÃŒgen
496    REAL(wp) ::  near_facade_temperature
497    REAL(wp) ::  phi_hc_nd_dummy
498    REAL(wp), INTENT(IN) :: theta_m_t_prev
499!
500!-- Calculation of total mass specific thermal load (internal and external)
501    phi_mtot = ( phi_m + h_t_wm * indoor_wall_temperature                                   &
502                       + h_t_3  * ( phi_st + h_t_es * pt(k,j,i)                                    &
503                                            + h_t_1 *                                              &
504                                    ( ( ( phi_ia + phi_hc_nd_dummy ) / h_v )                       &
505                                                 + near_facade_temperature )                       &
506                                  ) / h_t_2                                                        &
507               )                                                                !< [degree_C] Eq. (C.5)
508!
509!-- Calculation of component temperature at current timestep
510    theta_m_t = ( ( theta_m_t_prev                                                                 &
511                    * ( ( c_m / 3600.0_wp ) - 0.5_wp * ( h_t_3 + h_t_wm ) )                        &
512                     + phi_mtot                                                                    &
513                  )                                                                                &
514                  /   ( ( c_m / 3600.0_wp ) + 0.5_wp * ( h_t_3 + h_t_wm ) )                        &
515                )                                                               !< [degree_C] Eq. (C.4)
516!
517!-- Calculation of mean inner temperature for the RC-node in current timestep
518    theta_m = ( theta_m_t + theta_m_t_prev ) * 0.5_wp                           !< [degree_C] Eq. (C.9)
519
520!
521!-- Calculation of mean surface temperature of the RC-node in current timestep
522    theta_s = ( (   h_t_ms * theta_m + phi_st + h_t_es * pt(k,j,i)                                 &
523                  + h_t_1  * ( near_facade_temperature                                             &
524                           + ( phi_ia + phi_hc_nd_dummy ) / h_v )                                  &
525                )                                                                                  &
526                / ( h_t_ms + h_t_es + h_t_1 )                                                      &
527              )                                                                 !< [degree_C] Eq. (C.10)
528
529!
530!-- Calculation of the air temperature of the RC-node
531
532
533    theta_air = ( h_t_is * theta_s + h_v * near_facade_temperature + phi_ia + phi_hc_nd_dummy ) /  &
534                ( h_t_is + h_v )                                                !< [degree_C] Eq. (C.11)
535
536
537 END SUBROUTINE im_calc_temperatures
538
539
540!--------------------------------------------------------------------------------------------------!
541! Description:
542! ------------
543!> Initialization of the indoor model.
544!> Static information are calculated here, e.g. building parameters and geometrical information,
545!> anything that doesn't change in time.
546!
547!-- Input values
548!-- Input datas from Palm, M4
549!     i_global             -->  net_sw_in                         !< global radiation [W/m2]
550!     theta_e              -->  pt(k,j,i)                         !< undisturbed outside temperature, 1. PALM volume, for windows
551!     theta_sup = theta_f  -->  surf_usm_h%pt_10cm(m)
552!                               surf_usm_v(l)%pt_10cm(m)          !< Air temperature, facade near (10cm) air temperature from
553                                                                  !< 1. Palm volume
554!     theta_node           -->  t_wall_h(nzt_wall,m)
555!                               t_wall_v(l)%t(nzt_wall,m)         !< Temperature of innermost wall layer, for opaque wall
556!--------------------------------------------------------------------------------------------------!
557 SUBROUTINE im_init
558
559    USE control_parameters,                                                                        &
560        ONLY:  message_string, time_since_reference_point
561
562    USE indices,                                                                                   &
563        ONLY:  nxl, nxr, nyn, nys, nzb, nzt, wall_flags_total_0
564
565    USE grid_variables,                                                                            &
566        ONLY:  dx, dy
567
568    USE pegrid
569
570    USE surface_mod,                                                                               &
571        ONLY:  surf_usm_h, surf_usm_v
572
573    USE urban_surface_mod,                                                                         &
574        ONLY:  building_pars, building_type
575
576    INTEGER(iwp) ::  bt          !< local building type
577    INTEGER(iwp) ::  day_of_year !< day of the year
578    INTEGER(iwp) ::  i           !< running index along x-direction
579    INTEGER(iwp) ::  j           !< running index along y-direction
580    INTEGER(iwp) ::  k           !< running index along z-direction
581    INTEGER(iwp) ::  l           !< running index for surface-element orientation
582    INTEGER(iwp) ::  m           !< running index surface elements
583    INTEGER(iwp) ::  n           !< building index
584    INTEGER(iwp) ::  nb          !< building index
585
586    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids           !< building IDs on entire model domain
587    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_final     !< building IDs on entire model domain,
588                                                                    !< multiple occurences are sorted out
589    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_final_tmp !< temporary array used for resizing
590    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_l         !< building IDs on local subdomain
591    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_l_tmp     !< temporary array used to resize array of building IDs
592    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  displace_dum        !< displacements of start addresses, used for MPI_ALLGATHERV
593    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  k_max_l             !< highest vertical index of a building on subdomain
594    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  k_min_l             !< lowest vertical index of a building on subdomain
595    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  n_fa                !< counting array
596    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facades_h       !< dummy array used for summing-up total number of
597                                                                    !< horizontal facade elements
598    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facades_v       !< dummy array used for summing-up total number of
599                                                                    !< vertical facade elements
600    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  receive_dum_h       !< dummy array used for MPI_ALLREDUCE
601    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  receive_dum_v       !< dummy array used for MPI_ALLREDUCE
602
603    INTEGER(iwp), DIMENSION(0:numprocs-1) ::  num_buildings         !< number of buildings with different ID on entire model domain
604    INTEGER(iwp), DIMENSION(0:numprocs-1) ::  num_buildings_l       !< number of buildings with different ID on local subdomain
605
606    REAL(wp) ::  u_tmp                                     !< dummy for temporary calculation of u-value without h_is
607    REAL(wp) ::  du_tmp                                    !< 1/u_tmp
608    REAL(wp) ::  du_win_tmp                                !< 1/building(nb)%u_value_win
609    REAL(wp) ::  facade_area_v                             !< dummy to compute the total facade area from vertical walls
610
611    REAL(wp), DIMENSION(:), ALLOCATABLE ::  volume         !< total building volume at each discrete height level
612    REAL(wp), DIMENSION(:), ALLOCATABLE ::  volume_l       !< total building volume at each discrete height level,
613                                                           !< on local subdomain
614
615    CALL location_message( 'initializing indoor model', 'start' )
616!
617!-- Initializing of indoor model is only possible if buildings can be distinguished by their IDs.
618    IF ( .NOT. building_id_f%from_file )  THEN
619       message_string = 'Indoor model requires information about building_id'
620       CALL message( 'im_init', 'PA0999', 1, 2, 0, 6, 0  )
621    ENDIF
622!
623!-- Determine number of different building IDs on local subdomain.
624    num_buildings_l = 0
625    num_buildings   = 0
626    ALLOCATE( build_ids_l(1) )
627    DO  i = nxl, nxr
628       DO  j = nys, nyn
629          IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
630             IF ( num_buildings_l(myid) > 0 )  THEN
631                IF ( ANY( building_id_f%var(j,i) == build_ids_l ) )  THEN
632                   CYCLE
633                ELSE
634                   num_buildings_l(myid) = num_buildings_l(myid) + 1
635!
636!--                Resize array with different local building ids
637                   ALLOCATE( build_ids_l_tmp(1:SIZE(build_ids_l)) )
638                   build_ids_l_tmp = build_ids_l
639                   DEALLOCATE( build_ids_l )
640                   ALLOCATE( build_ids_l(1:num_buildings_l(myid)) )
641                   build_ids_l(1:num_buildings_l(myid)-1) =                                        &
642                                                          build_ids_l_tmp(1:num_buildings_l(myid)-1)
643                   build_ids_l(num_buildings_l(myid)) = building_id_f%var(j,i)
644                   DEALLOCATE( build_ids_l_tmp )
645                ENDIF
646!
647!--          First occuring building id on PE
648             ELSE
649                num_buildings_l(myid) = num_buildings_l(myid) + 1
650                build_ids_l(1) = building_id_f%var(j,i)
651             ENDIF
652          ENDIF
653       ENDDO
654    ENDDO
655!
656!-- Determine number of building IDs for the entire domain. (Note, building IDs can appear multiple
657!-- times as buildings might be distributed over several PEs.)
658#if defined( __parallel )
659    CALL MPI_ALLREDUCE( num_buildings_l, num_buildings, numprocs, MPI_INTEGER, MPI_SUM, comm2d,    &
660                        ierr )
661#else
662    num_buildings = num_buildings_l
663#endif
664    ALLOCATE( build_ids(1:SUM(num_buildings)) )
665!
666!-- Gather building IDs. Therefore, first, determine displacements used required for MPI_GATHERV
667!-- call.
668    ALLOCATE( displace_dum(0:numprocs-1) )
669    displace_dum(0) = 0
670    DO i = 1, numprocs-1
671       displace_dum(i) = displace_dum(i-1) + num_buildings(i-1)
672    ENDDO
673
674#if defined( __parallel )
675    CALL MPI_ALLGATHERV( build_ids_l(1:num_buildings_l(myid)),                                     &
676                         num_buildings(myid),                                                      &
677                         MPI_INTEGER,                                                              &
678                         build_ids,                                                                &
679                         num_buildings,                                                            &
680                         displace_dum,                                                             &
681                         MPI_INTEGER,                                                              &
682                         comm2d, ierr )
683
684    DEALLOCATE( displace_dum )
685
686#else
687    build_ids = build_ids_l
688#endif
689!
690!-- Note: in parallel mode, building IDs can occur mutliple times, as each PE has send its own ids.
691!-- Therefore, sort out building IDs which appear multiple times.
692    num_build = 0
693    DO  n = 1, SIZE(build_ids)
694
695       IF ( ALLOCATED(build_ids_final) )  THEN
696          IF ( ANY( build_ids(n) == build_ids_final ) )  THEN
697             CYCLE
698          ELSE
699             num_build = num_build + 1
700!
701!--          Resize
702             ALLOCATE( build_ids_final_tmp(1:num_build) )
703             build_ids_final_tmp(1:num_build-1) = build_ids_final(1:num_build-1)
704             DEALLOCATE( build_ids_final )
705             ALLOCATE( build_ids_final(1:num_build) )
706             build_ids_final(1:num_build-1) = build_ids_final_tmp(1:num_build-1)
707             build_ids_final(num_build) = build_ids(n)
708             DEALLOCATE( build_ids_final_tmp )
709          ENDIF
710       ELSE
711          num_build = num_build + 1
712          ALLOCATE( build_ids_final(1:num_build) )
713          build_ids_final(num_build) = build_ids(n)
714       ENDIF
715    ENDDO
716
717!
718!-- Allocate building-data structure array. Note, this is a global array and all building IDs on
719!-- domain are known by each PE. Further attributes, e.g. height-dependent arrays, however, are only
720!-- allocated on PEs where  the respective building is present (in order to reduce memory demands).
721    ALLOCATE( buildings(1:num_build) )
722
723!
724!-- Store building IDs and check if building with certain ID is present on subdomain.
725    DO  nb = 1, num_build
726       buildings(nb)%id = build_ids_final(nb)
727
728       IF ( ANY( building_id_f%var(nys:nyn,nxl:nxr) == buildings(nb)%id ) )                        &
729          buildings(nb)%on_pe = .TRUE.
730    ENDDO
731!
732!-- Determine the maximum vertical dimension occupied by each building.
733    ALLOCATE( k_min_l(1:num_build) )
734    ALLOCATE( k_max_l(1:num_build) )
735    k_min_l = nzt + 1
736    k_max_l = 0
737
738    DO  i = nxl, nxr
739       DO  j = nys, nyn
740          IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
741             nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM=1 )
742             DO  k = nzb, nzt+1
743!
744!--             Check if grid point belongs to a building.
745                IF ( BTEST( wall_flags_total_0(k,j,i), 6 ) )  THEN
746                   k_min_l(nb) = MIN( k_min_l(nb), k )
747                   k_max_l(nb) = MAX( k_max_l(nb), k )
748                ENDIF
749
750             ENDDO
751          ENDIF
752       ENDDO
753    ENDDO
754
755#if defined( __parallel )
756    CALL MPI_ALLREDUCE( k_min_l(:), buildings(:)%kb_min, num_build, MPI_INTEGER, MPI_MIN, comm2d,  &
757                        ierr )
758    CALL MPI_ALLREDUCE( k_max_l(:), buildings(:)%kb_max, num_build, MPI_INTEGER, MPI_MAX, comm2d,  &
759                        ierr )
760#else
761    buildings(:)%kb_min = k_min_l(:)
762    buildings(:)%kb_max = k_max_l(:)
763#endif
764
765    DEALLOCATE( k_min_l )
766    DEALLOCATE( k_max_l )
767!
768!-- Calculate building height.
769    DO  nb = 1, num_build
770       buildings(nb)%building_height = 0.0_wp
771       DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
772          buildings(nb)%building_height = buildings(nb)%building_height + dzw(k+1)
773       ENDDO
774    ENDDO
775!
776!-- Calculate building volume
777    DO  nb = 1, num_build
778!
779!--    Allocate temporary array for summing-up building volume
780       ALLOCATE( volume(buildings(nb)%kb_min:buildings(nb)%kb_max)   )
781       ALLOCATE( volume_l(buildings(nb)%kb_min:buildings(nb)%kb_max) )
782       volume   = 0.0_wp
783       volume_l = 0.0_wp
784!
785!--    Calculate building volume per height level on each PE where these building is present.
786       IF ( buildings(nb)%on_pe )  THEN
787
788          ALLOCATE( buildings(nb)%volume(buildings(nb)%kb_min:buildings(nb)%kb_max)   )
789          ALLOCATE( buildings(nb)%vol_frac(buildings(nb)%kb_min:buildings(nb)%kb_max) )
790          buildings(nb)%volume   = 0.0_wp
791          buildings(nb)%vol_frac = 0.0_wp
792
793          IF ( ANY( building_id_f%var(nys:nyn,nxl:nxr) == buildings(nb)%id ) )  THEN
794             DO  i = nxl, nxr
795                DO  j = nys, nyn
796                   DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
797                      IF ( building_id_f%var(j,i) /= building_id_f%fill )                          &
798                         volume_l(k) = volume_l(k) + dx * dy * dzw(k+1)
799                   ENDDO
800                ENDDO
801             ENDDO
802          ENDIF
803       ENDIF
804!
805!--    Sum-up building volume from all subdomains
806#if defined( __parallel )
807       CALL MPI_ALLREDUCE( volume_l, volume, SIZE(volume), MPI_REAL, MPI_SUM, comm2d, ierr )
808#else
809       volume = volume_l
810#endif
811!
812!--    Save total building volume as well as local fraction on volume on building data structure.
813       IF ( ALLOCATED( buildings(nb)%volume ) )  buildings(nb)%volume = volume
814!
815!--    Determine fraction of local on total building volume
816       IF ( buildings(nb)%on_pe )  buildings(nb)%vol_frac = volume_l / volume
817!
818!--    Calculate total building volume
819       IF ( ALLOCATED( buildings(nb)%volume ) )  buildings(nb)%vol_tot = SUM( buildings(nb)%volume )
820
821       DEALLOCATE( volume   )
822       DEALLOCATE( volume_l )
823
824    ENDDO
825!
826!-- Allocate arrays for indoor temperature.
827    DO  nb = 1, num_build
828       IF ( buildings(nb)%on_pe )  THEN
829          ALLOCATE( buildings(nb)%t_in(buildings(nb)%kb_min:buildings(nb)%kb_max)   )
830          ALLOCATE( buildings(nb)%t_in_l(buildings(nb)%kb_min:buildings(nb)%kb_max) )
831          buildings(nb)%t_in   = 0.0_wp
832          buildings(nb)%t_in_l = 0.0_wp
833       ENDIF
834    ENDDO
835!
836!-- Allocate arrays for number of facades per height level. Distinguish between horizontal and
837!-- vertical facades.
838    DO  nb = 1, num_build
839       IF ( buildings(nb)%on_pe )  THEN
840          ALLOCATE( buildings(nb)%num_facade_h(buildings(nb)%kb_min:buildings(nb)%kb_max) )
841          ALLOCATE( buildings(nb)%num_facade_v(buildings(nb)%kb_min:buildings(nb)%kb_max) )
842
843          buildings(nb)%num_facade_h = 0
844          buildings(nb)%num_facade_v = 0
845       ENDIF
846    ENDDO
847!
848!-- Determine number of facade elements per building on local subdomain.
849!-- Distinguish between horizontal and vertical facade elements.
850!
851!-- Horizontal facades
852    buildings(:)%num_facades_per_building_h_l = 0
853    DO  l = 0, 1
854       DO  m = 1, surf_usm_h(l)%ns
855!
856!--       For the current facade element determine corresponding building index.
857!--       First, obtain j,j,k indices of the building. Please note the offset between facade/surface
858!--       element and building location (for horizontal surface elements the horizontal offsets are
859!--       zero).
860          i = surf_usm_h(l)%i(m) + surf_usm_h(l)%ioff
861          j = surf_usm_h(l)%j(m) + surf_usm_h(l)%joff
862          k = surf_usm_h(l)%k(m) + surf_usm_h(l)%koff
863!
864!--       Determine building index and check whether building is on PE.
865          nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM=1 )
866
867          IF ( buildings(nb)%on_pe )  THEN
868!
869!--          Count number of facade elements at each height level.
870             buildings(nb)%num_facade_h(k) = buildings(nb)%num_facade_h(k) + 1
871!
872!--          Moreover, sum up number of local facade elements per building.
873             buildings(nb)%num_facades_per_building_h_l =                                             &
874                                                      buildings(nb)%num_facades_per_building_h_l + 1
875          ENDIF
876       ENDDO
877    ENDDO
878!
879!-- Vertical facades
880    buildings(:)%num_facades_per_building_v_l = 0
881    DO  l = 0, 3
882       DO  m = 1, surf_usm_v(l)%ns
883!
884!--       For the current facade element determine corresponding building index.
885!--       First, obtain j,j,k indices of the building. Please note the offset between facade/surface
886!--       element and building location (for vertical surface elements the vertical offsets are
887!--       zero).
888          i = surf_usm_v(l)%i(m) + surf_usm_v(l)%ioff
889          j = surf_usm_v(l)%j(m) + surf_usm_v(l)%joff
890          k = surf_usm_v(l)%k(m) + surf_usm_v(l)%koff
891
892          nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM=1 )
893          IF ( buildings(nb)%on_pe )  THEN
894             buildings(nb)%num_facade_v(k) = buildings(nb)%num_facade_v(k) + 1
895             buildings(nb)%num_facades_per_building_v_l =                                          &
896                                                      buildings(nb)%num_facades_per_building_v_l + 1
897          ENDIF
898       ENDDO
899    ENDDO
900!
901!-- Determine total number of facade elements per building and assign number to building data type.
902    DO  nb = 1, num_build
903!
904!--    Allocate dummy array used for summing-up facade elements.
905!--    Please note, dummy arguments are necessary as building-date type arrays are not necessarily
906!--    allocated on all PEs.
907       ALLOCATE( num_facades_h(buildings(nb)%kb_min:buildings(nb)%kb_max) )
908       ALLOCATE( num_facades_v(buildings(nb)%kb_min:buildings(nb)%kb_max) )
909       ALLOCATE( receive_dum_h(buildings(nb)%kb_min:buildings(nb)%kb_max) )
910       ALLOCATE( receive_dum_v(buildings(nb)%kb_min:buildings(nb)%kb_max) )
911       num_facades_h = 0
912       num_facades_v = 0
913       receive_dum_h = 0
914       receive_dum_v = 0
915
916       IF ( buildings(nb)%on_pe )  THEN
917          num_facades_h = buildings(nb)%num_facade_h
918          num_facades_v = buildings(nb)%num_facade_v
919       ENDIF
920
921#if defined( __parallel )
922       CALL MPI_ALLREDUCE( num_facades_h,                                                          &
923                           receive_dum_h,                                                          &
924                           buildings(nb)%kb_max - buildings(nb)%kb_min + 1,                        &
925                           MPI_INTEGER,                                                            &
926                           MPI_SUM,                                                                &
927                           comm2d,                                                                 &
928                           ierr )
929
930       CALL MPI_ALLREDUCE( num_facades_v,                                                          &
931                           receive_dum_v,                                                          &
932                           buildings(nb)%kb_max - buildings(nb)%kb_min + 1,                        &
933                           MPI_INTEGER,                                                            &
934                           MPI_SUM,                                                                &
935                           comm2d,                                                                 &
936                           ierr )
937       IF ( ALLOCATED( buildings(nb)%num_facade_h ) )  buildings(nb)%num_facade_h = receive_dum_h
938       IF ( ALLOCATED( buildings(nb)%num_facade_v ) )  buildings(nb)%num_facade_v = receive_dum_v
939#else
940       buildings(nb)%num_facade_h = num_facades_h
941       buildings(nb)%num_facade_v = num_facades_v
942#endif
943
944!
945!--    Deallocate dummy arrays
946       DEALLOCATE( num_facades_h )
947       DEALLOCATE( num_facades_v )
948       DEALLOCATE( receive_dum_h )
949       DEALLOCATE( receive_dum_v )
950!
951!--    Allocate index arrays which link facade elements with surface-data type.
952!--    Please note, no height levels are considered here (information is stored in surface-data type
953!--    itself).
954       IF ( buildings(nb)%on_pe )  THEN
955!
956!--       Determine number of facade elements per building.
957          buildings(nb)%num_facades_per_building_h = SUM( buildings(nb)%num_facade_h )
958          buildings(nb)%num_facades_per_building_v = SUM( buildings(nb)%num_facade_v )
959!
960!--       Allocate arrays which link the building with the horizontal and vertical urban-type
961!--       surfaces. Please note, linking arrays are allocated over all facade elements, which is
962!--       required in case a building is located at the subdomain boundaries, where the building and
963!--       the corresponding surface elements are located on different subdomains.
964          ALLOCATE( buildings(nb)%l_h(1:buildings(nb)%num_facades_per_building_h_l) )
965          ALLOCATE( buildings(nb)%m_h(1:buildings(nb)%num_facades_per_building_h_l) )
966
967          ALLOCATE( buildings(nb)%l_v(1:buildings(nb)%num_facades_per_building_v_l) )
968          ALLOCATE( buildings(nb)%m_v(1:buildings(nb)%num_facades_per_building_v_l) )
969
970          ALLOCATE( buildings(nb)%theta_m_t_prev_h(1:buildings(nb)%num_facades_per_building_h_l) )
971          ALLOCATE( buildings(nb)%theta_m_t_prev_v(1:buildings(nb)%num_facades_per_building_v_l) )
972       ENDIF
973
974       IF ( buildings(nb)%on_pe )  THEN
975          ALLOCATE( buildings(nb)%vpf(buildings(nb)%kb_min:buildings(nb)%kb_max) )
976          buildings(nb)%vpf = 0.0_wp
977
978          facade_area_v = 0.0_wp
979          DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
980             facade_area_v = facade_area_v + buildings(nb)%num_facade_v(k) * dzw(k+1) * dx
981          ENDDO
982!
983!--       Determine volume per total facade area (vpf). For the horizontal facade area
984!--       num_facades_per_building_h can be taken, multiplied with dx*dy.
985!--       However, due to grid stretching, vertical facade elements must be summed-up vertically.
986!--       Please note, if dx /= dy, an error is made!
987          buildings(nb)%vpf = buildings(nb)%vol_tot /                                              &
988                              ( buildings(nb)%num_facades_per_building_h * dx * dy + facade_area_v )
989!
990!--       Determine floor-area-per-facade.
991          buildings(nb)%fapf = buildings(nb)%num_facades_per_building_h     * dx * dy              &
992                               / ( buildings(nb)%num_facades_per_building_h * dx * dy              &
993                                   + facade_area_v )
994       ENDIF
995    ENDDO
996!
997!-- Link facade elements with surface data type.
998!-- Allocate array for counting.
999    ALLOCATE( n_fa(1:num_build) )
1000    n_fa = 1
1001
1002    DO  l = 0, 1
1003       DO  m = 1, surf_usm_h(l)%ns
1004          i = surf_usm_h(l)%i(m) + surf_usm_h(l)%ioff
1005          j = surf_usm_h(l)%j(m) + surf_usm_h(l)%joff
1006
1007          nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM=1 )
1008
1009          IF ( buildings(nb)%on_pe )  THEN
1010             buildings(nb)%l_h(n_fa(nb)) = l
1011             buildings(nb)%m_h(n_fa(nb)) = m
1012             n_fa(nb) = n_fa(nb) + 1
1013          ENDIF
1014       ENDDO
1015    ENDDO
1016
1017    n_fa = 1
1018    DO  l = 0, 3
1019       DO  m = 1, surf_usm_v(l)%ns
1020          i = surf_usm_v(l)%i(m) + surf_usm_v(l)%ioff
1021          j = surf_usm_v(l)%j(m) + surf_usm_v(l)%joff
1022
1023          nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM=1 )
1024
1025          IF ( buildings(nb)%on_pe )  THEN
1026             buildings(nb)%l_v(n_fa(nb)) = l
1027             buildings(nb)%m_v(n_fa(nb)) = m
1028             n_fa(nb) = n_fa(nb) + 1
1029          ENDIF
1030       ENDDO
1031    ENDDO
1032    DEALLOCATE( n_fa )
1033!
1034!-- Initialize building parameters, first by mean building type. Note, in this case all buildings
1035!-- have the same type.
1036!-- In a second step initialize with building tpyes from static input file, where building types can
1037!-- be individual for each building.
1038    buildings(:)%lambda_layer3       = building_pars(31,building_type)
1039    buildings(:)%s_layer3            = building_pars(44,building_type)
1040    buildings(:)%f_c_win             = building_pars(119,building_type)
1041    buildings(:)%g_value_win         = building_pars(120,building_type)
1042    buildings(:)%u_value_win         = building_pars(121,building_type)
1043    buildings(:)%eta_ve              = building_pars(124,building_type)
1044    buildings(:)%factor_a            = building_pars(125,building_type)
1045    buildings(:)%factor_c            = building_pars(126,building_type)
1046    buildings(:)%lambda_at           = building_pars(127,building_type)
1047    buildings(:)%theta_int_h_set     = building_pars(13,building_type)
1048    buildings(:)%theta_int_c_set     = building_pars(12,building_type)
1049    buildings(:)%q_h_max             = building_pars(128,building_type)
1050    buildings(:)%q_c_max             = building_pars(129,building_type)
1051    buildings(:)%qint_high           = building_pars(130,building_type)
1052    buildings(:)%qint_low            = building_pars(131,building_type)
1053    buildings(:)%height_storey       = building_pars(132,building_type)
1054    buildings(:)%height_cei_con      = building_pars(133,building_type)
1055    buildings(:)%params_waste_heat_h = building_pars(134,building_type)
1056    buildings(:)%params_waste_heat_c = building_pars(135,building_type)
1057!
1058!-- Initialize seasonal dependent parameters, depending on day of the year.
1059!-- First, calculated day of the year.
1060    CALL get_date_time( time_since_reference_point, day_of_year = day_of_year )
1061!
1062!-- Summer is defined in between northward- and southward equinox.
1063    IF ( day_of_year >= northward_equinox  .AND.  day_of_year <= southward_equinox )  THEN
1064       buildings(:)%air_change_low      = summer_pars(0,building_type)
1065       buildings(:)%air_change_high     = summer_pars(1,building_type)
1066    ELSE
1067       buildings(:)%air_change_low      = winter_pars(0,building_type)
1068       buildings(:)%air_change_high     = winter_pars(1,building_type)
1069    ENDIF
1070!
1071!-- Initialize ventilation load. Please note, building types > 7 are actually not allowed (check
1072!-- already in urban_surface_mod and netcdf_data_input_mod.
1073!-- However, the building data base may be later extended.
1074    IF ( building_type ==  1  .OR.  building_type ==  2  .OR.                                      &
1075         building_type ==  3  .OR.  building_type == 10  .OR.                                      &
1076         building_type == 11  .OR.  building_type == 12 )  THEN
1077       buildings(:)%ventilation_int_loads = 1
1078!
1079!-- Office, building with large windows
1080    ELSEIF ( building_type ==  4  .OR.  building_type ==  5  .OR.                                  &
1081             building_type ==  6  .OR.  building_type ==  7  .OR.                                  &
1082             building_type ==  8  .OR.  building_type ==  9)  THEN
1083       buildings(:)%ventilation_int_loads = 2
1084!
1085!-- Industry, hospitals
1086    ELSEIF ( building_type == 13  .OR.  building_type == 14  .OR.                                  &
1087             building_type == 15  .OR.  building_type == 16  .OR.                                  &
1088             building_type == 17  .OR.  building_type == 18 )  THEN
1089       buildings(:)%ventilation_int_loads = 3
1090    ENDIF
1091!
1092!-- Initialization of building parameters - level 2
1093    IF ( building_type_f%from_file )  THEN
1094       DO  i = nxl, nxr
1095          DO  j = nys, nyn
1096              IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
1097                 nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM=1 )
1098                 bt = building_type_f%var(j,i)
1099
1100                 buildings(nb)%lambda_layer3       = building_pars(31,bt)
1101                 buildings(nb)%s_layer3            = building_pars(44,bt)
1102                 buildings(nb)%f_c_win             = building_pars(119,bt)
1103                 buildings(nb)%g_value_win         = building_pars(120,bt)
1104                 buildings(nb)%u_value_win         = building_pars(121,bt)
1105                 buildings(nb)%eta_ve              = building_pars(124,bt)
1106                 buildings(nb)%factor_a            = building_pars(125,bt)
1107                 buildings(nb)%factor_c            = building_pars(126,bt)
1108                 buildings(nb)%lambda_at           = building_pars(127,bt)
1109                 buildings(nb)%theta_int_h_set     = building_pars(13,bt)
1110                 buildings(nb)%theta_int_c_set     = building_pars(12,bt)
1111                 buildings(nb)%q_h_max             = building_pars(128,bt)
1112                 buildings(nb)%q_c_max             = building_pars(129,bt)
1113                 buildings(nb)%qint_high           = building_pars(130,bt)
1114                 buildings(nb)%qint_low            = building_pars(131,bt)
1115                 buildings(nb)%height_storey       = building_pars(132,bt)
1116                 buildings(nb)%height_cei_con      = building_pars(133,bt)
1117                 buildings(nb)%params_waste_heat_h = building_pars(134,bt)
1118                 buildings(nb)%params_waste_heat_c = building_pars(135,bt)
1119
1120              IF ( day_of_year >= northward_equinox  .AND.  day_of_year <= southward_equinox )  THEN
1121                 buildings(nb)%air_change_low      = summer_pars(0,bt)
1122                 buildings(nb)%air_change_high     = summer_pars(1,bt)
1123              ELSE
1124                 buildings(nb)%air_change_low      = winter_pars(0,bt)
1125                 buildings(nb)%air_change_high     = winter_pars(1,bt)
1126              ENDIF
1127
1128!
1129!--              Initialize ventilaation load. Please note, building types > 7
1130!--              are actually not allowed (check already in urban_surface_mod
1131!--              and netcdf_data_input_mod. However, the building data base may
1132!--              be later extended.
1133                 IF ( bt ==  1  .OR.  bt ==  2  .OR.                                               &
1134                      bt ==  3  .OR.  bt == 10  .OR.                                               &
1135                      bt == 11  .OR.  bt == 12 )  THEN
1136                    buildings(nb)%ventilation_int_loads = 1
1137!
1138!--              Office, building with large windows
1139                 ELSEIF ( bt ==  4  .OR.  bt ==  5  .OR.                                           &
1140                          bt ==  6  .OR.  bt ==  7  .OR.                                           &
1141                          bt ==  8  .OR.  bt ==  9)  THEN
1142                    buildings(nb)%ventilation_int_loads = 2
1143!
1144!--              Industry, hospitals
1145                 ELSEIF ( bt == 13  .OR.  bt == 14  .OR.                                           &
1146                          bt == 15  .OR.  bt == 16  .OR.                                           &
1147                          bt == 17  .OR.  bt == 18 )  THEN
1148                    buildings(nb)%ventilation_int_loads = 3
1149                 ENDIF
1150              ENDIF
1151           ENDDO
1152        ENDDO
1153    ENDIF
1154!
1155!-- Calculation of surface-related heat transfer coeffiecient out of standard u-values from building
1156!-- database.
1157!-- Only amount of extern and surface is used.
1158!-- Otherwise amount between air and surface taken account twice.
1159    DO nb = 1, num_build
1160       IF ( buildings(nb)%on_pe ) THEN
1161          du_win_tmp = 1.0_wp / buildings(nb)%u_value_win
1162          u_tmp = buildings(nb)%u_value_win * ( du_win_tmp / ( du_win_tmp -                        &
1163                  0.125_wp + ( 1.0_wp / h_is ) ) )
1164
1165          du_tmp = 1.0_wp / u_tmp
1166
1167          buildings(nb)%h_es = 1.0_wp / ( du_tmp - ( 1.0_wp / h_is ) )
1168
1169       ENDIF
1170    ENDDO
1171!
1172!-- Initialize indoor temperature. Actually only for output at initial state.
1173    DO  nb = 1, num_build
1174       IF ( buildings(nb)%on_pe )  THEN
1175          buildings(nb)%t_in(:) = initial_indoor_temperature
1176
1177!
1178!--       (after first loop, use theta_m_t as theta_m_t_prev)
1179          buildings(nb)%theta_m_t_prev_h(:) = initial_indoor_temperature
1180          buildings(nb)%theta_m_t_prev_v(:) = initial_indoor_temperature
1181
1182       ENDIF
1183    ENDDO
1184
1185    CALL location_message( 'initializing indoor model', 'finished' )
1186
1187 END SUBROUTINE im_init
1188
1189
1190!--------------------------------------------------------------------------------------------------!
1191! Description:
1192! ------------
1193!> Main part of the indoor model.
1194!> Calculation of .... (kanani: Please describe)
1195!--------------------------------------------------------------------------------------------------!
1196 SUBROUTINE im_main_heatcool
1197
1198!     USE basic_constants_and_equations_mod,                                     &
1199!         ONLY:  c_p
1200
1201    USE control_parameters,                                                                        &
1202        ONLY:  time_since_reference_point
1203
1204    USE grid_variables,                                                                            &
1205        ONLY:  dx, dy
1206
1207    USE pegrid
1208
1209    USE surface_mod,                                                                               &
1210        ONLY:  ind_pav_green,                                                                      &
1211               ind_veg_wall,                                                                       &
1212               ind_wat_win,                                                                        &
1213               surf_usm_h,                                                                         &
1214               surf_usm_v
1215
1216    USE urban_surface_mod,                                                                         &
1217        ONLY:  building_type,                                                                      &
1218               nzt_wall,                                                                           &
1219               t_green_h,                                                                          &
1220               t_green_v,                                                                          &
1221               t_wall_h,                                                                           &
1222               t_wall_v,                                                                           &
1223               t_window_h,                                                                         &
1224               t_window_v
1225
1226
1227    INTEGER(iwp) ::  fa   !< running index for facade elements of each building
1228    INTEGER(iwp) ::  i    !< index of facade-adjacent atmosphere grid point in x-direction
1229    INTEGER(iwp) ::  j    !< index of facade-adjacent atmosphere grid point in y-direction
1230    INTEGER(iwp) ::  k    !< index of facade-adjacent atmosphere grid point in z-direction
1231    INTEGER(iwp) ::  kk   !< vertical index of indoor grid point adjacent to facade
1232    INTEGER(iwp) ::  l    !< running index for surface-element orientation
1233    INTEGER(iwp) ::  m    !< running index surface elements
1234    INTEGER(iwp) ::  nb   !< running index for buildings
1235
1236    LOGICAL  ::  during_spinup                    !< flag indicating that the simulation is still in wall/soil spinup
1237
1238    REAL(wp) ::  frac_green                       !< dummy for green fraction
1239    REAL(wp) ::  frac_wall                        !< dummy for wall fraction
1240    REAL(wp) ::  frac_win                         !< dummy for window fraction
1241!     REAL(wp) ::  indoor_wall_window_temperature   !< weighted temperature of innermost wall/window layer
1242    REAL(wp) ::  indoor_wall_temperature          !< temperature of innermost wall layer evtl in im_calc_temperatures einfÃŒgen
1243    REAL(wp) ::  near_facade_temperature          !< outside air temperature 10cm away from facade
1244    REAL(wp) ::  second_of_day                    !< second of the current day
1245    REAL(wp) ::  time_utc_hour                    !< time of day (hour UTC)
1246
1247    REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in_l_send   !< dummy send buffer used for summing-up indoor temperature per kk-level
1248    REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in_recv     !< dummy recv buffer used for summing-up indoor temperature per kk-level
1249!
1250!-- Determine time of day in hours.
1251    CALL get_date_time( time_since_reference_point, second_of_day=second_of_day )
1252    time_utc_hour = second_of_day / seconds_per_hour
1253!
1254!-- Check if the simulation is still in wall/soil spinup mode
1255    during_spinup = MERGE( .TRUE., .FALSE., time_since_reference_point < 0.0_wp )
1256!
1257!-- Following calculations must be done for each facade element.
1258    DO  nb = 1, num_build
1259!
1260!--    First, check whether building is present on local subdomain.
1261       IF ( buildings(nb)%on_pe )  THEN
1262!
1263!--       Determine daily schedule. 08:00-18:00 = 1, other hours = 0.
1264!--       Residental Building, panel WBS 70
1265          IF ( buildings(nb)%ventilation_int_loads == 1 )  THEN
1266             IF ( time_utc_hour >= 8.0_wp  .AND.  time_utc_hour <= 18.0_wp )  THEN
1267                schedule_d = 0
1268             ELSE
1269                schedule_d = 1
1270             ENDIF
1271          ENDIF
1272!
1273!--       Office, building with large windows
1274          IF ( buildings(nb)%ventilation_int_loads == 2 )  THEN
1275             IF ( time_utc_hour >= 8.0_wp  .AND.  time_utc_hour <= 18.0_wp )  THEN
1276                schedule_d = 1
1277             ELSE
1278                schedule_d = 0
1279             ENDIF
1280          ENDIF
1281!
1282!--       Industry, hospitals
1283          IF ( buildings(nb)%ventilation_int_loads == 3 )  THEN
1284             IF ( time_utc_hour >= 6.0_wp  .AND.  time_utc_hour <= 22.0_wp )  THEN
1285                schedule_d = 1
1286             ELSE
1287                schedule_d = 0
1288             ENDIF
1289          ENDIF
1290!
1291!--       Initialize/reset indoor temperature
1292          buildings(nb)%t_in_l = 0.0_wp
1293!
1294!--       Horizontal surfaces
1295          DO  fa = 1, buildings(nb)%num_facades_per_building_h_l
1296!
1297!--          Determine indices where corresponding surface-type information is stored.
1298             l = buildings(nb)%l_h(fa)
1299             m = buildings(nb)%m_h(fa)
1300!
1301!--          During spinup set window fraction to zero and add these to wall fraction.
1302             frac_win   = MERGE( surf_usm_h(l)%frac(m,ind_wat_win), 0.0_wp, .NOT. during_spinup )
1303             frac_wall  = MERGE( surf_usm_h(l)%frac(m,ind_veg_wall),                               &
1304                                 surf_usm_h(l)%frac(m,ind_veg_wall) +                              &
1305                                 surf_usm_h(l)%frac(m,ind_wat_win),                                &
1306                                 .NOT. during_spinup )
1307             frac_green = surf_usm_h(l)%frac(m,ind_pav_green)
1308!
1309!--          Determine building height level index.
1310             kk = surf_usm_h(l)%k(m) + surf_usm_h(l)%koff
1311!
1312!--          Building geometries --> not time-dependent
1313             facade_element_area          = dx * dy                               !< [m2] surface area per facade element
1314             floor_area_per_facade        = buildings(nb)%fapf                    !< [m2/m2] floor area per facade area
1315             indoor_volume_per_facade     = buildings(nb)%vpf(kk)                 !< [m3/m2] indoor air volume per facade area
1316             buildings(nb)%area_facade    = facade_element_area *                                  &
1317                                            ( buildings(nb)%num_facades_per_building_h +           &
1318                                              buildings(nb)%num_facades_per_building_v ) !< [m2] area of total facade
1319             window_area_per_facade       = frac_win  * facade_element_area              !< [m2] window area per facade element
1320
1321             buildings(nb)%net_floor_area = buildings(nb)%vol_tot / ( buildings(nb)%height_storey )
1322             total_area                   = buildings(nb)%net_floor_area                            !< [m2] area of all surfaces
1323                                                                                                    !< pointing to zone  Eq. (9) according to section 7.2.2.2
1324             a_m                          = buildings(nb)%factor_a * total_area *                  &
1325                                            ( facade_element_area / buildings(nb)%area_facade ) *  &
1326                                            buildings(nb)%lambda_at                                 !< [m2] standard values
1327                                                                                                    !< according to Table 12 section 12.3.1.2  (calculate over Eq. (65) according to section 12.3.1.2)
1328             c_m                          = buildings(nb)%factor_c * total_area *                  &
1329                                            ( facade_element_area / buildings(nb)%area_facade )     !< [J/K] standard values
1330                                                                                                    !< according to table 12 section 12.3.1.2 (calculate over Eq. (66) according to section 12.3.1.2)
1331!
1332!--          Calculation of heat transfer coefficient for transmission --> not time-dependent
1333             h_t_es   = window_area_per_facade * buildings(nb)%h_es                                   !< [W/K] only for windows
1334
1335             h_t_is  = buildings(nb)%area_facade * h_is                                               !< [W/K] with h_is = 3.45 W /
1336                                                                                                      !< (m2 K) between surface and air, Eq. (9)
1337             h_t_ms  = a_m * h_ms                                                                     !< [W/K] with h_ms = 9.10 W /
1338                                                                                                      !< (m2 K) between component and surface, Eq. (64)
1339             h_t_wall  = 1.0_wp / ( 1.0_wp / ( ( facade_element_area - window_area_per_facade )    &  !< [W/K]
1340                                    * buildings(nb)%lambda_layer3 / buildings(nb)%s_layer3 * 0.5_wp &
1341                                             ) + 1.0_wp / h_t_ms )                                    !< [W/K] opaque components
1342             h_t_wm  = 1.0_wp / ( 1.0_wp / h_t_wall - 1.0_wp / h_t_ms )                               !< [W/K] emmision Eq. (63),
1343                                                                                                      !< Section 12.2.2
1344!
1345!--          Internal air loads dependent on the occupacy of the room.
1346!--          Basical internal heat gains (qint_low) with additional internal heat gains by occupancy (qint_high) (0,5*phi_int).
1347             phi_ia = 0.5_wp * ( ( buildings(nb)%qint_high * schedule_d + buildings(nb)%qint_low ) &
1348                              * floor_area_per_facade )
1349             q_int = phi_ia / total_area
1350!
1351!--          Airflow dependent on the occupacy of the room.
1352!--          Basical airflow (air_change_low) with additional airflow gains by occupancy (air_change_high)
1353             air_change = ( buildings(nb)%air_change_high * schedule_d + buildings(nb)%air_change_low )  !< [1/h]?
1354!
1355!--          Heat transfer of ventilation.
1356!--          Not less than 0.01 W/K to avoid division by 0 in further calculations with heat
1357!--          capacity of air 0.33 Wh/m2K.
1358             h_v   = MAX( 0.01_wp , ( air_change * indoor_volume_per_facade *                      &
1359                                      0.33_wp * (1.0_wp - buildings(nb)%eta_ve ) ) )    !< [W/K] from ISO 13789 Eq.(10)
1360
1361!--          Heat transfer coefficient auxiliary variables
1362             h_t_1 = 1.0_wp / ( ( 1.0_wp / h_v )   + ( 1.0_wp / h_t_is ) )  !< [W/K] Eq. (C.6)
1363             h_t_2 = h_t_1 + h_t_es                                         !< [W/K] Eq. (C.7)
1364             h_t_3 = 1.0_wp / ( ( 1.0_wp / h_t_2 ) + ( 1.0_wp / h_t_ms ) )  !< [W/K] Eq. (C.8)
1365!
1366!--          Net short-wave radiation through window area (was i_global)
1367             net_sw_in = surf_usm_h(l)%rad_sw_in(m) - surf_usm_h(l)%rad_sw_out(m)
1368!
1369!--          Quantities needed for im_calc_temperatures
1370             i = surf_usm_h(l)%i(m)
1371             j = surf_usm_h(l)%j(m)
1372             k = surf_usm_h(l)%k(m)
1373             near_facade_temperature = surf_usm_h(l)%pt_10cm(m)
1374!              indoor_wall_window_temperature = frac_wall  * t_wall_h(l)%val(nzt_wall,m)             &
1375!                                             + frac_win   * t_window_h(l)%val(nzt_wall,m)           &
1376!                                             + frac_green * t_green_h(l)%val(nzt_wall,m)
1377             indoor_wall_temperature = frac_wall  * t_wall_h(l)%val(nzt_wall,m)                    &
1378                                     + frac_win   * t_window_h(l)%val(nzt_wall,m)                  &
1379                                     + frac_green * t_green_h(l)%val(nzt_wall,m)
1380!
1381!--          Solar thermal gains. If net_sw_in larger than sun-protection threshold parameter
1382!--          (params_solar_protection), sun protection will be activated.
1383             IF ( net_sw_in <= params_solar_protection )  THEN
1384                solar_protection_off = 1
1385                solar_protection_on  = 0
1386             ELSE
1387                solar_protection_off = 0
1388                solar_protection_on  = 1
1389             ENDIF
1390!
1391!--          Calculation of total heat gains from net_sw_in through windows [W] in respect on
1392!--          automatic sun protection.
1393!--          DIN 4108 - 2 chap.8
1394             phi_sol = (   window_area_per_facade * net_sw_in * solar_protection_off               &
1395                         + window_area_per_facade * net_sw_in * buildings(nb)%f_c_win *            &
1396                           solar_protection_on )                                                   &
1397                       * buildings(nb)%g_value_win * ( 1.0_wp - params_f_f ) * params_f_w
1398             q_sol = phi_sol
1399!
1400!--          Calculation of the mass specific thermal load for internal and external heatsources of
1401!--          the inner node.
1402             phi_m   = (a_m / total_area) * ( phi_ia + phi_sol )                                    !< [W] Eq. (C.2) with
1403                                                                                                    !< phi_ia=0,5*phi_int
1404             q_c_m = phi_m
1405!
1406!--          Calculation mass specific thermal load implied non thermal mass
1407             phi_st  =   ( 1.0_wp - ( a_m / total_area ) - ( h_t_es / ( 9.1_wp * total_area ) ) )  &
1408                       * ( phi_ia + phi_sol )                                                       !< [W] Eq. (C.3) with
1409                                                                                                    !< phi_ia=0,5*phi_int
1410             q_c_st = phi_st
1411!
1412!--          Calculations for deriving indoor temperature and heat flux into the wall
1413!--          Step 1: indoor temperature without heating and cooling
1414!--          section C.4.1 Picture C.2 zone 3)
1415             phi_hc_nd = 0.0_wp
1416
1417             CALL  im_calc_temperatures ( i, j, k, indoor_wall_temperature, &
1418                                          near_facade_temperature, phi_hc_nd, buildings(nb)%theta_m_t_prev_h(fa) )
1419!
1420!--          If air temperature between border temperatures of heating and cooling, assign output
1421!--          variable, then ready.
1422             IF ( buildings(nb)%theta_int_h_set <= theta_air  .AND.                                &
1423                  theta_air <= buildings(nb)%theta_int_c_set )  THEN
1424                phi_hc_nd_ac = 0.0_wp
1425                phi_hc_nd    = phi_hc_nd_ac
1426                theta_air_ac = theta_air
1427!
1428!--          Step 2: Else, apply 10 W/m2 heating/cooling power and calculate indoor temperature
1429!--          again.
1430             ELSE
1431!
1432!--             Temperature not correct, calculation method according to section C4.2
1433                theta_air_0 = theta_air                                                  !< temperature without heating/cooling
1434!
1435!--             Heating or cooling?
1436                IF ( theta_air_0 > buildings(nb)%theta_int_c_set )  THEN
1437                   theta_air_set = buildings(nb)%theta_int_c_set
1438                ELSE
1439                   theta_air_set = buildings(nb)%theta_int_h_set
1440                ENDIF
1441!
1442!--             Calculate the temperature with phi_hc_nd_10
1443                phi_hc_nd_10 = 10.0_wp * floor_area_per_facade
1444                phi_hc_nd    = phi_hc_nd_10
1445
1446                CALL  im_calc_temperatures ( i, j, k, indoor_wall_temperature, &
1447                                             near_facade_temperature, phi_hc_nd, buildings(nb)%theta_m_t_prev_h(fa) )
1448                theta_air_10 = theta_air                                                !< temperature with 10 W/m2 of heating
1449!
1450!--             Avoid division by zero at first timestep where the denominator can become zero.
1451                IF ( ABS( theta_air_10  - theta_air_0 ) < 1E-10_wp )  THEN
1452                   phi_hc_nd_un = phi_hc_nd_10
1453                ELSE
1454                   phi_hc_nd_un = phi_hc_nd_10 * ( theta_air_set - theta_air_0 )                   &
1455                                               / ( theta_air_10  - theta_air_0 )             !< Eq. (C.13)
1456                ENDIF
1457!
1458!--             Step 3: with temperature ratio to determine the heating or cooling capacity.
1459!--             If necessary, limit the power to maximum power.
1460!--             section C.4.1 Picture C.2 zone 2) and 4)
1461                buildings(nb)%phi_c_max = buildings(nb)%q_c_max * floor_area_per_facade
1462                buildings(nb)%phi_h_max = buildings(nb)%q_h_max * floor_area_per_facade
1463                IF ( buildings(nb)%phi_c_max < phi_hc_nd_un  .AND.                                 &
1464                     phi_hc_nd_un < buildings(nb)%phi_h_max )  THEN
1465                   phi_hc_nd_ac = phi_hc_nd_un
1466                   phi_hc_nd = phi_hc_nd_un
1467                ELSE
1468!
1469!--             Step 4: inner temperature with maximum heating (phi_hc_nd_un positive) or cooling
1470!--                     (phi_hc_nd_un negative)
1471!--             section C.4.1 Picture C.2 zone 1) and 5)
1472                   IF ( phi_hc_nd_un > 0.0_wp )  THEN
1473                      phi_hc_nd_ac = buildings(nb)%phi_h_max                            !< Limit heating
1474                   ELSE
1475                      phi_hc_nd_ac = buildings(nb)%phi_c_max                            !< Limit cooling
1476                   ENDIF
1477                ENDIF
1478                phi_hc_nd = phi_hc_nd_ac
1479!
1480!--             Calculate the temperature with phi_hc_nd_ac (new)
1481                CALL  im_calc_temperatures ( i, j, k, indoor_wall_temperature, &
1482                                             near_facade_temperature, phi_hc_nd, buildings(nb)%theta_m_t_prev_h(fa) )
1483                theta_air_ac = theta_air
1484             ENDIF
1485!
1486!--          Update theta_m_t_prev
1487             buildings(nb)%theta_m_t_prev_h(fa) = theta_m_t
1488
1489
1490             q_vent = h_v * ( theta_air - near_facade_temperature )
1491!
1492!--          Calculate the operating temperature with weighted mean temperature of air and mean
1493!--          solar temperature.
1494!--          Will be used for thermal comfort calculations.
1495             theta_op     = 0.3_wp * theta_air_ac + 0.7_wp * theta_s          !< [degree_C] operative Temperature Eq. (C.12)
1496
1497!              surf_usm_h(l)%t_indoor(m) = theta_op                               !< not integrated now
1498!
1499!--          Heat flux into the wall. Value needed in urban_surface_mod to
1500!--          calculate heat transfer through wall layers towards the facade
1501!--          (use c_p * rho_surface to convert [W/m2] into [K m/s])
1502             IF ( (facade_element_area - window_area_per_facade) > 0.0_wp )  THEN
1503                q_wall = h_t_wm * ( indoor_wall_temperature - theta_m )                 &
1504                                    / ( facade_element_area - window_area_per_facade )
1505             ELSE
1506                q_wall = 0.0_wp
1507             ENDIF
1508
1509             IF ( window_area_per_facade > 0.0_wp )  THEN
1510                q_win = h_t_es * ( pt(k,j,i) - theta_s ) / ( window_area_per_facade )
1511             ELSE
1512                q_win = 0.0_wp
1513             ENDIF
1514!
1515!--          Transfer q_wall & q_win back to USM (innermost wall/window layer)
1516             surf_usm_h(l)%iwghf_eb(m)        = - q_wall
1517             surf_usm_h(l)%iwghf_eb_window(m) = - q_win
1518!
1519!--          Sum up operational indoor temperature per kk-level. Further below, this temperature is
1520!--          reduced by MPI to one temperature per kk-level and building (processor overlapping).
1521             buildings(nb)%t_in_l(kk) = buildings(nb)%t_in_l(kk) + theta_op
1522!
1523!--          Calculation of waste heat.
1524!--          Anthropogenic heat output.
1525             IF ( phi_hc_nd_ac > 0.0_wp )  THEN
1526                heating_on = 1
1527                cooling_on = 0
1528             ELSE
1529                heating_on = 0
1530                cooling_on = -1
1531             ENDIF
1532
1533             q_waste_heat = ( phi_hc_nd * (                                                        &
1534                              buildings(nb)%params_waste_heat_h * heating_on +                     &
1535                              buildings(nb)%params_waste_heat_c * cooling_on )                     &
1536                            ) / facade_element_area                                             !< [W/m2] , observe the directional
1537                                                                                                !< convention in PALM!
1538             surf_usm_h(l)%waste_heat(m) = q_waste_heat
1539          ENDDO !< Horizontal surfaces loop
1540!
1541!--       Vertical surfaces
1542          DO  fa = 1, buildings(nb)%num_facades_per_building_v_l
1543!
1544!--          Determine indices where corresponding surface-type information is stored.
1545             l = buildings(nb)%l_v(fa)
1546             m = buildings(nb)%m_v(fa)
1547!
1548!--          During spinup set window fraction to zero and add these to wall fraction.
1549             frac_win   = MERGE( surf_usm_v(l)%frac(m,ind_wat_win), 0.0_wp, .NOT. during_spinup )
1550             frac_wall  = MERGE( surf_usm_v(l)%frac(m,ind_veg_wall),                               &
1551                                 surf_usm_v(l)%frac(m,ind_veg_wall) +                              &
1552                                 surf_usm_v(l)%frac(m,ind_wat_win),                                &
1553                                 .NOT. during_spinup )
1554             frac_green = surf_usm_v(l)%frac(m,ind_pav_green)
1555!
1556!--          Determine building height level index.
1557             kk = surf_usm_v(l)%k(m) + surf_usm_v(l)%koff
1558!
1559!--          (SOME OF THE FOLLOWING (not time-dependent) COULD PROBABLY GO INTO A FUNCTION
1560!--          EXCEPT facade_element_area, EVERYTHING IS CALCULATED EQUALLY)
1561!--          Building geometries  --> not time-dependent
1562             IF ( l == 0  .OR. l == 1 ) facade_element_area = dx * dzw(kk+1)    !< [m2] surface area per facade element
1563             IF ( l == 2  .OR. l == 3 ) facade_element_area = dy * dzw(kk+1)    !< [m2] surface area per facade element
1564
1565             floor_area_per_facade        = buildings(nb)%fapf                  !< [m2/m2] floor area per facade area
1566             indoor_volume_per_facade     = buildings(nb)%vpf(kk)               !< [m3/m2] indoor air volume per facade area
1567             buildings(nb)%area_facade    = facade_element_area *                                  &
1568                                            ( buildings(nb)%num_facades_per_building_h +           &
1569                                              buildings(nb)%num_facades_per_building_v )  !< [m2] area of total facade
1570             window_area_per_facade       = frac_win * facade_element_area                !< [m2] window area per facade element
1571
1572             buildings(nb)%net_floor_area = buildings(nb)%vol_tot / ( buildings(nb)%height_storey )
1573             total_area                   = buildings(nb)%net_floor_area                              !< [m2] area of all surfaces
1574                                                                                                      !< pointing to zone  Eq. (9) according to section 7.2.2.2
1575             a_m                          = buildings(nb)%factor_a * total_area *                  &
1576                                            ( facade_element_area / buildings(nb)%area_facade ) *  &
1577                                              buildings(nb)%lambda_at                                 !< [m2] standard values
1578                                                                                                      !< according to Table 12 section 12.3.1.2  (calculate over Eq. (65) according to section 12.3.1.2)
1579             c_m                          = buildings(nb)%factor_c * total_area *                   &
1580                                            ( facade_element_area / buildings(nb)%area_facade )       !< [J/K] standard values
1581                                                                                                      !< according to table 12 section 12.3.1.2 (calculate over Eq. (66) according to section 12.3.1.2)
1582!
1583!--          Calculation of heat transfer coefficient for transmission --> not time-dependent
1584             h_t_es   = window_area_per_facade * buildings(nb)%h_es                                   !< [W/K] only for windows
1585
1586             h_t_is  = buildings(nb)%area_facade  * h_is                                              !< [W/K] with h_is = 3.45 W /
1587                                                                                                      !< (m2 K) between surface and air, Eq. (9)
1588             h_t_ms  = a_m * h_ms                                                                     !< [W/K] with h_ms = 9.10 W /
1589                                                                                                      !< (m2 K) between component and surface, Eq. (64)
1590             h_t_wall  = 1.0_wp / ( 1.0_wp / ( ( facade_element_area - window_area_per_facade )    &  !< [W/K]
1591                                    * buildings(nb)%lambda_layer3 / buildings(nb)%s_layer3 * 0.5_wp &
1592                                             ) + 1.0_wp / h_t_ms )                                    !< [W/K] opaque components
1593             h_t_wm  = 1.0_wp / ( 1.0_wp / h_t_wall - 1.0_wp / h_t_ms )                               !< [W/K] emmision Eq. (63), Section 12.2.2
1594!
1595!--          Internal air loads dependent on the occupacy of the room.
1596!--          Basical internal heat gains (qint_low) with additional internal heat gains by occupancy
1597!--          (qint_high) (0,5*phi_int)
1598             phi_ia = 0.5_wp * ( ( buildings(nb)%qint_high * schedule_d + buildings(nb)%qint_low ) &
1599                             * floor_area_per_facade )
1600             q_int = phi_ia
1601
1602!
1603!--          Airflow dependent on the occupacy of the room.
1604!--          Basical airflow (air_change_low) with additional airflow gains by occupancy
1605!--          (air_change_high)
1606             air_change = ( buildings(nb)%air_change_high * schedule_d +                           &
1607                            buildings(nb)%air_change_low )
1608!
1609!--          Heat transfer of ventilation.
1610!--          Not less than 0.01 W/K to avoid division by 0 in further calculations with heat
1611!--          capacity of air 0.33 Wh/m2K
1612             h_v   = MAX( 0.01_wp , ( air_change * indoor_volume_per_facade *                      &
1613                                    0.33_wp * (1.0_wp - buildings(nb)%eta_ve ) ) )                    !< [W/K] from ISO 13789
1614                                                                                                      !< Eq.(10)
1615
1616!--          Heat transfer coefficient auxiliary variables
1617             h_t_1 = 1.0_wp / ( ( 1.0_wp / h_v )   + ( 1.0_wp / h_t_is ) )                            !< [W/K] Eq. (C.6)
1618             h_t_2 = h_t_1 + h_t_es                                                                   !< [W/K] Eq. (C.7)
1619             h_t_3 = 1.0_wp / ( ( 1.0_wp / h_t_2 ) + ( 1.0_wp / h_t_ms ) )                            !< [W/K] Eq. (C.8)
1620!
1621!--          Net short-wave radiation through window area (was i_global)
1622             net_sw_in = surf_usm_v(l)%rad_sw_in(m) - surf_usm_v(l)%rad_sw_out(m)
1623!
1624!--          Quantities needed for im_calc_temperatures
1625             i = surf_usm_v(l)%i(m)
1626             j = surf_usm_v(l)%j(m)
1627             k = surf_usm_v(l)%k(m)
1628             near_facade_temperature = surf_usm_v(l)%pt_10cm(m)
1629
1630!              indoor_wall_window_temperature = frac_wall  * t_wall_v(l)%val(nzt_wall,m)             &
1631!                                             + frac_win   * t_window_v(l)%val(nzt_wall,m)           &
1632!                                             + frac_green * t_green_v(l)%val(nzt_wall,m)
1633
1634             indoor_wall_temperature = frac_wall  * t_wall_v(l)%val(nzt_wall,m)                    &
1635                                     + frac_win   * t_window_v(l)%val(nzt_wall,m)                  &
1636                                     + frac_green * t_green_v(l)%val(nzt_wall,m)
1637
1638!
1639!--          Solar thermal gains. If net_sw_in larger than sun-protection
1640!--          threshold parameter (params_solar_protection), sun protection will
1641!--          be activated
1642             IF ( net_sw_in <= params_solar_protection )  THEN
1643                solar_protection_off = 1
1644                solar_protection_on  = 0
1645             ELSE
1646                solar_protection_off = 0
1647                solar_protection_on  = 1
1648             ENDIF
1649!
1650!--          Calculation of total heat gains from net_sw_in through windows [W] in respect on
1651!--          automatic sun protection.
1652!--          DIN 4108 - 2 chap.8
1653             phi_sol = (   window_area_per_facade * net_sw_in * solar_protection_off               &
1654                         + window_area_per_facade * net_sw_in * buildings(nb)%f_c_win *            &
1655                           solar_protection_on )                                                   &
1656                       * buildings(nb)%g_value_win * ( 1.0_wp - params_f_f ) * params_f_w
1657             q_sol = phi_sol
1658!
1659!--          Calculation of the mass specific thermal load for internal and external heatsources.
1660             phi_m   = (a_m / total_area) * ( phi_ia + phi_sol )          !< [W] Eq. (C.2) with phi_ia=0,5*phi_int
1661             q_c_m = phi_m
1662!
1663!--          Calculation mass specific thermal load implied non thermal mass.
1664             phi_st  =   ( 1.0_wp - ( a_m / total_area ) - ( h_t_es / ( 9.1_wp * total_area ) ) )  &
1665                       * ( phi_ia + phi_sol )                                                       !< [W] Eq. (C.3) with
1666                                                                                                    !< phi_ia=0,5*phi_int
1667             q_c_st = phi_st
1668!
1669!--          Calculations for deriving indoor temperature and heat flux into the wall.
1670!--          Step 1: indoor temperature without heating and cooling.
1671!--          section C.4.1 Picture C.2 zone 3)
1672             phi_hc_nd = 0.0_wp
1673             CALL im_calc_temperatures ( i, j, k, indoor_wall_temperature, &
1674                                         near_facade_temperature, phi_hc_nd, buildings(nb)%theta_m_t_prev_v(fa) )
1675!
1676!--          If air temperature between border temperatures of heating and cooling, assign output
1677!--          variable, then ready.
1678             IF ( buildings(nb)%theta_int_h_set <= theta_air  .AND.                                &
1679                  theta_air <= buildings(nb)%theta_int_c_set )  THEN
1680                phi_hc_nd_ac = 0.0_wp
1681                phi_hc_nd    = phi_hc_nd_ac
1682                theta_air_ac = theta_air
1683!
1684!--          Step 2: Else, apply 10 W/m2 heating/cooling power and calculate indoor temperature
1685!--          again.
1686             ELSE
1687!
1688!--             Temperature not correct, calculation method according to section C4.2
1689                theta_air_0 = theta_air !< Note temperature without heating/cooling
1690!
1691!--             Heating or cooling?
1692                IF ( theta_air_0 > buildings(nb)%theta_int_c_set )  THEN
1693                   theta_air_set = buildings(nb)%theta_int_c_set
1694                ELSE
1695                   theta_air_set = buildings(nb)%theta_int_h_set
1696                ENDIF
1697
1698!--             Calculate the temperature with phi_hc_nd_10
1699                phi_hc_nd_10 = 10.0_wp * floor_area_per_facade
1700                phi_hc_nd    = phi_hc_nd_10
1701
1702                CALL  im_calc_temperatures ( i, j, k, indoor_wall_temperature, &
1703                                             near_facade_temperature, phi_hc_nd, buildings(nb)%theta_m_t_prev_v(fa) )
1704
1705                theta_air_10 = theta_air !< Note the temperature with 10 W/m2 of heating
1706!
1707!--             Avoid division by zero at first timestep where the denominator can become zero.
1708                IF ( ABS( theta_air_10  - theta_air_0 ) < 1E-10_wp )  THEN
1709                   phi_hc_nd_un = phi_hc_nd_10
1710                ELSE
1711                   phi_hc_nd_un = phi_hc_nd_10 * ( theta_air_set - theta_air_0 )                   &
1712                                               / ( theta_air_10  - theta_air_0 )             !< Eq. (C.13)
1713                ENDIF
1714!
1715!--             Step 3: with temperature ratio to determine the heating or cooling capacity
1716!--             If necessary, limit the power to maximum power.
1717!--             section C.4.1 Picture C.2 zone 2) and 4)
1718                buildings(nb)%phi_c_max = buildings(nb)%q_c_max * floor_area_per_facade
1719                buildings(nb)%phi_h_max = buildings(nb)%q_h_max * floor_area_per_facade
1720                IF ( buildings(nb)%phi_c_max < phi_hc_nd_un  .AND.                                 &
1721                     phi_hc_nd_un < buildings(nb)%phi_h_max )  THEN
1722                   phi_hc_nd_ac = phi_hc_nd_un
1723                   phi_hc_nd = phi_hc_nd_un
1724                ELSE
1725!
1726!--             Step 4: inner temperature with maximum heating (phi_hc_nd_un positive) or cooling
1727!--                     (phi_hc_nd_un negative)
1728!--             section C.4.1 Picture C.2 zone 1) and 5)
1729                   IF ( phi_hc_nd_un > 0.0_wp )  THEN
1730                      phi_hc_nd_ac = buildings(nb)%phi_h_max                                         !< Limit heating
1731                   ELSE
1732                      phi_hc_nd_ac = buildings(nb)%phi_c_max                                         !< Limit cooling
1733                   ENDIF
1734                ENDIF
1735                phi_hc_nd = phi_hc_nd_ac
1736!
1737!--             Calculate the temperature with phi_hc_nd_ac (new)
1738                CALL  im_calc_temperatures ( i, j, k, indoor_wall_temperature, &
1739                                             near_facade_temperature, phi_hc_nd, buildings(nb)%theta_m_t_prev_v(fa) )
1740                theta_air_ac = theta_air
1741             ENDIF
1742!
1743!--          Update theta_m_t_prev
1744             buildings(nb)%theta_m_t_prev_v(fa) = theta_m_t
1745
1746
1747             q_vent = h_v * ( theta_air - near_facade_temperature )
1748!
1749!--          Calculate the operating temperature with weighted mean of temperature of air and mean.
1750!--          Will be used for thermal comfort calculations.
1751             theta_op     = 0.3_wp * theta_air_ac + 0.7_wp * theta_s
1752
1753!              surf_usm_v(l)%t_indoor(m) = theta_op                  !< not integrated yet
1754!
1755!--          Heat flux into the wall. Value needed in urban_surface_mod to
1756!--          calculate heat transfer through wall layers towards the facade
1757             IF ( (facade_element_area - window_area_per_facade) > 0.0_wp )  THEN
1758                q_wall = h_t_wm * ( indoor_wall_temperature - theta_m )                 &
1759                                    / ( facade_element_area - window_area_per_facade )
1760             ELSE
1761                q_wall = 0.0_wp
1762             ENDIF
1763
1764             IF ( window_area_per_facade > 0.0_wp )  THEN
1765                q_win = h_t_es * ( pt(k,j,i) - theta_s ) / ( window_area_per_facade )
1766             ELSE
1767                q_win = 0.0_wp
1768             ENDIF
1769
1770!
1771!--          Transfer q_wall & q_win back to USM (innermost wall/window layer)
1772             surf_usm_v(l)%iwghf_eb(m)        = - q_wall
1773             surf_usm_v(l)%iwghf_eb_window(m) = - q_win
1774
1775!              print*, "wwfjg", surf_usm_v(l)%iwghf_eb(m), surf_usm_v(l)%iwghf_eb_window(m)
1776!
1777!--          Sum up operational indoor temperature per kk-level. Further below, this temperature is
1778!--          reduced by MPI to one temperature per kk-level and building (processor overlapping).
1779             buildings(nb)%t_in_l(kk) = buildings(nb)%t_in_l(kk) + theta_op
1780!
1781!--          Calculation of waste heat.
1782!--          Anthropogenic heat output.
1783             IF ( phi_hc_nd_ac > 0.0_wp )  THEN
1784                heating_on = 1
1785                cooling_on = 0
1786             ELSE
1787                heating_on = 0
1788                cooling_on = -1
1789             ENDIF
1790
1791             q_waste_heat = ( phi_hc_nd * ( buildings(nb)%params_waste_heat_h * heating_on +       &
1792                                            buildings(nb)%params_waste_heat_c * cooling_on )       &
1793                                                    ) / facade_element_area  !< [W/m2] , observe the directional convention in
1794                                                                             !< PALM!
1795             surf_usm_v(l)%waste_heat(m) = q_waste_heat
1796          ENDDO !< Vertical surfaces loop
1797       ENDIF !< buildings(nb)%on_pe
1798    ENDDO !< buildings loop
1799
1800!
1801!-- Determine the mean building temperature.
1802    DO  nb = 1, num_build
1803!
1804!--    Allocate dummy array used for summing-up facade elements.
1805!--    Please note, dummy arguments are necessary as building-date type arrays are not necessarily
1806!--    allocated on all PEs.
1807       ALLOCATE( t_in_l_send(buildings(nb)%kb_min:buildings(nb)%kb_max) )
1808       ALLOCATE( t_in_recv(buildings(nb)%kb_min:buildings(nb)%kb_max) )
1809       t_in_l_send = 0.0_wp
1810       t_in_recv   = 0.0_wp
1811
1812       IF ( buildings(nb)%on_pe )  THEN
1813          t_in_l_send = buildings(nb)%t_in_l
1814       ENDIF
1815
1816
1817#if defined( __parallel )
1818       CALL MPI_ALLREDUCE( t_in_l_send,                                                            &
1819                           t_in_recv,                                                              &
1820                           buildings(nb)%kb_max - buildings(nb)%kb_min + 1,                        &
1821                           MPI_REAL,                                                               &
1822                           MPI_SUM,                                                                &
1823                           comm2d,                                                                 &
1824                           ierr )
1825
1826       IF ( ALLOCATED( buildings(nb)%t_in ) )  buildings(nb)%t_in = t_in_recv
1827#else
1828       IF ( ALLOCATED( buildings(nb)%t_in ) )  buildings(nb)%t_in = buildings(nb)%t_in_l
1829#endif
1830
1831       IF ( ALLOCATED( buildings(nb)%t_in ) )  THEN
1832!
1833!--       Average indoor temperature. Note, in case a building is completely surrounded by higher
1834!--       buildings, it may have no facade elements at some height levels, which will lead to a
1835!--       division by zero.
1836          DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
1837             IF ( buildings(nb)%num_facade_h(k) + buildings(nb)%num_facade_v(k) > 0 )  THEN
1838                buildings(nb)%t_in(k) = buildings(nb)%t_in(k) /                                    &
1839                                        REAL( buildings(nb)%num_facade_h(k) +                      &
1840                                              buildings(nb)%num_facade_v(k), KIND = wp )
1841             ENDIF
1842          ENDDO
1843!
1844!--       If indoor temperature is not defined because of missing facade elements, the values from
1845!--       the above-lying level will be taken.
1846!--       At least at the top of the buildings facades are defined, so that at least there an indoor
1847!--       temperature is defined. This information will propagate downwards the building.
1848          DO  k = buildings(nb)%kb_max-1, buildings(nb)%kb_min, -1
1849             IF ( buildings(nb)%num_facade_h(k) + buildings(nb)%num_facade_v(k) <= 0 )  THEN
1850                buildings(nb)%t_in(k) = buildings(nb)%t_in(k+1)
1851             ENDIF
1852          ENDDO
1853       ENDIF
1854
1855
1856!
1857!--    Deallocate dummy arrays
1858       DEALLOCATE( t_in_l_send )
1859       DEALLOCATE( t_in_recv )
1860
1861    ENDDO
1862
1863 END SUBROUTINE im_main_heatcool
1864
1865
1866!--------------------------------------------------------------------------------------------------!
1867! Description:
1868!-------------
1869!> Check data output for plant canopy model
1870!--------------------------------------------------------------------------------------------------!
1871 SUBROUTINE im_check_data_output( var, unit )
1872
1873    CHARACTER (LEN=*) ::  unit   !<
1874    CHARACTER (LEN=*) ::  var    !<
1875
1876    SELECT CASE ( TRIM( var ) )
1877
1878
1879        CASE ( 'im_hf_roof')
1880           unit = 'W m-2'
1881
1882        CASE ( 'im_hf_wall_win' )
1883           unit = 'W m-2'
1884
1885        CASE ( 'im_hf_wall_win_waste' )
1886           unit = 'W m-2'
1887
1888        CASE ( 'im_hf_roof_waste' )
1889           unit = 'W m-2'
1890
1891        CASE ( 'im_t_indoor_mean' )
1892           unit = 'K'
1893
1894        CASE ( 'im_t_indoor_roof' )
1895           unit = 'K'
1896
1897        CASE ( 'im_t_indoor_wall_win' )
1898           unit = 'K'
1899           
1900        CASE ( 'im_t_indoor_wall' )
1901           unit = 'K'
1902
1903        CASE DEFAULT
1904           unit = 'illegal'
1905
1906    END SELECT
1907
1908 END SUBROUTINE
1909
1910
1911!--------------------------------------------------------------------------------------------------!
1912! Description:
1913!-------------
1914!> Check parameters routine for plant canopy model
1915!--------------------------------------------------------------------------------------------------!
1916 SUBROUTINE im_check_parameters
1917
1918!   USE control_parameters,
1919!       ONLY: message_string
1920
1921 END SUBROUTINE im_check_parameters
1922
1923
1924!--------------------------------------------------------------------------------------------------!
1925! Description:
1926!-------------
1927!> Subroutine defining appropriate grid for netcdf variables.
1928!> It is called from subroutine netcdf.
1929!--------------------------------------------------------------------------------------------------!
1930 SUBROUTINE im_define_netcdf_grid( var, found, grid_x, grid_y, grid_z )
1931
1932    CHARACTER (LEN=*), INTENT(OUT) ::  grid_x
1933    CHARACTER (LEN=*), INTENT(OUT) ::  grid_y
1934    CHARACTER (LEN=*), INTENT(OUT) ::  grid_z
1935    CHARACTER (LEN=*), INTENT(IN)  ::  var
1936
1937    LOGICAL, INTENT(OUT)           ::  found
1938
1939
1940    found   = .TRUE.
1941!
1942!-- Check for the grid
1943    SELECT CASE ( TRIM( var ) )
1944
1945       CASE ( 'im_hf_roof', 'im_hf_roof_waste' )
1946          grid_x = 'x'
1947          grid_y = 'y'
1948          grid_z = 'zw'
1949!
1950!--    Heat fluxes at vertical walls are actually defined on stagged grid, i.e. xu, yv.
1951       CASE ( 'im_hf_wall_win', 'im_hf_wall_win_waste' )
1952          grid_x = 'x'
1953          grid_y = 'y'
1954          grid_z = 'zu'
1955
1956       CASE ( 'im_t_indoor_mean', 'im_t_indoor_roof', 'im_t_indoor_wall_win', 'indoor_wall' )
1957          grid_x = 'x'
1958          grid_y = 'y'
1959          grid_z = 'zw'
1960
1961       CASE DEFAULT
1962          found  = .FALSE.
1963          grid_x = 'none'
1964          grid_y = 'none'
1965          grid_z = 'none'
1966    END SELECT
1967
1968 END SUBROUTINE im_define_netcdf_grid
1969
1970
1971!--------------------------------------------------------------------------------------------------!
1972! Description:
1973! ------------
1974!> Subroutine defining 3D output variables
1975!--------------------------------------------------------------------------------------------------!
1976 SUBROUTINE im_data_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
1977
1978    USE indices
1979
1980    USE kinds
1981
1982    CHARACTER (LEN=*) ::  variable !<
1983
1984    INTEGER(iwp) ::  av    !<
1985    INTEGER(iwp) ::  i     !<
1986    INTEGER(iwp) ::  j     !<
1987    INTEGER(iwp) ::  k     !<
1988    INTEGER(iwp) ::  l     !<
1989    INTEGER(iwp) ::  m     !<
1990    INTEGER(iwp) ::  nb    !< index of the building in the building data structure
1991    INTEGER(iwp) ::  nzb_do !< lower limit of the data output (usually 0)
1992    INTEGER(iwp) ::  nzt_do !< vertical upper limit of the data output (usually nz_do3d)
1993
1994    LOGICAL      ::  found !<
1995
1996    REAL(wp), INTENT(IN) ::  fill_value !< value for the _FillValue attribute
1997
1998    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
1999
2000    local_pf = fill_value
2001
2002    found = .TRUE.
2003
2004    SELECT CASE ( TRIM( variable ) )
2005!
2006!--     Output of indoor temperature. All grid points within the building are filled with values,
2007!--     while atmospheric grid points are set to _FillValues.
2008        CASE ( 'im_t_indoor_mean' )
2009           IF ( av == 0 ) THEN
2010              DO  i = nxl, nxr
2011                 DO  j = nys, nyn
2012                    IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
2013!
2014!--                    Determine index of the building within the building data structure.
2015                       nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM=1 )
2016                       IF ( buildings(nb)%on_pe )  THEN
2017!
2018!--                       Write mean building temperature onto output array. Please note, in
2019!--                       contrast to many other loops in the output, the vertical bounds are
2020!--                       determined by the lowest and hightest vertical index occupied by the
2021!--                       building.
2022                          DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
2023                             local_pf(i,j,k) = buildings(nb)%t_in(k)
2024                          ENDDO
2025                       ENDIF
2026                    ENDIF
2027                 ENDDO
2028              ENDDO
2029           ENDIF
2030
2031        CASE ( 'im_hf_roof' )
2032           IF ( av == 0 )  THEN
2033              DO  m = 1, surf_usm_h(0)%ns
2034                 i = surf_usm_h(0)%i(m) !+ surf_usm_h%ioff
2035                 j = surf_usm_h(0)%j(m) !+ surf_usm_h%joff
2036                 k = surf_usm_h(0)%k(m) !+ surf_usm_h%koff
2037                 local_pf(i,j,k) = surf_usm_h(0)%iwghf_eb(m)
2038              ENDDO
2039           ENDIF
2040
2041        CASE ( 'im_hf_roof_waste' )
2042           IF ( av == 0 )  THEN
2043              DO m = 1, surf_usm_h(0)%ns
2044                 i = surf_usm_h(0)%i(m) !+ surf_usm_h%ioff
2045                 j = surf_usm_h(0)%j(m) !+ surf_usm_h%joff
2046                 k = surf_usm_h(0)%k(m) !+ surf_usm_h%koff
2047                 local_pf(i,j,k) = surf_usm_h(0)%waste_heat(m)
2048              ENDDO
2049           ENDIF
2050
2051       CASE ( 'im_hf_wall_win' )
2052           IF ( av == 0 )  THEN
2053              DO l = 0, 3
2054                 DO m = 1, surf_usm_v(l)%ns
2055                    i = surf_usm_v(l)%i(m) !+ surf_usm_v(l)%ioff
2056                    j = surf_usm_v(l)%j(m) !+ surf_usm_v(l)%joff
2057                    k = surf_usm_v(l)%k(m) !+ surf_usm_v(l)%koff
2058                    local_pf(i,j,k) = surf_usm_v(l)%iwghf_eb(m)
2059                 ENDDO
2060              ENDDO
2061           ENDIF
2062
2063        CASE ( 'im_hf_wall_win_waste' )
2064           IF ( av == 0 )  THEN
2065              DO l = 0, 3
2066                 DO m = 1, surf_usm_v(l)%ns
2067                    i = surf_usm_v(l)%i(m) !+ surf_usm_v(l)%ioff
2068                    j = surf_usm_v(l)%j(m) !+ surf_usm_v(l)%joff
2069                    k = surf_usm_v(l)%k(m) !+ surf_usm_v(l)%koff
2070                    local_pf(i,j,k) =  surf_usm_v(l)%waste_heat(m)
2071                 ENDDO
2072              ENDDO
2073           ENDIF
2074
2075!
2076!< NOTE im_t_indoor_roof and im_t_indoor_wall_win not work yet
2077
2078!         CASE ( 'im_t_indoor_roof' )
2079!            IF ( av == 0 )  THEN
2080!               DO  m = 1, surf_usm_h%ns
2081!                   i = surf_usm_h%i(m) !+ surf_usm_h%ioff
2082!                   j = surf_usm_h%j(m) !+ surf_usm_h%joff
2083!                   k = surf_usm_h%k(m) !+ surf_usm_h%koff
2084!                   local_pf(i,j,k) = surf_usm_h%t_indoor(m)
2085!               ENDDO
2086!            ENDIF
2087!
2088!         CASE ( 'im_t_indoor_wall_win' )
2089!            IF ( av == 0 )  THEN
2090!               DO l = 0, 3
2091!                  DO m = 1, surf_usm_v(l)%ns
2092!                     i = surf_usm_v(l)%i(m) !+ surf_usm_v(l)%ioff
2093!                     j = surf_usm_v(l)%j(m) !+ surf_usm_v(l)%joff
2094!                     k = surf_usm_v(l)%k(m) !+ surf_usm_v(l)%koff
2095!                     local_pf(i,j,k) = surf_usm_v(l)%t_indoor(m)
2096!                  ENDDO
2097!               ENDDO
2098!            ENDIF
2099
2100        CASE DEFAULT
2101           found = .FALSE.
2102
2103    END SELECT
2104
2105 END SUBROUTINE im_data_output_3d
2106
2107
2108!--------------------------------------------------------------------------------------------------!
2109! Description:
2110! ------------
2111!> Parin for &indoor_parameters for indoor model
2112!--------------------------------------------------------------------------------------------------!
2113 SUBROUTINE im_parin
2114
2115    USE control_parameters,                                                                        &
2116        ONLY:  indoor_model
2117
2118
2119    CHARACTER (LEN=80) ::  line  !< string containing current line of file PARIN
2120
2121    NAMELIST /indoor_parameters/  indoor_during_spinup,                                            &
2122                                  initial_indoor_temperature
2123
2124
2125!
2126!-- Try to find indoor model package
2127    REWIND ( 11 )
2128    line = ' '
2129    DO  WHILE ( INDEX( line, '&indoor_parameters' ) == 0 )
2130       READ ( 11, '(A)', END=10 )  line
2131    ENDDO
2132    BACKSPACE ( 11 )
2133
2134!
2135!-- Read user-defined namelist
2136    READ ( 11, indoor_parameters )
2137!
2138!-- Set flag that indicates that the indoor model is switched on
2139    indoor_model = .TRUE.
2140
2141!
2142!--    Activate spinup (maybe later
2143!        IF ( spinup_time > 0.0_wp )  THEN
2144!           coupling_start_time = spinup_time
2145!           end_time = end_time + spinup_time
2146!           IF ( spinup_pt_mean == 9999999.9_wp )  THEN
2147!              spinup_pt_mean = pt_surface
2148!           ENDIF
2149!           spinup = .TRUE.
2150!        ENDIF
2151
2152 10 CONTINUE
2153
2154 END SUBROUTINE im_parin
2155
2156
2157END MODULE indoor_model_mod
Note: See TracBrowser for help on using the repository browser.