[GHC] #9968: DeriveAnyClass fails on multi-parameter type classes

GHC ghc-devs at haskell.org
Wed Jul 29 17:51:45 UTC 2015


#9968: DeriveAnyClass fails on multi-parameter type classes
-------------------------------------+-------------------------------------
        Reporter:  goldfire          |                   Owner:  dreixel
            Type:  bug               |                  Status:  new
        Priority:  high              |               Milestone:  7.12.1
       Component:  Compiler          |                 Version:  7.10.1-rc1
      Resolution:                    |                Keywords:
Operating System:  Unknown/Multiple  |            Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |               Test Case:
      Blocked By:                    |                Blocking:
 Related Tickets:  #9821             |  Differential Revisions:
-------------------------------------+-------------------------------------

Comment (by osa1):

 I managed to get a panic out of this: (this is with GHC 7.10.2)

 {{{
 ➜  trac9968  cat Bug.hs
 {-# LANGUAGE DeriveAnyClass, MultiParamTypeClasses, FunctionalDependencies
 #-}

 module Bug where

 class C a b where
   showFirst  :: (a, b) -> String
   showSecond :: (a, b) -> String

 data X
   deriving (C Bool)

 main :: IO ()
 main = putStrLn "ok"
 ➜  trac9968  runhaskell Bug.hs
 Var/Type length mismatch:
   [b_alK]
   []
 Var/Type length mismatch:
   [b_alK]
   []
 Var/Type length mismatch:
   [b_alK]
   []
 Var/Type length mismatch:
   [b_alK]
   []
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.10.2 for x86_64-unknown-linux):
         funResultTy forall b_alK. C X b_alK => (X, b_alK) -> String

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

 A question about how `deriving` syntax supposed to work:

 Let's say we have

 {{{
 class C a b

 data X
 }}}

 as in the example above.

 We can do `deriving (C Bool)`, which implements an instance for `C Bool X`
 but
 if I want to derive `C X Bool`, is there a way to do that?  Currently if I
 try
 to do `deriving (C X Bool)` or `deriving (C Bool X)` I'm getting this
 error:

 {{{
 ➜  trac9968  runhaskell Bug.hs

 Bug.hs:10:13:
     Expected kind ‘k0 -> GHC.Prim.Constraint’,
       but ‘C Bool X’ has kind ‘GHC.Prim.Constraint’
     In the data declaration for ‘X’
 }}}

 Which is clear enough but I'm wondering if there are any workarounds to
 make
 `deriving (C X Bool)` work.

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


More information about the ghc-tickets mailing list