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

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

Radiative transfer model RTM version 4.1

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