accelerate-1.2.0.0: An embedded language for accelerated array processing

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

Data.Array.Accelerate

Contents

Description

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

Abstract interface:

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

Stratified language:

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

Optimisations:

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

Code execution:

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

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
IfThenElse Acc Source # 
Instance details

Associated Types

type EltT Acc a :: Constraint Source #

Methods

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

Unlift Acc (Acc a) Source # 
Instance details

Methods

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

Lift Acc (Acc a) Source # 
Instance details

Associated Types

type Plain (Acc a) :: * Source #

Methods

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

(Arrays a, Arrays b) => Unlift Acc (Acc a, Acc b) Source # 
Instance details

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

type Plain (Array sh e) :: * Source #

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

show :: Acc arrs -> String #

showList :: [Acc arrs] -> ShowS #

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

Methods

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

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

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

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

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 15-elements wide.

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

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

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

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

Associated Types

type Plain (Array sh e) :: * Source #

Methods

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

Elt e => IsList (Vector e) Source # 
Instance details

Associated Types

type Item (Vector e) :: * #

Methods

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

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

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

Show (Vector e) Source # 
Instance details

Methods

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

show :: Vector e -> String #

showList :: [Vector e] -> ShowS #

Show (Scalar e) Source # 
Instance details

Methods

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

show :: Scalar e -> String #

showList :: [Scalar e] -> ShowS #

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

Methods

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

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

Show (Array sh e) Source # 
Instance details

Methods

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

show :: Array sh e -> String #

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

Show (Array DIM2 e) Source # 
Instance details

Methods

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

show :: Array DIM2 e -> String #

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

NFData (Array sh e) Source # 
Instance details

Methods

rnf :: Array sh e -> () #

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

Methods

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

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

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

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

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

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

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

Minimal complete definition

arrays, flavour, toArr, fromArr

Instances
Arrays () Source # 
Instance details

Methods

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

flavour :: () -> ArraysFlavour ()

toArr :: ArrRepr () -> ()

fromArr :: () -> ArrRepr ()

(Arrays a, Arrays b) => Arrays (a, b) Source # 
Instance details

Methods

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

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

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

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

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

Methods

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

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

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

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

(Arrays a, Arrays b, Arrays c) => Arrays (a, b, c) Source # 
Instance details

Methods

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

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

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

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

(Arrays a, Arrays b, Arrays c, Arrays d) => Arrays (a, b, c, d) Source # 
Instance details

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

type Scalar = Array DIM0 Source #

Scalar arrays hold a single element

type Vector = Array DIM1 Source #

Vectors are one-dimensional arrays

type Matrix = Array DIM2 Source #

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

Array elements

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

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

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

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

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

Minimal complete definition

eltType, fromElt, toElt

Instances
Elt Bool Source # 
Instance details

Methods

eltType :: Bool -> TupleType (EltRepr Bool)

fromElt :: Bool -> EltRepr Bool

toElt :: EltRepr Bool -> Bool

Elt Char Source # 
Instance details

Methods

eltType :: Char -> TupleType (EltRepr Char)

fromElt :: Char -> EltRepr Char

toElt :: EltRepr Char -> Char

Elt Double Source # 
Instance details

Methods

eltType :: Double -> TupleType (EltRepr Double)

fromElt :: Double -> EltRepr Double

toElt :: EltRepr Double -> Double

Elt Float Source # 
Instance details

Methods

eltType :: Float -> TupleType (EltRepr Float)

fromElt :: Float -> EltRepr Float

toElt :: EltRepr Float -> Float

Elt Int Source # 
Instance details

Methods

eltType :: Int -> TupleType (EltRepr Int)

fromElt :: Int -> EltRepr Int

toElt :: EltRepr Int -> Int

Elt Int8 Source # 
Instance details

Methods

eltType :: Int8 -> TupleType (EltRepr Int8)

fromElt :: Int8 -> EltRepr Int8

toElt :: EltRepr Int8 -> Int8

Elt Int16 Source # 
Instance details

Methods

eltType :: Int16 -> TupleType (EltRepr Int16)

fromElt :: Int16 -> EltRepr Int16

toElt :: EltRepr Int16 -> Int16

Elt Int32 Source # 
Instance details

Methods

eltType :: Int32 -> TupleType (EltRepr Int32)

fromElt :: Int32 -> EltRepr Int32

toElt :: EltRepr Int32 -> Int32

Elt Int64 Source # 
Instance details

Methods

eltType :: Int64 -> TupleType (EltRepr Int64)

fromElt :: Int64 -> EltRepr Int64

toElt :: EltRepr Int64 -> Int64

Elt Ordering Source # 
Instance details

Methods

eltType :: Ordering -> TupleType (EltRepr Ordering)

fromElt :: Ordering -> EltRepr Ordering

toElt :: EltRepr Ordering -> Ordering

Elt Word Source # 
Instance details

Methods

eltType :: Word -> TupleType (EltRepr Word)

fromElt :: Word -> EltRepr Word

toElt :: EltRepr Word -> Word

Elt Word8 Source # 
Instance details

Methods

eltType :: Word8 -> TupleType (EltRepr Word8)

fromElt :: Word8 -> EltRepr Word8

toElt :: EltRepr Word8 -> Word8

Elt Word16 Source # 
Instance details

Methods

eltType :: Word16 -> TupleType (EltRepr Word16)

fromElt :: Word16 -> EltRepr Word16

toElt :: EltRepr Word16 -> Word16

Elt Word32 Source # 
Instance details

Methods

eltType :: Word32 -> TupleType (EltRepr Word32)

fromElt :: Word32 -> EltRepr Word32

toElt :: EltRepr Word32 -> Word32

Elt Word64 Source # 
Instance details

Methods

eltType :: Word64 -> TupleType (EltRepr Word64)

fromElt :: Word64 -> EltRepr Word64

toElt :: EltRepr Word64 -> Word64

Elt () Source # 
Instance details

Methods

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

fromElt :: () -> EltRepr ()

toElt :: EltRepr () -> ()

Elt CChar Source # 
Instance details

Methods

eltType :: CChar -> TupleType (EltRepr CChar)

fromElt :: CChar -> EltRepr CChar

toElt :: EltRepr CChar -> CChar

Elt CSChar Source # 
Instance details

Methods

eltType :: CSChar -> TupleType (EltRepr CSChar)

fromElt :: CSChar -> EltRepr CSChar

toElt :: EltRepr CSChar -> CSChar

Elt CUChar Source # 
Instance details

Methods

eltType :: CUChar -> TupleType (EltRepr CUChar)

fromElt :: CUChar -> EltRepr CUChar

toElt :: EltRepr CUChar -> CUChar

Elt CShort Source # 
Instance details

Methods

eltType :: CShort -> TupleType (EltRepr CShort)

fromElt :: CShort -> EltRepr CShort

toElt :: EltRepr CShort -> CShort

Elt CUShort Source # 
Instance details

Methods

eltType :: CUShort -> TupleType (EltRepr CUShort)

fromElt :: CUShort -> EltRepr CUShort

toElt :: EltRepr CUShort -> CUShort

Elt CInt Source # 
Instance details

Methods

eltType :: CInt -> TupleType (EltRepr CInt)

fromElt :: CInt -> EltRepr CInt

toElt :: EltRepr CInt -> CInt

Elt CUInt Source # 
Instance details

Methods

eltType :: CUInt -> TupleType (EltRepr CUInt)

fromElt :: CUInt -> EltRepr CUInt

toElt :: EltRepr CUInt -> CUInt

Elt CLong Source # 
Instance details

Methods

eltType :: CLong -> TupleType (EltRepr CLong)

fromElt :: CLong -> EltRepr CLong

toElt :: EltRepr CLong -> CLong

Elt CULong Source # 
Instance details

Methods

eltType :: CULong -> TupleType (EltRepr CULong)

fromElt :: CULong -> EltRepr CULong

toElt :: EltRepr CULong -> CULong

Elt CLLong Source # 
Instance details

Methods

eltType :: CLLong -> TupleType (EltRepr CLLong)

fromElt :: CLLong -> EltRepr CLLong

toElt :: EltRepr CLLong -> CLLong

Elt CULLong Source # 
Instance details

Methods

eltType :: CULLong -> TupleType (EltRepr CULLong)

fromElt :: CULLong -> EltRepr CULLong

toElt :: EltRepr CULLong -> CULLong

Elt CFloat Source # 
Instance details

Methods

eltType :: CFloat -> TupleType (EltRepr CFloat)

fromElt :: CFloat -> EltRepr CFloat

toElt :: EltRepr CFloat -> CFloat

Elt CDouble Source # 
Instance details

Methods

eltType :: CDouble -> TupleType (EltRepr CDouble)

fromElt :: CDouble -> EltRepr CDouble

toElt :: EltRepr CDouble -> CDouble

Elt Half Source # 
Instance details

Methods

eltType :: Half -> TupleType (EltRepr Half)

fromElt :: Half -> EltRepr Half

toElt :: EltRepr Half -> Half

Elt All Source # 
Instance details

Methods

eltType :: All -> TupleType (EltRepr All)

fromElt :: All -> EltRepr All

toElt :: EltRepr All -> All

Elt Z Source # 
Instance details

Methods

eltType :: Z -> TupleType (EltRepr Z)

fromElt :: Z -> EltRepr Z

toElt :: EltRepr Z -> Z

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

Methods

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

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

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

Elt (Complex Double) Source # 
Instance details

Methods

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

fromElt :: Complex Double -> EltRepr (Complex Double)

toElt :: EltRepr (Complex Double) -> Complex Double

Elt (Complex Float) Source # 
Instance details

Methods

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

fromElt :: Complex Float -> EltRepr (Complex Float)

toElt :: EltRepr (Complex Float) -> Complex Float

Elt (Complex CFloat) Source # 
Instance details

Methods

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

fromElt :: Complex CFloat -> EltRepr (Complex CFloat)

toElt :: EltRepr (Complex CFloat) -> Complex CFloat

Elt (Complex CDouble) Source # 
Instance details

Methods

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

fromElt :: Complex CDouble -> EltRepr (Complex CDouble)

toElt :: EltRepr (Complex CDouble) -> Complex CDouble

Elt (Complex Half) Source # 
Instance details

Methods

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

fromElt :: Complex Half -> EltRepr (Complex Half)

toElt :: EltRepr (Complex Half) -> Complex Half

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

Elt (Any Z) Source # 
Instance details

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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
Eq Z Source # 
Instance details

Methods

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

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

Show Z Source # 
Instance details

Methods

showsPrec :: Int -> Z -> ShowS #

show :: Z -> String #

showList :: [Z] -> ShowS #

Slice Z Source # 
Instance details

Associated Types

type SliceShape Z :: * Source #

type CoSliceShape Z :: * Source #

type FullShape Z :: * Source #

Methods

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

Shape Z Source # 
Instance details

Methods

rank :: Z -> Int

size :: Z -> Int

empty :: Z

ignore :: Z

intersect :: Z -> Z -> Z

union :: Z -> Z -> Z

toIndex :: Z -> Z -> Int

fromIndex :: Z -> Int -> Z

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

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

rangeToShape :: (Z, Z) -> Z

shapeToRange :: Z -> (Z, Z)

shapeToList :: Z -> [Int]

listToShape :: [Int] -> Z

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

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

Elt Z Source # 
Instance details

Methods

eltType :: Z -> TupleType (EltRepr Z)

fromElt :: Z -> EltRepr Z

toElt :: EltRepr Z -> Z

Unlift Exp Z Source # 
Instance details

Methods

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

Lift Exp Z Source # 
Instance details

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

Elt e => IsList (Vector e) Source # 
Instance details

Associated Types

type Item (Vector e) :: * #

Methods

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

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

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

Show (Vector e) Source # 
Instance details

Methods

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

show :: Vector e -> String #

showList :: [Vector e] -> ShowS #

Show (Scalar e) Source # 
Instance details

Methods

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

show :: Scalar e -> String #

showList :: [Scalar e] -> ShowS #

Elt (Any Z) Source # 
Instance details

Methods

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

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

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

Show (Array DIM2 e) Source # 
Instance details

Methods

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

show :: Array DIM2 e -> String #

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

type SliceShape Z Source # 
Instance details
type SliceShape Z = Z
type CoSliceShape Z Source # 
Instance details
type FullShape Z Source # 
Instance details
type FullShape Z = Z
type Plain Z Source # 
Instance details
type Plain Z = Z
type Item (Vector e) Source # 
Instance details
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
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e) Source # 
Instance details

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

Elt e => IsList (Vector e) Source # 
Instance details

Associated Types

type Item (Vector e) :: * #

Methods

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

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

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

Show (Vector e) Source # 
Instance details

Methods

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

show :: Vector e -> String #

showList :: [Vector e] -> ShowS #

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

Methods

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

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

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

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

Methods

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

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

Show (Array DIM2 e) Source # 
Instance details

Methods

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

show :: Array DIM2 e -> String #

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

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

Methods

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

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

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

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

Associated Types

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

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

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

Methods

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

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

Associated Types

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

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

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

Methods

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

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

Methods

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

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

empty :: sh :. Int

ignore :: sh :. Int

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

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

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

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

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

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

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

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

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

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

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

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

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

Methods

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

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

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

type DIM0 = Z Source #

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

Shapes and indices of multi-dimensional arrays

Minimal complete definition

sliceAnyIndex, sliceNoneIndex

Instances
Shape Z Source # 
Instance details

Methods

rank :: Z -> Int

size :: Z -> Int

empty :: Z

ignore :: Z

intersect :: Z -> Z -> Z

union :: Z -> Z -> Z

toIndex :: Z -> Z -> Int

fromIndex :: Z -> Int -> Z

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

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

rangeToShape :: (Z, Z) -> Z

shapeToRange :: Z -> (Z, Z)

shapeToList :: Z -> [Int]

listToShape :: [Int] -> Z

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

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

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

Methods

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

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

empty :: sh :. Int

ignore :: sh :. Int

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Minimal complete definition

sliceIndex

Associated Types

type SliceShape sl :: * Source #

type CoSliceShape sl :: * Source #

type FullShape sl :: * Source #

Methods

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

Instances
Slice Z Source # 
Instance details

Associated Types

type SliceShape Z :: * Source #

type CoSliceShape Z :: * Source #

type FullShape Z :: * Source #

Methods

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

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

Associated Types

type SliceShape (Any sh) :: * Source #

type CoSliceShape (Any sh) :: * Source #

type FullShape (Any sh) :: * Source #

Methods

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

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

Associated Types

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

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

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

Methods

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

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

Associated Types

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

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

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

Methods

sliceIndex :: (sl :. All) -> SliceIndex (EltRepr (sl :. All)) (EltRepr (SliceShape (sl :. All))) (EltRepr (CoSliceShape (sl :. All))) (EltRepr (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
Eq All Source # 
Instance details

Methods

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

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

Show All Source # 
Instance details

Methods

showsPrec :: Int -> All -> ShowS #

show :: All -> String #

showList :: [All] -> ShowS #

Elt All Source # 
Instance details

Methods

eltType :: All -> TupleType (EltRepr All)

fromElt :: All -> EltRepr All

toElt :: EltRepr All -> All

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

Associated Types

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

Methods

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

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

Associated Types

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

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

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

Methods

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

type SliceShape (sl :. All) Source # 
Instance details
type SliceShape (sl :. All) = SliceShape sl :. Int
type CoSliceShape (sl :. All) Source # 
Instance details
type FullShape (sl :. All) Source # 
Instance details
type FullShape (sl :. All) = FullShape sl :. Int
type Plain (ix :. All) Source # 
Instance details
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
Shape sh => Lift Exp (Any sh) Source # 
Instance details

Associated Types

type Plain (Any sh) :: * Source #

Methods

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

Eq (Any sh) Source # 
Instance details

Methods

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

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

Show (Any sh) Source # 
Instance details

Methods

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

show :: Any sh -> String #

showList :: [Any sh] -> ShowS #

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

Associated Types

type SliceShape (Any sh) :: * Source #

type CoSliceShape (Any sh) :: * Source #

type FullShape (Any sh) :: * Source #

Methods

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

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

Methods

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

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

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

Elt (Any Z) Source # 
Instance details

Methods

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

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

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

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

Array access

Element indexing

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

(!!) :: (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 :: (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 :: 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 :: 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 :: 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 :: (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 (index1 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 (index1 10) (\ix -> unindex1 ix + 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

(++) :: forall sh e. (Slice sh, Shape sh, Elt e) => Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e) infixr 5 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]

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

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

Minimal complete definition

ifThenElse

Associated Types

type EltT t a :: Constraint Source #

Methods

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

Instances
IfThenElse Exp Source # 
Instance details

Associated Types

type EltT Exp a :: Constraint Source #

Methods

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

IfThenElse Acc Source # 
Instance details

Associated Types

type EltT Acc a :: Constraint Source #

Methods

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

Controlling execution

(>->) :: (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 :: (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 :: (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 8-tuples and return eight arrays, analogous to unzip.

Modifying Arrays

Shape manipulation

reshape :: (Shape sh, Shape sh', Elt e) => Exp sh -> Acc (Array sh' e) -> Acc (Array sh e) 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 :: (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 :: (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 :: forall sh e. (Slice sh, 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 :: forall sh e. (Slice sh, 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 :: forall sh e. (Slice sh, 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 :: forall sh e. (Slice sh, 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

:: (Slice sh, 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

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

combination function

-> Acc (Array sh' a)

array of default values

-> (Exp sh -> Exp sh')

index permutation function

-> Acc (Array sh a)

array of source values to be permuted

-> Acc (Array sh' a) 

Generalised forward permutation operation (array scatter).

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

The combination function must be associative and commutative. Elements that are mapped to the magic index ignore by the permutation function 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 -> index1 (xs!ix)) ones
:}
>>> let xs = fromList (Z :. 20) [0,0,1,2,1,1,2,4,8,3,4,9,8,3,2,5,5,3,1,2] :: 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 (index2 n n) 0
            ones  = fill (index1 n)   1
        in
        permute const zeros (\(unindex1 -> i) -> index2 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.

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.

ignore :: Shape sh => Exp sh Source #

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

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

:: (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 :: forall sh e. (Shape sh, Slice 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])

Folding

fold :: (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 (\v -> let (x,_,_,_) = unlift v :: (Exp e, Exp e, Exp e, Exp e) in x)
        . fold1 f
        . map g
        where
          f :: (Num a, Ord a) => Exp (a,a,a,a) -> Exp (a,a,a,a) -> Exp (a,a,a,a)
          f x y =
            let (mssx, misx, mcsx, tsx) = unlift x
                (mssy, misy, mcsy, tsy) = unlift y
            in
            lift ( mssx `max` (mssy `max` (mcsx+misy))
                 , misx `max` (tsx+misy)
                 , mcsy `max` (mcsx+tsy)
                 , tsx+tsy
                 )
          --
          g :: (Num a, Ord a) => Exp a -> Exp (a,a,a,a)
          g x = let y = max x 0
                in  lift (y,y,y,x)
:}
>>> let vec = fromList (Z:.10) [-2,1,-3,4,-1,2,1,-5,4,0] :: 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 :: (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 :: (Shape sh, Elt a, Elt i, IsIntegral i) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Segments i) -> Acc (Array (sh :. Int) a) 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 :: (Shape sh, Elt a, Elt i, IsIntegral i) => (Exp a -> Exp a -> Exp a) -> Acc (Array (sh :. Int) a) -> Acc (Segments i) -> Acc (Array (sh :. Int) a) 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 length of each of the logical sub-arrays.

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 :: (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 :: (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' :: (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 :: (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 :: (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' :: (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

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

stencil2 Source #

Arguments

:: (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 (Elt (StencilRepr sh stencil), Stencil sh a (StencilRepr sh stencil)) => Stencil sh a stencil Source #

Minimal complete definition

stencilPrj

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

data Boundary 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 :: (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
IfThenElse Exp Source # 
Instance details

Associated Types

type EltT Exp a :: Constraint Source #

Methods

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

Unlift Exp () Source # 
Instance details

Methods

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

Unlift Exp Z Source # 
Instance details

Methods

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

Lift Exp Bool Source # 
Instance details

Associated Types

type Plain Bool :: * Source #

Methods

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

Lift Exp Char Source # 
Instance details

Associated Types

type Plain Char :: * Source #

Methods

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

Lift Exp Double Source # 
Instance details

Associated Types

type Plain Double :: * Source #

Methods

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

Lift Exp Float Source # 
Instance details

Associated Types

type Plain Float :: * Source #

Methods

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

Lift Exp Int Source # 
Instance details

Associated Types

type Plain Int :: * Source #

Methods

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

Lift Exp Int8 Source # 
Instance details

Associated Types

type Plain Int8 :: * Source #

Methods

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

Lift Exp Int16 Source # 
Instance details

Associated Types

type Plain Int16 :: * Source #

Methods

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

Lift Exp Int32 Source # 
Instance details

Associated Types

type Plain Int32 :: * Source #

Methods

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

Lift Exp Int64 Source # 
Instance details

Associated Types

type Plain Int64 :: * Source #

Methods

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

Lift Exp Word Source # 
Instance details

Associated Types

type Plain Word :: * Source #

Methods

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

Lift Exp Word8 Source # 
Instance details

Associated Types

type Plain Word8 :: * Source #

Methods

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

Lift Exp Word16 Source # 
Instance details

Associated Types

type Plain Word16 :: * Source #

Methods

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

Lift Exp Word32 Source # 
Instance details

Associated Types

type Plain Word32 :: * Source #

Methods

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

Lift Exp Word64 Source # 
Instance details

Associated Types

type Plain Word64 :: * Source #

Methods

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

Lift Exp () Source # 
Instance details

Associated Types

type Plain () :: * Source #

Methods

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

Lift Exp CChar Source # 
Instance details

Associated Types

type Plain CChar :: * Source #

Methods

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

Lift Exp CSChar Source # 
Instance details

Associated Types

type Plain CSChar :: * Source #

Methods

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

Lift Exp CUChar Source # 
Instance details

Associated Types

type Plain CUChar :: * Source #

Methods

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

Lift Exp CShort Source # 
Instance details

Associated Types

type Plain CShort :: * Source #

Methods

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

Lift Exp CUShort Source # 
Instance details

Associated Types

type Plain CUShort :: * Source #

Lift Exp CInt Source # 
Instance details

Associated Types

type Plain CInt :: * Source #

Methods

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

Lift Exp CUInt Source # 
Instance details

Associated Types

type Plain CUInt :: * Source #

Methods

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

Lift Exp CLong Source # 
Instance details

Associated Types

type Plain CLong :: * Source #

Methods

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

Lift Exp CULong Source # 
Instance details

Associated Types

type Plain CULong :: * Source #

Methods

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

Lift Exp CLLong Source # 
Instance details

Associated Types

type Plain CLLong :: * Source #

Methods

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

Lift Exp CULLong Source # 
Instance details

Associated Types

type Plain CULLong :: * Source #

Lift Exp CFloat Source # 
Instance details

Associated Types

type Plain CFloat :: * Source #

Methods

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

Lift Exp CDouble Source # 
Instance details

Associated Types

type Plain CDouble :: * Source #

Lift Exp Z Source # 
Instance details

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

Unlift Exp (Exp e) Source # 
Instance details

Methods

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

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

Associated Types

type Plain (Maybe a) :: * Source #

Methods

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

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

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

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

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

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

Associated Types

type Plain (Product a) :: * Source #

Methods

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

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

Associated Types

type Plain (Any sh) :: * Source #

Methods

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

Lift Exp (Exp e) Source # 
Instance details

Associated Types

type Plain (Exp e) :: * Source #

Methods

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

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

Methods

unlift :: Exp (Plain (Exp a, Exp b)) -> (Exp a, Exp b) Source #

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

Methods

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

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

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

Associated Types

type Plain (Either a b) :: * Source #

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g)) => Lift Exp (a, b, c, d, e, f, g) Source # 
Instance details

Associated Types

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

Methods

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

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h) Source # 
Instance details

Methods

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

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h)) => Lift Exp (a, b, c, d, e, f, g, h) Source # 
Instance details

Associated Types

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

Methods

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

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i) Source # 
Instance details

Methods

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

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i)) => Lift Exp (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Associated Types

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

Methods

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

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j) Source # 
Instance details

Methods

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

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j)) => Lift Exp (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Associated Types

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

Methods

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

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k) Source # 
Instance details

Methods

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

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Associated Types

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

Methods

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

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k, Elt l) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l) Source # 
Instance details

Methods

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

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Lift Exp l, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k), Elt (Plain l)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Associated Types

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

Methods

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

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

Methods

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

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Lift Exp l, Lift Exp m, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k), Elt (Plain l), Elt (Plain m)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 
Instance details

Associated Types

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

Methods

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

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

Methods

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

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Lift Exp l, Lift Exp m, Lift Exp n, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k), Elt (Plain l), Elt (Plain m), Elt (Plain n)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 
Instance details

Associated Types

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

Methods

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

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

Methods

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

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Lift Exp l, Lift Exp m, Lift Exp n, Lift Exp o, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k), Elt (Plain l), Elt (Plain m), Elt (Plain n), Elt (Plain o)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 
Instance details

Associated Types

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

Methods

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

Bounded (Exp Bool) # 
Instance details
Bounded (Exp Char) # 
Instance details
Bounded (Exp Int) # 
Instance details
Bounded (Exp Int8) # 
Instance details
Bounded (Exp Int16) # 
Instance details
Bounded (Exp Int32) # 
Instance details
Bounded (Exp Int64) # 
Instance details
Bounded (Exp Word) # 
Instance details
Bounded (Exp Word8) # 
Instance details
Bounded (Exp Word16) # 
Instance details
Bounded (Exp Word32) # 
Instance details
Bounded (Exp Word64) # 
Instance details
Bounded (Exp ()) # 
Instance details

Methods

minBound :: Exp () #

maxBound :: Exp () #

(Bounded a, Bounded b) => Bounded (Exp (a, b)) # 
Instance details

Methods

minBound :: Exp (a, b) #

maxBound :: Exp (a, b) #

(Bounded a, Bounded b, Bounded c) => Bounded (Exp (a, b, c)) # 
Instance details

Methods

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

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

(Bounded a, Bounded b, Bounded c, Bounded d) => Bounded (Exp (a, b, c, d)) # 
Instance details

Methods

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

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

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e) => Bounded (Exp (a, b, c, d, e)) # 
Instance details

Methods

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

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

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f) => Bounded (Exp (a, b, c, d, e, f)) # 
Instance details

Methods

minBound :: Exp (a, b, c, d, e, f) #

maxBound :: Exp (a, b, c, d, e, f) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g) => Bounded (Exp (a, b, c, d, e, f, g)) # 
Instance details

Methods

minBound :: Exp (a, b, c, d, e, f, g) #

maxBound :: Exp (a, b, c, d, e, f, g) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h) => Bounded (Exp (a, b, c, d, e, f, g, h)) # 
Instance details

Methods

minBound :: Exp (a, b, c, d, e, f, g, h) #

maxBound :: Exp (a, b, c, d, e, f, g, h) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i) => Bounded (Exp (a, b, c, d, e, f, g, h, i)) # 
Instance details

Methods

minBound :: Exp (a, b, c, d, e, f, g, h, i) #

maxBound :: Exp (a, b, c, d, e, f, g, h, i) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j) => Bounded (Exp (a, b, c, d, e, f, g, h, i, j)) # 
Instance details

Methods

minBound :: Exp (a, b, c, d, e, f, g, h, i, j) #

maxBound :: Exp (a, b, c, d, e, f, g, h, i, j) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k) => Bounded (Exp (a, b, c, d, e, f, g, h, i, j, k)) # 
Instance details

Methods

minBound :: Exp (a, b, c, d, e, f, g, h, i, j, k) #

maxBound :: Exp (a, b, c, d, e, f, g, h, i, j, k) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l) => Bounded (Exp (a, b, c, d, e, f, g, h, i, j, k, l)) # 
Instance details

Methods

minBound :: Exp (a, b, c, d, e, f, g, h, i, j, k, l) #

maxBound :: Exp (a, b, c, d, e, f, g, h, i, j, k, l) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m) => Bounded (Exp (a, b, c, d, e, f, g, h, i, j, k, l, m)) # 
Instance details

Methods

minBound :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) #

maxBound :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) #

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

Methods

minBound :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) #

maxBound :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) #

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

Methods

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

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

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m, Bounded n, Bounded o, Bounded p) => Bounded (Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)) # 
Instance details

Methods

minBound :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) #

maxBound :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) #

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

Methods

minBound :: Exp (Min a) #

maxBound :: Exp (Min a) #

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

Methods

minBound :: Exp (Max a) #

maxBound :: Exp (Max a) #

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

Methods

minBound :: Exp (Sum a) #

maxBound :: Exp (Sum a) #

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

Methods

minBound :: Exp (Product a) #

maxBound :: Exp (Product a) #

Bounded (Exp CChar) # 
Instance details
Bounded (Exp CSChar) # 
Instance details
Bounded (Exp CUChar) # 
Instance details
Bounded (Exp CShort) # 
Instance details
Bounded (Exp CUShort) # 
Instance details
Bounded (Exp CInt) # 
Instance details
Bounded (Exp CUInt) # 
Instance details
Bounded (Exp CLong) # 
Instance details
Bounded (Exp CULong) # 
Instance details
Bounded (Exp CLLong) # 
Instance details
Bounded (Exp CULLong) # 
Instance details
Enum (Exp Double) # 
Instance details
Enum (Exp Float) # 
Instance details
Enum (Exp Int) # 
Instance details
Enum (Exp Int8) # 
Instance details
Enum (Exp Int16) # 
Instance details
Enum (Exp Int32) # 
Instance details
Enum (Exp Int64) # 
Instance details
Enum (Exp Word) # 
Instance details
Enum (Exp Word8) # 
Instance details
Enum (Exp Word16) # 
Instance details
Enum (Exp Word32) # 
Instance details
Enum (Exp Word64) # 
Instance details
Enum (Exp CShort) # 
Instance details
Enum (Exp CUShort) # 
Instance details
Enum (Exp CInt) # 
Instance details
Enum (Exp CUInt) # 
Instance details
Enum (Exp CLong) # 
Instance details
Enum (Exp CULong) # 
Instance details
Enum (Exp CLLong) # 
Instance details
Enum (Exp CULLong) # 
Instance details
Enum (Exp CFloat) # 
Instance details
Enum (Exp CDouble) # 
Instance details
Enum (Exp Half) # 
Instance details
Eq a => Eq (Exp a) # 
Instance details

Methods

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

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

Floating (Exp Double) # 
Instance details
Floating (Exp Float) # 
Instance details
(RealFloat a, Elt (Complex a)) => Floating (Exp (Complex a)) # 
Instance details

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) # 
Instance details
Floating (Exp CDouble) # 
Instance details
Floating (Exp Half) # 
Instance details
Fractional (Exp Double) # 
Instance details
Fractional (Exp Float) # 
Instance details
(RealFloat a, Elt (Complex a)) => Fractional (Exp (Complex a)) # 
Instance details

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) # 
Instance details
Fractional (Exp CDouble) # 
Instance details
Fractional (Exp Half) # 
Instance details
Integral (Exp Int) # 
Instance details

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) # 
Instance details
Integral (Exp Int16) # 
Instance details
Integral (Exp Int32) # 
Instance details
Integral (Exp Int64) # 
Instance details
Integral (Exp Word) # 
Instance details
Integral (Exp Word8) # 
Instance details
Integral (Exp Word16) # 
Instance details
Integral (Exp Word32) # 
Instance details
Integral (Exp Word64) # 
Instance details
Integral (Exp CShort) # 
Instance details
Integral (Exp CUShort) # 
Instance details
Integral (Exp CInt) # 
Instance details
Integral (Exp CUInt) # 
Instance details
Integral (Exp CLong) # 
Instance details
Integral (Exp CULong) # 
Instance details
Integral (Exp CLLong) # 
Instance details
Integral (Exp CULLong) # 
Instance details
Num (Exp Double) # 
Instance details
Num (Exp Float) # 
Instance details
Num (Exp Int) # 
Instance details

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) # 
Instance details
Num (Exp Int16) # 
Instance details
Num (Exp Int32) # 
Instance details
Num (Exp Int64) # 
Instance details
Num (Exp Word) # 
Instance details
Num (Exp Word8) # 
Instance details
Num (Exp Word16) # 
Instance details
Num (Exp Word32) # 
Instance details
Num (Exp Word64) # 
Instance details
(RealFloat a, Elt (Complex a)) => Num (Exp (Complex a)) # 
Instance details

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)) # 
Instance details

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)) # 
Instance details

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)) # 
Instance details

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)) # 
Instance details

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) # 
Instance details
Num (Exp CUShort) # 
Instance details
Num (Exp CInt) # 
Instance details
Num (Exp CUInt) # 
Instance details
Num (Exp CLong) # 
Instance details
Num (Exp CULong) # 
Instance details
Num (Exp CLLong) # 
Instance details
Num (Exp CULLong) # 
Instance details
Num (Exp CFloat) # 
Instance details
Num (Exp CDouble) # 
Instance details
Num (Exp Half) # 
Instance details
Ord a => Ord (Exp a) # 
Instance details

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) # 
Instance details

Methods

toRational :: Exp a -> Rational #

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

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) # 
Instance details

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) # 
Instance details

Methods

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

