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

Last change on this file since 3829 was 3786, checked in by raasch, 5 years ago

unused variables removed, interoperable C datatypes introduced in particle type to avoid compiler warnings

  • Property svn:keywords set to Id
File size: 84.9 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!
24!
25! Former revisions:
26! -----------------
27! $Id: indoor_model_mod.f90 3786 2019-03-06 16:58:03Z raasch $
28! unused variables removed
29!
30! 3759 2019-02-21 15:53:45Z suehring
31! - Calculation of total building volume
32! - Several bugfixes
33! - Calculation of building height revised
34!
35! 3745 2019-02-15 18:57:56Z suehring
36! - remove building_type from module
37! - initialize parameters for each building individually instead of a bulk
38!   initializaion with  identical building type for all
39! - output revised
40! - add missing _wp
41! - some restructuring of variables in building data structure
42!
43! 3744 2019-02-15 18:38:58Z suehring
44! Some interface calls moved to module_interface + cleanup
45!
46! 3597 2018-12-04 08:40:18Z maronga
47! Renamed t_surf_10cm to pt_10cm
48!
49! 3593 2018-12-03 13:51:13Z kanani
50! Replace degree symbol by degree_C
51!
52! 3524 2018-11-14 13:36:44Z raasch
53! working precision added to make code Fortran 2008 conform
54!
55! 3469 2018-10-30 20:05:07Z kanani
56! Initial revision (tlang, suehring, kanani, srissman)
57!
58!
59!
60! Authors:
61! --------
62! @author Tobias Lang
63! @author Jens Pfafferott
64! @author Farah Kanani-Suehring
65! @author Matthias Suehring
66! @author Sascha Rißmann
67!
68!
69! Description:
70! ------------
71!> <Description of the new module>
72!> Module for Indoor Climate Model (ICM)
73!> The module is based on the DIN EN ISO 13790 with simplified hour-based procedure.
74!> This model is a equivalent circuit diagram of a three-point RC-model (5R1C).
75!> This module differ between indoor-air temperature an average temperature of indoor surfaces which make it prossible to determine thermal comfort
76!> the heat transfer between indoor and outdoor is simplified
77
78!> @todo Replace window_area_per_facade by %frac(1,m) for window
79!> @todo emissivity change for window blinds if solar_protection_on=1
80!> @todo write datas in netcdf file as output data
81!> @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
82!>
83!> @note Do we allow use of integer flags, or only logical flags? (concerns e.g. cooling_on, heating_on)
84!> @note How to write indoor temperature output to pt array?
85!>
86!> @bug  <Enter known bugs here>
87!------------------------------------------------------------------------------!
88 MODULE indoor_model_mod 
89
90    USE control_parameters,                                                    &
91        ONLY:  initializing_actions
92
93    USE kinds
94   
95    USE netcdf_data_input_mod,                                                 &
96        ONLY:  building_id_f, building_type_f
97
98    USE surface_mod,                                                           &
99        ONLY:  surf_usm_h, surf_usm_v
100
101
102    IMPLICIT NONE
103
104!
105!-- Define data structure for buidlings.
106    TYPE build
107
108       INTEGER(iwp) ::  id                                !< building ID
109       INTEGER(iwp) ::  kb_min                            !< lowest vertical index of a building
110       INTEGER(iwp) ::  kb_max                            !< highest vertical index of a building
111       INTEGER(iwp) ::  num_facades_per_building_h = 0    !< total number of horizontal facades elements
112       INTEGER(iwp) ::  num_facades_per_building_h_l = 0  !< number of horizontal facade elements on local subdomain
113       INTEGER(iwp) ::  num_facades_per_building_v = 0    !< total number of vertical facades elements
114       INTEGER(iwp) ::  num_facades_per_building_v_l = 0  !< number of vertical facade elements on local subdomain
115
116       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  l_v            !< index array linking surface-element orientation index
117                                                                  !< for vertical surfaces with building
118       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  m_h            !< index array linking surface-element index for
119                                                                  !< horizontal surfaces with building
120       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  m_v            !< index array linking surface-element index for
121                                                                  !< vertical surfaces with building
122       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facade_h   !< number of horizontal facade elements per buidling
123                                                                  !< and height level
124       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facade_v   !< number of vertical facades elements per buidling
125                                                                  !< and height level
126                                                                 
127       INTEGER(iwp) ::  ventilation_int_loads
128
129       LOGICAL ::  on_pe = .FALSE.   !< flag indicating whether a building with certain ID is on local subdomain
130       
131       REAL(wp) ::  building_height   !< building height
132       REAL(wp) ::  lambda_layer3     !< [W/(m*K)] Thermal conductivity of the inner layer 
133       REAL(wp) ::  s_layer3          !< [m] half thickness of the inner layer (layer_3)
134       REAL(wp) ::  f_c_win           !< [-] shading factor
135       REAL(wp) ::  g_value_win       !< [-] SHGC factor
136       REAL(wp) ::  u_value_win       !< [W/(m2*K)] transmittance
137       REAL(wp) ::  air_change_low    !< [1/h] air changes per time_utc_hour
138       REAL(wp) ::  air_change_high   !< [1/h] air changes per time_utc_hour
139       REAL(wp) ::  eta_ve            !< [-] heat recovery efficiency
140       REAL(wp) ::  factor_a          !< [-] Dynamic parameters specific effective surface according to Table 12; 2.5
141                                      !< (very light, light and medium), 3.0 (heavy), 3.5 (very heavy)
142       REAL(wp) ::  factor_c          !< [J/(m2 K)] Dynamic parameters inner heatstorage according to Table 12; 80000
143                                      !< (very light), 110000 (light), 165000 (medium), 260000 (heavy), 370000 (very heavy)
144       REAL(wp) ::  lambda_at         !< [-] ratio internal surface/floor area chap. 7.2.2.2.
145       REAL(wp) ::  theta_int_h_set   !< [degree_C] Max. Setpoint temperature (winter)
146       REAL(wp) ::  theta_int_c_set   !< [degree_C] Max. Setpoint temperature (summer)
147       REAL(wp) ::  phi_h_max         !< [W] Max. Heating capacity (negative)
148       REAL(wp) ::  phi_c_max         !< [W] Max. Cooling capacity (negative)
149       REAL(wp) ::  qint_high         !< [W/m2] internal heat gains, option Database qint_0-23
150       REAL(wp) ::  qint_low          !< [W/m2] internal heat gains, option Database qint_0-23
151       REAL(wp) ::  height_storey     !< [m] storey heigth
152       REAL(wp) ::  height_cei_con    !< [m] ceiling construction heigth
153       REAL(wp) ::  vol_tot           !< total building volume
154
155       REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in       !< mean building indoor temperature, height dependent
156       REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in_l     !< mean building indoor temperature on local subdomain, height dependent
157       REAL(wp), DIMENSION(:), ALLOCATABLE ::  volume     !< total building volume, height dependent
158       REAL(wp), DIMENSION(:), ALLOCATABLE ::  vol_frac   !< fraction of local on total building volume, height dependent
159       REAL(wp), DIMENSION(:), ALLOCATABLE ::  vpf        !< building volume volume per facade element, height dependent
160       
161    END TYPE build
162
163    TYPE(build), DIMENSION(:), ALLOCATABLE ::  buildings   !< building array
164
165    INTEGER(iwp) ::  num_build   !< total number of buildings in domain
166
167!
168!-- Declare all global variables within the module
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   
222    REAL(wp) ::  f_sr                        !< [-] factor surface reduction
223    REAL(wp) ::  f_cei                       !< [-] ceiling reduction factor
224    REAL(wp) ::  ngs                         !< [m2] netto ground surface
225   
226    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
227    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)
228    REAL(wp), PARAMETER ::  params_f_win             = 0.5_wp      !< [-] proportion of window area, Database A_win aus Datenbank 27 window_area_per_facade_percent
229    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
230    REAL(wp), PARAMETER ::  params_waste_heat_c      = 4.0_wp      !< [-] anthropogenic heat outputs for cooling e.g. 4 for KKM with COP = 3
231    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
232    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)
233    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)
234
235   
236   
237    SAVE
238
239
240    PRIVATE
241   
242!
243!-- Add INTERFACES that must be available to other modules
244    PUBLIC im_init, im_main_heatcool, im_parin, im_define_netcdf_grid,          &
245           im_check_data_output, im_data_output_3d, im_check_parameters
246   
247
248!
249!-- Add VARIABLES that must be available to other modules
250    PUBLIC dt_indoor, skip_time_do_indoor, time_indoor
251
252!
253!-- PALM interfaces:
254!-- Data output checks for 2D/3D data to be done in check_parameters
255     INTERFACE im_check_data_output
256        MODULE PROCEDURE im_check_data_output
257     END INTERFACE im_check_data_output
258!
259!-- Input parameter checks to be done in check_parameters
260     INTERFACE im_check_parameters
261        MODULE PROCEDURE im_check_parameters
262     END INTERFACE im_check_parameters
263!
264!-- Data output of 3D data
265     INTERFACE im_data_output_3d
266        MODULE PROCEDURE im_data_output_3d
267     END INTERFACE im_data_output_3d
268
269!
270!-- Definition of data output quantities
271     INTERFACE im_define_netcdf_grid
272        MODULE PROCEDURE im_define_netcdf_grid
273     END INTERFACE im_define_netcdf_grid
274!
275! !
276! !-- Output of information to the header file
277!     INTERFACE im_header
278!        MODULE PROCEDURE im_header
279!     END INTERFACE im_header
280!
281!-- Calculations for indoor temperatures 
282    INTERFACE im_calc_temperatures
283       MODULE PROCEDURE im_calc_temperatures
284    END INTERFACE im_calc_temperatures
285!
286!-- Initialization actions 
287    INTERFACE im_init
288       MODULE PROCEDURE im_init
289    END INTERFACE im_init
290!
291!-- Main part of indoor model 
292    INTERFACE im_main_heatcool
293       MODULE PROCEDURE im_main_heatcool
294    END INTERFACE im_main_heatcool
295!
296!-- Reading of NAMELIST parameters
297    INTERFACE im_parin
298       MODULE PROCEDURE im_parin
299    END INTERFACE im_parin
300
301 CONTAINS
302
303!------------------------------------------------------------------------------!
304! Description:
305! ------------
306!< Calculation of the air temperatures and mean radiation temperature
307!< This is basis for the operative temperature
308!< Based on a Crank-Nicholson scheme with a timestep of a hour
309!------------------------------------------------------------------------------!
310 SUBROUTINE im_calc_temperatures ( i, j, k, indoor_wall_window_temperature,    &
311                                   near_facade_temperature, phi_hc_nd_dummy )
312 
313    USE arrays_3d,                                                             &
314        ONLY:  pt
315   
316   
317    IMPLICIT NONE
318   
319   
320    INTEGER(iwp) ::  i
321    INTEGER(iwp) ::  j
322    INTEGER(iwp) ::  k
323   
324    REAL(wp) ::  indoor_wall_window_temperature  !< weighted temperature of innermost wall/window layer
325    REAL(wp) ::  near_facade_temperature
326    REAL(wp) ::  phi_hc_nd_dummy
327   
328
329    !< Calculation of total mass specific thermal load (internal and external)
330    phi_mtot = ( phi_m + h_tr_em * indoor_wall_window_temperature              &
331                       + h_tr_3  * ( phi_st + h_tr_w * pt(k,j,i)               &
332                                            + h_tr_1 *                         &
333                                               ( ( ( phi_ia + phi_hc_nd_dummy ) / h_ve )  &
334                                                 + near_facade_temperature )   &
335                                   ) / h_tr_2                                  &
336               )                                                                !< [degree_C] Eq. (C.5)
337   
338    !< Calculation of component temperature at factual timestep
339    theta_m_t = ( ( theta_m_t_prev                                               &
340                    * ( ( c_m / 3600.0_wp ) - 0.5_wp * ( h_tr_3 + h_tr_em ) ) + phi_mtot &
341                  )                                                              &
342                  /   ( ( c_m / 3600.0_wp ) + 0.5_wp * ( h_tr_3 + h_tr_em ) )            &
343                )                                                               !< [degree_C] Eq. (C.4)
344
345    !< Calculation of mean inner temperature for the RC-node in actual timestep
346    theta_m = ( theta_m_t + theta_m_t_prev ) * 0.5_wp                              !< [degree_C] Eq. (C.9)
347   
348    !< Calculation of mean surface temperature of the RC-node in actual timestep
349    theta_s = ( (   h_tr_ms * theta_m + phi_st + h_tr_w * pt(k,j,i)                         &
350                  + h_tr_1  * ( near_facade_temperature + ( phi_ia + phi_hc_nd_dummy ) / h_ve ) &
351                )                                                                           &
352                / ( h_tr_ms + h_tr_w + h_tr_1 )                                             &
353              )                                                                 !< [degree_C] Eq. (C.10)
354   
355    !< Calculation of the air temperature of the RC-node
356    theta_air = ( h_tr_is * theta_s + h_ve * near_facade_temperature         &
357                                    + phi_ia + phi_hc_nd_dummy ) / ( h_tr_is + h_ve ) !< [degree_C] Eq. (C.11)
358
359 END SUBROUTINE im_calc_temperatures
360
361!------------------------------------------------------------------------------!
362! Description:
363! ------------
364!> Initialization of the indoor model.
365!> Static information are calculated here, e.g. building parameters and
366!> geometrical information, everything that doesn't change in time.
367!
368!-- Input values
369!-- Input datas from Palm, M4
370!     i_global             -->  net_sw_in                         !global radiation [W/m2]
371!     theta_e              -->  pt(k,j,i)                         !undisturbed outside temperature, 1. PALM volume, for windows
372!     theta_sup = theta_f  -->  surf_usm_h%pt_10cm(m)
373!                               surf_usm_v(l)%pt_10cm(m)   !Air temperature, facade near (10cm) air temperature from 1. Palm volume
374!     theta_node           -->  t_wall_h(nzt_wall,m)
375!                               t_wall_v(l)%t(nzt_wall,m)         !Temperature of innermost wall layer, for opaque wall
376!------------------------------------------------------------------------------!
377 SUBROUTINE im_init
378 
379    USE arrays_3d,                                                             &
380        ONLY:  dzw
381
382    USE control_parameters,                                                    &
383        ONLY:  message_string
384
385    USE indices,                                                               &
386        ONLY:  nxl, nxr, nyn, nys, nzb, nzt, wall_flags_0
387
388    USE grid_variables,                                                        &
389        ONLY:  dx, dy
390
391    USE pegrid
392
393    USE surface_mod,                                                           &
394        ONLY:  surf_usm_h, surf_usm_v
395       
396    USE urban_surface_mod,                                                     &
397        ONLY:  building_pars, building_type
398
399    IMPLICIT NONE
400
401    INTEGER(iwp) ::  bt   !< local building type
402    INTEGER(iwp) ::  i    !< running index along x-direction
403    INTEGER(iwp) ::  j    !< running index along y-direction
404    INTEGER(iwp) ::  k    !< running index along z-direction
405    INTEGER(iwp) ::  l    !< running index for surface-element orientation
406    INTEGER(iwp) ::  m    !< running index surface elements
407    INTEGER(iwp) ::  n    !< building index
408    INTEGER(iwp) ::  nb   !< building index
409
410    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids           !< building IDs on entire model domain
411    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_final     !< building IDs on entire model domain,
412                                                                    !< multiple occurences are sorted out
413    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_final_tmp !< temporary array used for resizing
414    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_l         !< building IDs on local subdomain
415    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_l_tmp     !< temporary array used to resize array of building IDs
416    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  displace_dum        !< displacements of start addresses, used for MPI_ALLGATHERV
417    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  k_max_l             !< highest vertical index of a building on subdomain
418    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  k_min_l             !< lowest vertical index of a building on subdomain
419    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  n_fa                !< counting array
420    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facades_h       !< dummy array used for summing-up total number of
421                                                                    !< horizontal facade elements
422    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facades_v       !< dummy array used for summing-up total number of
423                                                                    !< vertical facade elements
424    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  receive_dum_h       !< dummy array used for MPI_ALLREDUCE 
425    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  receive_dum_v       !< dummy array used for MPI_ALLREDUCE 
426
427    INTEGER(iwp), DIMENSION(0:numprocs-1) ::  num_buildings         !< number of buildings with different ID on entire model domain
428    INTEGER(iwp), DIMENSION(0:numprocs-1) ::  num_buildings_l       !< number of buildings with different ID on local subdomain
429   
430    REAL(wp), DIMENSION(:), ALLOCATABLE ::  volume         !< total building volume at each discrete height level
431    REAL(wp), DIMENSION(:), ALLOCATABLE ::  volume_l       !< total building volume at each discrete height level,
432                                                           !< on local subdomain
433
434    CALL location_message( 'initializing indoor model', .FALSE. )
435
436!
437!-- Initializing of indoor model is only possible if buildings can be
438!-- distinguished by their IDs.
439    IF ( .NOT. building_id_f%from_file )  THEN
440       message_string = 'Indoor model requires information about building_id'
441       CALL message( 'im_init', 'PA0999', 1, 2, 0, 6, 0  )
442    ENDIF
443!
444!-- Determine number of different building IDs on local subdomain.
445    num_buildings_l = 0
446    num_buildings   = 0
447    ALLOCATE( build_ids_l(1) )
448    DO  i = nxl, nxr
449       DO  j = nys, nyn
450          IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
451             IF ( num_buildings_l(myid) > 0 )  THEN
452                IF ( ANY( building_id_f%var(j,i) .EQ.  build_ids_l ) )  THEN
453                   CYCLE
454                ELSE
455                   num_buildings_l(myid) = num_buildings_l(myid) + 1
456!
457!--                Resize array with different local building ids
458                   ALLOCATE( build_ids_l_tmp(1:SIZE(build_ids_l)) )
459                   build_ids_l_tmp = build_ids_l
460                   DEALLOCATE( build_ids_l )
461                   ALLOCATE( build_ids_l(1:num_buildings_l(myid)) )
462                   build_ids_l(1:num_buildings_l(myid)-1) =                 &
463                               build_ids_l_tmp(1:num_buildings_l(myid)-1)
464                   build_ids_l(num_buildings_l(myid)) = building_id_f%var(j,i)
465                   DEALLOCATE( build_ids_l_tmp )
466                ENDIF
467!
468!--          First occuring building id on PE
469             ELSE
470                num_buildings_l(myid) = num_buildings_l(myid) + 1
471                build_ids_l(1) = building_id_f%var(j,i)
472             ENDIF
473          ENDIF
474       ENDDO
475    ENDDO
476!
477!-- Determine number of building IDs for the entire domain. (Note, building IDs
478!-- can appear multiple times as buildings might be distributed over several
479!-- PEs.)
480#if defined( __parallel ) 
481    CALL MPI_ALLREDUCE( num_buildings_l, num_buildings, numprocs,              &
482                        MPI_INTEGER, MPI_SUM, comm2d, ierr ) 
483#else
484    num_buildings = num_buildings_l
485#endif
486    ALLOCATE( build_ids(1:SUM(num_buildings)) )
487!
488!-- Gather building IDs. Therefore, first, determine displacements used
489!-- required for MPI_GATHERV call.
490    ALLOCATE( displace_dum(0:numprocs-1) )
491    displace_dum(0) = 0
492    DO i = 1, numprocs-1
493       displace_dum(i) = displace_dum(i-1) + num_buildings(i-1)
494    ENDDO
495
496#if defined( __parallel ) 
497    CALL MPI_ALLGATHERV( build_ids_l(1:num_buildings_l(myid)),                 &
498                         num_buildings(myid),                                  &
499                         MPI_INTEGER,                                          &
500                         build_ids,                                            &
501                         num_buildings,                                        &
502                         displace_dum,                                         & 
503                         MPI_INTEGER,                                          &
504                         comm2d, ierr )   
505
506    DEALLOCATE( displace_dum )
507
508#else
509    build_ids = build_ids_l
510#endif
511!
512!-- Note: in parallel mode, building IDs can occur mutliple times, as
513!-- each PE has send its own ids. Therefore, sort out building IDs which
514!-- appear multiple times.
515    num_build = 0
516    DO  n = 1, SIZE(build_ids)
517
518       IF ( ALLOCATED(build_ids_final) )  THEN
519          IF ( ANY( build_ids(n) .EQ. build_ids_final ) )  THEN    !FK: Warum ANY?, Warum .EQ.? --> s.o
520             CYCLE
521          ELSE
522             num_build = num_build + 1
523!
524!--          Resize
525             ALLOCATE( build_ids_final_tmp(1:num_build) )
526             build_ids_final_tmp(1:num_build-1) = build_ids_final(1:num_build-1)
527             DEALLOCATE( build_ids_final )
528             ALLOCATE( build_ids_final(1:num_build) )
529             build_ids_final(1:num_build-1) = build_ids_final_tmp(1:num_build-1)
530             build_ids_final(num_build) = build_ids(n)
531             DEALLOCATE( build_ids_final_tmp )
532          ENDIF             
533       ELSE
534          num_build = num_build + 1
535          ALLOCATE( build_ids_final(1:num_build) )
536          build_ids_final(num_build) = build_ids(n)
537       ENDIF
538    ENDDO
539
540!
541!-- Allocate building-data structure array. Note, this is a global array
542!-- and all building IDs on domain are known by each PE. Further attributes,
543!-- e.g. height-dependent arrays, however, are only allocated on PEs where
544!-- the respective building is present (in order to reduce memory demands).
545    ALLOCATE( buildings(1:num_build) )
546
547!
548!-- Store building IDs and check if building with certain ID is present on
549!-- subdomain.
550    DO  nb = 1, num_build
551       buildings(nb)%id = build_ids_final(nb)
552
553       IF ( ANY( building_id_f%var(nys:nyn,nxl:nxr) == buildings(nb)%id ) )    &
554          buildings(nb)%on_pe = .TRUE.
555    ENDDO 
556!
557!-- Determine the maximum vertical dimension occupied by each building.
558    ALLOCATE( k_min_l(1:num_build) )
559    ALLOCATE( k_max_l(1:num_build) )
560    k_min_l = nzt + 1
561    k_max_l = 0   
562
563    DO  i = nxl, nxr
564       DO  j = nys, nyn
565          IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
566             nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ),    &
567                         DIM = 1 )
568             DO  k = nzb+1, nzt+1
569!
570!--             Check if grid point belongs to a building.
571                IF ( BTEST( wall_flags_0(k,j,i), 6 ) )  THEN
572                   k_min_l(nb) = MIN( k_min_l(nb), k )
573                   k_max_l(nb) = MAX( k_max_l(nb), k )
574                ENDIF
575
576             ENDDO
577          ENDIF
578       ENDDO
579    ENDDO
580
581    DO nb = 1, num_build
582#if defined( __parallel ) 
583       CALL MPI_ALLREDUCE( k_min_l(nb), buildings(nb)%kb_min, 1, MPI_INTEGER,  &
584                           MPI_MIN, comm2d, ierr )
585       CALL MPI_ALLREDUCE( k_max_l(nb), buildings(nb)%kb_max, 1, MPI_INTEGER,  &
586                           MPI_MAX, comm2d, ierr )
587#else
588       buildings(nb)%kb_min = k_min_l(nb)
589       buildings(nb)%kb_max = k_max_l(nb)
590#endif
591
592    ENDDO 
593
594    DEALLOCATE( k_min_l )
595    DEALLOCATE( k_max_l )
596!
597!-- Calculate building height.
598    DO  nb = 1, num_build
599       buildings(nb)%building_height = 0.0_wp
600       DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
601          buildings(nb)%building_height = buildings(nb)%building_height        &
602                                        + dzw(k)
603       ENDDO
604    ENDDO
605!
606!-- Calculate building volume
607    DO  nb = 1, num_build
608!
609!--    Allocate temporary array for summing-up building volume
610       ALLOCATE( volume(buildings(nb)%kb_min:buildings(nb)%kb_max)   )
611       ALLOCATE( volume_l(buildings(nb)%kb_min:buildings(nb)%kb_max) )
612       volume   = 0.0_wp
613       volume_l = 0.0_wp
614!
615!--    Calculate building volume per height level on each PE where
616!--    these building is present.
617       IF ( buildings(nb)%on_pe )  THEN
618          ALLOCATE( buildings(nb)%volume(buildings(nb)%kb_min:buildings(nb)%kb_max)   )
619          ALLOCATE( buildings(nb)%vol_frac(buildings(nb)%kb_min:buildings(nb)%kb_max) )
620          buildings(nb)%volume   = 0.0_wp
621          buildings(nb)%vol_frac = 0.0_wp
622         
623          IF ( ANY( building_id_f%var(nys:nyn,nxl:nxr) == buildings(nb)%id ) ) &
624          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) = 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!--    Calculate total building volume
652       IF ( ALLOCATED( buildings(nb)%volume ) )                                &
653          buildings(nb)%vol_tot = SUM( buildings(nb)%volume )
654       
655       DEALLOCATE( volume   )
656       DEALLOCATE( volume_l )
657
658    ENDDO
659
660!
661!-- Allocate arrays for indoor temperature. 
662    DO  nb = 1, num_build
663       IF ( buildings(nb)%on_pe )  THEN
664          ALLOCATE( buildings(nb)%t_in(buildings(nb)%kb_min:buildings(nb)%kb_max)   )
665          ALLOCATE( buildings(nb)%t_in_l(buildings(nb)%kb_min:buildings(nb)%kb_max) )
666          buildings(nb)%t_in   = 0.0_wp
667          buildings(nb)%t_in_l = 0.0_wp
668       ENDIF
669    ENDDO
670!
671!-- Allocate arrays for number of facades per height level. Distinguish between
672!-- horizontal and vertical facades.
673    DO  nb = 1, num_build
674       IF ( buildings(nb)%on_pe )  THEN
675          ALLOCATE( buildings(nb)%num_facade_h(buildings(nb)%kb_min:buildings(nb)%kb_max) )
676          ALLOCATE( buildings(nb)%num_facade_v(buildings(nb)%kb_min:buildings(nb)%kb_max) )
677
678          buildings(nb)%num_facade_h = 0
679          buildings(nb)%num_facade_v = 0
680       ENDIF
681    ENDDO
682!
683!-- Determine number of facade elements per building on local subdomain.
684!-- Distinguish between horizontal and vertical facade elements.
685!
686!-- Horizontal facades
687    buildings(:)%num_facades_per_building_h_l = 0
688    DO  m = 1, surf_usm_h%ns
689!
690!--    For the current facade element determine corresponding building index.
691!--    First, obtain j,j,k indices of the building. Please note the
692!--    offset between facade/surface element and building location (for
693!--    horizontal surface elements the horizontal offsets are zero).
694       i = surf_usm_h%i(m) + surf_usm_h%ioff
695       j = surf_usm_h%j(m) + surf_usm_h%joff
696       k = surf_usm_h%k(m) + surf_usm_h%koff
697!
698!--    Determine building index and check whether building is on PE
699       nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM = 1 )
700       IF ( buildings(nb)%on_pe )  THEN
701!
702!--       Count number of facade elements at each height level.
703          buildings(nb)%num_facade_h(k) = buildings(nb)%num_facade_h(k) + 1 
704!
705!--       Moreover, sum up number of local facade elements per building.
706          buildings(nb)%num_facades_per_building_h_l =                         &
707                                buildings(nb)%num_facades_per_building_h_l + 1
708       ENDIF
709    ENDDO
710!
711!-- Vertical facades
712    buildings(:)%num_facades_per_building_v_l = 0
713    DO  l = 0, 3
714       DO  m = 1, surf_usm_v(l)%ns
715!
716!--       For the current facade element determine corresponding building index.
717!--       First, obtain j,j,k indices of the building. Please note the
718!--       offset between facade/surface element and building location (for
719!--       vertical surface elements the vertical offsets are zero).
720          i = surf_usm_v(l)%i(m) + surf_usm_v(l)%ioff
721          j = surf_usm_v(l)%j(m) + surf_usm_v(l)%joff
722          k = surf_usm_v(l)%k(m) + surf_usm_v(l)%koff
723
724          nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ),        &
725                       DIM = 1 )
726          IF ( buildings(nb)%on_pe )  THEN
727             buildings(nb)%num_facade_v(k) = buildings(nb)%num_facade_v(k) + 1 
728             buildings(nb)%num_facades_per_building_v_l =                      &
729                                buildings(nb)%num_facades_per_building_v_l + 1
730          ENDIF
731       ENDDO
732    ENDDO
733
734!
735!-- Determine total number of facade elements per building and assign number to
736!-- building data type.
737    DO  nb = 1, num_build
738!
739!--    Allocate dummy array used for summing-up facade elements.
740!--    Please note, dummy arguments are necessary as building-date type
741!--    arrays are not necessarily allocated on all PEs.
742       ALLOCATE( num_facades_h(buildings(nb)%kb_min:buildings(nb)%kb_max) )
743       ALLOCATE( num_facades_v(buildings(nb)%kb_min:buildings(nb)%kb_max) )
744       ALLOCATE( receive_dum_h(buildings(nb)%kb_min:buildings(nb)%kb_max) )
745       ALLOCATE( receive_dum_v(buildings(nb)%kb_min:buildings(nb)%kb_max) )
746       num_facades_h = 0
747       num_facades_v = 0
748       receive_dum_h = 0
749       receive_dum_v = 0
750
751       IF ( buildings(nb)%on_pe )  THEN
752          num_facades_h = buildings(nb)%num_facade_h
753          num_facades_v = buildings(nb)%num_facade_v
754       ENDIF
755
756#if defined( __parallel ) 
757       CALL MPI_ALLREDUCE( num_facades_h,                                      &
758                           receive_dum_h,                                      &
759                           buildings(nb)%kb_max - buildings(nb)%kb_min + 1,    &
760                           MPI_INTEGER,                                        &
761                           MPI_SUM,                                            &
762                           comm2d,                                             &
763                           ierr )
764
765       CALL MPI_ALLREDUCE( num_facades_v,                                      &
766                           receive_dum_v,                                      &
767                           buildings(nb)%kb_max - buildings(nb)%kb_min + 1,    &
768                           MPI_INTEGER,                                        &
769                           MPI_SUM,                                            &
770                           comm2d,                                             &
771                           ierr )
772       IF ( ALLOCATED( buildings(nb)%num_facade_h ) )                          &  !FK: Was wenn not allocated? --> s.o.
773           buildings(nb)%num_facade_h = receive_dum_h
774       IF ( ALLOCATED( buildings(nb)%num_facade_v ) )                          &
775           buildings(nb)%num_facade_v = receive_dum_v
776#else
777       buildings(nb)%num_facade_h = num_facades_h
778       buildings(nb)%num_facade_v = num_facades_v
779#endif
780!
781!--    Deallocate dummy arrays
782       DEALLOCATE( num_facades_h )
783       DEALLOCATE( num_facades_v )
784       DEALLOCATE( receive_dum_h )
785       DEALLOCATE( receive_dum_v )
786!
787!--    Allocate index arrays which link facade elements with surface-data type.
788!--    Please note, no height levels are considered here (information is stored
789!--    in surface-data type itself).
790       IF ( buildings(nb)%on_pe )  THEN
791!
792!--       Determine number of facade elements per building.
793          buildings(nb)%num_facades_per_building_h = SUM( buildings(nb)%num_facade_h )
794          buildings(nb)%num_facades_per_building_v = SUM( buildings(nb)%num_facade_v )
795!
796!--       Allocate arrays which link the building with the horizontal and vertical
797!--       urban-type surfaces. Please note, linking arrays are allocated over all
798!--       facade elements, which is required in case a building is located at the
799!--       subdomain boundaries, where the building and the corresponding surface
800!--       elements are located on different subdomains.
801          ALLOCATE( buildings(nb)%m_h(1:buildings(nb)%num_facades_per_building_h_l) )
802
803          ALLOCATE( buildings(nb)%l_v(1:buildings(nb)%num_facades_per_building_v_l) )
804          ALLOCATE( buildings(nb)%m_v(1:buildings(nb)%num_facades_per_building_v_l) )
805       ENDIF
806!
807!--    Determine volume per facade element (vpf)
808       IF ( buildings(nb)%on_pe )  THEN
809          ALLOCATE( buildings(nb)%vpf(buildings(nb)%kb_min:buildings(nb)%kb_max) )
810         
811          DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
812             buildings(nb)%vpf(k) = buildings(nb)%volume(k) /                  &
813                                    ( buildings(nb)%num_facade_h(k) +          &
814                                      buildings(nb)%num_facade_v(k) )
815          ENDDO
816       ENDIF
817    ENDDO
818!
819!-- Link facade elements with surface data type.
820!-- Allocate array for counting.
821    ALLOCATE( n_fa(1:num_build) )
822    n_fa = 1
823
824    DO  m = 1, surf_usm_h%ns
825       i = surf_usm_h%i(m) + surf_usm_h%ioff
826       j = surf_usm_h%j(m) + surf_usm_h%joff
827
828       nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM = 1 )
829
830       IF ( buildings(nb)%on_pe )  THEN
831          buildings(nb)%m_h(n_fa(nb)) = m
832          n_fa(nb) = n_fa(nb) + 1 
833       ENDIF
834    ENDDO
835
836    n_fa = 1
837    DO  l = 0, 3
838       DO  m = 1, surf_usm_v(l)%ns
839          i = surf_usm_v(l)%i(m) + surf_usm_v(l)%ioff
840          j = surf_usm_v(l)%j(m) + surf_usm_v(l)%joff
841
842          nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM = 1 )
843
844          IF ( buildings(nb)%on_pe )  THEN
845             buildings(nb)%l_v(n_fa(nb)) = l
846             buildings(nb)%m_v(n_fa(nb)) = m
847             n_fa(nb) = n_fa(nb) + 1   
848          ENDIF
849       ENDDO
850    ENDDO
851    DEALLOCATE( n_fa )
852
853!
854!-- Initialize building parameters, first by mean building type. Note,
855!-- in this case all buildings have the same type.
856!-- In a second step initialize with building tpyes from static input file,
857!-- where building types can be individual for each building.
858    buildings(:)%lambda_layer3    = building_pars(63,building_type)
859    buildings(:)%s_layer3         = building_pars(57,building_type)
860    buildings(:)%f_c_win          = building_pars(119,building_type)
861    buildings(:)%g_value_win      = building_pars(120,building_type)   
862    buildings(:)%u_value_win      = building_pars(121,building_type)   
863    buildings(:)%air_change_low   = building_pars(122,building_type)   
864    buildings(:)%air_change_high  = building_pars(123,building_type)   
865    buildings(:)%eta_ve           = building_pars(124,building_type)   
866    buildings(:)%factor_a         = building_pars(125,building_type)   
867    buildings(:)%factor_c         = building_pars(126,building_type)
868    buildings(:)%lambda_at        = building_pars(127,building_type)   
869    buildings(:)%theta_int_h_set  = building_pars(118,building_type)   
870    buildings(:)%theta_int_c_set  = building_pars(117,building_type)
871    buildings(:)%phi_h_max        = building_pars(128,building_type)   
872    buildings(:)%phi_c_max        = building_pars(129,building_type)         
873    buildings(:)%qint_high        = building_pars(130,building_type)
874    buildings(:)%qint_low         = building_pars(131,building_type)
875    buildings(:)%height_storey    = building_pars(132,building_type)
876    buildings(:)%height_cei_con   = building_pars(133,building_type)
877!
878!-- Initialize ventilaation load. Please note, building types > 7 are actually
879!-- not allowed (check already in urban_surface_mod and netcdf_data_input_mod.
880!-- However, the building data base may be later extended.
881    IF ( building_type ==  1  .OR.  building_type ==  2  .OR.                  &
882         building_type ==  3  .OR.  building_type == 10  .OR.                  &
883         building_type == 11  .OR.  building_type == 12 )  THEN
884       buildings(nb)%ventilation_int_loads = 1
885!
886!-- Office, building with large windows
887    ELSEIF ( building_type ==  4  .OR.  building_type ==  5  .OR.              &
888             building_type ==  6  .OR.  building_type ==  7  .OR.              &
889             building_type ==  8  .OR.  building_type ==  9)  THEN
890       buildings(nb)%ventilation_int_loads = 2
891!
892!-- Industry, hospitals
893    ELSEIF ( building_type == 13  .OR.  building_type == 14  .OR.              &
894             building_type == 15  .OR.  building_type == 16  .OR.              &
895             building_type == 17  .OR.  building_type == 18 )  THEN
896       buildings(nb)%ventilation_int_loads = 3
897    ENDIF
898!
899!-- Initialization of building parameters - level 2
900    IF ( building_type_f%from_file )  THEN
901       DO  i = nxl, nxr
902          DO  j = nys, nyn
903              IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
904                 nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ),    &
905                              DIM = 1 )
906                 bt = building_type_f%var(j,i)
907                 
908                 buildings(nb)%lambda_layer3    = building_pars(63,bt)
909                 buildings(nb)%s_layer3         = building_pars(57,bt)
910                 buildings(nb)%f_c_win          = building_pars(119,bt)
911                 buildings(nb)%g_value_win      = building_pars(120,bt)   
912                 buildings(nb)%u_value_win      = building_pars(121,bt)   
913                 buildings(nb)%air_change_low   = building_pars(122,bt)   
914                 buildings(nb)%air_change_high  = building_pars(123,bt)   
915                 buildings(nb)%eta_ve           = building_pars(124,bt)   
916                 buildings(nb)%factor_a         = building_pars(125,bt)   
917                 buildings(nb)%factor_c         = building_pars(126,bt)
918                 buildings(nb)%lambda_at        = building_pars(127,bt)   
919                 buildings(nb)%theta_int_h_set  = building_pars(118,bt)   
920                 buildings(nb)%theta_int_c_set  = building_pars(117,bt)
921                 buildings(nb)%phi_h_max        = building_pars(128,bt)   
922                 buildings(nb)%phi_c_max        = building_pars(129,bt)         
923                 buildings(nb)%qint_high        = building_pars(130,bt)
924                 buildings(nb)%qint_low         = building_pars(131,bt)
925                 buildings(nb)%height_storey    = building_pars(132,bt)
926                 buildings(nb)%height_cei_con   = building_pars(133,bt)                 
927!
928!--              Initialize ventilaation load. Please note, building types > 7
929!--              are actually not allowed (check already in urban_surface_mod 
930!--              and netcdf_data_input_mod. However, the building data base may
931!--              be later extended.
932                 IF ( bt ==  1  .OR.  bt ==  2  .OR.                           &
933                      bt ==  3  .OR.  bt == 10  .OR.                           &
934                      bt == 11  .OR.  bt == 12 )  THEN
935                    buildings(nb)%ventilation_int_loads = 1
936!                   
937!--              Office, building with large windows
938                 ELSEIF ( bt ==  4  .OR.  bt ==  5  .OR.                       &
939                          bt ==  6  .OR.  bt ==  7  .OR.                       &
940                          bt ==  8  .OR.  bt ==  9)  THEN
941                    buildings(nb)%ventilation_int_loads = 2
942!
943!--              Industry, hospitals
944                 ELSEIF ( bt == 13  .OR.  bt == 14  .OR.                       &
945                          bt == 15  .OR.  bt == 16  .OR.                       &
946                          bt == 17  .OR.  bt == 18 )  THEN
947                    buildings(nb)%ventilation_int_loads = 3
948                 ENDIF
949              ENDIF
950           ENDDO
951        ENDDO
952    ENDIF
953!
954!-- Initial room temperature [K]
955!-- (after first loop, use theta_m_t as theta_m_t_prev)
956    theta_m_t_prev = initial_indoor_temperature
957!
958!-- Initialize indoor temperature. Actually only for output at initial state.
959    DO  nb = 1, num_build
960       buildings(nb)%t_in(:) = initial_indoor_temperature
961    ENDDO
962
963    CALL location_message( 'finished', .TRUE. )
964
965 END SUBROUTINE im_init
966
967
968!------------------------------------------------------------------------------!
969! Description:
970! ------------
971!> Main part of the indoor model.
972!> Calculation of .... (kanani: Please describe)
973!------------------------------------------------------------------------------!
974 SUBROUTINE im_main_heatcool
975
976    USE arrays_3d,                                                             &
977        ONLY:  ddzw, dzw
978
979    USE date_and_time_mod,                                                     &
980        ONLY:  time_utc
981
982    USE grid_variables,                                                        &
983        ONLY:  dx, dy
984
985    USE pegrid
986   
987    USE surface_mod,                                                           &
988        ONLY:  ind_veg_wall, ind_wat_win, surf_usm_h, surf_usm_v
989
990    USE urban_surface_mod,                                                     &
991        ONLY:  nzt_wall, t_wall_h, t_wall_v, t_window_h, t_window_v,           &
992               building_type
993
994
995    IMPLICIT NONE
996
997    INTEGER(iwp) ::  i    !< index of facade-adjacent atmosphere grid point in x-direction
998    INTEGER(iwp) ::  j    !< index of facade-adjacent atmosphere grid point in y-direction
999    INTEGER(iwp) ::  k    !< index of facade-adjacent atmosphere grid point in z-direction
1000    INTEGER(iwp) ::  kk   !< vertical index of indoor grid point adjacent to facade
1001    INTEGER(iwp) ::  l    !< running index for surface-element orientation
1002    INTEGER(iwp) ::  m    !< running index surface elements
1003    INTEGER(iwp) ::  nb   !< running index for buildings
1004    INTEGER(iwp) ::  fa   !< running index for facade elements of each building
1005
1006    REAL(wp) ::  indoor_wall_window_temperature   !< weighted temperature of innermost wall/window layer
1007    REAL(wp) ::  near_facade_temperature          !< outside air temperature 10cm away from facade
1008    REAL(wp) ::  time_utc_hour                    !< time of day (hour UTC)
1009
1010    REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in_l_send   !< dummy send buffer used for summing-up indoor temperature per kk-level
1011    REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in_recv     !< dummy recv buffer used for summing-up indoor temperature per kk-level
1012!
1013!-- Determine time of day in hours.
1014    time_utc_hour = time_utc / 3600.0_wp
1015!
1016!-- Following calculations must be done for each facade element.
1017    DO  nb = 1, num_build
1018!
1019!--    First, check whether building is present on local subdomain.
1020       IF ( buildings(nb)%on_pe )  THEN
1021!
1022!--       Determine daily schedule. 08:00-18:00 = 1, other hours = 0.
1023!--       Residental Building, panel WBS 70   
1024          IF ( buildings(nb)%ventilation_int_loads == 1 )  THEN
1025             IF ( time_utc_hour >= 6.0_wp  .AND.  time_utc_hour <= 8.0_wp )  THEN
1026                schedule_d = 1
1027             ELSEIF ( time_utc_hour >= 18.0_wp  .AND.  time_utc_hour <= 23.0_wp )  THEN
1028                schedule_d = 1
1029             ELSE
1030                schedule_d = 0
1031             ENDIF
1032          ENDIF
1033!
1034!--       Office, building with large windows
1035          IF ( buildings(nb)%ventilation_int_loads == 2 )  THEN
1036             IF ( time_utc_hour >= 8.0_wp  .AND.  time_utc_hour <= 18.0_wp )  THEN
1037                schedule_d = 1
1038             ELSE
1039                schedule_d = 0
1040             ENDIF
1041          ENDIF
1042!       
1043!--       Industry, hospitals
1044          IF ( buildings(nb)%ventilation_int_loads == 3 )  THEN
1045             IF ( time_utc_hour >= 6.0_wp  .AND.  time_utc_hour <= 22.0_wp )  THEN
1046                schedule_d = 1
1047             ELSE
1048                schedule_d = 0
1049             ENDIF
1050          ENDIF
1051!
1052!--       Initialize/reset indoor temperature
1053          buildings(nb)%t_in_l = 0.0_wp 
1054!
1055!--       Horizontal surfaces
1056          DO  fa = 1, buildings(nb)%num_facades_per_building_h_l
1057!
1058!--          Determine index where corresponding surface-type information
1059!--          is stored.
1060             m = buildings(nb)%m_h(fa)
1061!
1062!--          Determine building height level index.
1063             kk = surf_usm_h%k(m) + surf_usm_h%koff
1064!           
1065!--          Building geometries --> not time-dependent
1066             facade_element_area      = dx * dy                             !< [m2] surface area per facade element   
1067             floor_area_per_facade    = buildings(nb)%vpf(kk) * ddzw(kk)    !< [m2] net floor area per facade element       
1068             indoor_volume_per_facade = buildings(nb)%vpf(kk)               !< [m3] indoor air volume per facade element           
1069             window_area_per_facade   = surf_usm_h%frac(ind_wat_win,m)  * facade_element_area  !< [m2] window area per facade element
1070             
1071! print*, "building_height", building_height
1072! print*, "num_facades_v_l", buildings(nb)%num_facades_per_building_v_l
1073! print*, "num_facades_v", buildings(nb)%num_facades_per_building_v
1074! print*, "kb_min_max", buildings(nb)%kb_min, buildings(nb)%kb_max
1075! print*, "dzw kk", dzw(kk), kk
1076
1077             f_cei                    = buildings(nb)%building_height /        &
1078                                       (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             f_cei                    = buildings(nb)%building_height /        &
1275                                        (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       IF ( ALLOCATED( buildings(nb)%t_in ) )                                  &
1482          buildings(nb)%t_in = buildings(nb)%t_in_l
1483#endif
1484       IF ( ALLOCATED( buildings(nb)%t_in ) )                                  &
1485          buildings(nb)%t_in =   buildings(nb)%t_in /                          &
1486                               ( buildings(nb)%num_facade_h +                  &
1487                                 buildings(nb)%num_facade_v )
1488!
1489!--    Deallocate dummy arrays
1490       DEALLOCATE( t_in_l_send )
1491       DEALLOCATE( t_in_recv )
1492
1493    ENDDO
1494
1495
1496 END SUBROUTINE im_main_heatcool
1497
1498!-----------------------------------------------------------------------------!
1499! Description:
1500!-------------
1501!> Check data output for plant canopy model
1502!-----------------------------------------------------------------------------!
1503 SUBROUTINE im_check_data_output( var, unit )
1504       
1505    IMPLICIT NONE
1506   
1507    CHARACTER (LEN=*) ::  unit   !<
1508    CHARACTER (LEN=*) ::  var    !<
1509       
1510    SELECT CASE ( TRIM( var ) )
1511   
1512   
1513        CASE ( 'im_hf_roof')
1514           unit = 'W m-2'
1515       
1516        CASE ( 'im_hf_wall_win' )
1517           unit = 'W m-2'
1518           
1519        CASE ( 'im_hf_wall_win_waste' )
1520           unit = 'W m-2'
1521           
1522        CASE ( 'im_hf_roof_waste' )
1523           unit = 'W m-2'
1524       
1525        CASE ( 'im_t_indoor' )
1526           unit = 'K'
1527       
1528        CASE DEFAULT
1529           unit = 'illegal'
1530           
1531    END SELECT
1532   
1533 END SUBROUTINE
1534
1535
1536!-----------------------------------------------------------------------------!
1537! Description:
1538!-------------
1539!> Check parameters routine for plant canopy model
1540!-----------------------------------------------------------------------------!
1541 SUBROUTINE im_check_parameters
1542
1543!!!!   USE control_parameters,
1544!!!!       ONLY: message_string
1545       
1546   IMPLICIT NONE
1547   
1548 END SUBROUTINE im_check_parameters
1549
1550!-----------------------------------------------------------------------------!
1551! Description:
1552!-------------
1553!> Subroutine defining appropriate grid for netcdf variables.
1554!> It is called from subroutine netcdf.
1555!-----------------------------------------------------------------------------!
1556 SUBROUTINE im_define_netcdf_grid( var, found, grid_x, grid_y, grid_z )
1557
1558   IMPLICIT NONE
1559   
1560   CHARACTER (LEN=*), INTENT(IN)  ::  var
1561   LOGICAL, INTENT(OUT)           ::  found
1562   CHARACTER (LEN=*), INTENT(OUT) ::  grid_x
1563   CHARACTER (LEN=*), INTENT(OUT) ::  grid_y
1564   CHARACTER (LEN=*), INTENT(OUT) ::  grid_z
1565   
1566   found   = .TRUE.
1567   
1568!
1569!-- Check for the grid
1570    SELECT CASE ( TRIM( var ) )
1571
1572       CASE ( 'im_hf_roof', 'im_hf_roof_waste' )
1573          grid_x = 'x'
1574          grid_y = 'y'
1575          grid_z = 'zw'
1576!
1577!--    Heat fluxes at vertical walls are actually defined on stagged grid, i.e. xu, yv.
1578       CASE ( 'im_hf_wall_win', 'im_hf_wall_win_waste' )
1579          grid_x = 'x'
1580          grid_y = 'y'
1581          grid_z = 'zu'
1582         
1583       CASE ( 'im_t_indoor' )
1584          grid_x = 'x'
1585          grid_y = 'y'
1586          grid_z = 'zw'
1587         
1588       CASE DEFAULT
1589          found  = .FALSE.
1590          grid_x = 'none'
1591          grid_y = 'none'
1592          grid_z = 'none'
1593    END SELECT
1594   
1595 END SUBROUTINE im_define_netcdf_grid
1596
1597!------------------------------------------------------------------------------!
1598! Description:
1599! ------------
1600!> Subroutine defining 3D output variables
1601!------------------------------------------------------------------------------!
1602 SUBROUTINE im_data_output_3d( av, variable, found, local_pf, fill_value,      &
1603                               nzb_do, nzt_do )
1604
1605   USE indices
1606   
1607   USE kinds
1608         
1609   IMPLICIT NONE
1610   
1611    CHARACTER (LEN=*) ::  variable !<
1612
1613    INTEGER(iwp) ::  av    !<
1614    INTEGER(iwp) ::  i     !<
1615    INTEGER(iwp) ::  j     !<
1616    INTEGER(iwp) ::  k     !<
1617    INTEGER(iwp) ::  l     !<
1618    INTEGER(iwp) ::  m     !<
1619    INTEGER(iwp) ::  nb    !< index of the building in the building data structure
1620    INTEGER(iwp) ::  nzb_do !< lower limit of the data output (usually 0)
1621    INTEGER(iwp) ::  nzt_do !< vertical upper limit of the data output (usually nz_do3d)
1622
1623   
1624    LOGICAL      ::  found !<
1625
1626    REAL(wp), INTENT(IN) ::  fill_value !< value for the _FillValue attribute
1627
1628    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
1629   
1630    local_pf = fill_value
1631   
1632    found = .TRUE.
1633   
1634    SELECT CASE ( TRIM( variable ) )
1635!
1636!--     Output of indoor temperature. All grid points within the building are
1637!--     filled with values, while atmospheric grid points are set to _FillValues.
1638        CASE ( 'im_t_indoor' )
1639           IF ( av == 0 ) THEN
1640              DO  i = nxl, nxr
1641                 DO  j = nys, nyn
1642                    IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
1643!
1644!--                    Determine index of the building within the building data structure.
1645                       nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ),   &
1646                                    DIM = 1 )
1647                       IF ( buildings(nb)%on_pe )  THEN
1648!
1649!--                       Write mean building temperature onto output array. Please note,
1650!--                       in contrast to many other loops in the output, the vertical
1651!--                       bounds are determined by the lowest and hightest vertical index
1652!--                       occupied by the building.
1653                          DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
1654                             local_pf(i,j,k) = buildings(nb)%t_in(k)
1655                          ENDDO
1656                       ENDIF
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.