Skip to content
Snippets Groups Projects
Commit c60977e6 authored by Ian Lynagh's avatar Ian Lynagh
Browse files

Merge branch 'master' of darcs.haskell.org:/srv/darcs//testsuite

parents 9a767ff9 ad4020db
No related branches found
No related tags found
No related merge requests found
Showing
with 120 additions and 162 deletions
......@@ -1056,6 +1056,8 @@ tests/typecheck/should_run/T3731
tests/typecheck/should_run/T3731-short
tests/typecheck/should_run/T4809
tests/typecheck/should_run/T5759
tests/typecheck/should_run/T5573a
tests/typecheck/should_run/T5573b
tests/typecheck/should_run/church
tests/typecheck/should_run/mc17
tests/typecheck/should_run/tcrun001
......@@ -1102,6 +1104,11 @@ tests/typecheck/should_run/tcrun043
tests/typecheck/should_run/tcrun044
tests/typecheck/should_run/tcrun045
tests/typecheck/should_run/tcrun046
tests/typecheck/should_run/tcrun047
tests/typecheck/should_run/tcrun048
tests/typecheck/should_run/tcrun049
tests/typecheck/should_run/tcrun050
tests/typecheck/should_run/tcrun051
tests/typecheck/should_run/testeq2
tests/typecheck/testeq1/typecheck.testeq1
......
data Unboxed1 = Unboxed1 (# Int, Bool #)
data Unboxed2 = Unboxed2 (# Int, (# Int, Bool #) #)
o1 = Unboxed1 (# 5, True #)
o2 = Unboxed2 (# 6, (# 7, False #) #)
force_them :: Int
force_them = x + (if b then 1 else 2) + y + z + (if c then 3 else 4)
where
Unboxed1 (# x, b #) = o1
Unboxed2 (# y, (# z, c #) #) = o2
\ No newline at end of file
......@@ -35,6 +35,7 @@ test('print031', normal, ghci_script, ['print031.script'])
test('print032', normal, ghci_script, ['print032.script'])
test('print033', normal, ghci_script, ['print033.script'])
test('print034', normal, ghci_script, ['print034.script'])
test('print035', normal, ghci_script, ['print035.script'])
test('break001', normal, ghci_script, ['break001.script'])
test('break002', normal, ghci_script, ['break002.script'])
......
Stopped at break026.hs:(5,1)-(7,35)
_result :: t1 = _
_result :: t = _
Stopped at break026.hs:5:16-22
_result :: Integer = _
c :: Integer = 0
go :: Integer -> [t] -> Integer = _
xs :: [t] = _
go :: Integer -> [t1] -> Integer = _
xs :: [t1] = _
Stopped at break026.hs:(6,9)-(7,35)
_result :: t1 = _
f :: t1 -> t -> t1 = _
_result :: t = _
f :: t -> t1 -> t = _
Stopped at break026.hs:7:23-35
_result :: Integer = _
c :: Integer = 0
......@@ -15,25 +15,25 @@ f :: Integer -> Integer -> Integer = _
x :: Integer = 1
xs :: [Integer] = _
Stopped at break026.hs:(6,9)-(7,35)
_result :: t1 = _
f :: t1 -> t -> t1 = _
_result :: t = _
f :: t -> t1 -> t = _
Stopped at break026.hs:7:23-35
_result :: t1 = _
c :: t1 = _
f :: t1 -> Integer -> t1 = _
_result :: t = _
c :: t = _
f :: t -> Integer -> t = _
x :: Integer = 2
xs :: [Integer] = _
c = 1
Stopped at break026.hs:(5,1)-(7,35)
_result :: t1 = _
_result :: t = _
Stopped at break026.hs:5:16-22
_result :: Integer = _
c :: Integer = 0
go :: Integer -> [t] -> Integer = _
xs :: [t] = _
go :: Integer -> [t1] -> Integer = _
xs :: [t1] = _
Stopped at break026.hs:(6,9)-(7,35)
_result :: t1 = _
f :: t1 -> t -> t1 = _
_result :: t = _
f :: t -> t1 -> t = _
Stopped at break026.hs:7:23-35
_result :: Integer = _
c :: Integer = 0
......@@ -41,12 +41,12 @@ f :: Integer -> Integer -> Integer = _
x :: Integer = 1
xs :: [Integer] = _
Stopped at break026.hs:(6,9)-(7,35)
_result :: t1 = _
f :: t1 -> t -> t1 = _
_result :: t = _
f :: t -> t1 -> t = _
Stopped at break026.hs:7:23-35
_result :: t1 = _
c :: t1 = _
f :: t1 -> Integer -> t1 = _
_result :: t = _
c :: t = _
f :: t -> Integer -> t = _
x :: Integer = 2
xs :: [Integer] = _
Stopped at break026.hs:7:27-31
......
-- Unboxed tuples in data constructor arguments need to be
-- handled correctly by RtClosureInspect
:set -XUnboxedTuples -fobject-code
:l ../Unboxed
:p o1
:p o2
force_them
:p o1
:p o2
\ No newline at end of file
o1 = (_t1::Unboxed1)
o2 = (_t2::Unboxed2)
23
o1 = Unboxed1 ((#,#) 5 True)
o2 = Unboxed2 ((#,#) 6 ((#,#) 7 False))
T5971.hs:6:7:
The exact Name `x' is not in scope
Probable cause: you used a unique name (NameU), perhaps via newName,
in Template Haskell, but did not bind it
Probable cause: you used a unique Template Haskell name (NameU),
perhaps via newName, but did not bind it
If that's it, then -ddump-splices might be useful
In the result of the splice:
$(newName "x" >>= varE)
......
tc141.hs:11:12:
You cannot bind scoped type variable `a'
in a pattern binding signature
In the pattern: p :: a
In the pattern: (p :: a, q :: a)
In a pattern binding: (p :: a, q :: a) = x
tc141.hs:11:31:
Couldn't match expected type `a1' with actual type `a'
`a1' is a rigid type variable bound by
an expression type signature: a1 at tc141.hs:11:31
`a' is a rigid type variable bound by
the inferred type of f :: (a, a) -> (t, a) at tc141.hs:11:1
In the expression: q :: a
In the expression: (q :: a, p)
In the expression: let (p :: a, q :: a) = x in (q :: a, p)
tc141.hs:13:13:
You cannot bind scoped type variable `a'
in a pattern binding signature
In the pattern: y :: a
In a pattern binding: y :: a = a
In the expression:
let y :: a = a in
let
v :: a
v = b
in v
tc141.hs:15:18:
Couldn't match expected type `a2' with actual type `t'
`a2' is a rigid type variable bound by
the type signature for v :: a2 at tc141.hs:14:19
`t' is a rigid type variable bound by
the inferred type of g :: a -> t -> a1 at tc141.hs:13:1
In the expression: b
In an equation for `v': v = b
In the expression:
let
v :: a
v = b
in v
tc141.hs:11:12:
You cannot bind scoped type variable `a'
in a pattern binding signature
In the pattern: p :: a
In the pattern: (p :: a, q :: a)
In a pattern binding: (p :: a, q :: a) = x
tc141.hs:11:31:
Couldn't match expected type `a1' with actual type `a'
`a1' is a rigid type variable bound by
an expression type signature: a1 at tc141.hs:11:31
`a' is a rigid type variable bound by
the inferred type of f :: (a, a) -> (t, a) at tc141.hs:11:1
In the expression: q :: a
In the expression: (q :: a, p)
In the expression: let (p :: a, q :: a) = x in (q :: a, p)
tc141.hs:13:13:
You cannot bind scoped type variable `a'
in a pattern binding signature
In the pattern: y :: a
In a pattern binding: y :: a = a
In the expression:
let y :: a = a in
let
v :: a
v = b
in v
tc141.hs:15:18:
Couldn't match expected type `a2' with actual type `t'
`a2' is a rigid type variable bound by
the type signature for v :: a2 at tc141.hs:14:19
`t' is a rigid type variable bound by
the inferred type of g :: a -> t -> a1 at tc141.hs:13:1
In the expression: b
In an equation for `v': v = b
In the expression:
let
v :: a
v = b
in v
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
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# #)
......@@ -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, [''])
......
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'
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 }
{-# 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 #)
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 #) }
{-# 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.
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 ""
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
{-# LANGUAGE MagicHash, UnboxedTuples, BangPatterns #-}
module T5573a where
module Main where
import GHC.Exts
-- This is ok
{-# NOINLINE foo1 #-} -- Make it harder to get right
foo1 x = (# x,x #)
bar y = let (# x, _ #) = foo1 y in x
-- Nested unboxed tuple not ok
{-# NOINLINE foo2 #-} -- Make it harder to get right
foo2 x = (# x, (# True, False #) #)
-- Unboxed tuple argument not ok
{-# NOINLINE foo3 #-} -- Make it harder to get right
foo3 (# x,y #) = x
main = print $ foo3 (# if b then x + y else x - y, 30 #)
where (# x, _ #) = foo1 10
(# y, (# b, _ #) #) = foo2 20
30
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment