[GHC] #11680: Out-of-scope suggestion given for an out-of-scope variable when using TH
GHC
ghc-devs at haskell.org
Sat Mar 5 15:58:18 UTC 2016
#11680: Out-of-scope suggestion given for an out-of-scope variable when using TH
-------------------------------------+-------------------------------------
Reporter: jme | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1-rc2
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Incorrect
Unknown/Multiple | warning at compile-time
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
With GHC 8.x, compiling
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
module A where
import Language.Haskell.TH
sep :: Q [Dec]
sep = [d| x = () |]
}}}
and
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
module B where
import A
f :: Int
f = foo
$(sep)
foo :: Int
foo = 3
}}}
produces
{{{
$ ghc-HEAD/inplace/bin/ghc-stage2 --version
The Glorious Glasgow Haskell Compilation System, version 8.1.20160303
$ ghc-HEAD/inplace/bin/ghc-stage2 B.hs
[1 of 2] Compiling A ( A.hs, A.o )
[2 of 2] Compiling B ( B.hs, B.o )
B.hs:8:5: error:
• Variable not in scope: foo :: Int
• Perhaps you meant ‘foo’ (line 13)
}}}
The problem is that when the typechecker constructs the suggestion, it
uses the
currently available `GlobalRdrEnv` rather than the one in existence when
the renamer determined that `foo` is unbound.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11680>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list