accelerate-1.0.0.0: An embedded language for accelerated array processing

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

Data.Array.Accelerate

Contents

Description

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

Abstract interface:

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

Stratified language:

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

Optimisations:

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

Code execution:

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

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

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

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

Additional components:
Contact:
Tip:

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

./foo +RTS -A64M -n2M -RTS

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

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

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

Synopsis

The Accelerate Array Language

Embedded array computations

data Acc a #

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

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

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

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

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

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

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

See also Exp, which encapsulates embedded scalar computations.

Fusion:

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

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

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

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

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

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

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

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

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

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

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

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

Instances

IfThenElse Acc # 

Associated Types

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

Methods

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

Unlift Acc (Acc a) # 

Methods

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

Lift Acc (Acc a) # 

Associated Types

type Plain (Acc a) :: * #

Methods

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

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

Methods

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

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

Associated Types

type Plain (a, b) :: * #

Methods

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

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

Associated Types

type Plain (Array sh e) :: * #

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Arrays

data Array sh e #

Dense, regular, multi-dimensional arrays.

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

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

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

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

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

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

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

Instances

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

Associated Types

type Plain (Array sh e) :: * #

Methods

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

Elt e => IsList (Vector e) # 

Associated Types

type Item (Vector e) :: * #

Methods

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

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

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

Show (Vector e) # 

Methods

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

show :: Vector e -> String #

showList :: [Vector e] -> ShowS #

Show (Scalar e) # 

Methods

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

show :: Scalar e -> String #

showList :: [Scalar e] -> ShowS #

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

Methods

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

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

Show (Array sh e) # 

Methods

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

show :: Array sh e -> String #

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

Show (Array DIM2 e) # 

Methods

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

show :: Array DIM2 e -> String #

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

NFData (Array sh e) # 

Methods

rnf :: Array sh e -> () #

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

Methods

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

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

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

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

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

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

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

Minimal complete definition

arrays, flavour, toArr, fromArr

Instances

Arrays () # 

Methods

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

flavour :: () -> ArraysFlavour ()

toArr :: ArrRepr () -> ()

fromArr :: () -> ArrRepr ()

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

type Scalar e = Array DIM0 e #

Scalars arrays hold a single element

type Vector e = Array DIM1 e #

Vectors are one-dimensional arrays

type Segments i = Vector i #

Segment descriptor (vector of segment lengths).

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

Array elements

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

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

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

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

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

Minimal complete definition

eltType, fromElt, toElt

Instances

Elt Bool # 

Methods

eltType :: Bool -> TupleType (EltRepr Bool)

fromElt :: Bool -> EltRepr Bool

toElt :: EltRepr Bool -> Bool

Elt Char # 

Methods

eltType :: Char -> TupleType (EltRepr Char)

fromElt :: Char -> EltRepr Char

toElt :: EltRepr Char -> Char

Elt Double # 

Methods

eltType :: Double -> TupleType (EltRepr Double)

fromElt :: Double -> EltRepr Double

toElt :: EltRepr Double -> Double

Elt Float # 

Methods

eltType :: Float -> TupleType (EltRepr Float)

fromElt :: Float -> EltRepr Float

toElt :: EltRepr Float -> Float

Elt Int # 

Methods

eltType :: Int -> TupleType (EltRepr Int)

fromElt :: Int -> EltRepr Int

toElt :: EltRepr Int -> Int

Elt Int8 # 

Methods

eltType :: Int8 -> TupleType (EltRepr Int8)

fromElt :: Int8 -> EltRepr Int8

toElt :: EltRepr Int8 -> Int8

Elt Int16 # 

Methods

eltType :: Int16 -> TupleType (EltRepr Int16)

fromElt :: Int16 -> EltRepr Int16

toElt :: EltRepr Int16 -> Int16

Elt Int32 # 

Methods

eltType :: Int32 -> TupleType (EltRepr Int32)

fromElt :: Int32 -> EltRepr Int32

toElt :: EltRepr Int32 -> Int32

Elt Int64 # 

Methods

eltType :: Int64 -> TupleType (EltRepr Int64)

fromElt :: Int64 -> EltRepr Int64

toElt :: EltRepr Int64 -> Int64

Elt Word # 

Methods

eltType :: Word -> TupleType (EltRepr Word)

fromElt :: Word -> EltRepr Word

toElt :: EltRepr Word -> Word

Elt Word8 # 

Methods

eltType :: Word8 -> TupleType (EltRepr Word8)

fromElt :: Word8 -> EltRepr Word8

toElt :: EltRepr Word8 -> Word8

Elt Word16 # 

Methods

eltType :: Word16 -> TupleType (EltRepr Word16)

fromElt :: Word16 -> EltRepr Word16

toElt :: EltRepr Word16 -> Word16

Elt Word32 # 

Methods

eltType :: Word32 -> TupleType (EltRepr Word32)

fromElt :: Word32 -> EltRepr Word32

toElt :: EltRepr Word32 -> Word32

Elt Word64 # 

Methods

eltType :: Word64 -> TupleType (EltRepr Word64)

fromElt :: Word64 -> EltRepr Word64

toElt :: EltRepr Word64 -> Word64

Elt () # 

Methods

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

fromElt :: () -> EltRepr ()

toElt :: EltRepr () -> ()

Elt CChar # 

Methods

eltType :: CChar -> TupleType (EltRepr CChar)

fromElt :: CChar -> EltRepr CChar

toElt :: EltRepr CChar -> CChar

Elt CSChar # 

Methods

eltType :: CSChar -> TupleType (EltRepr CSChar)

fromElt :: CSChar -> EltRepr CSChar

toElt :: EltRepr CSChar -> CSChar

Elt CUChar # 

Methods

eltType :: CUChar -> TupleType (EltRepr CUChar)

fromElt :: CUChar -> EltRepr CUChar

toElt :: EltRepr CUChar -> CUChar

Elt CShort # 

Methods

eltType :: CShort -> TupleType (EltRepr CShort)

fromElt :: CShort -> EltRepr CShort

toElt :: EltRepr CShort -> CShort

Elt CUShort # 

Methods

eltType :: CUShort -> TupleType (EltRepr CUShort)

fromElt :: CUShort -> EltRepr CUShort

toElt :: EltRepr CUShort -> CUShort

Elt CInt # 

Methods

eltType :: CInt -> TupleType (EltRepr CInt)

fromElt :: CInt -> EltRepr CInt

toElt :: EltRepr CInt -> CInt

Elt CUInt # 

Methods

eltType :: CUInt -> TupleType (EltRepr CUInt)

fromElt :: CUInt -> EltRepr CUInt

toElt :: EltRepr CUInt -> CUInt

Elt CLong # 

Methods

eltType :: CLong -> TupleType (EltRepr CLong)

fromElt :: CLong -> EltRepr CLong

toElt :: EltRepr CLong -> CLong

Elt CULong # 

Methods

eltType :: CULong -> TupleType (EltRepr CULong)

fromElt :: CULong -> EltRepr CULong

toElt :: EltRepr CULong -> CULong

Elt CLLong # 

Methods

eltType :: CLLong -> TupleType (EltRepr CLLong)

fromElt :: CLLong -> EltRepr CLLong

toElt :: EltRepr CLLong -> CLLong

Elt CULLong # 

Methods

eltType :: CULLong -> TupleType (EltRepr CULLong)

fromElt :: CULLong -> EltRepr CULLong

toElt :: EltRepr CULLong -> CULLong

Elt CFloat # 

Methods

eltType :: CFloat -> TupleType (EltRepr CFloat)

fromElt :: CFloat -> EltRepr CFloat

toElt :: EltRepr CFloat -> CFloat

Elt CDouble # 

Methods

eltType :: CDouble -> TupleType (EltRepr CDouble)

fromElt :: CDouble -> EltRepr CDouble

toElt :: EltRepr CDouble -> CDouble

Elt All # 

Methods

eltType :: All -> TupleType (EltRepr All)

fromElt :: All -> EltRepr All

toElt :: EltRepr All -> All

Elt Z # 

Methods

eltType :: Z -> TupleType (EltRepr Z)

fromElt :: Z -> EltRepr Z

toElt :: EltRepr Z -> Z

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

Methods

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

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

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

Elt (Any Z) # 

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

Array shapes & indices

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

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

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

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

Z :. Int

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

Z :. Int :. Int

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

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

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

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

data Z #

Rank-0 index

Constructors

Z 

Instances

Eq Z # 

Methods

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

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

Show Z # 

Methods

showsPrec :: Int -> Z -> ShowS #

show :: Z -> String #

showList :: [Z] -> ShowS #

Slice Z # 

Associated Types

type SliceShape Z :: * #

type CoSliceShape Z :: * #

type FullShape Z :: * #

Methods

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

Shape Z # 

Methods

rank :: Z -> Int

size :: Z -> Int

empty :: Z

ignore :: Z

intersect :: Z -> Z -> Z

union :: Z -> Z -> Z

toIndex :: Z -> Z -> Int

fromIndex :: Z -> Int -> Z

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

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

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

rangeToShape :: (Z, Z) -> Z

shapeToRange :: Z -> (Z, Z)

shapeToList :: Z -> [Int]

listToShape :: [Int] -> Z

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

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

Elt Z # 

Methods

eltType :: Z -> TupleType (EltRepr Z)

fromElt :: Z -> EltRepr Z

toElt :: EltRepr Z -> Z

Unlift Exp Z # 

Methods

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

Lift Exp Z # 

Associated Types

type Plain Z :: * #

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

Elt e => IsList (Vector e) # 

Associated Types

type Item (Vector e) :: * #

Methods

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

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

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

Show (Vector e) # 

Methods

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

show :: Vector e -> String #

showList :: [Vector e] -> ShowS #

Show (Scalar e) # 

Methods

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

show :: Scalar e -> String #

showList :: [Scalar e] -> ShowS #

Elt (Any Z) # 

Methods

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

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

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

Show (Array DIM2 e) # 

Methods

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

show :: Array DIM2 e -> String #

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

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

data tail :. head infixl 3 #

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

Constructors

tail :. head infixl 3 

Instances

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

Elt e => IsList (Vector e) # 

Associated Types

type Item (Vector e) :: * #

Methods

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

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

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

Show (Vector e) # 

Methods

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

show :: Vector e -> String #

showList :: [Vector e] -> ShowS #

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

Methods

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

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

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

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

Methods

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

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

Show (Array DIM2 e) # 

Methods

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

show :: Array DIM2 e -> String #

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

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

Methods

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

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

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

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

Associated Types

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

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

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

Methods

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

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

Associated Types

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

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

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

Methods

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

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

Methods

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

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

empty :: sh :. Int

ignore :: sh :. Int

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Methods

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

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

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

type DIM0 = Z #

type DIM1 = DIM0 :. Int #

type DIM2 = DIM1 :. Int #

type DIM3 = DIM2 :. Int #

type DIM4 = DIM3 :. Int #

type DIM5 = DIM4 :. Int #

type DIM6 = DIM5 :. Int #

type DIM7 = DIM6 :. Int #

type DIM8 = DIM7 :. Int #

type DIM9 = DIM8 :. Int #

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

Shapes and indices of multi-dimensional arrays

Minimal complete definition

sliceAnyIndex, sliceNoneIndex

Instances

Shape Z # 

Methods

rank :: Z -> Int

size :: Z -> Int

empty :: Z

ignore :: Z

intersect :: Z -> Z -> Z

union :: Z -> Z -> Z

toIndex :: Z -> Z -> Int

fromIndex :: Z -> Int -> Z

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

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

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

rangeToShape :: (Z, Z) -> Z

shapeToRange :: Z -> (Z, Z)

shapeToList :: Z -> [Int]

listToShape :: [Int] -> Z

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

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

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

Methods

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

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

empty :: sh :. Int

ignore :: sh :. Int

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Minimal complete definition

sliceIndex

Associated Types

type SliceShape sl :: * #

type CoSliceShape sl :: * #

type FullShape sl :: * #

Methods

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

Instances

Slice Z # 

Associated Types

type SliceShape Z :: * #

type CoSliceShape Z :: * #

type FullShape Z :: * #

Methods

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

Shape sh => Slice (Any sh) # 

Associated Types

type SliceShape (Any sh) :: * #

type CoSliceShape (Any sh) :: * #

type FullShape (Any sh) :: * #

Methods

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

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

Associated Types

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

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

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

Methods

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

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

Associated Types

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

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

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

Methods

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

data All #

Marker for entire dimensions in slice and replicate descriptors.

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

See slice and replicate for examples.

Constructors

All 

Instances

Eq All # 

Methods

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

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

Show All # 

Methods

showsPrec :: Int -> All -> ShowS #

show :: All -> String #

showList :: [All] -> ShowS #

Elt All # 

Methods

eltType :: All -> TupleType (EltRepr All)

fromElt :: All -> EltRepr All

toElt :: EltRepr All -> All

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

Associated Types

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

Methods

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

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

Associated Types

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

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

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

Methods

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

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

data Any sh #

Marker for arbitrary dimensions in slice and replicate descriptors.

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

See slice and replicate for examples.

Constructors

Any 

Instances

Shape sh => Lift Exp (Any sh) # 

Associated Types

type Plain (Any sh) :: * #

Methods

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

Eq (Any sh) # 

Methods

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

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

Show (Any sh) # 

Methods

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

show :: Any sh -> String #

showList :: [Any sh] -> ShowS #

Shape sh => Slice (Any sh) # 

Associated Types

type SliceShape (Any sh) :: * #

type CoSliceShape (Any sh) :: * #

type FullShape (Any sh) :: * #

Methods

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

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

Methods

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

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

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

Elt (Any Z) # 

Methods

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

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

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

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

Array access

Element indexing

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

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

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

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

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

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

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

Extract the element of a singleton array.

the xs  ==  xs ! Z

Shape information

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

Test whether an array is empty.

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

Get the length of a vector.

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

Extract the shape (extent) of an array.

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

The number of elements in the array

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

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

Construction

Introduction

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

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

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

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

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

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

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

Initialisation

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

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

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

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

Or equivalently:

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

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

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

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

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

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

Create an array where all elements are the same value.

Enumeration

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

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

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

enumFromStepN #

Arguments

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

x: start

-> Exp e

y: step

-> Acc (Array sh e) 

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

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

Concatenation

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

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

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

Composition

Flow control

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

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

See also: ifThenElse.

acond #

Arguments

:: Arrays a 
=> Exp Bool

if-condition

-> Acc a

then-array

-> Acc a

else-array

-> Acc a 

An array-level if-then-else construct.

awhile #

Arguments

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

keep evaluating while this returns True

-> (Acc a -> Acc a)

function to apply

-> Acc a

initial value

-> Acc a 

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

class IfThenElse t where #

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

Minimal complete definition

ifThenElse

Associated Types

type EltT t a :: Constraint #

Methods

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

Instances

IfThenElse Exp # 

Associated Types

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

Methods

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

IfThenElse Acc # 

Associated Types

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

Methods

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

Controlling execution

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

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

Denotationally, we have

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

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

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

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

Here is the synthetic example:

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

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

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

Element-wise operations

Indexing

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

Pair each element with its index

Mapping

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

Apply the given function element-wise to an array.

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

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

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

Zipping

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Unzipping

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Modifying Arrays

Shape manipulation

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

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

precondition: shapeSize sh == shapeSize sh'

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

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

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

Replication

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

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

For example, given the following vector:

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

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

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

...or as columns:

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

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

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

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

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

Of course, Any and All can be used together.

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

Extracting sub-arrays

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

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

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

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

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

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

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

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

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

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

Of course, Any and All can be used together.

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

slit i n = take n . drop i

Permutations

Forward permutation (scatter)

permute #

Arguments

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

combination function

-> Acc (Array sh' a)

array of default values

-> (Exp sh -> Exp sh')

index permutation function

-> Acc (Array sh a)

array of source values to be permuted

-> Acc (Array sh' a) 

Generalised forward permutation operation (array scatter).

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

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

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

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

Regarding array fusion:

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

ignore :: Shape sh => Exp sh #

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

scatter #

Arguments

:: Elt e 
=> Acc (Vector Int)

destination indices to scatter into

-> Acc (Vector e)

default values

-> Acc (Vector e)

source values

-> Acc (Vector e) 

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

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

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

Backward permutation (gather)

backpermute #

Arguments

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

shape of the result array

-> (Exp sh' -> Exp sh)

index permutation function

-> Acc (Array sh a)

source array

-> Acc (Array sh' a) 

Generalised backward permutation operation (array gather).

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

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

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

gather #

Arguments

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

index of source at each index to gather

-> Acc (Vector e)

source values

-> Acc (Array sh e) 

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

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

Specialised permutations

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

Reverse the elements of a vector.

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

Transpose the rows and columns of a matrix.

Filtering

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

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

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

Folding

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Segmented reductions

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

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

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

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

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

Specialised reductions

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

Check if all elements satisfy a predicate

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

Check if any element satisfies the predicate

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

Check if all elements are True

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

Check if any element is True

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

Compute the sum of elements

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

Compute the product of the elements

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

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

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

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

Scans (prefix sums)

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

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

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

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

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

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

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

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

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

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

Right-to-left variant of scanl.

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

Right-to-left variant of scanl1.

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

Right-to-left variant of scanl'.

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

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

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

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

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

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

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

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

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

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

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

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

Segmented scans

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

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

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

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

Segmented version of scanl1 along the innermost dimension.

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

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

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

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

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

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

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

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

Segmented version of prescanl.

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

Segmented version of postscanl.

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

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

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

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

Segmented version of scanr1.

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

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

Segmented version of scanr'.

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

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

Segmented version of prescanr.

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

Segmented version of postscanr.

Stencils

stencil #

Arguments

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

stencil function

-> Boundary a

boundary condition

-> Acc (Array sh a)

source array

-> Acc (Array sh b)

destination array

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

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

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

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

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

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

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

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

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

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

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

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

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

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

stencil2 #

Arguments

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

binary stencil function

-> Boundary a

boundary condition #1

-> Acc (Array sh a)

source array #1

-> Boundary b

boundary condition #2

-> Acc (Array sh b)

source array #2

-> Acc (Array sh c)

destination array

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

Stencil specification

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

Minimal complete definition

stencilPrj

Instances

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

data Boundary a #

Boundary condition specification for stencil operations.

Constructors

Clamp

clamp coordinates to the extent of the array

Mirror

mirror coordinates beyond the array extent

Wrap

wrap coordinates around on each dimension

Constant a

use a constant value for outlying coordinates

Instances

Common stencil patterns

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

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

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

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

The Accelerate Expression Language

Scalar data types

data Exp t #

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

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

Instances

IfThenElse Exp # 

Associated Types

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

Methods

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

Unlift Exp () # 

Methods

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

Unlift Exp Z # 

Methods

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

Lift Exp Bool # 

Associated Types

type Plain Bool :: * #

Methods

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

Lift Exp Char # 

Associated Types

type Plain Char :: * #

Methods

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

Lift Exp Double # 

Associated Types

type Plain Double :: * #

Methods

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

Lift Exp Float # 

Associated Types

type Plain Float :: * #

Methods

lift :: Float -> Exp (Plain Float) #

Lift Exp Int # 

Associated Types

type Plain Int :: * #

Methods

lift :: Int -> Exp (Plain Int) #

Lift Exp Int8 # 

Associated Types

type Plain Int8 :: * #

Methods

lift :: Int8 -> Exp (Plain Int8) #

Lift Exp Int16 # 

Associated Types

type Plain Int16 :: * #

Methods

lift :: Int16 -> Exp (Plain Int16) #

Lift Exp Int32 # 

Associated Types

type Plain Int32 :: * #

Methods

lift :: Int32 -> Exp (Plain Int32) #

Lift Exp Int64 # 

Associated Types

type Plain Int64 :: * #

Methods

lift :: Int64 -> Exp (Plain Int64) #

Lift Exp Word # 

Associated Types

type Plain Word :: * #

Methods

lift :: Word -> Exp (Plain Word) #

Lift Exp Word8 # 

Associated Types

type Plain Word8 :: * #

Methods

lift :: Word8 -> Exp (Plain Word8) #

Lift Exp Word16 # 

Associated Types

type Plain Word16 :: * #

Methods

lift :: Word16 -> Exp (Plain Word16) #

Lift Exp Word32 # 

Associated Types

type Plain Word32 :: * #

Methods

lift :: Word32 -> Exp (Plain Word32) #

Lift Exp Word64 # 

Associated Types

type Plain Word64 :: * #

Methods

lift :: Word64 -> Exp (Plain Word64) #

Lift Exp () # 

Associated Types

type Plain () :: * #

Methods

lift :: () -> Exp (Plain ()) #

Lift Exp CChar # 

Associated Types

type Plain CChar :: * #

Methods

lift :: CChar -> Exp (Plain CChar) #

Lift Exp CSChar # 

Associated Types

type Plain CSChar :: * #

Methods

lift :: CSChar -> Exp (Plain CSChar) #

Lift Exp CUChar # 

Associated Types

type Plain CUChar :: * #

Methods

lift :: CUChar -> Exp (Plain CUChar) #

Lift Exp CShort # 

Associated Types

type Plain CShort :: * #

Methods

lift :: CShort -> Exp (Plain CShort) #

Lift Exp CUShort # 

Associated Types

type Plain CUShort :: * #

Methods

lift :: CUShort -> Exp (Plain CUShort) #

Lift Exp CInt # 

Associated Types

type Plain CInt :: * #

Methods

lift :: CInt -> Exp (Plain CInt) #

Lift Exp CUInt # 

Associated Types

type Plain CUInt :: * #

Methods

lift :: CUInt -> Exp (Plain CUInt) #

Lift Exp CLong # 

Associated Types

type Plain CLong :: * #

Methods

lift :: CLong -> Exp (Plain CLong) #

Lift Exp CULong # 

Associated Types

type Plain CULong :: * #

Methods

lift :: CULong -> Exp (Plain CULong) #

Lift Exp CLLong # 

Associated Types

type Plain CLLong :: * #

Methods

lift :: CLLong -> Exp (Plain CLLong) #

Lift Exp CULLong # 

Associated Types

type Plain CULLong :: * #

Methods

lift :: CULLong -> Exp (Plain CULLong) #

Lift Exp CFloat # 

Associated Types

type Plain CFloat :: * #

Methods

lift :: CFloat -> Exp (Plain CFloat) #

Lift Exp CDouble # 

Associated Types

type Plain CDouble :: * #

Methods

lift :: CDouble -> Exp (Plain CDouble) #

Lift Exp Z # 

Associated Types

type Plain Z :: * #

Methods

lift :: Z -> Exp (Plain Z) #

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e)

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e, Exp e, Exp e)

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)

Unlift Exp (Exp e) # 

Methods

unlift :: Exp (Plain (Exp e)) -> Exp e #

Shape sh => Lift Exp (Any sh) # 

Associated Types

type Plain (Any sh) :: * #

Methods

lift :: Any sh -> Exp (Plain (Any sh)) #

Lift Exp (Exp e) # 

Associated Types

type Plain (Exp e) :: * #

Methods

lift :: Exp e -> Exp (Plain (Exp e)) #

(Elt a, Elt b) => Unlift Exp (Exp a, Exp b) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b)) -> (Exp a, Exp b) #

(Elt e, Slice (Plain ix), Unlift Exp ix) => Unlift Exp ((:.) ix (Exp e)) # 

Methods

unlift :: Exp (Plain (ix :. Exp e)) -> ix :. Exp e #

(Elt e, Slice ix) => Unlift Exp ((:.) (Exp ix) (Exp e)) # 

Methods

unlift :: Exp (Plain (Exp ix :. Exp e)) -> Exp ix :. Exp e #

(Lift Exp a, Lift Exp b, Elt (Plain a), Elt (Plain b)) => Lift Exp (a, b) # 

Associated Types

type Plain (a, b) :: * #

Methods

lift :: (a, b) -> Exp (Plain (a, b)) #

(Elt e, Slice (Plain ix), Lift Exp ix) => Lift Exp ((:.) ix (Exp e)) # 

Associated Types

type Plain ((:.) ix (Exp e)) :: * #

Methods

lift :: (ix :. Exp e) -> Exp (Plain (ix :. Exp e)) #

(Slice (Plain ix), Lift Exp ix) => Lift Exp ((:.) ix All) # 

Associated Types

type Plain ((:.) ix All) :: * #

Methods

lift :: (ix :. All) -> Exp (Plain (ix :. All)) #

(Slice (Plain ix), Lift Exp ix) => Lift Exp ((:.) ix Int) # 

Associated Types

type Plain ((:.) ix Int) :: * #

Methods

lift :: (ix :. Int) -> Exp (Plain (ix :. Int)) #

(Elt a, Elt b, Elt c) => Unlift Exp (Exp a, Exp b, Exp c) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c)) -> (Exp a, Exp b, Exp c) #

(Lift Exp a, Lift Exp b, Lift Exp c, Elt (Plain a), Elt (Plain b), Elt (Plain c)) => Lift Exp (a, b, c) # 

Associated Types

type Plain (a, b, c) :: * #

Methods

lift :: (a, b, c) -> Exp (Plain (a, b, c)) #

(Elt a, Elt b, Elt c, Elt d) => Unlift Exp (Exp a, Exp b, Exp c, Exp d) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d)) -> (Exp a, Exp b, Exp c, Exp d) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d)) => Lift Exp (a, b, c, d) # 

Associated Types

type Plain (a, b, c, d) :: * #

Methods

lift :: (a, b, c, d) -> Exp (Plain (a, b, c, d)) #

(Elt a, Elt b, Elt c, Elt d, Elt e) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e)) -> (Exp a, Exp b, Exp c, Exp d, Exp e) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e)) => Lift Exp (a, b, c, d, e) # 

Associated Types

type Plain (a, b, c, d, e) :: * #

Methods

lift :: (a, b, c, d, e) -> Exp (Plain (a, b, c, d, e)) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f)) => Lift Exp (a, b, c, d, e, f) # 

Associated Types

type Plain (a, b, c, d, e, f) :: * #

Methods

lift :: (a, b, c, d, e, f) -> Exp (Plain (a, b, c, d, e, f)) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g)) => Lift Exp (a, b, c, d, e, f, g) # 

Associated Types

type Plain (a, b, c, d, e, f, g) :: * #

Methods

