accelerate-1.3.0.0: An embedded language for accelerated array processing
Copyright[2008..2020] The Accelerate Team
LicenseBSD3
MaintainerTrevor L. McDonell <trevor.mcdonell@gmail.com>
Stabilityexperimental
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Data.Array.Accelerate

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:

Examples:
Starting a new project:

Accelerate and its associated packages are available on both Hackage and Stackage. A project template is available to help create a new projects using the stack build tool. To create a new project using the template:

stack new PROJECT_NAME https://github.com/AccelerateHS/accelerate/raw/stable/accelerate.hsfiles
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 Source #

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.

A simple example

As a simple example, to compute a vector dot product we can 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.

Avoiding nested parallelism

As mentioned above, embedded scalar computations of type Exp can not initiate further collective operations.

Suppose we wanted to extend our above dotp function to matrix-vector multiplication. First, let's rewrite our dotp function to take Acc arrays as input (which is typically what we want):

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

We might then be inclined to lift our dot-product program to the following (incorrect) matrix-vector product, by applying dotp to each row of the input matrix:

mvm_ndp :: Num a => Acc (Matrix a) -> Acc (Vector a) -> Acc (Vector a)
mvm_ndp mat vec =
  let Z :. rows :. cols  = unlift (shape mat)  :: Z :. Exp Int :. Exp Int
  in  generate (index1 rows)
               (\row -> the $ dotp vec (slice mat (lift (row :. All))))

Here, we use generate to create a one-dimensional vector by applying at each index a function to slice out the corresponding row of the matrix to pass to the dotp function. However, since both generate and slice are data-parallel operations, and moreover that slice depends on the argument row given to it by the generate function, this definition requires nested data-parallelism, and is thus not permitted. The clue that this definition is invalid is that in order to create a program which will be accepted by the type checker, we must use the function the to retrieve the result of the dotp operation, effectively concealing that dotp is a collective array computation in order to match the type expected by generate, which is that of scalar expressions. Additionally, since we have fooled the type-checker, this problem will only be discovered at program runtime.

In order to avoid this problem, we can make use of the fact that operations in Accelerate are rank polymorphic. The fold operation reduces along the innermost dimension of an array of arbitrary rank, reducing the rank (dimensionality) of the array by one. Thus, we can replicate the input vector to as many rows there are in the input matrix, and perform the dot-product of the vector with every row simultaneously:

mvm :: A.Num a => Acc (Matrix a) -> Acc (Vector a) -> Acc (Vector a)
mvm mat vec =
  let Z :. rows :. cols = unlift (shape mat) :: Z :. Exp Int :. Exp Int
      vec'              = A.replicate (lift (Z :. rows :. All)) vec
  in
  A.fold (+) 0 ( A.zipWith (*) mat vec' )

Note that the intermediate, replicated array vec' is never actually created in memory; it will be fused directly into the operation which consumes it. We discuss fusion next.

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:

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:

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

Instances details
IfThenElse Acc Source # 
Instance details

Defined in Data.Array.Accelerate.Prelude

Associated Types

type EltT Acc a Source #

Methods

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

Unlift Acc () Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

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

Lift Acc () Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain () Source #

Methods

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

Unlift Acc (Acc a) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

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

Lift Acc (Acc a) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (Acc a) Source #

Methods

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

(Arrays x0, Arrays x1) => Unlift Acc (Acc x0, Acc x1) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Acc (Plain (Acc x0, Acc x1)) -> (Acc x0, Acc x1) Source #

((Lift Acc x0, Lift Acc x1), (Arrays (Plain x0), Arrays (Plain x1))) => Lift Acc (x0, x1) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (x0, x1) Source #

Methods

lift :: (x0, x1) -> Acc (Plain (x0, x1)) Source #

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

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (Array sh e) Source #

Methods

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

(Arrays x0, Arrays x1, Arrays x2) => Unlift Acc (Acc x0, Acc x1, Acc x2) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Acc (Plain (Acc x0, Acc x1, Acc x2)) -> (Acc x0, Acc x1, Acc x2) Source #

((Lift Acc x0, Lift Acc x1, Lift Acc x2), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2))) => Lift Acc (x0, x1, x2) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (x0, x1, x2) Source #

Methods

lift :: (x0, x1, x2) -> Acc (Plain (x0, x1, x2)) Source #

(Arrays x0, Arrays x1, Arrays x2, Arrays x3) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Acc (Plain (Acc x0, Acc x1, Acc x2, Acc x3)) -> (Acc x0, Acc x1, Acc x2, Acc x3) Source #

((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3))) => Lift Acc (x0, x1, x2, x3) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (x0, x1, x2, x3) Source #

Methods

lift :: (x0, x1, x2, x3) -> Acc (Plain (x0, x1, x2, x3)) Source #

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Acc (Plain (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4)) -> (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4) Source #

((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4))) => Lift Acc (x0, x1, x2, x3, x4) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (x0, x1, x2, x3, x4) Source #

Methods

lift :: (x0, x1, x2, x3, x4) -> Acc (Plain (x0, x1, x2, x3, x4)) Source #

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Acc (Plain (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5)) -> (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5) Source #

((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4, Lift Acc x5), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4), Arrays (Plain x5))) => Lift Acc (x0, x1, x2, x3, x4, x5) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (x0, x1, x2, x3, x4, x5) Source #

Methods

lift :: (x0, x1, x2, x3, x4, x5) -> Acc (Plain (x0, x1, x2, x3, x4, x5)) Source #

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Acc (Plain (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6)) -> (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6) Source #

((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4, Lift Acc x5, Lift Acc x6), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4), Arrays (Plain x5), Arrays (Plain x6))) => Lift Acc (x0, x1, x2, x3, x4, x5, x6) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (x0, x1, x2, x3, x4, x5, x6) Source #

Methods

lift :: (x0, x1, x2, x3, x4, x5, x6) -> Acc (Plain (x0, x1, x2, x3, x4, x5, x6)) Source #

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Acc (Plain (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7)) -> (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7) Source #

((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4, Lift Acc x5, Lift Acc x6, Lift Acc x7), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4), Arrays (Plain x5), Arrays (Plain x6), Arrays (Plain x7))) => Lift Acc (x0, x1, x2, x3, x4, x5, x6, x7) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (x0, x1, x2, x3, x4, x5, x6, x7) Source #

Methods

lift :: (x0, x1, x2, x3, x4, x5, x6, x7) -> Acc (Plain (x0, x1, x2, x3, x4, x5, x6, x7)) Source #

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Acc (Plain (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8)) -> (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8) Source #

((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4, Lift Acc x5, Lift Acc x6, Lift Acc x7, Lift Acc x8), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4), Arrays (Plain x5), Arrays (Plain x6), Arrays (Plain x7), Arrays (Plain x8))) => Lift Acc (x0, x1, x2, x3, x4, x5, x6, x7, x8) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8) Source #

Methods

lift :: (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Acc (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8)) Source #

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Acc (Plain (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9)) -> (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9) Source #

((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4, Lift Acc x5, Lift Acc x6, Lift Acc x7, Lift Acc x8, Lift Acc x9), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4), Arrays (Plain x5), Arrays (Plain x6), Arrays (Plain x7), Arrays (Plain x8), Arrays (Plain x9))) => Lift Acc (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) Source #

Methods

lift :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Acc (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9)) Source #

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Acc (Plain (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10)) -> (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10) Source #

((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4, Lift Acc x5, Lift Acc x6, Lift Acc x7, Lift Acc x8, Lift Acc x9, Lift Acc x10), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4), Arrays (Plain x5), Arrays (Plain x6), Arrays (Plain x7), Arrays (Plain x8), Arrays (Plain x9), Arrays (Plain x10))) => Lift Acc (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) Source #

Methods

lift :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Acc (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10)) Source #

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Acc (Plain (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11)) -> (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11) Source #

((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4, Lift Acc x5, Lift Acc x6, Lift Acc x7, Lift Acc x8, Lift Acc x9, Lift Acc x10, Lift Acc x11), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4), Arrays (Plain x5), Arrays (Plain x6), Arrays (Plain x7), Arrays (Plain x8), Arrays (Plain x9), Arrays (Plain x10), Arrays (Plain x11))) => Lift Acc (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) Source #

Methods

lift :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Acc (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11)) Source #

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11, Arrays x12) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Acc (Plain (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12)) -> (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12) Source #

((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4, Lift Acc x5, Lift Acc x6, Lift Acc x7, Lift Acc x8, Lift Acc x9, Lift Acc x10, Lift Acc x11, Lift Acc x12), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4), Arrays (Plain x5), Arrays (Plain x6), Arrays (Plain x7), Arrays (Plain x8), Arrays (Plain x9), Arrays (Plain x10), Arrays (Plain x11), Arrays (Plain x12))) => Lift Acc (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) Source #

Methods

lift :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Acc (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12)) Source #

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11, Arrays x12, Arrays x13) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12, Acc x13) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Acc (Plain (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12, Acc x13)) -> (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12, Acc x13) Source #

((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4, Lift Acc x5, Lift Acc x6, Lift Acc x7, Lift Acc x8, Lift Acc x9, Lift Acc x10, Lift Acc x11, Lift Acc x12, Lift Acc x13), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4), Arrays (Plain x5), Arrays (Plain x6), Arrays (Plain x7), Arrays (Plain x8), Arrays (Plain x9), Arrays (Plain x10), Arrays (Plain x11), Arrays (Plain x12), Arrays (Plain x13))) => Lift Acc (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) Source #

Methods

lift :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Acc (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13)) Source #

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11, Arrays x12, Arrays x13, Arrays x14) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12, Acc x13, Acc x14) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Acc (Plain (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12, Acc x13, Acc x14)) -> (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12, Acc x13, Acc x14) Source #

((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4, Lift Acc x5, Lift Acc x6, Lift Acc x7, Lift Acc x8, Lift Acc x9, Lift Acc x10, Lift Acc x11, Lift Acc x12, Lift Acc x13, Lift Acc x14), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4), Arrays (Plain x5), Arrays (Plain x6), Arrays (Plain x7), Arrays (Plain x8), Arrays (Plain x9), Arrays (Plain x10), Arrays (Plain x11), Arrays (Plain x12), Arrays (Plain x13), Arrays (Plain x14))) => Lift Acc (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) Source #

Methods

lift :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Acc (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14)) Source #

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11, Arrays x12, Arrays x13, Arrays x14, Arrays x15) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12, Acc x13, Acc x14, Acc x15) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Acc (Plain (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12, Acc x13, Acc x14, Acc x15)) -> (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12, Acc x13, Acc x14, Acc x15) Source #

((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4, Lift Acc x5, Lift Acc x6, Lift Acc x7, Lift Acc x8, Lift Acc x9, Lift Acc x10, Lift Acc x11, Lift Acc x12, Lift Acc x13, Lift Acc x14, Lift Acc x15), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4), Arrays (Plain x5), Arrays (Plain x6), Arrays (Plain x7), Arrays (Plain x8), Arrays (Plain x9), Arrays (Plain x10), Arrays (Plain x11), Arrays (Plain x12), Arrays (Plain x13), Arrays (Plain x14), Arrays (Plain x15))) => Lift Acc (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) Source #

Methods

lift :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Acc (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15)) Source #

Arrays arrs => Show (Acc arrs) Source # 
Instance details

Defined in Data.Array.Accelerate.Pretty

Methods

showsPrec :: Int -> Acc arrs -> ShowS #

show :: Acc arrs -> String #

showList :: [Acc arrs] -> ShowS #

Arrays b => Afunction (Acc b) Source # 
Instance details

Defined in Data.Array.Accelerate.Trafo.Sharing

Associated Types

type AfunctionR (Acc b) Source #

type ArraysFunctionR (Acc b)

Methods

afunctionRepr :: AfunctionRepr (Acc b) (AfunctionR (Acc b)) (ArraysFunctionR (Acc b))

convertOpenAfun :: HasCallStack => Config -> ArrayLayout aenv aenv -> Acc b -> OpenAfun aenv (ArraysFunctionR (Acc b))

Afunction (Acc a -> f) => Show (Acc a -> f) Source # 
Instance details

Defined in Data.Array.Accelerate.Pretty

Methods

showsPrec :: Int -> (Acc a -> f) -> ShowS #

show :: (Acc a -> f) -> String #

showList :: [Acc a -> f] -> ShowS #

(Arrays a, Afunction r) => Afunction (Acc a -> r) Source # 
Instance details

Defined in Data.Array.Accelerate.Trafo.Sharing

Associated Types

type AfunctionR (Acc a -> r) Source #

type ArraysFunctionR (Acc a -> r)

Methods

afunctionRepr :: AfunctionRepr (Acc a -> r) (AfunctionR (Acc a -> r)) (ArraysFunctionR (Acc a -> r))

convertOpenAfun :: HasCallStack => Config -> ArrayLayout aenv aenv -> (Acc a -> r) -> OpenAfun aenv (ArraysFunctionR (Acc a -> r))

type EltT Acc a Source # 
Instance details

Defined in Data.Array.Accelerate.Prelude

type EltT Acc a = Arrays a
type AfunctionR (Acc b) Source # 
Instance details

Defined in Data.Array.Accelerate.Trafo.Sharing

type AfunctionR (Acc b) = b
type Plain (Acc a) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

type Plain (Acc a) = a
type AfunctionR (Acc a -> r) Source # 
Instance details

Defined in Data.Array.Accelerate.Trafo.Sharing

type AfunctionR (Acc a -> r) = a -> AfunctionR r

Arrays

data Array sh e Source #

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 16-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

Instances details
(Shape sh, Elt e) => Lift Acc (Array sh e) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (Array sh e) Source #

Methods

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

Elt e => IsList (Array DIM1 e) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

Associated Types

type Item (Array DIM1 e) #

Methods

fromList :: [Item (Array DIM1 e)] -> Array DIM1 e #

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

toList :: Array DIM1 e -> [Item (Array DIM1 e)] #

(Shape sh, Elt e, Eq sh, Eq e) => Eq (Array sh e) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

Methods

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

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

(Shape sh, Elt e, Show e) => Show (Array sh e) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

Methods

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

show :: Array sh e -> String #

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

(Shape sh, Elt e) => NFData (Array sh e) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

Methods

rnf :: Array sh e -> () #

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

Defined in Data.Array.Accelerate.Sugar.Array

Associated Types

type ArraysR (Array sh e)

Methods

arraysR :: ArraysR (ArraysR (Array sh e))

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

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

type Item (Vector e) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

type Item (Vector e) = e
type Plain (Array sh e) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

type Plain (Array sh e) = Array sh e

class Arrays a Source #

The Arrays class characterises the types which can appear in collective Accelerate computations of type Acc.

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

Instances

Instances details
Arrays () Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

Associated Types

type ArraysR ()

Methods

arraysR :: ArraysR (ArraysR ())

toArr :: ArraysR () -> ()

fromArr :: () -> ArraysR ()

(Arrays x0, Arrays x1) => Arrays (x0, x1) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

Associated Types

type ArraysR (x0, x1)

Methods

arraysR :: ArraysR (ArraysR (x0, x1))

toArr :: ArraysR (x0, x1) -> (x0, x1)

fromArr :: (x0, x1) -> ArraysR (x0, x1)

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

Defined in Data.Array.Accelerate.Sugar.Array

Associated Types

type ArraysR (Array sh e)

Methods

arraysR :: ArraysR (ArraysR (Array sh e))

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

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

(Arrays x0, Arrays x1, Arrays x2) => Arrays (x0, x1, x2) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

Associated Types

type ArraysR (x0, x1, x2)

Methods

arraysR :: ArraysR (ArraysR (x0, x1, x2))

toArr :: ArraysR (x0, x1, x2) -> (x0, x1, x2)

fromArr :: (x0, x1, x2) -> ArraysR (x0, x1, x2)

(Arrays x0, Arrays x1, Arrays x2, Arrays x3) => Arrays (x0, x1, x2, x3) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

Associated Types

type ArraysR (x0, x1, x2, x3)

Methods

arraysR :: ArraysR (ArraysR (x0, x1, x2, x3))

toArr :: ArraysR (x0, x1, x2, x3) -> (x0, x1, x2, x3)

fromArr :: (x0, x1, x2, x3) -> ArraysR (x0, x1, x2, x3)

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4) => Arrays (x0, x1, x2, x3, x4) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

Associated Types

type ArraysR (x0, x1, x2, x3, x4)

Methods

arraysR :: ArraysR (ArraysR (x0, x1, x2, x3, x4))

toArr :: ArraysR (x0, x1, x2, x3, x4) -> (x0, x1, x2, x3, x4)

fromArr :: (x0, x1, x2, x3, x4) -> ArraysR (x0, x1, x2, x3, x4)

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5) => Arrays (x0, x1, x2, x3, x4, x5) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

Associated Types

type ArraysR (x0, x1, x2, x3, x4, x5)

Methods

arraysR :: ArraysR (ArraysR (x0, x1, x2, x3, x4, x5))

toArr :: ArraysR (x0, x1, x2, x3, x4, x5) -> (x0, x1, x2, x3, x4, x5)

fromArr :: (x0, x1, x2, x3, x4, x5) -> ArraysR (x0, x1, x2, x3, x4, x5)

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6) => Arrays (x0, x1, x2, x3, x4, x5, x6) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

Associated Types

type ArraysR (x0, x1, x2, x3, x4, x5, x6)

Methods

arraysR :: ArraysR (ArraysR (x0, x1, x2, x3, x4, x5, x6))

toArr :: ArraysR (x0, x1, x2, x3, x4, x5, x6) -> (x0, x1, x2, x3, x4, x5, x6)

fromArr :: (x0, x1, x2, x3, x4, x5, x6) -> ArraysR (x0, x1, x2, x3, x4, x5, x6)

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7) => Arrays (x0, x1, x2, x3, x4, x5, x6, x7) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

Associated Types

type ArraysR (x0, x1, x2, x3, x4, x5, x6, x7)

Methods

arraysR :: ArraysR (ArraysR (x0, x1, x2, x3, x4, x5, x6, x7))

toArr :: ArraysR (x0, x1, x2, x3, x4, x5, x6, x7) -> (x0, x1, x2, x3, x4, x5, x6, x7)

