I've been thinking about this some more (and actually trying it,
getting my hands dirty) and while the essential elegance remains
unchanged (and, in fact, my appreciation for it has increased), some
more thoughts have come up.

Mark Jones wrote:

   As a final comment, I'll go even further: It's not clear to me that
   *any form of overloading* is the right solution here.  Here's another
   version of your code in a more explicit style:

     data Pair a b = Pair { fst'::a, snd'::b }

     data SortedList s a  = SortedList { emptySort   :: s,
                                         isEmptySort :: s -> Bool,
                                         findInSort  :: s -> a -> Maybe a,
                                         addToSort   :: s -> a -> s,
                                         sortToList  :: s -> [a],
                                         listToSort  :: [a] -> s }

     data FiniteMap m k a = FiniteMap { emptyMap     :: m,
                                        bindMap      :: m -> k -> a -> m,
                                        lookupMap    :: m -> k -> Maybe a }

     finiteMapFromSort  :: SortedList s (Pair k a) -> FiniteMap s k a
     finiteMapFromSort s = FiniteMap {emptyMap, bindMap, lookupMap}
      where emptyMap      = emptySort s
            bindMap m k a = addToSort s m (Pair k a)
            lookupMap m k = map snd' (findInSort s m (Pair k undefined))

   There are elements here of both the previous solutions.  The datatypes
   themselves are most closely related to the version using parametric type
   classes, while the function "finiteMapFromSort" plays the same role in
   naming the construction at the value level as your MkFinMap constructor
   did at the type level.

What I missed on the initial reading (and what took me trying it out
to get through my thick skull) is that this solution essentially adds
an argument to each function call.  For example, the type of emptySort
is now SortedList s a -> s, not just s.  So I have to say "emptySort
foo" to get my initial, empty sorted list.

Now there's nothing wrong with this --- that's what aliases (or even
classes and instances) are for.  What I am now disputing is Mark's
claim above that no form of overloading is used here.  In fact, this
*is* overloading --- with the dictionary parameter made explicit.  In
"emptySort foo" above, "foo" is the dictionary.

But this little trick lets the Haskell programmer (such as myself) do
something really neat --- get his grubby little hands on the
dictionaries and manipulate them.  If we use a class in conjunction
with the "dictionary data types" above (if I may abuse terminology in
this way), then we can get the *effect* of parametric classes (and a
lot of other things as well) without having them implemented in the
language.  Because the data type definition "groups" all of the data
parameters in its scope, it also lets us collapse many (I don't know
about all) of the cases where we need multi-parameter classes into a
single type parameter class.  This is truly elegant.

In fact, I am having to restrain myself from running right off to
Mark's paper on monad transformers and modular interpreters to see if
I can't get all the code in that paper (which was in Gofer) to work
using this technique.  Unfortunately, my company doesn't pay me to do
those kinds of little, two week digressions.  But my palms are
itching.........

                                        Dave Barton <*>
                                        [EMAIL PROTECTED] )0(
                                        http://www.averstar.com/~dlb


Reply via email to