Blame test/mpi/f90/pt2pt/psendf90.f90

Packit Service c5cf8c
! This file created from f77/pt2pt/psendf.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
! This program is based on the allpair.f test from the MPICH-1 test
Packit Service c5cf8c
! (test/pt2pt/allpair.f), which in turn was inspired by a bug report from
Packit Service c5cf8c
! fsset@corelli.lerc.nasa.gov (Scott Townsend)
Packit Service c5cf8c
Packit Service c5cf8c
      program psend
Packit Service c5cf8c
      use mpi
Packit Service c5cf8c
      integer ierr, errs, comm
Packit Service c5cf8c
      logical mtestGetIntraComm
Packit Service c5cf8c
      logical verbose
Packit Service c5cf8c
      common /flags/ verbose
Packit Service c5cf8c
Packit Service c5cf8c
      errs = 0
Packit Service c5cf8c
      verbose = .false.
Packit Service c5cf8c
!      verbose = .true.
Packit Service c5cf8c
      call MTest_Init( ierr )
Packit Service c5cf8c
Packit Service c5cf8c
      do while ( mtestGetIntraComm( comm, 2, .false. ) )
Packit Service c5cf8c
         call test_pair_psend( comm, errs )
Packit Service c5cf8c
         call mtestFreeComm( comm )
Packit Service c5cf8c
      enddo
Packit Service c5cf8c
!
Packit Service c5cf8c
      call MTest_Finalize( errs )
Packit Service c5cf8c
!
Packit Service c5cf8c
      end
Packit Service c5cf8c
!
Packit Service c5cf8c
      subroutine test_pair_psend( comm, errs )
Packit Service c5cf8c
      use mpi
Packit Service c5cf8c
      integer comm, errs
Packit Service c5cf8c
      integer rank, size, ierr, next, prev, tag, count, i
Packit Service c5cf8c
      integer TEST_SIZE
Packit Service c5cf8c
      parameter (TEST_SIZE=2000)
Packit Service c5cf8c
      integer status(MPI_STATUS_SIZE)
Packit Service c5cf8c
      integer statuses(MPI_STATUS_SIZE,2), requests(2)
Packit Service c5cf8c
      real send_buf(TEST_SIZE), recv_buf(TEST_SIZE)
Packit Service c5cf8c
      logical verbose
Packit Service c5cf8c
      common /flags/ verbose
Packit Service c5cf8c
!
Packit Service c5cf8c
      if (verbose) then
Packit Service c5cf8c
         print *, ' Persistent send and recv'
Packit Service c5cf8c
      endif
Packit Service c5cf8c
!
Packit Service c5cf8c
      call mpi_comm_rank( comm, rank, ierr )
Packit Service c5cf8c
      call mpi_comm_size( comm, size, ierr )
Packit Service c5cf8c
      next = rank + 1
Packit Service c5cf8c
      if (next .ge. size) next = 0
Packit Service c5cf8c
!
Packit Service c5cf8c
      prev = rank - 1
Packit Service c5cf8c
      if (prev .lt. 0) prev = size - 1
Packit Service c5cf8c
!
Packit Service c5cf8c
      tag = 3123
Packit Service c5cf8c
      count = TEST_SIZE / 5
Packit Service c5cf8c
!
Packit Service c5cf8c
      call clear_test_data(recv_buf,TEST_SIZE)
Packit Service c5cf8c
      call MPI_Recv_init(recv_buf, TEST_SIZE, MPI_REAL, &
Packit Service c5cf8c
      &                   MPI_ANY_SOURCE, MPI_ANY_TAG, comm, &
Packit Service c5cf8c
      &                   requests(2), ierr)
Packit Service c5cf8c
!
Packit Service c5cf8c
      if (rank .eq. 0) then
Packit Service c5cf8c
!
Packit Service c5cf8c
         call init_test_data(send_buf,TEST_SIZE)
Packit Service c5cf8c
!
Packit Service c5cf8c
         call MPI_Send_init(send_buf, count, MPI_REAL, next, tag, &
Packit Service c5cf8c
      &                      comm, requests(1), ierr)
Packit Service c5cf8c
!
Packit Service c5cf8c
         call MPI_Startall(2, requests, ierr)
Packit Service c5cf8c
         call MPI_Waitall(2, requests, statuses, ierr)
Packit Service c5cf8c
!
Packit Service c5cf8c
         call msg_check( recv_buf, next, tag, count, statuses(1,2), &
Packit Service c5cf8c
      &        TEST_SIZE, 'persistent send/recv', errs )
Packit Service c5cf8c
!
Packit Service c5cf8c
         call MPI_Request_free(requests(1), ierr)
Packit Service c5cf8c
!
Packit Service c5cf8c
      else if (prev .eq. 0) then
Packit Service c5cf8c
!
Packit Service c5cf8c
         call MPI_Send_init(send_buf, count, MPI_REAL, prev, tag, &
Packit Service c5cf8c
      &                      comm, requests(1), ierr)
Packit Service c5cf8c
         call MPI_Start(requests(2), ierr)
Packit Service c5cf8c
         call MPI_Wait(requests(2), status, ierr)
Packit Service c5cf8c
!
Packit Service c5cf8c
         call msg_check( recv_buf, prev, tag, count, status, TEST_SIZE, &
Packit Service c5cf8c
      &                   'persistent send/recv', errs )
Packit Service c5cf8c
!
Packit Service c5cf8c
         do i = 1,count
Packit Service c5cf8c
            send_buf(i) = recv_buf(i)
Packit Service c5cf8c
         end do
Packit Service c5cf8c
!
Packit Service c5cf8c
         call MPI_Start(requests(1), ierr)
Packit Service c5cf8c
         call MPI_Wait(requests(1), status, ierr)
Packit Service c5cf8c
!
Packit Service c5cf8c
         call MPI_Request_free(requests(1), ierr)
Packit Service c5cf8c
      end if
Packit Service c5cf8c
!
Packit Service c5cf8c
      call dummyRef( send_buf, count, ierr )
Packit Service c5cf8c
      call MPI_Request_free(requests(2), ierr)
Packit Service c5cf8c
!
Packit Service c5cf8c
      end