synthesizer-llvm-0.7.0.1: Efficient signal processing using runtime compilation

Safe HaskellNone
LanguageHaskell98

Synthesizer.LLVM.Frame.SerialVector

Description

A special vector type that represents a time-sequence of samples. This way we can distinguish safely between LLVM vectors used for parallel signals and pipelines and those used for chunky processing of scalar signals. For the chunky processing this data type allows us to derive the factor from the type that time constants have to be multiplied with.

Synopsis

Documentation

newtype T v Source

Constructors

Cons v 

Instances

Eq v => Eq (T v) 
Num v => Num (T v) 
Storable v => Storable (T v) 
C v => C (T v) 
Additive v => Additive (T v) 
PseudoRing v => PseudoRing (T v) 
PseudoModule v => PseudoModule (T v) 
IntegerConstant v => IntegerConstant (T v) 
Field v => Field (T v) 
RationalConstant v => RationalConstant (T v) 
Real v => Real (T v) 
Fraction v => Fraction (T v) 
Algebraic v => Algebraic (T v) 
Transcendental v => Transcendental (T v) 
Undefined v => Undefined (T v) 
Zero v => Zero (T v) 
MakeValueTuple v => MakeValueTuple (T v) 
Phi v => Phi (T v) 
Simple v => Sized (T v) 
(C v, Zero v) => Zero (T v) 
C v => C (T v) 
Simple v => Read (T v)

This instance also allows to wrap tuples of vectors, but you cannot reasonably use them, because it would mean to serialize vectors with different element types.

MakeArguments (T v) 
type Arguments f (T v) = f (T v) 
type Struct (T v) = Struct v 
type Scalar (T v) = Scalar v 
type ValueTuple (T v) = T (ValueTuple v) 
type Size (T v) = Size v 
type WriteIt (T v) = v 
type Element (T v) = Element v 
type ReadIt (T v) = v 

type Plain n a = T (Vector n a) Source

type Value n a = T (Value (Vector n a)) Source

plain :: Vector n a -> Plain n a Source

value :: Value (Vector n a) -> Value n a Source

constant :: Positive n => a -> T (Constant n a) Source

class (Positive (Size v), Sized v, Phi (ReadIt v), Undefined (ReadIt v), Phi v, Undefined v) => Read v where Source

Minimal complete definition

extract, readStart, readNext

Associated Types

type Element v :: * Source

type ReadIt v :: * Source

Instances

Read v => Read (T v) 
Read v => Read (Result v) 
Simple v => Read (T v)

This instance also allows to wrap tuples of vectors, but you cannot reasonably use them, because it would mean to serialize vectors with different element types.

Read v => Read (Nodes13 v) 
Read v => Read (Nodes02 v) 
(Read va, Read vb, (~) * (Size va) (Size vb)) => Read (va, vb) 
(Positive n, IsPrimitive a, IsFirstClass a) => Read (Value n a)

The implementation of extract may need to perform arithmetics at run-time and is thus a bit inefficient.

(Read va, Read vb, Read vc, (~) * (Size va) (Size vb), (~) * (Size vb) (Size vc)) => Read (va, vb, vc) 

class (Read v, Phi (WriteIt v), Undefined (WriteIt v)) => C v where Source

Minimal complete definition

insert, writeStart, writeNext, writeStop

Associated Types

type WriteIt v :: * Source

Instances

C v => C (T v) 
C v => C (Result v) 
C v => C (T v) 
C v => C (Nodes13 v) 
C v => C (Nodes02 v) 
(C va, C vb, (~) * (Size va) (Size vb)) => C (va, vb) 
(Positive n, IsPrimitive a, IsFirstClass a) => C (Value n a)

The implementation of insert may need to perform arithmetics at run-time and is thus a bit inefficient.

(C va, C vb, C vc, (~) * (Size va) (Size vb), (~) * (Size vb) (Size vc)) => C (va, vb, vc) 

class (C v, Phi (WriteIt v), Zero (WriteIt v)) => Zero v where Source

Instances

Zero v => Zero (T v) 
(C v, Zero v) => Zero (T v) 
(Zero va, Zero vb, (~) * (Size va) (Size vb)) => Zero (va, vb) 
(Zero va, Zero vb, Zero vc, (~) * (Size va) (Size vb), (~) * (Size vb) (Size vc)) => Zero (va, vb, vc) 

newtype Iterator mode it v Source

Constructors

Iterator it 

Instances

C it => C (Iterator mode it v) 
Undefined it => Undefined (Iterator mode it v) 
Phi it => Phi (Iterator mode it v) 
type Struct (Iterator mode it v) = Struct it 

class Positive (Size valueTuple) => Sized valueTuple Source

The type parameter value shall be a virtual LLVM register or a wrapper around one or more virtual LLVM registers.

Associated Types

type Size valueTuple :: * Source

Instances

Sized (Value a)

Basic LLVM types are all counted as scalar values, even LLVM Vectors. This means that an LLVM Vector can be used for parallel handling of data.

Sized value => Sized (T value) 
Sized v => Sized (Result v) 
Simple v => Sized (T v) 
Sized value => Sized (Nodes13 value) 
Sized value => Sized (Nodes02 value) 
(Sized value0, Sized value1, (~) * (Size value0) (Size value1)) => Sized (value0, value1) 
Positive n => Sized (Value n a) 
(Sized value0, Sized value1, Sized value2, (~) * (Size value0) (Size value1), (~) * (Size value1) (Size value2)) => Sized (value0, value1, value2) 

size :: Sized v => v -> Int Source

sizeOfIterator :: Sized v => Iterator mode it v -> Int Source

withSize :: Sized v => (Int -> m v) -> m v Source

iteratePlain :: Positive n => (a -> a) -> a -> Plain n a Source

reverse :: C v => v -> CodeGenFunction r v Source

shiftUp :: C v => Element v -> v -> CodeGenFunction r (Element v, v) Source

replicate :: Positive n => a -> Plain n a Source

fromList :: Positive n => T [] a -> Plain n a Source

mapPlain :: Positive n => (a -> b) -> Plain n a -> Plain n b Source

mapV :: Functor m => (Value (Vector n a) -> m (Value (Vector n b))) -> Value n a -> m (Value n b) Source

zipV :: Functor m => (c -> d) -> (Value (Vector n a) -> Value (Vector n b) -> m c) -> Value n a -> Value n b -> m d Source