[GHC] #11066: Inacessible branch should be warning - otherwise breaks type soundness?

GHC ghc-devs at haskell.org
Wed Feb 1 21:22:52 UTC 2017


#11066: Inacessible branch should be warning - otherwise breaks type soundness?
-------------------------------------+-------------------------------------
        Reporter:  rrnewton          |                Owner:
            Type:  bug               |               Status:  new
        Priority:  high              |            Milestone:  8.2.1
       Component:  Compiler          |              Version:  7.10.2
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  Incorrect         |  Unknown/Multiple
  warning at compile-time            |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:  #8128, #8740      |  Differential Rev(s):  Phab:D1454
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by jstolarek):

 I've been bitten by this bug just now. With GHC 8.0.1 this simple program
 will not compile because of inaccessible branches:

 {{{#!hs
 {-# LANGUAGE GADTs, StandaloneDeriving #-}

 module T11066 where

 data Foo a where
     A :: Foo Int
     B :: Foo Bool
     C :: Foo a -> Foo a

 deriving instance Eq  (Foo a)
 deriving instance Ord (Foo a)
 }}}

 GHC complains with five identical error messages, one for each derived
 function of `Ord` type class (this error is for `compare`):

 {{{
 T11066.hs:11:1:
     Couldn't match type ‘Bool’ with ‘Int’
     Inaccessible code in
       a pattern with constructor A :: Foo Int, in a case alternative
     In the pattern: A {}
     In a case alternative: A {} -> GT
     In the expression:
       case b of {
         A {} -> GT
         B -> EQ
         _ -> LT }
     When typechecking the code for  ‘compare’
       in a derived instance for ‘Ord (Foo a)’:
       To see the code I am typechecking, use -ddump-deriv
 }}}

 Here's the derived code of `compare` (after some cleanup):

 {{{#!hs
 instance Ord (Foo a) where
   compare a b = case a of
         A -> case b of
                A -> EQ
                _ -> LT
         B -> case b of
                A {} -> GT
                B -> EQ
                _ -> LT
         C c -> case b of
                C d -> (c `compare` d)
                _   -> GT
 }}}

 It is of course possible to write a well-typed instance of `Ord`:

 {{{#!hs
 instance Ord (Foo a) where
     compare  A     A    = EQ
     compare  A     _    = LT
     compare  _     A    = GT
     compare  B     B    = EQ
     compare  B    (C _) = LT
     compare (C _)  B    = GT
     compare (C a) (C b) = compare a b
 }}}

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


More information about the ghc-tickets mailing list