dph-base-0.4.0: Basic Definitions for Data-Parallel Haskell.Source codeContentsIndex
Data.Array.Parallel.Arr
Portabilitynon-portable (unboxed values and GHC libraries)
Stabilityinternal
MaintainerRoman Leshchinskiy <rl@cse.unsw.edu.au>
Contents
Types
Operations on immutable arrays
Operations on mutable arrays
Types
Elements of unboxed arrays
Operations on mutable arrays
Operations on immutable arrays
Basic operations
Streaming
Higher-order and arithmetic operations
Conversions to/from lists
I/O
Description
Interface to the Arr modules
Synopsis
data BBArr e
data MBBArr s e
lengthBB :: BBArr e -> Int
indexBB :: BBArr e -> Int -> e
extractBB :: BBArr e -> Int -> Int -> BBArr e
newMBB :: Int -> ST s (MBBArr s e)
lengthMBB :: MBBArr s e -> Int
readMBB :: MBBArr s e -> Int -> ST s e
writeMBB :: MBBArr s e -> Int -> e -> ST s ()
unsafeFreezeMBB :: MBBArr s e -> Int -> ST s (BBArr e)
unsafeFreezeAllMBB :: MBBArr s e -> ST s (BBArr e)
extractMBB :: MBBArr s e -> Int -> Int -> ST s (BBArr e)
copyMBB :: MBBArr s e -> Int -> BBArr e -> ST s ()
data BUArr e
data MBUArr s e
class HS e => UAE e where
indexBU :: BUArr e -> Int -> e
readMBU :: MBUArr s e -> Int -> ST s e
writeMBU :: MBUArr s e -> Int -> e -> ST s ()
lengthMBU :: MBUArr s e -> Int
newMBU :: forall s e. UAE e => Int -> ST s (MBUArr s e)
extractMBU :: UAE e => MBUArr s e -> Int -> Int -> ST s (BUArr e)
copyMBU :: UAE e => MBUArr s e -> Int -> BUArr e -> ST s ()
unsafeFreezeMBU :: MBUArr s e -> Int -> ST s (BUArr e)
unsafeFreezeAllMBU :: MBUArr s e -> ST s (BUArr e)
lengthBU :: BUArr e -> Int
emptyBU :: UAE e => BUArr e
replicateBU :: UAE e => Int -> e -> BUArr e
sliceBU :: BUArr e -> Int -> Int -> BUArr e
extractBU :: UAE e => BUArr e -> Int -> Int -> BUArr e
streamBU :: UAE e => BUArr e -> Stream e
unstreamBU :: UAE e => Stream e -> BUArr e
mapBU :: (UAE a, UAE b) => (a -> b) -> BUArr a -> BUArr b
foldlBU :: UAE b => (a -> b -> a) -> a -> BUArr b -> a
foldBU :: UAE a => (a -> a -> a) -> a -> BUArr a -> a
scanlBU :: (UAE a, UAE b) => (a -> b -> a) -> a -> BUArr b -> BUArr a
scanBU :: UAE a => (a -> a -> a) -> a -> BUArr a -> BUArr a
sumBU :: (UAE a, Num a) => BUArr a -> a
toBU :: UAE e => [e] -> BUArr e
fromBU :: UAE e => BUArr e -> [e]
hPutBU :: forall e. UAE e => Handle -> BUArr e -> IO ()
hGetBU :: forall e. UAE e => Handle -> IO (BUArr e)
Types
data BBArr e Source
Immutable boxed arrays
show/hide Instances
Show e => Show (BBArr e)
HS e => HS (BBArr e)
data MBBArr s e Source
Mutable boxed arrays
Operations on immutable arrays
lengthBB :: BBArr e -> IntSource
Length of an immutable boxed array
indexBB :: BBArr e -> Int -> eSource
Access an element in an immutable, boxed array
extractBB :: BBArr e -> Int -> Int -> BBArr eSource
Extract a slice from an array (given by its start index and length)
Operations on mutable arrays
newMBB :: Int -> ST s (MBBArr s e)Source
Allocate a boxed array
lengthMBB :: MBBArr s e -> IntSource
Length of a mutable boxed array
readMBB :: MBBArr s e -> Int -> ST s eSource
Access an element in an mutable, boxed array
writeMBB :: MBBArr s e -> Int -> e -> ST s ()Source
Update an element in an mutable, boxed array
unsafeFreezeMBB :: MBBArr s e -> Int -> ST s (BBArr e)Source

Turn a mutable into an immutable array WITHOUT copying its contents, which implies that the mutable array must not be mutated anymore after this operation has been executed.

  • The explicit size parameter supports partially filled arrays (and must be less than or equal the size used when allocating the mutable array)
