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

    r668 r707  
    44! Current revisions:
    55! -----------------
    6 ! Calls of exchange_horiz are modified.
    7 ! Adaption to slooping surface.
     6! bc_lr/ns replaced by bc_lr/ns_cyc,
     7! calls of exchange_horiz are modified,
     8! adaption to slooping surface,
    89!
    910! Former revisions:
     
    234235!--       when a sloping surface is used
    235236          IF ( sloping_surface )  THEN
    236              IF ( nxl ==  0 ) pt(:,:,nxlg:nxl-1) = pt(:,:,nxlg:nxl-1) - pt_slope_offset
    237              IF ( nxr == nx )  pt(:,:,nxr+1:nxrg) = pt(:,:,nxr+1:nxrg) + pt_slope_offset
     237             IF ( nxl ==  0 )  pt(:,:,nxlg:nxl-1) = pt(:,:,nxlg:nxl-1) - &
     238                                                    pt_slope_offset
     239             IF ( nxr == nx )  pt(:,:,nxr+1:nxrg) = pt(:,:,nxr+1:nxrg) + &
     240                                                    pt_slope_offset
    238241          ENDIF
    239242
     
    255258                   CALL disturb_field( nzb_u_inner, tend, u )
    256259                   CALL disturb_field( nzb_v_inner, tend, v )
    257                 ELSEIF ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic' )  THEN
     260                ELSEIF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
    258261!
    259262!--                Runs with a non-cyclic lateral wall need perturbations
Note: See TracChangeset for help on using the changeset viewer.