[GHC] #15481: TH fails to recover from reifyFixity with -fexternal-interpreter
GHC
ghc-devs at haskell.org
Mon Aug 6 11:21:34 UTC 2018
#15481: TH fails to recover from reifyFixity with -fexternal-interpreter
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.8.1
Component: Template | Version: 8.4.3
Haskell |
Keywords: RemoteGHCi | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
(Originally reported at https://github.com/glguy/th-
abstraction/issues/53.)
If you compile the following program:
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
module Bug where
import Language.Haskell.TH
main :: IO ()
main = putStrLn $(recover (stringE "reifyFixity failed")
(do foo <- newName "foo"
_ <- reifyFixity foo
stringE "reifyFixity successful"))
}}}
It will work fine without the use of `-fexternal-interpreter`. However,
using `-fexternal-interpreter` will result in an error:
{{{
$ /opt/ghc/8.4.3/bin/ghc Bug.hs -fforce-recomp
[1 of 1] Compiling Bug ( Bug.hs, Bug.o )
$ /opt/ghc/8.4.3/bin/ghc Bug.hs -fforce-recomp -fexternal-interpreter
[1 of 1] Compiling Bug ( Bug.hs, Bug.o )
Bug.hs:7:19: error:
• The exact Name ‘foo_a3MT’ is not in scope
Probable cause: you used a unique Template Haskell name (NameU),
perhaps via newName, but did not bind it
If that's it, then -ddump-splices might be useful
• In the untyped splice:
$(recover
(stringE "reifyFixity failed")
(do foo <- newName "foo"
_ <- reifyFixity foo
stringE "reifyFixity successful"))
|
7 | main = putStrLn $(recover (stringE "reifyFixity failed")
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
Bug.hs:7:19: error:
• The exact Name ‘foo_a3MT’ is not in scope
Probable cause: you used a unique Template Haskell name (NameU),
perhaps via newName, but did not bind it
If that's it, then -ddump-splices might be useful
• In the untyped splice:
$(recover
(stringE "reifyFixity failed")
(do foo <- newName "foo"
_ <- reifyFixity foo
stringE "reifyFixity successful"))
|
7 | main = putStrLn $(recover (stringE "reifyFixity failed")
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15481>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list