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

Last change on this file since 4683 was 4681, checked in by pavelkrc, 4 years ago

Fix indexing of horizontal surfaces in indoor model

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