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

Safe HaskellNone
LanguageHaskell98

Data.Repa.Array.Meta

Contents

Description

Meta arrays either generate elements on the fly, or wrap an inner array to provide an extra features.

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.

Combining layouts

Combining 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).

Synopsis

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

Instances

Eq (Name l) => Eq (Name (D l)) Source # 

Methods

(==) :: Name (D l) -> Name (D l) -> Bool #

(/=) :: Name (D l) -> Name (D l) -> Bool #

Eq l => Eq (D l) Source # 

Methods

(==) :: D l -> D l -> Bool #

(/=) :: D l -> D l -> Bool #

Show (Name l) => Show (Name (D l)) Source # 

Methods

showsPrec :: Int -> Name (D l) -> ShowS #

show :: Name (D l) -> String #

showList :: [Name (D l)] -> ShowS #

Show l => Show (D l) Source # 

Methods

showsPrec :: Int -> D l -> ShowS #

show :: D l -> String #

showList :: [D l] -> ShowS #

Layout l => Layout (D l) Source #

Delayed arrays.

Associated Types

data Name (D l) :: * Source #

type Index (D l) :: * Source #

Methods

name :: Name (D l) Source #

create :: Name (D l) -> Index (D l) -> D l Source #

extent :: D l -> Index (D l) Source #

toIndex :: D l -> Index (D l) -> Int Source #

fromIndex :: D l -> Int -> Index (D l) Source #

Layout l => Bulk (D l) a Source #

Delayed arrays.

Associated Types

data Array (D l) a :: * Source #

Methods

layout :: Array (D l) a -> D l Source #

index :: Array (D l) a -> Index (D l) -> a Source #

(Layout l1, Target l2 a) => Load (D l1) l2 a Source # 

Methods

loadS :: Array (D l1) a -> Buffer l2 a -> IO () Source #

loadP :: Gang -> Array (D l1) a -> Buffer l2 a -> IO () Source #

data Name (D l) Source # 
data Name (D l) = D (Name l)
type Index (D l) Source # 
type Index (D l) = Index l
data Array (D l) Source # 
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 :: 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.

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.

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

Instances

(Eq (Name l1), Eq (Name l2)) => Eq (Name (D2 l1 l2)) Source # 

Methods

(==) :: Name (D2 l1 l2) -> Name (D2 l1 l2) -> Bool #

(/=) :: Name (D2 l1 l2) -> Name (D2 l1 l2) -> Bool #

(Show (Name l1), Show (Name l2)) => Show (Name (D2 l1 l2)) Source # 

Methods

showsPrec :: Int -> Name (D2 l1 l2) -> ShowS #

show :: Name (D2 l1 l2) -> String #

showList :: [Name (D2 l1 l2)] -> ShowS #

(Eq l1, Eq l2) => Eq (D2 l1 l2) Source # 

Methods

(==) :: D2 l1 l2 -> D2 l1 l2 -> Bool #

(/=) :: D2 l1 l2 -> D2 l1 l2 -> Bool #

(Show l1, Show l2) => Show (D2 l1 l2) Source # 

Methods

showsPrec :: Int -> D2 l1 l2 -> ShowS #

show :: D2 l1 l2 -> String #

showList :: [D2 l1 l2] -> ShowS #

(Layout l1, Layout l2, (~) * (Index l1) (Index l2)) => Layout (D2 l1 l2) Source #

Delayed arrays.

Associated Types

data Name (D2 l1 l2) :: * Source #

type Index (D2 l1 l2) :: * Source #

Methods

name :: Name (D2 l1 l2) Source #

create :: Name (D2 l1 l2) -> Index (D2 l1 l2) -> D2 l1 l2 Source #

extent :: D2 l1 l2 -> Index (D2 l1 l2) Source #

toIndex :: D2 l1 l2 -> Index (D2 l1 l2) -> Int Source #

fromIndex :: D2 l1 l2 -> Int -> Index (D2 l1 l2) Source #

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

Delayed arrays.

Associated Types

data Array (D2 l1 l2) a :: * Source #

