Changeset 4267 for palm


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

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

Location:
palm/trunk/SOURCE
Files:
3 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
  • palm/trunk/SOURCE/palm_date_time_mod.f90

    r4227 r4267  
    2525! -----------------
    2626! $Id$
     27! Add days of northward- and southward equinox
     28!
     29! 4227 2019-09-10 18:04:34Z gronemeier
    2730! Complete rework of module date_and_time_mod:
    2831!  - renamed module to prevent confusion with
     
    6467    INTEGER(iwp), PARAMETER ::  minutes_per_hour   = 60_iwp                                 !< minutes in an hour
    6568    INTEGER(iwp), PARAMETER ::  months_per_year    = 12_iwp                                 !< months in a year
     69!
     70!-- Definition of mean northward and southward equinox (summer and winter half year)
     71!-- in days of year. For simplicity, March 21 and September 21 is assumed.
     72    INTEGER(iwp), PARAMETER ::  northward_equinox  = 80_iwp
     73    INTEGER(iwp), PARAMETER ::  southward_equinox  = 264_iwp
    6674
    6775    REAL(wp),     PARAMETER ::  seconds_per_minute = 60.0_wp                                !< seconds in a minute
     
    146154       minutes_per_hour,   &
    147155       months_per_year,    &
     156       northward_equinox,  &
    148157       seconds_per_minute, &
    149158       seconds_per_hour,   &
    150159       seconds_per_day,    &
     160       southward_equinox,  &
    151161       weekdays
    152162
  • palm/trunk/SOURCE/urban_surface_mod.f90

    r4259 r4267  
    2828! -----------------
    2929! $Id$
     30! Revision of some indoor-model parameters
     31!
     32! 4259 2019-10-09 10:05:22Z suehring
    3033! Instead of terminate the job in case the relative wall fractions do not
    3134! sum-up to one, give only an informative message and normalize the fractions.
     
    91769179           0.76_wp,        &  !< parameter 120 - g-value windows
    91779180           5.0_wp,         &  !< parameter 121 - u-value windows
    9178            0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
    9179            0.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
     9181           0.5_wp,         &  !< parameter 122 - basical airflow without occupancy of the room for - summer 0.5_wp, winter 0.1
     9182           2.0_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room for - summer 2.0_wp, winter 0.5
    91809183           0.0_wp,         &  !< parameter 124 - heat recovery efficiency
    91819184           3.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
    91829185           370000.0_wp,    &  !< parameter 126 - dynamic parameter innner heatstorage
    91839186           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
    9184            100000.0_wp,    &  !< parameter 128 - maximal heating capacity
     9187           100.0_wp,       &  !< parameter 128 - maximal heating capacity
    91859188           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
    9186            3.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
    9187            10.0_wp,        &  !< parameter 131 - basic internal heat gains without occupancy of the room
     9189           2.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
     9190           6.0_wp,         &  !< parameter 131 - basic internal heat gains without occupancy of the room
    91889191           3.0_wp,         &  !< parameter 132 - storey height
    91899192           0.2_wp,         &  !< parameter 133 - ceiling construction height
     
    91929195                            /)
    91939196                           
    9194         building_pars(:,2) = (/   &
     9197     building_pars(:,2) = (/   &
    91959198           0.73_wp,        &  !< parameter 0   - wall fraction above ground floor level
    91969199           0.27_wp,        &  !< parameter 1   - window fraction above ground floor level
     
    93159318           0.6_wp,         &  !< parameter 120 - g-value windows
    93169319           3.0_wp,         &  !< parameter 121 - u-value windows
    9317            0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
    9318            0.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
     9320           0.5_wp,         &  !< parameter 122 - basical airflow without occupancy of the room for - summer 0.5_wp for winter 0.1
     9321           2.0_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room for - summer 2.0_wp for winter 0.5
    93199322           0.0_wp,         &  !< parameter 124 - heat recovery efficiency
    93209323           2.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
    93219324           165000.0_wp,    &  !< parameter 126 - dynamic parameter innner heatstorage
    93229325           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
    9323            100000.0_wp,    &  !< parameter 128 - maximal heating capacity
     9326           100.0_wp,       &  !< parameter 128 - maximal heating capacity
    93249327           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
    9325            4.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
    9326            8.0_wp,         &  !< parameter 131 - basic internal heat gains without occupancy of the room
     9328           2.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
     9329           6.0_wp,         &  !< parameter 131 - basic internal heat gains without occupancy of the room
    93279330           3.0_wp,         &  !< parameter 132 - storey height
    93289331           0.2_wp,         &  !< parameter 133 - ceiling construction height
     
    93309333           1.333_wp        &  !< parameter 135 - anthropogenic heat output for cooling
    93319334                            /)
    9332                            
    9333         building_pars(:,3) = (/   &
     9335
     9336  building_pars(:,3) = (/   &
    93349337           0.7_wp,         &  !< parameter 0   - wall fraction above ground floor level
    93359338           0.3_wp,         &  !< parameter 1   - window fraction above ground floor level
     
    94519454           5.0_wp,         &  !< parameter 117 - green albedo roof
    94529455           0.0_wp,         &  !< parameter 118 - green type roof
    9453            0.8_wp,         &  !< parameter 119 - shading factor
     9456           0.3_wp,         &  !< parameter 119 - shading factor
    94549457           0.5_wp,         &  !< parameter 120 - g-value windows
    9455            2.5_wp,         &  !< parameter 121 - u-value windows
    9456            0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
    9457            0.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
     9458           1.0_wp,         &  !< parameter 121 - u-value windows
     9459           0.8_wp,         &  !< parameter 122 - basical airflow without occupancy of the room for - summer 0.8_wp, winter 0.1
     9460           2.0_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room for - summer 2.0_wp, winter 0.5
    94589461           0.8_wp,         &  !< parameter 124 - heat recovery efficiency
    94599462           2.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
    94609463           80000.0_wp,     &  !< parameter 126 - dynamic parameter innner heatstorage
    94619464           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
    9462            100000.0_wp,    &  !< parameter 128 - maximal heating capacity
     9465           100.0_wp,       &  !< parameter 128 - maximal heating capacity
    94639466           0.0_wp,         &  !< parameter 129 - maximal cooling capacity
    9464            3.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
    9465            8.0_wp,         &  !< parameter 131 - basic internal heat gains without occupancy of the room
     9467           2.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
     9468           6.0_wp,         &  !< parameter 131 - basic internal heat gains without occupancy of the room
    94669469           3.0_wp,         &  !< parameter 132 - storey height
    94679470           0.2_wp,         &  !< parameter 133 - ceiling construction height
    94689471           -2.0_wp,        &  !< parameter 134 - anthropogenic heat output for heating
    94699472           1.25_wp         &  !< parameter 135 - anthropogenic heat output for cooling
    9470                             /)
     9473                            /)    
    94719474                           
    94729475        building_pars(:,4) = (/   &
     
    95909593           5.0_wp,         &  !< parameter 117 - green albedo roof
    95919594           0.0_wp,         &  !< parameter 118 - green type roof
    9592            0.8_wp,         &  !< parameter 119 - shading factor
     9595           0.25_wp,        &  !< parameter 119 - shading factor
    95939596           0.76_wp,        &  !< parameter 120 - g-value windows
    95949597           5.0_wp,         &  !< parameter 121 - u-value windows
    9595            0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
    9596            1.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
     9598           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room for - summer 0.1_wp, winter 0.1
     9599           1.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room for - summer 1.5_wp, winter 1.5
    95979600           0.0_wp,         &  !< parameter 124 - heat recovery efficiency
    95989601           3.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
    95999602           370000.0_wp,    &  !< parameter 126 - dynamic parameter innner heatstorage
    96009603           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
    9601            100000.0_wp,    &  !< parameter 128 - maximal heating capacity
    9602            0.0_wp,         &  !< parameter 129 - maximal cooling capacity
     9604           100.0_wp,       &  !< parameter 128 - maximal heating capacity
     9605           -200.0_wp,      &  !< parameter 129 - maximal cooling capacity
    96039606           3.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
    96049607           10.0_wp,        &  !< parameter 131 - basic internal heat gains without occupancy of the room
     
    97299732           5.0_wp,         &  !< parameter 117 - green albedo roof
    97309733           0.0_wp,         &  !< parameter 118 - green type roof
    9731            0.8_wp,         &  !< parameter 119 - shading factor
     9734           0.25_wp,        &  !< parameter 119 - shading factor
    97329735           0.6_wp,         &  !< parameter 120 - g-value windows
    97339736           3.0_wp,         &  !< parameter 121 - u-value windows
    9734            0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
    9735            1.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
     9737           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room for - summer 0.1_wp, winter 0.1
     9738           1.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room for - summer 1.5_wp, winter 1.5
    97369739           0.65_wp,        &  !< parameter 124 - heat recovery efficiency
    97379740           2.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
    97389741           165000.0_wp,    &  !< parameter 126 - dynamic parameter innner heatstorage
    97399742           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
    9740            100000.0_wp,    &  !< parameter 128 - maximal heating capacity
    9741            0.0_wp,         &  !< parameter 129 - maximal cooling capacity
     9743           100.0_wp,       &  !< parameter 128 - maximal heating capacity
     9744           -200.0_wp,      &  !< parameter 129 - maximal cooling capacity
    97429745           7.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
    97439746           20.0_wp,        &  !< parameter 131 - basic internal heat gains without occupancy of the room
     
    98689871           5.0_wp,         &  !< parameter 117 - green albedo roof
    98699872           0.0_wp,         &  !< parameter 118 - green type roof
    9870            0.8_wp,         &  !< parameter 119 - shading factor
     9873           0.25_wp,        &  !< parameter 119 - shading factor
    98719874           0.5_wp,         &  !< parameter 120 - g-value windows
    98729875           2.5_wp,         &  !< parameter 121 - u-value windows
    9873            0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room
    9874            1.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room
     9876           0.1_wp,         &  !< parameter 122 - basical airflow without occupancy of the room for - summer 0.1_wp, winter 0.1
     9877           1.5_wp,         &  !< parameter 123 - additional airflow depend of occupancy of the room for - summer 1.5_wp, winter 1.5
    98759878           0.9_wp,         &  !< parameter 124 - heat recovery efficiency
    98769879           2.5_wp,         &  !< parameter 125 - dynamic parameter specific effective surface
    98779880           80000.0_wp,     &  !< parameter 126 - dynamic parameter innner heatstorage
    98789881           4.5_wp,         &  !< parameter 127 - ratio internal surface/floor area
    9879            100000.0_wp,    &  !< parameter 128 - maximal heating capacity
    9880            0.0_wp,         &  !< parameter 129 - maximal cooling capacity
     9882           100.0_wp,       &  !< parameter 128 - maximal heating capacity
     9883           -80.0_wp,       &  !< parameter 129 - maximal cooling capacity
    98819884           5.0_wp,         &  !< parameter 130 - additional internal heat gains dependent on occupancy of the room
    98829885           15.0_wp,        &  !< parameter 131 - basic internal heat gains without occupancy of the room
Note: See TracChangeset for help on using the changeset viewer.