summaryrefslogtreecommitdiff
path: root/compiler/main
diff options
context:
space:
mode:
authorBen Gamari <bgamari.foss@gmail.com>2018-06-02 11:56:58 -0400
committerBen Gamari <ben@smart-cactus.org>2018-06-02 16:21:12 -0400
commitfaee23bb69ca813296da484bc177f4480bcaee9f (patch)
tree28e1c99f0de9d505c1df81ae7459839f5db4121c /compiler/main
parent13a86606e51400bc2a81a0e04cfbb94ada5d2620 (diff)
downloadhaskell-faee23bb69ca813296da484bc177f4480bcaee9f.tar.gz
vectorise: Put it out of its misery
Poor DPH and its vectoriser have long been languishing; sadly it seems there is little chance that the effort will be rekindled. Every few years we discuss what to do with this mass of code and at least once we have agreed that it should be archived on a branch and removed from `master`. Here we do just that, eliminating heaps of dead code in the process. Here we drop the ParallelArrays extension, the vectoriser, and the `vector` and `primitive` submodules. Test Plan: Validate Reviewers: simonpj, simonmar, hvr, goldfire, alanz Reviewed By: simonmar Subscribers: goldfire, rwbarton, thomie, mpickering, carter Differential Revision: https://phabricator.haskell.org/D4761
Diffstat (limited to 'compiler/main')
-rw-r--r--compiler/main/DynFlags.hs30
-rw-r--r--compiler/main/HscTypes.hs148
-rw-r--r--compiler/main/Packages.hs9
-rw-r--r--compiler/main/TidyPgm.hs58
4 files changed, 9 insertions, 236 deletions
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 2a96fd0966..558fa9963c 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -394,7 +394,6 @@ data DumpFlag
| Opt_D_dump_splices
| Opt_D_th_dec_file
| Opt_D_dump_BCOs
- | Opt_D_dump_vect
| Opt_D_dump_ticked
| Opt_D_dump_rtti
| Opt_D_source_stats
@@ -470,8 +469,6 @@ data GeneralFlag
| Opt_UnboxSmallStrictFields
| Opt_DictsCheap
| Opt_EnableRewriteRules -- Apply rewrite rules during simplification
- | Opt_Vectorise
- | Opt_VectorisationAvoidance
| Opt_RegsGraph -- do graph coloring register allocation
| Opt_RegsIterative -- do iterative coalescing graph coloring register allocation
| Opt_PedanticBottoms -- Be picky about how we treat bottom
@@ -667,8 +664,6 @@ optimisationFlags = EnumSet.fromList
, Opt_UnboxSmallStrictFields
, Opt_DictsCheap
, Opt_EnableRewriteRules
- , Opt_Vectorise
- , Opt_VectorisationAvoidance
, Opt_RegsGraph
, Opt_RegsIterative
, Opt_PedanticBottoms
@@ -3207,8 +3202,6 @@ dynamic_flags_deps = [
(setDumpFlag Opt_D_dump_hi)
, make_ord_flag defGhcFlag "ddump-minimal-imports"
(NoArg (setGeneralFlag Opt_D_dump_minimal_imports))
- , make_ord_flag defGhcFlag "ddump-vect"
- (setDumpFlag Opt_D_dump_vect)
, make_ord_flag defGhcFlag "ddump-hpc"
(setDumpFlag Opt_D_dump_ticked) -- back compat
, make_ord_flag defGhcFlag "ddump-ticked"
@@ -3334,7 +3327,6 @@ dynamic_flags_deps = [
------ Optimisation flags ------------------------------------------
, make_dep_flag defGhcFlag "Onot" (noArgM $ setOptLevel 0 )
"Use -O0 instead"
- , make_ord_flag defGhcFlag "Odph" (noArgM setDPHOpt)
, make_ord_flag defGhcFlag "O" (optIntSuffixM (\mb_n ->
setOptLevel (mb_n `orElse` 1)))
-- If the number is missing, use 1
@@ -3968,8 +3960,6 @@ fFlagsDeps = [
flagSpec "write-interface" Opt_WriteInterface,
flagSpec "unbox-small-strict-fields" Opt_UnboxSmallStrictFields,
flagSpec "unbox-strict-fields" Opt_UnboxStrictFields,
- flagSpec "vectorisation-avoidance" Opt_VectorisationAvoidance,
- flagSpec "vectorise" Opt_Vectorise,
flagSpec "version-macros" Opt_VersionMacros,
flagSpec "worker-wrapper" Opt_WorkerWrapper,
flagSpec "solve-constant-dicts" Opt_SolveConstantDicts,
@@ -4037,10 +4027,6 @@ fLangFlagsDeps = [
(deprecatedForExtension "ImplicitParams"),
depFlagSpec' "scoped-type-variables" LangExt.ScopedTypeVariables
(deprecatedForExtension "ScopedTypeVariables"),
- depFlagSpec' "parr" LangExt.ParallelArrays
- (deprecatedForExtension "ParallelArrays"),
- depFlagSpec' "PArr" LangExt.ParallelArrays
- (deprecatedForExtension "ParallelArrays"),
depFlagSpec' "allow-overlapping-instances" LangExt.OverlappingInstances
(deprecatedForExtension "OverlappingInstances"),
depFlagSpec' "allow-undecidable-instances" LangExt.UndecidableInstances
@@ -4380,11 +4366,6 @@ optLevelFlags -- see Note [Documenting optimisation flags]
, ([0,1,2], Opt_DoEtaReduction) -- See Note [Eta-reduction in -O0]
, ([0,1,2], Opt_DmdTxDictSel)
, ([0,1,2], Opt_LlvmTBAA)
- , ([0,1,2], Opt_VectorisationAvoidance)
- -- This one is important for a tiresome reason:
- -- we want to make sure that the bindings for data
- -- constructors are eta-expanded. This is probably
- -- a good thing anyway, but it seems fragile.
, ([0], Opt_IgnoreInterfacePragmas)
, ([0], Opt_OmitInterfacePragmas)
@@ -5129,17 +5110,6 @@ checkOptLevel n dflags
| otherwise
= Right dflags
--- -Odph is equivalent to
---
--- -O2 optimise as much as possible
--- -fmax-simplifier-iterations20 this is necessary sometimes
--- -fsimplifier-phases=3 we use an additional simplifier phase for fusion
---
-setDPHOpt :: DynFlags -> DynP DynFlags
-setDPHOpt dflags = setOptLevel 2 (dflags { maxSimplIterations = 20
- , simplPhases = 3
- })
-
setMainIs :: String -> DynP ()
setMainIs arg
| not (null main_fn) && isLower (head main_fn)
diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs
index e17e2794b4..7cb25dfefb 100644
--- a/compiler/main/HscTypes.hs
+++ b/compiler/main/HscTypes.hs
@@ -44,7 +44,7 @@ module HscTypes (
lookupHpt, eltsHpt, filterHpt, allHpt, mapHpt, delFromHpt,
addToHpt, addListToHpt, lookupHptDirectly, listToHpt,
hptCompleteSigs,
- hptInstances, hptRules, hptVectInfo, pprHPT,
+ hptInstances, hptRules, pprHPT,
-- * State relating to known packages
ExternalPackageState(..), EpsStats(..), addEpsInStats,
@@ -123,10 +123,6 @@ module HscTypes (
-- * Breakpoints
ModBreaks (..), emptyModBreaks,
- -- * Vectorisation information
- VectInfo(..), IfaceVectInfo(..), noVectInfo, plusVectInfo,
- noIfaceVectInfo, isNoIfaceVectInfo,
-
-- * Safe Haskell information
IfaceTrustInfo, getSafeMode, setSafeMode, noIfaceTrustInfo,
trustInfoToNum, numToTrustInfo, IsSafeImport,
@@ -161,11 +157,9 @@ import Avail
import Module
import InstEnv ( InstEnv, ClsInst, identicalClsInstHead )
import FamInstEnv
-import CoreSyn ( CoreProgram, RuleBase, CoreRule, CoreVect )
+import CoreSyn ( CoreProgram, RuleBase, CoreRule )
import Name
import NameEnv
-import NameSet
-import VarEnv
import VarSet
import Var
import Id
@@ -665,13 +659,6 @@ hptInstances hsc_env want_this_module
return (md_insts details, md_fam_insts details)
in (concat insts, concat famInsts)
--- | Get the combined VectInfo of all modules in the home package table. In
--- contrast to instances and rules, we don't care whether the modules are
--- "below" us in the dependency sense. The VectInfo of those modules not "below"
--- us does not affect the compilation of the current module.
-hptVectInfo :: HscEnv -> VectInfo
-hptVectInfo = concatVectInfo . hptAllThings ((: []) . md_vect_info . hm_details)
-
-- | Get rules from modules "below" this one (in the dependency sense)
hptRules :: HscEnv -> [(ModuleName, IsBootInterface)] -> [CoreRule]
hptRules = hptSomeThingsBelowUs (md_rules . hm_details) False
@@ -934,9 +921,7 @@ data ModIface
mi_fam_insts :: [IfaceFamInst], -- ^ Sorted family instances
mi_rules :: [IfaceRule], -- ^ Sorted rules
mi_orphan_hash :: !Fingerprint, -- ^ Hash for orphan rules, class and family
- -- instances, and vectorise pragmas combined
-
- mi_vect_info :: !IfaceVectInfo, -- ^ Vectorisation information
+ -- instances combined
-- Cached environments for easy lookup
-- These are computed (lazily) from other fields
@@ -1040,7 +1025,6 @@ instance Binary ModIface where
mi_fam_insts = fam_insts,
mi_rules = rules,
mi_orphan_hash = orphan_hash,
- mi_vect_info = vect_info,
mi_hpc = hpc_info,
mi_trust = trust,
mi_trust_pkg = trust_pkg,
@@ -1069,7 +1053,6 @@ instance Binary ModIface where
put_ bh fam_insts
lazyPut bh rules
put_ bh orphan_hash
- put_ bh vect_info
put_ bh hpc_info
put_ bh trust
put_ bh trust_pkg
@@ -1100,7 +1083,6 @@ instance Binary ModIface where
fam_insts <- {-# SCC "bin_fam_insts" #-} get bh
rules <- {-# SCC "bin_rules" #-} lazyGet bh
orphan_hash <- get bh
- vect_info <- get bh
hpc_info <- get bh
trust <- get bh
trust_pkg <- get bh
@@ -1131,7 +1113,6 @@ instance Binary ModIface where
mi_fam_insts = fam_insts,
mi_rules = rules,
mi_orphan_hash = orphan_hash,
- mi_vect_info = vect_info,
mi_hpc = hpc_info,
mi_trust = trust,
mi_trust_pkg = trust_pkg,
@@ -1172,7 +1153,6 @@ emptyModIface mod
mi_decls = [],
mi_globals = Nothing,
mi_orphan_hash = fingerprint0,
- mi_vect_info = noIfaceVectInfo,
mi_warn_fn = emptyIfaceWarnCache,
mi_fix_fn = emptyIfaceFixCache,
mi_hash_fn = emptyIfaceHashCache,
@@ -1211,7 +1191,6 @@ data ModDetails
md_rules :: ![CoreRule], -- ^ Domain may include 'Id's from other modules
md_anns :: ![Annotation], -- ^ Annotations present in this module: currently
-- they only annotate things also declared in this module
- md_vect_info :: !VectInfo, -- ^ Module vectorisation information
md_complete_sigs :: [CompleteMatch]
-- ^ Complete match pragmas for this module
}
@@ -1225,7 +1204,6 @@ emptyModDetails
md_rules = [],
md_fam_insts = [],
md_anns = [],
- md_vect_info = noVectInfo,
md_complete_sigs = [] }
-- | Records the modules directly imported by a module for extracting e.g.
@@ -1292,9 +1270,6 @@ data ModGuts
mg_complete_sigs :: [CompleteMatch], -- ^ Complete Matches
mg_hpc_info :: !HpcInfo, -- ^ Coverage tick boxes in the module
mg_modBreaks :: !(Maybe ModBreaks), -- ^ Breakpoints for the module
- mg_vect_decls:: ![CoreVect], -- ^ Vectorisation declarations in this module
- -- (produced by desugarer & consumed by vectoriser)
- mg_vect_info :: !VectInfo, -- ^ Pool of vectorised declarations in the module
-- The next two fields are unusual, because they give instance
-- environments for *all* modules in the home package, including
@@ -2323,7 +2298,6 @@ lookupFixity env n = case lookupNameEnv env n of
-- * A transformation rule in a module other than the one defining
-- the function in the head of the rule
--
--- * A vectorisation pragma
type WhetherHasOrphans = Bool
-- | Does this module define family instances?
@@ -2517,7 +2491,6 @@ type PackageTypeEnv = TypeEnv
type PackageRuleBase = RuleBase
type PackageInstEnv = InstEnv
type PackageFamInstEnv = FamInstEnv
-type PackageVectInfo = VectInfo
type PackageAnnEnv = AnnEnv
type PackageCompleteMatchMap = CompleteMatchMap
@@ -2579,8 +2552,6 @@ data ExternalPackageState
-- from all the external-package modules
eps_rule_base :: !PackageRuleBase, -- ^ The total 'RuleEnv' accumulated
-- from all the external-package modules
- eps_vect_info :: !PackageVectInfo, -- ^ The total 'VectInfo' accumulated
- -- from all the external-package modules
eps_ann_env :: !PackageAnnEnv, -- ^ The total 'AnnEnv' accumulated
-- from all the external-package modules
eps_complete_matches :: !PackageCompleteMatchMap,
@@ -2883,119 +2854,6 @@ isHpcUsed (NoHpcInfo { hpcUsed = used }) = used
{-
************************************************************************
* *
-\subsection{Vectorisation Support}
-* *
-************************************************************************
-
-The following information is generated and consumed by the vectorisation
-subsystem. It communicates the vectorisation status of declarations from one
-module to another.
-
-Why do we need both f and f_v in the ModGuts/ModDetails/EPS version VectInfo
-below? We need to know `f' when converting to IfaceVectInfo. However, during
-vectorisation, we need to know `f_v', whose `Var' we cannot lookup based
-on just the OccName easily in a Core pass.
--}
-
--- |Vectorisation information for 'ModGuts', 'ModDetails' and 'ExternalPackageState'; see also
--- documentation at 'Vectorise.Env.GlobalEnv'.
---
--- NB: The following tables may also include 'Var's, 'TyCon's and 'DataCon's from imported modules,
--- which have been subsequently vectorised in the current module.
---
-data VectInfo
- = VectInfo
- { vectInfoVar :: DVarEnv (Var , Var ) -- ^ @(f, f_v)@ keyed on @f@
- , vectInfoTyCon :: NameEnv (TyCon , TyCon) -- ^ @(T, T_v)@ keyed on @T@
- , vectInfoDataCon :: NameEnv (DataCon, DataCon) -- ^ @(C, C_v)@ keyed on @C@
- , vectInfoParallelVars :: DVarSet -- ^ set of parallel variables
- , vectInfoParallelTyCons :: NameSet -- ^ set of parallel type constructors
- }
-
--- |Vectorisation information for 'ModIface'; i.e, the vectorisation information propagated
--- across module boundaries.
---
--- NB: The field 'ifaceVectInfoVar' explicitly contains the workers of data constructors as well as
--- class selectors — i.e., their mappings are /not/ implicitly generated from the data types.
--- Moreover, whether the worker of a data constructor is in 'ifaceVectInfoVar' determines
--- whether that data constructor was vectorised (or is part of an abstractly vectorised type
--- constructor).
---
-data IfaceVectInfo
- = IfaceVectInfo
- { ifaceVectInfoVar :: [Name] -- ^ All variables in here have a vectorised variant
- , ifaceVectInfoTyCon :: [Name] -- ^ All 'TyCon's in here have a vectorised variant;
- -- the name of the vectorised variant and those of its
- -- data constructors are determined by
- -- 'OccName.mkVectTyConOcc' and
- -- 'OccName.mkVectDataConOcc'; the names of the
- -- isomorphisms are determined by 'OccName.mkVectIsoOcc'
- , ifaceVectInfoTyConReuse :: [Name] -- ^ The vectorised form of all the 'TyCon's in here
- -- coincides with the unconverted form; the name of the
- -- isomorphisms is determined by 'OccName.mkVectIsoOcc'
- , ifaceVectInfoParallelVars :: [Name] -- iface version of 'vectInfoParallelVar'
- , ifaceVectInfoParallelTyCons :: [Name] -- iface version of 'vectInfoParallelTyCon'
- }
-
-noVectInfo :: VectInfo
-noVectInfo
- = VectInfo emptyDVarEnv emptyNameEnv emptyNameEnv emptyDVarSet emptyNameSet
-
-plusVectInfo :: VectInfo -> VectInfo -> VectInfo
-plusVectInfo vi1 vi2 =
- VectInfo (vectInfoVar vi1 `plusDVarEnv` vectInfoVar vi2)
- (vectInfoTyCon vi1 `plusNameEnv` vectInfoTyCon vi2)
- (vectInfoDataCon vi1 `plusNameEnv` vectInfoDataCon vi2)
- (vectInfoParallelVars vi1 `unionDVarSet` vectInfoParallelVars vi2)
- (vectInfoParallelTyCons vi1 `unionNameSet` vectInfoParallelTyCons vi2)
-
-concatVectInfo :: [VectInfo] -> VectInfo
-concatVectInfo = foldr plusVectInfo noVectInfo
-
-noIfaceVectInfo :: IfaceVectInfo
-noIfaceVectInfo = IfaceVectInfo [] [] [] [] []
-
-isNoIfaceVectInfo :: IfaceVectInfo -> Bool
-isNoIfaceVectInfo (IfaceVectInfo l1 l2 l3 l4 l5)
- = null l1 && null l2 && null l3 && null l4 && null l5
-
-instance Outputable VectInfo where
- ppr info = vcat
- [ text "variables :" <+> ppr (vectInfoVar info)
- , text "tycons :" <+> ppr (vectInfoTyCon info)
- , text "datacons :" <+> ppr (vectInfoDataCon info)
- , text "parallel vars :" <+> ppr (vectInfoParallelVars info)
- , text "parallel tycons :" <+> ppr (vectInfoParallelTyCons info)
- ]
-
-instance Outputable IfaceVectInfo where
- ppr info = vcat
- [ text "variables :" <+> ppr (ifaceVectInfoVar info)
- , text "tycons :" <+> ppr (ifaceVectInfoTyCon info)
- , text "tycons reuse :" <+> ppr (ifaceVectInfoTyConReuse info)
- , text "parallel vars :" <+> ppr (ifaceVectInfoParallelVars info)
- , text "parallel tycons :" <+> ppr (ifaceVectInfoParallelTyCons info)
- ]
-
-
-instance Binary IfaceVectInfo where
- put_ bh (IfaceVectInfo a1 a2 a3 a4 a5) = do
- put_ bh a1
- put_ bh a2
- put_ bh a3
- put_ bh a4
- put_ bh a5
- get bh = do
- a1 <- get bh
- a2 <- get bh
- a3 <- get bh
- a4 <- get bh
- a5 <- get bh
- return (IfaceVectInfo a1 a2 a3 a4 a5)
-
-{-
-************************************************************************
-* *
\subsection{Safe Haskell Support}
* *
************************************************************************
diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs
index f27e597a39..008e9b5da0 100644
--- a/compiler/main/Packages.hs
+++ b/compiler/main/Packages.hs
@@ -911,15 +911,6 @@ packageFlagErr :: DynFlags
-> PackageFlag
-> [(PackageConfig, UnusablePackageReason)]
-> IO a
-
--- for missing DPH package we emit a more helpful error message, because
--- this may be the result of using -fdph-par or -fdph-seq.
-packageFlagErr dflags (ExposePackage _ (PackageArg pkg) _) []
- | is_dph_package pkg
- = throwGhcExceptionIO (CmdLineError (showSDoc dflags $ dph_err))
- where dph_err = text "the " <> text pkg <> text " package is not installed."
- $$ text "To install it: \"cabal install dph\"."
- is_dph_package pkg = "dph" `isPrefixOf` pkg
packageFlagErr dflags flag reasons
= packageFlagErr' dflags (pprFlag flag) reasons
diff --git a/compiler/main/TidyPgm.hs b/compiler/main/TidyPgm.hs
index ce8ac53919..1728bc0a69 100644
--- a/compiler/main/TidyPgm.hs
+++ b/compiler/main/TidyPgm.hs
@@ -61,7 +61,6 @@ import Maybes
import UniqSupply
import ErrUtils (Severity(..))
import Outputable
-import UniqDFM
import SrcLoc
import qualified ErrUtils as Err
@@ -71,7 +70,7 @@ import Data.List ( sortBy )
import Data.IORef ( atomicModifyIORef' )
{-
-Constructing the TypeEnv, Instances, Rules, VectInfo from which the
+Constructing the TypeEnv, Instances, Rules from which the
ModIface is constructed, and which goes on to subsequent modules in
--make mode.
@@ -165,7 +164,6 @@ mkBootModDetailsTc hsc_env
, md_rules = []
, md_anns = []
, md_exports = exports
- , md_vect_info = noVectInfo
, md_complete_sigs = []
})
}
@@ -246,9 +244,8 @@ First we figure out which Ids are "external" Ids. An
unit. These are
a) the user exported ones
b) the ones bound to static forms
- c) ones mentioned in the unfoldings, workers,
- rules of externally-visible ones ,
- or vectorised versions of externally-visible ones
+ c) ones mentioned in the unfoldings, workers, or
+ rules of externally-visible ones
While figuring out which Ids are external, we pick a "tidy" OccName
for each one. That is, we make its OccName distinct from the other
@@ -324,7 +321,6 @@ tidyProgram hsc_env (ModGuts { mg_module = mod
, mg_binds = binds
, mg_patsyns = patsyns
, mg_rules = imp_rules
- , mg_vect_info = vect_info
, mg_anns = anns
, mg_complete_sigs = complete_sigs
, mg_deps = deps
@@ -351,7 +347,7 @@ tidyProgram hsc_env (ModGuts { mg_module = mod
; (unfold_env, tidy_occ_env)
<- chooseExternalIds hsc_env mod omit_prags expose_all
- binds implicit_binds imp_rules (vectInfoVar vect_info)
+ binds implicit_binds imp_rules
; let { (trimmed_binds, trimmed_rules)
= findExternalRules omit_prags binds imp_rules unfold_env }
@@ -373,8 +369,6 @@ tidyProgram hsc_env (ModGuts { mg_module = mod
-- and indeed it does, but if omit_prags is on, ext_rules is
-- empty
- ; tidy_vect_info = tidyVectInfo tidy_env vect_info
-
-- Tidy the Ids inside each PatSyn, very similarly to DFunIds
-- and then override the PatSyns in the type_env with the new tidy ones
-- This is really the only reason we keep mg_patsyns at all; otherwise
@@ -444,7 +438,6 @@ tidyProgram hsc_env (ModGuts { mg_module = mod
ModDetails { md_types = tidy_type_env,
md_rules = tidy_rules,
md_insts = tidy_cls_insts,
- md_vect_info = tidy_vect_info,
md_fam_insts = fam_insts,
md_exports = exports,
md_anns = anns, -- are already tidy
@@ -493,38 +486,6 @@ extendTypeEnvWithPatSyns :: [PatSyn] -> TypeEnv -> TypeEnv
extendTypeEnvWithPatSyns tidy_patsyns type_env
= extendTypeEnvList type_env [AConLike (PatSynCon ps) | ps <- tidy_patsyns ]
-tidyVectInfo :: TidyEnv -> VectInfo -> VectInfo
-tidyVectInfo (_, var_env) info@(VectInfo { vectInfoVar = vars
- , vectInfoParallelVars = parallelVars
- })
- = info { vectInfoVar = tidy_vars
- , vectInfoParallelVars = tidy_parallelVars
- }
- where
- -- we only export mappings whose domain and co-domain is exported (otherwise, the iface is
- -- inconsistent)
- tidy_vars = mkDVarEnv [ (tidy_var, (tidy_var, tidy_var_v))
- | (var, var_v) <- eltsUDFM vars
- , let tidy_var = lookup_var var
- tidy_var_v = lookup_var var_v
- , isExternalId tidy_var && isExportedId tidy_var
- , isExternalId tidy_var_v && isExportedId tidy_var_v
- , isDataConWorkId var || not (isImplicitId var)
- ]
-
- tidy_parallelVars = mkDVarSet
- [ tidy_var
- | var <- dVarSetElems parallelVars
- , let tidy_var = lookup_var var
- , isExternalId tidy_var && isExportedId tidy_var
- ]
-
- lookup_var var = lookupWithDefaultVarEnv var_env var var
-
- -- We need to make sure that all names getting into the iface version of 'VectInfo' are
- -- external; otherwise, 'MkIface' will bomb out.
- isExternalId = isExternalName . idName
-
{-
Note [Don't attempt to trim data types]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -641,11 +602,10 @@ chooseExternalIds :: HscEnv
-> [CoreBind]
-> [CoreBind]
-> [CoreRule]
- -> DVarEnv (Var, Var)
-> IO (UnfoldEnv, TidyOccEnv)
-- Step 1 from the notes above
-chooseExternalIds hsc_env mod omit_prags expose_all binds implicit_binds imp_id_rules vect_vars
+chooseExternalIds hsc_env mod omit_prags expose_all binds implicit_binds imp_id_rules
= do { (unfold_env1,occ_env1) <- search init_work_list emptyVarEnv init_occ_env
; let internal_ids = filter (not . (`elemVarEnv` unfold_env1)) binders
; tidy_internal internal_ids unfold_env1 occ_env1 }
@@ -665,13 +625,10 @@ chooseExternalIds hsc_env mod omit_prags expose_all binds implicit_binds imp_id_
-- An Id should be external if either (a) it is exported,
-- (b) it appears in the RHS of a local rule for an imported Id, or
- -- (c) it is the vectorised version of an imported Id.
-- See Note [Which rules to expose]
is_external id = isExportedId id || id `elemVarSet` rule_rhs_vars
- || id `elemVarSet` vect_var_vs
rule_rhs_vars = mapUnionVarSet ruleRhsFreeVars imp_id_rules
- vect_var_vs = mkVarSet [var_v | (var, var_v) <- eltsUDFM vect_vars, isGlobalId var]
binders = map fst $ flattenBinds binds
implicit_binders = bindersOfBinds implicit_binds
@@ -721,9 +678,6 @@ chooseExternalIds hsc_env mod omit_prags expose_all binds implicit_binds imp_id_
| omit_prags = ([], False)
| otherwise = addExternal expose_all refined_id
- -- add vectorised version if any exists
- new_ids' = new_ids ++ maybeToList (fmap snd $ lookupDVarEnv vect_vars idocc)
-
-- 'idocc' is an *occurrence*, but we need to see the
-- unfolding in the *definition*; so look up in binder_set
refined_id = case lookupVarSet binder_set idocc of
@@ -734,7 +688,7 @@ chooseExternalIds hsc_env mod omit_prags expose_all binds implicit_binds imp_id_
referrer' | isExportedId refined_id = refined_id
| otherwise = referrer
--
- search (zip new_ids' (repeat referrer') ++ rest) unfold_env' occ_env'
+ search (zip new_ids (repeat referrer') ++ rest) unfold_env' occ_env'
tidy_internal :: [Id] -> UnfoldEnv -> TidyOccEnv
-> IO (UnfoldEnv, TidyOccEnv)