accelerate-0.15.1.0: An embedded language for accelerated array processing

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

Data.Array.Accelerate

Contents

Description

This module defines an embedded language of array computations for high-performance computing. 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 executed on a range of architectures.

Abstract interface:

The types representing array computations are only exported abstractly — i.e., 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.

Code execution:

Access to the various backends is via a run function in backend-specific top level modules. Currently, we have the following:

Examples and documentation:

Synopsis

The Accelerate Array Language

Array data types

data Acc a #

Array-valued collective computations

Instances

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

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

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

Minimal complete definition

arrays, arrays', toArr, toArr', fromArr, fromArr'

Instances

Arrays () # 

Methods

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

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

toArr :: ArrRepr () -> ()

toArr' :: ArrRepr' () -> ()

fromArr :: () -> ArrRepr ()

fromArr' :: () -> ArrRepr' ()

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

Methods

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

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

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

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

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

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

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

Methods

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

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

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

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

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

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

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

Methods

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

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

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

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

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

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

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

Methods

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

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

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

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

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

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

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

Methods

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

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

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

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

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

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

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

Methods

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

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

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

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

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

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

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

Methods

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

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

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

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

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

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

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

Methods

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

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

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

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

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

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

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

Methods

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

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

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

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

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

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

data Array sh e #

Multi-dimensional arrays for array processing.

If device and host memory are separate, arrays will be transferred to the device when necessary (if possible asynchronously and in parallel with other tasks) and cached on the device if sufficient memory is available.

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 (Array sh e) # 

Methods

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

show :: Array sh e -> String #

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

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

Methods

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

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

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

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

fromArr :: Array sh e -> ArrRepr (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

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

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

Accelerate supports as array elements only simple atomic types, and tuples thereof. These element types are stored efficiently in memory, unpacked as consecutive elements without pointers.

This class characterises the types of values that can be array elements, and hence, appear in scalar Accelerate expressions.

Minimal complete definition

eltType, fromElt, toElt, eltType', fromElt', toElt'

Instances

Elt Bool # 

Methods

eltType :: Bool -> TupleType (EltRepr Bool)

fromElt :: Bool -> EltRepr Bool

toElt :: EltRepr Bool -> Bool

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

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

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

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

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

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

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

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

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

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

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

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

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

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

fromElt' :: Word64 -> EltRepr' Word64

toElt' :: EltRepr' Word64 -> Word64

Elt () # 

Methods

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

fromElt :: () -> EltRepr ()

toElt :: EltRepr () -> ()

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

fromElt' :: () -> EltRepr' ()

toElt' :: EltRepr' () -> ()

Elt CChar # 

Methods

eltType :: CChar -> TupleType (EltRepr CChar)

fromElt :: CChar -> EltRepr CChar

toElt :: EltRepr CChar -> CChar

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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)

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

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)

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

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)

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)

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)

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)

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)

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)

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)

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)

Shapes & Indices

Array indices are snoc type lists; that is, they are backwards and the end-of-list token, Z, occurs on the left. For example, the type of a rank-2 array index is Z :. Int :. Int.

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

dim :: Z -> Int

size :: Z -> Int

ignore :: Z

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

Elt Z # 

Methods

eltType :: Z -> TupleType (EltRepr Z)

fromElt :: Z -> EltRepr Z

toElt :: EltRepr Z -> Z

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

Elt (Any Z) # 

Methods

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

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

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

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

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

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

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

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)

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 head, Show tail) => Show ((:.) tail head) # 

Methods

showsPrec :: Int -> (tail :. head) -> ShowS #

show :: (tail :. head) -> String #

showList :: [tail :. head] -> 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

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

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

ignore :: sh :. Int

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

(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

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

class (Elt sh, Elt (Any sh), Shape (EltRepr sh)) => Shape sh #

Shapes and indices of multi-dimensional arrays

Minimal complete definition

sliceAnyIndex

Instances

Shape Z # 

Methods

dim :: Z -> Int

size :: Z -> Int

ignore :: Z

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

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

Methods

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

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

ignore :: sh :. Int

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

data All #

Marker for entire dimensions in slice descriptors.

For example, when used in slices passed to replicate, the occurrences of All indicate the dimensions into which the array's existing extent will be placed, rather than the new dimensions introduced by replication.

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

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 shapes in slice descriptors. Such arbitrary shapes may include an unknown number of dimensions.

Any can be used in the leftmost position of a slice instead of Z, for example (Any :. _ :. _). In the following definition Any is used to match against whatever shape the type variable sh takes:

repN :: (Shape sh, Elt e) => Int -> Acc (Array sh e) -> Acc (Array (sh:.Int) e)
repN n a = replicate (constant $ Any :. n) a

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)

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

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

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

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 #

Accessors

Indexing

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

Expression form that extracts a scalar from an array

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

Expression form that extracts a scalar from an array at a linear index

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

Extraction of the element in a singleton array

Shape information

null :: (Shape ix, Elt e) => Acc (Array ix 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 ix, Elt e) => Acc (Array ix e) -> Exp ix #

Expression form that yields the shape of an array

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

Expression form that yields the size of an array

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

The total number of elements in an array of the given Shape

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.

This can be used to cut out entire dimensions. The opposite of replicate. For example, if mat is a two dimensional array, the following will select a specific row and yield a one dimensional result:

slice mat (lift (Z :. (2::Int) :. All))

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

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

Yield all but the last element of the input vector. The vector must not be empty.

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

Yield all but the first element of the input vector. The vector must not be empty.

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

Yield the first n elements of the input vector. The vector must contain no more than n elements.

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

Yield all but the first n elements of the input vector. The vector must contain no fewer than n elements.

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

Yield a slit (slice) from the vector. The vector must contain at least i + n elements. Denotationally, we have:

slit i n = take n . drop i

Construction

Introduction

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

Array inlet: makes an array available for processing using the Accelerate language.

