clash-prelude-0.3: CAES Language for Synchronous Hardware - Prelude library

Safe HaskellNone
LanguageHaskell2010

CLaSH.Sized.Vector

Synopsis

Documentation

data Vec where Source

Constructors

Nil :: Vec 0 a 
(:>) :: a -> Vec n a -> Vec (n + 1) a 

Instances

Functor (Vec n) 
KnownNat n => Applicative (Vec n) 
Foldable (Vec n) 
Traversable (Vec n) 
Eq a => Eq (Vec n a) 
Show a => Show (Vec n a) 
(KnownNat n, KnownNat (BitSize a), BitVector a) => BitVector (Vec n a) 
Pack (Vec n a) 
type BitSize (Vec n a) = * n (BitSize a) 
type SignalP (Vec n a) = Vec n (Signal a) 

(<:) :: Vec n a -> a -> Vec (n + 1) a Source

Add an element to the tail of the vector

vhead :: Vec (n + 1) a -> a Source

Extract the first element of a vector

vtail :: Vec (n + 1) a -> Vec n a Source

Extract the elements after the head of a vector

vlast :: Vec (n + 1) a -> a Source

Extract the last element of a vector

vinit :: Vec (n + 1) a -> Vec n a Source

Extract all the elements of a vector except the last element

(+>>) :: a -> Vec n a -> Vec n a Source

Add an element to the head of the vector, and extract all elements of the resulting vector except the last element

(<<+) :: Vec n a -> a -> Vec n a Source

Add an element to the tail of the vector, and extract all elements of the resulting vector except the first element

(<++>) :: Vec n a -> Vec m a -> Vec (n + m) a Source

Append two vectors

vconcat :: Vec n (Vec m a) -> Vec (n * m) a Source

Concatenate a vector of vectors

vsplit :: SNat m -> Vec (m + n) a -> (Vec m a, Vec n a) Source

Split a vector into two vectors at the given point

vsplitI :: KnownNat m => Vec (m + n) a -> (Vec m a, Vec n a) Source

Split a vector into two vectors where the length of the two is determined by the context

vunconcat :: KnownNat n => SNat m -> Vec (n * m) a -> Vec n (Vec m a) Source

Split a vector of (n * m) elements into a vector of vectors with length m, where m is given

vunconcatI :: (KnownNat n, KnownNat m) => Vec (n * m) a -> Vec n (Vec m a) Source

Split a vector of (n * m) elements into a vector of vectors with length m, where m is determined by the context

vmerge :: Vec n a -> Vec n a -> Vec (n + n) a Source

Merge two vectors, alternating their elements, i.e.,

vmerge <xn, ..., x2, x1>  <yn, ..., y2, y1> == <xn, yn, ..., x2, y2, x1, y1>

vreverse :: Vec n a -> Vec n a Source

Returns the elements in a list in reverse order

vmap :: (a -> b) -> Vec n a -> Vec n b Source

vmap f xs is the list obtained by applying f to each element of xs, i.e.,

vmap f <xn, ..., x2, x1> == <f xn, ..., f x2, f x1>

vzipWith :: (a -> b -> c) -> Vec n a -> Vec n b -> Vec n c Source

vzipWith generalises vzip by zipping with the function given as the first argument, instead of a tupling function. For example, vzipWith (+) is applied to two vectors to produce the vector of corresponding sums.

vfoldr :: (a -> b -> b) -> b -> Vec n a -> b Source

vfoldr, applied to a binary operator, a starting value (typically the right-identity of the operator), and a vector, reduces the vector using the binary operator, from right to left:

foldr f z <xn, ..., x2, x1> == xn `f` (... (x2 `f` (x1 `f` z))...)

vfoldl :: (b -> a -> b) -> b -> Vec n a -> b Source

vfoldl, applied to a binary operator, a starting value (typically the left-identity of the operator), and a vector, reduces the vector using the binary operator, from left to right:

vfoldl f z <xn, ..., x2, x1> == (...((z `f` xn)... `f` x2) `f` x1

vfoldr1 :: (a -> a -> a) -> Vec (n + 1) a -> a Source

vfoldr1 is a variant of vfoldr that has no starting value argument, and thus must be applied to non-empty vectors.

vfoldl1 :: (a -> a -> a) -> Vec (n + 1) a -> a Source

vfoldl1 is a variant of vfoldl that has no starting value argument, and thus must be applied to non-empty vectors.

vzip :: Vec n a -> Vec n b -> Vec n (a, b) Source

vzip takes two lists and returns a list of corresponding pairs.

vunzip :: Vec n (a, b) -> (Vec n a, Vec n b) Source

vunzip transforms a list of pairs into a list of first components and a list of second components.

(!) :: (KnownNat n, Integral i) => Vec n a -> i -> a Source

Vector index (subscript) operator, descending from maxIndex, where the last element has subscript 0.

<1,2,3,4,5> ! 4 == 1
<1,2,3,4,5> ! maxIndex == 1
<1,2,3,4,5> ! 1 == 4

vreplace :: (KnownNat n, Integral i) => Vec n a -> i -> a -> Vec n a Source

Replace an element of a vector at the given index (subscript), NB: vector elements have a descending subscript starting from maxIndex and ending at 0

vreplace <1,2,3,4,5> 3 7 == <1,7,3,4,5>

maxIndex :: forall n a. KnownNat n => Vec n a -> Integer Source

Index (subscript) of the head of the vector

vtake :: SNat m -> Vec (m + n) a -> Vec m a Source

vtake n, applied to a vector xs, returns the n-length prefix of xs

vtake (snat :: SNat 3) <1,2,3,4,5> == <1,2,3>
vtake d3 <1,2,3,4,5> == <1,2,3>
vtake (snat :: SNat 0) <1,2> == <>
vtake (snat :: SNat 4) <1,2> == TYPE ERROR

vtakeI :: KnownNat m => Vec (m + n) a -> Vec m a Source

vtakeI xs, returns the prefix of xs as demanded by the context

vdrop :: SNat m -> Vec (m + n) a -> Vec n a Source

vdrop n xs returns the suffix of xs after the first n elements

vdrop (snat :: SNat 3) <1,2,3,4,5> == <4,5>
vdrop d3 <1,2,3,4,5> == <4,5>
vdrop (snat :: SNat 0) <1,2> == <1,2>
vdrop (snat :: SNat 4) <1,2> == TYPE ERROR

vdropI :: KnownNat m => Vec (m + n) a -> Vec n a Source

vdropI xs, returns the suffix of xs as demanded by the context

vexact :: SNat m -> Vec (m + (n + 1)) a -> a Source

vexact n xs returns n'th element of xs, NB: vector elements have a descending subscript starting from maxIndex and ending at 0

vexact (snat :: SNat 1) <1,2,3,4,5> == 4

vselect :: ((f + (s * n)) + 1) <= i => SNat f -> SNat s -> SNat (n + 1) -> Vec i a -> Vec (n + 1) a Source

vselect f s n xs selects n elements with stepsize s and offset f from xs

vselect (snat :: SNat 1) (snat :: SNat 2) (snat :: SNat 3) 1,2,3,4,5,6,7,8 == 2,4,6

vselectI :: (((f + (s * n)) + 1) <= i, KnownNat (n + 1)) => SNat f -> SNat s -> Vec i a -> Vec (n + 1) a Source

vselectI f s xs selects as many elements as demanded by the context with stepsize s and offset f from xs

vcopy :: SNat n -> a -> Vec n a Source

vcopy n a returns a vector that has n copies of a

vcopyI :: KnownNat n => a -> Vec n a Source

vcopy a creates a vector with as many copies of a as demanded by the context

viterate :: SNat n -> (a -> a) -> a -> Vec n a Source

viterate n f x returns a vector starting with x followed by n repeated applications of f to x

viterate (snat :: SNat 4) f x = <x, f x, f (f x), f (f (f x))>

viterateI :: KnownNat n => (a -> a) -> a -> Vec n a Source

viterate f x returns a vector starting with x followed by n repeated applications of f to x, where n is determined by the context

vgenerate :: SNat n -> (a -> a) -> a -> Vec n a Source

vgenerate n f x returns a vector with n repeated applications of f to x

vgenerate (snat :: SNat 4) f x = <f x, f (f x), f (f (f x)), f (f (f (f x)))>

vgenerateI :: KnownNat n => (a -> a) -> a -> Vec n a Source

vgenerate f x returns a vector with n repeated applications of f to x, where n is determined by the context

toList :: Vec n a -> [a] Source

Convert a vector to a list

v :: Lift a => [a] -> ExpQ Source

Create a vector literal from a list literal

$(v [1::Signed 8,2,3,4,5]) == <1,2,3,4,5> :: Vec 5 (Signed 8)