show :: Exp e -> String #

showList :: [Exp e] -> ShowS #

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

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)) # 
Instance details

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 ()) # 
Instance details

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)) # 
Instance details

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)) # 
Instance details

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)) # 
Instance details

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)) # 
Instance details

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)) # 
Instance details

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)) # 
Instance details

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

Since: 1.2.0.0

Instance details

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

Since: 1.2.0.0

Instance details

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)) # 
Instance details

Methods

mempty :: Exp (Maybe a) #

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

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

Monoid (Exp ()) # 
Instance details

Methods

mempty :: Exp () #

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

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

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

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)) # 
Instance details

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)) # 
Instance details

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)) # 
Instance details

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)) # 
Instance details

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)) # 
Instance details

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)) # 
Instance details

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)) # 
Instance details

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)) # 
Instance details

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)) # 
Instance details

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)) # 
Instance details

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) # 
Instance details

Methods

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

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

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

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

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
Eq Bool Source # 
Instance details
Eq Char Source # 
Instance details
Eq Double Source # 
Instance details
Eq Float Source # 
Instance details
Eq Int Source # 
Instance details

Methods

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

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

Eq Int8 Source # 
Instance details
Eq Int16 Source # 
Instance details
Eq Int32 Source # 
Instance details
Eq Int64 Source # 
Instance details
Eq Ordering Source # 
Instance details
Eq Word Source # 
Instance details
Eq Word8 Source # 
Instance details
Eq Word16 Source # 
Instance details
Eq Word32 Source # 
Instance details
Eq Word64 Source # 
Instance details
Eq () Source # 
Instance details

Methods

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

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

Eq CChar Source # 
Instance details
Eq CSChar Source # 
Instance details
Eq CUChar Source # 
Instance details
Eq CShort Source # 
Instance details
Eq CUShort Source # 
Instance details
Eq CInt Source # 
Instance details
Eq CUInt Source # 
Instance details
Eq CLong Source # 
Instance details
Eq CULong Source # 
Instance details
Eq CLLong Source # 
Instance details
Eq CULLong Source # 
Instance details
Eq CFloat Source # 
Instance details
Eq CDouble Source # 
Instance details
Eq Half Source # 
Instance details
Eq a => Eq (Maybe a) Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

(==) :: Exp (a, b, c, d) -> Exp (a, b, c, d) -> Exp Bool Source #

(/=) :: Exp (a, b, c, d) -> Exp (a, b, c, d) -> Exp Bool Source #

(Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e) Source # 
Instance details

Methods

(==) :: Exp (a, b, c, d, e) -> Exp (a, b, c, d, e) -> Exp Bool Source #

(/=) :: Exp (a, b, c, d, e) -> Exp (a, b, c, d, e) -> Exp Bool Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (a, b, c, d, e, f) Source # 
Instance details

Methods

(==) :: Exp (a, b, c, d, e, f) -> Exp (a, b, c, d, e, f) -> Exp Bool Source #

(/=) :: Exp (a, b, c, d, e, f) -> Exp (a, b, c, d, e, f) -> Exp Bool Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (a, b, c, d, e, f, g) Source # 
Instance details

Methods

(==) :: Exp (a, b, c, d, e, f, g) -> Exp (a, b, c, d, e, f, g) -> Exp Bool Source #

(/=) :: Exp (a, b, c, d, e, f, g) -> Exp (a, b, c, d, e, f, g) -> Exp Bool Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h) => Eq (a, b, c, d, e, f, g, h) Source # 
Instance details

Methods

(==) :: Exp (a, b, c, d, e, f, g, h) -> Exp (a, b, c, d, e, f, g, h) -> Exp Bool Source #

(/=) :: Exp (a, b, c, d, e, f, g, h) -> Exp (a, b, c, d, e, f, g, h) -> Exp Bool Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) => Eq (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Methods

(==) :: Exp (a, b, c, d, e, f, g, h, i) -> Exp (a, b, c, d, e, f, g, h, i) -> Exp Bool Source #

(/=) :: Exp (a, b, c, d, e, f, g, h, i) -> Exp (a, b, c, d, e, f, g, h, i) -> Exp Bool Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j) => Eq (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Methods

(==) :: Exp (a, b, c, d, e, f, g, h, i, j) -> Exp (a, b, c, d, e, f, g, h, i, j) -> Exp Bool Source #

(/=) :: Exp (a, b, c, d, e, f, g, h, i, j) -> Exp (a, b, c, d, e, f, g, h, i, j) -> Exp Bool Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k) => Eq (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Methods

(==) :: Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp Bool Source #

(/=) :: Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp Bool Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l) => Eq (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Methods

(==) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp Bool Source #

(/=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp Bool Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 
Instance details

Methods

(==) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp Bool Source #

(/=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp Bool Source #

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

Methods

(==) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp Bool Source #

(/=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp Bool Source #

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

Methods

(==) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp Bool Source #

(/=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp Bool Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o, Eq p) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source # 
Instance details

Methods

(==) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> Exp Bool Source #

(/=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> 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
Ord Bool Source # 
Instance details
Ord Char Source # 
Instance details
Ord Double Source # 
Instance details
Ord Float Source # 
Instance details
Ord Int Source # 
Instance details
Ord Int8 Source # 
Instance details
Ord Int16 Source # 
Instance details
Ord Int32 Source # 
Instance details
Ord Int64 Source # 
Instance details
Ord Ordering Source # 
Instance details
Ord Word Source # 
Instance details
Ord Word8 Source # 
Instance details
Ord Word16 Source # 
Instance details
Ord Word32 Source # 
Instance details
Ord Word64 Source # 
Instance details
Ord () Source # 
Instance details

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
Ord CSChar Source # 
Instance details
Ord CUChar Source # 
Instance details
Ord CShort Source # 
Instance details
Ord CUShort Source # 
Instance details
Ord CInt Source # 
Instance details
Ord CUInt Source # 
Instance details
Ord CLong Source # 
Instance details
Ord CULong Source # 
Instance details
Ord CLLong Source # 
Instance details
Ord CULLong Source # 
Instance details
Ord CFloat Source # 
Instance details
Ord CDouble Source # 
Instance details
Ord Half Source # 
Instance details
Ord a => Ord (Maybe a) Source # 
Instance details

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 #

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

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

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

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

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

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 a, Ord b) => Ord (a, b) Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

Methods

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

(>) :: Exp (a, b, c) -> Exp (a, b, c) -> Exp Bool Source #

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

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

min :: Exp (a, b, c) -> Exp (a, b, c) -> Exp (a, b, c) Source #

max :: Exp (a, b, c) -> Exp (a, b, c) -> Exp (a, b, c) Source #

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

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

Methods

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

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

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

(>=) :: Exp (a, b, c, d) -> Exp (a, b, c, d) -> Exp Bool Source #

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

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

compare :: Exp (a, b, c, d) -> Exp (a, b, c, d) -> Exp Ordering Source #

(Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) Source # 
Instance details

Methods

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

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

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

(>=) :: Exp (a, b, c, d, e) -> Exp (a, b, c, d, e) -> Exp Bool Source #

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

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

compare :: Exp (a, b, c, d, e) -> Exp (a, b, c, d, e) -> Exp Ordering Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f) => Ord (a, b, c, d, e, f) Source # 
Instance details

Methods

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

(>) :: Exp (a, b, c, d, e, f) -> Exp (a, b, c, d, e, f) -> Exp Bool Source #

(<=) :: Exp (a, b, c, d, e, f) -> Exp (a, b, c, d, e, f) -> Exp Bool Source #

(>=) :: Exp (a, b, c, d, e, f) -> Exp (a, b, c, d, e, f) -> Exp Bool Source #

min :: Exp (a, b, c, d, e, f) -> Exp (a, b, c, d, e, f) -> Exp (a, b, c, d, e, f) Source #

max :: Exp (a, b, c, d, e, f) -> Exp (a, b, c, d, e, f) -> Exp (a, b, c, d, e, f) Source #

compare :: Exp (a, b, c, d, e, f) -> Exp (a, b, c, d, e, f) -> Exp Ordering Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g) => Ord (a, b, c, d, e, f, g) Source # 
Instance details

Methods

(<) :: Exp (a, b, c, d, e, f, g) -> Exp (a, b, c, d, e, f, g) -> Exp Bool Source #

(>) :: Exp (a, b, c, d, e, f, g) -> Exp (a, b, c, d, e, f, g) -> Exp Bool Source #

(<=) :: Exp (a, b, c, d, e, f, g) -> Exp (a, b, c, d, e, f, g) -> Exp Bool Source #

(>=) :: Exp (a, b, c, d, e, f, g) -> Exp (a, b, c, d, e, f, g) -> Exp Bool Source #

min :: Exp (a, b, c, d, e, f, g) -> Exp (a, b, c, d, e, f, g) -> Exp (a, b, c, d, e, f, g) Source #

max :: Exp (a, b, c, d, e, f, g) -> Exp (a, b, c, d, e, f, g) -> Exp (a, b, c, d, e, f, g) Source #

compare :: Exp (a, b, c, d, e, f, g) -> Exp (a, b, c, d, e, f, g) -> Exp Ordering Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h) => Ord (a, b, c, d, e, f, g, h) Source # 
Instance details

Methods

(<) :: Exp (a, b, c, d, e, f, g, h) -> Exp (a, b, c, d, e, f, g, h) -> Exp Bool Source #

(>) :: Exp (a, b, c, d, e, f, g, h) -> Exp (a, b, c, d, e, f, g, h) -> Exp Bool Source #

(<=) :: Exp (a, b, c, d, e, f, g, h) -> Exp (a, b, c, d, e, f, g, h) -> Exp Bool Source #

(>=) :: Exp (a, b, c, d, e, f, g, h) -> Exp (a, b, c, d, e, f, g, h) -> Exp Bool Source #

min :: Exp (a, b, c, d, e, f, g, h) -> Exp (a, b, c, d, e, f, g, h) -> Exp (a, b, c, d, e, f, g, h) Source #

max :: Exp (a, b, c, d, e, f, g, h) -> Exp (a, b, c, d, e, f, g, h) -> Exp (a, b, c, d, e, f, g, h) Source #

compare :: Exp (a, b, c, d, e, f, g, h) -> Exp (a, b, c, d, e, f, g, h) -> Exp Ordering Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) => Ord (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Methods

(<) :: Exp (a, b, c, d, e, f, g, h, i) -> Exp (a, b, c, d, e, f, g, h, i) -> Exp Bool Source #

(>) :: Exp (a, b, c, d, e, f, g, h, i) -> Exp (a, b, c, d, e, f, g, h, i) -> Exp Bool Source #

(<=) :: Exp (a, b, c, d, e, f, g, h, i) -> Exp (a, b, c, d, e, f, g, h, i) -> Exp Bool Source #

(>=) :: Exp (a, b, c, d, e, f, g, h, i) -> Exp (a, b, c, d, e, f, g, h, i) -> Exp Bool Source #

min :: Exp (a, b, c, d, e, f, g, h, i) -> Exp (a, b, c, d, e, f, g, h, i) -> Exp (a, b, c, d, e, f, g, h, i) Source #

max :: Exp (a, b, c, d, e, f, g, h, i) -> Exp (a, b, c, d, e, f, g, h, i) -> Exp (a, b, c, d, e, f, g, h, i) Source #

compare :: Exp (a, b, c, d, e, f, g, h, i) -> Exp (a, b, c, d, e, f, g, h, i) -> Exp Ordering Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j) => Ord (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Methods

(<) :: Exp (a, b, c, d, e, f, g, h, i, j) -> Exp (a, b, c, d, e, f, g, h, i, j) -> Exp Bool Source #

(>) :: Exp (a, b, c, d, e, f, g, h, i, j) -> Exp (a, b, c, d, e, f, g, h, i, j) -> Exp Bool Source #

(<=) :: Exp (a, b, c, d, e, f, g, h, i, j) -> Exp (a, b, c, d, e, f, g, h, i, j) -> Exp Bool Source #

(>=) :: Exp (a, b, c, d, e, f, g, h, i, j) -> Exp (a, b, c, d, e, f, g, h, i, j) -> Exp Bool Source #

min :: Exp (a, b, c, d, e, f, g, h, i, j) -> Exp (a, b, c, d, e, f, g, h, i, j) -> Exp (a, b, c, d, e, f, g, h, i, j) Source #

max :: Exp (a, b, c, d, e, f, g, h, i, j) -> Exp (a, b, c, d, e, f, g, h, i, j) -> Exp (a, b, c, d, e, f, g, h, i, j) Source #

compare :: Exp (a, b, c, d, e, f, g, h, i, j) -> Exp (a, b, c, d, e, f, g, h, i, j) -> Exp Ordering Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k) => Ord (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Methods

(<) :: Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp Bool Source #

(>) :: Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp Bool Source #

(<=) :: Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp Bool Source #

(>=) :: Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp Bool Source #

min :: Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp (a, b, c, d, e, f, g, h, i, j, k) Source #

max :: Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp (a, b, c, d, e, f, g, h, i, j, k) Source #

compare :: Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp Ordering Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l) => Ord (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Methods

(<) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp Bool Source #

(>) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp Bool Source #

(<=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp Bool Source #

(>=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp Bool Source #

min :: Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l) Source #

max :: Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l) Source #

compare :: Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp Ordering Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 
Instance details

Methods

(<) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp Bool Source #

(>) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp Bool Source #

(<=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp Bool Source #

(>=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp Bool Source #

min :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

max :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

compare :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp Ordering Source #

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

Methods

(<) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp Bool Source #

(>) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp Bool Source #

(<=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp Bool Source #

(>=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp Bool Source #

min :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

max :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

compare :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp Ordering Source #

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

Methods

(<) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp Bool Source #

(>) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp Bool Source #

(<=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp Bool Source #

(>=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp Bool Source #

min :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

max :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

compare :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp Ordering Source #

data Ordering #

Constructors

LT 
EQ 
GT 
Instances
Bounded Ordering

Since: 2.1

Instance details
Enum Ordering

Since: 2.1

Instance details
Eq Ordering 
Instance details
Ord Ordering 
Instance details
Read Ordering

Since: 2.1

Instance details
Show Ordering 
Instance details
Generic Ordering 
Instance details

Associated Types

type Rep Ordering :: * -> * #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Semigroup Ordering

Since: 4.9.0.0

Instance details
Monoid Ordering

Since: 2.1

Instance details
NFData Ordering 
Instance details

Methods

rnf :: Ordering -> () #

Hashable Ordering 
Instance details

Methods

hashWithSalt :: Int -> Ordering -> Int #

hash :: Ordering -> Int #

AsEmpty Ordering 
Instance details

Methods

_Empty :: Prism' Ordering () #

Elt Ordering Source # 
Instance details

Methods

eltType :: Ordering -> TupleType (EltRepr Ordering)

fromElt :: Ordering -> EltRepr Ordering

toElt :: EltRepr Ordering -> Ordering

Eq Ordering Source # 
Instance details
Ord Ordering Source # 
Instance details
() :=> (Bounded Ordering) 
Instance details

Methods

ins :: () :- Bounded Ordering #

() :=> (Enum Ordering) 
Instance details

Methods

ins :: () :- Enum Ordering #

() :=> (Read Ordering) 
Instance details

Methods

ins :: () :- Read Ordering #

() :=> (Show Ordering) 
Instance details

Methods

ins :: () :- Show Ordering #

() :=> (Semigroup Ordering) 
Instance details

Methods

ins :: () :- Semigroup Ordering #

() :=> (Monoid Ordering) 
Instance details

Methods

ins :: () :- Monoid Ordering #

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

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 #

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

type Integral a = (Enum a, Real 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

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

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

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 (Real a, Fractional a) => RealFrac a where Source #

Extracting components of fractions.

Minimal complete definition

properFraction, truncate, round, ceiling, floor

Methods

properFraction :: (Num b, ToFloating b a, IsIntegral b) => Exp a -> (Exp b, Exp a) Source #

truncate :: (Elt b, IsIntegral b) => Exp a -> Exp b Source #

truncate x returns the integer nearest x between zero and x

round :: (Elt b, IsIntegral 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 :: (Elt b, IsIntegral b) => Exp a -> Exp b Source #

ceiling x returns the least integer not less than x

floor :: (Elt b, IsIntegral b) => Exp a -> Exp b Source #

floor x returns the greatest integer not greater than x

Instances
RealFrac Double Source # 
Instance details
RealFrac Float Source # 
Instance details
RealFrac CFloat Source # 
Instance details
RealFrac CDouble Source # 
Instance details
RealFrac Half Source # 
Instance details

Methods

properFraction :: (Num b, ToFloating b Half, IsIntegral b) => Exp Half -> (Exp b, Exp Half) Source #

truncate :: (Elt b, IsIntegral b) => Exp Half -> Exp b Source #

round :: (Elt b, IsIntegral b) => Exp Half -> Exp b Source #

ceiling :: (Elt b, IsIntegral b) => Exp Half -> Exp b Source #

floor :: (Elt b, IsIntegral b) => Exp Half -> Exp b Source #

div' :: (RealFrac a, Elt b, IsIntegral b) => Exp a -> Exp a -> Exp b Source #

Generalisation of div to any instance of RealFrac

mod' :: (Floating a, RealFrac a, ToFloating Int a) => Exp a -> Exp a -> Exp a Source #

Generalisation of mod to any instance of RealFrac

divMod' :: (Floating a, RealFrac a, Num b, IsIntegral 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)

floatRadix :: RealFloat a => Exp a -> Exp Int64 Source #

The radix of the representation (often 2) (constant)

floatDigits :: Exp a -> Exp Int Source #

The number of digits of floatRadix in the significand (constant)

floatDigits :: RealFloat a => Exp a -> Exp Int Source #

The number of digits of floatRadix in the significand (constant)

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

The lowest and highest values the exponent may assume (constant)

floatRange :: RealFloat a => Exp a -> (Exp Int, Exp Int) Source #

The lowest and highest values the exponent may assume (constant)

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

encodeFloat :: (FromIntegral Int a, FromIntegral Int64 a) => 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

isIEEE :: RealFloat a => Exp a -> Exp Bool Source #

True if the argument is an IEEE floating point number

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
RealFloat Double Source # 
Instance details
RealFloat Float Source # 
Instance details
RealFloat CFloat Source # 
Instance details
RealFloat CDouble Source # 
Instance details
RealFloat Half Source # 
Instance details

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.

Minimal complete definition

fromIntegral

Methods

fromIntegral :: Integral a => Exp a -> Exp b Source #

General coercion from integral types

Instances
FromIntegral Int Double Source # 
Instance details
FromIntegral Int Float Source # 
Instance details
FromIntegral Int Int Source # 
Instance details
FromIntegral Int Int8 Source # 
Instance details
FromIntegral Int Int16 Source # 
Instance details
FromIntegral Int Int32 Source # 
Instance details
FromIntegral Int Int64 Source # 
Instance details
FromIntegral Int Word Source # 
Instance details
FromIntegral Int Word8 Source # 
Instance details
FromIntegral Int Word16 Source # 
Instance details
FromIntegral Int Word32 Source # 
Instance details
FromIntegral Int Word64 Source # 
Instance details
FromIntegral Int CShort Source # 
Instance details
FromIntegral Int CUShort Source # 
Instance details
FromIntegral Int CInt Source # 
Instance details
FromIntegral Int CUInt Source # 
Instance details
FromIntegral Int CLong Source # 
Instance details
FromIntegral Int CULong Source # 
Instance details
FromIntegral Int CLLong Source # 
Instance details
FromIntegral Int CULLong Source # 
Instance details
FromIntegral Int CFloat Source # 
Instance details
FromIntegral Int CDouble Source # 
Instance details
FromIntegral Int Half Source # 
Instance details
FromIntegral Int8 Double Source # 
Instance details
FromIntegral Int8 Float Source # 
Instance details
FromIntegral Int8 Int Source # 
Instance details
FromIntegral Int8 Int8 Source # 
Instance details
FromIntegral Int8 Int16 Source # 
Instance details
FromIntegral Int8 Int32 Source # 
Instance details
FromIntegral Int8 Int64 Source # 
Instance details
FromIntegral Int8 Word Source # 
Instance details
FromIntegral Int8 Word8 Source # 
Instance details
FromIntegral Int8 Word16 Source # 
Instance details
FromIntegral Int8 Word32 Source # 
Instance details
FromIntegral Int8 Word64 Source # 
Instance details
FromIntegral Int8 CShort Source # 
Instance details
FromIntegral Int8 CUShort Source # 
Instance details
FromIntegral Int8 CInt Source # 
Instance details
FromIntegral Int8 CUInt Source # 
Instance details
FromIntegral Int8 CLong Source # 
Instance details
FromIntegral Int8 CULong Source # 
Instance details
FromIntegral Int8 CLLong Source # 
Instance details
FromIntegral Int8 CULLong Source # 
Instance details
FromIntegral Int8 CFloat Source # 
Instance details
FromIntegral Int8 CDouble Source # 
Instance details
FromIntegral Int8 Half Source # 
Instance details
FromIntegral Int16 Double Source # 
Instance details
FromIntegral Int16 Float Source # 
Instance details
FromIntegral Int16 Int Source # 
Instance details
FromIntegral Int16 Int8 Source # 
Instance details
FromIntegral Int16 Int16 Source # 
Instance details
FromIntegral Int16 Int32 Source # 
Instance details
FromIntegral Int16 Int64 Source # 
Instance details
FromIntegral Int16 Word Source # 
Instance details
FromIntegral Int16 Word8 Source # 
Instance details
FromIntegral Int16 Word16 Source # 
Instance details
FromIntegral Int16 Word32 Source # 
Instance details
FromIntegral Int16 Word64 Source # 
Instance details
FromIntegral Int16 CShort Source # 
Instance details
FromIntegral Int16 CUShort Source # 
Instance details
FromIntegral Int16 CInt Source # 
Instance details
FromIntegral Int16 CUInt Source # 
Instance details
FromIntegral Int16 CLong Source # 
Instance details
FromIntegral Int16 CULong Source # 
Instance details
FromIntegral Int16 CLLong Source # 
Instance details
FromIntegral Int16 CULLong Source # 
Instance details
FromIntegral Int16 CFloat Source # 
Instance details
FromIntegral Int16 CDouble Source # 
Instance details
FromIntegral Int16 Half Source # 
Instance details
FromIntegral Int32 Double Source # 
Instance details
FromIntegral Int32 Float Source # 
Instance details
FromIntegral Int32 Int Source # 
Instance details
FromIntegral Int32 Int8 Source # 
Instance details
FromIntegral Int32 Int16 Source # 
Instance details
FromIntegral Int32 Int32 Source # 
Instance details
FromIntegral Int32 Int64 Source # 
Instance details
FromIntegral Int32 Word Source # 
Instance details
FromIntegral Int32 Word8 Source # 
Instance details
FromIntegral Int32 Word16 Source # 
Instance details
FromIntegral Int32 Word32 Source # 
Instance details
FromIntegral Int32 Word64 Source # 
Instance details
FromIntegral Int32 CShort Source # 
Instance details
FromIntegral Int32 CUShort Source # 
Instance details
FromIntegral Int32 CInt Source # 
Instance details
FromIntegral Int32 CUInt Source # 
Instance details
FromIntegral Int32 CLong Source # 
Instance details
FromIntegral Int32 CULong Source # 
Instance details
FromIntegral Int32 CLLong Source # 
Instance details
FromIntegral Int32 CULLong Source # 
Instance details
FromIntegral Int32 CFloat Source # 
Instance details
FromIntegral Int32 CDouble Source # 
Instance details
FromIntegral Int32 Half Source # 
Instance details
FromIntegral Int64 Double Source # 
Instance details
FromIntegral Int64 Float Source # 
Instance details
FromIntegral Int64 Int Source # 
Instance details
FromIntegral Int64 Int8 Source # 
Instance details
FromIntegral Int64 Int16 Source # 
Instance details
FromIntegral Int64 Int32 Source # 
Instance details
FromIntegral Int64 Int64 Source # 
Instance details
FromIntegral Int64 Word Source # 
Instance details
FromIntegral Int64 Word8 Source # 
Instance details
FromIntegral Int64 Word16 Source # 
Instance details
FromIntegral Int64 Word32 Source # 
Instance details
FromIntegral Int64 Word64 Source # 
Instance details
FromIntegral Int64 CShort Source # 
Instance details
FromIntegral Int64 CUShort Source # 
Instance details
FromIntegral Int64 CInt Source # 
Instance details
FromIntegral Int64 CUInt Source # 
Instance details
FromIntegral Int64 CLong Source # 
Instance details
FromIntegral Int64 CULong Source # 
Instance details
FromIntegral Int64 CLLong Source # 
Instance details
FromIntegral Int64 CULLong Source # 
Instance details
FromIntegral Int64 CFloat Source # 
Instance details
FromIntegral Int64 CDouble Source # 
Instance details
FromIntegral Int64 Half Source # 
Instance details
FromIntegral Word Double Source # 
Instance details
FromIntegral Word Float Source # 
Instance details
FromIntegral Word Int Source # 
Instance details
FromIntegral Word Int8 Source # 
Instance details
FromIntegral Word Int16 Source # 
Instance details
FromIntegral Word Int32 Source # 
Instance details
FromIntegral Word Int64 Source # 
Instance details
FromIntegral Word Word Source # 
Instance details
FromIntegral Word Word8 Source # 
Instance details
FromIntegral Word Word16 Source # 
Instance details
FromIntegral Word Word32 Source # 
Instance details
FromIntegral Word Word64 Source # 
Instance details
FromIntegral Word CShort Source # 
Instance details
FromIntegral Word CUShort Source # 
Instance details
FromIntegral Word CInt Source # 
Instance details
FromIntegral Word CUInt Source # 
Instance details
FromIntegral Word CLong Source # 
Instance details
FromIntegral Word CULong Source # 
Instance details
FromIntegral Word CLLong Source # 
Instance details
FromIntegral Word CULLong Source # 
Instance details
FromIntegral Word CFloat Source # 
Instance details
FromIntegral Word CDouble Source # 
Instance details
FromIntegral Word Half Source # 
Instance details
FromIntegral Word8 Double Source # 
Instance details
FromIntegral Word8 Float Source # 
Instance details
FromIntegral Word8 Int Source # 
Instance details
FromIntegral Word8 Int8 Source # 
Instance details
FromIntegral Word8 Int16 Source # 
Instance details
FromIntegral Word8 Int32 Source # 
Instance details
FromIntegral Word8 Int64 Source # 
Instance details
FromIntegral Word8 Word Source # 
Instance details
FromIntegral Word8 Word8 Source # 
Instance details
FromIntegral Word8 Word16 Source # 
Instance details
FromIntegral Word8 Word32 Source # 
Instance details
FromIntegral Word8 Word64 Source # 
Instance details
FromIntegral Word8 CShort Source # 
Instance details
FromIntegral Word8 CUShort Source # 
Instance details
FromIntegral Word8 CInt Source # 
Instance details
FromIntegral Word8 CUInt Source # 
Instance details
FromIntegral Word8 CLong Source # 
Instance details
FromIntegral Word8 CULong Source # 
Instance details
FromIntegral Word8 CLLong Source # 
Instance details
FromIntegral Word8 CULLong Source # 
Instance details
FromIntegral Word8 CFloat Source # 
Instance details
FromIntegral Word8 CDouble Source # 
Instance details
FromIntegral Word8 Half Source # 
Instance details
FromIntegral Word16 Double Source # 
Instance details
FromIntegral Word16 Float Source # 
Instance details
FromIntegral Word16 Int Source # 
Instance details
FromIntegral Word16 Int8 Source # 
Instance details
FromIntegral Word16 Int16 Source # 
Instance details
FromIntegral Word16 Int32 Source # 
Instance details
FromIntegral Word16 Int64 Source # 
Instance details
FromIntegral Word16 Word Source # 
Instance details
FromIntegral Word16 Word8 Source # 
Instance details
FromIntegral Word16 Word16 Source # 
Instance details
FromIntegral Word16 Word32 Source # 
Instance details
FromIntegral Word16 Word64 Source # 
Instance details
FromIntegral Word16 CShort Source # 
Instance details
FromIntegral Word16 CUShort Source # 
Instance details
FromIntegral Word16 CInt Source # 
Instance details
FromIntegral Word16 CUInt Source # 
Instance details
FromIntegral Word16 CLong Source # 
Instance details
FromIntegral Word16 CULong Source # 
Instance details
FromIntegral Word16 CLLong Source # 
Instance details
FromIntegral Word16 CULLong Source # 
Instance details
FromIntegral Word16 CFloat Source # 
Instance details
FromIntegral Word16 CDouble Source # 
Instance details
FromIntegral Word16 Half Source # 
Instance details
FromIntegral Word32 Double Source # 
Instance details
FromIntegral Word32 Float Source # 
Instance details
FromIntegral Word32 Int Source # 
Instance details
FromIntegral Word32 Int8 Source # 
Instance details
FromIntegral Word32 Int16 Source # 
Instance details
FromIntegral Word32 Int32 Source # 
Instance details
FromIntegral Word32 Int64 Source # 
Instance details
FromIntegral Word32 Word Source # 
Instance details
FromIntegral Word32 Word8 Source # 
Instance details
FromIntegral Word32 Word16 Source # 
Instance details
FromIntegral Word32 Word32 Source # 
Instance details
FromIntegral Word32 Word64 Source # 
Instance details
FromIntegral Word32 CShort Source # 
Instance details
FromIntegral Word32 CUShort Source # 
Instance details
FromIntegral Word32 CInt Source # 
Instance details
FromIntegral Word32 CUInt Source # 
Instance details
FromIntegral Word32 CLong Source # 
Instance details
FromIntegral Word32 CULong Source # 
Instance details
FromIntegral Word32 CLLong Source # 
Instance details
FromIntegral Word32 CULLong Source # 
Instance details
FromIntegral Word32 CFloat Source # 
Instance details
FromIntegral Word32 CDouble Source # 
Instance details
FromIntegral Word32 Half Source # 
Instance details
FromIntegral Word64 Double Source # 
Instance details
FromIntegral Word64 Float Source # 
Instance details
FromIntegral Word64 Int Source # 
Instance details
FromIntegral Word64 Int8 Source # 
Instance details
FromIntegral Word64 Int16 Source # 
Instance details
FromIntegral Word64 Int32 Source # 
Instance details
FromIntegral Word64 Int64 Source # 
Instance details
FromIntegral Word64 Word Source # 
Instance details
FromIntegral Word64 Word8 Source # 
Instance details
FromIntegral Word64 Word16 Source # 
Instance details
FromIntegral Word64 Word32 Source # 
Instance details
FromIntegral Word64 Word64 Source # 
Instance details
FromIntegral Word64 CShort Source # 
Instance details
FromIntegral Word64 CUShort Source # 
Instance details
FromIntegral Word64 CInt Source # 
Instance details
FromIntegral Word64 CUInt Source # 
Instance details
FromIntegral Word64 CLong Source # 
Instance details
FromIntegral Word64 CULong Source # 
Instance details
FromIntegral Word64 CLLong Source # 
Instance details
FromIntegral Word64 CULLong Source # 
Instance details
FromIntegral Word64 CFloat Source # 
Instance details
FromIntegral Word64 CDouble Source # 
Instance details
FromIntegral Word64 Half Source # 
Instance details
FromIntegral CShort Double Source # 
Instance details
FromIntegral CShort Float Source # 
Instance details
FromIntegral CShort Int Source # 
Instance details
FromIntegral CShort Int8 Source # 
Instance details
FromIntegral CShort Int16 Source # 
Instance details
FromIntegral CShort Int32 Source # 
Instance details
FromIntegral CShort Int64 Source # 
Instance details
FromIntegral CShort Word Source # 
Instance details
FromIntegral CShort Word8 Source # 
Instance details
FromIntegral CShort Word16 Source # 
Instance details
FromIntegral CShort Word32 Source # 
Instance details
FromIntegral CShort Word64 Source # 
Instance details
FromIntegral CShort CShort Source # 
Instance details
FromIntegral CShort CUShort Source # 
Instance details
FromIntegral CShort CInt Source # 
Instance details
FromIntegral CShort CUInt Source # 
Instance details
FromIntegral CShort CLong Source # 
Instance details
FromIntegral CShort CULong Source # 
Instance details
FromIntegral CShort CLLong Source # 
Instance details
FromIntegral CShort CULLong Source # 
Instance details
FromIntegral CShort CFloat Source # 
Instance details
FromIntegral CShort CDouble Source # 
Instance details
FromIntegral CShort Half Source # 
Instance details
FromIntegral CUShort Double Source # 
Instance details
FromIntegral CUShort Float Source # 
Instance details
FromIntegral CUShort Int Source # 
Instance details
FromIntegral CUShort Int8 Source # 
Instance details
FromIntegral CUShort Int16 Source # 
Instance details
FromIntegral CUShort Int32 Source # 
Instance details
FromIntegral CUShort Int64 Source # 
Instance details
FromIntegral CUShort Word Source # 
Instance details
FromIntegral CUShort Word8 Source # 
Instance details
FromIntegral CUShort Word16 Source # 
Instance details
FromIntegral CUShort Word32 Source # 
Instance details
FromIntegral CUShort Word64 Source # 
Instance details
FromIntegral CUShort CShort Source # 
Instance details
FromIntegral CUShort CUShort Source # 
Instance details
FromIntegral CUShort CInt Source # 
Instance details
FromIntegral CUShort CUInt Source # 
Instance details
FromIntegral CUShort CLong Source # 
Instance details
FromIntegral CUShort CULong Source # 
Instance details
FromIntegral CUShort CLLong Source # 
Instance details
FromIntegral CUShort CULLong Source # 
Instance details
FromIntegral CUShort CFloat Source # 
Instance details
FromIntegral CUShort CDouble Source # 
Instance details
FromIntegral CUShort Half Source # 
Instance details
FromIntegral CInt Double Source # 
Instance details
FromIntegral CInt Float Source # 
Instance details
FromIntegral CInt Int Source # 
Instance details
FromIntegral CInt Int8 Source # 
Instance details
FromIntegral CInt Int16 Source # 
Instance details
FromIntegral CInt Int32 Source # 
Instance details
FromIntegral CInt Int64 Source # 
Instance details
FromIntegral CInt Word Source # 
Instance details
FromIntegral CInt Word8 Source # 
Instance details
FromIntegral CInt Word16 Source # 
Instance details
FromIntegral CInt Word32 Source # 
Instance details
FromIntegral CInt Word64 Source # 
Instance details
FromIntegral CInt CShort Source # 
Instance details
FromIntegral CInt CUShort Source # 
Instance details
FromIntegral CInt CInt Source # 
Instance details
FromIntegral CInt CUInt Source # 
Instance details
FromIntegral CInt CLong Source # 
Instance details
FromIntegral CInt CULong Source # 
Instance details
FromIntegral CInt CLLong Source # 
Instance details
FromIntegral CInt CULLong Source # 
Instance details
FromIntegral CInt CFloat Source # 
Instance details
FromIntegral CInt CDouble Source # 
Instance details
FromIntegral CInt Half Source # 
Instance details
FromIntegral CUInt Double Source # 
Instance details
FromIntegral CUInt Float Source # 
Instance details
FromIntegral CUInt Int Source # 
Instance details
FromIntegral CUInt Int8 Source # 
Instance details
FromIntegral CUInt Int16 Source # 
Instance details
FromIntegral CUInt Int32 Source # 
Instance details
FromIntegral CUInt Int64 Source # 
Instance details
FromIntegral CUInt Word Source # 
Instance details
FromIntegral CUInt Word8 Source # 
Instance details
FromIntegral CUInt Word16 Source # 
Instance details
FromIntegral CUInt Word32 Source # 
Instance details
FromIntegral CUInt Word64 Source # 
Instance details
FromIntegral CUInt CShort Source # 
Instance details
FromIntegral CUInt CUShort Source # 
Instance details
FromIntegral CUInt CInt Source # 
Instance details
FromIntegral CUInt CUInt Source # 
Instance details
FromIntegral CUInt CLong Source # 
Instance details
FromIntegral CUInt CULong Source # 
Instance details
FromIntegral CUInt CLLong Source # 
Instance details
FromIntegral CUInt CULLong Source # 
Instance details
FromIntegral CUInt CFloat Source # 
Instance details
FromIntegral CUInt CDouble Source # 
Instance details
FromIntegral CUInt Half Source # 
Instance details
FromIntegral CLong Double Source # 
Instance details
FromIntegral CLong Float Source # 
Instance details
FromIntegral CLong Int Source # 
Instance details
FromIntegral CLong Int8 Source # 
Instance details
FromIntegral CLong Int16 Source # 
Instance details
FromIntegral CLong Int32 Source # 
Instance details
FromIntegral CLong Int64 Source # 
Instance details
FromIntegral CLong Word Source # 
Instance details
FromIntegral CLong Word8 Source # 
Instance details
FromIntegral CLong Word16 Source # 
Instance details
FromIntegral CLong Word32 Source # 
Instance details
FromIntegral CLong Word64 Source # 
Instance details
FromIntegral CLong CShort Source # 
Instance details
FromIntegral CLong CUShort Source # 
Instance details
FromIntegral CLong CInt Source # 
Instance details
FromIntegral CLong CUInt Source # 
Instance details
FromIntegral CLong CLong Source # 
Instance details
FromIntegral CLong CULong Source # 
Instance details
FromIntegral CLong CLLong Source # 
Instance details
FromIntegral CLong CULLong Source # 
Instance details
FromIntegral CLong CFloat Source # 
Instance details
FromIntegral CLong CDouble Source # 
Instance details
FromIntegral CLong Half Source # 
Instance details
FromIntegral CULong Double Source # 
Instance details
FromIntegral CULong Float Source # 
Instance details
FromIntegral CULong Int Source # 
Instance details
FromIntegral CULong Int8 Source # 
Instance details
FromIntegral CULong Int16 Source # 
Instance details
FromIntegral CULong Int32 Source # 
Instance details
FromIntegral CULong Int64 Source # 
Instance details
FromIntegral CULong Word Source # 
Instance details
FromIntegral CULong Word8 Source # 
Instance details
FromIntegral CULong Word16 Source # 
Instance details
FromIntegral CULong Word32 Source # 
Instance details
FromIntegral CULong Word64 Source # 
Instance details
FromIntegral CULong CShort Source # 
Instance details
FromIntegral CULong CUShort Source # 
Instance details
FromIntegral CULong CInt Source # 
Instance details
FromIntegral CULong CUInt Source # 
Instance details
FromIntegral CULong CLong Source # 
Instance details
FromIntegral CULong CULong Source # 
Instance details
FromIntegral CULong CLLong Source # 
Instance details
FromIntegral CULong CULLong Source # 
Instance details
FromIntegral CULong CFloat Source # 
Instance details
FromIntegral CULong CDouble Source # 
Instance details
FromIntegral CULong Half Source # 
Instance details
FromIntegral CLLong Double Source # 
Instance details
FromIntegral CLLong Float Source # 
Instance details
FromIntegral CLLong Int Source # 
Instance details
FromIntegral CLLong Int8 Source # 
Instance details
FromIntegral CLLong Int16 Source # 
Instance details
FromIntegral CLLong Int32 Source # 
Instance details
FromIntegral CLLong Int64 Source # 
Instance details
FromIntegral CLLong Word Source # 
Instance details
FromIntegral CLLong Word8 Source # 
Instance details
FromIntegral CLLong Word16 Source # 
Instance details
FromIntegral CLLong Word32 Source # 
Instance details
FromIntegral CLLong Word64 Source # 
Instance details
FromIntegral CLLong CShort Source # 
Instance details
FromIntegral CLLong CUShort Source # 
Instance details
FromIntegral CLLong CInt Source # 
Instance details
FromIntegral CLLong CUInt Source # 
Instance details
FromIntegral CLLong CLong Source # 
Instance details
FromIntegral CLLong CULong Source # 
Instance details
FromIntegral CLLong CLLong Source # 
Instance details
FromIntegral CLLong CULLong Source # 
Instance details
FromIntegral CLLong CFloat Source # 
Instance details
FromIntegral CLLong CDouble Source # 
Instance details
FromIntegral CLLong Half Source # 
Instance details
FromIntegral CULLong Double Source # 
Instance details
FromIntegral CULLong Float Source # 
Instance details
FromIntegral CULLong Int Source # 
Instance details
FromIntegral CULLong Int8 Source # 
Instance details
FromIntegral CULLong Int16 Source # 
Instance details
FromIntegral CULLong Int32 Source # 
Instance details
FromIntegral CULLong Int64 Source # 
Instance details
FromIntegral CULLong Word Source # 
Instance details
FromIntegral CULLong Word8 Source # 
Instance details
FromIntegral CULLong Word16 Source # 
Instance details
FromIntegral CULLong Word32 Source # 
Instance details
FromIntegral CULLong Word64 Source # 
Instance details
FromIntegral CULLong CShort Source # 
Instance details
FromIntegral CULLong CUShort Source # 
Instance details
FromIntegral CULLong CInt Source # 
Instance details
FromIntegral CULLong CUInt Source # 
Instance details
FromIntegral CULLong CLong Source # 
Instance details
FromIntegral CULLong CULong Source # 
Instance details
FromIntegral CULLong CLLong Source # 
Instance details
FromIntegral CULLong CULLong Source # 
Instance details
FromIntegral CULLong CFloat Source # 
Instance details
FromIntegral CULLong CDouble Source # 
Instance details
FromIntegral CULLong Half Source # 
Instance details
(FromIntegral a b, Num b, Elt (Complex b)) => FromIntegral a (Complex b) Source # 
Instance details

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 to types.

Minimal complete definition

toFloating

Methods

toFloating :: (Num a, Floating b) => Exp a -> Exp b Source #

General coercion to floating types

Instances
ToFloating Double Double Source # 
Instance details
ToFloating Double Float Source # 
Instance details
ToFloating Double CFloat Source # 
Instance details
ToFloating Double CDouble Source # 
Instance details
ToFloating Double Half Source # 
Instance details
ToFloating Float Double Source # 
Instance details
ToFloating Float Float Source # 
Instance details
ToFloating Float CFloat Source # 
Instance details
ToFloating Float CDouble Source # 
Instance details
ToFloating Float Half Source # 
Instance details
ToFloating Int Double Source # 
Instance details
ToFloating Int Float Source # 
Instance details
ToFloating Int CFloat Source # 
Instance details
ToFloating Int CDouble Source # 
Instance details
ToFloating Int Half Source # 
Instance details
ToFloating Int8 Double Source # 
Instance details
ToFloating Int8 Float Source # 
Instance details
ToFloating Int8 CFloat Source # 
Instance details
ToFloating Int8 CDouble Source # 
Instance details
ToFloating Int8 Half Source # 
Instance details
ToFloating Int16 Double Source # 
Instance details
ToFloating Int16 Float Source # 
Instance details
ToFloating Int16 CFloat Source # 
Instance details
ToFloating Int16 CDouble Source # 
Instance details
ToFloating Int16 Half Source # 
Instance details
ToFloating Int32 Double Source # 
Instance details
ToFloating Int32 Float Source # 
Instance details
ToFloating Int32 CFloat Source # 
Instance details
ToFloating Int32 CDouble Source # 
Instance details
ToFloating Int32 Half Source # 
Instance details
ToFloating Int64 Double Source # 
Instance details
ToFloating Int64 Float Source # 
Instance details
ToFloating Int64 CFloat Source # 
Instance details
ToFloating Int64 CDouble Source # 
Instance details
ToFloating Int64 Half Source # 
Instance details
ToFloating Word Double Source # 
Instance details
ToFloating Word Float Source # 
Instance details
ToFloating Word CFloat Source # 
Instance details
ToFloating Word CDouble Source # 
Instance details
ToFloating Word Half Source # 
Instance details
ToFloating Word8 Double Source # 
Instance details
ToFloating Word8 Float Source # 
Instance details
ToFloating Word8 CFloat Source # 
Instance details
ToFloating Word8 CDouble Source # 
Instance details
ToFloating Word8 Half Source # 
Instance details
ToFloating Word16 Double Source # 
Instance details
ToFloating Word16 Float Source # 
Instance details
ToFloating Word16 CFloat Source # 
Instance details
ToFloating Word16 CDouble Source # 
Instance details
ToFloating Word16 Half Source # 
Instance details
ToFloating Word32 Double Source # 
Instance details
ToFloating Word32 Float Source # 
Instance details
ToFloating Word32 CFloat Source # 
Instance details
ToFloating Word32 CDouble Source # 
Instance details
ToFloating Word32 Half Source # 
Instance details
ToFloating Word64 Double Source # 
Instance details
ToFloating Word64 Float Source # 
Instance details
ToFloating Word64 CFloat Source # 
Instance details
ToFloating Word64 CDouble Source # 
Instance details
ToFloating Word64 Half Source # 
Instance details
ToFloating CShort Double Source # 
Instance details
ToFloating CShort Float Source # 
Instance details
ToFloating CShort CFloat Source # 
Instance details
ToFloating CShort CDouble Source # 
Instance details
ToFloating CShort Half Source # 
Instance details
ToFloating CUShort Double Source # 
Instance details
ToFloating CUShort Float Source # 
Instance details
ToFloating CUShort CFloat Source # 
Instance details
ToFloating CUShort CDouble Source # 
Instance details
ToFloating CUShort Half Source # 
Instance details
ToFloating CInt Double Source # 
Instance details
ToFloating CInt Float Source # 
Instance details
ToFloating CInt CFloat Source # 
Instance details
ToFloating CInt CDouble Source # 
Instance details
ToFloating CInt Half Source # 
Instance details
ToFloating CUInt Double Source # 
Instance details
ToFloating CUInt Float Source # 
Instance details
ToFloating CUInt CFloat Source # 
Instance details
ToFloating CUInt CDouble Source # 
Instance details
ToFloating CUInt Half Source # 
Instance details
ToFloating CLong Double Source # 
Instance details
ToFloating CLong Float Source # 
Instance details
ToFloating CLong CFloat Source # 
Instance details
ToFloating CLong CDouble Source # 
Instance details
ToFloating CLong Half Source # 
Instance details
ToFloating CULong Double Source # 
Instance details
ToFloating CULong Float Source # 
Instance details
ToFloating CULong CFloat Source # 
Instance details
ToFloating CULong CDouble Source # 
Instance details
ToFloating CULong Half Source # 
Instance details
ToFloating CLLong Double Source # 
Instance details
ToFloating CLLong Float Source # 
Instance details
ToFloating CLLong CFloat Source # 
Instance details
ToFloating CLLong CDouble Source # 
Instance details
ToFloating CLLong Half Source # 
Instance details
ToFloating CULLong Double Source # 
Instance details
ToFloating CULLong Float Source # 
Instance details
ToFloating CULLong CFloat Source # 
Instance details
ToFloating CULLong CDouble Source # 
Instance details
ToFloating CULLong Half Source # 
Instance details
ToFloating CFloat Double Source # 
Instance details
ToFloating CFloat Float Source # 
Instance details
ToFloating CFloat CFloat Source # 
Instance details
ToFloating CFloat CDouble Source # 
Instance details
ToFloating CFloat Half Source # 
Instance details
ToFloating CDouble Double Source # 
Instance details
ToFloating CDouble Float Source # 
Instance details
ToFloating CDouble CFloat Source # 
Instance details
ToFloating CDouble CDouble Source # 
Instance details
ToFloating CDouble Half Source # 
Instance details
ToFloating Half Double Source # 
Instance details
ToFloating Half Float Source # 
Instance details
ToFloating Half CFloat Source # 
Instance details
ToFloating Half CDouble Source # 
Instance details
ToFloating Half Half Source # 
Instance details

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

class Lift c e where Source #

The class of types e which can be lifted into c.

Minimal complete definition

lift

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
Lift Exp Bool Source # 
Instance details

Associated Types

type Plain Bool :: * Source #

Methods

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

Lift Exp Char Source # 
Instance details

Associated Types

type Plain Char :: * Source #

Methods

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

Lift Exp Double Source # 
Instance details

Associated Types

type Plain Double :: * Source #

Methods

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

Lift Exp Float Source # 
Instance details

Associated Types

type Plain Float :: * Source #

Methods

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

Lift Exp Int Source # 
Instance details

Associated Types

type Plain Int :: * Source #

Methods

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

Lift Exp Int8 Source # 
Instance details

Associated Types

type Plain Int8 :: * Source #

Methods

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

Lift Exp Int16 Source # 
Instance details

Associated Types

type Plain Int16 :: * Source #

Methods

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

Lift Exp Int32 Source # 
Instance details

Associated Types

type Plain Int32 :: * Source #

Methods

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

Lift Exp Int64 Source # 
Instance details

Associated Types

type Plain Int64 :: * Source #

Methods

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

Lift Exp Word Source # 
Instance details

Associated Types

type Plain Word :: * Source #

Methods

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

Lift Exp Word8 Source # 
Instance details

Associated Types

type Plain Word8 :: * Source #

Methods

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

Lift Exp Word16 Source # 
Instance details

Associated Types

type Plain Word16 :: * Source #

Methods

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

Lift Exp Word32 Source # 
Instance details

Associated Types

type Plain Word32 :: * Source #

Methods

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

Lift Exp Word64 Source # 
Instance details

Associated Types

type Plain Word64 :: * Source #

Methods

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

Lift Exp () Source # 
Instance details

Associated Types

type Plain () :: * Source #

Methods

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

Lift Exp CChar Source # 
Instance details

Associated Types

type Plain CChar :: * Source #

Methods

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

Lift Exp CSChar Source # 
Instance details

Associated Types

type Plain CSChar :: * Source #

Methods

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

Lift Exp CUChar Source # 
Instance details

Associated Types

type Plain CUChar :: * Source #

Methods

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

Lift Exp CShort Source # 
Instance details

Associated Types

type Plain CShort :: * Source #

Methods

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

Lift Exp CUShort Source # 
Instance details

Associated Types

type Plain CUShort :: * Source #

Lift Exp CInt Source # 
Instance details

Associated Types

type Plain CInt :: * Source #

Methods

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

Lift Exp CUInt Source # 
Instance details

Associated Types

type Plain CUInt :: * Source #

Methods

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

Lift Exp CLong Source # 
Instance details

Associated Types

type Plain CLong :: * Source #

Methods

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

Lift Exp CULong Source # 
Instance details

Associated Types

type Plain CULong :: * Source #

Methods

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

Lift Exp CLLong Source # 
Instance details

Associated Types

type Plain CLLong :: * Source #

Methods

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

Lift Exp CULLong Source # 
Instance details

Associated Types

type Plain CULLong :: * Source #

Lift Exp CFloat Source # 
Instance details

Associated Types

type Plain CFloat :: * Source #

Methods

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

Lift Exp CDouble Source # 
Instance details

Associated Types

type Plain CDouble :: * Source #

Lift Exp Z Source # 
Instance details

Associated Types

type Plain Z :: * Source #

Methods

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

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

Associated Types

type Plain (Maybe a) :: * Source #

Methods

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

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

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

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

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

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

Associated Types

type Plain (Product a) :: * Source #

Methods

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

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

Associated Types

type Plain (Any sh) :: * Source #

Methods

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

Lift Exp (Exp e) Source # 
Instance details

Associated Types

type Plain (Exp e) :: * Source #

Methods

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

Lift Acc (Acc a) Source # 
Instance details

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

Associated Types

type Plain (Either a b) :: * Source #

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

type Plain (Array sh e) :: * Source #

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g)) => Lift Exp (a, b, c, d, e, f, g) Source # 
Instance details

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h)) => Lift Exp (a, b, c, d, e, f, g, h) Source # 
Instance details

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i)) => Lift Exp (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j)) => Lift Exp (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Associated Types

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

Methods

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

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

Associated Types

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

Methods

lift :: (a, b, c, d, e, f, g, h, i, j) -> Acc (Plain (a, b, c, d, e, f, g, h, i, j)) Source #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k) :: * Source #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j, k)) Source #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Lift Acc h, Lift Acc i, Lift Acc j, Lift Acc k, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g), Arrays (Plain h), Arrays (Plain i), Arrays (Plain j), Arrays (Plain k)) => Lift Acc (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k) :: * Source #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k) -> Acc (Plain (a, b, c, d, e, f, g, h, i, j, k)) Source #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Lift Exp l, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k), Elt (Plain l)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l) :: * Source #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j, k, l)) Source #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Lift Acc h, Lift Acc i, Lift Acc j, Lift Acc k, Lift Acc l, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g), Arrays (Plain h), Arrays (Plain i), Arrays (Plain j), Arrays (Plain k), Arrays (Plain l)) => Lift Acc (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l) :: * Source #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Acc (Plain (a, b, c, d, e, f, g, h, i, j, k, l)) Source #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Lift Exp l, Lift Exp m, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k), Elt (Plain l), Elt (Plain m)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 
Instance details

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l, m) :: * Source #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j, k, l, m)) Source #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Lift Acc h, Lift Acc i, Lift Acc j, Lift Acc k, Lift Acc l, Lift Acc m, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g), Arrays (Plain h), Arrays (Plain i), Arrays (Plain j), Arrays (Plain k), Arrays (Plain l), Arrays (Plain m)) => Lift Acc (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 
Instance details

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l, m) :: * Source #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Acc (Plain (a, b, c, d, e, f, g, h, i, j, k, l, m)) Source #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Lift Exp l, Lift Exp m, Lift Exp n, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k), Elt (Plain l), Elt (Plain m), Elt (Plain n)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 
Instance details

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n) :: * Source #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n)) Source #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Lift Acc h, Lift Acc i, Lift Acc j, Lift Acc k, Lift Acc l, Lift Acc m, Lift Acc n, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g), Arrays (Plain h), Arrays (Plain i), Arrays (Plain j), Arrays (Plain k), Arrays (Plain l), Arrays (Plain m), Arrays (Plain n)) => Lift Acc (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 
Instance details

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n) :: * Source #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Acc (Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n)) Source #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Lift Exp l, Lift Exp m, Lift Exp n, Lift Exp o, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k), Elt (Plain l), Elt (Plain m), Elt (Plain n), Elt (Plain o)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 
Instance details

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) :: * Source #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)) Source #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Lift Acc h, Lift Acc i, Lift Acc j, Lift Acc k, Lift Acc l, Lift Acc m, Lift Acc n, Lift Acc o, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g), Arrays (Plain h), Arrays (Plain i), Arrays (Plain j), Arrays (Plain k), Arrays (Plain l), Arrays (Plain m), Arrays (Plain n), Arrays (Plain o)) => Lift Acc (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 
Instance details

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) :: * Source #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Acc (Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)) Source #

