repa-array-4.1.0.1: Bulk array representations and operators.

Safe HaskellNone
LanguageHaskell98

Data.Repa.Array.Auto

Contents

Synopsis

Documentation

type Array a = Array A a Source

Arrays of elements that are automatically layed out into some efficient runtime representation.

The implementation uses type families to chose unboxed representations for all elements that can be unboxed. In particular: arrays of unboxed tuples are represented as tuples of unboxed arrays, and nested arrays are represented using a segment descriptor and a single single flat vector containing all the elements.

type Elem a = (Bulk A a, Windowable A a) Source

Class of elements that can be automatically organised into arrays.

type Build a t = (Bulk A a, Target A a, Unpack (Buffer A a) t) Source

Class of elements where arrays of those elements can be constructed in arbitrary order.

Basics

index :: Elem a => Array a -> Int -> a Source

O(1). Get an element from an array.

If the provided index is outside the extent of the array then the result depends on the layout.

(!) :: Elem a => Array a -> Int -> a Source

O(1). Alias for index

length :: Elem a => Array a -> Int Source

O(1). Get the number of elements in an array.

head :: Elem a => Array a -> Maybe a Source

O(1). Take the head of an array, or Nothing if it's empty.

init :: Elem a => Array a -> Maybe (Array a) Source

O(1). Take the initial elements of an array, or Nothing if it's empty.

tail :: Elem a => Array a -> Maybe (Array a) Source

O(1). Take the tail of an array, or Nothing if it's empty.

Conversion

fromList :: Build a at => [a] -> Array a Source

Convert a list to an array.

fromLists :: Build a at => [[a]] -> Array (Array a) Source

Convert a nested list to an array.

fromListss :: Build a at => [[[a]]] -> Array (Array (Array a)) Source

Convert a triply nested list to a triply nested array.

toList :: Elem a => Array a -> [a] Source

Convert an array to a list.

toLists :: (Elem a, Elem (Array a)) => Array (Array a) -> [[a]] Source

Convert a nested array to some lists.

toListss :: (Elem a, Elem (Array a), Elem (Array (Array a))) => Array (Array (Array a)) -> [[[a]]] Source

Convert a triply nested array to a triply nested list.

Operators

Mapping

map :: (Elem a, Build b bt) => (a -> b) -> Array a -> Array b Source

Apply a function to all the elements of a list.

map2 :: (Elem a, Elem b, Build c ct) => (a -> b -> c) -> Array a -> Array b -> Maybe (Array c) Source

Combine two arrays of the same length element-wise.

If the arrays don't have the same length then Nothing.

mapElems :: (Array a -> Array b) -> Array (Array a) -> Array (Array b) Source

Apply a function to all the elements of a doubly nested array, preserving the nesting structure.

  • This function has a non-standard time complexity. As nested arrays use a segment descriptor based representation, detatching and reattaching the nesting structure is a constant time operation. However, the array passed to the worker function will also contain any elements in the array representation that are not reachable from the segment descriptor. This matters if the source array was produced by a function that filters the segments directly, like slices.

Folding

foldl :: Elem b => (a -> b -> a) -> a -> Array b -> a Source

Left fold of all elements in an array.

sum :: (Elem a, Num a) => Array a -> a Source

Yield the sum of the elements of an array.

prod :: (Elem a, Num a) => Array a -> a Source

Yield the product of the elements of an array.

mean :: (Elem a, Fractional a) => Array a -> a Source

Yield the mean value of the elements of an array.

std :: (Elem a, Floating a) => Array a -> a Source

Yield the standard deviation of the elements of an array

correlate :: (Elem a, Floating a) => Array a -> Array a -> a Source

Compute the Pearson correlation of two arrays.

If the arrays differ in length then only the common prefix is correlated.

folds Source

Arguments

:: (Elem a, Build n nt, Build b bt) 
=> (a -> b -> b)

Worker function.

-> b

Initial state when folding segments.

