[commit: ghc] master: Avoid double error on out-of-scope identifier (c2b7a3d)

git at git.haskell.org git at git.haskell.org
Fri Apr 22 10:30:12 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/c2b7a3d9f6ad946a2cb2773e96a377cc2216cb5b/ghc

>---------------------------------------------------------------

commit c2b7a3d9f6ad946a2cb2773e96a377cc2216cb5b
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Thu Apr 21 14:34:07 2016 +0100

    Avoid double error on out-of-scope identifier
    
    Trac #11941 demonstrated a case where an out-of-scope error also
    gave rise to a (bogus and confusing) stage restriction message.
    
    It's caused by the fact that out-of-scope errors do not stop
    renaming, but rather return an "unbound name".  We need to
    detect this in the stage-restriction test to avoid the double
    error.  Easy fix.


>---------------------------------------------------------------

c2b7a3d9f6ad946a2cb2773e96a377cc2216cb5b
 compiler/typecheck/TcEnv.hs      | 12 ++++++++----
 testsuite/tests/th/T11941.hs     |  7 +++++++
 testsuite/tests/th/T11941.stderr |  6 ++++++
 testsuite/tests/th/all.T         |  1 +
 4 files changed, 22 insertions(+), 4 deletions(-)

diff --git a/compiler/typecheck/TcEnv.hs b/compiler/typecheck/TcEnv.hs
index b2a31b1..5bc3d00 100644
--- a/compiler/typecheck/TcEnv.hs
+++ b/compiler/typecheck/TcEnv.hs
@@ -966,7 +966,10 @@ notFound name
   = do { lcl_env <- getLclEnv
        ; let stage = tcl_th_ctxt lcl_env
        ; case stage of   -- See Note [Out of scope might be a staging error]
-           Splice {} -> stageRestrictionError (quotes (ppr name))
+           Splice {}
+             | isUnboundName name -> failM  -- If the name really isn't in scope
+                                            -- don't report it again (Trac #11941)
+             | otherwise -> stageRestrictionError (quotes (ppr name))
            _ -> failWithTc $
                 vcat[text "GHC internal error:" <+> quotes (ppr name) <+>
                      text "is not in scope during type checking, but it passed the renamer",
@@ -986,13 +989,14 @@ wrongThingErr expected thing name
   = failWithTc (pprTcTyThingCategory thing <+> quotes (ppr name) <+>
                 text "used as a" <+> text expected)
 
-{-
-Note [Out of scope might be a staging error]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+{- Note [Out of scope might be a staging error]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 Consider
   x = 3
   data T = MkT $(foo x)
 
+where 'foo' is is imported from somewhere.
+
 This is really a staging error, because we can't run code involving 'x'.
 But in fact the type checker processes types first, so 'x' won't even be
 in the type envt when we look for it in $(foo x).  So inside splices we
diff --git a/testsuite/tests/th/T11941.hs b/testsuite/tests/th/T11941.hs
new file mode 100644
index 0000000..ed7e746
--- /dev/null
+++ b/testsuite/tests/th/T11941.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module T11941 where
+
+import Data.Monoid
+
+const (return []) $ mempty { getFrst = Just () }
diff --git a/testsuite/tests/th/T11941.stderr b/testsuite/tests/th/T11941.stderr
new file mode 100644
index 0000000..4508ed3
--- /dev/null
+++ b/testsuite/tests/th/T11941.stderr
@@ -0,0 +1,6 @@
+
+T11941.hs:7:30: error:
+    Not in scope: ‘getFrst’
+    Perhaps you meant one of these:
+      ‘getFirst’ (imported from Data.Monoid),
+      ‘getLast’ (imported from Data.Monoid)
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index 648f7c9..09960d1 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -403,3 +403,4 @@ test('T11463', normal, compile_and_run, ['-v0 -dsuppress-uniques'])
 test('T11680', normal, compile_fail, ['-v0'])
 test('T11809', normal, compile, ['-v0'])
 test('T11797', normal, compile, ['-v0 -dsuppress-uniques'])
+test('T11941', normal, compile_fail, ['-v0'])



More information about the ghc-commits mailing list