
Hi Phil. First a quick style comment, then I'll get to the meat of
your question.
getRanq1 is correct; although quite verbose. A simpler definition is this:
getRanq1 = State ranq1
This uses the State constructor from Control.Monad.State:
State :: (s -> (a,s)) -> State s a
What it sounds like you want is this:
main = do
x <- getARandomNumber
... do some other stuff
y <- getAnotherRandomNumber
.. etc.
using State. There are two ways to go about this; the first is, if
the entire computation is pure, that is, the "do some other stuff"
doesn't do IO, you can embed the whole computation in "State":
seed = 124353542542
main = do
result <- evalState randomComputation (ranq1Init seed)
... some IO using result ...
randomComputation = do
x <- getRanq1
let y = some pure computation using x
z <- getRanq1
w <- something that uses x, y, and z that also uses the random source
... etc.
return (some result)
The other option, if you want to do IO in between, is to use a
"transformer" version of State:
type MyMonad a = StateT Word64 IO a
main = withStateT (ranq1Init seed) $ do
x <- getRanq1_t
liftIO $ print x
...
y <- getRanq1_t
...
getRanq1_t :: MyMonad Double
getRanq1_t = liftStateT getRanq1
liftStateT :: State s a -> MyMonad a
liftStateT m = StateT $ \s -> return (runState m s)
withStateT :: Word64 -> MyMonad a -> IO a
withStateT s m = evalStateT m s -- can also just use "withStateT =
flip evalStateT"
This uses these functions from Control.Monad.State:
liftIO :: MonadIO m => IO a -> m a
This takes any IO action and puts it into any monad that supports
IO. In this case, StateT s IO a fits.
runState :: StateT s a -> s -> (a,s)
This evaluates a pure stateful computation and gives you the result.
StateT :: (s -> m (a,s)) -> StateT s m a
This builds a StateT directly. You could get away without it like this:
liftStateT m = do
s <- get
let (a, s') = runState m s
put s'
return a
(note the similarity to your getRanq1 function!)
evalStateT :: StateT s m a -> s -> m a
This is just evalState for the transformer version of State. In
our case it has the type (MyMonad a -> Word64 -> IO a)
This said, as a beginner I recommend trying to make more of your code
pure so you can avoid IO; you do need side effects for some things,
but while learning it makes sense to try as hard as you can to avoid
it. You can make a lot of interesting programs with just "interact"
and pure functions.
If you're just doing text operations, try to make your program look like this:
main = interact pureMain
pureMain :: String -> String
pureMain s = ...
You'll find it will teach you a lot about laziness & the power of
purity! A key insight is that State *is* pure, even though code using
it looks somewhat imperative.
-- ryan
P.S. If you can't quite get out of the imperative mindset you can
visit imperative island via the ST boat.
2009/1/7 Phil
Hi,
I'm a newbie looking to get my head around using the State Monad for random number generation. I've written non-monad code that achieves this no problem. When attempting to use the state monad I can get what I know to be the correct initial value and state, but can't figure out for the life of me how to then increment it without binding more calls there and then. Doing several contiguous calls is not what I want to do here – and the examples I've read all show this (using something like liftM2 (,) myRandom myRandom). I want to be able to do:
Get_a_random_number
< a whole load of other stuff >
Get the next number as defined by the updated state in the first call
<some more stuff>
Get another number, and so on.
I get the first number fine, but am lost at how to get the second, third, forth etc without binding there and then. I just want each number one at a time where and when I want it, rather than saying give 1,2,10 or even 'n' numbers now. I'm sure it's blindly obvious!
Note: I'm not using Haskell's built in Random functionality (nor is that an option), I'll spare the details of the method I'm using (NRC's ranq1) as I know it works for the non-Monad case, and it's irrelevent to the question. So the code is:
ranq1 :: Word64 -> ( Double, Word64 ) ranq1 state = ( output, newState ) where newState = ranq1Increment state output = convert_to_double newState
ranq1Init :: Word64 -> Word64 ranq1Init = convert_to_word64 . ranq1Increment . xor_v_init
-- I'll leave the detail of how ranq1Increment works out for brevity. I know this bit works fine. Same goes for the init function it's just providing an initial state.
-- The Monad State Attempt getRanq1 :: State Word64 Double getRanq1 = do state <- get let ( randDouble, newState ) = ranq1 state put newState return randDouble
_________ And then in my main _________
-- 124353542542 is just an arbitrary seed main :: IO() main = do let x = evalState getRanq1 (ranq1Init 124353542542) print (x)
As I said this works fine; x gives me the correct first value for this sequence, but how do I then get the second and third without writing the giveMeTenRandoms style function? I guess what I want is a next() type function, imperatively speaking.
Many thanks for any help,
Phil.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe