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

Safe HaskellNone
LanguageHaskell98

Synthesizer.LLVM.Causal.Render

Contents

Synopsis

type driven

class RunArg a Source #

Minimal complete definition

buildArg

Instances
RunArg Float Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

Associated Types

type DSLArg Float :: Type Source #

Methods

buildArg :: T Float (DSLArg Float)

RunArg Int Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

Associated Types

type DSLArg Int :: Type Source #

Methods

buildArg :: T Int (DSLArg Int)

RunArg Word Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

Associated Types

type DSLArg Word :: Type Source #

Methods

buildArg :: T Word (DSLArg Word)

RunArg Word32 Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

Associated Types

type DSLArg Word32 :: Type Source #

RunArg () Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

Associated Types

type DSLArg () :: Type Source #

Methods

buildArg :: T () (DSLArg ())

a ~ ChunkSize => RunArg (T a) Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

Associated Types

type DSLArg (T a) :: Type Source #

Methods

buildArg :: T0 (T a) (DSLArg (T a))

RunArg a => RunArg (T a) Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

Associated Types

type DSLArg (T a) :: Type Source #

Methods

buildArg :: T0 (T a) (DSLArg (T a))

C a => RunArg (Vector a) Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

Associated Types

type DSLArg (Vector a) :: Type Source #

Methods

buildArg :: T (Vector a) (DSLArg (Vector a))

C a => RunArg (Vector a) Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

Associated Types

type DSLArg (Vector a) :: Type Source #

Methods

buildArg :: T (Vector a) (DSLArg (Vector a))

C a => RunArg (Buffer a) Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

Associated Types

type DSLArg (Buffer a) :: Type Source #

Methods

buildArg :: T (Buffer a) (DSLArg (Buffer a))

RunArg a => RunArg (SampleRate a) Source # 
Instance details

Defined in Synthesizer.LLVM.Server.Common

Associated Types

type DSLArg (SampleRate a) :: Type Source #

Methods

buildArg :: T (SampleRate a) (DSLArg (SampleRate a))

(RunArg a, RunArg b) => RunArg (a, b) Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

Associated Types

type DSLArg (a, b) :: Type Source #

Methods

buildArg :: T (a, b) (DSLArg (a, b))

(time ~ T int, TimeInteger int, C a) => RunArg (T time a) Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

Associated Types

type DSLArg (T time a) :: Type Source #

Methods

buildArg :: T0 (T time a) (DSLArg (T time a))

(Natural n, C a, IsSized (Struct a), Natural (n :*: SizeOf (Struct a))) => RunArg (Array n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

Associated Types

type DSLArg (Array n a) :: Type Source #

Methods

buildArg :: T (Array n a) (DSLArg (Array n a))

(RunArg a, RunArg b, RunArg c) => RunArg (a, b, c) Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

Associated Types

type DSLArg (a, b, c) :: Type Source #

Methods

buildArg :: T (a, b, c) (DSLArg (a, b, c))

type family DSLArg a Source #

Instances
type DSLArg Float Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

type DSLArg Float = Exp Float
type DSLArg Int Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

type DSLArg Int = Exp Int
type DSLArg Word Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

type DSLArg Word = Exp Word
type DSLArg Word32 Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

type DSLArg Word32 = Exp Word32
type DSLArg () Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

type DSLArg () = ()
type DSLArg (T a) Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

type DSLArg (T a) = T (T ())
type DSLArg (T a) Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

type DSLArg (T a) = T (DSLArg a)
type DSLArg (Vector a) Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

type DSLArg (Vector a) = T (T a)
type DSLArg (Vector a) Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

type DSLArg (Vector a) = T (T a)
type DSLArg (Buffer a) Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

type DSLArg (Buffer a) = Exp (StorableVector a)
type DSLArg (SampleRate a) Source # 
Instance details

Defined in Synthesizer.LLVM.Server.Common

type DSLArg (a, b) Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

type DSLArg (a, b) = (DSLArg a, DSLArg b)
type DSLArg (T time a) Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

type DSLArg (T time a) = T (T (T a))
type DSLArg (Array n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

type DSLArg (Array n a) = Exp (Array n a)
type DSLArg (a, b, c) Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

type DSLArg (a, b, c) = (DSLArg a, DSLArg b, DSLArg c)

run :: Run f => (In f ~ a, Default a, Element a ~ al) => (Out f ~ b, Default b, Element b ~ bl) => DSL f al bl -> IO f Source #

runPlugged :: Run f => T (In f) a -> DSL f a b -> T b (Out f) -> IO f Source #

processIO :: (C p, Read a, Default a, Default d) => (Exp p -> T (Element a) (Element d)) -> IO (p -> T a d) Source #

data Buffer a Source #

Instances
C a => RunArg (Buffer a) Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

Associated Types

type DSLArg (Buffer a) :: Type Source #

Methods

buildArg :: T (Buffer a) (DSLArg (Buffer a))

type DSLArg (Buffer a) Source # 
Instance details

Defined in Synthesizer.LLVM.Private.Render

type DSLArg (Buffer a) = Exp (StorableVector a)

explicit argument converters

runPluggedExplicit :: T (Plugs f a b) () (DSL f a b) f -> T (In f) a -> DSL f a b -> T b (Out f) -> IO f Source #

build :: (Run f, C p) => T (Plugs f a b) p (DSL f a b) f Source #

type Plugs f a b = ReaderT (T (In f) a, T b (Out f)) IO Source #

internally used in FunctionalPlug

processIOParametric :: (C p, Read a, x ~ Value (Ptr (Struct p))) => T a b -> T x b c -> T c d -> IO (Creator p -> T a d) Source #