Ignore:
Timestamp:
Jun 10, 2016 12:06:59 PM (8 years ago)
Author:
suehring
Message:

Rename multigrid into multigrid_noopt and multigrid_fast into multigrid, subroutines poismg is renamed into poismg_noopt and poismg_fast_mod into poismg_mod

File:
1 edited

Legend:

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

    r1911 r1931  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Rename multigrid into multigrid_noopt and multigrid_fast into multigrid
    2222!
    2323! Former revisions:
     
    225225    INTEGER(iwp) ::  cyn     !< index for north canyon wall
    226226    INTEGER(iwp) ::  cys     !< index for south canyon wall
    227     INTEGER(iwp) ::  gls     !< number of lateral ghost points at total model
    228                              !< domain boundaries required for multigrid solver
     227    INTEGER(iwp) ::  gls     !< number of lateral ghost points at total model domain boundaries required for multigrid solver
    229228    INTEGER(iwp) ::  i       !< index variable along x
    230229    INTEGER(iwp) ::  ii      !< loop variable for reading topography file
     
    242241
    243242    INTEGER(iwp), DIMENSION(:), ALLOCATABLE   ::                               &
    244                      vertical_influence  !< number of vertical grid points above
    245                                          !< obstacle where adjustment of near-
    246                                          !< wall mixing length is required
     243                     vertical_influence  !< number of vertical grid points above obstacle where adjustment of near-wall mixing length is required
    247244                                         
    248     INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  corner_nl  !< index of
    249                                          !< north-left corner location to limit
    250                                          !< near-wall mixing length
     245    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  corner_nl  !< index of north-left corner location to limit near-wall mixing length
    251246    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  corner_nr  !< north-right
    252247    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  corner_sl  !< south-left
    253248    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  corner_sr  !< south-right
    254     INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  wall_l     !< distance to
    255                                                              !< adjacent left-facing
     249    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  wall_l     !< distance to adjacent left-facing
    256250                                                             !< wall
    257251    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  wall_n     !< north-facing
     
    260254    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_local  !< index for topography
    261255                                                             !< top at cell-center
    262     INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_tmp    !< dummy to calculate
    263                                                              !< topography indices
    264                                                              !< on u- and v-grid
     256    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_tmp    !< dummy to calculate topography indices on u- and v-grid
    265257
    266258    LOGICAL  :: flag_set = .FALSE.  !< steering variable for advection flags
     
    270262    REAL(wp) ::  dz_stretched  !< stretched vertical grid spacing
    271263
    272     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  topo_height  !< input variable for
    273                                                            !< topography height
     264    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  topo_height  !< input variable for topography height
    274265
    275266   
     
    11381129
    11391130!
    1140 !-- Calculate wall flag arrays for the multigrid method
    1141     IF ( psolver(1:9) == 'multigrid' )  THEN
     1131!-- Calculate wall flag arrays for the multigrid method.
     1132!-- Please note, wall flags are only applied in the not cache-optimized
     1133!-- version.
     1134    IF ( psolver == 'multigrid_noopt' )  THEN
    11421135!
    11431136!--    Gridpoint increment of the current level
     
    11931186!--       In case of masking method, flags are not set and multigrid method
    11941187!--       works like FFT-solver
    1195           IF ( psolver == 'multigrid' .AND. .NOT. masking_method )  THEN
     1188          IF ( .NOT. masking_method )  THEN
    11961189
    11971190             DO  i = nxl_l-1, nxr_l+1
Note: See TracChangeset for help on using the changeset viewer.