lift :: (a, b, c, d, e, f, g) -> Exp (Plain (a, b, c, d, e, f, g)) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h)) => Lift Exp (a, b, c, d, e, f, g, h) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h) -> Exp (Plain (a, b, c, d, e, f, g, h)) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i)) => Lift Exp (a, b, c, d, e, f, g, h, i) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i) -> Exp (Plain (a, b, c, d, e, f, g, h, i)) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j)) => Lift Exp (a, b, c, d, e, f, g, h, i, j) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j)) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j, k)) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k, Elt l) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Lift Exp l, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k), Elt (Plain l)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k, l) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j, k, l)) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k, Elt l, Elt m) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Lift Exp l, Lift Exp m, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k), Elt (Plain l), Elt (Plain m)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l, m) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j, k, l, m)) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k, Elt l, Elt m, Elt n) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Lift Exp l, Lift Exp m, Lift Exp n, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k), Elt (Plain l), Elt (Plain m), Elt (Plain n)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n)) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k, Elt l, Elt m, Elt n, Elt o) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n, Exp o) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n, Exp o)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n, Exp o) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Lift Exp l, Lift Exp m, Lift Exp n, Lift Exp o, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k), Elt (Plain l), Elt (Plain m), Elt (Plain n), Elt (Plain o)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)) #

Floating b => Floating (Fold a (Exp b)) # 

Methods

pi :: Fold a (Exp b) #

exp :: Fold a (Exp b) -> Fold a (Exp b) #

log :: Fold a (Exp b) -> Fold a (Exp b) #

sqrt :: Fold a (Exp b) -> Fold a (Exp b) #

(**) :: Fold a (Exp b) -> Fold a (Exp b) -> Fold a (Exp b) #

logBase :: Fold a (Exp b) -> Fold a (Exp b) -> Fold a (Exp b) #

sin :: Fold a (Exp b) -> Fold a (Exp b) #

cos :: Fold a (Exp b) -> Fold a (Exp b) #

tan :: Fold a (Exp b) -> Fold a (Exp b) #

asin :: Fold a (Exp b) -> Fold a (Exp b) #

acos :: Fold a (Exp b) -> Fold a (Exp b) #

atan :: Fold a (Exp b) -> Fold a (Exp b) #

sinh :: Fold a (Exp b) -> Fold a (Exp b) #

cosh :: Fold a (Exp b) -> Fold a (Exp b) #

tanh :: Fold a (Exp b) -> Fold a (Exp b) #

asinh :: Fold a (Exp b) -> Fold a (Exp b) #

acosh :: Fold a (Exp b) -> Fold a (Exp b) #

atanh :: Fold a (Exp b) -> Fold a (Exp b) #

log1p :: Fold a (Exp b) -> Fold a (Exp b) #

expm1 :: Fold a (Exp b) -> Fold a (Exp b) #

log1pexp :: Fold a (Exp b) -> Fold a (Exp b) #

log1mexp :: Fold a (Exp b) -> Fold a (Exp b) #

Fractional b => Fractional (Fold a (Exp b)) # 

Methods

(/) :: Fold a (Exp b) -> Fold a (Exp b) -> Fold a (Exp b) #

recip :: Fold a (Exp b) -> Fold a (Exp b) #

fromRational :: Rational -> Fold a (Exp b) #

Num b => Num (Fold a (Exp b)) # 

Methods

(+) :: Fold a (Exp b) -> Fold a (Exp b) -> Fold a (Exp b) #

(-) :: Fold a (Exp b) -> Fold a (Exp b) -> Fold a (Exp b) #

(*) :: Fold a (Exp b) -> Fold a (Exp b) -> Fold a (Exp b) #

negate :: Fold a (Exp b) -> Fold a (Exp b) #

abs :: Fold a (Exp b) -> Fold a (Exp b) #

signum :: Fold a (Exp b) -> Fold a (Exp b) #

fromInteger :: Integer -> Fold a (Exp b) #

type EltT Exp t # 
type EltT Exp t = Elt t
type Plain (Exp e) # 
type Plain (Exp e) = e
type Plain ((:.) ix (Exp e)) # 
type Plain ((:.) ix (Exp e)) = (:.) (Plain ix) e

Type classes

Basic type classes

class Elt a => Eq a where #

The Eq class defines equality == and inequality /= for scalar Accelerate expressions.

For convenience, we include Elt as a superclass.

Minimal complete definition

(==) | (/=)

Methods

(==) :: Exp a -> Exp a -> Exp Bool infix 4 #

(/=) :: Exp a -> Exp a -> Exp Bool infix 4 #

Instances

Eq Bool # 

Methods

(==) :: Exp Bool -> Exp Bool -> Exp Bool #

(/=) :: Exp Bool -> Exp Bool -> Exp Bool #

Eq Char # 

Methods

(==) :: Exp Char -> Exp Char -> Exp Bool #

(/=) :: Exp Char -> Exp Char -> Exp Bool #

Eq Double # 
Eq Float # 

Methods

(==) :: Exp Float -> Exp Float -> Exp Bool #

(/=) :: Exp Float -> Exp Float -> Exp Bool #

Eq Int # 

Methods

(==) :: Exp Int -> Exp Int -> Exp Bool #

(/=) :: Exp Int -> Exp Int -> Exp Bool #

Eq Int8 # 

Methods

(==) :: Exp Int8 -> Exp Int8 -> Exp Bool #

(/=) :: Exp Int8 -> Exp Int8 -> Exp Bool #

Eq Int16 # 

Methods

(==) :: Exp Int16 -> Exp Int16 -> Exp Bool #

(/=) :: Exp Int16 -> Exp Int16 -> Exp Bool #

Eq Int32 # 

Methods

(==) :: Exp Int32 -> Exp Int32 -> Exp Bool #

(/=) :: Exp Int32 -> Exp Int32 -> Exp Bool #

Eq Int64 # 

Methods

(==) :: Exp Int64 -> Exp Int64 -> Exp Bool #

(/=) :: Exp Int64 -> Exp Int64 -> Exp Bool #

Eq Word # 

Methods

(==) :: Exp Word -> Exp Word -> Exp Bool #

(/=) :: Exp Word -> Exp Word -> Exp Bool #

Eq Word8 # 

Methods

(==) :: Exp Word8 -> Exp Word8 -> Exp Bool #

(/=) :: Exp Word8 -> Exp Word8 -> Exp Bool #

Eq Word16 # 
Eq Word32 # 
Eq Word64 # 
Eq () # 

Methods

(==) :: Exp () -> Exp () -> Exp Bool #

(/=) :: Exp () -> Exp () -> Exp Bool #

Eq CChar # 

Methods

(==) :: Exp CChar -> Exp CChar -> Exp Bool #

(/=) :: Exp CChar -> Exp CChar -> Exp Bool #

Eq CSChar # 
Eq CUChar # 
Eq CShort # 
Eq CUShort # 
Eq CInt # 

Methods

(==) :: Exp CInt -> Exp CInt -> Exp Bool #

(/=) :: Exp CInt -> Exp CInt -> Exp Bool #

Eq CUInt # 

Methods

(==) :: Exp CUInt -> Exp CUInt -> Exp Bool #

(/=) :: Exp CUInt -> Exp CUInt -> Exp Bool #

Eq CLong # 

Methods

(==) :: Exp CLong -> Exp CLong -> Exp Bool #

(/=) :: Exp CLong -> Exp CLong -> Exp Bool #

Eq CULong # 
Eq CLLong # 
Eq CULLong # 
Eq CFloat # 
Eq CDouble # 
(Eq a, Eq b) => Eq (a, b) # 

Methods

(==) :: Exp (a, b) -> Exp (a, b) -> Exp Bool #

(/=) :: Exp (a, b) -> Exp (a, b) -> Exp Bool #

(Eq a, Eq b, Eq c) => Eq (a, b, c) # 

Methods

(==) :: Exp (a, b, c) -> Exp (a, b, c) -> Exp Bool #

(/=) :: Exp (a, b, c) -> Exp (a, b, c) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) # 

Methods

(==) :: Exp (a, b, c, d) -> Exp (a, b, c, d) -> Exp Bool #

(/=) :: Exp (a, b, c, d) -> Exp (a, b, c, d) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e) # 

Methods

(==) :: Exp (a, b, c, d, e) -> Exp (a, b, c, d, e) -> Exp Bool #

(/=) :: Exp (a, b, c, d, e) -> Exp (a, b, c, d, e) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (a, b, c, d, e, f) # 

Methods

(==) :: Exp (a, b, c, d, e, f) -> Exp (a, b, c, d, e, f) -> Exp Bool #

(/=) :: Exp (a, b, c, d, e, f) -> Exp (a, b, c, d, e, f) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (a, b, c, d, e, f, g) # 

Methods

(==) :: Exp (a, b, c, d, e, f, g) -> Exp (a, b, c, d, e, f, g) -> Exp Bool #

(/=) :: Exp (a, b, c, d, e, f, g) -> Exp (a, b, c, d, e, f, g) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h) => Eq (a, b, c, d, e, f, g, h) # 

Methods

(==) :: Exp (a, b, c, d, e, f, g, h) -> Exp (a, b, c, d, e, f, g, h) -> Exp Bool #

(/=) :: Exp (a, b, c, d, e, f, g, h) -> Exp (a, b, c, d, e, f, g, h) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) => Eq (a, b, c, d, e, f, g, h, i) # 

Methods

(==) :: Exp (a, b, c, d, e, f, g, h, i) -> Exp (a, b, c, d, e, f, g, h, i) -> Exp Bool #

(/=) :: Exp (a, b, c, d, e, f, g, h, i) -> Exp (a, b, c, d, e, f, g, h, i) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j) => Eq (a, b, c, d, e, f, g, h, i, j) # 

Methods

(==) :: Exp (a, b, c, d, e, f, g, h, i, j) -> Exp (a, b, c, d, e, f, g, h, i, j) -> Exp Bool #

(/=) :: Exp (a, b, c, d, e, f, g, h, i, j) -> Exp (a, b, c, d, e, f, g, h, i, j) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k) => Eq (a, b, c, d, e, f, g, h, i, j, k) # 

Methods

(==) :: Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp Bool #

(/=) :: Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l) => Eq (a, b, c, d, e, f, g, h, i, j, k, l) # 

Methods

(==) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp Bool #

(/=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m) # 

Methods

(==) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp Bool #

(/=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n) # 

Methods

(==) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp Bool #

(/=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) # 

Methods

(==) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp Bool #

(/=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp Bool #

class Eq a => Ord a where #

The Ord class for totally ordered datatypes

Minimal complete definition

(<=)

Methods

(<) :: Exp a -> Exp a -> Exp Bool infix 4 #

(>) :: Exp a -> Exp a -> Exp Bool infix 4 #

(<=) :: Exp a -> Exp a -> Exp Bool infix 4 #

(>=) :: Exp a -> Exp a -> Exp Bool infix 4 #

min :: Exp a -> Exp a -> Exp a #

max :: Exp a -> Exp a -> Exp a #

Instances

Ord Bool # 

Methods

(<) :: Exp Bool -> Exp Bool -> Exp Bool #

(>) :: Exp Bool -> Exp Bool -> Exp Bool #

(<=) :: Exp Bool -> Exp Bool -> Exp Bool #

(>=) :: Exp Bool -> Exp Bool -> Exp Bool #

min :: Exp Bool -> Exp Bool -> Exp Bool #

max :: Exp Bool -> Exp Bool -> Exp Bool #

Ord Char # 

Methods

(<) :: Exp Char -> Exp Char -> Exp Bool #

(>) :: Exp Char -> Exp Char -> Exp Bool #

(<=) :: Exp Char -> Exp Char -> Exp Bool #

(>=) :: Exp Char -> Exp Char -> Exp Bool #

min :: Exp Char -> Exp Char -> Exp Char #

max :: Exp Char -> Exp Char -> Exp Char #

Ord Double # 
Ord Float # 
Ord Int # 

Methods

(<) :: Exp Int -> Exp Int -> Exp Bool #

(>) :: Exp Int -> Exp Int -> Exp Bool #

(<=) :: Exp Int -> Exp Int -> Exp Bool #

(>=) :: Exp Int -> Exp Int -> Exp Bool #

min :: Exp Int -> Exp Int -> Exp Int #

max :: Exp Int -> Exp Int -> Exp Int #

Ord Int8 # 

Methods

(<) :: Exp Int8 -> Exp Int8 -> Exp Bool #

(>) :: Exp Int8 -> Exp Int8 -> Exp Bool #

(<=) :: Exp Int8 -> Exp Int8 -> Exp Bool #

(>=) :: Exp Int8 -> Exp Int8 -> Exp Bool #

min :: Exp Int8 -> Exp Int8 -> Exp Int8 #

max :: Exp Int8 -> Exp Int8 -> Exp Int8 #

Ord Int16 # 
Ord Int32 # 
Ord Int64 # 
Ord Word # 

Methods

(<) :: Exp Word -> Exp Word -> Exp Bool #

(>) :: Exp Word -> Exp Word -> Exp Bool #

(<=) :: Exp Word -> Exp Word -> Exp Bool #

(>=) :: Exp Word -> Exp Word -> Exp Bool #

min :: Exp Word -> Exp Word -> Exp Word #

max :: Exp Word -> Exp Word -> Exp Word #

Ord Word8 # 
Ord Word16 # 
Ord Word32 # 
Ord Word64 # 
Ord () # 

Methods

(<) :: Exp () -> Exp () -> Exp Bool #

(>) :: Exp () -> Exp () -> Exp Bool #

(<=) :: Exp () -> Exp () -> Exp Bool #

(>=) :: Exp () -> Exp () -> Exp Bool #

min :: Exp () -> Exp () -> Exp () #

max :: Exp () -> Exp () -> Exp () #

Ord CChar # 
Ord CSChar # 
Ord CUChar # 
Ord CShort # 
Ord CUShort # 
Ord CInt # 

Methods

(<) :: Exp CInt -> Exp CInt -> Exp Bool #

(>) :: Exp CInt -> Exp CInt -> Exp Bool #

(<=) :: Exp CInt -> Exp CInt -> Exp Bool #

(>=) :: Exp CInt -> Exp CInt -> Exp Bool #

min :: Exp CInt -> Exp CInt -> Exp CInt #

max :: Exp CInt -> Exp CInt -> Exp CInt #

Ord CUInt # 
Ord CLong # 
Ord CULong # 
Ord CLLong # 
Ord CULLong # 
Ord CFloat # 
Ord CDouble # 
(Ord a, Ord b) => Ord (a, b) # 

Methods

(<) :: Exp (a, b) -> Exp (a, b) -> Exp Bool #

(>) :: Exp (a, b) -> Exp (a, b) -> Exp Bool #

(<=) :: Exp (a, b) -> Exp (a, b) -> Exp Bool #

(>=) :: Exp (a, b) -> Exp (a, b) -> Exp Bool #

min :: Exp (a, b) -> Exp (a, b) -> Exp (a, b) #

max :: Exp (a, b) -> Exp (a, b) -> Exp (a, b) #

(Ord a, Ord b, Ord c) => Ord (a, b, c) # 

Methods

(<) :: Exp (a, b, c) -> Exp (a, b, c) -> Exp Bool #

(>) :: Exp (a, b, c) -> Exp (a, b, c) -> Exp Bool #

(<=) :: Exp (a, b, c) -> Exp (a, b, c) -> Exp Bool #

(>=) :: Exp (a, b, c) -> Exp (a, b, c) -> Exp Bool #

min :: Exp (a, b, c) -> Exp (a, b, c) -> Exp (a, b, c) #

max :: Exp (a, b, c) -> Exp (a, b, c) -> Exp (a, b, c) #

(Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) # 

Methods

(<) :: Exp (a, b, c, d) -> Exp (a, b, c, d) -> Exp Bool #

(>) :: Exp (a, b, c, d) -> Exp (a, b, c, d) -> Exp Bool #

(<=) :: Exp (a, b, c, d) -> Exp (a, b, c, d) -> Exp Bool #

(>=) :: Exp (a, b, c, d) -> Exp (a, b, c, d) -> Exp Bool #

min :: Exp (a, b, c, d) -> Exp (a, b, c, d) -> Exp (a, b, c, d) #

max :: Exp (a, b, c, d) -> Exp (a, b, c, d) -> Exp (a, b, c, d) #

(Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) # 

Methods

(<) :: Exp (a, b, c, d, e) -> Exp (a, b, c, d, e) -> Exp Bool #

(>) :: Exp (a, b, c, d, e) -> Exp (a, b, c, d, e) -> Exp Bool #

(<=) :: Exp (a, b, c, d, e) -> Exp (a, b, c, d, e) -> Exp Bool #

(>=) :: Exp (a, b, c, d, e) -> Exp (a, b, c, d, e) -> Exp Bool #

min :: Exp (a, b, c, d, e) -> Exp (a, b, c, d, e) -> Exp (a, b, c, d, e) #

max :: Exp (a, b, c, d, e) -> Exp (a, b, c, d, e) -> Exp (a, b, c, d, e) #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f) => Ord (a, b, c, d, e, f) # 

Methods

(<) :: Exp (a, b, c, d, e, f) -> Exp (a, b, c, d, e, f) -> Exp Bool #

(>) :: Exp (a, b, c, d, e, f) -> Exp (a, b, c, d, e, f) -> Exp Bool #

(<=) :: Exp (a, b, c, d, e, f) -> Exp (a, b, c, d, e, f) -> Exp Bool #

(>=) :: Exp (a, b, c, d, e, f) -> Exp (a, b, c, d, e, f) -> Exp Bool #

min :: Exp (a, b, c, d, e, f) -> Exp (a, b, c, d, e, f) -> Exp (a, b, c, d, e, f) #

max :: Exp (a, b, c, d, e, f) -> Exp (a, b, c, d, e, f) -> Exp (a, b, c, d, e, f) #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g) => Ord (a, b, c, d, e, f, g) # 

Methods

(<) :: Exp (a, b, c, d, e, f, g) -> Exp (a, b, c, d, e, f, g) -> Exp Bool #

(>) :: Exp (a, b, c, d, e, f, g) -> Exp (a, b, c, d, e, f, g) -> Exp Bool #

(<=) :: Exp (a, b, c, d, e, f, g) -> Exp (a, b, c, d, e, f, g) -> Exp Bool #

(>=) :: Exp (a, b, c, d, e, f, g) -> Exp (a, b, c, d, e, f, g) -> Exp Bool #

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) #

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) #

(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) # 

Methods

(<) :: Exp (a, b, c, d, e, f, g, h) -> Exp (a, b, c, d, e, f, g, h) -> Exp Bool #

(>) :: Exp (a, b, c, d, e, f, g, h) -> Exp (a, b, c, d, e, f, g, h) -> Exp Bool #

(<=) :: Exp (a, b, c, d, e, f, g, h) -> Exp (a, b, c, d, e, f, g, h) -> Exp Bool #

(>=) :: Exp (a, b, c, d, e, f, g, h) -> Exp (a, b, c, d, e, f, g, h) -> Exp Bool #

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) #

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) #

(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) # 

Methods

(<) :: Exp (a, b, c, d, e, f, g, h, i) -> Exp (a, b, c, d, e, f, g, h, i) -> Exp Bool #

(>) :: Exp (a, b, c, d, e, f, g, h, i) -> Exp (a, b, c, d, e, f, g, h, i) -> Exp Bool #

(<=) :: Exp (a, b, c, d, e, f, g, h, i) -> Exp (a, b, c, d, e, f, g, h, i) -> Exp Bool #

(>=) :: Exp (a, b, c, d, e, f, g, h, i) -> Exp (a, b, c, d, e, f, g, h, i) -> Exp Bool #

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) #

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) #

(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) # 

Methods

(<) :: Exp (a, b, c, d, e, f, g, h, i, j) -> Exp (a, b, c, d, e, f, g, h, i, j) -> Exp Bool #

(>) :: Exp (a, b, c, d, e, f, g, h, i, j) -> Exp (a, b, c, d, e, f, g, h, i, j) -> Exp Bool #

(<=) :: Exp (a, b, c, d, e, f, g, h, i, j) -> Exp (a, b, c, d, e, f, g, h, i, j) -> Exp Bool #

(>=) :: Exp (a, b, c, d, e, f, g, h, i, j) -> Exp (a, b, c, d, e, f, g, h, i, j) -> Exp Bool #

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) #

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) #

(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) # 

Methods

(<) :: Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp Bool #

(>) :: Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp Bool #

(<=) :: Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp Bool #

(>=) :: Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp (a, b, c, d, e, f, g, h, i, j, k) -> Exp Bool #

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) #

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) #

(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) # 

Methods

(<) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp Bool #

(>) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp Bool #

(<=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp Bool #

(>=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp Bool #

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) #

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) #

(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) # 

Methods

(<) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp Bool #

(>) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp Bool #

(<=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp Bool #

(>=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp Bool #

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) #

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) #

(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) # 

Methods

(<) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp Bool #

(>) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp Bool #

(<=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp Bool #

(>=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp Bool #

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) #

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) #

(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) # 

Methods

(<) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp Bool #

(>) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp Bool #

(<=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp Bool #

(>=) :: Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp Bool #

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) #

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) #

type Bounded a = (Elt a, Bounded (Exp a)) #

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)) #

Basic numeric class

(+) :: Num a => a -> a -> a #

(-) :: Num a => a -> a -> a #

(*) :: Num a => a -> a -> a #

negate :: Num a => a -> a #

Unary negation.

abs :: Num a => a -> a #

Absolute value.

signum :: Num a => a -> a #

Sign of a number. The functions abs and signum should satisfy the law:

abs x * signum x == x

For real numbers, the signum is either -1 (negative), 0 (zero) or 1 (positive).

fromInteger :: Num a => Integer -> a #

Conversion from an Integer. An integer literal represents the application of the function fromInteger to the appropriate value of type Integer, so such literals have type (Num a) => a.

type Integral a = (Enum a, Real a, Integral (Exp a)) #

Integral numbers, supporting integral division

quot :: Integral a => a -> a -> a #

integer division truncated toward zero

rem :: Integral a => a -> a -> a #

integer remainder, satisfying

(x `quot` y)*y + (x `rem` y) == x

div :: Integral a => a -> a -> a #

integer division truncated toward negative infinity

mod :: Integral a => a -> a -> a #

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)) #

Fractional numbers, supporting real division

(/) :: Fractional a => a -> a -> a #

fractional division

recip :: Fractional a => a -> a #

reciprocal fraction

fromRational :: Fractional a => Rational -> a #

Conversion from a Rational (that is Ratio Integer). A floating literal stands for an application of fromRational to a value of type Rational, so such literals have type (Fractional a) => a.

type Floating a = (Fractional a, Floating (Exp a)) #

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 #

logBase :: Floating a => a -> a -> a #

class (Real a, Fractional a) => RealFrac a where #

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) #

truncate :: (Elt b, IsIntegral b) => Exp a -> Exp b #

truncate x returns the integer nearest x between zero and x

round :: (Elt b, IsIntegral b) => Exp a -> Exp b #

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 #

ceiling x returns the least integer not less than x

floor :: (Elt b, IsIntegral b) => Exp a -> Exp b #

floor x returns the greatest integer not greater than x

Instances

RealFrac Double # 

Methods

properFraction :: (Num b, ToFloating b Double, IsIntegral b) => Exp Double -> (Exp b, Exp Double) #

truncate :: (Elt b, IsIntegral b) => Exp Double -> Exp b #

round :: (Elt b, IsIntegral b) => Exp Double -> Exp b #

ceiling :: (Elt b, IsIntegral b) => Exp Double -> Exp b #

floor :: (Elt b, IsIntegral b) => Exp Double -> Exp b #

RealFrac Float # 

Methods

properFraction :: (Num b, ToFloating b Float, IsIntegral b) => Exp Float -> (Exp b, Exp Float) #

truncate :: (Elt b, IsIntegral b) => Exp Float -> Exp b #

round :: (Elt b, IsIntegral b) => Exp Float -> Exp b #

ceiling :: (Elt b, IsIntegral b) => Exp Float -> Exp b #

floor :: (Elt b, IsIntegral b) => Exp Float -> Exp b #

RealFrac CFloat # 

Methods

properFraction :: (Num b, ToFloating b CFloat, IsIntegral b) => Exp CFloat -> (Exp b, Exp CFloat) #

truncate :: (Elt b, IsIntegral b) => Exp CFloat -> Exp b #

round :: (Elt b, IsIntegral b) => Exp CFloat -> Exp b #

ceiling :: (Elt b, IsIntegral b) => Exp CFloat -> Exp b #

floor :: (Elt b, IsIntegral b) => Exp CFloat -> Exp b #

RealFrac CDouble # 

Methods

properFraction :: (Num b, ToFloating b CDouble, IsIntegral b) => Exp CDouble -> (Exp b, Exp CDouble) #

truncate :: (Elt b, IsIntegral b) => Exp CDouble -> Exp b #

round :: (Elt b, IsIntegral b) => Exp CDouble -> Exp b #

ceiling :: (Elt b, IsIntegral b) => Exp CDouble -> Exp b #

floor :: (Elt b, IsIntegral b) => Exp CDouble -> Exp b #

div' :: (RealFrac a, Elt b, IsIntegral b) => Exp a -> Exp a -> Exp b #

Generalisation of div to any instance of RealFrac

mod' :: (Floating a, RealFrac a, ToFloating Int a) => Exp a -> Exp a -> Exp a #

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) #

Generalisation of divMod to any instance of RealFrac

class (RealFrac a, Floating a) => RealFloat a where #

Efficient, machine-independent access to the components of a floating-point number

Minimal complete definition

isNaN, atan2

Methods

floatRadix :: Exp a -> Exp Int64 #

The radix of the representation (often 2) (constant)

floatRadix :: RealFloat a => Exp a -> Exp Int64 #

The radix of the representation (often 2) (constant)

floatDigits :: Exp a -> Exp Int #

The number of digits of floatRadix in the significand (constant)

floatDigits :: RealFloat a => Exp a -> Exp Int #

The number of digits of floatRadix in the significand (constant)

floatRange :: Exp a -> (Exp Int, Exp Int) #

The lowest and highest values the exponent may assume (constant)

floatRange :: RealFloat a => Exp a -> (Exp Int, Exp Int) #

The lowest and highest values the exponent may assume (constant)

decodeFloat :: Exp a -> (Exp Int64, Exp Int) #

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 #

Inverse of decodeFloat

exponent :: Exp a -> Exp Int #

Corresponds to the second component of decodeFloat

significand :: Exp a -> Exp a #

Corresponds to the first component of decodeFloat

scaleFloat :: Exp Int -> Exp a -> Exp a #

Multiply a floating point number by an integer power of the radix

isNaN :: Exp a -> Exp Bool #

True if the argument is an IEEE "not-a-number" (NaN) value

isInfinite :: Exp a -> Exp Bool #

True if the argument is an IEEE infinity or negative-infinity

isDenormalized :: Exp a -> Exp Bool #

