synthesizer-llvm-1.0: Efficient signal processing using runtime compilation
Safe HaskellSafe-Inferred
LanguageHaskell98

Synthesizer.LLVM.Generator.Render

Synopsis

Documentation

derefFillPtr :: Importer (Ptr param -> Word -> Ptr struct -> IO Word) Source #

compile :: (C a, T a ~ value, C param, Struct param ~ paramStruct) => (Exp param -> T value) -> IO (Ptr paramStruct -> Word -> Ptr a -> IO Word) Source #

runAux :: (C p, C a, T a ~ value) => (Exp p -> T value) -> IO (IO () -> Int -> p -> IO (Vector a)) Source #

run_ :: (C p, C a, T a ~ value) => (Exp p -> T value) -> IO (Int -> p -> IO (Vector a)) Source #

derefStartPtr :: Importer (Ptr param -> IO (Ptr globalState)) Source #

derefStopPtr :: Importer (Ptr globalState -> IO ()) Source #

derefChunkPtr :: Importer (Ptr globalState -> Word -> Ptr a -> IO Word) Source #

type MemoryPtr a = Ptr (Struct a) Source #

type WithGlobalState param = Struct (param, ()) Source #

type Pair a b = Struct (a, (b, ())) Source #

type Triple a b c = Struct (a, (b, (c, ()))) Source #

tripleStruct :: (IsSized a, IsSized b, IsSized c) => Value a -> Value b -> Value c -> CodeGenFunction r (Value (Triple a b c)) Source #

compileHandler :: (C param, Struct param ~ paramStruct, C a, T a ~ value) => (Exp param -> T value) -> CodeGenModule (Function (Word8 -> Ptr paramStruct -> Word -> Ptr a -> IO (Pair (Ptr (WithGlobalState paramStruct)) Word))) Source #

This is a pretty ugly hack, but its seems to be the least ugly one. We need to solve the following problem: We have a function of type Exp param -> T value. This means that all methods in T value depend on Exp param. We need to choose one piece of LLVM code in Exp param that generates appropriate code for all methods in T value. If we access a function parameter via Memory.load paramPtr this means that all methods must end up in the same LLVM function in order to access this parameter. Thus I have to put all functionality in one LLVM function and then the three functions in compileChunky jump into the handler function with a Word8 code specifying the actual sub-routine. We need to squeeze all possible inputs and outputs through one function interface.

However, since the handler is marked as internal the optimizer inlines it in the three functions from compileChunky and eliminates dead code. This way, we end up with the code that we would have written otherwise.

The alternative would be to construct T value multiple times. Due to existential quantification we cannot prove that the pointer types of different methods match, so we need to cast pointers. However, with the current approach we also have to do that.

compileChunky :: (IsSized paramStruct, Value (Ptr paramStruct) ~ pPtr, C state, Struct state ~ stateStruct, C global, Struct global ~ globalStruct, Triple paramStruct globalStruct stateStruct ~ triple, IsSized local, C a, T a ~ value) => (forall r z. Phi z => pPtr -> global -> Value (Ptr local) -> () -> state -> T r z (value, state)) -> (forall r. pPtr -> CodeGenFunction r (global, state)) -> (forall r. pPtr -> global -> CodeGenFunction r ()) -> IO (Ptr paramStruct -> IO (Ptr triple), Finalizer triple, Ptr triple -> Word -> Ptr a -> IO Word) Source #

runChunkyAux :: (C a, T a ~ value, C p) => (Exp p -> T value) -> IO (IO () -> ChunkSize -> p -> IO (Vector a)) Source #

runChunky :: (C a, T a ~ value, C p) => (Exp p -> T value) -> IO (ChunkSize -> p -> IO (Vector a)) Source #

runChunkyOnVector :: (C a, T a ~ al) => (C b, T b ~ bl) => (T al -> T bl) -> IO (ChunkSize -> Vector a -> IO (Vector b)) Source #

class Run f where Source #

Associated Types

type DSL f Source #

type Shape f Source #

Methods

build :: C p => (Exp p -> DSL f) -> IO (IO (p, IO ()) -> Shape f -> f) Source #

Instances

Instances details
RunIO a => Run (IO a) Source # 
Instance details

Defined in Synthesizer.LLVM.Generator.Render

Associated Types

type DSL (IO a) Source #

type Shape (IO a) Source #

Methods

build :: C p => (Exp p -> DSL (IO a)) -> IO (IO (p, IO ()) -> Shape (IO a) -> IO a) Source #

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

Defined in Synthesizer.LLVM.Generator.Render

Associated Types

type DSL (Vector a) Source #

type Shape (Vector a) Source #

Methods

build :: C p => (Exp p -> DSL (Vector a)) -> IO (IO (p, IO ()) -> Shape (Vector a) -> Vector a) Source #

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

Defined in Synthesizer.LLVM.Generator.Render

Associated Types

type DSL (Vector a) Source #

type Shape (Vector a) Source #

Methods

build :: C p => (Exp p -> DSL (Vector a)) -> IO (IO (p, IO ()) -> Shape (Vector a) -> Vector a) Source #

