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

Safe HaskellNone
LanguageHaskell98

Data.Repa.Array

Contents

Description

NOTE: This is an ALPHA version of Repa 4. The API is not yet complete with respect to Repa 3. Some important functions are still missing, and the docs may not be up-to-date.

A Repa array is a wrapper around an underlying container structure that holds the array elements.

In the type (Array l a), the l specifies the Layout of data, which includes the type of the underlying container, as well as how the elements should be arranged in that container. The a specifies the element type.

Material layouts

Material layouts hold real data and are defined in Data.Repa.Array.Material.

For performance reasons, random access indexing into these layouts is not bounds checked. However, all bulk operators like map and concat are guaranteed to be safe.

  • B -- Boxed vectors.
  • U -- Adaptive unboxed vectors.
  • F -- Foreign memory buffers.
  • N -- Nested arrays.

Delayed layouts

Delayed layouts represent the elements of an array by a function that computes those elements on demand.

  • D -- Functions from indices to elements.

Index-space layouts

Index-space produce the corresponding index for each element of the array, rather than real data. They can be used to define an array shape without needing to provide element data.

  • L -- Linear spaces.
  • RW -- RowWise spaces.

Meta layouts

Meta layouts combine existing layouts into new ones.

  • W -- Windowed arrays.
  • E -- Dense arrays.
  • T2 -- Tupled arrays.

Array fusion

Array fusion is achieved via the delayed (D) layout and the computeS function. For example:

> import Data.Repa.Array
> computeS U $ A.map (+ 1) $ A.map (* 2) $ fromList U [1 .. 100 :: Int]

Lets look at the result of the first map:

> :type A.map (* 2) $ fromList U [1 .. 100 :: Int]
A.map (* 2) $ fromList U [1 .. 100 :: Int] 
    :: Array (D U) Int

In the type Array (D U) Int, the outer D indicates that the array is represented as a function that computes each element on demand.

Applying a second map layers another element-producing function on top:

> :type A.map (+ 1) $ A.map (* 2) $ fromList U [1 .. 100 :: Int]
A.map (+ 1) $ A.map (* 2) $ fromList U [1 .. 100 :: Int]
    :: Array (D (D U)) Int

At runtime, indexing into an array of the above type involves calling the outer D-elayed function, which calls the inner D-elayed function, which retrieves source data from the inner U-nboxed array. Although this works, indexing into a deep stack of delayed arrays can be quite expensive.

To fully evaluate a delayed array, use the computeS function, which computes each element of the array sequentially. We pass computeS the name of the desired result layout, in this case we use U to indicate an unboxed array of values:

> :type computeS U $ A.map (+ 1) $ A.map (* 2) $ fromList U [1 .. 100 :: Int]
computeS U $ A.map (+ 1) $ A.map (* 2) $ fromList U [1 .. 100 :: Int]
     :: Array U Int

At runtime, each element of the result will be computed by first reading the source element, applying (*2) to it, then applying (+1) to it, then writing to the result array. Array "fusion" is achieved by the fact that result of applying (*2) to an element is used directly, without writing it to an intermediate buffer.

An added bonus is that during compilation, the GHC simplifier will inline the definitions of map and computeS, then eliminate the intermediate function calls. In the compiled code all intermediate values will be stored unboxed in registers, without any overhead due to boxing or laziness.

When used correctly, array fusion allows Repa programs to run as fast as equivalents in C or Fortran. However, without fusion the programs typically run 10-20x slower (so remember apply computeS to delayed arrays).

How to write fast code

  1. Add INLINE pragmas to all leaf-functions in your code, expecially ones that compute numeric results. Non-inlined lazy function calls can cost upwards of 50 cycles each, while each numeric operator only costs one (or less). Inlining leaf functions also ensures they are specialised at the appropriate numeric types.
  2. Add bang patterns to all function arguments, and all fields of your data types. In a high-performance Haskell program, the cost of lazy evaluation can easily dominate the run time if not handled correctly. You don't want to rely on the strictness analyser in numeric code because if it does not return a perfect result then the performance of your program will be awful. This is less of a problem for general Haskell code, and in a different context relying on strictness analysis is fine.
  3. Compile your program with ghc -O2 -fllvm -optlo-O3. The LLVM compiler produces better object code that GHC's internal native code generator.

