accelerate-1.0.0.0: An embedded language for accelerated array processing

Copyright[2008..2017] Manuel M T Chakravarty Gabriele Keller
[2009..2017] Trevor L. McDonell
[2013..2017] Robert Clifton-Everest
[2014..2014] Frederik M. Madsen
LicenseBSD3
MaintainerTrevor L. McDonell <tmcdonell@cse.unsw.edu.au>
Stabilityexperimental
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell98

Data.Array.Accelerate

Contents

Description

Data.Array.Accelerate defines an embedded language of array computations for high-performance computing in Haskell. Computations on multi-dimensional, regular arrays are expressed in the form of parameterised collective operations such as maps, reductions, and permutations. These computations are online compiled and can be executed on a range of architectures.

Abstract interface:

The types representing array computations are only exported abstractly; client code can generate array computations and submit them for execution, but it cannot inspect these computations. This is to allow for more flexibility for future extensions of this library.

Stratified language:

Accelerate distinguishes the types of collective operations Acc from the type of scalar operations Exp to achieve a stratified language. Collective operations comprise many scalar computations that are executed in parallel, but scalar computations can not contain collective operations. This separation excludes nested, irregular data-parallelism statically; instead, Accelerate is limited to flat data-parallelism involving only regular, multi-dimensional arrays.

Optimisations:

Accelerate uses a number of scalar and array optimisations, including array fusion, in order to improve the performance of programs. Fusing a program entails combining successive traversals (loops) over an array into a single traversal, which reduces memory traffic and eliminates intermediate arrays.

Code execution:

Several backends are available which can be used to evaluate accelerate programs:

  • Data.Array.Accelerate.Interpreter: simple interpreter in Haskell as a reference implementation defining the semantics of the Accelerate language
  • accelerate-llvm-native: implementation supporting parallel execution on multicore CPUs (e.g. x86).
  • accelerate-llvm-ptx: implementation supporting parallel execution on CUDA-capable NVIDIA GPUs.
  • accelerate-cuda: an older implementation supporting parallel execution on CUDA-capable NVIDIA GPUs. NOTE: This backend is being deprecated in favour of accelerate-llvm-ptx.
Examples:
  • The accelerate-examples package demonstrates a range of computational kernels and several complete applications:

    • Implementation of the canny edge detector
    • Interactive Mandelbrot set generator
    • N-body simulation of gravitational attraction between large bodies
    • Implementation of the PageRank algorithm
    • A simple, real-time, interactive ray tracer.
    • A particle based simulation of stable fluid flows
    • A cellular automaton simulation
    • A "password recovery" tool, for dictionary attacks on MD5 hashes.

  • lulesh-accelerate is an implementation of the Livermore Unstructured Lagrangian Explicit Shock Hydrodynamics (LULESH) application. LULESH is representative of typical hydrodynamics codes, although simplified and hard-coded to solve the Sedov blast problem on an unstructured hexahedron mesh.

Additional components:
Contact:
Tip:

Accelerate tends to stress GHC's garbage collector, so it helps to increase the default GC allocation sizes. This can be done when running an executable by specifying RTS options on the command line, for example:

./foo +RTS -A64M -n2M -RTS

You can make these settings the default by adding the following ghc-options to your .cabal file or similar:

ghc-options: -with-rtsopts=-n2M -with-rtsopts=-A64M

To specify RTS options you will also need to compile your program with -rtsopts.

Synopsis

The Accelerate Array Language

Embedded array computations

data Acc a #

Accelerate is an embedded language that distinguishes between vanilla arrays (e.g. in Haskell memory on the CPU) and embedded arrays (e.g. in device memory on a GPU), as well as the computations on both of these. Since Accelerate is an embedded language, programs written in Accelerate are not compiled by the Haskell compiler (GHC). Rather, each Accelerate backend is a runtime compiler which generates and executes parallel SIMD code of the target language at application runtime.

The type constructor Acc represents embedded collective array operations. A term of type Acc a is an Accelerate program which, once executed, will produce a value of type a (an Array or a tuple of Arrays). Collective operations of type Acc a comprise many scalar expressions, wrapped in type constructor Exp, which will be executed in parallel. Although collective operations comprise many scalar operations executed in parallel, scalar operations cannot initiate new collective operations: this stratification between scalar operations in Exp and array operations in Acc helps statically exclude nested data parallelism, which is difficult to execute efficiently on constrained hardware such as GPUs.

For example, to compute a vector dot product we could write:

dotp :: Num a => Vector a -> Vector a -> Acc (Scalar a)
dotp xs ys =
  let
      xs' = use xs
      ys' = use ys
  in
  fold (+) 0 ( zipWith (*) xs' ys' )

The function dotp consumes two one-dimensional arrays (Vectors) of values, and produces a single (Scalar) result as output. As the return type is wrapped in the type Acc, we see that it is an embedded Accelerate computation - it will be evaluated in the object language of dynamically generated parallel code, rather than the meta language of vanilla Haskell.

As the arguments to dotp are plain Haskell arrays, to make these available to Accelerate computations they must be embedded with the use function.

An Accelerate backend is used to evaluate the embedded computation and return the result back to vanilla Haskell. Calling the run function of a backend will generate code for the target architecture, compile, and execute it. For example, the following backends are available:

See also Exp, which encapsulates embedded scalar computations.

Fusion:

Array computations of type Acc will be subject to array fusion; Accelerate will combine individual Acc computations into a single computation, which reduces the number of traversals over the input data and thus improves performance. As such, it is often useful to have some intuition on when fusion should occur.

The main idea is to first partition array operations into two categories:

  1. Element-wise operations, such as map, generate, and backpermute. Each element of these operations can be computed independently of all others.
  2. Collective operations such as fold, scanl, and stencil. To compute each output element of these operations requires reading multiple elements from the input array(s).

Element-wise operations fuse together whenever the consumer operation uses a single element of the input array. Element-wise operations can both fuse their inputs into themselves, as well be fused into later operations. Both these examples should fuse into a single loop:

map -> reverse -> reshape -> map -> map
map -> backpermute ->
                      zipWith -> map
          generate ->

If the consumer operation uses more than one element of the input array (typically, via generate indexing an array multiple times), then the input array will be completely evaluated first; no fusion occurs in this case, because fusing the first operation into the second implies duplicating work.

On the other hand, collective operations can fuse their input arrays into themselves, but on output always evaluate to an array; collective operations will not be fused into a later step. For example:

     use ->
            zipWith -> fold |-> map
generate ->

Here the element-wise sequence (use + generate + zipWith) will fuse into a single operation, which then fuses into the collective fold operation. At this point in the program the fold must now be evaluated. In the final step the map reads in the array produced by fold. As there is no fusion between the fold and map steps, this program consists of two "loops"; one for the use + generate + zipWith + fold step, and one for the final map step.

You can see how many operations will be executed in the fused program by Show-ing the Acc program, or by using the debugging option -ddump-dot to save the program as a graphviz DOT file.

As a special note, the operations unzip and reshape, when applied to a real array, are executed in constant time, so in this situation these operations will not be fused.

Tips:
  • Since Acc represents embedded computations that will only be executed when evaluated by a backend, we can programatically generate these computations using the meta language Haskell; for example, unrolling loops or embedding input values into the generated code.
  • It is usually best to keep all intermediate computations in Acc, and only run the computation at the very end to produce the final result. This enables optimisations between intermediate results (e.g. array fusion) and, if the target architecture has a separate memory space as is the case of GPUs, to prevent excessive data transfers.

Instances

IfThenElse Acc # 

Associated Types

type EltT (Acc :: * -> *) a :: Constraint #

Methods

ifThenElse :: EltT Acc a => Exp Bool -> Acc a -> Acc a -> Acc a #

Unlift Acc (Acc a) # 

Methods

unlift :: Acc (Plain (Acc a)) -> Acc a #

Lift Acc (Acc a) # 

Associated Types

type Plain (Acc a) :: * #

Methods

lift :: Acc a -> Acc (Plain (Acc a)) #

(Arrays a, Arrays b) => Unlift Acc (Acc a, Acc b) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b)) -> (Acc a, Acc b) #

(Lift Acc a, Lift Acc b, Arrays (Plain a), Arrays (Plain b)) => Lift Acc (a, b) # 

Associated Types

type Plain (a, b) :: * #

Methods

lift :: (a, b) -> Acc (Plain (a, b)) #

(Shape sh, Elt e) => Lift Acc (Array sh e) # 

Associated Types

type Plain (Array sh e) :: * #

Methods

lift :: Array sh e -> Acc (Plain (Array sh e)) #

(Arrays a, Arrays b, Arrays c) => Unlift Acc (Acc a, Acc b, Acc c) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c)) -> (Acc a, Acc b, Acc c) #

(Lift Acc a, Lift Acc b, Lift Acc c, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c)) => Lift Acc (a, b, c) # 

Associated Types

type Plain (a, b, c) :: * #

Methods

lift :: (a, b, c) -> Acc (Plain (a, b, c)) #

(Arrays a, Arrays b, Arrays c, Arrays d) => Unlift Acc (Acc a, Acc b, Acc c, Acc d) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d)) -> (Acc a, Acc b, Acc c, Acc d) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d)) => Lift Acc (a, b, c, d) # 

Associated Types

type Plain (a, b, c, d) :: * #

Methods

lift :: (a, b, c, d) -> Acc (Plain (a, b, c, d)) #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e)) -> (Acc a, Acc b, Acc c, Acc d, Acc e) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e)) => Lift Acc (a, b, c, d, e) # 

Associated Types

type Plain (a, b, c, d, e) :: * #

Methods

lift :: (a, b, c, d, e) -> Acc (Plain (a, b, c, d, e)) #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f)) => Lift Acc (a, b, c, d, e, f) # 

Associated Types

type Plain (a, b, c, d, e, f) :: * #

Methods

lift :: (a, b, c, d, e, f) -> Acc (Plain (a, b, c, d, e, f)) #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g)) => Lift Acc (a, b, c, d, e, f, g) # 

Associated Types

type Plain (a, b, c, d, e, f, g) :: * #

Methods

lift :: (a, b, c, d, e, f, g) -> Acc (Plain (a, b, c, d, e, f, g)) #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Lift Acc h, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g), Arrays (Plain h)) => Lift Acc (a, b, c, d, e, f, g, h) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h) -> Acc (Plain (a, b, c, d, e, f, g, h)) #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Lift Acc h, Lift Acc i, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g), Arrays (Plain h), Arrays (Plain i)) => Lift Acc (a, b, c, d, e, f, g, h, i) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i) -> Acc (Plain (a, b, c, d, e, f, g, h, i)) #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Lift Acc h, Lift Acc i, Lift Acc j, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g), Arrays (Plain h), Arrays (Plain i), Arrays (Plain j)) => Lift Acc (a, b, c, d, e, f, g, h, i, j) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j) -> Acc (Plain (a, b, c, d, e, f, g, h, i, j)) #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j, Arrays k) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Lift Acc h, Lift Acc i, Lift Acc j, Lift Acc k, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g), Arrays (Plain h), Arrays (Plain i), Arrays (Plain j), Arrays (Plain k)) => Lift Acc (a, b, c, d, e, f, g, h, i, j, k) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k) -> Acc (Plain (a, b, c, d, e, f, g, h, i, j, k)) #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j, Arrays k, Arrays l) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Lift Acc h, Lift Acc i, Lift Acc j, Lift Acc k, Lift Acc l, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g), Arrays (Plain h), Arrays (Plain i), Arrays (Plain j), Arrays (Plain k), Arrays (Plain l)) => Lift Acc (a, b, c, d, e, f, g, h, i, j, k, l) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Acc (Plain (a, b, c, d, e, f, g, h, i, j, k, l)) #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j, Arrays k, Arrays l, Arrays m) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Lift Acc h, Lift Acc i, Lift Acc j, Lift Acc k, Lift Acc l, Lift Acc m, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g), Arrays (Plain h), Arrays (Plain i), Arrays (Plain j), Arrays (Plain k), Arrays (Plain l), Arrays (Plain m)) => Lift Acc (a, b, c, d, e, f, g, h, i, j, k, l, m) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l, m) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Acc (Plain (a, b, c, d, e, f, g, h, i, j, k, l, m)) #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j, Arrays k, Arrays l, Arrays m, Arrays n) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m, Acc n) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m, Acc n)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m, Acc n) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Lift Acc h, Lift Acc i, Lift Acc j, Lift Acc k, Lift Acc l, Lift Acc m, Lift Acc n, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g), Arrays (Plain h), Arrays (Plain i), Arrays (Plain j), Arrays (Plain k), Arrays (Plain l), Arrays (Plain m), Arrays (Plain n)) => Lift Acc (a, b, c, d, e, f, g, h, i, j, k, l, m, n) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Acc (Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n)) #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j, Arrays k, Arrays l, Arrays m, Arrays n, Arrays o) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m, Acc n, Acc o) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m, Acc n, Acc o)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m, Acc n, Acc o) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Lift Acc h, Lift Acc i, Lift Acc j, Lift Acc k, Lift Acc l, Lift Acc m, Lift Acc n, Lift Acc o, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g), Arrays (Plain h), Arrays (Plain i), Arrays (Plain j), Arrays (Plain k), Arrays (Plain l), Arrays (Plain m), Arrays (Plain n), Arrays (Plain o)) => Lift Acc (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Acc (Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)) #

type EltT Acc a # 
type EltT Acc a = Arrays a
type Plain (Acc a) # 
type Plain (Acc a) = a

Arrays

data Array sh e #

Dense, regular, multi-dimensional arrays.

The Array is the core computational unit of Accelerate; all programs in Accelerate take zero or more arrays as input and produce one or more arrays as output. The Array type has two type parameters:

  • sh: is the shape of the array, tracking the dimensionality and extent of each dimension of the array; for example, DIM1 for one-dimensional Vectors, DIM2 for two-dimensional matrices, and so on.
  • e: represents the type of each element of the array; for example, Int, Float, et cetera.

Array data is store unboxed in an unzipped struct-of-array representation. Elements are laid out in row-major order (the right-most index of a Shape is the fastest varying). The allowable array element types are members of the Elt class, which roughly consists of:

  • Signed and unsigned integers (8, 16, 32, and 64-bits wide).
  • Floating point numbers (single and double precision)
  • Char
  • Bool
  • ()
  • Shapes formed from Z and (:.)
  • Nested tuples of all of these, currently up to 15-elements wide.

Note that Array itself is not an allowable element type---there are no nested arrays in Accelerate, regular arrays only!

If device and host memory are separate, arrays will be transferred to the device when necessary (possibly asynchronously and in parallel with other tasks) and cached on the device if sufficient memory is available. Arrays are made available to embedded language computations via use.

Section "Getting data in" lists functions for getting data into and out of the Array type.

Instances

(Shape sh, Elt e) => Lift Acc (Array sh e) # 

Associated Types

type Plain (Array sh e) :: * #

Methods

lift :: Array sh e -> Acc (Plain (Array sh e)) #

Elt e => IsList (Vector e) # 

Associated Types

type Item (Vector e) :: * #

Methods

fromList :: [Item (Vector e)] -> Vector e #

fromListN :: Int -> [Item (Vector e)] -> Vector e #

toList :: Vector e -> [Item (Vector e)] #

Show (Vector e) # 

Methods

showsPrec :: Int -> Vector e -> ShowS #

show :: Vector e -> String #

showList :: [Vector e] -> ShowS #

Show (Scalar e) # 

Methods

showsPrec :: Int -> Scalar e -> ShowS #

show :: Scalar e -> String #

showList :: [Scalar e] -> ShowS #

(Eq sh, Eq e) => Eq (Array sh e) # 

Methods

(==) :: Array sh e -> Array sh e -> Bool #

(/=) :: Array sh e -> Array sh e -> Bool #

Show (Array sh e) # 

Methods

showsPrec :: Int -> Array sh e -> ShowS #

show :: Array sh e -> String #

showList :: [Array sh e] -> ShowS #

Show (Array DIM2 e) # 

Methods

showsPrec :: Int -> Array DIM2 e -> ShowS #

show :: Array DIM2 e -> String #

showList :: [Array DIM2 e] -> ShowS #

NFData (Array sh e) # 

Methods

rnf :: Array sh e -> () #

(Shape sh, Elt e) => Arrays (Array sh e) # 

Methods

arrays :: Array sh e -> ArraysR (ArrRepr (Array sh e))

flavour :: Array sh e -> ArraysFlavour (Array sh e)

toArr :: ArrRepr (Array sh e) -> Array sh e

fromArr :: Array sh e -> ArrRepr (Array sh e)

type Item (Vector e) # 
type Item (Vector e) = e
type Plain (Array sh e) # 
type Plain (Array sh e) = Array sh e

class (Typeable a, Typeable (ArrRepr a)) => Arrays a #

Arrays consists of nested tuples of individual Arrays, currently up to 15-elements wide. Accelerate computations can thereby return multiple results.

Minimal complete definition

arrays, flavour, toArr, fromArr

Instances

Arrays () # 

Methods

arrays :: () -> ArraysR (ArrRepr ())

flavour :: () -> ArraysFlavour ()

toArr :: ArrRepr () -> ()

fromArr :: () -> ArrRepr ()

(Arrays a, Arrays b) => Arrays (a, b) # 

Methods

arrays :: (a, b) -> ArraysR (ArrRepr (a, b))

flavour :: (a, b) -> ArraysFlavour (a, b)

toArr :: ArrRepr (a, b) -> (a, b)

fromArr :: (a, b) -> ArrRepr (a, b)

(Shape sh, Elt e) => Arrays (Array sh e) # 

Methods

arrays :: Array sh e -> ArraysR (ArrRepr (Array sh e))

flavour :: Array sh e -> ArraysFlavour (Array sh e)

toArr :: ArrRepr (Array sh e) -> Array sh e

fromArr :: Array sh e -> ArrRepr (Array sh e)

(Arrays a, Arrays b, Arrays c) => Arrays (a, b, c) # 

Methods

arrays :: (a, b, c) -> ArraysR (ArrRepr (a, b, c))

flavour :: (a, b, c) -> ArraysFlavour (a, b, c)

toArr :: ArrRepr (a, b, c) -> (a, b, c)

fromArr :: (a, b, c) -> ArrRepr (a, b, c)

(Arrays a, Arrays b, Arrays c, Arrays d) => Arrays (a, b, c, d) # 

Methods

arrays :: (a, b, c, d) -> ArraysR (ArrRepr (a, b, c, d))

flavour :: (a, b, c, d) -> ArraysFlavour (a, b, c, d)

toArr :: ArrRepr (a, b, c, d) -> (a, b, c, d)

fromArr :: (a, b, c, d) -> ArrRepr (a, b, c, d)

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e) => Arrays (a, b, c, d, e) # 

Methods

arrays :: (a, b, c, d, e) -> ArraysR (ArrRepr (a, b, c, d, e))

flavour :: (a, b, c, d, e) -> ArraysFlavour (a, b, c, d, e)

toArr :: ArrRepr (a, b, c, d, e) -> (a, b, c, d, e)

fromArr :: (a, b, c, d, e) -> ArrRepr (a, b, c, d, e)

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f) => Arrays (a, b, c, d, e, f) # 

Methods

arrays :: (a, b, c, d, e, f) -> ArraysR (ArrRepr (a, b, c, d, e, f))

flavour :: (a, b, c, d, e, f) -> ArraysFlavour (a, b, c, d, e, f)

toArr :: ArrRepr (a, b, c, d, e, f) -> (a, b, c, d, e, f)

fromArr :: (a, b, c, d, e, f) -> ArrRepr (a, b, c, d, e, f)

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g) => Arrays (a, b, c, d, e, f, g) # 

Methods

arrays :: (a, b, c, d, e, f, g) -> ArraysR (ArrRepr (a, b, c, d, e, f, g))

flavour :: (a, b, c, d, e, f, g) -> ArraysFlavour (a, b, c, d, e, f, g)

toArr :: ArrRepr (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g)

fromArr :: (a, b, c, d, e, f, g) -> ArrRepr (a, b, c, d, e, f, g)

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h) => Arrays (a, b, c, d, e, f, g, h) # 

Methods

arrays :: (a, b, c, d, e, f, g, h) -> ArraysR (ArrRepr (a, b, c, d, e, f, g, h))

flavour :: (a, b, c, d, e, f, g, h) -> ArraysFlavour (a, b, c, d, e, f, g, h)

toArr :: ArrRepr (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h)

fromArr :: (a, b, c, d, e, f, g, h) -> ArrRepr (a, b, c, d, e, f, g, h)

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i) => Arrays (a, b, c, d, e, f, g, h, i) # 

Methods

arrays :: (a, b, c, d, e, f, g, h, i) -> ArraysR (ArrRepr (a, b, c, d, e, f, g, h, i))

flavour :: (a, b, c, d, e, f, g, h, i) -> ArraysFlavour (a, b, c, d, e, f, g, h, i)

toArr :: ArrRepr (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i)

fromArr :: (a, b, c, d, e, f, g, h, i) -> ArrRepr (a, b, c, d, e, f, g, h, i)

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j) => Arrays (a, b, c, d, e, f, g, h, i, j) # 

Methods

arrays :: (a, b, c, d, e, f, g, h, i, j) -> ArraysR (ArrRepr (a, b, c, d, e, f, g, h, i, j))

flavour :: (a, b, c, d, e, f, g, h, i, j) -> ArraysFlavour (a, b, c, d, e, f, g, h, i, j)

toArr :: ArrRepr (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j)

fromArr :: (a, b, c, d, e, f, g, h, i, j) -> ArrRepr (a, b, c, d, e, f, g, h, i, j)

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j, Arrays k) => Arrays (a, b, c, d, e, f, g, h, i, j, k) # 

Methods

arrays :: (a, b, c, d, e, f, g, h, i, j, k) -> ArraysR (ArrRepr (a, b, c, d, e, f, g, h, i, j, k))

flavour :: (a, b, c, d, e, f, g, h, i, j, k) -> ArraysFlavour (a, b, c, d, e, f, g, h, i, j, k)

toArr :: ArrRepr (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k)

fromArr :: (a, b, c, d, e, f, g, h, i, j, k) -> ArrRepr (a, b, c, d, e, f, g, h, i, j, k)

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j, Arrays k, Arrays l) => Arrays (a, b, c, d, e, f, g, h, i, j, k, l) # 

Methods

arrays :: (a, b, c, d, e, f, g, h, i, j, k, l) -> ArraysR (ArrRepr (a, b, c, d, e, f, g, h, i, j, k, l))

flavour :: (a, b, c, d, e, f, g, h, i, j, k, l) -> ArraysFlavour (a, b, c, d, e, f, g, h, i, j, k, l)

toArr :: ArrRepr (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l)

fromArr :: (a, b, c, d, e, f, g, h, i, j, k, l) -> ArrRepr (a, b, c, d, e, f, g, h, i, j, k, l)

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j, Arrays k, Arrays l, Arrays m) => Arrays (a, b, c, d, e, f, g, h, i, j, k, l, m) # 

Methods

arrays :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> ArraysR (ArrRepr (a, b, c, d, e, f, g, h, i, j, k, l, m))

flavour :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> ArraysFlavour (a, b, c, d, e, f, g, h, i, j, k, l, m)

toArr :: ArrRepr (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m)

fromArr :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> ArrRepr (a, b, c, d, e, f, g, h, i, j, k, l, m)

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j, Arrays k, Arrays l, Arrays m, Arrays n) => Arrays (a, b, c, d, e, f, g, h, i, j, k, l, m, n) # 

Methods

arrays :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> ArraysR (ArrRepr (a, b, c, d, e, f, g, h, i, j, k, l, m, n))

flavour :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> ArraysFlavour (a, b, c, d, e, f, g, h, i, j, k, l, m, n)

toArr :: ArrRepr (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n)

fromArr :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> ArrRepr (a, b, c, d, e, f, g, h, i, j, k, l, m, n)

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j, Arrays k, Arrays l, Arrays m, Arrays n, Arrays o) => Arrays (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) # 

Methods

arrays :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> ArraysR (ArrRepr (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))

flavour :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> ArraysFlavour (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)

toArr :: ArrRepr (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)

fromArr :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> ArrRepr (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)

type Scalar e = Array DIM0 e #

Scalars arrays hold a single element

type Vector e = Array DIM1 e #

Vectors are one-dimensional arrays

type Segments i = Vector i #

Segment descriptor (vector of segment lengths).

To represent nested one-dimensional arrays, we use a flat array of data values in conjunction with a segment descriptor, which stores the lengths of the subarrays.

Array elements

class (Show a, Typeable a, Typeable (EltRepr a), ArrayElt (EltRepr a)) => Elt a #

The Elt class characterises the allowable array element types, and hence the types which can appear in scalar Accelerate expressions.

Accelerate arrays consist of simple atomic types as well as nested tuples thereof, stored efficiently in memory as consecutive unpacked elements without pointers. It roughly consists of:

  • Signed and unsigned integers (8, 16, 32, and 64-bits wide)
  • Floating point numbers (single and double precision)
  • Char
  • Bool
  • ()
  • Shapes formed from Z and (:.)
  • Nested tuples of all of these, currently up to 15-elements wide

Adding new instances for Elt consists of explaining to Accelerate how to map between your data type and a (tuple of) primitive values. For examples see:

Minimal complete definition

eltType, fromElt, toElt

Instances

Elt Bool # 

Methods

eltType :: Bool -> TupleType (EltRepr Bool)

fromElt :: Bool -> EltRepr Bool

toElt :: EltRepr Bool -> Bool

Elt Char # 

Methods

eltType :: Char -> TupleType (EltRepr Char)

fromElt :: Char -> EltRepr Char

toElt :: EltRepr Char -> Char

Elt Double # 

Methods

eltType :: Double -> TupleType (EltRepr Double)

fromElt :: Double -> EltRepr Double

toElt :: EltRepr Double -> Double

Elt Float # 

Methods

eltType :: Float -> TupleType (EltRepr Float)

fromElt :: Float -> EltRepr Float

toElt :: EltRepr Float -> Float

Elt Int # 

Methods

eltType :: Int -> TupleType (EltRepr Int)

fromElt :: Int -> EltRepr Int

toElt :: EltRepr Int -> Int

Elt Int8 # 

Methods

eltType :: Int8 -> TupleType (EltRepr Int8)

fromElt :: Int8 -> EltRepr Int8

toElt :: EltRepr Int8 -> Int8

Elt Int16 # 

Methods

eltType :: Int16 -> TupleType (EltRepr Int16)

fromElt :: Int16 -> EltRepr Int16

toElt :: EltRepr Int16 -> Int16

Elt Int32 # 

Methods

eltType :: Int32 -> TupleType (EltRepr Int32)

fromElt :: Int32 -> EltRepr Int32

toElt :: EltRepr Int32 -> Int32

Elt Int64 # 

Methods

eltType :: Int64 -> TupleType (EltRepr Int64)

fromElt :: Int64 -> EltRepr Int64

toElt :: EltRepr Int64 -> Int64

Elt Word # 

Methods

eltType :: Word -> TupleType (EltRepr Word)

fromElt :: Word -> EltRepr Word

toElt :: EltRepr Word -> Word

Elt Word8 # 

Methods

eltType :: Word8 -> TupleType (EltRepr Word8)

fromElt :: Word8 -> EltRepr Word8

toElt :: EltRepr Word8 -> Word8

Elt Word16 # 

Methods

eltType :: Word16 -> TupleType (EltRepr Word16)

fromElt :: Word16 -> EltRepr Word16

toElt :: EltRepr Word16 -> Word16

Elt Word32 # 

Methods

eltType :: Word32 -> TupleType (EltRepr Word32)

fromElt :: Word32 -> EltRepr Word32

toElt :: EltRepr Word32 -> Word32

Elt Word64 # 

Methods

eltType :: Word64 -> TupleType (EltRepr Word64)

fromElt :: Word64 -> EltRepr Word64

toElt :: EltRepr Word64 -> Word64

Elt () # 

Methods

eltType :: () -> TupleType (EltRepr ())

fromElt :: () -> EltRepr ()

toElt :: EltRepr () -> ()

Elt CChar # 

Methods

eltType :: CChar -> TupleType (EltRepr CChar)

fromElt :: CChar -> EltRepr CChar

toElt :: EltRepr CChar -> CChar

Elt CSChar # 

Methods

eltType :: CSChar -> TupleType (EltRepr CSChar)

fromElt :: CSChar -> EltRepr CSChar

toElt :: EltRepr CSChar -> CSChar

Elt CUChar # 

Methods

eltType :: CUChar -> TupleType (EltRepr CUChar)

fromElt :: CUChar -> EltRepr CUChar

toElt :: EltRepr CUChar -> CUChar

Elt CShort # 

Methods

eltType :: CShort -> TupleType (EltRepr CShort)

fromElt :: CShort -> EltRepr CShort

toElt :: EltRepr CShort -> CShort

Elt CUShort # 

Methods

eltType :: CUShort -> TupleType (EltRepr CUShort)

fromElt :: CUShort -> EltRepr CUShort

toElt :: EltRepr CUShort -> CUShort

Elt CInt # 

Methods

eltType :: CInt -> TupleType (EltRepr CInt)

fromElt :: CInt -> EltRepr CInt

toElt :: EltRepr CInt -> CInt

Elt CUInt # 

Methods

eltType :: CUInt -> TupleType (EltRepr CUInt)

fromElt :: CUInt -> EltRepr CUInt

toElt :: EltRepr CUInt -> CUInt

Elt CLong # 

Methods

eltType :: CLong -> TupleType (EltRepr CLong)

fromElt :: CLong -> EltRepr CLong

toElt :: EltRepr CLong -> CLong

Elt CULong # 

Methods

eltType :: CULong -> TupleType (EltRepr CULong)

fromElt :: CULong -> EltRepr CULong

toElt :: EltRepr CULong -> CULong

Elt CLLong # 

Methods

eltType :: CLLong -> TupleType (EltRepr CLLong)

fromElt :: CLLong -> EltRepr CLLong

toElt :: EltRepr CLLong -> CLLong

Elt CULLong # 

Methods

eltType :: CULLong -> TupleType (EltRepr CULLong)

fromElt :: CULLong -> EltRepr CULLong

toElt :: EltRepr CULLong -> CULLong

Elt CFloat # 

Methods

eltType :: CFloat -> TupleType (EltRepr CFloat)

fromElt :: CFloat -> EltRepr CFloat

toElt :: EltRepr CFloat -> CFloat

Elt CDouble # 

Methods

eltType :: CDouble -> TupleType (EltRepr CDouble)

fromElt :: CDouble -> EltRepr CDouble

toElt :: EltRepr CDouble -> CDouble

Elt All # 

Methods

eltType :: All -> TupleType (EltRepr All)

fromElt :: All -> EltRepr All

toElt :: EltRepr All -> All

Elt Z # 

Methods

eltType :: Z -> TupleType (EltRepr Z)

fromElt :: Z -> EltRepr Z

toElt :: EltRepr Z -> Z

Shape sh => Elt (Any ((:.) sh Int)) # 

Methods

eltType :: Any (sh :. Int) -> TupleType (EltRepr (Any (sh :. Int)))

fromElt :: Any (sh :. Int) -> EltRepr (Any (sh :. Int))

toElt :: EltRepr (Any (sh :. Int)) -> Any (sh :. Int)

Elt (Any Z) # 

Methods

eltType :: Any Z -> TupleType (EltRepr (Any Z))

fromElt :: Any Z -> EltRepr (Any Z)

toElt :: EltRepr (Any Z) -> Any Z

(Elt a, Elt b) => Elt (a, b) # 

Methods

eltType :: (a, b) -> TupleType (EltRepr (a, b))

fromElt :: (a, b) -> EltRepr (a, b)

toElt :: EltRepr (a, b) -> (a, b)

(Elt t, Elt h) => Elt ((:.) t h) # 

Methods

eltType :: (t :. h) -> TupleType (EltRepr (t :. h))

fromElt :: (t :. h) -> EltRepr (t :. h)

toElt :: EltRepr (t :. h) -> t :. h

(Elt a, Elt b, Elt c) => Elt (a, b, c) # 

Methods

eltType :: (a, b, c) -> TupleType (EltRepr (a, b, c))

fromElt :: (a, b, c) -> EltRepr (a, b, c)

toElt :: EltRepr (a, b, c) -> (a, b, c)

(Elt a, Elt b, Elt c, Elt d) => Elt (a, b, c, d) # 

Methods

eltType :: (a, b, c, d) -> TupleType (EltRepr (a, b, c, d))

fromElt :: (a, b, c, d) -> EltRepr (a, b, c, d)

toElt :: EltRepr (a, b, c, d) -> (a, b, c, d)

(Elt a, Elt b, Elt c, Elt d, Elt e) => Elt (a, b, c, d, e) # 

Methods

eltType :: (a, b, c, d, e) -> TupleType (EltRepr (a, b, c, d, e))

fromElt :: (a, b, c, d, e) -> EltRepr (a, b, c, d, e)

toElt :: EltRepr (a, b, c, d, e) -> (a, b, c, d, e)

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => Elt (a, b, c, d, e, f) # 

Methods

eltType :: (a, b, c, d, e, f) -> TupleType (EltRepr (a, b, c, d, e, f))

fromElt :: (a, b, c, d, e, f) -> EltRepr (a, b, c, d, e, f)

toElt :: EltRepr (a, b, c, d, e, f) -> (a, b, c, d, e, f)

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g) => Elt (a, b, c, d, e, f, g) # 

Methods

eltType :: (a, b, c, d, e, f, g) -> TupleType (EltRepr (a, b, c, d, e, f, g))

fromElt :: (a, b, c, d, e, f, g) -> EltRepr (a, b, c, d, e, f, g)

toElt :: EltRepr (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g)

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => Elt (a, b, c, d, e, f, g, h) # 

Methods

eltType :: (a, b, c, d, e, f, g, h) -> TupleType (EltRepr (a, b, c, d, e, f, g, h))

fromElt :: (a, b, c, d, e, f, g, h) -> EltRepr (a, b, c, d, e, f, g, h)

toElt :: EltRepr (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h)

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => Elt (a, b, c, d, e, f, g, h, i) # 

Methods

eltType :: (a, b, c, d, e, f, g, h, i) -> TupleType (EltRepr (a, b, c, d, e, f, g, h, i))

fromElt :: (a, b, c, d, e, f, g, h, i) -> EltRepr (a, b, c, d, e, f, g, h, i)

toElt :: EltRepr (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i)

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j) => Elt (a, b, c, d, e, f, g, h, i, j) # 

Methods

eltType :: (a, b, c, d, e, f, g, h, i, j) -> TupleType (EltRepr (a, b, c, d, e, f, g, h, i, j))

fromElt :: (a, b, c, d, e, f, g, h, i, j) -> EltRepr (a, b, c, d, e, f, g, h, i, j)

toElt :: EltRepr (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j)

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k) => Elt (a, b, c, d, e, f, g, h, i, j, k) # 

Methods

eltType :: (a, b, c, d, e, f, g, h, i, j, k) -> TupleType (EltRepr (a, b, c, d, e, f, g, h, i, j, k))

fromElt :: (a, b, c, d, e, f, g, h, i, j, k) -> EltRepr (a, b, c, d, e, f, g, h, i, j, k)

toElt :: EltRepr (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k)

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k, Elt l) => Elt (a, b, c, d, e, f, g, h, i, j, k, l) # 

Methods

eltType :: (a, b, c, d, e, f, g, h, i, j, k, l) -> TupleType (EltRepr (a, b, c, d, e, f, g, h, i, j, k, l))

fromElt :: (a, b, c, d, e, f, g, h, i, j, k, l) -> EltRepr (a, b, c, d, e, f, g, h, i, j, k, l)

toElt :: EltRepr (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l)

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k, Elt l, Elt m) => Elt (a, b, c, d, e, f, g, h, i, j, k, l, m) # 

Methods

eltType :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> TupleType (EltRepr (a, b, c, d, e, f, g, h, i, j, k, l, m))

fromElt :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> EltRepr (a, b, c, d, e, f, g, h, i, j, k, l, m)

toElt :: EltRepr (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m)

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k, Elt l, Elt m, Elt n) => Elt (a, b, c, d, e, f, g, h, i, j, k, l, m, n) # 

Methods

eltType :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> TupleType (EltRepr (a, b, c, d, e, f, g, h, i, j, k, l, m, n))

fromElt :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> EltRepr (a, b, c, d, e, f, g, h, i, j, k, l, m, n)

toElt :: EltRepr (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n)

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k, Elt l, Elt m, Elt n, Elt o) => Elt (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) # 

Methods

eltType :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> TupleType (EltRepr (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))

fromElt :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> EltRepr (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)

toElt :: EltRepr (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)

Array shapes & indices

Operations in Accelerate take the form of collective operations over arrays of the type Array sh e. Much like the repa library, arrays in Accelerate are parameterised by a type sh which determines the dimensionality of the array and the type of each index, as well as the type of each element of the array e.

Shape types, and multidimensional array indices, are built like lists (technically; a heterogeneous snoc-list) using Z and (:.):

data Z = Z
data tail :. head = tail :. head

Here, the constructor Z corresponds to a shape with zero dimension (or a Scalar array, with one element) and is used to mark the end of the list. The constructor (:.) adds additional dimensions to the shape on the right. For example:

Z :. Int

is the type of the shape of a one-dimensional array (Vector) indexed by an Int, while:

Z :. Int :. Int

is the type of the shape of a two-dimensional array (a matrix) indexed by an Int in each dimension.

This style is used to construct both the type and value of the shape. For example, to define the shape of a vector of ten elements:

sh :: Z :. Int
sh = Z :. 10

Note that the right-most index is the innermost dimension. This is the fastest-varying index, and corresponds to the elements of the array which are adjacent in memory.

data Z #

Rank-0 index

Constructors

Z 

Instances

Eq Z # 

Methods

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

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

Show Z # 

Methods

showsPrec :: Int -> Z -> ShowS #

show :: Z -> String #

showList :: [Z] -> ShowS #

Slice Z # 

Associated Types

type SliceShape Z :: * #

type CoSliceShape Z :: * #

type FullShape Z :: * #

Methods

sliceIndex :: Z -> SliceIndex (EltRepr Z) (EltRepr (SliceShape Z)) (EltRepr (CoSliceShape Z)) (EltRepr (FullShape Z)) #

Shape Z # 

Methods

rank :: Z -> Int

size :: Z -> Int

empty :: Z

ignore :: Z

intersect :: Z -> Z -> Z

union :: Z -> Z -> Z

toIndex :: Z -> Z -> Int

fromIndex :: Z -> Int -> Z

bound :: Z -> Z -> Boundary a -> Either a Z

iter :: Z -> (Z -> a) -> (a -> a -> a) -> a -> a

iter1 :: Z -> (Z -> a) -> (a -> a -> a) -> a

rangeToShape :: (Z, Z) -> Z

shapeToRange :: Z -> (Z, Z)

shapeToList :: Z -> [Int]

listToShape :: [Int] -> Z

sliceAnyIndex :: Z -> SliceIndex (EltRepr (Any Z)) (EltRepr Z) () (EltRepr Z)

sliceNoneIndex :: Z -> SliceIndex (EltRepr Z) () (EltRepr Z) (EltRepr Z)

Elt Z # 

Methods

eltType :: Z -> TupleType (EltRepr Z)

fromElt :: Z -> EltRepr Z

toElt :: EltRepr Z -> Z

Unlift Exp Z # 

Methods

unlift :: Exp (Plain Z) -> Z #

Lift Exp Z # 

Associated Types

type Plain Z :: * #

Methods

lift :: Z -> Exp (Plain Z) #

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e)

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e, Exp e, Exp e)

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)

Elt e => IsList (Vector e) # 

Associated Types

type Item (Vector e) :: * #

Methods

fromList :: [Item (Vector e)] -> Vector e #

fromListN :: Int -> [Item (Vector e)] -> Vector e #

toList :: Vector e -> [Item (Vector e)] #

Show (Vector e) # 

Methods

showsPrec :: Int -> Vector e -> ShowS #

show :: Vector e -> String #

showList :: [Vector e] -> ShowS #

Show (Scalar e) # 

Methods

showsPrec :: Int -> Scalar e -> ShowS #

show :: Scalar e -> String #

showList :: [Scalar e] -> ShowS #

Elt (Any Z) # 

Methods

eltType :: Any Z -> TupleType (EltRepr (Any Z))

fromElt :: Any Z -> EltRepr (Any Z)

toElt :: EltRepr (Any Z) -> Any Z

Show (Array DIM2 e) # 

Methods

showsPrec :: Int -> Array DIM2 e -> ShowS #

show :: Array DIM2 e -> String #

showList :: [Array DIM2 e] -> ShowS #

type SliceShape Z # 
type SliceShape Z = Z
type CoSliceShape Z # 
type FullShape Z # 
type FullShape Z = Z
type Plain Z # 
type Plain Z = Z
type Item (Vector e) # 
type Item (Vector e) = e

data tail :. head infixl 3 #

Increase an index rank by one dimension. The :. operator is used to construct both values and types.

Constructors

tail :. head infixl 3 

Instances

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e)

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e, Exp e, Exp e)

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)

(Elt e, Slice (Plain ix), Unlift Exp ix) => Unlift Exp ((:.) ix (Exp e)) # 

Methods

unlift :: Exp (Plain (ix :. Exp e)) -> ix :. Exp e #

(Elt e, Slice ix) => Unlift Exp ((:.) (Exp ix) (Exp e)) # 

Methods

unlift :: Exp (Plain (Exp ix :. Exp e)) -> Exp ix :. Exp e #

(Elt e, Slice (Plain ix), Lift Exp ix) => Lift Exp ((:.) ix (Exp e)) # 

Associated Types

type Plain ((:.) ix (Exp e)) :: * #

Methods

lift :: (ix :. Exp e) -> Exp (Plain (ix :. Exp e)) #

(Slice (Plain ix), Lift Exp ix) => Lift Exp ((:.) ix All) # 

Associated Types

type Plain ((:.) ix All) :: * #

Methods

lift :: (ix :. All) -> Exp (Plain (ix :. All)) #

(Slice (Plain ix), Lift Exp ix) => Lift Exp ((:.) ix Int) # 

Associated Types

type Plain ((:.) ix Int) :: * #

Methods

lift :: (ix :. Int) -> Exp (Plain (ix :. Int)) #

Elt e => IsList (Vector e) # 

Associated Types

type Item (Vector e) :: * #

Methods

fromList :: [Item (Vector e)] -> Vector e #

fromListN :: Int -> [Item (Vector e)] -> Vector e #

toList :: Vector e -> [Item (Vector e)] #

Show (Vector e) # 

Methods

showsPrec :: Int -> Vector e -> ShowS #

show :: Vector e -> String #

showList :: [Vector e] -> ShowS #

Shape sh => Elt (Any ((:.) sh Int)) # 

Methods

eltType :: Any (sh :. Int) -> TupleType (EltRepr (Any (sh :. Int)))

fromElt :: Any (sh :. Int) -> EltRepr (Any (sh :. Int))

toElt :: EltRepr (Any (sh :. Int)) -> Any (sh :. Int)

(Eq head, Eq tail) => Eq ((:.) tail head) # 

Methods

(==) :: (tail :. head) -> (tail :. head) -> Bool #

(/=) :: (tail :. head) -> (tail :. head) -> Bool #

Show (Array DIM2 e) # 

Methods

showsPrec :: Int -> Array DIM2 e -> ShowS #

show :: Array DIM2 e -> String #

showList :: [Array DIM2 e] -> ShowS #

(Show sh, Show sz) => Show ((:.) sh sz) # 

Methods

showsPrec :: Int -> (sh :. sz) -> ShowS #

show :: (sh :. sz) -> String #

showList :: [sh :. sz] -> ShowS #

Slice sl => Slice ((:.) sl Int) # 

Associated Types

type SliceShape ((:.) sl Int) :: * #

type CoSliceShape ((:.) sl Int) :: * #

type FullShape ((:.) sl Int) :: * #

Methods

sliceIndex :: (sl :. Int) -> SliceIndex (EltRepr (sl :. Int)) (EltRepr (SliceShape (sl :. Int))) (EltRepr (CoSliceShape (sl :. Int))) (EltRepr (FullShape (sl :. Int))) #

Slice sl => Slice ((:.) sl All) # 

Associated Types

type SliceShape ((:.) sl All) :: * #

type CoSliceShape ((:.) sl All) :: * #

type FullShape ((:.) sl All) :: * #

Methods

sliceIndex :: (sl :. All) -> SliceIndex (EltRepr (sl :. All)) (EltRepr (SliceShape (sl :. All))) (EltRepr (CoSliceShape (sl :. All))) (EltRepr (FullShape (sl :. All))) #

Shape sh => Shape ((:.) sh Int) # 

Methods

rank :: (sh :. Int) -> Int

size :: (sh :. Int) -> Int

empty :: sh :. Int

ignore :: sh :. Int

intersect :: (sh :. Int) -> (sh :. Int) -> sh :. Int

union :: (sh :. Int) -> (sh :. Int) -> sh :. Int

toIndex :: (sh :. Int) -> (sh :. Int) -> Int

fromIndex :: (sh :. Int) -> Int -> sh :. Int

bound :: (sh :. Int) -> (sh :. Int) -> Boundary a -> Either a (sh :. Int)

iter :: (sh :. Int) -> ((sh :. Int) -> a) -> (a -> a -> a) -> a -> a

iter1 :: (sh :. Int) -> ((sh :. Int) -> a) -> (a -> a -> a) -> a

rangeToShape :: (sh :. Int, sh :. Int) -> sh :. Int

shapeToRange :: (sh :. Int) -> (sh :. Int, sh :. Int)

shapeToList :: (sh :. Int) -> [Int]

listToShape :: [Int] -> sh :. Int

sliceAnyIndex :: (sh :. Int) -> SliceIndex (EltRepr (Any (sh :. Int))) (EltRepr (sh :. Int)) () (EltRepr (sh :. Int))

sliceNoneIndex :: (sh :. Int) -> SliceIndex (EltRepr (sh :. Int)) () (EltRepr (sh :. Int)) (EltRepr (sh :. Int))

(Elt t, Elt h) => Elt ((:.) t h) # 

Methods

eltType :: (t :. h) -> TupleType (EltRepr (t :. h))

fromElt :: (t :. h) -> EltRepr (t :. h)

toElt :: EltRepr (t :. h) -> t :. h

(Stencil ((:.) sh Int) a row2, Stencil ((:.) sh Int) a row1, Stencil ((:.) sh Int) a row0) => Stencil ((:.) ((:.) sh Int) Int) a (row2, row1, row0) # 

Associated Types

type StencilRepr ((:.) ((:.) sh Int) Int) (row2, row1, row0) :: *

Methods

stencilPrj :: ((sh :. Int) :. Int) -> a -> Exp (StencilRepr ((sh :. Int) :. Int) (row2, row1, row0)) -> (row2, row1, row0)

(Stencil ((:.) sh Int) a row1, Stencil ((:.) sh Int) a row2, Stencil ((:.) sh Int) a row3, Stencil ((:.) sh Int) a row4, Stencil ((:.) sh Int) a row5) => Stencil ((:.) ((:.) sh Int) Int) a (row1, row2, row3, row4, row5) # 

Associated Types

type StencilRepr ((:.) ((:.) sh Int) Int) (row1, row2, row3, row4, row5) :: *

Methods

stencilPrj :: ((sh :. Int) :. Int) -> a -> Exp (StencilRepr ((sh :. Int) :. Int) (row1, row2, row3, row4, row5)) -> (row1, row2, row3, row4, row5)

(Stencil ((:.) sh Int) a row1, Stencil ((:.) sh Int) a row2, Stencil ((:.) sh Int) a row3, Stencil ((:.) sh Int) a row4, Stencil ((:.) sh Int) a row5, Stencil ((:.) sh Int) a row6, Stencil ((:.) sh Int) a row7) => Stencil ((:.) ((:.) sh Int) Int) a (row1, row2, row3, row4, row5, row6, row7) # 

Associated Types

type StencilRepr ((:.) ((:.) sh Int) Int) (row1, row2, row3, row4, row5, row6, row7) :: *

Methods

stencilPrj :: ((sh :. Int) :. Int) -> a -> Exp (StencilRepr ((sh :. Int) :. Int) (row1, row2, row3, row4, row5, row6, row7)) -> (row1, row2, row3, row4, row5, row6, row7)

(Stencil ((:.) sh Int) a row1, Stencil ((:.) sh Int) a row2, Stencil ((:.) sh Int) a row3, Stencil ((:.) sh Int) a row4, Stencil ((:.) sh Int) a row5, Stencil ((:.) sh Int) a row6, Stencil ((:.) sh Int) a row7, Stencil ((:.) sh Int) a row8, Stencil ((:.) sh Int) a row9) => Stencil ((:.) ((:.) sh Int) Int) a (row1, row2, row3, row4, row5, row6, row7, row8, row9) # 

Associated Types

type StencilRepr ((:.) ((:.) sh Int) Int) (row1, row2, row3, row4, row5, row6, row7, row8, row9) :: *

Methods

stencilPrj :: ((sh :. Int) :. Int) -> a -> Exp (StencilRepr ((sh :. Int) :. Int) (row1, row2, row3, row4, row5, row6, row7, row8, row9)) -> (row1, row2, row3, row4, row5, row6, row7, row8, row9)

type Item (Vector e) # 
type Item (Vector e) = e
type SliceShape ((:.) sl Int) # 
type SliceShape ((:.) sl Int) = SliceShape sl
type SliceShape ((:.) sl All) # 
type CoSliceShape ((:.) sl Int) # 
type CoSliceShape ((:.) sl All) # 
type FullShape ((:.) sl Int) # 
type FullShape ((:.) sl Int) = (:.) (FullShape sl) Int
type FullShape ((:.) sl All) # 
type FullShape ((:.) sl All) = (:.) (FullShape sl) Int
type Plain ((:.) ix (Exp e)) # 
type Plain ((:.) ix (Exp e)) = (:.) (Plain ix) e
type Plain ((:.) ix All) # 
type Plain ((:.) ix All) = (:.) (Plain ix) All
type Plain ((:.) ix Int) # 
type Plain ((:.) ix Int) = (:.) (Plain ix) Int

type DIM0 = Z #

type DIM1 = DIM0 :. Int #

type DIM2 = DIM1 :. Int #

type DIM3 = DIM2 :. Int #

type DIM4 = DIM3 :. Int #

type DIM5 = DIM4 :. Int #

type DIM6 = DIM5 :. Int #

type DIM7 = DIM6 :. Int #

type DIM8 = DIM7 :. Int #

type DIM9 = DIM8 :. Int #

class (Elt sh, Elt (Any sh), Shape (EltRepr sh), FullShape sh ~ sh, CoSliceShape sh ~ sh, SliceShape sh ~ Z) => Shape sh #

Shapes and indices of multi-dimensional arrays

Minimal complete definition

sliceAnyIndex, sliceNoneIndex

Instances

Shape Z # 

Methods

rank :: Z -> Int

size :: Z -> Int

empty :: Z

ignore :: Z

intersect :: Z -> Z -> Z

union :: Z -> Z -> Z

toIndex :: Z -> Z -> Int

fromIndex :: Z -> Int -> Z

bound :: Z -> Z -> Boundary a -> Either a Z

iter :: Z -> (Z -> a) -> (a -> a -> a) -> a -> a

iter1 :: Z -> (Z -> a) -> (a -> a -> a) -> a

rangeToShape :: (Z, Z) -> Z

shapeToRange :: Z -> (Z, Z)

shapeToList :: Z -> [Int]

listToShape :: [Int] -> Z

sliceAnyIndex :: Z -> SliceIndex (EltRepr (Any Z)) (EltRepr Z) () (EltRepr Z)

sliceNoneIndex :: Z -> SliceIndex (EltRepr Z) () (EltRepr Z) (EltRepr Z)

Shape sh => Shape ((:.) sh Int) # 

Methods

rank :: (sh :. Int) -> Int

size :: (sh :. Int) -> Int

empty :: sh :. Int

ignore :: sh :. Int

intersect :: (sh :. Int) -> (sh :. Int) -> sh :. Int

union :: (sh :. Int) -> (sh :. Int) -> sh :. Int

toIndex :: (sh :. Int) -> (sh :. Int) -> Int

fromIndex :: (sh :. Int) -> Int -> sh :. Int

bound :: (sh :. Int) -> (sh :. Int) -> Boundary a -> Either a (sh :. Int)

iter :: (sh :. Int) -> ((sh :. Int) -> a) -> (a -> a -> a) -> a -> a

iter1 :: (sh :. Int) -> ((sh :. Int) -> a) -> (a -> a -> a) -> a

rangeToShape :: (sh :. Int, sh :. Int) -> sh :. Int

shapeToRange :: (sh :. Int) -> (sh :. Int, sh :. Int)

shapeToList :: (sh :. Int) -> [Int]

listToShape :: [Int] -> sh :. Int

sliceAnyIndex :: (sh :. Int) -> SliceIndex (EltRepr (Any (sh :. Int))) (EltRepr (sh :. Int)) () (EltRepr (sh :. Int))

sliceNoneIndex :: (sh :. Int) -> SliceIndex (EltRepr (sh :. Int)) () (EltRepr (sh :. Int)) (EltRepr (sh :. Int))

class (Elt sl, Shape (SliceShape sl), Shape (CoSliceShape sl), Shape (FullShape sl)) => Slice sl where #

Slices, aka generalised indices, as n-tuples and mappings of slice indices to slices, co-slices, and slice dimensions

Minimal complete definition

sliceIndex

Associated Types

type SliceShape sl :: * #

type CoSliceShape sl :: * #

type FullShape sl :: * #

Methods

sliceIndex :: sl -> SliceIndex (EltRepr sl) (EltRepr (SliceShape sl)) (EltRepr (CoSliceShape sl)) (EltRepr (FullShape sl)) #

Instances

Slice Z # 

Associated Types

type SliceShape Z :: * #

type CoSliceShape Z :: * #

type FullShape Z :: * #

Methods

sliceIndex :: Z -> SliceIndex (EltRepr Z) (EltRepr (SliceShape Z)) (EltRepr (CoSliceShape Z)) (EltRepr (FullShape Z)) #

Shape sh => Slice (Any sh) # 

Associated Types

type SliceShape (Any sh) :: * #

type CoSliceShape (Any sh) :: * #

type FullShape (Any sh) :: * #

Methods

sliceIndex :: Any sh -> SliceIndex (EltRepr (Any sh)) (EltRepr (SliceShape (Any sh))) (EltRepr (CoSliceShape (Any sh))) (EltRepr (FullShape (Any sh))) #

Slice sl => Slice ((:.) sl Int) # 

Associated Types

type SliceShape ((:.) sl Int) :: * #

type CoSliceShape ((:.) sl Int) :: * #

type FullShape ((:.) sl Int) :: * #

Methods

sliceIndex :: (sl :. Int) -> SliceIndex (EltRepr (sl :. Int)) (EltRepr (SliceShape (sl :. Int))) (EltRepr (CoSliceShape (sl :. Int))) (EltRepr (FullShape (sl :. Int))) #

Slice sl => Slice ((:.) sl All) # 

Associated Types

type SliceShape ((:.) sl All) :: * #

type CoSliceShape ((:.) sl All) :: * #

type FullShape ((:.) sl All) :: * #

Methods

sliceIndex :: (sl :. All) -> SliceIndex (EltRepr (sl :. All)) (EltRepr (SliceShape (sl :. All))) (EltRepr (CoSliceShape (sl :. All))) (EltRepr (FullShape (sl :. All))) #

data All #

Marker for entire dimensions in slice and replicate descriptors.

Occurrences of All indicate the dimensions into which the array's existing extent will be placed unchanged.

See slice and replicate for examples.

Constructors

All 

Instances

Eq All # 

Methods

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

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

Show All # 

Methods

showsPrec :: Int -> All -> ShowS #

show :: All -> String #

showList :: [All] -> ShowS #

Elt All # 

Methods

eltType :: All -> TupleType (EltRepr All)

fromElt :: All -> EltRepr All

toElt :: EltRepr All -> All

(Slice (Plain ix), Lift Exp ix) => Lift Exp ((:.) ix All) # 

Associated Types

type Plain ((:.) ix All) :: * #

Methods

lift :: (ix :. All) -> Exp (Plain (ix :. All)) #

Slice sl => Slice ((:.) sl All) # 

Associated Types

type SliceShape ((:.) sl All) :: * #

type CoSliceShape ((:.) sl All) :: * #

type FullShape ((:.) sl All) :: * #

Methods

sliceIndex :: (sl :. All) -> SliceIndex (EltRepr (sl :. All)) (EltRepr (SliceShape (sl :. All))) (EltRepr (CoSliceShape (sl :. All))) (EltRepr (FullShape (sl :. All))) #

type SliceShape ((:.) sl All) # 
type CoSliceShape ((:.) sl All) # 
type FullShape ((:.) sl All) # 
type FullShape ((:.) sl All) = (:.) (FullShape sl) Int
type Plain ((:.) ix All) # 
type Plain ((:.) ix All) = (:.) (Plain ix) All

data Any sh #

Marker for arbitrary dimensions in slice and replicate descriptors.

Any can be used in the leftmost position of a slice instead of Z, indicating that any dimensionality is admissible in that position.

See slice and replicate for examples.

Constructors

Any 

Instances

Shape sh => Lift Exp (Any sh) # 

Associated Types

type Plain (Any sh) :: * #

Methods

lift :: Any sh -> Exp (Plain (Any sh)) #

Eq (Any sh) # 

Methods

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

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

Show (Any sh) # 

Methods

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

show :: Any sh -> String #

showList :: [Any sh] -> ShowS #

Shape sh => Slice (Any sh) # 

Associated Types

type SliceShape (Any sh) :: * #

type CoSliceShape (Any sh) :: * #

type FullShape (Any sh) :: * #

Methods

sliceIndex :: Any sh -> SliceIndex (EltRepr (Any sh)) (EltRepr (SliceShape (Any sh))) (EltRepr (CoSliceShape (Any sh))) (EltRepr (FullShape (Any sh))) #

Shape sh => Elt (Any ((:.) sh Int)) # 

Methods

eltType :: Any (sh :. Int) -> TupleType (EltRepr (Any (sh :. Int)))

fromElt :: Any (sh :. Int) -> EltRepr (Any (sh :. Int))

toElt :: EltRepr (Any (sh :. Int)) -> Any (sh :. Int)

Elt (Any Z) # 

Methods

eltType :: Any Z -> TupleType (EltRepr (Any Z))

fromElt :: Any Z -> EltRepr (Any Z)

toElt :: EltRepr (Any Z) -> Any Z

type SliceShape (Any sh) # 
type SliceShape (Any sh) = sh
type CoSliceShape (Any sh) # 
type CoSliceShape (Any sh) = Z
type FullShape (Any sh) # 
type FullShape (Any sh) = sh
type Plain (Any sh) # 
type Plain (Any sh) = Any sh

Array access

Element indexing

(!) :: (Shape sh, Elt e) => Acc (Array sh e) -> Exp sh -> Exp e infixl 9 #

Multidimensional array indexing. Extract the value from an array at the specified zero-based index.

>>> let mat = fromList (Z:.5:.10) [0..]
>>> mat
Matrix (Z :. 5 :. 10)
  [  0,  1,  2,  3,  4,  5,  6,  7,  8,  9,
    10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
    20, 21, 22, 23, 24, 25, 26, 27, 28, 29,
    30, 31, 32, 33, 34, 35, 36, 37, 38, 39,
    40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>> mat ! Z:.1:.2
12

(!!) :: (Shape sh, Elt e) => Acc (Array sh e) -> Exp Int -> Exp e infixl 9 #

Extract the value from an array at the specified linear index. Multidimensional arrays in Accelerate are stored in row-major order with zero-based indexing.

>>> let mat = fromList (Z:.5:.10) [0..]
>>> mat
Matrix (Z :. 5 :. 10)
  [  0,  1,  2,  3,  4,  5,  6,  7,  8,  9,
    10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
    20, 21, 22, 23, 24, 25, 26, 27, 28, 29,
    30, 31, 32, 33, 34, 35, 36, 37, 38, 39,
    40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>> mat !! 12
12

the :: Elt e => Acc (Scalar e) -> Exp e #

Extract the element of a singleton array.

the xs  ==  xs ! Z

Shape information

null :: (Shape sh, Elt e) => Acc (Array sh e) -> Exp Bool #

Test whether an array is empty.

length :: Elt e => Acc (Vector e) -> Exp Int #

Get the length of a vector.

shape :: (Shape sh, Elt e) => Acc (Array sh e) -> Exp sh #

Extract the shape (extent) of an array.

size :: (Shape sh, Elt e) => Acc (Array sh e) -> Exp Int #

The number of elements in the array

shapeSize :: Shape sh => Exp sh -> Exp Int #

The number of elements that would be held by an array of the given shape.

Construction

Introduction

use :: Arrays arrays => arrays -> Acc arrays #

Make an array from vanilla Haskell available for processing within embedded Accelerate computations.

Depending upon which backend is used to eventually execute array computations, use may entail data transfer (e.g. to a GPU).

use is overloaded so that it can accept tuples of Arrays:

>>> let vec = fromList (Z:.10) [0..]  :: Array DIM1 Int
Vector (Z :. 10) [0,1,2,3,4,5,6,7,8,9]
>>> let mat = fromList (Z:.5:.10) [0..]  :: Array DIM2 Int
>>> mat
Matrix (Z :. 5 :. 10)
  [  0,  1,  2,  3,  4,  5,  6,  7,  8,  9,
    10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
    20, 21, 22, 23, 24, 25, 26, 27, 28, 29,
    30, 31, 32, 33, 34, 35, 36, 37, 38, 39,
    40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>> let vec' = use vec         :: Acc (Array DIM1 Int)
>>> let mat' = use mat         :: Acc (Array DIM2 Int)
>>> let tup  = use (vec, mat)  :: Acc (Array DIM1 Int, Array DIM2 Int)

unit :: Elt e => Exp e -> Acc (Scalar e) #

Construct a singleton (one element) array from a scalar value (or tuple of scalar values).

Initialisation

generate :: (Shape sh, Elt a) => Exp sh -> (Exp sh -> Exp a) -> Acc (Array sh a) #

Construct a new array by applying a function to each index.

For example, the following will generate a one-dimensional array (Vector) of three floating point numbers:

>>> generate (index1 3) (\_ -> 1.2)
Vector (Z :. 3) [1.2,1.2,1.2]

Or equivalently:

>>> fill (constant (Z :. 3)) 1.2
Vector (Z :. 3) [1.2,1.2,1.2]

The following will create a vector with the elements [1..10]:

>>> generate (index1 10) (\ix -> unindex1 ix + 1)
Vector (Z :. 10) [1,2,3,4,5,6,7,8,9,10]
NOTE:

Using generate, it is possible to introduce nested data parallelism, which will cause the program to fail.

If the index given by the scalar function is then used to dispatch further parallel work, whose result is returned into Exp terms by array indexing operations such as (!) or the, the program will fail with the error: './Data/Array/Accelerate/Trafo/Sharing.hs:447 (convertSharingExp): inconsistent valuation @ shared 'Exp' tree ...'.

fill :: (Shape sh, Elt e) => Exp sh -> Exp e -> Acc (Array sh e) #

Create an array where all elements are the same value.

Enumeration

enumFromN :: (Shape sh, Num e, FromIntegral Int e) => Exp sh -> Exp e -> Acc (Array sh e) #

Create an array of the given shape containing the values x, x+1, etc. (in row-major order).

>>> enumFromN (constant (Z:.5:.10)) 0 :: Array DIM2 Int
Matrix (Z :. 5 :. 10)
  [  0,  1,  2,  3,  4,  5,  6,  7,  8,  9,
    10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
    20, 21, 22, 23, 24, 25, 26, 27, 28, 29,
    30, 31, 32, 33, 34, 35, 36, 37, 38, 39,
    40, 41, 42, 43, 44, 45, 46, 47, 48, 49]

enumFromStepN #

Arguments

:: (Shape sh, Num e, FromIntegral Int e) 
=> Exp sh 
-> Exp e

x: start

-> Exp e

y: step

-> Acc (Array sh e) 

Create an array of the given shape containing the values x, x+y, x+y+y etc. (in row-major order).

>>> enumFromStepN (constant (Z:.5:.10)) 0 0.5 :: Array DIM2 Float
Matrix (Z :. 5 :. 10)
  [  0.0,  0.5,  1.0,  1.5,  2.0,  2.5,  3.0,  3.5,  4.0,  4.5,
     5.0,  5.5,  6.0,  6.5,  7.0,  7.5,  8.0,  8.5,  9.0,  9.5,
    10.0, 10.5, 11.0, 11.5, 12.0, 12.5, 13.0, 13.5, 14.0, 14.5,
    15.0, 15.5, 16.0, 16.5, 17.0, 17.5, 18.0, 18.5, 19.0, 19.5,
    20.0, 20.5, 21.0, 21.5, 22.0, 22.5, 23.0, 23.5, 24.0, 24.5]

Concatenation

(++) :: forall sh e. (Slice sh, Shape sh, Elt e) => Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e) infixr 5 #

Concatenate innermost component of two arrays. The extent of the lower dimensional component is the intersection of the two arrays.

>>> let m1 = fromList (Z:.5:.10) [0..]
>>> m1
Matrix (Z :. 5 :. 10)
  [  0,  1,  2,  3,  4,  5,  6,  7,  8,  9,
    10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
    20, 21, 22, 23, 24, 25, 26, 27, 28, 29,
    30, 31, 32, 33, 34, 35, 36, 37, 38, 39,
    40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>> let m2 = fromList (Z:.10:.3) [0..]
>>> m2
Matrix (Z :. 10 :. 3)
  [  0,  1,  2,
     3,  4,  5,
     6,  7,  8,
     9, 10, 11,
    12, 13, 14,
    15, 16, 17,
    18, 19, 20,
    21, 22, 23,
    24, 25, 26,
    27, 28, 29]
>>> use m1 ++ use m2
Matrix (Z :. 5 :. 13)
  [  0,  1,  2,  3,  4,  5,  6,  7,  8,  9,  0,  1,  2,
    10, 11, 12, 13, 14, 15, 16, 17, 18, 19,  3,  4,  5,
    20, 21, 22, 23, 24, 25, 26, 27, 28, 29,  6,  7,  8,
    30, 31, 32, 33, 34, 35, 36, 37, 38, 39,  9, 10, 11,
    40, 41, 42, 43, 44, 45, 46, 47, 48, 49, 12, 13, 14]

Composition

Flow control

(?|) :: Arrays a => Exp Bool -> (Acc a, Acc a) -> Acc a infix 0 #

Infix version of acond. If the predicate evaluates to True, the first component of the tuple is returned, else the second.

See also: ifThenElse.

acond #

Arguments

:: Arrays a 
=> Exp Bool

if-condition

-> Acc a

then-array

-> Acc a

else-array

-> Acc a 

An array-level if-then-else construct.

awhile #

Arguments

:: Arrays a 
=> (Acc a -> Acc (Scalar Bool))

keep evaluating while this returns True

-> (Acc a -> Acc a)

function to apply

-> Acc a

initial value

-> Acc a 

An array-level while construct. Continue to apply the given function, starting with the initial value, until the test function evaluates to False.

class IfThenElse t where #

For use with -XRebindableSyntax, this class provides ifThenElse lifted to both scalar and array types.

Minimal complete definition

ifThenElse

Associated Types

type EltT t a :: Constraint #

Methods

ifThenElse :: EltT t a => Exp Bool -> t a -> t a -> t a #

Instances

IfThenElse Exp # 

Associated Types

type EltT (Exp :: * -> *) a :: Constraint #

Methods

ifThenElse :: EltT Exp a => Exp Bool -> Exp a -> Exp a -> Exp a #

IfThenElse Acc # 

Associated Types

type EltT (Acc :: * -> *) a :: Constraint #

Methods

ifThenElse :: EltT Acc a => Exp Bool -> Acc a -> Acc a -> Acc a #

Controlling execution

(>->) :: (Arrays a, Arrays b, Arrays c) => (Acc a -> Acc b) -> (Acc b -> Acc c) -> Acc a -> Acc c infixl 1 #

Pipelining of two array computations. The first argument will be fully evaluated before being passed to the second computation. This can be used to prevent the argument being fused into the function, for example.

Denotationally, we have

(acc1 >-> acc2) arrs = let tmp = acc1 arrs
                       in  tmp `seq` acc2 tmp

compute :: Arrays a => Acc a -> Acc a #

Force an array expression to be evaluated, preventing it from fusing with other operations. Forcing operations to be computed to memory, rather than being fused into their consuming function, can sometimes improve performance. For example, computing a matrix transpose could provide better memory locality for the subsequent operation. Preventing fusion to split large operations into several simpler steps could also help by reducing register pressure.

Preventing fusion also means that the individual operations are available to be executed concurrently with other kernels. In particular, consider using this if you have a series of operations that are compute bound rather than memory bound.

Here is the synthetic example:

loop :: Exp Int -> Exp Int
loop ticks =
  let clockRate = 900000   -- kHz
  in  while (\i -> i < clockRate * ticks) (+1) 0

test :: Acc (Vector Int)
test =
  zip3
    (compute $ map loop (use $ fromList (Z:.1) [10]))
    (compute $ map loop (use $ fromList (Z:.1) [10]))
    (compute $ map loop (use $ fromList (Z:.1) [10]))

Without the use of compute, the operations are fused together and the three long-running loops are executed sequentially in a single kernel. Instead, the individual operations can now be executed concurrently, potentially reducing overall runtime.

Element-wise operations

Indexing

indexed :: (Shape sh, Elt a) => Acc (Array sh a) -> Acc (Array sh (sh, a)) #

Pair each element with its index

Mapping

map :: (Shape sh, Elt a, Elt b) => (Exp a -> Exp b) -> Acc (Array sh a) -> Acc (Array sh b) #

Apply the given function element-wise to an array.

map f [x1, x2, ... xn] = [f x1, f x2, ... f xn]

imap :: (Shape sh, Elt a, Elt b) => (Exp sh -> Exp a -> Exp b) -> Acc (Array sh a) -> Acc (Array sh b) #

Apply a function to every element of an array and its index

Zipping

zipWith :: (Shape sh, Elt a, Elt b, Elt c) => (Exp a -> Exp b -> Exp c) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) #

Apply the given binary function element-wise to the two arrays. The extent of the resulting array is the intersection of the extents of the two source arrays.

zipWith3 :: (Shape sh, Elt a, Elt b, Elt c, Elt d) => (Exp a -> Exp b -> Exp c -> Exp d) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) #

Zip three arrays with the given function, analogous to zipWith.

zipWith4 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e) => (Exp a -> Exp b -> Exp c -> Exp d -> Exp e) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) #

Zip four arrays with the given function, analogous to zipWith.

zipWith5 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => (Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) #

Zip five arrays with the given function, analogous to zipWith.

zipWith6 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g) => (Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) #

Zip six arrays with the given function, analogous to zipWith.

zipWith7 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => (Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g -> Exp h) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h) #

Zip seven arrays with the given function, analogous to zipWith.

zipWith8 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => (Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g -> Exp h -> Exp i) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h) -> Acc (Array sh i) #

Zip eight arrays with the given function, analogous to zipWith.

zipWith9 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j) => (Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g -> Exp h -> Exp i -> Exp j) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h) -> Acc (Array sh i) -> Acc (Array sh j) #

Zip nine arrays with the given function, analogous to zipWith.

izipWith :: (Shape sh, Elt a, Elt b, Elt c) => (Exp sh -> Exp a -> Exp b -> Exp c) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) #

Zip two arrays with a function that also takes the element index

izipWith3 :: (Shape sh, Elt a, Elt b, Elt c, Elt d) => (Exp sh -> Exp a -> Exp b -> Exp c -> Exp d) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) #

Zip three arrays with a function that also takes the element index, analogous to izipWith.

izipWith4 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e) => (Exp sh -> Exp a -> Exp b -> Exp c -> Exp d -> Exp e) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) #

Zip four arrays with the given function that also takes the element index, analogous to zipWith.

izipWith5 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => (Exp sh -> Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) #

Zip five arrays with the given function that also takes the element index, analogous to zipWith.

izipWith6 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g) => (Exp sh -> Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) #

Zip six arrays with the given function that also takes the element index, analogous to zipWith.

izipWith7 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => (Exp sh -> Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g -> Exp h) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h) #

Zip seven arrays with the given function that also takes the element index, analogous to zipWith.

izipWith8 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => (Exp sh -> Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g -> Exp h -> Exp i) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h) -> Acc (Array sh i) #

Zip eight arrays with the given function that also takes the element index, analogous to zipWith.

izipWith9 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j) => (Exp sh -> Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g -> Exp h -> Exp i -> Exp j) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h) -> Acc (Array sh i) -> Acc (Array sh j) #

Zip nine arrays with the given function that also takes the element index, analogous to zipWith.

zip :: (Shape sh, Elt a, Elt b) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh (a, b)) #

Combine the elements of two arrays pairwise. The shape of the result is the intersection of the two argument shapes.

zip3 :: (Shape sh, Elt a, Elt b, Elt c) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh (a, b, c)) #

Take three arrays and return an array of triples, analogous to zip.

zip4 :: (Shape sh, Elt a, Elt b, Elt c, Elt d) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh (a, b, c, d)) #

Take four arrays and return an array of quadruples, analogous to zip.

zip5 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh (a, b, c, d, e)) #

Take five arrays and return an array of five-tuples, analogous to zip.

zip6 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh (a, b, c, d, e, f)) #

Take six arrays and return an array of six-tuples, analogous to zip.

zip7 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh (a, b, c, d, e, f, g)) #

Take seven arrays and return an array of seven-tuples, analogous to zip.

zip8 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h) -> Acc (Array sh (a, b, c, d, e, f, g, h)) #

Take seven arrays and return an array of seven-tuples, analogous to zip.

zip9 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h) -> Acc (Array sh i) -> Acc (Array sh (a, b, c, d, e, f, g, h, i)) #

Take seven arrays and return an array of seven-tuples, analogous to zip.

Unzipping

unzip :: (Shape sh, Elt a, Elt b) => Acc (Array sh (a, b)) -> (Acc (Array sh a), Acc (Array sh b)) #

The converse of zip, but the shape of the two results is identical to the shape of the argument.

If the argument array is manifest in memory, unzip is a NOP.

unzip3 :: (Shape sh, Elt a, Elt b, Elt c) => Acc (Array sh (a, b, c)) -> (Acc (Array sh a), Acc (Array sh b), Acc (Array sh c)) #

Take an array of triples and return three arrays, analogous to unzip.

unzip4 :: (Shape sh, Elt a, Elt b, Elt c, Elt d) => Acc (Array sh (a, b, c, d)) -> (Acc (Array sh a), Acc (Array sh b), Acc (Array sh c), Acc (Array sh d)) #

Take an array of quadruples and return four arrays, analogous to unzip.

unzip5 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e) => Acc (Array sh (a, b, c, d, e)) -> (Acc (Array sh a), Acc (Array sh b), Acc (Array sh c), Acc (Array sh d), Acc (Array sh e)) #

Take an array of 5-tuples and return five arrays, analogous to unzip.

unzip6 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => Acc (Array sh (a, b, c, d, e, f)) -> (Acc (Array sh a), Acc (Array sh b), Acc (Array sh c), Acc (Array sh d), Acc (Array sh e), Acc (Array sh f)) #

Take an array of 6-tuples and return six arrays, analogous to unzip.

unzip7 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g) => Acc (Array sh (a, b, c, d, e, f, g)) -> (Acc (Array sh a), Acc (Array sh b), Acc (Array sh c), Acc (Array sh d), Acc (Array sh e), Acc (Array sh f), Acc (Array sh g)) #

Take an array of 7-tuples and return seven arrays, analogous to unzip.

unzip8 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => Acc (Array sh (a, b, c, d, e, f, g, h)) -> (Acc (Array sh a), Acc (Array sh b), Acc (Array sh c), Acc (Array sh d), Acc (Array sh e), Acc (Array sh f), Acc (Array sh g), Acc (Array sh h)) #

Take an array of 8-tuples and return eight arrays, analogous to unzip.

unzip9 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => Acc (Array sh (a, b, c, d, e, f, g, h, i)) -> (Acc (Array sh a), Acc (Array sh b), Acc (Array sh c), Acc (Array sh d), Acc (Array sh e), Acc (Array sh f), Acc (Array sh g), Acc (Array sh h), Acc (Array sh i)) #

Take an array of 8-tuples and return eight arrays, analogous to unzip.

Modifying Arrays

Shape manipulation

reshape :: (Shape sh, Shape sh', Elt e) => Exp sh -> Acc (Array sh' e) -> Acc (Array sh e) #

Change the shape of an array without altering its contents. The size of the source and result arrays must be identical.

precondition: shapeSize sh == shapeSize sh'

If the argument array is manifest in memory, reshape is a NOP. If the argument is to be fused into a subsequent operation, reshape corresponds to an index transformation in the fused code.

flatten :: forall sh e. (Shape sh, Elt e) => Acc (Array sh e) -> Acc (Vector e) #

Flatten the given array of arbitrary dimension into a one-dimensional vector. As with reshape, this operation performs no work.

Replication

replicate :: (Slice slix, Elt e) => Exp slix -> Acc (Array (SliceShape slix) e) -> Acc (Array (FullShape slix) e) #

Replicate an array across one or more dimensions as specified by the generalised array index provided as the first argument.

For example, given the following vector:

>>> let vec = fromList (Z:.10) [0..]
Vector (Z :. 10) [0,1,2,3,4,5,6,7,8,9]

...we can replicate these elements to form a two-dimensional array either by replicating those elements as new rows:

>>> replicate (lift (Z :. 4 :. All)) (use vec)
Matrix (Z :. 4 :. 10)
  [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9,
    0, 1, 2, 3, 4, 5, 6, 7, 8, 9,
    0, 1, 2, 3, 4, 5, 6, 7, 8, 9,
    0, 1, 2, 3, 4, 5, 6, 7, 8, 9]

...or as columns:

>>> replicate (lift (Z :. All :. 4)) (use vec)
Matrix (Z :. 10 :. 4)
  [ 0, 0, 0, 0,
    1, 1, 1, 1,
    2, 2, 2, 2,
    3, 3, 3, 3,
    4, 4, 4, 4,
    5, 5, 5, 5,
    6, 6, 6, 6,
    7, 7, 7, 7,
    8, 8, 8, 8,
    9, 9, 9, 9]

Replication along more than one dimension is also possible. Here we replicate twice across the first dimension and three times across the third dimension:

>>> replicate (lift (Z :. 2 :. All :. 3)) (use vec)
Array (Z :. 2 :. 10 :. 3) [0,0,0,1,1,1,2,2,2,3,3,3,4,4,4,5,5,5,6,6,6,7,7,7,8,8,8,9,9,9,0,0,0,1,1,1,2,2,2,3,3,3,4,4,4,5,5,5,6,6,6,7,7,7,8,8,8,9,9,9]

The marker Any can be used in the slice specification to match against some arbitrary dimension. For example, here Any matches against whatever shape type variable sh takes.

rep0 :: (Shape sh, Elt e) => Exp Int -> Acc (Array sh e) -> Acc (Array (sh :. Int) e)
rep0 n a = replicate (lift (Any :. n)) a
>>> let x = unit 42  :: Acc (Scalar Int)
>>> rep0 10 x
Vector (Z :. 10) [42,42,42,42,42,42,42,42,42,42]
>>> rep0 5 (use vec)
Matrix (Z :. 10 :. 5)
  [ 0, 0, 0, 0, 0,
    1, 1, 1, 1, 1,
    2, 2, 2, 2, 2,
    3, 3, 3, 3, 3,
    4, 4, 4, 4, 4,
    5, 5, 5, 5, 5,
    6, 6, 6, 6, 6,
    7, 7, 7, 7, 7,
    8, 8, 8, 8, 8,
    9, 9, 9, 9, 9]

Of course, Any and All can be used together.

rep1 :: (Shape sh, Elt e) => Exp Int -> Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int :. Int) e)
rep1 n a = A.replicate (lift (Any :. n :. All)) a
>>> rep1 5 (use vec)
Matrix (Z :. 5 :. 10)
  [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9,
    0, 1, 2, 3, 4, 5, 6, 7, 8, 9,
    0, 1, 2, 3, 4, 5, 6, 7, 8, 9,
    0, 1, 2, 3, 4, 5, 6, 7, 8, 9,
    0, 1, 2, 3, 4, 5, 6, 7, 8, 9]

Extracting sub-arrays

slice :: (Slice slix, Elt e) => Acc (Array (FullShape slix) e) -> Exp slix -> Acc (Array (SliceShape slix) e) #

Index an array with a generalised array index, supplied as the second argument. The result is a new array (possibly a singleton) containing the selected dimensions (Alls) in their entirety.

slice is the opposite of replicate, and can be used to cut out entire dimensions. For example, for the two dimensional array mat:

>>> let mat = fromList (Z:.5:.10) [0..]
>>> mat
Matrix (Z :. 5 :. 10)
  [  0,  1,  2,  3,  4,  5,  6,  7,  8,  9,
    10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
    20, 21, 22, 23, 24, 25, 26, 27, 28, 29,
    30, 31, 32, 33, 34, 35, 36, 37, 38, 39,
    40, 41, 42, 43, 44, 45, 46, 47, 48, 49]

...will can select a specific row to yield a one dimensional result by fixing the row index (2) while allowing the column index to vary (via All):

>>> slice (use mat) (lift (Z :. 2 :. All))
Vector (Z :. 10) [20,21,22,23,24,25,26,27,28,29]

A fully specified index (with no Alls) returns a single element (zero dimensional array).

>>> slice (use mat) (lift (Z :. 4 :. 2))
Scalar Z [42]

The marker Any can be used in the slice specification to match against some arbitrary (lower) dimension. Here Any matches whatever shape type variable sh takes:

sl0 :: (Shape sh, Elt e) => Acc (Array (sh:.Int) e) -> Exp Int -> Acc (Array sh e)
sl0 a n = A.slice a (lift (Any :. n))
>>> let vec = fromList (Z:.10) [0..]
>>> sl0 (use vec) 4
Scalar Z [4]
>>> sl0 (use mat) 4
Vector (Z :. 5) [4,14,24,34,44]

Of course, Any and All can be used together.

sl1 :: (Shape sh, Elt e) => Acc (Array (sh:.Int:.Int) e) -> Exp Int -> Acc (Array (sh:.Int) e)
sl1 a n = A.slice a (lift (Any :. n :. All))
>>> sl1 (use mat) 4
Vector (Z :. 10) [40,41,42,43,44,45,46,47,48,49]
>>> let cube = fromList (Z:.3:.4:.5) [0..]
>>> cube
Array (Z :. 3 :. 4 :. 5) [0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,32,33,34,35,36,37,38,39,40,41,42,43,44,45,46,47,48,49,50,51,52,53,54,55,56,57,58,59]
>>> sl1 (use cube) 2
Matrix (Z :. 3 :. 5)
  [ 10, 11, 12, 13, 14,
    30, 31, 32, 33, 34,
    50, 51, 52, 53, 54]

init :: forall sh e. (Slice sh, Shape sh, Elt e) => Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e) #

Yield all but the elements in the last index of the innermost dimension.

>>> let mat = fromList (Z:.5:.10) [0..]
>>> mat
Matrix (Z :. 5 :. 10)
  [  0,  1,  2,  3,  4,  5,  6,  7,  8,  9,
    10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
    20, 21, 22, 23, 24, 25, 26, 27, 28, 29,
    30, 31, 32, 33, 34, 35, 36, 37, 38, 39,
    40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>> init (use mat)
Matrix (Z :. 5 :. 9)
  [  0,  1,  2,  3,  4,  5,  6,  7,  8,
    10, 11, 12, 13, 14, 15, 16, 17, 18,
    20, 21, 22, 23, 24, 25, 26, 27, 28,
    30, 31, 32, 33, 34, 35, 36, 37, 38,
    40, 41, 42, 43, 44, 45, 46, 47, 48]

tail :: forall sh e. (Slice sh, Shape sh, Elt e) => Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e) #

Yield all but the first element along the innermost dimension of an array. The innermost dimension must not be empty.

>>> let mat = fromList (Z:.5:.10) [0..]
>>> mat
Matrix (Z :. 5 :. 10)
  [  0,  1,  2,  3,  4,  5,  6,  7,  8,  9,
    10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
    20, 21, 22, 23, 24, 25, 26, 27, 28, 29,
    30, 31, 32, 33, 34, 35, 36, 37, 38, 39,
    40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>> tail (use mat)
Matrix (Z :. 5 :. 9)
  [  1,  2,  3,  4,  5,  6,  7,  8,  9,
    11, 12, 13, 14, 15, 16, 17, 18, 19,
    21, 22, 23, 24, 25, 26, 27, 28, 29,
    31, 32, 33, 34, 35, 36, 37, 38, 39,
    41, 42, 43, 44, 45, 46, 47, 48, 49]

take :: forall sh e. (Slice sh, Shape sh, Elt e) => Exp Int -> Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e) #

Yield the first n elements in the innermost dimension of the array (plus all lower dimensional elements).

>>> let mat = fromList (Z:.5:.10) [0..]
>>> mat
Matrix (Z :. 5 :. 10)
  [  0,  1,  2,  3,  4,  5,  6,  7,  8,  9,
    10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
    20, 21, 22, 23, 24, 25, 26, 27, 28, 29,
    30, 31, 32, 33, 34, 35, 36, 37, 38, 39,
    40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>> take 5 (use mat)
Matrix (Z :. 5 :. 5)
  [  0,  1,  2,  3,  4,
    10, 11, 12, 13, 14,
    20, 21, 22, 23, 24,
    30, 31, 32, 33, 34,
    40, 41, 42, 43, 44]

drop :: forall sh e. (Slice sh, Shape sh, Elt e) => Exp Int -> Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e) #

Yield all but the first n elements along the innermost dimension of the array (plus all lower dimensional elements).

>>> let mat = fromList (Z:.5:.10) [0..]
>>> mat
Matrix (Z :. 5 :. 10)
  [  0,  1,  2,  3,  4,  5,  6,  7,  8,  9,
    10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
    20, 21, 22, 23, 24, 25, 26, 27, 28, 29,
    30, 31, 32, 33, 34, 35, 36, 37, 38, 39,
    40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>> drop 7 (use mat)
Matrix (Z :. 5 :. 3)
  [  7,  8,  9,
    17, 18, 19,
    27, 28, 29,
    37, 38, 39,
    47, 48, 49]

slit :: forall sh e. (Slice sh, Shape sh, Elt e) => Exp Int -> Exp Int -> Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e) #

Yield a slit (slice) of the innermost indices of an array. Denotationally, we have:

slit i n = take n . drop i

Permutations

Forward permutation (scatter)

permute #

Arguments

:: (Shape sh, Shape sh', Elt a) 
=> (Exp a -> Exp a -> Exp a)

combination function

-> Acc (Array sh' a)

array of default values

-> (Exp sh -> Exp sh')

index permutation function

-> Acc (Array sh a)

array of source values to be permuted

-> Acc (Array sh' a) 

Generalised forward permutation operation (array scatter).

Forward permutation specified by a function mapping indices from the source array to indices in the result array. The result array is initialised with the given defaults and any further values that are permuted into the result array are added to the current value using the given combination function.

The combination function must be associative and commutative. Elements that are mapped to the magic value ignore by the permutation function are dropped.

For example, we can use permute to compute the occurrence count (histogram) for an array of values in the range [0,10):

histogram :: Acc (Vector Int) -> Acc (Vector Int)
histogram xs =
  let zeros = fill (constant (Z:.10)) 0
      ones  = fill (shape xs)         1
  in
  permute (+) zeros (\ix -> index1 (xs!ix)) ones
>>> let xs = fromList (Z :. 20) [0,0,1,2,1,1,2,4,8,3,4,9,8,3,2,5,5,3,1,2]
>>> histogram (use xs)
Vector (Z :. 10) [2,4,4,3,2,2,0,0,2,1]
Note:

Regarding array fusion:

  1. The permute operation will always be evaluated; it can not be fused into a later step.
  2. Since the index permutation function might not cover all positions in the output array (the function is not surjective), the array of default values must be evaluated. However, other operations may fuse into this.
  3. The array of source values can fuse into the permutation operation.

ignore :: Shape sh => Exp sh #

Magic value identifying elements that are ignored in a forward permutation.

scatter #

Arguments

:: Elt e 
=> Acc (Vector Int)

destination indices to scatter into

-> Acc (Vector e)

default values

-> Acc (Vector e)

source values

-> Acc (Vector e) 

Overwrite elements of the destination by scattering the values of the source array according to the given index mapping.

Note that if the destination index appears more than once in the mapping the result is undefined.

>>> let to    = fromList (Z :. 6) [1,3,7,2,5,8]
>>> let input = fromList (Z :. 7) [1,9,6,4,4,2,5]
>>> scatter (use to) (fill (constant (Z:.10)) 0) (use input)
Vector (Z :. 10) [0,1,4,9,0,4,0,6,2,0]

Backward permutation (gather)

backpermute #

Arguments

:: (Shape sh, Shape sh', Elt a) 
=> Exp sh'

shape of the result array

-> (Exp sh' -> Exp sh)

index permutation function

-> Acc (Array sh a)

source array

-> Acc (Array sh' a) 

Generalised backward permutation operation (array gather).

Backward permutation specified by a function mapping indices in the destination array to indices in the source array. Elements of the output array are thus generated by reading from the corresponding index in the source array.

For example, backpermute can be used to transpose a matrix; at every index Z:.y:.x in the result array, we get the value at that index by reading from the source array at index Z:.x:.y:

swap :: Exp DIM2 -> Exp DIM2
swap = lift1 $ \(Z:.y:.x) -> Z:.x:.y
>>> let mat = fromList (Z:.5:.10) [0..]
>>> mat
Matrix (Z :. 5 :. 10)
  [  0,  1,  2,  3,  4,  5,  6,  7,  8,  9,
    10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
    20, 21, 22, 23, 24, 25, 26, 27, 28, 29,
    30, 31, 32, 33, 34, 35, 36, 37, 38, 39,
    40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>> let mat' = use mat
>>> backpermute (swap (shape mat')) swap mat'
Matrix (Z :. 10 :. 5)
  [ 0, 10, 20, 30, 40,
    1, 11, 21, 31, 41,
    2, 12, 22, 32, 42,
    3, 13, 23, 33, 43,
    4, 14, 24, 34, 44,
    5, 15, 25, 35, 45,
    6, 16, 26, 36, 46,
    7, 17, 27, 37, 47,
    8, 18, 28, 38, 48,
    9, 19, 29, 39, 49]

gather #

Arguments

:: (Shape sh, Elt e) 
=> Acc (Array sh Int)

index of source at each index to gather

-> Acc (Vector e)

source values

-> Acc (Array sh e) 

Gather elements from a source array by reading values at the given indices.

>>> let input = fromList (Z:.9) [1,9,6,4,4,2,0,1,2]
>>> let from  = fromList (Z:.6) [1,3,7,2,5,3]
>>> gather (use from) (use input)
Vector (Z :. 6) [9,4,1,6,2,4]

Specialised permutations

reverse :: Elt e => Acc (Vector e) -> Acc (Vector e) #

Reverse the elements of a vector.

transpose :: Elt e => Acc (Array DIM2 e) -> Acc (Array DIM2 e) #

Transpose the rows and columns of a matrix.

Filtering

filter :: forall sh e. (Shape sh, Slice sh, Elt e) => (Exp e -> Exp Bool) -> Acc (Array (sh :. Int) e) -> Acc (Vector e, Array sh Int) #

Drop elements that do not satisfy the predicate. Returns the elements which pass the predicate, together with a segment descriptor indicating how many elements along each outer dimension were valid.

>>> let vec = fromList (Z :. 10) [1..10] :: Vector Int
>>> vec
Vector (Z :. 10) [1,2,3,4,5,6,7,8,9,10]
>>> filter even (use vec)
(Vector (Z :. 5) [2,4,6,8,10], Scalar Z [5])
>>> let mat = fromList (Z :. 4 :. 10) [1,2,3,4,5,6,7,8,9,10,1,1,1,1,1,2,2,2,2,2,2,4,6,8,10,12,14,16,18,20,1,3,5,7,9,11,13,15,17,19] :: Array DIM2 Int
>>> mat
Matrix (Z :. 4 :. 10)
  [ 1, 2, 3, 4,  5,  6,  7,  8,  9, 10,
    1, 1, 1, 1,  1,  2,  2,  2,  2,  2,
    2, 4, 6, 8, 10, 12, 14, 16, 18, 20,
    1, 3, 5, 7,  9, 11, 13, 15, 17, 19]
>>> filter odd (use mat)
(Vector (Z :. 20) [1,3,5,7,9,1,1,1,1,1,1,3,5,7,9,11,13,15,17,19], Vector (Z :. 4) [5,5,0,10])

Folding

fold :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array sh a) #

Reduction of the innermost dimension of an array of arbitrary rank. The first argument needs to be an associative function to enable an efficient parallel implementation. The initial element does not need to be an identity element of the combination function.

>>> let mat = fromList (Z:.5:.10) [0..]
>>> mat
Matrix (Z :. 5 :. 10)
  [  0,  1,  2,  3,  4,  5,  6,  7,  8,  9,
    10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
    20, 21, 22, 23, 24, 25, 26, 27, 28, 29,
    30, 31, 32, 33, 34, 35, 36, 37, 38, 39,
    40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>> fold (+) 42 (use mat)
Vector (Z :. 5) [87,187,287,387,487]

Reductions with non-commutative operators are supported. For example, the following computes the maximum segment sum problem along each innermost dimension of the array.

https://en.wikipedia.org/wiki/Maximum_subarray_problem

maximumSegmentSum
    :: forall sh e. (Shape sh, Num e, Ord e)
    => Acc (Array (sh :. Int) e)
    -> Acc (Array sh e)
maximumSegmentSum
  = map (\v -> let (x,_,_,_) = unlift v :: (Exp e, Exp e, Exp e, Exp e) in x)
  . fold1 f
  . map g
  where
    f :: (Num a, Ord a) => Exp (a,a,a,a) -> Exp (a,a,a,a) -> Exp (a,a,a,a)
    f x y =
      let (mssx, misx, mcsx, tsx) = unlift x
          (mssy, misy, mcsy, tsy) = unlift y
      in
      lift ( mssx `max` (mssy `max` (mcsx+misy))
           , misx `max` (tsx+misy)
           , mcsy `max` (mcsx+tsy)
           , tsx+tsy
           )

    g :: (Num a, Ord a) => Exp a -> Exp (a,a,a,a)
    g x = let y = max x 0
          in  lift (y,y,y,x)
>>> let vec = fromList (Z:.10) [-2,1,-3,4,-1,2,1,-5,4,0]
>>> maximumSegmentSum (use vec)
Scalar Z [6]

See also Fold, which can be a useful way to compute multiple results from a single reduction.

fold1 :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Acc (Array (sh :. Int) a) -> Acc (Array sh a) #

Variant of fold that requires the reduced array to be non-empty and doesn't need an default value. The first argument needs to be an associative function to enable an efficient parallel implementation. The initial element does not need to be an identity element.

foldAll :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array sh a) -> Acc (Scalar a) #

Reduction of an array of arbitrary rank to a single scalar value. The first argument needs to be an associative function to enable efficient parallel implementation. The initial element does not need to be an identity element.

>>> let vec = fromList (Z:.10) [0..]
>>> foldAll (+) 42 (use vec)
Scalar Z [87]
>>> let mat = fromList (Z:.5:.10) [0..]
>>> foldAll (+) 0 (use mat)
Scalar Z [1225]

fold1All :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Acc (Array sh a) -> Acc (Scalar a) #

Variant of foldAll that requires the reduced array to be non-empty and doesn't need an default value. The first argument must be an associative function.

Segmented reductions

foldSeg :: (Shape sh, Elt a, Elt i, IsIntegral i) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Segments i) -> Acc (Array (sh :. Int) a) #

Segmented reduction along the innermost dimension of an array. The segment descriptor specifies the lengths of the logical sub-arrays, each of which is reduced independently. The innermost dimension must contain at least as many elements as required by the segment descriptor (sum thereof).

>>> let seg = fromList (Z:.4) [1,4,0,3]
>>> seg
Vector (Z :. 4) [1,4,0,3]
>>> let mat = fromList (Z:.5:.10) [0..]
>>> mat
Matrix (Z :. 5 :. 10)
  [  0,  1,  2,  3,  4,  5,  6,  7,  8,  9,
    10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
    20, 21, 22, 23, 24, 25, 26, 27, 28, 29,
    30, 31, 32, 33, 34, 35, 36, 37, 38, 39,
    40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>> foldSeg (+) 0 (use mat) (use seg)
Matrix (Z :. 5 :. 4)
  [  0,  10, 0,  18,
    10,  50, 0,  48,
    20,  90, 0,  78,
    30, 130, 0, 108,
    40, 170, 0, 138]

fold1Seg :: (Shape sh, Elt a, Elt i, IsIntegral i) => (Exp a -> Exp a -> Exp a) -> Acc (Array (sh :. Int) a) -> Acc (Segments i) -> Acc (Array (sh :. Int) a) #

Variant of foldSeg that requires all segments of the reduced array to be non-empty and doesn't need a default value. The segment descriptor specifies the length of each of the logical sub-arrays.

Specialised reductions

all :: (Shape sh, Elt e) => (Exp e -> Exp Bool) -> Acc (Array sh e) -> Acc (Scalar Bool) #

Check if all elements satisfy a predicate

any :: (Shape sh, Elt e) => (Exp e -> Exp Bool) -> Acc (Array sh e) -> Acc (Scalar Bool) #

Check if any element satisfies the predicate

and :: Shape sh => Acc (Array sh Bool) -> Acc (Scalar Bool) #

Check if all elements are True

or :: Shape sh => Acc (Array sh Bool) -> Acc (Scalar Bool) #

Check if any element is True

sum :: (Shape sh, Num e) => Acc (Array sh e) -> Acc (Scalar e) #

Compute the sum of elements

product :: (Shape sh, Num e) => Acc (Array sh e) -> Acc (Scalar e) #

Compute the product of the elements

minimum :: (Shape sh, Ord e) => Acc (Array sh e) -> Acc (Scalar e) #

Yield the minimum element of an array. The array must not be empty.

maximum :: (Shape sh, Ord e) => Acc (Array sh e) -> Acc (Scalar e) #

Yield the maximum element of an array. The array must not be empty.

Scans (prefix sums)

scanl :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a) #

Data.List style left-to-right scan along the innermost dimension of an arbitrary rank array. The first argument needs to be an associative function to enable efficient parallel implementation. The initial value (second argument) may be arbitrary.

>>> scanl (+) 10 (use $ fromList (Z :. 10) [0..])
Array (Z :. 11) [10,10,11,13,16,20,25,31,38,46,55]
>>> scanl (+) 0 (use $ fromList (Z :. 4 :. 10) [0..])
Matrix (Z :. 4 :. 11)
  [ 0,  0,  1,  3,   6,  10,  15,  21,  28,  36,  45,
    0, 10, 21, 33,  46,  60,  75,  91, 108, 126, 145,
    0, 20, 41, 63,  86, 110, 135, 161, 188, 216, 245,
    0, 30, 61, 93, 126, 160, 195, 231, 268, 306, 345]

scanl1 :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a) #

Data.List style left-to-right scan along the innermost dimension without an initial value (aka inclusive scan). The array must not be empty. The first argument needs to be an associative function. Denotationally, we have:

scanl1 f e arr = tail (scanl f e arr)
>>> scanl (+) (use $ fromList (Z:.4:.10) [0..])
Matrix (Z :. 4 :. 10)
  [  0,  1,  3,   6,  10,  15,  21,  28,  36,  45,
    10, 21, 33,  46,  60,  75,  91, 108, 126, 145,
    20, 41, 63,  86, 110, 135, 161, 188, 216, 245,
    30, 61, 93, 126, 160, 195, 231, 268, 306, 345]

scanl' :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> (Acc (Array (sh :. Int) a), Acc (Array sh a)) #

Variant of scanl, where the last element (final reduction result) along each dimension is returned separately. Denotationally we have:

scanl' f e arr = (init res, unit (res!len))
  where
    len = shape arr
    res = scanl f e arr
>>> let (res,sum) = scanl' (+) 0 (use $ fromList (Z:.10) [0..])
>>> res
Vector (Z :. 10) [0,0,1,3,6,10,15,21,28,36]
>>> sum
Scalar Z [45]
>>> let (res,sums) = scanl' (+) 0 (use $ fromList (Z:.4:.10) [0..])
>>> res
Matrix (Z :. 4 :. 10)
  [ 0,  0,  1,  3,   6,  10,  15,  21,  28,  36,
    0, 10, 21, 33,  46,  60,  75,  91, 108, 126,
    0, 20, 41, 63,  86, 110, 135, 161, 188, 216,
    0, 30, 61, 93, 126, 160, 195, 231, 268, 306]
>>> sums
Vector (Z :. 4) [45,145,245,345]

scanr :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a) #

Right-to-left variant of scanl.

scanr1 :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a) #

Right-to-left variant of scanl1.

scanr' :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> (Acc (Array (sh :. Int) a), Acc (Array sh a)) #

Right-to-left variant of scanl'.

prescanl :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a) #

Left-to-right prescan (aka exclusive scan). As for scan, the first argument must be an associative function. Denotationally, we have

prescanl f e = Prelude.fst . scanl' f e
>>> let vec = fromList (Z:.10) [1..10]
>>> prescanl (+) 0 (use vec)
Vector (Z :. 10) [0,0,1,3,6,10,15,21,28,36]

postscanl :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a) #

Left-to-right postscan, a variant of scanl1 with an initial value. As with scanl1, the array must not be empty. Denotationally, we have:

postscanl f e = map (e `f`) . scanl1 f
>>> let vec = fromList (Z:.10) [1..10]
>>> postscanl (+) 42 (use vec)
Vector (Z :. 10) [42,43,45,48,52,57,63,70,78,87]

prescanr :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a) #

Right-to-left prescan (aka exclusive scan). As for scan, the first argument must be an associative function. Denotationally, we have

prescanr f e = Prelude.fst . scanr' f e

postscanr :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a) #

Right-to-left postscan, a variant of scanr1 with an initial value. Denotationally, we have

postscanr f e = map (e `f`) . scanr1 f

Segmented scans

scanlSeg :: forall sh e i. (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e) #

Segmented version of scanl along the innermost dimension of an array. The innermost dimension must have at least as many elements as the sum of the segment descriptor.

>>> let seg = fromList (Z:.4) [1,4,0,3]
>>> seg
Vector (Z :. 4) [1,4,0,3]
>>> let mat = fromList (Z:.5:.10) [0..]
>>> mat
Matrix (Z :. 5 :. 10)
  [  0,  1,  2,  3,  4,  5,  6,  7,  8,  9,
    10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
    20, 21, 22, 23, 24, 25, 26, 27, 28, 29,
    30, 31, 32, 33, 34, 35, 36, 37, 38, 39,
    40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>> scanlSeg (+) 0 (use mat) (use seg)
Matrix (Z :. 5 :. 12)
  [ 0,  0, 0,  1,  3,   6,  10, 0, 0,  5, 11,  18,
    0, 10, 0, 11, 23,  36,  50, 0, 0, 15, 31,  48,
    0, 20, 0, 21, 43,  66,  90, 0, 0, 25, 51,  78,
    0, 30, 0, 31, 63,  96, 130, 0, 0, 35, 71, 108,
    0, 40, 0, 41, 83, 126, 170, 0, 0, 45, 91, 138]

scanl1Seg :: (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e) #

Segmented version of scanl1 along the innermost dimension.

As with scanl1, the total number of elements considered, in this case given by the sum of segment descriptor, must not be zero. The input vector must contain at least this many elements.

Zero length segments are allowed, and the behaviour is as if those entries were not present in the segment descriptor; that is:

scanl1Seg f xs [n,0,0] == scanl1Seg f xs [n]   where n /= 0
>>> let seg = fromList (Z:.4) [1,4,0,3]
>>> seg
Vector (Z :. 4) [1,4,0,3]
>>> let mat = fromList (Z:.5:.10) [0..]
>>> mat
Matrix (Z :. 5 :. 10)
  [  0,  1,  2,  3,  4,  5,  6,  7,  8,  9,
    10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
    20, 21, 22, 23, 24, 25, 26, 27, 28, 29,
    30, 31, 32, 33, 34, 35, 36, 37, 38, 39,
    40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>> scanl1Seg (+) (use mat) (use seg)
Matrix (Z :. 5 :. 8)
  [  0,  1,  3,   6,  10,  5, 11,  18,
    10, 11, 23,  36,  50, 15, 31,  48,
    20, 21, 43,  66,  90, 25, 51,  78,
    30, 31, 63,  96, 130, 35, 71, 108,
    40, 41, 83, 126, 170, 45, 91, 138]

scanl'Seg :: forall sh e i. (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e, Array (sh :. Int) e) #

Segmented version of scanl' along the innermost dimension of an array. The innermost dimension must have at least as many elements as the sum of the segment descriptor.

The first element of the resulting tuple is a vector of scanned values. The second element is a vector of segment scan totals and has the same size as the segment vector.

>>> let seg = fromList (Z:.4) [1,4,0,3]
>>> seg
Vector (Z :. 4) [1,4,0,3]
>>> let mat = fromList (Z:.5:.10) [0..]
>>> mat
Matrix (Z :. 5 :. 10)
  [  0,  1,  2,  3,  4,  5,  6,  7,  8,  9,
    10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
    20, 21, 22, 23, 24, 25, 26, 27, 28, 29,
    30, 31, 32, 33, 34, 35, 36, 37, 38, 39,
    40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>> let (res,sums) = scanl'Seg (+) 0 (use mat) (use seg)
>>> res
Matrix (Z :. 5 :. 8)
  [ 0, 0,  1,  3,   6, 0,  5, 11,
    0, 0, 11, 23,  36, 0, 15, 31,
    0, 0, 21, 43,  66, 0, 25, 51,
    0, 0, 31, 63,  96, 0, 35, 71,
    0, 0, 41, 83, 126, 0, 45, 91]
>>> sums
Matrix (Z :. 5 :. 4)
  [  0,  10, 0,  18,
    10,  50, 0,  48,
    20,  90, 0,  78,
    30, 130, 0, 108,
    40, 170, 0, 138]

prescanlSeg :: (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e) #

Segmented version of prescanl.

postscanlSeg :: (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e) #

Segmented version of postscanl.

scanrSeg :: forall sh e i. (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e) #

Segmented version of scanr along the innermost dimension of an array. The innermost dimension must have at least as many elements as the sum of the segment descriptor.

>>> let seg = fromList (Z:.4) [1,4,0,3]
>>> seg
Vector (Z :. 4) [1,4,0,3]
>>> let mat = fromList (Z:.5:.10) [0..]
>>> mat
Matrix (Z :. 5 :. 10)
  [  0,  1,  2,  3,  4,  5,  6,  7,  8,  9,
    10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
    20, 21, 22, 23, 24, 25, 26, 27, 28, 29,
    30, 31, 32, 33, 34, 35, 36, 37, 38, 39,
    40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>> scanrSeg (+) 0 (use mat) (use seg)
Matrix (Z :. 5 :. 12)
  [  2, 0,  18,  15, 11,  6, 0, 0,  24, 17,  9, 0,
    12, 0,  58,  45, 31, 16, 0, 0,  54, 37, 19, 0,
    22, 0,  98,  75, 51, 26, 0, 0,  84, 57, 29, 0,
    32, 0, 138, 105, 71, 36, 0, 0, 114, 77, 39, 0,
    42, 0, 178, 135, 91, 46, 0, 0, 144, 97, 49, 0]

scanr1Seg :: (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e) #

Segmented version of scanr1.

>>> let seg = fromList (Z:.4) [1,4,0,3]
>>> seg
Vector (Z :. 4) [1,4,0,3]
>>> let mat = fromList (Z:.5:.10) [0..]
>>> mat
Matrix (Z :. 5 :. 10)
  [  0,  1,  2,  3,  4,  5,  6,  7,  8,  9,
    10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
    20, 21, 22, 23, 24, 25, 26, 27, 28, 29,
    30, 31, 32, 33, 34, 35, 36, 37, 38, 39,
    40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>> scanr1Seg (+) (use mat) (use seg)
Matrix (Z :. 5 :. 8)
  [  0,  10,   9,  7,  4,  18, 13,  7,
    10,  50,  39, 27, 14,  48, 33, 17,
    20,  90,  69, 47, 24,  78, 53, 27,
    30, 130,  99, 67, 34, 108, 73, 37,
    40, 170, 129, 87, 44, 138, 93, 47]

scanr'Seg :: forall sh e i. (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e, Array (sh :. Int) e) #

Segmented version of scanr'.

>>> let seg = fromList (Z:.4) [1,4,0,3]
>>> seg
Vector (Z :. 4) [1,4,0,3]
>>> let mat = fromList (Z:.5:.10) [0..]
>>> mat
Matrix (Z :. 5 :. 10)
  [  0,  1,  2,  3,  4,  5,  6,  7,  8,  9,
    10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
    20, 21, 22, 23, 24, 25, 26, 27, 28, 29,
    30, 31, 32, 33, 34, 35, 36, 37, 38, 39,
    40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>> let (res,sums) = scanr'Seg (+) 0 (use mat) (use seg)
>>> res
Matrix (Z :. 5 :. 8)
  [ 0,  15, 11,  6, 0, 17,  9, 0,
    0,  45, 31, 16, 0, 37, 19, 0,
    0,  75, 51, 26, 0, 57, 29, 0,
    0, 105, 71, 36, 0, 77, 39, 0,
    0, 135, 91, 46, 0, 97, 49, 0]
>>> sums
Matrix (Z :. 5 :. 4)
  [  2,  18, 0,  24,
    12,  58, 0,  54,
    22,  98, 0,  84,
    32, 138, 0, 114,
    42, 178, 0, 144]

prescanrSeg :: (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e) #

Segmented version of prescanr.

postscanrSeg :: (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e) #

Segmented version of postscanr.

Stencils

stencil #

Arguments

:: (Stencil sh a stencil, Elt b) 
=> (stencil -> Exp b)

stencil function

-> Boundary a

boundary condition

-> Acc (Array sh a)

source array

-> Acc (Array sh b)

destination array

Map a stencil over an array. In contrast to map, the domain of a stencil function is an entire neighbourhood of each array element. Neighbourhoods are sub-arrays centred around a focal point. They are not necessarily rectangular, but they are symmetric and have an extent of at least three along each axis. Due to the symmetry requirement the extent is necessarily odd. The focal point is the array position that is determined by the stencil.

For those array positions where the neighbourhood extends past the boundaries of the source array, a boundary condition determines the contents of the out-of-bounds neighbourhood positions.

Stencil neighbourhoods are specified via nested tuples, where the nesting depth is equal to the dimensionality of the array. For example, a 3x1 stencil for a one-dimensional array:

s31 :: Stencil3 a -> Exp a
s31 (l,c,r) = ...

...where c is the focal point of the stencil, and l and r represent the elements to the left and right of the focal point, respectively. Similarly, a 3x3 stencil for a two-dimensional array:

s33 :: Stencil3x3 a -> Exp a
s33 ((_,t,_)

,(l,c,r) ,(_,b,_)) = ...

...where c is again the focal point and t, b, l and r are the elements to the top, bottom, left, and right of the focal point, respectively (the diagonal elements have been elided).

For example, the following computes a 5x5 Gaussian blur as a separable 2-pass operation.

type Stencil5x1 a = (Stencil3 a, Stencil5 a, Stencil3 a)
type Stencil1x5 a = (Stencil3 a, Stencil3 a, Stencil3 a, Stencil3 a, Stencil3 a)

convolve5x1 :: Num a => [Exp a] -> Stencil5x1 a -> Exp a
convolve5x1 kernel (_, (a,b,c,d,e), _)
  = Prelude.sum $ Prelude.zipWith (*) kernel [a,b,c,d,e]

convolve1x5 :: Num a => [Exp a] -> Stencil1x5 a -> Exp a
convolve1x5 kernel ((_,a,_), (_,b,_), (_,c,_), (_,d,_), (_,e,_))
  = Prelude.sum $ Prelude.zipWith (*) kernel [a,b,c,d,e]

gaussian = [0.06136,0.24477,0.38774,0.24477,0.06136]

blur :: Num a => Acc (Array DIM2 a) -> Acc (Array DIM2 a)
blur = stencil (convolve5x1 gaussian) Clamp
     . stencil (convolve1x5 gaussian) Clamp

stencil2 #

Arguments

:: (Stencil sh a stencil1, Stencil sh b stencil2, Elt c) 
=> (stencil1 -> stencil2 -> Exp c)

binary stencil function

-> Boundary a

boundary condition #1

-> Acc (Array sh a)

source array #1

-> Boundary b

boundary condition #2

-> Acc (Array sh b)

source array #2

-> Acc (Array sh c)

destination array

Map a binary stencil of an array. The extent of the resulting array is the intersection of the extents of the two source arrays. This is the stencil equivalent of zipWith.

Stencil specification

class (Elt (StencilRepr sh stencil), Stencil sh a (StencilRepr sh stencil)) => Stencil sh a stencil #

Minimal complete definition

stencilPrj

Instances

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e)

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e, Exp e, Exp e)

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)

(Stencil ((:.) sh Int) a row2, Stencil ((:.) sh Int) a row1, Stencil ((:.) sh Int) a row0) => Stencil ((:.) ((:.) sh Int) Int) a (row2, row1, row0) # 

Associated Types

type StencilRepr ((:.) ((:.) sh Int) Int) (row2, row1, row0) :: *

Methods

stencilPrj :: ((sh :. Int) :. Int) -> a -> Exp (StencilRepr ((sh :. Int) :. Int) (row2, row1, row0)) -> (row2, row1, row0)

(Stencil ((:.) sh Int) a row1, Stencil ((:.) sh Int) a row2, Stencil ((:.) sh Int) a row3, Stencil ((:.) sh Int) a row4, Stencil ((:.) sh Int) a row5) => Stencil ((:.) ((:.) sh Int) Int) a (row1, row2, row3, row4, row5) # 

Associated Types

type StencilRepr ((:.) ((:.) sh Int) Int) (row1, row2, row3, row4, row5) :: *

Methods

stencilPrj :: ((sh :. Int) :. Int) -> a -> Exp (StencilRepr ((sh :. Int) :. Int) (row1, row2, row3, row4, row5)) -> (row1, row2, row3, row4, row5)

(Stencil ((:.) sh Int) a row1, Stencil ((:.) sh Int) a row2, Stencil ((:.) sh Int) a row3, Stencil ((:.) sh Int) a row4, Stencil ((:.) sh Int) a row5, Stencil ((:.) sh Int) a row6, Stencil ((:.) sh Int) a row7) => Stencil ((:.) ((:.) sh Int) Int) a (row1, row2, row3, row4, row5, row6, row7) # 

Associated Types

type StencilRepr ((:.) ((:.) sh Int) Int) (row1, row2, row3, row4, row5, row6, row7) :: *

Methods

stencilPrj :: ((sh :. Int) :. Int) -> a -> Exp (StencilRepr ((sh :. Int) :. Int) (row1, row2, row3, row4, row5, row6, row7)) -> (row1, row2, row3, row4, row5, row6, row7)

(Stencil ((:.) sh Int) a row1, Stencil ((:.) sh Int) a row2, Stencil ((:.) sh Int) a row3, Stencil ((:.) sh Int) a row4, Stencil ((:.) sh Int) a row5, Stencil ((:.) sh Int) a row6, Stencil ((:.) sh Int) a row7, Stencil ((:.) sh Int) a row8, Stencil ((:.) sh Int) a row9) => Stencil ((:.) ((:.) sh Int) Int) a (row1, row2, row3, row4, row5, row6, row7, row8, row9) # 

Associated Types

type StencilRepr ((:.) ((:.) sh Int) Int) (row1, row2, row3, row4, row5, row6, row7, row8, row9) :: *

Methods

stencilPrj :: ((sh :. Int) :. Int) -> a -> Exp (StencilRepr ((sh :. Int) :. Int) (row1, row2, row3, row4, row5, row6, row7, row8, row9)) -> (row1, row2, row3, row4, row5, row6, row7, row8, row9)

data Boundary a #

Boundary condition specification for stencil operations.

Constructors

Clamp

clamp coordinates to the extent of the array

Mirror

mirror coordinates beyond the array extent

Wrap

wrap coordinates around on each dimension

Constant a

use a constant value for outlying coordinates

Instances

Common stencil patterns

type Stencil3 a = (Exp a, Exp a, Exp a) #

type Stencil5 a = (Exp a, Exp a, Exp a, Exp a, Exp a) #

type Stencil7 a = (Exp a, Exp a, Exp a, Exp a, Exp a, Exp a, Exp a) #

type Stencil9 a = (Exp a, Exp a, Exp a, Exp a, Exp a, Exp a, Exp a, Exp a, Exp a) #

The Accelerate Expression Language

Scalar data types

data Exp t #

The type Exp represents embedded scalar expressions. The collective operations of Accelerate Acc consist of many scalar expressions executed in data-parallel.

Note that scalar expressions can not initiate new collective operations: doing so introduces nested data parallelism, which is difficult to execute efficiently on constrained hardware such as GPUs, and is thus currently unsupported.

Instances

IfThenElse Exp # 

Associated Types

type EltT (Exp :: * -> *) a :: Constraint #

Methods

ifThenElse :: EltT Exp a => Exp Bool -> Exp a -> Exp a -> Exp a #

Unlift Exp () # 

Methods

unlift :: Exp (Plain ()) -> () #

Unlift Exp Z # 

Methods

unlift :: Exp (Plain Z) -> Z #

Lift Exp Bool # 

Associated Types

type Plain Bool :: * #

Methods

lift :: Bool -> Exp (Plain Bool) #

Lift Exp Char # 

Associated Types

type Plain Char :: * #

Methods

lift :: Char -> Exp (Plain Char) #

Lift Exp Double # 

Associated Types

type Plain Double :: * #

Methods

lift :: Double -> Exp (Plain Double) #

Lift Exp Float # 

Associated Types

type Plain Float :: * #

Methods

lift :: Float -> Exp (Plain Float) #

Lift Exp Int # 

Associated Types

type Plain Int :: * #

Methods

lift :: Int -> Exp (Plain Int) #

Lift Exp Int8 # 

Associated Types

type Plain Int8 :: * #

Methods

lift :: Int8 -> Exp (Plain Int8) #

Lift Exp Int16 # 

Associated Types

type Plain Int16 :: * #

Methods

lift :: Int16 -> Exp (Plain Int16) #

Lift Exp Int32 # 

Associated Types

type Plain Int32 :: * #

Methods

lift :: Int32 -> Exp (Plain Int32) #

Lift Exp Int64 # 

Associated Types

type Plain Int64 :: * #

Methods

lift :: Int64 -> Exp (Plain Int64) #

Lift Exp Word # 

Associated Types

type Plain Word :: * #

Methods

lift :: Word -> Exp (Plain Word) #

Lift Exp Word8 # 

Associated Types

type Plain Word8 :: * #

Methods

lift :: Word8 -> Exp (Plain Word8) #

Lift Exp Word16 # 

Associated Types

type Plain Word16 :: * #

Methods

lift :: Word16 -> Exp (Plain Word16) #

Lift Exp Word32 # 

Associated Types

type Plain Word32 :: * #

Methods

lift :: Word32 -> Exp (Plain Word32) #

Lift Exp Word64 # 

Associated Types

type Plain Word64 :: * #

Methods

lift :: Word64 -> Exp (Plain Word64) #

Lift Exp () # 

Associated Types

type Plain () :: * #

Methods

lift :: () -> Exp (Plain ()) #

Lift Exp CChar # 

Associated Types

type Plain CChar :: * #

Methods

lift :: CChar -> Exp (Plain CChar) #

Lift Exp CSChar # 

Associated Types

type Plain CSChar :: * #

Methods

lift :: CSChar -> Exp (Plain CSChar) #

Lift Exp CUChar # 

Associated Types

type Plain CUChar :: * #

Methods

lift :: CUChar -> Exp (Plain CUChar) #

Lift Exp CShort # 

Associated Types

type Plain CShort :: * #

Methods

lift :: CShort -> Exp (Plain CShort) #

Lift Exp CUShort # 

Associated Types

type Plain CUShort :: * #

Methods

lift :: CUShort -> Exp (Plain CUShort) #

Lift Exp CInt # 

Associated Types

type Plain CInt :: * #

Methods

lift :: CInt -> Exp (Plain CInt) #

Lift Exp CUInt # 

Associated Types

type Plain CUInt :: * #

Methods

lift :: CUInt -> Exp (Plain CUInt) #

Lift Exp CLong # 

Associated Types

type Plain CLong :: * #

Methods

lift :: CLong -> Exp (Plain CLong) #

Lift Exp CULong # 

Associated Types

type Plain CULong :: * #

Methods

lift :: CULong -> Exp (Plain CULong) #

Lift Exp CLLong # 

Associated Types

type Plain CLLong :: * #

Methods

lift :: CLLong -> Exp (Plain CLLong) #

Lift Exp CULLong # 

Associated Types

type Plain CULLong :: * #

Methods

lift :: CULLong -> Exp (Plain CULLong) #

Lift Exp CFloat # 

Associated Types

type Plain CFloat :: * #

Methods

lift :: CFloat -> Exp (Plain CFloat) #

Lift Exp CDouble # 

Associated Types

type Plain CDouble :: * #

Methods

lift :: CDouble -> Exp (Plain CDouble) #

Lift Exp Z # 

Associated Types

type Plain Z :: * #

Methods

lift :: Z -> Exp (Plain Z) #

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e)

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e, Exp e, Exp e)

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)

Unlift Exp (Exp e) # 

Methods

unlift :: Exp (Plain (Exp e)) -> Exp e #

Shape sh => Lift Exp (Any sh) # 

Associated Types

type Plain (Any sh) :: * #

Methods

lift :: Any sh -> Exp (Plain (Any sh)) #

Lift Exp (Exp e) # 

Associated Types

type Plain (Exp e) :: * #

Methods

lift :: Exp e -> Exp (Plain (Exp e)) #

(Elt a, Elt b) => Unlift Exp (Exp a, Exp b) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b)) -> (Exp a, Exp b) #

(Elt e, Slice (Plain ix), Unlift Exp ix) => Unlift Exp ((:.) ix (Exp e)) # 

Methods

unlift :: Exp (Plain (ix :. Exp e)) -> ix :. Exp e #

(Elt e, Slice ix) => Unlift Exp ((:.) (Exp ix) (Exp e)) # 

Methods

unlift :: Exp (Plain (Exp ix :. Exp e)) -> Exp ix :. Exp e #

(Lift Exp a, Lift Exp b, Elt (Plain a), Elt (Plain b)) => Lift Exp (a, b) # 

Associated Types

type Plain (a, b) :: * #

Methods

lift :: (a, b) -> Exp (Plain (a, b)) #

(Elt e, Slice (Plain ix), Lift Exp ix) => Lift Exp ((:.) ix (Exp e)) # 

Associated Types

type Plain ((:.) ix (Exp e)) :: * #

Methods

lift :: (ix :. Exp e) -> Exp (Plain (ix :. Exp e)) #

(Slice (Plain ix), Lift Exp ix) => Lift Exp ((:.) ix All) # 

Associated Types

type Plain ((:.) ix All) :: * #

Methods

lift :: (ix :. All) -> Exp (Plain (ix :. All)) #

(Slice (Plain ix), Lift Exp ix) => Lift Exp ((:.) ix Int) # 

Associated Types

type Plain ((:.) ix Int) :: * #

Methods

lift :: (ix :. Int) -> Exp (Plain (ix :. Int)) #

(Elt a, Elt b, Elt c) => Unlift Exp (Exp a, Exp b, Exp c) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c)) -> (Exp a, Exp b, Exp c) #

(Lift Exp a, Lift Exp b, Lift Exp c, Elt (Plain a), Elt (Plain b), Elt (Plain c)) => Lift Exp (a, b, c) # 

Associated Types

type Plain (a, b, c) :: * #

Methods

lift :: (a, b, c) -> Exp (Plain (a, b, c)) #

(Elt a, Elt b, Elt c, Elt d) => Unlift Exp (Exp a, Exp b, Exp c, Exp d) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d)) -> (Exp a, Exp b, Exp c, Exp d) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d)) => Lift Exp (a, b, c, d) # 

Associated Types

type Plain (a, b, c, d) :: * #

Methods

lift :: (a, b, c, d) -> Exp (Plain (a, b, c, d)) #

(Elt a, Elt b, Elt c, Elt d, Elt e) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e)) -> (Exp a, Exp b, Exp c, Exp d, Exp e) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e)) => Lift Exp (a, b, c, d, e) # 

Associated Types

type Plain (a, b, c, d, e) :: * #

Methods

lift :: (a, b, c, d, e) -> Exp (Plain (a, b, c, d, e)) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f)) => Lift Exp (a, b, c, d, e, f) # 

Associated Types

type Plain (a, b, c, d, e, f) :: * #

Methods

lift :: (a, b, c, d, e, f) -> Exp (Plain (a, b, c, d, e, f)) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g)) => Lift Exp (a, b, c, d, e, f, g) # 

Associated Types

type Plain (a, b, c, d, e, f, g) :: * #

Methods

lift :: (a, b, c, d, e, f, g) -> Exp (Plain (a, b, c, d, e, f, g)) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h)) => Lift Exp (a, b, c, d, e, f, g, h) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h) -> Exp (Plain (a, b, c, d, e, f, g, h)) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i)) => Lift Exp (a, b, c, d, e, f, g, h, i) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i) -> Exp (Plain (a, b, c, d, e, f, g, h, i)) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j)) => Lift Exp (a, b, c, d, e, f, g, h, i, j) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j)) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j, k)) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k, Elt l) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Lift Exp l, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k), Elt (Plain l)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k, l) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j, k, l)) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k, Elt l, Elt m) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Lift Exp l, Lift Exp m, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k), Elt (Plain l), Elt (Plain m)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l, m) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j, k, l, m)) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k, Elt l, Elt m, Elt n) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Lift Exp l, Lift Exp m, Lift Exp n, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k), Elt (Plain l), Elt (Plain m), Elt (Plain n)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n)) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k, Elt l, Elt m, Elt n, Elt o) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n, Exp o) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n, Exp o)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n, Exp o) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Lift Exp l, Lift Exp m, Lift Exp n, Lift Exp o, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k), Elt (Plain l), Elt (Plain m), Elt (Plain n), Elt (Plain o)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)) #

Floating b => Floating (Fold a (Exp b)) # 

Methods

pi :: Fold a (Exp b) #

exp :: Fold a (Exp b) -> Fold a (Exp b) #

log :: Fold a (Exp b) -> Fold a (Exp b) #

sqrt :: Fold a (Exp b) -> Fold a (Exp b) #

(**) :: Fold a (Exp b) -> Fold a (Exp b) -> Fold a (Exp b) #

logBase :: Fold a (Exp b) -> Fold a (Exp b) -> Fold a (Exp b) #

sin :: Fold a (Exp b) -> Fold a (Exp b) #

cos :: Fold a (Exp b) -> Fold a (Exp b) #

tan :: Fold a (Exp b) -> Fold a (Exp b) #

asin :: Fold a (Exp b) -> Fold a (Exp b) #

acos :: Fold a (Exp b) -> Fold a (Exp b) #

atan :: Fold a (Exp b) -> Fold a (Exp b) #

sinh :: Fold a (Exp b) -> Fold a (Exp b) #

cosh :: Fold a (Exp b) -> Fold a (Exp b) #

tanh :: Fold a (Exp b) -> Fold a (Exp b) #

asinh :: Fold a (Exp b) -> Fold a (Exp b) #

acosh :: Fold a (Exp b) -> Fold a (Exp b) #

atanh :: Fold a (Exp b) -> Fold a (Exp b) #

log1p :: Fold a (Exp b) -> Fold a (Exp b) #

expm1 :: Fold a (Exp b) -> Fold a (Exp b) #

log1pexp :: Fold a (Exp b) -> Fold a (Exp b) #

log1mexp :: Fold a (Exp b) -> Fold a (Exp b) #

Fractional b => Fractional (Fold a (Exp b)) # 

Methods

(/) :: Fold a (Exp b) -> Fold a (Exp b) -> Fold a (Exp b) #

recip :: Fold a (Exp b) -> Fold a (Exp b) #

fromRational :: Rational -> Fold a (Exp b) #

Num b => Num (Fold a (Exp b)) # 

Methods

(+) :: Fold a (Exp b) -> Fold a (Exp b) -> Fold a (Exp b) #

(-) :: Fold a (Exp b) -> Fold a (Exp b) -> Fold a (Exp b) #

(*) :: Fold a (Exp b) -> Fold a (Exp b) -> Fold a (Exp b) #

negate :: Fold a (Exp b) -> Fold a (Exp b) #

abs :: Fold a (Exp b) -> Fold a (Exp b) #

signum :: Fold a (Exp b) -> Fold a (Exp b) #

fromInteger :: Integer -> Fold a (Exp b) #

type EltT Exp t # 
type EltT Exp t = Elt t
type Plain (Exp e) # 
type Plain (Exp e) = e
type Plain ((:.) ix (Exp e)) # 
type Plain ((:.) ix (Exp e)) = (:.) (Plain ix) e

Type classes

Basic type classes

class Elt a => Eq a where #

The Eq class defines equality == and inequality /= for scalar Accelerate expressions.

For convenience, we include Elt as a superclass.

Minimal complete definition

(==) | (/=)

Methods

(==) :: Exp a -> Exp a -> Exp Bool infix 4 #

(/=) :: Exp a -> Exp a -> Exp Bool infix 4 #

Instances

Eq Bool # 

Methods

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

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

Eq Char # 

Methods

(==) :: Exp Char -> Exp Char -> Exp Bool #

(/=) :: Exp Char -> Exp Char -> Exp Bool #

Eq Double # 
Eq Float # 

Methods

(==) :: Exp Float -> Exp Float -> Exp Bool #

(/=) :: Exp Float -> Exp Float -> Exp Bool #

Eq Int # 

Methods

(==) :: Exp Int -> Exp Int -> Exp Bool #

(/=) :: Exp Int -> Exp Int -> Exp Bool #

Eq Int8 # 

Methods

(==) :: Exp Int8 -> Exp Int8 -> Exp Bool #

(/=) :: Exp Int8 -> Exp Int8 -> Exp Bool #

Eq Int16 # 

Methods

(==) :: Exp Int16 -> Exp Int16 -> Exp Bool #

(/=) :: Exp Int16 -> Exp Int16 -> Exp Bool #

Eq Int32 # 

Methods

(==) :: Exp Int32 -> Exp Int32 -> Exp Bool #

(/=) :: Exp Int32 -> Exp Int32 -> Exp Bool #

Eq Int64 # 

Methods

(==) :: Exp Int64 -> Exp Int64 -> Exp Bool #

(/=) :: Exp Int64 -> Exp Int64 -> Exp Bool #

Eq Word # 

Methods

(==) :: Exp Word -> Exp Word -> Exp Bool #

(/=) :: Exp Word -> Exp Word -> Exp Bool #

Eq Word8 # 

Methods

(==) :: Exp Word8 -> Exp Word8 -> Exp Bool #

(/=) :: Exp Word8 -> Exp Word8 -> Exp Bool #

Eq Word16 # 
Eq Word32 # 
Eq Word64 # 
Eq () # 

Methods

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

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

Eq CChar # 

Methods

(==) :: Exp CChar -> Exp CChar -> Exp Bool #

(/=) :: Exp CChar -> Exp CChar -> Exp Bool #

Eq CSChar # 
Eq CUChar # 
Eq CShort # 
Eq CUShort # 
Eq CInt # 

Methods

(==) :: Exp CInt -> Exp CInt -> Exp Bool #

(/=) :: Exp CInt -> Exp CInt -> Exp Bool #

Eq CUInt # 

Methods

(==) :: Exp CUInt -> Exp CUInt -> Exp Bool #

(/=) :: Exp CUInt -> Exp CUInt -> Exp Bool #

Eq CLong # 

Methods

(==) :: Exp CLong -> Exp CLong -> Exp Bool #

(/=) :: Exp CLong -> Exp CLong -> Exp Bool #

Eq CULong # 
Eq CLLong # 
Eq CULLong # 
Eq CFloat # 
Eq CDouble # 
(Eq a, Eq b) => Eq (a, b) # 

Methods

(==) :: Exp (a, b) -> Exp (a, b) -> Exp Bool #

(/=) :: Exp (a, b) -> Exp (a, b) -> Exp Bool #

(Eq a, Eq b, Eq c) => Eq (a, b, c) # 

Methods

(==) :: Exp (a, b, c) -> Exp (a, b, c) -> Exp Bool #

(/=) :: Exp (a, b, c) -> Exp (a, b, c) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) # 

Methods

(==) :: Exp (a, b, c, d) -> Exp (a, b, c, d) -> Exp Bool #

(/=) :: Exp (a, b, c, d) -> Exp (a, b, c, d) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e) # 

Methods

(==) :: Exp (a, b, c, d, e) -> Exp (a, b, c, d, e) -> Exp Bool #

(/=) :: Exp (a, b, c, d, e) -> Exp (a, b, c, d, e) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (a, b, c, d, e, f) # 

Methods

(==) :: Exp (a, b, c, d, e, f) -> Exp (a, b, c, d, e, f) -> Exp Bool #

(/=) :: Exp (a, b, c, d, e, f) -> Exp (a, b, c, d, e, f) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (a, b, c, d, e, f, g) # 

Methods

(==) :: Exp (a, b, c, d, e, f, g) -> Exp (a, b, c, d, e, f, g) -> Exp Bool #

(/=) :: Exp (a, b, c, d, e, f, g) -> Exp (a, b, c, d, e, f, g) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h) => Eq (a, b, c, d, e, f, g, h) # 

Methods

(==) :: Exp (a, b, c, d, e, f, g, h) -> Exp (a, b, c, d, e, f, g, h) -> Exp Bool #

(/=) :: Exp (a, b, c, d, e, f, g, h) -> Exp (a, b, c, d, e, f, g, h) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) => Eq (a, b, c, d, e, f, g, h, i) # 

Methods

(==) :: Exp (a, b, c, d, e, f, g, h, i) -> Exp (a, b, c, d, e, f, g, h, i) -> Exp Bool #

(/=) :: Exp (a, b, c, d, e, f, g, h, i) -> Exp (a, b, c, d, e, f, g, h, i) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j) => Eq (a, b, c, d, e, f, g, h, i, j) # 

Methods

(==) :: Exp (a, b, c, d, e, f, g, h, i, j) -> Exp (a, b, c, d, e, f, g, h, i, j) -> Exp Bool #

(/=) :: Exp (a, b, c, d, e, f, g, h, i, j) -> Exp (a, b, c, d, e, f, g, h, i, j) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k) => Eq (a, b, c, d, e, f, g, h, i, j, k) # 

Methods

(==) :: Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp Bool #

(/=) :: Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l) => Eq (a, b, c, d, e, f, g, h, i, j, k, l) # 

Methods

(==) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp Bool #

(/=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m) # 

Methods

(==) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp Bool #

(/=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n) # 

Methods

(==) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp Bool #

(/=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) # 

Methods

(==) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp Bool #

(/=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp Bool #

class Eq a => Ord a where #

The Ord class for totally ordered datatypes

Minimal complete definition

(<=)

Methods

(<) :: Exp a -> Exp a -> Exp Bool infix 4 #

(>) :: Exp a -> Exp a -> Exp Bool infix 4 #

(<=) :: Exp a -> Exp a -> Exp Bool infix 4 #

(>=) :: Exp a -> Exp a -> Exp Bool infix 4 #

min :: Exp a -> Exp a -> Exp a #

max :: Exp a -> Exp a -> Exp a #

Instances

Ord Bool # 

Methods

(<) :: Exp Bool -> Exp Bool -> Exp Bool #

(>) :: Exp Bool -> Exp Bool -> Exp Bool #

(<=) :: Exp Bool -> Exp Bool -> Exp Bool #

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

min :: Exp Bool -> Exp Bool -> Exp Bool #

max :: Exp Bool -> Exp Bool -> Exp Bool #

Ord Char # 

Methods

(<) :: Exp Char -> Exp Char -> Exp Bool #

(>) :: Exp Char -> Exp Char -> Exp Bool #

(<=) :: Exp Char -> Exp Char -> Exp Bool #

(>=) :: Exp Char -> Exp Char -> Exp Bool #

min :: Exp Char -> Exp Char -> Exp Char #

max :: Exp Char -> Exp Char -> Exp Char #

Ord Double # 
Ord Float # 
Ord Int # 

Methods

(<) :: Exp Int -> Exp Int -> Exp Bool #

(>) :: Exp Int -> Exp Int -> Exp Bool #

(<=) :: Exp Int -> Exp Int -> Exp Bool #

(>=) :: Exp Int -> Exp Int -> Exp Bool #

min :: Exp Int -> Exp Int -> Exp Int #

max :: Exp Int -> Exp Int -> Exp Int #

Ord Int8 # 

Methods

(<) :: Exp Int8 -> Exp Int8 -> Exp Bool #

(>) :: Exp Int8 -> Exp Int8 -> Exp Bool #

(<=) :: Exp Int8 -> Exp Int8 -> Exp Bool #

(>=) :: Exp Int8 -> Exp Int8 -> Exp Bool #

min :: Exp Int8 -> Exp Int8 -> Exp Int8 #

max :: Exp Int8 -> Exp Int8 -> Exp Int8 #

Ord Int16 # 
Ord Int32 # 
Ord Int64 # 
Ord Word # 

Methods

(<) :: Exp Word -> Exp Word -> Exp Bool #

(>) :: Exp Word -> Exp Word -> Exp Bool #

(<=) :: Exp Word -> Exp Word -> Exp Bool #

(>=) :: Exp Word -> Exp Word -> Exp Bool #

min :: Exp Word -> Exp Word -> Exp Word #

max :: Exp Word -> Exp Word -> Exp Word #

Ord Word8 # 
Ord Word16 # 
Ord Word32 # 
Ord Word64 #