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

Safe HaskellNone
LanguageHaskell98

Synthesizer.LLVM.Frame.Stereo

Description

Re-export functions from Sound.Frame.Stereo and add (orphan) instances for various LLVM type classes. If you want to use the Stereo datatype with synthesizer-llvm we recommend to import this module instead of Sound.Frame.Stereo or Sound.Frame.NumericPrelude.Stereo.

Synopsis

Documentation

data T a :: * -> *

Instances

Functor T 
Applicative T 
Foldable T 
Traversable T 
Eq a => Eq (T a) 
Show a => Show (T a) 
Arbitrary a => Arbitrary (T a) 
Storable a => Storable (T a) 
C a => C (T a) 
C a => C (T a) 
Sized value => Sized (T value) Source 
Zero v => Zero (T v) Source 
C v => C (T v) Source 
Read v => Read (T v) Source 
Flatten a => Flatten (T a) Source 
MakeGuidedArguments a => MakeGuidedArguments (T a) Source 
MakeArguments a => MakeArguments (T a) Source 
(Arithmetic a, IsConst a, C (Value (State a))) => C (Parameter a) (T (Value a)) (T (Value a)) Source 
(PseudoRing a, RationalConstant a, C a) => C (Parameter a) (T a) (T a) Source 
type GuidedArguments f (T a) = T (GuidedArguments f a) Source 
type Arguments f (T a) = T (Arguments f a) Source

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

type Struct (T l) 
type Size (T v) = Size v 
type Element (T v) = T (Element v) 
type ValueTuple (T h) = T (ValueTuple h) 
type Size (T value) = Size value Source 
type WriteIt (T v) = T (WriteIt v) Source 
type Element (T v) = T (Element v) Source 
type ReadIt (T v) = T (ReadIt v) Source 
type Registers (T a) = T (Registers a) Source 
type PatternArguments (T a) = T (PatternArguments a) Source 
type Input (Parameter a) (T (Value a)) = T (Value a) Source 
type Input (Parameter a) (T a) = T a Source 
type Output (Parameter a) (T (Value a)) = T (Value a) Source 
type Output (Parameter a) (T a) = T a Source 

cons :: a -> a -> T a

left :: T a -> a

right :: T a -> a

data Channel :: *

Constructors

Left 
Right 

select :: T a -> Channel -> a

arrowFromMono :: Arrow arrow => arrow a b -> arrow (T a) (T b)

Run a causal process independently on each stereo channel.

arrowFromMonoControlled :: Arrow arrow => arrow (c, a) b -> arrow (c, T a) (T b)

arrowFromChannels :: Arrow arrow => arrow a b -> arrow a b -> arrow (T a) (T b)

interleave :: (T a, T b) -> T (a, b)

sequence :: Functor f => f (T a) -> T (f a)

liftApplicative :: Applicative f => (f a -> f b) -> f (T a) -> f (T b)