*Main> :t rollDie ~>> (rollDie ~>> rollDie)
rollDie ~>> (rollDie ~>> rollDie) :: Seed -> (Int, Seed)

This is a function. How exactly do you want ghci to show it? When you figure that out, feel free to make an instance of Show for it.

Meanwhile, you can just apply the function to a Seed value and see what happens:

*Main> rollDie ~>> rollDie ~>> rollDie $ 6
(1,1145965850)

michael rice wrote:
OK, I changed the operator from (>>) to (~>>). When I try to use it I get this:

[mich...@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 /<lrpal...@gmail.com>/* wrote:


    From: Luke Palmer <lrpal...@gmail.com>
    Subject: Re: [Haskell-cafe] Overriding a Prelude function?
    To: "michael rice" <nowg...@yahoo.com>
    Cc: "Ross Mellgren" <rmm-hask...@z.odi.ac>, "Dan Weston"
    <weston...@imageworks.com>, "haskell-cafe@haskell.org"
    <haskell-cafe@haskell.org>
    Date: Wednesday, April 22, 2009, 5:02 PM

    On Wed, Apr 22, 2009 at 1:47 PM, michael rice <nowg...@yahoo.com
    </mc/compose?to=nowg...@yahoo.com>> wrote:

        Here's what I get:

        [mich...@localhost ~]$ ghci
        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.
        Prelude> import Prelude hiding ((>>))


    You know, to avoid this nonsense you could just name the operator
    something else, like >>~, or ~>>, or $...@**!.  Operators are just names.

    Luke


        <interactive>:1:0: parse error on input `import'
        Prelude>

        =====

        I was passing seed0 to rollDie and getting back (r1,seed1)
                 passing seed1 to rollDie and getting back (r2,seed2)
                 passing seed2 to rollDie and getting back (r3,seed3)

        Just based on the problem text, I would guess that
                passing rollDie and seed0 to (>>) I would get back
        (r3,seed3),
        losing the intermediate random numbers r1 and r2 along the way, at
        least that's what I understood it to say.

        So, I know that next I'm probably going to have to do something to
        remedy that, but I haven't gotten to that next step yet. What is
        unsugar?

        Thanks in advance for your patience.

        Michael


        --- On *Wed, 4/22/09, Dan Weston /<weston...@imageworks.com
        </mc/compose?to=weston...@imageworks.com>>/* wrote:


            From: Dan Weston <weston...@imageworks.com
            </mc/compose?to=weston...@imageworks.com>>
            Subject: Re: [Haskell-cafe] Overriding a Prelude function?
            To: "Ross Mellgren" <rmm-hask...@z.odi.ac
            </mc/compose?to=rmm-hask...@z.odi.ac>>
            Cc: "michael rice" <nowg...@yahoo.com
            </mc/compose?to=nowg...@yahoo.com>>,
            "haskell-cafe@haskell.org
            </mc/compose?to=haskell-c...@haskell.org>"
            <haskell-cafe@haskell.org
            </mc/compose?to=haskell-c...@haskell.org>>
            Date: Wednesday, April 22, 2009, 12:37 PM

            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
             >>
             >> ==============
             >>
             >> [mich...@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)
             >>
             >> [mich...@localhost ~]$
             >>
             >>
             >> _______________________________________________
             >> Haskell-Cafe mailing list
             >> Haskell-Cafe@haskell.org
            <http://mc/compose?to=haskell-c...@haskell.org>
            <mailto:Haskell-Cafe@haskell.org
            <http://mc/compose?to=haskell-c...@haskell.org>>

             >> http://www.haskell.org/mailman/listinfo/haskell-cafe
             >



        _______________________________________________
        Haskell-Cafe mailing list
        Haskell-Cafe@haskell.org </mc/compose?to=haskell-c...@haskell.org>
        http://www.haskell.org/mailman/listinfo/haskell-cafe




_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to