|
Packit Service |
c5cf8c |
! This file created from f77/coll/alltoallwf.f with f77tof90
|
|
Packit Service |
c5cf8c |
! -*- Mode: Fortran; -*-
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
! (C) 2003 by Argonne National Laboratory.
|
|
Packit Service |
c5cf8c |
! See COPYRIGHT in top-level directory.
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
program main
|
|
Packit Service |
c5cf8c |
use mpi
|
|
Packit Service |
c5cf8c |
integer ierr, errs
|
|
Packit Service |
c5cf8c |
integer i, intsize, ans, size, rank, color, comm, newcomm
|
|
Packit Service |
c5cf8c |
integer maxSize
|
|
Packit Service |
c5cf8c |
parameter (maxSize=32)
|
|
Packit Service |
c5cf8c |
integer scounts(maxSize), sdispls(maxSize), stypes(maxSize)
|
|
Packit Service |
c5cf8c |
integer rcounts(maxSize), rdispls(maxSize), rtypes(maxSize)
|
|
Packit Service |
c5cf8c |
integer sbuf(maxSize), rbuf(maxSize)
|
|
Packit Service |
c5cf8c |
errs = 0
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
call mtest_init( ierr )
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
call mpi_type_size( MPI_INTEGER, intsize, ierr )
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
! Get a comm
|
|
Packit Service |
c5cf8c |
call mpi_comm_dup( MPI_COMM_WORLD, comm, ierr )
|
|
Packit Service |
c5cf8c |
call mpi_comm_size( comm, size, ierr )
|
|
Packit Service |
c5cf8c |
if (size .gt. maxSize) then
|
|
Packit Service |
c5cf8c |
call mpi_comm_rank( comm, rank, ierr )
|
|
Packit Service |
c5cf8c |
color = 1
|
|
Packit Service |
c5cf8c |
if (rank .lt. maxSize) color = 0
|
|
Packit Service |
c5cf8c |
call mpi_comm_split( comm, color, rank, newcomm, ierr )
|
|
Packit Service |
c5cf8c |
call mpi_comm_free( comm, ierr )
|
|
Packit Service |
c5cf8c |
comm = newcomm
|
|
Packit Service |
c5cf8c |
call mpi_comm_size( comm, size, ierr )
|
|
Packit Service |
c5cf8c |
endif
|
|
Packit Service |
c5cf8c |
call mpi_comm_rank( comm, rank, ierr )
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
if (size .le. maxSize) then
|
|
Packit Service |
c5cf8c |
! Initialize the data. Just use this as an all to all
|
|
Packit Service |
c5cf8c |
do i=1, size
|
|
Packit Service |
c5cf8c |
scounts(i) = 1
|
|
Packit Service |
c5cf8c |
sdispls(i) = (i-1)*intsize
|
|
Packit Service |
c5cf8c |
stypes(i) = MPI_INTEGER
|
|
Packit Service |
c5cf8c |
sbuf(i) = rank * size + i
|
|
Packit Service |
c5cf8c |
rcounts(i) = 1
|
|
Packit Service |
c5cf8c |
rdispls(i) = (i-1)*intsize
|
|
Packit Service |
c5cf8c |
rtypes(i) = MPI_INTEGER
|
|
Packit Service |
c5cf8c |
rbuf(i) = -1
|
|
Packit Service |
c5cf8c |
enddo
|
|
Packit Service |
c5cf8c |
call mpi_alltoallw( sbuf, scounts, sdispls, stypes, &
|
|
Packit Service |
c5cf8c |
& rbuf, rcounts, rdispls, rtypes, comm, ierr )
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
! check rbuf(i) = data from the ith location of the ith send buf, or
|
|
Packit Service |
c5cf8c |
! rbuf(i) = (i-1) * size + i
|
|
Packit Service |
c5cf8c |
do i=1, size
|
|
Packit Service |
c5cf8c |
ans = (i-1) * size + rank + 1
|
|
Packit Service |
c5cf8c |
if (rbuf(i) .ne. ans) then
|
|
Packit Service |
c5cf8c |
errs = errs + 1
|
|
Packit Service |
c5cf8c |
print *, rank, ' rbuf(', i, ') = ', rbuf(i), &
|
|
Packit Service |
c5cf8c |
& ' expected ', ans
|
|
Packit Service |
c5cf8c |
endif
|
|
Packit Service |
c5cf8c |
enddo
|
|
Packit Service |
c5cf8c |
endif
|
|
Packit Service |
c5cf8c |
call mpi_comm_free( comm, ierr )
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
call mtest_finalize( errs )
|
|
Packit Service |
c5cf8c |
end
|
|
Packit Service |
c5cf8c |
|