Ignore:
Timestamp:
Sep 21, 2020 7:40:16 PM (4 years ago)
Author:
maronga
Message:

bugfix in indoor model, code layout change in urban surface model, indoor model integrated in spinup mechanism

File:
1 edited

Legend:

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

    r4681 r4687  
    2525! -----------------
    2626! $Id$
     27! Bugfix: values of theta_m_t_prev were not stored for individual surfaces and thus re-used by all
     28! surfaces and buildings, which led to excessive indoor temperatures
     29!
     30! 4681 2020-09-16 10:23:06Z pavelkrc
    2731! Bugfix for implementation of downward surfaces
    2832!
     
    126130! @author Matthias Suehring
    127131! @author Sascha Rißmann
     132! @author Björn Maronga
    128133!
    129134!
     
    144149!> @note How to write indoor temperature output to pt array?
    145150!>
    146 !> @bug  <Enter known bugs here>
     151!> @bug  Calculation of iwghf_eb and iwghf_eb_window is faulty
    147152!--------------------------------------------------------------------------------------------------!
    148153 MODULE indoor_model_mod
     
    234239       REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in       !< mean building indoor temperature, height dependent
    235240       REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in_l     !< mean building indoor temperature on local subdomain, height dependent
     241       REAL(wp), DIMENSION(:), ALLOCATABLE ::  theta_m_t_prev_h !< [degree_C] value of theta_m_t from previous time step (horizontal)
     242       REAL(wp), DIMENSION(:), ALLOCATABLE ::  theta_m_t_prev_v !< [degree_C] value of theta_m_t from previous time step (vertical)
    236243       REAL(wp), DIMENSION(:), ALLOCATABLE ::  volume     !< total building volume, height dependent
    237244       REAL(wp), DIMENSION(:), ALLOCATABLE ::  vol_frac   !< fraction of local on total building volume, height dependent
     
    319326    REAL(wp) ::  theta_air_set                       !< [degree_C] Setpoint_temperature for the room
    320327    REAL(wp) ::  theta_m                             !< [degree_C} inner temperature of the RC-node
    321     REAL(wp) ::  theta_m_t                           !< [degree_C] (Fictive) component temperature timestep
    322     REAL(wp) ::  theta_m_t_prev                      !< [degree_C] (Fictive) component temperature previous timestep (do not change)
     328    REAL(wp) ::  theta_m_t                           !< [degree_C] (Fictive) component temperature during timestep
    323329    REAL(wp) ::  theta_op                            !< [degree_C] operative temperature
    324330    REAL(wp) ::  theta_s                             !< [degree_C] surface temperature of the RC-node
     
    449455!--------------------------------------------------------------------------------------------------!
    450456 SUBROUTINE im_calc_temperatures ( i, j, k, indoor_wall_window_temperature,                        &
    451                                    near_facade_temperature, phi_hc_nd_dummy )
     457                                   near_facade_temperature, phi_hc_nd_dummy, theta_m_t_prev )
    452458
    453459    INTEGER(iwp) ::  i
     
    458464    REAL(wp) ::  near_facade_temperature
    459465    REAL(wp) ::  phi_hc_nd_dummy
     466    REAL(wp), INTENT(IN) :: theta_m_t_prev
    460467!
    461468!-- Calculation of total mass specific thermal load (internal and external)
     
    468475               )                                                                !< [degree_C] Eq. (C.5)
    469476!
    470 !-- Calculation of component temperature at factual timestep
     477!-- Calculation of component temperature at current timestep
    471478    theta_m_t = ( ( theta_m_t_prev                                                                 &
    472479                    * ( ( c_m / 3600.0_wp ) - 0.5_wp * ( h_t_3 + h_t_wm ) )                        &
     
    476483                )                                                               !< [degree_C] Eq. (C.4)
    477484!
    478 !-- Calculation of mean inner temperature for the RC-node in actual timestep
     485!-- Calculation of mean inner temperature for the RC-node in current timestep
    479486    theta_m = ( theta_m_t + theta_m_t_prev ) * 0.5_wp                           !< [degree_C] Eq. (C.9)
    480487
    481488!
    482 !-- Calculation of mean surface temperature of the RC-node in actual timestep
     489!-- Calculation of mean surface temperature of the RC-node in current timestep
    483490    theta_s = ( (   h_t_ms * theta_m + phi_st + h_t_es * pt(k,j,i)                                 &
    484491                  + h_t_1  * ( near_facade_temperature                                             &
     
    490497!
    491498!-- Calculation of the air temperature of the RC-node
     499
     500
    492501    theta_air = ( h_t_is * theta_s + h_v * near_facade_temperature + phi_ia + phi_hc_nd_dummy ) /  &
    493502                ( h_t_is + h_v )                                                !< [degree_C] Eq. (C.11)
     503
    494504
    495505 END SUBROUTINE im_calc_temperatures
     
    925935          ALLOCATE( buildings(nb)%l_v(1:buildings(nb)%num_facades_per_building_v_l) )
    926936          ALLOCATE( buildings(nb)%m_v(1:buildings(nb)%num_facades_per_building_v_l) )
     937
     938          ALLOCATE( buildings(nb)%theta_m_t_prev_h(1:buildings(nb)%num_facades_per_building_h_l) )
     939          ALLOCATE( buildings(nb)%theta_m_t_prev_v(1:buildings(nb)%num_facades_per_building_v_l) )
    927940       ENDIF
    928941
     
    11251138    ENDDO
    11261139!
    1127 !-- Initial room temperature [K]
    1128 !-- (after first loop, use theta_m_t as theta_m_t_prev)
    1129     theta_m_t_prev = initial_indoor_temperature
    1130 !
    11311140!-- Initialize indoor temperature. Actually only for output at initial state.
    11321141    DO  nb = 1, num_build
    1133        IF ( buildings(nb)%on_pe )  buildings(nb)%t_in(:) = initial_indoor_temperature
     1142       IF ( buildings(nb)%on_pe )  THEN
     1143          buildings(nb)%t_in(:) = initial_indoor_temperature
     1144
     1145!
     1146!--       (after first loop, use theta_m_t as theta_m_t_prev)
     1147          buildings(nb)%theta_m_t_prev_h(:) = initial_indoor_temperature
     1148          buildings(nb)%theta_m_t_prev_v(:) = initial_indoor_temperature
     1149
     1150       ENDIF
    11341151    ENDDO
    11351152
     
    13371354
    13381355             CALL  im_calc_temperatures ( i, j, k, indoor_wall_window_temperature,                 &
    1339                                           near_facade_temperature, phi_hc_nd )
     1356                                          near_facade_temperature, phi_hc_nd, buildings(nb)%theta_m_t_prev_h(fa) )
    13401357!
    13411358!--          If air temperature between border temperatures of heating and cooling, assign output
     
    13661383
    13671384                CALL  im_calc_temperatures ( i, j, k, indoor_wall_window_temperature,              &
    1368                                              near_facade_temperature, phi_hc_nd )
     1385                                             near_facade_temperature, phi_hc_nd, buildings(nb)%theta_m_t_prev_h(fa) )
    13691386                theta_air_10 = theta_air                                                !< temperature with 10 W/m2 of heating
    13701387                phi_hc_nd_un = phi_hc_nd_10 * (theta_air_set - theta_air_0)                        &
     
    13951412!--             Calculate the temperature with phi_hc_nd_ac (new)
    13961413                CALL  im_calc_temperatures ( i, j, k, indoor_wall_window_temperature,              &
    1397                                              near_facade_temperature, phi_hc_nd )
     1414                                             near_facade_temperature, phi_hc_nd, buildings(nb)%theta_m_t_prev_h(fa) )
    13981415                theta_air_ac = theta_air
    13991416             ENDIF
    14001417!
    14011418!--          Update theta_m_t_prev
    1402              theta_m_t_prev = theta_m_t
     1419             buildings(nb)%theta_m_t_prev_h(fa) = theta_m_t
     1420
    14031421
    14041422             q_vent = h_v * ( theta_air - near_facade_temperature )
     
    14081426!--          Will be used for thermal comfort calculations.
    14091427             theta_op     = 0.3_wp * theta_air_ac + 0.7_wp * theta_s          !< [degree_C] operative Temperature Eq. (C.12)
     1428
    14101429!              surf_usm_h(l)%t_indoor(m) = theta_op                               !< not integrated now
    14111430!
     
    14401459                            ) / facade_element_area                                             !< [W/m2] , observe the directional
    14411460                                                                                                !< convention in PALM!
    1442              surf_usm_h(l)%waste_heat(m) = q_waste_heat
     1461             surf_usm_h(l)%waste_heat(m) = 0.0_wp !q_waste_heat
    14431462          ENDDO !< Horizontal surfaces loop
    14441463!
     
    15241543             k = surf_usm_v(l)%k(m)
    15251544             near_facade_temperature = surf_usm_v(l)%pt_10cm(m)
    1526              indoor_wall_window_temperature =                                                      &
    1527                                     surf_usm_v(l)%frac(m,ind_veg_wall) * t_wall_v(l)%val(nzt_wall,m) &
     1545             indoor_wall_window_temperature =                                                          &
     1546                                    surf_usm_v(l)%frac(m,ind_veg_wall) * t_wall_v(l)%val(nzt_wall,m)   &
    15281547                                  + surf_usm_v(l)%frac(m,ind_wat_win)  * t_window_v(l)%val(nzt_wall,m)
     1548
    15291549!
    15301550!--          Solar thermal gains. If net_sw_in larger than sun-protection
     
    15631583             phi_hc_nd = 0.0_wp
    15641584             CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature,                  &
    1565                                          near_facade_temperature, phi_hc_nd )
     1585                                         near_facade_temperature, phi_hc_nd, buildings(nb)%theta_m_t_prev_v(fa) )
    15661586!
    15671587!--          If air temperature between border temperatures of heating and cooling, assign output
     
    15921612
    15931613                CALL  im_calc_temperatures ( i, j, k, indoor_wall_window_temperature,              &
    1594                                              near_facade_temperature, phi_hc_nd )
     1614                                             near_facade_temperature, phi_hc_nd, buildings(nb)%theta_m_t_prev_v(fa) )
    15951615
    15961616                theta_air_10 = theta_air !< Note the temperature with 10 W/m2 of heating
     
    16231643!--             Calculate the temperature with phi_hc_nd_ac (new)
    16241644                CALL  im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
    1625                                              near_facade_temperature, phi_hc_nd )
     1645                                             near_facade_temperature, phi_hc_nd, buildings(nb)%theta_m_t_prev_v(fa) )
    16261646                theta_air_ac = theta_air
    16271647             ENDIF
    16281648!
    16291649!--          Update theta_m_t_prev
    1630              theta_m_t_prev = theta_m_t
     1650             buildings(nb)%theta_m_t_prev_v(fa) = theta_m_t
     1651
    16311652
    16321653             q_vent = h_v * ( theta_air - near_facade_temperature )
     
    16351656!--          Will be used for thermal comfort calculations.
    16361657             theta_op     = 0.3_wp * theta_air_ac + 0.7_wp * theta_s
     1658
    16371659!              surf_usm_v(l)%t_indoor(m) = theta_op                  !< not integrated yet
    16381660!
     
    16651687                                                    ) / facade_element_area  !< [W/m2] , observe the directional convention in
    16661688                                                                             !< PALM!
    1667              surf_usm_v(l)%waste_heat(m) = q_waste_heat
     1689             surf_usm_v(l)%waste_heat(m) = 0.0_wp !q_waste_heat
    16681690          ENDDO !< Vertical surfaces loop
    16691691       ENDIF !< buildings(nb)%on_pe
Note: See TracChangeset for help on using the changeset viewer.