Methods

layout :: Array (D2 l1 l2) a -> D2 l1 l2 Source #

index :: Array (D2 l1 l2) a -> Index (D2 l1 l2) -> a Source #

(Layout lSrc1, Layout lSrc2, Target lDst a, (~) * (Index lSrc1) (Index lSrc2)) => Load (D2 lSrc1 lSrc2) lDst a Source # 

Methods

loadS :: Array (D2 lSrc1 lSrc2) a -> Buffer lDst a -> IO () Source #

loadP :: Gang -> Array (D2 lSrc1 lSrc2) a -> Buffer lDst a -> IO () Source #

data Name (D2 l1 l2) Source # 
data Name (D2 l1 l2) = D2 (Name l1) (Name l2)
type Index (D2 l1 l2) Source # 
type Index (D2 l1 l2) = Index l1
data Array (D2 l1 l2) Source # 
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.

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.

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

Instances

Eq L Source # 

Methods

(==) :: L -> L -> Bool #

(/=) :: L -> L -> Bool #

Show L Source # 

Methods

showsPrec :: Int -> L -> ShowS #

show :: L -> String #

showList :: [L] -> ShowS #

Layout L Source #

Linear layout.

Associated Types

data Name L :: * Source #

type Index L :: * Source #

Bulk L Int Source #

Linear arrays.

Associated Types

data Array L Int :: * Source #

Methods

layout :: Array L Int -> L Source #

index :: Array L Int -> Index L -> Int Source #

Eq (Name L) Source # 

Methods

(==) :: Name L -> Name L -> Bool #

(/=) :: Name L -> Name L -> Bool #

Show (Name L) Source # 

Methods

showsPrec :: Int -> Name L -> ShowS #

show :: Name L -> String #

showList :: [Name L] -> ShowS #

data Name L Source # 
data Name L = L
type Index L Source # 
type Index L = Int
data Array L Int Source # 

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

Instances

Eq (Name (RW sh)) => Eq (Name (RW ((:.) sh Int))) Source # 

Methods

(==) :: Name (RW (sh :. Int)) -> Name (RW (sh :. Int)) -> Bool #

(/=) :: Name (RW (sh :. Int)) -> Name (RW (sh :. Int)) -> Bool #

Eq (Name (RW Z)) Source # 

Methods

(==) :: Name (RW Z) -> Name (RW Z) -> Bool #

(/=) :: Name (RW Z) -> Name (RW Z) -> Bool #

Eq sh => Eq (RW sh) Source # 

Methods

(==) :: RW sh -> RW sh -> Bool #

(/=) :: RW sh -> RW sh -> Bool #

Show (Name (RW sh)) => Show (Name (RW ((:.) sh Int))) Source # 

Methods

showsPrec :: Int -> Name (RW (sh :. Int)) -> ShowS #

show :: Name (RW (sh :. Int)) -> String #

showList :: [Name (RW (sh :. Int))] -> ShowS #

Show (Name (RW Z)) Source # 

Methods

showsPrec :: Int -> Name (RW Z) -> ShowS #

show :: Name (RW Z) -> String #

showList :: [Name (RW Z)] -> ShowS #

Show sh => Show (RW sh) Source # 

Methods

showsPrec :: Int -> RW sh -> ShowS #

show :: RW sh -> String #

showList :: [RW sh] -> ShowS #

Shape sh => Shape (RW sh) Source # 

Methods

rank :: RW sh -> Int Source #

zeroDim :: RW sh Source #

unitDim :: RW sh Source #

intersectDim :: RW sh -> RW sh -> RW sh Source #

addDim :: RW sh -> RW sh -> RW sh Source #

size :: RW sh -> Int Source #

inShapeRange :: RW sh -> RW sh -> RW sh -> Bool Source #

listOfShape :: RW sh -> [Int] Source #

shapeOfList :: [Int] -> Maybe (RW sh) Source #

(Layout (RW sh), (~) * (Index (RW sh)) sh) => Layout (RW ((:.) sh Int)) Source # 

Associated Types

