PageRenderTime 54ms CodeModel.GetById 21ms RepoModel.GetById 0ms app.codeStats 0ms

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

http://picorec.googlecode.com/
Haskell | 977 lines | 568 code | 150 blank | 259 comment | 20 complexity | 4deb899c28c84e670a757c341389cbd5 MD5 | raw file
Possible License(s): BSD-3-Clause, BSD-2-Clause
  1. %
  2. % (c) The University of Glasgow, 2006
  3. %
  4. \begin{code}
  5. -- | Package manipulation
  6. module Packages (
  7. module PackageConfig,
  8. -- * The PackageConfigMap
  9. PackageConfigMap, emptyPackageConfigMap, lookupPackage,
  10. extendPackageConfigMap, dumpPackages,
  11. -- * Reading the package config, and processing cmdline args
  12. PackageState(..),
  13. initPackages,
  14. getPackageDetails,
  15. lookupModuleInAllPackages,
  16. -- * Inspecting the set of packages in scope
  17. getPackageIncludePath,
  18. getPackageLibraryPath,
  19. getPackageLinkOpts,
  20. getPackageExtraCcOpts,
  21. getPackageFrameworkPath,
  22. getPackageFrameworks,
  23. getPreloadPackagesAnd,
  24. collectIncludeDirs, collectLibraryPaths, collectLinkOpts,
  25. packageHsLibs,
  26. -- * Utils
  27. isDllName
  28. )
  29. where
  30. #include "HsVersions.h"
  31. import PackageConfig
  32. import DynFlags ( dopt, DynFlag(..), DynFlags(..), PackageFlag(..) )
  33. import StaticFlags
  34. import Config ( cProjectVersion )
  35. import Name ( Name, nameModule_maybe )
  36. import UniqFM
  37. import Module
  38. import Util
  39. import Panic
  40. import Outputable
  41. import Maybes
  42. import System.Environment ( getEnv )
  43. import Distribution.InstalledPackageInfo
  44. import Distribution.InstalledPackageInfo.Binary
  45. import Distribution.Package hiding (PackageId,depends)
  46. import FastString
  47. import ErrUtils ( debugTraceMsg, putMsg, Message )
  48. import Exception
  49. import System.Directory
  50. import System.FilePath
  51. import Control.Monad
  52. import Data.List as List
  53. import Data.Map (Map)
  54. import qualified Data.Map as Map
  55. import qualified FiniteMap as Map
  56. import qualified Data.Set as Set
  57. -- ---------------------------------------------------------------------------
  58. -- The Package state
  59. -- | Package state is all stored in 'DynFlag's, including the details of
  60. -- all packages, which packages are exposed, and which modules they
  61. -- provide.
  62. --
  63. -- The package state is computed by 'initPackages', and kept in DynFlags.
  64. --
  65. -- * @-package <pkg>@ causes @<pkg>@ to become exposed, and all other packages
  66. -- with the same name to become hidden.
  67. --
  68. -- * @-hide-package <pkg>@ causes @<pkg>@ to become hidden.
  69. --
  70. -- * Let @exposedPackages@ be the set of packages thus exposed.
  71. -- Let @depExposedPackages@ be the transitive closure from @exposedPackages@ of
  72. -- their dependencies.
  73. --
  74. -- * When searching for a module from an preload import declaration,
  75. -- only the exposed modules in @exposedPackages@ are valid.
  76. --
  77. -- * When searching for a module from an implicit import, all modules
  78. -- from @depExposedPackages@ are valid.
  79. --
  80. -- * When linking in a compilation manager mode, we link in packages the
  81. -- program depends on (the compiler knows this list by the
  82. -- time it gets to the link step). Also, we link in all packages
  83. -- which were mentioned with preload @-package@ flags on the command-line,
  84. -- or are a transitive dependency of same, or are \"base\"\/\"rts\".
  85. -- The reason for this is that we might need packages which don't
  86. -- contain any Haskell modules, and therefore won't be discovered
  87. -- by the normal mechanism of dependency tracking.
  88. -- Notes on DLLs
  89. -- ~~~~~~~~~~~~~
  90. -- When compiling module A, which imports module B, we need to
  91. -- know whether B will be in the same DLL as A.
  92. -- If it's in the same DLL, we refer to B_f_closure
  93. -- If it isn't, we refer to _imp__B_f_closure
  94. -- When compiling A, we record in B's Module value whether it's
  95. -- in a different DLL, by setting the DLL flag.
  96. data PackageState = PackageState {
  97. pkgIdMap :: PackageConfigMap, -- PackageId -> PackageConfig
  98. -- The exposed flags are adjusted according to -package and
  99. -- -hide-package flags, and -ignore-package removes packages.
  100. preloadPackages :: [PackageId],
  101. -- The packages we're going to link in eagerly. This list
  102. -- should be in reverse dependency order; that is, a package
  103. -- is always mentioned before the packages it depends on.
  104. moduleToPkgConfAll :: UniqFM [(PackageConfig,Bool)], -- ModuleEnv mapping
  105. -- Derived from pkgIdMap.
  106. -- Maps Module to (pkgconf,exposed), where pkgconf is the
  107. -- PackageConfig for the package containing the module, and
  108. -- exposed is True if the package exposes that module.
  109. installedPackageIdMap :: InstalledPackageIdMap
  110. }
  111. -- | A PackageConfigMap maps a 'PackageId' to a 'PackageConfig'
  112. type PackageConfigMap = UniqFM PackageConfig
  113. type InstalledPackageIdMap = Map InstalledPackageId PackageId
  114. type InstalledPackageIndex = Map InstalledPackageId PackageConfig
  115. emptyPackageConfigMap :: PackageConfigMap
  116. emptyPackageConfigMap = emptyUFM
  117. -- | Find the package we know about with the given id (e.g. \"foo-1.0\"), if any
  118. lookupPackage :: PackageConfigMap -> PackageId -> Maybe PackageConfig
  119. lookupPackage = lookupUFM
  120. extendPackageConfigMap
  121. :: PackageConfigMap -> [PackageConfig] -> PackageConfigMap
  122. extendPackageConfigMap pkg_map new_pkgs
  123. = foldl add pkg_map new_pkgs
  124. where add pkg_map p = addToUFM pkg_map (packageConfigId p) p
  125. -- | Looks up the package with the given id in the package state, panicing if it is
  126. -- not found
  127. getPackageDetails :: PackageState -> PackageId -> PackageConfig
  128. getPackageDetails ps pid = expectJust "getPackageDetails" (lookupPackage (pkgIdMap ps) pid)
  129. -- ----------------------------------------------------------------------------
  130. -- Loading the package config files and building up the package state
  131. -- | Call this after 'DynFlags.parseDynFlags'. It reads the package
  132. -- configuration files, and sets up various internal tables of package
  133. -- information, according to the package-related flags on the
  134. -- command-line (@-package@, @-hide-package@ etc.)
  135. --
  136. -- Returns a list of packages to link in if we're doing dynamic linking.
  137. -- This list contains the packages that the user explicitly mentioned with
  138. -- @-package@ flags.
  139. --
  140. -- 'initPackages' can be called again subsequently after updating the
  141. -- 'packageFlags' field of the 'DynFlags', and it will update the
  142. -- 'pkgState' in 'DynFlags' and return a list of packages to
  143. -- link in.
  144. initPackages :: DynFlags -> IO (DynFlags, [PackageId])
  145. initPackages dflags = do
  146. pkg_db <- case pkgDatabase dflags of
  147. Nothing -> readPackageConfigs dflags
  148. Just db -> return $ maybeHidePackages dflags db
  149. (pkg_state, preload, this_pkg)
  150. <- mkPackageState dflags pkg_db [] (thisPackage dflags)
  151. return (dflags{ pkgDatabase = Just pkg_db,
  152. pkgState = pkg_state,
  153. thisPackage = this_pkg },
  154. preload)
  155. -- -----------------------------------------------------------------------------
  156. -- Reading the package database(s)
  157. readPackageConfigs :: DynFlags -> IO [PackageConfig]
  158. readPackageConfigs dflags = do
  159. e_pkg_path <- tryIO (getEnv "GHC_PACKAGE_PATH")
  160. system_pkgconfs <- getSystemPackageConfigs dflags
  161. let pkgconfs = case e_pkg_path of
  162. Left _ -> system_pkgconfs
  163. Right path
  164. | last cs == "" -> init cs ++ system_pkgconfs
  165. | otherwise -> cs
  166. where cs = parseSearchPath path
  167. -- if the path ends in a separator (eg. "/foo/bar:")
  168. -- the we tack on the system paths.
  169. pkgs <- mapM (readPackageConfig dflags)
  170. (pkgconfs ++ reverse (extraPkgConfs dflags))
  171. -- later packages shadow earlier ones. extraPkgConfs
  172. -- is in the opposite order to the flags on the
  173. -- command line.
  174. return (concat pkgs)
  175. getSystemPackageConfigs :: DynFlags -> IO [FilePath]
  176. getSystemPackageConfigs dflags = do
  177. -- System one always comes first
  178. let system_pkgconf = systemPackageConfig dflags
  179. -- Read user's package conf (eg. ~/.ghc/i386-linux-6.3/package.conf)
  180. -- unless the -no-user-package-conf flag was given.
  181. user_pkgconf <- do
  182. if not (dopt Opt_ReadUserPackageConf dflags) then return [] else do
  183. appdir <- getAppUserDataDirectory "ghc"
  184. let
  185. dir = appdir </> (TARGET_ARCH ++ '-':TARGET_OS ++ '-':cProjectVersion)
  186. pkgconf = dir </> "package.conf.d"
  187. --
  188. exist <- doesDirectoryExist pkgconf
  189. if exist then return [pkgconf] else return []
  190. `catchIO` (\_ -> return [])
  191. return (system_pkgconf : user_pkgconf)
  192. readPackageConfig :: DynFlags -> FilePath -> IO [PackageConfig]
  193. readPackageConfig dflags conf_file = do
  194. isdir <- doesDirectoryExist conf_file
  195. proto_pkg_configs <-
  196. if isdir
  197. then do let filename = conf_file </> "package.cache"
  198. debugTraceMsg dflags 2 (text "Using binary package database:" <+> text filename)
  199. conf <- readBinPackageDB filename
  200. return (map installedPackageInfoToPackageConfig conf)
  201. else do
  202. isfile <- doesFileExist conf_file
  203. when (not isfile) $
  204. ghcError $ InstallationError $
  205. "can't find a package database at " ++ conf_file
  206. debugTraceMsg dflags 2 (text "Using package config file:" <+> text conf_file)
  207. str <- readFile conf_file
  208. return (map installedPackageInfoToPackageConfig $ read str)
  209. let
  210. top_dir = topDir dflags
  211. pkg_configs1 = mungePackagePaths top_dir proto_pkg_configs
  212. pkg_configs2 = maybeHidePackages dflags pkg_configs1
  213. --
  214. return pkg_configs2
  215. maybeHidePackages :: DynFlags -> [PackageConfig] -> [PackageConfig]
  216. maybeHidePackages dflags pkgs
  217. | dopt Opt_HideAllPackages dflags = map hide pkgs
  218. | otherwise = pkgs
  219. where
  220. hide pkg = pkg{ exposed = False }
  221. mungePackagePaths :: String -> [PackageConfig] -> [PackageConfig]
  222. -- Replace the string "$topdir" at the beginning of a path
  223. -- with the current topdir (obtained from the -B option).
  224. mungePackagePaths top_dir ps = map munge_pkg ps
  225. where
  226. munge_pkg p = p{ importDirs = munge_paths (importDirs p),
  227. includeDirs = munge_paths (includeDirs p),
  228. libraryDirs = munge_paths (libraryDirs p),
  229. frameworkDirs = munge_paths (frameworkDirs p),
  230. haddockInterfaces = munge_paths (haddockInterfaces p),
  231. haddockHTMLs = munge_paths (haddockHTMLs p)
  232. }
  233. munge_paths = map munge_path
  234. munge_path p
  235. | Just p' <- stripPrefix "$topdir" p = top_dir ++ p'
  236. | Just p' <- stripPrefix "$httptopdir" p = toHttpPath top_dir ++ p'
  237. | otherwise = p
  238. toHttpPath p = "file:///" ++ p
  239. -- -----------------------------------------------------------------------------
  240. -- Modify our copy of the package database based on a package flag
  241. -- (-package, -hide-package, -ignore-package).
  242. applyPackageFlag
  243. :: UnusablePackages
  244. -> [PackageConfig] -- Initial database
  245. -> PackageFlag -- flag to apply
  246. -> IO [PackageConfig] -- new database
  247. applyPackageFlag unusable pkgs flag =
  248. case flag of
  249. ExposePackage str ->
  250. case selectPackages (matchingStr str) pkgs unusable of
  251. Left ps -> packageFlagErr flag ps
  252. Right (p:ps,qs) -> return (p':ps')
  253. where p' = p {exposed=True}
  254. ps' = hideAll (pkgName (sourcePackageId p)) (ps++qs)
  255. _ -> panic "applyPackageFlag"
  256. ExposePackageId str ->
  257. case selectPackages (matchingId str) pkgs unusable of
  258. Left ps -> packageFlagErr flag ps
  259. Right (p:ps,qs) -> return (p':ps')
  260. where p' = p {exposed=True}
  261. ps' = hideAll (pkgName (sourcePackageId p)) (ps++qs)
  262. _ -> panic "applyPackageFlag"
  263. HidePackage str ->
  264. case selectPackages (matchingStr str) pkgs unusable of
  265. Left ps -> packageFlagErr flag ps
  266. Right (ps,qs) -> return (map hide ps ++ qs)
  267. where hide p = p {exposed=False}
  268. _ -> panic "applyPackageFlag"
  269. where
  270. -- When a package is requested to be exposed, we hide all other
  271. -- packages with the same name.
  272. hideAll name ps = map maybe_hide ps
  273. where maybe_hide p
  274. | pkgName (sourcePackageId p) == name = p {exposed=False}
  275. | otherwise = p
  276. selectPackages :: (PackageConfig -> Bool) -> [PackageConfig]
  277. -> UnusablePackages
  278. -> Either [(PackageConfig, UnusablePackageReason)]
  279. ([PackageConfig], [PackageConfig])
  280. selectPackages matches pkgs unusable
  281. = let
  282. (ps,rest) = partition matches pkgs
  283. reasons = [ (p, Map.lookup (installedPackageId p) unusable)
  284. | p <- ps ]
  285. in
  286. if all (isJust.snd) reasons
  287. then Left [ (p, reason) | (p,Just reason) <- reasons ]
  288. else Right (sortByVersion [ p | (p,Nothing) <- reasons ], rest)
  289. -- A package named on the command line can either include the
  290. -- version, or just the name if it is unambiguous.
  291. matchingStr :: String -> PackageConfig -> Bool
  292. matchingStr str p
  293. = str == display (sourcePackageId p)
  294. || str == display (pkgName (sourcePackageId p))
  295. matchingId :: String -> PackageConfig -> Bool
  296. matchingId str p = InstalledPackageId str == installedPackageId p
  297. sortByVersion :: [InstalledPackageInfo_ m] -> [InstalledPackageInfo_ m]
  298. sortByVersion = sortBy (flip (comparing (pkgVersion.sourcePackageId)))
  299. comparing :: Ord a => (t -> a) -> t -> t -> Ordering
  300. comparing f a b = f a `compare` f b
  301. packageFlagErr :: PackageFlag
  302. -> [(PackageConfig, UnusablePackageReason)]
  303. -> IO a
  304. -- for missing DPH package we emit a more helpful error message, because
  305. -- this may be the result of using -fdph-par or -fdph-seq.
  306. packageFlagErr (ExposePackage pkg) [] | is_dph_package pkg
  307. = ghcError (CmdLineError (showSDoc $ dph_err))
  308. where dph_err = text "the " <> text pkg <> text " package is not installed."
  309. $$ text "To install it: \"cabal install dph\"."
  310. is_dph_package pkg = "dph" `isPrefixOf` pkg
  311. packageFlagErr flag reasons = ghcError (CmdLineError (showSDoc $ err))
  312. where err = text "cannot satisfy " <> ppr_flag <>
  313. (if null reasons then empty else text ": ") $$
  314. nest 4 (ppr_reasons $$
  315. text "(use -v for more information)")
  316. ppr_flag = case flag of
  317. IgnorePackage p -> text "-ignore-package " <> text p
  318. HidePackage p -> text "-hide-package " <> text p
  319. ExposePackage p -> text "-package " <> text p
  320. ExposePackageId p -> text "-package-id " <> text p
  321. ppr_reasons = vcat (map ppr_reason reasons)
  322. ppr_reason (p, reason) = pprReason (pprIPkg p <+> text "is") reason
  323. -- -----------------------------------------------------------------------------
  324. -- Hide old versions of packages
  325. --
  326. -- hide all packages for which there is also a later version
  327. -- that is already exposed. This just makes it non-fatal to have two
  328. -- versions of a package exposed, which can happen if you install a
  329. -- later version of a package in the user database, for example.
  330. --
  331. hideOldPackages :: DynFlags -> [PackageConfig] -> IO [PackageConfig]
  332. hideOldPackages dflags pkgs = mapM maybe_hide pkgs
  333. where maybe_hide p
  334. | not (exposed p) = return p
  335. | (p' : _) <- later_versions = do
  336. debugTraceMsg dflags 2 $
  337. (ptext (sLit "hiding package") <+> pprSPkg p <+>
  338. ptext (sLit "to avoid conflict with later version") <+>
  339. pprSPkg p')
  340. return (p {exposed=False})
  341. | otherwise = return p
  342. where myname = pkgName (sourcePackageId p)
  343. myversion = pkgVersion (sourcePackageId p)
  344. later_versions = [ p | p <- pkgs, exposed p,
  345. let pkg = sourcePackageId p,
  346. pkgName pkg == myname,
  347. pkgVersion pkg > myversion ]
  348. -- -----------------------------------------------------------------------------
  349. -- Wired-in packages
  350. findWiredInPackages
  351. :: DynFlags
  352. -> [PackageConfig] -- database
  353. -> IO [PackageConfig]
  354. findWiredInPackages dflags pkgs = do
  355. --
  356. -- Now we must find our wired-in packages, and rename them to
  357. -- their canonical names (eg. base-1.0 ==> base).
  358. --
  359. let
  360. wired_in_pkgids :: [String]
  361. wired_in_pkgids = map packageIdString
  362. [ primPackageId,
  363. integerPackageId,
  364. basePackageId,
  365. rtsPackageId,
  366. thPackageId,
  367. dphSeqPackageId,
  368. dphParPackageId ]
  369. matches :: PackageConfig -> String -> Bool
  370. pc `matches` pid = display (pkgName (sourcePackageId pc)) == pid
  371. -- find which package corresponds to each wired-in package
  372. -- delete any other packages with the same name
  373. -- update the package and any dependencies to point to the new
  374. -- one.
  375. --
  376. -- When choosing which package to map to a wired-in package
  377. -- name, we prefer exposed packages, and pick the latest
  378. -- version. To override the default choice, -hide-package
  379. -- could be used to hide newer versions.
  380. --
  381. findWiredInPackage :: [PackageConfig] -> String
  382. -> IO (Maybe InstalledPackageId)
  383. findWiredInPackage pkgs wired_pkg =
  384. let all_ps = [ p | p <- pkgs, p `matches` wired_pkg ] in
  385. case all_ps of
  386. [] -> notfound
  387. many -> pick (head (sortByVersion many))
  388. where
  389. notfound = do
  390. debugTraceMsg dflags 2 $
  391. ptext (sLit "wired-in package ")
  392. <> text wired_pkg
  393. <> ptext (sLit " not found.")
  394. return Nothing
  395. pick :: InstalledPackageInfo_ ModuleName
  396. -> IO (Maybe InstalledPackageId)
  397. pick pkg = do
  398. debugTraceMsg dflags 2 $
  399. ptext (sLit "wired-in package ")
  400. <> text wired_pkg
  401. <> ptext (sLit " mapped to ")
  402. <> pprIPkg pkg
  403. return (Just (installedPackageId pkg))
  404. mb_wired_in_ids <- mapM (findWiredInPackage pkgs) wired_in_pkgids
  405. let
  406. wired_in_ids = catMaybes mb_wired_in_ids
  407. -- this is old: we used to assume that if there were
  408. -- multiple versions of wired-in packages installed that
  409. -- they were mutually exclusive. Now we're assuming that
  410. -- you have one "main" version of each wired-in package
  411. -- (the latest version), and the others are backward-compat
  412. -- wrappers that depend on this one. e.g. base-4.0 is the
  413. -- latest, base-3.0 is a compat wrapper depending on base-4.0.
  414. {-
  415. deleteOtherWiredInPackages pkgs = filterOut bad pkgs
  416. where bad p = any (p `matches`) wired_in_pkgids
  417. && package p `notElem` map fst wired_in_ids
  418. -}
  419. updateWiredInDependencies pkgs = map upd_pkg pkgs
  420. where upd_pkg p
  421. | installedPackageId p `elem` wired_in_ids
  422. = p { sourcePackageId = (sourcePackageId p){ pkgVersion = Version [] [] } }
  423. | otherwise
  424. = p
  425. return $ updateWiredInDependencies pkgs
  426. -- ----------------------------------------------------------------------------
  427. data UnusablePackageReason
  428. = IgnoredWithFlag
  429. | MissingDependencies [InstalledPackageId]
  430. | ShadowedBy InstalledPackageId
  431. type UnusablePackages = Map InstalledPackageId UnusablePackageReason
  432. pprReason :: SDoc -> UnusablePackageReason -> SDoc
  433. pprReason pref reason = case reason of
  434. IgnoredWithFlag ->
  435. pref <+> ptext (sLit "ignored due to an -ignore-package flag")
  436. MissingDependencies deps ->
  437. pref <+>
  438. ptext (sLit "unusable due to missing or recursive dependencies:") $$
  439. nest 2 (hsep (map (text.display) deps))
  440. ShadowedBy ipid ->
  441. pref <+> ptext (sLit "shadowed by package ") <> text (display ipid)
  442. reportUnusable :: DynFlags -> UnusablePackages -> IO ()
  443. reportUnusable dflags pkgs = mapM_ report (Map.toList pkgs)
  444. where
  445. report (ipid, reason) =
  446. debugTraceMsg dflags 2 $
  447. pprReason
  448. (ptext (sLit "package") <+>
  449. text (display ipid) <+> text "is") reason
  450. -- ----------------------------------------------------------------------------
  451. --
  452. -- Detect any packages that have missing dependencies, and also any
  453. -- mutually-recursive groups of packages (loops in the package graph
  454. -- are not allowed). We do this by taking the least fixpoint of the
  455. -- dependency graph, repeatedly adding packages whose dependencies are
  456. -- satisfied until no more can be added.
  457. --
  458. findBroken :: [PackageConfig] -> UnusablePackages
  459. findBroken pkgs = go [] Map.empty pkgs
  460. where
  461. go avail ipids not_avail =
  462. case partitionWith (depsAvailable ipids) not_avail of
  463. ([], not_avail) ->
  464. Map.fromList [ (installedPackageId p, MissingDependencies deps)
  465. | (p,deps) <- not_avail ]
  466. (new_avail, not_avail) ->
  467. go (new_avail ++ avail) new_ipids (map fst not_avail)
  468. where new_ipids = Map.insertList
  469. [ (installedPackageId p, p) | p <- new_avail ]
  470. ipids
  471. depsAvailable :: InstalledPackageIndex
  472. -> PackageConfig
  473. -> Either PackageConfig (PackageConfig, [InstalledPackageId])
  474. depsAvailable ipids pkg
  475. | null dangling = Left pkg
  476. | otherwise = Right (pkg, dangling)
  477. where dangling = filter (not . (`Map.member` ipids)) (depends pkg)
  478. -- -----------------------------------------------------------------------------
  479. -- Eliminate shadowed packages, giving the user some feedback
  480. -- later packages in the list should shadow earlier ones with the same
  481. -- package name/version. Additionally, a package may be preferred if
  482. -- it is in the transitive closure of packages selected using -package-id
  483. -- flags.
  484. shadowPackages :: [PackageConfig] -> [InstalledPackageId] -> UnusablePackages
  485. shadowPackages pkgs preferred
  486. = let (shadowed,_) = foldl check ([],emptyUFM) pkgs
  487. in Map.fromList shadowed
  488. where
  489. check (shadowed,pkgmap) pkg
  490. | Just oldpkg <- lookupUFM pkgmap (packageConfigId pkg)
  491. , let
  492. ipid_new = installedPackageId pkg
  493. ipid_old = installedPackageId oldpkg
  494. --
  495. , ipid_old /= ipid_new
  496. = if ipid_old `elem` preferred
  497. then ( (ipid_new, ShadowedBy ipid_old) : shadowed, pkgmap )
  498. else ( (ipid_old, ShadowedBy ipid_new) : shadowed, pkgmap' )
  499. | otherwise
  500. = (shadowed, pkgmap')
  501. where
  502. pkgmap' = addToUFM pkgmap (packageConfigId pkg) pkg
  503. -- -----------------------------------------------------------------------------
  504. ignorePackages :: [PackageFlag] -> [PackageConfig] -> UnusablePackages
  505. ignorePackages flags pkgs = Map.fromList (concatMap doit flags)
  506. where
  507. doit (IgnorePackage str) =
  508. case partition (matchingStr str) pkgs of
  509. (ps, _) -> [ (installedPackageId p, IgnoredWithFlag)
  510. | p <- ps ]
  511. -- missing package is not an error for -ignore-package,
  512. -- because a common usage is to -ignore-package P as
  513. -- a preventative measure just in case P exists.
  514. doit _ = panic "ignorePackages"
  515. -- -----------------------------------------------------------------------------
  516. depClosure :: InstalledPackageIndex
  517. -> [InstalledPackageId]
  518. -> [InstalledPackageId]
  519. depClosure index ipids = closure Map.empty ipids
  520. where
  521. closure set [] = Map.keys set
  522. closure set (ipid : ipids)
  523. | ipid `Map.member` set = closure set ipids
  524. | Just p <- Map.lookup ipid index = closure (Map.insert ipid p set)
  525. (depends p ++ ipids)
  526. | otherwise = closure set ipids
  527. -- -----------------------------------------------------------------------------
  528. -- When all the command-line options are in, we can process our package
  529. -- settings and populate the package state.
  530. mkPackageState
  531. :: DynFlags
  532. -> [PackageConfig] -- initial database
  533. -> [PackageId] -- preloaded packages
  534. -> PackageId -- this package
  535. -> IO (PackageState,
  536. [PackageId], -- new packages to preload
  537. PackageId) -- this package, might be modified if the current
  538. -- package is a wired-in package.
  539. mkPackageState dflags pkgs0 preload0 this_package = do
  540. {-
  541. Plan.
  542. 1. P = transitive closure of packages selected by -package-id
  543. 2. Apply shadowing. When there are multiple packages with the same
  544. sourcePackageId,
  545. * if one is in P, use that one
  546. * otherwise, use the one highest in the package stack
  547. [
  548. rationale: we cannot use two packages with the same sourcePackageId
  549. in the same program, because sourcePackageId is the symbol prefix.
  550. Hence we must select a consistent set of packages to use. We have
  551. a default algorithm for doing this: packages higher in the stack
  552. shadow those lower down. This default algorithm can be overriden
  553. by giving explicit -package-id flags; then we have to take these
  554. preferences into account when selecting which other packages are
  555. made available.
  556. Our simple algorithm throws away some solutions: there may be other
  557. consistent sets that would satisfy the -package flags, but it's
  558. not GHC's job to be doing constraint solving.
  559. ]
  560. 3. remove packages selected by -ignore-package
  561. 4. remove any packages with missing dependencies, or mutually recursive
  562. dependencies.
  563. 5. report (with -v) any packages that were removed by steps 2-4
  564. 6. apply flags to set exposed/hidden on the resulting packages
  565. - if any flag refers to a package which was removed by 2-4, then
  566. we can give an error message explaining why
  567. 7. hide any packages which are superseded by later exposed packages
  568. -}
  569. let
  570. flags = reverse (packageFlags dflags)
  571. -- pkgs0 with duplicate packages filtered out. This is
  572. -- important: it is possible for a package in the global package
  573. -- DB to have the same IPID as a package in the user DB, and
  574. -- we want the latter to take precedence. This is not the same
  575. -- as shadowing (below), since in this case the two packages
  576. -- have the same ABI and are interchangeable.
  577. --
  578. -- #4072: note that we must retain the ordering of the list here
  579. -- so that shadowing behaves as expected when we apply it later.
  580. pkgs0_unique = snd $ foldr del (Set.empty,[]) pkgs0
  581. where del p (s,ps)
  582. | pid `Set.member` s = (s,ps)
  583. | otherwise = (Set.insert pid s, p:ps)
  584. where pid = installedPackageId p
  585. -- XXX this is just a variant of nub
  586. ipid_map = Map.fromList [ (installedPackageId p, p) | p <- pkgs0 ]
  587. ipid_selected = depClosure ipid_map [ InstalledPackageId i
  588. | ExposePackageId i <- flags ]
  589. (ignore_flags, other_flags) = partition is_ignore flags
  590. is_ignore IgnorePackage{} = True
  591. is_ignore _ = False
  592. shadowed = shadowPackages pkgs0_unique ipid_selected
  593. ignored = ignorePackages ignore_flags pkgs0_unique
  594. pkgs0' = filter (not . (`Map.member` (Map.union shadowed ignored)) . installedPackageId) pkgs0_unique
  595. broken = findBroken pkgs0'
  596. unusable = shadowed `Map.union` ignored `Map.union` broken
  597. reportUnusable dflags unusable
  598. --
  599. -- Modify the package database according to the command-line flags
  600. -- (-package, -hide-package, -ignore-package, -hide-all-packages).
  601. --
  602. pkgs1 <- foldM (applyPackageFlag unusable) pkgs0_unique other_flags
  603. let pkgs2 = filter (not . (`Map.member` unusable) . installedPackageId) pkgs1
  604. -- Here we build up a set of the packages mentioned in -package
  605. -- flags on the command line; these are called the "preload"
  606. -- packages. we link these packages in eagerly. The preload set
  607. -- should contain at least rts & base, which is why we pretend that
  608. -- the command line contains -package rts & -package base.
  609. --
  610. let preload1 = [ installedPackageId p | f <- flags, p <- get_exposed f ]
  611. get_exposed (ExposePackage s) = filter (matchingStr s) pkgs2
  612. get_exposed (ExposePackageId s) = filter (matchingId s) pkgs2
  613. get_exposed _ = []
  614. -- hide packages that are subsumed by later versions
  615. pkgs3 <- hideOldPackages dflags pkgs2
  616. -- sort out which packages are wired in
  617. pkgs4 <- findWiredInPackages dflags pkgs3
  618. let pkg_db = extendPackageConfigMap emptyPackageConfigMap pkgs4
  619. ipid_map = Map.fromList [ (installedPackageId p, packageConfigId p)
  620. | p <- pkgs4 ]
  621. lookupIPID ipid@(InstalledPackageId str)
  622. | Just pid <- Map.lookup ipid ipid_map = return pid
  623. | otherwise = missingPackageErr str
  624. preload2 <- mapM lookupIPID preload1
  625. let
  626. -- add base & rts to the preload packages
  627. basicLinkedPackages
  628. | dopt Opt_AutoLinkPackages dflags
  629. = filter (flip elemUFM pkg_db) [basePackageId, rtsPackageId]
  630. | otherwise = []
  631. -- but in any case remove the current package from the set of
  632. -- preloaded packages so that base/rts does not end up in the
  633. -- set up preloaded package when we are just building it
  634. preload3 = nub $ filter (/= this_package)
  635. $ (basicLinkedPackages ++ preload2)
  636. -- Close the preload packages with their dependencies
  637. dep_preload <- closeDeps pkg_db ipid_map (zip preload3 (repeat Nothing))
  638. let new_dep_preload = filter (`notElem` preload0) dep_preload
  639. let pstate = PackageState{ preloadPackages = dep_preload,
  640. pkgIdMap = pkg_db,
  641. moduleToPkgConfAll = mkModuleMap pkg_db,
  642. installedPackageIdMap = ipid_map
  643. }
  644. return (pstate, new_dep_preload, this_package)
  645. -- -----------------------------------------------------------------------------
  646. -- Make the mapping from module to package info
  647. mkModuleMap
  648. :: PackageConfigMap
  649. -> UniqFM [(PackageConfig, Bool)]
  650. mkModuleMap pkg_db = foldr extend_modmap emptyUFM pkgids
  651. where
  652. pkgids = map packageConfigId (eltsUFM pkg_db)
  653. extend_modmap pkgid modmap =
  654. addListToUFM_C (++) modmap
  655. ([(m, [(pkg, True)]) | m <- exposed_mods] ++
  656. [(m, [(pkg, False)]) | m <- hidden_mods])
  657. where
  658. pkg = expectJust "mkModuleMap" (lookupPackage pkg_db pkgid)
  659. exposed_mods = exposedModules pkg
  660. hidden_mods = hiddenModules pkg
  661. pprSPkg :: PackageConfig -> SDoc
  662. pprSPkg p = text (display (sourcePackageId p))
  663. pprIPkg :: PackageConfig -> SDoc
  664. pprIPkg p = text (display (installedPackageId p))
  665. -- -----------------------------------------------------------------------------
  666. -- Extracting information from the packages in scope
  667. -- Many of these functions take a list of packages: in those cases,
  668. -- the list is expected to contain the "dependent packages",
  669. -- i.e. those packages that were found to be depended on by the
  670. -- current module/program. These can be auto or non-auto packages, it
  671. -- doesn't really matter. The list is always combined with the list
  672. -- of preload (command-line) packages to determine which packages to
  673. -- use.
  674. -- | Find all the include directories in these and the preload packages
  675. getPackageIncludePath :: DynFlags -> [PackageId] -> IO [String]
  676. getPackageIncludePath dflags pkgs =
  677. collectIncludeDirs `fmap` getPreloadPackagesAnd dflags pkgs
  678. collectIncludeDirs :: [PackageConfig] -> [FilePath]
  679. collectIncludeDirs ps = nub (filter notNull (concatMap includeDirs ps))
  680. -- | Find all the library paths in these and the preload packages
  681. getPackageLibraryPath :: DynFlags -> [PackageId] -> IO [String]
  682. getPackageLibraryPath dflags pkgs =
  683. collectLibraryPaths `fmap` getPreloadPackagesAnd dflags pkgs
  684. collectLibraryPaths :: [PackageConfig] -> [FilePath]
  685. collectLibraryPaths ps = nub (filter notNull (concatMap libraryDirs ps))
  686. -- | Find all the link options in these and the preload packages
  687. getPackageLinkOpts :: DynFlags -> [PackageId] -> IO [String]
  688. getPackageLinkOpts dflags pkgs =
  689. collectLinkOpts dflags `fmap` getPreloadPackagesAnd dflags pkgs
  690. collectLinkOpts :: DynFlags -> [PackageConfig] -> [String]
  691. collectLinkOpts dflags ps = concat (map all_opts ps)
  692. where
  693. libs p = packageHsLibs dflags p ++ extraLibraries p
  694. all_opts p = map ("-l" ++) (libs p) ++ ldOptions p
  695. packageHsLibs :: DynFlags -> PackageConfig -> [String]
  696. packageHsLibs dflags p = map (mkDynName . addSuffix) (hsLibraries p)
  697. where
  698. ways0 = ways dflags
  699. ways1 = filter ((/= WayDyn) . wayName) ways0
  700. -- the name of a shared library is libHSfoo-ghc<version>.so
  701. -- we leave out the _dyn, because it is superfluous
  702. -- debug RTS includes support for -eventlog
  703. ways2 | WayDebug `elem` map wayName ways1
  704. = filter ((/= WayEventLog) . wayName) ways1
  705. | otherwise
  706. = ways1
  707. tag = mkBuildTag (filter (not . wayRTSOnly) ways2)
  708. rts_tag = mkBuildTag ways2
  709. mkDynName | opt_Static = id
  710. | otherwise = (++ ("-ghc" ++ cProjectVersion))
  711. addSuffix rts@"HSrts" = rts ++ (expandTag rts_tag)
  712. addSuffix other_lib = other_lib ++ (expandTag tag)
  713. expandTag t | null t = ""
  714. | otherwise = '_':t
  715. -- | Find all the C-compiler options in these and the preload packages
  716. getPackageExtraCcOpts :: DynFlags -> [PackageId] -> IO [String]
  717. getPackageExtraCcOpts dflags pkgs = do
  718. ps <- getPreloadPackagesAnd dflags pkgs
  719. return (concatMap ccOptions ps)
  720. -- | Find all the package framework paths in these and the preload packages
  721. getPackageFrameworkPath :: DynFlags -> [PackageId] -> IO [String]
  722. getPackageFrameworkPath dflags pkgs = do
  723. ps <- getPreloadPackagesAnd dflags pkgs
  724. return (nub (filter notNull (concatMap frameworkDirs ps)))
  725. -- | Find all the package frameworks in these and the preload packages
  726. getPackageFrameworks :: DynFlags -> [PackageId] -> IO [String]
  727. getPackageFrameworks dflags pkgs = do
  728. ps <- getPreloadPackagesAnd dflags pkgs
  729. return (concatMap frameworks ps)
  730. -- -----------------------------------------------------------------------------
  731. -- Package Utils
  732. -- | Takes a 'Module', and if the module is in a package returns
  733. -- @(pkgconf, exposed)@ where pkgconf is the PackageConfig for that package,
  734. -- and exposed is @True@ if the package exposes the module.
  735. lookupModuleInAllPackages :: DynFlags -> ModuleName -> [(PackageConfig,Bool)]
  736. lookupModuleInAllPackages dflags m =
  737. case lookupUFM (moduleToPkgConfAll (pkgState dflags)) m of
  738. Nothing -> []
  739. Just ps -> ps
  740. -- | Find all the 'PackageConfig' in both the preload packages from 'DynFlags' and corresponding to the list of
  741. -- 'PackageConfig's
  742. getPreloadPackagesAnd :: DynFlags -> [PackageId] -> IO [PackageConfig]
  743. getPreloadPackagesAnd dflags pkgids =
  744. let
  745. state = pkgState dflags
  746. pkg_map = pkgIdMap state
  747. ipid_map = installedPackageIdMap state
  748. preload = preloadPackages state
  749. pairs = zip pkgids (repeat Nothing)
  750. in do
  751. all_pkgs <- throwErr (foldM (add_package pkg_map ipid_map) preload pairs)
  752. return (map (getPackageDetails state) all_pkgs)
  753. -- Takes a list of packages, and returns the list with dependencies included,
  754. -- in reverse dependency order (a package appears before those it depends on).
  755. closeDeps :: PackageConfigMap
  756. -> Map InstalledPackageId PackageId
  757. -> [(PackageId, Maybe PackageId)]
  758. -> IO [PackageId]
  759. closeDeps pkg_map ipid_map ps = throwErr (closeDepsErr pkg_map ipid_map ps)
  760. throwErr :: MaybeErr Message a -> IO a
  761. throwErr m = case m of
  762. Failed e -> ghcError (CmdLineError (showSDoc e))
  763. Succeeded r -> return r
  764. closeDepsErr :: PackageConfigMap
  765. -> Map InstalledPackageId PackageId
  766. -> [(PackageId,Maybe PackageId)]
  767. -> MaybeErr Message [PackageId]
  768. closeDepsErr pkg_map ipid_map ps = foldM (add_package pkg_map ipid_map) [] ps
  769. -- internal helper
  770. add_package :: PackageConfigMap
  771. -> Map InstalledPackageId PackageId
  772. -> [PackageId]
  773. -> (PackageId,Maybe PackageId)
  774. -> MaybeErr Message [PackageId]
  775. add_package pkg_db ipid_map ps (p, mb_parent)
  776. | p `elem` ps = return ps -- Check if we've already added this package
  777. | otherwise =
  778. case lookupPackage pkg_db p of
  779. Nothing -> Failed (missingPackageMsg (packageIdString p) <>
  780. missingDependencyMsg mb_parent)
  781. Just pkg -> do
  782. -- Add the package's dependents also
  783. ps' <- foldM add_package_ipid ps (depends pkg)
  784. return (p : ps')
  785. where
  786. add_package_ipid ps ipid@(InstalledPackageId str)
  787. | Just pid <- Map.lookup ipid ipid_map
  788. = add_package pkg_db ipid_map ps (pid, Just p)
  789. | otherwise
  790. = Failed (missingPackageMsg str <> missingDependencyMsg mb_parent)
  791. missingPackageErr :: String -> IO a
  792. missingPackageErr p = ghcError (CmdLineError (showSDoc (missingPackageMsg p)))
  793. missingPackageMsg :: String -> SDoc
  794. missingPackageMsg p = ptext (sLit "unknown package:") <+> text p
  795. missingDependencyMsg :: Maybe PackageId -> SDoc
  796. missingDependencyMsg Nothing = empty
  797. missingDependencyMsg (Just parent)
  798. = space <> parens (ptext (sLit "dependency of") <+> ftext (packageIdFS parent))
  799. -- -----------------------------------------------------------------------------
  800. -- | Will the 'Name' come from a dynamically linked library?
  801. isDllName :: PackageId -> Name -> Bool
  802. -- Despite the "dll", I think this function just means that
  803. -- the synbol comes from another dynamically-linked package,
  804. -- and applies on all platforms, not just Windows
  805. isDllName this_pkg name
  806. | opt_Static = False
  807. | Just mod <- nameModule_maybe name = modulePackageId mod /= this_pkg
  808. | otherwise = False -- no, it is not even an external name
  809. -- -----------------------------------------------------------------------------
  810. -- Displaying packages
  811. -- | Show package info on console, if verbosity is >= 3
  812. dumpPackages :: DynFlags -> IO ()
  813. dumpPackages dflags
  814. = do let pkg_map = pkgIdMap (pkgState dflags)
  815. putMsg dflags $
  816. vcat (map (text . showInstalledPackageInfo
  817. . packageConfigToInstalledPackageInfo)
  818. (eltsUFM pkg_map))
  819. \end{code}