feldspar-language-0.6.0.2: A functional embedded language for DSP and parallelism

Safe HaskellNone

Feldspar.Repa

Contents

Synopsis

Documentation

data Z Source

  • Shapes

Constructors

Z 

Instances

data tail :. head Source

Constructors

tail :. head 

Instances

Slice sl => Slice (:. sl All) 
Slice sl => Slice (:. sl (Data Length)) 
Shape sh => Shape (:. sh (Data Length)) 

type DIM0 = ZSource

class Shape sh whereSource

Methods

dim :: sh -> IntSource

Get the number of dimensions in a shape

zeroDim :: shSource

The shape of an array of size zero, with a particular dimension

unitDim :: shSource

The shape of an array with size one, with a particular dimension

size :: sh -> Data LengthSource

Get the total number of elements in an array with this shape.

toIndex :: sh -> sh -> Data IndexSource

Index into flat, linear, row-major representation

fromIndex :: sh -> Data Index -> shSource

Inverse of toIndex.

intersectDim :: sh -> sh -> shSource

The intersection of two dimensions.

inRange :: sh -> sh -> sh -> Data BoolSource

Check whether an index is within a given shape. inRange l u i checks that i fits between l and u.

toList :: sh -> [Data Length]Source

Turn a shape into a list. Used in the Syntactic instance.

toShape :: Int -> Data [Length] -> shSource

Reconstruct a shape. Used in the Syntactic instance.

Instances

Shape Z 
Shape sh => Shape (:. sh (Data Length)) 

data All Source

  • Slices

Constructors

All 

Instances

Slice sl => Slice (:. sl All) 

data Any sh Source

Constructors

Any 

Instances

Slice (Any sh) 

type family FullShape ss Source

type family SliceShape ss Source

class Slice ss whereSource

Instances

Slice Z 
Slice (Any sh) 
Slice sl => Slice (:. sl All) 
Slice sl => Slice (:. sl (Data Length)) 

data Vector sh a Source

  • Vectors

Constructors

Vector sh (sh -> a) 

Instances

Annotatable a => Annotatable (Vector s a) 
(Shape sh, Syntax a) => Syntactic (Vector sh a) 
(Syntax a, Shape sh) => Sized (Vector sh a) 
Syntax a => Indexed (Vector sh a) 
(Syntactic (Vector sh a), ~ (* -> *) (Domain (Vector sh a)) FeldDomainAll, Type (Internal (Vector sh a)), Shape sh, Syntax a) => Syntax (Vector sh a) 
CollMap (Vector sh a) (Vector sh a) 

type DVector sh a = Vector sh (Data a)Source

fromVector :: (Shape sh, Type a) => DVector sh a -> Data [a]Source

  • Fuctions

Store a vector in an array.

toVector :: (Shape sh, Type a) => sh -> Data [a] -> DVector sh aSource

Restore a vector from an array

freezeVector :: (Shape sh, Type a) => DVector sh a -> (Data [Length], Data [a])Source

fromList :: Type a => [Data a] -> Data [a]Source

thawVector :: (Shape sh, Type a) => (Data [Length], Data [a]) -> DVector sh aSource

memorize :: (Shape sh, Type a) => DVector sh a -> DVector sh aSource

Store a vector in memory. Use this function instead of force if possible as it is both much more safe and faster.

extent :: Vector sh a -> shSource

The shape and size of the vector

newExtent :: sh -> Vector sh a -> Vector sh aSource

Change the extent of the vector to the supplied value. If the supplied extent will contain more elements than the old extent, the new elements will have undefined value.

traverse :: (Shape sh, Shape sh') => Vector sh a -> (sh -> sh') -> ((sh -> a) -> sh' -> a') -> Vector sh' a'Source

Change shape and transform elements of a vector. This function is the most general way of manipulating a vector.

replicate :: (Slice sl, Shape (FullShape sl), Shape (SliceShape sl)) => sl -> Vector (SliceShape sl) a -> Vector (FullShape sl) aSource

Duplicates part of a vector along a new dimension.

slice :: (Slice sl, Shape (FullShape sl), Shape (SliceShape sl)) => Vector (FullShape sl) a -> sl -> Vector (SliceShape sl) aSource

Extracts a slice from a vector.

reshape :: (Shape sh, Shape sh') => sh -> Vector sh' a -> Vector sh aSource

Change the shape of a vector. This function is potentially unsafe, the new shape need to have fewer or equal number of elements compared to the old shape.

unit :: a -> Vector Z aSource

A scalar (zero dimensional) vector

(!:) :: Shape sh => Vector sh a -> sh -> aSource

Index into a vector

diagonal :: Vector DIM2 a -> Vector DIM1 aSource

Extract the diagonal of a two dimensional vector

backpermute :: (Shape sh, Shape sh') => sh' -> (sh' -> sh) -> Vector sh a -> Vector sh' aSource

Change the shape of a vector.

map :: (a -> b) -> Vector sh a -> Vector sh bSource

Map a function on all the elements of a vector

zip :: Shape sh => Vector sh a -> Vector sh b -> Vector sh (a, b)Source

Combines the elements of two vectors. The size of the resulting vector will be the intersection of the two argument vectors.

zipWith :: Shape sh => (a -> b -> c) -> Vector sh a -> Vector sh b -> Vector sh cSource

Combines the elements of two vectors pointwise using a function. The size of the resulting vector will be the intersection of the two argument vectors.

fold :: (Shape sh, Syntax a) => (a -> a -> a) -> a -> Vector (sh :. Data Length) a -> Vector sh aSource

Reduce a vector along its last dimension

fold' :: (Shape sh, Syntax a) => (a -> a -> a) -> Vector sh a -> Vector (sh :. Data Length) a -> Vector sh aSource

A generalization of fold which allows for different initial values when starting to fold.

sum :: (Shape sh, Type a, Numeric a) => DVector (sh :. Data Length) a -> DVector sh aSource

Summing a vector along its last dimension

(...) :: Data Index -> Data Index -> DVector DIM1 IndexSource

Enumerating a vector

mmMult :: (Type e, Numeric e) => DVector DIM2 e -> DVector DIM2 e -> DVector DIM2 eSource

Matrix multiplication

Operations on one dimensional vectors

newLen :: Syntax a => Data Length -> Vector DIM1 a -> Vector DIM1 aSource

Change the length of the vector to the supplied value. If the supplied length is greater than the old length, the new elements will have undefined value. The resulting vector has only one segment.

head :: Syntax a => Vector DIM1 a -> aSource

last :: Syntax a => Vector DIM1 a -> aSource

permute :: (Data Length -> Data Index -> Data Index) -> Vector DIM1 a -> Vector DIM1 aSource

Permute a vector

enumFromTo :: Data Index -> Data Index -> Vector DIM1 (Data Index)Source

enumFromTo m n: Enumerate the indexes from m to n

In order to enumerate a different type, use i2n, e.g:

 map i2n (10...20) :: Vector1 Word8

enumFrom :: Data Index -> Vector DIM1 (Data Index)Source

enumFrom m: Enumerate the indexes from m to maxBound

foldl :: Syntax a => (a -> b -> a) -> a -> Vector DIM1 b -> aSource

Corresponds to the standard foldl.

fold1 :: Syntax a => (a -> a -> a) -> Vector DIM1 a -> aSource

Corresponds to the standard foldl1.

sum1 :: (Syntax a, Num a) => Vector DIM1 a -> aSource

scalarProd :: (Syntax a, Num a) => Vector DIM1 a -> Vector DIM1 a -> aSource

Scalar product of two vectors