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

Last change on this file since 3593 was 3593, checked in by kanani, 5 years ago

Bugfix for missing array allocation (biometeorology_mod), remove degree symbol (biometeorology_mod, indoor_model_mod, multi_agent_system_mod, surface_mod, wind_turbine_model_mod)

  • Property svn:keywords set to Id
File size: 69.7 KB
RevLine 
[3469]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-2018 Leibniz Universitaet Hannover
18! Copyright 2018-2018 Hochschule Offenburg
19!--------------------------------------------------------------------------------!
20!
21! Current revisions:
22! -----------------
23!
24!
25! Former revisions:
26! -----------------
27! $Id: indoor_model_mod.f90 3593 2018-12-03 13:51:13Z kanani $
[3593]28! Replace degree symbol by degree_C
29!
30! 3524 2018-11-14 13:36:44Z raasch
[3524]31! working precision added to make code Fortran 2008 conform
32!
33! 3469 2018-10-30 20:05:07Z kanani
[3469]34! Initial revision (tlang, suehring, kanani, srissman)
35!
36!
37!
38! Authors:
39! --------
40! @author Tobias Lang
41! @author Jens Pfafferott
42! @author Farah Kanani-Suehring
43! @author Matthias Suehring
44! @author Sascha Rißmann
45!
46!
47! Description:
48! ------------
49!> <Description of the new module>
50!> Module for Indoor Climate Model (ICM)
51!> The module is based on the DIN EN ISO 13790 with simplified hour-based procedure.
52!> This model is a equivalent circuit diagram of a three-point RC-model (5R1C).
53!> This module differ between indoor-air temperature an average temperature of indoor surfaces which make it prossible to determine thermal comfort
54!> the heat transfer between indoor and outdoor is simplified
55
56!> @todo Replace window_area_per_facade by %frac(1,m) for window
57!> @todo emissivity change for window blinds if solar_protection_on=1
58!> @todo write datas in netcdf file as output data
59!> @todo reduce the building volume with netto ground surface to take respect costruction areas like walls and ceilings. Have effect on factor_a, factor_c, airchange and lambda_at
60!>
61!> @note Do we allow use of integer flags, or only logical flags? (concerns e.g. cooling_on, heating_on)
62!> @note How to write indoor temperature output to pt array?
63!>
64!> @bug  <Enter known bugs here>
65!------------------------------------------------------------------------------!
66 MODULE indoor_model_mod 
67
68    USE control_parameters,                                                    &
69        ONLY:  initializing_actions
70
71    USE kinds
72
73    USE surface_mod,                                                           &
74        ONLY:  surf_usm_h, surf_usm_v
75
76
77    IMPLICIT NONE
78
79!
80!-- Define data structure for buidlings.
81    TYPE build
82
83       INTEGER(iwp) ::  id                             !< building ID
84       INTEGER(iwp) ::  kb_min                         !< lowest vertical index of a building
85       INTEGER(iwp) ::  kb_max                         !< highest vertical index of a building
86       INTEGER(iwp) ::  num_facades_per_building_h     !< total number of horizontal facades elements
87       INTEGER(iwp) ::  num_facades_per_building_h_l   !< number of horizontal facade elements on local subdomain
88       INTEGER(iwp) ::  num_facades_per_building_v     !< total number of vertical facades elements
89       INTEGER(iwp) ::  num_facades_per_building_v_l   !< number of vertical facade elements on local subdomain
90
91       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  l_v            !< index array linking surface-element orientation index
92                                                                  !< for vertical surfaces with building
93       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  m_h            !< index array linking surface-element index for
94                                                                  !< horizontal surfaces with building
95       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  m_v            !< index array linking surface-element index for
96                                                                  !< vertical surfaces with building
97       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facade_h   !< number of horizontal facade elements per buidling
98                                                                  !< and height level
99       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facade_v   !< number of vertical facades elements per buidling
100                                                                  !< and height level
101
102       LOGICAL ::  on_pe = .FALSE.   !< flag indicating whether a building with certain ID is on local subdomain
103
104       REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in       !< mean building indoor temperature, height dependent
105       REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in_l     !< mean building indoor temperature on local subdomain, height dependent
106       REAL(wp), DIMENSION(:), ALLOCATABLE ::  volume     !< total building volume, height dependent
107       REAL(wp), DIMENSION(:), ALLOCATABLE ::  vol_frac   !< fraction of local on total building volume, height dependent
108       REAL(wp), DIMENSION(:), ALLOCATABLE ::  vpf        !< building volume volume per facade element, height dependent
109
110    END TYPE build
111
112    TYPE(build), DIMENSION(:), ALLOCATABLE ::  buildings   !< building array
113
114    INTEGER(iwp) ::  num_build   !< total number of buildings in domain
115
116    REAL(wp) ::  volume_fraction
117
118    REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in     !< dummy array for indoor temperature for the
119                                                     !< total building volume at each discrete height level
120    REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in_l   !< dummy array for indoor temperature for the
121                                                     !< local building volume fraction at each discrete height level
122
123!
124!-- Declare all global variables within the module
125
126    INTEGER(iwp) ::  building_type = 1       !< namelist parameter with
127                                             !< X1=construction year (cy) 1950, X2=cy 2000, X3=cy 2050
128                                             !< R=Residental building, O=Office, RW=Enlarged Windows, P=Panel type (Plattenbau) WBS 70, H=Hospital (in progress), I=Industrial halls (in progress), S=Special Building (in progress)
129                                             !< (0=R1, 1=R2, 2=R3, 3=O1, 4=O2, 5=O3,...)
130    INTEGER(iwp) ::  cooling_on              !< Indoor cooling flag (0=off, 1=on)
131    INTEGER(iwp) ::  heating_on              !< Indoor heating flag (0=off, 1=on)
132    INTEGER(iwp) ::  solar_protection_off    !< Solar protection off
133    INTEGER(iwp) ::  solar_protection_on     !< Solar protection on
134
135    REAL(wp) ::  air_change_high             !< [1/h] air changes per time_utc_hour
136    REAL(wp) ::  air_change_low              !< [1/h] air changes per time_utc_hour
137    REAL(wp) ::  eff_mass_area               !< [m²] the effective mass-related area
138    REAL(wp) ::  floor_area_per_facade       !< [m²] net floor area (Sum of all floors)
139    REAL(wp) ::  total_area                  !<! [m²] area of all surfaces pointing to zone
140    REAL(wp) ::  window_area_per_facade      !< [m2] window area per facade element
141    REAL(wp) ::  air_change                  !< [1/h] Airflow
142    REAL(wp) ::  bldg_part_surf_i    = 4     !< [m²_surf,i] part building surface, from Palm, das mÃŒsste mittlerweile "facade_element_area" sein!
143    REAL(wp) ::  facade_element_area         !< [m²_facade] building surface facade
144    REAL(wp) ::  indoor_volume_per_facade    !< [m³] indoor air volume per facade element
145    REAL(wp) ::  c_m                         !< [J/K] internal heat storage capacity
146    REAL(wp) ::  dt_indoor = 3600.0_wp       !< [s] namelist parameter: time interval for indoor-model application
147    REAL(wp) ::  eta_ve                      !< [-] heat recovery efficiency
148    REAL(wp) ::  f_c_win                     !< [-] shading factor
149    REAL(wp) ::  factor_a                    !< [-] Dynamic parameters specific effective surface according to Table 12; 2.5 (very light, light and medium), 3.0 (heavy), 3.5 (very heavy)
150    REAL(wp) ::  factor_c                    !< [J/(m2 K)] Dynamic parameters inner heatstorage according to Table 12; 80000 (very light), 110000 (light), 165000 (medium), 260000 (heavy), 370000 (very heavy)
151    REAL(wp) ::  g_value_win                 !< [-] SHGC factor
152    REAL(wp) ::  h_tr_1                      !<! [W/K] Heat transfer coefficient auxiliary variable 1
153    REAL(wp) ::  h_tr_2                      !<! [W/K] Heat transfer coefficient auxiliary variable 2
154    REAL(wp) ::  h_tr_3                      !<! [W/K] Heat transfer coefficient auxiliary variable 3
155    REAL(wp) ::  h_tr_em                     !<! [W/K] Heat transfer coefficient of the emmision (got with h_tr_ms the thermal mass)
156    REAL(wp) ::  h_tr_is                     !<! [W/K] thermal coupling conductance (Thermischer Kopplungsleitwert)
157    REAL(wp) ::  h_tr_ms                     !<! [W/K] Heat transfer conductance term (got with h_tr_em the thermal mass)
158    REAL(wp) ::  h_tr_op                     !<! [W/K] heat transfer coefficient of opaque components (assumption: got all thermal mass) contains of h_tr_em and h_tr_ms
159    REAL(wp) ::  h_tr_w                      !<! [W/K] heat transfer coefficient of doors, windows, curtain walls and glazed walls (assumption: thermal mass=0)
160    REAL(wp) ::  h_ve                        !<! [W/K] heat transfer of ventilation
161    REAL(wp) ::  height_storey               !< [m] storey heigth
162    REAL(wp) ::  height_cei_con              !< [m] ceiling construction heigth   
163    REAL(wp) ::  initial_indoor_temperature  !< namelist parameter
164    REAL(wp) ::  lambda_at                   !< [-] ratio internal surface/floor area chap. 7.2.2.2.
165    REAL(wp) ::  lambda_layer3               !< [W/(m*K)] Thermal conductivity of the inner layer 
166    REAL(wp) ::  net_sw_in                   !< net short-wave radiation (in - out; was i_global --> CORRECT?)
167    REAL(wp) ::  qint_high                   !< [W/m2] internal heat gains, option Database qint_0-23
168    REAL(wp) ::  qint_low                    !< [W/m2] internal heat gains, option Database qint_0-23
169    REAL(wp) ::  phi_c_max                   !< [W] Max. Cooling capacity (negative)
170    REAL(wp) ::  phi_h_max                   !< [W] Max. Heating capacity (negative)
171    REAL(wp) ::  phi_hc_nd                   !<! [W] heating demand and/or cooling demand
172    REAL(wp) ::  phi_hc_nd_10                !<! [W] heating demand and/or cooling demand for heating or cooling
173    REAL(wp) ::  phi_hc_nd_ac                !<! [W] actual heating demand and/or cooling demand
174    REAL(wp) ::  phi_hc_nd_un                !<! [W] unlimited heating demand and/or cooling demand which is necessary to reach the demanded required temperature (heating is positive, cooling is negative)
175    REAL(wp) ::  phi_ia                      !< [W] internal air load = internal loads * 0.5, Eq. (C.1)
176    REAL(wp) ::  phi_m                       !<! [W] mass specific thermal load (internal and external)
177    REAL(wp) ::  phi_mtot                    !<! [W] total mass specific thermal load (internal and external)
178    REAL(wp) ::  phi_sol                     !< [W] solar loads
179    REAL(wp) ::  phi_st                      !<! [W] mass specific thermal load implied non thermal mass
180    REAL(wp) ::  q_emission                  !< emissions, in first version = 0, option for second part of the project
181    REAL(wp) ::  q_wall_win               !< heat flux from indoor into wall/window
182    REAL(wp) ::  q_waste_heat                !< waste heat, sum of waste heat over the roof to Palm
183    REAL(wp) ::  q_waste_heat_bldg           !< [W/building] waste heat of the complete building, in Palm sum of all indoor_model-calculations
184    REAL(wp) ::  s_layer3                    !< [m] half thickness of the inner layer (layer_3)
185    REAL(wp) ::  schedule_d                  !< activation for internal loads (low or high + low)
186    REAL(wp) ::  skip_time_do_indoor = 0.0_wp  !< [s] Indoor model is not called before this time
[3593]187    REAL(wp) ::  theta_air                   !<! [degree_C] air temperature of the RC-node
188    REAL(wp) ::  theta_air_0                 !<! [degree_C] air temperature of the RC-node in equilibrium
189    REAL(wp) ::  theta_air_10                !<! [degree_C] air temperature of the RC-node from a heating capacity of 10 W/m²
190    REAL(wp) ::  theta_air_ac                !< [degree_C] actual room temperature after heating/cooling
191    REAL(wp) ::  theta_air_set               !< [degree_C] Setpoint_temperature for the room
192    REAL(wp) ::  theta_int_c_set             !< [degree_C] Max. Setpoint temperature (summer)
193    REAL(wp) ::  theta_int_h_set             !< [degree_C] Max. Setpoint temperature (winter)
194    REAL(wp) ::  theta_m                     !<! [degree_C} inner temperature of the RC-node
195    REAL(wp) ::  theta_m_t                   !<! [degree_C] (Fictive) component temperature timestep
196    REAL(wp) ::  theta_m_t_prev              !< [degree_C] (Fictive) component temperature previous timestep (do not change)
197    REAL(wp) ::  theta_op                    !< [degree_C] operative temperature
198    REAL(wp) ::  theta_s                     !<! [degree_C] surface temperature of the RC-node
[3469]199    REAL(wp) ::  time_indoor = 0.0_wp        !< [s] time since last call of indoor model
200    REAL(wp) ::  time_utc_hour               !< Time in hours per day (UTC)
201    REAL(wp) ::  u_value_win                 !< [W/(m2*K)] transmittance
202    REAL(wp) ::  ventilation_int_loads       !< Zuteilung der GebÀude fÃŒr Verlauf/AktivitÀt der LÃŒftung und internen Lasten
203
204!
205!-- Declare all global parameters within the module   
206    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
207    REAL(wp), PARAMETER ::  params_f_w               = 0.9_wp      !< [-] correction factor (fuer nicht senkrechten Stahlungseinfall DIN 4108-2 chap.8, (hier konstant, keine WinkelabhÀngigkeit)
208    REAL(wp), PARAMETER ::  params_f_win             = 0.5_wp      !< [-] proportion of window area, Database A_win aus Datenbank 27 window_area_per_facade_percent
209    REAL(wp), PARAMETER ::  params_solar_protection  = 300.0_wp    !< [W/m2] chap. G.5.3.1 sun protection closed, if the radiation on facade exceeds this value
210    REAL(wp), PARAMETER ::  params_waste_heat_c      = 4.0_wp      !< [-] anthropogenic heat outputs for cooling e.g. 4 for KKM with COP = 3
211    REAL(wp), PARAMETER ::  params_waste_heat_h      = 1.111_wp    !< [-] anthropogenic heat outputs for heating e.g. 1 / 0.9 = 1.111111 for combustion with eta = 0.9 or -3 for WP with COP = 4
212    REAL(wp), PARAMETER ::  h_is                     = 3.45_wp     !< [W/(m^2 K)]  h_is = 3.45 between surface and air (chap. 7.2.2.2)
213    REAL(wp), PARAMETER ::  h_ms                     = 9.1_wp      !< [W/K] h_ms = 9.10 W / (m2 K) between component and surface (chap. 12.2.2)
214 
215    SAVE
216
217
218    PRIVATE
219   
220!
221!-- Add INTERFACES that must be available to other modules
222    PUBLIC im_init, im_main_heatcool, im_parin 
223
224!
225!-- Add VARIABLES that must be available to other modules
226    PUBLIC dt_indoor, skip_time_do_indoor, time_indoor
227
228!
229!-- Calculations for indoor temperatures 
230    INTERFACE im_calc_temperatures
231       MODULE PROCEDURE im_calc_temperatures
232    END INTERFACE im_calc_temperatures
233!
234!-- Initialization actions 
235    INTERFACE im_init
236       MODULE PROCEDURE im_init
237    END INTERFACE im_init
238 
239!
240!-- Main part of indoor model 
241    INTERFACE im_main_heatcool
242       MODULE PROCEDURE im_main_heatcool
243    END INTERFACE im_main_heatcool
244!
245!-- Reading of NAMELIST parameters
246    INTERFACE im_parin
247       MODULE PROCEDURE im_parin
248    END INTERFACE im_parin
249
250 CONTAINS
251
252!------------------------------------------------------------------------------!
253! Description:
254! ------------
255!< Calculation of the air temperatures and mean radiation temperature
256!< This is basis for the operative temperature
257!< Based on a Crank-Nicholson scheme with a timestep of a hour
258!------------------------------------------------------------------------------!
259 SUBROUTINE im_calc_temperatures ( i, j, k, indoor_wall_window_temperature,    &
260                                   near_facade_temperature, phi_hc_nd_dummy )
261 
262    USE arrays_3d,                                                             &
263        ONLY:  pt
264
265
266    IMPLICIT NONE
267   
268   
269    INTEGER(iwp) ::  i
270    INTEGER(iwp) ::  j
271    INTEGER(iwp) ::  k
272   
273    REAL(wp) ::  indoor_wall_window_temperature  !< weighted temperature of innermost wall/window layer
274    REAL(wp) ::  near_facade_temperature
275    REAL(wp) ::  phi_hc_nd_dummy
276
277    !< Calculation of total mass specific thermal load (internal and external)
278    phi_mtot = ( phi_m + h_tr_em * indoor_wall_window_temperature              &
279                       + h_tr_3  * ( phi_st + h_tr_w * pt(k,j,i)               &
280                                            + h_tr_1 *                         &
281                                               ( ( ( phi_ia + phi_hc_nd_dummy ) / h_ve )  &
282                                                 + near_facade_temperature )   &
283                                   ) / h_tr_2                                  &
[3593]284               )                                                                !< [degree_C] Eq. (C.5)
[3469]285   
286    !< Calculation of component temperature at factual timestep
287    theta_m_t = ( ( theta_m_t_prev                                               &
288                    * ( ( c_m / 3600 ) - 0.5 * ( h_tr_3 + h_tr_em ) ) + phi_mtot &
289                  )                                                              &
290                  /   ( ( c_m / 3600 ) + 0.5 * ( h_tr_3 + h_tr_em ) )            &
[3593]291                )                                                               !< [degree_C] Eq. (C.4)
[3469]292
293    !< Calculation of mean inner temperature for the RC-node in actual timestep
[3593]294    theta_m = ( theta_m_t + theta_m_t_prev ) * 0.5                              !< [degree_C] Eq. (C.9)
[3469]295   
296    !< Calculation of mean surface temperature of the RC-node in actual timestep
297    theta_s = ( (   h_tr_ms * theta_m + phi_st + h_tr_w * pt(k,j,i)                         &
298                  + h_tr_1  * ( near_facade_temperature + ( phi_ia + phi_hc_nd_dummy ) / h_ve ) &
299                )                                                                           &
300                / ( h_tr_ms + h_tr_w + h_tr_1 )                                             &
[3593]301              )                                                                 !< [degree_C] Eq. (C.10)
[3469]302   
303    !< Calculation of the air temperature of the RC-node
304    theta_air = ( h_tr_is * theta_s + h_ve * near_facade_temperature         &
[3593]305                                    + phi_ia + phi_hc_nd_dummy ) / ( h_tr_is + h_ve ) !< [degree_C] Eq. (C.11)
[3469]306
307 END SUBROUTINE im_calc_temperatures
308
309!------------------------------------------------------------------------------!
310! Description:
311! ------------
312!> Initialization of the indoor model.
313!> Static information are calculated here, e.g. building parameters and
314!> geometrical information, everything that doesn't change in time.
315!
316!-- Input values
317!-- Input datas from Palm, M4
318!     i_global             -->  net_sw_in                         !global radiation [W/m2]
319!     theta_e              -->  pt(k,j,i)                         !undisturbed outside temperature, 1. PALM volume, for windows
320!     theta_sup = theta_f  -->  surf_usm_h%t_surf_10cm(m)
321!                               surf_usm_v(l)%t_surf_10cm(m)   !Air temperature, facade near (10cm) air temperature from 1. Palm volume
322!     theta_node           -->  t_wall_h(nzt_wall,m)
323!                               t_wall_v(l)%t(nzt_wall,m)         !Temperature of innermost wall layer, for opaque wall
324!------------------------------------------------------------------------------!
325 SUBROUTINE im_init
326 
327    USE arrays_3d,                                                             &
328        ONLY:  dzw
329
330    USE control_parameters,                                                    &
331        ONLY:  message_string
332
333    USE indices,                                                               &
334        ONLY:  nxl, nxr, nyn, nys, nzb, nzt, wall_flags_0
335
336    USE grid_variables,                                                        &
337        ONLY:  dx, dy
338
339    USE netcdf_data_input_mod,                                                 &
340        ONLY:  building_id_f
341
342    USE pegrid
343
344    USE surface_mod,                                                           &
345        ONLY:  surf_usm_h, surf_usm_v
346       
347    USE urban_surface_mod,                                                     &
348        ONLY:  building_pars, building_type
349
350    IMPLICIT NONE
351
352    INTEGER(iwp) ::  fa   !< running index for facade elements of each building
353    INTEGER(iwp) ::  i    !< running index along x-direction
354    INTEGER(iwp) ::  j    !< running index along y-direction
355    INTEGER(iwp) ::  k    !< running index along z-direction
356    INTEGER(iwp) ::  l    !< running index for surface-element orientation
357    INTEGER(iwp) ::  m    !< running index surface elements
358    INTEGER(iwp) ::  n    !< building index
359    INTEGER(iwp) ::  nb   !< building index
360
361    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids           !< building IDs on entire model domain
362    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_final     !< building IDs on entire model domain,
363                                                                    !< multiple occurences are sorted out
364    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_final_tmp !< temporary array used for resizing
365    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_l         !< building IDs on local subdomain
366    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_l_tmp     !< temporary array used to resize array of building IDs
367    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  displace_dum        !< displacements of start addresses, used for MPI_ALLGATHERV
368    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  k_max_l             !< highest vertical index of a building on subdomain
369    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  k_min_l             !< lowest vertical index of a building on subdomain
370    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  n_fa                !< counting array
371    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facades_h       !< dummy array used for summing-up total number of
372                                                                    !< horizontal facade elements
373    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facades_v       !< dummy array used for summing-up total number of
374                                                                    !< vertical facade elements
375    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  receive_dum_h       !< dummy array used for MPI_ALLREDUCE 
376    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  receive_dum_v       !< dummy array used for MPI_ALLREDUCE 
377
378    INTEGER(iwp), DIMENSION(0:numprocs-1) ::  num_buildings         !< number of buildings with different ID on entire model domain
379    INTEGER(iwp), DIMENSION(0:numprocs-1) ::  num_buildings_l       !< number of buildings with different ID on local subdomain
380
381    REAL(wp), DIMENSION(:), ALLOCATABLE ::  local_weight   !< dummy representing fraction of local on total building volume,
382                                                           !< height dependent
383    REAL(wp), DIMENSION(:), ALLOCATABLE ::  volume         !< total building volume at each discrete height level
384    REAL(wp), DIMENSION(:), ALLOCATABLE ::  volume_l       !< total building volume at each discrete height level,
385                                                           !< on local subdomain
386
387!
388!-- Initializing of indoor model is only possible if buildings can be
389!-- distinguished by their IDs.
390    IF ( .NOT. building_id_f%from_file )  THEN
391       message_string = 'Indoor model requires information about building_id'
392       CALL message( 'im_init', 'PA0999', 1, 2, 0, 6, 0  )
393    ENDIF
394!
395!-- Determine number of different building IDs on local subdomain.
396    num_buildings_l = 0
397    num_buildings   = 0
398    ALLOCATE( build_ids_l(1) )
399    DO  i = nxl, nxr
400       DO  j = nys, nyn
401          IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
402             IF ( num_buildings_l(myid) > 0 )  THEN
403                IF ( ANY( building_id_f%var(j,i) .EQ.  build_ids_l ) )  THEN
404                   CYCLE
405                ELSE
406                   num_buildings_l(myid) = num_buildings_l(myid) + 1
407!
408!--                Resize array with different local building ids
409                   ALLOCATE( build_ids_l_tmp(1:SIZE(build_ids_l)) )
410                   build_ids_l_tmp = build_ids_l
411                   DEALLOCATE( build_ids_l )
412                   ALLOCATE( build_ids_l(1:num_buildings_l(myid)) )
413                   build_ids_l(1:num_buildings_l(myid)-1) =                 &
414                               build_ids_l_tmp(1:num_buildings_l(myid)-1)
415                   build_ids_l(num_buildings_l(myid)) = building_id_f%var(j,i)
416                   DEALLOCATE( build_ids_l_tmp )
417                ENDIF
418!
419!--          First occuring building id on PE
420             ELSE
421                num_buildings_l(myid) = num_buildings_l(myid) + 1
422                build_ids_l(1) = building_id_f%var(j,i)
423             ENDIF
424          ENDIF
425       ENDDO
426    ENDDO
427!
428!-- Determine number of building IDs for the entire domain. (Note, building IDs
429!-- can appear multiple times as buildings might be distributed over several
430!-- PEs.)
431#if defined( __parallel ) 
432    CALL MPI_ALLREDUCE( num_buildings_l, num_buildings, numprocs,              &
433                        MPI_INTEGER, MPI_SUM, comm2d, ierr ) 
434#else
435    num_buildings = num_buildings_l
436#endif
437    ALLOCATE( build_ids(1:SUM(num_buildings)) )
438!
439!-- Gather building IDs. Therefore, first, determine displacements used
440!-- required for MPI_GATHERV call.
441    ALLOCATE( displace_dum(0:numprocs-1) )
442    displace_dum(0) = 0
443    DO i = 1, numprocs-1
444       displace_dum(i) = displace_dum(i-1) + num_buildings(i-1)
445    ENDDO
446
447#if defined( __parallel ) 
448    CALL MPI_ALLGATHERV( build_ids_l(1:num_buildings_l(myid)),                 &
449                         num_buildings(myid),                                  &
450                         MPI_INTEGER,                                          &
451                         build_ids,                                            &
452                         num_buildings,                                        &
453                         displace_dum,                                         & 
454                         MPI_INTEGER,                                          &
455                         comm2d, ierr )   
456
457    DEALLOCATE( displace_dum )
458
459#else
460    build_ids = build_ids_l
461#endif
462!
463!-- Note: in parallel mode, building IDs can occur mutliple times, as
464!-- each PE has send its own ids. Therefore, sort out building IDs which
465!-- appear multiple times.
466    num_build = 0
467    DO  n = 1, SIZE(build_ids)
468
469       IF ( ALLOCATED(build_ids_final) )  THEN
470          IF ( ANY( build_ids(n) .EQ. build_ids_final ) )  THEN    !FK: Warum ANY?, Warum .EQ.? --> s.o
471             CYCLE
472          ELSE
473             num_build = num_build + 1
474!
475!--          Resize
476             ALLOCATE( build_ids_final_tmp(1:num_build) )
477             build_ids_final_tmp(1:num_build-1) = build_ids_final(1:num_build-1)
478             DEALLOCATE( build_ids_final )
479             ALLOCATE( build_ids_final(1:num_build) )
480             build_ids_final(1:num_build-1) = build_ids_final_tmp(1:num_build-1)
481             build_ids_final(num_build) = build_ids(n)
482             DEALLOCATE( build_ids_final_tmp )
483          ENDIF             
484       ELSE
485          num_build = num_build + 1
486          ALLOCATE( build_ids_final(1:num_build) )
487          build_ids_final(num_build) = build_ids(n)
488       ENDIF
489    ENDDO
490
491!
492!-- Allocate building-data structure array. Note, this is a global array
493!-- and all building IDs on domain are known by each PE. Further attributes,
494!-- e.g. height-dependent arrays, however, are only allocated on PEs where
495!-- the respective building is present (in order to reduce memory demands).
496    ALLOCATE( buildings(1:num_build) )
497!
498!-- Store building IDs and check if building with certain ID is present on
499!-- subdomain.
500    DO  nb = 1, num_build
501       buildings(nb)%id = build_ids_final(nb)
502
503       IF ( ANY( building_id_f%var == buildings(nb)%id ) )                      &
504          buildings(nb)%on_pe = .TRUE.
505    ENDDO 
506!
507!-- Determine the maximum vertical dimension occupied by each building.
508    ALLOCATE( k_min_l(1:num_build) )
509    ALLOCATE( k_max_l(1:num_build) )
510    k_min_l = nzt + 1
511    k_max_l = 0   
512
513    DO  i = nxl, nxr
514       DO  j = nys, nyn
515          IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
516             nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ),   &
517                         DIM = 1 )
518             DO  k = nzb+1, nzt+1
519!
520!--             Check if grid point belongs to a building.
521                IF ( BTEST( wall_flags_0(k,j,i), 6 ) )  THEN
522                   k_min_l(nb) = MIN( k_min_l(nb), k )
523                   k_max_l(nb) = MAX( k_max_l(nb), k )
524                ENDIF
525
526             ENDDO
527          ENDIF
528       ENDDO
529    ENDDO
530
531    DO nb = 1, num_build
532#if defined( __parallel ) 
533       CALL MPI_ALLREDUCE( k_min_l(nb), buildings(nb)%kb_min, 1, MPI_INTEGER,  &
534                           MPI_MIN, comm2d, ierr )
535       CALL MPI_ALLREDUCE( k_max_l(nb), buildings(nb)%kb_max, 1, MPI_INTEGER,  &
536                           MPI_MAX, comm2d, ierr )
537#else
538       buildings(nb)%kb_min = k_min_l(nb)
539       buildings(nb)%kb_max = k_max_l(nb)
540#endif
541
542    ENDDO 
543
544    DEALLOCATE( k_min_l )
545    DEALLOCATE( k_max_l )
546!
547!-- Calculate building volume
548    DO  nb = 1, num_build
549!
550!--    Allocate temporary array for summing-up building volume
551       ALLOCATE( volume(buildings(nb)%kb_min:buildings(nb)%kb_max)   )
552       ALLOCATE( volume_l(buildings(nb)%kb_min:buildings(nb)%kb_max) )
553       volume   = 0.0_wp
554       volume_l = 0.0_wp
555!
556!--    Calculate building volume per height level on each PE where
557!--    these building is present.
558       IF ( buildings(nb)%on_pe )  THEN
559          ALLOCATE( buildings(nb)%volume(buildings(nb)%kb_min:buildings(nb)%kb_max)   )
560          ALLOCATE( buildings(nb)%vol_frac(buildings(nb)%kb_min:buildings(nb)%kb_max) )
561          buildings(nb)%volume   = 0.0_wp
562          buildings(nb)%vol_frac = 0.0_wp
563         
564          IF ( ANY( building_id_f%var == buildings(nb)%id ) )  THEN
565             DO  i = nxl, nxr
566                DO  j = nys, nyn
567                   DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
568                      IF ( building_id_f%var(j,i) /= building_id_f%fill )      &
569                         volume_l(k) = dx * dy * dzw(k)
570                   ENDDO
571                ENDDO
572             ENDDO
573          ENDIF
574       ENDIF
575!
576!--    Sum-up building volume from all subdomains
577#if defined( __parallel ) 
578       CALL MPI_ALLREDUCE( volume_l, volume, SIZE(volume), MPI_REAL, MPI_SUM,  &
579                           comm2d, ierr )
580#else
581       volume = volume_l
582#endif
583!
584!--    Save total building volume as well as local fraction on volume on
585!--    building data structure.
586       IF ( ALLOCATED( buildings(nb)%volume ) )  buildings(nb)%volume = volume
587!
588!--    Determine fraction of local on total building volume
589       IF ( buildings(nb)%on_pe )  buildings(nb)%vol_frac = volume_l / volume
590
591       DEALLOCATE( volume   )
592       DEALLOCATE( volume_l )
593
594    ENDDO
595
596!
597!-- Allocate arrays for indoor temperature. 
598    DO  nb = 1, num_build
599       IF ( buildings(nb)%on_pe )  THEN
600          ALLOCATE( buildings(nb)%t_in(buildings(nb)%kb_min:buildings(nb)%kb_max)   )
601          ALLOCATE( buildings(nb)%t_in_l(buildings(nb)%kb_min:buildings(nb)%kb_max) )
602          buildings(nb)%t_in   = 0.0_wp
603          buildings(nb)%t_in_l = 0.0_wp
604       ENDIF
605    ENDDO
606!
607!-- Allocate arrays for number of facades per height level. Distinguish between
608!-- horizontal and vertical facades.
609    DO  nb = 1, num_build
610       IF ( buildings(nb)%on_pe )  THEN
611          ALLOCATE( buildings(nb)%num_facade_h(buildings(nb)%kb_min:buildings(nb)%kb_max) )
612          ALLOCATE( buildings(nb)%num_facade_v(buildings(nb)%kb_min:buildings(nb)%kb_max) )
613
614          buildings(nb)%num_facade_h = 0
615          buildings(nb)%num_facade_v = 0
616       ENDIF
617    ENDDO
618!
619!-- Determine number of facade elements per building on local subdomain.
620!-- Distinguish between horizontal and vertical facade elements.
621!
622!-- Horizontal facades
623    buildings(:)%num_facades_per_building_h_l = 0
624    DO  m = 1, surf_usm_h%ns
625!
626!--    For the current facade element determine corresponding building index.
627!--    First, obtain j,j,k indices of the building. Please note the
628!--    offset between facade/surface element and building location (for
629!--    horizontal surface elements the horizontal offsets are zero).
630       i = surf_usm_h%i(m) + surf_usm_h%ioff
631       j = surf_usm_h%j(m) + surf_usm_h%joff
632       k = surf_usm_h%k(m) + surf_usm_h%koff
633!
634!--    Determine building index and check whether building is on PE
635       nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM = 1 )
636       IF ( buildings(nb)%on_pe )  THEN
637!
638!--       Count number of facade elements at each height level.
639          buildings(nb)%num_facade_h(k) = buildings(nb)%num_facade_h(k) + 1 
640!
641!--       Moreover, sum up number of local facade elements per building.
642          buildings(nb)%num_facades_per_building_h_l =                         &
643                                buildings(nb)%num_facades_per_building_h_l + 1
644       ENDIF
645    ENDDO
646!
647!-- Vertical facades
648    buildings(:)%num_facades_per_building_v_l = 0
649    DO  l = 0, 3
650       DO  m = 1, surf_usm_v(l)%ns
651!
652!--       For the current facade element determine corresponding building index.
653!--       First, obtain j,j,k indices of the building. Please note the
654!--       offset between facade/surface element and building location (for
655!--       vertical surface elements the vertical offsets are zero).
656          i = surf_usm_v(l)%i(m) + surf_usm_v(l)%ioff
657          j = surf_usm_v(l)%j(m) + surf_usm_v(l)%joff
658          k = surf_usm_v(l)%k(m) + surf_usm_v(l)%koff
659
660          nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ),        &
661                       DIM = 1 )
662          IF ( buildings(nb)%on_pe )  THEN
663             buildings(nb)%num_facade_v(k) = buildings(nb)%num_facade_v(k) + 1 
664             buildings(nb)%num_facades_per_building_v_l =                      &
665                                buildings(nb)%num_facades_per_building_v_l + 1
666          ENDIF
667       ENDDO
668    ENDDO
669
670!
671!-- Determine total number of facade elements per building and assign number to
672!-- building data type.
673    DO  nb = 1, num_build
674!
675!--    Allocate dummy array used for summing-up facade elements.
676!--    Please note, dummy arguments are necessary as building-date type
677!--    arrays are not necessarily allocated on all PEs.
678       ALLOCATE( num_facades_h(buildings(nb)%kb_min:buildings(nb)%kb_max) )
679       ALLOCATE( num_facades_v(buildings(nb)%kb_min:buildings(nb)%kb_max) )
680       ALLOCATE( receive_dum_h(buildings(nb)%kb_min:buildings(nb)%kb_max) )
681       ALLOCATE( receive_dum_v(buildings(nb)%kb_min:buildings(nb)%kb_max) )
682       num_facades_h = 0
683       num_facades_v = 0
684       receive_dum_h = 0
685       receive_dum_v = 0
686
687       IF ( buildings(nb)%on_pe )  THEN
688          num_facades_h = buildings(nb)%num_facade_h
689          num_facades_v = buildings(nb)%num_facade_v
690       ENDIF
691
692#if defined( __parallel ) 
693       CALL MPI_ALLREDUCE( num_facades_h,                                      &
694                           receive_dum_h,                                      &
695                           buildings(nb)%kb_max - buildings(nb)%kb_min + 1,    &
696                           MPI_INTEGER,                                        &
697                           MPI_SUM,                                            &
698                           comm2d,                                             &
699                           ierr )
700
701       CALL MPI_ALLREDUCE( num_facades_v,                                      &
702                           receive_dum_v,                                      &
703                           buildings(nb)%kb_max - buildings(nb)%kb_min + 1,    &
704                           MPI_INTEGER,                                        &
705                           MPI_SUM,                                            &
706                           comm2d,                                             &
707                           ierr )
708       IF ( ALLOCATED( buildings(nb)%num_facade_h ) )                          &  !FK: Was wenn not allocated? --> s.o.
709           buildings(nb)%num_facade_h = receive_dum_h
710       IF ( ALLOCATED( buildings(nb)%num_facade_v ) )                          &
711           buildings(nb)%num_facade_v = receive_dum_v
712#else
713       buildings(nb)%num_facade_h = num_facades_h
714       buildings(nb)%num_facade_v = num_facades_v
715#endif
716!
717!--    Deallocate dummy arrays
718       DEALLOCATE( num_facades_h )
719       DEALLOCATE( num_facades_v )
720       DEALLOCATE( receive_dum_h )
721       DEALLOCATE( receive_dum_v )
722!
723!--    Allocate index arrays which link facade elements with surface-data type.
724!--    Please note, no height levels are considered here (information is stored
725!--    in surface-data type itself).
726       IF ( buildings(nb)%on_pe )  THEN
727!
728!--       Determine number of facade elements per building.
729          buildings(nb)%num_facades_per_building_h = SUM( buildings(nb)%num_facade_h )
730          buildings(nb)%num_facades_per_building_v = SUM( buildings(nb)%num_facade_v )
731!
732!--       Allocate arrays which link the building with the horizontal and vertical
733!--       urban-type surfaces. Please note, linking arrays are allocated over all
734!--       facade elements, which is required in case a building is located at the
735!--       subdomain boundaries, where the building and the corresponding surface
736!--       elements are located on different subdomains.
737          ALLOCATE( buildings(nb)%m_h(1:buildings(nb)%num_facades_per_building_h_l) )
738
739          ALLOCATE( buildings(nb)%l_v(1:buildings(nb)%num_facades_per_building_v_l) )
740          ALLOCATE( buildings(nb)%m_v(1:buildings(nb)%num_facades_per_building_v_l) )
741       ENDIF
742!
743!--    Determine volume per facade element (vpf)
744       IF ( buildings(nb)%on_pe )  THEN
745          ALLOCATE( buildings(nb)%vpf(buildings(nb)%kb_min:buildings(nb)%kb_max) )
746         
747          DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
748             buildings(nb)%vpf(k) = buildings(nb)%volume(k) /                  &
749                                    ( buildings(nb)%num_facade_h(k) +          &
750                                      buildings(nb)%num_facade_v(k) )
751          ENDDO
752       ENDIF
753    ENDDO
754!
755!-- Link facade elements with surface data type.
756!-- Allocate array for counting.
757    ALLOCATE( n_fa(1:num_build) )
758    n_fa = 1
759
760    DO  m = 1, surf_usm_h%ns
761       i = surf_usm_h%i(m) + surf_usm_h%ioff
762       j = surf_usm_h%j(m) + surf_usm_h%joff
763
764       nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM = 1 )
765
766       buildings(nb)%m_h(n_fa(nb)) = m
767       n_fa(nb) = n_fa(nb) + 1     
768    ENDDO
769
770    n_fa = 1
771    DO  l = 0, 3
772       DO  m = 1, surf_usm_v(l)%ns
773          i = surf_usm_v(l)%i(m) + surf_usm_v(l)%ioff
774          j = surf_usm_v(l)%j(m) + surf_usm_v(l)%joff
775
776          nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM = 1 )
777
778          buildings(nb)%l_v(n_fa(nb)) = l
779          buildings(nb)%m_v(n_fa(nb)) = m
780          n_fa(nb) = n_fa(nb) + 1     
781       ENDDO
782    ENDDO
783    DEALLOCATE( n_fa )
784
785!
786!-- Building parameters by type of building. Assigned in urban_surface_mod.f90
787
788    lambda_layer3            = building_pars(63, building_type)
789    s_layer3                 = building_pars(57, building_type)
790    f_c_win                  = building_pars(119, building_type)
791    g_value_win              = building_pars(120, building_type)   
792    u_value_win              = building_pars(121, building_type)   
793    air_change_low           = building_pars(122, building_type)   
794    air_change_high          = building_pars(123, building_type)   
795    eta_ve                   = building_pars(124, building_type)   
796    factor_a                 = building_pars(125, building_type)   
797    factor_c                 = building_pars(126, building_type)
798    lambda_at                = building_pars(127, building_type)   
799    theta_int_h_set          = building_pars(118, building_type)   
800    theta_int_c_set          = building_pars(117, building_type)
801    phi_h_max                = building_pars(128, building_type)   
802    phi_c_max                = building_pars(129, building_type)         
803    qint_high                = building_pars(130, building_type)
804    qint_low                 = building_pars(131, building_type)
805    height_storey            = building_pars(132, building_type)
806    height_cei_con           = building_pars(133, building_type)
807
808!
809!-- Setting of initial room temperature [K]
810!-- (after first loop, use theta_m_t as theta_m_t_prev)
811    theta_m_t_prev = initial_indoor_temperature
812
813
814 END SUBROUTINE im_init
815
816
817!------------------------------------------------------------------------------!
818! Description:
819! ------------
820!> Main part of the indoor model.
821!> Calculation of .... (kanani: Please describe)
822!------------------------------------------------------------------------------!
823 SUBROUTINE im_main_heatcool
824
825    USE arrays_3d,                                                             &
826        ONLY:  ddzw, dzw
827
828    USE basic_constants_and_equations_mod,                                     &
829        ONLY:  c_p
830
831    USE control_parameters,                                                    &
832        ONLY:  rho_surface
833
834    USE date_and_time_mod,                                                     &
835        ONLY:  time_utc
836
837    USE grid_variables,                                                        &
838        ONLY:  dx, dy
839
840    USE pegrid
841   
842    USE surface_mod,                                                           &
843        ONLY:  ind_veg_wall, ind_wat_win, surf_usm_h, surf_usm_v
844
845    USE urban_surface_mod,                                                     &
846        ONLY:  nzt_wall, t_surf_10cm_h, t_surf_10cm_v, t_wall_h, t_wall_v,     &
847               t_window_h, t_window_v, building_type
848
849
850    IMPLICIT NONE
851
852    INTEGER(iwp) ::  i    !< index of facade-adjacent atmosphere grid point in x-direction
853    INTEGER(iwp) ::  j    !< index of facade-adjacent atmosphere grid point in y-direction
854    INTEGER(iwp) ::  k    !< index of facade-adjacent atmosphere grid point in z-direction
855    INTEGER(iwp) ::  kk   !< vertical index of indoor grid point adjacent to facade
856    INTEGER(iwp) ::  l    !< running index for surface-element orientation
857    INTEGER(iwp) ::  m    !< running index surface elements
858    INTEGER(iwp) ::  nb   !< running index for buildings
859    INTEGER(iwp) ::  fa   !< running index for facade elements of each building
860
861    REAL(wp) ::  indoor_wall_window_temperature   !< weighted temperature of innermost wall/window layer
862    REAL(wp) ::  near_facade_temperature          !< outside air temperature 10cm away from facade
863    REAL(wp) ::  time_utc_hour                    !< time of day (hour UTC)
864
865    REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in_l_send   !< dummy send buffer used for summing-up indoor temperature per kk-level
866    REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in_recv     !< dummy recv buffer used for summing-up indoor temperature per kk-level
867
868!
869!-- Daily schedule, here for 08:00-18:00 = 1, other hours = 0.
870!-- time_utc_hour is calculated here based on time_utc [s] from
871!-- date_and_time_mod.
872!-- (kanani: Does this schedule not depend on if it's an office or resident
873!-- building?)
874    time_utc_hour = time_utc / 3600.0_wp
875
876!
877!-- Allocation of the load profiles to the building types
878!-- Residental Building, panel WBS 70
879    if      (building_type ==  1 .OR. &
880             building_type ==  2 .OR. &
881             building_type ==  3 .OR. &
882             building_type == 10 .OR. &
883             building_type == 11 .OR. &
884             building_type == 12) then
885                                        ventilation_int_loads = 1
886!-- Office, building with large windows
887    else if (building_type ==  4 .OR. &
888             building_type ==  5 .OR. &
889             building_type ==  6 .OR. &
890             building_type ==  7 .OR. &
891             building_type ==  8 .OR. &
892             building_type ==  9) then
893                                        ventilation_int_loads = 2
894!-- Industry, hospitals
895    else if (building_type == 13 .OR. &
896             building_type == 14 .OR. &
897             building_type == 15 .OR. &
898             building_type == 16 .OR. &
899             building_type == 17 .OR. &
900             building_type == 18) then
901                                        ventilation_int_loads = 3
902
903    end if
904
905!-- Residental Building, panel WBS 70
906   
907    if (ventilation_int_loads == 1) THEN
908       if ( time_utc_hour >= 6.0_wp .AND. time_utc_hour <= 8.0_wp )  THEN
909          schedule_d = 1
910       else if ( time_utc_hour >= 18.0_wp .AND. time_utc_hour <= 23.0_wp )  THEN
911          schedule_d = 1
912       else
913          schedule_d = 0
914       end if
915    end if
916
917!-- Office, building with large windows
918
919    if (ventilation_int_loads == 2) THEN
920       if ( time_utc_hour >= 8.0_wp  .AND.  time_utc_hour <= 18.0_wp )  THEN
921          schedule_d = 1
922       else
923          schedule_d = 0
924       end if
925    end if
926       
927!-- Industry, hospitals
928    if (ventilation_int_loads == 3) THEN
929       if ( time_utc_hour >= 6.0_wp  .AND.  time_utc_hour <= 22.0_wp )  THEN
930          schedule_d = 1
931       else
932          schedule_d = 0
933       end if
934    end if
935
936
937!
938!-- Following calculations must be done for each facade element.
939    DO  nb = 1, num_build
940!
941!--    First, check whether building is present on local subdomain.
942       IF ( buildings(nb)%on_pe )  THEN
943!
944!--       Initialize/reset indoor temperature
945          buildings(nb)%t_in   = 0.0_wp
946          buildings(nb)%t_in_l = 0.0_wp 
947!
948!--       Horizontal surfaces
949          DO  fa = 1, buildings(nb)%num_facades_per_building_h_l
950!
951!--          Determine index where corresponding surface-type information
952!--          is stored.
953             m = buildings(nb)%m_h(fa)
954!
955!--          Determine building height level index.
956             kk = surf_usm_h%k(m) + surf_usm_h%koff
957!           
958!--          Building geometries --> not time-dependent
959             facade_element_area      = dx * dy                             !< [m2] surface area per facade element   
960             floor_area_per_facade    = buildings(nb)%vpf(kk) * ddzw(kk)    !< [m2] net floor area per facade element       
961             indoor_volume_per_facade = buildings(nb)%vpf(kk)               !< [m3] indoor air volume per facade element           
962             window_area_per_facade   = surf_usm_h%frac(ind_wat_win,m)  * facade_element_area  !< [m2] window area per facade element
963             eff_mass_area            = factor_a * floor_area_per_facade    !< [m2] standard values according to Table 12 section 12.3.1.2  (calculate over Eq. (65) according to section 12.3.1.2)
964             c_m                      = factor_c * floor_area_per_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)
965             total_area               = lambda_at * floor_area_per_facade   !< [m2] area of all surfaces pointing to zone  Eq. (9) according to section 7.2.2.2
966
967!--          Calculation of heat transfer coefficient for transmission --> not time-dependent
968             h_tr_w   = window_area_per_facade * u_value_win   !< [W/K] only for windows
969             h_tr_is  = total_area * h_is                      !< [W/K] with h_is = 3.45 W / (m2 K) between surface and air, Eq. (9)
970             h_tr_ms  = eff_mass_area * h_ms                    !< [W/K] with h_ms = 9.10 W / (m2 K) between component and surface, Eq. (64)
971             h_tr_op  = 1 / ( 1 / ( ( facade_element_area - window_area_per_facade ) &
972                                    * lambda_layer3 / s_layer3 * 0.5 ) + 1 / h_tr_ms )
973             h_tr_em  = 1 / ( 1 / h_tr_op - 1 / h_tr_ms )      !< [W/K] Eq. (63), Section 12.2.2
974!
975!--          internal air loads dependent on the occupacy of the room
976!--          basical internal heat gains (qint_low) with additional internal heat gains by occupancy (qint_high) (0,5*phi_int)
977             phi_ia = 0.5 * ( ( qint_high * schedule_d + qint_low )            &
978                              * floor_area_per_facade )         !< [W] Eq. (C.1)
979!
980!--          Airflow dependent on the occupacy of the room
981!--          basical airflow (air_change_low) with additional airflow gains by occupancy (air_change_high)
982             air_change = ( air_change_high * schedule_d + air_change_low )  !< [1/h]?
983!
984!--          Heat transfer of ventilation
985!--          not less than 0.01 W/K to provide division by 0 in further calculations
986!--          with heat capacity of air 0.33 Wh/m2K
[3524]987             h_ve   = MAX( 0.01_wp , ( air_change * indoor_volume_per_facade *      &
988                                    0.33_wp * (1 - eta_ve ) ) )    !< [W/K] from ISO 13789 Eq.(10)
[3469]989
990!--          Heat transfer coefficient auxiliary variables
991             h_tr_1 = 1 / ( ( 1 / h_ve )   + ( 1 / h_tr_is ) )  !< [W/K] Eq. (C.6)
992             h_tr_2 = h_tr_1 + h_tr_w                           !< [W/K] Eq. (C.7)
993             h_tr_3 = 1 / ( ( 1 / h_tr_2 ) + ( 1 / h_tr_ms ) )  !< [W/K] Eq. (C.8)
994!
995!--          Net short-wave radiation through window area (was i_global)
996             net_sw_in = surf_usm_h%rad_sw_in(m) - surf_usm_h%rad_sw_out(m)
997!
998!--          Quantities needed for im_calc_temperatures
999             i = surf_usm_h%i(m)
1000             j = surf_usm_h%j(m)
1001             k = surf_usm_h%k(m)
1002             near_facade_temperature = t_surf_10cm_h(m)
1003             indoor_wall_window_temperature =                                  &
1004                  surf_usm_h%frac(ind_veg_wall,m) * t_wall_h(nzt_wall,m)       &
1005                + surf_usm_h%frac(ind_wat_win,m)  * t_window_h(nzt_wall,m)
1006!
1007!--          Solar thermal gains. If net_sw_in larger than sun-protection
1008!--          threshold parameter (params_solar_protection), sun protection will
1009!--          be activated
1010             IF ( net_sw_in <= params_solar_protection )  THEN
1011                solar_protection_off = 1
1012                solar_protection_on  = 0 
1013             ELSE
1014                solar_protection_off = 0
1015                solar_protection_on  = 1 
1016             ENDIF
1017!
1018!--          Calculation of total heat gains from net_sw_in through windows [W] in respect on automatic sun protection
1019!--          DIN 4108 - 2 chap.8
1020             phi_sol = (   window_area_per_facade * net_sw_in * solar_protection_off               &
1021                         + window_area_per_facade * net_sw_in * f_c_win * solar_protection_on )    &
1022                       * g_value_win * ( 1 - params_f_f ) * params_f_w              !< [W]
1023!
1024!--          Calculation of the mass specific thermal load for internal and external heatsources of the inner node
1025             phi_m   = (eff_mass_area / total_area) * ( phi_ia + phi_sol )          !< [W] Eq. (C.2) with phi_ia=0,5*phi_int
1026!
1027!--          Calculation mass specific thermal load implied non thermal mass
1028             phi_st  =   ( 1 - ( eff_mass_area / total_area ) - ( h_tr_w / ( 9.1 * total_area ) ) ) &
1029                       * ( phi_ia + phi_sol )                                       !< [W] Eq. (C.3) with phi_ia=0,5*phi_int
1030!
1031!--          Calculations for deriving indoor temperature and heat flux into the wall
1032!--          Step 1: Indoor temperature without heating and cooling
1033!--          section C.4.1 Picture C.2 zone 3)
1034             phi_hc_nd = 0
1035             
1036             CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
1037                                         near_facade_temperature, phi_hc_nd )
1038!
1039!--          If air temperature between border temperatures of heating and cooling, assign output variable, then ready   
1040             IF ( theta_int_h_set <= theta_air  .AND.  theta_air <= theta_int_c_set )  THEN
1041                phi_hc_nd_ac = 0
1042                phi_hc_nd    = phi_hc_nd_ac
1043                theta_air_ac = theta_air
1044!
1045!--          Step 2: Else, apply 10 W/m² heating/cooling power and calculate indoor temperature
1046!--          again.
1047             ELSE
1048!
1049!--             Temperature not correct, calculation method according to section C4.2
1050                theta_air_0 = theta_air !< Note temperature without heating/cooling
1051
1052!--             Heating or cooling?
1053                IF ( theta_air > theta_int_c_set )  THEN
1054                   theta_air_set = theta_int_c_set
1055                ELSE
1056                   theta_air_set = theta_int_h_set 
1057                ENDIF
1058
1059!--             Calculate the temperature with phi_hc_nd_10
1060                phi_hc_nd_10 = 10.0_wp * floor_area_per_facade
1061                phi_hc_nd    = phi_hc_nd_10
1062       
1063                CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
1064                                            near_facade_temperature, phi_hc_nd )
1065
1066                theta_air_10 = theta_air !< Note the temperature with 10 W/m2 of heating
1067!
1068   
1069                phi_hc_nd_un = phi_hc_nd_10 * (theta_air_set - theta_air_0)                        &
1070                                            / (theta_air_10  - theta_air_0)            !< Eq. (C.13)
1071                                           
1072                                           
1073                                       
1074!--             Step 3: With temperature ratio to determine the heating or cooling capacity   
1075!--             If necessary, limit the power to maximum power
1076!--             section C.4.1 Picture C.2 zone 2) and 4)
1077                IF ( phi_c_max < phi_hc_nd_un  .AND.  phi_hc_nd_un < phi_h_max )  THEN
1078                   phi_hc_nd_ac = phi_hc_nd_un
1079                   phi_hc_nd = phi_hc_nd_un   
1080                ELSE
1081!--             Step 4: Inner temperature with maximum heating (phi_hc_nd_un positive) or cooling (phi_hc_nd_un negative)
1082!--             section C.4.1 Picture C.2 zone 1) and 5)
1083                   IF ( phi_hc_nd_un > 0 )  THEN
1084                      phi_hc_nd_ac = phi_h_max                                         !< Limit heating
1085                   ELSE
1086                      phi_hc_nd_ac = phi_c_max                                         !< Limit cooling
1087                   ENDIF
1088                ENDIF
1089       
1090                phi_hc_nd = phi_hc_nd_ac   
1091!
1092!--             Calculate the temperature with phi_hc_nd_ac (new)
1093                CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
1094                                            near_facade_temperature, phi_hc_nd )
1095
1096                theta_air_ac = theta_air
1097       
1098             ENDIF
1099!
1100!--          Update theta_m_t_prev
1101             theta_m_t_prev = theta_m_t
1102!
1103!--          Calculate the operating temperature with weighted mean temperature of air and mean solar temperature
1104!--          Will be used for thermal comfort calculations
[3593]1105             theta_op     = 0.3 * theta_air_ac + 0.7 * theta_s          !< [degree_C] operative Temperature Eq. (C.12)
[3469]1106!
1107!--          Heat flux into the wall. Value needed in urban_surface_mod to
1108!--          calculate heat transfer through wall layers towards the facade
1109!--          (use c_p * rho_surface to convert [W/m2] into [K m/s])
1110             q_wall_win = h_tr_ms * ( theta_s - theta_m )                    &
1111                                    / (   facade_element_area                  &
1112                                        - window_area_per_facade )
1113!
1114!--          Transfer q_wall_win back to USM (innermost wall/window layer)
1115             surf_usm_h%iwghf_eb(m)        = q_wall_win
1116             surf_usm_h%iwghf_eb_window(m) = q_wall_win
1117!
1118!--          Sum up operational indoor temperature per kk-level. Further below,
1119!--          this temperature is reduced by MPI to one temperature per kk-level
1120!--          and building (processor overlapping)
1121             buildings(nb)%t_in_l(kk) = buildings(nb)%t_in_l(kk) + theta_op
1122!
1123!--          Calculation of waste heat
1124!--          Anthropogenic heat output
1125              IF ( phi_hc_nd_ac > 0 )  THEN
1126                   heating_on = 1
1127                   cooling_on = 0
1128              ELSE
1129                   heating_on = 0
1130                   cooling_on = 1
1131              ENDIF
1132
1133             q_waste_heat = (phi_hc_nd * (params_waste_heat_h * heating_on + params_waste_heat_c * cooling_on))  !< [W/m2]  anthropogenic heat output
1134!              surf_usm_h%shf(m)=q_waste_heat
1135             
1136          ENDDO !< Horizontal surfaces loop
1137!
1138!--       Vertical surfaces
1139          DO  fa = 1, buildings(nb)%num_facades_per_building_v_l
1140!
1141!--          Determine indices where corresponding surface-type information
1142!--          is stored.
1143             l = buildings(nb)%l_v(fa)
1144             m = buildings(nb)%m_v(fa)
1145!
1146!--          Determine building height level index.
1147             kk = surf_usm_v(l)%k(m) + surf_usm_v(l)%koff
1148!
1149!--          Building geometries  --> not time-dependent
1150             IF ( l == 0  .OR. l == 1 ) facade_element_area = dx * dzw(kk)  !< [m2] surface area per facade element
1151             IF ( l == 2  .OR. l == 3 ) facade_element_area = dy * dzw(kk)  !< [m2] surface area per facade element
1152             floor_area_per_facade    = buildings(nb)%vpf(kk) * ddzw(kk)    !< [m2] net floor area per facade element       
1153             indoor_volume_per_facade = buildings(nb)%vpf(kk)               !< [m3] indoor air volume per facade element           
1154             window_area_per_facade   = surf_usm_v(l)%frac(ind_wat_win,m)  * facade_element_area  !< [m2] window area per facade element
1155             eff_mass_area            = factor_a * floor_area_per_facade    !< [m2] standard values according to Table 12 section 12.3.1.2  (calculate over Eq. (65) according to section 12.3.1.2)
1156             c_m                      = factor_c * floor_area_per_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)
1157             total_area               = lambda_at * floor_area_per_facade   !< [m2] area of all surfaces pointing to zone Eq. (9) according to section 7.2.2.2
1158!
1159!--          Calculation of heat transfer coefficient for transmission --> not time-dependent
1160             h_tr_w   = window_area_per_facade * u_value_win   !< [W/K] only for windows
1161             h_tr_is  = total_area * h_is                      !< [W/K] with h_is = 3.45 W / (m2 K) between surface and air, Eq. (9)
1162             h_tr_ms  = eff_mass_area * h_ms                   !< [W/K] with h_ms = 9.10 W / (m2 K) between component and surface, Eq. (64)
1163             h_tr_op  = 1 / ( 1 / ( ( facade_element_area - window_area_per_facade ) &
1164                                    * lambda_layer3 / s_layer3 * 0.5 ) + 1 / h_tr_ms )
1165             h_tr_em  = 1 / ( 1 / h_tr_op - 1 / h_tr_ms )      !< [W/K] Eq. (63), Section 12.2.2
1166!
1167!--          internal air loads dependent on the occupacy of the room
1168!--          basical internal heat gains (qint_low) with additional internal heat gains by occupancy (qint_high) (0,5*phi_int)
1169             phi_ia = 0.5 * ( ( qint_high * schedule_d + qint_low )            &
1170                              * floor_area_per_facade )                      !< [W] Eq. (C.1)
1171!
1172!--          Airflow dependent on the occupacy of the room
1173!--          basical airflow (air_change_low) with additional airflow gains by occupancy (air_change_high)
1174             air_change = ( air_change_high * schedule_d + air_change_low ) 
1175!
1176!--          Heat transfer of ventilation
1177!--          not less than 0.01 W/K to provide division by 0 in further calculations
1178!--          with heat capacity of air 0.33 Wh/m2K
[3524]1179             h_ve   = MAX( 0.01_wp , ( air_change * indoor_volume_per_facade *      &
1180                                    0.33_wp * (1 - eta_ve ) ) )                    !< [W/K] from ISO 13789 Eq.(10)
[3469]1181                                   
1182!--          Heat transfer coefficient auxiliary variables
1183             h_tr_1 = 1 / ( ( 1 / h_ve )   + ( 1 / h_tr_is ) )                  !< [W/K] Eq. (C.6)
1184             h_tr_2 = h_tr_1 + h_tr_w                                           !< [W/K] Eq. (C.7)
1185             h_tr_3 = 1 / ( ( 1 / h_tr_2 ) + ( 1 / h_tr_ms ) )                  !< [W/K] Eq. (C.8)
1186!
1187!--          Net short-wave radiation through window area (was i_global)
1188             net_sw_in = surf_usm_v(l)%rad_sw_in(m) - surf_usm_v(l)%rad_sw_out(m)
1189!
1190!--          Quantities needed for im_calc_temperatures
1191             i = surf_usm_v(l)%i(m)
1192             j = surf_usm_v(l)%j(m)
1193             k = surf_usm_v(l)%k(m)
1194             near_facade_temperature = t_surf_10cm_v(l)%t(m)
1195             indoor_wall_window_temperature =                                    &
1196                  surf_usm_v(l)%frac(ind_veg_wall,m) * t_wall_v(l)%t(nzt_wall,m) &
1197                + surf_usm_v(l)%frac(ind_wat_win,m)  * t_window_v(l)%t(nzt_wall,m)
1198!
1199!--          Solar thermal gains. If net_sw_in larger than sun-protection
1200!--          threshold parameter (params_solar_protection), sun protection will
1201!--          be activated
1202             IF ( net_sw_in <= params_solar_protection )  THEN
1203                solar_protection_off = 1
1204                solar_protection_on  = 0 
1205             ELSE
1206                solar_protection_off = 0
1207                solar_protection_on  = 1 
1208             ENDIF
1209!
1210!--          Calculation of total heat gains from net_sw_in through windows [W] in respect on automatic sun protection
1211!--          DIN 4108 - 2 chap.8
1212             phi_sol = (   window_area_per_facade * net_sw_in * solar_protection_off               &
1213                         + window_area_per_facade * net_sw_in * f_c_win * solar_protection_on )    &
1214                       * g_value_win * ( 1 - params_f_f ) * params_f_w
1215!
1216!--          Calculation of the mass specific thermal load for internal and external heatsources
1217             phi_m   = (eff_mass_area / total_area) * ( phi_ia + phi_sol )          !< [W] Eq. (C.2) with phi_ia=0,5*phi_int
1218!
1219!--          Calculation mass specific thermal load implied non thermal mass
1220             phi_st  =   ( 1 - ( eff_mass_area / total_area ) - ( h_tr_w / ( 9.1 * total_area ) ) ) &
1221                       * ( phi_ia + phi_sol )                                       !< [W] Eq. (C.3) with phi_ia=0,5*phi_int
1222!
1223!--          Calculations for deriving indoor temperature and heat flux into the wall
1224!--          Step 1: Indoor temperature without heating and cooling
1225!--          section C.4.1 Picture C.2 zone 3)
1226             phi_hc_nd = 0
1227             
1228             CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
1229                                         near_facade_temperature, phi_hc_nd )
1230!
1231!--          If air temperature between border temperatures of heating and cooling, assign output variable, then ready 
1232             IF ( theta_int_h_set <= theta_air  .AND.  theta_air <= theta_int_c_set )  THEN
1233                phi_hc_nd_ac = 0
1234                phi_hc_nd    = phi_hc_nd_ac
1235                theta_air_ac = theta_air
1236!
1237!--          Step 2: Else, apply 10 W/m² heating/cooling power and calculate indoor temperature
1238!--          again.
1239             ELSE
1240!
1241!--             Temperature not correct, calculation method according to section C4.2
1242                theta_air_0 = theta_air !< Note temperature without heating/cooling
1243
1244!--             Heating or cooling?
1245                IF ( theta_air > theta_int_c_set )  THEN
1246                   theta_air_set = theta_int_c_set
1247                ELSE
1248                   theta_air_set = theta_int_h_set 
1249                ENDIF
1250
1251!--             Calculate the temperature with phi_hc_nd_10
1252                phi_hc_nd_10 = 10.0_wp * floor_area_per_facade
1253                phi_hc_nd    = phi_hc_nd_10
1254       
1255                CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
1256                                            near_facade_temperature, phi_hc_nd )
1257
1258                theta_air_10 = theta_air !< Note the temperature with 10 W/m2 of heating
1259
1260               
1261                phi_hc_nd_un = phi_hc_nd_10 * (theta_air_set - theta_air_0)                        &
1262                                            / (theta_air_10  - theta_air_0)            !< Eq. (C.13)
1263!     
1264!--             Step 3: With temperature ratio to determine the heating or cooling capacity   
1265!--             If necessary, limit the power to maximum power
1266!--             section C.4.1 Picture C.2 zone 2) and 4)
1267                IF ( phi_c_max < phi_hc_nd_un  .AND.  phi_hc_nd_un < phi_h_max )  THEN
1268                   phi_hc_nd_ac = phi_hc_nd_un
1269                   phi_hc_nd = phi_hc_nd_un
1270                ELSE
1271!--             Step 4: Inner temperature with maximum heating (phi_hc_nd_un positive) or cooling (phi_hc_nd_un negative)
1272!--             section C.4.1 Picture C.2 zone 1) and 5)
1273                   IF ( phi_hc_nd_un > 0 )  THEN
1274                      phi_hc_nd_ac = phi_h_max                                         !< Limit heating
1275                   ELSE
1276                      phi_hc_nd_ac = phi_c_max                                         !< Limit cooling
1277                   ENDIF
1278                ENDIF
1279       
1280                phi_hc_nd = phi_hc_nd_ac   
1281!
1282!--             Calculate the temperature with phi_hc_nd_ac (new)
1283                CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
1284                                            near_facade_temperature, phi_hc_nd )
1285
1286                theta_air_ac = theta_air
1287       
1288             ENDIF
1289!
1290!--          Update theta_m_t_prev
1291             theta_m_t_prev = theta_m_t
1292!
1293!--          Calculate the operating temperature with weighted mean of temperature of air and mean
1294!--          Will be used for thermal comfort calculations
1295             theta_op     = 0.3 * theta_air_ac + 0.7 * theta_s
1296!
1297!--          Heat flux into the wall. Value needed in urban_surface_mod to
1298!--          calculate heat transfer through wall layers towards the facade
1299             q_wall_win = h_tr_ms * ( theta_s - theta_m )                    &
1300                                    / (   facade_element_area                  &
1301                                        - window_area_per_facade )
1302!
1303!--          Transfer q_wall_win back to USM (innermost wall/window layer)
1304             surf_usm_v(l)%iwghf_eb(m)        = q_wall_win
1305             surf_usm_v(l)%iwghf_eb_window(m) = q_wall_win
1306!
1307!--          Sum up operational indoor temperature per kk-level. Further below,
1308!--          this temperature is reduced by MPI to one temperature per kk-level
1309!--          and building (processor overlapping)
1310             buildings(nb)%t_in_l(kk) = buildings(nb)%t_in_l(kk) + theta_op
1311
1312!
1313!--          Calculation of waste heat
1314!--          Anthropogenic heat output
1315              IF ( phi_hc_nd_ac > 0 )  THEN
1316                   heating_on = 1
1317                   cooling_on = 0
1318              ELSE
1319                   heating_on = 0
1320                   cooling_on = 1
1321              ENDIF
1322
1323             q_waste_heat = (phi_hc_nd * (params_waste_heat_h * heating_on + params_waste_heat_c * cooling_on))   !< [W/m2] , anthropogenic heat output
1324!              surf_usm_v(l)%waste_heat(m)=q_waste_heat
1325             
1326          ENDDO !< Vertical surfaces loop
1327
1328       ENDIF !< buildings(nb)%on_pe
1329    ENDDO !< buildings loop
1330
1331!
1332!-- Determine total number of facade elements per building and assign number to
1333!-- building data type.
1334    DO  nb = 1, num_build
1335!
1336!--    Allocate dummy array used for summing-up facade elements.
1337!--    Please note, dummy arguments are necessary as building-date type
1338!--    arrays are not necessarily allocated on all PEs.
1339       ALLOCATE( t_in_l_send(buildings(nb)%kb_min:buildings(nb)%kb_max) )
1340       ALLOCATE( t_in_recv(buildings(nb)%kb_min:buildings(nb)%kb_max) )
1341       t_in_l_send = 0.0_wp
1342       t_in_recv   = 0.0_wp
1343
1344       IF ( buildings(nb)%on_pe )  THEN
1345          t_in_l_send = buildings(nb)%t_in_l
1346       ENDIF
1347
1348#if defined( __parallel ) 
1349       CALL MPI_ALLREDUCE( t_in_l_send,                                        &
1350                           t_in_recv,                                          &
1351                           buildings(nb)%kb_max - buildings(nb)%kb_min + 1,    &
1352                           MPI_REAL,                                           &
1353                           MPI_SUM,                                            &
1354                           comm2d,                                             &
1355                           ierr )
1356
1357       IF ( ALLOCATED( buildings(nb)%t_in ) )                                  &
1358           buildings(nb)%t_in = t_in_recv
1359#else
1360       buildings(nb)%t_in = buildings(nb)%t_in_l
1361#endif
1362
1363       buildings(nb)%t_in =   buildings(nb)%t_in /                             &
1364                            ( buildings(nb)%num_facade_h +                     &
1365                              buildings(nb)%num_facade_v )
1366!
1367!--    Deallocate dummy arrays
1368       DEALLOCATE( t_in_l_send )
1369       DEALLOCATE( t_in_recv )
1370
1371    ENDDO
1372
1373
1374 END SUBROUTINE im_main_heatcool
1375
1376!------------------------------------------------------------------------------!
1377! Description:
1378! ------------
1379!> Parin for &indoor_parameters for indoor model
1380!------------------------------------------------------------------------------!
1381 SUBROUTINE im_parin
1382   
1383    USE control_parameters,                                                    &
1384        ONLY:  indoor_model
1385   
1386    IMPLICIT NONE
1387
1388    CHARACTER (LEN=80) ::  line  !< string containing current line of file PARIN
1389
1390   
1391   
1392    NAMELIST /indoor_parameters/  building_type, dt_indoor,                           &
1393                                  initial_indoor_temperature
1394
1395!    line = ' '
1396
1397!
1398!-- Try to find indoor model package
1399    REWIND ( 11 )
1400    line = ' '
1401    DO   WHILE ( INDEX( line, '&indoor_parameters' ) == 0 )
1402       READ ( 11, '(A)', END=10 )  line
1403!    PRINT*, 'line: ', line
1404    ENDDO
1405    BACKSPACE ( 11 )
1406
1407!
1408!-- Read user-defined namelist
1409    READ ( 11, indoor_parameters )
1410!
1411!-- Set flag that indicates that the indoor model is switched on
1412    indoor_model = .TRUE.
1413
1414!
1415!--    Activate spinup (maybe later
1416!        IF ( spinup_time > 0.0_wp )  THEN
1417!           coupling_start_time = spinup_time
1418!           end_time = end_time + spinup_time
1419!           IF ( spinup_pt_mean == 9999999.9_wp )  THEN
1420!              spinup_pt_mean = pt_surface
1421!           ENDIF
1422!           spinup = .TRUE.
1423!        ENDIF
1424
1425 10 CONTINUE
1426   
1427 END SUBROUTINE im_parin
1428
1429
1430END MODULE indoor_model_mod
Note: See TracBrowser for help on using the repository browser.