[Haskell-cafe] Re: Implementing "unionAll"

Leon Smith leon.p.smith at gmail.com
Thu Feb 18 20:22:08 EST 2010


On Thu, Feb 18, 2010 at 3:07 AM, Evan Laforge <qdunkan at gmail.com> wrote:
> BTW, I notice that your merges, like mine, are left-biased.  This is a
> useful property (my callers require it), and doesn't seem to cost
> anything to implement, so maybe you could commit to it in the
> documentation?

Also, I did briefly consider giving up left bias.  GHC has an
optimization strategy that seeks to reduce pattern matching,  and due
to interactions with this I could have saved a few kilobytes of -O2
object code size by giving up left-bias.

For example:

    module MergeLeft where

    mergeBy :: (a -> a -> Ordering) -> [a] -> [a] -> [a]
    mergeBy cmp = loop
      where
        loop [] ys  = ys
        loop xs []  = xs
        loop (x:xs) (y:ys)
          = case cmp x y of
             GT -> y : loop (x:xs) ys
             _  -> x : loop xs (y:ys)

compiles ghc-6.12.1 -O2 to a 4208 byte object file for x64 ELF.   By
changing the very last line to:

             _  -> x : loop (y:ys) xs

I get a 3336 byte object file instead,  but of course this is no
longer left- (or right-) biased.    Repeat this strategy across the
entire module,  and you can save 3 kilobytes or so.   However,  in
today's modern computing environment,  left-bias is clearly a greater
benefit to more people.

If you are curious why,  I suggest taking a look at GHC's core output
for each of these two variants.   The hackage package "ghc-core"
makes this a little bit more pleasant,  as it can pretty-print it for
you.

It's amazing to think that this library,  at 55k (Optimized -O2 for
x64),  would take up most of the memory of my very first computer,  a
Commodore 64.   Of course,  I'm sure there are many others on this
list who's first computers had a small fraction of 64k of memory to
play with.  :-)


More information about the Haskell-Cafe mailing list