data Name (RW ((:.) sh Int)) :: * Source #

type Index (RW ((:.) sh Int)) :: * Source #

Methods

name :: Name (RW (sh :. Int)) Source #

create :: Name (RW (sh :. Int)) -> Index (RW (sh :. Int)) -> RW (sh :. Int) Source #

extent :: RW (sh :. Int) -> Index (RW (sh :. Int)) Source #

toIndex :: RW (sh :. Int) -> Index (RW (sh :. Int)) -> Int Source #

fromIndex :: RW (sh :. Int) -> Int -> Index (RW (sh :. Int)) Source #

Layout (RW Z) Source # 

Associated Types

data Name (RW Z) :: * Source #

type Index (RW Z) :: * Source #

Methods

name :: Name (RW Z) Source #

create :: Name (RW Z) -> Index (RW Z) -> RW Z Source #

extent :: RW Z -> Index (RW Z) Source #

toIndex :: RW Z -> Index (RW Z) -> Int Source #

fromIndex :: RW Z -> Int -> Index (RW Z) Source #

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

Row-wise arrays.

Associated Types

data Array (RW sh) sh :: * Source #

Methods

layout :: Array (RW sh) sh -> RW sh Source #

index :: Array (RW sh) sh -> Index (RW sh) -> sh Source #

data Name (RW ((:.) sh Int)) Source # 
data Name (RW ((:.) sh Int)) = RC (Name (RW sh))
data Name (RW Z) Source # 
data Name (RW Z) = RZ
type Index (RW ((:.) sh Int)) Source # 
type Index (RW ((:.) sh Int)) = (:.) sh Int
type Index (RW Z) Source # 
type Index (RW Z) = Z
data Array (RW sh) sh Source # 
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]

Windowed arrays

data W l Source #

Constructors

Window 

Fields

Instances

Eq (Name l) => Eq (Name (W l)) Source # 

Methods

(==) :: Name (W l) -> Name (W l) -> Bool #

(/=) :: Name (W l) -> Name (W l) -> Bool #

(Eq l, Eq (Index l)) => Eq (W l) Source # 

Methods

(==) :: W l -> W l -> Bool #

(/=) :: W l -> W l -> Bool #

Show (Name l) => Show (Name (W l)) Source # 

Methods

showsPrec :: Int -> Name (W l) -> ShowS #

show :: Name (W l) -> String #

showList :: [Name (W l)] -> ShowS #

(Show l, Show (Index l)) => Show (W l) Source # 

Methods

showsPrec :: Int -> W l -> ShowS #

show :: W l -> String #

showList :: [W l] -> ShowS #

Layout l => Layout (W l) Source #

Windowed arrays.

Associated Types

data Name (W l) :: * Source #

type Index (W l) :: * Source #

Methods

name :: Name (W l) Source #

create :: Name (W l) -> Index (W l) -> W l Source #

extent :: W l -> Index (W l) Source #

toIndex :: W l -> Index (W l) -> Int Source #

fromIndex :: W l -> Int -> Index (W l) Source #

Bulk l a => Bulk (W l) a Source #

Windowed arrays.

Associated Types

data Array (W l) a :: * Source #

Methods

layout :: Array (W l) a -> W l Source #

index :: Array (W l) a -> Index (W l) -> a Source #

Bulk l a => Windowable (W l) a Source #

Windows are windowable.

Methods

window :: Index (W l) -> Index (W l) -> Array (W l) a -> Array (W l) a Source #

data Name (W l) Source # 
data Name (W l) = W (Name l)
type Index (W l) Source # 
type Index (W l) = Index l
data Array (W l) Source # 
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.

Minimal complete definition

window

Methods

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

Instances

Windowable B a Source #

Boxed windows.

Methods

window :: Index B -> Index B -> Array B a -> Array B a Source #

Storable a => Windowable F a Source #

Windowing Foreign arrays.

Methods

window :: Index F -> Index F -> Array F a -> Array F a Source #

Unbox a => Windowable U a Source #

Windowing Unboxed arrays.

Methods

