diff --git a/testsuite/driver/testglobals.py b/testsuite/driver/testglobals.py index d3b566c4937429e1c33c5ba44c9e207f262dd6c1..d7e63d1c875dc57ec700e38b7251c5595038866f 100644 --- a/testsuite/driver/testglobals.py +++ b/testsuite/driver/testglobals.py @@ -144,7 +144,6 @@ def getTestRun(): class TestOptions: def __init__(self): - # if not None then we look for namebase.stderr etc rather than # using the test name self.with_namebase = None @@ -253,6 +252,9 @@ class TestOptions: # The directory the test is in self.testdir = '.' + # Should we redirect stdout and stderr to a single file? + self.combined_output = False + # The default set of options global default_testopts default_testopts = TestOptions() diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 15b6d4eb668d5714766fc6989c6802b14287c34a..ee9cc7c077b5104ca7e7946c99d1b48cfb6ea6c9 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -141,6 +141,9 @@ def ignore_output( opts ): def no_stdin( opts ): opts.no_stdin = 1 +def combined_output( opts ): + opts.combined_output = True + # ----- def expect_fail_for( ways ): @@ -1155,11 +1158,18 @@ def simple_run( name, way, prog, args ): stdin_comes_from = '' else: stdin_comes_from = ' <' + use_stdin + + if opts.combined_output: + redirection = ' >' + run_stdout \ + + ' 2>&1' + else: + redirection = ' >' + run_stdout \ + + ' 2>' + run_stderr + cmd = prog + ' ' + args + ' ' \ + my_rts_flags + ' ' \ + stdin_comes_from \ - + ' >' + run_stdout \ - + ' 2>' + run_stderr + + redirection if getTestOpts().cmd_wrapper != None: cmd = getTestOpts().cmd_wrapper(cmd); @@ -1183,7 +1193,7 @@ def simple_run( name, way, prog, args ): check_prof = my_rts_flags.find("-p") != -1 if not opts.ignore_output: - if not check_stderr_ok(name): + if not opts.combined_output and not check_stderr_ok(name): return failBecause('bad stderr') if not check_stdout_ok(name): return failBecause('bad stdout') @@ -1445,7 +1455,7 @@ def check_stderr_ok( name ): if platform_specific: return str else: - return normalise_output(str) + return normalise_errmsg(str) return compare_outputs('stderr', \ two_normalisers(norm, getTestOpts().extra_normaliser), \ diff --git a/testsuite/tests/ghci.debugger/scripts/all.T b/testsuite/tests/ghci.debugger/scripts/all.T index c9c5fe89c119781a912ec49650099f94cca65492..d7a1403b18b79ce9d90859236dfe4498696f8c14 100644 --- a/testsuite/tests/ghci.debugger/scripts/all.T +++ b/testsuite/tests/ghci.debugger/scripts/all.T @@ -44,20 +44,20 @@ test('break006', normal, ghci_script, ['break006.script']) test('break007', extra_clean(['Break007.o', 'Break007.hi']), ghci_script, ['break007.script']) test('break008', normal, ghci_script, ['break008.script']) -test('break009', normal, ghci_script, ['break009.script']) +test('break009', combined_output, ghci_script, ['break009.script']) test('break010', normal, ghci_script, ['break010.script']) -test('break011', normal, ghci_script, ['break011.script']) +test('break011', combined_output, ghci_script, ['break011.script']) test('break012', normal, ghci_script, ['break012.script']) test('break013', normal, ghci_script, ['break013.script']) test('break014', normal, ghci_script, ['break014.script']) test('break015', expect_broken(1532), ghci_script, ['break015.script']) -test('break016', normal, ghci_script, ['break016.script']) -test('break017', normal, ghci_script, ['break017.script']) +test('break016', combined_output, ghci_script, ['break016.script']) +test('break017', combined_output, ghci_script, ['break017.script']) test('break018', normal, ghci_script, ['break018.script']) test('break019', normal, ghci_script, ['break019.script']) test('break020', normal, ghci_script, ['break020.script']) test('break021', normal, ghci_script, ['break021.script']) -test('break024', normal, ghci_script, ['break024.script']) +test('break024', combined_output, ghci_script, ['break024.script']) test('break025', normal, ghci_script, ['break025.script']) test('break026', normal, ghci_script, ['break026.script']) test('break027', normal, ghci_script, ['break027.script']) @@ -74,7 +74,7 @@ test('dynbrk009', normal, ghci_script, ['dynbrk009.script']) test('result001', expect_broken(1531), ghci_script, ['result001.script']) -test('listCommand001', normal, ghci_script, ['listCommand001.script']) +test('listCommand001', combined_output, ghci_script, ['listCommand001.script']) test('listCommand002', normal, ghci_script, ['listCommand002.script']) test('hist001', normal, ghci_script, ['hist001.script']) diff --git a/testsuite/tests/ghci/scripts/Defer02.stderr b/testsuite/tests/ghci/scripts/Defer02.stderr index 005e85cb5f1a80efa07b05229cc915ac3c56460e..227594c4c38b30c9bc37d2b0c5a83775b66170ce 100644 --- a/testsuite/tests/ghci/scripts/Defer02.stderr +++ b/testsuite/tests/ghci/scripts/Defer02.stderr @@ -1,91 +1,150 @@ - -../../typecheck/should_run/Defer01.hs:11:40: Warning: - Couldn't match type `Char' with `[Char]' - Expected type: String - Actual type: Char - In the first argument of `putStr', namely ',' - In the second argument of `(>>)', namely putStr ',' - In the expression: putStr "Hello World" >> putStr ',' - -../../typecheck/should_run/Defer01.hs:14:5: Warning: - Couldn't match expected type `Int' with actual type `Char' - In the expression: 'p' - In an equation for `a': a = 'p' - -../../typecheck/should_run/Defer01.hs:18:9: Warning: - No instance for (Eq B) arising from a use of `==' - Possible fix: add an instance declaration for (Eq B) - In the expression: x == x - In an equation for `b': b x = x == x - -../../typecheck/should_run/Defer01.hs:28:5: Warning: - No instance for (Num (a -> a)) arising from the literal `1' - Possible fix: add an instance declaration for (Num (a -> a)) - In the expression: 1 - In an equation for `d': d = 1 - -../../typecheck/should_run/Defer01.hs:31:5: Warning: - Couldn't match expected type `Char -> t' with actual type `Char' - The function `e' is applied to one argument, - but its type `Char' has none - In the expression: e 'q' - In an equation for `f': f = e 'q' - -../../typecheck/should_run/Defer01.hs:34:8: Warning: - Couldn't match expected type `a' with actual type `Char' - `a' is a rigid type variable bound by - the type signature for h :: a -> (Char, Char) - at ../../typecheck/should_run/Defer01.hs:33:6 - In the expression: x - In the expression: (x, 'c') - In an equation for `h': h x = (x, 'c') - -../../typecheck/should_run/Defer01.hs:39:17: Warning: - Couldn't match expected type `Bool' with actual type `T a' - In the return type of a call of `K' - In the first argument of `not', namely `(K a)' - In the expression: (not (K a)) - -../../typecheck/should_run/Defer01.hs:43:5: Warning: - No instance for (MyClass a1) arising from a use of `myOp' - In the expression: myOp 23 - In an equation for `j': j = myOp 23 - -../../typecheck/should_run/Defer01.hs:43:10: Warning: - No instance for (Num a1) arising from the literal `23' - The type variable `a1' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - Note: there are several potential instances: - instance Num Double -- Defined in `GHC.Float' - instance Num Float -- Defined in `GHC.Float' - instance Num Int -- Defined in `GHC.Num' - ...plus one other - In the first argument of `myOp', namely `23' - In the expression: myOp 23 - In an equation for `j': j = myOp 23 - -../../typecheck/should_run/Defer01.hs:46:7: Warning: - Couldn't match expected type `Bool' with actual type `Int' - In the expression: x - In an equation for `k': k x = x - -../../typecheck/should_run/Defer01.hs:49:5: Warning: - Couldn't match expected type `IO a0' - with actual type `Char -> IO ()' - In the first argument of `(>>)', namely `putChar' - In the expression: putChar >> putChar 'p' - In an equation for `l': l = putChar >> putChar 'p' - -:8:11: - Couldn't match type `Bool' with `Int' - Expected type: C Int - Actual type: C Bool - In the return type of a call of `C2' - In the first argument of `c', namely `(C2 True)' - In the first argument of `print', namely `(c (C2 True))' - -:14:8: - Couldn't match expected type `Bool' with actual type `Int' - In the first argument of `print', namely `(k 2)' - In the expression: print (k 2) - In an equation for `it': it = print (k 2) + +../../typecheck/should_run/Defer01.hs:11:40: Warning: + Couldn't match type `Char' with `[Char]' + Expected type: String + Actual type: Char + In the first argument of `putStr', namely ',' + In the second argument of `(>>)', namely putStr ',' + In the expression: putStr "Hello World" >> putStr ',' + +../../typecheck/should_run/Defer01.hs:14:5: Warning: + Couldn't match expected type `Int' with actual type `Char' + In the expression: 'p' + In an equation for `a': a = 'p' + +../../typecheck/should_run/Defer01.hs:18:9: Warning: + No instance for (Eq B) arising from a use of `==' + Possible fix: add an instance declaration for (Eq B) + In the expression: x == x + In an equation for `b': b x = x == x + +../../typecheck/should_run/Defer01.hs:28:5: Warning: + No instance for (Num (a -> a)) arising from the literal `1' + Possible fix: add an instance declaration for (Num (a -> a)) + In the expression: 1 + In an equation for `d': d = 1 + +../../typecheck/should_run/Defer01.hs:31:5: Warning: + Couldn't match expected type `Char -> t' with actual type `Char' + The function `e' is applied to one argument, + but its type `Char' has none + In the expression: e 'q' + In an equation for `f': f = e 'q' + +../../typecheck/should_run/Defer01.hs:34:8: Warning: + Couldn't match expected type `a' with actual type `Char' + `a' is a rigid type variable bound by + the type signature for h :: a -> (Char, Char) + at ../../typecheck/should_run/Defer01.hs:33:6 + In the expression: x + In the expression: (x, 'c') + In an equation for `h': h x = (x, 'c') + +../../typecheck/should_run/Defer01.hs:39:17: Warning: + Couldn't match expected type `Bool' with actual type `T a' + In the return type of a call of `K' + In the first argument of `not', namely `(K a)' + In the expression: (not (K a)) + +../../typecheck/should_run/Defer01.hs:43:5: Warning: + No instance for (MyClass a1) arising from a use of `myOp' + In the expression: myOp 23 + In an equation for `j': j = myOp 23 + +../../typecheck/should_run/Defer01.hs:43:10: Warning: + No instance for (Num a1) arising from the literal `23' + The type variable `a1' is ambiguous + Possible fix: add a type signature that fixes these type variable(s) + Note: there are several potential instances: + instance Num Double -- Defined in `GHC.Float' + instance Num Float -- Defined in `GHC.Float' + instance Num Int -- Defined in `GHC.Num' + ...plus one other + In the first argument of `myOp', namely `23' + In the expression: myOp 23 + In an equation for `j': j = myOp 23 + +../../typecheck/should_run/Defer01.hs:46:7: Warning: + Couldn't match expected type `Bool' with actual type `Int' + In the expression: x + In an equation for `k': k x = x + +../../typecheck/should_run/Defer01.hs:49:5: Warning: + Couldn't match expected type `IO a0' + with actual type `Char -> IO ()' + In the first argument of `(>>)', namely `putChar' + In the expression: putChar >> putChar 'p' + In an equation for `l': l = putChar >> putChar 'p' +*** Exception: ../../typecheck/should_run/Defer01.hs:11:40: + Couldn't match type `Char' with `[Char]' + Expected type: String + Actual type: Char + In the first argument of `putStr', namely ',' + In the second argument of `(>>)', namely putStr ',' + In the expression: putStr "Hello World" >> putStr ',' +(deferred type error) +*** Exception: ../../typecheck/should_run/Defer01.hs:14:5: + Couldn't match expected type `Int' with actual type `Char' + In the expression: 'p' + In an equation for `a': a = 'p' +(deferred type error) +*** Exception: ../../typecheck/should_run/Defer01.hs:18:9: + No instance for (Eq B) arising from a use of `==' + Possible fix: add an instance declaration for (Eq B) + In the expression: x == x + In an equation for `b': b x = x == x +(deferred type error) + +:8:11: + Couldn't match type `Bool' with `Int' + Expected type: C Int + Actual type: C Bool + In the return type of a call of `C2' + In the first argument of `c', namely `(C2 True)' + In the first argument of `print', namely `(c (C2 True))' +*** Exception: ../../typecheck/should_run/Defer01.hs:28:5: + No instance for (Num (a -> a)) arising from the literal `1' + Possible fix: add an instance declaration for (Num (a -> a)) + In the expression: 1 + In an equation for `d': d = 1 +(deferred type error) +*** Exception: ../../typecheck/should_run/Defer01.hs:31:5: + Couldn't match expected type `Char -> t' with actual type `Char' + The function `e' is applied to one argument, + but its type `Char' has none + In the expression: e 'q' + In an equation for `f': f = e 'q' +(deferred type error) +*** Exception: ../../typecheck/should_run/Defer01.hs:34:8: + Couldn't match expected type `a' with actual type `Char' + `a' is a rigid type variable bound by + the type signature for h :: a -> (Char, Char) + at ../../typecheck/should_run/Defer01.hs:33:6 + In the expression: x + In the expression: (x, 'c') + In an equation for `h': h x = (x, 'c') +(deferred type error) +*** Exception: ../../typecheck/should_run/Defer01.hs:39:17: + Couldn't match expected type `Bool' with actual type `T a' + In the return type of a call of `K' + In the first argument of `not', namely `(K a)' + In the expression: (not (K a)) +(deferred type error) +*** Exception: ../../typecheck/should_run/Defer01.hs:43:5: + No instance for (MyClass a1) arising from a use of `myOp' + In the expression: myOp 23 + In an equation for `j': j = myOp 23 +(deferred type error) + +:14:8: + Couldn't match expected type `Bool' with actual type `Int' + In the first argument of `print', namely `(k 2)' + In the expression: print (k 2) + In an equation for `it': it = print (k 2) +*** Exception: ../../typecheck/should_run/Defer01.hs:49:5: + Couldn't match expected type `IO a0' + with actual type `Char -> IO ()' + In the first argument of `(>>)', namely `putChar' + In the expression: putChar >> putChar 'p' + In an equation for `l': l = putChar >> putChar 'p' +(deferred type error) diff --git a/testsuite/tests/ghci/scripts/Defer02.stdout b/testsuite/tests/ghci/scripts/Defer02.stdout index 32e51d6d6541e1585931f3390a424a32234f6289..4fd8c5d880746c5a130a50074b1d629fd9d8fcf6 100644 --- a/testsuite/tests/ghci/scripts/Defer02.stdout +++ b/testsuite/tests/ghci/scripts/Defer02.stdout @@ -1,59 +1 @@ -Hello World*** Exception: ../../typecheck/should_run/Defer01.hs:11:40: - Couldn't match type `Char' with `[Char]' - Expected type: String - Actual type: Char - In the first argument of `putStr', namely ',' - In the second argument of `(>>)', namely putStr ',' - In the expression: putStr "Hello World" >> putStr ',' -(deferred type error) -*** Exception: ../../typecheck/should_run/Defer01.hs:14:5: - Couldn't match expected type `Int' with actual type `Char' - In the expression: 'p' - In an equation for `a': a = 'p' -(deferred type error) -*** Exception: ../../typecheck/should_run/Defer01.hs:18:9: - No instance for (Eq B) arising from a use of `==' - Possible fix: add an instance declaration for (Eq B) - In the expression: x == x - In an equation for `b': b x = x == x -(deferred type error) -*** Exception: ../../typecheck/should_run/Defer01.hs:28:5: - No instance for (Num (a -> a)) arising from the literal `1' - Possible fix: add an instance declaration for (Num (a -> a)) - In the expression: 1 - In an equation for `d': d = 1 -(deferred type error) -*** Exception: ../../typecheck/should_run/Defer01.hs:31:5: - Couldn't match expected type `Char -> t' with actual type `Char' - The function `e' is applied to one argument, - but its type `Char' has none - In the expression: e 'q' - In an equation for `f': f = e 'q' -(deferred type error) -(*** Exception: ../../typecheck/should_run/Defer01.hs:34:8: - Couldn't match expected type `a' with actual type `Char' - `a' is a rigid type variable bound by - the type signature for h :: a -> (Char, Char) - at ../../typecheck/should_run/Defer01.hs:33:6 - In the expression: x - In the expression: (x, 'c') - In an equation for `h': h x = (x, 'c') -(deferred type error) -*** Exception: ../../typecheck/should_run/Defer01.hs:39:17: - Couldn't match expected type `Bool' with actual type `T a' - In the return type of a call of `K' - In the first argument of `not', namely `(K a)' - In the expression: (not (K a)) -(deferred type error) -"*** Exception: ../../typecheck/should_run/Defer01.hs:43:5: - No instance for (MyClass a1) arising from a use of `myOp' - In the expression: myOp 23 - In an equation for `j': j = myOp 23 -(deferred type error) -*** Exception: ../../typecheck/should_run/Defer01.hs:49:5: - Couldn't match expected type `IO a0' - with actual type `Char -> IO ()' - In the first argument of `(>>)', namely `putChar' - In the expression: putChar >> putChar 'p' - In an equation for `l': l = putChar >> putChar 'p' -(deferred type error) +Hello World(" \ No newline at end of file diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 2a49c9c11289c2dd2fe48940767ebad61dd8c1ec..bdec94ac97648d38d0fa6e29c2ca7f3b1e964400 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -2,15 +2,15 @@ setTestOpts(if_compiler_profiled(skip)) -test('ghci001', normal, ghci_script, ['ghci001.script']) -test('ghci002', normal, ghci_script, ['ghci002.script']) -test('ghci003', normal, ghci_script, ['ghci003.script']) -test('ghci004', normal, ghci_script, ['ghci004.script']) -test('ghci005', normal, ghci_script, ['ghci005.script']) -test('ghci006', normal, ghci_script, ['ghci006.script']) -test('ghci007', normal, ghci_script, ['ghci007.script']) -test('ghci008', normal, ghci_script, ['ghci008.script']) -test('ghci009', normal, ghci_script, ['ghci009.script']) +test('ghci001', combined_output, ghci_script, ['ghci001.script']) +test('ghci002', combined_output, ghci_script, ['ghci002.script']) +test('ghci003', combined_output, ghci_script, ['ghci003.script']) +test('ghci004', combined_output, ghci_script, ['ghci004.script']) +test('ghci005', combined_output, ghci_script, ['ghci005.script']) +test('ghci006', combined_output, ghci_script, ['ghci006.script']) +test('ghci007', combined_output, ghci_script, ['ghci007.script']) +test('ghci008', combined_output, ghci_script, ['ghci008.script']) +test('ghci009', combined_output, ghci_script, ['ghci009.script']) # Skip this test: deadlock can't be detected now, because we wait for # signals to arrive if there are signal handlers installed, and GHCi @@ -72,7 +72,7 @@ test('ghci051', normal, ghci_script, ['ghci051.script']) test('ghci052', normal, ghci_script, ['ghci052.script']) test('ghci053', normal, ghci_script, ['ghci053.script']) test('ghci054', normal, ghci_script, ['ghci054.script']) -test('ghci055', normal, ghci_script, ['ghci055.script']) +test('ghci055', combined_output, ghci_script, ['ghci055.script']) test('ghci056', [ @@ -107,7 +107,7 @@ test('T5045', normal, ghci_script, ['T5045.script']) test('T5130', normal, ghci_script, ['T5130.script']) test('T5417', normal, ghci_script, ['T5417.script']) test('T5545', normal, ghci_script, ['T5545.script']) -test('T5557', normal, ghci_script, ['T5557.script']) +test('T5557', combined_output, ghci_script, ['T5557.script']) test('T5566', normal, ghci_script, ['T5566.script']) test('GhciKinds', normal, ghci_script, ['GhciKinds.script']) test('T5564', normal, ghci_script, ['T5564.script']) diff --git a/testsuite/tests/ghci/scripts/ghci044.stderr b/testsuite/tests/ghci/scripts/ghci044.stderr index dfcbd10860907e0aeaa4b3b58f07a89584b9f258..a5e6a543ee62973845112fda48d70dd44ae8462e 100644 --- a/testsuite/tests/ghci/scripts/ghci044.stderr +++ b/testsuite/tests/ghci/scripts/ghci044.stderr @@ -7,7 +7,7 @@ Use -XFlexibleInstances if you want to disable this.) In the instance declaration for `C [Int]' -:8:10: +:7:10: Overlapping instance declarations: - instance C a => C [a] -- Defined at :8:10 instance C [Int] -- Defined at :7:10 + instance C a => C [a] -- Defined at :8:10 diff --git a/testsuite/tests/ghci/should_run/all.T b/testsuite/tests/ghci/should_run/all.T index f6e2c146be0ebd5746ab769cd51f276c2e3b546b..89347ebc85eadd862fd9aad6e159dfd5f222cde9 100644 --- a/testsuite/tests/ghci/should_run/all.T +++ b/testsuite/tests/ghci/should_run/all.T @@ -13,7 +13,8 @@ test('2881', just_ghci, compile_and_run, ['']) test('3171', [if_platform('i386-unknown-mingw32',skip), - req_interp], + req_interp, + combined_output], run_command, ['$MAKE -s --no-print-directory 3171']) diff --git a/testsuite/tests/haddock/haddock_examples/haddock.Test.stderr b/testsuite/tests/haddock/haddock_examples/haddock.Test.stderr index 3e944ee3134651a41241b8100ffcc9b270a03fc7..74956de414d070cd37b411416da2761148b0ae97 100644 --- a/testsuite/tests/haddock/haddock_examples/haddock.Test.stderr +++ b/testsuite/tests/haddock/haddock_examples/haddock.Test.stderr @@ -1,166 +1,166 @@ -[1 of 3] Compiling Visible ( Visible.hs, Visible.o ) - -==================== Parser ==================== -module Visible where -visible :: Int -> Int -visible a = a - - -[2 of 3] Compiling Hidden ( Hidden.hs, Hidden.o ) - -==================== Parser ==================== -module Hidden where -hidden :: Int -> Int -hidden a = a - - -[3 of 3] Compiling Test ( Test.hs, Test.o ) - -==================== Parser ==================== - -module Test ( - , , T(..), T2, T3(..), T4(..), T5(..), - T6(..), N1(..), N2(..), N3(..), N4, N5(..), N6(..), N7(..), - , R(..), R1(..), , p, q, u, - , C(a, b), D(..), E, F(..), , a, - , f, g, , , - , , , - , , , - , , , - , , , - , module Hidden, , module Visible, - , , Ex(..), , k, l, m, o, - , , , f' - ) where -import Hidden -import Visible - -data T a b - = A Int Maybe Float | - B (T a b, T Int Float) - -data T2 a b = T2 a b - -data T3 a b = A1 a | B1 b -data T4 a b = A2 a | B2 b -data T5 a b = A3 a | B3 b - -data T6 - = A4 | - B4 | - C4 - -newtype N1 a = N1 a - -newtype N2 a b = N2 {n :: a b} - -newtype N3 a b = N3 {n3 :: a b } - -newtype N4 a b = N4 a -newtype N5 a b = N5 {n5 :: a b } -newtype N6 a b = N6 {n6 :: a b} - -newtype N7 a b = N7 {n7 :: a b} -class D a => C a where - a :: IO a - b :: [a] - c :: a - -class D a where - d :: T a b - e :: (a, a) - -instance D Int where - d = undefined - e = undefined -instance Test.D Float where - d = undefined - e = undefined -class E a where - ee :: a - -class F a where - ff :: a - -data R - = - C1 {p :: Int , - q :: forall a. a -> a , - r :: Int , - s :: Int } | - - C2 {t :: T1 - -> (T2 Int Int) -> (T3 Bool Bool) -> (T4 Float Float) -> T5 () (), - u :: Int, - v :: Int} - -data R1 - = - C3 {s1 :: Int , - s2 :: Int , - s3 :: Int } - - - - -f :: C a => a -> Int - -foreign import ccall safe "static header.h g" g :: Int -> IO CInt - -h :: Int -h = 42 - - - - - - - - - - - - - -data Ex a - = forall b. C b => Ex1 b | - forall b. Ex2 b | - forall b. C a => Ex3 b | - Ex4 forall a. a -> a - -k :: - T () () - -> (T2 Int Int) - -> (T3 Bool Bool -> T4 Float Float) - -> T5 () () -> IO () -l :: (Int, Int, Float) -> Int - -m :: R -> N1 () -> IO Int - -newn :: R -> N1 () -> IO Int -newn = undefined - -foreign import ccall unsafe "static header.h o" o - :: Float -> IO Float - -newp :: Int -newp = undefined - -f' :: Int -data T1 -f = undefined -f' = undefined -type CInt = Int -k = undefined -l = undefined -m = undefined - - - -Test.hs:32:9: Warning: `p' is exported by `p' and `R(..)' - -Test.hs:32:12: Warning: `q' is exported by `q' and `R(..)' - -Test.hs:32:15: Warning: `u' is exported by `u' and `R(..)' - -Test.hs:38:9: Warning: `a' is exported by `a' and `C(a, b)' +[1 of 3] Compiling Visible ( Visible.hs, Visible.o ) + +==================== Parser ==================== +module Visible where +visible :: Int -> Int +visible a = a + + +[2 of 3] Compiling Hidden ( Hidden.hs, Hidden.o ) + +==================== Parser ==================== +module Hidden where +hidden :: Int -> Int +hidden a = a + + +[3 of 3] Compiling Test ( Test.hs, Test.o ) + +==================== Parser ==================== + +module Test ( + , , T(..), T2, T3(..), T4(..), T5(..), + T6(..), N1(..), N2(..), N3(..), N4, N5(..), N6(..), N7(..), + , R(..), R1(..), , p, q, u, + , C(a, b), D(..), E, F(..), , a, + , f, g, , , + , , , + , , , + , , , + , , , + , module Hidden, , module Visible, + , , Ex(..), , k, l, m, o, + , , , f' + ) where +import Hidden +import Visible + +data T a b + = A Int (Maybe Float) | + B (T a b, T Int Float) + +data T2 a b = T2 a b + +data T3 a b = A1 a | B1 b +data T4 a b = A2 a | B2 b +data T5 a b = A3 a | B3 b + +data T6 + = A4 | + B4 | + C4 + +newtype N1 a = N1 a + +newtype N2 a b = N2 {n :: a b} + +newtype N3 a b = N3 {n3 :: a b } + +newtype N4 a b = N4 a +newtype N5 a b = N5 {n5 :: a b } +newtype N6 a b = N6 {n6 :: a b} + +newtype N7 a b = N7 {n7 :: a b} +class D a => C a where + a :: IO a + b :: [a] + c :: a + +class D a where + d :: T a b + e :: (a, a) + +instance D Int where + d = undefined + e = undefined +instance Test.D Float where + d = undefined + e = undefined +class E a where + ee :: a + +class F a where + ff :: a + +data R + = + C1 {p :: Int , + q :: forall a. a -> a , + r :: Int , + s :: Int } | + + C2 {t :: T1 + -> (T2 Int Int) -> (T3 Bool Bool) -> (T4 Float Float) -> T5 () (), + u :: Int, + v :: Int} + +data R1 + = + C3 {s1 :: Int , + s2 :: Int , + s3 :: Int } + + + + +f :: C a => a -> Int + +foreign import ccall safe "static header.h g" g :: Int -> IO CInt + +h :: Int +h = 42 + + + + + + + + + + + + + +data Ex a + = forall b. C b => Ex1 b | + forall b. Ex2 b | + forall b. C a => Ex3 b | + Ex4 (forall a. a -> a) + +k :: + T () () + -> (T2 Int Int) + -> (T3 Bool Bool -> T4 Float Float) + -> T5 () () -> IO () +l :: (Int, Int, Float) -> Int + +m :: R -> N1 () -> IO Int + +newn :: R -> N1 () -> IO Int +newn = undefined + +foreign import ccall unsafe "static header.h o" o + :: Float -> IO Float + +newp :: Int +newp = undefined + +f' :: Int +data T1 +f = undefined +f' = undefined +type CInt = Int +k = undefined +l = undefined +m = undefined + + + +Test.hs:32:9: Warning: `p' is exported by `p' and `R(..)' + +Test.hs:32:12: Warning: `q' is exported by `q' and `R(..)' + +Test.hs:32:15: Warning: `u' is exported by `u' and `R(..)' + +Test.hs:38:9: Warning: `a' is exported by `a' and `C(a, b)' diff --git a/testsuite/tests/indexed-types/should_fail/SimpleFail2b.stderr b/testsuite/tests/indexed-types/should_fail/SimpleFail2b.stderr index ebc7d27f8fed03725d940695e3959d6305fefc3d..119fec01454345d699318dc7fe5bbc15eacad9e0 100644 --- a/testsuite/tests/indexed-types/should_fail/SimpleFail2b.stderr +++ b/testsuite/tests/indexed-types/should_fail/SimpleFail2b.stderr @@ -1,5 +1,5 @@ -SimpleFail2b.hs:10:11: +SimpleFail2b.hs:9:11: Conflicting family instance declarations: - data Sd Int -- Defined at SimpleFail2b.hs:10:11 data Sd Int -- Defined at SimpleFail2b.hs:9:11 + data Sd Int -- Defined at SimpleFail2b.hs:10:11 diff --git a/testsuite/tests/module/mod51.stderr b/testsuite/tests/module/mod51.stderr index e33e43fddd9ec3cf1cd8154368e6ef27b28ba223..2d7a02d40d5d477365aebd0f92b28375a0b065c7 100644 --- a/testsuite/tests/module/mod51.stderr +++ b/testsuite/tests/module/mod51.stderr @@ -1,5 +1,5 @@ -mod51.hs:3:25: +mod51.hs:3:22: Duplicate instance declarations: - instance Eq T -- Defined at mod51.hs:3:25 instance Eq T -- Defined at mod51.hs:3:22 + instance Eq T -- Defined at mod51.hs:3:25 diff --git a/testsuite/tests/numeric/should_run/all.T b/testsuite/tests/numeric/should_run/all.T index 2cfcae77568bf711ca7cb40c3f15f7e3f90524f4..5849ca4e0ba9ef6e58d746d9a2cdef144b33609e 100644 --- a/testsuite/tests/numeric/should_run/all.T +++ b/testsuite/tests/numeric/should_run/all.T @@ -56,4 +56,5 @@ test('4383', normal, compile_and_run, ['']) test('add2', normal, compile_and_run, ['']) test('mul2', normal, compile_and_run, ['']) +test('quotRem2', normal, compile_and_run, ['']) diff --git a/testsuite/tests/numeric/should_run/quotRem2.hs b/testsuite/tests/numeric/should_run/quotRem2.hs new file mode 100644 index 0000000000000000000000000000000000000000..bb7fb6cd12c9d015ebffbd959163429355258b11 --- /dev/null +++ b/testsuite/tests/numeric/should_run/quotRem2.hs @@ -0,0 +1,34 @@ + +{-# LANGUAGE MagicHash, UnboxedTuples #-} + +import GHC.Prim +import GHC.Word +import Control.Monad +import Data.Bits + +main :: IO () +main = do f 5 6 23 + f 0x80000000 0 0x80000001 + f 0xFC1D8A3BFB29FC6A 49 0xFD94E3B7FE36FB18 + +f :: Word -> Word -> Word -> IO () +f wxHigh@(W# xHigh) wxLow@(W# xLow) wy@(W# y) + = do when debugging $ putStrLn "-----" + when debugging $ putStrLn ("Doing " ++ show (wxHigh, wxLow) + ++ " `quotRem` " ++ show wy) + let ix = (toInteger wxHigh `shiftL` bitSize wxHigh) + .|. toInteger wxLow + wanted = ix `quotRem` toInteger wy + when debugging $ putStrLn ("Wanted: " ++ show wanted) + case quotRemWord2# xHigh xLow y of + (# q, r #) -> + do let wq = W# q + wr = W# r + got = (toInteger wq, toInteger wr) + when debugging $ putStrLn ("Got: " ++ show got) + if wanted == got then putStrLn "Worked" + else putStrLn "Failed" + +debugging :: Bool +debugging = False + diff --git a/testsuite/tests/numeric/should_run/quotRem2.stdout b/testsuite/tests/numeric/should_run/quotRem2.stdout new file mode 100644 index 0000000000000000000000000000000000000000..e09c6b64c1487fd4c69324542eecded2d71c8d63 --- /dev/null +++ b/testsuite/tests/numeric/should_run/quotRem2.stdout @@ -0,0 +1,3 @@ +Worked +Worked +Worked diff --git a/testsuite/tests/safeHaskell/ghci/p12.stderr b/testsuite/tests/safeHaskell/ghci/p12.stderr index 4df01fd599370cd6160fd5a7fcfbc0d05db2b27a..4f3e0106df057c3fdac2c09d76fbb8933bf3c3fc 100644 --- a/testsuite/tests/safeHaskell/ghci/p12.stderr +++ b/testsuite/tests/safeHaskell/ghci/p12.stderr @@ -1,3 +1,5 @@ +don't know how to reverse -XSafe +Some flags have not been recognized: -fno-package-trust : Data.ByteString: Can't be safely imported! diff --git a/testsuite/tests/safeHaskell/ghci/p12.stdout b/testsuite/tests/safeHaskell/ghci/p12.stdout deleted file mode 100644 index 5d16ff7a9f60a582d1af32b5f992be6929c0a633..0000000000000000000000000000000000000000 --- a/testsuite/tests/safeHaskell/ghci/p12.stdout +++ /dev/null @@ -1,2 +0,0 @@ -don't know how to reverse -XSafe -Some flags have not been recognized: -fno-package-trust diff --git a/testsuite/tests/safeHaskell/ghci/p13.stdout b/testsuite/tests/safeHaskell/ghci/p13.stdout deleted file mode 100644 index e69de29bb2d1d6434b8b29ae775ad8c2e48c5391..0000000000000000000000000000000000000000 diff --git a/testsuite/tests/safeHaskell/ghci/p2.stderr b/testsuite/tests/safeHaskell/ghci/p2.stderr index 342bb05686a6fdd0eecc5bec09bbf6c1511788ba..0b446d53f6fb31d48d0c1d4a919e5562b6e45164 100644 --- a/testsuite/tests/safeHaskell/ghci/p2.stderr +++ b/testsuite/tests/safeHaskell/ghci/p2.stderr @@ -1,2 +1,4 @@ package flags have changed, resetting and loading new packages... package flags have changed, resetting and loading new packages... +cannot satisfy -package -all + (use -v for more information) diff --git a/testsuite/tests/safeHaskell/ghci/p2.stdout b/testsuite/tests/safeHaskell/ghci/p2.stdout deleted file mode 100644 index c6efa9ed48a31156878c6525f042118e19c7599d..0000000000000000000000000000000000000000 --- a/testsuite/tests/safeHaskell/ghci/p2.stdout +++ /dev/null @@ -1,2 +0,0 @@ -cannot satisfy -package -all - (use -v for more information) diff --git a/testsuite/tests/safeHaskell/ghci/p3.stderr b/testsuite/tests/safeHaskell/ghci/p3.stderr index 8e4ee4018ce67cf3b406b785dacce29d68c82646..72fbb805d0d7c3e8cdfa0348caf917b9a6d71827 100644 --- a/testsuite/tests/safeHaskell/ghci/p3.stderr +++ b/testsuite/tests/safeHaskell/ghci/p3.stderr @@ -2,6 +2,7 @@ : System.IO.Unsafe: Can't be safely imported! The module itself isn't safe. +can't import System.IO.Unsafe as it isn't trusted. : Data.ByteString: Can't be safely imported! diff --git a/testsuite/tests/safeHaskell/ghci/p3.stdout b/testsuite/tests/safeHaskell/ghci/p3.stdout deleted file mode 100644 index 268f05e8d9ad2aa00ab3ec90853b65217533ea73..0000000000000000000000000000000000000000 --- a/testsuite/tests/safeHaskell/ghci/p3.stdout +++ /dev/null @@ -1 +0,0 @@ -can't import System.IO.Unsafe as it isn't trusted. diff --git a/testsuite/tests/safeHaskell/ghci/p5.stdout b/testsuite/tests/safeHaskell/ghci/p5.stderr similarity index 100% rename from testsuite/tests/safeHaskell/ghci/p5.stdout rename to testsuite/tests/safeHaskell/ghci/p5.stderr diff --git a/testsuite/tests/safeHaskell/ghci/p7.stdout b/testsuite/tests/safeHaskell/ghci/p7.stderr similarity index 100% rename from testsuite/tests/safeHaskell/ghci/p7.stdout rename to testsuite/tests/safeHaskell/ghci/p7.stderr diff --git a/testsuite/tests/safeHaskell/ghci/p8.stdout b/testsuite/tests/safeHaskell/ghci/p8.stderr similarity index 100% rename from testsuite/tests/safeHaskell/ghci/p8.stdout rename to testsuite/tests/safeHaskell/ghci/p8.stderr diff --git a/testsuite/tests/th/T1835.stdout b/testsuite/tests/th/T1835.stdout index ba8e65f4189feeb1fa6832586b279dd1c8776bfe..c82b6723f990fcd903d809152856ccf1714c9f48 100644 --- a/testsuite/tests/th/T1835.stdout +++ b/testsuite/tests/th/T1835.stdout @@ -1,8 +1,8 @@ class GHC.Classes.Eq a_0 => Main.MyClass a_0 -instance Main.MyClass Main.Foo +instance GHC.Classes.Ord a_1 => Main.MyClass (Main.Quux2 a_1) +instance GHC.Classes.Eq a_2 => Main.MyClass (Main.Quux a_2) instance Main.MyClass Main.Baz -instance GHC.Classes.Eq a_1 => Main.MyClass (Main.Quux a_1) -instance GHC.Classes.Ord a_2 => Main.MyClass (Main.Quux2 a_2) +instance Main.MyClass Main.Foo True True True diff --git a/testsuite/tests/typecheck/should_compile/T2494.stderr b/testsuite/tests/typecheck/should_compile/T2494.stderr index 35c9e95d1d73551246ac877a5aeae4d765f1c33e..2e943ac0a5e8e9a791b543d8e60584a746f5a6f8 100644 --- a/testsuite/tests/typecheck/should_compile/T2494.stderr +++ b/testsuite/tests/typecheck/should_compile/T2494.stderr @@ -1,10 +1,10 @@ T2494.hs:15:14: - Couldn't match type `a' with `b' - `a' is a rigid type variable bound by - the RULE "foo/foo" at T2494.hs:13:16 + Couldn't match type `b' with `a' `b' is a rigid type variable bound by the RULE "foo/foo" at T2494.hs:14:16 + `a' is a rigid type variable bound by + the RULE "foo/foo" at T2494.hs:13:16 Expected type: Maybe (m a) -> Maybe (m a) Actual type: Maybe (m b) -> Maybe (m b) In the first argument of `foo', namely `g' diff --git a/testsuite/tests/typecheck/should_fail/T5691.hs b/testsuite/tests/typecheck/should_fail/T5691.hs new file mode 100644 index 0000000000000000000000000000000000000000..c63ba7b8d2e8b2d6052b0135c77d633bc075a5dc --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T5691.hs @@ -0,0 +1,29 @@ +{-# LANGUAGE ScopedTypeVariables #-} + +module GHCBug where + +import Control.Applicative as Ap +import Control.Monad (MonadPlus, mplus, mzero) +import Control.Monad.Identity (Identity, runIdentity) + +newtype PrintRuleInterp v = MkPRI { printRule_ :: Int -> String } +class Test p where + test :: p a -> p a + +instance Test PrintRuleInterp where + test (f :: p a) = + MkPRI $ printRule_ f + + +newtype RecDecParser a = MkRD { + parseRD :: String -> [(String, a)] + } + +pure_ v = MkRD $ \s -> pure (s , v) + +instance MonadPlus RecDecParser where + mzero = MkRD $ const Ap.empty + mplus a b = MkRD $ const Ap.empty + + + diff --git a/testsuite/tests/typecheck/should_fail/T5691.stderr b/testsuite/tests/typecheck/should_fail/T5691.stderr new file mode 100644 index 0000000000000000000000000000000000000000..0102aef55ad8905a4845c0affdbc5ae6832f262c --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T5691.stderr @@ -0,0 +1,14 @@ + +T5691.hs:14:9: + Couldn't match type `p' with `PrintRuleInterp' + Expected type: p a + Actual type: PrintRuleInterp a + In the pattern: f :: p a + In an equation for `test': test (f :: p a) = MkPRI $ printRule_ f + In the instance declaration for `Test PrintRuleInterp' + +T5691.hs:24:10: + No instance for (Monad RecDecParser) + arising from the superclasses of an instance declaration + Possible fix: add an instance declaration for (Monad RecDecParser) + In the instance declaration for `MonadPlus RecDecParser' diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index fad44dab05970e9052e518e9fb9c10de9acca963..901a3b0739c4810366ce25bbfe30e04819db62c7 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -268,6 +268,7 @@ 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, ['']) test('T5858', normal, compile_fail, ['']) diff --git a/testsuite/tests/typecheck/should_fail/tcfail043.stderr b/testsuite/tests/typecheck/should_fail/tcfail043.stderr index 3e52e69c564de662a52a0f8a1dbef62a12ab330b..a1904d2b4c0a8f2cc8ff9f437f4deba89b372be2 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail043.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail043.stderr @@ -29,8 +29,8 @@ tcfail043.hs:40:25: Probable fix: give these definition(s) an explicit type signature or use -XNoMonomorphismRestriction Note: there are several potential instances: - instance Eq_ a => Eq_ [a] -- Defined at tcfail043.hs:23:10 instance Eq_ Int -- Defined at tcfail043.hs:20:10 + instance Eq_ a => Eq_ [a] -- Defined at tcfail043.hs:23:10 In the expression: eq a (hd bs) In the expression: if eq a (hd bs) then True else search a (tl bs) In the expression: