Data.Ord and Heaps (Was: Why functional programming matters)

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

Hi, I'm sorry it took me so long to respond! apfelmus@quantentunnel.de wrote:
[newtype Ord a => Reverse a = Reverse { unReverse :: a }]
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.
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.
[...]
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.
I stumbled over the similarity of heaps and lists when implementing take, takeWhile, span, break, etc. (btw, they are included in heap-0.2 which I uploaded yesterday); so a heap is really nothing but a packed representation of a sorted list :)
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:
[...]
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
Where? :) Regards, Stephan -- Früher hieß es ja: Ich denke, also bin ich. Heute weiß man: Es geht auch so. - Dieter Nuhr

Stephan Friedrichs wrote:
I'm sorry it took me so long to respond!
No worries :)
In conclusion: the ordering policy stuff should not be part of Data.Heap, this is a job for Data.Ord. This sounds really useful. How about you propose this to the base-package maintainers? :)
What, me? :D
Where? :)
Proposals for the base package go to libraries@haskell.org . A proposal is a darcs patch + a deadline. Unfortunately, ghc 6.8.* isn't yet available on Macports, I'd have to install 6.6.1 again on my wiped disk to get a haskell compiler and darcs. I'm currently leaning towards code like data OrdBy p a = OrdBy { unOrdBy :: a } instance Eq a => Eq (OrdBy p a) where (==) = (==) `on` unOrdBy data Reverse type Reversed a = OrdBy Reverse a instance Ord a => Ord (OrdBy Reverse a) where compare = flip $ comparing unOrdBy and probably another example for custom orderings. Do you now a good one? I'm not so happy about the names. In particular, I don't like unOrdBy , too much cAmelCase. Any other ideas? Maybe data Rearrange p a = Rearrange { unRearrange :: a } data ReOrd p a = ReOrd { unReOrd :: a } But I guess it can't be helped and it's not too bad either. The class constraint Ord (OrdBy p a) => will be common in user code, but it's a bit bulky for my taste. However, its main problem is that it's not Haskell98 :( A multi-parameter class (just like in the original heap-0.1) class OrdPolicy p a where ... instance OrdPolicy p a => Ord (OrdBy p a) where ... is shorter but not H98 either. The name could be a mot juste, too. class Rearranged p a where ... class Ord' p a where ... class OrdBy p a where ... -- clashes with the name of the type Regards, apfelmus

(Sorry for the late reply.) apfelmus@quantentunnel.de wrote:
I'd really like to write
class (forall a . Ord p a) => OrdPolicy p where
but I guess that's (currently) not possible.
Actually, it seems that something like this can be achieved, at some price. First, I change the statement ;-) to class (forall a . Ord a => Ord p a) => OrdPolicy p since I guess this is what you really want. Then, we reify the Ord class with a GADT: data O a where O :: Ord a => O a Then, we reify the forall, using GADT+impredicativity: data O1 p where O1:: (forall a . Ord a => O (p a)) -> O1 p We can express the constraint with a class OrdAll, providing the GADT proof: class OrdAll p where ordAll :: O1 p Instances are easy to define, I think: instance OrdAll [] where ordAll = O1 O Your class becomes then: class OrdAll p => OrdPolicy p where ... Actually, using this is not exactly nice, since you have to 'instantiate' the forall on your own. For example, fooSort :: forall p a . (OrdPolicy p, Ord a) => [p a] -> [p a] fooSort = case ordAll of O1 o -> case o of (O :: O (p a)) -> sort * * * Actually, a simpler (untested) approach could be: class OrdAll p where ordAll :: Ord a => O (p a) This would make the O1 hack useless. Regards, Zun.

Roberto Zunino wrote:
I'd really like to write
class (forall a . Ord p a) => OrdPolicy p where
but I guess that's (currently) not possible.
Actually, it seems that something like this can be achieved, at some price.
data O a where O :: Ord a => O a
data O1 p where O1:: (forall a . Ord a => O (p a)) -> O1 p
Ah, very nice :)
First, I change the statement ;-) to
class (forall a . Ord a => Ord p a) => OrdPolicy p
since I guess this is what you really want.
Right, modulo the fact that I also forgot the parenthesis class (forall a . Ord a => Ord (p a)) => OrdPolicy p So, the intention is to automatically have the instance instance (OrdPolicy p, Ord a) => Ord (p a) where which can be obtained from your GADT proof compare = case ordAll of O1 o -> case o of (O :: O (p a)) -> compare This instance declaration is a bit problematic because it contains only type variables. Fortunately, the phantom type approach doesn't have this problem: data OrdBy p a = OrdBy { unOrdBy :: a } data O a where O :: Ord a => O a class OrdPolicy p where -- simplified O1 ordAll :: Ord a => O (OrdBy p a) instance (Ord a, OrdPolicy p) => Ord (OrdBy p a) where compare = case ordAll of { (O :: O (OrdBy p a)) -> compare } By making the dictionary in O explicit, we can even make this Haskell98! 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' On second thought, being polymorphic in a is probably too restrictive: the only usable OrdPolicy besides the identity is Reverse :) After all, there aren't so many useful functions with type compare' :: forall a. (a -> a -> Ordering) -> (a -> a -> Ordering) So, other custom orderings usually depend on the type a . Did you have any specific examples in mind, Stephan? At the moment, I can only think of ordering Maybe a such that Nothing is either the largest or the smallest element on f g x y = g x `f` g y data Up instance Ord a => Ord (OrdBy Up (Maybe a)) where compare = f `on` unOrdBy where f Nothing Nothing = EQ f x Nothing = LT f Nothing y = GT f (Just x) (Just y) = compare x y data Down instance Ord a => Ord (OrdBy Down (Maybe a)) where compare = f `on` unOrdBy where f Nothing Nothing = EQ f x Nothing = GT f Nothing y = LT f (Just x) (Just y) = compare x y But I think that those two orderings merit special data types like data Raised a = Bottom | Raise a deriving (Eq, Ord) data Lowered a = Lower a | Top deriving (Eq, Ord) instead of type Raised a = OrdBy Down (Maybe a) type Lowered a = OrdBy Up (Maybe a) Regards, apfelmus
participants (4)
-
apfelmus
-
apfelmus@quantentunnel.de
-
Roberto Zunino
-
Stephan Friedrichs