uvector-0.1.1.0: Fast unboxed arrays with a flexible interface

PortabilitySee .cabal file
MaintainerDon Stewart

Data.Array.Vector

Contents

Description

The top level interface to operations on strict, non-nested, fusible arrays.

Note that the time complexities provided for functions in this package depend on fusion. Thus the times given assume that fusion did not occur and that the full operation is performed. In some cases fusion can take multiple O(n) operations on UArrs and optimize them out of the generated code completely.

Synopsis

Array classes

class UA e whereSource

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

data UArr e Source

The basic array datatype.

data MUArr e :: * -> *Source

Methods

sliceU :: UArr e -> Int -> Int -> UArr eSource

O(1). sliceU restricts access to a subrange of the original array (no copying).

lengthMU :: MUArr e s -> IntSource

O(1). lengthMU yields the length of a mutable unboxed array.

newMU :: Int -> ST s (MUArr e s)Source

O(1). newMU allocates a mutable unboxed array of the specified length.

readMU :: MUArr e s -> Int -> ST s eSource

O(1). readMU reads the element at the specified index of a mutable unboxed array.

writeMU :: MUArr e s -> Int -> e -> ST s ()Source

O(1). writeMU writes a new value to the specified index of a mutable unboxed array.

copyMU :: MUArr e s -> Int -> UArr e -> ST s ()Source

O(n). copyMU copies the contents of an immutable unboxed array into a mutable one starting from the specified index.

unsafeFreezeMU :: MUArr e s -> Int -> ST s (UArr e)Source

O(1). unsafeFreezeMU converts a prefix of a mutable array into an immutable unboxed array, without copying. The mutable array must not be mutated after this.

memcpyMU :: MUArr e s -> MUArr e s -> Int -> ST s ()Source

Copy a portion of one mutable array to a second.

memcpyOffMU :: MUArr e s -> MUArr e s -> Int -> Int -> Int -> ST s ()Source

Copy a portion of one mutable array to a second, beginning at the specified offsets for each.

memmoveOffMU :: MUArr e s -> MUArr e s -> Int -> Int -> Int -> ST s ()Source

Copy a portion of one mutable array to a second, beginning at the specified offsets for each. This operation is safe even if the source and destination are the same.

Instances

UA Bool 
UA Char 
UA Double 
UA Float 
UA Int 
UA Int8 
UA Int16 
UA Int32 
UA Int64 
UA Word 
UA Word8 
UA Word16 
UA Word32 
UA Word64 
UA ()

Array operations on the unit representation.

(Integral a, UA a) => UA (Ratio a) 
(RealFloat a, UA a) => UA (Complex a) 
(UA a, UA b) => UA (:*: a b)

Array operations on the pair representation.

Streaming pure arrays

streamU :: UA a => UArr a -> Stream aSource

O(1). streamU generates a stream from an array, from left to right.

unstreamU :: UA a => Stream a -> UArr aSource

O(n). unstreamU creates an array from a stream, filling it from left to right.

Conversions to/from lists

toU :: UA e => [e] -> UArr eSource

O(n). toU turns a list into a UArr.

fromU :: UA e => UArr e -> [e]Source

O(n). fromU collects the elements of a UArr into a list.

Basic operations on pure arrays

Introducing and eliminating UArrs

emptyU :: UA e => UArr eSource

O(1). emptyU yields an empty array.

singletonU :: UA e => e -> UArr eSource

O(1). singletonU yields a singleton array containing the given element.

Basic interface

consU :: UA e => e -> UArr e -> UArr eSource

O(n). consU prepends the given element to an array.

snocU :: UA e => UArr e -> e -> UArr eSource

O(n). snocU appends the given element to an array.

appendU :: UA e => UArr e -> UArr e -> UArr eSource

O(n). appendU concatenates two arrays.

concatU :: UA e => [UArr e] -> UArr eSource

O(n). Concatenate a list of arrays.

headU :: UA e => UArr e -> eSource

O(1). headU yields the first element of an array.

lastU :: UA e => UArr e -> eSource

O(n). lastU yields the last element of an array.

tailU :: UA e => UArr e -> UArr eSource

O(n). tailU yields the given array without its initial element.

initU :: UA e => UArr e -> UArr eSource

O(n). initU yields the input array without its last element.

nullU :: UA e => UArr e -> BoolSource

O(1). nullU tests whether the given array is empty.

unitsU :: Int -> UArr ()Source

O(1). Yield an array of units.

lengthU :: UA e => UArr e -> IntSource

O(1). lengthU returns the length of a UArr as an Int.

Transforming UArrs

mapU :: (UA e, UA e') => (e -> e') -> UArr e -> UArr e'Source

O(n). mapU maps a function over an array.

Reducing UArrs (folds)

foldU :: UA a => (a -> a -> a) -> a -> UArr a -> aSource

O(n). foldU reduces an array using an associative combination function and its unit.

fold1U :: UA a => (a -> a -> a) -> UArr a -> aSource

O(n). fold1U is a variant of foldU that requires a non-empty input array. Throws an exception if its input array is empty.

fold1MaybeU :: UA a => (a -> a -> a) -> UArr a -> MaybeS aSource

O(n). fold1MaybeU behaves like fold1U but returns NothingS if the input array is empty.

foldlU :: UA a => (b -> a -> b) -> b -> UArr a -> bSource

O(n). foldlU reduces an array proceeding from the left.

foldl1U :: UA a => (a -> a -> a) -> UArr a -> aSource

O(n). foldl1U is a variant of foldlU that assumes a non-empty input array, but requires no starting element. Throws an exception if the input array is empty.

foldrU :: UA a => (a -> b -> b) -> b -> UArr a -> bSource

O(n) foldrU, applied to a binary operator, a starting value (typically the right-identity of the operator), and a 'UArr a', reduces the 'UArr a' using the binary operator, from right to left.

foldr1U :: UA a => (a -> a -> a) -> UArr a -> aSource

O(n) A variant of foldr that has no starting value argument, and thus must be applied to a non-empty 'UArr a'.

foldl1MaybeU :: UA a => (a -> a -> a) -> UArr a -> MaybeS aSource

O(n). foldl1MaybeU behaves like foldl1U but returns NothingS if the input array is empty.

Logical operations

andU :: UArr Bool -> BoolSource

O(n). andU yields the conjunction of a boolean array.

orU :: UArr Bool -> BoolSource

O(n). andU yields the disjunction of a boolean array.

anyU :: UA e => (e -> Bool) -> UArr e -> BoolSource

O(n). anyU p u determines whether any element in array u satisfies predicate p.

allU :: UA e => (e -> Bool) -> UArr e -> BoolSource

O(n). allU p u determines whether all elements in array u satisfy predicate p.

Arithmetic operations

sumU :: (Num e, UA e) => UArr e -> eSource

O(n). sumU computes the sum of an array of a Num instance.

productU :: (Num e, UA e) => UArr e -> eSource

O(n). productU computes the product of an array of a Num instance.

maximumU :: (Ord e, UA e) => UArr e -> eSource

O(n). maximumU finds the maximum element in an array of orderable elements.

minimumU :: (Ord e, UA e) => UArr e -> eSource

O(n). minimumU finds the minimum element in an array of orderable elements.

maximumByU :: UA e => (e -> e -> Ordering) -> UArr e -> eSource

O(n). maximumByU finds the maximum element in an array under the given ordering.

minimumByU :: UA e => (e -> e -> Ordering) -> UArr e -> eSource

O(n). minimumByU finds the minimum element in an array under the given ordering.

Building UArrs

Scans

scanlU :: (UA a, UA b) => (b -> a -> b) -> b -> UArr a -> UArr bSource

O(n). scanlU is equivalent to foldlU on all prefixes (except the array itself) of the input array.

N.B: the behavior of this function differs from that of Data.List. Compare:

scanl (+) 0.0 [1..5] gives [0.0,1.0,3.0,6.0,10.0,15.0]

