[commit: ghc] wip/T9732: Binding things matched by an unboxed pattern synonym should require a bang (05feff2)
git at git.haskell.org
git at git.haskell.org
Wed Nov 12 11:06:55 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/T9732
Link : http://ghc.haskell.org/trac/ghc/changeset/05feff27130542204e5300b53053abe6fd624602/ghc
>---------------------------------------------------------------
commit 05feff27130542204e5300b53053abe6fd624602
Author: Dr. ERDI Gergo <gergo at erdi.hu>
Date: Sat Nov 8 16:59:47 2014 +0800
Binding things matched by an unboxed pattern synonym should require a bang
>---------------------------------------------------------------
05feff27130542204e5300b53053abe6fd624602
testsuite/tests/patsyn/should_compile/all.T | 1 +
testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs | 10 ++++++++++
testsuite/tests/patsyn/should_fail/all.T | 2 +-
testsuite/tests/patsyn/should_fail/unboxed-bind.hs | 10 ++++++++++
testsuite/tests/patsyn/should_fail/unboxed-bind.stderr | 6 ++++++
5 files changed, 28 insertions(+), 1 deletion(-)
diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T
index d851bc3..94950a1 100644
--- a/testsuite/tests/patsyn/should_compile/all.T
+++ b/testsuite/tests/patsyn/should_compile/all.T
@@ -10,3 +10,4 @@ test('incomplete', normal, compile, [''])
test('export', normal, compile, [''])
test('T8966', normal, compile, [''])
test('T9023', normal, compile, [''])
+test('unboxed-bind-bang', normal, compile, [''])
diff --git a/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs
new file mode 100644
index 0000000..a972b21
--- /dev/null
+++ b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs
@@ -0,0 +1,10 @@
+{-# LANGUAGE PatternSynonyms, MagicHash, BangPatterns #-}
+module ShouldCompile where
+
+import GHC.Base
+
+data Foo = MkFoo Int# Int#
+
+pattern P x = MkFoo 0# x
+
+f x = let !(P arg) = x in arg
diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T
index ea671dc..ee5768c 100644
--- a/testsuite/tests/patsyn/should_fail/all.T
+++ b/testsuite/tests/patsyn/should_fail/all.T
@@ -1,4 +1,3 @@
-
test('mono', normal, compile_fail, [''])
test('unidir', normal, compile_fail, [''])
test('local', normal, compile_fail, [''])
@@ -8,3 +7,4 @@ test('T9161-1', normal, compile_fail, [''])
test('T9161-2', normal, compile_fail, [''])
test('T9705-1', normal, compile_fail, [''])
test('T9705-2', normal, compile_fail, [''])
+test('unboxed-bind', normal, compile_fail, [''])
diff --git a/testsuite/tests/patsyn/should_fail/unboxed-bind.hs b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs
new file mode 100644
index 0000000..ef1b070
--- /dev/null
+++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs
@@ -0,0 +1,10 @@
+{-# LANGUAGE PatternSynonyms, MagicHash #-}
+module ShouldFail where
+
+import GHC.Base
+
+data Foo = MkFoo Int# Int#
+
+pattern P x = MkFoo 0# x
+
+f x = let P arg = x in arg
diff --git a/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr
new file mode 100644
index 0000000..17ca7af
--- /dev/null
+++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr
@@ -0,0 +1,6 @@
+
+unboxed-bind.hs:10:11:
+ Pattern bindings containing unlifted types should use an outermost bang pattern:
+ P arg = x
+ In the expression: let P arg = x in arg
+ In an equation for ‘f’: f x = let P arg = x in arg
More information about the ghc-commits
mailing list