summaryrefslogtreecommitdiff
path: root/compiler/GHC/Tc
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/GHC/Tc')
-rw-r--r--compiler/GHC/Tc/Gen/Bind.hs14
-rw-r--r--compiler/GHC/Tc/Gen/Match.hs4
-rw-r--r--compiler/GHC/Tc/Gen/Splice.hs2
-rw-r--r--compiler/GHC/Tc/Module.hs8
-rw-r--r--compiler/GHC/Tc/TyCl/Instance.hs4
-rw-r--r--compiler/GHC/Tc/Utils/Zonk.hs4
6 files changed, 18 insertions, 18 deletions
diff --git a/compiler/GHC/Tc/Gen/Bind.hs b/compiler/GHC/Tc/Gen/Bind.hs
index 4528bb5f1b..b61d265583 100644
--- a/compiler/GHC/Tc/Gen/Bind.hs
+++ b/compiler/GHC/Tc/Gen/Bind.hs
@@ -438,7 +438,7 @@ recursivePatSynErr loc binds
2 (vcat $ map pprLBind . bagToList $ binds)
where
pprLoc loc = parens (text "defined at" <+> ppr loc)
- pprLBind (L loc bind) = pprWithCommas ppr (collectHsBindBinders bind)
+ pprLBind (L loc bind) = pprWithCommas ppr (collectHsBindBinders CollNoDictBinders bind)
<+> pprLoc loc
tc_single :: forall thing.
@@ -488,7 +488,7 @@ mkEdges sig_fn binds
key_map :: NameEnv BKey -- Which binding it comes from
key_map = mkNameEnv [(bndr, key) | (L _ bind, key) <- keyd_binds
- , bndr <- collectHsBindBinders bind ]
+ , bndr <- collectHsBindBinders CollNoDictBinders bind ]
------------------------
tcPolyBinds :: TcSigFun -> TcPragEnv
@@ -531,7 +531,7 @@ tcPolyBinds sig_fn prag_fn rec_group rec_tc closed bind_list
; return result }
where
- binder_names = collectHsBindListBinders bind_list
+ binder_names = collectHsBindListBinders CollNoDictBinders bind_list
loc = foldr1 combineSrcSpans (map getLoc bind_list)
-- The mbinds have been dependency analysed and
-- may no longer be adjacent; so find the narrowest
@@ -1245,7 +1245,7 @@ tcMonoBinds is_rec sig_fn no_gen
, mbis ) }
where
- bndrs = collectPatBinders pat
+ bndrs = collectPatBinders CollNoDictBinders pat
-- GENERAL CASE
tcMonoBinds _ sig_fn no_gen binds
@@ -1407,7 +1407,7 @@ tcLhs sig_fn no_gen (PatBind { pat_lhs = pat, pat_rhs = grhss })
; return (TcPatBind mbis pat' grhss pat_ty) }
where
- bndr_names = collectPatBinders pat
+ bndr_names = collectPatBinders CollNoDictBinders pat
(nosig_names, sig_names) = partitionWith find_sig bndr_names
find_sig :: Name -> Either Name (Name, TcIdSigInfo)
@@ -1672,7 +1672,7 @@ decideGeneralisationPlan dflags lbinds closed sig_fn
partial_sig_mrs
= [ null theta
| TcIdSig (PartialSig { psig_hs_ty = hs_ty })
- <- mapMaybe sig_fn (collectHsBindListBinders lbinds)
+ <- mapMaybe sig_fn (collectHsBindListBinders CollNoDictBinders lbinds)
, let (L _ theta, _) = splitLHsQualTy (hsSigWcType hs_ty) ]
has_partial_sigs = not (null partial_sig_mrs)
@@ -1724,7 +1724,7 @@ isClosedBndrGroup type_env binds
in [(f, open_fvs)]
bindFvs (PatBind { pat_lhs = pat, pat_ext = fvs })
= let open_fvs = get_open_fvs fvs
- in [(b, open_fvs) | b <- collectPatBinders pat]
+ in [(b, open_fvs) | b <- collectPatBinders CollNoDictBinders pat]
bindFvs _
= []
diff --git a/compiler/GHC/Tc/Gen/Match.hs b/compiler/GHC/Tc/Gen/Match.hs
index 3d20305c88..fb8d58c520 100644
--- a/compiler/GHC/Tc/Gen/Match.hs
+++ b/compiler/GHC/Tc/Gen/Match.hs
@@ -1062,8 +1062,8 @@ tcApplicativeStmts ctxt pairs rhs_ty thing_inside
; return (ApplicativeArgMany x stmts' ret' pat' ctxt) }
get_arg_bndrs :: ApplicativeArg GhcTc -> [Id]
- get_arg_bndrs (ApplicativeArgOne { app_arg_pattern = pat }) = collectPatBinders pat
- get_arg_bndrs (ApplicativeArgMany { bv_pattern = pat }) = collectPatBinders pat
+ get_arg_bndrs (ApplicativeArgOne { app_arg_pattern = pat }) = collectPatBinders CollNoDictBinders pat
+ get_arg_bndrs (ApplicativeArgMany { bv_pattern = pat }) = collectPatBinders CollNoDictBinders pat
{- Note [ApplicativeDo and constraints]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
diff --git a/compiler/GHC/Tc/Gen/Splice.hs b/compiler/GHC/Tc/Gen/Splice.hs
index dfb6e4fe3e..2e55974f90 100644
--- a/compiler/GHC/Tc/Gen/Splice.hs
+++ b/compiler/GHC/Tc/Gen/Splice.hs
@@ -1153,7 +1153,7 @@ instance TH.Quasi TcM where
where
checkTopDecl :: HsDecl GhcPs -> TcM ()
checkTopDecl (ValD _ binds)
- = mapM_ bindName (collectHsBindBinders binds)
+ = mapM_ bindName (collectHsBindBinders CollNoDictBinders binds)
checkTopDecl (SigD _ _)
= return ()
checkTopDecl (AnnD _ _)
diff --git a/compiler/GHC/Tc/Module.hs b/compiler/GHC/Tc/Module.hs
index a77f9fe71a..e8073d763e 100644
--- a/compiler/GHC/Tc/Module.hs
+++ b/compiler/GHC/Tc/Module.hs
@@ -1493,7 +1493,7 @@ tcTopSrcDecls (HsGroup { hs_tyclds = tycl_decls,
; fo_fvs = foldr (\gre fvs -> fvs `addOneFV` greMangledName gre)
emptyFVs fo_gres
- ; sig_names = mkNameSet (collectHsValBinders hs_val_binds)
+ ; sig_names = mkNameSet (collectHsValBinders CollNoDictBinders hs_val_binds)
`minusNameSet` getTypeSigNames val_sigs
-- Extend the GblEnv with the (as yet un-zonked)
@@ -2363,8 +2363,8 @@ tcUserStmt rdr_stmt@(L loc _)
; opt_pr_flag <- goptM Opt_PrintBindResult
; let print_result_plan
| opt_pr_flag -- The flag says "print result"
- , [v] <- collectLStmtBinders gi_stmt -- One binder
- = [mk_print_result_plan gi_stmt v]
+ , [v] <- collectLStmtBinders CollNoDictBinders gi_stmt -- One binder
+ = [mk_print_result_plan gi_stmt v]
| otherwise = []
-- The plans are:
@@ -2414,7 +2414,7 @@ tcGhciStmts stmts
io_ret_ty = mkTyConApp ioTyCon [ret_ty]
tc_io_stmts = tcStmtsAndThen GhciStmtCtxt tcDoStmt stmts
(mkCheckExpType io_ret_ty)
- names = collectLStmtsBinders stmts
+ names = collectLStmtsBinders CollNoDictBinders stmts
-- OK, we're ready to typecheck the stmts
; traceTc "GHC.Tc.Module.tcGhciStmts: tc stmts" empty
diff --git a/compiler/GHC/Tc/TyCl/Instance.hs b/compiler/GHC/Tc/TyCl/Instance.hs
index 69656b41da..d4e8827d3d 100644
--- a/compiler/GHC/Tc/TyCl/Instance.hs
+++ b/compiler/GHC/Tc/TyCl/Instance.hs
@@ -1153,9 +1153,9 @@ tcInstDecls2 tycl_decls inst_decls
; let dm_binds = unionManyBags dm_binds_s
-- (b) instance declarations
- ; let dm_ids = collectHsBindsBinders dm_binds
+ ; let dm_ids = collectHsBindsBinders CollNoDictBinders dm_binds
-- Add the default method Ids (again)
- -- (they were arready added in GHC.Tc.TyCl.Utils.tcAddImplicits)
+ -- (they were already added in GHC.Tc.TyCl.Utils.tcAddImplicits)
-- See Note [Default methods in the type environment]
; inst_binds_s <- tcExtendGlobalValEnv dm_ids $
mapM tcInstDecl2 inst_decls
diff --git a/compiler/GHC/Tc/Utils/Zonk.hs b/compiler/GHC/Tc/Utils/Zonk.hs
index 9e2908fff8..b34e3269a1 100644
--- a/compiler/GHC/Tc/Utils/Zonk.hs
+++ b/compiler/GHC/Tc/Utils/Zonk.hs
@@ -531,7 +531,7 @@ zonkLocalBinds env (HsIPBinds x (IPBinds dict_binds binds )) = do
zonkRecMonoBinds :: ZonkEnv -> LHsBinds GhcTc -> TcM (ZonkEnv, LHsBinds GhcTc)
zonkRecMonoBinds env binds
= fixM (\ ~(_, new_binds) -> do
- { let env1 = extendIdZonkEnvRec env (collectHsBindsBinders new_binds)
+ { let env1 = extendIdZonkEnvRec env (collectHsBindsBinders CollNoDictBinders new_binds)
; binds' <- zonkMonoBinds env1 binds
; return (env1, binds') })
@@ -580,7 +580,7 @@ zonk_bind env (AbsBinds { abs_tvs = tyvars, abs_ev_vars = evs
; (env2, new_ev_binds) <- zonkTcEvBinds_s env1 ev_binds
; (new_val_bind, new_exports) <- fixM $ \ ~(new_val_binds, _) ->
do { let env3 = extendIdZonkEnvRec env2 $
- collectHsBindsBinders new_val_binds
+ collectHsBindsBinders CollNoDictBinders new_val_binds
; new_val_binds <- mapBagM (zonk_val_bind env3) val_binds
; new_exports <- mapM (zonk_export env3) exports
; return (new_val_binds, new_exports) }