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.

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

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

>>> let vec = fromList (Z:.10) [0..] :: Vector Float
>>> run $ foldAll (+) 42 (use vec)
Scalar Z [87.0]
>>> let mat = fromList (Z:.5:.10) [0..] :: Matrix Float
>>> run $ foldAll (+) 0 (use mat)
Scalar Z [1225.0]

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

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

Segmented reductions

foldSeg :: forall sh e i. (Shape sh, Elt e, Elt i, i ~ EltR i, IsIntegral i) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e) Source #

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

>>> let seg = fromList (Z:.4) [1,4,0,3] :: Segments Int
>>> seg
Vector (Z :. 4) [1,4,0,3]
>>> 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 $ foldSeg (+) 0 (use mat) (use seg)
Matrix (Z :. 5 :. 4)
  [  0,  10, 0,  18,
    10,  50, 0,  48,
    20,  90, 0,  78,
    30, 130, 0, 108,
    40, 170, 0, 138]

fold1Seg :: forall sh e i. (Shape sh, Elt e, Elt i, i ~ EltR i, IsIntegral i) => (Exp e -> Exp e -> Exp e) -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e) Source #

Variant of foldSeg that requires all segments of the reduced array to be non-empty, and does not need a default value. The segment descriptor species the length of each of the logical sub-arrays.

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

Segmented reduction along the innermost dimension of an array. The segment descriptor specifies the starting index (offset) along the innermost dimension to the beginning of each logical sub-array.

The value in the output array at index i is the reduction of values between the indices of the segment descriptor at index i and (i+1).

We have that:

foldSeg f z xs seg  ==  foldSeg' f z xs (scanl (+) 0 seg)

Since: 1.3.0.0

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

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

Since: 1.3.0.0

Specialised reductions

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

Check if all elements along the innermost dimension satisfy a predicate.

>>> 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 $ all even (use mat)
Vector (Z :. 4) [False,False,True,False]

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

Check if any element along the innermost dimension satisfies the predicate.

>>> 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 $ any even (use mat)
Vector (Z :. 4) [True,True,True,False]

and :: Shape sh => Acc (Array (sh :. Int) Bool) -> Acc (Array sh Bool) Source #

Check if all elements along the innermost dimension are True.

or :: Shape sh => Acc (Array (sh :. Int) Bool) -> Acc (Array sh Bool) Source #

Check if any element along the innermost dimension is True.

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

Compute the sum of elements along the innermost dimension of the array. To find the sum of the entire array, flatten it first.

>>> let mat = fromList (Z:.2:.5) [0..] :: Matrix Int
>>> run $ sum (use mat)
Vector (Z :. 2) [10,35]

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

Compute the product of the elements along the innermost dimension of the array. To find the product of the entire array, flatten it first.

>>> let mat = fromList (Z:.2:.5) [0..] :: Matrix Int
>>> run $ product (use mat)
Vector (Z :. 2) [0,15120]

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

Yield the minimum element along the innermost dimension of the array. To find find the minimum element of the entire array, flatten it first.

The array must not be empty. See also fold1.

>>> let mat = fromList (Z :. 3 :. 4) [1,4,3,8, 0,2,8,4, 7,9,8,8] :: Matrix Int
>>> mat
Matrix (Z :. 3 :. 4)
  [ 1, 4, 3, 8,
    0, 2, 8, 4,
    7, 9, 8, 8]
>>> run $ minimum (use mat)
Vector (Z :. 3) [1,0,7]

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

Yield the maximum element along the innermost dimension of the array. To find the maximum element of the entire array, flatten it first.

The array must not be empty. See also fold1.

>>> let mat = fromList (Z :. 3 :. 4) [1,4,3,8, 0,2,8,4, 7,9,8,8] :: Matrix Int
>>> mat
Matrix (Z :. 3 :. 4)
  [ 1, 4, 3, 8,
    0, 2, 8, 4,
    7, 9, 8, 8]
>>> run $ maximum (use mat)
Vector (Z :. 3) [8,8,9]

Scans (prefix sums)

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

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

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

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

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

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

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

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

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

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

Right-to-left variant of scanl.

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

Right-to-left variant of scanl1.

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

Right-to-left variant of scanl'.

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

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

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

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

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

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

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

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

prescanr f e = afst . scanr' f e

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

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

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

Segmented scans

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

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

>>> let seg = fromList (Z:.4) [1,4,0,3] :: Segments Int
>>> seg
Vector (Z :. 4) [1,4,0,3]
>>> 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 $ scanlSeg (+) 0 (use mat) (use seg)
Matrix (Z :. 5 :. 12)
  [ 0,  0, 0,  1,  3,   6,  10, 0, 0,  5, 11,  18,
    0, 10, 0, 11, 23,  36,  50, 0, 0, 15, 31,  48,
    0, 20, 0, 21, 43,  66,  90, 0, 0, 25, 51,  78,
    0, 30, 0, 31, 63,  96, 130, 0, 0, 35, 71, 108,
    0, 40, 0, 41, 83, 126, 170, 0, 0, 45, 91, 138]

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

Segmented version of scanl1 along the innermost dimension.

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

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

scanl1Seg f xs [n,0,0] == scanl1Seg f xs [n]   where n /= 0
>>> let seg = fromList (Z:.4) [1,4,0,3] :: Segments Int
>>> seg
Vector (Z :. 4) [1,4,0,3]
>>> 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 $ scanl1Seg (+) (use mat) (use seg)
Matrix (Z :. 5 :. 8)
  [  0,  1,  3,   6,  10,  5, 11,  18,
    10, 11, 23,  36,  50, 15, 31,  48,
    20, 21, 43,  66,  90, 25, 51,  78,
    30, 31, 63,  96, 130, 35, 71, 108,
    40, 41, 83, 126, 170, 45, 91, 138]

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

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

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

>>> let seg = fromList (Z:.4) [1,4,0,3] :: Segments Int
>>> seg
Vector (Z :. 4) [1,4,0,3]
>>> 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 (res,sums) = run $ scanl'Seg (+) 0 (use mat) (use seg)
>>> res
Matrix (Z :. 5 :. 8)
  [ 0, 0,  1,  3,   6, 0,  5, 11,
    0, 0, 11, 23,  36, 0, 15, 31,
    0, 0, 21, 43,  66, 0, 25, 51,
    0, 0, 31, 63,  96, 0, 35, 71,
    0, 0, 41, 83, 126, 0, 45, 91]
>>> sums
Matrix (Z :. 5 :. 4)
  [  0,  10, 0,  18,
    10,  50, 0,  48,
    20,  90, 0,  78,
    30, 130, 0, 108,
    40, 170, 0, 138]

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

Segmented version of prescanl.

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

Segmented version of postscanl.

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

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

>>> let seg = fromList (Z:.4) [1,4,0,3] :: Segments Int
>>> seg
Vector (Z :. 4) [1,4,0,3]
>>> 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 $ scanrSeg (+) 0 (use mat) (use seg)
Matrix (Z :. 5 :. 12)
  [  2, 0,  18,  15, 11,  6, 0, 0,  24, 17,  9, 0,
    12, 0,  58,  45, 31, 16, 0, 0,  54, 37, 19, 0,
    22, 0,  98,  75, 51, 26, 0, 0,  84, 57, 29, 0,
    32, 0, 138, 105, 71, 36, 0, 0, 114, 77, 39, 0,
    42, 0, 178, 135, 91, 46, 0, 0, 144, 97, 49, 0]

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

Segmented version of scanr1.

>>> let seg = fromList (Z:.4) [1,4,0,3] :: Segments Int
>>> seg
Vector (Z :. 4) [1,4,0,3]
>>> 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 $ scanr1Seg (+) (use mat) (use seg)
Matrix (Z :. 5 :. 8)
  [  0,  10,   9,  7,  4,  18, 13,  7,
    10,  50,  39, 27, 14,  48, 33, 17,
    20,  90,  69, 47, 24,  78, 53, 27,
    30, 130,  99, 67, 34, 108, 73, 37,
    40, 170, 129, 87, 44, 138, 93, 47]

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

Segmented version of scanr'.

>>> let seg = fromList (Z:.4) [1,4,0,3] :: Segments Int
>>> seg
Vector (Z :. 4) [1,4,0,3]
>>> 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 (res,sums) = run $ scanr'Seg (+) 0 (use mat) (use seg)
>>> res
Matrix (Z :. 5 :. 8)
  [ 0,  15, 11,  6, 0, 17,  9, 0,
    0,  45, 31, 16, 0, 37, 19, 0,
    0,  75, 51, 26, 0, 57, 29, 0,
    0, 105, 71, 36, 0, 77, 39, 0,
    0, 135, 91, 46, 0, 97, 49, 0]
>>> sums
Matrix (Z :. 5 :. 4)
  [  2,  18, 0,  24,
    12,  58, 0,  54,
    22,  98, 0,  84,
    32, 138, 0, 114,
    42, 178, 0, 144]

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

Segmented version of prescanr.

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

Segmented version of postscanr.

Stencils

stencil Source #

Arguments

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

stencil function

-> Boundary (Array sh a)

boundary condition

-> Acc (Array sh a)

source array

-> Acc (Array sh b)

destination array

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

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

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

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

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

s33 :: Stencil3x3 a -> Exp a
s33 ((_,t,_)
    ,(l,c,r)
    ,(_,b,_)) = ...

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

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

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

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

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

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

blur :: Num a => Acc (Matrix a) -> Acc (Matrix a)
blur = stencil (convolve5x1 gaussian) clamp
     . stencil (convolve1x5 gaussian) clamp
Note:

Since accelerate-1.3.0.0, we allow the source array to fuse into the stencil operation. However, since a stencil computation (typically) requires multiple values from the source array, this means that the work of the fused operation will be duplicated for each element in the stencil pattern.

For example, suppose we write:

blur . map f

The operation f will be fused into each element of the first Gaussian blur kernel, resulting in a stencil equivalent to:

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

This duplication is often beneficial, however you may choose to instead force the array to be evaluated first, preventing fusion, using the compute operation. Benchmarking should reveal which approach is best for your application.

stencil2 Source #

Arguments

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

binary stencil function

-> Boundary (Array sh a)

boundary condition #1

-> Acc (Array sh a)

source array #1

-> Boundary (Array sh b)

boundary condition #2

-> Acc (Array sh b)

source array #2

-> Acc (Array sh c)

destination array

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

Stencil specification

class Stencil sh e stencil Source #

Minimal complete definition

stencilR, stencilPrj

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)

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

data Boundary t Source #

Boundary condition specification for stencil operations

clamp :: Boundary (Array sh e) Source #

Boundary condition where elements of the stencil which would be out-of-bounds are instead clamped to the edges of the array.

In the following 3x3 stencil, the out-of-bounds element b will instead return the value at position c:

  +------------+
  |a           |
 b|cd          |
  |e           |
  +------------+

mirror :: Boundary (Array sh e) Source #

Stencil boundary condition where coordinates beyond the array extent are instead mirrored

In the following 5x3 stencil, the out-of-bounds element c will instead return the value at position d, and similarly the element at b will return the value at e:

  +------------+
  |a           |
bc|def         |
  |g           |
  +------------+

wrap :: Boundary (Array sh e) Source #

Stencil boundary condition where coordinates beyond the array extent instead wrap around the array (circular boundary conditions).

In the following 3x3 stencil, the out of bounds elements will be read as in the pattern on the right.

 a bc
  +------------+      +------------+
 d|ef          |      |ef         d|
 g|hi          |  ->  |hi         g|
  |            |      |bc         a|
  +------------+      +------------+

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

Stencil boundary condition where the given function is applied to any outlying coordinates.

The function is passed the out-of-bounds index, so you can use it to specify different boundary conditions at each side. For example, the following would clamp out-of-bounds elements in the y-direction to zero, while having circular boundary conditions in the x-direction.

ring :: Acc (Matrix Float) -> Acc (Matrix Float)
ring xs = stencil f boundary xs
  where
    boundary :: Boundary (Matrix Float)
    boundary = function $ \(unlift -> Z :. y :. x) ->
      if y < 0 || y >= height
        then 0
        else if x < 0
               then xs ! index2 y (width+x)
               else xs ! index2 y (x-width)

    f :: Stencil3x3 Float -> Exp Float
    f = ...

    Z :. height :. width = unlift (shape xs)

Common stencil patterns

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

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

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

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

The Accelerate Expression Language

Scalar data types

data Exp t Source #

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

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

Instances

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 #

Unlift Exp () Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

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

Unlift Exp Z Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

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

Lift Exp Bool Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Bool Source #

Methods

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

Lift Exp Char Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Char Source #

Methods

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

Lift Exp Double Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Double Source #

Methods

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

Lift Exp Float Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Float Source #

Methods

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

Lift Exp Int Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Int Source #

Methods

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

Lift Exp Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Int8 Source #

Methods

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

Lift Exp Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Int16 Source #

Methods

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

Lift Exp Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Int32 Source #

Methods

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

Lift Exp Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Int64 Source #

Methods

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

Lift Exp Word Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Word Source #

Methods

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

Lift Exp Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Word8 Source #

Methods

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

Lift Exp Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Word16 Source #

Methods

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

Lift Exp Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Word32 Source #

Methods

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

Lift Exp Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Word64 Source #

Methods

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

Lift Exp () Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain () Source #

Methods

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

Lift Exp CChar Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CChar Source #

Methods

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

Lift Exp CSChar Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CSChar Source #

Methods

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

Lift Exp CUChar Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CUChar Source #

Methods

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

Lift Exp CShort Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CShort Source #

Methods

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

Lift Exp CUShort Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CUShort Source #

Lift Exp CInt Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CInt Source #

Methods

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

Lift Exp CUInt Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CUInt Source #

Methods

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

Lift Exp CLong Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CLong Source #

Methods

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

Lift Exp CULong Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CULong Source #

Methods

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

Lift Exp CLLong Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CLLong Source #

Methods

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

Lift Exp CULLong Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CULLong Source #

Lift Exp CFloat Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CFloat Source #

Methods

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

Lift Exp CDouble Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CDouble Source #

Lift Exp Half Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Half Source #

Methods

lift :: Half -> Exp (Plain Half) 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 a => Unlift Exp (Complex (Exp a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Complex

Methods

unlift :: Exp (Plain (Complex (Exp a))) -> Complex (Exp a) Source #

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

Defined in Data.Array.Accelerate.Data.Semigroup

Methods

unlift :: Exp (Plain (Min (Exp a))) -> Min (Exp a) Source #

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

Defined in Data.Array.Accelerate.Data.Semigroup

Methods

unlift :: Exp (Plain (Max (Exp a))) -> Max (Exp a) Source #

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

Defined in Data.Array.Accelerate.Data.Monoid

Methods

unlift :: Exp (Plain (Sum (Exp a))) -> Sum (Exp a) Source #

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

Defined in Data.Array.Accelerate.Data.Monoid

Methods

unlift :: Exp (Plain (Product (Exp a))) -> Product (Exp a) Source #

Unlift Exp (Exp e) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

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

(Lift Exp a, Elt (Plain a)) => Lift Exp (Maybe a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Maybe

Associated Types

type Plain (Maybe a) Source #

Methods

lift :: Maybe a -> Exp (Plain (Maybe a)) Source #

(Lift Exp a, Elt (Plain a)) => Lift Exp (Complex a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Complex

Associated Types

type Plain (Complex a) Source #

Methods

lift :: Complex a -> Exp (Plain (Complex a)) Source #

(Lift Exp a, Elt (Plain a)) => Lift Exp (Min a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Semigroup

Associated Types

type Plain (Min a) Source #

Methods

lift :: Min a -> Exp (Plain (Min a)) Source #

(Lift Exp a, Elt (Plain a)) => Lift Exp (Max a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Semigroup

Associated Types

type Plain (Max a) Source #

Methods

lift :: Max a -> Exp (Plain (Max a)) Source #

(Lift Exp a, Elt (Plain a)) => Lift Exp (Sum a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Monoid

Associated Types

type Plain (Sum a) Source #

Methods

lift :: Sum a -> Exp (Plain (Sum a)) Source #

(Lift Exp a, Elt (Plain a)) => Lift Exp (Product a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Monoid

Associated Types

type Plain (Product a) Source #

Methods

lift :: Product a -> Exp (Plain (Product a)) Source #

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

Lift Exp (Exp e) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (Exp e) Source #

Methods

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

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

Defined in Data.Array.Accelerate.Lift

Methods

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

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

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

Defined in Data.Array.Accelerate.Data.Either

Associated Types

type Plain (Either a b) Source #

Methods

lift :: Either a b -> Exp (Plain (Either a b)) Source #

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

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (x0, x1) Source #

Methods

lift :: (x0, x1) -> Exp (Plain (x0, x1)) 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 #

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

Defined in Data.Array.Accelerate.Lift

Methods

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

((Lift Exp x0, Lift Exp x1, Lift Exp x2), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2)) Source #

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

Defined in Data.Array.Accelerate.Lift

Methods

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

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3)) Source #

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

Defined in Data.Array.Accelerate.Lift

Methods

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

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4)) Source #

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

Defined in Data.Array.Accelerate.Lift

Methods

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

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4, Lift Exp x5), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4), Elt (Plain x5))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4, x5)) Source #

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

Defined in Data.Array.Accelerate.Lift

Methods

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

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4, Lift Exp x5, Lift Exp x6), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4), Elt (Plain x5), Elt (Plain x6))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4, x5, x6)) Source #

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

Defined in Data.Array.Accelerate.Lift

Methods

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

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4, Lift Exp x5, Lift Exp x6, Lift Exp x7), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4), Elt (Plain x5), Elt (Plain x6), Elt (Plain x7))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4, x5, x6, x7)) Source #

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

Defined in Data.Array.Accelerate.Lift

Methods

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

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4, Lift Exp x5, Lift Exp x6, Lift Exp x7, Lift Exp x8), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4), Elt (Plain x5), Elt (Plain x6), Elt (Plain x7), Elt (Plain x8))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8)) Source #

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

Defined in Data.Array.Accelerate.Lift

Methods

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

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4, Lift Exp x5, Lift Exp x6, Lift Exp x7, Lift Exp x8, Lift Exp x9), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4), Elt (Plain x5), Elt (Plain x6), Elt (Plain x7), Elt (Plain x8), Elt (Plain x9))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9)) Source #

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

Defined in Data.Array.Accelerate.Lift

Methods

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

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4, Lift Exp x5, Lift Exp x6, Lift Exp x7, Lift Exp x8, Lift Exp x9, Lift Exp x10), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4), Elt (Plain x5), Elt (Plain x6), Elt (Plain x7), Elt (Plain x8), Elt (Plain x9), Elt (Plain x10))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10)) Source #

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

Defined in Data.Array.Accelerate.Lift

Methods

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

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4, Lift Exp x5, Lift Exp x6, Lift Exp x7, Lift Exp x8, Lift Exp x9, Lift Exp x10, Lift Exp x11), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4), Elt (Plain x5), Elt (Plain x6), Elt (Plain x7), Elt (Plain x8), Elt (Plain x9), Elt (Plain x10), Elt (Plain x11))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11)) Source #

(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) => Unlift Exp (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11, Exp x12) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

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

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4, Lift Exp x5, Lift Exp x6, Lift Exp x7, Lift Exp x8, Lift Exp x9, Lift Exp x10, Lift Exp x11, Lift Exp x12), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4), Elt (Plain x5), Elt (Plain x6), Elt (Plain x7), Elt (Plain x8), Elt (Plain x9), Elt (Plain x10), Elt (Plain x11), Elt (Plain x12))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12)) Source #

(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) => Unlift Exp (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11, Exp x12, Exp x13) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

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

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4, Lift Exp x5, Lift Exp x6, Lift Exp x7, Lift Exp x8, Lift Exp x9, Lift Exp x10, Lift Exp x11, Lift Exp x12, Lift Exp x13), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4), Elt (Plain x5), Elt (Plain x6), Elt (Plain x7), Elt (Plain x8), Elt (Plain x9), Elt (Plain x10), Elt (Plain x11), Elt (Plain x12), Elt (Plain x13))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13)) Source #

(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) => Unlift Exp (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11, Exp x12, Exp x13, Exp x14) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

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

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4, Lift Exp x5, Lift Exp x6, Lift Exp x7, Lift Exp x8, Lift Exp x9, Lift Exp x10, Lift Exp x11, Lift Exp x12, Lift Exp x13, Lift Exp x14), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4), Elt (Plain x5), Elt (Plain x6), Elt (Plain x7), Elt (Plain x8), Elt (Plain x9), Elt (Plain x10), Elt (Plain x11), Elt (Plain x12), Elt (Plain x13), Elt (Plain x14))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14)) Source #

(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) => Unlift Exp (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11, Exp x12, Exp x13, Exp x14, Exp x15) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

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

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4, Lift Exp x5, Lift Exp x6, Lift Exp x7, Lift Exp x8, Lift Exp x9, Lift Exp x10, Lift Exp x11, Lift Exp x12, Lift Exp x13, Lift Exp x14, Lift Exp x15), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4), Elt (Plain x5), Elt (Plain x6), Elt (Plain x7), Elt (Plain x8), Elt (Plain x9), Elt (Plain x10), Elt (Plain x11), Elt (Plain x12), Elt (Plain x13), Elt (Plain x14), Elt (Plain x15))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15)) Source #

Bounded (Exp Bool) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Bounded (Exp Char) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Bounded (Exp Int) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Bounded (Exp Int8) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Bounded (Exp Int16) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Bounded (Exp Int32) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Bounded (Exp Int64) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Bounded (Exp Word) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Bounded (Exp Word8) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Bounded (Exp Word16) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Bounded (Exp Word32) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Bounded (Exp Word64) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Bounded (Exp ()) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Methods

minBound :: Exp () #

maxBound :: Exp () #

(Bounded x0, Bounded x1) => Bounded (Exp (x0, x1)) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Methods

minBound :: Exp (x0, x1) #

maxBound :: Exp (x0, x1) #

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

Defined in Data.Array.Accelerate.Classes.Bounded

Methods

minBound :: Exp (x0, x1, x2) #

maxBound :: Exp (x0, x1, x2) #

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

Defined in Data.Array.Accelerate.Classes.Bounded

Methods

minBound :: Exp (x0, x1, x2, x3) #

maxBound :: Exp (x0, x1, x2, x3) #

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

Defined in Data.Array.Accelerate.Classes.Bounded

Methods

minBound :: Exp (x0, x1, x2, x3, x4) #

maxBound :: Exp (x0, x1, x2, x3, x4) #

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

Defined in Data.Array.Accelerate.Classes.Bounded

Methods

minBound :: Exp (x0, x1, x2, x3, x4, x5) #

maxBound :: Exp (x0, x1, x2, x3, x4, x5) #

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

Defined in Data.Array.Accelerate.Classes.Bounded

Methods

minBound :: Exp (x0, x1, x2, x3, x4, x5, x6) #

maxBound :: Exp (x0, x1, x2, x3, x4, x5, x6) #

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

Defined in Data.Array.Accelerate.Classes.Bounded

Methods

minBound :: Exp (x0, x1, x2, x3, x4, x5, x6, x7) #

maxBound :: Exp (x0, x1, x2, x3, x4, x5, x6, x7) #

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

Defined in Data.Array.Accelerate.Classes.Bounded

Methods

minBound :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) #

maxBound :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) #

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

Defined in Data.Array.Accelerate.Classes.Bounded

Methods

minBound :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) #

maxBound :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) #

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

Defined in Data.Array.Accelerate.Classes.Bounded

Methods

minBound :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) #

maxBound :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) #

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

Defined in Data.Array.Accelerate.Classes.Bounded

Methods

minBound :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) #

maxBound :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) #

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

Defined in Data.Array.Accelerate.Classes.Bounded

Methods

minBound :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) #

maxBound :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) #

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

Defined in Data.Array.Accelerate.Classes.Bounded

Methods

minBound :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) #

maxBound :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) #

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

Defined in Data.Array.Accelerate.Classes.Bounded

Methods

minBound :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) #

maxBound :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) #

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

Defined in Data.Array.Accelerate.Classes.Bounded

Methods

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

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

Bounded a => Bounded (Exp (Min a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Semigroup

Methods

minBound :: Exp (Min a) #

maxBound :: Exp (Min a) #

Bounded a => Bounded (Exp (Max a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Semigroup

Methods

minBound :: Exp (Max a) #

maxBound :: Exp (Max a) #

Bounded a => Bounded (Exp (Sum a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Monoid

Methods

minBound :: Exp (Sum a) #

maxBound :: Exp (Sum a) #

Bounded a => Bounded (Exp (Product a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Monoid

Methods

minBound :: Exp (Product a) #

maxBound :: Exp (Product a) #

Bounded (Exp CChar) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Bounded (Exp CSChar) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Bounded (Exp CUChar) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Bounded (Exp CShort) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Bounded (Exp CUShort) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Bounded (Exp CInt) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Bounded (Exp CUInt) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Bounded (Exp CLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Bounded (Exp CULong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Bounded (Exp CLLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Bounded (Exp CULLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Enum (Exp Double) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Enum (Exp Float) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Enum (Exp Int) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Enum (Exp Int8) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Enum (Exp Int16) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Enum (Exp Int32) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Enum (Exp Int64) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Integral a => Enum (Exp (Ratio a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Ratio

Methods

succ :: Exp (Ratio a) -> Exp (Ratio a) #

pred :: Exp (Ratio a) -> Exp (Ratio a) #

toEnum :: Int -> Exp (Ratio a) #

fromEnum :: Exp (Ratio a) -> Int #

enumFrom :: Exp (Ratio a) -> [Exp (Ratio a)] #

enumFromThen :: Exp (Ratio a) -> Exp (Ratio a) -> [Exp (Ratio a)] #

enumFromTo :: Exp (Ratio a) -> Exp (Ratio a) -> [Exp (Ratio a)] #

enumFromThenTo :: Exp (Ratio a) -> Exp (Ratio a) -> Exp (Ratio a) -> [Exp (Ratio a)] #

Enum (Exp Word) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Enum (Exp Word8) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Enum (Exp Word16) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Enum (Exp Word32) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Enum (Exp Word64) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Enum (Exp CShort) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Enum (Exp CUShort) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Enum (Exp CInt) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Enum (Exp CUInt) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Enum (Exp CLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Enum (Exp CULong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Enum (Exp CLLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Enum (Exp CULLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Enum (Exp CFloat) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Enum (Exp CDouble) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Enum (Exp Half) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Eq (Exp a) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Methods

(==) :: Exp a -> Exp a -> Bool #

(/=) :: Exp a -> Exp a -> Bool #

Floating (Exp Double) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Floating

Floating (Exp Float) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Floating

RealFloat a => Floating (Exp (Complex a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Complex

Methods

pi :: Exp (Complex a) #

exp :: Exp (Complex a) -> Exp (Complex a) #

log :: Exp (Complex a) -> Exp (Complex a) #

sqrt :: Exp (Complex a) -> Exp (Complex a) #

(**) :: Exp (Complex a) -> Exp (Complex a) -> Exp (Complex a) #

logBase :: Exp (Complex a) -> Exp (Complex a) -> Exp (Complex a) #

sin :: Exp (Complex a) -> Exp (Complex a) #

cos :: Exp (Complex a) -> Exp (Complex a) #

tan :: Exp (Complex a) -> Exp (Complex a) #

asin :: Exp (Complex a) -> Exp (Complex a) #

acos :: Exp (Complex a) -> Exp (Complex a) #

atan :: Exp (Complex a) -> Exp (Complex a) #

sinh :: Exp (Complex a) -> Exp (Complex a) #

cosh :: Exp (Complex a) -> Exp (Complex a) #

tanh :: Exp (Complex a) -> Exp (Complex a) #

asinh :: Exp (Complex a) -> Exp (Complex a) #

acosh :: Exp (Complex a) -> Exp (Complex a) #

atanh :: Exp (Complex a) -> Exp (Complex a) #

log1p :: Exp (Complex a) -> Exp (Complex a) #

expm1 :: Exp (Complex a) -> Exp (Complex a) #

log1pexp :: Exp (Complex a) -> Exp (Complex a) #

log1mexp :: Exp (Complex a) -> Exp (Complex a) #

Floating (Exp CFloat) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Floating

Floating (Exp CDouble) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Floating

Floating (Exp Half) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Floating

Fractional (Exp Double) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Fractional

Fractional (Exp Float) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Fractional

Integral a => Fractional (Exp (Ratio a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Ratio

Methods

(/) :: Exp (Ratio a) -> Exp (Ratio a) -> Exp (Ratio a) #

recip :: Exp (Ratio a) -> Exp (Ratio a) #

fromRational :: Rational -> Exp (Ratio a) #

RealFloat a => Fractional (Exp (Complex a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Complex

Methods

(/) :: Exp (Complex a) -> Exp (Complex a) -> Exp (Complex a) #

recip :: Exp (Complex a) -> Exp (Complex a) #

fromRational :: Rational -> Exp (Complex a) #

Fractional (Exp CFloat) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Fractional

Fractional (Exp CDouble) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Fractional

Fractional (Exp Half) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Fractional

Integral (Exp Int) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Methods

quot :: Exp Int -> Exp Int -> Exp Int #

rem :: Exp Int -> Exp Int -> Exp Int #

div :: Exp Int -> Exp Int -> Exp Int #

mod :: Exp Int -> Exp Int -> Exp Int #

quotRem :: Exp Int -> Exp Int -> (Exp Int, Exp Int) #

divMod :: Exp Int -> Exp Int -> (Exp Int, Exp Int) #

toInteger :: Exp Int -> Integer #

Integral (Exp Int8) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Integral (Exp Int16) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Integral (Exp Int32) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Integral (Exp Int64) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Integral (Exp Word) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Integral (Exp Word8) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Integral (Exp Word16) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Integral (Exp Word32) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Integral (Exp Word64) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Integral (Exp CShort) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Integral (Exp CUShort) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Integral (Exp CInt) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Integral (Exp CUInt) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Integral (Exp CLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Integral (Exp CULong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Integral (Exp CLLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Integral (Exp CULLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Num (Exp Double) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Num (Exp Float) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Num (Exp Int) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Methods

(+) :: Exp Int -> Exp Int -> Exp Int #

(-) :: Exp Int -> Exp Int -> Exp Int #

(*) :: Exp Int -> Exp Int -> Exp Int #

negate :: Exp Int -> Exp Int #

abs :: Exp Int -> Exp Int #

signum :: Exp Int -> Exp Int #

fromInteger :: Integer -> Exp Int #

Num (Exp Int8) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Num (Exp Int16) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Num (Exp Int32) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Num (Exp Int64) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Integral a => Num (Exp (Ratio a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Ratio

Methods

(+) :: Exp (Ratio a) -> Exp (Ratio a) -> Exp (Ratio a) #

(-) :: Exp (Ratio a) -> Exp (Ratio a) -> Exp (Ratio a) #

(*) :: Exp (Ratio a) -> Exp (Ratio a) -> Exp (Ratio a) #

negate :: Exp (Ratio a) -> Exp (Ratio a) #

abs :: Exp (Ratio a) -> Exp (Ratio a) #

signum :: Exp (Ratio a) -> Exp (Ratio a) #

fromInteger :: Integer -> Exp (Ratio a) #

Num (Exp Word) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Num (Exp Word8) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Num (Exp Word16) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Num (Exp Word32) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Num (Exp Word64) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

RealFloat a => Num (Exp (Complex a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Complex

Methods

(+) :: Exp (Complex a) -> Exp (Complex a) -> Exp (Complex a) #

(-) :: Exp (Complex a) -> Exp (Complex a) -> Exp (Complex a) #

(*) :: Exp (Complex a) -> Exp (Complex a) -> Exp (Complex a) #

negate :: Exp (Complex a) -> Exp (Complex a) #

abs :: Exp (Complex a) -> Exp (Complex a) #

signum :: Exp (Complex a) -> Exp (Complex a) #

fromInteger :: Integer -> Exp (Complex a) #

Num a => Num (Exp (Min a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Semigroup

Methods

(+) :: Exp (Min a) -> Exp (Min a) -> Exp (Min a) #

(-) :: Exp (Min a) -> Exp (Min a) -> Exp (Min a) #

(*) :: Exp (Min a) -> Exp (Min a) -> Exp (Min a) #

negate :: Exp (Min a) -> Exp (Min a) #

abs :: Exp (Min a) -> Exp (Min a) #

signum :: Exp (Min a) -> Exp (Min a) #

fromInteger :: Integer -> Exp (Min a) #

Num a => Num (Exp (Max a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Semigroup

Methods

(+) :: Exp (Max a) -> Exp (Max a) -> Exp (Max a) #

(-) :: Exp (Max a) -> Exp (Max a) -> Exp (Max a) #

(*) :: Exp (Max a) -> Exp (Max a) -> Exp (Max a) #

negate :: Exp (Max a) -> Exp (Max a) #

abs :: Exp (Max a) -> Exp (Max a) #

signum :: Exp (Max a) -> Exp (Max a) #

fromInteger :: Integer -> Exp (Max a) #

Num a => Num (Exp (Sum a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Monoid

Methods

(+) :: Exp (Sum a) -> Exp (Sum a) -> Exp (Sum a) #

(-) :: Exp (Sum a) -> Exp (Sum a) -> Exp (Sum a) #

(*) :: Exp (Sum a) -> Exp (Sum a) -> Exp (Sum a) #

negate :: Exp (Sum a) -> Exp (Sum a) #

abs :: Exp (Sum a) -> Exp (Sum a) #

signum :: Exp (Sum a) -> Exp (Sum a) #

fromInteger :: Integer -> Exp (Sum a) #

Num a => Num (Exp (Product a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Monoid

Methods

(+) :: Exp (Product a) -> Exp (Product a) -> Exp (Product a) #

(-) :: Exp (Product a) -> Exp (Product a) -> Exp (Product a) #

(*) :: Exp (Product a) -> Exp (Product a) -> Exp (Product a) #

negate :: Exp (Product a) -> Exp (Product a) #

abs :: Exp (Product a) -> Exp (Product a) #

signum :: Exp (Product a) -> Exp (Product a) #

fromInteger :: Integer -> Exp (Product a) #

Num (Exp CShort) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Num (Exp CUShort) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Num (Exp CInt) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Num (Exp CUInt) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Num (Exp CLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Num (Exp CULong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Num (Exp CLLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Num (Exp CULLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Num (Exp CFloat) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Num (Exp CDouble) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Num (Exp Half) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Ord a => Ord (Exp a) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Methods

compare :: Exp a -> Exp a -> Ordering #

(<) :: Exp a -> Exp a -> Bool #

(<=) :: Exp a -> Exp a -> Bool #

(>) :: Exp a -> Exp a -> Bool #

(>=) :: Exp a -> Exp a -> Bool #

max :: Exp a -> Exp a -> Exp a #

min :: Exp a -> Exp a -> Exp a #

(Num a, Ord a) => Real (Exp a) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Real

Methods

toRational :: Exp a -> Rational #

RealFloat a => RealFloat (Exp a) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.RealFloat

Methods

floatRadix :: Exp a -> Integer #

floatDigits :: Exp a -> Int #

floatRange :: Exp a -> (Int, Int) #

decodeFloat :: Exp a -> (Integer, Int) #

encodeFloat :: Integer -> Int -> Exp a #

exponent :: Exp a -> Int #

significand :: Exp a -> Exp a #

scaleFloat :: Int -> Exp a -> Exp a #

isNaN :: Exp a -> Bool #

isInfinite :: Exp a -> Bool #

isDenormalized :: Exp a -> Bool #

isNegativeZero :: Exp a -> Bool #

isIEEE :: Exp a -> Bool #

atan2 :: Exp a -> Exp a -> Exp a #

RealFrac a => RealFrac (Exp a) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.RealFrac

Methods

properFraction :: Integral b => Exp a -> (b, Exp a) #

truncate :: Integral b => Exp a -> b #

round :: Integral b => Exp a -> b #

ceiling :: Integral b => Exp a -> b #

floor :: Integral b => Exp a -> b #

Elt e => Show (Exp e) Source # 
Instance details

Defined in Data.Array.Accelerate.Pretty

Methods

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

show :: Exp e -> String #

showList :: [Exp e] -> ShowS #

(Semigroup (Exp a), Elt a) => Semigroup (Exp (Maybe a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Maybe

Methods

(<>) :: Exp (Maybe a) -> Exp (Maybe a) -> Exp (Maybe a) #

sconcat :: NonEmpty (Exp (Maybe a)) -> Exp (Maybe a) #

stimes :: Integral b => b -> Exp (Maybe a) -> Exp (Maybe a) #

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

Defined in Data.Array.Accelerate.Data.Either

Methods

(<>) :: Exp (Either a b) -> Exp (Either a b) -> Exp (Either a b) #

sconcat :: NonEmpty (Exp (Either a b)) -> Exp (Either a b) #

stimes :: Integral b0 => b0 -> Exp (Either a b) -> Exp (Either a b) #

Semigroup (Exp ()) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Semigroup

Methods

(<>) :: Exp () -> Exp () -> Exp () #

sconcat :: NonEmpty (Exp ()) -> Exp () #

stimes :: Integral b => b -> Exp () -> Exp () #

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

Defined in Data.Array.Accelerate.Data.Semigroup

Methods

(<>) :: Exp (a, b) -> Exp (a, b) -> Exp (a, b) #

sconcat :: NonEmpty (Exp (a, b)) -> Exp (a, b) #

stimes :: Integral b0 => b0 -> Exp (a, b) -> Exp (a, b) #

(Elt a, Elt b, Elt c, Semigroup (Exp a), Semigroup (Exp b), Semigroup (Exp c)) => Semigroup (Exp (a, b, c)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Semigroup

Methods

(<>) :: Exp (a, b, c) -> Exp (a, b, c) -> Exp (a, b, c) #

sconcat :: NonEmpty (Exp (a, b, c)) -> Exp (a, b, c) #

stimes :: Integral b0 => b0 -> Exp (a, b, c) -> Exp (a, b, c) #

(Elt a, Elt b, Elt c, Elt d, Semigroup (Exp a), Semigroup (Exp b), Semigroup (Exp c), Semigroup (Exp d)) => Semigroup (Exp (a, b, c, d)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Semigroup

Methods

(<>) :: Exp (a, b, c, d) -> Exp (a, b, c, d) -> Exp (a, b, c, d) #

sconcat :: NonEmpty (Exp (a, b, c, d)) -> Exp (a, b, c, d) #

stimes :: Integral b0 => b0 -> Exp (a, b, c, d) -> Exp (a, b, c, d) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Semigroup (Exp a), Semigroup (Exp b), Semigroup (Exp c), Semigroup (Exp d), Semigroup (Exp e)) => Semigroup (Exp (a, b, c, d, e)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Semigroup

Methods

(<>) :: Exp (a, b, c, d, e) -> Exp (a, b, c, d, e) -> Exp (a, b, c, d, e) #

sconcat :: NonEmpty (Exp (a, b, c, d, e)) -> Exp (a, b, c, d, e) #

stimes :: Integral b0 => b0 -> Exp (a, b, c, d, e) -> Exp (a, b, c, d, e) #

Ord a => Semigroup (Exp (Min a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Semigroup

Methods

(<>) :: Exp (Min a) -> Exp (Min a) -> Exp (Min a) #

sconcat :: NonEmpty (Exp (Min a)) -> Exp (Min a) #

stimes :: Integral b => b -> Exp (Min a) -> Exp (Min a) #

Ord a => Semigroup (Exp (Max a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Semigroup

Methods

(<>) :: Exp (Max a) -> Exp (Max a) -> Exp (Max a) #

sconcat :: NonEmpty (Exp (Max a)) -> Exp (Max a) #

stimes :: Integral b => b -> Exp (Max a) -> Exp (Max a) #

Num a => Semigroup (Exp (Sum a)) Source #

Since: 1.2.0.0

Instance details

Defined in Data.Array.Accelerate.Data.Monoid

Methods

(<>) :: Exp (Sum a) -> Exp (Sum a) -> Exp (Sum a) #

sconcat :: NonEmpty (Exp (Sum a)) -> Exp (Sum a) #

stimes :: Integral b => b -> Exp (Sum a) -> Exp (Sum a) #

Num a => Semigroup (Exp (Product a)) Source #

Since: 1.2.0.0

Instance details

Defined in Data.Array.Accelerate.Data.Monoid

Methods

(<>) :: Exp (Product a) -> Exp (Product a) -> Exp (Product a) #

sconcat :: NonEmpty (Exp (Product a)) -> Exp (Product a) #

stimes :: Integral b => b -> Exp (Product a) -> Exp (Product a) #

(Monoid (Exp a), Elt a) => Monoid (Exp (Maybe a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Maybe

Methods

mempty :: Exp (Maybe a) #

mappend :: Exp (Maybe a) -> Exp (Maybe a) -> Exp (Maybe a) #

mconcat :: [Exp (Maybe a)] -> Exp (Maybe a) #

Monoid (Exp ()) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Monoid

Methods

mempty :: Exp () #

mappend :: Exp () -> Exp () -> Exp () #

mconcat :: [Exp ()] -> Exp () #

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

Defined in Data.Array.Accelerate.Data.Monoid

Methods

mempty :: Exp (a, b) #

mappend :: Exp (a, b) -> Exp (a, b) -> Exp (a, b) #

mconcat :: [Exp (a, b)] -> Exp (a, b) #

(Elt a, Elt b, Elt c, Monoid (Exp a), Monoid (Exp b), Monoid (Exp c)) => Monoid (Exp (a, b, c)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Monoid

Methods

mempty :: Exp (a, b, c) #

mappend :: Exp (a, b, c) -> Exp (a, b, c) -> Exp (a, b, c) #

mconcat :: [Exp (a, b, c)] -> Exp (a, b, c) #

(Elt a, Elt b, Elt c, Elt d, Monoid (Exp a), Monoid (Exp b), Monoid (Exp c), Monoid (Exp d)) => Monoid (Exp (a, b, c, d)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Monoid

Methods

mempty :: Exp (a, b, c, d) #

mappend :: Exp (a, b, c, d) -> Exp (a, b, c, d) -> Exp (a, b, c, d) #

mconcat :: [Exp (a, b, c, d)] -> Exp (a, b, c, d) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Monoid (Exp a), Monoid (Exp b), Monoid (Exp c), Monoid (Exp d), Monoid (Exp e)) => Monoid (Exp (a, b, c, d, e)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Monoid

Methods

mempty :: Exp (a, b, c, d, e) #

mappend :: Exp (a, b, c, d, e) -> Exp (a, b, c, d, e) -> Exp (a, b, c, d, e) #

mconcat :: [Exp (a, b, c, d, e)] -> Exp (a, b, c, d, e) #

(Ord a, Bounded a) => Monoid (Exp (Min a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Semigroup

Methods

mempty :: Exp (Min a) #

mappend :: Exp (Min a) -> Exp (Min a) -> Exp (Min a) #

mconcat :: [Exp (Min a)] -> Exp (Min a) #

(Ord a, Bounded a) => Monoid (Exp (Max a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Semigroup

Methods

mempty :: Exp (Max a) #

mappend :: Exp (Max a) -> Exp (Max a) -> Exp (Max a) #

mconcat :: [Exp (Max a)] -> Exp (Max a) #

Num a => Monoid (Exp (Sum a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Monoid

Methods

mempty :: Exp (Sum a) #

mappend :: Exp (Sum a) -> Exp (Sum a) -> Exp (Sum a) #

mconcat :: [Exp (Sum a)] -> Exp (Sum a) #

Num a => Monoid (Exp (Product a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Monoid

Methods

mempty :: Exp (Product a) #

mappend :: Exp (Product a) -> Exp (Product a) -> Exp (Product a) #

mconcat :: [Exp (Product a)] -> Exp (Product a) #

Floating b => Floating (Fold a (Exp b)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Fold

Methods

pi :: Fold a (Exp b) #

exp :: Fold a (Exp b) -> Fold a (Exp b) #

log :: Fold a (Exp b) -> Fold a (Exp b) #

sqrt :: Fold a (Exp b) -> Fold a (Exp b) #

(**) :: Fold a (Exp b) -> Fold a (Exp b) -> Fold a (Exp b) #

logBase :: Fold a (Exp b) -> Fold a (Exp b) -> Fold a (Exp b) #

sin :: Fold a (Exp b) -> Fold a (Exp b) #

cos :: Fold a (Exp b) -> Fold a (Exp b) #

tan :: Fold a (Exp b) -> Fold a (Exp b) #

asin :: Fold a (Exp b) -> Fold a (Exp b) #

acos :: Fold a (Exp b) -> Fold a (Exp b) #

atan :: Fold a (Exp b) -> Fold a (Exp b) #

sinh :: Fold a (Exp b) -> Fold a (Exp b) #

cosh :: Fold a (Exp b) -> Fold a (Exp b) #

tanh :: Fold a (Exp b) -> Fold a (Exp b) #

asinh :: Fold a (Exp b) -> Fold a (Exp b) #

acosh :: Fold a (Exp b) -> Fold a (Exp b) #

atanh :: Fold a (Exp b) -> Fold a (Exp b) #

log1p :: Fold a (Exp b) -> Fold a (Exp b) #

expm1 :: Fold a (Exp b) -> Fold a (Exp b) #

log1pexp :: Fold a (Exp b) -> Fold a (Exp b) #

log1mexp :: Fold a (Exp b) -> Fold a (Exp b) #

Fractional b => Fractional (Fold a (Exp b)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Fold

Methods

(/) :: Fold a (Exp b) -> Fold a (Exp b) -> Fold a (Exp b) #

recip :: Fold a (Exp b) -> Fold a (Exp b) #

fromRational :: Rational -> Fold a (Exp b) #

Num b => Num (Fold a (Exp b)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Fold

Methods

(+) :: Fold a (Exp b) -> Fold a (Exp b) -> Fold a (Exp b) #

(-) :: Fold a (Exp b) -> Fold a (Exp b) -> Fold a (Exp b) #

(*) :: Fold a (Exp b) -> Fold a (Exp b) -> Fold a (Exp b) #

negate :: Fold a (Exp b) -> Fold a (Exp b) #

abs :: Fold a (Exp b) -> Fold a (Exp b) #

signum :: Fold a (Exp b) -> Fold a (Exp b) #

fromInteger :: Integer -> Fold a (Exp b) #

Function (Exp a -> f) => Show (Exp a -> f) Source # 
Instance details

Defined in Data.Array.Accelerate.Pretty

Methods

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

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

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

type EltT Exp t Source # 
Instance details

Defined in Data.Array.Accelerate.Prelude

type EltT Exp t = Elt t
type Plain (Exp e) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

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

Defined in Data.Array.Accelerate.Lift

type Plain (ix :. Exp e) = Plain ix :. e

SIMD vectors

data Vec (n :: Nat) a Source #

Instances

Instances details
Eq (Vec n a) Source # 
Instance details

Defined in Data.Primitive.Vec

Methods

(==) :: Vec n a -> Vec n a -> Bool #

(/=) :: Vec n a -> Vec n a -> Bool #

(Show a, Prim a, KnownNat n) => Show (Vec n a) Source # 
Instance details

Defined in Data.Primitive.Vec

Methods

showsPrec :: Int -> Vec n a -> ShowS #

show :: Vec n a -> String #

showList :: [Vec n a] -> ShowS #

(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

type VecElt a = (Elt a, Prim a, IsSingle a, EltR a ~ a) Source #

Type classes

Basic type classes

class Elt a => Eq a where Source #

The Eq class defines equality == and inequality /= for scalar Accelerate expressions.

For convenience, we include Elt as a superclass.

Minimal complete definition

(==) | (/=)

Methods

(==) :: Exp a -> Exp a -> Exp Bool infix 4 Source #

(/=) :: Exp a -> Exp a -> Exp Bool infix 4 Source #

Instances

Instances details
Eq Bool Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq Char Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Methods

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

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

Eq Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq Ordering Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Eq Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq () Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Methods

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

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

Eq CChar Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq CSChar Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq CUChar Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq CShort Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq CUShort Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq CInt Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq CUInt Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq CLong Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq CULong Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq CLLong Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq CULLong Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq CFloat Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq CDouble Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Eq Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

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 #

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

Defined in Data.Array.Accelerate.Data.Maybe

Methods

(==) :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Bool Source #

(/=) :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Bool Source #

Integral a => Eq (Ratio a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Ratio

Methods

(==) :: Exp (Ratio a) -> Exp (Ratio a) -> Exp Bool Source #

(/=) :: Exp (Ratio a) -> Exp (Ratio a) -> Exp Bool Source #

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

Defined in Data.Array.Accelerate.Data.Complex

Methods

(==) :: Exp (Complex a) -> Exp (Complex a) -> Exp Bool Source #

(/=) :: Exp (Complex a) -> Exp (Complex a) -> Exp Bool Source #

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

Defined in Data.Array.Accelerate.Data.Semigroup

Methods

(==) :: Exp (Min a) -> Exp (Min a) -> Exp Bool Source #

(/=) :: Exp (Min a) -> Exp (Min a) -> Exp Bool Source #

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

Defined in Data.Array.Accelerate.Data.Semigroup

Methods

(==) :: Exp (Max a) -> Exp (Max a) -> Exp Bool Source #

(/=) :: Exp (Max a) -> Exp (Max a) -> Exp Bool Source #

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

Defined in Data.Array.Accelerate.Data.Monoid

Methods

(==) :: Exp (Sum a) -> Exp (Sum a) -> Exp Bool Source #

(/=) :: Exp (Sum a) -> Exp (Sum a) -> Exp Bool Source #

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

Defined in Data.Array.Accelerate.Data.Monoid

Methods

(==) :: Exp (Product a) -> Exp (Product a) -> Exp Bool Source #

(/=) :: Exp (Product a) -> Exp (Product a) -> Exp Bool Source #

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

Defined in Data.Array.Accelerate.Data.Either

Methods

(==) :: Exp (Either a b) -> Exp (Either a b) -> Exp Bool Source #

(/=) :: Exp (Either a b) -> Exp (Either a b) -> Exp Bool Source #

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

Defined in Data.Array.Accelerate.Classes.Eq

Methods

(==) :: Exp (x0, x1) -> Exp (x0, x1) -> Exp Bool Source #

(/=) :: Exp (x0, x1) -> Exp (x0, x1) -> Exp Bool Source #

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 #

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

Defined in Data.Array.Accelerate.Classes.Eq

Methods

(==) :: Exp (x0, x1, x2) -> Exp (x0, x1, x2) -> Exp Bool Source #

(/=) :: Exp (x0, x1, x2) -> Exp (x0, x1, x2) -> Exp Bool Source #

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

Defined in Data.Array.Accelerate.Classes.Eq

Methods

(==) :: Exp (x0, x1, x2, x3) -> Exp (x0, x1, x2, x3) -> Exp Bool Source #

(/=) :: Exp (x0, x1, x2, x3) -> Exp (x0, x1, x2, x3) -> Exp Bool Source #

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

Defined in Data.Array.Accelerate.Classes.Eq

Methods

(==) :: Exp (x0, x1, x2, x3, x4) -> Exp (x0, x1, x2, x3, x4) -> Exp Bool Source #

(/=) :: Exp (x0, x1, x2, x3, x4) -> Exp (x0, x1, x2, x3, x4) -> Exp Bool Source #

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

Defined in Data.Array.Accelerate.Classes.Eq

Methods

(==) :: Exp (x0, x1, x2, x3, x4, x5) -> Exp (x0, x1, x2, x3, x4, x5) -> Exp Bool Source #

(/=) :: Exp (x0, x1, x2, x3, x4, x5) -> Exp (x0, x1, x2, x3, x4, x5) -> Exp Bool Source #

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

Defined in Data.Array.Accelerate.Classes.Eq

Methods

(==) :: Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp Bool Source #

(/=) :: Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp Bool Source #

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

Defined in Data.Array.Accelerate.Classes.Eq

Methods

(==) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp Bool Source #

(/=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp Bool Source #

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

Defined in Data.Array.Accelerate.Classes.Eq

Methods

(==) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp Bool Source #

(/=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp Bool Source #

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

Defined in Data.Array.Accelerate.Classes.Eq

Methods

(==) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp Bool Source #

(/=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp Bool Source #

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

Defined in Data.Array.Accelerate.Classes.Eq

Methods

(==) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp Bool Source #

(/=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp Bool Source #

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

Defined in Data.Array.Accelerate.Classes.Eq

Methods

(==) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp Bool Source #

(/=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp Bool Source #

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

Defined in Data.Array.Accelerate.Classes.Eq

Methods

(==) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp Bool Source #

(/=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp Bool Source #

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

Defined in Data.Array.Accelerate.Classes.Eq

Methods

(==) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp Bool Source #

(/=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp Bool Source #

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

Defined in Data.Array.Accelerate.Classes.Eq

Methods

(==) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp Bool Source #

(/=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp Bool Source #

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

Defined in Data.Array.Accelerate.Classes.Eq

Methods

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

(/=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Exp Bool Source #

class Eq a => Ord a where Source #

The Ord class for totally ordered datatypes

Minimal complete definition

(<=) | compare

Methods

(<) :: Exp a -> Exp a -> Exp Bool infix 4 Source #

(>) :: Exp a -> Exp a -> Exp Bool infix 4 Source #

(<=) :: Exp a -> Exp a -> Exp Bool infix 4 Source #

(>=) :: Exp a -> Exp a -> Exp Bool infix 4 Source #

min :: Exp a -> Exp a -> Exp a Source #

max :: Exp a -> Exp a -> Exp a Source #

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

Instances

Instances details
Ord Char Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord Ordering Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord () Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Methods

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

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

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

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

min :: Exp () -> Exp () -> Exp () Source #

max :: Exp () -> Exp () -> Exp () Source #

compare :: Exp () -> Exp () -> Exp Ordering Source #

Ord CChar Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord CSChar Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord CUChar Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord CShort Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord CUShort Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord CInt Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord CUInt Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord CLong Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord CULong Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord CLLong Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord CULLong Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord CFloat Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord CDouble Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

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 #

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

Defined in Data.Array.Accelerate.Data.Maybe

Methods

(<) :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Bool Source #

(>) :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Bool Source #

(<=) :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Bool Source #

(>=) :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Bool Source #

min :: Exp (Maybe a) -> Exp (Maybe a) -> Exp (Maybe a) Source #

max :: Exp (Maybe a) -> Exp (Maybe a) -> Exp (Maybe a) Source #

compare :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Ordering Source #

Integral a => Ord (Ratio a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Ratio

Methods

(<) :: Exp (Ratio a) -> Exp (Ratio a) -> Exp Bool Source #

(>) :: Exp (Ratio a) -> Exp (Ratio a) -> Exp Bool Source #

(<=) :: Exp (Ratio a) -> Exp (Ratio a) -> Exp Bool Source #

(>=) :: Exp (Ratio a) -> Exp (Ratio a) -> Exp Bool Source #

min :: Exp (Ratio a) -> Exp (Ratio a) -> Exp (Ratio a) Source #

max :: Exp (Ratio a) -> Exp (Ratio a) -> Exp (Ratio a) Source #

compare :: Exp (Ratio a) -> Exp (Ratio a) -> Exp Ordering Source #

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

Defined in Data.Array.Accelerate.Data.Semigroup

Methods

(<) :: Exp (Min a) -> Exp (Min a) -> Exp Bool Source #

(>) :: Exp (Min a) -> Exp (Min a) -> Exp Bool Source #

(<=) :: Exp (Min a) -> Exp (Min a) -> Exp Bool Source #

(>=) :: Exp (Min a) -> Exp (Min a) -> Exp Bool Source #

min :: Exp (Min a) -> Exp (Min a) -> Exp (Min a) Source #

max :: Exp (Min a) -> Exp (Min a) -> Exp (Min a) Source #

compare :: Exp (Min a) -> Exp (Min a) -> Exp Ordering Source #

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

Defined in Data.Array.Accelerate.Data.Semigroup

Methods

(<) :: Exp (Max a) -> Exp (Max a) -> Exp Bool Source #

(>) :: Exp (Max a) -> Exp (Max a) -> Exp Bool Source #

(<=) :: Exp (Max a) -> Exp (Max a) -> Exp Bool Source #

(>=) :: Exp (Max a) -> Exp (Max a) -> Exp Bool Source #

min :: Exp (Max a) -> Exp (Max a) -> Exp (Max a) Source #

max :: Exp (Max a) -> Exp (Max a) -> Exp (Max a) Source #

compare :: Exp (Max a) -> Exp (Max a) -> Exp Ordering Source #

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

Defined in Data.Array.Accelerate.Data.Monoid

Methods

(<) :: Exp (Sum a) -> Exp (Sum a) -> Exp Bool Source #

(>) :: Exp (Sum a) -> Exp (Sum a) -> Exp Bool Source #

(<=) :: Exp (Sum a) -> Exp (Sum a) -> Exp Bool Source #

(>=) :: Exp (Sum a) -> Exp (Sum a) -> Exp Bool Source #

min :: Exp (Sum a) -> Exp (Sum a) -> Exp (Sum a) Source #

max :: Exp (Sum a) -> Exp (Sum a) -> Exp (Sum a) Source #

compare :: Exp (Sum a) -> Exp (Sum a) -> Exp Ordering Source #

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

Defined in Data.Array.Accelerate.Data.Monoid

Methods

(<) :: Exp (Product a) -> Exp (Product a) -> Exp Bool Source #

(>) :: Exp (Product a) -> Exp (Product a) -> Exp Bool Source #

(<=) :: Exp (Product a) -> Exp (Product a) -> Exp Bool Source #

(>=) :: Exp (Product a) -> Exp (Product a) -> Exp Bool Source #

min :: Exp (Product a) -> Exp (Product a) -> Exp (Product a) Source #

max :: Exp (Product a) -> Exp (Product a) -> Exp (Product a) Source #

compare :: Exp (Product a) -> Exp (Product a) -> Exp Ordering Source #

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

Defined in Data.Array.Accelerate.Data.Either

Methods

(<) :: Exp (Either a b) -> Exp (Either a b) -> Exp Bool Source #

(>) :: Exp (Either a b) -> Exp (Either a b) -> Exp Bool Source #

(<=) :: Exp (Either a b) -> Exp (Either a b) -> Exp Bool Source #

(>=) :: Exp (Either a b) -> Exp (Either a b) -> Exp Bool Source #

min :: Exp (Either a b) -> Exp (Either a b) -> Exp (Either a b) Source #

max :: Exp (Either a b) -> Exp (Either a b) -> Exp (Either a b) Source #

compare :: Exp (Either a b) -> Exp (Either a b) -> Exp Ordering Source #

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

Defined in Data.Array.Accelerate.Classes.Ord

Methods

(<) :: Exp (x0, x1) -> Exp (x0, x1) -> Exp Bool Source #

(>) :: Exp (x0, x1) -> Exp (x0, x1) -> Exp Bool Source #

(<=) :: Exp (x0, x1) -> Exp (x0, x1) -> Exp Bool Source #

(>=) :: Exp (x0, x1) -> Exp (x0, x1) -> Exp Bool Source #

min :: Exp (x0, x1) -> Exp (x0, x1) -> Exp (x0, x1) Source #

max :: Exp (x0, x1) -> Exp (x0, x1) -> Exp (x0, x1) Source #

compare :: Exp (x0, x1) -> Exp (x0, x1) -> Exp Ordering 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 #

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

Defined in Data.Array.Accelerate.Classes.Ord

Methods

(<) :: Exp (x0, x1, x2) -> Exp (x0, x1, x2) -> Exp Bool Source #

(>) :: Exp (x0, x1, x2) -> Exp (x0, x1, x2) -> Exp Bool Source #

(<=) :: Exp (x0, x1, x2) -> Exp (x0, x1, x2) -> Exp Bool Source #

(>=) :: Exp (x0, x1, x2) -> Exp (x0, x1, x2) -> Exp Bool Source #

min :: Exp (x0, x1, x2) -> Exp (x0, x1, x2) -> Exp (x0, x1, x2) Source #

max :: Exp (x0, x1, x2) -> Exp (x0, x1, x2) -> Exp (x0, x1, x2) Source #

compare :: Exp (x0, x1, x2) -> Exp (x0, x1, x2) -> Exp Ordering Source #

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

Defined in Data.Array.Accelerate.Classes.Ord

Methods

(<) :: Exp (x0, x1, x2, x3) -> Exp (x0, x1, x2, x3) -> Exp Bool Source #

(>) :: Exp (x0, x1, x2, x3) -> Exp (x0, x1, x2, x3) -> Exp Bool Source #

(<=) :: Exp (x0, x1, x2, x3) -> Exp (x0, x1, x2, x3) -> Exp Bool Source #

(>=) :: Exp (x0, x1, x2, x3) -> Exp (x0, x1, x2, x3) -> Exp Bool Source #

min :: Exp (x0, x1, x2, x3) -> Exp (x0, x1, x2, x3) -> Exp (x0, x1, x2, x3) Source #

max :: Exp (x0, x1, x2, x3) -> Exp (x0, x1, x2, x3) -> Exp (x0, x1, x2, x3) Source #

compare :: Exp (x0, x1, x2, x3) -> Exp (x0, x1, x2, x3) -> Exp Ordering Source #

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

Defined in Data.Array.Accelerate.Classes.Ord

Methods

(<) :: Exp (x0, x1, x2, x3, x4) -> Exp (x0, x1, x2, x3, x4) -> Exp Bool Source #

(>) :: Exp (x0, x1, x2, x3, x4) -> Exp (x0, x1, x2, x3, x4) -> Exp Bool Source #

(<=) :: Exp (x0, x1, x2, x3, x4) -> Exp (x0, x1, x2, x3, x4) -> Exp Bool Source #

(>=) :: Exp (x0, x1, x2, x3, x4) -> Exp (x0, x1, x2, x3, x4) -> Exp Bool Source #

min :: Exp (x0, x1, x2, x3, x4) -> Exp (x0, x1, x2, x3, x4) -> Exp (x0, x1, x2, x3, x4) Source #

max :: Exp (x0, x1, x2, x3, x4) -> Exp (x0, x1, x2, x3, x4) -> Exp (x0, x1, x2, x3, x4) Source #

compare :: Exp (x0, x1, x2, x3, x4) -> Exp (x0, x1, x2, x3, x4) -> Exp Ordering Source #

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

Defined in Data.Array.Accelerate.Classes.Ord

Methods

(<) :: Exp (x0, x1, x2, x3, x4, x5) -> Exp (x0, x1, x2, x3, x4, x5) -> Exp Bool Source #

(>) :: Exp (x0, x1, x2, x3, x4, x5) -> Exp (x0, x1, x2, x3, x4, x5) -> Exp Bool Source #

(<=) :: Exp (x0, x1, x2, x3, x4, x5) -> Exp (x0, x1, x2, x3, x4, x5) -> Exp Bool Source #

(>=) :: Exp (x0, x1, x2, x3, x4, x5) -> Exp (x0, x1, x2, x3, x4, x5) -> Exp Bool Source #

min :: Exp (x0, x1, x2, x3, x4, x5) -> Exp (x0, x1, x2, x3, x4, x5) -> Exp (x0, x1, x2, x3, x4, x5) Source #

max :: Exp (x0, x1, x2, x3, x4, x5) -> Exp (x0, x1, x2, x3, x4, x5) -> Exp (x0, x1, x2, x3, x4, x5) Source #

compare :: Exp (x0, x1, x2, x3, x4, x5) -> Exp (x0, x1, x2, x3, x4, x5) -> Exp Ordering Source #

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

Defined in Data.Array.Accelerate.Classes.Ord

Methods

(<) :: Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp Bool Source #

(>) :: Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp Bool Source #

(<=) :: Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp Bool Source #

(>=) :: Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp Bool Source #

min :: Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp (x0, x1, x2, x3, x4, x5, x6) Source #

max :: Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp (x0, x1, x2, x3, x4, x5, x6) Source #

compare :: Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp Ordering Source #

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

Defined in Data.Array.Accelerate.Classes.Ord

Methods

(<) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp Bool Source #

(>) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp Bool Source #

(<=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp Bool Source #

(>=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp Bool Source #

min :: Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7) Source #

max :: Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7) Source #

compare :: Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp Ordering Source #

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

Defined in Data.Array.Accelerate.Classes.Ord

Methods

(<) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp Bool Source #

(>) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp Bool Source #

(<=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp Bool Source #

(>=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp Bool Source #

min :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) Source #

max :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) Source #

compare :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp Ordering Source #

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

Defined in Data.Array.Accelerate.Classes.Ord

Methods

(<) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp Bool Source #

(>) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp Bool Source #

(<=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp Bool Source #

(>=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp Bool Source #

min :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) Source #

max :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) Source #

compare :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp Ordering Source #

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

Defined in Data.Array.Accelerate.Classes.Ord

Methods

(<) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp Bool Source #

(>) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp Bool Source #

(<=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp Bool Source #

(>=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp Bool Source #

min :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) Source #

max :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) Source #

compare :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp Ordering Source #

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

Defined in Data.Array.Accelerate.Classes.Ord

Methods

(<) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp Bool Source #

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

(<=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp Bool Source #

(>=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp Bool Source #

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

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

compare :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp Ordering Source #

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

Defined in Data.Array.Accelerate.Classes.Ord

Methods

(<) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp Bool Source #

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

(<=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp Bool Source #

(>=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp Bool Source #

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

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

compare :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp Ordering Source #

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

Defined in Data.Array.Accelerate.Classes.Ord

Methods

(<) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp Bool Source #

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

(<=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp Bool Source #

(>=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp Bool Source #

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

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

compare :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp Ordering Source #

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

Defined in Data.Array.Accelerate.Classes.Ord

Methods

(<) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp Bool Source #

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

(<=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp Bool Source #

(>=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp Bool Source #

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

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

compare :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp Ordering Source #

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

Defined in Data.Array.Accelerate.Classes.Ord

Methods

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

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

(<=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Exp Bool Source #

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

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

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

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

data Ordering #

Constructors

LT 
EQ 
GT 

Instances

Instances details
Bounded Ordering

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Ordering

Since: base-2.1

Instance details

Defined in GHC.Enum

Eq Ordering 
Instance details

Defined in GHC.Classes

Ord Ordering 
Instance details

Defined in GHC.Classes

Read Ordering

Since: base-2.1

Instance details

Defined in GHC.Read

Show Ordering

Since: base-2.1

Instance details

Defined in GHC.Show

Ix Ordering

Since: base-2.1

Instance details

Defined in GHC.Ix

Generic Ordering

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Ordering :: Type -> Type #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Semigroup Ordering

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Monoid Ordering

Since: base-2.1

Instance details

Defined in GHC.Base

NFData Ordering 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Ordering -> () #

Hashable Ordering 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Ordering -> Int #

hash :: Ordering -> Int #

AsEmpty Ordering 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' Ordering () #

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

Eq Ordering Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Ord Ordering Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

type Rep Ordering 
Instance details

Defined in GHC.Generics

type Rep Ordering = D1 ('MetaData "Ordering" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "LT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EQ" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GT" 'PrefixI 'False) (U1 :: Type -> Type)))

type Enum a = Enum (Exp a) Source #

Operations over sequentially ordered types

succ :: Enum a => a -> a #

the successor of a value. For numeric types, succ adds 1.

pred :: Enum a => a -> a #

the predecessor of a value. For numeric types, pred subtracts 1.

type Bounded a = (Elt a, Bounded (Exp a)) Source #

Name the upper and lower limits of a type. Types which are not totally ordered may still have upper and lower bounds.

minBound :: Bounded a => a #

maxBound :: Bounded a => a #

Numeric type classes

type Num a = (Elt a, Num (Exp a)) Source #

Conversion from an Integer.

An integer literal represents the application of the function fromInteger to the appropriate value of type Integer. We export this specialised version where the return type is fixed to an Exp term in order to improve type checking in Accelerate modules when RebindableSyntax is enabled.

fromInteger :: Num a => Integer -> Exp a fromInteger = P.fromInteger

Basic numeric class

(+) :: Num a => a -> a -> a infixl 6 #

(-) :: Num a => a -> a -> a infixl 6 #

(*) :: Num a => a -> a -> a infixl 7 #

negate :: Num a => a -> a #

Unary negation.

abs :: Num a => a -> a #

Absolute value.

signum :: Num a => a -> a #

Sign of a number. The functions abs and signum should satisfy the law:

abs x * signum x == x

For real numbers, the signum is either -1 (negative), 0 (zero) or 1 (positive).

fromInteger :: Num a => Integer -> a #

Conversion from an Integer. An integer literal represents the application of the function fromInteger to the appropriate value of type Integer, so such literals have type (Num a) => a.

type Integral a = (Enum a, Ord a, Num a, Integral (Exp a)) Source #

Integral numbers, supporting integral division

quot :: Integral a => a -> a -> a infixl 7 #

integer division truncated toward zero

rem :: Integral a => a -> a -> a infixl 7 #

integer remainder, satisfying

(x `quot` y)*y + (x `rem` y) == x

div :: Integral a => a -> a -> a infixl 7 #

integer division truncated toward negative infinity

mod :: Integral a => a -> a -> a infixl 7 #

integer modulus, satisfying

(x `div` y)*y + (x `mod` y) == x

quotRem :: Integral a => a -> a -> (a, a) #

simultaneous quot and rem

divMod :: Integral a => a -> a -> (a, a) #

simultaneous div and mod

class (Num a, Ord a) => Rational a where Source #

Numbers which can be expressed as the quotient of two integers.

Accelerate does not have an arbitrary precision Integer type, however fixed-length large integers are provide by the accelerate-bignum package.

Methods

toRational :: (FromIntegral Int64 b, Integral b) => Exp a -> Exp (Ratio b) Source #

Convert a number to the quotient of two integers

Instances

Instances details
Rational Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Rational Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Rational Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Rational Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Rational Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Rational Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Rational Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Rational Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Rational Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Rational Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Rational Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Rational Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Rational Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

type Fractional a = (Num a, Fractional (Exp a)) Source #

Conversion from a Rational.

A floating point literal representations the application of the function fromRational to a value of type Rational. We export this specialised version where the return type is fixed to an Exp term in order to improve type checking in Accelerate modules when RebindableSyntax is enabled.

fromRational :: Fractional a => Rational -> Exp a fromRational = P.fromRational

Fractional numbers, supporting real division

(/) :: Fractional a => a -> a -> a infixl 7 #

Fractional division.

recip :: Fractional a => a -> a #

Reciprocal fraction.

fromRational :: Fractional a => Rational -> a #

Conversion from a Rational (that is Ratio Integer). A floating literal stands for an application of fromRational to a value of type Rational, so such literals have type (Fractional a) => a.

type Floating a = (Fractional a, Floating (Exp a)) Source #

Trigonometric and hyperbolic functions and related functions

pi :: Floating a => a #

sin :: Floating a => a -> a #

cos :: Floating a => a -> a #

tan :: Floating a => a -> a #

asin :: Floating a => a -> a #

acos :: Floating a => a -> a #

atan :: Floating a => a -> a #

sinh :: Floating a => a -> a #

cosh :: Floating a => a -> a #

tanh :: Floating a => a -> a #

asinh :: Floating a => a -> a #

acosh :: Floating a => a -> a #

atanh :: Floating a => a -> a #

exp :: Floating a => a -> a #

sqrt :: Floating a => a -> a #

log :: Floating a => a -> a #

(**) :: Floating a => a -> a -> a infixr 8 #

logBase :: Floating a => a -> a -> a #

class (Ord a, Fractional a) => RealFrac a where Source #

Extracting components of fractions.

Minimal complete definition

properFraction

Methods

properFraction :: (Integral b, FromIntegral Int64 b) => Exp a -> (Exp b, Exp a) Source #

The function properFraction takes a real fractional number x and returns a pair (n,f) such that x = n+f, and:

  • n is an integral number with the same sign as x; and
  • f is a fraction with the same type and sign as x, and with absolute value less than 1.

The default definitions of the ceiling, floor, truncate and round functions are in terms of properFraction.

truncate :: (Integral b, FromIntegral Int64 b) => Exp a -> Exp b Source #

truncate x returns the integer nearest x between zero and x

round :: (Integral b, FromIntegral Int64 b) => Exp a -> Exp b Source #

round x returns the nearest integer to x; the even integer if x is equidistant between two integers

ceiling :: (Integral b, FromIntegral Int64 b) => Exp a -> Exp b Source #

ceiling x returns the least integer not less than x

floor :: (Integral b, FromIntegral Int64 b) => Exp a -> Exp b Source #

floor x returns the greatest integer not greater than x

Instances

Instances details
RealFrac Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.RealFrac

RealFrac Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.RealFrac

RealFrac CFloat Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.RealFrac

RealFrac CDouble Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.RealFrac

RealFrac Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.RealFrac

(Integral a, FromIntegral a Int64) => RealFrac (Ratio a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Ratio

div' :: (RealFrac a, FromIntegral Int64 b, Integral b) => Exp a -> Exp a -> Exp b Source #

Generalisation of div to any instance of RealFrac

mod' :: (Floating a, RealFrac a, ToFloating Int64 a) => Exp a -> Exp a -> Exp a Source #

Generalisation of mod to any instance of RealFrac

divMod' :: (Floating a, RealFrac a, Integral b, FromIntegral Int64 b, ToFloating b a) => Exp a -> Exp a -> (Exp b, Exp a) Source #

Generalisation of divMod to any instance of RealFrac

class (RealFrac a, Floating a) => RealFloat a where Source #

Efficient, machine-independent access to the components of a floating-point number

Methods

floatRadix :: Exp a -> Exp Int64 Source #

The radix of the representation (often 2) (constant)

default floatRadix :: RealFloat a => Exp a -> Exp Int64 Source #

floatDigits :: Exp a -> Exp Int Source #

The number of digits of floatRadix in the significand (constant)

default floatDigits :: RealFloat a => Exp a -> Exp Int Source #

floatRange :: Exp a -> (Exp Int, Exp Int) Source #

The lowest and highest values the exponent may assume (constant)

default floatRange :: RealFloat a => Exp a -> (Exp Int, Exp Int) Source #

decodeFloat :: Exp a -> (Exp Int64, Exp Int) Source #

Return the significand and an appropriately scaled exponent. If (m,n) = decodeFloat x then x = m*b^^n, where b is the floating-point radix (floatRadix). Furthermore, either m and n are both zero, or b^(d-1) <= abs m < b^d, where d = floatDigits x.

encodeFloat :: Exp Int64 -> Exp Int -> Exp a Source #

Inverse of decodeFloat

exponent :: Exp a -> Exp Int Source #

Corresponds to the second component of decodeFloat

significand :: Exp a -> Exp a Source #

Corresponds to the first component of decodeFloat

scaleFloat :: Exp Int -> Exp a -> Exp a Source #

Multiply a floating point number by an integer power of the radix

isNaN :: Exp a -> Exp Bool Source #

True if the argument is an IEEE "not-a-number" (NaN) value

isInfinite :: Exp a -> Exp Bool Source #

True if the argument is an IEEE infinity or negative-infinity

isDenormalized :: Exp a -> Exp Bool Source #

True if the argument is too small to be represented in normalized format

isNegativeZero :: Exp a -> Exp Bool Source #

True if the argument is an IEEE negative zero

isIEEE :: Exp a -> Exp Bool Source #

True if the argument is an IEEE floating point number

default isIEEE :: RealFloat a => Exp a -> Exp Bool Source #

atan2 :: Exp a -> Exp a -> Exp a Source #

A version of arctangent taking two real floating-point arguments. For real floating x and y, atan2 y x computes the angle (from the positive x-axis) of the vector from the origin to the point (x,y). atan2 y x returns a value in the range [-pi, pi].

Instances

Instances details
RealFloat Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.RealFloat

RealFloat Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.RealFloat

RealFloat CFloat Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.RealFloat

RealFloat CDouble Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.RealFloat

RealFloat Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.RealFloat

Numeric conversion classes

class FromIntegral a b where Source #

Accelerate lacks a most-general lossless Integer type, which the standard fromIntegral function uses as an intermediate value when coercing from integral types. Instead, we use this class to capture a direct coercion between two types.

Methods

fromIntegral :: Integral a => Exp a -> Exp b Source #

General coercion from integral types

Instances

Instances details
FromIntegral Int Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

(FromIntegral a b, Integral b) => FromIntegral a (Ratio b) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Ratio

Methods

fromIntegral :: Exp a -> Exp (Ratio b) Source #

(FromIntegral a b, Num b, Elt (Complex b)) => FromIntegral a (Complex b) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Complex

Methods

fromIntegral :: Exp a -> Exp (Complex b) Source #

class ToFloating a b where Source #

Accelerate lacks an arbitrary-precision Rational type, which the standard realToFrac uses as an intermediate value when coercing to floating-point types. Instead, we use this class to capture a direct coercion between two types.

Methods

toFloating :: (Num a, Floating b) => Exp a -> Exp b Source #

General coercion to floating types

Instances

Instances details
ToFloating Double Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Double Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Double Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Float Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Float Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Float Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int8 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int8 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int8 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int16 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int16 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int16 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int32 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int32 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int32 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int64 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int64 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int64 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word8 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word8 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word8 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word16 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word16 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word16 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word32 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word32 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word32 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word64 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word64 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word64 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Half Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Half Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Half Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

(Integral a, ToFloating a b) => ToFloating (Ratio a) b Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Ratio

Methods

toFloating :: Exp (Ratio a) -> Exp b Source #

Lifting and Unlifting

A value of type Int is a plain Haskell value (unlifted), whereas an Exp Int is a lifted value, that is, an integer lifted into the domain of embedded expressions (an abstract syntax tree in disguise). Both Acc and Exp are surface types into which values may be lifted. Lifting plain array and scalar surface types is equivalent to use and constant respectively.

In general an Exp Int cannot be unlifted into an Int, because the actual number will not be available until a later stage of execution (e.g. during GPU execution, when run is called). Similarly an Acc array can not be unlifted to a vanilla array; you should instead run the expression with a specific backend to evaluate it.

Lifting and unlifting are also used to pack and unpack an expression into and out of constructors such as tuples, respectively. Those expressions, at runtime, will become tuple dereferences. For example:

>>> let sh = constant (Z :. 4 :. 10)   :: Exp DIM2
>>> let Z :. x :. y = unlift sh        :: Z :. Exp Int :. Exp Int
>>> let t = lift (x,y)                 :: Exp (Int, Int)
>>> let xs = use $ fromList (Z:.10) [0..]   :: Acc (Vector Int)
>>> let ys = use $ fromList (Z:.3:.4) [0..] :: Acc (Matrix Int)
>>> let r  = (xs,ys)                        :: (Acc (Vector Int), Acc (Matrix Int))
>>> let r' = lift r                         :: Acc (Vector Int, Matrix Int)
Note:

Use of lift and unlift is probably the most common source of type errors when using Accelerate. GHC is not very good at determining the type the [un]lifted expression should have, so it is often necessary to add an explicit type signature.

For example, in the following GHC will complain that it can not determine the type of y, even though we might expect that to be obvious (or for it to not care):

fst :: (Elt a, Elt b) => Exp (a,b) -> Exp a
fst t = let (x,y) = unlift t in x

The fix is to instead add an explicit type signature. Note that this requires the ScopedTypeVariables extension and to bring the type variables a and b into scope with forall:

fst :: forall a b. (Elt a, Elt b) => Exp (a,b) -> Exp a
fst t = let (x,y) = unlift t  :: (Exp a, Exp b)
        in x

For an alternative, see section Pattern synonyms.

class Lift c e where Source #

The class of types e which can be lifted into c.

Associated Types

type Plain e Source #

An associated-type (i.e. a type-level function) that strips all instances of surface type constructors c from the input type e.

For example, the tuple types (Exp Int, Int) and (Int, Exp Int) have the same "Plain" representation. That is, the following type equality holds:

Plain (Exp Int, Int) ~ (Int,Int) ~ Plain (Int, Exp Int)

Methods

lift :: e -> c (Plain e) Source #

Lift the given value into a surface type c --- either Exp for scalar expressions or Acc for array computations. The value may already contain subexpressions in c.

Instances

Instances details
Lift Exp Bool Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Bool Source #

Methods

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

Lift Exp Char Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Char Source #

Methods

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

Lift Exp Double Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Double Source #

Methods

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

Lift Exp Float Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Float Source #

Methods

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

Lift Exp Int Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Int Source #

Methods

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

Lift Exp Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Int8 Source #

Methods

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

Lift Exp Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Int16 Source #

Methods

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

Lift Exp Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Int32 Source #

Methods

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

Lift Exp Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Int64 Source #

Methods

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

Lift Exp Word Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Word Source #

Methods

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

Lift Exp Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Word8 Source #

Methods

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

Lift Exp Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Word16 Source #

Methods

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

Lift Exp Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Word32 Source #

Methods

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

Lift Exp Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Word64 Source #

Methods

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

Lift Exp () Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain () Source #

Methods

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

Lift Exp CChar Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CChar Source #

Methods

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

Lift Exp CSChar Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CSChar Source #

Methods

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

Lift Exp CUChar Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CUChar Source #

Methods

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

Lift Exp CShort Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CShort Source #

Methods

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

Lift Exp CUShort Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CUShort Source #

Lift Exp CInt Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CInt Source #

Methods

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

Lift Exp CUInt Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CUInt Source #

Methods

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

Lift Exp CLong Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CLong Source #

Methods

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

Lift Exp CULong Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CULong Source #

Methods

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

Lift Exp CLLong Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CLLong Source #

Methods

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

Lift Exp CULLong Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CULLong Source #

Lift Exp CFloat Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CFloat Source #

Methods

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

Lift Exp CDouble Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CDouble Source #

Lift Exp Half Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Half Source #

Methods

lift :: Half -> Exp (Plain Half) 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 #

Lift Acc () Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain () Source #

Methods

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

(Lift Exp a, Elt (Plain a)) => Lift Exp (Maybe a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Maybe

Associated Types

type Plain (Maybe a) Source #

Methods

lift :: Maybe a -> Exp (Plain (Maybe a)) Source #

(Lift Exp a, Elt (Plain a)) => Lift Exp (Complex a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Complex

Associated Types

type Plain (Complex a) Source #

Methods

lift :: Complex a -> Exp (Plain (Complex a)) Source #

(Lift Exp a, Elt (Plain a)) => Lift Exp (Min a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Semigroup

Associated Types

type Plain (Min a) Source #

Methods

lift :: Min a -> Exp (Plain (Min a)) Source #

(Lift Exp a, Elt (Plain a)) => Lift Exp (Max a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Semigroup

Associated Types

type Plain (Max a) Source #

Methods

lift :: Max a -> Exp (Plain (Max a)) Source #

(Lift Exp a, Elt (Plain a)) => Lift Exp (Sum a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Monoid

Associated Types

type Plain (Sum a) Source #

Methods

lift :: Sum a -> Exp (Plain (Sum a)) Source #

(Lift Exp a, Elt (Plain a)) => Lift Exp (Product a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Monoid

Associated Types

type Plain (Product a) Source #

Methods

lift :: Product a -> Exp (Plain (Product a)) Source #

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

Lift Exp (Exp e) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (Exp e) Source #

Methods

lift :: Exp e -> Exp (Plain (Exp e)) 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 #

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

Defined in Data.Array.Accelerate.Data.Either

Associated Types

type Plain (Either a b) Source #

Methods

lift :: Either a b -> Exp (Plain (Either a b)) Source #

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

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain (x0, x1) Source #

Methods

lift :: (x0, x1) -> Exp (Plain (x0, x1)) 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 #

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

((Lift Exp x0, Lift Exp x1, Lift Exp x2), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2))) => Lift Exp (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) -> Exp (Plain (x0, x1, 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 #

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, 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 #

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, 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 #

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4, Lift Exp x5), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4), Elt (Plain x5))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4, 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 #

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4, Lift Exp x5, Lift Exp x6), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4), Elt (Plain x5), Elt (Plain x6))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4, x5, 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 #

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4, Lift Exp x5, Lift Exp x6, Lift Exp x7), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4), Elt (Plain x5), Elt (Plain x6), Elt (Plain x7))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4, x5, x6, 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 #

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4, Lift Exp x5, Lift Exp x6, Lift Exp x7, Lift Exp x8), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4), Elt (Plain x5), Elt (Plain x6), Elt (Plain x7), Elt (Plain x8))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4, x5, x6, x7, 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 #

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4, Lift Exp x5, Lift Exp x6, Lift Exp x7, Lift Exp x8, Lift Exp x9), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4), Elt (Plain x5), Elt (Plain x6), Elt (Plain x7), Elt (Plain x8), Elt (Plain x9))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, 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 #

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4, Lift Exp x5, Lift Exp x6, Lift Exp x7, Lift Exp x8, Lift Exp x9, Lift Exp x10), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4), Elt (Plain x5), Elt (Plain x6), Elt (Plain x7), Elt (Plain x8), Elt (Plain x9), Elt (Plain x10))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, 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 #

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4, Lift Exp x5, Lift Exp x6, Lift Exp x7, Lift Exp x8, Lift Exp x9, Lift Exp x10, Lift Exp x11), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4), Elt (Plain x5), Elt (Plain x6), Elt (Plain x7), Elt (Plain x8), Elt (Plain x9), Elt (Plain x10), Elt (Plain x11))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, 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 #

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4, Lift Exp x5, Lift Exp x6, Lift Exp x7, Lift Exp x8, Lift Exp x9, Lift Exp x10, Lift Exp x11, Lift Exp x12), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4), Elt (Plain x5), Elt (Plain x6), Elt (Plain x7), Elt (Plain x8), Elt (Plain x9), Elt (Plain x10), Elt (Plain x11), Elt (Plain x12))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, 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 #

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4, Lift Exp x5, Lift Exp x6, Lift Exp x7, Lift Exp x8, Lift Exp x9, Lift Exp x10, Lift Exp x11, Lift Exp x12, Lift Exp x13), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4), Elt (Plain x5), Elt (Plain x6), Elt (Plain x7), Elt (Plain x8), Elt (Plain x9), Elt (Plain x10), Elt (Plain x11), Elt (Plain x12), Elt (Plain x13))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, 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 #

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4, Lift Exp x5, Lift Exp x6, Lift Exp x7, Lift Exp x8, Lift Exp x9, Lift Exp x10, Lift Exp x11, Lift Exp x12, Lift Exp x13, Lift Exp x14), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4), Elt (Plain x5), Elt (Plain x6), Elt (Plain x7), Elt (Plain x8), Elt (Plain x9), Elt (Plain x10), Elt (Plain x11), Elt (Plain x12), Elt (Plain x13), Elt (Plain x14))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, 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 #

((Lift Exp x0, Lift Exp x1, Lift Exp x2, Lift Exp x3, Lift Exp x4, Lift Exp x5, Lift Exp x6, Lift Exp x7, Lift Exp x8, Lift Exp x9, Lift Exp x10, Lift Exp x11, Lift Exp x12, Lift Exp x13, Lift Exp x14, Lift Exp x15), (Elt (Plain x0), Elt (Plain x1), Elt (Plain x2), Elt (Plain x3), Elt (Plain x4), Elt (Plain x5), Elt (Plain x6), Elt (Plain x7), Elt (Plain x8), Elt (Plain x9), Elt (Plain x10), Elt (Plain x11), Elt (Plain x12), Elt (Plain x13), Elt (Plain x14), Elt (Plain x15))) => Lift Exp (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) -> Exp (Plain (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, 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 #

class Lift c e => Unlift c e where Source #

A limited subset of types which can be lifted, can also be unlifted.

Methods

unlift :: c (Plain e) -> e Source #

Unlift the outermost constructor through the surface type. This is only possible if the constructor is fully determined by its type - i.e., it is a singleton.

Instances

Instances details
Unlift Exp () Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

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

Unlift Exp Z Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

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

Unlift Acc () Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

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

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

Defined in Data.Array.Accelerate.Data.Complex

Methods

unlift :: Exp (Plain (Complex (Exp a))) -> Complex (Exp a) Source #

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

Defined in Data.Array.Accelerate.Data.Semigroup

Methods

unlift :: Exp (Plain (Min (Exp a))) -> Min (Exp a) Source #

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

Defined in Data.Array.Accelerate.Data.Semigroup

Methods

unlift :: Exp (Plain (Max (Exp a))) -> Max (Exp a) Source #

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

Defined in Data.Array.Accelerate.Data.Monoid

Methods

unlift :: Exp (Plain (Sum (Exp a))) -> Sum (Exp a) Source #

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

Defined in Data.Array.Accelerate.Data.Monoid

Methods

unlift :: Exp (Plain (Product (Exp a))) -> Product (Exp a) Source #

Unlift Exp (Exp e) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

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

Unlift Acc (Acc a) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

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

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

Defined in Data.Array.Accelerate.Lift

Methods

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

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

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

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

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Exp (Plain (Exp x0, Exp x1, Exp x2)) -> (Exp x0, Exp x1, Exp x2) 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 #

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

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Exp (Plain (Exp x0, Exp x1, Exp x2, Exp x3)) -> (Exp x0, Exp x1, Exp x2, Exp x3) 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 #

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

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Exp (Plain (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4)) -> (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4) 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 #

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

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Exp (Plain (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5)) -> (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5) 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 #

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

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Exp (Plain (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6)) -> (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6) 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 #

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

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Exp (Plain (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7)) -> (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7) 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 #

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

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Exp (Plain (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8)) -> (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8) 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 #

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

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Exp (Plain (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9)) -> (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9) 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 #

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

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Exp (Plain (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10)) -> (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10) 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 #

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

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Exp (Plain (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11)) -> (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp 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) => 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 #

(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) => Unlift Exp (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11, Exp x12) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Exp (Plain (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11, Exp x12)) -> (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11, Exp 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) => 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 #

(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) => Unlift Exp (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11, Exp x12, Exp x13) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Exp (Plain (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11, Exp x12, Exp x13)) -> (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11, Exp x12, Exp 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) => 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 #

(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) => Unlift Exp (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11, Exp x12, Exp x13, Exp x14) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Exp (Plain (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11, Exp x12, Exp x13, Exp x14)) -> (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11, Exp x12, Exp x13, Exp 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) => 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 #

(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) => Unlift Exp (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11, Exp x12, Exp x13, Exp x14, Exp x15) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Methods

unlift :: Exp (Plain (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11, Exp x12, Exp x13, Exp x14, Exp x15)) -> (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11, Exp x12, Exp x13, Exp x14, Exp x15) 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 #

lift1 :: (Unlift Exp a, Lift Exp b) => (a -> b) -> Exp (Plain a) -> Exp (Plain b) Source #

Lift a unary function into Exp.

lift2 :: (Unlift Exp a, Unlift Exp b, Lift Exp c) => (a -> b -> c) -> Exp (Plain a) -> Exp (Plain b) -> Exp (Plain c) Source #

Lift a binary function into Exp.

lift3 :: (Unlift Exp a, Unlift Exp b, Unlift Exp c, Lift Exp d) => (a -> b -> c -> d) -> Exp (Plain a) -> Exp (Plain b) -> Exp (Plain c) -> Exp (Plain d) Source #

Lift a ternary function into Exp.

ilift1 :: (Exp Int -> Exp Int) -> Exp DIM1 -> Exp DIM1 Source #

Lift a unary function to a computation over rank-1 indices.

ilift2 :: (Exp Int -> Exp Int -> Exp Int) -> Exp DIM1 -> Exp DIM1 -> Exp DIM1 Source #

Lift a binary function to a computation over rank-1 indices.

ilift3 :: (Exp Int -> Exp Int -> Exp Int -> Exp Int) -> Exp DIM1 -> Exp DIM1 -> Exp DIM1 -> Exp DIM1 Source #

Lift a ternary function to a computation over rank-1 indices.

Pattern synonyms

Pattern synonyms can be used as an alternative to lift and unlift for constructing and accessing data types isomorphic to simple product (tuple) types.

In contrast to lift and unlift however, pattern synonyms do not require these data types to be fully polymorphic.

For example, let's say we have regular Haskell data type representing a point in two-dimensional space:

data Point = Point_ Float Float
  deriving (Generic, Elt)

Here we derive instance an instance of the Elt class (via Generic), so that this data type can be used within scalar Accelerate expressions

In order to access the individual fields of the data constructor from within an Accelerate expression, we define the following pattern synonym:

pattern Point :: Exp Float -> Exp Float -> Exp Point
pattern Point x y = Pattern (x,y)

Notice how we named the constructor of our original datatype with a trailing underscore, so that we can use the undecorated name for the pattern synonym; these must have unique names.

In essence, the Pattern pattern is really telling GHC how to treat our Point type as a regular pair for use in Accelerate code. The pattern can then be used on both the left and right hand side of an expression:

addPoint :: Exp Point -> Exp Point -> Exp Point
addPoint (Point x1 y1) (Point x2 y2) = Point (x1+x2) (y1+y2)

Similarly, we can define pattern synonyms for values in Acc. We can also use record syntax to generate field accessors, if we desire:

data SparseVector a = SparseVector_ (Vector Int) (Vector a)
  deriving (Generic, Arrays)

pattern SparseVector :: Elt a => Acc (Vector Int) -> Acc (Vector a) -> Acc (SparseVector a)
pattern SparseVector { indices, values } = Pattern (indices, values)

For convenience, we have defined several pattern synonyms for regular tuples, T2 (for pairs), T3 (for triples), and so on up to T16. These are occasionally more convenient to use than lift and unlift together with the regular tuple syntax.

Since: 1.3.0.0

pattern Pattern :: forall b a context. IsPattern context a b => b -> context a Source #

A pattern synonym for working with (product) data types. You can declare your own pattern synonyms based off of this.

pattern T2 :: IsPattern con (x0, x1) (con x0, con x1) => con x0 -> con x1 -> con (x0, x1) Source #

pattern T3 :: IsPattern con (x0, x1, x2) (con x0, con x1, con x2) => con x0 -> con x1 -> con x2 -> con (x0, x1, x2) Source #

pattern T4 :: IsPattern con (x0, x1, x2, x3) (con x0, con x1, con x2, con x3) => con x0 -> con x1 -> con x2 -> con x3 -> con (x0, x1, x2, x3) Source #

pattern T5 :: IsPattern con (x0, x1, x2, x3, x4) (con x0, con x1, con x2, con x3, con x4) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con (x0, x1, x2, x3, x4) Source #

pattern T6 :: IsPattern con (x0, x1, x2, x3, x4, x5) (con x0, con x1, con x2, con x3, con x4, con x5) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con (x0, x1, x2, x3, x4, x5) Source #

pattern T7 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6) (con x0, con x1, con x2, con x3, con x4, con x5, con x6) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con (x0, x1, x2, x3, x4, x5, x6) Source #

pattern T8 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con (x0, x1, x2, x3, x4, x5, x6, x7) Source #

pattern T9 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8) Source #

pattern T10 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) Source #

pattern T11 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9, con x10) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con x10 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) Source #

pattern T12 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9, con x10, con x11) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con x10 -> con x11 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) Source #

pattern T13 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9, con x10, con x11, con x12) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con x10 -> con x11 -> con x12 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) Source #

pattern T14 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9, con x10, con x11, con x12, con x13) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con x10 -> con x11 -> con x12 -> con x13 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) Source #

pattern T15 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9, con x10, con x11, con x12, con x13, con x14) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con x10 -> con x11 -> con x12 -> con x13 -> con x14 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) Source #

pattern T16 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9, con x10, con x11, con x12, con x13, con x14, con x15) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con x10 -> con x11 -> con x12 -> con x13 -> con x14 -> con x15 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) Source #

pattern Z_ :: Exp DIM0 Source #

Pattern synonyms for indices, which may be more convenient to use than lift and unlift.

pattern Ix :: (Elt a, Elt b) => Exp a -> Exp b -> Exp (a :. b) infixl 3 Source #

pattern (::.) :: (Elt a, Elt b) => Exp a -> Exp b -> Exp (a :. b) infixl 3 Source #

pattern I0 :: () => Exp Z Source #

pattern I1 :: Elt x0 => Exp x0 -> Exp ((:.) Z x0) Source #

pattern I2 :: (Elt x0, Elt x1) => Exp x0 -> Exp x1 -> Exp ((:.) ((:.) Z x0) x1) Source #

pattern I3 :: (Elt x0, Elt x1, Elt x2) => Exp x0 -> Exp x1 -> Exp x2 -> Exp ((:.) ((:.) ((:.) Z x0) x1) x2) Source #

pattern I4 :: (Elt x0, Elt x1, Elt x2, Elt x3) => Exp x0 -> Exp x1 -> Exp x2 -> Exp x3 -> Exp ((:.) ((:.) ((:.) ((:.) Z x0) x1) x2) x3) Source #

pattern I5 :: (Elt x0, Elt x1, Elt x2, Elt x3, Elt x4) => Exp x0 -> Exp x1 -> Exp x2 -> Exp x3 -> Exp x4 -> Exp ((:.) ((:.) ((:.) ((:.) ((:.) Z x0) x1) x2) x3) x4) Source #

pattern I6 :: (Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5) => Exp x0 -> Exp x1 -> Exp x2 -> Exp x3 -> Exp x4 -> Exp x5 -> Exp ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) Z x0) x1) x2) x3) x4) x5) Source #

pattern I7 :: (Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6) => Exp x0 -> Exp x1 -> Exp x2 -> Exp x3 -> Exp x4 -> Exp x5 -> Exp x6 -> Exp ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) Z x0) x1) x2) x3) x4) x5) x6) Source #

pattern I8 :: (Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7) => Exp x0 -> Exp x1 -> Exp x2 -> Exp x3 -> Exp x4 -> Exp x5 -> Exp x6 -> Exp x7 -> Exp ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) Z x0) x1) x2) x3) x4) x5) x6) x7) Source #

pattern I9 :: (Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8) => Exp x0 -> Exp x1 -> Exp x2 -> Exp x3 -> Exp x4 -> Exp x5 -> Exp x6 -> Exp x7 -> Exp x8 -> Exp ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) Z x0) x1) x2) x3) x4) x5) x6) x7) x8) Source #

pattern Vec2 :: Prim a => a -> a -> Vec2 a Source #

pattern V2 :: IsVector con vec (con x0, con x1) => con x0 -> con x1 -> con vec Source #

pattern Vec3 :: Prim a => a -> a -> a -> Vec3 a Source #

pattern V3 :: IsVector con vec (con x0, con x1, con x2) => con x0 -> con x1 -> con x2 -> con vec Source #

pattern Vec4 :: Prim a => a -> a -> a -> a -> Vec4 a Source #

pattern V4 :: IsVector con vec (con x0, con x1, con x2, con x3) => con x0 -> con x1 -> con x2 -> con x3 -> con vec Source #

pattern Vec8 :: Prim a => a -> a -> a -> a -> a -> a -> a -> a -> Vec8 a Source #

pattern V8 :: IsVector con vec (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con vec Source #

pattern Vec16 :: Prim a => a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> Vec16 a Source #

pattern V16 :: IsVector con vec (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9, con x10, con x11, con x12, con x13, con x14, con x15) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con x10 -> con x11 -> con x12 -> con x13 -> con x14 -> con x15 -> con vec Source #

Specialised pattern synonyms for tuples, which may be more convenient to use than lift and unlift. For example, to construct a pair:

let a = 4        :: Exp Int
let b = 2        :: Exp Float
let c = T2 a b   -- :: Exp (Int, Float); equivalent to 'lift (a,b)'

Similarly they can be used to destruct values:

let T2 x y = c   -- x :: Exp Int, y :: Exp Float; equivalent to 'let (x,y) = unlift c'

These pattern synonyms can be used for both Exp and Acc terms.

Similarly, we have patterns for constructing and destructing indices of a given dimensionality:

let ix = Ix 2 3    -- :: Exp DIM2
let I2 y x = ix    -- y :: Exp Int, x :: Exp Int

mkPattern :: Name -> DecsQ Source #

Generate pattern synonyms for the given simple (Haskell'98) sum or product data type.

Constructor and record selectors are renamed to add a trailing underscore if it does not exist, or to remove it if it does. For infix constructors, the name is prepended with a colon :. For example:

data Point = Point { xcoord_ :: Float, ycoord_ :: Float }
  deriving (Generic, Elt)

Will create the pattern synonym:

Point_ :: Exp Float -> Exp Float -> Exp Point

together with the selector functions

xcoord :: Exp Point -> Exp Float
ycoord :: Exp Point -> Exp Float

mkPatterns :: [Name] -> DecsQ Source #

As mkPattern, but for a list of types

Scalar operations

Introduction

constant :: forall e. (HasCallStack, Elt e) => e -> Exp e Source #

Scalar expression inlet: make a Haskell value available for processing in an Accelerate scalar expression.

Note that this embeds the value directly into the expression. Depending on the backend used to execute the computation, this might not always be desirable. For example, a backend that does external code generation may embed this constant directly into the generated code, which means new code will need to be generated and compiled every time the value changes. In such cases, consider instead lifting scalar values into (singleton) arrays so that they can be passed as an input to the computation and thus the value can change without the need to generate fresh code.

Tuples

fst :: (Elt a, Elt b) => Exp (a, b) -> Exp a Source #

Extract the first component of a scalar pair.

afst :: (Arrays a, Arrays b) => Acc (a, b) -> Acc a Source #

Extract the first component of an array pair.

snd :: (Elt a, Elt b) => Exp (a, b) -> Exp b Source #

Extract the second component of a scalar pair.

asnd :: (Arrays a, Arrays b) => Acc (a, b) -> Acc b Source #

Extract the second component of an array pair

curry :: Lift f (f a, f b) => (f (Plain (f a), Plain (f b)) -> f c) -> f a -> f b -> f c Source #

Converts an uncurried function to a curried function.

uncurry :: Unlift f (f a, f b) => (f a -> f b -> f c) -> f (Plain (f a), Plain (f b)) -> f c Source #

Converts a curried function to a function on pairs.

Flow control

(?) :: Elt t => Exp Bool -> (Exp t, Exp t) -> Exp t infix 0 Source #

An infix version of cond. 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.

match :: Matching f => f -> f Source #

The match operation is the core operation which enables embedded pattern matching. It is applied to an n-ary scalar function, and generates the necessary case-statements in the embedded code for each argument. For example, given the function:

example1 :: Exp (Maybe Bool) -> Exp Int
example1 Nothing_ = 0
example1 (Just_ False_) = 1
example1 (Just_ True_) = 2

In order to use this function it must be applied to the match operator:

match example1

Using the infix-flip operator (&), we can also write case statements inline. For example, instead of this:

example2 x = case f x of
  Nothing_ -> ...      -- error: embedded pattern synonym...
  Just_ y  -> ...      -- ...used outside of 'match' context

This can be written instead as:

example3 x = f x & match \case
  Nothing_ -> ...
  Just_ y  -> ...

And utilising the LambdaCase and BlockArguments syntactic extensions.

The Template Haskell splice mkPattern (or mkPatterns) can be used to generate the pattern synonyms for a given Haskell'98 sum or product data type. For example:

data Option a = None | Some a
  deriving (Generic, Elt)

mkPattern ''Option

Which can then be used such as:

isNone :: Elt a => Exp (Option a) -> Exp Bool
isNone = match \case
  None_   -> True_
  Some_{} -> False_

Since: 1.3.0.0

cond Source #

Arguments

:: Elt t 
=> Exp Bool

condition

-> Exp t

then-expression

-> Exp t

else-expression

-> Exp t 

A scalar-level if-then-else construct.

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

while Source #

Arguments

:: forall e. Elt e 
=> (Exp e -> Exp Bool)

keep evaluating while this returns True

-> (Exp e -> Exp e)

function to apply

-> Exp e

initial value

-> Exp e 

While construct. Continue to apply the given function, starting with the initial value, until the test function evaluates to False.

iterate :: Elt a => Exp Int -> (Exp a -> Exp a) -> Exp a -> Exp a Source #

Repeatedly apply a function a fixed number of times

Scalar reduction

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

Reduce along an innermost slice of an array sequentially, by applying a binary operator to a starting value and the array from left to right.

Logical operations

(&&) :: Exp Bool -> Exp Bool -> Exp Bool infixr 3 Source #

Conjunction: True if both arguments are true. This is a short-circuit operator, so the second argument will be evaluated only if the first is true.

(||) :: Exp Bool -> Exp Bool -> Exp Bool infixr 2 Source #

Disjunction: True if either argument is true. This is a short-circuit operator, so the second argument will be evaluated only if the first is false.

not :: Exp Bool -> Exp Bool Source #

Logical negation

Numeric operations

subtract :: Num a => Exp a -> Exp a -> Exp a Source #

subtract is the same as flip (-).

even :: Integral a => Exp a -> Exp Bool Source #

Determine if a number is even

odd :: Integral a => Exp a -> Exp Bool Source #

Determine if a number is odd

gcd :: Integral a => Exp a -> Exp a -> Exp a Source #

gcd x y is the non-negative factor of both x and y of which every common factor of both x and y is also a factor; for example:

gcd 4 2 = 2
gcd (-4) 6 = 2
gcd 0 4 = 4
gcd 0 0 = 0

That is, the common divisor that is "greatest" in the divisibility preordering.

lcm :: Integral a => Exp a -> Exp a -> Exp a Source #

lcm x y is the smallest positive integer that both x and y divide.

(^) :: forall a b. (Num a, Integral b) => Exp a -> Exp b -> Exp a infixr 8 Source #

Raise a number to a non-negative integral power

(^^) :: (Fractional a, Integral b) => Exp a -> Exp b -> Exp a infixr 8 Source #

Raise a number to an integral power

Shape manipulation

index0 :: Exp Z Source #

The one index for a rank-0 array.

index1 :: Elt i => Exp i -> Exp (Z :. i) Source #

Turn an Int expression into a rank-1 indexing expression.

unindex1 :: Elt i => Exp (Z :. i) -> Exp i Source #

Turn a rank-1 indexing expression into an Int expression.

index2 :: Elt i => Exp i -> Exp i -> Exp ((Z :. i) :. i) Source #

Creates a rank-2 index from two Exp Int`s

unindex2 :: Elt i => Exp ((Z :. i) :. i) -> Exp (i, i) Source #

Destructs a rank-2 index to an Exp tuple of two Int`s.

index3 :: Elt i => Exp i -> Exp i -> Exp i -> Exp (((Z :. i) :. i) :. i) Source #

Create a rank-3 index from three Exp Int`s

unindex3 :: Elt i => Exp (((Z :. i) :. i) :. i) -> Exp (i, i, i) Source #

Destruct a rank-3 index into an Exp tuple of Int`s

indexHead :: (Elt sh, Elt a) => Exp (sh :. a) -> Exp a Source #

Get the innermost dimension of a shape.

The innermost dimension (right-most component of the shape) is the index of the array which varies most rapidly, and corresponds to elements of the array which are adjacent in memory.

Another way to think of this is, for example when writing nested loops over an array in C, this index corresponds to the index iterated over by the innermost nested loop.

indexTail :: (Elt sh, Elt a) => Exp (sh :. a) -> Exp sh Source #

Get all but the innermost element of a shape

toIndex Source #

Arguments

:: forall sh. Shape sh 
=> Exp sh

extent of the array

-> Exp sh

index to remap

-> Exp Int 

Map a multi-dimensional index into a linear, row-major representation of an array.

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

Inverse of toIndex

intersect :: forall sh. Shape sh => Exp sh -> Exp sh -> Exp sh Source #

Intersection of two shapes

Conversions

ord :: Exp Char -> Exp Int Source #

Convert a character to an Int.

chr :: Exp Int -> Exp Char Source #

Convert an Int into a character.

boolToInt :: Exp Bool -> Exp Int Source #

Convert a Boolean value to an Int, where False turns into '0' and True into '1'.

bitcast :: (Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b), BitSizeEq (EltR a) (EltR b)) => Exp a -> Exp b Source #

Reinterpret a value as another type. The two representations must have the same bit size.

Foreign Function Interface (FFI)

foreignAcc :: forall as bs asm. (Arrays as, Arrays bs, Foreign asm) => asm (ArraysR as -> ArraysR bs) -> (Acc as -> Acc bs) -> Acc as -> Acc bs Source #

Call a foreign array function.

The form the first argument takes is dependent on the backend being targeted. Note that the foreign function only has access to the input array(s) passed in as its argument.

In case the operation is being executed on a backend which does not support this foreign implementation, the fallback implementation is used instead, which itself could be a foreign implementation for a (presumably) different backend, or an implementation in pure Accelerate. In this way, multiple foreign implementations can be supplied, and will be tested for suitability against the target backend in sequence.

For an example see the accelerate-fft package.

foreignExp :: forall x y asm. (Elt x, Elt y, Foreign asm) => asm (EltR x -> EltR y) -> (Exp x -> Exp y) -> Exp x -> Exp y Source #

Call a foreign scalar expression.

The form of the first argument is dependent on the backend being targeted. Note that the foreign function only has access to the input element(s) passed in as its first argument.

As with foreignAcc, the fallback implementation itself may be a (sequence of) foreign implementation(s) for a different backend(s), or implemented purely in Accelerate.

Plain arrays

Operations

arrayRank :: forall sh e. Shape sh => Array sh e -> Int Source #

Rank of an array (as a plain Haskell value)

arrayShape :: Shape sh => Array sh e -> sh Source #

Shape of an array (as a plain Haskell value)

arraySize :: Shape sh => Array sh e -> Int Source #

Total number of elements in an array (as a plain Haskell value)

arrayReshape :: (Shape sh, Shape sh') => sh -> Array sh' e -> Array sh e Source #

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

indexArray :: (Shape sh, Elt e) => Array sh e -> sh -> e Source #

Array indexing in plain Haskell code.

linearIndexArray :: Elt e => Array sh e -> Int -> e Source #

Linear array indexing in plain Haskell code.

Getting data in

We often need to generate or read data into an Array so that it can be used in Accelerate. The base accelerate library includes basic conversions routines, but for additional functionality see the accelerate-io package, which includes conversions between:

  • repa: another Haskell library for high-performance parallel arrays
  • vector: efficient boxed and unboxed one-dimensional arrays
  • array: immutable arrays
  • BMP: uncompressed BMP image files
  • bytestring compact, immutable binary data
  • As well as copying data directly from raw Ptrs

Function

fromFunction :: (Shape sh, Elt e) => sh -> (sh -> e) -> Array sh e Source #

Create an array from its representation function, applied at each index of the array

fromFunctionM :: forall sh e. (Shape sh, Elt e) => sh -> (sh -> IO e) -> IO (Array sh e) Source #

Create an array using a monadic function applied at each index

Since: 1.2.0.0

Lists

fromList :: forall sh e. (Shape sh, Elt e) => sh -> [e] -> Array sh e Source #

Convert elements of a list into an Accelerate Array

This will generate a new multidimensional Array of the specified shape and extent by consuming elements from the list and adding them to the array in row-major order.

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

Note that we pull elements off the list lazily, so infinite lists are accepted:

>>> fromList (Z:.5:.10) (repeat 0) :: Matrix Float
Matrix (Z :. 5 :. 10)
  [ 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0,
    0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0,
    0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0,
    0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0,
    0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0]

You can also make use of the OverloadedLists extension to produce one-dimensional vectors from a finite list.

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

Note that this requires first traversing the list to determine its length, and then traversing it a second time to collect the elements into the array, thus forcing the spine of the list to be manifest on the heap.

toList :: forall sh e. (Shape sh, Elt e) => Array sh e -> [e] Source #

Convert an accelerated Array to a list in row-major order

Useful re-exports

(.) :: (b -> c) -> (a -> b) -> a -> c infixr 9 #

Function composition.

($) :: forall (r :: RuntimeRep) a (b :: TYPE r). (a -> b) -> a -> b infixr 0 #

Application operator. This operator is redundant, since ordinary application (f x) means the same as (f $ x). However, $ has low, right-associative binding precedence, so it sometimes allows parentheses to be omitted; for example:

f $ g $ h x  =  f (g (h x))

It is also useful in higher-order situations, such as map ($ 0) xs, or zipWith ($) fs xs.

Note that ($) is levity-polymorphic in its result type, so that foo $ True where foo :: Bool -> Int# is well-typed.

(&) :: a -> (a -> b) -> b infixl 1 #

& is a reverse application operator. This provides notational convenience. Its precedence is one higher than that of the forward application operator $, which allows & to be nested in $.

>>> 5 & (+1) & show
"6"

Since: base-4.8.0.0

error :: forall (r :: RuntimeRep) (a :: TYPE r). HasCallStack => [Char] -> a #

error stops execution and displays an error message.

undefined :: forall (r :: RuntimeRep) (a :: TYPE r). HasCallStack => a #

A special case of error. It is expected that compilers will recognize this and insert error messages which are more appropriate to the context in which undefined appears.

const :: a -> b -> a #

const x is a unary function which evaluates to x for all inputs.

>>> const 42 "hello"
42
>>> map (const 42) [0..3]
[42,42,42,42]

otherwise :: Bool #

otherwise is defined as the value True. It helps to make guards more readable. eg.

 f x | x < 0     = ...
     | otherwise = ...

class Show a #

Conversion of values to readable Strings.

Derived instances of Show have the following properties, which are compatible with derived instances of Read:

  • The result of show is a syntactically correct Haskell expression containing only constants, given the fixity declarations in force at the point where the type is declared. It contains only the constructor names defined in the data type, parentheses, and spaces. When labelled constructor fields are used, braces, commas, field names, and equal signs are also used.
  • If the constructor is defined to be an infix operator, then showsPrec will produce infix applications of the constructor.
  • the representation will be enclosed in parentheses if the precedence of the top-level constructor in x is less than d (associativity is ignored). Thus, if d is 0 then the result is never surrounded in parentheses; if d is 11 it is always surrounded in parentheses, unless it is an atomic expression.
  • If the constructor is defined using record syntax, then show will produce the record-syntax form, with the fields given in the same order as the original declaration.

For example, given the declarations

infixr 5 :^:
data Tree a =  Leaf a  |  Tree a :^: Tree a

the derived instance of Show is equivalent to

instance (Show a) => Show (Tree a) where

       showsPrec d (Leaf m) = showParen (d > app_prec) $
            showString "Leaf " . showsPrec (app_prec+1) m
         where app_prec = 10

       showsPrec d (u :^: v) = showParen (d > up_prec) $
            showsPrec (up_prec+1) u .
            showString " :^: "      .
            showsPrec (up_prec+1) v
         where up_prec = 5

Note that right-associativity of :^: is ignored. For example,

  • show (Leaf 1 :^: Leaf 2 :^: Leaf 3) produces the string "Leaf 1 :^: (Leaf 2 :^: Leaf 3)".

Minimal complete definition

showsPrec | show

Instances

Instances details
Show Bool

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Bool -> ShowS #

show :: Bool -> String #

showList :: [Bool] -> ShowS #

Show Char

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Char -> ShowS #

show :: Char -> String #

showList :: [Char] -> ShowS #

Show Int

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Int -> ShowS #

show :: Int -> String #

showList :: [Int] -> ShowS #

Show Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int8 -> ShowS #

show :: Int8 -> String #

showList :: [Int8] -> ShowS #

Show Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int16 -> ShowS #

show :: Int16 -> String #

showList :: [Int16] -> ShowS #

Show Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int32 -> ShowS #

show :: Int32 -> String #

showList :: [Int32] -> ShowS #

Show Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int64 -> ShowS #

show :: Int64 -> String #

showList :: [Int64] -> ShowS #

Show Integer

Since: base-2.1

Instance details

Defined in GHC.Show

Show Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Show

Show Ordering

Since: base-2.1

Instance details

Defined in GHC.Show

Show Word

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Word -> ShowS #

show :: Word -> String #

showList :: [Word] -> ShowS #

Show Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Show Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Show RuntimeRep

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Show VecCount

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Show VecElem

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Show CallStack

Since: base-4.9.0.0

Instance details

Defined in GHC.Show

Show SomeTypeRep

Since: base-4.10.0.0

Instance details

Defined in Data.Typeable.Internal

Show Exp 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Exp -> ShowS #

show :: Exp -> String #

showList :: [Exp] -> ShowS #

Show Match 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Match -> ShowS #

show :: Match -> String #

showList :: [Match] -> ShowS #

Show Clause 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Pat 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Pat -> ShowS #

show :: Pat -> String #

showList :: [Pat] -> ShowS #

Show Type 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Show Dec 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Dec -> ShowS #

show :: Dec -> String #

showList :: [Dec] -> ShowS #

Show Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Show FunDep 
Instance details

Defined in Language.Haskell.TH.Syntax

Show InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Overlap 
Instance details

Defined in Language.Haskell.TH.Syntax

Show ()

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> () -> ShowS #

show :: () -> String #

showList :: [()] -> ShowS #

Show TyCon

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> TyCon -> ShowS #

show :: TyCon -> String #

showList :: [TyCon] -> ShowS #

Show Module

Since: base-4.9.0.0

Instance details

Defined in GHC.Show

Show TrName

Since: base-4.9.0.0

Instance details

Defined in GHC.Show

Show KindRep 
Instance details

Defined in GHC.Show

Show TypeLitSort

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Show Handle

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show ThreadId

Since: base-4.2.0.0

Instance details

Defined in GHC.Conc.Sync

Show Void

Since: base-4.8.0.0

Instance details

Defined in Data.Void

Methods

showsPrec :: Int -> Void -> ShowS #

show :: Void -> String #

showList :: [Void] -> ShowS #

Show Version

Since: base-2.1

Instance details

Defined in Data.Version

Show HandlePosn

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Handle

Show PatternMatchFail

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Show RecSelError

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Show RecConError

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Show RecUpdError

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Show NoMethodError

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Show TypeError

Since: base-4.9.0.0

Instance details

Defined in Control.Exception.Base

Show NonTermination

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Show NestedAtomically

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Show BlockReason

Since: base-4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Show ThreadStatus

Since: base-4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Show CDev 
Instance details

Defined in System.Posix.Types

Methods

showsPrec :: Int -> CDev -> ShowS #

show :: CDev -> String #

showList :: [CDev] -> ShowS #

Show CIno 
Instance details

Defined in System.Posix.Types

Methods

showsPrec :: Int -> CIno -> ShowS #

show :: CIno -> String #

showList :: [CIno] -> ShowS #

Show CMode 
Instance details

Defined in System.Posix.Types

Methods

showsPrec :: Int -> CMode -> ShowS #

show :: CMode -> String #

showList :: [CMode] -> ShowS #

Show COff 
Instance details

Defined in System.Posix.Types

Methods

showsPrec :: Int -> COff -> ShowS #

show :: COff -> String #

showList :: [COff] -> ShowS #

Show CPid 
Instance details

Defined in System.Posix.Types

Methods

showsPrec :: Int -> CPid -> ShowS #

show :: CPid -> String #

showList :: [CPid] -> ShowS #

Show CSsize 
Instance details

Defined in System.Posix.Types

Show CGid 
Instance details

Defined in System.Posix.Types

Methods

showsPrec :: Int -> CGid -> ShowS #

show :: CGid -> String #

showList :: [CGid] -> ShowS #

Show CNlink 
Instance details

Defined in System.Posix.Types

Show CUid 
Instance details

Defined in System.Posix.Types

Methods

showsPrec :: Int -> CUid -> ShowS #

show :: CUid -> String #

showList :: [CUid] -> ShowS #

Show CCc 
Instance details

Defined in System.Posix.Types

Methods

showsPrec :: Int -> CCc -> ShowS #

show :: CCc -> String #

showList :: [CCc] -> ShowS #

Show CSpeed 
Instance details

Defined in System.Posix.Types

Show CTcflag 
Instance details

Defined in System.Posix.Types

Show CRLim 
Instance details

Defined in System.Posix.Types

Methods

showsPrec :: Int -> CRLim -> ShowS #

show :: CRLim -> String #

showList :: [CRLim] -> ShowS #

Show CBlkSize 
Instance details

Defined in System.Posix.Types

Show CBlkCnt 
Instance details

Defined in System.Posix.Types

Show CClockId 
Instance details

Defined in System.Posix.Types

Show CFsBlkCnt 
Instance details

Defined in System.Posix.Types

Show CFsFilCnt 
Instance details

Defined in System.Posix.Types

Show CId 
Instance details

Defined in System.Posix.Types

Methods

showsPrec :: Int -> CId -> ShowS #

show :: CId -> String #

showList :: [CId] -> ShowS #

Show CKey 
Instance details

Defined in System.Posix.Types

Methods

showsPrec :: Int -> CKey -> ShowS #

show :: CKey -> String #

showList :: [CKey] -> ShowS #

Show CSocklen 
Instance details

Defined in System.Posix.Types

Show CNfds 
Instance details

Defined in System.Posix.Types

Methods

showsPrec :: Int -> CNfds -> ShowS #

show :: CNfds -> String #

showList :: [CNfds] -> ShowS #

Show Fd 
Instance details

Defined in System.Posix.Types

Methods

showsPrec :: Int -> Fd -> ShowS #

show :: Fd -> String #

showList :: [Fd] -> ShowS #

Show BlockedIndefinitelyOnMVar

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show BlockedIndefinitelyOnSTM

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show Deadlock

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show AllocationLimitExceeded

Since: base-4.7.1.0

Instance details

Defined in GHC.IO.Exception

Show CompactionFailed

Since: base-4.10.0.0

Instance details

Defined in GHC.IO.Exception

Show AssertionFailed

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show SomeAsyncException

Since: base-4.7.0.0

Instance details

Defined in GHC.IO.Exception

Show AsyncException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show ArrayException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show FixIOException

Since: base-4.11.0.0

Instance details

Defined in GHC.IO.Exception

Show ExitCode 
Instance details

Defined in GHC.IO.Exception

Show IOErrorType

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show HandleType

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show BufferMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show Newline

Since: base-4.3.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show NewlineMode

Since: base-4.3.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show SeekMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Device

Show TextEncoding

Since: base-4.3.0.0

Instance details

Defined in GHC.IO.Encoding.Types

Show CodingProgress

Since: base-4.4.0.0

Instance details

Defined in GHC.IO.Encoding.Types

Show MaskingState

Since: base-4.3.0.0

Instance details

Defined in GHC.IO

Show IOException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show ErrorCall

Since: base-4.0.0.0

Instance details

Defined in GHC.Exception

Show ArithException

Since: base-4.0.0.0

Instance details

Defined in GHC.Exception.Type

Show All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> All -> ShowS #

show :: All -> String #

showList :: [All] -> ShowS #

Show Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Any -> ShowS #

show :: Any -> String #

showList :: [Any] -> ShowS #

Show Fixity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Show Associativity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Show SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show SomeSymbol

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeLits

Show SomeNat

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeNats

Show CChar 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CChar -> ShowS #

show :: CChar -> String #

showList :: [CChar] -> ShowS #

Show CSChar 
Instance details

Defined in Foreign.C.Types

Show CUChar 
Instance details

Defined in Foreign.C.Types

Show CShort 
Instance details

Defined in Foreign.C.Types

Show CUShort 
Instance details

Defined in Foreign.C.Types

Show CInt 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CInt -> ShowS #

show :: CInt -> String #

showList :: [CInt] -> ShowS #

Show CUInt 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CUInt -> ShowS #

show :: CUInt -> String #

showList :: [CUInt] -> ShowS #

Show CLong 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CLong -> ShowS #

show :: CLong -> String #

showList :: [CLong] -> ShowS #

Show CULong 
Instance details

Defined in Foreign.C.Types

Show CLLong 
Instance details

Defined in Foreign.C.Types

Show CULLong 
Instance details

Defined in Foreign.C.Types

Show CBool 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CBool -> ShowS #

show :: CBool -> String #

showList :: [CBool] -> ShowS #

Show CFloat 
Instance details

Defined in Foreign.C.Types

Show CDouble 
Instance details

Defined in Foreign.C.Types

Show CPtrdiff 
Instance details

Defined in Foreign.C.Types

Show CSize 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CSize -> ShowS #

show :: CSize -> String #

showList :: [CSize] -> ShowS #

Show CWchar 
Instance details

Defined in Foreign.C.Types

Show CSigAtomic 
Instance details

Defined in Foreign.C.Types

Show CClock 
Instance details

Defined in Foreign.C.Types

Show CTime 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CTime -> ShowS #

show :: CTime -> String #

showList :: [CTime] -> ShowS #

Show CUSeconds 
Instance details

Defined in Foreign.C.Types

Show CSUSeconds 
Instance details

Defined in Foreign.C.Types

Show CIntPtr 
Instance details

Defined in Foreign.C.Types

Show CUIntPtr 
Instance details

Defined in Foreign.C.Types

Show CIntMax 
Instance details

Defined in Foreign.C.Types

Show CUIntMax 
Instance details

Defined in Foreign.C.Types

Show WordPtr 
Instance details

Defined in Foreign.Ptr

Show IntPtr 
Instance details

Defined in Foreign.Ptr

Show IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Show Fingerprint

Since: base-4.7.0.0

Instance details

Defined in GHC.Fingerprint.Type

Show GeneralCategory

Since: base-2.1

Instance details

Defined in GHC.Unicode

Show SrcLoc

Since: base-4.9.0.0

Instance details

Defined in GHC.Show

Show SomeException

Since: base-3.0

Instance details

Defined in GHC.Exception.Type

Show ASCII7_Invalid 
Instance details

Defined in Basement.String.Encoding.ASCII7

Methods

showsPrec :: Int -> ASCII7_Invalid -> ShowS #

show :: ASCII7_Invalid -> String #

showList :: [ASCII7_Invalid] -> ShowS #

Show ISO_8859_1_Invalid 
Instance details

Defined in Basement.String.Encoding.ISO_8859_1

Methods

showsPrec :: Int -> ISO_8859_1_Invalid -> ShowS #

show :: ISO_8859_1_Invalid -> String #

showList :: [ISO_8859_1_Invalid] -> ShowS #

Show UTF16_Invalid 
Instance details

Defined in Basement.String.Encoding.UTF16

Methods

showsPrec :: Int -> UTF16_Invalid -> ShowS #

show :: UTF16_Invalid -> String #

showList :: [UTF16_Invalid] -> ShowS #

Show UTF32_Invalid 
Instance details

Defined in Basement.String.Encoding.UTF32

Methods

showsPrec :: Int -> UTF32_Invalid -> ShowS #

show :: UTF32_Invalid -> String #

showList :: [UTF32_Invalid] -> ShowS #

Show Encoding 
Instance details

Defined in Basement.String

Show String 
Instance details

Defined in Basement.UTF8.Base

Show FileSize 
Instance details

Defined in Basement.Types.OffsetSize

Show ShortByteString 
Instance details

Defined in Data.ByteString.Short.Internal

Show ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Show ByteString 
Instance details

Defined in Data.ByteString.Internal

Show Clock 
Instance details

Defined in System.Clock

Methods

showsPrec :: Int -> Clock -> ShowS #

show :: Clock -> String #

showList :: [Clock] -> ShowS #

Show TimeSpec 
Instance details

Defined in System.Clock

Show IntSet 
Instance details

Defined in Data.IntSet.Internal

Show Blake2b_160 
Instance details

Defined in Crypto.Hash.Blake2b

Show Blake2b_224 
Instance details

Defined in Crypto.Hash.Blake2b

Show Blake2b_256 
Instance details

Defined in Crypto.Hash.Blake2b

Show Blake2b_384 
Instance details

Defined in Crypto.Hash.Blake2b

Show Blake2b_512 
Instance details

Defined in Crypto.Hash.Blake2b

Show Blake2bp_512 
Instance details

Defined in Crypto.Hash.Blake2bp

Show Blake2s_160 
Instance details

Defined in Crypto.Hash.Blake2s

Show Blake2s_224 
Instance details

Defined in Crypto.Hash.Blake2s

Show Blake2s_256 
Instance details

Defined in Crypto.Hash.Blake2s

Show Blake2sp_224 
Instance details

Defined in Crypto.Hash.Blake2sp

Show Blake2sp_256 
Instance details

Defined in Crypto.Hash.Blake2sp

Show Keccak_224 
Instance details

Defined in Crypto.Hash.Keccak

Show Keccak_256 
Instance details

Defined in Crypto.Hash.Keccak

Show Keccak_384 
Instance details

Defined in Crypto.Hash.Keccak

Show Keccak_512 
Instance details

Defined in Crypto.Hash.Keccak

Show MD2 
Instance details

Defined in Crypto.Hash.MD2

Methods

showsPrec :: Int -> MD2 -> ShowS #

show :: MD2 -> String #

showList :: [MD2] -> ShowS #

Show MD4 
Instance details

Defined in Crypto.Hash.MD4

Methods

showsPrec :: Int -> MD4 -> ShowS #

show :: MD4 -> String #

showList :: [MD4] -> ShowS #

Show MD5 
Instance details

Defined in Crypto.Hash.MD5

Methods

showsPrec :: Int -> MD5 -> ShowS #

show :: MD5 -> String #

showList :: [MD5] -> ShowS #

Show RIPEMD160 
Instance details

Defined in Crypto.Hash.RIPEMD160

Show SHA1 
Instance details

Defined in Crypto.Hash.SHA1

Methods

showsPrec :: Int -> SHA1 -> ShowS #

show :: SHA1 -> String #

showList :: [SHA1] -> ShowS #

Show SHA224 
Instance details

Defined in Crypto.Hash.SHA224

Show SHA256 
Instance details

Defined in Crypto.Hash.SHA256

Show SHA3_224 
Instance details

Defined in Crypto.Hash.SHA3

Show SHA3_256 
Instance details

Defined in Crypto.Hash.SHA3

Show SHA3_384 
Instance details

Defined in Crypto.Hash.SHA3

Show SHA3_512 
Instance details

Defined in Crypto.Hash.SHA3

Show SHA384 
Instance details

Defined in Crypto.Hash.SHA384

Show SHA512 
Instance details

Defined in Crypto.Hash.SHA512

Show SHA512t_224 
Instance details

Defined in Crypto.Hash.SHA512t

Show SHA512t_256 
Instance details

Defined in Crypto.Hash.SHA512t

Show Skein256_224 
Instance details

Defined in Crypto.Hash.Skein256

Show Skein256_256 
Instance details

Defined in Crypto.Hash.Skein256

Show Skein512_224 
Instance details

Defined in Crypto.Hash.Skein512

Show Skein512_256 
Instance details

Defined in Crypto.Hash.Skein512

Show Skein512_384 
Instance details

Defined in Crypto.Hash.Skein512

Show Skein512_512 
Instance details

Defined in Crypto.Hash.Skein512

Show Tiger 
Instance details

Defined in Crypto.Hash.Tiger

Methods

showsPrec :: Int -> Tiger -> ShowS #

show :: Tiger -> String #

showList :: [Tiger] -> ShowS #

Show Whirlpool 
Instance details

Defined in Crypto.Hash.Whirlpool

Show FileType 
Instance details

Defined in System.Directory.Internal.Common

Show Permissions 
Instance details

Defined in System.Directory.Internal.Common

Show XdgDirectory 
Instance details

Defined in System.Directory.Internal.Common

Show XdgDirectoryList 
Instance details

Defined in System.Directory.Internal.Common

Show Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

Show ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Show Half 
Instance details

Defined in Numeric.Half

Methods

showsPrec :: Int -> Half -> ShowS #

show :: Half -> String #

showList :: [Half] -> ShowS #

Show Name 
Instance details

Defined in Hedgehog.Internal.State

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Show Environment 
Instance details

Defined in Hedgehog.Internal.State

Show EnvironmentError 
Instance details

Defined in Hedgehog.Internal.State

Show PropertyName 
Instance details

Defined in Hedgehog.Internal.Property

Show Confidence 
Instance details

Defined in Hedgehog.Internal.Property

Show PropertyConfig 
Instance details

Defined in Hedgehog.Internal.Property

Show TestLimit 
Instance details

Defined in Hedgehog.Internal.Property

Show TestCount 
Instance details

Defined in Hedgehog.Internal.Property

Show DiscardCount 
Instance details

Defined in Hedgehog.Internal.Property

Show DiscardLimit 
Instance details

Defined in Hedgehog.Internal.Property

Show ShrinkLimit 
Instance details

Defined in Hedgehog.Internal.Property

Show ShrinkCount 
Instance details

Defined in Hedgehog.Internal.Property

Show ShrinkRetries 
Instance details

Defined in Hedgehog.Internal.Property

Show GroupName 
Instance details

Defined in Hedgehog.Internal.Property

Show PropertyCount 
Instance details

Defined in Hedgehog.Internal.Property

Show TerminationCriteria 
Instance details

Defined in Hedgehog.Internal.Property

Show Log 
Instance details

Defined in Hedgehog.Internal.Property

Methods

showsPrec :: Int -> Log -> ShowS #

show :: Log -> String #

showList :: [Log] -> ShowS #

Show Journal 
Instance details

Defined in Hedgehog.Internal.Property

Show Failure 
Instance details

Defined in Hedgehog.Internal.Property

Show Diff 
Instance details

Defined in Hedgehog.Internal.Property

Methods

showsPrec :: Int -> Diff -> ShowS #

show :: Diff -> String #

showList :: [Diff] -> ShowS #

Show Cover 
Instance details

Defined in Hedgehog.Internal.Property

Methods

showsPrec :: Int -> Cover -> ShowS #

show :: Cover -> String #

showList :: [Cover] -> ShowS #

Show CoverCount 
Instance details

Defined in Hedgehog.Internal.Property

Show CoverPercentage 
Instance details

Defined in Hedgehog.Internal.Property

Show LabelName 
Instance details

Defined in Hedgehog.Internal.Property

Show LineNo 
Instance details

Defined in Hedgehog.Internal.Source

Show ColumnNo 
Instance details

Defined in Hedgehog.Internal.Source

Show Span 
Instance details

Defined in Hedgehog.Internal.Source

Methods

showsPrec :: Int -> Span -> ShowS #

show :: Span -> String #

showList :: [Span] -> ShowS #

Show Seed 
Instance details

Defined in Hedgehog.Internal.Seed

Methods

showsPrec :: Int -> Seed -> ShowS #

show :: Seed -> String #

showList :: [Seed] -> ShowS #

Show Size 
Instance details

Defined in Hedgehog.Internal.Range

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

Show RuleBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Phases 
Instance details

Defined in Language.Haskell.TH.Syntax

Show RuleMatch 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Inline 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Pragma 
Instance details

Defined in Language.Haskell.TH.Syntax

Show DerivClause 
Instance details

Defined in Language.Haskell.TH.Syntax

Show DerivStrategy 
Instance details

Defined in Language.Haskell.TH.Syntax

Show TySynEqn 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Fixity 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Info 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Info -> ShowS #

show :: Info -> String #

showList :: [Info] -> ShowS #

Show Con 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Con -> ShowS #

show :: Con -> String #

showList :: [Con] -> ShowS #

Show TyVarBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Show DefName 
Instance details

Defined in Control.Lens.Internal.FieldTH

Show IsCmdStart 
Instance details

Defined in Options.Applicative.Types

Show Backtracking 
Instance details

Defined in Options.Applicative.Types

Show ParserPrefs 
Instance details

Defined in Options.Applicative.Types

Show OptName 
Instance details

Defined in Options.Applicative.Types

Show OptVisibility 
Instance details

Defined in Options.Applicative.Types

Show OptProperties 
Instance details

Defined in Options.Applicative.Types

Show CompletionResult 
Instance details

Defined in Options.Applicative.Types

Show ArgPolicy 
Instance details

Defined in Options.Applicative.Types

Show OptHelpInfo 
Instance details

Defined in Options.Applicative.Types

Show AltNodeType 
Instance details

Defined in Options.Applicative.Types

Show Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Methods

showsPrec :: Int -> Doc -> ShowS #

show :: Doc -> String #

showList :: [Doc] -> ShowS #

Show TextDetails 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Show Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

Show Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

Show FusionDepth 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Show PageWidth 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Show LayoutOptions 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Show Color 
Instance details

Defined in Prettyprinter.Render.Terminal.Internal

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Show Intensity 
Instance details

Defined in Prettyprinter.Render.Terminal.Internal

Show Bold 
Instance details

Defined in Prettyprinter.Render.Terminal.Internal

Methods

showsPrec :: Int -> Bold -> ShowS #

show :: Bold -> String #

showList :: [Bold] -> ShowS #

Show Underlined 
Instance details

Defined in Prettyprinter.Render.Terminal.Internal

Show Italicized 
Instance details

Defined in Prettyprinter.Render.Terminal.Internal

Show AnsiStyle 
Instance details

Defined in Prettyprinter.Render.Terminal.Internal

Show ByteArray

Since: primitive-0.6.3.0

Instance details

Defined in Data.Primitive.ByteArray

Show InvalidAccess 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Show ResourceCleanupException 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Show ResourceError 
Instance details

Defined in Test.Tasty.Core

Methods

showsPrec :: Int -> ResourceError -> ShowS #

show :: ResourceError -> String #

showList :: [ResourceError] -> ShowS #

Show FailureReason 
Instance details

Defined in Test.Tasty.Core

Show Outcome 
Instance details

Defined in Test.Tasty.Core

Show Result 
Instance details

Defined in Test.Tasty.Core

Show Progress 
Instance details

Defined in Test.Tasty.Core

Show DependencyType 
Instance details

Defined in Test.Tasty.Core

Show Timeout 
Instance details

Defined in Test.Tasty.Options.Core

Show ForallVisFlag 
Instance details

Defined in Language.Haskell.TH.Ppr

Show ModName 
Instance details

Defined in Language.Haskell.TH.Syntax

Show PkgName 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Module 
Instance details

Defined in Language.Haskell.TH.Syntax

Show OccName 
Instance details

Defined in Language.Haskell.TH.Syntax

Show NameFlavour 
Instance details

Defined in Language.Haskell.TH.Syntax

Show NameSpace 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Loc 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Loc -> ShowS #

show :: Loc -> String #

showList :: [Loc] -> ShowS #

Show ModuleInfo 
Instance details

Defined in Language.Haskell.TH.Syntax

Show FixityDirection 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Lit 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Lit -> ShowS #

show :: Lit -> String #

showList :: [Lit] -> ShowS #

Show Bytes 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Bytes -> ShowS #

show :: Bytes -> String #

showList :: [Bytes] -> ShowS #

Show Body 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Body -> ShowS #

show :: Body -> String #

showList :: [Body] -> ShowS #

Show Guard 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Guard -> ShowS #

show :: Guard -> String #

showList :: [Guard] -> ShowS #

Show Stmt 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Stmt -> ShowS #

show :: Stmt -> String #

showList :: [Stmt] -> ShowS #

Show Range 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Range -> ShowS #

show :: Range -> String #

showList :: [Range] -> ShowS #

Show TypeFamilyHead 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Foreign 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Callconv 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Safety 
Instance details

Defined in Language.Haskell.TH.Syntax

Show AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

Show SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Syntax

Show SourceStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Show DecidedStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Bang 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Bang -> ShowS #

show :: Bang -> String #

showList :: [Bang] -> ShowS #

Show PatSynDir 
Instance details

Defined in Language.Haskell.TH.Syntax

Show PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Syntax

Show FamilyResultSig 
Instance details

Defined in Language.Haskell.TH.Syntax

Show TyLit 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> TyLit -> ShowS #

show :: TyLit -> String #

showList :: [TyLit] -> ShowS #

Show Role 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Role -> ShowS #

show :: Role -> String #

showList :: [Role] -> ShowS #

Show AnnLookup 
Instance details

Defined in Language.Haskell.TH.Syntax

Show DatatypeInfo 
Instance details

Defined in Language.Haskell.TH.Datatype

Show DatatypeVariant 
Instance details

Defined in Language.Haskell.TH.Datatype

Show ConstructorInfo 
Instance details

Defined in Language.Haskell.TH.Datatype

Show ConstructorVariant 
Instance details

Defined in Language.Haskell.TH.Datatype

Show FieldStrictness 
Instance details

Defined in Language.Haskell.TH.Datatype

Show Unpackedness 
Instance details

Defined in Language.Haskell.TH.Datatype

Show Strictness 
Instance details

Defined in Language.Haskell.TH.Datatype

Show ZonedTime 
Instance details

Defined in Data.Time.LocalTime.Internal.ZonedTime

Show LocalTime 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

Show Layer 
Instance details

Defined in Prettyprinter.Render.Terminal.Internal

Methods

showsPrec :: Int -> Layer -> ShowS #

show :: Layer -> String #

showList :: [Layer] -> ShowS #

Show All Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Methods

showsPrec :: Int -> All -> ShowS #

show :: All -> String #

showList :: [All] -> ShowS #

Show Z Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

Methods

showsPrec :: Int -> Z -> ShowS #

show :: Z -> String #

showList :: [Z] -> ShowS #

Show Slot 
Instance details

Defined in Data.HashTable.ST.Basic

Methods

showsPrec :: Int -> Slot -> ShowS #

show :: Slot -> String #

showList :: [Slot] -> ShowS #

Show SlotFindResponse 
Instance details

Defined in Data.HashTable.ST.Basic

Methods

showsPrec :: Int -> SlotFindResponse -> ShowS #

show :: SlotFindResponse -> String #

showList :: [SlotFindResponse] -> ShowS #

Show a => Show [a]

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> [a] -> ShowS #

show :: [a] -> String #

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

Show a => Show (Maybe a)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Maybe a -> ShowS #

show :: Maybe a -> String #

showList :: [Maybe a] -> ShowS #

Show a => Show (Ratio a)

Since: base-2.0.1

Instance details

Defined in GHC.Real

Methods

showsPrec :: Int -> Ratio a -> ShowS #

show :: Ratio a -> String #

showList :: [Ratio a] -> ShowS #

Show (Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

showsPrec :: Int -> Ptr a -> ShowS #

show :: Ptr a -> String #

showList :: [Ptr a] -> ShowS #

Show (FunPtr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

showsPrec :: Int -> FunPtr a -> ShowS #

show :: FunPtr a -> String #

showList :: [FunPtr a] -> ShowS #

Show p => Show (Par1 p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> Par1 p -> ShowS #

show :: Par1 p -> String #

showList :: [Par1 p] -> ShowS #

Show (ForeignPtr a)

Since: base-2.1

Instance details

Defined in GHC.ForeignPtr

Show a => Show (Complex a)

Since: base-2.1

Instance details

Defined in Data.Complex

Methods

showsPrec :: Int -> Complex a -> ShowS #

show :: Complex a -> String #

showList :: [Complex a] -> ShowS #

Show a => Show (Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Min a -> ShowS #

show :: Min a -> String #

showList :: [Min a] -> ShowS #

Show a => Show (Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Max a -> ShowS #

show :: Max a -> String #

showList :: [Max a] -> ShowS #

Show a => Show (First a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> First a -> ShowS #

show :: First a -> String #

showList :: [First a] -> ShowS #

Show a => Show (Last a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Last a -> ShowS #

show :: Last a -> String #

showList :: [Last a] -> ShowS #

Show m => Show (WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Show a => Show (Option a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Option a -> ShowS #

show :: Option a -> String #

showList :: [Option a] -> ShowS #

Show a => Show (ZipList a)

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

Methods

showsPrec :: Int -> ZipList a -> ShowS #

show :: ZipList a -> String #

showList :: [ZipList a] -> ShowS #

Show a => Show (Identity a)

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

showsPrec :: Int -> Identity a -> ShowS #

show :: Identity a -> String #

showList :: [Identity a] -> ShowS #

Show a => Show (First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

showsPrec :: Int -> First a -> ShowS #

show :: First a -> String #

showList :: [First a] -> ShowS #

Show a => Show (Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

showsPrec :: Int -> Last a -> ShowS #

show :: Last a -> String #

showList :: [Last a] -> ShowS #

Show a => Show (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Dual a -> ShowS #

show :: Dual a -> String #

showList :: [Dual a] -> ShowS #

Show a => Show (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Sum a -> ShowS #

show :: Sum a -> String #

showList :: [Sum a] -> ShowS #

Show a => Show (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Product a -> ShowS #

show :: Product a -> String #

showList :: [Product a] -> ShowS #

Show a => Show (Down a)

This instance would be equivalent to the derived instances of the Down newtype if the getDown field were removed

Since: base-4.7.0.0

Instance details

Defined in Data.Ord

Methods

showsPrec :: Int -> Down a -> ShowS #

show :: Down a -> String #

showList :: [Down a] -> ShowS #

Show a => Show (NonEmpty a)

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> NonEmpty a -> ShowS #

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

(PrimType ty, Show ty) => Show (UArray ty) 
Instance details

Defined in Basement.UArray.Base

Methods

showsPrec :: Int -> UArray ty -> ShowS #

show :: UArray ty -> String #

showList :: [UArray ty] -> ShowS #

(PrimType ty, Show ty) => Show (Block ty) 
Instance details

Defined in Basement.Block.Base

Methods

showsPrec :: Int -> Block ty -> ShowS #

show :: Block ty -> String #

showList :: [Block ty] -> ShowS #

Show a => Show (NonEmpty a) 
Instance details

Defined in Basement.NonEmpty

Methods

showsPrec :: Int -> NonEmpty a -> ShowS #

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Show (Offset ty) 
Instance details

Defined in Basement.Types.OffsetSize

Methods

showsPrec :: Int -> Offset ty -> ShowS #

show :: Offset ty -> String #

showList :: [Offset ty] -> ShowS #

Show (CountOf ty) 
Instance details

Defined in Basement.Types.OffsetSize

Methods

showsPrec :: Int -> CountOf ty -> ShowS #

show :: CountOf ty -> String #

showList :: [CountOf ty] -> ShowS #

Show (Zn64 n) 
Instance details

Defined in Basement.Bounded

Methods

showsPrec :: Int -> Zn64 n -> ShowS #

show :: Zn64 n -> String #

showList :: [Zn64 n] -> ShowS #

Show (Zn n) 
Instance details

Defined in Basement.Bounded

Methods

showsPrec :: Int -> Zn n -> ShowS #

show :: Zn n -> String #

showList :: [Zn n] -> ShowS #

Show a => Show (ExitCase a) 
Instance details

Defined in Control.Monad.Catch

Methods

showsPrec :: Int -> ExitCase a -> ShowS #

show :: ExitCase a -> String #

showList :: [ExitCase a] -> ShowS #

Show a => Show (IntMap a) 
Instance details

Defined in Data.IntMap.Internal

Methods

showsPrec :: Int -> IntMap a -> ShowS #

show :: IntMap a -> String #

showList :: [IntMap a] -> ShowS #

Show vertex => Show (SCC vertex)

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

showsPrec :: Int -> SCC vertex -> ShowS #

show :: SCC vertex -> String #

showList :: [SCC vertex] -> ShowS #

Show a => Show (Tree a) 
Instance details

Defined in Data.Tree

Methods

showsPrec :: Int -> Tree a -> ShowS #

show :: Tree a -> String #

showList :: [Tree a] -> ShowS #

Show a => Show (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

showsPrec :: Int -> Seq a -> ShowS #

show :: Seq a -> String #

showList :: [Seq a] -> ShowS #

Show a => Show (ViewL a) 
Instance details

Defined in Data.Sequence.Internal

Methods

showsPrec :: Int -> ViewL a -> ShowS #

show :: ViewL a -> String #

showList :: [ViewL a] -> ShowS #

Show a => Show (ViewR a) 
Instance details

Defined in Data.Sequence.Internal

Methods

showsPrec :: Int -> ViewR a -> ShowS #

show :: ViewR a -> String #

showList :: [ViewR a] -> ShowS #

Show a => Show (Set a) 
Instance details

Defined in Data.Set.Internal

Methods

showsPrec :: Int -> Set a -> ShowS #

show :: Set a -> String #

showList :: [Set a] -> ShowS #

Show (Blake2s bitlen) 
Instance details

Defined in Crypto.Hash.Blake2

Methods

showsPrec :: Int -> Blake2s bitlen -> ShowS #

show :: Blake2s bitlen -> String #

showList :: [Blake2s bitlen] -> ShowS #

Show (Blake2b bitlen) 
Instance details

Defined in Crypto.Hash.Blake2

Methods

showsPrec :: Int -> Blake2b bitlen -> ShowS #

show :: Blake2b bitlen -> String #

showList :: [Blake2b bitlen] -> ShowS #

Show (Blake2sp bitlen) 
Instance details

Defined in Crypto.Hash.Blake2

Methods

showsPrec :: Int -> Blake2sp bitlen -> ShowS #

show :: Blake2sp bitlen -> String #

showList :: [Blake2sp bitlen] -> ShowS #

Show (Blake2bp bitlen) 
Instance details

Defined in Crypto.Hash.Blake2

Methods

showsPrec :: Int -> Blake2bp bitlen -> ShowS #

show :: Blake2bp bitlen -> String #

showList :: [Blake2bp bitlen] -> ShowS #

Show (SHAKE128 bitlen) 
Instance details

Defined in Crypto.Hash.SHAKE

Methods

showsPrec :: Int -> SHAKE128 bitlen -> ShowS #

show :: SHAKE128 bitlen -> String #

showList :: [SHAKE128 bitlen] -> ShowS #

Show (SHAKE256 bitlen) 
Instance details

Defined in Crypto.Hash.SHAKE

Methods

showsPrec :: Int -> SHAKE256 bitlen -> ShowS #

show :: SHAKE256 bitlen -> String #

showList :: [SHAKE256 bitlen] -> ShowS #

Show (Digest a) 
Instance details

Defined in Crypto.Hash.Types

Methods

showsPrec :: Int -> Digest a -> ShowS #

show :: Digest a -> String #

showList :: [Digest a] -> ShowS #

Show a => Show (Hashed a) 
Instance details

Defined in Data.Hashable.Class

Methods

showsPrec :: Int -> Hashed a -> ShowS #

show :: Hashed a -> String #

showList :: [Hashed a] -> ShowS #

Show (Symbolic a) 
Instance details

Defined in Hedgehog.Internal.State

Methods

showsPrec :: Int -> Symbolic a -> ShowS #

show :: Symbolic a -> String #

showList :: [Symbolic a] -> ShowS #

Show a => Show (Concrete a) 
Instance details

Defined in Hedgehog.Internal.State

Methods

showsPrec :: Int -> Concrete a -> ShowS #

show :: Concrete a -> String #

showList :: [Concrete a] -> ShowS #

Show a => Show (Label a) 
Instance details

Defined in Hedgehog.Internal.Property

Methods

showsPrec :: Int -> Label a -> ShowS #

show :: Label a -> String #

showList :: [Label a] -> ShowS #

Show a => Show (Coverage a) 
Instance details

Defined in Hedgehog.Internal.Property

Methods

showsPrec :: Int -> Coverage a -> ShowS #

show :: Coverage a -> String #

showList :: [Coverage a] -> ShowS #

Show (Opaque a) 
Instance details

Defined in Hedgehog.Internal.Opaque

Methods

showsPrec :: Int -> Opaque a -> ShowS #

show :: Opaque a -> String #

showList :: [Opaque a] -> ShowS #

(Show a, Prim a) => Show (Vector a) 
Instance details

Defined in Data.Vector.Primitive

Methods

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

show :: Vector a -> String #

showList :: [Vector a] -> ShowS #

(Show a, Storable a) => Show (Vector a) 
Instance details

Defined in Data.Vector.Storable

Methods

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

show :: Vector a -> String #

showList :: [Vector a] -> ShowS #

Show a => Show (HashSet a) 
Instance details

Defined in Data.HashSet.Internal

Methods

showsPrec :: Int -> HashSet a -> ShowS #

show :: HashSet a -> String #

showList :: [HashSet a] -> ShowS #

Show a => Show (Vector a) 
Instance details

Defined in Data.Vector

Methods

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

show :: Vector a -> String #

showList :: [Vector a] -> ShowS #

Show (Option a) 
Instance details

Defined in Options.Applicative.Types

Methods

showsPrec :: Int -> Option a -> ShowS #

show :: Option a -> String #

showList :: [Option a] -> ShowS #

Show h => Show (ParserFailure h) 
Instance details

Defined in Options.Applicative.Types

Show a => Show (ParserResult a) 
Instance details

Defined in Options.Applicative.Types

Show a => Show (OptTree a) 
Instance details

Defined in Options.Applicative.Types

Methods

showsPrec :: Int -> OptTree a -> ShowS #

show :: OptTree a -> String #

showList :: [OptTree a] -> ShowS #

Show (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

showsPrec :: Int -> Doc a -> ShowS #

show :: Doc a -> String #

showList :: [Doc a] -> ShowS #

Show a => Show (AnnotDetails a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Show a => Show (Span a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

showsPrec :: Int -> Span a -> ShowS #

show :: Span a -> String #

showList :: [Span a] -> ShowS #

Show (Doc ann)

(show doc) prettyprints document doc with defaultLayoutOptions, ignoring all annotations.

Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

showsPrec :: Int -> Doc ann -> ShowS #

show :: Doc ann -> String #

showList :: [Doc ann] -> ShowS #

Show ann => Show (SimpleDocStream ann) 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

(Show a, Prim a) => Show (PrimArray a)

Since: primitive-0.6.4.0

Instance details

Defined in Data.Primitive.PrimArray

Show a => Show (SmallArray a) 
Instance details

Defined in Data.Primitive.SmallArray

Show a => Show (Array a) 
Instance details

Defined in Data.Primitive.Array

Methods

showsPrec :: Int -> Array a -> ShowS #

show :: Array a -> String #

showList :: [Array a] -> ShowS #

Show a => Show (Window a) 
Instance details

Defined in System.Console.Terminal.Common

Methods

showsPrec :: Int -> Window a -> ShowS #

show :: Window a -> String #

showList :: [Window a] -> ShowS #

Show (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

showsPrec :: Int -> Doc a -> ShowS #

show :: Doc a -> String #

showList :: [Doc a] -> ShowS #

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 #

Elt e => Show (Exp e) Source # 
Instance details

Defined in Data.Array.Accelerate.Pretty

Methods

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

show :: Exp e -> String #

showList :: [Exp e] -> ShowS #

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 #

Function (Exp a -> f) => Show (Exp a -> f) Source # 
Instance details

Defined in Data.Array.Accelerate.Pretty

Methods

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

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

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

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 #

(Show a, Show b) => Show (Either a b)

Since: base-3.0

Instance details

Defined in Data.Either

Methods

showsPrec :: Int -> Either a b -> ShowS #

show :: Either a b -> String #

showList :: [Either a b] -> ShowS #

Show (V1 p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> V1 p -> ShowS #

show :: V1 p -> String #

showList :: [V1 p] -> ShowS #

Show (U1 p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> U1 p -> ShowS #

show :: U1 p -> String #

showList :: [U1 p] -> ShowS #

Show (TypeRep a) 
Instance details

Defined in Data.Typeable.Internal

Methods

showsPrec :: Int -> TypeRep a -> ShowS #

show :: TypeRep a -> String #

showList :: [TypeRep a] -> ShowS #

(Show a, Show b) => Show (a, b)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b) -> ShowS #

show :: (a, b) -> String #

showList :: [(a, b)] -> ShowS #

Show (ST s a)

Since: base-2.1

Instance details

Defined in GHC.ST

Methods

showsPrec :: Int -> ST s a -> ShowS #

show :: ST s a -> String #

showList :: [ST s a] -> ShowS #

(Ix a, Show a, Show b) => Show (Array a b)

Since: base-2.1

Instance details

Defined in GHC.Arr

Methods

showsPrec :: Int -> Array a b -> ShowS #

show :: Array a b -> String #

showList :: [Array a b] -> ShowS #

HasResolution a => Show (Fixed a)

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

showsPrec :: Int -> Fixed a -> ShowS #

show :: Fixed a -> String #

showList :: [Fixed a] -> ShowS #

(Show a, Show b) => Show (Arg a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Arg a b -> ShowS #

show :: Arg a b -> String #

showList :: [Arg a b] -> ShowS #

Show (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

showsPrec :: Int -> Proxy s -> ShowS #

show :: Proxy s -> String #

showList :: [Proxy s] -> ShowS #

(Show k, Show a) => Show (Map k a) 
Instance details

Defined in Data.Map.Internal

Methods

showsPrec :: Int -> Map k a -> ShowS #

show :: Map k a -> String #

showList :: [Map k a] -> ShowS #

(Show1 m, Show a) => Show (MaybeT m a) 
Instance details

Defined in Control.Monad.Trans.Maybe

Methods

showsPrec :: Int -> MaybeT m a -> ShowS #

show :: MaybeT m a -> String #

showList :: [MaybeT m a] -> ShowS #

(Show1 f, Show a) => Show (Cofree f a) 
Instance details

Defined in Control.Comonad.Cofree

Methods

showsPrec :: Int -> Cofree f a -> ShowS #

show :: Cofree f a -> String #

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

(Show1 f, Show a) => Show (Free f a) 
Instance details

Defined in Control.Monad.Free

Methods

showsPrec :: Int -> Free f a -> ShowS #

show :: Free f a -> String #

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

(Show a, Show1 v) => Show (Var a v) 
Instance details

Defined in Hedgehog.Internal.State

Methods

showsPrec :: Int -> Var a v -> ShowS #

show :: Var a v -> String #

showList :: [Var a v] -> ShowS #

Show (Action m state) 
Instance details

Defined in Hedgehog.Internal.State

Methods

showsPrec :: Int -> Action m state -> ShowS #

show :: Action m state -> String #

showList :: [Action m state] -> ShowS #

Show (Sequential m state) 
Instance details

Defined in Hedgehog.Internal.State

Methods

showsPrec :: Int -> Sequential m state -> ShowS #

show :: Sequential m state -> String #

showList :: [Sequential m state] -> ShowS #

Show (Parallel m state) 
Instance details

Defined in Hedgehog.Internal.State

Methods

showsPrec :: Int -> Parallel m state -> ShowS #

show :: Parallel m state -> String #

showList :: [Parallel m state] -> ShowS #

(Show1 m, Show a) => Show (TreeT m a) 
Instance details

Defined in Hedgehog.Internal.Tree

Methods

showsPrec :: Int -> TreeT m a -> ShowS #

show :: TreeT m a -> String #

showList :: [TreeT m a] -> ShowS #

(Show1 m, Show a) => Show (NodeT m a) 
Instance details

Defined in Hedgehog.Internal.Tree

Methods

showsPrec :: Int -> NodeT m a -> ShowS #

show :: NodeT m a -> String #

showList :: [NodeT m a] -> ShowS #

Show (f a) => Show (Yoneda f a) 
Instance details

Defined in Data.Functor.Yoneda

Methods

showsPrec :: Int -> Yoneda f a -> ShowS #

show :: Yoneda f a -> String #

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

(Show k, Show v) => Show (HashMap k v) 
Instance details

Defined in Data.HashMap.Internal

Methods

showsPrec :: Int -> HashMap k v -> ShowS #

show :: HashMap k v -> String #

showList :: [HashMap k v] -> ShowS #

(Show i, Show a) => Show (Level i a) 
Instance details

Defined in Control.Lens.Internal.Level

Methods

showsPrec :: Int -> Level i a -> ShowS #

show :: Level i a -> String #

showList :: [Level i a] -> ShowS #

(Show1 m, Show a) => Show (ListT m a) 
Instance details

Defined in Control.Monad.Trans.List

Methods

showsPrec :: Int -> ListT m a -> ShowS #

show :: ListT m a -> String #

showList :: [ListT m a] -> ShowS #

(Show a, Prim a, KnownNat n) => Show (Vec n a) Source # 
Instance details

Defined in Data.Primitive.Vec

Methods

showsPrec :: Int -> Vec n a -> ShowS #

show :: Vec n a -> String #

showList :: [Vec n a] -> ShowS #

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

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

Show (f p) => Show (Rec1 f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> Rec1 f p -> ShowS #

show :: Rec1 f p -> String #

showList :: [Rec1 f p] -> ShowS #

Show (URec Char p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Char p -> ShowS #

show :: URec Char p -> String #

showList :: [URec Char p] -> ShowS #

Show (URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Double p -> ShowS #

show :: URec Double p -> String #

showList :: [URec Double p] -> ShowS #

Show (URec Float p) 
Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Float p -> ShowS #

show :: URec Float p -> String #

showList :: [URec Float p] -> ShowS #

Show (URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Int p -> ShowS #

show :: URec Int p -> String #

showList :: [URec Int p] -> ShowS #

Show (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Word p -> ShowS #

show :: URec Word p -> String #

showList :: [URec Word p] -> ShowS #

(Show a, Show b, Show c) => Show (a, b, c)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c) -> ShowS #

show :: (a, b, c) -> String #

showList :: [(a, b, c)] -> ShowS #

Show a => Show (Const a b)

This instance would be equivalent to the derived instances of the Const newtype if the getConst field were removed

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Const

Methods

showsPrec :: Int -> Const a b -> ShowS #

show :: Const a b -> String #

showList :: [Const a b] -> ShowS #

Show (f a) => Show (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

showsPrec :: Int -> Ap f a -> ShowS #

show :: Ap f a -> String #

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

Show (f a) => Show (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Alt f a -> ShowS #

show :: Alt f a -> String #

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

Show (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

showsPrec :: Int -> (a :~: b) -> ShowS #

show :: (a :~: b) -> String #

showList :: [a :~: b] -> ShowS #

Show (p a a) => Show (Join p a) 
Instance details

Defined in Data.Bifunctor.Join

Methods

showsPrec :: Int -> Join p a -> ShowS #

show :: Join p a -> String #

showList :: [Join p a] -> ShowS #

Show (p (Fix p a) a) => Show (Fix p a) 
Instance details

Defined in Data.Bifunctor.Fix

Methods

showsPrec :: Int -> Fix p a -> ShowS #

show :: Fix p a -> String #

showList :: [Fix p a] -> ShowS #

(Show1 f, Show a) => Show (IdentityT f a) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

showsPrec :: Int -> IdentityT f a -> ShowS #

show :: IdentityT f a -> String #

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

(Show e, Show1 m, Show a) => Show (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

showsPrec :: Int -> ExceptT e m a -> ShowS #

show :: ExceptT e m a -> String #

showList :: [ExceptT e m a] -> ShowS #

(Show a, Show (f b)) => Show (FreeF f a b) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

showsPrec :: Int -> FreeF f a b -> ShowS #

show :: FreeF f a b -> String #

showList :: [FreeF f a b] -> ShowS #

(Show1 f, Show1 m, Show a) => Show (FreeT f m a) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

showsPrec :: Int -> FreeT f m a -> ShowS #

show :: FreeT f m a -> String #

showList :: [FreeT f m a] -> ShowS #

(Show a, Show (f b)) => Show (CofreeF f a b) 
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

showsPrec :: Int -> CofreeF f a b -> ShowS #

show :: CofreeF f a b -> String #

showList :: [CofreeF f a b] -> ShowS #

Show (w (CofreeF f a (CofreeT f w a))) => Show (CofreeT f w a) 
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

showsPrec :: Int -> CofreeT f w a -> ShowS #

show :: CofreeT f w a -> String #

showList :: [CofreeT f w a] -> ShowS #

Show (HashTable s k v) 
Instance details

Defined in Data.HashTable.ST.Cuckoo

Methods

showsPrec :: Int -> HashTable s k v -> ShowS #

show :: HashTable s k v -> String #

showList :: [HashTable s k v] -> ShowS #

Show (HashTable s k v) 
Instance details

Defined in Data.HashTable.ST.Basic

Methods

showsPrec :: Int -> HashTable s k v -> ShowS #

show :: HashTable s k v -> String #

showList :: [HashTable s k v] -> ShowS #

(Show e, Show1 m, Show a) => Show (ErrorT e m a) 
Instance details

Defined in Control.Monad.Trans.Error

Methods

showsPrec :: Int -> ErrorT e m a -> ShowS #

show :: ErrorT e m a -> String #

showList :: [ErrorT e m a] -> ShowS #

Show b => Show (Tagged s b) 
Instance details

Defined in Data.Tagged

Methods

showsPrec :: Int -> Tagged s b -> ShowS #

show :: Tagged s b -> String #

showList :: [Tagged s b] -> ShowS #

(Show w, Show1 m, Show a) => Show (WriterT w m a) 
Instance details

Defined in Control.Monad.Trans.Writer.Lazy

Methods

showsPrec :: Int -> WriterT w m a -> ShowS #

show :: WriterT w m a -> String #

showList :: [WriterT w m a] -> ShowS #

(Show w, Show1 m, Show a) => Show (WriterT w m a) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

showsPrec :: Int -> WriterT w m a -> ShowS #

show :: WriterT w m a -> String #

showList :: [WriterT w m a] -> ShowS #

Show c => Show (K1 i c p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> K1 i c p -> ShowS #

show :: K1 i c p -> String #

showList :: [K1 i c p] -> ShowS #

(Show (f p), Show (g p)) => Show ((f :+: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> (f :+: g) p -> ShowS #

show :: (f :+: g) p -> String #

showList :: [(f :+: g) p] -> ShowS #

(Show (f p), Show (g p)) => Show ((f :*: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> (f :*: g) p -> ShowS #

show :: (f :*: g) p -> String #

showList :: [(f :*: g) p] -> ShowS #

(Show a, Show b, Show c, Show d) => Show (a, b, c, d)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d) -> ShowS #

show :: (a, b, c, d) -> String #

showList :: [(a, b, c, d)] -> ShowS #

(Show1 f, Show1 g, Show a) => Show (Product f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

showsPrec :: Int -> Product f g a -> ShowS #

show :: Product f g a -> String #

showList :: [Product f g a] -> ShowS #

(Show1 f, Show1 g, Show a) => Show (Sum f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

showsPrec :: Int -> Sum f g a -> ShowS #

show :: Sum f g a -> String #

showList :: [Sum f g a] -> ShowS #

Show (a :~~: b)

Since: base-4.10.0.0

Instance details

Defined in Data.Type.Equality

Methods

showsPrec :: Int -> (a :~~: b) -> ShowS #

show :: (a :~~: b) -> String #

showList :: [a :~~: b] -> ShowS #

(Show i, Show a) => Show (Magma i t b a) 
Instance details

Defined in Control.Lens.Internal.Magma

Methods

showsPrec :: Int -> Magma i t b a -> ShowS #

show :: Magma i t b a -> String #

showList :: [Magma i t b a] -> ShowS #

Show (f p) => Show (M1 i c f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> M1 i c f p -> ShowS #

show :: M1 i c f p -> String #

showList :: [M1 i c f p] -> ShowS #

Show (f (g p)) => Show ((f :.: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> (f :.: g) p -> ShowS #

show :: (f :.: g) p -> String #

showList :: [(f :.: g) p] -> ShowS #

(Show a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e) -> ShowS #

show :: (a, b, c, d, e) -> String #

showList :: [(a, b, c, d, e)] -> ShowS #

(Show1 f, Show1 g, Show a) => Show (Compose f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

showsPrec :: Int -> Compose f g a -> ShowS #

show :: Compose f g a -> String #

showList :: [Compose f g a] -> ShowS #

Show (p a b) => Show (WrappedBifunctor p a b) 
Instance details

Defined in Data.Bifunctor.Wrapped

Show (g b) => Show (Joker g a b) 
Instance details

Defined in Data.Bifunctor.Joker

Methods

showsPrec :: Int -> Joker g a b -> ShowS #

show :: Joker g a b -> String #

showList :: [Joker g a b] -> ShowS #

Show (p b a) => Show (Flip p a b) 
Instance details

Defined in Data.Bifunctor.Flip

Methods

showsPrec :: Int -> Flip p a b -> ShowS #

show :: Flip p a b -> String #

showList :: [Flip p a b] -> ShowS #

Show (f a) => Show (Clown f a b) 
Instance details

Defined in Data.Bifunctor.Clown

Methods

showsPrec :: Int -> Clown f a b -> ShowS #

show :: Clown f a b -> String #

showList :: [Clown f a b] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f) => Show (a, b, c, d, e, f)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f) -> ShowS #

show :: (a, b, c, d, e, f) -> String #

showList :: [(a, b, c, d, e, f)] -> ShowS #

(Show (p a b), Show (q a b)) => Show (Sum p q a b) 
Instance details

Defined in Data.Bifunctor.Sum

Methods

showsPrec :: Int -> Sum p q a b -> ShowS #

show :: Sum p q a b -> String #

showList :: [Sum p q a b] -> ShowS #

(Show (f a b), Show (g a b)) => Show (Product f g a b) 
Instance details

Defined in Data.Bifunctor.Product

Methods

showsPrec :: Int -> Product f g a b -> ShowS #

show :: Product f g a b -> String #

showList :: [Product f g a b] -> ShowS #

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

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g) -> ShowS #

show :: (a, b, c, d, e, f, g) -> String #

showList :: [(a, b, c, d, e, f, g)] -> ShowS #

Show (f (p a b)) => Show (Tannen f p a b) 
Instance details

Defined in Data.Bifunctor.Tannen

Methods

showsPrec :: Int -> Tannen f p a b -> ShowS #

show :: Tannen f p a b -> String #

showList :: [Tannen f p a b] -> ShowS #

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

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h) -> ShowS #

show :: (a, b, c, d, e, f, g, h) -> String #

showList :: [(a, b, c, d, e, f, g, h)] -> ShowS #

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

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i) -> String #

showList :: [(a, b, c, d, e, f, g, h, i)] -> ShowS #

Show (p (f a) (g b)) => Show (Biff p f g a b) 
Instance details

Defined in Data.Bifunctor.Biff

Methods

showsPrec :: Int -> Biff p f g a b -> ShowS #

show :: Biff p f g a b -> String #

showList :: [Biff p f g a b] -> ShowS #

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

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i, j) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j)] -> ShowS #

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

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i, j, k) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> ShowS #

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

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i, j, k, l) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> ShowS #

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

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> ShowS #

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

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> ShowS #

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

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> ShowS #

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

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> ShowS #

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

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> ShowS #

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

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n, Show o, Show p) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source # 
Instance details

Defined in Data.Array.Accelerate.Orphans

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)] -> ShowS #

class Generic a #

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

A Generic instance must satisfy the following laws:

from . toid
to . fromid

Minimal complete definition

from, to

Instances

Instances details
Generic Bool

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Bool :: Type -> Type #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Generic Ordering

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Ordering :: Type -> Type #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Generic Exp 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Exp :: Type -> Type #

Methods

from :: Exp -> Rep Exp x #

to :: Rep Exp x -> Exp #

Generic Match 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Match :: Type -> Type #

Methods

from :: Match -> Rep Match x #

to :: Rep Match x -> Match #

Generic Clause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Clause :: Type -> Type #

Methods

from :: Clause -> Rep Clause x #

to :: Rep Clause x -> Clause #

Generic Pat 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Pat :: Type -> Type #

Methods

from :: Pat -> Rep Pat x #

to :: Rep Pat x -> Pat #

Generic Type 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Type :: Type -> Type #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

Generic Dec 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Dec :: Type -> Type #

Methods

from :: Dec -> Rep Dec x #

to :: Rep Dec x -> Dec #

Generic Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Name :: Type -> Type #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

Generic FunDep 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FunDep :: Type -> Type #

Methods

from :: FunDep -> Rep FunDep x #

to :: Rep FunDep x -> FunDep #

Generic InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep InjectivityAnn :: Type -> Type #

Generic Overlap 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Overlap :: Type -> Type #

Methods

from :: Overlap -> Rep Overlap x #

to :: Rep Overlap x -> Overlap #

Generic ()

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep () :: Type -> Type #

Methods

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

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

Generic Void

Since: base-4.8.0.0

Instance details

Defined in Data.Void

Associated Types

type Rep Void :: Type -> Type #

Methods

from :: Void -> Rep Void x #

to :: Rep Void x -> Void #

Generic Version

Since: base-4.9.0.0

Instance details

Defined in Data.Version

Associated Types

type Rep Version :: Type -> Type #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Generic ExitCode 
Instance details

Defined in GHC.IO.Exception

Associated Types

type Rep ExitCode :: Type -> Type #

Methods

from :: ExitCode -> Rep ExitCode x #

to :: Rep ExitCode x -> ExitCode #

Generic All

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep All :: Type -> Type #

Methods

from :: All -> Rep All x #

to :: Rep All x -> All #

Generic Any

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep Any :: Type -> Type #

Methods

from :: Any -> Rep Any x #

to :: Rep Any x -> Any #

Generic Fixity

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Fixity :: Type -> Type #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic Associativity

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Associativity :: Type -> Type #

Generic SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceUnpackedness :: Type -> Type #

Generic SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceStrictness :: Type -> Type #

Generic DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep DecidedStrictness :: Type -> Type #

Generic Clock 
Instance details

Defined in System.Clock

Associated Types

type Rep Clock :: Type -> Type #

Methods

from :: Clock -> Rep Clock x #

to :: Rep Clock x -> Clock #

Generic TimeSpec 
Instance details

Defined in System.Clock

Associated Types

type Rep TimeSpec :: Type -> Type #

Methods

from :: TimeSpec -> Rep TimeSpec x #

to :: Rep TimeSpec x -> TimeSpec #

Generic Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

Associated Types

type Rep Extension :: Type -> Type #

Generic ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Associated Types

type Rep ForeignSrcLang :: Type -> Type #

Generic Half 
Instance details

Defined in Numeric.Half

Associated Types

type Rep Half :: Type -> Type #

Methods

from :: Half -> Rep Half x #

to :: Rep Half x -> Half #

Generic RuleBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleBndr :: Type -> Type #

Methods

from :: RuleBndr -> Rep RuleBndr x #

to :: Rep RuleBndr x -> RuleBndr #

Generic Phases 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Phases :: Type -> Type #

Methods

from :: Phases -> Rep Phases x #

to :: Rep Phases x -> Phases #

Generic RuleMatch 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleMatch :: Type -> Type #

Generic Inline 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Inline :: Type -> Type #

Methods

from :: Inline -> Rep Inline x #

to :: Rep Inline x -> Inline #

Generic Pragma 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Pragma :: Type -> Type #

Methods

from :: Pragma -> Rep Pragma x #

to :: Rep Pragma x -> Pragma #

Generic DerivClause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivClause :: Type -> Type #

Generic DerivStrategy 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivStrategy :: Type -> Type #

Generic TySynEqn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TySynEqn :: Type -> Type #

Methods

from :: TySynEqn -> Rep TySynEqn x #

to :: Rep TySynEqn x -> TySynEqn #

Generic Fixity 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Fixity :: Type -> Type #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic Info 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Info :: Type -> Type #

Methods

from :: Info -> Rep Info x #

to :: Rep Info x -> Info #

Generic Con 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Con :: Type -> Type #

Methods

from :: Con -> Rep Con x #

to :: Rep Con x -> Con #

Generic TyVarBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TyVarBndr :: Type -> Type #

Generic Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Associated Types

type Rep Doc :: Type -> Type #

Methods

from :: Doc -> Rep Doc x #

to :: Rep Doc x -> Doc #

Generic TextDetails 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep TextDetails :: Type -> Type #

Generic Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Style :: Type -> Type #

Methods

from :: Style -> Rep Style x #

to :: Rep Style x -> Style #

Generic Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Mode :: Type -> Type #

Methods

from :: Mode -> Rep Mode x #

to :: Rep Mode x -> Mode #

Generic Outcome 
Instance details

Defined in Test.Tasty.Core

Associated Types

type Rep Outcome :: Type -> Type #

Methods

from :: Outcome -> Rep Outcome x #

to :: Rep Outcome x -> Outcome #

Generic ModName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModName :: Type -> Type #

Methods

from :: ModName -> Rep ModName x #

to :: Rep ModName x -> ModName #

Generic PkgName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PkgName :: Type -> Type #

Methods

from :: PkgName -> Rep PkgName x #

to :: Rep PkgName x -> PkgName #

Generic Module 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Module :: Type -> Type #

Methods

from :: Module -> Rep Module x #

to :: Rep Module x -> Module #

Generic OccName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep OccName :: Type -> Type #

Methods

from :: OccName -> Rep OccName x #

to :: Rep OccName x -> OccName #

Generic NameFlavour 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameFlavour :: Type -> Type #

Generic NameSpace 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameSpace :: Type -> Type #

Generic Loc 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Loc :: Type -> Type #

Methods

from :: Loc -> Rep Loc x #

to :: Rep Loc x -> Loc #

Generic ModuleInfo 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModuleInfo :: Type -> Type #

Generic FixityDirection 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FixityDirection :: Type -> Type #

Generic Lit 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Lit :: Type -> Type #

Methods

from :: Lit -> Rep Lit x #

to :: Rep Lit x -> Lit #

Generic Bytes 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Bytes :: Type -> Type #

Methods

from :: Bytes -> Rep Bytes x #

to :: Rep Bytes x -> Bytes #

Generic Body 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Body :: Type -> Type #

Methods

from :: Body -> Rep Body x #

to :: Rep Body x -> Body #

Generic Guard 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Guard :: Type -> Type #

Methods

from :: Guard -> Rep Guard x #

to :: Rep Guard x -> Guard #

Generic Stmt 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Stmt :: Type -> Type #

Methods

from :: Stmt -> Rep Stmt x #

to :: Rep Stmt x -> Stmt #

Generic Range 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Range :: Type -> Type #

Methods

from :: Range -> Rep Range x #

to :: Rep Range x -> Range #

Generic TypeFamilyHead 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TypeFamilyHead :: Type -> Type #

Generic Foreign 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Foreign :: Type -> Type #

Methods

from :: Foreign -> Rep Foreign x #

to :: Rep Foreign x -> Foreign #

Generic Callconv 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Callconv :: Type -> Type #

Methods

from :: Callconv -> Rep Callconv x #

to :: Rep Callconv x -> Callconv #

Generic Safety 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Safety :: Type -> Type #

Methods

from :: Safety -> Rep Safety x #

to :: Rep Safety x -> Safety #

Generic AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnTarget :: Type -> Type #

Generic SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceUnpackedness :: Type -> Type #

Generic SourceStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceStrictness :: Type -> Type #

Generic DecidedStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DecidedStrictness :: Type -> Type #

Generic Bang 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Bang :: Type -> Type #

Methods

from :: Bang -> Rep Bang x #

to :: Rep Bang x -> Bang #

Generic PatSynDir 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynDir :: Type -> Type #

Generic PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynArgs :: Type -> Type #

Generic FamilyResultSig 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FamilyResultSig :: Type -> Type #

Generic TyLit 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TyLit :: Type -> Type #

Methods

from :: TyLit -> Rep TyLit x #

to :: Rep TyLit x -> TyLit #

Generic Role 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Role :: Type -> Type #

Methods

from :: Role -> Rep Role x #

to :: Rep Role x -> Role #

Generic AnnLookup 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnLookup :: Type -> Type #

Generic DatatypeInfo 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep DatatypeInfo :: Type -> Type #

Generic DatatypeVariant 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep DatatypeVariant :: Type -> Type #

Generic ConstructorInfo 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep ConstructorInfo :: Type -> Type #

Generic ConstructorVariant 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep ConstructorVariant :: Type -> Type #

Generic FieldStrictness 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep FieldStrictness :: Type -> Type #

Generic Unpackedness 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep Unpackedness :: Type -> Type #

Generic Strictness 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep Strictness :: Type -> Type #

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 #

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 #

Generic [a]

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep [a] :: Type -> Type #

Methods

from :: [a] -> Rep [a] x #

to :: Rep [a] x -> [a] #

Generic (Maybe a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Maybe a) :: Type -> Type #

Methods

from :: Maybe a -> Rep (Maybe a) x #

to :: Rep (Maybe a) x -> Maybe a #

Generic (Ratio a) Source # 
Instance details

Defined in Data.Array.Accelerate.Orphans

Associated Types

type Rep (Ratio a) :: Type -> Type #

Methods

from :: Ratio a -> Rep (Ratio a) x #

to :: Rep (Ratio a) x -> Ratio a #

Generic (Par1 p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Par1 p) :: Type -> Type #

Methods

from :: Par1 p -> Rep (Par1 p) x #

to :: Rep (Par1 p) x -> Par1 p #

Generic (Complex a)

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

Associated Types

type Rep (Complex a) :: Type -> Type #

Methods

from :: Complex a -> Rep (Complex a) x #

to :: Rep (Complex a) x -> Complex a #

Generic (Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Min a) :: Type -> Type #

Methods

from :: Min a -> Rep (Min a) x #

to :: Rep (Min a) x -> Min a #

Generic (Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Max a) :: Type -> Type #

Methods

from :: Max a -> Rep (Max a) x #

to :: Rep (Max a) x -> Max a #

Generic (First a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (First a) :: Type -> Type #

Methods

from :: First a -> Rep (First a) x #

to :: Rep (First a) x -> First a #

Generic (Last a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Last a) :: Type -> Type #

Methods

from :: Last a -> Rep (Last a) x #

to :: Rep (Last a) x -> Last a #

Generic (WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (WrappedMonoid m) :: Type -> Type #

Generic (Option a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Option a) :: Type -> Type #

Methods

from :: Option a -> Rep (Option a) x #

to :: Rep (Option a) x -> Option a #

Generic (ZipList a)

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

Associated Types

type Rep (ZipList a) :: Type -> Type #

Methods

from :: ZipList a -> Rep (ZipList a) x #

to :: Rep (ZipList a) x -> ZipList a #

Generic (Identity a)

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Associated Types

type Rep (Identity a) :: Type -> Type #

Methods

from :: Identity a -> Rep (Identity a) x #

to :: Rep (Identity a) x -> Identity a #

Generic (First a)

Since: base-4.7.0.0

Instance details

Defined in Data.Monoid

Associated Types

type Rep (First a) :: Type -> Type #

Methods

from :: First a -> Rep (First a) x #

to :: Rep (First a) x -> First a #

Generic (Last a)

Since: base-4.7.0.0

Instance details

Defined in Data.Monoid

Associated Types

type Rep (Last a) :: Type -> Type #

Methods

from :: Last a -> Rep (Last a) x #

to :: Rep (Last a) x -> Last a #

Generic (Dual a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Dual a) :: Type -> Type #

Methods

from :: Dual a -> Rep (Dual a) x #

to :: Rep (Dual a) x -> Dual a #

Generic (Endo a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Endo a) :: Type -> Type #

Methods

from :: Endo a -> Rep (Endo a) x #

to :: Rep (Endo a) x -> Endo a #

Generic (Sum a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Sum a) :: Type -> Type #

Methods

from :: Sum a -> Rep (Sum a) x #

to :: Rep (Sum a) x -> Sum a #

Generic (Product a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Product a) :: Type -> Type #

Methods

from :: Product a -> Rep (Product a) x #

to :: Rep (Product a) x -> Product a #

Generic (Down a)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Down a) :: Type -> Type #

Methods

from :: Down a -> Rep (Down a) x #

to :: Rep (Down a) x -> Down a #

Generic (NonEmpty a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (NonEmpty a) :: Type -> Type #

Methods

from :: NonEmpty a -> Rep (NonEmpty a) x #

to :: Rep (NonEmpty a) x -> NonEmpty a #

Generic (SCC vertex)

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Associated Types

type Rep (SCC vertex) :: Type -> Type #

Methods

from :: SCC vertex -> Rep (SCC vertex) x #

to :: Rep (SCC vertex) x -> SCC vertex #

Generic (Tree a)

Since: containers-0.5.8

Instance details

Defined in Data.Tree

Associated Types

type Rep (Tree a) :: Type -> Type #

Methods

from :: Tree a -> Rep (Tree a) x #

to :: Rep (Tree a) x -> Tree a #

Generic (FingerTree a)

Since: containers-0.6.1

Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (FingerTree a) :: Type -> Type #

Methods

from :: FingerTree a -> Rep (FingerTree a) x #

to :: Rep (FingerTree a) x -> FingerTree a #

Generic (Digit a)

Since: containers-0.6.1

Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Digit a) :: Type -> Type #

Methods

from :: Digit a -> Rep (Digit a) x #

to :: Rep (Digit a) x -> Digit a #

Generic (Node a)

Since: containers-0.6.1

Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Node a) :: Type -> Type #

Methods

from :: Node a -> Rep (Node a) x #

to :: Rep (Node a) x -> Node a #

Generic (Elem a)

Since: containers-0.6.1

Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Elem a) :: Type -> Type #

Methods

from :: Elem a -> Rep (Elem a) x #

to :: Rep (Elem a) x -> Elem a #

Generic (ViewL a)

Since: containers-0.5.8

Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (ViewL a) :: Type -> Type #

Methods

from :: ViewL a -> Rep (ViewL a) x #

to :: Rep (ViewL a) x -> ViewL a #

Generic (ViewR a)

Since: containers-0.5.8

Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (ViewR a) :: Type -> Type #

Methods

from :: ViewR a -> Rep (ViewR a) x #

to :: Rep (ViewR a) x -> ViewR a #

Generic (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep (Doc a) :: Type -> Type #

Methods

from :: Doc a -> Rep (Doc a) x #

to :: Rep (Doc a) x -> Doc a #

Generic (Doc ann) 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Associated Types

type Rep (Doc ann) :: Type -> Type #

Methods

from :: Doc ann -> Rep (Doc ann) x #

to :: Rep (Doc ann) x -> Doc ann #

Generic (SimpleDocStream ann) 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Associated Types

type Rep (SimpleDocStream ann) :: Type -> Type #

Methods

from :: SimpleDocStream ann -> Rep (SimpleDocStream ann) x #

to :: Rep (SimpleDocStream ann) x -> SimpleDocStream ann #

Generic (Window a) 
Instance details

Defined in System.Console.Terminal.Common

Associated Types

type Rep (Window a) :: Type -> Type #

Methods

from :: Window a -> Rep (Window a) x #

to :: Rep (Window a) x -> Window a #

Generic (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Associated Types

type Rep (Doc a) :: Type -> Type #

Methods

from :: Doc a -> Rep (Doc a) x #

to :: Rep (Doc a) x -> Doc a #

Generic (SimpleDoc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Associated Types

type Rep (SimpleDoc a) :: Type -> Type #

Methods

from :: SimpleDoc a -> Rep (SimpleDoc a) x #

to :: Rep (SimpleDoc a) x -> SimpleDoc a #

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 #

Generic (Either a b)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Either a b) :: Type -> Type #

Methods

from :: Either a b -> Rep (Either a b) x #

to :: Rep (Either a b) x -> Either a b #

Generic (V1 p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (V1 p) :: Type -> Type #

Methods

from :: V1 p -> Rep (V1 p) x #

to :: Rep (V1 p) x -> V1 p #

Generic (U1 p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (U1 p) :: Type -> Type #

Methods

from :: U1 p -> Rep (U1 p) x #

to :: Rep (U1 p) x -> U1 p #

Generic (a, b)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b) :: Type -> Type #

Methods

from :: (a, b) -> Rep (a, b) x #

to :: Rep (a, b) x -> (a, b) #

Generic (Arg a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Arg a b) :: Type -> Type #

Methods

from :: Arg a b -> Rep (Arg a b) x #

to :: Rep (Arg a b) x -> Arg a b #

Generic (WrappedMonad m a)

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

Associated Types

type Rep (WrappedMonad m a) :: Type -> Type #

Methods

from :: WrappedMonad m a -> Rep (WrappedMonad m a) x #

to :: Rep (WrappedMonad m a) x -> WrappedMonad m a #

Generic (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: Type -> Type #

Methods

from :: Proxy t -> Rep (Proxy t) x #

to :: Rep (Proxy t) x -> Proxy t #

Generic (Cofree f a) 
Instance details

Defined in Control.Comonad.Cofree

Associated Types

type Rep (Cofree f a) :: Type -> Type #

Methods

from :: Cofree f a -> Rep (Cofree f a) x #

to :: Rep (Cofree f a) x -> Cofree f a #

Generic (Free f a) 
Instance details

Defined in Control.Monad.Free

Associated Types

type Rep (Free f a) :: Type -> Type #

Methods

from :: Free f a -> Rep (Free f a) x #

to :: Rep (Free f a) x -> Free f a #

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 #

Generic (Rec1 f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Rec1 f p) :: Type -> Type #

Methods

from :: Rec1 f p -> Rep (Rec1 f p) x #

to :: Rep (Rec1 f p) x -> Rec1 f p #

Generic (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec (Ptr ()) p) :: Type -> Type #

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x #

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p #

Generic (URec Char p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Char p) :: Type -> Type #

Methods

from :: URec Char p -> Rep (URec Char p) x #

to :: Rep (URec Char p) x -> URec Char p #

Generic (URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Double p) :: Type -> Type #

Methods

from :: URec Double p -> Rep (URec Double p) x #

to :: Rep (URec Double p) x -> URec Double p #

Generic (URec Float p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Float p) :: Type -> Type #

Methods

from :: URec Float p -> Rep (URec Float p) x #

to :: Rep (URec Float p) x -> URec Float p #

Generic (URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Int p) :: Type -> Type #

Methods

from :: URec Int p -> Rep (URec Int p) x #

to :: Rep (URec Int p) x -> URec Int p #

Generic (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Word p) :: Type -> Type #

Methods

from :: URec Word p -> Rep (URec Word p) x #

to :: Rep (URec Word p) x -> URec Word p #

Generic (a, b, c)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c) :: Type -> Type #

Methods

from :: (a, b, c) -> Rep (a, b, c) x #

to :: Rep (a, b, c) x -> (a, b, c) #

Generic (WrappedArrow a b c)

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

Associated Types

type Rep (WrappedArrow a b c) :: Type -> Type #

Methods

from :: WrappedArrow a b c -> Rep (WrappedArrow a b c) x #

to :: Rep (WrappedArrow a b c) x -> WrappedArrow a b c #

Generic (Kleisli m a b)

Since: base-4.14.0.0

Instance details

Defined in Control.Arrow

Associated Types

type Rep (Kleisli m a b) :: Type -> Type #

Methods

from :: Kleisli m a b -> Rep (Kleisli m a b) x #

to :: Rep (Kleisli m a b) x -> Kleisli m a b #

Generic (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Associated Types

type Rep (Const a b) :: Type -> Type #

Methods

from :: Const a b -> Rep (Const a b) x #

to :: Rep (Const a b) x -> Const a b #

Generic (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Associated Types

type Rep (Ap f a) :: Type -> Type #

Methods

from :: Ap f a -> Rep (Ap f a) x #

to :: Rep (Ap f a) x -> Ap f a #

Generic (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Alt f a) :: Type -> Type #

Methods

from :: Alt f a -> Rep (Alt f a) x #

to :: Rep (Alt f a) x -> Alt f a #

Generic (Join p a) 
Instance details

Defined in Data.Bifunctor.Join

Associated Types

type Rep (Join p a) :: Type -> Type #

Methods

from :: Join p a -> Rep (Join p a) x #

to :: Rep (Join p a) x -> Join p a #

Generic (Fix p a) 
Instance details

Defined in Data.Bifunctor.Fix

Associated Types

type Rep (Fix p a) :: Type -> Type #

Methods

from :: Fix p a -> Rep (Fix p a) x #

to :: Rep (Fix p a) x -> Fix p a #

Generic (FreeF f a b) 
Instance details

Defined in Control.Monad.Trans.Free

Associated Types

type Rep (FreeF f a b) :: Type -> Type #

Methods

from :: FreeF f a b -> Rep (FreeF f a b) x #

to :: Rep (FreeF f a b) x -> FreeF f a b #

Generic (CofreeF f a b) 
Instance details

Defined in Control.Comonad.Trans.Cofree

Associated Types

type Rep (CofreeF f a b) :: Type -> Type #

Methods

from :: CofreeF f a b -> Rep (CofreeF f a b) x #

to :: Rep (CofreeF f a b) x -> CofreeF f a b #

Generic (Tagged s b) 
Instance details

Defined in Data.Tagged

Associated Types

type Rep (Tagged s b) :: Type -> Type #

Methods

from :: Tagged s b -> Rep (Tagged s b) x #

to :: Rep (Tagged s b) x -> Tagged s b #

Generic (K1 i c p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (K1 i c p) :: Type -> Type #

Methods

from :: K1 i c p -> Rep (K1 i c p) x #

to :: Rep (K1 i c p) x -> K1 i c p #

Generic ((f :+: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :+: g) p) :: Type -> Type #

Methods

from :: (f :+: g) p -> Rep ((f :+: g) p) x #

to :: Rep ((f :+: g) p) x -> (f :+: g) p #

Generic ((f :*: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :*: g) p) :: Type -> Type #

Methods

from :: (f :*: g) p -> Rep ((f :*: g) p) x #

to :: Rep ((f :*: g) p) x -> (f :*: g) p #

Generic (a, b, c, d)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d) :: Type -> Type #

Methods

from :: (a, b, c, d) -> Rep (a, b, c, d) x #

to :: Rep (a, b, c, d) x -> (a, b, c, d) #

Generic (Product f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Associated Types

type Rep (Product f g a) :: Type -> Type #

Methods

from :: Product f g a -> Rep (Product f g a) x #

to :: Rep (Product f g a) x -> Product f g a #

Generic (Sum f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Associated Types

type Rep (Sum f g a) :: Type -> Type #

Methods

from :: Sum f g a -> Rep (Sum f g a) x #

to :: Rep (Sum f g a) x -> Sum f g a #

Generic (M1 i c f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (M1 i c f p) :: Type -> Type #

Methods

from :: M1 i c f p -> Rep (M1 i c f p) x #

to :: Rep (M1 i c f p) x -> M1 i c f p #

Generic ((f :.: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :.: g) p) :: Type -> Type #

Methods

from :: (f :.: g) p -> Rep ((f :.: g) p) x #

to :: Rep ((f :.: g) p) x -> (f :.: g) p #

Generic (a, b, c, d, e)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e) :: Type -> Type #

Methods

from :: (a, b, c, d, e) -> Rep (a, b, c, d, e) x #

to :: Rep (a, b, c, d, e) x -> (a, b, c, d, e) #

Generic (Compose f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Associated Types

type Rep (Compose f g a) :: Type -> Type #

Methods

from :: Compose f g a -> Rep (Compose f g a) x #

to :: Rep (Compose f g a) x -> Compose f g a #

Generic (WrappedBifunctor p a b) 
Instance details

Defined in Data.Bifunctor.Wrapped

Associated Types

type Rep (WrappedBifunctor p a b) :: Type -> Type #

Methods

from :: WrappedBifunctor p a b -> Rep (WrappedBifunctor p a b) x #

to :: Rep (WrappedBifunctor p a b) x -> WrappedBifunctor p a b #

Generic (Joker g a b) 
Instance details

Defined in Data.Bifunctor.Joker

Associated Types

type Rep (Joker g a b) :: Type -> Type #

Methods

from :: Joker g a b -> Rep (Joker g a b) x #

to :: Rep (Joker g a b) x -> Joker g a b #

Generic (Flip p a b) 
Instance details

Defined in Data.Bifunctor.Flip

Associated Types

type Rep (Flip p a b) :: Type -> Type #

Methods

from :: Flip p a b -> Rep (Flip p a b) x #

to :: Rep (Flip p a b) x -> Flip p a b #

Generic (Clown f a b) 
Instance details

Defined in Data.Bifunctor.Clown

Associated Types

type Rep (Clown f a b) :: Type -> Type #

Methods

from :: Clown f a b -> Rep (Clown f a b) x #

to :: Rep (Clown f a b) x -> Clown f a b #

Generic (a, b, c, d, e, f)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f) -> Rep (a, b, c, d, e, f) x #

to :: Rep (a, b, c, d, e, f) x -> (a, b, c, d, e, f) #

Generic (Sum p q a b) 
Instance details

Defined in Data.Bifunctor.Sum

Associated Types

type Rep (Sum p q a b) :: Type -> Type #

Methods

from :: Sum p q a b -> Rep (Sum p q a b) x #

to :: Rep (Sum p q a b) x -> Sum p q a b #

Generic (Product f g a b) 
Instance details

Defined in Data.Bifunctor.Product

Associated Types

type Rep (Product f g a b) :: Type -> Type #

Methods

from :: Product f g a b -> Rep (Product f g a b) x #

to :: Rep (Product f g a b) x -> Product f g a b #

Generic (a, b, c, d, e, f, g)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g) -> Rep (a, b, c, d, e, f, g) x #

to :: Rep (a, b, c, d, e, f, g) x -> (a, b, c, d, e, f, g) #

Generic (Tannen f p a b) 
Instance details

Defined in Data.Bifunctor.Tannen

Associated Types

type Rep (Tannen f p a b) :: Type -> Type #

Methods

from :: Tannen f p a b -> Rep (Tannen f p a b) x #

to :: Rep (Tannen f p a b) x -> Tannen f p a b #

Generic (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Data.Array.Accelerate.Orphans

Associated Types

type Rep (a, b, c, d, e, f, g, h) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g, h) -> Rep (a, b, c, d, e, f, g, h) x #

to :: Rep (a, b, c, d, e, f, g, h) x -> (a, b, c, d, e, f, g, h) #

Generic (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Data.Array.Accelerate.Orphans

Associated Types

type Rep (a, b, c, d, e, f, g, h, i) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g, h, i) -> Rep (a, b, c, d, e, f, g, h, i) x #

to :: Rep (a, b, c, d, e, f, g, h, i) x -> (a, b, c, d, e, f, g, h, i) #

Generic (Biff p f g a b) 
Instance details

Defined in Data.Bifunctor.Biff

Associated Types

type Rep (Biff p f g a b) :: Type -> Type #

Methods

from :: Biff p f g a b -> Rep (Biff p f g a b) x #

to :: Rep (Biff p f g a b) x -> Biff p f g a b #

Generic (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Data.Array.Accelerate.Orphans

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g, h, i, j) -> Rep (a, b, c, d, e, f, g, h, i, j) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j) x -> (a, b, c, d, e, f, g, h, i, j) #

Generic (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Data.Array.Accelerate.Orphans

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k) -> Rep (a, b, c, d, e, f, g, h, i, j, k) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k) x -> (a, b, c, d, e, f, g, h, i, j, k) #

Generic (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Data.Array.Accelerate.Orphans

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l) x -> (a, b, c, d, e, f, g, h, i, j, k, l) #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 
Instance details

Defined in Data.Array.Accelerate.Orphans

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) x -> (a, b, c, d, e, f, g, h, i, j, k, l, m) #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 
Instance details

Defined in Data.Array.Accelerate.Orphans

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) x -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 
Instance details

Defined in Data.Array.Accelerate.Orphans

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) x -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source # 
Instance details

Defined in Data.Array.Accelerate.Orphans

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) x -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) #

type HasCallStack = ?callStack :: CallStack #

Request a CallStack.

NOTE: The implicit parameter ?callStack :: CallStack is an implementation detail and should not be considered part of the CallStack API, we may decide to change the implementation in the future.

Since: base-4.9.0.0

data Int #

A fixed-precision integer type with at least the range [-2^29 .. 2^29-1]. The exact range for a given implementation can be determined by using minBound and maxBound from the Bounded class.

Instances

Instances details
Bounded Int

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

minBound :: Int #

maxBound :: Int #

Enum Int

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

succ :: Int -> Int #

pred :: Int -> Int #

toEnum :: Int -> Int #

fromEnum :: Int -> Int #

enumFrom :: Int -> [Int] #

enumFromThen :: Int -> Int -> [Int] #

enumFromTo :: Int -> Int -> [Int] #

enumFromThenTo :: Int -> Int -> Int -> [Int] #

Eq Int 
Instance details

Defined in GHC.Classes

Methods

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

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

Integral Int

Since: base-2.0.1

Instance details

Defined in GHC.Real

Methods

quot :: Int -> Int -> Int #

rem :: Int -> Int -> Int #

div :: Int -> Int -> Int #

mod :: Int -> Int -> Int #

quotRem :: Int -> Int -> (Int, Int) #

divMod :: Int -> Int -> (Int, Int) #

toInteger :: Int -> Integer #

Num Int

Since: base-2.1

Instance details

Defined in GHC.Num

Methods

(+) :: Int -> Int -> Int #

(-) :: Int -> Int -> Int #

(*) :: Int -> Int -> Int #

negate :: Int -> Int #

abs :: Int -> Int #

signum :: Int -> Int #

fromInteger :: Integer -> Int #

Ord Int 
Instance details

Defined in GHC.Classes

Methods

compare :: Int -> Int -> Ordering #

(<) :: Int -> Int -> Bool #

(<=) :: Int -> Int -> Bool #

(>) :: Int -> Int -> Bool #

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

max :: Int -> Int -> Int #

min :: Int -> Int -> Int #

Read Int

Since: base-2.1

Instance details

Defined in GHC.Read

Real Int

Since: base-2.0.1

Instance details

Defined in GHC.Real

Methods

toRational :: Int -> Rational #

Show Int

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Int -> ShowS #

show :: Int -> String #

showList :: [Int] -> ShowS #

Ix Int

Since: base-2.1

Instance details

Defined in GHC.Ix

Methods

range :: (Int, Int) -> [Int] #

index :: (Int, Int) -> Int -> Int #

unsafeIndex :: (Int, Int) -> Int -> Int #

inRange :: (Int, Int) -> Int -> Bool #

rangeSize :: (Int, Int) -> Int #

unsafeRangeSize :: (Int, Int) -> Int #

PrintfArg Int

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Int

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int -> Int #

alignment :: Int -> Int #

peekElemOff :: Ptr Int -> Int -> IO Int #

pokeElemOff :: Ptr Int -> Int -> Int -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int #

pokeByteOff :: Ptr b -> Int -> Int -> IO () #

peek :: Ptr Int -> IO Int #

poke :: Ptr Int -> Int -> IO () #

Bits Int

Since: base-2.1

Instance details

Defined in Data.Bits

Methods

(.&.) :: Int -> Int -> Int #

(.|.) :: Int -> Int -> Int #

xor :: Int -> Int -> Int #

complement :: Int -> Int #

shift :: Int -> Int -> Int #

rotate :: Int -> Int -> Int #

zeroBits :: Int #

bit :: Int -> Int #

setBit :: Int -> Int -> Int #

clearBit :: Int -> Int -> Int #

complementBit :: Int -> Int -> Int #

testBit :: Int -> Int -> Bool #

bitSizeMaybe :: Int -> Maybe Int #

bitSize :: Int -> Int #

isSigned :: Int -> Bool #

shiftL :: Int -> Int -> Int #

unsafeShiftL :: Int -> Int -> Int #

shiftR :: Int -> Int -> Int #

unsafeShiftR :: Int -> Int -> Int #

rotateL :: Int -> Int -> Int #

rotateR :: Int -> Int -> Int #

popCount :: Int -> Int #

FiniteBits Int

Since: base-4.6.0.0

Instance details

Defined in Data.Bits

PrimType Int 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int :: Nat #

PrimMemoryComparable Int 
Instance details

Defined in Basement.PrimType

Subtractive Int 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Int #

Methods

(-) :: Int -> Int -> Difference Int #

NFData Int 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int -> () #

Hashable Int 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int -> Int #

hash :: Int -> Int #

Prim Int 
Instance details

Defined in Data.Primitive.Types

Unbox Int 
Instance details

Defined in Data.Vector.Unboxed.Base

Pretty Int
>>> pretty (123 :: Int)
123
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Int -> Doc ann #

prettyList :: [Int] -> Doc ann #

Pretty Int 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

pretty :: Int -> Doc b #

prettyList :: [Int] -> Doc b #

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

Eq Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Methods

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

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

Ord Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

FiniteBits Int Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Bits Int Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Rational Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Lift Int 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int -> Q Exp #

liftTyped :: Int -> Q (TExp Int) #

Vector Vector Int 
Instance details

Defined in Data.Vector.Unboxed.Base

FunctorWithIndex Int []

The position in the list is available as the index.

Instance details

Defined in Control.Lens.Indexed

Methods

imap :: (Int -> a -> b) -> [a] -> [b] #

imapped :: IndexedSetter Int [a] [b] a b #

FunctorWithIndex Int ZipList

Same instance as for [].

Instance details

Defined in Control.Lens.Indexed

Methods

imap :: (Int -> a -> b) -> ZipList a -> ZipList b #

imapped :: IndexedSetter Int (ZipList a) (ZipList b) a b #

FunctorWithIndex Int NonEmpty 
Instance details

Defined in Control.Lens.Indexed

Methods

imap :: (Int -> a -> b) -> NonEmpty a -> NonEmpty b #

imapped :: IndexedSetter Int (NonEmpty a) (NonEmpty b) a b #

FunctorWithIndex Int IntMap 
Instance details

Defined in Control.Lens.Indexed

Methods

imap :: (Int -> a -> b) -> IntMap a -> IntMap b #

imapped :: IndexedSetter Int (IntMap a) (IntMap b) a b #

FunctorWithIndex Int Seq

The position in the Seq is available as the index.

Instance details

Defined in Control.Lens.Indexed

Methods

imap :: (Int -> a -> b) -> Seq a -> Seq b #

imapped :: IndexedSetter Int (Seq a) (Seq b) a b #

FunctorWithIndex Int Vector 
Instance details

Defined in Control.Lens.Indexed

Methods

imap :: (Int -> a -> b) -> Vector a -> Vector b #

imapped :: IndexedSetter Int (Vector a) (Vector b) a b #

FoldableWithIndex Int [] 
Instance details

Defined in Control.Lens.Indexed

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> [a] -> m #

ifolded :: IndexedFold Int [a] a #

ifoldr :: (Int -> a -> b -> b) -> b -> [a] -> b #

ifoldl :: (Int -> b -> a -> b) -> b -> [a] -> b #

ifoldr' :: (Int -> a -> b -> b) -> b -> [a] -> b #

ifoldl' :: (Int -> b -> a -> b) -> b -> [a] -> b #

FoldableWithIndex Int ZipList 
Instance details

Defined in Control.Lens.Indexed

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> ZipList a -> m #

ifolded :: IndexedFold Int (ZipList a) a #

ifoldr :: (Int -> a -> b -> b) -> b -> ZipList a -> b #

ifoldl :: (Int -> b -> a -> b) -> b -> ZipList a -> b #

ifoldr' :: (Int -> a -> b -> b) -> b -> ZipList a -> b #

ifoldl' :: (Int -> b -> a -> b) -> b -> ZipList a -> b #

FoldableWithIndex Int NonEmpty 
Instance details

Defined in Control.Lens.Indexed

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> NonEmpty a -> m #

ifolded :: IndexedFold Int (NonEmpty a) a #

ifoldr :: (Int -> a -> b -> b) -> b -> NonEmpty a -> b #

ifoldl :: (Int -> b -> a -> b) -> b -> NonEmpty a -> b #

ifoldr' :: (Int -> a -> b -> b) -> b -> NonEmpty a -> b #

ifoldl' :: (Int -> b -> a -> b) -> b -> NonEmpty a -> b #

FoldableWithIndex Int IntMap 
Instance details

Defined in Control.Lens.Indexed

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> IntMap a -> m #

ifolded :: IndexedFold Int (IntMap a) a #

ifoldr :: (Int -> a -> b -> b) -> b -> IntMap a -> b #

ifoldl :: (Int -> b -> a -> b) -> b -> IntMap a -> b #

ifoldr' :: (Int -> a -> b -> b) -> b -> IntMap a -> b #

ifoldl' :: (Int -> b -> a -> b) -> b -> IntMap a -> b #

FoldableWithIndex Int Seq 
Instance details

Defined in Control.Lens.Indexed

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> Seq a -> m #

ifolded :: IndexedFold Int (Seq a) a #

ifoldr :: (Int -> a -> b -> b) -> b -> Seq a -> b #

ifoldl :: (Int -> b -> a -> b) -> b -> Seq a -> b #

ifoldr' :: (Int -> a -> b -> b) -> b -> Seq a -> b #

ifoldl' :: (Int -> b -> a -> b) -> b -> Seq a -> b #

FoldableWithIndex Int Vector 
Instance details

Defined in Control.Lens.Indexed

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> Vector a -> m #

ifolded :: IndexedFold Int (Vector a) a #

ifoldr :: (Int -> a -> b -> b) -> b -> Vector a -> b #

ifoldl :: (Int -> b -> a -> b) -> b -> Vector a -> b #

ifoldr' :: (Int -> a -> b -> b) -> b -> Vector a -> b #

ifoldl' :: (Int -> b -> a -> b) -> b -> Vector a -> b #

TraversableWithIndex Int [] 
Instance details

Defined in Control.Lens.Indexed

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> [a] -> f [b] #

itraversed :: IndexedTraversal Int [a] [b] a b #

TraversableWithIndex Int ZipList 
Instance details

Defined in Control.Lens.Indexed

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> ZipList a -> f (ZipList b) #

itraversed :: IndexedTraversal Int (ZipList a) (ZipList b) a b #

TraversableWithIndex Int NonEmpty 
Instance details

Defined in Control.Lens.Indexed

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> NonEmpty a -> f (NonEmpty b) #

itraversed :: IndexedTraversal Int (NonEmpty a) (NonEmpty b) a b #

TraversableWithIndex Int IntMap 
Instance details

Defined in Control.Lens.Indexed

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> IntMap a -> f (IntMap b) #

itraversed :: IndexedTraversal Int (IntMap a) (IntMap b) a b #

TraversableWithIndex Int Seq 
Instance details

Defined in Control.Lens.Indexed

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> Seq a -> f (Seq b) #

itraversed :: IndexedTraversal Int (Seq a) (Seq b) a b #

TraversableWithIndex Int Vector 
Instance details

Defined in Control.Lens.Indexed

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> Vector a -> f (Vector b) #

itraversed :: IndexedTraversal Int (Vector a) (Vector b) a b #

TraverseMin Int IntMap 
Instance details

Defined in Control.Lens.Traversal

TraverseMax Int IntMap 
Instance details

Defined in Control.Lens.Traversal

MVector MVector Int 
Instance details

Defined in Data.Vector.Unboxed.Base

ToFloating Int Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

Lift Exp Int Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Int Source #

Methods

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

FromIntegral Int Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

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)

Generic1 (URec Int :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec Int) :: k -> Type #

Methods

from1 :: forall (a :: k0). URec Int a -> Rep1 (URec Int) a #

to1 :: forall (a :: k0). Rep1 (URec Int) a -> URec Int a #

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

Bounded (Exp Int) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Enum (Exp Int) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Integral (Exp Int) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Methods

quot :: Exp Int -> Exp Int -> Exp Int #

rem :: Exp Int -> Exp Int -> Exp Int #

div :: Exp Int -> Exp Int -> Exp Int #

mod :: Exp Int -> Exp Int -> Exp Int #

quotRem :: Exp Int -> Exp Int -> (Exp Int, Exp Int) #

divMod :: Exp Int -> Exp Int -> (Exp Int, Exp Int) #

toInteger :: Exp Int -> Integer #

Num (Exp Int) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Methods

(+) :: Exp Int -> Exp Int -> Exp Int #

(-) :: Exp Int -> Exp Int -> Exp Int #

(*) :: Exp Int -> Exp Int -> Exp Int #

negate :: Exp Int -> Exp Int #

abs :: Exp Int -> Exp Int #

signum :: Exp Int -> Exp Int #

fromInteger :: Integer -> Exp Int #

Foldable (UInt :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => UInt m -> m #

foldMap :: Monoid m => (a -> m) -> UInt a -> m #

foldMap' :: Monoid m => (a -> m) -> UInt a -> m #

foldr :: (a -> b -> b) -> b -> UInt a -> b #

foldr' :: (a -> b -> b) -> b -> UInt a -> b #

foldl :: (b -> a -> b) -> b -> UInt a -> b #

foldl' :: (b -> a -> b) -> b -> UInt a -> b #

foldr1 :: (a -> a -> a) -> UInt a -> a #

foldl1 :: (a -> a -> a) -> UInt a -> a #

toList :: UInt a -> [a] #

null :: UInt a -> Bool #

length :: UInt a -> Int #

elem :: Eq a => a -> UInt a -> Bool #

maximum :: Ord a => UInt a -> a #

minimum :: Ord a => UInt a -> a #

sum :: Num a => UInt a -> a #

product :: Num a => UInt a -> a #

Traversable (UInt :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UInt a -> f (UInt b) #

sequenceA :: Applicative f => UInt (f a) -> f (UInt a) #

mapM :: Monad m => (a -> m b) -> UInt a -> m (UInt b) #

sequence :: Monad m => UInt (m a) -> m (UInt 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)

FunctorWithIndex [Int] Tree 
Instance details

Defined in Control.Lens.Indexed

Methods

imap :: ([Int] -> a -> b) -> Tree a -> Tree b #

imapped :: IndexedSetter [Int] (Tree a) (Tree b) a b #

FoldableWithIndex [Int] Tree 
Instance details

Defined in Control.Lens.Indexed

Methods

ifoldMap :: Monoid m => ([Int] -> a -> m) -> Tree a -> m #

ifolded :: IndexedFold [Int] (Tree a) a #

ifoldr :: ([Int] -> a -> b -> b) -> b -> Tree a -> b #

ifoldl :: ([Int] -> b -> a -> b) -> b -> Tree a -> b #

ifoldr' :: ([Int] -> a -> b -> b) -> b -> Tree a -> b #

ifoldl' :: ([Int] -> b -> a -> b) -> b -> Tree a -> b #

TraversableWithIndex [Int] Tree 
Instance details

Defined in Control.Lens.Indexed

Methods

itraverse :: Applicative f => ([Int] -> a -> f b) -> Tree a -> f (Tree b) #

itraversed :: IndexedTraversal [Int] (Tree a) (Tree b) a b #

Bizarre (Indexed Int) Mafic 
Instance details

Defined in Control.Lens.Internal.Magma

Methods

bazaar :: Applicative f => Indexed Int a (f b) -> Mafic a b t -> f t #

Reifies Z Int 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy Z -> Int #

Reifies n Int => Reifies (D n :: Type) Int 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy (D n) -> Int #

Reifies n Int => Reifies (SD n :: Type) Int 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy (SD n) -> Int #

Reifies n Int => Reifies (PD n :: Type) Int 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy (PD n) -> 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)] #

Functor (URec Int :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec Int a -> URec Int b #

(<$) :: a -> URec Int b -> URec Int a #

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 #

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)

Eq (URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: URec Int p -> URec Int p -> Bool #

(/=) :: URec Int p -> URec Int p -> Bool #

Ord (URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec Int p -> URec Int p -> Ordering #

(<) :: URec Int p -> URec Int p -> Bool #

(<=) :: URec Int p -> URec Int p -> Bool #

(>) :: URec Int p -> URec Int p -> Bool #

(>=) :: URec Int p -> URec Int p -> Bool #

max :: URec Int p -> URec Int p -> URec Int p #

min :: URec Int p -> URec Int p -> URec Int p #

Show (URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Int p -> ShowS #

show :: URec Int p -> String #

showList :: [URec Int p] -> ShowS #

Generic (URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Int p) :: Type -> Type #

Methods

from :: URec Int p -> Rep (URec Int p) x #

to :: Rep (URec Int p) x -> URec Int p #

type PrimSize Int 
Instance details

Defined in Basement.PrimType

type PrimSize Int = 8
type Difference Int 
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Int 
Instance details

Defined in Basement.Nat

newtype Vector Int 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int = V_Int (Vector Int)
type Plain Int Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

type Plain Int = Int
data URec Int (p :: k)

Used for marking occurrences of Int#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

data URec Int (p :: k) = UInt {}
newtype MVector s Int 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int = MV_Int (MVector s Int)
type Rep1 (URec Int :: k -> Type) 
Instance details

Defined in GHC.Generics

type Rep1 (URec Int :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UInt" 'PrefixI 'True) (S1 ('MetaSel ('Just "uInt#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UInt :: k -> Type)))
type Item (Vector e) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Array

type Item (Vector e) = e
type SliceShape (sl :. Int) Source # 
Instance details

Defined in Data.Array.Accelerate.Sugar.Shape

type SliceShape (sl :. Int) = SliceShape sl
type CoSliceShape (sl :. Int) 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 Plain (ix :. Int) Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

type Plain (ix :. Int) = Plain ix :. Int
type Rep (URec Int p) 
Instance details

Defined in GHC.Generics

type Rep (URec Int p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UInt" 'PrefixI 'True) (S1 ('MetaSel ('Just "uInt#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UInt :: Type -> Type)))

data Int8 #

8-bit signed integer type

Instances

Instances details
Bounded Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

succ :: Int8 -> Int8 #

pred :: Int8 -> Int8 #

toEnum :: Int -> Int8 #

fromEnum :: Int8 -> Int #

enumFrom :: Int8 -> [Int8] #

enumFromThen :: Int8 -> Int8 -> [Int8] #

enumFromTo :: Int8 -> Int8 -> [Int8] #

enumFromThenTo :: Int8 -> Int8 -> Int8 -> [Int8] #

Eq Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

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

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

Integral Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

quot :: Int8 -> Int8 -> Int8 #

rem :: Int8 -> Int8 -> Int8 #

div :: Int8 -> Int8 -> Int8 #

mod :: Int8 -> Int8 -> Int8 #

quotRem :: Int8 -> Int8 -> (Int8, Int8) #

divMod :: Int8 -> Int8 -> (Int8, Int8) #

toInteger :: Int8 -> Integer #

Num Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(+) :: Int8 -> Int8 -> Int8 #

(-) :: Int8 -> Int8 -> Int8 #

(*) :: Int8 -> Int8 -> Int8 #

negate :: Int8 -> Int8 #

abs :: Int8 -> Int8 #

signum :: Int8 -> Int8 #

fromInteger :: Integer -> Int8 #

Ord Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int8 -> Int8 -> Ordering #

(<) :: Int8 -> Int8 -> Bool #

(<=) :: Int8 -> Int8 -> Bool #

(>) :: Int8 -> Int8 -> Bool #

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

max :: Int8 -> Int8 -> Int8 #

min :: Int8 -> Int8 -> Int8 #

Read Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int8 -> Rational #

Show Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int8 -> ShowS #

show :: Int8 -> String #

showList :: [Int8] -> ShowS #

Ix Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

range :: (Int8, Int8) -> [Int8] #

index :: (Int8, Int8) -> Int8 -> Int #

unsafeIndex :: (Int8, Int8) -> Int8 -> Int #

inRange :: (Int8, Int8) -> Int8 -> Bool #

rangeSize :: (Int8, Int8) -> Int #

unsafeRangeSize :: (Int8, Int8) -> Int #

PrintfArg Int8

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Int8

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int8 -> Int #

alignment :: Int8 -> Int #

peekElemOff :: Ptr Int8 -> Int -> IO Int8 #

pokeElemOff :: Ptr Int8 -> Int -> Int8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int8 #

pokeByteOff :: Ptr b -> Int -> Int8 -> IO () #

peek :: Ptr Int8 -> IO Int8 #

poke :: Ptr Int8 -> Int8 -> IO () #

Bits Int8

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int8

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

PrimType Int8 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int8 :: Nat #

PrimMemoryComparable Int8 
Instance details

Defined in Basement.PrimType

Subtractive Int8 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Int8 #

Methods

(-) :: Int8 -> Int8 -> Difference Int8 #

NFData Int8 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int8 -> () #

Hashable Int8 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int8 -> Int #

hash :: Int8 -> Int #

Prim Int8 
Instance details

Defined in Data.Primitive.Types

Unbox Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

Pretty Int8 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Int8 -> Doc ann #

prettyList :: [Int8] -> Doc ann #

Pretty Int8 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

pretty :: Int8 -> Doc b #

prettyList :: [Int8] -> Doc b #

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

Eq Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

FiniteBits Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Bits Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Rational Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Lift Int8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int8 -> Q Exp #

liftTyped :: Int8 -> Q (TExp Int8) #

Vector Vector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

ToFloating Int8 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int8 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int8 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

Lift Exp Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Int8 Source #

Methods

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

FromIntegral Int Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

Bounded (Exp Int8) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Enum (Exp Int8) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Integral (Exp Int8) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Num (Exp Int8) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

type PrimSize Int8 
Instance details

Defined in Basement.PrimType

type PrimSize Int8 = 1
type Difference Int8 
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Int8 
Instance details

Defined in Basement.Nat

type NatNumMaxBound Int8 = 127
newtype Vector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

type Plain Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

type Plain Int8 = Int8
newtype MVector s Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int8 = MV_Int8 (MVector s Int8)

data Int16 #

16-bit signed integer type

Instances

Instances details
Bounded Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Eq Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

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

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

Integral Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Num Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int16 -> Int16 -> Ordering #

(<) :: Int16 -> Int16 -> Bool #

(<=) :: Int16 -> Int16 -> Bool #

(>) :: Int16 -> Int16 -> Bool #

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

max :: Int16 -> Int16 -> Int16 #

min :: Int16 -> Int16 -> Int16 #

Read Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int16 -> Rational #

Show Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int16 -> ShowS #

show :: Int16 -> String #

showList :: [Int16] -> ShowS #

Ix Int16

Since: base-2.1

Instance details

Defined in GHC.Int

PrintfArg Int16

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Int16

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int16 -> Int #

alignment :: Int16 -> Int #

peekElemOff :: Ptr Int16 -> Int -> IO Int16 #

pokeElemOff :: Ptr Int16 -> Int -> Int16 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int16 #

pokeByteOff :: Ptr b -> Int -> Int16 -> IO () #

peek :: Ptr Int16 -> IO Int16 #

poke :: Ptr Int16 -> Int16 -> IO () #

Bits Int16

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int16

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

PrimType Int16 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int16 :: Nat #

PrimMemoryComparable Int16 
Instance details

Defined in Basement.PrimType

Subtractive Int16 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Int16 #

Methods

(-) :: Int16 -> Int16 -> Difference Int16 #

NFData Int16 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int16 -> () #

Hashable Int16 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int16 -> Int #

hash :: Int16 -> Int #

Prim Int16 
Instance details

Defined in Data.Primitive.Types

Unbox Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

Pretty Int16 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Int16 -> Doc ann #

prettyList :: [Int16] -> Doc ann #

Pretty Int16 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

pretty :: Int16 -> Doc b #

prettyList :: [Int16] -> Doc b #

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

Eq Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

FiniteBits Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Bits Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Rational Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Lift Int16 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int16 -> Q Exp #

liftTyped :: Int16 -> Q (TExp Int16) #

Vector Vector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

ToFloating Int16 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int16 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int16 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

Lift Exp Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Int16 Source #

Methods

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

FromIntegral Int Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

Bounded (Exp Int16) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Enum (Exp Int16) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Integral (Exp Int16) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Num (Exp Int16) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

type PrimSize Int16 
Instance details

Defined in Basement.PrimType

type PrimSize Int16 = 2
type Difference Int16 
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Int16 
Instance details

Defined in Basement.Nat

type NatNumMaxBound Int16 = 32767
newtype Vector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

type Plain Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

newtype MVector s Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

data Int32 #

32-bit signed integer type

Instances

Instances details
Bounded Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Eq Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

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

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

Integral Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Num Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int32 -> Int32 -> Ordering #

(<) :: Int32 -> Int32 -> Bool #

(<=) :: Int32 -> Int32 -> Bool #

(>) :: Int32 -> Int32 -> Bool #

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

max :: Int32 -> Int32 -> Int32 #

min :: Int32 -> Int32 -> Int32 #

Read Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int32 -> Rational #

Show Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int32 -> ShowS #

show :: Int32 -> String #

showList :: [Int32] -> ShowS #

Ix Int32

Since: base-2.1

Instance details

Defined in GHC.Int

PrintfArg Int32

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Int32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int32 -> Int #

alignment :: Int32 -> Int #

peekElemOff :: Ptr Int32 -> Int -> IO Int32 #

pokeElemOff :: Ptr Int32 -> Int -> Int32 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int32 #

pokeByteOff :: Ptr b -> Int -> Int32 -> IO () #

peek :: Ptr Int32 -> IO Int32 #

poke :: Ptr Int32 -> Int32 -> IO () #

Bits Int32

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int32

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

PrimType Int32 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int32 :: Nat #

PrimMemoryComparable Int32 
Instance details

Defined in Basement.PrimType

Subtractive Int32 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Int32 #

Methods

(-) :: Int32 -> Int32 -> Difference Int32 #

NFData Int32 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int32 -> () #

Hashable Int32 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int32 -> Int #

hash :: Int32 -> Int #

Prim Int32 
Instance details

Defined in Data.Primitive.Types

Unbox Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

Pretty Int32 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Int32 -> Doc ann #

prettyList :: [Int32] -> Doc ann #

Pretty Int32 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

pretty :: Int32 -> Doc b #

prettyList :: [Int32] -> Doc b #

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

Eq Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

FiniteBits Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Bits Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Rational Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Lift Int32 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int32 -> Q Exp #

liftTyped :: Int32 -> Q (TExp Int32) #

Vector Vector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

ToFloating Int32 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int32 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int32 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

Lift Exp Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Int32 Source #

Methods

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

FromIntegral Int Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

Bounded (Exp Int32) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Enum (Exp Int32) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Integral (Exp Int32) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Num (Exp Int32) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

type PrimSize Int32 
Instance details

Defined in Basement.PrimType

type PrimSize Int32 = 4
type Difference Int32 
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Int32 
Instance details

Defined in Basement.Nat

type NatNumMaxBound Int32 = 2147483647
newtype Vector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

type Plain Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

newtype MVector s Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

data Int64 #

64-bit signed integer type

Instances

Instances details
Bounded Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Eq Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

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

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

Integral Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Num Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int64 -> Int64 -> Ordering #

(<) :: Int64 -> Int64 -> Bool #

(<=) :: Int64 -> Int64 -> Bool #

(>) :: Int64 -> Int64 -> Bool #

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

max :: Int64 -> Int64 -> Int64 #

min :: Int64 -> Int64 -> Int64 #

Read Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int64 -> Rational #

Show Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int64 -> ShowS #

show :: Int64 -> String #

showList :: [Int64] -> ShowS #

Ix Int64

Since: base-2.1

Instance details

Defined in GHC.Int

PrintfArg Int64

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Int64

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int64 -> Int #

alignment :: Int64 -> Int #

peekElemOff :: Ptr Int64 -> Int -> IO Int64 #

pokeElemOff :: Ptr Int64 -> Int -> Int64 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int64 #

pokeByteOff :: Ptr b -> Int -> Int64 -> IO () #

peek :: Ptr Int64 -> IO Int64 #

poke :: Ptr Int64 -> Int64 -> IO () #

Bits Int64

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int64

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

PrimType Int64 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int64 :: Nat #

PrimMemoryComparable Int64 
Instance details

Defined in Basement.PrimType

Subtractive Int64 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Int64 #

Methods

(-) :: Int64 -> Int64 -> Difference Int64 #

NFData Int64 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int64 -> () #

Hashable Int64 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int64 -> Int #

hash :: Int64 -> Int #

Prim Int64 
Instance details

Defined in Data.Primitive.Types

Unbox Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

Pretty Int64 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Int64 -> Doc ann #

prettyList :: [Int64] -> Doc ann #

Pretty Int64 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

pretty :: Int64 -> Doc b #

prettyList :: [Int64] -> Doc b #

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

Eq Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

FiniteBits Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Bits Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Rational Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Lift Int64 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int64 -> Q Exp #

liftTyped :: Int64 -> Q (TExp Int64) #

Vector Vector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

ToFloating Int64 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int64 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int64 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

Lift Exp Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Int64 Source #

Methods

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

FromIntegral Int Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

Bounded (Exp Int64) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Enum (Exp Int64) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Integral (Exp Int64) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Num (Exp Int64) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

type PrimSize Int64 
Instance details

Defined in Basement.PrimType

type PrimSize Int64 = 8
type Difference Int64 
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Int64 
Instance details

Defined in Basement.Nat

type NatNumMaxBound Int64 = 9223372036854775807
newtype Vector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

type Plain Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

newtype MVector s Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

data Word #

A Word is an unsigned integral type, with the same size as Int.

Instances

Instances details
Bounded Word

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Word

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

succ :: Word -> Word #

pred :: Word -> Word #

toEnum :: Int -> Word #

fromEnum :: Word -> Int #

enumFrom :: Word -> [Word] #

enumFromThen :: Word -> Word -> [Word] #

enumFromTo :: Word -> Word -> [Word] #

enumFromThenTo :: Word -> Word -> Word -> [Word] #

Eq Word 
Instance details

Defined in GHC.Classes

Methods

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

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

Integral Word

Since: base-2.1

Instance details

Defined in GHC.Real

Methods

quot :: Word -> Word -> Word #

rem :: Word -> Word -> Word #

div :: Word -> Word -> Word #

mod :: Word -> Word -> Word #

quotRem :: Word -> Word -> (Word, Word) #

divMod :: Word -> Word -> (Word, Word) #

toInteger :: Word -> Integer #

Num Word

Since: base-2.1

Instance details

Defined in GHC.Num

Methods

(+) :: Word -> Word -> Word #

(-) :: Word -> Word -> Word #

(*) :: Word -> Word -> Word #

negate :: Word -> Word #

abs :: Word -> Word #

signum :: Word -> Word #

fromInteger :: Integer -> Word #

Ord Word 
Instance details

Defined in GHC.Classes

Methods

compare :: Word -> Word -> Ordering #

(<) :: Word -> Word -> Bool #

(<=) :: Word -> Word -> Bool #

(>) :: Word -> Word -> Bool #

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

max :: Word -> Word -> Word #

min :: Word -> Word -> Word #

Read Word

Since: base-4.5.0.0

Instance details

Defined in GHC.Read

Real Word

Since: base-2.1

Instance details

Defined in GHC.Real

Methods

toRational :: Word -> Rational #

Show Word

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Word -> ShowS #

show :: Word -> String #

showList :: [Word] -> ShowS #

Ix Word

Since: base-4.6.0.0

Instance details

Defined in GHC.Ix

Methods

range :: (Word, Word) -> [Word] #

index :: (Word, Word) -> Word -> Int #

unsafeIndex :: (Word, Word) -> Word -> Int #

inRange :: (Word, Word) -> Word -> Bool #

rangeSize :: (Word, Word) -> Int #

unsafeRangeSize :: (Word, Word) -> Int #

PrintfArg Word

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Word

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Word -> Int #

alignment :: Word -> Int #

peekElemOff :: Ptr Word -> Int -> IO Word #

pokeElemOff :: Ptr Word -> Int -> Word -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word #

pokeByteOff :: Ptr b -> Int -> Word -> IO () #

peek :: Ptr Word -> IO Word #

poke :: Ptr Word -> Word -> IO () #

Bits Word

Since: base-2.1

Instance details

Defined in Data.Bits

FiniteBits Word

Since: base-4.6.0.0

Instance details

Defined in Data.Bits

PrimType Word 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word :: Nat #

PrimMemoryComparable Word 
Instance details

Defined in Basement.PrimType

Subtractive Word 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Word #

Methods

(-) :: Word -> Word -> Difference Word #

NFData Word 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word -> () #

Hashable Word 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word -> Int #

hash :: Word -> Int #

Prim Word 
Instance details

Defined in Data.Primitive.Types

Unbox Word 
Instance details

Defined in Data.Vector.Unboxed.Base

Pretty Word 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Word -> Doc ann #

prettyList :: [Word] -> Doc ann #

Pretty Word 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

pretty :: Word -> Doc b #

prettyList :: [Word] -> Doc b #

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

Eq Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

FiniteBits Word Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Bits Word Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Rational Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Lift Word 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word -> Q Exp #

liftTyped :: Word -> Q (TExp Word) #

Vector Vector Word 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word 
Instance details

Defined in Data.Vector.Unboxed.Base

ToFloating Word Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

Lift Exp Word Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Word Source #

Methods

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

FromIntegral Int Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

Generic1 (URec Word :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec Word) :: k -> Type #

Methods

from1 :: forall (a :: k0). URec Word a -> Rep1 (URec Word) a #

to1 :: forall (a :: k0). Rep1 (URec Word) a -> URec Word a #

Bounded (Exp Word) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Enum (Exp Word) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Integral (Exp Word) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Num (Exp Word) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Foldable (UWord :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => UWord m -> m #

foldMap :: Monoid m => (a -> m) -> UWord a -> m #

foldMap' :: Monoid m => (a -> m) -> UWord a -> m #

foldr :: (a -> b -> b) -> b -> UWord a -> b #

foldr' :: (a -> b -> b) -> b -> UWord a -> b #

foldl :: (b -> a -> b) -> b -> UWord a -> b #

foldl' :: (b -> a -> b) -> b -> UWord a -> b #

foldr1 :: (a -> a -> a) -> UWord a -> a #

foldl1 :: (a -> a -> a) -> UWord a -> a #

toList :: UWord a -> [a] #

null :: UWord a -> Bool #

length :: UWord a -> Int #

elem :: Eq a => a -> UWord a -> Bool #

maximum :: Ord a => UWord a -> a #

minimum :: Ord a => UWord a -> a #

sum :: Num a => UWord a -> a #

product :: Num a => UWord a -> a #

Traversable (UWord :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UWord a -> f (UWord b) #

sequenceA :: Applicative f => UWord (f a) -> f (UWord a) #

mapM :: Monad m => (a -> m b) -> UWord a -> m (UWord b) #

sequence :: Monad m => UWord (m a) -> m (UWord a) #

Functor (URec Word :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec Word a -> URec Word b #

(<$) :: a -> URec Word b -> URec Word a #

Eq (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: URec Word p -> URec Word p -> Bool #

(/=) :: URec Word p -> URec Word p -> Bool #

Ord (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec Word p -> URec Word p -> Ordering #

(<) :: URec Word p -> URec Word p -> Bool #

(<=) :: URec Word p -> URec Word p -> Bool #

(>) :: URec Word p -> URec Word p -> Bool #

(>=) :: URec Word p -> URec Word p -> Bool #

max :: URec Word p -> URec Word p -> URec Word p #

min :: URec Word p -> URec Word p -> URec Word p #

Show (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Word p -> ShowS #

show :: URec Word p -> String #

showList :: [URec Word p] -> ShowS #

Generic (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Word p) :: Type -> Type #

Methods

from :: URec Word p -> Rep (URec Word p) x #

to :: Rep (URec Word p) x -> URec Word p #

type PrimSize Word 
Instance details

Defined in Basement.PrimType

type PrimSize Word = 8
type Difference Word 
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Word 
Instance details

Defined in Basement.Nat

newtype Vector Word 
Instance details

Defined in Data.Vector.Unboxed.Base

type Plain Word Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

type Plain Word = Word
data URec Word (p :: k)

Used for marking occurrences of Word#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

data URec Word (p :: k) = UWord {}
newtype MVector s Word 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word = MV_Word (MVector s Word)
type Rep1 (URec Word :: k -> Type) 
Instance details

Defined in GHC.Generics

type Rep1 (URec Word :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UWord" 'PrefixI 'True) (S1 ('MetaSel ('Just "uWord#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UWord :: k -> Type)))
type Rep (URec Word p) 
Instance details

Defined in GHC.Generics

type Rep (URec Word p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UWord" 'PrefixI 'True) (S1 ('MetaSel ('Just "uWord#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UWord :: Type -> Type)))

data Word8 #

8-bit unsigned integer type

Instances

Instances details
Bounded Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

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

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

Integral Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Num Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

compare :: Word8 -> Word8 -> Ordering #

(<) :: Word8 -> Word8 -> Bool #

(<=) :: Word8 -> Word8 -> Bool #

(>) :: Word8 -> Word8 -> Bool #

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

max :: Word8 -> Word8 -> Word8 #

min :: Word8 -> Word8 -> Word8 #

Read Word8

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

toRational :: Word8 -> Rational #

Show Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Ix Word8

Since: base-2.1

Instance details

Defined in GHC.Word

PrintfArg Word8

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Word8

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Word8 -> Int #

alignment :: Word8 -> Int #

peekElemOff :: Ptr Word8 -> Int -> IO Word8 #

pokeElemOff :: Ptr Word8 -> Int -> Word8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word8 #

pokeByteOff :: Ptr b -> Int -> Word8 -> IO () #

peek :: Ptr Word8 -> IO Word8 #

poke :: Ptr Word8 -> Word8 -> IO () #

Bits Word8

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word8

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

PrimType Word8 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word8 :: Nat #

PrimMemoryComparable Word8 
Instance details

Defined in Basement.PrimType

Subtractive Word8 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Word8 #

Methods

(-) :: Word8 -> Word8 -> Difference Word8 #

NFData Word8 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word8 -> () #

Hashable Word8 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word8 -> Int #

hash :: Word8 -> Int #

Prim Word8 
Instance details

Defined in Data.Primitive.Types

Unbox Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

Pretty Word8 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Word8 -> Doc ann #

prettyList :: [Word8] -> Doc ann #

Pretty Word8 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

pretty :: Word8 -> Doc b #

prettyList :: [Word8] -> Doc b #

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

Eq Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

FiniteBits Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Bits Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Rational Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Lift Word8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word8 -> Q Exp #

liftTyped :: Word8 -> Q (TExp Word8) #

Vector Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

ToFloating Word8 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word8 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word8 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

Lift Exp Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Word8 Source #

Methods

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

FromIntegral Int Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

Cons ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

Cons ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

Snoc ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

Snoc ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

Bounded (Exp Word8) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Enum (Exp Word8) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Integral (Exp Word8) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Num (Exp Word8) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

type PrimSize Word8 
Instance details

Defined in Basement.PrimType

type PrimSize Word8 = 1
type Difference Word8 
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Word8 
Instance details

Defined in Basement.Nat

newtype Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

type Plain Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

newtype MVector s Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

data Word16 #

16-bit unsigned integer type

Instances

Instances details
Bounded Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

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

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

Integral Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Num Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word16

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word16

Since: base-2.1

Instance details

Defined in GHC.Word

PrintfArg Word16

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Word16

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word16

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word16

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

PrimType Word16 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word16 :: Nat #

PrimMemoryComparable Word16 
Instance details

Defined in Basement.PrimType

Subtractive Word16 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Word16 #

NFData Word16 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word16 -> () #

Hashable Word16 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word16 -> Int #

hash :: Word16 -> Int #

Prim Word16 
Instance details

Defined in Data.Primitive.Types

Unbox Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

Pretty Word16 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Word16 -> Doc ann #

prettyList :: [Word16] -> Doc ann #

Pretty Word16 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

pretty :: Word16 -> Doc b #

prettyList :: [Word16] -> Doc b #

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

Eq Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

FiniteBits Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Bits Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Rational Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Lift Word16 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word16 -> Q Exp #

liftTyped :: Word16 -> Q (TExp Word16) #

Vector Vector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

ToFloating Word16 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word16 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word16 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

Lift Exp Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Word16 Source #

Methods

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

FromIntegral Int Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

Bounded (Exp Word16) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Enum (Exp Word16) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Integral (Exp Word16) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Num (Exp Word16) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

type PrimSize Word16 
Instance details

Defined in Basement.PrimType

type PrimSize Word16 = 2
type Difference Word16 
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Word16 
Instance details

Defined in Basement.Nat

type NatNumMaxBound Word16 = 65535
newtype Vector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

type Plain Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

newtype MVector s Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

data Word32 #

32-bit unsigned integer type

Instances

Instances details
Bounded Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

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

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

Integral Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Num Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word32

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word32

Since: base-2.1

Instance details

Defined in GHC.Word

PrintfArg Word32

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Word32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word32

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word32

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

PrimType Word32 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word32 :: Nat #

PrimMemoryComparable Word32 
Instance details

Defined in Basement.PrimType

Subtractive Word32 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Word32 #

NFData Word32 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word32 -> () #

Hashable Word32 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word32 -> Int #

hash :: Word32 -> Int #

Prim Word32 
Instance details

Defined in Data.Primitive.Types

Unbox Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

Pretty Word32 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Word32 -> Doc ann #

prettyList :: [Word32] -> Doc ann #

Pretty Word32 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

pretty :: Word32 -> Doc b #

prettyList :: [Word32] -> Doc b #

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

Eq Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

FiniteBits Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Bits Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Rational Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Lift Word32 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word32 -> Q Exp #

liftTyped :: Word32 -> Q (TExp Word32) #

Vector Vector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

ToFloating Word32 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word32 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word32 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

Lift Exp Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Word32 Source #

Methods

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

FromIntegral Int Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

Bounded (Exp Word32) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Enum (Exp Word32) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Integral (Exp Word32) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Num (Exp Word32) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

type PrimSize Word32 
Instance details

Defined in Basement.PrimType

type PrimSize Word32 = 4
type Difference Word32 
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Word32 
Instance details

Defined in Basement.Nat

type NatNumMaxBound Word32 = 4294967295
newtype Vector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

type Plain Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

newtype MVector s Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

data Word64 #

64-bit unsigned integer type

Instances

Instances details
Bounded Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

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

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

Integral Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Num Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word64

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word64

Since: base-2.1

Instance details

Defined in GHC.Word

PrintfArg Word64

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Word64

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word64

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word64

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

PrimType Word64 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word64 :: Nat #

PrimMemoryComparable Word64 
Instance details

Defined in Basement.PrimType

Subtractive Word64 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Word64 #

NFData Word64 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word64 -> () #

Hashable Word64 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word64 -> Int #

hash :: Word64 -> Int #

Prim Word64 
Instance details

Defined in Data.Primitive.Types

Unbox Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

Pretty Word64 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Word64 -> Doc ann #

prettyList :: [Word64] -> Doc ann #

Pretty Word64 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

pretty :: Word64 -> Doc b #

prettyList :: [Word64] -> Doc b #

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

Eq Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

FiniteBits Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Bits Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Rational Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Lift Word64 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word64 -> Q Exp #

liftTyped :: Word64 -> Q (TExp Word64) #

Vector Vector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

ToFloating Word64 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word64 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word64 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

Lift Exp Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Word64 Source #

Methods

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

FromIntegral Int Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Int Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Word Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

Bounded (Exp Word64) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Enum (Exp Word64) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Integral (Exp Word64) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Num (Exp Word64) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

type PrimSize Word64 
Instance details

Defined in Basement.PrimType

type PrimSize Word64 = 8
type Difference Word64 
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Word64 
Instance details

Defined in Basement.Nat

type NatNumMaxBound Word64 = 18446744073709551615
newtype Vector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

type Plain Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

newtype MVector s Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Half #

Constructors

Half 

Fields

Instances

Instances details
Eq Half 
Instance details

Defined in Numeric.Half

Methods

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

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

Floating Half 
Instance details

Defined in Numeric.Half

Methods

pi :: Half #

exp :: Half -> Half #

log :: Half -> Half #

sqrt :: Half -> Half #

(**) :: Half -> Half -> Half #

logBase :: Half -> Half -> Half #

sin :: Half -> Half #

cos :: Half -> Half #

tan :: Half -> Half #

asin :: Half -> Half #

acos :: Half -> Half #

atan :: Half -> Half #

sinh :: Half -> Half #

cosh :: Half -> Half #

tanh :: Half -> Half #

asinh :: Half -> Half #

acosh :: Half -> Half #

atanh :: Half -> Half #

log1p :: Half -> Half #

expm1 :: Half -> Half #

log1pexp :: Half -> Half #

log1mexp :: Half -> Half #

Fractional Half 
Instance details

Defined in Numeric.Half

Methods

(/) :: Half -> Half -> Half #

recip :: Half -> Half #

fromRational :: Rational -> Half #

Num Half 
Instance details

Defined in Numeric.Half

Methods

(+) :: Half -> Half -> Half #

(-) :: Half -> Half -> Half #

(*) :: Half -> Half -> Half #

negate :: Half -> Half #

abs :: Half -> Half #

signum :: Half -> Half #

fromInteger :: Integer -> Half #

Ord Half 
Instance details

Defined in Numeric.Half

Methods

compare :: Half -> Half -> Ordering #

(<) :: Half -> Half -> Bool #

(<=) :: Half -> Half -> Bool #

(>) :: Half -> Half -> Bool #

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

max :: Half -> Half -> Half #

min :: Half -> Half -> Half #

Read Half 
Instance details

Defined in Numeric.Half

Real Half 
Instance details

Defined in Numeric.Half

Methods

toRational :: Half -> Rational #

RealFloat Half 
Instance details

Defined in Numeric.Half

RealFrac Half 
Instance details

Defined in Numeric.Half

Methods

properFraction :: Integral b => Half -> (b, Half) #

truncate :: Integral b => Half -> b #

round :: Integral b => Half -> b #

ceiling :: Integral b => Half -> b #

floor :: Integral b => Half -> b #

Show Half 
Instance details

Defined in Numeric.Half

Methods

showsPrec :: Int -> Half -> ShowS #

show :: Half -> String #

showList :: [Half] -> ShowS #

Generic Half 
Instance details

Defined in Numeric.Half

Associated Types

type Rep Half :: Type -> Type #

Methods

from :: Half -> Rep Half x #

to :: Rep Half x -> Half #

Storable Half 
Instance details

Defined in Numeric.Half

Methods

sizeOf :: Half -> Int #

alignment :: Half -> Int #

peekElemOff :: Ptr Half -> Int -> IO Half #

pokeElemOff :: Ptr Half -> Int -> Half -> IO () #

peekByteOff :: Ptr b -> Int -> IO Half #

pokeByteOff :: Ptr b -> Int -> Half -> IO () #

peek :: Ptr Half -> IO Half #

poke :: Ptr Half -> Half -> IO () #

NFData Half 
Instance details

Defined in Numeric.Half

Methods

rnf :: Half -> () #

Prim Half Source # 
Instance details

Defined in Data.Array.Accelerate.Orphans

RealFrac Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.RealFrac

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

Eq Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

RealFloat Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.RealFloat

Rational Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Lift Half 
Instance details

Defined in Numeric.Half

Methods

lift :: Half -> Q Exp #

liftTyped :: Half -> Q (TExp Half) #

ToFloating Double Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Float Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int8 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int16 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int32 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int64 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word8 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word16 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word32 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word64 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Half Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Half Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Half Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

Lift Exp Half Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Half Source #

Methods

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

FromIntegral Int Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

Enum (Exp Half) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Floating (Exp Half) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Floating

Fractional (Exp Half) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Fractional

Num (Exp Half) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

type Rep Half 
Instance details

Defined in Numeric.Half

type Rep Half = D1 ('MetaData "Half" "Numeric.Half" "half-0.3-5I6Y1Z6OYBD6TOLu4NSPvX" 'True) (C1 ('MetaCons "Half" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHalf") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CUShort)))
type Plain Half Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

type Plain Half = Half

data Float #

Single-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE single-precision type.

Instances

Instances details
Eq Float

Note that due to the presence of NaN, Float's Eq instance does not satisfy reflexivity.

>>> 0/0 == (0/0 :: Float)
False

Also note that Float's Eq instance does not satisfy substitutivity:

>>> 0 == (-0 :: Float)
True
>>> recip 0 == recip (-0 :: Float)
False
Instance details

Defined in GHC.Classes

Methods

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

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

Floating Float

Since: base-2.1

Instance details

Defined in GHC.Float

Ord Float

Note that due to the presence of NaN, Float's Ord instance does not satisfy reflexivity.

>>> 0/0 <= (0/0 :: Float)
False

Also note that, due to the same, Ord's operator interactions are not respected by Float's instance:

>>> (0/0 :: Float) > 1
False
>>> compare (0/0 :: Float) 1
GT
Instance details

Defined in GHC.Classes

Methods

compare :: Float -> Float -> Ordering #

(<) :: Float -> Float -> Bool #

(<=) :: Float -> Float -> Bool #

(>) :: Float -> Float -> Bool #

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

max :: Float -> Float -> Float #

min :: Float -> Float -> Float #

Read Float

Since: base-2.1

Instance details

Defined in GHC.Read

RealFloat Float

Since: base-2.1

Instance details

Defined in GHC.Float

PrintfArg Float

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Float

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Float -> Int #

alignment :: Float -> Int #

peekElemOff :: Ptr Float -> Int -> IO Float #

pokeElemOff :: Ptr Float -> Int -> Float -> IO () #

peekByteOff :: Ptr b -> Int -> IO Float #

pokeByteOff :: Ptr b -> Int -> Float -> IO () #

peek :: Ptr Float -> IO Float #

poke :: Ptr Float -> Float -> IO () #

PrimType Float 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Float :: Nat #

Subtractive Float 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Float #

Methods

(-) :: Float -> Float -> Difference Float #

NFData Float 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Float -> () #

Hashable Float

Note: prior to hashable-1.3.0.0, hash 0.0 /= hash (-0.0)

The hash of NaN is not well defined.

Since: hashable-1.3.0.0

Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Float -> Int #

hash :: Float -> Int #

Prim Float 
Instance details

Defined in Data.Primitive.Types

Unbox Float 
Instance details

Defined in Data.Vector.Unboxed.Base

Pretty Float
>>> pretty (pi :: Float)
3.1415927
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Float -> Doc ann #

prettyList :: [Float] -> Doc ann #

Pretty Float 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

pretty :: Float -> Doc b #

prettyList :: [Float] -> Doc b #

RealFrac Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.RealFrac

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

Eq Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

RealFloat Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.RealFloat

Rational Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Lift Float 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Float -> Q Exp #

liftTyped :: Float -> Q (TExp Float) #

Vector Vector Float 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Float 
Instance details

Defined in Data.Vector.Unboxed.Base

ToFloating Double Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Float Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Float Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Float Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int8 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int16 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int32 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int64 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word8 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word16 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word32 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word64 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Half Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

Lift Exp Float Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Float Source #

Methods

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

FromIntegral Int Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

Generic1 (URec Float :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec Float) :: k -> Type #

Methods

from1 :: forall (a :: k0). URec Float a -> Rep1 (URec Float) a #

to1 :: forall (a :: k0). Rep1 (URec Float) a -> URec Float a #

Enum (Exp Float) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Floating (Exp Float) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Floating

Fractional (Exp Float) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Fractional

Num (Exp Float) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Foldable (UFloat :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => UFloat m -> m #

foldMap :: Monoid m => (a -> m) -> UFloat a -> m #

foldMap' :: Monoid m => (a -> m) -> UFloat a -> m #

foldr :: (a -> b -> b) -> b -> UFloat a -> b #

foldr' :: (a -> b -> b) -> b -> UFloat a -> b #

foldl :: (b -> a -> b) -> b -> UFloat a -> b #

foldl' :: (b -> a -> b) -> b -> UFloat a -> b #

foldr1 :: (a -> a -> a) -> UFloat a -> a #

foldl1 :: (a -> a -> a) -> UFloat a -> a #

toList :: UFloat a -> [a] #

null :: UFloat a -> Bool #

length :: UFloat a -> Int #

elem :: Eq a => a -> UFloat a -> Bool #

maximum :: Ord a => UFloat a -> a #

minimum :: Ord a => UFloat a -> a #

sum :: Num a => UFloat a -> a #

product :: Num a => UFloat a -> a #

Traversable (UFloat :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UFloat a -> f (UFloat b) #

sequenceA :: Applicative f => UFloat (f a) -> f (UFloat a) #

mapM :: Monad m => (a -> m b) -> UFloat a -> m (UFloat b) #

sequence :: Monad m => UFloat (m a) -> m (UFloat a) #

Functor (URec Float :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec Float a -> URec Float b #

(<$) :: a -> URec Float b -> URec Float a #

Eq (URec Float p) 
Instance details

Defined in GHC.Generics

Methods

(==) :: URec Float p -> URec Float p -> Bool #

(/=) :: URec Float p -> URec Float p -> Bool #

Ord (URec Float p) 
Instance details

Defined in GHC.Generics

Methods

compare :: URec Float p -> URec Float p -> Ordering #

(<) :: URec Float p -> URec Float p -> Bool #

(<=) :: URec Float p -> URec Float p -> Bool #

(>) :: URec Float p -> URec Float p -> Bool #

(>=) :: URec Float p -> URec Float p -> Bool #

max :: URec Float p -> URec Float p -> URec Float p #

min :: URec Float p -> URec Float p -> URec Float p #

Show (URec Float p) 
Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Float p -> ShowS #

show :: URec Float p -> String #

showList :: [URec Float p] -> ShowS #

Generic (URec Float p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Float p) :: Type -> Type #

Methods

from :: URec Float p -> Rep (URec Float p) x #

to :: Rep (URec Float p) x -> URec Float p #

type PrimSize Float 
Instance details

Defined in Basement.PrimType

type PrimSize Float = 4
type Difference Float 
Instance details

Defined in Basement.Numerical.Subtractive

newtype Vector Float 
Instance details

Defined in Data.Vector.Unboxed.Base

type Plain Float Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

data URec Float (p :: k)

Used for marking occurrences of Float#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

data URec Float (p :: k) = UFloat {}
newtype MVector s Float 
Instance details

Defined in Data.Vector.Unboxed.Base

type Rep1 (URec Float :: k -> Type) 
Instance details

Defined in GHC.Generics

type Rep1 (URec Float :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UFloat" 'PrefixI 'True) (S1 ('MetaSel ('Just "uFloat#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UFloat :: k -> Type)))
type Rep (URec Float p) 
Instance details

Defined in GHC.Generics

type Rep (URec Float p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UFloat" 'PrefixI 'True) (S1 ('MetaSel ('Just "uFloat#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UFloat :: Type -> Type)))

data Double #

Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.

Instances

Instances details
Eq Double

Note that due to the presence of NaN, Double's Eq instance does not satisfy reflexivity.

>>> 0/0 == (0/0 :: Double)
False

Also note that Double's Eq instance does not satisfy substitutivity:

>>> 0 == (-0 :: Double)
True
>>> recip 0 == recip (-0 :: Double)
False
Instance details

Defined in GHC.Classes

Methods

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

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

Floating Double

Since: base-2.1

Instance details

Defined in GHC.Float

Ord Double

Note that due to the presence of NaN, Double's Ord instance does not satisfy reflexivity.

>>> 0/0 <= (0/0 :: Double)
False

Also note that, due to the same, Ord's operator interactions are not respected by Double's instance:

>>> (0/0 :: Double) > 1
False
>>> compare (0/0 :: Double) 1
GT
Instance details

Defined in GHC.Classes

Read Double

Since: base-2.1

Instance details

Defined in GHC.Read

RealFloat Double

Since: base-2.1

Instance details

Defined in GHC.Float

PrintfArg Double

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Double

Since: base-2.1

Instance details

Defined in Foreign.Storable

PrimType Double 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Double :: Nat #

Subtractive Double 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Double #

NFData Double 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Double -> () #

Hashable Double

Note: prior to hashable-1.3.0.0, hash 0.0 /= hash (-0.0)

The hash of NaN is not well defined.

Since: hashable-1.3.0.0

Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Double -> Int #

hash :: Double -> Int #

Prim Double 
Instance details

Defined in Data.Primitive.Types

Unbox Double 
Instance details

Defined in Data.Vector.Unboxed.Base

Pretty Double
>>> pretty (exp 1 :: Double)
2.71828182845904...
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Double -> Doc ann #

prettyList :: [Double] -> Doc ann #

Pretty Double 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

pretty :: Double -> Doc b #

prettyList :: [Double] -> Doc b #

RealFrac Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.RealFrac

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

Eq Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

RealFloat Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.RealFloat

Rational Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Rational

Lift Double 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Double -> Q Exp #

liftTyped :: Double -> Q (TExp Double) #

Vector Vector Double 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Double 
Instance details

Defined in Data.Vector.Unboxed.Base

ToFloating Double Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Double Float Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Double Half Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Float Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int8 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int16 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int32 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Int64 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word8 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word16 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word32 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Word64 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

ToFloating Half Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.ToFloating

Lift Exp Double Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Double Source #

Methods

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

FromIntegral Int Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int8 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int16 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int32 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Int64 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word8 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word16 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word32 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

FromIntegral Word64 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.FromIntegral

Generic1 (URec Double :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec Double) :: k -> Type #

Methods

from1 :: forall (a :: k0). URec Double a -> Rep1 (URec Double) a #

to1 :: forall (a :: k0). Rep1 (URec Double) a -> URec Double a #

Enum (Exp Double) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Floating (Exp Double) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Floating

Fractional (Exp Double) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Fractional

Num (Exp Double) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

Foldable (UDouble :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => UDouble m -> m #

foldMap :: Monoid m => (a -> m) -> UDouble a -> m #

foldMap' :: Monoid m => (a -> m) -> UDouble a -> m #

foldr :: (a -> b -> b) -> b -> UDouble a -> b #

foldr' :: (a -> b -> b) -> b -> UDouble a -> b #

foldl :: (b -> a -> b) -> b -> UDouble a -> b #

foldl' :: (b -> a -> b) -> b -> UDouble a -> b #

foldr1 :: (a -> a -> a) -> UDouble a -> a #

foldl1 :: (a -> a -> a) -> UDouble a -> a #

toList :: UDouble a -> [a] #

null :: UDouble a -> Bool #

length :: UDouble a -> Int #

elem :: Eq a => a -> UDouble a -> Bool #

maximum :: Ord a => UDouble a -> a #

minimum :: Ord a => UDouble a -> a #

sum :: Num a => UDouble a -> a #

product :: Num a => UDouble a -> a #

Traversable (UDouble :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UDouble a -> f (UDouble b) #

sequenceA :: Applicative f => UDouble (f a) -> f (UDouble a) #

mapM :: Monad m => (a -> m b) -> UDouble a -> m (UDouble b) #

sequence :: Monad m => UDouble (m a) -> m (UDouble a) #

Functor (URec Double :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec Double a -> URec Double b #

(<$) :: a -> URec Double b -> URec Double a #

Eq (URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: URec Double p -> URec Double p -> Bool #

(/=) :: URec Double p -> URec Double p -> Bool #

Ord (URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec Double p -> URec Double p -> Ordering #

(<) :: URec Double p -> URec Double p -> Bool #

(<=) :: URec Double p -> URec Double p -> Bool #

(>) :: URec Double p -> URec Double p -> Bool #

(>=) :: URec Double p -> URec Double p -> Bool #

max :: URec Double p -> URec Double p -> URec Double p #

min :: URec Double p -> URec Double p -> URec Double p #

Show (URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Double p -> ShowS #

show :: URec Double p -> String #

showList :: [URec Double p] -> ShowS #

Generic (URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Double p) :: Type -> Type #

Methods

from :: URec Double p -> Rep (URec Double p) x #

to :: Rep (URec Double p) x -> URec Double p #

type PrimSize Double 
Instance details

Defined in Basement.PrimType

type PrimSize Double = 8
type Difference Double 
Instance details

Defined in Basement.Numerical.Subtractive

newtype Vector Double 
Instance details

Defined in Data.Vector.Unboxed.Base

type Plain Double Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

data URec Double (p :: k)

Used for marking occurrences of Double#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

data URec Double (p :: k) = UDouble {}
newtype MVector s Double 
Instance details

Defined in Data.Vector.Unboxed.Base

type Rep1 (URec Double :: k -> Type) 
Instance details

Defined in GHC.Generics

type Rep1 (URec Double :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UDouble" 'PrefixI 'True) (S1 ('MetaSel ('Just "uDouble#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UDouble :: k -> Type)))
type Rep (URec Double p) 
Instance details

Defined in GHC.Generics

type Rep (URec Double p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UDouble" 'PrefixI 'True) (S1 ('MetaSel ('Just "uDouble#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UDouble :: Type -> Type)))

data Bool #

Constructors

False 
True 

Instances

Instances details
Bounded Bool

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Bool

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

succ :: Bool -> Bool #

pred :: Bool -> Bool #

toEnum :: Int -> Bool #

fromEnum :: Bool -> Int #

enumFrom :: Bool -> [Bool] #

enumFromThen :: Bool -> Bool -> [Bool] #

enumFromTo :: Bool -> Bool -> [Bool] #

enumFromThenTo :: Bool -> Bool -> Bool -> [Bool] #

Eq Bool 
Instance details

Defined in GHC.Classes

Methods

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

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

Ord Bool 
Instance details

Defined in GHC.Classes

Methods

compare :: Bool -> Bool -> Ordering #

(<) :: Bool -> Bool -> Bool #

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

(>) :: Bool -> Bool -> Bool #

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

max :: Bool -> Bool -> Bool #

min :: Bool -> Bool -> Bool #

Read Bool

Since: base-2.1

Instance details

Defined in GHC.Read

Show Bool

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Bool -> ShowS #

show :: Bool -> String #

showList :: [Bool] -> ShowS #

Ix Bool

Since: base-2.1

Instance details

Defined in GHC.Ix

Methods

range :: (Bool, Bool) -> [Bool] #

index :: (Bool, Bool) -> Bool -> Int #

unsafeIndex :: (Bool, Bool) -> Bool -> Int #

inRange :: (Bool, Bool) -> Bool -> Bool #

rangeSize :: (Bool, Bool) -> Int #

unsafeRangeSize :: (Bool, Bool) -> Int #

Generic Bool

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Bool :: Type -> Type #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Storable Bool

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Bool -> Int #

alignment :: Bool -> Int #

peekElemOff :: Ptr Bool -> Int -> IO Bool #

pokeElemOff :: Ptr Bool -> Int -> Bool -> IO () #

peekByteOff :: Ptr b -> Int -> IO Bool #

pokeByteOff :: Ptr b -> Int -> Bool -> IO () #

peek :: Ptr Bool -> IO Bool #

poke :: Ptr Bool -> Bool -> IO () #

Bits Bool

Interpret Bool as 1-bit bit-field

Since: base-4.7.0.0

Instance details

Defined in Data.Bits

FiniteBits Bool

Since: base-4.7.0.0

Instance details

Defined in Data.Bits

NFData Bool 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Bool -> () #

Hashable Bool 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Bool -> Int #

hash :: Bool -> Int #

Unbox Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

Pretty Bool
>>> pretty True
True
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Bool -> Doc ann #

prettyList :: [Bool] -> Doc ann #

Pretty Bool 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

pretty :: Bool -> Doc b #

prettyList :: [Bool] -> Doc b #

SingKind Bool

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type DemoteRep Bool

Methods

fromSing :: forall (a :: Bool). Sing a -> DemoteRep Bool

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

Eq Bool Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

FiniteBits Bool Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Bits Bool Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Lift Bool 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Bool -> Q Exp #

liftTyped :: Bool -> Q (TExp Bool) #

Vector Vector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

SingI 'False

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing 'False

SingI 'True

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing 'True

Lift Exp Bool Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Bool Source #

Methods

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

Bounded (Exp Bool) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

type Rep Bool 
Instance details

Defined in GHC.Generics

type Rep Bool = D1 ('MetaData "Bool" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "False" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "True" 'PrefixI 'False) (U1 :: Type -> Type))
newtype Vector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

type DemoteRep Bool 
Instance details

Defined in GHC.Generics

type DemoteRep Bool = Bool
data Sing (a :: Bool) 
Instance details

Defined in GHC.Generics

data Sing (a :: Bool) where
type Plain Bool Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

type Plain Bool = Bool
newtype MVector s Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Bool = MV_Bool (MVector s Word8)

data Maybe a #

The Maybe type encapsulates an optional value. A value of type Maybe a either contains a value of type a (represented as Just a), or it is empty (represented as Nothing). Using Maybe is a good way to deal with errors or exceptional cases without resorting to drastic measures such as error.

The Maybe type is also a monad. It is a simple kind of error monad, where all errors are represented by Nothing. A richer error monad can be built using the Either type.

Constructors

Nothing 
Just a 

Instances

Instances details
Monad Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b #

(>>) :: Maybe a -> Maybe b -> Maybe b #

return :: a -> Maybe a #

Functor Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

fmap :: (a -> b) -> Maybe a -> Maybe b #

(<$) :: a -> Maybe b -> Maybe a #

MonadFix Maybe

Since: base-2.1

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Maybe a) -> Maybe a #

MonadFail Maybe

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fail

Methods

fail :: String -> Maybe a #

Applicative Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

pure :: a -> Maybe a #

(<*>) :: Maybe (a -> b) -> Maybe a -> Maybe b #

liftA2 :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c #

(*>) :: Maybe a -> Maybe b -> Maybe b #

(<*) :: Maybe a -> Maybe b -> Maybe a #

Foldable Maybe

Since: base-2.1

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Maybe m -> m #

foldMap :: Monoid m => (a -> m) -> Maybe a -> m #

foldMap' :: Monoid m => (a -> m) -> Maybe a -> m #

foldr :: (a -> b -> b) -> b -> Maybe a -> b #

foldr' :: (a -> b -> b) -> b -> Maybe a -> b #

foldl :: (b -> a -> b) -> b -> Maybe a -> b #

foldl' :: (b -> a -> b) -> b -> Maybe a -> b #

foldr1 :: (a -> a -> a) -> Maybe a -> a #

foldl1 :: (a -> a -> a) -> Maybe a -> a #

toList :: Maybe a -> [a] #

null :: Maybe a -> Bool #

length :: Maybe a -> Int #

elem :: Eq a => a -> Maybe a -> Bool #

maximum :: Ord a => Maybe a -> a #

minimum :: Ord a => Maybe a -> a #

sum :: Num a => Maybe a -> a #

product :: Num a => Maybe a -> a #

Traversable Maybe

Since: base-2.1

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Maybe a -> f (Maybe b) #

sequenceA :: Applicative f => Maybe (f a) -> f (Maybe a) #

mapM :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b) #

sequence :: Monad m => Maybe (m a) -> m (Maybe a) #

Eq1 Maybe

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Maybe a -> Maybe b -> Bool #

Ord1 Maybe

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Maybe a -> Maybe b -> Ordering #

Read1 Maybe

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Maybe a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Maybe a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Maybe a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Maybe a] #

Show1 Maybe

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Maybe a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Maybe a] -> ShowS #

Alternative Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

empty :: Maybe a #

(<|>) :: Maybe a -> Maybe a -> Maybe a #

some :: Maybe a -> Maybe [a] #

many :: Maybe a -> Maybe [a] #

MonadPlus Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mzero :: Maybe a #

mplus :: Maybe a -> Maybe a -> Maybe a #

MonadFailure Maybe 
Instance details

Defined in Basement.Monad

Associated Types

type Failure Maybe #

Methods

mFail :: Failure Maybe -> Maybe () #

MonadThrow Maybe 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> Maybe a #

NFData1 Maybe

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Maybe a -> () #

Hashable1 Maybe 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Maybe a -> Int #

Functor Maybe Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Maybe

Methods

fmap :: (Elt a, Elt b, Elt (Maybe a), Elt (Maybe b)) => (Exp a -> Exp b) -> Exp (Maybe a) -> Exp (Maybe b) Source #

(<$) :: (Elt a, Elt b, Elt (Maybe a), Elt (Maybe b)) => Exp a -> Exp (Maybe b) -> Exp (Maybe a) Source #

MonadBaseControl Maybe Maybe 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM Maybe a #

FunctorWithIndex () Maybe 
Instance details

Defined in Control.Lens.Indexed

Methods

imap :: (() -> a -> b) -> Maybe a -> Maybe b #

imapped :: IndexedSetter () (Maybe a) (Maybe b) a b #

FoldableWithIndex () Maybe 
Instance details

Defined in Control.Lens.Indexed

Methods

ifoldMap :: Monoid m => (() -> a -> m) -> Maybe a -> m #

ifolded :: IndexedFold () (Maybe a) a #

ifoldr :: (() -> a -> b -> b) -> b -> Maybe a -> b #

ifoldl :: (() -> b -> a -> b) -> b -> Maybe a -> b #

ifoldr' :: (() -> a -> b -> b) -> b -> Maybe a -> b #

ifoldl' :: (() -> b -> a -> b) -> b -> Maybe a -> b #

TraversableWithIndex () Maybe 
Instance details

Defined in Control.Lens.Indexed

Methods

itraverse :: Applicative f => (() -> a -> f b) -> Maybe a -> f (Maybe b) #

itraversed :: IndexedTraversal () (Maybe a) (Maybe b) a b #

Lift a => Lift (Maybe a :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Maybe a -> Q Exp #

liftTyped :: Maybe a -> Q (TExp (Maybe a)) #

(Lift Exp a, Elt (Plain a)) => Lift Exp (Maybe a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Maybe

Associated Types

type Plain (Maybe a) Source #

Methods

lift :: Maybe a -> Exp (Plain (Maybe a)) Source #

Eq a => Eq (Maybe a)

Since: base-2.1

Instance details

Defined in GHC.Maybe

Methods

(==) :: Maybe a -> Maybe a -> Bool #

(/=) :: Maybe a -> Maybe a -> Bool #

Ord a => Ord (Maybe a)

Since: base-2.1

Instance details

Defined in GHC.Maybe

Methods

compare :: Maybe a -> Maybe a -> Ordering #

(<) :: Maybe a -> Maybe a -> Bool #

(<=) :: Maybe a -> Maybe a -> Bool #

(>) :: Maybe a -> Maybe a -> Bool #

(>=) :: Maybe a -> Maybe a -> Bool #

max :: Maybe a -> Maybe a -> Maybe a #

min :: Maybe a -> Maybe a -> Maybe a #

Read a => Read (Maybe a)

Since: base-2.1

Instance details

Defined in GHC.Read

Show a => Show (Maybe a)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Maybe a -> ShowS #

show :: Maybe a -> String #

showList :: [Maybe a] -> ShowS #

Generic (Maybe a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Maybe a) :: Type -> Type #

Methods

from :: Maybe a -> Rep (Maybe a) x #

to :: Rep (Maybe a) x -> Maybe a #

Semigroup a => Semigroup (Maybe a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: Maybe a -> Maybe a -> Maybe a #

sconcat :: NonEmpty (Maybe a) -> Maybe a #

stimes :: Integral b => b -> Maybe a -> Maybe a #

(Semigroup (Exp a), Elt a) => Semigroup (Exp (Maybe a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Maybe

Methods

(<>) :: Exp (Maybe a) -> Exp (Maybe a) -> Exp (Maybe a) #

sconcat :: NonEmpty (Exp (Maybe a)) -> Exp (Maybe a) #

stimes :: Integral b => b -> Exp (Maybe a) -> Exp (Maybe a) #

Semigroup a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S."

Since 4.11.0: constraint on inner a value generalised from Monoid to Semigroup.

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

mconcat :: [Maybe a] -> Maybe a #

(Monoid (Exp a), Elt a) => Monoid (Exp (Maybe a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Maybe

Methods

mempty :: Exp (Maybe a) #

mappend :: Exp (Maybe a) -> Exp (Maybe a) -> Exp (Maybe a) #

mconcat :: [Exp (Maybe a)] -> Exp (Maybe a) #

NFData a => NFData (Maybe a) 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Maybe a -> () #

Hashable a => Hashable (Maybe a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Maybe a -> Int #

hash :: Maybe a -> Int #

Ixed (Maybe a) 
Instance details

Defined in Control.Lens.At

Methods

ix :: Index (Maybe a) -> Traversal' (Maybe a) (IxValue (Maybe a)) #

At (Maybe a) 
Instance details

Defined in Control.Lens.At

Methods

at :: Index (Maybe a) -> Lens' (Maybe a) (Maybe (IxValue (Maybe a))) #

AsEmpty (Maybe a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (Maybe a) () #

Pretty a => Pretty (Maybe a)

Ignore Nothings, print Just contents.

>>> pretty (Just True)
True
>>> braces (pretty (Nothing :: Maybe Bool))
{}
>>> pretty [Just 1, Nothing, Just 3, Nothing]
[1, 3]
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Maybe a -> Doc ann #

prettyList :: [Maybe a] -> Doc ann #

Pretty a => Pretty (Maybe a) 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

pretty :: Maybe a -> Doc b #

prettyList :: [Maybe a] -> Doc b #

SingKind a => SingKind (Maybe a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type DemoteRep (Maybe a)

Methods

fromSing :: forall (a0 :: Maybe a). Sing a0 -> DemoteRep (Maybe a)

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

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

Defined in Data.Array.Accelerate.Data.Maybe

Methods

(==) :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Bool Source #

(/=) :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Bool Source #

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

Defined in Data.Array.Accelerate.Data.Maybe

Methods

(<) :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Bool Source #

(>) :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Bool Source #

(<=) :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Bool Source #

(>=) :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Bool Source #

min :: Exp (Maybe a) -> Exp (Maybe a) -> Exp (Maybe a) Source #

max :: Exp (Maybe a) -> Exp (Maybe a) -> Exp (Maybe a) Source #

compare :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Ordering Source #

Generic1 Maybe

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Maybe :: k -> Type #

Methods

from1 :: forall (a :: k). Maybe a -> Rep1 Maybe a #

to1 :: forall (a :: k). Rep1 Maybe a -> Maybe a #

SingI ('Nothing :: Maybe a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing 'Nothing

Each (Maybe a) (Maybe b) a b
each :: Traversal (Maybe a) (Maybe b) a b
Instance details

Defined in Control.Lens.Each

Methods

each :: Traversal (Maybe a) (Maybe b) a b #

SingI a2 => SingI ('Just a2 :: Maybe a1)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing ('Just a2)

type Failure Maybe 
Instance details

Defined in Basement.Monad

type Failure Maybe = ()
type StM Maybe a 
Instance details

Defined in Control.Monad.Trans.Control

type StM Maybe a = a
type Rep (Maybe a) 
Instance details

Defined in GHC.Generics

type Rep (Maybe a) = D1 ('MetaData "Maybe" "GHC.Maybe" "base" 'False) (C1 ('MetaCons "Nothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Just" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type Index (Maybe a) 
Instance details

Defined in Control.Lens.At

type Index (Maybe a) = ()
type IxValue (Maybe a) 
Instance details

Defined in Control.Lens.At

type IxValue (Maybe a) = a
type DemoteRep (Maybe a) 
Instance details

Defined in GHC.Generics

type DemoteRep (Maybe a) = Maybe (DemoteRep a)
data Sing (b :: Maybe a) 
Instance details

Defined in GHC.Generics

data Sing (b :: Maybe a) where
type Plain (Maybe a) Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Maybe

type Plain (Maybe a) = Maybe (Plain a)
type Rep1 Maybe 
Instance details

Defined in GHC.Generics

type Rep1 Maybe = D1 ('MetaData "Maybe" "GHC.Maybe" "base" 'False) (C1 ('MetaCons "Nothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Just" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

pattern Nothing_ :: forall a. (HasCallStack, Elt a) => Exp (Maybe a) Source #

pattern Just_ :: forall a. (HasCallStack, Elt a) => Exp a -> Exp (Maybe a) Source #

data Char #

The character type Char is an enumeration whose values represent Unicode (or equivalently ISO/IEC 10646) code points (i.e. characters, see http://www.unicode.org/ for details). This set extends the ISO 8859-1 (Latin-1) character set (the first 256 characters), which is itself an extension of the ASCII character set (the first 128 characters). A character literal in Haskell has type Char.

To convert a Char to or from the corresponding Int value defined by Unicode, use toEnum and fromEnum from the Enum class respectively (or equivalently ord and chr).

Instances

Instances details
Bounded Char

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Char

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

succ :: Char -> Char #

pred :: Char -> Char #

toEnum :: Int -> Char #

fromEnum :: Char -> Int #

enumFrom :: Char -> [Char] #

enumFromThen :: Char -> Char -> [Char] #

enumFromTo :: Char -> Char -> [Char] #

enumFromThenTo :: Char -> Char -> Char -> [Char] #

Eq Char 
Instance details

Defined in GHC.Classes

Methods

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

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

Ord Char 
Instance details

Defined in GHC.Classes

Methods

compare :: Char -> Char -> Ordering #

(<) :: Char -> Char -> Bool #

(<=) :: Char -> Char -> Bool #

(>) :: Char -> Char -> Bool #

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

max :: Char -> Char -> Char #

min :: Char -> Char -> Char #

Read Char

Since: base-2.1

Instance details

Defined in GHC.Read

Show Char

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Char -> ShowS #

show :: Char -> String #

showList :: [Char] -> ShowS #

Ix Char

Since: base-2.1

Instance details

Defined in GHC.Ix

Methods

range :: (Char, Char) -> [Char] #

index :: (Char, Char) -> Char -> Int #

unsafeIndex :: (Char, Char) -> Char -> Int #

inRange :: (Char, Char) -> Char -> Bool #

rangeSize :: (Char, Char) -> Int #

unsafeRangeSize :: (Char, Char) -> Int #

PrintfArg Char

Since: base-2.1

Instance details

Defined in Text.Printf

IsChar Char

Since: base-2.1

Instance details

Defined in Text.Printf

Methods

toChar :: Char -> Char #

fromChar :: Char -> Char #

Storable Char

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Char -> Int #

alignment :: Char -> Int #

peekElemOff :: Ptr Char -> Int -> IO Char #

pokeElemOff :: Ptr Char -> Int -> Char -> IO () #

peekByteOff :: Ptr b -> Int -> IO Char #

pokeByteOff :: Ptr b -> Int -> Char -> IO () #

peek :: Ptr Char -> IO Char #

poke :: Ptr Char -> Char -> IO () #

PrimType Char 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Char :: Nat #

PrimMemoryComparable Char 
Instance details

Defined in Basement.PrimType

Subtractive Char 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Char #

Methods

(-) :: Char -> Char -> Difference Char #

NFData Char 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Char -> () #

Hashable Char 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Char -> Int #

hash :: Char -> Int #

Prim Char 
Instance details

Defined in Data.Primitive.Types

Unbox Char 
Instance details

Defined in Data.Vector.Unboxed.Base

Pretty Char

Instead of (pretty 'n'), consider using line as a more readable alternative.

>>> pretty 'f' <> pretty 'o' <> pretty 'o'
foo
>>> pretty ("string" :: String)
string
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Char -> Doc ann #

prettyList :: [Char] -> Doc ann #

ErrorList Char 
Instance details

Defined in Control.Monad.Trans.Error

Methods

listMsg :: String -> [Char] #

Pretty Char 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

pretty :: Char -> Doc b #

prettyList :: [Char] -> Doc b #

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

Eq Char Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord Char Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

Lift Char 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Char -> Q Exp #

liftTyped :: Char -> Q (TExp Char) #

Vector Vector Char 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Char 
Instance details

Defined in Data.Vector.Unboxed.Base

Lift Exp Char Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain Char Source #

Methods

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

KnownSymbol n => Reifies (n :: Symbol) String 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy n -> String #

Cons Text Text Char Char 
Instance details

Defined in Control.Lens.Cons

Methods

_Cons :: Prism Text Text (Char, Text) (Char, Text) #

Cons Text Text Char Char 
Instance details

Defined in Control.Lens.Cons

Methods

_Cons :: Prism Text Text (Char, Text) (Char, Text) #

Snoc Text Text Char Char 
Instance details

Defined in Control.Lens.Cons

Methods

_Snoc :: Prism Text Text (Text, Char) (Text, Char) #

Snoc Text Text Char Char 
Instance details

Defined in Control.Lens.Cons

Methods

_Snoc :: Prism Text Text (Text, Char) (Text, Char) #

Generic1 (URec Char :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec Char) :: k -> Type #

Methods

from1 :: forall (a :: k0). URec Char a -> Rep1 (URec Char) a #

to1 :: forall (a :: k0). Rep1 (URec Char) a -> URec Char a #

Bounded (Exp Char) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Foldable (UChar :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => UChar m -> m #

foldMap :: Monoid m => (a -> m) -> UChar a -> m #

foldMap' :: Monoid m => (a -> m) -> UChar a -> m #

foldr :: (a -> b -> b) -> b -> UChar a -> b #

foldr' :: (a -> b -> b) -> b -> UChar a -> b #

foldl :: (b -> a -> b) -> b -> UChar a -> b #

foldl' :: (b -> a -> b) -> b -> UChar a -> b #

foldr1 :: (a -> a -> a) -> UChar a -> a #

foldl1 :: (a -> a -> a) -> UChar a -> a #

toList :: UChar a -> [a] #

null :: UChar a -> Bool #

length :: UChar a -> Int #

elem :: Eq a => a -> UChar a -> Bool #

maximum :: Ord a => UChar a -> a #

minimum :: Ord a => UChar a -> a #

sum :: Num a => UChar a -> a #

product :: Num a => UChar a -> a #

Traversable (UChar :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UChar a -> f (UChar b) #

sequenceA :: Applicative f => UChar (f a) -> f (UChar a) #

mapM :: Monad m => (a -> m b) -> UChar a -> m (UChar b) #

sequence :: Monad m => UChar (m a) -> m (UChar a) #

Functor (URec Char :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec Char a -> URec Char b #

(<$) :: a -> URec Char b -> URec Char a #

Eq (URec Char p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: URec Char p -> URec Char p -> Bool #

(/=) :: URec Char p -> URec Char p -> Bool #

Ord (URec Char p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec Char p -> URec Char p -> Ordering #

(<) :: URec Char p -> URec Char p -> Bool #

(<=) :: URec Char p -> URec Char p -> Bool #

(>) :: URec Char p -> URec Char p -> Bool #

(>=) :: URec Char p -> URec Char p -> Bool #

max :: URec Char p -> URec Char p -> URec Char p #

min :: URec Char p -> URec Char p -> URec Char p #

Show (URec Char p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Char p -> ShowS #

show :: URec Char p -> String #

showList :: [URec Char p] -> ShowS #

Generic (URec Char p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Char p) :: Type -> Type #

Methods

from :: URec Char p -> Rep (URec Char p) x #

to :: Rep (URec Char p) x -> URec Char p #

type PrimSize Char 
Instance details

Defined in Basement.PrimType

type PrimSize Char = 4
type Difference Char 
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Char 
Instance details

Defined in Basement.Nat

type NatNumMaxBound Char = 1114111
newtype Vector Char 
Instance details

Defined in Data.Vector.Unboxed.Base

type Plain Char Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

type Plain Char = Char
data URec Char (p :: k)

Used for marking occurrences of Char#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

data URec Char (p :: k) = UChar {}
newtype MVector s Char 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Char = MV_Char (MVector s Char)
type Rep1 (URec Char :: k -> Type) 
Instance details

Defined in GHC.Generics

type Rep1 (URec Char :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "uChar#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UChar :: k -> Type)))
type Rep (URec Char p) 
Instance details

Defined in GHC.Generics

type Rep (URec Char p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "uChar#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UChar :: Type -> Type)))

data CFloat #

Haskell type representing the C float type. (The concrete types of Foreign.C.Types are platform-specific.)

Instances

Instances details
Enum CFloat 
Instance details

Defined in Foreign.C.Types

Eq CFloat 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Floating CFloat 
Instance details

Defined in Foreign.C.Types

Fractional CFloat 
Instance details

Defined in Foreign.C.Types

Num CFloat 
Instance details

Defined in Foreign.C.Types

Ord CFloat 
Instance details

Defined in Foreign.C.Types

Read CFloat 
Instance details

Defined in Foreign.C.Types

Real CFloat 
Instance details

Defined in Foreign.C.Types

RealFloat CFloat 
Instance details

Defined in Foreign.C.Types

RealFrac CFloat 
Instance details

Defined in Foreign.C.Types

Methods

properFraction :: Integral b => CFloat -> (b, CFloat) #

truncate :: Integral b => CFloat -> b #

round :: Integral b => CFloat -> b #

ceiling :: Integral b => CFloat -> b #

floor :: Integral b => CFloat -> b #

Show CFloat 
Instance details

Defined in Foreign.C.Types

Storable CFloat 
Instance details

Defined in Foreign.C.Types

Subtractive CFloat 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CFloat #

NFData CFloat

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CFloat -> () #

Prim CFloat 
Instance details

Defined in Data.Primitive.Types

Wrapped CFloat 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CFloat #

RealFrac CFloat Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.RealFrac

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

Eq CFloat Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord CFloat Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

RealFloat CFloat Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.RealFloat

Rewrapped CFloat t 
Instance details

Defined in Control.Lens.Wrapped

Lift Exp CFloat Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CFloat Source #

Methods

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

Enum (Exp CFloat) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Floating (Exp CFloat) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Floating

Fractional (Exp CFloat) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Fractional

Num (Exp CFloat) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

type Difference CFloat 
Instance details

Defined in Basement.Numerical.Subtractive

type Unwrapped CFloat 
Instance details

Defined in Control.Lens.Wrapped

type Plain CFloat Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

data CDouble #

Haskell type representing the C double type. (The concrete types of Foreign.C.Types are platform-specific.)

Instances

Instances details
Enum CDouble 
Instance details

Defined in Foreign.C.Types

Eq CDouble 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Floating CDouble 
Instance details

Defined in Foreign.C.Types

Fractional CDouble 
Instance details

Defined in Foreign.C.Types

Num CDouble 
Instance details

Defined in Foreign.C.Types

Ord CDouble 
Instance details

Defined in Foreign.C.Types

Read CDouble 
Instance details

Defined in Foreign.C.Types

Real CDouble 
Instance details

Defined in Foreign.C.Types

RealFloat CDouble 
Instance details

Defined in Foreign.C.Types

RealFrac CDouble 
Instance details

Defined in Foreign.C.Types

Methods

properFraction :: Integral b => CDouble -> (b, CDouble) #

truncate :: Integral b => CDouble -> b #

round :: Integral b => CDouble -> b #

ceiling :: Integral b => CDouble -> b #

floor :: Integral b => CDouble -> b #

Show CDouble 
Instance details

Defined in Foreign.C.Types

Storable CDouble 
Instance details

Defined in Foreign.C.Types

Subtractive CDouble 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CDouble #

NFData CDouble

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CDouble -> () #

Prim CDouble 
Instance details

Defined in Data.Primitive.Types

Wrapped CDouble 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CDouble #

RealFrac CDouble Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.RealFrac

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

Eq CDouble Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord CDouble Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

RealFloat CDouble Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.RealFloat

Rewrapped CDouble t 
Instance details

Defined in Control.Lens.Wrapped

Lift Exp CDouble Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CDouble Source #

Enum (Exp CDouble) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Floating (Exp CDouble) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Floating

Fractional (Exp CDouble) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Fractional

Num (Exp CDouble) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

type Difference CDouble 
Instance details

Defined in Basement.Numerical.Subtractive

type Unwrapped CDouble 
Instance details

Defined in Control.Lens.Wrapped

type Plain CDouble Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

data CShort #

Haskell type representing the C short type. (The concrete types of Foreign.C.Types are platform-specific.)

Instances

Instances details
Bounded CShort 
Instance details

Defined in Foreign.C.Types

Enum CShort 
Instance details

Defined in Foreign.C.Types

Eq CShort 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CShort 
Instance details

Defined in Foreign.C.Types

Num CShort 
Instance details

Defined in Foreign.C.Types

Ord CShort 
Instance details

Defined in Foreign.C.Types

Read CShort 
Instance details

Defined in Foreign.C.Types

Real CShort 
Instance details

Defined in Foreign.C.Types

Show CShort 
Instance details

Defined in Foreign.C.Types

Storable CShort 
Instance details

Defined in Foreign.C.Types

Bits CShort 
Instance details

Defined in Foreign.C.Types

FiniteBits CShort 
Instance details

Defined in Foreign.C.Types

Subtractive CShort 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CShort #

NFData CShort

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CShort -> () #

Prim CShort 
Instance details

Defined in Data.Primitive.Types

Wrapped CShort 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CShort #

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

Eq CShort Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord CShort Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

FiniteBits CShort Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Bits CShort Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Rewrapped CShort t 
Instance details

Defined in Control.Lens.Wrapped

Lift Exp CShort Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CShort Source #

Methods

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

Bounded (Exp CShort) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Enum (Exp CShort) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Integral (Exp CShort) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Num (Exp CShort) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

type Difference CShort 
Instance details

Defined in Basement.Numerical.Subtractive

type Unwrapped CShort 
Instance details

Defined in Control.Lens.Wrapped

type Plain CShort Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

data CUShort #

Haskell type representing the C unsigned short type. (The concrete types of Foreign.C.Types are platform-specific.)

Instances

Instances details
Bounded CUShort 
Instance details

Defined in Foreign.C.Types

Enum CUShort 
Instance details

Defined in Foreign.C.Types

Eq CUShort 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CUShort 
Instance details

Defined in Foreign.C.Types

Num CUShort 
Instance details

Defined in Foreign.C.Types

Ord CUShort 
Instance details

Defined in Foreign.C.Types

Read CUShort 
Instance details

Defined in Foreign.C.Types

Real CUShort 
Instance details

Defined in Foreign.C.Types

Show CUShort 
Instance details

Defined in Foreign.C.Types

Storable CUShort 
Instance details

Defined in Foreign.C.Types

Bits CUShort 
Instance details

Defined in Foreign.C.Types

FiniteBits CUShort 
Instance details

Defined in Foreign.C.Types

Subtractive CUShort 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CUShort #

NFData CUShort

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CUShort -> () #

Prim CUShort 
Instance details

Defined in Data.Primitive.Types

Wrapped CUShort 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CUShort #

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

Eq CUShort Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord CUShort Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

FiniteBits CUShort Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Bits CUShort Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Rewrapped CUShort t 
Instance details

Defined in Control.Lens.Wrapped

Lift Exp CUShort Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CUShort Source #

Bounded (Exp CUShort) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Enum (Exp CUShort) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Integral (Exp CUShort) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Num (Exp CUShort) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

type Difference CUShort 
Instance details

Defined in Basement.Numerical.Subtractive

type Unwrapped CUShort 
Instance details

Defined in Control.Lens.Wrapped

type Plain CUShort Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

data CInt #

Haskell type representing the C int type. (The concrete types of Foreign.C.Types are platform-specific.)

Instances

Instances details
Bounded CInt 
Instance details

Defined in Foreign.C.Types

Enum CInt 
Instance details

Defined in Foreign.C.Types

Methods

succ :: CInt -> CInt #

pred :: CInt -> CInt #

toEnum :: Int -> CInt #

fromEnum :: CInt -> Int #

enumFrom :: CInt -> [CInt] #

enumFromThen :: CInt -> CInt -> [CInt] #

enumFromTo :: CInt -> CInt -> [CInt] #

enumFromThenTo :: CInt -> CInt -> CInt -> [CInt] #

Eq CInt 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CInt 
Instance details

Defined in Foreign.C.Types

Methods

quot :: CInt -> CInt -> CInt #

rem :: CInt -> CInt -> CInt #

div :: CInt -> CInt -> CInt #

mod :: CInt -> CInt -> CInt #

quotRem :: CInt -> CInt -> (CInt, CInt) #

divMod :: CInt -> CInt -> (CInt, CInt) #

toInteger :: CInt -> Integer #

Num CInt 
Instance details

Defined in Foreign.C.Types

Methods

(+) :: CInt -> CInt -> CInt #

(-) :: CInt -> CInt -> CInt #

(*) :: CInt -> CInt -> CInt #

negate :: CInt -> CInt #

abs :: CInt -> CInt #

signum :: CInt -> CInt #

fromInteger :: Integer -> CInt #

Ord CInt 
Instance details

Defined in Foreign.C.Types

Methods

compare :: CInt -> CInt -> Ordering #

(<) :: CInt -> CInt -> Bool #

(<=) :: CInt -> CInt -> Bool #

(>) :: CInt -> CInt -> Bool #

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

max :: CInt -> CInt -> CInt #

min :: CInt -> CInt -> CInt #

Read CInt 
Instance details

Defined in Foreign.C.Types

Real CInt 
Instance details

Defined in Foreign.C.Types

Methods

toRational :: CInt -> Rational #

Show CInt 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CInt -> ShowS #

show :: CInt -> String #

showList :: [CInt] -> ShowS #

Storable CInt 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CInt -> Int #

alignment :: CInt -> Int #

peekElemOff :: Ptr CInt -> Int -> IO CInt #

pokeElemOff :: Ptr CInt -> Int -> CInt -> IO () #

peekByteOff :: Ptr b -> Int -> IO CInt #

pokeByteOff :: Ptr b -> Int -> CInt -> IO () #

peek :: Ptr CInt -> IO CInt #

poke :: Ptr CInt -> CInt -> IO () #

Bits CInt 
Instance details

Defined in Foreign.C.Types

FiniteBits CInt 
Instance details

Defined in Foreign.C.Types

Subtractive CInt 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CInt #

Methods

(-) :: CInt -> CInt -> Difference CInt #

NFData CInt

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CInt -> () #

Prim CInt 
Instance details

Defined in Data.Primitive.Types

Wrapped CInt 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CInt #

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

Eq CInt Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord CInt Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

FiniteBits CInt Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Bits CInt Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Rewrapped CInt t 
Instance details

Defined in Control.Lens.Wrapped

Lift Exp CInt Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CInt Source #

Methods

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

Bounded (Exp CInt) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Enum (Exp CInt) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Integral (Exp CInt) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Num (Exp CInt) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

type Difference CInt 
Instance details

Defined in Basement.Numerical.Subtractive

type Unwrapped CInt 
Instance details

Defined in Control.Lens.Wrapped

type Plain CInt Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

type Plain CInt = CInt

data CUInt #

Haskell type representing the C unsigned int type. (The concrete types of Foreign.C.Types are platform-specific.)

Instances

Instances details
Bounded CUInt 
Instance details

Defined in Foreign.C.Types

Enum CUInt 
Instance details

Defined in Foreign.C.Types

Eq CUInt 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CUInt 
Instance details

Defined in Foreign.C.Types

Num CUInt 
Instance details

Defined in Foreign.C.Types

Ord CUInt 
Instance details

Defined in Foreign.C.Types

Methods

compare :: CUInt -> CUInt -> Ordering #

(<) :: CUInt -> CUInt -> Bool #

(<=) :: CUInt -> CUInt -> Bool #

(>) :: CUInt -> CUInt -> Bool #

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

max :: CUInt -> CUInt -> CUInt #

min :: CUInt -> CUInt -> CUInt #

Read CUInt 
Instance details

Defined in Foreign.C.Types

Real CUInt 
Instance details

Defined in Foreign.C.Types

Methods

toRational :: CUInt -> Rational #

Show CUInt 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CUInt -> ShowS #

show :: CUInt -> String #

showList :: [CUInt] -> ShowS #

Storable CUInt 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CUInt -> Int #

alignment :: CUInt -> Int #

peekElemOff :: Ptr CUInt -> Int -> IO CUInt #

pokeElemOff :: Ptr CUInt -> Int -> CUInt -> IO () #

peekByteOff :: Ptr b -> Int -> IO CUInt #

pokeByteOff :: Ptr b -> Int -> CUInt -> IO () #

peek :: Ptr CUInt -> IO CUInt #

poke :: Ptr CUInt -> CUInt -> IO () #

Bits CUInt 
Instance details

Defined in Foreign.C.Types

FiniteBits CUInt 
Instance details

Defined in Foreign.C.Types

Subtractive CUInt 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CUInt #

Methods

(-) :: CUInt -> CUInt -> Difference CUInt #

NFData CUInt

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CUInt -> () #

Prim CUInt 
Instance details

Defined in Data.Primitive.Types

Wrapped CUInt 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CUInt #

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

Eq CUInt Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord CUInt Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

FiniteBits CUInt Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Bits CUInt Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Rewrapped CUInt t 
Instance details

Defined in Control.Lens.Wrapped

Lift Exp CUInt Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CUInt Source #

Methods

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

Bounded (Exp CUInt) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Enum (Exp CUInt) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Integral (Exp CUInt) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Num (Exp CUInt) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

type Difference CUInt 
Instance details

Defined in Basement.Numerical.Subtractive

type Unwrapped CUInt 
Instance details

Defined in Control.Lens.Wrapped

type Plain CUInt Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

data CLong #

Haskell type representing the C long type. (The concrete types of Foreign.C.Types are platform-specific.)

Instances

Instances details
Bounded CLong 
Instance details

Defined in Foreign.C.Types

Enum CLong 
Instance details

Defined in Foreign.C.Types

Eq CLong 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CLong 
Instance details

Defined in Foreign.C.Types

Num CLong 
Instance details

Defined in Foreign.C.Types

Ord CLong 
Instance details

Defined in Foreign.C.Types

Methods

compare :: CLong -> CLong -> Ordering #

(<) :: CLong -> CLong -> Bool #

(<=) :: CLong -> CLong -> Bool #

(>) :: CLong -> CLong -> Bool #

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

max :: CLong -> CLong -> CLong #

min :: CLong -> CLong -> CLong #

Read CLong 
Instance details

Defined in Foreign.C.Types

Real CLong 
Instance details

Defined in Foreign.C.Types

Methods

toRational :: CLong -> Rational #

Show CLong 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CLong -> ShowS #

show :: CLong -> String #

showList :: [CLong] -> ShowS #

Storable CLong 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CLong -> Int #

alignment :: CLong -> Int #

peekElemOff :: Ptr CLong -> Int -> IO CLong #

pokeElemOff :: Ptr CLong -> Int -> CLong -> IO () #

peekByteOff :: Ptr b -> Int -> IO CLong #

pokeByteOff :: Ptr b -> Int -> CLong -> IO () #

peek :: Ptr CLong -> IO CLong #

poke :: Ptr CLong -> CLong -> IO () #

Bits CLong 
Instance details

Defined in Foreign.C.Types

FiniteBits CLong 
Instance details

Defined in Foreign.C.Types

Subtractive CLong 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CLong #

Methods

(-) :: CLong -> CLong -> Difference CLong #

NFData CLong

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CLong -> () #

Prim CLong 
Instance details

Defined in Data.Primitive.Types

Wrapped CLong 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CLong #

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

Eq CLong Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord CLong Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

FiniteBits CLong Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Bits CLong Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Rewrapped CLong t 
Instance details

Defined in Control.Lens.Wrapped

Lift Exp CLong Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CLong Source #

Methods

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

Bounded (Exp CLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Enum (Exp CLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Integral (Exp CLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Num (Exp CLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

type Difference CLong 
Instance details

Defined in Basement.Numerical.Subtractive

type Unwrapped CLong 
Instance details

Defined in Control.Lens.Wrapped

type Plain CLong Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

data CULong #

Haskell type representing the C unsigned long type. (The concrete types of Foreign.C.Types are platform-specific.)

Instances

Instances details
Bounded CULong 
Instance details

Defined in Foreign.C.Types

Enum CULong 
Instance details

Defined in Foreign.C.Types

Eq CULong 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CULong 
Instance details

Defined in Foreign.C.Types

Num CULong 
Instance details

Defined in Foreign.C.Types

Ord CULong 
Instance details

Defined in Foreign.C.Types

Read CULong 
Instance details

Defined in Foreign.C.Types

Real CULong 
Instance details

Defined in Foreign.C.Types

Show CULong 
Instance details

Defined in Foreign.C.Types

Storable CULong 
Instance details

Defined in Foreign.C.Types

Bits CULong 
Instance details

Defined in Foreign.C.Types

FiniteBits CULong 
Instance details

Defined in Foreign.C.Types

Subtractive CULong 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CULong #

NFData CULong

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CULong -> () #

Prim CULong 
Instance details

Defined in Data.Primitive.Types

Wrapped CULong 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CULong #

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

Eq CULong Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord CULong Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

FiniteBits CULong Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Bits CULong Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Rewrapped CULong t 
Instance details

Defined in Control.Lens.Wrapped

Lift Exp CULong Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CULong Source #

Methods

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

Bounded (Exp CULong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Enum (Exp CULong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Integral (Exp CULong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Num (Exp CULong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

type Difference CULong 
Instance details

Defined in Basement.Numerical.Subtractive

type Unwrapped CULong 
Instance details

Defined in Control.Lens.Wrapped

type Plain CULong Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

data CLLong #

Haskell type representing the C long long type. (The concrete types of Foreign.C.Types are platform-specific.)

Instances

Instances details
Bounded CLLong 
Instance details

Defined in Foreign.C.Types

Enum CLLong 
Instance details

Defined in Foreign.C.Types

Eq CLLong 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CLLong 
Instance details

Defined in Foreign.C.Types

Num CLLong 
Instance details

Defined in Foreign.C.Types

Ord CLLong 
Instance details

Defined in Foreign.C.Types

Read CLLong 
Instance details

Defined in Foreign.C.Types

Real CLLong 
Instance details

Defined in Foreign.C.Types

Show CLLong 
Instance details

Defined in Foreign.C.Types

Storable CLLong 
Instance details

Defined in Foreign.C.Types

Bits CLLong 
Instance details

Defined in Foreign.C.Types

FiniteBits CLLong 
Instance details

Defined in Foreign.C.Types

Subtractive CLLong 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CLLong #

NFData CLLong

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CLLong -> () #

Prim CLLong 
Instance details

Defined in Data.Primitive.Types

Wrapped CLLong 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CLLong #

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

Eq CLLong Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord CLLong Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

FiniteBits CLLong Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Bits CLLong Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Rewrapped CLLong t 
Instance details

Defined in Control.Lens.Wrapped

Lift Exp CLLong Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CLLong Source #

Methods

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

Bounded (Exp CLLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Enum (Exp CLLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Integral (Exp CLLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Num (Exp CLLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

type Difference CLLong 
Instance details

Defined in Basement.Numerical.Subtractive

type Unwrapped CLLong 
Instance details

Defined in Control.Lens.Wrapped

type Plain CLLong Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

data CULLong #

Haskell type representing the C unsigned long long type. (The concrete types of Foreign.C.Types are platform-specific.)

Instances

Instances details
Bounded CULLong 
Instance details

Defined in Foreign.C.Types

Enum CULLong 
Instance details

Defined in Foreign.C.Types

Eq CULLong 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CULLong 
Instance details

Defined in Foreign.C.Types

Num CULLong 
Instance details

Defined in Foreign.C.Types

Ord CULLong 
Instance details

Defined in Foreign.C.Types

Read CULLong 
Instance details

Defined in Foreign.C.Types

Real CULLong 
Instance details

Defined in Foreign.C.Types

Show CULLong 
Instance details

Defined in Foreign.C.Types

Storable CULLong 
Instance details

Defined in Foreign.C.Types

Bits CULLong 
Instance details

Defined in Foreign.C.Types

FiniteBits CULLong 
Instance details

Defined in Foreign.C.Types

Subtractive CULLong 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CULLong #

NFData CULLong

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CULLong -> () #

Prim CULLong 
Instance details

Defined in Data.Primitive.Types

Wrapped CULLong 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CULLong #

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

Eq CULLong Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord CULLong Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

FiniteBits CULLong Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Bits CULLong Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Rewrapped CULLong t 
Instance details

Defined in Control.Lens.Wrapped

Lift Exp CULLong Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CULLong Source #

Bounded (Exp CULLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

Enum (Exp CULLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Enum

Integral (Exp CULLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Integral

Num (Exp CULLong) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Num

type Difference CULLong 
Instance details

Defined in Basement.Numerical.Subtractive

type Unwrapped CULLong 
Instance details

Defined in Control.Lens.Wrapped

type Plain CULLong Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

data CChar #

Haskell type representing the C char type. (The concrete types of Foreign.C.Types are platform-specific.)

Instances

Instances details
Bounded CChar 
Instance details

Defined in Foreign.C.Types

Enum CChar 
Instance details

Defined in Foreign.C.Types

Eq CChar 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CChar 
Instance details

Defined in Foreign.C.Types

Num CChar 
Instance details

Defined in Foreign.C.Types

Ord CChar 
Instance details

Defined in Foreign.C.Types

Methods

compare :: CChar -> CChar -> Ordering #

(<) :: CChar -> CChar -> Bool #

(<=) :: CChar -> CChar -> Bool #

(>) :: CChar -> CChar -> Bool #

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

max :: CChar -> CChar -> CChar #

min :: CChar -> CChar -> CChar #

Read CChar 
Instance details

Defined in Foreign.C.Types

Real CChar 
Instance details

Defined in Foreign.C.Types

Methods

toRational :: CChar -> Rational #

Show CChar 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CChar -> ShowS #

show :: CChar -> String #

showList :: [CChar] -> ShowS #

Storable CChar 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CChar -> Int #

alignment :: CChar -> Int #

peekElemOff :: Ptr CChar -> Int -> IO CChar #

pokeElemOff :: Ptr CChar -> Int -> CChar -> IO () #

peekByteOff :: Ptr b -> Int -> IO CChar #

pokeByteOff :: Ptr b -> Int -> CChar -> IO () #

peek :: Ptr CChar -> IO CChar #

poke :: Ptr CChar -> CChar -> IO () #

Bits CChar 
Instance details

Defined in Foreign.C.Types

FiniteBits CChar 
Instance details

Defined in Foreign.C.Types

PrimType CChar 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize CChar :: Nat #

PrimMemoryComparable CChar 
Instance details

Defined in Basement.PrimType

Subtractive CChar 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CChar #

Methods

(-) :: CChar -> CChar -> Difference CChar #

NFData CChar

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CChar -> () #

Prim CChar 
Instance details

Defined in Data.Primitive.Types

Wrapped CChar 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CChar #

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

Eq CChar Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord CChar Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

FiniteBits CChar Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Bits CChar Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Rewrapped CChar t 
Instance details

Defined in Control.Lens.Wrapped

Lift Exp CChar Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CChar Source #

Methods

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

Bounded (Exp CChar) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

type PrimSize CChar 
Instance details

Defined in Basement.PrimType

type PrimSize CChar = 1
type Difference CChar 
Instance details

Defined in Basement.Numerical.Subtractive

type Unwrapped CChar 
Instance details

Defined in Control.Lens.Wrapped

type Plain CChar Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

data CSChar #

Haskell type representing the C signed char type. (The concrete types of Foreign.C.Types are platform-specific.)

Instances

Instances details
Bounded CSChar 
Instance details

Defined in Foreign.C.Types

Enum CSChar 
Instance details

Defined in Foreign.C.Types

Eq CSChar 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CSChar 
Instance details

Defined in Foreign.C.Types

Num CSChar 
Instance details

Defined in Foreign.C.Types

Ord CSChar 
Instance details

Defined in Foreign.C.Types

Read CSChar 
Instance details

Defined in Foreign.C.Types

Real CSChar 
Instance details

Defined in Foreign.C.Types

Show CSChar 
Instance details

Defined in Foreign.C.Types

Storable CSChar 
Instance details

Defined in Foreign.C.Types

Bits CSChar 
Instance details

Defined in Foreign.C.Types

FiniteBits CSChar 
Instance details

Defined in Foreign.C.Types

Subtractive CSChar 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CSChar #

NFData CSChar

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CSChar -> () #

Prim CSChar 
Instance details

Defined in Data.Primitive.Types

Wrapped CSChar 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CSChar #

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

Eq CSChar Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord CSChar Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

FiniteBits CSChar Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Bits CSChar Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Rewrapped CSChar t 
Instance details

Defined in Control.Lens.Wrapped

Lift Exp CSChar Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CSChar Source #

Methods

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

Bounded (Exp CSChar) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

type Difference CSChar 
Instance details

Defined in Basement.Numerical.Subtractive

type Unwrapped CSChar 
Instance details

Defined in Control.Lens.Wrapped

type Plain CSChar Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

data CUChar #

Haskell type representing the C unsigned char type. (The concrete types of Foreign.C.Types are platform-specific.)

Instances

Instances details
Bounded CUChar 
Instance details

Defined in Foreign.C.Types

Enum CUChar 
Instance details

Defined in Foreign.C.Types

Eq CUChar 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CUChar 
Instance details

Defined in Foreign.C.Types

Num CUChar 
Instance details

Defined in Foreign.C.Types

Ord CUChar 
Instance details

Defined in Foreign.C.Types

Read CUChar 
Instance details

Defined in Foreign.C.Types

Real CUChar 
Instance details

Defined in Foreign.C.Types

Show CUChar 
Instance details

Defined in Foreign.C.Types

Storable CUChar 
Instance details

Defined in Foreign.C.Types

Bits CUChar 
Instance details

Defined in Foreign.C.Types

FiniteBits CUChar 
Instance details

Defined in Foreign.C.Types

PrimType CUChar 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize CUChar :: Nat #

PrimMemoryComparable CUChar 
Instance details

Defined in Basement.PrimType

Subtractive CUChar 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference CUChar #

NFData CUChar

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CUChar -> () #

Prim CUChar 
Instance details

Defined in Data.Primitive.Types

Wrapped CUChar 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CUChar #

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

Eq CUChar Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Eq

Ord CUChar Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Ord

FiniteBits CUChar Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Bits CUChar Source # 
Instance details

Defined in Data.Array.Accelerate.Data.Bits

Rewrapped CUChar t 
Instance details

Defined in Control.Lens.Wrapped

Lift Exp CUChar Source # 
Instance details

Defined in Data.Array.Accelerate.Lift

Associated Types

type Plain CUChar Source #

Methods

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

Bounded (Exp CUChar) Source # 
Instance details

Defined in Data.Array.Accelerate.Classes.Bounded

type PrimSize CUChar 
Instance details

Defined in Basement.PrimType

type PrimSize CUChar = 1
type Difference CUChar 
Instance details

Defined in Basement.Numerical.Subtractive

type Unwrapped CUChar 
Instance details

Defined in Control.Lens.Wrapped

type Plain CUChar Source # 
Instance details

Defined in Data.Array.Accelerate.Lift