New monads/MonadRandom: Difference between revisions
BrettGiles (talk | contribs) m (Headings - link to splittable) |
CaleGibbard (talk | contribs) No edit summary |
||
Line 6: | Line 6: | ||
<haskell> | <haskell> | ||
{-# OPTIONS_GHC -fglasgow-exts #-} | {-# OPTIONS_GHC -fglasgow-exts #-} | ||
module MonadRandom ( | module MonadRandom ( | ||
MonadRandom, | MonadRandom, | ||
getRandom, | getRandom, | ||
getRandomR, | getRandomR, | ||
getRandoms, | |||
getRandomRs, | |||
evalRandomT, | evalRandomT, | ||
evalRand, | evalRand, | ||
Line 17: | Line 19: | ||
Rand, RandomT -- but not the data constructors | Rand, RandomT -- 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.Arrow | |||
class (Monad m) => MonadRandom m where | class (Monad m) => MonadRandom m where | ||
getRandom :: (Random a) => m a | getRandom :: (Random a) => m a | ||
getRandoms :: (Random a) => m [a] | |||
getRandomR :: (Random a) => (a,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 (RandomGen g) => RandomT g m a = RandomT { unRT :: 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 34: | Line 39: | ||
put v' | put v' | ||
return x | return x | ||
instance (Monad m, RandomGen g) => MonadRandom (RandomT g m) where | instance (Monad m, RandomGen g) => MonadRandom (RandomT g m) where | ||
getRandom = | getRandom = RandomT . liftState $ random | ||
getRandomR (x,y) = (RandomT . liftState | getRandoms = RandomT . liftState $ first randoms . split | ||
getRandomR (x,y) = RandomT . liftState $ randomR (x,y) | |||
getRandomRs (x,y) = RandomT . liftState $ | |||
first (randomRs (x,y)) . split | |||
evalRandomT :: (Monad m, RandomGen g) => RandomT g m a -> g -> m a | evalRandomT :: (Monad m, RandomGen g) => RandomT g m a -> g -> m a | ||
evalRandomT x g = evalStateT (unRT x) g | evalRandomT x g = evalStateT (unRT x) g | ||
runRandomT :: (Monad m, RandomGen g) => RandomT g m a -> g -> m (a, g) | runRandomT :: (Monad m, RandomGen g) => RandomT g m a -> g -> m (a, g) | ||
runRandomT x g = runStateT (unRT x) g | runRandomT x g = runStateT (unRT x) g | ||
-- Boring random monad :) | -- Boring random monad :) | ||
newtype Rand g a = Rand { unRand :: RandomT g Identity a } | newtype Rand g a = Rand { unRand :: RandomT 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 x g = runIdentity (evalRandomT (unRand x) g) | ||
runRand :: (RandomGen g) => Rand g a -> g -> (a, g) | runRand :: (RandomGen g) => Rand g a -> g -> (a, g) | ||
runRand x g = runIdentity (runRandomT (unRand x) g) | runRand x g = runIdentity (runRandomT (unRand x) g) | ||
evalRandIO :: Rand StdGen a -> IO a | evalRandIO :: Rand StdGen a -> IO a | ||
evalRandIO x = getStdRandom (runIdentity . runStateT (unRT (unRand x))) | evalRandIO x = getStdRandom (runIdentity . runStateT (unRT (unRand 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" | ||
Line 66: | Line 74: | ||
return $ fst $ head $ dropWhile (\(x,q) -> q < p) cs | return $ fst $ head $ dropWhile (\(x,q) -> q < p) cs | ||
</haskell> | </haskell> | ||
To make use of common transformer stacks involving Rand and RandomT, the following definitions may prove useful: | To make use of common transformer stacks involving Rand and RandomT, the following definitions may prove useful: |
Revision as of 00:02, 4 December 2006
A simple monad transformer to allow computations in the transformed monad to generate random values.
The code
{-# OPTIONS_GHC -fglasgow-exts #-}
module MonadRandom (
MonadRandom,
getRandom,
getRandomR,
getRandoms,
getRandomRs,
evalRandomT,
evalRand,
evalRandIO,
fromList,
Rand, RandomT -- but not the data constructors
) where
import System.Random
import Control.Monad.State
import Control.Monad.Identity
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 (RandomGen g) => RandomT g m a = RandomT { unRT :: 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 (RandomT g m) where
getRandom = RandomT . liftState $ random
getRandoms = RandomT . liftState $ first randoms . split
getRandomR (x,y) = RandomT . liftState $ randomR (x,y)
getRandomRs (x,y) = RandomT . liftState $
first (randomRs (x,y)) . split
evalRandomT :: (Monad m, RandomGen g) => RandomT g m a -> g -> m a
evalRandomT x g = evalStateT (unRT x) g
runRandomT :: (Monad m, RandomGen g) => RandomT g m a -> g -> m (a, g)
runRandomT x g = runStateT (unRT x) g
-- Boring random monad :)
newtype Rand g a = Rand { unRand :: RandomT g Identity a }
deriving (Functor, Monad, MonadRandom)
evalRand :: (RandomGen g) => Rand g a -> g -> a
evalRand x g = runIdentity (evalRandomT (unRand x) g)
runRand :: (RandomGen g) => Rand g a -> g -> (a, g)
runRand x g = runIdentity (runRandomT (unRand x) g)
evalRandIO :: Rand StdGen a -> IO a
evalRandIO x = getStdRandom (runIdentity . runStateT (unRT (unRand x)))
fromList :: (MonadRandom m) => [(a,Rational)] -> m a
fromList [] = error "MonadRandom.fromList called with empty list"
fromList [(x,_)] = return x
fromList xs = do let s = fromRational $ sum (map snd xs) -- total weight
cs = scanl1 (\(x,q) (y,s) -> (y, s+q)) xs -- cumulative weight
p <- liftM toRational $ getRandomR (0.0,s)
return $ fst $ head $ dropWhile (\(x,q) -> q < p) cs
To make use of common transformer stacks involving Rand and RandomT, the following definitions may prove useful:
instance (MonadRandom m) => MonadRandom (StateT s m) where
getRandom = lift getRandom
getRandomR r = lift $ getRandomR r
instance (MonadRandom m, Monoid w) => MonadRandom (WriterT w m) where
getRandom = lift getRandom
getRandomR r = lift $ getRandomR r
instance (MonadRandom m) => MonadRandom (ReaderT r m) where
getRandom = lift getRandom
getRandomR r = lift $ getRandomR r
instance (MonadState s m, RandomGen g) => MonadState s (RandomT g m) where
get = lift get
put s = lift $ put s
instance (MonadReader r m, RandomGen g) => MonadReader r (RandomT g m) where
ask = lift ask
local f m = RandomT $ local f (unRT m)
instance (MonadWriter w m, RandomGen g, Monoid w) => MonadWriter w (RandomT g m) where
tell w = lift $ tell w
listen m = RandomT $ listen (unRT m)
pass m = RandomT $ pass (unRT m)
You may also want a MonadRandom instance for IO:
instance MonadRandom IO where
getRandom = randomIO
getRandomR = randomRIO
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 .