window :: Index U -> Index U -> Array U a -> Array U a Source #

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

Windowing Nested arrays.

Methods

window :: Index N -> Index N -> Array N (Array l a) -> Array N (Array l a) Source #

Bulk l a => Windowable (W l) a Source #

Windows are windowable.

Methods

window :: Index (W l) -> Index (W l) -> Array (W l) a -> Array (W l) a Source #

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

Tupled windows.

Methods

window :: Index (T2 l1 l2) -> Index (T2 l1 l2) -> Array (T2 l1 l2) (a, b) -> Array (T2 l1 l2) (a, b) Source #

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.

tail :: (Windowable l a, Index l ~ Int) => Array l a -> Maybe (Array l a) Source #

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

init :: (Windowable l a, Index l ~ Int) => Array l a -> Maybe (Array l a) Source #

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

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)) Source # 

Methods

(==) :: Name (E r l) -> Name (E r l) -> Bool #

(/=) :: Name (E r l) -> Name (E r l) -> Bool #

(Show (Name r), Show (Name l)) => Show (Name (E r l)) Source # 

Methods

showsPrec :: Int -> Name (E r l) -> ShowS #

show :: Name (E r l) -> String #

showList :: [Name (E r l)] -> ShowS #

(Eq r, Eq l) => Eq (E r l) Source # 

Methods

(==) :: E r l -> E r l -> Bool #

(/=) :: E r l -> E r l -> Bool #

(Show r, Show l) => Show (E r l) Source # 

Methods

showsPrec :: Int -> E r l -> ShowS #

show :: E r l -> String #

showList :: [E r l] -> ShowS #

((~) * (Index r) Int, Layout r, Layout l) => Layout (E r l) Source #

Dense arrays.

Associated Types

data Name (E r l) :: * Source #

type Index (E r l) :: * Source #

Methods

name :: Name (E r l) Source #

create :: Name (E r l) -> Index (E r l) -> E r l Source #

extent :: E r l -> Index (E r l) Source #

toIndex :: E r l -> Index (E r l) -> Int Source #

fromIndex :: E r l -> Int -> Index (E r l) Source #

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

Dense arrays.

Associated Types

data Array (E r l) a :: * Source #

Methods

layout :: Array (E r l) a -> E r l Source #

index :: Array (E r l) a -> Index (E r l) -> a Source #

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

Dense buffers.

Associated Types

data Buffer (E r l) a :: * Source #

Methods

unsafeNewBuffer :: E r l -> IO (Buffer (E r l) a) Source #

unsafeReadBuffer :: Buffer (E r l) a -> Int -> IO a Source #

unsafeWriteBuffer :: Buffer (E r l) a -> Int -> a -> IO () Source #

unsafeGrowBuffer :: Buffer (E r l) a -> Int -> IO (Buffer (E r l) a) Source #

unsafeSliceBuffer :: Int -> Int -> Buffer (E r l) a -> IO (Buffer (E r l) a) Source #

unsafeFreezeBuffer :: Buffer (E r l) a -> IO (Array (E r l) a) Source #

unsafeThawBuffer :: Array (E r l) a -> IO (Buffer (E r l) a) Source #

touchBuffer :: Buffer (E r l) a -> IO () Source #

bufferLayout :: Buffer (E r l) a -> E r l Source #

data Name (E r l) Source # 
data Name (E r l) = E (Name r) (Name l)
type Index (E r l) Source # 
type Index (E r l) = Index l
data Array (E r l) Source # 
data Array (E r l) = Array l (Array r a)
data Buffer (E r l) Source # 
data Buffer (E r l) = EBuffer !l !(Buffer 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.

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)) Source # 

Methods

(==) :: Name (T2 l1 l2) -> Name (T2 l1 l2) -> Bool #

(/=) :: Name (T2 l1 l2) -> Name (T2 l1 l2) -> Bool #

(Show (Name l1), Show (Name l2)) => Show (Name (T2 l1 l2)) Source # 

Methods

showsPrec :: Int -> Name (T2 l1 l2) -> ShowS #

