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

Safe HaskellNone
LanguageHaskell98

Synthesizer.LLVM.MIDI.BendModulation

Contents

Description

Various LLVM related instances of the BM.T type. I have setup a separate module since these instances are orphan and need several language extensions.

Synopsis

Documentation

data T a #

bend is a frequency factor and depth is a modulation depth to be interpreted by the instrument.

Constructors

Cons 

Fields

Instances
Functor T 
Instance details

Defined in Synthesizer.MIDI.Value.BendModulation

Methods

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

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

Applicative T 
Instance details

Defined in Synthesizer.MIDI.Value.BendModulation

Methods

pure :: a -> T a #

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

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

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

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

Foldable T 
Instance details

Defined in Synthesizer.MIDI.Value.BendModulation

Methods

fold :: Monoid m => T m -> m #

foldMap :: Monoid m => (a -> m) -> T a -> m #

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

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

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

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

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

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

toList :: T a -> [a] #

null :: T a -> Bool #

length :: T a -> Int #

elem :: Eq a => a -> T a -> Bool #

maximum :: Ord a => T a -> a #

minimum :: Ord a => T a -> a #

sum :: Num a => T a -> a #

product :: Num a => T a -> a #

Traversable T 
Instance details

Defined in Synthesizer.MIDI.Value.BendModulation

Methods

traverse :: Applicative f => (a -> f b) -> T a -> f (T b) #

sequenceA :: Applicative f => T (f a) -> f (T a) #

mapM :: Monad m => (a -> m b) -> T a -> m (T b) #

sequence :: Monad m => T (m a) -> m (T a) #

Eq a => Eq (T a) 
Instance details

Defined in Synthesizer.MIDI.Value.BendModulation

Methods

(==) :: T a -> T a -> Bool #

(/=) :: T a -> T a -> Bool #

Show a => Show (T a) 
Instance details

Defined in Synthesizer.MIDI.Value.BendModulation

Methods

showsPrec :: Int -> T a -> ShowS #

show :: T a -> String #

showList :: [T a] -> ShowS #

Storable a => Storable (T a) 
Instance details

Defined in Synthesizer.MIDI.Value.BendModulation

Methods

sizeOf :: T a -> Int #

alignment :: T a -> Int #

peekElemOff :: Ptr (T a) -> Int -> IO (T a) #

pokeElemOff :: Ptr (T a) -> Int -> T a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (T a) #

pokeByteOff :: Ptr b -> Int -> T a -> IO () #

peek :: Ptr (T a) -> IO (T a) #

poke :: Ptr (T a) -> T a -> IO () #

NFData a => NFData (T a) 
Instance details

Defined in Synthesizer.MIDI.Value.BendModulation

Methods

rnf :: T a -> () #

C l => C (T l) 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

Methods

pack :: T l -> Struct (T l)

unpack :: Struct (T l) -> T l

C l => C (T l) 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

Associated Types

type Struct (T l) :: Type

Methods

load :: Value (Ptr (Struct (T l))) -> CodeGenFunction r (T l)

store :: T l -> Value (Ptr (Struct (T l))) -> CodeGenFunction r ()

decompose :: Value (Struct (T l)) -> CodeGenFunction r (T l)

compose :: T l -> CodeGenFunction r (Value (Struct (T l)))

C a => C (T a) 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

Associated Types

type Repr (T a) :: Type

Methods

cons :: T a -> T0 (T a)

undef :: T0 (T a)

zero :: T0 (T a)

phi :: BasicBlock -> T0 (T a) -> CodeGenFunction r (T0 (T a))

addPhi :: BasicBlock -> T0 (T a) -> T0 (T a) -> CodeGenFunction r ()

Phi a => Phi (T a) 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

Methods

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

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

Undefined a => Undefined (T a) 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

Methods

undef :: T a

Select a => Select (T a) 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

Methods

select :: Value Bool -> T a -> T a -> CodeGenFunction r (T a)

Zero a => Zero (T a) 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

Methods

zero :: T a

Value h => Value (T h) 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

Associated Types

type ValueOf (T h) :: Type

Methods

valueOf :: T h -> ValueOf (T h)

C l => C (T l) 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

Methods

pack :: T l -> Struct (T l)

unpack :: Struct (T l) -> T l

C v => C (T v) 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

Methods

insert :: Value Word32 -> Element (T v) -> T v -> CodeGenFunction r (T v)

Simple v => Simple (T v) 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

Associated Types

type Element (T v) :: Type

type Size (T v) :: Type

Methods

shuffleMatch :: ConstValue (Vector (Size (T v)) Word32) -> T v -> CodeGenFunction r (T v)