unsafeFreezeAllMBB :: MBBArr s e -> ST s (BBArr e)Source

Turn a mutable into an immutable array WITHOUT copying its contents, which implies that the mutable array must not be mutated anymore after this operation has been executed.

  • In contrast to unsafeFreezeMBB, this operation always freezes the entire array.
extractMBB :: MBBArr s e -> Int -> Int -> ST s (BBArr e)Source
Extract a slice from a mutable array (the slice is immutable)
copyMBB :: MBBArr s e -> Int -> BBArr e -> ST s ()Source
Copy a the contents of an immutable array into a mutable array from the specified position on
Types
data BUArr e Source
Immutable unboxed arrays
show/hide Instances
(Eq e, UAE e) => Eq (BUArr e)
(Show e, UAE e) => Show (BUArr e)
HS e => HS (BUArr e)
data MBUArr s e Source
Mutable unboxed arrays
show/hide Instances
HS e => HS (MBUArr s e)
Elements of unboxed arrays
class HS e => UAE e whereSource
Class of elements that can be stored in unboxed arrays
Methods
indexBU :: BUArr e -> Int -> eSource
Yield the element at the given position of an immutable array.
readMBU :: MBUArr s e -> Int -> ST s eSource
Read the element at the given position of a mutable array.
writeMBU :: MBUArr s e -> Int -> e -> ST s ()Source
Write the element at the given position of a mutable array.
show/hide Instances
Operations on mutable arrays
lengthMBU :: MBUArr s e -> IntSource
Number of elements of a mutable unboxed array
newMBU :: forall s e. UAE e => Int -> ST s (MBUArr s e)Source
Allocate an uninitialised unboxed array
extractMBU :: UAE e => MBUArr s e -> Int -> Int -> ST s (BUArr e)Source
Extract a slice from a mutable array (the slice is immutable)
copyMBU :: UAE e => MBUArr s e -> Int -> BUArr e -> ST s ()Source
Copy a the contents of an immutable array into a mutable array from the specified position on
unsafeFreezeMBU :: MBUArr s e -> Int -> ST s (BUArr e)Source

Turn a mutable into an immutable array WITHOUT copying its contents, which implies that the mutable array must not be mutated anymore after this operation has been executed.

  • The explicit size parameter supports partially filled arrays (and must be less than or equal the size used when allocating the mutable array)
unsafeFreezeAllMBU :: MBUArr s e -> ST s (BUArr e)Source

Turn a mutable into an immutable array WITHOUT copying its contents, which implies that the mutable array must not be mutated anymore after this operation has been executed.

  • In contrast to unsafeFreezeMBU, this operation always freezes the entire array.
Operations on immutable arrays
Basic operations
lengthBU :: BUArr e -> IntSource
Number of elements of an immutable unboxed array
emptyBU :: UAE e => BUArr eSource
Empty array
replicateBU :: UAE e => Int -> e -> BUArr eSource

Combinators for unboxed arrays -

Replicate combinator for unboxed arrays

sliceBU :: BUArr e -> Int -> Int -> BUArr eSource
Produces an array that consists of a subrange of the original one without copying any elements.
extractBU :: UAE e => BUArr e -> Int -> Int -> BUArr eSource
Extract a slice from an array (given by its start index and length)
Streaming
streamBU :: UAE e => BUArr e -> Stream eSource

Stream of unboxed arrays -------------------------

Generate a stream from an array, from left to right

unstreamBU :: UAE e => Stream e -> BUArr eSource
Construct an array from a stream, filling it from left to right
Higher-order and arithmetic operations
mapBU :: (UAE a, UAE b) => (a -> b) -> BUArr a -> BUArr bSource
Map a function over an unboxed array
foldlBU :: UAE b => (a -> b -> a) -> a -> BUArr b -> aSource
Reduce an unboxed array
foldBU :: UAE a => (a -> a -> a) -> a -> BUArr a -> aSource
Reduce an unboxed array using an *associative* combining operator
scanlBU :: (UAE a, UAE b) => (a -> b -> a) -> a -> BUArr b -> BUArr aSource
Prefix reduction of an unboxed array
scanBU :: UAE a => (a -> a -> a) -> a -> BUArr a -> BUArr aSource
Prefix reduction of an unboxed array using an *associative* combining operator
sumBU :: (UAE a, Num a) => BUArr a -> aSource
Summation of an unboxed array
Conversions to/from lists
toBU :: UAE e => [e] -> BUArr eSource
Convert a list to an array
fromBU :: UAE e => BUArr e -> [e]Source
Convert an array to a list
I/O
hPutBU :: forall e. UAE e => Handle -> BUArr e -> IO ()Source
hGetBU :: forall e. UAE e => Handle -> IO (BUArr e)Source
Produced by Haddock version 2.6.1