(RunArg a, Run f) => Run (a -> f) Source # 
Instance details

Defined in Synthesizer.LLVM.Generator.Render

Associated Types

type DSL (a -> f) Source #

type Shape (a -> f) Source #

Methods

build :: C p => (Exp p -> DSL (a -> f)) -> IO (IO (p, IO ()) -> Shape (a -> f) -> a -> f) Source #

class RunIO a where Source #

Associated Types

type DSL_IO a Source #

type ShapeIO a Source #

Methods

buildIO :: C p => (Exp p -> T (DSL_IO a)) -> IO (IO (p, IO ()) -> ShapeIO a -> IO a) Source #

Instances

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

Defined in Synthesizer.LLVM.Generator.Render

Associated Types

type DSL_IO (Vector a) Source #

type ShapeIO (Vector a) Source #

Methods

buildIO :: C p => (Exp p -> T (DSL_IO (Vector a))) -> IO (IO (p, IO ()) -> ShapeIO (Vector a) -> IO (Vector a)) Source #

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

Defined in Synthesizer.LLVM.Generator.Render

Associated Types

type DSL_IO (Vector a) Source #

type ShapeIO (Vector a) Source #

Methods

buildIO :: C p => (Exp p -> T (DSL_IO (Vector a))) -> IO (IO (p, IO ()) -> ShapeIO (Vector a) -> IO (Vector a)) Source #

buildIOGen :: Monad m => (final -> shape -> p -> m a) -> m (p, final) -> shape -> m a Source #

data BuildArg a Source #

Constructors

forall al.C al => BuildArg (Exp al -> DSLArg a) (a -> IO (al, IO ())) 

class RunArg a where Source #

Associated Types

type DSLArg a Source #

Instances

Instances details
RunArg Word32 Source # 
Instance details

Defined in Synthesizer.LLVM.Generator.Render

Associated Types

type DSLArg Word32 Source #

RunArg () Source # 
Instance details

Defined in Synthesizer.LLVM.Generator.Render

Associated Types

type DSLArg () Source #

Methods

buildArg :: BuildArg () Source #

RunArg Float Source # 
Instance details

Defined in Synthesizer.LLVM.Generator.Render

Associated Types

type DSLArg Float Source #

RunArg Int Source # 
Instance details

Defined in Synthesizer.LLVM.Generator.Render

Associated Types

type DSLArg Int Source #

RunArg Word Source # 
Instance details

Defined in Synthesizer.LLVM.Generator.Render

Associated Types

type DSLArg Word Source #

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

Defined in Synthesizer.LLVM.Generator.Render

Associated Types

type DSLArg (T a) Source #

Methods

buildArg :: BuildArg (T a) Source #

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

Defined in Synthesizer.LLVM.Generator.Render

Associated Types

type DSLArg (T a) Source #

Methods

buildArg :: BuildArg (T a) Source #

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

Defined in Synthesizer.LLVM.Generator.Render

Associated Types

type DSLArg (Vector a) Source #

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

Defined in Synthesizer.LLVM.Generator.Render

Associated Types

type DSLArg (Vector a) Source #

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

Defined in Synthesizer.LLVM.Generator.Render

Associated Types

type DSLArg (Buffer a) Source #

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

Defined in Synthesizer.LLVM.Server.Common

Associated Types

type DSLArg (SampleRate a) Source #

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

Defined in Synthesizer.LLVM.Generator.Render

Associated Types

type DSLArg (T time a) Source #

Methods

buildArg :: BuildArg (T time a) Source #

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

Defined in Synthesizer.LLVM.Generator.Render

Associated Types

type DSLArg (Array n a) Source #

Methods

buildArg :: BuildArg (Array n a) Source #

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

Defined in Synthesizer.LLVM.Generator.Render

Associated Types

type DSLArg (a, b) Source #

Methods

buildArg :: BuildArg (a, b) Source #

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

Defined in Synthesizer.LLVM.Generator.Render

Associated Types

type DSLArg (a, b, c) Source #

Methods

buildArg :: BuildArg (a, b, c) Source #

newtype Buffer a Source #

Constructors

Buffer (Vector a) 

Instances

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

Defined in Synthesizer.LLVM.Generator.Render

Associated Types

type DSLArg (Buffer a) Source #

type DSLArg (Buffer a) Source # 
Instance details

Defined in Synthesizer.LLVM.Generator.Render

newDisposeArg :: C handle => (a -> IO handle) -> (handle -> IO ()) -> (Exp handle -> DSLArg a) -> BuildArg a Source #

class TimeInteger int where Source #

Methods

subdivideLong :: T (T int) a -> T Int a Source #

Instances

Instances details
TimeInteger Integer Source # 
Instance details

Defined in Synthesizer.LLVM.Generator.Render

Methods

subdivideLong :: T (T Integer) a -> T Int a Source #

TimeInteger Int Source # 
Instance details

Defined in Synthesizer.LLVM.Generator.Render

Methods

subdivideLong :: T (T Int) a -> T Int0 a Source #

run :: Run f => DSL f -> IO (Shape f -> f) Source #