[GHC] #12080: RebindableSyntax breaks deriving Ord

GHC ghc-devs at haskell.org
Wed May 18 07:45:49 UTC 2016


#12080: RebindableSyntax breaks deriving Ord
-------------------------------------+-------------------------------------
           Reporter:  afarmer        |             Owner:  afarmer
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  7.10.3
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:  #11396
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The code generated with `deriving (Ord)` includes if-expressions which are
 subject to rebindable syntax:

 {{{
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE RebindableSyntax #-}

 import Prelude

 class IfThenElse a b where
   ifThenElse :: a -> b -> b -> b

 instance IfThenElse Bool b where
   ifThenElse c x y = if c then x else y

 data Foo = Foo | Bar | Baz deriving (Eq, Ord)

 main :: IO ()
 main = print $ Foo < Bar
 }}}

 when loaded into ghci (7.10, but not specific to that version):

 {{{
 [1 of 1] Compiling Main             ( Foo.hs, interpreted )

 Foo.hs:13:42:
     Bad call to tagToEnum# at type a_aQy
       Specify the type by giving a type signature
       e.g. (tagToEnum# x) :: Bool
     In the expression: (GHC.Prim.tagToEnum# (a# GHC.Prim.<# b#))
     In the expression:
       if (GHC.Prim.tagToEnum# (a# GHC.Prim.<# b#)) then
           LT
       else
           if (GHC.Prim.tagToEnum# (a# GHC.Prim.==# b#)) then EQ else GT
     In a case alternative:
         b#
           -> if (GHC.Prim.tagToEnum# (a# GHC.Prim.<# b#)) then
                  LT
              else
                  if (GHC.Prim.tagToEnum# (a# GHC.Prim.==# b#)) then EQ
 else GT
     When typechecking the code for  ‘compare’
       in a derived instance for ‘Ord Foo’:
       To see the code I am typechecking, use -ddump-deriv

 Foo.hs:13:42:
     No instance for (IfThenElse a0 Ordering)
       arising from an if statement
     The type variable ‘a0’ is ambiguous
     Note: there is a potential instance available:
       instance IfThenElse Bool b -- Defined at Foo.hs:10:10
     In the expression:
       if (GHC.Prim.tagToEnum# (a# GHC.Prim.<# b#)) then
           LT
       else
           if (GHC.Prim.tagToEnum# (a# GHC.Prim.==# b#)) then EQ else GT
     In a case alternative:
         b#
           -> if (GHC.Prim.tagToEnum# (a# GHC.Prim.<# b#)) then
                  LT
              else
                  if (GHC.Prim.tagToEnum# (a# GHC.Prim.==# b#)) then EQ
 else GT
     In the expression:
       case (Main.$con2tag_rjG b) of {
         b#
           -> if (GHC.Prim.tagToEnum# (a# GHC.Prim.<# b#)) then
                  LT
              else
                  if (GHC.Prim.tagToEnum# (a# GHC.Prim.==# b#)) then EQ
 else GT }
     When typechecking the code for  ‘compare’
       in a derived instance for ‘Ord Foo’:
       To see the code I am typechecking, use -ddump-deriv
 Failed, modules loaded: none.
 }}}

 The if-expressions are generated by `nlHsIf`, which calls `mkHsIf`, which
 uses `Just noSyntaxExpr` as its first argument. I'm going to add a new
 function `nlBuiltInHsIf` which uses `Nothing` as the first argument,
 forcing the built-in if (according to Note [Rebindable if]), then use this
 new function when deriving stuff.

 I'll post a patch soonish.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12080>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list