On Mon, Dec 8, 2008 at 2:04 AM, Martin Hofmann <martin.hofmann@uni-bamberg.de> wrote:
I am storing the TH data types 'Exp' and 'Pat' in Maps and Sets. As a
first attempt to quickly get rid of typechecker's complaints I defined
some naive instances of Ord for Exp and Pat.

Now it took me about a week to realise, that 'instance Ord Pat' causes
ghc to loop. Apparently, there is a reason, why Pat and Exp are not
instances of Ord. What is so bad about it?

If Pat and Exp should not be instances of Ord, maybe a note in the
source code or haddock would be helpful. On the other hand, what would
argue against a lexicographic ordering (apart from the inefficient
implementation of the following one)?

Following some literate code to reproduce the <<loop>> (or stack
overflow in GHCi), by commenting and uncommenting the appropriate lines:

Try this:

data Foo = Foo deriving Eq

instance Ord Foo

Then try Foo < Foo.

instance Ord Foo is not the same as "deriving Ord"; it declares an instance using all default definitions, which are self-referential.

It would be nice if typeclass authors could somehow declare the minimal complete definition, so we could get a warning in this case.

Luke
 




> {-# OPTIONS_GHC -fglasgow-exts -fth #-}
> module Test where
> import Language.Haskell.TH
> import Data.Set


-------------------
 naive Ord

> instance Ord Exp

> instance Ord Pat

-------------------
 lexicographic Ord

 instance Ord Exp where
    compare l r = compare (show l) (show r)

 instance Ord Pat where
    compare l r = compare (show l) (show r)

-------------------


> mkVP s = VarP $ mkName s
> mkVE s = VarE $ mkName s
> rule1 = (,) [mkVP "x_14"] (mkVE "y_14")
> rule2 = (,) [InfixP (mkVP "x1_15") '(:) (mkVP "x_16")] (InfixE (Just (mkVE "y1_15")) (ConE '(:)) (Just (mkVE "ys_16")))

> stack_overflow = fromList [rule1,rule2]


Thanks,

Martin


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