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

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

Indoor model: revision of some parameters and implementation of seasonal-dependent parameters

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