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

Synthesizer.LLVM.Causal.Functional

Synopsis

Documentation

data T inp out Source #

Instances

Instances details
Applicative (T inp) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

Methods

pure :: a -> T inp a #

(<*>) :: T inp (a -> b) -> T inp a -> T inp b #

liftA2 :: (a -> b -> c) -> T inp a -> T inp b -> T inp c #

(*>) :: T inp a -> T inp b -> T inp b #

(<*) :: T inp a -> T inp b -> T inp a #

Functor (T inp) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

Methods

fmap :: (a -> b) -> T inp a -> T inp b #

(<$) :: a -> T inp b -> T inp a #

(PseudoRing b, Real b, IntegerConstant b) => Num (T a b) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

Methods

(+) :: T a b -> T a b -> T a b #

(-) :: T a b -> T a b -> T a b #

(*) :: T a b -> T a b -> T a b #

negate :: T a b -> T a b #

abs :: T a b -> T a b #

signum :: T a b -> T a b #

fromInteger :: Integer -> T a b #

(Field b, Real b, RationalConstant b) => Fractional (T a b) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

Methods

(/) :: T a b -> T a b -> T a b #

recip :: T a b -> T a b #

fromRational :: Rational -> T a b #

Additive b => C (T a b) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

Methods

zero :: T a b #

(+) :: T a b -> T a b -> T a b #

(-) :: T a b -> T a b -> T a b #

negate :: T a b -> T a b #

(Transcendental b, RationalConstant b) => C (T a b) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

Methods

sqrt :: T a b -> T a b #

root :: Integer -> T a b -> T a b #

(^/) :: T a b -> Rational -> T a b #

(Field b, RationalConstant b) => C (T a b) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

Methods

(/) :: T a b -> T a b -> T a b #

recip :: T a b -> T a b #

fromRational' :: Rational -> T a b #

(^-) :: T a b -> Integer -> T a b #

(PseudoRing b, IntegerConstant b) => C (T a b) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

Methods

(*) :: T a b -> T a b -> T a b #

one :: T a b #

fromInteger :: Integer -> T a b #

(^) :: T a b -> Integer -> T a b #

(Transcendental b, RationalConstant b) => C (T a b) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

Methods

pi :: T a b #

exp :: T a b -> T a b #

log :: T a b -> T a b #

logBase :: T a b -> T a b -> T a b #

(**) :: T a b -> T a b -> T a b #

sin :: T a b -> T a b #

cos :: T a b -> T a b #

tan :: T a b -> T a b #

asin :: T a b -> T a b #

acos :: T a b -> T a b #

atan :: T a b -> T a b #

sinh :: T a b -> T a b #

cosh :: T a b -> T a b #

tanh :: T a b -> T a b #

asinh :: T a b -> T a b #

acosh :: T a b -> T a b #

atanh :: T a b -> T a b #

lift :: T inp out -> T inp out Source #

fromSignal :: T out -> T inp out Source #

($&) :: T b c -> T a b -> T a c infixr 0 Source #

(&|&) :: T a b -> T a c -> T a (b, c) infixr 3 Source #

compile :: T inp out -> T inp out Source #

compileSignal :: T () out -> T out Source #

withArgs :: MakeArguments inp => (Arguments (T inp) inp -> T inp out) -> T inp out Source #

Using withArgs you can simplify

let x = F.lift (arr fst)
    y = F.lift (arr (fst.snd))
    z = F.lift (arr (snd.snd))
in  F.compile (f x y z)

to

withArgs $ \(x,(y,z)) -> f x y z

class MakeArguments arg Source #

Minimal complete definition

makeArgs

Instances

Instances details
MakeArguments () Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

Methods

makeArgs :: Functor f => f () -> Arguments f () Source #

