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

Control.Distributed.MPI.Binary

Description

 
Synopsis

Types, and associated functions and constants

Communicators

newtype Comm #

Constructors

Comm CComm 

Instances

Instances details
Eq Comm 
Instance details

Defined in Control.Distributed.MPI

Methods

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

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

Ord Comm 
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 
Instance details

Defined in Control.Distributed.MPI

Methods

showsPrec :: Int -> Comm -> ShowS #

show :: Comm -> String #

showList :: [Comm] -> ShowS #

Message sizes

newtype Count #

Constructors

Count CInt 

Instances

Instances details
Enum Count 
Instance details

Defined in Control.Distributed.MPI

Eq Count 
Instance details

Defined in Control.Distributed.MPI

Methods

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

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

Integral Count 
Instance details

Defined in Control.Distributed.MPI

Num Count 
Instance details

Defined in Control.Distributed.MPI

Ord Count 
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 
Instance details

Defined in Control.Distributed.MPI

Real Count 
Instance details

Defined in Control.Distributed.MPI

Methods

toRational :: Count -> Rational #

Show Count 
Instance details

Defined in Control.Distributed.MPI

Methods

showsPrec :: Int -> Count -> ShowS #

show :: Count -> String #

showList :: [Count] -> ShowS #

Generic Count 
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 
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 
Instance details

Defined in Control.Distributed.MPI

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

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

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

Process ranks

newtype Rank #

Constructors

Rank CInt 

Instances

Instances details
Enum Rank 
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 
Instance details

Defined in Control.Distributed.MPI

Methods

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

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

Integral Rank 
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 
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 
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 
Instance details

Defined in Control.Distributed.MPI

Real Rank 
Instance details

Defined in Control.Distributed.MPI

Methods

toRational :: Rank -> Rational #

Show Rank 
Instance details

Defined in Control.Distributed.MPI

Methods

showsPrec :: Int -> Rank -> ShowS #

show :: Rank -> String #

showList :: [Rank] -> ShowS #

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

type Rep Rank 
Instance details

Defined in Control.Distributed.MPI

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

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

toRank :: Enum e => e -> 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.Binary

Methods

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

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

Ord Status Source # 
Instance details

Defined in Control.Distributed.MPI.Binary

Read Status Source # 
Instance details

Defined in Control.Distributed.MPI.Binary

Show Status Source # 
Instance details

Defined in Control.Distributed.MPI.Binary

Message tags

newtype Tag #

Constructors

Tag CInt 

Instances

Instances details
Enum Tag 
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 
Instance details

Defined in Control.Distributed.MPI

Methods

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

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

Num Tag 
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 
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 
Instance details

Defined in Control.Distributed.MPI

Show Tag 
Instance details

Defined in Control.Distributed.MPI

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Generic Tag 
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 
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 
Instance details

Defined in Control.Distributed.MPI

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

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

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

data Request a Source #

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

Functions

Initialization and shutdown

abort :: Comm -> Int -> IO () #

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 :: Comm -> IO () #

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 #

Orphan instances

Binary CInt Source # 
Instance details

Methods

put :: CInt -> Put #

get :: Get CInt #

putList :: [CInt] -> Put #

Binary Rank Source # 
Instance details

Methods

put :: Rank -> Put #

get :: Get Rank #

putList :: [Rank] -> Put #