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

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

removed unused variable in indoor model and updated urban_environment test cases

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