Safe Haskell | None |
---|---|
Language | Haskell2010 |
- constant :: Write sig y => LazySize -> y -> sig y
- linear :: (C y, Write sig y) => LazySize -> y -> y -> sig y
- linearMultiscale :: (C y, Write sig y) => LazySize -> y -> y -> sig y
- linearMultiscaleNeutral :: (C y, Write sig y) => LazySize -> y -> sig y
- line :: (C y, Write sig y) => LazySize -> Int -> (y, y) -> sig y
- exponential :: (C y, Write sig y) => LazySize -> y -> y -> sig y
- exponentialMultiscale :: (C y, Write sig y) => LazySize -> y -> y -> sig y
- exponentialMultiscaleNeutral :: (C y, Write sig y) => LazySize -> y -> sig y
- exponential2 :: (C y, Write sig y) => LazySize -> y -> y -> sig y
- exponential2Multiscale :: (C y, Write sig y) => LazySize -> y -> y -> sig y
- exponential2MultiscaleNeutral :: (C y, Write sig y) => LazySize -> y -> sig y
- vectorExponential :: (C y, C y v, Write sig v) => LazySize -> y -> v -> sig v
- vectorExponential2 :: (C y, C y v, Write sig v) => LazySize -> y -> v -> sig v
- cosine :: (C y, Write sig y) => LazySize -> y -> y -> sig y
- cosineMultiscaleLinear :: (C y, Write sig y) => LazySize -> y -> y -> sig y
- cosineMultiscale :: (C y, Write sig (T y), Transform sig (T y), Transform sig y) => LazySize -> y -> y -> sig y
- cosineWithSlope :: C y => (y -> y -> signal) -> y -> y -> signal
- cubicHermite :: (C y, Write sig y) => LazySize -> (y, (y, y)) -> (y, (y, y)) -> sig y
- cubicFunc :: C y => (y, (y, y)) -> (y, (y, y)) -> y -> y
- data Control y
- = CtrlStep
- | CtrlLin
- | CtrlExp {
- ctrlExpSaturation :: y
- | CtrlCos
- | CtrlCubic {
- ctrlCubicGradient0 :: y
- ctrlCubicGradient1 :: y
- data ControlPiece y = ControlPiece {}
- newtype PieceRightSingle y = PRS y
- newtype PieceRightDouble y = PRD y
- type ControlDist y = (y, Control y, y)
- (#|-) :: (y, Control y) -> (PieceRightSingle y, [ControlPiece y]) -> (ControlDist y, [ControlPiece y])
- (-|#) :: y -> (ControlDist y, [ControlPiece y]) -> (PieceRightSingle y, [ControlPiece y])
- (#|=) :: (y, Control y) -> (PieceRightDouble y, [ControlPiece y]) -> (ControlDist y, [ControlPiece y])
- (=|#) :: (y, y) -> (ControlDist y, [ControlPiece y]) -> (PieceRightDouble y, [ControlPiece y])
- (#|) :: (y, Control y) -> y -> (ControlDist y, [ControlPiece y])
- (|#) :: y -> (ControlDist y, [ControlPiece y]) -> [ControlPiece y]
- piecewise :: (C y, C y, Write sig y) => LazySize -> [ControlPiece y] -> sig y
- piecewisePart :: (C y, Write sig y) => LazySize -> y -> y -> y -> y -> Int -> Control y -> sig y
- curveMultiscale :: Write sig y => LazySize -> (y -> y -> y) -> y -> y -> sig y
- curveMultiscaleNeutral :: Write sig y => LazySize -> (y -> y -> y) -> y -> y -> sig y
Control curve generation
linearMultiscale :: (C y, Write sig y) => LazySize -> y -> y -> sig y
Minimize rounding errors by reducing number of operations per element to a logarithmuc number.
linearMultiscaleNeutral :: (C y, Write sig y) => LazySize -> y -> sig y
Linear curve starting at zero.
:: (C y, Write sig y) | |
=> LazySize | |
-> Int | length |
-> (y, y) | initial and final value |
-> sig y | linear progression |
Linear curve of a fixed length. The final value is not actually reached, instead we stop one step before. This way we can concatenate several lines without duplicate adjacent values.
:: (C y, C y v, Write sig v) | |
=> LazySize | |
-> y | time where the function reaches 1/e of the initial value |
-> v | initial value |
-> sig v | exponential decay |
This is an extension of exponential
to vectors
which is straight-forward but requires more explicit signatures.
But since it is needed rarely I setup a separate function.
cosineWithSlope :: C y => (y -> y -> signal) -> y -> y -> signal
cubicHermite :: (C y, Write sig y) => LazySize -> (y, (y, y)) -> (y, (y, y)) -> sig y
cubicFunc :: C y => (y, (y, y)) -> (y, (y, y)) -> y -> y
0 16 0 8 16 0 4 8 12 16 0 2 4 6 8 10 12 14 16 0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16
data Control y
Deprecated: use Synthesizer.Generic.Piece instead
The curve type of a piece of a piecewise defined control curve.
data ControlPiece y
The full description of a control curve piece.
Eq y => Eq (ControlPiece y) | |
Show y => Show (ControlPiece y) |
newtype PieceRightSingle y
PRS y |
newtype PieceRightDouble y
PRD y |
type ControlDist y = (y, Control y, y)
(#|-) :: (y, Control y) -> (PieceRightSingle y, [ControlPiece y]) -> (ControlDist y, [ControlPiece y]) infixr 5
The 6 operators simplify constructing a list of ControlPiece 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.
(-|#) :: y -> (ControlDist y, [ControlPiece y]) -> (PieceRightSingle y, [ControlPiece y]) infixr 5
(#|=) :: (y, Control y) -> (PieceRightDouble y, [ControlPiece y]) -> (ControlDist y, [ControlPiece y]) infixr 5
(=|#) :: (y, y) -> (ControlDist y, [ControlPiece y]) -> (PieceRightDouble y, [ControlPiece y]) infixr 5
(#|) :: (y, Control y) -> y -> (ControlDist y, [ControlPiece y]) infixr 5
(|#) :: y -> (ControlDist y, [ControlPiece y]) -> [ControlPiece y] infixr 5
Auxiliary functions
curveMultiscale :: Write sig y => LazySize -> (y -> y -> y) -> y -> y -> sig y
curveMultiscaleNeutral :: Write sig y => LazySize -> (y -> y -> y) -> y -> y -> sig y