Depending upon the backend used to execute array computations, this may trigger (asynchronous) data transfer.

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

Scalar inlet: injects a scalar (or a tuple of scalars) into a singleton array for use in the Accelerate language.

Initialisation

generate :: (Shape ix, Elt a) => Exp ix -> (Exp ix -> Exp a) -> Acc (Array ix 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)

Or, equivalently:

generate (constant (Z :. (3::Int))) (\_ -> 1.2)

Finally, the following will create an array equivalent to '[1..10]':

generate (index1 10) $ \ ix ->
         let (Z :. i) = unlift ix
         in fromIntegral i
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 ...'.

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, assuming arr is a vector (one-dimensional array),

replicate (lift (Z :. (2::Int) :. All :. (3::Int))) arr

yields a three dimensional array, where arr is replicated twice across the first and three times across the third dimension.

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, Elt e, IsNum 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).

enumFromStepN #

Arguments

:: (Shape sh, Elt e, IsNum 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).

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 outermost component of two arrays. The extent of the lower dimensional component is the intersection of the two arrays.

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.

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 :: Arrays a => (Acc a -> Acc (Scalar Bool)) -> (Acc a -> Acc a) -> Acc a -> Acc a #

An array-level while construct

Pipelining

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

Denotationally, we have

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

Modifying Arrays

Shape manipulation

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

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

precondition: size ix == size ix'

flatten :: (Shape ix, Elt a) => Acc (Array ix a) -> Acc (Vector a) #

Flattens a given array of arbitrary dimension.

Permutations

permute #

Arguments

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

combination function

