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

Commits:

3 changed files:

Changes:

  • compiler/GHC/Rename/Expr.hs
    ... ... @@ -512,7 +512,7 @@ rnExpr (ExplicitList _ exps)
    512 512
            ; let rn_list  = ExplicitList noExtField exps'
    
    513 513
                  lit_n    = mkIntegralLit (length exps)
    
    514 514
                  hs_lit   = genHsIntegralLit lit_n
    
    515
    -             exp_list = genHsApps' (L (noAnnSrcSpan loc) from_list_n_name) [hs_lit, wrapGenSpan rn_list]
    
    515
    +             exp_list = genHsApps' (wrapGenSpan from_list_n_name) [hs_lit, wrapGenSpan rn_list]
    
    516 516
            ; return ( mkExpandedExpr rn_list exp_list
    
    517 517
                     , fvs `plusFV` fvs') } }
    
    518 518
     
    

  • compiler/GHC/Tc/Gen/Expr.hs
    ... ... @@ -334,7 +334,7 @@ tcExpr e@(HsLit x lit) res_ty
    334 334
            ; tcWrapResult e (HsLit x (convertLit lit)) lit_ty res_ty }
    
    335 335
     
    
    336 336
     tcExpr (HsPar x expr) res_ty
    
    337
    -  = do { expr' <- tcMonoLExprNC expr res_ty
    
    337
    +  = do { expr' <- tcMonoLExpr expr res_ty
    
    338 338
            ; return (HsPar x expr') }
    
    339 339
     
    
    340 340
     tcExpr (HsPragE x prag expr) res_ty
    

  • compiler/GHC/Tc/Gen/Head.hs
    ... ... @@ -1090,19 +1090,18 @@ 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
    -      HsPar{} -> thing_inside
    
    1093
    +      HsPar _ e -> add_expr_ctxt (unLoc e) thing_inside
    
    1094 1094
           -- We don't want to say 'In the expression (e)',
    
    1095 1095
           -- we just want to say 'In the expression, 'e'
    
    1096 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
    
    1097 1099
           XExpr (ExpandedThingRn o _) -> addExpansionErrCtxt o (srcCodeOriginErrCtxMsg o) thing_inside
    
    1098 1100
           _ -> addErrCtxt (ExprCtxt e) thing_inside -- no op in generated code
    
    1099 1101
     
    
    1100 1102
     
    
    1101 1103
     addLExprCtxt :: SrcSpan -> HsExpr GhcRn -> TcRn a -> TcRn a
    
    1102 1104
     addLExprCtxt lspan e thing_inside
    
    1103
    -  | not (isGeneratedSrcSpan lspan)
    
    1104
    -  , (HsPar _ e') <- e
    
    1105
    -  = setSrcSpan lspan $ add_expr_ctxt (unLoc e') thing_inside
    
    1106 1105
       | not (isGeneratedSrcSpan lspan)
    
    1107 1106
       = setSrcSpan lspan $ add_expr_ctxt e thing_inside
    
    1108 1107
       | otherwise