Changeset 3759 for palm


Ignore:
Timestamp:
Feb 21, 2019 3:53:45 PM (5 years ago)
Author:
suehring
Message:

Indoor model: provide total building volume; several bugfixes; calculation of building height in IM revised

File:
1 edited

Legend:

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

    r3745 r3759  
    2626! -----------------
    2727! $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
    2833! - remove building_type from module
    2934! - initialize parameters for each building individually instead of a bulk
     
    98103    TYPE build
    99104
    100        INTEGER(iwp) ::  id                             !< building ID
    101        INTEGER(iwp) ::  kb_min                         !< lowest vertical index of a building
    102        INTEGER(iwp) ::  kb_max                         !< highest vertical index of a building
    103        INTEGER(iwp) ::  num_facades_per_building_h     !< total number of horizontal facades elements
    104        INTEGER(iwp) ::  num_facades_per_building_h_l   !< number of horizontal facade elements on local subdomain
    105        INTEGER(iwp) ::  num_facades_per_building_v     !< total number of vertical facades elements
    106        INTEGER(iwp) ::  num_facades_per_building_v_l   !< number of vertical facade elements on local subdomain
     105       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
    107112
    108113       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  l_v            !< index array linking surface-element orientation index
     
    121126       LOGICAL ::  on_pe = .FALSE.   !< flag indicating whether a building with certain ID is on local subdomain
    122127       
    123        
     128       REAL(wp) ::  building_height   !< building height
    124129       REAL(wp) ::  lambda_layer3     !< [W/(m*K)] Thermal conductivity of the inner layer 
    125130       REAL(wp) ::  s_layer3          !< [m] half thickness of the inner layer (layer_3)
     
    143148       REAL(wp) ::  height_storey     !< [m] storey heigth
    144149       REAL(wp) ::  height_cei_con    !< [m] ceiling construction heigth
     150       REAL(wp) ::  vol_tot           !< total building volume
    145151
    146152       REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in       !< mean building indoor temperature, height dependent
     
    165171!
    166172!-- Declare all global variables within the module
    167 
    168 !     INTEGER(iwp) ::  building_type = 1       !< namelist parameter with
    169                                              !< X1=construction year (cy) 1950, X2=cy 2000, X3=cy 2050
    170                                              !< 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,...)
    172173    INTEGER(iwp) ::  cooling_on              !< Indoor cooling flag (0=off, 1=on)
    173174    INTEGER(iwp) ::  heating_on              !< Indoor heating flag (0=off, 1=on)
     
    227228    REAL(wp) ::  f_cei                       !< [-] ceiling reduction factor
    228229    REAL(wp) ::  ngs                         !< [m2] netto ground surface
    229     REAL(wp) ::  building_height
    230230   
    231231    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
     
    283283!        MODULE PROCEDURE im_header
    284284!     END INTERFACE im_header
    285 
    286 !-- Data Output
    287 !    INTERFACE im_data_output
    288 !       MODULE PROCEDURE im_data_output
    289 !    END INTERFACE im_data_output
    290285!
    291286!-- Calculations for indoor temperatures 
     
    564559       buildings(nb)%id = build_ids_final(nb)
    565560
    566        IF ( ANY( building_id_f%var == buildings(nb)%id ) )                      &
     561       IF ( ANY( building_id_f%var(nys:nyn,nxl:nxr) == buildings(nb)%id ) )    &
    567562          buildings(nb)%on_pe = .TRUE.
    568563    ENDDO
     
    577572       DO  j = nys, nyn
    578573          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) ),    &
    580575                         DIM = 1 )
    581576             DO  k = nzb+1, nzt+1
     
    608603    DEALLOCATE( k_max_l )
    609604!
     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!
    610614!-- Calculate building volume
    611615    DO  nb = 1, num_build
     
    625629          buildings(nb)%vol_frac = 0.0_wp
    626630         
    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
    628633             DO  i = nxl, nxr
    629634                DO  j = nys, nyn
    630635                   DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
    631636                      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)
    633638                   ENDDO
    634639                ENDDO
     
    651656!--    Determine fraction of local on total building volume
    652657       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       
    654663       DEALLOCATE( volume   )
    655664       DEALLOCATE( volume_l )
     
    827836       nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM = 1 )
    828837
    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
    831842    ENDDO
    832843
     
    839850          nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM = 1 )
    840851
    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
    844857       ENDDO
    845858    ENDDO
     
    10701083             window_area_per_facade   = surf_usm_h%frac(ind_wat_win,m)  * facade_element_area  !< [m2] window area per facade element
    10711084             
    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              
    10751085! print*, "building_height", building_height
    10761086! print*, "num_facades_v_l", buildings(nb)%num_facades_per_building_v_l
     
    10791089! print*, "dzw kk", dzw(kk), kk
    10801090
    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
    10821093             ngs                      = buildings(nb)%vpf(kk)/f_cei                    !< [m2] calculation of netto ground surface
    10831094             f_sr                     = ngs/floor_area_per_facade                      !< [-] factor for surface reduction
     
    12741285             indoor_volume_per_facade = buildings(nb)%vpf(kk)               !< [m3] indoor air volume per facade element           
    12751286             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 redcution
     1287
     1288             f_cei                    = buildings(nb)%building_height /        &
     1289                                        (buildings(nb)%height_storey-buildings(nb)%height_cei_con) !< [-] factor for ceiling redcution
    12791290             ngs                      = buildings(nb)%vpf(kk)/f_cei                    !< [m2] calculation of netto ground surface
    12801291             f_sr                     = ngs/floor_area_per_facade                      !< [-] factor for surface reduction
     
    14821493           buildings(nb)%t_in = t_in_recv
    14831494#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
    14851497#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 )
    14901502!
    14911503!--    Deallocate dummy arrays
     
    16471659                       nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ),   &
    16481660                                    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
    16571671                    ENDIF
    16581672                 ENDDO
Note: See TracChangeset for help on using the changeset viewer.