Copyright | (c) Henning Thielemann 2006-2010 |
---|---|
License | GPL |
Maintainer | synthesizer@henning-thielemann.de |
Stability | provisional |
Portability | requires multi-parameter type classes |
Safe Haskell | None |
Language | Haskell2010 |
Basic waveforms
If you want to use parametrized waves with two parameters
then zip your parameter signals and apply uncurry
to the wave function.
- newtype T t y = Cons {}
- fromFunction :: (t -> y) -> T t y
- raise :: C y => y -> T t y -> T t y
- amplify :: C y => y -> T t y -> T t y
- distort :: (y -> z) -> T t y -> T t z
- overtone :: (C t, C n) => n -> T t y -> T t y
- apply :: T t y -> T t -> y
- phaseOffset :: C a => T a b -> a -> T a b
- sine :: C a => T a a
- cosine :: C a => T a a
- helix :: C a => T a (T a)
- fastSine2 :: (Ord a, C a) => T a a
- fastSine2Alt :: C a => T a a
- fastSine3 :: (Ord a, C a) => T a a
- fastSine3Alt :: (C a, C a) => T a a
- fastSine4 :: (Ord a, C a) => T a a
- fastSine4Alt :: (C a, C a) => T a a
- fastSine4LeastSquares :: (Ord a, C a) => T a a
- fastSinePolynomials :: C a => [T a]
- fastSines :: C a => [T a a]
- rationalHelix1 :: C a => a -> T a (T a)
- rationalHelix1Alt :: C a => a -> T a (T a)
- rationalHelix :: C a => Int -> a -> T a (T a)
- saw :: C a => T a a
- sawCos :: (C a, C a) => T a a
- sawComplex :: (Power a, C a, C a) => T a (T a)
- square :: (Ord a, C a) => T a a
- squareCos :: (C a, C a) => T a a
- squareComplex :: (Power a, C a, C a) => T a (T a)
- triangle :: (Ord a, C a) => T a a
- truncOddCosine :: C a => Int -> T a a
- truncOddTriangle :: C a => Int -> T a a
- truncCosine :: C a => a -> T a a
- truncTriangle :: C a => a -> T a a
- powerNormed :: (C a, C a) => a -> T a a
- powerNormed2 :: (C a, C a) => a -> T a a
- logitSaw :: C a => a -> T a a
- logitSine :: C a => a -> T a a
- sineSquare :: (C a, C a) => a -> T a a
- piecewiseParabolaSaw :: (C a, Ord a) => a -> T a a
- piecewiseSineSaw :: (C a, Ord a) => a -> T a a
- sineSawSmooth :: C a => a -> T a a
- sineSawSharp :: C a => a -> T a a
- sawGaussianHarmonics :: (C a, C a) => a -> [Harmonic a]
- sawPike :: (Ord a, C a) => a -> T a a
- trianglePike :: (C a, C a) => a -> T a a
- trianglePikeShift :: (C a, C a) => a -> a -> T a a
- squarePike :: C a => a -> T a a
- squarePikeShift :: C a => a -> a -> T a a
- squareAsymmetric :: (Ord a, C a) => a -> T a a
- squareBalanced :: (Ord a, C a) => a -> T a a
- triangleAsymmetric :: (Ord a, C a) => a -> T a a
- trapezoid :: (C a, C a) => a -> T a a
- trapezoidAsymmetric :: (C a, C a) => a -> a -> T a a
- trapezoidBalanced :: (C a, C a) => a -> a -> T a a
- trapezoidSkew :: (Ord a, C a) => a -> T a a
- data Harmonic a = Harmonic {
- harmonicPhase :: T a
- harmonicAmplitude :: a
- harmonic :: T a -> a -> Harmonic a
- composedHarmonics :: C a => [Harmonic a] -> T a a
Documentation
fromFunction :: (t -> y) -> T t y Source #
phaseOffset :: C a => T a b -> a -> T a b Source #
Turn an unparametrized waveform into a parametrized one, where the parameter is a phase offset. This way you may express a phase modulated oscillator using a shape modulated oscillator.
flip phaseOffset
could have also be named rotateLeft
,
since it rotates the wave to the left.
fastSine2Alt :: C a => T a a Source #
fastSine3 :: (Ord a, C a) => T a a Source #
Piecewise third order polynomial approximation by integrating fastSine2
.
fastSine4 :: (Ord a, C a) => T a a Source #
Piecewise fourth order polynomial approximation by integrating fastSine3
.
fastSine4LeastSquares :: (Ord a, C a) => T a a Source #
Least squares approximation of sine by fourth order polynomials computed with MuPad.
fastSinePolynomials :: C a => [T a] Source #
The coefficient of the highest power is the reciprocal of an element from http://oeis.org/A000111 and the polynomial coefficients are http://oeis.org/A119879 .
mapM_ print $ map (\p -> fmap ((round :: Rational -> Integer) . (/last(Poly.coeffs p))) p) (take 10 $ fastSinePolynomials)
rationalHelix1 :: C a => a -> T a (T a) Source #
This is a helix that is distorted in phase
such that it becomes a purely rational function.
It is guaranteed that the magnitude of the wave is one.
For the distortion factor recip pi
you get the closest approximation
to an undistorted helix.
We have chosen this scaling in order to stay with field operations.
rationalHelix :: C a => Int -> a -> T a (T a) Source #
Here we distort the rational helix in phase
using tangent approximations by a sum of 2*n reciprocal functions.
For the tangent function we obtain perfect cosine and sine,
thus for k = recip pi
and high n
we approach an undistorted complex helix.
saw tooth, it's a ramp down in order to have a positive coefficient for the first partial sine
sawCos :: (C a, C a) => T a a Source #
This wave has the same absolute Fourier coefficients as saw
but the partial waves are shifted by 90 degree.
That is, it is the Hilbert transform of the saw wave.
The formula is derived from sawComplex
.
sawComplex :: (Power a, C a, C a) => T a (T a) Source #
sawCos + i*saw
This is an analytic function and thus it may be used for frequency shifting.
The formula can be derived from the power series of the logarithm function.
squareCos :: (C a, C a) => T a a Source #
This wave has the same absolute Fourier coefficients as square
but the partial waves are shifted by 90 degree.
That is, it is the Hilbert transform of the saw wave.
squareComplex :: (Power a, C a, C a) => T a (T a) Source #
squareCos + i*square
This is an analytic function and thus it may be used for frequency shifting.
The formula can be derived from the power series of the area tangens function.
truncCosine :: C a => a -> T a a Source #
A truncated cosine plus a ramp that guarantees a bump of high 2 at the boundaries.
It is truncCosine (2 * fromIntegral n + 0.5) == truncOddCosine (2*n)
truncTriangle :: C a => a -> T a a Source #
powerNormed2 :: (C a, C a) => a -> T a a Source #
Power function.
Roughly the map p x -> x**p
but retains the sign of x
and
normalizes the mapping over [0,1]
to an L2 norm of 1.
logitSaw :: C a => a -> T a a Source #
Tangens hyperbolicus allows interpolation
between some kind of saw tooth and square wave.
In principle it is not necessary
because you can distort a saw tooth oscillation by map tanh
.
logitSine :: C a => a -> T a a Source #
Tangens hyperbolicus of a sine allows interpolation
between some kind of sine and square wave.
In principle it is not necessary
because you can distort a square oscillation by map tanh
.
sawGaussianHarmonics :: (C a, C a) => a -> [Harmonic a] Source #
Harmonics of a saw wave that is smoothed by a Gaussian lowpass filter. This can also be used to interpolate between saw wave and sine. The parameter is the cutoff-frequency defined as the standard deviation of the Gaussian in frequency space. That is, high values approximate a saw and need many harmonics, whereas low values tend to a sine and need only few harmonics.
saw with space
triangle with space
:: (C a, C a) | |
=> a | pike width ranging from 0 to 1 |
-> a | shift ranges from -1 to 1; 0 yields |
-> T a a |
triangle with space and shift
square with space, can also be generated by mixing square waves with different phases
:: C a | |
=> a | pike width ranging from 0 to 1 |
-> a | shift ranges from -1 to 1; 0 yields |
-> T a a |
square with space and shift
:: (Ord a, C a) | |
=> a | value between -1 and 1 controlling the ratio of high and low time:
-1 turns the high time to zero,
1 makes the low time zero,
0 yields |
-> T a a |
square with different times for high and low
squareBalanced :: (Ord a, C a) => a -> T a a Source #
Like squareAsymmetric
but with zero average.
It could be simulated by adding two saw oscillations
with 180 degree phase difference and opposite sign.
:: (Ord a, C a) | |
=> a | asymmetry parameter ranging from -1 to 1: For 0 you obtain the usual triangle. For -1 you obtain a falling saw tooth starting with its maximum. For 1 you obtain a rising saw tooth starting with a zero. |
-> T a a |
triangle
:: (C a, C a) | |
=> a | width of the plateau ranging from 0 to 1:
0 yields |
-> T a a |
Mixing trapezoid
and trianglePike
you can get back a triangle wave form
:: (C a, C a) | |
=> a | sum of the plateau widths ranging from 0 to 1:
0 yields |
-> a | asymmetry of the plateau widths ranging from -1 to 1 |
-> T a a |
Trapezoid with distinct high and low time. That is the high and low trapezoids are symmetric itself, but the whole waveform is not symmetric.
trapezoidBalanced :: (C a, C a) => a -> a -> T a a Source #
trapezoid with distinct high and low time and zero direct current offset
:: (Ord a, C a) | |
=> a | width of the ramp, that is 1 yields a downwards saw ramp and 0 yields a square wave. |
-> T a a |
parametrized trapezoid that can range from a saw ramp to a square waveform.
This is similar to Polar coordinates,
but the range of the phase is from 0
to 1
, not 0
to 2*pi
.
If you need to represent a harmonic by complex coefficients
instead of the polar representation,
then please build a complex valued polynomial from your coefficients
and use it to distort a helix
.
distort (Poly.evaluate (Poly.fromCoeffs complexCoefficients)) helix
Harmonic | |
|