Ignore:
Timestamp:
Feb 15, 2019 6:38:58 PM (5 years ago)
Author:
suehring
Message:

Coupling of indoor model to atmosphere; output of indoor temperatures and waste heat; enable restarts with indoor model; bugfix plant transpiration; bugfix - missing calculation of 10cm temperature

File:
1 edited

Legend:

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

    r3685 r3744  
    2121! Current revisions:
    2222! -----------------
    23 !
     23! - remove building_type from module
     24! - initialize parameters for each building individually instead of a bulk
     25!   initializaion with  identical building type for all
     26! - output revised
     27! - add missing _wp
     28! - some restructuring of variables in building data structure
    2429!
    2530! Former revisions:
     
    7681
    7782    USE kinds
     83   
     84    USE netcdf_data_input_mod,                                                 &
     85        ONLY:  building_id_f, building_type_f
    7886
    7987    USE surface_mod,                                                           &
     
    105113       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facade_v   !< number of vertical facades elements per buidling
    106114                                                                  !< and height level
     115                                                                 
     116       INTEGER(iwp) ::  ventilation_int_loads
    107117
    108118       LOGICAL ::  on_pe = .FALSE.   !< flag indicating whether a building with certain ID is on local subdomain
     119       
     120       
     121       REAL(wp) ::  lambda_layer3     !< [W/(m*K)] Thermal conductivity of the inner layer 
     122       REAL(wp) ::  s_layer3          !< [m] half thickness of the inner layer (layer_3)
     123       REAL(wp) ::  f_c_win           !< [-] shading factor
     124       REAL(wp) ::  g_value_win       !< [-] SHGC factor
     125       REAL(wp) ::  u_value_win       !< [W/(m2*K)] transmittance
     126       REAL(wp) ::  air_change_low    !< [1/h] air changes per time_utc_hour
     127       REAL(wp) ::  air_change_high   !< [1/h] air changes per time_utc_hour
     128       REAL(wp) ::  eta_ve            !< [-] heat recovery efficiency
     129       REAL(wp) ::  factor_a          !< [-] Dynamic parameters specific effective surface according to Table 12; 2.5
     130                                      !< (very light, light and medium), 3.0 (heavy), 3.5 (very heavy)
     131       REAL(wp) ::  factor_c          !< [J/(m2 K)] Dynamic parameters inner heatstorage according to Table 12; 80000
     132                                      !< (very light), 110000 (light), 165000 (medium), 260000 (heavy), 370000 (very heavy)
     133       REAL(wp) ::  lambda_at         !< [-] ratio internal surface/floor area chap. 7.2.2.2.
     134       REAL(wp) ::  theta_int_h_set   !< [degree_C] Max. Setpoint temperature (winter)
     135       REAL(wp) ::  theta_int_c_set   !< [degree_C] Max. Setpoint temperature (summer)
     136       REAL(wp) ::  phi_h_max         !< [W] Max. Heating capacity (negative)
     137       REAL(wp) ::  phi_c_max         !< [W] Max. Cooling capacity (negative)
     138       REAL(wp) ::  qint_high         !< [W/m2] internal heat gains, option Database qint_0-23
     139       REAL(wp) ::  qint_low          !< [W/m2] internal heat gains, option Database qint_0-23
     140       REAL(wp) ::  height_storey     !< [m] storey heigth
     141       REAL(wp) ::  height_cei_con    !< [m] ceiling construction heigth
    109142
    110143       REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in       !< mean building indoor temperature, height dependent
     
    113146       REAL(wp), DIMENSION(:), ALLOCATABLE ::  vol_frac   !< fraction of local on total building volume, height dependent
    114147       REAL(wp), DIMENSION(:), ALLOCATABLE ::  vpf        !< building volume volume per facade element, height dependent
    115 
     148       
    116149    END TYPE build
    117150
     
    130163!-- Declare all global variables within the module
    131164
    132     INTEGER(iwp) ::  building_type = 1       !< namelist parameter with
     165!     INTEGER(iwp) ::  building_type = 1       !< namelist parameter with
    133166                                             !< X1=construction year (cy) 1950, X2=cy 2000, X3=cy 2050
    134167                                             !< R=Residental building, O=Office, RW=Enlarged Windows, P=Panel type (Plattenbau) WBS 70, H=Hospital (in progress), I=Industrial halls (in progress), S=Special Building (in progress)
     
    139172    INTEGER(iwp) ::  solar_protection_on     !< Solar protection on
    140173
    141     REAL(wp) ::  air_change_high             !< [1/h] air changes per time_utc_hour
    142     REAL(wp) ::  air_change_low              !< [1/h] air changes per time_utc_hour
    143     REAL(wp) ::  eff_mass_area               !< [m²] the effective mass-related area
    144     REAL(wp) ::  floor_area_per_facade       !< [m²] net floor area (Sum of all floors)
    145     REAL(wp) ::  total_area                  !<! [m²] area of all surfaces pointing to zone
     174    REAL(wp) ::  eff_mass_area               !< [m2] the effective mass-related area
     175    REAL(wp) ::  floor_area_per_facade       !< [m2] net floor area (Sum of all floors)
     176    REAL(wp) ::  total_area                  !<! [m2] area of all surfaces pointing to zone
    146177    REAL(wp) ::  window_area_per_facade      !< [m2] window area per facade element
    147178    REAL(wp) ::  air_change                  !< [1/h] Airflow
    148     REAL(wp) ::  bldg_part_surf_i    = 4     !< [m²_surf,i] part building surface, from Palm, das mÃŒsste mittlerweile "facade_element_area" sein!
    149     REAL(wp) ::  facade_element_area         !< [m²_facade] building surface facade
    150     REAL(wp) ::  indoor_volume_per_facade    !< [m³] indoor air volume per facade element
     179    REAL(wp) ::  facade_element_area         !< [m2_facade] building surface facade
     180    REAL(wp) ::  indoor_volume_per_facade    !< [m3] indoor air volume per facade element
    151181    REAL(wp) ::  c_m                         !< [J/K] internal heat storage capacity
    152182    REAL(wp) ::  dt_indoor = 3600.0_wp       !< [s] namelist parameter: time interval for indoor-model application
    153     REAL(wp) ::  eta_ve                      !< [-] heat recovery efficiency
    154     REAL(wp) ::  f_c_win                     !< [-] shading factor
    155     REAL(wp) ::  factor_a                    !< [-] Dynamic parameters specific effective surface according to Table 12; 2.5 (very light, light and medium), 3.0 (heavy), 3.5 (very heavy)
    156     REAL(wp) ::  factor_c                    !< [J/(m2 K)] Dynamic parameters inner heatstorage according to Table 12; 80000 (very light), 110000 (light), 165000 (medium), 260000 (heavy), 370000 (very heavy)
    157     REAL(wp) ::  g_value_win                 !< [-] SHGC factor
    158183    REAL(wp) ::  h_tr_1                      !<! [W/K] Heat transfer coefficient auxiliary variable 1
    159184    REAL(wp) ::  h_tr_2                      !<! [W/K] Heat transfer coefficient auxiliary variable 2
     
    165190    REAL(wp) ::  h_tr_w                      !<! [W/K] heat transfer coefficient of doors, windows, curtain walls and glazed walls (assumption: thermal mass=0)
    166191    REAL(wp) ::  h_ve                        !<! [W/K] heat transfer of ventilation
    167     REAL(wp) ::  height_storey               !< [m] storey heigth
    168     REAL(wp) ::  height_cei_con              !< [m] ceiling construction heigth   
    169192    REAL(wp) ::  initial_indoor_temperature  !< namelist parameter
    170     REAL(wp) ::  lambda_at                   !< [-] ratio internal surface/floor area chap. 7.2.2.2.
    171     REAL(wp) ::  lambda_layer3               !< [W/(m*K)] Thermal conductivity of the inner layer 
    172193    REAL(wp) ::  net_sw_in                   !< net short-wave radiation (in - out; was i_global --> CORRECT?)
    173     REAL(wp) ::  qint_high                   !< [W/m2] internal heat gains, option Database qint_0-23
    174     REAL(wp) ::  qint_low                    !< [W/m2] internal heat gains, option Database qint_0-23
    175     REAL(wp) ::  phi_c_max                   !< [W] Max. Cooling capacity (negative)
    176     REAL(wp) ::  phi_h_max                   !< [W] Max. Heating capacity (negative)
    177194    REAL(wp) ::  phi_hc_nd                   !<! [W] heating demand and/or cooling demand
    178195    REAL(wp) ::  phi_hc_nd_10                !<! [W] heating demand and/or cooling demand for heating or cooling
     
    185202    REAL(wp) ::  phi_st                      !<! [W] mass specific thermal load implied non thermal mass
    186203    REAL(wp) ::  q_emission                  !< emissions, in first version = 0, option for second part of the project
    187     REAL(wp) ::  q_wall_win               !< heat flux from indoor into wall/window
     204    REAL(wp) ::  q_wall_win                  !< heat flux from indoor into wall/window
    188205    REAL(wp) ::  q_waste_heat                !< waste heat, sum of waste heat over the roof to Palm
    189206    REAL(wp) ::  q_waste_heat_bldg           !< [W/building] waste heat of the complete building, in Palm sum of all indoor_model-calculations
    190     REAL(wp) ::  s_layer3                    !< [m] half thickness of the inner layer (layer_3)
    191207    REAL(wp) ::  schedule_d                  !< activation for internal loads (low or high + low)
    192208    REAL(wp) ::  skip_time_do_indoor = 0.0_wp  !< [s] Indoor model is not called before this time
    193209    REAL(wp) ::  theta_air                   !<! [degree_C] air temperature of the RC-node
    194210    REAL(wp) ::  theta_air_0                 !<! [degree_C] air temperature of the RC-node in equilibrium
    195     REAL(wp) ::  theta_air_10                !<! [degree_C] air temperature of the RC-node from a heating capacity of 10 W/m²
     211    REAL(wp) ::  theta_air_10                !<! [degree_C] air temperature of the RC-node from a heating capacity of 10 W/m2
    196212    REAL(wp) ::  theta_air_ac                !< [degree_C] actual room temperature after heating/cooling
    197213    REAL(wp) ::  theta_air_set               !< [degree_C] Setpoint_temperature for the room
    198     REAL(wp) ::  theta_int_c_set             !< [degree_C] Max. Setpoint temperature (summer)
    199     REAL(wp) ::  theta_int_h_set             !< [degree_C] Max. Setpoint temperature (winter)
    200214    REAL(wp) ::  theta_m                     !<! [degree_C} inner temperature of the RC-node
    201215    REAL(wp) ::  theta_m_t                   !<! [degree_C] (Fictive) component temperature timestep
     
    205219    REAL(wp) ::  time_indoor = 0.0_wp        !< [s] time since last call of indoor model
    206220    REAL(wp) ::  time_utc_hour               !< Time in hours per day (UTC)
    207     REAL(wp) ::  u_value_win                 !< [W/(m2*K)] transmittance
    208221    REAL(wp) ::  ventilation_int_loads       !< Zuteilung der GebÀude fÃŒr Verlauf/AktivitÀt der LÃŒftung und internen Lasten
    209 
    210 !
    211 !-- Declare all global parameters within the module   
     222   
     223    REAL(wp) ::  f_sr                        !< [-] factor surface reduction
     224    REAL(wp) ::  f_cei                       !< [-] ceiling reduction factor
     225    REAL(wp) ::  ngs                         !< [m2] netto ground surface
     226    REAL(wp) ::  building_height
     227   
    212228    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
    213229    REAL(wp), PARAMETER ::  params_f_w               = 0.9_wp      !< [-] correction factor (fuer nicht senkrechten Stahlungseinfall DIN 4108-2 chap.8, (hier konstant, keine WinkelabhÀngigkeit)
     
    218234    REAL(wp), PARAMETER ::  h_is                     = 3.45_wp     !< [W/(m^2 K)]  h_is = 3.45 between surface and air (chap. 7.2.2.2)
    219235    REAL(wp), PARAMETER ::  h_ms                     = 9.1_wp      !< [W/K] h_ms = 9.10 W / (m2 K) between component and surface (chap. 12.2.2)
    220  
     236
     237   
     238   
    221239    SAVE
    222240
     
    226244!
    227245!-- Add INTERFACES that must be available to other modules
    228     PUBLIC im_init, im_main_heatcool, im_parin
     246    PUBLIC im_init, im_main_heatcool, im_parin, im_define_netcdf_grid,          &
     247           im_check_data_output, im_data_output_3d, im_check_parameters
     248   
    229249
    230250!
     
    232252    PUBLIC dt_indoor, skip_time_do_indoor, time_indoor
    233253
     254!
     255!-- PALM interfaces:
     256!-- Data output checks for 2D/3D data to be done in check_parameters
     257     INTERFACE im_check_data_output
     258        MODULE PROCEDURE im_check_data_output
     259     END INTERFACE im_check_data_output
     260!
     261!-- Input parameter checks to be done in check_parameters
     262     INTERFACE im_check_parameters
     263        MODULE PROCEDURE im_check_parameters
     264     END INTERFACE im_check_parameters
     265!
     266!-- Data output of 3D data
     267     INTERFACE im_data_output_3d
     268        MODULE PROCEDURE im_data_output_3d
     269     END INTERFACE im_data_output_3d
     270
     271!
     272!-- Definition of data output quantities
     273     INTERFACE im_define_netcdf_grid
     274        MODULE PROCEDURE im_define_netcdf_grid
     275     END INTERFACE im_define_netcdf_grid
     276!
     277! !
     278! !-- Output of information to the header file
     279!     INTERFACE im_header
     280!        MODULE PROCEDURE im_header
     281!     END INTERFACE im_header
     282
     283!-- Data Output
     284!    INTERFACE im_data_output
     285!       MODULE PROCEDURE im_data_output
     286!    END INTERFACE im_data_output
    234287!
    235288!-- Calculations for indoor temperatures 
     
    242295       MODULE PROCEDURE im_init
    243296    END INTERFACE im_init
    244  
    245297!
    246298!-- Main part of indoor model 
     
    268320    USE arrays_3d,                                                             &
    269321        ONLY:  pt
    270 
    271 
     322   
     323   
    272324    IMPLICIT NONE
    273325   
     
    280332    REAL(wp) ::  near_facade_temperature
    281333    REAL(wp) ::  phi_hc_nd_dummy
     334   
    282335
    283336    !< Calculation of total mass specific thermal load (internal and external)
     
    292345    !< Calculation of component temperature at factual timestep
    293346    theta_m_t = ( ( theta_m_t_prev                                               &
    294                     * ( ( c_m / 3600 ) - 0.5 * ( h_tr_3 + h_tr_em ) ) + phi_mtot &
     347                    * ( ( c_m / 3600.0_wp ) - 0.5_wp * ( h_tr_3 + h_tr_em ) ) + phi_mtot &
    295348                  )                                                              &
    296                   /   ( ( c_m / 3600 ) + 0.5 * ( h_tr_3 + h_tr_em ) )            &
     349                  /   ( ( c_m / 3600.0_wp ) + 0.5_wp * ( h_tr_3 + h_tr_em ) )            &
    297350                )                                                               !< [degree_C] Eq. (C.4)
    298351
    299352    !< Calculation of mean inner temperature for the RC-node in actual timestep
    300     theta_m = ( theta_m_t + theta_m_t_prev ) * 0.5                              !< [degree_C] Eq. (C.9)
     353    theta_m = ( theta_m_t + theta_m_t_prev ) * 0.5_wp                              !< [degree_C] Eq. (C.9)
    301354   
    302355    !< Calculation of mean surface temperature of the RC-node in actual timestep
     
    343396        ONLY:  dx, dy
    344397
    345     USE netcdf_data_input_mod,                                                 &
    346         ONLY:  building_id_f
    347 
    348398    USE pegrid
    349399
     
    356406    IMPLICIT NONE
    357407
     408    INTEGER(iwp) ::  bt   !< local building type
    358409    INTEGER(iwp) ::  fa   !< running index for facade elements of each building
    359410    INTEGER(iwp) ::  i    !< running index along x-direction
     
    384435    INTEGER(iwp), DIMENSION(0:numprocs-1) ::  num_buildings         !< number of buildings with different ID on entire model domain
    385436    INTEGER(iwp), DIMENSION(0:numprocs-1) ::  num_buildings_l       !< number of buildings with different ID on local subdomain
    386 
     437   
    387438    REAL(wp), DIMENSION(:), ALLOCATABLE ::  local_weight   !< dummy representing fraction of local on total building volume,
    388439                                                           !< height dependent
     
    503554!-- the respective building is present (in order to reduce memory demands).
    504555    ALLOCATE( buildings(1:num_build) )
     556
    505557!
    506558!-- Store building IDs and check if building with certain ID is present on
     
    792844
    793845!
    794 !-- Building parameters by type of building. Assigned in urban_surface_mod.f90
    795 
    796     lambda_layer3            = building_pars(63, building_type)
    797     s_layer3                 = building_pars(57, building_type)
    798     f_c_win                  = building_pars(119, building_type)
    799     g_value_win              = building_pars(120, building_type)   
    800     u_value_win              = building_pars(121, building_type)   
    801     air_change_low           = building_pars(122, building_type)   
    802     air_change_high          = building_pars(123, building_type)   
    803     eta_ve                   = building_pars(124, building_type)   
    804     factor_a                 = building_pars(125, building_type)   
    805     factor_c                 = building_pars(126, building_type)
    806     lambda_at                = building_pars(127, building_type)   
    807     theta_int_h_set          = building_pars(118, building_type)   
    808     theta_int_c_set          = building_pars(117, building_type)
    809     phi_h_max                = building_pars(128, building_type)   
    810     phi_c_max                = building_pars(129, building_type)         
    811     qint_high                = building_pars(130, building_type)
    812     qint_low                 = building_pars(131, building_type)
    813     height_storey            = building_pars(132, building_type)
    814     height_cei_con           = building_pars(133, building_type)
    815 
    816 !
    817 !-- Setting of initial room temperature [K]
     846!-- Initialize building parameters, first by mean building type. Note,
     847!-- in this case all buildings have the same type.
     848!-- In a second step initialize with building tpyes from static input file,
     849!-- where building types can be individual for each building.
     850    buildings(:)%lambda_layer3    = building_pars(63,building_type)
     851    buildings(:)%s_layer3         = building_pars(57,building_type)
     852    buildings(:)%f_c_win          = building_pars(119,building_type)
     853    buildings(:)%g_value_win      = building_pars(120,building_type)   
     854    buildings(:)%u_value_win      = building_pars(121,building_type)   
     855    buildings(:)%air_change_low   = building_pars(122,building_type)   
     856    buildings(:)%air_change_high  = building_pars(123,building_type)   
     857    buildings(:)%eta_ve           = building_pars(124,building_type)   
     858    buildings(:)%factor_a         = building_pars(125,building_type)   
     859    buildings(:)%factor_c         = building_pars(126,building_type)
     860    buildings(:)%lambda_at        = building_pars(127,building_type)   
     861    buildings(:)%theta_int_h_set  = building_pars(118,building_type)   
     862    buildings(:)%theta_int_c_set  = building_pars(117,building_type)
     863    buildings(:)%phi_h_max        = building_pars(128,building_type)   
     864    buildings(:)%phi_c_max        = building_pars(129,building_type)         
     865    buildings(:)%qint_high        = building_pars(130,building_type)
     866    buildings(:)%qint_low         = building_pars(131,building_type)
     867    buildings(:)%height_storey    = building_pars(132,building_type)
     868    buildings(:)%height_cei_con   = building_pars(133,building_type)
     869!
     870!-- Initialize ventilaation load. Please note, building types > 7 are actually
     871!-- not allowed (check already in urban_surface_mod and netcdf_data_input_mod.
     872!-- However, the building data base may be later extended.
     873    IF ( building_type ==  1  .OR.  building_type ==  2  .OR.                  &
     874         building_type ==  3  .OR.  building_type == 10  .OR.                  &
     875         building_type == 11  .OR.  building_type == 12 )  THEN
     876       buildings(nb)%ventilation_int_loads = 1
     877!
     878!-- Office, building with large windows
     879    ELSEIF ( building_type ==  4  .OR.  building_type ==  5  .OR.              &
     880             building_type ==  6  .OR.  building_type ==  7  .OR.              &
     881             building_type ==  8  .OR.  building_type ==  9)  THEN
     882       buildings(nb)%ventilation_int_loads = 2
     883!
     884!-- Industry, hospitals
     885    ELSEIF ( building_type == 13  .OR.  building_type == 14  .OR.              &
     886             building_type == 15  .OR.  building_type == 16  .OR.              &
     887             building_type == 17  .OR.  building_type == 18 )  THEN
     888       buildings(nb)%ventilation_int_loads = 3
     889    ENDIF
     890!
     891!-- Initialization of building parameters - level 2
     892    IF ( building_type_f%from_file )  THEN
     893       DO  i = nxl, nxr
     894          DO  j = nys, nyn
     895              IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
     896                 nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ),    &
     897                              DIM = 1 )
     898                 bt = building_type_f%var(j,i)
     899                 
     900                 buildings(nb)%lambda_layer3    = building_pars(63,bt)
     901                 buildings(nb)%s_layer3         = building_pars(57,bt)
     902                 buildings(nb)%f_c_win          = building_pars(119,bt)
     903                 buildings(nb)%g_value_win      = building_pars(120,bt)   
     904                 buildings(nb)%u_value_win      = building_pars(121,bt)   
     905                 buildings(nb)%air_change_low   = building_pars(122,bt)   
     906                 buildings(nb)%air_change_high  = building_pars(123,bt)   
     907                 buildings(nb)%eta_ve           = building_pars(124,bt)   
     908                 buildings(nb)%factor_a         = building_pars(125,bt)   
     909                 buildings(nb)%factor_c         = building_pars(126,bt)
     910                 buildings(nb)%lambda_at        = building_pars(127,bt)   
     911                 buildings(nb)%theta_int_h_set  = building_pars(118,bt)   
     912                 buildings(nb)%theta_int_c_set  = building_pars(117,bt)
     913                 buildings(nb)%phi_h_max        = building_pars(128,bt)   
     914                 buildings(nb)%phi_c_max        = building_pars(129,bt)         
     915                 buildings(nb)%qint_high        = building_pars(130,bt)
     916                 buildings(nb)%qint_low         = building_pars(131,bt)
     917                 buildings(nb)%height_storey    = building_pars(132,bt)
     918                 buildings(nb)%height_cei_con   = building_pars(133,bt)                 
     919!
     920!--              Initialize ventilaation load. Please note, building types > 7
     921!--              are actually not allowed (check already in urban_surface_mod 
     922!--              and netcdf_data_input_mod. However, the building data base may
     923!--              be later extended.
     924                 IF ( bt ==  1  .OR.  bt ==  2  .OR.                           &
     925                      bt ==  3  .OR.  bt == 10  .OR.                           &
     926                      bt == 11  .OR.  bt == 12 )  THEN
     927                    buildings(nb)%ventilation_int_loads = 1
     928!                   
     929!--              Office, building with large windows
     930                 ELSEIF ( bt ==  4  .OR.  bt ==  5  .OR.                       &
     931                          bt ==  6  .OR.  bt ==  7  .OR.                       &
     932                          bt ==  8  .OR.  bt ==  9)  THEN
     933                    buildings(nb)%ventilation_int_loads = 2
     934!
     935!--              Industry, hospitals
     936                 ELSEIF ( bt == 13  .OR.  bt == 14  .OR.                       &
     937                          bt == 15  .OR.  bt == 16  .OR.                       &
     938                          bt == 17  .OR.  bt == 18 )  THEN
     939                    buildings(nb)%ventilation_int_loads = 3
     940                 ENDIF
     941              ENDIF
     942           ENDDO
     943        ENDDO
     944    ENDIF
     945!
     946!-- Initial room temperature [K]
    818947!-- (after first loop, use theta_m_t as theta_m_t_prev)
    819948    theta_m_t_prev = initial_indoor_temperature
     949!
     950!-- Initialize indoor temperature. Actually only for output at initial state.
     951    DO  nb = 1, num_build
     952       buildings(nb)%t_in(:) = initial_indoor_temperature
     953    ENDDO
    820954
    821955    CALL location_message( 'finished', .TRUE. )
     
    8741008    REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in_l_send   !< dummy send buffer used for summing-up indoor temperature per kk-level
    8751009    REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in_recv     !< dummy recv buffer used for summing-up indoor temperature per kk-level
    876 
    877 !
    878 !-- Daily schedule, here for 08:00-18:00 = 1, other hours = 0.
    879 !-- time_utc_hour is calculated here based on time_utc [s] from
    880 !-- date_and_time_mod.
    881 !-- (kanani: Does this schedule not depend on if it's an office or resident
    882 !-- building?)
     1010!
     1011!-- Determine time of day in hours.
    8831012    time_utc_hour = time_utc / 3600.0_wp
    884 
    885 !
    886 !-- Allocation of the load profiles to the building types
    887 !-- Residental Building, panel WBS 70
    888     if      (building_type ==  1 .OR. &
    889              building_type ==  2 .OR. &
    890              building_type ==  3 .OR. &
    891              building_type == 10 .OR. &
    892              building_type == 11 .OR. &
    893              building_type == 12) then
    894                                         ventilation_int_loads = 1
    895 !-- Office, building with large windows
    896     else if (building_type ==  4 .OR. &
    897              building_type ==  5 .OR. &
    898              building_type ==  6 .OR. &
    899              building_type ==  7 .OR. &
    900              building_type ==  8 .OR. &
    901              building_type ==  9) then
    902                                         ventilation_int_loads = 2
    903 !-- Industry, hospitals
    904     else if (building_type == 13 .OR. &
    905              building_type == 14 .OR. &
    906              building_type == 15 .OR. &
    907              building_type == 16 .OR. &
    908              building_type == 17 .OR. &
    909              building_type == 18) then
    910                                         ventilation_int_loads = 3
    911 
    912     end if
    913 
    914 !-- Residental Building, panel WBS 70
    915    
    916     if (ventilation_int_loads == 1) THEN
    917        if ( time_utc_hour >= 6.0_wp .AND. time_utc_hour <= 8.0_wp )  THEN
    918           schedule_d = 1
    919        else if ( time_utc_hour >= 18.0_wp .AND. time_utc_hour <= 23.0_wp )  THEN
    920           schedule_d = 1
    921        else
    922           schedule_d = 0
    923        end if
    924     end if
    925 
    926 !-- Office, building with large windows
    927 
    928     if (ventilation_int_loads == 2) THEN
    929        if ( time_utc_hour >= 8.0_wp  .AND.  time_utc_hour <= 18.0_wp )  THEN
    930           schedule_d = 1
    931        else
    932           schedule_d = 0
    933        end if
    934     end if
    935        
    936 !-- Industry, hospitals
    937     if (ventilation_int_loads == 3) THEN
    938        if ( time_utc_hour >= 6.0_wp  .AND.  time_utc_hour <= 22.0_wp )  THEN
    939           schedule_d = 1
    940        else
    941           schedule_d = 0
    942        end if
    943     end if
    944 
    945 
    9461013!
    9471014!-- Following calculations must be done for each facade element.
     
    9511018       IF ( buildings(nb)%on_pe )  THEN
    9521019!
     1020!--       Determine daily schedule. 08:00-18:00 = 1, other hours = 0.
     1021!--       Residental Building, panel WBS 70   
     1022          IF ( buildings(nb)%ventilation_int_loads == 1 )  THEN
     1023             IF ( time_utc_hour >= 6.0_wp  .AND.  time_utc_hour <= 8.0_wp )  THEN
     1024                schedule_d = 1
     1025             ELSEIF ( time_utc_hour >= 18.0_wp  .AND.  time_utc_hour <= 23.0_wp )  THEN
     1026                schedule_d = 1
     1027             ELSE
     1028                schedule_d = 0
     1029             ENDIF
     1030          ENDIF
     1031!
     1032!--       Office, building with large windows
     1033          IF ( buildings(nb)%ventilation_int_loads == 2 )  THEN
     1034             IF ( time_utc_hour >= 8.0_wp  .AND.  time_utc_hour <= 18.0_wp )  THEN
     1035                schedule_d = 1
     1036             ELSE
     1037                schedule_d = 0
     1038             ENDIF
     1039          ENDIF
     1040!       
     1041!--       Industry, hospitals
     1042          IF ( buildings(nb)%ventilation_int_loads == 3 )  THEN
     1043             IF ( time_utc_hour >= 6.0_wp  .AND.  time_utc_hour <= 22.0_wp )  THEN
     1044                schedule_d = 1
     1045             ELSE
     1046                schedule_d = 0
     1047             ENDIF
     1048          ENDIF
     1049!
    9531050!--       Initialize/reset indoor temperature
    954           buildings(nb)%t_in   = 0.0_wp
    9551051          buildings(nb)%t_in_l = 0.0_wp
    9561052!
     
    9701066             indoor_volume_per_facade = buildings(nb)%vpf(kk)               !< [m3] indoor air volume per facade element           
    9711067             window_area_per_facade   = surf_usm_h%frac(ind_wat_win,m)  * facade_element_area  !< [m2] window area per facade element
    972              eff_mass_area            = factor_a * floor_area_per_facade    !< [m2] standard values according to Table 12 section 12.3.1.2  (calculate over Eq. (65) according to section 12.3.1.2)
    973              c_m                      = factor_c * floor_area_per_facade    !< [J/K] standard values according to table 12 section 12.3.1.2 (calculate over Eq. (66) according to section 12.3.1.2)
    974              total_area               = lambda_at * floor_area_per_facade   !< [m2] area of all surfaces pointing to zone  Eq. (9) according to section 7.2.2.2
     1068             
     1069!              building_height          = buildings(nb)%num_facades_per_building_v_l * 0.1 * dzw(kk)
     1070             building_height          = buildings(nb)%kb_max * dzw(kk)
     1071             
     1072! print*, "building_height", building_height
     1073! print*, "num_facades_v_l", buildings(nb)%num_facades_per_building_v_l
     1074! print*, "num_facades_v", buildings(nb)%num_facades_per_building_v
     1075! print*, "kb_min_max", buildings(nb)%kb_min, buildings(nb)%kb_max
     1076! print*, "dzw kk", dzw(kk), kk
     1077
     1078             f_cei                    = building_height/(buildings(nb)%height_storey-buildings(nb)%height_cei_con) !< [-] factor for ceiling redcution
     1079             ngs                      = buildings(nb)%vpf(kk)/f_cei                    !< [m2] calculation of netto ground surface
     1080             f_sr                     = ngs/floor_area_per_facade                      !< [-] factor for surface reduction
     1081             eff_mass_area            = buildings(nb)%factor_a * ngs    !< [m2] standard values according to Table 12 section 12.3.1.2  (calculate over Eq. (65) according to section 12.3.1.2)
     1082             c_m                      = buildings(nb)%factor_c * ngs    !< [J/K] standard values according to table 12 section 12.3.1.2 (calculate over Eq. (66) according to section 12.3.1.2)
     1083             total_area               = buildings(nb)%lambda_at * floor_area_per_facade   !< [m2] area of all surfaces pointing to zone  Eq. (9) according to section 7.2.2.2
    9751084
    9761085!--          Calculation of heat transfer coefficient for transmission --> not time-dependent
    977              h_tr_w   = window_area_per_facade * u_value_win   !< [W/K] only for windows
     1086             h_tr_w   = window_area_per_facade * buildings(nb)%u_value_win   !< [W/K] only for windows
    9781087             h_tr_is  = total_area * h_is                      !< [W/K] with h_is = 3.45 W / (m2 K) between surface and air, Eq. (9)
    9791088             h_tr_ms  = eff_mass_area * h_ms                    !< [W/K] with h_ms = 9.10 W / (m2 K) between component and surface, Eq. (64)
    980              h_tr_op  = 1 / ( 1 / ( ( facade_element_area - window_area_per_facade ) &
    981                                     * lambda_layer3 / s_layer3 * 0.5 ) + 1 / h_tr_ms )
    982              h_tr_em  = 1 / ( 1 / h_tr_op - 1 / h_tr_ms )      !< [W/K] Eq. (63), Section 12.2.2
     1089             h_tr_op  = 1.0_wp / ( 1.0_wp / ( ( facade_element_area - window_area_per_facade ) &
     1090                                    * buildings(nb)%lambda_layer3 / buildings(nb)%s_layer3 * 0.5_wp ) + 1.0_wp / h_tr_ms )
     1091             h_tr_em  = 1.0_wp / ( 1.0_wp / h_tr_op - 1.0_wp / h_tr_ms )      !< [W/K] Eq. (63), Section 12.2.2
    9831092!
    9841093!--          internal air loads dependent on the occupacy of the room
    9851094!--          basical internal heat gains (qint_low) with additional internal heat gains by occupancy (qint_high) (0,5*phi_int)
    986              phi_ia = 0.5 * ( ( qint_high * schedule_d + qint_low )            &
    987                               * floor_area_per_facade )         !< [W] Eq. (C.1)
     1095             phi_ia = 0.5_wp * ( ( buildings(nb)%qint_high * schedule_d + buildings(nb)%qint_low )            &
     1096                              * ngs )         !< [W] Eq. (C.1)
    9881097!
    9891098!--          Airflow dependent on the occupacy of the room
    9901099!--          basical airflow (air_change_low) with additional airflow gains by occupancy (air_change_high)
    991              air_change = ( air_change_high * schedule_d + air_change_low )  !< [1/h]?
     1100             air_change = ( buildings(nb)%air_change_high * schedule_d + buildings(nb)%air_change_low )  !< [1/h]?
    9921101!
    9931102!--          Heat transfer of ventilation
     
    9951104!--          with heat capacity of air 0.33 Wh/m2K
    9961105             h_ve   = MAX( 0.01_wp , ( air_change * indoor_volume_per_facade *      &
    997                                     0.33_wp * (1 - eta_ve ) ) )    !< [W/K] from ISO 13789 Eq.(10)
     1106                                    0.33_wp * (1.0_wp - buildings(nb)%eta_ve ) ) )    !< [W/K] from ISO 13789 Eq.(10)
    9981107
    9991108!--          Heat transfer coefficient auxiliary variables
    1000              h_tr_1 = 1 / ( ( 1 / h_ve )   + ( 1 / h_tr_is ) )  !< [W/K] Eq. (C.6)
     1109             h_tr_1 = 1.0_wp / ( ( 1.0_wp / h_ve )   + ( 1.0_wp / h_tr_is ) )  !< [W/K] Eq. (C.6)
    10011110             h_tr_2 = h_tr_1 + h_tr_w                           !< [W/K] Eq. (C.7)
    1002              h_tr_3 = 1 / ( ( 1 / h_tr_2 ) + ( 1 / h_tr_ms ) )  !< [W/K] Eq. (C.8)
     1111             h_tr_3 = 1.0_wp / ( ( 1.0_wp / h_tr_2 ) + ( 1.0_wp / h_tr_ms ) )  !< [W/K] Eq. (C.8)
    10031112!
    10041113!--          Net short-wave radiation through window area (was i_global)
     
    10281137!--          DIN 4108 - 2 chap.8
    10291138             phi_sol = (   window_area_per_facade * net_sw_in * solar_protection_off               &
    1030                          + window_area_per_facade * net_sw_in * f_c_win * solar_protection_on )    &
    1031                        * g_value_win * ( 1 - params_f_f ) * params_f_w              !< [W]
     1139                         + window_area_per_facade * net_sw_in * buildings(nb)%f_c_win * solar_protection_on )    &
     1140                       * buildings(nb)%g_value_win * ( 1.0_wp - params_f_f ) * params_f_w              !< [W]
    10321141!
    10331142!--          Calculation of the mass specific thermal load for internal and external heatsources of the inner node
     
    10351144!
    10361145!--          Calculation mass specific thermal load implied non thermal mass
    1037              phi_st  =   ( 1 - ( eff_mass_area / total_area ) - ( h_tr_w / ( 9.1 * total_area ) ) ) &
     1146             phi_st  =   ( 1.0_wp - ( eff_mass_area / total_area ) - ( h_tr_w / ( 9.1_wp * total_area ) ) ) &
    10381147                       * ( phi_ia + phi_sol )                                       !< [W] Eq. (C.3) with phi_ia=0,5*phi_int
    10391148!
     
    10411150!--          Step 1: Indoor temperature without heating and cooling
    10421151!--          section C.4.1 Picture C.2 zone 3)
    1043              phi_hc_nd = 0
     1152             phi_hc_nd = 0.0_wp
    10441153             
    10451154             CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
     
    10471156!
    10481157!--          If air temperature between border temperatures of heating and cooling, assign output variable, then ready   
    1049              IF ( theta_int_h_set <= theta_air  .AND.  theta_air <= theta_int_c_set )  THEN
    1050                 phi_hc_nd_ac = 0
     1158             IF ( buildings(nb)%theta_int_h_set <= theta_air  .AND.  theta_air <= buildings(nb)%theta_int_c_set )  THEN
     1159                phi_hc_nd_ac = 0.0_wp
    10511160                phi_hc_nd    = phi_hc_nd_ac
    10521161                theta_air_ac = theta_air
    10531162!
    1054 !--          Step 2: Else, apply 10 W/m² heating/cooling power and calculate indoor temperature
     1163!--          Step 2: Else, apply 10 W/m2 heating/cooling power and calculate indoor temperature
    10551164!--          again.
    10561165             ELSE
     
    10601169
    10611170!--             Heating or cooling?
    1062                 IF ( theta_air > theta_int_c_set )  THEN
    1063                    theta_air_set = theta_int_c_set
     1171                IF ( theta_air > buildings(nb)%theta_int_c_set )  THEN
     1172                   theta_air_set = buildings(nb)%theta_int_c_set
    10641173                ELSE
    1065                    theta_air_set = theta_int_h_set
     1174                   theta_air_set = buildings(nb)%theta_int_h_set
    10661175                ENDIF
    10671176
     
    10791188                                            / (theta_air_10  - theta_air_0)            !< Eq. (C.13)
    10801189                                           
    1081                                            
    1082                                        
    10831190!--             Step 3: With temperature ratio to determine the heating or cooling capacity   
    10841191!--             If necessary, limit the power to maximum power
    10851192!--             section C.4.1 Picture C.2 zone 2) and 4)
    1086                 IF ( phi_c_max < phi_hc_nd_un  .AND.  phi_hc_nd_un < phi_h_max )  THEN
     1193                IF ( buildings(nb)%phi_c_max < phi_hc_nd_un  .AND.  phi_hc_nd_un < buildings(nb)%phi_h_max )  THEN
    10871194                   phi_hc_nd_ac = phi_hc_nd_un
    10881195                   phi_hc_nd = phi_hc_nd_un   
     
    10901197!--             Step 4: Inner temperature with maximum heating (phi_hc_nd_un positive) or cooling (phi_hc_nd_un negative)
    10911198!--             section C.4.1 Picture C.2 zone 1) and 5)
    1092                    IF ( phi_hc_nd_un > 0 )  THEN
    1093                       phi_hc_nd_ac = phi_h_max                                         !< Limit heating
     1199                   IF ( phi_hc_nd_un > 0.0_wp )  THEN
     1200                      phi_hc_nd_ac = buildings(nb)%phi_h_max                                         !< Limit heating
    10941201                   ELSE
    1095                       phi_hc_nd_ac = phi_c_max                                         !< Limit cooling
     1202                      phi_hc_nd_ac = buildings(nb)%phi_c_max                                         !< Limit cooling
    10961203                   ENDIF
    10971204                ENDIF
     
    11121219!--          Calculate the operating temperature with weighted mean temperature of air and mean solar temperature
    11131220!--          Will be used for thermal comfort calculations
    1114              theta_op     = 0.3 * theta_air_ac + 0.7 * theta_s          !< [degree_C] operative Temperature Eq. (C.12)
     1221             theta_op     = 0.3_wp * theta_air_ac + 0.7_wp * theta_s          !< [degree_C] operative Temperature Eq. (C.12)
    11151222!
    11161223!--          Heat flux into the wall. Value needed in urban_surface_mod to
     
    11321239!--          Calculation of waste heat
    11331240!--          Anthropogenic heat output
    1134               IF ( phi_hc_nd_ac > 0 )  THEN
    1135                    heating_on = 1
    1136                    cooling_on = 0
    1137               ELSE
    1138                    heating_on = 0
    1139                    cooling_on = 1
    1140               ENDIF
    1141 
    1142              q_waste_heat = (phi_hc_nd * (params_waste_heat_h * heating_on + params_waste_heat_c * cooling_on))  !< [W/m2]  anthropogenic heat output
    1143 !              surf_usm_h%shf(m)=q_waste_heat
     1241             IF ( phi_hc_nd_ac > 0.0_wp )  THEN
     1242                heating_on = 1
     1243                cooling_on = 0
     1244             ELSE
     1245                heating_on = 0
     1246                cooling_on = 1
     1247             ENDIF
     1248
     1249             q_waste_heat = (phi_hc_nd * (params_waste_heat_h * heating_on + params_waste_heat_c * cooling_on))!< [W/GebÀudemodell] , observe the directional convention in PALM!
     1250             surf_usm_h%waste_heat(m) = q_waste_heat
    11441251             
    11451252          ENDDO !< Horizontal surfaces loop
     
    11561263             kk = surf_usm_v(l)%k(m) + surf_usm_v(l)%koff
    11571264!
     1265!--          (SOME OF THE FOLLOWING (not time-dependent COULD PROBABLY GO INTO A FUNCTION
     1266!--          EXCEPT facade_element_area, EVERYTHING IS CALCULATED EQUALLY)
    11581267!--          Building geometries  --> not time-dependent
    11591268             IF ( l == 0  .OR. l == 1 ) facade_element_area = dx * dzw(kk)  !< [m2] surface area per facade element
     
    11621271             indoor_volume_per_facade = buildings(nb)%vpf(kk)               !< [m3] indoor air volume per facade element           
    11631272             window_area_per_facade   = surf_usm_v(l)%frac(ind_wat_win,m)  * facade_element_area  !< [m2] window area per facade element
    1164              eff_mass_area            = factor_a * floor_area_per_facade    !< [m2] standard values according to Table 12 section 12.3.1.2  (calculate over Eq. (65) according to section 12.3.1.2)
    1165              c_m                      = factor_c * floor_area_per_facade    !< [J/K] standard values according to table 12 section 12.3.1.2 (calculate over Eq. (66) according to section 12.3.1.2)
    1166              total_area               = lambda_at * floor_area_per_facade   !< [m2] area of all surfaces pointing to zone Eq. (9) according to section 7.2.2.2
     1273             
     1274             building_height          = buildings(nb)%kb_max * dzw(kk)
     1275             f_cei                    = building_height/(buildings(nb)%height_storey-buildings(nb)%height_cei_con) !< [-] factor for ceiling redcution
     1276             ngs                      = buildings(nb)%vpf(kk)/f_cei                    !< [m2] calculation of netto ground surface
     1277             f_sr                     = ngs/floor_area_per_facade                      !< [-] factor for surface reduction
     1278             eff_mass_area            = buildings(nb)%factor_a * ngs    !< [m2] standard values according to Table 12 section 12.3.1.2  (calculate over Eq. (65) according to section 12.3.1.2)
     1279             c_m                      = buildings(nb)%factor_c * ngs    !< [J/K] standard values according to table 12 section 12.3.1.2 (calculate over Eq. (66) according to section 12.3.1.2)
     1280             total_area               = buildings(nb)%lambda_at * floor_area_per_facade   !< [m2] area of all surfaces pointing to zone  Eq. (9) according to section 7.2.2.2
    11671281!
    11681282!--          Calculation of heat transfer coefficient for transmission --> not time-dependent
    1169              h_tr_w   = window_area_per_facade * u_value_win   !< [W/K] only for windows
     1283             h_tr_w   = window_area_per_facade * buildings(nb)%u_value_win   !< [W/K] only for windows
    11701284             h_tr_is  = total_area * h_is                      !< [W/K] with h_is = 3.45 W / (m2 K) between surface and air, Eq. (9)
    11711285             h_tr_ms  = eff_mass_area * h_ms                   !< [W/K] with h_ms = 9.10 W / (m2 K) between component and surface, Eq. (64)
    1172              h_tr_op  = 1 / ( 1 / ( ( facade_element_area - window_area_per_facade ) &
    1173                                     * lambda_layer3 / s_layer3 * 0.5 ) + 1 / h_tr_ms )
    1174              h_tr_em  = 1 / ( 1 / h_tr_op - 1 / h_tr_ms )      !< [W/K] Eq. (63), Section 12.2.2
     1286             h_tr_op  = 1.0_wp / ( 1.0_wp / ( ( facade_element_area - window_area_per_facade ) &
     1287                                    * buildings(nb)%lambda_layer3 / buildings(nb)%s_layer3 * 0.5_wp ) + 1.0_wp / h_tr_ms )
     1288             h_tr_em  = 1.0_wp / ( 1.0_wp / h_tr_op - 1.0_wp / h_tr_ms )      !< [W/K] Eq. (63), Section 12.2.2
    11751289!
    11761290!--          internal air loads dependent on the occupacy of the room
    11771291!--          basical internal heat gains (qint_low) with additional internal heat gains by occupancy (qint_high) (0,5*phi_int)
    1178              phi_ia = 0.5 * ( ( qint_high * schedule_d + qint_low )            &
    1179                               * floor_area_per_facade )                      !< [W] Eq. (C.1)
     1292             phi_ia = 0.5_wp * ( ( buildings(nb)%qint_high * schedule_d + buildings(nb)%qint_low )            &
     1293                              * ngs )                      !< [W] Eq. (C.1)
    11801294!
    11811295!--          Airflow dependent on the occupacy of the room
    11821296!--          basical airflow (air_change_low) with additional airflow gains by occupancy (air_change_high)
    1183              air_change = ( air_change_high * schedule_d + air_change_low ) 
     1297             air_change = ( buildings(nb)%air_change_high * schedule_d + buildings(nb)%air_change_low ) 
    11841298!
    11851299!--          Heat transfer of ventilation
     
    11871301!--          with heat capacity of air 0.33 Wh/m2K
    11881302             h_ve   = MAX( 0.01_wp , ( air_change * indoor_volume_per_facade *      &
    1189                                     0.33_wp * (1 - eta_ve ) ) )                    !< [W/K] from ISO 13789 Eq.(10)
     1303                                    0.33_wp * (1 - buildings(nb)%eta_ve ) ) )                    !< [W/K] from ISO 13789 Eq.(10)
    11901304                                   
    11911305!--          Heat transfer coefficient auxiliary variables
    1192              h_tr_1 = 1 / ( ( 1 / h_ve )   + ( 1 / h_tr_is ) )                  !< [W/K] Eq. (C.6)
     1306             h_tr_1 = 1.0_wp / ( ( 1.0_wp / h_ve )   + ( 1.0_wp / h_tr_is ) )                  !< [W/K] Eq. (C.6)
    11931307             h_tr_2 = h_tr_1 + h_tr_w                                           !< [W/K] Eq. (C.7)
    1194              h_tr_3 = 1 / ( ( 1 / h_tr_2 ) + ( 1 / h_tr_ms ) )                  !< [W/K] Eq. (C.8)
     1308             h_tr_3 = 1.0_wp / ( ( 1.0_wp / h_tr_2 ) + ( 1.0_wp / h_tr_ms ) )                  !< [W/K] Eq. (C.8)
    11951309!
    11961310!--          Net short-wave radiation through window area (was i_global)
     
    12201334!--          DIN 4108 - 2 chap.8
    12211335             phi_sol = (   window_area_per_facade * net_sw_in * solar_protection_off               &
    1222                          + window_area_per_facade * net_sw_in * f_c_win * solar_protection_on )    &
    1223                        * g_value_win * ( 1 - params_f_f ) * params_f_w
     1336                         + window_area_per_facade * net_sw_in * buildings(nb)%f_c_win * solar_protection_on )    &
     1337                       * buildings(nb)%g_value_win * ( 1.0_wp - params_f_f ) * params_f_w
    12241338!
    12251339!--          Calculation of the mass specific thermal load for internal and external heatsources
     
    12271341!
    12281342!--          Calculation mass specific thermal load implied non thermal mass
    1229              phi_st  =   ( 1 - ( eff_mass_area / total_area ) - ( h_tr_w / ( 9.1 * total_area ) ) ) &
     1343             phi_st  =   ( 1.0_wp - ( eff_mass_area / total_area ) - ( h_tr_w / ( 9.1_wp * total_area ) ) ) &
    12301344                       * ( phi_ia + phi_sol )                                       !< [W] Eq. (C.3) with phi_ia=0,5*phi_int
    12311345!
     
    12331347!--          Step 1: Indoor temperature without heating and cooling
    12341348!--          section C.4.1 Picture C.2 zone 3)
    1235              phi_hc_nd = 0
    1236              
     1349             phi_hc_nd = 0.0_wp
    12371350             CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
    12381351                                         near_facade_temperature, phi_hc_nd )
    12391352!
    12401353!--          If air temperature between border temperatures of heating and cooling, assign output variable, then ready 
    1241              IF ( theta_int_h_set <= theta_air  .AND.  theta_air <= theta_int_c_set )  THEN
    1242                 phi_hc_nd_ac = 0
     1354             IF ( buildings(nb)%theta_int_h_set <= theta_air  .AND.  theta_air <= buildings(nb)%theta_int_c_set )  THEN
     1355                phi_hc_nd_ac = 0.0_wp
    12431356                phi_hc_nd    = phi_hc_nd_ac
    12441357                theta_air_ac = theta_air
    12451358!
    1246 !--          Step 2: Else, apply 10 W/m² heating/cooling power and calculate indoor temperature
     1359!--          Step 2: Else, apply 10 W/m2 heating/cooling power and calculate indoor temperature
    12471360!--          again.
    12481361             ELSE
     
    12521365
    12531366!--             Heating or cooling?
    1254                 IF ( theta_air > theta_int_c_set )  THEN
    1255                    theta_air_set = theta_int_c_set
     1367                IF ( theta_air > buildings(nb)%theta_int_c_set )  THEN
     1368                   theta_air_set = buildings(nb)%theta_int_c_set
    12561369                ELSE
    1257                    theta_air_set = theta_int_h_set
     1370                   theta_air_set = buildings(nb)%theta_int_h_set
    12581371                ENDIF
    12591372
     
    12741387!--             If necessary, limit the power to maximum power
    12751388!--             section C.4.1 Picture C.2 zone 2) and 4)
    1276                 IF ( phi_c_max < phi_hc_nd_un  .AND.  phi_hc_nd_un < phi_h_max )  THEN
     1389                IF ( buildings(nb)%phi_c_max < phi_hc_nd_un  .AND.  phi_hc_nd_un < buildings(nb)%phi_h_max )  THEN
    12771390                   phi_hc_nd_ac = phi_hc_nd_un
    12781391                   phi_hc_nd = phi_hc_nd_un
     
    12801393!--             Step 4: Inner temperature with maximum heating (phi_hc_nd_un positive) or cooling (phi_hc_nd_un negative)
    12811394!--             section C.4.1 Picture C.2 zone 1) and 5)
    1282                    IF ( phi_hc_nd_un > 0 )  THEN
    1283                       phi_hc_nd_ac = phi_h_max                                         !< Limit heating
     1395                   IF ( phi_hc_nd_un > 0.0_wp )  THEN
     1396                      phi_hc_nd_ac = buildings(nb)%phi_h_max                                         !< Limit heating
    12841397                   ELSE
    1285                       phi_hc_nd_ac = phi_c_max                                         !< Limit cooling
     1398                      phi_hc_nd_ac = buildings(nb)%phi_c_max                                         !< Limit cooling
    12861399                   ENDIF
    12871400                ENDIF
     
    13021415!--          Calculate the operating temperature with weighted mean of temperature of air and mean
    13031416!--          Will be used for thermal comfort calculations
    1304              theta_op     = 0.3 * theta_air_ac + 0.7 * theta_s
     1417             theta_op     = 0.3_wp * theta_air_ac + 0.7_wp * theta_s
    13051418!
    13061419!--          Heat flux into the wall. Value needed in urban_surface_mod to
     
    13221435!--          Calculation of waste heat
    13231436!--          Anthropogenic heat output
    1324               IF ( phi_hc_nd_ac > 0 )  THEN
    1325                    heating_on = 1
    1326                    cooling_on = 0
    1327               ELSE
    1328                    heating_on = 0
    1329                    cooling_on = 1
    1330               ENDIF
    1331 
    1332              q_waste_heat = (phi_hc_nd * (params_waste_heat_h * heating_on + params_waste_heat_c * cooling_on))   !< [W/m2] , anthropogenic heat output
    1333 !              surf_usm_v(l)%waste_heat(m)=q_waste_heat
    1334              
     1437             IF ( phi_hc_nd_ac > 0.0_wp )  THEN
     1438                heating_on = 1
     1439                cooling_on = 0
     1440             ELSE
     1441                heating_on = 0
     1442                cooling_on = 1
     1443             ENDIF
     1444
     1445             q_waste_heat = (phi_hc_nd * (params_waste_heat_h * heating_on + params_waste_heat_c * cooling_on))!< [W/GebÀudemodell] , observe the directional convention in PALM!
     1446             surf_usm_v(l)%waste_heat(m) = q_waste_heat
     1447
    13351448          ENDDO !< Vertical surfaces loop
    13361449
     
    13391452
    13401453!
    1341 !-- Determine total number of facade elements per building and assign number to
    1342 !-- building data type.
     1454!-- Determine the mean building temperature.
    13431455    DO  nb = 1, num_build
    13441456!
     
    13831495 END SUBROUTINE im_main_heatcool
    13841496
     1497!-----------------------------------------------------------------------------!
     1498! Description:
     1499!-------------
     1500!> Check data output for plant canopy model
     1501!-----------------------------------------------------------------------------!
     1502 SUBROUTINE im_check_data_output( var, unit )
     1503       
     1504    IMPLICIT NONE
     1505   
     1506    CHARACTER (LEN=*) ::  unit   !<
     1507    CHARACTER (LEN=*) ::  var    !<
     1508       
     1509    SELECT CASE ( TRIM( var ) )
     1510   
     1511   
     1512        CASE ( 'im_hf_roof')
     1513           unit = 'W m-2'
     1514       
     1515        CASE ( 'im_hf_wall_win' )
     1516           unit = 'W m-2'
     1517           
     1518        CASE ( 'im_hf_wall_win_waste' )
     1519           unit = 'W m-2'
     1520           
     1521        CASE ( 'im_hf_roof_waste' )
     1522           unit = 'W m-2'
     1523       
     1524        CASE ( 'im_t_indoor' )
     1525           unit = 'K'
     1526       
     1527        CASE DEFAULT
     1528           unit = 'illegal'
     1529           
     1530    END SELECT
     1531   
     1532 END SUBROUTINE
     1533
     1534
     1535!-----------------------------------------------------------------------------!
     1536! Description:
     1537!-------------
     1538!> Check parameters routine for plant canopy model
     1539!-----------------------------------------------------------------------------!
     1540 SUBROUTINE im_check_parameters
     1541
     1542!!!!   USE control_parameters,
     1543!!!!       ONLY: message_string
     1544       
     1545   IMPLICIT NONE
     1546   
     1547 END SUBROUTINE im_check_parameters
     1548
     1549!-----------------------------------------------------------------------------!
     1550! Description:
     1551!-------------
     1552!> Subroutine defining appropriate grid for netcdf variables.
     1553!> It is called from subroutine netcdf.
     1554!-----------------------------------------------------------------------------!
     1555 SUBROUTINE im_define_netcdf_grid( var, found, grid_x, grid_y, grid_z )
     1556
     1557   IMPLICIT NONE
     1558   
     1559   CHARACTER (LEN=*), INTENT(IN)  ::  var
     1560   LOGICAL, INTENT(OUT)           ::  found
     1561   CHARACTER (LEN=*), INTENT(OUT) ::  grid_x
     1562   CHARACTER (LEN=*), INTENT(OUT) ::  grid_y
     1563   CHARACTER (LEN=*), INTENT(OUT) ::  grid_z
     1564   
     1565   found   = .TRUE.
     1566   
     1567!
     1568!-- Check for the grid
     1569    SELECT CASE ( TRIM( var ) )
     1570
     1571       CASE ( 'im_hf_roof', 'im_hf_roof_waste' )
     1572          grid_x = 'x'
     1573          grid_y = 'y'
     1574          grid_z = 'zw'
     1575!
     1576!--    Heat fluxes at vertical walls are actually defined on stagged grid, i.e. xu, yv.
     1577       CASE ( 'im_hf_wall_win', 'im_hf_wall_win_waste' )
     1578          grid_x = 'x'
     1579          grid_y = 'y'
     1580          grid_z = 'zu'
     1581         
     1582       CASE ( 'im_t_indoor' )
     1583          grid_x = 'x'
     1584          grid_y = 'y'
     1585          grid_z = 'zw'
     1586         
     1587       CASE DEFAULT
     1588          found  = .FALSE.
     1589          grid_x = 'none'
     1590          grid_y = 'none'
     1591          grid_z = 'none'
     1592    END SELECT
     1593   
     1594 END SUBROUTINE im_define_netcdf_grid
     1595
     1596!------------------------------------------------------------------------------!
     1597! Description:
     1598! ------------
     1599!> Subroutine defining 3D output variables
     1600!------------------------------------------------------------------------------!
     1601 SUBROUTINE im_data_output_3d( av, variable, found, local_pf, fill_value,      &
     1602                               nzb_do, nzt_do )
     1603
     1604   USE indices
     1605   
     1606   USE kinds
     1607         
     1608   IMPLICIT NONE
     1609   
     1610    CHARACTER (LEN=*) ::  variable !<
     1611
     1612    INTEGER(iwp) ::  av    !<
     1613    INTEGER(iwp) ::  i     !<
     1614    INTEGER(iwp) ::  j     !<
     1615    INTEGER(iwp) ::  k     !<
     1616    INTEGER(iwp) ::  l     !<
     1617    INTEGER(iwp) ::  m     !<
     1618    INTEGER(iwp) ::  nb    !< index of the building in the building data structure
     1619    INTEGER(iwp) ::  nzb_do !< lower limit of the data output (usually 0)
     1620    INTEGER(iwp) ::  nzt_do !< vertical upper limit of the data output (usually nz_do3d)
     1621
     1622   
     1623    LOGICAL      ::  found !<
     1624
     1625    REAL(wp), INTENT(IN) ::  fill_value !< value for the _FillValue attribute
     1626
     1627    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
     1628   
     1629    local_pf = fill_value
     1630   
     1631    found = .TRUE.
     1632   
     1633    SELECT CASE ( TRIM( variable ) )
     1634!
     1635!--     Output of indoor temperature. All grid points within the building are
     1636!--     filled with values, while atmospheric grid points are set to _FillValues.
     1637        CASE ( 'im_t_indoor' )
     1638           IF ( av == 0 ) THEN
     1639              DO  i = nxl, nxr
     1640                 DO  j = nys, nyn
     1641                    IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
     1642!
     1643!--                    Determine index of the building within the building data structure.
     1644                       nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ),   &
     1645                                    DIM = 1 )
     1646!
     1647!--                    Write mean building temperature onto output array. Please note,
     1648!--                    in contrast to many other loops in the output, the vertical
     1649!--                    bounds are determined by the lowest and hightest vertical index
     1650!--                    occupied by the building.
     1651                       DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
     1652                          local_pf(i,j,k) = buildings(nb)%t_in(k)
     1653                       ENDDO
     1654                    ENDIF
     1655                 ENDDO
     1656              ENDDO
     1657           ENDIF 
     1658
     1659        CASE ( 'im_hf_roof' )
     1660           IF ( av == 0 ) THEN
     1661              DO  m = 1, surf_usm_h%ns
     1662                  i = surf_usm_h%i(m) !+ surf_usm_h%ioff
     1663                  j = surf_usm_h%j(m) !+ surf_usm_h%joff
     1664                  k = surf_usm_h%k(m) !+ surf_usm_h%koff
     1665                  local_pf(i,j,k) = surf_usm_h%iwghf_eb(m)
     1666              ENDDO
     1667           ENDIF
     1668   
     1669        CASE ( 'im_hf_roof_waste' )
     1670           IF ( av == 0 ) THEN
     1671              DO m = 1, surf_usm_h%ns
     1672                 i = surf_usm_h%i(m) !+ surf_usm_h%ioff
     1673                 j = surf_usm_h%j(m) !+ surf_usm_h%joff
     1674                 k = surf_usm_h%k(m) !+ surf_usm_h%koff
     1675                 local_pf(i,j,k) = surf_usm_h%waste_heat(m)
     1676              ENDDO
     1677           ENDIF                     
     1678       
     1679       CASE ( 'im_hf_wall_win' )
     1680           IF ( av == 0 ) THEN
     1681              DO l = 0, 3
     1682                 DO m = 1, surf_usm_v(l)%ns
     1683                    i = surf_usm_v(l)%i(m) !+ surf_usm_v(l)%ioff
     1684                    j = surf_usm_v(l)%j(m) !+ surf_usm_v(l)%joff
     1685                    k = surf_usm_v(l)%k(m) !+ surf_usm_v(l)%koff
     1686                    local_pf(i,j,k) = surf_usm_v(l)%iwghf_eb(m)
     1687                 ENDDO
     1688              ENDDO
     1689           ENDIF
     1690           
     1691        CASE ( 'im_hf_wall_win_waste' )
     1692           IF ( av == 0 ) THEN
     1693              DO l = 0, 3
     1694                 DO m = 1, surf_usm_v(l)%ns
     1695                    i = surf_usm_v(l)%i(m) !+ surf_usm_v(l)%ioff
     1696                    j = surf_usm_v(l)%j(m) !+ surf_usm_v(l)%joff
     1697                    k = surf_usm_v(l)%k(m) !+ surf_usm_v(l)%koff
     1698                    local_pf(i,j,k) =  surf_usm_v(l)%waste_heat(m)
     1699                 ENDDO
     1700              ENDDO
     1701           ENDIF     
     1702   
     1703        CASE DEFAULT
     1704           found = .FALSE.
     1705           
     1706    END SELECT   
     1707
     1708 END SUBROUTINE im_data_output_3d         
    13851709!------------------------------------------------------------------------------!
    13861710! Description:
     
    13971721    CHARACTER (LEN=80) ::  line  !< string containing current line of file PARIN
    13981722
    1399    
    1400    
    1401     NAMELIST /indoor_parameters/  building_type, dt_indoor,                           &
    1402                                   initial_indoor_temperature
    1403 
    1404 !    line = ' '
     1723    NAMELIST /indoor_parameters/  dt_indoor, initial_indoor_temperature
    14051724
    14061725!
     
    14101729    DO   WHILE ( INDEX( line, '&indoor_parameters' ) == 0 )
    14111730       READ ( 11, '(A)', END=10 )  line
    1412 !    PRINT*, 'line: ', line
    14131731    ENDDO
    14141732    BACKSPACE ( 11 )
Note: See TracChangeset for help on using the changeset viewer.