Ignore:
Timestamp:
Mar 6, 2019 4:58:03 PM (5 years ago)
Author:
raasch
Message:

unused variables removed, interoperable C datatypes introduced in particle type to avoid compiler warnings

File:
1 edited

Legend:

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

    r3759 r3786  
    2626! -----------------
    2727! $Id$
     28! unused variables removed
     29!
     30! 3759 2019-02-21 15:53:45Z suehring
    2831! - Calculation of total building volume
    2932! - Several bugfixes
     
    161164
    162165    INTEGER(iwp) ::  num_build   !< total number of buildings in domain
    163 
    164     REAL(wp) ::  volume_fraction
    165 
    166     REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in     !< dummy array for indoor temperature for the
    167                                                      !< total building volume at each discrete height level
    168     REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in_l   !< dummy array for indoor temperature for the
    169                                                      !< local building volume fraction at each discrete height level
    170166
    171167!
     
    205201    REAL(wp) ::  phi_sol                     !< [W] solar loads
    206202    REAL(wp) ::  phi_st                      !<! [W] mass specific thermal load implied non thermal mass
    207     REAL(wp) ::  q_emission                  !< emissions, in first version = 0, option for second part of the project
     203!    REAL(wp) ::  q_emission                  !< emissions, in first version = 0, option for second part of the project
    208204    REAL(wp) ::  q_wall_win                  !< heat flux from indoor into wall/window
    209205    REAL(wp) ::  q_waste_heat                !< waste heat, sum of waste heat over the roof to Palm
    210     REAL(wp) ::  q_waste_heat_bldg           !< [W/building] waste heat of the complete building, in Palm sum of all indoor_model-calculations
     206!    REAL(wp) ::  q_waste_heat_bldg           !< [W/building] waste heat of the complete building, in Palm sum of all indoor_model-calculations
    211207    REAL(wp) ::  schedule_d                  !< activation for internal loads (low or high + low)
    212208    REAL(wp) ::  skip_time_do_indoor = 0.0_wp  !< [s] Indoor model is not called before this time
     
    222218    REAL(wp) ::  theta_s                     !<! [degree_C] surface temperature of the RC-node
    223219    REAL(wp) ::  time_indoor = 0.0_wp        !< [s] time since last call of indoor model
    224     REAL(wp) ::  time_utc_hour               !< Time in hours per day (UTC)
    225     REAL(wp) ::  ventilation_int_loads       !< Zuteilung der GebÀude fÃŒr Verlauf/AktivitÀt der LÃŒftung und internen Lasten
     220!    REAL(wp) ::  time_utc_hour               !< Time in hours per day (UTC)
    226221   
    227222    REAL(wp) ::  f_sr                        !< [-] factor surface reduction
     
    405400
    406401    INTEGER(iwp) ::  bt   !< local building type
    407     INTEGER(iwp) ::  fa   !< running index for facade elements of each building
    408402    INTEGER(iwp) ::  i    !< running index along x-direction
    409403    INTEGER(iwp) ::  j    !< running index along y-direction
     
    434428    INTEGER(iwp), DIMENSION(0:numprocs-1) ::  num_buildings_l       !< number of buildings with different ID on local subdomain
    435429   
    436     REAL(wp), DIMENSION(:), ALLOCATABLE ::  local_weight   !< dummy representing fraction of local on total building volume,
    437                                                            !< height dependent
    438430    REAL(wp), DIMENSION(:), ALLOCATABLE ::  volume         !< total building volume at each discrete height level
    439431    REAL(wp), DIMENSION(:), ALLOCATABLE ::  volume_l       !< total building volume at each discrete height level,
     
    984976    USE arrays_3d,                                                             &
    985977        ONLY:  ddzw, dzw
    986 
    987     USE basic_constants_and_equations_mod,                                     &
    988         ONLY:  c_p
    989 
    990     USE control_parameters,                                                    &
    991         ONLY:  rho_surface
    992978
    993979    USE date_and_time_mod,                                                     &
Note: See TracChangeset for help on using the changeset viewer.