scanlU (+) 0.0 $ toU [1..5] gives toU [0.0,1.0,3.0,6.0,10.0]

To get behavior closer to the List counterpart, see scanResU.

scanl1U :: UA a => (a -> a -> a) -> UArr a -> UArr aSource

O(n). scanl1U is like scanlU, but requires no starting value.

scanU :: UA a => (a -> a -> a) -> a -> UArr a -> UArr aSource

O(n). scanU is equivalent to foldU on all prefixes (except the array itself) of the input array.

scan1U :: UA a => (a -> a -> a) -> UArr a -> UArr aSource

O(n). scan1U is like scanU, but requires no starting value.

scanResU :: UA a => (a -> a -> a) -> a -> UArr a -> UArr a :*: aSource

O(n). scanResU behaves like scanU, but yields a strict pair with the scanU result as its fstS and the missing element (foldU on the same arguments) as its sndS. Compare:

scanl (+) 0.0 [1..5] gives [0.0,1.0,3.0,6.0,10.0,15.0]

scanlU (+) 0.0 $ toU [1..5] gives toU [0.0,1.0,3.0,6.0,10.0]

scanResU (+) 0.0 $ toU [1..5] gives toU [0.0,1.0,3.0,6.0,10.0] :*: 15.0.

Accumulating UArrs

mapAccumLU :: (UA a, UA b) => (c -> a -> c :*: b) -> c -> UArr a -> UArr bSource

O(n). mapAccumLU is an accumulating map from left to right. Unlike its List counterpart, it does not return the accumulator.

Generating UArrs

iterateU :: UA a => Int -> (a -> a) -> a -> UArr aSource

O(n). iterateU n f a constructs an array of size n by iteratively applying f to a.

replicateU :: UA e => Int -> e -> UArr eSource

O(n). replicateU n e yields an array containing n repetitions of e.

replicateEachU :: UA e => Int -> UArr Int -> UArr e -> UArr eSource

O(n). replicateEachU n r e yields an array such that each element in e is repeated as many times as the value contained at the corresponding index in r. For example:

replicateEachU 10 (toU [1..3]) (toU [3..5]) yields toU [3.0,4.0,4.0,5.0,5.0,5.0]

N.B: the n parameter specifies how many elements are allocated for the output array, but the function will happily overrun the allocated buffer for all sorts of interesting effects! The caller is expected to ensure that n <= sumU r.

Unfolding UArrs

unfoldU :: UA a => Int -> (b -> MaybeS (a :*: b)) -> b -> UArr aSource

O(n). unfoldU n f z builds an array of size n from a seed value z by iteratively applying f, stopping when n elements have been generated or f returns NothingS.

Subarrays

Breaking arrays

takeU :: UA e => Int -> UArr e -> UArr eSource

O(n). takeU yields the prefix of the given length of an array.

dropU :: UA e => Int -> UArr e -> UArr eSource

O(n). dropU yields the suffix obtained by dropping the given number of elements from an array.

splitAtU :: UA e => Int -> UArr e -> (UArr e, UArr e)Source

O(n). splitAtU splits an array into two subarrays at the given index.

takeWhileU :: UA e => (e -> Bool) -> UArr e -> UArr eSource

O(n). takeWhileU, applied to a predicate p and a UArr xs, returns the longest prefix (possibly empty) of xs of elements that satisfy p.

dropWhileU :: UA e => (e -> Bool) -> UArr e -> UArr eSource

O(n). dropWhileU p xs returns the suffix remaining after takeWhileU p xs.

Searching Arrays

Searching by equality

elemU :: (Eq e, UA e) => e -> UArr e -> BoolSource

O(n). elemU determines whether the given element is in an array.

notElemU :: (Eq e, UA e) => e -> UArr e -> BoolSource

O(n). Negation of elemU.

Searching with a predicate

filterU :: UA e => (e -> Bool) -> UArr e -> UArr eSource

O(n). filterU extracts all elements from an array that satisfy the given predicate.

