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