|
Packit |
0848f5 |
! This file created from test/mpi/f77/coll/inplacef.f with f77tof90
|
|
Packit |
0848f5 |
! -*- Mode: Fortran; -*-
|
|
Packit |
0848f5 |
!
|
|
Packit |
0848f5 |
! (C) 2005 by Argonne National Laboratory.
|
|
Packit |
0848f5 |
! See COPYRIGHT in top-level directory.
|
|
Packit |
0848f5 |
!
|
|
Packit |
0848f5 |
! This is a simple test that Fortran support the MPI_IN_PLACE value
|
|
Packit |
0848f5 |
!
|
|
Packit |
0848f5 |
program main
|
|
Packit |
0848f5 |
use mpi
|
|
Packit |
0848f5 |
integer ierr, errs
|
|
Packit |
0848f5 |
integer comm, root
|
|
Packit |
0848f5 |
integer rank, size
|
|
Packit |
0848f5 |
integer i
|
|
Packit |
0848f5 |
integer MAX_SIZE
|
|
Packit |
0848f5 |
parameter (MAX_SIZE=1024)
|
|
Packit |
0848f5 |
integer rbuf(MAX_SIZE), rdispls(MAX_SIZE), rcount(MAX_SIZE), &
|
|
Packit |
0848f5 |
& sbuf(MAX_SIZE)
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
errs = 0
|
|
Packit |
0848f5 |
call mtest_init( ierr )
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
comm = MPI_COMM_WORLD
|
|
Packit |
0848f5 |
call mpi_comm_rank( comm, rank, ierr )
|
|
Packit |
0848f5 |
call mpi_comm_size( comm, size, ierr )
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
root = 0
|
|
Packit |
0848f5 |
! Gather with inplace
|
|
Packit |
0848f5 |
do i=1,size
|
|
Packit |
0848f5 |
rbuf(i) = - i
|
|
Packit |
0848f5 |
enddo
|
|
Packit |
0848f5 |
rbuf(1+root) = root
|
|
Packit |
0848f5 |
if (rank .eq. root) then
|
|
Packit |
0848f5 |
call mpi_gather( MPI_IN_PLACE, 1, MPI_INTEGER, rbuf, 1, &
|
|
Packit |
0848f5 |
& MPI_INTEGER, root, comm, ierr )
|
|
Packit |
0848f5 |
do i=1,size
|
|
Packit |
0848f5 |
if (rbuf(i) .ne. i-1) then
|
|
Packit |
0848f5 |
errs = errs + 1
|
|
Packit |
0848f5 |
print *, '[',rank,'] rbuf(', i, ') = ', rbuf(i), &
|
|
Packit |
0848f5 |
& ' in gather'
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
enddo
|
|
Packit |
0848f5 |
else
|
|
Packit |
0848f5 |
call mpi_gather( rank, 1, MPI_INTEGER, rbuf, 1, MPI_INTEGER, &
|
|
Packit |
0848f5 |
& root, comm, ierr )
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
! Gatherv with inplace
|
|
Packit |
0848f5 |
do i=1,size
|
|
Packit |
0848f5 |
rbuf(i) = - i
|
|
Packit |
0848f5 |
rcount(i) = 1
|
|
Packit |
0848f5 |
rdispls(i) = i-1
|
|
Packit |
0848f5 |
enddo
|
|
Packit |
0848f5 |
rbuf(1+root) = root
|
|
Packit |
0848f5 |
if (rank .eq. root) then
|
|
Packit |
0848f5 |
call mpi_gatherv( MPI_IN_PLACE, 1, MPI_INTEGER, rbuf, rcount, &
|
|
Packit |
0848f5 |
& rdispls, MPI_INTEGER, root, comm, ierr )
|
|
Packit |
0848f5 |
do i=1,size
|
|
Packit |
0848f5 |
if (rbuf(i) .ne. i-1) then
|
|
Packit |
0848f5 |
errs = errs + 1
|
|
Packit |
0848f5 |
print *, '[', rank, '] rbuf(', i, ') = ', rbuf(i), &
|
|
Packit |
0848f5 |
& ' in gatherv'
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
enddo
|
|
Packit |
0848f5 |
else
|
|
Packit |
0848f5 |
call mpi_gatherv( rank, 1, MPI_INTEGER, rbuf, rcount, rdispls, &
|
|
Packit |
0848f5 |
& MPI_INTEGER, root, comm, ierr )
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
! Scatter with inplace
|
|
Packit |
0848f5 |
do i=1,size
|
|
Packit |
0848f5 |
sbuf(i) = i
|
|
Packit |
0848f5 |
enddo
|
|
Packit |
0848f5 |
rbuf(1) = -1
|
|
Packit |
0848f5 |
if (rank .eq. root) then
|
|
Packit |
0848f5 |
call mpi_scatter( sbuf, 1, MPI_INTEGER, MPI_IN_PLACE, 1, &
|
|
Packit |
0848f5 |
& MPI_INTEGER, root, comm, ierr )
|
|
Packit |
0848f5 |
else
|
|
Packit |
0848f5 |
call mpi_scatter( sbuf, 1, MPI_INTEGER, rbuf, 1, &
|
|
Packit |
0848f5 |
& MPI_INTEGER, root, comm, ierr )
|
|
Packit |
0848f5 |
if (rbuf(1) .ne. rank+1) then
|
|
Packit |
0848f5 |
errs = errs + 1
|
|
Packit |
0848f5 |
print *, '[', rank, '] rbuf = ', rbuf(1), &
|
|
Packit |
0848f5 |
& ' in scatter'
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
call mtest_finalize( errs )
|
|
Packit |
0848f5 |
call mpi_finalize( ierr )
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
end
|