Ignore:
Timestamp:
Jul 22, 2019 5:00:34 PM (5 years ago)
Author:
suehring
Message:

Control discretization of advection term: separate initialization of WS advection flags for momentum and scalars. In this context, resort the bits and do some minor formatting; Make initialization of scalar-advection flags more flexible, i.e. introduce an arguemnt list to indicate non-cyclic boundaries (required for decycled scalars such as chemical species or aerosols); Introduce extended 'degradation zones', where horizontal advection of passive scalars is discretized by first-order scheme at all grid points that in the vicinity of buildings (<= 3 grid points). Even though no building is within the numerical stencil, first-order scheme is used. At fourth and fifth grid point the order of the horizontal advection scheme is successively upgraded. These extended degradation zones are used to avoid stationary numerical oscillations, which are responsible for high concentration maxima that may appear under shear-free stable conditions. Therefore, an additional 3D interger array used to store control flags is introduced; Change interface for scalar advection routine; Bugfix, avoid uninitialized value sk_num in vector version of WS scalar advection; Chemistry: Decycling boundary conditions are only set at the ghost points not on the prognostic grid points; Land-surface model: Relax checks for non-consistent initialization in case static or dynamic input is provided. For example, soil_temperature or deep_soil_temperature is not mandatory any more if dynamic input is available. Also, improper settings of x_type in namelist are only checked if no static file is available.

File:
1 edited

