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

Last change on this file since 4403 was 4402, checked in by suehring, 4 years ago

Indoor model: major bugfix in calculation of energy demand - floor-area-per-facade was wrongly calculated leading to unrealistically high energy demands and thus to unreallistically high waste-heat fluxes.

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