|
Synthesizer.Dimensional.RateAmplitude.Control | Portability | requires multi-parameter type classes | Stability | provisional | Maintainer | [email protected] |
|
|
|
|
|
Description |
Control curves which can be used
as envelopes, for controlling filter parameters and so on.
|
|
Synopsis |
|
constant :: (C y, C u, C v) => T v y -> T s u t (R s v y y) | | constantVector :: T v y -> yv -> T s u t (R s v y yv) | | linear :: (C q, C q, C u, C v) => T (DimensionGradient u v) q -> T v q -> T s u q (R s v q q) | | line :: (C q, C u, C v) => T u q -> (T v q, T v q) -> T s u q (R s v q q) | | exponential :: (C q, C q, C u, C v) => T u q -> T v q -> T s u q (R s v q q) | | exponential2 :: (C q, C q, C u, C v) => T u q -> T v q -> T s u q (R s v q q) | | exponentialFromTo :: (C q, C q, C u, C v) => T u q -> (T v q, T v q) -> T s u q (R s v q q) | | cubicHermite :: (C q, C q, C u, C v) => (T u q, (T v q, T (DimensionGradient u v) q)) -> (T u q, (T v q, T (DimensionGradient u v) q)) -> T s u q (R s v q q) | | stepPiece :: (C q, C u, C v) => Piece s u v q | | linearPiece :: (C q, C u, C v) => Piece s u v q | | exponentialPiece :: (C q, C u, C v) => T v q -> Piece s u v q | | cosinePiece :: (C q, C u, C v) => Piece s u v q | | cubicPiece :: (C q, C u, C v) => T (DimensionGradient u v) q -> T (DimensionGradient u v) q -> Piece s u v q | | piecewise :: (C q, C q, C u, C v) => Piecewise s u v q -> T s u q (R s v q q) | | piecewiseVolume :: (C q, C q, C u, C v) => Piecewise s u v q -> T v q -> T s u q (R s v q q) | | type Piece s u v q = Piece (T u q) (T v q) (T v q -> q -> T s u q (R s q)) | | type Piecewise s u v q = T (T u q) (T v q) (T v q -> q -> T s u q (R s q)) | | (-|#) :: y -> (PieceDist t y sig, T t y sig) -> (PieceRightSingle y, T t y sig) | | (#|-) :: (t, Piece t y sig) -> (PieceRightSingle y, T t y sig) -> (PieceDist t y sig, T t y sig) | | (=|#) :: (y, y) -> (PieceDist t y sig, T t y sig) -> (PieceRightDouble y, T t y sig) | | (#|=) :: (t, Piece t y sig) -> (PieceRightDouble y, T t y sig) -> (PieceDist t y sig, T t y sig) | | (|#) :: y -> (PieceDist t y sig, T t y sig) -> T t y sig | | (#|) :: (t, Piece t y sig) -> y -> (PieceDist t y sig, T t y sig) | | mapLinearDimension :: (C y, C y, C u, C v) => T v y -> T (Mul v u) y -> T s u t (R s u y y -> R s (Mul v u) y y) | | mapExponentialDimension :: (C y, C u) => y -> T u y -> T s u t (R s Scalar y y -> R s u y y) |
|
|
|
Primitives
|
|
|
:: (C y, C u, C v) | | => T v y | value
| -> T s u t (R s v y y) | |
|
|
|
:: | | => T v y | amplitude
| -> yv | value
| -> T s u t (R s v y yv) | | The amplitude must be positive!
This is not checked.
|
|
|
|
:: (C q, C q, C u, C v) | | => T (DimensionGradient u v) q | slope of the curve
| -> T v q | initial value
| -> T s u q (R s v q q) | | Caution: This control curve can contain samples
with an absolute value greater than 1.
Linear curves starting with zero are impossible.
Maybe you prefer using line.
|
|
|
|
:: (C q, C u, C v) | | => T u q | duration of the ramp
| -> (T v q, T v q) | initial and final value
| -> T s u q (R s v q q) | | Generates a finite ramp.
|
|
|
|
:: (C q, C q, C u, C v) | | => T u q | time where the function reaches 1/e of the initial value
| -> T v q | initial value
| -> T s u q (R s v q q) | |
|
|
|
:: (C q, C q, C u, C v) | | => T u q | half life, time where the function reaches 1/2 of the initial value
| -> T v q | initial value
| -> T s u q (R s v q q) | |
|
|
|
:: (C q, C q, C u, C v) | | => T u q | duration of the ramp
| -> (T v q, T v q) | initial and final value
| -> T s u q (R s v q q) | | Generate an exponential curve through two nodes.
|
|
|
|
|
Piecewise
|
|
|
|
|
|
|
|
|
|
|
|
|
Since this function looks for the maximum node value,
and since the signal parameter inference phase must be completed before signal processing,
infinite descriptions cannot be used here.
|
|
|
|
type Piece s u v q = Piece (T u q) (T v q) (T v q -> q -> T s u q (R s q)) | Source |
|
|
type Piecewise s u v q = T (T u q) (T v q) (T v q -> q -> T s u q (R s q)) | Source |
|
|
|
|
|
The 6 operators simplify constructing a list of PieceData a.
The description consists of nodes (namely the curve values at nodes)
and the connecting curve types.
The naming scheme is as follows:
In the middle there is a bar |.
With respect to the bar,
the pad symbol # is at the side of the curve type,
at the other side there is nothing, a minus sign -, or an equality sign =.
- Nothing means that here is the start or the end node of a curve.
- Minus means that here is a node where left and right curve meet at the same value.
The node description is thus one value.
- Equality sign means that here is a split node,
where left and right curve might have different ending and beginning values, respectively.
The node description consists of a pair of values.
|
|
|
|
|
|
|
|
|
|
Preparation
|
|
|
:: (C y, C y, C u, C v) | | => T v y | range: one is mapped to center + range * ampX
| -> T (Mul v u) y | center: zero is mapped to center
| -> T s u t (R s u y y -> R s (Mul v u) y y) | | Map a control curve without amplitude unit
by a linear (affine) function with a unit.
|
|
|
|
:: (C y, C u) | | => y | range: one is mapped to center*range, must be positive
| -> T u y | center: zero is mapped to center
| -> T s u t (R s Scalar y y -> R s u y y) | | Map a control curve without amplitude unit
exponentially to one with a unit.
|
|
|
Produced by Haddock version 2.4.2 |