PageRenderTime 61ms CodeModel.GetById 18ms RepoModel.GetById 0ms app.codeStats 0ms

/ghc-7.0.4/compiler/main/HscTypes.lhs

http://picorec.googlecode.com/
Haskell | 1710 lines | 887 code | 261 blank | 562 comment | 20 complexity | 644346083585be87dd13674e40378241 MD5 | raw file
Possible License(s): BSD-3-Clause, BSD-2-Clause

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. -- * 'Ghc' monad stuff
  9. Ghc(..), GhcT(..), liftGhcT,
  10. GhcMonad(..), WarnLogMonad(..),
  11. liftIO,
  12. ioMsgMaybe, ioMsg,
  13. logWarnings, clearWarnings, hasWarnings,
  14. SourceError, GhcApiError, mkSrcErr, srcErrorMessages, mkApiErr,
  15. throwOneError, handleSourceError,
  16. reflectGhc, reifyGhc,
  17. handleFlagWarnings,
  18. -- * Sessions and compilation state
  19. Session(..), withSession, modifySession, withTempSession,
  20. HscEnv(..), hscEPS,
  21. FinderCache, FindResult(..), ModLocationCache,
  22. Target(..), TargetId(..), pprTarget, pprTargetId,
  23. ModuleGraph, emptyMG,
  24. -- ** Callbacks
  25. GhcApiCallbacks(..), withLocalCallbacks,
  26. -- * Information about modules
  27. ModDetails(..), emptyModDetails,
  28. ModGuts(..), CoreModule(..), CgGuts(..), ForeignStubs(..),
  29. ImportedMods,
  30. ModSummary(..), ms_mod_name, showModMsg, isBootSummary,
  31. msHsFilePath, msHiFilePath, msObjFilePath,
  32. -- * Information about the module being compiled
  33. HscSource(..), isHsBoot, hscSourceString, -- Re-exported from DriverPhases
  34. -- * State relating to modules in this package
  35. HomePackageTable, HomeModInfo(..), emptyHomePackageTable,
  36. hptInstances, hptRules, hptVectInfo,
  37. -- * State relating to known packages
  38. ExternalPackageState(..), EpsStats(..), addEpsInStats,
  39. PackageTypeEnv, PackageIfaceTable, emptyPackageIfaceTable,
  40. lookupIfaceByModule, emptyModIface,
  41. PackageInstEnv, PackageRuleBase,
  42. -- * Annotations
  43. prepareAnnotations,
  44. -- * Interactive context
  45. InteractiveContext(..), emptyInteractiveContext,
  46. icPrintUnqual, extendInteractiveContext,
  47. substInteractiveContext,
  48. mkPrintUnqualified, pprModulePrefix,
  49. -- * Interfaces
  50. ModIface(..), mkIfaceWarnCache, mkIfaceHashCache, mkIfaceFixCache,
  51. emptyIfaceWarnCache,
  52. -- * Fixity
  53. FixityEnv, FixItem(..), lookupFixity, emptyFixityEnv,
  54. -- * TyThings and type environments
  55. TyThing(..),
  56. tyThingClass, tyThingTyCon, tyThingDataCon, tyThingId,
  57. implicitTyThings, isImplicitTyThing,
  58. TypeEnv, lookupType, lookupTypeHscEnv, mkTypeEnv, emptyTypeEnv,
  59. extendTypeEnv, extendTypeEnvList, extendTypeEnvWithIds, lookupTypeEnv,
  60. typeEnvElts, typeEnvClasses, typeEnvTyCons, typeEnvIds,
  61. typeEnvDataCons,
  62. -- * MonadThings
  63. MonadThings(..),
  64. -- * Information on imports and exports
  65. WhetherHasOrphans, IsBootInterface, Usage(..),
  66. Dependencies(..), noDependencies,
  67. NameCache(..), OrigNameCache, OrigIParamCache,
  68. Avails, availsToNameSet, availsToNameEnv, availName, availNames,
  69. GenAvailInfo(..), AvailInfo, RdrAvailInfo,
  70. IfaceExport,
  71. -- * Warnings
  72. Warnings(..), WarningTxt(..), plusWarns,
  73. -- * Linker stuff
  74. Linkable(..), isObjectLinkable,
  75. Unlinked(..), CompiledByteCode,
  76. isObject, nameOfObject, isInterpretable, byteCodeOfObject,
  77. -- * Program coverage
  78. HpcInfo(..), emptyHpcInfo, isHpcUsed, AnyHpcUsage,
  79. -- * Breakpoints
  80. ModBreaks (..), BreakIndex, emptyModBreaks,
  81. -- * Vectorisation information
  82. VectInfo(..), IfaceVectInfo(..), noVectInfo, plusVectInfo,
  83. noIfaceVectInfo
  84. ) where
  85. #include "HsVersions.h"
  86. #ifdef GHCI
  87. import ByteCodeAsm ( CompiledByteCode )
  88. import {-# SOURCE #-} InteractiveEval ( Resume )
  89. #endif
  90. import HsSyn
  91. import RdrName
  92. import Name
  93. import NameEnv
  94. import NameSet
  95. import Module
  96. import InstEnv ( InstEnv, Instance )
  97. import FamInstEnv ( FamInstEnv, FamInst )
  98. import Rules ( RuleBase )
  99. import CoreSyn ( CoreBind )
  100. import VarEnv
  101. import Var
  102. import Id
  103. import Type
  104. import Annotations
  105. import Class ( Class, classAllSelIds, classATs, classTyCon )
  106. import TyCon
  107. import DataCon ( DataCon, dataConImplicitIds, dataConWrapId )
  108. import PrelNames ( gHC_PRIM )
  109. import Packages hiding ( Version(..) )
  110. import DynFlags ( DynFlags(..), isOneShot, HscTarget (..), dopt,
  111. DynFlag(..) )
  112. import DriverPhases ( HscSource(..), isHsBoot, hscSourceString, Phase )
  113. import BasicTypes ( IPName, defaultFixity, WarningTxt(..) )
  114. import OptimizationFuel ( OptFuelState )
  115. import IfaceSyn
  116. import CoreSyn ( CoreRule )
  117. import Maybes ( orElse, expectJust, catMaybes )
  118. import Outputable
  119. import BreakArray
  120. import SrcLoc ( SrcSpan, Located(..) )
  121. import UniqFM ( lookupUFM, eltsUFM, emptyUFM )
  122. import UniqSupply ( UniqSupply )
  123. import FastString
  124. import StringBuffer ( StringBuffer )
  125. import Fingerprint
  126. import MonadUtils
  127. import Data.Dynamic ( Typeable )
  128. import qualified Data.Dynamic as Dyn
  129. import Bag
  130. import ErrUtils
  131. import System.FilePath
  132. import System.Time ( ClockTime )
  133. import Data.IORef
  134. import Data.Array ( Array, array )
  135. import Data.List
  136. import Data.Map (Map)
  137. import Control.Monad ( mplus, guard, liftM, when )
  138. import Exception
  139. \end{code}
  140. %************************************************************************
  141. %* *
  142. \subsection{Compilation environment}
  143. %* *
  144. %************************************************************************
  145. \begin{code}
  146. -- | The Session is a handle to the complete state of a compilation
  147. -- session. A compilation session consists of a set of modules
  148. -- constituting the current program or library, the context for
  149. -- interactive evaluation, and various caches.
  150. data Session = Session !(IORef HscEnv) !(IORef WarningMessages)
  151. mkSrcErr :: ErrorMessages -> SourceError
  152. srcErrorMessages :: SourceError -> ErrorMessages
  153. mkApiErr :: SDoc -> GhcApiError
  154. throwOneError :: MonadIO m => ErrMsg -> m ab
  155. throwOneError err = liftIO $ throwIO $ mkSrcErr $ unitBag err
  156. -- | A source error is an error that is caused by one or more errors in the
  157. -- source code. A 'SourceError' is thrown by many functions in the
  158. -- compilation pipeline. Inside GHC these errors are merely printed via
  159. -- 'log_action', but API clients may treat them differently, for example,
  160. -- insert them into a list box. If you want the default behaviour, use the
  161. -- idiom:
  162. --
  163. -- > handleSourceError printExceptionAndWarnings $ do
  164. -- > ... api calls that may fail ...
  165. --
  166. -- The 'SourceError's error messages can be accessed via 'srcErrorMessages'.
  167. -- This list may be empty if the compiler failed due to @-Werror@
  168. -- ('Opt_WarnIsError').
  169. --
  170. -- See 'printExceptionAndWarnings' for more information on what to take care
  171. -- of when writing a custom error handler.
  172. data SourceError = SourceError ErrorMessages
  173. instance Show SourceError where
  174. show (SourceError msgs) = unlines . map show . bagToList $ msgs
  175. -- ToDo: is there some nicer way to print this?
  176. sourceErrorTc :: Dyn.TyCon
  177. sourceErrorTc = Dyn.mkTyCon "SourceError"
  178. {-# NOINLINE sourceErrorTc #-}
  179. instance Typeable SourceError where
  180. typeOf _ = Dyn.mkTyConApp sourceErrorTc []
  181. instance Exception SourceError
  182. mkSrcErr = SourceError
  183. -- | Perform the given action and call the exception handler if the action
  184. -- throws a 'SourceError'. See 'SourceError' for more information.
  185. handleSourceError :: (ExceptionMonad m) =>
  186. (SourceError -> m a) -- ^ exception handler
  187. -> m a -- ^ action to perform
  188. -> m a
  189. handleSourceError handler act =
  190. gcatch act (\(e :: SourceError) -> handler e)
  191. srcErrorMessages (SourceError msgs) = msgs
  192. -- | XXX: what exactly is an API error?
  193. data GhcApiError = GhcApiError SDoc
  194. instance Show GhcApiError where
  195. show (GhcApiError msg) = showSDoc msg
  196. ghcApiErrorTc :: Dyn.TyCon
  197. ghcApiErrorTc = Dyn.mkTyCon "GhcApiError"
  198. {-# NOINLINE ghcApiErrorTc #-}
  199. instance Typeable GhcApiError where
  200. typeOf _ = Dyn.mkTyConApp ghcApiErrorTc []
  201. instance Exception GhcApiError
  202. mkApiErr = GhcApiError
  203. -- | A monad that allows logging of warnings.
  204. class Monad m => WarnLogMonad m where
  205. setWarnings :: WarningMessages -> m ()
  206. getWarnings :: m WarningMessages
  207. logWarnings :: WarnLogMonad m => WarningMessages -> m ()
  208. logWarnings warns = do
  209. warns0 <- getWarnings
  210. setWarnings (unionBags warns warns0)
  211. -- | Clear the log of 'Warnings'.
  212. clearWarnings :: WarnLogMonad m => m ()
  213. clearWarnings = setWarnings emptyBag
  214. -- | Returns true if there were any warnings.
  215. hasWarnings :: WarnLogMonad m => m Bool
  216. hasWarnings = getWarnings >>= return . not . isEmptyBag
  217. -- | A monad that has all the features needed by GHC API calls.
  218. --
  219. -- In short, a GHC monad
  220. --
  221. -- - allows embedding of IO actions,
  222. --
  223. -- - can log warnings,
  224. --
  225. -- - allows handling of (extensible) exceptions, and
  226. --
  227. -- - maintains a current session.
  228. --
  229. -- If you do not use 'Ghc' or 'GhcT', make sure to call 'GHC.initGhcMonad'
  230. -- before any call to the GHC API functions can occur.
  231. --
  232. class (Functor m, MonadIO m, WarnLogMonad m, ExceptionMonad m)
  233. => GhcMonad m where
  234. getSession :: m HscEnv
  235. setSession :: HscEnv -> m ()
  236. -- | Call the argument with the current session.
  237. withSession :: GhcMonad m => (HscEnv -> m a) -> m a
  238. withSession f = getSession >>= f
  239. -- | Set the current session to the result of applying the current session to
  240. -- the argument.
  241. modifySession :: GhcMonad m => (HscEnv -> HscEnv) -> m ()
  242. modifySession f = do h <- getSession
  243. setSession $! f h
  244. withSavedSession :: GhcMonad m => m a -> m a
  245. withSavedSession m = do
  246. saved_session <- getSession
  247. m `gfinally` setSession saved_session
  248. -- | Call an action with a temporarily modified Session.
  249. withTempSession :: GhcMonad m => (HscEnv -> HscEnv) -> m a -> m a
  250. withTempSession f m =
  251. withSavedSession $ modifySession f >> m
  252. -- | A minimal implementation of a 'GhcMonad'. If you need a custom monad,
  253. -- e.g., to maintain additional state consider wrapping this monad or using
  254. -- 'GhcT'.
  255. newtype Ghc a = Ghc { unGhc :: Session -> IO a }
  256. instance Functor Ghc where
  257. fmap f m = Ghc $ \s -> f `fmap` unGhc m s
  258. instance Monad Ghc where
  259. return a = Ghc $ \_ -> return a
  260. m >>= g = Ghc $ \s -> do a <- unGhc m s; unGhc (g a) s
  261. instance MonadIO Ghc where
  262. liftIO ioA = Ghc $ \_ -> ioA
  263. instance ExceptionMonad Ghc where
  264. gcatch act handle =
  265. Ghc $ \s -> unGhc act s `gcatch` \e -> unGhc (handle e) s
  266. gblock (Ghc m) = Ghc $ \s -> gblock (m s)
  267. gunblock (Ghc m) = Ghc $ \s -> gunblock (m s)
  268. gmask f =
  269. Ghc $ \s -> gmask $ \io_restore ->
  270. let
  271. g_restore (Ghc m) = Ghc $ \s -> io_restore (m s)
  272. in
  273. unGhc (f g_restore) s
  274. instance WarnLogMonad Ghc where
  275. setWarnings warns = Ghc $ \(Session _ wref) -> writeIORef wref warns
  276. -- | Return 'Warnings' accumulated so far.
  277. getWarnings = Ghc $ \(Session _ wref) -> readIORef wref
  278. instance GhcMonad Ghc where
  279. getSession = Ghc $ \(Session r _) -> readIORef r
  280. setSession s' = Ghc $ \(Session r _) -> writeIORef r s'
  281. -- | A monad transformer to add GHC specific features to another monad.
  282. --
  283. -- Note that the wrapped monad must support IO and handling of exceptions.
  284. newtype GhcT m a = GhcT { unGhcT :: Session -> m a }
  285. liftGhcT :: Monad m => m a -> GhcT m a
  286. liftGhcT m = GhcT $ \_ -> m
  287. instance Functor m => Functor (GhcT m) where
  288. fmap f m = GhcT $ \s -> f `fmap` unGhcT m s
  289. instance Monad m => Monad (GhcT m) where
  290. return x = GhcT $ \_ -> return x
  291. m >>= k = GhcT $ \s -> do a <- unGhcT m s; unGhcT (k a) s
  292. instance MonadIO m => MonadIO (GhcT m) where
  293. liftIO ioA = GhcT $ \_ -> liftIO ioA
  294. instance ExceptionMonad m => ExceptionMonad (GhcT m) where
  295. gcatch act handle =
  296. GhcT $ \s -> unGhcT act s `gcatch` \e -> unGhcT (handle e) s
  297. gblock (GhcT m) = GhcT $ \s -> gblock (m s)
  298. gunblock (GhcT m) = GhcT $ \s -> gunblock (m s)
  299. gmask f =
  300. GhcT $ \s -> gmask $ \io_restore ->
  301. let
  302. g_restore (GhcT m) = GhcT $ \s -> io_restore (m s)
  303. in
  304. unGhcT (f g_restore) s
  305. instance MonadIO m => WarnLogMonad (GhcT m) where
  306. setWarnings warns = GhcT $ \(Session _ wref) -> liftIO $ writeIORef wref warns
  307. -- | Return 'Warnings' accumulated so far.
  308. getWarnings = GhcT $ \(Session _ wref) -> liftIO $ readIORef wref
  309. instance (Functor m, ExceptionMonad m, MonadIO m) => GhcMonad (GhcT m) where
  310. getSession = GhcT $ \(Session r _) -> liftIO $ readIORef r
  311. setSession s' = GhcT $ \(Session r _) -> liftIO $ writeIORef r s'
  312. -- | Lift an IO action returning errors messages into a 'GhcMonad'.
  313. --
  314. -- In order to reduce dependencies to other parts of the compiler, functions
  315. -- outside the "main" parts of GHC return warnings and errors as a parameter
  316. -- and signal success via by wrapping the result in a 'Maybe' type. This
  317. -- function logs the returned warnings and propagates errors as exceptions
  318. -- (of type 'SourceError').
  319. --
  320. -- This function assumes the following invariants:
  321. --
  322. -- 1. If the second result indicates success (is of the form 'Just x'),
  323. -- there must be no error messages in the first result.
  324. --
  325. -- 2. If there are no error messages, but the second result indicates failure
  326. -- there should be warnings in the first result. That is, if the action
  327. -- failed, it must have been due to the warnings (i.e., @-Werror@).
  328. ioMsgMaybe :: GhcMonad m =>
  329. IO (Messages, Maybe a) -> m a
  330. ioMsgMaybe ioA = do
  331. ((warns,errs), mb_r) <- liftIO ioA
  332. logWarnings warns
  333. case mb_r of
  334. Nothing -> liftIO $ throwIO (mkSrcErr errs)
  335. Just r -> ASSERT( isEmptyBag errs ) return r
  336. -- | Lift a non-failing IO action into a 'GhcMonad'.
  337. --
  338. -- Like 'ioMsgMaybe', but assumes that the action will never return any error
  339. -- messages.
  340. ioMsg :: GhcMonad m => IO (Messages, a) -> m a
  341. ioMsg ioA = do
  342. ((warns,errs), r) <- liftIO ioA
  343. logWarnings warns
  344. ASSERT( isEmptyBag errs ) return r
  345. -- | Reflect a computation in the 'Ghc' monad into the 'IO' monad.
  346. --
  347. -- You can use this to call functions returning an action in the 'Ghc' monad
  348. -- inside an 'IO' action. This is needed for some (too restrictive) callback
  349. -- arguments of some library functions:
  350. --
  351. -- > libFunc :: String -> (Int -> IO a) -> IO a
  352. -- > ghcFunc :: Int -> Ghc a
  353. -- >
  354. -- > ghcFuncUsingLibFunc :: String -> Ghc a -> Ghc a
  355. -- > ghcFuncUsingLibFunc str =
  356. -- > reifyGhc $ \s ->
  357. -- > libFunc $ \i -> do
  358. -- > reflectGhc (ghcFunc i) s
  359. --
  360. reflectGhc :: Ghc a -> Session -> IO a
  361. reflectGhc m = unGhc m
  362. -- > Dual to 'reflectGhc'. See its documentation.
  363. reifyGhc :: (Session -> IO a) -> Ghc a
  364. reifyGhc act = Ghc $ act
  365. handleFlagWarnings :: GhcMonad m => DynFlags -> [Located String] -> m ()
  366. handleFlagWarnings dflags warns
  367. = when (dopt Opt_WarnDeprecatedFlags dflags)
  368. (handleFlagWarnings' dflags warns)
  369. handleFlagWarnings' :: GhcMonad m => DynFlags -> [Located String] -> m ()
  370. handleFlagWarnings' _ [] = return ()
  371. handleFlagWarnings' dflags warns
  372. = do -- It would be nicer if warns :: [Located Message], but that has circular
  373. -- import problems.
  374. logWarnings $ listToBag (map mkFlagWarning warns)
  375. when (dopt Opt_WarnIsError dflags) $
  376. liftIO $ throwIO $ mkSrcErr emptyBag
  377. mkFlagWarning :: Located String -> WarnMsg
  378. mkFlagWarning (L loc warn)
  379. = mkPlainWarnMsg loc (text warn)
  380. \end{code}
  381. \begin{code}
  382. -- | These functions are called in various places of the GHC API.
  383. --
  384. -- API clients can override any of these callbacks to change GHC's default
  385. -- behaviour.
  386. data GhcApiCallbacks
  387. = GhcApiCallbacks {
  388. -- | Called by 'load' after the compilating of each module.
  389. --
  390. -- The default implementation simply prints all warnings and errors to
  391. -- @stderr@. Don't forget to call 'clearWarnings' when implementing your
  392. -- own call.
  393. --
  394. -- The first argument is the module that was compiled.
  395. --
  396. -- The second argument is @Nothing@ if no errors occured, but there may
  397. -- have been warnings. If it is @Just err@ at least one error has
  398. -- occured. If 'srcErrorMessages' is empty, compilation failed due to
  399. -- @-Werror@.
  400. reportModuleCompilationResult :: GhcMonad m =>
  401. ModSummary -> Maybe SourceError
  402. -> m ()
  403. }
  404. -- | Temporarily modify the callbacks. After the action is executed all
  405. -- callbacks are reset (not, however, any other modifications to the session
  406. -- state.)
  407. withLocalCallbacks :: GhcMonad m =>
  408. (GhcApiCallbacks -> GhcApiCallbacks)
  409. -> m a -> m a
  410. withLocalCallbacks f m = do
  411. hsc_env <- getSession
  412. let cb0 = hsc_callbacks hsc_env
  413. let cb' = f cb0
  414. setSession (hsc_env { hsc_callbacks = cb' `seq` cb' })
  415. r <- m
  416. hsc_env' <- getSession
  417. setSession (hsc_env' { hsc_callbacks = cb0 })
  418. return r
  419. \end{code}
  420. \begin{code}
  421. -- | Hscenv is like 'Session', except that some of the fields are immutable.
  422. -- An HscEnv is used to compile a single module from plain Haskell source
  423. -- code (after preprocessing) to either C, assembly or C--. Things like
  424. -- the module graph don't change during a single compilation.
  425. --
  426. -- Historical note: \"hsc\" used to be the name of the compiler binary,
  427. -- when there was a separate driver and compiler. To compile a single
  428. -- module, the driver would invoke hsc on the source code... so nowadays
  429. -- we think of hsc as the layer of the compiler that deals with compiling
  430. -- a single module.
  431. data HscEnv
  432. = HscEnv {
  433. hsc_dflags :: DynFlags,
  434. -- ^ The dynamic flag settings
  435. hsc_callbacks :: GhcApiCallbacks,
  436. -- ^ Callbacks for the GHC API.
  437. hsc_targets :: [Target],
  438. -- ^ The targets (or roots) of the current session
  439. hsc_mod_graph :: ModuleGraph,
  440. -- ^ The module graph of the current session
  441. hsc_IC :: InteractiveContext,
  442. -- ^ The context for evaluating interactive statements
  443. hsc_HPT :: HomePackageTable,
  444. -- ^ The home package table describes already-compiled
  445. -- home-package modules, /excluding/ the module we
  446. -- are compiling right now.
  447. -- (In one-shot mode the current module is the only
  448. -- home-package module, so hsc_HPT is empty. All other
  449. -- modules count as \"external-package\" modules.
  450. -- However, even in GHCi mode, hi-boot interfaces are
  451. -- demand-loaded into the external-package table.)
  452. --
  453. -- 'hsc_HPT' is not mutable because we only demand-load
  454. -- external packages; the home package is eagerly
  455. -- loaded, module by module, by the compilation manager.
  456. --
  457. -- The HPT may contain modules compiled earlier by @--make@
  458. -- but not actually below the current module in the dependency
  459. -- graph.
  460. -- (This changes a previous invariant: changed Jan 05.)
  461. hsc_EPS :: {-# UNPACK #-} !(IORef ExternalPackageState),
  462. -- ^ Information about the currently loaded external packages.
  463. -- This is mutable because packages will be demand-loaded during
  464. -- a compilation run as required.
  465. hsc_NC :: {-# UNPACK #-} !(IORef NameCache),
  466. -- ^ As with 'hsc_EPS', this is side-effected by compiling to
  467. -- reflect sucking in interface files. They cache the state of
  468. -- external interface files, in effect.
  469. hsc_FC :: {-# UNPACK #-} !(IORef FinderCache),
  470. -- ^ The cached result of performing finding in the file system
  471. hsc_MLC :: {-# UNPACK #-} !(IORef ModLocationCache),
  472. -- ^ This caches the location of modules, so we don't have to
  473. -- search the filesystem multiple times. See also 'hsc_FC'.
  474. hsc_OptFuel :: OptFuelState,
  475. -- ^ Settings to control the use of \"optimization fuel\":
  476. -- by limiting the number of transformations,
  477. -- we can use binary search to help find compiler bugs.
  478. hsc_type_env_var :: Maybe (Module, IORef TypeEnv)
  479. -- ^ Used for one-shot compilation only, to initialise
  480. -- the 'IfGblEnv'. See 'TcRnTypes.tcg_type_env_var' for
  481. -- 'TcRunTypes.TcGblEnv'
  482. }
  483. hscEPS :: HscEnv -> IO ExternalPackageState
  484. hscEPS hsc_env = readIORef (hsc_EPS hsc_env)
  485. -- | A compilation target.
  486. --
  487. -- A target may be supplied with the actual text of the
  488. -- module. If so, use this instead of the file contents (this
  489. -- is for use in an IDE where the file hasn't been saved by
  490. -- the user yet).
  491. data Target = Target
  492. { targetId :: TargetId -- ^ module or filename
  493. , targetAllowObjCode :: Bool -- ^ object code allowed?
  494. , targetContents :: Maybe (StringBuffer,ClockTime)
  495. -- ^ in-memory text buffer?
  496. }
  497. data TargetId
  498. = TargetModule ModuleName
  499. -- ^ A module name: search for the file
  500. | TargetFile FilePath (Maybe Phase)
  501. -- ^ A filename: preprocess & parse it to find the module name.
  502. -- If specified, the Phase indicates how to compile this file
  503. -- (which phase to start from). Nothing indicates the starting phase
  504. -- should be determined from the suffix of the filename.
  505. deriving Eq
  506. pprTarget :: Target -> SDoc
  507. pprTarget (Target id obj _) =
  508. (if obj then char '*' else empty) <> pprTargetId id
  509. instance Outputable Target where
  510. ppr = pprTarget
  511. pprTargetId :: TargetId -> SDoc
  512. pprTargetId (TargetModule m) = ppr m
  513. pprTargetId (TargetFile f _) = text f
  514. instance Outputable TargetId where
  515. ppr = pprTargetId
  516. -- | Helps us find information about modules in the home package
  517. type HomePackageTable = ModuleNameEnv HomeModInfo
  518. -- Domain = modules in the home package that have been fully compiled
  519. -- "home" package name cached here for convenience
  520. -- | Helps us find information about modules in the imported packages
  521. type PackageIfaceTable = ModuleEnv ModIface
  522. -- Domain = modules in the imported packages
  523. emptyHomePackageTable :: HomePackageTable
  524. emptyHomePackageTable = emptyUFM
  525. emptyPackageIfaceTable :: PackageIfaceTable
  526. emptyPackageIfaceTable = emptyModuleEnv
  527. -- | Information about modules in the package being compiled
  528. data HomeModInfo
  529. = HomeModInfo {
  530. hm_iface :: !ModIface,
  531. -- ^ The basic loaded interface file: every loaded module has one of
  532. -- these, even if it is imported from another package
  533. hm_details :: !ModDetails,
  534. -- ^ Extra information that has been created from the 'ModIface' for
  535. -- the module, typically during typechecking
  536. hm_linkable :: !(Maybe Linkable)
  537. -- ^ The actual artifact we would like to link to access things in
  538. -- this module.
  539. --
  540. -- 'hm_linkable' might be Nothing:
  541. --
  542. -- 1. If this is an .hs-boot module
  543. --
  544. -- 2. Temporarily during compilation if we pruned away
  545. -- the old linkable because it was out of date.
  546. --
  547. -- After a complete compilation ('GHC.load'), all 'hm_linkable' fields
  548. -- in the 'HomePackageTable' will be @Just@.
  549. --
  550. -- When re-linking a module ('HscMain.HscNoRecomp'), we construct the
  551. -- 'HomeModInfo' by building a new 'ModDetails' from the old
  552. -- 'ModIface' (only).
  553. }
  554. -- | Find the 'ModIface' for a 'Module', searching in both the loaded home
  555. -- and external package module information
  556. lookupIfaceByModule
  557. :: DynFlags
  558. -> HomePackageTable
  559. -> PackageIfaceTable
  560. -> Module
  561. -> Maybe ModIface
  562. lookupIfaceByModule dflags hpt pit mod
  563. | modulePackageId mod == thisPackage dflags
  564. = -- The module comes from the home package, so look first
  565. -- in the HPT. If it's not from the home package it's wrong to look
  566. -- in the HPT, because the HPT is indexed by *ModuleName* not Module
  567. fmap hm_iface (lookupUFM hpt (moduleName mod))
  568. `mplus` lookupModuleEnv pit mod
  569. | otherwise = lookupModuleEnv pit mod -- Look in PIT only
  570. -- If the module does come from the home package, why do we look in the PIT as well?
  571. -- (a) In OneShot mode, even home-package modules accumulate in the PIT
  572. -- (b) Even in Batch (--make) mode, there is *one* case where a home-package
  573. -- module is in the PIT, namely GHC.Prim when compiling the base package.
  574. -- We could eliminate (b) if we wanted, by making GHC.Prim belong to a package
  575. -- of its own, but it doesn't seem worth the bother.
  576. \end{code}
  577. \begin{code}
  578. hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([Instance], [FamInst])
  579. -- ^ Find all the instance declarations (of classes and families) that are in
  580. -- modules imported by this one, directly or indirectly, and are in the Home
  581. -- Package Table. This ensures that we don't see instances from modules @--make@
  582. -- compiled before this one, but which are not below this one.
  583. hptInstances hsc_env want_this_module
  584. = let (insts, famInsts) = unzip $ flip hptAllThings hsc_env $ \mod_info -> do
  585. guard (want_this_module (moduleName (mi_module (hm_iface mod_info))))
  586. let details = hm_details mod_info
  587. return (md_insts details, md_fam_insts details)
  588. in (concat insts, concat famInsts)
  589. hptVectInfo :: HscEnv -> VectInfo
  590. -- ^ Get the combined VectInfo of all modules in the home package table. In
  591. -- contrast to instances and rules, we don't care whether the modules are
  592. -- \"below\" us in the dependency sense. The VectInfo of those modules not \"below\"
  593. -- us does not affect the compilation of the current module.
  594. hptVectInfo = concatVectInfo . hptAllThings ((: []) . md_vect_info . hm_details)
  595. hptRules :: HscEnv -> [(ModuleName, IsBootInterface)] -> [CoreRule]
  596. -- ^ Get rules from modules \"below\" this one (in the dependency sense)
  597. hptRules = hptSomeThingsBelowUs (md_rules . hm_details) False
  598. hptAnns :: HscEnv -> Maybe [(ModuleName, IsBootInterface)] -> [Annotation]
  599. -- ^ Get annotations from modules \"below\" this one (in the dependency sense)
  600. hptAnns hsc_env (Just deps) = hptSomeThingsBelowUs (md_anns . hm_details) False hsc_env deps
  601. hptAnns hsc_env Nothing = hptAllThings (md_anns . hm_details) hsc_env
  602. hptAllThings :: (HomeModInfo -> [a]) -> HscEnv -> [a]
  603. hptAllThings extract hsc_env = concatMap extract (eltsUFM (hsc_HPT hsc_env))
  604. hptSomeThingsBelowUs :: (HomeModInfo -> [a]) -> Bool -> HscEnv -> [(ModuleName, IsBootInterface)] -> [a]
  605. -- Get things from modules \"below\" this one (in the dependency sense)
  606. -- C.f Inst.hptInstances
  607. hptSomeThingsBelowUs extract include_hi_boot hsc_env deps
  608. | isOneShot (ghcMode (hsc_dflags hsc_env)) = []
  609. | otherwise
  610. = let
  611. hpt = hsc_HPT hsc_env
  612. in
  613. [ thing
  614. | -- Find each non-hi-boot module below me
  615. (mod, is_boot_mod) <- deps
  616. , include_hi_boot || not is_boot_mod
  617. -- unsavoury: when compiling the base package with --make, we
  618. -- sometimes try to look up RULES etc for GHC.Prim. GHC.Prim won't
  619. -- be in the HPT, because we never compile it; it's in the EPT
  620. -- instead. ToDo: clean up, and remove this slightly bogus
  621. -- filter:
  622. , mod /= moduleName gHC_PRIM
  623. -- Look it up in the HPT
  624. , let things = case lookupUFM hpt mod of
  625. Just info -> extract info
  626. Nothing -> pprTrace "WARNING in hptSomeThingsBelowUs" msg []
  627. msg = vcat [ptext (sLit "missing module") <+> ppr mod,
  628. ptext (sLit "Probable cause: out-of-date interface files")]
  629. -- This really shouldn't happen, but see Trac #962
  630. -- And get its dfuns
  631. , thing <- things ]
  632. \end{code}
  633. %************************************************************************
  634. %* *
  635. \subsection{Dealing with Annotations}
  636. %* *
  637. %************************************************************************
  638. \begin{code}
  639. prepareAnnotations :: HscEnv -> Maybe ModGuts -> IO AnnEnv
  640. -- ^ Deal with gathering annotations in from all possible places
  641. -- and combining them into a single 'AnnEnv'
  642. prepareAnnotations hsc_env mb_guts
  643. = do { eps <- hscEPS hsc_env
  644. ; let -- Extract annotations from the module being compiled if supplied one
  645. mb_this_module_anns = fmap (mkAnnEnv . mg_anns) mb_guts
  646. -- Extract dependencies of the module if we are supplied one,
  647. -- otherwise load annotations from all home package table
  648. -- entries regardless of dependency ordering.
  649. home_pkg_anns = (mkAnnEnv . hptAnns hsc_env) $ fmap (dep_mods . mg_deps) mb_guts
  650. other_pkg_anns = eps_ann_env eps
  651. ann_env = foldl1' plusAnnEnv $ catMaybes [mb_this_module_anns,
  652. Just home_pkg_anns,
  653. Just other_pkg_anns]
  654. ; return ann_env }
  655. \end{code}
  656. %************************************************************************
  657. %* *
  658. \subsection{The Finder cache}
  659. %* *
  660. %************************************************************************
  661. \begin{code}
  662. -- | The 'FinderCache' maps home module names to the result of
  663. -- searching for that module. It records the results of searching for
  664. -- modules along the search path. On @:load@, we flush the entire
  665. -- contents of this cache.
  666. --
  667. -- Although the @FinderCache@ range is 'FindResult' for convenience ,
  668. -- in fact it will only ever contain 'Found' or 'NotFound' entries.
  669. --
  670. type FinderCache = ModuleNameEnv FindResult
  671. -- | The result of searching for an imported module.
  672. data FindResult
  673. = Found ModLocation Module
  674. -- ^ The module was found
  675. | NoPackage PackageId
  676. -- ^ The requested package was not found
  677. | FoundMultiple [PackageId]
  678. -- ^ _Error_: both in multiple packages
  679. | NotFound [FilePath] (Maybe PackageId) [PackageId] [PackageId]
  680. -- ^ The module was not found, including either
  681. -- * the specified places were searched
  682. -- * the package that this module should have been in
  683. -- * list of packages in which the module was hidden,
  684. -- * list of hidden packages containing this module
  685. | NotFoundInPackage PackageId
  686. -- ^ The module was not found in this package
  687. -- | Cache that remembers where we found a particular module. Contains both
  688. -- home modules and package modules. On @:load@, only home modules are
  689. -- purged from this cache.
  690. type ModLocationCache = ModuleEnv ModLocation
  691. \end{code}
  692. %************************************************************************
  693. %* *
  694. \subsection{Symbol tables and Module details}
  695. %* *
  696. %************************************************************************
  697. \begin{code}
  698. -- | A 'ModIface' plus a 'ModDetails' summarises everything we know
  699. -- about a compiled module. The 'ModIface' is the stuff *before* linking,
  700. -- and can be written out to an interface file. The 'ModDetails is after
  701. -- linking and can be completely recovered from just the 'ModIface'.
  702. --
  703. -- When we read an interface file, we also construct a 'ModIface' from it,
  704. -- except that we explicitly make the 'mi_decls' and a few other fields empty;
  705. -- as when reading we consolidate the declarations etc. into a number of indexed
  706. -- maps and environments in the 'ExternalPackageState'.
  707. data ModIface
  708. = ModIface {
  709. mi_module :: !Module, -- ^ Name of the module we are for
  710. mi_iface_hash :: !Fingerprint, -- ^ Hash of the whole interface
  711. mi_mod_hash :: !Fingerprint, -- ^ Hash of the ABI only
  712. mi_orphan :: !WhetherHasOrphans, -- ^ Whether this module has orphans
  713. mi_finsts :: !WhetherHasFamInst, -- ^ Whether this module has family instances
  714. mi_boot :: !IsBootInterface, -- ^ Read from an hi-boot file?
  715. mi_deps :: Dependencies,
  716. -- ^ The dependencies of the module. This is
  717. -- consulted for directly-imported modules, but not
  718. -- for anything else (hence lazy)
  719. mi_usages :: [Usage],
  720. -- ^ Usages; kept sorted so that it's easy to decide
  721. -- whether to write a new iface file (changing usages
  722. -- doesn't affect the hash of this module)
  723. -- NOT STRICT! we read this field lazily from the interface file
  724. -- It is *only* consulted by the recompilation checker
  725. -- Exports
  726. -- Kept sorted by (mod,occ), to make version comparisons easier
  727. mi_exports :: ![IfaceExport],
  728. -- ^ Records the modules that are the declaration points for things
  729. -- exported by this module, and the 'OccName's of those things
  730. mi_exp_hash :: !Fingerprint, -- ^ Hash of export list
  731. mi_fixities :: [(OccName,Fixity)],
  732. -- ^ Fixities
  733. -- NOT STRICT! we read this field lazily from the interface file
  734. mi_warns :: Warnings,
  735. -- ^ Warnings
  736. -- NOT STRICT! we read this field lazily from the interface file
  737. mi_anns :: [IfaceAnnotation],
  738. -- ^ Annotations
  739. -- NOT STRICT! we read this field lazily from the interface file
  740. -- Type, class and variable declarations
  741. -- The hash of an Id changes if its fixity or deprecations change
  742. -- (as well as its type of course)
  743. -- Ditto data constructors, class operations, except that
  744. -- the hash of the parent class/tycon changes
  745. mi_decls :: [(Fingerprint,IfaceDecl)], -- ^ Sorted type, variable, class etc. declarations
  746. mi_globals :: !(Maybe GlobalRdrEnv),
  747. -- ^ Binds all the things defined at the top level in
  748. -- the /original source/ code for this module. which
  749. -- is NOT the same as mi_exports, nor mi_decls (which
  750. -- may contains declarations for things not actually
  751. -- defined by the user). Used for GHCi and for inspecting
  752. -- the contents of modules via the GHC API only.
  753. --
  754. -- (We need the source file to figure out the
  755. -- top-level environment, if we didn't compile this module
  756. -- from source then this field contains @Nothing@).
  757. --
  758. -- Strictly speaking this field should live in the
  759. -- 'HomeModInfo', but that leads to more plumbing.
  760. -- Instance declarations and rules
  761. mi_insts :: [IfaceInst], -- ^ Sorted class instance
  762. mi_fam_insts :: [IfaceFamInst], -- ^ Sorted family instances
  763. mi_rules :: [IfaceRule], -- ^ Sorted rules
  764. mi_orphan_hash :: !Fingerprint, -- ^ Hash for orphan rules and
  765. -- class and family instances
  766. -- combined
  767. mi_vect_info :: !IfaceVectInfo, -- ^ Vectorisation information
  768. -- Cached environments for easy lookup
  769. -- These are computed (lazily) from other fields
  770. -- and are not put into the interface file
  771. mi_warn_fn :: Name -> Maybe WarningTxt, -- ^ Cached lookup for 'mi_warns'
  772. mi_fix_fn :: OccName -> Fixity, -- ^ Cached lookup for 'mi_fixities'
  773. mi_hash_fn :: OccName -> Maybe (OccName, Fingerprint),
  774. -- ^ Cached lookup for 'mi_decls'.
  775. -- The @Nothing@ in 'mi_hash_fn' means that the thing
  776. -- isn't in decls. It's useful to know that when
  777. -- seeing if we are up to date wrt. the old interface.
  778. -- The 'OccName' is the parent of the name, if it has one.
  779. mi_hpc :: !AnyHpcUsage
  780. -- ^ True if this program uses Hpc at any point in the program.
  781. }
  782. -- | The 'ModDetails' is essentially a cache for information in the 'ModIface'
  783. -- for home modules only. Information relating to packages will be loaded into
  784. -- global environments in 'ExternalPackageState'.
  785. data ModDetails
  786. = ModDetails {
  787. -- The next two fields are created by the typechecker
  788. md_exports :: [AvailInfo],
  789. md_types :: !TypeEnv, -- ^ Local type environment for this particular module
  790. md_insts :: ![Instance], -- ^ 'DFunId's for the instances in this module
  791. md_fam_insts :: ![FamInst],
  792. md_rules :: ![CoreRule], -- ^ Domain may include 'Id's from other modules
  793. md_anns :: ![Annotation], -- ^ Annotations present in this module: currently
  794. -- they only annotate things also declared in this module
  795. md_vect_info :: !VectInfo -- ^ Module vectorisation information
  796. }
  797. emptyModDetails :: ModDetails
  798. emptyModDetails = ModDetails { md_types = emptyTypeEnv,
  799. md_exports = [],
  800. md_insts = [],
  801. md_rules = [],
  802. md_fam_insts = [],
  803. md_anns = [],
  804. md_vect_info = noVectInfo
  805. }
  806. -- | Records the modules directly imported by a module for extracting e.g. usage information
  807. type ImportedMods = ModuleEnv [(ModuleName, Bool, SrcSpan)]
  808. -- TODO: we are not actually using the codomain of this type at all, so it can be
  809. -- replaced with ModuleEnv ()
  810. -- | A ModGuts is carried through the compiler, accumulating stuff as it goes
  811. -- There is only one ModGuts at any time, the one for the module
  812. -- being compiled right now. Once it is compiled, a 'ModIface' and
  813. -- 'ModDetails' are extracted and the ModGuts is dicarded.
  814. data ModGuts
  815. = ModGuts {
  816. mg_module :: !Module, -- ^ Module being compiled
  817. mg_boot :: IsBootInterface, -- ^ Whether it's an hs-boot module
  818. mg_exports :: ![AvailInfo], -- ^ What it exports
  819. mg_deps :: !Dependencies, -- ^ What it depends on, directly or
  820. -- otherwise
  821. mg_dir_imps :: !ImportedMods, -- ^ Directly-imported modules; used to
  822. -- generate initialisation code
  823. mg_used_names:: !NameSet, -- ^ What the module needed (used in 'MkIface.mkIface')
  824. mg_rdr_env :: !GlobalRdrEnv, -- ^ Top-level lexical environment
  825. -- These fields all describe the things **declared in this module**
  826. mg_fix_env :: !FixityEnv, -- ^ Fixities declared in this module
  827. -- TODO: I'm unconvinced this is actually used anywhere
  828. mg_types :: !TypeEnv, -- ^ Types declared in this module
  829. mg_insts :: ![Instance], -- ^ Class instances declared in this module
  830. mg_fam_insts :: ![FamInst], -- ^ Family instances declared in this module
  831. mg_rules :: ![CoreRule], -- ^ Before the core pipeline starts, contains
  832. -- See Note [Overall plumbing for rules] in Rules.lhs
  833. mg_binds :: ![CoreBind], -- ^ Bindings for this module
  834. mg_foreign :: !ForeignStubs, -- ^ Foreign exports declared in this module
  835. mg_warns :: !Warnings, -- ^ Warnings declared in the module
  836. mg_anns :: [Annotation], -- ^ Annotations declared in this module
  837. mg_hpc_info :: !HpcInfo, -- ^ Coverage tick boxes in the module
  838. mg_modBreaks :: !ModBreaks, -- ^ Breakpoints for the module
  839. mg_vect_info :: !VectInfo, -- ^ Pool of vectorised declarations in the module
  840. -- The next two fields are unusual, because they give instance
  841. -- environments for *all* modules in the home package, including
  842. -- this module, rather than for *just* this module.
  843. -- Reason: when looking up an instance we don't want to have to
  844. -- look at each module in the home package in turn
  845. mg_inst_env :: InstEnv,
  846. -- ^ Class instance environment from /home-package/ modules (including
  847. -- this one); c.f. 'tcg_inst_env'
  848. mg_fam_inst_env :: FamInstEnv
  849. -- ^ Type-family instance enviroment for /home-package/ modules
  850. -- (including this one); c.f. 'tcg_fam_inst_env'
  851. }
  852. -- The ModGuts takes on several slightly different forms:
  853. --
  854. -- After simplification, the following fields change slightly:
  855. -- mg_rules Orphan rules only (local ones now attached to binds)
  856. -- mg_binds With rules attached
  857. -- | A CoreModule consists of just the fields of a 'ModGuts' that are needed for
  858. -- the 'GHC.compileToCoreModule' interface.
  859. data CoreModule
  860. = CoreModule {
  861. -- | Module name
  862. cm_module :: !Module,
  863. -- | Type environment for types declared in this module
  864. cm_types :: !TypeEnv,
  865. -- | Declarations
  866. cm_binds :: [CoreBind],
  867. -- | Imports
  868. cm_imports :: ![Module]
  869. }
  870. instance Outputable CoreModule where
  871. ppr (CoreModule {cm_module = mn, cm_types = te, cm_binds = cb}) =
  872. text "%module" <+> ppr mn <+> ppr te $$ vcat (map ppr cb)
  873. -- The ModGuts takes on several slightly different forms:
  874. --
  875. -- After simplification, the following fields change slightly:
  876. -- mg_rules Orphan rules only (local ones now attached to binds)
  877. -- mg_binds With rules attached
  878. ---------------------------------------------------------
  879. -- The Tidy pass forks the information about this module:
  880. -- * one lot goes to interface file generation (ModIface)
  881. -- and later compilations (ModDetails)
  882. -- * the other lot goes to code generation (CgGuts)
  883. -- | A restricted form of 'ModGuts' for code generation purposes
  884. data CgGuts
  885. = CgGuts {
  886. cg_module :: !Module, -- ^ Module being compiled
  887. cg_tycons :: [TyCon],
  888. -- ^ Algebraic data types (including ones that started
  889. -- life as classes); generate constructors and info
  890. -- tables. Includes newtypes, just for the benefit of
  891. -- External Core
  892. cg_binds :: [CoreBind],
  893. -- ^ The tidied main bindings, including
  894. -- previously-implicit bindings for record and class
  895. -- selectors, and data construtor wrappers. But *not*
  896. -- data constructor workers; reason: we we regard them
  897. -- as part of the code-gen of tycons
  898. cg_dir_imps :: ![Module],
  899. -- ^ Directly-imported modules; used to generate
  900. -- initialisation code
  901. cg_foreign :: !ForeignStubs, -- ^ Foreign export stubs
  902. cg_dep_pkgs :: ![PackageId], -- ^ Dependent packages, used to
  903. -- generate #includes for C code gen
  904. cg_hpc_info :: !HpcInfo, -- ^ Program coverage tick box information
  905. cg_modBreaks :: !ModBreaks -- ^ Module breakpoints
  906. }
  907. -----------------------------------
  908. -- | Foreign export stubs
  909. data ForeignStubs = NoStubs -- ^ We don't have any stubs
  910. | ForeignStubs
  911. SDoc
  912. SDoc
  913. -- ^ There are some stubs. Parameters:
  914. --
  915. -- 1) Header file prototypes for
  916. -- "foreign exported" functions
  917. --
  918. -- 2) C stubs to use when calling
  919. -- "foreign exported" functions
  920. \end{code}
  921. \begin{code}
  922. emptyModIface :: Module -> ModIface
  923. emptyModIface mod
  924. = ModIface { mi_module = mod,
  925. mi_iface_hash = fingerprint0,
  926. mi_mod_hash = fingerprint0,
  927. mi_orphan = False,
  928. mi_finsts = False,
  929. mi_boot = False,
  930. mi_deps = noDependencies,
  931. mi_usages = [],
  932. mi_exports = [],
  933. mi_exp_hash = fingerprint0,
  934. mi_fixities = [],
  935. mi_warns = NoWarnings,
  936. mi_anns = [],
  937. mi_insts = [],
  938. mi_fam_insts = [],
  939. mi_rules = [],
  940. mi_decls = [],
  941. mi_globals = Nothing,
  942. mi_orphan_hash = fingerprint0,
  943. mi_vect_info = noIfaceVectInfo,
  944. mi_warn_fn = emptyIfaceWarnCache,
  945. mi_fix_fn = emptyIfaceFixCache,
  946. mi_hash_fn = emptyIfaceHashCache,
  947. mi_hpc = False
  948. }
  949. \end{code}
  950. %************************************************************************
  951. %* *
  952. \subsection{The interactive context}
  953. %* *
  954. %************************************************************************
  955. \begin{code}
  956. -- | Interactive context, recording information relevant to GHCi
  957. data InteractiveContext
  958. = InteractiveContext {
  959. ic_toplev_scope :: [Module] -- ^ The context includes the "top-level" scope of
  960. -- these modules
  961. , ic_exports :: [(Module, Maybe (ImportDecl RdrName))] -- ^ The context includes just the exported parts of these
  962. -- modules
  963. , ic_rn_gbl_env :: GlobalRdrEnv -- ^ The contexts' cached 'GlobalRdrEnv', built from
  964. -- 'ic_toplev_scope' and 'ic_exports'
  965. , ic_tmp_ids :: [Id] -- ^ Names bound during interaction with the user.
  966. -- Later Ids shadow earlier ones with the same OccName
  967. -- Expressions are typed with these Ids in the envt
  968. -- For runtime-debugging, these Ids may have free
  969. -- TcTyVars of RuntimUnkSkol flavour, but no free TyVars
  970. -- (because the typechecker doesn't expect that)
  971. #ifdef GHCI
  972. , ic_resume :: [Resume] -- ^ The stack of breakpoint contexts
  973. #endif
  974. , ic_cwd :: Maybe FilePath -- virtual CWD of the program
  975. }
  976. emptyInteractiveContext :: InteractiveContext
  977. emptyInteractiveContext
  978. = InteractiveContext { ic_toplev_scope = [],
  979. ic_exports = [],
  980. ic_rn_gbl_env = emptyGlobalRdrEnv,
  981. ic_tmp_ids = []
  982. #ifdef GHCI
  983. , ic_resume = []
  984. #endif
  985. , ic_cwd = Nothing
  986. }
  987. icPrintUnqual :: DynFlags -> InteractiveContext -> PrintUnqualified
  988. icPrintUnqual dflags ictxt = mkPrintUnqualified dflags (ic_rn_gbl_env ictxt)
  989. extendInteractiveContext
  990. :: InteractiveContext
  991. -> [Id]
  992. -> InteractiveContext
  993. extendInteractiveContext ictxt ids
  994. = ictxt { ic_tmp_ids = snub ((ic_tmp_ids ictxt \\ ids) ++ ids)
  995. -- NB. must be this way around, because we want
  996. -- new ids to shadow existing bindings.
  997. }
  998. where snub = map head . group . sort
  999. substInteractiveContext :: InteractiveContext -> TvSubst -> InteractiveContext
  1000. substInteractiveContext ictxt subst | isEmptyTvSubst subst = ictxt
  1001. substInteractiveContext ictxt@InteractiveContext{ic_tmp_ids=ids} subst
  1002. = ictxt { ic_tmp_ids = map subst_ty ids }
  1003. where
  1004. subst_ty id = id `setIdType` substTy subst (idType id)
  1005. \end{code}
  1006. %************************************************************************
  1007. %* *
  1008. Building a PrintUnqualified
  1009. %* *
  1010. %************************************************************************
  1011. Note [Printing original names]
  1012. ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  1013. Deciding how to print names is pretty tricky. We are given a name
  1014. P:M.T, where P is the package name, M is the defining module, and T is
  1015. the occurrence name, and we have to decide in which form to display
  1016. the name given a GlobalRdrEnv describing the current scope.
  1017. Ideally we want to display the name in the form in which it is in
  1018. scope. However, the name might not be in scope at all, and that's
  1019. where it gets tricky. Here are the cases:
  1020. 1. T uniquely maps to P:M.T ---> "T" NameUnqual
  1021. 2. There is an X for which X.T
  1022. uniquely maps to P:M.T ---> "X.T" NameQual X
  1023. 3. There is no binding for "M.T" ---> "M.T" NameNotInScope1
  1024. 4. Otherwise ---> "P:M.T" NameNotInScope2
  1025. (3) and (4) apply when the entity P:M.T is not in the GlobalRdrEnv at
  1026. all. In these cases we still want to refer to the name as "M.T", *but*
  1027. "M.T" might mean something else in the current scope (e.g. if there's
  1028. an "import X as M"), so to avoid confusion we avoid using "M.T" if
  1029. there's already a binding for it. Instead we write P:M.T.
  1030. There's one further subtlety: in case (3), what if there are two
  1031. things around, P1:M.T and P2:M.T? Then we don't want to print both of
  1032. them as M.T! However only one of the modules P1:M and P2:M can be
  1033. exposed (say P2), so we use M.T for that, and P1:M.T for the other one.
  1034. This is handled by the qual_mod component of PrintUnqualified, inside
  1035. the (ppr mod) of case (3), in Name.pprModulePrefix
  1036. \begin{code}
  1037. -- | Creates some functions that work out the best ways to format
  1038. -- names for the user according to a set of heuristics
  1039. mkPrintUnqualified :: DynFlags -> GlobalRdrEnv -> PrintUnqualified
  1040. mkPrintUnqualified dflags env = (qual_name, qual_mod)
  1041. where
  1042. qual_name mod occ -- The (mod,occ) pair is the original name of the thing
  1043. | [gre] <- unqual_gres, right_name gre = NameUnqual
  1044. -- If there's a unique entity that's in scope unqualified with 'occ'
  1045. -- AND that entity is the right one, then we can use the unqualified name
  1046. | [gre] <- qual_gres = NameQual (get_qual_mod (gre_prov gre))
  1047. | null qual_gres =
  1048. if null (lookupGRE_RdrName (mkRdrQual (moduleName mod) occ) env)
  1049. then NameNotInScope1
  1050. else NameNotInScope2
  1051. | otherwise = panic "mkPrintUnqualified"
  1052. where
  1053. right_name gre = nameModule_maybe (gre_name gre) == Just mod
  1054. unqual_gres = lookupGRE_RdrName (mkRdrUnqual occ) env
  1055. qual_gres = filter right_name (lookupGlobalRdrEnv env occ)
  1056. get_qual_mod LocalDef = moduleName mod
  1057. get_qual_mod (Imported is) = ASSERT( not (null is) ) is_as (is_decl (head is))
  1058. -- we can mention a module P:M without the P: qualifier iff
  1059. -- "import M" would resolve unambiguously to P:M. (if P is the
  1060. -- current package we can just assume it is unqualified).
  1061. qual_mod mod
  1062. | modulePackageId mod == thisPackage dflags = False
  1063. | [pkgconfig] <- [pkg | (pkg,exposed_module) <- lookup,
  1064. exposed pkg && exposed_module],
  1065. packageConfigId pkgconfig == modulePackageId mod
  1066. -- this says: we are given a module P:M, is there just one exposed package
  1067. -- that exposes a module M, and is it package P?
  1068. = False
  1069. | otherwise = True
  1070. where lookup = lookupModuleInAllPackages dflags (moduleName mod)
  1071. \end{code}
  1072. %************************************************************************
  1073. %* *
  1074. TyThing
  1075. %* *
  1076. %************************************************************************
  1077. \begin{code}
  1078. -- | Determine the 'TyThing's brought into scope by another 'TyThing'
  1079. -- /other/ than itself. For example, Id's don't have any implicit TyThings
  1080. -- as they just bring themselves into scope, but classes bring their
  1081. -- dictionary datatype, type constructor and some selector functions into
  1082. -- scope, just for a start!
  1083. -- N.B. the set of TyThings returned here *must* match the set of
  1084. -- names returned by LoadIface.ifaceDeclSubBndrs, in the sense that
  1085. -- TyThing.getOccName should define a bijection between the two lists.
  1086. -- This invariant is used in LoadIface.loadDecl (see note [Tricky iface loop])
  1087. -- The order of the list does not matter.
  1088. implicitTyThings :: TyThing -> [TyThing]
  1089. -- For data and newtype declarations:
  1090. implicitTyThings (ATyCon tc)
  1091. = -- fields (names of selectors)
  1092. -- (possibly) implicit coercion and family coercion
  1093. -- depending on whether it's a newtype or a family instance or both
  1094. implicitCoTyCon tc ++
  1095. -- for each data constructor in order,
  1096. -- the contructor, worker, and (possibly) wrapper
  1097. concatMap (extras_plus . ADataCon) (tyConDataCons tc)
  1098. implicitTyThings (AClass cl)
  1099. = -- dictionary datatype:
  1100. -- [extras_plus:]
  1101. -- type constructor
  1102. -- [recursive call:]
  1103. -- (possibly) newtype coe

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