
I'm experimenting with different ways of working with both state and randomness at the same time. I put together this simple little example as a starting point, where the state in question is a list of Ints, and I want to be able to push a random number onto the stack. {-# LANGUAGE PackageImports #-} import "mtl" Control.Monad.State import Control.Monad.Random type Stack = [Int] -- push a random number onto the stack pushRandom:: State (Stack, StdGen) () pushRandom = do (xs,gen) <- get (r,gen') <- return $ randomR (1,100) gen put(r:xs,gen') That implementation works just fine. GHCi> execState pushRandom ([5,4,3,2,1], mkStdGen 0) ([46,5,4,3,2,1],40014 40692) But... I think it would be nicer to use Rand. Unfortunately, I can't figure out how to write the correct type signature. (Compiler message is: `Rand g' is not applied to enough type arguments Expected kind `*', but `Rand g' has kind `* -> *'). pushRandom2 :: (RandomGen g) => State (Stack, Rand g) () pushRandom2 = do (xs,gen) <- get (x,gen') <- getRandomR (0,100) gen put (1:xs,gen) And I'd really like to try using RandT, because this seems like the right situation for it. This compiles just fine. pushRandom3 :: (RandomGen g) => RandT g (State Stack) () pushRandom3 = do xs <- get r <- getRandomR (1,100) put (r:xs) But I don't know if it works, because I can't figure out the magic incantation to get it to run! GHCi> evalRandT $ pushRandom3 (mkStdGen 0) [5,4,3,2,1] <interactive>:1:12: Couldn't match expected type `StdGen -> [t] -> RandT g m a' against inferred type `RandT g1 (State Stack) ()' In the second argument of `($)', namely `pushRandom3 (mkStdGen 0) [5, 4, 3, 2, ....]' In the expression: evalRandT $ pushRandom3 (mkStdGen 0) [5, 4, 3, 2, ....] In the definition of `it': it = evalRandT $ pushRandom3 (mkStdGen 0) [5, 4, 3, ....] To summarise: Q1: How can I fix pushRandom2? Q2: How can I run pushRandom3? Thank you in advance for anyone who can help. Amy

On Sat, Dec 11, 2010 at 01:48:36AM +0000, Amy de Buitléir wrote:
And I'd really like to try using RandT, because this seems like the right situation for it. This compiles just fine.
pushRandom3 :: (RandomGen g) => RandT g (State Stack) () pushRandom3 = do xs <- get r <- getRandomR (1,100) put (r:xs)
Indeed, this is the right way to do it!
But I don't know if it works, because I can't figure out the magic incantation to get it to run!
Let's look at the type of evalRandT: *Main Control.Monad.Random> :t evalRandT evalRandT :: (Monad m, RandomGen g) => RandT g m a -> g -> m a So we have: *Main Control.Monad.Random> :t evalRandT pushRandom3 evalRandT pushRandom3 :: (RandomGen g) => g -> State Stack () Let's pass it a generator: *Main Control.Monad.Random> :t evalRandT pushRandom3 (mkStdGen 0) evalRandT pushRandom3 (mkStdGen 0) :: State Stack () (Note, if you use mkStdGen 0 you will get the same random numbers every time you run your program; instead you could use getStdGen to get one based on the system clock or something like that.) Now we have a State computation, so let's run it: *Main Control.Monad.Random> :t execState (evalRandT pushRandom3 (mkStdGen 0)) execState (evalRandT pushRandom3 (mkStdGen 0)) :: Stack -> Stack *Main Control.Monad.Random> :t execState (evalRandT pushRandom3 (mkStdGen 0)) [1,2,3,4,5] execState (evalRandT pushRandom3 (mkStdGen 0)) [1,2,3,4,5] :: Stack -Brent
participants (2)
-
Amy de Buitléir
-
Brent Yorgey