Ignore:
Timestamp:
Oct 16, 2019 6:58:49 PM (5 years ago)
Author:
suehring
Message:

Indoor model: revision of some parameters and implementation of seasonal-dependent parameters

File:
1 edited

Legend:

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

    r4246 r4267  
    2626! -----------------
    2727! $Id$
     28! Bugfix in initialization, some indices to access building_pars where wrong.
     29! Introduction of seasonal parameters.
     30!
     31! 4246 2019-09-30 09:27:52Z pavelkrc
    2832!
    2933!
     
    121125    USE netcdf_data_input_mod,                                                 &
    122126        ONLY:  building_id_f, building_type_f
     127
     128    USE palm_date_time_mod,                                                    &
     129        ONLY:  get_date_time, northward_equinox, seconds_per_hour,             &
     130               southward_equinox
    123131
    124132    USE surface_mod,                                                           &
     
    273281    REAL(wp), PARAMETER ::  params_solar_protection  = 300.0_wp    !< [W/m2] chap. G.5.3.1 sun protection closed, if the radiation
    274282                                                                   !< on facade exceeds this value
    275 
    276    
     283!
     284!-- Definition of seasonal parameters, summer and winter, for different building types
     285    REAL(wp), DIMENSION(0:1,1:7) ::  summer_pars = RESHAPE( (/               & ! building_type 1
     286                                          0.5_wp,                              & ! basical airflow without occupancy of the room
     287                                          2.0_wp,                              & ! additional airflow depend of occupancy of the room
     288                                          0.5_wp,                              & ! building_type 2: basical airflow without occupancy of the room
     289                                          2.0_wp,                              & ! additional airflow depend of occupancy of the room
     290                                          0.8_wp,                              & ! building_type 3: basical airflow without occupancy of the room
     291                                          2.0_wp,                              & ! additional airflow depend of occupancy of the room
     292                                          0.1_wp,                              & ! building_type 4: basical airflow without occupancy of the room
     293                                          1.5_wp,                              & ! additional airflow depend of occupancy of the room
     294                                          0.1_wp,                              & ! building_type 5: basical airflow without occupancy of the room
     295                                          1.5_wp,                              & ! additional airflow depend of occupancy of the room
     296                                          0.1_wp,                              & ! building_type 6: basical airflow without occupancy of the room
     297                                          1.5_wp,                              & ! additional airflow depend of occupancy of the room
     298                                          0.1_wp,                              & ! building_type 7: basical airflow without occupancy of the room
     299                                          1.5_wp                               & ! additional airflow depend of occupancy of the room
     300                                                           /), (/ 2, 7 /) )
     301
     302    REAL(wp), DIMENSION(0:1,1:7) ::  winter_pars = RESHAPE( (/               & ! building_type 1
     303                                          0.1_wp,                              & ! basical airflow without occupancy of the room
     304                                          0.5_wp,                              & ! additional airflow depend of occupancy of the room
     305                                          0.1_wp,                              & ! building_type 2: basical airflow without occupancy of the room
     306                                          0.5_wp,                              & ! additional airflow depend of occupancy of the room
     307                                          0.1_wp,                              & ! building_type 3: basical airflow without occupancy of the room
     308                                          0.5_wp,                              & ! additional airflow depend of occupancy of the room
     309                                          0.1_wp,                              & ! building_type 4: basical airflow without occupancy of the room
     310                                          1.5_wp,                              & ! additional airflow depend of occupancy of the room
     311                                          0.1_wp,                              & ! building_type 5: basical airflow without occupancy of the room
     312                                          1.5_wp,                              & ! additional airflow depend of occupancy of the room
     313                                          0.1_wp,                              & ! building_type 6: basical airflow without occupancy of the room
     314                                          1.5_wp,                              & ! additional airflow depend of occupancy of the room
     315                                          0.1_wp,                              & ! building_type 7: basical airflow without occupancy of the room
     316                                          1.5_wp                               & ! additional airflow depend of occupancy of the room
     317                                                           /), (/ 2, 7 /) )
     318
    277319    SAVE
    278320
     
    424466
    425467    USE control_parameters,                                                    &
    426         ONLY:  message_string
     468        ONLY:  message_string, time_since_reference_point
    427469
    428470    USE indices,                                                               &
     
    442484    IMPLICIT NONE
    443485
    444     INTEGER(iwp) ::  bt   !< local building type
    445     INTEGER(iwp) ::  i    !< running index along x-direction
    446     INTEGER(iwp) ::  j    !< running index along y-direction
    447     INTEGER(iwp) ::  k    !< running index along z-direction
    448     INTEGER(iwp) ::  l    !< running index for surface-element orientation
    449     INTEGER(iwp) ::  m    !< running index surface elements
    450     INTEGER(iwp) ::  n    !< building index
    451     INTEGER(iwp) ::  nb   !< building index
     486    INTEGER(iwp) ::  bt          !< local building type
     487    INTEGER(iwp) ::  day_of_year !< day of the year
     488    INTEGER(iwp) ::  i           !< running index along x-direction
     489    INTEGER(iwp) ::  j           !< running index along y-direction
     490    INTEGER(iwp) ::  k           !< running index along z-direction
     491    INTEGER(iwp) ::  l           !< running index for surface-element orientation
     492    INTEGER(iwp) ::  m           !< running index surface elements
     493    INTEGER(iwp) ::  n           !< building index
     494    INTEGER(iwp) ::  nb          !< building index
    452495
    453496    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids           !< building IDs on entire model domain
     
    927970!-- In a second step initialize with building tpyes from static input file,
    928971!-- where building types can be individual for each building.
    929     buildings(:)%lambda_layer3       = building_pars(63,building_type)
    930     buildings(:)%s_layer3            = building_pars(57,building_type)
     972    buildings(:)%lambda_layer3       = building_pars(31,building_type)
     973    buildings(:)%s_layer3            = building_pars(44,building_type)
    931974    buildings(:)%f_c_win             = building_pars(119,building_type)
    932975    buildings(:)%g_value_win         = building_pars(120,building_type)   
    933     buildings(:)%u_value_win         = building_pars(121,building_type)   
    934     buildings(:)%air_change_low      = building_pars(122,building_type)   
    935     buildings(:)%air_change_high     = building_pars(123,building_type)   
     976    buildings(:)%u_value_win         = building_pars(121,building_type)       
    936977    buildings(:)%eta_ve              = building_pars(124,building_type)   
    937978    buildings(:)%factor_a            = building_pars(125,building_type)   
    938979    buildings(:)%factor_c            = building_pars(126,building_type)
    939980    buildings(:)%lambda_at           = building_pars(127,building_type)   
    940     buildings(:)%theta_int_h_set     = building_pars(118,building_type)   
    941     buildings(:)%theta_int_c_set     = building_pars(117,building_type)
     981    buildings(:)%theta_int_h_set     = building_pars(13,building_type)   
     982    buildings(:)%theta_int_c_set     = building_pars(12,building_type)
    942983    buildings(:)%q_h_max             = building_pars(128,building_type)   
    943984    buildings(:)%q_c_max             = building_pars(129,building_type)         
     
    948989    buildings(:)%params_waste_heat_h = building_pars(134,building_type)
    949990    buildings(:)%params_waste_heat_c = building_pars(135,building_type)
     991!
     992!-- Initialize seasonal dependent parameters, depending on day of the year.
     993!-- First, calculated day of the year.
     994    CALL get_date_time( time_since_reference_point, day_of_year = day_of_year )
     995!
     996!-- Summer is defined in between northward- and southward equinox.
     997    IF ( day_of_year >= northward_equinox  .AND.                               &
     998         day_of_year <= southward_equinox )  THEN
     999       buildings(:)%air_change_low      = summer_pars(0,building_type)   
     1000       buildings(:)%air_change_high     = summer_pars(1,building_type)
     1001    ELSE
     1002       buildings(:)%air_change_low      = winter_pars(0,building_type)   
     1003       buildings(:)%air_change_high     = winter_pars(1,building_type)
     1004    ENDIF
    9501005!
    9511006!-- Initialize ventilaation load. Please note, building types > 7 are actually
     
    9791034                 bt = building_type_f%var(j,i)
    9801035                 
    981                  buildings(nb)%lambda_layer3       = building_pars(63,bt)
    982                  buildings(nb)%s_layer3            = building_pars(57,bt)
     1036                 buildings(nb)%lambda_layer3       = building_pars(31,bt)
     1037                 buildings(nb)%s_layer3            = building_pars(44,bt)
    9831038                 buildings(nb)%f_c_win             = building_pars(119,bt)
    9841039                 buildings(nb)%g_value_win         = building_pars(120,bt)   
    9851040                 buildings(nb)%u_value_win         = building_pars(121,bt)   
    986                  buildings(nb)%air_change_low      = building_pars(122,bt)   
    987                  buildings(nb)%air_change_high     = building_pars(123,bt)   
    9881041                 buildings(nb)%eta_ve              = building_pars(124,bt)   
    9891042                 buildings(nb)%factor_a            = building_pars(125,bt)   
    9901043                 buildings(nb)%factor_c            = building_pars(126,bt)
    9911044                 buildings(nb)%lambda_at           = building_pars(127,bt)   
    992                  buildings(nb)%theta_int_h_set     = building_pars(118,bt)   
    993                  buildings(nb)%theta_int_c_set     = building_pars(117,bt)
     1045                 buildings(nb)%theta_int_h_set     = building_pars(13,bt)   
     1046                 buildings(nb)%theta_int_c_set     = building_pars(12,bt)
    9941047                 buildings(nb)%q_h_max             = building_pars(128,bt)   
    9951048                 buildings(nb)%q_c_max             = building_pars(129,bt)         
     
    10001053                 buildings(nb)%params_waste_heat_h = building_pars(134,bt)
    10011054                 buildings(nb)%params_waste_heat_c = building_pars(135,bt)
     1055
     1056              IF ( day_of_year >= northward_equinox  .AND.                     &
     1057                   day_of_year <= southward_equinox )  THEN
     1058                 buildings(nb)%air_change_low      = summer_pars(0,bt)   
     1059                 buildings(nb)%air_change_high     = summer_pars(1,bt)
     1060              ELSE
     1061                 buildings(nb)%air_change_low      = winter_pars(0,bt)   
     1062                 buildings(nb)%air_change_high     = winter_pars(1,bt)
     1063              ENDIF
     1064
    10021065!
    10031066!--              Initialize ventilaation load. Please note, building types > 7
     
    10391102          du_tmp = 1.0_wp / u_tmp
    10401103         
    1041           buildings(nb)%h_es = ( du_tmp / ( du_tmp - ( 1.0_wp / h_is ) ) ) *   &
    1042                                  u_tmp   
     1104          buildings(nb)%h_es = 1.0_wp / ( du_tmp - ( 1.0_wp / h_is ) )
     1105
    10431106       ENDIF
    10441107    ENDDO
     
    10781141    USE grid_variables,                                                        &
    10791142        ONLY:  dx, dy
    1080 
    1081     USE palm_date_time_mod,                                                    &
    1082         ONLY:  get_date_time, seconds_per_hour
    10831143
    10841144    USE pegrid
     
    11241184!--       Residental Building, panel WBS 70   
    11251185          IF ( buildings(nb)%ventilation_int_loads == 1 )  THEN
    1126              IF ( time_utc_hour >= 6.0_wp  .AND.  time_utc_hour <= 8.0_wp )  THEN
     1186             IF ( time_utc_hour >= 8.0_wp  .AND.  time_utc_hour <= 18.0_wp )  THEN
     1187                schedule_d = 0
     1188             ELSE
    11271189                schedule_d = 1
    1128              ELSEIF ( time_utc_hour >= 18.0_wp  .AND.  time_utc_hour <= 23.0_wp )  THEN
    1129                 schedule_d = 1
    1130              ELSE
    1131                 schedule_d = 0
    11321190             ENDIF
    11331191          ENDIF
Note: See TracChangeset for help on using the changeset viewer.