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

Last change on this file since 4700 was 4698, checked in by maronga, 4 years ago

bugfix in urban surface model (introduced in previous revision)

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