{- |
Copyright   :  (c) Henning Thielemann 2008
License     :  GPL

Maintainer  :  synthesizer@henning-thielemann.de
Stability   :  provisional
Portability :  requires multi-parameter type classes

Signals equipped with a phantom type parameter that reflects the sample rate.
-}
module Synthesizer.Dimensional.Straight.Signal where

import qualified Synthesizer.Dimensional.Abstraction.RateIndependent as Ind

import qualified Synthesizer.Format as Format
import qualified Synthesizer.Dimensional.RatePhantom as RP

import qualified Synthesizer.State.Signal as Sig

-- import qualified Number.DimensionTerm        as DN
-- import qualified Algebra.DimensionTerm       as Dim

{-
import qualified Algebra.Module         as Module
import qualified Algebra.Field          as Field
import qualified Algebra.Ring           as Ring
-}

-- import Number.DimensionTerm ((&/&))


-- import NumericPrelude
import PreludeBase
-- import Prelude ()


newtype T seq yv =
   Cons {
       samples :: seq yv   {-^ the sampled values -}
     }
--   deriving (Eq, Show)

instance Functor seq => Functor (T seq) where
   fmap f = Cons . fmap f . samples

instance Format.C seq => Format.C (T seq) where
   format p = Format.format p . samples

instance (Format.C seq, Show y) => Show (T seq y) where
   showsPrec = Format.format


type R s yv = RP.T s S yv
type S = T Sig.T

{- |
In contrast to 'Synthesizer.Dimensional.Rate.Dirac'
where only booleans are possible (peak or not peak)
we can also have signals of booleans or other enumerations.
In this case we consider the signal as piecewise constant.
-}
type Binary s = R s Bool



{-# INLINE replaceSamples #-}
replaceSamples :: Sig.T yv1 -> R s yv0 -> R s yv1
replaceSamples ss _  =  fromSamples ss


{-# INLINE processSamples #-}
processSamples :: Ind.C w =>
   (seq0 yv0 -> seq1 yv1) -> w (T seq0) yv0 -> w (T seq1) yv1
processSamples f =
   Ind.processSignal (processSamplesPrivate f)

{-# INLINE processSamplesPrivate #-}
processSamplesPrivate ::
   (seq0 yv0 -> seq1 yv1) -> T seq0 yv0 -> T seq1 yv1
processSamplesPrivate f =
   Cons . f . samples


{-# INLINE fromSamples #-}
fromSamples :: Sig.T yv -> R s yv
fromSamples  =  RP.fromSignal . Cons

{-# INLINE toSamples #-}
toSamples :: Ind.C w => w (T seq) yv -> seq yv
toSamples  =  samples . Ind.toSignal