[GHC] #10562: GHC 7.10.2 RC cannot build boolsimplifier-0.1.8

GHC ghc-devs at haskell.org
Thu Jun 25 15:50:30 UTC 2015


#10562: GHC 7.10.2 RC cannot build boolsimplifier-0.1.8
-------------------------------------+-------------------------------------
        Reporter:  snoyberg          |                   Owner:
            Type:  bug               |                  Status:  new
        Priority:  normal            |               Milestone:  7.10.2
       Component:  Compiler          |                 Version:  7.10.2-rc1
      Resolution:                    |                Keywords:
Operating System:  Linux             |            Architecture:  x86_64
 Type of failure:  GHC rejects       |  (amd64)
  valid program                      |               Test Case:
      Blocked By:                    |                Blocking:
 Related Tickets:                    |  Differential Revisions:
-------------------------------------+-------------------------------------

Comment (by simonpj):

 Here is a smaller test case
 {{{
 {-# LANGUAGE GADTs, TypeFamilies #-}
 module T10562 where

 type family Flip a

 data QueryRep qtyp a where
     QAtom :: a -> QueryRep () a
     QOp   :: QueryRep (Flip qtyp) a -> QueryRep qtyp a

 instance (Eq a) => Eq (QueryRep qtyp a)

 instance (Ord a) => Ord (QueryRep qtyp a) where
   compare (QOp a) (QOp b) = a `compare` b
 }}}
 With 7.10 we get
 {{{
 T10562.hs:13:31:
     Overlapping instances for Eq (QueryRep (Flip qtyp) a)
       arising from a use of ‘compare’
 }}}
 The problem arises because of the "silent superclass" trick (which is
 happily gone from HEAD).  The instance declaration that is actually
 checked is
 {{{
 instance (Eq (QueryRep qtyp a), Ord a) => Ord (QueryRep qtyp a)
 }}}
 with an extra `Eq (QueryRep qtyp a)` constraint.  That gets GHC confused
 when it tries to solve `Eq (QueryRep (Flip qtyp) a)` from a method.

 A workaround is to use `-XIncoherentInstances` for this module.

 Exactly the same failure happens with GHC 7.8.3 doesn't it?  Though
 apparently not with 7.8.2, mysteriously.

 I'm sorry but it's not feasible to get HEAD's solution into 7.10 now.  It
 works fine in HEAD, and I'll add the example as a test case, to check it
 stays working.

 Simon

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


More information about the ghc-tickets mailing list