Skip to content
Snippets Groups Projects
Commit adbaa9a9 authored by Ryan Scott's avatar Ryan Scott Committed by Marge Bot
Browse files

Remove unnecessary extendTyVarEnvFVRn function

The `extendTyVarEnvFVRn` function does the exact same thing as
`bindLocalNamesFV`. I see no meaningful distinction between the two functions,
so let's just remove the former (which is only used in a handful of places) in
favor of the latter.

Historical note: `extendTyVarEnvFVRn` and `bindLocalNamesFV` used to be
distinct functions, but their implementations were synchronized in 2004 as a
part of commit 20e39e0e.
parent 6a375b53
No related branches found
No related tags found
No related merge requests found
......@@ -41,7 +41,7 @@ import GHC.Rename.Pat
import GHC.Rename.Names
import GHC.Rename.Env
import GHC.Rename.Fixity
import GHC.Rename.Utils ( HsDocContext(..), mapFvRn, extendTyVarEnvFVRn
import GHC.Rename.Utils ( HsDocContext(..), mapFvRn
, checkDupRdrNames, checkDupRdrNamesN, warnUnusedLocalBinds
, checkUnusedRecordWildcard
, checkDupAndShadowedNames, bindLocalNamesFV
......@@ -869,7 +869,7 @@ rnMethodBinds is_cls_decl cls ktv_names binds sigs
sig_ctxt | is_cls_decl = ClsDeclCtxt cls
| otherwise = InstDeclCtxt bound_nms
; (spec_inst_prags', sip_fvs) <- renameSigs sig_ctxt spec_inst_prags
; (other_sigs', sig_fvs) <- extendTyVarEnvFVRn ktv_names $
; (other_sigs', sig_fvs) <- bindLocalNamesFV ktv_names $
renameSigs sig_ctxt other_sigs
-- Rename the bindings RHSs. Again there's an issue about whether the
......
......@@ -32,7 +32,7 @@ import GHC.Rename.Env
import GHC.Rename.Utils ( HsDocContext(..), mapFvRn, bindLocalNames
, checkDupRdrNamesN, bindLocalNamesFV
, checkShadowedRdrNames, warnUnusedTypePatterns
, extendTyVarEnvFVRn, newLocalBndrsRn
, newLocalBndrsRn
, withHsDocContext, noNestedForallsContextsErr
, addNoNestedForallsContextsErr, checkInferredVars )
import GHC.Rename.Unbound ( mkUnboundName, notInScopeErr )
......@@ -628,7 +628,7 @@ rnClsInstDecl (ClsInstDecl { cid_poly_ty = inst_ty, cid_binds = mbinds
-- Both need to have the instance type variables in scope
; traceRn "rnSrcInstDecl" (ppr inst_ty' $$ ppr ktv_names)
; ((ats', adts'), more_fvs)
<- extendTyVarEnvFVRn ktv_names $
<- bindLocalNamesFV ktv_names $
do { (ats', at_fvs) <- rnATInstDecls rnTyFamInstDecl cls ktv_names ats
; (adts', adt_fvs) <- rnATInstDecls rnDataFamInstDecl cls ktv_names adts
; return ( (ats', adts'), at_fvs `plusFV` adt_fvs) }
......@@ -2043,7 +2043,7 @@ rnLDerivStrategy doc mds thing_inside
-- (Wrinkle: Derived instances) in GHC.Hs.Type.
addNoNestedForallsContextsErr doc
(quotes (text "via") <+> text "type") via_body
(thing, fvs2) <- extendTyVarEnvFVRn via_tvs thing_inside
(thing, fvs2) <- bindLocalNamesFV via_tvs thing_inside
pure (ViaStrategy via_ty', thing, fvs1 `plusFV` fvs2)
inf_err = Just (text "Inferred type variables are not allowed")
......
......@@ -25,7 +25,7 @@ module GHC.Rename.Utils (
bindLocalNames, bindLocalNamesFV,
addNameClashErrRn, extendTyVarEnvFVRn,
addNameClashErrRn,
checkInferredVars,
noNestedForallsContextsErr, addNoNestedForallsContextsErr
......@@ -101,11 +101,6 @@ bindLocalNamesFV names enclosed_scope
= do { (result, fvs) <- bindLocalNames names enclosed_scope
; return (result, delFVs names fvs) }
-------------------------------------
extendTyVarEnvFVRn :: [Name] -> RnM (a, FreeVars) -> RnM (a, FreeVars)
extendTyVarEnvFVRn tyvars thing_inside = bindLocalNamesFV tyvars thing_inside
-------------------------------------
checkDupRdrNames :: [LocatedN RdrName] -> RnM ()
-- Check for duplicated names in a binding group
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment