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

Last change on this file since 3534 was 3524, checked in by raasch, 5 years ago

unused variables removed, missing working precision added, missing preprocessor directives added, bugfix concerning allocation of t_surf_wall_v in nopointer case, declaration statements rearranged to avoid compile time errors, mpi_abort arguments replaced to avoid compile errors

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