|
Packit Service |
c5cf8c |
! This file created from test/mpi/f77/coll/redscatf.f with f77tof90
|
|
Packit Service |
c5cf8c |
! -*- Mode: Fortran; -*-
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
! (C) 2011 by Argonne National Laboratory.
|
|
Packit Service |
c5cf8c |
! See COPYRIGHT in top-level directory.
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
subroutine uop( cin, cout, count, datatype )
|
|
Packit Service |
c5cf8c |
use mpi_f08
|
|
Packit Service |
c5cf8c |
integer cin(*), cout(*)
|
|
Packit Service |
c5cf8c |
integer count
|
|
Packit Service |
c5cf8c |
TYPE(MPI_Datatype) datatype
|
|
Packit Service |
c5cf8c |
integer i
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
if (datatype .ne. MPI_INTEGER) then
|
|
Packit Service |
c5cf8c |
write(6,*) 'Invalid datatype ',datatype,' passed to user_op()'
|
|
Packit Service |
c5cf8c |
return
|
|
Packit Service |
c5cf8c |
endif
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
do i=1, count
|
|
Packit Service |
c5cf8c |
cout(i) = cin(i) + cout(i)
|
|
Packit Service |
c5cf8c |
enddo
|
|
Packit Service |
c5cf8c |
end
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
! Test of reduce scatter.
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
! Each processor contributes its rank + the index to the reduction,
|
|
Packit Service |
c5cf8c |
! then receives the ith sum
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
! Can be called with any number of processors.
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
program main
|
|
Packit Service |
c5cf8c |
use mpi_f08
|
|
Packit Service |
c5cf8c |
integer errs, ierr, toterr
|
|
Packit Service |
c5cf8c |
integer maxsize
|
|
Packit Service |
c5cf8c |
parameter (maxsize=1024)
|
|
Packit Service |
c5cf8c |
integer sendbuf(maxsize), recvbuf, recvcounts(maxsize)
|
|
Packit Service |
c5cf8c |
integer size, rank, i, sumval
|
|
Packit Service |
c5cf8c |
TYPE(MPI_Comm) comm
|
|
Packit Service |
c5cf8c |
TYPE(MPI_Op) sumop
|
|
Packit Service |
c5cf8c |
external uop
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
errs = 0
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
call mtest_init( ierr )
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
comm = MPI_COMM_WORLD
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
call mpi_comm_size( comm, size, ierr )
|
|
Packit Service |
c5cf8c |
call mpi_comm_rank( comm, rank, ierr )
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
if (size .gt. maxsize) then
|
|
Packit Service |
c5cf8c |
endif
|
|
Packit Service |
c5cf8c |
do i=1, size
|
|
Packit Service |
c5cf8c |
sendbuf(i) = rank + i - 1
|
|
Packit Service |
c5cf8c |
recvcounts(i) = 1
|
|
Packit Service |
c5cf8c |
enddo
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
call mpi_reduce_scatter( sendbuf, recvbuf, recvcounts, &
|
|
Packit Service |
c5cf8c |
& MPI_INTEGER, MPI_SUM, comm, ierr )
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
sumval = size * rank + ((size - 1) * size)/2
|
|
Packit Service |
c5cf8c |
! recvbuf should be size * (rank + i)
|
|
Packit Service |
c5cf8c |
if (recvbuf .ne. sumval) then
|
|
Packit Service |
c5cf8c |
errs = errs + 1
|
|
Packit Service |
c5cf8c |
print *, "Did not get expected value for reduce scatter"
|
|
Packit Service |
c5cf8c |
print *, rank, " Got ", recvbuf, " expected ", sumval
|
|
Packit Service |
c5cf8c |
endif
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
call mpi_op_create( uop, .true., sumop, ierr )
|
|
Packit Service |
c5cf8c |
call mpi_reduce_scatter( sendbuf, recvbuf, recvcounts, &
|
|
Packit Service |
c5cf8c |
& MPI_INTEGER, sumop, comm, ierr )
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
sumval = size * rank + ((size - 1) * size)/2
|
|
Packit Service |
c5cf8c |
! recvbuf should be size * (rank + i)
|
|
Packit Service |
c5cf8c |
if (recvbuf .ne. sumval) then
|
|
Packit Service |
c5cf8c |
errs = errs + 1
|
|
Packit Service |
c5cf8c |
print *, "sumop: Did not get expected value for reduce scatter"
|
|
Packit Service |
c5cf8c |
print *, rank, " Got ", recvbuf, " expected ", sumval
|
|
Packit Service |
c5cf8c |
endif
|
|
Packit Service |
c5cf8c |
call mpi_op_free( sumop, ierr )
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
call mtest_finalize( errs )
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
end
|