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

Last change on this file since 4145 was 4144, checked in by raasch, 5 years ago

relational operators .EQ., .NE., etc. replaced by ==, /=, etc.

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