-- |
-- Module:     Control.Wire.Prefab.Random
-- Copyright:  (c) 2011 Ertugrul Soeylemez
-- License:    BSD3
-- Maintainer: Ertugrul Soeylemez <es@ertes.de>
--
-- Wires for generating random noise.

module Control.Wire.Prefab.Random
    ( -- * Random noise
      noise,
      noiseR,

      -- * Specific types
      noiseF,
      noiseF1,
      wackelkontakt
    )
    where

import Control.Arrow
import Control.Monad
import Control.Wire.Classes
import Control.Wire.Types
import System.Random


-- | Random number wires.

class Arrow (>~) => WRandom (>~) where
    -- | Generate random noise.
    noise :: Random b => Wire e (>~) a b

    -- | Generate random noise in a certain range given by the input
    -- signal.
    --
    -- * Depends: Current instant.
    noiseR :: Random b => Wire e (>~) (b, b) b

    -- | Generate a random boolean, where the input signal is the
    -- probability to be 'True'.
    --
    -- * Depends: Current instant.
    wackelkontakt :: Wire e (>~) Double Bool

instance MonadRandom m => WRandom (Kleisli m) where
    noise  = mkFixM (liftM Right . const getRandom)
    noiseR = mkFixM (liftM Right . getRandomR)
    wackelkontakt =
        mkFixM $ \p -> do
            s <- getRandom
            return (Right (not (s >= p)))


-- | Generate random noise in range 0 <= x < 1.

noiseF :: WRandom (>~) => Wire e (>~) a Double
noiseF = noise


-- | Generate random noise in range -1 <= x < 1.

noiseF1 :: (Arrow (Wire e (>~)), WRandom (>~)) => Wire e (>~) a Double
noiseF1 = ((*2) . pred) ^<< noise