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

Last change on this file since 3745 was 3745, checked in by suehring, 5 years ago

document last commit

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