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

Safe HaskellNone
LanguageHaskell2010

Feldspar.Vector.Internal

Contents

Synopsis

Types

data Vector a Source

Symbolic vector

Instances

Len Vector 
Ixmap Vector 
Pushy Vector 
(Syntax a, Show (Internal a)) => Show (Vector a) 
(Arbitrary (Internal a), Syntax a) => Arbitrary (Vector a) 
Syntax a => Syntactic (Vector a) 
Syntax a => Sized (Vector a) 
Syntax a => Indexed (Vector a) 
(ElemWise a, Syntax (Vector a)) => ElemWise (Vector a) 
CollMap (Vector a) (Vector b) 
Numeric a => Mul (Data a) (Matrix a) 
Numeric a => Mul (Data a) (Vector1 a) 
Numeric a => Mul (Vector1 a) (Matrix a) 
Numeric a => Mul (Vector1 a) (Vector1 a) 
Numeric a => Mul (Vector1 a) (Data a) 
Numeric a => Mul (Matrix a) (Matrix a) 
Numeric a => Mul (Matrix a) (Vector1 a) 
Numeric a => Mul (Matrix a) (Data a) 
type Internal (Vector a) = [Internal a] 
type Domain (Vector a) = FeldDomain 
type CollSize (Vector a) = Data Length 
type CollIndex (Vector a) = Data Index 
type Elem (Vector a) = a 
type Scalar (Vector a) = Scalar a 
type Prod (Data a) (Matrix a) = Matrix a 
type Prod (Data a) (Vector1 a) = Vector1 a 
type Prod (Vector1 a) (Matrix a) = Vector1 a 
type Prod (Vector1 a) (Vector1 a) = Data a 
type Prod (Vector1 a) (Data a) = Vector1 a 
type Prod (Matrix a) (Matrix a) = Matrix a 
type Prod (Matrix a) (Vector1 a) = Vector1 a 
type Prod (Matrix a) (Data a) = Matrix a 

type Vector1 a = Vector (Data a) Source

Non-nested vector

type Vector2 a = Vector (Vector (Data a)) Source

Two-level nested vector

Construction/conversion

segments :: Vector a -> [Vector a] Source

Breaks up a segmented vector into a list of single-segment vectors.

mergeSegments :: Syntax a => Vector a -> Vector a Source

Converts a segmented vector to a vector with a single segment.

freezeVector :: Type a => Vector (Data a) -> Data [a] Source

Converts a non-nested vector to a core vector.

thawVector :: Type a => Data [a] -> Vector (Data a) Source

Converts a non-nested core array to a vector.

thawVector' :: Type a => Length -> Data [a] -> Vector (Data a) Source

Operations

newLen :: Syntax a => Data Length -> Vector a -> Vector 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.

withLen :: (Syntax a, Syntax b) => Data Length -> (Vector a -> Vector b) -> Vector a -> Vector b Source

Change the length of the vector before and after calling the function.

(++) :: Vector a -> Vector a -> Vector a infixr 5 Source

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

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

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

Permute a single-segment vector

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

Permute a vector

enumFromTo :: forall a. Integral a => Data a -> Data a -> Vector (Data a) Source

enumFromTo m n: Enumerate the integers from m to n

enumFrom :: Integral a => Data a -> Vector (Data a) Source

enumFrom m: Enumerate the indexes from m to maxBound

(...) :: Integral a => Data a -> Data a -> Vector (Data a) Source

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

map f v is the Vector obtained by applying f to each element of f.

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

Zipping two Vectors

zip3 :: (Syntax a, Syntax b, Syntax c) => Vector a -> Vector b -> Vector c -> Vector (a, b, c) Source

Zipping three Vectors

zip4 :: (Syntax a, Syntax b, Syntax c, Syntax d) => Vector a -> Vector b -> Vector c -> Vector d -> Vector (a, b, c, d) Source

Zipping four Vectors

zip5 :: (Syntax a, Syntax b, Syntax c, Syntax d, Syntax e) => Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector (a, b, c, d, e) Source

Zipping five Vectors

unzip :: Vector (a, b) -> (Vector a, Vector b) Source

Unzip to two Vectors

unzip3 :: Vector (a, b, c) -> (Vector a, Vector b, Vector c) Source

Unzip to three Vectors

unzip4 :: Vector (a, b, c, d) -> (Vector a, Vector b, Vector c, Vector d) Source

Unzip to four Vectors

unzip5 :: Vector (a, b, c, d, e) -> (Vector a, Vector b, Vector c, Vector d, Vector e) Source

Unzip to five Vectors

zipWith :: (Syntax a, Syntax b) => (a -> b -> c) -> Vector a -> Vector b -> Vector c Source

Generalization of zip using the supplied function instead of tupling to combine the elements

zipWith3 :: (Syntax a, Syntax b, Syntax c) => (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector d Source

Generalization of zip3 using the supplied function instead of tupling to combine the elements

zipWith4 :: (Syntax a, Syntax b, Syntax c, Syntax d) => (a -> b -> c -> d -> e) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e Source

Generalization of zip4 using the supplied function instead of tupling to combine the elements

zipWith5 :: (Syntax a, Syntax b, Syntax c, Syntax d, Syntax e) => (a -> b -> c -> d -> e -> f) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector f Source

Generalization of zip5 using the supplied function instead of tupling to combine the elements

fold :: Syntax a => (a -> b -> a) -> a -> Vector b -> a Source

Corresponds to the standard foldl.

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

Corresponds to the standard foldl1.

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

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

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

any :: (a -> Data Bool) -> Vector a -> Data Bool Source

all :: (a -> Data Bool) -> Vector a -> Data Bool Source

eqVector :: Eq a => Vector (Data a) -> Vector (Data a) -> Data Bool Source

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

Scalar product of two vectors

scan :: (Syntax a, Syntax b) => (a -> b -> a) -> a -> Vector b -> Vector a Source

tVec :: Patch a a -> Patch (Vector a) (Vector a) Source

tVec1 :: Patch a a -> Patch (Vector (Data a)) (Vector (Data a)) Source