mpi-hs-0.5.2.0: MPI bindings for Haskell

Copyright(C) 2018 Erik Schnetter
LicenseApache-2.0
MaintainerErik Schnetter <schnetter@gmail.com>
Stabilityexperimental
PortabilityRequires an externally installed MPI library
Safe HaskellNone
LanguageHaskell2010

Control.Distributed.MPI

Contents

Description

MPI (the Message Passing Interface) is widely used standard for distributed-memory programming on HPC (High Performance Computing) systems. MPI allows exchanging data (_messages_) between programs running in parallel. There are several high-quality open source MPI implementations (e.g. MPICH, MVAPICH, OpenMPI) as well as a variety of closed-source implementations. These libraries can typically make use of high-bandwidth low-latency communication hardware such as InfiniBand.

This library mpi-hs provides Haskell bindings for MPI. It is based on ideas taken from haskell-mpi, Boost.MPI, and MPI for Python.

mpi-hs provides two API levels: A low-level API gives rather direct access to the MPI API, apart from certain "reasonable" mappings from C to Haskell (e.g. output arguments that are in C stored to a pointer are in Haskell regular return values). A high-level API simplifies exchanging arbitrary values that can be serialized.

This module MPI is the low-level interface.

In general, the MPI C API is translated to Haskell in the following way, greatly aided by c2hs:

  • Names of constants and functions have the MPI_ prefix removed. Underscores are replaced by CamelCase. The MPI module is intended to be imported qualified, as in 'import qualified Control.Distributed.MPI as MPI'.
  • Opaque types such as MPI_Request are wrapped via newtypes.
  • The MPI error return code is omitted. Currently error codes are ignored, since the default MPI behaviour is to terminate the application instead of actually returning error codes. In the future, error codes might be reported via exceptions.
  • Output arguments that are written via pointers in C are returned. Some functions now return tuples. If the output argument is a boolean value that indicates whether another output argument is valid, then this is translated into a Maybe.
  • MPI has a facility to pass MPI_STATUS_IGNORE to indicate that no message status should be returned. This is instead handled by providing alternative functions ending with an underscore (e.g. recv_) that return () instead of Status.
  • Datatype arguments are hidden. Instead, the correct MPI datatypes are inferred from the pointer type specifying the communication buffers. (This translation could be relaxed, and the original MPI functions could be exposed as well when needed.)
Synopsis

Types, and associated functions and constants

Communication buffers

class Buffer buf where Source #

A generic pointer-like type that supports converting to a Ptr, and which knows the type and number of its elements. This class describes the MPI buffers used to send and receive messages.

Associated Types

type Elem buf Source #

Methods

withPtrLenType :: buf -> (Ptr (Elem buf) -> Count -> Datatype -> IO a) -> IO a Source #

Instances
Buffer ByteString Source # 
Instance details

Defined in Control.Distributed.MPI

Associated Types

type Elem ByteString :: Type Source #

(Storable a, HasDatatype a, Integral i) => Buffer (StablePtr a, i) Source # 
Instance details

Defined in Control.Distributed.MPI

Associated Types

type Elem (StablePtr a, i) :: Type Source #

Methods

withPtrLenType :: (StablePtr a, i) -> (Ptr (Elem (StablePtr a, i)) -> Count -> Datatype -> IO a0) -> IO a0 Source #

(Storable a, HasDatatype a, Integral i) => Buffer (Ptr a, i) Source # 
Instance details

Defined in Control.Distributed.MPI

Associated Types

type Elem (Ptr a, i) :: Type Source #

Methods

withPtrLenType :: (Ptr a, i) -> (Ptr (Elem (Ptr a, i)) -> Count -> Datatype -> IO a0) -> IO a0 Source #

(Storable a, HasDatatype a, Integral i) => Buffer (ForeignPtr a, i) Source # 
Instance details

Defined in Control.Distributed.MPI

Associated Types

