| [edited version of original message:]
| Now it is obvious that I can use sorted lists as one implementation of
| finite maps ... [but] the *only* way I have been able to make this work,
| after lots of trying and mind-bending, is to introduce a "phantom" type
| to allow me | to combine things appropriately:
|
| > data MkFinMap m k a = MkFinMap (m (Pair k a))
|
| And this does just what I want it to, at the cost of a type definition
| (MkFinMap) that seems totally unnecessary. ... This way, I have to
| export a type name, "MkFinMap", which is, in some sense, totally
| non-intuitive; sooner or later, when building his tree, the user will
| have to refer to "MkFinMap" in order to resolve the base type.
I don't really see why you find this non-intuitive. Yes, you can
use a sorted list to implement a finite map, and the type constructor
(MkFinMap s) is just the name for this implementation, based on a
sorted list implementation s. Your instance declaration captures
this very nicely:
instance (SortedList s (Pair k a)) => FiniteMap (MkFinMap s) k a where ...
Just read this as: "If s constructs sorted lists of (Pair k a),
then (MkFinMap s) constructs finite maps from k to a."
However, it's not clear to me that constructor classes are the right
solution to this problem at all. Parametric classes, introduced by
Chen, Hudak and Odersky back in 1992 may well do a better job. Alas,
there's been a tendency to ignore parametric classes on the (false)
assumption that constructor classes provide a better way to solve the
same problems. In my opinion, the two approaches are complementary.
In this case, we could define a parametric class SortedList such that
(s::SortedList a) means "s is a sorted list of a values." If you prefer,
you could write this simply as a two parameter class SortedList s a,
although that hides the distinction between parameter and result types.
A key point here is that both s and a parameters have kind *; there are
no constructor classes. With parametric type classes, you get a
slightly more aggressive overloading mechanism, coupled with a more
relaxed approach to ambiguity. The first of these points means that a
type (s::SortedList a, t::SortedList a) => ... can be simplified by
unifying s and t. The second means that a type (s::SortedList a) => ...
need not be considered as ambiguous if s, but not a, appears to the
right of the => sign. This means that you could define:
> class s :: SortedList a where
> emptySort :: s
> findInSort :: s -> a -> Maybe a
> ...
> class m :: FiniteMap k a where
> emptyMap :: m
> bindMap :: m -> k -> a -> m k a
> ...
> instance (s :: SortedList (Pair k a)) => s :: FiniteMap k a where ...
> ...
Sadly, none of the current Haskell implementations support parametric
type classes.
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.
All the best,
Mark