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/salsa_mod.f90

    r4079 r4102  
    2626! -----------------
    2727! $Id$
     28! Slightly revise setting of boundary conditions at horizontal walls, use
     29! data-structure offset index instead of pre-calculate it for each facing
     30!
     31! 4079 2019-07-09 18:04:41Z suehring
    2832! Application of monotonic flux limiter for the vertical scalar advection
    2933! up to the topography top (only for the cache-optimized version at the
     
    80178021    INTEGER(iwp) ::  j    !< grid index y direction
    80188022    INTEGER(iwp) ::  k    !< grid index y direction
    8019     INTEGER(iwp) ::  kb   !< variable to set respective boundary value, depends on facing.
    80208023    INTEGER(iwp) ::  l    !< running index boundary type, for up- and downward-facing walls
    80218024    INTEGER(iwp) ::  m    !< running index surface elements
     
    80308033!--       belongs to the atmospheric grid point, therefore, set s_p at k-1
    80318034          DO  l = 0, 1
    8032 !
    8033 !--          Set kb, for upward-facing surfaces value at topography top (k-1) is
    8034 !--          set, for downward-facing surfaces at topography bottom (k+1)
    8035              kb = MERGE ( -1, 1, l == 0 )
    80368035             !$OMP PARALLEL PRIVATE( ib, ic, icc, ig, i, j, k )
    80378036             !$OMP DO
     
    80438042
    80448043                DO  ib = 1, nbins_aerosol
    8045                    aerosol_number(ib)%conc_p(k+kb,j,i) = aerosol_number(ib)%conc(k+kb,j,i)
     8044                   aerosol_number(ib)%conc_p(k+bc_h(l)%koff,j,i) =             &
     8045                                    aerosol_number(ib)%conc(k+bc_h(l)%koff,j,i)
    80468046                   DO  ic = 1, ncomponents_mass
    80478047                      icc = ( ic - 1 ) * nbins_aerosol + ib
    8048                       aerosol_mass(icc)%conc_p(k+kb,j,i) = aerosol_mass(icc)%conc(k+kb,j,i)
     8048                      aerosol_mass(icc)%conc_p(k+bc_h(l)%koff,j,i) =           &
     8049                                    aerosol_mass(icc)%conc(k+bc_h(l)%koff,j,i)
    80498050                   ENDDO
    80508051                ENDDO
    80518052                IF ( .NOT. salsa_gases_from_chem )  THEN
    80528053                   DO  ig = 1, ngases_salsa
    8053                       salsa_gas(ig)%conc_p(k+kb,j,i) = salsa_gas(ig)%conc(k+kb,j,i)
     8054                      salsa_gas(ig)%conc_p(k+bc_h(l)%koff,j,i) =               &
     8055                                    salsa_gas(ig)%conc(k+bc_h(l)%koff,j,i)
    80548056                   ENDDO
    80558057                ENDIF
     
    80638065
    80648066          DO l = 0, 1
    8065 !
    8066 !--          Set kb, for upward-facing surfaces value at topography top (k-1) is
    8067 !--          set, for downward-facing surfaces at topography bottom (k+1)
    8068              kb = MERGE( -1, 1, l == 0 )
    80698067             !$OMP PARALLEL PRIVATE( ib, ic, icc, ig, i, j, k )
    80708068             !$OMP DO
     
    80768074
    80778075                DO  ib = 1, nbins_aerosol
    8078                    aerosol_number(ib)%conc_p(k+kb,j,i) = aerosol_number(ib)%conc_p(k,j,i)
     8076                   aerosol_number(ib)%conc_p(k+bc_h(l)%koff,j,i) =             &
     8077                                               aerosol_number(ib)%conc_p(k,j,i)
    80798078                   DO  ic = 1, ncomponents_mass
    80808079                      icc = ( ic - 1 ) * nbins_aerosol + ib
    8081                       aerosol_mass(icc)%conc_p(k+kb,j,i) = aerosol_mass(icc)%conc_p(k,j,i)
     8080                      aerosol_mass(icc)%conc_p(k+bc_h(l)%koff,j,i) =           &
     8081                                               aerosol_mass(icc)%conc_p(k,j,i)
    80828082                   ENDDO
    80838083                ENDDO
    80848084                IF ( .NOT. salsa_gases_from_chem ) THEN
    80858085                   DO  ig = 1, ngases_salsa
    8086                       salsa_gas(ig)%conc_p(k+kb,j,i) = salsa_gas(ig)%conc_p(k,j,i)
     8086                      salsa_gas(ig)%conc_p(k+bc_h(l)%koff,j,i) =               &
     8087                                               salsa_gas(ig)%conc_p(k,j,i)
    80878088                   ENDDO
    80888089                ENDIF
Note: See TracChangeset for help on using the changeset viewer.