|
Packit Service |
c5cf8c |
! This file created from test/mpi/f77/pt2pt/utilsf.f with f77tof90
|
|
Packit Service |
c5cf8c |
! -*- Mode: Fortran; -*-
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
! (C) 2012 by Argonne National Laboratory.
|
|
Packit Service |
c5cf8c |
! See COPYRIGHT in top-level directory.
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
!------------------------------------------------------------------------------
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
! Check for correct source, tag, count, and data in test message.
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
!------------------------------------------------------------------------------
|
|
Packit Service |
c5cf8c |
subroutine msg_check( recv_buf, source, tag, count, status, n, &
|
|
Packit Service |
c5cf8c |
& name, errs )
|
|
Packit Service |
c5cf8c |
use mpi
|
|
Packit Service |
c5cf8c |
integer n, errs
|
|
Packit Service |
c5cf8c |
real recv_buf(n)
|
|
Packit Service |
c5cf8c |
integer source, tag, count, rank, status(MPI_STATUS_SIZE)
|
|
Packit Service |
c5cf8c |
character*(*) name
|
|
Packit Service |
c5cf8c |
logical foundError
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
integer ierr, recv_src, recv_tag, recv_count
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
foundError = .false.
|
|
Packit Service |
c5cf8c |
recv_src = status(MPI_SOURCE)
|
|
Packit Service |
c5cf8c |
recv_tag = status(MPI_TAG)
|
|
Packit Service |
c5cf8c |
call MPI_Comm_rank( MPI_COMM_WORLD, rank, ierr )
|
|
Packit Service |
c5cf8c |
call MPI_Get_count(status, MPI_REAL, recv_count, ierr)
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
if (recv_src .ne. source) then
|
|
Packit Service |
c5cf8c |
print *, '[', rank, '] Unexpected source:', recv_src, &
|
|
Packit Service |
c5cf8c |
& ' in ', name
|
|
Packit Service |
c5cf8c |
errs = errs + 1
|
|
Packit Service |
c5cf8c |
foundError = .true.
|
|
Packit Service |
c5cf8c |
end if
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
if (recv_tag .ne. tag) then
|
|
Packit Service |
c5cf8c |
print *, '[', rank, '] Unexpected tag:', recv_tag, ' in ', name
|
|
Packit Service |
c5cf8c |
errs = errs + 1
|
|
Packit Service |
c5cf8c |
foundError = .true.
|
|
Packit Service |
c5cf8c |
end if
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
if (recv_count .ne. count) then
|
|
Packit Service |
c5cf8c |
print *, '[', rank, '] Unexpected count:', recv_count, &
|
|
Packit Service |
c5cf8c |
& ' in ', name
|
|
Packit Service |
c5cf8c |
errs = errs + 1
|
|
Packit Service |
c5cf8c |
foundError = .true.
|
|
Packit Service |
c5cf8c |
end if
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
call verify_test_data(recv_buf, count, n, name, errs )
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
end
|
|
Packit Service |
c5cf8c |
!------------------------------------------------------------------------------
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
! Check that requests have been set to null
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
!------------------------------------------------------------------------------
|
|
Packit Service |
c5cf8c |
subroutine rq_check( requests, n, msg )
|
|
Packit Service |
c5cf8c |
use mpi
|
|
Packit Service |
c5cf8c |
integer n, requests(n)
|
|
Packit Service |
c5cf8c |
character*(*) msg
|
|
Packit Service |
c5cf8c |
integer i
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
do 10 i=1, n
|
|
Packit Service |
c5cf8c |
if (requests(i) .ne. MPI_REQUEST_NULL) then
|
|
Packit Service |
c5cf8c |
print *, 'Nonnull request in ', msg
|
|
Packit Service |
c5cf8c |
endif
|
|
Packit Service |
c5cf8c |
10 continue
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
end
|
|
Packit Service |
c5cf8c |
!------------------------------------------------------------------------------
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
! Initialize test data buffer with integral sequence.
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
!------------------------------------------------------------------------------
|
|
Packit Service |
c5cf8c |
subroutine init_test_data(buf,n)
|
|
Packit Service |
c5cf8c |
integer n
|
|
Packit Service |
c5cf8c |
real buf(n)
|
|
Packit Service |
c5cf8c |
integer i
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
do 10 i = 1, n
|
|
Packit Service |
c5cf8c |
buf(i) = REAL(i)
|
|
Packit Service |
c5cf8c |
10 continue
|
|
Packit Service |
c5cf8c |
end
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
!------------------------------------------------------------------------------
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
! Clear test data buffer
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
!------------------------------------------------------------------------------
|
|
Packit Service |
c5cf8c |
subroutine clear_test_data(buf, n)
|
|
Packit Service |
c5cf8c |
integer n
|
|
Packit Service |
c5cf8c |
real buf(n)
|
|
Packit Service |
c5cf8c |
integer i
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
do 10 i = 1, n
|
|
Packit Service |
c5cf8c |
buf(i) = 0.
|
|
Packit Service |
c5cf8c |
10 continue
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
end
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
!------------------------------------------------------------------------------
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
! Verify test data buffer
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
!------------------------------------------------------------------------------
|
|
Packit Service |
c5cf8c |
subroutine verify_test_data( buf, count, n, name, errs )
|
|
Packit Service |
c5cf8c |
use mpi
|
|
Packit Service |
c5cf8c |
integer n, errs
|
|
Packit Service |
c5cf8c |
real buf(n)
|
|
Packit Service |
c5cf8c |
character *(*) name
|
|
Packit Service |
c5cf8c |
integer count, ierr, i
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
do 10 i = 1, count
|
|
Packit Service |
c5cf8c |
if (buf(i) .ne. REAL(i)) then
|
|
Packit Service |
c5cf8c |
print 100, buf(i), i, count, name
|
|
Packit Service |
c5cf8c |
errs = errs + 1
|
|
Packit Service |
c5cf8c |
endif
|
|
Packit Service |
c5cf8c |
10 continue
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
do 20 i = count + 1, n
|
|
Packit Service |
c5cf8c |
if (buf(i) .ne. 0.) then
|
|
Packit Service |
c5cf8c |
print 100, buf(i), i, n, name
|
|
Packit Service |
c5cf8c |
errs = errs + 1
|
|
Packit Service |
c5cf8c |
endif
|
|
Packit Service |
c5cf8c |
20 continue
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
100 format('Invalid data', f6.1, ' at ', i4, ' of ', i4, ' in ', a)
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
end
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
! This routine is used to prevent the compiler from deallocating the
|
|
Packit Service |
c5cf8c |
! array "a", which may happen in some of the tests (see the text in
|
|
Packit Service |
c5cf8c |
! the MPI standard about why this may be a problem in valid Fortran
|
|
Packit Service |
c5cf8c |
! codes). Without this, for example, tests fail with the Cray ftn
|
|
Packit Service |
c5cf8c |
! compiler.
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
subroutine dummyRef( a, n, ie )
|
|
Packit Service |
c5cf8c |
integer n, ie
|
|
Packit Service |
c5cf8c |
real a(n)
|
|
Packit Service |
c5cf8c |
! This condition will never be true, but the compile won't know that
|
|
Packit Service |
c5cf8c |
if (ie .eq. -1) then
|
|
Packit Service |
c5cf8c |
print *, a(n)
|
|
Packit Service |
c5cf8c |
endif
|
|
Packit Service |
c5cf8c |
return
|
|
Packit Service |
c5cf8c |
end
|