extract :: Value Word32 -> T v -> CodeGenFunction r (Element (T v))

C l => C (T l) 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

Methods

load :: Value (Ptr (T l)) -> CodeGenFunction r (T0 (T l))

store :: T0 (T l) -> Value (Ptr (T l)) -> CodeGenFunction r ()

C l => C (T l) 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

Methods

load :: Value (Ptr (T l)) -> CodeGenFunction r (ValueOf (T l))

store :: ValueOf (T l) -> Value (Ptr (T l)) -> CodeGenFunction r ()

MakeArguments (T a) Source # 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

Methods

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

Aggregate e mv => Aggregate (T e) (T mv) 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

Associated Types

type MultiValuesOf (T e) :: Type

type ExpressionsOf (T mv) :: Type

Methods

bundle :: T e -> CodeGenFunction r (T mv)

dissect :: T mv -> T e

type Arguments f (T a) Source # 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

type Arguments f (T a) = f (T a)
type Struct (T l) 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

type Struct (T l)
type Repr (T a) 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

type Repr (T a) = T (Repr a)
type ValueOf (T h) 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

type ValueOf (T h) = T (ValueOf h)
type Element (T v) 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

type Element (T v) = T (Element v)
type Size (T v) 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

type Size (T v) = Size v
type ExpressionsOf (T mv) 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

type ExpressionsOf (T mv) = T (ExpressionsOf mv)
type MultiValuesOf (T e) 
Instance details

Defined in Synthesizer.LLVM.MIDI.BendModulation

type MultiValuesOf (T e) = T (MultiValuesOf e)

deflt :: C a => T a #

shift :: C a => a -> T a -> T a #

Multiply the pitch bend by a given factor. This way you can e.g. shift the pitch bend from around 1 to the actual frequency.

multiValue :: T (T a) -> T (T a) Source #

unMultiValue :: T (T a) -> T (T a) Source #

Orphan instances

C l => C (T l) Source # 
Instance details

Methods

pack :: T l -> Struct (T l)

unpack :: Struct (T l) -> T l

C l => C (T l) Source # 
Instance details

Associated Types

type Struct (T l) :: Type

Methods

load :: Value (Ptr (Struct (T l))) -> CodeGenFunction r (T l)

store :: T l -> Value (Ptr (Struct (T l))) -> CodeGenFunction r ()

decompose :: Value (Struct (T l)) -> CodeGenFunction r (T l)

compose :: T l -> CodeGenFunction r (Value (Struct (T l)))

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

Associated Types

type Repr (T a) :: Type

Methods

cons :: T a -> T0 (T a)

undef :: T0 (T a)

zero :: T0 (T a)

phi :: BasicBlock -> T0 (T a) -> CodeGenFunction r (T0 (T a))

addPhi :: BasicBlock -> T0 (T a) -> T0 (T a) -> CodeGenFunction r ()

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

Methods

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

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

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

Methods

undef :: T a

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

Methods

select :: Value Bool -> T a -> T a -> CodeGenFunction r (T a)

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

Methods

zero :: T a

Value h => Value (T h) Source # 
Instance details

Associated Types

type ValueOf (T h) :: Type

Methods

valueOf :: T h -> ValueOf (T h)

C l => C (T l) Source # 
Instance details

Methods

pack :: T l -> Struct (T l)

unpack :: Struct (T l) -> T l

C v => C (T v) Source # 
Instance details

Methods

insert :: Value Word32 -> Element (T v) -> T v -> CodeGenFunction r (T v)

Simple v => Simple (T v) Source # 
Instance details

Associated Types

type Element (T v) :: Type

type Size (T v) :: Type

Methods

shuffleMatch :: ConstValue (Vector (Size (T v)) Word32) -> T v -> CodeGenFunction r (T v)

extract :: Value Word32 -> T v -> CodeGenFunction r (Element (T v))

C l => C (T l) Source # 
Instance details

Methods

load :: Value (Ptr (T l)) -> CodeGenFunction r (T0 (T l))

store :: T0 (T l) -> Value (Ptr (T l)) -> CodeGenFunction r ()

C l => C (T l) Source # 
Instance details

Methods

load :: Value (Ptr (T l)) -> CodeGenFunction r (ValueOf (T l))

store :: ValueOf (T l) -> Value (Ptr (T l)) -> CodeGenFunction r ()

MakeArguments (T a) Source # 
Instance details

Methods

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

Aggregate e mv => Aggregate (T e) (T mv) Source # 
Instance details

Associated Types

type MultiValuesOf (T e) :: Type

type ExpressionsOf (T mv) :: Type

Methods

bundle :: T e -> CodeGenFunction r (T mv)

dissect :: T mv -> T e