|
|
|
|
|
| Description |
|
|
| Synopsis |
|
| class UA e where | | | | streamU :: UA a => UArr a -> Stream a | | | unstreamU :: UA a => Stream a -> UArr a | | | toU :: UA e => [e] -> UArr e | | | fromU :: UA e => UArr e -> [e] | | | emptyU :: UA e => UArr e | | | singletonU :: UA e => e -> UArr e | | | consU :: UA e => e -> UArr e -> UArr e | | | snocU :: UA e => UArr e -> e -> UArr e | | | appendU :: UA e => UArr e -> UArr e -> UArr e | | | headU :: UA e => UArr e -> e | | | lastU :: UA e => UArr e -> e | | | tailU :: UA e => UArr e -> UArr e | | | initU :: UA e => UArr e -> UArr e | | | nullU :: UA e => UArr e -> Bool | | | unitsU :: Int -> UArr () | | | lengthU :: UA e => UArr e -> Int | | | mapU :: (UA e, UA e') => (e -> e') -> UArr e -> UArr e' | | | 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 | | | 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 | | | 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 | | | 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 | | | replicateU :: UA e => Int -> e -> UArr e | | | replicateEachU :: UA e => Int -> UArr Int -> 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) | | | takeWhileU :: UA e => (e -> Bool) -> UArr e -> UArr e | | | dropWhileU :: UA e => (e -> Bool) -> UArr e -> UArr e | | | elemU :: (Eq e, UA e) => e -> UArr e -> Bool | | | notElemU :: (Eq e, UA e) => e -> UArr e -> Bool | | | filterU :: UA e => (e -> Bool) -> UArr e -> UArr e | | | findU :: UA a => (a -> Bool) -> UArr a -> Maybe a | | | indexU :: UA e => UArr e -> Int -> e | | | findIndexU :: UA a => (a -> Bool) -> UArr a -> Maybe Int | | | lookupU :: (Eq a, UA a, UA b) => a -> UArr (a :*: b) -> Maybe b | | | 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 | | | 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 | | | fstU :: (UA a, UA b) => UArr (a :*: b) -> UArr a | | | sndU :: (UA a, UA b) => UArr (a :*: b) -> UArr b | | | enumFromToU :: (UA a, Integral a) => a -> a -> UArr a | | | enumFromToFracU :: (UA a, RealFrac a) => a -> a -> UArr a | | | enumFromThenToU :: Int -> Int -> Int -> UArr Int | | | enumFromStepLenU :: Int -> Int -> Int -> UArr Int | | | enumFromToEachU :: Int -> UArr (Int :*: Int) -> UArr Int | | | combineU :: UA a => UArr Bool -> UArr a -> UArr a -> UArr a | | | packU :: UA e => UArr e -> UArr Bool -> UArr e | | | indexedU :: UA e => UArr e -> UArr (Int :*: e) | | | repeatU :: UA e => Int -> UArr e -> UArr e | | | unfoldU :: UA a => Int -> (b -> MaybeS (a :*: b)) -> b -> UArr a | | | class UA a => UIO a where | | | | newU :: UA e => Int -> (forall s. MUArr e s -> ST s ()) -> UArr e | | | unsafeFreezeAllMU :: UA e => 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 () | | | unstreamMU :: UA a => MUArr a s -> Stream a -> ST s Int | | | data a :*: b = !a :*: !b | | | | | fstS :: (a :*: b) -> a | | | sndS :: (a :*: b) -> b | | | pairS :: (a, b) -> a :*: b | | | unpairS :: (a :*: b) -> (a, b) | | | unsafe_pairS :: (a, b) -> a :*: b | | | unsafe_unpairS :: (a :*: b) -> (a, b) | | | curryS :: ((a :*: b) -> c) -> a -> b -> c | | | uncurryS :: (a -> b -> c) -> (a :*: b) -> c | | | | | maybeS :: b -> (a -> b) -> MaybeS a -> b | | | fromMaybeS :: a -> MaybeS a -> a |
|
|
|
| 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 | | | Restrict access to a subrange of the original array (no copying)
| | | | Yield the length of a mutable unboxed array
| | | | Allocate a mutable unboxed array
| | | | Read an element from a mutable unboxed array
| | | | Update an element in a mutable unboxed array
| | | | Copy the contents of an immutable unboxed array into a mutable one
from the specified position on
| | | | Convert a mutable into an immutable unboxed array
|
| | Instances | |
|
|
| The pure and mutable array types
|
|
| Streaming pure arrays
|
|
|
| Generate a stream from an array, from left to right
|
|
|
| Create an array from a stream, filling it from left to right
|
|
| Conversions to/from lists
|
|
|
Conversion
-----------
Turn a list into a parallel array
|
|
|
| Collect the elements of a parallel array in a list
|
|
| Basic operations on pure arrays
|
|
| Introducing and eliminating UArrs
|
|
|
| Yield an empty array
|
|
|
| Yield a singleton array
|
|
| Basic interface
|
|
|
| Prepend an element to an array
|
|
|
| Append an element to an array
|
|
|
| Concatenate two arrays
|
|
|
|
|
|
|
|
|
|
|
| Test whether the given array is empty
|
|
|
Basic operations on unboxed arrays
-----------------------------------
Yield an array of units
|
|
|
| O(1), length returns the length of a UArr as an Int.
|
|
| Transforming UArrs
|
|
|
| Map a function over an array
|
|
| Reducing UArrs (folds)
|
|
|
| Array reduction that requires an associative combination function with its
unit
|
|
|
| Reduction of a non-empty array which requires an associative combination
function
|
|
|
|
|
| Array reduction proceeding from the left
|
|
|
Array reduction proceeding from the left for non-empty arrays
FIXME: Rewrite for Streams.
foldl1U :: UA a => (a -> a -> a) -> UArr a -> a
{--}
foldl1U f arr = checkNotEmpty (here foldl1U) (lengthU arr) $
foldlU f (arr indexU 0) (sliceU arr 1 (lengthU arr - 1))
|
|
|
|
| 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
|
|
| Building UArrs
|
|
| Scans
|
|
|
| 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 UArrs
|
|
|
Accumulating map from left to right. Does not return the accumulator.
FIXME: Naming inconsistent with lists.
|
|
| Generating UArrs
|
|
|
| Yield an array where all elements contain the same value
|
|
|
|
| Subarrays
|
|
| Breaking arrays
|
|
|
|
|
|
|
| Split an array into two halves at the given index
|
|
|
| takeWhile, applied to a predicate p and a UArr xs,
returns the longest prefix (possibly empty) of xs of elements that satisfy p.
|
|
|
| dropWhile p xs returns the suffix remaining after takeWhile p xs.
|
|
| Searching Arrays
|
|
| Searching by equality
|
|
|
| Determine whether the given element is in an array
|
|
|
| Negation of elemU
|
|
| Searching with a predicate
|
|
|
| Extract all elements from an array that meet the given predicate
|
|
|
| O(n),fusion. The find function takes a predicate and an array
and returns the first element in the list matching the predicate, or
Nothing if there is no such element.
|
|
| Indexing UArr
|
|
|
| Array indexing
|
|
|
| O(n), fusion, The findIndex function takes a predicate and an array and returns
the index of the first element in the array satisfying the predicate,
or Nothing if there is no such element.
|
|
|
| O(n),fusion. lookup key assocs looks up a key in an array
of pairs treated as an association table.
|
|
| Zipping and unzipping
|
|
|
| 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
|
|
|
|
|
|
| Low level conversions
|
|
| Low level conversions
|
|
| Copying arrays
|
|
| Packing CStrings and pointers
|
|
| Using UArrs as CStrings
|
|
| I/O with UArrs
|
|
|
|
|
| Extract all elements from an array according to a given flag array
|
|
|
Indexing
---------
Associate each element of the array with its index
|
|
|
| Repeat an array n times
|
|
| Permutations
|
|
| Searching
|
|
| Arrays of pairs
|
|
| Random arrays
|
|
|
|
| I/O
|
|
|
| | Methods | | | Instances | |
|
|
| Operations on mutable arrays
|
|
|
| Creating unboxed arrays
------------------------
|
|
|
|
|
| Permutations
-------------
|
|
|
|
|
| Fill a mutable array from a stream from left to right and yield
the number of elements written.
|
|
| Strict pairs and sums
|
|
|
| Strict pair
| | Constructors | | Instances | |
|
|
|
|
|
| Injection and projection functions
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| Currying
|
|
| curryS :: ((a :*: b) -> c) -> a -> b -> c | Source |
|
|
| uncurryS :: (a -> b -> c) -> (a :*: b) -> c | Source |
|
|
| Strict Maybe
|
|
|
| Strict Maybe
| | Constructors | | Instances | |
|
|
|
|
|
|
| Lazy wrapper
|
|
| Class of hyperstrict types
|
|
| Produced by Haddock version 2.4.2 |