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

    r669 r707  
    44! Current revisions:
    55! -----------------
     6! bc_lr/ns replaced by bc_lr/ns_cyc/dirrad/raddir
    67!
    78! ATTENTION: nnz_x undefined problem still has to be solved!!!!!!!!
     
    186187!
    187188!-- If necessary, set horizontal boundary conditions to non-cyclic
    188     IF ( bc_lr /= 'cyclic' )  cyclic(1) = .FALSE.
    189     IF ( bc_ns /= 'cyclic' )  cyclic(2) = .FALSE.
     189    IF ( .NOT. bc_lr_cyc )  cyclic(1) = .FALSE.
     190    IF ( .NOT. bc_ns_cyc )  cyclic(2) = .FALSE.
    190191
    191192!
     
    331332    nzt  = MIN( nz, nzta )
    332333    nnz  = nza
     334
     335!
     336!-- Set switches to define if the PE is situated at the border of the virtual
     337!-- processor grid
     338    IF ( nxl == 0 )   left_border_pe  = .TRUE.
     339    IF ( nxr == nx )  right_border_pe = .TRUE.
     340    IF ( nys == 0 )   south_border_pe = .TRUE.
     341    IF ( nyn == ny )  north_border_pe = .TRUE.
    333342
    334343!
     
    10661075!-- horizontal boundary conditions.
    10671076    IF ( pleft == MPI_PROC_NULL )  THEN
    1068        IF ( bc_lr == 'dirichlet/radiation' )  THEN
     1077       IF ( bc_lr_dirrad )  THEN
    10691078          inflow_l  = .TRUE.
    1070        ELSEIF ( bc_lr == 'radiation/dirichlet' )  THEN
     1079       ELSEIF ( bc_lr_raddir )  THEN
    10711080          outflow_l = .TRUE.
    10721081       ENDIF
     
    10741083
    10751084    IF ( pright == MPI_PROC_NULL )  THEN
    1076        IF ( bc_lr == 'dirichlet/radiation' )  THEN
     1085       IF ( bc_lr_dirrad )  THEN
    10771086          outflow_r = .TRUE.
    1078        ELSEIF ( bc_lr == 'radiation/dirichlet' )  THEN
     1087       ELSEIF ( bc_lr_raddir )  THEN
    10791088          inflow_r  = .TRUE.
    10801089       ENDIF
     
    10821091
    10831092    IF ( psouth == MPI_PROC_NULL )  THEN
    1084        IF ( bc_ns == 'dirichlet/radiation' )  THEN
     1093       IF ( bc_ns_dirrad )  THEN
    10851094          outflow_s = .TRUE.
    1086        ELSEIF ( bc_ns == 'radiation/dirichlet' )  THEN
     1095       ELSEIF ( bc_ns_raddir )  THEN
    10871096          inflow_s  = .TRUE.
    10881097       ENDIF
     
    10901099
    10911100    IF ( pnorth == MPI_PROC_NULL )  THEN
    1092        IF ( bc_ns == 'dirichlet/radiation' )  THEN
     1101       IF ( bc_ns_dirrad )  THEN
    10931102          inflow_n  = .TRUE.
    1094        ELSEIF ( bc_ns == 'radiation/dirichlet' )  THEN
     1103       ELSEIF ( bc_ns_raddir )  THEN
    10951104          outflow_n = .TRUE.
    10961105       ENDIF
     
    11221131
    11231132#else
    1124     IF ( bc_lr == 'dirichlet/radiation' )  THEN
     1133    IF ( bc_lr_dirrad )  THEN
    11251134       inflow_l  = .TRUE.
    11261135       outflow_r = .TRUE.
    1127     ELSEIF ( bc_lr == 'radiation/dirichlet' )  THEN
     1136    ELSEIF ( bc_lr_raddir )  THEN
    11281137       outflow_l = .TRUE.
    11291138       inflow_r  = .TRUE.
    11301139    ENDIF
    11311140
    1132     IF ( bc_ns == 'dirichlet/radiation' )  THEN
     1141    IF ( bc_ns_dirrad )  THEN
    11331142       inflow_n  = .TRUE.
    11341143       outflow_s = .TRUE.
    1135     ELSEIF ( bc_ns == 'radiation/dirichlet' )  THEN
     1144    ELSEIF ( bc_ns_raddir )  THEN
    11361145       outflow_n = .TRUE.
    11371146       inflow_s  = .TRUE.
Note: See TracChangeset for help on using the changeset viewer.