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

    r684 r707  
    55! Current revisions:
    66! -----------------
    7 !
     7! +bc_lr_dirrad, bc_lr_raddir, bc_ns_dirrad, bc_ns_raddir, left_border_pe,
     8! north_border_pe, right_border_pe, south_border_pe
     9! p_sub renamed p_loc
    810!
    911! Former revisions:
     
    261263    REAL, DIMENSION(:,:,:), ALLOCATABLE ::                                     &
    262264          canopy_heat_flux, cdc, d, diss, lad_s, lad_u, lad_v, lad_w, lai,     &
    263           l_wall, p_sub, sec, sls, tend, u_m_l, u_m_n, u_m_r, u_m_s, v_m_l,    &
     265          l_wall, p_loc, sec, sls, tend, u_m_l, u_m_n, u_m_r, u_m_s, v_m_l,    &
    264266          v_m_n, v_m_r, v_m_s, w_m_l, w_m_n, w_m_r, w_m_s
    265267
     
    481483
    482484    LOGICAL ::  adjust_mixing_length = .FALSE., avs_output = .FALSE., &
    483                 bc_lr_cyc =.TRUE., bc_ns_cyc = .TRUE., &
     485                bc_lr_cyc =.TRUE., bc_lr_dirrad = .FALSE., &
     486                bc_lr_raddir = .FALSE., bc_ns_cyc = .TRUE., &
     487                bc_ns_dirrad = .FALSE., bc_ns_raddir = .FALSE., &
    484488                call_psolver_at_all_substeps = .TRUE., &
    485489                cloud_droplets = .FALSE., cloud_physics = .FALSE., &
     
    12311235    INTEGER, DIMENSION(:), ALLOCATABLE ::  ngp_yz, type_xz, type_yz
    12321236
    1233     LOGICAL ::  collective_wait = .FALSE., reorder = .TRUE., &
     1237    LOGICAL ::  collective_wait = .FALSE., left_border_pe  = .FALSE.,  &
     1238                north_border_pe = .FALSE., reorder = .TRUE.,           &
     1239                right_border_pe = .FALSE., south_border_pe = .TRUE.,   &
    12341240                synchronous_exchange = .FALSE.
     1241
    12351242    LOGICAL, DIMENSION(2) ::  cyclic = (/ .TRUE. , .TRUE. /), &
    12361243                              remain_dims
Note: See TracChangeset for help on using the changeset viewer.