[commit: ghc] wip/T9732: Binding things matched by an unboxed pattern synonym should require a bang (73e69d0)
git at git.haskell.org
git at git.haskell.org
Thu Oct 30 15:40:08 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/T9732
Link : http://ghc.haskell.org/trac/ghc/changeset/73e69d0616979d9b6969f06b908ec0ff700901b8/ghc
>---------------------------------------------------------------
commit 73e69d0616979d9b6969f06b908ec0ff700901b8
Author: Dr. ERDI Gergo <gergo at erdi.hu>
Date: Wed Oct 29 11:58:29 2014 +0800
Binding things matched by an unboxed pattern synonym should require a bang
>---------------------------------------------------------------
73e69d0616979d9b6969f06b908ec0ff700901b8
testsuite/tests/patsyn/should_fail/all.T | 1 +
testsuite/tests/patsyn/should_fail/unboxed-bind.hs | 8 ++++++++
testsuite/tests/patsyn/should_fail/unboxed-bind.stderr | 9 +++++++++
3 files changed, 18 insertions(+)
diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T
index bff6bdf..808e261 100644
--- a/testsuite/tests/patsyn/should_fail/all.T
+++ b/testsuite/tests/patsyn/should_fail/all.T
@@ -6,3 +6,4 @@ test('T8961', normal, multimod_compile_fail, ['T8961',''])
test('as-pattern', normal, compile_fail, [''])
test('T9161-1', normal, compile_fail, [''])
test('T9161-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..037dc0e
--- /dev/null
+++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE PatternSynonyms, MagicHash #-}
+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..429ed07
--- /dev/null
+++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr
@@ -0,0 +1,9 @@
+
+unboxed-bind.hs:1:1:
+ The IO action ‘main’ is not defined in module ‘Main’
+
+unboxed-bind.hs:8: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