{-# OPTIONS -fno-implicit-prelude -fglasgow-exts #-}
{- |
Copyright   :  (c) Henning Thielemann 2006
License     :  GPL

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

-}
module Synthesizer.Inference.Reader.Noise
  (white,
   whiteGen,
   randomPeeks) where


import qualified Synthesizer.SampleRateContext.Noise as NoiseC

import qualified Synthesizer.Inference.Reader.Signal as SigR
import qualified Synthesizer.Inference.Reader.Process as Proc

import qualified Algebra.OccasionallyScalar as OccScalar
import qualified Algebra.Algebraic          as Algebraic
import qualified Algebra.Field              as Field
import qualified Algebra.Ring               as Ring

import System.Random (Random, RandomGen)

-- import NumericPrelude
import PreludeBase as P



white :: (Ring.C yv, Random yv, Algebraic.C q') =>
      q'  {-^ width of the frequency band -}
   -> q'  {-^ volume caused by the given frequency band -}
   -> Proc.T t q' (SigR.T y q' yv)
          {-^ noise -}
white bandWidth volume = SigR.lift $ NoiseC.white bandWidth volume

whiteGen :: (Ring.C yv, Random yv, RandomGen g, Algebraic.C q') =>
      g   {-^ random generator, can be used to choose a seed -}
   -> q'  {-^ width of the frequency band -}
   -> q'  {-^ volume caused by the given frequency band -}
   -> Proc.T t q' (SigR.T y q' yv)
          {-^ noise -}
whiteGen gen bandWidth volume = SigR.lift (NoiseC.whiteGen gen bandWidth volume)

{-
The Field.C q constraint could be lifted to Ring.C
if we would use direct division instead of toFrequencyScalar.
-}
randomPeeks ::
   (Field.C q, Random q, Ord q,
    Field.C q', OccScalar.C q q') =>
   Proc.T q q'
      (   SigR.T q q' q  {-   momentary densities (frequency),
                              @p@ means that there is about one peak
                              in the time range of @1\/p@. -}
       -> [Bool])
                         {-   Every occurence of 'True' represents a peak. -}
randomPeeks = SigR.lift NoiseC.randomPeeks