diff options
Diffstat (limited to 'compiler/main')
-rw-r--r-- | compiler/main/GHC.hs | 8 | ||||
-rw-r--r-- | compiler/main/HscMain.hs | 2 | ||||
-rw-r--r-- | compiler/main/HscTypes.lhs | 63 | ||||
-rw-r--r-- | compiler/main/InteractiveEval.hs | 2 | ||||
-rw-r--r-- | compiler/main/SysTools.lhs | 2 | ||||
-rw-r--r-- | compiler/main/TidyPgm.lhs | 2 |
6 files changed, 52 insertions, 27 deletions
diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs index df670f1d63..6c31e2e1bf 100644 --- a/compiler/main/GHC.hs +++ b/compiler/main/GHC.hs @@ -168,7 +168,7 @@ module GHC ( pprFundeps, -- ** Instances - Instance, + ClsInst, instanceDFunId, pprInstance, pprInstanceHdr, pprFamInst, pprFamInstHdr, @@ -915,7 +915,7 @@ getBindings = withSession $ \hsc_env -> return $ icInScopeTTs $ hsc_IC hsc_env -- | Return the instances for the current interactive session. -getInsts :: GhcMonad m => m ([Instance], [FamInst]) +getInsts :: GhcMonad m => m ([ClsInst], [FamInst]) getInsts = withSession $ \hsc_env -> return $ ic_instances (hsc_IC hsc_env) @@ -928,7 +928,7 @@ data ModuleInfo = ModuleInfo { minf_type_env :: TypeEnv, minf_exports :: NameSet, -- ToDo, [AvailInfo] like ModDetails? minf_rdr_env :: Maybe GlobalRdrEnv, -- Nothing for a compiled/package mod - minf_instances :: [Instance], + minf_instances :: [ClsInst], minf_iface :: Maybe ModIface #ifdef GHCI ,minf_modBreaks :: ModBreaks @@ -1011,7 +1011,7 @@ modInfoExports minf = nameSetToList $! minf_exports minf -- | Returns the instances defined by the specified module. -- Warning: currently unimplemented for package modules. -modInfoInstances :: ModuleInfo -> [Instance] +modInfoInstances :: ModuleInfo -> [ClsInst] modInfoInstances = minf_instances modInfoIsExportedName :: ModuleInfo -> Name -> Bool diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index 2882816c0b..8c9e9a8f00 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -296,7 +296,7 @@ hscTcRcLookupName hsc_env name = -- "name not found", and the Maybe in the return type -- is used to indicate that. -hscTcRnGetInfo :: HscEnv -> Name -> IO (Maybe (TyThing, Fixity, [Instance])) +hscTcRnGetInfo :: HscEnv -> Name -> IO (Maybe (TyThing, Fixity, [ClsInst])) hscTcRnGetInfo hsc_env name = runHsc hsc_env $ ioMsgMaybe' $ tcRnGetInfo hsc_env name diff --git a/compiler/main/HscTypes.lhs b/compiler/main/HscTypes.lhs index 6b389fd1b2..3eda19fba1 100644 --- a/compiler/main/HscTypes.lhs +++ b/compiler/main/HscTypes.lhs @@ -119,7 +119,7 @@ import HsSyn import RdrName import Avail import Module -import InstEnv ( InstEnv, Instance ) +import InstEnv ( InstEnv, ClsInst ) import FamInstEnv import Rules ( RuleBase ) import CoreSyn ( CoreProgram ) @@ -467,7 +467,7 @@ lookupIfaceByModule dflags hpt pit mod -- modules imported by this one, directly or indirectly, and are in the Home -- Package Table. This ensures that we don't see instances from modules @--make@ -- compiled before this one, but which are not below this one. -hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([Instance], [FamInst]) +hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([ClsInst], [FamInst]) hptInstances hsc_env want_this_module = let (insts, famInsts) = unzip $ flip hptAllThings hsc_env $ \mod_info -> do guard (want_this_module (moduleName (mi_module (hm_iface mod_info)))) @@ -693,7 +693,7 @@ data ModIface -- 'HomeModInfo', but that leads to more plumbing. -- Instance declarations and rules - mi_insts :: [IfaceInst], -- ^ Sorted class instance + mi_insts :: [IfaceClsInst], -- ^ Sorted class instance mi_fam_insts :: [IfaceFamInst], -- ^ Sorted family instances mi_rules :: [IfaceRule], -- ^ Sorted rules mi_orphan_hash :: !Fingerprint, -- ^ Hash for orphan rules and class @@ -771,7 +771,7 @@ data ModDetails -- The next two fields are created by the typechecker md_exports :: [AvailInfo], md_types :: !TypeEnv, -- ^ Local type environment for this particular module - md_insts :: ![Instance], -- ^ 'DFunId's for the instances in this module + md_insts :: ![ClsInst], -- ^ 'DFunId's for the instances in this module md_fam_insts :: ![FamInst], md_rules :: ![CoreRule], -- ^ Domain may include 'Id's from other modules md_anns :: ![Annotation], -- ^ Annotations present in this module: currently @@ -817,7 +817,7 @@ data ModGuts -- ToDo: I'm unconvinced this is actually used anywhere mg_tcs :: ![TyCon], -- ^ TyCons declared in this module -- (includes TyCons for classes) - mg_insts :: ![Instance], -- ^ Class instances declared in this module + mg_insts :: ![ClsInst], -- ^ Class instances declared in this module mg_fam_insts :: ![FamInst], -- ^ Family instances declared in this module mg_rules :: ![CoreRule], -- ^ Before the core pipeline starts, contains -- See Note [Overall plumbing for rules] in Rules.lhs @@ -937,7 +937,7 @@ data InteractiveContext -- ^ Variables defined automatically by the system (e.g. -- record field selectors). See Notes [ic_sys_vars] - ic_instances :: ([Instance], [FamInst]), + ic_instances :: ([ClsInst], [FamInst]), -- ^ All instances and family instances created during -- this session. These are grabbed en masse after each -- update to be sure that proper overlapping is retained. @@ -1163,10 +1163,34 @@ mkPrintUnqualified dflags env = (qual_name, qual_mod) %************************************************************************ %* * - TyThing + Implicit TyThings %* * %************************************************************************ +Note [Implicit TyThings] +~~~~~~~~~~~~~~~~~~~~~~~~ + DEFINITION: An "implicit" TyThing is one that does not have its own + IfaceDecl in an interface file. Instead, its binding in the type + environment is created as part of typechecking the IfaceDecl for + some other thing. + +Examples: + * All DataCons are implicit, because they are generated from the + IfaceDecl for the data/newtype. Ditto class methods. + + * Record selectors are *not* implicit, because they get their own + free-standing IfaceDecl. + + * Associated data/type families are implicit because they are + included in the IfaceDecl of the parent class. (NB: the + IfaceClass decl happens to use IfaceDecl recursively for the + associated types, but that's irrelevant here.) + + * Dictionary function Ids are not implict. + + * Axioms for newtypes are implicit (same as above), but axioms + for data/type family instances are *not* implicit (like DFunIds). + \begin{code} -- | Determine the 'TyThing's brought into scope by another 'TyThing' -- /other/ than itself. For example, Id's don't have any implicit TyThings @@ -1175,7 +1199,7 @@ mkPrintUnqualified dflags env = (qual_name, qual_mod) -- scope, just for a start! -- N.B. the set of TyThings returned here *must* match the set of --- names returned by LoadIface.ifaceDeclSubBndrs, in the sense that +-- names returned by LoadIface.ifaceDeclImplicitBndrs, in the sense that -- TyThing.getOccName should define a bijection between the two lists. -- This invariant is used in LoadIface.loadDecl (see note [Tricky iface loop]) -- The order of the list does not matter. @@ -1201,9 +1225,10 @@ implicitTyConThings :: TyCon -> [TyThing] implicitTyConThings tc = class_stuff ++ -- fields (names of selectors) - -- (possibly) implicit coercion and family coercion - -- depending on whether it's a newtype or a family instance or both + + -- (possibly) implicit newtype coercion implicitCoTyCon tc ++ + -- for each data constructor in order, -- the contructor, worker, and (possibly) wrapper concatMap (extras_plus . ADataCon) (tyConDataCons tc) @@ -1218,14 +1243,11 @@ implicitTyConThings tc extras_plus :: TyThing -> [TyThing] extras_plus thing = thing : implicitTyThings thing --- For newtypes and indexed data types (and both), --- add the implicit coercion tycon +-- For newtypes (only) add the implicit coercion tycon implicitCoTyCon :: TyCon -> [TyThing] implicitCoTyCon tc - = map ACoAxiom . catMaybes $ [-- Just if newtype, Nothing if not - newTyConCo_maybe tc, - -- Just if family instance, Nothing if not - tyConFamilyCoercion_maybe tc] + | Just co <- newTyConCo_maybe tc = [ACoAxiom co] + | otherwise = [] -- | Returns @True@ if there should be no interface-file declaration -- for this thing on its own: either it is built-in, or it is part @@ -1235,7 +1257,7 @@ isImplicitTyThing :: TyThing -> Bool isImplicitTyThing (ADataCon {}) = True isImplicitTyThing (AnId id) = isImplicitId id isImplicitTyThing (ATyCon tc) = isImplicitTyCon tc -isImplicitTyThing (ACoAxiom {}) = True +isImplicitTyThing (ACoAxiom ax) = isImplicitCoAxiom ax -- | tyThingParent_maybe x returns (Just p) -- when pprTyThingInContext sould print a declaration for p @@ -1321,13 +1343,14 @@ mkTypeEnvWithImplicits things = mkTypeEnv (concatMap implicitTyThings things) typeEnvFromEntities :: [Id] -> [TyCon] -> [FamInst] -> TypeEnv -typeEnvFromEntities ids tcs faminsts = +typeEnvFromEntities ids tcs famInsts = mkTypeEnv ( map AnId ids ++ map ATyCon all_tcs ++ concatMap implicitTyConThings all_tcs + ++ map (ACoAxiom . famInstAxiom) famInsts ) where - all_tcs = tcs ++ map famInstTyCon faminsts + all_tcs = tcs ++ famInstsRepTyCons famInsts lookupTypeEnv = lookupNameEnv @@ -1432,7 +1455,7 @@ mkIfaceHashCache pairs = \occ -> lookupOccEnv env occ where env = foldr add_decl emptyOccEnv pairs - add_decl (v,d) env0 = foldr add_imp env1 (ifaceDeclSubBndrs d) + add_decl (v,d) env0 = foldr add_imp env1 (ifaceDeclImplicitBndrs d) where decl_name = ifName d env1 = extendOccEnv env0 decl_name (decl_name, v) diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs index 3439231aa6..eee5c00255 100644 --- a/compiler/main/InteractiveEval.hs +++ b/compiler/main/InteractiveEval.hs @@ -869,7 +869,7 @@ moduleIsInterpreted modl = withSession $ \h -> -- are in scope (qualified or otherwise). Otherwise we list a whole lot too many! -- The exact choice of which ones to show, and which to hide, is a judgement call. -- (see Trac #1581) -getInfo :: GhcMonad m => Name -> m (Maybe (TyThing,Fixity,[Instance])) +getInfo :: GhcMonad m => Name -> m (Maybe (TyThing,Fixity,[ClsInst])) getInfo name = withSession $ \hsc_env -> do mb_stuff <- liftIO $ hscTcRnGetInfo hsc_env name diff --git a/compiler/main/SysTools.lhs b/compiler/main/SysTools.lhs index 23906c69bc..75b4d542a5 100644 --- a/compiler/main/SysTools.lhs +++ b/compiler/main/SysTools.lhs @@ -192,6 +192,7 @@ initSysTools mbMinusB Nothing -> pgmError ("No entry for " ++ show key ++ " in " ++ show settingsFile) ; targetArch <- readSetting "target arch" ; targetOS <- readSetting "target os" + ; targetWordSize <- readSetting "target word size" ; targetHasGnuNonexecStack <- readSetting "target has GNU nonexec stack" ; targetHasIdentDirective <- readSetting "target has .ident directive" ; targetHasSubsectionsViaSymbols <- readSetting "target has subsections via symbols" @@ -257,6 +258,7 @@ initSysTools mbMinusB sTargetPlatform = Platform { platformArch = targetArch, platformOS = targetOS, + platformWordSize = targetWordSize, platformHasGnuNonexecStack = targetHasGnuNonexecStack, platformHasIdentDirective = targetHasIdentDirective, platformHasSubsectionsViaSymbols = targetHasSubsectionsViaSymbols diff --git a/compiler/main/TidyPgm.lhs b/compiler/main/TidyPgm.lhs index 830a352be2..5e2a9375a0 100644 --- a/compiler/main/TidyPgm.lhs +++ b/compiler/main/TidyPgm.lhs @@ -488,7 +488,7 @@ mustExposeTyCon exports tc exported_con con = any (`elemNameSet` exports) (dataConName con : dataConFieldLabels con) -tidyInstances :: (DFunId -> DFunId) -> [Instance] -> [Instance] +tidyInstances :: (DFunId -> DFunId) -> [ClsInst] -> [ClsInst] tidyInstances tidy_dfun ispecs = map tidy ispecs where |