class Lift c e => Unlift c e where Source #

A limited subset of types which can be lifted, can also be unlifted.

Minimal complete definition

unlift

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
Unlift Exp () Source # 
Instance details

Methods

unlift :: Exp (Plain ()) -> () Source #

Unlift Exp Z Source # 
Instance details

Methods

unlift :: Exp (Plain Z) -> Z Source #

(Elt a, Elt (Complex a)) => Unlift Exp (Complex (Exp a)) Source # 
Instance details

Methods

unlift :: Exp (Plain (Complex (Exp a))) -> Complex (Exp a) Source #

Elt a => Unlift Exp (Min (Exp a)) Source # 
Instance details

Methods

unlift :: Exp (Plain (Min (Exp a))) -> Min (Exp a) Source #

Elt a => Unlift Exp (Max (Exp a)) Source # 
Instance details

Methods

unlift :: Exp (Plain (Max (Exp a))) -> Max (Exp a) Source #

Elt a => Unlift Exp (Sum (Exp a)) Source # 
Instance details

Methods

unlift :: Exp (Plain (Sum (Exp a))) -> Sum (Exp a) Source #

Elt a => Unlift Exp (Product (Exp a)) Source # 
Instance details

Methods

unlift :: Exp (Plain (Product (Exp a))) -> Product (Exp a) Source #

Unlift Exp (Exp e) Source # 
Instance details

Methods

unlift :: Exp (Plain (Exp e)) -> Exp e Source #

Unlift Acc (Acc a) Source # 
Instance details

Methods

unlift :: Acc (Plain (Acc a)) -> Acc a Source #

(Elt a, Elt b) => Unlift Exp (Exp a, Exp b) Source # 
Instance details

Methods

unlift :: Exp (Plain (Exp a, Exp b)) -> (Exp a, Exp b) Source #

(Elt e, Slice (Plain ix), Unlift Exp ix) => Unlift Exp (ix :. Exp e) Source # 
Instance details

Methods

unlift :: Exp (Plain (ix :. Exp e)) -> ix :. Exp e Source #

(Elt e, Slice ix) => Unlift Exp (Exp ix :. Exp e) Source # 
Instance details

Methods

unlift :: Exp (Plain (Exp ix :. Exp e)) -> Exp ix :. Exp e Source #

(Arrays a, Arrays b) => Unlift Acc (Acc a, Acc b) Source # 
Instance details

Methods

unlift :: Acc (Plain (Acc a, Acc b)) -> (Acc a, Acc b) Source #

(Elt a, Elt b, Elt c) => Unlift Exp (Exp a, Exp b, Exp c) Source # 
Instance details

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c)) -> (Exp a, Exp b, Exp c) Source #

(Arrays a, Arrays b, Arrays c) => Unlift Acc (Acc a, Acc b, Acc c) Source # 
Instance details

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c)) -> (Acc a, Acc b, Acc c) Source #

(Elt a, Elt b, Elt c, Elt d) => Unlift Exp (Exp a, Exp b, Exp c, Exp d) Source # 
Instance details

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d)) -> (Exp a, Exp b, Exp c, Exp d) Source #

(Arrays a, Arrays b, Arrays c, Arrays d) => Unlift Acc (Acc a, Acc b, Acc c, Acc d) Source # 
Instance details

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d)) -> (Acc a, Acc b, Acc c, Acc d) Source #

(Elt a, Elt b, Elt c, Elt d, Elt e) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e) Source # 
Instance details

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e)) -> (Exp a, Exp b, Exp c, Exp d, Exp e) Source #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e) Source # 
Instance details

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e)) -> (Acc a, Acc b, Acc c, Acc d, Acc e) Source #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f) Source # 
Instance details

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f) Source #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f) Source # 
Instance details

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f) Source #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g) Source # 
Instance details

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g) Source #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g) Source # 
Instance details

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g) Source #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h) Source # 
Instance details

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h) Source #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h) Source # 
Instance details

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h) Source #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i) Source # 
Instance details

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i) Source #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i) Source # 
Instance details

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i) Source #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j) Source # 
Instance details

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j) Source #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j) Source # 
Instance details

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j) Source #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k) Source # 
Instance details

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k) Source #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j, Arrays k) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k) Source # 
Instance details

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k) Source #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k, Elt l) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l) Source # 
Instance details

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l) Source #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j, Arrays k, Arrays l) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l) Source # 
Instance details

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l) Source #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k, Elt l, Elt m) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m) Source # 
Instance details

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m) Source #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j, Arrays k, Arrays l, Arrays m) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m) Source # 
Instance details

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m) Source #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k, Elt l, Elt m, Elt n) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n) Source # 
Instance details

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n) Source #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j, Arrays k, Arrays l, Arrays m, Arrays n) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m, Acc n) Source # 
Instance details

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m, Acc n)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m, Acc n) Source #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k, Elt l, Elt m, Elt n, Elt o) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n, Exp o) Source # 
Instance details

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n, Exp o)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n, Exp o) Source #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j, Arrays k, Arrays l, Arrays m, Arrays n, Arrays o) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m, Acc n, Acc o) Source # 
Instance details

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m, Acc n, Acc o)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m, Acc n, Acc o) 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.

Scalar operations

Introduction

constant :: Elt t => t -> Exp t 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 :: forall a b. (Elt a, Elt b) => Exp (a, b) -> Exp a Source #

Extract the first component of a scalar pair.

afst :: forall a b. (Arrays a, Arrays b) => Acc (a, b) -> Acc a Source #

Extract the first component of an array pair.

snd :: forall a b. (Elt a, Elt b) => Exp (a, b) -> Exp b Source #

Extract the second component of a scalar pair.

