[Git][ghc/ghc][wip/T502] Add test for old issue displaying unboxed tuples in error messages (#502)
KevinBuhr
gitlab at gitlab.haskell.org
Fri May 10 02:52:26 UTC 2019
KevinBuhr pushed to branch wip/T502 at Glasgow Haskell Compiler / GHC
Commits:
ee91f93b by Kevin Buhr at 2019-05-10T02:52:08Z
Add test for old issue displaying unboxed tuples in error messages (#502)
- - - - -
3 changed files:
- + testsuite/tests/typecheck/should_fail/T502.hs
- + testsuite/tests/typecheck/should_fail/T502.stderr
- testsuite/tests/typecheck/should_fail/all.T
Changes:
=====================================
testsuite/tests/typecheck/should_fail/T502.hs
=====================================
@@ -0,0 +1,10 @@
+{-# LANGUAGE MagicHash, UnboxedTuples #-}
+
+module T502 where
+
+-- As per #502, the following type error message should correctly
+-- display the unboxed tuple type.
+bar :: Int
+bar = snd foo
+ where foo :: (# Int, Int #)
+ foo = undefined
=====================================
testsuite/tests/typecheck/should_fail/T502.stderr
=====================================
@@ -0,0 +1,12 @@
+
+T502.hs:8:11: error:
+ • Couldn't match expected type ‘(a0, Int)’
+ with actual type ‘(# Int, Int #)’
+ • In the first argument of ‘snd’, namely ‘foo’
+ In the expression: snd foo
+ In an equation for ‘bar’:
+ bar
+ = snd foo
+ where
+ foo :: (# Int, Int #)
+ foo = undefined
=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -515,3 +515,4 @@ test('T16204c', normal, compile_fail, [''])
test('T16394', normal, compile_fail, [''])
test('T16414', normal, compile_fail, [''])
test('T16627', normal, compile_fail, [''])
+test('T502', normal, compile_fail, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/ee91f93bc76a6ddd399c9fbbb194441497ffa523
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/ee91f93bc76a6ddd399c9fbbb194441497ffa523
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20190509/a6ee563a/attachment-0001.html>
More information about the ghc-commits
mailing list