[Haskell-cafe] How Albus Dumbledore would sell Haskell

Dan Weston westondan at imageworks.com
Fri Apr 20 20:13:37 EDT 2007


Simon Peyton-Jones wrote:
> Lots of interesting ideas on this thread, and Haskell-Cafe threads are *supposed* to wander a bit.  But, just to remind you all: I'm particularly interested in
> 
>   concrete examples (pref running code) of programs that are
>        * small
>        * useful
>        * demonstrate Haskell's power
>        * preferably something that might be a bit
>                tricky in another language
> 
> I have lots of *general* ideas.  What I'm hoping is that I can steal working code for one or two compelling examples, so that I can spend my time thinking about how to present it, rather than on dreaming up the example and writing the code.

Put up or shut up, huh? OK, I have attached my feeble contribution for 
consideration. Not quite as trivial as a prime number generator.

Since many in the audience might be database people, it might be 
instructive how some simple relational algebra (inner join, transitive 
closure) can be done from scratch (and without looking first at how 
others do it!). It's not quite point-free, but I was surprised how 
easily the set-like list invariant (sorted, no duplicates) was preserved 
through many of the operations, allowing me to junk the set datatype I 
started out with. In a non-FP language, I would have likely overlooked 
this. Also, I reminded me of how Haskell enables the easy and powerful 
method of writing a correct by naive algorithm and continuously 
transforming it into what you want. In C++, the code noise is so high 
that this would be prohibitive and tedious.

Obviously, some QuickCheck is needed to round things off, but I ran out 
of time for this week.

There are no monads, but I slipped the categorical product operator *** 
in there, along with lots of higher-order functions and showed how 
easily one-off utility functions are created when needed.

It all fits on one slide. Plus, the indentation is so visually 
appealing! Code as art.

Dan
-------------- next part --------------
module TransitiveClosure(innerJoin,transitiveClosure) where

import Data.List(sort,nubBy)
import Control.Arrow((***))

----------------------------------------------------------------------
-- RELATIONAL ALGEBRA

ifKeyMatchesAddValue seekKey (findKey,value) =
                  if seekKey === findKey then (:) value
                                         else id

lookupAll   seekKey      = foldr (ifKeyMatchesAddValue seekKey) []
lookupAllIn keyValueDict = flip lookupAll keyValueDict

-- PRE : abDict and bcDict are set-like
-- POST: Returned   acDict is  set-like
innerJoin :: (Ord a, Ord b, Ord c) => [(a, b)] -> [(b, c)] -> [(a, c)]
innerJoin abDict bcDict  = concatMap innerJoinFor joinKeys
  where getKeys          = map fst
                 `andThen` removeDupsFromSorted
        joinKeys         = getKeys abDict
        joinedValues     = lookupAllIn abDict
                 `andThen` concatMap (lookupAllIn bcDict)
                 `andThen` sortAndRemoveDups
        innerJoinFor     = dup -- key into (joinKey,seekKey)
                 `andThen` (repeat       {- joinKey -} ***
                            joinedValues {- seekKey -})
                 `andThen` uncurry zip   -- (joinKey,joinedValues)

-- PRE : Arg is set-like
-- POST: Returned is set-like, transitiveClosure is idempotent
transitiveClosure :: (Ord a) => [(a, a)] -> [(a, a)]
transitiveClosure  aaDict
      | aaDict === aaDictNew = aaDictNew
      | otherwise            = transitiveClosure aaDictNew
  where aaDictNew            = mergeInSelfJoin aaDict
        mergeInSelfJoin d    = d `merge` innerJoin d d

----------------------------------------------------------------------
-- USING LISTS AS SETS

-- DEF: A list is set-like if it is in strictly increasing order

-- Why is this not in Prelude?
dup x = (x,x)

-- I prefer reading function composition from left-to-right
andThen = flip (.)

-- Uses < instead of == to preserve set-like structures
x === y = not (x < y || y < x)

-- PRE : Arg is sorted
-- POST: Result is set-like
removeDupsFromSorted :: Ord a => [a] -> [a]
removeDupsFromSorted = nubBy (===)

-- POST: Result is set-like
sortAndRemoveDups :: Ord a => [a] -> [a]
sortAndRemoveDups = sort
          `andThen` removeDupsFromSorted

-- PRE : Args  are set-like
-- POST: Result is set-like, the sorted union of args
merge as []  = as
merge []  bs = bs
merge aas@(a:as) bbs@(b:bs) | a < b     = a : merge as  bbs
                            | b < a     = b : merge aas bs
                            | otherwise = a : merge as  bs


More information about the Haskell-Cafe mailing list