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

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

Change order of dimension in surface arrays %frac, %emissivity and %albedo to allow for better vectorization in the radiation interactions; Set back turbulent length scale to 8 x grid spacing in the parametrized mode for the synthetic turbulence generator (was accidentally changed in last commit)

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