#5358: Exotic form of kind ghc-prim:GHC.Prim.?{(w) tc 34g}
---------------------------------+------------------------------------------
Reporter: alios | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 7.4.1
Component: Template Haskell | Version: 7.0.4
Keywords: | Testcase:
Blockedby: | Difficulty:
Os: Linux | Blocking:
Architecture: x86 | Failure: None/Unknown
---------------------------------+------------------------------------------
Changes (by igloo):
* component: Compiler => Template Haskell
* milestone: => 7.4.1
Comment:
Thanks for the report. Here's a testcase:
{{{
{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH
t1, t2 :: Int
t1 x = x
t2 x = x
prop_x1 x = t1 x == t2 x
runTests = $( do VarI _ t _ _ <- reify (mkName "prop_x1")
error $ pprint t
)
}}}
{{{
$ ghci q.hs
GHCi, version 7.3.20110729: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
[1 of 1] Compiling Main ( q.hs, interpreted )
Loading package pretty-1.1.0.0 ... linking ... done.
Loading package array-0.3.0.3 ... linking ... done.
Loading package containers-0.4.1.0 ... linking ... done.
Loading package template-haskell ... linking ... done.
q.hs:6:1:
The equation(s) for `t1' have one argument,
but its type `Int' has none
q.hs:7:1:
The equation(s) for `t2' have one argument,
but its type `Int' has none
q.hs:9:13:
The function `t1' is applied to one argument,
but its type `Int' has none
In the first argument of `(==)', namely `t1 x'
In the expression: t1 x == t2 x
In an equation for `prop_x1': prop_x1 x = t1 x == t2 x
q.hs:11:15:ghc-stage2: panic! (the 'impossible' happened)
(GHC version 7.3.20110729 for x86_64-unknown-linux):
Exotic form of kind ghc-prim:GHC.Prim.?{(w) tc 34g}
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5358#comment:1>
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