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

Last change on this file since 3685 was 3685, checked in by knoop, 5 years ago

Some interface calls moved to module_interface + cleanup

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