[GHC] #8128: Standalone deriving fails for GADTs due to inaccessible code

GHC ghc-devs at haskell.org
Tue Aug 13 11:56:21 CEST 2013


#8128: Standalone deriving fails for GADTs due to inaccessible code
-------------------------------------+-------------------------------------
       Reporter:  adamgundry         |             Owner:
           Type:  bug                |            Status:  new
       Priority:  normal             |         Milestone:
      Component:  Compiler (Type     |           Version:  7.7
  checker)                           |  Operating System:  Unknown/Multiple
       Keywords:                     |   Type of failure:  GHC rejects
   Architecture:  Unknown/Multiple   |  valid program
     Difficulty:  Unknown            |         Test Case:
     Blocked By:                     |          Blocking:
Related Tickets:                     |
-------------------------------------+-------------------------------------
 Consider the following:

 {{{
 {-# LANGUAGE StandaloneDeriving, GADTs, FlexibleInstances #-}

 module StandaloneDerivingGADT where

 data T a where
   MkT1 :: T Int
   MkT2 :: (Bool -> Bool) -> T Bool

 deriving instance Show (T Int)
 }}}

 This gives the error:

 {{{
 StandaloneDerivingGADT.hs:9:1:
     Couldn't match type ‛Int’ with ‛Bool’
     Inaccessible code in
       a pattern with constructor
         MkT2 :: (Bool -> Bool) -> T Bool,
       in an equation for ‛showsPrec’
     In the pattern: MkT2 b1
     In an equation for ‛showsPrec’:
         showsPrec a (MkT2 b1)
           = showParen
               ((a >= 11)) ((.) (showString "MkT2 ") (showsPrec 11 b1))
     When typechecking the code for  ‛showsPrec’
       in a standalone derived instance for ‛Show (T Int)’:
       To see the code I am typechecking, use -ddump-deriv
     In the instance declaration for ‛Show (T Int)’
 }}}

 The derived instance declaration matches on all the constructors, even if
 they cannot possibly match. It should omit obviously inaccessible
 constructors so that this example is accepted. For reference, the derived
 code is:

 {{{
   instance GHC.Show.Show
              (StandaloneDerivingGADT.T GHC.Types.Int) where
     GHC.Show.showsPrec _ StandaloneDerivingGADT.MkT1
       = GHC.Show.showString "MkT1"
     GHC.Show.showsPrec a_aij (StandaloneDerivingGADT.MkT2 b1_aik)
       = GHC.Show.showParen
           ((a_aij GHC.Classes.>= 11))
           ((GHC.Base..)
              (GHC.Show.showString "MkT2 ") (GHC.Show.showsPrec 11 b1_aik))
     GHC.Show.showList = GHC.Show.showList__ (GHC.Show.showsPrec 0)
 }}}

 The same problem applies to other derivable classes (e.g. `Eq`).

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




More information about the ghc-tickets mailing list