Ignore:
Timestamp:
Oct 16, 2020 2:27:48 PM (4 years ago)
Author:
suehring
Message:

Indoor-model new: Namelist parameter added to switch-off/on the indoor model during wall/soil spinup; bugfixes concerning indoor model: bugfix in window-wall treatment during spinup - in the urban-surface model the window fraction is set to zero during spinup, so it is done here also; bugfix in wall treatment - inner wall temperature was too low due to wrong weighting of wall/green/window fractions; Revision of 10-cm temperature at vertical walls - assume grid-cell temperature rather than employ MOST; call hourly-based indoor model only once per hour during spinup, not every timestep; add missing dependency in Makefile; urban-surface model: bugfix in openmp directive

File:
1 edited

Legend:

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

    r4730 r4750  
    2525! -----------------
    2626! $Id$
     27! - Namelist parameter added to switch-off/on the indoor model during wall/soil spinup
     28! - Bugfix in window-wall treatment during spinup - in the urban-surface model the window fraction
     29!   is set to zero during spinup, so it is done here also
     30! - Bugfix in wall treatment - inner wall temperature was too low due to wrong weighting of
     31!   wall/green/window fractions
     32!
     33! 4730 2020-10-07 10:48:51Z suehring
    2734! Bugfix - avoid divisions by zero
    2835!
     
    271278    TYPE(build), DIMENSION(:), ALLOCATABLE ::  buildings   !< building array
    272279
    273     INTEGER(iwp) ::  num_build   !< total number of buildings in domain
     280    INTEGER(iwp) ::  cooling_on              !< Indoor cooling flag (0=off, 1=on)
     281    INTEGER(iwp) ::  heating_on              !< Indoor heating flag (0=off, 1=on)
     282    INTEGER(iwp) ::  num_build               !< total number of buildings in domain
     283    INTEGER(iwp) ::  solar_protection_off    !< Solar protection off
     284    INTEGER(iwp) ::  solar_protection_on     !< Solar protection on
     285
     286    LOGICAL ::  indoor_during_spinup = .FALSE.      !< namelist parameter used to switch-off/on the indoor model during spinup
    274287!
    275288!-- Declare all global variables within the module
     
    289302    REAL(wp), PARAMETER ::  params_solar_protection  = 300.0_wp    !< [W/m2] chap. G.5.3.1 sun protection closed, if the radiation
    290303                                                                   !< on facade exceeds this value
    291 
    292     INTEGER(iwp) ::  cooling_on              !< Indoor cooling flag (0=off, 1=on)
    293     INTEGER(iwp) ::  heating_on              !< Indoor heating flag (0=off, 1=on)
    294     INTEGER(iwp) ::  solar_protection_off    !< Solar protection off
    295     INTEGER(iwp) ::  solar_protection_on     !< Solar protection on
    296 
    297304
    298305    REAL(wp) ::  a_m                                 !< [m2] the effective mass-related area
     
    416423!
    417424!-- Add VARIABLES that must be available to other modules
    418     PUBLIC dt_indoor, skip_time_do_indoor, time_indoor
     425    PUBLIC dt_indoor,                                                                              &
     426           indoor_during_spinup,                                                                   &
     427           skip_time_do_indoor,                                                                    &
     428           time_indoor
    419429
    420430!
     
    11981208
    11991209    USE surface_mod,                                                                               &
    1200         ONLY:  ind_veg_wall, ind_wat_win, surf_usm_h, surf_usm_v
     1210        ONLY:  ind_pav_green,                                                                      &
     1211               ind_veg_wall,                                                                       &
     1212               ind_wat_win,                                                                        &
     1213               surf_usm_h,                                                                         &
     1214               surf_usm_v
    12011215
    12021216    USE urban_surface_mod,                                                                         &
    1203         ONLY:  building_type, nzt_wall, t_wall_h, t_wall_v, t_window_h, t_window_v
     1217        ONLY:  building_type,                                                                      &
     1218               nzt_wall,                                                                           &
     1219               t_green_h,                                                                          &
     1220               t_green_v,                                                                          &
     1221               t_wall_h,                                                                           &
     1222               t_wall_v,                                                                           &
     1223               t_window_h,                                                                         &
     1224               t_window_v
    12041225
    12051226
     
    12131234    INTEGER(iwp) ::  nb   !< running index for buildings
    12141235
    1215     REAL(wp) ::  indoor_wall_window_temperature   !< weighted temperature of innermost wall/window layer
    1216    
    1217     REAL(wp) ::  indoor_wall_temperature   !< temperature of innermost wall layer evtl in im_calc_temperatures einfÃŒgen
    1218    
     1236    LOGICAL  ::  during_spinup                    !< flag indicating that the simulation is still in wall/soil spinup
     1237
     1238    REAL(wp) ::  frac_green                       !< dummy for green fraction
     1239    REAL(wp) ::  frac_wall                        !< dummy for wall fraction
     1240    REAL(wp) ::  frac_win                         !< dummy for window fraction
     1241!     REAL(wp) ::  indoor_wall_window_temperature   !< weighted temperature of innermost wall/window layer
     1242    REAL(wp) ::  indoor_wall_temperature          !< temperature of innermost wall layer evtl in im_calc_temperatures einfÃŒgen
    12191243    REAL(wp) ::  near_facade_temperature          !< outside air temperature 10cm away from facade
    12201244    REAL(wp) ::  second_of_day                    !< second of the current day
     
    12271251    CALL get_date_time( time_since_reference_point, second_of_day=second_of_day )
    12281252    time_utc_hour = second_of_day / seconds_per_hour
     1253!
     1254!-- Check if the simulation is still in wall/soil spinup mode
     1255    during_spinup = MERGE( .TRUE., .FALSE., time_since_reference_point < 0.0_wp )
    12291256!
    12301257!-- Following calculations must be done for each facade element.
     
    12721299             m = buildings(nb)%m_h(fa)
    12731300!
     1301!--          During spinup set window fraction to zero and add these to wall fraction.
     1302             frac_win   = MERGE( surf_usm_h(l)%frac(m,ind_wat_win), 0.0_wp, .NOT. during_spinup )
     1303             frac_wall  = MERGE( surf_usm_h(l)%frac(m,ind_veg_wall),                               &
     1304                                 surf_usm_h(l)%frac(m,ind_veg_wall) +                              &
     1305                                 surf_usm_h(l)%frac(m,ind_wat_win),                                &
     1306                                 .NOT. during_spinup )
     1307             frac_green = surf_usm_h(l)%frac(m,ind_pav_green)
     1308!
    12741309!--          Determine building height level index.
    12751310             kk = surf_usm_h(l)%k(m) + surf_usm_h(l)%koff
     
    12811316             buildings(nb)%area_facade    = facade_element_area *                                  &
    12821317                                            ( buildings(nb)%num_facades_per_building_h +           &
    1283                                               buildings(nb)%num_facades_per_building_v )              !< [m2] area of total facade
    1284              window_area_per_facade       = surf_usm_h(l)%frac(m,ind_wat_win)  * facade_element_area  !< [m2] window area per facade
    1285                                                                                                       !< element
     1318                                              buildings(nb)%num_facades_per_building_v ) !< [m2] area of total facade
     1319             window_area_per_facade       = frac_win  * facade_element_area              !< [m2] window area per facade element
    12861320
    12871321             buildings(nb)%net_floor_area = buildings(nb)%vol_tot / ( buildings(nb)%height_storey )
     
    13381372             k = surf_usm_h(l)%k(m)
    13391373             near_facade_temperature = surf_usm_h(l)%pt_10cm(m)
    1340              indoor_wall_window_temperature =                                                             &
    1341                                             surf_usm_h(l)%frac(m,ind_veg_wall) * t_wall_h(l)%val(nzt_wall,m) &
    1342                                           + surf_usm_h(l)%frac(m,ind_wat_win)  * t_window_h(l)%val(nzt_wall,m)
    1343              indoor_wall_temperature = surf_usm_h(l)%frac(m,ind_veg_wall) * t_wall_h(l)%val(nzt_wall,m)
     1374!              indoor_wall_window_temperature = frac_wall  * t_wall_h(l)%val(nzt_wall,m)             &
     1375!                                             + frac_win   * t_window_h(l)%val(nzt_wall,m)           &
     1376!                                             + frac_green * t_green_h(l)%val(nzt_wall,m)
     1377             indoor_wall_temperature = frac_wall  * t_wall_h(l)%val(nzt_wall,m)                    &
     1378                                     + frac_win   * t_window_h(l)%val(nzt_wall,m)                  &
     1379                                     + frac_green * t_green_h(l)%val(nzt_wall,m)
    13441380!
    13451381!--          Solar thermal gains. If net_sw_in larger than sun-protection threshold parameter
     
    15101546             m = buildings(nb)%m_v(fa)
    15111547!
     1548!--          During spinup set window fraction to zero and add these to wall fraction.
     1549             frac_win   = MERGE( surf_usm_v(l)%frac(m,ind_wat_win), 0.0_wp, .NOT. during_spinup )
     1550             frac_wall  = MERGE( surf_usm_v(l)%frac(m,ind_veg_wall),                               &
     1551                                 surf_usm_v(l)%frac(m,ind_veg_wall) +                              &
     1552                                 surf_usm_v(l)%frac(m,ind_wat_win),                                &
     1553                                 .NOT. during_spinup )
     1554             frac_green = surf_usm_v(l)%frac(m,ind_pav_green)
     1555!
    15121556!--          Determine building height level index.
    15131557             kk = surf_usm_v(l)%k(m) + surf_usm_v(l)%koff
     
    15231567             buildings(nb)%area_facade    = facade_element_area *                                  &
    15241568                                            ( buildings(nb)%num_facades_per_building_h +           &
    1525                                               buildings(nb)%num_facades_per_building_v )              !< [m2] area of total facade
    1526              window_area_per_facade       = surf_usm_v(l)%frac(m,ind_wat_win) * facade_element_area   !< [m2] window area per
    1527                                                                                                       !< facade element
     1569                                              buildings(nb)%num_facades_per_building_v )  !< [m2] area of total facade
     1570             window_area_per_facade       = frac_win * facade_element_area                !< [m2] window area per facade element
    15281571
    15291572             buildings(nb)%net_floor_area = buildings(nb)%vol_tot / ( buildings(nb)%height_storey )
     
    15621605!--          (air_change_high)
    15631606             air_change = ( buildings(nb)%air_change_high * schedule_d +                           &
    1564                           buildings(nb)%air_change_low )
     1607                            buildings(nb)%air_change_low )
    15651608!
    15661609!--          Heat transfer of ventilation.
     
    15841627             k = surf_usm_v(l)%k(m)
    15851628             near_facade_temperature = surf_usm_v(l)%pt_10cm(m)
    1586              indoor_wall_window_temperature =                                                          &
    1587                                     surf_usm_v(l)%frac(m,ind_veg_wall) * t_wall_v(l)%val(nzt_wall,m)   &
    1588                                   + surf_usm_v(l)%frac(m,ind_wat_win)  * t_window_v(l)%val(nzt_wall,m)
    1589              indoor_wall_temperature = surf_usm_v(l)%frac(m,ind_veg_wall) * t_wall_v(l)%val(nzt_wall,m)
     1629
     1630!              indoor_wall_window_temperature = frac_wall  * t_wall_v(l)%val(nzt_wall,m)             &
     1631!                                             + frac_win   * t_window_v(l)%val(nzt_wall,m)           &
     1632!                                             + frac_green * t_green_v(l)%val(nzt_wall,m)
     1633
     1634             indoor_wall_temperature = frac_wall  * t_wall_v(l)%val(nzt_wall,m)                    &
     1635                                     + frac_win   * t_window_v(l)%val(nzt_wall,m)                  &
     1636                                     + frac_green * t_green_v(l)%val(nzt_wall,m)
    15901637
    15911638!
     
    17251772             surf_usm_v(l)%iwghf_eb(m)        = - q_wall
    17261773             surf_usm_v(l)%iwghf_eb_window(m) = - q_win
     1774
     1775!              print*, "wwfjg", surf_usm_v(l)%iwghf_eb(m), surf_usm_v(l)%iwghf_eb_window(m)
    17271776!
    17281777!--          Sum up operational indoor temperature per kk-level. Further below, this temperature is
     
    20702119    CHARACTER (LEN=80) ::  line  !< string containing current line of file PARIN
    20712120
    2072     NAMELIST /indoor_parameters/  initial_indoor_temperature
     2121    NAMELIST /indoor_parameters/  indoor_during_spinup,                                            &
     2122                                  initial_indoor_temperature
    20732123
    20742124
Note: See TracChangeset for help on using the changeset viewer.