mp_iallgather_c Subroutine

private subroutine mp_iallgather_c(msgout, msgin, gid, request)

Gathers a datum from all processes and all processes receive the same data

Data size All processes send equal-sized data

MPI mapping mpi_allgather

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), intent(in) :: msgout

Datum to send

complex(kind=real_4), intent(out), CONTIGUOUS :: msgin(:)

Received data

type(mp_comm_type), intent(in) :: gid

Message passing environment identifier

type(mp_request_type), intent(inout) :: request

Source Code

      SUBROUTINE mp_iallgather_c (msgout, msgin, gid, request)
      !! Gathers a datum from all processes and all processes receive the
      !! same data
      !!
      !! Data size
      !! All processes send equal-sized data
      !!
      !! MPI mapping
      !! mpi_allgather

         COMPLEX(kind=real_4), INTENT(IN)                    :: msgout
         !! Datum to send
         COMPLEX(kind=real_4), CONTIGUOUS, INTENT(OUT)       :: msgin(:)
         !! Received data
         TYPE(mp_comm_type), INTENT(IN)           :: gid
         !! Message passing environment identifier
         TYPE(mp_request_type), INTENT(INOUT)     :: request

         CHARACTER(LEN=*), PARAMETER :: routineN = 'mp_iallgather_c'

         INTEGER                                  :: handle, ierr
#if defined(__parallel)
         INTEGER                                  :: rcount, scount
#endif

         ierr = 0
         CALL timeset(routineN, handle)

#if defined(__parallel)
         scount = 1
         rcount = 1
         CALL MPI_IALLGATHER(msgout, scount, MPI_COMPLEX, &
                             msgin, rcount, MPI_COMPLEX, &
                             gid%handle, request%handle, ierr)
         IF (ierr /= 0) CALL mp_stop(ierr, "mpi_iallgather @ "//routineN)
#else
         MARK_USED(gid)
         msgin = msgout
         request = mp_request_null
#endif
         CALL timestop(handle)
      END SUBROUTINE mp_iallgather_c