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

Last change on this file since 3677 was 3597, checked in by maronga, 5 years ago

revised calculation of near surface air potential temperature

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