| Safe Haskell | None | 
|---|
Data.Random.RVar
- type RVar = RVarT Identity
- runRVar :: RandomSource m s => RVar a -> s -> m a
- data RVarT m a
- runRVarT :: (Lift n m, RandomSource m s) => RVarT n a -> s -> m a
- runRVarTWith :: RandomSource m s => (forall t. n t -> m t) -> RVarT n a -> s -> m a
Documentation
An opaque type modeling a "random variable" - a value 
 which depends on the outcome of some random event.  RVars 
 can be conveniently defined by an imperative-looking style:
 normalPair =  do
     u <- stdUniform
     t <- stdUniform
     let r = sqrt (-2 * log u)
         theta = (2 * pi) * t
         
         x = r * cos theta
         y = r * sin theta
     return (x,y)
OR by a more applicative style:
logNormal = exp <$> stdNormal
Once defined (in any style), there are several ways to sample RVars:
-  In a monad, using a RandomSource:
runRVar (uniform 1 100) DevRandom :: IO Int
-  In a monad, using a MonadRandominstance:
sampleRVar (uniform 1 100) :: State PureMT Int
- As a pure function transforming a functional RNG:
sampleState (uniform 1 100) :: StdGen -> (Int, StdGen)
(where sampleState = runState . sampleRVar)
runRVar :: RandomSource m s => RVar a -> s -> m a
"Run" an RVar - samples the random variable from the provided
 source of entropy.
data RVarT m a
A random variable with access to operations in an underlying monad. Useful examples include any form of state for implementing random processes with hysteresis, or writer monads for implementing tracing of complicated algorithms.
For example, a simple random walk can be implemented as an RVarT IO value:
 rwalkIO :: IO (RVarT IO Double)
 rwalkIO d = do
     lastVal <- newIORef 0
     
     let x = do
             prev    <- lift (readIORef lastVal)
             change  <- rvarT StdNormal
             
             let new = prev + change
             lift (writeIORef lastVal new)
             return new
         
     return x
To run the random walk it must first be initialized, after which it can be sampled as usual:
 do
     rw <- rwalkIO
     x <- sampleRVarT rw
     y <- sampleRVarT rw
     ...
The same random-walk process as above can be implemented using MTL types
 as follows (using import Control.Monad.Trans as MTL):
 rwalkState :: RVarT (State Double) Double
 rwalkState = do
     prev <- MTL.lift get
     change  <- rvarT StdNormal
     
     let new = prev + change
     MTL.lift (put new)
     return new
Invocation is straightforward (although a bit noisy) if you're used to MTL:
 rwalk :: Int -> Double -> StdGen -> ([Double], StdGen)
 rwalk count start gen = 
     flip evalState start .
         flip runStateT gen .
             sampleRVarTWith MTL.lift $
                 replicateM count rwalkState
Instances
runRVarT :: (Lift n m, RandomSource m s) => RVarT n a -> s -> m aSource
Like runRVarTWith, but using an implicit lifting (provided by the 
 Lift class)
runRVarTWith :: RandomSource m s => (forall t. n t -> m t) -> RVarT n a -> s -> m a
"Runs" an RVarT, sampling the random variable it defines.
The first argument lifts the base monad into the sampling monad. This operation must obey the "monad transformer" laws:
lift . return = return lift (x >>= f) = (lift x) >>= (lift . f)
One example of a useful non-standard lifting would be one that takes
 State s to another monad with a different state representation (such as
 IO with the state mapped to an IORef):
 embedState :: (Monad m) => m s -> (s -> m ()) -> State s a -> m a
 embedState get put = \m -> do
     s <- get
     (res,s) <- return (runState m s)
     put s
     return res
The ability to lift is very important - without it, every RVar would have
 to either be given access to the full capability of the monad in which it
 will eventually be sampled (which, incidentally, would also have to be 
 monomorphic so you couldn't sample one RVar in more than one monad)
 or functions manipulating RVars would have to use higher-ranked 
 types to enforce the same kind of isolation and polymorphism.