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

Last change on this file since 4255 was 4246, checked in by pavelkrc, 5 years ago

Convert CRLF line endings to LF

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