Ignore:
Timestamp:
Feb 27, 2020 3:24:30 PM (4 years ago)
Author:
raasch
Message:

serial (non-MPI) test case added, several bugfixes for the serial mode

File:
1 edited

Legend:

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

    r4414 r4429  
    2525! -----------------
    2626! $Id$
     27! bugfix: cpp-directives added for serial mode
     28!
     29! 4414 2020-02-19 20:16:04Z suehring
    2730! Remove double-declared use only construct.
    2831!
     
    11721175!> Gather subdomain data from all PEs.
    11731176!------------------------------------------------------------------------------!
     1177#if defined( __parallel )
    11741178    SUBROUTINE mg_gather_noopt( f2, f2_sub )
    11751179
     
    12071211
    12081212
    1209 #if defined( __parallel )
    12101213       CALL cpu_log( log_point_s(34), 'mg_gather_noopt', 'start' )
    12111214
     
    12421245
    12431246       CALL cpu_log( log_point_s(34), 'mg_gather_noopt', 'stop' )
    1244 #endif
    12451247       
    12461248    END SUBROUTINE mg_gather_noopt
    1247 
     1249#endif
    12481250
    12491251
     
    12541256!>       non-blocking communication
    12551257!------------------------------------------------------------------------------!
     1258#if defined( __parallel )
    12561259    SUBROUTINE mg_scatter_noopt( p2, p2_sub )
    12571260
     
    12671270
    12681271       IMPLICIT NONE
    1269 
    1270        INTEGER(iwp) ::  nwords  !<
    12711272
    12721273       REAL(wp), DIMENSION(nzb:nzt_mg(grid_level-1)+1,                         &
     
    12781279                           mg_loc_ind(1,myid)-1:mg_loc_ind(2,myid)+1) ::  p2_sub  !<
    12791280
    1280 !
    1281 !--    Find out the number of array elements of the subdomain array
    1282        nwords = SIZE( p2_sub )
    1283 
    1284 #if defined( __parallel )
     1281
    12851282       CALL cpu_log( log_point_s(35), 'mg_scatter_noopt', 'start' )
    12861283
     
    12891286
    12901287       CALL cpu_log( log_point_s(35), 'mg_scatter_noopt', 'stop' )
    1291 #endif
    12921288       
    12931289    END SUBROUTINE mg_scatter_noopt
     1290#endif
    12941291
    12951292
     
    13521349
    13531350       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  f2_sub  !<
     1351
     1352#if defined( __parallel )
    13541353       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  p2_sub  !<
     1354#endif
    13551355
    13561356!
     
    14371437!
    14381438!--          Gather all arrays from the subdomains on PE0
     1439#if defined( __parallel )
    14391440             CALL mg_gather_noopt( f2, f2_sub )
     1441#endif
    14401442
    14411443!
Note: See TracChangeset for help on using the changeset viewer.