Ignore:
Timestamp:
Jul 9, 2019 6:04:41 PM (5 years ago)
Author:
suehring
Message:

Implementation of a monotonic flux limiter for vertical advection term in Wicker-Skamarock scheme. The flux limiter is currently only applied for passive scalars (passive scalar, chemical species, aerosols) within the region up to the highest topography, in order to avoid the built-up of large concentrations within poorly resolved cavities in urban environments. To enable the limiter monotonic_limiter_z = .T. must be set. Note, the limiter is currently only implemented for the cache-optimized version of advec_ws. Further changes in offline nesting: Set boundary condition for w at nzt+1 at all lateral boundaries (even though these won't enter the numerical solution), in order to avoid high vertical velocities in the run-control file which might built-up due to the mass-conservation; bugfix in offline nesting for chemical species

File:
1 edited

Legend:

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

    r4022 r4079  
    2525! -----------------
    2626! $Id$
     27! - Set boundary condition for w at nzt+1 at the lateral boundaries, even
     28!   though these won't enter the numerical solution. However, due to the mass
     29!   conservation these values might some up to very large values which will
     30!   occur in the run-control file
     31! - Bugfix in offline nesting of chemical species
     32! - Do not set Neumann conditions for TKE and passive scalar
     33!
     34! 4022 2019-06-12 11:52:39Z suehring
    2735! Detection of boundary-layer depth in stable boundary layer on basis of
    2836! boundary data improved
     
    353361                                   BTEST( wall_flags_0(k,j,-1), 3 ) )
    354362             ENDDO
     363             w(nzt,j,-1) = w(nzt-1,j,-1)
    355364          ENDDO
    356365
     
    427436                                    BTEST( wall_flags_0(k,j,nxr+1), 3 ) )
    428437             ENDDO
     438             w(nzt,j,nxr+1) = w(nzt-1,j,nxr+1)
    429439          ENDDO
    430440
     
    504514                                  BTEST( wall_flags_0(k,-1,i), 3 ) )
    505515             ENDDO
     516             w(nzt,-1,i) = w(nzt-1,-1,i)
    506517          ENDDO
    507518
     
    580591                                      BTEST( wall_flags_0(k,nyn+1,i), 3 ) )
    581592             ENDDO
     593             w(nzt,nyn+1,i) = w(nzt-1,nyn+1,i)
    582594          ENDDO
    583595
     
    710722                   DO  j = nys, nyn
    711723                      chem_species(n)%conc(nzt+1,j,i) = interpolate_in_time(   &
    712                                               nest_offl%chem_north(0,j,i,n),   &
    713                                               nest_offl%chem_north(1,j,i,n),   &
     724                                              nest_offl%chem_top(0,j,i,n),   &
     725                                              nest_offl%chem_top(1,j,i,n),   &
    714726                                              fac_dt                       )
    715727                   ENDDO
     
    727739          IF (  bc_dirichlet_n )  diss(:,nyn+1,:) = diss(:,nyn,:)
    728740       ENDIF
    729        IF ( .NOT. constant_diffusion )  THEN
    730           IF (  bc_dirichlet_l )  e(:,:,nxl-1) = e(:,:,nxl)
    731           IF (  bc_dirichlet_r )  e(:,:,nxr+1) = e(:,:,nxr)
    732           IF (  bc_dirichlet_s )  e(:,nys-1,:) = e(:,nys,:)
    733           IF (  bc_dirichlet_n )  e(:,nyn+1,:) = e(:,nyn,:)
    734           e(nzt+1,:,:) = e(nzt,:,:)
    735        ENDIF
    736        IF ( passive_scalar )  THEN
    737           IF (  bc_dirichlet_l )  s(:,:,nxl-1) = s(:,:,nxl)
    738           IF (  bc_dirichlet_r )  s(:,:,nxr+1) = s(:,:,nxr)
    739           IF (  bc_dirichlet_s )  s(:,nys-1,:) = s(:,nys,:)
    740           IF (  bc_dirichlet_n )  s(:,nyn+1,:) = s(:,nyn,:)
    741        ENDIF
     741!        IF ( .NOT. constant_diffusion )  THEN
     742!           IF (  bc_dirichlet_l )  e(:,:,nxl-1) = e(:,:,nxl)
     743!           IF (  bc_dirichlet_r )  e(:,:,nxr+1) = e(:,:,nxr)
     744!           IF (  bc_dirichlet_s )  e(:,nys-1,:) = e(:,nys,:)
     745!           IF (  bc_dirichlet_n )  e(:,nyn+1,:) = e(:,nyn,:)
     746!           e(nzt+1,:,:) = e(nzt,:,:)
     747!        ENDIF
     748!        IF ( passive_scalar )  THEN
     749!           IF (  bc_dirichlet_l )  s(:,:,nxl-1) = s(:,:,nxl)
     750!           IF (  bc_dirichlet_r )  s(:,:,nxr+1) = s(:,:,nxr)
     751!           IF (  bc_dirichlet_s )  s(:,nys-1,:) = s(:,nys,:)
     752!           IF (  bc_dirichlet_n )  s(:,nyn+1,:) = s(:,nyn,:)
     753!        ENDIF
    742754
    743755       CALL exchange_horiz( u, nbgp )
     
    755767          ENDDO
    756768       ENDIF
    757        
     769!
     770!--    Set top boundary condition at all horizontal grid points, also at the
     771!--    lateral boundary grid points.
     772       w(nzt+1,:,:) = w(nzt,:,:)       
    758773!
    759774!--    In case of Rayleigh damping, where the profiles u_init, v_init
Note: See TracChangeset for help on using the changeset viewer.