Changeset 3759
- Timestamp:
- Feb 21, 2019 3:53:45 PM (6 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/indoor_model_mod.f90
r3745 r3759 26 26 ! ----------------- 27 27 ! $Id$ 28 ! - Calculation of total building volume 29 ! - Several bugfixes 30 ! - Calculation of building height revised 31 ! 32 ! 3745 2019-02-15 18:57:56Z suehring 28 33 ! - remove building_type from module 29 34 ! - initialize parameters for each building individually instead of a bulk … … 98 103 TYPE build 99 104 100 INTEGER(iwp) :: id !< building ID101 INTEGER(iwp) :: kb_min !< lowest vertical index of a building102 INTEGER(iwp) :: kb_max !< highest vertical index of a building103 INTEGER(iwp) :: num_facades_per_building_h !< total number of horizontal facades elements104 INTEGER(iwp) :: num_facades_per_building_h_l !< number of horizontal facade elements on local subdomain105 INTEGER(iwp) :: num_facades_per_building_v !< total number of vertical facades elements106 INTEGER(iwp) :: num_facades_per_building_v_l !< number of vertical facade elements on local subdomain105 INTEGER(iwp) :: id !< building ID 106 INTEGER(iwp) :: kb_min !< lowest vertical index of a building 107 INTEGER(iwp) :: kb_max !< highest vertical index of a building 108 INTEGER(iwp) :: num_facades_per_building_h = 0 !< total number of horizontal facades elements 109 INTEGER(iwp) :: num_facades_per_building_h_l = 0 !< number of horizontal facade elements on local subdomain 110 INTEGER(iwp) :: num_facades_per_building_v = 0 !< total number of vertical facades elements 111 INTEGER(iwp) :: num_facades_per_building_v_l = 0 !< number of vertical facade elements on local subdomain 107 112 108 113 INTEGER(iwp), DIMENSION(:), ALLOCATABLE :: l_v !< index array linking surface-element orientation index … … 121 126 LOGICAL :: on_pe = .FALSE. !< flag indicating whether a building with certain ID is on local subdomain 122 127 123 128 REAL(wp) :: building_height !< building height 124 129 REAL(wp) :: lambda_layer3 !< [W/(m*K)] Thermal conductivity of the inner layer 125 130 REAL(wp) :: s_layer3 !< [m] half thickness of the inner layer (layer_3) … … 143 148 REAL(wp) :: height_storey !< [m] storey heigth 144 149 REAL(wp) :: height_cei_con !< [m] ceiling construction heigth 150 REAL(wp) :: vol_tot !< total building volume 145 151 146 152 REAL(wp), DIMENSION(:), ALLOCATABLE :: t_in !< mean building indoor temperature, height dependent … … 165 171 ! 166 172 !-- Declare all global variables within the module 167 168 ! INTEGER(iwp) :: building_type = 1 !< namelist parameter with169 !< X1=construction year (cy) 1950, X2=cy 2000, X3=cy 2050170 !< R=Residental building, O=Office, RW=Enlarged Windows, P=Panel type (Plattenbau) WBS 70, H=Hospital (in progress), I=Industrial halls (in progress), S=Special Building (in progress)171 !< (0=R1, 1=R2, 2=R3, 3=O1, 4=O2, 5=O3,...)172 173 INTEGER(iwp) :: cooling_on !< Indoor cooling flag (0=off, 1=on) 173 174 INTEGER(iwp) :: heating_on !< Indoor heating flag (0=off, 1=on) … … 227 228 REAL(wp) :: f_cei !< [-] ceiling reduction factor 228 229 REAL(wp) :: ngs !< [m2] netto ground surface 229 REAL(wp) :: building_height230 230 231 231 REAL(wp), PARAMETER :: params_f_f = 0.3_wp !< [-] frame ratio chap. 8.3.2.1.1 for buildings with mostly cooling 2.0_wp … … 283 283 ! MODULE PROCEDURE im_header 284 284 ! END INTERFACE im_header 285 286 !-- Data Output287 ! INTERFACE im_data_output288 ! MODULE PROCEDURE im_data_output289 ! END INTERFACE im_data_output290 285 ! 291 286 !-- Calculations for indoor temperatures … … 564 559 buildings(nb)%id = build_ids_final(nb) 565 560 566 IF ( ANY( building_id_f%var == buildings(nb)%id ) )&561 IF ( ANY( building_id_f%var(nys:nyn,nxl:nxr) == buildings(nb)%id ) ) & 567 562 buildings(nb)%on_pe = .TRUE. 568 563 ENDDO … … 577 572 DO j = nys, nyn 578 573 IF ( building_id_f%var(j,i) /= building_id_f%fill ) THEN 579 nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), &574 nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), & 580 575 DIM = 1 ) 581 576 DO k = nzb+1, nzt+1 … … 608 603 DEALLOCATE( k_max_l ) 609 604 ! 605 !-- Calculate building height. 606 DO nb = 1, num_build 607 buildings(nb)%building_height = 0.0_wp 608 DO k = buildings(nb)%kb_min, buildings(nb)%kb_max 609 buildings(nb)%building_height = buildings(nb)%building_height & 610 + dzw(k) 611 ENDDO 612 ENDDO 613 ! 610 614 !-- Calculate building volume 611 615 DO nb = 1, num_build … … 625 629 buildings(nb)%vol_frac = 0.0_wp 626 630 627 IF ( ANY( building_id_f%var == buildings(nb)%id ) ) THEN 631 IF ( ANY( building_id_f%var(nys:nyn,nxl:nxr) == buildings(nb)%id ) ) & 632 THEN 628 633 DO i = nxl, nxr 629 634 DO j = nys, nyn 630 635 DO k = buildings(nb)%kb_min, buildings(nb)%kb_max 631 636 IF ( building_id_f%var(j,i) /= building_id_f%fill ) & 632 volume_l(k) = dx * dy * dzw(k)637 volume_l(k) = volume_l(k) + dx * dy * dzw(k) 633 638 ENDDO 634 639 ENDDO … … 651 656 !-- Determine fraction of local on total building volume 652 657 IF ( buildings(nb)%on_pe ) buildings(nb)%vol_frac = volume_l / volume 653 658 ! 659 !-- Calculate total building volume 660 IF ( ALLOCATED( buildings(nb)%volume ) ) & 661 buildings(nb)%vol_tot = SUM( buildings(nb)%volume ) 662 654 663 DEALLOCATE( volume ) 655 664 DEALLOCATE( volume_l ) … … 827 836 nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM = 1 ) 828 837 829 buildings(nb)%m_h(n_fa(nb)) = m 830 n_fa(nb) = n_fa(nb) + 1 838 IF ( buildings(nb)%on_pe ) THEN 839 buildings(nb)%m_h(n_fa(nb)) = m 840 n_fa(nb) = n_fa(nb) + 1 841 ENDIF 831 842 ENDDO 832 843 … … 839 850 nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM = 1 ) 840 851 841 buildings(nb)%l_v(n_fa(nb)) = l 842 buildings(nb)%m_v(n_fa(nb)) = m 843 n_fa(nb) = n_fa(nb) + 1 852 IF ( buildings(nb)%on_pe ) THEN 853 buildings(nb)%l_v(n_fa(nb)) = l 854 buildings(nb)%m_v(n_fa(nb)) = m 855 n_fa(nb) = n_fa(nb) + 1 856 ENDIF 844 857 ENDDO 845 858 ENDDO … … 1070 1083 window_area_per_facade = surf_usm_h%frac(ind_wat_win,m) * facade_element_area !< [m2] window area per facade element 1071 1084 1072 ! building_height = buildings(nb)%num_facades_per_building_v_l * 0.1 * dzw(kk)1073 building_height = buildings(nb)%kb_max * dzw(kk)1074 1075 1085 ! print*, "building_height", building_height 1076 1086 ! print*, "num_facades_v_l", buildings(nb)%num_facades_per_building_v_l … … 1079 1089 ! print*, "dzw kk", dzw(kk), kk 1080 1090 1081 f_cei = building_height/(buildings(nb)%height_storey-buildings(nb)%height_cei_con) !< [-] factor for ceiling redcution 1091 f_cei = buildings(nb)%building_height / & 1092 (buildings(nb)%height_storey-buildings(nb)%height_cei_con) !< [-] factor for ceiling redcution 1082 1093 ngs = buildings(nb)%vpf(kk)/f_cei !< [m2] calculation of netto ground surface 1083 1094 f_sr = ngs/floor_area_per_facade !< [-] factor for surface reduction … … 1274 1285 indoor_volume_per_facade = buildings(nb)%vpf(kk) !< [m3] indoor air volume per facade element 1275 1286 window_area_per_facade = surf_usm_v(l)%frac(ind_wat_win,m) * facade_element_area !< [m2] window area per facade element 1276 1277 building_height = buildings(nb)%kb_max * dzw(kk)1278 f_cei = building_height/(buildings(nb)%height_storey-buildings(nb)%height_cei_con) !< [-] factor for ceiling redcution1287 1288 f_cei = buildings(nb)%building_height / & 1289 (buildings(nb)%height_storey-buildings(nb)%height_cei_con) !< [-] factor for ceiling redcution 1279 1290 ngs = buildings(nb)%vpf(kk)/f_cei !< [m2] calculation of netto ground surface 1280 1291 f_sr = ngs/floor_area_per_facade !< [-] factor for surface reduction … … 1482 1493 buildings(nb)%t_in = t_in_recv 1483 1494 #else 1484 buildings(nb)%t_in = buildings(nb)%t_in_l 1495 IF ( ALLOCATED( buildings(nb)%t_in ) ) & 1496 buildings(nb)%t_in = buildings(nb)%t_in_l 1485 1497 #endif 1486 1487 buildings(nb)%t_in = buildings(nb)%t_in /&1488 ( buildings(nb)%num_facade_h +&1489 buildings(nb)%num_facade_v )1498 IF ( ALLOCATED( buildings(nb)%t_in ) ) & 1499 buildings(nb)%t_in = buildings(nb)%t_in / & 1500 ( buildings(nb)%num_facade_h + & 1501 buildings(nb)%num_facade_v ) 1490 1502 ! 1491 1503 !-- Deallocate dummy arrays … … 1647 1659 nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), & 1648 1660 DIM = 1 ) 1649 ! 1650 !-- Write mean building temperature onto output array. Please note, 1651 !-- in contrast to many other loops in the output, the vertical 1652 !-- bounds are determined by the lowest and hightest vertical index 1653 !-- occupied by the building. 1654 DO k = buildings(nb)%kb_min, buildings(nb)%kb_max 1655 local_pf(i,j,k) = buildings(nb)%t_in(k) 1656 ENDDO 1661 IF ( buildings(nb)%on_pe ) THEN 1662 ! 1663 !-- Write mean building temperature onto output array. Please note, 1664 !-- in contrast to many other loops in the output, the vertical 1665 !-- bounds are determined by the lowest and hightest vertical index 1666 !-- occupied by the building. 1667 DO k = buildings(nb)%kb_min, buildings(nb)%kb_max 1668 local_pf(i,j,k) = buildings(nb)%t_in(k) 1669 ENDDO 1670 ENDIF 1657 1671 ENDIF 1658 1672 ENDDO
Note: See TracChangeset
for help on using the changeset viewer.