Expected behavior of "deriving Ord"?

Conal Elliott conal at conal.net
Wed Mar 19 18:01:12 EDT 2008


Thanks for the pointers.  I'd found 10.1 but hadn't noticed 10.5.

So I suggest that you use an explicit Ord instance and define min/max the
> way you want.
>

Yep.  That's my solution:

    instance Ord a => Ord (AddBounds a) where
      MinBound  <= _         = True
      NoBound _ <= MinBound  = False
      NoBound a <= NoBound b = a <= b
      NoBound _ <= MaxBound  = True
      MaxBound  <= MaxBound  = True
      MaxBound  <= _         = False

      MinBound  `min` _         = MinBound
      _         `min` MinBound  = MinBound
      NoBound a `min` NoBound b = NoBound (a `min` b)
      u         `min` MaxBound  = u
      MaxBound  `min` v         = v

      MinBound  `max` v         = v
      u         `max` MinBound  = u
      NoBound a `max` NoBound b = NoBound (a `max` b)
      _         `max` MaxBound  = MaxBound
      MaxBound  `max` _         = MaxBound

Cheers,  - Conal


On Wed, Mar 19, 2008 at 2:35 PM, Duncan Coutts <duncan.coutts at worc.ox.ac.uk>
wrote:

>
> On Wed, 2008-03-19 at 14:11 -0700, Conal Elliott wrote:
> > I have an algebraic data type (not newtype) that derives Ord:
> >
> >     data AddBounds a = MinBound | NoBound a | MaxBound
> >         deriving (Eq, Ord, Read, Show)
> >
> > I was hoping to get a min method defined in terms of the min method of
> > the type argument (a).  Instead, I think GHC is producing something in
> > terms of compare or (<=).  Maybe it's defaulting min altogether.  What
> > is the expected behavior in (a) the language standard and (b) GHC?
>
> The H98 report says:
>
>        10.1  Derived instances of Eq and Ord
>        The class methods automatically introduced by derived instances
>        of Eq and Ord are (==), (/=), compare, (<), (<=), (>), (>=),
>        max, and min. The latter seven operators are defined so as to
>        compare their arguments lexicographically with respect to the
>        constructor set given, with earlier constructors in the datatype
>        declaration counting as smaller than later ones. For example,
>        for the Bool datatype, we have that (True > False) == True.
>
>        Derived comparisons always traverse constructors from left to
>        right. These examples illustrate this property:
>
>          (1,undefined) == (2,undefined) =>    False
>          (undefined,1) == (undefined,2) =>    _|_
>
>        All derived operations of class Eq and Ord are strict in both
>        arguments. For example, False <= _|_ is _|_, even though False
>        is the first constructor of the Bool type.
>
> Which doesn't seem to help but looking at the later example:
>
>        10.5  An Example
>        As a complete example, consider a tree datatype:
>
>          data Tree a = Leaf a | Tree a :^: Tree a
>                deriving (Eq, Ord, Read, Show)
>
>         Automatic derivation of instance declarations for Bounded and
>        Enum are not possible, as Tree is not an enumeration or
>        single-constructor datatype. The complete instance declarations
>        for Tree are shown in Figure 10.1, Note the implicit use of
>        default class method definitions---for example, only <= is
>        defined for Ord, with the other class methods (<, >, >=, max,
>        and min) being defined by the defaults given in the class
>        declaration shown in Figure 6.1 (page ).
>
> So that is relying on the default class methods:
>
>    max x y | x <= y    =  y
>            | otherwise =  x
>    min x y | x <= y    =  x
>            | otherwise =  y
>
> As for GHC, Looking at the comments in compiler/typecheck/TcGenDeriv.lhs
> it says that it generates code that uses compare like so:
>
>        max a b = case (compare a b) of { LT -> b; EQ -> a;  GT -> a }
>        min a b = case (compare a b) of { LT -> a; EQ -> b;  GT -> b }
>
> > The reason I care is that my type parameter a turns out to have
> > partial information, specifically lower bounds.  The type of min
> > allows this partial info to be used in producing partial info about
> > the result, while the type of (<=) and compare do not.
>
> So I suggest that you use an explicit Ord instance and define min/max
> the way you want.
>
> Duncan
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20080319/6f2e563e/attachment.htm


More information about the Glasgow-haskell-users mailing list