Difference between revisions of "New monads/MonadRandom"

From HaskellWiki
Jump to navigation Jump to search
m (evalRandomT was missing "RandomGen g" in the type signature)
(→‎Connection to stochastics: fix do block code indentation)
 
(25 intermediate revisions by 11 users not shown)
Line 1: Line 1:
  +
[[Category:Code]]
From New monads, copied from [http://haskell.org/hawiki/MonadRandom old wiki].
 
  +
[[Category:Mathematics]]
 
= MonadRandom =
 
   
 
A simple monad transformer to allow computations in the transformed monad to generate random values.
 
A simple monad transformer to allow computations in the transformed monad to generate random values.
  +
==The code==
 
  +
<haskell>{-#LANGUAGE MultiParamTypeClasses, UndecidableInstances #-}
[http://haskell.org/hawiki/CaleGibbard_2fBSDLicense "CaleGibbard/BSDLicense"]
 
  +
{-#LANGUAGE GeneralizedNewtypeDeriving, FlexibleInstances #-}
 
  +
 
<haskell>
 
{-# OPTIONS_GHC -fglasgow-exts #-}
 
 
 
module MonadRandom (
 
module MonadRandom (
 
MonadRandom,
 
MonadRandom,
 
getRandom,
 
getRandom,
 
getRandomR,
 
getRandomR,
evalRandomT,
+
getRandoms,
  +
getRandomRs,
  +
evalRandT,
 
evalRand,
 
evalRand,
 
evalRandIO,
 
evalRandIO,
 
fromList,
 
fromList,
Rand, RandomT -- but not the data constructors
+
Rand, RandT -- but not the data constructors
 
) where
 
) where
  +
 
 
import System.Random
 
import System.Random
 
import Control.Monad.State
 
import Control.Monad.State
 
import Control.Monad.Identity
 
import Control.Monad.Identity
  +
import Control.Monad.Writer
 
  +
import Control.Monad.Reader
  +
import Control.Arrow
  +
 
class (Monad m) => MonadRandom m where
 
class (Monad m) => MonadRandom m where
getRandom :: (Random a) => m a
+
getRandom :: (Random a) => m a
getRandomR :: (Random a) => (a,a) -> m a
+
getRandoms :: (Random a) => m [a]
  +
getRandomR :: (Random a) => (a,a) -> m a
 
  +
getRandomRs :: (Random a) => (a,a) -> m [a]
newtype (RandomGen g) => RandomT g m a = RandomT { unRT :: StateT g m a }
 
  +
  +
newtype RandT g m a = RandT (StateT g m a)
 
deriving (Functor, Monad, MonadTrans, MonadIO)
 
deriving (Functor, Monad, MonadTrans, MonadIO)
  +
 
 
liftState :: (MonadState s m) => (s -> (a,s)) -> m a
 
liftState :: (MonadState s m) => (s -> (a,s)) -> m a
 
liftState t = do v <- get
 
liftState t = do v <- get
Line 38: Line 41:
 
put v'
 
put v'
 
return x
 
return x
  +
 
instance (Monad m, RandomGen g) => MonadRandom (RandomT g m) where
+
instance (Monad m, RandomGen g) => MonadRandom (RandT g m) where
getRandom = (RandomT . liftState) random
+
getRandom = RandT $ liftState random
getRandomR (x,y) = (RandomT . liftState) (randomR (x,y))
+
getRandoms = RandT $ liftState $ first randoms . split
  +
getRandomR (x,y) = RandT $ liftState $ randomR (x,y)
 
  +
getRandomRs (x,y) = RandT $ liftState $
evalRandomT :: (Monad m, RandomGen g) => RandomT g m a -> g -> m a
 
  +
first (randomRs (x,y)) . split
evalRandomT x g = evalStateT (unRT x) g
 
  +
 
  +
evalRandT :: (Monad m, RandomGen g) => RandT g m a -> g -> m a
  +
evalRandT (RandT x) g = evalStateT x g
  +
  +
runRandT :: (Monad m, RandomGen g) => RandT g m a -> g -> m (a, g)
  +
runRandT (RandT x) g = runStateT x g
  +
 
-- Boring random monad :)
 
-- Boring random monad :)
newtype Rand g a = Rand { unRand :: RandomT g Identity a }
+
newtype Rand g a = Rand (RandT g Identity a)
 
deriving (Functor, Monad, MonadRandom)
 
deriving (Functor, Monad, MonadRandom)
  +
 
 
evalRand :: (RandomGen g) => Rand g a -> g -> a
 
evalRand :: (RandomGen g) => Rand g a -> g -> a
evalRand x g = runIdentity (evalRandomT (unRand x) g)
+
evalRand (Rand x) g = runIdentity (evalRandT x g)
  +
 
  +
runRand :: (RandomGen g) => Rand g a -> g -> (a, g)
  +
runRand (Rand x) g = runIdentity (runRandT x g)
  +
 
evalRandIO :: Rand StdGen a -> IO a
 
evalRandIO :: Rand StdGen a -> IO a
evalRandIO x = getStdRandom (runIdentity . runStateT (unRT (unRand x)))
+
evalRandIO (Rand (RandT x)) = getStdRandom (runIdentity . runStateT x)
  +
 
 
fromList :: (MonadRandom m) => [(a,Rational)] -> m a
 
fromList :: (MonadRandom m) => [(a,Rational)] -> m a
 
fromList [] = error "MonadRandom.fromList called with empty list"
 
fromList [] = error "MonadRandom.fromList called with empty list"
 
fromList [(x,_)] = return x
 
fromList [(x,_)] = return x
fromList xs = do let s = fromRational $ sum (map snd xs) -- total weight
+
fromList xs = do
cs = scanl1 (\(x,q) (y,s) -> (y, s+q)) xs -- cumulative weight
+
let total = fromRational $ sum (map snd xs) :: Double -- total weight
p <- liftM toRational $ getRandomR (0.0,s)
+
cumulative = scanl1 (\(x,q) (y,s) -> (y, s+q)) xs -- cumulative weights
return $ fst $ head $ dropWhile (\(x,q) -> q < p) cs
+
p <- liftM toRational $ getRandomR (0.0, total)
  +
return $ fst . head . dropWhile (\(x,q) -> q < p) $ cumulative
 
</haskell>
 
</haskell>
  +
  +
To make use of common transformer stacks involving Rand and RandT, the following definitions may prove useful:
  +
  +
<haskell>
  +
instance (MonadRandom m) => MonadRandom (StateT s m) where
  +
getRandom = lift getRandom
  +
getRandomR = lift . getRandomR
  +
getRandoms = lift getRandoms
  +
getRandomRs = lift . getRandomRs
  +
  +
instance (MonadRandom m, Monoid w) => MonadRandom (WriterT w m) where
  +
getRandom = lift getRandom
  +
getRandomR = lift . getRandomR
  +
getRandoms = lift getRandoms
  +
getRandomRs = lift . getRandomRs
  +
  +
instance (MonadRandom m) => MonadRandom (ReaderT r m) where
  +
getRandom = lift getRandom
  +
getRandomR = lift . getRandomR
  +
getRandoms = lift getRandoms
  +
getRandomRs = lift . getRandomRs
  +
  +
instance (MonadState s m, RandomGen g) => MonadState s (RandT g m) where
  +
get = lift get
  +
put = lift . put
  +
  +
instance (MonadReader r m, RandomGen g) => MonadReader r (RandT g m) where
  +
ask = lift ask
  +
local f (RandT m) = RandT $ local f m
  +
  +
instance (MonadWriter w m, RandomGen g, Monoid w) => MonadWriter w (RandT g m) where
  +
tell = lift . tell
  +
listen (RandT m) = RandT $ listen m
  +
pass (RandT m) = RandT $ pass m
  +
</haskell>
  +
  +
You may also want a MonadRandom instance for IO:
  +
  +
<haskell>
  +
instance MonadRandom IO where
  +
getRandom = randomIO
  +
getRandomR = randomRIO
  +
getRandoms = fmap randoms newStdGen
  +
getRandomRs b = fmap (randomRs b) newStdGen
  +
  +
</haskell>
  +
  +
== Connection to stochastics ==
  +
  +
There is some correspondence between notions in programming and in mathematics:
  +
  +
{|
  +
|-
  +
|random generator || ~ || random variable / probabilistic experiment
  +
|-
  +
|result of a random generator || ~ || outcome of a probabilistic experiment
  +
|}
  +
  +
Thus the signature
  +
<haskell>rx :: (MonadRandom m, Random a) => m a</haskell>
  +
can be considered as "<hask>rx</hask> is a random variable". In the do-notation the line
  +
<haskell>x <- rx</haskell>
  +
means that "<hask>x</hask> is an outcome of <hask>rx</hask>".
  +
  +
In a language without higher order functions and using a random
  +
generator "function" it is not possible to work with random variables, it
  +
is only possible to compute with outcomes, e.g. <code>rand()+rand()</code>. In a
  +
language where random generators are implemented as objects, computing
  +
with random variables is possible but still cumbersome.
  +
  +
In Haskell we have both options either computing with outcomes
  +
<haskell>
  +
do x <- rx
  +
y <- ry
  +
return (x+y)
  +
</haskell>
  +
or computing with random variables
  +
<haskell>
  +
liftM2 (+) rx ry
  +
</haskell>
  +
  +
This means that <hask>liftM</hask> like functions convert ordinary arithmetic into
  +
random variable arithmetic. But there is also some arithmetic on random
  +
variables which can not be performed on outcomes. For example, given a
  +
function that repeats an action until the result fulfills a certain
  +
property (I wonder if there is already something of this kind in the
  +
standard libraries)
  +
<haskell>
  +
untilM :: Monad m => (a -> Bool) -> m a -> m a
  +
untilM p m =
  +
do x <- m
  +
if p x then return x else untilM p m
  +
</haskell>
  +
we can suppress certain outcomes of an experiment. E.g. if
  +
<haskell>
  +
getRandomR (-10,10)
  +
</haskell>
  +
is a uniformly distributed random variable between −10 and 10, then
  +
<haskell>
  +
untilM (0/=) (getRandomR (-10,10))
  +
</haskell>
  +
is a random variable with a uniform distribution of {−10, &hellip;, −1, 1, &hellip;, 10}.
  +
  +
==See also==
  +
* <hask>Arbitrary</hask> type class of [[Introduction to QuickCheck|Quickcheck]]
  +
* http://www.haskell.org/pipermail/haskell-cafe/2005-May/009775.html
  +
* [[New monads/MonadRandomSplittable]]
  +
* [http://hackage.haskell.org/packages/archive/pkg-list.html#cat:Control The package list of Hackage]
  +
* [http://hackage.haskell.org/cgi-bin/hackage-scripts/package/MonadRandom The MonadRandom package on Hackage]
  +
* http://code.haskell.org/monadrandom/

Latest revision as of 13:41, 2 April 2019


A simple monad transformer to allow computations in the transformed monad to generate random values.

The code

{-#LANGUAGE MultiParamTypeClasses, UndecidableInstances #-} 
{-#LANGUAGE GeneralizedNewtypeDeriving, FlexibleInstances #-}
 
module MonadRandom (
    MonadRandom,
    getRandom,
    getRandomR,
    getRandoms,
    getRandomRs,
    evalRandT,
    evalRand,
    evalRandIO,
    fromList,
    Rand, RandT -- but not the data constructors
    ) where
 
import System.Random
import Control.Monad.State
import Control.Monad.Identity
import Control.Monad.Writer
import Control.Monad.Reader
import Control.Arrow
 
class (Monad m) => MonadRandom m where
    getRandom   :: (Random a) => m a
    getRandoms  :: (Random a) => m [a]
    getRandomR  :: (Random a) => (a,a) -> m a
    getRandomRs :: (Random a) => (a,a) -> m [a]
 
newtype RandT g m a = RandT (StateT g m a)
    deriving (Functor, Monad, MonadTrans, MonadIO)
 
liftState :: (MonadState s m) => (s -> (a,s)) -> m a
liftState t = do v <- get
                 let (x, v') = t v
                 put v'
                 return x
 
instance (Monad m, RandomGen g) => MonadRandom (RandT g m) where
    getRandom         = RandT $ liftState  random
    getRandoms        = RandT $ liftState $ first randoms . split
    getRandomR (x,y)  = RandT $ liftState $ randomR (x,y) 
    getRandomRs (x,y) = RandT $ liftState $
                            first (randomRs (x,y)) . split
 
evalRandT :: (Monad m, RandomGen g) => RandT g m a -> g -> m a
evalRandT (RandT x) g = evalStateT x g
 
runRandT  :: (Monad m, RandomGen g) => RandT g m a -> g -> m (a, g)
runRandT (RandT x) g = runStateT x g
 
-- Boring random monad :)
newtype Rand g a = Rand (RandT g Identity a)
    deriving (Functor, Monad, MonadRandom)
 
evalRand :: (RandomGen g) => Rand g a -> g -> a
evalRand (Rand x) g = runIdentity (evalRandT x g)
 
runRand :: (RandomGen g) => Rand g a -> g -> (a, g)
runRand (Rand x) g  = runIdentity (runRandT x g)
 
evalRandIO :: Rand StdGen a -> IO a
evalRandIO (Rand (RandT x)) = getStdRandom (runIdentity . runStateT x)
 
fromList :: (MonadRandom m) => [(a,Rational)] -> m a
fromList [] = error "MonadRandom.fromList called with empty list"
fromList [(x,_)] = return x
fromList xs = do 
       let total = fromRational $ sum (map snd xs) :: Double  -- total weight
           cumulative = scanl1 (\(x,q) (y,s) -> (y, s+q)) xs  -- cumulative weights
       p <- liftM toRational $ getRandomR (0.0, total)
       return $ fst . head . dropWhile (\(x,q) -> q < p) $ cumulative

To make use of common transformer stacks involving Rand and RandT, the following definitions may prove useful:

instance (MonadRandom m) => MonadRandom (StateT s m) where
    getRandom = lift getRandom
    getRandomR = lift . getRandomR
    getRandoms = lift getRandoms
    getRandomRs = lift . getRandomRs

instance (MonadRandom m, Monoid w) => MonadRandom (WriterT w m) where
    getRandom = lift getRandom
    getRandomR = lift . getRandomR
    getRandoms = lift getRandoms
    getRandomRs = lift . getRandomRs

instance (MonadRandom m) => MonadRandom (ReaderT r m) where
    getRandom = lift getRandom
    getRandomR = lift . getRandomR
    getRandoms = lift getRandoms
    getRandomRs = lift . getRandomRs

instance (MonadState s m, RandomGen g) => MonadState s (RandT g m) where
    get = lift get
    put = lift . put

instance (MonadReader r m, RandomGen g) => MonadReader r (RandT g m) where
    ask = lift ask
    local f (RandT m) = RandT $ local f m

instance (MonadWriter w m, RandomGen g, Monoid w) => MonadWriter w (RandT g m) where
    tell = lift . tell
    listen (RandT m) = RandT $ listen m
    pass (RandT m) = RandT $ pass m

You may also want a MonadRandom instance for IO:

instance MonadRandom IO where
    getRandom = randomIO
    getRandomR = randomRIO
    getRandoms = fmap randoms newStdGen
    getRandomRs b = fmap (randomRs b) newStdGen

Connection to stochastics

There is some correspondence between notions in programming and in mathematics:

random generator ~ random variable / probabilistic experiment
result of a random generator ~ outcome of a probabilistic experiment

Thus the signature

rx :: (MonadRandom m, Random a) => m a

can be considered as "rx is a random variable". In the do-notation the line

x <- rx

means that "x is an outcome of rx".

In a language without higher order functions and using a random generator "function" it is not possible to work with random variables, it is only possible to compute with outcomes, e.g. rand()+rand(). In a language where random generators are implemented as objects, computing with random variables is possible but still cumbersome.

In Haskell we have both options either computing with outcomes

    do x <- rx
       y <- ry
       return (x+y)

or computing with random variables

   liftM2 (+) rx ry

This means that liftM like functions convert ordinary arithmetic into random variable arithmetic. But there is also some arithmetic on random variables which can not be performed on outcomes. For example, given a function that repeats an action until the result fulfills a certain property (I wonder if there is already something of this kind in the standard libraries)

  untilM :: Monad m => (a -> Bool) -> m a -> m a
  untilM p m =
     do x <- m
        if p x then return x else untilM p m

we can suppress certain outcomes of an experiment. E.g. if

  getRandomR (-10,10)

is a uniformly distributed random variable between −10 and 10, then

  untilM (0/=) (getRandomR (-10,10))

is a random variable with a uniform distribution of {−10, …, −1, 1, …, 10}.

See also