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

Safe HaskellNone
LanguageHaskell98

Synthesizer.LLVM.Filter.ComplexFirstOrderPacked

Documentation

data Parameter a Source #

Constructors

Parameter (Vector D3 a) (Vector D3 a) 

parameterPlain :: C a => a -> a -> Parameter a Source #

parameter :: (Transcendental a, RationalConstant a) => Exp a -> Exp a -> ParameterExp a Source #

causal :: (Vector n a, n ~ D3, PseudoRing a) => T (ParameterMV a, T (T a)) (T (T a)) Source #

data ParameterMV a Source #

Instances
Vector D3 a => C (ParameterMV a) Source # 
Instance details

Defined in Synthesizer.LLVM.Filter.ComplexFirstOrderPacked

Associated Types

type Struct (ParameterMV a) :: Type

Methods

load :: Value (Ptr (Struct (ParameterMV a))) -> CodeGenFunction r (ParameterMV a)

store :: ParameterMV a -> Value (Ptr (Struct (ParameterMV a))) -> CodeGenFunction r ()

decompose :: Value (Struct (ParameterMV a)) -> CodeGenFunction r (ParameterMV a)

compose :: ParameterMV a -> CodeGenFunction r (Value (Struct (ParameterMV a)))

C a => Phi (ParameterMV a) Source # 
Instance details

Defined in Synthesizer.LLVM.Filter.ComplexFirstOrderPacked

Methods

phi :: BasicBlock -> ParameterMV a -> CodeGenFunction r (ParameterMV a)

addPhi :: BasicBlock -> ParameterMV a -> ParameterMV a -> CodeGenFunction r ()

C a => Undefined (ParameterMV a) Source # 
Instance details

Defined in Synthesizer.LLVM.Filter.ComplexFirstOrderPacked

Methods

undef :: ParameterMV a

(Vector n a, n ~ D3, PseudoRing a, inp ~ T a, out ~ T a) => C (ParameterMV a) (T inp) (T out) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Controlled

Associated Types

type Input (ParameterMV a) (T out) :: Type Source #

type Output (ParameterMV a) (T inp) :: Type Source #

Methods

process :: T0 (ParameterMV a, T inp) (T out) Source #

type Struct (ParameterMV a) Source # 
Instance details

Defined in Synthesizer.LLVM.Filter.ComplexFirstOrderPacked

type Struct (ParameterMV a)
type ExpressionsOf (ParameterMV a) Source # 
Instance details

Defined in Synthesizer.LLVM.Filter.ComplexFirstOrderPacked

type ExpressionsOf (ParameterMV a)
type Input (ParameterMV a) (T out) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Controlled

type Input (ParameterMV a) (T out) = T out
type Output (ParameterMV a) (T inp) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Controlled

type Output (ParameterMV a) (T inp) = T inp