Changeset 4402 for palm/trunk/SOURCE/indoor_model_mod.f90
- Timestamp:
- Feb 11, 2020 5:34:53 PM (5 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/indoor_model_mod.f90
r4346 r4402 26 26 ! ----------------- 27 27 ! $Id$ 28 ! Major bugfix in calculation of energy demand - floor-area-per-facade was wrongly 29 ! calculated leading to unrealistically high energy demands and thus to 30 ! unreallistically high waste-heat fluxes. 31 ! 32 ! 4346 2019-12-18 11:55:56Z motisi 28 33 ! Introduction of wall_flags_total_0, which currently sets bits based on static 29 34 ! topography information used in wall_flags_static_0 … … 133 138 MODULE indoor_model_mod 134 139 140 USE arrays_3d, & 141 ONLY: ddzw, & 142 dzw, & 143 pt 144 135 145 USE control_parameters, & 136 146 ONLY: initializing_actions … … 188 198 !< (very light), 110000 (light), 165000 (medium), 260000 (heavy), 370000 (very heavy) 189 199 REAL(wp) :: f_c_win !< [-] shading factor 200 REAL(wp) :: fapf !< [m2/m2] floor area per facade 190 201 REAL(wp) :: g_value_win !< [-] SHGC factor 191 202 REAL(wp) :: h_es !< [W/(m2 K)] surface-related heat transfer coefficient between extern and surface … … 408 419 SUBROUTINE im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, & 409 420 near_facade_temperature, phi_hc_nd_dummy ) 410 411 USE arrays_3d, & 412 ONLY: pt 413 414 415 IMPLICIT NONE 416 417 421 418 422 INTEGER(iwp) :: i 419 423 INTEGER(iwp) :: j … … 477 481 !------------------------------------------------------------------------------! 478 482 SUBROUTINE im_init 479 480 USE arrays_3d, &481 ONLY: dzw482 483 483 484 USE control_parameters, & … … 497 498 USE urban_surface_mod, & 498 499 ONLY: building_pars, building_type 499 500 IMPLICIT NONE501 500 502 501 INTEGER(iwp) :: bt !< local building type … … 908 907 ALLOCATE( buildings(nb)%m_v(1:buildings(nb)%num_facades_per_building_v_l) ) 909 908 ENDIF 910 ! 911 !-- Determine volume per facade element (vpf) 909 912 910 IF ( buildings(nb)%on_pe ) THEN 913 911 ALLOCATE( buildings(nb)%vpf(buildings(nb)%kb_min:buildings(nb)%kb_max) ) 914 912 buildings(nb)%vpf = 0.0_wp 915 916 DO k = buildings(nb)%kb_min, buildings(nb)%kb_max 917 ! 918 !-- In order to avoid division by zero, check if the number of facade 919 !-- elements is /= 0. This can e.g. happen if a building is embedded 920 !-- in higher terrain and at a given k-level neither horizontal nor 921 !-- vertical facade elements are located. 922 IF ( buildings(nb)%num_facade_h(k) & 923 + buildings(nb)%num_facade_v(k) > 0 ) THEN 924 buildings(nb)%vpf(k) = buildings(nb)%volume(k) / & 925 REAL( buildings(nb)%num_facade_h(k) + & 926 buildings(nb)%num_facade_v(k), KIND = wp ) 927 ENDIF 928 ENDDO 929 ENDIF 930 931 ! 932 !-- Determine volume per total facade area (vpf). For the horizontal facade 933 !-- area num_facades_per_building_h can be taken, multiplied with dx*dy. 934 !-- However, due to grid stretching, vertical facade elements must be 935 !-- summed-up vertically. Please note, if dx /= dy, an error is made! 936 IF ( buildings(nb)%on_pe ) THEN 937 913 938 914 facade_area_v = 0.0_wp 939 915 DO k = buildings(nb)%kb_min, buildings(nb)%kb_max … … 941 917 * dzw(k+1) * dx 942 918 ENDDO 943 919 ! 920 !-- Determine volume per total facade area (vpf). For the horizontal facade 921 !-- area num_facades_per_building_h can be taken, multiplied with dx*dy. 922 !-- However, due to grid stretching, vertical facade elements must be 923 !-- summed-up vertically. Please note, if dx /= dy, an error is made! 944 924 buildings(nb)%vpf = buildings(nb)%vol_tot / & 945 925 ( buildings(nb)%num_facades_per_building_h * dx * dy + & 946 926 facade_area_v ) 927 ! 928 !-- Determine floor-area-per-facade. 929 buildings(nb)%fapf = buildings(nb)%num_facades_per_building_h & 930 * dx * dy & 931 / ( buildings(nb)%num_facades_per_building_h & 932 * dx * dy + facade_area_v ) 947 933 ENDIF 948 934 ENDDO … … 1146 1132 SUBROUTINE im_main_heatcool 1147 1133 1148 USE arrays_3d, &1149 ONLY: ddzw, dzw1150 1151 1134 ! USE basic_constants_and_equations_mod, & 1152 1135 ! ONLY: c_p … … 1166 1149 ONLY: nzt_wall, t_wall_h, t_wall_v, t_window_h, t_window_v, & 1167 1150 building_type 1168 1169 1170 IMPLICIT NONE1171 1151 1172 1152 INTEGER(iwp) :: i !< index of facade-adjacent atmosphere grid point in x-direction … … 1237 1217 !-- Determine building height level index. 1238 1218 kk = surf_usm_h%k(m) + surf_usm_h%koff 1239 ! 1219 ! 1240 1220 !-- Building geometries --> not time-dependent 1241 facade_element_area = dx * dy 1242 floor_area_per_facade = buildings(nb)% vpf(kk) * ddzw(kk+1)!< [m2/m2] floor area per facade area1243 indoor_volume_per_facade = buildings(nb)%vpf(kk) 1221 facade_element_area = dx * dy !< [m2] surface area per facade element 1222 floor_area_per_facade = buildings(nb)%fapf !< [m2/m2] floor area per facade area 1223 indoor_volume_per_facade = buildings(nb)%vpf(kk) !< [m3/m2] indoor air volume per facade area 1244 1224 buildings(nb)%area_facade = facade_element_area * & 1245 1225 ( buildings(nb)%num_facades_per_building_h + & … … 1447 1427 !-- EXCEPT facade_element_area, EVERYTHING IS CALCULATED EQUALLY) 1448 1428 !-- Building geometries --> not time-dependent 1449 IF ( l == 0 .OR. l == 1 ) facade_element_area = dx * dzw(kk+1) !< [m2] surface area per facade element 1450 IF ( l == 2 .OR. l == 3 ) facade_element_area = dy * dzw(kk+1) !< [m2] surface area per facade element 1451 floor_area_per_facade = buildings(nb)%vpf(kk) * ddzw(kk+1) !< [m2/m2] floor area per facade area 1452 indoor_volume_per_facade = buildings(nb)%vpf(kk) !< [m3/m2] indoor air volume per facade area 1429 IF ( l == 0 .OR. l == 1 ) facade_element_area = dx * dzw(kk+1) !< [m2] surface area per facade element 1430 IF ( l == 2 .OR. l == 3 ) facade_element_area = dy * dzw(kk+1) !< [m2] surface area per facade element 1431 1432 floor_area_per_facade = buildings(nb)%fapf !< [m2/m2] floor area per facade area 1433 indoor_volume_per_facade = buildings(nb)%vpf(kk) !< [m3/m2] indoor air volume per facade area 1453 1434 buildings(nb)%area_facade = facade_element_area * & 1454 1435 ( buildings(nb)%num_facades_per_building_h + & 1455 1436 buildings(nb)%num_facades_per_building_v ) !< [m2] area of total facade 1456 window_area_per_facade = surf_usm_v(l)%frac(ind_wat_win,m) * facade_element_area 1437 window_area_per_facade = surf_usm_v(l)%frac(ind_wat_win,m) * facade_element_area !< [m2] window area per facade element 1457 1438 1458 1439 buildings(nb)%net_floor_area = buildings(nb)%vol_tot / ( buildings(nb)%height_storey ) … … 1571 1552 theta_air_10 = theta_air !< Note the temperature with 10 W/m2 of heating 1572 1553 1573 1574 1554 phi_hc_nd_un = phi_hc_nd_10 * ( theta_air_set - theta_air_0 ) & 1575 1555 / ( theta_air_10 - theta_air_0 ) !< Eq. (C.13) … … 1642 1622 ) / facade_element_area !< [W/m2] , observe the directional convention in PALM! 1643 1623 surf_usm_v(l)%waste_heat(m) = q_waste_heat 1644 1645 1624 ENDDO !< Vertical surfaces loop 1646 1647 1625 ENDIF !< buildings(nb)%on_pe 1648 1626 ENDDO !< buildings loop … … 1724 1702 !-----------------------------------------------------------------------------! 1725 1703 SUBROUTINE im_check_data_output( var, unit ) 1726 1727 IMPLICIT NONE 1728 1704 1729 1705 CHARACTER (LEN=*) :: unit !< 1730 1706 CHARACTER (LEN=*) :: var !< … … 1771 1747 ! USE control_parameters, 1772 1748 ! ONLY: message_string 1773 1774 IMPLICIT NONE1775 1749 1776 1750 END SUBROUTINE im_check_parameters … … 1784 1758 SUBROUTINE im_define_netcdf_grid( var, found, grid_x, grid_y, grid_z ) 1785 1759 1786 IMPLICIT NONE1787 1760 1788 1761 CHARACTER (LEN=*), INTENT(IN) :: var … … 1831 1804 nzb_do, nzt_do ) 1832 1805 1833 USE indices 1834 1835 USE kinds 1836 1837 IMPLICIT NONE 1838 1806 USE indices 1807 1808 USE kinds 1809 1839 1810 CHARACTER (LEN=*) :: variable !< 1840 1811 … … 1971 1942 USE control_parameters, & 1972 1943 ONLY: indoor_model 1973 1974 IMPLICIT NONE 1944 1975 1945 1976 1946 CHARACTER (LEN=80) :: line !< string containing current line of file PARIN
Note: See TracChangeset
for help on using the changeset viewer.