A question for more experienced Haskell users than myself.
I have defined a class of data structures that can be used in a sorted
list:
> class SortedList s a where
> emptySort :: s a
> isEmptySort :: s a -> Bool
> findInSort :: s a -> a -> Maybe a
> addToSort :: s a -> a -> s a
> sortToList :: s a -> [ a ]
> listToSort :: [ a ] -> s a
And a class of finite maps that map a key to an element, whatever that
might be:
> class FiniteMap m k a where
> emptyMap :: m k a
> bindMap :: m k a -> k -> a -> m k a
> lookupMap :: m k a -> k -> Maybe a
All this is familiar to anyone who has read Okaskai.
Now it is obvious that I can use sorted lists as one implementation of
finite maps (of course, there may be many others). I can pair up a
key with the value and stick it in the sorted list:
> data Pair a b = Pair a b
> instance Eq k => Eq (Pair k a) where
> Pair x y == Pair x' y' = x == x'
> instance Ord k => Ord (Pair k a) where
> Pair x y <= Pair x' y' = x <= x'
> Pair x y > Pair x' y' = x > x'
> Pair x y < Pair x' y' = x < x'
But note that, when I ask for a key via findInSort, I need to give it
a blank, or zero, value:
> class ZeroVal a where
> zer:: a
and we assume that findInSort returns the value it found in the table
and not what was fed to it. Note, also, that Pair is different from
tuples, in the sense that the second value does not enter into the
calculation of the position at all (and therefore need not be in class
Ord).
The question is, how to make all this work cleanly. FiniteMap has one
more type parameter than SortedList, which is completely
understandable given the fact that we are pairing up the last two
types. (I have tried to give FiniteMap only two, and ran into
problems there as well).
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))
> instance (SortedList m (Pair k a), ZeroVal a) =>
> FiniteMap (MkFinMap m) k a where
> emptyMap = MkFinMap emptySort
> bindMap (MkFinMap t) k x = MkFinMap (addToSort t (Pair k x))
> lookupMap (MkFinMap t) k =
> let r = findInSort t (Pair k zer)
> in case r of
> Nothing -> Nothing
> Just (Pair k' x) -> Just x
And this does just what I want it to, at the cost of a type definition
(MkFinMap) that seems totally unnecessary. Assuming I am using a
balanced tree type BalTree to implement all this, it seems intuitively
that there should be someway that BalTree can work for both the finite
maps and the sorted lists. 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.
Is there any way to avoid this? Or is it just an inevitable
consequence of mixing types like this?
Dave Barton <*>
[EMAIL PROTECTED] )0(
http://www.averstar.com/~dlb