True if the argument is too small to be represented in normalized format

isNegativeZero :: Exp a -> Exp Bool #

True if the argument is an IEEE negative zero

isIEEE :: Exp a -> Exp Bool #

True if the argument is an IEEE floating point number

isIEEE :: RealFloat a => Exp a -> Exp Bool #

True if the argument is an IEEE floating point number

atan2 :: Exp a -> Exp a -> Exp a #

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 # 
RealFloat Float # 
RealFloat CFloat # 
RealFloat CDouble # 

Numeric conversion classes

class FromIntegral a b where #

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 #

General coercion from integral types

Instances

FromIntegral Int Double # 
FromIntegral Int Float # 

Methods

fromIntegral :: Exp Int -> Exp Float #

FromIntegral Int Int # 

Methods

fromIntegral :: Exp Int -> Exp Int #

FromIntegral Int Int8 # 

Methods

fromIntegral :: Exp Int -> Exp Int8 #

FromIntegral Int Int16 # 

Methods

fromIntegral :: Exp Int -> Exp Int16 #

FromIntegral Int Int32 # 

Methods

fromIntegral :: Exp Int -> Exp Int32 #

FromIntegral Int Int64 # 

Methods

fromIntegral :: Exp Int -> Exp Int64 #

FromIntegral Int Word # 

Methods

fromIntegral :: Exp Int -> Exp Word #

FromIntegral Int Word8 # 

Methods

fromIntegral :: Exp Int -> Exp Word8 #

FromIntegral Int Word16 # 
FromIntegral Int Word32 # 
FromIntegral Int Word64 # 
FromIntegral Int CShort # 
FromIntegral Int CUShort # 
FromIntegral Int CInt # 

Methods

fromIntegral :: Exp Int -> Exp CInt #

FromIntegral Int CUInt # 

Methods

fromIntegral :: Exp Int -> Exp CUInt #

FromIntegral Int CLong # 

Methods

fromIntegral :: Exp Int -> Exp CLong #

FromIntegral Int CULong # 
FromIntegral Int CLLong # 
FromIntegral Int CULLong # 
FromIntegral Int CFloat # 
FromIntegral Int CDouble # 
FromIntegral Int8 Double # 
FromIntegral Int8 Float # 
FromIntegral Int8 Int # 

Methods

fromIntegral :: Exp Int8 -> Exp Int #

FromIntegral Int8 Int8 # 

Methods

fromIntegral :: Exp Int8 -> Exp Int8 #

FromIntegral Int8 Int16 # 
FromIntegral Int8 Int32 # 
FromIntegral Int8 Int64 # 
FromIntegral Int8 Word # 

Methods

fromIntegral :: Exp Int8 -> Exp Word #

FromIntegral Int8 Word8 # 
FromIntegral Int8 Word16 # 
FromIntegral Int8 Word32 # 
FromIntegral Int8 Word64 # 
FromIntegral Int8 CShort # 
FromIntegral Int8 CUShort # 
FromIntegral Int8 CInt # 

Methods

fromIntegral :: Exp Int8 -> Exp CInt #

FromIntegral Int8 CUInt # 
FromIntegral Int8 CLong # 
FromIntegral Int8 CULong # 
FromIntegral Int8 CLLong # 
FromIntegral Int8 CULLong # 
FromIntegral Int8 CFloat # 
FromIntegral Int8 CDouble # 
FromIntegral Int16 Double # 
FromIntegral Int16 Float # 
FromIntegral Int16 Int # 

Methods

fromIntegral :: Exp Int16 -> Exp Int #

FromIntegral Int16 Int8 # 
FromIntegral Int16 Int16 # 
FromIntegral Int16 Int32 # 
FromIntegral Int16 Int64 # 
FromIntegral Int16 Word # 
FromIntegral Int16 Word8 # 
FromIntegral Int16 Word16 # 
FromIntegral Int16 Word32 # 
FromIntegral Int16 Word64 # 
FromIntegral Int16 CShort # 
FromIntegral Int16 CUShort # 
FromIntegral Int16 CInt # 
FromIntegral Int16 CUInt # 
FromIntegral Int16 CLong # 
FromIntegral Int16 CULong # 
FromIntegral Int16 CLLong # 
FromIntegral Int16 CULLong # 
FromIntegral Int16 CFloat # 
FromIntegral Int16 CDouble # 
FromIntegral Int32 Double # 
FromIntegral Int32 Float # 
FromIntegral Int32 Int # 

Methods

fromIntegral :: Exp Int32 -> Exp Int #

FromIntegral Int32 Int8 # 
FromIntegral Int32 Int16 # 
FromIntegral Int32 Int32 # 
FromIntegral Int32 Int64 # 
FromIntegral Int32 Word # 
FromIntegral Int32 Word8 # 
FromIntegral Int32 Word16 # 
FromIntegral Int32 Word32 # 
FromIntegral Int32 Word64 # 
FromIntegral Int32 CShort # 
FromIntegral Int32 CUShort # 
FromIntegral Int32 CInt # 
FromIntegral Int32 CUInt # 
FromIntegral Int32 CLong # 
FromIntegral Int32 CULong # 
FromIntegral Int32 CLLong # 
FromIntegral Int32 CULLong # 
FromIntegral Int32 CFloat # 
FromIntegral Int32 CDouble # 
FromIntegral Int64 Double # 
FromIntegral Int64 Float # 
FromIntegral Int64 Int # 

Methods

fromIntegral :: Exp Int64 -> Exp Int #

FromIntegral Int64 Int8 # 
FromIntegral Int64 Int16 # 
FromIntegral Int64 Int32 # 
FromIntegral Int64 Int64 # 
FromIntegral Int64 Word # 
FromIntegral Int64 Word8 # 
FromIntegral Int64 Word16 # 
FromIntegral Int64 Word32 # 
FromIntegral Int64 Word64 # 
FromIntegral Int64 CShort # 
FromIntegral Int64 CUShort # 
FromIntegral Int64 CInt # 
FromIntegral Int64 CUInt # 
FromIntegral Int64 CLong # 
FromIntegral Int64 CULong # 
FromIntegral Int64 CLLong # 
FromIntegral Int64 CULLong # 
FromIntegral Int64 CFloat # 
FromIntegral Int64 CDouble # 
FromIntegral Word Double # 
FromIntegral Word Float # 
FromIntegral Word Int # 

Methods

fromIntegral :: Exp Word -> Exp Int #

FromIntegral Word Int8 # 

Methods

fromIntegral :: Exp Word -> Exp Int8 #

FromIntegral Word Int16 # 
FromIntegral Word Int32 # 
FromIntegral Word Int64 # 
FromIntegral Word Word # 

Methods

fromIntegral :: Exp Word -> Exp Word #

FromIntegral Word Word8 # 
FromIntegral Word Word16 # 
FromIntegral Word Word32 # 
FromIntegral Word Word64 # 
FromIntegral Word CShort # 
FromIntegral Word CUShort # 
FromIntegral Word CInt # 

Methods

fromIntegral :: Exp Word -> Exp CInt #

FromIntegral Word CUInt # 
FromIntegral Word CLong # 
FromIntegral Word CULong # 
FromIntegral Word CLLong # 
FromIntegral Word CULLong # 
FromIntegral Word CFloat # 
FromIntegral Word CDouble # 
FromIntegral Word8 Double # 
FromIntegral Word8 Float # 
FromIntegral Word8 Int # 

Methods

fromIntegral :: Exp Word8 -> Exp Int #

FromIntegral Word8 Int8 # 
FromIntegral Word8 Int16 # 
FromIntegral Word8 Int32 # 
FromIntegral Word8 Int64 # 
FromIntegral Word8 Word # 
FromIntegral Word8 Word8 # 
FromIntegral Word8 Word16 # 
FromIntegral Word8 Word32 # 
FromIntegral Word8 Word64 # 
FromIntegral Word8 CShort # 
FromIntegral Word8 CUShort # 
FromIntegral Word8 CInt # 
FromIntegral Word8 CUInt # 
FromIntegral Word8 CLong # 
FromIntegral Word8 CULong # 
FromIntegral Word8 CLLong # 
FromIntegral Word8 CULLong # 
FromIntegral Word8 CFloat # 
FromIntegral Word8 CDouble # 
FromIntegral Word16 Double # 
FromIntegral Word16 Float # 
FromIntegral Word16 Int # 
FromIntegral Word16 Int8 # 
FromIntegral Word16 Int16 # 
FromIntegral Word16 Int32 # 
FromIntegral Word16 Int64 # 
FromIntegral Word16 Word # 
FromIntegral Word16 Word8 # 
FromIntegral Word16 Word16 # 
FromIntegral Word16 Word32 # 
FromIntegral Word16 Word64 # 
FromIntegral Word16 CShort # 
FromIntegral Word16 CUShort # 
FromIntegral Word16 CInt # 
FromIntegral Word16 CUInt # 
FromIntegral Word16 CLong # 
FromIntegral Word16 CULong # 
FromIntegral Word16 CLLong # 
FromIntegral Word16 CULLong # 
FromIntegral Word16 CFloat # 
FromIntegral Word16 CDouble # 
FromIntegral Word32 Double # 
FromIntegral Word32 Float # 
FromIntegral Word32 Int # 
FromIntegral Word32 Int8 # 
FromIntegral Word32 Int16 # 
FromIntegral Word32 Int32 # 
FromIntegral Word32 Int64 # 
FromIntegral Word32 Word # 
FromIntegral Word32 Word8 # 
FromIntegral Word32 Word16 # 
FromIntegral Word32 Word32 # 
FromIntegral Word32 Word64 # 
FromIntegral Word32 CShort # 
FromIntegral Word32 CUShort # 
FromIntegral Word32 CInt # 
FromIntegral Word32 CUInt # 
FromIntegral Word32 CLong # 
FromIntegral Word32 CULong # 
FromIntegral Word32 CLLong # 
FromIntegral Word32 CULLong # 
FromIntegral Word32 CFloat # 
FromIntegral Word32 CDouble # 
FromIntegral Word64 Double # 
FromIntegral Word64 Float # 
FromIntegral Word64 Int # 
FromIntegral Word64 Int8 # 
FromIntegral Word64 Int16 # 
FromIntegral Word64 Int32 # 
FromIntegral Word64 Int64 # 
FromIntegral Word64 Word # 
FromIntegral Word64 Word8 # 
FromIntegral Word64 Word16 # 
FromIntegral Word64 Word32 # 
FromIntegral Word64 Word64 # 
FromIntegral Word64 CShort # 
FromIntegral Word64 CUShort # 
FromIntegral Word64 CInt # 
FromIntegral Word64 CUInt # 
FromIntegral Word64 CLong # 
FromIntegral Word64 CULong # 
FromIntegral Word64 CLLong # 
FromIntegral Word64 CULLong # 
FromIntegral Word64 CFloat # 
FromIntegral Word64 CDouble # 
FromIntegral CShort Double # 
FromIntegral CShort Float # 
FromIntegral CShort Int # 
FromIntegral CShort Int8 # 
FromIntegral CShort Int16 # 
FromIntegral CShort Int32 # 
FromIntegral CShort Int64 # 
FromIntegral CShort Word # 
FromIntegral CShort Word8 # 
FromIntegral CShort Word16 # 
FromIntegral CShort Word32 # 
FromIntegral CShort Word64 # 
FromIntegral CShort CShort # 
FromIntegral CShort CUShort # 
FromIntegral CShort CInt # 
FromIntegral CShort CUInt # 
FromIntegral CShort CLong # 
FromIntegral CShort CULong # 
FromIntegral CShort CLLong # 
FromIntegral CShort CULLong # 
FromIntegral CShort CFloat # 
FromIntegral CShort CDouble # 
FromIntegral CUShort Double # 
FromIntegral CUShort Float # 
FromIntegral CUShort Int # 
FromIntegral CUShort Int8 # 
FromIntegral CUShort Int16 # 
FromIntegral CUShort Int32 # 
FromIntegral CUShort Int64 # 
FromIntegral CUShort Word # 
FromIntegral CUShort Word8 # 
FromIntegral CUShort Word16 # 
FromIntegral CUShort Word32 # 
FromIntegral CUShort Word64 # 
FromIntegral CUShort CShort # 
FromIntegral CUShort CUShort # 
FromIntegral CUShort CInt # 
FromIntegral CUShort CUInt # 
FromIntegral CUShort CLong # 
FromIntegral CUShort CULong # 
FromIntegral CUShort CLLong # 
FromIntegral CUShort CULLong # 
FromIntegral CUShort CFloat # 
FromIntegral CUShort CDouble # 
FromIntegral CInt Double # 
FromIntegral CInt Float # 
FromIntegral CInt Int # 

Methods

fromIntegral :: Exp CInt -> Exp Int #

FromIntegral CInt Int8 # 

Methods

fromIntegral :: Exp CInt -> Exp Int8 #

FromIntegral CInt Int16 # 
FromIntegral CInt Int32 # 
FromIntegral CInt Int64 # 
FromIntegral CInt Word # 

Methods

fromIntegral :: Exp CInt -> Exp Word #

FromIntegral CInt Word8 # 
FromIntegral CInt Word16 # 
FromIntegral CInt Word32 # 
FromIntegral CInt Word64 # 
FromIntegral CInt CShort # 
FromIntegral CInt CUShort # 
FromIntegral CInt CInt # 

Methods

fromIntegral :: Exp CInt -> Exp CInt #

FromIntegral CInt CUInt # 
FromIntegral CInt CLong # 
FromIntegral CInt CULong # 
FromIntegral CInt CLLong # 
FromIntegral CInt CULLong # 
FromIntegral CInt CFloat # 
FromIntegral CInt CDouble # 
FromIntegral CUInt Double # 
FromIntegral CUInt Float # 
FromIntegral CUInt Int # 

Methods

fromIntegral :: Exp CUInt -> Exp Int #

FromIntegral CUInt Int8 # 
FromIntegral CUInt Int16 # 
FromIntegral CUInt Int32 # 
FromIntegral CUInt Int64 # 
FromIntegral CUInt Word # 
FromIntegral CUInt Word8 # 
FromIntegral CUInt Word16 # 
FromIntegral CUInt Word32 # 
FromIntegral CUInt Word64 # 
FromIntegral CUInt CShort # 
FromIntegral CUInt CUShort # 
FromIntegral CUInt CInt # 
FromIntegral CUInt CUInt # 
FromIntegral CUInt CLong # 
FromIntegral CUInt CULong # 
FromIntegral CUInt CLLong # 
FromIntegral CUInt CULLong # 
FromIntegral CUInt CFloat # 
FromIntegral CUInt CDouble # 
FromIntegral CLong Double # 
FromIntegral CLong Float # 
FromIntegral CLong Int # 

Methods

fromIntegral :: Exp CLong -> Exp Int #

FromIntegral CLong Int8 # 
FromIntegral CLong Int16 # 
FromIntegral CLong Int32 # 
FromIntegral CLong Int64 # 
FromIntegral CLong Word # 
FromIntegral CLong Word8 # 
FromIntegral CLong Word16 # 
FromIntegral CLong Word32 # 
FromIntegral CLong Word64 # 
FromIntegral CLong CShort # 
FromIntegral CLong CUShort # 
FromIntegral CLong CInt # 
FromIntegral CLong CUInt # 
FromIntegral CLong CLong # 
FromIntegral CLong CULong # 
FromIntegral CLong CLLong # 
FromIntegral CLong CULLong # 
FromIntegral CLong CFloat # 
FromIntegral CLong CDouble # 
FromIntegral CULong Double # 
FromIntegral CULong Float # 
FromIntegral CULong Int # 
FromIntegral CULong Int8 # 
FromIntegral CULong Int16 # 
FromIntegral CULong Int32 # 
FromIntegral CULong Int64 # 
FromIntegral CULong Word # 
FromIntegral CULong Word8 # 
FromIntegral CULong Word16 # 
FromIntegral CULong Word32 # 
FromIntegral CULong Word64 # 
FromIntegral CULong CShort # 
FromIntegral CULong CUShort # 
FromIntegral CULong CInt # 
FromIntegral CULong CUInt # 
FromIntegral CULong CLong # 
FromIntegral CULong CULong # 
FromIntegral CULong CLLong # 
FromIntegral CULong CULLong # 
FromIntegral CULong CFloat # 
FromIntegral CULong CDouble # 
FromIntegral CLLong Double # 
FromIntegral CLLong Float # 
FromIntegral CLLong Int # 
FromIntegral CLLong Int8 # 
FromIntegral CLLong Int16 # 
FromIntegral CLLong Int32 # 
FromIntegral CLLong Int64 # 
FromIntegral CLLong Word # 
FromIntegral CLLong Word8 # 
FromIntegral CLLong Word16 # 
FromIntegral CLLong Word32 # 
FromIntegral CLLong Word64 # 
FromIntegral CLLong CShort # 
FromIntegral CLLong CUShort # 
FromIntegral CLLong CInt # 
FromIntegral CLLong CUInt # 
FromIntegral CLLong CLong # 
FromIntegral CLLong CULong # 
FromIntegral CLLong CLLong # 
FromIntegral CLLong CULLong # 
FromIntegral CLLong CFloat # 
FromIntegral CLLong CDouble # 
FromIntegral CULLong Double # 
FromIntegral CULLong Float # 
FromIntegral CULLong Int # 
FromIntegral CULLong Int8 # 
FromIntegral CULLong Int16 # 
FromIntegral CULLong Int32 # 
FromIntegral CULLong Int64 # 
FromIntegral CULLong Word # 
FromIntegral CULLong Word8 # 
FromIntegral CULLong Word16 # 
FromIntegral CULLong Word32 # 
FromIntegral CULLong Word64 # 
FromIntegral CULLong CShort # 
FromIntegral CULLong CUShort # 
FromIntegral CULLong CInt # 
FromIntegral CULLong CUInt # 
FromIntegral CULLong CLong # 
FromIntegral CULLong CULong # 
FromIntegral CULLong CLLong # 
FromIntegral CULLong CULLong # 
FromIntegral CULLong CFloat # 
FromIntegral CULLong CDouble # 

class ToFloating a b where #

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 #

General coercion to floating types

Instances

ToFloating Double Double # 
ToFloating Double Float # 
ToFloating Double CFloat # 
ToFloating Double CDouble # 
ToFloating Float Double # 
ToFloating Float Float # 

Methods

toFloating :: Exp Float -> Exp Float #

ToFloating Float CFloat # 
ToFloating Float CDouble # 
ToFloating Int Double # 

Methods

toFloating :: Exp Int -> Exp Double #

ToFloating Int Float # 

Methods

toFloating :: Exp Int -> Exp Float #

ToFloating Int CFloat # 

Methods

toFloating :: Exp Int -> Exp CFloat #

ToFloating Int CDouble # 

Methods

toFloating :: Exp Int -> Exp CDouble #

ToFloating Int8 Double # 

Methods

toFloating :: Exp Int8 -> Exp Double #

ToFloating Int8 Float # 

Methods

toFloating :: Exp Int8 -> Exp Float #

ToFloating Int8 CFloat # 

Methods

toFloating :: Exp Int8 -> Exp CFloat #

ToFloating Int8 CDouble # 
ToFloating Int16 Double # 
ToFloating Int16 Float # 

Methods

toFloating :: Exp Int16 -> Exp Float #

ToFloating Int16 CFloat # 
ToFloating Int16 CDouble # 
ToFloating Int32 Double # 
ToFloating Int32 Float # 

Methods

toFloating :: Exp Int32 -> Exp Float #

ToFloating Int32 CFloat # 
ToFloating Int32 CDouble # 
ToFloating Int64 Double # 
ToFloating Int64 Float # 

Methods

toFloating :: Exp Int64 -> Exp Float #

ToFloating Int64 CFloat # 
ToFloating Int64 CDouble # 
ToFloating Word Double # 

Methods

toFloating :: Exp Word -> Exp Double #

ToFloating Word Float # 

Methods

toFloating :: Exp Word -> Exp Float #

ToFloating Word CFloat # 

Methods

toFloating :: Exp Word -> Exp CFloat #

ToFloating Word CDouble # 
ToFloating Word8 Double # 
ToFloating Word8 Float # 

Methods

toFloating :: Exp Word8 -> Exp Float #

ToFloating Word8 CFloat # 
ToFloating Word8 CDouble # 
ToFloating Word16 Double # 
ToFloating Word16 Float # 
ToFloating Word16 CFloat # 
ToFloating Word16 CDouble # 
ToFloating Word32 Double # 
ToFloating Word32 Float # 
ToFloating Word32 CFloat # 
ToFloating Word32 CDouble # 
ToFloating Word64 Double # 
ToFloating Word64 Float # 
ToFloating Word64 CFloat # 
ToFloating Word64 CDouble # 
ToFloating CShort Double # 
ToFloating CShort Float # 
ToFloating CShort CFloat # 
ToFloating CShort CDouble # 
ToFloating CUShort Double # 
ToFloating CUShort Float # 
ToFloating CUShort CFloat # 
ToFloating CUShort CDouble # 
ToFloating CInt Double # 

Methods

toFloating :: Exp CInt -> Exp Double #

ToFloating CInt Float # 

Methods

toFloating :: Exp CInt -> Exp Float #

ToFloating CInt CFloat # 

Methods

toFloating :: Exp CInt -> Exp CFloat #

ToFloating CInt CDouble # 
ToFloating CUInt Double # 
ToFloating CUInt Float # 

Methods

toFloating :: Exp CUInt -> Exp Float #

ToFloating CUInt CFloat # 
ToFloating CUInt CDouble # 
ToFloating CLong Double # 
ToFloating CLong Float # 

Methods

toFloating :: Exp CLong -> Exp Float #

ToFloating CLong CFloat # 
ToFloating CLong CDouble # 
ToFloating CULong Double # 
ToFloating CULong Float # 
ToFloating CULong CFloat # 
ToFloating CULong CDouble # 
ToFloating CLLong Double # 
ToFloating CLLong Float # 
ToFloating CLLong CFloat # 
ToFloating CLLong CDouble # 
ToFloating CULLong Double # 
ToFloating CULLong Float # 
ToFloating CULLong CFloat # 
ToFloating CULLong CDouble # 
ToFloating CFloat Double # 
ToFloating CFloat Float # 
ToFloating CFloat CFloat # 
ToFloating CFloat CDouble # 
ToFloating CDouble Double # 
ToFloating CDouble Float # 
ToFloating CDouble CFloat # 
ToFloating CDouble CDouble # 

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 r  = scanl' f z xs             :: (Acc (Vector Int), Acc (Scalar Int))
>>> let r' = lift r                    :: Acc (Vector Int, Scalar 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 #

The class of types e which can be lifted into c.

Minimal complete definition

lift

Associated Types

type Plain e #

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) #

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 # 

Associated Types

type Plain Bool :: * #

Methods

lift :: Bool -> Exp (Plain Bool) #

Lift Exp Char # 

Associated Types

type Plain Char :: * #

Methods

lift :: Char -> Exp (Plain Char) #

Lift Exp Double # 

Associated Types

type Plain Double :: * #

Methods

lift :: Double -> Exp (Plain Double) #

Lift Exp Float # 

Associated Types

type Plain Float :: * #

Methods

lift :: Float -> Exp (Plain Float) #

Lift Exp Int # 

Associated Types

type Plain Int :: * #

Methods

lift :: Int -> Exp (Plain Int) #

Lift Exp Int8 # 

Associated Types

type Plain Int8 :: * #

Methods

lift :: Int8 -> Exp (Plain Int8) #

Lift Exp Int16 # 

Associated Types

type Plain Int16 :: * #

Methods

lift :: Int16 -> Exp (Plain Int16) #

Lift Exp Int32 # 

Associated Types

type Plain Int32 :: * #

Methods

lift :: Int32 -> Exp (Plain Int32) #

Lift Exp Int64 # 

Associated Types

type Plain Int64 :: * #

Methods

lift :: Int64 -> Exp (Plain Int64) #

Lift Exp Word # 

Associated Types

type Plain Word :: * #

Methods

lift :: Word -> Exp (Plain Word) #

Lift Exp Word8 # 

Associated Types

type Plain Word8 :: * #

Methods

lift :: Word8 -> Exp (Plain Word8) #

Lift Exp Word16 # 

Associated Types

type Plain Word16 :: * #

Methods

lift :: Word16 -> Exp (Plain Word16) #

Lift Exp Word32 # 

Associated Types

type Plain Word32 :: * #

Methods

lift :: Word32 -> Exp (Plain Word32) #

Lift Exp Word64 # 

Associated Types

type Plain Word64 :: * #

Methods

lift :: Word64 -> Exp (Plain Word64) #

Lift Exp () # 

Associated Types

type Plain () :: * #

Methods

lift :: () -> Exp (Plain ()) #

Lift Exp CChar # 

Associated Types

type Plain CChar :: * #

Methods

lift :: CChar -> Exp (Plain CChar) #

Lift Exp CSChar # 

Associated Types

type Plain CSChar :: * #

Methods

lift :: CSChar -> Exp (Plain CSChar) #

Lift Exp CUChar # 

Associated Types

type Plain CUChar :: * #

Methods

lift :: CUChar -> Exp (Plain CUChar) #

Lift Exp CShort # 

Associated Types

type Plain CShort :: * #

Methods

lift :: CShort -> Exp (Plain CShort) #

Lift Exp CUShort # 

Associated Types

type Plain CUShort :: * #

Methods

lift :: CUShort -> Exp (Plain CUShort) #

Lift Exp CInt # 

Associated Types

type Plain CInt :: * #

Methods

lift :: CInt -> Exp (Plain CInt) #

Lift Exp CUInt # 

Associated Types

type Plain CUInt :: * #

Methods

lift :: CUInt -> Exp (Plain CUInt) #

Lift Exp CLong # 

Associated Types

type Plain CLong :: * #

Methods

lift :: CLong -> Exp (Plain CLong) #

Lift Exp CULong # 

Associated Types

type Plain CULong :: * #

Methods

lift :: CULong -> Exp (Plain CULong) #

Lift Exp CLLong # 

Associated Types

type Plain CLLong :: * #

Methods

lift :: CLLong -> Exp (Plain CLLong) #

Lift Exp CULLong # 

Associated Types

type Plain CULLong :: * #

Methods

lift :: CULLong -> Exp (Plain CULLong) #

Lift Exp CFloat # 

Associated Types

type Plain CFloat :: * #

Methods

lift :: CFloat -> Exp (Plain CFloat) #

Lift Exp CDouble # 

Associated Types

type Plain CDouble :: * #

Methods

lift :: CDouble -> Exp (Plain CDouble) #

Lift Exp Z # 

Associated Types

