List traversal

From HaskellWiki
Jump to navigation Jump to search

Traversing a list is sometimes more difficult than it seems to be at the first glance. With "traversal" I mean to consume one or more lists and produce one or more new ones. Our goal is to do this efficiently and lazily.

As a running example I use the partitionEithers function that can be found in the Data.Either module since base-4.0.

Its type signature is

partitionEithers :: [Either a b] -> ([a], [b])

and it does what you expect:

Prelude Data.Either> partitionEithers [Left 'a', Right False, Left 'z']
("az",[False])
Prelude Data.Either> take 100 $ snd $ partitionEithers $ cycle [Left 'a', Right (0 :: Int)]
[0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0]

The second example is especially important because it shows that the input can be infinitely long and the output can be, too. That's the proof that the implementation is lazy. We will use this example as test for our implementations below.


First attempt - quadratic runtime, not lazy

In our first attempt we maintain a state containing two lists that we want to extend to the result lists step by step.

partitionEithers2 :: [Either a b] -> ([a], [b])
partitionEithers2 =
   let aux ab [] = ab
       aux (as, bs) (Left a  : es) = aux (as ++ [a], bs) es
       aux (as, bs) (Right b : es) = aux (as, bs ++ [b]) es
   in  aux ([], [])

This implementation works for finite lists but fails for infinite ones. You will also notice that it is quite slow. The reason is that appending something to a list like as requires length as steps in order to reach the end of as. Since we do this repeatedly we end up with quadratic runtime.


Second attempt - linear runtime, still not lazy

We have learned that appending something to a list is expensive. However prepending a single element is very cheap, it needs only constant number of operations. Thus we will implement the following idea: We prepend new elements to the result list and since this reverses the order of elements, we reverse the result lists in the end.

partitionEithers1 :: [Either a b] -> ([a], [b])
partitionEithers1 xs =
   let aux ab [] = ab
       aux (as, bs) (Left a  : es) = aux (a : as, bs) es
       aux (as, bs) (Right b : es) = aux (as, b : bs) es
       (ys,zs) = aux ([], []) xs
   in  (reverse ys, reverse zs)

This implementation is much faster than the first one but it cannot be lazy because reverse is not lazy.


Third attempt - linear runtime and full laziness

In order to get linear runtime and full laziness we must produce the list in the same order as the input. However we must avoid appending to the end of the list. Instead we must prepend elements to lists that become known in the future. We must be very careful that the leading elements of the result lists can be generated without touching the following elements. Here is the solution:

partitionEithers :: [Either a b] -> ([a], [b])
partitionEithers [] = ([], [])
partitionEithers (Left a : es) =
   let (as,bs) = partitionEithers es
   in  (a:as, bs)
partitionEithers (Right b : es) =
   let (as,bs) = partitionEithers es
   in  (as, b:bs)

It is crucial to know that a let binding matches the top-most data constructor lazily. The following expressions would match strictly and thus would fail:

   (\(as,bs) -> (a:as, bs)) $ partitionEithers es
   case partitionEithers es of (as,bs) -> (a:as, bs)

Matching the pair constructor strictly means that the recursive call to partitionEithers is triggered before the pair constructor of the result is generated. This starts a cascade that forces all recursive calls until the end of the input list.

This is different for lazy pattern matches. The above let can be rewritten equivalently to:

   let ~(as,bs) = partitionEithers es
   in  (a:as, bs)
   (\ ~(as,bs) -> (a:as, bs)) $ partitionEithers es
   case partitionEithers es of ~(as,bs) -> (a:as, bs)

or without the tilde as syntactic sugar:

   case partitionEithers es of ab -> (a : fst ab, snd ab)

Of course, both fst and snd contain strict pattern matches on the pair constructor but the key difference to above is that these matches happen inside the pair constructor of (a : fst ab, snd ab). That is, the outer pair constructor can be generated before the evaluation of ab is started.

Fourth attempt - expert solution

Now real experts would not recurse manually but would let foldr do this job. This allows for fusion. Additionally real experts would add the line (\ ~(as,bs) -> (as,bs)) in order to generate the pair constructor of the result completely independent from the input. This yields maximum laziness.

partitionEithersFoldr :: [Either a b] -> ([a], [b])
partitionEithersFoldr =
   (\ ~(as,bs) -> (as,bs)) .
   foldr
      (\e ~(as,bs) ->
         case e of
            Left a -> (a:as, bs)
            Right b -> (as, b:bs))
      ([], [])


Fifth attempt - your solution

If you are tired of all these corner cases that we need to respect in order to get full laziness then you might prefer to solve the problem by just combining functions that are known to be lazy. It is good style anyway to avoid explicit recursion. Of course, when combining lazy functions you must still take care that the combinators maintain laziness. Thus my exercise for you at the end of this article is to implement partitionEithers using standard functions, say, from base before version 4. A small hint: the module Data.Maybe turns out to be very useful.