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
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:
| ... | ... | @@ -897,9 +897,9 @@ ppr_expr (NegApp _ e _) = char '-' <+> pprDebugParendExpr appPrec e |
| 897 | 897 | |
| 898 | 898 | ppr_expr (SectionL _ expr op)
|
| 899 | 899 | | Just pp_op <- ppr_infix_expr (unLoc op)
|
| 900 | - = text "<SectionL>" <+> pp_infixly pp_op
|
|
| 900 | + = pp_infixly pp_op
|
|
| 901 | 901 | | otherwise
|
| 902 | - = text "<SectionL>" <+> pp_prefixly
|
|
| 902 | + = pp_prefixly
|
|
| 903 | 903 | where
|
| 904 | 904 | pp_expr = pprDebugParendExpr opPrec expr
|
| 905 | 905 | |
| ... | ... | @@ -910,9 +910,9 @@ ppr_expr (SectionL _ expr op) |
| 910 | 910 | |
| 911 | 911 | ppr_expr (SectionR _ op expr)
|
| 912 | 912 | | Just pp_op <- ppr_infix_expr (unLoc op)
|
| 913 | - = text "<SectionR>" <+> pp_infixly pp_op
|
|
| 913 | + = pp_infixly pp_op
|
|
| 914 | 914 | | otherwise
|
| 915 | - = text "<SectionR>" <+> pp_prefixly
|
|
| 915 | + = pp_prefixly
|
|
| 916 | 916 | where
|
| 917 | 917 | pp_expr = pprDebugParendExpr opPrec expr
|
| 918 | 918 |
| ... | ... | @@ -186,7 +186,7 @@ Note [Instantiation variables are short lived] |
| 186 | 186 | tcExprSigma :: Bool -> HsExpr GhcRn -> TcM (HsExpr GhcTc, TcSigmaType)
|
| 187 | 187 | tcExprSigma inst rn_expr
|
| 188 | 188 | = do { (fun@(rn_fun,fun_lspan), rn_args) <- splitHsApps rn_expr
|
| 189 | - ; ds_flag <- getDeepSubsumptionFlag_DataConHead rn_fun
|
|
| 189 | + -- ; ds_flag <- getDeepSubsumptionFlag_DataConHead rn_fun
|
|
| 190 | 190 | -- ; do_ql <- wantQuickLook rn_fun
|
| 191 | 191 | ; (tc_fun, fun_sigma) <- tcInferAppHead fun
|
| 192 | 192 | ; code_orig <- getSrcCodeOrigin
|
| ... | ... | @@ -1845,12 +1845,9 @@ mkErrCtxt env ctxts |
| 1845 | 1845 | go :: Bool -> Int -> TidyEnv -> [ErrCtxt] -> TcM [ErrCtxtMsg]
|
| 1846 | 1846 | go _ _ _ [] = return []
|
| 1847 | 1847 | go dbg n env (MkErrCtxt LandmarkUserSrcCode ctxt : ctxts)
|
| 1848 | - | n < mAX_CONTEXTS -- Too verbose || dbg
|
|
| 1849 | 1848 | = do { (env', msg) <- liftZonkM $ ctxt env
|
| 1850 | 1849 | ; rest <- go dbg n env' ctxts
|
| 1851 | 1850 | ; return (msg : rest) }
|
| 1852 | - | otherwise
|
|
| 1853 | - = go dbg n env ctxts
|
|
| 1854 | 1851 | go dbg n env (MkErrCtxt _ ctxt : ctxts)
|
| 1855 | 1852 | | n < mAX_CONTEXTS -- Too verbose || dbg
|
| 1856 | 1853 | = do { (env', msg) <- liftZonkM $ ctxt env
|
| 1 | 1 | default-fail05.hs:11:10: error: [GHC-39999]
|
| 2 | - • Ambiguous type variable ‘f0’ arising from a use of ‘toList’
|
|
| 3 | - prevents the constraint ‘(Foldable f0)’ from being solved.
|
|
| 4 | - Probable fix: use a type annotation to specify what ‘f0’ should be.
|
|
| 2 | + • Ambiguous type variable ‘t0’ arising from a use of ‘toList’
|
|
| 3 | + prevents the constraint ‘(Foldable t0)’ from being solved.
|
|
| 4 | + Probable fix: use a type annotation to specify what ‘t0’ should be.
|
|
| 5 | 5 | Potentially matching instances:
|
| 6 | - instance Foldable (Either a)
|
|
| 7 | - -- Defined in ‘GHC.Internal.Data.Foldable’
|
|
| 8 | - instance Foldable Maybe -- Defined in ‘GHC.Internal.Data.Foldable’
|
|
| 9 | - ...plus three others
|
|
| 10 | - ...plus 26 instances involving out-of-scope types
|
|
| 11 | - (use -fprint-potential-instances to see them all)
|
|
| 6 | + instance Foldable (Either a)
|
|
| 7 | + -- Defined in ‘GHC.Internal.Data.Foldable’
|
|
| 8 | + instance Foldable Maybe -- Defined in ‘GHC.Internal.Data.Foldable’
|
|
| 9 | + ...plus three others
|
|
| 10 | + ...plus 26 instances involving out-of-scope types
|
|
| 11 | + (use -fprint-potential-instances to see them all)
|
|
| 12 | 12 | • In the first argument of ‘($)’, namely ‘toList’
|
| 13 | 13 | In the first argument of ‘print’, namely ‘(toList $ pure 21)’
|
| 14 | 14 | In a stmt of a 'do' block: print (toList $ pure 21)
|
| 15 | 15 | |
| 16 | 16 | default-fail05.hs:11:19: error: [GHC-39999]
|
| 17 | - • Ambiguous type variable ‘f0’ arising from a use of ‘pure’
|
|
| 18 | - prevents the constraint ‘(Applicative f0)’ from being solved.
|
|
| 19 | - Probable fix: use a type annotation to specify what ‘f0’ should be.
|
|
| 17 | + • Ambiguous type variable ‘t0’ arising from a use of ‘pure’
|
|
| 18 | + prevents the constraint ‘(Applicative t0)’ from being solved.
|
|
| 19 | + Probable fix: use a type annotation to specify what ‘t0’ should be.
|
|
| 20 | 20 | Potentially matching instances:
|
| 21 | - instance Applicative IO -- Defined in ‘GHC.Internal.Base’
|
|
| 22 | - instance Applicative Maybe -- Defined in ‘GHC.Internal.Base’
|
|
| 23 | - ...plus six others
|
|
| 24 | - ...plus 9 instances involving out-of-scope types
|
|
| 25 | - (use -fprint-potential-instances to see them all)
|
|
| 21 | + instance Applicative IO -- Defined in ‘GHC.Internal.Base’
|
|
| 22 | + instance Applicative Maybe -- Defined in ‘GHC.Internal.Base’
|
|
| 23 | + ...plus six others
|
|
| 24 | + ...plus 9 instances involving out-of-scope types
|
|
| 25 | + (use -fprint-potential-instances to see them all)
|
|
| 26 | 26 | • In the second argument of ‘($)’, namely ‘pure 21’
|
| 27 | 27 | In the first argument of ‘print’, namely ‘(toList $ pure 21)’
|
| 28 | 28 | In a stmt of a 'do' block: print (toList $ pure 21)
|
| 29 | 29 | |
| 30 | 30 | default-fail05.hs:12:3: error: [GHC-39999]
|
| 31 | - • Ambiguous type variable ‘t0’ arising from a use of ‘traverse’
|
|
| 32 | - prevents the constraint ‘(Traversable t0)’ from being solved.
|
|
| 31 | + • Ambiguous type variable ‘t1’ arising from a use of ‘traverse’
|
|
| 32 | + prevents the constraint ‘(Traversable t1)’ from being solved.
|
|
| 33 | 33 | Relevant bindings include
|
| 34 | - main :: IO (t0 ()) (bound at default-fail05.hs:10:1)
|
|
| 35 | - Probable fix: use a type annotation to specify what ‘t0’ should be.
|
|
| 34 | + main :: IO (t1 ()) (bound at default-fail05.hs:10:1)
|
|
| 35 | + Probable fix: use a type annotation to specify what ‘t1’ should be.
|
|
| 36 | 36 | Potentially matching instances:
|
| 37 | - instance Traversable (Either a)
|
|
| 38 | - -- Defined in ‘GHC.Internal.Data.Traversable’
|
|
| 39 | - instance Traversable Maybe
|
|
| 40 | - -- Defined in ‘GHC.Internal.Data.Traversable’
|
|
| 41 | - ...plus three others
|
|
| 42 | - ...plus 28 instances involving out-of-scope types
|
|
| 43 | - (use -fprint-potential-instances to see them all)
|
|
| 37 | + instance Traversable (Either a)
|
|
| 38 | + -- Defined in ‘GHC.Internal.Data.Traversable’
|
|
| 39 | + instance Traversable Maybe
|
|
| 40 | + -- Defined in ‘GHC.Internal.Data.Traversable’
|
|
| 41 | + ...plus three others
|
|
| 42 | + ...plus 28 instances involving out-of-scope types
|
|
| 43 | + (use -fprint-potential-instances to see them all)
|
|
| 44 | 44 | • In a stmt of a 'do' block: traverse print (pure 42)
|
| 45 | 45 | In the expression:
|
| 46 | - do print (toList $ pure 21)
|
|
| 47 | - traverse print (pure 42)
|
|
| 46 | + do print (toList $ pure 21)
|
|
| 47 | + traverse print (pure 42)
|
|
| 48 | 48 | In an equation for ‘main’:
|
| 49 | - main
|
|
| 50 | - = do print (toList $ pure 21)
|
|
| 51 | - traverse print (pure 42)
|
|
| 49 | + main
|
|
| 50 | + = do print (toList $ pure 21)
|
|
| 51 | + traverse print (pure 42)
|
|
| 52 | 52 | |
| 53 | 53 | default-fail05.hs:12:19: error: [GHC-39999]
|
| 54 | - • Ambiguous type variable ‘t0’ arising from a use of ‘pure’
|
|
| 55 | - prevents the constraint ‘(Applicative t0)’ from being solved.
|
|
| 54 | + • Ambiguous type variable ‘t1’ arising from a use of ‘pure’
|
|
| 55 | + prevents the constraint ‘(Applicative t1)’ from being solved.
|
|
| 56 | 56 | Relevant bindings include
|
| 57 | - main :: IO (t0 ()) (bound at default-fail05.hs:10:1)
|
|
| 58 | - Probable fix: use a type annotation to specify what ‘t0’ should be.
|
|
| 57 | + main :: IO (t1 ()) (bound at default-fail05.hs:10:1)
|
|
| 58 | + Probable fix: use a type annotation to specify what ‘t1’ should be.
|
|
| 59 | 59 | Potentially matching instances:
|
| 60 | - instance Applicative IO -- Defined in ‘GHC.Internal.Base’
|
|
| 61 | - instance Applicative Maybe -- Defined in ‘GHC.Internal.Base’
|
|
| 62 | - ...plus six others
|
|
| 63 | - ...plus 9 instances involving out-of-scope types
|
|
| 64 | - (use -fprint-potential-instances to see them all)
|
|
| 60 | + instance Applicative IO -- Defined in ‘GHC.Internal.Base’
|
|
| 61 | + instance Applicative Maybe -- Defined in ‘GHC.Internal.Base’
|
|
| 62 | + ...plus six others
|
|
| 63 | + ...plus 9 instances involving out-of-scope types
|
|
| 64 | + (use -fprint-potential-instances to see them all)
|
|
| 65 | 65 | • In the second argument of ‘traverse’, namely ‘(pure 42)’
|
| 66 | 66 | In a stmt of a 'do' block: traverse print (pure 42)
|
| 67 | 67 | In the expression:
|
| 68 | - do print (toList $ pure 21)
|
|
| 69 | - traverse print (pure 42) |
|
| 68 | + do print (toList $ pure 21)
|
|
| 69 | + traverse print (pure 42)
|
|
| 70 | + |
| ... | ... | @@ -3,23 +3,22 @@ RecordDotSyntaxFail11.hs:8:3: error: [GHC-39999] |
| 3 | 3 | prevents the constraint ‘(Show a0)’ from being solved.
|
| 4 | 4 | Probable fix: use a type annotation to specify what ‘a0’ should be.
|
| 5 | 5 | Potentially matching instances:
|
| 6 | - instance Show Ordering -- Defined in ‘GHC.Internal.Show’
|
|
| 7 | - instance Show Integer -- Defined in ‘GHC.Internal.Show’
|
|
| 8 | - ...plus 25 others
|
|
| 9 | - ...plus 13 instances involving out-of-scope types
|
|
| 10 | - (use -fprint-potential-instances to see them all)
|
|
| 6 | + instance Show Ordering -- Defined in ‘GHC.Internal.Show’
|
|
| 7 | + instance Show Integer -- Defined in ‘GHC.Internal.Show’
|
|
| 8 | + ...plus 25 others
|
|
| 9 | + ...plus 13 instances involving out-of-scope types
|
|
| 10 | + (use -fprint-potential-instances to see them all)
|
|
| 11 | 11 | • In the first argument of ‘($)’, namely ‘print’
|
| 12 | 12 | In a stmt of a 'do' block: print $ (.foo.bar.baz) a
|
| 13 | 13 | In the expression:
|
| 14 | - do let a = Foo {foo = ...}
|
|
| 15 | - print $ (.foo.bar.baz) a
|
|
| 14 | + do let a = Foo {foo = ...}
|
|
| 15 | + print $ (.foo.bar.baz) a
|
|
| 16 | 16 | |
| 17 | 17 | RecordDotSyntaxFail11.hs:8:11: error: [GHC-39999]
|
| 18 | 18 | • No instance for ‘GHC.Internal.Records.HasField "baz" Int a0’
|
| 19 | - arising from the expression (.foo.bar.baz)
|
|
| 19 | + arising from the expression (.foo.bar.baz)
|
|
| 20 | 20 | NB: ‘Int’ is not a record type.
|
| 21 | - • In the second argument of ‘($)’, namely ‘(.foo.bar.baz) a’
|
|
| 21 | + • In the expression: (.foo.bar.baz)
|
|
| 22 | + In the second argument of ‘($)’, namely ‘(.foo.bar.baz) a’
|
|
| 22 | 23 | In a stmt of a 'do' block: print $ (.foo.bar.baz) a
|
| 23 | - In the expression:
|
|
| 24 | - do let a = Foo {foo = ...}
|
|
| 25 | - print $ (.foo.bar.baz) a |
|
| 24 | + |
| 1 | 1 | T13393.hs:61:3: error: [GHC-39999]
|
| 2 | - • Ambiguous type variable ‘t0’ arising from a do statement
|
|
| 2 | + • Ambiguous type variable ‘t0’ arising from a use of ‘mapM’
|
|
| 3 | 3 | prevents the constraint ‘(Traversable t0)’ from being solved.
|
| 4 | 4 | Probable fix: use a type annotation to specify what ‘t0’ should be.
|
| 5 | 5 | Potentially matching instances:
|
| 1 | 1 | T14590.hs:4:13: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
|
| 2 | 2 | • Found hole: _ :: Int -> Int -> Int
|
| 3 | - • In the expression: (x `_`) y
|
|
| 3 | + • In the expression: x `_`
|
|
| 4 | + In the expression: (x `_`) y
|
|
| 4 | 5 | In an equation for ‘f1’: f1 x y = (x `_`) y
|
| 5 | 6 | • Relevant bindings include
|
| 6 | 7 | y :: Int (bound at T14590.hs:4:6)
|
| ... | ... | @@ -87,7 +88,8 @@ T14590.hs:4:13: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] |
| 87 | 88 | T14590.hs:5:13: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
|
| 88 | 89 | • Found hole: _a :: Int -> Int -> Int
|
| 89 | 90 | Or perhaps ‘_a’ is mis-spelled, or not in scope
|
| 90 | - • In the expression: (x `_a`) y
|
|
| 91 | + • In the expression: x `_a`
|
|
| 92 | + In the expression: (x `_a`) y
|
|
| 91 | 93 | In an equation for ‘f2’: f2 x y = (x `_a`) y
|
| 92 | 94 | • Relevant bindings include
|
| 93 | 95 | y :: Int (bound at T14590.hs:5:6)
|
| ... | ... | @@ -173,7 +175,8 @@ T14590.hs:5:13: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] |
| 173 | 175 | |
| 174 | 176 | T14590.hs:6:11: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
|
| 175 | 177 | • Found hole: _ :: Int -> Int -> Int
|
| 176 | - • In the expression: (`_` x) y
|
|
| 178 | + • In the expression: `_` x
|
|
| 179 | + In the expression: (`_` x) y
|
|
| 177 | 180 | In an equation for ‘f3’: f3 x y = (`_` x) y
|
| 178 | 181 | • Relevant bindings include
|
| 179 | 182 | y :: Int (bound at T14590.hs:6:6)
|
| ... | ... | @@ -260,7 +263,8 @@ T14590.hs:6:11: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] |
| 260 | 263 | T14590.hs:7:11: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
|
| 261 | 264 | • Found hole: _a :: Int -> Int -> Int
|
| 262 | 265 | Or perhaps ‘_a’ is mis-spelled, or not in scope
|
| 263 | - • In the expression: (`_a` x) y
|
|
| 266 | + • In the expression: `_a` x
|
|
| 267 | + In the expression: (`_a` x) y
|
|
| 264 | 268 | In an equation for ‘f4’: f4 x y = (`_a` x) y
|
| 265 | 269 | • Relevant bindings include
|
| 266 | 270 | y :: Int (bound at T14590.hs:7:6)
|
| ... | ... | @@ -22,6 +22,6 @@ T6069.hs:15:16: error: [GHC-83865] |
| 22 | 22 | Expected: ST s2 Int -> b2
|
| 23 | 23 | Actual: (forall s. ST s b2) -> b2
|
| 24 | 24 | • In the second argument of ‘(.)’, namely ‘runST’
|
| 25 | - In the expression: print . runST
|
|
| 25 | + In the first argument of ‘($)’, namely ‘(print . runST)’
|
|
| 26 | 26 | In the expression: (print . runST) $
|
| 27 | 27 |