-> Acc (Array ix' a)

array of default values

-> (Exp ix -> Exp ix')

permutation

-> Acc (Array ix a)

array to be permuted

-> Acc (Array ix' a) 

Forward permutation specified by an index mapping. 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.

backpermute #

Arguments

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

shape of the result array

-> (Exp ix' -> Exp ix)

permutation

-> Acc (Array ix a)

source array

-> Acc (Array ix' a) 

Backward permutation specified by an index mapping from the destination array specifying which element of the source array to read.

ignore :: Shape ix => Exp ix #

Magic value identifying elements that are ignored in a forward permutation. Note that this currently does not work for singleton arrays.

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.

Element-wise operations

Mapping

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

Apply the given function element-wise to the given array.

Zipping

zipWith :: (Shape ix, Elt a, Elt b, Elt c) => (Exp a -> Exp b -> Exp c) -> Acc (Array ix a) -> Acc (Array ix b) -> Acc (Array ix 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.

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.

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.

Working with predicates

Filtering

filter :: Elt a => (Exp a -> Exp Bool) -> Acc (Vector a) -> Acc (Vector a) #

Drop elements that do not satisfy the predicate

Scatter

scatter #

Arguments

:: Elt e 
=> Acc (Vector Int)

index mapping

-> Acc (Vector e)

default

-> Acc (Vector e)

input

-> Acc (Vector e)

output

Copy elements from source array to destination array according to an index mapping. This is a forward-permute operation where a to vector encodes an input to output index mapping. Output elements for indices that are not mapped assume the default vector's value.

For example:

default = [0, 0, 0, 0, 0, 0, 0, 0, 0]
to      = [1, 3, 7, 2, 5, 8]
input   = [1, 9, 6, 4, 4, 2, 5]

output  = [0, 1, 4, 9, 0, 4, 0, 6, 2]

Note if the same index appears in the index mapping more than once, the result is undefined. It does not makes sense for the to vector to be larger than the input vector.

scatterIf #

Arguments

:: (Elt e, Elt e') 
=> Acc (Vector Int)

index mapping

-> Acc (Vector e)

mask

-> (Exp e -> Exp Bool)

predicate

-> Acc (Vector e')

default

-> Acc (Vector e')

input

-> Acc (Vector e')

output

Conditionally copy elements from source array to destination array according to an index mapping. This is a forward-permute operation where a to vector encodes an input to output index mapping. In addition, there is a mask vector, and an associated predicate function. The mapping will only occur if the predicate function applied to the mask at that position resolves to True. If not copied, the output array assumes the default vector's value.

For example:

default = [0, 0, 0, 0, 0, 0, 0, 0, 0]
to      = [1, 3, 7, 2, 5, 8]
mask    = [3, 4, 9, 2, 7, 5]
pred    = (>* 4)
input   = [1, 9, 6, 4, 4, 2, 5]

output  = [0, 0, 0, 0, 0, 4, 0, 6, 2]

Note if the same index appears in the mapping more than once, the result is undefined. The to and mask vectors must be the same length. It does not make sense for these to be larger than the input vector.

Gather

gather #

Arguments

:: Elt e 
=> Acc (Vector Int)

index mapping

-> Acc (Vector e)

input

-> Acc (Vector e)

output

Copy elements from source array to destination array according to a map. This is a backpermute operation where a map vector encodes the output to input index mapping.

For example:

input  = [1, 9, 6, 4, 4, 2, 0, 1, 2]
from   = [1, 3, 7, 2, 5, 3]

output = [9, 4, 1, 6, 2, 4]

gatherIf #

Arguments

:: (Elt e, Elt e') 
=> Acc (Vector Int)

index mapping

-> Acc (Vector e)

mask

-> (Exp e -> Exp Bool)

predicate

-> Acc (Vector e')

default

-> Acc (Vector e')

input

-> Acc (Vector e')

output

Conditionally copy elements from source array to destination array according to an index mapping. This is a backpermute operation where a from vector encodes the output to input index mapping. In addition, there is a mask vector, and an associated predication function, that specifies whether an element will be copied. If not copied, the output array assumes the default vector's value.

For example:

default = [6, 6, 6, 6, 6, 6]
from    = [1, 3, 7, 2, 5, 3]
mask    = [3, 4, 9, 2, 7, 5]
pred    = (>* 4)
input   = [1, 9, 6, 4, 4, 2, 0, 1, 2]

output  = [6, 6, 1, 6, 2, 4]

Folding

fold :: (Shape ix, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (ix :. Int) a) -> Acc (Array ix 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.

fold1 :: (Shape ix, Elt a) => (Exp a -> Exp a -> Exp a) -> Acc (Array (ix :. Int) a) -> Acc (Array ix 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.

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.

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.

Segmented reductions

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

Segmented reduction along the innermost dimension. Performs one individual reduction per segment of the source array. These reductions proceed in parallel.

The source array must have at least rank 1. The Segments array determines the lengths of the logical sub-arrays, each of which is folded separately.

fold1Seg :: (Shape ix, Elt a, Elt i, IsIntegral i) => (Exp a -> Exp a -> Exp a) -> Acc (Array (ix :. Int) a) -> Acc (Segments i) -> Acc (Array (ix :. 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 source array must have at least rank 1. The Segments array determines the lengths of the logical sub-arrays, each of which is folded separately.

Specialised folds

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, Elt e, IsNum e) => Acc (Array sh e) -> Acc (Scalar e) #

Compute the sum of elements

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

Compute the product of the elements

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

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

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

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

Prefix sums (scans)

scanl :: Elt a => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Vector a) -> Acc (Vector a) #

Data.List style left-to-right scan, but with the additional restriction that the first argument needs to be an associative function to enable an efficient parallel implementation. The initial value (second argument) may be arbitrary.

scanl1 :: Elt a => (Exp a -> Exp a -> Exp a) -> Acc (Vector a) -> Acc (Vector a) #

Data.List style left-to-right scan without an initial value (aka inclusive scan). Again, the first argument needs to be an associative function. Denotationally, we have

scanl1 f e arr = tail (scanl f e arr)

scanl' :: Elt a => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Vector a) -> (Acc (Vector a), Acc (Scalar a)) #

Variant of scanl, where the final result of the reduction is returned separately. Denotationally, we have

scanl' f e arr = (init res, unit (res!len))
  where
    len = shape arr
    res = scanl f e arr

scanr :: Elt a => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Vector a) -> Acc (Vector a) #

Right-to-left variant of scanl.

scanr1 :: Elt a => (Exp a -> Exp a -> Exp a) -> Acc (Vector a) -> Acc (Vector a) #

Right-to-left variant of scanl1.

scanr' :: Elt a => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Vector a) -> (Acc (Vector a), Acc (Scalar a)) #

Right-to-left variant of scanl'.

prescanl :: Elt a => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Vector a) -> Acc (Vector 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

postscanl :: Elt a => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Vector a) -> Acc (Vector a) #

Left-to-right postscan, a variant of scanl1 with an initial value. Denotationally, we have

postscanl f e = map (e `f`) . scanl1 f

prescanr :: Elt a => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Vector a) -> Acc (Vector 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 :: Elt a => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Vector a) -> Acc (Vector 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 :: (Elt a, Elt i, IsIntegral i) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Vector a) -> Acc (Segments i) -> Acc (Vector a) #

Segmented version of scanl

scanl1Seg :: (Elt a, Elt i, IsIntegral i) => (Exp a -> Exp a -> Exp a) -> Acc (Vector a) -> Acc (Segments i) -> Acc (Vector a) #

Segmented version of scanl1.

scanl'Seg :: forall a i. (Elt a, Elt i, IsIntegral i) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Vector a) -> Acc (Segments i) -> Acc (Vector a, Vector a) #

Segmented version of scanl'

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.

prescanlSeg :: (Elt a, Elt i, IsIntegral i) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Vector a) -> Acc (Segments i) -> Acc (Vector a) #

Segmented version of prescanl.

postscanlSeg :: (Elt a, Elt i, IsIntegral i) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Vector a) -> Acc (Segments i) -> Acc (Vector a) #

Segmented version of postscanl.

scanrSeg :: (Elt a, Elt i, IsIntegral i) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Vector a) -> Acc (Segments i) -> Acc (Vector a) #

Segmented version of scanr.

scanr1Seg :: (Elt a, Elt i, IsIntegral i) => (Exp a -> Exp a -> Exp a) -> Acc (Vector a) -> Acc (Segments i) -> Acc (Vector a) #

Segmented version of scanr1.

scanr'Seg :: forall a i. (Elt a, Elt i, IsIntegral i) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Vector a) -> Acc (Segments i) -> Acc (Vector a, Vector a) #

Segmented version of scanr'.

prescanrSeg :: (Elt a, Elt i, IsIntegral i) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Vector a) -> Acc (Segments i) -> Acc (Vector a) #

Segmented version of prescanr.

postscanrSeg :: (Elt a, Elt i, IsIntegral i) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Vector a) -> Acc (Segments i) -> Acc (Vector a) #

Segmented version of postscanr.

Stencil

stencil #

Arguments

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

stencil function

-> Boundary a

boundary condition

-> Acc (Array ix a)

source array

-> Acc (Array ix 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 in each dimension and have an extent of at least three in each dimensions — 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.

stencil2 #

Arguments

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

binary stencil function

-> Boundary a

boundary condition #1

-> Acc (Array ix a)

source array #1

-> Boundary b

boundary condition #2

-> Acc (Array ix b)

source array #2

-> Acc (Array ix 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.

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

Foreign

foreignAcc :: (Arrays acc, Arrays res, Foreign ff) => ff acc res -> (Acc acc -> Acc res) -> Acc acc -> Acc res #

Call a foreign function. The form the function takes is dependent on the backend being used. The arguments are passed as either a single array or as a tuple of arrays. In addition a pure Accelerate version of the function needs to be provided to support backends other than the one being targeted.

foreignAcc2 :: (Arrays acc, Arrays res, Foreign ff1, Foreign ff2) => ff1 acc res -> ff2 acc res -> (Acc acc -> Acc res) -> Acc acc -> Acc res #

Call a foreign function with foreign implementations for two different backends.

foreignAcc3 :: (Arrays acc, Arrays res, Foreign ff1, Foreign ff2, Foreign ff3) => ff1 acc res -> ff2 acc res -> ff3 acc res -> (Acc acc -> Acc res) -> Acc acc -> Acc res #

Call a foreign function with foreign implementations for three different backends.

foreignExp :: (Elt e, Elt res, Foreign ff) => ff e res -> (Exp e -> Exp res) -> Exp e -> Exp res #

Call a foreign expression function. The form the function takes is dependent on the backend being used. The arguments are passed as either a single scalar element or as a tuple of elements. In addition a pure Accelerate version of the function needs to be provided to support backends other than the one being targeted.

foreignExp2 :: (Elt e, Elt res, Foreign ff1, Foreign ff2) => ff1 e res -> ff2 e res -> (Exp e -> Exp res) -> Exp e -> Exp res #

Call a foreign function with foreign implementations for two different backends.

foreignExp3 :: (Elt e, Elt res, Foreign ff1, Foreign ff2, Foreign ff3) => ff1 e res -> ff2 e res -> ff3 e res -> (Exp e -> Exp res) -> Exp e -> Exp res #

Call a foreign function with foreign implementations for three different backends.

The Accelerate Expression Language

Scalar data types

data Exp t #

Scalar expressions for plain array computations.

Instances

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)

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

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

Type classes

class Typeable a => IsScalar a #

All scalar type

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

Element types

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

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

fromElt' :: Int -> EltRepr' Int

toElt' :: EltRepr' Int -> Int

IArray UArray Int 

Methods

bounds :: Ix i => UArray i Int -> (i, i) #

numElements :: Ix i => UArray i Int -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Int)] -> UArray i Int

unsafeAt :: Ix i => UArray i Int -> Int -> Int

unsafeReplace :: Ix i => UArray i Int -> [(Int, Int)] -> UArray i Int

unsafeAccum :: Ix i => (Int -> e' -> Int) -> UArray i Int -> [(Int, e')] -> UArray i Int

unsafeAccumArray :: Ix i => (Int -> e' -> Int) -> Int -> (i, i) -> [(Int, e')] -> UArray i Int

Vector Vector Int 
MVector MVector Int 
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 #

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 #

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)

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)

MArray (STUArray s) Int (ST s) 

Methods

getBounds :: Ix i => STUArray s i Int -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Int -> ST s Int

newArray :: Ix i => (i, i) -> Int -> ST s (STUArray s i Int) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int)

unsafeRead :: Ix i => STUArray s i Int -> Int -> ST s Int

unsafeWrite :: Ix i => STUArray s i Int -> Int -> Int -> ST s ()

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 #

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

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

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

ignore :: sh :. Int

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

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

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

fromElt' :: Int8 -> EltRepr' Int8

toElt' :: EltRepr' Int8 -> Int8

IArray UArray Int8 

Methods

bounds :: Ix i => UArray i Int8 -> (i, i) #

numElements :: Ix i => UArray i Int8 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Int8)] -> UArray i Int8

