#5007: "deriving" seems to ignore class context for a type family
----------------------------------------+-----------------------------------
  Reporter:  jkff                       |          Owner:  simonpj              
                                   
      Type:  bug                        |         Status:  closed               
                                   
  Priority:  high                       |      Milestone:  7.2.1                
                                   
 Component:  Compiler (Type checker)    |        Version:  7.0.2                
                                   
Resolution:  invalid                    |       Keywords:  type families, 
datatype contexts, type classes, deriving
  Testcase:                             |      Blockedby:                       
                                   
Difficulty:                             |             Os:  Unknown/Multiple     
                                   
  Blocking:                             |   Architecture:  Unknown/Multiple     
                                   
   Failure:  GHC rejects valid program  |  
----------------------------------------+-----------------------------------
Changes (by simonpj):

  * status:  new => closed
  * resolution:  => invalid


Comment:

 The error message is quite right.

 Using a context on a data type declaration, as you are doing, is a mis-
 feature of Haskell.  If you read its specification carefully you'll see
 that it is practically useless. Any program using it is suspicious.
 Certainly, it has absolutely no effect on 'deriving' declarations.

 You can follow the advice in the error message and use a standalone
 deriving declaration, thus
 {{{
 {-# LANGUAGE StandaloneDeriving, FlexibleContexts, UndecidableInstances,
 TypeFamilies #-}

 module T5007 where

 class Foo a where
    data Bar a :: *

 class (Show (Bar a)) => Qux a
 data Xyzzy a = Xyzzy (Bar a)

 deriving instance Show (Bar a) => Show (Xyzzy a)
 }}}

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