[GHC] #14627: qAddTopDecls: can't convert top-level declarations
GHC
ghc-devs at haskell.org
Tue Jan 2 18:49:27 UTC 2018
#14627: qAddTopDecls: can't convert top-level declarations
-------------------------------------+-------------------------------------
Reporter: tianxiaogu | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.2
Keywords: | Operating System: Linux
Architecture: x86_64 | Type of failure: Compile-time
(amd64) | crash or panic
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
The following program crashes 8.2.2 and HEAD (8.5.20171228).
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH.Syntax (addTopDecls)
$(do
ds <- [d| f = Bool
|]
addTopDecls ds
[d| g = cab
|])
}}}
Output:
{{{
Exception when trying to run compile-time code:
ghc: panic! (the 'impossible' happened)
(GHC version 8.5.20171228 for x86_64-unknown-linux):
qAddTopDecls: can't convert top-level declarations
Illegal variable name: ‘Bool’
When splicing a TH declaration: f_0 = Bool
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in
ghc:Outputable
pprPanic, called at compiler/typecheck/TcSplice.hs:886:27 in
ghc:TcSplice
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14627>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list