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

Commits:

2 changed files:

Changes:

  • compiler/GHC/Tc/Gen/Head.hs
    ... ... @@ -1107,12 +1107,11 @@ add_expr_ctxt e thing_inside
    1107 1107
        -- Flip error ctxt into expansion mode
    
    1108 1108
     
    
    1109 1109
           _ -> addErrCtxt (ExprCtxt e) thing_inside
    
    1110
    -  -- no op in generated code
    
    1111 1110
     
    
    1112 1111
     
    
    1113 1112
     addLExprCtxt :: SrcSpan -> HsExpr GhcRn -> TcRn a -> TcRn a
    
    1114 1113
     addLExprCtxt lspan e thing_inside
    
    1115 1114
       | not (isGeneratedSrcSpan lspan)
    
    1116 1115
       = setSrcSpan lspan $ add_expr_ctxt e thing_inside
    
    1117
    -  | otherwise
    
    1116
    +  | otherwise   -- no op in generated code
    
    1118 1117
       = thing_inside

  • compiler/GHC/Tc/Gen/Match.hs
    ... ... @@ -42,7 +42,7 @@ import GHC.Prelude
    42 42
     import {-# SOURCE #-}   GHC.Tc.Gen.Expr( tcSyntaxOp, tcInferRho, tcInferRhoFRRNC
    
    43 43
                                            , tcMonoLExprNC, tcMonoLExpr, tcExpr
    
    44 44
                                            , tcCheckMonoExpr, tcCheckMonoExprNC
    
    45
    -                                       , tcCheckPolyExpr, tcPolyLExpr )
    
    45
    +                                       , tcCheckPolyExpr, tcPolyExpr )
    
    46 46
     
    
    47 47
     import GHC.Rename.Utils ( bindLocalNames )
    
    48 48
     import GHC.Tc.Errors.Types
    
    ... ... @@ -420,10 +420,15 @@ tcDoStmts mDoExpr ss@(L _ stmts) res_ty
    420 420
             }
    
    421 421
     
    
    422 422
     tcBody :: LHsExpr GhcRn -> ExpRhoType -> TcM (LHsExpr GhcTc)
    
    423
    -tcBody body res_ty
    
    424
    -  = do  { traceTc "tcBody" (ppr res_ty)
    
    425
    -        ; tcPolyLExpr body res_ty
    
    426
    -        }
    
    423
    +tcBody (L lspan e) res_ty
    
    424
    +  = L lspan <$>
    
    425
    +      do  { traceTc "tcBody" (ppr res_ty)
    
    426
    +          ; setSrcSpanA lspan $
    
    427
    +              addErrCtxt (ExprCtxt e) $
    
    428
    +               -- We want the right hand side of a match or an equation
    
    429
    +               -- to always get printed
    
    430
    +              tcPolyExpr e res_ty)
    
    431
    +          }
    
    427 432
     
    
    428 433
     {-
    
    429 434
     ************************************************************************