[Haskell-beginners] Thompson Exercise 9.13

Daniel Fischer daniel.is.fischer at web.de
Thu Jul 15 11:19:46 EDT 2010


On Thursday 15 July 2010 15:46:15, dan portin wrote:
> > [...] it needs to traverse the entire list before it can start
> > assembling the result.
> > To avoid that, so the result can be assembled from the start of the
> > list, you need to make the pattern match on the second argument lazy,
> >
> > f (x,y) ~(xs,ys) = (x:xs,y:ys)
> >
> > or
> >
> > f (x,y) p = (x : fst p, y : snd p)
> >
> > Now
> >
> > f (x,y) (f (x1,y1) ([],[]))
> > ~> let (xs,ys) = f (x1,y1) ([],[]) in (x:xs, y:ys)
>
> This makes sense. I didn't realize Haskell was doing this.

I said it was subtle :)

> Of course, that could be a downside to evaluating by
> hand on paper, where you often 'think lazily.' I assumed Haskell
> evaluated the expression in a similar way to
> your 'let ...' clause.
>

Pattern matching is strict (if you're matching against a refutable pattern; 
matching a variable pattern or wildcard always succeeds, so no evaluation 
is ever necessary then).
Another way to achieve the same is

f (x,y) p = let (xs,ys) = p in (x:xs, y:ys)

Patterns bound in a let-expression or where-clause have an implicit ~, so a 
potential pattern-match failure is only reported when you're demanding a 
bound value which isn't there:

Prelude> let foo x mb = let Just xs = mb in Just (x:xs)
Prelude> foo True Nothing
Just [True*** Exception: <interactive>:1:19-30: Irrefutable pattern failed 
for pattern Data.Maybe.Just xs


> > > *last* :: [a] -> a
> > > last xs = head $ foldr f [] xs
> > >  where f :: a -> [a] -> [a]
> > >        f x [] = [x]
> > >        f x ys = ys ++ [x]
> >
> > last xs = head (reverse xs), yes, it's correct, but not very pretty.
> > And not very efficient since it builds a left-associated nest of (++)
> > applications and needs to pattern match to decide which branch to
> > take.
> >
> > last (1:2:3:4:[])
> > ~> head $ foldr f [] (1:2:3:4:[])
> > ~> head $ f 1 (f 2 (f 3 (f 4 [])))
> > ~> head $ f 1 (f 2 (f 3 [4]))
> > ~> head $ f 1 (f 2 ([4] ++ [3]))
> > ~> head $ f 1 (([4] ++ [3]) ++ [2])
> > ~> head $ ((([4] ++ [3]) ++ [2]) ++ [1]
> >
> > a) in the second branch of f, you don't actually need to concatenate,
> >
> > f x [] = [x]
> > f _ ys = ys
> >
> > works too, but is faster.
> >
> > b) you can get much faster by delaying the pattern match,
> >
> > f x ys = (case ys of { [] -> x; y:_ -> y }) : []
>
> Yes, nesting each element inside (++) operators was an oversight on my
> part. Your solution (a) is much cleaner, since
>
> head $ foldr f [] (1:2:3:[])
> ~> head $ f 1 (f 2 (f 3 []))
> ~> head $ f 1 (f 2 (3:[]))
> ~> head $ f 1 (3:[])
> ~> head $ (3:[])
>
> I'm confused about (b), however. I was under the
> impression<http://www.haskell.org/tutorial/patterns.html>that the
> pattern match
>
> f P1 ... P1N = E1
> f P2 ... P2N = E2
>
> is *semantically* equivalent to
>
> f x1 ... xn = case (x1, ..., xn) of { P1 ... P1n -> E1; P2 ... P2n ->
> E2}.
>
> Of course, "semantically equivalent" doesn't mean "as efficient."

That's the one point.
However, that's not the point here. It was late and very hot, so I didn't 
write it as clear as was desirable, the function in b) can also be written 
as

f x ys = z : []
  where
    z = case ys of
          [] -> x
          y:_ -> y

I think that makes it more understandable, the point is that the 
constructor (:) is applied on the RHS before we look whether ys matches [] 
or (_:_).

If we evaluate it for a short list:

head $ foldr f [] (1:2:3:[])
~> head $ f 1 (foldr f [] (2:3:[]))
~> head (z1 : [])
      where z1 = case foldr f [] (2:3:[]) of { [] -> 1; y:_ -> y }
~> z1 where z1 = case foldr f [] (2:3:[]) of { [] -> 1; y:_ -> y }
~> case foldr f [] (2:3:[]) of { [] -> 1; y:_ -> y }
~> case f 2 (foldr f [] (3:[])) of { [] -> 1; y:_ -> y }
~> case z2 : [] of { [] -> 1; y:_ -> y }
      where
        z2 = case foldr f [] (3:[]) of { [] -> 2; w:_ -> w }
~> z2 where z2 = case foldr f [] (3:[]) of { [] -> 2; w:_ -> w }
~> case foldr f [] (3:[]) of { [] -> 2; w:_ -> w }
~> case f 3 (foldr f [] []) of { [] -> 2; w:_ -> w }
~> case z3 : [] of { [] -> 2; w:_ -> w }
      where
        z3 = case foldr f [] [] of { [] -> 3; v:_ -> v }
~> z3 where z3 = case foldr f [] [] of { [] -> 3; v:_ -> v }
~> case foldr f [] [] of { [] -> 3; v:_ -> v }
~> case [] of { [] -> 3; v:_ -> v }
~> 3

We never have deep nesting, we always have progress looking at no more than 
two successive list elements and can let the start of the list be garbage 
collected almost immediately.

Now with

g x [] = [x]
g _ ys = ys

we get

head $ foldr g [] (1:2:3:[])
~> head $ g 1 (foldr g [] (2:3:[]))
-- we don't know which branch to take for g 1 _, so we
-- must evaluate foldr g [] (2:3:[]) to see
~> head $ g 1 (g 2 (foldr g [] (3:[])))
-- we don't know which branch to take for g 2 _, so
~> head $ g 1 (g 2 (g 3 (foldr g [] [])))
-- we don't know which branch to take for g 3 _, so
~> head $ g 1 (g 2 (g 3 []))
~> head $ g 1 (g 2 [3])
~> head $ g 1 [3]
~> head $ [3]
~> 3

And you see that we get nested calls to g, the nesting depth is length list 
and we hold on to the start of the list until we can finally apply head.
This doesn't require more reduction steps [both need O(length list) steps], 
but it requires O(length list) space vs O(1) space for the f above, hence 
this is much slower.

> I don't understand whether the move from matching against
> '_ ys' to y:_ is supposed to make the definition of f more efficient to
> compute, or whether the use of case expressions is
> supposed to.
>

What makes it more efficient is that we start constructing the result 
before we investigate the arguments. Thus we can know which branch to take 
before we've reached the end of the list.

> > > *init* :: [a] -> [a]
> > > init xs = tail $ foldr f [] xs
> > >  where f :: a -> [a] -> [a]
> > >        f x [] = [x]
> > >        f x (y:xs) = y : x : xs
> >
> > Correct too, but again not very efficient since it has to find the
> > last element and bubble it to the front.
> >
> > Much faster:
> >
> > import Data.Maybe (fromMaybe)
> >
> > init' :: [a] -> [a]
> > init' = fromMaybe (error "init': empty list") . foldr f Nothing
> >    where
> >        f x mb = Just $ case mb of
> >                          Just xs -> x:xs
> >                          Nothing -> []
> >
> > By delaying the pattern match on the Maybe until after the constructor
> > is applied, we can start building the output with minimal delay (we
> > only need to look whether there's a next list element to decide
> > whether to cons it to the front or not).
>
> I'm not sure what you mean by "applying the constructor [Just],"

Similar to the above,

f x mb = Just zs
  where
    zs = case mb of
            Just xs -> x:xs
            Nothing -> []

By having the result Just something before we inspect the arguments, we can 
start building the result almost immediately, we only have to see whether 
the second argument comes from a call to f (in other words, whether there's 
at least one further element in the list) to know which branch to take.
If we pattern match first, we again build a nest of applications of f until 
we reach the end of the list and can only then start to unwind the stack.

> or which function
> you are forcing to evaluate (after 'applying the constructor').
> Obviously, I need to
> learn more about Haskell's monads and type constructors.
>

Nothing to do with monads, it's all about laziness and pattern matching.
As a general rule, in

foldr fun z xs

you want fun to be as lazy as possible in its second argument, i.e. do 
everything you can do before even looking at it.
If you can even do something before looking at fun's first argument, all 
the better.

> > > (2) Is there a way to eliminate the
> > > post-processing of the lists (i.e., *head* in *last* and *tail* in
> > > *init*)?
> >
> > Not in a clean way.
> >
> > Let us consider last first.
> >
> > Suppose we had
> >
> > last xs = foldr f z xs
> >
> > without post-processing.
> > Since foldr f z [] = z and last [] = error "Prelude.last: empty list",
> > we must have z = error "...".
> > Now last (... x:[]) = x and
> > foldr f z (... x:[]) = ... (f x z)
> >
> > So f x y = y if y is not error "..." and f x (error "...") = x, that
> > means f would have to find out whether its second argument is a
> > specific error and return its first argument in that case, otherwise
> > its second argument. It's possible to do that, but very unclean.
>
> That's helpful. I was trying to *name* a list at a particular stage of
> construction, and it
> failed for just this reason.



More information about the Beginners mailing list