accelerate-0.9.0.1: An embedded language for accelerated array processing

Portabilitynon-portable (GHC extensions)
Stabilityexperimental
MaintainerManuel M T Chakravarty <chak@cse.unsw.edu.au>
Safe HaskellNone

Data.Array.Accelerate.Array.Sugar

Contents

Description

 

Synopsis

Array representation

data Array sh e whereSource

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.

Constructors

Array :: (Shape sh, Elt e) => EltRepr sh -> ArrayData (EltRepr e) -> Array sh e 

Instances

Typeable2 Array 
Show (Array sh e) 
Delayable (Array sh e) 
(Shape sh, Elt e) => Arrays (Array sh e) 

type Scalar e = Array DIM0 eSource

Scalars

type Vector e = Array DIM1 eSource

Vectors

type Segments = Vector IntSource

Segment descriptor

Class of supported surface element types and their mapping to representation types

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

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

Instances

Elt Bool 
Elt Char 
Elt Double 
Elt Float 
Elt Int 
Elt Int8 
Elt Int16 
Elt Int32 
Elt Int64 
Elt Word 
Elt Word8 
Elt Word16 
Elt Word32 
Elt Word64 
Elt () 
Elt All 
Elt Z 
Shape sh => Elt (Any (:. sh Int)) 
Elt (Any Z) 
(Elt a, Elt b) => Elt (a, b) 
(Elt t, Elt h) => Elt (:. t h) 
(Elt a, Elt b, Elt c) => Elt (a, b, c) 
(Elt a, Elt b, Elt c, Elt d) => Elt (a, b, c, d) 
(Elt a, Elt b, Elt c, Elt d, Elt e) => Elt (a, b, c, d, e) 
(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => Elt (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) 
(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) 
(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) 

type family EltRepr a :: *Source

Representation change for array element types ----------------------------------------------

Type representation mapping

We represent tuples by using '()' and '(,)' as type-level nil and snoc to construct snoc-lists of types.

type family EltRepr' a :: *Source

Derived functions

liftToElt :: (Elt a, Elt b) => (EltRepr a -> EltRepr b) -> a -> bSource

liftToElt2 :: (Elt a, Elt b, Elt c) => (EltRepr a -> EltRepr b -> EltRepr c) -> a -> b -> cSource

sinkFromElt :: (Elt a, Elt b) => (a -> b) -> EltRepr a -> EltRepr bSource

sinkFromElt2 :: (Elt a, Elt b, Elt c) => (a -> b -> c) -> EltRepr a -> EltRepr b -> EltRepr cSource

Array shapes

type DIM0 = ZSource

Array indexing and slicing

data Z Source

Surface types representing array indices and slices ----------------------------------------------------

Array indices are snoc type lists

For example, the type of a rank-2 array index is 'Z :.Int :. Int'.

Rank-0 index

Constructors

Z 

Instances

Show Z 
Typeable Z 
Slice Z 
Shape Z 
Elt Z 
Unlift Z 
Lift Z 
Elt e => Stencil DIM1 e (e, e, e) 
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e) 
Elt e => Stencil DIM1 e (e, e, e, e, e) 
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e) 
Elt e => Stencil DIM1 e (e, e, e, e, e, e, e) 
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) 
Elt e => Stencil DIM1 e (e, e, e, e, e, e, e, e, e) 
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) 
Elt (Any Z) 

data tail :. head Source

Increase an index rank by one dimension

Constructors

tail :. head 

Instances

Typeable2 :. 
Elt e => Stencil DIM1 e (e, e, e) 
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e) 
Elt e => Stencil DIM1 e (e, e, e, e, e) 
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e) 
Elt e => Stencil DIM1 e (e, e, e, e, e, e, e) 
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) 
Elt e => Stencil DIM1 e (e, e, e, e, e, e, e, e, e) 
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) 
Shape sh => Elt (Any (:. sh Int)) 
(Show tail, Show head) => Show (:. tail head) 
Slice sl => Slice (:. sl Int) 
Slice sl => Slice (:. sl All) 
Shape sh => Shape (:. sh Int) 
(Elt t, Elt h) => Elt (:. t h) 
(Elt e, Slice (Plain ix), Unlift ix) => Unlift (:. ix (Exp e)) 
(Elt e, Slice (Plain ix), Lift ix) => Lift (:. ix (Exp e)) 
(Slice (Plain ix), Lift ix) => Lift (:. ix All) 
(Slice (Plain ix), Lift ix) => Lift (:. ix Int) 
(Stencil (:. sh Int) a row1, Stencil (:. sh Int) a row2, Stencil (:. sh Int) a row3) => Stencil (:. (:. sh Int) Int) a (row1, row2, row3) 
(Stencil (:. sh Int) a row2, Stencil (:. sh Int) a row1, Stencil (:. sh Int) a row0) => Stencil (:. (:. sh Int) Int) a (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) 
(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) 
(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) 
(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) 
(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) 
(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) 

data All Source

Marker for entire dimensions in slice descriptors

Constructors

All 

Instances

Show All 
Typeable All 
Elt All 
Slice sl => Slice (:. sl All) 
(Slice (Plain ix), Lift ix) => Lift (:. ix All) 

data Any sh Source

Marker for arbitrary shapes in slice descriptors

Constructors

Any 

Instances

Typeable1 Any 
Show (Any sh) 
Shape sh => Slice (Any sh) 
Shape sh => Elt (Any (:. sh Int)) 
Elt (Any Z) 
Shape sh => Lift (Any sh) 

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

Shapes and indices of multi-dimensional arrays

Methods

dim :: sh -> IntSource

Number of dimensions of a shape or index (>= 0).

size :: sh -> IntSource

Total number of elements in an array of the given shape.

ignore :: shSource

Magic value identifying elements ignored in permute.

index :: sh -> sh -> IntSource

Map a multi-dimensional index into one in a linear, row-major representation of the array (first argument is the shape, second argument is the index).

bound :: sh -> sh -> Boundary a -> Either a shSource

Apply a boundary condition to an index.

iter :: sh -> (sh -> a) -> (a -> a -> a) -> a -> aSource

Iterate through the entire shape, applying the function; third argument combines results and fourth is returned in case of an empty iteration space; the index space is traversed in row-major order.

rangeToShape :: (sh, sh) -> shSource

Convert a minpoint-maxpoint index into a shape.

shapeToRange :: sh -> (sh, sh)Source

Convert a shape into a minpoint-maxpoint index.

shapeToList :: sh -> [Int]Source

Convert a shape to a list of dimensions.

listToShape :: [Int] -> shSource

Convert a list of dimensions into a shape.

sliceAnyIndex :: sh -> SliceIndex (EltRepr (Any sh)) (EltRepr sh) () (EltRepr sh)Source

The slice index for slice specifier 'Any sh'

Instances

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

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

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

Associated Types

type SliceShape sl :: *Source

type CoSliceShape sl :: *Source

type FullShape sl :: *Source

Instances

Slice Z 
Shape sh => Slice (Any sh) 
Slice sl => Slice (:. sl Int) 
Slice sl => Slice (:. sl All) 

Array shape query, indexing, and conversions

shape :: Shape sh => Array sh e -> shSource

Yield an array's shape

(!) :: Array sh e -> sh -> eSource

Array indexing

newArray :: (Shape sh, Elt e) => sh -> (sh -> e) -> Array sh eSource

Create an array from its representation function

allocateArray :: (Shape sh, Elt e) => sh -> Array sh eSource

Creates a new, uninitialized Accelerate array.

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

Convert an IArray to an accelerated array.

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

Convert an accelerated array to an IArray

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

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

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

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