[Haskell] help -- need a random number

Marc A. Ziegert coeus at gmx.de
Thu Apr 26 14:11:23 EDT 2007


module Dice where

import System.Random
import System.IO.Unsafe (unsafePerformIO,unsafeInterleaveIO)
import Data.List (unfoldr)

dice4,dice6,dice8,dice10,dice12,dice20,dice666 :: [Int]
dice4 = randomRs (1,4) (read "foo"::StdGen)
dice6 = randomRs (1,6) (mkStdGen 5)
dice8 = randomRs (1,8) (unsafePerformIO newStdGen)
dice10 = unfoldr (Just . randomR (1,10)) (read "42"::StdGen)
dice12 = fmap ((+1).(mod `flip` 12)) $ randoms (read "bar"::StdGen)
dice20 = [succ $ x `mod` 20|x<-unfoldr (Just . random) (mkStdGen 23)]
dice666 = unfoldr (\io_a -> Just . unsafePerformIO $ fmap ((,)`flip` io_a) io_a) $ randomRIO (1,666)




Am Donnerstag, 26. April 2007 18:58 schrieb robert bauer:
> Hi,
> 
> I need some random numbers.  The documentation identifies StdGen, but I can't figure out how to invoke it.  The documentation is great
> in every way, except an actual example that I can essentially cut and paste.
> 
> Thanks
> 
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
> 
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: not available
Url : http://www.haskell.org/pipermail/haskell/attachments/20070426/29212dd4/attachment.bin


More information about the Haskell mailing list