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

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

Indoor model: bugfix - avoid divisions by zero

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