[Haskell-cafe] Type constraints for class instances

Stephen Marsh freeyourmind at gmail.com
Fri Mar 21 12:01:59 EDT 2008


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 <freeyourmind at gmail.com>:

> 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 <gtener at gmail.com>:
>
> > 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 at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> >
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20080321/d1825533/attachment.htm


More information about the Haskell-Cafe mailing list