synthesizer-0.2: Audio signal processing coded in HaskellSource codeContentsIndex
Synthesizer.State.ToneModulation
Contents
lazy oscillator
handling of phases as needed for oscillators
Synopsis
type Cell sig y = T (sig y)
interpolateCell :: Read sig y => T a y -> T b y -> (a, b) -> Cell sig y -> y
data Prototype sig a v = Prototype {
protoMarginLeap :: Margin
protoMarginStep :: Margin
protoIpOffset :: Int
protoPeriod :: a
protoPeriodInt :: Int
protoShapeLimits :: (a, a)
protoSignal :: sig v
}
makePrototype :: (C a, Read sig v) => Margin -> Margin -> a -> sig v -> Prototype sig a v
sampledToneCell :: (C a, Transform sig v) => Prototype sig a v -> a -> T a -> ((a, a), Cell sig v)
oscillatorCells :: (C t, Transform sig y) => Margin -> Margin -> t -> sig y -> (t, T t) -> (T t, T t) -> T ((t, t), Cell sig y)
checkNonNeg :: (Ord a, C a, Show a) => a -> a
makeCell :: Transform sig y => Int -> sig y -> Cell sig y
oscillatorCoords :: C t => Int -> t -> (t, T t) -> (T t, T t) -> T (Coords t)
limitRelativeShapes :: C t => Margin -> Margin -> Int -> (t, T t) -> (t, T t)
limitMinRelativeValues :: (C t, Ord t) => t -> (t, T t) -> (t, T t)
freqsToPhases :: C a => T a -> T a (T a)
freqsToPhasesSync :: C a => T a -> T a (T a)
Documentation
type Cell sig y = T (sig y)Source
interpolateCell :: Read sig y => T a y -> T b y -> (a, b) -> Cell sig y -> ySource
data Prototype sig a v Source
Constructors
Prototype
protoMarginLeap :: Margin
protoMarginStep :: Margin
protoIpOffset :: Int
protoPeriod :: a
protoPeriodInt :: Int
protoShapeLimits :: (a, a)
protoSignal :: sig v
makePrototype :: (C a, Read sig v) => Margin -> Margin -> a -> sig v -> Prototype sig a vSource
sampledToneCell :: (C a, Transform sig v) => Prototype sig a v -> a -> T a -> ((a, a), Cell sig v)Source
lazy oscillator
oscillatorCells :: (C t, Transform sig y) => Margin -> Margin -> t -> sig y -> (t, T t) -> (T t, T t) -> T ((t, t), Cell sig y)Source
This function should not be used, since it requires recomputation of shapes and freqs lists.
checkNonNeg :: (Ord a, C a, Show a) => a -> aSource
makeCell :: Transform sig y => Int -> sig y -> Cell sig ySource
oscillatorCoords :: C t => Int -> t -> (t, T t) -> (T t, T t) -> T (Coords t)Source
limitRelativeShapes :: C t => Margin -> Margin -> Int -> (t, T t) -> (t, T t)Source
limitMinRelativeValues :: (C t, Ord t) => t -> (t, T t) -> (t, T t)Source
handling of phases as needed for oscillators
freqsToPhases :: C a => T a -> T 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. The last element is omitted.
freqsToPhasesSync :: C a => T a -> T a (T a)Source
Like freqsToPhases but the first element is omitted.
Produced by Haddock version 2.4.2