[commit: ghc] ghc-8.0: Allow typed holes to be levity-polymorphic (f4ac734)
git at git.haskell.org
git at git.haskell.org
Tue Aug 30 21:43:48 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : ghc-8.0
Link : http://ghc.haskell.org/trac/ghc/changeset/f4ac734d754e2d4399525038e8a4dd4a841ce8af/ghc
>---------------------------------------------------------------
commit f4ac734d754e2d4399525038e8a4dd4a841ce8af
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Fri Aug 26 17:24:10 2016 +0100
Allow typed holes to be levity-polymorphic
This one-line change fixes Trac #12531. Hooray.
Simple, non-invasive; can merge to 8.0.2
(cherry picked from commit ae66f356fb0dbf79dab1074d71275904c448b329)
>---------------------------------------------------------------
f4ac734d754e2d4399525038e8a4dd4a841ce8af
compiler/typecheck/TcExpr.hs | 8 ++++----
.../T5472.stdout => partial-sigs/should_compile/12531.stderr} | 0
testsuite/tests/partial-sigs/should_compile/T12531.hs | 6 ++++++
testsuite/tests/partial-sigs/should_compile/all.T | 1 +
4 files changed, 11 insertions(+), 4 deletions(-)
diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs
index d083f3f..0933623 100644
--- a/compiler/typecheck/TcExpr.hs
+++ b/compiler/typecheck/TcExpr.hs
@@ -1593,16 +1593,16 @@ tc_infer_id lbl id_name
tcUnboundId :: UnboundVar -> ExpRhoType -> TcM (HsExpr TcId)
--- Typechedk an occurrence of an unbound Id
+-- Typecheck an occurrence of an unbound Id
--
--- Some of these started life as a true hole "_". Others might simply
--- be variables that accidentally have no binding site
+-- Some of these started life as a true expression hole "_".
+-- Others might simply be variables that accidentally have no binding site
--
-- We turn all of them into HsVar, since HsUnboundVar can't contain an
-- Id; and indeed the evidence for the CHoleCan does bind it, so it's
-- not unbound any more!
tcUnboundId unbound res_ty
- = do { ty <- newFlexiTyVarTy liftedTypeKind
+ = do { ty <- newOpenFlexiTyVarTy -- Allow Int# etc (Trac #12531)
; let occ = unboundVarOcc unbound
; name <- newSysName occ
; let ev = mkLocalId name ty
diff --git a/testsuite/tests/deSugar/should_run/T5472.stdout b/testsuite/tests/partial-sigs/should_compile/12531.stderr
similarity index 100%
copy from testsuite/tests/deSugar/should_run/T5472.stdout
copy to testsuite/tests/partial-sigs/should_compile/12531.stderr
diff --git a/testsuite/tests/partial-sigs/should_compile/T12531.hs b/testsuite/tests/partial-sigs/should_compile/T12531.hs
new file mode 100644
index 0000000..2488db2
--- /dev/null
+++ b/testsuite/tests/partial-sigs/should_compile/T12531.hs
@@ -0,0 +1,6 @@
+{-# LANGUAGE MagicHash #-}
+
+module T12531 where
+import GHC.Exts
+
+f x = I# (_ +# x)
diff --git a/testsuite/tests/partial-sigs/should_compile/all.T b/testsuite/tests/partial-sigs/should_compile/all.T
index 63a6efc..38c937c 100644
--- a/testsuite/tests/partial-sigs/should_compile/all.T
+++ b/testsuite/tests/partial-sigs/should_compile/all.T
@@ -63,3 +63,4 @@ test('ExprSigLocal', normal, compile, [''])
test('T11016', normal, compile, [''])
test('T11192', normal, compile, [''])
test('T12156', normal, compile_fail, ['-fdefer-typed-holes'])
+test('T12531', normal, compile, ['-fdefer-typed-holes'])
More information about the ghc-commits
mailing list