synthesizer-0.0.3: Audio signal processing coded in HaskellSource codeContentsIndex
Synthesizer.Inference.Reader.Process
Portabilityrequires multi-parameter type classes (OccasionallyScalar)
Stabilityprovisional
Maintainersynthesizer@henning-thielemann.de
Description

Light-weight sample parameter inference which will fit most needs. We only do "poor man's inference", only for sample rates. The sample rate will be provided in a Reader monad. We almost do not need monad functionality but only Control.Applicative functionality.

In contrast to the run-time inference approach, we have the static guarantee that the sample rate is fixed before passing a signal to the outside world.

Synopsis
newtype T t t' a = Cons {
process :: t' -> a
}
run :: t' -> T t t' a -> (t', a)
share :: T t t' a -> (a -> T t t' b) -> T t t' b
injectParam :: (a -> T t t' b) -> T t t' (a -> b)
extractParam :: T t t' (a -> b) -> a -> T t t' b
convertTimeParam :: (t' -> t' -> t) -> t' -> (t -> a) -> T t t' a
loop :: Functor f => f (a -> a) -> f a
pure :: a -> T t t' a
($:) :: Applicative f => f (a -> b) -> f a -> f b
($::) :: (Applicative f, Traversable t) => f (t a -> b) -> t (f a) -> f b
($^) :: Functor f => (a -> b) -> f a -> f b
($#) :: Applicative f => f (a -> b) -> a -> f b
(.:) :: Applicative f => f (b -> c) -> f (a -> b) -> f (a -> c)
(.^) :: Functor f => (b -> c) -> f (a -> b) -> f (a -> c)
liftP :: Applicative f => f (a -> b) -> f a -> f b
liftP2 :: Applicative f => f (a -> b -> c) -> f a -> f b -> f c
liftP3 :: Applicative f => f (a -> b -> c -> d) -> f a -> f b -> f c -> f d
liftP4 :: Applicative f => f (a -> b -> c -> d -> e) -> f a -> f b -> f c -> f d -> f e
Documentation
newtype T t t' a Source
This wraps a function which computes a sample rate dependent result. Sample rate tells how many values per unit are stored for representation of a signal.
Constructors
Cons
process :: t' -> a
show/hide Instances
Monad (T t t')
Functor (T t t')
MonadFix (T t t')
Applicative (T t t')
run :: t' -> T t t' a -> (t', a)Source
shareSource
::
=> T t t' aprocess that provides a result
-> a -> T t t' bfunction that can re-use that result as much as it wants
-> T t t' b
Re-use a result several times without recomputing. With a simple let you can re-use a result but it must be recomputed due to the dependency on the sample rate.
injectParam :: (a -> T t t' b) -> T t t' (a -> b)Source
extractParam :: T t t' (a -> b) -> a -> T t t' bSource
convertTimeParam :: (t' -> t' -> t) -> t' -> (t -> a) -> T t t' aSource
The first argument will be a function like InferenceReader.Signal.toTimeScalar. If you use this function instead of InferenceReader.Signal.toTimeScalar directly, the type t can be automatically infered.
loopSource
:: Functor f
=> f (a -> a)process chain that shall be looped
-> f a
Create a loop (feedback) from one node to another one. That is, compute the fix point of a process iteration.
pure :: a -> T t t' aSource
This corresponds to Control.Applicative.pure
($:) :: Applicative f => f (a -> b) -> f a -> f bSource
This corresponds to <*>
($::) :: (Applicative f, Traversable t) => f (t a -> b) -> t (f a) -> f bSource
Instead of mixMulti $:: map f xs the caller should write mixMulti $: mapM f xs in order to save the user from learning another infix operator.
($^) :: Functor f => (a -> b) -> f a -> f bSource
($#) :: Applicative f => f (a -> b) -> a -> f bSource
(.:) :: Applicative f => f (b -> c) -> f (a -> b) -> f (a -> c)Source
(.^) :: Functor f => (b -> c) -> f (a -> b) -> f (a -> c)Source
liftP :: Applicative f => f (a -> b) -> f a -> f bSource
Our signal processors have types like f (a -> b -> c). They could also have the type a -> b -> f c or f a -> f b -> f c. We did not choose the last variant for reduction of redundancy in type signatures, and we did not choose the second variant for easy composition of processors. However the forms are freely convertible, and if you prefer the last one because you do not want to sprinkle '($:)' in your code, then you may want to convert the processors using the following functions, that can be defined purely in the Applicative class.
liftP2 :: Applicative f => f (a -> b -> c) -> f a -> f b -> f cSource
liftP3 :: Applicative f => f (a -> b -> c -> d) -> f a -> f b -> f c -> f dSource
liftP4 :: Applicative f => f (a -> b -> c -> d -> e) -> f a -> f b -> f c -> f d -> f eSource
Produced by Haddock version 2.3.0