Random number example

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@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> Can I employ a 'do' expression from the command line? Also, can I now use functions (>>) (>>=) and 'return' defined in the Prelude and still have this code work? Michael ================== {-# LANGUAGE NoImplicitPrelude #-} import Prelude hiding ((>>), (>>=), return) type Seed = Int type Random a = Seed -> (a, Seed) randomNext :: Seed -> Seed randomNext rand = if newRand > 0 then newRand else newRand + 2147483647 where newRand = 16807 * lo - 2836 * hi (hi,lo) = rand `divMod` 127773 rollDie :: Random Int rollDie seed = ((seed `mod` 6) + 1, randomNext seed) (>>) :: Random a -> Random b -> Random b (>>) m n = \seed0 -> let (result1, seed1) = m seed0 (result2, seed2) = n seed1 in (result2, seed2) (>>=) :: Random a -> (a -> Random b) -> Random b (>>=) m g = \seed0 -> let (result1, seed1) = m seed0 (result2, seed2) = (g result1) seed1 in (result2, seed2) return :: a -> Random a return x = \seed0 -> (x, seed0) sumTwoDice :: Random Int sumTwoDice = rollDie >>= (\die1 -> rollDie >>= (\die2 -> return (die1 + die2)))

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@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

So there are a couple problems. First is you are trying to rebind prelude functions, when instead you should be creating an instance of Monad. This requires a bit of shuffling because without language extensions you can't instance Monad Random for your type of Random, as it is a type synonym. So, changing the type synonym to a newtype and instancing monad, you get: module Rand9b where import Control.Applicative (Applicative(..), (<$>), (<*>)) import Control.Monad (ap, liftM) type Seed = Int newtype Random a = Rand { unRand :: (Seed -> (a, Seed)) } randomNext :: Seed -> Seed randomNext rand = if newRand > 0 then newRand else newRand + 2147483647 where newRand = 16807 * lo - 2836 * hi (hi,lo) = rand `divMod` 127773 rollDie :: Random Int rollDie = Rand $ \ seed -> ((seed `mod` 6) + 1, randomNext seed) instance Monad Random where (>>=) = randomBind return = randomReturn instance Functor Random where fmap = liftM instance Applicative Random where pure = return (<*>) = ap randomBind :: Random a -> (a -> Random b) -> Random b m `randomBind` g = Rand $ \seed0 -> let (result1, seed1) = unRand m $ seed0 (result2, seed2) = unRand (g result1) $ seed1 in (result2, seed2) randomReturn :: a -> Random a randomReturn x = Rand $ \ seed0 -> (x, seed0) sumTwoDice :: Random Int sumTwoDice = (+) <$> rollDie <*> rollDie I also threw in instances of Functor and Applicative, so that I could simplify sumTwoDice using applicative form (much nicer, no? Applicative is totally rockin') Now you need one more thing, a way to convert a series of Random actions into a pure function: runRandom :: Seed -> Random a -> a runRandom s f = fst . unRand f $ s which now makes what you want to do in GHCi easy and well wrapped: Prelude> :reload [1 of 1] Compiling Rand9b ( rand9b.hs, interpreted ) Ok, modules loaded: Rand9b. *Rand9b> runRandom 0 sumTwoDice 3 Hope this helps, -Ross On Apr 23, 2009, at 11:28 AM, michael rice wrote:
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@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>
Can I employ a 'do' expression from the command line?
Also, can I now use functions (>>) (>>=) and 'return' defined in the Prelude and still have this code work?
Michael
==================
{-# LANGUAGE NoImplicitPrelude #-}
import Prelude hiding ((>>), (>>=), return)
type Seed = Int type Random a = Seed -> (a, Seed)
randomNext :: Seed -> Seed randomNext rand = if newRand > 0 then newRand else newRand + 2147483647 where newRand = 16807 * lo - 2836 * hi (hi,lo) = rand `divMod` 127773
rollDie :: Random Int rollDie seed = ((seed `mod` 6) + 1, randomNext seed)
(>>) :: Random a -> Random b -> Random b (>>) m n = \seed0 -> let (result1, seed1) = m seed0 (result2, seed2) = n seed1 in (result2, seed2)
(>>=) :: Random a -> (a -> Random b) -> Random b (>>=) m g = \seed0 -> let (result1, seed1) = m seed0 (result2, seed2) = (g result1) seed1 in (result2, seed2)
return :: a -> Random a return x = \seed0 -> (x, seed0)
sumTwoDice :: Random Int sumTwoDice = rollDie >>= (\die1 -> rollDie >>= (\die2 -> return (die1 + die2)))
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Apr 23, 2009, at 11:28 , michael rice wrote:
<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
Pretty much any time you get this kind of message, you've forgotten to include one or more arguments (how many is indicated by the number of "->"s) so ghci is trying to print a function. In this case, while the definition of sumTwoDice *looks* like it doesn't take any arguments, if you look at the definition of the Random type, it is a function (in fact, the very type ghci is trying to print). You need to give it a seed before it will produce a result. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH
participants (4)
-
Brandon S. Allbery KF8NH
-
Daniel Fischer
-
michael rice
-
Ross Mellgren