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

Safe HaskellNone

Feldspar.BitVector

Contents

Description

A Vector interface to packed sequences of bits

Synopsis

Types and classes

class (Type w, Numeric w, Bits w, Integral w) => Unit w whereSource

A Unit is the internal representation of a BitVector

Methods

width :: Proxy w -> LengthSource

data BitVector w Source

Constructors

BitVector 

Fields

segments :: [Segment w]
 

Instances

Unit a => Syntactic (BitVector a) 
(Unit w, ~ * (Size w) (Range w)) => Indexed (BitVector w) 
Unit a => Syntax (BitVector a) 
Unit w => Wrap (BitVector w) (Data [w]) 
(Wrap t u, Unit w, Nat s) => Wrap (BitVector w -> t) (Data' s [w] -> u) 

data Segment w Source

Constructors

Segment 

Fields

numUnits :: Data Length
 
elements :: Data Index -> Data w
 

Feldspar integration of BitVector

Operations

length :: forall w. Unit w => BitVector w -> Data LengthSource

freezeBitVector :: forall w. Unit w => BitVector w -> Data [w]Source

unfreezeBitVector :: forall w. Unit w => Data [w] -> BitVector wSource

fromVector :: forall w. (Unit w, Size w ~ Range w) => Vector (Data Bool) -> BitVector wSource

Transforms a bool vector to a bitvector. Length of the vector has to be divisible by the wordlength, otherwise booleans at the end will be dropped.

toVector :: forall w. (Unit w, Size w ~ Range w) => BitVector w -> Vector (Data Bool)Source

fromBits :: forall w. Unit w => [Bool] -> BitVector wSource

fromUnits :: Unit w => [w] -> BitVector wSource

map :: (Unit w, Size w ~ Range w) => (Data Bool -> Data Bool) -> BitVector w -> BitVector wSource

takeUnits :: forall w. Unit w => Data Length -> BitVector w -> BitVector wSource

dropUnits :: forall w. Unit w => Data Length -> BitVector w -> BitVector wSource

(++) :: forall w. Unit w => BitVector w -> BitVector w -> BitVector wSource

drop :: forall w. (Unit w, Size w ~ Range w) => Data Length -> Data w -> BitVector w -> BitVector wSource

fold :: forall w a. (Syntax a, Unit w, Size w ~ Range w) => (a -> Data Bool -> a) -> a -> BitVector w -> aSource

zipWith :: forall w. (Unit w, Size w ~ Range w) => (Data Bool -> Data Bool -> Data Bool) -> BitVector w -> BitVector w -> BitVector wSource

head :: (Unit w, Size w ~ Range w) => BitVector w -> Data BoolSource

tail :: forall w. (Unit w, Size w ~ Range w) => Data Bool -> BitVector w -> BitVector wSource

Boolean functions extended to words

boolFun1 :: (Syntax t, Unit w, Size w ~ Range w) => (Data Bool -> Data Bool) -> ((Data w -> Data w) -> t) -> tSource

boolFun2 :: (Syntax t, Unit w, Size w ~ Range w) => (Data Bool -> Data Bool -> Data Bool) -> ((Data w -> Data w -> Data w) -> t) -> tSource

Wrapping for bitvectors

Patch combinators for bitvectors