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

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

Coupling of indoor model to atmosphere; output of indoor temperatures and waste heat; enable restarts with indoor model; bugfix plant transpiration; bugfix - missing calculation of 10cm temperature

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