Legend:

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

    r3927 r4109  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! - Separate initialization of advection flags for momentum and scalars.
     23! - Change subroutine interface for ws_init_flags_scalar to pass boundary flags
    2324!
    2425! Former revisions:
     
    373374 
    374375    USE advec_ws,                                                              &
    375         ONLY:  ws_init_flags
     376        ONLY:  ws_init_flags_momentum, ws_init_flags_scalar
    376377
    377378    USE arrays_3d,                                                             &
     
    380381    USE control_parameters,                                                    &
    381382        ONLY:  bc_lr_cyc, bc_ns_cyc,                                           &
     383               bc_dirichlet_l,                                                 &
     384               bc_dirichlet_n,                                                 &
     385               bc_dirichlet_r,                                                 &
     386               bc_dirichlet_s,                                                 &
     387               bc_radiation_l,                                                 &
     388               bc_radiation_n,                                                 &
     389               bc_radiation_r,                                                 &
     390               bc_radiation_s,                                                 &
    382391               constant_flux_layer, dz, dz_max, dz_stretch_factor,             &
    383392               dz_stretch_factor_array, dz_stretch_level, dz_stretch_level_end,&
     
    392401       
    393402    USE indices,                                                               &
    394         ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg, nz,   &
     403        ONLY:  advc_flags_m,                                                   &
     404               advc_flags_s,                                                   &
     405               nbgp, nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg, nz,   &
    395406               nzb, nzb_diff, nzb_diff_s_inner, nzb_diff_s_outer,              &
    396407               nzb_max, nzb_s_inner, nzb_s_outer, nzb_u_inner,                 &
     
    845856!-- Calculate wall flag arrays for the multigrid method.
    846857!-- Please note, wall flags are only applied in the non-optimized version.
    847     IF ( psolver == 'multigrid_noopt' )  CALL poismg_noopt_init 
     858    IF ( psolver == 'multigrid_noopt' )  CALL poismg_noopt_init
    848859
    849860!
    850861!-- Init flags for ws-scheme to degrade order of the numerics near walls, i.e.
    851 !-- to decrease the numerical stencil appropriately.
    852     IF ( momentum_advec == 'ws-scheme'  .OR.  scalar_advec == 'ws-scheme' )    &
    853        CALL ws_init_flags
     862!-- to decrease the numerical stencil appropriately. The order of the scheme
     863!-- is degraded near solid walls as well as near non-cyclic inflow and outflow
     864!-- boundaries. Do this separately for momentum and scalars.
     865    IF ( momentum_advec == 'ws-scheme' )  THEN
     866       ALLOCATE( advc_flags_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     867       CALL ws_init_flags_momentum
     868    ENDIF
     869    IF ( scalar_advec == 'ws-scheme'   )  THEN
     870       ALLOCATE( advc_flags_s(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     871       advc_flags_s = 0
     872       
     873       CALL ws_init_flags_scalar( bc_dirichlet_l  .OR.  bc_radiation_l,        &
     874                                  bc_dirichlet_n  .OR.  bc_radiation_n,        &
     875                                  bc_dirichlet_r  .OR.  bc_radiation_r,        &
     876                                  bc_dirichlet_s  .OR.  bc_radiation_s,        &
     877                                  advc_flags_s )
     878    ENDIF
    854879
    855880!
     
    861886       DO  j = nys, nyn
    862887          DO  k = nzb, nzt + 1
    863              k_top = MAX( k_top, MERGE( k, 0,                                  &
    864                                         .NOT. BTEST( topo(k,j,i), 0 ) ) )
     888             k_top = MAX( k_top, MERGE( k, 0, .NOT. BTEST( topo(k,j,i), 0 ) ) )
    865889          ENDDO
    866890       ENDDO
     
    24962520    USE control_parameters,                                                    &
    24972521        ONLY:  bc_lr_cyc, bc_ns_cyc, constant_flux_layer, land_surface,        &
    2498                use_surface_fluxes, use_top_fluxes, urban_surface
     2522               scalar_advec, use_surface_fluxes, use_top_fluxes, urban_surface
    24992523
    25002524    USE indices,                                                               &
     
    27242748          wall_flags_0(nzt+1,j,i) = IBSET( wall_flags_0(nzt+1,j,i), 22 )
    27252749          wall_flags_0(nzt+1,j,i) = IBSET( wall_flags_0(nzt+1,j,i), 23 )
     2750!
     2751!--       Set flags indicating that topography is close by in horizontal
     2752!--       direction, i.e. flags that infold the topography. These will be used
     2753!--       to set advection flags for passive scalars, where due to large
     2754!--       gradients near buildings stationary numerical oscillations can produce
     2755!--       unrealistically high concentrations. This is only necessary if
     2756!--       WS-scheme is applied for scalar advection. Note, these flags will be
     2757!--       only used for passive scalars such as chemical species or aerosols.
     2758          IF ( scalar_advec == 'ws-scheme' )  THEN
     2759             DO k = nzb, nzt
     2760                IF ( BTEST( wall_flags_0(k,j,i), 0 )  .AND. (                   &
     2761                     ANY( .NOT. BTEST( wall_flags_0(k,j-3:j+3,i-1), 0 ) )  .OR.&
     2762                     ANY( .NOT. BTEST( wall_flags_0(k,j-3:j+3,i-2), 0 ) )  .OR.&
     2763                     ANY( .NOT. BTEST( wall_flags_0(k,j-3:j+3,i-3), 0 ) )  .OR.&
     2764                     ANY( .NOT. BTEST( wall_flags_0(k,j-3:j+3,i+1), 0 ) )  .OR.&
     2765                     ANY( .NOT. BTEST( wall_flags_0(k,j-3:j+3,i+2), 0 ) )  .OR.&
     2766                     ANY( .NOT. BTEST( wall_flags_0(k,j-3:j+3,i+3), 0 ) )  .OR.&
     2767                     ANY( .NOT. BTEST( wall_flags_0(k,j-1,i-3:i+3), 0 ) )  .OR.&
     2768                     ANY( .NOT. BTEST( wall_flags_0(k,j-2,i-3:i+3), 0 ) )  .OR.&
     2769                     ANY( .NOT. BTEST( wall_flags_0(k,j-3,i-3:i+3), 0 ) )  .OR.&
     2770                     ANY( .NOT. BTEST( wall_flags_0(k,j+1,i-3:i+3), 0 ) )  .OR.&
     2771                     ANY( .NOT. BTEST( wall_flags_0(k,j+2,i-3:i+3), 0 ) )  .OR.&
     2772                     ANY( .NOT. BTEST( wall_flags_0(k,j+3,i-3:i+3), 0 ) )      &
     2773                                                            ) )                &
     2774                   wall_flags_0(k,j,i) = IBSET( wall_flags_0(k,j,i), 31 )
     2775                     
     2776             ENDDO
     2777          ENDIF
    27262778       ENDDO
    27272779    ENDDO
Note: See TracChangeset for help on using the changeset viewer.