Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC Commits: 32ac5a05 by Apoorv Ingle at 2025-11-23T16:42:39-06:00 make sure landmark error contexts are always printed. accept some testcases - - - - - 8 changed files: - compiler/GHC/Hs/Expr.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Utils/Monad.hs - testsuite/tests/default/default-fail05.stderr - testsuite/tests/parser/should_fail/RecordDotSyntaxFail11.stderr - testsuite/tests/polykinds/T13393.stderr - testsuite/tests/typecheck/should_compile/T14590.stderr - testsuite/tests/typecheck/should_fail/T6069.stderr Changes: ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -897,9 +897,9 @@ ppr_expr (NegApp _ e _) = char '-' <+> pprDebugParendExpr appPrec e ppr_expr (SectionL _ expr op) | Just pp_op <- ppr_infix_expr (unLoc op) - = text "<SectionL>" <+> pp_infixly pp_op + = pp_infixly pp_op | otherwise - = text "<SectionL>" <+> pp_prefixly + = pp_prefixly where pp_expr = pprDebugParendExpr opPrec expr @@ -910,9 +910,9 @@ ppr_expr (SectionL _ expr op) ppr_expr (SectionR _ op expr) | Just pp_op <- ppr_infix_expr (unLoc op) - = text "<SectionR>" <+> pp_infixly pp_op + = pp_infixly pp_op | otherwise - = text "<SectionR>" <+> pp_prefixly + = pp_prefixly where pp_expr = pprDebugParendExpr opPrec expr ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -186,7 +186,7 @@ Note [Instantiation variables are short lived] tcExprSigma :: Bool -> HsExpr GhcRn -> TcM (HsExpr GhcTc, TcSigmaType) tcExprSigma inst rn_expr = do { (fun@(rn_fun,fun_lspan), rn_args) <- splitHsApps rn_expr - ; ds_flag <- getDeepSubsumptionFlag_DataConHead rn_fun + -- ; ds_flag <- getDeepSubsumptionFlag_DataConHead rn_fun -- ; do_ql <- wantQuickLook rn_fun ; (tc_fun, fun_sigma) <- tcInferAppHead fun ; code_orig <- getSrcCodeOrigin ===================================== compiler/GHC/Tc/Utils/Monad.hs ===================================== @@ -1845,12 +1845,9 @@ mkErrCtxt env ctxts go :: Bool -> Int -> TidyEnv -> [ErrCtxt] -> TcM [ErrCtxtMsg] go _ _ _ [] = return [] go dbg n env (MkErrCtxt LandmarkUserSrcCode ctxt : ctxts) - | n < mAX_CONTEXTS -- Too verbose || dbg = do { (env', msg) <- liftZonkM $ ctxt env ; rest <- go dbg n env' ctxts ; return (msg : rest) } - | otherwise - = go dbg n env ctxts go dbg n env (MkErrCtxt _ ctxt : ctxts) | n < mAX_CONTEXTS -- Too verbose || dbg = do { (env', msg) <- liftZonkM $ ctxt env ===================================== testsuite/tests/default/default-fail05.stderr ===================================== @@ -1,69 +1,70 @@ default-fail05.hs:11:10: error: [GHC-39999] - • Ambiguous type variable ‘f0’ arising from a use of ‘toList’ - prevents the constraint ‘(Foldable f0)’ from being solved. - Probable fix: use a type annotation to specify what ‘f0’ should be. + • Ambiguous type variable ‘t0’ arising from a use of ‘toList’ + prevents the constraint ‘(Foldable t0)’ from being solved. + Probable fix: use a type annotation to specify what ‘t0’ should be. Potentially matching instances: - instance Foldable (Either a) - -- Defined in ‘GHC.Internal.Data.Foldable’ - instance Foldable Maybe -- Defined in ‘GHC.Internal.Data.Foldable’ - ...plus three others - ...plus 26 instances involving out-of-scope types - (use -fprint-potential-instances to see them all) + instance Foldable (Either a) + -- Defined in ‘GHC.Internal.Data.Foldable’ + instance Foldable Maybe -- Defined in ‘GHC.Internal.Data.Foldable’ + ...plus three others + ...plus 26 instances involving out-of-scope types + (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) default-fail05.hs:11:19: error: [GHC-39999] - • Ambiguous type variable ‘f0’ arising from a use of ‘pure’ - prevents the constraint ‘(Applicative f0)’ from being solved. - Probable fix: use a type annotation to specify what ‘f0’ should be. + • Ambiguous type variable ‘t0’ arising from a use of ‘pure’ + prevents the constraint ‘(Applicative t0)’ from being solved. + Probable fix: use a type annotation to specify what ‘t0’ should be. Potentially matching instances: - instance Applicative IO -- Defined in ‘GHC.Internal.Base’ - instance Applicative Maybe -- Defined in ‘GHC.Internal.Base’ - ...plus six others - ...plus 9 instances involving out-of-scope types - (use -fprint-potential-instances to see them all) + instance Applicative IO -- Defined in ‘GHC.Internal.Base’ + instance Applicative Maybe -- Defined in ‘GHC.Internal.Base’ + ...plus six others + ...plus 9 instances involving out-of-scope types + (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) default-fail05.hs:12:3: error: [GHC-39999] - • Ambiguous type variable ‘t0’ arising from a use of ‘traverse’ - prevents the constraint ‘(Traversable t0)’ from being solved. + • Ambiguous type variable ‘t1’ arising from a use of ‘traverse’ + prevents the constraint ‘(Traversable t1)’ from being solved. Relevant bindings include - main :: IO (t0 ()) (bound at default-fail05.hs:10:1) - Probable fix: use a type annotation to specify what ‘t0’ should be. + main :: IO (t1 ()) (bound at default-fail05.hs:10:1) + Probable fix: use a type annotation to specify what ‘t1’ should be. Potentially matching instances: - instance Traversable (Either a) - -- Defined in ‘GHC.Internal.Data.Traversable’ - instance Traversable Maybe - -- Defined in ‘GHC.Internal.Data.Traversable’ - ...plus three others - ...plus 28 instances involving out-of-scope types - (use -fprint-potential-instances to see them all) + instance Traversable (Either a) + -- Defined in ‘GHC.Internal.Data.Traversable’ + instance Traversable Maybe + -- Defined in ‘GHC.Internal.Data.Traversable’ + ...plus three others + ...plus 28 instances involving out-of-scope types + (use -fprint-potential-instances to see them all) • In a stmt of a 'do' block: traverse print (pure 42) In the expression: - do print (toList $ pure 21) - traverse print (pure 42) + do print (toList $ pure 21) + traverse print (pure 42) In an equation for ‘main’: - main - = do print (toList $ pure 21) - traverse print (pure 42) + main + = do print (toList $ pure 21) + traverse print (pure 42) default-fail05.hs:12:19: error: [GHC-39999] - • Ambiguous type variable ‘t0’ arising from a use of ‘pure’ - prevents the constraint ‘(Applicative t0)’ from being solved. + • Ambiguous type variable ‘t1’ arising from a use of ‘pure’ + prevents the constraint ‘(Applicative t1)’ from being solved. Relevant bindings include - main :: IO (t0 ()) (bound at default-fail05.hs:10:1) - Probable fix: use a type annotation to specify what ‘t0’ should be. + main :: IO (t1 ()) (bound at default-fail05.hs:10:1) + Probable fix: use a type annotation to specify what ‘t1’ should be. Potentially matching instances: - instance Applicative IO -- Defined in ‘GHC.Internal.Base’ - instance Applicative Maybe -- Defined in ‘GHC.Internal.Base’ - ...plus six others - ...plus 9 instances involving out-of-scope types - (use -fprint-potential-instances to see them all) + instance Applicative IO -- Defined in ‘GHC.Internal.Base’ + instance Applicative Maybe -- Defined in ‘GHC.Internal.Base’ + ...plus six others + ...plus 9 instances involving out-of-scope types + (use -fprint-potential-instances to see them all) • In the second argument of ‘traverse’, namely ‘(pure 42)’ In a stmt of a 'do' block: traverse print (pure 42) In the expression: - do print (toList $ pure 21) - traverse print (pure 42) + do print (toList $ pure 21) + traverse print (pure 42) + ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail11.stderr ===================================== @@ -3,23 +3,22 @@ RecordDotSyntaxFail11.hs:8:3: error: [GHC-39999] prevents the constraint ‘(Show a0)’ from being solved. Probable fix: use a type annotation to specify what ‘a0’ should be. Potentially matching instances: - instance Show Ordering -- Defined in ‘GHC.Internal.Show’ - instance Show Integer -- Defined in ‘GHC.Internal.Show’ - ...plus 25 others - ...plus 13 instances involving out-of-scope types - (use -fprint-potential-instances to see them all) + instance Show Ordering -- Defined in ‘GHC.Internal.Show’ + instance Show Integer -- Defined in ‘GHC.Internal.Show’ + ...plus 25 others + ...plus 13 instances involving out-of-scope types + (use -fprint-potential-instances to see them all) • In the first argument of ‘($)’, namely ‘print’ In a stmt of a 'do' block: print $ (.foo.bar.baz) a In the expression: - do let a = Foo {foo = ...} - print $ (.foo.bar.baz) a + do let a = Foo {foo = ...} + print $ (.foo.bar.baz) a RecordDotSyntaxFail11.hs:8:11: error: [GHC-39999] • No instance for ‘GHC.Internal.Records.HasField "baz" Int a0’ - arising from the expression (.foo.bar.baz) + arising from the expression (.foo.bar.baz) NB: ‘Int’ is not a record type. - • In the second argument of ‘($)’, namely ‘(.foo.bar.baz) a’ + • In the expression: (.foo.bar.baz) + In the second argument of ‘($)’, namely ‘(.foo.bar.baz) a’ In a stmt of a 'do' block: print $ (.foo.bar.baz) a - In the expression: - do let a = Foo {foo = ...} - print $ (.foo.bar.baz) a + ===================================== testsuite/tests/polykinds/T13393.stderr ===================================== @@ -1,5 +1,5 @@ T13393.hs:61:3: error: [GHC-39999] - • Ambiguous type variable ‘t0’ arising from a do statement + • Ambiguous type variable ‘t0’ arising from a use of ‘mapM’ prevents the constraint ‘(Traversable t0)’ from being solved. Probable fix: use a type annotation to specify what ‘t0’ should be. Potentially matching instances: ===================================== testsuite/tests/typecheck/should_compile/T14590.stderr ===================================== @@ -1,6 +1,7 @@ T14590.hs:4:13: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] • Found hole: _ :: Int -> Int -> Int - • In the expression: (x `_`) y + • In the expression: x `_` + 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) @@ -87,7 +88,8 @@ T14590.hs:4:13: 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`) y + • In the expression: x `_a` + 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) @@ -173,7 +175,8 @@ T14590.hs:5:13: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] T14590.hs:6:11: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] • Found hole: _ :: Int -> Int -> Int - • In the expression: (`_` x) y + • In the expression: `_` x + In the expression: (`_` x) y In an equation for ‘f3’: f3 x y = (`_` x) y • Relevant bindings include y :: Int (bound at T14590.hs:6:6) @@ -260,7 +263,8 @@ T14590.hs:6:11: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] T14590.hs:7:11: 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: (`_a` x) y + • In the expression: `_a` x + In the expression: (`_a` x) y In an equation for ‘f4’: f4 x y = (`_a` x) y • Relevant bindings include y :: Int (bound at T14590.hs:7:6) ===================================== testsuite/tests/typecheck/should_fail/T6069.stderr ===================================== @@ -22,6 +22,6 @@ T6069.hs:15:16: error: [GHC-83865] Expected: ST s2 Int -> b2 Actual: (forall s. ST s b2) -> b2 • In the second argument of ‘(.)’, namely ‘runST’ - In the expression: print . runST + In the first argument of ‘($)’, namely ‘(print . runST)’ In the expression: (print . runST) $ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/32ac5a0589a73993ecc6b5e2601b9d33... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/32ac5a0589a73993ecc6b5e2601b9d33... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Apoorv Ingle (@ani)