synthesizer-core-0.7.0.2: Audio signal processing coded in Haskell: Low level part

Portabilityrequires multi-parameter type classes
Stabilityprovisional
Maintainersynthesizer@henning-thielemann.de
Safe HaskellNone

Synthesizer.Basic.Wave

Contents

Description

Basic waveforms

If you want to use parametrized waves with two parameters then zip your parameter signals and apply uncurry to the wave function.

Synopsis

Definition and construction

newtype T t y

Constructors

Cons 

Fields

decons :: T t -> y
 

Instances

C a y => C a (T t y) 
Functor (T t) 
Applicative (T t) 
C y => C (T t y) 

fromFunction :: (t -> y) -> T t y

Operations on waves

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

Turn an unparametrized waveform into a parametrized one, where the parameter is a phase offset. This way you 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.

Examples

unparameterized

sine :: C a => T a a

map a phase to value of a sine wave

cosine :: C a => T a a

helix :: C a => T a (T a)

fastSine2 :: (Ord a, C a) => T a a

Approximation of sine by parabolas. Surprisingly it is not really faster than sine. The wave results from integrating the triangle wave, thus it the k-th harmonic has amplitude recip (k^3).

fastSine2Alt :: C a => T a a

fastSine3 :: (Ord a, C a) => T a a

Piecewise third order polynomial approximation by integrating fastSine2.

fastSine3Alt :: (C a, C a) => T a a

fastSine4 :: (Ord a, C a) => T a a

Piecewise fourth order polynomial approximation by integrating fastSine3.

fastSine4Alt :: (C a, C a) => T a a

fastSine4LeastSquares :: (Ord a, C a) => T a a

Least squares approximation of sine by fourth order polynomials computed with MuPad.

fastSinePolynomials :: C a => [T a]

The coefficient of the highest power is the reciprocal of an element from http:www.research.att.com~njassequences/A000111 and the polynomial coefficients are http:www.research.att.com~njassequences/A119879 .

 mapM_ print $ map (\p -> fmap ((round :: Rational -> Integer) . (/last(Poly.coeffs p))) p) (take 10 $ fastSinePolynomials)

fastSines :: C a => [T a a]

rationalHelix1 :: C a => a -> T a (T a)

This is a helix that is distorted in phase such that is 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.

rationalHelix1Alt :: C a => a -> T a (T a)

rationalHelix :: C a => Int -> a -> T a (T a)

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.

helixFromTangent :: C a => a -> T a

saw :: C a => T a a

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

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)

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.

square :: (Ord a, C a) => T a a

square

squareCos :: (C a, C a) => T a a

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)

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.

triangle :: (Ord a, C a) => T a a

triangle

discretely parameterized

truncOddCosine :: C a => Int -> T a a

A truncated cosine. This has rich overtones.

truncOddTriangle :: C a => Int -> T a a

For parameter zero this is saw.

continuously parameterized

truncCosine :: C a => a -> T a a

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

powerNormed :: (C a, C a) => a -> T a a

Power function.

Roughly the map x p -> x**p but retains the sign of x and normalizes the mapping over [-1,1] to L2 norm of 1.

power01Normed :: (C a, C a) => a -> a -> a

auxiliary

powerSigned :: (C a, C a) => a -> a -> a

auxiliary

logitSaw :: C a => a -> T a a

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

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.

sineSquare

Arguments

:: (C a, C a) 
=> a

0 for sine, 1 for square

-> T a a 

Interpolation between sine and square.

piecewiseParabolaSaw

Arguments

:: (C a, Ord a) 
=> a

0 for fastSine2, 1 for saw

-> T a a 

Interpolation between fastSine2 and saw. We just shrink the parabola towards the borders and insert a linear curve such that its slope matches the one of the parabola.

piecewiseSineSaw

Arguments

:: (C a, Ord a) 
=> a

0 for sine, 1 for saw

-> T a a 

Interpolation between sine and saw. We just shrink the sine towards the borders and insert a linear curve such that its slope matches the one of the sine.

sineSawSmooth

Arguments

:: C a 
=> a

0 for sine, 1 for saw

-> T a a 

Interpolation between sine and saw with smooth intermediate shapes but no perfect saw.

sineSawSharp

Arguments

:: C a 
=> a

0 for sine, 1 for saw

-> T a a 

Interpolation between sine and saw with perfect saw, but sharp intermediate shapes.

affineComb :: C a => a -> (a, a) -> a

sawGaussianHarmonics :: (C a, C a) => a -> [Harmonic a]

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.

sawPike

Arguments

:: (Ord a, C a) 
=> a

pike width ranging from 0 to 1, 1 yields saw

-> T a a 

saw with space

trianglePike

Arguments

:: (C a, C a) 
=> a

pike width ranging from 0 to 1, 1 yields triangle

-> T a a 

triangle with space

trianglePikeShift

Arguments

:: (C a, C a) 
=> a

pike width ranging from 0 to 1

-> a

shift ranges from -1 to 1; 0 yields trianglePike

-> T a a 

triangle with space and shift

squarePike

Arguments

:: C a 
=> a

pike width ranging from 0 to 1, 1 yields square

-> T a a 

square with space, can also be generated by mixing square waves with different phases

squarePikeShift

Arguments

:: C a 
=> a

pike width ranging from 0 to 1

-> a

shift ranges from -1 to 1; 0 yields squarePike

-> T a a 

square with space and shift

squareAsymmetric

Arguments

:: (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 square

-> T a a 

square with different times for high and low

squareBalanced :: (Ord a, C a) => a -> T a a

Like squareAsymmetric but with zero average. It could be simulated by adding two saw oscillations with 180 degree phase difference and opposite sign.

triangleAsymmetric

Arguments

:: (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

trapezoid

Arguments

:: (C a, C a) 
=> a

width of the plateau ranging from 0 to 1: 0 yields triangle, 1 yields square

-> T a a 

Mixing trapezoid and trianglePike you can get back a triangle wave form

trapezoidAsymmetric

Arguments

:: (C a, C a) 
=> a

sum of the plateau widths ranging from 0 to 1: 0 yields triangleAsymmetric, 1 yields squareAsymmetric

-> 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

trapezoid with distinct high and low time and zero direct current offset

trapezoidSkew

Arguments

:: (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.

data Harmonic a

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

Constructors

Harmonic 

Fields

harmonicPhase :: T a
 
harmonicAmplitude :: a
 

harmonic :: T a -> a -> Harmonic a

composedHarmonics :: C a => [Harmonic a] -> T a a

Specify the wave by its harmonics.

The function is implemented quite efficiently by applying the Horner scheme to a polynomial with complex coefficients (the harmonic parameters) using a complex exponential as argument.