accelerate-0.5.0.0: An embedded language for accelerated array processing

Data.Array.Accelerate

Contents

Description

An embedded language of accelerated array computations

Copyright (c) [2008..2009] Manuel M T Chakravarty, Gabriele Keller, Sean Lee

License: BSD3

Synopsis

Scalar 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 Prelude.minBound and Prelude.maxBound from the Prelude.Bounded class.

Instances

Bounded Int 
Enum Int 
Eq Int 
Integral Int 
Num Int 
Ord Int 
Real Int 
Show Int 
Ix Int 
Typeable Int 
Bits Int 
IsScalar Int 
IsBounded Int 
IsNum Int 
IsIntegral Int 
ArrayElem Int 
Ix Int 
Shape Int 
ShapeBase Int 
Elem Int 
IArray UArray Int 
MArray (STUArray s) Int (ST s) 
SliceIx sl => SliceIx (sl, Int) 
Ix ix => Ix (ix, Int) 
Ix (Int, Int) 
Ix (Int, Int, Int) 
Ix (Int, Int, Int, Int) 
Ix (Int, Int, Int, Int, Int) 

data Int8

8-bit signed integer type

Instances

Bounded Int8 
Enum Int8 
Eq Int8 
Integral Int8 
Num Int8 
Ord Int8 
Read Int8 
Real Int8 
Show Int8 
Ix Int8 
Typeable Int8 
Bits Int8 
IsScalar Int8 
IsBounded Int8 
IsNum Int8 
IsIntegral Int8 
ArrayElem Int8 
Elem Int8 
IArray UArray Int8 
MArray (STUArray s) Int8 (ST s) 

data Int16

16-bit signed integer type

data Int32

32-bit signed integer type

data Int64

64-bit signed integer type

data Word

A Word is an unsigned integral type, with the same size as Int.

Instances

Bounded Word 
Enum Word 
Eq Word 
Integral Word 
Num Word 
Ord Word 
Read Word 
Real Word 
Show Word 
Ix Word 
Typeable Word 
Bits Word 
IsScalar Word 
IsBounded Word 
IsNum Word 
IsIntegral Word 
ArrayElem Word 
Elem Word 
IArray UArray Word 
MArray (STUArray s) Word (ST s) 

data Word8

8-bit unsigned integer type

data Word16

16-bit unsigned integer type

data Word32

32-bit unsigned integer type

data Word64

64-bit unsigned integer type

data CShort

Haskell type representing the C short type.

data CUShort

Haskell type representing the C unsigned short type.

data CInt

Haskell type representing the C int type.

Instances

data CUInt

Haskell type representing the C unsigned int type.

data CLong

Haskell type representing the C long type.

data CULong

Haskell type representing the C unsigned long type.

data CLLong

Haskell type representing the C long long type.

data CULLong

Haskell type representing the C unsigned long long type.

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.

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.

data CFloat

Haskell type representing the C float type.

data CDouble

Haskell type representing the C double type.

data Bool

Instances

Bounded Bool 
Enum Bool 
Eq Bool 
Ord Bool 
Show Bool 
Ix Bool 
Typeable Bool 
IsScalar Bool 
IsBounded Bool 
IsNonNum Bool 
ArrayElem Bool 
Elem Bool 
IArray UArray Bool 
MArray (STUArray s) Bool (ST s) 

data Char

Instances

Bounded Char 
Enum Char 
Eq Char 
Ord Char 
Show Char 
Ix Char 
Typeable Char 
IsScalar Char 
IsBounded Char 
IsNonNum Char 
ArrayElem Char 
Elem Char 
IArray UArray Char 
MArray (STUArray s) Char (ST s) 

data CChar

Haskell type representing the C char type.

data CSChar

Haskell type representing the C signed char type.

data CUChar

Haskell type representing the C unsigned char type.

Array data types

data Array dim e Source

Surface arrays ---------------

Multi-dimensional arrays for array processing