type Elem (ForeignPtr a, i) :: Type Source #

Methods

withPtrLenType :: (ForeignPtr a, i) -> (Ptr (Elem (ForeignPtr a, i)) -> Count -> Datatype -> IO a0) -> IO a0 Source #

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
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 #

data ComparisonResult Source #

The result of comparing two MPI communicator (see commCompare).

Instances
Enum ComparisonResult Source # 
Instance details

Defined in Control.Distributed.MPI

Eq ComparisonResult Source # 
Instance details

Defined in Control.Distributed.MPI

Ord ComparisonResult Source # 
Instance details

Defined in Control.Distributed.MPI

Read ComparisonResult Source # 
Instance details

Defined in Control.Distributed.MPI

Show ComparisonResult Source # 
Instance details

Defined in Control.Distributed.MPI

Generic ComparisonResult Source # 
Instance details

Defined in Control.Distributed.MPI

Associated Types

type Rep ComparisonResult :: Type -> Type #

Store ComparisonResult Source # 
Instance details

Defined in Control.Distributed.MPI

type Rep ComparisonResult Source # 
Instance details

Defined in Control.Distributed.MPI

type Rep ComparisonResult = D1 (MetaData "ComparisonResult" "Control.Distributed.MPI" "mpi-hs-0.5.2.0-6qrutEbP7yF4EH47o63F1o" False) ((C1 (MetaCons "Identical" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Congruent" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Similar" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Unequal" PrefixI False) (U1 :: Type -> Type)))

commCompare Source #

Arguments

:: Comm

Communicator

-> Comm

Other communicator

-> IO ComparisonResult 

Compare two communicators (MPI_Comm_compare).

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).

commNull :: Comm Source #

A null (invalid) communicator (MPI_COMM_NULL).

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 #

A newtype wrapper describing the size of a message. Use toCount and fromCount to convert between Count and other integral types.

Constructors

Count CInt 
Instances
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 () #

Store Count Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

size :: Size Count

poke :: Count -> Poke ()

peek :: Peek Count

type Rep Count Source # 
Instance details

Defined in Control.Distributed.MPI

type Rep Count = D1 (MetaData "Count" "Control.Distributed.MPI" "mpi-hs-0.5.2.0-6qrutEbP7yF4EH47o63F1o" 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.

countUndefined :: Count Source #

Error value returned by getCount if the message is too large, or if the message size is not an integer multiple of the provided datatype (MPI_UNDEFINED).

Datatypes

newtype Datatype Source #

An MPI datatype, wrapping MPI_Datatype. Datatypes need to be explicitly created and freed by the MPI library. Predefined datatypes exist for most simple C types such as CInt or CDouble.

Constructors

Datatype CDatatype 

datatypeNull :: Datatype Source #

A null (invalid) datatype.

datatypeByte :: Datatype Source #

MPI datatype for a byte (essentially CUChar) (MPI_BYTE).

datatypeChar :: Datatype Source #

MPI datatype for CChar (MPI_CHAR).

datatypeDouble :: Datatype Source #

MPI datatype for CDouble (MPI_DOUBLE).

datatypeFloat :: Datatype Source #

MPI datatype for CFloat (MPI_FLOAT).

datatypeInt :: Datatype Source #

MPI datatype for CInt (MPI_INT).

datatypeLong :: Datatype Source #

MPI datatype for CLong (MPI_LONG).

datatypeLongDouble :: Datatype Source #

MPI datatype for the C type 'long double' (MPI_LONG_DOUBLE).

datatypeLongLongInt :: Datatype Source #

MPI datatype for CLLong (MPI_LONG_LONG_INT). (There is no MPI datatype for 'CULLong@).

datatypeShort :: Datatype Source #

MPI datatype for CShort (MPI_SHORT).

datatypeUnsigned :: Datatype Source #

MPI datatype for CUInt (MPI_UNSIGNED).

datatypeUnsignedChar :: Datatype Source #

MPI datatype for CUChar (MPI_UNSIGNED_CHAR).

datatypeUnsignedLong :: Datatype Source #

MPI datatype for CULong (MPI_UNSIGNED_LONG).

datatypeUnsignedShort :: Datatype Source #

MPI datatype for CUShort (MPI_UNSIGNED_SHORT).

class HasDatatype a where Source #

A type class mapping Haskell types to MPI datatypes. This is used to automatically determine the MPI datatype for communication buffers.

Instances
HasDatatype CChar Source # 
Instance details

Defined in Control.Distributed.MPI

HasDatatype CUChar Source # 
Instance details

Defined in Control.Distributed.MPI

HasDatatype CShort Source # 
Instance details

Defined in Control.Distributed.MPI

HasDatatype CUShort Source # 
Instance details

Defined in Control.Distributed.MPI

HasDatatype CInt Source # 
Instance details

Defined in Control.Distributed.MPI

HasDatatype CUInt Source # 
Instance details

Defined in Control.Distributed.MPI

HasDatatype CLong Source # 
Instance details

Defined in Control.Distributed.MPI

HasDatatype CULong Source # 
Instance details

Defined in Control.Distributed.MPI

HasDatatype CLLong Source # 
Instance details

Defined in Control.Distributed.MPI

HasDatatype CFloat Source # 
Instance details

Defined in Control.Distributed.MPI

HasDatatype CDouble Source # 
Instance details

Defined in Control.Distributed.MPI

HasDatatype a => HasDatatype (Min a) Source # 
Instance details

Defined in Control.Distributed.MPI

HasDatatype a => HasDatatype (Max a) Source # 
Instance details

Defined in Control.Distributed.MPI

HasDatatype a => HasDatatype (Sum a) Source # 
Instance details

Defined in Control.Distributed.MPI

HasDatatype a => HasDatatype (Product a) Source # 
Instance details

Defined in Control.Distributed.MPI

Reduction operations

newtype Op Source #

An MPI reduction operation, wrapping MPI_Op. Reduction operations need to be explicitly created and freed by the MPI library. Predefined operation exist for simple semigroups such as sum, maximum, or minimum.

An MPI reduction operation corresponds to a Semigroup, not a Monoid, i.e. MPI has no notion of a respective neutral element.

Constructors

Op COp 
Instances
Eq Op Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

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

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

Ord Op Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

compare :: Op -> Op -> Ordering #

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

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

(>) :: Op -> Op -> Bool #

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

max :: Op -> Op -> Op #

min :: Op -> Op -> Op #

Show Op Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

showsPrec :: Int -> Op -> ShowS #

show :: Op -> String #

showList :: [Op] -> ShowS #

opNull :: Op Source #

A null (invalid) reduction operation (MPI_OP_NULL).

opBand :: Op Source #

The bitwise and (.&.) reduction operation (MPI_BAND).

opBor :: Op Source #

The bitwise or (.|.) reduction operation (MPI_BOR).

opBxor :: Op Source #

The bitwise (xor) reduction operation (MPI_BXOR).

opLand :: Op Source #

The logical and (&&) reduction operation (MPI_LAND).

opLor :: Op Source #

The logical or (||) reduction operation (MPI_LOR).

opLxor :: Op Source #

The logical xor reduction operation (MPI_LXOR).

opMax :: Op Source #

The maximum reduction operation (MPI_MAX).

opMaxloc :: Op Source #

The argmax reduction operation to find the maximum and its rank (MPI_MAXLOC).

opMin :: Op Source #

The minimum reduction operation (MPI_MIN).

opMinloc :: Op Source #

The argmin reduction operation to find the minimum and its rank (MPI_MINLOC).

opProd :: Op Source #

The (product) reduction operation (MPI_PROD).

opSum :: Op Source #

The (sum) reduction operation (MPI_SUM).

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
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 () #

Binary Rank Source # 
Instance details

Defined in Control.Distributed.MPI.Binary

Methods

put :: Rank -> Put #

get :: Get Rank #

putList :: [Rank] -> Put #

Store Rank Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

size :: Size Rank

poke :: Rank -> Poke ()

peek :: Peek Rank

type Rep Rank Source # 
Instance details

Defined in Control.Distributed.MPI

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

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.

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.

Communication requests

newtype Request Source #

An MPI request, wrapping MPI_Request. A request describes a communication that is currently in progress. Each request must be explicitly freed via cancel, test, or wait.

Some MPI functions modify existing requests. The new requests are never interesting, and will not be returned.

TODO: Handle Comm, Datatype etc. in this way as well (all except Status).

Constructors

Request CRequest 
Instances
Eq Request Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

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

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

Ord Request Source # 
Instance details

Defined in Control.Distributed.MPI

Show Request Source # 
Instance details

Defined in Control.Distributed.MPI

requestNull :: IO Request Source #

A null (invalid) request (MPI_REQUEST_NULL).

Message status

newtype Status Source #

An MPI status, wrapping MPI_Status. The status describes certain properties of a message. It contains information such as the source of a communication (getSource), the message tag (getTag), or the size of the message (getCount, getElements).

In many cases, the status is not interesting. In this case, you can use alternative functions ending with an underscore (e.g. recv_) that do not calculate a status.

The status is particularly interesting when using probe or iprobe, as it describes a message that is ready to be received, but which has not been received yet.

Constructors

Status (ForeignPtr Status) 
Instances
Eq Status Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

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

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

Ord Status Source # 
Instance details

Defined in Control.Distributed.MPI

Show Status Source # 
Instance details

Defined in Control.Distributed.MPI

getSource :: Status -> IO Rank Source #

Get the source rank of a message (MPI_SOURCE).

getTag :: Status -> IO Tag Source #

Get the message tag (MPI_TAG).

getCount Source #

Arguments

:: Status

Message status

-> Datatype

MPI datatype

-> IO Count 

Get the size of a message, in terms of objects of type Datatype (MPI_Get_count). To determine the MPI datatype for a given Haskell type, use datatype (call e.g. as 'datatype @CInt').

getElements Source #

Arguments

:: Status

Message status

-> Datatype

MPI datatype

-> IO Int 

Get the number of elements in message, in terms of sub-object of the type datatype (MPI_Get_elements). This is useful when a message contains partial objects of type datatype. To determine the MPI datatype for a given Haskell type, use datatype (call e.g. as 'datatype @CInt').

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
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 () #

Store Tag Source # 
Instance details

Defined in Control.Distributed.MPI

Methods

size :: Size Tag

poke :: Tag -> Poke ()

peek :: Peek Tag

type Rep Tag Source # 
Instance details

Defined in Control.Distributed.MPI

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

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.

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.

Thread support

data ThreadSupport Source #

Thread support levels for MPI (see initThread):

  • ThreadSingle (MPI_THREAD_SINGLE): The application must be
  • single-threaded
  • ThreadFunneled (MPI_THREAD_FUNNELED): The application might be multi-threaded, but only a single thread will call MPI
  • ThreadSerialized (MPI_THREAD_SERIALIZED): The application might be multi-threaded, but the application guarantees that only one thread at a time will call MPI
  • ThreadMultiple (MPI_THREAD_MULTIPLE): The application is multi-threaded, and different threads might call MPI at the same time
Instances
Enum ThreadSupport Source #

When MPI is initialized with this library, then it will remember the provided level of thread support. (This might be less than the requested level.)

Instance details

Defined in Control.Distributed.MPI

Eq ThreadSupport Source # 
Instance details

Defined in Control.Distributed.MPI

Ord ThreadSupport Source # 
Instance details

Defined in Control.Distributed.MPI

Read ThreadSupport Source # 
Instance details

Defined in Control.Distributed.MPI

Show ThreadSupport Source # 
Instance details

Defined in Control.Distributed.MPI

Generic ThreadSupport Source # 
Instance details

Defined in Control.Distributed.MPI

Associated Types

type Rep ThreadSupport :: Type -> Type #

Store ThreadSupport Source # 
Instance details

Defined in Control.Distributed.MPI

type Rep ThreadSupport Source # 
Instance details

Defined in Control.Distributed.MPI

type Rep ThreadSupport = D1 (MetaData "ThreadSupport" "Control.Distributed.MPI" "mpi-hs-0.5.2.0-6qrutEbP7yF4EH47o63F1o" False) ((C1 (MetaCons "ThreadSingle" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ThreadFunneled" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ThreadSerialized" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ThreadMultiple" PrefixI False) (U1 :: Type -> Type)))

Functions

Initialization and shutdown

abort Source #

Arguments

:: Comm

Communicator describing which processes to terminate

-> Int

Error code

-> IO () 

Terminate MPI execution environment (MPI_Abort).

finalize :: IO () Source #

Finalize (shut down) the MPI library (collective, MPI_Finalize).

finalized :: IO Bool Source #

Return whether the MPI library has been finalized (MPI_Finalized).

init :: IO () Source #

Initialize the MPI library (collective, MPI_Init). This corresponds to calling initThread ThreadSingle.

initThread Source #

Arguments

:: ThreadSupport

required level of thread support

-> IO ThreadSupport

provided level of thread support

Initialize the MPI library (collective, MPI_Init_thread). Note that the provided level of thread support might be less than (!) the required level.

initialized :: IO Bool Source #

Return whether the MPI library has been initialized (MPI_Initialized).

Inquiry

getLibraryVersion :: IO String Source #

Return the version of the MPI library (MPI_Get_library_version). Note that the version of the MPI standard that this library implements is returned by getVersion.

getProcessorName :: IO String Source #

Return the name of the current process (MPI_Get_Processor_name). This should uniquely identify the hardware on which this process is running.

getVersion :: IO Version Source #

Return the version of the MPI standard implemented by this library (MPI_Get_version). Note that the version of the MPI library itself is returned by getLibraryVersion.

Point-to-point (blocking)

probe Source #

Arguments

:: Rank

Source rank (may be anySource)

-> Tag

Message tag (may be anyTag)

-> Comm

Communicator

-> IO Status

Message status

Probe (wait) for an incoming message (MPI_Probe).

probe_ Source #

Arguments

:: Rank

Source rank (may be anySource)

-> Tag

Message tag (may be anyTag)

-> Comm

Communicator

-> IO () 

Probe (wait) for an incoming message (MPI_Probe). This function does not return a status, which might be more efficient if the status is not needed.

recv Source #

Arguments

:: Buffer rb 
=> rb

Receive buffer

-> Rank

Source rank (may be anySource)

-> Tag

Message tag (may be anyTag)

-> Comm

Communicator

-> IO Status

Message status

Receive a message (MPI_Recv). The MPI datatypeis determined automatically from the buffer pointer type.

recv_ Source #

Arguments

:: Buffer rb 
=> rb

Receive buffer

-> Rank

Source rank (may be anySource)

-> Tag

Message tag (may be anyTag)

-> Comm

Communicator

-> IO () 

Receive a message (MPI_Recv). The MPI datatype is determined automatically from the buffer pointer type. This function does not return a status, which might be more efficient if the status is not needed.

send Source #

Arguments

:: Buffer sb 
=> sb

Send buffer

-> Rank

Destination rank

-> Tag

Message tag

-> Comm

Communicator

-> IO () 

Send a message (MPI_Send). The MPI datatype is determined automatically from the buffer pointer type.

sendrecv Source #

Arguments

:: (Buffer sb, Buffer rb) 
=> sb

Send buffer

-> Rank

Destination rank

-> Tag

Sent message tag

-> rb

Receive buffer

-> Rank

Source rank (may be anySource)

-> Tag

Received message tag (may be anyTag)

-> Comm

Communicator

-> IO Status

Status for received message

Send and receive a message with a single call (MPI_Sendrecv). The MPI datatypes are determined automatically from the buffer pointer types.

sendrecv_ Source #

Arguments

:: (Buffer sb, Buffer rb) 
=> sb

Send buffer

-> Rank

Destination rank

-> Tag

Sent message tag

-> rb

Receive buffer

-> Rank

Source rank (may be anySource)

-> Tag

Received message tag (may be anyTag)

-> Comm

Communicator

-> IO () 

Send and receive a message with a single call (MPI_Sendrecv). The MPI datatypes are determined automatically from the buffer pointer types. This function does not return a status, which might be more efficient if the status is not needed.

wait Source #

Arguments

:: Request

Communication request

-> IO Status

Message status

Wait for a communication request to complete, then free the request (MPI_Wait).

wait_ Source #

Arguments

:: Request

Communication request

-> IO () 

Wait for a communication request to complete, then free the request (MPI_Wait). This function does not return a status, which might be more efficient if the status is not needed.

Point-to-point (non-blocking)

iprobe Source #

Arguments

:: Rank

Source rank (may be anySource)

-> Tag

Message tag (may be anyTag)

-> Comm

Communicator

-> IO (Maybe Status)

Just Status of the message if a message is available, else Nothing

Probe (check) for incoming messages without waiting (non-blocking, MPI_Iprobe).

iprobe_ Source #

Arguments

:: Rank

Source rank (may be anySource)

-> Tag

Message tag (may be anyTag)

-> Comm

Communicator

-> IO Bool

Whether a message is available

Probe (check) for an incoming message without waiting (MPI_Iprobe). This function does not return a status, which might be more efficient if the status is not needed.

irecv Source #

Arguments

:: Buffer rb 
=> rb

Receive buffer

-> Rank

Source rank (may be anySource)

-> Tag

Message tag (may be anyTag)

-> Comm

Communicator

-> IO Request

Communication request

Begin to receive a message, and return a handle to the communication request (non-blocking, MPI_Irecv). The request must be freed by calling test, wait, or similar. The MPI datatype is determined automatically from the buffer pointer type.

isend Source #

Arguments

:: Buffer sb 
=> sb

Send buffer

-> Rank

Destination rank

-> Tag

Message tag

-> Comm

Communicator

-> IO Request

Communication request

Begin to send a message, and return a handle to the communication request (non-blocking, MPI_Isend). The request must be freed by calling test, wait, or similar. The MPI datatype is determined automatically from the buffer pointer type.

requestGetStatus Source #

Arguments

:: Request

Communication request

-> IO (Maybe Status)

Just Status if the request has completed, else Nothing

Check whether a communication has completed without freeing the communication request (MPI_Request_get_status).

requestGetStatus_ :: Request -> IO Bool Source #

Check whether a communication has completed without freeing the communication request (MPI_Request_get_status). This function does not return a status, which might be more efficient if the status is not needed.

test Source #

Arguments

:: Request

Communication request

-> IO (Maybe Status)

Just Status if the request has completed, else Nothing

Check whether a communication has completed, and free the communication request if so (MPI_Test).

test_ :: Request -> IO Bool Source #

Check whether a communication has completed, and free the communication request if so (MPI_Test). This function does not return a status, which might be more efficient if the status is not needed.

Collective (blocking)

allgather Source #

Arguments

:: (Buffer sb, Buffer rb) 
=> sb

Source buffer

-> rb

Destination buffer

-> Comm

Communicator

-> IO () 

Gather data from all processes and broadcast the result (collective, MPI_Allgather).

allreduce Source #

Arguments

:: (Buffer sb, Buffer rb) 
=> sb

Source buffer

-> rb

Destination buffer

-> Op

Reduction operation

-> Comm

Communicator

-> IO () 

Reduce data from all processes and broadcast the result (collective, MPI_Allreduce). The MPI datatype is determined automatically from the buffer pointer types.

alltoall Source #

Arguments

:: (Buffer sb, Buffer rb) 
=> sb

Source buffer

-> rb

Destination buffer

-> Comm

Communicator

-> IO () 

Send data from all processes to all processes (collective, MPI_Alltoall). The MPI datatypes are determined automatically from the buffer pointer types.

barrier Source #

Arguments

:: Comm

Communicator

-> IO () 

Barrier (collective, MPI_Barrier).

bcast Source #

Arguments

:: Buffer b 
=> b

Buffer (read on the root process, written on all other processes)

-> Rank

Root rank (sending process)

-> Comm

Communicator

-> IO () 

Broadcast data from one process to all processes (collective, MPI_Bcast). The MPI datatype is determined automatically from the buffer pointer type.

exscan Source #

Arguments

:: (Buffer sb, Buffer rb) 
=> sb

Source buffer

-> rb

Destination buffer

-> Op

Reduction operation

-> Comm

Communicator

-> IO () 

Reduce data from all processes via an exclusive (prefix) scan (collective, MPI_Exscan). Each process with rank r receives the result of reducing data from rank 0 to rank r-1 (inclusive). Rank 0 should logically receive a neutral element of the reduction operation, but instead receives an undefined value since MPI is not aware of neutral values for reductions.

The MPI datatype is determined automatically from the buffer pointer type.

gather Source #

Arguments

:: (Buffer sb, Buffer rb) 
=> sb

Source buffer

-> rb

Destination buffer (only used on the root process)

-> Rank

Root rank

-> Comm

Communicator

-> IO () 

Gather data from all processes to the root process (collective, MPI_Gather). The MPI datatypes are determined automatically from the buffer pointer types.

reduce Source #

Arguments

:: (Buffer sb, Buffer rb) 
=> sb

Source buffer

-> rb

Destination buffer

-> Op

Reduction operation

-> Rank

Root rank

-> Comm

Communicator

-> IO () 

Reduce data from all processes (collective, MPI_Reduce). The result is only available on the root process. The MPI datatypes are determined automatically from the buffer pointer types.

scan Source #

Arguments

:: (Buffer sb, Buffer rb) 
=> sb

Source buffer

-> rb

Destination buffer

-> Op

Reduction operation

-> Comm

Communicator

-> IO () 

Reduce data from all processes via an (inclusive) scan (collective, MPI_Scan). Each process with rank r receives the result of reducing data from rank 0 to rank r (inclusive). The MPI datatype is determined automatically from the buffer pointer type.

scatter Source #

Arguments

:: (Buffer sb, Buffer rb) 
=> sb

Source buffer (only used on the root process)

-> rb

Destination buffer

-> Rank

Root rank

-> Comm

Communicator

-> IO () 

Scatter data from the root process to all processes (collective, MPI_Scatter). The MPI datatypes are determined automatically from the buffer pointer types.

Collective (non-blocking)

iallgather Source #

Arguments

:: (Buffer sb, Buffer rb) 
=> sb

Source buffer

-> rb

Destination buffer

-> Comm

Communicator

-> IO Request

Communication request

Begin to gather data from all processes and broadcast the result, and return a handle to the communication request (collective, non-blocking, MPI_Iallgather). The request must be freed by calling test, wait, or similar. The MPI datatypes are determined automatically from the buffer pointer types.

iallreduce Source #

Arguments

:: (Buffer sb, Buffer rb) 
=> sb

Source buffer

-> rb

Destination buffer

-> Op

Reduction operation

-> Comm

Communicator

-> IO Request

Communication request

Begin to reduce data from all processes and broadcast the result, and return a handle to the communication request (collective, non-blocking, MPI_Iallreduce). The request must be freed by calling test, wait, or similar. The MPI datatype is determined automatically from the buffer pointer types.

ialltoall Source #

Arguments

:: (Buffer sb, Buffer rb) 
=> sb

Source buffer

-> rb

Destination buffer

-> Comm

Communicator

-> IO Request

Communication request

Begin to send data from all processes to all processes, and return a handle to the communication request (collective, non-blocking, MPI_Ialltoall). The request must be freed by calling test, wait, or similar. The MPI datatypes are determined automatically from the buffer pointer types.

ibarrier Source #

Arguments

:: Comm

Communicator

-> IO Request 

Start a barrier, and return a handle to the communication request (collective, non-blocking, MPI_Ibarrier). The request must be freed by calling test, wait, or similar.

ibcast Source #

Arguments

:: Buffer b 
=> b

Buffer (read on the root process, written on all other processes)

-> Rank

Root rank (sending process)

-> Comm

Communicator

-> IO Request

Communication request

Begin to broadcast data from one process to all processes, and return a handle to the communication request (collective, non-blocking, MPI_Ibcast). The request must be freed by calling test, wait, or similar. The MPI datatype is determined automatically from the buffer pointer type.

iexscan Source #

Arguments

:: (Buffer sb, Buffer rb) 
=> sb

Source buffer

-> rb

Destination buffer

-> Op

Reduction operation

-> Comm

Communicator

-> IO Request

Communication request

Begin to reduce data from all processes via an exclusive (prefix) scan, and return a handle to the communication request (collective, non-blocking, MPI_Iexscan). Each process with rank r receives the result of reducing data from rank 0 to rank r-1 (inclusive). Rank 0 should logically receive a neutral element of the reduction operation, but instead receives an undefined value since MPI is not aware of neutral values for reductions.

The request must be freed by calling test, wait, or similar. The MPI datatype is determined automatically from the buffer pointer type.

igather Source #

Arguments

:: (Buffer rb, Buffer sb) 
=> sb

Source buffer

-> rb

Destination buffer (relevant only on the root process)

-> Rank

Root rank

-> Comm

Communicator

-> IO Request

Communication request

Begin to gather data from all processes to the root process, and return a handle to the communication request (collective, non-blocking, MPI_Igather). The request must be freed by calling test, wait, or similar. The MPI datatypes are determined automatically from the buffer pointer types.

ireduce Source #

Arguments

:: (Buffer sb, Buffer rb) 
=> sb

Source buffer

-> rb

Destination buffer

-> Op

Reduction operation

-> Rank

Root rank

-> Comm

Communicator

-> IO Request

Communication request

Begin to reduce data from all processes, and return a handle to the communication request (collective, non-blocking, MPI_Ireduce). The result is only available on the root process. The request must be freed by calling test, wait, or similar. The MPI datatypes are determined automatically from the buffer pointer types.

iscan Source #

Arguments

:: (Buffer sb, Buffer rb) 
=> sb

Source buffer

-> rb

Destination buffer

-> Op

Reduction operation

-> Comm

Communicator

-> IO Request

Communication request

Begin to reduce data from all processes via an (inclusive) scan, and return a handle to the communication request (collective, non-blocking, MPI_Iscan). Each process with rank r receives the result of reducing data from rank 0 to rank r (inclusive). The request must be freed by calling test, wait, or similar. The MPI datatype is determined automatically from the buffer pointer type.

iscatter Source #

Arguments

:: (Buffer sb, Buffer rb) 
=> sb

Source buffer (only used on the root process)

-> rb

Destination buffer

-> Rank

Root rank

-> Comm

Communicator

-> IO Request

Communication request

Begin to scatter data from the root process to all processes, and return a handle to the communication request (collective, non-blocking, MPI_Iscatter). The request must be freed by calling test, wait, or similar. The MPI datatypes are determined automatically from the buffer pointer types.

Timing

wtick :: IO Double Source #

Wall time tick (accuracy of wtime) (in seconds)

wtime :: IO Double Source #

Current wall time (in seconds)