summaryrefslogtreecommitdiff
path: root/testsuite/tests/typecheck/should_fail
diff options
context:
space:
mode:
authorMax Bolingbroke <batterseapower@hotmail.com>2012-05-15 16:37:28 +0100
committerMax Bolingbroke <batterseapower@hotmail.com>2012-05-15 22:19:10 +0100
commitada75a845fe1b1e7b051ec82556fd464efc2ecda (patch)
treef217ba2d7f70c28a1954f1f03aac30d7977a52c0 /testsuite/tests/typecheck/should_fail
parent24d70daed5082f1aa32424e12650e136ca404771 (diff)
downloadhaskell-ada75a845fe1b1e7b051ec82556fd464efc2ecda.tar.gz
Testsuite update for unboxed tuples in arguments
We are careful to test slow calls and RtClosureInspect, as well as standard fast calls
Diffstat (limited to 'testsuite/tests/typecheck/should_fail')
-rw-r--r--testsuite/tests/typecheck/should_fail/T5573a.hs16
-rw-r--r--testsuite/tests/typecheck/should_fail/T5573a.stderr16
-rw-r--r--testsuite/tests/typecheck/should_fail/T5573b.hs8
-rw-r--r--testsuite/tests/typecheck/should_fail/T5573b.stderr7
-rw-r--r--testsuite/tests/typecheck/should_fail/all.T6
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail087.hs13
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail087.stderr7
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail115.hs13
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail115.stderr14
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail120.hs14
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail120.stderr7
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail141.hs17
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail141.stderr7
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail159.stderr4
14 files changed, 2 insertions, 147 deletions
diff --git a/testsuite/tests/typecheck/should_fail/T5573a.hs b/testsuite/tests/typecheck/should_fail/T5573a.hs
deleted file mode 100644
index 13b384848d..0000000000
--- a/testsuite/tests/typecheck/should_fail/T5573a.hs
+++ /dev/null
@@ -1,16 +0,0 @@
-{-# LANGUAGE MagicHash, UnboxedTuples, BangPatterns #-}
-module T5573a where
-
-import GHC.Exts
-
--- This is ok
-foo1 x = (# x,x #)
-bar y = let (# x, _ #) = foo1 y in x
-
--- Nested unboxed tuple not ok
-foo2 x = (# x, (# True, False #) #)
-
--- Unboxed tuple argument not ok
-foo3 (# x,y #) = x
-
-
diff --git a/testsuite/tests/typecheck/should_fail/T5573a.stderr b/testsuite/tests/typecheck/should_fail/T5573a.stderr
deleted file mode 100644
index 52aa99ae71..0000000000
--- a/testsuite/tests/typecheck/should_fail/T5573a.stderr
+++ /dev/null
@@ -1,16 +0,0 @@
-
-T5573a.hs:11:16:
- Couldn't match kind `ArgKind' against `(#)'
- Kind incompatibility when matching types:
- t0 :: ArgKind
- (# t0, t1 #) :: (#)
- In the expression: (# True, False #)
- In the expression: (# x, (# True, False #) #)
-
-T5573a.hs:14:6:
- Couldn't match kind `ArgKind' against `(#)'
- Kind incompatibility when matching types:
- t0 :: ArgKind
- (# t0, t1 #) :: (#)
- In the pattern: (# x, y #)
- In an equation for `foo3': foo3 (# x, y #) = x
diff --git a/testsuite/tests/typecheck/should_fail/T5573b.hs b/testsuite/tests/typecheck/should_fail/T5573b.hs
deleted file mode 100644
index 0a187c9b87..0000000000
--- a/testsuite/tests/typecheck/should_fail/T5573b.hs
+++ /dev/null
@@ -1,8 +0,0 @@
-{-# LANGUAGE MagicHash, UnboxedTuples, BangPatterns #-}
-module T5573b where
-
-import GHC.Exts
-
-foo :: Double# -> (# (# Double#, Double# #), Double# #)
-foo x = (# (# x, x #), x #)
-
diff --git a/testsuite/tests/typecheck/should_fail/T5573b.stderr b/testsuite/tests/typecheck/should_fail/T5573b.stderr
deleted file mode 100644
index b2cbf6d0eb..0000000000
--- a/testsuite/tests/typecheck/should_fail/T5573b.stderr
+++ /dev/null
@@ -1,7 +0,0 @@
-
-T5573b.hs:6:22:
- Kind mis-match
- The first argument of an unboxed tuple should have kind `ArgKind',
- but `(# Double#, Double# #)' has kind `(#)'
- In the type signature for `foo':
- foo :: Double# -> (# (# Double#, Double# #), Double# #)
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index e27d0ccaa0..98df6dad39 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -73,7 +73,6 @@ test('tcfail083', normal, compile_fail, [''])
test('tcfail084', normal, compile_fail, [''])
test('tcfail085', normal, compile_fail, [''])
test('tcfail086', normal, compile_fail, [''])
-test('tcfail087', only_compiler_types(['ghc']), compile_fail, [''])
test('tcfail088', normal, compile_fail, [''])
test('tcfail089', normal, compile_fail, [''])
test('tcfail090', only_compiler_types(['ghc']), compile_fail, [''])
@@ -99,12 +98,10 @@ test('tcfail110', normal, compile_fail, [''])
test('tcfail112', normal, compile_fail, [''])
test('tcfail113', normal, compile_fail, [''])
test('tcfail114', normal, compile_fail, [''])
-test('tcfail115', only_compiler_types(['ghc']), compile_fail, [''])
test('tcfail116', normal, compile_fail, [''])
test('tcfail117', normal, compile_fail, [''])
test('tcfail118', normal, compile_fail, [''])
test('tcfail119', normal, compile_fail, [''])
-test('tcfail120', only_compiler_types(['ghc']), compile_fail, [''])
test('tcfail121', normal, compile_fail, [''])
test('tcfail122', only_compiler_types(['ghc']), compile_fail, [''])
test('tcfail123', only_compiler_types(['ghc']), compile_fail, [''])
@@ -128,7 +125,6 @@ test('tcfail138', normal, compile, [''])
test('tcfail139', normal, compile_fail, [''])
test('tcfail140', normal, compile_fail, [''])
-test('tcfail141', only_compiler_types(['ghc']), compile_fail, [''])
test('tcfail142', normal, compile_fail, [''])
test('tcfail143', normal, compile_fail, [''])
test('tcfail144', normal, compile, [''])
@@ -266,8 +262,6 @@ test('AssocTyDef08', normal, compile_fail, [''])
test('AssocTyDef09', normal, compile_fail, [''])
test('T3592', normal, compile_fail, [''])
test('T5570', normal, compile_fail, [''])
-test('T5573a', normal, compile_fail, [''])
-test('T5573b', normal, compile_fail, [''])
test('T5691', normal, compile_fail, [''])
test('T5689', normal, compile_fail, [''])
test('T5684', normal, compile_fail, [''])
diff --git a/testsuite/tests/typecheck/should_fail/tcfail087.hs b/testsuite/tests/typecheck/should_fail/tcfail087.hs
deleted file mode 100644
index 6055a13d21..0000000000
--- a/testsuite/tests/typecheck/should_fail/tcfail087.hs
+++ /dev/null
@@ -1,13 +0,0 @@
-{-# LANGUAGE UnboxedTuples #-}
-
--- !!! Check that unboxed tuples can't be function arguments
-module ShouldFail where
-
-data Ex = Ex (# Int,Int #)
-
-f :: (# Int,Int #) -> Int
-f x = error "urk"
-
-g (# x,y #) = x
-
-
diff --git a/testsuite/tests/typecheck/should_fail/tcfail087.stderr b/testsuite/tests/typecheck/should_fail/tcfail087.stderr
deleted file mode 100644
index 3c244ddc8b..0000000000
--- a/testsuite/tests/typecheck/should_fail/tcfail087.stderr
+++ /dev/null
@@ -1,7 +0,0 @@
-
-tcfail087.hs:6:14:
- Kind mis-match
- Expected kind `ArgKind', but `(# Int, Int #)' has kind `(#)'
- In the type `(# Int, Int #)'
- In the definition of data constructor `Ex'
- In the data declaration for `Ex'
diff --git a/testsuite/tests/typecheck/should_fail/tcfail115.hs b/testsuite/tests/typecheck/should_fail/tcfail115.hs
deleted file mode 100644
index 971f625a9a..0000000000
--- a/testsuite/tests/typecheck/should_fail/tcfail115.hs
+++ /dev/null
@@ -1,13 +0,0 @@
-{-# LANGUAGE UnboxedTuples #-}
-
--- Unboxed tuples; c.f. tcfail120, tc209
-
-module ShouldFail where
-
-type T a = Int -> (# Int, Int #)
-
-g t = case t of r -> (r :: (# Int, Int #))
-
-f :: T a -> T a
-f t = \x -> case t x of r -> r
-
diff --git a/testsuite/tests/typecheck/should_fail/tcfail115.stderr b/testsuite/tests/typecheck/should_fail/tcfail115.stderr
deleted file mode 100644
index 89f5178c87..0000000000
--- a/testsuite/tests/typecheck/should_fail/tcfail115.stderr
+++ /dev/null
@@ -1,14 +0,0 @@
-
-tcfail115.hs:9:24:
- Couldn't match kind `ArgKind' against `(#)'
- Kind incompatibility when matching types:
- t0 :: ArgKind
- (# Int, Int #) :: (#)
- In the expression: (r :: (# Int, Int #))
- In a case alternative: r -> (r :: (# Int, Int #))
-
-tcfail115.hs:12:25:
- The variable `r' cannot have an unboxed tuple type: (# Int, Int #)
- In a case alternative: r -> r
- In the expression: case t x of { r -> r }
- In the expression: \ x -> case t x of { r -> r }
diff --git a/testsuite/tests/typecheck/should_fail/tcfail120.hs b/testsuite/tests/typecheck/should_fail/tcfail120.hs
deleted file mode 100644
index 04b7cd60ab..0000000000
--- a/testsuite/tests/typecheck/should_fail/tcfail120.hs
+++ /dev/null
@@ -1,14 +0,0 @@
-
-{-# LANGUAGE UnboxedTuples #-}
-
--- Could be ok, because nothing is bound to the unboxed tuple
--- but actually rejected, because a wild card is rather like
--- an unused variable. Could fix this, but it's really a corner case
-
-module ShouldFail where
-
-type T a = Int -> (# Int, Int #)
-
-f2 :: T a -> T a
-f2 t = \x -> case t x of _ -> (# 3,4 #)
-
diff --git a/testsuite/tests/typecheck/should_fail/tcfail120.stderr b/testsuite/tests/typecheck/should_fail/tcfail120.stderr
deleted file mode 100644
index 7693b0c7c5..0000000000
--- a/testsuite/tests/typecheck/should_fail/tcfail120.stderr
+++ /dev/null
@@ -1,7 +0,0 @@
-
-tcfail120.hs:13:26:
- A wild-card pattern cannot have an unboxed tuple type:
- (# Int, Int #)
- In the pattern: _
- In a case alternative: _ -> (# 3, 4 #)
- In the expression: case t x of { _ -> (# 3, 4 #) }
diff --git a/testsuite/tests/typecheck/should_fail/tcfail141.hs b/testsuite/tests/typecheck/should_fail/tcfail141.hs
deleted file mode 100644
index 12504d04f3..0000000000
--- a/testsuite/tests/typecheck/should_fail/tcfail141.hs
+++ /dev/null
@@ -1,17 +0,0 @@
-{-# LANGUAGE MagicHash, UnboxedTuples #-}
-
--- Should fail, because f :: (# Int#, ByteArray# #)
-
-module ShouldFail where
-
-import GHC.Prim (Int#, ByteArray#)
-
-main :: IO ()
-main = let f = int2Integer# 0# in putStrLn ""
-
-
-int2Integer# :: Int# -> (# Int#, ByteArray# #)
-int2Integer# = undefined
--- This function doesn't have to work!
--- We just need it for its type.
-
diff --git a/testsuite/tests/typecheck/should_fail/tcfail141.stderr b/testsuite/tests/typecheck/should_fail/tcfail141.stderr
deleted file mode 100644
index 27c7ede212..0000000000
--- a/testsuite/tests/typecheck/should_fail/tcfail141.stderr
+++ /dev/null
@@ -1,7 +0,0 @@
-
-tcfail141.hs:10:12:
- The variable `f' cannot have an unboxed tuple type:
- (# Int#, ByteArray# #)
- In the expression: let f = int2Integer# 0# in putStrLn ""
- In an equation for `main':
- main = let f = int2Integer# 0# in putStrLn ""
diff --git a/testsuite/tests/typecheck/should_fail/tcfail159.stderr b/testsuite/tests/typecheck/should_fail/tcfail159.stderr
index 0556582417..c809e39d89 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail159.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail159.stderr
@@ -1,8 +1,8 @@
tcfail159.hs:9:11:
- Couldn't match kind `*' against `(#)'
+ Couldn't match kind `*' against `#'
Kind incompatibility when matching types:
t0 :: *
- (# Int, Int #) :: (#)
+ (# Int, Int #) :: #
In the pattern: ~(# p, q #)
In a case alternative: ~(# p, q #) -> p