{-# LANGUAGE NoImplicitPrelude #-} {- | -} module Synthesizer.Generic.Displacement where import qualified Algebra.Additive as Additive import qualified Synthesizer.Generic.Signal as SigG -- import qualified Prelude as P import PreludeBase import NumericPrelude {- * Mixing -} {-| Mix two signals. In opposition to 'zipWith' the result has the length of the longer signal. -} mix :: (Additive.C v, SigG.Transform sig v) => sig v -> sig v -> sig v mix = SigG.mix {- relict from Prelude98's Num mixMono :: Ring.C a => [a] -> [a] -> [a] mixMono [] x = x mixMono x [] = x mixMono (x:xs) (y:ys) = x+y : mixMono xs ys -} {-| Mix one or more signals. -} mixMulti :: (Additive.C v, SigG.Transform sig v) => [sig v] -> sig v mixMulti = foldl mix SigG.empty {-| Add a number to all of the signal values. This is useful for adjusting the center of a modulation. -} raise :: (Additive.C v, SigG.Transform sig v) => v -> sig v -> sig v raise x = SigG.map ((+) x) {- * Distortion -} {- | In "Synthesizer.Basic.Distortion" you find a collection of appropriate distortion functions. -} distort :: (SigG.Read sig c, SigG.Transform sig v) => (c -> v -> v) -> sig c -> sig v -> sig v distort = SigG.zipWith