Synopsis

Documentation

class Layout l => Bulk l a where Source

Class of array representations that we can read elements from in a random-access manner.

Associated Types

data Array l a Source

An Array supplies an element of type a to each position in the index space associated with layout l.

Methods

layout :: Array l a -> l Source

O(1). Get the layout of an array.

index :: Array l a -> Index l -> 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.

Instances

Bulk B a

Boxed arrays.

Storable a => Bulk F a

Foreign arrays.

Unbox a => Bulk U a

Unboxed arrays.

Bulk L Int

Linear arrays.

(BulkI l a, Windowable l a) => Bulk N (Array l a)

Nested arrays.

(Layout (RW sh), (~) * (Index (RW sh)) sh) => Bulk (RW sh) sh

Row-wise arrays.

Bulk l a => Bulk (W l) a

Windowed arrays.

Layout l => Bulk (D l) a

Delayed arrays.

((~) * (Index r) Int, Layout l, Bulk r a) => Bulk (E r l) a

Dense arrays.

(Layout l1, Layout l2, (~) * (Index l1) (Index l2)) => Bulk (D2 l1 l2) a

Delayed arrays.

(Bulk l1 a, Bulk l2 b, (~) * (Index l1) (Index l2)) => Bulk (T2 l1 l2) (a, b)

Tupled arrays.

type BulkI l a = (Bulk l a, Index l ~ Int) Source

Constraint synonym that requires an integer index space.

(!) :: Bulk l a => Array l a -> Index l -> a Source

O(1). Alias for index.

length :: Bulk l a => Array l a -> Int Source

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

Index arrays

Index arrays define an index space but do not contain concrete element values. Indexing into any point in the array produces the index at that point. Index arrays are typically used to provide an array shape to other array operators.

Linear spaces

data L Source

A linear layout with the elements indexed by integers.

  • Indexing is not bounds checked. Indexing outside the extent yields the corresponding index.

Constructors

Linear 

Fields

linearLength :: Int
 

Instances

Eq L 
Show L 
Layout L

Linear layout.

Bulk L Int

Linear arrays.

Eq (Name L) 
Show (Name L) 
data Name L = L 
type Index L = Int 
data Array L Int = LArray Int 

linear :: Int -> Array L Int Source

Construct a linear array that produces the corresponding index for every element.

> toList $ linear 10
   [0, 1, 2, 3, 4, 5, 6, 7, 8, 9]

RowWise spaces

data RW sh Source

A row-wise layout that maps higher rank indices to linear ones in a row-major order.

Indices are ordered so the inner-most coordinate varies most frequently:

> Prelude.map (fromIndex (RowWise (ish2 2 3))) [0..5]
   [(Z :. 0) :. 0, (Z :. 0) :. 1, (Z :. 0) :. 2, 
    (Z :. 1) :. 0, (Z :. 1) :. 1, (Z :. 1) :. 2]
  • Indexing is not bounds checked. Indexing outside the extent yields the corresponding index.

Constructors

RowWise 

Fields

rowWiseShape :: !sh
 

Instances

Eq (Name (RW sh)) => Eq (Name (RW ((:.) sh Int))) 
Eq (Name (RW Z)) 
Eq sh => Eq (RW sh) 
Show (Name (RW sh)) => Show (Name (RW ((:.) sh Int))) 
Show (Name (RW Z)) 
Show sh => Show (RW sh) 
Shape sh => Shape (RW sh) 
(Layout (RW sh), (~) * (Index (RW sh)) sh) => Layout (RW ((:.) sh Int)) 
Layout (RW Z) 
(Layout (RW sh), (~) * (Index (RW sh)) sh) => Bulk (RW sh) sh

Row-wise arrays.

data Name (RW ((:.) sh Int)) = RC (Name (RW sh)) 
data Name (RW Z) = RZ 
type Index (RW ((:.) sh Int)) = (:.) sh Int 
type Index (RW Z) = Z 
data Array (RW sh) sh = RArray sh 

rowWise :: sh -> Array (RW sh) sh Source

Construct a rowWise array that produces the corresponding index for every element.

> toList $ rowWise (ish2 3 2) 
   [(Z :. 0) :. 0, (Z :. 0) :. 1,
    (Z :. 1) :. 0, (Z :. 1) :. 1,
    (Z :. 2) :. 0, (Z :. 2) :. 1]

