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

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

Building data base: Indoor-model parameters for some building types adjusted in order to avoid unrealistically high indoor temperatures (S. Rissmann); Indoor model: Bugfix in determination of minimum facade height and in location message, avoid divisions by zero, minor optimizations; radiation model: Modify check in order to avoid equality comparisons of floating points

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