#4124: GHC rejects instance quotations with splices in the instance head
---------------------------------+------------------------------------------
Reporter: lilac | Owner:
Type: bug | Status: new
Priority: normal | Component: Template Haskell
Version: 6.12.1 | Keywords:
Os: Unknown/Multiple | Testcase:
Architecture: Unknown/Multiple | Failure: GHC rejects valid program
---------------------------------+------------------------------------------
I think the following code should be accepted.
{{{
{-# LANGUAGE TemplateHaskell #-}
class Storable a where
data X = X
[d| instance Storable $( [t| X |] ) where |]
}}}
GHC disagrees, saying:
{{{
test.hs:4:4:
Illegal instance declaration for `Storable t_aKj'
(All instance types must be of the form (T a1 ... an)
where a1 ... an are type *variables*,
and each type variable appears at most once in the instance head.
Use -XFlexibleInstances if you want to disable this.)
In the instance declaration for `Storable $[t| X |]'
In the Template Haskell quotation
[d|
instance Storable $[t| X |] where |]
In the expression:
[d|
instance Storable $[t| X |] where |]
}}}
This checking seems inappropriate before the type is actually spliced in!
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4124>
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