unsafeAt :: Ix i => UArray i Int8 -> Int -> Int8

unsafeReplace :: Ix i => UArray i Int8 -> [(Int, Int8)] -> UArray i Int8

unsafeAccum :: Ix i => (Int8 -> e' -> Int8) -> UArray i Int8 -> [(Int, e')] -> UArray i Int8

unsafeAccumArray :: Ix i => (Int8 -> e' -> Int8) -> Int8 -> (i, i) -> [(Int, e')] -> UArray i Int8

Vector Vector Int8 
MVector MVector Int8 
Lift Exp Int8 # 

Associated Types

type Plain Int8 :: * #

Methods

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

MArray (STUArray s) Int8 (ST s) 

Methods

getBounds :: Ix i => STUArray s i Int8 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Int8 -> ST s Int

newArray :: Ix i => (i, i) -> Int8 -> ST s (STUArray s i Int8) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int8) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int8)

unsafeRead :: Ix i => STUArray s i Int8 -> Int -> ST s Int8

unsafeWrite :: Ix i => STUArray s i Int8 -> Int -> Int8 -> ST s ()

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

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

fromElt' :: Int16 -> EltRepr' Int16

toElt' :: EltRepr' Int16 -> Int16

IArray UArray Int16 

Methods

bounds :: Ix i => UArray i Int16 -> (i, i) #

numElements :: Ix i => UArray i Int16 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Int16)] -> UArray i Int16

unsafeAt :: Ix i => UArray i Int16 -> Int -> Int16

unsafeReplace :: Ix i => UArray i Int16 -> [(Int, Int16)] -> UArray i Int16

unsafeAccum :: Ix i => (Int16 -> e' -> Int16) -> UArray i Int16 -> [(Int, e')] -> UArray i Int16

unsafeAccumArray :: Ix i => (Int16 -> e' -> Int16) -> Int16 -> (i, i) -> [(Int, e')] -> UArray i Int16

Vector Vector Int16 
MVector MVector Int16 
Lift Exp Int16 # 

Associated Types

type Plain Int16 :: * #

Methods

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

MArray (STUArray s) Int16 (ST s) 

Methods

getBounds :: Ix i => STUArray s i Int16 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Int16 -> ST s Int

newArray :: Ix i => (i, i) -> Int16 -> ST s (STUArray s i Int16) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int16) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int16)

unsafeRead :: Ix i => STUArray s i Int16 -> Int -> ST s Int16

unsafeWrite :: Ix i => STUArray s i Int16 -> Int -> Int16 -> ST s ()

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

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

fromElt' :: Int32 -> EltRepr' Int32

toElt' :: EltRepr' Int32 -> Int32

IArray UArray Int32 

Methods

bounds :: Ix i => UArray i Int32 -> (i, i) #

