
OK, I changed the operator from (>>) to (~>>). When I try to use it I get this:
[michael@localhost ~]$ ghci rand
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 ( rand.hs, interpreted )
Ok, modules loaded: Main.
*Main> rollDie ~>> (rollDie ~>> rollDie)
<interactive>:1:0:
No instance for (Show (Seed -> (Int, Seed)))
arising from a use of `print' at <interactive>:1:0-32
Possible fix:
add an instance declaration for (Show (Seed -> (Int, Seed)))
In a stmt of a 'do' expression: print it
*Main>
Michael
--- On Wed, 4/22/09, Luke Palmer
I think
import Prelude hiding ((>>))
does that.
-Ross
On Apr 22, 2009, at 11:44 AM, michael rice wrote:
I've been working through this example from: http://en.wikibooks.org/wiki/Haskell/Understanding_monads
I understand what they're doing all the way up to the definition of (>>), which duplicates Prelude function (>>). To continue following the example, I need to know how to override the Prelude (>>) with the (>>) definition in my file rand.hs.
Michael
==============
[michael@localhost ~]$ cat rand.hs import System.Random
type Seed = Int
randomNext :: Seed -> Seed randomNext rand = if newRand > 0 then newRand else newRand + 2147483647
where newRand = 16807 * lo - 2836 * hi (hi,lo) = rand `divMod` 127773
toDieRoll :: Seed -> Int toDieRoll seed = (seed `mod` 6) + 1
rollDie :: Seed -> (Int, Seed) rollDie seed = ((seed `mod` 6) + 1, randomNext seed)
sumTwoDice :: Seed -> (Int, Seed) sumTwoDice seed0 = let (die1, seed1) = rollDie seed0 (die2, seed2) = rollDie seed1 in (die1 + die2, seed2)
(>>) m n = \seed0 ->
let (result1, seed1) = m seed0 (result2, seed2) = n seed1 in (result2, seed2)
[michael@localhost ~]$
_______________________________________________
Haskell-Cafe mailing list Haskell-Cafe@haskell.org mailto:Haskell-Cafe@haskell.org
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe