[commit: ghc] master: Fix Trac #10618 (out of scope operator) (4f9d600)
git at git.haskell.org
git at git.haskell.org
Wed Jul 8 22:42:49 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/4f9d6008c04b71fc9449b3dc10861f757539ed0f/ghc
>---------------------------------------------------------------
commit 4f9d6008c04b71fc9449b3dc10861f757539ed0f
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Wed Jul 8 23:42:28 2015 +0100
Fix Trac #10618 (out of scope operator)
Out of scope variables now generate HsUnboundVar,
and the fixity re-jigging wasn't taking this into
account.
>---------------------------------------------------------------
4f9d6008c04b71fc9449b3dc10861f757539ed0f
compiler/rename/RnTypes.hs | 7 +++++--
testsuite/tests/rename/should_fail/T10618.hs | 3 +++
testsuite/tests/rename/should_fail/T10618.stderr | 6 ++++++
testsuite/tests/rename/should_fail/all.T | 1 +
4 files changed, 15 insertions(+), 2 deletions(-)
diff --git a/compiler/rename/RnTypes.hs b/compiler/rename/RnTypes.hs
index 705ca55..ac2982b 100644
--- a/compiler/rename/RnTypes.hs
+++ b/compiler/rename/RnTypes.hs
@@ -829,8 +829,11 @@ mkOpAppRn e1 op fix e2 -- Default case, no rearrangment
----------------------------
get_op :: LHsExpr Name -> Name
-get_op (L _ (HsVar n)) = n
-get_op other = pprPanic "get_op" (ppr other)
+-- An unbound name could be either HsVar or HsUnboundVra
+-- See RnExpr.rnUnboundVar
+get_op (L _ (HsVar n)) = n
+get_op (L _ (HsUnboundVar occ)) = mkUnboundName (mkRdrUnqual occ)
+get_op other = pprPanic "get_op" (ppr other)
-- Parser left-associates everything, but
-- derived instances may have correctly-associated things to
diff --git a/testsuite/tests/rename/should_fail/T10618.hs b/testsuite/tests/rename/should_fail/T10618.hs
new file mode 100644
index 0000000..28b665f
--- /dev/null
+++ b/testsuite/tests/rename/should_fail/T10618.hs
@@ -0,0 +1,3 @@
+module T10618 where
+
+foo = Just $ Nothing <> Nothing
diff --git a/testsuite/tests/rename/should_fail/T10618.stderr b/testsuite/tests/rename/should_fail/T10618.stderr
new file mode 100644
index 0000000..01e1948
--- /dev/null
+++ b/testsuite/tests/rename/should_fail/T10618.stderr
@@ -0,0 +1,6 @@
+
+T10618.hs:3:22: error:
+ Variable not in scope: (<>) :: Maybe (Maybe a0) -> Maybe a1 -> t
+ Perhaps you meant one of these:
+ ‘<$>’ (imported from Prelude), ‘*>’ (imported from Prelude),
+ ‘<$’ (imported from Prelude)
diff --git a/testsuite/tests/rename/should_fail/all.T b/testsuite/tests/rename/should_fail/all.T
index 0df9868..bfd81c5 100644
--- a/testsuite/tests/rename/should_fail/all.T
+++ b/testsuite/tests/rename/should_fail/all.T
@@ -133,3 +133,4 @@ test('T9032',
normal,
run_command,
['$MAKE -s --no-print-directory T9032'])
+test('T10618', normal, compile_fail, [''])
More information about the ghc-commits
mailing list