Ignore:
Timestamp:
Jan 21, 2021 5:59:25 PM (3 years ago)
Author:
suehring
Message:

Bugfix in indoor model: consider previous indoor temperature during restarts; Further bugfix in mpi-io restart mechanism for the waste-heat flux from buildings

File:
1 edited

Legend:

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

    r4843 r4850  
    2525! -----------------
    2626! $Id$
     27! Enable restart mechanism for previous indoor temperature
     28!
     29! 4843 2021-01-15 15:22:11Z raasch
    2730! local namelist parameter added to switch off the module although the respective module namelist
    2831! appears in the namelist file
     
    590593    INTEGER(iwp) ::  bt          !< local building type
    591594    INTEGER(iwp) ::  day_of_year !< day of the year
     595    INTEGER(iwp) ::  fa          !< running index for facade elements of each building
    592596    INTEGER(iwp) ::  i           !< running index along x-direction
    593597    INTEGER(iwp) ::  j           !< running index along y-direction
     
    11851189!
    11861190!-- Initialize indoor temperature. Actually only for output at initial state.
    1187     DO  nb = 1, num_build
    1188        IF ( buildings(nb)%on_pe )  THEN
    1189           buildings(nb)%t_in(:) = initial_indoor_temperature
    1190 
    1191 !
    1192 !--       (after first loop, use theta_m_t as theta_m_t_prev)
    1193           buildings(nb)%theta_m_t_prev_h(:) = initial_indoor_temperature
    1194           buildings(nb)%theta_m_t_prev_v(:) = initial_indoor_temperature
    1195 
    1196        ENDIF
    1197     ENDDO
     1191    IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
     1192       DO  nb = 1, num_build
     1193          IF ( buildings(nb)%on_pe )  THEN
     1194             buildings(nb)%t_in(:) = initial_indoor_temperature
     1195
     1196!
     1197!--          (after first loop, use theta_m_t as theta_m_t_prev)
     1198             buildings(nb)%theta_m_t_prev_h(:) = initial_indoor_temperature
     1199             buildings(nb)%theta_m_t_prev_v(:) = initial_indoor_temperature
     1200
     1201          ENDIF
     1202       ENDDO
     1203!
     1204!-- Initialize indoor temperature at previous timestep.
     1205    ELSE
     1206       DO  nb = 1, num_build
     1207          IF ( buildings(nb)%on_pe )  THEN
     1208!
     1209!--          Mean indoor temperature can be initialized with initial value. This is just
     1210!--          used for output.
     1211             buildings(nb)%t_in(:) = initial_indoor_temperature
     1212!
     1213!--          Initialize theta_m_t_prev arrays. The respective data during the restart mechanism
     1214!--          is stored on the surface-data array.
     1215             DO  fa = 1, buildings(nb)%num_facades_per_building_h_l
     1216!
     1217!--             Determine indices where corresponding surface-type information is stored.
     1218                l = buildings(nb)%l_h(fa)
     1219                m = buildings(nb)%m_h(fa)
     1220                buildings(nb)%theta_m_t_prev_h(fa) = surf_usm_h(l)%t_prev(m)
     1221             ENDDO
     1222             DO  fa = 1, buildings(nb)%num_facades_per_building_v_l
     1223!
     1224!--             Determine indices where corresponding surface-type information is stored.
     1225                l = buildings(nb)%l_v(fa)
     1226                m = buildings(nb)%m_v(fa)
     1227                buildings(nb)%theta_m_t_prev_v(fa) = surf_usm_v(l)%t_prev(m)
     1228             ENDDO
     1229          ENDIF
     1230       ENDDO
     1231    ENDIF
    11981232
    11991233    CALL location_message( 'initializing indoor model', 'finished' )
     
    13031337          ENDIF
    13041338!
    1305 !--       Initialize/reset indoor temperature
     1339!--       Initialize/reset indoor temperature - note, this is only for output
    13061340          buildings(nb)%t_in_l = 0.0_wp
    13071341!
     
    15481582                              buildings(nb)%params_waste_heat_h * heating_on +                     &
    15491583                              buildings(nb)%params_waste_heat_c * cooling_on )                     &
    1550                             ) / facade_element_area                                             !< [W/m2] , observe the directional
    1551                                                                                                 !< convention in PALM!
     1584                            ) / facade_element_area  !< [W/m2] , observe the directional convention in PALM!
     1585!
     1586!--          Store waste heat and previous previous indoor temperature on surface-data type.
     1587!--          These will be used in the urban-surface model.
     1588             surf_usm_h(l)%t_prev(m) = buildings(nb)%theta_m_t_prev_h(fa)
    15521589             surf_usm_h(l)%waste_heat(m) = q_waste_heat
    15531590          ENDDO !< Horizontal surfaces loop
     
    15591596             l = buildings(nb)%l_v(fa)
    15601597             m = buildings(nb)%m_v(fa)
     1598
    15611599!
    15621600!--          During spinup set window fraction to zero and add these to wall fraction.
     
    18051843             q_waste_heat = ( phi_hc_nd * ( buildings(nb)%params_waste_heat_h * heating_on +       &
    18061844                                            buildings(nb)%params_waste_heat_c * cooling_on )       &
    1807                                                     ) / facade_element_area  !< [W/m2] , observe the directional convention in
    1808                                                                              !< PALM!
     1845                            ) / facade_element_area  !< [W/m2] , observe the directional convention in PALM!
     1846!
     1847!--          Store waste heat and previous previous indoor temperature on surface-data type.
     1848!--          These will be used in the urban-surface model.
     1849             surf_usm_v(l)%t_prev(m)     = buildings(nb)%theta_m_t_prev_v(fa)
    18091850             surf_usm_v(l)%waste_heat(m) = q_waste_heat
    18101851          ENDDO !< Vertical surfaces loop
Note: See TracChangeset for help on using the changeset viewer.