Changeset 1931


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

Location:
palm/trunk/SOURCE
Files:
6 edited
2 moved

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/Makefile

    r1917 r1931  
    2020# Current revisions:
    2121# ------------------
    22 #
     22# poismg renamed poismg_noopt, poismg_fast_mod renamed poismg_mod
    2323#
    2424# Former revisions:
     
    310310        package_parin.f90 palm.f90 parin.f90 plant_canopy_model_mod.f90 pmc_interface_mod.f90 \
    311311        pmc_client_mod.f90 pmc_general_mod.f90 pmc_handle_communicator_mod.f90 \
    312         pmc_mpi_wrapper_mod.f90 pmc_server_mod.f90 poisfft_mod.f90 poismg.f90 \
    313         poismg_fast_mod.f90 pres.f90 print_1d.f90 production_e.f90 \
     312        pmc_mpi_wrapper_mod.f90 pmc_server_mod.f90 poisfft_mod.f90 poismg_mod.f90 \
     313        poismg_noopt.f90 pres.f90 print_1d.f90 production_e.f90 \
    314314        prognostic_equations.f90 progress_bar_mod.f90 radiation_model_mod.f90 \
    315315        random_function_mod.f90 random_gauss.f90 random_generator_parallel_mod.f90 \
     
    501501pmc_server_mod.o: pmc_general_mod.o pmc_handle_communicator_mod.o pmc_mpi_wrapper_mod.o
    502502poisfft_mod.o: modules.o cpulog_mod.o fft_xy_mod.o mod_kinds.o tridia_solver_mod.o
    503 poismg.o: modules.o cpulog_mod.o mod_kinds.o
    504 poismg_fast_mod.o: modules.o cpulog_mod.o mod_kinds.o
    505 pres.o: modules.o cpulog_mod.o mod_kinds.o poisfft_mod.o poismg_fast_mod.o
     503poismg_mod.o: modules.o cpulog_mod.o mod_kinds.o
     504poismg_noopt.o: modules.o cpulog_mod.o mod_kinds.o
     505pres.o: modules.o cpulog_mod.o mod_kinds.o poisfft_mod.o poismg_mod.o
    506506print_1d.o: modules.o cpulog_mod.o mod_kinds.o
    507507production_e.o: modules.o mod_kinds.o wall_fluxes.o
  • palm/trunk/SOURCE/check_parameters.f90

    r1930 r1931  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Rename multigrid into multigrid_noopt and multigrid_fast into multigrid
    2222!
    2323! Former revisions:
     
    829829!-- Pressure solver:
    830830    IF ( psolver /= 'poisfft'  .AND.  psolver /= 'sor'  .AND.                  &
    831          psolver /= 'multigrid'  .AND.  psolver /= 'multigrid_fast' )  THEN
     831         psolver /= 'multigrid'  .AND.  psolver /= 'multigrid_noopt' )  THEN
    832832       message_string = 'unknown solver for perturbation pressure: psolver' // &
    833833                        ' = "' // TRIM( psolver ) // '"'
  • palm/trunk/SOURCE/cpulog_mod.f90

    r1851 r1931  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Adjustment in character length and format statement
    2222!
    2323! Former revisions:
     
    155155       REAL(wp)           ::  vector     !<
    156156       INTEGER(iwp)       ::  counts     !<
    157        CHARACTER (LEN=20) ::  place      !<
     157       CHARACTER (LEN=25) ::  place      !<
    158158    END TYPE logpoint
    159159
     
    550550   101 FORMAT (/'special measures:'/ &
    551551               &'-----------------------------------------------------------', &
    552                &'--------------------')
    553 
    554    102 FORMAT (A20,2X,F9.3,2X,F7.2,1X,I7,3(1X,F9.3))
     552               &'------------------------')
     553
     554   102 FORMAT (A25,2X,F9.3,2X,F7.2,1X,I7,3(1X,F9.3))
    555555   103 FORMAT (/'Barriers are set in front of collective operations')
    556556   104 FORMAT (/'No barriers are set in front of collective operations')
     
    560560   108 FORMAT ('Accelerator boards per node: ',14X,I2)
    561561   109 FORMAT ('Accelerator boards: ',23X,I2)
    562    110 FORMAT ('----------------------------------------------------------',   &
    563                &'------------'//&
    564                &'place:                        mean        counts      min  ', &
     562   110 FORMAT ('-------------------------------------------------------------',     &
     563               &'---------'//&
     564               &'place:                              mean        counts      min  ',&
    565565               &'     max       rms'/ &
    566                &'                           sec.      %                sec. ', &
     566               &'                                sec.      %                sec. ', &
    567567               &'     sec.      sec.'/  &
    568                &'-----------------------------------------------------------', &
    569                &'-------------------')
     568               &'-----------------------------------------------------------',      &
     569               &'------------------------')
    570570   111 FORMAT (/'Barriers are set at beginning (start/continue) of measurements')
    571571
  • palm/trunk/SOURCE/header.f90

    r1903 r1931  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Rename multigrid into multigrid_noopt
    2222!
    2323! Former revisions:
     
    553553                             nzt_mg(1)
    554554       ENDIF
    555        IF ( psolver == 'multigrid' .AND. masking_method )  WRITE ( io, 144 )
     555       IF ( psolver == 'multigrid_noopt' .AND. masking_method )  WRITE ( io, 144 )
    556556    ENDIF
    557557    IF ( call_psolver_at_all_substeps  .AND. timestep_scheme(1:5) == 'runge' ) &
  • 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
  • palm/trunk/SOURCE/poismg_mod.f90

    r1930 r1931  
    1 !> @file poismg_fast_mod.f90
     1!> @file poismg.f90
    22!--------------------------------------------------------------------------------!
    33! This file is part of PALM.
     
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Rename subroutines and cpu-measure log points to indicate default version
    2222!
    2323! Former revisions:
     
    9292    REAL(wp), DIMENSION(:,:), SAVE, ALLOCATABLE ::  f1_mg_b, f2_mg_b, f3_mg_b  !< blocked version of f1_mg ...
    9393
    94     INTERFACE poismg_fast
    95        MODULE PROCEDURE poismg_fast
    96     END INTERFACE poismg_fast
     94    INTERFACE poismg
     95       MODULE PROCEDURE poismg
     96    END INTERFACE poismg
    9797
    9898    INTERFACE sort_k_to_even_odd_blocks
     
    102102    END INTERFACE sort_k_to_even_odd_blocks
    103103
    104     PUBLIC poismg_fast
     104    PUBLIC poismg
    105105
    106106 CONTAINS
     
    112112!> V- or W-Cycle scheme.
    113113!------------------------------------------------------------------------------!
    114     SUBROUTINE poismg_fast( r )
     114    SUBROUTINE poismg( r )
    115115
    116116       USE arrays_3d,                                                          &
     
    140140
    141141
    142        CALL cpu_log( log_point_s(29), 'poismg_fast', 'start' )
     142       CALL cpu_log( log_point_s(29), 'poismg', 'start' )
    143143!
    144144!--    Initialize arrays and variables used in this subroutine
     
    198198                  mgcycles < maximum_mgcycles )
    199199 
    200           CALL next_mg_level_fast( d, p_loc, p3, r)
     200          CALL next_mg_level( d, p_loc, p3, r)
    201201
    202202!
     
    204204!--       cycles to be performed
    205205          IF ( maximum_mgcycles == 0 )  THEN
    206              CALL resid_fast( d, p_loc, r )
     206             CALL resid( d, p_loc, r )
    207207             maxerror = SUM( r(nzb+1:nzt,nys:nyn,nxl:nxr)**2 )
    208208
     
    224224          IF ( mgcycles > 1000  .AND.  mg_cycles == -1 )  THEN
    225225             message_string = 'no sufficient convergence within 1000 cycles'
    226              CALL message( 'poismg_fast', 'PA0283', 1, 2, 0, 6, 0 )
     226             CALL message( 'poismg', 'PA0283', 1, 2, 0, 6, 0 )
    227227          ENDIF
    228228
     
    238238       grid_level = 0
    239239
    240        CALL cpu_log( log_point_s(29), 'poismg_fast', 'stop' )
    241 
    242     END SUBROUTINE poismg_fast
     240       CALL cpu_log( log_point_s(29), 'poismg', 'stop' )
     241
     242    END SUBROUTINE poismg
    243243
    244244
     
    248248!> Computes the residual of the perturbation pressure.
    249249!------------------------------------------------------------------------------!
    250     SUBROUTINE resid_fast( f_mg, p_mg, r )
     250    SUBROUTINE resid( f_mg, p_mg, r )
    251251
    252252
     
    366366       CALL cpu_log( log_point_s(53), 'resid', 'stop' )
    367367
    368     END SUBROUTINE resid_fast
     368    END SUBROUTINE resid
    369369
    370370
     
    375375!> scheme
    376376!------------------------------------------------------------------------------!
    377     SUBROUTINE restrict_fast( f_mg, r )
     377    SUBROUTINE restrict( f_mg, r )
    378378
    379379
     
    503503       CALL sort_k_to_even_odd_blocks( f_mg , l)
    504504
    505     END SUBROUTINE restrict_fast
     505    END SUBROUTINE restrict
    506506
    507507
     
    512512!> to the next finer grid.
    513513!------------------------------------------------------------------------------!
    514     SUBROUTINE prolong_fast( p, temp )
     514    SUBROUTINE prolong( p, temp )
    515515
    516516
     
    670670       CALL cpu_log( log_point_s(55), 'prolong', 'stop' )
    671671
    672     END SUBROUTINE prolong_fast
     672    END SUBROUTINE prolong
    673673
    674674
     
    679679!> 3D-Red-Black decomposition (GS-RB) is used.
    680680!------------------------------------------------------------------------------!
    681     SUBROUTINE redblack_fast( f_mg, p_mg )
     681    SUBROUTINE redblack( f_mg, p_mg )
    682682
    683683
     
    981981       ENDDO
    982982
    983     END SUBROUTINE redblack_fast
     983    END SUBROUTINE redblack
    984984
    985985
     
    12361236!> Gather subdomain data from all PEs.
    12371237!------------------------------------------------------------------------------!
    1238     SUBROUTINE mg_gather_fast( f2, f2_sub )
     1238    SUBROUTINE mg_gather( f2, f2_sub )
    12391239
    12401240       USE control_parameters,                                                 &
     
    13071307#endif
    13081308   
    1309     END SUBROUTINE mg_gather_fast
     1309    END SUBROUTINE mg_gather
    13101310
    13111311
     
    13171317!>       non-blocking communication
    13181318!------------------------------------------------------------------------------!
    1319     SUBROUTINE mg_scatter_fast( p2, p2_sub )
     1319    SUBROUTINE mg_scatter( p2, p2_sub )
    13201320
    13211321       USE control_parameters,                                                 &
     
    13531353#endif
    13541354   
    1355     END SUBROUTINE mg_scatter_fast
     1355    END SUBROUTINE mg_scatter
    13561356
    13571357
     
    13661366!> but leads to an increase in computing time.
    13671367!------------------------------------------------------------------------------!
    1368     RECURSIVE SUBROUTINE next_mg_level_fast( f_mg, p_mg, p3, r )
     1368    RECURSIVE SUBROUTINE next_mg_level( f_mg, p_mg, p3, r )
    13691369
    13701370       USE control_parameters,                                                 &
     
    14251425          ind_even_odd = even_odd_level(grid_level)
    14261426
    1427           CALL redblack_fast( f_mg, p_mg )
     1427          CALL redblack( f_mg, p_mg )
    14281428
    14291429          ngsrb = ngsrb / 2
     
    14381438          ind_even_odd = even_odd_level(grid_level)
    14391439
    1440           CALL redblack_fast( f_mg, p_mg )
     1440          CALL redblack( f_mg, p_mg )
    14411441
    14421442!
    14431443!--       Determination of the actual residual
    1444           CALL resid_fast( f_mg, p_mg, r )
     1444          CALL resid( f_mg, p_mg, r )
    14451445
    14461446!--       Restriction of the residual (finer grid values!) to the next coarser
     
    14851485                              nxl_mg(grid_level)-1:nxr_mg(grid_level)+1) )
    14861486
    1487              CALL restrict_fast( f2_sub, r )
     1487             CALL restrict( f2_sub, r )
    14881488
    14891489!
     
    15011501!
    15021502!--          Gather all arrays from the subdomains on PE0
    1503              CALL mg_gather_fast( f2, f2_sub )
     1503             CALL mg_gather( f2, f2_sub )
    15041504
    15051505!
     
    15461546          ELSE
    15471547
    1548              CALL restrict_fast( f2, r )
     1548             CALL restrict( f2, r )
    15491549
    15501550             ind_even_odd = even_odd_level(grid_level)  ! must be after restrict
     
    15561556!
    15571557!--       Repeat the same procedure till the coarsest grid is reached
    1558           CALL next_mg_level_fast( f2, p2, p3, r )
     1558          CALL next_mg_level( f2, p2, p3, r )
    15591559
    15601560       ENDIF
     
    15771577                       mg_loc_ind(1,myid)-1:mg_loc_ind(2,myid)+1) )
    15781578
    1579              CALL mg_scatter_fast( p2, p2_sub )
     1579             CALL mg_scatter( p2, p2_sub )
    15801580
    15811581!
     
    16471647             ENDIF
    16481648
    1649              CALL prolong_fast( p2_sub, p3 )
     1649             CALL prolong( p2_sub, p3 )
    16501650
    16511651!
     
    16621662          ELSE
    16631663
    1664              CALL prolong_fast( p2, p3 )
     1664             CALL prolong( p2, p3 )
    16651665
    16661666          ENDIF
     
    16791679!
    16801680!--       Relaxation of the new solution
    1681           CALL redblack_fast( f_mg, p_mg )
     1681          CALL redblack( f_mg, p_mg )
    16821682
    16831683       ENDIF
     
    16981698
    16991699!
    1700 !--    Reset counter for the next call of poismg_fast
     1700!--    Reset counter for the next call of poismg
    17011701       grid_level_count(grid_level) = 0
    17021702
     
    17161716    20 CONTINUE
    17171717
    1718     END SUBROUTINE next_mg_level_fast
     1718    END SUBROUTINE next_mg_level
    17191719
    17201720
  • palm/trunk/SOURCE/poismg_noopt.f90

    r1930 r1931  
    1 !> @file poismg.f90
     1!> @file poismg_noopt.f90
    22!--------------------------------------------------------------------------------!
    33! This file is part of PALM.
     
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Rename subroutines and cpu-measure log points to indicate _noopt version
    2222!
    2323! Former revisions:
     
    129129!> @todo Further work required.
    130130!------------------------------------------------------------------------------!
    131  SUBROUTINE poismg( r )
     131 SUBROUTINE poismg_noopt( r )
    132132 
    133133
     
    162162
    163163
    164     CALL cpu_log( log_point_s(29), 'poismg', 'start' )
     164    CALL cpu_log( log_point_s(29), 'poismg_noopt', 'start' )
    165165!
    166166!-- Initialize arrays and variables used in this subroutine
     
    206206               mgcycles < maximum_mgcycles )
    207207 
    208        CALL next_mg_level( d, p_loc, p3, r)
     208       CALL next_mg_level_noopt( d, p_loc, p3, r)
    209209
    210210!
     
    212212!--    cycles to be performed
    213213       IF ( maximum_mgcycles == 0 )  THEN
    214           CALL resid( d, p_loc, r )
     214          CALL resid_noopt( d, p_loc, r )
    215215          maxerror = SUM( r(nzb+1:nzt,nys:nyn,nxl:nxr)**2 )
    216216
     
    232232       IF ( mgcycles > 1000  .AND.  mg_cycles == -1 )  THEN
    233233          message_string = 'no sufficient convergence within 1000 cycles'
    234           CALL message( 'poismg', 'PA0283', 1, 2, 0, 6, 0 )
     234          CALL message( 'poismg_noopt', 'PA0283', 1, 2, 0, 6, 0 )
    235235       ENDIF
    236236
     
    244244    grid_level = 0
    245245
    246     CALL cpu_log( log_point_s(29), 'poismg', 'stop' )
    247 
    248  END SUBROUTINE poismg
     246    CALL cpu_log( log_point_s(29), 'poismg_noopt', 'stop' )
     247
     248 END SUBROUTINE poismg_noopt
    249249
    250250
     
    254254!> Computes the residual of the perturbation pressure.
    255255!------------------------------------------------------------------------------!
    256  SUBROUTINE resid( f_mg, p_mg, r )
     256 SUBROUTINE resid_noopt( f_mg, p_mg, r )
    257257
    258258
     
    391391
    392392
    393  END SUBROUTINE resid
     393 END SUBROUTINE resid_noopt
    394394
    395395
     
    400400!> scheme.
    401401!------------------------------------------------------------------------------!
    402  SUBROUTINE restrict( f_mg, r )
     402 SUBROUTINE restrict_noopt( f_mg, r )
    403403
    404404
     
    607607
    608608
    609 END SUBROUTINE restrict
     609END SUBROUTINE restrict_noopt
    610610
    611611
     
    616616!> to the next finer grid.
    617617!------------------------------------------------------------------------------!
    618  SUBROUTINE prolong( p, temp )
     618 SUBROUTINE prolong_noopt( p, temp )
    619619
    620620
     
    722722
    723723 
    724  END SUBROUTINE prolong
     724 END SUBROUTINE prolong_noopt
    725725
    726726
     
    731731!> 3D-Red-Black decomposition (GS-RB) is used.
    732732!------------------------------------------------------------------------------!
    733  SUBROUTINE redblack( f_mg, p_mg )
     733 SUBROUTINE redblack_noopt( f_mg, p_mg )
    734734
    735735
     
    821821          IF ( .NOT. unroll )  THEN
    822822
    823              CALL cpu_log( log_point_s(36), 'redblack_no_unroll', 'start' )
     823             CALL cpu_log( log_point_s(36), 'redblack_no_unroll_noopt', 'start' )
    824824
    825825!
     
    923923                ENDDO
    924924             ENDDO
    925              CALL cpu_log( log_point_s(36), 'redblack_no_unroll', 'stop' )
     925             CALL cpu_log( log_point_s(36), 'redblack_no_unroll_noopt', 'stop' )
    926926
    927927          ELSE
     
    929929!
    930930!--          Loop unrolling along y, only one i loop for better cache use
    931              CALL cpu_log( log_point_s(38), 'redblack_unroll', 'start' )
     931             CALL cpu_log( log_point_s(38), 'redblack_unroll_noopt', 'start' )
    932932             DO  ic = nxl_mg(l), nxr_mg(l), 2
    933933                DO  jc = nys_mg(l), nyn_mg(l), 4
     
    10901090                ENDDO
    10911091             ENDDO
    1092              CALL cpu_log( log_point_s(38), 'redblack_unroll', 'stop' )
     1092             CALL cpu_log( log_point_s(38), 'redblack_unroll_noopt', 'stop' )
    10931093
    10941094          ENDIF
     
    11741174
    11751175
    1176  END SUBROUTINE redblack
     1176 END SUBROUTINE redblack_noopt
    11771177
    11781178
     
    11831183!> Gather subdomain data from all PEs.
    11841184!------------------------------------------------------------------------------!
    1185  SUBROUTINE mg_gather( f2, f2_sub )
     1185 SUBROUTINE mg_gather_noopt( f2, f2_sub )
    11861186
    11871187    USE control_parameters,                                                    &
     
    12221222
    12231223#if defined( __parallel )
    1224     CALL cpu_log( log_point_s(34), 'mg_gather', 'start' )
     1224    CALL cpu_log( log_point_s(34), 'mg_gather_noopt', 'start' )
    12251225
    12261226    f2_l = 0.0_wp
     
    12551255                        nwords, MPI_REAL, MPI_SUM, comm2d, ierr )
    12561256
    1257     CALL cpu_log( log_point_s(34), 'mg_gather', 'stop' )
     1257    CALL cpu_log( log_point_s(34), 'mg_gather_noopt', 'stop' )
    12581258#endif
    12591259   
    1260  END SUBROUTINE mg_gather
     1260 END SUBROUTINE mg_gather_noopt
    12611261
    12621262
     
    12681268!>       non-blocking communication
    12691269!------------------------------------------------------------------------------!
    1270  SUBROUTINE mg_scatter( p2, p2_sub )
     1270 SUBROUTINE mg_scatter_noopt( p2, p2_sub )
    12711271
    12721272    USE control_parameters,                                                    &
     
    13001300
    13011301#if defined( __parallel )
    1302     CALL cpu_log( log_point_s(35), 'mg_scatter', 'start' )
     1302    CALL cpu_log( log_point_s(35), 'mg_scatter_noopt', 'start' )
    13031303
    13041304    p2_sub = p2(:,mg_loc_ind(3,myid)-1:mg_loc_ind(4,myid)+1, &
    13051305                  mg_loc_ind(1,myid)-1:mg_loc_ind(2,myid)+1)
    13061306
    1307     CALL cpu_log( log_point_s(35), 'mg_scatter', 'stop' )
     1307    CALL cpu_log( log_point_s(35), 'mg_scatter_noopt', 'stop' )
    13081308#endif
    13091309   
    1310  END SUBROUTINE mg_scatter
     1310 END SUBROUTINE mg_scatter_noopt
    13111311
    13121312
     
    13211321!> but leads to an increase in computing time.
    13221322!------------------------------------------------------------------------------!
    1323  RECURSIVE SUBROUTINE next_mg_level( f_mg, p_mg, p3, r )
     1323 RECURSIVE SUBROUTINE next_mg_level_noopt( f_mg, p_mg, p3, r )
    13241324
    13251325    USE control_parameters,                                                    &
     
    13831383       ngsrb = 2 * ngsrb
    13841384
    1385        CALL redblack( f_mg, p_mg )
     1385       CALL redblack_noopt( f_mg, p_mg )
    13861386
    13871387       ngsrb = ngsrb / 2
     
    13941394!
    13951395!--    Solution on the actual grid level
    1396        CALL redblack( f_mg, p_mg )
     1396       CALL redblack_noopt( f_mg, p_mg )
    13971397
    13981398!
    13991399!--    Determination of the actual residual
    1400        CALL resid( f_mg, p_mg, r )
     1400       CALL resid_noopt( f_mg, p_mg, r )
    14011401
    14021402!
     
    14411441                           nxl_mg(grid_level)-1:nxr_mg(grid_level)+1) )
    14421442
    1443           CALL restrict( f2_sub, r )
     1443          CALL restrict_noopt( f2_sub, r )
    14441444
    14451445!
     
    14571457!
    14581458!--       Gather all arrays from the subdomains on PE0
    1459           CALL mg_gather( f2, f2_sub )
     1459          CALL mg_gather_noopt( f2, f2_sub )
    14601460
    14611461!
     
    15021502       ELSE
    15031503
    1504           CALL restrict( f2, r )
     1504          CALL restrict_noopt( f2, r )
    15051505
    15061506       ENDIF
     
    15101510!
    15111511!--    Repeat the same procedure till the coarsest grid is reached
    1512        CALL next_mg_level( f2, p2, p3, r )
     1512       CALL next_mg_level_noopt( f2, p2, p3, r )
    15131513
    15141514    ENDIF
     
    15311531                    mg_loc_ind(1,myid)-1:mg_loc_ind(2,myid)+1) )
    15321532
    1533           CALL mg_scatter( p2, p2_sub )
     1533          CALL mg_scatter_noopt( p2, p2_sub )
    15341534
    15351535!
     
    16011601          ENDIF
    16021602
    1603           CALL prolong( p2_sub, p3 )
     1603          CALL prolong_noopt( p2_sub, p3 )
    16041604
    16051605!
     
    16161616       ELSE
    16171617
    1618           CALL prolong( p2, p3 )
     1618          CALL prolong_noopt( p2, p3 )
    16191619
    16201620       ENDIF
     
    16331633!
    16341634!--    Relaxation of the new solution
    1635        CALL redblack( f_mg, p_mg )
     1635       CALL redblack_noopt( f_mg, p_mg )
    16361636
    16371637    ENDIF
     
    16521652
    16531653!
    1654 !-- Reset counter for the next call of poismg
     1654!-- Reset counter for the next call of poismg_noopt
    16551655    grid_level_count(grid_level) = 0
    16561656
     
    16681668 20 CONTINUE
    16691669
    1670  END SUBROUTINE next_mg_level
     1670 END SUBROUTINE next_mg_level_noopt
  • palm/trunk/SOURCE/pres.f90

    r1930 r1931  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! Rename multigrid into multigrid_noopt and multigrid_fast into multigrid
    2222!
    2323! Former revisions:
     
    570570          CALL poismg( tend )
    571571       ELSE
    572           CALL poismg_fast( tend )
     572          CALL poismg_noopt( tend )
    573573       ENDIF
    574574
Note: See TracChangeset for help on using the changeset viewer.