[commit: ghc] master: Allow typed holes to be levity-polymorphic (ae66f35)

git at git.haskell.org git at git.haskell.org
Fri Aug 26 16:36:02 UTC 2016


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

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

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

commit ae66f356fb0dbf79dab1074d71275904c448b329
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


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

ae66f356fb0dbf79dab1074d71275904c448b329
 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 dc1a90f..8ae454c 100644
--- a/compiler/typecheck/TcExpr.hs
+++ b/compiler/typecheck/TcExpr.hs
@@ -1658,16 +1658,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 104c2ad..17c769e 100644
--- a/testsuite/tests/partial-sigs/should_compile/all.T
+++ b/testsuite/tests/partial-sigs/should_compile/all.T
@@ -65,3 +65,4 @@ test('T12033', normal, compile, [''])
 test('T11339a', normal, compile, [''])
 test('T11670', 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