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

Last change on this file since 4646 was 4646, checked in by raasch, 4 years ago

files re-formatted to follow the PALM coding standard

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