[Haskell-cafe] Overriding a Prelude function?
Ross Mellgren
rmm-haskell at z.odi.ac
Wed Apr 22 12:47:01 EDT 2009
True enough -- if you really want to redefine the monadic operator,
you have to use
{-# LANGUAGE NoImplicitPrelude #-}
import Prelude hiding ((>>), (>>=), return)
or something like it, although Michael's example didn't appear to be
going quite that far.
-Ross
On Apr 22, 2009, at 12:37 PM, Dan Weston wrote:
> Be aware that the do unsugars to (Prelude.>>), not your (>>), even
> if you hide (Prelude.>>):
>
> import Prelude hiding ((>>))
> m >> f = error "Call me!"
> main = putStrLn . show $ do [3,4]
> [5]
>
> The desugaring of the do { [3,4]; [5] } is (Prelude.>>) [3,4] [5] =
> [5,5], whereas you might have hoped for [3,4] >> [5] = error "Call
> me!"
>
> Dan
>
> Ross Mellgren wrote:
>> 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 at 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 at localhost ~]$
>>>
>>>
>>> _______________________________________________
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe at haskell.org <mailto:Haskell-Cafe at haskell.org>
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
More information about the Haskell-Cafe
mailing list