Ignore:
Timestamp:
Oct 7, 2016 2:08:57 PM (8 years ago)
Author:
suehring
Message:

Bugfix, restore flags for nest boundaries in multigrid solver; bugfix: setting Neumann boundary conditions for topography arrays in case of non-cyclic boundary conditions

File:
1 edited

Legend:

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

    r2001 r2021  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Bugfix: setting Neumann boundary conditions for topography required for
     23! topography flags in multigrid_noopt solver
    2324!
    2425! Former revisions:
     
    211212               io_blocks, io_group, inflow_l, inflow_n, inflow_r, inflow_s,    &
    212213               masking_method, maximum_grid_level, message_string,             &
    213                momentum_advec, nest_domain, ocean, outflow_l, outflow_n,       &
     214               momentum_advec, nest_domain, nest_bound_l, nest_bound_n,        &
     215               nest_bound_r, nest_bound_s, ocean, outflow_l, outflow_n,        &
    214216               outflow_r, outflow_s, psolver, scalar_advec, topography,        &
    215217               topography_grid_convention, use_surface_fluxes, use_top_fluxes, &
    216                wall_adjustment_factor 
    217        
     218               wall_adjustment_factor
     219         
    218220    USE grid_variables,                                                        &
    219221        ONLY:  ddx, ddx2, ddx2_mg, ddy, ddy2, ddy2_mg, dx, dx2, dy, dy2, fwxm, &
     
    13431345!--          Set non-cyclic boundary conditions on respective multigrid level
    13441346             IF ( .NOT. bc_ns_cyc )  THEN
    1345                 IF ( nys == 0  )  THEN
     1347                IF ( inflow_s .OR. outflow_s .OR. nest_bound_s  )  THEN
    13461348                   nzb_tmp(-2,:) = nzb_tmp(0,:)
    13471349                   nzb_tmp(-1,:) = nzb_tmp(0,:)
    13481350                ENDIF
    1349                 IF ( nyn == ny )  THEN
    1350                    nzb_tmp(ny+2,:) = nzb_tmp(ny,:)
    1351                    nzb_tmp(ny+1,:) = nzb_tmp(ny,:)
     1351                IF ( inflow_n .OR. outflow_n .OR. nest_bound_n )  THEN
     1352                   nzb_tmp(nyn_l+2,:) = nzb_tmp(nyn_l,:)
     1353                   nzb_tmp(nyn_l+1,:) = nzb_tmp(nyn_l,:)
    13521354                ENDIF
    13531355             ENDIF
    13541356             IF ( .NOT. bc_lr_cyc )  THEN
    1355                 IF ( nxl == 0  )  THEN
     1357                IF ( inflow_l .OR. outflow_l .OR. nest_bound_l  )  THEN
    13561358                   nzb_tmp(:,-2) = nzb_tmp(:,0)
    13571359                   nzb_tmp(:,-1) = nzb_tmp(:,0)
    13581360                ENDIF
    1359                 IF ( nxr == nx )  THEN
    1360                    nzb_tmp(:,nx+1) = nzb_tmp(:,nx)   
    1361                    nzb_tmp(:,nx+2) = nzb_tmp(:,nx)     
     1361                IF ( inflow_r .OR. outflow_r .OR. nest_bound_r )  THEN
     1362                   nzb_tmp(:,nxr_l+1) = nzb_tmp(:,nxr_l)   
     1363                   nzb_tmp(:,nxr_l+2) = nzb_tmp(:,nxr_l)     
    13621364                ENDIF       
    13631365             ENDIF
     
    14201422!
    14211423!-- Allocate flags needed for masking walls. Even though these flags are only
    1422 !-- required in the ws-scheme, the arrays need to be allocated as they are
     1424!-- required in the ws-scheme, the arrays need to be allocated here as they are
    14231425!-- used in OpenACC directives.
    14241426    ALLOCATE( wall_flags_0(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                     &
     
    14271429    wall_flags_00 = 0
    14281430!
    1429 !-- Init flags for ws-scheme to degrade order near walls
     1431!-- Init flags for ws-scheme to degrade order of the numerics near walls, i.e.
     1432!-- to decrease the numerical stencil appropriately.
    14301433    IF ( momentum_advec == 'ws-scheme'  .OR.  scalar_advec == 'ws-scheme'  .OR.&
    14311434         scalar_advec   == 'ws-scheme-mono' )  THEN
Note: See TracChangeset for help on using the changeset viewer.