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

Feldspar.Vector

Contents

Description

A high-level interface to the operations in the core language (Feldspar.Core). Many of the functions defined here are imitations of Haskell's list operations, and to a first approximation they behave accordingly.

Synopsis

Types

type Size = IntSource

Dynamic size of a vector

type Ix = IntSource

Vector index

data Par n Source

Empty type denoting a parallel (random) access pattern for elements in a vector. The argument denotes the static size of the vector.

Instances

data Seq n Source

Empty type denoting a sequential access pattern for elements in a vector. The argument denotes the static size of the vector.

Instances

data n :>> a whereSource

Symbolic vector. For example,

 Seq D10 :>> Par D5 :>> Data Int

is a sequential (symbolic) vector of parallel vectors of integers. The type numbers D10 and D5 denote the static size of the vector, i.e. the allocated size of the array used if and when the vector gets written to memory (e.g. by toPar).

If it is known that the vector will never be written to memory, it is not needed to specify a static size. In that case, it is possible to use () as the static size type. This way, attempting to write to memory will result in a type error.

The Size argument to the Indexed and Unfold constructors is called the dynamic size, since it can vary freely during execution.

Constructors

Indexed :: Data Size -> (Data Ix -> a) -> Par n :>> a 
Unfold :: Computable s => Data Size -> (s -> (a, s)) -> s -> Seq n :>> a 

Instances

RandomAccess (:>> (Par n) a) 
(NaturalT n1, NaturalT n2, Storable a, AccessPattern t1, AccessPattern t2) => Computable (:>> (t1 n1) (:>> (t2 n2) (Data a))) 
(NaturalT n, Storable a, AccessPattern t) => Computable (:>> (t n) (Data a)) 

type VectorP n a = Par n :>> Data aSource

Non-nested parallel vector

type VectorS n a = Seq n :>> Data aSource

Non-nested sequential vector

type family a :+ b Source

Addition for static vector size

type family a :* b Source

Multiplication for static vector size

Construction/conversion

class AccessPattern t whereSource

A class for generalizing over parallel and sequential vectors.

Methods

genericVector :: (Par n :>> a) -> (Seq n :>> a) -> t n :>> aSource

indexed :: Data Size -> (Data Ix -> a) -> Par n :>> aSource

Constructs a parallel vector from an index function. The function is assumed to be defined for the domain [0 .. n-1], were n is the dynamic size.

unfold :: Computable s => Data Size -> (s -> (a, s)) -> s -> Seq n :>> aSource

Constructs a sequential vector from a "step" function and an initial state.

freezeVector :: forall t n a. (NaturalT n, Storable a) => (t n :>> Data a) -> Data (n :> a)Source

Converts a non-nested vector to a core vector.

unfreezeVector :: (NaturalT n, Storable a, AccessPattern t) => Data Size -> Data (n :> a) -> t n :>> Data aSource

Converts a non-nested core vector to a parallel vector.

vector :: (NaturalT n, Storable a, AccessPattern t, ListBased a ~ a) => [a] -> t n :>> Data aSource

Constructs a non-nested vector.

toSeq :: (t n :>> a) -> Seq n :>> aSource

Convert any vector to a sequential one. This operation is always "cheap".

resize :: NaturalT n => (t m :>> a) -> t n :>> aSource

Changes the static size of a vector.

toPar :: (NaturalT n, Storable a) => (t n :>> Data a) -> VectorP n aSource

Convert any non-nested vector to a parallel one with cheap lookups. Internally, this is done by writing the vector to memory.

Operations

index :: (t :>> a) -> Data Ix -> aSource

Look up an index in a vector. This operation takes linear time for sequential vectors.

length :: (t n :>> a) -> Data SizeSource

The dynamic size of a vector

(++) :: Computable a => (t m :>> a) -> (t n :>> a) -> t (m :+ n) :>> aSource

take :: Data Int -> (t n :>> a) -> t n :>> aSource

drop :: Data Int -> (t n :>> a) -> t n :>> aSource

dropWhile :: (a -> Data Bool) -> (t n :>> a) -> t n :>> aSource

splitAt :: Data Int -> (t n :>> a) -> (t n :>> a, t n :>> a)Source

head :: (t n :>> a) -> aSource

last :: (t n :>> a) -> aSource

tail :: (t n :>> a) -> t n :>> aSource

init :: (t n :>> a) -> t n :>> aSource

tails :: AccessPattern u => (t n :>> a) -> u n :>> (t n :>> a)Source

Like Haskell's tails, but does not include the empty vector. This is actually just to make the types simpler (the result is square).

inits :: AccessPattern u => (t n :>> a) -> u n :>> (t n :>> a)Source

Like Haskell's inits, but does not include the empty vector. This is actually just to make the types simpler (the result is square).

permute :: (Data Size -> Data Ix -> Data Ix) -> (Par n :>> a) -> Par n :>> aSource

reverse :: (Par n :>> a) -> Par n :>> aSource

replicate :: AccessPattern t => Data Int -> a -> t n :>> aSource

zip :: (t n :>> a) -> (t n :>> b) -> t n :>> (a, b)Source

unzip :: (t n :>> (a, b)) -> (t n :>> a, t n :>> b)Source

map :: (a -> b) -> (t n :>> a) -> t n :>> bSource

zipWith :: (a -> b -> c) -> (t n :>> a) -> (t n :>> b) -> t n :>> cSource

fold :: Computable a => (a -> b -> a) -> a -> (t n :>> b) -> aSource

Corresponds to Haskell's foldl.

fold1 :: Computable a => (a -> a -> a) -> (t n :>> a) -> aSource

Corresponds to Haskell's foldl1.

scan :: Computable a => (a -> b -> a) -> a -> (t n :>> b) -> Seq n :>> aSource

Corresponds to Haskell's scanl.

scan1 :: Computable a => (a -> a -> a) -> (t n :>> a) -> Seq n :>> aSource

Corresponds to Haskell's scanl1.

sum :: (Num a, Computable a) => (t n :>> a) -> aSource

maximum :: Storable a => (t n :>> Data a) -> Data aSource

minimum :: Storable a => (t n :>> Data a) -> Data aSource

scalarProd :: (Primitive a, Num a) => (t n :>> Data a) -> (t n :>> Data a) -> Data aSource

Scalar product of two vectors