Data.Ord and Heaps
apfelmus
apfelmus at quantentunnel.de
Thu Feb 14 06:53:19 EST 2008
Ross Paterson wrote:
> Stephan Friedrichs wrote:
>> apfelmus wrote:
>>> [newtype Ord a => Reverse a = Reverse { unReverse :: a }]
>>>
>>> Yes. I mean "non-standard" in the software-reuse sense, i.e. Ord is for
>>> user-defined orderings and should be the only such mechanism in order
>>> to enable reuse. In fact, Data.Heap clearly shows that Data.Ord is
>>> currently missing functionality.
>> Ah, now I see. The entire ordering policy mechanism - no matter how it
>> is going to be solved - belongs into Data.Ord and not in Data.Heap. As
>> soon as Data.Ord provides a solution, I'll use it in Data.Heap.
>
> Unfortunately the Data.Ord module is constrained to use only Haskell
> 98 features, because it is used by all implementations. So it could
> include the above Reverse (also mentioned in the group-by HW paper),
> but not the various OrdPolicy proposals.
The advantage of policies is that the Heap interface is implemented
exactly once. Using Reverse is no problem, but you'd have to implement
one normal version (MinHeap a) and one boilerplate version (MinHeap
(Reverse a)). Implementing Heap p a for both p = Identity and p =
Reverse at once can eliminate this boilerplate.
Fortunately, the "polymorphic policies" Identity and Reverse can be
implemented in Haskell98!
data OrdBy p a = OrdBy { unOrdBy :: a }
class OrdPolicy p where
compare' :: Ord a => OrdBy p a -> OrdBy p a -> Ordering
instance (Ord a, OrdPolicy p) => Ord (OrdBy p a) where
compare = compare'
class Heap h where
empty :: Ord a => h a
insert :: Ord a => a -> h a -> h a
viewHead :: Ord a => h a -> Maybe (a, h a)
data HeapP p a = ... -- MinHeap (OrdBy p a)
instance OrdPolicy p => Heap (HeapP p) where
...
What probably can't be done in Haskell98 are policies p that only work
for specific types, i.e. such that OrdBy p a is not always an instance
of Ord . Of course, there is the question whether they are needed or
whether they are just overengineering. I hope that Stephan Friedrichs
has a compelling example for the former? :)
That being said, I think there might be a Haskell98 way to implement
even them. The trick here is that while class contexts like Ord (OrdBy
p a) are not H98, contexts like Ord (p a) with type variables only are.
class Identity f where
to :: a -> f a
from :: f a -> a
-- subject to to . from = id and from . to = id
-- the latter holds automatically thanks to parametricity
data Heap p a = ... -- MinHeap (p a)
empty :: (Identity p, Ord (p a)) => Heap p a
insert :: (Identity p, Ord (p a)) => a -> Heap p a -> Heap p a
viewHead :: (Identity p, Ord (p a)) => Heap p a -> Maybe (a, Heap p a)
In other words, the context (Identity p, Ord (p a)) expresses what a
multi-parameter type class OrdPolicy p a would do, too. I wonder
whether this trick can be used to encode arbitrary multi-parameter type
classes in plain Haskell98. I guess not, because interestingly, Ord (p
a) is not a valid context for class or instance declarations, it's only
ok for function definitions. So, defining stuff like
instance Show (p a) => Show (Heap p a) where ...
is not possible, which limits this approach somewhat. Another limit of
non-polymorphic policies is that the Heap class would have to be
multi-parameter (which it should be anyway of course, but that's not H98).
Regards,
apfelmus
More information about the Libraries
mailing list