[Haskell-cafe] Re: so how does one convert an IO a into an a ?
André Pang
ozone at algorithm.com.au
Thu Jul 8 19:24:25 EDT 2004
On 09/07/2004, at 4:50 AM, Crypt Master wrote:
> One person mentioned how random just returns an interative program
> which when eveluated returns the Int. Also from the school of
> expression book he says " The right way to think of (>>=) above is
> simply this: It "Executes" e1 ..." in relation to "do pat <- e1 ...".
>
> so I have this:
>
> <code>
> rollDice :: IO Int
> rollDice = getStdRandom (randomR (1,6))
>
> rl :: [Int]
> rl = [ (getRndNum x) | x <- [1..] ]
>
> getRndNum :: Int -> Int
> getRndNum x = do n <- rollDice
> return n
> </code> *PS Pretend return is correctly aligned under n. dont what
> ahppens in copy and paste*
Other people have covered a lot about IO, but for your particular
problem of random numbers, here's a reasonably simple solution:
module RandomList where
import Random
seed :: Int
seed = 69
randomList :: [Int]
randomList = randomRs (1,6) (mkStdGen seed)
Usage:
RandomList> :t randomList
randomList :: [Int]
RandomList> take 10 randomList
[6,2,6,2,6,2,1,3,2,3]
RandomList>
The key to figuring out how on earth to use the combinations of
randomRs and generators is having good documentation on the Random
module, which I found here:
http://www.haskell.org/ghc/docs/latest/html/libraries/base/
System.Random.html#t%3ARandom
I'm guessing you're using hugs, which does give you the Random module,
but it's not exactly easy to figure out from reading the source code
(especially if you're a Haskell beginner)!
--
% Andre Pang : trust.in.love.to.save
More information about the Haskell-Cafe
mailing list