PageRenderTime 69ms CodeModel.GetById 30ms RepoModel.GetById 0ms app.codeStats 1ms

/compiler/main/Packages.hs

http://github.com/ghc/ghc
Haskell | 1530 lines | 915 code | 185 blank | 430 comment | 56 complexity | aefa91e117110352b15310a994163111 MD5 | raw file
Possible License(s): MIT, BSD-3-Clause, GPL-3.0

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

  1. -- (c) The University of Glasgow, 2006
  2. {-# LANGUAGE CPP, ScopedTypeVariables, BangPatterns #-}
  3. -- | Package manipulation
  4. module Packages (
  5. module PackageConfig,
  6. -- * Reading the package config, and processing cmdline args
  7. PackageState(preloadPackages, explicitPackages),
  8. emptyPackageState,
  9. initPackages,
  10. readPackageConfigs,
  11. getPackageConfRefs,
  12. resolvePackageConfig,
  13. readPackageConfig,
  14. listPackageConfigMap,
  15. -- * Querying the package config
  16. lookupPackage,
  17. searchPackageId,
  18. getPackageDetails,
  19. listVisibleModuleNames,
  20. lookupModuleInAllPackages,
  21. lookupModuleWithSuggestions,
  22. lookupPluginModuleWithSuggestions,
  23. LookupResult(..),
  24. ModuleSuggestion(..),
  25. ModuleOrigin(..),
  26. -- * Inspecting the set of packages in scope
  27. getPackageIncludePath,
  28. getPackageLibraryPath,
  29. getPackageLinkOpts,
  30. getPackageExtraCcOpts,
  31. getPackageFrameworkPath,
  32. getPackageFrameworks,
  33. getPreloadPackagesAnd,
  34. collectIncludeDirs, collectLibraryPaths, collectLinkOpts,
  35. packageHsLibs,
  36. -- * Utils
  37. unitIdPackageIdString,
  38. pprFlag,
  39. pprPackages,
  40. pprPackagesSimple,
  41. pprModuleMap,
  42. isDllName
  43. )
  44. where
  45. #include "HsVersions.h"
  46. import GHC.PackageDb
  47. import PackageConfig
  48. import DynFlags
  49. import Name ( Name, nameModule_maybe )
  50. import UniqFM
  51. import UniqDFM
  52. import Module
  53. import Util
  54. import Panic
  55. import Outputable
  56. import Maybes
  57. import System.Environment ( getEnv )
  58. import FastString
  59. import ErrUtils ( debugTraceMsg, MsgDoc )
  60. import Exception
  61. import Unique
  62. import System.Directory
  63. import System.FilePath as FilePath
  64. import qualified System.FilePath.Posix as FilePath.Posix
  65. import Control.Monad
  66. import Data.Char ( toUpper )
  67. import Data.List as List
  68. import Data.Map (Map)
  69. import Data.Set (Set)
  70. #if __GLASGOW_HASKELL__ > 710
  71. import Data.Semigroup ( Semigroup )
  72. import qualified Data.Semigroup as Semigroup
  73. #endif
  74. import qualified Data.Map as Map
  75. import qualified Data.Map.Strict as MapStrict
  76. import qualified FiniteMap as Map
  77. import qualified Data.Set as Set
  78. -- ---------------------------------------------------------------------------
  79. -- The Package state
  80. -- | Package state is all stored in 'DynFlags', including the details of
  81. -- all packages, which packages are exposed, and which modules they
  82. -- provide.
  83. --
  84. -- The package state is computed by 'initPackages', and kept in DynFlags.
  85. -- It is influenced by various package flags:
  86. --
  87. -- * @-package <pkg>@ and @-package-id <pkg>@ cause @<pkg>@ to become exposed.
  88. -- If @-hide-all-packages@ was not specified, these commands also cause
  89. -- all other packages with the same name to become hidden.
  90. --
  91. -- * @-hide-package <pkg>@ causes @<pkg>@ to become hidden.
  92. --
  93. -- * (there are a few more flags, check below for their semantics)
  94. --
  95. -- The package state has the following properties.
  96. --
  97. -- * Let @exposedPackages@ be the set of packages thus exposed.
  98. -- Let @depExposedPackages@ be the transitive closure from @exposedPackages@ of
  99. -- their dependencies.
  100. --
  101. -- * When searching for a module from an preload import declaration,
  102. -- only the exposed modules in @exposedPackages@ are valid.
  103. --
  104. -- * When searching for a module from an implicit import, all modules
  105. -- from @depExposedPackages@ are valid.
  106. --
  107. -- * When linking in a compilation manager mode, we link in packages the
  108. -- program depends on (the compiler knows this list by the
  109. -- time it gets to the link step). Also, we link in all packages
  110. -- which were mentioned with preload @-package@ flags on the command-line,
  111. -- or are a transitive dependency of same, or are \"base\"\/\"rts\".
  112. -- The reason for this is that we might need packages which don't
  113. -- contain any Haskell modules, and therefore won't be discovered
  114. -- by the normal mechanism of dependency tracking.
  115. -- Notes on DLLs
  116. -- ~~~~~~~~~~~~~
  117. -- When compiling module A, which imports module B, we need to
  118. -- know whether B will be in the same DLL as A.
  119. -- If it's in the same DLL, we refer to B_f_closure
  120. -- If it isn't, we refer to _imp__B_f_closure
  121. -- When compiling A, we record in B's Module value whether it's
  122. -- in a different DLL, by setting the DLL flag.
  123. -- | Given a module name, there may be multiple ways it came into scope,
  124. -- possibly simultaneously. This data type tracks all the possible ways
  125. -- it could have come into scope. Warning: don't use the record functions,
  126. -- they're partial!
  127. data ModuleOrigin =
  128. -- | Module is hidden, and thus never will be available for import.
  129. -- (But maybe the user didn't realize), so we'll still keep track
  130. -- of these modules.)
  131. ModHidden
  132. -- | Module is public, and could have come from some places.
  133. | ModOrigin {
  134. -- | @Just False@ means that this module is in
  135. -- someone's @exported-modules@ list, but that package is hidden;
  136. -- @Just True@ means that it is available; @Nothing@ means neither
  137. -- applies.
  138. fromOrigPackage :: Maybe Bool
  139. -- | Is the module available from a reexport of an exposed package?
  140. -- There could be multiple.
  141. , fromExposedReexport :: [PackageConfig]
  142. -- | Is the module available from a reexport of a hidden package?
  143. , fromHiddenReexport :: [PackageConfig]
  144. -- | Did the module export come from a package flag? (ToDo: track
  145. -- more information.
  146. , fromPackageFlag :: Bool
  147. }
  148. instance Outputable ModuleOrigin where
  149. ppr ModHidden = text "hidden module"
  150. ppr (ModOrigin e res rhs f) = sep (punctuate comma (
  151. (case e of
  152. Nothing -> []
  153. Just False -> [text "hidden package"]
  154. Just True -> [text "exposed package"]) ++
  155. (if null res
  156. then []
  157. else [text "reexport by" <+>
  158. sep (map (ppr . packageConfigId) res)]) ++
  159. (if null rhs
  160. then []
  161. else [text "hidden reexport by" <+>
  162. sep (map (ppr . packageConfigId) res)]) ++
  163. (if f then [text "package flag"] else [])
  164. ))
  165. -- | Smart constructor for a module which is in @exposed-modules@. Takes
  166. -- as an argument whether or not the defining package is exposed.
  167. fromExposedModules :: Bool -> ModuleOrigin
  168. fromExposedModules e = ModOrigin (Just e) [] [] False
  169. -- | Smart constructor for a module which is in @reexported-modules@. Takes
  170. -- as an argument whether or not the reexporting package is expsed, and
  171. -- also its 'PackageConfig'.
  172. fromReexportedModules :: Bool -> PackageConfig -> ModuleOrigin
  173. fromReexportedModules True pkg = ModOrigin Nothing [pkg] [] False
  174. fromReexportedModules False pkg = ModOrigin Nothing [] [pkg] False
  175. -- | Smart constructor for a module which was bound by a package flag.
  176. fromFlag :: ModuleOrigin
  177. fromFlag = ModOrigin Nothing [] [] True
  178. #if __GLASGOW_HASKELL__ > 710
  179. instance Semigroup ModuleOrigin where
  180. ModOrigin e res rhs f <> ModOrigin e' res' rhs' f' =
  181. ModOrigin (g e e') (res ++ res') (rhs ++ rhs') (f || f')
  182. where g (Just b) (Just b')
  183. | b == b' = Just b
  184. | otherwise = panic "ModOrigin: package both exposed/hidden"
  185. g Nothing x = x
  186. g x Nothing = x
  187. _x <> _y = panic "ModOrigin: hidden module redefined"
  188. #endif
  189. instance Monoid ModuleOrigin where
  190. mempty = ModOrigin Nothing [] [] False
  191. mappend (ModOrigin e res rhs f) (ModOrigin e' res' rhs' f') =
  192. ModOrigin (g e e') (res ++ res') (rhs ++ rhs') (f || f')
  193. where g (Just b) (Just b')
  194. | b == b' = Just b
  195. | otherwise = panic "ModOrigin: package both exposed/hidden"
  196. g Nothing x = x
  197. g x Nothing = x
  198. mappend _ _ = panic "ModOrigin: hidden module redefined"
  199. -- | Is the name from the import actually visible? (i.e. does it cause
  200. -- ambiguity, or is it only relevant when we're making suggestions?)
  201. originVisible :: ModuleOrigin -> Bool
  202. originVisible ModHidden = False
  203. originVisible (ModOrigin b res _ f) = b == Just True || not (null res) || f
  204. -- | Are there actually no providers for this module? This will never occur
  205. -- except when we're filtering based on package imports.
  206. originEmpty :: ModuleOrigin -> Bool
  207. originEmpty (ModOrigin Nothing [] [] False) = True
  208. originEmpty _ = False
  209. -- | 'UniqFM' map from 'UnitId'
  210. type UnitIdMap = UniqDFM
  211. -- | 'UniqFM' map from 'UnitId' to 'PackageConfig'
  212. type PackageConfigMap = UnitIdMap PackageConfig
  213. -- | 'UniqFM' map from 'UnitId' to (1) whether or not all modules which
  214. -- are exposed should be dumped into scope, (2) any custom renamings that
  215. -- should also be apply, and (3) what package name is associated with the
  216. -- key, if it might be hidden
  217. type VisibilityMap =
  218. UnitIdMap (Bool, [(ModuleName, ModuleName)], FastString)
  219. -- | Map from 'ModuleName' to 'Module' to all the origins of the bindings
  220. -- in scope. The 'PackageConf' is not cached, mostly for convenience reasons
  221. -- (since this is the slow path, we'll just look it up again).
  222. type ModuleToPkgConfAll =
  223. Map ModuleName (Map Module ModuleOrigin)
  224. data PackageState = PackageState {
  225. -- | A mapping of 'UnitId' to 'PackageConfig'. This list is adjusted
  226. -- so that only valid packages are here. 'PackageConfig' reflects
  227. -- what was stored *on disk*, except for the 'trusted' flag, which
  228. -- is adjusted at runtime. (In particular, some packages in this map
  229. -- may have the 'exposed' flag be 'False'.)
  230. pkgIdMap :: PackageConfigMap,
  231. -- | The packages we're going to link in eagerly. This list
  232. -- should be in reverse dependency order; that is, a package
  233. -- is always mentioned before the packages it depends on.
  234. preloadPackages :: [UnitId],
  235. -- | Packages which we explicitly depend on (from a command line flag).
  236. -- We'll use this to generate version macros.
  237. explicitPackages :: [UnitId],
  238. -- | This is a full map from 'ModuleName' to all modules which may possibly
  239. -- be providing it. These providers may be hidden (but we'll still want
  240. -- to report them in error messages), or it may be an ambiguous import.
  241. moduleToPkgConfAll :: !ModuleToPkgConfAll,
  242. -- | A map, like 'moduleToPkgConfAll', but controlling plugin visibility.
  243. pluginModuleToPkgConfAll :: !ModuleToPkgConfAll
  244. }
  245. emptyPackageState :: PackageState
  246. emptyPackageState = PackageState {
  247. pkgIdMap = emptyPackageConfigMap,
  248. preloadPackages = [],
  249. explicitPackages = [],
  250. moduleToPkgConfAll = Map.empty,
  251. pluginModuleToPkgConfAll = Map.empty
  252. }
  253. type InstalledPackageIndex = Map UnitId PackageConfig
  254. -- | Empty package configuration map
  255. emptyPackageConfigMap :: PackageConfigMap
  256. emptyPackageConfigMap = emptyUDFM
  257. -- | Find the package we know about with the given key (e.g. @foo_HASH@), if any
  258. lookupPackage :: DynFlags -> UnitId -> Maybe PackageConfig
  259. lookupPackage dflags = lookupPackage' (pkgIdMap (pkgState dflags))
  260. lookupPackage' :: PackageConfigMap -> UnitId -> Maybe PackageConfig
  261. lookupPackage' = lookupUDFM
  262. -- | Search for packages with a given package ID (e.g. \"foo-0.1\")
  263. searchPackageId :: DynFlags -> SourcePackageId -> [PackageConfig]
  264. searchPackageId dflags pid = filter ((pid ==) . sourcePackageId)
  265. (listPackageConfigMap dflags)
  266. -- | Extends the package configuration map with a list of package configs.
  267. extendPackageConfigMap
  268. :: PackageConfigMap -> [PackageConfig] -> PackageConfigMap
  269. extendPackageConfigMap pkg_map new_pkgs
  270. = foldl add pkg_map new_pkgs
  271. where add pkg_map p = addToUDFM pkg_map (packageConfigId p) p
  272. -- | Looks up the package with the given id in the package state, panicing if it is
  273. -- not found
  274. getPackageDetails :: DynFlags -> UnitId -> PackageConfig
  275. getPackageDetails dflags pid =
  276. expectJust "getPackageDetails" (lookupPackage dflags pid)
  277. -- | Get a list of entries from the package database. NB: be careful with
  278. -- this function, although all packages in this map are "visible", this
  279. -- does not imply that the exposed-modules of the package are available
  280. -- (they may have been thinned or renamed).
  281. listPackageConfigMap :: DynFlags -> [PackageConfig]
  282. listPackageConfigMap dflags = eltsUDFM (pkgIdMap (pkgState dflags))
  283. -- ----------------------------------------------------------------------------
  284. -- Loading the package db files and building up the package state
  285. -- | Call this after 'DynFlags.parseDynFlags'. It reads the package
  286. -- database files, and sets up various internal tables of package
  287. -- information, according to the package-related flags on the
  288. -- command-line (@-package@, @-hide-package@ etc.)
  289. --
  290. -- Returns a list of packages to link in if we're doing dynamic linking.
  291. -- This list contains the packages that the user explicitly mentioned with
  292. -- @-package@ flags.
  293. --
  294. -- 'initPackages' can be called again subsequently after updating the
  295. -- 'packageFlags' field of the 'DynFlags', and it will update the
  296. -- 'pkgState' in 'DynFlags' and return a list of packages to
  297. -- link in.
  298. initPackages :: DynFlags -> IO (DynFlags, [UnitId])
  299. initPackages dflags = do
  300. pkg_db <-
  301. case pkgDatabase dflags of
  302. Nothing -> readPackageConfigs dflags
  303. Just db -> return $ map (\(p, pkgs)
  304. -> (p, setBatchPackageFlags dflags pkgs)) db
  305. (pkg_state, preload, this_pkg)
  306. <- mkPackageState dflags pkg_db []
  307. return (dflags{ pkgDatabase = Just pkg_db,
  308. pkgState = pkg_state,
  309. thisPackage = this_pkg },
  310. preload)
  311. -- -----------------------------------------------------------------------------
  312. -- Reading the package database(s)
  313. readPackageConfigs :: DynFlags -> IO [(FilePath, [PackageConfig])]
  314. readPackageConfigs dflags = do
  315. conf_refs <- getPackageConfRefs dflags
  316. confs <- liftM catMaybes $ mapM (resolvePackageConfig dflags) conf_refs
  317. mapM (readPackageConfig dflags) confs
  318. getPackageConfRefs :: DynFlags -> IO [PkgConfRef]
  319. getPackageConfRefs dflags = do
  320. let system_conf_refs = [UserPkgConf, GlobalPkgConf]
  321. e_pkg_path <- tryIO (getEnv $ map toUpper (programName dflags) ++ "_PACKAGE_PATH")
  322. let base_conf_refs = case e_pkg_path of
  323. Left _ -> system_conf_refs
  324. Right path
  325. | not (null path) && isSearchPathSeparator (last path)
  326. -> map PkgConfFile (splitSearchPath (init path)) ++ system_conf_refs
  327. | otherwise
  328. -> map PkgConfFile (splitSearchPath path)
  329. return $ reverse (extraPkgConfs dflags base_conf_refs)
  330. -- later packages shadow earlier ones. extraPkgConfs
  331. -- is in the opposite order to the flags on the
  332. -- command line.
  333. resolvePackageConfig :: DynFlags -> PkgConfRef -> IO (Maybe FilePath)
  334. resolvePackageConfig dflags GlobalPkgConf = return $ Just (systemPackageConfig dflags)
  335. -- NB: This logic is reimplemented in Cabal, so if you change it,
  336. -- make sure you update Cabal. (Or, better yet, dump it in the
  337. -- compiler info so Cabal can use the info.)
  338. resolvePackageConfig dflags UserPkgConf = runMaybeT $ do
  339. dir <- versionedAppDir dflags
  340. let pkgconf = dir </> "package.conf.d"
  341. exist <- tryMaybeT $ doesDirectoryExist pkgconf
  342. if exist then return pkgconf else mzero
  343. resolvePackageConfig _ (PkgConfFile name) = return $ Just name
  344. readPackageConfig :: DynFlags -> FilePath -> IO (FilePath, [PackageConfig])
  345. readPackageConfig dflags conf_file = do
  346. isdir <- doesDirectoryExist conf_file
  347. proto_pkg_configs <-
  348. if isdir
  349. then readDirStylePackageConfig conf_file
  350. else do
  351. isfile <- doesFileExist conf_file
  352. if isfile
  353. then do
  354. mpkgs <- tryReadOldFileStylePackageConfig
  355. case mpkgs of
  356. Just pkgs -> return pkgs
  357. Nothing -> throwGhcExceptionIO $ InstallationError $
  358. "ghc no longer supports single-file style package " ++
  359. "databases (" ++ conf_file ++
  360. ") use 'ghc-pkg init' to create the database with " ++
  361. "the correct format."
  362. else throwGhcExceptionIO $ InstallationError $
  363. "can't find a package database at " ++ conf_file
  364. let
  365. top_dir = topDir dflags
  366. pkgroot = takeDirectory conf_file
  367. pkg_configs1 = map (mungePackagePaths top_dir pkgroot) proto_pkg_configs
  368. pkg_configs2 = setBatchPackageFlags dflags pkg_configs1
  369. --
  370. return (conf_file, pkg_configs2)
  371. where
  372. readDirStylePackageConfig conf_dir = do
  373. let filename = conf_dir </> "package.cache"
  374. debugTraceMsg dflags 2 (text "Using binary package database:" <+> text filename)
  375. readPackageDbForGhc filename
  376. -- Single-file style package dbs have been deprecated for some time, but
  377. -- it turns out that Cabal was using them in one place. So this is a
  378. -- workaround to allow older Cabal versions to use this newer ghc.
  379. -- We check if the file db contains just "[]" and if so, we look for a new
  380. -- dir-style db in conf_file.d/, ie in a dir next to the given file.
  381. -- We cannot just replace the file with a new dir style since Cabal still
  382. -- assumes it's a file and tries to overwrite with 'writeFile'.
  383. -- ghc-pkg also cooperates with this workaround.
  384. tryReadOldFileStylePackageConfig = do
  385. content <- readFile conf_file `catchIO` \_ -> return ""
  386. if take 2 content == "[]"
  387. then do
  388. let conf_dir = conf_file <.> "d"
  389. direxists <- doesDirectoryExist conf_dir
  390. if direxists
  391. then do debugTraceMsg dflags 2 (text "Ignoring old file-style db and trying:" <+> text conf_dir)
  392. liftM Just (readDirStylePackageConfig conf_dir)
  393. else return (Just []) -- ghc-pkg will create it when it's updated
  394. else return Nothing
  395. setBatchPackageFlags :: DynFlags -> [PackageConfig] -> [PackageConfig]
  396. setBatchPackageFlags dflags pkgs = maybeDistrustAll pkgs
  397. where
  398. maybeDistrustAll pkgs'
  399. | gopt Opt_DistrustAllPackages dflags = map distrust pkgs'
  400. | otherwise = pkgs'
  401. distrust pkg = pkg{ trusted = False }
  402. -- TODO: This code is duplicated in utils/ghc-pkg/Main.hs
  403. mungePackagePaths :: FilePath -> FilePath -> PackageConfig -> PackageConfig
  404. -- Perform path/URL variable substitution as per the Cabal ${pkgroot} spec
  405. -- (http://www.haskell.org/pipermail/libraries/2009-May/011772.html)
  406. -- Paths/URLs can be relative to ${pkgroot} or ${pkgrooturl}.
  407. -- The "pkgroot" is the directory containing the package database.
  408. --
  409. -- Also perform a similar substitution for the older GHC-specific
  410. -- "$topdir" variable. The "topdir" is the location of the ghc
  411. -- installation (obtained from the -B option).
  412. mungePackagePaths top_dir pkgroot pkg =
  413. pkg {
  414. importDirs = munge_paths (importDirs pkg),
  415. includeDirs = munge_paths (includeDirs pkg),
  416. libraryDirs = munge_paths (libraryDirs pkg),
  417. frameworkDirs = munge_paths (frameworkDirs pkg),
  418. haddockInterfaces = munge_paths (haddockInterfaces pkg),
  419. haddockHTMLs = munge_urls (haddockHTMLs pkg)
  420. }
  421. where
  422. munge_paths = map munge_path
  423. munge_urls = map munge_url
  424. munge_path p
  425. | Just p' <- stripVarPrefix "${pkgroot}" p = pkgroot ++ p'
  426. | Just p' <- stripVarPrefix "$topdir" p = top_dir ++ p'
  427. | otherwise = p
  428. munge_url p
  429. | Just p' <- stripVarPrefix "${pkgrooturl}" p = toUrlPath pkgroot p'
  430. | Just p' <- stripVarPrefix "$httptopdir" p = toUrlPath top_dir p'
  431. | otherwise = p
  432. toUrlPath r p = "file:///"
  433. -- URLs always use posix style '/' separators:
  434. ++ FilePath.Posix.joinPath
  435. (r : -- We need to drop a leading "/" or "\\"
  436. -- if there is one:
  437. dropWhile (all isPathSeparator)
  438. (FilePath.splitDirectories p))
  439. -- We could drop the separator here, and then use </> above. However,
  440. -- by leaving it in and using ++ we keep the same path separator
  441. -- rather than letting FilePath change it to use \ as the separator
  442. stripVarPrefix var path = case stripPrefix var path of
  443. Just [] -> Just []
  444. Just cs@(c : _) | isPathSeparator c -> Just cs
  445. _ -> Nothing
  446. -- -----------------------------------------------------------------------------
  447. -- Modify our copy of the package database based on trust flags,
  448. -- -trust and -distrust.
  449. applyTrustFlag
  450. :: DynFlags
  451. -> UnusablePackages
  452. -> [PackageConfig]
  453. -> TrustFlag
  454. -> IO [PackageConfig]
  455. applyTrustFlag dflags unusable pkgs flag =
  456. case flag of
  457. -- we trust all matching packages. Maybe should only trust first one?
  458. -- and leave others the same or set them untrusted
  459. TrustPackage str ->
  460. case selectPackages (matchingStr str) pkgs unusable of
  461. Left ps -> trustFlagErr dflags flag ps
  462. Right (ps,qs) -> return (map trust ps ++ qs)
  463. where trust p = p {trusted=True}
  464. DistrustPackage str ->
  465. case selectPackages (matchingStr str) pkgs unusable of
  466. Left ps -> trustFlagErr dflags flag ps
  467. Right (ps,qs) -> return (map distrust ps ++ qs)
  468. where distrust p = p {trusted=False}
  469. applyPackageFlag
  470. :: DynFlags
  471. -> UnusablePackages
  472. -> Bool -- if False, if you expose a package, it implicitly hides
  473. -- any previously exposed packages with the same name
  474. -> [PackageConfig]
  475. -> VisibilityMap -- Initially exposed
  476. -> PackageFlag -- flag to apply
  477. -> IO VisibilityMap -- Now exposed
  478. applyPackageFlag dflags unusable no_hide_others pkgs vm flag =
  479. case flag of
  480. ExposePackage _ arg (ModRenaming b rns) ->
  481. case selectPackages (matching arg) pkgs unusable of
  482. Left ps -> packageFlagErr dflags flag ps
  483. Right (p:_,_) -> return vm'
  484. where
  485. n = fsPackageName p
  486. vm' = addToUDFM_C edit vm_cleared (packageConfigId p) (b, rns, n)
  487. edit (b, rns, n) (b', rns', _) = (b || b', rns ++ rns', n)
  488. -- In the old days, if you said `ghc -package p-0.1 -package p-0.2`
  489. -- (or if p-0.1 was registered in the pkgdb as exposed: True),
  490. -- the second package flag would override the first one and you
  491. -- would only see p-0.2 in exposed modules. This is good for
  492. -- usability.
  493. --
  494. -- However, with thinning and renaming (or Backpack), there might be
  495. -- situations where you legitimately want to see two versions of a
  496. -- package at the same time, and this behavior would make it
  497. -- impossible to do so. So we decided that if you pass
  498. -- -hide-all-packages, this should turn OFF the overriding behavior
  499. -- where an exposed package hides all other packages with the same
  500. -- name. This should not affect Cabal at all, which only ever
  501. -- exposes one package at a time.
  502. --
  503. -- NB: Why a variable no_hide_others? We have to apply this logic to
  504. -- -plugin-package too, and it's more consistent if the switch in
  505. -- behavior is based off of
  506. -- -hide-all-packages/-hide-all-plugin-packages depending on what
  507. -- flag is in question.
  508. vm_cleared | no_hide_others = vm
  509. | otherwise = filterUDFM_Directly
  510. (\k (_,_,n') -> k == getUnique (packageConfigId p)
  511. || n /= n') vm
  512. _ -> panic "applyPackageFlag"
  513. HidePackage str ->
  514. case selectPackages (matchingStr str) pkgs unusable of
  515. Left ps -> packageFlagErr dflags flag ps
  516. Right (ps,_) -> return vm'
  517. where vm' = delListFromUDFM vm (map packageConfigId ps)
  518. selectPackages :: (PackageConfig -> Bool) -> [PackageConfig]
  519. -> UnusablePackages
  520. -> Either [(PackageConfig, UnusablePackageReason)]
  521. ([PackageConfig], [PackageConfig])
  522. selectPackages matches pkgs unusable
  523. = let (ps,rest) = partition matches pkgs
  524. in if null ps
  525. then Left (filter (matches.fst) (Map.elems unusable))
  526. -- NB: packages from later package databases are LATER
  527. -- in the list. We want to prefer the latest package.
  528. else Right (sortByVersion (reverse ps), rest)
  529. -- A package named on the command line can either include the
  530. -- version, or just the name if it is unambiguous.
  531. matchingStr :: String -> PackageConfig -> Bool
  532. matchingStr str p
  533. = str == sourcePackageIdString p
  534. || str == packageNameString p
  535. matchingId :: String -> PackageConfig -> Bool
  536. matchingId str p = str == unitIdString (packageConfigId p)
  537. matching :: PackageArg -> PackageConfig -> Bool
  538. matching (PackageArg str) = matchingStr str
  539. matching (UnitIdArg str) = matchingId str
  540. sortByVersion :: [PackageConfig] -> [PackageConfig]
  541. sortByVersion = sortBy (flip (comparing packageVersion))
  542. comparing :: Ord a => (t -> a) -> t -> t -> Ordering
  543. comparing f a b = f a `compare` f b
  544. packageFlagErr :: DynFlags
  545. -> PackageFlag
  546. -> [(PackageConfig, UnusablePackageReason)]
  547. -> IO a
  548. -- for missing DPH package we emit a more helpful error message, because
  549. -- this may be the result of using -fdph-par or -fdph-seq.
  550. packageFlagErr dflags (ExposePackage _ (PackageArg pkg) _) []
  551. | is_dph_package pkg
  552. = throwGhcExceptionIO (CmdLineError (showSDoc dflags $ dph_err))
  553. where dph_err = text "the " <> text pkg <> text " package is not installed."
  554. $$ text "To install it: \"cabal install dph\"."
  555. is_dph_package pkg = "dph" `isPrefixOf` pkg
  556. packageFlagErr dflags flag reasons
  557. = packageFlagErr' dflags (pprFlag flag) reasons
  558. trustFlagErr :: DynFlags
  559. -> TrustFlag
  560. -> [(PackageConfig, UnusablePackageReason)]
  561. -> IO a
  562. trustFlagErr dflags flag reasons
  563. = packageFlagErr' dflags (pprTrustFlag flag) reasons
  564. packageFlagErr' :: DynFlags
  565. -> SDoc
  566. -> [(PackageConfig, UnusablePackageReason)]
  567. -> IO a
  568. packageFlagErr' dflags flag_doc reasons
  569. = throwGhcExceptionIO (CmdLineError (showSDoc dflags $ err))
  570. where err = text "cannot satisfy " <> flag_doc <>
  571. (if null reasons then Outputable.empty else text ": ") $$
  572. nest 4 (ppr_reasons $$
  573. text "(use -v for more information)")
  574. ppr_reasons = vcat (map ppr_reason reasons)
  575. ppr_reason (p, reason) =
  576. pprReason (ppr (unitId p) <+> text "is") reason
  577. pprFlag :: PackageFlag -> SDoc
  578. pprFlag flag = case flag of
  579. HidePackage p -> text "-hide-package " <> text p
  580. ExposePackage doc _ _ -> text doc
  581. pprTrustFlag :: TrustFlag -> SDoc
  582. pprTrustFlag flag = case flag of
  583. TrustPackage p -> text "-trust " <> text p
  584. DistrustPackage p -> text "-distrust " <> text p
  585. -- -----------------------------------------------------------------------------
  586. -- Wired-in packages
  587. wired_in_pkgids :: [String]
  588. wired_in_pkgids = map unitIdString wiredInUnitIds
  589. type WiredPackagesMap = Map UnitId UnitId
  590. findWiredInPackages
  591. :: DynFlags
  592. -> [PackageConfig] -- database
  593. -> VisibilityMap -- info on what packages are visible
  594. -- for wired in selection
  595. -> IO ([PackageConfig], -- package database updated for wired in
  596. WiredPackagesMap) -- map from unit id to wired identity
  597. findWiredInPackages dflags pkgs vis_map = do
  598. --
  599. -- Now we must find our wired-in packages, and rename them to
  600. -- their canonical names (eg. base-1.0 ==> base).
  601. --
  602. let
  603. matches :: PackageConfig -> String -> Bool
  604. pc `matches` pid = packageNameString pc == pid
  605. -- find which package corresponds to each wired-in package
  606. -- delete any other packages with the same name
  607. -- update the package and any dependencies to point to the new
  608. -- one.
  609. --
  610. -- When choosing which package to map to a wired-in package
  611. -- name, we try to pick the latest version of exposed packages.
  612. -- However, if there are no exposed wired in packages available
  613. -- (e.g. -hide-all-packages was used), we can't bail: we *have*
  614. -- to assign a package for the wired-in package: so we try again
  615. -- with hidden packages included to (and pick the latest
  616. -- version).
  617. --
  618. -- You can also override the default choice by using -ignore-package:
  619. -- this works even when there is no exposed wired in package
  620. -- available.
  621. --
  622. findWiredInPackage :: [PackageConfig] -> String
  623. -> IO (Maybe PackageConfig)
  624. findWiredInPackage pkgs wired_pkg =
  625. let all_ps = [ p | p <- pkgs, p `matches` wired_pkg ]
  626. all_exposed_ps =
  627. [ p | p <- all_ps
  628. , elemUDFM (packageConfigId p) vis_map ] in
  629. case all_exposed_ps of
  630. [] -> case all_ps of
  631. [] -> notfound
  632. many -> pick (head (sortByVersion many))
  633. many -> pick (head (sortByVersion many))
  634. where
  635. notfound = do
  636. debugTraceMsg dflags 2 $
  637. text "wired-in package "
  638. <> text wired_pkg
  639. <> text " not found."
  640. return Nothing
  641. pick :: PackageConfig
  642. -> IO (Maybe PackageConfig)
  643. pick pkg = do
  644. debugTraceMsg dflags 2 $
  645. text "wired-in package "
  646. <> text wired_pkg
  647. <> text " mapped to "
  648. <> ppr (unitId pkg)
  649. return (Just pkg)
  650. mb_wired_in_pkgs <- mapM (findWiredInPackage pkgs) wired_in_pkgids
  651. let
  652. wired_in_pkgs = catMaybes mb_wired_in_pkgs
  653. wired_in_ids = map unitId wired_in_pkgs
  654. -- this is old: we used to assume that if there were
  655. -- multiple versions of wired-in packages installed that
  656. -- they were mutually exclusive. Now we're assuming that
  657. -- you have one "main" version of each wired-in package
  658. -- (the latest version), and the others are backward-compat
  659. -- wrappers that depend on this one. e.g. base-4.0 is the
  660. -- latest, base-3.0 is a compat wrapper depending on base-4.0.
  661. {-
  662. deleteOtherWiredInPackages pkgs = filterOut bad pkgs
  663. where bad p = any (p `matches`) wired_in_pkgids
  664. && package p `notElem` map fst wired_in_ids
  665. -}
  666. wiredInMap :: Map UnitId UnitId
  667. wiredInMap = foldl' add_mapping Map.empty pkgs
  668. where add_mapping m pkg
  669. | let key = unitId pkg
  670. , key `elem` wired_in_ids
  671. = Map.insert key (stringToUnitId (packageNameString pkg)) m
  672. | otherwise = m
  673. updateWiredInDependencies pkgs = map (upd_deps . upd_pkg) pkgs
  674. where upd_pkg pkg
  675. | unitId pkg `elem` wired_in_ids
  676. = pkg {
  677. unitId = stringToUnitId (packageNameString pkg)
  678. }
  679. | otherwise
  680. = pkg
  681. upd_deps pkg = pkg {
  682. depends = map upd_wired_in (depends pkg),
  683. exposedModules
  684. = map (\(k,v) -> (k, fmap upd_wired_in_mod v))
  685. (exposedModules pkg)
  686. }
  687. upd_wired_in_mod (Module uid m) = Module (upd_wired_in uid) m
  688. upd_wired_in key
  689. | Just key' <- Map.lookup key wiredInMap = key'
  690. | otherwise = key
  691. return (updateWiredInDependencies pkgs, wiredInMap)
  692. updateVisibilityMap :: WiredPackagesMap -> VisibilityMap -> VisibilityMap
  693. updateVisibilityMap wiredInMap vis_map = foldl' f vis_map (Map.toList wiredInMap)
  694. where f vm (from, to) = case lookupUDFM vis_map from of
  695. Nothing -> vm
  696. Just r -> addToUDFM vm to r
  697. -- ----------------------------------------------------------------------------
  698. type IsShadowed = Bool
  699. data UnusablePackageReason
  700. = IgnoredWithFlag
  701. | MissingDependencies IsShadowed [UnitId]
  702. type UnusablePackages = Map UnitId
  703. (PackageConfig, UnusablePackageReason)
  704. pprReason :: SDoc -> UnusablePackageReason -> SDoc
  705. pprReason pref reason = case reason of
  706. IgnoredWithFlag ->
  707. pref <+> text "ignored due to an -ignore-package flag"
  708. MissingDependencies is_shadowed deps ->
  709. pref <+> text "unusable due to"
  710. <+> (if is_shadowed then text "shadowed"
  711. else text "missing or recursive")
  712. <+> text "dependencies:" $$
  713. nest 2 (hsep (map ppr deps))
  714. reportUnusable :: DynFlags -> UnusablePackages -> IO ()
  715. reportUnusable dflags pkgs = mapM_ report (Map.toList pkgs)
  716. where
  717. report (ipid, (_, reason)) =
  718. debugTraceMsg dflags 2 $
  719. pprReason
  720. (text "package" <+> ppr ipid <+> text "is") reason
  721. -- ----------------------------------------------------------------------------
  722. --
  723. -- Detect any packages that have missing dependencies, and also any
  724. -- mutually-recursive groups of packages (loops in the package graph
  725. -- are not allowed). We do this by taking the least fixpoint of the
  726. -- dependency graph, repeatedly adding packages whose dependencies are
  727. -- satisfied until no more can be added.
  728. --
  729. findBroken :: IsShadowed
  730. -> [PackageConfig]
  731. -> Map UnitId PackageConfig
  732. -> UnusablePackages
  733. findBroken is_shadowed pkgs pkg_map0 = go [] pkg_map0 pkgs
  734. where
  735. go avail pkg_map not_avail =
  736. case partitionWith (depsAvailable pkg_map) not_avail of
  737. ([], not_avail) ->
  738. Map.fromList [ (unitId p, (p, MissingDependencies is_shadowed deps))
  739. | (p,deps) <- not_avail ]
  740. (new_avail, not_avail) ->
  741. go (new_avail ++ avail) pkg_map' (map fst not_avail)
  742. where pkg_map' = Map.insertList
  743. [ (unitId p, p) | p <- new_avail ]
  744. pkg_map
  745. depsAvailable :: InstalledPackageIndex
  746. -> PackageConfig
  747. -> Either PackageConfig (PackageConfig, [UnitId])
  748. depsAvailable pkg_map pkg
  749. | null dangling = Left pkg
  750. | otherwise = Right (pkg, dangling)
  751. where dangling = filter (not . (`Map.member` pkg_map)) (depends pkg)
  752. -- -----------------------------------------------------------------------------
  753. -- Ignore packages
  754. ignorePackages :: [IgnorePackageFlag] -> [PackageConfig] -> UnusablePackages
  755. ignorePackages flags pkgs = Map.fromList (concatMap doit flags)
  756. where
  757. doit (IgnorePackage str) =
  758. case partition (matchingStr str) pkgs of
  759. (ps, _) -> [ (unitId p, (p, IgnoredWithFlag))
  760. | p <- ps ]
  761. -- missing package is not an error for -ignore-package,
  762. -- because a common usage is to -ignore-package P as
  763. -- a preventative measure just in case P exists.
  764. -- -----------------------------------------------------------------------------
  765. -- When all the command-line options are in, we can process our package
  766. -- settings and populate the package state.
  767. mkPackageState
  768. :: DynFlags
  769. -> [(FilePath, [PackageConfig])] -- initial databases
  770. -> [UnitId] -- preloaded packages
  771. -> IO (PackageState,
  772. [UnitId], -- new packages to preload
  773. UnitId) -- this package, might be modified if the current
  774. -- package is a wired-in package.
  775. mkPackageState dflags0 dbs preload0 = do
  776. dflags <- interpretPackageEnv dflags0
  777. -- Compute the unit id
  778. let this_package = thisPackage dflags
  779. {-
  780. Plan.
  781. There are two main steps for making the package state:
  782. 1. We want to build a single, unified package database based
  783. on all of the input databases, which upholds the invariant that
  784. there is only one package per any UnitId, and that there are no
  785. dangling dependencies. We'll do this by successively merging each
  786. input database into this unified database:
  787. a) if an input database defines unit ID that is already in
  788. the unified database, that package SHADOWS the existing
  789. package in the current unified database
  790. * for every such shadowed package, we remove it and any
  791. packages which transitively depend on it from the
  792. unified datbase
  793. b) remove packages selected by -ignore-package from input database
  794. c) remove any packages with missing dependencies or mutually recursive
  795. dependencies from the input database
  796. d) report (with -v) any packages that were removed by steps 1-3
  797. e) merge the input database into the unified database
  798. 2. We want to look at the flags controlling package visibility,
  799. and build a mapping of what module names are in scope and
  800. where they live.
  801. a) on the final, unified database, we apply -trust/-distrust
  802. flags directly, modifying the database so that the 'trusted'
  803. field has the correct value.
  804. b) we use the -package/-hide-package flags to compute a
  805. visibility map, stating what packages are "exposed" for
  806. the purposes of computing the module map.
  807. * if any flag refers to a package which was removed by 1-5, then
  808. we can give an error message explaining why
  809. * if -hide-all-packages what not specified, this step also
  810. hides packages which are superseded by later exposed packages
  811. * this step is done TWICE if -plugin-package/-hide-all-plugin-packages
  812. are used
  813. c) based on the visibility map, we pick wired packages and rewrite
  814. them to have the expected unitId.
  815. d) finally, using the visibility map and the package database,
  816. we build a mapping saying what every in scope module name points to.
  817. -}
  818. let other_flags = reverse (packageFlags dflags)
  819. ignore_flags = reverse (ignorePackageFlags dflags)
  820. let merge (pkg_map, prev_unusable) (db_path, db) = do
  821. debugTraceMsg dflags 2 $
  822. text "loading package database" <+> text db_path
  823. forM_ (Set.toList shadow_set) $ \pkg ->
  824. debugTraceMsg dflags 2 $
  825. text "package" <+> ppr pkg <+>
  826. text "shadows a previously defined package"
  827. reportUnusable dflags unusable
  828. -- NB: an unusable unit ID can become usable again
  829. -- if it's validly specified in a later package stack.
  830. -- Keep unusable up-to-date!
  831. return (pkg_map', (prev_unusable `Map.difference` pkg_map')
  832. `Map.union` unusable)
  833. where -- The set of UnitIds which appear in both
  834. -- db and pkgs (to be shadowed from pkgs)
  835. shadow_set :: Set UnitId
  836. shadow_set = foldr ins Set.empty db
  837. where ins pkg s
  838. -- If the package from the upper database is
  839. -- in the lower database, and the ABIs don't
  840. -- match...
  841. | Just old_pkg <- Map.lookup (unitId pkg) pkg_map
  842. , abiHash old_pkg /= abiHash pkg
  843. -- ...add this unit ID to the set of unit IDs
  844. -- which (transitively) should be shadowed from
  845. -- the lower database.
  846. = Set.insert (unitId pkg) s
  847. | otherwise
  848. = s
  849. -- Remove shadow_set from pkg_map...
  850. shadowed_pkgs0 :: [PackageConfig]
  851. shadowed_pkgs0 = filter (not . (`Set.member` shadow_set) . unitId)
  852. (Map.elems pkg_map)
  853. -- ...and then remove anything transitively broken
  854. -- this way.
  855. shadowed = findBroken True shadowed_pkgs0 Map.empty
  856. shadowed_pkgs :: [PackageConfig]
  857. shadowed_pkgs = filter (not . (`Map.member` shadowed) . unitId)
  858. shadowed_pkgs0
  859. -- Apply ignore flags to db (TODO: could extend command line
  860. -- flag format to support per-database ignore now! More useful
  861. -- than what we have now.)
  862. ignored = ignorePackages ignore_flags db
  863. db2 = filter (not . (`Map.member` ignored) . unitId) db
  864. -- Look for broken packages (either from ignore, or possibly
  865. -- because the db was broken to begin with)
  866. mk_pkg_map = Map.fromList . map (\p -> (unitId p, p))
  867. broken = findBroken False db2 (mk_pkg_map shadowed_pkgs)
  868. db3 = filter (not . (`Map.member` broken) . unitId) db2
  869. unusable = shadowed `Map.union` ignored
  870. `Map.union` broken
  871. -- Now merge the sets together (NB: later overrides
  872. -- earlier!)
  873. pkg_map' :: Map UnitId PackageConfig
  874. pkg_map' = mk_pkg_map (shadowed_pkgs ++ db3)
  875. (pkg_map1, unusable) <- foldM merge (Map.empty, Map.empty) dbs
  876. -- Apply trust flags (these flags apply regardless of whether
  877. -- or not packages are visible or not)
  878. pkgs1 <- foldM (applyTrustFlag dflags unusable)
  879. (Map.elems pkg_map1) (reverse (trustFlags dflags))
  880. --
  881. -- Calculate the initial set of packages, prior to any package flags.
  882. -- This set contains the latest version of all valid (not unusable) packages,
  883. -- or is empty if we have -hide-all-packages
  884. --
  885. let preferLater pkg pkg' =
  886. case comparing packageVersion pkg pkg' of
  887. GT -> pkg
  888. _ -> pkg'
  889. calcInitial m pkg = addToUDFM_C preferLater m (fsPackageName pkg) pkg
  890. initial = if gopt Opt_HideAllPackages dflags
  891. then emptyUDFM
  892. else foldl' calcInitial emptyUDFM pkgs1
  893. vis_map1 = foldUDFM (\p vm ->
  894. if exposed p
  895. then addToUDFM vm (packageConfigId p)
  896. (True, [], fsPackageName p)
  897. else vm)
  898. emptyUDFM initial
  899. --
  900. -- Compute a visibility map according to the command-line flags (-package,
  901. -- -hide-package). This needs to know about the unusable packages, since if a
  902. -- user tries to enable an unusable package, we should let them know.
  903. --
  904. vis_map2 <- foldM (applyPackageFlag dflags unusable
  905. (gopt Opt_HideAllPackages dflags) pkgs1)
  906. vis_map1 other_flags
  907. --
  908. -- Sort out which packages are wired in. This has to be done last, since
  909. -- it modifies the unit ids of wired in packages, but when we process
  910. -- package arguments we need to key against the old versions.
  911. --
  912. (pkgs2, wired_map) <- findWiredInPackages dflags pkgs1 vis_map2
  913. -- Update the visibility map, so we treat wired packages as visible.
  914. let vis_map = updateVisibilityMap wired_map vis_map2
  915. let hide_plugin_pkgs = gopt Opt_HideAllPluginPackages dflags
  916. plugin_vis_map <-
  917. case pluginPackageFlags dflags of
  918. -- common case; try to share the old vis_map
  919. [] | not hide_plugin_pkgs -> return vis_map
  920. | otherwise -> return emptyUDFM
  921. _ -> do let plugin_vis_map1
  922. | hide_plugin_pkgs = emptyUDFM
  923. -- Use the vis_map PRIOR to wired in,
  924. -- because otherwise applyPackageFlag
  925. -- won't work.
  926. | otherwise = vis_map2
  927. plugin_vis_map2
  928. <- foldM (applyPackageFlag dflags unusable
  929. (gopt Opt_HideAllPluginPackages dflags) pkgs1)
  930. plugin_vis_map1
  931. (reverse (pluginPackageFlags dflags))
  932. -- Updating based on wired in packages is mostly
  933. -- good hygiene, because it won't matter: no wired in
  934. -- package has a compiler plugin.
  935. -- TODO: If a wired in package had a compiler plugin,
  936. -- and you tried to pick different wired in packages
  937. -- with the plugin flags and the normal flags... what
  938. -- would happen? I don't know! But this doesn't seem
  939. -- likely to actually happen.
  940. return (updateVisibilityMap wired_map plugin_vis_map2)
  941. --
  942. -- Here we build up a set of the packages mentioned in -package
  943. -- flags on the command line; these are called the "preload"
  944. -- packages. we link these packages in eagerly. The preload set
  945. -- should contain at least rts & base, which is why we pretend that
  946. -- the command line contains -package rts & -package base.
  947. --
  948. let preload1 = [ let key = unitId p
  949. in fromMaybe key (Map.lookup key wired_map)
  950. | f <- other_flags, p <- get_exposed f ]
  951. get_exposed (ExposePackage _ a _) = take 1 . sortByVersion
  952. . filter (matching a)
  953. $ pkgs1
  954. get_exposed _ = []
  955. let pkg_db = extendPackageConfigMap emptyPackageConfigMap pkgs2
  956. let preload2 = preload1
  957. let
  958. -- add base & rts to the preload packages
  959. basicLinkedPackages
  960. | gopt Opt_AutoLinkPackages dflags
  961. = filter (flip elemUDFM pkg_db)
  962. [baseUnitId, rtsUnitId]
  963. | otherwise = []
  964. -- but in any case remove the current package from the set of
  965. -- preloaded packages so that base/rts does not end up in the
  966. -- set up preloaded package when we are just building it
  967. preload3 = nub $ filter (/= this_package)
  968. $ (basicLinkedPackages ++ preload2)
  969. -- Close the preload packages with their dependencies
  970. dep_preload <- closeDeps dflags pkg_db (zip preload3 (repeat Nothing))
  971. let new_dep_preload = filter (`notElem` preload0) dep_preload
  972. -- Force pstate to avoid leaking the dflags0 passed to mkPackageState
  973. let !pstate = PackageState{
  974. preloadPackages = dep_preload,
  975. explicitPackages = foldUDFM (\pkg xs ->
  976. if elemUDFM (packageConfigId pkg) vis_map
  977. then packageConfigId pkg : xs
  978. else xs) [] pkg_db,
  979. pkgIdMap = pkg_db,
  980. moduleToPkgConfAll = mkModuleToPkgConfAll dflags pkg_db vis_map,
  981. pluginModuleToPkgConfAll = mkModuleToPkgConfAll dflags pkg_db plugin_vis_map
  982. }
  983. return (pstate, new_dep_preload, this_package)
  984. -- -----------------------------------------------------------------------------
  985. -- | Makes the mapping from module to package info
  986. mkModuleToPkgConfAll
  987. :: DynFlags
  988. -> PackageConfigMap
  989. -> VisibilityMap
  990. -> ModuleToPkgConfAll
  991. mkModuleToPkgConfAll dflags pkg_db vis_map =
  992. foldl' extend_modmap emptyMap (eltsUDFM pkg_db)
  993. where
  994. emptyMap = Map.empty
  995. sing pk m _ = Map.singleton (mkModule pk m)
  996. addListTo = foldl' merge
  997. merge m (k, v) = MapStrict.insertWith (Map.unionWith mappend) k v m
  998. setOrigins m os = fmap (const os) m
  999. extend_modmap modmap pkg = addListTo modmap theBindings
  1000. where
  1001. theBindings :: [(ModuleName, Map Module ModuleOrigin)]
  1002. theBindings | Just (b,rns,_) <- lookupUDFM vis_map (packageConfigId pkg)
  1003. = newBindings b rns
  1004. | otherwise = newBindings False []
  1005. newBindings :: Bool
  1006. -> [(ModuleName, ModuleName)]
  1007. -> [(ModuleName, Map Module ModuleOrigin)]
  1008. newBindings e rns = es e ++ hiddens ++ map rnBinding rns
  1009. rnBinding :: (ModuleName, ModuleName)
  1010. -> (ModuleName, Map Module ModuleOrigin)
  1011. rnBinding (orig, new) = (new, setOrigins origEntry fromFlag)
  1012. where origEntry = case lookupUFM esmap orig of
  1013. Just r -> r
  1014. Nothing -> throwGhcException (CmdLineError (showSDoc dflags
  1015. (text "package flag: could not find module name" <+>
  1016. ppr orig <+> text "in package" <+> ppr pk)))
  1017. es :: Bool -> [(ModuleName, Map Module ModuleOrigin)]
  1018. es e = do
  1019. (m, exposedReexport) <- exposed_mods
  1020. let (pk', m', pkg', origin') =
  1021. case exposedReexport of
  1022. Nothing -> (pk, m, pkg, fromExposedModules e)
  1023. Just (Module pk' m') ->
  1024. let pkg' = pkg_lookup pk'
  1025. in (pk', m', pkg', fromReexportedModules e pkg')
  1026. return (m, sing pk' m' pkg' origin')
  1027. esmap :: UniqFM (Map Module ModuleOrigin)
  1028. esmap = listToUFM (es False) -- parameter here doesn't matter, orig will
  1029. -- be overwritten
  1030. hiddens = [(m, sing pk m pkg ModHidden) | m <- hidden_mods]
  1031. pk = packageConfigId pkg
  1032. pkg_lookup = expectJust "mkModuleToPkgConf" . lookupPackage' pkg_db
  1033. exposed_mods = exposedModules pkg
  1034. hidden_mods = hiddenModules pkg
  1035. -- -----------------------------------------------------------------------------
  1036. -- Extracting information from the packages in scope
  1037. -- Many of these functions take a list of packages: in those cases,
  1038. -- the list is expected to contain the "dependent packages",
  1039. -- i.e. those packages that were found to be depended on by the
  1040. -- current module/program. These can be auto

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