#4528: stand-alone deriving sometimes fails for GADTs
-------------------------------+--------------------------------------------
    Reporter:  nestra          |       Owner:                              
        Type:  bug             |      Status:  new                         
    Priority:  normal          |   Component:  Compiler (Type checker)     
     Version:  7.0.1           |    Keywords:  deriving mechanism, GADTs   
    Testcase:                  |   Blockedby:                              
          Os:  Linux           |    Blocking:                              
Architecture:  x86_64 (amd64)  |     Failure:  Compile-time performance bug
-------------------------------+--------------------------------------------
 Consider the following module

 {{{
 {-# LANGUAGE GADTs, StandaloneDeriving #-}
 module Foo where

 data Foo a where
   A, B :: Foo Int

 deriving instance Enum (Foo a)
 }}}

 Loading it into GHCi causes the following message:

 {{{
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.0.1 for x86_64-unknown-linux):
         maybe_is_tagToEnum_call.extract_constr_Ids

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
 }}}

 In the case of Bounded instead of Enum in the original code, it does not
 work either but the error message is more "even-tempered":

 {{{
 Foo.hs:7:1:
     Couldn't match type `a' with `Int'
       `a' is a rigid type variable bound by
           the instance declaration at Foo.hs:7:32
     In the expression: A
     In an equation for `minBound': minBound = A
     When typechecking the code for  `minBound'
       in a standalone derived instance for `Bounded (Foo a)':
       To see the code I am typechecking, use -ddump-deriv
     In the instance declaration for `Bounded (Foo a)'

 Foo.hs:7:1:
     Couldn't match type `a' with `Int'
       `a' is a rigid type variable bound by
           the instance declaration at Foo.hs:7:32
     In the expression: B
     In an equation for `maxBound': maxBound = B
     When typechecking the code for  `maxBound'
       in a standalone derived instance for `Bounded (Foo a)':
       To see the code I am typechecking, use -ddump-deriv
     In the instance declaration for `Bounded (Foo a)'
 Failed, modules loaded: none.
 }}}

 I suspect that this is also a bug, as it would be perfectly reasonable to
 have minBound and maxBound for a type such as Foo Int.

 A similar deriving fails also for Read class, among those I tried.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4528>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to