Meta arrays

Delayed arrays

data D l Source

Delayed arrays wrap functions from an index to element value. The index space is specified by an inner layout, l.

Every time you index into a delayed array the element at that position is recomputed.

Constructors

Delayed 

Fields

delayedLayout :: l
 

Instances

Eq (Name l) => Eq (Name (D l)) 
Eq l => Eq (D l) 
Show (Name l) => Show (Name (D l)) 
Show l => Show (D l) 
Layout l => Layout (D l)

Delayed arrays.

Layout l => Bulk (D l) a

Delayed arrays.

(Layout l1, Target l2 a) => Load (D l1) l2 a 
data Name (D l) = D (Name l) 
type Index (D l) = Index l 
data Array (D l) = ADelayed !l (Index l -> a) 

fromFunction :: l -> (Index l -> a) -> Array (D l) a Source

Wrap a function as a delayed array.

> toList $ fromFunction (Linear 10) (* 2)
    = [0, 2, 4, 6, 8, 10, 12, 14, 16, 18]

toFunction :: Bulk l a => Array (D l) a -> (l, Index l -> a) Source

Produce the extent of an array, and a function to retrieve an arbitrary element.

delay :: Bulk l a => Array l a -> Array (D l) a Source

Wrap an existing array in a delayed one.

data D2 l1 l2 Source

A delayed array formed from two source arrays. The source arrays can have different layouts but must have the same extent.

Constructors

Delayed2 

Fields

delayed2Layout1 :: l1
 
delayed2Layout2 :: l2
 

Instances

(Eq (Name l1), Eq (Name l2)) => Eq (Name (D2 l1 l2)) 
(Show (Name l1), Show (Name l2)) => Show (Name (D2 l1 l2)) 
(Eq l1, Eq l2) => Eq (D2 l1 l2) 
(Show l1, Show l2) => Show (D2 l1 l2) 
(Layout l1, Layout l2, (~) * (Index l1) (Index l2)) => Layout (D2 l1 l2)

Delayed arrays.

(Layout l1, Layout l2, (~) * (Index l1) (Index l2)) => Bulk (D2 l1 l2) a

Delayed arrays.

(Layout lSrc1, Layout lSrc2, Target lDst a, (~) * (Index lSrc1) (Index lSrc2)) => Load (D2 lSrc1 lSrc2) lDst a 
data Name (D2 l1 l2) = D2 (Name l1) (Name l2) 
type Index (D2 l1 l2) = Index l1 
data Array (D2 l1 l2) = ADelayed2 !l1 !l2 (Index l1 -> a) 

delay2 :: (Bulk l1 a, Bulk l2 b, Index l1 ~ Index l2) => Array l1 a -> Array l2 b -> Maybe (Array (D2 l1 l2) (a, b)) Source

Wrap two existing arrays in a delayed array.

Windowed arrays

data W l Source

Constructors

Window 

Fields

windowStart :: Index l
 
windowSize :: Index l
 
windowInner :: l
 

Instances

Eq (Name l) => Eq (Name (W l)) 
(Eq l, Eq (Index l)) => Eq (W l) 
Show (Name l) => Show (Name (W l)) 
(Show l, Show (Index l)) => Show (W l) 
Layout l => Layout (W l)

Windowed arrays.

Bulk l a => Bulk (W l) a

Windowed arrays.

Bulk l a => Windowable (W l) a

Windows are windowable.

data Name (W l) = W (Name l) 
type Index (W l) = Index l 
data Array (W l) = WArray !(Index l) !(Index l) !(Array l a) 

class Bulk l a => Windowable l a where Source

Class of array representations that can be windowed directly.

The underlying representation can encode the window, without needing to add a wrapper to the existing layout.

Methods

window :: Index l -> Index l -> Array l a -> Array l a Source

Instances

Windowable B a

Boxed windows.

Storable a => Windowable F a

Windowing Foreign arrays.

Unbox a => Windowable U a

Windowing Unboxed arrays.

(BulkI l a, Windowable l a) => Windowable N (Array l a)

Windowing Nested arrays.

Bulk l a => Windowable (W l) a

Windows are windowable.

(Windowable l1 a, Windowable l2 b, (~) * (Index l1) (Index l2)) => Windowable (T2 l1 l2) (a, b)

