Ignore:
Timestamp:
Sep 25, 2019 4:06:01 PM (5 years ago)
Author:
suehring
Message:

Building data base: Indoor-model parameters for some building types adjusted in order to avoid unrealistically high indoor temperatures (S. Rissmann); Indoor model: Bugfix in determination of minimum facade height and in location message, avoid divisions by zero, minor optimizations; radiation model: Modify check in order to avoid equality comparisons of floating points

File:
1 edited

Legend:

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

    r4227 r4238  
    2626! -----------------
    2727! $Id$
     28! - Bugfix in determination of minimum facade height and in location message
     29! - Bugfix, avoid division by zero
     30! - Some optimization
     31!
     32! 4227 2019-09-10 18:04:34Z gronemeier
    2833! implement new palm_date_time_mod
    2934!
     
    469474                                                           !< on local subdomain
    470475
    471     CALL location_message( 'initializing indoor model', .FALSE. )
     476    CALL location_message( 'initializing indoor model', 'start' )
    472477!
    473478!-- Initializing of indoor model is only possible if buildings can be
     
    615620    ENDDO
    616621
    617     DO nb = 1, num_build
    618622#if defined( __parallel )
    619        CALL MPI_ALLREDUCE( k_min_l(nb), buildings(nb)%kb_min, 1, MPI_INTEGER,  &
    620                           MPI_MIN, comm2d, ierr )
    621        CALL MPI_ALLREDUCE( k_max_l(nb), buildings(nb)%kb_max, 1, MPI_INTEGER,  &
    622                           MPI_MAX, comm2d, ierr )
     623    CALL MPI_ALLREDUCE( k_min_l(:), buildings(:)%kb_min, num_build,            &
     624                        MPI_INTEGER, MPI_MIN, comm2d, ierr )
     625    CALL MPI_ALLREDUCE( k_max_l(:), buildings(:)%kb_max, num_build,            &
     626                        MPI_INTEGER, MPI_MAX, comm2d, ierr )
    623627#else
    624        buildings(nb)%kb_min = k_min_l(nb)
    625        buildings(nb)%kb_max = k_max_l(nb)
     628    buildings(:)%kb_min = k_min_l(:)
     629    buildings(:)%kb_max = k_max_l(:)
    626630#endif
    627 
    628     ENDDO
    629631
    630632    DEALLOCATE( k_min_l )
     
    746748    ENDDO
    747749!
    748 !-- Vertical facades!
     750!-- Vertical facades
    749751    buildings(:)%num_facades_per_building_v_l = 0
    750752    DO  l = 0, 3
     
    842844       ENDIF
    843845!
    844 ! --    Determine volume per facade element (vpf)
     846!--    Determine volume per facade element (vpf)
    845847       IF ( buildings(nb)%on_pe )  THEN
    846848          ALLOCATE( buildings(nb)%vpf(buildings(nb)%kb_min:buildings(nb)%kb_max) )
     849          buildings(nb)%vpf = 0.0_wp
    847850         
    848851          DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
    849              buildings(nb)%vpf(k) = buildings(nb)%volume(k) /                  &
     852!
     853!--          In order to avoid division by zero, check if the number of facade
     854!--          elements is /= 0. This can e.g. happen if a building is embedded
     855!--          in higher terrain and at a given k-level neither horizontal nor
     856!--          vertical facade elements are located.
     857             IF ( buildings(nb)%num_facade_h(k)                                &
     858                + buildings(nb)%num_facade_v(k) > 0 )  THEN 
     859                buildings(nb)%vpf(k) = buildings(nb)%volume(k) /               &
    850860                                REAL( buildings(nb)%num_facade_h(k) +          &
    851861                                      buildings(nb)%num_facade_v(k), KIND = wp )
     862             ENDIF
    852863          ENDDO
    853864       ENDIF
     
    10371048    ENDDO
    10381049
    1039     CALL location_message( 'finished', .TRUE. )
     1050    CALL location_message( 'initializing indoor model', 'finished' )
    10401051
    10411052 END SUBROUTINE im_init
     
    17901801           IF ( av == 0 ) THEN
    17911802              DO  m = 1, surf_usm_h%ns
    1792                   i = surf_usm_h%i(m) !+ surf_usm_h%ioff
    1793                   j = surf_usm_h%j(m) !+ surf_usm_h%joff
    1794                   k = surf_usm_h%k(m) !+ surf_usm_h%koff
    1795                   local_pf(i,j,k) = surf_usm_h%iwghf_eb(m)
     1803                 i = surf_usm_h%i(m) !+ surf_usm_h%ioff
     1804                 j = surf_usm_h%j(m) !+ surf_usm_h%joff
     1805                 k = surf_usm_h%k(m) !+ surf_usm_h%koff
     1806                 local_pf(i,j,k) = surf_usm_h%iwghf_eb(m)
    17961807              ENDDO
    17971808           ENDIF
Note: See TracChangeset for help on using the changeset viewer.