type Plain Z :: * #

Methods

lift :: Z -> Exp (Plain Z) #

Shape sh => Lift Exp (Any sh) # 

Associated Types

type Plain (Any sh) :: * #

Methods

lift :: Any sh -> Exp (Plain (Any sh)) #

Lift Exp (Exp e) # 

Associated Types

type Plain (Exp e) :: * #

Methods

lift :: Exp e -> Exp (Plain (Exp e)) #

Lift Acc (Acc a) # 

Associated Types

type Plain (Acc a) :: * #

Methods

lift :: Acc a -> Acc (Plain (Acc a)) #

(Lift Exp a, Lift Exp b, Elt (Plain a), Elt (Plain b)) => Lift Exp (a, b) # 

Associated Types

type Plain (a, b) :: * #

Methods

lift :: (a, b) -> Exp (Plain (a, b)) #

(Elt e, Slice (Plain ix), Lift Exp ix) => Lift Exp ((:.) ix (Exp e)) # 

Associated Types

type Plain ((:.) ix (Exp e)) :: * #

Methods

lift :: (ix :. Exp e) -> Exp (Plain (ix :. Exp e)) #

(Slice (Plain ix), Lift Exp ix) => Lift Exp ((:.) ix All) # 

Associated Types

type Plain ((:.) ix All) :: * #

Methods

lift :: (ix :. All) -> Exp (Plain (ix :. All)) #

(Slice (Plain ix), Lift Exp ix) => Lift Exp ((:.) ix Int) # 

Associated Types

type Plain ((:.) ix Int) :: * #

Methods

lift :: (ix :. Int) -> Exp (Plain (ix :. Int)) #

(Lift Acc a, Lift Acc b, Arrays (Plain a), Arrays (Plain b)) => Lift Acc (a, b) # 

Associated Types

type Plain (a, b) :: * #

Methods

lift :: (a, b) -> Acc (Plain (a, b)) #

(Shape sh, Elt e) => Lift Acc (Array sh e) # 

Associated Types

type Plain (Array sh e) :: * #

Methods

lift :: Array sh e -> Acc (Plain (Array sh e)) #

(Lift Exp a, Lift Exp b, Lift Exp c, Elt (Plain a), Elt (Plain b), Elt (Plain c)) => Lift Exp (a, b, c) # 

Associated Types

type Plain (a, b, c) :: * #

Methods

lift :: (a, b, c) -> Exp (Plain (a, b, c)) #

(Lift Acc a, Lift Acc b, Lift Acc c, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c)) => Lift Acc (a, b, c) # 

Associated Types

type Plain (a, b, c) :: * #

Methods

lift :: (a, b, c) -> Acc (Plain (a, b, c)) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d)) => Lift Exp (a, b, c, d) # 

Associated Types

type Plain (a, b, c, d) :: * #

Methods

lift :: (a, b, c, d) -> Exp (Plain (a, b, c, d)) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d)) => Lift Acc (a, b, c, d) # 

Associated Types

type Plain (a, b, c, d) :: * #

Methods

lift :: (a, b, c, d) -> Acc (Plain (a, b, c, d)) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e)) => Lift Exp (a, b, c, d, e) # 

Associated Types

type Plain (a, b, c, d, e) :: * #

Methods

lift :: (a, b, c, d, e) -> Exp (Plain (a, b, c, d, e)) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e)) => Lift Acc (a, b, c, d, e) # 

Associated Types

type Plain (a, b, c, d, e) :: * #

Methods

lift :: (a, b, c, d, e) -> Acc (Plain (a, b, c, d, e)) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f)) => Lift Exp (a, b, c, d, e, f) # 

Associated Types

type Plain (a, b, c, d, e, f) :: * #

Methods

lift :: (a, b, c, d, e, f) -> Exp (Plain (a, b, c, d, e, f)) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f)) => Lift Acc (a, b, c, d, e, f) # 

Associated Types

type Plain (a, b, c, d, e, f) :: * #

Methods

lift :: (a, b, c, d, e, f) -> Acc (Plain (a, b, c, d, e, f)) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g)) => Lift Exp (a, b, c, d, e, f, g) # 

Associated Types

type Plain (a, b, c, d, e, f, g) :: * #

Methods

lift :: (a, b, c, d, e, f, g) -> Exp (Plain (a, b, c, d, e, f, g)) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g)) => Lift Acc (a, b, c, d, e, f, g) # 

Associated Types

type Plain (a, b, c, d, e, f, g) :: * #

Methods

lift :: (a, b, c, d, e, f, g) -> Acc (Plain (a, b, c, d, e, f, g)) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h)) => Lift Exp (a, b, c, d, e, f, g, h) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h) -> Exp (Plain (a, b, c, d, e, f, g, h)) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Lift Acc h, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g), Arrays (Plain h)) => Lift Acc (a, b, c, d, e, f, g, h) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h) -> Acc (Plain (a, b, c, d, e, f, g, h)) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i)) => Lift Exp (a, b, c, d, e, f, g, h, i) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i) -> Exp (Plain (a, b, c, d, e, f, g, h, i)) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Lift Acc h, Lift Acc i, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g), Arrays (Plain h), Arrays (Plain i)) => Lift Acc (a, b, c, d, e, f, g, h, i) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i) -> Acc (Plain (a, b, c, d, e, f, g, h, i)) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j)) => Lift Exp (a, b, c, d, e, f, g, h, i, j) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j)) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Lift Acc h, Lift Acc i, Lift Acc j, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g), Arrays (Plain h), Arrays (Plain i), Arrays (Plain j)) => Lift Acc (a, b, c, d, e, f, g, h, i, j) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j) -> Acc (Plain (a, b, c, d, e, f, g, h, i, j)) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j, k)) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Lift Acc h, Lift Acc i, Lift Acc j, Lift Acc k, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g), Arrays (Plain h), Arrays (Plain i), Arrays (Plain j), Arrays (Plain k)) => Lift Acc (a, b, c, d, e, f, g, h, i, j, k) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k) -> Acc (Plain (a, b, c, d, e, f, g, h, i, j, k)) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Lift Exp l, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k), Elt (Plain l)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k, l) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j, k, l)) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Lift Acc h, Lift Acc i, Lift Acc j, Lift Acc k, Lift Acc l, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g), Arrays (Plain h), Arrays (Plain i), Arrays (Plain j), Arrays (Plain k), Arrays (Plain l)) => Lift Acc (a, b, c, d, e, f, g, h, i, j, k, l) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Acc (Plain (a, b, c, d, e, f, g, h, i, j, k, l)) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Lift Exp l, Lift Exp m, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k), Elt (Plain l), Elt (Plain m)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k, l, m) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l, m) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j, k, l, m)) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Lift Acc h, Lift Acc i, Lift Acc j, Lift Acc k, Lift Acc l, Lift Acc m, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g), Arrays (Plain h), Arrays (Plain i), Arrays (Plain j), Arrays (Plain k), Arrays (Plain l), Arrays (Plain m)) => Lift Acc (a, b, c, d, e, f, g, h, i, j, k, l, m) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l, m) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Acc (Plain (a, b, c, d, e, f, g, h, i, j, k, l, m)) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Lift Exp l, Lift Exp m, Lift Exp n, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k), Elt (Plain l), Elt (Plain m), Elt (Plain n)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n)) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Lift Acc h, Lift Acc i, Lift Acc j, Lift Acc k, Lift Acc l, Lift Acc m, Lift Acc n, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g), Arrays (Plain h), Arrays (Plain i), Arrays (Plain j), Arrays (Plain k), Arrays (Plain l), Arrays (Plain m), Arrays (Plain n)) => Lift Acc (a, b, c, d, e, f, g, h, i, j, k, l, m, n) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Acc (Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n)) #

(Lift Exp a, Lift Exp b, Lift Exp c, Lift Exp d, Lift Exp e, Lift Exp f, Lift Exp g, Lift Exp h, Lift Exp i, Lift Exp j, Lift Exp k, Lift Exp l, Lift Exp m, Lift Exp n, Lift Exp o, Elt (Plain a), Elt (Plain b), Elt (Plain c), Elt (Plain d), Elt (Plain e), Elt (Plain f), Elt (Plain g), Elt (Plain h), Elt (Plain i), Elt (Plain j), Elt (Plain k), Elt (Plain l), Elt (Plain m), Elt (Plain n), Elt (Plain o)) => Lift Exp (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Exp (Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)) #

(Lift Acc a, Lift Acc b, Lift Acc c, Lift Acc d, Lift Acc e, Lift Acc f, Lift Acc g, Lift Acc h, Lift Acc i, Lift Acc j, Lift Acc k, Lift Acc l, Lift Acc m, Lift Acc n, Lift Acc o, Arrays (Plain a), Arrays (Plain b), Arrays (Plain c), Arrays (Plain d), Arrays (Plain e), Arrays (Plain f), Arrays (Plain g), Arrays (Plain h), Arrays (Plain i), Arrays (Plain j), Arrays (Plain k), Arrays (Plain l), Arrays (Plain m), Arrays (Plain n), Arrays (Plain o)) => Lift Acc (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) # 

Associated Types

type Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) :: * #

Methods

lift :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Acc (Plain (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)) #

class Lift c e => Unlift c e where #

A limited subset of types which can be lifted, can also be unlifted.

Minimal complete definition

unlift

Methods

unlift :: c (Plain e) -> e #

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 () # 

Methods

unlift :: Exp (Plain ()) -> () #

Unlift Exp Z # 

Methods

unlift :: Exp (Plain Z) -> Z #

Unlift Exp (Exp e) # 

Methods

unlift :: Exp (Plain (Exp e)) -> Exp e #

Unlift Acc (Acc a) # 

Methods

unlift :: Acc (Plain (Acc a)) -> Acc a #

(Elt a, Elt b) => Unlift Exp (Exp a, Exp b) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b)) -> (Exp a, Exp b) #

(Elt e, Slice (Plain ix), Unlift Exp ix) => Unlift Exp ((:.) ix (Exp e)) # 

Methods

unlift :: Exp (Plain (ix :. Exp e)) -> ix :. Exp e #

(Elt e, Slice ix) => Unlift Exp ((:.) (Exp ix) (Exp e)) # 

Methods

unlift :: Exp (Plain (Exp ix :. Exp e)) -> Exp ix :. Exp e #

(Arrays a, Arrays b) => Unlift Acc (Acc a, Acc b) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b)) -> (Acc a, Acc b) #

(Elt a, Elt b, Elt c) => Unlift Exp (Exp a, Exp b, Exp c) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c)) -> (Exp a, Exp b, Exp c) #

(Arrays a, Arrays b, Arrays c) => Unlift Acc (Acc a, Acc b, Acc c) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c)) -> (Acc a, Acc b, Acc c) #

(Elt a, Elt b, Elt c, Elt d) => Unlift Exp (Exp a, Exp b, Exp c, Exp d) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d)) -> (Exp a, Exp b, Exp c, Exp d) #

(Arrays a, Arrays b, Arrays c, Arrays d) => Unlift Acc (Acc a, Acc b, Acc c, Acc d) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d)) -> (Acc a, Acc b, Acc c, Acc d) #

(Elt a, Elt b, Elt c, Elt d, Elt e) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e)) -> (Exp a, Exp b, Exp c, Exp d, Exp e) #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e)) -> (Acc a, Acc b, Acc c, Acc d, Acc e) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f) #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g) #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h) #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i) #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j) #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k) #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j, Arrays k) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k, Elt l) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l) #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j, Arrays k, Arrays l) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k, Elt l, Elt m) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m) #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j, Arrays k, Arrays l, Arrays m) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k, Elt l, Elt m, Elt n) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n) #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j, Arrays k, Arrays l, Arrays m, Arrays n) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m, Acc n) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m, Acc n)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m, Acc n) #

(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j, Elt k, Elt l, Elt m, Elt n, Elt o) => Unlift Exp (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n, Exp o) # 

Methods

unlift :: Exp (Plain (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n, Exp o)) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i, Exp j, Exp k, Exp l, Exp m, Exp n, Exp o) #

(Arrays a, Arrays b, Arrays c, Arrays d, Arrays e, Arrays f, Arrays g, Arrays h, Arrays i, Arrays j, Arrays k, Arrays l, Arrays m, Arrays n, Arrays o) => Unlift Acc (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m, Acc n, Acc o) # 

Methods

unlift :: Acc (Plain (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m, Acc n, Acc o)) -> (Acc a, Acc b, Acc c, Acc d, Acc e, Acc f, Acc g, Acc h, Acc i, Acc j, Acc k, Acc l, Acc m, Acc n, Acc o) #

lift1 :: (Unlift Exp a, Lift Exp b) => (a -> b) -> Exp (Plain a) -> Exp (Plain b) #

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) #

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) #

Lift a ternary function into Exp.

ilift1 :: (Exp Int -> Exp Int) -> Exp DIM1 -> Exp DIM1 #

Lift a unary function to a computation over rank-1 indices.

ilift2 :: (Exp Int -> Exp Int -> Exp Int) -> Exp DIM1 -> Exp DIM1 -> Exp DIM1 #

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 #

Lift a ternary function to a computation over rank-1 indices.

Scalar operations

Introduction

constant :: Elt t => t -> Exp t #

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 #

Extract the first component of a scalar pair.

afst :: forall a b. (Arrays a, Arrays b) => Acc (a, b) -> Acc a #

Extract the first component of an array pair.

snd :: forall a b. (Elt a, Elt b) => Exp (a, b) -> Exp b #

Extract the second component of a scalar pair.

asnd :: forall a b. (Arrays a, Arrays b) => Acc (a, b) -> Acc b #

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 #

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 #

Converts a curried function to a function on pairs.

Flow control

(?) :: Elt t => Exp Bool -> (Exp t, Exp t) -> Exp t infix 0 #

An infix version of cond. If the predicate evaluates to True, the first component of the tuple is returned, else the second.

See also: ifThenElse.

caseof #

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 #

Arguments

:: Elt t 
=> Exp Bool

condition

-> Exp t

then-expression

-> Exp t

else-expression

-> Exp t 

A scalar-level if-then-else construct.

while #

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 #

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 #

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 #

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 #

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 #

Logical negation

Numeric operations

subtract :: Num a => Exp a -> Exp a -> Exp a #

subtract is the same as flip (-).

even :: Integral a => Exp a -> Exp Bool #

Determine if a number is even

odd :: Integral a => Exp a -> Exp Bool #

Determine if a number is odd

gcd :: Integral a => Exp a -> Exp a -> Exp a #

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 #

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 #

Raise a number to a non-negative integral power

(^^) :: (Fractional a, Integral b) => Exp a -> Exp b -> Exp a infixr 8 #

Raise a number to an integral power

Shape manipulation

index0 :: Exp Z #

The one index for a rank-0 array.

index1 :: Elt i => Exp i -> Exp (Z :. i) #

Turn an Int expression into a rank-1 indexing expression.

unindex1 :: Elt i => Exp (Z :. i) -> Exp i #

Turn a rank-1 indexing expression into an Int expression.

index2 :: (Elt i, Slice (Z :. i)) => Exp i -> Exp i -> Exp ((Z :. i) :. i) #

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) #

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) #

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) #

Destruct a rank-3 index into an Exp tuple of Int`s

indexHead :: (Slice sh, Elt a) => Exp (sh :. a) -> Exp a #

Get the innermost dimension of a shape

indexTail :: (Slice sh, Elt a) => Exp (sh :. a) -> Exp sh #

Get all but the innermost element of a shape

toIndex #

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 #

Inverse of toIndex

intersect :: Shape sh => Exp sh -> Exp sh -> Exp sh #

Intersection of two shapes

Conversions

ord :: Exp Char -> Exp Int #

Convert a character to an Int.

chr :: Exp Int -> Exp Char #

Convert an Int into a character.

boolToInt :: Exp Bool -> Exp Int #

Convert a Boolean value to an Int, where False turns into '0' and True into '1'.

bitcast :: (Elt a, Elt b, IsScalar a, IsScalar b, BitSizeEq a b) => Exp a -> Exp b #

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 #

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 of 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 #

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 #

Rank of an array.

arrayShape :: Shape sh => Array sh e -> sh #

Array shape in plain Haskell code.

arraySize :: Shape sh => sh -> Int #

Total number of elements in an array of the given Shape.

indexArray :: Array sh e -> sh -> e #

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 #

Create an array from its representation function, applied at each index of the array.

Lists

fromList :: (Shape sh, Elt e) => sh -> [e] -> Array sh e #

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) :: Array DIM2 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] #

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.

For instance,

>>> 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 

Methods

minBound :: Int #

maxBound :: Int #

Enum Int 

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 

Methods

(==) :: Int -> Int -> Bool #

(/=) :: Int -> Int -> Bool #

Integral Int 

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 #

Data Int 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int -> c Int #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int #

toConstr :: Int -> Constr #

dataTypeOf :: Int -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Int) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int) #

gmapT :: (forall b. Data b => b -> b) -> Int -> Int #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int -> m Int #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int #

Num Int 

Methods

(+) :: Int -> Int -> Int #

(-) :: Int -> Int -> Int #

(*) :: Int -> Int -> Int #

negate :: Int -> Int #

abs :: Int -> Int #

signum :: Int -> Int #

fromInteger :: Integer -> Int #

Ord Int 

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 
Real Int 

Methods

toRational :: Int -> Rational #

Show Int 

Methods

showsPrec :: Int -> Int -> ShowS #

show :: Int -> String #

showList :: [Int] -> ShowS #

Ix Int 

Methods

range :: (Int, Int) -> [Int] #

index :: (Int, Int) -> Int -> Int #

unsafeIndex :: (Int, Int) -> Int -> Int

inRange :: (Int, Int) -> Int -> Bool #

rangeSize :: (Int, Int) -> Int #

unsafeRangeSize :: (Int, Int) -> Int

Lift Int 

Methods

lift :: Int -> Q Exp #

PrintfArg Int 
Storable Int 

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 

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 
NFData Int 

Methods

rnf :: Int -> () #

Hashable Int 

Methods

hashWithSalt :: Int -> Int -> Int #

hash :: Int -> Int #

Prim Int 
Unbox Int 
IsScalar Int # 

Methods

scalarType :: ScalarType Int

IsBounded Int # 

Methods

boundedType :: BoundedType Int

IsNum Int # 

Methods

numType :: NumType Int

IsIntegral Int # 

Methods

integralType :: IntegralType Int

Elt Int # 

Methods

eltType :: Int -> TupleType (EltRepr Int)

fromElt :: Int -> EltRepr Int

toElt :: EltRepr Int -> Int

Eq Int # 

Methods

(==) :: Exp Int -> Exp Int -> Exp Bool #

(/=) :: Exp Int -> Exp Int -> Exp Bool #

Ord Int # 

Methods

(<) :: Exp Int -> Exp Int -> Exp Bool #

(>) :: Exp Int -> Exp Int -> Exp Bool #

(<=) :: Exp Int -> Exp Int -> Exp Bool #

(>=) :: Exp Int -> Exp Int -> Exp Bool #

min :: Exp Int -> Exp Int -> Exp Int #

max :: Exp Int -> Exp Int -> Exp Int #

FiniteBits Int # 
Bits Int # 
Vector Vector Int 
MVector MVector Int 
FromIntegral Int Double # 
FromIntegral Int Float # 

Methods

fromIntegral :: Exp Int -> Exp Float #

FromIntegral Int Int # 

Methods

fromIntegral :: Exp Int -> Exp Int #

FromIntegral Int Int8 # 

Methods

fromIntegral :: Exp Int -> Exp Int8 #

FromIntegral Int Int16 # 

Methods

fromIntegral :: Exp Int -> Exp Int16 #

FromIntegral Int Int32 # 

Methods

fromIntegral :: Exp Int -> Exp Int32 #

FromIntegral Int Int64 # 

Methods

fromIntegral :: Exp Int -> Exp Int64 #

FromIntegral Int Word # 

Methods

fromIntegral :: Exp Int -> Exp Word #

FromIntegral Int Word8 # 

Methods

fromIntegral :: Exp Int -> Exp Word8 #

FromIntegral Int Word16 # 
FromIntegral Int Word32 # 
FromIntegral Int Word64 # 
FromIntegral Int CShort # 
FromIntegral Int CUShort # 
FromIntegral Int CInt # 

Methods

fromIntegral :: Exp Int -> Exp CInt #

FromIntegral Int CUInt # 

Methods

fromIntegral :: Exp Int -> Exp CUInt #

FromIntegral Int CLong # 

Methods

fromIntegral :: Exp Int -> Exp CLong #

FromIntegral Int CULong # 
FromIntegral Int CLLong # 
FromIntegral Int CULLong # 
FromIntegral Int CFloat # 
FromIntegral Int CDouble # 
FromIntegral Int8 Int # 

Methods

fromIntegral :: Exp Int8 -> Exp Int #

FromIntegral Int16 Int # 

Methods

fromIntegral :: Exp Int16 -> Exp Int #

FromIntegral Int32 Int # 

Methods

fromIntegral :: Exp Int32 -> Exp Int #

FromIntegral Int64 Int # 

Methods

fromIntegral :: Exp Int64 -> Exp Int #

FromIntegral Word Int # 

Methods

fromIntegral :: Exp Word -> Exp Int #

FromIntegral Word8 Int # 

Methods

fromIntegral :: Exp Word8 -> Exp Int #

FromIntegral Word16 Int # 
FromIntegral Word32 Int # 
FromIntegral Word64 Int # 
FromIntegral CShort Int # 
FromIntegral CUShort Int # 
FromIntegral CInt Int # 

Methods

fromIntegral :: Exp CInt -> Exp Int #

FromIntegral CUInt Int # 

Methods

fromIntegral :: Exp CUInt -> Exp Int #

FromIntegral CLong Int # 

Methods

fromIntegral :: Exp CLong -> Exp Int #

FromIntegral CULong Int # 
FromIntegral CLLong Int # 
FromIntegral CULLong Int # 
ToFloating Int Double # 

Methods

toFloating :: Exp Int -> Exp Double #

ToFloating Int Float # 

Methods

toFloating :: Exp Int -> Exp Float #

ToFloating Int CFloat # 

Methods

toFloating :: Exp Int -> Exp CFloat #

ToFloating Int CDouble # 

Methods

toFloating :: Exp Int -> Exp CDouble #

Lift Exp Int # 

Associated Types

type Plain Int :: * #

Methods

lift :: Int -> Exp (Plain Int) #

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e)

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e, Exp e, Exp e)

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) # 

Associated Types

type StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) :: *

Methods

stencilPrj :: DIM1 -> e -> Exp (StencilRepr DIM1 (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)) -> (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e)

(Slice (Plain ix), Lift Exp ix) => Lift Exp ((:.) ix Int) # 

Associated Types

type Plain ((:.) ix Int) :: * #

Methods

lift :: (ix :. Int) -> Exp (Plain (ix :. Int)) #

Elt e => IsList (Vector e) # 

Associated Types

type Item (Vector e) :: * #

Methods

fromList :: [Item (Vector e)] -> Vector e #

fromListN :: Int -> [Item (Vector e)] -> Vector e #

toList :: Vector e -> [Item (Vector e)] #

Functor (URec Int) 

Methods

fmap :: (a -> b) -> URec Int a -> URec Int b #

(<$) :: a -> URec Int b -> URec Int a #

Show (Vector e) # 

Methods

showsPrec :: Int -> Vector e -> ShowS #

show :: Vector e -> String #

showList :: [Vector e] -> ShowS #

Foldable (URec Int) 

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) 

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) #

Generic1 (URec Int) 

Associated Types

type Rep1 (URec Int :: * -> *) :: * -> * #

Methods

from1 :: URec Int a -> Rep1 (URec Int) a #

to1 :: Rep1 (URec Int) a -> URec Int a #

Shape sh => Elt (Any ((:.) sh Int)) # 

Methods

eltType :: Any (sh :. Int) -> TupleType (EltRepr (Any (sh :. Int)))

fromElt :: Any (sh :. Int) -> EltRepr (Any (sh :. Int))

toElt :: EltRepr (Any (sh :. Int)) -> Any (sh :. Int)

Eq (URec Int p) 

Methods

(==) :: URec Int p -> URec Int p -> Bool #

(/=) :: URec Int p -> URec Int p -> Bool #

Ord (URec Int p) 

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) 

Methods

showsPrec :: Int -> URec Int p -> ShowS #

show :: URec Int p -> String #

showList :: [URec Int p] -> ShowS #

Show (Array DIM2 e) # 

Methods

showsPrec :: Int -> Array DIM2 e -> ShowS #

show :: Array DIM2 e -> String #

showList :: [Array DIM2 e] -> ShowS #

Generic (URec Int p) 

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 #

Slice sl => Slice ((:.) sl Int) # 

Associated Types

type SliceShape ((:.) sl Int) :: * #

type CoSliceShape ((:.) sl Int) :: * #

type FullShape ((:.) sl Int) :: * #

Methods

sliceIndex :: (sl :. Int) -> SliceIndex (EltRepr (sl :. Int)) (EltRepr (SliceShape (sl :. Int))) (EltRepr (CoSliceShape (sl :. Int))) (EltRepr (FullShape (sl :. Int))) #

Shape sh => Shape ((:.) sh Int) # 

Methods

rank :: (sh :. Int) -> Int

size :: (sh :. Int) -> Int

empty :: sh :. Int

ignore :: sh :. Int

intersect :: (sh :. Int) -> (sh :. Int) -> sh :. Int

union :: (sh :. Int) -> (sh :. Int) -> sh :. Int

toIndex :: (sh :. Int) -> (sh :. Int) -> Int

fromIndex :: (sh :. Int) -> Int -> sh :. Int

bound :: (sh :. Int) -> (sh :. Int) -> Boundary a -> Either a (sh :. Int)

iter :: (sh :. Int) -> ((sh :. Int) -> a) -> (a -> a -> a) -> a -> a

iter1 :: (sh :. Int) -> ((sh :. Int) -> a) -> (a -> a -> a) -> a

rangeToShape :: (sh :. Int, sh :. Int) -> sh :. Int

shapeToRange :: (sh :. Int) -> (sh :. Int, sh :. Int)

shapeToList :: (sh :. Int) -> [Int]

listToShape :: [Int] -> sh :. Int

sliceAnyIndex :: (sh :. Int) -> SliceIndex (EltRepr (Any (sh :. Int))) (EltRepr (sh :. Int)) () (EltRepr (sh :. Int))

sliceNoneIndex :: (sh :. Int) -> SliceIndex (EltRepr (sh :. Int)) () (EltRepr (sh :. Int)) (EltRepr (sh :. Int))

(Stencil ((:.) sh Int) a row2, Stencil ((:.) sh Int) a row1, Stencil ((:.) sh Int) a row0) => Stencil ((:.) ((:.) sh Int) Int) a (row2, row1, row0) # 

Associated Types

type StencilRepr ((:.) ((:.) sh Int) Int) (row2, row1, row0) :: *

Methods

stencilPrj :: ((sh :. Int) :. Int) -> a -> Exp (StencilRepr ((sh :. Int) :. Int) (row2, row1, row0)) -> (row2, row1, row0)

(Stencil ((:.) sh Int) a row1, Stencil ((:.) sh Int) a row2, Stencil ((:.) sh Int) a row3, Stencil ((:.) sh Int) a row4, Stencil ((:.) sh Int) a row5) => Stencil ((:.) ((:.) sh Int) Int) a (row1, row2, row3, row4, row5) # 

Associated Types

type StencilRepr ((:.) ((:.) sh Int) Int) (row1, row2, row3, row4, row5) :: *

Methods

stencilPrj :: ((sh :. Int) :. Int) -> a -> Exp (StencilRepr ((sh :. Int) :. Int) (row1, row2, row3, row4, row5)) -> (row1, row2, row3, row4, row5)

(Stencil ((:.) sh Int) a row1, Stencil ((:.) sh Int) a row2, Stencil ((:.) sh Int) a row3, Stencil ((:.) sh Int) a row4, Stencil ((:.) sh Int) a row5, Stencil ((:.) sh Int) a row6, Stencil ((:.) sh Int) a row7) => Stencil ((:.) ((:.) sh Int) Int) a (row1, row2, row3, row4, row5, row6, row7) # 

Associated Types

type StencilRepr ((:.) ((:.) sh Int) Int) (row1, row2, row3, row4, row5, row6, row7) :: *

Methods

stencilPrj :: ((sh :. Int) :. Int) -> a -> Exp (StencilRepr ((sh :. Int) :. Int) (row1, row2, row3, row4, row5, row6, row7)) -> (row1, row2, row3, row4, row5, row6, row7)

(Stencil ((:.) sh Int) a row1, Stencil ((:.) sh Int) a row2, Stencil ((:.) sh Int) a row3, Stencil ((:.) sh Int) a row4, Stencil ((:.) sh Int) a row5, Stencil ((:.) sh Int) a row6, Stencil ((:.) sh Int) a row7, Stencil ((:.) sh Int) a row8, Stencil ((:.) sh Int) a row9) => Stencil ((:.) ((:.) sh Int) Int) a (row1, row2, row3, row4, row5, row6, row7, row8, row9) # 

Associated Types

type StencilRepr ((:.) ((:.) sh Int) Int) (row1, row2, row3, row4, row5, row6, row7, row8, row9) :: *

Methods

stencilPrj :: ((sh :. Int) :. Int) -> a -> Exp (StencilRepr ((sh :. Int) :. Int) (row1, row2, row3, row4, row5, row6, row7, row8, row9)) -> (row1, row2, row3, row4, row5, row6, row7, row8, row9)

data URec Int

Used for marking occurrences of Int#

data URec Int = UInt {}
data Vector Int 
type Plain Int # 
type Plain Int = Int
data MVector s Int 
type Rep1 (URec Int) 
type Rep1 (URec Int) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UInt" PrefixI True) (S1 (MetaSel (Just Symbol "uInt#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UInt))
type Item (Vector e) # 
type Item (Vector e) = e
type Rep (URec Int p) 
type Rep (URec Int p) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UInt" PrefixI True) (S1 (MetaSel (Just Symbol "uInt#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UInt))
type SliceShape ((:.) sl Int) # 
type SliceShape ((:.) sl Int) = SliceShape sl
type CoSliceShape ((:.) sl Int) # 
type FullShape ((:.) sl Int) # 
type FullShape ((:.) sl Int) = (:.) (FullShape sl) Int
type Plain ((:.) ix Int) # 
type Plain ((:.) ix Int) = (:.) (Plain ix) Int

data Int8 :: * #

8-bit signed integer type

Instances

Bounded Int8 
Enum Int8 

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 

Methods

(==) :: Int8 -> Int8 -> Bool #

(/=) :: Int8 -> Int8 -> Bool #

Integral Int8 

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 #

Data Int8 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int8 -> c Int8 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int8 #

toConstr :: Int8 -> Constr #

dataTypeOf :: Int8 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Int8) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int8) #

gmapT :: (forall b. Data b => b -> b) -> Int8 -> Int8 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int8 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int8 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int8 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int8 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int8 -> m Int8 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int8 -> m Int8 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int8 -> m Int8 #

Num Int8 

Methods

(+) :: Int8 -> Int8 -> Int8 #

(-) :: Int8 -> Int8 -> Int8 #

(*) :: Int8 -> Int8 -> Int8 #

negate :: Int8 -> Int8 #

abs :: Int8 -> Int8 #

signum :: Int8 -> Int8 #

fromInteger :: Integer -> Int8 #

Ord Int8 

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 
Real Int8 

Methods

toRational :: Int8 -> Rational #

Show Int8 

Methods

showsPrec :: Int -> Int8 -> ShowS #

show :: Int8 -> String #

showList :: [Int8] -> ShowS #

Ix Int8 

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 

Methods

lift :: Int8 -> Q Exp #

PrintfArg Int8 
Storable Int8 

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 
FiniteBits Int8 
NFData Int8 

Methods

rnf :: Int8 -> () #

Hashable Int8 

Methods

hashWithSalt :: Int -> Int8 -> Int #

hash :: Int8 -> Int #

Prim Int8 
Unbox Int8 
IsScalar Int8 # 

Methods

scalarType :: ScalarType Int8

IsBounded Int8 # 

Methods

boundedType :: BoundedType Int8

IsNum Int8 # 

Methods

numType :: NumType Int8

IsIntegral Int8 # 

Methods

integralType :: IntegralType Int8

Elt Int8 # 

Methods

eltType :: Int8 -> TupleType (EltRepr Int8)

fromElt :: Int8 -> EltRepr Int8

toElt :: EltRepr Int8 -> Int8

Eq Int8 # 

Methods

(==) :: Exp Int8 -> Exp Int8 -> Exp Bool #

(/=) :: Exp Int8 -> Exp Int8 -> Exp Bool #

Ord Int8 # 

Methods

(<) :: Exp Int8 -> Exp Int8 -> Exp Bool #

(>) :: Exp Int8 -> Exp Int8 -> Exp Bool #

(<=) :: Exp Int8 -> Exp Int8 -> Exp Bool #

(>=) :: Exp Int8 -> Exp Int8 -> Exp Bool #

min :: Exp Int8 -> Exp Int8 -> Exp Int8 #

max :: Exp Int8 -> Exp Int8 -> Exp Int8 #

FiniteBits Int8 # 
Bits Int8 # 
Vector Vector Int8 
MVector MVector Int8 
FromIntegral Int Int8 # 

Methods

fromIntegral :: Exp Int -> Exp Int8 #

FromIntegral Int8 Double # 
FromIntegral Int8 Float # 
FromIntegral Int8 Int # 

Methods

fromIntegral :: Exp Int8 -> Exp Int #

FromIntegral Int8 Int8 # 

Methods

fromIntegral :: Exp Int8 -> Exp Int8 #

FromIntegral Int8 Int16 # 
FromIntegral Int8 Int32 # 
FromIntegral Int8 Int64 # 
FromIntegral Int8 Word # 

Methods

fromIntegral :: Exp Int8 -> Exp Word #

FromIntegral Int8 Word8 # 
FromIntegral Int8 Word16 # 
FromIntegral Int8 Word32 # 
FromIntegral Int8 Word64 # 
FromIntegral Int8 CShort # 
FromIntegral Int8 CUShort # 
FromIntegral Int8 CInt # 

Methods

fromIntegral :: Exp Int8 -> Exp CInt #

FromIntegral Int8 CUInt # 
FromIntegral Int8 CLong # 
FromIntegral Int8 CULong # 
FromIntegral Int8 CLLong # 
FromIntegral Int8 CULLong # 
FromIntegral Int8 CFloat # 
FromIntegral Int8 CDouble # 
FromIntegral Int16 Int8 # 
FromIntegral Int32 Int8 # 
FromIntegral Int64 Int8 # 
FromIntegral Word Int8 # 

Methods

fromIntegral :: Exp Word -> Exp Int8 #

FromIntegral Word8 Int8 # 
FromIntegral Word16 Int8 # 
FromIntegral Word32 Int8 # 
FromIntegral Word64 Int8 # 
FromIntegral CShort Int8 # 
FromIntegral CUShort Int8 # 
FromIntegral CInt Int8 # 

Methods

fromIntegral :: Exp CInt -> Exp Int8 #

FromIntegral CUInt Int8 # 
FromIntegral CLong Int8 # 
FromIntegral CULong Int8 # 
FromIntegral CLLong Int8 # 
FromIntegral CULLong Int8 # 
ToFloating Int8 Double # 

Methods

toFloating :: Exp Int8 -> Exp Double #

ToFloating Int8 Float # 

Methods

toFloating :: Exp Int8 -> Exp Float #

ToFloating Int8 CFloat # 

Methods

toFloating :: Exp Int8 -> Exp CFloat #

ToFloating Int8 CDouble # 
Lift Exp Int8 # 

Associated Types

type Plain Int8 :: * #

Methods

lift :: Int8 -> Exp (Plain Int8) #

data Vector Int8 
type Plain Int8 # 
type Plain Int8 = Int8
data MVector s Int8 

data Int16 :: * #

16-bit signed integer type

Instances

Bounded Int16 
Enum Int16 
Eq Int16 

Methods

(==) :: Int16 -> Int16 -> Bool #

(/=) :: Int16 -> Int16 -> Bool #

Integral Int16 
Data Int16 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int16 -> c Int16 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int16 #

toConstr :: Int16 -> Constr #

dataTypeOf :: Int16 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Int16) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int16) #

gmapT :: (forall b. Data b => b -> b) -> Int16 -> Int16 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int16 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int16 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int16 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int16 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int16 -> m Int16 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int16 -> m Int16 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int16 -> m Int16 #

Num Int16 
Ord Int16 

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 
Real Int16 

Methods

toRational :: Int16 -> Rational #

Show Int16 

Methods

showsPrec :: Int -> Int16 -> ShowS #

show :: Int16 -> String #

showList :: [Int16] -> ShowS #

Ix Int16 
Lift Int16 

Methods

lift :: Int16 -> Q Exp #

PrintfArg Int16 
Storable Int16 

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 
FiniteBits Int16 
NFData Int16 

Methods

rnf :: Int16 -> () #

Hashable Int16 

Methods

hashWithSalt :: Int -> Int16 -> Int #

hash :: Int16 -> Int #

Prim Int16 
Unbox Int16 
IsScalar Int16 # 

Methods

scalarType :: ScalarType Int16

IsBounded Int16 # 

Methods

boundedType :: BoundedType Int16

IsNum Int16 # 

Methods

numType :: NumType Int16

IsIntegral Int16 # 

Methods

integralType :: IntegralType Int16

Elt Int16 # 

Methods

eltType :: Int16 -> TupleType (EltRepr Int16)

fromElt :: Int16 -> EltRepr Int16

toElt :: EltRepr Int16 -> Int16

Eq Int16 # 

Methods

(==) :: Exp Int16 -> Exp Int16 -> Exp Bool #

(/=) :: Exp Int16 -> Exp Int16 -> Exp Bool #

Ord Int16 # 
FiniteBits Int16 # 
Bits Int16 # 
Vector Vector Int16 
MVector MVector Int16 
FromIntegral Int Int16 # 

Methods

fromIntegral :: Exp Int -> Exp Int16 #

FromIntegral Int8 Int16 # 
FromIntegral Int16 Double # 
FromIntegral Int16 Float # 
FromIntegral Int16 Int # 

Methods

fromIntegral :: Exp Int16 -> Exp Int #

FromIntegral Int16 Int8 # 
FromIntegral Int16 Int16 # 
FromIntegral Int16 Int32 # 
FromIntegral Int16 Int64 # 
FromIntegral Int16 Word # 
FromIntegral Int16 Word8 # 
FromIntegral Int16 Word16 # 
FromIntegral Int16 Word32 # 
FromIntegral Int16 Word64 # 
FromIntegral Int16 CShort # 
FromIntegral Int16 CUShort # 
FromIntegral Int16 CInt # 
FromIntegral Int16 CUInt # 
FromIntegral Int16 CLong # 
FromIntegral Int16 CULong # 
FromIntegral Int16 CLLong # 
FromIntegral Int16 CULLong # 
FromIntegral Int16 CFloat # 
FromIntegral Int16 CDouble # 
FromIntegral Int32 Int16 # 
FromIntegral Int64 Int16 # 
FromIntegral Word Int16 # 
FromIntegral Word8 Int16 # 
FromIntegral Word16 Int16 # 
FromIntegral Word32 Int16 # 
FromIntegral Word64 Int16 # 
FromIntegral CShort Int16 # 
FromIntegral CUShort Int16 # 
FromIntegral CInt Int16 # 
FromIntegral CUInt Int16 # 
FromIntegral CLong Int16 # 
FromIntegral CULong Int16 # 
FromIntegral CLLong Int16 # 
FromIntegral CULLong Int16 # 
ToFloating Int16 Double # 
ToFloating Int16 Float # 

Methods

toFloating :: Exp Int16 -> Exp Float #

ToFloating Int16 CFloat # 
ToFloating Int16 CDouble # 
Lift Exp Int16 # 

Associated Types

type Plain Int16 :: * #

Methods

lift :: Int16 -> Exp (Plain Int16) #

data Vector Int16 
type Plain Int16 # 
data MVector s Int16 

data Int32 :: * #

32-bit signed integer type

Instances

Bounded Int32 
Enum Int32 
Eq Int32 

Methods

(==) :: Int32 -> Int32 -> Bool #

(/=) :: Int32 -> Int32 -> Bool #

Integral Int32 
Data Int32 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int32 -> c Int32 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int32 #

toConstr :: Int32 -> Constr #

dataTypeOf :: Int32 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Int32) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int32) #

gmapT :: (forall b. Data b => b -> b) -> Int32 -> Int32 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int32 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int32 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int32 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int32 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int32 -> m Int32 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int32 -> m Int32 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int32 -> m Int32 #

Num Int32 
Ord Int32 

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 
Real Int32 

Methods

toRational :: Int32 -> Rational #

Show Int32 

Methods

showsPrec :: Int -> Int32 -> ShowS #

show :: Int32 -> String #

showList :: [Int32] -> ShowS #

Ix Int32 
Lift Int32 

Methods

lift :: Int32 -> Q Exp #

PrintfArg Int32 
Storable Int32 

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 
FiniteBits Int32 
NFData Int32 

Methods

rnf :: Int32 -> () #

Hashable Int32 

Methods

hashWithSalt :: Int -> Int32 -> Int #

hash :: Int32 -> Int #

Prim Int32 
Unbox Int32 
IsScalar Int32 # 

Methods

scalarType :: ScalarType Int32

IsBounded Int32 # 

Methods

boundedType :: BoundedType Int32

IsNum Int32 # 

Methods

numType :: NumType Int32

IsIntegral Int32 # 

Methods

integralType :: IntegralType Int32

Elt Int32 # 

Methods

eltType :: Int32 -> TupleType (EltRepr Int32)

fromElt :: Int32 -> EltRepr Int32

toElt :: EltRepr Int32 -> Int32

Eq Int32 # 

Methods

(==) :: Exp Int32 -> Exp Int32 -> Exp Bool #

(/=) :: Exp Int32 -> Exp Int32 -> Exp Bool #

Ord Int32 # 
FiniteBits Int32 # 
Bits Int32 # 
Vector Vector Int32 
MVector MVector Int32 
FromIntegral Int Int32 # 

Methods

fromIntegral :: Exp Int -> Exp Int32 #

FromIntegral Int8 Int32 # 
FromIntegral Int16 Int32 # 
FromIntegral Int32 Double # 
FromIntegral Int32 Float # 
FromIntegral Int32 Int # 

Methods

fromIntegral :: Exp Int32 -> Exp Int #

FromIntegral Int32 Int8 # 
FromIntegral Int32 Int16 # 
FromIntegral Int32 Int32 # 
FromIntegral Int32 Int64 # 
FromIntegral Int32 Word # 
FromIntegral Int32 Word8 # 
FromIntegral Int32 Word16 # 
FromIntegral Int32 Word32 # 
FromIntegral Int32 Word64 # 
FromIntegral Int32 CShort # 
FromIntegral Int32 CUShort # 
FromIntegral Int32 CInt # 
FromIntegral Int32 CUInt # 
FromIntegral Int32 CLong # 
FromIntegral Int32 CULong # 
FromIntegral Int32 CLLong # 
FromIntegral Int32 CULLong # 
FromIntegral Int32 CFloat # 
FromIntegral Int32 CDouble # 
FromIntegral Int64 Int32 # 
FromIntegral Word Int32 # 
FromIntegral Word8 Int32 # 
FromIntegral Word16 Int32 # 
FromIntegral Word32 Int32 # 
FromIntegral Word64 Int32 # 
FromIntegral CShort Int32 # 
FromIntegral CUShort Int32 # 
FromIntegral CInt Int32 # 
FromIntegral CUInt Int32 # 
FromIntegral CLong Int32 # 
FromIntegral CULong Int32 # 
FromIntegral CLLong Int32 # 
FromIntegral CULLong Int32 # 
ToFloating Int32 Double # 
ToFloating Int32 Float # 

Methods

toFloating :: Exp Int32 -> Exp Float #

ToFloating Int32 CFloat # 
ToFloating Int32 CDouble # 
Lift Exp Int32 # 

Associated Types

type Plain Int32 :: * #

Methods

lift :: Int32 -> Exp (Plain Int32) #

data Vector Int32 
type Plain Int32 # 
data MVector s Int32 

data Int64 :: * #

64-bit signed integer type

Instances

Bounded Int64 
Enum Int64 
Eq Int64 

Methods

(==) :: Int64 -> Int64 -> Bool #

(/=) :: Int64 -> Int64 -> Bool #

Integral Int64 
Data Int64 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int64 -> c Int64 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int64 #

toConstr :: Int64 -> Constr #

dataTypeOf :: Int64 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Int64) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int64) #

gmapT :: (forall b. Data b => b -> b) -> Int64 -> Int64 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int64 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int64 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int64 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int64 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 #

Num Int64 
Ord Int64 

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 
Real Int64 

Methods

toRational :: Int64 -> Rational #

Show Int64 

Methods

showsPrec :: Int -> Int64 -> ShowS #

show :: Int64 -> String #

showList :: [Int64] -> ShowS #

Ix Int64 
Lift Int64 

Methods

lift :: Int64 -> Q Exp #

PrintfArg Int64 
Storable Int64 

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 
FiniteBits Int64 
NFData Int64 

Methods

rnf :: Int64 -> () #

Hashable Int64 

Methods

hashWithSalt :: Int -> Int64 -> Int #

hash :: Int64 -> Int #

Prim Int64 
Unbox Int64 
IsScalar Int64 # 

Methods

scalarType :: ScalarType Int64

IsBounded Int64 # 

Methods

boundedType :: BoundedType Int64

IsNum Int64 # 

Methods

numType :: NumType Int64

IsIntegral Int64 # 

Methods

integralType :: IntegralType Int64

Elt Int64 # 

Methods

eltType :: Int64 -> TupleType (EltRepr Int64)

fromElt :: Int64 -> EltRepr Int64

toElt :: EltRepr Int64 -> Int64

Eq Int64 # 

Methods

(==) :: Exp Int64 -> Exp Int64 -> Exp Bool #

(/=) :: Exp Int64 -> Exp Int64 -> Exp Bool #

Ord Int64 # 
FiniteBits Int64 # 
Bits Int64 # 
Vector Vector Int64 
MVector MVector Int64 
FromIntegral Int Int64 # 

Methods

fromIntegral :: Exp Int -> Exp Int64 #

FromIntegral Int8 Int64 # 
FromIntegral Int16 Int64 # 
FromIntegral Int32 Int64 # 
FromIntegral Int64 Double # 
FromIntegral Int64 Float # 
FromIntegral Int64 Int # 

Methods

fromIntegral :: Exp Int64 -> Exp Int #

FromIntegral Int64 Int8 # 
FromIntegral Int64 Int16 # 
FromIntegral Int64 Int32 # 
FromIntegral Int64 Int64 # 
FromIntegral Int64 Word # 
FromIntegral Int64 Word8 # 
FromIntegral Int64 Word16 # 
FromIntegral Int64 Word32 # 
FromIntegral Int64 Word64 # 
FromIntegral Int64 CShort # 
FromIntegral Int64 CUShort # 
FromIntegral Int64 CInt # 
FromIntegral Int64 CUInt # 
FromIntegral Int64 CLong # 
FromIntegral Int64 CULong # 
FromIntegral Int64 CLLong # 
FromIntegral Int64 CULLong # 
FromIntegral Int64 CFloat # 
FromIntegral Int64 CDouble # 
FromIntegral Word Int64 # 
FromIntegral Word8 Int64 # 
FromIntegral Word16 Int64 # 
FromIntegral Word32 Int64 # 
FromIntegral Word64 Int64 # 
FromIntegral CShort Int64 # 
FromIntegral CUShort Int64 # 
FromIntegral CInt Int64 # 
FromIntegral CUInt Int64 # 
FromIntegral CLong Int64 # 
FromIntegral CULong Int64 # 
FromIntegral CLLong Int64 # 
FromIntegral CULLong Int64 # 
ToFloating Int64 Double # 
ToFloating Int64 Float # 

Methods

toFloating :: Exp Int64 -> Exp Float #

ToFloating Int64 CFloat # 
ToFloating Int64 CDouble # 
Lift Exp Int64 # 

Associated Types

type Plain Int64 :: * #

Methods

lift :: Int64 -> Exp (Plain Int64) #

data Vector Int64 
type Plain Int64 # 
data MVector s Int64 

data Word :: * #

A Word is an unsigned integral type, with the same size as Int.

Instances

Bounded Word 
Enum Word 

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 

Methods

(==) :: Word -> Word -> Bool #

(/=) :: Word -> Word -> Bool #

Integral Word 

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 #

Data Word 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word -> c Word #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word #

toConstr :: Word -> Constr #

dataTypeOf :: Word -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Word) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word) #

gmapT :: (forall b. Data b => b -> b) -> Word -> Word #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word -> m Word #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word #

Num Word 

Methods

(+) :: Word -> Word -> Word #

(-) :: Word -> Word -> Word #

(*) :: Word -> Word -> Word #

negate :: Word -> Word #

abs :: Word -> Word #

signum :: Word -> Word #

fromInteger :: Integer -> Word #

Ord Word 

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 
Real Word 

Methods

toRational :: Word -> Rational #

Show Word 

Methods

showsPrec :: Int -> Word -> ShowS #

show :: Word -> String #

showList :: [Word] -> ShowS #

Ix Word 

Methods

range :: (Word, Word) -> [Word] #

index :: (Word, Word) -> Word -> Int #

unsafeIndex :: (Word, Word) -> Word -> Int

inRange :: (Word, Word) -> Word -> Bool #

rangeSize :: (Word, Word) -> Int #

unsafeRangeSize :: (Word, Word) -> Int

Lift Word 

Methods

lift :: Word -> Q Exp #

PrintfArg Word 
Storable Word 

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 
FiniteBits Word 
NFData Word 

Methods

rnf :: Word -> () #

Hashable Word 

Methods

hashWithSalt :: Int -> Word -> Int #

hash :: Word -> Int #

Prim Word 
Unbox Word 
IsScalar Word # 

Methods

scalarType :: ScalarType Word

IsBounded Word # 

Methods

boundedType :: BoundedType Word

IsNum Word # 

Methods

numType :: NumType Word

IsIntegral Word # 

Methods

integralType :: IntegralType Word

Elt Word # 

Methods

eltType :: Word -> TupleType (EltRepr Word)

fromElt :: Word -> EltRepr Word

toElt :: EltRepr Word -> Word

Eq Word # 

Methods

(==) :: Exp Word -> Exp Word -> Exp Bool #

(/=) :: Exp Word -> Exp Word -> Exp Bool #

Ord Word # 

Methods

(<) :: Exp Word -> Exp Word -> Exp Bool #

(>) :: Exp Word -> Exp Word -> Exp Bool #

(<=) :: Exp Word -> Exp Word -> Exp Bool #

(>=) :: Exp Word -> Exp Word -> Exp Bool #

min :: Exp Word -> Exp Word -> Exp Word #

max :: Exp Word -> Exp Word -> Exp Word #

FiniteBits Word # 
Bits Word # 
Vector Vector Word 
MVector MVector Word 
FromIntegral Int Word # 

Methods

fromIntegral :: Exp Int -> Exp Word #

FromIntegral Int8 Word # 

Methods

fromIntegral :: Exp Int8 -> Exp Word #

FromIntegral Int16 Word # 
FromIntegral Int32 Word # 
FromIntegral Int64 Word # 
FromIntegral Word Double # 
FromIntegral Word Float # 
FromIntegral Word Int # 

Methods

fromIntegral :: Exp Word -> Exp Int #

FromIntegral Word Int8 # 

Methods

fromIntegral :: Exp Word -> Exp Int8 #

FromIntegral Word Int16 # 
FromIntegral Word Int32 # 
FromIntegral Word Int64 # 
FromIntegral Word Word # 

Methods

fromIntegral :: Exp Word -> Exp Word #

FromIntegral Word Word8 # 
FromIntegral Word Word16 # 
FromIntegral Word Word32 # 
FromIntegral Word Word64 # 
FromIntegral Word CShort # 
FromIntegral Word CUShort # 
FromIntegral Word CInt # 

Methods

fromIntegral :: Exp Word -> Exp CInt #

FromIntegral Word CUInt # 
FromIntegral Word CLong # 
FromIntegral Word CULong # 
FromIntegral Word CLLong # 
FromIntegral Word CULLong # 
FromIntegral Word CFloat # 
FromIntegral Word CDouble # 
FromIntegral Word8 Word # 
FromIntegral Word16 Word # 
FromIntegral Word32 Word # 
FromIntegral Word64 Word # 
FromIntegral CShort Word # 
FromIntegral CUShort Word # 
FromIntegral CInt Word # 

Methods

fromIntegral :: Exp CInt -> Exp Word #

FromIntegral CUInt Word # 
FromIntegral CLong Word # 
FromIntegral CULong Word # 
FromIntegral CLLong Word # 
FromIntegral CULLong Word # 
ToFloating Word Double # 

Methods

toFloating :: Exp Word -> Exp Double #

ToFloating Word Float # 

Methods

toFloating :: Exp Word -> Exp Float #

ToFloating Word CFloat # 

Methods

toFloating :: Exp Word -> Exp CFloat #

ToFloating Word CDouble # 
Lift Exp Word # 

Associated Types

type Plain Word :: * #

Methods

lift :: Word -> Exp (Plain Word) #

Functor (URec Word) 

Methods

fmap :: (a -> b) -> URec Word a -> URec Word b #

(<$) :: a -> URec Word b -> URec Word a #

Foldable (URec Word) 

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) 

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) #

Generic1 (URec Word) 

Associated Types

type Rep1 (URec Word :: * -> *) :: * -> * #

Methods

from1 :: URec Word a -> Rep1 (URec Word) a #

to1 :: Rep1 (URec Word) a -> URec Word a #

Eq (URec Word p) 

Methods

(==) :: URec Word p -> URec Word p -> Bool #

(/=) :: URec Word p -> URec Word p -> Bool #

Ord (URec Word p) 

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) 

Methods

showsPrec :: Int -> URec Word p -> ShowS #

show :: URec Word p -> String #

showList :: [URec Word p] -> ShowS #

Generic (URec Word p) 

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 #

data URec Word

Used for marking occurrences of Word#

data URec Word = UWord {}
data Vector Word 
type Plain Word # 
type Plain Word = Word
data MVector s Word 
type Rep1 (URec Word) 
type Rep1 (URec Word) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UWord" PrefixI True) (S1 (MetaSel (Just Symbol "uWord#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UWord))
type Rep (URec Word p) 
type Rep (URec Word p) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UWord" PrefixI True) (S1 (MetaSel (Just Symbol "uWord#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UWord))

data Word8 :: * #

8-bit unsigned integer type

Instances

Bounded Word8 
Enum Word8 
Eq Word8 

Methods

(==) :: Word8 -> Word8 -> Bool #

(/=) :: Word8 -> Word8 -> Bool #

Integral Word8 
Data Word8 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word8 -> c Word8 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word8 #

toConstr :: Word8 -> Constr #

dataTypeOf :: Word8 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Word8) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word8) #

gmapT :: (forall b. Data b => b -> b) -> Word8 -> Word8 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word8 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word8 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word8 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word8 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word8 -> m Word8 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word8 -> m Word8 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word8 -> m Word8 #

Num Word8 
Ord Word8 

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 
Real Word8 

Methods

toRational :: Word8 -> Rational #

Show Word8 

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Ix Word8 
Lift Word8 

Methods

lift :: Word8 -> Q Exp #

PrintfArg Word8 
Storable Word8 

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 
FiniteBits Word8 
NFData Word8 

Methods

rnf :: Word8 -> () #

Hashable Word8 

Methods

hashWithSalt :: Int -> Word8 -> Int #

hash :: Word8 -> Int #

Prim Word8 
Unbox Word8 
IsScalar Word8 # 

Methods

scalarType :: ScalarType Word8

IsBounded Word8 # 

Methods

boundedType :: BoundedType Word8

IsNum Word8 # 

Methods

numType :: NumType Word8

IsIntegral Word8 # 

Methods

integralType :: IntegralType Word8

Elt Word8 # 

Methods

eltType :: Word8 -> TupleType (EltRepr Word8)

fromElt :: Word8 -> EltRepr Word8

toElt :: EltRepr Word8 -> Word8

Eq Word8 # 

Methods

(==) :: Exp Word8 -> Exp Word8 -> Exp Bool #

(/=) :: Exp Word8 -> Exp Word8 -> Exp Bool #

Ord Word8 # 
FiniteBits Word8 # 
Bits Word8 # 
Vector Vector Word8 
MVector MVector Word8 
FromIntegral Int Word8 # 

Methods

fromIntegral :: Exp Int -> Exp Word8 #

FromIntegral Int8 Word8 # 
FromIntegral Int16 Word8 # 
FromIntegral Int32 Word8 # 
FromIntegral Int64 Word8 # 
FromIntegral Word Word8 # 
FromIntegral Word8 Double # 
FromIntegral Word8 Float # 
FromIntegral Word8 Int # 

Methods

fromIntegral :: Exp Word8 -> Exp Int #

FromIntegral Word8 Int8 # 
FromIntegral Word8 Int16 # 
FromIntegral Word8 Int32 # 
FromIntegral Word8 Int64 # 
FromIntegral Word8 Word # 
FromIntegral Word8 Word8 # 
FromIntegral Word8 Word16 # 
FromIntegral Word8 Word32 # 
FromIntegral Word8 Word64 # 
FromIntegral Word8 CShort # 
FromIntegral Word8 CUShort # 
FromIntegral Word8 CInt # 
FromIntegral Word8 CUInt # 
FromIntegral Word8 CLong # 
FromIntegral Word8 CULong # 
FromIntegral Word8 CLLong # 
FromIntegral Word8 CULLong # 
FromIntegral Word8 CFloat # 
FromIntegral Word8 CDouble # 
FromIntegral Word16 Word8 # 
FromIntegral Word32 Word8 # 
FromIntegral Word64 Word8 # 
FromIntegral CShort Word8 # 
FromIntegral CUShort Word8 # 
FromIntegral CInt Word8 # 
FromIntegral CUInt Word8 # 
FromIntegral CLong Word8 # 
FromIntegral CULong Word8 # 
FromIntegral CLLong Word8 # 
FromIntegral CULLong Word8 # 
ToFloating Word8 Double # 
ToFloating Word8 Float # 

Methods

toFloating :: Exp Word8 -> Exp Float #

ToFloating Word8 CFloat # 
ToFloating Word8 CDouble # 
Lift Exp Word8 # 

Associated Types

type Plain Word8 :: * #

Methods

lift :: Word8 -> Exp (Plain Word8) #

data Vector Word8 
type Plain Word8 # 
data MVector s Word8 

data Word16 :: * #

16-bit unsigned integer type

Instances

Bounded Word16 
Enum Word16 
Eq Word16 

Methods

(==) :: Word16 -> Word16 -> Bool #

(/=) :: Word16 -> Word16 -> Bool #

Integral Word16 
Data Word16 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word16 -> c Word16 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word16 #

toConstr :: Word16 -> Constr #

dataTypeOf :: Word16 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Word16) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word16) #

gmapT :: (forall b. Data b => b -> b) -> Word16 -> Word16 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word16 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word16 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word16 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word16 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word16 -> m Word16 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word16 -> m Word16 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word16 -> m Word16 #

Num Word16 
Ord Word16 
Read Word16 
Real Word16 
Show Word16 
Ix Word16 
Lift Word16 

Methods

lift :: Word16 -> Q Exp #

PrintfArg Word16 
Storable Word16 
Bits Word16 
FiniteBits Word16 
NFData Word16 

Methods

rnf :: Word16 -> () #

Hashable Word16 

Methods

hashWithSalt :: Int -> Word16 -> Int #

hash :: Word16 -> Int #

Prim Word16 
Unbox Word16 
IsScalar Word16 # 

Methods

scalarType :: ScalarType Word16

IsBounded Word16 # 

Methods

boundedType :: BoundedType Word16

IsNum Word16 # 

Methods

numType :: NumType Word16

IsIntegral Word16 # 

Methods

integralType :: IntegralType Word16

Elt Word16 # 

Methods

eltType :: Word16 -> TupleType (EltRepr Word16)

fromElt :: Word16 -> EltRepr Word16

toElt :: EltRepr Word16 -> Word16

Eq Word16 # 
Ord Word16 # 
FiniteBits Word16 # 
Bits Word16 # 
Vector Vector Word16 
MVector MVector Word16 
FromIntegral Int Word16 # 
FromIntegral Int8 Word16 # 
FromIntegral Int16 Word16 # 
FromIntegral Int32 Word16 # 
FromIntegral Int64 Word16 # 
FromIntegral Word Word16 # 
FromIntegral Word8 Word16 # 
FromIntegral Word16 Double # 
FromIntegral Word16 Float # 
FromIntegral Word16 Int # 
FromIntegral Word16 Int8 # 
FromIntegral Word16 Int16 # 
FromIntegral Word16 Int32 # 
FromIntegral Word16 Int64 # 
FromIntegral Word16 Word # 
FromIntegral Word16 Word8 # 
FromIntegral Word16 Word16 # 
FromIntegral Word16 Word32 # 
FromIntegral Word16 Word64 # 
FromIntegral Word16 CShort # 
FromIntegral Word16 CUShort # 
FromIntegral Word16 CInt # 
FromIntegral Word16 CUInt # 
FromIntegral Word16 CLong # 
FromIntegral Word16 CULong # 
FromIntegral Word16 CLLong # 
FromIntegral Word16 CULLong # 
FromIntegral Word16 CFloat # 
FromIntegral Word16 CDouble # 
FromIntegral Word32 Word16 # 
FromIntegral Word64 Word16 # 
FromIntegral CShort Word16 # 
FromIntegral CUShort Word16 # 
FromIntegral CInt Word16 # 
FromIntegral CUInt Word16 # 
FromIntegral CLong Word16 # 
FromIntegral CULong Word16 # 
FromIntegral CLLong Word16 # 
FromIntegral CULLong Word16 # 
ToFloating Word16 Double # 
ToFloating Word16 Float # 
ToFloating Word16 CFloat # 
ToFloating Word16 CDouble # 
Lift Exp Word16 # 

Associated Types

type Plain Word16 :: * #

Methods

lift :: Word16 -> Exp (Plain Word16) #

data Vector Word16 
type Plain Word16 # 
data MVector s Word16 

data Word32 :: * #

32-bit unsigned integer type

Instances

Bounded Word32 
Enum Word32 
Eq Word32 

Methods

(==) :: Word32 -> Word32 -> Bool #

(/=) :: Word32 -> Word32 -> Bool #

Integral Word32 
Data Word32 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word32 -> c Word32 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word32 #

toConstr :: Word32 -> Constr #

dataTypeOf :: Word32 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Word32) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word32) #

gmapT :: (forall b. Data b => b -> b) -> Word32 -> Word32 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word32 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word32 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word32 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word32 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 #

Num Word32 
Ord Word32 
Read Word32 
Real Word32 
Show Word32 
Ix Word32 
Lift Word32 

Methods

lift :: Word32 -> Q Exp #

PrintfArg Word32 
Storable Word32 
Bits Word32 
FiniteBits Word32 
NFData Word32 

Methods

rnf :: Word32 -> () #

Hashable Word32 

Methods

hashWithSalt :: Int -> Word32 -> Int #

hash :: Word32 -> Int #

Prim Word32 
Unbox Word32 
IsScalar Word32 # 

Methods

scalarType :: ScalarType Word32

IsBounded Word32 # 

Methods

boundedType :: BoundedType Word32

IsNum Word32 # 

Methods

numType :: NumType Word32

IsIntegral Word32 # 

Methods

integralType :: IntegralType Word32

Elt Word32 # 

Methods

eltType :: Word32 -> TupleType (EltRepr Word32)

fromElt :: Word32 -> EltRepr Word32

toElt :: EltRepr Word32 -> Word32

Eq Word32 # 
Ord Word32 # 
FiniteBits Word32 # 
Bits Word32 # 
Vector Vector Word32 
MVector MVector Word32 
FromIntegral Int Word32 # 
FromIntegral Int8 Word32 # 
FromIntegral Int16 Word32 # 
FromIntegral Int32 Word32 # 
FromIntegral Int64 Word32 # 
FromIntegral Word Word32 # 
FromIntegral Word8 Word32 # 
FromIntegral Word16 Word32 # 
FromIntegral Word32 Double # 
FromIntegral Word32 Float # 
FromIntegral Word32 Int # 
FromIntegral Word32 Int8 # 
FromIntegral Word32 Int16 # 
FromIntegral Word32 Int32 # 
FromIntegral Word32 Int64 # 
FromIntegral Word32 Word # 
FromIntegral Word32 Word8 # 
FromIntegral Word32 Word16 # 
FromIntegral Word32 Word32 # 
FromIntegral Word32 Word64 # 
FromIntegral Word32 CShort # 
FromIntegral Word32 CUShort # 
FromIntegral Word32 CInt # 
FromIntegral Word32 CUInt # 
FromIntegral Word32 CLong # 
FromIntegral Word32 CULong # 
FromIntegral Word32 CLLong # 
FromIntegral Word32 CULLong # 
FromIntegral Word32 CFloat # 
FromIntegral Word32 CDouble # 
FromIntegral Word64 Word32 # 
FromIntegral CShort Word32 # 
FromIntegral CUShort Word32 # 
FromIntegral CInt Word32 # 
FromIntegral CUInt Word32 # 
FromIntegral CLong Word32 # 
FromIntegral CULong Word32 # 
FromIntegral CLLong Word32 # 
FromIntegral CULLong Word32 # 
ToFloating Word32 Double # 
ToFloating Word32 Float # 
ToFloating Word32 CFloat # 
ToFloating Word32 CDouble # 
Lift Exp Word32 # 

Associated Types

type Plain Word32 :: * #

Methods

lift :: Word32 -> Exp (Plain Word32) #

data Vector Word32 
type Plain Word32 # 
data MVector s Word32 

data Word64 :: * #

64-bit unsigned integer type

Instances

Bounded Word64 
Enum Word64 
Eq Word64 

Methods

(==) :: Word64 -> Word64 -> Bool #

(/=) :: Word64 -> Word64 -> Bool #

Integral Word64 
Data Word64 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word64 -> c Word64 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word64 #

toConstr :: Word64 -> Constr #

dataTypeOf :: Word64 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Word64) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word64) #

gmapT :: (forall b. Data b => b -> b) -> Word64 -> Word64 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word64 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word64 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word64 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word64 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word64 -> m Word64 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word64 -> m Word64 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word64 -> m Word64 #

Num Word64 
Ord Word64 
Read Word64 
Real Word64 
Show Word64 
Ix Word64 
Lift Word64 

Methods

lift :: Word64 -> Q Exp #

PrintfArg Word64 
Storable Word64 
Bits Word64 
FiniteBits Word64 
NFData Word64 

Methods

rnf :: Word64 -> () #

Hashable Word64 

Methods

hashWithSalt :: Int -> Word64 -> Int #

hash :: Word64 -> Int #

Prim Word64 
Unbox Word64 
IsScalar Word64 # 

Methods

scalarType :: ScalarType Word64

IsBounded Word64 # 

Methods

boundedType :: BoundedType Word64

IsNum Word64 # 

Methods

numType :: NumType Word64

IsIntegral Word64 # 

Methods

integralType :: IntegralType Word64

Elt Word64 # 

Methods

eltType :: Word64 -> TupleType (EltRepr Word64)

fromElt :: Word64 -> EltRepr Word64

toElt :: EltRepr Word64 -> Word64

Eq Word64 # 
Ord Word64 # 
FiniteBits Word64 # 
Bits Word64 # 
Vector Vector Word64 
MVector MVector Word64 
FromIntegral Int Word64 # 
FromIntegral Int8 Word64 # 
FromIntegral Int16 Word64 # 
FromIntegral Int32 Word64 # 
FromIntegral Int64 Word64 # 
FromIntegral Word Word64 # 
FromIntegral Word8 Word64 # 
FromIntegral Word16 Word64 # 
FromIntegral Word32 Word64 # 
FromIntegral Word64 Double # 
FromIntegral Word64 Float # 
FromIntegral Word64 Int # 
FromIntegral Word64 Int8 # 
FromIntegral Word64 Int16 # 
FromIntegral Word64 Int32 # 
FromIntegral Word64 Int64 # 
FromIntegral Word64 Word # 
FromIntegral Word64 Word8 # 
FromIntegral Word64 Word16 # 
FromIntegral Word64 Word32 # 
FromIntegral Word64 Word64 # 
FromIntegral Word64 CShort # 
FromIntegral Word64 CUShort # 
FromIntegral Word64 CInt # 
FromIntegral Word64 CUInt # 
FromIntegral Word64 CLong # 
FromIntegral Word64 CULong # 
FromIntegral Word64 CLLong # 
FromIntegral Word64 CULLong # 
FromIntegral Word64 CFloat # 
FromIntegral Word64 CDouble # 
FromIntegral CShort Word64 # 
FromIntegral CUShort Word64 # 
FromIntegral CInt Word64 # 
FromIntegral CUInt Word64 # 
FromIntegral CLong Word64 # 
FromIntegral CULong Word64 # 
FromIntegral CLLong Word64 # 
FromIntegral CULLong Word64 # 
ToFloating Word64 Double # 
ToFloating Word64 Float # 
ToFloating Word64 CFloat # 
ToFloating Word64 CDouble # 
Lift Exp Word64 # 

Associated Types

type Plain Word64 :: * #

Methods

lift :: Word64 -> Exp (Plain Word64) #

data Vector Word64 
type Plain Word64 # 
data MVector s Word64 

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 

Methods

(==) :: Float -> Float -> Bool #

(/=) :: Float -> Float -> Bool #

Floating Float 
Data Float 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Float -> c Float #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Float #

toConstr :: Float -> Constr #

dataTypeOf :: Float -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Float) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Float) #

gmapT :: (forall b. Data b => b -> b) -> Float -> Float #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r #

gmapQ :: (forall d. Data d => d -> u) -> Float -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Float -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Float -> m Float #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float #

Ord Float 

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 
RealFloat Float 
Lift Float 

Methods

lift :: Float -> Q Exp #

PrintfArg Float 
Storable Float 

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 () #

NFData Float 

Methods

rnf :: Float -> () #

Hashable Float 

Methods

hashWithSalt :: Int -> Float -> Int #

hash :: Float -> Int #

Prim Float 
Unbox Float 
IsScalar Float # 

Methods

scalarType :: ScalarType Float

IsNum Float # 

Methods

numType :: NumType Float

IsFloating Float # 

Methods

floatingType :: FloatingType Float

Elt Float # 

Methods

eltType :: Float -> TupleType (EltRepr Float)

fromElt :: Float -> EltRepr Float

toElt :: EltRepr Float -> Float

Eq Float # 

Methods

(==) :: Exp Float -> Exp Float -> Exp Bool #

(/=) :: Exp Float -> Exp Float -> Exp Bool #

Ord Float # 
RealFrac Float # 

Methods

properFraction :: (Num b, ToFloating b Float, IsIntegral b) => Exp Float -> (Exp b, Exp Float) #

truncate :: (Elt b, IsIntegral b) => Exp Float -> Exp b #

round :: (Elt b, IsIntegral b) => Exp Float -> Exp b #

ceiling :: (Elt b, IsIntegral b) => Exp Float -> Exp b #

floor :: (Elt b, IsIntegral b) => Exp Float -> Exp b #

RealFloat Float # 
Vector Vector Float 
MVector MVector Float 
FromIntegral Int Float # 

Methods

fromIntegral :: Exp Int -> Exp Float #

FromIntegral Int8 Float # 
FromIntegral Int16 Float # 
FromIntegral Int32 Float # 
FromIntegral Int64 Float # 
FromIntegral Word Float # 
FromIntegral Word8 Float # 
FromIntegral Word16 Float # 
FromIntegral Word32 Float # 
FromIntegral Word64 Float # 
FromIntegral CShort Float # 
FromIntegral CUShort Float # 
FromIntegral CInt Float # 
FromIntegral CUInt Float # 
FromIntegral CLong Float # 
FromIntegral CULong Float # 
FromIntegral CLLong Float # 
FromIntegral CULLong Float # 
ToFloating Double Float # 
ToFloating Float Double # 
ToFloating Float Float # 

Methods

toFloating :: Exp Float -> Exp Float #

ToFloating Float CFloat # 
ToFloating Float CDouble # 
ToFloating Int Float # 

Methods

toFloating :: Exp Int -> Exp Float #

ToFloating Int8 Float # 

Methods

toFloating :: Exp Int8 -> Exp Float #

ToFloating Int16 Float # 

Methods

toFloating :: Exp Int16 -> Exp Float #

ToFloating Int32 Float # 

Methods

toFloating :: Exp Int32 -> Exp Float #

ToFloating Int64 Float # 

Methods

toFloating :: Exp Int64 -> Exp Float #

ToFloating Word Float # 

Methods

toFloating :: Exp Word -> Exp Float #

ToFloating Word8 Float # 

Methods

toFloating :: Exp Word8 -> Exp Float #

ToFloating Word16 Float # 
ToFloating Word32 Float # 
ToFloating Word64 Float # 
ToFloating CShort Float # 
ToFloating CUShort Float # 
ToFloating CInt Float # 

Methods

toFloating :: Exp CInt -> Exp Float #

ToFloating CUInt Float # 

Methods

toFloating :: Exp CUInt -> Exp Float #

ToFloating CLong Float # 

Methods

toFloating :: Exp CLong -> Exp Float #

ToFloating CULong Float # 
ToFloating CLLong Float # 
ToFloating CULLong Float # 
ToFloating CFloat Float # 
ToFloating CDouble Float # 
Lift Exp Float # 

Associated Types

type Plain Float :: * #

Methods

lift :: Float -> Exp (Plain Float) #

Functor (URec Float) 

Methods

fmap :: (a -> b) -> URec Float a -> URec Float b #

(<$) :: a -> URec Float b -> URec Float a #

Foldable (URec Float) 

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) 

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) #

Generic1 (URec Float) 

Associated Types

type Rep1 (URec Float :: * -> *) :: * -> * #

Methods

from1 :: URec Float a -> Rep1 (URec Float) a #

to1 :: Rep1 (URec Float) a -> URec Float a #

Eq (URec Float p) 

Methods

(==) :: URec Float p -> URec Float p -> Bool #

(/=) :: URec Float p -> URec Float p -> Bool #

Ord (URec Float p) 

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) 

Methods

showsPrec :: Int -> URec Float p -> ShowS #

show :: URec Float p -> String #

showList :: [URec Float p] -> ShowS #

Generic (URec Float p) 

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 #

data URec Float

Used for marking occurrences of Float#

data Vector Float 
type Plain Float # 
data MVector s Float 
type Rep1 (URec Float) 
type Rep1 (URec Float) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UFloat" PrefixI True) (S1 (MetaSel (Just Symbol "uFloat#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UFloat))
type Rep (URec Float p) 
type Rep (URec Float p) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UFloat" PrefixI True) (S1 (MetaSel (Just Symbol "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 

Methods

(==) :: Double -> Double -> Bool #

(/=) :: Double -> Double -> Bool #

Floating Double 
Data Double 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Double -> c Double #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Double #

toConstr :: Double -> Constr #

dataTypeOf :: Double -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Double) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Double) #

gmapT :: (forall b. Data b => b -> b) -> Double -> Double #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r #

gmapQ :: (forall d. Data d => d -> u) -> Double -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Double -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Double -> m Double #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double #

Ord Double 
Read Double 
RealFloat Double 
Lift Double 

Methods

lift :: Double -> Q Exp #

PrintfArg Double 
Storable Double 
NFData Double 

Methods

rnf :: Double -> () #

Hashable Double 

Methods

hashWithSalt :: Int -> Double -> Int #

hash :: Double -> Int #

Prim Double 
Unbox Double 
IsScalar Double # 

Methods

scalarType :: ScalarType Double

IsNum Double # 

Methods

numType :: NumType Double

IsFloating Double # 

Methods

floatingType :: FloatingType Double

Elt Double # 

Methods

eltType :: Double -> TupleType (EltRepr Double)

fromElt :: Double -> EltRepr Double

toElt :: EltRepr Double -> Double

Eq Double # 
Ord Double # 
RealFrac Double # 

Methods

properFraction :: (Num b, ToFloating b Double, IsIntegral b) => Exp Double -> (Exp b, Exp Double) #

truncate :: (Elt b, IsIntegral b) => Exp Double -> Exp b #

round :: (Elt b, IsIntegral b) => Exp Double -> Exp b #

ceiling :: (Elt b, IsIntegral b) => Exp Double -> Exp b #

floor :: (Elt b, IsIntegral b) => Exp Double -> Exp b #

RealFloat Double # 
Vector Vector Double 
MVector MVector Double 
FromIntegral Int Double # 
FromIntegral Int8 Double # 
FromIntegral Int16 Double # 
FromIntegral Int32 Double # 
FromIntegral Int64 Double # 
FromIntegral Word Double # 
FromIntegral Word8 Double # 
FromIntegral Word16 Double # 
FromIntegral Word32 Double # 
FromIntegral Word64 Double # 
FromIntegral CShort Double # 
FromIntegral CUShort Double # 
FromIntegral CInt Double # 
FromIntegral CUInt Double # 
FromIntegral CLong Double # 
FromIntegral CULong Double # 
FromIntegral CLLong Double # 
FromIntegral CULLong Double # 
ToFloating Double Double # 
ToFloating Double Float # 
ToFloating Double CFloat # 
ToFloating Double CDouble # 
ToFloating Float Double # 
ToFloating Int Double # 

Methods

toFloating :: Exp Int -> Exp Double #

ToFloating Int8 Double # 

Methods

toFloating :: Exp Int8 -> Exp Double #

ToFloating Int16 Double # 
ToFloating Int32 Double # 
ToFloating Int64 Double # 
ToFloating Word Double # 

Methods

toFloating :: Exp Word -> Exp Double #

ToFloating Word8 Double # 
ToFloating Word16 Double # 
ToFloating Word32 Double # 
ToFloating Word64 Double # 
ToFloating CShort Double # 
ToFloating CUShort Double # 
ToFloating CInt Double # 

Methods

toFloating :: Exp CInt -> Exp Double #

ToFloating CUInt Double # 
ToFloating CLong Double # 
ToFloating CULong Double # 
ToFloating CLLong Double # 
ToFloating CULLong Double # 
ToFloating CFloat Double # 
ToFloating CDouble Double # 
Lift Exp Double # 

Associated Types

type Plain Double :: * #

Methods

lift :: Double -> Exp (Plain Double) #

Functor (URec Double) 

Methods

fmap :: (a -> b) -> URec Double a -> URec Double b #

(<$) :: a -> URec Double b -> URec Double a #

Foldable (URec Double) 

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) 

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) #

Generic1 (URec Double) 

Associated Types

type Rep1 (URec Double :: * -> *) :: * -> * #

Methods

from1 :: URec Double a -> Rep1 (URec Double) a #

to1 :: Rep1 (URec Double) a -> URec Double a #

Eq (URec Double p) 

Methods

(==) :: URec Double p -> URec Double p -> Bool #

(/=) :: URec Double p -> URec Double p -> Bool #

Ord (URec Double p) 

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) 

Methods

showsPrec :: Int -> URec Double p -> ShowS #

show :: URec Double p -> String #

showList :: [URec Double p] -> ShowS #

Generic (URec Double p) 

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 #

data URec Double

Used for marking occurrences of Double#

data Vector Double 
type Plain Double # 
data MVector s Double 
type Rep1 (URec Double) 
type Rep1 (URec Double) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UDouble" PrefixI True) (S1 (MetaSel (Just Symbol "uDouble#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UDouble))
type Rep (URec Double p) 
type Rep (URec Double p) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UDouble" PrefixI True) (S1 (MetaSel (Just Symbol "uDouble#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UDouble))

data Bool :: * #

Constructors

False 
True 

Instances

Bounded Bool 
Enum Bool 

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 

Methods

(==) :: Bool -> Bool -> Bool #

(/=) :: Bool -> Bool -> Bool #

Data Bool 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bool -> c Bool #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bool #

toConstr :: Bool -> Constr #

dataTypeOf :: Bool -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Bool) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bool) #

gmapT :: (forall b. Data b => b -> b) -> Bool -> Bool #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bool -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bool -> r #

gmapQ :: (forall d. Data d => d -> u) -> Bool -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Bool -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bool -> m Bool #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m Bool #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m Bool #

Ord Bool 

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 
Show Bool 

Methods

showsPrec :: Int -> Bool -> ShowS #

show :: Bool -> String #

showList :: [Bool] -> ShowS #

Ix Bool 

Methods

range :: (Bool, Bool) -> [Bool] #

index :: (Bool, Bool) -> Bool -> Int #

unsafeIndex :: (Bool, Bool) -> Bool -> Int

inRange :: (Bool, Bool) -> Bool -> Bool #

rangeSize :: (Bool, Bool) -> Int #

unsafeRangeSize :: (Bool, Bool) -> Int

Generic Bool 

Associated Types

type Rep Bool :: * -> * #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Lift Bool 

Methods

lift :: Bool -> Q Exp #

Storable Bool 

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 
FiniteBits Bool 
NFData Bool 

Methods

rnf :: Bool -> () #

Hashable Bool 

Methods

hashWithSalt :: Int -> Bool -> Int #

hash :: Bool -> Int #

Unbox Bool 
IsScalar Bool # 

Methods

scalarType :: ScalarType Bool

IsBounded Bool # 

Methods

boundedType :: BoundedType Bool

IsNonNum Bool # 

Methods

nonNumType :: NonNumType Bool

Elt Bool # 

Methods

eltType :: Bool -> TupleType (EltRepr Bool)

fromElt :: Bool -> EltRepr Bool

toElt :: EltRepr Bool -> Bool

Eq Bool # 

Methods

(==) :: Exp Bool -> Exp Bool -> Exp Bool #

(/=) :: Exp Bool -> Exp Bool -> Exp Bool #

Ord Bool # 

Methods

(<) :: Exp Bool -> Exp Bool -> Exp Bool #

(>) :: Exp Bool -> Exp Bool -> Exp Bool #

(<=) :: Exp Bool -> Exp Bool -> Exp Bool #

(>=) :: Exp Bool -> Exp Bool -> Exp Bool #

min :: Exp Bool -> Exp Bool -> Exp Bool #

max :: Exp Bool -> Exp Bool -> Exp Bool #

FiniteBits Bool # 
Bits Bool # 
SingI Bool False 

Methods

sing :: Sing False a

SingI Bool True 

Methods

sing :: Sing True a

Vector Vector Bool 
MVector MVector Bool 
Lift Exp Bool # 

Associated Types

type Plain Bool :: * #

Methods

lift :: Bool -> Exp (Plain Bool) #

SingKind Bool (KProxy Bool) 

Associated Types

type DemoteRep (KProxy Bool) (kparam :: KProxy (KProxy Bool)) :: *

Methods

fromSing :: Sing (KProxy Bool) a -> DemoteRep (KProxy Bool) kparam

type Rep Bool 
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 Bool 
data Sing Bool where
data Vector Bool 
type Plain Bool # 
type Plain Bool = Bool
data MVector s Bool 
type (==) Bool a b 
type (==) Bool a b = EqBool a b
type DemoteRep Bool (KProxy Bool) 
type DemoteRep Bool (KProxy Bool) = Bool

data Char :: * #

The character type Char is an enumeration whose values represent Unicode (or equivalently ISO/IEC 10646) 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 
Enum Char 

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 

Methods

(==) :: Char -> Char -> Bool #

(/=) :: Char -> Char -> Bool #

Data Char 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Char -> c Char #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Char #

toConstr :: Char -> Constr #

dataTypeOf :: Char -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Char) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Char) #

gmapT :: (forall b. Data b => b -> b) -> Char -> Char #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r #

gmapQ :: (forall d. Data d => d -> u) -> Char -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Char -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Char -> m Char #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char #

Ord Char 

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 
Show Char 

Methods

showsPrec :: Int -> Char -> ShowS #

show :: Char -> String #

showList :: [Char] -> ShowS #

Ix Char 

Methods

range :: (Char, Char) -> [Char] #

index :: (Char, Char) -> Char -> Int #

unsafeIndex :: (Char, Char) -> Char -> Int

inRange :: (Char, Char) -> Char -> Bool #

rangeSize :: (Char, Char) -> Int #

unsafeRangeSize :: (Char, Char) -> Int

Lift Char 

Methods

lift :: Char -> Q Exp #

PrintfArg Char 
IsChar Char 

Methods

toChar :: Char -> Char #

fromChar :: Char -> Char #

Storable Char 

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 () #

NFData Char 

Methods

rnf :: Char -> () #

Hashable Char 

Methods

hashWithSalt :: Int -> Char -> Int #

hash :: Char -> Int #

Prim Char 
ErrorList Char 

Methods

listMsg :: String -> [Char] #

Unbox Char 
IsScalar Char # 

Methods

scalarType :: ScalarType Char

IsBounded Char # 

Methods

boundedType :: BoundedType Char

IsNonNum Char # 

Methods

nonNumType :: NonNumType Char

Elt Char # 

Methods

eltType :: Char -> TupleType (EltRepr Char)

fromElt :: Char -> EltRepr Char

toElt :: EltRepr Char -> Char

Eq Char # 

Methods

(==) :: Exp Char -> Exp Char -> Exp Bool #

(/=) :: Exp Char -> Exp Char -> Exp Bool #

Ord Char # 

Methods

(<) :: Exp Char -> Exp Char -> Exp Bool #

(>) :: Exp Char -> Exp Char -> Exp Bool #

(<=) :: Exp Char -> Exp Char -> Exp Bool #

(>=) :: Exp Char -> Exp Char -> Exp Bool #

min :: Exp Char -> Exp Char -> Exp Char #

max :: Exp Char -> Exp Char -> Exp Char #

Vector Vector Char 
MVector MVector Char 
Lift Exp Char # 

Associated Types

type Plain Char :: * #

Methods

lift :: Char -> Exp (Plain Char) #

Functor (URec Char) 

Methods

fmap :: (a -> b) -> URec Char a -> URec Char b #

(<$) :: a -> URec Char b -> URec Char a #

IsString (Seq Char) 

Methods

fromString :: String -> Seq Char #

Foldable (URec Char) 

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) 

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) #

Generic1 (URec Char) 

Associated Types

type Rep1 (URec Char :: * -> *) :: * -> * #

Methods

from1 :: URec Char a -> Rep1 (URec Char) a #

to1 :: Rep1 (URec Char) a -> URec Char a #

Eq (URec Char p) 

Methods

(==) :: URec Char p -> URec Char p -> Bool #

(/=) :: URec Char p -> URec Char p -> Bool #

Ord (URec Char p) 

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) 

Methods

showsPrec :: Int -> URec Char p -> ShowS #

show :: URec Char p -> String #

showList :: [URec Char p] -> ShowS #

Generic (URec Char p) 

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 #

data URec Char

Used for marking occurrences of Char#

data URec Char = UChar {}
data Vector Char 
type Plain Char # 
type Plain Char = Char
data MVector s Char 
type Rep1 (URec Char) 
type Rep1 (URec Char) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UChar" PrefixI True) (S1 (MetaSel (Just Symbol "uChar#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UChar))
type Rep (URec Char p) 
type Rep (URec Char p) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UChar" PrefixI True) (S1 (MetaSel (Just Symbol "uChar#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UChar))

data CFloat :: * #

Haskell type representing the C float type.

Instances

Enum CFloat 
Eq CFloat 

Methods

(==) :: CFloat -> CFloat -> Bool #

(/=) :: CFloat -> CFloat -> Bool #

Floating CFloat 
Fractional CFloat 
Num CFloat 
Ord CFloat 
Read CFloat 
Real CFloat 
RealFloat CFloat 
RealFrac CFloat 

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 
Storable CFloat 
NFData CFloat

Since: 1.4.0.0

Methods

rnf :: CFloat -> () #

IsScalar CFloat # 

Methods

scalarType :: ScalarType CFloat

IsNum CFloat # 

Methods

numType :: NumType CFloat

IsFloating CFloat # 

Methods

floatingType :: FloatingType CFloat

Elt CFloat # 

Methods

eltType :: CFloat -> TupleType (EltRepr CFloat)

fromElt :: CFloat -> EltRepr CFloat

toElt :: EltRepr CFloat -> CFloat

Eq CFloat # 
Ord CFloat # 
RealFrac CFloat # 

Methods

properFraction :: (Num b, ToFloating b CFloat, IsIntegral b) => Exp CFloat -> (Exp b, Exp CFloat) #

truncate :: (Elt b, IsIntegral b) => Exp CFloat -> Exp b #

round :: (Elt b, IsIntegral b) => Exp CFloat -> Exp b #

ceiling :: (Elt b, IsIntegral b) => Exp CFloat -> Exp b #

floor :: (Elt b, IsIntegral b) => Exp CFloat -> Exp b #

RealFloat CFloat # 
FromIntegral Int CFloat # 
FromIntegral Int8 CFloat # 
FromIntegral Int16 CFloat # 
FromIntegral Int32 CFloat # 
FromIntegral Int64 CFloat # 
FromIntegral Word CFloat # 
FromIntegral Word8 CFloat # 
FromIntegral Word16 CFloat # 
FromIntegral Word32 CFloat # 
FromIntegral Word64 CFloat # 
FromIntegral CShort CFloat # 
FromIntegral CUShort CFloat # 
FromIntegral CInt CFloat # 
FromIntegral CUInt CFloat # 
FromIntegral CLong CFloat # 
FromIntegral CULong CFloat # 
FromIntegral CLLong CFloat # 
FromIntegral CULLong CFloat # 
ToFloating Double CFloat # 
ToFloating Float CFloat # 
ToFloating Int CFloat # 

Methods

toFloating :: Exp Int -> Exp CFloat #

ToFloating Int8 CFloat # 

Methods

toFloating :: Exp Int8 -> Exp CFloat #

ToFloating Int16 CFloat # 
ToFloating Int32 CFloat # 
ToFloating Int64 CFloat # 
ToFloating Word CFloat # 

Methods

toFloating :: Exp Word -> Exp CFloat #

ToFloating Word8 CFloat # 
ToFloating Word16 CFloat # 
ToFloating Word32 CFloat # 
ToFloating Word64 CFloat # 
ToFloating CShort CFloat # 
ToFloating CUShort CFloat # 
ToFloating CInt CFloat # 

Methods

toFloating :: Exp CInt -> Exp CFloat #

ToFloating CUInt CFloat # 
ToFloating CLong CFloat # 
ToFloating CULong CFloat # 
ToFloating CLLong CFloat # 
ToFloating CULLong CFloat # 
ToFloating CFloat Double # 
ToFloating CFloat Float # 
ToFloating CFloat CFloat # 
ToFloating CFloat CDouble # 
ToFloating CDouble CFloat # 
Lift Exp CFloat # 

Associated Types

type Plain CFloat :: * #

Methods

lift :: CFloat -> Exp (Plain CFloat) #

type Plain CFloat # 

data CDouble :: * #

Haskell type representing the C double type.

Instances

Enum CDouble 
Eq CDouble 

Methods

(==) :: CDouble -> CDouble -> Bool #

(/=) :: CDouble -> CDouble -> Bool #

Floating CDouble 
Fractional CDouble 
Num CDouble 
Ord CDouble 
Read CDouble 
Real CDouble 
RealFloat CDouble 
RealFrac CDouble 

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 
Storable CDouble 
NFData CDouble

Since: 1.4.0.0

Methods

rnf :: CDouble -> () #

IsScalar CDouble # 

Methods

scalarType :: ScalarType CDouble

IsNum CDouble # 

Methods

numType :: NumType CDouble

IsFloating CDouble # 

Methods

floatingType :: FloatingType CDouble

Elt CDouble # 

Methods

eltType :: CDouble -> TupleType (EltRepr CDouble)

fromElt :: CDouble -> EltRepr CDouble

toElt :: EltRepr CDouble -> CDouble

Eq CDouble # 
Ord CDouble # 
RealFrac CDouble # 

Methods

properFraction :: (Num b, ToFloating b CDouble, IsIntegral b) => Exp CDouble -> (Exp b, Exp CDouble) #

truncate :: (Elt b, IsIntegral b) => Exp CDouble -> Exp b #

round :: (Elt b, IsIntegral b) => Exp CDouble -> Exp b #

ceiling :: (Elt b, IsIntegral b) => Exp CDouble -> Exp b #

floor :: (Elt b, IsIntegral b) => Exp CDouble -> Exp b #

RealFloat CDouble # 
FromIntegral Int CDouble # 
FromIntegral Int8 CDouble # 
FromIntegral Int16 CDouble # 
FromIntegral Int32 CDouble # 
FromIntegral Int64 CDouble # 
FromIntegral Word CDouble # 
FromIntegral Word8 CDouble # 
FromIntegral Word16 CDouble # 
FromIntegral Word32 CDouble # 
FromIntegral Word64 CDouble # 
FromIntegral CShort CDouble # 
FromIntegral CUShort CDouble # 
FromIntegral CInt CDouble # 
FromIntegral CUInt CDouble # 
FromIntegral CLong CDouble # 
FromIntegral CULong CDouble # 
FromIntegral CLLong CDouble # 
FromIntegral CULLong CDouble # 
ToFloating Double CDouble # 
ToFloating Float CDouble # 
ToFloating Int CDouble # 

Methods

toFloating :: Exp Int -> Exp CDouble #

ToFloating Int8 CDouble # 
ToFloating Int16 CDouble # 
ToFloating Int32 CDouble # 
ToFloating Int64 CDouble # 
ToFloating Word CDouble # 
ToFloating Word8 CDouble # 
ToFloating Word16 CDouble # 
ToFloating Word32 CDouble # 
ToFloating Word64 CDouble # 
ToFloating CShort CDouble # 
ToFloating CUShort CDouble # 
ToFloating CInt CDouble # 
ToFloating CUInt CDouble # 
ToFloating CLong CDouble # 
ToFloating CULong CDouble # 
ToFloating CLLong CDouble # 
ToFloating CULLong CDouble # 
ToFloating CFloat CDouble # 
ToFloating CDouble Double # 
ToFloating CDouble Float # 
ToFloating CDouble CFloat # 
ToFloating CDouble CDouble # 
Lift Exp CDouble # 

Associated Types

type Plain CDouble :: * #

Methods

lift :: CDouble -> Exp (Plain CDouble) #

type Plain CDouble # 

data CShort :: * #

Haskell type representing the C short type.

Instances

Bounded CShort 
Enum CShort 
Eq CShort 

Methods

(==) :: CShort -> CShort -> Bool #

(/=) :: CShort -> CShort -> Bool #

Integral CShort 
Num CShort 
Ord CShort 
Read CShort 
Real CShort 
Show CShort 
Storable CShort 
Bits CShort 
FiniteBits CShort 
NFData CShort

Since: 1.4.0.0

Methods

rnf :: CShort -> () #

IsScalar CShort # 

Methods

scalarType :: ScalarType CShort

IsBounded CShort # 

Methods

boundedType :: BoundedType CShort

IsNum CShort # 

Methods

numType :: NumType CShort

IsIntegral CShort # 

Methods

integralType :: IntegralType CShort

Elt CShort # 

Methods

eltType :: CShort -> TupleType (EltRepr CShort)

fromElt :: CShort -> EltRepr CShort

toElt :: EltRepr CShort -> CShort

Eq CShort # 
Ord CShort # 
FiniteBits CShort # 
Bits CShort # 
FromIntegral Int CShort # 
FromIntegral Int8 CShort # 
FromIntegral Int16 CShort # 
FromIntegral Int32 CShort # 
FromIntegral Int64 CShort # 
FromIntegral Word CShort # 
FromIntegral Word8 CShort # 
FromIntegral Word16 CShort # 
FromIntegral Word32 CShort # 
FromIntegral Word64 CShort # 
FromIntegral CShort Double # 
FromIntegral CShort Float # 
FromIntegral CShort Int # 
FromIntegral CShort Int8 # 
FromIntegral CShort Int16 # 
FromIntegral CShort Int32 # 
FromIntegral CShort Int64 # 
FromIntegral CShort Word # 
FromIntegral CShort Word8 # 
FromIntegral CShort Word16 # 
FromIntegral CShort Word32 # 
FromIntegral CShort Word64 # 
FromIntegral CShort CShort # 
FromIntegral CShort CUShort # 
FromIntegral CShort CInt # 
FromIntegral CShort CUInt # 
FromIntegral CShort CLong # 
FromIntegral CShort CULong # 
FromIntegral CShort CLLong # 
FromIntegral CShort CULLong # 
FromIntegral CShort CFloat # 
FromIntegral CShort CDouble # 
FromIntegral CUShort CShort # 
FromIntegral CInt CShort # 
FromIntegral CUInt CShort # 
FromIntegral CLong CShort # 
FromIntegral CULong CShort # 
FromIntegral CLLong CShort # 
FromIntegral CULLong CShort # 
ToFloating CShort Double # 
ToFloating CShort Float # 
ToFloating CShort CFloat # 
ToFloating CShort CDouble # 
Lift Exp CShort # 

Associated Types

type Plain CShort :: * #

Methods

lift :: CShort -> Exp (Plain CShort) #

type Plain CShort # 

data CUShort :: * #

Haskell type representing the C unsigned short type.

Instances

Bounded CUShort 
Enum CUShort 
Eq CUShort 

Methods

(==) :: CUShort -> CUShort -> Bool #

(/=) :: CUShort -> CUShort -> Bool #

Integral CUShort 
Num CUShort 
Ord CUShort 
Read CUShort 
Real CUShort 
Show CUShort 
Storable CUShort 
Bits CUShort 
FiniteBits CUShort 
NFData CUShort

Since: 1.4.0.0

Methods

rnf :: CUShort -> () #

IsScalar CUShort # 

Methods

scalarType :: ScalarType CUShort

IsBounded CUShort # 

Methods

boundedType :: BoundedType CUShort

IsNum CUShort # 

Methods

numType :: NumType CUShort

IsIntegral CUShort # 

Methods

integralType :: IntegralType CUShort

Elt CUShort # 

Methods

eltType :: CUShort -> TupleType (EltRepr CUShort)

fromElt :: CUShort -> EltRepr CUShort

toElt :: EltRepr CUShort -> CUShort

Eq CUShort # 
Ord CUShort # 
FiniteBits CUShort # 
Bits CUShort # 
FromIntegral Int CUShort # 
FromIntegral Int8 CUShort # 
FromIntegral Int16 CUShort # 
FromIntegral Int32 CUShort # 
FromIntegral Int64 CUShort # 
FromIntegral Word CUShort # 
FromIntegral Word8 CUShort # 
FromIntegral Word16 CUShort # 
FromIntegral Word32 CUShort # 
FromIntegral Word64 CUShort # 
FromIntegral CShort CUShort # 
FromIntegral CUShort Double # 
FromIntegral CUShort Float # 
FromIntegral CUShort Int # 
FromIntegral CUShort Int8 # 
FromIntegral CUShort Int16 # 
FromIntegral CUShort Int32 # 
FromIntegral CUShort Int64 # 
FromIntegral CUShort Word # 
FromIntegral CUShort Word8 # 
FromIntegral CUShort Word16 # 
FromIntegral CUShort Word32 # 
FromIntegral CUShort Word64 # 
FromIntegral CUShort CShort # 
FromIntegral CUShort CUShort # 
FromIntegral CUShort CInt # 
FromIntegral CUShort CUInt # 
FromIntegral CUShort CLong # 
FromIntegral CUShort CULong # 
FromIntegral CUShort CLLong # 
FromIntegral CUShort CULLong # 
FromIntegral CUShort CFloat # 
FromIntegral CUShort CDouble # 
FromIntegral CInt CUShort # 
FromIntegral CUInt CUShort # 
FromIntegral CLong CUShort # 
FromIntegral CULong CUShort # 
FromIntegral CLLong CUShort # 
FromIntegral CULLong CUShort # 
ToFloating CUShort Double # 
ToFloating CUShort Float # 
ToFloating CUShort CFloat # 
ToFloating CUShort CDouble # 
Lift Exp CUShort # 

Associated Types

type Plain CUShort :: * #

Methods

lift :: CUShort -> Exp (Plain CUShort) #

type Plain CUShort # 

data CInt :: * #

Haskell type representing the C int type.

Instances

Bounded CInt 
Enum CInt 

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 

Methods

(==) :: CInt -> CInt -> Bool #

(/=) :: CInt -> CInt -> Bool #

Integral CInt 

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 

Methods

(+) :: CInt -> CInt -> CInt #

(-) :: CInt -> CInt -> CInt #

(*) :: CInt -> CInt -> CInt #

negate :: CInt -> CInt #

abs :: CInt -> CInt #

signum :: CInt -> CInt #

fromInteger :: Integer -> CInt #

Ord CInt 

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 
Real CInt 

Methods

toRational :: CInt -> Rational #

Show CInt 

Methods

showsPrec :: Int -> CInt -> ShowS #

show :: CInt -> String #

showList :: [CInt] -> ShowS #

Storable CInt 

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 
FiniteBits CInt 
NFData CInt

Since: 1.4.0.0

Methods

rnf :: CInt -> () #

IsScalar CInt # 

Methods

scalarType :: ScalarType CInt

IsBounded CInt # 

Methods

boundedType :: BoundedType CInt

IsNum CInt # 

Methods

numType :: NumType CInt

IsIntegral CInt # 

Methods

integralType :: IntegralType CInt

Elt CInt # 

Methods

eltType :: CInt -> TupleType (EltRepr CInt)

fromElt :: CInt -> EltRepr CInt

toElt :: EltRepr CInt -> CInt

Eq CInt # 

Methods

(==) :: Exp CInt -> Exp CInt -> Exp Bool #

(/=) :: Exp CInt -> Exp CInt -> Exp Bool #

Ord CInt # 

Methods

(<) :: Exp CInt -> Exp CInt -> Exp Bool #

(>) :: Exp CInt -> Exp CInt -> Exp Bool #

(<=) :: Exp CInt -> Exp CInt -> Exp Bool #

(>=) :: Exp CInt -> Exp CInt -> Exp Bool #

min :: Exp CInt -> Exp CInt -> Exp CInt #

max :: Exp CInt -> Exp CInt -> Exp CInt #

FiniteBits CInt # 
Bits CInt # 
FromIntegral Int CInt # 

Methods

fromIntegral :: Exp Int -> Exp CInt #

FromIntegral Int8 CInt # 

Methods

fromIntegral :: Exp Int8 -> Exp CInt #

FromIntegral Int16 CInt # 
FromIntegral Int32 CInt # 
FromIntegral Int64 CInt # 
FromIntegral Word CInt # 

Methods

fromIntegral :: Exp Word -> Exp CInt #

FromIntegral Word8 CInt # 
FromIntegral Word16 CInt # 
FromIntegral Word32 CInt # 
FromIntegral Word64 CInt # 
FromIntegral CShort CInt # 
FromIntegral CUShort CInt # 
FromIntegral CInt Double # 
FromIntegral CInt Float # 
FromIntegral CInt Int # 

Methods

fromIntegral :: Exp CInt -> Exp Int #

FromIntegral CInt Int8 # 

Methods

fromIntegral :: Exp CInt -> Exp Int8 #

FromIntegral CInt Int16 # 
FromIntegral CInt Int32 # 
FromIntegral CInt Int64 # 
FromIntegral CInt Word # 

Methods

fromIntegral :: Exp CInt -> Exp Word #

FromIntegral CInt Word8 # 
FromIntegral CInt Word16 # 
FromIntegral CInt Word32 # 
FromIntegral CInt Word64 # 
FromIntegral CInt CShort # 
FromIntegral CInt CUShort # 
FromIntegral CInt CInt # 

Methods

fromIntegral :: Exp CInt -> Exp CInt #

FromIntegral CInt CUInt # 
FromIntegral CInt CLong # 
FromIntegral CInt CULong # 
FromIntegral CInt CLLong # 
FromIntegral CInt CULLong # 
FromIntegral CInt CFloat # 
FromIntegral CInt CDouble # 
FromIntegral CUInt CInt # 
FromIntegral CLong CInt # 
FromIntegral CULong CInt # 
FromIntegral CLLong CInt # 
FromIntegral CULLong CInt # 
ToFloating CInt Double # 

Methods

toFloating :: Exp CInt -> Exp Double #

ToFloating CInt Float # 

Methods

toFloating :: Exp CInt -> Exp Float #

ToFloating CInt CFloat # 

Methods

toFloating :: Exp CInt -> Exp CFloat #

ToFloating CInt CDouble # 
Lift Exp CInt # 

Associated Types

type Plain CInt :: * #

Methods

lift :: CInt -> Exp (Plain CInt) #

type Plain CInt # 
type Plain CInt = CInt

data CUInt :: * #

Haskell type representing the C unsigned int type.

Instances

Bounded CUInt 
Enum CUInt 
Eq CUInt 

Methods

(==) :: CUInt -> CUInt -> Bool #

(/=) :: CUInt -> CUInt -> Bool #

Integral CUInt 
Num CUInt 
Ord CUInt 

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 
Real CUInt 

Methods

toRational :: CUInt -> Rational #

Show CUInt 

Methods

showsPrec :: Int -> CUInt -> ShowS #

show :: CUInt -> String #

showList :: [CUInt] -> ShowS #

Storable CUInt 

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 
FiniteBits CUInt 
NFData CUInt

Since: 1.4.0.0

Methods

rnf :: CUInt -> () #

IsScalar CUInt # 

Methods

scalarType :: ScalarType CUInt

IsBounded CUInt # 

Methods

boundedType :: BoundedType CUInt

IsNum CUInt # 

Methods

numType :: NumType CUInt

IsIntegral CUInt # 

Methods

integralType :: IntegralType CUInt

Elt CUInt # 

Methods

eltType :: CUInt -> TupleType (EltRepr CUInt)

fromElt :: CUInt -> EltRepr CUInt

toElt :: EltRepr CUInt -> CUInt

Eq CUInt # 

Methods

(==) :: Exp CUInt -> Exp CUInt -> Exp Bool #

(/=) :: Exp CUInt -> Exp CUInt -> Exp Bool #

Ord CUInt # 
FiniteBits CUInt # 
Bits CUInt # 
FromIntegral Int CUInt # 

Methods

fromIntegral :: Exp Int -> Exp CUInt #

FromIntegral Int8 CUInt # 
FromIntegral Int16 CUInt # 
FromIntegral Int32 CUInt # 
FromIntegral Int64 CUInt # 
FromIntegral Word CUInt # 
FromIntegral Word8 CUInt # 
FromIntegral Word16 CUInt # 
FromIntegral Word32 CUInt # 
FromIntegral Word64 CUInt # 
FromIntegral CShort CUInt # 
FromIntegral CUShort CUInt # 
FromIntegral CInt CUInt # 
FromIntegral CUInt Double # 
FromIntegral CUInt Float # 
FromIntegral CUInt Int # 

Methods

fromIntegral :: Exp CUInt -> Exp Int #

FromIntegral CUInt Int8 # 
FromIntegral CUInt Int16 # 
FromIntegral CUInt Int32 # 
FromIntegral CUInt Int64 # 
FromIntegral CUInt Word # 
FromIntegral CUInt Word8 # 
FromIntegral CUInt Word16 # 
FromIntegral CUInt Word32 # 
FromIntegral CUInt Word64 # 
FromIntegral CUInt CShort # 
FromIntegral CUInt CUShort # 
FromIntegral CUInt CInt # 
FromIntegral CUInt CUInt # 
FromIntegral CUInt CLong # 
FromIntegral CUInt CULong # 
FromIntegral CUInt CLLong # 
FromIntegral CUInt CULLong # 
FromIntegral CUInt CFloat # 
FromIntegral CUInt CDouble # 
FromIntegral CLong CUInt # 
FromIntegral CULong CUInt # 
FromIntegral CLLong CUInt # 
FromIntegral CULLong CUInt # 
ToFloating CUInt Double # 
ToFloating CUInt Float # 

Methods

toFloating :: Exp CUInt -> Exp Float #

ToFloating CUInt CFloat # 
ToFloating CUInt CDouble # 
Lift Exp CUInt # 

Associated Types

type Plain CUInt :: * #

Methods

lift :: CUInt -> Exp (Plain CUInt) #

type Plain CUInt # 

data CLong :: * #

Haskell type representing the C long type.

Instances

Bounded CLong 
Enum CLong 
Eq CLong 

Methods

(==) :: CLong -> CLong -> Bool #

(/=) :: CLong -> CLong -> Bool #

Integral CLong 
Num CLong 
Ord CLong 

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 
Real CLong 

Methods

toRational :: CLong -> Rational #

Show CLong 

Methods

showsPrec :: Int -> CLong -> ShowS #

show :: CLong -> String #

showList :: [CLong] -> ShowS #

Storable CLong 

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 
FiniteBits CLong 
NFData CLong

Since: 1.4.0.0

Methods

rnf :: CLong -> () #

IsScalar CLong # 

Methods

scalarType :: ScalarType CLong

IsBounded CLong # 

Methods

boundedType :: BoundedType CLong

IsNum CLong # 

Methods

numType :: NumType CLong

IsIntegral CLong # 

Methods

integralType :: IntegralType CLong

Elt CLong # 

Methods

eltType :: CLong -> TupleType (EltRepr CLong)

fromElt :: CLong -> EltRepr CLong

toElt :: EltRepr CLong -> CLong

Eq CLong # 

Methods

(==) :: Exp CLong -> Exp CLong -> Exp Bool #

(/=) :: Exp CLong -> Exp CLong -> Exp Bool #

Ord CLong # 
FiniteBits CLong # 
Bits CLong # 
FromIntegral Int CLong # 

Methods

fromIntegral :: Exp Int -> Exp CLong #

FromIntegral Int8 CLong # 
FromIntegral Int16 CLong # 
FromIntegral Int32 CLong # 
FromIntegral Int64 CLong # 
FromIntegral Word CLong # 
FromIntegral Word8 CLong # 
FromIntegral Word16 CLong # 
FromIntegral Word32 CLong # 
FromIntegral Word64 CLong # 
FromIntegral CShort CLong # 
FromIntegral CUShort CLong # 
FromIntegral CInt CLong # 
FromIntegral CUInt CLong # 
FromIntegral CLong Double # 
FromIntegral CLong Float # 
FromIntegral CLong Int # 

Methods

fromIntegral :: Exp CLong -> Exp Int #

FromIntegral CLong Int8 # 
FromIntegral CLong Int16 # 
FromIntegral CLong Int32 # 
FromIntegral CLong Int64 # 
FromIntegral CLong Word # 
FromIntegral CLong Word8 # 
FromIntegral CLong Word16 # 
FromIntegral CLong Word32 # 
FromIntegral CLong Word64 # 
FromIntegral CLong CShort # 
FromIntegral CLong CUShort # 
FromIntegral CLong CInt # 
FromIntegral CLong CUInt # 
FromIntegral CLong CLong # 
FromIntegral CLong CULong # 
FromIntegral CLong CLLong # 
FromIntegral CLong CULLong # 
FromIntegral CLong CFloat # 
FromIntegral CLong CDouble # 
FromIntegral CULong CLong # 
FromIntegral CLLong CLong # 
FromIntegral CULLong CLong # 
ToFloating CLong Double # 
ToFloating CLong Float # 

Methods

toFloating :: Exp CLong -> Exp Float #

ToFloating CLong CFloat # 
ToFloating CLong CDouble # 
Lift Exp CLong # 

Associated Types

type Plain CLong :: * #

Methods

lift :: CLong -> Exp (Plain CLong) #

type Plain CLong # 

data CULong :: * #

Haskell type representing the C unsigned long type.

Instances

Bounded CULong 
Enum CULong 
Eq CULong 

Methods

(==) :: CULong -> CULong -> Bool #

(/=) :: CULong -> CULong -> Bool #

Integral CULong 
Num CULong 
Ord CULong 
Read CULong 
Real CULong 
Show CULong 
Storable CULong 
Bits CULong 
FiniteBits CULong 
NFData CULong

Since: 1.4.0.0

Methods

rnf :: CULong -> () #

IsScalar CULong # 

Methods

scalarType :: ScalarType CULong

IsBounded CULong # 

Methods

boundedType :: BoundedType CULong

IsNum CULong # 

Methods

numType :: NumType CULong

IsIntegral CULong # 

Methods

integralType :: IntegralType CULong

Elt CULong # 

Methods

eltType :: CULong -> TupleType (EltRepr CULong)

fromElt :: CULong -> EltRepr CULong

toElt :: EltRepr CULong -> CULong

Eq CULong # 
Ord CULong # 
FiniteBits CULong # 
Bits CULong # 
FromIntegral Int CULong # 
FromIntegral Int8 CULong # 
FromIntegral Int16 CULong # 
FromIntegral Int32 CULong # 
FromIntegral Int64 CULong # 
FromIntegral Word CULong # 
FromIntegral Word8 CULong # 
FromIntegral Word16 CULong # 
FromIntegral Word32 CULong # 
FromIntegral Word64 CULong # 
FromIntegral CShort CULong # 
FromIntegral CUShort CULong # 
FromIntegral CInt CULong # 
FromIntegral CUInt CULong # 
FromIntegral CLong CULong # 
FromIntegral CULong Double # 
FromIntegral CULong Float # 
FromIntegral CULong Int # 
FromIntegral CULong Int8 # 
FromIntegral CULong Int16 # 
FromIntegral CULong Int32 # 
FromIntegral CULong Int64 # 
FromIntegral CULong Word # 
FromIntegral CULong Word8 # 
FromIntegral CULong Word16 # 
FromIntegral CULong Word32 # 
FromIntegral CULong Word64 # 
FromIntegral CULong CShort # 
FromIntegral CULong CUShort # 
FromIntegral CULong CInt # 
FromIntegral CULong CUInt # 
FromIntegral CULong CLong # 
FromIntegral CULong CULong # 
FromIntegral CULong CLLong # 
FromIntegral CULong CULLong # 
FromIntegral CULong CFloat # 
FromIntegral CULong CDouble # 
FromIntegral CLLong CULong # 
FromIntegral CULLong CULong # 
ToFloating CULong Double # 
ToFloating CULong Float # 
ToFloating CULong CFloat # 
ToFloating CULong CDouble # 
Lift Exp CULong # 

Associated Types

type Plain CULong :: * #

Methods

lift :: CULong -> Exp (Plain CULong) #

type Plain CULong # 

data CLLong :: * #

Haskell type representing the C long long type.

Instances

Bounded CLLong 
Enum CLLong 
Eq CLLong 

Methods

(==) :: CLLong -> CLLong -> Bool #

(/=) :: CLLong -> CLLong -> Bool #

Integral CLLong 
Num CLLong 
Ord CLLong 
Read CLLong 
Real CLLong 
Show CLLong 
Storable CLLong 
Bits CLLong 
FiniteBits CLLong 
NFData CLLong

Since: 1.4.0.0

Methods

rnf :: CLLong -> () #

IsScalar CLLong # 

Methods

scalarType :: ScalarType CLLong

IsBounded CLLong # 

Methods

boundedType :: BoundedType CLLong

IsNum CLLong # 

Methods

numType :: NumType CLLong

IsIntegral CLLong # 

Methods

integralType :: IntegralType CLLong

Elt CLLong # 

Methods

eltType :: CLLong -> TupleType (EltRepr CLLong)

fromElt :: CLLong -> EltRepr CLLong

toElt :: EltRepr CLLong -> CLLong

Eq CLLong # 
Ord CLLong # 
FiniteBits CLLong # 
Bits CLLong # 
FromIntegral Int CLLong # 
FromIntegral Int8 CLLong # 
FromIntegral Int16 CLLong # 
FromIntegral Int32 CLLong # 
FromIntegral Int64 CLLong # 
FromIntegral Word CLLong # 
FromIntegral Word8 CLLong # 
FromIntegral Word16 CLLong # 
FromIntegral Word32 CLLong # 
FromIntegral Word64 CLLong # 
FromIntegral CShort CLLong # 
FromIntegral CUShort CLLong # 
FromIntegral CInt CLLong # 
FromIntegral CUInt CLLong # 
FromIntegral CLong CLLong # 
FromIntegral CULong CLLong # 
FromIntegral CLLong Double # 
FromIntegral CLLong Float # 
FromIntegral CLLong Int # 
FromIntegral CLLong Int8 # 
FromIntegral CLLong Int16 # 
FromIntegral CLLong Int32 # 
FromIntegral CLLong Int64 # 
FromIntegral CLLong Word # 
FromIntegral CLLong Word8 # 
FromIntegral CLLong Word16 # 
FromIntegral CLLong Word32 # 
FromIntegral CLLong Word64 # 
FromIntegral CLLong CShort # 
FromIntegral CLLong CUShort # 
FromIntegral CLLong CInt # 
FromIntegral CLLong CUInt # 
FromIntegral CLLong CLong # 
FromIntegral CLLong CULong # 
FromIntegral CLLong CLLong # 
FromIntegral CLLong CULLong # 
FromIntegral CLLong CFloat # 
FromIntegral CLLong CDouble # 
FromIntegral CULLong CLLong # 
ToFloating CLLong Double # 
ToFloating CLLong Float # 
ToFloating CLLong CFloat # 
ToFloating CLLong CDouble # 
Lift Exp CLLong # 

Associated Types

type Plain CLLong :: * #

Methods

lift :: CLLong -> Exp (Plain CLLong) #

type Plain CLLong # 

data CULLong :: * #

Haskell type representing the C unsigned long long type.

Instances

Bounded CULLong 
Enum CULLong 
Eq CULLong 

Methods

(==) :: CULLong -> CULLong -> Bool #

(/=) :: CULLong -> CULLong -> Bool #

Integral CULLong 
Num CULLong 
Ord CULLong 
Read CULLong 
Real CULLong 
Show CULLong 
Storable CULLong 
Bits CULLong 
FiniteBits CULLong 
NFData CULLong

Since: 1.4.0.0

Methods

rnf :: CULLong -> () #

IsScalar CULLong # 

Methods

scalarType :: ScalarType CULLong

IsBounded CULLong # 

Methods

boundedType :: BoundedType CULLong

IsNum CULLong # 

Methods

numType :: NumType CULLong

IsIntegral CULLong # 

Methods

integralType :: IntegralType CULLong

Elt CULLong # 

Methods

eltType :: CULLong -> TupleType (EltRepr CULLong)

fromElt :: CULLong -> EltRepr CULLong

toElt :: EltRepr CULLong -> CULLong

Eq CULLong # 
Ord CULLong # 
FiniteBits CULLong # 
Bits CULLong # 
FromIntegral Int CULLong # 
FromIntegral Int8 CULLong # 
FromIntegral Int16 CULLong # 
FromIntegral Int32 CULLong # 
FromIntegral Int64 CULLong # 
FromIntegral Word CULLong # 
FromIntegral Word8 CULLong # 
FromIntegral Word16 CULLong # 
FromIntegral Word32 CULLong # 
FromIntegral Word64 CULLong # 
FromIntegral CShort CULLong # 
FromIntegral CUShort CULLong # 
FromIntegral CInt CULLong # 
FromIntegral CUInt CULLong # 
FromIntegral CLong CULLong # 
FromIntegral CULong CULLong # 
FromIntegral CLLong CULLong # 
FromIntegral CULLong Double # 
FromIntegral CULLong Float # 
FromIntegral CULLong Int # 
FromIntegral CULLong Int8 # 
FromIntegral CULLong Int16 # 
FromIntegral CULLong Int32 # 
FromIntegral CULLong Int64 # 
FromIntegral CULLong Word # 
FromIntegral CULLong Word8 # 
FromIntegral CULLong Word16 # 
FromIntegral CULLong Word32 # 
FromIntegral CULLong Word64 # 
FromIntegral CULLong CShort # 
FromIntegral CULLong CUShort # 
FromIntegral CULLong CInt # 
FromIntegral CULLong CUInt # 
FromIntegral CULLong CLong # 
FromIntegral CULLong CULong # 
FromIntegral CULLong CLLong # 
FromIntegral CULLong CULLong # 
FromIntegral CULLong CFloat # 
FromIntegral CULLong CDouble # 
ToFloating CULLong Double # 
ToFloating CULLong Float # 
ToFloating CULLong CFloat # 
ToFloating CULLong CDouble # 
Lift Exp CULLong # 

Associated Types

type Plain CULLong :: * #

Methods

lift :: CULLong -> Exp (Plain CULLong) #

type Plain CULLong # 

data CChar :: * #

Haskell type representing the C char type.

Instances

Bounded CChar 
Enum CChar 
Eq CChar 

Methods

(==) :: CChar -> CChar -> Bool #

(/=) :: CChar -> CChar -> Bool #

Integral CChar 
Num CChar 
Ord CChar 

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 
Real CChar 

Methods

toRational :: CChar -> Rational #

Show CChar 

Methods

showsPrec :: Int -> CChar -> ShowS #

show :: CChar -> String #

showList :: [CChar] -> ShowS #

Storable CChar 

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 
FiniteBits CChar 
NFData CChar

Since: 1.4.0.0

Methods

rnf :: CChar -> () #

IsScalar CChar # 

Methods

scalarType :: ScalarType CChar

IsBounded CChar # 

Methods

boundedType :: BoundedType CChar

IsNonNum CChar # 

Methods

nonNumType :: NonNumType CChar

Elt CChar # 

Methods

eltType :: CChar -> TupleType (EltRepr CChar)

fromElt :: CChar -> EltRepr CChar

toElt :: EltRepr CChar -> CChar

Eq CChar # 

Methods

(==) :: Exp CChar -> Exp CChar -> Exp Bool #

(/=) :: Exp CChar -> Exp CChar -> Exp Bool #

Ord CChar # 
Lift Exp CChar # 

Associated Types

type Plain CChar :: * #

Methods

lift :: CChar -> Exp (Plain CChar) #

type Plain CChar # 

data CSChar :: * #

Haskell type representing the C signed char type.

Instances

Bounded CSChar 
Enum CSChar 
Eq CSChar 

Methods

(==) :: CSChar -> CSChar -> Bool #

(/=) :: CSChar -> CSChar -> Bool #

Integral CSChar 
Num CSChar 
Ord CSChar 
Read CSChar 
Real CSChar 
Show CSChar 
Storable CSChar 
Bits CSChar 
FiniteBits CSChar 
NFData CSChar

Since: 1.4.0.0

Methods

rnf :: CSChar -> () #

IsScalar CSChar # 

Methods

scalarType :: ScalarType CSChar

IsBounded CSChar # 

Methods

boundedType :: BoundedType CSChar

IsNonNum CSChar # 

Methods

nonNumType :: NonNumType CSChar

Elt CSChar # 

Methods

eltType :: CSChar -> TupleType (EltRepr CSChar)

fromElt :: CSChar -> EltRepr CSChar

toElt :: EltRepr CSChar -> CSChar

Eq CSChar # 
Ord CSChar # 
Lift Exp CSChar # 

Associated Types

type Plain CSChar :: * #

Methods

lift :: CSChar -> Exp (Plain CSChar) #

type Plain CSChar # 

data CUChar :: * #

Haskell type representing the C unsigned char type.

Instances

Bounded CUChar 
Enum CUChar 
Eq CUChar 

Methods

(==) :: CUChar -> CUChar -> Bool #

(/=) :: CUChar -> CUChar -> Bool #

Integral CUChar 
Num CUChar 
Ord CUChar 
Read CUChar 
Real CUChar 
Show CUChar 
Storable CUChar 
Bits CUChar 
FiniteBits CUChar 
NFData CUChar

Since: 1.4.0.0

Methods

rnf :: CUChar -> () #

IsScalar CUChar # 

Methods

scalarType :: ScalarType CUChar

IsBounded CUChar # 

Methods

boundedType :: BoundedType CUChar

IsNonNum CUChar # 

Methods

nonNumType :: NonNumType CUChar

Elt CUChar # 

Methods

eltType :: CUChar -> TupleType (EltRepr CUChar)

fromElt :: CUChar -> EltRepr CUChar

toElt :: EltRepr CUChar -> CUChar

Eq CUChar # 
Ord CUChar # 
Lift Exp CUChar # 

Associated Types

type Plain CUChar :: * #

Methods

lift :: CUChar -> Exp (Plain CUChar) #

type Plain CUChar # 

Avoid using these in your own functions wherever possible.

class Typeable a => IsScalar a #

All scalar types

Minimal complete definition

scalarType

Instances

IsScalar Bool # 

Methods

scalarType :: ScalarType Bool

IsScalar Char # 

Methods

scalarType :: ScalarType Char

IsScalar Double # 

Methods

scalarType :: ScalarType Double

IsScalar Float # 

Methods

scalarType :: ScalarType Float

IsScalar Int # 

Methods

scalarType :: ScalarType Int

IsScalar Int8 # 

Methods

scalarType :: ScalarType Int8

IsScalar Int16 # 

Methods

scalarType :: ScalarType Int16

IsScalar Int32 # 

Methods

scalarType :: ScalarType Int32

IsScalar Int64 # 

Methods

scalarType :: ScalarType Int64

IsScalar Word # 

Methods

scalarType :: ScalarType Word

IsScalar Word8 # 

Methods

scalarType :: ScalarType Word8

IsScalar Word16 # 

Methods

scalarType :: ScalarType Word16

IsScalar Word32 # 

Methods

scalarType :: ScalarType Word32

IsScalar Word64 # 

Methods

scalarType :: ScalarType Word64

IsScalar CChar # 

Methods

scalarType :: ScalarType CChar

IsScalar CSChar # 

Methods

scalarType :: ScalarType CSChar

IsScalar CUChar # 

Methods

scalarType :: ScalarType CUChar

IsScalar CShort # 

Methods

scalarType :: ScalarType CShort

IsScalar CUShort # 

Methods

scalarType :: ScalarType CUShort

IsScalar CInt # 

Methods

scalarType :: ScalarType CInt

IsScalar CUInt # 

Methods

scalarType :: ScalarType CUInt

IsScalar CLong # 

Methods

scalarType :: ScalarType CLong

IsScalar CULong # 

Methods

scalarType :: ScalarType CULong

IsScalar CLLong # 

Methods

scalarType :: ScalarType CLLong

IsScalar CULLong # 

Methods

scalarType :: ScalarType CULLong

IsScalar CFloat # 

Methods

scalarType :: ScalarType CFloat

IsScalar CDouble # 

Methods

scalarType :: ScalarType CDouble

class (Num a, IsScalar a) => IsNum a #

Numeric types

Minimal complete definition

numType

Instances

IsNum Double # 

Methods

numType :: NumType Double

IsNum Float # 

Methods

numType :: NumType Float

IsNum Int # 

Methods

numType :: NumType Int

IsNum Int8 # 

Methods

numType :: NumType Int8

IsNum Int16 # 

Methods

numType :: NumType Int16

IsNum Int32 # 

Methods

numType :: NumType Int32

IsNum Int64 # 

Methods

numType :: NumType Int64

IsNum Word # 

Methods

numType :: NumType Word

IsNum Word8 # 

Methods

numType :: NumType Word8

IsNum Word16 # 

Methods

numType :: NumType Word16

IsNum Word32 # 

Methods

numType :: NumType Word32

IsNum Word64 # 

Methods

numType :: NumType Word64

IsNum CShort # 

Methods

numType :: NumType CShort

IsNum CUShort # 

Methods

numType :: NumType CUShort

IsNum CInt # 

Methods

numType :: NumType CInt

IsNum CUInt # 

Methods

numType :: NumType CUInt

IsNum CLong # 

Methods

numType :: NumType CLong

IsNum CULong # 

Methods

numType :: NumType CULong

IsNum CLLong # 

Methods

numType :: NumType CLLong

IsNum CULLong # 

Methods

numType :: NumType CULLong

IsNum CFloat # 

Methods

numType :: NumType CFloat

IsNum CDouble # 

Methods

numType :: NumType CDouble

class IsBounded a #

Bounded types

Minimal complete definition

boundedType

Instances

IsBounded Bool # 

Methods

boundedType :: BoundedType Bool

IsBounded Char # 

Methods

boundedType :: BoundedType Char

IsBounded Int # 

Methods

boundedType :: BoundedType Int

IsBounded Int8 # 

Methods

boundedType :: BoundedType Int8

IsBounded Int16 # 

Methods

boundedType :: BoundedType Int16

IsBounded Int32 # 

Methods

boundedType :: BoundedType Int32

IsBounded Int64 # 

Methods

boundedType :: BoundedType Int64

IsBounded Word # 

Methods

boundedType :: BoundedType Word

IsBounded Word8 # 

Methods

boundedType :: BoundedType Word8

IsBounded Word16 # 

Methods

boundedType :: BoundedType Word16

IsBounded Word32 # 

Methods

boundedType :: BoundedType Word32

IsBounded Word64 # 

Methods

boundedType :: BoundedType Word64

IsBounded CChar # 

Methods

boundedType :: BoundedType CChar

IsBounded CSChar # 

Methods

boundedType :: BoundedType CSChar

IsBounded CUChar # 

Methods

boundedType :: BoundedType CUChar

IsBounded CShort # 

Methods

boundedType :: BoundedType CShort

IsBounded CUShort # 

Methods

boundedType :: BoundedType CUShort

IsBounded CInt # 

Methods

boundedType :: BoundedType CInt

IsBounded CUInt # 

Methods

boundedType :: BoundedType CUInt

IsBounded CLong # 

Methods

boundedType :: BoundedType CLong

IsBounded CULong # 

Methods

boundedType :: BoundedType CULong

IsBounded CLLong # 

Methods

boundedType :: BoundedType CLLong

IsBounded CULLong # 

Methods

boundedType :: BoundedType CULLong

class (IsScalar a, IsNum a, IsBounded a) => IsIntegral a #

Integral types

Minimal complete definition

integralType

Instances

IsIntegral Int # 

Methods

integralType :: IntegralType Int

IsIntegral Int8 # 

Methods

integralType :: IntegralType Int8

IsIntegral Int16 # 

Methods

integralType :: IntegralType Int16

IsIntegral Int32 # 

Methods

integralType :: IntegralType Int32

IsIntegral Int64 # 

Methods

integralType :: IntegralType Int64

IsIntegral Word # 

Methods

integralType :: IntegralType Word

IsIntegral Word8 # 

Methods

integralType :: IntegralType Word8

IsIntegral Word16 # 

Methods

integralType :: IntegralType Word16

IsIntegral Word32 # 

Methods

integralType :: IntegralType Word32

IsIntegral Word64 # 

Methods

integralType :: IntegralType Word64

IsIntegral CShort # 

Methods

integralType :: IntegralType CShort

IsIntegral CUShort # 

Methods

integralType :: IntegralType CUShort

IsIntegral CInt # 

Methods

integralType :: IntegralType CInt

IsIntegral CUInt # 

Methods

integralType :: IntegralType CUInt

IsIntegral CLong # 

Methods

integralType :: IntegralType CLong

IsIntegral CULong # 

Methods

integralType :: IntegralType CULong

IsIntegral CLLong # 

Methods

integralType :: IntegralType CLLong

IsIntegral CULLong # 

Methods

integralType :: IntegralType CULLong

class (Floating a, IsScalar a, IsNum a) => IsFloating a #

Floating types

Minimal complete definition

floatingType

Instances

IsFloating Double # 

Methods

floatingType :: FloatingType Double

IsFloating Float # 

Methods

floatingType :: FloatingType Float

IsFloating CFloat # 

Methods

floatingType :: FloatingType CFloat

IsFloating CDouble # 

Methods

floatingType :: FloatingType CDouble

class IsNonNum a #

Non-numeric types

Minimal complete definition

nonNumType

Instances

IsNonNum Bool # 

Methods

nonNumType :: NonNumType Bool

IsNonNum Char # 

Methods

nonNumType :: NonNumType Char

IsNonNum CChar # 

Methods

nonNumType :: NonNumType CChar

IsNonNum CSChar # 

Methods

nonNumType :: NonNumType CSChar

IsNonNum CUChar # 

Methods

nonNumType :: NonNumType CUChar