Tupled windows.

windowed :: Index l -> Index l -> Array l a -> Array (W l) a Source

Wrap a window around an exiting array.

entire :: Bulk l a => Array l a -> Array (W l) a Source

Wrap a window around an existing array that encompases the entire array.

Tupled arrays

data T2 l1 l2 Source

Tupled arrays where the components are unpacked and can have separate representations.

Constructors

Tup2 !l1 !l2 

Instances

(Eq (Name l1), Eq (Name l2)) => Eq (Name (T2 l1 l2)) 
(Show (Name l1), Show (Name l2)) => Show (Name (T2 l1 l2)) 
(Eq l1, Eq l2) => Eq (T2 l1 l2) 
(Show (Array l1 a), Show (Array l2 b)) => Show (Array (T2 l1 l2) (a, b)) 
(Show l1, Show l2) => Show (T2 l1 l2) 
((~) * (Index l1) (Index l2), Layout l1, Layout l2) => Layout (T2 l1 l2) 
(Bulk l1 a, Bulk l2 b, (~) * (Index l1) (Index l2)) => Bulk (T2 l1 l2) (a, b)

Tupled arrays.

(Windowable l1 a, Windowable l2 b, (~) * (Index l1) (Index l2)) => Windowable (T2 l1 l2) (a, b)

Tupled windows.

(Target l1 a, Target l2 b, (~) * (Index l1) (Index l2)) => Target (T2 l1 l2) (a, b)

Tupled buffers.

(Unpack (Buffer s r1 a) t1, Unpack (Buffer s r2 b) t2) => Unpack (Buffer s (T2 r1 r2) (a, b)) (t1, t2) 
data Buffer s (T2 l1 l2) (a, b) = T2Buffer !(Buffer s l1 a) !(Buffer s l2 b) 
data Name (T2 l1 l2) = T2 !(Name l1) !(Name l2) 
type Index (T2 l1 l2) = Index l1 
data Array (T2 l1 l2) (a, b) = T2Array !(Array l1 a) !(Array l2 b) 

tup2 :: (Bulk l1 a, Bulk l2 b, Index l1 ~ Index l2) => Array l1 a -> Array l2 b -> Array (T2 l1 l2) (a, b) Source

Tuple two arrays into an array of pairs.

The two argument arrays must have the same index type, but can have different extents. The extent of the result is the intersection of the extents of the two argument arrays.

untup2 :: Array (T2 l1 l2) (a, b) -> (Array l1 a, Array l2 b) Source

Untuple an array of tuples in to a tuple of arrays.

  • The two returned components may have different extents, though they are guaranteed to be at least as big as the argument array. This is the key property that makes untup2 different from unzip.

Material arrays

Material arrays are represented as concrete data in memory and are defined in Data.Repa.Array.Material. Indexing into these arrays is not bounds checked, so you may want to use them in conjunction with a Checked layout.

type Material l a = (Bulk l a, Windowable l a, Target l a) Source

Classes supported by all material representations.

We can index them in a random-access manner, window them in constant time, and use them as targets for a computation.

In particular, delayed arrays are not material as we cannot use them as targets for a computation.

Dense arrays

data E r l Source

The Dense layout maps a higher-ranked index space to some underlying linear index space.

For example, we can create a dense 2D row-wise array where the elements are stored in a flat unboxed vector:

> import Data.Repa.Array.Material
> let Just arr  = fromListInto (matrix U 10 10) [1000..1099 :: Float]