Instances

Show (Array dim e) 
(Ix dim, Elem e) => Arrays (Array dim e) 

type Scalar e = Array DIM0 eSource

Scalars

type Vector e = Array DIM1 eSource

Vectors

Array element types

class (Show a, Typeable a, Typeable (ElemRepr a), Typeable (ElemRepr' a), ArrayElem (ElemRepr a), ArrayElem (ElemRepr' a)) => Elem a Source

Instances

Elem Bool 
Elem Char 
Elem Double 
Elem Float 
Elem Int 
Elem Int8 
Elem Int16 
Elem Int32 
Elem Int64 
Elem Word 
Elem Word8 
Elem Word16 
Elem Word32 
Elem Word64 
Elem () 
Elem All 
(Elem a, Elem b) => Elem (a, b) 
(Elem a, Elem b, Elem c) => Elem (a, b, c) 
(Elem a, Elem b, Elem c, Elem d) => Elem (a, b, c, d) 
(Elem a, Elem b, Elem c, Elem d, Elem e) => Elem (a, b, c, d, e) 

Array shapes & indices

class (Shape ix, Ix (ElemRepr ix)) => Ix ix whereSource

Indices as n-tuples

Methods

dim :: ix -> IntSource

size :: ix -> IntSource

Instances

Ix Int 
Ix () 
Ix (Int, Int) 
Ix (Int, Int, Int) 
Ix (Int, Int, Int, Int) 
Ix (Int, Int, Int, Int, Int) 

data All Source

Surface types (tuples of scalars) ----------------------------------

Identifier for entire dimensions in slice descriptors

Constructors

All 

Instances

Show All 
Typeable All 
Shape All 
ShapeBase All 
Elem All 

class (Shape sl, SliceIx (ElemRepr sl), Ix (Slice sl), Ix (CoSlice sl), Ix (SliceDim sl), SliceIxConv sl) => SliceIx sl whereSource

Associated Types

type Slice sl :: *Source

type CoSlice sl :: *Source

type SliceDim sl :: *Source

Methods

sliceIndex :: sl -> SliceIndex (ElemRepr sl) (Slice (ElemRepr sl)) (CoSlice (ElemRepr sl)) (SliceDim (ElemRepr sl))Source

Instances

(Shape sl, SliceIx (ElemRepr sl), Ix (Slice sl), Ix (CoSlice sl), Ix (SliceDim sl), SliceIxConv sl) => SliceIx sl 

type DIM0 = ()Source

Shorthand for common shape types

type DIM2 = (Int, Int)Source

type DIM3 = (Int, Int, Int)Source

type DIM4 = (Int, Int, Int, Int)Source

type DIM5 = (Int, Int, Int, Int, Int)Source

Array operations

arrayShape :: Ix dim => Array dim e -> dimSource

indexArray :: Array dim e -> dim -> eSource

fromIArray :: (IArray a e, Ix dim, Ix dim, Elem e) => a dim e -> Array dim eSource

Convert an IArray to an accelerated array.

toIArray :: (IArray a e, Ix dim, Ix dim, Elem e) => Array dim e -> a dim eSource

Convert an accelerated array to an IArray

fromList :: (Ix dim, Elem e) => dim -> [e] -> Array dim eSource

Convert a list (with elements in row-major order) to an accelerated array.

toList :: Array dim e -> [e]Source

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

class Delayable (ArraysRepr as) => Arrays as Source

Instances

Arrays () 
(Arrays as1, Arrays as2) => Arrays (as1, as2) 
(Ix dim, Elem e) => Arrays (Array dim e) 

Surface language

Array and scalar expressions

data Acc a Source

data Exp t Source

Instances

(Elem t, IsBounded t) => Bounded (Exp t) 
(Elem t, IsScalar t) => Enum (Exp t) 
(Elem t, IsScalar t) => Eq (Exp t) 
(Elem t, IsFloating t) => Floating (Exp t) 
(Elem t, IsFloating t) => Fractional (Exp t) 
(Elem t, IsIntegral t) => Integral (Exp t) 
(Elem t, IsNum t) => Num (Exp t) 
(Elem t, IsScalar t) => Ord (Exp t) 
(Elem t, IsNum t) => Real (Exp t) 
(Elem t, IsFloating t) => RealFloat (Exp t) 
(Elem t, IsFloating t) => RealFrac (Exp t) 
Show (Exp t) 
(Elem t, IsNum t, IsIntegral t) => Bits (Exp t) 

Scalar introduction

constant :: Elem t => t -> Exp tSource

Array introduction

use :: (Ix dim, Elem e) => Array dim e -> Acc (Array dim e)Source

unit :: Elem e => Exp e -> Acc (Scalar e)Source

Shape manipulation

reshape :: (Ix dim, Ix dim', Elem e) => Exp dim -> Acc (Array dim' e) -> Acc (Array dim e)Source

Collective array operations

slice :: forall slix e. (SliceIx slix, Elem e) => Acc (Array (SliceDim slix) e) -> Exp slix -> Acc (Array (Slice slix) e)Source

replicate :: forall slix e. (SliceIx slix, Elem e) => Exp slix -> Acc (Array (Slice slix) e) -> Acc (Array (SliceDim slix) e)Source

zip :: (Ix dim, Elem a, Elem b) => Acc (Array dim a) -> Acc (Array dim b) -> Acc (Array dim (a, b))Source

map :: (Ix dim, Elem a, Elem b) => (Exp a -> Exp b) -> Acc (Array dim a) -> Acc (Array dim b)Source

zipWith :: (Ix dim, Elem a, Elem b, Elem c) => (Exp a -> Exp b -> Exp c) -> Acc (Array dim a) -> Acc (Array dim b) -> Acc (Array dim c)Source

scan :: Elem a => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Vector a) -> (Acc (Vector a), Acc (Scalar a))Source

fold :: Elem a => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Vector a) -> Acc (Scalar a)Source

permute :: (Ix dim, Ix dim', Elem a) => (Exp a -> Exp a -> Exp a) -> Acc (Array dim' a) -> (Exp dim -> Exp dim') -> Acc (Array dim a) -> Acc (Array dim' a)Source

backpermute :: (Ix dim, Ix dim', Elem a) => Exp dim' -> (Exp dim' -> Exp dim) -> Acc (Array dim a) -> Acc (Array dim' a)Source

Conditional expressions

(?) :: Elem t => Exp Bool -> (Exp t, Exp t) -> Exp tSource

Array operations with a scalar result

(!) :: (Ix dim, Elem e) => Acc (Array dim e) -> Exp dim -> Exp eSource

shape :: Ix dim => Acc (Array dim e) -> Exp dimSource

Instances of Bounded, Enum, Eq, Ord, Bits, Num, Real, Floating,

Methods of H98 classes that we need to redefine as their signatures

(==*) :: (Elem t, IsScalar t) => Exp t -> Exp t -> Exp BoolSource

(/=*) :: (Elem t, IsScalar t) => Exp t -> Exp t -> Exp BoolSource

(<*) :: (Elem t, IsScalar t) => Exp t -> Exp t -> Exp BoolSource

(<=*) :: (Elem t, IsScalar t) => Exp t -> Exp t -> Exp BoolSource

(>*) :: (Elem t, IsScalar t) => Exp t -> Exp t -> Exp BoolSource

(>=*) :: (Elem t, IsScalar t) => Exp t -> Exp t -> Exp BoolSource

max :: (Elem t, IsScalar t) => Exp t -> Exp t -> Exp tSource

min :: (Elem t, IsScalar t) => Exp t -> Exp t -> Exp tSource

Standard functions that we need to redefine as their signatures change

Conversions

Constants

ignore :: Ix dim => Exp dimSource