findU :: UA a => (a -> Bool) -> UArr a -> Maybe aSource

O(n), fusion. The findU 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.

findIndexU :: UA a => (a -> Bool) -> UArr a -> Maybe IntSource

O(n), fusion. The findIndexU 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.

Indexing UArrs

indexU :: UA e => UArr e -> Int -> eSource

indexU extracts an element out of an immutable unboxed array.

TODO: use indexU, the non-streaming version.

lookupU :: (Eq a, UA a, UA b) => a -> UArr (a :*: b) -> Maybe bSource

O(n), fusion. lookupU key assocs looks up a key in an array of pairs treated as an association table.

Zipping and unzipping

zipU :: (UA a, UA b) => UArr a -> UArr b -> UArr (a :*: b)Source

O(1). Elementwise pairing of array elements.

N.B: The output will be as long as the first array (and will thus access past the end of the second array), unlike its List counterpart. This will not occur at the time zipU is called, but only after the resulting array is accessed.

zip3U :: (UA e1, UA e2, UA e3) => UArr e1 -> UArr e2 -> UArr e3 -> UArr ((e1 :*: e2) :*: e3)Source

O(1). zip3U takes three arrays and returns an array of triples.

unzipU :: (UA a, UA b) => UArr (a :*: b) -> UArr a :*: UArr bSource

O(1). Elementwise unpairing of array elements.

unzip3U :: (UA e1, UA e2, UA e3) => UArr ((e1 :*: e2) :*: e3) -> (UArr e1 :*: UArr e2) :*: UArr e3Source

O(1). unzip3U unpairs an array of strict triples into three arrays.

zipWithU :: (UA a, UA b, UA c) => (a -> b -> c) -> UArr a -> UArr b -> UArr cSource

O(n). zipWithU applies a function to corresponding elements of two arrays, yielding an array containing the results.

zipWith3U :: (UA a, UA b, UA c, UA d) => (a -> b -> c -> d) -> UArr a -> UArr b -> UArr c -> UArr dSource

O(n). zipWith3U applies a function to corresponding elements of three arrays, yielding an array with the results.

fstU :: (UA a, UA b) => UArr (a :*: b) -> UArr aSource

O(1). Yield the first components of an array of pairs.

sndU :: (UA a, UA b) => UArr (a :*: b) -> UArr bSource

O(1). Yield the second components of an array of pairs.

Enumerations

enumFromToU :: (UA a, Integral a) => a -> a -> UArr aSource

O(n). enumFromToU yields an enumerated array, analogous to enumFromTo, but only works on instances of Integral.

enumFromToFracU :: (UA a, RealFrac a) => a -> a -> UArr aSource

O(n). Like enumFromToU, but works on fractional numbers (still incrementing by 1 each time).

enumFromThenToU :: Int -> Int -> Int -> UArr IntSource

O(n). enumFromThenToU yields an enumerated array using a specific step value.

enumFromStepLenU :: Int -> Int -> Int -> UArr IntSource

O(n). enumFromStepLenU s d n yields an enumerated array of length n starting from s with an increment of d.

enumFromToEachU :: Int -> UArr (Int :*: Int) -> UArr IntSource

O(n). enumFromToEachU n u yields an array by taking each strict pair u and treating it as a range to generate successive values over. For example:

enumFromToEachU 7 (toU [3 :*: 6, 8 :*: 10]) yields toU [3,4,5,6,8,9,10]

N.B: This function will allocate n slots for the output array, and will happily overrun its allocated space if the u leads it to do so. The caller is expected to ensure that n = (sumU . mapU (\(x :*: y) - y - x + 1) $ u).

combineU :: UA a => UArr Bool -> UArr a -> UArr a -> UArr aSource

O(n). combineU f a1 a2 yields an array by picking elements from a1 if f is True at the given position, and picking elements from a2 otherwise. For example:

combineU (toU [True,True,False,True,False,False]) (toU [1..3]) (toU [4..6])

yields toU [1.0,2.0,4.0,3.0,5.0,6.0].

