Ignore:
Timestamp:
Jul 17, 2019 4:00:03 PM (5 years ago)
Author:
suehring
Message:

Bugfix, set Neumann boundary conditions for the subgrid TKE at vertical walls instead of implicit Dirichlet conditions that always act as a sink term for the subgrid TKE. Therefore, add new data structure for vertical surfaces and revise the setting of the boundary grid point index space. Moreover, slightly revise setting of boundary conditions at upward- and downward facing surfaces. Finally, setting of boundary conditions for subgrid TKE and dissipation (in RANS mode) is now modularized. Update test case results.

File:
1 edited

Legend:

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

    r4080 r4102  
    2727! -----------------
    2828! $Id$
     29! Slightly revise setting of boundary conditions at horizontal walls, use
     30! data-structure offset index instead of pre-calculate it for each facing
     31!
     32! 4080 2019-07-09 18:17:37Z suehring
    2933! Restore accidantly removed limitation to positive values
    3034!
     
    804808    INTEGER(iwp) ::  j                            !< grid index y direction.
    805809    INTEGER(iwp) ::  k                            !< grid index z direction.
    806     INTEGER(iwp) ::  kb                           !< variable to set respective boundary value, depends on facing.
    807810    INTEGER(iwp) ::  l                            !< running index boundary type, for up- and downward-facing walls.
    808811    INTEGER(iwp) ::  m                            !< running index surface elements.
     
    839842       CASE ( 'set_bc_bottomtop' )                   
    840843!
    841 !--          Bottom boundary condtions for chemical species     
     844!--       Boundary condtions for chemical species at horizontal walls     
    842845          DO  lsp = 1, nspec                                                     
    843              IF ( ibc_cs_b == 0 )  THEN                   
     846             IF ( ibc_cs_b == 0 )  THEN
    844847                DO  l = 0, 1
    845 !
    846 !--                Set index kb: For upward-facing surfaces (l=0), kb=-1, i.e.
    847 !--                the chem_species(nspec)%conc_p value at the topography top (k-1)
    848 !--                is set; for downward-facing surfaces (l=1), kb=1, i.e. the
    849 !--                value at the topography bottom (k+1) is set.
    850 
    851                    kb = MERGE( -1, 1, l == 0 )
    852848                   !$OMP PARALLEL DO PRIVATE( i, j, k )
    853849                   DO  m = 1, bc_h(l)%ns
     
    855851                       j = bc_h(l)%j(m)
    856852                       k = bc_h(l)%k(m)
    857                       chem_species(lsp)%conc_p(k+kb,j,i) = chem_species(lsp)%conc(k+kb,j,i)
     853                      chem_species(lsp)%conc_p(k+bc_h(l)%koff,j,i) =           &
     854                                      chem_species(lsp)%conc(k+bc_h(l)%koff,j,i)
    858855                   ENDDO                                       
    859856                ENDDO                                       
     
    863860!--             in boundary_conds there is som extra loop over m here for passive tracer
    864861                DO  l = 0, 1
    865                    kb = MERGE( -1, 1, l == 0 )
    866862                   !$OMP PARALLEL DO PRIVATE( i, j, k )                                           
    867863                   DO m = 1, bc_h(l)%ns
     
    869865                      j = bc_h(l)%j(m)
    870866                      k = bc_h(l)%k(m)
    871                       chem_species(lsp)%conc_p(k+kb,j,i) = chem_species(lsp)%conc_p(k,j,i)
     867                      chem_species(lsp)%conc_p(k+bc_h(l)%koff,j,i) =           &
     868                                         chem_species(lsp)%conc_p(k,j,i)
    872869
    873870                   ENDDO
Note: See TracChangeset for help on using the changeset viewer.