Stephan Friedrichs wrote:
apfelmus wrote:
[...]
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

This solution should be used for all collections depending on Ord instances, including Data.Map, Data.Set and others. As long as I only include it in my tiny heap package, it is as 'non-standard' as my approach, isn't it?

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.

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
[...]
  instance Heap MinHeap where ...
  newtype MaxHeap a = M (MinHeap (Reverse a))
  instance Heap MaxHeap where ...

I've actually thought about this. Realising MinHeap and MaxHeap is no problem, but I decided against it, because implementing a custom order becomes quite complicated: You have to declare an

newtype MyHeap a = ...

instance Heap MyHeap where
    -- about 10 functions

instead of just

data PriorityPolicy

instance HeapPolicy PP MyPriorityType where
    heapCompare = const (comparing priority)

Note that the Heap class contains only three primitive operations (empty, insert, viewHead), all the others have default implementations in terms of those three. There is even an underappreciated unfold among them :)

  toAscList = unfoldr viewHead

The structure becomes especially clear by noting that any Heap is defined by just two primitives

  inject :: Ord a => Maybe (a, Heap a) -> Heap a
  view   :: Ord a => Heap a -> Maybe (a, Heap a)

We have inject = maybe empty (uncurry insert) . This is just like lists, except that view . inject ≠ id since view returns the smallest element.


However, just that we managed to reduce the number of primitive operations doesn't mean that the policy approach isn't preferable. It needs 0 primitive operations, after all. But as foreshadowed in my reply, it's possible to do policies within Ord. Don't stop thinking about your good idea just because you can start coding :)

Here's one way to do it:

   module Data.Ord where
     ...
class (Ord p a) => OrdPolicy p a where -- the policy p is a type constructor
        to   :: a -> p a
        from :: p a -> a

     instance OrdPolicy Identity a where ...

     newtype Reverse a = Reverse a
     instance Ord a => Reverse a where
        compare = flip $ comparing from
     instance OrdPolicy Reverse a where
        to = Reverse; from (Reverse x) = x

   module Data.Heap where
     ...
     newtype Heap p a = Heap (MinHeap (p a))
     type MaxHeap a   = Heap Reverse a

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

     instance OrdPolicy p a => Heap (Heap p a) a where
        ...

What I don't like about this is that the policy is not polymorphic in the element types, forcing the Heap class to be multi-parameter. I'd really like to write

  class (forall a . Ord p a) => OrdPolicy p where

but I guess that's (currently) not possible. The original "phantom policy" approach can't quite do this either:

   module Data.Ord where
     ...
     newtype OrdBy p a = OrdBy { unOrdBy :: a }

     data Reverse
     instance Ord a => Ord (OrdBy Reverse a) where
        compare = flip $ comparing unOrdBy

   module Data.Heap where
     ...
     newtype Heap p a = Heap (MinHeap (OrdBy p a))
     type MaxHeap a   = Heap Reverse a

     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)

     instance (Ord (OrdBy p a)) => Heap (Heap p) where   -- forall a?
        ...

However, a distinct advantage of using OrdBy for all ordering policies is that the from and to functions are no longer necessary. All ordering policies use the same type OrdBy which automatically guarantees that from and to are inverse to each other. This would be an informal requirement otherwise, so I think that phantom policies are clearly superior to type constructor policies. Fortunately, this is orthogonal to making Heap a multi- parameter type class and ensuring that OrdBy p a instances are polymorphic in a .


In conclusion: the ordering policy stuff should not be part of Data.Heap, this is a job for Data.Ord.
As mentioned above: This sounds really useful. How about you propose this to the base-package maintainers? :)

What, me? :D


Regards,
apfelmus

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

Reply via email to