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

Last change on this file since 4780 was 4780, checked in by suehring, 3 years ago

Urban-surface model and indoor model: Default building parameters updated and extended; revision of summer- and wintertime-dependent indoor parameters (responsible S. Rissmann); extension of albedo parameters to different building facades and roofs; first and second wall layer initialized with individual building properties rather than with with the same properties (heat capacity and conductivity)

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