MakeArguments (T a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

Methods

makeArgs :: Functor f => f (T a) -> Arguments f (T a) Source #

MakeArguments (Value a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

Methods

makeArgs :: Functor f => f (Value a) -> Arguments f (Value a) Source #

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

Defined in Synthesizer.LLVM.Causal.Functional

Methods

makeArgs :: Functor f => f (T a) -> Arguments f (T a) Source #

MakeArguments (Parameter a) Source # 
Instance details

Defined in Synthesizer.LLVM.Filter.Allpass

Methods

makeArgs :: Functor f => f (Parameter a) -> Arguments f (Parameter a) Source #

MakeArguments (ParameterPacked a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Exponential2

MakeArguments (AnyArg a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

Methods

makeArgs :: Functor f => f (AnyArg a) -> Arguments f (AnyArg a) Source #

MakeArguments (T a) Source # 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

Methods

makeArgs :: Functor f => f (T a) -> Arguments f (T a) Source #

MakeArguments (CascadeParameter n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Filter.Allpass

MakeArguments (ParameterValue n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Filter.SecondOrderCascade

Methods

makeArgs :: Functor f => f (ParameterValue n a) -> Arguments f (ParameterValue n a) Source #

MakeArguments (Constant n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

Methods

makeArgs :: Functor f => f (Constant n a) -> Arguments f (Constant n a) Source #

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

Defined in Synthesizer.LLVM.Causal.Functional

Methods

makeArgs :: Functor f => f (a, b) -> Arguments f (a, b) Source #

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

Defined in Synthesizer.LLVM.Causal.Functional

Methods

makeArgs :: Functor f => f (a, b, c) -> Arguments f (a, b, c) Source #

type family Arguments (f :: * -> *) arg Source #

Instances

Instances details
type Arguments f () Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

type Arguments f () = f ()
type Arguments f (T a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

type Arguments f (T a) = f (T a)
type Arguments f (Value a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

type Arguments f (Value a) = f (Value a)
type Arguments f (T a) Source #

Consistent with pair instance. You may use AnyArg or withGuidedArgs to stop descending into the stereo channels.

Instance details

Defined in Synthesizer.LLVM.Causal.Functional

type Arguments f (T a) = T (Arguments f a)
type Arguments f (Parameter a) Source # 
Instance details

Defined in Synthesizer.LLVM.Filter.Allpass

type Arguments f (Parameter a) = f (Parameter a)
type Arguments f (ParameterPacked a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Exponential2

type Arguments f (AnyArg a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

type Arguments f (AnyArg a) = f a
type Arguments f (T a) Source # 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

type Arguments f (T a) = f (T a)
type Arguments f (CascadeParameter n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Filter.Allpass

type Arguments f (ParameterValue n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Filter.SecondOrderCascade

type Arguments f (ParameterValue n a) = f (ParameterValue n a)
type Arguments f (Constant n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

type Arguments f (Constant n a) = f (Constant n a)
type Arguments f (a, b) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

type Arguments f (a, b) = (Arguments f a, Arguments f b)
type Arguments f (a, b, c) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

type Arguments f (a, b, c) = (Arguments f a, Arguments f b, Arguments f c)

makeArgs :: (MakeArguments arg, Functor f) => f arg -> Arguments f arg Source #

newtype AnyArg a Source #

You can use this to explicitly stop breaking of composed data types. It might be more comfortable to do this using withGuidedArgs.

Constructors

AnyArg 

Fields

Instances

Instances details
MakeArguments (AnyArg a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

Methods

makeArgs :: Functor f => f (AnyArg a) -> Arguments f (AnyArg a) Source #

type Arguments f (AnyArg a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

type Arguments f (AnyArg a) = f a

newtype Ground f a Source #

Constructors

Ground (f a) 

Instances

Instances details
(Functor f, f ~ g) => MakeGroundArguments f (Ground g a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

Methods

makeGroundArgs :: f (GroundArguments (Ground g a)) -> Ground g a Source #

type GroundArguments (Ground f a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

type GroundArguments (Ground f a) = a

withGroundArgs :: (MakeGroundArguments (T inp) args, GroundArguments args ~ inp) => (args -> T inp out) -> T inp out Source #

This is similar to withArgs but it requires to specify the decomposition depth using constructors in the arguments.

class Functor f => MakeGroundArguments f args Source #

Minimal complete definition

makeGroundArgs

Instances

Instances details
Functor f => MakeGroundArguments f () Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

Methods

makeGroundArgs :: f (GroundArguments ()) -> () Source #

MakeGroundArguments f a => MakeGroundArguments f (T a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

Methods

makeGroundArgs :: f (GroundArguments (T a)) -> T a Source #

(Functor f, f ~ g) => MakeGroundArguments f (Ground g a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

Methods

makeGroundArgs :: f (GroundArguments (Ground g a)) -> Ground g a Source #

(MakeGroundArguments f a, MakeGroundArguments f b) => MakeGroundArguments f (a, b) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

Methods

makeGroundArgs :: f (GroundArguments (a, b)) -> (a, b) Source #

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

Defined in Synthesizer.LLVM.Causal.Functional

Methods

makeGroundArgs :: f (GroundArguments (a, b, c)) -> (a, b, c) Source #

type family GroundArguments args Source #

Instances

Instances details
type GroundArguments () Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

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

Defined in Synthesizer.LLVM.Causal.Functional

type GroundArguments (Ground f a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

type GroundArguments (Ground f a) = a
type GroundArguments (a, b) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

type GroundArguments (a, b, c) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

data Atom a Source #

Constructors

Atom 

Instances

Instances details
MakeGuidedArguments (Atom a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

type GuidedArguments f (Atom a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

type GuidedArguments f (Atom a) = f a
type PatternArguments (Atom a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

type PatternArguments (Atom a) = a

withGuidedArgs :: (MakeGuidedArguments pat, PatternArguments pat ~ inp) => pat -> (GuidedArguments (T inp) pat -> T inp out) -> T inp out Source #

This is similar to withArgs but it allows to specify the decomposition depth using a pattern.

class MakeGuidedArguments pat Source #

Minimal complete definition

makeGuidedArgs

Instances

Instances details
MakeGuidedArguments () Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

Methods

makeGuidedArgs :: Functor f => () -> f (PatternArguments ()) -> GuidedArguments f () Source #

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

Defined in Synthesizer.LLVM.Causal.Functional

Methods

makeGuidedArgs :: Functor f => T a -> f (PatternArguments (T a)) -> GuidedArguments f (T a) Source #

MakeGuidedArguments (Atom a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

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

Defined in Synthesizer.LLVM.Causal.Functional

Methods

makeGuidedArgs :: Functor f => (a, b) -> f (PatternArguments (a, b)) -> GuidedArguments f (a, b) Source #

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

Defined in Synthesizer.LLVM.Causal.Functional

Methods

makeGuidedArgs :: Functor f => (a, b, c) -> f (PatternArguments (a, b, c)) -> GuidedArguments f (a, b, c) Source #

type family GuidedArguments (f :: * -> *) pat Source #

Instances

Instances details
type GuidedArguments f () Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

type GuidedArguments f () = f ()
type GuidedArguments f (T a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

type GuidedArguments f (T a) = T (GuidedArguments f a)
type GuidedArguments f (Atom a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

type GuidedArguments f (Atom a) = f a
type GuidedArguments f (a, b) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

type GuidedArguments f (a, b, c) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

type family PatternArguments pat Source #

Instances

Instances details
type PatternArguments () Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

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

Defined in Synthesizer.LLVM.Causal.Functional

type PatternArguments (Atom a) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

type PatternArguments (Atom a) = a
type PatternArguments (a, b) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

type PatternArguments (a, b, c) Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Functional

newtype PrepareArguments f merged separated Source #

Constructors

PrepareArguments (f merged -> separated) 

withPreparedArgs :: PrepareArguments (T inp) inp a -> (a -> T inp out) -> T inp out Source #

Alternative to withGuidedArgs. This way of pattern construction is even Haskell 98.

withPreparedArgs2 :: PrepareArguments (T (inp0, inp1)) inp0 a -> PrepareArguments (T (inp0, inp1)) inp1 b -> (a -> b -> T (inp0, inp1) out) -> T (inp0, inp1) out Source #

pairArgs :: Functor f => PrepareArguments f a0 b0 -> PrepareArguments f a1 b1 -> PrepareArguments f (a0, a1) (b0, b1) Source #

tripleArgs :: Functor f => PrepareArguments f a0 b0 -> PrepareArguments f a1 b1 -> PrepareArguments f a2 b2 -> PrepareArguments f (a0, a1, a2) (b0, b1, b2) Source #