Ignore:
Timestamp:
Aug 24, 2020 4:02:40 PM (4 years ago)
Author:
raasch
Message:

files re-formatted to follow the PALM coding standard

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/indoor_model_mod.f90

    r4481 r4646  
    11!> @file indoor_model_mod.f90
    2 !--------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
    44!
    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/>.
     5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
     6! Public License as published by the Free Software Foundation, either version 3 of the License, or
     7! (at your option) any later version.
     8!
     9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
     10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
     11! Public License for more details.
     12!
     13! You should have received a copy of the GNU General Public License along with PALM. If not, see
     14! <http://www.gnu.org/licenses/>.
    1615!
    1716! Copyright 2018-2020 Leibniz Universitaet Hannover
    1817! Copyright 2018-2020 Hochschule Offenburg
    19 !--------------------------------------------------------------------------------!
     18!--------------------------------------------------------------------------------------------------!
    2019!
    2120! Current revisions:
    2221! -----------------
    23 ! 
    24 ! 
     22!
     23!
    2524! Former revisions:
    2625! -----------------
    2726! $Id$
    28 ! Change order of dimension in surface array %frac to allow for better
    29 ! vectorization.
    30 !
     27! file re-formatted to follow the PALM coding standard
     28!
     29! 4481 2020-03-31 18:55:54Z maronga
     30! Change order of dimension in surface array %frac to allow for better vectorization.
     31!
    3132! 4441 2020-03-04 19:20:35Z suehring
    32 ! Major bugfix in calculation of energy demand - floor-area-per-facade was wrongly
    33 ! calculated leading to unrealistically high energy demands and thus to
    34 ! unreallistically high waste-heat fluxes.
    35 ! 
     33! Major bugfix in calculation of energy demand - floor-area-per-facade was wrongly calculated
     34! leading to unrealistically high energy demands and thus to unreallistically high waste-heat
     35! fluxes.
     36!
    3637! 4346 2019-12-18 11:55:56Z motisi
    37 ! Introduction of wall_flags_total_0, which currently sets bits based on static
    38 ! topography information used in wall_flags_static_0
    39 ! 
     38! Introduction of wall_flags_total_0, which currently sets bits based on static topography
     39! information used in wall_flags_static_0
     40!
    4041! 4329 2019-12-10 15:46:36Z motisi
    4142! Renamed wall_flags_0 to wall_flags_static_0
    42 ! 
     43!
    4344! 4310 2019-11-26 19:01:28Z suehring
    44 ! Remove dt_indoor from namelist input. The indoor model is an hourly-based
    45 ! model, calling it more/less often lead to inaccurate results.
    46 ! 
     45! Remove dt_indoor from namelist input. The indoor model is an hourly-based model, calling it
     46! more/less often lead to inaccurate results.
     47!
    4748! 4299 2019-11-22 10:13:38Z suehring
    48 ! Output of indoor temperature revised (to avoid non-defined values within
    49 ! buildings)
    50 !
     49! Output of indoor temperature revised (to avoid non-defined values within buildings)
     50!
    5151! 4267 2019-10-16 18:58:49Z suehring
    5252! Bugfix in initialization, some indices to access building_pars where wrong.
    5353! Introduction of seasonal parameters.
    54 ! 
     54!
    5555! 4246 2019-09-30 09:27:52Z pavelkrc
    56 ! 
    57 ! 
     56!
     57!
    5858! 4242 2019-09-27 12:59:10Z suehring
    5959! Bugfix in array index
    60 ! 
     60!
    6161! 4238 2019-09-25 16:06:01Z suehring
    6262! - Bugfix in determination of minimum facade height and in location message
    6363! - Bugfix, avoid division by zero
    64 ! - Some optimization 
    65 ! 
     64! - Some optimization
     65!
    6666! 4227 2019-09-10 18:04:34Z gronemeier
    6767! implement new palm_date_time_mod
     
    7272! 4209 2019-09-02 12:00:03Z suehring
    7373! - Bugfix in initialization of indoor temperature
    74 ! - Prescibe default indoor temperature in case it is not given in the
    75 !   namelist input
     74! - Prescibe default indoor temperature in case it is not given in the namelist input
    7675!
    7776! 4182 2019-08-21 14:37:54Z scharf
    7877! Corrected "Former revisions" section
    79 ! 
     78!
    8079! 4148 2019-08-08 11:26:00Z suehring
    81 ! Bugfix in case of non grid-resolved buildings. Further, vertical grid spacing
    82 ! is now considered at the correct level. 
     80! Bugfix in case of non grid-resolved buildings. Further, vertical grid spacing is now considered at
     81! the correct level.
    8382! - change calculation of a_m and c_m
    8483! - change calculation of u-values (use h_es in building array)
     
    9392!   in building array
    9493! - change calculation of q_waste_heat
    95 ! - bugfix in averaging mean indoor temperature 
    96 ! 
     94! - bugfix in averaging mean indoor temperature
     95!
    9796! 3759 2019-02-21 15:53:45Z suehring
    9897! - Calculation of total building volume
    9998! - Several bugfixes
    10099! - Calculation of building height revised
    101 ! 
     100!
    102101! 3745 2019-02-15 18:57:56Z suehring
    103102! - remove building_type from module
    104 ! - initialize parameters for each building individually instead of a bulk
    105 !   initializaion with  identical building type for all
     103! - initialize parameters for each building individually instead of a bulk initializaion with
     104!   identical building type for all
    106105! - output revised
    107106! - add missing _wp
    108107! - some restructuring of variables in building data structure
    109 ! 
     108!
    110109! 3744 2019-02-15 18:38:58Z suehring
    111110! Some interface calls moved to module_interface + cleanup
    112 ! 
     111!
    113112! 3469 2018-10-30 20:05:07Z kanani
    114113! Initial revision (tlang, suehring, kanani, srissman)!
     
    125124! Description:
    126125! ------------
    127 !> <Description of the new module>
    128126!> Module for Indoor Climate Model (ICM)
    129127!> The module is based on the DIN EN ISO 13790 with simplified hour-based procedure.
    130128!> This model is a equivalent circuit diagram of a three-point RC-model (5R1C).
    131 !> This module differ between indoor-air temperature an average temperature of indoor surfaces which make it prossible to determine thermal comfort
    132 !> the heat transfer between indoor and outdoor is simplified
    133 
     129!> This module differs between indoor-air temperature an average temperature of indoor surfaces which make it prossible to determine
     130!> thermal comfort
     131!> the heat transfer between indoor and outdoor is simplified
     132
     133!> @todo Many statement comments that are given as doxygen comments need to be changed to normal comments
    134134!> @todo Replace window_area_per_facade by %frac(1,m) for window
    135 !> @todo emissivity change for window blinds if solar_protection_on=1 
     135!> @todo emissivity change for window blinds if solar_protection_on=1
    136136
    137137!> @note Do we allow use of integer flags, or only logical flags? (concerns e.g. cooling_on, heating_on)
     
    139139!>
    140140!> @bug  <Enter known bugs here>
    141 !------------------------------------------------------------------------------!
    142  MODULE indoor_model_mod 
    143 
    144     USE arrays_3d,                                                             &
    145         ONLY:  ddzw,                                                           &
    146                dzw,                                                            &
     141!--------------------------------------------------------------------------------------------------!
     142 MODULE indoor_model_mod
     143
     144    USE arrays_3d,                                                                                 &
     145        ONLY:  ddzw,                                                                               &
     146               dzw,                                                                                &
    147147               pt
    148148
    149     USE control_parameters,                                                    &
     149    USE control_parameters,                                                                        &
    150150        ONLY:  initializing_actions
    151151
    152152    USE kinds
    153    
    154     USE netcdf_data_input_mod,                                                 &
     153
     154    USE netcdf_data_input_mod,                                                                     &
    155155        ONLY:  building_id_f, building_type_f
    156156
    157     USE palm_date_time_mod,                                                    &
    158         ONLY:  get_date_time, northward_equinox, seconds_per_hour,             &
    159                southward_equinox
    160 
    161     USE surface_mod,                                                           &
     157    USE palm_date_time_mod,                                                                        &
     158        ONLY:  get_date_time, northward_equinox, seconds_per_hour, southward_equinox
     159
     160    USE surface_mod,                                                                               &
    162161        ONLY:  surf_usm_h, surf_usm_v
    163162
     
    170169
    171170       INTEGER(iwp) ::  id                                !< building ID
     171       INTEGER(iwp) ::  kb_max                            !< highest vertical index of a building
    172172       INTEGER(iwp) ::  kb_min                            !< lowest vertical index of a building
    173        INTEGER(iwp) ::  kb_max                            !< highest vertical index of a building
    174173       INTEGER(iwp) ::  num_facades_per_building_h = 0    !< total number of horizontal facades elements
    175174       INTEGER(iwp) ::  num_facades_per_building_h_l = 0  !< number of horizontal facade elements on local subdomain
     
    179178
    180179       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  l_v            !< index array linking surface-element orientation index
    181                                                                   !< for vertical surfaces with building 
     180                                                                  !< for vertical surfaces with building
    182181       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  m_h            !< index array linking surface-element index for
    183182                                                                  !< horizontal surfaces with building
    184        INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  m_v            !< index array linking surface-element index for 
     183       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  m_v            !< index array linking surface-element index for
    185184                                                                  !< vertical surfaces with building
    186        INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facade_h   !< number of horizontal facade elements per buidling 
     185       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facade_h   !< number of horizontal facade elements per buidling
    187186                                                                  !< and height level
    188187       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facade_v   !< number of vertical facades elements per buidling
    189188                                                                  !< and height level
    190                                                                  
     189
    191190
    192191       LOGICAL ::  on_pe = .FALSE.   !< flag indicating whether a building with certain ID is on local subdomain
    193        
     192
    194193       REAL(wp) ::  air_change_high       !< [1/h] air changes per time_utc_hour
    195194       REAL(wp) ::  air_change_low        !< [1/h] air changes per time_utc_hour
     
    199198       REAL(wp) ::  factor_a              !< [-] Dynamic parameters specific effective surface according to Table 12; 2.5
    200199                                          !< (very light, light and medium), 3.0 (heavy), 3.5 (very heavy)
    201        REAL(wp) ::  factor_c              !< [J/(m2 K)] Dynamic parameters inner heatstorage according to Table 12; 80000 
     200       REAL(wp) ::  factor_c              !< [J/(m2 K)] Dynamic parameters inner heatstorage according to Table 12; 80000
    202201                                          !< (very light), 110000 (light), 165000 (medium), 260000 (heavy), 370000 (very heavy)
    203202       REAL(wp) ::  f_c_win               !< [-] shading factor
    204203       REAL(wp) ::  fapf                  !< [m2/m2] floor area per facade
    205204       REAL(wp) ::  g_value_win           !< [-] SHGC factor
    206        REAL(wp) ::  h_es                  !< [W/(m2 K)] surface-related heat transfer coefficient between extern and surface 
     205       REAL(wp) ::  h_es                  !< [W/(m2 K)] surface-related heat transfer coefficient between extern and surface
    207206       REAL(wp) ::  height_cei_con        !< [m] ceiling construction heigth
    208207       REAL(wp) ::  height_storey         !< [m] storey heigth
    209208       REAL(wp) ::  params_waste_heat_c   !< [-] anthropogenic heat outputs for cooling e.g. 1.33 for KKM with COP = 3
    210        REAL(wp) ::  params_waste_heat_h   !< [-] anthropogenic heat outputs for heating e.g. 1 - 0.9 = 0.1 for combustion with eta = 0.9 or -2 for WP with COP = 3
     209       REAL(wp) ::  params_waste_heat_h   !< [-] anthropogenic heat outputs for heating e.g. 1 - 0.9 = 0.1 for combustion with
     210                                          !< eta = 0.9 or -2 for WP with COP = 3
    211211       REAL(wp) ::  phi_c_max             !< [W] Max. Cooling capacity (negative)
    212212       REAL(wp) ::  phi_h_max             !< [W] Max. Heating capacity (positive)
     
    229229       REAL(wp), DIMENSION(:), ALLOCATABLE ::  vol_frac   !< fraction of local on total building volume, height dependent
    230230       REAL(wp), DIMENSION(:), ALLOCATABLE ::  vpf        !< building volume volume per facade element, height dependent
    231        
     231
    232232    END TYPE build
    233233
     
    237237!
    238238!-- Declare all global variables within the module
     239
     240    REAL(wp), PARAMETER ::  dt_indoor = 3600.0_wp                  !< [s] time interval for indoor-model application, fixed to
     241                                                                   !< 3600.0 due to model requirements
     242    REAL(wp), PARAMETER ::  h_is                     = 3.45_wp     !< [W/(m2 K)] surface-related heat transfer coefficient between
     243                                                                   !< surface and air (chap. 7.2.2.2)
     244    REAL(wp), PARAMETER ::  h_ms                     = 9.1_wp      !< [W/(m2 K)] surface-related heat transfer coefficient between
     245                                                                   !< component and surface (chap. 12.2.2)
     246    REAL(wp), PARAMETER ::  params_f_f               = 0.3_wp      !< [-] frame ratio chap. 8.3.2.1.1 for buildings with mostly
     247                                                                   !< cooling 2.0_wp
     248    REAL(wp), PARAMETER ::  params_f_w               = 0.9_wp      !< [-] correction factor (fuer nicht senkrechten Stahlungseinfall
     249                                                                   !< DIN 4108-2 chap.8, (hier konstant, keine WinkelabhÀngigkeit)
     250    REAL(wp), PARAMETER ::  params_f_win             = 0.5_wp      !< [-] proportion of window area, Database A_win aus
     251                                                                   !< Datenbank 27 window_area_per_facade_percent
     252    REAL(wp), PARAMETER ::  params_solar_protection  = 300.0_wp    !< [W/m2] chap. G.5.3.1 sun protection closed, if the radiation
     253                                                                   !< on facade exceeds this value
     254
    239255    INTEGER(iwp) ::  cooling_on              !< Indoor cooling flag (0=off, 1=on)
    240256    INTEGER(iwp) ::  heating_on              !< Indoor heating flag (0=off, 1=on)
     
    242258    INTEGER(iwp) ::  solar_protection_on     !< Solar protection on
    243259
    244     REAL(wp), PARAMETER ::  dt_indoor = 3600.0_wp    !< [s] time interval for indoor-model application, fixed to 3600.0 due to model requirements
    245260
    246261    REAL(wp) ::  a_m                                 !< [m2] the effective mass-related area
     
    251266    REAL(wp) ::  h_t_1                               !< [W/K] Heat transfer coefficient auxiliary variable 1
    252267    REAL(wp) ::  h_t_2                               !< [W/K] Heat transfer coefficient auxiliary variable 2
    253     REAL(wp) ::  h_t_3                               !< [W/K] Heat transfer coefficient auxiliary variable 3
    254     REAL(wp) ::  h_t_wm                              !< [W/K] Heat transfer coefficient of the emmision (got with h_t_ms the thermal mass)
     268    REAL(wp) ::  h_t_3                               !< [W/K] Heat transfer coefficient auxiliary variable 3
     269    REAL(wp) ::  h_t_es                              !< [W/K] heat transfer coefficient of doors, windows, curtain walls and
     270                                                     !< glazed walls (assumption: thermal mass=0)
    255271    REAL(wp) ::  h_t_is                              !< [W/K] thermal coupling conductance (Thermischer Kopplungsleitwert)
    256272    REAL(wp) ::  h_t_ms                              !< [W/K] Heat transfer conductance term (got with h_t_wm the thermal mass)
    257273    REAL(wp) ::  h_t_wall                            !< [W/K] heat transfer coefficient of opaque components (assumption: got all
    258274                                                     !< thermal mass) contains of h_t_wm and h_t_ms
    259     REAL(wp) ::  h_t_es                              !< [W/K] heat transfer coefficient of doors, windows, curtain walls and
    260                                                      !< glazed walls (assumption: thermal mass=0)
     275    REAL(wp) ::  h_t_wm                              !< [W/K] Heat transfer coefficient of the emmision (got with h_t_ms the
     276                                                     !< thermal mass)
    261277    REAL(wp) ::  h_v                                 !< [W/K] heat transfer of ventilation
    262278    REAL(wp) ::  indoor_volume_per_facade            !< [m3] indoor air volume per facade element
     
    264280    REAL(wp) ::  net_sw_in                           !< [W/m2] net short-wave radiation
    265281    REAL(wp) ::  phi_hc_nd                           !< [W] heating demand and/or cooling demand
    266     REAL(wp) ::  phi_hc_nd_10                        !< [W] heating demand and/or cooling demand for heating or cooling 
     282    REAL(wp) ::  phi_hc_nd_10                        !< [W] heating demand and/or cooling demand for heating or cooling
    267283    REAL(wp) ::  phi_hc_nd_ac                        !< [W] actual heating demand and/or cooling demand
    268284    REAL(wp) ::  phi_hc_nd_un                        !< [W] unlimited heating demand and/or cooling demand which is necessary to
    269                                                      !< reach the demanded required temperature (heating is positive, 
    270                                                      !< cooling is negative) 
     285                                                     !< reach the demanded required temperature (heating is positive,
     286                                                     !< cooling is negative)
    271287    REAL(wp) ::  phi_ia                              !< [W] internal air load = internal loads * 0.5, Eq. (C.1)
    272288    REAL(wp) ::  phi_m                               !< [W] mass specific thermal load (internal and external)
    273289    REAL(wp) ::  phi_mtot                            !< [W] total mass specific thermal load (internal and external)
    274290    REAL(wp) ::  phi_sol                             !< [W] solar loads
    275     REAL(wp) ::  phi_st                              !< [W] mass specific thermal load implied non thermal mass 
     291    REAL(wp) ::  phi_st                              !< [W] mass specific thermal load implied non thermal mass
    276292    REAL(wp) ::  q_wall_win                          !< [W/m2]heat flux from indoor into wall/window
    277293    REAL(wp) ::  q_waste_heat                        !< [W/m2]waste heat, sum of waste heat over the roof to Palm
    278                                                      
     294
    279295    REAL(wp) ::  q_c_m                               !< [W] Energy of thermal storage mass specific thermal load for internal
    280296                                                     !< and external heatsources (for energy bilanz)
    281     REAL(wp) ::  q_c_st                              !< [W] Energy of thermal storage mass specific thermal load implied non thermal mass (for energy bilanz)
     297    REAL(wp) ::  q_c_st                              !< [W] Energy of thermal storage mass specific thermal load implied non
     298                                                     !< thermal mass (for energy bilanz)
    282299    REAL(wp) ::  q_int                               !< [W] Energy of internal air load (for energy bilanz)
    283300    REAL(wp) ::  q_sol                               !< [W] Energy of solar (for energy bilanz)
    284301    REAL(wp) ::  q_trans                             !< [W] Energy of transmission (for energy bilanz)
    285302    REAL(wp) ::  q_vent                              !< [W] Energy of ventilation (for energy bilanz)
    286                                                      
     303
    287304    REAL(wp) ::  schedule_d                          !< [-] activation for internal loads (low or high + low)
    288305    REAL(wp) ::  skip_time_do_indoor = 0.0_wp        !< [s] Indoor model is not called before this time
    289306    REAL(wp) ::  theta_air                           !< [degree_C] air temperature of the RC-node
    290307    REAL(wp) ::  theta_air_0                         !< [degree_C] air temperature of the RC-node in equilibrium
    291     REAL(wp) ::  theta_air_10                        !< [degree_C] air temperature of the RC-node from a heating capacity 
     308    REAL(wp) ::  theta_air_10                        !< [degree_C] air temperature of the RC-node from a heating capacity
    292309                                                     !< of 10 W/m2
    293310    REAL(wp) ::  theta_air_ac                        !< [degree_C] actual room temperature after heating/cooling
     
    301318    REAL(wp) ::  total_area                          !< [m2] area of all surfaces pointing to zone
    302319    REAL(wp) ::  window_area_per_facade              !< [m2] window area per facade element
    303    
    304     REAL(wp), PARAMETER ::  h_is                     = 3.45_wp     !< [W/(m2 K)] surface-related heat transfer coefficient between
    305                                                                    !< surface and air (chap. 7.2.2.2)
    306     REAL(wp), PARAMETER ::  h_ms                     = 9.1_wp      !< [W/(m2 K)] surface-related heat transfer coefficient between component and surface (chap. 12.2.2)
    307     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
    308     REAL(wp), PARAMETER ::  params_f_w               = 0.9_wp      !< [-] correction factor (fuer nicht senkrechten Stahlungseinfall
    309                                                                    !< DIN 4108-2 chap.8, (hier konstant, keine WinkelabhÀngigkeit)
    310     REAL(wp), PARAMETER ::  params_f_win             = 0.5_wp      !< [-] proportion of window area, Database A_win aus
    311                                                                    !< Datenbank 27 window_area_per_facade_percent
    312     REAL(wp), PARAMETER ::  params_solar_protection  = 300.0_wp    !< [W/m2] chap. G.5.3.1 sun protection closed, if the radiation
    313                                                                    !< on facade exceeds this value
     320
    314321!
    315322!-- Definition of seasonal parameters, summer and winter, for different building types
    316     REAL(wp), DIMENSION(0:1,1:7) ::  summer_pars = RESHAPE( (/               & ! building_type 1
    317                                           0.5_wp,                              & ! basical airflow without occupancy of the room
    318                                           2.0_wp,                              & ! additional airflow depend of occupancy of the room
    319                                           0.5_wp,                              & ! building_type 2: basical airflow without occupancy of the room
    320                                           2.0_wp,                              & ! additional airflow depend of occupancy of the room
    321                                           0.8_wp,                              & ! building_type 3: basical airflow without occupancy of the room
    322                                           2.0_wp,                              & ! additional airflow depend of occupancy of the room
    323                                           0.1_wp,                              & ! building_type 4: basical airflow without occupancy of the room
    324                                           1.5_wp,                              & ! additional airflow depend of occupancy of the room
    325                                           0.1_wp,                              & ! building_type 5: basical airflow without occupancy of the room
    326                                           1.5_wp,                              & ! additional airflow depend of occupancy of the room
    327                                           0.1_wp,                              & ! building_type 6: basical airflow without occupancy of the room
    328                                           1.5_wp,                              & ! additional airflow depend of occupancy of the room
    329                                           0.1_wp,                              & ! building_type 7: basical airflow without occupancy of the room
    330                                           1.5_wp                               & ! additional airflow depend of occupancy of the room
     323    REAL(wp), DIMENSION(0:1,1:7) ::  summer_pars = RESHAPE( (/                & ! building_type 1
     324                                          0.5_wp,                             & ! basical airflow without occupancy of the room
     325                                          2.0_wp,                             & ! additional airflow depend of occupancy of the room
     326                                          0.5_wp,                             & ! building_type 2: basical airflow without occupancy
     327                                                                                ! of the room
     328                                          2.0_wp,                             & ! additional airflow depend of occupancy of the room
     329                                          0.8_wp,                             & ! building_type 3: basical airflow without occupancy
     330                                                                                ! of the room
     331                                          2.0_wp,                             & ! additional airflow depend of occupancy of the room
     332                                          0.1_wp,                             & ! building_type 4: basical airflow without occupancy
     333                                                                                ! of the room
     334                                          1.5_wp,                             & ! additional airflow depend of occupancy of the room
     335                                          0.1_wp,                             & ! building_type 5: basical airflow without occupancy
     336                                                                                ! of the room
     337                                          1.5_wp,                             & ! additional airflow depend of occupancy of the room
     338                                          0.1_wp,                             & ! building_type 6: basical airflow without occupancy
     339                                                                                ! of the room
     340                                          1.5_wp,                             & ! additional airflow depend of occupancy of the room
     341                                          0.1_wp,                             & ! building_type 7: basical airflow without occupancy
     342                                                                                ! of the room
     343                                          1.5_wp                              & ! additional airflow depend of occupancy of the room
    331344                                                           /), (/ 2, 7 /) )
    332345
    333     REAL(wp), DIMENSION(0:1,1:7) ::  winter_pars = RESHAPE( (/               & ! building_type 1
    334                                           0.1_wp,                              & ! basical airflow without occupancy of the room
    335                                           0.5_wp,                              & ! additional airflow depend of occupancy of the room
    336                                           0.1_wp,                              & ! building_type 2: basical airflow without occupancy of the room
    337                                           0.5_wp,                              & ! additional airflow depend of occupancy of the room
    338                                           0.1_wp,                              & ! building_type 3: basical airflow without occupancy of the room
    339                                           0.5_wp,                              & ! additional airflow depend of occupancy of the room
    340                                           0.1_wp,                              & ! building_type 4: basical airflow without occupancy of the room
    341                                           1.5_wp,                              & ! additional airflow depend of occupancy of the room
    342                                           0.1_wp,                              & ! building_type 5: basical airflow without occupancy of the room
    343                                           1.5_wp,                              & ! additional airflow depend of occupancy of the room
    344                                           0.1_wp,                              & ! building_type 6: basical airflow without occupancy of the room
    345                                           1.5_wp,                              & ! additional airflow depend of occupancy of the room
    346                                           0.1_wp,                              & ! building_type 7: basical airflow without occupancy of the room
    347                                           1.5_wp                               & ! additional airflow depend of occupancy of the room
     346    REAL(wp), DIMENSION(0:1,1:7) ::  winter_pars = RESHAPE( (/                & ! building_type 1
     347                                          0.1_wp,                             & ! basical airflow without occupancy of the room
     348                                          0.5_wp,                             & ! additional airflow depend of occupancy of the room
     349                                          0.1_wp,                             & ! building_type 2: basical airflow without occupancy
     350                                                                                ! of the room
     351                                          0.5_wp,                             & ! additional airflow depend of occupancy of the room
     352                                          0.1_wp,                             & ! building_type 3: basical airflow without occupancy
     353                                                                                ! of the room
     354                                          0.5_wp,                             & ! additional airflow depend of occupancy of the room
     355                                          0.1_wp,                             & ! building_type 4: basical airflow without occupancy
     356                                                                                ! of the room
     357                                          1.5_wp,                             & ! additional airflow depend of occupancy of the room
     358                                          0.1_wp,                             & ! building_type 5: basical airflow without occupancy
     359                                                                                ! of the room
     360                                          1.5_wp,                             & ! additional airflow depend of occupancy of the room
     361                                          0.1_wp,                             & ! building_type 6: basical airflow without occupancy
     362                                                                                ! of the room
     363                                          1.5_wp,                             & ! additional airflow depend of occupancy of the room
     364                                          0.1_wp,                             & ! building_type 7: basical airflow without occupancy
     365                                                                                ! of the room
     366                                          1.5_wp                              & ! additional airflow depend of occupancy of the room
    348367                                                           /), (/ 2, 7 /) )
    349368
     
    352371
    353372    PRIVATE
    354    
     373
    355374!
    356375!-- Add INTERFACES that must be available to other modules
    357     PUBLIC im_init, im_main_heatcool, im_parin, im_define_netcdf_grid,          &
    358            im_check_data_output, im_data_output_3d, im_check_parameters
    359    
     376    PUBLIC im_init, im_main_heatcool, im_parin, im_define_netcdf_grid, im_check_data_output,       &
     377           im_data_output_3d, im_check_parameters
     378
    360379
    361380!
     
    385404        MODULE PROCEDURE im_define_netcdf_grid
    386405     END INTERFACE im_define_netcdf_grid
    387 ! 
     406!
    388407! !
    389408! !-- Output of information to the header file
     
    392411!     END INTERFACE im_header
    393412!
    394 !-- Calculations for indoor temperatures 
     413!-- Calculations for indoor temperatures
    395414    INTERFACE im_calc_temperatures
    396415       MODULE PROCEDURE im_calc_temperatures
    397416    END INTERFACE im_calc_temperatures
    398417!
    399 !-- Initialization actions 
     418!-- Initialization actions
    400419    INTERFACE im_init
    401420       MODULE PROCEDURE im_init
    402421    END INTERFACE im_init
    403422!
    404 !-- Main part of indoor model 
     423!-- Main part of indoor model
    405424    INTERFACE im_main_heatcool
    406425       MODULE PROCEDURE im_main_heatcool
     
    414433 CONTAINS
    415434
    416 !------------------------------------------------------------------------------!
     435!--------------------------------------------------------------------------------------------------!
    417436! Description:
    418437! ------------
    419 !< Calculation of the air temperatures and mean radiation temperature
    420 !< This is basis for the operative temperature
    421 !< Based on a Crank-Nicholson scheme with a timestep of a hour
    422 !------------------------------------------------------------------------------!
    423  SUBROUTINE im_calc_temperatures ( i, j, k, indoor_wall_window_temperature,    &
     438!< Calculation of the air temperatures and mean radiation temperature.
     439!< This is basis for the operative temperature.
     440!< Based on a Crank-Nicholson scheme with a timestep of a hour.
     441!--------------------------------------------------------------------------------------------------!
     442 SUBROUTINE im_calc_temperatures ( i, j, k, indoor_wall_window_temperature,                        &
    424443                                   near_facade_temperature, phi_hc_nd_dummy )
    425444
     
    427446    INTEGER(iwp) ::  j
    428447    INTEGER(iwp) ::  k
    429    
     448
    430449    REAL(wp) ::  indoor_wall_window_temperature  !< weighted temperature of innermost wall/window layer
    431450    REAL(wp) ::  near_facade_temperature
     
    433452!
    434453!-- Calculation of total mass specific thermal load (internal and external)
    435     phi_mtot = ( phi_m + h_t_wm * indoor_wall_window_temperature               &
    436                        + h_t_3  * ( phi_st + h_t_es * pt(k,j,i)                &
    437                                             + h_t_1 *                          &
    438                                     ( ( ( phi_ia + phi_hc_nd_dummy ) / h_v )   &
    439                                                  + near_facade_temperature )   &
    440                                    ) / h_t_2                                   &
     454    phi_mtot = ( phi_m + h_t_wm * indoor_wall_window_temperature                                   &
     455                       + h_t_3  * ( phi_st + h_t_es * pt(k,j,i)                                    &
     456                                            + h_t_1 *                                              &
     457                                    ( ( ( phi_ia + phi_hc_nd_dummy ) / h_v )                       &
     458                                                 + near_facade_temperature )                       &
     459                                  ) / h_t_2                                                        &
    441460               )                                                                !< [degree_C] Eq. (C.5)
    442 ! 
     461!
    443462!-- Calculation of component temperature at factual timestep
    444     theta_m_t = ( ( theta_m_t_prev                                             &
    445                     * ( ( c_m / 3600.0_wp ) - 0.5_wp * ( h_t_3 + h_t_wm ) )    &
    446                      + phi_mtot                                                &
    447                   )                                                            &
    448                   /   ( ( c_m / 3600.0_wp ) + 0.5_wp * ( h_t_3 + h_t_wm ) )    &
     463    theta_m_t = ( ( theta_m_t_prev                                                                 &
     464                    * ( ( c_m / 3600.0_wp ) - 0.5_wp * ( h_t_3 + h_t_wm ) )                        &
     465                     + phi_mtot                                                                    &
     466                  )                                                                                &
     467                  /   ( ( c_m / 3600.0_wp ) + 0.5_wp * ( h_t_3 + h_t_wm ) )                        &
    449468                )                                                               !< [degree_C] Eq. (C.4)
    450469!
    451470!-- Calculation of mean inner temperature for the RC-node in actual timestep
    452471    theta_m = ( theta_m_t + theta_m_t_prev ) * 0.5_wp                           !< [degree_C] Eq. (C.9)
    453    
     472
    454473!
    455474!-- Calculation of mean surface temperature of the RC-node in actual timestep
    456     theta_s = ( (   h_t_ms * theta_m + phi_st + h_t_es * pt(k,j,i)             &
    457                   + h_t_1  * ( near_facade_temperature                         &
    458                            + ( phi_ia + phi_hc_nd_dummy ) / h_v )              &
    459                 )                                                              &
    460                 / ( h_t_ms + h_t_es + h_t_1 )                                  &
     475    theta_s = ( (   h_t_ms * theta_m + phi_st + h_t_es * pt(k,j,i)                                 &
     476                  + h_t_1  * ( near_facade_temperature                                             &
     477                           + ( phi_ia + phi_hc_nd_dummy ) / h_v )                                  &
     478                )                                                                                  &
     479                / ( h_t_ms + h_t_es + h_t_1 )                                                      &
    461480              )                                                                 !< [degree_C] Eq. (C.10)
    462    
     481
    463482!
    464483!-- Calculation of the air temperature of the RC-node
    465     theta_air = ( h_t_is * theta_s + h_v * near_facade_temperature             &
    466                 + phi_ia + phi_hc_nd_dummy ) / ( h_t_is + h_v )                 !< [degree_C] Eq. (C.11)
     484    theta_air = ( h_t_is * theta_s + h_v * near_facade_temperature + phi_ia + phi_hc_nd_dummy ) /  &
     485                ( h_t_is + h_v )                                                !< [degree_C] Eq. (C.11)
    467486
    468487 END SUBROUTINE im_calc_temperatures
    469488
    470 !------------------------------------------------------------------------------!
     489
     490!--------------------------------------------------------------------------------------------------!
    471491! Description:
    472492! ------------
    473493!> Initialization of the indoor model.
    474 !> Static information are calculated here, e.g. building parameters and
    475 !> geometrical information, everything that doesn't change in time.
     494!> Static information are calculated here, e.g. building parameters and geometrical information,
     495!> anything that doesn't change in time.
    476496!
    477497!-- Input values
     
    480500!     theta_e              -->  pt(k,j,i)                         !< undisturbed outside temperature, 1. PALM volume, for windows
    481501!     theta_sup = theta_f  -->  surf_usm_h%pt_10cm(m)
    482 !                               surf_usm_v(l)%pt_10cm(m)          !< Air temperature, facade near (10cm) air temperature from 1. Palm volume
     502!                               surf_usm_v(l)%pt_10cm(m)          !< Air temperature, facade near (10cm) air temperature from
     503                                                                  !< 1. Palm volume
    483504!     theta_node           -->  t_wall_h(nzt_wall,m)
    484505!                               t_wall_v(l)%t(nzt_wall,m)         !< Temperature of innermost wall layer, for opaque wall
    485 !------------------------------------------------------------------------------!
     506!--------------------------------------------------------------------------------------------------!
    486507 SUBROUTINE im_init
    487508
    488     USE control_parameters,                                                    &
     509    USE control_parameters,                                                                        &
    489510        ONLY:  message_string, time_since_reference_point
    490511
    491     USE indices,                                                               &
     512    USE indices,                                                                                   &
    492513        ONLY:  nxl, nxr, nyn, nys, nzb, nzt, wall_flags_total_0
    493514
    494     USE grid_variables,                                                        &
     515    USE grid_variables,                                                                            &
    495516        ONLY:  dx, dy
    496517
    497518    USE pegrid
    498519
    499     USE surface_mod,                                                           &
     520    USE surface_mod,                                                                               &
    500521        ONLY:  surf_usm_h, surf_usm_v
    501        
    502     USE urban_surface_mod,                                                     &
     522
     523    USE urban_surface_mod,                                                                         &
    503524        ONLY:  building_pars, building_type
    504525
     
    514535
    515536    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids           !< building IDs on entire model domain
    516     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_final     !< building IDs on entire model domain, 
    517                                                                     !< multiple occurences are sorted out 
     537    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_final     !< building IDs on entire model domain,
     538                                                                    !< multiple occurences are sorted out
    518539    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_final_tmp !< temporary array used for resizing
    519540    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_l         !< building IDs on local subdomain
     
    523544    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  k_min_l             !< lowest vertical index of a building on subdomain
    524545    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  n_fa                !< counting array
    525     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facades_h       !< dummy array used for summing-up total number of 
     546    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facades_h       !< dummy array used for summing-up total number of
    526547                                                                    !< horizontal facade elements
    527     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facades_v       !< dummy array used for summing-up total number of 
     548    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facades_v       !< dummy array used for summing-up total number of
    528549                                                                    !< vertical facade elements
    529     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  receive_dum_h       !< dummy array used for MPI_ALLREDUCE 
    530     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  receive_dum_v       !< dummy array used for MPI_ALLREDUCE 
    531    
     550    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  receive_dum_h       !< dummy array used for MPI_ALLREDUCE
     551    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  receive_dum_v       !< dummy array used for MPI_ALLREDUCE
     552
    532553    INTEGER(iwp), DIMENSION(0:numprocs-1) ::  num_buildings         !< number of buildings with different ID on entire model domain
    533554    INTEGER(iwp), DIMENSION(0:numprocs-1) ::  num_buildings_l       !< number of buildings with different ID on local subdomain
    534                                                              
     555
    535556    REAL(wp) ::  u_tmp                                     !< dummy for temporary calculation of u-value without h_is
    536557    REAL(wp) ::  du_tmp                                    !< 1/u_tmp
     
    544565    CALL location_message( 'initializing indoor model', 'start' )
    545566!
    546 !-- Initializing of indoor model is only possible if buildings can be
    547 !-- distinguished by their IDs.
     567!-- Initializing of indoor model is only possible if buildings can be distinguished by their IDs.
    548568    IF ( .NOT. building_id_f%from_file )  THEN
    549569       message_string = 'Indoor model requires information about building_id'
     
    559579          IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
    560580             IF ( num_buildings_l(myid) > 0 )  THEN
    561                 IF ( ANY( building_id_f%var(j,i) .EQ.  build_ids_l ) )  THEN
     581                IF ( ANY( building_id_f%var(j,i) == build_ids_l ) )  THEN
    562582                   CYCLE
    563583                ELSE
     
    569589                   DEALLOCATE( build_ids_l )
    570590                   ALLOCATE( build_ids_l(1:num_buildings_l(myid)) )
    571                    build_ids_l(1:num_buildings_l(myid)-1) =                 &
    572                                build_ids_l_tmp(1:num_buildings_l(myid)-1)
     591                   build_ids_l(1:num_buildings_l(myid)-1) =                                        &
     592                                                          build_ids_l_tmp(1:num_buildings_l(myid)-1)
    573593                   build_ids_l(num_buildings_l(myid)) = building_id_f%var(j,i)
    574594                   DEALLOCATE( build_ids_l_tmp )
    575595                ENDIF
    576596!
    577 !--          First occuring building id on PE 
    578              ELSE 
     597!--          First occuring building id on PE
     598             ELSE
    579599                num_buildings_l(myid) = num_buildings_l(myid) + 1
    580600                build_ids_l(1) = building_id_f%var(j,i)
     
    584604    ENDDO
    585605!
    586 !-- Determine number of building IDs for the entire domain. (Note, building IDs
    587 !-- can appear multiple times as buildings might be distributed over several
    588 !-- PEs.)
    589 #if defined( __parallel )
    590     CALL MPI_ALLREDUCE( num_buildings_l, num_buildings, numprocs,              &
    591                         MPI_INTEGER, MPI_SUM, comm2d, ierr )
     606!-- Determine number of building IDs for the entire domain. (Note, building IDs can appear multiple
     607!-- times as buildings might be distributed over several PEs.)
     608#if defined( __parallel )
     609    CALL MPI_ALLREDUCE( num_buildings_l, num_buildings, numprocs, MPI_INTEGER, MPI_SUM, comm2d,    &
     610                        ierr )
    592611#else
    593612    num_buildings = num_buildings_l
     
    595614    ALLOCATE( build_ids(1:SUM(num_buildings)) )
    596615!
    597 !-- Gather building IDs. Therefore, first, determine displacements used
    598 !-- required for MPI_GATHERV call.
     616!-- Gather building IDs. Therefore, first, determine displacements used required for MPI_GATHERV
     617!-- call.
    599618    ALLOCATE( displace_dum(0:numprocs-1) )
    600619    displace_dum(0) = 0
     
    603622    ENDDO
    604623
    605 #if defined( __parallel ) 
    606     CALL MPI_ALLGATHERV( build_ids_l(1:num_buildings_l(myid)),                 &
    607                          num_buildings(myid),                                  &
    608                          MPI_INTEGER,                                          &
    609                          build_ids,                                            &
    610                          num_buildings,                                        &
    611                          displace_dum,                                         &
    612                          MPI_INTEGER,                                          &
    613                          comm2d, ierr )   
     624#if defined( __parallel )
     625    CALL MPI_ALLGATHERV( build_ids_l(1:num_buildings_l(myid)),                                     &
     626                         num_buildings(myid),                                                      &
     627                         MPI_INTEGER,                                                              &
     628                         build_ids,                                                                &
     629                         num_buildings,                                                            &
     630                         displace_dum,                                                             &
     631                         MPI_INTEGER,                                                              &
     632                         comm2d, ierr )
    614633
    615634    DEALLOCATE( displace_dum )
     
    619638#endif
    620639!
    621 !-- Note: in parallel mode, building IDs can occur mutliple times, as
    622 !-- each PE has send its own ids. Therefore, sort out building IDs which
    623 !-- appear multiple times.
     640!-- Note: in parallel mode, building IDs can occur mutliple times, as each PE has send its own ids.
     641!-- Therefore, sort out building IDs which appear multiple times.
    624642    num_build = 0
    625643    DO  n = 1, SIZE(build_ids)
     
    639657             build_ids_final(num_build) = build_ids(n)
    640658             DEALLOCATE( build_ids_final_tmp )
    641           ENDIF             
     659          ENDIF
    642660       ELSE
    643661          num_build = num_build + 1
     
    648666
    649667!
    650 !-- Allocate building-data structure array. Note, this is a global array
    651 !-- and all building IDs on domain are known by each PE. Further attributes,
    652 !-- e.g. height-dependent arrays, however, are only allocated on PEs where
    653 !-- the respective building is present (in order to reduce memory demands).
     668!-- Allocate building-data structure array. Note, this is a global array and all building IDs on
     669!-- domain are known by each PE. Further attributes, e.g. height-dependent arrays, however, are only
     670!-- allocated on PEs where  the respective building is present (in order to reduce memory demands).
    654671    ALLOCATE( buildings(1:num_build) )
    655672
    656673!
    657 !-- Store building IDs and check if building with certain ID is present on
    658 !-- subdomain.
     674!-- Store building IDs and check if building with certain ID is present on subdomain.
    659675    DO  nb = 1, num_build
    660676       buildings(nb)%id = build_ids_final(nb)
    661677
    662        IF ( ANY( building_id_f%var(nys:nyn,nxl:nxr) == buildings(nb)%id ) )    &
     678       IF ( ANY( building_id_f%var(nys:nyn,nxl:nxr) == buildings(nb)%id ) )                        &
    663679          buildings(nb)%on_pe = .TRUE.
    664     ENDDO 
    665 !
    666 !-- Determine the maximum vertical dimension occupied by each building. 
     680    ENDDO
     681!
     682!-- Determine the maximum vertical dimension occupied by each building.
    667683    ALLOCATE( k_min_l(1:num_build) )
    668684    ALLOCATE( k_max_l(1:num_build) )
    669685    k_min_l = nzt + 1
    670     k_max_l = 0   
     686    k_max_l = 0
    671687
    672688    DO  i = nxl, nxr
    673689       DO  j = nys, nyn
    674690          IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
    675              nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ),    &
    676                          DIM = 1 )
     691             nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM=1 )
    677692             DO  k = nzb, nzt+1
    678693!
    679 !--             Check if grid point belongs to a building. 
     694!--             Check if grid point belongs to a building.
    680695                IF ( BTEST( wall_flags_total_0(k,j,i), 6 ) )  THEN
    681696                   k_min_l(nb) = MIN( k_min_l(nb), k )
     
    688703    ENDDO
    689704
    690 #if defined( __parallel ) 
    691     CALL MPI_ALLREDUCE( k_min_l(:), buildings(:)%kb_min, num_build,            &
    692                         MPI_INTEGER, MPI_MIN, comm2d, ierr )
    693     CALL MPI_ALLREDUCE( k_max_l(:), buildings(:)%kb_max, num_build,            &
    694                         MPI_INTEGER, MPI_MAX, comm2d, ierr )
     705#if defined( __parallel )
     706    CALL MPI_ALLREDUCE( k_min_l(:), buildings(:)%kb_min, num_build, MPI_INTEGER, MPI_MIN, comm2d,  &
     707                        ierr )
     708    CALL MPI_ALLREDUCE( k_max_l(:), buildings(:)%kb_max, num_build, MPI_INTEGER, MPI_MAX, comm2d,  &
     709                        ierr )
    695710#else
    696711    buildings(:)%kb_min = k_min_l(:)
     
    705720       buildings(nb)%building_height = 0.0_wp
    706721       DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
    707           buildings(nb)%building_height = buildings(nb)%building_height        &
    708                                         + dzw(k+1)
     722          buildings(nb)%building_height = buildings(nb)%building_height + dzw(k+1)
    709723       ENDDO
    710724    ENDDO
     
    719733       volume_l = 0.0_wp
    720734!
    721 !--    Calculate building volume per height level on each PE where
    722 !--    these building is present.
     735!--    Calculate building volume per height level on each PE where these building is present.
    723736       IF ( buildings(nb)%on_pe )  THEN
    724737
     
    727740          buildings(nb)%volume   = 0.0_wp
    728741          buildings(nb)%vol_frac = 0.0_wp
    729          
    730           IF ( ANY( building_id_f%var(nys:nyn,nxl:nxr) == buildings(nb)%id ) ) &
    731           THEN
     742
     743          IF ( ANY( building_id_f%var(nys:nyn,nxl:nxr) == buildings(nb)%id ) )  THEN
    732744             DO  i = nxl, nxr
    733745                DO  j = nys, nyn
    734746                   DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
    735                       IF ( building_id_f%var(j,i) /= building_id_f%fill )      &
     747                      IF ( building_id_f%var(j,i) /= building_id_f%fill )                          &
    736748                         volume_l(k) = volume_l(k) + dx * dy * dzw(k+1)
    737749                   ENDDO
     
    742754!
    743755!--    Sum-up building volume from all subdomains
    744 #if defined( __parallel )
    745        CALL MPI_ALLREDUCE( volume_l, volume, SIZE(volume), MPI_REAL, MPI_SUM,  &
    746                            comm2d, ierr )
     756#if defined( __parallel )
     757       CALL MPI_ALLREDUCE( volume_l, volume, SIZE(volume), MPI_REAL, MPI_SUM, comm2d, ierr )
    747758#else
    748759       volume = volume_l
    749760#endif
    750761!
    751 !--    Save total building volume as well as local fraction on volume on
    752 !--    building data structure.
     762!--    Save total building volume as well as local fraction on volume on building data structure.
    753763       IF ( ALLOCATED( buildings(nb)%volume ) )  buildings(nb)%volume = volume
    754764!
     
    757767!
    758768!--    Calculate total building volume
    759        IF ( ALLOCATED( buildings(nb)%volume ) )                                &
    760           buildings(nb)%vol_tot = SUM( buildings(nb)%volume )
     769       IF ( ALLOCATED( buildings(nb)%volume ) )  buildings(nb)%vol_tot = SUM( buildings(nb)%volume )
    761770
    762771       DEALLOCATE( volume   )
     
    765774    ENDDO
    766775!
    767 !-- Allocate arrays for indoor temperature. 
     776!-- Allocate arrays for indoor temperature.
    768777    DO  nb = 1, num_build
    769778       IF ( buildings(nb)%on_pe )  THEN
     
    775784    ENDDO
    776785!
    777 !-- Allocate arrays for number of facades per height level. Distinguish between
    778 !-- horizontal and vertical facades.
     786!-- Allocate arrays for number of facades per height level. Distinguish between horizontal and
     787!-- vertical facades.
    779788    DO  nb = 1, num_build
    780789       IF ( buildings(nb)%on_pe )  THEN
     
    795804!
    796805!--    For the current facade element determine corresponding building index.
    797 !--    First, obtain j,j,k indices of the building. Please note the
    798 !--    offset between facade/surface element and building location (for
    799 !--    horizontal surface elements the horizontal offsets are zero).
     806!--    First, obtain j,j,k indices of the building. Please note the offset between facade/surface
     807!--    element and building location (for horizontal surface elements the horizontal offsets are
     808!--    zero).
    800809       i = surf_usm_h%i(m) + surf_usm_h%ioff
    801810       j = surf_usm_h%j(m) + surf_usm_h%joff
    802811       k = surf_usm_h%k(m) + surf_usm_h%koff
    803812!
    804 !--    Determine building index and check whether building is on PE
    805        nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM = 1 )
     813!--    Determine building index and check whether building is on PE.
     814       nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM=1 )
    806815
    807816       IF ( buildings(nb)%on_pe )  THEN
    808817!
    809818!--       Count number of facade elements at each height level.
    810           buildings(nb)%num_facade_h(k) = buildings(nb)%num_facade_h(k) + 1 
     819          buildings(nb)%num_facade_h(k) = buildings(nb)%num_facade_h(k) + 1
    811820!
    812821!--       Moreover, sum up number of local facade elements per building.
    813           buildings(nb)%num_facades_per_building_h_l =                         &
    814                                 buildings(nb)%num_facades_per_building_h_l + 1
     822          buildings(nb)%num_facades_per_building_h_l =                                             &
     823                                                      buildings(nb)%num_facades_per_building_h_l + 1
    815824       ENDIF
    816825    ENDDO
     
    822831!
    823832!--       For the current facade element determine corresponding building index.
    824 !--       First, obtain j,j,k indices of the building. Please note the
    825 !--       offset between facade/surface element and building location (for
    826 !--       vertical surface elements the vertical offsets are zero).
     833!--       First, obtain j,j,k indices of the building. Please note the offset between facade/surface
     834!--       element and building location (for vertical surface elements the vertical offsets are
     835!--       zero).
    827836          i = surf_usm_v(l)%i(m) + surf_usm_v(l)%ioff
    828837          j = surf_usm_v(l)%j(m) + surf_usm_v(l)%joff
    829838          k = surf_usm_v(l)%k(m) + surf_usm_v(l)%koff
    830839
    831           nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ),        &
    832                        DIM = 1 )
     840          nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM=1 )
    833841          IF ( buildings(nb)%on_pe )  THEN
    834              buildings(nb)%num_facade_v(k) = buildings(nb)%num_facade_v(k) + 1 
    835              buildings(nb)%num_facades_per_building_v_l =                      &
    836                                 buildings(nb)%num_facades_per_building_v_l + 1
     842             buildings(nb)%num_facade_v(k) = buildings(nb)%num_facade_v(k) + 1
     843             buildings(nb)%num_facades_per_building_v_l =                                          &
     844                                                      buildings(nb)%num_facades_per_building_v_l + 1
    837845          ENDIF
    838846       ENDDO
    839847    ENDDO
    840848!
    841 !-- Determine total number of facade elements per building and assign number to
    842 !-- building data type.
     849!-- Determine total number of facade elements per building and assign number to building data type.
    843850    DO  nb = 1, num_build
    844851!
    845 !--    Allocate dummy array used for summing-up facade elements. 
    846 !--    Please note, dummy arguments are necessary as building-date type
    847 !--    arrays are not necessarily allocated on all PEs.
     852!--    Allocate dummy array used for summing-up facade elements.
     853!--    Please note, dummy arguments are necessary as building-date type arrays are not necessarily
     854!--    allocated on all PEs.
    848855       ALLOCATE( num_facades_h(buildings(nb)%kb_min:buildings(nb)%kb_max) )
    849856       ALLOCATE( num_facades_v(buildings(nb)%kb_min:buildings(nb)%kb_max) )
     
    860867       ENDIF
    861868
    862 #if defined( __parallel ) 
    863        CALL MPI_ALLREDUCE( num_facades_h,                                      &
    864                            receive_dum_h,                                      &
    865                            buildings(nb)%kb_max - buildings(nb)%kb_min + 1,    &
    866                            MPI_INTEGER,                                        &
    867                            MPI_SUM,                                            &
    868                            comm2d,                                             &
     869#if defined( __parallel )
     870       CALL MPI_ALLREDUCE( num_facades_h,                                                          &
     871                           receive_dum_h,                                                          &
     872                           buildings(nb)%kb_max - buildings(nb)%kb_min + 1,                        &
     873                           MPI_INTEGER,                                                            &
     874                           MPI_SUM,                                                                &
     875                           comm2d,                                                                 &
    869876                           ierr )
    870877
    871        CALL MPI_ALLREDUCE( num_facades_v,                                      &
    872                            receive_dum_v,                                      &
    873                            buildings(nb)%kb_max - buildings(nb)%kb_min + 1,    &
    874                            MPI_INTEGER,                                        &
    875                            MPI_SUM,                                            &
    876                            comm2d,                                             &
     878       CALL MPI_ALLREDUCE( num_facades_v,                                                          &
     879                           receive_dum_v,                                                          &
     880                           buildings(nb)%kb_max - buildings(nb)%kb_min + 1,                        &
     881                           MPI_INTEGER,                                                            &
     882                           MPI_SUM,                                                                &
     883                           comm2d,                                                                 &
    877884                           ierr )
    878        IF ( ALLOCATED( buildings(nb)%num_facade_h ) )                          &
    879            buildings(nb)%num_facade_h = receive_dum_h
    880        IF ( ALLOCATED( buildings(nb)%num_facade_v ) )                          &
    881            buildings(nb)%num_facade_v = receive_dum_v
     885       IF ( ALLOCATED( buildings(nb)%num_facade_h ) )  buildings(nb)%num_facade_h = receive_dum_h
     886       IF ( ALLOCATED( buildings(nb)%num_facade_v ) )  buildings(nb)%num_facade_v = receive_dum_v
    882887#else
    883888       buildings(nb)%num_facade_h = num_facades_h
     
    893898!
    894899!--    Allocate index arrays which link facade elements with surface-data type.
    895 !--    Please note, no height levels are considered here (information is stored
    896 !--    in surface-data type itself).
     900!--    Please note, no height levels are considered here (information is stored in surface-data type
     901!--    itself).
    897902       IF ( buildings(nb)%on_pe )  THEN
    898903!
     
    901906          buildings(nb)%num_facades_per_building_v = SUM( buildings(nb)%num_facade_v )
    902907!
    903 !--       Allocate arrays which link the building with the horizontal and vertical
    904 !--       urban-type surfaces. Please note, linking arrays are allocated over all
    905 !--       facade elements, which is required in case a building is located at the
    906 !--       subdomain boundaries, where the building and the corresponding surface
    907 !--       elements are located on different subdomains.
     908!--       Allocate arrays which link the building with the horizontal and vertical urban-type
     909!--       surfaces. Please note, linking arrays are allocated over all facade elements, which is
     910!--       required in case a building is located at the subdomain boundaries, where the building and
     911!--       the corresponding surface elements are located on different subdomains.
    908912          ALLOCATE( buildings(nb)%m_h(1:buildings(nb)%num_facades_per_building_h_l) )
    909913
     
    916920          buildings(nb)%vpf = 0.0_wp
    917921
    918           facade_area_v = 0.0_wp         
     922          facade_area_v = 0.0_wp
    919923          DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
    920              facade_area_v = facade_area_v + buildings(nb)%num_facade_v(k)     &
    921                              * dzw(k+1) * dx
     924             facade_area_v = facade_area_v + buildings(nb)%num_facade_v(k) * dzw(k+1) * dx
    922925          ENDDO
    923926!
    924 !--       Determine volume per total facade area (vpf). For the horizontal facade
    925 !--       area num_facades_per_building_h can be taken, multiplied with dx*dy.
    926 !--       However, due to grid stretching, vertical facade elements must be
    927 !--       summed-up vertically. Please note, if dx /= dy, an error is made!
    928           buildings(nb)%vpf = buildings(nb)%vol_tot /                          &
    929                         ( buildings(nb)%num_facades_per_building_h * dx * dy + &
    930                           facade_area_v )
     927!--       Determine volume per total facade area (vpf). For the horizontal facade area
     928!--       num_facades_per_building_h can be taken, multiplied with dx*dy.
     929!--       However, due to grid stretching, vertical facade elements must be summed-up vertically.
     930!--       Please note, if dx /= dy, an error is made!
     931          buildings(nb)%vpf = buildings(nb)%vol_tot /                                              &
     932                              ( buildings(nb)%num_facades_per_building_h * dx * dy + facade_area_v )
    931933!
    932934!--       Determine floor-area-per-facade.
    933           buildings(nb)%fapf = buildings(nb)%num_facades_per_building_h        &
    934                              * dx * dy                                         &
    935                              / ( buildings(nb)%num_facades_per_building_h      &
    936                                * dx * dy + facade_area_v )
     935          buildings(nb)%fapf = buildings(nb)%num_facades_per_building_h     * dx * dy              &
     936                               / ( buildings(nb)%num_facades_per_building_h * dx * dy              &
     937                                   + facade_area_v )
    937938       ENDIF
    938939    ENDDO
    939940!
    940 !-- Link facade elements with surface data type. 
     941!-- Link facade elements with surface data type.
    941942!-- Allocate array for counting.
    942943    ALLOCATE( n_fa(1:num_build) )
     
    947948       j = surf_usm_h%j(m) + surf_usm_h%joff
    948949
    949        nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM = 1 )
     950       nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM=1 )
    950951
    951952       IF ( buildings(nb)%on_pe )  THEN
    952953          buildings(nb)%m_h(n_fa(nb)) = m
    953           n_fa(nb) = n_fa(nb) + 1 
     954          n_fa(nb) = n_fa(nb) + 1
    954955       ENDIF
    955956    ENDDO
     
    961962          j = surf_usm_v(l)%j(m) + surf_usm_v(l)%joff
    962963
    963           nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM = 1 )
     964          nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM=1 )
    964965
    965966          IF ( buildings(nb)%on_pe )  THEN
    966967             buildings(nb)%l_v(n_fa(nb)) = l
    967968             buildings(nb)%m_v(n_fa(nb)) = m
    968              n_fa(nb) = n_fa(nb) + 1   
     969             n_fa(nb) = n_fa(nb) + 1
    969970          ENDIF
    970971       ENDDO
     
    972973    DEALLOCATE( n_fa )
    973974!
    974 !-- Initialize building parameters, first by mean building type. Note,
    975 !-- in this case all buildings have the same type.
    976 !-- In a second step initialize with building tpyes from static input file,
    977 !-- where building types can be individual for each building.
     975!-- Initialize building parameters, first by mean building type. Note, in this case all buildings
     976!-- have the same type.
     977!-- In a second step initialize with building tpyes from static input file, where building types can
     978!-- be individual for each building.
    978979    buildings(:)%lambda_layer3       = building_pars(31,building_type)
    979980    buildings(:)%s_layer3            = building_pars(44,building_type)
    980981    buildings(:)%f_c_win             = building_pars(119,building_type)
    981     buildings(:)%g_value_win         = building_pars(120,building_type)   
    982     buildings(:)%u_value_win         = building_pars(121,building_type)       
    983     buildings(:)%eta_ve              = building_pars(124,building_type)   
    984     buildings(:)%factor_a            = building_pars(125,building_type)   
     982    buildings(:)%g_value_win         = building_pars(120,building_type)
     983    buildings(:)%u_value_win         = building_pars(121,building_type)
     984    buildings(:)%eta_ve              = building_pars(124,building_type)
     985    buildings(:)%factor_a            = building_pars(125,building_type)
    985986    buildings(:)%factor_c            = building_pars(126,building_type)
    986     buildings(:)%lambda_at           = building_pars(127,building_type)   
    987     buildings(:)%theta_int_h_set     = building_pars(13,building_type)   
     987    buildings(:)%lambda_at           = building_pars(127,building_type)
     988    buildings(:)%theta_int_h_set     = building_pars(13,building_type)
    988989    buildings(:)%theta_int_c_set     = building_pars(12,building_type)
    989     buildings(:)%q_h_max             = building_pars(128,building_type)   
    990     buildings(:)%q_c_max             = building_pars(129,building_type)         
     990    buildings(:)%q_h_max             = building_pars(128,building_type)
     991    buildings(:)%q_c_max             = building_pars(129,building_type)
    991992    buildings(:)%qint_high           = building_pars(130,building_type)
    992993    buildings(:)%qint_low            = building_pars(131,building_type)
     
    997998!
    998999!-- Initialize seasonal dependent parameters, depending on day of the year.
    999 !-- First, calculated day of the year. 
     1000!-- First, calculated day of the year.
    10001001    CALL get_date_time( time_since_reference_point, day_of_year = day_of_year )
    10011002!
    1002 !-- Summer is defined in between northward- and southward equinox.
    1003     IF ( day_of_year >= northward_equinox  .AND.                               &
    1004          day_of_year <= southward_equinox )  THEN
    1005        buildings(:)%air_change_low      = summer_pars(0,building_type)   
     1003!-- Summer is defined in between northward- and southward equinox.
     1004    IF ( day_of_year >= northward_equinox  .AND.  day_of_year <= southward_equinox )  THEN
     1005       buildings(:)%air_change_low      = summer_pars(0,building_type)
    10061006       buildings(:)%air_change_high     = summer_pars(1,building_type)
    10071007    ELSE
    1008        buildings(:)%air_change_low      = winter_pars(0,building_type)   
     1008       buildings(:)%air_change_low      = winter_pars(0,building_type)
    10091009       buildings(:)%air_change_high     = winter_pars(1,building_type)
    10101010    ENDIF
    10111011!
    1012 !-- Initialize ventilaation load. Please note, building types > 7 are actually
    1013 !-- not allowed (check already in urban_surface_mod and netcdf_data_input_mod.
    1014 !-- However, the building data base may be later extended. 
    1015     IF ( building_type ==  1  .OR.  building_type ==  2  .OR.                  &
    1016          building_type ==  3  .OR.  building_type == 10  .OR.                  &
     1012!-- Initialize ventilation load. Please note, building types > 7 are actually not allowed (check
     1013!-- already in urban_surface_mod and netcdf_data_input_mod.
     1014!-- However, the building data base may be later extended.
     1015    IF ( building_type ==  1  .OR.  building_type ==  2  .OR.                                      &
     1016         building_type ==  3  .OR.  building_type == 10  .OR.                                      &
    10171017         building_type == 11  .OR.  building_type == 12 )  THEN
    10181018       buildings(:)%ventilation_int_loads = 1
    10191019!
    10201020!-- Office, building with large windows
    1021     ELSEIF ( building_type ==  4  .OR.  building_type ==  5  .OR.              &
    1022              building_type ==  6  .OR.  building_type ==  7  .OR.              &
     1021    ELSEIF ( building_type ==  4  .OR.  building_type ==  5  .OR.                                  &
     1022             building_type ==  6  .OR.  building_type ==  7  .OR.                                  &
    10231023             building_type ==  8  .OR.  building_type ==  9)  THEN
    10241024       buildings(:)%ventilation_int_loads = 2
    10251025!
    10261026!-- Industry, hospitals
    1027     ELSEIF ( building_type == 13  .OR.  building_type == 14  .OR.              &
    1028              building_type == 15  .OR.  building_type == 16  .OR.              &
     1027    ELSEIF ( building_type == 13  .OR.  building_type == 14  .OR.                                  &
     1028             building_type == 15  .OR.  building_type == 16  .OR.                                  &
    10291029             building_type == 17  .OR.  building_type == 18 )  THEN
    10301030       buildings(:)%ventilation_int_loads = 3
     
    10361036          DO  j = nys, nyn
    10371037              IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
    1038                  nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), &
    1039                               DIM = 1 )
     1038                 nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM=1 )
    10401039                 bt = building_type_f%var(j,i)
    1041                  
     1040
    10421041                 buildings(nb)%lambda_layer3       = building_pars(31,bt)
    10431042                 buildings(nb)%s_layer3            = building_pars(44,bt)
    10441043                 buildings(nb)%f_c_win             = building_pars(119,bt)
    1045                  buildings(nb)%g_value_win         = building_pars(120,bt)   
    1046                  buildings(nb)%u_value_win         = building_pars(121,bt)   
    1047                  buildings(nb)%eta_ve              = building_pars(124,bt)   
    1048                  buildings(nb)%factor_a            = building_pars(125,bt)   
     1044                 buildings(nb)%g_value_win         = building_pars(120,bt)
     1045                 buildings(nb)%u_value_win         = building_pars(121,bt)
     1046                 buildings(nb)%eta_ve              = building_pars(124,bt)
     1047                 buildings(nb)%factor_a            = building_pars(125,bt)
    10491048                 buildings(nb)%factor_c            = building_pars(126,bt)
    1050                  buildings(nb)%lambda_at           = building_pars(127,bt)   
    1051                  buildings(nb)%theta_int_h_set     = building_pars(13,bt)   
     1049                 buildings(nb)%lambda_at           = building_pars(127,bt)
     1050                 buildings(nb)%theta_int_h_set     = building_pars(13,bt)
    10521051                 buildings(nb)%theta_int_c_set     = building_pars(12,bt)
    1053                  buildings(nb)%q_h_max             = building_pars(128,bt)   
    1054                  buildings(nb)%q_c_max             = building_pars(129,bt)         
     1052                 buildings(nb)%q_h_max             = building_pars(128,bt)
     1053                 buildings(nb)%q_c_max             = building_pars(129,bt)
    10551054                 buildings(nb)%qint_high           = building_pars(130,bt)
    10561055                 buildings(nb)%qint_low            = building_pars(131,bt)
    10571056                 buildings(nb)%height_storey       = building_pars(132,bt)
    1058                  buildings(nb)%height_cei_con      = building_pars(133,bt) 
     1057                 buildings(nb)%height_cei_con      = building_pars(133,bt)
    10591058                 buildings(nb)%params_waste_heat_h = building_pars(134,bt)
    10601059                 buildings(nb)%params_waste_heat_c = building_pars(135,bt)
    10611060
    1062               IF ( day_of_year >= northward_equinox  .AND.                     &
    1063                    day_of_year <= southward_equinox )  THEN
    1064                  buildings(nb)%air_change_low      = summer_pars(0,bt)   
     1061              IF ( day_of_year >= northward_equinox  .AND.  day_of_year <= southward_equinox )  THEN
     1062                 buildings(nb)%air_change_low      = summer_pars(0,bt)
    10651063                 buildings(nb)%air_change_high     = summer_pars(1,bt)
    10661064              ELSE
    1067                  buildings(nb)%air_change_low      = winter_pars(0,bt)   
     1065                 buildings(nb)%air_change_low      = winter_pars(0,bt)
    10681066                 buildings(nb)%air_change_high     = winter_pars(1,bt)
    10691067              ENDIF
    10701068
    10711069!
    1072 !--              Initialize ventilaation load. Please note, building types > 7 
    1073 !--              are actually not allowed (check already in urban_surface_mod 
    1074 !--              and netcdf_data_input_mod. However, the building data base may 
    1075 !--              be later extended. 
    1076                  IF ( bt ==  1  .OR.  bt ==  2  .OR.                           &
    1077                       bt ==  3  .OR.  bt == 10  .OR.                           &
     1070!--              Initialize ventilaation load. Please note, building types > 7
     1071!--              are actually not allowed (check already in urban_surface_mod
     1072!--              and netcdf_data_input_mod. However, the building data base may
     1073!--              be later extended.
     1074                 IF ( bt ==  1  .OR.  bt ==  2  .OR.                                               &
     1075                      bt ==  3  .OR.  bt == 10  .OR.                                               &
    10781076                      bt == 11  .OR.  bt == 12 )  THEN
    10791077                    buildings(nb)%ventilation_int_loads = 1
    1080 !                   
     1078!
    10811079!--              Office, building with large windows
    1082                  ELSEIF ( bt ==  4  .OR.  bt ==  5  .OR.                       &
    1083                           bt ==  6  .OR.  bt ==  7  .OR.                       &
     1080                 ELSEIF ( bt ==  4  .OR.  bt ==  5  .OR.                                           &
     1081                          bt ==  6  .OR.  bt ==  7  .OR.                                           &
    10841082                          bt ==  8  .OR.  bt ==  9)  THEN
    10851083                    buildings(nb)%ventilation_int_loads = 2
    10861084!
    10871085!--              Industry, hospitals
    1088                  ELSEIF ( bt == 13  .OR.  bt == 14  .OR.                       &
    1089                           bt == 15  .OR.  bt == 16  .OR.                       &
     1086                 ELSEIF ( bt == 13  .OR.  bt == 14  .OR.                                           &
     1087                          bt == 15  .OR.  bt == 16  .OR.                                           &
    10901088                          bt == 17  .OR.  bt == 18 )  THEN
    10911089                    buildings(nb)%ventilation_int_loads = 3
     
    10961094    ENDIF
    10971095!
    1098 !-- Calculation of surface-related heat transfer coeffiecient
    1099 !-- out of standard u-values from building database
    1100 !-- only amount of extern and surface is used
    1101 !-- otherwise amount between air and surface taken account twice
     1096!-- Calculation of surface-related heat transfer coeffiecient out of standard u-values from building
     1097!-- database.
     1098!-- Only amount of extern and surface is used.
     1099!-- Otherwise amount between air and surface taken account twice.
    11021100    DO nb = 1, num_build
    1103        IF ( buildings(nb)%on_pe ) THEN   
     1101       IF ( buildings(nb)%on_pe ) THEN
    11041102          du_win_tmp = 1.0_wp / buildings(nb)%u_value_win
    1105           u_tmp = buildings(nb)%u_value_win * ( du_win_tmp / ( du_win_tmp -    &
     1103          u_tmp = buildings(nb)%u_value_win * ( du_win_tmp / ( du_win_tmp -                        &
    11061104                  0.125_wp + ( 1.0_wp / h_is ) ) )
    1107                  
     1105
    11081106          du_tmp = 1.0_wp / u_tmp
    1109          
     1107
    11101108          buildings(nb)%h_es = 1.0_wp / ( du_tmp - ( 1.0_wp / h_is ) )
    11111109
     
    11191117!-- Initialize indoor temperature. Actually only for output at initial state.
    11201118    DO  nb = 1, num_build
    1121        IF ( buildings(nb)%on_pe )                                              &
    1122           buildings(nb)%t_in(:) = initial_indoor_temperature
     1119       IF ( buildings(nb)%on_pe )  buildings(nb)%t_in(:) = initial_indoor_temperature
    11231120    ENDDO
    11241121
     
    11281125
    11291126
    1130 !------------------------------------------------------------------------------!
     1127!--------------------------------------------------------------------------------------------------!
    11311128! Description:
    11321129! ------------
    11331130!> Main part of the indoor model.
    11341131!> Calculation of .... (kanani: Please describe)
    1135 !------------------------------------------------------------------------------!
     1132!--------------------------------------------------------------------------------------------------!
    11361133 SUBROUTINE im_main_heatcool
    11371134
     
    11391136!         ONLY:  c_p
    11401137
    1141     USE control_parameters,                                                    &
     1138    USE control_parameters,                                                                        &
    11421139        ONLY:  time_since_reference_point
    11431140
    1144     USE grid_variables,                                                        &
     1141    USE grid_variables,                                                                            &
    11451142        ONLY:  dx, dy
    11461143
    11471144    USE pegrid
    1148    
    1149     USE surface_mod,                                                           &
     1145
     1146    USE surface_mod,                                                                               &
    11501147        ONLY:  ind_veg_wall, ind_wat_win, surf_usm_h, surf_usm_v
    11511148
    1152     USE urban_surface_mod,                                                     &
    1153         ONLY:  nzt_wall, t_wall_h, t_wall_v, t_window_h, t_window_v,           &
    1154                building_type
    1155 
     1149    USE urban_surface_mod,                                                                         &
     1150        ONLY:  building_type, nzt_wall, t_wall_h, t_wall_v, t_window_h, t_window_v
     1151
     1152
     1153    INTEGER(iwp) ::  fa   !< running index for facade elements of each building
    11561154    INTEGER(iwp) ::  i    !< index of facade-adjacent atmosphere grid point in x-direction
    11571155    INTEGER(iwp) ::  j    !< index of facade-adjacent atmosphere grid point in y-direction
     
    11611159    INTEGER(iwp) ::  m    !< running index surface elements
    11621160    INTEGER(iwp) ::  nb   !< running index for buildings
    1163     INTEGER(iwp) ::  fa   !< running index for facade elements of each building
    11641161
    11651162    REAL(wp) ::  indoor_wall_window_temperature   !< weighted temperature of innermost wall/window layer
     
    11711168    REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in_recv     !< dummy recv buffer used for summing-up indoor temperature per kk-level
    11721169!
    1173 !-- Determine time of day in hours. 
     1170!-- Determine time of day in hours.
    11741171    CALL get_date_time( time_since_reference_point, second_of_day=second_of_day )
    11751172    time_utc_hour = second_of_day / seconds_per_hour
     
    11781175    DO  nb = 1, num_build
    11791176!
    1180 !--    First, check whether building is present on local subdomain. 
     1177!--    First, check whether building is present on local subdomain.
    11811178       IF ( buildings(nb)%on_pe )  THEN
    11821179!
    11831180!--       Determine daily schedule. 08:00-18:00 = 1, other hours = 0.
    1184 !--       Residental Building, panel WBS 70   
     1181!--       Residental Building, panel WBS 70
    11851182          IF ( buildings(nb)%ventilation_int_loads == 1 )  THEN
    11861183             IF ( time_utc_hour >= 8.0_wp  .AND.  time_utc_hour <= 18.0_wp )  THEN
     
    11991196             ENDIF
    12001197          ENDIF
    1201 !       
     1198!
    12021199!--       Industry, hospitals
    12031200          IF ( buildings(nb)%ventilation_int_loads == 3 )  THEN
     
    12101207!
    12111208!--       Initialize/reset indoor temperature
    1212           buildings(nb)%t_in_l = 0.0_wp 
     1209          buildings(nb)%t_in_l = 0.0_wp
    12131210!
    12141211!--       Horizontal surfaces
    12151212          DO  fa = 1, buildings(nb)%num_facades_per_building_h_l
    12161213!
    1217 !--          Determine index where corresponding surface-type information
    1218 !--          is stored.
     1214!--          Determine index where corresponding surface-type information is stored.
    12191215             m = buildings(nb)%m_h(fa)
    12201216!
    1221 !--          Determine building height level index. 
     1217!--          Determine building height level index.
    12221218             kk = surf_usm_h%k(m) + surf_usm_h%koff
    12231219!
    12241220!--          Building geometries --> not time-dependent
    1225              facade_element_area          = dx * dy                               !< [m2] surface area per facade element   
     1221             facade_element_area          = dx * dy                               !< [m2] surface area per facade element
    12261222             floor_area_per_facade        = buildings(nb)%fapf                    !< [m2/m2] floor area per facade area
    1227              indoor_volume_per_facade     = buildings(nb)%vpf(kk)                 !< [m3/m2] indoor air volume per facade area
    1228              buildings(nb)%area_facade    = facade_element_area *                                   &
    1229                                           ( buildings(nb)%num_facades_per_building_h +              &
    1230                                             buildings(nb)%num_facades_per_building_v )                !< [m2] area of total facade
    1231              window_area_per_facade       = surf_usm_h%frac(m,ind_wat_win)  * facade_element_area     !< [m2] window area per facade element
     1223             indoor_volume_per_facade     = buildings(nb)%vpf(kk)                 !< [m3/m2] indoor air volume per facade area
     1224             buildings(nb)%area_facade    = facade_element_area *                                  &
     1225                                            ( buildings(nb)%num_facades_per_building_h +           &
     1226                                              buildings(nb)%num_facades_per_building_v )              !< [m2] area of total facade
     1227             window_area_per_facade       = surf_usm_h%frac(m,ind_wat_win)  * facade_element_area     !< [m2] window area per facade
     1228                                                                                                      !< element
    12321229
    12331230             buildings(nb)%net_floor_area = buildings(nb)%vol_tot / ( buildings(nb)%height_storey )
    1234              total_area                   = buildings(nb)%net_floor_area                              !< [m2] area of all surfaces pointing to zone  Eq. (9) according to section 7.2.2.2
    1235              a_m                          = buildings(nb)%factor_a * total_area *                   &
    1236                                           ( facade_element_area / buildings(nb)%area_facade ) *     &
    1237                                             buildings(nb)%lambda_at                                   !< [m2] standard values according to Table 12 section 12.3.1.2  (calculate over Eq. (65) according to section 12.3.1.2)
    1238              c_m                          = buildings(nb)%factor_c * total_area *                   &
    1239                                           ( facade_element_area / buildings(nb)%area_facade )         !< [J/K] standard values according to table 12 section 12.3.1.2 (calculate over Eq. (66) according to section 12.3.1.2)             
     1231             total_area                   = buildings(nb)%net_floor_area                            !< [m2] area of all surfaces
     1232                                                                                                    !< pointing to zone  Eq. (9) according to section 7.2.2.2
     1233             a_m                          = buildings(nb)%factor_a * total_area *                  &
     1234                                            ( facade_element_area / buildings(nb)%area_facade ) *  &
     1235                                            buildings(nb)%lambda_at                                 !< [m2] standard values
     1236                                                                                                    !< according to Table 12 section 12.3.1.2  (calculate over Eq. (65) according to section 12.3.1.2)
     1237             c_m                          = buildings(nb)%factor_c * total_area *                  &
     1238                                            ( facade_element_area / buildings(nb)%area_facade )     !< [J/K] standard values
     1239                                                                                                    !< according to table 12 section 12.3.1.2 (calculate over Eq. (66) according to section 12.3.1.2)
    12401240!
    12411241!--          Calculation of heat transfer coefficient for transmission --> not time-dependent
    12421242             h_t_es   = window_area_per_facade * buildings(nb)%h_es                                   !< [W/K] only for windows
    12431243
    1244              h_t_is  = buildings(nb)%area_facade  * h_is                                                             !< [W/K] with h_is = 3.45 W / (m2 K) between surface and air, Eq. (9)
    1245              h_t_ms  = a_m * h_ms                                                                     !< [W/K] with h_ms = 9.10 W / (m2 K) between component and surface, Eq. (64)
    1246              h_t_wall  = 1.0_wp / ( 1.0_wp / ( ( facade_element_area - window_area_per_facade )     & !< [W/K]
     1244             h_t_is  = buildings(nb)%area_facade * h_is                                               !< [W/K] with h_is = 3.45 W /
     1245                                                                                                      !< (m2 K) between surface and air, Eq. (9)
     1246             h_t_ms  = a_m * h_ms                                                                     !< [W/K] with h_ms = 9.10 W /
     1247                                                                                                      !< (m2 K) between component and surface, Eq. (64)
     1248             h_t_wall  = 1.0_wp / ( 1.0_wp / ( ( facade_element_area - window_area_per_facade )    &  !< [W/K]
    12471249                                    * buildings(nb)%lambda_layer3 / buildings(nb)%s_layer3 * 0.5_wp &
    12481250                                             ) + 1.0_wp / h_t_ms )                                    !< [W/K] opaque components
    1249              h_t_wm  = 1.0_wp / ( 1.0_wp / h_t_wall - 1.0_wp / h_t_ms )                               !< [W/K] emmision Eq. (63), Section 12.2.2
    1250 !
    1251 !--          internal air loads dependent on the occupacy of the room
    1252 !--          basical internal heat gains (qint_low) with additional internal heat gains by occupancy (qint_high) (0,5*phi_int)
    1253              phi_ia = 0.5_wp * ( ( buildings(nb)%qint_high * schedule_d + buildings(nb)%qint_low )  &
    1254                               * floor_area_per_facade )
     1251             h_t_wm  = 1.0_wp / ( 1.0_wp / h_t_wall - 1.0_wp / h_t_ms )                               !< [W/K] emmision Eq. (63),
     1252                                                                                                      !< Section 12.2.2
     1253!
     1254!--          Internal air loads dependent on the occupacy of the room.
     1255!--          Basical internal heat gains (qint_low) with additional internal heat gains by occupancy (qint_high) (0,5*phi_int).
     1256             phi_ia = 0.5_wp * ( ( buildings(nb)%qint_high * schedule_d + buildings(nb)%qint_low ) &
     1257                              * floor_area_per_facade )
    12551258             q_int = phi_ia / total_area
    12561259!
    1257 !--          Airflow dependent on the occupacy of the room
    1258 !--          basical airflow (air_change_low) with additional airflow gains by occupancy (air_change_high)
    1259              air_change = ( buildings(nb)%air_change_high * schedule_d + buildings(nb)%air_change_low )  !< [1/h]? 
    1260 !
    1261 !--          Heat transfer of ventilation 
    1262 !--          not less than 0.01 W/K to provide division by 0 in further calculations
    1263 !--          with heat capacity of air 0.33 Wh/m2K
    1264              h_v   = MAX( 0.01_wp , ( air_change * indoor_volume_per_facade *      &
    1265                                     0.33_wp * (1.0_wp - buildings(nb)%eta_ve ) ) )    !< [W/K] from ISO 13789 Eq.(10)
     1260!--          Airflow dependent on the occupacy of the room.
     1261!--          Basical airflow (air_change_low) with additional airflow gains by occupancy (air_change_high)
     1262             air_change = ( buildings(nb)%air_change_high * schedule_d + buildings(nb)%air_change_low )  !< [1/h]?
     1263!
     1264!--          Heat transfer of ventilation.
     1265!--          Not less than 0.01 W/K to avoid division by 0 in further calculations with heat
     1266!--          capacity of air 0.33 Wh/m2K.
     1267             h_v   = MAX( 0.01_wp , ( air_change * indoor_volume_per_facade *                      &
     1268                                      0.33_wp * (1.0_wp - buildings(nb)%eta_ve ) ) )    !< [W/K] from ISO 13789 Eq.(10)
    12661269
    12671270!--          Heat transfer coefficient auxiliary variables
     
    12781281             k = surf_usm_h%k(m)
    12791282             near_facade_temperature = surf_usm_h%pt_10cm(m)
    1280              indoor_wall_window_temperature =                                  &
    1281                   surf_usm_h%frac(m,ind_veg_wall) * t_wall_h(nzt_wall,m)       &
    1282                 + surf_usm_h%frac(m,ind_wat_win)  * t_window_h(nzt_wall,m)
    1283 !
    1284 !--          Solar thermal gains. If net_sw_in larger than sun-protection
    1285 !--          threshold parameter (params_solar_protection), sun protection will
    1286 !--          be activated
    1287              IF ( net_sw_in <= params_solar_protection )  THEN
     1283             indoor_wall_window_temperature =                                                      &
     1284                                            surf_usm_h%frac(m,ind_veg_wall) * t_wall_h(nzt_wall,m) &
     1285                                          + surf_usm_h%frac(m,ind_wat_win)  * t_window_h(nzt_wall,m)
     1286!
     1287!--          Solar thermal gains. If net_sw_in larger than sun-protection threshold parameter
     1288!--          (params_solar_protection), sun protection will be activated.
     1289             IF ( net_sw_in <= params_solar_protection )  THEN
    12881290                solar_protection_off = 1
    12891291                solar_protection_on  = 0
    1290              ELSE 
     1292             ELSE
    12911293                solar_protection_off = 0
    12921294                solar_protection_on  = 1
    12931295             ENDIF
    12941296!
    1295 !--          Calculation of total heat gains from net_sw_in through windows [W] in respect on automatic sun protection
     1297!--          Calculation of total heat gains from net_sw_in through windows [W] in respect on
     1298!--          automatic sun protection.
    12961299!--          DIN 4108 - 2 chap.8
    1297              phi_sol = (   window_area_per_facade * net_sw_in * solar_protection_off                           &
    1298                          + window_area_per_facade * net_sw_in * buildings(nb)%f_c_win * solar_protection_on )  &
     1300             phi_sol = (   window_area_per_facade * net_sw_in * solar_protection_off               &
     1301                         + window_area_per_facade * net_sw_in * buildings(nb)%f_c_win *            &
     1302                           solar_protection_on )                                                   &
    12991303                       * buildings(nb)%g_value_win * ( 1.0_wp - params_f_f ) * params_f_w
    1300              q_sol = phi_sol           
    1301 !
    1302 !--          Calculation of the mass specific thermal load for internal and external heatsources of the inner node
    1303              phi_m   = (a_m / total_area) * ( phi_ia + phi_sol )                                    !< [W] Eq. (C.2) with phi_ia=0,5*phi_int
     1304             q_sol = phi_sol
     1305!
     1306!--          Calculation of the mass specific thermal load for internal and external heatsources of
     1307!--          the inner node.
     1308             phi_m   = (a_m / total_area) * ( phi_ia + phi_sol )                                    !< [W] Eq. (C.2) with
     1309                                                                                                    !< phi_ia=0,5*phi_int
    13041310             q_c_m = phi_m
    13051311!
    1306 !--          Calculation mass specific thermal load implied non thermal mass
    1307              phi_st  =   ( 1.0_wp - ( a_m / total_area ) - ( h_t_es / ( 9.1_wp * total_area ) ) ) &
    1308                        * ( phi_ia + phi_sol )                                                       !< [W] Eq. (C.3) with phi_ia=0,5*phi_int
    1309              q_c_st = phi_st           
     1312!--          Calculation mass specific thermal load implied non thermal mass
     1313             phi_st  =   ( 1.0_wp - ( a_m / total_area ) - ( h_t_es / ( 9.1_wp * total_area ) ) )  &
     1314                       * ( phi_ia + phi_sol )                                                       !< [W] Eq. (C.3) with
     1315                                                                                                    !< phi_ia=0,5*phi_int
     1316             q_c_st = phi_st
    13101317!
    13111318!--          Calculations for deriving indoor temperature and heat flux into the wall
    1312 !--          Step 1: Indoor temperature without heating and cooling
     1319!--          Step 1: indoor temperature without heating and cooling
    13131320!--          section C.4.1 Picture C.2 zone 3)
    13141321             phi_hc_nd = 0.0_wp
    1315              
    1316              CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
    1317                                          near_facade_temperature, phi_hc_nd )
    1318 !
    1319 !--          If air temperature between border temperatures of heating and cooling, assign output variable, then ready   
    1320              IF ( buildings(nb)%theta_int_h_set <= theta_air  .AND.  theta_air <= buildings(nb)%theta_int_c_set )  THEN
     1322
     1323             CALL  im_calc_temperatures ( i, j, k, indoor_wall_window_temperature,                 &
     1324                                          near_facade_temperature, phi_hc_nd )
     1325!
     1326!--          If air temperature between border temperatures of heating and cooling, assign output
     1327!--          variable, then ready.
     1328             IF ( buildings(nb)%theta_int_h_set <= theta_air  .AND.                                &
     1329                  theta_air <= buildings(nb)%theta_int_c_set )  THEN
    13211330                phi_hc_nd_ac = 0.0_wp
    1322                 phi_hc_nd    = phi_hc_nd_ac           
     1331                phi_hc_nd    = phi_hc_nd_ac
    13231332                theta_air_ac = theta_air
    13241333!
     
    13281337!
    13291338!--             Temperature not correct, calculation method according to section C4.2
    1330                 theta_air_0 = theta_air                                                  !< temperature without heating/cooling 
     1339                theta_air_0 = theta_air                                                  !< temperature without heating/cooling
    13311340!
    13321341!--             Heating or cooling?
    13331342                IF ( theta_air_0 > buildings(nb)%theta_int_c_set )  THEN
    13341343                   theta_air_set = buildings(nb)%theta_int_c_set
    1335                 ELSE 
    1336                    theta_air_set = buildings(nb)%theta_int_h_set 
     1344                ELSE
     1345                   theta_air_set = buildings(nb)%theta_int_h_set
    13371346                ENDIF
    13381347!
    1339 !--             Calculate the temperature with phi_hc_nd_10 
     1348!--             Calculate the temperature with phi_hc_nd_10
    13401349                phi_hc_nd_10 = 10.0_wp * floor_area_per_facade
    13411350                phi_hc_nd    = phi_hc_nd_10
    1342                
    1343                 CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
    1344                                             near_facade_temperature, phi_hc_nd )
     1351
     1352                CALL  im_calc_temperatures ( i, j, k, indoor_wall_window_temperature,              &
     1353                                             near_facade_temperature, phi_hc_nd )
    13451354                theta_air_10 = theta_air                                                !< temperature with 10 W/m2 of heating
    1346                 phi_hc_nd_un = phi_hc_nd_10 * (theta_air_set - theta_air_0)          &
     1355                phi_hc_nd_un = phi_hc_nd_10 * (theta_air_set - theta_air_0)                        &
    13471356                                            / (theta_air_10  - theta_air_0)             !< Eq. (C.13)
    13481357!
    1349 !--             Step 3: With temperature ratio to determine the heating or cooling capacity   
    1350 !--             If necessary, limit the power to maximum power
     1358!--             Step 3: with temperature ratio to determine the heating or cooling capacity.
     1359!--             If necessary, limit the power to maximum power.
    13511360!--             section C.4.1 Picture C.2 zone 2) and 4)
    1352                 buildings(nb)%phi_c_max = buildings(nb)%q_c_max * floor_area_per_facade             
     1361                buildings(nb)%phi_c_max = buildings(nb)%q_c_max * floor_area_per_facade
    13531362                buildings(nb)%phi_h_max = buildings(nb)%q_h_max * floor_area_per_facade
    1354                 IF ( buildings(nb)%phi_c_max < phi_hc_nd_un  .AND.  phi_hc_nd_un < buildings(nb)%phi_h_max )  THEN
     1363                IF ( buildings(nb)%phi_c_max < phi_hc_nd_un  .AND.                                 &
     1364                     phi_hc_nd_un < buildings(nb)%phi_h_max )  THEN
    13551365                   phi_hc_nd_ac = phi_hc_nd_un
    1356                    phi_hc_nd = phi_hc_nd_un 
     1366                   phi_hc_nd = phi_hc_nd_un
    13571367                ELSE
    13581368!
    1359 !--             Step 4: Inner temperature with maximum heating (phi_hc_nd_un positive) or cooling (phi_hc_nd_un negative)
     1369!--             Step 4: inner temperature with maximum heating (phi_hc_nd_un positive) or cooling
     1370!--                     (phi_hc_nd_un negative)
    13601371!--             section C.4.1 Picture C.2 zone 1) and 5)
    13611372                   IF ( phi_hc_nd_un > 0.0_wp )  THEN
    13621373                      phi_hc_nd_ac = buildings(nb)%phi_h_max                            !< Limit heating
    1363                    ELSE 
     1374                   ELSE
    13641375                      phi_hc_nd_ac = buildings(nb)%phi_c_max                            !< Limit cooling
    13651376                   ENDIF
    13661377                ENDIF
    1367                 phi_hc_nd = phi_hc_nd_ac   
     1378                phi_hc_nd = phi_hc_nd_ac
    13681379!
    13691380!--             Calculate the temperature with phi_hc_nd_ac (new)
    1370                 CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
    1371                                             near_facade_temperature, phi_hc_nd )
     1381                CALL  im_calc_temperatures ( i, j, k, indoor_wall_window_temperature,              &
     1382                                             near_facade_temperature, phi_hc_nd )
    13721383                theta_air_ac = theta_air
    13731384             ENDIF
     
    13751386!--          Update theta_m_t_prev
    13761387             theta_m_t_prev = theta_m_t
    1377              
     1388
    13781389             q_vent = h_v * ( theta_air - near_facade_temperature )
    13791390!
    1380 !--          Calculate the operating temperature with weighted mean temperature of air and mean solar temperature
    1381 !--          Will be used for thermal comfort calculations
     1391!--          Calculate the operating temperature with weighted mean temperature of air and mean
     1392!--          solar temperature.
     1393!--          Will be used for thermal comfort calculations.
    13821394             theta_op     = 0.3_wp * theta_air_ac + 0.7_wp * theta_s          !< [degree_C] operative Temperature Eq. (C.12)
    13831395!              surf_usm_h%t_indoor(m) = theta_op                               !< not integrated now
    13841396!
    1385 !--          Heat flux into the wall. Value needed in urban_surface_mod to 
     1397!--          Heat flux into the wall. Value needed in urban_surface_mod to
    13861398!--          calculate heat transfer through wall layers towards the facade
    13871399!--          (use c_p * rho_surface to convert [W/m2] into [K m/s])
    1388              q_wall_win = h_t_ms * ( theta_s - theta_m )                       &
    1389                                     / (   facade_element_area                  &
    1390                                         - window_area_per_facade )
    1391              q_trans = q_wall_win * facade_element_area                                       
     1400             q_wall_win = h_t_ms * ( theta_s - theta_m )                                           &
     1401                                    / ( facade_element_area - window_area_per_facade )
     1402             q_trans = q_wall_win * facade_element_area
    13921403!
    13931404!--          Transfer q_wall_win back to USM (innermost wall/window layer)
     
    13951406             surf_usm_h%iwghf_eb_window(m) = q_wall_win
    13961407!
    1397 !--          Sum up operational indoor temperature per kk-level. Further below,
    1398 !--          this temperature is reduced by MPI to one temperature per kk-level
    1399 !--          and building (processor overlapping)
     1408!--          Sum up operational indoor temperature per kk-level. Further below, this temperature is
     1409!--          reduced by MPI to one temperature per kk-level and building (processor overlapping).
    14001410             buildings(nb)%t_in_l(kk) = buildings(nb)%t_in_l(kk) + theta_op
    14011411!
    1402 !--          Calculation of waste heat
    1403 !--          Anthropogenic heat output
    1404              IF ( phi_hc_nd_ac > 0.0_wp )  THEN 
     1412!--          Calculation of waste heat.
     1413!--          Anthropogenic heat output.
     1414             IF ( phi_hc_nd_ac > 0.0_wp )  THEN
    14051415                heating_on = 1
    14061416                cooling_on = 0
    1407              ELSE 
     1417             ELSE
    14081418                heating_on = 0
    14091419                cooling_on = -1
    14101420             ENDIF
    14111421
    1412              q_waste_heat = ( phi_hc_nd * (                                    &
    1413                               buildings(nb)%params_waste_heat_h * heating_on + &
    1414                               buildings(nb)%params_waste_heat_c * cooling_on ) &
    1415                             ) / facade_element_area                                               !< [W/m2] , observe the directional convention in PALM!
     1422             q_waste_heat = ( phi_hc_nd * (                                                        &
     1423                              buildings(nb)%params_waste_heat_h * heating_on +                     &
     1424                              buildings(nb)%params_waste_heat_c * cooling_on )                     &
     1425                            ) / facade_element_area                                             !< [W/m2] , observe the directional
     1426                                                                                                !< convention in PALM!
    14161427             surf_usm_h%waste_heat(m) = q_waste_heat
    14171428          ENDDO !< Horizontal surfaces loop
     
    14201431          DO  fa = 1, buildings(nb)%num_facades_per_building_v_l
    14211432!
    1422 !--          Determine indices where corresponding surface-type information
    1423 !--          is stored.
     1433!--          Determine indices where corresponding surface-type information is stored.
    14241434             l = buildings(nb)%l_v(fa)
    14251435             m = buildings(nb)%m_v(fa)
    14261436!
    1427 !--          Determine building height level index. 
     1437!--          Determine building height level index.
    14281438             kk = surf_usm_v(l)%k(m) + surf_usm_v(l)%koff
    14291439!
    1430 !--          (SOME OF THE FOLLOWING (not time-dependent COULD PROBABLY GO INTO A FUNCTION
     1440!--          (SOME OF THE FOLLOWING (not time-dependent) COULD PROBABLY GO INTO A FUNCTION
    14311441!--          EXCEPT facade_element_area, EVERYTHING IS CALCULATED EQUALLY)
    14321442!--          Building geometries  --> not time-dependent
     
    14351445
    14361446             floor_area_per_facade        = buildings(nb)%fapf                  !< [m2/m2] floor area per facade area
    1437              indoor_volume_per_facade     = buildings(nb)%vpf(kk)               !< [m3/m2] indoor air volume per facade area
    1438              buildings(nb)%area_facade    = facade_element_area *                                   &
    1439                                           ( buildings(nb)%num_facades_per_building_h +              &
    1440                                             buildings(nb)%num_facades_per_building_v )                !< [m2] area of total facade
    1441              window_area_per_facade       = surf_usm_v(l)%frac(m,ind_wat_win)  * facade_element_area  !< [m2] window area per facade element
     1447             indoor_volume_per_facade     = buildings(nb)%vpf(kk)               !< [m3/m2] indoor air volume per facade area
     1448             buildings(nb)%area_facade    = facade_element_area *                                  &
     1449                                            ( buildings(nb)%num_facades_per_building_h +           &
     1450                                              buildings(nb)%num_facades_per_building_v )              !< [m2] area of total facade
     1451             window_area_per_facade       = surf_usm_v(l)%frac(m,ind_wat_win) * facade_element_area   !< [m2] window area per
     1452                                                                                                      !< facade element
    14421453
    14431454             buildings(nb)%net_floor_area = buildings(nb)%vol_tot / ( buildings(nb)%height_storey )
    1444              total_area                   = buildings(nb)%net_floor_area                              !< [m2] area of all surfaces pointing to zone  Eq. (9) according to section 7.2.2.2
    1445              a_m                          = buildings(nb)%factor_a * total_area *                   &
    1446                                           ( facade_element_area / buildings(nb)%area_facade ) *     &
    1447                                             buildings(nb)%lambda_at                                   !< [m2] standard values according to Table 12 section 12.3.1.2  (calculate over Eq. (65) according to section 12.3.1.2)
     1455             total_area                   = buildings(nb)%net_floor_area                              !< [m2] area of all surfaces
     1456                                                                                                      !< pointing to zone  Eq. (9) according to section 7.2.2.2
     1457             a_m                          = buildings(nb)%factor_a * total_area *                  &
     1458                                            ( facade_element_area / buildings(nb)%area_facade ) *  &
     1459                                              buildings(nb)%lambda_at                                 !< [m2] standard values
     1460                                                                                                      !< according to Table 12 section 12.3.1.2  (calculate over Eq. (65) according to section 12.3.1.2)
    14481461             c_m                          = buildings(nb)%factor_c * total_area *                   &
    1449                                           ( facade_element_area / buildings(nb)%area_facade )         !< [J/K] standard values according to table 12 section 12.3.1.2 (calculate over Eq. (66) according to section 12.3.1.2)
     1462                                            ( facade_element_area / buildings(nb)%area_facade )       !< [J/K] standard values
     1463                                                                                                      !< according to table 12 section 12.3.1.2 (calculate over Eq. (66) according to section 12.3.1.2)
    14501464!
    14511465!--          Calculation of heat transfer coefficient for transmission --> not time-dependent
    14521466             h_t_es   = window_area_per_facade * buildings(nb)%h_es                                   !< [W/K] only for windows
    14531467
    1454              h_t_is  = buildings(nb)%area_facade  * h_is                                                             !< [W/K] with h_is = 3.45 W / (m2 K) between surface and air, Eq. (9)
    1455              h_t_ms  = a_m * h_ms                                                                     !< [W/K] with h_ms = 9.10 W / (m2 K) between component and surface, Eq. (64)
    1456              h_t_wall  = 1.0_wp / ( 1.0_wp / ( ( facade_element_area - window_area_per_facade )     & !< [W/K]
     1468             h_t_is  = buildings(nb)%area_facade  * h_is                                              !< [W/K] with h_is = 3.45 W /
     1469                                                                                                      !< (m2 K) between surface and air, Eq. (9)
     1470             h_t_ms  = a_m * h_ms                                                                     !< [W/K] with h_ms = 9.10 W /
     1471                                                                                                      !< (m2 K) between component and surface, Eq. (64)
     1472             h_t_wall  = 1.0_wp / ( 1.0_wp / ( ( facade_element_area - window_area_per_facade )    &  !< [W/K]
    14571473                                    * buildings(nb)%lambda_layer3 / buildings(nb)%s_layer3 * 0.5_wp &
    14581474                                             ) + 1.0_wp / h_t_ms )                                    !< [W/K] opaque components
    14591475             h_t_wm  = 1.0_wp / ( 1.0_wp / h_t_wall - 1.0_wp / h_t_ms )                               !< [W/K] emmision Eq. (63), Section 12.2.2
    14601476!
    1461 !--          internal air loads dependent on the occupacy of the room
    1462 !--          basical internal heat gains (qint_low) with additional internal heat gains by occupancy (qint_high) (0,5*phi_int)
    1463              phi_ia = 0.5_wp * ( ( buildings(nb)%qint_high * schedule_d + buildings(nb)%qint_low )  &
    1464                               * floor_area_per_facade )
     1477!--          Internal air loads dependent on the occupacy of the room.
     1478!--          Basical internal heat gains (qint_low) with additional internal heat gains by occupancy
     1479!--          (qint_high) (0,5*phi_int)
     1480             phi_ia = 0.5_wp * ( ( buildings(nb)%qint_high * schedule_d + buildings(nb)%qint_low ) &
     1481                             * floor_area_per_facade )
    14651482             q_int = phi_ia
    14661483
    14671484!
    1468 !--          Airflow dependent on the occupacy of the room
    1469 !--          basical airflow (air_change_low) with additional airflow gains by occupancy (air_change_high)
    1470              air_change = ( buildings(nb)%air_change_high * schedule_d + buildings(nb)%air_change_low ) 
    1471 !
    1472 !--          Heat transfer of ventilation
    1473 !--          not less than 0.01 W/K to provide division by 0 in further calculations
    1474 !--          with heat capacity of air 0.33 Wh/m2K
    1475              h_v   = MAX( 0.01_wp , ( air_change * indoor_volume_per_facade *                       &
    1476                                     0.33_wp * (1.0_wp - buildings(nb)%eta_ve ) ) )                    !< [W/K] from ISO 13789 Eq.(10)
    1477                                    
     1485!--          Airflow dependent on the occupacy of the room.
     1486!--          Basical airflow (air_change_low) with additional airflow gains by occupancy
     1487!--          (air_change_high)
     1488             air_change = ( buildings(nb)%air_change_high * schedule_d +                           &
     1489                          buildings(nb)%air_change_low )
     1490!
     1491!--          Heat transfer of ventilation.
     1492!--          Not less than 0.01 W/K to avoid division by 0 in further calculations with heat
     1493!--          capacity of air 0.33 Wh/m2K
     1494             h_v   = MAX( 0.01_wp , ( air_change * indoor_volume_per_facade *                      &
     1495                                    0.33_wp * (1.0_wp - buildings(nb)%eta_ve ) ) )                    !< [W/K] from ISO 13789
     1496                                                                                                      !< Eq.(10)
     1497
    14781498!--          Heat transfer coefficient auxiliary variables
    14791499             h_t_1 = 1.0_wp / ( ( 1.0_wp / h_v )   + ( 1.0_wp / h_t_is ) )                            !< [W/K] Eq. (C.6)
     
    14861506!--          Quantities needed for im_calc_temperatures
    14871507             i = surf_usm_v(l)%i(m)
    1488              j = surf_usm_v(l)%j(m)   
     1508             j = surf_usm_v(l)%j(m)
    14891509             k = surf_usm_v(l)%k(m)
    14901510             near_facade_temperature = surf_usm_v(l)%pt_10cm(m)
    1491              indoor_wall_window_temperature =                                                       &
    1492                   surf_usm_v(l)%frac(m,ind_veg_wall) * t_wall_v(l)%t(nzt_wall,m)                    &
    1493                 + surf_usm_v(l)%frac(m,ind_wat_win)  * t_window_v(l)%t(nzt_wall,m)
    1494 !
    1495 !--          Solar thermal gains. If net_sw_in larger than sun-protection 
    1496 !--          threshold parameter (params_solar_protection), sun protection will 
     1511             indoor_wall_window_temperature =                                                      &
     1512                                    surf_usm_v(l)%frac(m,ind_veg_wall) * t_wall_v(l)%t(nzt_wall,m) &
     1513                                  + surf_usm_v(l)%frac(m,ind_wat_win)  * t_window_v(l)%t(nzt_wall,m)
     1514!
     1515!--          Solar thermal gains. If net_sw_in larger than sun-protection
     1516!--          threshold parameter (params_solar_protection), sun protection will
    14971517!--          be activated
    1498              IF ( net_sw_in <= params_solar_protection )  THEN 
     1518             IF ( net_sw_in <= params_solar_protection )  THEN
    14991519                solar_protection_off = 1
    1500                 solar_protection_on  = 0 
    1501              ELSE 
     1520                solar_protection_on  = 0
     1521             ELSE
    15021522                solar_protection_off = 0
    1503                 solar_protection_on  = 1 
     1523                solar_protection_on  = 1
    15041524             ENDIF
    15051525!
    1506 !--          Calculation of total heat gains from net_sw_in through windows [W] in respect on automatic sun protection
     1526!--          Calculation of total heat gains from net_sw_in through windows [W] in respect on
     1527!--          automatic sun protection.
    15071528!--          DIN 4108 - 2 chap.8
    1508              phi_sol = (   window_area_per_facade * net_sw_in * solar_protection_off                             &
    1509                          + window_area_per_facade * net_sw_in * buildings(nb)%f_c_win * solar_protection_on )    &
     1529             phi_sol = (   window_area_per_facade * net_sw_in * solar_protection_off               &
     1530                         + window_area_per_facade * net_sw_in * buildings(nb)%f_c_win *            &
     1531                           solar_protection_on )                                                   &
    15101532                       * buildings(nb)%g_value_win * ( 1.0_wp - params_f_f ) * params_f_w
    15111533             q_sol = phi_sol
    15121534!
    1513 !--          Calculation of the mass specific thermal load for internal and external heatsources
     1535!--          Calculation of the mass specific thermal load for internal and external heatsources.
    15141536             phi_m   = (a_m / total_area) * ( phi_ia + phi_sol )          !< [W] Eq. (C.2) with phi_ia=0,5*phi_int
    15151537             q_c_m = phi_m
    15161538!
    1517 !--          Calculation mass specific thermal load implied non thermal mass
    1518              phi_st  =   ( 1.0_wp - ( a_m / total_area ) - ( h_t_es / ( 9.1_wp * total_area ) ) )                &
    1519                        * ( phi_ia + phi_sol )                                                                       !< [W] Eq. (C.3) with phi_ia=0,5*phi_int
    1520              q_c_st = phi_st
    1521 !
    1522 !--          Calculations for deriving indoor temperature and heat flux into the wall
    1523 !--          Step 1: Indoor temperature without heating and cooling
     1539!--          Calculation mass specific thermal load implied non thermal mass.
     1540             phi_st  =   ( 1.0_wp - ( a_m / total_area ) - ( h_t_es / ( 9.1_wp * total_area ) ) )  &
     1541                       * ( phi_ia + phi_sol )                                                       !< [W] Eq. (C.3) with
     1542                                                                                                    !< phi_ia=0,5*phi_int
     1543             q_c_st = phi_st
     1544!
     1545!--          Calculations for deriving indoor temperature and heat flux into the wall.
     1546!--          Step 1: indoor temperature without heating and cooling.
    15241547!--          section C.4.1 Picture C.2 zone 3)
    15251548             phi_hc_nd = 0.0_wp
    1526              CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
     1549             CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature,                  &
    15271550                                         near_facade_temperature, phi_hc_nd )
    15281551!
    1529 !--          If air temperature between border temperatures of heating and cooling, assign output variable, then ready 
    1530              IF ( buildings(nb)%theta_int_h_set <= theta_air  .AND.  theta_air <= buildings(nb)%theta_int_c_set )  THEN
     1552!--          If air temperature between border temperatures of heating and cooling, assign output
     1553!--          variable, then ready.
     1554             IF ( buildings(nb)%theta_int_h_set <= theta_air  .AND.                                &
     1555                  theta_air <= buildings(nb)%theta_int_c_set )  THEN
    15311556                phi_hc_nd_ac = 0.0_wp
    15321557                phi_hc_nd    = phi_hc_nd_ac
     
    15431568                IF ( theta_air_0 > buildings(nb)%theta_int_c_set )  THEN
    15441569                   theta_air_set = buildings(nb)%theta_int_c_set
    1545                 ELSE 
    1546                    theta_air_set = buildings(nb)%theta_int_h_set 
     1570                ELSE
     1571                   theta_air_set = buildings(nb)%theta_int_h_set
    15471572                ENDIF
    15481573
     
    15501575                phi_hc_nd_10 = 10.0_wp * floor_area_per_facade
    15511576                phi_hc_nd    = phi_hc_nd_10
    1552        
    1553                 CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
    1554                                             near_facade_temperature, phi_hc_nd )
     1577
     1578                CALL  im_calc_temperatures ( i, j, k, indoor_wall_window_temperature,              &
     1579                                             near_facade_temperature, phi_hc_nd )
    15551580
    15561581                theta_air_10 = theta_air !< Note the temperature with 10 W/m2 of heating
    15571582
    1558                 phi_hc_nd_un = phi_hc_nd_10 * ( theta_air_set - theta_air_0 )  &
     1583                phi_hc_nd_un = phi_hc_nd_10 * ( theta_air_set - theta_air_0 )                      &
    15591584                                            / ( theta_air_10  - theta_air_0 )            !< Eq. (C.13)
    15601585!
    1561 !--             Step 3: With temperature ratio to determine the heating or cooling capacity   
    1562 !--             If necessary, limit the power to maximum power
     1586!--             Step 3: with temperature ratio to determine the heating or cooling capacity
     1587!--             If necessary, limit the power to maximum power.
    15631588!--             section C.4.1 Picture C.2 zone 2) and 4)
    15641589                buildings(nb)%phi_c_max = buildings(nb)%q_c_max * floor_area_per_facade
    15651590                buildings(nb)%phi_h_max = buildings(nb)%q_h_max * floor_area_per_facade
    1566                 IF ( buildings(nb)%phi_c_max < phi_hc_nd_un  .AND.  phi_hc_nd_un < buildings(nb)%phi_h_max )  THEN
     1591                IF ( buildings(nb)%phi_c_max < phi_hc_nd_un  .AND.                                 &
     1592                     phi_hc_nd_un < buildings(nb)%phi_h_max )  THEN
    15671593                   phi_hc_nd_ac = phi_hc_nd_un
    15681594                   phi_hc_nd = phi_hc_nd_un
    15691595                ELSE
    15701596!
    1571 !--             Step 4: Inner temperature with maximum heating (phi_hc_nd_un positive) or cooling (phi_hc_nd_un negative)
     1597!--             Step 4: inner temperature with maximum heating (phi_hc_nd_un positive) or cooling
     1598!--                     (phi_hc_nd_un negative)
    15721599!--             section C.4.1 Picture C.2 zone 1) and 5)
    15731600                   IF ( phi_hc_nd_un > 0.0_wp )  THEN
    15741601                      phi_hc_nd_ac = buildings(nb)%phi_h_max                                         !< Limit heating
    1575                    ELSE 
     1602                   ELSE
    15761603                      phi_hc_nd_ac = buildings(nb)%phi_c_max                                         !< Limit cooling
    15771604                   ENDIF
    15781605                ENDIF
    1579                 phi_hc_nd = phi_hc_nd_ac 
     1606                phi_hc_nd = phi_hc_nd_ac
    15801607!
    15811608!--             Calculate the temperature with phi_hc_nd_ac (new)
    1582                 CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
    1583                                             near_facade_temperature, phi_hc_nd )
     1609                CALL  im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
     1610                                             near_facade_temperature, phi_hc_nd )
    15841611                theta_air_ac = theta_air
    15851612             ENDIF
     
    15871614!--          Update theta_m_t_prev
    15881615             theta_m_t_prev = theta_m_t
    1589              
     1616
    15901617             q_vent = h_v * ( theta_air - near_facade_temperature )
    15911618!
    1592 !--          Calculate the operating temperature with weighted mean of temperature of air and mean
    1593 !--          Will be used for thermal comfort calculations 
     1619!--          Calculate the operating temperature with weighted mean of temperature of air and mean.
     1620!--          Will be used for thermal comfort calculations.
    15941621             theta_op     = 0.3_wp * theta_air_ac + 0.7_wp * theta_s
    15951622!              surf_usm_v(l)%t_indoor(m) = theta_op                  !< not integrated yet
    15961623!
    1597 !--          Heat flux into the wall. Value needed in urban_surface_mod to 
     1624!--          Heat flux into the wall. Value needed in urban_surface_mod to
    15981625!--          calculate heat transfer through wall layers towards the facade
    1599              q_wall_win = h_t_ms * ( theta_s - theta_m )                       &
    1600                                     / (   facade_element_area                  &
    1601                                         - window_area_per_facade )
     1626             q_wall_win = h_t_ms * ( theta_s - theta_m )                                           &
     1627                                    / ( facade_element_area - window_area_per_facade )
    16021628             q_trans = q_wall_win * facade_element_area
    16031629!
     
    16061632             surf_usm_v(l)%iwghf_eb_window(m) = q_wall_win
    16071633!
    1608 !--          Sum up operational indoor temperature per kk-level. Further below,
    1609 !--          this temperature is reduced by MPI to one temperature per kk-level
    1610 !--          and building (processor overlapping)
     1634!--          Sum up operational indoor temperature per kk-level. Further below, this temperature is
     1635!--          reduced by MPI to one temperature per kk-level and building (processor overlapping).
    16111636             buildings(nb)%t_in_l(kk) = buildings(nb)%t_in_l(kk) + theta_op
    16121637!
    1613 !--          Calculation of waste heat
    1614 !--          Anthropogenic heat output
    1615              IF ( phi_hc_nd_ac > 0.0_wp )  THEN 
     1638!--          Calculation of waste heat.
     1639!--          Anthropogenic heat output.
     1640             IF ( phi_hc_nd_ac > 0.0_wp )  THEN
    16161641                heating_on = 1
    16171642                cooling_on = 0
    1618              ELSE 
     1643             ELSE
    16191644                heating_on = 0
    16201645                cooling_on = -1
    16211646             ENDIF
    16221647
    1623              q_waste_heat = ( phi_hc_nd * (                                    &
    1624                     buildings(nb)%params_waste_heat_h * heating_on +           &
    1625                     buildings(nb)%params_waste_heat_c * cooling_on )           &
    1626                             ) / facade_element_area !< [W/m2] , observe the directional convention in PALM!
     1648             q_waste_heat = ( phi_hc_nd * ( buildings(nb)%params_waste_heat_h * heating_on +       &
     1649                                            buildings(nb)%params_waste_heat_c * cooling_on )       &
     1650                                                    ) / facade_element_area  !< [W/m2] , observe the directional convention in
     1651                                                                             !< PALM!
    16271652             surf_usm_v(l)%waste_heat(m) = q_waste_heat
    16281653          ENDDO !< Vertical surfaces loop
     
    16311656
    16321657!
    1633 !-- Determine the mean building temperature. 
     1658!-- Determine the mean building temperature.
    16341659    DO  nb = 1, num_build
    16351660!
    1636 !--    Allocate dummy array used for summing-up facade elements. 
    1637 !--    Please note, dummy arguments are necessary as building-date type
    1638 !--    arrays are not necessarily allocated on all PEs.
     1661!--    Allocate dummy array used for summing-up facade elements.
     1662!--    Please note, dummy arguments are necessary as building-date type arrays are not necessarily
     1663!--    allocated on all PEs.
    16391664       ALLOCATE( t_in_l_send(buildings(nb)%kb_min:buildings(nb)%kb_max) )
    16401665       ALLOCATE( t_in_recv(buildings(nb)%kb_min:buildings(nb)%kb_max) )
     
    16471672
    16481673
    1649 #if defined( __parallel ) 
    1650        CALL MPI_ALLREDUCE( t_in_l_send,                                        &
    1651                            t_in_recv,                                          &
    1652                            buildings(nb)%kb_max - buildings(nb)%kb_min + 1,    &
    1653                            MPI_REAL,                                           &
    1654                            MPI_SUM,                                            &
    1655                            comm2d,                                             &
     1674#if defined( __parallel )
     1675       CALL MPI_ALLREDUCE( t_in_l_send,                                                            &
     1676                           t_in_recv,                                                              &
     1677                           buildings(nb)%kb_max - buildings(nb)%kb_min + 1,                        &
     1678                           MPI_REAL,                                                               &
     1679                           MPI_SUM,                                                                &
     1680                           comm2d,                                                                 &
    16561681                           ierr )
    16571682
    1658        IF ( ALLOCATED( buildings(nb)%t_in ) )                                  &
    1659            buildings(nb)%t_in = t_in_recv
     1683       IF ( ALLOCATED( buildings(nb)%t_in ) )  buildings(nb)%t_in = t_in_recv
    16601684#else
    1661        IF ( ALLOCATED( buildings(nb)%t_in ) )                                  &
    1662           buildings(nb)%t_in = buildings(nb)%t_in_l
     1685       IF ( ALLOCATED( buildings(nb)%t_in ) )  buildings(nb)%t_in = buildings(nb)%t_in_l
    16631686#endif
    16641687
    16651688       IF ( ALLOCATED( buildings(nb)%t_in ) )  THEN
    16661689!
    1667 !--       Average indoor temperature. Note, in case a building is completely
    1668 !--       surrounded by higher buildings, it may have no facade elements
    1669 !--       at some height levels, which will lead to a divide by zero.
     1690!--       Average indoor temperature. Note, in case a building is completely surrounded by higher
     1691!--       buildings, it may have no facade elements at some height levels, which will lead to a
     1692!--       division by zero.
    16701693          DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
    1671              IF ( buildings(nb)%num_facade_h(k) +                              &
    1672                   buildings(nb)%num_facade_v(k) > 0 )  THEN
    1673                 buildings(nb)%t_in(k) = buildings(nb)%t_in(k) /                &
    1674                                REAL( buildings(nb)%num_facade_h(k) +           &
    1675                                      buildings(nb)%num_facade_v(k), KIND = wp )
     1694             IF ( buildings(nb)%num_facade_h(k) + buildings(nb)%num_facade_v(k) > 0 )  THEN
     1695                buildings(nb)%t_in(k) = buildings(nb)%t_in(k) /                                    &
     1696                                        REAL( buildings(nb)%num_facade_h(k) +                      &
     1697                                              buildings(nb)%num_facade_v(k), KIND = wp )
    16761698             ENDIF
    16771699          ENDDO
    16781700!
    1679 !--       If indoor temperature is not defined because of missing facade
    1680 !--       elements, the values from the above-lying level will be taken.
    1681 !--       At least at the top of the buildings facades are defined, so that
    1682 !--       at least there an indoor temperature is defined. This information
    1683 !--       will propagate downwards the building.
     1701!--       If indoor temperature is not defined because of missing facade elements, the values from
     1702!--       the above-lying level will be taken.
     1703!--       At least at the top of the buildings facades are defined, so that at least there an indoor
     1704!--       temperature is defined. This information will propagate downwards the building.
    16841705          DO  k = buildings(nb)%kb_max-1, buildings(nb)%kb_min, -1
    1685              IF ( buildings(nb)%num_facade_h(k) +                              &
    1686                   buildings(nb)%num_facade_v(k) <= 0 )  THEN
     1706             IF ( buildings(nb)%num_facade_h(k) + buildings(nb)%num_facade_v(k) <= 0 )  THEN
    16871707                buildings(nb)%t_in(k) = buildings(nb)%t_in(k+1)
    16881708             ENDIF
    16891709          ENDDO
    16901710       ENDIF
    1691        
     1711
    16921712
    16931713!
     
    16971717
    16981718    ENDDO
    1699    
     1719
    17001720 END SUBROUTINE im_main_heatcool
    17011721
    1702 !-----------------------------------------------------------------------------!
     1722
     1723!--------------------------------------------------------------------------------------------------!
    17031724! Description:
    17041725!-------------
    17051726!> Check data output for plant canopy model
    1706 !-----------------------------------------------------------------------------!
     1727!--------------------------------------------------------------------------------------------------!
    17071728 SUBROUTINE im_check_data_output( var, unit )
    17081729
    17091730    CHARACTER (LEN=*) ::  unit   !<
    17101731    CHARACTER (LEN=*) ::  var    !<
    1711        
     1732
    17121733    SELECT CASE ( TRIM( var ) )
    1713    
    1714    
     1734
     1735
    17151736        CASE ( 'im_hf_roof')
    17161737           unit = 'W m-2'
    1717        
     1738
    17181739        CASE ( 'im_hf_wall_win' )
    17191740           unit = 'W m-2'
    1720            
     1741
    17211742        CASE ( 'im_hf_wall_win_waste' )
    17221743           unit = 'W m-2'
    1723            
     1744
    17241745        CASE ( 'im_hf_roof_waste' )
    17251746           unit = 'W m-2'
    1726        
     1747
    17271748        CASE ( 'im_t_indoor_mean' )
    17281749           unit = 'K'
    1729            
     1750
    17301751        CASE ( 'im_t_indoor_roof' )
    17311752           unit = 'K'
    1732            
     1753
    17331754        CASE ( 'im_t_indoor_wall_win' )
    17341755           unit = 'K'
    1735        
     1756
    17361757        CASE DEFAULT
    17371758           unit = 'illegal'
    1738            
     1759
    17391760    END SELECT
    1740    
     1761
    17411762 END SUBROUTINE
    17421763
    17431764
    1744 !-----------------------------------------------------------------------------!
     1765!--------------------------------------------------------------------------------------------------!
    17451766! Description:
    17461767!-------------
    17471768!> Check parameters routine for plant canopy model
    1748 !-----------------------------------------------------------------------------!
     1769!--------------------------------------------------------------------------------------------------!
    17491770 SUBROUTINE im_check_parameters
    17501771
    17511772!   USE control_parameters,
    17521773!       ONLY: message_string
    1753    
     1774
    17541775 END SUBROUTINE im_check_parameters
    17551776
    1756 !-----------------------------------------------------------------------------!
     1777
     1778!--------------------------------------------------------------------------------------------------!
    17571779! Description:
    17581780!-------------
    17591781!> Subroutine defining appropriate grid for netcdf variables.
    17601782!> It is called from subroutine netcdf.
    1761 !-----------------------------------------------------------------------------!
     1783!--------------------------------------------------------------------------------------------------!
    17621784 SUBROUTINE im_define_netcdf_grid( var, found, grid_x, grid_y, grid_z )
    17631785
    1764    
    1765    CHARACTER (LEN=*), INTENT(IN)  ::  var
    1766    LOGICAL, INTENT(OUT)           ::  found
    1767    CHARACTER (LEN=*), INTENT(OUT) ::  grid_x
    1768    CHARACTER (LEN=*), INTENT(OUT) ::  grid_y
    1769    CHARACTER (LEN=*), INTENT(OUT) ::  grid_z
    1770    
    1771    found   = .TRUE.
    1772    
     1786    CHARACTER (LEN=*), INTENT(OUT) ::  grid_x
     1787    CHARACTER (LEN=*), INTENT(OUT) ::  grid_y
     1788    CHARACTER (LEN=*), INTENT(OUT) ::  grid_z
     1789    CHARACTER (LEN=*), INTENT(IN)  ::  var
     1790
     1791    LOGICAL, INTENT(OUT)           ::  found
     1792
     1793
     1794    found   = .TRUE.
    17731795!
    17741796!-- Check for the grid
     
    17901812          grid_y = 'y'
    17911813          grid_z = 'zw'
    1792          
     1814
    17931815       CASE DEFAULT
    17941816          found  = .FALSE.
     
    17971819          grid_z = 'none'
    17981820    END SELECT
    1799    
     1821
    18001822 END SUBROUTINE im_define_netcdf_grid
    18011823
    1802 !------------------------------------------------------------------------------!
     1824
     1825!--------------------------------------------------------------------------------------------------!
    18031826! Description:
    18041827! ------------
    18051828!> Subroutine defining 3D output variables
    1806 !------------------------------------------------------------------------------!
    1807  SUBROUTINE im_data_output_3d( av, variable, found, local_pf, fill_value,      &
    1808                                nzb_do, nzt_do )
     1829!--------------------------------------------------------------------------------------------------!
     1830 SUBROUTINE im_data_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
    18091831
    18101832    USE indices
     
    18121834    USE kinds
    18131835
    1814     CHARACTER (LEN=*) ::  variable !< 
    1815 
    1816     INTEGER(iwp) ::  av    !< 
    1817     INTEGER(iwp) ::  i     !< 
    1818     INTEGER(iwp) ::  j     !< 
    1819     INTEGER(iwp) ::  k     !< 
     1836    CHARACTER (LEN=*) ::  variable !<
     1837
     1838    INTEGER(iwp) ::  av    !<
     1839    INTEGER(iwp) ::  i     !<
     1840    INTEGER(iwp) ::  j     !<
     1841    INTEGER(iwp) ::  k     !<
    18201842    INTEGER(iwp) ::  l     !<
    1821     INTEGER(iwp) ::  m     !< 
    1822     INTEGER(iwp) ::  nb    !< index of the building in the building data structure 
     1843    INTEGER(iwp) ::  m     !<
     1844    INTEGER(iwp) ::  nb    !< index of the building in the building data structure
    18231845    INTEGER(iwp) ::  nzb_do !< lower limit of the data output (usually 0)
    18241846    INTEGER(iwp) ::  nzt_do !< vertical upper limit of the data output (usually nz_do3d)
    1825    
    1826     LOGICAL      ::  found !< 
     1847
     1848    LOGICAL      ::  found !<
    18271849
    18281850    REAL(wp), INTENT(IN) ::  fill_value !< value for the _FillValue attribute
    18291851
    1830     REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !< 
    1831    
     1852    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
     1853
    18321854    local_pf = fill_value
    1833    
     1855
    18341856    found = .TRUE.
    1835    
     1857
    18361858    SELECT CASE ( TRIM( variable ) )
    18371859!
    1838 !--     Output of indoor temperature. All grid points within the building are
    1839 !--     filled with values, while atmospheric grid points are set to _FillValues.
     1860!--     Output of indoor temperature. All grid points within the building are filled with values,
     1861!--     while atmospheric grid points are set to _FillValues.
    18401862        CASE ( 'im_t_indoor_mean' )
    18411863           IF ( av == 0 ) THEN
     
    18441866                    IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
    18451867!
    1846 !--                    Determine index of the building within the building data structure.
    1847                        nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ),   &
    1848                                     DIM = 1 )
     1868!--                    Determine index of the building within the building data structure.
     1869                       nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM=1 )
    18491870                       IF ( buildings(nb)%on_pe )  THEN
    18501871!
    1851 !--                       Write mean building temperature onto output array. Please note,
    1852 !--                       in contrast to many other loops in the output, the vertical
    1853 !--                       bounds are determined by the lowest and hightest vertical index
    1854 !--                       occupied by the building.
     1872!--                       Write mean building temperature onto output array. Please note, in
     1873!--                       contrast to many other loops in the output, the vertical bounds are
     1874!--                       determined by the lowest and hightest vertical index occupied by the
     1875!--                       building.
    18551876                          DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
    18561877                             local_pf(i,j,k) = buildings(nb)%t_in(k)
     
    18601881                 ENDDO
    18611882              ENDDO
    1862            ENDIF 
     1883           ENDIF
    18631884
    18641885        CASE ( 'im_hf_roof' )
    1865            IF ( av == 0 ) THEN
     1886           IF ( av == 0 )  THEN
    18661887              DO  m = 1, surf_usm_h%ns
    18671888                 i = surf_usm_h%i(m) !+ surf_usm_h%ioff
     
    18701891                 local_pf(i,j,k) = surf_usm_h%iwghf_eb(m)
    18711892              ENDDO
    1872            ENDIF 
     1893           ENDIF
    18731894
    18741895        CASE ( 'im_hf_roof_waste' )
    1875            IF ( av == 0 ) THEN
    1876               DO m = 1, surf_usm_h%ns 
     1896           IF ( av == 0 )  THEN
     1897              DO m = 1, surf_usm_h%ns
    18771898                 i = surf_usm_h%i(m) !+ surf_usm_h%ioff
    18781899                 j = surf_usm_h%j(m) !+ surf_usm_h%joff
     
    18831904
    18841905       CASE ( 'im_hf_wall_win' )
    1885            IF ( av == 0 ) THEN
     1906           IF ( av == 0 )  THEN
    18861907              DO l = 0, 3
    18871908                 DO m = 1, surf_usm_v(l)%ns
     
    18951916
    18961917        CASE ( 'im_hf_wall_win_waste' )
    1897            IF ( av == 0 ) THEN
     1918           IF ( av == 0 )  THEN
    18981919              DO l = 0, 3
    1899                  DO m = 1, surf_usm_v(l)%ns 
     1920                 DO m = 1, surf_usm_v(l)%ns
    19001921                    i = surf_usm_v(l)%i(m) !+ surf_usm_v(l)%ioff
    19011922                    j = surf_usm_v(l)%j(m) !+ surf_usm_v(l)%joff
    19021923                    k = surf_usm_v(l)%k(m) !+ surf_usm_v(l)%koff
    1903                     local_pf(i,j,k) =  surf_usm_v(l)%waste_heat(m) 
     1924                    local_pf(i,j,k) =  surf_usm_v(l)%waste_heat(m)
    19041925                 ENDDO
    19051926              ENDDO
     
    19101931
    19111932!         CASE ( 'im_t_indoor_roof' )
    1912 !            IF ( av == 0 ) THEN
     1933!            IF ( av == 0 )  THEN
    19131934!               DO  m = 1, surf_usm_h%ns
    19141935!                   i = surf_usm_h%i(m) !+ surf_usm_h%ioff
     
    19181939!               ENDDO
    19191940!            ENDIF
    1920 ! 
     1941!
    19211942!         CASE ( 'im_t_indoor_wall_win' )
    1922 !            IF ( av == 0 ) THEN           
     1943!            IF ( av == 0 )  THEN
    19231944!               DO l = 0, 3
    19241945!                  DO m = 1, surf_usm_v(l)%ns
     
    19331954        CASE DEFAULT
    19341955           found = .FALSE.
    1935            
    1936     END SELECT   
    1937 
    1938  END SUBROUTINE im_data_output_3d         
    1939 !------------------------------------------------------------------------------!
     1956
     1957    END SELECT
     1958
     1959 END SUBROUTINE im_data_output_3d
     1960
     1961
     1962!--------------------------------------------------------------------------------------------------!
    19401963! Description:
    19411964! ------------
    19421965!> Parin for &indoor_parameters for indoor model
    1943 !------------------------------------------------------------------------------!
     1966!--------------------------------------------------------------------------------------------------!
    19441967 SUBROUTINE im_parin
    1945    
    1946     USE control_parameters,                                                    &
     1968
     1969    USE control_parameters,                                                                        &
    19471970        ONLY:  indoor_model
    19481971
     
    19511974
    19521975    NAMELIST /indoor_parameters/  initial_indoor_temperature
     1976
    19531977
    19541978!
     
    19561980    REWIND ( 11 )
    19571981    line = ' '
    1958     DO   WHILE ( INDEX( line, '&indoor_parameters' ) == 0 )
     1982    DO  WHILE ( INDEX( line, '&indoor_parameters' ) == 0 )
    19591983       READ ( 11, '(A)', END=10 )  line
    19601984    ENDDO
     
    19802004
    19812005 10 CONTINUE
    1982    
     2006
    19832007 END SUBROUTINE im_parin
    19842008
Note: See TracChangeset for help on using the changeset viewer.