numElements :: Ix i => UArray i Int32 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Int32)] -> UArray i Int32

unsafeAt :: Ix i => UArray i Int32 -> Int -> Int32

unsafeReplace :: Ix i => UArray i Int32 -> [(Int, Int32)] -> UArray i Int32

unsafeAccum :: Ix i => (Int32 -> e' -> Int32) -> UArray i Int32 -> [(Int, e')] -> UArray i Int32

unsafeAccumArray :: Ix i => (Int32 -> e' -> Int32) -> Int32 -> (i, i) -> [(Int, e')] -> UArray i Int32

Vector Vector Int32 
MVector MVector Int32 
Lift Exp Int32 # 

Associated Types

type Plain Int32 :: * #

Methods

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

MArray (STUArray s) Int32 (ST s) 

Methods

getBounds :: Ix i => STUArray s i Int32 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Int32 -> ST s Int

newArray :: Ix i => (i, i) -> Int32 -> ST s (STUArray s i Int32) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int32) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int32)

unsafeRead :: Ix i => STUArray s i Int32 -> Int -> ST s Int32

unsafeWrite :: Ix i => STUArray s i Int32 -> Int -> Int32 -> ST s ()

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

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

fromElt' :: Int64 -> EltRepr' Int64

toElt' :: EltRepr' Int64 -> Int64

IArray UArray Int64 

Methods

bounds :: Ix i => UArray i Int64 -> (i, i) #

numElements :: Ix i => UArray i Int64 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Int64)] -> UArray i Int64

unsafeAt :: Ix i => UArray i Int64 -> Int -> Int64

unsafeReplace :: Ix i => UArray i Int64 -> [(Int, Int64)] -> UArray i Int64

unsafeAccum :: Ix i => (Int64 -> e' -> Int64) -> UArray i Int64 -> [(Int, e')] -> UArray i Int64

unsafeAccumArray :: Ix i => (Int64 -> e' -> Int64) -> Int64 -> (i, i) -> [(Int, e')] -> UArray i Int64

Vector Vector Int64 
MVector MVector Int64 
Lift Exp Int64 # 

Associated Types

type Plain Int64 :: * #

Methods

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

MArray (STUArray s) Int64 (ST s) 

Methods

getBounds :: Ix i => STUArray s i Int64 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Int64 -> ST s Int

newArray :: Ix i => (i, i) -> Int64 -> ST s (STUArray s i Int64) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int64) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int64)

unsafeRead :: Ix i => STUArray s i Int64 -> Int -> ST s Int64

unsafeWrite :: Ix i => STUArray s i Int64 -> Int -> Int64 -> ST s ()

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

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

fromElt' :: Word -> EltRepr' Word

toElt' :: EltRepr' Word -> Word

IArray UArray Word 

Methods

bounds :: Ix i => UArray i Word -> (i, i) #

numElements :: Ix i => UArray i Word -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Word)] -> UArray i Word

unsafeAt :: Ix i => UArray i Word -> Int -> Word

unsafeReplace :: Ix i => UArray i Word -> [(Int, Word)] -> UArray i Word

unsafeAccum :: Ix i => (Word -> e' -> Word) -> UArray i Word -> [(Int, e')] -> UArray i Word

unsafeAccumArray :: Ix i => (Word -> e' -> Word) -> Word -> (i, i) -> [(Int, e')] -> UArray i Word

Vector Vector Word 
MVector MVector Word 
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 #

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 #

MArray (STUArray s) Word (ST s) 

Methods

getBounds :: Ix i => STUArray s i Word -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word -> ST s Int

newArray :: Ix i => (i, i) -> Word -> ST s (STUArray s i Word) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word)

unsafeRead :: Ix i => STUArray s i Word -> Int -> ST s Word

unsafeWrite :: Ix i => STUArray s i Word -> Int -> Word -> ST s ()

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

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

fromElt' :: Word8 -> EltRepr' Word8

toElt' :: EltRepr' Word8 -> Word8

IArray UArray Word8 

Methods

bounds :: Ix i => UArray i Word8 -> (i, i) #

numElements :: Ix i => UArray i Word8 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Word8)] -> UArray i Word8

unsafeAt :: Ix i => UArray i Word8 -> Int -> Word8

unsafeReplace :: Ix i => UArray i Word8 -> [(Int, Word8)] -> UArray i Word8

unsafeAccum :: Ix i => (Word8 -> e' -> Word8) -> UArray i Word8 -> [(Int, e')] -> UArray i Word8

unsafeAccumArray :: Ix i => (Word8 -> e' -> Word8) -> Word8 -> (i, i) -> [(Int, e')] -> UArray i Word8

Vector Vector Word8 
MVector MVector Word8 
Lift Exp Word8 # 

Associated Types

type Plain Word8 :: * #

Methods

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

MArray (STUArray s) Word8 (ST s) 

Methods

getBounds :: Ix i => STUArray s i Word8 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word8 -> ST s Int

newArray :: Ix i => (i, i) -> Word8 -> ST s (STUArray s i Word8) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word8) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word8)

unsafeRead :: Ix i => STUArray s i Word8 -> Int -> ST s Word8

unsafeWrite :: Ix i => STUArray s i Word8 -> Int -> Word8 -> ST s ()

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

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

fromElt' :: Word16 -> EltRepr' Word16

toElt' :: EltRepr' Word16 -> Word16

IArray UArray Word16 

Methods

bounds :: Ix i => UArray i Word16 -> (i, i) #

numElements :: Ix i => UArray i Word16 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Word16)] -> UArray i Word16

unsafeAt :: Ix i => UArray i Word16 -> Int -> Word16

unsafeReplace :: Ix i => UArray i Word16 -> [(Int, Word16)] -> UArray i Word16

unsafeAccum :: Ix i => (Word16 -> e' -> Word16) -> UArray i Word16 -> [(Int, e')] -> UArray i Word16

unsafeAccumArray :: Ix i => (Word16 -> e' -> Word16) -> Word16 -> (i, i) -> [(Int, e')] -> UArray i Word16

Vector Vector Word16 
MVector MVector Word16 
Lift Exp Word16 # 

Associated Types

type Plain Word16 :: * #

Methods

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

MArray (STUArray s) Word16 (ST s) 

Methods

getBounds :: Ix i => STUArray s i Word16 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word16 -> ST s Int

newArray :: Ix i => (i, i) -> Word16 -> ST s (STUArray s i Word16) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word16) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word16)

unsafeRead :: Ix i => STUArray s i Word16 -> Int -> ST s Word16

unsafeWrite :: Ix i => STUArray s i Word16 -> Int -> Word16 -> ST s ()

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

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

fromElt' :: Word32 -> EltRepr' Word32

toElt' :: EltRepr' Word32 -> Word32

IArray UArray Word32 

Methods

bounds :: Ix i => UArray i Word32 -> (i, i) #

numElements :: Ix i => UArray i Word32 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Word32)] -> UArray i Word32

unsafeAt :: Ix i => UArray i Word32 -> Int -> Word32

unsafeReplace :: Ix i => UArray i Word32 -> [(Int, Word32)] -> UArray i Word32

unsafeAccum :: Ix i => (Word32 -> e' -> Word32) -> UArray i Word32 -> [(Int, e')] -> UArray i Word32

unsafeAccumArray :: Ix i => (Word32 -> e' -> Word32) -> Word32 -> (i, i) -> [(Int, e')] -> UArray i Word32

Vector Vector Word32 
MVector MVector Word32 
Lift Exp Word32 # 

Associated Types

type Plain Word32 :: * #

Methods

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

MArray (STUArray s) Word32 (ST s) 

Methods

getBounds :: Ix i => STUArray s i Word32 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word32 -> ST s Int

newArray :: Ix i => (i, i) -> Word32 -> ST s (STUArray s i Word32) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word32) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word32)

unsafeRead :: Ix i => STUArray s i Word32 -> Int -> ST s Word32

unsafeWrite :: Ix i => STUArray s i Word32 -> Int -> Word32 -> ST s ()

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

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

fromElt' :: Word64 -> EltRepr' Word64

toElt' :: EltRepr' Word64 -> Word64

IArray UArray Word64 

Methods

bounds :: Ix i => UArray i Word64 -> (i, i) #

numElements :: Ix i => UArray i Word64 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Word64)] -> UArray i Word64

unsafeAt :: Ix i => UArray i Word64 -> Int -> Word64

unsafeReplace :: Ix i => UArray i Word64 -> [(Int, Word64)] -> UArray i Word64

unsafeAccum :: Ix i => (Word64 -> e' -> Word64) -> UArray i Word64 -> [(Int, e')] -> UArray i Word64

unsafeAccumArray :: Ix i => (Word64 -> e' -> Word64) -> Word64 -> (i, i) -> [(Int, e')] -> UArray i Word64

Vector Vector Word64 
MVector MVector Word64 
Lift Exp Word64 # 

Associated Types

type Plain Word64 :: * #

Methods

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

MArray (STUArray s) Word64 (ST s) 

Methods

getBounds :: Ix i => STUArray s i Word64 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word64 -> ST s Int

newArray :: Ix i => (i, i) -> Word64 -> ST s (STUArray s i Word64) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word64) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word64)

unsafeRead :: Ix i => STUArray s i Word64 -> Int -> ST s Word64

unsafeWrite :: Ix i => STUArray s i Word64 -> Int -> Word64 -> ST s ()

data Vector Word64 
type Plain Word64 # 
data MVector s Word64 

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

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

fromElt' :: CShort -> EltRepr' CShort

toElt' :: EltRepr' CShort -> CShort

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

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

fromElt' :: CUShort -> EltRepr' CUShort

toElt' :: EltRepr' CUShort -> CUShort

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

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

fromElt' :: CInt -> EltRepr' CInt

toElt' :: EltRepr' CInt -> CInt

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

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

fromElt' :: CUInt -> EltRepr' CUInt

toElt' :: EltRepr' CUInt -> CUInt

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

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

fromElt' :: CLong -> EltRepr' CLong

toElt' :: EltRepr' CLong -> CLong

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

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

fromElt' :: CULong -> EltRepr' CULong

toElt' :: EltRepr' CULong -> CULong

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

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

fromElt' :: CLLong -> EltRepr' CLLong

toElt' :: EltRepr' CLLong -> CLLong

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

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

fromElt' :: CULLong -> EltRepr' CULLong

toElt' :: EltRepr' CULLong -> CULLong

Lift Exp CULLong # 

Associated Types

type Plain CULLong :: * #

Methods

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

type Plain CULLong # 

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

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

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

fromElt' :: Float -> EltRepr' Float

toElt' :: EltRepr' Float -> Float

IArray UArray Float 

Methods

bounds :: Ix i => UArray i Float -> (i, i) #

numElements :: Ix i => UArray i Float -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Float)] -> UArray i Float

unsafeAt :: Ix i => UArray i Float -> Int -> Float

unsafeReplace :: Ix i => UArray i Float -> [(Int, Float)] -> UArray i Float

unsafeAccum :: Ix i => (Float -> e' -> Float) -> UArray i Float -> [(Int, e')] -> UArray i Float

unsafeAccumArray :: Ix i => (Float -> e' -> Float) -> Float -> (i, i) -> [(Int, e')] -> UArray i Float

Vector Vector Float 
MVector MVector 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 #

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 #

MArray (STUArray s) Float (ST s) 

Methods

getBounds :: Ix i => STUArray s i Float -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Float -> ST s Int

newArray :: Ix i => (i, i) -> Float -> ST s (STUArray s i Float) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Float) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Float)

unsafeRead :: Ix i => STUArray s i Float -> Int -> ST s Float

unsafeWrite :: Ix i => STUArray s i Float -> Int -> Float -> ST s ()

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

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

fromElt' :: Double -> EltRepr' Double

toElt' :: EltRepr' Double -> Double

IArray UArray Double 

Methods

bounds :: Ix i => UArray i Double -> (i, i) #

numElements :: Ix i => UArray i Double -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Double)] -> UArray i Double

unsafeAt :: Ix i => UArray i Double -> Int -> Double

unsafeReplace :: Ix i => UArray i Double -> [(Int, Double)] -> UArray i Double

unsafeAccum :: Ix i => (Double -> e' -> Double) -> UArray i Double -> [(Int, e')] -> UArray i Double

unsafeAccumArray :: Ix i => (Double -> e' -> Double) -> Double -> (i, i) -> [(Int, e')] -> UArray i Double

Vector Vector Double 
MVector MVector 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 #

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 #

MArray (STUArray s) Double (ST s) 

Methods

getBounds :: Ix i => STUArray s i Double -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Double -> ST s Int

newArray :: Ix i => (i, i) -> Double -> ST s (STUArray s i Double) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Double) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Double)

unsafeRead :: Ix i => STUArray s i Double -> Int -> ST s Double

unsafeWrite :: Ix i => STUArray s i Double -> Int -> Double -> ST s ()

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

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

fromElt' :: CFloat -> EltRepr' CFloat

toElt' :: EltRepr' CFloat -> 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 
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

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

fromElt' :: CDouble -> EltRepr' CDouble

toElt' :: EltRepr' CDouble -> CDouble

Lift Exp CDouble # 

Associated Types

type Plain CDouble :: * #

Methods

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

type Plain CDouble # 

data Bool :: * #

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

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

fromElt' :: Bool -> EltRepr' Bool

toElt' :: EltRepr' Bool -> Bool

IArray UArray Bool 

Methods

bounds :: Ix i => UArray i Bool -> (i, i) #

numElements :: Ix i => UArray i Bool -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Bool)] -> UArray i Bool

unsafeAt :: Ix i => UArray i Bool -> Int -> Bool

unsafeReplace :: Ix i => UArray i Bool -> [(Int, Bool)] -> UArray i Bool

unsafeAccum :: Ix i => (Bool -> e' -> Bool) -> UArray i Bool -> [(Int, e')] -> UArray i Bool

unsafeAccumArray :: Ix i => (Bool -> e' -> Bool) -> Bool -> (i, i) -> [(Int, e')] -> UArray i 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

MArray (STUArray s) Bool (ST s) 

Methods

getBounds :: Ix i => STUArray s i Bool -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Bool -> ST s Int

newArray :: Ix i => (i, i) -> Bool -> ST s (STUArray s i Bool) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Bool) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Bool)

unsafeRead :: Ix i => STUArray s i Bool -> Int -> ST s Bool

unsafeWrite :: Ix i => STUArray s i Bool -> Int -> Bool -> ST s ()

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

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

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

fromElt' :: Char -> EltRepr' Char

toElt' :: EltRepr' Char -> Char

IArray UArray Char 

Methods

bounds :: Ix i => UArray i Char -> (i, i) #

numElements :: Ix i => UArray i Char -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Char)] -> UArray i Char

unsafeAt :: Ix i => UArray i Char -> Int -> Char

unsafeReplace :: Ix i => UArray i Char -> [(Int, Char)] -> UArray i Char

unsafeAccum :: Ix i => (Char -> e' -> Char) -> UArray i Char -> [(Int, e')] -> UArray i Char

unsafeAccumArray :: Ix i => (Char -> e' -> Char) -> Char -> (i, i) -> [(Int, e')] -> UArray i 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 #

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 #

MArray (STUArray s) Char (ST s) 

Methods

getBounds :: Ix i => STUArray s i Char -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Char -> ST s Int

newArray :: Ix i => (i, i) -> Char -> ST s (STUArray s i Char) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Char) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Char)

unsafeRead :: Ix i => STUArray s i Char -> Int -> ST s Char

unsafeWrite :: Ix i => STUArray s i Char -> Int -> Char -> ST s ()

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

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

fromElt' :: CChar -> EltRepr' CChar

toElt' :: EltRepr' CChar -> 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 
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

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

fromElt' :: CSChar -> EltRepr' CSChar

toElt' :: EltRepr' CSChar -> 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 
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

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

fromElt' :: CUChar -> EltRepr' CUChar

toElt' :: EltRepr' CUChar -> CUChar

Lift Exp CUChar # 

Associated Types

type Plain CUChar :: * #

Methods

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

type Plain CUChar # 

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

Exp (Z :. Int :. Int)
    -> unlift    :: (Z :. Exp Int :. Exp Int)
    -> lift      :: Exp (Z :. Int :. Int)
    -> ...
Acc (Scalar Int, Vector Float)
    -> unlift    :: (Acc (Scalar Int), Acc (Vector Float))
    -> lift      :: Acc (Scalar Int, Vector Float)
    -> ...

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

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 #

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

lift1 :: (Unlift Exp e1, Lift Exp e2) => (e1 -> e2) -> Exp (Plain e1) -> Exp (Plain e2) #

Lift a unary function into Exp.

lift2 :: (Unlift Exp e1, Unlift Exp e2, Lift Exp e3) => (e1 -> e2 -> e3) -> Exp (Plain e1) -> Exp (Plain e2) -> Exp (Plain e3) #

Lift a binary 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.

Operations

Some of the standard Haskell 98 typeclass functions need to be reimplemented because their types change. If so, function names kept the same and infix operations are suffixed by an asterisk. If not reimplemented here, the standard typeclass instances apply.

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.

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 :: Elt e => (Exp e -> Exp Bool) -> (Exp e -> Exp e) -> Exp e -> Exp e #

While construct. Continue to apply the given function, starting with the initial value, until the test function evaluates to true.

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.

Basic operations

(&&*) :: Exp Bool -> Exp Bool -> Exp Bool infixr 3 #

Conjunction

(||*) :: Exp Bool -> Exp Bool -> Exp Bool infixr 2 #

Disjunction

not :: Exp Bool -> Exp Bool #

Negation

(==*) :: (Elt t, IsScalar t) => Exp t -> Exp t -> Exp Bool infix 4 #

Equality lifted into Accelerate expressions.

(/=*) :: (Elt t, IsScalar t) => Exp t -> Exp t -> Exp Bool infix 4 #

Inequality lifted into Accelerate expressions.

(<*) :: (Elt t, IsScalar t) => Exp t -> Exp t -> Exp Bool infix 4 #

Smaller-than lifted into Accelerate expressions.

(<=*) :: (Elt t, IsScalar t) => Exp t -> Exp t -> Exp Bool infix 4 #

Smaller-or-equal lifted into Accelerate expressions.

(>*) :: (Elt t, IsScalar t) => Exp t -> Exp t -> Exp Bool infix 4 #

Greater-than lifted into Accelerate expressions.

(>=*) :: (Elt t, IsScalar t) => Exp t -> Exp t -> Exp Bool infix 4 #

Greater-or-equal lifted into Accelerate expressions.

Numeric functions

truncate :: (Elt a, Elt b, IsFloating a, IsIntegral b) => Exp a -> Exp b #

truncate x returns the integer nearest x between zero and x.

round :: (Elt a, Elt b, IsFloating a, IsIntegral b) => Exp a -> Exp b #

round x returns the nearest integer to x, or the even integer if x is equidistant between two integers.

floor :: (Elt a, Elt b, IsFloating a, IsIntegral b) => Exp a -> Exp b #

floor x returns the greatest integer not greater than x.

ceiling :: (Elt a, Elt b, IsFloating a, IsIntegral b) => Exp a -> Exp b #

ceiling x returns the least integer not less than x.

even :: (Elt a, IsIntegral a) => Exp a -> Exp Bool #

return if the integer is even

odd :: (Elt a, IsIntegral a) => Exp a -> Exp Bool #

return if the integer is odd

Bitwise functions

bit :: (Elt t, IsIntegral t) => Exp Int -> Exp t #

bit i is a value with the ith bit set and all other bits clear

setBit :: (Elt t, IsIntegral t) => Exp t -> Exp Int -> Exp t #

x `setBit` i is the same as x .|. bit i

clearBit :: (Elt t, IsIntegral t) => Exp t -> Exp Int -> Exp t #

x `clearBit` i is the same as x .&. complement (bit i)

complementBit :: (Elt t, IsIntegral t) => Exp t -> Exp Int -> Exp t #

x `complementBit` i is the same as x `xor` bit i

testBit :: (Elt t, IsIntegral t) => Exp t -> Exp Int -> Exp Bool #

Return True if the nth bit of the argument is 1

shift :: (Elt t, IsIntegral t) => Exp t -> Exp Int -> Exp t #

shift x i shifts x left by i bits if i is positive, or right by -i bits otherwise. Right shifts perform sign extension on signed number types; i.e. they fill the top bits with 1 if the x is negative and with 0 otherwise.

shiftL :: (Elt t, IsIntegral t) => Exp t -> Exp Int -> Exp t #

Shift the argument left by the specified number of bits (which must be non-negative).

shiftR :: (Elt t, IsIntegral t) => Exp t -> Exp Int -> Exp t #

Shift the first argument right by the specified number of bits. The result is undefined for negative shift amounts and shift amounts greater or equal to the bitSize.

Right shifts perform sign extension on signed number types; i.e. they fill the top bits with 1 if the x is negative and with 0 otherwise.

rotate :: (Elt t, IsIntegral t) => Exp t -> Exp Int -> Exp t #

rotate x i rotates x left by i bits if i is positive, or right by -i bits otherwise.

rotateL :: (Elt t, IsIntegral t) => Exp t -> Exp Int -> Exp t #

Rotate the argument left by the specified number of bits (which must be non-negative).

rotateR :: (Elt t, IsIntegral t) => Exp t -> Exp Int -> Exp t #

Rotate the argument right by the specified number of bits (which must be non-negative).

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.

indexHead :: Slice sh => Exp (sh :. Int) -> Exp Int #

Get the outermost dimension of a shape

indexTail :: Slice sh => Exp (sh :. Int) -> Exp sh #

Get all but the outermost element of a shape

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

Map a multi-dimensional index into a linear, row-major representation of an array. The first argument is the array shape, the second is the index.

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

fromIntegral :: (Elt a, Elt b, IsIntegral a, IsNum b) => Exp a -> Exp b #

General coercion from integral types

Plain arrays

Operations

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

Conversions

For additional conversion routines, see the accelerate-io package: http://hackage.haskell.org/package/accelerate-io

Function

fromFunction :: (Shape sh, Elt e) => sh -> (sh -> e) -> Array sh e #

Create an array from its representation function.

Lists

fromList :: (Shape sh, Elt e) => sh -> [e] -> Array sh e #

Convert a list, with elements in row-major order, into an accelerated array.

toList :: forall sh e. Array sh e -> [e] #

Convert an accelerated array to a list in row-major order.

IArray

fromIArray :: (EltRepr ix ~ EltRepr sh, IArray a e, Ix ix, Shape sh, Elt ix, Elt e) => a ix e -> Array sh e #

Convert an IArray to an accelerated array.

While the type signature mentions Accelerate internals that are not exported, in practice satisfying the type equality is straight forward. The index type ix must be the unit type () for singleton arrays, or an Int or tuple of Int's for multidimensional arrays.

toIArray :: (EltRepr ix ~ EltRepr sh, IArray a e, Ix ix, Shape sh, Elt ix, Elt e) => Array sh e -> a ix e #

Convert an accelerated array to an IArray.