#5612: panic, impossible happened, "Exotic form of kind"
-------------------------------------------+--------------------------------
Reporter: guest | Owner: dreixel
Type: bug | Status: new
Priority: normal | Milestone: 7.4.1
Component: Compiler | Version: 7.3
Keywords: PolyKinds, TemplateHaskell | Os: Linux
Architecture: x86 | Failure: Other
Difficulty: | Testcase:
Blockedby: | Blocking:
Related: |
-------------------------------------------+--------------------------------
Changes (by lunaris):
* keywords: => PolyKinds, TemplateHaskell
* version: 7.0.3 => 7.3
Comment:
I can reproduce what appears to be the same bug with the following:
First.hs:
{{{
{-# LANGUAGE PolyKinds #-}
module First where
data Proxy (as :: [*])
= Proxy
f :: Proxy as -> ()
f _
= ()
}}}
Second.hs:
{{{
module Second where
import First
import Language.Haskell.TH
}}}
GHCI session:
{{{
% ghci -XTemplateHaskell Second.hs
GHCi, version 7.3.20111204: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
[1 of 2] Compiling First ( First.hs, interpreted )
[2 of 2] Compiling Second ( Second.hs, interpreted )
Ok, modules loaded: Second, First.
*Second> $(reify 'f >>= stringE . show)
Loading package array-0.3.0.3 ... linking ... done.
Loading package deepseq-1.2.0.1 ... linking ... done.
Loading package containers-0.4.2.0 ... linking ... done.
Loading package pretty-1.1.0.0 ... linking ... done.
Loading package template-haskell ... linking ... done.
<interactive>:2:3:
Exception when trying to run compile-time code:
<interactive>: panic! (the 'impossible' happened)
(GHC version 7.3.20111204 for x86_64-unknown-linux):
Exotic form of kind [ghc-prim:GHC.Prim.*{(w) tc 34d}]
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
Code: (>>=) reify 'f (.) stringE show
In the expression: $(reify 'f >>= stringE . show)
In an equation for `it': it = $(reify 'f >>= stringE . show)
}}}
As far as I can tell, there aren't any TH constructors for promoted kinds
yet, so reifyKind in TcSplice can't do anything better.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5612#comment:3>
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