fromArr :: (x0, x1, x2, x3, x4, x5, x6, x7) -> ArraysR (x0, x1, x2, x3, x4, x5, x6, x7)

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8) => Arrays (x0, x1, x2, x3, x4, x5, x6, x7, x8) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

Associated Types

type ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8)

Methods

arraysR :: ArraysR (ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8))

toArr :: ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8)

fromArr :: (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8)

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9) => Arrays (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

Associated Types

type ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9)

Methods

arraysR :: ArraysR (ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9))

toArr :: ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9)

fromArr :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9)

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10) => Arrays (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

Associated Types

type ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10)

Methods

arraysR :: ArraysR (ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10))

toArr :: ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10)

fromArr :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10)

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11) => Arrays (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

Associated Types

type ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11)

Methods

arraysR :: ArraysR (ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11))

toArr :: ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11)

fromArr :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11)

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11, Arrays x12) => Arrays (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

Associated Types

type ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12)

Methods

arraysR :: ArraysR (ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12))

toArr :: ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12)

fromArr :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12)

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11, Arrays x12, Arrays x13) => Arrays (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

Associated Types

type ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13)

Methods

arraysR :: ArraysR (ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13))

toArr :: ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13)

fromArr :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13)

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11, Arrays x12, Arrays x13, Arrays x14) => Arrays (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

Associated Types

type ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14)

Methods

arraysR :: ArraysR (ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14))

toArr :: ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14)

fromArr :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14)

(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11, Arrays x12, Arrays x13, Arrays x14, Arrays x15) => Arrays (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

Associated Types

type ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15)

Methods

arraysR :: ArraysR (ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15))

toArr :: ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15)

fromArr :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15)

type Scalar Source #

Arguments

 = Array DIM0

Scalar arrays hold a single element

type Vector Source #

Arguments

 = Array DIM1

Vectors are one-dimensional arrays

type Matrix Source #

Arguments

 = Array DIM2

Matrices are two-dimensional arrays

type Segments = Vector Source #

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 sub-arrays.

Array elements

class Elt a Source #

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

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 (half, single, and double precision)
  • Char
  • Bool
  • ()
  • Shapes formed from Z and (:.)
  • Nested tuples of all of these, currently up to 16-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:

For simple types it is possible to derive Elt automatically, for example:

data Point = Point Int Float
  deriving (Generic, Elt)
data Option a = None | Just a
  deriving (Generic, Elt)

See the function match for details on how to use sum types in embedded code.

Instances

Instances details
Elt Bool Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR Bool

Methods

eltR :: TypeR (EltR Bool)

tagsR :: [TagR (EltR Bool)]

fromElt :: Bool -> EltR Bool

toElt :: EltR Bool -> Bool

Elt Char Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR Char

Methods

eltR :: TypeR (EltR Char)

tagsR :: [TagR (EltR Char)]

fromElt :: Char -> EltR Char

toElt :: EltR Char -> Char

Elt Double Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR Double

Methods

eltR :: TypeR (EltR Double)

tagsR :: [TagR (EltR Double)]

fromElt :: Double -> EltR Double

toElt :: EltR Double -> Double

Elt Float Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR Float

Methods

eltR :: TypeR (EltR Float)

tagsR :: [TagR (EltR Float)]

fromElt :: Float -> EltR Float

toElt :: EltR Float -> Float

Elt Int Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR Int

Methods

eltR :: TypeR (EltR Int)

tagsR :: [TagR (EltR Int)]

fromElt :: Int -> EltR Int

toElt :: EltR Int -> Int

Elt Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR Int8

Methods

eltR :: TypeR (EltR Int8)

tagsR :: [TagR (EltR Int8)]

fromElt :: Int8 -> EltR Int8

toElt :: EltR Int8 -> Int8

Elt Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR Int16

Methods

eltR :: TypeR (EltR Int16)

tagsR :: [TagR (EltR Int16)]

fromElt :: Int16 -> EltR Int16

toElt :: EltR Int16 -> Int16

Elt Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR Int32

Methods

eltR :: TypeR (EltR Int32)

tagsR :: [TagR (EltR Int32)]

fromElt :: Int32 -> EltR Int32

toElt :: EltR Int32 -> Int32

Elt Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR Int64

Methods

eltR :: TypeR (EltR Int64)

tagsR :: [TagR (EltR Int64)]

fromElt :: Int64 -> EltR Int64

toElt :: EltR Int64 -> Int64

Elt Ordering Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR Ordering

Methods

eltR :: TypeR (EltR Ordering)

tagsR :: [TagR (EltR Ordering)]

fromElt :: Ordering -> EltR Ordering

toElt :: EltR Ordering -> Ordering

Elt Word Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR Word

Methods

eltR :: TypeR (EltR Word)

tagsR :: [TagR (EltR Word)]

fromElt :: Word -> EltR Word

toElt :: EltR Word -> Word

Elt Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR Word8

Methods

eltR :: TypeR (EltR Word8)

tagsR :: [TagR (EltR Word8)]

fromElt :: Word8 -> EltR Word8

toElt :: EltR Word8 -> Word8

Elt Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR Word16

Methods

eltR :: TypeR (EltR Word16)

tagsR :: [TagR (EltR Word16)]

fromElt :: Word16 -> EltR Word16

toElt :: EltR Word16 -> Word16

Elt Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR Word32

Methods

eltR :: TypeR (EltR Word32)

tagsR :: [TagR (EltR Word32)]

fromElt :: Word32 -> EltR Word32

toElt :: EltR Word32 -> Word32

Elt Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR Word64

Methods

eltR :: TypeR (EltR Word64)

tagsR :: [TagR (EltR Word64)]

fromElt :: Word64 -> EltR Word64

toElt :: EltR Word64 -> Word64

Elt () Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR ()

Methods

eltR :: TypeR (EltR ())

tagsR :: [TagR (EltR ())]

fromElt :: () -> EltR ()

toElt :: EltR () -> ()

Elt CChar Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR CChar

Methods

eltR :: TypeR (EltR CChar)

tagsR :: [TagR (EltR CChar)]

fromElt :: CChar -> EltR CChar

toElt :: EltR CChar -> CChar

Elt CSChar Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR CSChar

Methods

eltR :: TypeR (EltR CSChar)

tagsR :: [TagR (EltR CSChar)]

fromElt :: CSChar -> EltR CSChar

toElt :: EltR CSChar -> CSChar

Elt CUChar Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR CUChar

Methods

eltR :: TypeR (EltR CUChar)

tagsR :: [TagR (EltR CUChar)]

fromElt :: CUChar -> EltR CUChar

toElt :: EltR CUChar -> CUChar

Elt CShort Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR CShort

Methods

eltR :: TypeR (EltR CShort)

tagsR :: [TagR (EltR CShort)]

fromElt :: CShort -> EltR CShort

toElt :: EltR CShort -> CShort

Elt CUShort Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR CUShort

Methods

eltR :: TypeR (EltR CUShort)

tagsR :: [TagR (EltR CUShort)]

fromElt :: CUShort -> EltR CUShort

toElt :: EltR CUShort -> CUShort

Elt CInt Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR CInt

Methods

eltR :: TypeR (EltR CInt)

tagsR :: [TagR (EltR CInt)]

fromElt :: CInt -> EltR CInt

toElt :: EltR CInt -> CInt

Elt CUInt Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR CUInt

Methods

eltR :: TypeR (EltR CUInt)

tagsR :: [TagR (EltR CUInt)]

fromElt :: CUInt -> EltR CUInt

toElt :: EltR CUInt -> CUInt

Elt CLong Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR CLong

Methods

eltR :: TypeR (EltR CLong)

tagsR :: [TagR (EltR CLong)]

fromElt :: CLong -> EltR CLong

toElt :: EltR CLong -> CLong

Elt CULong Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR CULong

Methods

eltR :: TypeR (EltR CULong)

tagsR :: [TagR (EltR CULong)]

fromElt :: CULong -> EltR CULong

toElt :: EltR CULong -> CULong

Elt CLLong Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR CLLong

Methods

eltR :: TypeR (EltR CLLong)

tagsR :: [TagR (EltR CLLong)]

fromElt :: CLLong -> EltR CLLong

toElt :: EltR CLLong -> CLLong

Elt CULLong Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR CULLong

Methods

eltR :: TypeR (EltR CULLong)

tagsR :: [TagR (EltR CULLong)]

fromElt :: CULLong -> EltR CULLong

toElt :: EltR CULLong -> CULLong

Elt CFloat Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR CFloat

Methods

eltR :: TypeR (EltR CFloat)

tagsR :: [TagR (EltR CFloat)]

fromElt :: CFloat -> EltR CFloat

toElt :: EltR CFloat -> CFloat

Elt CDouble Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR CDouble

Methods

eltR :: TypeR (EltR CDouble)

tagsR :: [TagR (EltR CDouble)]

fromElt :: CDouble -> EltR CDouble

toElt :: EltR CDouble -> CDouble

Elt Half Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR Half

Methods

eltR :: TypeR (EltR Half)

tagsR :: [TagR (EltR Half)]

fromElt :: Half -> EltR Half

toElt :: EltR Half -> Half

Elt All Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type EltR All

Methods

eltR :: TypeR (EltR All)

tagsR :: [TagR (EltR All)]

fromElt :: All -> EltR All

toElt :: EltR All -> All

Elt Z Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type EltR Z

Methods

eltR :: TypeR (EltR Z)

tagsR :: [TagR (EltR Z)]

fromElt :: Z -> EltR Z

toElt :: EltR Z -> Z

Elt a => Elt (Maybe a) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR (Maybe a)

Methods

eltR :: TypeR (EltR (Maybe a))

tagsR :: [TagR (EltR (Maybe a))]

fromElt :: Maybe a -> EltR (Maybe a)

toElt :: EltR (Maybe a) -> Maybe a

Elt a => Elt (Ratio a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Ratio

Associated Types

type EltR (Ratio a)

Methods

eltR :: TypeR (EltR (Ratio a))

tagsR :: [TagR (EltR (Ratio a))]

fromElt :: Ratio a -> EltR (Ratio a)

toElt :: EltR (Ratio a) -> Ratio a

Elt a => Elt (Complex a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Complex

Associated Types

type EltR (Complex a)

Methods

eltR :: TypeR (EltR (Complex a))

tagsR :: [TagR (EltR (Complex a))]

fromElt :: Complex a -> EltR (Complex a)

toElt :: EltR (Complex a) -> Complex a

Elt a => Elt (Min a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Semigroup

Associated Types

type EltR (Min a)

Methods

eltR :: TypeR (EltR (Min a))

tagsR :: [TagR (EltR (Min a))]

fromElt :: Min a -> EltR (Min a)

toElt :: EltR (Min a) -> Min a

Elt a => Elt (Max a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Semigroup

Associated Types

type EltR (Max a)

Methods

eltR :: TypeR (EltR (Max a))

tagsR :: [TagR (EltR (Max a))]

fromElt :: Max a -> EltR (Max a)

toElt :: EltR (Max a) -> Max a

Elt a => Elt (Sum a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Monoid

Associated Types

type EltR (Sum a)

Methods

eltR :: TypeR (EltR (Sum a))

tagsR :: [TagR (EltR (Sum a))]

fromElt :: Sum a -> EltR (Sum a)

toElt :: EltR (Sum a) -> Sum a

Elt a => Elt (Product a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Monoid

Associated Types

type EltR (Product a)

Methods

eltR :: TypeR (EltR (Product a))

tagsR :: [TagR (EltR (Product a))]

fromElt :: Product a -> EltR (Product a)

toElt :: EltR (Product a) -> Product a

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

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type EltR (Any (sh :. Int))

Methods

eltR :: TypeR (EltR (Any (sh :. Int)))

tagsR :: [TagR (EltR (Any (sh :. Int)))]

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

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

Elt (Any Z) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type EltR (Any Z)

Methods

eltR :: TypeR (EltR (Any Z))

tagsR :: [TagR (EltR (Any Z))]

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

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

(Elt a, Elt b) => Elt (Either a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR (Either a b)

Methods

eltR :: TypeR (EltR (Either a b))

tagsR :: [TagR (EltR (Either a b))]

fromElt :: Either a b -> EltR (Either a b)

toElt :: EltR (Either a b) -> Either a b

(Elt x0, Elt x1) => Elt (x0, x1) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR (x0, x1)

Methods

eltR :: TypeR (EltR (x0, x1))

tagsR :: [TagR (EltR (x0, x1))]

fromElt :: (x0, x1) -> EltR (x0, x1)

toElt :: EltR (x0, x1) -> (x0, x1)

(KnownNat n, VecElt a) => Elt (Vec n a) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Vec

Associated Types

type EltR (Vec n a)

Methods

eltR :: TypeR (EltR (Vec n a))

tagsR :: [TagR (EltR (Vec n a))]

fromElt :: Vec n a -> EltR (Vec n a)

toElt :: EltR (Vec n a) -> Vec n a

(Elt t, Elt h) => Elt (t :. h) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type EltR (t :. h)

Methods

eltR :: TypeR (EltR (t :. h))

tagsR :: [TagR (EltR (t :. h))]

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

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

(Elt x0, Elt x1, Elt x2) => Elt (x0, x1, x2) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR (x0, x1, x2)

Methods

eltR :: TypeR (EltR (x0, x1, x2))

tagsR :: [TagR (EltR (x0, x1, x2))]

fromElt :: (x0, x1, x2) -> EltR (x0, x1, x2)

toElt :: EltR (x0, x1, x2) -> (x0, x1, x2)

(Elt x0, Elt x1, Elt x2, Elt x3) => Elt (x0, x1, x2, x3) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR (x0, x1, x2, x3)

Methods

eltR :: TypeR (EltR (x0, x1, x2, x3))

tagsR :: [TagR (EltR (x0, x1, x2, x3))]

fromElt :: (x0, x1, x2, x3) -> EltR (x0, x1, x2, x3)

toElt :: EltR (x0, x1, x2, x3) -> (x0, x1, x2, x3)

(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4) => Elt (x0, x1, x2, x3, x4) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR (x0, x1, x2, x3, x4)

Methods

eltR :: TypeR (EltR (x0, x1, x2, x3, x4))

tagsR :: [TagR (EltR (x0, x1, x2, x3, x4))]

fromElt :: (x0, x1, x2, x3, x4) -> EltR (x0, x1, x2, x3, x4)

toElt :: EltR (x0, x1, x2, x3, x4) -> (x0, x1, x2, x3, x4)

(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5) => Elt (x0, x1, x2, x3, x4, x5) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR (x0, x1, x2, x3, x4, x5)

Methods

eltR :: TypeR (EltR (x0, x1, x2, x3, x4, x5))

tagsR :: [TagR (EltR (x0, x1, x2, x3, x4, x5))]

fromElt :: (x0, x1, x2, x3, x4, x5) -> EltR (x0, x1, x2, x3, x4, x5)

toElt :: EltR (x0, x1, x2, x3, x4, x5) -> (x0, x1, x2, x3, x4, x5)

(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6) => Elt (x0, x1, x2, x3, x4, x5, x6) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR (x0, x1, x2, x3, x4, x5, x6)

Methods

eltR :: TypeR (EltR (x0, x1, x2, x3, x4, x5, x6))

tagsR :: [TagR (EltR (x0, x1, x2, x3, x4, x5, x6))]

fromElt :: (x0, x1, x2, x3, x4, x5, x6) -> EltR (x0, x1, x2, x3, x4, x5, x6)

toElt :: EltR (x0, x1, x2, x3, x4, x5, x6) -> (x0, x1, x2, x3, x4, x5, x6)

(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7) => Elt (x0, x1, x2, x3, x4, x5, x6, x7) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR (x0, x1, x2, x3, x4, x5, x6, x7)

Methods

eltR :: TypeR (EltR (x0, x1, x2, x3, x4, x5, x6, x7))

tagsR :: [TagR (EltR (x0, x1, x2, x3, x4, x5, x6, x7))]

fromElt :: (x0, x1, x2, x3, x4, x5, x6, x7) -> EltR (x0, x1, x2, x3, x4, x5, x6, x7)

toElt :: EltR (x0, x1, x2, x3, x4, x5, x6, x7) -> (x0, x1, x2, x3, x4, x5, x6, x7)

(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8) => Elt (x0, x1, x2, x3, x4, x5, x6, x7, x8) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8)

Methods

eltR :: TypeR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8))

tagsR :: [TagR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8))]

fromElt :: (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8)

toElt :: EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8)

(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8, Elt x9) => Elt (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9)

Methods

eltR :: TypeR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9))

tagsR :: [TagR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9))]

fromElt :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9)

toElt :: EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9)

(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8, Elt x9, Elt x10) => Elt (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10)

Methods

eltR :: TypeR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10))

tagsR :: [TagR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10))]

fromElt :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10)

toElt :: EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10)

(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8, Elt x9, Elt x10, Elt x11) => Elt (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11)

Methods

eltR :: TypeR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11))

tagsR :: [TagR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11))]

fromElt :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11)

toElt :: EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11)

(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8, Elt x9, Elt x10, Elt x11, Elt x12) => Elt (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12)

Methods

eltR :: TypeR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12))

tagsR :: [TagR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12))]

fromElt :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12)

toElt :: EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12)

(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8, Elt x9, Elt x10, Elt x11, Elt x12, Elt x13) => Elt (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13)

Methods

eltR :: TypeR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13))

tagsR :: [TagR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13))]

fromElt :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13)

toElt :: EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13)

(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8, Elt x9, Elt x10, Elt x11, Elt x12, Elt x13, Elt x14) => Elt (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14)

Methods

eltR :: TypeR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14))

tagsR :: [TagR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14))]

fromElt :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14)

toElt :: EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14)

(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8, Elt x9, Elt x10, Elt x11, Elt x12, Elt x13, Elt x14, Elt x15) => Elt (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Elt

Associated Types

type EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15)

Methods

eltR :: TypeR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15))

tagsR :: [TagR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15))]

fromElt :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15)

toElt :: EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15)

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

Rank-0 index

Constructors

Z 

Instances

Instances details
Eq Z Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Methods

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

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

Show Z Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Methods

showsPrec :: Int -> Z -> ShowS #

show :: Z -> String #

showList :: [Z] -> ShowS #

Generic Z Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type Rep Z :: Type -> Type #

Methods

from :: Z -> Rep Z x #

to :: Rep Z x -> Z #

Elt Z Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type EltR Z

Methods

eltR :: TypeR (EltR Z)

tagsR :: [TagR (EltR Z)]

fromElt :: Z -> EltR Z

toElt :: EltR Z -> Z

Slice Z Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type SliceShape Z Source #

type CoSliceShape Z Source #

type FullShape Z Source #

Methods

sliceIndex :: SliceIndex (EltR Z) (EltR (SliceShape Z)) (EltR (CoSliceShape Z)) (EltR (FullShape Z)) Source #

Shape Z Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Methods

shapeR :: ShapeR (EltR Z)

sliceAnyIndex :: SliceIndex (EltR (Any Z)) (EltR Z) () (EltR Z)

sliceNoneIndex :: SliceIndex (EltR Z) () (EltR Z) (EltR Z)

Eq Z Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Methods

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

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

Ord Z Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Methods

(<) :: Exp Z -> Exp Z -> Exp Bool Source #

(>) :: Exp Z -> Exp Z -> Exp Bool Source #

(<=) :: Exp Z -> Exp Z -> Exp Bool Source #

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

min :: Exp Z -> Exp Z -> Exp Z Source #

max :: Exp Z -> Exp Z -> Exp Z Source #

compare :: Exp Z -> Exp Z -> Exp Ordering Source #

Unlift Exp Z Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

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

Lift Exp Z Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Z Source #

Methods

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

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e) Source # 
Instance details

Defined in Data.Array.Accelerate.Smart

Associated Types

type StencilR DIM1 (Exp e, Exp e, Exp e)

Methods

stencilR :: StencilR (EltR DIM1) (EltR e) (StencilR DIM1 (Exp e, Exp e, Exp e))

stencilPrj :: SmartExp (StencilR 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) Source # 
Instance details

Defined in Data.Array.Accelerate.Smart

Associated Types

type StencilR DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e)

Methods

stencilR :: StencilR (EltR DIM1) (EltR e) (StencilR DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e))

stencilPrj :: SmartExp (StencilR 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) Source # 
Instance details

Defined in Data.Array.Accelerate.Smart

Associated Types

type StencilR DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)

Methods

stencilR :: StencilR (EltR DIM1) (EltR e) (StencilR DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e))

stencilPrj :: SmartExp (StencilR 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) Source # 
Instance details

Defined in Data.Array.Accelerate.Smart

Associated Types

type StencilR DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)

Methods

stencilR :: StencilR (EltR DIM1) (EltR e) (StencilR DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e))

stencilPrj :: SmartExp (StencilR 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 (Any Z) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type EltR (Any Z)

Methods

eltR :: TypeR (EltR (Any Z))

tagsR :: [TagR (EltR (Any Z))]

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

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

Elt e => IsList (Array DIM1 e) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

Associated Types

type Item (Array DIM1 e) #

Methods

fromList :: [Item (Array DIM1 e)] -> Array DIM1 e #

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

toList :: Array DIM1 e -> [Item (Array DIM1 e)] #

type Rep Z Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

type Rep Z = D1 ('MetaData "Z" "Data.Array.Accelerate.Sugar.Shape" "accelerate-1.3.0.0-JUAol0vo0mBEBEK4xLffPu" 'False) (C1 ('MetaCons "Z" 'PrefixI 'False) (U1 :: Type -> Type))
type SliceShape Z Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

type SliceShape Z = Z
type CoSliceShape Z Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

type FullShape Z Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

type FullShape Z = Z
type Plain Z Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

type Plain Z = Z
type Item (Vector e) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

type Item (Vector e) = e

data tail :. head infixl 3 Source #

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

Constructors

!tail :. !head infixl 3 

Instances

Instances details
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e) Source # 
Instance details

Defined in Data.Array.Accelerate.Smart

Associated Types

type StencilR DIM1 (Exp e, Exp e, Exp e)

Methods

stencilR :: StencilR (EltR DIM1) (EltR e) (StencilR DIM1 (Exp e, Exp e, Exp e))

stencilPrj :: SmartExp (StencilR 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) Source # 
Instance details

Defined in Data.Array.Accelerate.Smart

Associated Types

type StencilR DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e)

Methods

stencilR :: StencilR (EltR DIM1) (EltR e) (StencilR DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e))

stencilPrj :: SmartExp (StencilR 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) Source # 
Instance details

Defined in Data.Array.Accelerate.Smart

Associated Types

type StencilR DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)

Methods

stencilR :: StencilR (EltR DIM1) (EltR e) (StencilR DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e))

stencilPrj :: SmartExp (StencilR 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) Source # 
Instance details

Defined in Data.Array.Accelerate.Smart

Associated Types

type StencilR DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)

Methods

stencilR :: StencilR (EltR DIM1) (EltR e) (StencilR DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e))

stencilPrj :: SmartExp (StencilR 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, Elt (Plain ix), Unlift Exp ix) => Unlift Exp (ix :. Exp e) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

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

(Elt e, Elt ix) => Unlift Exp (Exp ix :. Exp e) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

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

(Elt e, Elt (Plain ix), Lift Exp ix) => Lift Exp (ix :. Exp e) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (ix :. Exp e) Source #

Methods

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

(Elt (Plain ix), Lift Exp ix) => Lift Exp (ix :. All) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (ix :. All) Source #

Methods

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

(Elt (Plain ix), Lift Exp ix) => Lift Exp (ix :. Int) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (ix :. Int) Source #

Methods

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

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

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type EltR (Any (sh :. Int))

Methods

eltR :: TypeR (EltR (Any (sh :. Int)))

tagsR :: [TagR (EltR (Any (sh :. Int)))]

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

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

Elt e => IsList (Array DIM1 e) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

Associated Types

type Item (Array DIM1 e) #

Methods

fromList :: [Item (Array DIM1 e)] -> Array DIM1 e #

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

toList :: Array DIM1 e -> [Item (Array DIM1 e)] #

(Eq tail, Eq head) => Eq (tail :. head) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Methods

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

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

(Show sh, Show sz) => Show (sh :. sz) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Methods

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

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

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

Generic (tail :. head) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type Rep (tail :. head) :: Type -> Type #

Methods

from :: (tail :. head) -> Rep (tail :. head) x #

to :: Rep (tail :. head) x -> tail :. head #

(Elt t, Elt h) => Elt (t :. h) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type EltR (t :. h)

Methods

eltR :: TypeR (EltR (t :. h))

tagsR :: [TagR (EltR (t :. h))]

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

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

Slice sl => Slice (sl :. Int) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type SliceShape (sl :. Int) Source #

type CoSliceShape (sl :. Int) Source #

type FullShape (sl :. Int) Source #

Methods

sliceIndex :: SliceIndex (EltR (sl :. Int)) (EltR (SliceShape (sl :. Int))) (EltR (CoSliceShape (sl :. Int))) (EltR (FullShape (sl :. Int))) Source #

Slice sl => Slice (sl :. All) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type SliceShape (sl :. All) Source #

type CoSliceShape (sl :. All) Source #

type FullShape (sl :. All) Source #

Methods

sliceIndex :: SliceIndex (EltR (sl :. All)) (EltR (SliceShape (sl :. All))) (EltR (CoSliceShape (sl :. All))) (EltR (FullShape (sl :. All))) Source #

Shape sh => Shape (sh :. Int) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Methods

shapeR :: ShapeR (EltR (sh :. Int))

sliceAnyIndex :: SliceIndex (EltR (Any (sh :. Int))) (EltR (sh :. Int)) () (EltR (sh :. Int))

sliceNoneIndex :: SliceIndex (EltR (sh :. Int)) () (EltR (sh :. Int)) (EltR (sh :. Int))

Eq sh => Eq (sh :. Int) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Methods

(==) :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp Bool Source #

(/=) :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp Bool Source #

Ord sh => Ord (sh :. Int) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Methods

(<) :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp Bool Source #

(>) :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp Bool Source #

(<=) :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp Bool Source #

(>=) :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp Bool Source #

min :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp (sh :. Int) Source #

max :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp (sh :. Int) Source #

compare :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp Ordering Source #

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

Defined in Data.Array.Accelerate.Smart

Associated Types

type StencilR ((sh :. Int) :. Int) (row2, row1, row0)

Methods

stencilR :: StencilR (EltR ((sh :. Int) :. Int)) (EltR a) (StencilR ((sh :. Int) :. Int) (row2, row1, row0))

stencilPrj :: SmartExp (StencilR ((sh :. Int) :. Int) (row2, row1, row0)) -> (row2, row1, row0)

(Stencil (sh :. Int) a row4, Stencil (sh :. Int) a row3, Stencil (sh :. Int) a row2, Stencil (sh :. Int) a row1, Stencil (sh :. Int) a row0) => Stencil ((sh :. Int) :. Int) a (row4, row3, row2, row1, row0) Source # 
Instance details

Defined in Data.Array.Accelerate.Smart

Associated Types

type StencilR ((sh :. Int) :. Int) (row4, row3, row2, row1, row0)

Methods

stencilR :: StencilR (EltR ((sh :. Int) :. Int)) (EltR a) (StencilR ((sh :. Int) :. Int) (row4, row3, row2, row1, row0))

stencilPrj :: SmartExp (StencilR ((sh :. Int) :. Int) (row4, row3, row2, row1, row0)) -> (row4, row3, row2, row1, row0)

(Stencil (sh :. Int) a row6, Stencil (sh :. Int) a row5, Stencil (sh :. Int) a row4, Stencil (sh :. Int) a row3, Stencil (sh :. Int) a row2, Stencil (sh :. Int) a row1, Stencil (sh :. Int) a row0) => Stencil ((sh :. Int) :. Int) a (row6, row5, row4, row3, row2, row1, row0) Source # 
Instance details

Defined in Data.Array.Accelerate.Smart

Associated Types

type StencilR ((sh :. Int) :. Int) (row6, row5, row4, row3, row2, row1, row0)

Methods

stencilR :: StencilR (EltR ((sh :. Int) :. Int)) (EltR a) (StencilR ((sh :. Int) :. Int) (row6, row5, row4, row3, row2, row1, row0))

stencilPrj :: SmartExp (StencilR ((sh :. Int) :. Int) (row6, row5, row4, row3, row2, row1, row0)) -> (row6, row5, row4, row3, row2, row1, row0)

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

Defined in Data.Array.Accelerate.Smart

Associated Types

type StencilR ((sh :. Int) :. Int) (row8, row7, row6, row5, row4, row3, row2, row1, row0)

Methods

stencilR :: StencilR (EltR ((sh :. Int) :. Int)) (EltR a) (StencilR ((sh :. Int) :. Int) (row8, row7, row6, row5, row4, row3, row2, row1, row0))

stencilPrj :: SmartExp (StencilR ((sh :. Int) :. Int) (row8, row7, row6, row5, row4, row3, row2, row1, row0)) -> (row8, row7, row6, row5, row4, row3, row2, row1, row0)

type Item (Vector e) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

type Item (Vector e) = e
type Rep (tail :. head) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

type Rep (tail :. head) = D1 ('MetaData ":." "Data.Array.Accelerate.Sugar.Shape" "accelerate-1.3.0.0-JUAol0vo0mBEBEK4xLffPu" 'False) (C1 ('MetaCons ":." ('InfixI 'LeftAssociative 3) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 tail) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 head)))
type SliceShape (sl :. Int) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

type SliceShape (sl :. Int) = SliceShape sl
type SliceShape (sl :. All) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

type SliceShape (sl :. All) = SliceShape sl :. Int
type CoSliceShape (sl :. Int) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

type CoSliceShape (sl :. All) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

type FullShape (sl :. Int) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

type FullShape (sl :. Int) = FullShape sl :. Int
type FullShape (sl :. All) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

type FullShape (sl :. All) = FullShape sl :. Int
type Plain (ix :. Exp e) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

type Plain (ix :. Exp e) = Plain ix :. e
type Plain (ix :. All) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

type Plain (ix :. All) = Plain ix :. All
type Plain (ix :. Int) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

type Plain (ix :. Int) = Plain ix :. Int

type DIM0 = Z Source #

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

Shapes and indices of multi-dimensional arrays

Minimal complete definition

shapeR, sliceAnyIndex, sliceNoneIndex

Instances

Instances details
Shape Z Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Methods

shapeR :: ShapeR (EltR Z)

sliceAnyIndex :: SliceIndex (EltR (Any Z)) (EltR Z) () (EltR Z)

sliceNoneIndex :: SliceIndex (EltR Z) () (EltR Z) (EltR Z)

Shape sh => Shape (sh :. Int) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Methods

shapeR :: ShapeR (EltR (sh :. Int))

sliceAnyIndex :: SliceIndex (EltR (Any (sh :. Int))) (EltR (sh :. Int)) () (EltR (sh :. Int))

sliceNoneIndex :: SliceIndex (EltR (sh :. Int)) () (EltR (sh :. Int)) (EltR (sh :. Int))

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

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

Associated Types

type SliceShape sl :: Type Source #

type CoSliceShape sl :: Type Source #

type FullShape sl :: Type Source #

Methods

sliceIndex :: SliceIndex (EltR sl) (EltR (SliceShape sl)) (EltR (CoSliceShape sl)) (EltR (FullShape sl)) Source #

Instances

Instances details
Slice Z Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type SliceShape Z Source #

type CoSliceShape Z Source #

type FullShape Z Source #

Methods

sliceIndex :: SliceIndex (EltR Z) (EltR (SliceShape Z)) (EltR (CoSliceShape Z)) (EltR (FullShape Z)) Source #

Shape sh => Slice (Any sh) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type SliceShape (Any sh) Source #

type CoSliceShape (Any sh) Source #

type FullShape (Any sh) Source #

Methods

sliceIndex :: SliceIndex (EltR (Any sh)) (EltR (SliceShape (Any sh))) (EltR (CoSliceShape (Any sh))) (EltR (FullShape (Any sh))) Source #

Slice sl => Slice (sl :. Int) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type SliceShape (sl :. Int) Source #

type CoSliceShape (sl :. Int) Source #

type FullShape (sl :. Int) Source #

Methods

sliceIndex :: SliceIndex (EltR (sl :. Int)) (EltR (SliceShape (sl :. Int))) (EltR (CoSliceShape (sl :. Int))) (EltR (FullShape (sl :. Int))) Source #

Slice sl => Slice (sl :. All) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type SliceShape (sl :. All) Source #

type CoSliceShape (sl :. All) Source #

type FullShape (sl :. All) Source #

Methods

sliceIndex :: SliceIndex (EltR (sl :. All)) (EltR (SliceShape (sl :. All))) (EltR (CoSliceShape (sl :. All))) (EltR (FullShape (sl :. All))) Source #

data All Source #

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

Instances details
Eq All Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Methods

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

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

Show All Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Methods

showsPrec :: Int -> All -> ShowS #

show :: All -> String #

showList :: [All] -> ShowS #

Generic All Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type Rep All :: Type -> Type #

Methods

from :: All -> Rep All x #

to :: Rep All x -> All #

Elt All Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type EltR All

Methods

eltR :: TypeR (EltR All)

tagsR :: [TagR (EltR All)]

fromElt :: All -> EltR All

toElt :: EltR All -> All

(Elt (Plain ix), Lift Exp ix) => Lift Exp (ix :. All) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (ix :. All) Source #

Methods

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

Slice sl => Slice (sl :. All) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type SliceShape (sl :. All) Source #

type CoSliceShape (sl :. All) Source #

type FullShape (sl :. All) Source #

Methods

sliceIndex :: SliceIndex (EltR (sl :. All)) (EltR (SliceShape (sl :. All))) (EltR (CoSliceShape (sl :. All))) (EltR (FullShape (sl :. All))) Source #

type Rep All Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

type Rep All = D1 ('MetaData "All" "Data.Array.Accelerate.Sugar.Shape" "accelerate-1.3.0.0-JUAol0vo0mBEBEK4xLffPu" 'False) (C1 ('MetaCons "All" 'PrefixI 'False) (U1 :: Type -> Type))
type SliceShape (sl :. All) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

type SliceShape (sl :. All) = SliceShape sl :. Int
type CoSliceShape (sl :. All) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

type FullShape (sl :. All) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

type FullShape (sl :. All) = FullShape sl :. Int
type Plain (ix :. All) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

type Plain (ix :. All) = Plain ix :. All

data Any sh Source #

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

Instances details
(Shape sh, Elt (Any sh)) => Lift Exp (Any sh) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (Any sh) Source #

Methods

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

Eq (Any sh) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Methods

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

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

Show (Any sh) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Methods

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

show :: Any sh -> String #

showList :: [Any sh] -> ShowS #

Generic (Any sh) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type Rep (Any sh) :: Type -> Type #

Methods

from :: Any sh -> Rep (Any sh) x #

to :: Rep (Any sh) x -> Any sh #

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

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type EltR (Any (sh :. Int))

Methods

eltR :: TypeR (EltR (Any (sh :. Int)))

tagsR :: [TagR (EltR (Any (sh :. Int)))]

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

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

Elt (Any Z) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type EltR (Any Z)

Methods

eltR :: TypeR (EltR (Any Z))

tagsR :: [TagR (EltR (Any Z))]

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

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

Shape sh => Slice (Any sh) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Associated Types

type SliceShape (Any sh) Source #

type CoSliceShape (Any sh) Source #

type FullShape (Any sh) Source #

Methods

sliceIndex :: SliceIndex (EltR (Any sh)) (EltR (SliceShape (Any sh))) (EltR (CoSliceShape (Any sh))) (EltR (FullShape (Any sh))) Source #

type Rep (Any sh) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

type Rep (Any sh) = D1 ('MetaData "Any" "Data.Array.Accelerate.Sugar.Shape" "accelerate-1.3.0.0-JUAol0vo0mBEBEK4xLffPu" 'False) (C1 ('MetaCons "Any" 'PrefixI 'False) (U1 :: Type -> Type))
type SliceShape (Any sh) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

type SliceShape (Any sh) = sh
type CoSliceShape (Any sh) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

type CoSliceShape (Any sh) = Z
type FullShape (Any sh) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

type FullShape (Any sh) = sh
type Plain (Any sh) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

type Plain (Any sh) = Any sh

Array access

Element indexing

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

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

>>> let mat = fromList (Z:.5:.10) [0..] :: Matrix 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]
>>> runExp $ use mat ! constant (Z:.1:.2)
12

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

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..] :: Matrix 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]
>>> runExp $ use mat !! 12
12

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

Extract the element of a singleton array.

the xs  ==  xs ! Z

Shape information

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

Test whether an array is empty.

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

Get the length of a vector.

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

Extract the shape (extent) of an array.

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

The number of elements in the array

shapeSize :: forall sh. Shape sh => Exp sh -> Exp Int Source #

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

Construction

Introduction

use :: forall arrays. Arrays arrays => arrays -> Acc arrays Source #

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..] :: Vector Int
>>> vec
Vector (Z :. 10) [0,1,2,3,4,5,6,7,8,9]
>>> let mat = fromList (Z:.5:.10) [0..] :: Matrix 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 (Vector Int)
>>> let mat' = use mat         :: Acc (Matrix Int)
>>> let tup  = use (vec, mat)  :: Acc (Vector Int, Matrix Int)

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

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

Initialisation

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

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:

>>> run $ generate (I1 3) (\_ -> 1.2) :: Vector Float
Vector (Z :. 3) [1.2,1.2,1.2]

Or equivalently:

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

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

>>> run $ generate (I1 10) (\(I1 i) -> i + 1) :: Vector Int
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) Source #

Create an array where all elements are the same value.

>>> run $ fill (constant (Z:.10)) 0 :: Vector Float
Vector (Z :. 10) [0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0]

Enumeration

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

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

>>> run $ enumFromN (constant (Z:.5:.10)) 0 :: Matrix 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 Source #

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

>>> run $ enumFromStepN (constant (Z:.5:.10)) 0 0.5 :: Matrix 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

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

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..] :: Matrix Int
>>> 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..] :: Matrix Int
>>> 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]
>>> run $ 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]

concatOn :: (Shape sh, Elt e) => Lens' (Exp sh) (Exp Int) -> Acc (Array sh e) -> Acc (Array sh e) -> Acc (Array sh e) Source #

Generalised version of (++) where the argument Lens' specifies which dimension to concatenate along.

Appropriate lenses are available from lens-accelerate.

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

Expansion

expand :: (Elt a, Elt b) => (Exp a -> Exp Int) -> (Exp a -> Exp Int -> Exp b) -> Acc (Vector a) -> Acc (Vector b) Source #

A recipe for generating flattened implementations of some kinds of irregular nested parallelism. Given two functions that:

  1. for each source element, determine how many target elements it expands into; and
  2. computes a particular target element based on a source element and the target element index associated with the source

The following example implements the Sieve of Eratosthenes, a contraction style algorithm which first computes all primes less than sqrt n, then uses this intermediate result to sieve away all numbers in the range [sqrt n .. n]. The expand function is used to calculate and flatten the sieves. For each prime p and upper limit c2, function sz computes the number of contributions in the sieve. Then, for each prime p and sieve index i, the function get computes the sieve contribution. The final step produces all the new primes in the interval [c1 .. c2].

>>> :{
  primes :: Exp Int -> Acc (Vector Int)
  primes n = afst loop
    where
      c0    = unit 2
      a0    = use $ fromList (Z:.0) []
      limit = truncate (sqrt (fromIntegral (n+1) :: Exp Float))
      loop  = awhile
                (\(T2 _   c) -> map (< n+1) c)
                (\(T2 old c) ->
                  let c1 = the c
                      c2 = c1 < limit ? ( c1*c1, n+1 )
                      --
                      sieves =
                        let sz p    = (c2 - p) `quot` p
                            get p i = (2+i)*p
                        in
                        map (subtract c1) (expand sz get old)
                      --
                      new =
                        let m     = c2-c1
                            put i = let s = sieves ! i
                                     in s >= 0 && s < m ? (Just_ (I1 s), Nothing_)
                        in
                        afst
                          $ filter (> 0)
                          $ permute const (enumFromN (I1 m) c1) put
                          $ fill (shape sieves) 0
                   in
                   T2 (old ++ new) (unit c2))
                (T2 a0 c0)
:}
>>> run $ primes 100
Vector (Z :. 25) [2,3,5,7,11,13,17,19,23,29,31,37,41,43,47,53,59,61,67,71,73,79,83,89,97]

Inspired by the paper Data-Parallel Flattening by Expansion by Martin Elsman, Troels Henriksen, and Niels Gustav Westphal Serup, ARRAY'19.

Since: 1.3.0.0

Composition

Flow control

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

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

Enabling the RebindableSyntax extension will allow you to use the standard if-then-else syntax instead.

acond Source #

Arguments

:: Arrays a 
=> Exp Bool

if-condition

-> Acc a

then-array

-> Acc a

else-array

-> Acc a 

An array-level if-then-else construct.

Enabling the RebindableSyntax extension will allow you to use the standard if-then-else syntax instead.

awhile Source #

Arguments

:: forall a. 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 Source #

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

Associated Types

type EltT t a :: Constraint Source #

Methods

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

Instances

Instances details
IfThenElse Exp Source # 
Instance details

Defined in Data.Array.Accelerate.Prelude

Associated Types

type EltT Exp a Source #

Methods

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

IfThenElse Acc Source # 
Instance details

Defined in Data.Array.Accelerate.Prelude

Associated Types

type EltT Acc a Source #

Methods

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

Controlling execution

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

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

For an example use of this operation see the compute function.

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

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

Pair each element with its index

>>> let xs = fromList (Z:.5) [0..] :: Vector Float
>>> run $ indexed (use xs)
Vector (Z :. 5) [(Z :. 0,0.0),(Z :. 1,1.0),(Z :. 2,2.0),(Z :. 3,3.0),(Z :. 4,4.0)]
>>> let mat = fromList (Z:.3:.4) [0..] :: Matrix Float
>>> run $ indexed (use mat)
Matrix (Z :. 3 :. 4)
  [ (Z :. 0 :. 0,0.0), (Z :. 0 :. 1,1.0),  (Z :. 0 :. 2,2.0),  (Z :. 0 :. 3,3.0),
    (Z :. 1 :. 0,4.0), (Z :. 1 :. 1,5.0),  (Z :. 1 :. 2,6.0),  (Z :. 1 :. 3,7.0),
    (Z :. 2 :. 0,8.0), (Z :. 2 :. 1,9.0), (Z :. 2 :. 2,10.0), (Z :. 2 :. 3,11.0)]

Mapping

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

Apply the given function element-wise to an array. Denotationally we have:

map f [x1, x2, ... xn] = [f x1, f x2, ... f xn]
>>> let xs = fromList (Z:.10) [0..] :: Vector Int
>>> xs
Vector (Z :. 10) [0,1,2,3,4,5,6,7,8,9]
>>> run $ map (+1) (use xs)
Vector (Z :. 10) [1,2,3,4,5,6,7,8,9,10]

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

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

Zipping

zipWith :: forall sh a b c. (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) Source #

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.

>>> let xs = fromList (Z:.3:.5) [0..] :: Matrix Int
>>> xs
Matrix (Z :. 3 :. 5)
  [  0,  1,  2,  3,  4,
     5,  6,  7,  8,  9,
    10, 11, 12, 13, 14]
>>> let ys = fromList (Z:.5:.10) [1..] :: Matrix Int
>>> ys
Matrix (Z :. 5 :. 10)
  [  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]
>>> run $ zipWith (+) (use xs) (use ys)
Matrix (Z :. 3 :. 5)
  [  1,  3,  5,  7,  9,
    16, 18, 20, 22, 24,
    31, 33, 35, 37, 39]

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

>>> let m1 = fromList (Z:.5:.10) [0..] :: Matrix Int
>>> let m2 = fromList (Z:.10:.5) [0..] :: Matrix Float
>>> run $ zip (use m1) (use m2)
Matrix (Z :. 5 :. 5)
  [   (0,0.0),   (1,1.0),   (2,2.0),   (3,3.0),   (4,4.0),
     (10,5.0),  (11,6.0),  (12,7.0),  (13,8.0),  (14,9.0),
    (20,10.0), (21,11.0), (22,12.0), (23,13.0), (24,14.0),
    (30,15.0), (31,16.0), (32,17.0), (33,18.0), (34,19.0),
    (40,20.0), (41,21.0), (42,22.0), (43,23.0), (44,24.0)]

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

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

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

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

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

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

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

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

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 no-op.

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

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

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

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

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

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

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

Take an array of 9-tuples and return nine arrays, analogous to unzip.

Modifying Arrays

Shape manipulation

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

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 no-op. 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) Source #

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

Replication

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

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 Int
>>> vec
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:

>>> run $ replicate (constant (Z :. (4::Int) :. 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:

>>> run $ replicate (lift (Z :. All :. (4::Int))) (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:

>>> run $ replicate (constant (Z :. (2::Int) :. All :. (3::Int))) (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.

>>> :{
  let 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)
>>> run $ rep0 10 x
Vector (Z :. 10) [42,42,42,42,42,42,42,42,42,42]
>>> run $ 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.

>>> :{
  let rep1 :: (Shape sh, Elt e) => Exp Int -> Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int :. Int) e)
      rep1 n a = replicate (lift (Any :. n :. All)) a
:}
>>> run $ 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 :: forall slix e. (Slice slix, Elt e) => Acc (Array (FullShape slix) e) -> Exp slix -> Acc (Array (SliceShape slix) e) Source #

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..] :: Matrix 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]

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

>>> run $ slice (use mat) (constant (Z :. (2::Int) :. 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).

>>> run $ slice (use mat) (constant (Z :. 4 :. 2 :: DIM2))
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:

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

Of course, Any and All can be used together.

>>> :{
  let sl1 :: (Shape sh, Elt e) => Acc (Array (sh:.Int:.Int) e) -> Exp Int -> Acc (Array (sh:.Int) e)
      sl1 a n = slice a (lift (Any :. n :. All))
:}
>>> run $ 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..] :: Array DIM3 Int
>>> 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]
>>> run $ sl1 (use cube) 2
Matrix (Z :. 3 :. 5)
  [ 10, 11, 12, 13, 14,
    30, 31, 32, 33, 34,
    50, 51, 52, 53, 54]

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

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

>>> let mat = fromList (Z:.5:.10) [0..] :: Matrix 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]
>>> run $ 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 :: (Shape sh, Elt e) => Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e) Source #

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..] :: Matrix 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]
>>> run $ 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 :: (Shape sh, Elt e) => Exp Int -> Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e) Source #

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

>>> let mat = fromList (Z:.5:.10) [0..] :: Matrix 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]
>>> run $ 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 :: (Shape sh, Elt e) => Exp Int -> Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e) Source #

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..] :: Matrix 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]
>>> run $ drop 7 (use mat)
Matrix (Z :. 5 :. 3)
  [  7,  8,  9,
    17, 18, 19,
    27, 28, 29,
    37, 38, 39,
    47, 48, 49]

slit Source #

Arguments

:: (Shape sh, Elt e) 
=> Exp Int

starting index

-> Exp Int

length

-> 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

initOn :: (Shape sh, Elt e) => Lens' (Exp sh) (Exp Int) -> Acc (Array sh e) -> Acc (Array sh e) Source #

Generalised version of init where the argument Lens' specifies which dimension to operate over.

Appropriate lenses are available from lens-accelerate.

Since: 1.2.0.0

tailOn :: (Shape sh, Elt e) => Lens' (Exp sh) (Exp Int) -> Acc (Array sh e) -> Acc (Array sh e) Source #

Generalised version of tail where the argument Lens' specifies which dimension to operate over.

Appropriate lenses are available from lens-accelerate.

Since: 1.2.0.0

takeOn :: (Shape sh, Elt e) => Lens' (Exp sh) (Exp Int) -> Exp Int -> Acc (Array sh e) -> Acc (Array sh e) Source #

Generalised version of take where the argument Lens' specifies which dimension to operate over.

Appropriate lenses are available from lens-accelerate.

Since: 1.2.0.0

dropOn :: (Shape sh, Elt e) => Lens' (Exp sh) (Exp Int) -> Exp Int -> Acc (Array sh e) -> Acc (Array sh e) Source #

Generalised version of drop where the argument Lens' specifies which dimension to operate over.

Appropriate lenses are available from lens-accelerate.

Since: 1.2.0.0

slitOn Source #

Arguments

:: (Shape sh, Elt e) 
=> Lens' (Exp sh) (Exp Int) 
-> Exp Int

starting index

-> Exp Int

length

-> Acc (Array sh e) 
-> Acc (Array sh e) 

Generalised version of drop where the argument Lens' specifies which dimension to operate over.

Appropriate lenses are available from lens-accelerate.

Since: 1.2.0.0

Permutations

Forward permutation (scatter)

permute Source #

Arguments

:: forall sh sh' a. (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 (Maybe 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 for which the permutation function returns Nothing are dropped.

The combination function is given the new value being permuted as its first argument, and the current value of the array as its second.

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

>>> :{
  let 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 -> Just_ (I1 (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] :: Vector Int
>>> run $ histogram (use xs)
Vector (Z :. 10) [2,4,4,3,2,2,0,0,2,1]

As a second example, note that the dimensionality of the source and destination arrays can differ. In this way, we can use permute to create an identity matrix by overwriting elements along the diagonal:

>>> :{
  let identity :: Num a => Exp Int -> Acc (Matrix a)
      identity n =
        let zeros = fill (I2 n n) 0
            ones  = fill (I1 n)   1
        in
        permute const zeros (\(I1 i) -> Just_ (I2 i i)) ones
:}
>>> run $ identity 5 :: Matrix Int
Matrix (Z :. 5 :. 5)
  [ 1, 0, 0, 0, 0,
    0, 1, 0, 0, 0,
    0, 0, 1, 0, 0,
    0, 0, 0, 1, 0,
    0, 0, 0, 0, 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.
  4. If the array of default values is only used once, it will be updated in-place. This behaviour can be disabled this with -fno-inplace.

Regarding the defaults array:

If you are sure that the default values are not necessary---they are not used by the combination function and every element will be overwritten---a default array created by filling with the value undef will give you a new uninitialised array.

Regarding the combination function:

The function const can be used to replace elements of the defaults array with the new values. If the permutation function maps multiple values to the same location in the results array (the function is not injective) then this operation is non-deterministic.

Since Accelerate uses an unzipped struct-of-array representation, where the individual components of product types (for example, pairs) are stored in separate arrays, storing values of product type requires multiple store instructions.

Accelerate prior to version 1.3.0.0 performs this operation atomically, to ensure that the stored values are always consistent (each component of the product type is written by the same thread). Later versions relax this restriction, but this behaviour can be disabled with -fno-fast-permute-const.

scatter Source #

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] :: Vector Int
>>> let input = fromList (Z :. 7) [1,9,6,4,4,2,5] :: Vector Int
>>> run $ 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 Source #

Arguments

:: forall sh sh' a. (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:

>>> :{
  let swap :: Exp DIM2 -> Exp DIM2
      swap = lift1 f
        where
          f :: Z :. Exp Int :. Exp Int -> Z :. Exp Int :. Exp Int
          f (Z:.y:.x) = Z :. x :. y
:}
>>> let mat = fromList (Z:.5:.10) [0..] :: Matrix 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 mat' = use mat
>>> run $ 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 Source #

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] :: Vector Int
>>> let from  = fromList (Z:.6) [1,3,7,2,5,3] :: Vector Int
>>> run $ 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) Source #

Reverse the elements of a vector.

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

Transpose the rows and columns of a matrix.

reverseOn :: (Shape sh, Elt e) => Lens' (Exp sh) (Exp Int) -> Acc (Array sh e) -> Acc (Array sh e) Source #

Generalised version of reverse where the argument Lens' specifies which dimension to reverse.

Appropriate lenses are available from lens-accelerate.

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

Since: 1.2.0.0

transposeOn :: (Shape sh, Elt e) => Lens' (Exp sh) (Exp Int) -> Lens' (Exp sh) (Exp Int) -> Acc (Array sh e) -> Acc (Array sh e) Source #

Generalised version of transpose where the argument Lens's specify which two dimensions to transpose.

Appropriate lenses are available from lens-accelerate.

>>> let mat = fromList (Z:.5:.10) [0..] :: Matrix 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]
>>> run $ transposeOn _1 _2 (use 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]
>>> let box = fromList (Z:.2:.3:.5) [0..] :: Array DIM3 Int
>>> box
Array (Z :. 2 :. 3 :. 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]
>>> run $ transposeOn _1 _2 (use box)
Array (Z :. 2 :. 5 :. 3) [0,5,10,1,6,11,2,7,12,3,8,13,4,9,14,15,20,25,16,21,26,17,22,27,18,23,28,19,24,29]
>>> run $ transposeOn _2 _3 (use box)
Array (Z :. 3 :. 2 :. 5) [0,1,2,3,4,15,16,17,18,19,5,6,7,8,9,20,21,22,23,24,10,11,12,13,14,25,26,27,28,29]
>>> run $ transposeOn _1 _3 (use box)
Array (Z :. 5 :. 3 :. 2) [0,15,5,20,10,25,1,16,6,21,11,26,2,17,7,22,12,27,3,18,8,23,13,28,4,19,9,24,14,29]

Since: 1.2.0.0

Filtering

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

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]
>>> run $ 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] :: Matrix 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]
>>> run $ 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])

compact :: forall sh e. (Shape sh, Elt e) => Acc (Array (sh :. Int) Bool) -> Acc (Array (sh :. Int) e) -> Acc (Vector e, Array sh Int) Source #

As filter, but with separate arrays for the data elements and the flags indicating which elements of that array should be kept.

Folding

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

Reduction of the innermost dimension of an array of arbitrary rank.

The shape of the result obeys the property:

shape (fold f z xs) == indexTail (shape xs)

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..] :: Matrix 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]
>>> run $ 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

>>> :{
  let maximumSegmentSum
          :: forall sh e. (Shape sh, Num e, Ord e)
          => Acc (Array (sh :. Int) e)
          -> Acc (Array sh e)
      maximumSegmentSum
        = map (\(T4 x _ _ _) -> 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 T4 mssx misx mcsx tsx = x
                T4 mssy misy mcsy tsy = y
            in
            T4 (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 T4 y y y x
:}
>>> let vec = fromList (Z:.10) [-2,1,-3,4,-1,2,1,-5,4,0] :: Vector Int
>>> run $ maximumSegmentSum (use vec)
Scalar Z [6]

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

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

Variant of fold that requires the innermost dimension of the array to be non-empty and doesn't need an default value.

The shape of the result obeys the property:

shape (fold f z xs) == indexTail (shape xs)

The first argument needs to be an associative function to enable an efficient parallel implementation, but does not need to be commutative.

<