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

Safe HaskellNone
LanguageHaskell2010

Feldspar.Repa

Contents

Synopsis

Documentation

data Z Source

  • Shapes

Constructors

Z 

Instances

Slice Z 
Shape Z 
type SliceShape Z = Z 
type FullShape Z = Z 

data tail :. head infixl 3 Source

Constructors

tail :. head infixl 3 

Instances

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

type DIM0 = Z Source

class Shape sh where Source

Methods

dim :: sh -> Int Source

Get the number of dimensions in a shape

zeroDim :: sh Source

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

unitDim :: sh Source

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

size :: sh -> Data Length Source

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

toIndex :: sh -> sh -> Data Index Source

Index into flat, linear, row-major representation

fromIndex :: sh -> Data Index -> sh Source

Inverse of toIndex.

intersectDim :: sh -> sh -> sh Source

The intersection of two dimensions.

inRange :: sh -> sh -> sh -> Data Bool Source

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] -> sh Source

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) 
type SliceShape ((:.) sl All) = (:.) (SliceShape sl) (Data Length) 
type FullShape ((:.) sl All) = (:.) (FullShape sl) (Data Length) 

data Any sh Source

Constructors

Any 

Instances

Slice (Any sh) 
type SliceShape (Any sh) = sh 
type FullShape (Any sh) = sh 

type family FullShape ss Source

Instances

type FullShape Z = Z 
type FullShape (Any sh) = sh 
type FullShape ((:.) sl All) = (:.) (FullShape sl) (Data Length) 
type FullShape ((:.) sl (Data Length)) = (:.) (FullShape sl) (Data Length) 

type family SliceShape ss Source

Instances

type SliceShape Z = Z 
type SliceShape (Any sh) = sh 
type SliceShape ((:.) sl All) = (:.) (SliceShape sl) (Data Length) 
type SliceShape ((:.) sl (Data Length)) = SliceShape sl 

class Slice ss where Source

Methods

sliceOfFull :: ss -> FullShape ss -> SliceShape ss Source

fullOfSlice :: ss -> SliceShape ss -> FullShape ss Source

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

(Shape sh, Syntax a) => Syntactic (Vector sh a) 
(Syntax a, Shape sh) => Sized (Vector sh a) 
Syntax a => Indexed (Vector sh a) 
CollMap (Vector sh a) (Vector sh a) 
type Internal (Vector sh a) = ([Length], [Internal a]) 
type Domain (Vector sh a) = FeldDomain 
type CollSize (Vector sh a) = sh 
type CollIndex (Vector sh a) = sh 
type Elem (Vector sh a) = 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 a Source

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

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

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

The shape and size of the vector

newExtent :: sh -> Vector sh a -> Vector sh a Source

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) a Source

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) a Source

Extracts a slice from a vector.

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

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

A scalar (zero dimensional) vector

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

Index into a vector

diagonal :: Vector DIM2 a -> Vector DIM1 a Source

Extract the diagonal of a two dimensional vector

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

Change the shape of a vector.

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

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

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

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

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

Summing a vector along its last dimension

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

Enumerating a vector

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

Matrix multiplication

Operations on one dimensional vectors

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

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.

(++) :: Syntax a => Vector DIM1 a -> Vector DIM1 a -> Vector DIM1 a infixr 5 Source

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

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

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

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

Corresponds to the standard foldl.

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

Corresponds to the standard foldl1.

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

maximum :: Ord a => Vector DIM1 (Data a) -> Data a Source

minimum :: Ord a => Vector DIM1 (Data a) -> Data a Source

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

Scalar product of two vectors