Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC
Commits:
-
744f5ea2
by Apoorv Ingle at 2025-12-22T11:40:39-06:00
-
9e0ddc42
by Apoorv Ingle at 2026-01-09T12:09:25+01:00
7 changed files:
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Utils/Monad.hs
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail10.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail13.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail8.stderr
Changes:
| ... | ... | @@ -81,6 +81,8 @@ import qualified GHC.Data.Strict as Strict |
| 81 | 81 | |
| 82 | 82 | |
| 83 | 83 | import Language.Haskell.Syntax.Basic (FieldLabelString(..))
|
| 84 | +import Language.Haskell.Syntax (HsExpr (RecordUpd, HsGetField, HsProjection))
|
|
| 85 | +import GHC.Hs.Expr (SrcCodeOrigin(..))
|
|
| 84 | 86 | |
| 85 | 87 | import Control.Monad ( unless, when, foldM, forM_ )
|
| 86 | 88 | import Data.Bifunctor ( bimap )
|
| ... | ... | @@ -2685,6 +2687,10 @@ isHasFieldOrigin = \case |
| 2685 | 2687 | RecordUpdOrigin {} -> True
|
| 2686 | 2688 | RecordFieldProjectionOrigin {} -> True
|
| 2687 | 2689 | GetFieldOrigin {} -> True
|
| 2690 | + ExpansionOrigin (OrigExpr e)
|
|
| 2691 | + | HsGetField{} <- e -> True
|
|
| 2692 | + | RecordUpd{} <- e -> True
|
|
| 2693 | + | HsProjection{} <- e -> True
|
|
| 2688 | 2694 | _ -> False
|
| 2689 | 2695 | |
| 2690 | 2696 | -----------------------
|
| ... | ... | @@ -958,7 +958,7 @@ addArgCtxt arg_no (app_head, app_head_lspan) (L arg_loc arg) thing_inside |
| 958 | 958 | , ppr arg
|
| 959 | 959 | , ppr arg_no])
|
| 960 | 960 | ; setSrcSpanA arg_loc $
|
| 961 | - mkNthFunArgErrCtxt app_head arg arg_no $
|
|
| 961 | + addNthFunArgErrCtxt app_head arg arg_no $
|
|
| 962 | 962 | thing_inside
|
| 963 | 963 | }
|
| 964 | 964 | | otherwise
|
| ... | ... | @@ -971,8 +971,8 @@ addArgCtxt arg_no (app_head, app_head_lspan) (L arg_loc arg) thing_inside |
| 971 | 971 | thing_inside
|
| 972 | 972 | }
|
| 973 | 973 | where
|
| 974 | - mkNthFunArgErrCtxt :: HsExpr GhcRn -> HsExpr GhcRn -> Int -> TcM a -> TcM a
|
|
| 975 | - mkNthFunArgErrCtxt app_head arg arg_no thing_inside
|
|
| 974 | + addNthFunArgErrCtxt :: HsExpr GhcRn -> HsExpr GhcRn -> Int -> TcM a -> TcM a
|
|
| 975 | + addNthFunArgErrCtxt app_head arg arg_no thing_inside
|
|
| 976 | 976 | | XExpr (ExpandedThingRn o _) <- arg
|
| 977 | 977 | = addExpansionErrCtxt o (FunAppCtxt (FunAppCtxtExpr app_head arg) arg_no) $
|
| 978 | 978 | thing_inside
|
| ... | ... | @@ -765,7 +765,7 @@ tcXExpr :: XXExprGhcRn -> ExpRhoType -> TcM (HsExpr GhcTc) |
| 765 | 765 | tcXExpr (ExpandedThingRn o e) res_ty
|
| 766 | 766 | = mkExpandedTc o <$> -- necessary for hpc ticks
|
| 767 | 767 | -- Need to call tcExpr and not tcApp
|
| 768 | - -- as e can be let statements which tcApp cannot gracefully handle
|
|
| 768 | + -- as e can be let statement which tcApp cannot gracefully handle
|
|
| 769 | 769 | tcExpr e res_ty
|
| 770 | 770 | |
| 771 | 771 | -- For record selection, same as HsVar case
|
| ... | ... | @@ -1079,7 +1079,7 @@ setSrcSpan :: SrcSpan -> TcRn a -> TcRn a |
| 1079 | 1079 | setSrcSpan (RealSrcSpan loc _) thing_inside
|
| 1080 | 1080 | = updLclCtxt (\env -> env { tcl_loc = loc }) thing_inside
|
| 1081 | 1081 | |
| 1082 | -setSrcSpan (UnhelpfulSpan _) thing_inside
|
|
| 1082 | +setSrcSpan loc thing_inside
|
|
| 1083 | 1083 | = thing_inside
|
| 1084 | 1084 | |
| 1085 | 1085 | getSrcCodeOrigin :: TcRn (Maybe SrcCodeOrigin)
|
| 1 | 1 | RecordDotSyntaxFail10.hs:40:11: error: [GHC-39999]
|
| 2 | 2 | • No instance for ‘HasField "quux" Quux String’
|
| 3 | + arising from a record update
|
|
| 3 | 4 | NB: ‘HasField’ is not the built-in ‘GHC.Internal.Records.HasField’ class.
|
| 4 | 5 | • In the second argument of ‘($)’, namely ‘a {foo.bar.baz.quux}’
|
| 5 | - In a stmt of a 'do' block: print $ a {foo.bar.baz.quux}
|
|
| 6 | 6 | In the expression:
|
| 7 | - do let a = Foo {foo = ...}
|
|
| 8 | - let quux = "Expecto patronum!"
|
|
| 9 | - print $ a {foo.bar.baz.quux} |
|
| 7 | + do let a = Foo {foo = ...}
|
|
| 8 | + let quux = "Expecto patronum!"
|
|
| 9 | + print $ a {foo.bar.baz.quux}
|
|
| 10 | + In an equation for ‘main’:
|
|
| 11 | + main
|
|
| 12 | + = do let a = ...
|
|
| 13 | + let quux = "Expecto patronum!"
|
|
| 14 | + print $ a {foo.bar.baz.quux}
|
|
| 15 | + |
| ... | ... | @@ -3,8 +3,11 @@ RecordDotSyntaxFail13.hs:26:11: error: [GHC-39999] |
| 3 | 3 | arising from a record update
|
| 4 | 4 | NB: ‘HasField’ is not the built-in ‘GHC.Internal.Records.HasField’ class.
|
| 5 | 5 | • In the second argument of ‘($)’, namely ‘a {foo}’
|
| 6 | - In a stmt of a 'do' block: print $ a {foo}
|
|
| 7 | 6 | In the expression:
|
| 8 | 7 | do let a = Foo {foo = 12}
|
| 9 | 8 | print $ a {foo}
|
| 9 | + In an equation for ‘main’:
|
|
| 10 | + main
|
|
| 11 | + = do let a = ...
|
|
| 12 | + print $ a {foo}
|
|
| 10 | 13 |
| ... | ... | @@ -3,7 +3,6 @@ RecordDotSyntaxFail8.hs:47:17: error: [GHC-39999] |
| 3 | 3 | arising from selecting the field ‘quux1’
|
| 4 | 4 | NB: ‘HasField’ is not the built-in ‘GHC.Internal.Records.HasField’ class.
|
| 5 | 5 | • In the second argument of ‘($)’, namely ‘....bar.baz.quux1’
|
| 6 | - In a stmt of a 'do' block: print @Quux $ ....baz.quux1
|
|
| 7 | 6 | In the expression:
|
| 8 | 7 | do let a = Foo {foo = ...}
|
| 9 | 8 | print @Quux $ ....quux1
|
| ... | ... | @@ -11,13 +10,19 @@ RecordDotSyntaxFail8.hs:47:17: error: [GHC-39999] |
| 11 | 10 | print @Quux $ b.quux2
|
| 12 | 11 | let c = Foo {foo = ...}
|
| 13 | 12 | ...
|
| 13 | + In an equation for ‘main’:
|
|
| 14 | + main
|
|
| 15 | + = do let a = ...
|
|
| 16 | + print @Quux $ ....quux1
|
|
| 17 | + let b = myQuux
|
|
| 18 | + print @Quux $ b.quux2
|
|
| 19 | + ...
|
|
| 14 | 20 | |
| 15 | 21 | RecordDotSyntaxFail8.hs:50:17: error: [GHC-39999]
|
| 16 | 22 | • No instance for ‘HasField "quux2" Quux Quux’
|
| 17 | 23 | arising from selecting the field ‘quux2’
|
| 18 | 24 | NB: ‘HasField’ is not the built-in ‘GHC.Internal.Records.HasField’ class.
|
| 19 | 25 | • In the second argument of ‘($)’, namely ‘b.quux2’
|
| 20 | - In a stmt of a 'do' block: print @Quux $ b.quux2
|
|
| 21 | 26 | In the expression:
|
| 22 | 27 | do let a = Foo {foo = ...}
|
| 23 | 28 | print @Quux $ ....quux1
|
| ... | ... | @@ -25,12 +30,31 @@ RecordDotSyntaxFail8.hs:50:17: error: [GHC-39999] |
| 25 | 30 | print @Quux $ b.quux2
|
| 26 | 31 | let c = Foo {foo = ...}
|
| 27 | 32 | ...
|
| 33 | + In an equation for ‘main’:
|
|
| 34 | + main
|
|
| 35 | + = do let a = ...
|
|
| 36 | + print @Quux $ ....quux1
|
|
| 37 | + let b = myQuux
|
|
| 38 | + print @Quux $ b.quux2
|
|
| 39 | + ...
|
|
| 28 | 40 | |
| 29 | 41 | RecordDotSyntaxFail8.hs:53:17: error: [GHC-39999]
|
| 30 | - • No instance for ‘HasField "quux3" Quux r0’
|
|
| 42 | + • No instance for ‘HasField "quux3" Quux a0’
|
|
| 31 | 43 | arising from selecting the field ‘quux3’
|
| 32 | 44 | NB: ‘HasField’ is not the built-in ‘GHC.Internal.Records.HasField’ class.
|
| 33 | 45 | • In the expression: ....bar.baz.quux3
|
| 34 | - In the second argument of ‘($)’, namely ‘....baz.quux3.wob’
|
|
| 35 | - In a stmt of a 'do' block: print @Bool $ ....quux3.wob
|
|
| 46 | + In the expression:
|
|
| 47 | + do let a = Foo {foo = ...}
|
|
| 48 | + print @Quux $ ....quux1
|
|
| 49 | + let b = myQuux
|
|
| 50 | + print @Quux $ b.quux2
|
|
| 51 | + let c = Foo {foo = ...}
|
|
| 52 | + ...
|
|
| 53 | + In an equation for ‘main’:
|
|
| 54 | + main
|
|
| 55 | + = do let a = ...
|
|
| 56 | + print @Quux $ ....quux1
|
|
| 57 | + let b = myQuux
|
|
| 58 | + print @Quux $ b.quux2
|
|
| 59 | + ...
|
|
| 36 | 60 |