Stephan Friedrichs wrote:
I just uploaded a generalised heap (min-, max- and custom-heaps) implementation:

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/heap-0.1

Feedback would be appreciated :)

Feedback: I think the HeapPolicy thing is too non-standard. The canonical way would be to use a MinHeap and let the Ord instance handle everything. A MaxHeap can then be obtained via a different Ord instance

   newtype Ord a => Reverse a = Reverse { unReverse :: a }

   instance Ord a => Ord (Reverse a) where
     compare = comparing unReverse

This newtype should be in Data.Ord, of course. Being minimum/maximum-agnostic seems like a noble goal but turns out not to be that good. To see why, I'd like to report the first documentation bug: will a custom heap's head be the minimum or the maximum with respect to a custom heapCompare ? (ok, the docs for head indicate minimum, but the docs for HeapPolicy should say so, too.)


Simply setting

  type MaxHeap a = MinHeap (Reverse a)

is inferior to a "native" MaxHeap since we'd have to pack/unpack the Reverse all the time. But a type class for heaps - which should be present anyway - can solve that problem:

  class Heap h where
     empty    :: h a
     insert   :: Ord a => a -> h a -> h a
     viewHead :: Ord a => h a -> Maybe (a, h a)

     fromAscList :: Ord a => [a] -> h a
     toAscList   :: Ord a => h a -> [a]


     null    :: Ord a => h a -> Bool
     null = isNothing . viewHead

     singleton :: Ord a => a -> h a
     singleton = flip insert empty

     head      :: Ord a => h a -> a
     head = fst . fromJust . viewHead

     deleteHead :: Ord a => h a -> h a
     deleteHead = maybe empty snd . viewHead

     ... etc.

  instance Heap MinHeap where ...

  newtype MaxHeap a = M (MinHeap (Reverse a))
  instance Heap MaxHeap where ...

The union and unions functions are probably best not put in this class but implemented via separate Monoid instances.


In conclusion: the ordering policy stuff should not be part of Data.Heap, this is a job for Data.Ord.


In particular, Data.Ord might contain something like

   newtype OrdBy p a = OrdBy { unOrdBy :: a }

   class OrdPolicy p a where ...

   instance OrdPolicy p a => Ord (OrdBy p a) where ...

which can then be used to implement heaps with such different orderings in one go:

   newtype OrdPolicy p a => HeapP p a = HeapP (MinHeap (OrdBy p a))

   instance Heap (HeapP p) where ...


Regards,
apfelmus

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to