Copyright | (c) Henning Thielemann 2008-2009 |
---|---|
License | GPL |
Maintainer | synthesizer@henning-thielemann.de |
Stability | provisional |
Portability | requires multi-parameter type classes and local universal quantification |
Safe Haskell | None |
Language | Haskell2010 |
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 as an argument of a special type T
.
This argument will almost never be passed explicitly
but should be handled by operators analogous to '($)' and '(.)'.
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. However we still need to make it safe that signals that are rendered for one sample rate are not processed with another sample rate.
- newtype T s u t a = Cons {}
- run :: C u => T (Recip u) t -> (forall s. T s u t a) -> a
- withParam :: (a -> T s u t b) -> T s u t (a -> b)
- getSampleRate :: C u => T s u t (T (Recip u) t)
- toTimeScalar :: (C t, C u) => T u t -> T s u t t
- toFrequencyScalar :: (C t, C u) => T (Recip u) t -> T s u t t
- toTimeDimension :: (C t, C u) => t -> T s u t (T u t)
- toFrequencyDimension :: (C t, C u) => t -> T s u t (T (Recip u) t)
- intFromTime :: (C t, C u) => String -> T u t -> T s u t Int
- intFromTime98 :: (C t, RealFrac t, C u) => String -> T u t -> T s u t Int
- type DimensionGradient u v = Mul (Recip u) v
- toGradientScalar :: (C q, C u, C v) => T v q -> T (DimensionGradient u v) q -> T s u q q
- loop :: Functor f => f (a -> a) -> f a
- pure :: a -> T s u 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
- ($#) :: Functor f => f (a -> b) -> a -> f b
- (.:) :: (Applicative f, Arrow arrow) => f (arrow b c) -> f (arrow a b) -> f (arrow a c)
- (.^) :: (Functor f, Arrow arrow) => arrow b c -> f (arrow a b) -> f (arrow 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
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.
The process is labeled with a type variable s
which is part the signals.
This way we can ensure that signals are only used
with the sample rate they are created for.
run :: C u => T (Recip u) t -> (forall s. T s u t a) -> a Source #
Get results from the Process monad.
You can obtain only signals (or other values)
that do not implicitly depend on the sample rate,
that is value without the s
type parameter.
type DimensionGradient u v = Mul (Recip u) v Source #
toGradientScalar :: (C q, C u, C v) => T v q -> T (DimensionGradient u v) q -> T s u q q Source #
:: 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.
($:) :: Applicative f => f (a -> b) -> f a -> f b infixl 0 #
This corresponds to <*>
($::) :: (Applicative f, Traversable t) => f (t a -> b) -> t (f a) -> f b infixl 0 #
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.
(.:) :: (Applicative f, Arrow arrow) => f (arrow b c) -> f (arrow a b) -> f (arrow a c) infixr 9 #
liftP :: Applicative f => f (a -> b) -> f a -> f b #
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 for simplifying sharing,
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 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 #