mpi-hs-0.7.2.0: MPI bindings for Haskell
Copyright(C) 2019 Erik Schnetter
LicenseApache-2.0
MaintainerErik Schnetter <schnetter@gmail.com>
Stabilityexperimental
PortabilityRequires an externally installed MPI library
Safe HaskellNone
LanguageHaskell2010

Control.Distributed.MPI.Storable

Description

 
Synopsis

Types, and associated functions and constants

Communicators

newtype Comm Source #

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.

Constructors

Comm CComm 

Instances

Instances details
Eq Comm Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

(==) :: Comm -> Comm -> Bool #

(/=) :: Comm -> Comm -> Bool #

Ord Comm Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

compare :: Comm -> Comm -> Ordering #

(<) :: Comm -> Comm -> Bool #

(<=) :: Comm -> Comm -> Bool #

(>) :: Comm -> Comm -> Bool #

(>=) :: Comm -> Comm -> Bool #

max :: Comm -> Comm -> Comm #

min :: Comm -> Comm -> Comm #

Show Comm Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

showsPrec :: Int -> Comm -> ShowS #

show :: Comm -> String #

showList :: [Comm] -> ShowS #

commSelf :: Comm Source #

The self communicator (MPI_COMM_SELF). Each process has its own self communicator that includes only this process.

commWorld :: Comm Source #

The world communicator, which includes all processes (MPI_COMM_WORLD).

Message sizes

newtype Count Source #

Constructors

Count CInt 

Instances

Instances details
Enum Count Source # 
Instance details

Defined in Control.Distributed.MPI

Eq Count Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

(==) :: Count -> Count -> Bool #

(/=) :: Count -> Count -> Bool #

Integral Count Source # 
Instance details

Defined in Control.Distributed.MPI

Num Count Source # 
Instance details

Defined in Control.Distributed.MPI

Ord Count Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

compare :: Count -> Count -> Ordering #

(<) :: Count -> Count -> Bool #

(<=) :: Count -> Count -> Bool #

(>) :: Count -> Count -> Bool #

(>=) :: Count -> Count -> Bool #

max :: Count -> Count -> Count #

min :: Count -> Count -> Count #

Read Count Source # 
Instance details

Defined in Control.Distributed.MPI

Real Count Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

toRational :: Count -> Rational #

Show Count Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

showsPrec :: Int -> Count -> ShowS #

show :: Count -> String #

showList :: [Count] -> ShowS #

Generic Count Source # 
Instance details

Defined in Control.Distributed.MPI

Associated Types

type Rep Count :: Type -> Type #

Methods

from :: Count -> Rep Count x #

to :: Rep Count x -> Count #

Storable Count Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

sizeOf :: Count -> Int #

alignment :: Count -> Int #

peekElemOff :: Ptr Count -> Int -> IO Count #

pokeElemOff :: Ptr Count -> Int -> Count -> IO () #

peekByteOff :: Ptr b -> Int -> IO Count #

pokeByteOff :: Ptr b -> Int -> Count -> IO () #

peek :: Ptr Count -> IO Count #

poke :: Ptr Count -> Count -> IO () #

type Rep Count Source # 
Instance details

Defined in Control.Distributed.MPI

