{-# LINE 1 "lib/Control/Distributed/MPI.chs" #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE PartialTypeSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -Wno-type-defaults #-}
module Control.Distributed.MPI
(
Comm(..)
, ComparisonResult(..)
, commCompare
, commRank
, commSize
, commNull
, commSelf
, commWorld
, Count(..)
, fromCount
, toCount
, countUndefined
, Datatype(..)
, Pointer(..)
, datatypeNull
, datatypeByte
, datatypeChar
, datatypeDouble
, datatypeFloat
, datatypeInt
, datatypeLong
, datatypeLongDouble
, datatypeLongLongInt
, datatypeShort
, datatypeUnsigned
, datatypeUnsignedChar
, datatypeUnsignedLong
, datatypeUnsignedShort
, HasDatatype(..)
, Op(..)
, opNull
, opBand
, opBor
, opBxor
, opLand
, opLor
, opLxor
, opMax
, opMaxloc
, opMin
, opMinloc
, opProd
, opSum
, Rank(..)
, fromRank
, rootRank
, toRank
, anySource
, Request(..)
, requestNull
, Status(..)
, getSource
, getTag
, getCount
, getElements
, Tag(..)
, fromTag
, toTag
, unitTag
, anyTag
, ThreadSupport(..)
, threadSupport
, abort
, finalize
, finalized
, init
, initThread
, initialized
, getLibraryVersion
, getProcessorName
, getVersion
, probe
, probe_
, recv
, recv_
, send
, sendrecv
, sendrecv_
, wait
, wait_
, iprobe
, iprobe_
, irecv
, isend
, test
, test_
, allgather
, allreduce
, alltoall
, barrier
, bcast
, exscan
, gather
, reduce
, scan
, scatter
, iallgather
, iallreduce
, ialltoall
, ibarrier
, ibcast
, iexscan
, igather
, ireduce
, iscan
, iscatter
, wtick
, wtime
) where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.ForeignPtr as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import qualified Foreign.Storable as C2HSImp
import qualified System.IO.Unsafe as C2HSImp
import Prelude hiding (fromEnum, fst, init, toEnum)
import qualified Prelude
import Control.Monad (liftM)
import Data.Coerce
import Data.IORef
import Data.Ix
import qualified Data.Monoid as Monoid
import qualified Data.Semigroup as Semigroup
import Data.Version
import Foreign
import Foreign.C.String
import Foreign.C.Types
import GHC.Arr (indexError)
import System.IO.Unsafe (unsafePerformIO)
default (Int)
{-# LINE 253 "lib/Control/Distributed/MPI.chs" #-}
foreign import ccall "&rts_argc" rtsArgc :: Ptr CInt
foreign import ccall "&rts_argv" rtsArgv :: Ptr (Ptr CString)
argc :: CInt
argv :: Ptr CString
argc = unsafePerformIO $ peek rtsArgc
argv = unsafePerformIO $ peek rtsArgv
fromEnum :: (Enum e, Integral i) => e -> i
fromEnum = fromIntegral . Prelude.fromEnum
toEnum :: (Integral i, Enum e) => i -> e
toEnum = Prelude.toEnum . fromIntegral
bool2maybe :: (Bool, a) -> Maybe a
bool2maybe (False, _) = Nothing
bool2maybe (True, x) = Just x
peekBool :: (Integral a, Storable a) => Ptr a -> IO Bool
peekBool = liftM toBool . peek
peekCoerce :: (Storable a, Coercible a b) => Ptr a -> IO b
peekCoerce = liftM coerce . peek
peekEnum :: (Integral i, Storable i, Enum e) => Ptr i -> IO e
peekEnum = liftM toEnum . peek
peekInt :: (Integral i, Storable i) => Ptr i -> IO Int
peekInt = liftM fromIntegral . peek
class Pointer p where
withPtr :: Storable a => p a -> (Ptr a -> IO b) -> IO b
instance Pointer Ptr where
withPtr p f = f p
instance Pointer ForeignPtr where
withPtr = withForeignPtr
instance Pointer StablePtr where
withPtr p f = f (castPtr (castStablePtrToPtr p))
newtype Comm = Comm (C2HSImp.ForeignPtr (Comm))
withComm :: Comm -> (C2HSImp.Ptr Comm -> IO b) -> IO b
withComm (Comm fptr) = C2HSImp.withForeignPtr fptr
{-# LINE 328 "lib/Control/Distributed/MPI.chs" #-}
deriving instance Eq Comm
deriving instance Ord Comm
deriving instance Show Comm
data ComparisonResult = Identical
| Congruent
| Similar
| Unequal
deriving (Eq,Ord,Read,Show)
instance Enum ComparisonResult where
succ Identical = Congruent
succ Congruent = Similar
succ Similar = Unequal
succ Unequal = error "ComparisonResult.succ: Unequal has no successor"
pred Congruent = Identical
pred Similar = Congruent
pred Unequal = Similar
pred Identical = error "ComparisonResult.pred: Identical has no predecessor"
enumFromTo from to = go from
where
end = fromEnum to
go v = case compare (fromEnum v) end of
LT -> v : go (succ v)
EQ -> [v]
GT -> []
enumFrom from = enumFromTo from Unequal
fromEnum Identical = 0
fromEnum Congruent = 1
fromEnum Similar = 2
fromEnum Unequal = 3
toEnum 0 = Identical
toEnum 1 = Congruent
toEnum 2 = Similar
toEnum 3 = Unequal
toEnum unmatched = error ("ComparisonResult.toEnum: Cannot match " ++ show unmatched)
{-# LINE 335 "lib/Control/Distributed/MPI.chs" #-}
newtype Count = Count CInt
deriving (Eq, Ord, Enum, Integral, Num, Real, Storable)
instance Read Count where
readsPrec p = map (\(c, s) -> (Count c, s)) . readsPrec p
instance Show Count where
showsPrec p (Count c) = showsPrec p c
toCount :: Integral i => i -> Count
toCount i = Count (fromIntegral i)
fromCount :: Integral i => Count -> i
fromCount (Count c) = fromIntegral c
newtype Datatype = Datatype (C2HSImp.ForeignPtr (Datatype))
withDatatype :: Datatype -> (C2HSImp.Ptr Datatype -> IO b) -> IO b
withDatatype (Datatype fptr) = C2HSImp.withForeignPtr fptr
{-# LINE 365 "lib/Control/Distributed/MPI.chs" #-}
deriving instance Eq Datatype
deriving instance Ord Datatype
deriving instance Show Datatype
newtype Op = Op (C2HSImp.ForeignPtr (Op))
withOp :: Op -> (C2HSImp.Ptr Op -> IO b) -> IO b
withOp (Op fptr) = C2HSImp.withForeignPtr fptr
{-# LINE 380 "lib/Control/Distributed/MPI.chs" #-}
deriving instance Eq Op
deriving instance Ord Op
deriving instance Show Op
newtype Rank = Rank CInt
deriving (Eq, Ord, Enum, Integral, Num, Real, Storable)
instance Read Rank where
readsPrec p = map (\(r, s) -> (Rank r, s)) . readsPrec p
instance Show Rank where
showsPrec p (Rank r) = showsPrec p r
instance Ix Rank where
range (Rank rmin, Rank rmax) = Rank <$> [rmin..rmax]
{-# INLINE index #-}
index b@(Rank rmin, _) i@(Rank r)
| inRange b i = fromIntegral (r - rmin)
| otherwise = indexError b i "MPI.Rank"
inRange (Rank rmin, Rank rmax) (Rank r) = rmin <= r && r <= rmax
toRank :: Enum e => e -> Rank
toRank e = Rank (fromIntegral (fromEnum e))
fromRank :: Enum e => Rank -> e
fromRank (Rank r) = toEnum (fromIntegral r)
rootRank :: Rank
rootRank = toRank 0
newtype Request = Request (C2HSImp.ForeignPtr (Request))
withRequest :: Request -> (C2HSImp.Ptr Request -> IO b) -> IO b
withRequest (Request fptr) = C2HSImp.withForeignPtr fptr
{-# LINE 432 "lib/Control/Distributed/MPI.chs" #-}
deriving instance Eq Request
deriving instance Ord Request
deriving instance Show Request
newtype Status = Status (C2HSImp.ForeignPtr (Status))
withStatus :: Status -> (C2HSImp.Ptr Status -> IO b) -> IO b
withStatus (Status fptr) = C2HSImp.withForeignPtr fptr
{-# LINE 452 "lib/Control/Distributed/MPI.chs" #-}
deriving instance Eq Status
deriving instance Ord Status
deriving instance Show Status
getSource :: Status -> IO Rank
getSource (Status fst) =
withForeignPtr fst (\pst -> Rank <$> (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CInt}) pst)
getTag :: Status -> IO Tag
getTag (Status fst) =
withForeignPtr fst (\pst -> Tag <$> (\ptr -> do {C2HSImp.peekByteOff ptr 4 :: IO C2HSImp.CInt}) pst)
newtype Tag = Tag CInt
deriving (Eq, Ord, Read, Show, Enum, Num, Storable)
toTag :: Enum e => e -> Tag
toTag e = Tag (fromIntegral (fromEnum e))
fromTag :: Enum e => Tag -> e
fromTag (Tag t) = toEnum (fromIntegral t)
unitTag :: Tag
unitTag = toTag ()
data ThreadSupport = ThreadSingle
| ThreadFunneled
| ThreadSerialized
| ThreadMultiple
deriving (Eq,Ord,Read,Show)
instance Enum ThreadSupport where
succ ThreadSingle = ThreadFunneled
succ ThreadFunneled = ThreadSerialized
succ ThreadSerialized = ThreadMultiple
succ ThreadMultiple = error "ThreadSupport.succ: ThreadMultiple has no successor"
pred ThreadFunneled = ThreadSingle
pred ThreadSerialized = ThreadFunneled
pred ThreadMultiple = ThreadSerialized
pred ThreadSingle = error "ThreadSupport.pred: ThreadSingle has no predecessor"
enumFromTo from to = go from
where
end = fromEnum to
go v = case compare (fromEnum v) end of
LT -> v : go (succ v)
EQ -> [v]
GT -> []
enumFrom from = enumFromTo from ThreadMultiple
fromEnum ThreadSingle = 0
fromEnum ThreadFunneled = 1
fromEnum ThreadSerialized = 2
fromEnum ThreadMultiple = 3
toEnum 0 = ThreadSingle
toEnum 1 = ThreadFunneled
toEnum 2 = ThreadSerialized
toEnum 3 = ThreadMultiple
toEnum unmatched = error ("ThreadSupport.toEnum: Cannot match " ++ show unmatched)
{-# LINE 512 "lib/Control/Distributed/MPI.chs" #-}
threadSupport :: IO (Maybe ThreadSupport)
threadSupport = readIORef providedThreadSupport
providedThreadSupport :: IORef (Maybe ThreadSupport)
providedThreadSupport = unsafePerformIO (newIORef Nothing)
commNull :: (Comm)
commNull =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
commNull'_ a1' >>
return (Comm a1'')
{-# LINE 532 "lib/Control/Distributed/MPI.chs" #-}
commSelf :: (Comm)
commSelf =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
commSelf'_ a1' >>
return (Comm a1'')
{-# LINE 536 "lib/Control/Distributed/MPI.chs" #-}
commWorld :: (Comm)
commWorld =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
commWorld'_ a1' >>
return (Comm a1'')
{-# LINE 540 "lib/Control/Distributed/MPI.chs" #-}
countUndefined :: (Count)
countUndefined =
C2HSImp.unsafePerformIO $
countUndefined'_ >>= \res ->
let {res' = toCount res} in
return (res')
{-# LINE 547 "lib/Control/Distributed/MPI.chs" #-}
datatypeNull :: (Datatype)
datatypeNull =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
datatypeNull'_ a1' >>
return (Datatype a1'')
{-# LINE 552 "lib/Control/Distributed/MPI.chs" #-}
datatypeByte :: (Datatype)
datatypeByte =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
datatypeByte'_ a1' >>
return (Datatype a1'')
{-# LINE 555 "lib/Control/Distributed/MPI.chs" #-}
datatypeChar :: (Datatype)
datatypeChar =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
datatypeChar'_ a1' >>
return (Datatype a1'')
{-# LINE 558 "lib/Control/Distributed/MPI.chs" #-}
datatypeDouble :: (Datatype)
datatypeDouble =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
datatypeDouble'_ a1' >>
return (Datatype a1'')
{-# LINE 561 "lib/Control/Distributed/MPI.chs" #-}
datatypeFloat :: (Datatype)
datatypeFloat =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
datatypeFloat'_ a1' >>
return (Datatype a1'')
{-# LINE 564 "lib/Control/Distributed/MPI.chs" #-}
datatypeInt :: (Datatype)
datatypeInt =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
datatypeInt'_ a1' >>
return (Datatype a1'')
{-# LINE 567 "lib/Control/Distributed/MPI.chs" #-}
datatypeLong :: (Datatype)
datatypeLong =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
datatypeLong'_ a1' >>
return (Datatype a1'')
{-# LINE 570 "lib/Control/Distributed/MPI.chs" #-}
datatypeLongDouble :: (Datatype)
datatypeLongDouble =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
datatypeLongDouble'_ a1' >>
return (Datatype a1'')
{-# LINE 573 "lib/Control/Distributed/MPI.chs" #-}
datatypeLongLongInt :: (Datatype)
datatypeLongLongInt =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
datatypeLongLongInt'_ a1' >>
return (Datatype a1'')
{-# LINE 577 "lib/Control/Distributed/MPI.chs" #-}
datatypeShort :: (Datatype)
datatypeShort =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
datatypeShort'_ a1' >>
return (Datatype a1'')
{-# LINE 580 "lib/Control/Distributed/MPI.chs" #-}
datatypeUnsigned :: (Datatype)
datatypeUnsigned =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
datatypeUnsigned'_ a1' >>
return (Datatype a1'')
{-# LINE 583 "lib/Control/Distributed/MPI.chs" #-}
datatypeUnsignedChar :: (Datatype)
datatypeUnsignedChar =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
datatypeUnsignedChar'_ a1' >>
return (Datatype a1'')
{-# LINE 586 "lib/Control/Distributed/MPI.chs" #-}
datatypeUnsignedLong :: (Datatype)
datatypeUnsignedLong =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
datatypeUnsignedLong'_ a1' >>
return (Datatype a1'')
{-# LINE 589 "lib/Control/Distributed/MPI.chs" #-}
datatypeUnsignedShort :: (Datatype)
datatypeUnsignedShort =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
datatypeUnsignedShort'_ a1' >>
return (Datatype a1'')
{-# LINE 592 "lib/Control/Distributed/MPI.chs" #-}
class HasDatatype a where datatype :: Datatype
instance HasDatatype CChar where datatype = datatypeChar
instance HasDatatype CDouble where datatype = datatypeDouble
instance HasDatatype CFloat where datatype = datatypeFloat
instance HasDatatype CInt where datatype = datatypeInt
instance HasDatatype CLLong where datatype = datatypeLongLongInt
instance HasDatatype CLong where datatype = datatypeLong
instance HasDatatype CShort where datatype = datatypeShort
instance HasDatatype CUChar where datatype = datatypeUnsignedChar
instance HasDatatype CUInt where datatype = datatypeUnsigned
instance HasDatatype CULong where datatype = datatypeUnsignedLong
instance HasDatatype CUShort where datatype = datatypeUnsignedShort
opNull :: (Op)
opNull =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
opNull'_ a1' >>
return (Op a1'')
{-# LINE 694 "lib/Control/Distributed/MPI.chs" #-}
opBand :: (Op)
opBand =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
opBand'_ a1' >>
return (Op a1'')
{-# LINE 697 "lib/Control/Distributed/MPI.chs" #-}
opBor :: (Op)
opBor =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
opBor'_ a1' >>
return (Op a1'')
{-# LINE 700 "lib/Control/Distributed/MPI.chs" #-}
opBxor :: (Op)
opBxor =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
opBxor'_ a1' >>
return (Op a1'')
{-# LINE 703 "lib/Control/Distributed/MPI.chs" #-}
opLand :: (Op)
opLand =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
opLand'_ a1' >>
return (Op a1'')
{-# LINE 706 "lib/Control/Distributed/MPI.chs" #-}
opLor :: (Op)
opLor =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
opLor'_ a1' >>
return (Op a1'')
{-# LINE 709 "lib/Control/Distributed/MPI.chs" #-}
opLxor :: (Op)
opLxor =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
opLxor'_ a1' >>
return (Op a1'')
{-# LINE 712 "lib/Control/Distributed/MPI.chs" #-}
opMax :: (Op)
opMax =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
opMax'_ a1' >>
return (Op a1'')
{-# LINE 715 "lib/Control/Distributed/MPI.chs" #-}
opMaxloc :: (Op)
opMaxloc =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
opMaxloc'_ a1' >>
return (Op a1'')
{-# LINE 719 "lib/Control/Distributed/MPI.chs" #-}
opMin :: (Op)
opMin =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
opMin'_ a1' >>
return (Op a1'')
{-# LINE 722 "lib/Control/Distributed/MPI.chs" #-}
opMinloc :: (Op)
opMinloc =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
opMinloc'_ a1' >>
return (Op a1'')
{-# LINE 726 "lib/Control/Distributed/MPI.chs" #-}
opProd :: (Op)
opProd =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
opProd'_ a1' >>
return (Op a1'')
{-# LINE 729 "lib/Control/Distributed/MPI.chs" #-}
opSum :: (Op)
opSum =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
opSum'_ a1' >>
return (Op a1'')
{-# LINE 732 "lib/Control/Distributed/MPI.chs" #-}
instance HasDatatype a => HasDatatype (Monoid.Product a) where
datatype = datatype @a
instance HasDatatype a => HasDatatype (Monoid.Sum a) where
datatype = datatype @a
instance HasDatatype a => HasDatatype (Semigroup.Max a) where
datatype = datatype @a
instance HasDatatype a => HasDatatype (Semigroup.Min a) where
datatype = datatype @a
anySource :: (Rank)
anySource =
C2HSImp.unsafePerformIO $
anySource'_ >>= \res ->
let {res' = toRank res} in
return (res')
{-# LINE 759 "lib/Control/Distributed/MPI.chs" #-}
requestNull :: (Request)
requestNull =
C2HSImp.unsafePerformIO $
C2HSImp.mallocForeignPtrBytes 8 >>= \a1'' -> C2HSImp.withForeignPtr a1'' $ \a1' ->
requestNull'_ a1' >>
return (Request a1'')
{-# LINE 764 "lib/Control/Distributed/MPI.chs" #-}
statusIgnore :: (Status)
statusIgnore =
C2HSImp.unsafePerformIO $
statusIgnore'_ >>= \res ->
(\x -> C2HSImp.newForeignPtr_ x >>= (return . Status)) res >>= \res' ->
return (res')
{-# LINE 768 "lib/Control/Distributed/MPI.chs" #-}
withStatusIgnore :: (Ptr Status -> IO a) -> IO a
withStatusIgnore = withStatus statusIgnore
anyTag :: (Tag)
anyTag =
C2HSImp.unsafePerformIO $
anyTag'_ >>= \res ->
let {res' = toTag res} in
return (res')
{-# LINE 779 "lib/Control/Distributed/MPI.chs" #-}
abort :: (Comm)
-> (Int)
-> IO ()
abort a1 a2 =
withComm a1 $ \a1' ->
let {a2' = fromIntegral a2} in
abort'_ a1' a2' >>= \res ->
return res >>
return ()
{-# LINE 795 "lib/Control/Distributed/MPI.chs" #-}
allgatherTyped :: (Ptr ()) -> (Count) -> (Datatype) -> (Ptr ()) -> (Count) -> (Datatype) -> (Comm) -> IO ()
allgatherTyped a1 a2 a3 a4 a5 a6 a7 =
let {a1' = id a1} in
let {a2' = fromCount a2} in
withDatatype a3 $ \a3' ->
let {a4' = id a4} in
let {a5' = fromCount a5} in
withDatatype a6 $ \a6' ->
withComm a7 $ \a7' ->
allgatherTyped'_ a1' a2' a3' a4' a5' a6' a7' >>= \res ->
return res >>
return ()
{-# LINE 805 "lib/Control/Distributed/MPI.chs" #-}
allgather :: forall a b p q.
( Pointer p, Pointer q
, Storable a, HasDatatype a, Storable b, HasDatatype b)
=> p a
-> Count
-> q b
-> Count
-> Comm
-> IO ()
allgather sendbuf sendcount recvbuf recvcount comm =
withPtr sendbuf $ \sendbuf' ->
withPtr recvbuf $ \recvbuf' ->
allgatherTyped (castPtr sendbuf') sendcount (datatype @a)
(castPtr recvbuf') recvcount (datatype @b)
comm
allreduceTyped :: (Ptr ()) -> (Ptr ()) -> (Count) -> (Datatype) -> (Op) -> (Comm) -> IO ()
allreduceTyped a1 a2 a3 a4 a5 a6 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = fromCount a3} in
withDatatype a4 $ \a4' ->
withOp a5 $ \a5' ->
withComm a6 $ \a6' ->
allreduceTyped'_ a1' a2' a3' a4' a5' a6' >>= \res ->
return res >>
return ()
{-# LINE 835 "lib/Control/Distributed/MPI.chs" #-}
allreduce :: forall a p q.
( Pointer p, Pointer q, Storable a, HasDatatype a)
=> p a
-> q a
-> Count
-> Op
-> Comm
-> IO ()
allreduce sendbuf recvbuf count op comm =
withPtr sendbuf $ \sendbuf' ->
withPtr recvbuf $ \recvbuf' ->
allreduceTyped (castPtr sendbuf') (castPtr recvbuf') count (datatype @a) op
comm
alltoallTyped :: (Ptr ()) -> (Count) -> (Datatype) -> (Ptr ()) -> (Count) -> (Datatype) -> (Comm) -> IO ()
alltoallTyped a1 a2 a3 a4 a5 a6 a7 =
let {a1' = id a1} in
let {a2' = fromCount a2} in
withDatatype a3 $ \a3' ->
let {a4' = id a4} in
let {a5' = fromCount a5} in
withDatatype a6 $ \a6' ->
withComm a7 $ \a7' ->
alltoallTyped'_ a1' a2' a3' a4' a5' a6' a7' >>= \res ->
return res >>
return ()
{-# LINE 864 "lib/Control/Distributed/MPI.chs" #-}
alltoall :: forall a b p q.
( Pointer p, Pointer q
, Storable a, HasDatatype a, Storable b, HasDatatype b)
=> p a
-> Count
-> q b
-> Count
-> Comm
-> IO ()
alltoall sendbuf sendcount recvbuf recvcount comm =
withPtr sendbuf $ \sendbuf' ->
withPtr recvbuf $ \recvbuf' ->
alltoallTyped (castPtr sendbuf') sendcount (datatype @a)
(castPtr recvbuf') recvcount (datatype @b)
comm
barrier :: (Comm)
-> IO ()
barrier a1 =
withComm a1 $ \a1' ->
barrier'_ a1' >>= \res ->
return res >>
return ()
{-# LINE 890 "lib/Control/Distributed/MPI.chs" #-}
bcastTyped :: (Ptr ()) -> (Count) -> (Datatype) -> (Rank) -> (Comm) -> IO ()
bcastTyped a1 a2 a3 a4 a5 =
let {a1' = id a1} in
let {a2' = fromCount a2} in
withDatatype a3 $ \a3' ->
let {a4' = fromRank a4} in
withComm a5 $ \a5' ->
bcastTyped'_ a1' a2' a3' a4' a5' >>= \res ->
return res >>
return ()
{-# LINE 898 "lib/Control/Distributed/MPI.chs" #-}
bcast :: forall a p. (Pointer p, Storable a, HasDatatype a)
=> p a
-> Count
-> Rank
-> Comm
-> IO ()
bcast buf count root comm =
withPtr buf $ \buf' ->
bcastTyped (castPtr buf') count (datatype @a) root comm
commCompare :: (Comm)
-> (Comm)
-> IO ((ComparisonResult))
commCompare a1 a2 =
withComm a1 $ \a1' ->
withComm a2 $ \a2' ->
alloca $ \a3' ->
commCompare'_ a1' a2' a3' >>= \res ->
return res >>
peekEnum a3'>>= \a3'' ->
return (a3'')
{-# LINE 921 "lib/Control/Distributed/MPI.chs" #-}
commRank :: (Comm)
-> IO ((Rank))
commRank a1 =
withComm a1 $ \a1' ->
alloca $ \a2' ->
commRank'_ a1' a2' >>= \res ->
return res >>
peekCoerce a2'>>= \a2'' ->
return (a2'')
{-# LINE 928 "lib/Control/Distributed/MPI.chs" #-}
commSize :: (Comm)
-> IO ((Rank))
commSize a1 =
withComm a1 $ \a1' ->
alloca $ \a2' ->
commSize'_ a1' a2' >>= \res ->
return res >>
peekCoerce a2'>>= \a2'' ->
return (a2'')
{-# LINE 935 "lib/Control/Distributed/MPI.chs" #-}
exscanTyped :: (Ptr ()) -> (Ptr ()) -> (Count) -> (Datatype) -> (Op) -> (Comm) -> IO ()
exscanTyped a1 a2 a3 a4 a5 a6 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = fromCount a3} in
withDatatype a4 $ \a4' ->
withOp a5 $ \a5' ->
withComm a6 $ \a6' ->
exscanTyped'_ a1' a2' a3' a4' a5' a6' >>= \res ->
return res >>
return ()
{-# LINE 944 "lib/Control/Distributed/MPI.chs" #-}
exscan :: forall a p q.
( Pointer p, Pointer q, Storable a, HasDatatype a)
=> p a
-> q a
-> Count
-> Op
-> Comm
-> IO ()
exscan sendbuf recvbuf count op comm =
withPtr sendbuf $ \sendbuf' ->
withPtr recvbuf $ \recvbuf' ->
exscanTyped (castPtr sendbuf') (castPtr recvbuf') count (datatype @a) op comm
finalize :: IO ()
finalize =
finalize'_ >>= \res ->
return res >>
return ()
{-# LINE 971 "lib/Control/Distributed/MPI.chs" #-}
finalized :: IO ((Bool))
finalized =
alloca $ \a1' ->
finalized'_ a1' >>= \res ->
return res >>
peekBool a1'>>= \a1'' ->
return (a1'')
{-# LINE 975 "lib/Control/Distributed/MPI.chs" #-}
gatherTyped :: (Ptr ()) -> (Count) -> (Datatype) -> (Ptr ()) -> (Count) -> (Datatype) -> (Rank) -> (Comm) -> IO ()
gatherTyped a1 a2 a3 a4 a5 a6 a7 a8 =
let {a1' = id a1} in
let {a2' = fromCount a2} in
withDatatype a3 $ \a3' ->
let {a4' = id a4} in
let {a5' = fromCount a5} in
withDatatype a6 $ \a6' ->
let {a7' = fromRank a7} in
withComm a8 $ \a8' ->
gatherTyped'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
return res >>
return ()
{-# LINE 986 "lib/Control/Distributed/MPI.chs" #-}
gather :: forall a b p q.
( Pointer p, Pointer q
, Storable a, HasDatatype a, Storable b, HasDatatype b)
=> p a
-> Count
-> q b
-> Count
-> Rank
-> Comm
-> IO ()
gather sendbuf sendcount recvbuf recvcount root comm =
withPtr sendbuf $ \sendbuf' ->
withPtr recvbuf $ \recvbuf' ->
gatherTyped (castPtr sendbuf') sendcount (datatype @a)
(castPtr recvbuf') recvcount (datatype @b)
root comm
getCount :: (Status)
-> (Datatype)
-> IO ((Int))
getCount a1 a2 =
withStatus a1 $ \a1' ->
withDatatype a2 $ \a2' ->
alloca $ \a3' ->
getCount'_ a1' a2' a3' >>= \res ->
return res >>
peekInt a3'>>= \a3'' ->
return (a3'')
{-# LINE 1018 "lib/Control/Distributed/MPI.chs" #-}
getElements :: (Status)
-> (Datatype)
-> IO ((Int))
getElements a1 a2 =
withStatus a1 $ \a1' ->
withDatatype a2 $ \a2' ->
alloca $ \a3' ->
getElements'_ a1' a2' a3' >>= \res ->
return res >>
peekInt a3'>>= \a3'' ->
return (a3'')
{-# LINE 1030 "lib/Control/Distributed/MPI.chs" #-}
getLibraryVersion_ :: (CString) -> IO ((Int))
getLibraryVersion_ a1 =
let {a1' = id a1} in
alloca $ \a2' ->
getLibraryVersion_'_ a1' a2' >>= \res ->
return res >>
peekInt a2'>>= \a2'' ->
return (a2'')
{-# LINE 1035 "lib/Control/Distributed/MPI.chs" #-}
getLibraryVersion :: IO String
getLibraryVersion =
do buf <- mallocForeignPtrBytes 256
{-# LINE 1043 "lib/Control/Distributed/MPI.chs" #-}
withForeignPtr buf $ \ptr ->
do len <- getLibraryVersion_ ptr
str <- peekCStringLen (ptr, len)
return str
getProcessorName_ :: (CString) -> IO ((Int))
getProcessorName_ a1 =
let {a1' = id a1} in
alloca $ \a2' ->
getProcessorName_'_ a1' a2' >>= \res ->
return res >>
peekInt a2'>>= \a2'' ->
return (a2'')
{-# LINE 1052 "lib/Control/Distributed/MPI.chs" #-}
getProcessorName :: IO String
getProcessorName =
do buf <- mallocForeignPtrBytes 256
{-# LINE 1060 "lib/Control/Distributed/MPI.chs" #-}
withForeignPtr buf $ \ptr ->
do len <- getProcessorName_ ptr
str <- peekCStringLen (ptr, len)
return str
getVersion_ :: IO ((Int), (Int))
getVersion_ =
alloca $ \a1' ->
alloca $ \a2' ->
getVersion_'_ a1' a2' >>= \res ->
return res >>
peekInt a1'>>= \a1'' ->
peekInt a2'>>= \a2'' ->
return (a1'', a2'')
{-# LINE 1069 "lib/Control/Distributed/MPI.chs" #-}
getVersion :: IO Version
getVersion =
do (major, minor) <- getVersion_
return (makeVersion [major, minor])
iallgatherTyped :: (Ptr ()) -> (Count) -> (Datatype) -> (Ptr ()) -> (Count) -> (Datatype) -> (Comm) -> IO ((Request))
iallgatherTyped a1 a2 a3 a4 a5 a6 a7 =
let {a1' = id a1} in
let {a2' = fromCount a2} in
withDatatype a3 $ \a3' ->
let {a4' = id a4} in
let {a5' = fromCount a5} in
withDatatype a6 $ \a6' ->
withComm a7 $ \a7' ->
C2HSImp.mallocForeignPtrBytes 8 >>= \a8'' -> C2HSImp.withForeignPtr a8'' $ \a8' ->
iallgatherTyped'_ a1' a2' a3' a4' a5' a6' a7' a8' >>
return (Request a8'')
{-# LINE 1090 "lib/Control/Distributed/MPI.chs" #-}
iallgather :: forall a b p q.
( Pointer p, Pointer q
, Storable a, HasDatatype a, Storable b, HasDatatype b)
=> p a
-> Count
-> q b
-> Count
-> Comm
-> IO Request
iallgather sendbuf sendcount recvbuf recvcount comm =
withPtr sendbuf $ \sendbuf' ->
withPtr recvbuf $ \recvbuf' ->
iallgatherTyped (castPtr sendbuf') sendcount (datatype @a)
(castPtr recvbuf') recvcount (datatype @b)
comm
iallreduceTyped :: (Ptr ()) -> (Ptr ()) -> (Count) -> (Datatype) -> (Op) -> (Comm) -> IO ((Request))
iallreduceTyped a1 a2 a3 a4 a5 a6 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = fromCount a3} in
withDatatype a4 $ \a4' ->
withOp a5 $ \a5' ->
withComm a6 $ \a6' ->
C2HSImp.mallocForeignPtrBytes 8 >>= \a7'' -> C2HSImp.withForeignPtr a7'' $ \a7' ->
iallreduceTyped'_ a1' a2' a3' a4' a5' a6' a7' >>
return (Request a7'')
{-# LINE 1123 "lib/Control/Distributed/MPI.chs" #-}
iallreduce :: forall a p q.
( Pointer p, Pointer q, Storable a, HasDatatype a)
=> p a
-> q a
-> Count
-> Op
-> Comm
-> IO Request
iallreduce sendbuf recvbuf count op comm =
withPtr sendbuf $ \sendbuf' ->
withPtr recvbuf $ \recvbuf' ->
iallreduceTyped (castPtr sendbuf') (castPtr recvbuf') count (datatype @a) op
comm
ialltoallTyped :: (Ptr ()) -> (Count) -> (Datatype) -> (Ptr ()) -> (Count) -> (Datatype) -> (Comm) -> IO ((Request))
ialltoallTyped a1 a2 a3 a4 a5 a6 a7 =
let {a1' = id a1} in
let {a2' = fromCount a2} in
withDatatype a3 $ \a3' ->
let {a4' = id a4} in
let {a5' = fromCount a5} in
withDatatype a6 $ \a6' ->
withComm a7 $ \a7' ->
C2HSImp.mallocForeignPtrBytes 8 >>= \a8'' -> C2HSImp.withForeignPtr a8'' $ \a8' ->
ialltoallTyped'_ a1' a2' a3' a4' a5' a6' a7' a8' >>
return (Request a8'')
{-# LINE 1155 "lib/Control/Distributed/MPI.chs" #-}
ialltoall :: forall a b p q.
( Pointer p, Pointer q
, Storable a, HasDatatype a, Storable b, HasDatatype b)
=> p a
-> Count
-> q b
-> Count
-> Comm
-> IO Request
ialltoall sendbuf sendcount recvbuf recvcount comm =
withPtr sendbuf $ \sendbuf' ->
withPtr recvbuf $ \recvbuf' ->
ialltoallTyped (castPtr sendbuf') sendcount (datatype @a)
(castPtr recvbuf') recvcount (datatype @b)
comm
ibarrier :: (Comm)
-> IO ((Request))
ibarrier a1 =
withComm a1 $ \a1' ->
C2HSImp.mallocForeignPtrBytes 8 >>= \a2'' -> C2HSImp.withForeignPtr a2'' $ \a2' ->
ibarrier'_ a1' a2' >>
return (Request a2'')
{-# LINE 1187 "lib/Control/Distributed/MPI.chs" #-}
ibcastTyped :: (Ptr ()) -> (Count) -> (Datatype) -> (Rank) -> (Comm) -> IO ((Request))
ibcastTyped a1 a2 a3 a4 a5 =
let {a1' = id a1} in
let {a2' = fromCount a2} in
withDatatype a3 $ \a3' ->
let {a4' = fromRank a4} in
withComm a5 $ \a5' ->
C2HSImp.mallocForeignPtrBytes 8 >>= \a6'' -> C2HSImp.withForeignPtr a6'' $ \a6' ->
ibcastTyped'_ a1' a2' a3' a4' a5' a6' >>
return (Request a6'')
{-# LINE 1196 "lib/Control/Distributed/MPI.chs" #-}
ibcast :: forall a p. (Pointer p, Storable a, HasDatatype a)
=> p a
-> Count
-> Rank
-> Comm
-> IO Request
ibcast buf count root comm =
withPtr buf $ \buf' ->
ibcastTyped (castPtr buf') count (datatype @a) root comm
iexscanTyped :: (Ptr ()) -> (Ptr ()) -> (Count) -> (Datatype) -> (Op) -> (Comm) -> IO ((Request))
iexscanTyped a1 a2 a3 a4 a5 a6 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = fromCount a3} in
withDatatype a4 $ \a4' ->
withOp a5 $ \a5' ->
withComm a6 $ \a6' ->
C2HSImp.mallocForeignPtrBytes 8 >>= \a7'' -> C2HSImp.withForeignPtr a7'' $ \a7' ->
iexscanTyped'_ a1' a2' a3' a4' a5' a6' a7' >>
return (Request a7'')
{-# LINE 1224 "lib/Control/Distributed/MPI.chs" #-}
iexscan :: forall a p q.
( Pointer p, Pointer q, Storable a, HasDatatype a)
=> p a
-> q a
-> Count
-> Op
-> Comm
-> IO Request
iexscan sendbuf recvbuf count op comm =
withPtr sendbuf $ \sendbuf' ->
withPtr recvbuf $ \recvbuf' ->
iexscanTyped (castPtr sendbuf') (castPtr recvbuf') count (datatype @a) op comm
igatherTyped :: (Ptr ()) -> (Count) -> (Datatype) -> (Ptr ()) -> (Count) -> (Datatype) -> (Rank) -> (Comm) -> IO ((Request))
igatherTyped a1 a2 a3 a4 a5 a6 a7 a8 =
let {a1' = id a1} in
let {a2' = fromCount a2} in
withDatatype a3 $ \a3' ->
let {a4' = id a4} in
let {a5' = fromCount a5} in
withDatatype a6 $ \a6' ->
let {a7' = fromRank a7} in
withComm a8 $ \a8' ->
C2HSImp.mallocForeignPtrBytes 8 >>= \a9'' -> C2HSImp.withForeignPtr a9'' $ \a9' ->
igatherTyped'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>
return (Request a9'')
{-# LINE 1262 "lib/Control/Distributed/MPI.chs" #-}
igather :: forall a b p q.
( Pointer p, Pointer q
, Storable a, HasDatatype a, Storable b, HasDatatype b)
=> p a
-> Count
-> q b
-> Count
-> Rank
-> Comm
-> IO Request
igather sendbuf sendcount recvbuf recvcount root comm =
withPtr sendbuf $ \sendbuf' ->
withPtr recvbuf $ \recvbuf' ->
igatherTyped (castPtr sendbuf') sendcount (datatype @a)
(castPtr recvbuf') recvcount (datatype @b)
root comm
initialized :: IO ((Bool))
initialized =
alloca $ \a1' ->
initialized'_ a1' >>= \res ->
return res >>
peekBool a1'>>= \a1'' ->
return (a1'')
{-# LINE 1292 "lib/Control/Distributed/MPI.chs" #-}
init_ :: (CInt) -> (Ptr CString) -> IO ()
init_ a1 a2 =
with a1 $ \a1' ->
with a2 $ \a2' ->
init_'_ a1' a2' >>= \res ->
return res >>
return ()
{-# LINE 1297 "lib/Control/Distributed/MPI.chs" #-}
init :: IO ()
init = do init_ argc argv
writeIORef providedThreadSupport (Just ThreadSingle)
initThread_ :: (CInt) -> (Ptr CString) -> (ThreadSupport) -> IO ((ThreadSupport))
initThread_ a1 a2 a3 =
with a1 $ \a1' ->
with a2 $ \a2' ->
let {a3' = fromEnum a3} in
alloca $ \a4' ->
initThread_'_ a1' a2' a3' a4' >>= \res ->
return res >>
peekEnum a4'>>= \a4'' ->
return (a4'')
{-# LINE 1311 "lib/Control/Distributed/MPI.chs" #-}
initThread :: ThreadSupport
-> IO ThreadSupport
initThread ts = do ts' <- initThread_ argc argv ts
writeIORef providedThreadSupport (Just ts')
return ts'
iprobeBool :: Rank -> Tag -> Comm -> IO (Bool, Status)
iprobeBool rank tag comm =
withComm comm $ \comm' ->
do st <- Status <$> mallocForeignPtrBytes 24
{-# LINE 1326 "lib/Control/Distributed/MPI.chs" #-}
withStatus st $ \st' ->
do alloca $ \flag ->
do _ <- iprobeBool_
{-# LINE 1329 "lib/Control/Distributed/MPI.chs" #-}
(fromRank rank) (fromTag tag) comm' flag st'
b <- peekBool flag
return (b, st)
iprobe :: Rank
-> Tag
-> Comm
-> IO (Maybe Status)
iprobe rank tag comm = bool2maybe <$> iprobeBool rank tag comm
iprobe_ :: Rank
-> Tag
-> Comm
-> IO Bool
iprobe_ rank tag comm =
withComm comm $ \comm' ->
do withStatusIgnore $ \st ->
do alloca $ \flag ->
do _ <- iprobe__
{-# LINE 1356 "lib/Control/Distributed/MPI.chs" #-}
(fromRank rank) (fromTag tag) comm' flag st
peekBool flag
irecvTyped :: (Ptr ()) -> (Count) -> (Datatype) -> (Rank) -> (Tag) -> (Comm) -> IO ((Request))
irecvTyped a1 a2 a3 a4 a5 a6 =
let {a1' = id a1} in
let {a2' = fromCount a2} in
withDatatype a3 $ \a3' ->
let {a4' = fromRank a4} in
let {a5' = fromTag a5} in
withComm a6 $ \a6' ->
C2HSImp.mallocForeignPtrBytes 8 >>= \a7'' -> C2HSImp.withForeignPtr a7'' $ \a7' ->
irecvTyped'_ a1' a2' a3' a4' a5' a6' a7' >>
return (Request a7'')
{-# LINE 1368 "lib/Control/Distributed/MPI.chs" #-}
irecv :: forall a p. (Pointer p, Storable a, HasDatatype a)
=> p a
-> Count
-> Rank
-> Tag
-> Comm
-> IO Request
irecv recvbuf recvcount recvrank recvtag comm =
withPtr recvbuf $ \recvbuf' ->
irecvTyped (castPtr recvbuf') recvcount (datatype @a) recvrank recvtag comm
ireduceTyped :: (Ptr ()) -> (Ptr ()) -> (Count) -> (Datatype) -> (Op) -> (Rank) -> (Comm) -> IO ((Request))
ireduceTyped a1 a2 a3 a4 a5 a6 a7 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = fromCount a3} in
withDatatype a4 $ \a4' ->
withOp a5 $ \a5' ->
let {a6' = fromRank a6} in
withComm a7 $ \a7' ->
C2HSImp.mallocForeignPtrBytes 8 >>= \a8'' -> C2HSImp.withForeignPtr a8'' $ \a8' ->
ireduceTyped'_ a1' a2' a3' a4' a5' a6' a7' a8' >>
return (Request a8'')
{-# LINE 1396 "lib/Control/Distributed/MPI.chs" #-}
ireduce :: forall a p q.
( Pointer p, Pointer q, Storable a, HasDatatype a)
=> p a
-> q a
-> Count
-> Op
-> Rank
-> Comm
-> IO Request
ireduce sendbuf recvbuf count op rank comm =
withPtr sendbuf $ \sendbuf' ->
withPtr recvbuf $ \recvbuf' ->
ireduceTyped (castPtr sendbuf') (castPtr recvbuf') count (datatype @a) op rank
comm
iscanTyped :: (Ptr ()) -> (Ptr ()) -> (Count) -> (Datatype) -> (Op) -> (Comm) -> IO ((Request))
iscanTyped a1 a2 a3 a4 a5 a6 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = fromCount a3} in
withDatatype a4 $ \a4' ->
withOp a5 $ \a5' ->
withComm a6 $ \a6' ->
C2HSImp.mallocForeignPtrBytes 8 >>= \a7'' -> C2HSImp.withForeignPtr a7'' $ \a7' ->
iscanTyped'_ a1' a2' a3' a4' a5' a6' a7' >>
return (Request a7'')
{-# LINE 1427 "lib/Control/Distributed/MPI.chs" #-}
iscan :: forall a p q.
( Pointer p, Pointer q, Storable a, HasDatatype a)
=> p a
-> q a
-> Count
-> Op
-> Comm
-> IO Request
iscan sendbuf recvbuf count op comm =
withPtr sendbuf $ \sendbuf' ->
withPtr recvbuf $ \recvbuf' ->
iscanTyped (castPtr sendbuf') (castPtr recvbuf') count (datatype @a) op comm
iscatterTyped :: (Ptr ()) -> (Count) -> (Datatype) -> (Ptr ()) -> (Count) -> (Datatype) -> (Rank) -> (Comm) -> IO ((Request))
iscatterTyped a1 a2 a3 a4 a5 a6 a7 a8 =
let {a1' = id a1} in
let {a2' = fromCount a2} in
withDatatype a3 $ \a3' ->
let {a4' = id a4} in
let {a5' = fromCount a5} in
withDatatype a6 $ \a6' ->
let {a7' = fromRank a7} in
withComm a8 $ \a8' ->
C2HSImp.mallocForeignPtrBytes 8 >>= \a9'' -> C2HSImp.withForeignPtr a9'' $ \a9' ->
iscatterTyped'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>
return (Request a9'')
{-# LINE 1460 "lib/Control/Distributed/MPI.chs" #-}
iscatter :: forall a b p q.
( Pointer p, Pointer q
, Storable a, HasDatatype a, Storable b, HasDatatype b)
=> p a
-> Count
-> q b
-> Count
-> Rank
-> Comm
-> IO Request
iscatter sendbuf sendcount recvbuf recvcount root comm =
withPtr sendbuf $ \sendbuf' ->
withPtr recvbuf $ \recvbuf' ->
iscatterTyped (castPtr sendbuf') sendcount (datatype @a)
(castPtr recvbuf') recvcount (datatype @b)
root comm
isendTyped :: (Ptr ()) -> (Count) -> (Datatype) -> (Rank) -> (Tag) -> (Comm) -> IO ((Request))
isendTyped a1 a2 a3 a4 a5 a6 =
let {a1' = id a1} in
let {a2' = fromCount a2} in
withDatatype a3 $ \a3' ->
let {a4' = fromRank a4} in
let {a5' = fromTag a5} in
withComm a6 $ \a6' ->
C2HSImp.mallocForeignPtrBytes 8 >>= \a7'' -> C2HSImp.withForeignPtr a7'' $ \a7' ->
isendTyped'_ a1' a2' a3' a4' a5' a6' a7' >>
return (Request a7'')
{-# LINE 1494 "lib/Control/Distributed/MPI.chs" #-}
isend :: forall a p. (Pointer p, Storable a, HasDatatype a)
=> p a
-> Count
-> Rank
-> Tag
-> Comm
-> IO Request
isend sendbuf sendcount sendrank sendtag comm =
withPtr sendbuf $ \sendbuf' ->
isendTyped (castPtr sendbuf') sendcount (datatype @a) sendrank sendtag comm
probe :: (Rank)
-> (Tag)
-> (Comm)
-> IO ((Status))
probe a1 a2 a3 =
let {a1' = fromRank a1} in
let {a2' = fromTag a2} in
withComm a3 $ \a3' ->
C2HSImp.mallocForeignPtrBytes 24 >>= \a4'' -> C2HSImp.withForeignPtr a4'' $ \a4' ->
probe'_ a1' a2' a3' a4' >>
return (Status a4'')
{-# LINE 1521 "lib/Control/Distributed/MPI.chs" #-}
probe_ :: (Rank)
-> (Tag)
-> (Comm)
-> IO ()
probe_ a1 a2 a3 =
let {a1' = fromRank a1} in
let {a2' = fromTag a2} in
withComm a3 $ \a3' ->
withStatusIgnore $ \a4' ->
probe_'_ a1' a2' a3' a4' >>= \res ->
return res >>
return ()
{-# LINE 1532 "lib/Control/Distributed/MPI.chs" #-}
recvTyped :: (Ptr ()) -> (Count) -> (Datatype) -> (Rank) -> (Tag) -> (Comm) -> IO ((Status))
recvTyped a1 a2 a3 a4 a5 a6 =
let {a1' = id a1} in
let {a2' = fromCount a2} in
withDatatype a3 $ \a3' ->
let {a4' = fromRank a4} in
let {a5' = fromTag a5} in
withComm a6 $ \a6' ->
C2HSImp.mallocForeignPtrBytes 24 >>= \a7'' -> C2HSImp.withForeignPtr a7'' $ \a7' ->
recvTyped'_ a1' a2' a3' a4' a5' a6' a7' >>
return (Status a7'')
{-# LINE 1542 "lib/Control/Distributed/MPI.chs" #-}
recv :: forall a p. (Pointer p, Storable a, HasDatatype a)
=> p a
-> Count
-> Rank
-> Tag
-> Comm
-> IO Status
recv recvbuf recvcount recvrank recvtag comm =
withPtr recvbuf $ \recvbuf' ->
recvTyped (castPtr recvbuf') recvcount (datatype @a) recvrank recvtag comm
recvTyped_ :: (Ptr ()) -> (Count) -> (Datatype) -> (Rank) -> (Tag) -> (Comm) -> IO ()
recvTyped_ a1 a2 a3 a4 a5 a6 =
let {a1' = id a1} in
let {a2' = fromCount a2} in
withDatatype a3 $ \a3' ->
let {a4' = fromRank a4} in
let {a5' = fromTag a5} in
withComm a6 $ \a6' ->
withStatusIgnore $ \a7' ->
recvTyped_'_ a1' a2' a3' a4' a5' a6' a7' >>= \res ->
return res >>
return ()
{-# LINE 1567 "lib/Control/Distributed/MPI.chs" #-}
recv_ :: forall a p. (Pointer p, Storable a, HasDatatype a)
=> p a
-> Count
-> Rank
-> Tag
-> Comm
-> IO ()
recv_ recvbuf recvcount recvrank recvtag comm =
withPtr recvbuf $ \recvbuf' ->
recvTyped_ (castPtr recvbuf') recvcount (datatype @a) recvrank recvtag comm
reduceTyped :: (Ptr ()) -> (Ptr ()) -> (Count) -> (Datatype) -> (Op) -> (Rank) -> (Comm) -> IO ()
reduceTyped a1 a2 a3 a4 a5 a6 a7 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = fromCount a3} in
withDatatype a4 $ \a4' ->
withOp a5 $ \a5' ->
let {a6' = fromRank a6} in
withComm a7 $ \a7' ->
reduceTyped'_ a1' a2' a3' a4' a5' a6' a7' >>= \res ->
return res >>
return ()
{-# LINE 1593 "lib/Control/Distributed/MPI.chs" #-}
reduce :: forall a p q.
( Pointer p, Pointer q, Storable a, HasDatatype a)
=> p a
-> q a
-> Count
-> Op
-> Rank
-> Comm
-> IO ()
reduce sendbuf recvbuf count op rank comm =
withPtr sendbuf $ \sendbuf' ->
withPtr recvbuf $ \recvbuf' ->
reduceTyped (castPtr sendbuf') (castPtr recvbuf') count (datatype @a) op rank
comm
scanTyped :: (Ptr ()) -> (Ptr ()) -> (Count) -> (Datatype) -> (Op) -> (Comm) -> IO ()
scanTyped a1 a2 a3 a4 a5 a6 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = fromCount a3} in
withDatatype a4 $ \a4' ->
withOp a5 $ \a5' ->
withComm a6 $ \a6' ->
scanTyped'_ a1' a2' a3' a4' a5' a6' >>= \res ->
return res >>
return ()
{-# LINE 1621 "lib/Control/Distributed/MPI.chs" #-}
scan :: forall a p q.
( Pointer p, Pointer q, Storable a, HasDatatype a)
=> p a
-> q a
-> Count
-> Op
-> Comm
-> IO ()
scan sendbuf recvbuf count op comm =
withPtr sendbuf $ \sendbuf' ->
withPtr recvbuf $ \recvbuf' ->
scanTyped (castPtr sendbuf') (castPtr recvbuf') count (datatype @a) op comm
scatterTyped :: (Ptr ()) -> (Count) -> (Datatype) -> (Ptr ()) -> (Count) -> (Datatype) -> (Rank) -> (Comm) -> IO ()
scatterTyped a1 a2 a3 a4 a5 a6 a7 a8 =
let {a1' = id a1} in
let {a2' = fromCount a2} in
withDatatype a3 $ \a3' ->
let {a4' = id a4} in
let {a5' = fromCount a5} in
withDatatype a6 $ \a6' ->
let {a7' = fromRank a7} in
withComm a8 $ \a8' ->
scatterTyped'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
return res >>
return ()
{-# LINE 1651 "lib/Control/Distributed/MPI.chs" #-}
scatter :: forall a b p q.
( Pointer p, Pointer q
, Storable a, HasDatatype a, Storable b, HasDatatype b)
=> p a
-> Count
-> q b
-> Count
-> Rank
-> Comm
-> IO ()
scatter sendbuf sendcount recvbuf recvcount root comm =
withPtr sendbuf $ \sendbuf' ->
withPtr recvbuf $ \recvbuf' ->
scatterTyped (castPtr sendbuf') sendcount (datatype @a)
(castPtr recvbuf') recvcount (datatype @b)
root comm
sendTyped :: (Ptr ()) -> (Count) -> (Datatype) -> (Rank) -> (Tag) -> (Comm) -> IO ()
sendTyped a1 a2 a3 a4 a5 a6 =
let {a1' = id a1} in
let {a2' = fromCount a2} in
withDatatype a3 $ \a3' ->
let {a4' = fromRank a4} in
let {a5' = fromTag a5} in
withComm a6 $ \a6' ->
sendTyped'_ a1' a2' a3' a4' a5' a6' >>= \res ->
return res >>
return ()
{-# LINE 1681 "lib/Control/Distributed/MPI.chs" #-}
send :: forall a p. (Pointer p, Storable a, HasDatatype a)
=> p a
-> Count
-> Rank
-> Tag
-> Comm
-> IO ()
send sendbuf sendcount sendrank sendtag comm =
withPtr sendbuf $ \sendbuf' ->
sendTyped (castPtr sendbuf') sendcount (datatype @a) sendrank sendtag comm
sendrecvTyped :: (Ptr ()) -> (Count) -> (Datatype) -> (Rank) -> (Tag) -> (Ptr ()) -> (Count) -> (Datatype) -> (Rank) -> (Tag) -> (Comm) -> IO ((Status))
sendrecvTyped a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 =
let {a1' = id a1} in
let {a2' = fromCount a2} in
withDatatype a3 $ \a3' ->
let {a4' = fromRank a4} in
let {a5' = fromTag a5} in
let {a6' = id a6} in
let {a7' = fromCount a7} in
withDatatype a8 $ \a8' ->
let {a9' = fromRank a9} in
let {a10' = fromTag a10} in
withComm a11 $ \a11' ->
C2HSImp.mallocForeignPtrBytes 24 >>= \a12'' -> C2HSImp.withForeignPtr a12'' $ \a12' ->
sendrecvTyped'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' >>
return (Status a12'')
{-# LINE 1711 "lib/Control/Distributed/MPI.chs" #-}
sendrecv :: forall a b p q.
( Pointer p, Pointer q
, Storable a, HasDatatype a, Storable b, HasDatatype b)
=> p a
-> Count
-> Rank
-> Tag
-> q b
-> Count
-> Rank
-> Tag
-> Comm
-> IO Status
sendrecv sendbuf sendcount sendrank sendtag
recvbuf recvcount recvrank recvtag
comm =
withPtr sendbuf $ \sendbuf' ->
withPtr recvbuf $ \recvbuf' ->
sendrecvTyped (castPtr sendbuf') sendcount (datatype @a) sendrank sendtag
(castPtr recvbuf') recvcount (datatype @b) recvrank recvtag
comm
sendrecvTyped_ :: (Ptr ()) -> (Count) -> (Datatype) -> (Rank) -> (Tag) -> (Ptr ()) -> (Count) -> (Datatype) -> (Rank) -> (Tag) -> (Comm) -> IO ()
sendrecvTyped_ a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 =
let {a1' = id a1} in
let {a2' = fromCount a2} in
withDatatype a3 $ \a3' ->
let {a4' = fromRank a4} in
let {a5' = fromTag a5} in
let {a6' = id a6} in
let {a7' = fromCount a7} in
withDatatype a8 $ \a8' ->
let {a9' = fromRank a9} in
let {a10' = fromTag a10} in
withComm a11 $ \a11' ->
withStatusIgnore $ \a12' ->
sendrecvTyped_'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' >>= \res ->
return res >>
return ()
{-# LINE 1752 "lib/Control/Distributed/MPI.chs" #-}
sendrecv_ :: forall a b p q.
( Pointer p, Pointer q
, Storable a, HasDatatype a, Storable b, HasDatatype b)
=> p a
-> Count
-> Rank
-> Tag
-> q a
-> Count
-> Rank
-> Tag
-> Comm
-> IO ()
sendrecv_ sendbuf sendcount sendrank sendtag
recvbuf recvcount recvrank recvtag
comm =
withPtr sendbuf $ \sendbuf' ->
withPtr recvbuf $ \recvbuf' ->
sendrecvTyped_ (castPtr sendbuf') sendcount (datatype @a) sendrank sendtag
(castPtr recvbuf') recvcount (datatype @b) recvrank recvtag
comm
testBool :: Request -> IO (Bool, Status)
testBool req =
withRequest req $ \req' ->
alloca $ \flag ->
do st <- Status <$> mallocForeignPtrBytes 24
{-# LINE 1785 "lib/Control/Distributed/MPI.chs" #-}
withStatus st $ \st' ->
do _ <- testBool_ req' flag st'
b <- peekBool flag
return (b, st)
test :: Request
-> IO (Maybe Status)
test req = bool2maybe <$> testBool req
test_ :: Request
-> IO Bool
test_ req =
withRequest req $ \req' ->
alloca $ \flag ->
withStatusIgnore $ \st ->
do _ <- test__ req' flag st
peekBool flag
wait :: (Request)
-> IO ((Status))
wait a1 =
withRequest a1 $ \a1' ->
C2HSImp.mallocForeignPtrBytes 24 >>= \a2'' -> C2HSImp.withForeignPtr a2'' $ \a2' ->
wait'_ a1' a2' >>
return (Status a2'')
{-# LINE 1826 "lib/Control/Distributed/MPI.chs" #-}
wait_ :: (Request)
-> IO ()
wait_ a1 =
withRequest a1 $ \a1' ->
withStatusIgnore $ \a2' ->
wait_'_ a1' a2' >>= \res ->
return res >>
return ()
{-# LINE 1836 "lib/Control/Distributed/MPI.chs" #-}
wtick :: IO ((Double))
wtick =
wtick'_ >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 1839 "lib/Control/Distributed/MPI.chs" #-}
wtime :: IO ((Double))
wtime =
wtime'_ >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 1842 "lib/Control/Distributed/MPI.chs" #-}
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_comm_null"
commNull'_ :: ((C2HSImp.Ptr (Comm)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_comm_self"
commSelf'_ :: ((C2HSImp.Ptr (Comm)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_comm_world"
commWorld'_ :: ((C2HSImp.Ptr (Comm)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_undefined"
countUndefined'_ :: (IO C2HSImp.CInt)
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_datatype_null"
datatypeNull'_ :: ((C2HSImp.Ptr (Datatype)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_byte"
datatypeByte'_ :: ((C2HSImp.Ptr (Datatype)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_char"
datatypeChar'_ :: ((C2HSImp.Ptr (Datatype)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_double"
datatypeDouble'_ :: ((C2HSImp.Ptr (Datatype)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_float"
datatypeFloat'_ :: ((C2HSImp.Ptr (Datatype)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_int"
datatypeInt'_ :: ((C2HSImp.Ptr (Datatype)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_long"
datatypeLong'_ :: ((C2HSImp.Ptr (Datatype)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_long_double"
datatypeLongDouble'_ :: ((C2HSImp.Ptr (Datatype)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_long_long_int"
datatypeLongLongInt'_ :: ((C2HSImp.Ptr (Datatype)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_short"
datatypeShort'_ :: ((C2HSImp.Ptr (Datatype)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_unsigned"
datatypeUnsigned'_ :: ((C2HSImp.Ptr (Datatype)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_unsigned_char"
datatypeUnsignedChar'_ :: ((C2HSImp.Ptr (Datatype)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_unsigned_long"
datatypeUnsignedLong'_ :: ((C2HSImp.Ptr (Datatype)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_unsigned_short"
datatypeUnsignedShort'_ :: ((C2HSImp.Ptr (Datatype)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_op_null"
opNull'_ :: ((C2HSImp.Ptr (Op)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_band"
opBand'_ :: ((C2HSImp.Ptr (Op)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_bor"
opBor'_ :: ((C2HSImp.Ptr (Op)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_bxor"
opBxor'_ :: ((C2HSImp.Ptr (Op)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_land"
opLand'_ :: ((C2HSImp.Ptr (Op)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_lor"
opLor'_ :: ((C2HSImp.Ptr (Op)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_lxor"
opLxor'_ :: ((C2HSImp.Ptr (Op)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_max"
opMax'_ :: ((C2HSImp.Ptr (Op)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_maxloc"
opMaxloc'_ :: ((C2HSImp.Ptr (Op)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_min"
opMin'_ :: ((C2HSImp.Ptr (Op)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_minloc"
opMinloc'_ :: ((C2HSImp.Ptr (Op)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_prod"
opProd'_ :: ((C2HSImp.Ptr (Op)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_sum"
opSum'_ :: ((C2HSImp.Ptr (Op)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_any_source"
anySource'_ :: (IO C2HSImp.CInt)
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_request_null"
requestNull'_ :: ((C2HSImp.Ptr (Request)) -> (IO ()))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_status_ignore"
statusIgnore'_ :: (IO (C2HSImp.Ptr (Status)))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_get_any_tag"
anyTag'_ :: (IO C2HSImp.CInt)
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Abort"
abort'_ :: ((C2HSImp.Ptr (Comm)) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Allgather"
allgatherTyped'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> ((C2HSImp.Ptr (Comm)) -> (IO C2HSImp.CInt))))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Allreduce"
allreduceTyped'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> ((C2HSImp.Ptr (Op)) -> ((C2HSImp.Ptr (Comm)) -> (IO C2HSImp.CInt)))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Alltoall"
alltoallTyped'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> ((C2HSImp.Ptr (Comm)) -> (IO C2HSImp.CInt))))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Barrier"
barrier'_ :: ((C2HSImp.Ptr (Comm)) -> (IO C2HSImp.CInt))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Bcast"
bcastTyped'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Comm)) -> (IO C2HSImp.CInt))))))
foreign import ccall unsafe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Comm_compare"
commCompare'_ :: ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))
foreign import ccall unsafe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Comm_rank"
commRank'_ :: ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))
foreign import ccall unsafe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Comm_size"
commSize'_ :: ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Exscan"
exscanTyped'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> ((C2HSImp.Ptr (Op)) -> ((C2HSImp.Ptr (Comm)) -> (IO C2HSImp.CInt)))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h MPI_Finalize"
finalize'_ :: (IO C2HSImp.CInt)
foreign import ccall safe "Control/Distributed/MPI.chs.h MPI_Finalized"
finalized'_ :: ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Gather"
gatherTyped'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Comm)) -> (IO C2HSImp.CInt)))))))))
foreign import ccall unsafe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Get_count"
getCount'_ :: ((C2HSImp.Ptr (Status)) -> ((C2HSImp.Ptr (Datatype)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))
foreign import ccall unsafe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Get_elements"
getElements'_ :: ((C2HSImp.Ptr (Status)) -> ((C2HSImp.Ptr (Datatype)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))
foreign import ccall unsafe "Control/Distributed/MPI.chs.h MPI_Get_library_version"
getLibraryVersion_'_ :: ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))
foreign import ccall unsafe "Control/Distributed/MPI.chs.h MPI_Get_processor_name"
getProcessorName_'_ :: ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))
foreign import ccall unsafe "Control/Distributed/MPI.chs.h MPI_Get_version"
getVersion_'_ :: ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Iallgather"
iallgatherTyped'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr (Request)) -> (IO C2HSImp.CInt)))))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Iallreduce"
iallreduceTyped'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> ((C2HSImp.Ptr (Op)) -> ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr (Request)) -> (IO C2HSImp.CInt))))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Ialltoall"
ialltoallTyped'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr (Request)) -> (IO C2HSImp.CInt)))))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Ibarrier"
ibarrier'_ :: ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr (Request)) -> (IO C2HSImp.CInt)))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Ibcast"
ibcastTyped'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr (Request)) -> (IO C2HSImp.CInt)))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Iexscan"
iexscanTyped'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> ((C2HSImp.Ptr (Op)) -> ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr (Request)) -> (IO C2HSImp.CInt))))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Igather"
igatherTyped'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr (Request)) -> (IO C2HSImp.CInt))))))))))
foreign import ccall unsafe "Control/Distributed/MPI.chs.h MPI_Initialized"
initialized'_ :: ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))
foreign import ccall safe "Control/Distributed/MPI.chs.h MPI_Init"
init_'_ :: ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr (C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar))) -> (IO C2HSImp.CInt)))
foreign import ccall safe "Control/Distributed/MPI.chs.h MPI_Init_thread"
initThread_'_ :: ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr (C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar))) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_iprobe"
iprobeBool_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr (Status)) -> (IO C2HSImp.CInt))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h mpihs_iprobe"
iprobe__ :: (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr (Status)) -> (IO C2HSImp.CInt))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Irecv"
irecvTyped'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr (Request)) -> (IO C2HSImp.CInt))))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Ireduce"
ireduceTyped'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> ((C2HSImp.Ptr (Op)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr (Request)) -> (IO C2HSImp.CInt)))))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Iscan"
iscanTyped'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> ((C2HSImp.Ptr (Op)) -> ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr (Request)) -> (IO C2HSImp.CInt))))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Iscatter"
iscatterTyped'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr (Request)) -> (IO C2HSImp.CInt))))))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Isend"
isendTyped'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr (Request)) -> (IO C2HSImp.CInt))))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Probe"
probe'_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr (Status)) -> (IO C2HSImp.CInt)))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Probe"
probe_'_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr (Status)) -> (IO C2HSImp.CInt)))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Recv"
recvTyped'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr (Status)) -> (IO C2HSImp.CInt))))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Recv"
recvTyped_'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr (Status)) -> (IO C2HSImp.CInt))))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Reduce"
reduceTyped'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> ((C2HSImp.Ptr (Op)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Comm)) -> (IO C2HSImp.CInt))))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Scan"
scanTyped'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> ((C2HSImp.Ptr (Op)) -> ((C2HSImp.Ptr (Comm)) -> (IO C2HSImp.CInt)))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Scatter"
scatterTyped'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Comm)) -> (IO C2HSImp.CInt)))))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Send"
sendTyped'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Comm)) -> (IO C2HSImp.CInt)))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Sendrecv"
sendrecvTyped'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr (Status)) -> (IO C2HSImp.CInt)))))))))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h __c2hs_wrapped__MPI_Sendrecv"
sendrecvTyped_'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Datatype)) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Comm)) -> ((C2HSImp.Ptr (Status)) -> (IO C2HSImp.CInt)))))))))))))
foreign import ccall safe "Control/Distributed/MPI.chs.h MPI_Test"
testBool_ :: ((C2HSImp.Ptr (Request)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr (Status)) -> (IO C2HSImp.CInt))))
foreign import ccall safe "Control/Distributed/MPI.chs.h MPI_Test"
test__ :: ((C2HSImp.Ptr (Request)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr (Status)) -> (IO C2HSImp.CInt))))
foreign import ccall safe "Control/Distributed/MPI.chs.h MPI_Wait"
wait'_ :: ((C2HSImp.Ptr (Request)) -> ((C2HSImp.Ptr (Status)) -> (IO C2HSImp.CInt)))
foreign import ccall safe "Control/Distributed/MPI.chs.h MPI_Wait"
wait_'_ :: ((C2HSImp.Ptr (Request)) -> ((C2HSImp.Ptr (Status)) -> (IO C2HSImp.CInt)))
foreign import ccall unsafe "Control/Distributed/MPI.chs.h MPI_Wtick"
wtick'_ :: (IO C2HSImp.CDouble)
foreign import ccall unsafe "Control/Distributed/MPI.chs.h MPI_Wtime"
wtime'_ :: (IO C2HSImp.CDouble)