module Synthesizer.Dimensional.Straight.Displacement where

import qualified Synthesizer.Dimensional.Abstraction.RateIndependent as Ind
import qualified Synthesizer.Dimensional.Abstraction.Flat as Flat

import qualified Synthesizer.Dimensional.Straight.Signal as SigS
import qualified Synthesizer.State.Displacement as Disp
import qualified Synthesizer.State.Signal as Sig

import qualified Algebra.Additive              as Additive

-- 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.
-}
{-# INLINE mix #-}
mix :: (Additive.C v) => SigS.R s v -> SigS.R s v -> SigS.R s v
{- we can't assert equal sample rates of mixer inputs if 'w = RateWrapper'
mix :: (Ind.C w, Additive.C v) =>
   w SigS.S v -> w SigS.S v -> w SigS.S v
-}
mix x = SigS.processSamples (SigS.toSamples x Additive.+)

{-| Add a number to all of the signal values.
    This is useful for adjusting the center of a modulation. -}
{-# INLINE raise #-}
raise :: (Ind.C w, Additive.C v) =>
    v -> w SigS.S v -> w SigS.S v
raise x = SigS.processSamples (Disp.raise x)


{- * Distortion -}

{-# INLINE map #-}
map :: (Ind.C w, Flat.C flat y0) =>
    (y0 -> y1) ->
    w flat y0 ->
    w SigS.S y1
map f =
   Ind.processSignal
      (SigS.Cons .
       Sig.map f .
       Flat.unwrappedToSamples)

{- |
In "Synthesizer.State.Distortion" you find a collection
of appropriate distortion functions.
-}
{-# INLINE distort #-}
distort :: (c -> a -> a) -> SigS.R s c -> SigS.R s a -> SigS.R s a
{- we can't assert equal sample rates of inputs if 'w = RateWrapper'
distort :: (Ind.C w) =>
   (c -> a -> a) ->
   w SigS.S c ->
   w SigS.S a ->
   w SigS.S a
-}
distort f c = SigS.processSamples (Disp.distort f (SigS.toSamples c))