packU :: UA e => UArr e -> UArr Bool -> UArr eSource

O(n). packU extracts all elements from an array according to the provided flag array. For example:

packU (toU [1..5]) (toU [True,False,False,False,True])

yields toU [1.0,5.0].

indexedU :: UA e => UArr e -> UArr (Int :*: e)Source

O(n). indexedU associates each element of the array with its index.

repeatU :: UA e => Int -> UArr e -> UArr eSource

O(n). repeatU n u repeats an array u n times.

Operations on mutable arrays

newU :: UA e => Int -> (forall s. MUArr e s -> ST s ()) -> UArr eSource

O(n). newU constructs an immutable array of the given size by performing the provided initialization function on a mutable representation of the output array.

unsafeFreezeAllMU :: UA e => MUArr e s -> ST s (UArr e)Source

O(1). unsafeFreezeAllMU converts an entire mutable array into an immutable array, without copying. The mutable array must not be mutated after this.

permuteMU :: UA e => MUArr e s -> UArr e -> UArr Int -> ST s ()Source

O(n). permuteMU permutes a MUArr according to a UArr of permuted indices.

atomicUpdateMU :: UA e => MUArr e s -> UArr (Int :*: e) -> ST s ()Source

O(n). atomicUpdateMU arr upds replaces elements at specific indices of arr based on the contents of upds (where fstS indicates the index to replace, sndS the replacement value).

unstreamMU :: UA a => MUArr a s -> Stream a -> ST s IntSource

O(n). unstreamMU fills a mutable array from a stream from left to right and yields the number of elements written.

unsafeZipMU :: (UA a, UA b) => MUArr a s -> MUArr b s -> MUArr (a :*: b) sSource

Elementwise pairing of mutable arrays. This is an unsafe operation, as no copying is performed, so changes to the pair array will affect the original arrays, and vice versa.

unsafeUnzipMU :: (UA a, UA b) => MUArr (a :*: b) s -> MUArr a s :*: MUArr b sSource

Elementwise unpairing of mutable arrays. This is an unsafe operation, as no copying is performed, so changes to the unpaired arrays will affect the original, and vice versa.

Strict pairs and sums

data a :*: b Source

Strict pair

Constructors

!a :*: !b 

Instances

(Eq a, Eq b) => Eq (:*: a b) 
(Ord a, Ord b) => Ord (:*: a b) 
(Read a, Read b) => Read (:*: a b) 
(Show a, Show b) => Show (:*: a b) 
(UA a, UA b) => UA (:*: a b)

Array operations on the pair representation.

data EitherS a b Source

Strict sum

Constructors

LeftS !a 
RightS !b 

Injection and projection functions

fstS :: (a :*: b) -> aSource

Analog to fst in regular pairs.

sndS :: (a :*: b) -> bSource

Analog to snd in regular pairs.

pairS :: (a, b) -> a :*: bSource

Converts a pair to a strict pair.

unpairS :: (a :*: b) -> (a, b)Source

Converts a strict pair to a pair.

unsafe_pairS :: (a, b) -> a :*: bSource

unsafe_unpairS :: (a :*: b) -> (a, b)Source

Currying

curryS :: ((a :*: b) -> c) -> a -> b -> cSource

Analogous to curry in regular pairs.

uncurryS :: (a -> b -> c) -> (a :*: b) -> cSource

Analogous to uncurry in regular pairs.

Strict Maybe

data MaybeS a Source

Strict Maybe

Constructors

NothingS 
JustS !a 

Instances

Functor MaybeS 
Eq a => Eq (MaybeS a) 
Read a => Read (MaybeS a) 
Show a => Show (MaybeS a) 

maybeS :: b -> (a -> b) -> MaybeS a -> bSource

O(1). maybeS n f m is the catamorphism for MaybeS, returning n if m is NothingS, and applying f to the value wrapped in JustS otherwise.

fromMaybeS :: a -> MaybeS a -> aSource

O(1). fromMaybeS n m returns n if m is NothingS and the value wrapped in JustS otherwise.