[Git][ghc/ghc][wip/T26315] Fix unused variables

Simon Peyton Jones pushed to branch wip/T26315 at Glasgow Haskell Compiler / GHC Commits: 4b903d4d by Simon Peyton Jones at 2025-09-02T08:30:11+01:00 Fix unused variables - - - - - 1 changed file: - compiler/GHC/Tc/Solver/Dict.hs Changes: ===================================== compiler/GHC/Tc/Solver/Dict.hs ===================================== @@ -767,11 +767,10 @@ and Given/instance fundeps entirely. tryInertDicts :: DictCt -> SolverStage () tryInertDicts dict_ct = Stage $ do { inerts <- getInertCans - ; mode <- getTcSMode - ; try_inert_dicts mode inerts dict_ct } + ; try_inert_dicts inerts dict_ct } -try_inert_dicts :: TcSMode -> InertCans -> DictCt -> TcS (StopOrContinue ()) -try_inert_dicts mode inerts dict_w@(DictCt { di_ev = ev_w, di_cls = cls, di_tys = tys }) +try_inert_dicts :: InertCans -> DictCt -> TcS (StopOrContinue ()) +try_inert_dicts inerts dict_w@(DictCt { di_ev = ev_w, di_cls = cls, di_tys = tys }) | Just dict_i <- lookupInertDict inerts cls tys , let ev_i = dictCtEvidence dict_i loc_i = ctEvLoc ev_i @@ -866,8 +865,7 @@ try_instances inerts work_item@(DictCt { di_ev = ev, di_cls = cls | otherwise -- Wanted, but not cached = do { dflags <- getDynFlags - ; mode <- getTcSMode - ; lkup_res <- matchClassInst dflags mode inerts cls xis dict_loc + ; lkup_res <- matchClassInst dflags inerts cls xis dict_loc ; case lkup_res of OneInst { cir_what = what } -> do { let is_local_given = case what of { LocalInstance -> True; _ -> False } @@ -925,10 +923,10 @@ checkInstanceOK loc what pred | otherwise = loc -matchClassInst :: DynFlags -> TcSMode -> InertSet +matchClassInst :: DynFlags -> InertSet -> Class -> [Type] -> CtLoc -> TcS ClsInstResult -matchClassInst dflags mode inerts clas tys loc +matchClassInst dflags inerts clas tys loc -- First check whether there is an in-scope Given that could -- match this constraint. In that case, do not use any instance -- whether top level, or local quantified constraints. @@ -939,7 +937,7 @@ matchClassInst dflags mode inerts clas tys loc -- It is always safe to unpack constraint tuples -- And if we don't do so, we may never solve it at all -- See Note [Solving tuple constraints] - , not (noMatchableGivenDicts mode inerts loc clas tys) + , not (noMatchableGivenDicts inerts loc clas tys) = do { traceTcS "Delaying instance application" $ vcat [ text "Work item:" <+> pprClassPred clas tys ] ; return NotSure } @@ -970,8 +968,8 @@ matchClassInst dflags mode inerts clas tys loc -- potentially, match the given class constraint. This is used when checking to see if a -- Given might overlap with an instance. See Note [Instance and Given overlap] -- in GHC.Tc.Solver.Dict -noMatchableGivenDicts :: TcSMode -> InertSet -> CtLoc -> Class -> [TcType] -> Bool -noMatchableGivenDicts mode inerts@(IS { inert_cans = inert_cans }) loc_w clas tys +noMatchableGivenDicts :: InertSet -> CtLoc -> Class -> [TcType] -> Bool +noMatchableGivenDicts inerts@(IS { inert_cans = inert_cans }) loc_w clas tys = not $ anyBag matchable_given $ findDictsByClass (inert_dicts inert_cans) clas where View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4b903d4d1e4a9d95264339305661a291... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4b903d4d1e4a9d95264339305661a291... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Simon Peyton Jones (@simonpj)