
#12222: ghc panic kindFunResult with template haskell 'isInstance' -------------------------------------+------------------------------------- Reporter: ghorn | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 7.10.3 Haskell | Keywords: kindFunResult | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs --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" }}} {{{#!hs -- 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. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12222 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler