[Haskell-cafe] Re: Where do I put the seq?

Peter Verswyvelen bugfact at gmail.com
Thu Aug 20 04:52:53 EDT 2009


This is very very informative, thanks.
One thing I still struggle with (because I haven't practiced much I guess)
is writing down the desugaring/evaluation/expansion/reduction (how do you
call it?). I know how to do it more or less (tried it for a fix fac, since
fix feels like magic for an imperative programmer). This is unfortunate,
because the claim that "Haskell is easier to reason with" together with
"controlling space/time" only works I guess if you (1) developed an
intuition about how the evaluation exactly works and/or (2) are trained in
this algebraic rewriting (which I was 20 years ago ;-) If I do the
rewriting, I often get it wrong (too lazy, too strict) and this it is rather
useless. And many of the examples I've seem seem to skim many "obvious"
rewriting steps that don't feel that obvious to me.

But you gave a good exercise here :-)

This is typical for when I see Haskell code from experts: how do they make
it so compact? Often the code is unreadable then, but in the case of your
cleanup, I had to feeling "why didn't write it like that in the first place?
It seems so obvious" ;-) This also has an intimidating effect sometimes,
since as a newbie (and it feels that I'm still a newbie after a year) it's
hard to show code without looking like a fool. Luckily Haskell people are
very friendly and helpful!

On Thu, Aug 20, 2009 at 10:18 AM, Ryan Ingram <ryani.spam at gmail.com> wrote:

> On Wed, Aug 19, 2009 at 1:20 PM, Peter Verswyvelen<bugfact at gmail.com>
> wrote:
> > Well I really wrote this code as an exercise, and it was a good one. Now
> I
> > (or someone) needs to explain why it works.
>
> There's a bit of trickiness, but it's not that hard when you break it down.
>
> Lets look at a simplified version of "test":
>
> test = do
>    x <- inp
>    out "hello"
>    out x
>    test
>
> Desugaring a bit:
>
> test
> = inp >>= \x -> out hello >> out x >> test
> = S (\(i:is) -> (is, empty, i))
>   >>= \x -> S (\is -> (is, singleton "hello", ()))
>   >>= \_ -> S (\is -> (is, singleton x, ()))
>   >>= \_ -> test
>
> Now, inlining >>= and simplifying, we get:
>
> test = S (\i0 -> let
>           (i1, o1, x) = (\(i:is) -> (is, empty, i)) i0
>           (i2, o2, _) = (i1, singleton "hello", ())
>           (i3, o3, _) = (i2, singleton x, ())
>           (i4, o4, res) = step test i3
>           outputs = o1 `mappend` o2 `mappend` o3 `mappend` o4
>      in (i4, outputs, res))
>
> The first thing to notice is that when we run "test" by giving it some
> input, we *immediately* get a triple back:
>    (i4, outputs, res)
> with the values in the triple being unevaluated thunks.
>
> "res" is _|_; trying to evaluate it will infinite loop.  Similarily
> for i4.  But fortunately we never do; getOutput throws them both away.
> So the only thing we care about is "outputs".
>
> outputs is infinite as well, but we have hope!  As long as `mappend`
> is lazy in its second argument, we might be able to get some data out!
>
> Lets simplify Data.DList a bit:
>
> mappend = (.)
> singleton = (:)
> empty = id
> fromList = (++)
> toList = ($ [])
>
> Now lets try to evaluate (toList outputs):
>
> toList outputs
> = ($ []) (o1 . o2 . o3 . o4)
> = o1 . o2 . o3 . o4 $ []
> = o1 (o2 (o3 (o4 [])))
>
> We need to evaluate o1 in order to call it.  There is a possibility
> that it is _|_ :
>    (i1, o1, x) = (\(i:is) -> (is, empty, i)) i0
>
> Therefore
>   o1 = case i0 of
>       (i:is) -> empty
>       [] -> error "pattern match failure"
>    i1 = case i0 of
>       (i:is) -> is
>       [] -> error "pattern match failure"
>    x = case i0 of
>        (i:is) -> i
>        [] -> error "pattern match failure"
>
> So as long as you type a line, "o1" will be "empty" (= id).  But we
> don't know that you necessarily will type an input line, so the code
> *has* to wait for the line of input from the user, and can't print any
> later values.  (This is where you get into some of the craziness of
> lazy I/O)
>
> Once you type a line, i0 gets bound to (whatever you type : some lazy
> thunk representing the rest of the input) and o1 gets evaluated to id.
>
> toList outputs
> = o1 (o2 (o3 (o4 [])))
> = id (o2 (o3 (o4 [])))
> = o2 (o3 (o4 []))
>
> o2 and o3 are easy:
>           (i2, o2, _) = (i1, singleton "hello", ())
>           (i3, o3, _) = (i2, singleton x, ())
> therefore
>    o2 = ("hello" :)
>    o3 = (x :)
>
> toList outputs
> = o2 (o3 (o4 []))
> = ("hello":) ( (x:) (o4 []) )
> = "hello" : x : (o4 [])
>
> Now we have some data!  We can output these two elements without
> evaluating o4 at all!
>
> So we do, and then we need to evaluate o4.  But that just is starting
> over; o4 = getOutputs (step test i3).  We do have a different input
> (i3 vs. i0), but the rest of the logic is the same, and we keep going
> until we get to the end of the input list, at which point the pattern
> match failure in "inp" hits us.
>
> > But is this monad really useful? I mean it would be straightforward to
> write
> > this using the ST monad I guess?
>
> It's kind of useful.  I don't think I'd use ST, though.  It's isomorphic to
> StateT [String] (Writer (DList String))
>
> > Anyway, the reason why I want this pure code is that even with a console
> > based game, I don't want IO in it, since recording the input and
> replaying
> > it is vital to reproduce the actions the user did, and if things go wrong
> > (they always do), the log of all input can be used to restore the exact
> game
> > play. Of course you can do the same using imperative techniques and IO
> > redirection (which I did for my old games), but with this pure code you
> > don't have to worry about other places where IO could be used.
>
> For logging/testing/whatever, I suggest building your monad based off
> of MonadPrompt; it guarantees that all impure actions go through a
> datatype which you can then log.  Check it out!
> http://hackage.haskell.org/package/MonadPrompt
>
> You can then change the implementation of "what does this impure
> action do" without changing any of the logging or gameplay code.  For
> example, you could have a "object agent monad" which each character
> runs under, that is able to observe parts of the gamestate, and then
> write an interpreter that allows the user to play the game (through an
> impure I/O interface that draws to the screen) and another interpreter
> which runs an AI (through a pure functional or memory-state-based
> interface).
>
>  -- ryan
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090820/84c451a9/attachment.html


More information about the Haskell-Cafe mailing list