synthesizer-llvm-0.8.1.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) Source 
Num v => Num (T v) Source 
Storable v => Storable (T v) Source 
C v => C (T v) Source 
Additive v => Additive (T v) Source 
PseudoRing v => PseudoRing (T v) Source 
PseudoModule v => PseudoModule (T v) Source 
IntegerConstant v => IntegerConstant (T v) Source 
Field v => Field (T v) Source 
RationalConstant v => RationalConstant (T v) Source 
Real v => Real (T v) Source 
Fraction v => Fraction (T v) Source 
Algebraic v => Algebraic (T v) Source 
Transcendental v => Transcendental (T v) Source 
Undefined v => Undefined (T v) Source 
Zero v => Zero (T v) Source 
MakeValueTuple v => MakeValueTuple (T v) Source 
Phi v => Phi (T v) Source 
Simple v => Sized (T v) Source 
(C v, Zero v) => Zero (T v) Source 
C v => C (T v) Source 
Simple v => Read (T v) Source

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) Source 
type Arguments f (T v) = f (T v) Source 
type Struct (T v) = Struct v Source 
type Scalar (T v) = Scalar v Source 
type ValueTuple (T v) = T (ValueTuple v) Source 
type Size (T v) = Size v Source 
type WriteIt (T v) = v Source 
type Element (T v) = Element v Source 
type ReadIt (T v) = v Source 

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) Source 
Simple v => Read (T v) Source

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) Source 
Read v => Read (Nodes02 v) Source 
(Read va, Read vb, (~) * (Size va) (Size vb)) => Read (va, vb) Source 
(Positive n, IsPrimitive a, IsFirstClass a) => Read (Value n a) Source

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) Source 

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) Source 
C v => C (T v) Source 
C v => C (Nodes13 v) Source 
C v => C (Nodes02 v) Source 
(C va, C vb, (~) * (Size va) (Size vb)) => C (va, vb) Source 
(Positive n, IsPrimitive a, IsFirstClass a) => C (Value n a) Source

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) Source 

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

Instances

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

newtype Iterator mode it v Source

Constructors

Iterator it 

Instances

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

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) Source

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) Source 
Simple v => Sized (T v) Source 
Sized value => Sized (Nodes13 value) Source 
Sized value => Sized (Nodes02 value) Source 
(Sized value0, Sized value1, (~) * (Size value0) (Size value1)) => Sized (value0, value1) Source 
Positive n => Sized (Value n a) Source 
(Sized value0, Sized value1, Sized value2, (~) * (Size value0) (Size value1), (~) * (Size value1) (Size value2)) => Sized (value0, value1, value2) Source 

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