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

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

Output of indoor temperature revised (to avoid non-defined values within buildings)

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