ghc panic kindFunResult with template haskell 'isInstance'
--TH.hs
{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE TemplateHaskell #-}
module TH
( SomeClass
, doThStuff
) where
import Control.Monad ( void )
import Language.Haskell.TH
class SomeClass a where
doThStuff :: Name -> Q [Dec]
doThStuff name = reify name >>= go
go :: Info -> Q [Dec]
go (TyConI (DataD [] _ _ [(NormalC _ [(_,typ)])] _)) = do
void (isInstance ''SomeClass [typ]) -- THIS LINE CRASHES GHC
return []
go _ = fail "wrong info"
-- Bug.hs
{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE TemplateHaskell #-}
module Bug
( Bar(..)
) where
import TH
data Foo a = Foo a
instance SomeClass (Foo a)
data Bar f = Bar (Foo (f Int))
doThStuff ''Bar
I get this error:
$ runghc -ddump-splices Bug.hs
Bug.hs:1:1:
Exception when trying to run compile-time code:
ghc: panic! (the 'impossible' happened)
(GHC version 7.10.3 for x86_64-unknown-linux):
kindFunResult
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
Code: doThStuff ''Bar
If I comment out either instance SomeClass (Foo a)
or void (isInstance ''SomeClass [typ])
, the crash does not occur.
Trac metadata
Trac field | Value |
---|---|
Version | 7.10.3 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Template Haskell |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |