Copyright | (C) 2018 Erik Schnetter |
---|---|
License | Apache-2.0 |
Maintainer | Erik Schnetter <schnetter@gmail.com> |
Stability | experimental |
Portability | Requires an externally installed MPI library |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- newtype MPIException = MPIException String
- newtype Comm = Comm (ForeignPtr Comm)
- commSelf :: Comm
- commWorld :: Comm
- newtype Count = Count CInt
- fromCount :: Integral i => Count -> i
- toCount :: Integral i => i -> Count
- newtype Rank = Rank CInt
- anySource :: Rank
- commRank :: Comm -> IO Rank
- commSize :: Comm -> IO Rank
- fromRank :: Enum e => Rank -> e
- rootRank :: Rank
- toRank :: Enum e => e -> Rank
- data Status = Status {}
- newtype Tag = Tag CInt
- anyTag :: Tag
- fromTag :: Enum e => Tag -> e
- toTag :: Enum e => e -> Tag
- unitTag :: Tag
- data Request a
- abort :: Comm -> Int -> IO ()
- mainMPI :: IO () -> IO ()
- recv :: CanSerialize a => Rank -> Tag -> Comm -> IO (Status, a)
- recv_ :: CanSerialize a => Rank -> Tag -> Comm -> IO a
- send :: CanSerialize a => a -> Rank -> Tag -> Comm -> IO ()
- sendrecv :: (CanSerialize a, CanSerialize b) => a -> Rank -> Tag -> Rank -> Tag -> Comm -> IO (Status, b)
- sendrecv_ :: (CanSerialize a, CanSerialize b) => a -> Rank -> Tag -> Rank -> Tag -> Comm -> IO b
- irecv :: CanSerialize a => Rank -> Tag -> Comm -> IO (Request a)
- isend :: CanSerialize a => a -> Rank -> Tag -> Comm -> IO (Request ())
- test :: Request a -> IO (Maybe (Status, a))
- test_ :: Request a -> IO (Maybe a)
- wait :: Request a -> IO (Status, a)
- wait_ :: Request a -> IO a
- barrier :: Comm -> IO ()
- bcastRecv :: CanSerialize a => Rank -> Comm -> IO a
- bcastSend :: CanSerialize a => a -> Rank -> Comm -> IO ()
- ibarrier :: Comm -> IO (Request ())
- ibcastRecv :: CanSerialize a => Rank -> Comm -> IO (Request a)
- ibcastSend :: CanSerialize a => a -> Rank -> Comm -> IO (Request ())
Types, and associated functions and constants
newtype MPIException Source #
Exception type indicating an error in a call to MPI
Instances
Eq MPIException Source # | |
Defined in Control.Distributed.MPI.Binary (==) :: MPIException -> MPIException -> Bool # (/=) :: MPIException -> MPIException -> Bool # | |
Ord MPIException Source # | |
Defined in Control.Distributed.MPI.Binary compare :: MPIException -> MPIException -> Ordering # (<) :: MPIException -> MPIException -> Bool # (<=) :: MPIException -> MPIException -> Bool # (>) :: MPIException -> MPIException -> Bool # (>=) :: MPIException -> MPIException -> Bool # max :: MPIException -> MPIException -> MPIException # min :: MPIException -> MPIException -> MPIException # | |
Read MPIException Source # | |
Defined in Control.Distributed.MPI.Binary readsPrec :: Int -> ReadS MPIException # readList :: ReadS [MPIException] # | |
Show MPIException Source # | |
Defined in Control.Distributed.MPI.Binary showsPrec :: Int -> MPIException -> ShowS # show :: MPIException -> String # showList :: [MPIException] -> ShowS # | |
Exception MPIException Source # | |
Defined in Control.Distributed.MPI.Binary |
Communicators
An MPI communicator, wrapping MPI_Comm
. A communicator defines
an independent communication channel between a group of processes.
Communicators need to be explicitly created and freed by the MPI
library. commWorld
is a communicator that is always available,
and which includes all processes.
The self communicator (MPI_COMM_SELF
). Each process has its own
self communicator that includes only this process.
Message sizes
A newtype wrapper describing the size of a message. Use toCount
and fromCount
to convert between Count
and other integral
types.
Instances
Enum Count Source # | |
Defined in Control.Distributed.MPI | |
Eq Count Source # | |
Integral Count Source # | |
Num Count Source # | |
Ord Count Source # | |
Read Count Source # | |
Real Count Source # | |
Defined in Control.Distributed.MPI toRational :: Count -> Rational # | |
Show Count Source # | |
Generic Count Source # | |
Storable Count Source # | |
Store Count Source # | |
type Rep Count Source # | |
Defined in Control.Distributed.MPI |
Process ranks
A newtype wrapper describing the source or destination of a
message, i.e. a process. Each communicator numbers its processes
sequentially starting from zero. Use toRank
and fromRank
to
convert between Rank
and other integral types. rootRank
is the
root (first) process of a communicator.
The association between a rank and a communicator is not explicitly tracked. From MPI's point of view, ranks are simply integers. The same rank might correspond to different processes in different communicators.
Instances
Enum Rank Source # | |
Eq Rank Source # | |
Integral Rank Source # | |
Num Rank Source # | |
Ord Rank Source # | |
Read Rank Source # | |
Real Rank Source # | |
Defined in Control.Distributed.MPI toRational :: Rank -> Rational # | |
Show Rank Source # | |
Ix Rank Source # | |
Generic Rank Source # | |
Storable Rank Source # | |
Defined in Control.Distributed.MPI | |
Binary Rank Source # | |
Store Rank Source # | |
type Rep Rank Source # | |
Defined in Control.Distributed.MPI |
Return this process's rank in a communicator
(MPI_Comm_rank
).
Return the number of processes in a communicator
(MPI_Comm_size
).
Message status
The status of a finished communication, indicating rank and tag of the other communication end point.
Message tags
A newtype wrapper describing a message tag. A tag defines a
sub-channel within a communicator. While communicators are
heavy-weight object that are expensive to set up and tear down, a
tag is a lightweight mechanism using an integer. Use toTag
and
fromTag
to convert between Count
and other enum types.
unitTag
defines a standard tag that can be used as default.
A communication request, usually created by a non-blocking communication function.
Functions
Initialization and shutdown
Terminate MPI execution environment
(MPI_Abort
).
Convenience function to initialize and finalize MPI. This
initializes MPI with ThreadMultiple
thread support.
Point-to-point (blocking)
:: CanSerialize a | |
=> Rank | Source rank |
-> Tag | Source tag |
-> Comm | Communicator |
-> IO (Status, a) | Message status and received object |
Receive an object.
Receive an object without returning a status.
:: CanSerialize a | |
=> a | Object to send |
-> Rank | Destination rank |
-> Tag | Message tag |
-> Comm | Communicator |
-> IO () |
Send an object.
:: (CanSerialize a, CanSerialize b) | |
=> a | Object to send |
-> Rank | Destination rank |
-> Tag | Send message tag |
-> Rank | Source rank |
-> Tag | Receive message tag |
-> Comm | Communicator |
-> IO (Status, b) | Message status and received object |
Send and receive objects simultaneously.
:: (CanSerialize a, CanSerialize b) | |
=> a | Object to send |
-> Rank | Destination rank |
-> Tag | Send message tag |
-> Rank | Source rank |
-> Tag | Receive message tag |
-> Comm | Communicator |
-> IO b | Received object |
Send and receive objects simultaneously, without returning a status for the received message.
Point-to-point (non-blocking)
:: Request a | Communication request |
-> IO (Maybe (Status, a)) |
|
Check whether a communication has finished, and return the communication result if so.
:: Request a | Communication request |
-> IO (Maybe a) |
|
Check whether a communication has finished, and return the communication result if so, without returning a message status.
Wait for a communication to finish and return the communication result.
Wait for a communication to finish and return the communication result, without returning a message status.
Collective (blocking)
bcastRecv :: CanSerialize a => Rank -> Comm -> IO a Source #
Broadcast a message from one process (the "root") to all other
processes in the communicator. Call this function on all non-root
processes. Call bcastSend
instead on the root process.
bcastSend :: CanSerialize a => a -> Rank -> Comm -> IO () Source #
Broadcast a message from one process (the "root") to all other
processes in the communicator. Call this function on the root
process. Call bcastRecv
instead on all non-root processes.