#4235: deriving Enum fails for data instances
--------------------------------------------------------+-------------------
    Reporter:  nestra                                   |        Owner:         
                     
        Type:  bug                                      |       Status:  new    
                     
    Priority:  normal                                   |    Milestone:  6.14.1 
                     
   Component:  Compiler (Type checker)                  |      Version:  6.12.3 
                     
    Keywords:  instance deriving, type families, GADTs  |     Testcase:         
                     
   Blockedby:                                           |   Difficulty:         
                     
          Os:  Linux                                    |     Blocking:         
                     
Architecture:  x86_64 (amd64)                           |      Failure:  
Compile-time performance bug
--------------------------------------------------------+-------------------

Comment(by nestra):

 I discovered that this bug occurs even with the following example:
 {{{
 module Foo where

 data Foo a
   = A | B
   deriving (Enum)
 }}}

 {{{
 Foo.hs:1:0:
     Expecting an ordinary type, but found a type of kind * -> *
     In an expression type signature: Foo
     In the expression: GHC.Prim.tagToEnum# a :: Foo
     In the definition of `Foo.$tag2con_Foo':
         Foo.$tag2con_Foo (GHC.Types.I# a) = GHC.Prim.tagToEnum# a :: Foo
 }}}
 So, the bug is not specific to the extensions (although the examples
 revealing it occur in practice more probably when programming with type
 families or GADTs).

 The same behaviour is observed in the case of deriving Ix.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4235#comment:2>
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