| dph-base-0.3: Basic Definitions for Data-Parallel Haskell. | Contents | Index |
|
Data.Array.Parallel.Arr | Portability | non-portable (unboxed values and GHC libraries) | Stability | internal | Maintainer | Roman Leshchinskiy <rl@cse.unsw.edu.au> |
|
|
|
|
|
Description |
Interface to the Arr modules
|
|
Synopsis |
|
|
|
|
Types
|
|
data BBArr e |
Immutable boxed arrays
| Instances | |
|
|
data MBBArr s e |
|
|
Operations on immutable arrays
|
|
lengthBB :: BBArr e -> Int |
Length of an immutable boxed array
|
|
indexBB :: BBArr e -> Int -> e |
Access an element in an immutable, boxed array
|
|
extractBB :: BBArr e -> Int -> Int -> BBArr e |
Extract a slice from an array (given by its start index and length)
|
|
Operations on mutable arrays
|
|
newMBB :: Int -> ST s (MBBArr s e) |
Allocate a boxed array
|
|
lengthMBB :: MBBArr s e -> Int |
Length of a mutable boxed array
|
|
readMBB :: MBBArr s e -> Int -> ST s e |
Access an element in an mutable, boxed array
|
|
writeMBB :: MBBArr s e -> Int -> e -> ST s () |
Update an element in an mutable, boxed array
|
|
unsafeFreezeMBB :: MBBArr s e -> Int -> ST s (BBArr e) |
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) |
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) |
Extract a slice from a mutable array (the slice is immutable)
|
|
copyMBB :: MBBArr s e -> Int -> BBArr e -> ST s () |
Copy a the contents of an immutable array into a mutable array from the
specified position on
|
|
Types
|
|
data BUArr e |
Immutable unboxed arrays
| Instances | |
|
|
data MBUArr s e |
Mutable unboxed arrays
| Instances | |
|
|
Elements of unboxed arrays
|
|
class HS e => UAE e where |
Class of elements that can be stored in unboxed arrays
| | Methods | indexBU :: BUArr e -> Int -> e | Yield the element at the given position of an immutable array.
| | readMBU :: MBUArr s e -> Int -> ST s e | Read the element at the given position of a mutable array.
| | writeMBU :: MBUArr s e -> Int -> e -> ST s () | Write the element at the given position of a mutable array.
|
| | Instances | |
|
|
Operations on mutable arrays
|
|
lengthMBU :: MBUArr s e -> Int |
Number of elements of a mutable unboxed array
|
|
newMBU :: forall s e. UAE e => Int -> ST s (MBUArr s e) |
Allocate an uninitialised unboxed array
|
|
extractMBU :: UAE e => MBUArr s e -> Int -> Int -> ST s (BUArr e) |
Extract a slice from a mutable array (the slice is immutable)
|
|
copyMBU :: UAE e => MBUArr s e -> Int -> BUArr e -> ST s () |
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) |
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) |
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 -> Int |
Number of elements of an immutable unboxed array
|
|
emptyBU :: UAE e => BUArr e |
Empty array
|
|
replicateBU :: UAE e => Int -> e -> BUArr e |
Combinators for unboxed arrays
-
Replicate combinator for unboxed arrays
|
|
sliceBU :: BUArr e -> Int -> Int -> BUArr e |
Produces an array that consists of a subrange of the original one without
copying any elements.
|
|
extractBU :: UAE e => BUArr e -> Int -> Int -> BUArr e |
Extract a slice from an array (given by its start index and length)
|
|
Streaming
|
|
streamBU :: UAE e => BUArr e -> Stream e |
Stream of unboxed arrays
-------------------------
Generate a stream from an array, from left to right
|
|
unstreamBU :: UAE e => Stream e -> BUArr e |
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 b |
Map a function over an unboxed array
|
|
foldlBU :: UAE b => (a -> b -> a) -> a -> BUArr b -> a |
Reduce an unboxed array
|
|
foldBU :: UAE a => (a -> a -> a) -> a -> BUArr a -> a |
Reduce an unboxed array using an *associative* combining operator
|
|
scanlBU :: (UAE a, UAE b) => (a -> b -> a) -> a -> BUArr b -> BUArr a |
Prefix reduction of an unboxed array
|
|
scanBU :: UAE a => (a -> a -> a) -> a -> BUArr a -> BUArr a |
Prefix reduction of an unboxed array using an *associative* combining
operator
|
|
sumBU :: (UAE a, Num a) => BUArr a -> a |
Summation of an unboxed array
|
|
Conversions to/from lists
|
|
toBU :: UAE e => [e] -> BUArr e |
Convert a list to an array
|
|
fromBU :: UAE e => BUArr e -> [e] |
Convert an array to a list
|
|
I/O
|
|
hPutBU :: forall e. UAE e => Handle -> BUArr e -> IO () |
|
hGetBU :: forall e. UAE e => Handle -> IO (BUArr e) |
|
Produced by Haddock version 2.4.2 |