> :type arr
arr :: Array (E U (RW DIM2) Float

> arr ! (Z :. 5 :. 4)
> 1054.0

Constructors

Dense r l 

Instances

(Eq (Name r), Eq (Name l)) => Eq (Name (E r l)) 
(Show (Name r), Show (Name l)) => Show (Name (E r l)) 
(Eq r, Eq l) => Eq (E r l) 
(Show r, Show l) => Show (E r l) 
((~) * (Index r) Int, Layout r, Layout l) => Layout (E r l)

Dense arrays.

((~) * (Index r) Int, Layout l, Bulk r a) => Bulk (E r l) a

Dense arrays.

(Layout l, (~) * (Index r) Int, Target r a) => Target (E r l) a

Dense buffers.

Unpack (Buffer s r a) tBuf => Unpack (Buffer s (E r l) a) (l, tBuf) 
data Buffer s (E r l) a = EBuffer !l !(Buffer s r a) 
data Name (E r l) = E (Name r) (Name l) 
type Index (E r l) = Index l 
data Array (E r l) = Array l (Array r a) 

vector :: LayoutI l => Name l -> Int -> E l DIM1 Source

Yield a layout for a dense vector of the given length.

The first argument is the name of the underlying linear layout which stores the elements.

matrix :: LayoutI l => Name l -> Int -> Int -> E l DIM2 Source

Yield a layout for a matrix with the given number of rows and columns.

cube :: LayoutI l => Name l -> Int -> Int -> Int -> E l DIM3 Source

Yield a layout for a cube with the given number of planes, rows, and columns.

Conversion

fromList :: TargetI l a => Name l -> [a] -> Array l a Source

O(length src). Construct a linear array from a list of elements.

fromListInto :: Target l a => l -> [a] -> Maybe (Array l a) Source

O(length src). Construct an array from a list of elements, and give it the provided layout.

The length of the provided shape must match the length of the list, else Nothing.

toList :: Bulk l a => Array l a -> [a] Source

Convert an array to a list.

Computation

class (Bulk l1 a, Target l2 a) => Load l1 l2 a Source

Compute all elements defined by a delayed array and write them to a manifest target representation.

The instances of this class require that the source array has a delayed representation. If you want to use a pre-existing manifest array as the source then delay it first.

Minimal complete definition

loadS, loadP

Instances

(Layout l1, Target l2 a) => Load (D l1) l2 a 
(Layout lSrc1, Layout lSrc2, Target lDst a, (~) * (Index lSrc1) (Index lSrc2)) => Load (D2 lSrc1 lSrc2) lDst a 

class Layout l => Target l a Source

Class of manifest array representations that can be constructed in a random-access manner.

Instances

Target B a

Boxed buffers.

Storable a => Target F a

Foreign buffers

Unbox a => Target U a

Unboxed buffers.

(Layout l, (~) * (Index r) Int, Target r a) => Target (E r l) a

Dense buffers.

(Target l1 a, Target l2 b, (~) * (Index l1) (Index l2)) => Target (T2 l1 l2) (a, b)

Tupled buffers.

computeS :: (Load lSrc lDst a, Index lSrc ~ Index lDst) => Name lDst -> Array lSrc a -> Array lDst a Source

Sequential computation of delayed array elements.

Elements of the source array are computed sequentially and written to a new array of the specified layout.

computeIntoS :: Load lSrc lDst a => lDst -> Array lSrc a -> Maybe (Array lDst a) Source

Like computeS but use the provided desination layout.

The size of the destination layout must match the size of the source array, else Nothing.

Operators

Index space

Index space transforms view the elements of an array in a different order, but do not compute new elements. They are all constant time operations as the location of the required element in the source array is computed on demand.

reverse :: BulkI l a => Array l a -> Array (D l) a Source

O(1). View the elements of a vector in reverse order.

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

Mapping

map :: Bulk l a => (a -> b) -> Array l a -> Array (D l) b Source

Apply a worker function to each element of an array, yielding a new array with the same extent.

The resulting array is delayed, meaning every time you index into it the element at that index is recomputed.

map2 :: (Bulk l1 a, Bulk l2 b, Index l1 ~ Index l2) => (a -> b -> c) -> Array l1 a -> Array l2 b -> Maybe (Array (D2 l1 l2) c) Source

Combine two arrays element-wise using the given worker function.

The two source arrays must have the same extent, else Nothing.

mapS Source

Arguments

:: (Bulk lSrc a, Target lDst b, Index lSrc ~ Index lDst) 
=> Name lDst

Name of destination layout.

-> (a -> b)

Worker function.

-> Array lSrc a

Source array.

-> Array lDst b 

Like map, but immediately computeS the result.

map2S Source

Arguments

:: (Bulk lSrc1 a, Bulk lSrc2 b, Target lDst c, Index lSrc1 ~ Index lDst, Index lSrc2 ~ Index lDst) 
=> Name lDst

Name of destination layout.

-> (a -> b -> c)

Worker function.

-> Array lSrc1 a

Source array.

-> Array lSrc2 b

Source array

-> Maybe (Array lDst c) 

Like map2, but immediately computeS the result.

Filtering

filter :: (BulkI lSrc a, TargetI lDst a) => Name lDst -> (a -> Bool) -> Array lSrc a -> Array lDst a Source

Keep the elements of an array that match the given predicate.

Searching

findIndex :: BulkI l a => (a -> Bool) -> Array l 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.

Sloshing

Sloshing operators copy array elements into a different arrangement, but do not create new element values.

concat Source

Arguments

:: ConcatDict lOut lIn tIn lDst a 
=> Name lDst

Layout for destination.

-> Array lOut (Array lIn a)

Arrays to concatenate.

-> Array lDst a 

O(len result) Concatenate nested arrays.

> import Data.Repa.Array.Material
> let arrs = fromList B [fromList U [1, 2, 3], fromList U [5, 6, 7 :: Int]]
> toList $ concat U arrs
[1,2,3,5,6,7]

concatWith Source

Arguments

:: (ConcatDict lOut lIn tIn lDst a, BulkI lSep a) 
=> Name lDst

Result representation.

-> Array lSep a

Separator array.

-> Array lOut (Array lIn a)

Arrays to concatenate.

-> Array lDst a 

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

> import Data.Repa.Array.Material
> let sep  = fromList U [0, 0, 0]
> let arrs = fromList B [fromList U [1, 2, 3], fromList U [5, 6, 7 :: Int]]
> toList $ concatWith U sep arrs
[1,2,3,0,0,0,5,6,7,0,0,0]

unlines Source

Arguments

:: ConcatDict lOut lIn tIn lDst Char 
=> Name lDst

Result representation.

-> Array lOut (Array lIn Char)

Arrays to concatenate.

-> Array lDst Char 

Perform a concatWith, adding a newline character to the end of each inner array.

intercalate Source

Arguments

:: (ConcatDict lOut lIn tIn lDst a, BulkI lSep a) 
=> Name lDst

Result representation.

-> Array lSep a

Separator array.

-> Array lOut (Array lIn a)

Arrays to concatenate.

-> Array lDst a 

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

> import Data.Repa.Array.Material
> let sep  = fromList U [0, 0, 0]
> let arrs = fromList B [fromList U [1, 2, 3], fromList U [5, 6, 7 :: Int]]
> toList $ intercalate U sep arrs
[1,2,3,0,0,0,5,6,7]

type ConcatDict lOut lIn tIn lDst a = (BulkI lOut (Array lIn a), BulkI lIn a, TargetI lDst a, Unpack (Array lIn a) tIn) Source

Dictionaries needed to perform a concatenation.

partition Source

Arguments

:: (BulkI lSrc (Int, a), Target lDst a, Index lDst ~ Int, Elt a) 
=> Name lDst

Name of destination layout.

-> Int

Total number of segments.

-> Array lSrc (Int, a)

Segment numbers and values.

-> Array N (Array lDst a)

Result array

Take a desired number of segments, and array of key value pairs where the key is the segment number. Partition the values into the stated number of segments, discarding values where the key falls outside the given range.

  • This function operates by first allocating a buffer of size (segs * len src) and filling it with a default value. Both the worst case runtime and memory use will be poor for a large number of destination segments.

TODO: we need the pre-init because otherwise unused values in the elems array are undefined. We could avoid this by copying out the used elements after the partition loop finishes. Use a segmented extract function. This would also remove the dependency on the Elt class.

partitionBy Source

Arguments

:: (BulkI lSrc a, Target lDst a, Index lDst ~ Int, Elt a) 
=> Name lDst

Name of destination layout.

-> Int

Total number of Segments.

-> (a -> Int)

Get the segment number for this element.

-> Array lSrc a

Source values.

-> Array N (Array lDst a) 

Like partition but use the provided function to compute the segment number for each element.

partitionByIx Source

Arguments

:: (BulkI lSrc a, Target lDst a, Index lDst ~ Int, Elt a) 
=> Name lDst

Name of destination layout.

-> Int

Total number of Segments.

-> (Int -> a -> Int)

Get the segment number for this element.

-> Array lSrc a

Source values.

-> Array N (Array lDst a) 

Like partition but use the provided function to compute the segment number for each element. The function is given the index of the each element, along with the element itself.

Grouping

groups Source

Arguments

:: (GroupsDict lElt lGrp tGrp lLen tLen n, Eq n) 
=> Name lGrp

Layout for group names.

-> Name lLen

Layout gor group lengths.

-> Array lElt n

Input elements.

-> (Array (T2 lGrp lLen) (n, Int), Maybe (n, Int)) 

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

> import Data.Repa.Array.Material
> import Data.Repa.Nice
> nice $ groups U U (fromList U "waaabllle")
([(w,1),(a,3),(b,1),(l,3)],Just (e,1))

groupsWith Source

Arguments

:: GroupsDict lElt lGrp tGrp lLen tLen n 
=> Name lGrp

Layout for group names.

-> Name lLen

Layour for group lengths.

-> (n -> n -> Bool)

Comparison function.

-> Maybe (n, Int)

Starting element and count.

-> Array lElt n

Input elements.

-> (Array (T2 lGrp lLen) (n, Int), Maybe (n, Int)) 

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.

> import Data.Repa.Array.Material
> import Data.Repa.Nice
> nice $ groupsWith U U (==) (Just (w, 5)) (fromList U "waaabllle")
([(w,6),(a,3),(b,1),(l,3)],Just (e,1))

type GroupsDict lElt lGrp tGrp lLen tLen n = (Bulk lElt n, Target lGrp n, Target lLen Int, Index lGrp ~ Index lLen, Unpack (IOBuffer lLen Int) tLen, Unpack (IOBuffer lGrp n) tGrp) Source

Dictionaries need to perform a grouping.

Folding

foldl :: (Bulk l b, Index l ~ Int) => (a -> b -> a) -> a -> Array l b -> a Source

Left fold of all elements in an array, sequentially.

folds Source

Arguments

:: FoldsDict lSeg lElt lGrp tGrp lRes tRes n a b 
=> Name lGrp

Layout for group names.

-> Name lRes

Layout for fold results.

-> (a -> b -> b)

Worker function.

-> b

Initial state when folding segments.

-> Array lSeg (n, Int)

Segment names and lengths.

-> Array lElt a

Elements.

-> (Array (T2 lGrp lRes) (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.
> import Data.Repa.Array.Material
> import Data.Repa.Nice
> let segs  = fromList B [("red", 3), ("green", 5)]
> let vals  = fromList U [0..100 :: Int]
> nice $ fst $ folds B U (+) 0 segs vals
[("red",3),("green",25)]

foldsWith Source

Arguments

:: FoldsDict lSeg lElt lGrp tGrp lRes tRes n a b 
=> Name lGrp

Layout for group names.

-> Name lRes

Layout for fold results.

-> (a -> b -> b)

Worker function.

-> b

Initial state when folding segments.

-> Maybe (n, Int, b)

Name, length and initial state for first segment.

-> Array lSeg (n, Int)

Segment names and lengths.

-> Array lElt a

Elements.

-> (Array (T2 lGrp lRes) (n, b), Folds Int Int n a b) 

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

> import Data.Repa.Array.Material
> import Data.Repa.Nice
> let state = Just ("white", 4, 100)
> let segs  = fromList B [("red", 3), ("green", 5)]
> let vals  = fromList U [0..100 :: Int]
> nice $ fst $ foldsWith B U (+) 0  state segs vals
[("white",106),("red",15),("green",45)]

data Folds sLens sVals n a b :: * -> * -> * -> * -> * -> *

Return state of a folds operation.

Constructors

Folds 

Fields

_stateLens :: !sLens

State of lengths chain.

_stateVals :: !sVals

State of values chain.

_nameSeg :: !(Option n)

If we're currently in a segment, then hold its name,

_lenSeg :: !Int

Length of current segment.

_valSeg :: !b

Accumulated value of current segment.

Instances

(Show sLens, Show sVals, Show n, Show b) => Show (Folds sLens sVals n a b) 

type FoldsDict lSeg lElt lGrp tGrp lRes tRes n a b = (Bulk lSeg (n, Int), Bulk lElt a, Target lGrp n, Target lRes b, Index lGrp ~ Index lRes, Unpack (IOBuffer lGrp n) tGrp, Unpack (IOBuffer lRes b) tRes) Source

Dictionaries need to perform a segmented fold.