asnd :: forall a b. (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.

caseof Source #

Arguments

:: (Elt a, Elt b) 
=> Exp a

case subject

-> [(Exp a -> Exp Bool, Exp b)]

list of cases to attempt

-> Exp b

default value

-> Exp b 

A case-like control structure

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

:: 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 :: forall a. 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 :: forall sh a b. (Shape sh, Slice 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, Slice (Z :. i)) => Exp i -> Exp i -> Exp ((Z :. i) :. i) Source #

Creates a rank-2 index from two Exp Int`s

unindex2 :: forall i. (Elt i, Slice (Z :. 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, Slice (Z :. i), Slice ((Z :. i) :. i)) => Exp i -> Exp i -> Exp i -> Exp (((Z :. i) :. i) :. i) Source #

Create a rank-3 index from three Exp Int`s

unindex3 :: forall i. (Elt i, Slice (Z :. i), Slice ((Z :. i) :. i)) => Exp (((Z :. i) :. i) :. i) -> Exp (i, i, i) Source #

Destruct a rank-3 index into an Exp tuple of Int`s

indexHead :: (Slice 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 :: (Slice sh, Elt a) => Exp (sh :. a) -> Exp sh Source #

Get all but the innermost element of a shape

toIndex Source #

Arguments

:: 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 :: Shape sh => Exp sh -> Exp Int -> Exp sh Source #

Inverse of toIndex

intersect :: 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 (EltRepr a), IsScalar (EltRepr b), BitSizeEq (EltRepr a) (EltRepr 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 :: (Arrays as, Arrays bs, Foreign asm) => asm (as -> 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 :: (Elt x, Elt y, Foreign asm) => asm (x -> 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 :: Shape sh => sh -> Int Source #

Rank of an array.

arrayShape :: Shape sh => Array sh e -> sh Source #

Array shape in plain Haskell code.

arraySize :: Shape sh => sh -> Int Source #

Total number of elements in an array of the given Shape.

arrayReshape :: (Shape sh, Shape sh', Elt e) => 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 :: Array sh e -> sh -> e Source #

Array indexing in plain Haskell code.

linearIndexArray :: 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 :: (Shape sh, Elt e) => sh -> (sh -> IO e) -> IO (Array sh e) Source #

Create an array using a monadic function applied at each index.

Lists

fromList :: (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. Array sh e -> [e] Source #

Convert an accelerated Array to a list in row-major order.

Prelude re-exports

(.) :: (b -> c) -> (a -> b) -> a -> c infixr 9 #

Function composition.

($) :: (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.

error :: HasCallStack => [Char] -> a #

error stops execution and displays an error message.

undefined :: 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]

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
Bounded Int

Since: 2.1

Instance details

Methods

minBound :: Int #

maxBound :: Int #

Enum Int

Since: 2.1

Instance details

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

Methods

(==) :: Int -> Int -> Bool #

(/=) :: Int -> Int -> Bool #

Integral Int

Since: 2.0.1

Instance details

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: 2.1

Instance details

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

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: 2.1

Instance details
Real Int

Since: 2.0.1

Instance details

Methods

toRational :: Int -> Rational #

Show Int

Since: 2.1

Instance details

Methods

showsPrec :: Int -> Int -> ShowS #

show :: Int -> String #

showList :: [Int] -> ShowS #

Lift Int 
Instance details

Methods

lift :: Int -> Q Exp #

Pretty Int 
Instance details

Methods

pretty :: Int -> Doc #

prettyList :: [Int] -> Doc #

PrintfArg Int

Since: 2.1

Instance details
Storable Int

Since: 2.1

Instance details

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: 2.1

Instance details

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: 4.6.0.0

Instance details
PrimType Int 
Instance details

Associated Types

type PrimSize Int :: Nat #

PrimMemoryComparable Int 
Instance details
Subtractive Int 
Instance details

Associated Types

type Difference Int :: * #

Methods

(-) :: Int -> Int -> Difference Int #

NFData Int 
Instance details

Methods

rnf :: Int -> () #

Hashable Int 
Instance details

Methods

hashWithSalt :: Int -> Int -> Int #

hash :: Int -> Int #

Prim Int 
Instance details
Unbox Int 
Instance details
Pretty Int 
Instance details

Methods

pretty :: Int -> Doc b #

prettyList :: [Int] -> Doc b #

IsScalar Int Source # 
Instance details

Methods

scalarType :: ScalarType Int

IsBounded Int Source # 
Instance details

Methods

boundedType :: BoundedType Int

IsNum Int Source # 
Instance details

Methods

numType :: NumType Int

IsIntegral Int Source # 
Instance details

Methods

integralType :: IntegralType Int

Elt Int Source # 
Instance details

Methods

eltType :: Int -> TupleType (EltRepr Int)

fromElt :: Int -> EltRepr Int

toElt :: EltRepr Int -> Int

Eq Int Source # 
Instance details

Methods

(==) :: Exp Int -> Exp Int -> Exp Bool Source #

(/=) :: Exp Int -> Exp Int -> Exp Bool Source #

Ord Int Source # 
Instance details
FiniteBits Int Source # 
Instance details
Bits Int Source # 
Instance details
Vector Vector Int 
Instance details
FunctorWithIndex Int []

The position in the list is available as the index.

Instance details

Methods

imap :: (Int -> a -> b) -> [a] -> [b] #

imapped :: (Indexable Int p, Settable f) => p a (f b) -> [a] -> f [b] #

FunctorWithIndex Int ZipList

Same instance as for [].

Instance details

Methods

imap :: (Int -> a -> b) -> ZipList a -> ZipList b #

imapped :: (Indexable Int p, Settable f) => p a (f b) -> ZipList a -> f (ZipList b) #

FunctorWithIndex Int NonEmpty 
Instance details

Methods

imap :: (Int -> a -> b) -> NonEmpty a -> NonEmpty b #

imapped :: (Indexable Int p, Settable f) => p a (f b) -> NonEmpty a -> f (NonEmpty b) #

FunctorWithIndex Int IntMap 
Instance details

Methods

imap :: (Int -> a -> b) -> IntMap a -> IntMap b #

imapped :: (Indexable Int p, Settable f) => p a (f b) -> IntMap a -> f (IntMap b) #

FunctorWithIndex Int Seq

The position in the Seq is available as the index.

Instance details

Methods

imap :: (Int -> a -> b) -> Seq a -> Seq b #

imapped :: (Indexable Int p, Settable f) => p a (f b) -> Seq a -> f (Seq b) #

FunctorWithIndex Int Vector 
Instance details

Methods

imap :: (Int -> a -> b) -> Vector a -> Vector b #

imapped :: (Indexable Int p, Settable f) => p a (f b) -> Vector a -> f (Vector b) #

FoldableWithIndex Int [] 
Instance details

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> [a] -> m #

ifolded :: (Indexable Int p, Contravariant f, Applicative f) => p a (f a) -> [a] -> f [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

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> ZipList a -> m #

ifolded :: (Indexable Int p, Contravariant f, Applicative f) => p a (f a) -> ZipList a -> f (ZipList 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

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> NonEmpty a -> m #

ifolded :: (Indexable Int p, Contravariant f, Applicative f) => p a (f a) -> NonEmpty a -> f (NonEmpty 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

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> IntMap a -> m #

ifolded :: (Indexable Int p, Contravariant f, Applicative f) => p a (f a) -> IntMap a -> f (IntMap 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

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> Seq a -> m #

ifolded :: (Indexable Int p, Contravariant f, Applicative f) => p a (f a) -> Seq a -> f (Seq 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

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> Vector a -> m #

ifolded :: (Indexable Int p, Contravariant f, Applicative f) => p a (f a) -> Vector a -> f (Vector 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

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> [a] -> f [b] #

itraversed :: (Indexable Int p, Applicative f) => p a (f b) -> [a] -> f [b] #

TraversableWithIndex Int ZipList 
Instance details

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> ZipList a -> f (ZipList b) #

itraversed :: (Indexable Int p, Applicative f) => p a (f b) -> ZipList a -> f (ZipList b) #

TraversableWithIndex Int NonEmpty 
Instance details

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> NonEmpty a -> f (NonEmpty b) #

itraversed :: (Indexable Int p, Applicative f) => p a (f b) -> NonEmpty a -> f (NonEmpty b) #

TraversableWithIndex Int IntMap 
Instance details

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> IntMap a -> f (IntMap b) #

itraversed :: (Indexable Int p, Applicative f) => p a (f b) -> IntMap a -> f (IntMap b) #

TraversableWithIndex Int Seq 
Instance details

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> Seq a -> f (Seq b) #

itraversed :: (Indexable Int p, Applicative f) => p a (f b) -> Seq a -> f (Seq b) #

TraversableWithIndex Int Vector 
Instance details

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> Vector a -> f (Vector b) #

itraversed :: (Indexable Int p, Applicative f) => p a (f b) -> Vector a -> f (Vector b) #

TraverseMin Int IntMap 
Instance details

Methods

traverseMin :: (Indexable Int p, Applicative f) => p v (f v) -> IntMap v -> f (IntMap v) #

TraverseMax Int IntMap 
Instance details

Methods

traverseMax :: (Indexable Int p, Applicative f) => p v (f v) -> IntMap v -> f (IntMap v) #

MVector MVector Int 
Instance details
Lift Exp Int Source # 
Instance details

Associated Types

type Plain Int :: * Source #

Methods

lift :: Int -> Exp (Plain Int) Source #

ToFloating Int Double Source # 
Instance details
ToFloating Int Float Source # 
Instance details
ToFloating Int CFloat Source # 
Instance details
ToFloating Int CDouble Source # 
Instance details
ToFloating Int Half Source # 
Instance details
FromIntegral Int Double Source # 
Instance details
FromIntegral Int Float Source # 
Instance details
FromIntegral Int Int Source # 
Instance details
FromIntegral Int Int8 Source # 
Instance details
FromIntegral Int Int16 Source # 
Instance details
FromIntegral Int Int32 Source # 
Instance details
FromIntegral Int Int64 Source # 
Instance details
FromIntegral Int Word Source # 
Instance details
FromIntegral Int Word8 Source # 
Instance details
FromIntegral Int Word16 Source # 
Instance details
FromIntegral Int Word32 Source # 
Instance details
FromIntegral Int Word64 Source # 
Instance details
FromIntegral Int CShort Source # 
Instance details
FromIntegral Int CUShort Source # 
Instance details
FromIntegral Int CInt Source # 
Instance details
FromIntegral Int CUInt Source # 
Instance details
FromIntegral Int CLong Source # 
Instance details
FromIntegral Int CULong Source # 
Instance details
FromIntegral Int CLLong Source # 
Instance details
FromIntegral Int CULLong Source # 
Instance details
FromIntegral Int CFloat Source # 
Instance details
FromIntegral Int CDouble Source # 
Instance details
FromIntegral Int Half Source # 
Instance details
FromIntegral Int8 Int Source # 
Instance details
FromIntegral Int16 Int Source # 
Instance details
FromIntegral Int32 Int Source # 
Instance details
FromIntegral Int64 Int Source # 
Instance details
FromIntegral Word Int Source # 
Instance details
FromIntegral Word8 Int Source # 
Instance details
FromIntegral Word16 Int Source # 
Instance details
FromIntegral Word32 Int Source # 
Instance details
FromIntegral Word64 Int Source # 
Instance details
FromIntegral CShort Int Source # 
Instance details
FromIntegral CUShort Int Source # 
Instance details
FromIntegral CInt Int Source # 
Instance details
FromIntegral CUInt Int Source # 
Instance details
FromIntegral CLong Int Source # 
Instance details
FromIntegral CULong Int Source # 
Instance details
FromIntegral CLLong Int Source # 
Instance details
FromIntegral CULLong Int Source # 
Instance details
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e) Source # 
Instance details

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e)

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e) Source # 
Instance details

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e, Exp e, Exp e)

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) Source # 
Instance details

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) Source # 
Instance details

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)

() :=> (Bounded Int) 
Instance details

Methods

ins :: () :- Bounded Int #

() :=> (Enum Int) 
Instance details

Methods

ins :: () :- Enum Int #

() :=> (Eq Int) 
Instance details

Methods

ins :: () :- Eq Int #

() :=> (Integral Int) 
Instance details

Methods

ins :: () :- Integral Int #

() :=> (Num Int) 
Instance details

Methods

ins :: () :- Num Int #

() :=> (Ord Int) 
Instance details

Methods

ins :: () :- Ord Int #

() :=> (Read Int) 
Instance details

Methods

ins :: () :- Read Int #

() :=> (Real Int) 
Instance details

Methods

ins :: () :- Real Int #

() :=> (Show Int) 
Instance details

Methods

ins :: () :- Show Int #

() :=> (Bits Int) 
Instance details

Methods

ins :: () :- Bits Int #

Generic1 (URec Int :: k -> *) 
Instance details

Associated Types

type Rep1 (URec Int) :: k -> * #

Methods

from1 :: URec Int a -> Rep1 (URec Int) a #

to1 :: Rep1 (URec Int) a -> URec Int a #

(Slice (Plain ix), Lift Exp ix) => Lift Exp (ix :. Int) Source # 
Instance details

Associated Types

type Plain (ix :. Int) :: * Source #

Methods

lift :: (ix :. Int) -> Exp (Plain (ix :. Int)) Source #

Elt e => IsList (Vector e) # 
Instance details

Associated Types

type Item (Vector e) :: * #

Methods

fromList :: [Item (Vector e)] -> Vector e #

fromListN :: Int -> [Item (Vector e)] -> Vector e #

toList :: Vector e -> [Item (Vector e)] #

Bounded (Exp Int) # 
Instance details
Enum (Exp Int) # 
Instance details
Integral (Exp Int) # 
Instance details

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) # 
Instance details

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 #

Show (Vector e) # 
Instance details

Methods

showsPrec :: Int -> Vector e -> ShowS #

show :: Vector e -> String #

showList :: [Vector e] -> ShowS #

Shape sh => Elt (Any (sh :. Int)) Source # 
Instance details

Methods

eltType :: Any (sh :. Int) -> TupleType (EltRepr (Any (sh :. Int)))

fromElt :: Any (sh :. Int) -> EltRepr (Any (sh :. Int))

toElt :: EltRepr (Any (sh :. Int)) -> Any (sh :. Int)

FunctorWithIndex [Int] Tree 
Instance details

Methods

imap :: ([Int] -> a -> b) -> Tree a -> Tree b #

imapped :: (Indexable [Int] p, Settable f) => p a (f b) -> Tree a -> f (Tree b) #

FoldableWithIndex [Int] Tree 
Instance details

Methods

ifoldMap :: Monoid m => ([Int] -> a -> m) -> Tree a -> m #

ifolded :: (Indexable [Int] p, Contravariant f, Applicative f) => p a (f a) -> Tree a -> f (Tree 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

Methods

itraverse :: Applicative f => ([Int] -> a -> f b) -> Tree a -> f (Tree b) #

itraversed :: (Indexable [Int] p, Applicative f) => p a (f b) -> Tree a -> f (Tree b) #

Bizarre (Indexed Int) Mafic 
Instance details

Methods

bazaar :: Applicative f => Indexed Int a (f b) -> Mafic a b t -> f t #

Reifies Z Int 
Instance details

Methods

reflect :: proxy Z -> Int #

Reifies n Int => Reifies (D n :: *) Int 
Instance details

Methods

reflect :: proxy (D n) -> Int #

Reifies n Int => Reifies (SD n :: *) Int 
Instance details

Methods

reflect :: proxy (SD n) -> Int #

Reifies n Int => Reifies (PD n :: *) Int 
Instance details

Methods

reflect :: proxy (PD n) -> Int #

Functor (URec Int :: * -> *) 
Instance details

Methods

fmap :: (a -> b) -> URec Int a -> URec Int b #

(<$) :: a -> URec Int b -> URec Int a #

Show (Array DIM2 e) # 
Instance details

Methods

showsPrec :: Int -> Array DIM2 e -> ShowS #

show :: Array DIM2 e -> String #

showList :: [Array DIM2 e] -> ShowS #

Foldable (URec Int :: * -> *) 
Instance details

Methods

fold :: Monoid m => URec Int m -> m #

foldMap :: Monoid m => (a -> m) -> URec Int a -> m #

foldr :: (a -> b -> b) -> b -> URec Int a -> b #

foldr' :: (a -> b -> b) -> b -> URec Int a -> b #

foldl :: (b -> a -> b) -> b -> URec Int a -> b #

foldl' :: (b -> a -> b) -> b -> URec Int a -> b #

foldr1 :: (a -> a -> a) -> URec Int a -> a #

foldl1 :: (a -> a -> a) -> URec Int a -> a #

toList :: URec Int a -> [a] #

null :: URec Int a -> Bool #

length :: URec Int a -> Int #

elem :: Eq a => a -> URec Int a -> Bool #

maximum :: Ord a => URec Int a -> a #

minimum :: Ord a => URec Int a -> a #

sum :: Num a => URec Int a -> a #

product :: Num a => URec Int a -> a #

Traversable (URec Int :: * -> *) 
Instance details

Methods

traverse :: Applicative f => (a -> f b) -> URec Int a -> f (URec Int b) #

sequenceA :: Applicative f => URec Int (f a) -> f (URec Int a) #

mapM :: Monad m => (a -> m b) -> URec Int a -> m (URec Int b) #

sequence :: Monad m => URec Int (m a) -> m (URec Int a) #

Slice sl => Slice (sl :. Int) Source # 
Instance details

Associated Types

type SliceShape (sl :. Int) :: * Source #

type CoSliceShape (sl :. Int) :: * Source #

type FullShape (sl :. Int) :: * Source #

Methods

sliceIndex :: (sl :. Int) -> SliceIndex (EltRepr (sl :. Int)) (EltRepr (SliceShape (sl :. Int))) (EltRepr (CoSliceShape (sl :. Int))) (EltRepr (FullShape (sl :. Int))) Source #

Shape sh => Shape (sh :. Int) Source # 
Instance details

Methods

rank :: (sh :. Int) -> Int

size :: (sh :. Int) -> Int

empty :: sh :. Int

ignore :: sh :. Int

intersect :: (sh :. Int) -> (sh :. Int) -> sh :. Int

union :: (sh :. Int) -> (sh :. Int) -> sh :. Int

toIndex :: (sh :. Int) -> (sh :. Int) -> Int

fromIndex :: (sh :. Int) -> Int -> sh :. Int

iter :: (sh :. Int) -> ((sh :. Int) -> a) -> (a -> a -> a) -> a -> a

iter1 :: (sh :. Int) -> ((sh :. Int) -> a) -> (a -> a -> a) -> a

rangeToShape :: (sh :. Int, sh :. Int) -> sh :. Int

shapeToRange :: (sh :. Int) -> (sh :. Int, sh :. Int)

shapeToList :: (sh :. Int) -> [Int]

listToShape :: [Int] -> sh :. Int

sliceAnyIndex :: (sh :. Int) -> SliceIndex (EltRepr (Any (sh :. Int))) (EltRepr (sh :. Int)) () (EltRepr (sh :. Int))

sliceNoneIndex :: (sh :. Int) -> SliceIndex (EltRepr (sh :. Int)) () (EltRepr (sh :. Int)) (EltRepr (sh :. Int))

(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

Associated Types

type StencilRepr ((sh :. Int) :. Int) (row2, row1, row0) :: *

Methods

stencilPrj :: ((sh :. Int) :. Int) -> a -> Exp (StencilRepr ((sh :. Int) :. Int) (row2, row1, row0)) -> (row2, row1, row0)

(Stencil (sh :. Int) a row1, Stencil (sh :. Int) a row2, Stencil (sh :. Int) a row3, Stencil (sh :. Int) a row4, Stencil (sh :. Int) a row5) => Stencil ((sh :. Int) :. Int) a (row1, row2, row3, row4, row5) Source # 
Instance details

Associated Types

type StencilRepr ((sh :. Int) :. Int) (row1, row2, row3, row4, row5) :: *

Methods

stencilPrj :: ((sh :. Int) :. Int) -> a -> Exp (StencilRepr ((sh :. Int) :. Int) (row1, row2, row3, row4, row5)) -> (row1, row2, row3, row4, row5)

(Stencil (sh :. Int) a row1, Stencil (sh :. Int) a row2, Stencil (sh :. Int) a row3, Stencil (sh :. Int) a row4, Stencil (sh :. Int) a row5, Stencil (sh :. Int) a row6, Stencil (sh :. Int) a row7) => Stencil ((sh :. Int) :. Int) a (row1, row2, row3, row4, row5, row6, row7) Source # 
Instance details

Associated Types

type StencilRepr ((sh :. Int) :. Int) (row1, row2, row3, row4, row5, row6, row7) :: *

Methods

stencilPrj :: ((sh :. Int) :. Int) -> a -> Exp (StencilRepr ((sh :. Int) :. Int) (row1, row2, row3, row4, row5, row6, row7)) -> (row1, row2, row3, row4, row5, row6, row7)

(Stencil (sh :. Int) a row1, Stencil (sh :. Int) a row2, Stencil (sh :. Int) a row3, Stencil (sh :. Int) a row4, Stencil (sh :. Int) a row5, Stencil (sh :. Int) a row6, Stencil (sh :. Int) a row7, Stencil (sh :. Int) a row8, Stencil (sh :. Int) a row9) => Stencil ((sh :. Int) :. Int) a (row1, row2, row3, row4, row5, row6, row7, row8, row9) Source # 
Instance details

Associated Types

type StencilRepr ((sh :. Int) :. Int) (row1, row2, row3, row4, row5, row6, row7, row8, row9) :: *

Methods

stencilPrj :: ((sh :. Int) :. Int) -> a -> Exp (StencilRepr ((sh :. Int) :. Int) (row1, row2, row3, row4, row5, row6, row7, row8, row9)) -> (row1, row2, row3, row4, row5, row6, row7, row8, row9)

Eq (URec Int p) 
Instance details

Methods

(==) :: URec Int p -> URec Int p -> Bool #

(/=) :: URec Int p -> URec Int p -> Bool #

Ord (URec Int p) 
Instance details

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) 
Instance details

Methods

showsPrec :: Int -> URec Int p -> ShowS #

show :: URec Int p -> String #

showList :: [URec Int p] -> ShowS #

Generic (URec Int p) 
Instance details

Associated Types

type Rep (URec Int p) :: * -> * #

Methods

from :: URec Int p -> Rep (URec Int p) x #

to :: Rep (URec Int p) x -> URec Int p #

type PrimSize Int 
Instance details
type PrimSize Int = 8
type Difference Int 
Instance details
type NatNumMaxBound Int 
Instance details
data Vector Int 
Instance details
type Plain Int Source # 
Instance details
type Plain Int = Int
data URec Int (p :: k)

Used for marking occurrences of Int#

Since: 4.9.0.0

Instance details
data URec Int (p :: k) = UInt {}
data MVector s Int 
Instance details
type Rep1 (URec Int :: k -> *) 
Instance details
type Rep1 (URec Int :: k -> *) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UInt" PrefixI True) (S1 (MetaSel (Just "uInt#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UInt :: k -> *)))
type Item (Vector e) # 
Instance details
type Item (Vector e) = e
type SliceShape (sl :. Int) Source # 
Instance details
type SliceShape (sl :. Int) = SliceShape sl
type CoSliceShape (sl :. Int) Source # 
Instance details
type FullShape (sl :. Int) Source # 
Instance details
type FullShape (sl :. Int) = FullShape sl :. Int
type Plain (ix :. Int) Source # 
Instance details
type Plain (ix :. Int) = Plain ix :. Int
type Rep (URec Int p) 
Instance details
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 :: * -> *)))

data Int8 #

8-bit signed integer type

Instances
Bounded Int8

Since: 2.1

Instance details
Enum Int8

Since: 2.1

Instance details

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: 2.1

Instance details

Methods

(==) :: Int8 -> Int8 -> Bool #

(/=) :: Int8 -> Int8 -> Bool #

Integral Int8

Since: 2.1

Instance details

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: 2.1

Instance details

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: 2.1

Instance details

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: 2.1

Instance details
Real Int8

Since: 2.1

Instance details

Methods

toRational :: Int8 -> Rational #

Show Int8

Since: 2.1

Instance details

Methods

showsPrec :: Int -> Int8 -> ShowS #

show :: Int8 -> String #

showList :: [Int8] -> ShowS #

Ix Int8

Since: 2.1

Instance details

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

Lift Int8 
Instance details

Methods

lift :: Int8 -> Q Exp #

PrintfArg Int8

Since: 2.1

Instance details
Storable Int8

Since: 2.1

Instance details

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: 2.1

Instance details
FiniteBits Int8

Since: 4.6.0.0

Instance details
PrimType Int8 
Instance details

Associated Types

type PrimSize Int8 :: Nat #

PrimMemoryComparable Int8 
Instance details
Subtractive Int8 
Instance details

Associated Types

type Difference Int8 :: * #

Methods

(-) :: Int8 -> Int8 -> Difference Int8 #

NFData Int8 
Instance details

Methods

rnf :: Int8 -> () #

Hashable Int8 
Instance details

Methods

hashWithSalt :: Int -> Int8 -> Int #

hash :: Int8 -> Int #

Prim Int8 
Instance details
Unbox Int8 
Instance details
Pretty Int8 
Instance details

Methods

pretty :: Int8 -> Doc b #

prettyList :: [Int8] -> Doc b #

IsScalar Int8 Source # 
Instance details

Methods

scalarType :: ScalarType Int8

IsBounded Int8 Source # 
Instance details

Methods

boundedType :: BoundedType Int8

IsNum Int8 Source # 
Instance details

Methods

numType :: NumType Int8

IsIntegral Int8 Source # 
Instance details

Methods

integralType :: IntegralType Int8

Elt Int8 Source # 
Instance details

Methods

eltType :: Int8 -> TupleType (EltRepr Int8)

fromElt :: Int8 -> EltRepr Int8

toElt :: EltRepr Int8 -> Int8

Eq Int8 Source # 
Instance details
Ord Int8 Source # 
Instance details
FiniteBits Int8 Source # 
Instance details
Bits Int8 Source # 
Instance details
Vector Vector Int8 
Instance details
MVector MVector Int8 
Instance details
Lift Exp Int8 Source # 
Instance details

Associated Types

type Plain Int8 :: * Source #

Methods

lift :: Int8 -> Exp (Plain Int8) Source #

ToFloating Int8 Double Source # 
Instance details
ToFloating Int8 Float Source # 
Instance details
ToFloating Int8 CFloat Source # 
Instance details
ToFloating Int8 CDouble Source # 
Instance details
ToFloating Int8 Half Source # 
Instance details
FromIntegral Int Int8 Source # 
Instance details
FromIntegral Int8 Double Source # 
Instance details
FromIntegral Int8 Float Source # 
Instance details
FromIntegral Int8 Int Source # 
Instance details
FromIntegral Int8 Int8 Source # 
Instance details
FromIntegral Int8 Int16 Source # 
Instance details
FromIntegral Int8 Int32 Source # 
Instance details
FromIntegral Int8 Int64 Source # 
Instance details
FromIntegral Int8 Word Source # 
Instance details
FromIntegral Int8 Word8 Source # 
Instance details
FromIntegral Int8 Word16 Source # 
Instance details
FromIntegral Int8 Word32 Source # 
Instance details
FromIntegral Int8 Word64 Source # 
Instance details
FromIntegral Int8 CShort Source # 
Instance details
FromIntegral Int8 CUShort Source # 
Instance details
FromIntegral Int8 CInt Source # 
Instance details
FromIntegral Int8 CUInt Source # 
Instance details
FromIntegral Int8 CLong Source # 
Instance details
FromIntegral Int8 CULong Source # 
Instance details
FromIntegral Int8 CLLong Source # 
Instance details
FromIntegral Int8 CULLong Source # 
Instance details
FromIntegral Int8 CFloat Source # 
Instance details
FromIntegral Int8 CDouble Source # 
Instance details
FromIntegral Int8 Half Source # 
Instance details
FromIntegral Int16 Int8 Source # 
Instance details
FromIntegral Int32 Int8 Source # 
Instance details
FromIntegral Int64 Int8 Source # 
Instance details
FromIntegral Word Int8 Source # 
Instance details
FromIntegral Word8 Int8 Source # 
Instance details
FromIntegral Word16 Int8 Source # 
Instance details
FromIntegral Word32 Int8 Source # 
Instance details
FromIntegral Word64 Int8 Source # 
Instance details
FromIntegral CShort Int8 Source # 
Instance details
FromIntegral CUShort Int8 Source # 
Instance details
FromIntegral CInt Int8 Source # 
Instance details
FromIntegral CUInt Int8 Source # 
Instance details
FromIntegral CLong Int8 Source # 
Instance details
FromIntegral CULong Int8 Source # 
Instance details
FromIntegral CLLong Int8 Source # 
Instance details
FromIntegral CULLong Int8 Source # 
Instance details
Bounded (Exp Int8) # 
Instance details
Enum (Exp Int8) # 
Instance details
Integral (Exp Int8) # 
Instance details
Num (Exp Int8) # 
Instance details
type PrimSize Int8 
Instance details
type PrimSize Int8 = 1
type Difference Int8 
Instance details
type NatNumMaxBound Int8 
Instance details
type NatNumMaxBound Int8 = 127
data Vector Int8 
Instance details
type Plain Int8 Source # 
Instance details
type Plain Int8 = Int8
data MVector s Int8 
Instance details

data Int16 #

16-bit signed integer type

Instances
Bounded Int16

Since: 2.1

Instance details
Enum Int16

Since: 2.1

Instance details
Eq Int16

Since: 2.1

Instance details

Methods

(==) :: Int16 -> Int16 -> Bool #

(/=) :: Int16 -> Int16 -> Bool #

Integral Int16

Since: 2.1

Instance details
Num Int16

Since: 2.1

Instance details
Ord Int16

Since: 2.1

Instance details

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: 2.1

Instance details
Real Int16

Since: 2.1

Instance details

Methods

toRational :: Int16 -> Rational #

Show Int16

Since: 2.1

Instance details

Methods

showsPrec :: Int -> Int16 -> ShowS #

show :: Int16 -> String #

showList :: [Int16] -> ShowS #

Ix Int16

Since: 2.1

Instance details
Lift Int16 
Instance details

Methods

lift :: Int16 -> Q Exp #

PrintfArg Int16

Since: 2.1

Instance details
Storable Int16

Since: 2.1

Instance details

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: 2.1

Instance details
FiniteBits Int16

Since: 4.6.0.0

Instance details
PrimType Int16 
Instance details

Associated Types

type PrimSize Int16 :: Nat #

PrimMemoryComparable Int16 
Instance details
Subtractive Int16 
Instance details

Associated Types

type Difference Int16 :: * #

Methods

(-) :: Int16 -> Int16 -> Difference Int16 #

NFData Int16 
Instance details

Methods

rnf :: Int16 -> () #

Hashable Int16 
Instance details

Methods

hashWithSalt :: Int -> Int16 -> Int #

hash :: Int16 -> Int #

Prim Int16 
Instance details
Unbox Int16 
Instance details
Pretty Int16 
Instance details

Methods

pretty :: Int16 -> Doc b #

prettyList :: [Int16] -> Doc b #

IsScalar Int16 Source # 
Instance details

Methods

scalarType :: ScalarType Int16

IsBounded Int16 Source # 
Instance details

Methods

boundedType :: BoundedType Int16

IsNum Int16 Source # 
Instance details

Methods

numType :: NumType Int16

IsIntegral Int16 Source # 
Instance details

Methods

integralType :: IntegralType Int16

Elt Int16 Source # 
Instance details

Methods

eltType :: Int16 -> TupleType (EltRepr Int16)

fromElt :: Int16 -> EltRepr Int16

toElt :: EltRepr Int16 -> Int16

Eq Int16 Source # 
Instance details
Ord Int16 Source # 
Instance details
FiniteBits Int16 Source # 
Instance details
Bits Int16 Source # 
Instance details
Vector Vector Int16 
Instance details
MVector MVector Int16 
Instance details
Lift Exp Int16 Source # 
Instance details

Associated Types

type Plain Int16 :: * Source #

Methods

lift :: Int16 -> Exp (Plain Int16) Source #

ToFloating Int16 Double Source # 
Instance details
ToFloating Int16 Float Source # 
Instance details
ToFloating Int16 CFloat Source # 
Instance details
ToFloating Int16 CDouble Source # 
Instance details
ToFloating Int16 Half Source # 
Instance details
FromIntegral Int Int16 Source # 
Instance details
FromIntegral Int8 Int16 Source # 
Instance details
FromIntegral Int16 Double Source # 
Instance details
FromIntegral Int16 Float Source # 
Instance details
FromIntegral Int16 Int Source # 
Instance details
FromIntegral Int16 Int8 Source # 
Instance details
FromIntegral Int16 Int16 Source # 
Instance details
FromIntegral Int16 Int32 Source # 
Instance details
FromIntegral Int16 Int64 Source # 
Instance details
FromIntegral Int16 Word Source # 
Instance details
FromIntegral Int16 Word8 Source # 
Instance details
FromIntegral Int16 Word16 Source # 
Instance details
FromIntegral Int16 Word32 Source # 
Instance details
FromIntegral Int16 Word64 Source # 
Instance details
FromIntegral Int16 CShort Source # 
Instance details
FromIntegral Int16 CUShort Source # 
Instance details
FromIntegral Int16 CInt Source # 
Instance details
FromIntegral Int16 CUInt Source # 
Instance details
FromIntegral Int16 CLong Source # 
Instance details
FromIntegral Int16 CULong Source # 
Instance details
FromIntegral Int16 CLLong Source # 
Instance details
FromIntegral Int16 CULLong Source # 
Instance details
FromIntegral Int16 CFloat Source # 
Instance details
FromIntegral Int16 CDouble Source # 
Instance details
FromIntegral Int16 Half Source # 
Instance details
FromIntegral Int32 Int16 Source # 
Instance details
FromIntegral Int64 Int16 Source # 
Instance details
FromIntegral Word Int16 Source # 
Instance details
FromIntegral Word8 Int16 Source # 
Instance details
FromIntegral Word16 Int16 Source # 
Instance details
FromIntegral Word32 Int16 Source # 
Instance details
FromIntegral Word64 Int16 Source # 
Instance details
FromIntegral CShort Int16 Source # 
Instance details
FromIntegral CUShort Int16 Source # 
Instance details
FromIntegral CInt Int16 Source # 
Instance details
FromIntegral CUInt Int16 Source # 
Instance details
FromIntegral CLong Int16 Source # 
Instance details
FromIntegral CULong Int16 Source # 
Instance details
FromIntegral CLLong Int16 Source # 
Instance details
FromIntegral CULLong Int16 Source # 
Instance details
Bounded (Exp Int16) # 
Instance details
Enum (Exp Int16) # 
Instance details
Integral (Exp Int16) # 
Instance details
Num (Exp Int16) # 
Instance details
type PrimSize Int16 
Instance details
type PrimSize Int16 = 2
type Difference Int16 
Instance details
type NatNumMaxBound Int16 
Instance details
type NatNumMaxBound Int16 = 32767
data Vector Int16 
Instance details
type Plain Int16 Source # 
Instance details
data MVector s Int16 
Instance details

data Int32 #

32-bit signed integer type

Instances
Bounded Int32

Since: 2.1

Instance details
Enum Int32

Since: 2.1

Instance details
Eq Int32

Since: 2.1

Instance details

Methods

(==) :: Int32 -> Int32 -> Bool #

(/=) :: Int32 -> Int32 -> Bool #

Integral Int32

Since: 2.1

Instance details
Num Int32

Since: 2.1

Instance details
Ord Int32

Since: 2.1

Instance details

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: 2.1

Instance details
Real Int32

Since: 2.1

Instance details

Methods

toRational :: Int32 -> Rational #

Show Int32

Since: 2.1

Instance details

Methods

showsPrec :: Int -> Int32 -> ShowS #

show :: Int32 -> String #

showList :: [Int32] -> ShowS #

Ix Int32

Since: 2.1

Instance details
Lift Int32 
Instance details

Methods

lift :: Int32 -> Q Exp #

PrintfArg Int32

Since: 2.1

Instance details
Storable Int32

Since: 2.1

Instance details

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: 2.1

Instance details
FiniteBits Int32

Since: 4.6.0.0

Instance details
PrimType Int32 
Instance details

Associated Types

type PrimSize Int32 :: Nat #

PrimMemoryComparable Int32 
Instance details
Subtractive Int32 
Instance details

Associated Types

type Difference Int32 :: * #

Methods

(-) :: Int32 -> Int32 -> Difference Int32 #

NFData Int32 
Instance details

Methods

rnf :: Int32 -> () #

Hashable Int32 
Instance details

Methods

hashWithSalt :: Int -> Int32 -> Int #

hash :: Int32 -> Int #

Prim Int32 
Instance details
Unbox Int32 
Instance details
Pretty Int32 
Instance details

Methods

pretty :: Int32 -> Doc b #

prettyList :: [Int32] -> Doc b #

IsScalar Int32 Source # 
Instance details

Methods

scalarType :: ScalarType Int32

IsBounded Int32 Source # 
Instance details

Methods

boundedType :: BoundedType Int32

IsNum Int32 Source # 
Instance details

Methods

numType :: NumType Int32

IsIntegral Int32 Source # 
Instance details

Methods

integralType :: IntegralType Int32

Elt Int32 Source # 
Instance details

Methods

eltType :: Int32 -> TupleType (EltRepr Int32)

fromElt :: Int32 -> EltRepr Int32

toElt :: EltRepr Int32 -> Int32

Eq Int32 Source # 
Instance details
Ord Int32 Source # 
Instance details
FiniteBits Int32 Source # 
Instance details
Bits Int32 Source # 
Instance details
Vector Vector Int32 
Instance details
MVector MVector Int32 
Instance details
Lift Exp Int32 Source # 
Instance details

Associated Types

type Plain Int32 :: * Source #

Methods

lift :: Int32 -> Exp (Plain Int32) Source #

ToFloating Int32 Double Source # 
Instance details
ToFloating Int32 Float Source # 
Instance details
ToFloating Int32 CFloat Source # 
Instance details
ToFloating Int32 CDouble Source # 
Instance details
ToFloating Int32 Half Source # 
Instance details
FromIntegral Int Int32 Source # 
Instance details
FromIntegral Int8 Int32 Source # 
Instance details
FromIntegral Int16 Int32 Source # 
Instance details
FromIntegral Int32 Double Source # 
Instance details
FromIntegral Int32 Float Source # 
Instance details
FromIntegral Int32 Int Source # 
Instance details
FromIntegral Int32 Int8 Source # 
Instance details
FromIntegral Int32 Int16 Source # 
Instance details
FromIntegral Int32 Int32 Source # 
Instance details
FromIntegral Int32 Int64 Source # 
Instance details
FromIntegral Int32 Word Source # 
Instance details
FromIntegral Int32 Word8 Source # 
Instance details
FromIntegral Int32 Word16 Source # 
Instance details
FromIntegral Int32 Word32 Source # 
Instance details
FromIntegral Int32 Word64 Source # 
Instance details
FromIntegral Int32 CShort Source # 
Instance details
FromIntegral Int32 CUShort Source # 
Instance details
FromIntegral Int32 CInt Source # 
Instance details
FromIntegral Int32 CUInt Source # 
Instance details
FromIntegral Int32 CLong Source # 
Instance details
FromIntegral Int32 CULong Source # 
Instance details
FromIntegral Int32 CLLong Source # 
Instance details
FromIntegral Int32 CULLong Source # 
Instance details
FromIntegral Int32 CFloat Source # 
Instance details
FromIntegral Int32 CDouble Source # 
Instance details
FromIntegral Int32 Half Source # 
Instance details
FromIntegral Int64 Int32 Source # 
Instance details
FromIntegral Word Int32 Source # 
Instance details
FromIntegral Word8 Int32 Source # 
Instance details
FromIntegral Word16 Int32 Source # 
Instance details
FromIntegral Word32 Int32 Source # 
Instance details
FromIntegral Word64 Int32 Source # 
Instance details
FromIntegral CShort Int32 Source # 
Instance details
FromIntegral CUShort Int32 Source # 
Instance details
FromIntegral CInt Int32 Source # 
Instance details
FromIntegral CUInt Int32 Source # 
Instance details
FromIntegral CLong Int32 Source # 
Instance details
FromIntegral CULong Int32 Source # 
Instance details
FromIntegral CLLong Int32 Source # 
Instance details
FromIntegral CULLong Int32 Source # 
Instance details
Bounded (Exp Int32) # 
Instance details
Enum (Exp Int32) # 
Instance details
Integral (Exp Int32) # 
Instance details
Num (Exp Int32) # 
Instance details
type PrimSize Int32 
Instance details
type PrimSize Int32 = 4
type Difference Int32 
Instance details
type NatNumMaxBound Int32 
Instance details
type NatNumMaxBound Int32 = 2147483647
data Vector Int32 
Instance details
type Plain Int32 Source # 
Instance details
data MVector s Int32 
Instance details

data Int64 #

64-bit signed integer type

Instances
Bounded Int64

Since: 2.1

Instance details
Enum Int64

Since: 2.1

Instance details
Eq Int64

Since: 2.1

Instance details

Methods

(==) :: Int64 -> Int64 -> Bool #

(/=) :: Int64 -> Int64 -> Bool #

Integral Int64

Since: 2.1

Instance details
Num Int64

Since: 2.1

Instance details
Ord Int64

Since: 2.1

Instance details

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: 2.1

Instance details
Real Int64

Since: 2.1

Instance details

Methods

toRational :: Int64 -> Rational #

Show Int64

Since: 2.1

Instance details

Methods

showsPrec :: Int -> Int64 -> ShowS #

show :: Int64 -> String #

showList :: [Int64] -> ShowS #

Ix Int64

Since: 2.1

Instance details
Lift Int64 
Instance details

Methods

lift :: Int64 -> Q Exp #

PrintfArg Int64

Since: 2.1

Instance details
Storable Int64

Since: 2.1

Instance details

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: 2.1

Instance details
FiniteBits Int64

Since: 4.6.0.0

Instance details
PrimType Int64 
Instance details

Associated Types

type PrimSize Int64 :: Nat #

PrimMemoryComparable Int64 
Instance details
Subtractive Int64 
Instance details

Associated Types

type Difference Int64 :: * #

Methods

(-) :: Int64 -> Int64 -> Difference Int64 #

NFData Int64 
Instance details

Methods

rnf :: Int64 -> () #

Hashable Int64 
Instance details

Methods

hashWithSalt :: Int -> Int64 -> Int #

hash :: Int64 -> Int #

Prim Int64 
Instance details
Unbox Int64 
Instance details
Pretty Int64 
Instance details

Methods

pretty :: Int64 -> Doc b #

prettyList :: [Int64] -> Doc b #

IsScalar Int64 Source # 
Instance details

Methods

scalarType :: ScalarType Int64

IsBounded Int64 Source # 
Instance details

Methods

boundedType :: BoundedType Int64

IsNum Int64 Source # 
Instance details

Methods

numType :: NumType Int64

IsIntegral Int64 Source # 
Instance details

Methods

integralType :: IntegralType Int64

Elt Int64 Source # 
Instance details

Methods

eltType :: Int64 -> TupleType (EltRepr Int64)

fromElt :: Int64 -> EltRepr Int64

toElt :: EltRepr Int64 -> Int64

Eq Int64 Source # 
Instance details
Ord Int64 Source # 
Instance details
FiniteBits Int64 Source # 
Instance details
Bits Int64 Source # 
Instance details
Vector Vector Int64 
Instance details
MVector MVector Int64 
Instance details
Lift Exp Int64 Source # 
Instance details

Associated Types

type Plain Int64 :: * Source #

Methods

lift :: Int64 -> Exp (Plain Int64) Source #

ToFloating Int64 Double Source # 
Instance details
ToFloating Int64 Float Source # 
Instance details
ToFloating Int64 CFloat Source # 
Instance details
ToFloating Int64 CDouble Source # 
Instance details
ToFloating Int64 Half Source # 
Instance details
FromIntegral Int Int64 Source # 
Instance details
FromIntegral Int8 Int64 Source # 
Instance details
FromIntegral Int16 Int64 Source # 
Instance details
FromIntegral Int32 Int64 Source # 
Instance details
FromIntegral Int64 Double Source # 
Instance details
FromIntegral Int64 Float Source # 
Instance details
FromIntegral Int64 Int Source # 
Instance details
FromIntegral Int64 Int8 Source # 
Instance details
FromIntegral Int64 Int16 Source # 
Instance details
FromIntegral Int64 Int32 Source # 
Instance details
FromIntegral Int64 Int64 Source # 
Instance details
FromIntegral Int64 Word Source # 
Instance details
FromIntegral Int64 Word8 Source # 
Instance details
FromIntegral Int64 Word16 Source # 
Instance details
FromIntegral Int64 Word32 Source # 
Instance details
FromIntegral Int64 Word64 Source # 
Instance details
FromIntegral Int64 CShort Source # 
Instance details
FromIntegral Int64 CUShort Source # 
Instance details
FromIntegral Int64 CInt Source # 
Instance details
FromIntegral Int64 CUInt Source # 
Instance details
FromIntegral Int64 CLong Source # 
Instance details
FromIntegral Int64 CULong Source # 
Instance details
FromIntegral Int64 CLLong Source # 
Instance details
FromIntegral Int64 CULLong Source # 
Instance details
FromIntegral Int64 CFloat Source # 
Instance details
FromIntegral Int64 CDouble Source # 
Instance details
FromIntegral Int64 Half Source # 
Instance details
FromIntegral Word Int64 Source # 
Instance details
FromIntegral Word8 Int64 Source # 
Instance details
FromIntegral Word16 Int64 Source # 
Instance details
FromIntegral Word32 Int64 Source # 
Instance details
FromIntegral Word64 Int64 Source # 
Instance details
FromIntegral CShort Int64 Source # 
Instance details
FromIntegral CUShort Int64 Source # 
Instance details
FromIntegral CInt Int64 Source # 
Instance details
FromIntegral CUInt Int64 Source # 
Instance details
FromIntegral CLong Int64 Source # 
Instance details
FromIntegral CULong Int64 Source # 
Instance details
FromIntegral CLLong Int64 Source # 
Instance details
FromIntegral CULLong Int64 Source # 
Instance details
Bounded (Exp Int64) # 
Instance details
Enum (Exp Int64) # 
Instance details
Integral (Exp Int64) # 
Instance details
Num (Exp Int64) # 
Instance details
type PrimSize Int64 
Instance details
type PrimSize Int64 = 8
type Difference Int64 
Instance details
type NatNumMaxBound Int64 
Instance details
type NatNumMaxBound Int64 = 9223372036854775807
data Vector Int64 
Instance details
type Plain Int64 Source # 
Instance details
data MVector s Int64 
Instance details

data Word #

A Word is an unsigned integral type, with the same size as Int.

Instances
Bounded Word

Since: 2.1

Instance details
Enum Word

Since: 2.1

Instance details

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

Methods

(==) :: Word -> Word -> Bool #

(/=) :: Word -> Word -> Bool #

Integral Word

Since: 2.1

Instance details

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: 2.1

Instance details

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

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: 4.5.0.0

Instance details
Real Word

Since: 2.1

Instance details

Methods

toRational :: Word -> Rational #

Show Word

Since: 2.1

Instance details

Methods

showsPrec :: Int -> Word -> ShowS #

show :: Word -> String #

showList :: [Word] -> ShowS #

Lift Word 
Instance details

Methods

lift :: Word -> Q Exp #

PrintfArg Word

Since: 2.1

Instance details
Storable Word

Since: 2.1

Instance details

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: 2.1

Instance details
FiniteBits Word

Since: 4.6.0.0

Instance details
PrimType Word 
Instance details

Associated Types

type PrimSize Word :: Nat #

PrimMemoryComparable Word 
Instance details
Subtractive Word 
Instance details

Associated Types

type Difference Word :: * #

Methods

(-) :: Word -> Word -> Difference Word #

NFData Word 
Instance details

Methods

rnf :: Word -> () #

Hashable Word 
Instance details

Methods

hashWithSalt :: Int -> Word -> Int #

hash :: Word -> Int #

Prim Word 
Instance details
Unbox Word 
Instance details
Pretty Word 
Instance details

Methods

pretty :: Word -> Doc b #

prettyList :: [Word] -> Doc b #

IsScalar Word Source # 
Instance details

Methods

scalarType :: ScalarType Word

IsBounded Word Source # 
Instance details

Methods

boundedType :: BoundedType Word

IsNum Word Source # 
Instance details

Methods

numType :: NumType Word

IsIntegral Word Source # 
Instance details

Methods

integralType :: IntegralType Word

Elt Word Source # 
Instance details

Methods

eltType :: Word -> TupleType (EltRepr Word)

fromElt :: Word -> EltRepr Word

toElt :: EltRepr Word -> Word

Eq Word Source # 
Instance details
Ord Word Source # 
Instance details
FiniteBits Word Source # 
Instance details
Bits Word Source # 
Instance details
Vector Vector Word 
Instance details
MVector MVector Word 
Instance details
Lift Exp Word Source # 
Instance details

Associated Types

type Plain Word :: * Source #

Methods

lift :: Word -> Exp (Plain Word) Source #

ToFloating Word Double Source # 
Instance details
ToFloating Word Float Source # 
Instance details
ToFloating Word CFloat Source # 
Instance details
ToFloating Word CDouble Source # 
Instance details
ToFloating Word Half Source # 
Instance details
FromIntegral Int Word Source # 
Instance details
FromIntegral Int8 Word Source # 
Instance details
FromIntegral Int16 Word Source # 
Instance details
FromIntegral Int32 Word Source # 
Instance details
FromIntegral Int64 Word Source # 
Instance details
FromIntegral Word Double Source # 
Instance details
FromIntegral Word Float Source # 
Instance details
FromIntegral Word Int Source # 
Instance details
FromIntegral Word Int8 Source # 
Instance details
FromIntegral Word Int16 Source # 
Instance details
FromIntegral Word Int32 Source # 
Instance details
FromIntegral Word Int64 Source # 
Instance details
FromIntegral Word Word Source # 
Instance details
FromIntegral Word Word8 Source # 
Instance details
FromIntegral Word Word16 Source # 
Instance details
FromIntegral Word Word32 Source # 
Instance details
FromIntegral Word Word64 Source # 
Instance details
FromIntegral Word CShort Source # 
Instance details
FromIntegral Word CUShort Source # 
Instance details
FromIntegral Word CInt Source # 
Instance details
FromIntegral Word CUInt Source # 
Instance details
FromIntegral Word CLong Source # 
Instance details
FromIntegral Word CULong Source # 
Instance details
FromIntegral Word CLLong Source # 
Instance details
FromIntegral Word CULLong Source # 
Instance details
FromIntegral Word CFloat Source # 
Instance details
FromIntegral Word CDouble Source # 
Instance details
FromIntegral Word Half Source # 
Instance details
FromIntegral Word8 Word Source # 
Instance details
FromIntegral Word16 Word Source # 
Instance details
FromIntegral Word32 Word Source # 
Instance details
FromIntegral Word64 Word Source # 
Instance details
FromIntegral CShort Word Source # 
Instance details
FromIntegral CUShort Word Source # 
Instance details
FromIntegral CInt Word Source # 
Instance details
FromIntegral CUInt Word Source # 
Instance details
FromIntegral CLong Word Source # 
Instance details
FromIntegral CULong Word Source # 
Instance details
FromIntegral CLLong Word Source # 
Instance details
FromIntegral CULLong Word Source # 
Instance details
() :=> (Bounded Word) 
Instance details

Methods

ins :: () :- Bounded Word #

() :=> (Enum Word) 
Instance details

Methods

ins :: () :- Enum Word #

() :=> (Eq Word) 
Instance details

Methods

ins :: () :- Eq Word #

() :=> (Integral Word) 
Instance details

Methods

ins :: () :- Integral Word #

() :=> (Num Word) 
Instance details

Methods

ins :: () :- Num Word #

() :=> (Ord Word) 
Instance details

Methods

ins :: () :- Ord Word #

() :=> (Read Word) 
Instance details

Methods

ins :: () :- Read Word #

() :=> (Real Word) 
Instance details

Methods

ins :: () :- Real Word #

() :=> (Show Word) 
Instance details

Methods

ins :: () :- Show Word #

() :=> (Bits Word) 
Instance details

Methods

ins :: () :- Bits Word #

Generic1 (URec Word :: k -> *) 
Instance details

Associated Types

type Rep1 (URec Word) :: k -> * #

Methods

from1 :: URec Word a -> Rep1 (URec Word) a #

to1 :: Rep1 (URec Word) a -> URec Word a #

Bounded (Exp Word) # 
Instance details
Enum (Exp Word) # 
Instance details
Integral (Exp Word) # 
Instance details
Num (Exp Word) # 
Instance details
Functor (URec Word :: * -> *) 
Instance details

Methods

fmap :: (a -> b) -> URec Word a -> URec Word b #

(<$) :: a -> URec Word b -> URec Word a #

Foldable (URec Word :: * -> *) 
Instance details

Methods

fold :: Monoid m => URec Word m -> m #

foldMap :: Monoid m => (a -> m) -> URec Word a -> m #

foldr :: (a -> b -> b) -> b -> URec Word a -> b #

foldr' :: (a -> b -> b) -> b -> URec Word a -> b #

foldl :: (b -> a -> b) -> b -> URec Word a -> b #

foldl' :: (b -> a -> b) -> b -> URec Word a -> b #

foldr1 :: (a -> a -> a) -> URec Word a -> a #

foldl1 :: (a -> a -> a) -> URec Word a -> a #

toList :: URec Word a -> [a] #

null :: URec Word a -> Bool #

length :: URec Word a -> Int #

elem :: Eq a => a -> URec Word a -> Bool #

maximum :: Ord a => URec Word a -> a #

minimum :: Ord a => URec Word a -> a #

sum :: Num a => URec Word a -> a #

product :: Num a => URec Word a -> a #

Traversable (URec Word :: * -> *) 
Instance details

Methods

traverse :: Applicative f => (a -> f b) -> URec Word a -> f (URec Word b) #

sequenceA :: Applicative f => URec Word (f a) -> f (URec Word a) #

mapM :: Monad m => (a -> m b) -> URec Word a -> m (URec Word b) #

sequence :: Monad m => URec Word (m a) -> m (URec Word a) #

Eq (URec Word p) 
Instance details

Methods

(==) :: URec Word p -> URec Word p -> Bool #

(/=) :: URec Word p -> URec Word p -> Bool #

Ord (URec Word p) 
Instance details

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) 
Instance details

Methods

showsPrec :: Int -> URec Word p -> ShowS #

show :: URec Word p -> String #

showList :: [URec Word p] -> ShowS #

Generic (URec Word p) 
Instance details

Associated Types

type Rep (URec Word p) :: * -> * #

Methods

from :: URec Word p -> Rep (URec Word p) x #

to :: Rep (URec Word p) x -> URec Word p #

type PrimSize Word 
Instance details
type PrimSize Word = 8
type Difference Word 
Instance details
type NatNumMaxBound Word 
Instance details
data Vector Word 
Instance details
type Plain Word Source # 
Instance details
type Plain Word = Word
data URec Word (p :: k)

Used for marking occurrences of Word#

Since: 4.9.0.0

Instance details
data URec Word (p :: k) = UWord {}
data MVector s Word 
Instance details
type Rep1 (URec Word :: k -> *) 
Instance details
type Rep1 (URec Word :: k -> *) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UWord" PrefixI True) (S1 (MetaSel (Just "uWord#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UWord :: k -> *)))
type Rep (URec Word p) 
Instance details
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 :: * -> *)))

data Word8 #

8-bit unsigned integer type

Instances
Bounded Word8

Since: 2.1

Instance details
Enum Word8

Since: 2.1

Instance details
Eq Word8

Since: 2.1

Instance details

Methods

(==) :: Word8 -> Word8 -> Bool #

(/=) :: Word8 -> Word8 -> Bool #

Integral Word8

Since: 2.1

Instance details
Num Word8

Since: 2.1

Instance details
Ord Word8

Since: 2.1

Instance details

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: 2.1

Instance details
Real Word8

Since: 2.1

Instance details

Methods

toRational :: Word8 -> Rational #

Show Word8

Since: 2.1

Instance details

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Ix Word8

Since: 2.1

Instance details
Lift Word8 
Instance details

Methods

lift :: Word8 -> Q Exp #

PrintfArg Word8

Since: 2.1

Instance details
Storable Word8

Since: 2.1

Instance details

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: 2.1

Instance details
FiniteBits Word8

Since: 4.6.0.0

Instance details
PrimType Word8 
Instance details

Associated Types

type PrimSize Word8 :: Nat #

PrimMemoryComparable Word8 
Instance details
Subtractive Word8 
Instance details

Associated Types

type Difference Word8 :: * #

Methods

(-) :: Word8 -> Word8 -> Difference Word8 #

NFData Word8 
Instance details

Methods

rnf :: Word8 -> () #

Hashable Word8 
Instance details

Methods

hashWithSalt :: Int -> Word8 -> Int #

hash :: Word8 -> Int #

Prim Word8 
Instance details
Unbox Word8 
Instance details
Pretty Word8 
Instance details

Methods

pretty :: Word8 -> Doc b #

prettyList :: [Word8] -> Doc b #

IsScalar Word8 Source # 
Instance details

Methods

scalarType :: ScalarType Word8

IsBounded Word8 Source # 
Instance details

Methods

boundedType :: BoundedType Word8

IsNum Word8 Source # 
Instance details

Methods

numType :: NumType Word8

IsIntegral Word8 Source # 
Instance details

Methods

integralType :: IntegralType Word8

Elt Word8 Source # 
Instance details

Methods

eltType :: Word8 -> TupleType (EltRepr Word8)

fromElt :: Word8 -> EltRepr Word8

toElt :: EltRepr Word8 -> Word8

Eq Word8 Source # 
Instance details
Ord Word8 Source # 
Instance details
FiniteBits Word8 Source # 
Instance details
Bits Word8 Source # 
Instance details
Vector Vector Word8 
Instance details
MVector MVector Word8 
Instance details
Lift Exp Word8 Source # 
Instance details

Associated Types

type Plain Word8 :: * Source #

Methods

lift :: Word8 -> Exp (Plain Word8) Source #

ToFloating Word8 Double Source # 
Instance details
ToFloating Word8 Float Source # 
Instance details
ToFloating Word8 CFloat Source # 
Instance details
ToFloating Word8 CDouble Source # 
Instance details
ToFloating Word8 Half Source # 
Instance details
FromIntegral Int Word8 Source # 
Instance details
FromIntegral Int8 Word8 Source # 
Instance details
FromIntegral Int16 Word8 Source # 
Instance details
FromIntegral Int32 Word8 Source # 
Instance details
FromIntegral Int64 Word8 Source # 
Instance details
FromIntegral Word Word8 Source # 
Instance details
FromIntegral Word8 Double Source # 
Instance details
FromIntegral Word8 Float Source # 
Instance details
FromIntegral Word8 Int Source # 
Instance details
FromIntegral Word8 Int8 Source # 
Instance details
FromIntegral Word8 Int16 Source # 
Instance details
FromIntegral Word8 Int32 Source # 
Instance details
FromIntegral Word8 Int64 Source # 
Instance details
FromIntegral Word8 Word Source # 
Instance details
FromIntegral Word8 Word8 Source # 
Instance details
FromIntegral Word8 Word16 Source # 
Instance details
FromIntegral Word8 Word32 Source # 
Instance details
FromIntegral Word8 Word64 Source # 
Instance details
FromIntegral Word8 CShort Source # 
Instance details
FromIntegral Word8 CUShort Source # 
Instance details
FromIntegral Word8 CInt Source # 
Instance details
FromIntegral Word8 CUInt Source # 
Instance details
FromIntegral Word8 CLong Source # 
Instance details
FromIntegral Word8 CULong Source # 
Instance details
FromIntegral Word8 CLLong Source # 
Instance details
FromIntegral Word8 CULLong Source # 
Instance details
FromIntegral Word8 CFloat Source # 
Instance details
FromIntegral Word8 CDouble Source # 
Instance details
FromIntegral Word8 Half Source # 
Instance details
FromIntegral Word16 Word8 Source # 
Instance details
FromIntegral Word32 Word8 Source # 
Instance details
FromIntegral Word64 Word8 Source # 
Instance details
FromIntegral CShort Word8 Source # 
Instance details
FromIntegral CUShort Word8 Source # 
Instance details
FromIntegral CInt Word8 Source # 
Instance details
FromIntegral CUInt Word8 Source # 
Instance details
FromIntegral CLong Word8 Source # 
Instance details
FromIntegral CULong Word8 Source # 
Instance details
FromIntegral CLLong Word8 Source # 
Instance details
FromIntegral CULLong Word8 Source # 
Instance details
Cons ByteString ByteString Word8 Word8 
Instance details
Cons ByteString ByteString Word8 Word8 
Instance details
Snoc ByteString ByteString Word8 Word8 
Instance details
Snoc ByteString ByteString Word8 Word8 
Instance details
Bounded (Exp Word8) # 
Instance details
Enum (Exp Word8) # 
Instance details
Integral (Exp Word8) # 
Instance details
Num (Exp Word8) # 
Instance details
type PrimSize Word8 
Instance details
type PrimSize Word8 = 1
type Difference Word8 
Instance details
type NatNumMaxBound Word8 
Instance details
data Vector Word8 
Instance details
type Plain Word8 Source # 
Instance details
data MVector s Word8 
Instance details

data Word16 #

16-bit unsigned integer type

Instances
Bounded Word16

Since: 2.1

Instance details
Enum Word16

Since: 2.1

Instance details
Eq Word16

Since: 2.1

Instance details

Methods

(==) :: Word16 -> Word16 -> Bool #

(/=) :: Word16 -> Word16 -> Bool #

Integral Word16

Since: 2.1

Instance details
Num Word16

Since: 2.1

Instance details
Ord Word16

Since: 2.1

Instance details
Read Word16

Since: 2.1

Instance details
Real Word16

Since: 2.1

Instance details
Show Word16

Since: 2.1

Instance details
Ix Word16

Since: 2.1

Instance details
Lift Word16 
Instance details

Methods

lift :: Word16 -> Q Exp #

PrintfArg Word16

Since: 2.1

Instance details
Storable Word16

Since: 2.1

Instance details
Bits Word16

Since: 2.1

Instance details
FiniteBits Word16

Since: 4.6.0.0

Instance details
PrimType Word16 
Instance details

Associated Types

type PrimSize Word16 :: Nat #

PrimMemoryComparable Word16 
Instance details
Subtractive Word16 
Instance details

Associated Types

type Difference Word16 :: * #

NFData Word16 
Instance details

Methods

rnf :: Word16 -> () #

Hashable Word16 
Instance details

Methods

hashWithSalt :: Int -> Word16 -> Int #

hash :: Word16 -> Int #

Prim Word16 
Instance details
Unbox Word16 
Instance details
Pretty Word16 
Instance details

Methods

pretty :: Word16 -> Doc b #

prettyList :: [Word16] -> Doc b #

IsScalar Word16 Source # 
Instance details

Methods

scalarType :: ScalarType Word16

IsBounded Word16 Source # 
Instance details

Methods

boundedType :: BoundedType Word16

IsNum Word16 Source # 
Instance details

Methods

numType :: NumType Word16

IsIntegral Word16 Source # 
Instance details

Methods

integralType :: IntegralType Word16

Elt Word16 Source # 
Instance details

Methods

eltType :: Word16 -> TupleType (EltRepr Word16)

fromElt :: Word16 -> EltRepr Word16

toElt :: EltRepr Word16 -> Word16

Eq Word16 Source # 
Instance details
Ord Word16 Source # 
Instance details
FiniteBits Word16 Source # 
Instance details
Bits Word16 Source # 
Instance details
Vector Vector Word16 
Instance details
MVector MVector Word16 
Instance details
Lift Exp Word16 Source # 
Instance details

Associated Types

type Plain Word16 :: * Source #

Methods

lift :: Word16 -> Exp (Plain Word16) Source #

ToFloating Word16 Double Source # 
Instance details
ToFloating Word16 Float Source # 
Instance details
ToFloating Word16 CFloat Source # 
Instance details
ToFloating Word16 CDouble Source # 
Instance details
ToFloating Word16 Half Source # 
Instance details
FromIntegral Int Word16 Source # 
Instance details
FromIntegral Int8 Word16 Source # 
Instance details
FromIntegral Int16 Word16 Source # 
Instance details
FromIntegral Int32 Word16 Source # 
Instance details
FromIntegral Int64 Word16 Source # 
Instance details
FromIntegral Word Word16 Source # 
Instance details
FromIntegral Word8 Word16 Source # 
Instance details
FromIntegral Word16 Double Source # 
Instance details
FromIntegral Word16 Float Source # 
Instance details
FromIntegral Word16 Int Source # 
Instance details
FromIntegral Word16 Int8 Source # 
Instance details
FromIntegral Word16 Int16 Source # 
Instance details
FromIntegral Word16 Int32 Source # 
Instance details
FromIntegral Word16 Int64 Source # 
Instance details
FromIntegral Word16 Word Source # 
Instance details
FromIntegral Word16 Word8 Source # 
Instance details
FromIntegral Word16 Word16 Source # 
Instance details
FromIntegral Word16 Word32 Source # 
Instance details
FromIntegral Word16 Word64 Source # 
Instance details
FromIntegral Word16 CShort Source # 
Instance details
FromIntegral Word16 CUShort Source # 
Instance details
FromIntegral Word16 CInt Source # 
Instance details
FromIntegral Word16 CUInt Source # 
Instance details
FromIntegral Word16 CLong Source # 
Instance details
FromIntegral Word16 CULong Source # 
Instance details
FromIntegral Word16 CLLong Source # 
Instance details
FromIntegral Word16 CULLong Source # 
Instance details
FromIntegral Word16 CFloat Source # 
Instance details
FromIntegral Word16 CDouble Source # 
Instance details
FromIntegral Word16 Half Source # 
Instance details
FromIntegral Word32 Word16 Source # 
Instance details
FromIntegral Word64 Word16 Source # 
Instance details
FromIntegral CShort Word16 Source # 
Instance details
FromIntegral CUShort Word16 Source # 
Instance details
FromIntegral CInt Word16 Source # 
Instance details
FromIntegral CUInt Word16 Source # 
Instance details
FromIntegral CLong Word16 Source # 
Instance details
FromIntegral CULong Word16 Source # 
Instance details
FromIntegral CLLong Word16 Source # 
Instance details
FromIntegral CULLong Word16 Source # 
Instance details
Bounded (Exp Word16) # 
Instance details
Enum (Exp Word16) # 
Instance details
Integral (Exp Word16) # 
Instance details
Num (Exp Word16) # 
Instance details
type PrimSize Word16 
Instance details
type PrimSize Word16 = 2
type Difference Word16 
Instance details
type NatNumMaxBound Word16 
Instance details
type NatNumMaxBound Word16 = 65535
data Vector Word16 
Instance details
type Plain Word16 Source # 
Instance details
data MVector s Word16 
Instance details

data Word32 #

32-bit unsigned integer type

Instances
Bounded Word32

Since: 2.1

Instance details
Enum Word32

Since: 2.1

Instance details
Eq Word32

Since: 2.1

Instance details

Methods

(==) :: Word32 -> Word32 -> Bool #

(/=) :: Word32 -> Word32 -> Bool #

Integral Word32

Since: 2.1

Instance details
Num Word32

Since: 2.1

Instance details
Ord Word32

Since: 2.1

Instance details
Read Word32

Since: 2.1

Instance details
Real Word32

Since: 2.1

Instance details
Show Word32

Since: 2.1

Instance details
Ix Word32

Since: 2.1

Instance details
Lift Word32 
Instance details

Methods

lift :: Word32 -> Q Exp #

PrintfArg Word32

Since: 2.1

Instance details
Storable Word32

Since: 2.1

Instance details
Bits Word32

Since: 2.1

Instance details
FiniteBits Word32

Since: 4.6.0.0

Instance details
PrimType Word32 
Instance details

Associated Types

type PrimSize Word32 :: Nat #

PrimMemoryComparable Word32 
Instance details
Subtractive Word32 
Instance details

Associated Types

type Difference Word32 :: * #

NFData Word32 
Instance details

Methods

rnf :: Word32 -> () #

Hashable Word32 
Instance details

Methods

hashWithSalt :: Int -> Word32 -> Int #

hash :: Word32 -> Int #

Prim Word32 
Instance details
Unbox Word32 
Instance details
Pretty Word32 
Instance details

Methods

pretty :: Word32 -> Doc b #

prettyList :: [Word32] -> Doc b #

IsScalar Word32 Source # 
Instance details

Methods

scalarType :: ScalarType Word32

IsBounded Word32 Source # 
Instance details

Methods

boundedType :: BoundedType Word32

IsNum Word32 Source # 
Instance details

Methods

numType :: NumType Word32

IsIntegral Word32 Source # 
Instance details

Methods

integralType :: IntegralType Word32

Elt Word32 Source # 
Instance details

Methods

eltType :: Word32 -> TupleType (EltRepr Word32)

fromElt :: Word32 -> EltRepr Word32

toElt :: EltRepr Word32 -> Word32

Eq Word32 Source # 
Instance details
Ord Word32 Source # 
Instance details
FiniteBits Word32 Source # 
Instance details
Bits Word32 Source # 
Instance details
Vector Vector Word32 
Instance details
MVector MVector Word32 
Instance details
Lift Exp Word32 Source # 
Instance details

Associated Types

type Plain Word32 :: * Source #

Methods

lift :: Word32 -> Exp (Plain Word32) Source #

ToFloating Word32 Double Source # 
Instance details
ToFloating Word32 Float Source # 
Instance details
ToFloating Word32 CFloat Source # 
Instance details
ToFloating Word32 CDouble Source # 
Instance details
ToFloating Word32 Half Source # 
Instance details
FromIntegral Int Word32 Source # 
Instance details
FromIntegral Int8 Word32 Source # 
Instance details
FromIntegral Int16 Word32 Source # 
Instance details
FromIntegral Int32 Word32 Source # 
Instance details
FromIntegral Int64 Word32 Source # 
Instance details
FromIntegral Word Word32 Source # 
Instance details
FromIntegral Word8 Word32 Source # 
Instance details
FromIntegral Word16 Word32 Source # 
Instance details
FromIntegral Word32 Double Source # 
Instance details
FromIntegral Word32 Float Source # 
Instance details
FromIntegral Word32 Int Source # 
Instance details
FromIntegral Word32 Int8 Source # 
Instance details
FromIntegral Word32 Int16 Source # 
Instance details
FromIntegral Word32 Int32 Source # 
Instance details
FromIntegral Word32 Int64 Source # 
Instance details
FromIntegral Word32 Word Source # 
Instance details
FromIntegral Word32 Word8 Source # 
Instance details
FromIntegral Word32 Word16 Source # 
Instance details
FromIntegral Word32 Word32 Source # 
Instance details
FromIntegral Word32 Word64 Source # 
Instance details
FromIntegral Word32 CShort Source # 
Instance details
FromIntegral Word32 CUShort Source # 
Instance details
FromIntegral Word32 CInt Source # 
Instance details
FromIntegral Word32 CUInt Source # 
Instance details
FromIntegral Word32 CLong Source # 
Instance details
FromIntegral Word32 CULong Source # 
Instance details
FromIntegral Word32 CLLong Source # 
Instance details
FromIntegral Word32 CULLong Source # 
Instance details
FromIntegral Word32 CFloat Source # 
Instance details
FromIntegral Word32 CDouble Source # 
Instance details
FromIntegral Word32 Half Source # 
Instance details
FromIntegral Word64 Word32 Source # 
Instance details
FromIntegral CShort Word32 Source # 
Instance details
FromIntegral CUShort Word32 Source # 
Instance details
FromIntegral CInt Word32 Source # 
Instance details
FromIntegral CUInt Word32 Source # 
Instance details
FromIntegral CLong Word32 Source # 
Instance details
FromIntegral CULong Word32 Source # 
Instance details
FromIntegral CLLong Word32 Source # 
Instance details
FromIntegral CULLong Word32 Source # 
Instance details
Bounded (Exp Word32) # 
Instance details
Enum (Exp Word32) # 
Instance details
Integral (Exp Word32) # 
Instance details
Num (Exp Word32) # 
Instance details
type PrimSize Word32 
Instance details
type PrimSize Word32 = 4
type Difference Word32 
Instance details
type NatNumMaxBound Word32 
Instance details
type NatNumMaxBound Word32 = 4294967295
data Vector Word32 
Instance details
type Plain Word32 Source # 
Instance details
data MVector s Word32 
Instance details

data Word64 #

64-bit unsigned integer type

Instances
Bounded Word64

Since: 2.1

Instance details
Enum Word64

Since: 2.1

Instance details
Eq Word64

Since: 2.1

Instance details

Methods

(==) :: Word64 -> Word64 -> Bool #

(/=) :: Word64 -> Word64 -> Bool #

Integral Word64

Since: 2.1

Instance details
Num Word64

Since: 2.1

Instance details
Ord Word64

Since: 2.1

Instance details
Read Word64

Since: 2.1

Instance details
Real Word64

Since: 2.1

Instance details
Show Word64

Since: 2.1

Instance details
Ix Word64

Since: 2.1

Instance details
Lift Word64 
Instance details

Methods

lift :: Word64 -> Q Exp #

PrintfArg Word64

Since: 2.1

Instance details
Storable Word64

Since: 2.1

Instance details
Bits Word64

Since: 2.1

Instance details
FiniteBits Word64

Since: 4.6.0.0

Instance details
PrimType Word64 
Instance details

Associated Types

type PrimSize Word64 :: Nat #

PrimMemoryComparable Word64 
Instance details
Subtractive Word64 
Instance details

Associated Types

type Difference Word64 :: * #

NFData Word64 
Instance details

Methods

rnf :: Word64 -> () #

Hashable Word64 
Instance details

Methods

hashWithSalt :: Int -> Word64 -> Int #

hash :: Word64 -> Int #

Prim Word64 
Instance details
Unbox Word64 
Instance details
Pretty Word64 
Instance details

Methods

pretty :: Word64 -> Doc b #

prettyList :: [Word64] -> Doc b #

IsScalar Word64 Source # 
Instance details

Methods

scalarType :: ScalarType Word64

IsBounded Word64 Source # 
Instance details

Methods

boundedType :: BoundedType Word64

IsNum Word64 Source # 
Instance details

Methods

numType :: NumType Word64

IsIntegral Word64 Source # 
Instance details

Methods

integralType :: IntegralType Word64

Elt Word64 Source # 
Instance details

Methods

eltType :: Word64 -> TupleType (EltRepr Word64)

fromElt :: Word64 -> EltRepr Word64

toElt :: EltRepr Word64 -> Word64

Eq Word64 Source # 
Instance details
Ord Word64 Source # 
Instance details
FiniteBits Word64 Source # 
Instance details
Bits Word64 Source # 
Instance details
Vector Vector Word64 
Instance details
MVector MVector Word64 
Instance details
Lift Exp Word64 Source # 
Instance details

Associated Types

type Plain Word64 :: * Source #

Methods

lift :: Word64 -> Exp (Plain Word64) Source #

ToFloating Word64 Double Source # 
Instance details
ToFloating Word64 Float Source # 
Instance details
ToFloating Word64 CFloat Source # 
Instance details
ToFloating Word64 CDouble Source # 
Instance details
ToFloating Word64 Half Source # 
Instance details
FromIntegral Int Word64 Source # 
Instance details
FromIntegral Int8 Word64 Source # 
Instance details
FromIntegral Int16 Word64 Source # 
Instance details
FromIntegral Int32 Word64 Source # 
Instance details
FromIntegral Int64 Word64 Source # 
Instance details
FromIntegral Word Word64 Source # 
Instance details
FromIntegral Word8 Word64 Source # 
Instance details
FromIntegral Word16 Word64 Source # 
Instance details
FromIntegral Word32 Word64 Source # 
Instance details
FromIntegral Word64 Double Source # 
Instance details
FromIntegral Word64 Float Source # 
Instance details
FromIntegral Word64 Int Source # 
Instance details
FromIntegral Word64 Int8 Source # 
Instance details
FromIntegral Word64 Int16 Source # 
Instance details
FromIntegral Word64 Int32 Source # 
Instance details
FromIntegral Word64 Int64 Source # 
Instance details
FromIntegral Word64 Word Source # 
Instance details
FromIntegral Word64 Word8 Source # 
Instance details
FromIntegral Word64 Word16 Source # 
Instance details
FromIntegral Word64 Word32 Source # 
Instance details
FromIntegral Word64 Word64 Source # 
Instance details
FromIntegral Word64 CShort Source # 
Instance details
FromIntegral Word64 CUShort Source # 
Instance details
FromIntegral Word64 CInt Source # 
Instance details
FromIntegral Word64 CUInt Source # 
Instance details
FromIntegral Word64 CLong Source # 
Instance details
FromIntegral Word64 CULong Source # 
Instance details
FromIntegral Word64 CLLong Source # 
Instance details
FromIntegral Word64 CULLong Source # 
Instance details
FromIntegral Word64 CFloat Source # 
Instance details
FromIntegral Word64 CDouble Source # 
Instance details
FromIntegral Word64 Half Source # 
Instance details
FromIntegral CShort Word64 Source # 
Instance details
FromIntegral CUShort Word64 Source # 
Instance details
FromIntegral CInt Word64 Source # 
Instance details
FromIntegral CUInt Word64 Source # 
Instance details
FromIntegral CLong Word64 Source # 
Instance details
FromIntegral CULong Word64 Source # 
Instance details
FromIntegral CLLong Word64 Source # 
Instance details
FromIntegral CULLong Word64 Source # 
Instance details
Bounded (Exp Word64) # 
Instance details
Enum (Exp Word64) # 
Instance details
Integral (Exp Word64) # 
Instance details
Num (Exp Word64) # 
Instance details
type PrimSize Word64 
Instance details
type PrimSize Word64 = 8
type Difference Word64 
Instance details
type NatNumMaxBound Word64 
Instance details
type NatNumMaxBound Word64 = 18446744073709551615
data Vector Word64 
Instance details
type Plain Word64 Source # 
Instance details
data MVector s Word64 
Instance details

newtype Half #

Constructors

Half 

Fields

Instances
Eq Half 
Instance details

Methods

(==) :: Half -> Half -> Bool #

(/=) :: Half -> Half -> Bool #

Floating Half 
Instance details

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

Methods

(/) :: Half -> Half -> Half #

recip :: Half -> Half #

fromRational :: Rational -> Half #

Num Half 
Instance details

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

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
Real Half 
Instance details

Methods

toRational :: Half -> Rational #

RealFloat Half 
Instance details
RealFrac Half 
Instance details

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

Methods

showsPrec :: Int -> Half -> ShowS #

show :: Half -> String #

showList :: [Half] -> ShowS #

Storable Half 
Instance details

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 () #

IsScalar Half Source # 
Instance details

Methods

scalarType :: ScalarType Half

IsNum Half Source # 
Instance details

Methods

numType :: NumType Half

IsFloating Half Source # 
Instance details

Methods

floatingType :: FloatingType Half

Elt Half Source # 
Instance details

Methods

eltType :: Half -> TupleType (EltRepr Half)

fromElt :: Half -> EltRepr Half

toElt :: EltRepr Half -> Half

Eq Half Source # 
Instance details
Ord Half Source # 
Instance details
RealFrac Half Source # 
Instance details

Methods

properFraction :: (Num b, ToFloating b Half, IsIntegral b) => Exp Half -> (Exp b, Exp Half) Source #

truncate :: (Elt b, IsIntegral b) => Exp Half -> Exp b Source #

round :: (Elt b, IsIntegral b) => Exp Half -> Exp b Source #

ceiling :: (Elt b, IsIntegral b) => Exp Half -> Exp b Source #

floor :: (Elt b, IsIntegral b) => Exp Half -> Exp b Source #

RealFloat Half Source # 
Instance details
ToFloating Double Half Source # 
Instance details
ToFloating Float Half Source # 
Instance details
ToFloating Int Half Source # 
Instance details
ToFloating Int8 Half Source # 
Instance details
ToFloating Int16 Half Source # 
Instance details
ToFloating Int32 Half Source # 
Instance details
ToFloating Int64 Half Source # 
Instance details
ToFloating Word Half Source # 
Instance details
ToFloating Word8 Half Source # 
Instance details
ToFloating Word16 Half Source # 
Instance details
ToFloating Word32 Half Source # 
Instance details
ToFloating Word64 Half Source # 
Instance details
ToFloating CShort Half Source # 
Instance details
ToFloating CUShort Half Source # 
Instance details
ToFloating CInt Half Source # 
Instance details
ToFloating CUInt Half Source # 
Instance details
ToFloating CLong Half Source # 
Instance details
ToFloating CULong Half Source # 
Instance details
ToFloating CLLong Half Source # 
Instance details
ToFloating CULLong Half Source # 
Instance details
ToFloating CFloat Half Source # 
Instance details
ToFloating CDouble Half Source # 
Instance details
ToFloating Half Double Source # 
Instance details
ToFloating Half Float Source # 
Instance details
ToFloating Half CFloat Source # 
Instance details
ToFloating Half CDouble Source # 
Instance details
ToFloating Half Half Source # 
Instance details
FromIntegral Int Half Source # 
Instance details
FromIntegral Int8 Half Source # 
Instance details
FromIntegral Int16 Half Source # 
Instance details
FromIntegral Int32 Half Source # 
Instance details
FromIntegral Int64 Half Source # 
Instance details
FromIntegral Word Half Source # 
Instance details
FromIntegral Word8 Half Source # 
Instance details
FromIntegral Word16 Half Source # 
Instance details
FromIntegral Word32 Half Source # 
Instance details
FromIntegral Word64 Half Source # 
Instance details
FromIntegral CShort Half Source # 
Instance details
FromIntegral CUShort Half Source # 
Instance details
FromIntegral CInt Half Source # 
Instance details
FromIntegral CUInt Half Source # 
Instance details
FromIntegral CLong Half Source # 
Instance details
FromIntegral CULong Half Source # 
Instance details
FromIntegral CLLong Half Source # 
Instance details
FromIntegral CULLong Half Source # 
Instance details
Enum (Exp Half) # 
Instance details
Floating (Exp Half) # 
Instance details
Fractional (Exp Half) # 
Instance details
Num (Exp Half) # 
Instance details
Elt (Complex Half) Source # 
Instance details

Methods

eltType :: Complex Half -> TupleType (EltRepr (Complex Half))

fromElt :: Complex Half -> EltRepr (Complex Half)

toElt :: EltRepr (Complex Half) -> Complex 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
Eq Float 
Instance details

Methods

(==) :: Float -> Float -> Bool #

(/=) :: Float -> Float -> Bool #

Floating Float

Since: 2.1

Instance details
Ord Float 
Instance details

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: 2.1

Instance details
RealFloat Float

Since: 2.1

Instance details
Lift Float 
Instance details

Methods

lift :: Float -> Q Exp #

Pretty Float 
Instance details

Methods

pretty :: Float -> Doc #

prettyList :: [Float] -> Doc #

PrintfArg Float

Since: 2.1

Instance details
Storable Float

Since: 2.1

Instance details

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

Associated Types

type PrimSize Float :: Nat #

Subtractive Float 
Instance details

Associated Types

type Difference Float :: * #

Methods

(-) :: Float -> Float -> Difference Float #

NFData Float 
Instance details

Methods

rnf :: Float -> () #

Hashable Float 
Instance details

Methods

hashWithSalt :: Int -> Float -> Int #

hash :: Float -> Int #

Prim Float 
Instance details
Unbox Float 
Instance details
Pretty Float 
Instance details

Methods

pretty :: Float -> Doc b #

prettyList :: [Float] -> Doc b #

IsScalar Float Source # 
Instance details

Methods

scalarType :: ScalarType Float

IsNum Float Source # 
Instance details

Methods

numType :: NumType Float

IsFloating Float Source # 
Instance details

Methods

floatingType :: FloatingType Float

Elt Float Source # 
Instance details

Methods

eltType :: Float -> TupleType (EltRepr Float)

fromElt :: Float -> EltRepr Float

toElt :: EltRepr Float -> Float

Eq Float Source # 
Instance details
Ord Float Source # 
Instance details
RealFrac Float Source # 
Instance details
RealFloat Float Source # 
Instance details
Vector Vector Float 
Instance details
MVector MVector Float 
Instance details
Lift Exp Float Source # 
Instance details

Associated Types

type Plain Float :: * Source #

Methods

lift :: Float -> Exp (Plain Float) Source #

ToFloating Double Float Source # 
Instance details
ToFloating Float Double Source # 
Instance details
ToFloating Float Float Source # 
Instance details
ToFloating Float CFloat Source # 
Instance details
ToFloating Float CDouble Source # 
Instance details
ToFloating Float Half Source # 
Instance details
ToFloating Int Float Source # 
Instance details
ToFloating Int8 Float Source # 
Instance details
ToFloating Int16 Float Source # 
Instance details
ToFloating Int32 Float Source # 
Instance details
ToFloating Int64 Float Source # 
Instance details
ToFloating Word Float Source # 
Instance details
ToFloating Word8 Float Source # 
Instance details
ToFloating Word16 Float Source # 
Instance details
ToFloating Word32 Float Source # 
Instance details
ToFloating Word64 Float Source # 
Instance details
ToFloating CShort Float Source # 
Instance details
ToFloating CUShort Float Source # 
Instance details
ToFloating CInt Float Source # 
Instance details
ToFloating CUInt Float Source # 
Instance details
ToFloating CLong Float Source # 
Instance details
ToFloating CULong Float Source # 
Instance details
ToFloating CLLong Float Source # 
Instance details
ToFloating CULLong Float Source # 
Instance details
ToFloating CFloat Float Source # 
Instance details
ToFloating CDouble Float Source # 
Instance details
ToFloating Half Float Source # 
Instance details
FromIntegral Int Float Source # 
Instance details
FromIntegral Int8 Float Source # 
Instance details
FromIntegral Int16 Float Source # 
Instance details
FromIntegral Int32 Float Source # 
Instance details
FromIntegral Int64 Float Source # 
Instance details
FromIntegral Word Float Source # 
Instance details
FromIntegral Word8 Float Source # 
Instance details
FromIntegral Word16 Float Source # 
Instance details
FromIntegral Word32 Float Source # 
Instance details
FromIntegral Word64 Float Source # 
Instance details
FromIntegral CShort Float Source # 
Instance details
FromIntegral CUShort Float Source # 
Instance details
FromIntegral CInt Float Source # 
Instance details
FromIntegral CUInt Float Source # 
Instance details
FromIntegral CLong Float Source # 
Instance details
FromIntegral CULong Float Source # 
Instance details
FromIntegral CLLong Float Source # 
Instance details
FromIntegral CULLong Float Source # 
Instance details
() :=> (Enum Float) 
Instance details

Methods

ins :: () :- Enum Float #

() :=> (Eq Float) 
Instance details

Methods

ins :: () :- Eq Float #

() :=> (Floating Float) 
Instance details

Methods

ins :: () :- Floating Float #

() :=> (Fractional Float) 
Instance details

Methods

ins :: () :- Fractional Float #

() :=> (Num Float) 
Instance details

Methods

ins :: () :- Num Float #

() :=> (Ord Float) 
Instance details

Methods

ins :: () :- Ord Float #

() :=> (Real Float) 
Instance details

Methods

ins :: () :- Real Float #

() :=> (RealFloat Float) 
Instance details

Methods

ins :: () :- RealFloat Float #

() :=> (RealFrac Float) 
Instance details

Methods

ins :: () :- RealFrac Float #

Generic1 (URec Float :: k -> *) 
Instance details

Associated Types

type Rep1 (URec Float) :: k -> * #

Methods

from1 :: URec Float a -> Rep1 (URec Float) a #

to1 :: Rep1 (URec Float) a -> URec Float a #

Enum (Exp Float) # 
Instance details
Floating (Exp Float) # 
Instance details
Fractional (Exp Float) # 
Instance details
Num (Exp Float) # 
Instance details
Elt (Complex Float) Source # 
Instance details

Methods

eltType :: Complex Float -> TupleType (EltRepr (Complex Float))

fromElt :: Complex Float -> EltRepr (Complex Float)

toElt :: EltRepr (Complex Float) -> Complex Float

Functor (URec Float :: * -> *) 
Instance details

Methods

fmap :: (a -> b) -> URec Float a -> URec Float b #

(<$) :: a -> URec Float b -> URec Float a #

Foldable (URec Float :: * -> *) 
Instance details

Methods

fold :: Monoid m => URec Float m -> m #

foldMap :: Monoid m => (a -> m) -> URec Float a -> m #

foldr :: (a -> b -> b) -> b -> URec Float a -> b #

foldr' :: (a -> b -> b) -> b -> URec Float a -> b #

foldl :: (b -> a -> b) -> b -> URec Float a -> b #

foldl' :: (b -> a -> b) -> b -> URec Float a -> b #

foldr1 :: (a -> a -> a) -> URec Float a -> a #

foldl1 :: (a -> a -> a) -> URec Float a -> a #

toList :: URec Float a -> [a] #

null :: URec Float a -> Bool #

length :: URec Float a -> Int #

elem :: Eq a => a -> URec Float a -> Bool #

maximum :: Ord a => URec Float a -> a #

minimum :: Ord a => URec Float a -> a #

sum :: Num a => URec Float a -> a #

product :: Num a => URec Float a -> a #

Traversable (URec Float :: * -> *) 
Instance details

Methods

traverse :: Applicative f => (a -> f b) -> URec Float a -> f (URec Float b) #

sequenceA :: Applicative f => URec Float (f a) -> f (URec Float a) #

mapM :: Monad m => (a -> m b) -> URec Float a -> m (URec Float b) #

sequence :: Monad m => URec Float (m a) -> m (URec Float a) #

Eq (URec Float p) 
Instance details

Methods

(==) :: URec Float p -> URec Float p -> Bool #

(/=) :: URec Float p -> URec Float p -> Bool #

Ord (URec Float p) 
Instance details

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

Methods

showsPrec :: Int -> URec Float p -> ShowS #

show :: URec Float p -> String #

showList :: [URec Float p] -> ShowS #

Generic (URec Float p) 
Instance details

Associated Types

type Rep (URec Float p) :: * -> * #

Methods

from :: URec Float p -> Rep (URec Float p) x #

to :: Rep (URec Float p) x -> URec Float p #

type PrimSize Float 
Instance details
type PrimSize Float = 4
type Difference Float 
Instance details
data Vector Float 
Instance details
type Plain Float Source # 
Instance details
data URec Float (p :: k)

Used for marking occurrences of Float#

Since: 4.9.0.0

Instance details
data URec Float (p :: k) = UFloat {}
data MVector s Float 
Instance details
type Rep1 (URec Float :: k -> *) 
Instance details
type Rep1 (URec Float :: k -> *) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UFloat" PrefixI True) (S1 (MetaSel (Just "uFloat#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UFloat :: k -> *)))
type Rep (URec Float p) 
Instance details
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 :: * -> *)))

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
Eq Double 
Instance details

Methods

(==) :: Double -> Double -> Bool #

(/=) :: Double -> Double -> Bool #

Floating Double

Since: 2.1

Instance details
Ord Double 
Instance details
Read Double

Since: 2.1

Instance details
RealFloat Double

Since: 2.1

Instance details
Lift Double 
Instance details

Methods

lift :: Double -> Q Exp #

Pretty Double 
Instance details

Methods

pretty :: Double -> Doc #

prettyList :: [Double] -> Doc #

PrintfArg Double

Since: 2.1

Instance details
Storable Double

Since: 2.1

Instance details
PrimType Double 
Instance details

Associated Types

type PrimSize Double :: Nat #

Subtractive Double 
Instance details

Associated Types

type Difference Double :: * #

NFData Double 
Instance details

Methods

rnf :: Double -> () #

Hashable Double 
Instance details

Methods

hashWithSalt :: Int -> Double -> Int #

hash :: Double -> Int #

Prim Double 
Instance details
Unbox Double 
Instance details
Pretty Double 
Instance details

Methods

pretty :: Double -> Doc b #

prettyList :: [Double] -> Doc b #

IsScalar Double Source # 
Instance details

Methods

scalarType :: ScalarType Double

IsNum Double Source # 
Instance details

Methods

numType :: NumType Double

IsFloating Double Source # 
Instance details

Methods

floatingType :: FloatingType Double

Elt Double Source # 
Instance details

Methods

eltType :: Double -> TupleType (EltRepr Double)

fromElt :: Double -> EltRepr Double

toElt :: EltRepr Double -> Double

Eq Double Source # 
Instance details
Ord Double Source # 
Instance details
RealFrac Double Source # 
Instance details
RealFloat Double Source # 
Instance details
Vector Vector Double 
Instance details
MVector MVector Double 
Instance details
Lift Exp Double Source # 
Instance details

Associated Types

type Plain Double :: * Source #

Methods

lift :: Double -> Exp (Plain Double) Source #

ToFloating Double Double Source # 
Instance details
ToFloating Double Float Source # 
Instance details
ToFloating Double CFloat Source # 
Instance details
ToFloating Double CDouble Source # 
Instance details
ToFloating Double Half Source # 
Instance details
ToFloating Float Double Source # 
Instance details
ToFloating Int Double Source # 
Instance details
ToFloating Int8 Double Source # 
Instance details
ToFloating Int16 Double Source # 
Instance details
ToFloating Int32 Double Source # 
Instance details
ToFloating Int64 Double Source # 
Instance details
ToFloating Word Double Source # 
Instance details
ToFloating Word8 Double Source # 
Instance details
ToFloating Word16 Double Source # 
Instance details
ToFloating Word32 Double Source # 
Instance details
ToFloating Word64 Double Source # 
Instance details
ToFloating CShort Double Source # 
Instance details
ToFloating CUShort Double Source # 
Instance details
ToFloating CInt Double Source # 
Instance details
ToFloating CUInt Double Source # 
Instance details
ToFloating CLong Double Source # 
Instance details
ToFloating CULong Double Source # 
Instance details
ToFloating CLLong Double Source # 
Instance details
ToFloating CULLong Double Source # 
Instance details
ToFloating CFloat Double Source # 
Instance details
ToFloating CDouble Double Source # 
Instance details
ToFloating Half Double Source # 
Instance details
FromIntegral Int Double Source # 
Instance details
FromIntegral Int8 Double Source # 
Instance details
FromIntegral Int16 Double Source # 
Instance details
FromIntegral Int32 Double Source # 
Instance details
FromIntegral Int64 Double Source # 
Instance details
FromIntegral Word Double Source # 
Instance details
FromIntegral Word8 Double Source # 
Instance details
FromIntegral Word16 Double Source # 
Instance details
FromIntegral Word32 Double Source # 
Instance details
FromIntegral Word64 Double Source # 
Instance details
FromIntegral CShort Double Source # 
Instance details
FromIntegral CUShort Double Source # 
Instance details
FromIntegral CInt Double Source # 
Instance details
FromIntegral CUInt Double Source # 
Instance details
FromIntegral CLong Double Source # 
Instance details
FromIntegral CULong Double Source # 
Instance details
FromIntegral CLLong Double Source # 
Instance details
FromIntegral CULLong Double Source # 
Instance details
() :=> (Enum Double) 
Instance details

Methods

ins :: () :- Enum Double #

() :=> (Eq Double) 
Instance details

Methods

ins :: () :- Eq Double #

() :=> (Floating Double) 
Instance details

Methods

ins :: () :- Floating Double #

() :=> (Fractional Double) 
Instance details

Methods

ins :: () :- Fractional Double #

() :=> (Num Double) 
Instance details

Methods

ins :: () :- Num Double #

() :=> (Ord Double) 
Instance details

Methods

ins :: () :- Ord Double #

() :=> (Real Double) 
Instance details

Methods

ins :: () :- Real Double #

() :=> (RealFloat Double) 
Instance details

Methods

ins :: () :- RealFloat Double #

() :=> (RealFrac Double) 
Instance details

Methods

ins :: () :- RealFrac Double #

Generic1 (URec Double :: k -> *) 
Instance details

Associated Types

type Rep1 (URec Double) :: k -> * #

Methods

from1 :: URec Double a -> Rep1 (URec Double) a #

to1 :: Rep1 (URec Double) a -> URec Double a #

Enum (Exp Double) # 
Instance details
Floating (Exp Double) # 
Instance details
Fractional (Exp Double) # 
Instance details
Num (Exp Double) # 
Instance details
Elt (Complex Double) Source # 
Instance details

Methods

eltType :: Complex Double -> TupleType (EltRepr (Complex Double))

fromElt :: Complex Double -> EltRepr (Complex Double)

toElt :: EltRepr (Complex Double) -> Complex Double

Functor (URec Double :: * -> *) 
Instance details

Methods

fmap :: (a -> b) -> URec Double a -> URec Double b #

(<$) :: a -> URec Double b -> URec Double a #

Foldable (URec Double :: * -> *) 
Instance details

Methods

fold :: Monoid m => URec Double m -> m #

foldMap :: Monoid m => (a -> m) -> URec Double a -> m #

foldr :: (a -> b -> b) -> b -> URec Double a -> b #

foldr' :: (a -> b -> b) -> b -> URec Double a -> b #

foldl :: (b -> a -> b) -> b -> URec Double a -> b #

foldl' :: (b -> a -> b) -> b -> URec Double a -> b #

foldr1 :: (a -> a -> a) -> URec Double a -> a #

foldl1 :: (a -> a -> a) -> URec Double a -> a #

toList :: URec Double a -> [a] #

null :: URec Double a -> Bool #

length :: URec Double a -> Int #

elem :: Eq a => a -> URec Double a -> Bool #

maximum :: Ord a => URec Double a -> a #

minimum :: Ord a => URec Double a -> a #

sum :: Num a => URec Double a -> a #

product :: Num a => URec Double a -> a #

Traversable (URec Double :: * -> *) 
Instance details

Methods

traverse :: Applicative f => (a -> f b) -> URec Double a -> f (URec Double b) #

sequenceA :: Applicative f => URec Double (f a) -> f (URec Double a) #

mapM :: Monad m => (a -> m b) -> URec Double a -> m (URec Double b) #

sequence :: Monad m => URec Double (m a) -> m (URec Double a) #

Eq (URec Double p) 
Instance details

Methods

(==) :: URec Double p -> URec Double p -> Bool #

(/=) :: URec Double p -> URec Double p -> Bool #

Ord (URec Double p) 
Instance details

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) 
Instance details

Methods

showsPrec :: Int -> URec Double p -> ShowS #

show :: URec Double p -> String #

showList :: [URec Double p] -> ShowS #

Generic (URec Double p) 
Instance details

Associated Types

type Rep (URec Double p) :: * -> * #

Methods

from :: URec Double p -> Rep (URec Double p) x #

to :: Rep (URec Double p) x -> URec Double p #

type PrimSize Double 
Instance details
type PrimSize Double = 8
type Difference Double 
Instance details
data Vector Double 
Instance details
type Plain Double Source # 
Instance details
data URec Double (p :: k)

Used for marking occurrences of Double#

Since: 4.9.0.0

Instance details
data URec Double (p :: k) = UDouble {}
data MVector s Double 
Instance details
type Rep1 (URec Double :: k -> *) 
Instance details
type Rep1 (URec Double :: k -> *) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UDouble" PrefixI True) (S1 (MetaSel (Just "uDouble#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UDouble :: k -> *)))
type Rep (URec Double p) 
Instance details
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 :: * -> *)))

data Bool #

Constructors

False 
True 
Instances
Bounded Bool

Since: 2.1

Instance details
Enum Bool

Since: 2.1

Instance details

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

Methods

(==) :: Bool -> Bool -> Bool #

(/=) :: Bool -> Bool -> Bool #

Ord Bool 
Instance details

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: 2.1

Instance details
Show Bool 
Instance details

Methods

showsPrec :: Int -> Bool -> ShowS #

show :: Bool -> String #

showList :: [Bool] -> ShowS #

Generic Bool 
Instance details

Associated Types

type Rep Bool :: * -> * #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Lift Bool 
Instance details

Methods

lift :: Bool -> Q Exp #

Pretty Bool 
Instance details

Methods

pretty :: Bool -> Doc #

prettyList :: [Bool] -> Doc #

SingKind Bool

Since: 4.9.0.0

Instance details

Associated Types

type DemoteRep Bool :: *

Methods

fromSing :: Sing a -> DemoteRep Bool

Storable Bool

Since: 2.1

Instance details

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: 4.7.0.0

Instance details
FiniteBits Bool

Since: 4.7.0.0

Instance details
NFData Bool 
Instance details

Methods

rnf :: Bool -> () #

Hashable Bool 
Instance details

Methods

hashWithSalt :: Int -> Bool -> Int #

hash :: Bool -> Int #

Unbox Bool 
Instance details
AssertionPredicable Bool 
Instance details
Assertable Bool 
Instance details

Methods

assert :: Bool -> Assertion #

Pretty Bool 
Instance details

Methods

pretty :: Bool -> Doc b #

prettyList :: [Bool] -> Doc b #

IsScalar Bool Source # 
Instance details

Methods

scalarType :: ScalarType Bool

IsBounded Bool Source # 
Instance details

Methods

boundedType :: BoundedType Bool

IsNonNum Bool Source # 
Instance details

Methods

nonNumType :: NonNumType Bool

Elt Bool Source # 
Instance details

Methods

eltType :: Bool -> TupleType (EltRepr Bool)

fromElt :: Bool -> EltRepr Bool

toElt :: EltRepr Bool -> Bool

Eq Bool Source # 
Instance details
Ord Bool Source # 
Instance details
FiniteBits Bool Source # 
Instance details
Bits Bool Source # 
Instance details
SingI False

Since: 4.9.0.0

Instance details

Methods

sing :: Sing False

SingI True

Since: 4.9.0.0

Instance details

Methods

sing :: Sing True

Vector Vector Bool 
Instance details
MVector MVector Bool 
Instance details
Lift Exp Bool Source # 
Instance details

Associated Types

type Plain Bool :: * Source #

Methods

lift :: Bool -> Exp (Plain Bool) Source #

() :=> (Bounded Bool) 
Instance details

Methods

ins :: () :- Bounded Bool #

() :=> (Enum Bool) 
Instance details

Methods

ins :: () :- Enum Bool #

() :=> (Eq Bool) 
Instance details

Methods

ins :: () :- Eq Bool #

() :=> (Ord Bool) 
Instance details

Methods

ins :: () :- Ord Bool #

() :=> (Read Bool) 
Instance details

Methods

ins :: () :- Read Bool #

() :=> (Show Bool) 
Instance details

Methods

ins :: () :- Show Bool #

() :=> (Bits Bool) 
Instance details

Methods

ins :: () :- Bits Bool #

Bounded (Exp Bool) # 
Instance details
type Rep Bool 
Instance details
type Rep Bool = D1 (MetaData "Bool" "GHC.Types" "ghc-prim" False) (C1 (MetaCons "False" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "True" PrefixI False) (U1 :: * -> *))
data Sing (a :: Bool) 
Instance details
data Sing (a :: Bool) where
type DemoteRep Bool 
Instance details
type DemoteRep Bool = Bool
data Vector Bool 
Instance details
type Plain Bool Source # 
Instance details
type Plain Bool = Bool
data MVector s Bool 
Instance details

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
Bounded Char

Since: 2.1

Instance details
Enum Char

Since: 2.1

Instance details

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

Methods

(==) :: Char -> Char -> Bool #

(/=) :: Char -> Char -> Bool #

Ord Char 
Instance details

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: 2.1

Instance details
Show Char

Since: 2.1

Instance details

Methods

showsPrec :: Int -> Char -> ShowS #

show :: Char -> String #

showList :: [Char] -> ShowS #

Lift Char 
Instance details

Methods

lift :: Char -> Q Exp #

Pretty Char 
Instance details

Methods

pretty :: Char -> Doc #

prettyList :: [Char] -> Doc #

PrintfArg Char

Since: 2.1

Instance details
IsChar Char

Since: 2.1

Instance details

Methods

toChar :: Char -> Char #

fromChar :: Char -> Char #

Storable Char

Since: 2.1

Instance details

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

Associated Types

type PrimSize Char :: Nat #

PrimMemoryComparable Char 
Instance details
Subtractive Char 
Instance details

Associated Types

type Difference Char :: * #

Methods

(-) :: Char -> Char -> Difference Char #

NFData Char 
Instance details

Methods

rnf :: Char -> () #

Hashable Char 
Instance details

Methods

hashWithSalt :: Int -> Char -> Int #

hash :: Char -> Int #

Prim Char 
Instance details
Unbox Char 
Instance details
Assertable String 
Instance details

Methods

assert :: String -> Assertion #

ErrorList Char 
Instance details

Methods

listMsg :: String -> [Char] #

Pretty Char 
Instance details

Methods

pretty :: Char -> Doc b #

prettyList :: [Char] -> Doc b #

IsScalar Char Source # 
Instance details

Methods

scalarType :: ScalarType Char

IsBounded Char Source # 
Instance details

Methods

boundedType :: BoundedType Char

IsNonNum Char Source # 
Instance details

Methods

nonNumType :: NonNumType Char

Elt Char Source # 
Instance details

Methods

eltType :: Char -> TupleType (EltRepr Char)

fromElt :: Char -> EltRepr Char

toElt :: EltRepr Char -> Char

Eq Char Source # 
Instance details
Ord Char Source # 
Instance details
Vector Vector Char 
Instance details
MVector MVector Char 
Instance details
Lift Exp Char Source # 
Instance details

Associated Types

type Plain Char :: * Source #

Methods

lift :: Char -> Exp (Plain Char) Source #

KnownSymbol n => Reifies (n :: Symbol) String 
Instance details

Methods

reflect :: proxy n -> String #

Cons Text Text Char Char 
Instance details

Methods

_Cons :: Prism Text Text (Char, Text) (Char, Text) #

Cons Text Text Char Char 
Instance details

Methods

_Cons :: Prism Text Text (Char, Text) (Char, Text) #

Snoc Text Text Char Char 
Instance details

Methods

_Snoc :: Prism Text Text (Text, Char) (Text, Char) #

Snoc Text Text Char Char 
Instance details

Methods

_Snoc :: Prism Text Text (Text, Char) (Text, Char) #

() :=> (Bounded Char) 
Instance details

Methods

ins :: () :- Bounded Char #

() :=> (Enum Char) 
Instance details

Methods

ins :: () :- Enum Char #

() :=> (Ord Char) 
Instance details

Methods

ins :: () :- Ord Char #

() :=> (Read Char) 
Instance details

Methods

ins :: () :- Read Char #

() :=> (Show Char) 
Instance details

Methods

ins :: () :- Show Char #

Generic1 (URec Char :: k -> *) 
Instance details

Associated Types

type Rep1 (URec Char) :: k -> * #

Methods

from1 :: URec Char a -> Rep1 (URec Char) a #

to1 :: Rep1 (URec Char) a -> URec Char a #

Bounded (Exp Char) # 
Instance details
Functor (URec Char :: * -> *) 
Instance details

Methods

fmap :: (a -> b) -> URec Char a -> URec Char b #

(<$) :: a -> URec Char b -> URec Char a #

Foldable (URec Char :: * -> *) 
Instance details

Methods

fold :: Monoid m => URec Char m -> m #

foldMap :: Monoid m => (a -> m) -> URec Char a -> m #

foldr :: (a -> b -> b) -> b -> URec Char a -> b #

foldr' :: (a -> b -> b) -> b -> URec Char a -> b #

foldl :: (b -> a -> b) -> b -> URec Char a -> b #

foldl' :: (b -> a -> b) -> b -> URec Char a -> b #

foldr1 :: (a -> a -> a) -> URec Char a -> a #

foldl1 :: (a -> a -> a) -> URec Char a -> a #

toList :: URec Char a -> [a] #

null :: URec Char a -> Bool #

length :: URec Char a -> Int #

elem :: Eq a => a -> URec Char a -> Bool #

maximum :: Ord a => URec Char a -> a #

minimum :: Ord a => URec Char a -> a #

sum :: Num a => URec Char a -> a #

product :: Num a => URec Char a -> a #

Traversable (URec Char :: * -> *) 
Instance details

Methods

traverse :: Applicative f => (a -> f b) -> URec Char a -> f (URec Char b) #

sequenceA :: Applicative f => URec Char (f a) -> f (URec Char a) #

mapM :: Monad m => (a -> m b) -> URec Char a -> m (URec Char b) #

sequence :: Monad m => URec Char (m a) -> m (URec Char a) #

Eq (URec Char p) 
Instance details

Methods

(==) :: URec Char p -> URec Char p -> Bool #

(/=) :: URec Char p -> URec Char p -> Bool #

Ord (URec Char p) 
Instance details

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) 
Instance details

Methods

showsPrec :: Int -> URec Char p -> ShowS #

show :: URec Char p -> String #

showList :: [URec Char p] -> ShowS #

Generic (URec Char p) 
Instance details

Associated Types

type Rep (URec Char p) :: * -> * #

Methods

from :: URec Char p -> Rep (URec Char p) x #

to :: Rep (URec Char p) x -> URec Char p #

type PrimSize Char 
Instance details
type PrimSize Char = 4
type Difference Char 
Instance details
type NatNumMaxBound Char 
Instance details
type NatNumMaxBound Char = 1114111
data Vector Char 
Instance details
type Plain Char Source # 
Instance details
type Plain Char = Char
data URec Char (p :: k)

Used for marking occurrences of Char#

Since: 4.9.0.0

Instance details
data URec Char (p :: k) = UChar {}
data MVector s Char 
Instance details
type Rep1 (URec Char :: k -> *) 
Instance details
type Rep1 (URec Char :: k -> *) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UChar" PrefixI True) (S1 (MetaSel (Just "uChar#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UChar :: k -> *)))
type Rep (URec Char p) 
Instance details
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 :: * -> *)))

data CFloat #

Haskell type representing the C float type.

Instances
Enum CFloat 
Instance details
Eq CFloat 
Instance details

Methods

(==) :: CFloat -> CFloat -> Bool #

(/=) :: CFloat -> CFloat -> Bool #

Floating CFloat 
Instance details
Fractional CFloat 
Instance details
Num CFloat 
Instance details
Ord CFloat 
Instance details
Read CFloat 
Instance details
Real CFloat 
Instance details
RealFloat CFloat 
Instance details
RealFrac CFloat 
Instance details

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
Storable CFloat 
Instance details
Subtractive CFloat 
Instance details

Associated Types

type Difference CFloat :: * #

NFData CFloat

Since: 1.4.0.0

Instance details

Methods

rnf :: CFloat -> () #

Wrapped CFloat 
Instance details

Associated Types

type Unwrapped CFloat :: * #

IsScalar CFloat Source # 
Instance details

Methods

scalarType :: ScalarType CFloat

IsNum CFloat Source # 
Instance details

Methods

numType :: NumType CFloat

IsFloating CFloat Source # 
Instance details

Methods

floatingType :: FloatingType CFloat

Elt CFloat Source # 
Instance details

Methods

eltType :: CFloat -> TupleType (EltRepr CFloat)

fromElt :: CFloat -> EltRepr CFloat

toElt :: EltRepr CFloat -> CFloat

Eq CFloat Source # 
Instance details
Ord CFloat Source # 
Instance details
RealFrac CFloat Source # 
Instance details
RealFloat CFloat Source # 
Instance details
Rewrapped CFloat t 
Instance details
Lift Exp CFloat Source # 
Instance details

Associated Types

type Plain CFloat :: * Source #

Methods

lift :: CFloat -> Exp (Plain CFloat) Source #

ToFloating Double CFloat Source # 
Instance details
ToFloating Float CFloat Source # 
Instance details
ToFloating Int CFloat Source # 
Instance details
ToFloating Int8 CFloat Source # 
Instance details
ToFloating Int16 CFloat Source # 
Instance details
ToFloating Int32 CFloat Source # 
Instance details
ToFloating Int64 CFloat Source # 
Instance details
ToFloating Word CFloat Source # 
Instance details
ToFloating Word8 CFloat Source # 
Instance details
ToFloating Word16 CFloat Source # 
Instance details
ToFloating Word32 CFloat Source # 
Instance details
ToFloating Word64 CFloat Source # 
Instance details
ToFloating CShort CFloat Source # 
Instance details
ToFloating CUShort CFloat Source # 
Instance details
ToFloating CInt CFloat Source # 
Instance details
ToFloating CUInt CFloat Source # 
Instance details
ToFloating CLong CFloat Source # 
Instance details
ToFloating CULong CFloat Source # 
Instance details
ToFloating CLLong CFloat Source # 
Instance details
ToFloating CULLong CFloat Source # 
Instance details
ToFloating CFloat Double Source # 
Instance details
ToFloating CFloat Float Source # 
Instance details
ToFloating CFloat CFloat Source # 
Instance details
ToFloating CFloat CDouble Source # 
Instance details
ToFloating CFloat Half Source # 
Instance details
ToFloating CDouble CFloat Source # 
Instance details
ToFloating Half CFloat Source # 
Instance details
FromIntegral Int CFloat Source # 
Instance details
FromIntegral Int8 CFloat Source # 
Instance details
FromIntegral Int16 CFloat Source # 
Instance details
FromIntegral Int32 CFloat Source # 
Instance details
FromIntegral Int64 CFloat Source # 
Instance details
FromIntegral Word CFloat Source # 
Instance details
FromIntegral Word8 CFloat Source # 
Instance details
FromIntegral Word16 CFloat Source # 
Instance details
FromIntegral Word32 CFloat Source # 
Instance details
FromIntegral Word64 CFloat Source # 
Instance details
FromIntegral CShort CFloat Source # 
Instance details
FromIntegral CUShort CFloat Source # 
Instance details
FromIntegral CInt CFloat Source # 
Instance details
FromIntegral CUInt CFloat Source # 
Instance details
FromIntegral CLong CFloat Source # 
Instance details
FromIntegral CULong CFloat Source # 
Instance details
FromIntegral CLLong CFloat Source # 
Instance details
FromIntegral CULLong CFloat Source # 
Instance details
Enum (Exp CFloat) # 
Instance details
Floating (Exp CFloat) # 
Instance details
Fractional (Exp CFloat) # 
Instance details
Num (Exp CFloat) # 
Instance details
Elt (Complex CFloat) Source # 
Instance details

Methods

eltType :: Complex CFloat -> TupleType (EltRepr (Complex CFloat))

fromElt :: Complex CFloat -> EltRepr (Complex CFloat)

toElt :: EltRepr (Complex CFloat) -> Complex CFloat

type Difference CFloat 
Instance details
type Unwrapped CFloat 
Instance details
type Plain CFloat Source # 
Instance details

data CDouble #

Haskell type representing the C double type.

Instances
Enum CDouble 
Instance details
Eq CDouble 
Instance details

Methods

(==) :: CDouble -> CDouble -> Bool #

(/=) :: CDouble -> CDouble -> Bool #

Floating CDouble 
Instance details
Fractional CDouble 
Instance details
Num CDouble 
Instance details
Ord CDouble 
Instance details
Read CDouble 
Instance details
Real CDouble 
Instance details
RealFloat CDouble 
Instance details
RealFrac CDouble 
Instance details

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
Storable CDouble 
Instance details
Subtractive CDouble 
Instance details

Associated Types

type Difference CDouble :: * #

NFData CDouble

Since: 1.4.0.0

Instance details

Methods

rnf :: CDouble -> () #

Wrapped CDouble 
Instance details

Associated Types

type Unwrapped CDouble :: * #

IsScalar CDouble Source # 
Instance details

Methods

scalarType :: ScalarType CDouble

IsNum CDouble Source # 
Instance details

Methods

numType :: NumType CDouble

IsFloating CDouble Source # 
Instance details

Methods

floatingType :: FloatingType CDouble

Elt CDouble Source # 
Instance details

Methods

eltType :: CDouble -> TupleType (EltRepr CDouble)

fromElt :: CDouble -> EltRepr CDouble

toElt :: EltRepr CDouble -> CDouble

Eq CDouble Source # 
Instance details
Ord CDouble Source # 
Instance details
RealFrac CDouble Source # 
Instance details
RealFloat CDouble Source # 
Instance details
Rewrapped CDouble t 
Instance details
Lift Exp CDouble Source # 
Instance details

Associated Types

type Plain CDouble :: * Source #

ToFloating Double CDouble Source # 
Instance details
ToFloating Float CDouble Source # 
Instance details
ToFloating Int CDouble Source # 
Instance details
ToFloating Int8 CDouble Source # 
Instance details
ToFloating Int16 CDouble Source # 
Instance details
ToFloating Int32 CDouble Source # 
Instance details
ToFloating Int64 CDouble Source # 
Instance details
ToFloating Word CDouble Source # 
Instance details
ToFloating Word8 CDouble Source # 
Instance details
ToFloating Word16 CDouble Source # 
Instance details
ToFloating Word32 CDouble Source # 
Instance details
ToFloating Word64 CDouble Source # 
Instance details
ToFloating CShort CDouble Source # 
Instance details
ToFloating CUShort CDouble Source # 
Instance details
ToFloating CInt CDouble Source # 
Instance details
ToFloating CUInt CDouble Source # 
Instance details
ToFloating CLong CDouble Source # 
Instance details
ToFloating CULong CDouble Source # 
Instance details
ToFloating CLLong CDouble Source # 
Instance details
ToFloating CULLong CDouble Source # 
Instance details
ToFloating CFloat CDouble Source # 
Instance details
ToFloating CDouble Double Source # 
Instance details
ToFloating CDouble Float Source # 
Instance details
ToFloating CDouble CFloat Source # 
Instance details
ToFloating CDouble CDouble Source # 
Instance details
ToFloating CDouble Half Source # 
Instance details
ToFloating Half CDouble Source # 
Instance details
FromIntegral Int CDouble Source # 
Instance details
FromIntegral Int8 CDouble Source # 
Instance details
FromIntegral Int16 CDouble Source # 
Instance details
FromIntegral Int32 CDouble Source # 
Instance details
FromIntegral Int64 CDouble Source # 
Instance details
FromIntegral Word CDouble Source # 
Instance details
FromIntegral Word8 CDouble Source # 
Instance details
FromIntegral Word16 CDouble Source # 
Instance details
FromIntegral Word32 CDouble Source # 
Instance details
FromIntegral Word64 CDouble Source # 
Instance details
FromIntegral CShort CDouble Source # 
Instance details
FromIntegral CUShort CDouble Source # 
Instance details
FromIntegral CInt CDouble Source # 
Instance details
FromIntegral CUInt CDouble Source # 
Instance details
FromIntegral CLong CDouble Source # 
Instance details
FromIntegral CULong CDouble Source # 
Instance details
FromIntegral CLLong CDouble Source # 
Instance details
FromIntegral CULLong CDouble Source # 
Instance details
Enum (Exp CDouble) # 
Instance details
Floating (Exp CDouble) # 
Instance details
Fractional (Exp CDouble) # 
Instance details
Num (Exp CDouble) # 
Instance details
Elt (Complex CDouble) Source # 
Instance details

Methods

eltType :: Complex CDouble -> TupleType (EltRepr (Complex CDouble))

fromElt :: Complex CDouble -> EltRepr (Complex CDouble)

toElt :: EltRepr (Complex CDouble) -> Complex CDouble

type Difference CDouble 
Instance details
type Unwrapped CDouble 
Instance details
type Plain CDouble Source # 
Instance details

data CShort #

Haskell type representing the C short type.

Instances
Bounded CShort 
Instance details
Enum CShort 
Instance details
Eq CShort 
Instance details

Methods

(==) :: CShort -> CShort -> Bool #

(/=) :: CShort -> CShort -> Bool #

Integral CShort 
Instance details
Num CShort 
Instance details
Ord CShort 
Instance details
Read CShort 
Instance details
Real CShort 
Instance details
Show CShort 
Instance details
Storable CShort 
Instance details
Bits CShort 
Instance details
FiniteBits CShort 
Instance details
Subtractive CShort 
Instance details

Associated Types

type Difference CShort :: * #

NFData CShort

Since: 1.4.0.0

Instance details

Methods

rnf :: CShort -> () #

Wrapped CShort 
Instance details

Associated Types

type Unwrapped CShort :: * #

IsScalar CShort Source # 
Instance details

Methods

scalarType :: ScalarType CShort

IsBounded CShort Source # 
Instance details

Methods

boundedType :: BoundedType CShort

IsNum CShort Source # 
Instance details

Methods

numType :: NumType CShort

IsIntegral CShort Source # 
Instance details

Methods

integralType :: IntegralType CShort

Elt CShort Source # 
Instance details

Methods

eltType :: CShort -> TupleType (EltRepr CShort)

fromElt :: CShort -> EltRepr CShort

toElt :: EltRepr CShort -> CShort

Eq CShort Source # 
Instance details
Ord CShort Source # 
Instance details
FiniteBits CShort Source # 
Instance details
Bits CShort Source # 
Instance details
Rewrapped CShort t 
Instance details
Lift Exp CShort Source # 
Instance details

Associated Types

type Plain CShort :: * Source #

Methods

lift :: CShort -> Exp (Plain CShort) Source #

ToFloating CShort Double Source # 
Instance details
ToFloating CShort Float Source # 
Instance details
ToFloating CShort CFloat Source # 
Instance details
ToFloating CShort CDouble Source # 
Instance details
ToFloating CShort Half Source # 
Instance details
FromIntegral Int CShort Source # 
Instance details
FromIntegral Int8 CShort Source # 
Instance details
FromIntegral Int16 CShort Source # 
Instance details
FromIntegral Int32 CShort Source # 
Instance details
FromIntegral Int64 CShort Source # 
Instance details
FromIntegral Word CShort Source # 
Instance details
FromIntegral Word8 CShort Source # 
Instance details
FromIntegral Word16 CShort Source # 
Instance details
FromIntegral Word32 CShort Source # 
Instance details
FromIntegral Word64 CShort Source # 
Instance details
FromIntegral CShort Double Source # 
Instance details
FromIntegral CShort Float Source # 
Instance details
FromIntegral CShort Int Source # 
Instance details
FromIntegral CShort Int8 Source # 
Instance details
FromIntegral CShort Int16 Source # 
Instance details
FromIntegral CShort Int32 Source # 
Instance details
FromIntegral CShort Int64 Source # 
Instance details
FromIntegral CShort Word Source # 
Instance details
FromIntegral CShort Word8 Source # 
Instance details
FromIntegral CShort Word16 Source # 
Instance details
FromIntegral CShort Word32 Source # 
Instance details
FromIntegral CShort Word64 Source # 
Instance details
FromIntegral CShort CShort Source # 
Instance details
FromIntegral CShort CUShort Source # 
Instance details
FromIntegral CShort CInt Source # 
Instance details
FromIntegral CShort CUInt Source # 
Instance details
FromIntegral CShort CLong Source # 
Instance details
FromIntegral CShort CULong Source # 
Instance details
FromIntegral CShort CLLong Source # 
Instance details
FromIntegral CShort CULLong Source # 
Instance details
FromIntegral CShort CFloat Source # 
Instance details
FromIntegral CShort CDouble Source # 
Instance details
FromIntegral CShort Half Source # 
Instance details
FromIntegral CUShort CShort Source # 
Instance details
FromIntegral CInt CShort Source # 
Instance details
FromIntegral CUInt CShort Source # 
Instance details
FromIntegral CLong CShort Source # 
Instance details
FromIntegral CULong CShort Source # 
Instance details
FromIntegral CLLong CShort Source # 
Instance details
FromIntegral CULLong CShort Source # 
Instance details
Bounded (Exp CShort) # 
Instance details
Enum (Exp CShort) # 
Instance details
Integral (Exp CShort) # 
Instance details
Num (Exp CShort) # 
Instance details
type Difference CShort 
Instance details
type Unwrapped CShort 
Instance details
type Plain CShort Source # 
Instance details

data CUShort #

Haskell type representing the C unsigned short type.

Instances
Bounded CUShort 
Instance details
Enum CUShort 
Instance details
Eq CUShort 
Instance details

Methods

(==) :: CUShort -> CUShort -> Bool #

(/=) :: CUShort -> CUShort -> Bool #

Integral CUShort 
Instance details
Num CUShort 
Instance details
Ord CUShort 
Instance details
Read CUShort 
Instance details
Real CUShort 
Instance details
Show CUShort 
Instance details
Storable CUShort 
Instance details
Bits CUShort 
Instance details
FiniteBits CUShort 
Instance details
Subtractive CUShort 
Instance details

Associated Types

type Difference CUShort :: * #

NFData CUShort

Since: 1.4.0.0

Instance details

Methods

rnf :: CUShort -> () #

Wrapped CUShort 
Instance details

Associated Types

type Unwrapped CUShort :: * #

IsScalar CUShort Source # 
Instance details

Methods

scalarType :: ScalarType CUShort

IsBounded CUShort Source # 
Instance details

Methods

boundedType :: BoundedType CUShort

IsNum CUShort Source # 
Instance details

Methods

numType :: NumType CUShort

IsIntegral CUShort Source # 
Instance details

Methods

integralType :: IntegralType CUShort

Elt CUShort Source # 
Instance details

Methods

eltType :: CUShort -> TupleType (EltRepr CUShort)

fromElt :: CUShort -> EltRepr CUShort

toElt :: EltRepr CUShort -> CUShort

Eq CUShort Source # 
Instance details
Ord CUShort Source # 
Instance details
FiniteBits CUShort Source # 
Instance details
Bits CUShort Source # 
Instance details
Rewrapped CUShort t 
Instance details
Lift Exp CUShort Source # 
Instance details

Associated Types

type Plain CUShort :: * Source #

ToFloating CUShort Double Source # 
Instance details
ToFloating CUShort Float Source # 
Instance details
ToFloating CUShort CFloat Source # 
Instance details
ToFloating CUShort CDouble Source # 
Instance details
ToFloating CUShort Half Source # 
Instance details
FromIntegral Int CUShort Source # 
Instance details
FromIntegral Int8 CUShort Source # 
Instance details
FromIntegral Int16 CUShort Source # 
Instance details
FromIntegral Int32 CUShort Source # 
Instance details
FromIntegral Int64 CUShort Source # 
Instance details
FromIntegral Word CUShort Source # 
Instance details
FromIntegral Word8 CUShort Source # 
Instance details
FromIntegral Word16 CUShort Source # 
Instance details
FromIntegral Word32 CUShort Source # 
Instance details
FromIntegral Word64 CUShort Source # 
Instance details
FromIntegral CShort CUShort Source # 
Instance details
FromIntegral CUShort Double Source # 
Instance details
FromIntegral CUShort Float Source # 
Instance details
FromIntegral CUShort Int Source # 
Instance details
FromIntegral CUShort Int8 Source # 
Instance details
FromIntegral CUShort Int16 Source # 
Instance details
FromIntegral CUShort Int32 Source # 
Instance details
FromIntegral CUShort Int64 Source # 
Instance details
FromIntegral CUShort Word Source # 
Instance details
FromIntegral CUShort Word8 Source # 
Instance details
FromIntegral CUShort Word16 Source # 
Instance details
FromIntegral CUShort Word32 Source # 
Instance details
FromIntegral CUShort Word64 Source # 
Instance details
FromIntegral CUShort CShort Source # 
Instance details
FromIntegral CUShort CUShort Source # 
Instance details
FromIntegral CUShort CInt Source # 
Instance details
FromIntegral CUShort CUInt Source # 
Instance details
FromIntegral CUShort CLong Source # 
Instance details
FromIntegral CUShort CULong Source # 
Instance details
FromIntegral CUShort CLLong Source # 
Instance details
FromIntegral CUShort CULLong Source # 
Instance details
FromIntegral CUShort CFloat Source # 
Instance details
FromIntegral CUShort CDouble Source # 
Instance details
FromIntegral CUShort Half Source # 
Instance details
FromIntegral CInt CUShort Source # 
Instance details
FromIntegral CUInt CUShort Source # 
Instance details
FromIntegral CLong CUShort Source # 
Instance details
FromIntegral CULong CUShort Source # 
Instance details
FromIntegral CLLong CUShort Source # 
Instance details
FromIntegral CULLong CUShort Source # 
Instance details
Bounded (Exp CUShort) # 
Instance details
Enum (Exp CUShort) # 
Instance details
Integral (Exp CUShort) # 
Instance details
Num (Exp CUShort) # 
Instance details
type Difference CUShort 
Instance details
type Unwrapped CUShort 
Instance details
type Plain CUShort Source # 
Instance details

data CInt #

Haskell type representing the C int type.

Instances
Bounded CInt 
Instance details
Enum CInt 
Instance details

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

Methods

(==) :: CInt -> CInt -> Bool #

(/=) :: CInt -> CInt -> Bool #

Integral CInt 
Instance details

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

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

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
Real CInt 
Instance details

Methods

toRational :: CInt -> Rational #

Show CInt 
Instance details

Methods

showsPrec :: Int -> CInt -> ShowS #

show :: CInt -> String #

showList :: [CInt] -> ShowS #

Storable CInt 
Instance details

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
FiniteBits CInt 
Instance details
Subtractive CInt 
Instance details

Associated Types

type Difference CInt :: * #

Methods

(-) :: CInt -> CInt -> Difference CInt #

NFData CInt

Since: 1.4.0.0

Instance details

Methods

rnf :: CInt -> () #

Wrapped CInt 
Instance details

Associated Types

type Unwrapped CInt :: * #

IsScalar CInt Source # 
Instance details

Methods

scalarType :: ScalarType CInt

IsBounded CInt Source # 
Instance details

Methods

boundedType :: BoundedType CInt

IsNum CInt Source # 
Instance details

Methods

numType :: NumType CInt

IsIntegral CInt Source # 
Instance details

Methods

integralType :: IntegralType CInt

Elt CInt Source # 
Instance details

Methods

eltType :: CInt -> TupleType (EltRepr CInt)

fromElt :: CInt -> EltRepr CInt

toElt :: EltRepr CInt -> CInt

Eq CInt Source # 
Instance details
Ord CInt Source # 
Instance details
FiniteBits CInt Source # 
Instance details
Bits CInt Source # 
Instance details
Rewrapped CInt t 
Instance details
Lift Exp CInt Source # 
Instance details

Associated Types

type Plain CInt :: * Source #

Methods

lift :: CInt -> Exp (Plain CInt) Source #

ToFloating CInt Double Source # 
Instance details
ToFloating CInt Float Source # 
Instance details
ToFloating CInt CFloat Source # 
Instance details
ToFloating CInt CDouble Source # 
Instance details
ToFloating CInt Half Source # 
Instance details
FromIntegral Int CInt Source # 
Instance details
FromIntegral Int8 CInt Source # 
Instance details
FromIntegral Int16 CInt Source # 
Instance details
FromIntegral Int32 CInt Source # 
Instance details
FromIntegral Int64 CInt Source # 
Instance details
FromIntegral Word CInt Source # 
Instance details
FromIntegral Word8 CInt Source # 
Instance details
FromIntegral Word16 CInt Source # 
Instance details
FromIntegral Word32 CInt Source # 
Instance details
FromIntegral Word64 CInt Source # 
Instance details
FromIntegral CShort CInt Source # 
Instance details
FromIntegral CUShort CInt Source # 
Instance details
FromIntegral CInt Double Source # 
Instance details
FromIntegral CInt Float Source # 
Instance details
FromIntegral CInt Int Source # 
Instance details
FromIntegral CInt Int8 Source # 
Instance details
FromIntegral CInt Int16 Source # 
Instance details
FromIntegral CInt Int32 Source # 
Instance details
FromIntegral CInt Int64 Source # 
Instance details
FromIntegral CInt Word Source # 
Instance details
FromIntegral CInt Word8 Source # 
Instance details
FromIntegral CInt Word16 Source # 
Instance details
FromIntegral CInt Word32 Source # 
Instance details
FromIntegral CInt Word64 Source # 
Instance details
FromIntegral CInt CShort Source # 
Instance details
FromIntegral CInt CUShort Source # 
Instance details
FromIntegral CInt CInt Source # 
Instance details
FromIntegral CInt CUInt Source # 
Instance details
FromIntegral CInt CLong Source # 
Instance details
FromIntegral CInt CULong Source # 
Instance details
FromIntegral CInt CLLong Source # 
Instance details
FromIntegral CInt CULLong Source # 
Instance details
FromIntegral CInt CFloat Source # 
Instance details
FromIntegral CInt CDouble Source # 
Instance details
FromIntegral CInt Half Source # 
Instance details
FromIntegral CUInt CInt Source # 
Instance details
FromIntegral CLong CInt Source # 
Instance details
FromIntegral CULong CInt Source # 
Instance details
FromIntegral CLLong CInt Source # 
Instance details
FromIntegral CULLong CInt Source # 
Instance details
Bounded (Exp CInt) # 
Instance details
Enum (Exp CInt) # 
Instance details
Integral (Exp CInt) # 
Instance details
Num (Exp CInt) # 
Instance details
type Difference CInt 
Instance details
type Unwrapped CInt 
Instance details
type Plain CInt Source # 
Instance details
type Plain CInt = CInt

data CUInt #

Haskell type representing the C unsigned int type.

Instances
Bounded CUInt 
Instance details
Enum CUInt 
Instance details
Eq CUInt 
Instance details

Methods

(==) :: CUInt -> CUInt -> Bool #

(/=) :: CUInt -> CUInt -> Bool #

Integral CUInt 
Instance details
Num CUInt 
Instance details
Ord CUInt 
Instance details

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
Real CUInt 
Instance details

Methods

toRational :: CUInt -> Rational #

Show CUInt 
Instance details

Methods

showsPrec :: Int -> CUInt -> ShowS #

show :: CUInt -> String #

showList :: [CUInt] -> ShowS #

Storable CUInt 
Instance details

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
FiniteBits CUInt 
Instance details
Subtractive CUInt 
Instance details

Associated Types

type Difference CUInt :: * #

Methods

(-) :: CUInt -> CUInt -> Difference CUInt #

NFData CUInt

Since: 1.4.0.0

Instance details

Methods

rnf :: CUInt -> () #

Wrapped CUInt 
Instance details

Associated Types

type Unwrapped CUInt :: * #

IsScalar CUInt Source # 
Instance details

Methods

scalarType :: ScalarType CUInt

IsBounded CUInt Source # 
Instance details

Methods

boundedType :: BoundedType CUInt

IsNum CUInt Source # 
Instance details

Methods

numType :: NumType CUInt

IsIntegral CUInt Source # 
Instance details

Methods

integralType :: IntegralType CUInt

Elt CUInt Source # 
Instance details

Methods

eltType :: CUInt -> TupleType (EltRepr CUInt)

fromElt :: CUInt -> EltRepr CUInt

toElt :: EltRepr CUInt -> CUInt

Eq CUInt Source # 
Instance details
Ord CUInt Source # 
Instance details
FiniteBits CUInt Source # 
Instance details
Bits CUInt Source # 
Instance details
Rewrapped CUInt t 
Instance details
Lift Exp CUInt Source # 
Instance details

Associated Types

type Plain CUInt :: * Source #

Methods

lift :: CUInt -> Exp (Plain CUInt) Source #

ToFloating CUInt Double Source # 
Instance details
ToFloating CUInt Float Source # 
Instance details
ToFloating CUInt CFloat Source # 
Instance details
ToFloating CUInt CDouble Source # 
Instance details
ToFloating CUInt Half Source # 
Instance details
FromIntegral Int CUInt Source # 
Instance details
FromIntegral Int8 CUInt Source # 
Instance details
FromIntegral Int16 CUInt Source # 
Instance details
FromIntegral Int32 CUInt Source # 
Instance details
FromIntegral Int64 CUInt Source # 
Instance details
FromIntegral Word CUInt Source # 
Instance details
FromIntegral Word8 CUInt Source # 
Instance details
FromIntegral Word16 CUInt Source # 
Instance details
FromIntegral Word32 CUInt Source # 
Instance details
FromIntegral Word64 CUInt Source # 
Instance details
FromIntegral CShort CUInt Source # 
Instance details
FromIntegral CUShort CUInt Source # 
Instance details
FromIntegral CInt CUInt Source # 
Instance details
FromIntegral CUInt Double Source # 
Instance details
FromIntegral CUInt Float Source # 
Instance details
FromIntegral CUInt Int Source # 
Instance details
FromIntegral CUInt Int8 Source # 
Instance details
FromIntegral CUInt Int16 Source # 
Instance details
FromIntegral CUInt Int32 Source # 
Instance details
FromIntegral CUInt Int64 Source # 
Instance details
FromIntegral CUInt Word Source # 
Instance details
FromIntegral CUInt Word8 Source # 
Instance details
FromIntegral CUInt Word16 Source # 
Instance details
FromIntegral CUInt Word32 Source # 
Instance details
FromIntegral CUInt Word64 Source # 
Instance details
FromIntegral CUInt CShort Source # 
Instance details
FromIntegral CUInt CUShort Source # 
Instance details
FromIntegral CUInt CInt Source # 
Instance details
FromIntegral CUInt CUInt Source # 
Instance details
FromIntegral CUInt CLong Source # 
Instance details
FromIntegral CUInt CULong Source # 
Instance details
FromIntegral CUInt CLLong Source # 
Instance details
FromIntegral CUInt CULLong Source # 
Instance details
FromIntegral CUInt CFloat Source # 
Instance details
FromIntegral CUInt CDouble Source # 
Instance details
FromIntegral CUInt Half Source # 
Instance details
FromIntegral CLong CUInt Source # 
Instance details
FromIntegral CULong CUInt Source # 
Instance details
FromIntegral CLLong CUInt Source # 
Instance details
FromIntegral CULLong CUInt Source # 
Instance details
Bounded (Exp CUInt) # 
Instance details
Enum (Exp CUInt) # 
Instance details
Integral (Exp CUInt) # 
Instance details
Num (Exp CUInt) # 
Instance details
type Difference CUInt 
Instance details
type Unwrapped CUInt 
Instance details
type Plain CUInt Source # 
Instance details

data CLong #

Haskell type representing the C long type.

Instances
Bounded CLong 
Instance details
Enum CLong 
Instance details
Eq CLong 
Instance details

Methods

(==) :: CLong -> CLong -> Bool #

(/=) :: CLong -> CLong -> Bool #

Integral CLong 
Instance details
Num CLong 
Instance details
Ord CLong 
Instance details

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
Real CLong 
Instance details

Methods

toRational :: CLong -> Rational #

Show CLong 
Instance details

Methods

showsPrec :: Int -> CLong -> ShowS #

show :: CLong -> String #

showList :: [CLong] -> ShowS #

Storable CLong 
Instance details

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
FiniteBits CLong 
Instance details
Subtractive CLong 
Instance details

Associated Types

type Difference CLong :: * #

Methods

(-) :: CLong -> CLong -> Difference CLong #

NFData CLong

Since: 1.4.0.0

Instance details

Methods

rnf :: CLong -> () #

Wrapped CLong 
Instance details

Associated Types

type Unwrapped CLong :: * #

IsScalar CLong Source # 
Instance details

Methods

scalarType :: ScalarType CLong

IsBounded CLong Source # 
Instance details

Methods

boundedType :: BoundedType CLong

IsNum CLong Source # 
Instance details

Methods

numType :: NumType CLong

IsIntegral CLong Source # 
Instance details

Methods

integralType :: IntegralType CLong

Elt CLong Source # 
Instance details

Methods

eltType :: CLong -> TupleType (EltRepr CLong)

fromElt :: CLong -> EltRepr CLong

toElt :: EltRepr CLong -> CLong

Eq CLong Source # 
Instance details
Ord CLong Source # 
Instance details
FiniteBits CLong Source # 
Instance details
Bits CLong Source # 
Instance details
Rewrapped CLong t 
Instance details
Lift Exp CLong Source # 
Instance details

Associated Types

type Plain CLong :: * Source #

Methods

lift :: CLong -> Exp (Plain CLong) Source #

ToFloating CLong Double Source # 
Instance details
ToFloating CLong Float Source # 
Instance details
ToFloating CLong CFloat Source # 
Instance details
ToFloating CLong CDouble Source # 
Instance details
ToFloating CLong Half Source # 
Instance details
FromIntegral Int CLong Source # 
Instance details
FromIntegral Int8 CLong Source # 
Instance details
FromIntegral Int16 CLong Source # 
Instance details
FromIntegral Int32 CLong Source # 
Instance details
FromIntegral Int64 CLong Source # 
Instance details
FromIntegral Word CLong Source # 
Instance details
FromIntegral Word8 CLong Source # 
Instance details
FromIntegral Word16 CLong Source # 
Instance details
FromIntegral Word32 CLong Source # 
Instance details
FromIntegral Word64 CLong Source # 
Instance details
FromIntegral CShort CLong Source # 
Instance details
FromIntegral CUShort CLong Source # 
Instance details
FromIntegral CInt CLong Source # 
Instance details
FromIntegral CUInt CLong Source # 
Instance details
FromIntegral CLong Double Source # 
Instance details
FromIntegral CLong Float Source # 
Instance details
FromIntegral CLong Int Source # 
Instance details
FromIntegral CLong Int8 Source # 
Instance details
FromIntegral CLong Int16 Source # 
Instance details
FromIntegral CLong Int32 Source # 
Instance details
FromIntegral CLong Int64 Source # 
Instance details
FromIntegral CLong Word Source # 
Instance details
FromIntegral CLong Word8 Source # 
Instance details
FromIntegral CLong Word16 Source # 
Instance details
FromIntegral CLong Word32 Source # 
Instance details
FromIntegral CLong Word64 Source # 
Instance details
FromIntegral CLong CShort Source # 
Instance details
FromIntegral CLong CUShort Source # 
Instance details
FromIntegral CLong CInt Source # 
Instance details
FromIntegral CLong CUInt Source # 
Instance details
FromIntegral CLong CLong Source # 
Instance details
FromIntegral CLong CULong Source # 
Instance details
FromIntegral CLong CLLong Source # 
Instance details
FromIntegral CLong CULLong Source # 
Instance details
FromIntegral CLong CFloat Source # 
Instance details
FromIntegral CLong CDouble Source # 
Instance details
FromIntegral CLong Half Source # 
Instance details
FromIntegral CULong CLong Source # 
Instance details
FromIntegral CLLong CLong Source # 
Instance details
FromIntegral CULLong CLong Source # 
Instance details
Bounded (Exp CLong) # 
Instance details
Enum (Exp CLong) # 
Instance details
Integral (Exp CLong) # 
Instance details
Num (Exp CLong) # 
Instance details
type Difference CLong 
Instance details
type Unwrapped CLong 
Instance details
type Plain CLong Source # 
Instance details

data CULong #

Haskell type representing the C unsigned long type.

Instances
Bounded CULong 
Instance details
Enum CULong 
Instance details
Eq CULong 
Instance details

Methods

(==) :: CULong -> CULong -> Bool #

(/=) :: CULong -> CULong -> Bool #

Integral CULong 
Instance details
Num CULong 
Instance details
Ord CULong 
Instance details
Read CULong 
Instance details
Real CULong 
Instance details
Show CULong 
Instance details
Storable CULong 
Instance details
Bits CULong 
Instance details
FiniteBits CULong 
Instance details
Subtractive CULong 
Instance details

Associated Types

type Difference CULong :: * #

NFData CULong

Since: 1.4.0.0

Instance details

Methods

rnf :: CULong -> () #

Wrapped CULong 
Instance details

Associated Types

type Unwrapped CULong :: * #

IsScalar CULong Source # 
Instance details

Methods

scalarType :: ScalarType CULong

IsBounded CULong Source # 
Instance details

Methods

boundedType :: BoundedType CULong

IsNum CULong Source # 
Instance details

Methods

numType :: NumType CULong

IsIntegral CULong Source # 
Instance details

Methods

integralType :: IntegralType CULong

Elt CULong Source # 
Instance details

Methods

eltType :: CULong -> TupleType (EltRepr CULong)

fromElt :: CULong -> EltRepr CULong

toElt :: EltRepr CULong -> CULong

Eq CULong Source # 
Instance details
Ord CULong Source # 
Instance details
FiniteBits CULong Source # 
Instance details
Bits CULong Source # 
Instance details
Rewrapped CULong t 
Instance details
Lift Exp CULong Source # 
Instance details

Associated Types

type Plain CULong :: * Source #

Methods

lift :: CULong -> Exp (Plain CULong) Source #

ToFloating CULong Double Source # 
Instance details
ToFloating CULong Float Source # 
Instance details
ToFloating CULong CFloat Source # 
Instance details
ToFloating CULong CDouble Source # 
Instance details
ToFloating CULong Half Source # 
Instance details
FromIntegral Int CULong Source # 
Instance details
FromIntegral Int8 CULong Source # 
Instance details
FromIntegral Int16 CULong Source # 
Instance details
FromIntegral Int32 CULong Source # 
Instance details
FromIntegral Int64 CULong Source # 
Instance details
FromIntegral Word CULong Source # 
Instance details
FromIntegral Word8 CULong Source # 
Instance details
FromIntegral Word16 CULong Source # 
Instance details
FromIntegral Word32 CULong Source # 
Instance details
FromIntegral Word64 CULong Source # 
Instance details
FromIntegral CShort CULong Source # 
Instance details
FromIntegral CUShort CULong Source # 
Instance details
FromIntegral CInt CULong Source # 
Instance details
FromIntegral CUInt CULong Source # 
Instance details
FromIntegral CLong CULong Source # 
Instance details
FromIntegral CULong Double Source # 
Instance details
FromIntegral CULong Float Source # 
Instance details
FromIntegral CULong Int Source # 
Instance details
FromIntegral CULong Int8 Source # 
Instance details
FromIntegral CULong Int16 Source # 
Instance details
FromIntegral CULong Int32 Source # 
Instance details
FromIntegral CULong Int64 Source # 
Instance details
FromIntegral CULong Word Source # 
Instance details
FromIntegral CULong Word8 Source # 
Instance details
FromIntegral CULong Word16 Source # 
Instance details
FromIntegral CULong Word32 Source # 
Instance details
FromIntegral CULong Word64 Source # 
Instance details
FromIntegral CULong CShort Source # 
Instance details
FromIntegral CULong CUShort Source # 
Instance details
FromIntegral CULong CInt Source # 
Instance details
FromIntegral CULong CUInt Source # 
Instance details
FromIntegral CULong CLong Source # 
Instance details
FromIntegral CULong CULong Source # 
Instance details
FromIntegral CULong CLLong Source # 
Instance details
FromIntegral CULong CULLong Source # 
Instance details
FromIntegral CULong CFloat Source # 
Instance details
FromIntegral CULong CDouble Source # 
Instance details
FromIntegral CULong Half Source # 
Instance details
FromIntegral CLLong CULong Source # 
Instance details
FromIntegral CULLong CULong Source # 
Instance details
Bounded (Exp CULong) # 
Instance details
Enum (Exp CULong) # 
Instance details
Integral (Exp CULong) # 
Instance details
Num (Exp CULong) # 
Instance details
type Difference CULong 
Instance details
type Unwrapped CULong 
Instance details
type Plain CULong Source # 
Instance details

data CLLong #

Haskell type representing the C long long type.

Instances
Bounded CLLong 
Instance details
Enum CLLong 
Instance details
Eq CLLong 
Instance details

Methods

(==) :: CLLong -> CLLong -> Bool #

(/=) :: CLLong -> CLLong -> Bool #

Integral CLLong 
Instance details
Num CLLong 
Instance details
Ord CLLong 
Instance details
Read CLLong 
Instance details
Real CLLong 
Instance details
Show CLLong 
Instance details
Storable CLLong 
Instance details
Bits CLLong 
Instance details
FiniteBits CLLong 
Instance details
Subtractive CLLong 
Instance details

Associated Types

type Difference CLLong :: * #

NFData CLLong

Since: 1.4.0.0

Instance details

Methods

rnf :: CLLong -> () #

Wrapped CLLong 
Instance details

Associated Types

type Unwrapped CLLong :: * #

IsScalar CLLong Source # 
Instance details

Methods

scalarType :: ScalarType CLLong

IsBounded CLLong Source # 
Instance details

Methods

boundedType :: BoundedType CLLong

IsNum CLLong Source # 
Instance details

Methods

numType :: NumType CLLong

IsIntegral CLLong Source # 
Instance details

Methods

integralType :: IntegralType CLLong

Elt CLLong Source # 
Instance details

Methods

eltType :: CLLong -> TupleType (EltRepr CLLong)

fromElt :: CLLong -> EltRepr CLLong

toElt :: EltRepr CLLong -> CLLong

Eq CLLong Source # 
Instance details
Ord CLLong Source # 
Instance details
FiniteBits CLLong Source # 
Instance details
Bits CLLong Source # 
Instance details
Rewrapped CLLong t 
Instance details
Lift Exp CLLong Source # 
Instance details

Associated Types

type Plain CLLong :: * Source #

Methods

lift :: CLLong -> Exp (Plain CLLong) Source #

ToFloating CLLong Double Source # 
Instance details
ToFloating CLLong Float Source # 
Instance details
ToFloating CLLong CFloat Source # 
Instance details
ToFloating CLLong CDouble Source # 
Instance details
ToFloating CLLong Half Source # 
Instance details
FromIntegral Int CLLong Source # 
Instance details
FromIntegral Int8 CLLong Source # 
Instance details
FromIntegral Int16 CLLong Source # 
Instance details
FromIntegral Int32 CLLong Source # 
Instance details
FromIntegral Int64 CLLong Source # 
Instance details
FromIntegral Word CLLong Source # 
Instance details
FromIntegral Word8 CLLong Source # 
Instance details
FromIntegral Word16 CLLong Source # 
Instance details
FromIntegral Word32 CLLong Source # 
Instance details
FromIntegral Word64 CLLong Source # 
Instance details
FromIntegral CShort CLLong Source # 
Instance details
FromIntegral CUShort CLLong Source # 
Instance details
FromIntegral CInt CLLong Source # 
Instance details
FromIntegral CUInt CLLong Source # 
Instance details
FromIntegral CLong CLLong Source # 
Instance details
FromIntegral CULong CLLong Source # 
Instance details
FromIntegral CLLong Double Source # 
Instance details
FromIntegral CLLong Float Source # 
Instance details
FromIntegral CLLong Int Source # 
Instance details
FromIntegral CLLong Int8 Source # 
Instance details
FromIntegral CLLong Int16 Source # 
Instance details
FromIntegral CLLong Int32 Source # 
Instance details
FromIntegral CLLong Int64 Source # 
Instance details
FromIntegral CLLong Word Source # 
Instance details
FromIntegral CLLong Word8 Source # 
Instance details
FromIntegral CLLong Word16 Source # 
Instance details
FromIntegral CLLong Word32 Source # 
Instance details
FromIntegral CLLong Word64 Source # 
Instance details
FromIntegral CLLong CShort Source # 
Instance details
FromIntegral CLLong CUShort Source # 
Instance details
FromIntegral CLLong CInt Source # 
Instance details
FromIntegral CLLong CUInt Source # 
Instance details
FromIntegral CLLong CLong Source # 
Instance details
FromIntegral CLLong CULong Source # 
Instance details
FromIntegral CLLong CLLong Source # 
Instance details
FromIntegral CLLong CULLong Source # 
Instance details
FromIntegral CLLong CFloat Source # 
Instance details
FromIntegral CLLong CDouble Source # 
Instance details
FromIntegral CLLong Half Source # 
Instance details
FromIntegral CULLong CLLong Source # 
Instance details
Bounded (Exp CLLong) # 
Instance details
Enum (Exp CLLong) # 
Instance details
Integral (Exp CLLong) # 
Instance details
Num (Exp CLLong) # 
Instance details
type Difference CLLong 
Instance details
type Unwrapped CLLong 
Instance details
type Plain CLLong Source # 
Instance details

data CULLong #

Haskell type representing the C unsigned long long type.

Instances
Bounded CULLong 
Instance details
Enum CULLong 
Instance details
Eq CULLong 
Instance details

Methods

(==) :: CULLong -> CULLong -> Bool #

(/=) :: CULLong -> CULLong -> Bool #

Integral CULLong 
Instance details
Num CULLong 
Instance details
Ord CULLong 
Instance details
Read CULLong 
Instance details
Real CULLong 
Instance details
Show CULLong 
Instance details
Storable CULLong 
Instance details
Bits CULLong 
Instance details
FiniteBits CULLong 
Instance details
Subtractive CULLong 
Instance details

Associated Types

type Difference CULLong :: * #

NFData CULLong

Since: 1.4.0.0

Instance details

Methods

rnf :: CULLong -> () #

Wrapped CULLong 
Instance details

Associated Types

type Unwrapped CULLong :: * #

IsScalar CULLong Source # 
Instance details

Methods

scalarType :: ScalarType CULLong

IsBounded CULLong Source # 
Instance details

Methods

boundedType :: BoundedType CULLong

IsNum CULLong Source # 
Instance details

Methods

numType :: NumType CULLong

IsIntegral CULLong Source # 
Instance details

Methods

integralType :: IntegralType CULLong

Elt CULLong Source # 
Instance details

Methods

eltType :: CULLong -> TupleType (EltRepr CULLong)

fromElt :: CULLong -> EltRepr CULLong

toElt :: EltRepr CULLong -> CULLong

Eq CULLong Source # 
Instance details
Ord CULLong Source # 
Instance details
FiniteBits CULLong Source # 
Instance details
Bits CULLong Source # 
Instance details
Rewrapped CULLong t 
Instance details
Lift Exp CULLong Source # 
Instance details

Associated Types

type Plain CULLong :: * Source #

ToFloating CULLong Double Source # 
Instance details
ToFloating CULLong Float Source # 
Instance details
ToFloating CULLong CFloat Source # 
Instance details
ToFloating CULLong CDouble Source # 
Instance details
ToFloating CULLong Half Source # 
Instance details
FromIntegral Int CULLong Source # 
Instance details
FromIntegral Int8 CULLong Source # 
Instance details
FromIntegral Int16 CULLong Source # 
Instance details
FromIntegral Int32 CULLong Source # 
Instance details
FromIntegral Int64 CULLong Source # 
Instance details
FromIntegral Word CULLong Source # 
Instance details
FromIntegral Word8 CULLong Source # 
Instance details
FromIntegral Word16 CULLong Source # 
Instance details
FromIntegral Word32 CULLong Source # 
Instance details
FromIntegral Word64 CULLong Source # 
Instance details
FromIntegral CShort CULLong Source # 
Instance details
FromIntegral CUShort CULLong Source # 
Instance details
FromIntegral CInt CULLong Source # 
Instance details
FromIntegral CUInt CULLong Source # 
Instance details
FromIntegral CLong CULLong Source # 
Instance details
FromIntegral CULong CULLong Source # 
Instance details
FromIntegral CLLong CULLong Source # 
Instance details
FromIntegral CULLong Double Source # 
Instance details
FromIntegral CULLong Float Source # 
Instance details
FromIntegral CULLong Int Source # 
Instance details
FromIntegral CULLong Int8 Source # 
Instance details
FromIntegral CULLong Int16 Source # 
Instance details
FromIntegral CULLong Int32 Source # 
Instance details
FromIntegral CULLong Int64 Source # 
Instance details
FromIntegral CULLong Word Source # 
Instance details
FromIntegral CULLong Word8 Source # 
Instance details
FromIntegral CULLong Word16 Source # 
Instance details
FromIntegral CULLong Word32 Source # 
Instance details
FromIntegral CULLong Word64 Source # 
Instance details
FromIntegral CULLong CShort Source # 
Instance details
FromIntegral CULLong CUShort Source # 
Instance details
FromIntegral CULLong CInt Source # 
Instance details
FromIntegral CULLong CUInt Source # 
Instance details
FromIntegral CULLong CLong Source # 
Instance details
FromIntegral CULLong CULong Source # 
Instance details
FromIntegral CULLong CLLong Source # 
Instance details
FromIntegral CULLong CULLong Source # 
Instance details
FromIntegral CULLong CFloat Source # 
Instance details
FromIntegral CULLong CDouble Source # 
Instance details
FromIntegral CULLong Half Source # 
Instance details
Bounded (Exp CULLong) # 
Instance details
Enum (Exp CULLong) # 
Instance details
Integral (Exp CULLong) # 
Instance details
Num (Exp CULLong) # 
Instance details
type Difference CULLong 
Instance details
type Unwrapped CULLong 
Instance details
type Plain CULLong Source # 
Instance details

data CChar #

Haskell type representing the C char type.

Instances
Bounded CChar 
Instance details
Enum CChar 
Instance details
Eq CChar 
Instance details

Methods

(==) :: CChar -> CChar -> Bool #

(/=) :: CChar -> CChar -> Bool #

Integral CChar 
Instance details
Num CChar 
Instance details
Ord CChar 
Instance details

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
Real CChar 
Instance details

Methods

toRational :: CChar -> Rational #

Show CChar 
Instance details

Methods

showsPrec :: Int -> CChar -> ShowS #

show :: CChar -> String #

showList :: [CChar] -> ShowS #

Storable CChar 
Instance details

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
FiniteBits CChar 
Instance details
PrimType CChar 
Instance details

Associated Types

type PrimSize CChar :: Nat #

PrimMemoryComparable CChar 
Instance details
Subtractive CChar 
Instance details

Associated Types

type Difference CChar :: * #

Methods

(-) :: CChar -> CChar -> Difference CChar #

NFData CChar

Since: 1.4.0.0

Instance details

Methods

rnf :: CChar -> () #

Wrapped CChar 
Instance details

Associated Types

type Unwrapped CChar :: * #

IsScalar CChar Source # 
Instance details

Methods

scalarType :: ScalarType CChar

IsBounded CChar Source # 
Instance details

Methods

boundedType :: BoundedType CChar

IsNonNum CChar Source # 
Instance details

Methods

nonNumType :: NonNumType CChar

Elt CChar Source # 
Instance details

Methods

eltType :: CChar -> TupleType (EltRepr CChar)

fromElt :: CChar -> EltRepr CChar

toElt :: EltRepr CChar -> CChar

Eq CChar Source # 
Instance details
Ord CChar Source # 
Instance details
Rewrapped CChar t 
Instance details
Lift Exp CChar Source # 
Instance details

Associated Types

type Plain CChar :: * Source #

Methods

lift :: CChar -> Exp (Plain CChar) Source #

Bounded (Exp CChar) # 
Instance details
type PrimSize CChar 
Instance details
type PrimSize CChar = 1
type Difference CChar 
Instance details
type Unwrapped CChar 
Instance details
type Plain CChar Source # 
Instance details

data CSChar #

Haskell type representing the C signed char type.

Instances
Bounded CSChar 
Instance details
Enum CSChar 
Instance details
Eq CSChar 
Instance details

Methods

(==) :: CSChar -> CSChar -> Bool #

(/=) :: CSChar -> CSChar -> Bool #

Integral CSChar 
Instance details
Num CSChar 
Instance details
Ord CSChar 
Instance details
Read CSChar 
Instance details
Real CSChar 
Instance details
Show CSChar 
Instance details
Storable CSChar 
Instance details
Bits CSChar 
Instance details
FiniteBits CSChar 
Instance details
Subtractive CSChar 
Instance details

Associated Types

type Difference CSChar :: * #

NFData CSChar

Since: 1.4.0.0

Instance details

Methods

rnf :: CSChar -> () #

Wrapped CSChar 
Instance details

Associated Types

type Unwrapped CSChar :: * #

IsScalar CSChar Source # 
Instance details

Methods

scalarType :: ScalarType CSChar

IsBounded CSChar Source # 
Instance details

Methods

boundedType :: BoundedType CSChar

IsNonNum CSChar Source # 
Instance details

Methods

nonNumType :: NonNumType CSChar

Elt CSChar Source # 
Instance details

Methods

eltType :: CSChar -> TupleType (EltRepr CSChar)

fromElt :: CSChar -> EltRepr CSChar

toElt :: EltRepr CSChar -> CSChar

Eq CSChar Source # 
Instance details
Ord CSChar Source # 
Instance details
Rewrapped CSChar t 
Instance details
Lift Exp CSChar Source # 
Instance details

Associated Types

type Plain CSChar :: * Source #

Methods

lift :: CSChar -> Exp (Plain CSChar) Source #

Bounded (Exp CSChar) # 
Instance details
type Difference CSChar 
Instance details
type Unwrapped CSChar 
Instance details
type Plain CSChar Source # 
Instance details

data CUChar #

Haskell type representing the C unsigned char type.

Instances
Bounded CUChar 
Instance details
Enum CUChar 
Instance details
Eq CUChar 
Instance details

Methods

(==) :: CUChar -> CUChar -> Bool #

(/=) :: CUChar -> CUChar -> Bool #

Integral CUChar 
Instance details
Num CUChar 
Instance details
Ord CUChar 
Instance details
Read CUChar 
Instance details
Real CUChar 
Instance details
Show CUChar 
Instance details
Storable CUChar 
Instance details
Bits CUChar 
Instance details
FiniteBits CUChar 
Instance details
PrimType CUChar 
Instance details

Associated Types

type PrimSize CUChar :: Nat #

PrimMemoryComparable CUChar 
Instance details
Subtractive CUChar 
Instance details

Associated Types

type Difference CUChar :: * #

NFData CUChar

Since: 1.4.0.0

Instance details

Methods

rnf :: CUChar -> () #

Wrapped CUChar 
Instance details

Associated Types

type Unwrapped CUChar :: * #

IsScalar CUChar Source # 
Instance details

Methods

scalarType :: ScalarType CUChar

IsBounded CUChar Source # 
Instance details

Methods

boundedType :: BoundedType CUChar

IsNonNum CUChar Source # 
Instance details

Methods

nonNumType :: NonNumType CUChar

Elt CUChar Source # 
Instance details

Methods

eltType :: CUChar -> TupleType (EltRepr CUChar)

fromElt :: CUChar -> EltRepr CUChar

toElt :: EltRepr CUChar -> CUChar

Eq CUChar Source # 
Instance details
Ord CUChar Source # 
Instance details
Rewrapped CUChar t 
Instance details
Lift Exp CUChar Source # 
Instance details

Associated Types

type Plain CUChar :: * Source #

Methods

lift :: CUChar -> Exp (Plain CUChar) Source #

Bounded (Exp CUChar) # 
Instance details
type PrimSize CUChar 
Instance details
type PrimSize CUChar = 1
type Difference CUChar 
Instance details
type Unwrapped CUChar 
Instance details
type Plain CUChar Source # 
Instance details

Avoid using these in your own functions wherever possible.

class Typeable a => IsScalar a Source #

All scalar types

Minimal complete definition

scalarType

Instances
IsScalar Bool Source # 
Instance details

Methods

scalarType :: ScalarType Bool

IsScalar Char Source # 
Instance details

Methods

scalarType :: ScalarType Char

IsScalar Double Source # 
Instance details

Methods

scalarType :: ScalarType Double

IsScalar Float Source # 
Instance details

Methods

scalarType :: ScalarType Float

IsScalar Int Source # 
Instance details

Methods

scalarType :: ScalarType Int

IsScalar Int8 Source # 
Instance details

Methods

scalarType :: ScalarType Int8

IsScalar Int16 Source # 
Instance details

Methods

scalarType :: ScalarType Int16

IsScalar Int32 Source # 
Instance details

Methods

scalarType :: ScalarType Int32

IsScalar Int64 Source # 
Instance details

Methods

scalarType :: ScalarType Int64

IsScalar Word Source # 
Instance details

Methods

scalarType :: ScalarType Word

IsScalar Word8 Source # 
Instance details

Methods

scalarType :: ScalarType Word8

IsScalar Word16 Source # 
Instance details

Methods

scalarType :: ScalarType Word16

IsScalar Word32 Source # 
Instance details

Methods

scalarType :: ScalarType Word32

IsScalar Word64 Source # 
Instance details

Methods

scalarType :: ScalarType Word64

IsScalar CChar Source # 
Instance details

Methods

scalarType :: ScalarType CChar

IsScalar CSChar Source # 
Instance details

Methods

scalarType :: ScalarType CSChar

IsScalar CUChar Source # 
Instance details

Methods

scalarType :: ScalarType CUChar

IsScalar CShort Source # 
Instance details

Methods

scalarType :: ScalarType CShort

IsScalar CUShort Source # 
Instance details

Methods

scalarType :: ScalarType CUShort

IsScalar CInt Source # 
Instance details

Methods

scalarType :: ScalarType CInt

IsScalar CUInt Source # 
Instance details

Methods

scalarType :: ScalarType CUInt

IsScalar CLong Source # 
Instance details

Methods

scalarType :: ScalarType CLong

IsScalar CULong Source # 
Instance details

Methods

scalarType :: ScalarType CULong

IsScalar CLLong Source # 
Instance details

Methods

scalarType :: ScalarType CLLong

IsScalar CULLong Source # 
Instance details

Methods

scalarType :: ScalarType CULLong

IsScalar CFloat Source # 
Instance details

Methods

scalarType :: ScalarType CFloat

IsScalar CDouble Source # 
Instance details

Methods

scalarType :: ScalarType CDouble

IsScalar Half Source # 
Instance details

Methods

scalarType :: ScalarType Half

class (Num a, IsSingle a) => IsNum a Source #

Numeric types

Minimal complete definition

numType

Instances
IsNum Double Source # 
Instance details

Methods

numType :: NumType Double

IsNum Float Source # 
Instance details

Methods

numType :: NumType Float

IsNum Int Source # 
Instance details

Methods

numType :: NumType Int

IsNum Int8 Source # 
Instance details

Methods

numType :: NumType Int8

IsNum Int16 Source # 
Instance details

Methods

numType :: NumType Int16

IsNum Int32 Source # 
Instance details

Methods

numType :: NumType Int32

IsNum Int64 Source # 
Instance details

Methods

numType :: NumType Int64

IsNum Word Source # 
Instance details

Methods

numType :: NumType Word

IsNum Word8 Source # 
Instance details

Methods

numType :: NumType Word8

IsNum Word16 Source # 
Instance details

Methods

numType :: NumType Word16

IsNum Word32 Source # 
Instance details

Methods

numType :: NumType Word32

IsNum Word64 Source # 
Instance details

Methods

numType :: NumType Word64

IsNum CShort Source # 
Instance details

Methods

numType :: NumType CShort

IsNum CUShort Source # 
Instance details

Methods

numType :: NumType CUShort

IsNum CInt Source # 
Instance details

Methods

numType :: NumType CInt

IsNum CUInt Source # 
Instance details

Methods

numType :: NumType CUInt

IsNum CLong Source # 
Instance details

Methods

numType :: NumType CLong

IsNum CULong Source # 
Instance details

Methods

numType :: NumType CULong

IsNum CLLong Source # 
Instance details

Methods

numType :: NumType CLLong

IsNum CULLong Source # 
Instance details

Methods

numType :: NumType CULLong

IsNum CFloat Source # 
Instance details

Methods

numType :: NumType CFloat

IsNum CDouble Source # 
Instance details

Methods

numType :: NumType CDouble

IsNum Half Source # 
Instance details

Methods

numType :: NumType Half

class IsBounded a Source #

Bounded types

Minimal complete definition

boundedType

Instances
IsBounded Bool Source # 
Instance details

Methods

boundedType :: BoundedType Bool

IsBounded Char Source # 
Instance details

Methods

boundedType :: BoundedType Char

IsBounded Int Source # 
Instance details

Methods

boundedType :: BoundedType Int

IsBounded Int8 Source # 
Instance details

Methods

boundedType :: BoundedType Int8

IsBounded Int16 Source # 
Instance details

Methods

boundedType :: BoundedType Int16

IsBounded Int32 Source # 
Instance details

Methods

boundedType :: BoundedType Int32

IsBounded Int64 Source # 
Instance details

Methods

boundedType :: BoundedType Int64

IsBounded Word Source # 
Instance details

Methods

boundedType :: BoundedType Word

IsBounded Word8 Source # 
Instance details

Methods

boundedType :: BoundedType Word8

IsBounded Word16 Source # 
Instance details

Methods

boundedType :: BoundedType Word16

IsBounded Word32 Source # 
Instance details

Methods

boundedType :: BoundedType Word32

IsBounded Word64 Source # 
Instance details

Methods

boundedType :: BoundedType Word64

IsBounded CChar Source # 
Instance details

Methods

boundedType :: BoundedType CChar

IsBounded CSChar Source # 
Instance details

Methods

boundedType :: BoundedType CSChar

IsBounded CUChar Source # 
Instance details

Methods

boundedType :: BoundedType CUChar

IsBounded CShort Source # 
Instance details

Methods

boundedType :: BoundedType CShort

IsBounded CUShort Source # 
Instance details

Methods

boundedType :: BoundedType CUShort

IsBounded CInt Source # 
Instance details

Methods

boundedType :: BoundedType CInt

IsBounded CUInt Source # 
Instance details

Methods

boundedType :: BoundedType CUInt

IsBounded CLong Source # 
Instance details

Methods

boundedType :: BoundedType CLong

IsBounded CULong Source # 
Instance details

Methods

boundedType :: BoundedType CULong

IsBounded CLLong Source # 
Instance details

Methods

boundedType :: BoundedType CLLong

IsBounded CULLong Source # 
Instance details

Methods

boundedType :: BoundedType CULLong

class (IsSingle a, IsNum a, IsBounded a) => IsIntegral a Source #

Integral types

Minimal complete definition

integralType

Instances
IsIntegral Int Source # 
Instance details

Methods

integralType :: IntegralType Int

IsIntegral Int8 Source # 
Instance details

Methods

integralType :: IntegralType Int8

IsIntegral Int16 Source # 
Instance details

Methods

integralType :: IntegralType Int16

IsIntegral Int32 Source # 
Instance details

Methods

integralType :: IntegralType Int32

IsIntegral Int64 Source # 
Instance details

Methods

integralType :: IntegralType Int64

IsIntegral Word Source # 
Instance details

Methods

integralType :: IntegralType Word

IsIntegral Word8 Source # 
Instance details

Methods

integralType :: IntegralType Word8

IsIntegral Word16 Source # 
Instance details

Methods

integralType :: IntegralType Word16

IsIntegral Word32 Source # 
Instance details

Methods

integralType :: IntegralType Word32

IsIntegral Word64 Source # 
Instance details

Methods

integralType :: IntegralType Word64

IsIntegral CShort Source # 
Instance details

Methods

integralType :: IntegralType CShort

IsIntegral CUShort Source # 
Instance details

Methods

integralType :: IntegralType CUShort

IsIntegral CInt Source # 
Instance details

Methods

integralType :: IntegralType CInt

IsIntegral CUInt Source # 
Instance details

Methods

integralType :: IntegralType CUInt

IsIntegral CLong Source # 
Instance details

Methods

integralType :: IntegralType CLong

IsIntegral CULong Source # 
Instance details

Methods

integralType :: IntegralType CULong

IsIntegral CLLong Source # 
Instance details

Methods

integralType :: IntegralType CLLong

IsIntegral CULLong Source # 
Instance details

Methods

integralType :: IntegralType CULLong

class (Floating a, IsSingle a, IsNum a) => IsFloating a Source #

Floating types

Minimal complete definition

floatingType

Instances
IsFloating Double Source # 
Instance details

Methods

floatingType :: FloatingType Double

IsFloating Float Source # 
Instance details

Methods

floatingType :: FloatingType Float

IsFloating CFloat Source # 
Instance details

Methods

floatingType :: FloatingType CFloat

IsFloating CDouble Source # 
Instance details

Methods

floatingType :: FloatingType CDouble

IsFloating Half Source # 
Instance details

Methods

floatingType :: FloatingType Half

class IsNonNum a Source #

Non-numeric types

Minimal complete definition

nonNumType

Instances
IsNonNum Bool Source # 
Instance details

Methods

nonNumType :: NonNumType Bool

IsNonNum Char Source # 
Instance details

Methods

nonNumType :: NonNumType Char

IsNonNum CChar Source # 
Instance details

Methods

nonNumType :: NonNumType CChar

IsNonNum CSChar Source # 
Instance details

Methods

nonNumType :: NonNumType CSChar

IsNonNum CUChar Source # 
Instance details

Methods

nonNumType :: NonNumType CUChar