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

Last change on this file since 4313 was 4310, checked in by suehring, 4 years ago

Remove dt_indoor from namelist input. The indoor model is an hourly-based model, calling it more/less often lead to inaccurate results.

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