[commit: ghc] ghc-8.0: Not-in-scope variables are always errors (6071ecf)
git at git.haskell.org
git at git.haskell.org
Thu Aug 25 16:37:32 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : ghc-8.0
Link : http://ghc.haskell.org/trac/ghc/changeset/6071ecf4ff7501c70456c1448fa2f78e91bc8078/ghc
>---------------------------------------------------------------
commit 6071ecf4ff7501c70456c1448fa2f78e91bc8078
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Wed Aug 17 12:04:30 2016 +0100
Not-in-scope variables are always errors
This fixes Trac #12406. A not-in-scope error shoudl be an error
even if you have -fdefer-typed-holes.
(cherry picked from commit efc0372a157eadeee58bbada77c64d53590e04af)
>---------------------------------------------------------------
6071ecf4ff7501c70456c1448fa2f78e91bc8078
compiler/typecheck/TcErrors.hs | 10 ++++++++--
.../tests/partial-sigs/should_compile/T12156.stderr | 3 +--
testsuite/tests/partial-sigs/should_compile/all.T | 2 +-
testsuite/tests/typecheck/should_fail/T12406.hs | 20 ++++++++++++++++++++
testsuite/tests/typecheck/should_fail/T12406.stderr | 12 ++++++++++++
testsuite/tests/typecheck/should_fail/all.T | 1 +
6 files changed, 43 insertions(+), 5 deletions(-)
diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs
index 406f13d..d638892 100644
--- a/compiler/typecheck/TcErrors.hs
+++ b/compiler/typecheck/TcErrors.hs
@@ -613,9 +613,15 @@ maybeReportHoleError ctxt ct err
HoleWarn -> reportWarning (Reason Opt_WarnPartialTypeSignatures) err
HoleDefer -> return ()
- -- Otherwise this is a typed hole in an expression
+ | isOutOfScopeCt ct
+ = -- Always report an error for out-of-scope variables
+ -- See Trac #12170, #12406
+ reportError err
+
+ -- Otherwise this is a typed hole in an expression,
+ -- but not for an out-of-scope variable
| otherwise
- = -- If deferring, report a warning only if -Wtyped-holds is on
+ = -- If deferring, report a warning only if -Wtyped-holes is on
case cec_expr_holes ctxt of
HoleError -> reportError err
HoleWarn -> reportWarning (Reason Opt_WarnTypedHoles) err
diff --git a/testsuite/tests/partial-sigs/should_compile/T12156.stderr b/testsuite/tests/partial-sigs/should_compile/T12156.stderr
index 6508d8a..f1a5b9d 100644
--- a/testsuite/tests/partial-sigs/should_compile/T12156.stderr
+++ b/testsuite/tests/partial-sigs/should_compile/T12156.stderr
@@ -1,3 +1,2 @@
-T12156.hs:3:14: warning: [-Wtyped-holes (in -Wdefault)]
- Variable not in scope: v
+T12156.hs:3:14: error: Variable not in scope: v
diff --git a/testsuite/tests/partial-sigs/should_compile/all.T b/testsuite/tests/partial-sigs/should_compile/all.T
index bc3531a..63a6efc 100644
--- a/testsuite/tests/partial-sigs/should_compile/all.T
+++ b/testsuite/tests/partial-sigs/should_compile/all.T
@@ -62,4 +62,4 @@ test('T10463', normal, compile, [''])
test('ExprSigLocal', normal, compile, [''])
test('T11016', normal, compile, [''])
test('T11192', normal, compile, [''])
-test('T12156', normal, compile, ['-fdefer-typed-holes'])
+test('T12156', normal, compile_fail, ['-fdefer-typed-holes'])
diff --git a/testsuite/tests/typecheck/should_fail/T12406.hs b/testsuite/tests/typecheck/should_fail/T12406.hs
new file mode 100644
index 0000000..20264cc
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T12406.hs
@@ -0,0 +1,20 @@
+{-# LANGUAGE TypeFamilies #-}
+{-# OPTIONS_GHC -fdefer-typed-holes #-}
+
+module T12406 where
+
+-- import Control.Monad -- comment this out to cause error
+import Data.IORef
+
+class MonadRef m where
+ type Ref m :: * -> *
+ newRef :: a -> m (Ref m a)
+ readRef :: Ref m a -> m a
+
+instance MonadRef IO where
+ type Ref IO = IORef
+ newRef = newIORef
+ readRef = readIORef
+
+foo :: IO ()
+foo = newRef (pure ()) >>= join . readRef
diff --git a/testsuite/tests/typecheck/should_fail/T12406.stderr b/testsuite/tests/typecheck/should_fail/T12406.stderr
new file mode 100644
index 0000000..85096e6
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T12406.stderr
@@ -0,0 +1,12 @@
+
+T12406.hs:20:7: error:
+ • Couldn't match type ‘Ref m0’ with ‘IORef’
+ Expected type: IO (Ref m0 (f0 ()))
+ Actual type: IO (Ref IO (f0 ()))
+ The type variable ‘m0’ is ambiguous
+ • In the first argument of ‘(>>=)’, namely ‘newRef (pure ())’
+ In the expression: newRef (pure ()) >>= join . readRef
+ In an equation for ‘foo’: foo = newRef (pure ()) >>= join . readRef
+
+T12406.hs:20:28: error:
+ Variable not in scope: join :: m0 (f0 ()) -> IO ()
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index e6aa020..3880287 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -419,3 +419,4 @@ test('T12151', normal, compile_fail, [''])
test('T7437', normal, compile_fail, [''])
test('T11947a', normal, compile_fail, [''])
test('T11974b', normal, compile_fail, [''])
+test('T12406', normal, compile_fail, [''])
More information about the ghc-commits
mailing list