Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC

Commits:

5 changed files:

Changes:

  • compiler/GHC/Tc/Gen/App.hs
    ... ... @@ -426,7 +426,6 @@ tcApp rn_expr exp_res_ty
    426 426
            -- If it is generated code location span, blame it on the
    
    427 427
            -- source code origin stored in the lclEnv.
    
    428 428
            -- See Note [Error contexts in generated code]
    
    429
    -       -- See Note [Error Context Stack]
    
    430 429
            ; code_orig <- getSrcCodeOrigin
    
    431 430
            ; let fun_orig | not (isGeneratedSrcSpan fun_lspan)
    
    432 431
                           = exprCtOrigin rn_fun
    

  • compiler/GHC/Tc/Gen/Do.hs
    ... ... @@ -445,7 +445,7 @@ It stores the original statement (with location) and the expanded expression
    445 445
         as precise as possible, and not just blame the complete `do`-block.
    
    446 446
         Thus, when we typecheck the application `(>>) e1`, we push the "In the stmt of do block e1" with
    
    447 447
         the source location of `e1` in the error context stack as we walk inside an `ExpandedThingRn`.
    
    448
    -    See also Note [splitHsApps] and Note [Error Context Stack]
    
    448
    +    See also Note [splitHsApps]
    
    449 449
     
    
    450 450
       * After the expanded expression of a `do`-statement is typechecked
    
    451 451
         and before moving to the next statement of the `do`-block, we need to first pop the top
    

  • compiler/GHC/Tc/Gen/Head.hs
    ... ... @@ -1090,14 +1090,26 @@ add_expr_ctxt e thing_inside
    1090 1090
        --    f x = _
    
    1091 1091
        -- when we don't want to say "In the expression: _",
    
    1092 1092
        -- because it is mentioned in the error message itself
    
    1093
    +
    
    1093 1094
           HsPar _ e -> add_expr_ctxt (unLoc e) thing_inside
    
    1094
    -      -- We don't want to say 'In the expression (e)',
    
    1095
    -      -- we just want to say 'In the expression, 'e'
    
    1096
    -      -- which will be handeled by the recursive call in thing_inside
    
    1097
    -      -- This may be a little inefficient with nested parens exprs, eg. (((e)))
    
    1098
    -      -- But it should be okay as I do not expect too many parens to be nested consecutively
    
    1095
    +   -- We don't want to say 'In the expression (e)',
    
    1096
    +   -- we just want to say 'In the expression, 'e'
    
    1097
    +   -- which will be handeled by the recursive call in thing_inside
    
    1098
    +   -- This may be a little inefficient with nested parens exprs, eg. (((e)))
    
    1099
    +   -- But it should be okay as I do not expect too many parens to be nested consecutively
    
    1100
    +
    
    1101
    +      ExprWithTySig _ (L _ e') _
    
    1102
    +        | XExpr (ExpandedThingRn o _) <- e' -> addExpansionErrCtxt o (ExprCtxt e)
    
    1103
    +                                                  thing_inside
    
    1104
    +   -- There is a special case for expressions with signatures to avoid having too verbose
    
    1105
    +   -- error context. So here we flip the ErrCtxt state to expanded if the expression is expanded.
    
    1106
    +   -- c.f. RecordDotSyntaxFail9
    
    1107
    +
    
    1099 1108
           XExpr (ExpandedThingRn o _) -> addExpansionErrCtxt o (srcCodeOriginErrCtxMsg o) thing_inside
    
    1100
    -      _ -> addErrCtxt (ExprCtxt e) thing_inside -- no op in generated code
    
    1109
    +   -- Flip error ctxt into expansion mode
    
    1110
    +
    
    1111
    +      _ -> addErrCtxt (ExprCtxt e) thing_inside
    
    1112
    +  -- no op in generated code
    
    1101 1113
     
    
    1102 1114
     
    
    1103 1115
     addLExprCtxt :: SrcSpan -> HsExpr GhcRn -> TcRn a -> TcRn a
    

  • compiler/GHC/Tc/Types/LclEnv.hs
    ... ... @@ -112,7 +112,7 @@ This data structure keeps track of two things:
    112 112
     -}
    
    113 113
     
    
    114 114
     
    
    115
    --- See Note [Error Context Stack]
    
    115
    +-- See Note [ErrCtxtStack Manipulation]
    
    116 116
     type ErrCtxtStack = [ErrCtxt]
    
    117 117
     
    
    118 118
     -- | Get the original source code
    
    ... ... @@ -125,7 +125,7 @@ get_src_code_origin _ = Nothing
    125 125
     data TcLclCtxt
    
    126 126
       = TcLclCtxt {
    
    127 127
             tcl_loc         :: RealSrcSpan,     -- Source span
    
    128
    -        tcl_err_ctxt    :: ErrCtxtStack,    -- See Note [Error Context Stack]
    
    128
    +        tcl_err_ctxt    :: ErrCtxtStack,    -- See Note [ErrCtxtStack Manipulation]
    
    129 129
             tcl_tclvl       :: TcLevel,
    
    130 130
             tcl_bndrs       :: TcBinderStack,   -- Used for reporting relevant bindings,
    
    131 131
                                                 -- and for tidying type
    
    ... ... @@ -204,7 +204,7 @@ getLclEnvSrcCodeOrigin = get_src_code_origin . tcl_err_ctxt . tcl_lcl_ctxt
    204 204
     setLclEnvSrcCodeOrigin :: ErrCtxt -> TcLclEnv -> TcLclEnv
    
    205 205
     setLclEnvSrcCodeOrigin ec = modifyLclCtxt (setLclCtxtSrcCodeOrigin ec)
    
    206 206
     
    
    207
    --- See Note [ErrCtxt Stack Manipulation]
    
    207
    +-- See Note [ErrCtxtStack Manipulation]
    
    208 208
     setLclCtxtSrcCodeOrigin :: ErrCtxt -> TcLclCtxt -> TcLclCtxt
    
    209 209
     setLclCtxtSrcCodeOrigin ec lclCtxt
    
    210 210
       | MkErrCtxt (ExpansionCodeCtxt _) _ : ecs <- tcl_err_ctxt lclCtxt
    

  • compiler/GHC/Tc/Utils/Monad.hs
    ... ... @@ -1089,20 +1089,9 @@ getSrcCodeOrigin =
    1089 1089
            then getLclEnvSrcCodeOrigin <$> getLclEnv
    
    1090 1090
            else return Nothing
    
    1091 1091
     
    
    1092
    -
    
    1093
    --- | Mark the inner computation as being done inside generated code.
    
    1094
    ---
    
    1095
    --- See Note [Error contexts in generated code]
    
    1096
    --- See Note [Error Context Stack]
    
    1097
    --- setInGeneratedCode :: SrcCodeOrigin -> TcRn a -> TcRn a
    
    1098
    --- setInGeneratedCode sco thing_inside =
    
    1099
    ---   -- updLclCtxt setLclCtxtInGenCode $
    
    1100
    ---   updLclCtxt (setLclCtxtSrcCodeOrigin sco) thing_inside
    
    1101
    -
    
    1102 1092
     setSrcSpanA :: EpAnn ann -> TcRn a -> TcRn a
    
    1103 1093
     setSrcSpanA l = setSrcSpan (locA l)
    
    1104 1094
     
    
    1105
    -
    
    1106 1095
     addLocM :: (HasLoc t) => (a -> TcM b) -> GenLocated t a -> TcM b
    
    1107 1096
     addLocM fn (L loc a) = setSrcSpan (getHasLoc loc) $ fn a
    
    1108 1097
     
    
    ... ... @@ -1327,7 +1316,7 @@ So, it's better to do a `setSrcSpan` /before/ `addErrCtxt`.
    1327 1316
     more discussion of this fancy footwork
    
    1328 1317
     - See Note [Generated code and pattern-match checking] in `GHC.Types.Basic` for the
    
    1329 1318
     relation with pattern-match checks
    
    1330
    -- See Note [Error Context Stack] in `GHC.Tc.Types.LclEnv` for info about `ErrCtxtStack`
    
    1319
    +- See Note [ErrCtxtStack Manipulation] in `GHC.Tc.Types.LclEnv` for info about `ErrCtxtStack`
    
    1331 1320
     -}
    
    1332 1321
     
    
    1333 1322
     getErrCtxt :: TcM [ErrCtxt]