Why does "instance Ord Pat" causes <<loop>>

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:
{-# 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

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

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?
Oh, to answer this, my guess is that such an instance is just kind of silly. It is a meaningless, arbitrary ordering, and is brittle to splitting/combining cases. To put them in sets and maps, go ahead an define an arbitrary ordering however you can, but wrap it in a newtype like this: newtype OrdExp = OrdExp Exp instance Ord OrdExp where compare (OrdExp a) (OrdExp b) = compare (show a) (show b) An orphan instance is one which is defined in a module where neither the class nor the type being instantiated is defined. This newtype wrapping avoids orphan instances, and associates the arbitrary ordering to your own wrapper so if somebody else defined a different arbitrary ordering, they won't conflict. Orphan instances (almost?) always indicate a nonmodular design decision. Luke
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:
{-# 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

Hello Martin, Monday, December 8, 2008, 12:04:06 PM, you wrote:
Now it took me about a week to realise, that 'instance Ord Pat' causes ghc to loop.
naive Ord
instance Ord Exp
instance Ord Pat
i think you just don't learned this part of Haskell. empty instance declarations like these are possible but they doesn't mean automatic definition of some suitable compare. they just bring in some default definitions which may be mutual recursive, such as (==) and (/=) definitions in Eq class. this is intended to that your define either (==) or (/=), but compiler doesn't check this, so if you don't define anything, you will get endless loop if you want compiler to infer automatic instance definitions, the only way is to use GHC extension, smth like deriving instance Ord for Pat -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
participants (4)
-
Bulat Ziganshin
-
Luke Palmer
-
Martin Hofmann
-
wren ng thornton