-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Audio signal processing coded in Haskell: Low level part -- -- Low level audio signal processing used by the other synthesizer -- packages. The routines can be really fast due to StorableVector, -- Stream-like list type and aggressive inlining. For an interface to -- Haskore see -- http://code.haskell.org/haskore/revised/synthesizer/. For -- introductory examples see Synthesizer.Plain.Tutorial and -- Synthesizer.Generic.Tutorial. -- -- Functions: Oscillators, Noise generators, Frequency filters, Fast -- Fourier transform for computation of frequency spectrum @package synthesizer-core @version 0.8.4 module Synthesizer.ApplicativeUtility liftA4 :: Applicative f => (a -> b -> c -> d -> e) -> f a -> f b -> f c -> f d -> f e liftA5 :: Applicative f => (a -> b -> c -> d -> e -> g) -> f a -> f b -> f c -> f d -> f e -> f g liftA6 :: Applicative f => (a -> b -> c -> d -> e -> g -> h) -> f a -> f b -> f c -> f d -> f e -> f g -> f h -- | Create a loop (feedback) from one node to another one. That is, -- compute the fix point of a process iteration. loop :: Functor f => f (a -> a) -> f a -- | This corresponds to <*> ($:) :: Applicative f => f (a -> b) -> f a -> f b infixl 0 $: -- | Instead of mixMulti $:: map f xs the caller should write -- mixMulti $: mapM f xs in order to save the user from learning -- another infix operator. ($::) :: (Applicative f, Traversable t) => f (t a -> b) -> t (f a) -> f b infixl 0 $:: (.:) :: (Applicative f, Arrow arrow) => f (arrow b c) -> f (arrow a b) -> f (arrow a c) infixr 9 .: ($^) :: Functor f => (a -> b) -> f a -> f b infixl 0 $^ (.^) :: (Functor f, Arrow arrow) => arrow b c -> f (arrow a b) -> f (arrow a c) infixr 9 .^ ($#) :: Functor f => f (a -> b) -> a -> f b infixl 0 $# -- | Our signal processors have types like f (a -> b -> c). -- They could also have the type a -> b -> f c or f a -- -> f b -> f c. We did not choose the last variant for -- reduction of redundancy in type signatures and for simplifying -- sharing, and we did not choose the second variant for easy composition -- of processors. However the forms are freely convertible, and if you -- prefer the last one because you do not want to sprinkle ($:) in -- your code, then you may want to convert the processors using the -- following functions, that can be defined purely in the -- Applicative class. liftP :: Applicative f => f (a -> b) -> f a -> f b liftP2 :: Applicative f => f (a -> b -> c) -> f a -> f b -> f c liftP3 :: Applicative f => f (a -> b -> c -> d) -> f a -> f b -> f c -> f d liftP4 :: Applicative f => f (a -> b -> c -> d -> e) -> f a -> f b -> f c -> f d -> f e -- | The distortion functions have slope 1 at zero, if they are -- differentiable at that point, at all. This ensures that signals with -- low amplitude are only slightly altered. Non-differentiable -- distortions try to have an overall slope of 1. module Synthesizer.Basic.Distortion -- | limit, fuzz booster clip :: C a => a -> a -- | logit, tanh logit :: C a => a -> a -- | zig-zag zigZag :: C a => a -> a -- | sine sine :: C a => a -> a -- | Odd Chebyshev polynomial -- -- oddChebyshev n is an appropriately scaled Chebyshev -- polynomial of order 2*n+1. The argument n must be -- non-negative. -- --
--   Graphics.Gnuplot.Simple.plotFuncs [Graphics.Gnuplot.Simple.YRange (-1,1)] (Graphics.Gnuplot.Simple.linearScale 1000 (-7,7::Double)) (List.map oddChebyshev [0..5])
--   
oddChebyshev :: C a => C a => Int -> a -> a quantize :: C a => a -> a -- | Power function. Roughly the map p x -> x**p but retains -- the sign of x. powerSigned :: (C a, C a) => a -> a -> a module Synthesizer.Basic.DistortionControlled -- | limit, fuzz booster clip :: C a => a -> a -> a -- | logit, tanh logit :: C a => a -> a -> a -- | zig-zag zigZag :: C a => a -> a -> a -- | sine sine :: C a => a -> a -> a quantize :: C a => a -> a -> a module Synthesizer.Basic.Phase data T a fromRepresentative :: C a => a -> T a toRepresentative :: T a -> a increment :: C a => a -> T a -> T a decrement :: C a => a -> T a -> T a multiply :: (C a, C b) => b -> T a -> T a instance GHC.Classes.Eq a => GHC.Classes.Eq (Synthesizer.Basic.Phase.T a) instance GHC.Show.Show a => GHC.Show.Show (Synthesizer.Basic.Phase.T a) instance Foreign.Storable.Storable a => Foreign.Storable.Storable (Synthesizer.Basic.Phase.T a) instance (Algebra.Ring.C a, System.Random.Random a) => System.Random.Random (Synthesizer.Basic.Phase.T a) instance (Algebra.Ring.C a, System.Random.Random a) => Test.QuickCheck.Arbitrary.Arbitrary (Synthesizer.Basic.Phase.T a) instance Algebra.RealRing.C a => Algebra.Additive.C (Synthesizer.Basic.Phase.T a) -- | Basic waveforms -- -- If you want to use parametrized waves with two parameters then zip -- your parameter signals and apply uncurry to the wave function. module Synthesizer.Basic.Wave newtype T t y Cons :: (T t -> y) -> T t y [decons] :: T t y -> T t -> y 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 -- | 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. phaseOffset :: C a => T a b -> a -> T a b -- | map a phase to value of a sine wave sine :: C a => T a a cosine :: C a => T a a helix :: C a => T a (T 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). fastSine2 :: (Ord a, C a) => T a a fastSine2Alt :: C a => T a a -- | Piecewise third order polynomial approximation by integrating -- fastSine2. fastSine3 :: (Ord a, C a) => T a a fastSine3Alt :: (C a, C a) => T a a -- | Piecewise fourth order polynomial approximation by integrating -- fastSine3. fastSine4 :: (Ord a, C a) => T a a fastSine4Alt :: (C a, C a) => T a a -- | Least squares approximation of sine by fourth order polynomials -- computed with MuPad. fastSine4LeastSquares :: (Ord a, C a) => T a a -- | 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)
--   
fastSinePolynomials :: C a => [T a] fastSines :: C a => [T a a] -- | 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. rationalHelix1 :: C a => a -> T a (T a) rationalHelix1Alt :: C a => 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. rationalHelix :: C a => Int -> a -> T a (T a) -- | saw tooth, it's a ramp down in order to have a positive coefficient -- for the first partial sine saw :: 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. sawCos :: (C a, C a) => T a 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. sawComplex :: (Power a, C a, C a) => T a (T a) -- | superSaw n d requires 1 <= n and n*d <= -- 1. superSaw :: (C a, C a) => Int -> a -> T a a -- | square square :: (Ord 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. squareCos :: (C a, C a) => T a 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. squareComplex :: (Power a, C a, C a) => T a (T a) -- | triangle triangle :: (Ord a, C a) => T a a -- | A truncated cosine. This has rich overtones. truncOddCosine :: C a => Int -> T a a -- | For parameter zero this is saw. truncOddTriangle :: C a => Int -> 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) truncCosine :: C a => a -> T a a truncTriangle :: C a => a -> T a a -- | Power function. Roughly the map p x -> x**p but retains -- the sign of x and it should normalize the mapping over -- [-1,1] to an L2 norm of 1, but I got this one wrong. -- -- The sign is flipped with respect to saw and sine which -- is an historical artifact. -- | Deprecated: Use powerNormed2 instead. powerNormed :: (C a, C a) => a -> T a a -- | 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. powerNormed2 :: (C a, 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. logitSaw :: 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. logitSine :: C a => a -> T a a -- | Interpolation between sine and square. sineSquare :: (C a, C a) => a -> 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. piecewiseParabolaSaw :: (C a, Ord a) => a -> 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. piecewiseSineSaw :: (C a, Ord a) => a -> T a a -- | Interpolation between sine and saw with smooth -- intermediate shapes but no perfect saw. sineSawSmooth :: C a => a -> T a a -- | Interpolation between sine and saw with perfect saw, but -- sharp intermediate shapes. sineSawSharp :: C a => a -> T a 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. sawGaussianHarmonics :: (C a, C a) => a -> [Harmonic a] -- | saw with space sawPike :: (Ord a, C a) => a -> T a a -- | triangle with space trianglePike :: (C a, C a) => a -> T a a -- | triangle with space and shift trianglePikeShift :: (C a, C a) => a -> a -> T a a -- | square with space, can also be generated by mixing square waves with -- different phases squarePike :: C a => a -> T a a -- | square with space and shift squarePikeShift :: C a => a -> a -> T a a -- | square with different times for high and low squareAsymmetric :: (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. squareBalanced :: (Ord a, C a) => a -> T a a -- | triangle triangleAsymmetric :: (Ord a, C a) => a -> T a a -- | Mixing trapezoid and trianglePike you can get back a -- triangle wave form trapezoid :: (C a, C a) => a -> 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. trapezoidAsymmetric :: (C a, C a) => a -> a -> T a a -- | trapezoid with distinct high and low time and zero direct current -- offset trapezoidBalanced :: (C a, C a) => a -> a -> T a a -- | parametrized trapezoid that can range from a saw ramp to a square -- waveform. trapezoidSkew :: (Ord a, C a) => a -> T a 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
--   
data Harmonic a Harmonic :: T a -> a -> Harmonic a [harmonicPhase] :: Harmonic a -> T a [harmonicAmplitude] :: Harmonic a -> a harmonic :: T a -> a -> Harmonic 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. composedHarmonics :: C a => [Harmonic a] -> T a a instance Algebra.Additive.C y => Algebra.Additive.C (Synthesizer.Basic.Wave.T t y) instance Algebra.Module.C a y => Algebra.Module.C a (Synthesizer.Basic.Wave.T t y) instance GHC.Base.Functor (Synthesizer.Basic.Wave.T t) instance GHC.Base.Applicative (Synthesizer.Basic.Wave.T t) -- | Waveforms which are smoothed according to the oscillator frequency in -- order to suppress aliasing effects. module Synthesizer.Basic.WaveSmoothed data T t y fromFunction :: (t -> t -> y) -> T t y -- | Use this function for waves which are sufficiently smooth. If the -- Nyquist frequency is exceeded the wave is simply replaced by a -- constant zero wave. fromWave :: (C t, C t, C y) => T t y -> T t y fromControlledWave :: (C t, C t, C y) => (t -> T 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 apply :: T t y -> t -> T t -> y -- | map a phase to value of a sine wave sine :: (C a, C a) => T a a cosine :: (C a, C a) => T a a -- | saw tooth, it's a ramp down in order to have a positive coefficient -- for the first partial sine saw :: (C a, C a) => T a a -- | square square :: (C a, C a) => T a a -- | triangle triangle :: (C a, C a) => T a 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
--   
data Harmonic a harmonic :: T a -> a -> Harmonic 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. composedHarmonics :: (C a, C a) => [Harmonic a] -> T a a instance Algebra.Additive.C y => Algebra.Additive.C (Synthesizer.Basic.WaveSmoothed.T t y) instance Algebra.Module.C a y => Algebra.Module.C a (Synthesizer.Basic.WaveSmoothed.T t y) module Synthesizer.Causal.Displacement -- | Mix two signals. Unfortunately we have to use zipWith semantic -- here, that is the result is as long as the shorter of both inputs. mix :: (C v, Arrow arrow) => arrow (v, v) v -- | Add a number to all of the signal values. This is useful for adjusting -- the center of a modulation. raise :: (C v, Arrow arrow) => v -> arrow v v -- | In Synthesizer.Basic.Distortion you find a collection of -- appropriate distortion functions. distort :: Arrow arrow => (c -> a -> a) -> arrow (c, a) a mapLinear :: (C a, Arrow arrow) => a -> a -> arrow a a mapExponential :: (C a, Arrow arrow) => a -> a -> arrow a a module Synthesizer.Causal.Spatial -- | simulate an moving sounding object -- -- convert the way of the object through 2D or 3D space into a delay and -- attenuation information, sonicDelay is the reciprocal of the sonic -- velocity moveAround :: (C a, C a v, Arrow arrow) => a -> a -> v -> arrow v (a, a) -- | Utility functions based only on Arrow class. module Synthesizer.Causal.Utility map :: Arrow arrow => (b -> c) -> arrow a b -> arrow a c pure :: Arrow arrow => b -> arrow a b apply :: Arrow arrow => arrow a (b -> c) -> arrow a b -> arrow a c chainControlled :: Arrow arrow => [arrow (c, x) x] -> arrow (c, x) x replicateControlled :: Arrow arrow => Int -> arrow (c, x) x -> arrow (c, x) x module Synthesizer.Causal.Class class (Arrow process, ProcessOf (SignalOf process) ~ process) => C process where { type SignalOf process :: * -> *; } toSignal :: C process => process () a -> SignalOf process a fromSignal :: C process => SignalOf process b -> process a b type family ProcessOf (signal :: * -> *) :: * -> * -> * apply :: C process => process a b -> SignalOf process a -> SignalOf process b ($>) :: C process => process (a, b) c -> SignalOf process b -> process a c infixl 0 $> ($<) :: C process => process (a, b) c -> SignalOf process a -> process b c infixl 0 $< ($*) :: C process => process a b -> SignalOf process a -> SignalOf process b infixl 0 $* applyFst :: C process => process (a, b) c -> SignalOf process a -> process b c applySnd :: C process => process (a, b) c -> SignalOf process b -> process a c applyConst :: C process => process a b -> a -> SignalOf process b feedFst :: C process => SignalOf process a -> process b (a, b) feedSnd :: C process => SignalOf process a -> process b (b, a) feedConstFst :: Arrow process => a -> process b (a, b) feedConstSnd :: Arrow process => a -> process b (b, a) applyConstFst :: Arrow process => process (a, b) c -> a -> process b c applyConstSnd :: Arrow process => process (a, b) c -> b -> process a c chainControlled :: Arrow arrow => [arrow (c, x) x] -> arrow (c, x) x replicateControlled :: Arrow arrow => Int -> arrow (c, x) x -> arrow (c, x) x module Synthesizer.Format class C sig format :: (C sig, Show x) => Int -> sig x -> ShowS module Synthesizer.Frame.Stereo data () => T a left :: T a -> a right :: T a -> a cons :: a -> a -> T a map :: (a -> b) -> T a -> T b swap :: T a -> T a -- | Run a causal process independently on each stereo channel. arrowFromMono :: Arrow arrow => arrow a b -> arrow (T a) (T b) arrowFromMonoControlled :: Arrow arrow => arrow (c, a) b -> arrow (c, T a) (T b) arrowFromChannels :: Arrow arrow => arrow a b -> arrow a b -> arrow (T a) (T b) data () => Channel Left :: Channel Right :: Channel select :: T a -> Channel -> a interleave :: (T a, T b) -> T (a, b) sequence :: Functor f => f (T a) -> T (f a) liftApplicative :: Applicative f => (f a -> f b) -> f (T a) -> f (T b) module Synthesizer.Basic.Binary class C a outputFromCanonical :: (C a, Bounded int, C int, Monoid out) => (int -> out) -> a -> out numberOfChannels :: C a => a -> Int toCanonical :: (C real, Bounded int, C int) => int -> real fromCanonicalWith :: (C real, Bounded int, C int) => (real -> int) -> real -> int -- | Warning: This may produce negative results for positive input in some -- cases! The problem is that (maxBound :: Int32) cannot be represented -- exactly as Float, the Float value is actually a bit larger than the -- Int32 value. Thus when converting the Float back to Int32 it becomes -- negative. Better use fromCanonicalWith. fromCanonicalSimpleWith :: (C real, Bounded int, C int) => (real -> int) -> real -> int numberOfSignalChannels :: C yv => sig yv -> Int int16ToCanonical :: C a => Int16 -> a int16FromCanonical :: C a => a -> Int16 int16FromFloat :: Float -> Int16 int16FromDouble :: Double -> Int16 instance Synthesizer.Basic.Binary.C GHC.Types.Float instance Synthesizer.Basic.Binary.C GHC.Types.Double instance (Synthesizer.Basic.Binary.C a, Synthesizer.Basic.Binary.C b) => Synthesizer.Basic.Binary.C (a, b) instance Synthesizer.Basic.Binary.C a => Synthesizer.Basic.Binary.C (Sound.Frame.Stereo.T a) -- | Construction of a data type that describes piecewise defined curves. module Synthesizer.Piecewise type T t y sig = [PieceData t y sig] -- | The curve type of a piece of a piecewise defined control curve. newtype Piece t y sig Piece :: (y -> y -> t -> sig) -> Piece t y sig [computePiece] :: Piece t y sig -> y -> y -> t -> sig pieceFromFunction :: (y -> y -> t -> sig) -> Piece t y sig -- | The full description of a control curve piece. data PieceData t y sig PieceData :: Piece t y sig -> y -> y -> t -> PieceData t y sig [pieceType] :: PieceData t y sig -> Piece t y sig [pieceY0] :: PieceData t y sig -> y [pieceY1] :: PieceData t y sig -> y [pieceDur] :: PieceData t y sig -> t newtype PieceRightSingle y PRS :: y -> PieceRightSingle y newtype PieceRightDouble y PRD :: y -> PieceRightDouble y data PieceDist t y sig PD :: t -> Piece t y sig -> y -> PieceDist t y sig -- | The 6 operators simplify constructing a list of PieceData 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 -- =. -- --
    --
  1. Nothing means that here is the start or the end node of a -- curve.
  2. --
  3. Minus means that here is a node where left and right curve meet at -- the same value. The node description is thus one value.
  4. --
  5. 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.
  6. --
(#|-) :: (t, Piece t y sig) -> (PieceRightSingle y, T t y sig) -> (PieceDist t y sig, T t y sig) infixr 5 #|- (-|#) :: y -> (PieceDist t y sig, T t y sig) -> (PieceRightSingle y, T t y sig) infixr 5 -|# (#|=) :: (t, Piece t y sig) -> (PieceRightDouble y, T t y sig) -> (PieceDist t y sig, T t y sig) infixr 5 #|= (=|#) :: (y, y) -> (PieceDist t y sig, T t y sig) -> (PieceRightDouble y, T t y sig) infixr 5 =|# (#|) :: (t, Piece t y sig) -> y -> (PieceDist t y sig, T t y sig) infixr 5 #| (|#) :: y -> (PieceDist t y sig, T t y sig) -> T t y sig infixr 5 |# data FlatPosition FlatLeft :: FlatPosition FlatRight :: FlatPosition splitDurations :: C t => [t] -> [(Int, t)] instance GHC.Enum.Enum Synthesizer.Piecewise.FlatPosition instance GHC.Ix.Ix Synthesizer.Piecewise.FlatPosition instance GHC.Classes.Ord Synthesizer.Piecewise.FlatPosition instance GHC.Classes.Eq Synthesizer.Piecewise.FlatPosition instance GHC.Show.Show Synthesizer.Piecewise.FlatPosition module Synthesizer.Plain.Builder data T a type Put a = a -> T a put :: Put a run :: T a -> [a] signalToBinary :: (C v, C int, Bounded int) => [v] -> [int] signalToBinaryMono :: (C a, C int, Bounded int) => [a] -> [int] signalToBinaryStereo :: (C a, C int, Bounded int) => [(a, a)] -> [int] instance GHC.Base.Semigroup (Synthesizer.Plain.Builder.T a) instance GHC.Base.Monoid (Synthesizer.Plain.Builder.T a) module Synthesizer.Plain.Filter.Recursive -- | Description of a filter pole. data Pole a Pole :: !a -> !a -> Pole a -- | Resonance, that is the amplification of the band center frequency. [poleResonance] :: Pole a -> !a -- | Band center frequency. [poleFrequency] :: Pole a -> !a data Passband Lowpass :: Passband Highpass :: Passband instance GHC.Read.Read a => GHC.Read.Read (Synthesizer.Plain.Filter.Recursive.Pole a) instance GHC.Show.Show a => GHC.Show.Show (Synthesizer.Plain.Filter.Recursive.Pole a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Synthesizer.Plain.Filter.Recursive.Pole a) instance GHC.Enum.Enum Synthesizer.Plain.Filter.Recursive.Passband instance GHC.Classes.Eq Synthesizer.Plain.Filter.Recursive.Passband instance GHC.Show.Show Synthesizer.Plain.Filter.Recursive.Passband instance Algebra.Additive.C v => Algebra.Additive.C (Synthesizer.Plain.Filter.Recursive.Pole v) instance Algebra.Module.C a v => Algebra.Module.C a (Synthesizer.Plain.Filter.Recursive.Pole v) module Synthesizer.Plain.Filter.Recursive.AllpassPoly newtype Parameter a Parameter :: [a] -> Parameter a -- | Compute coefficients for an allpass that shifts low frequencies by -- approximately the shift you want. To achieve this we solve a linear -- least squares problem, where low frequencies are more weighted than -- high ones. The output is a list of coefficients for an arbitrary order -- allpass. shiftParam :: (Scalar a, Fractional a, C a) => Int -> a -> a -> Parameter a makePhase :: (C a, C a) => Parameter a -> a -> a scalarProdScrewExp :: C a => a -> Int -> a -> Int -> Int -> a screwProd :: C a => Int -> a -> Int -> Int -> a -> a integrateScrewExp :: C a => a -> Int -> (a, a) integrateNum :: (C a, C a v) => Int -> (a, a) -> (a -> v) -> v instance GHC.Show.Show a => GHC.Show.Show (Synthesizer.Plain.Filter.Recursive.AllpassPoly.Parameter a) -- | This is old code, handling Int16 using two characters. -- | Deprecated: Use Sound.Sox.Signal.List instead. module Synthesizer.Plain.IO -- | Uses endianess of the machine, like Sox does. writeInt16Stream :: FilePath -> [Int16] -> IO () -- | The end of the list is undefined, if the file has odd length. It would -- be better if it throws an exception. readInt16StreamStrict :: FilePath -> IO [Int16] -- | Write a little endian 16 bit integer stream via String data and -- writeFile. writeLEInt16Stream :: FilePath -> [Int16] -> IO () -- | The end of the list is undefined, if the file has odd length. It would -- be better if it throws an exception. readLEInt16Stream :: FilePath -> IO [Int16] putInt16Stream :: Handle -> [Int16] -> IO () putInt16StreamChunky :: Handle -> [Int16] -> IO () intToTwoLEChars :: Int -> [Char] twoLECharsToInt :: Char -> Char -> Int module Synthesizer.Plain.File -- | See write. render :: (Storable int, C int, C int, Bounded int, C a, C v) => Put int -> FilePath -> a -> (a -> [v]) -> IO ExitCode renderToInt16 :: (C a, C v) => FilePath -> a -> (a -> [v]) -> IO ExitCode renderMonoToInt16 :: C a => FilePath -> a -> (a -> [a]) -> IO ExitCode renderStereoToInt16 :: C a => FilePath -> a -> (a -> [(a, a)]) -> IO ExitCode -- | The output format is determined by SoX by the file name extension. The -- sample precision is determined by the provided Put function. -- -- Example: -- --
--   import qualified Synthesizer.Plain.Builder as Builder
--   
--   write (Builder.put :: Builder.Put Int16) "test.aiff" 44100 sound
--   
write :: (Storable int, C int, C int, Bounded int, C a, C v) => Put int -> FilePath -> a -> [v] -> IO ExitCode writeToInt16 :: (C a, C v) => FilePath -> a -> [v] -> IO ExitCode writeMonoToInt16 :: C a => FilePath -> a -> [a] -> IO ExitCode writeStereoToInt16 :: C a => FilePath -> a -> [(a, a)] -> IO ExitCode writeRaw :: (C a, C v, Storable v) => T -> FilePath -> a -> [v] -> IO ExitCode -- | You hardly need this routine since you can use a filename with -- .mp3 or .ogg extension for writeRaw and SoX -- will do the corresponding compression for you. writeRawCompressed :: (C a, C v, Storable v) => T -> FilePath -> a -> [v] -> IO ExitCode -- | Deprecated: If you want to generate AIFF, then just write to files -- with .aiff filename extension. If you want to convert files to AIFF, -- use Sound.Sox.Convert. rawToAIFF :: C a => FilePath -> T -> a -> Int -> IO ExitCode compress :: FilePath -> IO ExitCode -- | Deprecated: Use readMonoFromInt16 instead readAIFFMono :: C a => FilePath -> IO [a] -- | I suspect we cannot handle file closing properly. readMonoFromInt16 :: C a => FilePath -> IO [a] -- | Deprecated: This function will no longer be exported getInt16List :: Get [Int16] module Synthesizer.Plain.LorenzAttractor computeDerivatives :: C y => (y, y, y) -> (y, y, y) -> (y, y, y) explicitEuler :: C a v => a -> (v -> v) -> v -> [v] equilibrium :: (Double, Double, Double) example0 :: [(Double, Double, Double)] example :: [(Double, Double, Double)] -- | Support for stateful modifiers like controlled filters. This is -- similar to Synthesizer.Causal.Process but we cannot replace the -- Modifier structure by the Causal structure because the Modifier -- structure exhibits the state which allows stacking of modifiers using -- an efficient storage for the stacked state. More precisely, because -- Modifiers exhibits the type of the state, we can ensure that the state -- type of several modifiers is equal and thus the individual states can -- be stored in an array or a StorableVector. module Synthesizer.Plain.Modifier type T a = [a] data Simple s ctrl a b Simple :: s -> (ctrl -> a -> State s b) -> Simple s ctrl a b [init] :: Simple s ctrl a b -> s [step] :: Simple s ctrl a b -> ctrl -> a -> State s b -- | modif is a process controlled by values of type c with an internal -- state of type s, it converts an input value of type a into an output -- value of type b while turning into a new state -- -- ToDo: Shall finite signals be padded with zeros? static :: Simple s ctrl a b -> ctrl -> T a -> T b -- | Here the control may vary over the time. modulated :: Simple s ctrl a b -> T ctrl -> T a -> T b data Initialized s init ctrl a b Initialized :: (init -> s) -> (ctrl -> a -> State s b) -> Initialized s init ctrl a b [initInit] :: Initialized s init ctrl a b -> init -> s [initStep] :: Initialized s init ctrl a b -> ctrl -> a -> State s b initialize :: Initialized s init ctrl a b -> init -> Simple s ctrl a b staticInit :: Initialized s init ctrl a b -> init -> ctrl -> T a -> T b -- | Here the control may vary over the time. modulatedInit :: Initialized s init ctrl a b -> init -> T ctrl -> T a -> T b -- | The number of stacked state monads depends on the size of the list of -- state values. This is like a dynamically nested StateT. stackStatesR :: (a -> State s a) -> a -> State [s] a stackStatesL :: (a -> State s a) -> a -> State [s] a stackStatesStorableR :: Storable s => (a -> State s a) -> a -> State (Vector s) a stackStatesStorableL :: Storable s => (a -> State s a) -> a -> State (Vector s) a stackStatesStorableVaryL :: (Storable s, Storable c) => (c -> a -> State s a) -> Vector c -> a -> State (Vector s) a module Synthesizer.Plain.Play -- | See write. render :: (Storable int, C int, C int, Bounded int, C a, C v) => Put int -> a -> (a -> [v]) -> IO ExitCode renderToInt16 :: (C a, C v) => a -> (a -> [v]) -> IO ExitCode renderMonoToInt16 :: C a => a -> (a -> [a]) -> IO ExitCode renderStereoToInt16 :: C a => a -> (a -> [(a, a)]) -> IO ExitCode -- | See write. auto :: (Storable int, C int, C int, Bounded int, C a, C v) => Put int -> a -> [v] -> IO ExitCode toInt16 :: (C a, C v) => a -> [v] -> IO ExitCode monoToInt16 :: C a => a -> [a] -> IO ExitCode stereoToInt16 :: C a => a -> [(a, a)] -> IO ExitCode raw :: (C a, C v, Storable v) => T -> a -> [v] -> IO ExitCode exampleMono :: IO ExitCode exampleStereo :: IO ExitCode module Synthesizer.Plain.Signal type T = [] type Modifier s ctrl a b = Simple s ctrl a b -- | modif is a process controlled by values of type c with an internal -- state of type s, it converts an input value of type a into an output -- value of type b while turning into a new state -- -- ToDo: Shall finite signals be padded with zeros? modifyStatic :: Modifier s ctrl a b -> ctrl -> T a -> T b -- | Here the control may vary over the time. modifyModulated :: Modifier s ctrl a b -> T ctrl -> T a -> T b type ModifierInit s init ctrl a b = Initialized s init ctrl a b modifierInitialize :: ModifierInit s init ctrl a b -> init -> Modifier s ctrl a b modifyStaticInit :: ModifierInit s init ctrl a b -> init -> ctrl -> T a -> T b -- | Here the control may vary over the time. modifyModulatedInit :: ModifierInit s init ctrl a b -> init -> T ctrl -> T a -> T b unfoldR :: (acc -> Maybe (y, acc)) -> acc -> (acc, T y) reduceL :: (x -> acc -> Maybe acc) -> acc -> T x -> acc mapAccumL :: (x -> acc -> Maybe (y, acc)) -> acc -> T x -> (acc, T y) crochetL :: (x -> acc -> Maybe (y, acc)) -> acc -> T x -> T y -- | Feed back signal into signal processor, and apply a delay by one -- value. fix1 is a kind of generate. fix1 :: y -> (T y -> T y) -> T y -- | dropMarginRem n m xs drops at most the first m -- elements of xs and ensures that xs still contains -- n elements. Additionally returns the number of elements that -- could not be dropped due to the margin constraint. That is -- dropMarginRem n m xs == (k,ys) implies length xs - m == -- length ys - k. Requires length xs >= n. dropMarginRem :: Int -> Int -> T a -> (Int, T a) dropMargin :: Int -> Int -> T a -> T a -- | Test whether a list has at least n elements. lengthAtLeast :: Int -> T a -> Bool -- | Can be implemented more efficiently than just by zipWith and -- tails for other data structures. zipWithTails :: (y0 -> T y1 -> y2) -> T y0 -> T y1 -> T y2 zipWithRest :: (y0 -> y0 -> y1) -> T y0 -> T y0 -> (T y1, (Bool, T y0)) zipWithRestRec :: (y0 -> y0 -> y1) -> T y0 -> T y0 -> (T y1, (Bool, T y0)) zipWithAppend :: (y -> y -> y) -> T y -> T y -> T y -- | Tone generators with measures for band-limitation. -- -- They are not exactly band-limiting because this would cause infinite -- lag. Instead we use only cubic interpolation polynomials. This still -- incurs a small lag. -- -- https://youtu.be/lpM4Tawq-XU module Synthesizer.Plain.Oscillator.BandLimited -- | impulse train with static frequency staticImpulses :: C a => a -> a -> T a -- | impulse train with modulated frequency freqModImpulses :: C a => a -> T a -> T a -- | Noise and random processes. module Synthesizer.Plain.Noise -- | Deterministic white noise, uniformly distributed between -1 and 1. -- That is, variance is 1/3. white :: (C y, Random y) => T y whiteGen :: (C y, Random y, RandomGen g) => g -> T y -- | Approximates normal distribution with variance 1 by a quadratic -- B-spline distribution. whiteQuadraticBSplineGen :: (C y, Random y, RandomGen g) => g -> T y randomPeeks :: (C y, Random y) => T y -> T Bool randomPeeksGen :: (C y, Random y, RandomGen g) => g -> T y -> T Bool -- | Filter operators from calculus module Synthesizer.Plain.Filter.Recursive.Integration -- | Integrate with initial value zero. However the first emitted value is -- the value of the input signal. It maintains the length of the signal. run :: C v => T v -> T v -- | Integrate with initial condition. First emitted value is the initial -- condition. The signal becomes one element longer. runInit :: C v => v -> T v -> T v -- | http://en.wikipedia.org/wiki/Particle_displacement module Synthesizer.Plain.Displacement -- | Mix two signals. In opposition to zipWith the result has the -- length of the longer signal. mix :: C v => T v -> T v -> T v -- | Mix an arbitrary number of signals. mixMulti :: C v => [T v] -> T v -- | Add a number to all of the signal values. This is useful for adjusting -- the center of a modulation. raise :: C v => v -> T v -> T v -- | In Synthesizer.Basic.Distortion you find a collection of -- appropriate distortion functions. distort :: (c -> a -> a) -> T c -> T a -> T a module Synthesizer.Plain.Cut -- | Take signal until it falls short of a certain amplitude for a given -- time. takeUntilPause :: C a => a -> Int -> T a -> T a -- | Take values until the predicate p holds for n successive values. The -- list is truncated at the beginning of the interval of matching values. takeUntilInterval :: (a -> Bool) -> Int -> T a -> T a selectBool :: (T a, T a) -> T Bool -> T a select :: Ix i => Array i (T a) -> T i -> T a -- | Given a list of signals with time stamps, mix them into one signal as -- they occur in time. Ideally for composing music. -- -- Cf. series arrange :: C v => T Int (T v) -> T v module Synthesizer.Plain.Control constant :: y -> T y linear :: C y => y -> y -> T y -- | Minimize rounding errors by reducing number of operations per element -- to a logarithmuc number. linearMultiscale :: C y => y -> y -> T y -- | Linear curve starting at zero. linearMultiscaleNeutral :: C y => y -> T y -- | As stable as the addition of time values. linearStable :: C y => y -> y -> T y -- | It computes the same like linear but in a numerically more -- stable manner, namely using a subdivision scheme. The division needed -- is a division by two. -- --
--   0       4       8
--   0   2   4   6   8
--   0 1 2 3 4 5 6 7 8
--   
linearMean :: C y => y -> y -> T y -- | 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. line :: C y => Int -> (y, y) -> T y exponential :: C y => y -> y -> T y exponentialMultiscale :: C y => y -> y -> T y exponentialStable :: C y => y -> y -> T y exponentialMultiscaleNeutral :: C y => y -> T y exponential2 :: C y => y -> y -> T y exponential2Multiscale :: C y => y -> y -> T y exponential2Stable :: C y => y -> y -> T y exponential2MultiscaleNeutral :: C y => y -> T y exponentialFromTo :: C y => y -> y -> y -> T y exponentialFromToMultiscale :: C y => y -> y -> y -> T y -- | 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. vectorExponential :: (C y, C y v) => y -> v -> T v vectorExponential2 :: (C y, C y v) => y -> v -> T v cosine :: C y => y -> y -> T y cosineMultiscale :: C y => y -> y -> T y cosineSubdiv :: C y => y -> y -> T y cosineStable :: C y => y -> y -> T y cubicHermite :: C y => (y, (y, y)) -> (y, (y, y)) -> T y cubicHermiteStable :: C y => (y, (y, y)) -> (y, (y, y)) -> T y curveMultiscale :: (y -> y -> y) -> y -> y -> T y curveMultiscaleNeutral :: (y -> y -> y) -> y -> y -> T 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
--   
cubicFunc :: C y => (y, (y, y)) -> (y, (y, y)) -> y -> y cosineWithSlope :: C y => (y -> y -> signal) -> y -> y -> signal module Synthesizer.Plain.Filter.NonRecursive amplify :: C a => a -> T a -> T a amplifyVector :: C a v => a -> T v -> T v binomial :: (C a, C a, C a v) => a -> a -> T v -> T v binomial1 :: C v => T v -> T v delay :: C y => Int -> T y -> T y delayPad :: y -> Int -> T y -> T y -- | Forward difference quotient. Shortens the signal by one. Inverts -- run in the sense that differentiate (zero : integrate x) == -- x. The signal is shifted by a half time unit. differentiate :: C v => T v -> T v -- | Second derivative. It is differentiate2 == differentiate . -- differentiate but differentiate2 should be faster. differentiate2 :: C v => T v -> T v -- | Central difference quotient. Shortens the signal by two elements, and -- shifts the signal by one element. (Which can be fixed by prepending an -- appropriate value.) For linear functions this will yield essentially -- the same result as differentiate. You obtain the result of -- differentiateCenter if you smooth the one of -- differentiate by averaging pairs of adjacent values. -- -- ToDo: Vector variant differentiateCenter :: C v => T v -> T v downsample2 :: T a -> T a envelope :: C a => T a -> T a -> T a envelopeVector :: C a v => T a -> T v -> T v fadeInOut :: C a => Int -> Int -> Int -> T a -> T a fadeInOutAlt :: C a => Int -> Int -> Int -> T a -> T a -- | eps is the threshold relatively to the maximum. That is, if -- the gaussian falls below eps * gaussian 0, then the function -- truncated. gaussian :: (C a, C a, C a v) => a -> a -> a -> T v -> T v -- | Unmodulated non-recursive filter generic :: C a v => T a -> T v -> T v -- | Unmodulated non-recursive filter Output has same length as the input. -- -- It is elegant but leaks memory. genericAlt :: C a v => T a -> T v -> T v minRange :: Ord v => T v -> (Int, Int) -> v -- | The first argument is the amplification. The main reason to introduce -- it, was to have only a Module constraint instead of Field. This way we -- can also filter stereo signals. -- -- A control value n corresponds to filter window size -- 2*n+1. movingAverageModulatedPyramid :: (C a, C a v) => a -> Int -> Int -> T Int -> T v -> T v -- | Compute the sum of the values from index l to (r-1). (I.e. somehow a -- right open interval.) This can be used for implementation of a moving -- average filter. However, its counterpart sumRangeFromPyramid is -- much faster for large windows. sumRange :: C v => T v -> (Int, Int) -> v -- | This function should be much faster than sumRange but slower -- than the recursively implemented movingAverage. However in -- contrast to movingAverage it should not suffer from -- cancelation. sumRangeFromPyramid :: C v => [T v] -> (Int, Int) -> v -- | Moving (uniformly weighted) average in the most trivial form. This is -- very slow and needs about n * length x operations. sums :: C v => Int -> T v -> T v sumsDownsample2 :: C v => T v -> T v sumsPosModulated :: C v => T (Int, Int) -> T v -> T v -- | Moving average, where window bounds must be always non-negative. -- -- The laziness granularity is 2^height. sumsPosModulatedPyramid :: C v => Int -> T (Int, Int) -> T v -> T v sumsPyramid :: C v => Int -> T v -> T v propGeneric :: (C a v, Eq v) => T a -> T v -> Bool sumRangeFromPyramidFoldr :: C v => [T v] -> (Int, Int) -> v sumRangeFromPyramidRec :: C v => [T v] -> (Int, Int) -> v getRangeFromPyramid :: [T v] -> (Int, Int) -> [v] pyramid :: C v => T v -> [T v] module Synthesizer.Plain.Filter.Recursive.MovingAverage -- | Like sums but in a recursive form. This needs only linear time -- (independent of the window size) but may accumulate rounding errors. -- --
--   ys = xs * (1,0,0,0,-1) / (1,-1)
--   ys * (1,-1) = xs * (1,0,0,0,-1)
--   ys = xs * (1,0,0,0,-1) + ys * (0,1)
--   
sumsStaticInt :: C v => Int -> T v -> T v modulatedFrac :: (C a, C a v) => Int -> T a -> T v -> T v module Synthesizer.Plain.Analysis -- | Volume based on Manhattan norm. volumeMaximum :: C y => T y -> y -- | Volume based on Energy norm. volumeEuclidean :: C y => T y -> y volumeEuclideanSqr :: C y => T y -> y -- | Volume based on Sum norm. volumeSum :: (C y, C y) => T y -> y -- | Volume based on Manhattan norm. volumeVectorMaximum :: (C y yv, Ord y) => T yv -> y -- | Volume based on Energy norm. volumeVectorEuclidean :: (C y, C y yv) => T yv -> y volumeVectorEuclideanSqr :: (C y, Sqr y yv) => T yv -> y -- | Volume based on Sum norm. volumeVectorSum :: (C y yv, C y) => T yv -> y -- | Compute minimum and maximum value of the stream the efficient way. -- Input list must be non-empty and finite. bounds :: Ord y => T T y -> (y, y) -- | Input list must be finite. List is scanned twice, but counting may be -- faster. histogramDiscreteArray :: T T Int -> (Int, T Int) -- | Input list must be finite. If the input signal is empty, the offset is -- undefined. List is scanned twice, but counting may be faster. -- The sum of all histogram values is one less than the length of the -- signal. histogramLinearArray :: C y => T T y -> (Int, T y) -- | Input list must be finite. If the input signal is empty, the offset is -- undefined. List is scanned once, counting may be slower. histogramDiscreteIntMap :: T T Int -> (Int, T Int) histogramLinearIntMap :: C y => T T y -> (Int, T y) histogramIntMap :: C y => y -> T T y -> (Int, T Int) -- | Requires finite length. This is identical to the arithmetic mean. directCurrentOffset :: C y => T y -> y scalarProduct :: C y => T y -> T y -> y -- | directCurrentOffset must be non-zero. centroid :: C y => T y -> y centroidAlt :: C y => T y -> y firstMoment :: C y => T y -> y average :: C y => T y -> y rectify :: C y => T y -> T y -- | Detects zeros (sign changes) in a signal. This can be used as a simple -- measure of the portion of high frequencies or noise in the signal. It -- ca be used as voiced/unvoiced detector in a vocoder. -- -- zeros x !! n is True if and only if (x !! n -- >= 0) /= (x !! (n+1) >= 0). The result will be one value -- shorter than the input. zeros :: (Ord y, C y) => T y -> T Bool data BinaryLevel Low :: BinaryLevel High :: BinaryLevel binaryLevelFromBool :: Bool -> BinaryLevel binaryLevelToNumber :: C a => BinaryLevel -> a -- | Detect thresholds with a hysteresis. flipFlopHysteresis :: Ord y => (y, y) -> BinaryLevel -> T y -> T BinaryLevel flipFlopHysteresisStep :: Ord a => (a, a) -> BinaryLevel -> a -> BinaryLevel -- | Almost naive implementation of the chirp transform, a generalization -- of the Fourier transform. -- -- More sophisticated algorithms like Rader, Cooley-Tukey, Winograd, -- Prime-Factor may follow. chirpTransform :: C y => y -> T y -> T y binarySign :: (Ord y, C y) => T y -> T BinaryLevel -- | A kind of discretization for signals with sample values between -1 and -- 1. If you smooth the resulting signal (after you transformed with 'map -- binaryLevelToNumber'), you should obtain an approximation to the input -- signal. deltaSigmaModulation :: C y => T y -> T BinaryLevel -- | A kind of discretization for signals with sample values between 0 and -- a threshold. We accumulate input values and emit a threshold value -- whenever the accumulator exceeds the threshold. This is intended for -- generating clicks from input noise. -- -- See also deltaSigmaModulation. deltaSigmaModulationPositive :: C y => y -> T y -> T y spread :: C y => (y, y) -> [(Int, y)] instance GHC.Enum.Enum Synthesizer.Plain.Analysis.BinaryLevel instance GHC.Show.Show Synthesizer.Plain.Analysis.BinaryLevel instance GHC.Classes.Eq Synthesizer.Plain.Analysis.BinaryLevel module Synthesizer.Plain.Filter.LinearPredictive -- | Determine optimal filter coefficients and residue by adaptive -- approximation. The number of initial filter coefficients is used as -- filter order. approxCoefficients :: C a => a -> [a] -> [a] -> [(a, [a])] -- | Very simple random number generator which should be fast and should -- suffice for generating just noise. -- http://www.softpanorama.org/Algorithms/random_generators.shtml module Synthesizer.RandomKnuth data T cons :: Int -> T instance GHC.Show.Show Synthesizer.RandomKnuth.T instance System.Random.Internal.RandomGen Synthesizer.RandomKnuth.T module Synthesizer.Storable.Repair -- | Usage: removeClicks slopeDistance maxSpikeWidth minSpikeDistance -- thresholdUp thresholdDown -- -- slopeDistance is the distance of samples in which we analyse -- differences. The smoother the spike slope the larger -- slopeDistance must be. -- -- slopeDistance should be smaller than the _minimal_ spike -- width. maxSpikeWidth should be smaller than the minimal spike -- distance. Spike distance is measured from one spike beginning to the -- next one. -- -- thresholdUp is the minimal difference of two samples at -- slopeDistance that are to be considered an upward jump. -- thresholdDown is for downward jumps. If a threshold is -- Nothing then jumps in this direction are ignored. You should -- only use this if you are very sure that spikes with the according sign -- do not occur. Otherwise the algorithm will be confused by the jump in -- reverse direction at the end of the spike. -- -- Example: removeClicks 1 5 20 (Just 0.1) (Just 0.1). -- -- The algorithm works as follows: Chop the signal at jumps. Then begin -- at a certain distance behind the jump and search backwards for the -- matching jump at the end of the spike. If the borders of a spike are -- found this way, then they are connected by a linear ramp. removeClicks :: (Storable a, C a) => Int -> Int -> Int -> Maybe a -> Maybe a -> Vector a -> Vector a -- | Chunky signal stream build on StorableVector. -- -- Hints for fusion: - Higher order functions should always be inlined in -- the end in order to turn them into machine loops instead of calling a -- function in an inner loop. module Synthesizer.Storable.Signal type T = Vector hPut :: Storable a => Handle -> Vector a -> IO () data () => ChunkSize chunkSize :: Int -> ChunkSize defaultChunkSize :: ChunkSize scanL :: (Storable a, Storable b) => (a -> b -> a) -> a -> T b -> T a map :: (Storable x, Storable y) => (x -> y) -> Vector x -> Vector y iterate :: Storable a => ChunkSize -> (a -> a) -> a -> Vector a -- | Generates laziness breaks wherever one of the input signals has a -- chunk boundary. zipWith :: (Storable a, Storable b, Storable c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c append :: Storable a => Vector a -> Vector a -> Vector a infixr 5 `append` concat :: Storable a => [Vector a] -> Vector a span :: Storable a => (a -> Bool) -> Vector a -> (Vector a, Vector a) splitAt :: Storable a => Int -> Vector a -> (Vector a, Vector a) viewL :: Storable a => Vector a -> Maybe (a, Vector a) viewR :: Storable a => Vector a -> Maybe (Vector a, a) switchL :: Storable a => b -> (a -> Vector a -> b) -> Vector a -> b unfoldr :: Storable b => ChunkSize -> (a -> Maybe (b, a)) -> a -> Vector b reverse :: Storable a => Vector a -> Vector a crochetL :: (Storable x, Storable y) => (x -> acc -> Maybe (y, acc)) -> acc -> Vector x -> Vector y writeFile :: Storable a => FilePath -> Vector a -> IO () -- | This implementation generates laziness breaks whereever one of the -- original sequences has laziness breaks. It should be commutative in -- this respect. -- -- It is more efficient than mixSize since it appends the rest of -- the longer signal without copying. mix :: (C x, Storable x) => T x -> T x -> T x -- | Mix while maintaining the pattern of the second operand. This is -- closer to the behavior of Vector.zipWithLastPattern. mixSndPattern :: (C x, Storable x) => T x -> T x -> T x mixSize :: (C x, Storable x) => ChunkSize -> T x -> T x -> T x splitAtPad :: (C x, Storable x) => ChunkSize -> Int -> T x -> (T x, T x) null :: Storable a => Vector a -> Bool fromChunks :: Storable a => [Vector a] -> Vector a foldr :: Storable b => (b -> a -> a) -> a -> Vector b -> a delay :: Storable y => ChunkSize -> y -> Int -> T y -> T y delayLoop :: Storable y => (T y -> T y) -> T y -> T y delayLoopOverlap :: (C y, Storable y) => Int -> (T y -> T y) -> T y -> T y empty :: Storable a => Vector a cons :: Storable a => a -> Vector a -> Vector a replicate :: Storable a => ChunkSize -> Int -> a -> Vector a repeat :: Storable a => ChunkSize -> a -> Vector a drop :: Storable a => Int -> Vector a -> Vector a take :: Storable a => Int -> Vector a -> Vector a takeCrochet :: Storable a => Int -> T a -> T a fromList :: Storable a => ChunkSize -> [a] -> T a zipWithRest :: (Storable c, Storable x) => (x -> x -> c) -> T x -> T x -> (Vector c, (Bool, T x)) zipWithAppend :: Storable x => (x -> x -> x) -> T x -> T x -> T x switchR :: Storable a => b -> (Vector a -> a -> b) -> Vector a -> b toList :: Storable a => T a -> [a] chunks :: Vector a -> [Vector a] genericLength :: C i => T x -> i module Synthesizer.Storable.Play -- | Latency is high using Sox - We can achieve better results using ALSA's -- sound output! See synthesizer-alsa package. monoToInt16 :: (Storable a, C a) => a -> T a -> IO ExitCode stereoToInt16 :: (Storable a, C a) => a -> T (T a) -> IO ExitCode -- | Tone generators module Synthesizer.Storable.Oscillator -- | 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 freqToPhase :: (C a, Storable a) => T a -> T a -> T (T a) -- | oscillator with constant frequency static :: (C a, Storable a, Storable b) => ChunkSize -> T a b -> T a -> a -> T b -- | oscillator with modulated phase phaseMod :: (C a, Storable a, Storable b) => ChunkSize -> T a b -> a -> T a -> T b -- | oscillator with modulated shape shapeMod :: (C a, Storable a, Storable b, Storable c) => ChunkSize -> (c -> T a b) -> T a -> a -> T c -> T b -- | oscillator with modulated frequency freqMod :: (C a, Storable a, Storable b) => ChunkSize -> T a b -> T a -> T a -> T b -- | oscillator with both phase and frequency modulation phaseFreqMod :: (C a, Storable a, Storable b) => ChunkSize -> T a b -> T a -> T a -> T b -- | oscillator with both shape and frequency modulation shapeFreqMod :: (C a, Storable a, Storable b, Storable c) => ChunkSize -> (c -> T a b) -> T a -> T c -> T a -> T b -- | sine oscillator with static frequency staticSine :: (C a, C a, Storable a) => ChunkSize -> T a -> a -> T a -- | sine oscillator with modulated frequency freqModSine :: (C a, C a, Storable a) => ChunkSize -> T a -> T a -> T a -- | sine oscillator with modulated phase, useful for FM synthesis phaseModSine :: (C a, C a, Storable a) => ChunkSize -> a -> T a -> T a -- | saw tooth oscillator with modulated frequency staticSaw :: (C a, Storable a) => ChunkSize -> T a -> a -> T a -- | saw tooth oscillator with modulated frequency freqModSaw :: (C a, Storable a) => ChunkSize -> T a -> T a -> T a module Synthesizer.Storable.Generate -- | clickTrack silenceChunkSize barBeepFreq beatBeepFreq beepDur -- beatsPerBar beatPeriod generates click track for one bar. You may -- cycle it infinitely or replicate it as often as you want. clickTrack :: (C a, C a, Storable a) => ChunkSize -> a -> a -> Int -> Int -> Int -> T a clickTrackExample :: T Float module Synthesizer.Storable.Cut arrange :: (Storable v, C v) => ChunkSize -> T Int (T v) -> T v addChunkToBuffer :: (Storable a, C a) => Vector s a -> Int -> Vector a -> ST s () -- | The result is a Lazy StorableVector with chunks of the given size. arrangeEquidist :: (Storable v, C v) => ChunkSize -> T Int (T v) -> T v -- | Chunk sizes are adapted to the time differences. Explicit ChunkSize -- parameter is only required for zero padding. Since no ST monad is -- needed, this can be generalized to Generic.Signal.Transform class. arrangeAdaptive :: (Storable v, C v) => ChunkSize -> T Int (T v) -> T v -- | This function also uses the time differences as chunk sizes, but may -- occasionally use smaller chunk sizes due to the chunk structure of an -- input signal until the next signal starts. arrangeList :: (Storable v, C v) => ChunkSize -> T Int (T v) -> T v -- | Better name for the module is certainly Synthesizer.Generator.Signal module Synthesizer.State.Signal -- | Cf. StreamFusion Data.Stream data T a Cons :: !StateT s Maybe a -> !s -> T a -- | It is a common pattern to use switchL or viewL in a -- loop in order to traverse a signal. However this needs repeated -- packing and unpacking of the viewL function and the state. It -- seems that GHC is not clever enough to detect, that the view -- function does not change. With runViewL you can unpack a stream -- once and use an efficient viewL in the loop. runViewL :: T y -> (forall s. (s -> Maybe (y, s)) -> s -> x) -> x runSwitchL :: T y -> (forall s. (forall z. z -> (y -> s -> z) -> s -> z) -> s -> x) -> x generate :: (acc -> Maybe (y, acc)) -> acc -> T y unfoldR :: (acc -> Maybe (y, acc)) -> acc -> T y generateInfinite :: (acc -> (y, acc)) -> acc -> T y fromList :: [y] -> T y toList :: T y -> [y] fromStorableSignal :: Storable a => T a -> T a fromStrictStorableSignal :: Storable a => Vector a -> T a toStorableSignal :: Storable a => ChunkSize -> T a -> T a toStrictStorableSignal :: Storable a => Int -> T a -> Vector a toStorableSignalVary :: Storable a => LazySize -> T a -> T a fromPiecewiseConstant :: (C time, Integral time) => T time a -> T a iterate :: (a -> a) -> a -> T a iterateAssociative :: (a -> a -> a) -> a -> T a repeat :: a -> T a crochetL :: (x -> acc -> Maybe (y, acc)) -> acc -> T x -> T y scanL :: (acc -> x -> acc) -> acc -> T x -> T acc -- | input and output have equal length, that's better for fusion scanLClip :: (acc -> x -> acc) -> acc -> T x -> T acc map :: (a -> b) -> T a -> T b -- | This function will recompute the input lists and is thus probably not -- what you want. If you want to avoid recomputation please consider -- Causal.Process. unzip :: T (a, b) -> (T a, T b) unzip3 :: T (a, b, c) -> (T a, T b, T c) -- | This is a fusion friendly implementation of delay. However, in order -- to be a crochetL the output has the same length as the input, -- that is, the last element is removed - at least for finite input. delay1 :: a -> T a -> T a delay :: y -> Int -> T y -> T y take :: Int -> T a -> T a takeWhile :: (a -> Bool) -> T a -> T a replicate :: Int -> a -> T a zipWith :: (a -> b -> c) -> T a -> T b -> T c zipWithStorable :: (Storable b, Storable c) => (a -> b -> c) -> T a -> T b -> T c zipWith3 :: (a -> b -> c -> d) -> T a -> T b -> T c -> T d zipWith4 :: (a -> b -> c -> d -> e) -> T a -> T b -> T c -> T d -> T e zip :: T a -> T b -> T (a, b) zip3 :: T a -> T b -> T c -> T (a, b, c) zip4 :: T a -> T b -> T c -> T d -> T (a, b, c, d) foldL' :: (x -> acc -> acc) -> acc -> T x -> acc foldL :: (acc -> x -> acc) -> acc -> T x -> acc foldL1 :: (x -> x -> x) -> T x -> x length :: T a -> Int equal :: Eq a => T a -> T a -> Bool foldR :: (x -> acc -> acc) -> acc -> T x -> acc null :: T a -> Bool empty :: T a singleton :: a -> T a -- | This is expensive and should not be used to construct lists -- iteratively! cons :: a -> T a -> T a viewL :: T a -> Maybe (a, T a) viewR :: Storable a => T a -> Maybe (T a, a) viewRSize :: Storable a => ChunkSize -> T a -> Maybe (T a, a) switchL :: b -> (a -> T a -> b) -> T a -> b switchR :: Storable a => b -> (T a -> a -> b) -> T a -> b -- | This implementation requires that the input generator has to check -- repeatedly whether it is finished. extendConstant :: T a -> T a drop :: Int -> T a -> T a -- | This implementation expects that looking ahead is cheap. dropMarginRem :: Int -> Int -> T a -> (Int, T a) dropMargin :: Int -> Int -> T a -> T a dropMatch :: T b -> T a -> T a index :: Int -> T a -> a splitAt :: Storable a => Int -> T a -> (T a, T a) splitAtSize :: Storable a => ChunkSize -> Int -> T a -> (T a, T a) dropWhile :: (a -> Bool) -> T a -> T a span :: Storable a => (a -> Bool) -> T a -> (T a, T a) spanSize :: Storable a => ChunkSize -> (a -> Bool) -> T a -> (T a, T a) cycle :: T a -> T a mix :: C a => T a -> T a -> T a sub :: C a => T a -> T a -> T a neg :: C a => T a -> T a append :: T a -> T a -> T a infixr 5 `append` appendStored :: Storable a => T a -> T a -> T a appendStoredSize :: Storable a => ChunkSize -> T a -> T a -> T a -- | certainly inefficient because of frequent list deconstruction concat :: [T a] -> T a concatStored :: Storable a => [T a] -> T a concatStoredSize :: Storable a => ChunkSize -> [T a] -> T a liftA2 :: (a -> b -> c) -> T a -> T b -> T c reverse :: T a -> T a reverseStored :: Storable a => T a -> T a reverseStoredSize :: Storable a => ChunkSize -> T a -> T a sum :: C a => T a -> a maximum :: Ord a => T a -> a init :: T y -> T y sliceVert :: Int -> T y -> [T y] -- | Deprecated: use mapAdjacent zapWith :: (a -> a -> b) -> T a -> T b -- | Deprecated: use mapAdjacent zapWithAlt :: (a -> a -> b) -> T a -> T b mapAdjacent :: (a -> a -> b) -> T a -> T b modifyStatic :: Simple s ctrl a b -> ctrl -> T a -> T b -- | Here the control may vary over the time. modifyModulated :: Simple s ctrl a b -> T ctrl -> T a -> T b linearComb :: C t y => T t -> T y -> y mapTails :: (T y0 -> y1) -> T y0 -> T y1 -- | only non-empty suffixes are processed zipWithTails :: (y0 -> T y1 -> y2) -> T y0 -> T y1 -> T y2 -- | in contrast to zipWithTails it also generates the empty suffix -- (once) zipWithTails1 :: (y0 -> T y1 -> y2) -> T y0 -> T y1 -> T y2 -- | in contrast to zipWithTails it appends infinitely many empty -- suffixes zipWithTailsInf :: (y0 -> T y1 -> y2) -> T y0 -> T y1 -> T y2 zipWithAppend :: (y -> y -> y) -> T y -> T y -> T y zipStep :: (s -> Maybe (a, s)) -> (t -> Maybe (a, t)) -> (a -> a -> a) -> (s, t) -> Maybe (a, (s, t)) delayLoop :: (T y -> T y) -> T y -> T y delayLoopOverlap :: C y => Int -> (T y -> T y) -> T y -> T y sequence_ :: Monad m => T (m a) -> m () mapM_ :: Monad m => (a -> m ()) -> T a -> m () -- | Counterpart to mconcat. fold :: Monoid m => T m -> m -- | Deprecated: Use foldMap instead. monoidConcat :: Monoid m => T m -> m foldMap :: Monoid m => (a -> m) -> T a -> m -- | Deprecated: Use foldMap instead. monoidConcatMap :: Monoid m => (a -> m) -> T a -> m catMaybes :: T (Maybe a) -> T a flattenPairs :: T (a, a) -> T a interleave :: T y -> T y -> T y interleaveAlt :: T y -> T y -> T y instance GHC.Show.Show y => GHC.Show.Show (Synthesizer.State.Signal.T y) instance GHC.Classes.Eq y => GHC.Classes.Eq (Synthesizer.State.Signal.T y) instance Synthesizer.Format.C Synthesizer.State.Signal.T instance GHC.Base.Functor Synthesizer.State.Signal.T instance Data.Foldable.Foldable Synthesizer.State.Signal.T instance GHC.Base.Applicative Synthesizer.State.Signal.T instance GHC.Base.Monad Synthesizer.State.Signal.T instance Algebra.Additive.C y => Algebra.Additive.C (Synthesizer.State.Signal.T y) instance Algebra.Module.C y yv => Algebra.Module.C y (Synthesizer.State.Signal.T yv) instance GHC.Base.Semigroup (Synthesizer.State.Signal.T y) instance GHC.Base.Monoid (Synthesizer.State.Signal.T y) -- | Noise and random processes. This uses a fast reimplementation of -- randomR since the standard function seems not to be inlined (at -- least in GHC-6.8.2). module Synthesizer.State.NoiseCustom -- | Deterministic white noise, uniformly distributed between -1 and 1. -- That is, variance is 1/3. white :: (C y, Random y) => T y whiteGen :: (C y, Random y, RandomGen g) => g -> T y -- | Approximates normal distribution with variance 1 by a quadratic -- B-spline distribution. whiteQuadraticBSplineGen :: (C y, Random y, RandomGen g) => g -> T y randomPeeks :: (C y, Random y) => T y -> T Bool randomPeeksGen :: (C y, Random y, RandomGen g) => g -> T y -> T Bool randomRs :: (C y, Random y, RandomGen g) => (y, y) -> g -> T y randomR :: (RandomGen g, C y) => (y, y) -> g -> (y, g) -- | Noise and random processes. module Synthesizer.State.Noise -- | Deterministic white noise, uniformly distributed between -1 and 1. -- That is, variance is 1/3. white :: (C y, Random y) => T y whiteGen :: (C y, Random y, RandomGen g) => g -> T y -- | Approximates normal distribution with variance 1 by a quadratic -- B-spline distribution. whiteQuadraticBSplineGen :: (C y, Random y, RandomGen g) => g -> T y randomPeeks :: (C y, Random y) => T y -> T Bool randomPeeksGen :: (C y, Random y, RandomGen g) => g -> T y -> T Bool randomRs :: (C y, Random y, RandomGen g) => (y, y) -> g -> T y module Synthesizer.State.Displacement -- | Mix two signals. In opposition to zipWith the result has the -- length of the longer signal. mix :: C v => T v -> T v -> T v -- | Mix an arbitrary number of signals. mixMulti :: C v => [T v] -> T v -- | Add a number to all of the signal values. This is useful for adjusting -- the center of a modulation. raise :: C v => v -> T v -> T v -- | In Synthesizer.Basic.Distortion you find a collection of -- appropriate distortion functions. distort :: (c -> a -> a) -> T c -> T a -> T a mapLinear :: C a => a -> a -> T a -> T a mapExponential :: C a => a -> a -> T a -> T a module Synthesizer.State.Control constant :: a -> T a -- | 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. line :: C y => Int -> (y, y) -> T y linear :: C a => a -> a -> T a -- | As stable as the addition of time values. linearMultiscale :: C y => y -> y -> T y -- | Linear curve starting at zero. linearMultiscaleNeutral :: C y => y -> T y exponential :: C a => a -> a -> T a exponentialMultiscale :: C a => a -> a -> T a exponentialMultiscaleNeutral :: C y => y -> T y exponential2 :: C a => a -> a -> T a exponential2Multiscale :: C a => a -> a -> T a exponential2MultiscaleNeutral :: C y => y -> T y exponentialFromTo :: C y => y -> y -> y -> T y exponentialFromToMultiscale :: C y => y -> y -> y -> T y -- | 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. vectorExponential :: (C a, C a v) => a -> v -> T v vectorExponential2 :: (C a, C a v) => a -> v -> T v cosine :: C a => a -> a -> T a cubicHermite :: C a => (a, (a, a)) -> (a, (a, a)) -> T a curveMultiscale :: (y -> y -> y) -> y -> y -> T y curveMultiscaleNeutral :: (y -> y -> y) -> y -> y -> T y -- | See Synthesizer.Generic.Piece. module Synthesizer.State.Piece type T a = Piece a a (a -> T a) run :: C a => T a a (a -> T a) -> T a step :: T a linear :: C a => T a exponential :: C a => a -> T a cosine :: C a => T a -- |
--   Graphics.Gnuplot.Simple.plotList [] $ Sig.toList $ Piece.run $ 1 |# (10.9, Piece.halfSine FlatRight) #| 2
--   
halfSine :: C a => FlatPosition -> T a cubic :: C a => a -> a -> T a data FlatPosition FlatLeft :: FlatPosition FlatRight :: FlatPosition module Synthesizer.State.Analysis -- | Volume based on Manhattan norm. volumeMaximum :: C y => T y -> y -- | Volume based on Energy norm. volumeEuclidean :: C y => T y -> y volumeEuclideanSqr :: C y => T y -> y -- | Volume based on Sum norm. volumeSum :: (C y, C y) => T y -> y -- | Volume based on Manhattan norm. volumeVectorMaximum :: (C y yv, Ord y) => T yv -> y -- | Volume based on Energy norm. volumeVectorEuclidean :: (C y, C y yv) => T yv -> y volumeVectorEuclideanSqr :: (C y, Sqr y yv) => T yv -> y -- | Volume based on Sum norm. volumeVectorSum :: (C y yv, C y) => T yv -> y -- | Compute minimum and maximum value of the stream the efficient way. -- Input list must be non-empty and finite. bounds :: Ord y => T y -> (y, y) -- | Input list must be finite. List is scanned twice, but counting may be -- faster. histogramDiscreteArray :: T Int -> (Int, T Int) -- | Input list must be finite. If the input signal is empty, the offset is -- undefined. List is scanned twice, but counting may be faster. -- The sum of all histogram values is one less than the length of the -- signal. histogramLinearArray :: C y => T y -> (Int, T y) -- | Input list must be finite. If the input signal is empty, the offset is -- undefined. List is scanned once, counting may be slower. histogramDiscreteIntMap :: T Int -> (Int, T Int) histogramLinearIntMap :: C y => T y -> (Int, T y) histogramIntMap :: C y => y -> T y -> (Int, T Int) -- | Requires finite length. This is identical to the arithmetic mean. directCurrentOffset :: C y => T y -> y scalarProduct :: C y => T y -> T y -> y -- | directCurrentOffset must be non-zero. centroid :: C y => T y -> y centroidRecompute :: C y => T y -> y firstMoment :: C y => T y -> y average :: C y => T y -> y averageRecompute :: C y => T y -> y rectify :: C y => T y -> T y -- | Detects zeros (sign changes) in a signal. This can be used as a simple -- measure of the portion of high frequencies or noise in the signal. It -- ca be used as voiced/unvoiced detector in a vocoder. -- -- zeros x !! n is True if and only if (x !! n -- >= 0) /= (x !! (n+1) >= 0). The result will be one value -- shorter than the input. zeros :: (Ord y, C y) => T y -> T Bool -- | Detect thresholds with a hysteresis. flipFlopHysteresis :: Ord y => (y, y) -> BinaryLevel -> T y -> T BinaryLevel -- | Almost naive implementation of the chirp transform, a generalization -- of the Fourier transform. -- -- More sophisticated algorithms like Rader, Cooley-Tukey, Winograd, -- Prime-Factor may follow. chirpTransform :: C y => y -> T y -> T y -- | See NumericPrelude.AffineSpace for design discussion. module Synthesizer.Interpolation.Class -- | Given that scale zero v == Additive.zero this type class is -- equivalent to Module in the following way: -- --
--   scaleAndAccumulate (a,x) =
--      let ax = a *> x
--      in  (ax, (ax+))
--   
-- -- (see implementation of scaleAndAccumulateModule) and -- --
--   x+y = scaleAccumulate one y $ scale one x
--   zero = scale zero x
--   s*>x = scale s x
--   
-- -- But this redundancy is only because of a lack of the type system or -- lack of my imagination how to solve it better. Use this type class for -- all kinds of interpolation, that is where addition and scaling alone -- make no sense. -- -- I intended to name this class AffineSpace, because all interpolations -- should be affine combinations. This property is equivalent to -- interpolations that preserve constant functions. However, I cannot -- easily assert this property and I'm not entirely sure that all -- reasonable interpolations are actually affine. -- -- Early versions had a zero method, but this is against the -- idea of interpolation. For implementing zero we needed a -- Maybe wrapper for interpolation of StorableVectors. -- Btw. having zero instead of scale is also -- inefficient, since every sum must include a zero summand, which works -- well only when the optimizer simplifies addition with a constant. -- -- We use only one class method that contains actually two methods: -- scale and scaleAccumulate. We expect that instances -- are always defined on record types lifting interpolations from scalars -- to records. This should be done using makeMac and friends or -- the MAC type and the Applicative interface for records -- with many elements. class C a => C a v scaleAndAccumulate :: C a v => (a, v) -> (v, v -> v) scale :: C a v => (a, v) -> v scaleAccumulate :: C a v => (a, v) -> v -> v -- | Infix variant of scaleAccumulate. (+.*) :: C a v => v -> (a, v) -> v infixl 6 +.* combine2 :: C a v => a -> (v, v) -> v combineMany :: C a v => (a, T a) -> (v, T v) -> v scaleAndAccumulateRing :: C a => (a, a) -> (a, a -> a) scaleAndAccumulateModule :: C a v => (a, v) -> (v, v -> v) scaleAndAccumulateApplicative :: (C a v, Applicative f) => (a, f v) -> (f v, f v -> f v) scaleAndAccumulateRingApplicative :: (C a, Applicative f) => (a, f a) -> (f a, f a -> f a) scaleAndAccumulateModuleApplicative :: (C a v, Applicative f) => (a, f v) -> (f v, f v -> f v) -- | A special reader monad. newtype MAC a v x MAC :: ((a, v) -> (x, v -> x)) -> MAC a v x [runMac] :: MAC a v x -> (a, v) -> (x, v -> x) element :: C a x => (v -> x) -> MAC a v x makeMac :: C a x => (x -> v) -> (v -> x) -> (a, v) -> (v, v -> v) makeMac2 :: (C a x, C a y) => (x -> y -> v) -> (v -> x) -> (v -> y) -> (a, v) -> (v, v -> v) makeMac3 :: (C a x, C a y, C a z) => (x -> y -> z -> v) -> (v -> x) -> (v -> y) -> (v -> z) -> (a, v) -> (v, v -> v) instance GHC.Base.Functor (Synthesizer.Interpolation.Class.MAC a v) instance GHC.Base.Applicative (Synthesizer.Interpolation.Class.MAC a v) instance Synthesizer.Interpolation.Class.C GHC.Types.Float GHC.Types.Float instance Synthesizer.Interpolation.Class.C GHC.Types.Double GHC.Types.Double instance Synthesizer.Interpolation.Class.C a v => Synthesizer.Interpolation.Class.C a (Number.Complex.T v) instance Algebra.PrincipalIdealDomain.C a => Synthesizer.Interpolation.Class.C (Number.Ratio.T a) (Number.Ratio.T a) instance (Synthesizer.Interpolation.Class.C a v, Synthesizer.Interpolation.Class.C a w) => Synthesizer.Interpolation.Class.C a (v, w) instance (Synthesizer.Interpolation.Class.C a v, Synthesizer.Interpolation.Class.C a w, Synthesizer.Interpolation.Class.C a u) => Synthesizer.Interpolation.Class.C a (v, w, u) instance Synthesizer.Interpolation.Class.C a v => Synthesizer.Interpolation.Class.C a (Sound.Frame.Stereo.T v) module Synthesizer.Interpolation -- | interpolation as needed for resampling data T t y Cons :: !Margin -> !t -> T y -> y -> T t y [margin] :: T t y -> !Margin [func] :: T t y -> !t -> T y -> y data Margin cons :: Int -> Int -> (t -> T y -> y) -> T t y number :: T t y -> Int offset :: T t y -> Int data PrefixReader y a getNode :: PrefixReader y y fromPrefixReader :: String -> Int -> PrefixReader y (t -> y) -> T t y -- | Consider the signal to be piecewise constant, where the leading value -- is used for filling the interval [0,1). constant :: T t y instance GHC.Classes.Eq Synthesizer.Interpolation.Margin instance GHC.Show.Show Synthesizer.Interpolation.Margin instance GHC.Base.Functor (Synthesizer.Interpolation.PrefixReader y) instance GHC.Base.Applicative (Synthesizer.Interpolation.PrefixReader y) instance Test.QuickCheck.Arbitrary.Arbitrary Synthesizer.Interpolation.Margin module Synthesizer.State.Interpolation zeroPad :: C t => (T t y -> t -> T y -> a) -> y -> T t y -> t -> T y -> a constantPad :: C t => (T t y -> t -> T y -> a) -> T t y -> t -> T y -> a -- | Only for finite input signals. cyclicPad :: C t => (T t y -> t -> T y -> a) -> T t y -> t -> T y -> a -- | The extrapolation may miss some of the first and some of the last -- points extrapolationPad :: C t => (T t y -> t -> T y -> a) -> T t y -> t -> T y -> a skip :: C t => T t y -> (t, T y) -> (t, T y) single :: C t => T t y -> t -> T y -> y delayPad :: y -> Int -> T y -> T y module Synthesizer.State.Filter.Delay static :: C y => Int -> T y -> T y staticPad :: y -> Int -> T y -> T y staticPos :: C y => Int -> T y -> T y staticNeg :: Int -> T y -> T y -- | This is essentially different for constant interpolation, because this -- function "looks forward" whereas the other two variants "look -- backward". For the symmetric interpolation functions of linear and -- cubic interpolation, this does not really matter. modulated :: (C a, C v) => T a v -> Int -> T a -> T v -> T v module Synthesizer.State.Filter.NonRecursive amplify :: C a => a -> T a -> T a amplifyVector :: C a v => a -> T v -> T v envelope :: C a => T a -> T a -> T a envelopeVector :: C a v => T a -> T v -> T v fadeInOut :: C a => Int -> Int -> Int -> T a -> T a -- | Unmodulated non-recursive filter generic :: C a v => T a -> T v -> T v binomial :: (C a, C a, C a v) => a -> a -> T v -> T v binomial1 :: C v => T v -> T v -- | Moving (uniformly weighted) average in the most trivial form. This is -- very slow and needs about n * length x operations. sums :: C v => Int -> T v -> T v -- | This is inverse to frequency modulation. If all control values in -- ctrl are above one, then it holds: frequencyModulation -- ctrl (inverseFrequencyModulationFloor ctrl xs) == xs . Otherwise -- inverseFrequencyModulationFloor is lossy. For the precise -- property we refer to -- Test.Sound.Synthesizer.Plain.Interpolation. The modulation uses -- constant interpolation. Other interpolation types are tricky to -- implement, since they would need interpolation on non-equidistant -- grids. Ok, at least linear interpolation could be supported with -- acceptable effort, but perfect reconstruction would be hard to get. -- The process is not causal in any of its inputs, however control and -- input are aligned. -- -- If you use interpolation for resampling or frequency modulation, you -- may want to smooth the signal before resampling according to the local -- resampling factor. However you cannot simply use the resampling -- control to also control the smoothing, because of the subsequent -- distortion by resampling. Instead you have to stretch the control -- inversely to the resampling factor. This is the task of this function. -- It may be applied like: -- --
--   frequencyModulation ctrl (smooth (inverseFrequencyModulationFloor ctrl ctrl) xs)
--   
inverseFrequencyModulationFloor :: (Ord t, C t) => T t -> T v -> T v inverseFrequencyModulationCeiling :: (Ord t, C t) => T t -> T v -> T v -- | Forward difference quotient. Shortens the signal by one. Inverts -- run in the sense that differentiate (zero : integrate x) == -- x. The signal is shifted by a half time unit. differentiate :: C v => T v -> T v -- | Central difference quotient. Shortens the signal by two elements, and -- shifts the signal by one element. (Which can be fixed by prepending an -- appropriate value.) For linear functions this will yield essentially -- the same result as differentiate. You obtain the result of -- differentiateCenter if you smooth the one of -- differentiate by averaging pairs of adjacent values. -- -- ToDo: Vector variant differentiateCenter :: C v => T v -> T v -- | Second derivative. It is differentiate2 == differentiate . -- differentiate but differentiate2 should be faster. differentiate2 :: C v => T v -> T v -- | Special interpolations defined in terms of our custom Interpolation -- class. module Synthesizer.Interpolation.Custom -- | interpolation as needed for resampling data T t y -- | Consider the signal to be piecewise constant, where the leading value -- is used for filling the interval [0,1). constant :: T t y -- | Consider the signal to be piecewise linear. linear :: C t y => T t y -- | Consider the signal to be piecewise cubic, with smooth connections at -- the nodes. It uses a cubic curve which has node values x0 at 0 and x1 -- at 1 and derivatives (x1-xm1)2 and (x2-x0)2, respectively. You -- can see how it works if you evaluate the expression for t=0 and t=1 as -- well as the derivative at these points. cubic :: (C t, C t y) => T t y -- | List of functions must be non-empty. piecewise :: C t y => Int -> [t -> t] -> T t y piecewiseConstant :: C t y => T t y piecewiseLinear :: C t y => T t y piecewiseCubic :: (C t, C t y) => T t y -- | with this wrapper you can use the collection of interpolating -- functions from Donadio's DSP library function :: C t y => (Int, Int) -> (t -> t) -> T t y module Synthesizer.Basic.ToneModulation -- | 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. -- -- For this routine it would be simpler, if shape would measure -- in multiples of period (we would only need a Ring instance), -- but for shapeLimit it is better the way it is. untangleShapePhase :: C a => Int -> a -> (a, a) -> (a, a) untangleShapePhaseAnalytic :: C a => Int -> a -> (a, a) -> (a, a) flattenShapePhase :: C a => Int -> a -> (a, T a) -> (Int, (a, a)) flattenShapePhaseAnalytic :: C a => Int -> a -> (a, T a) -> (Int, (a, a)) shapeLimits :: C t => Margin -> Margin -> Int -> t -> (t, t) interpolationOffset :: Margin -> Margin -> Int -> Int interpolationNumber :: Margin -> Margin -> Int -> Int type Coords t = (Int, (Int, (t, t))) type Skip t = (Int, (t, T t)) -- | This module allows abstraction of operations that operate on the time -- axis and do also work on signal types without sample values. The most -- distinctive instances are certainly Dirac signals and chunky time -- values. module Synthesizer.Generic.Cut class Read sig null :: Read sig => sig -> Bool length :: Read sig => sig -> Int class (Read sig) => NormalForm sig -- | Evaluating the first value of the signal is necessary for avoiding a -- space leaks if you repeatedly drop a prefix from the signal and do not -- consume something from it. evaluateHead :: NormalForm sig => sig -> () class (Read sig, Monoid sig) => Transform sig take :: Transform sig => Int -> sig -> sig drop :: Transform sig => Int -> sig -> sig dropMarginRem :: Transform sig => Int -> Int -> sig -> (Int, sig) splitAt :: Transform sig => Int -> sig -> (sig, sig) reverse :: Transform sig => sig -> sig dropMarginRemChunky :: Transform sig => (sig -> [Int]) -> Int -> Int -> sig -> (Int, sig) intToChunky :: (C a, C a) => String -> Int -> T a intToChunky98 :: (Num a, C a) => String -> Int -> T a empty :: Monoid sig => sig cycle :: Monoid sig => sig -> sig append :: Monoid sig => sig -> sig -> sig concat :: Monoid sig => [sig] -> sig -- | Like lengthAtLeast n xs = length xs >= n, but is more -- efficient, because it is more lazy. lengthAtLeast :: Transform sig => Int -> sig -> Bool lengthAtMost :: Transform sig => Int -> sig -> Bool sliceVertical :: Transform sig => Int -> sig -> T sig instance Foreign.Storable.Storable y => Synthesizer.Generic.Cut.Transform (Data.StorableVector.Base.Vector y) instance Foreign.Storable.Storable y => Synthesizer.Generic.Cut.Transform (Data.StorableVector.Lazy.Vector y) instance Synthesizer.Generic.Cut.Transform [y] instance Synthesizer.Generic.Cut.Transform (Synthesizer.State.Signal.T y) instance (GHC.Real.Integral t, Numeric.NonNegative.Class.C t) => Synthesizer.Generic.Cut.Transform (Data.EventList.Relative.TimeTimePrivate.T t y) instance (GHC.Real.Integral t, Numeric.NonNegative.Class.C t) => Synthesizer.Generic.Cut.Transform (Data.EventList.Relative.BodyTimePrivate.T t y) instance (Algebra.ToInteger.C a, Algebra.NonNegative.C a) => Synthesizer.Generic.Cut.Transform (Number.NonNegativeChunky.T a) instance (GHC.Real.Integral a, Numeric.NonNegative.Class.C a) => Synthesizer.Generic.Cut.Transform (Numeric.NonNegative.ChunkyPrivate.T a) instance Foreign.Storable.Storable y => Synthesizer.Generic.Cut.NormalForm (Data.StorableVector.Base.Vector y) instance Foreign.Storable.Storable y => Synthesizer.Generic.Cut.NormalForm (Data.StorableVector.Lazy.Vector y) instance Control.DeepSeq.NFData y => Synthesizer.Generic.Cut.NormalForm [y] instance Control.DeepSeq.NFData y => Synthesizer.Generic.Cut.NormalForm (Synthesizer.State.Signal.T y) instance (GHC.Real.Integral t, Control.DeepSeq.NFData y) => Synthesizer.Generic.Cut.NormalForm (Data.EventList.Relative.BodyTimePrivate.T t y) instance (Algebra.ToInteger.C a, Algebra.NonNegative.C a, Control.DeepSeq.NFData a) => Synthesizer.Generic.Cut.NormalForm (Number.NonNegativeChunky.T a) instance (GHC.Real.Integral a, Algebra.NonNegative.C a, Control.DeepSeq.NFData a) => Synthesizer.Generic.Cut.NormalForm (Numeric.NonNegative.ChunkyPrivate.T a) instance Foreign.Storable.Storable y => Synthesizer.Generic.Cut.Read (Data.StorableVector.Base.Vector y) instance Foreign.Storable.Storable y => Synthesizer.Generic.Cut.Read (Data.StorableVector.Lazy.Vector y) instance Synthesizer.Generic.Cut.Read [y] instance Synthesizer.Generic.Cut.Read (Synthesizer.State.Signal.T y) instance GHC.Real.Integral t => Synthesizer.Generic.Cut.Read (Data.EventList.Relative.BodyTimePrivate.T t y) instance GHC.Real.Integral t => Synthesizer.Generic.Cut.Read (Data.EventList.Relative.TimeTimePrivate.T t y) instance (Algebra.ToInteger.C a, Algebra.NonNegative.C a) => Synthesizer.Generic.Cut.Read (Number.NonNegativeChunky.T a) instance GHC.Real.Integral a => Synthesizer.Generic.Cut.Read (Numeric.NonNegative.ChunkyPrivate.T a) module Synthesizer.Generic.CutChunky class (Transform chunky, Transform (Chunk chunky)) => C chunky where { type Chunk chunky :: *; } fromChunks :: C chunky => [Chunk chunky] -> chunky toChunks :: C chunky => chunky -> [Chunk chunky] instance Foreign.Storable.Storable a => Synthesizer.Generic.CutChunky.C (Data.StorableVector.Lazy.Vector a) instance (Algebra.ToInteger.C a, Algebra.NonNegative.C a, Synthesizer.Generic.Cut.Transform a) => Synthesizer.Generic.CutChunky.C (Number.NonNegativeChunky.T a) -- | Type classes that give a uniform interface to storable signals, -- stateful signals, lists, fusable lists. Some of the signal types -- require constraints on the element type. Storable signals require -- Storable elements. Thus we need multiparameter type classes. In this -- module we collect functions where the element type is not altered by -- the function. module Synthesizer.Generic.Signal class (Read (sig y), Read0 sig, Storage (sig y)) => Read sig y -- | This type is used for specification of the maximum size of strict -- packets. Packets can be smaller, can have different sizes in one -- signal. In some kinds of streams, like lists and stateful generators, -- the packet size is always 1. The packet size is not just a burden -- caused by efficiency, but we need control over packet size in -- applications with feedback. -- -- ToDo: Make the element type of the corresponding signal a type -- parameter. This helps to distinguish chunk sizes of scalar and -- vectorised signals. newtype LazySize LazySize :: Int -> LazySize class Storage signal where { data Constraints signal :: *; } constraints :: Storage signal => signal -> Constraints signal class (Write0 sig, Transform sig y) => Write sig y class (Transform (sig y), Transform0 sig, Read sig y) => Transform sig y class Read0 sig toList :: (Read0 sig, Storage (sig y)) => sig y -> [y] toState :: (Read0 sig, Storage (sig y)) => sig y -> T y foldL :: (Read0 sig, Storage (sig y)) => (s -> y -> s) -> s -> sig y -> s foldR :: (Read0 sig, Storage (sig y)) => (y -> s -> s) -> s -> sig y -> s index :: (Read0 sig, Storage (sig y)) => sig y -> Int -> y class (Read0 sig) => Transform0 sig cons :: (Transform0 sig, Storage (sig y)) => y -> sig y -> sig y takeWhile :: (Transform0 sig, Storage (sig y)) => (y -> Bool) -> sig y -> sig y dropWhile :: (Transform0 sig, Storage (sig y)) => (y -> Bool) -> sig y -> sig y span :: (Transform0 sig, Storage (sig y)) => (y -> Bool) -> sig y -> (sig y, sig y) -- | When using viewL for traversing a signal, it is certainly -- better to convert to State signal first, since this might involve -- optimized traversing like in case of Storable signals. viewL :: (Transform0 sig, Storage (sig y)) => sig y -> Maybe (y, sig y) viewR :: (Transform0 sig, Storage (sig y)) => sig y -> Maybe (sig y, y) zipWithAppend :: (Transform0 sig, Storage (sig y)) => (y -> y -> y) -> sig y -> sig y -> sig y map :: (Transform0 sig, Storage (sig y0), Storage (sig y1)) => (y0 -> y1) -> sig y0 -> sig y1 scanL :: (Transform0 sig, Storage (sig y0), Storage (sig y1)) => (y1 -> y0 -> y1) -> y1 -> sig y0 -> sig y1 crochetL :: (Transform0 sig, Storage (sig y0), Storage (sig y1)) => (y0 -> s -> Maybe (y1, s)) -> s -> sig y0 -> sig y1 -- | We could provide the LazySize by a Reader monad, but we don't -- do that because we expect that the choice of the lazy size is more -- local than say the choice of the sample rate. E.g. there is no need to -- have the same laziness coarseness for multiple signal processors. class Transform0 sig => Write0 sig fromList :: (Write0 sig, Storage (sig y)) => LazySize -> [y] -> sig y repeat :: (Write0 sig, Storage (sig y)) => LazySize -> y -> sig y replicate :: (Write0 sig, Storage (sig y)) => LazySize -> Int -> y -> sig y iterate :: (Write0 sig, Storage (sig y)) => LazySize -> (y -> y) -> y -> sig y iterateAssociative :: (Write0 sig, Storage (sig y)) => LazySize -> (y -> y -> y) -> y -> sig y unfoldR :: (Write0 sig, Storage (sig y)) => LazySize -> (s -> Maybe (y, s)) -> s -> sig y delay :: Write sig y => LazySize -> y -> Int -> sig y -> sig y zipWith :: (Read sig a, Transform sig b, Transform sig c) => (a -> b -> c) -> sig a -> sig b -> sig c zip :: (Read sig a, Transform sig b, Transform sig (a, b)) => sig a -> sig b -> sig (a, b) sum :: (C a, Read sig a) => sig a -> a zipWith3 :: (Read sig a, Read sig b, Transform sig c) => (a -> b -> c -> c) -> sig a -> sig b -> sig c -> sig c unzip :: (Transform sig (a, b), Transform sig a, Transform sig b) => sig (a, b) -> (sig a, sig b) unzip3 :: (Transform sig (a, b, c), Transform sig a, Transform sig b, Transform sig c) => sig (a, b, c) -> (sig a, sig b, sig c) foldMap :: (Read sig a, Monoid m) => (a -> m) -> sig a -> m tails :: Transform sig y => sig y -> T (sig y) singleton :: Transform sig y => y -> sig y snoc :: Transform sig y => sig y -> y -> sig y switchL :: Transform sig y => a -> (y -> sig y -> a) -> sig y -> a switchR :: Transform sig y => a -> (sig y -> y -> a) -> sig y -> a mapAdjacent :: (Read sig a, Transform sig a) => (a -> a -> a) -> sig a -> sig a sum1 :: (C a, Read sig a) => sig a -> a linearComb :: (C t y, Read sig t, Read sig y) => sig t -> sig y -> y -- | Deprecated: Use foldMap instead. monoidConcatMap :: (Read sig a, Monoid m) => (a -> m) -> sig a -> m -- | Like tail, but for an empty signal it simply returns an empty -- signal. laxTail :: Transform sig y => sig y -> sig y mix :: (C y, Transform sig y) => sig y -> sig y -> sig y delayLoop :: Transform sig y => (sig y -> sig y) -> sig y -> sig y delayLoopOverlap :: (C y, Write sig y) => Int -> (sig y -> sig y) -> sig y -> sig y fromState :: Write sig y => LazySize -> T y -> sig y modifyStatic :: Transform sig a => Simple s ctrl a a -> ctrl -> sig a -> sig a -- | Here the control may vary over the time. modifyModulated :: (Transform sig a, Transform sig b, Read sig ctrl) => Simple s ctrl a b -> sig ctrl -> sig a -> sig b -- | Only non-empty suffixes are processed. More oftenly we might need -- --
--   zipWithTails :: (Read sig b, Transform2 sig a) =>
--      (b -> sig a -> a) -> sig b -> sig a -> sig a
--   
-- -- this would preserve the chunk structure of sig a, but it is a -- bit more hassle to implement that. zipWithTails :: (Transform sig a, Transform sig b, Transform sig c) => (a -> sig b -> c) -> sig a -> sig b -> sig c runViewL :: Read sig y => sig y -> (forall s. (s -> Maybe (y, s)) -> s -> x) -> x runSwitchL :: Read sig y => sig y -> (forall s. (forall z. z -> (y -> s -> z) -> s -> z) -> s -> x) -> x extendConstant :: Write sig y => LazySize -> sig y -> sig y mapTails :: Transform sig a => (sig a -> a) -> sig a -> sig a -- | This can be used for internal signals that have no observable effect -- on laziness. E.g. when you construct a list by repeat -- defaultLazySize zero we assume that zero is defined for -- all Additive types. defaultLazySize :: LazySize readSVL :: (Storable a => Vector a -> b) -> Storage (Vector a) => Vector a -> b writeSVL :: (Storable a => Vector a) -> Storage (Vector a) => Vector a withStorableContext :: (ChunkSize -> a) -> LazySize -> a readSV :: (Storable a => Vector a -> b) -> Storage (Vector a) => Vector a -> b writeSV :: (Storable a => Vector a) -> Storage (Vector a) => Vector a indexByDrop :: Transform sig a => sig a -> Int -> a zipWithState :: (Transform sig b, Transform sig c) => (a -> b -> c) -> T a -> sig b -> sig c zipWithState3 :: (Transform sig c, Transform sig d) => (a -> b -> c -> d) -> T a -> T b -> sig c -> sig d -- | takeStateMatch len xs keeps a prefix of xs of the -- same length and block structure as len and stores it in the -- same type of container as len. takeStateMatch :: (Transform sig a, Transform sig b) => sig a -> T b -> sig b mapTailsAlt :: (Transform sig a, Write sig b) => LazySize -> (sig a -> b) -> sig a -> sig b null :: Read sig => sig -> Bool length :: Read sig => sig -> Int empty :: Monoid sig => sig cycle :: Monoid sig => sig -> sig append :: Monoid sig => sig -> sig -> sig concat :: Monoid sig => [sig] -> sig take :: Transform sig => Int -> sig -> sig drop :: Transform sig => Int -> sig -> sig dropMarginRem :: Transform sig => Int -> Int -> sig -> (Int, sig) splitAt :: Transform sig => Int -> sig -> (sig, sig) reverse :: Transform sig => sig -> sig -- | Like lengthAtLeast n xs = length xs >= n, but is more -- efficient, because it is more lazy. lengthAtLeast :: Transform sig => Int -> sig -> Bool lengthAtMost :: Transform sig => Int -> sig -> Bool sliceVertical :: Transform sig => Int -> sig -> T sig instance Algebra.IntegralDomain.C Synthesizer.Generic.Signal.LazySize instance Algebra.RealIntegral.C Synthesizer.Generic.Signal.LazySize instance Algebra.Absolute.C Synthesizer.Generic.Signal.LazySize instance Algebra.ToRational.C Synthesizer.Generic.Signal.LazySize instance Algebra.ToInteger.C Synthesizer.Generic.Signal.LazySize instance Algebra.ZeroTestable.C Synthesizer.Generic.Signal.LazySize instance Algebra.Ring.C Synthesizer.Generic.Signal.LazySize instance Algebra.Additive.C Synthesizer.Generic.Signal.LazySize instance GHC.Show.Show Synthesizer.Generic.Signal.LazySize instance GHC.Classes.Ord Synthesizer.Generic.Signal.LazySize instance GHC.Classes.Eq Synthesizer.Generic.Signal.LazySize instance Foreign.Storable.Storable y => Synthesizer.Generic.Signal.Write Data.StorableVector.Lazy.Vector y instance Synthesizer.Generic.Signal.Write [] y instance Synthesizer.Generic.Signal.Write Synthesizer.State.Signal.T y instance (Numeric.NonNegative.Class.C time, GHC.Real.Integral time) => Synthesizer.Generic.Signal.Write (Data.EventList.Relative.BodyTimePrivate.T time) y instance Synthesizer.Generic.Signal.Write0 Data.StorableVector.Lazy.Vector instance Synthesizer.Generic.Signal.Write0 [] instance Synthesizer.Generic.Signal.Write0 Synthesizer.State.Signal.T instance (Numeric.NonNegative.Class.C time, GHC.Real.Integral time) => Synthesizer.Generic.Signal.Write0 (Data.EventList.Relative.BodyTimePrivate.T time) instance GHC.Base.Semigroup Synthesizer.Generic.Signal.LazySize instance GHC.Base.Monoid Synthesizer.Generic.Signal.LazySize instance Algebra.Monoid.C Synthesizer.Generic.Signal.LazySize instance Algebra.NonNegative.C Synthesizer.Generic.Signal.LazySize instance Test.QuickCheck.Arbitrary.Arbitrary Synthesizer.Generic.Signal.LazySize instance Synthesizer.Generic.Cut.Read Synthesizer.Generic.Signal.LazySize instance Synthesizer.Generic.Cut.Transform Synthesizer.Generic.Signal.LazySize instance (Numeric.NonNegative.Class.C time, GHC.Real.Integral time) => Synthesizer.Generic.Signal.Transform0 (Data.EventList.Relative.BodyTimePrivate.T time) instance Foreign.Storable.Storable y => Synthesizer.Generic.Signal.Transform Data.StorableVector.Lazy.Vector y instance Foreign.Storable.Storable y => Synthesizer.Generic.Signal.Transform Data.StorableVector.Base.Vector y instance Synthesizer.Generic.Signal.Transform [] y instance Synthesizer.Generic.Signal.Transform Synthesizer.State.Signal.T y instance (Numeric.NonNegative.Class.C time, GHC.Real.Integral time) => Synthesizer.Generic.Signal.Transform (Data.EventList.Relative.BodyTimePrivate.T time) y instance Synthesizer.Generic.Signal.Transform0 Data.StorableVector.Lazy.Vector instance Synthesizer.Generic.Signal.Transform0 Data.StorableVector.Base.Vector instance Synthesizer.Generic.Signal.Transform0 [] instance Synthesizer.Generic.Signal.Transform0 Synthesizer.State.Signal.T instance Foreign.Storable.Storable y => Synthesizer.Generic.Signal.Read Data.StorableVector.Lazy.Vector y instance Foreign.Storable.Storable y => Synthesizer.Generic.Signal.Read Data.StorableVector.Base.Vector y instance Synthesizer.Generic.Signal.Read [] y instance Synthesizer.Generic.Signal.Read Synthesizer.State.Signal.T y instance (Numeric.NonNegative.Class.C time, GHC.Real.Integral time) => Synthesizer.Generic.Signal.Read (Data.EventList.Relative.BodyTimePrivate.T time) y instance Synthesizer.Generic.Signal.Read0 Data.StorableVector.Lazy.Vector instance Synthesizer.Generic.Signal.Read0 Data.StorableVector.Base.Vector instance Synthesizer.Generic.Signal.Read0 [] instance Synthesizer.Generic.Signal.Read0 Synthesizer.State.Signal.T instance (Numeric.NonNegative.Class.C time, GHC.Real.Integral time) => Synthesizer.Generic.Signal.Read0 (Data.EventList.Relative.BodyTimePrivate.T time) instance Foreign.Storable.Storable y => Synthesizer.Generic.Signal.Storage (Data.StorableVector.Lazy.Vector y) instance Foreign.Storable.Storable y => Synthesizer.Generic.Signal.Storage (Data.StorableVector.Base.Vector y) instance Synthesizer.Generic.Signal.Storage [y] instance Synthesizer.Generic.Signal.Storage (Synthesizer.State.Signal.T y) instance Synthesizer.Generic.Signal.Storage (Data.EventList.Relative.BodyTimePrivate.T time y) module Synthesizer.PiecewiseConstant.Storable toSignal :: Storable y => T StrictTime y -> T y toSignalInit :: Storable y => y -> T StrictTime y -> T y toSignalInitWith :: Storable c => (y -> c) -> c -> T StrictTime [y] -> T c module Synthesizer.PiecewiseConstant.Signal type T = T StrictTime type StrictTime = Integer type ShortStrictTime = Int type LazyTime = T StrictTime subdivideLazy :: C time => T (T time) body -> T time body -- | Subdivide lazy times into chunks that fit into the number range -- representable by Int. subdivideLazyToShort :: T LazyTime y -> T ShortStrictTime y subdivideLongStrict :: T StrictTime y -> T ShortStrictTime y -- | Returns a list of non-zero times. chopLongTime :: StrictTime -> [ShortStrictTime] longFromShortTime :: ShortStrictTime -> StrictTime zipWith :: C time => (a -> b -> c) -> T time a -> T time b -> T time c module Synthesizer.PiecewiseConstant.Generic toSignal :: Write sig y => T StrictTime y -> sig y toSignalInit :: Write sig y => y -> T StrictTime y -> sig y toSignalInitWith :: Write sig c => (y -> c) -> c -> T StrictTime [y] -> sig c -- | Noise and random processes. module Synthesizer.Generic.Noise -- | Deterministic white noise, uniformly distributed between -1 and 1. -- That is, variance is 1/3. white :: (C y, Random y, Write sig y) => LazySize -> sig y whiteGen :: (C y, Random y, RandomGen g, Write sig y) => LazySize -> g -> sig y -- | Approximates normal distribution with variance 1 by a quadratic -- B-spline distribution. whiteQuadraticBSplineGen :: (C y, Random y, RandomGen g, Write sig y) => LazySize -> g -> sig y randomPeeks :: (C y, Random y, Transform sig y, Transform sig Bool) => sig y -> sig Bool randomPeeksGen :: (C y, Random y, RandomGen g, Transform sig y, Transform sig Bool) => g -> sig y -> sig Bool -- | Filter operators from calculus module Synthesizer.Generic.Filter.Recursive.Integration -- | Integrate with initial value zero. However the first emitted value is -- the value of the input signal. It maintains the length of the signal. run :: (C v, Transform sig v) => sig v -> sig v -- | Integrate with initial condition. First emitted value is the initial -- condition. The signal become one element longer. runInit :: (C v, Transform sig v) => v -> sig v -> sig v -- | http://en.wikipedia.org/wiki/Particle_displacement module Synthesizer.Generic.Displacement -- | Mix two signals. In opposition to zipWith the result has the -- length of the longer signal. mix :: (C v, Transform sig v) => sig v -> sig v -> sig v -- | Mix one or more signals. mixMulti :: (C v, Transform sig v) => [sig v] -> sig v -- | Add a number to all of the signal values. This is useful for adjusting -- the center of a modulation. raise :: (C v, Transform sig v) => v -> sig v -> sig v -- | In Synthesizer.Basic.Distortion you find a collection of -- appropriate distortion functions. distort :: (Read sig c, Transform sig v) => (c -> v -> v) -> sig c -> sig v -> sig v mapLinear :: (C a, Transform sig a) => a -> a -> sig a -> sig a mapExponential :: (C a, Transform sig a) => a -> a -> sig a -> sig a module Synthesizer.Generic.Control constant :: Write sig y => LazySize -> y -> sig y linear :: (C y, Write sig y) => LazySize -> y -> y -> sig y -- | Minimize rounding errors by reducing number of operations per element -- to a logarithmuc number. linearMultiscale :: (C y, Write sig y) => LazySize -> y -> y -> sig y -- | Linear curve starting at zero. linearMultiscaleNeutral :: (C y, Write sig y) => LazySize -> y -> sig y -- | 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. 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 -- | 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. 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 -- | These are pieces that can be assembled to a control curve. This was -- formerly part of the Control module but because of the -- overlap with immediate control curve generators I created a new -- module. module Synthesizer.Generic.Piece type T sig a = Piece a a (LazySize -> a -> sig a) run :: (C a, Transform (sig a)) => LazySize -> T a a (LazySize -> a -> sig a) -> sig a step :: Write sig a => T sig a linear :: (C a, Write sig a) => T sig a exponential :: (C a, Write sig a) => a -> T sig a cosine :: (C a, Write sig a) => T sig a -- |
--   Graphics.Gnuplot.Simple.plotList [] $ Sig.toList $ run $ 1 |# (10.9, halfSine FlatRight) #| 2
--   
halfSine :: (C a, Write sig a) => FlatPosition -> T sig a cubic :: (C a, Write sig a) => a -> a -> T sig a data FlatPosition FlatLeft :: FlatPosition FlatRight :: FlatPosition module Synthesizer.Generic.Filter.NonRecursive negate :: (C a, Transform sig a) => sig a -> sig a amplify :: (C a, Transform sig a) => a -> sig a -> sig a amplifyVector :: (C a v, Transform sig v) => a -> sig v -> sig v normalize :: (C a, Transform sig a) => (sig a -> a) -> sig a -> sig a envelope :: (C a, Transform sig a) => sig a -> sig a -> sig a envelopeVector :: (C a v, Read sig a, Transform sig v) => sig a -> sig v -> sig v fadeInOut :: (C a, Write sig a) => Int -> Int -> Int -> sig a -> sig a delay :: (C y, Write sig y) => Int -> sig y -> sig y delayPad :: Write sig y => y -> Int -> sig y -> sig y delayPos :: (C y, Write sig y) => Int -> sig y -> sig y delayNeg :: Transform sig y => Int -> sig y -> sig y delayLazySize :: (C y, Write sig y) => LazySize -> Int -> sig y -> sig y -- | The pad value y must be defined, otherwise the chunk size of -- the padding can be observed. delayPadLazySize :: Write sig y => LazySize -> y -> Int -> sig y -> sig y delayPosLazySize :: (C y, Write sig y) => LazySize -> Int -> sig y -> sig y binomialMask :: (C a, Write sig a) => LazySize -> Int -> sig a binomial :: (C a, C a, C a v, Transform sig v) => a -> a -> sig v -> sig v binomial1 :: (C v, Transform sig v) => sig v -> sig v -- | Moving (uniformly weighted) average in the most trivial form. This is -- very slow and needs about n * length x operations. sums :: (C v, Transform sig v) => Int -> sig v -> sig v sumsDownsample2 :: (C v, Write sig v) => LazySize -> sig v -> sig v downsample2 :: Write sig v => LazySize -> sig v -> sig v downsample :: Write sig v => LazySize -> Int -> sig v -> sig v sumRange :: (C v, Transform sig v) => sig v -> (Int, Int) -> v pyramid :: (C v, Write sig v) => Int -> sig v -> ([Int], [sig v]) sumRangeFromPyramid :: (C v, Transform sig v) => [sig v] -> (Int, Int) -> v sumsPosModulated :: (C v, Transform sig (Int, Int), Transform sig v) => sig (Int, Int) -> sig v -> sig v sumsPosModulatedPyramid :: (C v, Transform sig (Int, Int), Write sig v) => Int -> sig (Int, Int) -> sig v -> sig v -- | The first argument is the amplification. The main reason to introduce -- it, was to have only a Module constraint instead of Field. This way we -- can also filter stereo signals. movingAverageModulatedPyramid :: (C a, C a v, Transform sig Int, Transform sig (Int, Int), Write sig v) => a -> Int -> Int -> sig Int -> sig v -> sig v inverseFrequencyModulationFloor :: (Ord t, C t, Write sig v, Read sig t) => LazySize -> sig t -> sig v -> sig v -- | Forward difference quotient. Shortens the signal by one. Inverts -- run in the sense that differentiate (zero : integrate x) == -- x. The signal is shifted by a half time unit. differentiate :: (C v, Transform sig v) => sig v -> sig v -- | Central difference quotient. Shortens the signal by two elements, and -- shifts the signal by one element. (Which can be fixed by prepending an -- appropriate value.) For linear functions this will yield essentially -- the same result as differentiate. You obtain the result of -- differentiateCenter if you smooth the one of -- differentiate by averaging pairs of adjacent values. -- -- ToDo: Vector variant differentiateCenter :: (C v, Transform sig v) => sig v -> sig v -- | Second derivative. It is differentiate2 == differentiate . -- differentiate but differentiate2 should be faster. differentiate2 :: (C v, Transform sig v) => sig v -> sig v -- | Unmodulated non-recursive filter (convolution) -- -- Brute force implementation. generic :: (C a v, Transform sig a, Write sig v) => sig a -> sig v -> sig v -- | Both should signals should have similar length. If they have -- considerably different length, then better use -- karatsubaFiniteInfinite. -- -- Implementation using Karatsuba trick and split-and-overlap-add. This -- way we stay in a ring, are faster than quadratic runtime but do not -- reach log-linear runtime. karatsubaFinite :: (C a, C b, C c, Transform sig a, Transform sig b, Transform sig c) => (a -> b -> c) -> sig a -> sig b -> sig c -- | The first operand must be finite and the second one can be infinite. -- For efficient operation we expect that the second signal is longer -- than the first one. karatsubaFiniteInfinite :: (C a, C b, C c, Transform sig a, Transform sig b, Transform sig c) => (a -> b -> c) -> sig a -> sig b -> sig c karatsubaInfinite :: (C a, C b, C c, Transform sig a, Transform sig c, Transform sig b) => (a -> b -> c) -> sig a -> sig b -> sig c type Pair a = (a, a) -- | Reasonable choices for the multiplication operation are (*), -- (*>), convolve. convolvePair :: (C a, C b, C c) => (a -> b -> c) -> Pair a -> Pair b -> Triple c sumAndConvolvePair :: (C a, C b, C c) => (a -> b -> c) -> Pair a -> Pair b -> ((a, b), Triple c) type Triple a = (a, a, a) convolvePairTriple :: (C a, C b, C c) => (a -> b -> c) -> Pair a -> Triple b -> (c, c, c, c) convolveTriple :: (C a, C b, C c) => (a -> b -> c) -> Triple a -> Triple b -> (c, c, c, c, c) sumAndConvolveTriple :: (C a, C b, C c) => (a -> b -> c) -> Triple a -> Triple b -> ((a, b), (c, c, c, c, c)) sumAndConvolveTripleAlt :: (C a, C b, C c) => (a -> b -> c) -> Triple a -> Triple b -> ((a, b), (c, c, c, c, c)) type Quadruple a = (a, a, a, a) convolveQuadruple :: (C a, C b, C c) => (a -> b -> c) -> Quadruple a -> Quadruple b -> (c, c, c, c, c, c, c) sumAndConvolveQuadruple :: (C a, C b, C c) => (a -> b -> c) -> Quadruple a -> Quadruple b -> ((a, b), (c, c, c, c, c, c, c)) sumAndConvolveQuadrupleAlt :: (C a, C b, C c) => (a -> b -> c) -> Quadruple a -> Quadruple b -> ((a, b), (c, c, c, c, c, c, c)) maybeAccumulateRangeFromPyramid :: Transform sig v => (v -> v -> v) -> [sig v] -> (Int, Int) -> Maybe v -- | Moving average, where window bounds must be always non-negative. -- -- The laziness granularity is 2^height. accumulatePosModulatedFromPyramid :: (Transform sig (Int, Int), Write sig v) => ([sig v] -> (Int, Int) -> v) -> ([Int], [sig v]) -> sig (Int, Int) -> sig v withPaddedInput :: (Transform sig Int, Transform sig (Int, Int), Write sig y) => y -> (sig (Int, Int) -> sig y -> v) -> Int -> sig Int -> sig y -> v -- | It must hold delay <= length a. addShiftedSimple :: (C a, Transform sig a) => Int -> sig a -> sig a -> sig a consumeRangeFromPyramid :: Transform sig v => (v -> a -> a) -> a -> [sig v] -> (Int, Int) -> a sumRangeFromPyramidReverse :: (C v, Transform sig v) => [sig v] -> (Int, Int) -> v sumRangeFromPyramidFoldr :: (C v, Transform sig v) => [sig v] -> (Int, Int) -> v module Synthesizer.Storable.Filter.NonRecursive delay :: (C y, Storable y) => Int -> T y -> T y delayPad :: Storable y => y -> Int -> T y -> T y delayPos :: (C y, Storable y) => Int -> T y -> T y delayNeg :: Storable y => Int -> T y -> T y downsample2 :: Storable v => T v -> T v sumsDownsample2 :: (C v, Storable v) => T v -> T v convolveDownsample2 :: (C a v, Storable a, Storable v) => T a -> T v -> T v -- | The function is like that of inverseFrequencyModulationFloor, -- but this function preserves in a sense the chunk structure. -- -- The result will have laziness breaks at least at the chunk boundaries -- that correspond to the breaks in the input signal. However we insert -- more breaks, such that a maximum chunk size can be warrented. (Since -- control and input signal are aligned in time, we might as well use the -- control chunk structure. Currently I do not know what is better. For -- the above example it doesn't matter. We might implement a variant in -- Causal.Filter.NonRecursive.) -- -- This function cannot be written using generic functions, since we have -- to inspect the chunks individually. inverseFrequencyModulationFloor :: (Storable v, Read sig t, C t, Ord t) => ChunkSize -> sig t -> T v -> T v sumsPosModulatedPyramid :: (C v, Storable v) => Int -> T (Int, Int) -> T v -> T v -- | Moving average, where window bounds must be always non-negative. -- -- The laziness granularity is 2^height. -- -- This function is only slightly more efficient than its counterpart -- from Generic.Filter, since it generates strict blocks and not -- one-block chunky signals. accumulatePosModulatedPyramid :: Storable v => ([T v] -> (Int, Int) -> v) -> ([Int], [T v]) -> T (Int, Int) -> T v accumulateBinPosModulatedPyramid :: Storable v => (v -> v -> v) -> Int -> T (Int, Int) -> T v -> T v -- | The first argument is the amplification. The main reason to introduce -- it, was to have only a Module constraint instead of Field. This way we -- can also filter stereo signals. movingAverageModulatedPyramid :: (C a, C a v, Storable Int, Storable v) => a -> Int -> Int -> T Int -> T v -> T v movingAccumulateModulatedPyramid :: Storable v => (v -> v -> v) -> v -> Int -> Int -> T Int -> T v -> T v sumsDownsample2Alt :: (C v, Storable v) => T v -> T v pyramid :: Storable v => (v -> v -> v) -> Int -> T v -> [T v] module Synthesizer.Generic.Analysis -- | Volume based on Manhattan norm. volumeMaximum :: (C y, Read sig y) => sig y -> y -- | Volume based on Energy norm. volumeEuclidean :: (C y, Read sig y) => sig y -> y volumeEuclideanSqr :: (C y, Read sig y) => sig y -> y -- | Volume based on Sum norm. volumeSum :: (C y, C y, Read sig y) => sig y -> y -- | Volume based on Manhattan norm. volumeVectorMaximum :: (C y yv, Ord y, Read sig yv) => sig yv -> y -- | Volume based on Energy norm. volumeVectorEuclidean :: (C y, C y yv, Read sig yv) => sig yv -> y volumeVectorEuclideanSqr :: (C y, Sqr y yv, Read sig yv) => sig yv -> y -- | Volume based on Sum norm. volumeVectorSum :: (C y yv, C y, Read sig yv) => sig yv -> y -- | Compute minimum and maximum value of the stream the efficient way. -- Input list must be non-empty and finite. bounds :: (Ord y, Read sig y) => sig y -> (y, y) -- | Requires finite length. This is identical to the arithmetic mean. directCurrentOffset :: (C y, Read sig y) => sig y -> y scalarProduct :: (C y, Read sig y) => sig y -> sig y -> y -- | directCurrentOffset must be non-zero. centroid :: (C y, Read sig y) => sig y -> y average :: (C y, Read sig y) => sig y -> y rectify :: (C y, Transform sig y) => sig y -> sig y -- | Detects zeros (sign changes) in a signal. This can be used as a simple -- measure of the portion of high frequencies or noise in the signal. It -- ca be used as voiced/unvoiced detector in a vocoder. -- -- zeros x !! n is True if and only if (x !! n -- >= 0) /= (x !! (n+1) >= 0). The result will be one value -- shorter than the input. zeros :: (Ord y, C y, Transform sig y, Transform sig Bool) => sig y -> sig Bool -- | Detect thresholds with a hysteresis. flipFlopHysteresis :: (Ord y, Transform sig y, Transform sig BinaryLevel) => (y, y) -> BinaryLevel -> sig y -> sig BinaryLevel -- | Almost naive implementation of the chirp transform, a generalization -- of the Fourier transform. -- -- More sophisticated algorithms like Rader, Cooley-Tukey, Winograd, -- Prime-Factor may follow. chirpTransform :: (Write sig y, C y) => LazySize -> y -> sig y -> sig y module Synthesizer.Generic.Cyclic fromSignal :: (Write sig yv, C yv) => LazySize -> Int -> sig yv -> sig yv reverse :: Transform sig y => sig y -> sig y -- | It must hold n <= CutG.length x. reperiodize :: (Transform sig yv, C yv) => Int -> sig yv -> sig yv -- | length of the input signals must be equal convolve :: (Transform sig y, C y) => sig y -> sig y -> sig y -- | The size of both input signals must be equal. -- -- Could be optimized by computing only first (length x) elements. filterNaive :: (Transform sig y, C y) => sig y -> sig y -> sig y convolveNaive :: (Transform sig y, C y) => sig y -> sig y -> sig y type Pair y = (y, y) convolvePair :: C y => Pair y -> Pair y -> Pair y sumAndConvolvePair :: C y => Pair y -> Pair y -> ((y, y), Pair y) type Triple y = (y, y, y) convolveTriple :: C y => Triple y -> Triple y -> Triple y sumAndConvolveTriple :: C y => Triple y -> Triple y -> ((y, y), Triple y) sumAndConvolveTripleAlt :: C y => Triple y -> Triple y -> ((y, y), Triple y) type Quadruple y = (y, y, y, y) convolveQuadruple :: C y => Quadruple y -> Quadruple y -> Quadruple y sumAndConvolveQuadruple :: C y => Quadruple y -> Quadruple y -> ((y, y), Quadruple y) -- | Complete implementation for Fast Fourier Transform for any signal -- length. Although defined for all kinds of signal storage, we need fast -- access to arbitrary indices. module Synthesizer.Generic.Fourier class C y => Element y recipInteger :: (Element y, Read sig y) => sig y -> y addId :: (Element y, Read sig y) => sig y -> y multId :: (Element y, Read sig y) => sig y -> y -- | It must hold: -- --
--   uncurry (*) (conjugatePrimitiveRootsOfUnity n) = 1
--   
-- --
--   mapPair ((^m), (^m)) (conjugatePrimitiveRootsOfUnity (n*m) y)
--      == conjugatePrimitiveRootsOfUnity n y@
--   
-- -- since we need for caching that the cache is uniquely determined by -- singal length and transform direction. conjugatePrimitiveRootsOfUnity :: (Element y, Read sig y) => sig y -> (y, y) transformForward :: (Element y, Transform sig y) => sig y -> sig y -- | Shall we divide the result values by the length of the signal? Our -- dimensional wrapper around the Fourier transform does not expect this. transformBackward :: (Element y, Transform sig y) => sig y -> sig y -- | The expression cacheForward prototype precomputes all data -- that is needed for forward Fourier transforms for signals of the type -- and length prototype. You can use this cache in -- transformWithCache. cacheForward :: (Element y, Transform sig y) => sig y -> Cache sig y -- | See cacheForward. cacheBackward :: (Element y, Transform sig y) => sig y -> Cache sig y -- | It is (cacheForward x, cacheBackward x) = cacheDuplex x but -- cacheDuplex shared common data of both caches. cacheDuplex :: (Element y, Transform sig y) => sig y -> (Cache sig y, Cache sig y) -- | The size and type of the signal must match the parameters, that the -- cache was generated for. transformWithCache :: (Element y, Transform sig y) => Cache sig y -> sig y -> sig y -- | Signal must have equal size and must not be empty. convolveCyclic :: (Element y, Transform sig y) => sig y -> sig y -> sig y -- | Filter window stored as spectrum such that it can be applied -- efficiently to long signals. data Window sig y window :: (Element y, Transform sig y) => sig y -> Window sig y -- | Efficient convolution of a large filter window with a probably -- infinite signal. convolveWithWindow :: (Element y, Transform sig y) => Window sig y -> sig y -> sig y instance GHC.Classes.Ord Synthesizer.Generic.Fourier.Direction instance GHC.Classes.Eq Synthesizer.Generic.Fourier.Direction instance GHC.Show.Show Synthesizer.Generic.Fourier.Direction instance GHC.Show.Show y => GHC.Show.Show (Synthesizer.Generic.Fourier.LevelCacheNaive y) instance GHC.Enum.Enum Synthesizer.Generic.Fourier.LevelSmall instance GHC.Classes.Ord Synthesizer.Generic.Fourier.LevelSmall instance GHC.Classes.Eq Synthesizer.Generic.Fourier.LevelSmall instance GHC.Show.Show Synthesizer.Generic.Fourier.LevelSmall instance GHC.Show.Show y => GHC.Show.Show (Synthesizer.Generic.Fourier.LevelCacheSmall y) instance GHC.Classes.Ord Synthesizer.Generic.Fourier.LevelRadix2 instance GHC.Classes.Eq Synthesizer.Generic.Fourier.LevelRadix2 instance GHC.Show.Show Synthesizer.Generic.Fourier.LevelRadix2 instance GHC.Show.Show (sig y) => GHC.Show.Show (Synthesizer.Generic.Fourier.LevelCacheRadix2 sig y) instance GHC.Show.Show Synthesizer.Generic.Fourier.LevelComposite instance GHC.Show.Show (sig y) => GHC.Show.Show (Synthesizer.Generic.Fourier.LevelCacheComposite sig y) instance GHC.Show.Show Synthesizer.Generic.Fourier.LevelCoprime instance GHC.Show.Show Synthesizer.Generic.Fourier.LevelPrime instance GHC.Show.Show Synthesizer.Generic.Fourier.Plan instance GHC.Show.Show (sig y) => GHC.Show.Show (Synthesizer.Generic.Fourier.LevelCachePrime sig y) instance (GHC.Show.Show y, GHC.Show.Show (sig y)) => GHC.Show.Show (Synthesizer.Generic.Fourier.Cache sig y) instance (GHC.Show.Show y, GHC.Show.Show (sig y)) => GHC.Show.Show (Synthesizer.Generic.Fourier.Window sig y) instance GHC.Classes.Eq Synthesizer.Generic.Fourier.Plan instance GHC.Classes.Ord Synthesizer.Generic.Fourier.Plan instance GHC.Classes.Eq Synthesizer.Generic.Fourier.LevelPrime instance GHC.Classes.Ord Synthesizer.Generic.Fourier.LevelPrime instance GHC.Classes.Eq Synthesizer.Generic.Fourier.LevelCoprime instance GHC.Classes.Ord Synthesizer.Generic.Fourier.LevelCoprime instance GHC.Classes.Eq Synthesizer.Generic.Fourier.LevelComposite instance GHC.Classes.Ord Synthesizer.Generic.Fourier.LevelComposite instance Algebra.Transcendental.C a => Synthesizer.Generic.Fourier.Element (Number.Complex.T a) instance (Synthesizer.Basic.NumberTheory.PrimitiveRoot a, Algebra.PrincipalIdealDomain.C a, GHC.Classes.Eq a) => Synthesizer.Generic.Fourier.Element (Number.ResidueClass.Check.T a) module Synthesizer.ChunkySize type T = T LazySize fromStorableVectorSize :: LazySize -> T toStorableVectorSize :: T -> LazySize toNullList :: T -> [()] module Synthesizer.State.Cut -- | Take signal until it falls short of a certain amplitude for a given -- time. takeUntilPause :: C a => a -> Int -> T a -> T a -- | Take values until the predicate p holds for n successive values. The -- list is truncated at the beginning of the interval of matching values. takeUntilInterval :: (a -> Bool) -> Int -> T a -> T a -- | Split a storable signal into a sequence of signals. A new piece is -- started whenever the Boolean signal contains a True. The first -- piece in the result is the part from the beginning until the first -- True. That is, if the signal Bool starts with a -- True, then the first result piece is empty. -- -- When the control signal is at least as long as the storable signal and -- if we neglect the chunking structure, then it holds -- --
--   concat (chopStorable bs xs) == xs
--   
chopStorable :: Storable a => T Bool -> T a -> [T a] chopChunkySize :: T Bool -> T -> [T] selectBool :: (T a, T a) -> T Bool -> T a select :: Ix i => Array i (T a) -> T i -> T a arrange :: C v => T Int (T v) -> T v -- | Given a list of signals with time stamps, mix them into one signal as -- they occur in time. Ideally for composing music. -- -- Cf. series arrangeList :: C v => T Int (T v) -> T v -- | Functions for cutting signals with respect to lazy chunky time -- measures. This is essential for realtime applications. module Synthesizer.ChunkySize.Cut class Read sig => Read sig length :: Read sig => sig -> T class (Read sig, Monoid sig) => Transform sig take :: Transform sig => T -> sig -> sig drop :: Transform sig => T -> sig -> sig splitAt :: Transform sig => T -> sig -> (sig, sig) instance Foreign.Storable.Storable y => Synthesizer.ChunkySize.Cut.Transform (Data.StorableVector.Lazy.Vector y) instance Synthesizer.ChunkySize.Cut.Transform [y] instance Synthesizer.ChunkySize.Cut.Transform (Synthesizer.State.Signal.T y) instance Foreign.Storable.Storable y => Synthesizer.ChunkySize.Cut.Read (Data.StorableVector.Lazy.Vector y) instance Synthesizer.ChunkySize.Cut.Read [y] instance Synthesizer.ChunkySize.Cut.Read (Synthesizer.State.Signal.T y) module Synthesizer.ChunkySize.Signal class (Write sig y, Transform (sig y)) => Write sig y unfoldRN :: Write sig y => T -> (s -> Maybe (y, s)) -> s -> sig y replicate :: Write sig y => T -> y -> sig y iterateN :: Write sig y => (y -> y) -> T -> y -> sig y fromState :: Write sig y => T -> T y -> sig y instance Foreign.Storable.Storable y => Synthesizer.ChunkySize.Signal.Write Data.StorableVector.Lazy.Vector y instance Synthesizer.ChunkySize.Signal.Write [] y instance Synthesizer.ChunkySize.Signal.Write Synthesizer.State.Signal.T y -- | Processes that use only the current and past data. Essentially this is -- a data type for the crochetL function. module Synthesizer.Causal.Process -- | Cf. StreamFusion T data T a b Cons :: !a -> StateT s Maybe b -> !s -> T a b fromStateMaybe :: (a -> StateT s Maybe b) -> s -> T a b fromState :: (a -> State s b) -> s -> T a b fromSimpleModifier :: Simple s ctrl a b -> T (ctrl, a) b fromInitializedModifier :: Initialized s init ctrl a b -> init -> T (ctrl, a) b id :: T a a map :: (a -> b) -> T a b -- | Send the first component of the input through the argument arrow, and -- copy the rest unchanged to the output. first :: Arrow a => a b c -> a (b, d) (c, d) -- | A mirror image of first. -- -- The default definition may be overridden with a more efficient version -- if desired. second :: Arrow a => a b c -> a (d, b) (d, c) compose :: T a b -> T b c -> T a c split :: T a b -> T c d -> T (a, c) (b, d) fanout :: T a b -> T a c -> T a (b, c) loop :: ArrowLoop a => a (b, d) (c, d) -> a b c apply :: (Transform sig a, Transform sig b) => T a b -> sig a -> sig b -- | I think this function does too much. Better use feedFst and -- (>>>). applyFst :: Read sig a => T (a, b) c -> sig a -> T b c -- | I think this function does too much. Better use feedSnd and -- (>>>). applySnd :: Read sig b => T (a, b) c -> sig b -> T a c applySameType :: Transform sig a => T a a -> sig a -> sig a -- | applyConst c x == apply c (repeat x) applyConst :: T a b -> a -> T b apply2 :: (Read sig a, Transform sig b, Transform sig c) => T (a, b) c -> sig a -> sig b -> sig c apply3 :: (Read sig a, Read sig b, Transform sig c, Transform sig d) => T (a, b, c) d -> sig a -> sig b -> sig c -> sig d applyStorableChunk :: (Storable a, Storable b) => T a b -> T (Vector a) (Vector b) feed :: Read sig a => sig a -> T () a feedFst :: Read sig a => sig a -> T b (a, b) feedSnd :: Read sig a => sig a -> T b (b, a) feedGenericFst :: Read sig a => sig a -> T b (a, b) feedGenericSnd :: Read sig a => sig a -> T b (b, a) feedConstFst :: a -> T b (a, b) feedConstSnd :: a -> T b (b, a) crochetL :: (x -> acc -> Maybe (y, acc)) -> acc -> T x y mapAccumL :: (x -> acc -> (y, acc)) -> acc -> T x y scanL :: (acc -> x -> acc) -> acc -> T x acc scanL1 :: (x -> x -> x) -> T x x zipWith :: Read sig a => (a -> b -> c) -> sig a -> T b c -- | Prepend an element to a signal, but keep the signal length, i.e. drop -- the last element. consInit :: x -> T x x chainControlled :: [T (c, x) x] -> T (c, x) x -- | If T would be the function type -> then -- replicateControlled 3 f computes (c,x) -> f(c, f(c, -- f(c, x))). replicateControlled :: Int -> T (c, x) x -> T (c, x) x feedback :: T (a, c) b -> T b c -> T a b feedbackControlled :: T ((ctrl, a), c) b -> T (ctrl, b) c -> T (ctrl, a) b -- | I think this function does too much. Better use feedFst and -- (>>>). applyFst' :: Read sig a => T (a, b) c -> sig a -> T b c -- | I think this function does too much. Better use feedSnd and -- (>>>). applySnd' :: Read sig b => T (a, b) c -> sig b -> T a c instance Control.Category.Category Synthesizer.Causal.Process.T instance Control.Arrow.Arrow Synthesizer.Causal.Process.T instance Control.Arrow.ArrowLoop Synthesizer.Causal.Process.T instance Synthesizer.Causal.Class.C Synthesizer.Causal.Process.T instance GHC.Base.Functor (Synthesizer.Causal.Process.T a) instance GHC.Base.Applicative (Synthesizer.Causal.Process.T a) instance Algebra.Additive.C b => Algebra.Additive.C (Synthesizer.Causal.Process.T a b) instance Algebra.Ring.C b => Algebra.Ring.C (Synthesizer.Causal.Process.T a b) instance Algebra.Field.C b => Algebra.Field.C (Synthesizer.Causal.Process.T a b) instance GHC.Num.Num b => GHC.Num.Num (Synthesizer.Causal.Process.T a b) instance GHC.Real.Fractional b => GHC.Real.Fractional (Synthesizer.Causal.Process.T a b) -- | Filter operators from calculus module Synthesizer.State.Filter.Recursive.Integration -- | Integrate with initial value zero. However the first emitted value is -- the value of the input signal. It maintains the length of the signal. run :: C v => T v -> T v -- | Integrate with initial condition. First emitted value is the initial -- condition. The signal become one element longer. runInit :: C v => v -> T v -> T v causal :: C v => T v v -- | Integrate with initial condition. First emitted value is the initial -- condition. The signal become one element longer. causalInit :: C v => v -> T v v module Synthesizer.State.Filter.Recursive.MovingAverage -- | Like sums but in a recursive form. This needs only linear time -- (independent of the window size) but may accumulate rounding errors. -- --
--   ys = xs * (1,0,0,0,-1) / (1,-1)
--   ys * (1,-1) = xs * (1,0,0,0,-1)
--   ys = xs * (1,0,0,0,-1) + ys * (0,1)
--   
sumsStaticInt :: C v => Int -> T v -> T v modulatedFrac :: (C a, C a v) => Int -> T a -> T v -> T v -- | All recursive filters with real coefficients can be decomposed into -- first order and second order filters with real coefficients. This -- follows from the Fundamental theorem of algebra. module Synthesizer.Plain.Filter.Recursive.SecondOrder -- | Parameters for a general recursive filter of 2nd order. data Parameter a Parameter :: !a -> Parameter a [c0, c1, c2, d1, d2] :: Parameter a -> !a data State a State :: !a -> State a [u1, u2, y1, y2] :: State a -> !a -- | Given a function which computes the filter parameters of a lowpass -- filter for a given frequency, turn that into a function which -- generates highpass parameters, if requested filter type is Highpass. adjustPassband :: C a => Passband -> (a -> Parameter a) -> a -> Parameter a -- | Change filter parameter such that result is amplified by a given -- factor. amplify :: C a => a -> Parameter a -> Parameter a causal :: (C a, C a v) => T (Parameter a, v) v modifier :: (C a, C a v) => Simple (State v) (Parameter a) v v modifierInit :: (C a, C a v) => Initialized (State v) (State v) (Parameter a) v v run :: (C a, C a v) => T (Parameter a) -> T v -> T v runInit :: (C a, C a v) => State v -> T (Parameter a) -> T v -> T v step :: (C a, C a v) => Parameter a -> v -> State (State v) v zeroState :: C a => State a instance GHC.Show.Show a => GHC.Show.Show (Synthesizer.Plain.Filter.Recursive.SecondOrder.Parameter a) instance GHC.Show.Show a => GHC.Show.Show (Synthesizer.Plain.Filter.Recursive.SecondOrder.State a) instance GHC.Base.Functor Synthesizer.Plain.Filter.Recursive.SecondOrder.State instance GHC.Base.Applicative Synthesizer.Plain.Filter.Recursive.SecondOrder.State instance Data.Foldable.Foldable Synthesizer.Plain.Filter.Recursive.SecondOrder.State instance Data.Traversable.Traversable Synthesizer.Plain.Filter.Recursive.SecondOrder.State instance Foreign.Storable.Storable a => Foreign.Storable.Storable (Synthesizer.Plain.Filter.Recursive.SecondOrder.State a) instance GHC.Base.Functor Synthesizer.Plain.Filter.Recursive.SecondOrder.Parameter instance GHC.Base.Applicative Synthesizer.Plain.Filter.Recursive.SecondOrder.Parameter instance Data.Foldable.Foldable Synthesizer.Plain.Filter.Recursive.SecondOrder.Parameter instance Data.Traversable.Traversable Synthesizer.Plain.Filter.Recursive.SecondOrder.Parameter instance Synthesizer.Interpolation.Class.C a v => Synthesizer.Interpolation.Class.C a (Synthesizer.Plain.Filter.Recursive.SecondOrder.Parameter v) instance Foreign.Storable.Storable a => Foreign.Storable.Storable (Synthesizer.Plain.Filter.Recursive.SecondOrder.Parameter a) -- | State variable filter. One filter that generates lowpass, bandpass, -- highpass, bandlimit at once. module Synthesizer.Plain.Filter.Recursive.Universal data Parameter a Parameter :: !a -> Parameter a [k1, k2, ampIn, ampI1, ampI2, ampLimit] :: Parameter a -> !a data Result a Result :: !a -> Result a [highpass, bandpass, lowpass, bandlimit] :: Result a -> !a type State v = (v, v) causal :: (C a, C a v) => T (Parameter a, v) (Result v) modifier :: (C a, C a v) => Simple (State v) (Parameter a) v (Result v) modifierInit :: (C a, C a v) => Initialized (State v) (v, v) (Parameter a) v (Result v) -- | The computation of the internal parameters is a bit complicated, but -- it fulfills the following properties: -- -- parameter :: C a => Pole a -> Parameter a -- | Convert parameters of universal filter to general second order filter -- parameters. Filtering with these parameters does not yield exactly the -- same result since the initial conditions are different. parameterToSecondOrderLowpass :: C a => Parameter a -> Parameter a run :: (C a, C a v) => T (Parameter a) -> T v -> T (Result v) runInit :: (C a, C a v) => (v, v) -> T (Parameter a) -> T v -> T (Result v) -- | Universal filter: Computes high pass, band pass, low pass in one go step :: (C a, C a v) => Parameter a -> v -> State (State v) (Result v) -- | The computation of the internal parameters is a bit complicated, but -- it fulfills the following properties: -- -- parameterAlt :: C a => Pole a -> Parameter a -- | The computation of the internal parameters is a bit complicated, but -- it fulfills the following properties: -- -- parameterOld :: C a => Pole a -> Parameter a instance GHC.Base.Functor Synthesizer.Plain.Filter.Recursive.Universal.Result instance GHC.Base.Applicative Synthesizer.Plain.Filter.Recursive.Universal.Result instance Data.Foldable.Foldable Synthesizer.Plain.Filter.Recursive.Universal.Result instance Data.Traversable.Traversable Synthesizer.Plain.Filter.Recursive.Universal.Result instance Algebra.Additive.C v => Algebra.Additive.C (Synthesizer.Plain.Filter.Recursive.Universal.Result v) instance Algebra.Module.C a v => Algebra.Module.C a (Synthesizer.Plain.Filter.Recursive.Universal.Result v) instance Foreign.Storable.Storable a => Foreign.Storable.Storable (Synthesizer.Plain.Filter.Recursive.Universal.Result a) instance GHC.Base.Functor Synthesizer.Plain.Filter.Recursive.Universal.Parameter instance GHC.Base.Applicative Synthesizer.Plain.Filter.Recursive.Universal.Parameter instance Data.Foldable.Foldable Synthesizer.Plain.Filter.Recursive.Universal.Parameter instance Data.Traversable.Traversable Synthesizer.Plain.Filter.Recursive.Universal.Parameter instance Synthesizer.Interpolation.Class.C a v => Synthesizer.Interpolation.Class.C a (Synthesizer.Plain.Filter.Recursive.Universal.Parameter v) instance Foreign.Storable.Storable a => Foreign.Storable.Storable (Synthesizer.Plain.Filter.Recursive.Universal.Parameter a) -- | All recursive filters with real coefficients can be decomposed into -- first order and second order filters with real coefficients. This -- follows from the Fundamental theorem of algebra. -- -- This implements a cascade of second order filters using -- StorableVectors for state and filter parameters. module Synthesizer.Plain.Filter.Recursive.SecondOrderCascade newtype Parameter a Parameter :: Vector (Parameter a) -> Parameter a type State a = Vector (State a) step :: (C a, C a v, Storable a, Storable v) => Parameter a -> v -> State (State v) v modifierInit :: (C a, C a v, Storable a, Storable v) => Initialized (State v) (State v) (Parameter a) v v modifier :: (C a, C a v, Storable a, Storable v) => Int -> Simple (State v) (Parameter a) v v causal :: (C a, C a v, Storable a, Storable v) => Int -> T (Parameter a, v) v instance (Synthesizer.Interpolation.Class.C a v, Foreign.Storable.Storable v) => Synthesizer.Interpolation.Class.C a (Synthesizer.Plain.Filter.Recursive.SecondOrderCascade.Parameter v) -- | First order lowpass and highpass with complex valued feedback. The -- complex feedback allows resonance. It is often called complex -- resonator. module Synthesizer.Plain.Filter.Recursive.FirstOrderComplex data Parameter a -- | The internal parameters are computed such that: -- -- parameter :: C a => Pole a -> Parameter a -- | The internal parameters are computed such that: -- -- parameterFromPeakWidth :: C a => a -> Pole a -> Parameter a -- | The internal parameters are computed such that: -- -- parameterFromPeakToDCRatio :: C a => Pole a -> Parameter a -- | Universal filter: Computes high pass, band pass, low pass in one go step :: C a v => Parameter a -> v -> State (T v) (Result v) modifierInit :: (C a, C a v) => Initialized (T v) (T v) (Parameter a) v (Result v) modifier :: (C a, C a v) => Simple (T v) (Parameter a) v (Result v) causal :: (C a, C a v) => T (Parameter a, v) (Result v) runInit :: (C a, C a v) => T v -> T (Parameter a) -> T v -> T (Result v) run :: (C a, C a v) => T (Parameter a) -> T v -> T (Result v) instance GHC.Show.Show a => GHC.Show.Show (Synthesizer.Plain.Filter.Recursive.FirstOrderComplex.Parameter a) instance Synthesizer.Interpolation.Class.C a v => Synthesizer.Interpolation.Class.C a (Synthesizer.Plain.Filter.Recursive.FirstOrderComplex.Parameter v) -- | First order low pass and high pass filter. module Synthesizer.Plain.Filter.Recursive.FirstOrder newtype Parameter a Parameter :: a -> Parameter a [getParameter] :: Parameter a -> a -- | Convert cut-off frequency to feedback factor. parameter :: C a => a -> Parameter a lowpassStep :: (C a, C a v) => Parameter a -> v -> State v v lowpassModifierInit :: (C a, C a v) => Initialized v v (Parameter a) v v lowpassModifier :: (C a, C a v) => Simple v (Parameter a) v v lowpassCausal :: (C a, C a v) => T (Parameter a, v) v lowpassInit :: (C a, C a v) => v -> T (Parameter a) -> T v -> T v lowpass :: (C a, C a v) => T (Parameter a) -> T v -> T v highpassStep :: (C a, C a v) => Parameter a -> v -> State v v highpassModifierInit :: (C a, C a v) => Initialized v v (Parameter a) v v highpassModifier :: (C a, C a v) => Simple v (Parameter a) v v highpassInit :: (C a, C a v) => v -> T (Parameter a) -> T v -> T v highpassInitAlt :: (C a, C a v) => v -> T (Parameter a) -> T v -> T v highpass :: (C a, C a v) => T (Parameter a) -> T v -> T v data Result a Result :: !a -> Result a [highpass_, lowpass_] :: Result a -> !a step :: C a v => Parameter a -> v -> State v (Result v) modifierInit :: C a v => Initialized v v (Parameter a) v (Result v) modifier :: C a v => Simple v (Parameter a) v (Result v) causal :: C a v => T (Parameter a, v) (Result v) causalInit :: C a v => v -> T (Parameter a, v) (Result v) instance GHC.Show.Show a => GHC.Show.Show (Synthesizer.Plain.Filter.Recursive.FirstOrder.Parameter a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Synthesizer.Plain.Filter.Recursive.FirstOrder.Parameter a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Synthesizer.Plain.Filter.Recursive.FirstOrder.Result a) instance GHC.Base.Functor Synthesizer.Plain.Filter.Recursive.FirstOrder.Result instance GHC.Base.Applicative Synthesizer.Plain.Filter.Recursive.FirstOrder.Result instance Data.Foldable.Foldable Synthesizer.Plain.Filter.Recursive.FirstOrder.Result instance Data.Traversable.Traversable Synthesizer.Plain.Filter.Recursive.FirstOrder.Result instance Algebra.Additive.C v => Algebra.Additive.C (Synthesizer.Plain.Filter.Recursive.FirstOrder.Result v) instance Algebra.Module.C a v => Algebra.Module.C a (Synthesizer.Plain.Filter.Recursive.FirstOrder.Result v) instance Foreign.Storable.Storable a => Foreign.Storable.Storable (Synthesizer.Plain.Filter.Recursive.FirstOrder.Result a) instance Test.QuickCheck.Arbitrary.Arbitrary a => Test.QuickCheck.Arbitrary.Arbitrary (Synthesizer.Plain.Filter.Recursive.FirstOrder.Result a) instance GHC.Base.Functor Synthesizer.Plain.Filter.Recursive.FirstOrder.Parameter instance GHC.Base.Applicative Synthesizer.Plain.Filter.Recursive.FirstOrder.Parameter instance Data.Foldable.Foldable Synthesizer.Plain.Filter.Recursive.FirstOrder.Parameter instance Data.Traversable.Traversable Synthesizer.Plain.Filter.Recursive.FirstOrder.Parameter instance Synthesizer.Interpolation.Class.C a v => Synthesizer.Interpolation.Class.C a (Synthesizer.Plain.Filter.Recursive.FirstOrder.Parameter v) instance Foreign.Storable.Storable a => Foreign.Storable.Storable (Synthesizer.Plain.Filter.Recursive.FirstOrder.Parameter a) instance Test.QuickCheck.Arbitrary.Arbitrary a => Test.QuickCheck.Arbitrary.Arbitrary (Synthesizer.Plain.Filter.Recursive.FirstOrder.Parameter a) -- | Comb filters, useful for emphasis of tones with harmonics and for -- repeated echos. module Synthesizer.State.Filter.Recursive.Comb -- | The most simple version of the Karplus-Strong algorithm which is -- suitable to simulate a plucked string. It is similar to the -- runProc function. karplusStrong :: (C a, C a v) => Parameter a -> T v -> T v -- | Infinitely many equi-delayed exponentially decaying echos. The echos -- are clipped to the input length. We think it is easier (and simpler to -- do efficiently) to pad the input with zeros or whatever instead of -- cutting the result according to the input length. run :: C a v => Int -> a -> T v -> T v -- | Echos of different delays. runMulti :: (C a, C a v) => [Int] -> a -> T v -> T v -- | Echos can be piped through an arbitrary signal processor. runProc :: C v => Int -> (T v -> T v) -> T v -> T v -- | Moog cascade lowpass with resonance. module Synthesizer.Plain.Filter.Recursive.Moog data Parameter a Parameter :: !a -> !Parameter a -> Parameter a -- | Feedback of the lowpass cascade [feedback] :: Parameter a -> !a -- | Feedback of each of the lowpasses of 1st order [lowpassParam] :: Parameter a -> !Parameter a parameter :: C a => Int -> Pole a -> Parameter a type State = [] -- | Choose one of the implementations below lowpass :: (C a, C a v) => Int -> T (Parameter a) -> T v -> T v lowpassModifier :: (C a, C a v) => Int -> Simple (State v) (Parameter a) v v lowpassCausal :: (C a, C a v) => Int -> T (Parameter a, v) v instance GHC.Show.Show a => GHC.Show.Show (Synthesizer.Plain.Filter.Recursive.Moog.Parameter a) instance GHC.Base.Functor Synthesizer.Plain.Filter.Recursive.Moog.Parameter instance GHC.Base.Applicative Synthesizer.Plain.Filter.Recursive.Moog.Parameter instance Data.Foldable.Foldable Synthesizer.Plain.Filter.Recursive.Moog.Parameter instance Data.Traversable.Traversable Synthesizer.Plain.Filter.Recursive.Moog.Parameter instance Synthesizer.Interpolation.Class.C a v => Synthesizer.Interpolation.Class.C a (Synthesizer.Plain.Filter.Recursive.Moog.Parameter v) -- | Comb filters, useful for emphasis of tones with harmonics and for -- repeated echos. module Synthesizer.Plain.Filter.Recursive.Comb -- | The most simple version of the Karplus-Strong algorithm which is -- suitable to simulate a plucked string. It is similar to the -- runProc function. karplusStrong :: (C a, C a v) => Parameter a -> T v -> T v -- | Infinitely many equi-delayed exponentially decaying echos. The echos -- are clipped to the input length. We think it is easier (and simpler to -- do efficiently) to pad the input with zeros or whatever instead of -- cutting the result according to the input length. run :: C a v => Int -> a -> T v -> T v -- | Echos of different delays. runMulti :: (C a, C a v) => [Int] -> a -> T v -> T v -- | Echos can be piped through an arbitrary signal processor. runProc :: C v => Int -> (T v -> T v) -> T v -> T v -- | Comb filters, useful for emphasis of tones with harmonics and for -- repeated echos. module Synthesizer.Generic.Filter.Recursive.Comb -- | The most simple version of the Karplus-Strong algorithm which is -- suitable to simulate a plucked string. It is similar to the -- runProc function. karplusStrong :: (C t, C t y, Write sig y) => Parameter t -> sig y -> sig y -- | Infinitely many equi-delayed exponentially decaying echos. The echos -- are clipped to the input length. We think it is easier (and simpler to -- do efficiently) to pad the input with zeros or whatever instead of -- cutting the result according to the input length. run :: (C t y, Write sig y) => Int -> t -> sig y -> sig y -- | Echos of different delays. Chunk size must be smaller than all of the -- delay times. runMulti :: (C t y, Write sig y) => [Int] -> t -> sig y -> sig y -- | Echos can be piped through an arbitrary signal processor. runProc :: (C y, Write sig y) => Int -> (sig y -> sig y) -> sig y -> sig y -- | Chebyshev lowpass and highpass module Synthesizer.Plain.Filter.Recursive.Chebyshev type ParameterA a = (a, Parameter a) parameterA :: (C a, Storable a) => Passband -> Int -> Pole a -> ParameterA a partialParameterA :: C a => Passband -> Int -> a -> T a -> a -> Parameter a type ParameterB a = Parameter a parameterB :: (C a, Storable a) => Passband -> Int -> Pole a -> ParameterB a partialParameterB :: C a => Passband -> Int -> a -> T a -> a -> Parameter a canonicalizeParameterA :: (C a, Storable a) => ParameterA a -> Parameter a causalA :: (C a, C a v, Storable a, Storable v) => Int -> T (ParameterA a, v) v runAPole :: (C a, C a v) => Passband -> Int -> T a -> T a -> T v -> T v causalAPole :: (C a, C a v) => Passband -> Int -> T (Pole a, v) v causalB :: (C a, C a v, Storable a, Storable v) => Int -> T (ParameterB a, v) v runBPole :: (C a, C a v) => Passband -> Int -> T a -> T a -> T v -> T v causalBPole :: (C a, C a v) => Passband -> Int -> T (Pole a, v) v lowpassACausalPole :: (C a, C a v) => Int -> T (Pole a, v) v highpassACausalPole :: (C a, C a v) => Int -> T (Pole a, v) v lowpassBCausalPole :: (C a, C a v) => Int -> T (Pole a, v) v highpassBCausalPole :: (C a, C a v) => Int -> T (Pole a, v) v lowpassAPole :: (C a, C a v) => Int -> T a -> T a -> T v -> T v highpassAPole :: (C a, C a v) => Int -> T a -> T a -> T v -> T v lowpassBPole :: (C a, C a v) => Int -> T a -> T a -> T v -> T v highpassBPole :: (C a, C a v) => Int -> T a -> T a -> T v -> T v makeCirclePoints :: C a => Int -> [T a] -- | Butterworth lowpass and highpass module Synthesizer.Plain.Filter.Recursive.Butterworth type Parameter a = Parameter a causal :: (C a, C a v, Storable a, Storable v) => Int -> T (Parameter a, v) v causalPole :: (C a, C a v) => Passband -> Int -> T (Pole a, v) v highpassCausalPole :: (C a, C a v) => Int -> T (Pole a, v) v highpassPole :: (C a, C a v) => Int -> T a -> T a -> T v -> T v lowpassCausalPole :: (C a, C a v) => Int -> T (Pole a, v) v lowpassPole :: (C a, C a v) => Int -> T a -> T a -> T v -> T v modifier :: (C a, C a v, Storable a, Storable v) => Int -> Simple (State v) (Parameter a) v v parameter :: (C a, Storable a) => Passband -> Int -> Pole a -> Parameter a partialParameter :: C a => Passband -> a -> a -> a -> Parameter a -- | When called as runPole kind order ratio freqs, the filter -- amplifies frequency 0 with factor 1 and frequency freq with -- factor ratio. -- -- It uses the frequency and ratio information directly and thus cannot -- benefit from efficient parameter interpolation (asynchronous run of a -- ControlledProcess). runPole :: (C a, C a v) => Passband -> Int -> T a -> T a -> T v -> T v checkedHalf :: String -> Int -> Int partialRatio :: C a => Int -> a -> a makeSines :: C a => Int -> [a] module Synthesizer.Plain.Filter.Recursive.Allpass newtype Parameter a -- | Feedback factor. Parameter :: a -> Parameter a [getParameter] :: Parameter a -> a type State v = (v, v) -- | Choose one of the implementations below cascade :: (C a, C a v) => Int -> T (Parameter a) -> T v -> T v cascadeCausal :: (C a, C a v) => Int -> T (Parameter a, v) v cascadeModifier :: (C a, C a v) => Int -> Simple [v] (Parameter a) v v cascadeParameter :: C a => Int -> a -> a -> Parameter a cascadeStep :: (C a, C a v) => Parameter a -> v -> State [v] v cascadeDiverseStep :: (C a, C a v) => [Parameter a] -> v -> State [v] v firstOrder :: (C a, C a v) => T (Parameter a) -> T v -> T v firstOrderCausal :: (C a, C a v) => T (Parameter a, v) v firstOrderModifier :: (C a, C a v) => Simple (State v) (Parameter a) v v firstOrderStep :: (C a, C a v) => Parameter a -> v -> State (State v) v flangerParameter :: C a => Int -> a -> Parameter a flangerPhase :: C a => a -- | Compute phase shift of an allpass at a given frequency. makePhase :: (C a, C a) => Parameter a -> a -> a -- | Compute the filter parameter such that a given phase shift is achieved -- at a certain frequency. -- -- Both frequency and phase are with respect to unit 1. This is conform -- to Phase definition and allows to avoid Transcendental constraint in -- some cases since we need no factor 2*pi. See for instance -- parameterApprox. However, it is intended that the phase -- parameter is not of type Phase, because for the -- cascadeParameter we divide by the cascade order and then there -- is a difference between phase pi and 3*pi. parameter :: C a => a -> a -> Parameter a -- | An approximation to parameter for small phase and frequency -- values. It needs only field operations due to our choice of the unit 1 -- for the phase parameter. parameterApprox :: C a => a -> a -> Parameter a -- | This is the same as parameter, but for phase = -- frequency it has a division of a zero by a zero of multiplicity -- 2, whereas parameter has a division of a non-zero number by -- zero. Thus parameter suffers less from cancellation if -- phase is close to frequency. parameterAlt :: C a => a -> a -> Parameter a -- | Simulate the Allpass cascade by a list of states of the partial -- allpasses cascadeState :: (C a, C a v) => Int -> T (Parameter a) -> T v -> T v -- | Directly implement the allpass cascade as multiple application of -- allpasses of 1st order cascadeIterative :: (C a, C a v) => Int -> T (Parameter a) -> T v -> T v cascadeStepRec :: (C a, C a v) => Parameter a -> v -> State [v] v cascadeStepScanl :: (C a, C a v) => Parameter a -> v -> State [v] v cascadeStepStack :: (C a, C a v) => Parameter a -> v -> State [v] v cascadeCausalModifier :: (C a, C a v) => Int -> T (Parameter a, v) v cascadeCausalStacked :: (C a, C a v) => Int -> T (Parameter a, v) v instance GHC.Show.Show a => GHC.Show.Show (Synthesizer.Plain.Filter.Recursive.Allpass.Parameter a) instance GHC.Base.Functor Synthesizer.Plain.Filter.Recursive.Allpass.Parameter instance GHC.Base.Applicative Synthesizer.Plain.Filter.Recursive.Allpass.Parameter instance Data.Foldable.Foldable Synthesizer.Plain.Filter.Recursive.Allpass.Parameter instance Data.Traversable.Traversable Synthesizer.Plain.Filter.Recursive.Allpass.Parameter instance Synthesizer.Interpolation.Class.C a v => Synthesizer.Interpolation.Class.C a (Synthesizer.Plain.Filter.Recursive.Allpass.Parameter v) instance Foreign.Storable.Storable a => Foreign.Storable.Storable (Synthesizer.Plain.Filter.Recursive.Allpass.Parameter a) -- | Basics for building tone generators. They generate signals of phases -- and these signals can be converted to arbitrary waveforms by mapping -- them via Wave objects. This is also the fundament for -- dimensional oscillators. module Synthesizer.Causal.Oscillator.Core static :: C a => T a -> a -> T (T a) -- | oscillator with modulated phase phaseMod :: C a => a -> T a (T a) -- | oscillator with modulated shape shapeMod :: C a => T a -> a -> T c (c, T a) -- | 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. freqMod :: C a => T a -> T a (T a) -- | Like freqMod but the first element is omitted. freqModSync :: C a => T a -> T a (T a) -- | oscillator with modulated frequency freqModAntiAlias :: C a => T a -> T a (a, T a) -- | oscillator with both phase and frequency modulation phaseFreqMod :: C a => T (a, a) (T a) -- | oscillator with both shape and frequency modulation shapeFreqMod :: C a => T a -> T (c, a) (c, T a) module Synthesizer.State.ToneModulation type Cell sig y = T (sig y) makeCell :: Transform sig y => Int -> sig y -> Cell sig y -- | cells are organised in a transposed style, when compared with -- Plain.ToneModulation interpolateCell :: Read sig y => T a y -> T b y -> (a, b) -> Cell sig y -> y data Prototype sig a 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) -- | This function should not be used, since it requires recomputation of -- shapes and freqs lists. -- | Deprecated: This function recomputes the shape and phase signals. -- Better use Causal.ToneModulation.oscillatorCells 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 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) module Synthesizer.Generic.Wave sample :: (C a, Transform sig v) => T a v -> sig v -> T a v -- | Interpolate first within waves and then across waves, which is simpler -- but maybe less efficient for lists. However for types with fast -- indexing/drop like StorableVector this is optimal. sampledTone :: (C a, Transform sig v) => T a v -> T a v -> a -> sig v -> a -> T a v module Synthesizer.Causal.ToneModulation -- | cells are organised in a transposed style, when compared with -- Plain.ToneModulation interpolateCell :: Read sig y => T a y -> T b y -> (a, b) -> Cell sig y -> y seekCell :: (C t, Transform sig y) => Int -> t -> ((t, T t), sig y) -> ((t, t), Cell sig y) oscillatorCells :: (C t, Transform sig y) => Margin -> Margin -> Int -> t -> sig y -> (t, T t) -> T (t, t) ((t, t), Cell sig y) -- | In contrast to the counterpart of this function for plain lists, it -- does not use sophisticated list transposition tricks, but seeks -- through the prototype signal using drop. Since drop is -- used in an inner loop, it must be fast. This is true for -- StorableVectors. oscillatorSuffixes :: (C t, Transform sig y) => Margin -> Margin -> Int -> t -> sig y -> (t, T t) -> T (t, t) ((t, T t), sig y) integrateFractional :: C t => t -> (t, T t) -> (Skip t, T (t, t) (Skip t)) -- | Delays output by one element and shorten it by one element at the end. integrateFractionalClip :: C t => t -> (t, T t) -> T (t, t) (Skip t) limitRelativeShapes :: (C t, Ord t) => Margin -> Margin -> Int -> t -> (t, T t t) limitMinRelativeValues :: (C t, Ord t) => t -> t -> (t, T t t) -- | Filter operators from calculus module Synthesizer.Causal.Filter.Recursive.Integration -- | Integrate with initial value zero. However the first emitted value is -- the value of the input signal. It maintains the length of the signal. run :: C v => T v v -- | Integrate with initial condition. First emitted value is the initial -- condition. The signal becomes one element longer. runInit :: C v => v -> T v v module Synthesizer.Causal.Cut take :: Int -> T a a module Synthesizer.Causal.Analysis flipFlopHysteresis :: Ord y => (y, y) -> BinaryLevel -> T y BinaryLevel deltaSigmaModulation :: C y => T y BinaryLevel deltaSigmaModulationPositive :: C y => T (y, y) y movingMedian :: Ord a => Int -> T a a module Synthesizer.Causal.Arrow class Arrow arrow => C arrow apply :: (C arrow, Transform sig a, Transform sig b) => arrow a b -> sig a -> sig b instance Synthesizer.Causal.Arrow.C Synthesizer.Causal.Process.T instance Synthesizer.Causal.Arrow.C (->) -- | Rendering sound effects off-line has its virtue, but really cool is -- real-time signal generation. For a long time I thought that it is the -- compiler's responsibility to make list based signal processing fast -- enough. However, the compiler has to respect correctness first. That -- is, it cannot do too fancy optimization, since the optimized program -- must still do the same as the unoptimized program. So, when we write -- functions that rely on the maximal flexibility, the compiler cannot -- turn it to something less flexible. Actually, a list as in -- Synthesizer.Plain.Signal is the best representation of a signal -- in terms of flexibility: It allows free choice of the element type, -- even functions, it is element-wise lazy, allowing for short feedback, -- it allows sharing of computed data. The drawback is, that it is slow -- and memory inefficient. In most cases we don't need this full -- flexibility, but the compiler has no chance to find this out -- automatically. It can merge several operations on a list to a single -- operation by the fusion technique, however even a single list -- operation is hard to perform in real-time. -- -- How do real-time software synthesizer achieve real-time performance? -- They get the popular fast inner loops by processing signals in chunks -- of raw data. This way, they lose flexibility, because they cannot do -- quick feedback. We can do the same in Haskell, getting the same -- restrictions. Additionally, in order to store raw data we must -- restrict the element types e.g. to the Storable class, since -- we use StorableVector in Synthesizer.Storable.Signal. -- With this technique single signal operations are fast, but their -- combination cannot be optimized in many cases. This is so, again, -- because top priority in optimization is correctness. Consider mix -- x (cons 0 x) where cons 0 x means 0:x for our -- chunky signal data. This expression is a perfect candidate for -- optimization. But in this case it must not be applied since the chunk -- structures of x and cons 0 x do not match. In such -- cases we would not gain anything over SuperCollider and CSound. -- -- Remember that we introduced the chunky signal representation entirely -- because of efficiency concerns. Actually we are not interested in a -- special chunk structure, so this should not be a reason for disabling -- optimization. Of course, we could ignore the correctness and write -- incorrect optimizer rules that are based on correct ideas. However, -- experience shows that wrong optimization leads to surprise and -- infelicities sooner or later. The later the worse, because the later -- the more code you have written relying on invalid optimization. -- -- What we can try is to use list representation, enjoy the optimization -- that GHC already provides for it, and then let fusion rules jump in -- that make lists disappear when they are used in connection with chunky -- sequences. E.g. Chunky.fromList (List.oscillator freq) could -- be turned into Chunky.oscillator freq. This approach would be -- really cool, but works only in theory. In practice it is hard to -- predict how GHC transforms various operations. Additionally to -- optimizer rule application it also expands functions to their -- definitions (known as inlining/unfolding) or specializes functions to -- fixed types. We cannot rely on our optimizer rules being actually -- applied. This means however, that in unpredictable cases the -- optimization fails and the efficiency drops from real-time to -- non-real-time. This is unacceptable. -- -- The solution is a third signal representation, see -- Synthesizer.State.Signal. (Already got tired?) It consists of -- no actual data but it is a function that generates elements. Its type -- is s -> Maybe (a,s) or short StateT s Maybe a. -- Given a state of type s it produces Nothing when the -- list terminates or Just the next element and the updated -- state. This can be easily converted from and to lists while preserving -- laziness. We convert to lists by List.unfoldr and from lists -- using viewL. Actually this signal representation is very -- close to the list representation used in the streams package. The main -- differences are: Firstly, we do not use a list storage that is fused -- away when only used temporarily. Thus we do not need a fusion rule -- (that could be skipped by the compiler). Secondly, we have no notion -- of Skip, since operations like filter are uncommon in -- signal processing. If we write our signal processing in terms of these -- virtual signals and then convert the result to regular lists or chunky -- sequences, then only one data structure will be built and GHC does -- it's best to generate efficient inner loops. -- -- We cannot use these virtual signals for sharing and feedback, because -- there is no data structure that stores the data. If we try to do so -- anyway, data will be recomputed. Thus we still need chunky sequences -- or lists for sharing of interim results and for feedback. Actually, an -- expression like mix x (reverse x) would definitely benefit -- from interim conversion to a chunky sequence, but for mix x (cons -- 0 x) this is overkill. -- -- In order to get processes like the last one efficient we have a new -- data type (no, not another one!) but this time it is not a signal data -- type but a signal processor type. It is the result of thinking about -- which processes allow sharing on a per-sample basis at all. We come to -- the conclusion that these can be only causal processes, i.e. processes -- that depend only on current and past data, not on data from the -- future. So, we already have a good name: -- Synthesizer.Causal.Process. Causal processes are -- Control.Arrows, however the higher level variant does no longer -- fit into the Arrow type class. This means that there are various -- combinations that turn causal processes into larger causal processes. -- It needs a bit experience in pointfree coding style in order to use -- the arrow combinators, but there is no way around it, when you want to -- use physical dimensions. GHC's arrow notation does only support types -- of the Arrow class. E.g. the expression mix x (cons 0 x) -- becomes Causal.mix <<< (Causal.id &&& -- Causal.cons 0). When you manage this burden you get processes -- that are warranted to be causal. They can not only be used to make -- something efficient, but they also allow to process data from the -- outside world in a streaming way without unsafeInterleaveIO -- as required e.g. in JACK plugins. -- -- We have now a pretty big set of signal storage types that differ -- considerably in performance but not in the set of operations. This -- calls for a type class! You find it in Synthesizer.Generic.Cut -- and Synthesizer.Generic.Signal. module Synthesizer.Storage module Synthesizer.Utility -- | If two values are equal, then return one of them, otherwise raise an -- error. common :: Eq a => String -> a -> a -> a fwrap :: C a => (a, a) -> a -> a fmod :: C a => a -> a -> a fmodAlt :: C a => a -> a -> a propFMod :: C a => a -> a -> Bool -- | This one should be more precise than affineCombAlt in floating -- computations whenever x1 is small and x0 is big. affineComb :: C t y => t -> (y, y) -> y affineCombAlt :: C t y => t -> (y, y) -> y balanceLevel :: C y => y -> [y] -> [y] randomRsBalanced :: (RandomGen g, Random y, C y) => g -> Int -> y -> y -> [y] -- | Plain interpolation functions. module Synthesizer.Interpolation.Core linear :: C a v => v -> v -> a -> v cubic :: (C a v, C a) => v -> v -> v -> v -> a -> v -- | The interpolators for module operations do not simply compute a -- straight linear combination of some vectors. Instead they add then -- scale, then add again, and so on. This is efficient whenever scaling -- and addition is cheap. In this case they might save multiplications. I -- can't say much about numeric cancellations, however. cubicAlt :: (C a v, C a) => v -> v -> v -> v -> a -> v -- | Special interpolations defined in terms of Module operations. module Synthesizer.Interpolation.Module -- | interpolation as needed for resampling data T t y -- | Consider the signal to be piecewise constant, where the leading value -- is used for filling the interval [0,1). constant :: T t y -- | Consider the signal to be piecewise linear. linear :: C t y => T t y -- | Consider the signal to be piecewise cubic, with smooth connections at -- the nodes. It uses a cubic curve which has node values x0 at 0 and x1 -- at 1 and derivatives (x1-xm1)2 and (x2-x0)2, respectively. You -- can see how it works if you evaluate the expression for t=0 and t=1 as -- well as the derivative at these points. cubic :: (C t, C t y) => T t y cubicAlt :: (C t, C t y) => T t y piecewise :: C t y => Int -> [t -> t] -> T t y piecewiseConstant :: C t y => T t y piecewiseLinear :: C t y => T t y piecewiseCubic :: (C t, C t y) => T t y -- | with this wrapper you can use the collection of interpolating -- functions from Donadio's DSP library function :: C t y => (Int, Int) -> (t -> t) -> T t y module Synthesizer.Plain.Interpolation -- | interpolation as needed for resampling data T t y func :: T t y -> t -> T y -> y offset :: T t y -> Int number :: T t y -> Int zeroPad :: C t => (T t y -> t -> T y -> a) -> y -> T t y -> t -> T y -> a constantPad :: C t => (T t y -> t -> T y -> a) -> T t y -> t -> T y -> a -- | Only for finite input signals. cyclicPad :: C t => (T t y -> t -> T y -> a) -> T t y -> t -> T y -> a -- | The extrapolation may miss some of the first and some of the last -- points extrapolationPad :: C t => (T t y -> t -> T y -> a) -> T t y -> t -> T y -> a single :: C t => T t y -> t -> T y -> y -- | All values of frequency control must be non-negative. multiRelative :: C t => T t y -> t -> T y -> T t -> T y multiRelativeZeroPad :: C t => y -> T t y -> t -> T t -> T y -> T y multiRelativeConstantPad :: C t => T t y -> t -> T t -> T y -> T y multiRelativeCyclicPad :: C t => T t y -> t -> T t -> T y -> T y -- | The extrapolation may miss some of the first and some of the last -- points multiRelativeExtrapolationPad :: C t => T t y -> t -> T t -> T y -> T y multiRelativeZeroPadConstant :: (C t, C y) => t -> T t -> T y -> T y multiRelativeZeroPadLinear :: (C t, C t y) => t -> T t -> T y -> T y multiRelativeZeroPadCubic :: (C t, C t y) => t -> T t -> T y -> T y -- | Consider the signal to be piecewise constant, where the leading value -- is used for filling the interval [0,1). constant :: T t y -- | Consider the signal to be piecewise linear. linear :: C t y => T t y -- | Consider the signal to be piecewise cubic, with smooth connections at -- the nodes. It uses a cubic curve which has node values x0 at 0 and x1 -- at 1 and derivatives (x1-xm1)2 and (x2-x0)2, respectively. You -- can see how it works if you evaluate the expression for t=0 and t=1 as -- well as the derivative at these points. cubic :: (C t, C t y) => T t y piecewise :: C t y => Int -> [t -> t] -> T t y -- | with this wrapper you can use the collection of interpolating -- functions from Donadio's DSP library function :: C t y => (Int, Int) -> (t -> t) -> T t y data Margin margin :: T t y -> Margin -- | alternative implementation of single singleRec :: (Ord t, C t) => T t y -> t -> T y -> y -- | 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. module Synthesizer.Plain.ToneModulation type Cell y = T (T y) interpolateCell :: T a y -> T b y -> (a, b) -> Cell y -> y data Prototype t y makePrototype :: C t => Margin -> Margin -> Int -> t -> T y -> Prototype t y sampledToneCell :: C t => Prototype t y -> t -> T t -> ((t, t), Cell y) oscillatorCells :: C t => Margin -> Margin -> Int -> t -> T y -> (t, T t) -> (T t, T t) -> T ((t, t), Cell y) seekCell :: C t => Int -> t -> ((t, T t), Cell y) -> ((t, t), Cell y) oscillatorSuffixes :: C t => Margin -> Margin -> Int -> t -> T y -> (t, T t) -> (T t, T t) -> T ((t, T t), Cell y) -- | 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 freqsToPhases :: C a => T a -> T a -> T (T a) dropFrac :: C i => i -> T a -> (Int, i, T a) dropRem :: Int -> T a -> (Int, T a) propDropFrac :: (C i, Eq a) => i -> T a -> Bool propDropRem :: Eq a => Int -> T a -> Bool oscillatorCoords :: C t => Int -> t -> (t, T t) -> (T t, T t) -> T (Coords t) integrateFractional :: C t => t -> (t, T t) -> (T t, T t) -> T (Skip t) limitRelativeShapes :: (C t, Ord t) => Margin -> Margin -> Int -> T y -> (t, T t) -> (t, T t) limitMinRelativeValues :: (C a, Ord a) => a -> a -> T a -> (a, T a) limitMaxRelativeValues :: (C a, Ord a) => a -> a -> T a -> (a, T a) -- | Avoids negative numbers and thus can be used with Chunky numbers. limitMaxRelativeValuesNonNeg :: (C a, Ord a) => a -> a -> T a -> (a, T a) module Synthesizer.Plain.Wave sample :: C a => T a v -> T v -> T a v -- | We assume that a tone was generated by a shape modulated oscillator. -- We try to reconstruct the wave function (with parameters shape control -- and phase) from a tone by interpolation. -- -- The unit for the shape control parameter is the sampling period. That -- is the shape parameter is a time parameter pointing to a momentary -- shape of the prototype signal. Of course this momentary shape does not -- exist and we can only guess it using interpolation. -- -- At the boundaries we repeat the outermost shapes that can be -- reconstructed entirely from interpolated data (that is, no -- extrapolation is needed). This way we cannot reproduce the shape at -- the boundaries because we have no data for cyclically extending it. On -- the other hand this method guarantees a nice wave shape with the -- required fractional period. -- -- It must be length tone >= Interpolation.number ipStep + -- Interpolation.number ipLeap * ceiling period. sampledTone :: C a => T a v -> T a v -> a -> T v -> a -> T a v -- | Tone generators -- -- Frequencies are always specified in ratios of the sample rate, e.g. -- the frequency 0.01 for the sample rate 44100 Hz means a physical -- frequency of 441 Hz. module Synthesizer.Plain.Oscillator type Phase a = a -- | oscillator with constant frequency static :: C a => T a b -> Phase a -> a -> T b -- | oscillator with modulated frequency freqMod :: C a => T a b -> Phase a -> T a -> T b -- | oscillator with modulated phase phaseMod :: C a => T a b -> a -> T (Phase a) -> T b -- | oscillator with modulated shape shapeMod :: C a => (c -> T a b) -> Phase a -> a -> T c -> T b -- | oscillator with both phase and frequency modulation phaseFreqMod :: C a => T a b -> T (Phase a) -> T a -> T b -- | oscillator with both shape and frequency modulation shapeFreqMod :: C a => (c -> T a b) -> Phase a -> T c -> T a -> T b -- | oscillator with a sampled waveform with constant frequency This is -- essentially an interpolation with cyclic padding. staticSample :: C a => T a b -> [b] -> Phase a -> a -> T b -- | oscillator with a sampled waveform with modulated frequency Should -- behave homogenously for different types of interpolation. freqModSample :: C a => T a b -> [b] -> Phase a -> T a -> T b -- | Shape control is a list of relative changes, each of which must be -- non-negative in order to allow lazy processing. '1' advances by one -- wave. Frequency control can be negative. If you want to use sampled -- waveforms as well then use sample in the list of waveforms. -- With sampled waves this function is identical to HunkTranspose in -- Assampler. -- -- Example: interpolate different versions of oddCosine and -- oddTriangle. -- -- You could also chop a tone into single waves and use the waves as -- input for this function but you certainly want to use -- sampledTone or shapeFreqModFromSampledTone instead, -- because in the wave information for shapeFreqModSample shape -- and phase are strictly separated. shapeFreqModSample :: (C c, C b) => T c (T b a) -> [T b a] -> c -> Phase b -> T c -> T b -> T a shapePhaseFreqModSample :: (C c, C b) => T c (T b a) -> [T b a] -> c -> T c -> T (Phase b) -> T b -> T a -- | Time stretching and frequency modulation of a pure tone. -- -- We consider a tone as the result of a shape modulated oscillator, and -- virtually reconstruct the waveform function (a function of time and -- phase) by interpolation and resample it. This way we can alter -- frequency and time progress of the tone independently. -- -- This function is identical to using shapeFreqMod with a wave -- function constructed by sampledTone but it consumes the sampled -- source tone lazily and thus allows only relative shape control with -- non-negative control steps. -- -- The function is similar to shapeFreqModSample but respects that -- in a sampled tone, phase and shape control advance synchronously. -- Actually we could re-use shapeFreqModSample with modified phase -- values. But we would have to cope with negative shape control jumps, -- and waves would be padded locally cyclically. The latter one is not -- wanted since we want padding according to the adjacencies in the -- source tone. Note that differently from shapeFreqModSample the -- shape control difference 1 does not mean to skip to the next -- wave, since this oscillator has no discrete waveforms. Instead -- 1 means that the shape alters as fast as in the prototype -- signal. -- -- Although the shape difference values must be non-negative I hesitate -- to give them the type Number.NonNegative.T t because then you -- cannot call this function with other types of non-negative numbers -- like T. -- -- The prototype tone signal is reproduced if freqs == repeat -- (1/period) and shapes == repeat 1. shapeFreqModFromSampledTone :: C t => T t y -> T t y -> t -> T y -> t -> t -> T t -> T t -> T y shapePhaseFreqModFromSampledTone :: C t => T t y -> T t y -> t -> T y -> t -> t -> T t -> T t -> T t -> T y -- | impulse train with static frequency staticImpulses :: C a => a -> a -> T a -- | impulse train with modulated frequency freqModImpulses :: C a => a -> T a -> T a -- | sine oscillator with static frequency staticSine :: (C a, C a) => a -> a -> T a -- | sine oscillator with modulated frequency freqModSine :: (C a, C a) => a -> T a -> T a -- | sine oscillator with modulated phase, useful for FM synthesis phaseModSine :: (C a, C a) => a -> T a -> T a -- | saw tooth oscillator with static frequency staticSaw :: C a => a -> a -> T a -- | saw tooth oscillator with modulated frequency freqModSaw :: C a => a -> T a -> T a -- | This module gives some introductory examples to signal processing with -- plain Haskell lists. For more complex examples see -- Synthesizer.Plain.Instrument and -- Synthesizer.Plain.Effect. The examples require a basic -- understanding of audio signal processing. -- -- In the Haddock documentation you will only see the API. In order to -- view the example code, please use the "Source code" links beside the -- function documentation. This requires however, that the Haddock was -- executed with hyperlink-source option. -- -- Using plain lists is not very fast, particularly not fast enough for -- serious real-time applications. It is however the most flexible data -- structure, which you can also use without knowledge of low level -- programming. For real-time applications see -- Synthesizer.Generic.Tutorial. -- | Deprecated: do not import that module, it is only intended for -- demonstration module Synthesizer.Plain.Tutorial -- | Play a simple sine tone at 44100 sample rate and 16 bit. These are the -- parameters used for compact disks. The period of the tone is -- 2*pi*10. Playing at sample rate 44100 Hz results in a tone of -- 44100 / (20*pi) Hz, that is about 702 Hz. This is -- simple enough to be performed in real-time, at least on my machine. -- For playback we use SoX. sine :: IO ExitCode -- | Now the same for a stereo signal. Both stereo channels are slightly -- detuned in order to achieve a stereophonic phasing effect. In -- principle there is no limit of the number of channels, but with more -- channels playback becomes difficult. Many signal processes in our -- package support any tuple and even nested tuples using the notion of -- an algebraic module (see C). A module is a vector -- space where the scalar numbers do not need to support division. A -- vector space is often also called a linear space, because all we -- require of vectors is that they can be added and scaled and these two -- operations fulfill some natural laws. sineStereo :: IO ExitCode -- | Of course we can also write a tone to disk using sox. writeSine :: IO ExitCode -- | For the following examples we will stick to monophonic sounds played -- at 44100 Hz. Thus we define a function for convenience. play :: T Double -> IO ExitCode -- | Now, let's repeat the sine example in a higher level style. We -- use the oscillator static that does not allow any modulation. -- We can however use any waveform. The waveform is essentially a -- function which maps from the phase to the displacement. Functional -- programming proves to be very useful here, since anonymous functions -- as waveforms are optimally supported by the language. We can also -- expect, that in compiled form the oscillator does not have to call -- back the waveform function by an expensive explicit function call, but -- that the compiler will inline both oscillator and waveform such that -- the oscillator is turned into a simple loop which handles both -- oscillation and waveform computation. -- -- Using the oscillator with sine also has the advantage that we -- do not have to cope with pis any longer. The frequency is given -- as ratio of the sample rate. That is, 0.01 at 44100 -- Hz sample rate means 441 Hz. This way all frequencies -- are given in the low-level signal processing. -- -- It is not optimal to handle frequencies this way, since all frequency -- values are bound to the sample rate. For overcoming this problem, see -- the high level routines using physical dimensions. For examples see -- Synthesizer.Dimensional.RateAmplitude.Demonstration. oscillator :: IO ExitCode -- | It is very simple to switch to another waveform like a saw tooth wave. -- Instead of a sharp saw tooth, we use an extreme asymmetric triangle. -- This is a poor man's band-limiting approach that shall reduce aliasing -- at high oscillation frequencies. We should really work on band-limited -- oscillators, but this is hard in the general case. saw :: IO ExitCode -- | When we apply a third power to each value of the saw tooths we get an -- oscillator with cubic polynomial functions as waveform. The distortion -- function applied to a saw wave can be used to turn every function on -- the interval [-1,1] into a waveform. cubic :: IO ExitCode -- | Now let's start with modulated tones. The first simple example is -- changing the degree of asymmetry according to a slow oscillator (LFO = -- low frequency oscillator). sawMorph :: IO ExitCode -- | It's also very common to modulate the frequency of a tone. laser :: IO ExitCode pingSig :: T Double -- | A simple sine wave with exponentially decaying amplitude. ping :: IO ExitCode -- | The ping sound can also be used to modulate the phase another -- oscillator. This is a well-known effect used excessively in FM -- synthesis, that was introduced by the Yamaha DX-7 synthesizer. fmPing :: IO ExitCode -- | One of the most impressive sounds effects is certainly frequency -- filtering, especially when the filter parameters are modulated. In -- this example we use a resonant lowpass whose resonance frequency is -- controlled by a slow sine wave. The frequency filters usually use -- internal filter parameters that are not very intuitive to use -- directly. Thus we apply a function (here parameter) in order to -- turn the intuitive parameters "resonance frequency" and "resonance" -- (resonance frequency amplification while frequency zero is left -- unchanged) into internal filter parameters. We have not merged these -- two steps since the computation of internal filter parameters is more -- expensive then the filtering itself and you may want to reduce the -- computation by computing the internal filter parameters at a low -- sample rate and interpolate them. However, in the list implementation -- this will not save you much time, if at all, since the list operations -- are too expensive. -- -- Now this is the example where my machine is no longer able to produce -- a constant audio stream in real-time. For tackling this problem, -- please continue with Synthesizer.Generic.Tutorial. filterSaw :: IO ExitCode module Synthesizer.Plain.Filter.Recursive.Test sampleRate :: C a => a chirp :: Double -> [Double] filter2ndOrderTest :: [Double] butterworthLowpassTest0 :: [Double] butterworthLowpassTest1 :: Double butterworthLowpassTest2 :: [Double] chebyParameterA :: C a => a -> T a -> a -> Parameter a chebyParameterB :: C a => a -> T a -> a -> Parameter a chebyshevALowpassTest0 :: Parameter Double chebyshevBLowpassTest0 :: Parameter Double chebyshevLowpassTest1 :: [Double] chebyshevALowpassTest2 :: [Double] chebyshevBLowpassTest2 :: [Double] moogLowpassTest :: [Double] universalTest :: [Result Double] complexRealTest :: [T Double] chirpComplex :: Double -> [T Double] complexTest :: [T Double] -- | Two allpasses that approach a relative phase difference of 90 degree -- over a large range of frequencies. -- -- ToDo: More parameters for controling the affected frequency range. module Synthesizer.Plain.Filter.Recursive.Hilbert data Parameter a Parameter :: [Parameter a] -> Parameter a [parameterCosine, parameterSine] :: Parameter a -> [Parameter a] polesCosine :: C a => [a] polesSine :: C a => [a] -- | Convert sample rate to allpass parameters. parameter :: C a => a -> Parameter a step2 :: (C a, C a v) => Parameter a -> v -> State [T v] (T v) modifierInit2 :: (C a, C a v) => Initialized [T v] [T v] (Parameter a) v (T v) runInit2 :: (C a, C a v) => [T v] -> Parameter a -> T v -> T (T v) run2 :: (C a, C a v) => Parameter a -> T v -> T (T v) cascade :: (C a, C a v) => [Parameter a] -> T v v -- | Although we get (almost) only the right-rotating part of the real -- input signal, the amplitude is as large as the input amplitude. That -- is, the amplitude actually doubled. causal2 :: (C a, C a v) => Parameter a -> T v (T v) causalComplex2 :: (C a, C a v) => Parameter a -> T (T v) (T v) causal :: (C a, C a v) => Parameter a -> T v (T v) causalComplex :: (C a, C a v) => Parameter a -> T (T v) (T v) -- | Approximation to perfect lowpass. However in the low frequencies the -- above filter is far away from being a perfect Hilbert filter, thus the -- cut is not straight as expected. This implementation is lazy, but -- shifts phases. lowpassStream :: (C a, C a, C a v) => a -> a -> T v -> T v -- | If we could achieve lowpass filtering while maintaining phases, we -- could do approximate Whittaker interpolation. Here we try to do this -- by filtering forward and backward. However, this does not work since -- we move the spectrum between two Hilbert transforms and thus the phase -- distortions do not match. It does not even yield a fine lowpass, since -- reversing the signal does not reverse the spectrum. lowpassMaintainPhase :: (C a, C a, C a v) => a -> a -> T v -> T v instance GHC.Show.Show a => GHC.Show.Show (Synthesizer.Plain.Filter.Recursive.Hilbert.Parameter a) module Synthesizer.Plain.Effect.Glass -- | We try to simulate the sound of broken glass as a mixture of short -- percussive sounds with random pitch glass :: Double -> [Double] module Synthesizer.Plain.Instrument -- | Create a sound of a slightly changed frequency just as needed for a -- simple stereo sound. stereoPhaser :: C a => (a -> [b]) -> a -> a -> [b] allpassPlain :: (C a, C a, C a a) => a -> a -> a -> a -> [a] allpassDown :: (C a, C a, C a a) => a -> Int -> a -> a -> a -> [a] moogDown :: (C a, C a, C a a) => a -> Int -> a -> a -> a -> [a] moogReso :: (C a, C a, C a a) => a -> Int -> a -> a -> a -> [a] bell :: (C a, C a) => a -> a -> [a] bellHarmonic :: (C a, C a) => a -> a -> a -> a -> [a] fastBell :: (C a, C a, C a a) => a -> a -> [a] squareBell :: (C a, C a, C a a) => a -> a -> [a] moogGuitar :: (C a, C a, C a a) => a -> a -> [a] moogGuitarSoft :: (C a, C a, C a a) => a -> a -> [a] simpleSaw :: (C a, C a, C a a) => a -> a -> [a] fatSaw :: (C a, C a, C a a) => a -> a -> [a] filterSaw :: (C a a, C a, C a) => a -> a -> a -> [a] fmBell :: (C a, C a) => a -> a -> a -> a -> [a] -- | low pass with resonance filterSweep :: (C v, C a v, C a, C a) => a -> a -> [v] -> [v] fatSawChordFilter :: (C a, C a, C a a) => a -> a -> [a] fatSawChord :: (C a, C a, C a a) => a -> a -> [a] filterDown :: (C a, C a) => a -> [Parameter a] -- | accumulate multiple similar saw sounds and observe the increase of -- volume The oscillator osc must accept relative frequencies. modulatedWave :: (C a, C a) => a -> (a -> [a] -> [a]) -> a -> a -> a -> a -> a -> [a] accumulatedSaws :: (Random a, C a, C a) => a -> a -> [[a]] choirWave :: C a => [a] choir :: (Random a, C a, C a) => a -> a -> [a] osciDoubleSaw :: (C a, C a a) => a -> [a] -> [a] -- | A tone with a waveform with roughly the dependency x -> x**p, where -- the waveform is normalized to constant quadratic norm osciSharp :: (C a, C a) => a -> a -> [a] -- | Build a saw sound from its harmonics and modulate it. Different to -- normal modulation I modulate each harmonic with the same depth rather -- than a proportional one. osciAbsModSaw :: (C a, C a) => a -> a -> [a] -- | Short pulsed Noise.white, i.e. Noise.white amplified with pulses of -- varying H/L ratio. pulsedNoise :: (C a, Random a, C a, C a) => a -> a -> [a] noiseBass :: (C a, Random a, C a, C a, C a a) => a -> a -> [a] -- | Drum sound using the Karplus-Strong-Algorithm This is a Noise.white -- enveloped by an exponential2 which is piped through the Karplus-Strong -- machine for generating some frequency. The whole thing is then -- frequency modulated to give a falling frequency. electroTom :: (C a, Random a, C a, C a, C a a) => a -> [a] module Synthesizer.Plain.Effect main :: IO ExitCode soundE :: Double -> [Double] soundB :: Double -> [Double] soundA :: Double -> [Double] sound9 :: Double -> [Double] sound8 :: Double -> [Double] sound7 :: Double -> [Double] sound6 :: Double -> [Double] sound5 :: Double -> [Double] sound4 :: Double -> [Double] sound3 :: Double -> [Double] sound2 :: Double -> [Double] sound1 :: Double -> [Double] sound0 :: Double -> [Double] soundm0 :: Double -> [Double] cFreq :: Double -- | An implementation of a Delay using a classical circular buffer running -- in the State Thread monad. module Synthesizer.Plain.Filter.Delay.ST modulated :: (C a, C v) => T a v -> Int -> [a] -> [v] -> [v] module Synthesizer.Plain.Filter.Delay.List -- | This is essentially different for constant interpolation, because this -- function "looks forward" whereas the other two variants "look -- backward". For the symmetric interpolation functions of linear and -- cubic interpolation, this does not really matter. modulated :: (C a, C v) => T a v -> Int -> [a] -> [v] -> [v] modulatedRev :: (C a, C v) => T a v -> Int -> [a] -> [v] -> [v] -- | Fast delay based on block lists. Blocks are arrays. They are part of -- Haskell 98. In contrast to ring buffers, block lists allow infinite -- look ahead. module Synthesizer.Plain.Filter.Delay.Block modulated :: (C a, C v) => T a v -> Int -> T a -> T v -> T v propDrop :: Int -> Int -> [Int] -> Property module Synthesizer.Plain.Filter.Delay phaser :: (C a v, C a) => a -> [a] -> [v] -> [v] plane :: Double -> [Double] -- | The test for constant interpolation will fail, due to different point -- of views in forward and backward interpolation. propAll :: [[Bool]] module Synthesizer.Plain.Effect.Fly main :: IO ExitCode sampleRate :: Double -- | stereo sound of a humming fly fly :: [(Double, Double)] module Synthesizer.Generic.Interpolation -- | interpolation as needed for resampling data T t y func :: Read sig y => T t y -> t -> sig y -> y offset :: T t y -> Int number :: T t y -> Int zeroPad :: (C t, Write sig y) => (T t y -> t -> sig y -> a) -> y -> T t y -> t -> sig y -> a constantPad :: (C t, Write sig y) => (T t y -> t -> sig y -> a) -> T t y -> t -> sig y -> a -- | Only for finite input signals. cyclicPad :: (C t, Transform sig y) => (T t y -> t -> sig y -> a) -> T t y -> t -> sig y -> a -- | The extrapolation may miss some of the first and some of the last -- points extrapolationPad :: (C t, Transform sig y) => (T t y -> t -> sig y -> a) -> T t y -> t -> sig y -> a single :: (C t, Transform sig y) => T t y -> t -> sig y -> y -- | All values of frequency control must be non-negative. multiRelative :: (C t, Transform sig t, Transform sig y) => T t y -> t -> sig y -> sig t -> sig y multiRelativeZeroPad :: (C t, Transform sig t, Transform sig y, Write sig y) => y -> T t y -> t -> sig t -> sig y -> sig y multiRelativeConstantPad :: (C t, Transform sig t, Transform sig y, Write sig y) => T t y -> t -> sig t -> sig y -> sig y multiRelativeCyclicPad :: (C t, Transform sig t, Transform sig y) => T t y -> t -> sig t -> sig y -> sig y -- | The extrapolation may miss some of the first and some of the last -- points multiRelativeExtrapolationPad :: (C t, Transform sig t, Transform sig y) => T t y -> t -> sig t -> sig y -> sig y multiRelativeZeroPadConstant :: (C t, C y, Transform sig t, Transform sig y, Write sig y) => t -> sig t -> sig y -> sig y multiRelativeZeroPadLinear :: (C t, C t y, Transform sig t, Transform sig y, Write sig y) => t -> sig t -> sig y -> sig y multiRelativeZeroPadCubic :: (C t, C t y, Transform sig t, Transform sig y, Write sig y) => t -> sig t -> sig y -> sig y module Synthesizer.Generic.Filter.Delay static :: (C y, Write sig y) => Int -> sig y -> sig y staticPad :: Write sig y => y -> Int -> sig y -> sig y staticPos :: (C y, Write sig y) => Int -> sig y -> sig y staticNeg :: Write sig y => Int -> sig y -> sig y -- | This is essentially different for constant interpolation, because this -- function "looks forward" whereas the other two variants "look -- backward". For the symmetric interpolation functions of linear and -- cubic interpolation, this does not really matter. modulated :: (C t, C y, Read sig t, Transform sig t, Transform sig y, Write sig y) => T t y -> Int -> sig t -> sig y -> sig y module Synthesizer.Generic.Filter.Recursive.MovingAverage -- | Like sums but in a recursive form. This needs only linear time -- (independent of the window size) but may accumulate rounding errors. -- --
--   ys = xs * (1,0,0,0,-1) / (1,-1)
--   ys * (1,-1) = xs * (1,0,0,0,-1)
--   ys = xs * (1,0,0,0,-1) + ys * (0,1)
--   
sumsStaticInt :: (C v, Write sig v) => Int -> sig v -> sig v modulatedFrac :: (C a, C a v, Transform sig a, Write sig v) => Int -> sig a -> sig v -> sig v module Synthesizer.Causal.Interpolation -- | interpolation as needed for resampling data T t y -- | All values of frequency control must be non-negative. relative :: C t => T t y -> t -> T y -> T t y relativeZeroPad :: C t => y -> T t y -> t -> T y -> T t y relativeConstantPad :: C t => T t y -> t -> T y -> T t y relativeCyclicPad :: C t => T t y -> t -> T y -> T t y -- | The extrapolation may miss some of the first and some of the last -- points relativeExtrapolationPad :: C t => T t y -> t -> T y -> T t y relativeZeroPadConstant :: (C t, C y) => t -> T y -> T t y relativeZeroPadLinear :: (C t, C t y) => t -> T y -> T t y relativeZeroPadCubic :: (C t, C t y) => t -> T y -> T t y -- | Tone generators module Synthesizer.Causal.Oscillator -- | oscillator with modulated phase phaseMod :: C a => T a b -> a -> T a b -- | oscillator with modulated shape shapeMod :: C a => (c -> T a b) -> T a -> a -> T c b -- | oscillator with modulated frequency freqMod :: C a => T a b -> T a -> T a b -- | oscillator with modulated frequency freqModAntiAlias :: C a => T a b -> T a -> T a b -- | oscillator with both phase and frequency modulation phaseFreqMod :: C a => T a b -> T (a, a) b -- | oscillator with both shape and frequency modulation shapeFreqMod :: C a => (c -> T a b) -> T a -> T (c, a) b -- | oscillator with a sampled waveform with modulated frequency Should -- behave homogenously for different types of interpolation. freqModSample :: C a => T a b -> T b -> T a -> T a b shapeFreqModSample :: (C c, C b) => T c (T b a) -> T (T b a) -> c -> T b -> T (c, b) a shapeFreqModFromSampledTone :: (C t, Transform sig y) => T t y -> T t y -> t -> sig y -> t -> T t -> T (t, t) y shapePhaseFreqModFromSampledTone :: (C t, Transform sig y) => T t y -> T t y -> t -> sig y -> t -> T t -> T (t, t, t) y -- | sine oscillator with modulated frequency freqModSine :: (C a, C a) => T a -> T a a -- | sine oscillator with modulated phase, useful for FM synthesis phaseModSine :: (C a, C a) => a -> T a a -- | saw tooth oscillator with modulated frequency freqModSaw :: C a => T a -> T a a -- | Tone generators module Synthesizer.State.Oscillator -- | Oscillator with constant frequency. It causes aliasing effects for -- sharp waveforms and high frequencies. static :: C a => T a b -> T a -> a -> T b -- | Oscillator with constant frequency that suppresses aliasing effects -- using waveforms with controllable smoothness. staticAntiAlias :: C a => T a b -> T a -> a -> T b -- | oscillator with modulated phase phaseMod :: C a => T a b -> a -> T a -> T b -- | oscillator with modulated shape shapeMod :: C a => (c -> T a b) -> T a -> a -> T c -> T b -- | oscillator with modulated frequency freqMod :: C a => T a b -> T a -> T a -> T b -- | oscillator with modulated frequency freqModAntiAlias :: C a => T a b -> T a -> T a -> T b -- | oscillator with both phase and frequency modulation phaseFreqMod :: C a => T a b -> T a -> T a -> T b -- | oscillator with both shape and frequency modulation shapeFreqMod :: C a => (c -> T a b) -> T a -> T c -> T a -> T b -- | oscillator with a sampled waveform with constant frequency This -- essentially an interpolation with cyclic padding. staticSample :: C a => T a b -> T b -> T a -> a -> T b -- | oscillator with a sampled waveform with modulated frequency Should -- behave homogenously for different types of interpolation. freqModSample :: C a => T a b -> T b -> T a -> T a -> T b shapeFreqModSample :: (C c, C a) => T c (T a b) -> T (T a b) -> c -> T a -> T c -> T a -> T b shapeFreqModFromSampledTone :: (C a, Transform sig b) => T a b -> T a b -> a -> sig b -> a -> T a -> T a -> T a -> T b shapePhaseFreqModFromSampledTone :: (C a, Transform sig b) => T a b -> T a b -> a -> sig b -> a -> T a -> T a -> T a -> T a -> T b -- | sine oscillator with static frequency staticSine :: (C a, C a) => T a -> a -> T a -- | sine oscillator with modulated frequency freqModSine :: (C a, C a) => T a -> T a -> T a -- | sine oscillator with modulated phase, useful for FM synthesis phaseModSine :: (C a, C a) => a -> T a -> T a -- | saw tooth oscillator with modulated frequency staticSaw :: C a => T a -> a -> T a -- | saw tooth oscillator with modulated frequency freqModSaw :: C a => T a -> T a -> T a -- | Several functions that add a loop to a sampled sound. This way you can -- obtain an infinite sound that consumes only finite space. module Synthesizer.Generic.Loop -- | Most simple of looping: You give start and length of the loop body and -- this part is repeated. The data behind start+length is ignored. simple :: Transform sig => Int -> Int -> sig -> sig -- | Create a smooth loop by cross-fading a part with delayed versions of -- itself. The loop length will be rounded to the next smaller even -- number. fade :: (Transform sig yv, C y, C y yv) => y -> Int -> Int -> sig yv -> sig yv -- | Resample a sampled sound with a smooth loop using our time -- manipulation algorithm. Time is first controlled linearly, then -- switches to a sine or triangular control. Loop start must be large -- enough in order provide enough spare data for interpolation at the -- beginning and loop start plus length must preserve according space at -- the end. One period is enough space for linear interpolation. -- -- In order to get a loopable sound with finite space we have to reduce -- the loop length to a multiple of a wave period. We will also modify -- the period a little bit, such that in our loop body there is an -- integral number of periods. -- -- We return the modified period and the looped sound. timeReverse :: (Write sig yv, C q, C q yv) => LazySize -> T q yv -> T q yv -> TimeControl q -> q -> q -> (q, sig yv) -> (q, sig yv) data TimeControl a timeControlSine :: C a => TimeControl a timeControlZigZag :: C a => TimeControl a -- | Tone generators -- -- Frequencies are always specified in ratios of the sample rate, e.g. -- the frequency 0.01 for the sample rate 44100 Hz means a physical -- frequency of 441 Hz. module Synthesizer.Generic.Oscillator -- | oscillator with constant frequency static :: (C a, Write sig b) => LazySize -> T a b -> T a -> a -> sig b -- | oscillator with modulated frequency freqMod :: (C a, Transform sig a, Transform sig b) => T a b -> T a -> sig a -> sig b -- | oscillator with modulated phase phaseMod :: (C a, Transform sig a, Transform sig b) => T a b -> a -> sig a -> sig b -- | oscillator with modulated shape shapeMod :: (C a, Transform sig c, Transform sig b) => (c -> T a b) -> T a -> a -> sig c -> sig b -- | oscillator with both phase and frequency modulation phaseFreqMod :: (C a, Transform sig a, Transform sig b) => T a b -> sig a -> sig a -> sig b -- | oscillator with both shape and frequency modulation shapeFreqMod :: (C a, Read sig c, Transform sig a, Transform sig b) => (c -> T a b) -> T a -> sig c -> sig a -> sig b -- | oscillator with a sampled waveform with constant frequency This is -- essentially an interpolation with cyclic padding. staticSample :: (C a, Read wave b, Write sig b) => LazySize -> T a b -> wave b -> T a -> a -> sig b -- | oscillator with a sampled waveform with modulated frequency Should -- behave homogenously for different types of interpolation. freqModSample :: (C a, Read wave b, Transform sig a, Transform sig b) => T a b -> wave b -> T a -> sig a -> sig b -- | sine oscillator with static frequency staticSine :: (C a, C a, Write sig a) => LazySize -> T a -> a -> sig a -- | sine oscillator with modulated frequency freqModSine :: (C a, C a, Transform sig a) => T a -> sig a -> sig a -- | sine oscillator with modulated phase, useful for FM synthesis phaseModSine :: (C a, C a, Transform sig a) => a -> sig a -> sig a -- | saw tooth oscillator with modulated frequency staticSaw :: (C a, Write sig a) => LazySize -> T a -> a -> sig a -- | saw tooth oscillator with modulated frequency freqModSaw :: (C a, Transform sig a) => T a -> sig a -> sig a -- | In this module we demonstrate techniques for getting sound in -- real-time. Getting real-time performance is mostly an issue of the -- right signal data structure. However, there is no one-size-fits-all -- data structure. For choosing the right one, you need to understand how -- various data structures work, what are their strengths and what are -- their weaknesses. -- | Deprecated: do not import that module, it is only intended for -- demonstration module Synthesizer.Generic.Tutorial -- | First, we define a play routine for lazy storable vectors. Storable -- lazy vectors are lazy lists of low-level arrays. They are both -- efficient in time and memory consumption, but the blocks disallow -- feedback by small delays. Elements of a storable vector must be of -- type class Storable. This means that elements must have fixed size and -- advanced data types like functions cannot be used. play :: T Double -> IO ExitCode -- | Here is a simple oscillator generated as lazy storable vector. An -- oscillator is a signal generator, that is it produces a signal without -- consuming other signals that correspond in time. Signal generators -- have the maximal block size as parameter. This is the lower limit of -- possible feedback delays. oscillator :: IO ExitCode -- | A routine just for the case that we want to post-process a signal -- somewhere else. write :: FilePath -> T Double -> IO ExitCode -- | The simple brass sound demonstrates how to generate piecewise defined -- curves. Some infix operators are used in order to make the pieces fit -- in height. There are also operators for intended jumps. brass :: IO ExitCode -- | We rewrite the filter example filterSaw in terms of type -- classes for more signal types. The constraints become quite large -- because we must assert, that a particular sample type can be used in -- the addressed signal type. filterSawSig :: (Write sig Double, Transform sig (Result Double), Transform sig (Parameter Double)) => sig Double -- | Here we instantiate filterSawSig for storable vectors and play -- it. This means that all operations convert a storable vector into -- another storable vector. While every single operation probably is as -- efficient as possible, the composition of all those processes could be -- more efficient. So keep on reading. filterSaw :: IO ExitCode -- | The next signal type we want to consider is the stateful signal -- generator. It is not a common data structure, where the sample values -- are materialized. Instead it is a description of how to generate -- sample values iteratively. This is almost identical to the -- Data.Stream module from the stream-fusion package. -- With respect to laziness and restrictions of the sample type (namely -- none), this signal representation is equivalent to lists. You can -- convert one into the other in a lossless way. That is, function as -- sample type is possible. Combination of such signal generators is -- easily possible and does not require temporary storage, because this -- signal representation needs no sample value storage at all. However at -- the end of such processes, the signal must be materialized. Here we -- write the result into a lazy storable vector and play that. What the -- compiler actually does is to create a single loop, that generates the -- storable vector to be played in one go. playState :: T Double -> IO ExitCode -- | We demonstrate the stateful signal generator using the known -- filterSaw example. Actually we can reuse the code from above, -- because the signal generator is also an instance of the generic signal -- class. filterSawState :: IO ExitCode -- | Merging subsequent signal processes based on signal generators into an -- efficient large signal processor is easy. Not storing intermediate -- results is however a problem in another situation: Sometimes you want -- to share one signal between several processes. filterPingStateProc :: T Double -> T Double -- | In the following example we generate an exponential curve which shall -- be used both as envelope and as resonance frequency control of a -- resonant lowpass. Actually, recomputing an exponential curve is not an -- issue, since it only needs one multiplication per sample. But it is -- simple enough to demonstrate the problem and its solutions. The -- expression let env = exponential2 50000 1 fools the reader of -- the program, since the env that is shared, is only the signal -- generator, that is, the description of how to compute the exponential -- curve successively. That is wherever a signal process reads -- env, it is computed again. filterPingState :: IO ExitCode -- | You can achieve sharing by a very simple way. You can write the result -- of the signal generator in a list (toList) and use this list as -- source for a new generator (fromList). fromList provides -- a signal generator that generates new sample values by delivering the -- next sample from the list. -- -- In a real world implementation you would move the Sig.fromList . -- Sig.toList to filterPingStateProc, since the caller cannot -- know, that this function uses the signal twice, and the implementor of -- filterPingStateProc cannot know, how expensive the computation -- of env is. -- -- You can use any other signal type for sharing, e.g. storable vectors, -- but whatever type you choose, you also get its disadvantages. Namely, -- storable vectors only work for storable samples and lists are -- generally slow, and they also cannot be optimized away, since this -- only works, when no sharing is required. -- -- Whenever a signal is shared as input between several signal processes, -- the actual materialized data is that between the slowest and the -- fastest reading process. This is due to lazy evaluation and garbage -- collection. If the different readers read with different speed, then -- you will certainly need a temporary sample storage. filterPingShare :: IO ExitCode -- | It is however not uncommon that all readers read with the same speed. -- In this case we would in principle only need to share the input signal -- per sample. This way we would not need a data structure for storing a -- sub-sequence of samples temporarily. But how to do that practically? -- -- The solution is not to think in terms of signals and signal -- processors, e.g. Sig.T a and Sig.T a -> Sig.T b -> -- Sig.T c, respectively, but in terms of signal processors, that -- are guaranteed to run in sync. That is we must assert that signal -- processors process the samples in chronological order and emit one -- sample per input sample. We call such processes "causal" processes. -- For example Causal.T (a,b) c represents the function -- Sig.T (a,b) -> Sig.T c but it also carries the guarantee, -- that for each input of type (a,b) one sample of type -- c is emitted or the output terminates. Internally it is the -- Kleisli arrow of the StateT Maybe monad. -- -- Another important application of the Causal arrow is feedback. Using -- causal processes guarantees, that a process cannot read ahead, such -- that it runs into future data, which does still not exist due to -- recursion. -- -- Programming with arrows needs a bit experience or Haskell extensions. -- Haskell extensions are either an Arrow syntax preprocessor or -- the preprocessor that is built into GHC. However, for computing with -- physical dimensions you can no longer use the original Arrow -- class and thus you cannot use the arrow syntax. So here is an example -- of how to program filterPingShare using Arrow -- combinators. filterPingCausal :: IO ExitCode module Synthesizer.Causal.Filter.NonRecursive amplify :: C a => a -> T a a amplifyVector :: C a v => a -> T v v envelope :: C a => T (a, a) a envelopeVector :: C a v => T (a, v) v crossfade :: (C a, C a a) => Int -> T (a, a) a accumulatePosModulatedFromPyramid :: Transform sig v => ([sig v] -> (Int, Int) -> v) -> [sig v] -> T (Int, Int) v sumsPosModulatedFromPyramid :: (C v, Transform sig v) => [sig v] -> T (Int, Int) v module Synthesizer.Zip -- | Parallel combination of two signals of equal length. data T a b Cons :: a -> b -> T a b [first] :: T a b -> a [second] :: T a b -> b -- | Zip together two signals. It is a checked error if their lengths -- differ. consChecked :: (Read a, Read b) => String -> a -> b -> T a b -- | Zip together two signals and shorten them to the length of the shorter -- one. consShorten :: (Transform a, Transform b) => a -> b -> T a b arrowFirst :: Arrow arrow => arrow a b -> arrow (T a c) (T b c) arrowSecond :: Arrow arrow => arrow a b -> arrow (T c a) (T c b) arrowFirstShorten :: (Arrow arrow, Transform b, Transform c) => arrow a b -> arrow (T a c) (T b c) arrowSecondShorten :: (Arrow arrow, Transform b, Transform c) => arrow a b -> arrow (T c a) (T c b) arrowFanout :: Arrow arrow => arrow a b -> arrow a c -> arrow a (T b c) arrowSplit :: Arrow arrow => arrow a c -> arrow b d -> arrow (T a b) (T c d) arrowFanoutShorten :: (Arrow arrow, Transform a, Transform b, Transform c) => arrow a b -> arrow a c -> arrow a (T b c) arrowSplitShorten :: (Arrow arrow, Transform a, Transform b, Transform c, Transform d) => arrow a c -> arrow b d -> arrow (T a b) (T c d) instance (GHC.Base.Semigroup a, GHC.Base.Semigroup b) => GHC.Base.Semigroup (Synthesizer.Zip.T a b) instance (GHC.Base.Monoid a, GHC.Base.Monoid b) => GHC.Base.Monoid (Synthesizer.Zip.T a b) instance (Synthesizer.Generic.Cut.Read a, Synthesizer.Generic.Cut.Read b) => Synthesizer.Generic.Cut.Read (Synthesizer.Zip.T a b) instance (Synthesizer.Generic.Cut.NormalForm a, Synthesizer.Generic.Cut.NormalForm b) => Synthesizer.Generic.Cut.NormalForm (Synthesizer.Zip.T a b) instance (Synthesizer.Generic.Cut.Transform a, Synthesizer.Generic.Cut.Transform b) => Synthesizer.Generic.Cut.Transform (Synthesizer.Zip.T a b) -- | Process chunks of data in the IO monad. Typical inputs are strict -- storable vectors and piecewise constant values, and typical outputs -- are strict storable vectors. You may also combine several of these -- types using the Zip type constructor. -- -- We may substitute IO by ST in the future, but I am uncertain about -- that. On the one hand, the admissible IO functionality is very -- restricted, only memory manipulation is allowed, on the other hand we -- use ForeignPtrs that are not part of ST framework. module Synthesizer.CausalIO.Process data T a b Cons :: (a -> state -> IO (b, state)) -> IO state -> (state -> IO ()) -> T a b fromCausal :: Monoid b => T a b -> T a b mapAccum :: (a -> state -> (b, state)) -> state -> T a b traverse :: state -> (a -> State state b) -> T a b -- | This function converts a process into a function on lazy storable -- vectors. To this end it must call unsafePerformIO, that is, the -- effects of all functions called in the process must not be observable. -- -- I am not sure, we need this function at all. runCont :: (Transform a, Transform b) => T a b -> IO (([a] -> [b]) -> [a] -> [b]) -- | The same restrictions as for runCont apply. runStorableChunkyCont :: (Storable a, Storable b) => T (Vector a) (Vector b) -> IO ((Vector a -> Vector b) -> Vector a -> Vector b) zip :: Arrow arrow => arrow a b -> arrow a c -> arrow a (T b c) -- | If the first process does not produce any output, then the continuing -- process will not be started. continue :: (Transform a, Transform sig b) => T a (sig b) -> (b -> T a (sig b)) -> T a (sig b) -- | Pass the last non-empty output chunk as parameter to the continuing -- process. This breaks the abstraction from the chunk sizes, but we need -- it for implementing vectorized processing. continueChunk :: (Transform a, Transform b) => T a b -> (b -> T a b) -> T a b instance Control.Category.Category Synthesizer.CausalIO.Process.T instance Control.Arrow.Arrow Synthesizer.CausalIO.Process.T instance (Synthesizer.Generic.Cut.Transform a, Synthesizer.Generic.Cut.Read b, GHC.Base.Semigroup b) => GHC.Base.Semigroup (Synthesizer.CausalIO.Process.T a b) instance (Synthesizer.Generic.Cut.Transform a, Synthesizer.Generic.Cut.Read b, GHC.Base.Monoid b) => GHC.Base.Monoid (Synthesizer.CausalIO.Process.T a b) module Synthesizer.CausalIO.Gate -- | Chunk represents a chunk of a Gate signal. -- -- It means (Chunk chunkDuration sustainDuration). -- -- sustainDuration means: Just (t,a) - key is released at time t with -- attribute a, e.g. the note-off-velocity, t must be smaller than -- chunkDuration! Nothing - key is in pressed or released state over the -- whole chunk data Chunk a Chunk :: StrictTime -> Maybe (StrictTime, a) -> Chunk a -- | smart constructor that checks the time constraints chunk :: StrictTime -> Maybe (StrictTime, a) -> Chunk a allToStorableVector :: Arrow arrow => arrow (Chunk a) (Vector ()) toStorableVector :: T (Chunk a) (Vector ()) allToChunkySize :: Arrow arrow => arrow (Chunk a) LazySize toChunkySize :: T (Chunk a) LazySize -- | Pass the second signal while the gate is open. -- -- For completeness we would need a data type analogously to ChunkySize, -- that measures signal duration in CausalIO processes. shorten -- could then be written as -- --
--   shorten = Zip.second ^<< Zip.arrowFirstShort Gate.toChunkySize
--   
shorten :: Transform signal => T (T (Chunk a) signal) signal instance GHC.Show.Show a => GHC.Show.Show (Synthesizer.CausalIO.Gate.Chunk a) instance Synthesizer.Generic.Cut.Read (Synthesizer.CausalIO.Gate.Chunk a) instance Synthesizer.Generic.Cut.NormalForm (Synthesizer.CausalIO.Gate.Chunk a) instance GHC.Base.Semigroup (Synthesizer.CausalIO.Gate.Chunk a) instance GHC.Base.Monoid (Synthesizer.CausalIO.Gate.Chunk a) instance Synthesizer.Generic.Cut.Transform (Synthesizer.CausalIO.Gate.Chunk a)