
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