[commit: ghc] ghc-8.2: Improve getNameToInstancesIndex (4f4f05a)
git at git.haskell.org
git at git.haskell.org
Thu Jun 22 14:35:23 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : ghc-8.2
Link : http://ghc.haskell.org/trac/ghc/changeset/4f4f05a6baf2f9616f8a48357d417a6855ff940e/ghc
>---------------------------------------------------------------
commit 4f4f05a6baf2f9616f8a48357d417a6855ff940e
Author: Douglas Wilson <douglas.wilson at gmail.com>
Date: Mon Jun 12 17:02:01 2017 -0400
Improve getNameToInstancesIndex
Put it in a GhcMonad.
Stop accidentally reversing the list of instances.
Add a comment noting the code is mostly copied from tcRnGetInfo.
Reviewers: austin, bgamari
Reviewed By: bgamari
Subscribers: mpickering, rwbarton, thomie
Differential Revision: https://phabricator.haskell.org/D3636
(cherry picked from commit f942f65a525dd972cd96e6ae42922b6a3ce4b2d0)
>---------------------------------------------------------------
4f4f05a6baf2f9616f8a48357d417a6855ff940e
compiler/main/GHC.hs | 18 ++++++++++--------
compiler/typecheck/TcRnDriver.hs | 8 ++++++++
2 files changed, 18 insertions(+), 8 deletions(-)
diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs
index 1dfa83e..8f50841 100644
--- a/compiler/main/GHC.hs
+++ b/compiler/main/GHC.hs
@@ -1241,22 +1241,24 @@ getGRE = withSession $ \hsc_env-> return $ ic_rn_gbl_env (hsc_IC hsc_env)
-- | Retrieve all type and family instances in the environment, indexed
-- by 'Name'. Each name's lists will contain every instance in which that name
-- is mentioned in the instance head.
-getNameToInstancesIndex :: HscEnv
- -> IO (Messages, Maybe (NameEnv ([ClsInst], [FamInst])))
-getNameToInstancesIndex hsc_env
- = runTcInteractive hsc_env $
+getNameToInstancesIndex :: GhcMonad m
+ => m (Messages, Maybe (NameEnv ([ClsInst], [FamInst])))
+getNameToInstancesIndex = do
+ hsc_env <- getSession
+ liftIO $ runTcInteractive hsc_env $
do { loadUnqualIfaces hsc_env (hsc_IC hsc_env)
; InstEnvs {ie_global, ie_local, ie_visible} <- tcGetInstEnvs
; (pkg_fie, home_fie) <- tcGetFamInstEnvs
- -- We use flip mappend to maintain the order of instances,
- -- and Data.Sequence.Seq to keep flip mappend fast
- ; let cls_index = Map.fromListWith (flip mappend)
+ -- We use Data.Sequence.Seq because we are creating left associated
+ -- mappends.
+ -- cls_index and fam_index below are adapted from TcRnDriver.lookupInsts
+ ; let cls_index = Map.fromListWith mappend
[ (n, Seq.singleton ispec)
| ispec <- instEnvElts ie_local ++ instEnvElts ie_global
, instIsVisible ie_visible ispec
, n <- nameSetElemsStable $ orphNamesOfClsInst ispec
]
- ; let fam_index = Map.fromListWith (flip mappend)
+ ; let fam_index = Map.fromListWith mappend
[ (n, Seq.singleton fispec)
| fispec <- famInstEnvElts home_fie ++ famInstEnvElts pkg_fie
, n <- nameSetElemsStable $ orphNamesOfFamInst fispec
diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs
index 740ed84..1f7a5e6 100644
--- a/compiler/typecheck/TcRnDriver.hs
+++ b/compiler/typecheck/TcRnDriver.hs
@@ -2436,6 +2436,14 @@ tcRnGetInfo hsc_env name
; (cls_insts, fam_insts) <- lookupInsts thing
; return (thing, fixity, cls_insts, fam_insts) }
+
+-- Lookup all class and family instances for a type constructor.
+--
+-- This function filters all instances in the type environment, so there
+-- is a lot of duplicated work if it is called many times in the same
+-- type environment. If this becomes a problem, the NameEnv computed
+-- in GHC.getNameToInstancesIndex could be cached in TcM and both functions
+-- could be changed to consult that index.
lookupInsts :: TyThing -> TcM ([ClsInst],[FamInst])
lookupInsts (ATyCon tc)
= do { InstEnvs { ie_global = pkg_ie, ie_local = home_ie, ie_visible = vis_mods } <- tcGetInstEnvs
More information about the ghc-commits
mailing list