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

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

bugfix in indoor model, code layout change in urban surface model, indoor model integrated in spinup mechanism

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