PageRenderTime 65ms CodeModel.GetById 25ms RepoModel.GetById 0ms app.codeStats 1ms

/compiler/main/HscTypes.lhs

https://bitbucket.org/carter/ghc
Haskell | 2240 lines | 1199 code | 332 blank | 709 comment | 31 complexity | c511ba096725089092d851859c70f704 MD5 | raw file

Large files files are truncated, but you can click here to view the full file

  1. %
  2. % (c) The University of Glasgow, 2006
  3. %
  4. \section[HscTypes]{Types for the per-module compiler}
  5. \begin{code}
  6. -- | Types for the per-module compiler
  7. module HscTypes (
  8. -- * compilation state
  9. HscEnv(..), hscEPS,
  10. FinderCache, FindResult(..), ModLocationCache,
  11. Target(..), TargetId(..), pprTarget, pprTargetId,
  12. ModuleGraph, emptyMG,
  13. -- * Information about modules
  14. ModDetails(..), emptyModDetails,
  15. ModGuts(..), CgGuts(..), ForeignStubs(..), appendStubC,
  16. ImportedMods, ImportedModsVal,
  17. ModSummary(..), ms_imps, ms_mod_name, showModMsg, isBootSummary,
  18. msHsFilePath, msHiFilePath, msObjFilePath,
  19. SourceModified(..),
  20. -- * Information about the module being compiled
  21. HscSource(..), isHsBoot, hscSourceString, -- Re-exported from DriverPhases
  22. -- * State relating to modules in this package
  23. HomePackageTable, HomeModInfo(..), emptyHomePackageTable,
  24. hptInstances, hptRules, hptVectInfo,
  25. hptObjs,
  26. -- * State relating to known packages
  27. ExternalPackageState(..), EpsStats(..), addEpsInStats,
  28. PackageTypeEnv, PackageIfaceTable, emptyPackageIfaceTable,
  29. lookupIfaceByModule, emptyModIface,
  30. PackageInstEnv, PackageRuleBase,
  31. mkSOName,
  32. -- * Annotations
  33. prepareAnnotations,
  34. -- * Interactive context
  35. InteractiveContext(..), emptyInteractiveContext,
  36. icPrintUnqual, icInScopeTTs, icPlusGblRdrEnv,
  37. extendInteractiveContext, substInteractiveContext,
  38. setInteractivePrintName,
  39. InteractiveImport(..),
  40. mkPrintUnqualified, pprModulePrefix,
  41. -- * Interfaces
  42. ModIface(..), mkIfaceWarnCache, mkIfaceHashCache, mkIfaceFixCache,
  43. emptyIfaceWarnCache,
  44. -- * Fixity
  45. FixityEnv, FixItem(..), lookupFixity, emptyFixityEnv,
  46. -- * TyThings and type environments
  47. TyThing(..), tyThingAvailInfo,
  48. tyThingTyCon, tyThingDataCon,
  49. tyThingId, tyThingCoAxiom, tyThingParent_maybe, tyThingsTyVars,
  50. implicitTyThings, implicitTyConThings, implicitClassThings,
  51. isImplicitTyThing,
  52. TypeEnv, lookupType, lookupTypeHscEnv, mkTypeEnv, emptyTypeEnv,
  53. typeEnvFromEntities, mkTypeEnvWithImplicits,
  54. extendTypeEnv, extendTypeEnvList, extendTypeEnvWithIds, lookupTypeEnv,
  55. typeEnvElts, typeEnvTyCons, typeEnvIds,
  56. typeEnvDataCons, typeEnvCoAxioms, typeEnvClasses,
  57. -- * MonadThings
  58. MonadThings(..),
  59. -- * Information on imports and exports
  60. WhetherHasOrphans, IsBootInterface, Usage(..),
  61. Dependencies(..), noDependencies,
  62. NameCache(..), OrigNameCache,
  63. IfaceExport,
  64. -- * Warnings
  65. Warnings(..), WarningTxt(..), plusWarns,
  66. -- * Linker stuff
  67. Linkable(..), isObjectLinkable, linkableObjs,
  68. Unlinked(..), CompiledByteCode,
  69. isObject, nameOfObject, isInterpretable, byteCodeOfObject,
  70. -- * Program coverage
  71. HpcInfo(..), emptyHpcInfo, isHpcUsed, AnyHpcUsage,
  72. -- * Breakpoints
  73. ModBreaks (..), BreakIndex, emptyModBreaks,
  74. -- * Vectorisation information
  75. VectInfo(..), IfaceVectInfo(..), noVectInfo, plusVectInfo,
  76. noIfaceVectInfo, isNoIfaceVectInfo,
  77. -- * Safe Haskell information
  78. IfaceTrustInfo, getSafeMode, setSafeMode, noIfaceTrustInfo,
  79. trustInfoToNum, numToTrustInfo, IsSafeImport,
  80. -- * result of the parser
  81. HsParsedModule(..),
  82. -- * Compilation errors and warnings
  83. SourceError, GhcApiError, mkSrcErr, srcErrorMessages, mkApiErr,
  84. throwOneError, handleSourceError,
  85. handleFlagWarnings, printOrThrowWarnings,
  86. ) where
  87. #include "HsVersions.h"
  88. #ifdef GHCI
  89. import ByteCodeAsm ( CompiledByteCode )
  90. import {-# SOURCE #-} InteractiveEval ( Resume )
  91. #endif
  92. import HsSyn
  93. import RdrName
  94. import Avail
  95. import Module
  96. import InstEnv ( InstEnv, ClsInst )
  97. import FamInstEnv
  98. import Rules ( RuleBase )
  99. import CoreSyn ( CoreProgram )
  100. import Name
  101. import NameEnv
  102. import NameSet
  103. import VarEnv
  104. import VarSet
  105. import Var
  106. import Id
  107. import IdInfo ( IdDetails(..) )
  108. import Type
  109. import Annotations
  110. import Class
  111. import TyCon
  112. import DataCon
  113. import PrelNames ( gHC_PRIM, ioTyConName, printName )
  114. import Packages hiding ( Version(..) )
  115. import DynFlags
  116. import DriverPhases
  117. import BasicTypes
  118. import IfaceSyn
  119. import CoreSyn ( CoreRule, CoreVect )
  120. import Maybes
  121. import Outputable
  122. import BreakArray
  123. import SrcLoc
  124. import Unique
  125. import UniqFM
  126. import UniqSupply
  127. import FastString
  128. import StringBuffer ( StringBuffer )
  129. import Fingerprint
  130. import MonadUtils
  131. import Bag
  132. import ErrUtils
  133. import Platform
  134. import Util
  135. import Control.Monad ( mplus, guard, liftM, when )
  136. import Data.Array ( Array, array )
  137. import Data.IORef
  138. import Data.Time
  139. import Data.Word
  140. import Data.Typeable ( Typeable )
  141. import Exception
  142. import System.FilePath
  143. -- -----------------------------------------------------------------------------
  144. -- Source Errors
  145. -- When the compiler (HscMain) discovers errors, it throws an
  146. -- exception in the IO monad.
  147. mkSrcErr :: ErrorMessages -> SourceError
  148. mkSrcErr = SourceError
  149. srcErrorMessages :: SourceError -> ErrorMessages
  150. srcErrorMessages (SourceError msgs) = msgs
  151. mkApiErr :: DynFlags -> SDoc -> GhcApiError
  152. mkApiErr dflags msg = GhcApiError (showSDoc dflags msg)
  153. throwOneError :: MonadIO m => ErrMsg -> m ab
  154. throwOneError err = liftIO $ throwIO $ mkSrcErr $ unitBag err
  155. -- | A source error is an error that is caused by one or more errors in the
  156. -- source code. A 'SourceError' is thrown by many functions in the
  157. -- compilation pipeline. Inside GHC these errors are merely printed via
  158. -- 'log_action', but API clients may treat them differently, for example,
  159. -- insert them into a list box. If you want the default behaviour, use the
  160. -- idiom:
  161. --
  162. -- > handleSourceError printExceptionAndWarnings $ do
  163. -- > ... api calls that may fail ...
  164. --
  165. -- The 'SourceError's error messages can be accessed via 'srcErrorMessages'.
  166. -- This list may be empty if the compiler failed due to @-Werror@
  167. -- ('Opt_WarnIsError').
  168. --
  169. -- See 'printExceptionAndWarnings' for more information on what to take care
  170. -- of when writing a custom error handler.
  171. newtype SourceError = SourceError ErrorMessages
  172. deriving Typeable
  173. instance Show SourceError where
  174. show (SourceError msgs) = unlines . map show . bagToList $ msgs
  175. instance Exception SourceError
  176. -- | Perform the given action and call the exception handler if the action
  177. -- throws a 'SourceError'. See 'SourceError' for more information.
  178. handleSourceError :: (ExceptionMonad m) =>
  179. (SourceError -> m a) -- ^ exception handler
  180. -> m a -- ^ action to perform
  181. -> m a
  182. handleSourceError handler act =
  183. gcatch act (\(e :: SourceError) -> handler e)
  184. -- | An error thrown if the GHC API is used in an incorrect fashion.
  185. newtype GhcApiError = GhcApiError String
  186. deriving Typeable
  187. instance Show GhcApiError where
  188. show (GhcApiError msg) = msg
  189. instance Exception GhcApiError
  190. -- | Given a bag of warnings, turn them into an exception if
  191. -- -Werror is enabled, or print them out otherwise.
  192. printOrThrowWarnings :: DynFlags -> Bag WarnMsg -> IO ()
  193. printOrThrowWarnings dflags warns
  194. | dopt Opt_WarnIsError dflags
  195. = when (not (isEmptyBag warns)) $ do
  196. throwIO $ mkSrcErr $ warns `snocBag` warnIsErrorMsg dflags
  197. | otherwise
  198. = printBagOfErrors dflags warns
  199. handleFlagWarnings :: DynFlags -> [Located String] -> IO ()
  200. handleFlagWarnings dflags warns
  201. = when (wopt Opt_WarnDeprecatedFlags dflags) $ do
  202. -- It would be nicer if warns :: [Located MsgDoc], but that
  203. -- has circular import problems.
  204. let bag = listToBag [ mkPlainWarnMsg dflags loc (text warn)
  205. | L loc warn <- warns ]
  206. printOrThrowWarnings dflags bag
  207. \end{code}
  208. %************************************************************************
  209. %* *
  210. \subsection{HscEnv}
  211. %* *
  212. %************************************************************************
  213. \begin{code}
  214. -- | Hscenv is like 'Session', except that some of the fields are immutable.
  215. -- An HscEnv is used to compile a single module from plain Haskell source
  216. -- code (after preprocessing) to either C, assembly or C--. Things like
  217. -- the module graph don't change during a single compilation.
  218. --
  219. -- Historical note: \"hsc\" used to be the name of the compiler binary,
  220. -- when there was a separate driver and compiler. To compile a single
  221. -- module, the driver would invoke hsc on the source code... so nowadays
  222. -- we think of hsc as the layer of the compiler that deals with compiling
  223. -- a single module.
  224. data HscEnv
  225. = HscEnv {
  226. hsc_dflags :: DynFlags,
  227. -- ^ The dynamic flag settings
  228. hsc_targets :: [Target],
  229. -- ^ The targets (or roots) of the current session
  230. hsc_mod_graph :: ModuleGraph,
  231. -- ^ The module graph of the current session
  232. hsc_IC :: InteractiveContext,
  233. -- ^ The context for evaluating interactive statements
  234. hsc_HPT :: HomePackageTable,
  235. -- ^ The home package table describes already-compiled
  236. -- home-package modules, /excluding/ the module we
  237. -- are compiling right now.
  238. -- (In one-shot mode the current module is the only
  239. -- home-package module, so hsc_HPT is empty. All other
  240. -- modules count as \"external-package\" modules.
  241. -- However, even in GHCi mode, hi-boot interfaces are
  242. -- demand-loaded into the external-package table.)
  243. --
  244. -- 'hsc_HPT' is not mutable because we only demand-load
  245. -- external packages; the home package is eagerly
  246. -- loaded, module by module, by the compilation manager.
  247. --
  248. -- The HPT may contain modules compiled earlier by @--make@
  249. -- but not actually below the current module in the dependency
  250. -- graph.
  251. --
  252. -- (This changes a previous invariant: changed Jan 05.)
  253. hsc_EPS :: {-# UNPACK #-} !(IORef ExternalPackageState),
  254. -- ^ Information about the currently loaded external packages.
  255. -- This is mutable because packages will be demand-loaded during
  256. -- a compilation run as required.
  257. hsc_NC :: {-# UNPACK #-} !(IORef NameCache),
  258. -- ^ As with 'hsc_EPS', this is side-effected by compiling to
  259. -- reflect sucking in interface files. They cache the state of
  260. -- external interface files, in effect.
  261. hsc_FC :: {-# UNPACK #-} !(IORef FinderCache),
  262. -- ^ The cached result of performing finding in the file system
  263. hsc_MLC :: {-# UNPACK #-} !(IORef ModLocationCache),
  264. -- ^ This caches the location of modules, so we don't have to
  265. -- search the filesystem multiple times. See also 'hsc_FC'.
  266. hsc_type_env_var :: Maybe (Module, IORef TypeEnv)
  267. -- ^ Used for one-shot compilation only, to initialise
  268. -- the 'IfGblEnv'. See 'TcRnTypes.tcg_type_env_var' for
  269. -- 'TcRunTypes.TcGblEnv'
  270. }
  271. -- | Retrieve the ExternalPackageState cache.
  272. hscEPS :: HscEnv -> IO ExternalPackageState
  273. hscEPS hsc_env = readIORef (hsc_EPS hsc_env)
  274. -- | A compilation target.
  275. --
  276. -- A target may be supplied with the actual text of the
  277. -- module. If so, use this instead of the file contents (this
  278. -- is for use in an IDE where the file hasn't been saved by
  279. -- the user yet).
  280. data Target
  281. = Target {
  282. targetId :: TargetId, -- ^ module or filename
  283. targetAllowObjCode :: Bool, -- ^ object code allowed?
  284. targetContents :: Maybe (StringBuffer,UTCTime)
  285. -- ^ in-memory text buffer?
  286. }
  287. data TargetId
  288. = TargetModule ModuleName
  289. -- ^ A module name: search for the file
  290. | TargetFile FilePath (Maybe Phase)
  291. -- ^ A filename: preprocess & parse it to find the module name.
  292. -- If specified, the Phase indicates how to compile this file
  293. -- (which phase to start from). Nothing indicates the starting phase
  294. -- should be determined from the suffix of the filename.
  295. deriving Eq
  296. pprTarget :: Target -> SDoc
  297. pprTarget (Target id obj _) =
  298. (if obj then char '*' else empty) <> pprTargetId id
  299. instance Outputable Target where
  300. ppr = pprTarget
  301. pprTargetId :: TargetId -> SDoc
  302. pprTargetId (TargetModule m) = ppr m
  303. pprTargetId (TargetFile f _) = text f
  304. instance Outputable TargetId where
  305. ppr = pprTargetId
  306. \end{code}
  307. %************************************************************************
  308. %* *
  309. \subsection{Package and Module Tables}
  310. %* *
  311. %************************************************************************
  312. \begin{code}
  313. -- | Helps us find information about modules in the home package
  314. type HomePackageTable = ModuleNameEnv HomeModInfo
  315. -- Domain = modules in the home package that have been fully compiled
  316. -- "home" package name cached here for convenience
  317. -- | Helps us find information about modules in the imported packages
  318. type PackageIfaceTable = ModuleEnv ModIface
  319. -- Domain = modules in the imported packages
  320. -- | Constructs an empty HomePackageTable
  321. emptyHomePackageTable :: HomePackageTable
  322. emptyHomePackageTable = emptyUFM
  323. -- | Constructs an empty PackageIfaceTable
  324. emptyPackageIfaceTable :: PackageIfaceTable
  325. emptyPackageIfaceTable = emptyModuleEnv
  326. -- | Information about modules in the package being compiled
  327. data HomeModInfo
  328. = HomeModInfo {
  329. hm_iface :: !ModIface,
  330. -- ^ The basic loaded interface file: every loaded module has one of
  331. -- these, even if it is imported from another package
  332. hm_details :: !ModDetails,
  333. -- ^ Extra information that has been created from the 'ModIface' for
  334. -- the module, typically during typechecking
  335. hm_linkable :: !(Maybe Linkable)
  336. -- ^ The actual artifact we would like to link to access things in
  337. -- this module.
  338. --
  339. -- 'hm_linkable' might be Nothing:
  340. --
  341. -- 1. If this is an .hs-boot module
  342. --
  343. -- 2. Temporarily during compilation if we pruned away
  344. -- the old linkable because it was out of date.
  345. --
  346. -- After a complete compilation ('GHC.load'), all 'hm_linkable' fields
  347. -- in the 'HomePackageTable' will be @Just@.
  348. --
  349. -- When re-linking a module ('HscMain.HscNoRecomp'), we construct the
  350. -- 'HomeModInfo' by building a new 'ModDetails' from the old
  351. -- 'ModIface' (only).
  352. }
  353. -- | Find the 'ModIface' for a 'Module', searching in both the loaded home
  354. -- and external package module information
  355. lookupIfaceByModule
  356. :: DynFlags
  357. -> HomePackageTable
  358. -> PackageIfaceTable
  359. -> Module
  360. -> Maybe ModIface
  361. lookupIfaceByModule dflags hpt pit mod
  362. | modulePackageId mod == thisPackage dflags
  363. -- The module comes from the home package, so look first
  364. -- in the HPT. If it's not from the home package it's wrong to look
  365. -- in the HPT, because the HPT is indexed by *ModuleName* not Module
  366. = fmap hm_iface (lookupUFM hpt (moduleName mod))
  367. `mplus` lookupModuleEnv pit mod
  368. | otherwise = lookupModuleEnv pit mod -- Look in PIT only
  369. -- If the module does come from the home package, why do we look in the PIT as well?
  370. -- (a) In OneShot mode, even home-package modules accumulate in the PIT
  371. -- (b) Even in Batch (--make) mode, there is *one* case where a home-package
  372. -- module is in the PIT, namely GHC.Prim when compiling the base package.
  373. -- We could eliminate (b) if we wanted, by making GHC.Prim belong to a package
  374. -- of its own, but it doesn't seem worth the bother.
  375. -- | Find all the instance declarations (of classes and families) that are in
  376. -- modules imported by this one, directly or indirectly, and are in the Home
  377. -- Package Table. This ensures that we don't see instances from modules @--make@
  378. -- compiled before this one, but which are not below this one.
  379. hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([ClsInst], [FamInst])
  380. hptInstances hsc_env want_this_module
  381. = let (insts, famInsts) = unzip $ flip hptAllThings hsc_env $ \mod_info -> do
  382. guard (want_this_module (moduleName (mi_module (hm_iface mod_info))))
  383. let details = hm_details mod_info
  384. return (md_insts details, md_fam_insts details)
  385. in (concat insts, concat famInsts)
  386. -- | Get the combined VectInfo of all modules in the home package table. In
  387. -- contrast to instances and rules, we don't care whether the modules are
  388. -- "below" us in the dependency sense. The VectInfo of those modules not "below"
  389. -- us does not affect the compilation of the current module.
  390. hptVectInfo :: HscEnv -> VectInfo
  391. hptVectInfo = concatVectInfo . hptAllThings ((: []) . md_vect_info . hm_details)
  392. -- | Get rules from modules "below" this one (in the dependency sense)
  393. hptRules :: HscEnv -> [(ModuleName, IsBootInterface)] -> [CoreRule]
  394. hptRules = hptSomeThingsBelowUs (md_rules . hm_details) False
  395. -- | Get annotations from modules "below" this one (in the dependency sense)
  396. hptAnns :: HscEnv -> Maybe [(ModuleName, IsBootInterface)] -> [Annotation]
  397. hptAnns hsc_env (Just deps) = hptSomeThingsBelowUs (md_anns . hm_details) False hsc_env deps
  398. hptAnns hsc_env Nothing = hptAllThings (md_anns . hm_details) hsc_env
  399. hptAllThings :: (HomeModInfo -> [a]) -> HscEnv -> [a]
  400. hptAllThings extract hsc_env = concatMap extract (eltsUFM (hsc_HPT hsc_env))
  401. -- | Get things from modules "below" this one (in the dependency sense)
  402. -- C.f Inst.hptInstances
  403. hptSomeThingsBelowUs :: (HomeModInfo -> [a]) -> Bool -> HscEnv -> [(ModuleName, IsBootInterface)] -> [a]
  404. hptSomeThingsBelowUs extract include_hi_boot hsc_env deps
  405. | isOneShot (ghcMode (hsc_dflags hsc_env)) = []
  406. | otherwise
  407. = let hpt = hsc_HPT hsc_env
  408. in
  409. [ thing
  410. | -- Find each non-hi-boot module below me
  411. (mod, is_boot_mod) <- deps
  412. , include_hi_boot || not is_boot_mod
  413. -- unsavoury: when compiling the base package with --make, we
  414. -- sometimes try to look up RULES etc for GHC.Prim. GHC.Prim won't
  415. -- be in the HPT, because we never compile it; it's in the EPT
  416. -- instead. ToDo: clean up, and remove this slightly bogus filter:
  417. , mod /= moduleName gHC_PRIM
  418. -- Look it up in the HPT
  419. , let things = case lookupUFM hpt mod of
  420. Just info -> extract info
  421. Nothing -> pprTrace "WARNING in hptSomeThingsBelowUs" msg []
  422. msg = vcat [ptext (sLit "missing module") <+> ppr mod,
  423. ptext (sLit "Probable cause: out-of-date interface files")]
  424. -- This really shouldn't happen, but see Trac #962
  425. -- And get its dfuns
  426. , thing <- things ]
  427. hptObjs :: HomePackageTable -> [FilePath]
  428. hptObjs hpt = concat (map (maybe [] linkableObjs . hm_linkable) (eltsUFM hpt))
  429. \end{code}
  430. %************************************************************************
  431. %* *
  432. \subsection{Dealing with Annotations}
  433. %* *
  434. %************************************************************************
  435. \begin{code}
  436. -- | Deal with gathering annotations in from all possible places
  437. -- and combining them into a single 'AnnEnv'
  438. prepareAnnotations :: HscEnv -> Maybe ModGuts -> IO AnnEnv
  439. prepareAnnotations hsc_env mb_guts = do
  440. eps <- hscEPS hsc_env
  441. let -- Extract annotations from the module being compiled if supplied one
  442. mb_this_module_anns = fmap (mkAnnEnv . mg_anns) mb_guts
  443. -- Extract dependencies of the module if we are supplied one,
  444. -- otherwise load annotations from all home package table
  445. -- entries regardless of dependency ordering.
  446. home_pkg_anns = (mkAnnEnv . hptAnns hsc_env) $ fmap (dep_mods . mg_deps) mb_guts
  447. other_pkg_anns = eps_ann_env eps
  448. ann_env = foldl1' plusAnnEnv $ catMaybes [mb_this_module_anns,
  449. Just home_pkg_anns,
  450. Just other_pkg_anns]
  451. return ann_env
  452. \end{code}
  453. %************************************************************************
  454. %* *
  455. \subsection{The Finder cache}
  456. %* *
  457. %************************************************************************
  458. \begin{code}
  459. -- | The 'FinderCache' maps home module names to the result of
  460. -- searching for that module. It records the results of searching for
  461. -- modules along the search path. On @:load@, we flush the entire
  462. -- contents of this cache.
  463. --
  464. -- Although the @FinderCache@ range is 'FindResult' for convenience,
  465. -- in fact it will only ever contain 'Found' or 'NotFound' entries.
  466. --
  467. type FinderCache = ModuleNameEnv FindResult
  468. -- | The result of searching for an imported module.
  469. data FindResult
  470. = Found ModLocation Module
  471. -- ^ The module was found
  472. | NoPackage PackageId
  473. -- ^ The requested package was not found
  474. | FoundMultiple [PackageId]
  475. -- ^ _Error_: both in multiple packages
  476. -- | Not found
  477. | NotFound
  478. { fr_paths :: [FilePath] -- Places where I looked
  479. , fr_pkg :: Maybe PackageId -- Just p => module is in this package's
  480. -- manifest, but couldn't find
  481. -- the .hi file
  482. , fr_mods_hidden :: [PackageId] -- Module is in these packages,
  483. -- but the *module* is hidden
  484. , fr_pkgs_hidden :: [PackageId] -- Module is in these packages,
  485. -- but the *package* is hidden
  486. , fr_suggestions :: [Module] -- Possible mis-spelled modules
  487. }
  488. -- | Cache that remembers where we found a particular module. Contains both
  489. -- home modules and package modules. On @:load@, only home modules are
  490. -- purged from this cache.
  491. type ModLocationCache = ModuleEnv ModLocation
  492. \end{code}
  493. %************************************************************************
  494. %* *
  495. \subsection{Symbol tables and Module details}
  496. %* *
  497. %************************************************************************
  498. \begin{code}
  499. -- | A 'ModIface' plus a 'ModDetails' summarises everything we know
  500. -- about a compiled module. The 'ModIface' is the stuff *before* linking,
  501. -- and can be written out to an interface file. The 'ModDetails is after
  502. -- linking and can be completely recovered from just the 'ModIface'.
  503. --
  504. -- When we read an interface file, we also construct a 'ModIface' from it,
  505. -- except that we explicitly make the 'mi_decls' and a few other fields empty;
  506. -- as when reading we consolidate the declarations etc. into a number of indexed
  507. -- maps and environments in the 'ExternalPackageState'.
  508. data ModIface
  509. = ModIface {
  510. mi_module :: !Module, -- ^ Name of the module we are for
  511. mi_iface_hash :: !Fingerprint, -- ^ Hash of the whole interface
  512. mi_mod_hash :: !Fingerprint, -- ^ Hash of the ABI only
  513. mi_flag_hash :: !Fingerprint, -- ^ Hash of the important flags
  514. -- used when compiling this module
  515. mi_orphan :: !WhetherHasOrphans, -- ^ Whether this module has orphans
  516. mi_finsts :: !WhetherHasFamInst, -- ^ Whether this module has family instances
  517. mi_boot :: !IsBootInterface, -- ^ Read from an hi-boot file?
  518. mi_deps :: Dependencies,
  519. -- ^ The dependencies of the module. This is
  520. -- consulted for directly-imported modules, but not
  521. -- for anything else (hence lazy)
  522. mi_usages :: [Usage],
  523. -- ^ Usages; kept sorted so that it's easy to decide
  524. -- whether to write a new iface file (changing usages
  525. -- doesn't affect the hash of this module)
  526. -- NOT STRICT! we read this field lazily from the interface file
  527. -- It is *only* consulted by the recompilation checker
  528. mi_exports :: ![IfaceExport],
  529. -- ^ Exports
  530. -- Kept sorted by (mod,occ), to make version comparisons easier
  531. -- Records the modules that are the declaration points for things
  532. -- exported by this module, and the 'OccName's of those things
  533. mi_exp_hash :: !Fingerprint,
  534. -- ^ Hash of export list
  535. mi_used_th :: !Bool,
  536. -- ^ Module required TH splices when it was compiled.
  537. -- This disables recompilation avoidance (see #481).
  538. mi_fixities :: [(OccName,Fixity)],
  539. -- ^ Fixities
  540. -- NOT STRICT! we read this field lazily from the interface file
  541. mi_warns :: Warnings,
  542. -- ^ Warnings
  543. -- NOT STRICT! we read this field lazily from the interface file
  544. mi_anns :: [IfaceAnnotation],
  545. -- ^ Annotations
  546. -- NOT STRICT! we read this field lazily from the interface file
  547. mi_decls :: [(Fingerprint,IfaceDecl)],
  548. -- ^ Type, class and variable declarations
  549. -- The hash of an Id changes if its fixity or deprecations change
  550. -- (as well as its type of course)
  551. -- Ditto data constructors, class operations, except that
  552. -- the hash of the parent class/tycon changes
  553. mi_globals :: !(Maybe GlobalRdrEnv),
  554. -- ^ Binds all the things defined at the top level in
  555. -- the /original source/ code for this module. which
  556. -- is NOT the same as mi_exports, nor mi_decls (which
  557. -- may contains declarations for things not actually
  558. -- defined by the user). Used for GHCi and for inspecting
  559. -- the contents of modules via the GHC API only.
  560. --
  561. -- (We need the source file to figure out the
  562. -- top-level environment, if we didn't compile this module
  563. -- from source then this field contains @Nothing@).
  564. --
  565. -- Strictly speaking this field should live in the
  566. -- 'HomeModInfo', but that leads to more plumbing.
  567. -- Instance declarations and rules
  568. mi_insts :: [IfaceClsInst], -- ^ Sorted class instance
  569. mi_fam_insts :: [IfaceFamInst], -- ^ Sorted family instances
  570. mi_rules :: [IfaceRule], -- ^ Sorted rules
  571. mi_orphan_hash :: !Fingerprint, -- ^ Hash for orphan rules, class and family
  572. -- instances, and vectorise pragmas combined
  573. mi_vect_info :: !IfaceVectInfo, -- ^ Vectorisation information
  574. -- Cached environments for easy lookup
  575. -- These are computed (lazily) from other fields
  576. -- and are not put into the interface file
  577. mi_warn_fn :: Name -> Maybe WarningTxt, -- ^ Cached lookup for 'mi_warns'
  578. mi_fix_fn :: OccName -> Fixity, -- ^ Cached lookup for 'mi_fixities'
  579. mi_hash_fn :: OccName -> Maybe (OccName, Fingerprint),
  580. -- ^ Cached lookup for 'mi_decls'.
  581. -- The @Nothing@ in 'mi_hash_fn' means that the thing
  582. -- isn't in decls. It's useful to know that when
  583. -- seeing if we are up to date wrt. the old interface.
  584. -- The 'OccName' is the parent of the name, if it has one.
  585. mi_hpc :: !AnyHpcUsage,
  586. -- ^ True if this program uses Hpc at any point in the program.
  587. mi_trust :: !IfaceTrustInfo,
  588. -- ^ Safe Haskell Trust information for this module.
  589. mi_trust_pkg :: !Bool
  590. -- ^ Do we require the package this module resides in be trusted
  591. -- to trust this module? This is used for the situation where a
  592. -- module is Safe (so doesn't require the package be trusted
  593. -- itself) but imports some trustworthy modules from its own
  594. -- package (which does require its own package be trusted).
  595. -- See Note [RnNames . Trust Own Package]
  596. }
  597. -- | The original names declared of a certain module that are exported
  598. type IfaceExport = AvailInfo
  599. -- | Constructs an empty ModIface
  600. emptyModIface :: Module -> ModIface
  601. emptyModIface mod
  602. = ModIface { mi_module = mod,
  603. mi_iface_hash = fingerprint0,
  604. mi_mod_hash = fingerprint0,
  605. mi_flag_hash = fingerprint0,
  606. mi_orphan = False,
  607. mi_finsts = False,
  608. mi_boot = False,
  609. mi_deps = noDependencies,
  610. mi_usages = [],
  611. mi_exports = [],
  612. mi_exp_hash = fingerprint0,
  613. mi_used_th = False,
  614. mi_fixities = [],
  615. mi_warns = NoWarnings,
  616. mi_anns = [],
  617. mi_insts = [],
  618. mi_fam_insts = [],
  619. mi_rules = [],
  620. mi_decls = [],
  621. mi_globals = Nothing,
  622. mi_orphan_hash = fingerprint0,
  623. mi_vect_info = noIfaceVectInfo,
  624. mi_warn_fn = emptyIfaceWarnCache,
  625. mi_fix_fn = emptyIfaceFixCache,
  626. mi_hash_fn = emptyIfaceHashCache,
  627. mi_hpc = False,
  628. mi_trust = noIfaceTrustInfo,
  629. mi_trust_pkg = False }
  630. -- | Constructs cache for the 'mi_hash_fn' field of a 'ModIface'
  631. mkIfaceHashCache :: [(Fingerprint,IfaceDecl)]
  632. -> (OccName -> Maybe (OccName, Fingerprint))
  633. mkIfaceHashCache pairs
  634. = \occ -> lookupOccEnv env occ
  635. where
  636. env = foldr add_decl emptyOccEnv pairs
  637. add_decl (v,d) env0 = foldr add env0 (ifaceDeclFingerprints v d)
  638. where
  639. add (occ,hash) env0 = extendOccEnv env0 occ (occ,hash)
  640. emptyIfaceHashCache :: OccName -> Maybe (OccName, Fingerprint)
  641. emptyIfaceHashCache _occ = Nothing
  642. -- | The 'ModDetails' is essentially a cache for information in the 'ModIface'
  643. -- for home modules only. Information relating to packages will be loaded into
  644. -- global environments in 'ExternalPackageState'.
  645. data ModDetails
  646. = ModDetails {
  647. -- The next two fields are created by the typechecker
  648. md_exports :: [AvailInfo],
  649. md_types :: !TypeEnv, -- ^ Local type environment for this particular module
  650. md_insts :: ![ClsInst], -- ^ 'DFunId's for the instances in this module
  651. md_fam_insts :: ![FamInst],
  652. md_rules :: ![CoreRule], -- ^ Domain may include 'Id's from other modules
  653. md_anns :: ![Annotation], -- ^ Annotations present in this module: currently
  654. -- they only annotate things also declared in this module
  655. md_vect_info :: !VectInfo -- ^ Module vectorisation information
  656. }
  657. -- | Constructs an empty ModDetails
  658. emptyModDetails :: ModDetails
  659. emptyModDetails
  660. = ModDetails { md_types = emptyTypeEnv,
  661. md_exports = [],
  662. md_insts = [],
  663. md_rules = [],
  664. md_fam_insts = [],
  665. md_anns = [],
  666. md_vect_info = noVectInfo }
  667. -- | Records the modules directly imported by a module for extracting e.g. usage information
  668. type ImportedMods = ModuleEnv [ImportedModsVal]
  669. type ImportedModsVal = (ModuleName, Bool, SrcSpan, IsSafeImport)
  670. -- | A ModGuts is carried through the compiler, accumulating stuff as it goes
  671. -- There is only one ModGuts at any time, the one for the module
  672. -- being compiled right now. Once it is compiled, a 'ModIface' and
  673. -- 'ModDetails' are extracted and the ModGuts is discarded.
  674. data ModGuts
  675. = ModGuts {
  676. mg_module :: !Module, -- ^ Module being compiled
  677. mg_boot :: IsBootInterface, -- ^ Whether it's an hs-boot module
  678. mg_exports :: ![AvailInfo], -- ^ What it exports
  679. mg_deps :: !Dependencies, -- ^ What it depends on, directly or
  680. -- otherwise
  681. mg_dir_imps :: !ImportedMods, -- ^ Directly-imported modules; used to
  682. -- generate initialisation code
  683. mg_used_names:: !NameSet, -- ^ What the module needed (used in 'MkIface.mkIface')
  684. mg_used_th :: !Bool, -- ^ Did we run a TH splice?
  685. mg_rdr_env :: !GlobalRdrEnv, -- ^ Top-level lexical environment
  686. -- These fields all describe the things **declared in this module**
  687. mg_fix_env :: !FixityEnv, -- ^ Fixities declared in this module
  688. -- ToDo: I'm unconvinced this is actually used anywhere
  689. mg_tcs :: ![TyCon], -- ^ TyCons declared in this module
  690. -- (includes TyCons for classes)
  691. mg_insts :: ![ClsInst], -- ^ Class instances declared in this module
  692. mg_fam_insts :: ![FamInst], -- ^ Family instances declared in this module
  693. mg_rules :: ![CoreRule], -- ^ Before the core pipeline starts, contains
  694. -- See Note [Overall plumbing for rules] in Rules.lhs
  695. mg_binds :: !CoreProgram, -- ^ Bindings for this module
  696. mg_foreign :: !ForeignStubs, -- ^ Foreign exports declared in this module
  697. mg_warns :: !Warnings, -- ^ Warnings declared in the module
  698. mg_anns :: [Annotation], -- ^ Annotations declared in this module
  699. mg_hpc_info :: !HpcInfo, -- ^ Coverage tick boxes in the module
  700. mg_modBreaks :: !ModBreaks, -- ^ Breakpoints for the module
  701. mg_vect_decls:: ![CoreVect], -- ^ Vectorisation declarations in this module
  702. -- (produced by desugarer & consumed by vectoriser)
  703. mg_vect_info :: !VectInfo, -- ^ Pool of vectorised declarations in the module
  704. -- The next two fields are unusual, because they give instance
  705. -- environments for *all* modules in the home package, including
  706. -- this module, rather than for *just* this module.
  707. -- Reason: when looking up an instance we don't want to have to
  708. -- look at each module in the home package in turn
  709. mg_inst_env :: InstEnv,
  710. -- ^ Class instance environment from /home-package/ modules (including
  711. -- this one); c.f. 'tcg_inst_env'
  712. mg_fam_inst_env :: FamInstEnv,
  713. -- ^ Type-family instance enviroment for /home-package/ modules
  714. -- (including this one); c.f. 'tcg_fam_inst_env'
  715. mg_safe_haskell :: SafeHaskellMode,
  716. -- ^ Safe Haskell mode
  717. mg_trust_pkg :: Bool,
  718. -- ^ Do we need to trust our own package for Safe Haskell?
  719. -- See Note [RnNames . Trust Own Package]
  720. mg_dependent_files :: [FilePath] -- ^ dependencies from addDependentFile
  721. }
  722. -- The ModGuts takes on several slightly different forms:
  723. --
  724. -- After simplification, the following fields change slightly:
  725. -- mg_rules Orphan rules only (local ones now attached to binds)
  726. -- mg_binds With rules attached
  727. ---------------------------------------------------------
  728. -- The Tidy pass forks the information about this module:
  729. -- * one lot goes to interface file generation (ModIface)
  730. -- and later compilations (ModDetails)
  731. -- * the other lot goes to code generation (CgGuts)
  732. -- | A restricted form of 'ModGuts' for code generation purposes
  733. data CgGuts
  734. = CgGuts {
  735. cg_module :: !Module,
  736. -- ^ Module being compiled
  737. cg_tycons :: [TyCon],
  738. -- ^ Algebraic data types (including ones that started
  739. -- life as classes); generate constructors and info
  740. -- tables. Includes newtypes, just for the benefit of
  741. -- External Core
  742. cg_binds :: CoreProgram,
  743. -- ^ The tidied main bindings, including
  744. -- previously-implicit bindings for record and class
  745. -- selectors, and data construtor wrappers. But *not*
  746. -- data constructor workers; reason: we we regard them
  747. -- as part of the code-gen of tycons
  748. cg_foreign :: !ForeignStubs, -- ^ Foreign export stubs
  749. cg_dep_pkgs :: ![PackageId], -- ^ Dependent packages, used to
  750. -- generate #includes for C code gen
  751. cg_hpc_info :: !HpcInfo, -- ^ Program coverage tick box information
  752. cg_modBreaks :: !ModBreaks -- ^ Module breakpoints
  753. }
  754. -----------------------------------
  755. -- | Foreign export stubs
  756. data ForeignStubs
  757. = NoStubs
  758. -- ^ We don't have any stubs
  759. | ForeignStubs SDoc SDoc
  760. -- ^ There are some stubs. Parameters:
  761. --
  762. -- 1) Header file prototypes for
  763. -- "foreign exported" functions
  764. --
  765. -- 2) C stubs to use when calling
  766. -- "foreign exported" functions
  767. appendStubC :: ForeignStubs -> SDoc -> ForeignStubs
  768. appendStubC NoStubs c_code = ForeignStubs empty c_code
  769. appendStubC (ForeignStubs h c) c_code = ForeignStubs h (c $$ c_code)
  770. \end{code}
  771. %************************************************************************
  772. %* *
  773. \subsection{The interactive context}
  774. %* *
  775. %************************************************************************
  776. \begin{code}
  777. -- | Interactive context, recording information about the state of the
  778. -- context in which statements are executed in a GHC session.
  779. data InteractiveContext
  780. = InteractiveContext {
  781. ic_dflags :: DynFlags,
  782. -- ^ The 'DynFlags' used to evaluate interative expressions
  783. -- and statements.
  784. ic_monad :: Name,
  785. -- ^ The monad that GHCi is executing in
  786. ic_imports :: [InteractiveImport],
  787. -- ^ The GHCi context is extended with these imports
  788. --
  789. -- This field is only stored here so that the client
  790. -- can retrieve it with GHC.getContext. GHC itself doesn't
  791. -- use it, but does reset it to empty sometimes (such
  792. -- as before a GHC.load). The context is set with GHC.setContext.
  793. ic_rn_gbl_env :: GlobalRdrEnv,
  794. -- ^ The cached 'GlobalRdrEnv', built by
  795. -- 'InteractiveEval.setContext' and updated regularly
  796. ic_tythings :: [TyThing],
  797. -- ^ TyThings defined by the user, in reverse order of
  798. -- definition. At a breakpoint, this list includes the
  799. -- local variables in scope at that point
  800. ic_sys_vars :: [Id],
  801. -- ^ Variables defined automatically by the system (e.g.
  802. -- record field selectors). See Notes [ic_sys_vars]
  803. ic_instances :: ([ClsInst], [FamInst]),
  804. -- ^ All instances and family instances created during
  805. -- this session. These are grabbed en masse after each
  806. -- update to be sure that proper overlapping is retained.
  807. -- That is, rather than re-check the overlapping each
  808. -- time we update the context, we just take the results
  809. -- from the instance code that already does that.
  810. ic_fix_env :: FixityEnv,
  811. -- ^ Fixities declared in let statements
  812. ic_int_print :: Name,
  813. -- ^ The function that is used for printing results
  814. -- of expressions in ghci and -e mode.
  815. ic_default :: Maybe [Type],
  816. -- ^ The current default types, set by a 'default' declaration
  817. #ifdef GHCI
  818. ic_resume :: [Resume],
  819. -- ^ The stack of breakpoint contexts
  820. #endif
  821. ic_cwd :: Maybe FilePath
  822. -- virtual CWD of the program
  823. }
  824. {-
  825. Note [ic_sys_vars]
  826. ~~~~~~~~~~~~~~~~~~
  827. This list constains any Ids that arise from TyCons, Classes or
  828. instances defined interactively, but that are not given by
  829. 'implicitTyThings'. This includes record selectors, default methods,
  830. and dfuns.
  831. We *could* get rid of this list and generate these Ids from
  832. ic_tythings:
  833. - dfuns come from Instances
  834. - record selectors from TyCons
  835. - default methods from Classes
  836. For record selectors the TyCon gives the Name, but in order to make an
  837. Id we would have to construct the type ourselves. Similarly for
  838. default methods. So for now we collect the Ids after tidying (see
  839. hscDeclsWithLocation) and save them in ic_sys_vars.
  840. -}
  841. -- | Constructs an empty InteractiveContext.
  842. emptyInteractiveContext :: DynFlags -> InteractiveContext
  843. emptyInteractiveContext dflags
  844. = InteractiveContext { ic_dflags = dflags,
  845. -- IO monad by default
  846. ic_monad = ioTyConName,
  847. ic_imports = [],
  848. ic_rn_gbl_env = emptyGlobalRdrEnv,
  849. ic_tythings = [],
  850. ic_sys_vars = [],
  851. ic_instances = ([],[]),
  852. ic_fix_env = emptyNameEnv,
  853. -- System.IO.print by default
  854. ic_int_print = printName,
  855. ic_default = Nothing,
  856. #ifdef GHCI
  857. ic_resume = [],
  858. #endif
  859. ic_cwd = Nothing }
  860. -- | This function returns the list of visible TyThings (useful for
  861. -- e.g. showBindings)
  862. icInScopeTTs :: InteractiveContext -> [TyThing]
  863. icInScopeTTs = ic_tythings
  864. -- | Get the PrintUnqualified function based on the flags and this InteractiveContext
  865. icPrintUnqual :: DynFlags -> InteractiveContext -> PrintUnqualified
  866. icPrintUnqual dflags InteractiveContext{ ic_rn_gbl_env = grenv } =
  867. mkPrintUnqualified dflags grenv
  868. -- | This function is called with new TyThings recently defined to update the
  869. -- InteractiveContext to include them. Ids are easily removed when shadowed,
  870. -- but Classes and TyCons are not. Some work could be done to determine
  871. -- whether they are entirely shadowed, but as you could still have references
  872. -- to them (e.g. instances for classes or values of the type for TyCons), it's
  873. -- not clear whether removing them is even the appropriate behavior.
  874. extendInteractiveContext :: InteractiveContext -> [TyThing] -> InteractiveContext
  875. extendInteractiveContext ictxt new_tythings
  876. = ictxt { ic_tythings = new_tythings ++ old_tythings
  877. , ic_rn_gbl_env = new_tythings `icPlusGblRdrEnv` ic_rn_gbl_env ictxt
  878. }
  879. where
  880. old_tythings = filter (not . shadowed) (ic_tythings ictxt)
  881. shadowed (AnId id) = ((`elem` new_names) . nameOccName . idName) id
  882. shadowed _ = False
  883. new_names = [ nameOccName (getName id) | AnId id <- new_tythings ]
  884. setInteractivePrintName :: InteractiveContext -> Name -> InteractiveContext
  885. setInteractivePrintName ic n = ic{ic_int_print = n}
  886. -- ToDo: should not add Ids to the gbl env here
  887. -- | Add TyThings to the GlobalRdrEnv, earlier ones in the list shadowing
  888. -- later ones, and shadowing existing entries in the GlobalRdrEnv.
  889. icPlusGblRdrEnv :: [TyThing] -> GlobalRdrEnv -> GlobalRdrEnv
  890. icPlusGblRdrEnv tythings env = extendOccEnvList env list
  891. where new_gres = gresFromAvails LocalDef (map tyThingAvailInfo tythings)
  892. list = [ (nameOccName (gre_name gre), [gre]) | gre <- new_gres ]
  893. substInteractiveContext :: InteractiveContext -> TvSubst -> InteractiveContext
  894. substInteractiveContext ictxt subst
  895. | isEmptyTvSubst subst = ictxt
  896. substInteractiveContext ictxt@InteractiveContext{ ic_tythings = tts } subst
  897. = ictxt { ic_tythings = map subst_ty tts }
  898. where subst_ty (AnId id) = AnId $ id `setIdType` substTy subst (idType id)
  899. subst_ty tt = tt
  900. data InteractiveImport
  901. = IIDecl (ImportDecl RdrName)
  902. -- ^ Bring the exports of a particular module
  903. -- (filtered by an import decl) into scope
  904. | IIModule ModuleName
  905. -- ^ Bring into scope the entire top-level envt of
  906. -- of this module, including the things imported
  907. -- into it.
  908. instance Outputable InteractiveImport where
  909. ppr (IIModule m) = char '*' <> ppr m
  910. ppr (IIDecl d) = ppr d
  911. \end{code}
  912. %************************************************************************
  913. %* *
  914. Building a PrintUnqualified
  915. %* *
  916. %************************************************************************
  917. Note [Printing original names]
  918. ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  919. Deciding how to print names is pretty tricky. We are given a name
  920. P:M.T, where P is the package name, M is the defining module, and T is
  921. the occurrence name, and we have to decide in which form to display
  922. the name given a GlobalRdrEnv describing the current scope.
  923. Ideally we want to display the name in the form in which it is in
  924. scope. However, the name might not be in scope at all, and that's
  925. where it gets tricky. Here are the cases:
  926. 1. T uniquely maps to P:M.T ---> "T" NameUnqual
  927. 2. There is an X for which X.T
  928. uniquely maps to P:M.T ---> "X.T" NameQual X
  929. 3. There is no binding for "M.T" ---> "M.T" NameNotInScope1
  930. 4. Otherwise ---> "P:M.T" NameNotInScope2
  931. (3) and (4) apply when the entity P:M.T is not in the GlobalRdrEnv at
  932. all. In these cases we still want to refer to the name as "M.T", *but*
  933. "M.T" might mean something else in the current scope (e.g. if there's
  934. an "import X as M"), so to avoid confusion we avoid using "M.T" if
  935. there's already a binding for it. Instead we write P:M.T.
  936. There's one further subtlety: in case (3), what if there are two
  937. things around, P1:M.T and P2:M.T? Then we don't want to print both of
  938. them as M.T! However only one of the modules P1:M and P2:M can be
  939. exposed (say P2), so we use M.T for that, and P1:M.T for the other one.
  940. This is handled by the qual_mod component of PrintUnqualified, inside
  941. the (ppr mod) of case (3), in Name.pprModulePrefix
  942. \begin{code}
  943. -- | Creates some functions that work out the best ways to format
  944. -- names for the user according to a set of heuristics
  945. mkPrintUnqualified :: DynFlags -> GlobalRdrEnv -> PrintUnqualified
  946. mkPrintUnqualified dflags env = (qual_name, qual_mod)
  947. where
  948. qual_name name
  949. | [gre] <- unqual_gres, right_name gre = NameUnqual
  950. -- If there's a unique entity that's in scope unqualified with 'occ'
  951. -- AND that entity is the right one, then we can use the unqualified name
  952. | [gre] <- qual_gres = NameQual (get_qual_mod (gre_prov gre))
  953. | null qual_gres =
  954. if null (lookupGRE_RdrName (mkRdrQual (moduleName mod) occ) env)
  955. then NameNotInScope1
  956. else NameNotInScope2
  957. | otherwise = NameNotInScope1 -- Can happen if 'f' is bound twice in the module
  958. -- Eg f = True; g = 0; f = False
  959. where
  960. mod = nameModule name
  961. occ = nameOccName name
  962. is_rdr_orig = nameUnique name == mkUniqueGrimily 0
  963. -- Note [Outputable Orig RdrName]
  964. right_name gre
  965. | is_rdr_orig = nameModule_maybe (gre_name gre) == Just mod
  966. | otherwise = gre_name gre == name
  967. unqual_gres = lookupGRE_RdrName (mkRdrUnqual occ) env
  968. qual_gres = filter right_name (lookupGlobalRdrEnv env occ)
  969. get_qual_mod LocalDef = moduleName mod
  970. get_qual_mod (Imported is) = ASSERT( not (null is) ) is_as (is_decl (head is))
  971. -- we can mention a module P:M without the P: qualifier iff
  972. -- "import M" would resolve unambiguously to P:M. (if P is the
  973. -- current package we can just assume it is unqualified).
  974. qual_mod mod
  975. | modulePackageId mod == thisPackage dflags = False
  976. | [pkgconfig] <- [pkg | (pkg,exposed_module) <- lookup,
  977. exposed pkg && exposed_module],
  978. packageConfigId pkgconfig == modulePackageId mod
  979. -- this says: we are given a module P:M, is there just one exposed package
  980. -- that exposes a module M, and is it package P?
  981. = False
  982. | otherwise = True
  983. where lookup = lookupModuleInAllPackages dflags (moduleName mod)
  984. -- Note [Outputable Orig RdrName]
  985. -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  986. -- This is a Grotesque Hack. The Outputable instance for RdrEnv wants
  987. -- to print Orig names, which are just pairs of (Module,OccName). But
  988. -- we want to use full Names here, because in GHCi we might have Ids
  989. -- that have the same (Module,OccName)

Large files files are truncated, but you can click here to view the full file