#6066: Constraint Kinds don't work with Template Haskell
------------------------------+---------------------------------------------
Reporter: sseverance | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.4.1 | Keywords:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
Failure: None/Unknown | Testcase:
Blockedby: | Blocking:
Related: |
------------------------------+---------------------------------------------
If I have a record with a constraint kind that has multiple constraints
such as:
{{{
type MyConstraint a = (Show a, Eq a, Typeable a)
data MyConstraint a => MyType a = MyType {
someField :: a
}
}}}
If I try to use template haskell on the type (in my case mkLabels from
fclabels) you get the following error: Can't represent tuple predicates
in Template Haskell: MyConstraint a
Complete Repro Case:
{{{
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DatatypeContexts #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE TemplateHaskell #-}
import Data.Label
import Data.Typeable
type MyConstraint a = (Show a, Eq a, Typeable a)
data MyConstraint a => MyType a = MyType {
myField :: a
} deriving (Show, Eq)
mkLabels [''MyType]
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/6066>
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