type Rep Count = D1 ('MetaData "Count" "Control.Distributed.MPI" "mpi-hs-0.7.2.0-BstjNceE1CR9yzzVMQzkf7" 'True) (C1 ('MetaCons "Count" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt)))

fromCount :: Integral i => Count -> i Source #

Convert a count to an integer.

toCount :: Integral i => i -> Count Source #

Convert an integer to a count.

Process ranks

newtype Rank Source #

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.

Constructors

Rank CInt 

Instances

Instances details
Enum Rank Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

succ :: Rank -> Rank #

pred :: Rank -> Rank #

toEnum :: Int -> Rank #

fromEnum :: Rank -> Int #

enumFrom :: Rank -> [Rank] #

enumFromThen :: Rank -> Rank -> [Rank] #

enumFromTo :: Rank -> Rank -> [Rank] #

enumFromThenTo :: Rank -> Rank -> Rank -> [Rank] #

Eq Rank Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

(==) :: Rank -> Rank -> Bool #

(/=) :: Rank -> Rank -> Bool #

Integral Rank Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

quot :: Rank -> Rank -> Rank #

rem :: Rank -> Rank -> Rank #

div :: Rank -> Rank -> Rank #

mod :: Rank -> Rank -> Rank #

quotRem :: Rank -> Rank -> (Rank, Rank) #

divMod :: Rank -> Rank -> (Rank, Rank) #

toInteger :: Rank -> Integer #

Num Rank Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

(+) :: Rank -> Rank -> Rank #

(-) :: Rank -> Rank -> Rank #

(*) :: Rank -> Rank -> Rank #

negate :: Rank -> Rank #

abs :: Rank -> Rank #

signum :: Rank -> Rank #

fromInteger :: Integer -> Rank #

Ord Rank Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

compare :: Rank -> Rank -> Ordering #

(<) :: Rank -> Rank -> Bool #

(<=) :: Rank -> Rank -> Bool #

(>) :: Rank -> Rank -> Bool #

(>=) :: Rank -> Rank -> Bool #

max :: Rank -> Rank -> Rank #

min :: Rank -> Rank -> Rank #

Read Rank Source # 
Instance details

Defined in Control.Distributed.MPI

Real Rank Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

toRational :: Rank -> Rational #

Show Rank Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

showsPrec :: Int -> Rank -> ShowS #

show :: Rank -> String #

showList :: [Rank] -> ShowS #

Ix Rank Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

range :: (Rank, Rank) -> [Rank] #

index :: (Rank, Rank) -> Rank -> Int #

unsafeIndex :: (Rank, Rank) -> Rank -> Int #

inRange :: (Rank, Rank) -> Rank -> Bool #

rangeSize :: (Rank, Rank) -> Int #

unsafeRangeSize :: (Rank, Rank) -> Int #

Generic Rank Source # 
Instance details

Defined in Control.Distributed.MPI

Associated Types

type Rep Rank :: Type -> Type #

Methods

from :: Rank -> Rep Rank x #

to :: Rep Rank x -> Rank #

Storable Rank Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

sizeOf :: Rank -> Int #

alignment :: Rank -> Int #

peekElemOff :: Ptr Rank -> Int -> IO Rank #

pokeElemOff :: Ptr Rank -> Int -> Rank -> IO () #

peekByteOff :: Ptr b -> Int -> IO Rank #

pokeByteOff :: Ptr b -> Int -> Rank -> IO () #

peek :: Ptr Rank -> IO Rank #

poke :: Ptr Rank -> Rank -> IO () #

type Rep Rank Source # 
Instance details

Defined in Control.Distributed.MPI

type Rep Rank = D1 ('MetaData "Rank" "Control.Distributed.MPI" "mpi-hs-0.7.2.0-BstjNceE1CR9yzzVMQzkf7" 'True) (C1 ('MetaCons "Rank" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt)))

anySource :: Rank Source #

Rank placeholder to specify that a message can be received from any source (MPI_ANY_SOURCE). When calling probe or recv (or iprobe or irecv) with anySource as source, the actual source can be determined from the returned message status via getSource.

commRank Source #

Arguments

:: Comm

Communicator

-> IO Rank 

Return this process's rank in a communicator (MPI_Comm_rank).

commSize Source #

Arguments

:: Comm

Communicator

-> IO Rank 

Return the number of processes in a communicator (MPI_Comm_size).

fromRank :: Enum e => Rank -> e Source #

Convert a rank to an enum.

rootRank :: Rank Source #

The root (first) rank of a communicator.

toRank :: Enum e => e -> Rank Source #

Convert an enum to a rank.

Message status

data Status Source #

The status of a finished communication, indicating rank and tag of the other communication end point.

Constructors

Status 

Fields

Instances

Instances details
Eq Status Source # 
Instance details

Defined in Control.Distributed.MPI.Storable

Methods

(==) :: Status -> Status -> Bool #

(/=) :: Status -> Status -> Bool #

Ord Status Source # 
Instance details

Defined in Control.Distributed.MPI.Storable

Read Status Source # 
Instance details

Defined in Control.Distributed.MPI.Storable

Show Status Source # 
Instance details

Defined in Control.Distributed.MPI.Storable

Message tags

newtype Tag Source #

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.

Constructors

Tag CInt 

Instances

Instances details
Enum Tag Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

succ :: Tag -> Tag #

pred :: Tag -> Tag #

toEnum :: Int -> Tag #

fromEnum :: Tag -> Int #

enumFrom :: Tag -> [Tag] #

enumFromThen :: Tag -> Tag -> [Tag] #

enumFromTo :: Tag -> Tag -> [Tag] #

enumFromThenTo :: Tag -> Tag -> Tag -> [Tag] #

Eq Tag Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

(==) :: Tag -> Tag -> Bool #

(/=) :: Tag -> Tag -> Bool #

Num Tag Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

(+) :: Tag -> Tag -> Tag #

(-) :: Tag -> Tag -> Tag #

(*) :: Tag -> Tag -> Tag #

negate :: Tag -> Tag #

abs :: Tag -> Tag #

signum :: Tag -> Tag #

fromInteger :: Integer -> Tag #

Ord Tag Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

compare :: Tag -> Tag -> Ordering #

(<) :: Tag -> Tag -> Bool #

(<=) :: Tag -> Tag -> Bool #

(>) :: Tag -> Tag -> Bool #

(>=) :: Tag -> Tag -> Bool #

max :: Tag -> Tag -> Tag #

min :: Tag -> Tag -> Tag #

Read Tag Source # 
Instance details

Defined in Control.Distributed.MPI

Show Tag Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Generic Tag Source # 
Instance details

Defined in Control.Distributed.MPI

Associated Types

type Rep Tag :: Type -> Type #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

Storable Tag Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

sizeOf :: Tag -> Int #

alignment :: Tag -> Int #

peekElemOff :: Ptr Tag -> Int -> IO Tag #

pokeElemOff :: Ptr Tag -> Int -> Tag -> IO () #

peekByteOff :: Ptr b -> Int -> IO Tag #

pokeByteOff :: Ptr b -> Int -> Tag -> IO () #

peek :: Ptr Tag -> IO Tag #

poke :: Ptr Tag -> Tag -> IO () #

type Rep Tag Source # 
Instance details

Defined in Control.Distributed.MPI

type Rep Tag = D1 ('MetaData "Tag" "Control.Distributed.MPI" "mpi-hs-0.7.2.0-BstjNceE1CR9yzzVMQzkf7" 'True) (C1 ('MetaCons "Tag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt)))

anyTag :: Tag Source #

Tag placeholder to specify that a message can have any tag (MPI_ANY_TAG). When calling probe or recv (or iprobe or irecv) with anyTag as tag, the actual tag can be determined from the returned message status via getTag.

fromTag :: Enum e => Tag -> e Source #

Convert a tag to an enum.

toTag :: Enum e => e -> Tag Source #

Convert an enum to a tag.

unitTag :: Tag Source #

Useful default tag.

data Request a Source #

A communication request, usually created by a non-blocking communication function.

Functions

Initialization and shutdown

abort Source #

Arguments

:: Comm

Communicator describing which processes to terminate

-> Int

Error code

-> IO () 

Terminate MPI execution environment (MPI_Abort).

mainMPI Source #

Arguments

:: IO ()

action to run with MPI, typically the whole program

-> IO () 

Convenience function to initialize and finalize MPI. This initializes MPI with ThreadMultiple thread support.

Point-to-point (blocking)

recv Source #

Arguments

:: CanSerialize a 
=> Rank

Source rank

-> Tag

Source tag

-> Comm

Communicator

-> IO (Status, a)

Message status and received object

Receive an object.

recv_ Source #

Arguments

:: CanSerialize a 
=> Rank

Source rank

-> Tag

Source tag

-> Comm

Communicator

-> IO a

Received object

Receive an object without returning a status.

send Source #

Arguments

:: CanSerialize a 
=> a

Object to send

-> Rank

Destination rank

-> Tag

Message tag

-> Comm

Communicator

-> IO () 

Send an object.

sendrecv Source #

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.

sendrecv_ Source #

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)

irecv Source #

Arguments

:: CanSerialize a 
=> Rank

Source rank

-> Tag

Source tag

-> Comm

Communicator

-> IO (Request a)

Communication request

Begin to receive an object. Call test or wait to finish the communication, and to obtain the received object.

isend Source #

Arguments

:: CanSerialize a 
=> a

Object to send

-> Rank

Destination rank

-> Tag

Message tag

-> Comm

Communicator

-> IO (Request ())

Communication request

Begin to send an object. Call test or wait to finish the communication.

test Source #

Arguments

:: Request a

Communication request

-> IO (Maybe (Status, a))

Just communication result, if communication has finished, else Nothing

Check whether a communication has finished, and return the communication result if so.

test_ Source #

Arguments

:: Request a

Communication request

-> IO (Maybe a)

Just communication result, if communication has finished, else Nothing

Check whether a communication has finished, and return the communication result if so, without returning a message status.

wait Source #

Arguments

:: Request a

Communication request

-> IO (Status, a)

Message status and communication result

Wait for a communication to finish and return the communication result.

wait_ Source #

Arguments

:: Request a

Communication request

-> IO a

Communication result

Wait for a communication to finish and return the communication result, without returning a message status.

Collective (blocking)

barrier Source #

Arguments

:: Comm

Communicator

-> IO () 

Barrier (collective, MPI_Barrier).

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.

Collective (non-blocking)

ibarrier :: Comm -> IO (Request ()) Source #

Begin a barrier. Call test or wait to finish the communication.

ibcast :: CanSerialize a => Maybe a -> Rank -> Comm -> IO (Request a) Source #

ibcastRecv :: CanSerialize a => Rank -> Comm -> IO (Request a) Source #

ibcastSend :: CanSerialize a => a -> Rank -> Comm -> IO (Request a) Source #

ibcastSend_ :: CanSerialize a => a -> Rank -> Comm -> IO (Request ()) Source #