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

Commits:

3 changed files:

Changes:

  • compiler/GHC/Tc/Gen/App.hs
    ... ... @@ -536,7 +536,7 @@ checkResultTy :: DeepSubsumptionFlag
    536 536
                                 --   expose foralls, but maybe not /deeply/ instantiated
    
    537 537
                   -> ExpRhoType -- Expected type; this is deeply skolemised
    
    538 538
                   -> TcM HsWrapper
    
    539
    -checkResultTy ds_flag rn_expr (fun, _) _inst_args app_res_rho (Infer inf_res)
    
    539
    +checkResultTy ds_flag rn_expr _ _ app_res_rho (Infer inf_res)
    
    540 540
       = fillInferResult ds_flag (exprCtOrigin rn_expr) app_res_rho inf_res
    
    541 541
     
    
    542 542
     checkResultTy ds_flag rn_expr (tc_fun, fun_loc) inst_args app_res_rho (Check res_ty)
    

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

  • 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, tcPolyExpr )
    
    45
    +                                       , tcCheckPolyExpr, tcPolyLExpr )
    
    46 46
     
    
    47 47
     import GHC.Rename.Utils ( bindLocalNames )
    
    48 48
     import GHC.Tc.Errors.Types
    
    ... ... @@ -420,15 +420,10 @@ tcDoStmts mDoExpr ss@(L _ stmts) res_ty
    420 420
             }
    
    421 421
     
    
    422 422
     tcBody :: LHsExpr GhcRn -> ExpRhoType -> TcM (LHsExpr GhcTc)
    
    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 in the error context
    
    430
    -              tcPolyExpr e res_ty
    
    431
    -          }
    
    423
    +tcBody body res_ty
    
    424
    +  = do  { traceTc "tcBody" (ppr res_ty)
    
    425
    +        ; tcPolyLExpr body res_ty
    
    426
    +        }
    
    432 427
     
    
    433 428
     {-
    
    434 429
     ************************************************************************