[Haskell-cafe] Random number example

Daniel Fischer daniel.is.fischer at web.de
Thu Apr 23 11:46:13 EDT 2009


Am Donnerstag 23 April 2009 17:28:58 schrieb michael rice:
> I pretty much followed the sequence of steps that led to this final code
> (see below), but will be looking it over for a while to make sure it sinks
> in. In the meantime, I get this when I try to use it (sumTwoDice) at the
> command line:
>
> [michael at localhost ~]$ ghci rand9
> GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
> Loading package ghc-prim ... linking ... done.
> Loading package integer ... linking ... done.
> Loading package base ... linking ... done.
> [1 of 1] Compiling Main             ( rand9.hs, interpreted )
> Ok, modules loaded: Main.
> *Main> sumTwoDice
>
> <interactive>:1:0:
>     No instance for (Show (Seed -> (Int, Seed)))
>       arising from a use of `print' at <interactive>:1:0-9
>     Possible fix:
>       add an instance declaration for (Show (Seed -> (Int, Seed)))
>     In a stmt of a 'do' expression: print it
> *Main>
>

sumTwoDice is a function, those have no (meaningful) Show instance.
What you probably wanted is

*Main> sumTwoDice 123456
*Main> 789

>
> Can I employ a 'do' expression from the command line?

Sure:
Prelude> do { line <- getLine; putStrLn (reverse line); putStrLn (drop 4 line) }
some input
tupni emos
 input

Just the do-expression must be an IO-action (which is then executed, like the above 
example) or it must have a showable type like

Prelude> do { x <- [1 .. 5]; let { y = x^2+1 }; [1,5 .. y] }
[1,1,5,1,5,9,1,5,9,13,17,1,5,9,13,17,21,25]


>
> Also, can I now use functions (>>) (>>=) and 'return' defined in the
> Prelude and still have this code work?

Almost. You would have to make Random an instance of Monad to use the Prelude (>>=), (>>) 
and return, but you cant make a type synonym like

type Random a = Seed -> (a,Seed)

an instance of a type class. So you have to put it inside a newtype wrapper:

newtype Random a = R (Seed -> (a,Seed))

instance Monad Random where
    return x = R (\s -> (x,s))
    (R r) >>= f = R $ \s -> let { (x,s') = r s; R g = f x } in g s'
>
> Michael
>



More information about the Haskell-Cafe mailing list