|
| Synthesizer.Plain.ToneModulation | | Portability | requires multi-parameter type classes | | Stability | provisional | | Maintainer | synthesizer@henning-thielemann.de |
|
|
|
|
|
| Description |
Avoid importing this module.
Better use functions from
Synthesizer.Plain.Oscillator and
Synthesizer.Basic.Wave
Input data is interpreted as samples of data on a cylinder
in the following form:
|* |
| * |
| * |
| * |
| * |
| * |
| * |
| *|
| * |
| * |
| * |
-----------
*
*
*
*
*
*
*
*
*
*
*
-----------
We have to interpolate in the parallelograms.
|
|
| Synopsis |
|
| interpolateCell :: T a y -> T b y -> (a, b) -> [[y]] -> y | | | untangleShapePhase :: C a => Int -> a -> (a, a) -> (a, a) | | | untangleShapePhaseAnalytic :: C a => Int -> a -> (a, a) -> (a, a) | | | solveSLE2 :: C a => ((a, a), (a, a)) -> (a, a) -> (a, a) | | | det2 :: C a => ((a, a), (a, a)) -> a | | | flattenShapePhase :: C a => Int -> a -> (a, T a) -> (Int, (a, a)) | | | shapeLimits :: C t => T a v -> T a v -> Int -> t -> (t, t) | | | interpolationOffset :: T a v -> T a v -> Int -> Int | | | data Prototype a v = Prototype {} | | | makePrototype :: C a => T a v -> T a v -> a -> [v] -> Prototype a v | | | sampledToneCell :: C a => Prototype a v -> a -> T a -> ((a, a), [[v]]) | | | sampledToneAltCell :: C a => Prototype a v -> a -> T a -> ((a, a), [[v]]) | | | oscillatorCells :: C t => T t y -> T t y -> t -> [y] -> (t, [t]) -> (T t, [t]) -> [((t, t), [[y]])] | | | dropFrac :: C i => i -> [a] -> (Int, i, [a]) | | | dropFrac' :: C i => i -> [a] -> (Int, i, [a]) | | | propDropFrac :: (C i, Eq a) => i -> [a] -> Bool | | | dropRem :: Int -> [a] -> (Int, [a]) | | | dropRem' :: Int -> [a] -> (Int, [a]) | | | propDropRem :: Eq a => Int -> [a] -> Bool | | | oscillatorCoords :: C t => Int -> t -> (t, [t]) -> (T t, [t]) -> [(Int, (Int, (t, t)))] | | | freqToPhase :: C a => T a -> [a] -> [T a] | | | limitRelativeShapes :: C t => T t y -> T t y -> Int -> [y] -> (t, [t]) -> (t, [t]) | | | limitMinRelativeValues :: (C a, Ord a) => a -> a -> [a] -> (a, [a]) | | | limitMaxRelativeValues :: (C a, Ord a) => a -> a -> [a] -> (a, [a]) | | | limitMaxRelativeValuesNonNeg :: (C a, Ord a) => a -> a -> [a] -> (a, [a]) | | | safeSub :: (C a, Ord a) => a -> a -> (Bool, a) |
|
|
|
| general helpers
|
|
| interpolateCell :: T a y -> T b y -> (a, b) -> [[y]] -> y | Source |
|
|
| untangleShapePhase :: C a => Int -> a -> (a, a) -> (a, a) | Source |
|
| Convert from the (shape,phase) parameter pair
to the index within a wave (step) and the index of a wave (leap)
in the sampled prototype tone.
|
|
| untangleShapePhaseAnalytic :: C a => Int -> a -> (a, a) -> (a, a) | Source |
|
|
| solveSLE2 :: C a => ((a, a), (a, a)) -> (a, a) -> (a, a) | Source |
|
|
| det2 :: C a => ((a, a), (a, a)) -> a | Source |
|
|
| flattenShapePhase :: C a => Int -> a -> (a, T a) -> (Int, (a, a)) | Source |
|
|
| shapeLimits :: C t => T a v -> T a v -> Int -> t -> (t, t) | Source |
|
|
|
|
| array based shape variable wave
|
|
|
| Constructors | | Prototype | | | protoIpLeap :: T a v | | | protoIpStep :: T a v | | | protoIpOffset :: Int | | | protoPeriod :: a | | | protoPeriodInt :: Int | | | protoShapeLimits :: (a, a) | | | protoArray :: Array Int v | |
|
|
|
|
|
|
|
|
|
|
| lazy oscillator
|
|
| oscillatorCells :: C t => T t y -> T t y -> t -> [y] -> (t, [t]) -> (T t, [t]) -> [((t, t), [[y]])] | Source |
|
|
| dropFrac :: C i => i -> [a] -> (Int, i, [a]) | Source |
|
|
| dropFrac' :: C i => i -> [a] -> (Int, i, [a]) | Source |
|
|
|
|
|
|
|
|
|
|
| oscillatorCoords :: C t => Int -> t -> (t, [t]) -> (T t, [t]) -> [(Int, (Int, (t, t)))] | Source |
|
|
| freqToPhase :: C a => T a -> [a] -> [T a] | Source |
|
| Convert a list of phase steps into a list of momentum phases
phase is a number in the interval [0,1)
freq contains the phase steps
|
|
| limitRelativeShapes :: C t => T t y -> T t y -> Int -> [y] -> (t, [t]) -> (t, [t]) | Source |
|
|
| limitMinRelativeValues :: (C a, Ord a) => a -> a -> [a] -> (a, [a]) | Source |
|
|
| limitMaxRelativeValues :: (C a, Ord a) => a -> a -> [a] -> (a, [a]) | Source |
|
|
| limitMaxRelativeValuesNonNeg :: (C a, Ord a) => a -> a -> [a] -> (a, [a]) | Source |
|
| Avoids negative numbers and thus can be used with Chunky numbers.
|
|
|
|
| Produced by Haddock version 2.3.0 |