Combining the Rand and State monads

I'm trying to develop a very simple simulation framework. A simulation consists of a list of models. Models generate output events based on an input event. Here is what I have currently (it works fine). -----8<----- import Data.List (foldl') import Control.Monad.State ( get, gets, modify, put, runState, State ) type Event = Char type Environment = String -- | Given an event, a model generates zero or more new events type Model = Event -> State Environment [Event] modelA :: Model modelA a = do s <- get put $ s ++ a:"A " return $ a:"hip " modelT :: Model modelT a = do s <- get put $ s ++ a:"T " return $ a:"hop " -- | Process a sequence of events using one model runModel :: Model -> [Event] -> State Environment [Event] runModel m [] = return [] runModel m (e:es) = do s <- get let (es', s') = runState (m e) s let (es'', s'') = runState (runModel m es) s' put s'' return $ es' ++ es'' -- | Process a sequence of events using multiple models runModels :: [Model] -> [Event] -> State Environment [Event] runModels [] es = return [] runModels (m:ms) es = do s <- get let (es', s') = runState (runModel m es) s let (es'', s'') = runState (runModels ms es) s' put s'' return $ es' ++ es'' ----->8----- Now what I want to do is to give models the ability to generate random numbers. So I thought I might change the definition of Model to: type Model g = Event -> StateT Environment (Rand g) [Event] And then I could alter one of the models to use random numbers like so: modelT :: Model g modelT _ = do s <- get put $ s ++ " R" n <- HOW DO I GET A RANDOM NUMBER???? return [n] I can't figure out how to get a random number from the inner monad. I assume I use lift, but I can't get it to work. Would it be better to use RandT instead of StateT? (And if so, how would I do the state operations?) Thank you in advance for any help!

On Thu, Apr 05, 2012 at 10:42:20AM +0000, Amy de Buitléir wrote:
I'm trying to develop a very simple simulation framework. A simulation consists of a list of models. Models generate output events based on an input event. Here is what I have currently (it works fine).
modelT :: Model g modelT _ = do s <- get put $ s ++ " R" n <- HOW DO I GET A RANDOM NUMBER???? return [n]
I assume you are using the MonadRandom package? Getting a random number is as simple as doing something like "getRandomR ('A','Z')" (or using any other method from the MonadRandom class [1]). There is an instance MonadRandom m => MonadRandom (StateT s m), so calls to getRandom, getRandomR, etc. are automatically lifted into your Model monad. Your problem seems to be the type you have given to modelT: it claims that it will work for *any* type g but this is not so; g must represent a pseudorandom number generator. This works: modelT :: RandomGen g => Model g modelT _ = do s <- get put $ s ++ " R" n <- getRandomR ('A', 'Z') return [n] -Brent [1] http://hackage.haskell.org/packages/archive/MonadRandom/0.1.6/doc/html/Contr...
participants (2)
-
Amy de Buitléir
-
Brent Yorgey