|
| Data.Array.Parallel.Unlifted.Sequential |
|
|
|
|
| Description |
(c) [2006..2007] Manuel M T Chakravarty & Roman Leshchinskiy
License : see librariesndpLICENSE
Maintainer : Roman Leshchinskiy rl@cse.unsw.edu.au
Stability : experimental
Portability : portable
Description ---------------------------------------------------------------
External interface to unlifted arrays.
Todo ----------------------------------------------------------------------
|
|
| Synopsis |
|
| class HS e => UA e where | | | | data USegd | | | data SUArr e | | | nullU :: UA e => UArr e -> Bool | | | emptyU :: UA e => UArr e | | | singletonU :: UA e => e -> UArr e | | | consU :: UA e => e -> UArr e -> UArr e | | | unitsU :: Int -> UArr () | | | replicateU :: UA e => Int -> e -> UArr e | | | replicateEachU :: UA e => Int -> UArr Int -> UArr e -> UArr e | | | (!:) :: UA e => UArr e -> Int -> e | | | (+:+) :: UA e => UArr e -> UArr e -> UArr e | | | indexedU :: UA e => UArr e -> UArr (Int :*: e) | | | repeatU :: UA e => Int -> UArr e -> UArr e | | | extractU :: UA a => UArr a -> Int -> Int -> UArr a | | | tailU :: UA e => UArr e -> UArr e | | | takeU :: UA e => Int -> UArr e -> UArr e | | | dropU :: UA e => Int -> UArr e -> UArr e | | | splitAtU :: UA e => Int -> UArr e -> (UArr e, UArr e) | | | permuteU :: UA e => UArr e -> UArr Int -> UArr e | | | bpermuteU :: UA e => UArr e -> UArr Int -> UArr e | | | bpermuteDftU :: UA e => Int -> (Int -> e) -> UArr (Int :*: e) -> UArr e | | | reverseU :: UA e => UArr e -> UArr e | | | updateU :: UA e => UArr e -> UArr (Int :*: e) -> UArr e | | | mapU :: (UA e, UA e') => (e -> e') -> UArr e -> UArr e' | | | zipWithU :: (UA a, UA b, UA c) => (a -> b -> c) -> UArr a -> UArr b -> UArr c | | | zipWith3U :: (UA a, UA b, UA c, UA d) => (a -> b -> c -> d) -> UArr a -> UArr b -> UArr c -> UArr d | | | filterU :: UA e => (e -> Bool) -> UArr e -> UArr e | | | packU :: UA e => UArr e -> UArr Bool -> UArr e | | | foldlU :: UA a => (b -> a -> b) -> b -> UArr a -> b | | | foldl1U :: UA a => (a -> a -> a) -> UArr a -> a | | | foldl1MaybeU :: UA a => (a -> a -> a) -> UArr a -> MaybeS a | | | foldU :: UA a => (a -> a -> a) -> a -> UArr a -> a | | | fold1U :: UA a => (a -> a -> a) -> UArr a -> a | | | fold1MaybeU :: UA a => (a -> a -> a) -> UArr a -> MaybeS a | | | scanlU :: (UA a, UA b) => (b -> a -> b) -> b -> UArr a -> UArr b | | | scanl1U :: UA a => (a -> a -> a) -> UArr a -> UArr a | | | scanU :: UA a => (a -> a -> a) -> a -> UArr a -> UArr a | | | scan1U :: UA a => (a -> a -> a) -> UArr a -> UArr a | | | scanResU :: UA a => (a -> a -> a) -> a -> UArr a -> UArr a :*: a | | | mapAccumLU :: (UA a, UA b) => (c -> a -> c :*: b) -> c -> UArr a -> UArr b | | | filterSU :: UA e => (e -> Bool) -> SUArr e -> SUArr e | | | packCU :: UA e => UArr Bool -> SUArr e -> SUArr e | | | combineU :: UA a => UArr Bool -> UArr a -> UArr a -> UArr a | | | combineSU :: UA a => UArr Bool -> SUArr a -> SUArr a -> UArr a | | | combineCU :: UA e => UArr Bool -> SUArr e -> SUArr e -> SUArr e | | | sliceSU :: UA e => SUArr e -> Int -> Int -> SUArr e | | | extractSU :: UA e => SUArr e -> Int -> Int -> SUArr e | | | takeCU :: UA e => Int -> SUArr e -> SUArr e | | | dropCU :: UA e => Int -> SUArr e -> SUArr e | | | elemU :: (Eq e, UA e) => e -> UArr e -> Bool | | | notElemU :: (Eq e, UA e) => e -> UArr e -> Bool | | | andU :: UArr Bool -> Bool | | | orU :: UArr Bool -> Bool | | | anyU :: UA e => (e -> Bool) -> UArr e -> Bool | | | allU :: UA e => (e -> Bool) -> UArr e -> Bool | | | sumU :: (Num e, UA e) => UArr e -> e | | | productU :: (Num e, UA e) => UArr e -> e | | | maximumU :: (Ord e, UA e) => UArr e -> e | | | minimumU :: (Ord e, UA e) => UArr e -> e | | | maximumByU :: UA e => (e -> e -> Ordering) -> UArr e -> e | | | minimumByU :: UA e => (e -> e -> Ordering) -> UArr e -> e | | | maximumIndexU :: (Ord e, UA e) => UArr e -> Int | | | minimumIndexU :: (Ord e, UA e) => UArr e -> Int | | | maximumIndexByU :: UA e => (e -> e -> Ordering) -> UArr e -> Int | | | minimumIndexByU :: UA e => (e -> e -> Ordering) -> UArr e -> Int | | | zipU :: (UA a, UA b) => UArr a -> UArr b -> UArr (a :*: b) | | | zip3U :: (UA e1, UA e2, UA e3) => UArr e1 -> UArr e2 -> UArr e3 -> UArr ((e1 :*: e2) :*: e3) | | | unzipU :: (UA a, UA b) => UArr (a :*: b) -> UArr a :*: UArr b | | | unzip3U :: (UA e1, UA e2, UA e3) => UArr ((e1 :*: e2) :*: e3) -> (UArr e1 :*: UArr e2) :*: UArr e3 | | | fstU :: (UA a, UA b) => UArr (a :*: b) -> UArr a | | | sndU :: (UA a, UA b) => UArr (a :*: b) -> UArr b | | | enumFromToU :: Int -> Int -> UArr Int | | | enumFromThenToU :: Int -> Int -> Int -> UArr Int | | | enumFromStepLenU :: Int -> Int -> Int -> UArr Int | | | enumFromToEachU :: Int -> UArr (Int :*: Int) -> UArr Int | | | findU :: UA a => (a -> Bool) -> UArr a -> Maybe a | | | findIndexU :: UA a => (a -> Bool) -> UArr a -> Maybe Int | | | toU :: UA e => [e] -> UArr e | | | fromU :: UA e => UArr e -> [e] | | | randomU :: (UA a, Random a, RandomGen g) => Int -> g -> UArr a | | | randomRU :: (UA a, Random a, RandomGen g) => Int -> (a, a) -> g -> UArr a | | | class UA a => UIO a where | | | | concatSU :: UA e => SUArr e -> UArr e | | | flattenSU :: UA e => SUArr e -> UArr e | | | (>:) :: UA a => USegd -> UArr a -> SUArr a | | | segmentU :: (UA e', UA e) => SUArr e' -> UArr e -> SUArr e | | | segmentArrU :: UA e => UArr Int -> UArr e -> SUArr e | | | segdSU :: UA e => SUArr e -> USegd | | | lengthSU :: UA e => SUArr e -> Int | | | singletonSU :: UA e => UArr e -> SUArr e | | | replicateSU :: UA e => UArr Int -> UArr e -> SUArr e | | | replicateCU :: UA e => Int -> UArr e -> SUArr e | | | (+:+^) :: UA e => SUArr e -> SUArr e -> SUArr e | | | indexedSU :: UA e => SUArr e -> SUArr (Int :*: e) | | | (^+:+^) :: UA a => SUArr a -> SUArr a -> SUArr a | | | (!:^) :: UA e => SUArr e -> UArr Int -> UArr e | | | lengthsSU :: UA e => SUArr e -> UArr Int | | | indicesSU :: UA e => SUArr e -> UArr Int | | | fstSU :: (UA a, UA b) => SUArr (a :*: b) -> SUArr a | | | sndSU :: (UA a, UA b) => SUArr (a :*: b) -> SUArr b | | | zipSU :: (UA a, UA b) => SUArr a -> SUArr b -> SUArr (a :*: b) | | | bpermuteSU :: UA e => SUArr e -> SUArr Int -> SUArr e | | | bpermuteSU' :: UA e => UArr e -> SUArr Int -> SUArr e | | | mapSU :: (UA a, UA b) => (a -> b) -> SUArr a -> SUArr b | | | zipWithSU :: (UA a, UA b, UA c) => (a -> b -> c) -> SUArr a -> SUArr b -> SUArr c | | | foldlSU :: (UA a, UA b) => (b -> a -> b) -> b -> SUArr a -> UArr b | | | foldSU :: UA a => (a -> a -> a) -> a -> SUArr a -> UArr a | | | fold1SU :: UA a => (a -> a -> a) -> SUArr a -> UArr a | | | andSU :: SUArr Bool -> UArr Bool | | | orSU :: SUArr Bool -> UArr Bool | | | sumSU :: (Num e, UA e) => SUArr e -> UArr e | | | productSU :: (Num e, UA e) => SUArr e -> UArr e | | | maximumSU :: (Ord e, UA e) => SUArr e -> UArr e | | | minimumSU :: (Ord e, UA e) => SUArr e -> UArr e | | | enumFromToSU :: (Enum e, UA e) => UArr e -> UArr e -> SUArr e | | | enumFromThenToSU :: (Enum e, UA e) => UArr e -> UArr e -> UArr e -> SUArr e | | | toSU :: UA e => [[e]] -> SUArr e | | | fromSU :: UA e => SUArr e -> [[e]] | | | lengthsUSegd :: USegd -> UArr Int | | | lengthsToUSegd :: UArr Int -> USegd | | | toUSegd :: UArr (Int :*: Int) -> USegd | | | fromUSegd :: USegd -> UArr (Int :*: Int) | | | newU :: UA e => Int -> (forall s. MUArr e s -> ST s ()) -> UArr e | | | permuteMU :: UA e => MUArr e s -> UArr e -> UArr Int -> ST s () | | | atomicUpdateMU :: UA e => MUArr e s -> UArr (Int :*: e) -> ST s () | | | unsafeFreezeAllMU :: UA e => MUArr e s -> ST s (UArr e) | | | idstr | | | name | | | versnum | | | date | | | version | | | copyright | | | disclaimer | | | lengthU' :: UA e => UArr e -> Int |
|
|
|
| Array classes
|
|
|
Basic operations on representation types
-----------------------------------------
This type class determines the types that can be elements immutable
unboxed arrays. The representation type of these arrays is defined by way
of an associated type. All representation-dependent functions are methods
of this class.
| | | Associated Types | | | | Methods | | | Yield the length of an unboxed array
| | | | Restrict access to a subrange of the original array (no copying)
| | | | Allocate a mutable unboxed array
| | | | Indicate whether the type supports atomic updates
| | | | Copy the contents of an immutable unboxed array into a mutable one
from the specified position on
|
| | Instances | |
|
|
| Array types
|
|
|
| Segment descriptors represent the structure of nested arrays. For each
segment, it stores the length and the starting index in the flat data
array.
| Instances | |
|
|
|
Segmented arrays
-----------------
Segmented arrays (only one level of segmentation)
| Instances | |
|
|
| Basic operations
|
|
|
| Test whether the given array is empty
|
|
|
| Yield an empty array
|
|
|
| Yield a singleton array
|
|
|
| Prepend an element to an array
|
|
|
Basic operations on unboxed arrays
-----------------------------------
Yield an array of units
|
|
|
| Yield an array where all elements contain the same value
|
|
|
|
|
| Array indexing
|
|
|
| Concatenate two arrays
|
|
|
Indexing
---------
Associate each element of the array with its index
|
|
|
| Repeat an array n times
|
|
| Subarrays
|
|
|
|
|
| Yield the tail of an array
|
|
|
| Extract a prefix of an array
|
|
|
| Extract a suffix of an array
|
|
|
| Split an array into two halves at the given index
|
|
| Permutations
|
|
|
| Standard permutation
|
|
|
| Back permutation operation (ie, the permutation vector determines for each
position in the result array its origin in the input array)
|
|
|
| :: UA e | | | => Int | length of result array
| | -> Int -> e | initialiser function
| | -> UArr (Int :*: e) | index-value pairs
| | -> UArr e | | Default back permute
- The values of the index-value pairs are written into the position in the
result array that is indicated by the corresponding index.
- All positions not covered by the index-value pairs will have the value
determined by the initialiser function for that index position.
|
|
|
|
| Reverse the order of elements in an array
|
|
|
| Yield an array constructed by updating the first array by the
associations from the second array (which contains index/value pairs).
|
|
| Higher-order operations
|
|
|
| Map a function over an array
|
|
|
|
|
|
|
| Extract all elements from an array that meet the given predicate
|
|
|
| Extract all elements from an array according to a given flag array
|
|
|
| Array reduction proceeding from the left
|
|
|
Array reduction proceeding from the left for non-empty arrays
FIXME: Rewrite for Streams.
|
|
|
|
|
| Array reduction that requires an associative combination function with its
unit
|
|
|
| Reduction of a non-empty array which requires an associative combination
function
|
|
|
|
|
| Prefix scan proceedings from left to right
|
|
|
| Prefix scan of a non-empty array proceeding from left to right
|
|
|
| Prefix scan proceeding from left to right that needs an associative
combination function with its unit
|
|
|
| Prefix scan of a non-empty array proceeding from left to right that needs
an associative combination function
|
|
|
|
|
Accumulating map from left to right. Does not return the accumulator.
FIXME: Naming inconsistent with lists.
|
|
|
| Filter segmented array
|
|
|
|
|
|
|
| Merge two segmented arrays according to flag array
|
|
|
|
| Segmented Subarrays
|
|
|
| Extract a subrange of the segmented array without copying the elements.
|
|
|
| Extract a subrange of the segmented array (elements are copied).
|
|
|
|
|
|
| Searching
|
|
|
| Determine whether the given element is in an array
|
|
|
| Negation of elemU
|
|
| Logical operations
|
|
|
|
|
|
|
|
|
|
| Arithmetic operations
|
|
|
| Compute the sum of an array of numerals
|
|
|
| Compute the product of an array of numerals
|
|
|
| Determine the maximum element in an array
|
|
|
| Determine the minimum element in an array
|
|
|
| Determine the maximum element in an array under the given ordering
|
|
|
| Determine the minimum element in an array under the given ordering
|
|
|
| Determine the index of the maximum element in an array
|
|
|
| Determine the index of the minimum element in an array
|
|
|
| Determine the index of the maximum element in an array under the given
ordering
|
|
|
| Determine the index of the minimum element in an array under the given
ordering
|
|
| Arrays of pairs
|
|
|
| Elementwise pairing of array elements.
|
|
|
|
|
| Elementwise unpairing of array elements.
|
|
|
|
|
| Yield the first components of an array of pairs.
|
|
|
| Yield the second components of an array of pairs.
|
|
| Enumerations
|
|
|
Yield an enumerated array
FIXME: See comments about enumFromThenToS
|
|
|
Yield an enumerated array using a specific step
FIXME: See comments about enumFromThenToS
|
|
|
|
|
|
| Searching
|
|
|
|
|
|
| Conversions to/from lists
|
|
|
Conversion
-----------
Turn a list into a parallel array
|
|
|
| Collect the elements of a parallel array in a list
|
|
| Unlifted.Sequential arrays
|
|
|
|
|
|
| I/O
|
|
|
| | Methods | | | Instances | |
|
|
| Segmentation
|
|
|
| Concatenate the subarrays of an array of arrays
|
|
|
| Yield the flat data array
|
|
|
| Compose a nested array.
|
|
|
| Segment an array according to the segmentation of the first argument
|
|
|
| Segment an array according to the segmentation of the first argument
|
|
|
Operations on segmented arrays
-------------------------------
Yield the segment descriptor
|
|
| Basic operations (segmented)
|
|
|
| Yield the number of segments.
|
|
|
| Segmentation
-------------
|
|
|
|
|
| Yield a segmented array, where each element contains the same array value
|
|
|
Concatenate two arrays
FIXME: rename
|
|
|
| Associate each data element with its index
|
|
|
| Concatenation
--------------
|
|
|
| Array indexing
|
|
| Basic operations lifted
|
|
|
| Yield the lengths of the segments.
|
|
|
| Yield the starting indices of the segments.
|
|
| Zipping (segmented)
|
|
|
| Zipping
--------
|
|
|
|
|
|
| Permutations (segmented)
|
|
|
| Segmented back permute
|
|
|
|
| Higher-order operations (segmented)
|
|
|
|
|
|
|
| Segmented array reduction proceeding from the left
|
|
|
| Segmented array reduction that requires an associative combination
function with its unit
|
|
|
| Segmented array reduction with non-empty subarrays and an associative
combination function
|
|
| Logical operations (segmented)
|
|
|
|
|
|
| Arithmetic operations (segmented)
|
|
|
| Compute the segmented sum of an array of numerals
|
|
|
| Compute the segmented product of an array of numerals
|
|
|
| Determine the maximum element in each subarray
|
|
|
| Determine the minimum element in each subarray
|
|
| Enumerations (segmented)
|
|
|
Enumeration functions
----------------------
Yield a segmented enumerated array
|
|
|
| Yield a segmented enumerated array using a specific step
|
|
| Conversions to/from lists (segmented)
|
|
|
Conversion
-----------
Turn a nested list into a segmented parallel array
|
|
|
| Turn a segmented array into a nested list
|
|
| Segment descriptors
|
|
|
| Yield the segment lengths of a segment descriptor
|
|
|
| Convert a length array into a segment descriptor.
|
|
|
| Convert an array of length/index pairs to a segment descriptor.
|
|
|
| Convert a segment descriptor to an array of length/index pairs.
|
|
| Mutable arrays
|
|
|
| Creating unboxed arrays
------------------------
|
|
|
| Permutations
-------------
|
|
|
|
|
|
| Library id
|
|
| idstr |
|
| name |
|
| versnum |
|
| date |
|
| version |
|
| copyright |
|
| disclaimer |
|
|
| FIXME: A fuseable version of lengthU, should go away
|
|
| Produced by Haddock version 2.4.2 |