
Hello everyone, I'm working on a small module for comparing things incomparable with Ord. More precisely I want to be able to compare equal infinite lists like [1..]. Obviously (1) compare [1..] [1..] = _|_ It is perfectly reasonable for Ord to behave this way. Hovever, it doesn't have to be just this way. Consider this class class YOrd a where ycmp :: a -> a -> (a,a) In a way, it tells a limited version of ordering, since there is no way to get `==` out of this. Still it can be useful when Ord fails. Consider this code: (2) sort [ [1..], [2..], [3..] ] It is ok, because compare can decide between any elements in finite time. However, this one (3) sort [ [1..], [1..] ] will fail because of (1). Compare is simply unable to tell that two infinite list are equivalent. I solved this by producing partial results while comparing lists. If we compare lists (1:xs) (1:ys) we may not be able to tell xs < ys, but we do can tell that 1 will be the first element of both of smaller and greater one. You can see this idea in the code below. --- cut here --- {-# OPTIONS_GHC -O2 #-} module Data.YOrd where -- Well defined where Eq means equality, not only equivalence class YOrd a where ycmp :: a -> a -> (a,a) instance (YOrd a) => YOrd [a] where ycmp [] [] = ([],[]) ycmp xs [] = ([],xs) ycmp [] xs = ([],xs) ycmp xs'@(x:xs) ys'@(y:ys) = let (sm,gt) = x `ycmp` y in let (smS,gtS) = xs `ycmp` ys in (sm:smS, gt:gtS) ycmpWrap x y = case x `compare` y of LT -> (x,y) GT -> (y,x) EQ -> (x,y) -- biased - but we have to make our minds! -- ugly, see the problem below instance YOrd Int where ycmp = ycmpWrap instance YOrd Char where ycmp = ycmpWrap instance YOrd Integer where ycmp = ycmpWrap -- ysort : sort of mergesort ysort :: (YOrd a) => [a] -> [a] ysort = head . mergeAll . wrap wrap :: [a] -> [[a]] wrap xs = map (:[]) xs mergeAll :: (YOrd a) => [[a]] -> [[a]] mergeAll [] = [] mergeAll [x] = [x] mergeAll (a:b:rest) = mergeAll ((merge a b) : (mergeAll rest)) merge :: (YOrd a) => [a] -> [a] -> [a] merge [] [] = [] merge xs [] = xs merge [] xs = xs merge (x:xs) (y:ys) = let (sm,gt) = x `ycmp` y in sm : (merge [gt] $ merge xs ys) --- cut here --- I'd like to write the following code: instance (Ord a) => YOrd a where ycmp x y = case x `compare` y of LT -> (x,y) GT -> (y,x) EQ -> (x,y) But i get an error "Undecidable instances" for any type [a]. Does anyone know the way to solve this? Best regards Christopher Skrzętnicki

First I'd like to say that this is a very clever idea. Thanks for the
exposition. :-)
2008/3/21 Krzysztof Skrzętnicki
I'd like to write the following code:
instance (Ord a) => YOrd a where ycmp x y = case x `compare` y of LT -> (x,y) GT -> (y,x) EQ -> (x,y)
But i get an error "Undecidable instances" for any type [a]. Does anyone know the way to solve this?
This type of superclassing is not supported by the typeclass system. Finding systems where it is supported is a point of much lost sleep on my part. The typical way to solve this is rather disappointing: wrap it in a newtype: newtype YOrdWrap a = YOrdWrap { yordUnwrap :: a } instance (Ord a) => YOrd (YOrdWrap a) where ycmp (YOrdWrap x) (YOrdWrap y) = ycmpWrap x y And then apply the constructor whenever you want to use a "normal" type. Luke

2008/3/21 Krzysztof Skrzętnicki
... I'd like to write the following code:
instance (Ord a) => YOrd a where ycmp x y = case x `compare` y of LT -> (x,y) GT -> (y,x) EQ -> (x,y)
But i get an error "Undecidable instances" for any type [a]. Does anyone know the way to solve this?
The module compiles fine when you add the following pragma's to your module: {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} See: http://www.haskell.org/ghc/docs/latest/html/users_guide/type-class-extension... http://www.haskell.org/ghc/docs/latest/html/users_guide/type-class-extension... regards, Bas

It compiles, but it doesn't work when i try to use it on lists. There
are some bugs in that code, but I need some time to fix it.
2008/3/21 Bas van Dijk
2008/3/21 Krzysztof Skrzętnicki
: ...
I'd like to write the following code:
instance (Ord a) => YOrd a where ycmp x y = case x `compare` y of LT -> (x,y) GT -> (y,x) EQ -> (x,y)
But i get an error "Undecidable instances" for any type [a]. Does anyone know the way to solve this?
The module compiles fine when you add the following pragma's to your module:
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-}
See: http://www.haskell.org/ghc/docs/latest/html/users_guide/type-class-extension... http://www.haskell.org/ghc/docs/latest/html/users_guide/type-class-extension...
regards,
Bas

There is a bug in the code:
*Main> ycmp [5,2] [2,5] :: ([Int], [Int])
([2,2],[5,5])
I think it is impossible to define a working (YOrd a) => YOrd [a] instance.
Consider:
let (a, b) = ycmp [[1..], [2..]] [[1..],[1..]]
head (b !! 1) -- would be nice if it was 2, but it is in fact _|_
We take forever to decide if [1..] is greater or less than [1..], so can
never decide if [1..] or [2..] comes next.
However Ord a => YOrd [a] can be made to work, and that is absolutely
awesome, esp. once you start thinking about things like Ord a => YOrd
(InfiniteTree a). This really is very cool, Krzysztof.
Stephen
2008/3/20 Krzysztof Skrzętnicki
Hello everyone,
I'm working on a small module for comparing things incomparable with Ord. More precisely I want to be able to compare equal infinite lists like [1..]. Obviously
(1) compare [1..] [1..] = _|_
It is perfectly reasonable for Ord to behave this way. Hovever, it doesn't have to be just this way. Consider this class
class YOrd a where ycmp :: a -> a -> (a,a)
In a way, it tells a limited version of ordering, since there is no way to get `==` out of this. Still it can be useful when Ord fails. Consider this code:
(2) sort [ [1..], [2..], [3..] ]
It is ok, because compare can decide between any elements in finite time. However, this one
(3) sort [ [1..], [1..] ]
will fail because of (1). Compare is simply unable to tell that two infinite list are equivalent. I solved this by producing partial results while comparing lists. If we compare lists (1:xs) (1:ys) we may not be able to tell xs < ys, but we do can tell that 1 will be the first element of both of smaller and greater one. You can see this idea in the code below.
--- cut here ---
{-# OPTIONS_GHC -O2 #-}
module Data.YOrd where
-- Well defined where Eq means equality, not only equivalence
class YOrd a where ycmp :: a -> a -> (a,a)
instance (YOrd a) => YOrd [a] where ycmp [] [] = ([],[]) ycmp xs [] = ([],xs) ycmp [] xs = ([],xs) ycmp xs'@(x:xs) ys'@(y:ys) = let (sm,gt) = x `ycmp` y in let (smS,gtS) = xs `ycmp` ys in (sm:smS, gt:gtS)
ycmpWrap x y = case x `compare` y of LT -> (x,y) GT -> (y,x) EQ -> (x,y) -- biased - but we have to make our minds!
-- ugly, see the problem below instance YOrd Int where ycmp = ycmpWrap instance YOrd Char where ycmp = ycmpWrap instance YOrd Integer where ycmp = ycmpWrap
-- ysort : sort of mergesort
ysort :: (YOrd a) => [a] -> [a]
ysort = head . mergeAll . wrap
wrap :: [a] -> [[a]] wrap xs = map (:[]) xs
mergeAll :: (YOrd a) => [[a]] -> [[a]] mergeAll [] = [] mergeAll [x] = [x] mergeAll (a:b:rest) = mergeAll ((merge a b) : (mergeAll rest))
merge :: (YOrd a) => [a] -> [a] -> [a] merge [] [] = [] merge xs [] = xs merge [] xs = xs merge (x:xs) (y:ys) = let (sm,gt) = x `ycmp` y in sm : (merge [gt] $ merge xs ys)
--- cut here ---
I'd like to write the following code:
instance (Ord a) => YOrd a where ycmp x y = case x `compare` y of LT -> (x,y) GT -> (y,x) EQ -> (x,y)
But i get an error "Undecidable instances" for any type [a]. Does anyone know the way to solve this?
Best regards
Christopher Skrzętnicki
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Actually, infinite trees wouldn't work, for a similar reason to above. You
can't decide sort order on the infinite left branches, so you could never
choose the correct right branch.
Stephen
2008/3/21 Stephen Marsh
There is a bug in the code:
*Main> ycmp [5,2] [2,5] :: ([Int], [Int]) ([2,2],[5,5])
I think it is impossible to define a working (YOrd a) => YOrd [a] instance. Consider:
let (a, b) = ycmp [[1..], [2..]] [[1..],[1..]]
head (b !! 1) -- would be nice if it was 2, but it is in fact _|_
We take forever to decide if [1..] is greater or less than [1..], so can never decide if [1..] or [2..] comes next.
However Ord a => YOrd [a] can be made to work, and that is absolutely awesome, esp. once you start thinking about things like Ord a => YOrd (InfiniteTree a). This really is very cool, Krzysztof.
Stephen
2008/3/20 Krzysztof Skrzętnicki
: Hello everyone,
I'm working on a small module for comparing things incomparable with Ord. More precisely I want to be able to compare equal infinite lists like [1..]. Obviously
(1) compare [1..] [1..] = _|_
It is perfectly reasonable for Ord to behave this way. Hovever, it doesn't have to be just this way. Consider this class
class YOrd a where ycmp :: a -> a -> (a,a)
In a way, it tells a limited version of ordering, since there is no way to get `==` out of this. Still it can be useful when Ord fails. Consider this code:
(2) sort [ [1..], [2..], [3..] ]
It is ok, because compare can decide between any elements in finite time. However, this one
(3) sort [ [1..], [1..] ]
will fail because of (1). Compare is simply unable to tell that two infinite list are equivalent. I solved this by producing partial results while comparing lists. If we compare lists (1:xs) (1:ys) we may not be able to tell xs < ys, but we do can tell that 1 will be the first element of both of smaller and greater one. You can see this idea in the code below.
--- cut here ---
{-# OPTIONS_GHC -O2 #-}
module Data.YOrd where
-- Well defined where Eq means equality, not only equivalence
class YOrd a where ycmp :: a -> a -> (a,a)
instance (YOrd a) => YOrd [a] where ycmp [] [] = ([],[]) ycmp xs [] = ([],xs) ycmp [] xs = ([],xs) ycmp xs'@(x:xs) ys'@(y:ys) = let (sm,gt) = x `ycmp` y in let (smS,gtS) = xs `ycmp` ys in (sm:smS, gt:gtS)
ycmpWrap x y = case x `compare` y of LT -> (x,y) GT -> (y,x) EQ -> (x,y) -- biased - but we have to make our minds!
-- ugly, see the problem below instance YOrd Int where ycmp = ycmpWrap instance YOrd Char where ycmp = ycmpWrap instance YOrd Integer where ycmp = ycmpWrap
-- ysort : sort of mergesort
ysort :: (YOrd a) => [a] -> [a]
ysort = head . mergeAll . wrap
wrap :: [a] -> [[a]] wrap xs = map (:[]) xs
mergeAll :: (YOrd a) => [[a]] -> [[a]] mergeAll [] = [] mergeAll [x] = [x] mergeAll (a:b:rest) = mergeAll ((merge a b) : (mergeAll rest))
merge :: (YOrd a) => [a] -> [a] -> [a] merge [] [] = [] merge xs [] = xs merge [] xs = xs merge (x:xs) (y:ys) = let (sm,gt) = x `ycmp` y in sm : (merge [gt] $ merge xs ys)
--- cut here ---
I'd like to write the following code:
instance (Ord a) => YOrd a where ycmp x y = case x `compare` y of LT -> (x,y) GT -> (y,x) EQ -> (x,y)
But i get an error "Undecidable instances" for any type [a]. Does anyone know the way to solve this?
Best regards
Christopher Skrzętnicki
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I fixed the code, see below. In fact, it works now for any listst of type (YOrd a) => [a]. It works for things like
ysort [[1..],[1..],[2..],[1..]] Unfortunately, the performance of ysort is rather low. I belive that it is impossible to create any sorting algorithm that uses ycmp instead of compare, that is faster than O(n^2). In fact, ysort is Theta(n^2), and it appears to be optimal. Why? Well, consider the bubble sort algorithm. Then ycmp will be simply sort of swap used there:
ycmp x y = case x `compare` y of
LT -> (x,y)
EQ -> (x,y)
GT -> (y,x)
And because it is the only possible operation here, it can't be
faster. (Though I may be wrong.)
Best regards,
Christopher Skrzętnicki.
---
--- http://hpaste.org/6536#a1
{-# OPTIONS_GHC -O2 #-}
module Data.YOrd (ysort, YOrd(..)) where
-- Well defined where Eq means equality, not only equivalence
class YOrd a where
ycmp :: a -> a -> (a,a)
instance (Ord a) => YOrd [a] where
ycmp = ycmpWith compare
where
ycmpWith _ xs [] = ([],xs)
ycmpWith _ [] xs = ([],xs)
ycmpWith cmp (xs'@(x:xs)) (ys'@(y:ys)) = case x `cmp` y of
LT -> (xs',ys')
GT -> (ys',xs')
EQ -> let (sm,gt)
= xs `ycmp` ys in
(x:sm,x:gt)
-- assumes that cmp is equality not equivalence relation here!
ycmpWrap cmp x y = case x `cmp` y of
LT -> (x,y)
EQ -> (x,y)
GT -> (y,x)
instance YOrd Integer where
ycmp = ycmpWrap compare
instance YOrd Char where
ycmp = ycmpWrap compare
instance YOrd Int where
ycmp = ycmpWrap compare
-- ysort : sorting in O(n^2)
ysort :: (YOrd a) => [a] -> [a]
ysort = head . mergeAll . wrap
wrap xs = map (:[]) xs
mergeAll [] = []
mergeAll [x] = [x]
mergeAll (a:b:rest) = mergeAll ((merge a b) : (mergeAll rest))
merge xs [] = xs
merge [] xs = xs
merge (x:xs) (y:ys) = let (sm,gt) = x `ycmp` y in
sm : (merge [gt] $ merge xs ys)
2008/3/21 Stephen Marsh
Actually, infinite trees wouldn't work, for a similar reason to above. You can't decide sort order on the infinite left branches, so you could never choose the correct right branch.
Stephen
2008/3/21 Stephen Marsh
: There is a bug in the code:
*Main> ycmp [5,2] [2,5] :: ([Int], [Int]) ([2,2],[5,5])
I think it is impossible to define a working (YOrd a) => YOrd [a] instance. Consider:
let (a, b) = ycmp [[1..], [2..]] [[1..],[1..]]
head (b !! 1) -- would be nice if it was 2, but it is in fact _|_
We take forever to decide if [1..] is greater or less than [1..], so can never decide if [1..] or [2..] comes next.
However Ord a => YOrd [a] can be made to work, and that is absolutely awesome, esp. once you start thinking about things like Ord a => YOrd (InfiniteTree a). This really is very cool, Krzysztof.
Stephen
2008/3/20 Krzysztof Skrzętnicki
: Hello everyone,
I'm working on a small module for comparing things incomparable with
Ord.
More precisely I want to be able to compare equal infinite lists like [1..]. Obviously
(1) compare [1..] [1..] = _|_
It is perfectly reasonable for Ord to behave this way. Hovever, it doesn't have to be just this way. Consider this class
class YOrd a where ycmp :: a -> a -> (a,a)
In a way, it tells a limited version of ordering, since there is no way to get `==` out of this. Still it can be useful when Ord fails. Consider this code:
(2) sort [ [1..], [2..], [3..] ]
It is ok, because compare can decide between any elements in finite time. However, this one
(3) sort [ [1..], [1..] ]
will fail because of (1). Compare is simply unable to tell that two infinite list are equivalent. I solved this by producing partial results while comparing lists. If we compare lists (1:xs) (1:ys) we may not be able to tell xs < ys, but we do can tell that 1 will be the first element of both of smaller and greater one. You can see this idea in the code below.
--- cut here ---
{-# OPTIONS_GHC -O2 #-}
module Data.YOrd where
-- Well defined where Eq means equality, not only equivalence
class YOrd a where ycmp :: a -> a -> (a,a)
instance (YOrd a) => YOrd [a] where ycmp [] [] = ([],[]) ycmp xs [] = ([],xs) ycmp [] xs = ([],xs) ycmp xs'@(x:xs) ys'@(y:ys) = let (sm,gt) = x `ycmp` y in let (smS,gtS) = xs `ycmp` ys in (sm:smS, gt:gtS)
ycmpWrap x y = case x `compare` y of LT -> (x,y) GT -> (y,x) EQ -> (x,y) -- biased - but we have to make our minds!
-- ugly, see the problem below instance YOrd Int where ycmp = ycmpWrap instance YOrd Char where ycmp = ycmpWrap instance YOrd Integer where ycmp = ycmpWrap
-- ysort : sort of mergesort
ysort :: (YOrd a) => [a] -> [a]
ysort = head . mergeAll . wrap
wrap :: [a] -> [[a]] wrap xs = map (:[]) xs
mergeAll :: (YOrd a) => [[a]] -> [[a]] mergeAll [] = [] mergeAll [x] = [x] mergeAll (a:b:rest) = mergeAll ((merge a b) : (mergeAll rest))
merge :: (YOrd a) => [a] -> [a] -> [a] merge [] [] = [] merge xs [] = xs merge [] xs = xs merge (x:xs) (y:ys) = let (sm,gt) = x `ycmp` y in sm : (merge [gt] $ merge xs ys)
--- cut here ---
I'd like to write the following code:
instance (Ord a) => YOrd a where ycmp x y = case x `compare` y of LT -> (x,y) GT -> (y,x) EQ -> (x,y)
But i get an error "Undecidable instances" for any type [a]. Does anyone know the way to solve this?
Best regards
Christopher Skrzętnicki
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Krzysztof Skrzętnicki wrote:
class YOrd a where ycmp :: a -> a -> (a,a)
Unfortunately, the performance of ysort is rather low. I believe that it is impossible to create any sorting algorithm that uses ycmp instead of compare, that is faster than O(n^2).
It is possible, the following implementation of mergesort is O(n log n) :) ysort :: (YOrd a) => [a] -> [a] ysort = head . mergeAll . map (:[]) where mergeAll (x:y:zs) = mergeAll $ merge x y : mergeAll zs mergeAll xs = xs merge [] ys = ys merge (x:xs) ys = merge3 x ys xs merge3 x [] xs = x : xs merge3 x (y:ys) xs = x' : merge3 y' xs ys where (x',y') = x `ycmp` y Mergesort works like a tournament and the idea is to introduce merge3 :: YOrd a => a -> [a] -> [a] -> [a] to make the intermediate candidates explicit. In a call merge3 x ys zs , the candidate x is pitted against the head of ys . The winner is moved to the front and the loser is the new candidate ( ycmp is enough to do that). Furthermore, there is the invariant that x became candidate by winning over all xs (formally: x <= minimum xs), there is no need to pit x against them for a second time. The whole thing is O(n log n) for the usual reasons, the important part being that merge3 is O(1 + length xs + length ys). The problem with your solution was that merge [gt] (merge xs ys) could be O(2 * length ys) or something. Both solutions are almost the same because merge3 x ys xs ~ merge [x] (merge xs ys) , but merge3 incorporates the additional insight that we don't need to pit x against the xs anymore. Regards, apfelmus

apfelmus wrote:
Krzysztof Skrzętnicki wrote:
class YOrd a where ycmp :: a -> a -> (a,a)
Unfortunately, the performance of ysort is rather low. I believe that it is impossible to create any sorting algorithm that uses ycmp instead of compare, that is faster than O(n^2).
It is possible, the following implementation of mergesort is O(n log n) :)
merge3 x [] xs = x : xs merge3 x (y:ys) xs = x' : merge3 y' xs ys where (x',y') = x `ycmp` y
invariant that x became candidate by winning over all xs
Oops, merge3 clearly violates this invariant since y' could be x . So, my previous post is all wrong λ(>_<)λ . Regards, apfelmus

Krzysztof Skrzętnicki wrote:
class YOrd a where ycmp :: a -> a -> (a,a)
Unfortunately, the performance of ysort is rather low. I believe that it is impossible to create any sorting algorithm that uses ycmp instead of compare, that is faster than O(n^2).
Ok, it is possible to be faster, namely O(n (log n)^2) and even better. Sorting algorithms based on a comparator function like ycmp are called "sorting networks" and in fact well-known. See also http://en.wikipedia.org/wiki/Sorting_network Regards, apfelmus
participants (5)
-
apfelmus
-
Bas van Dijk
-
Krzysztof Skrzętnicki
-
Luke Palmer
-
Stephen Marsh