| Copyright | (C) 2020 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 |
Control.Distributed.MPI.Serialize
Description
Synopsis
- newtype MPIException = MPIException String
- newtype Comm = Comm CComm
- 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 ()
- bcast :: CanSerialize a => Maybe a -> Rank -> Comm -> IO a
- bcastRecv :: CanSerialize a => Rank -> Comm -> IO a
- bcastSend :: CanSerialize a => a -> Rank -> Comm -> IO a
- bcastSend_ :: CanSerialize a => a -> Rank -> Comm -> IO ()
- ibarrier :: Comm -> IO (Request ())
- ibcast :: CanSerialize a => Maybe a -> Rank -> Comm -> IO (Request a)
- ibcastRecv :: CanSerialize a => Rank -> Comm -> IO (Request a)
- ibcastSend :: CanSerialize a => 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
Constructors
| MPIException String |
Instances
Communicators
Message sizes
Instances
| Enum Count | |
Defined in Control.Distributed.MPI | |
| Eq Count | |
| Integral Count | |
| Num Count | |
| Ord Count | |
| Read Count | |
| Real Count | |
Defined in Control.Distributed.MPI Methods toRational :: Count -> Rational # | |
| Show Count | |
| Generic Count | |
| Storable Count | |
| type Rep Count | |
Defined in Control.Distributed.MPI | |
Process ranks
Message status
The status of a finished communication, indicating rank and tag of the other communication end point.
Message tags
A communication request, usually created by a non-blocking communication function.
Functions
Initialization and shutdown
Convenience function to initialize and finalize MPI. This
initializes MPI with ThreadMultiple thread support.
Point-to-point (blocking)
Arguments
| :: CanSerialize a | |
| => Rank | Source rank |
| -> Tag | Source tag |
| -> Comm | Communicator |
| -> IO (Status, a) | Message status and received object |
Receive an object.
Arguments
| :: CanSerialize a | |
| => Rank | Source rank |
| -> Tag | Source tag |
| -> Comm | Communicator |
| -> IO a | Received object |
Receive an object without returning a status.
Arguments
| :: CanSerialize a | |
| => a | Object to send |
| -> Rank | Destination rank |
| -> Tag | Message tag |
| -> Comm | Communicator |
| -> IO () |
Send an object.
Arguments
| :: (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.
Arguments
| :: (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)
Arguments
| :: Request a | Communication request |
| -> IO (Maybe (Status, a)) |
|
Check whether a communication has finished, and return the communication result if so.
Arguments
| :: 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)
bcast :: CanSerialize a => Maybe a -> Rank -> Comm -> IO a Source #
Broadcast a message from one process (the "root") to all other
processes in the communicator. The send object must be present
(Just) on the root, and is ignored on all non-root processes.
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 a 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.
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.