[Haskell-cafe] Why does "instance Ord Pat" causes <<loop>>

Luke Palmer lrpalmer at gmail.com
Mon Dec 8 04:13:27 EST 2008


On Mon, Dec 8, 2008 at 2:04 AM, Martin Hofmann <
martin.hofmann at 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 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/20081208/cd29c883/attachment-0001.htm


More information about the Haskell-Cafe mailing list