[Git][ghc/ghc][wip/spj-apporv-Oct24] accept test cases with changed error messages

Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC Commits: 28caa69a by Apoorv Ingle at 2025-05-05T18:53:34-05:00 accept test cases with changed error messages - - - - - 22 changed files: - testsuite/tests/deSugar/should_compile/T10662.stderr - testsuite/tests/deSugar/should_compile/T3263-1.stderr - testsuite/tests/deSugar/should_compile/T3263-2.stderr - testsuite/tests/default/default-fail05.stderr - testsuite/tests/indexed-types/should_fail/T2693.stderr - testsuite/tests/plugins/test-defaulting-plugin.stderr - testsuite/tests/polykinds/T13393.stderr - testsuite/tests/printer/T17697.stderr - testsuite/tests/typecheck/should_compile/T14590.stderr - testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr - testsuite/tests/typecheck/should_fail/DoExpansion1.stderr - testsuite/tests/typecheck/should_fail/DoExpansion2.stderr - testsuite/tests/typecheck/should_fail/T10971d.stderr - testsuite/tests/typecheck/should_fail/T13311.stderr - testsuite/tests/typecheck/should_fail/T24064.stderr - testsuite/tests/typecheck/should_fail/T3613.stderr - testsuite/tests/typecheck/should_fail/T7851.stderr - testsuite/tests/typecheck/should_fail/T8603.stderr - testsuite/tests/typecheck/should_fail/T9612.stderr - testsuite/tests/typecheck/should_fail/tcfail128.stderr - testsuite/tests/typecheck/should_fail/tcfail168.stderr - testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr Changes: ===================================== testsuite/tests/deSugar/should_compile/T10662.stderr ===================================== @@ -1,6 +1,6 @@ - -T10662.hs:3:3: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)] +T10662.hs:2:8: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)] A do-notation statement discarded a result of type ‘String’ Suggested fix: Suppress this warning by saying ‘_ <- return $ let a = "hello" in a’ + ===================================== testsuite/tests/deSugar/should_compile/T3263-1.stderr ===================================== @@ -1,8 +1,8 @@ - -T3263-1.hs:25:3: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)] +T3263-1.hs:24:6: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)] A do-notation statement discarded a result of type ‘Int’ Suggested fix: Suppress this warning by saying ‘_ <- nonNullM’ -T3263-1.hs:35:3: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)] +T3263-1.hs:34:6: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)] A do-notation statement discarded a result of type ‘Int’ Suggested fix: Suppress this warning by saying ‘_ <- nonNullM’ + ===================================== testsuite/tests/deSugar/should_compile/T3263-2.stderr ===================================== @@ -1,10 +1,10 @@ - -T3263-2.hs:25:3: warning: [GHC-08838] [-Wwrong-do-bind (in -Wdefault)] +T3263-2.hs:24:6: warning: [GHC-08838] [-Wwrong-do-bind (in -Wdefault)] A do-notation statement discarded a result of type ‘m Int’ Suggested fix: Suppress this warning by saying ‘_ <- return (return 10 :: m Int)’ -T3263-2.hs:37:3: warning: [GHC-08838] [-Wwrong-do-bind (in -Wdefault)] +T3263-2.hs:36:6: warning: [GHC-08838] [-Wwrong-do-bind (in -Wdefault)] A do-notation statement discarded a result of type ‘m Int’ Suggested fix: Suppress this warning by saying ‘_ <- return (return 10 :: m Int)’ + ===================================== testsuite/tests/default/default-fail05.stderr ===================================== @@ -11,7 +11,7 @@ default-fail05.hs:11:10: error: [GHC-39999] (use -fprint-potential-instances to see them all) • In the first argument of ‘($)’, namely ‘toList’ In the first argument of ‘print’, namely ‘(toList $ pure 21)’ - In a stmt of a 'do' block: print (toList $ pure 21) + In the expression: print (toList $ pure 21) default-fail05.hs:11:19: error: [GHC-39999] • Ambiguous type variable ‘t0’ arising from a use of ‘pure’ @@ -25,7 +25,7 @@ default-fail05.hs:11:19: error: [GHC-39999] (use -fprint-potential-instances to see them all) • In the second argument of ‘($)’, namely ‘pure 21’ In the first argument of ‘print’, namely ‘(toList $ pure 21)’ - In a stmt of a 'do' block: print (toList $ pure 21) + In the expression: print (toList $ pure 21) default-fail05.hs:12:3: error: [GHC-39999] • Ambiguous type variable ‘t1’ arising from a use of ‘traverse’ ===================================== testsuite/tests/indexed-types/should_fail/T2693.stderr ===================================== @@ -1,8 +1,7 @@ - T2693.hs:12:15: error: [GHC-83865] • Couldn't match expected type: (a8, b1) with actual type: TFn a6 - The type variable ‘a6’ is ambiguous + The type variable ‘a6’ is ambiguous • In the first argument of ‘fst’, namely ‘x’ In the first argument of ‘(+)’, namely ‘fst x’ In the expression: fst x + fst x @@ -11,7 +10,7 @@ T2693.hs:12:15: error: [GHC-83865] T2693.hs:12:23: error: [GHC-83865] • Couldn't match expected type: (a8, b2) with actual type: TFn a7 - The type variable ‘a7’ is ambiguous + The type variable ‘a7’ is ambiguous • In the first argument of ‘fst’, namely ‘x’ In the second argument of ‘(+)’, namely ‘fst x’ In the expression: fst x + fst x @@ -20,7 +19,7 @@ T2693.hs:12:23: error: [GHC-83865] T2693.hs:19:15: error: [GHC-83865] • Couldn't match expected type: (a5, b0) with actual type: TFn a2 - The type variable ‘a2’ is ambiguous + The type variable ‘a2’ is ambiguous • In the first argument of ‘fst’, namely ‘x’ In the first argument of ‘(+)’, namely ‘fst x’ In the expression: fst x + snd x @@ -29,7 +28,7 @@ T2693.hs:19:15: error: [GHC-83865] T2693.hs:19:23: error: [GHC-83865] • Couldn't match expected type: (a4, a5) with actual type: TFn a3 - The type variable ‘a3’ is ambiguous + The type variable ‘a3’ is ambiguous • In the first argument of ‘snd’, namely ‘x’ In the second argument of ‘(+)’, namely ‘snd x’ In the expression: fst x + snd x @@ -40,10 +39,11 @@ T2693.hs:29:20: error: [GHC-83865] with: PVR a1 Expected: () -> Maybe (PVR a1) Actual: () -> Maybe (TFn a0) - The type variable ‘a0’ is ambiguous + The type variable ‘a0’ is ambiguous • In the first argument of ‘mapM’, namely ‘g’ - In a stmt of a 'do' block: pvs <- mapM g undefined + In the expression: mapM g undefined In the expression: do pvs <- mapM g undefined let n = (map pvrX pvs) `min` (map pvrX pvs) undefined + ===================================== testsuite/tests/plugins/test-defaulting-plugin.stderr ===================================== @@ -1,10 +1,9 @@ - test-defaulting-plugin.hs:28:11: warning: [GHC-18042] [-Wtype-defaults (in -Wall)] • Defaulting the type variable ‘a0’ to type ‘0’ in the following constraint KnownNat a0 arising from a use of ‘q’ • In the first argument of ‘(+)’, namely ‘q’ In the second argument of ‘($)’, namely ‘q + w’ - In a stmt of a 'do' block: print $ q + w + In the expression: print $ q + w test-defaulting-plugin.hs:28:15: warning: [GHC-18042] [-Wtype-defaults (in -Wall)] • Defaulting the type variable ‘a0’ to type ‘2’ in the following constraints @@ -16,7 +15,7 @@ test-defaulting-plugin.hs:28:15: warning: [GHC-18042] [-Wtype-defaults (in -Wall arising from a use of ‘w’ at test-defaulting-plugin.hs:28:15 • In the second argument of ‘(+)’, namely ‘w’ In the second argument of ‘($)’, namely ‘q + w’ - In a stmt of a 'do' block: print $ q + w + In the expression: print $ q + w test-defaulting-plugin.hs:29:11: warning: [GHC-18042] [-Wtype-defaults (in -Wall)] • Defaulting the type variable ‘b0’ to type ‘0’ in the following constraint @@ -35,3 +34,4 @@ test-defaulting-plugin.hs:29:11: warning: [GHC-18042] [-Wtype-defaults (in -Wall In the expression: do print $ q + w print $ mc Proxy Proxy + ===================================== testsuite/tests/polykinds/T13393.stderr ===================================== @@ -1,4 +1,3 @@ - T13393.hs:61:3: error: [GHC-39999] • Ambiguous type variable ‘t0’ arising from a use of ‘mapM’ prevents the constraint ‘(Traversable t0)’ from being solved. @@ -11,7 +10,7 @@ T13393.hs:61:3: error: [GHC-39999] ...plus four others ...plus 27 instances involving out-of-scope types (use -fprint-potential-instances to see them all) - • In a stmt of a 'do' block: + • In the expression: mapM putBackLeftOverInputAndReturnOutput undefined In the expression: do mapM putBackLeftOverInputAndReturnOutput undefined @@ -24,3 +23,4 @@ T13393.hs:61:3: error: [GHC-39999] putBackLeftOverInputAndReturnOutput (MkEncodeResult x) = do leftOvers .= x .... + ===================================== testsuite/tests/printer/T17697.stderr ===================================== @@ -1,8 +1,8 @@ -T17697.hs:6:5: warning: [GHC-88464] [-Wdeferred-out-of-scope-variables (in -Wdefault)] - Variable not in scope: threadDelay :: t0 -> IO a0 - -T17697.hs:6:5: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)] +T17697.hs:5:8: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)] A do-notation statement discarded a result of type ‘GHC.Internal.Types.ZonkAny 1’ Suggested fix: Suppress this warning by saying ‘_ <- threadDelay 1’ +T17697.hs:6:5: warning: [GHC-88464] [-Wdeferred-out-of-scope-variables (in -Wdefault)] + Variable not in scope: threadDelay :: t0 -> IO a0 + ===================================== testsuite/tests/typecheck/should_compile/T14590.stderr ===================================== @@ -1,7 +1,6 @@ -T14590.hs:4:11: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] +T14590.hs:4:13: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] • Found hole: _ :: Int -> Int -> Int - • In the expression: x `_` - In the expression: (x `_`) y + • In the expression: (x `_`) y In an equation for ‘f1’: f1 x y = (x `_`) y • Relevant bindings include y :: Int (bound at T14590.hs:4:6) @@ -85,11 +84,10 @@ T14590.hs:4:11: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] (imported from ‘Prelude’ at T14590.hs:1:8-13 (and originally defined in ‘GHC.Internal.Base’)) -T14590.hs:5:11: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] +T14590.hs:5:13: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] • Found hole: _a :: Int -> Int -> Int Or perhaps ‘_a’ is mis-spelled, or not in scope - • In the expression: x `_a` - In the expression: (x `_a`) y + • In the expression: (x `_a`) y In an equation for ‘f2’: f2 x y = (x `_a`) y • Relevant bindings include y :: Int (bound at T14590.hs:5:6) ===================================== testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr ===================================== @@ -11,7 +11,7 @@ valid_hole_fits.hs:9:6: warning: [GHC-88464] [-Wdeferred-out-of-scope-variables valid_hole_fits.hs:17:17: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] • Found hole: _ :: Int -> IO Int - • In a stmt of a 'do' block: y <- _ x + • In the expression: _ x In the expression: do x <- a 0 y <- _ x ===================================== testsuite/tests/typecheck/should_fail/DoExpansion1.stderr ===================================== @@ -1,4 +1,3 @@ - DoExpansion1.hs:7:19: warning: [GHC-39999] [-Wdeferred-type-errors (in -Wdefault)] • No instance for ‘Num String’ arising from the literal ‘1’ • In the first argument of ‘putStrLn’, namely ‘1’ @@ -23,7 +22,7 @@ DoExpansion1.hs:15:54: warning: [GHC-39999] [-Wdeferred-type-errors (in -Wdefaul DoExpansion1.hs:19:21: warning: [GHC-39999] [-Wdeferred-type-errors (in -Wdefault)] • No instance for ‘Num String’ arising from the literal ‘1’ • In the first argument of ‘putStrLn’, namely ‘1’ - In a stmt of a 'do' block: putStrLn 1 + In the expression: putStrLn 1 In the expression: do putStrLn 1 putStrLn "r2" @@ -32,7 +31,7 @@ DoExpansion1.hs:19:21: warning: [GHC-39999] [-Wdeferred-type-errors (in -Wdefaul DoExpansion1.hs:25:21: warning: [GHC-39999] [-Wdeferred-type-errors (in -Wdefault)] • No instance for ‘Num String’ arising from the literal ‘2’ • In the first argument of ‘putStrLn’, namely ‘2’ - In a stmt of a 'do' block: putStrLn 2 + In the expression: putStrLn 2 In the expression: do putStrLn "r1" putStrLn 2 @@ -46,3 +45,4 @@ DoExpansion1.hs:32:21: warning: [GHC-39999] [-Wdeferred-type-errors (in -Wdefaul do putStrLn "r1" putStrLn "r2" putStrLn 3 + ===================================== testsuite/tests/typecheck/should_fail/DoExpansion2.stderr ===================================== @@ -1,4 +1,3 @@ - DoExpansion2.hs:13:20: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)] • Couldn't match expected type ‘Int’ with actual type ‘Char’ • In the first argument of ‘(+)’, namely ‘x’ @@ -57,7 +56,7 @@ DoExpansion2.hs:34:22: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefaul with actual type: IO String • The function ‘getVal’ is applied to two visible arguments, but its type ‘Int -> IO String’ has only one - In a stmt of a 'do' block: Just x <- getVal 3 4 + In the expression: getVal 3 4 In the expression: do Just x <- getVal 3 4 return x @@ -71,3 +70,4 @@ DoExpansion2.hs:39:19: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefaul In the expression: do x <- getVal 3 return x + ===================================== testsuite/tests/typecheck/should_fail/T10971d.stderr ===================================== @@ -1,17 +1,16 @@ - T10971d.hs:4:14: error: [GHC-83865] • Couldn't match expected type: [a0] with actual type: Maybe a3 • In the first argument of ‘f’, namely ‘(Just 1)’ In the second argument of ‘($)’, namely ‘f (Just 1)’ - In a stmt of a 'do' block: print $ f (Just 1) + In the expression: print $ f (Just 1) T10971d.hs:5:19: error: [GHC-83865] • Couldn't match expected type: [b0] with actual type: Maybe a4 • In the second argument of ‘g’, namely ‘(Just 5)’ In the second argument of ‘($)’, namely ‘g (+ 1) (Just 5)’ - In a stmt of a 'do' block: print $ g (+ 1) (Just 5) + In the expression: print $ g (+ 1) (Just 5) T10971d.hs:6:23: error: [GHC-83865] • Couldn't match expected type: [a2] @@ -19,3 +18,4 @@ T10971d.hs:6:23: error: [GHC-83865] • In the second argument of ‘h’, namely ‘Nothing’ In the second argument of ‘($)’, namely ‘h (const 5) Nothing’ In a stmt of a 'do' block: print $ h (const 5) Nothing + ===================================== testsuite/tests/typecheck/should_fail/T13311.stderr ===================================== @@ -1,12 +1,12 @@ - T13311.hs:9:3: error: [GHC-83865] • Couldn't match expected type: IO a0 with actual type: Maybe a1 -> Maybe b0 • Probable cause: ‘f’ is applied to too few arguments - In a stmt of a 'do' block: f + In the expression: f In the expression: do f putChar 'a' In an equation for ‘g’: g = do f putChar 'a' + ===================================== testsuite/tests/typecheck/should_fail/T24064.stderr ===================================== @@ -1,4 +1,3 @@ - T24064.hs:42:3: error: [GHC-25897] • Could not deduce ‘m ~ X e0’ from the context: (C2 m, F2 m ~ Y) @@ -11,7 +10,7 @@ T24064.hs:42:3: error: [GHC-25897] the type signature for: test :: forall (m :: * -> *). (C2 m, F2 m ~ Y) => m () at T24064.hs:40:1-32 - • In a stmt of a 'do' block: fun1 + • In the expression: fun1 In the expression: do fun1 fun2 @@ -24,3 +23,4 @@ T24064.hs:42:3: error: [GHC-25897] g fun3 .... • Relevant bindings include test :: m () (bound at T24064.hs:41:1) + ===================================== testsuite/tests/typecheck/should_fail/T3613.stderr ===================================== @@ -1,4 +1,3 @@ - T3613.hs:14:20: error: [GHC-83865] • Couldn't match type ‘IO’ with ‘Maybe’ Expected: Maybe () @@ -11,7 +10,7 @@ T3613.hs:17:24: error: [GHC-83865] • Couldn't match type ‘IO’ with ‘Maybe’ Expected: Maybe () Actual: IO () - • In a stmt of a 'do' block: bar + • In the expression: bar In the first argument of ‘fooThen’, namely ‘(do bar undefined)’ @@ -19,3 +18,4 @@ T3613.hs:17:24: error: [GHC-83865] fooThen (do bar undefined) + ===================================== testsuite/tests/typecheck/should_fail/T7851.stderr ===================================== @@ -1,9 +1,8 @@ - T7851.hs:5:10: error: [GHC-83865] • Couldn't match expected type: IO a0 with actual type: a1 -> IO () • Probable cause: ‘print’ is applied to too few arguments - In a stmt of a 'do' block: print + In the expression: print In the expression: do print print "Hello" @@ -11,3 +10,4 @@ T7851.hs:5:10: error: [GHC-83865] bar = do print print "Hello" + ===================================== testsuite/tests/typecheck/should_fail/T8603.stderr ===================================== @@ -1,4 +1,3 @@ - T8603.hs:33:17: error: [GHC-18872] • Couldn't match kind ‘* -> *’ with ‘*’ When matching types @@ -10,7 +9,7 @@ T8603.hs:33:17: error: [GHC-18872] but its type ‘(Control.Monad.Trans.Class.MonadTrans t, Monad m) => m a -> t m a’ has only one - In a stmt of a 'do' block: prize <- lift uniform [1, 2, 3] + In the expression: lift uniform [1, 2, 3] In the expression: do prize <- lift uniform [1, 2, ....] return False @@ -21,9 +20,10 @@ T8603.hs:33:22: error: [GHC-83865] Expected: [a1] -> StateT s RV a0 Actual: [a1] -> RV a1 • In the first argument of ‘lift’, namely ‘uniform’ - In a stmt of a 'do' block: prize <- lift uniform [1, 2, 3] + In the expression: lift uniform [1, 2, 3] In the expression: do prize <- lift uniform [1, 2, ....] return False • Relevant bindings include testRVState1 :: RVState s Bool (bound at T8603.hs:32:1) + ===================================== testsuite/tests/typecheck/should_fail/T9612.stderr ===================================== @@ -1,4 +1,3 @@ - T9612.hs:16:9: error: [GHC-18872] • Couldn't match type: [(Int, a)] with: (Int, a) @@ -6,7 +5,7 @@ T9612.hs:16:9: error: [GHC-18872] constraint ‘MonadWriter (Int, a) (WriterT [(Int, a)] Identity)’ arising from a use of ‘tell’ instance ‘MonadWriter w (WriterT w m)’ at T9612.hs:20:10-59 - • In a stmt of a 'do' block: tell (n, x) + • In the expression: tell (n, x) In the expression: do tell (n, x) return (1, y) @@ -19,3 +18,4 @@ T9612.hs:16:9: error: [GHC-18872] y :: a (bound at T9612.hs:14:3) f :: a -> (Int, a) -> Writer [(Int, a)] (Int, a) (bound at T9612.hs:14:1) + ===================================== testsuite/tests/typecheck/should_fail/tcfail128.stderr ===================================== @@ -1,4 +1,3 @@ - tcfail128.hs:18:16: error: [GHC-39999] • Ambiguous type variable ‘b0’ arising from a use of ‘thaw’ prevents the constraint ‘(Data.Array.Base.MArray @@ -6,7 +5,7 @@ tcfail128.hs:18:16: error: [GHC-39999] Probable fix: use a type annotation to specify what ‘b0’ should be. one instance involving out-of-scope types (use -fprint-potential-instances to see them all) - • In a stmt of a 'do' block: v <- thaw tmp + • In the expression: thaw tmp In the expression: do let sL = ... dim = length sL @@ -19,3 +18,4 @@ tcfail128.hs:18:16: error: [GHC-39999] .... v <- thaw tmp return () + ===================================== testsuite/tests/typecheck/should_fail/tcfail168.stderr ===================================== @@ -1,9 +1,8 @@ - tcfail168.hs:7:11: error: [GHC-83865] • Couldn't match expected type: IO a0 with actual type: Char -> IO () • Probable cause: ‘putChar’ is applied to too few arguments - In a stmt of a 'do' block: putChar + In the expression: putChar In the expression: do putChar putChar 'a' @@ -16,3 +15,4 @@ tcfail168.hs:7:11: error: [GHC-83865] putChar 'a' putChar 'a' .... + ===================================== testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr ===================================== @@ -1,7 +1,7 @@ CaretDiagnostics1.hs:7:8-15: error: [GHC-83865] • Couldn't match expected type ‘IO a0’ with actual type ‘Int’ • In the second argument of ‘(+)’, namely ‘(3 :: Int)’ - In a stmt of a 'do' block: + In the expression: 10000000000000000000000000000000000000 + 2 + (3 :: Int) In the expression: do 10000000000000000000000000000000000000 + 2 + (3 :: Int) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/28caa69a244799f9a48b3826be1b787b... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/28caa69a244799f9a48b3826be1b787b... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Apoorv Ingle (@ani)