-> Array (n, Int)

Segment names and lengths.

-> Array a

Elements.

-> (Array (n, b), Folds Int Int n a b) 

Segmented fold over vectors of segment lengths and input values.

  • The total lengths of all segments need not match the length of the input elements vector. The returned Folds state can be inspected to determine whether all segments were completely folded, or the vector of segment lengths or elements was too short relative to the other.

foldsWith Source

Arguments

:: (Elem a, Build n nt, Build b bt) 
=> (a -> b -> b)

Worker function.

-> b

Initial state when folding segments.

-> Maybe (n, Int, b)

Name, length and initial state for first segment.

-> Array (n, Int)

Segment names and lengths.

-> Array a

Elements.

-> (Array (n, b), Folds Int Int n a b) 

Like folds, but take an initial state for the first segment.

Filtering

filter :: Build a at => (a -> Bool) -> Array a -> Array a Source

O(len src) Keep the elements of an array that match the given predicate.

slices Source

Arguments

:: Array Int

Segment starting positions.

-> Array Int

Segment lengths.

-> Array a

Array elements.

-> Array (Array a) 

O(1). Produce a nested array by taking slices from some array of elements.

  • This is a constant time operation, as the representation for nested vectors just wraps the starts, lengths and elements vectors.

trims :: Elem a => (a -> Bool) -> Array (Array a) -> Array (Array a) Source

For each segment of a nested vector, trim elements off the start and end of the segment that match the given predicate.

trimEnds :: Elem a => (a -> Bool) -> Array (Array a) -> Array (Array a) Source

For each segment of a nested array, trim elements off the end of the segment that match the given predicate.

trimStarts :: Elem a => (a -> Bool) -> Array (Array a) -> Array (Array a) Source

For each segment of a nested array, trim elements off the start of the segment that match the given predicate.

Zipping

zip :: (Elem a, Elem b) => Array a -> Array b -> Array (a, b) Source

O(1). Pack a pair of arrays to an array of pairs.

unzip :: (Elem a, Elem b) => Array (a, b) -> (Array a, Array b) Source

O(1). Unpack an array of pairs to a pair of arrays.

Sloshing

reverse :: Build a at => Array a -> Array a Source

O(n). Reverse the elements of a list.

> toList $ reverse $ fromList [0 .. 10 :: Int]
[10,9,8,7,6,5,4,3,2,1,0]

concat Source

Arguments

:: (Elem a, Build a at, Unpack (Array a) aat) 
=> Array (Array a)

Arrays to concatenate.

-> Array a 

Concatenate nested arrays.

concats :: Array (Array (Array a)) -> Array (Array a) Source

O(len result) Concatenate the outer two layers of a triply nested array. (Segmented concatenation).

  • The operation is performed entirely on the segment descriptors of the array, and does not require the inner array elements to be copied.
  • This version is faster than plain concat on triply nested arrays.

concatWith Source

Arguments

:: (Elem a, Build a at, Unpack (Array a) aat) 
=> Array a

Separator array.

-> Array (Array a)

Arrays to concatenate.

-> Array a 

O(len result) Concatenate the elements of some nested vector, inserting a copy of the provided separator array between each element.

unlines :: Unpack (Array Char) aat => Array (Array Char) -> Array Char Source

O(len result) Perform a concatWith, adding a newline character to the end of each inner array.

intercalate Source

Arguments

:: (Elem a, Build a at, Unpack (Array a) aat) 
=> Array a

Separator array.

-> Array (Array a)

Arrays to concatenate.

-> Array a 

O(len result) Insert a copy of the separator array between the elements of the second and concatenate the result.

ragspose3 :: Array (Array (Array a)) -> Array (Array (Array a)) Source

Ragged transpose of a triply nested array.

  • This operation is performed entirely on the segment descriptors of the nested arrays, and does not require the inner array elements to be copied.

Slicing

slice :: Elem a => Int -> Int -> Array a -> Maybe (Array a) Source

Take a slice out of an array, given a starting position and length.

Inserting

insert :: Build a at => (Int -> Maybe a) -> Array a -> Array a Source

Insert elements produced by the given function in to an array.

Searching

findIndex :: Elem a => (a -> Bool) -> Array a -> Maybe Int Source

O(len src) Yield Just the index of the first element matching the predicate or Nothing if no such element exists.

Merging

merge Source

Arguments

:: (Ord k, Elem (k, a), Elem (k, b), Build (k, c) ct) 
=> (k -> a -> b -> c)

Combine two values with the same key.

-> (k -> a -> c)

Handle a left value without a right value.

-> (k -> b -> c)

Handle a right value without a left value.

-> Array (k, a)

Array of keys and left values.

-> Array (k, b)

Array of keys and right values.

-> Array (k, c)

Array of keys and results.

Merge two sorted key-value streams.

mergeMaybe Source

Arguments

:: (Ord k, Elem (k, a), Elem (k, b), Build (k, c) ct) 
=> (k -> a -> b -> Maybe c)

Combine two values with the same key.

-> (k -> a -> Maybe c)

Handle a left value without a right value.

-> (k -> b -> Maybe c)

Handle a right value without a left value.

-> Array (k, a)

Array of keys and left values.

-> Array (k, b)

Array of keys and right values.

-> Array (k, c)

Array of keys and results.

Like merge, but only produce the elements where the worker functions return Just.

Compacting

compact :: (Elem a, Build b bt) => (s -> a -> (Maybe b, s)) -> s -> Array a -> Array b Source

Combination of fold and filter.

We walk over the stream front to back, maintaining an accumulator. At each point we can chose to emit an element (or not)

compactIn :: Build a at => (a -> a -> (Maybe a, a)) -> Array a -> Array a Source

Like compact but use the first value of the stream as the initial state, and add the final state to the end of the output.

Grouping

groups Source

Arguments

:: (Eq a, Build a at) 
=> Array a

Input elements.

-> (Array (a, Int), Maybe (a, Int))

Completed and final segment lengths.

From a stream of values which has consecutive runs of idential values, produce a stream of the lengths of these runs.

groupsWith Source

Arguments

:: Build a at 
=> (a -> a -> Bool)

Comparison function.

-> Maybe (a, Int)

Starting element and count.

-> Array a

Input elements.

-> (Array (a, Int), Maybe (a, Int))

Completed and final segment lengths.

Like groups, but use the given function to determine whether two consecutive elements should be in the same group. Also take an initial starting group and count.

Splitting

segment Source

Arguments

:: (Elem a, Unbox a) 
=> (a -> Bool)

Detect the start of a segment.

-> (a -> Bool)

Detect the end of a segment.

-> Array a

Array to segment.

-> Array (Array a) 

O(len src). Given predicates which detect the start and end of a segment, split an vector into the indicated segments.

segmentOn Source

Arguments

:: (Elem a, Eq a, Unbox a) 
=> (a -> Bool)

Detect the end of a segment.

-> Array a

Array to segment.

-> Array (Array a) 

O(len src). Given a terminating value, split an vector into segments.

The result segments do not include the terminator.

dice Source

Arguments

:: (Elem a, Unbox a) 
=> (a -> Bool)

Detect the start of an inner segment.

-> (a -> Bool)

Detect the end of an inner segment.

-> (a -> Bool)

Detect the start of an outer segment.

-> (a -> Bool)

Detect the end of an outer segment.

-> Array a

Array to dice.

-> Array (Array (Array a)) 

O(len src). Like segment, but cut the source array twice.

diceSep Source

Arguments

:: (Elem a, Eq a, Unbox a) 
=> a

Terminating element for inner segments.

-> a

Terminating element for outer segments.

-> Array a

Vector to dice.

-> Array (Array (Array a)) 

O(len src). Given field and row terminating values, split an array into rows and fields.