Ignore:
Timestamp:
Mar 29, 2011 11:39:40 AM (13 years ago)
Author:
raasch
Message:

New:
---

In case of multigrid method, on coarse grid levels, gathered data are
identically processed on all PEs (before, on PE0 only), so that the subsequent
scattering of data is not neccessary any more. (modules, init_pegrid, poismg)

Changed:


Calculation of weighted average of p is now handled in the same way
regardless of the number of ghost layers (advection scheme). (pres)

multigrid and sor method are using p_loc for iterative
advancements of pressure. p_sub removed. (init_3d_model, modules, poismg, pres, sor)

bc_lr and bc_ns replaced by bc_lr_dirrad, bc_lr_raddir, bc_ns_dirrad, bc_ns_raddir
for speed optimization. (calc_spectra, check_parameters, exchange_horiz,
exchange_horiz_2d, header, init_3d_model, init_grid, init_pegrid, modules,
poismg, pres, sor, time_integration, timestep)

grid_level directly used as index for MPI data type arrays. (exchange_horiz,
poismg)

initial assignments of zero to array p for iterative solvers only (init_3d_model)

Errors:


localsum calculation modified for proper OpenMP reduction. (pres)

Bugfix: bottom (nzb) and top (nzt+1) boundary conditions set in routines
resid and restrict. They were missed before, which may have led to
unpredictable results. (poismg)

File:
1 edited

Legend:

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

    r703 r707  
    44! Current revisions:
    55! -----------------
     6! bc_lr/ns replaced by bc_lr/ns_cyc
    67!
    78! Former revisions:
     
    104105!
    105106!-- Lateral boundary conditions in the non-parallel case
    106     IF ( bc_lr == 'cyclic' )  THEN
    107        ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
    108        ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
    109     ENDIF
    110 
    111     IF ( bc_ns == 'cyclic' )  THEN
     107    IF ( bc_lr_cyc )  THEN
     108       ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
     109       ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
     110    ENDIF
     111
     112    IF ( bc_ns_cyc )  THEN
    112113       ar(nysg:nys-1,:) = ar(nyn-nbgp+1:nyn,:)
    113114       ar(nyn+1:nyng,:) = ar(nys:nys+nbgp-1,:)
     
    222223!
    223224!-- Lateral boundary conditions in the non-parallel case
    224     IF ( bc_lr == 'cyclic' )  THEN
    225        ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
    226        ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
    227     ENDIF
    228 
    229     IF ( bc_ns == 'cyclic' )  THEN
     225    IF ( bc_lr_cyc )  THEN
     226       ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
     227       ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
     228    ENDIF
     229
     230    IF ( bc_ns_cyc )  THEN
    230231       ar(nysg:nys-1,:) = ar(nyn+1-nbgp:nyn,:)
    231232       ar(nyn+1:nyng,:) = ar(nys:nys-1+nbgp,:)
Note: See TracChangeset for help on using the changeset viewer.