show :: Name (T2 l1 l2) -> String #

showList :: [Name (T2 l1 l2)] -> ShowS #

(Eq l1, Eq l2) => Eq (T2 l1 l2) Source # 

Methods

(==) :: T2 l1 l2 -> T2 l1 l2 -> Bool #

(/=) :: T2 l1 l2 -> T2 l1 l2 -> Bool #

(Show (Array l1 a), Show (Array l2 b)) => Show (Array (T2 l1 l2) (a, b)) Source # 

Methods

showsPrec :: Int -> Array (T2 l1 l2) (a, b) -> ShowS #

show :: Array (T2 l1 l2) (a, b) -> String #

showList :: [Array (T2 l1 l2) (a, b)] -> ShowS #

(Show l1, Show l2) => Show (T2 l1 l2) Source # 

Methods

showsPrec :: Int -> T2 l1 l2 -> ShowS #

show :: T2 l1 l2 -> String #

showList :: [T2 l1 l2] -> ShowS #

((~) * (Index l1) (Index l2), Layout l1, Layout l2) => Layout (T2 l1 l2) Source # 

Associated Types

data Name (T2 l1 l2) :: * Source #

type Index (T2 l1 l2) :: * Source #

Methods

name :: Name (T2 l1 l2) Source #

create :: Name (T2 l1 l2) -> Index (T2 l1 l2) -> T2 l1 l2 Source #

extent :: T2 l1 l2 -> Index (T2 l1 l2) Source #

toIndex :: T2 l1 l2 -> Index (T2 l1 l2) -> Int Source #

fromIndex :: T2 l1 l2 -> Int -> Index (T2 l1 l2) Source #

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

Tupled arrays.

Associated Types

data Array (T2 l1 l2) (a, b) :: * Source #

Methods

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

index :: Array (T2 l1 l2) (a, b) -> Index (T2 l1 l2) -> (a, b) Source #

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

Tupled windows.

Methods

window :: Index (T2 l1 l2) -> Index (T2 l1 l2) -> Array (T2 l1 l2) (a, b) -> Array (T2 l1 l2) (a, b) Source #

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

Tupled buffers.

Associated Types

data Buffer (T2 l1 l2) (a, b) :: * Source #

Methods

unsafeNewBuffer :: T2 l1 l2 -> IO (Buffer (T2 l1 l2) (a, b)) Source #

unsafeReadBuffer :: Buffer (T2 l1 l2) (a, b) -> Int -> IO (a, b) Source #

unsafeWriteBuffer :: Buffer (T2 l1 l2) (a, b) -> Int -> (a, b) -> IO () Source #

unsafeGrowBuffer :: Buffer (T2 l1 l2) (a, b) -> Int -> IO (Buffer (T2 l1 l2) (a, b)) Source #

unsafeSliceBuffer :: Int -> Int -> Buffer (T2 l1 l2) (a, b) -> IO (Buffer (T2 l1 l2) (a, b)) Source #

unsafeFreezeBuffer :: Buffer (T2 l1 l2) (a, b) -> IO (Array (T2 l1 l2) (a, b)) Source #

unsafeThawBuffer :: Array (T2 l1 l2) (a, b) -> IO (Buffer (T2 l1 l2) (a, b)) Source #

touchBuffer :: Buffer (T2 l1 l2) (a, b) -> IO () Source #

bufferLayout :: Buffer (T2 l1 l2) (a, b) -> T2 l1 l2 Source #

data Name (T2 l1 l2) Source # 
data Name (T2 l1 l2) = T2 !(Name l1) !(Name l2)
type Index (T2 l1 l2) Source # 
type Index (T2 l1 l2) = Index l1
data Array (T2 l1 l2) (a, b) Source # 
data Array (T2 l1 l2) (a, b) = T2Array !(Array l1 a) !(Array l2 b)
data Buffer (T2 l1 l2) (a, b) Source # 
data Buffer (T2 l1 l2) (a, b) = T2Buffer !(Buffer l1 a) !(Buffer l2 b)

tup2 :: 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.