-- |
-- Module      :  FRP.Yampa.Random
-- Copyright   :  (c) Antony Courtney and Henrik Nilsson, Yale University, 2003
-- License     :  BSD-style (see the LICENSE file in the distribution)
--
-- Maintainer  :  ivan.perez@keera.co.uk
-- Stability   :  provisional
-- Portability :  non-portable (GHC extensions)
--
-- Signals and signal functions with noise and randomness.
--
-- The Random number generators are re-exported from "System.Random".
module FRP.Yampa.Random (

    -- * Random number generators
    RandomGen(..),
    Random(..),

    -- * Noise, random signals, and stochastic event sources
    noise,              -- :: noise :: (RandomGen g, Random b) =>
                        --        g -> SF a b
    noiseR,             -- :: noise :: (RandomGen g, Random b) =>
                        --        (b,b) -> g -> SF a b
    occasionally,       -- :: RandomGen g => g -> Time -> b -> SF a (Event b)

) where

import System.Random (Random (..), RandomGen (..))

import FRP.Yampa.Diagnostics
import FRP.Yampa.Event
import FRP.Yampa.InternalCore (SF (..), SF' (..), Time)

------------------------------------------------------------------------------
-- Noise (i.e. random signal generators) and stochastic processes
------------------------------------------------------------------------------

-- | Noise (random signal) with default range for type in question;
-- based on "randoms".
noise :: (RandomGen g, Random b) => g -> SF a b
noise :: g -> SF a b
noise g
g0 = [b] -> SF a b
forall b a. [b] -> SF a b
streamToSF (g -> [b]
forall a g. (Random a, RandomGen g) => g -> [a]
randoms g
g0)


-- | Noise (random signal) with specified range; based on "randomRs".
noiseR :: (RandomGen g, Random b) => (b,b) -> g -> SF a b
noiseR :: (b, b) -> g -> SF a b
noiseR (b, b)
range g
g0 = [b] -> SF a b
forall b a. [b] -> SF a b
streamToSF ((b, b) -> g -> [b]
forall a g. (Random a, RandomGen g) => (a, a) -> g -> [a]
randomRs (b, b)
range g
g0)


streamToSF :: [b] -> SF a b
streamToSF :: [b] -> SF a b
streamToSF []     = String -> String -> String -> SF a b
forall a. String -> String -> String -> a
intErr String
"AFRP" String
"streamToSF" String
"Empty list!"
streamToSF (b
b:[b]
bs) = SF :: forall a b. (a -> Transition a b) -> SF a b
SF {sfTF :: a -> Transition a b
sfTF = a -> Transition a b
forall p p. p -> (SF' p b, b)
tf0}
    where
        tf0 :: p -> (SF' p b, b)
tf0 p
_ = ([b] -> SF' p b
forall b p. [b] -> SF' p b
stsfAux [b]
bs, b
b)

        stsfAux :: [b] -> SF' p b
stsfAux []     = String -> String -> String -> SF' p b
forall a. String -> String -> String -> a
intErr String
"AFRP" String
"streamToSF" String
"Empty list!"
        -- Invarying since stsfAux [] is an error.
        stsfAux (b
b:[b]
bs) = (DTime -> p -> Transition p b) -> SF' p b
forall a b. (DTime -> a -> Transition a b) -> SF' a b
SF' DTime -> p -> Transition p b
forall p p. p -> p -> Transition p b
tf -- True
            where
                tf :: p -> p -> Transition p b
tf p
_ p
_ = ([b] -> SF' p b
stsfAux [b]
bs, b
b)

-- | Stochastic event source with events occurring on average once every t_avg
-- seconds. However, no more than one event results from any one sampling
-- interval in the case of relatively sparse sampling, thus avoiding an
-- "event backlog" should sampling become more frequent at some later
-- point in time.

occasionally :: RandomGen g => g -> Time -> b -> SF a (Event b)
occasionally :: g -> DTime -> b -> SF a (Event b)
occasionally g
g DTime
t_avg b
x | DTime
t_avg DTime -> DTime -> Bool
forall a. Ord a => a -> a -> Bool
> DTime
0 = SF :: forall a b. (a -> Transition a b) -> SF a b
SF {sfTF :: a -> Transition a (Event b)
sfTF = a -> Transition a (Event b)
forall p p a. p -> (SF' p (Event b), Event a)
tf0}
                       | Bool
otherwise = String -> String -> String -> SF a (Event b)
forall a. String -> String -> String -> a
usrErr String
"AFRP" String
"occasionally"
                                            String
"Non-positive average interval."
    where
        -- Generally, if events occur with an average frequency of f, the
        -- probability of at least one event occurring in an interval of t
        -- is given by (1 - exp (-f*t)). The goal in the following is to
        -- decide whether at least one event occurred in the interval of size
        -- dt preceding the current sample point. For the first point,
        -- we can think of the preceding interval as being 0, implying
        -- no probability of an event occurring.

    tf0 :: p -> (SF' p (Event b), Event a)
tf0 p
_ = ([DTime] -> SF' p (Event b)
forall p. [DTime] -> SF' p (Event b)
occAux (g -> [DTime]
forall a g. (Random a, RandomGen g) => g -> [a]
randoms g
g :: [Time]), Event a
forall a. Event a
NoEvent)

    occAux :: [DTime] -> SF' p (Event b)
occAux [] = SF' p (Event b)
forall a. HasCallStack => a
undefined
    occAux (DTime
r:[DTime]
rs) = (DTime -> p -> Transition p (Event b)) -> SF' p (Event b)
forall a b. (DTime -> a -> Transition a b) -> SF' a b
SF' DTime -> p -> Transition p (Event b)
forall p. DTime -> p -> Transition p (Event b)
tf -- True
        where
        tf :: DTime -> p -> Transition p (Event b)
tf DTime
dt p
_ = let p :: DTime
p = DTime
1 DTime -> DTime -> DTime
forall a. Num a => a -> a -> a
- DTime -> DTime
forall a. Floating a => a -> a
exp (-(DTime
dtDTime -> DTime -> DTime
forall a. Fractional a => a -> a -> a
/DTime
t_avg)) -- Probability for at least one
                                                -- event.
                  in ([DTime] -> SF' p (Event b)
occAux [DTime]
rs, if DTime
r DTime -> DTime -> Bool
forall a. Ord a => a -> a -> Bool
< DTime
p then b -> Event b
forall a. a -> Event a
Event b
x else Event b
forall a. Event a
NoEvent)


-- Vim modeline
-- vim:set tabstop=8 expandtab: