PageRenderTime 70ms CodeModel.GetById 4ms RepoModel.GetById 0ms app.codeStats 1ms

/utils/ghc-pkg/Main.hs

http://github.com/ghc/ghc
Haskell | 2253 lines | 1667 code | 260 blank | 326 comment | 111 complexity | dc4c3a46779808920b1e67ae8372ec87 MD5 | raw file
Possible License(s): MIT, BSD-3-Clause, GPL-3.0
  1. {-# LANGUAGE CPP #-}
  2. {-# LANGUAGE FlexibleInstances #-}
  3. {-# LANGUAGE LambdaCase #-}
  4. {-# LANGUAGE MultiParamTypeClasses #-}
  5. {-# LANGUAGE TypeSynonymInstances #-}
  6. {-# LANGUAGE GADTs #-}
  7. {-# LANGUAGE KindSignatures #-}
  8. {-# LANGUAGE DataKinds #-}
  9. {-# LANGUAGE TupleSections #-}
  10. {-# LANGUAGE ScopedTypeVariables #-}
  11. {-# OPTIONS_GHC -fno-warn-orphans #-}
  12. -- We never want to link against terminfo while bootstrapping.
  13. #if defined(BOOTSTRAPPING)
  14. #if defined(WITH_TERMINFO)
  15. #undef WITH_TERMINFO
  16. #endif
  17. #endif
  18. -- Fine if this comes from make/Hadrian or the pre-built base.
  19. #include <ghcplatform.h>
  20. -----------------------------------------------------------------------------
  21. --
  22. -- (c) The University of Glasgow 2004-2009.
  23. --
  24. -- Package management tool
  25. --
  26. -----------------------------------------------------------------------------
  27. module Main (main) where
  28. import qualified GHC.Unit.Database as GhcPkg
  29. import GHC.Unit.Database hiding (mkMungePathUrl)
  30. import GHC.HandleEncoding
  31. import GHC.BaseDir (getBaseDir)
  32. import GHC.Settings.Utils (getTargetArchOS, maybeReadFuzzy)
  33. import GHC.Platform.Host (hostPlatformArchOS)
  34. import GHC.UniqueSubdir (uniqueSubdir)
  35. import qualified GHC.Data.ShortText as ST
  36. import GHC.Version ( cProjectVersion )
  37. import qualified Distribution.Simple.PackageIndex as PackageIndex
  38. import qualified Data.Graph as Graph
  39. import qualified Distribution.ModuleName as ModuleName
  40. import Distribution.ModuleName (ModuleName)
  41. import Distribution.InstalledPackageInfo as Cabal
  42. import qualified Distribution.Parsec as Cabal
  43. import Distribution.Package hiding (installedUnitId)
  44. import Distribution.Text
  45. import Distribution.Version
  46. import Distribution.Backpack
  47. import Distribution.Pretty (Pretty (..))
  48. import Distribution.Types.UnqualComponentName
  49. import Distribution.Types.LibraryName
  50. import Distribution.Types.MungedPackageName
  51. import Distribution.Types.MungedPackageId
  52. import Distribution.Simple.Utils (toUTF8BS, writeUTF8File, readUTF8File)
  53. import qualified Data.Version as Version
  54. import System.FilePath as FilePath
  55. import qualified System.FilePath.Posix as FilePath.Posix
  56. import System.Directory ( getXdgDirectory, createDirectoryIfMissing,
  57. getModificationTime, XdgDirectory ( XdgData ) )
  58. import Text.Printf
  59. import Prelude
  60. import System.Console.GetOpt
  61. import qualified Control.Exception as Exception
  62. import Data.Maybe
  63. import Data.Bifunctor
  64. import Data.Char ( toLower )
  65. import Control.Monad
  66. import System.Directory ( doesDirectoryExist, getDirectoryContents,
  67. doesFileExist, removeFile,
  68. getCurrentDirectory )
  69. import System.Exit ( exitWith, ExitCode(..) )
  70. import System.Environment ( getArgs, getProgName, getEnv )
  71. import System.IO
  72. import System.IO.Error
  73. import GHC.IO ( catchException )
  74. import GHC.IO.Exception (IOErrorType(InappropriateType))
  75. import Data.List ( group, sort, sortBy, nub, partition, find
  76. , intercalate, intersperse, foldl', unfoldr
  77. , isInfixOf, isSuffixOf, isPrefixOf, stripPrefix )
  78. import Control.Concurrent
  79. import qualified Data.Foldable as F
  80. import qualified Data.Traversable as F
  81. import qualified Data.Set as Set
  82. import qualified Data.Map as Map
  83. import qualified Data.ByteString as BS
  84. #if defined(mingw32_HOST_OS)
  85. import GHC.ConsoleHandler
  86. #else
  87. import System.Posix hiding (fdToHandle)
  88. #endif
  89. #if defined(GLOB)
  90. import qualified System.Info(os)
  91. #endif
  92. #if defined(WITH_TERMINFO)
  93. import System.Console.Terminfo as Terminfo
  94. #endif
  95. #if defined(mingw32_HOST_OS)
  96. # if defined(i386_HOST_ARCH)
  97. # define WINDOWS_CCONV stdcall
  98. # elif defined(x86_64_HOST_ARCH)
  99. # define WINDOWS_CCONV ccall
  100. # else
  101. # error Unknown mingw32 arch
  102. # endif
  103. #endif
  104. -- | Short-circuit 'any' with a \"monadic predicate\".
  105. anyM :: (Monad m) => (a -> m Bool) -> [a] -> m Bool
  106. anyM _ [] = return False
  107. anyM p (x:xs) = do
  108. b <- p x
  109. if b
  110. then return True
  111. else anyM p xs
  112. -- -----------------------------------------------------------------------------
  113. -- Entry point
  114. main :: IO ()
  115. main = do
  116. configureHandleEncoding
  117. args <- getArgs
  118. case getOpt Permute (flags ++ deprecFlags) args of
  119. (cli,_,[]) | FlagHelp `elem` cli -> do
  120. prog <- getProgramName
  121. bye (usageInfo (usageHeader prog) flags)
  122. (cli,_,[]) | FlagVersion `elem` cli ->
  123. bye ourCopyright
  124. (cli,nonopts,[]) ->
  125. case getVerbosity Normal cli of
  126. Right v -> runit v cli nonopts
  127. Left err -> die err
  128. (_,_,errors) -> do
  129. prog <- getProgramName
  130. die (concat errors ++ shortUsage prog)
  131. -- -----------------------------------------------------------------------------
  132. -- Command-line syntax
  133. data Flag
  134. = FlagUser
  135. | FlagGlobal
  136. | FlagHelp
  137. | FlagVersion
  138. | FlagConfig FilePath
  139. | FlagGlobalConfig FilePath
  140. | FlagUserConfig FilePath
  141. | FlagForce
  142. | FlagForceFiles
  143. | FlagMultiInstance
  144. | FlagExpandEnvVars
  145. | FlagExpandPkgroot
  146. | FlagNoExpandPkgroot
  147. | FlagSimpleOutput
  148. | FlagNamesOnly
  149. | FlagIgnoreCase
  150. | FlagNoUserDb
  151. | FlagVerbosity (Maybe String)
  152. | FlagUnitId
  153. | FlagShowUnitIds
  154. deriving Eq
  155. flags :: [OptDescr Flag]
  156. flags = [
  157. Option [] ["user"] (NoArg FlagUser)
  158. "use the current user's package database",
  159. Option [] ["global"] (NoArg FlagGlobal)
  160. "use the global package database",
  161. Option ['f'] ["package-db"] (ReqArg FlagConfig "FILE/DIR")
  162. "use the specified package database",
  163. Option [] ["package-conf"] (ReqArg FlagConfig "FILE/DIR")
  164. "use the specified package database (DEPRECATED)",
  165. Option [] ["global-package-db"] (ReqArg FlagGlobalConfig "DIR")
  166. "location of the global package database",
  167. Option [] ["no-user-package-db"] (NoArg FlagNoUserDb)
  168. "never read the user package database",
  169. Option [] ["user-package-db"] (ReqArg FlagUserConfig "DIR")
  170. "location of the user package database (use instead of default)",
  171. Option [] ["no-user-package-conf"] (NoArg FlagNoUserDb)
  172. "never read the user package database (DEPRECATED)",
  173. Option [] ["force"] (NoArg FlagForce)
  174. "ignore missing dependencies, directories, and libraries",
  175. Option [] ["force-files"] (NoArg FlagForceFiles)
  176. "ignore missing directories and libraries only",
  177. Option [] ["enable-multi-instance"] (NoArg FlagMultiInstance)
  178. "allow registering multiple instances of the same package version",
  179. Option [] ["expand-env-vars"] (NoArg FlagExpandEnvVars)
  180. "expand environment variables (${name}-style) in input package descriptions",
  181. Option [] ["expand-pkgroot"] (NoArg FlagExpandPkgroot)
  182. "expand ${pkgroot}-relative paths to absolute in output package descriptions",
  183. Option [] ["no-expand-pkgroot"] (NoArg FlagNoExpandPkgroot)
  184. "preserve ${pkgroot}-relative paths in output package descriptions",
  185. Option ['?'] ["help"] (NoArg FlagHelp)
  186. "display this help and exit",
  187. Option ['V'] ["version"] (NoArg FlagVersion)
  188. "output version information and exit",
  189. Option [] ["simple-output"] (NoArg FlagSimpleOutput)
  190. "print output in easy-to-parse format for some commands",
  191. Option [] ["show-unit-ids"] (NoArg FlagShowUnitIds)
  192. "print unit-ids instead of package identifiers",
  193. Option [] ["names-only"] (NoArg FlagNamesOnly)
  194. "only print package names, not versions; can only be used with list --simple-output",
  195. Option [] ["ignore-case"] (NoArg FlagIgnoreCase)
  196. "ignore case for substring matching",
  197. Option [] ["ipid", "unit-id"] (NoArg FlagUnitId)
  198. "interpret package arguments as unit IDs (e.g. installed package IDs)",
  199. Option ['v'] ["verbose"] (OptArg FlagVerbosity "Verbosity")
  200. "verbosity level (0-2, default 1)"
  201. ]
  202. data Verbosity = Silent | Normal | Verbose
  203. deriving (Show, Eq, Ord)
  204. getVerbosity :: Verbosity -> [Flag] -> Either String Verbosity
  205. getVerbosity v [] = Right v
  206. getVerbosity _ (FlagVerbosity Nothing : fs) = getVerbosity Verbose fs
  207. getVerbosity _ (FlagVerbosity (Just "0") : fs) = getVerbosity Silent fs
  208. getVerbosity _ (FlagVerbosity (Just "1") : fs) = getVerbosity Normal fs
  209. getVerbosity _ (FlagVerbosity (Just "2") : fs) = getVerbosity Verbose fs
  210. getVerbosity _ (FlagVerbosity v : _) = Left ("Bad verbosity: " ++ show v)
  211. getVerbosity v (_ : fs) = getVerbosity v fs
  212. deprecFlags :: [OptDescr Flag]
  213. deprecFlags = [
  214. -- put deprecated flags here
  215. ]
  216. ourCopyright :: String
  217. ourCopyright = "GHC package manager version " ++ GHC.Version.cProjectVersion ++ "\n"
  218. shortUsage :: String -> String
  219. shortUsage prog = "For usage information see '" ++ prog ++ " --help'."
  220. usageHeader :: String -> String
  221. usageHeader prog = substProg prog $
  222. "Usage:\n" ++
  223. " $p init {path}\n" ++
  224. " Create and initialise a package database at the location {path}.\n" ++
  225. " Packages can be registered in the new database using the register\n" ++
  226. " command with --package-db={path}. To use the new database with GHC,\n" ++
  227. " use GHC's -package-db flag.\n" ++
  228. "\n" ++
  229. " $p register {filename | -}\n" ++
  230. " Register the package using the specified installed package\n" ++
  231. " description. The syntax for the latter is given in the $p\n" ++
  232. " documentation. The input file should be encoded in UTF-8.\n" ++
  233. "\n" ++
  234. " $p update {filename | -}\n" ++
  235. " Register the package, overwriting any other package with the\n" ++
  236. " same name. The input file should be encoded in UTF-8.\n" ++
  237. "\n" ++
  238. " $p unregister [pkg-id] \n" ++
  239. " Unregister the specified packages in the order given.\n" ++
  240. "\n" ++
  241. " $p expose {pkg-id}\n" ++
  242. " Expose the specified package.\n" ++
  243. "\n" ++
  244. " $p hide {pkg-id}\n" ++
  245. " Hide the specified package.\n" ++
  246. "\n" ++
  247. " $p trust {pkg-id}\n" ++
  248. " Trust the specified package.\n" ++
  249. "\n" ++
  250. " $p distrust {pkg-id}\n" ++
  251. " Distrust the specified package.\n" ++
  252. "\n" ++
  253. " $p list [pkg]\n" ++
  254. " List registered packages in the global database, and also the\n" ++
  255. " user database if --user is given. If a package name is given\n" ++
  256. " all the registered versions will be listed in ascending order.\n" ++
  257. " Accepts the --simple-output flag.\n" ++
  258. "\n" ++
  259. " $p dot\n" ++
  260. " Generate a graph of the package dependencies in a form suitable\n" ++
  261. " for input for the graphviz tools. For example, to generate a PDF\n" ++
  262. " of the dependency graph: ghc-pkg dot | tred | dot -Tpdf >pkgs.pdf\n" ++
  263. "\n" ++
  264. " $p find-module {module}\n" ++
  265. " List registered packages exposing module {module} in the global\n" ++
  266. " database, and also the user database if --user is given.\n" ++
  267. " All the registered versions will be listed in ascending order.\n" ++
  268. " Accepts the --simple-output flag.\n" ++
  269. "\n" ++
  270. " $p latest {pkg-id}\n" ++
  271. " Prints the highest registered version of a package.\n" ++
  272. "\n" ++
  273. " $p check\n" ++
  274. " Check the consistency of package dependencies and list broken packages.\n" ++
  275. " Accepts the --simple-output flag.\n" ++
  276. "\n" ++
  277. " $p describe {pkg}\n" ++
  278. " Give the registered description for the specified package. The\n" ++
  279. " description is returned in precisely the syntax required by $p\n" ++
  280. " register.\n" ++
  281. "\n" ++
  282. " $p field {pkg} {field}\n" ++
  283. " Extract the specified field of the package description for the\n" ++
  284. " specified package. Accepts comma-separated multiple fields.\n" ++
  285. "\n" ++
  286. " $p dump\n" ++
  287. " Dump the registered description for every package. This is like\n" ++
  288. " \"ghc-pkg describe '*'\", except that it is intended to be used\n" ++
  289. " by tools that parse the results, rather than humans. The output is\n" ++
  290. " always encoded in UTF-8, regardless of the current locale.\n" ++
  291. "\n" ++
  292. " $p recache\n" ++
  293. " Regenerate the package database cache. This command should only be\n" ++
  294. " necessary if you added a package to the database by dropping a file\n" ++
  295. " into the database directory manually. By default, the global DB\n" ++
  296. " is recached; to recache a different DB use --user or --package-db\n" ++
  297. " as appropriate.\n" ++
  298. "\n" ++
  299. " Substring matching is supported for {module} in find-module and\n" ++
  300. " for {pkg} in list, describe, and field, where a '*' indicates\n" ++
  301. " open substring ends (prefix*, *suffix, *infix*). Use --ipid to\n" ++
  302. " match against the installed package ID instead.\n" ++
  303. "\n" ++
  304. " When asked to modify a database (register, unregister, update,\n"++
  305. " hide, expose, and also check), ghc-pkg modifies the global database by\n"++
  306. " default. Specifying --user causes it to act on the user database,\n"++
  307. " or --package-db can be used to act on another database\n"++
  308. " entirely. When multiple of these options are given, the rightmost\n"++
  309. " one is used as the database to act upon.\n"++
  310. "\n"++
  311. " Commands that query the package database (list, tree, latest, describe,\n"++
  312. " field) operate on the list of databases specified by the flags\n"++
  313. " --user, --global, and --package-db. If none of these flags are\n"++
  314. " given, the default is --global --user.\n"++
  315. "\n" ++
  316. " The following optional flags are also accepted:\n"
  317. substProg :: String -> String -> String
  318. substProg _ [] = []
  319. substProg prog ('$':'p':xs) = prog ++ substProg prog xs
  320. substProg prog (c:xs) = c : substProg prog xs
  321. -- -----------------------------------------------------------------------------
  322. -- Do the business
  323. data Force = NoForce | ForceFiles | ForceAll | CannotForce
  324. deriving (Eq,Ord)
  325. -- | Enum flag representing argument type
  326. data AsPackageArg
  327. = AsUnitId
  328. | AsDefault
  329. -- | Represents how a package may be specified by a user on the command line.
  330. data PackageArg
  331. -- | A package identifier foo-0.1, or a glob foo-*
  332. = Id GlobPackageIdentifier
  333. -- | An installed package ID foo-0.1-HASH. This is guaranteed to uniquely
  334. -- match a single entry in the package database.
  335. | IUId UnitId
  336. -- | A glob against the package name. The first string is the literal
  337. -- glob, the second is a function which returns @True@ if the argument
  338. -- matches.
  339. | Substring String (String->Bool)
  340. runit :: Verbosity -> [Flag] -> [String] -> IO ()
  341. runit verbosity cli nonopts = do
  342. installSignalHandlers -- catch ^C and clean up
  343. when (verbosity >= Verbose)
  344. (putStr ourCopyright)
  345. prog <- getProgramName
  346. let
  347. force
  348. | FlagForce `elem` cli = ForceAll
  349. | FlagForceFiles `elem` cli = ForceFiles
  350. | otherwise = NoForce
  351. as_arg | FlagUnitId `elem` cli = AsUnitId
  352. | otherwise = AsDefault
  353. multi_instance = FlagMultiInstance `elem` cli
  354. expand_env_vars= FlagExpandEnvVars `elem` cli
  355. mexpand_pkgroot= foldl' accumExpandPkgroot Nothing cli
  356. where accumExpandPkgroot _ FlagExpandPkgroot = Just True
  357. accumExpandPkgroot _ FlagNoExpandPkgroot = Just False
  358. accumExpandPkgroot x _ = x
  359. splitFields fields = unfoldr splitComma (',':fields)
  360. where splitComma "" = Nothing
  361. splitComma fs = Just $ break (==',') (tail fs)
  362. -- | Parses a glob into a predicate which tests if a string matches
  363. -- the glob. Returns Nothing if the string in question is not a glob.
  364. -- At the moment, we only support globs at the beginning and/or end of
  365. -- strings. This function respects case sensitivity.
  366. --
  367. -- >>> fromJust (substringCheck "*") "anything"
  368. -- True
  369. --
  370. -- >>> fromJust (substringCheck "string") "string"
  371. -- True
  372. --
  373. -- >>> fromJust (substringCheck "*bar") "foobar"
  374. -- True
  375. --
  376. -- >>> fromJust (substringCheck "foo*") "foobar"
  377. -- True
  378. --
  379. -- >>> fromJust (substringCheck "*ooba*") "foobar"
  380. -- True
  381. --
  382. -- >>> fromJust (substringCheck "f*bar") "foobar"
  383. -- False
  384. substringCheck :: String -> Maybe (String -> Bool)
  385. substringCheck "" = Nothing
  386. substringCheck "*" = Just (const True)
  387. substringCheck [_] = Nothing
  388. substringCheck (h:t) =
  389. case (h, init t, last t) of
  390. ('*',s,'*') -> Just (isInfixOf (f s) . f)
  391. ('*',_, _ ) -> Just (isSuffixOf (f t) . f)
  392. ( _ ,s,'*') -> Just (isPrefixOf (f (h:s)) . f)
  393. _ -> Nothing
  394. where f | FlagIgnoreCase `elem` cli = map toLower
  395. | otherwise = id
  396. #if defined(GLOB)
  397. glob x | System.Info.os=="mingw32" = do
  398. -- glob echoes its argument, after win32 filename globbing
  399. (_,o,_,_) <- runInteractiveCommand ("glob "++x)
  400. txt <- hGetContents o
  401. return (read txt)
  402. glob x | otherwise = return [x]
  403. #endif
  404. --
  405. -- first, parse the command
  406. case nonopts of
  407. #if defined(GLOB)
  408. -- dummy command to demonstrate usage and permit testing
  409. -- without messing things up; use glob to selectively enable
  410. -- windows filename globbing for file parameters
  411. -- register, update, FlagGlobalConfig, FlagConfig; others?
  412. ["glob", filename] -> do
  413. print filename
  414. glob filename >>= print
  415. #endif
  416. ["init", filename] ->
  417. initPackageDB filename verbosity cli
  418. ["register", filename] ->
  419. registerPackage filename verbosity cli
  420. multi_instance
  421. expand_env_vars False force
  422. ["update", filename] ->
  423. registerPackage filename verbosity cli
  424. multi_instance
  425. expand_env_vars True force
  426. "unregister" : pkgarg_strs@(_:_) -> do
  427. forM_ pkgarg_strs $ \pkgarg_str -> do
  428. pkgarg <- readPackageArg as_arg pkgarg_str
  429. unregisterPackage pkgarg verbosity cli force
  430. ["expose", pkgarg_str] -> do
  431. pkgarg <- readPackageArg as_arg pkgarg_str
  432. exposePackage pkgarg verbosity cli force
  433. ["hide", pkgarg_str] -> do
  434. pkgarg <- readPackageArg as_arg pkgarg_str
  435. hidePackage pkgarg verbosity cli force
  436. ["trust", pkgarg_str] -> do
  437. pkgarg <- readPackageArg as_arg pkgarg_str
  438. trustPackage pkgarg verbosity cli force
  439. ["distrust", pkgarg_str] -> do
  440. pkgarg <- readPackageArg as_arg pkgarg_str
  441. distrustPackage pkgarg verbosity cli force
  442. ["list"] -> do
  443. listPackages verbosity cli Nothing Nothing
  444. ["list", pkgarg_str] ->
  445. case substringCheck pkgarg_str of
  446. Nothing -> do pkgarg <- readPackageArg as_arg pkgarg_str
  447. listPackages verbosity cli (Just pkgarg) Nothing
  448. Just m -> listPackages verbosity cli
  449. (Just (Substring pkgarg_str m)) Nothing
  450. ["dot"] -> do
  451. showPackageDot verbosity cli
  452. ["find-module", mod_name] -> do
  453. let match = maybe (==mod_name) id (substringCheck mod_name)
  454. listPackages verbosity cli Nothing (Just match)
  455. ["latest", pkgid_str] -> do
  456. pkgid <- readGlobPkgId pkgid_str
  457. latestPackage verbosity cli pkgid
  458. ["describe", pkgid_str] -> do
  459. pkgarg <- case substringCheck pkgid_str of
  460. Nothing -> readPackageArg as_arg pkgid_str
  461. Just m -> return (Substring pkgid_str m)
  462. describePackage verbosity cli pkgarg (fromMaybe False mexpand_pkgroot)
  463. ["field", pkgid_str, fields] -> do
  464. pkgarg <- case substringCheck pkgid_str of
  465. Nothing -> readPackageArg as_arg pkgid_str
  466. Just m -> return (Substring pkgid_str m)
  467. describeField verbosity cli pkgarg
  468. (splitFields fields) (fromMaybe True mexpand_pkgroot)
  469. ["check"] -> do
  470. checkConsistency verbosity cli
  471. ["dump"] -> do
  472. dumpUnits verbosity cli (fromMaybe False mexpand_pkgroot)
  473. ["recache"] -> do
  474. recache verbosity cli
  475. [] -> do
  476. die ("missing command\n" ++ shortUsage prog)
  477. (_cmd:_) -> do
  478. die ("command-line syntax error\n" ++ shortUsage prog)
  479. parseCheck :: Cabal.Parsec a => String -> String -> IO a
  480. parseCheck str what =
  481. case Cabal.eitherParsec str of
  482. Left e -> die ("cannot parse \'" ++ str ++ "\' as a " ++ what ++ ": " ++ e)
  483. Right x -> pure x
  484. -- | Either an exact 'PackageIdentifier', or a glob for all packages
  485. -- matching 'PackageName'.
  486. data GlobPackageIdentifier
  487. = ExactPackageIdentifier MungedPackageId
  488. | GlobPackageIdentifier MungedPackageName
  489. displayGlobPkgId :: GlobPackageIdentifier -> String
  490. displayGlobPkgId (ExactPackageIdentifier pid) = display pid
  491. displayGlobPkgId (GlobPackageIdentifier pn) = display pn ++ "-*"
  492. readGlobPkgId :: String -> IO GlobPackageIdentifier
  493. readGlobPkgId str
  494. | "-*" `isSuffixOf` str =
  495. GlobPackageIdentifier <$> parseCheck (init (init str)) "package identifier (glob)"
  496. | otherwise = ExactPackageIdentifier <$> parseCheck str "package identifier (exact)"
  497. readPackageArg :: AsPackageArg -> String -> IO PackageArg
  498. readPackageArg AsUnitId str = IUId <$> parseCheck str "installed package id"
  499. readPackageArg AsDefault str = Id <$> readGlobPkgId str
  500. -- -----------------------------------------------------------------------------
  501. -- Package databases
  502. -- Some commands operate on a single database:
  503. -- register, unregister, expose, hide, trust, distrust
  504. -- however these commands also check the union of the available databases
  505. -- in order to check consistency. For example, register will check that
  506. -- dependencies exist before registering a package.
  507. --
  508. -- Some commands operate on multiple databases, with overlapping semantics:
  509. -- list, describe, field
  510. data PackageDB (mode :: GhcPkg.DbMode)
  511. = PackageDB {
  512. location, locationAbsolute :: !FilePath,
  513. -- We need both possibly-relative and definitely-absolute package
  514. -- db locations. This is because the relative location is used as
  515. -- an identifier for the db, so it is important we do not modify it.
  516. -- On the other hand we need the absolute path in a few places
  517. -- particularly in relation to the ${pkgroot} stuff.
  518. packageDbLock :: !(GhcPkg.DbOpenMode mode GhcPkg.PackageDbLock),
  519. -- If package db is open in read write mode, we keep its lock around for
  520. -- transactional updates.
  521. packages :: [InstalledPackageInfo]
  522. }
  523. type PackageDBStack = [PackageDB 'GhcPkg.DbReadOnly]
  524. -- A stack of package databases. Convention: head is the topmost
  525. -- in the stack.
  526. -- | Selector for picking the right package DB to modify as 'register' and
  527. -- 'recache' operate on the database on top of the stack, whereas 'modify'
  528. -- changes the first database that contains a specific package.
  529. data DbModifySelector = TopOne | ContainsPkg PackageArg
  530. allPackagesInStack :: PackageDBStack -> [InstalledPackageInfo]
  531. allPackagesInStack = concatMap packages
  532. -- | Retain only the part of the stack up to and including the given package
  533. -- DB (where the global package DB is the bottom of the stack). The resulting
  534. -- package DB stack contains exactly the packages that packages from the
  535. -- specified package DB can depend on, since dependencies can only extend
  536. -- down the stack, not up (e.g. global packages cannot depend on user
  537. -- packages).
  538. stackUpTo :: FilePath -> PackageDBStack -> PackageDBStack
  539. stackUpTo to_modify = dropWhile ((/= to_modify) . location)
  540. getPkgDatabases :: Verbosity
  541. -> GhcPkg.DbOpenMode mode DbModifySelector
  542. -> Bool -- use the user db
  543. -> Bool -- read caches, if available
  544. -> Bool -- expand vars, like ${pkgroot} and $topdir
  545. -> [Flag]
  546. -> IO (PackageDBStack,
  547. -- the real package DB stack: [global,user] ++
  548. -- DBs specified on the command line with -f.
  549. GhcPkg.DbOpenMode mode (PackageDB mode),
  550. -- which one to modify, if any
  551. PackageDBStack)
  552. -- the package DBs specified on the command
  553. -- line, or [global,user] otherwise. This
  554. -- is used as the list of package DBs for
  555. -- commands that just read the DB, such as 'list'.
  556. getPkgDatabases verbosity mode use_user use_cache expand_vars my_flags = do
  557. -- Second we determine the location of the global package config. On Windows,
  558. -- this is found relative to the ghc-pkg.exe binary, whereas on Unix the
  559. -- location is passed to the binary using the --global-package-db flag by the
  560. -- wrapper script.
  561. let err_msg = "missing --global-package-db option, location of global package database unknown\n"
  562. global_conf <-
  563. case [ f | FlagGlobalConfig f <- my_flags ] of
  564. -- See Note [Base Dir] for more information on the base dir / top dir.
  565. [] -> do mb_dir <- getBaseDir
  566. case mb_dir of
  567. Nothing -> die err_msg
  568. Just dir -> do
  569. r <- lookForPackageDBIn dir
  570. case r of
  571. Nothing -> die ("Can't find package database in " ++ dir)
  572. Just path -> return path
  573. fs -> return (last fs)
  574. -- The value of the $topdir variable used in some package descriptions
  575. -- Note that the way we calculate this is slightly different to how it
  576. -- is done in ghc itself. We rely on the convention that the global
  577. -- package db lives in ghc's libdir.
  578. top_dir <- absolutePath (takeDirectory global_conf)
  579. let no_user_db = FlagNoUserDb `elem` my_flags
  580. -- get the location of the user package database, and create it if necessary
  581. -- getXdgDirectory can fail (e.g. if $HOME isn't set)
  582. e_appdir <- tryIO $ getXdgDirectory XdgData "ghc"
  583. mb_user_conf <-
  584. case [ f | FlagUserConfig f <- my_flags ] of
  585. _ | no_user_db -> return Nothing
  586. [] -> case e_appdir of
  587. Left _ -> return Nothing
  588. Right appdir -> do
  589. -- See Note [Settings File] about this file, and why we need GHC to share it with us.
  590. let settingsFile = top_dir </> "settings"
  591. exists_settings_file <- doesFileExist settingsFile
  592. targetArchOS <- case exists_settings_file of
  593. False -> do
  594. warn $ "WARNING: settings file doesn't exist " ++ show settingsFile
  595. warn "cannot know target platform so guessing target == host (native compiler)."
  596. pure hostPlatformArchOS
  597. True -> do
  598. settingsStr <- readFile settingsFile
  599. mySettings <- case maybeReadFuzzy settingsStr of
  600. Just s -> pure $ Map.fromList s
  601. -- It's excusable to not have a settings file (for now at
  602. -- least) but completely inexcusable to have a malformed one.
  603. Nothing -> die $ "Can't parse settings file " ++ show settingsFile
  604. case getTargetArchOS settingsFile mySettings of
  605. Right archOS -> pure archOS
  606. Left e -> die e
  607. let subdir = uniqueSubdir targetArchOS
  608. dir = appdir </> subdir
  609. r <- lookForPackageDBIn dir
  610. case r of
  611. Nothing -> return (Just (dir </> "package.conf.d", False))
  612. Just f -> return (Just (f, True))
  613. fs -> return (Just (last fs, True))
  614. -- If the user database exists, and for "use_user" commands (which includes
  615. -- "ghc-pkg check" and all commands that modify the db) we will attempt to
  616. -- use the user db.
  617. let sys_databases
  618. | Just (user_conf,user_exists) <- mb_user_conf,
  619. use_user || user_exists = [user_conf, global_conf]
  620. | otherwise = [global_conf]
  621. e_pkg_path <- tryIO (System.Environment.getEnv "GHC_PACKAGE_PATH")
  622. let env_stack =
  623. case e_pkg_path of
  624. Left _ -> sys_databases
  625. Right path
  626. | not (null path) && isSearchPathSeparator (last path)
  627. -> splitSearchPath (init path) ++ sys_databases
  628. | otherwise
  629. -> splitSearchPath path
  630. -- The "global" database is always the one at the bottom of the stack.
  631. -- This is the database we modify by default.
  632. virt_global_conf = last env_stack
  633. let db_flags = [ f | Just f <- map is_db_flag my_flags ]
  634. where is_db_flag FlagUser
  635. | Just (user_conf, _user_exists) <- mb_user_conf
  636. = Just user_conf
  637. is_db_flag FlagGlobal = Just virt_global_conf
  638. is_db_flag (FlagConfig f) = Just f
  639. is_db_flag _ = Nothing
  640. let flag_db_names | null db_flags = env_stack
  641. | otherwise = reverse (nub db_flags)
  642. -- For a "modify" command, treat all the databases as
  643. -- a stack, where we are modifying the top one, but it
  644. -- can refer to packages in databases further down the
  645. -- stack.
  646. -- -f flags on the command line add to the database
  647. -- stack, unless any of them are present in the stack
  648. -- already.
  649. let final_stack = filter (`notElem` env_stack)
  650. [ f | FlagConfig f <- reverse my_flags ]
  651. ++ env_stack
  652. top_db = if null db_flags
  653. then virt_global_conf
  654. else last db_flags
  655. (db_stack, db_to_operate_on) <- getDatabases top_dir mb_user_conf
  656. flag_db_names final_stack top_db
  657. let flag_db_stack = [ db | db_name <- flag_db_names,
  658. db <- db_stack, location db == db_name ]
  659. when (verbosity > Normal) $ do
  660. infoLn ("db stack: " ++ show (map location db_stack))
  661. F.forM_ db_to_operate_on $ \db ->
  662. infoLn ("modifying: " ++ (location db))
  663. infoLn ("flag db stack: " ++ show (map location flag_db_stack))
  664. return (db_stack, db_to_operate_on, flag_db_stack)
  665. where
  666. getDatabases top_dir mb_user_conf flag_db_names
  667. final_stack top_db = case mode of
  668. -- When we open in read only mode, we simply read all of the databases/
  669. GhcPkg.DbOpenReadOnly -> do
  670. db_stack <- mapM readDatabase final_stack
  671. return (db_stack, GhcPkg.DbOpenReadOnly)
  672. -- The only package db we open in read write mode is the one on the top of
  673. -- the stack.
  674. GhcPkg.DbOpenReadWrite TopOne -> do
  675. (db_stack, mto_modify) <- stateSequence Nothing
  676. [ \case
  677. to_modify@(Just _) -> (, to_modify) <$> readDatabase db_path
  678. Nothing -> if db_path /= top_db
  679. then (, Nothing) <$> readDatabase db_path
  680. else do
  681. db <- readParseDatabase verbosity mb_user_conf
  682. mode use_cache db_path
  683. `catchException` couldntOpenDbForModification db_path
  684. let ro_db = db { packageDbLock = GhcPkg.DbOpenReadOnly }
  685. return (ro_db, Just db)
  686. | db_path <- final_stack ]
  687. to_modify <- case mto_modify of
  688. Just db -> return db
  689. Nothing -> die "no database selected for modification"
  690. return (db_stack, GhcPkg.DbOpenReadWrite to_modify)
  691. -- The package db we open in read write mode is the first one included in
  692. -- flag_db_names that contains specified package. Therefore we need to
  693. -- open each one in read/write mode first and decide whether it's for
  694. -- modification based on its contents.
  695. GhcPkg.DbOpenReadWrite (ContainsPkg pkgarg) -> do
  696. (db_stack, mto_modify) <- stateSequence Nothing
  697. [ \case
  698. to_modify@(Just _) -> (, to_modify) <$> readDatabase db_path
  699. Nothing -> if db_path `notElem` flag_db_names
  700. then (, Nothing) <$> readDatabase db_path
  701. else do
  702. let hasPkg :: PackageDB mode -> Bool
  703. hasPkg = not . null . findPackage pkgarg . packages
  704. openRo (e::IOError) = do
  705. db <- readDatabase db_path
  706. if hasPkg db
  707. then couldntOpenDbForModification db_path e
  708. else return (db, Nothing)
  709. -- If we fail to open the database in read/write mode, we need
  710. -- to check if it's for modification first before throwing an
  711. -- error, so we attempt to open it in read only mode.
  712. Exception.handle openRo $ do
  713. db <- readParseDatabase verbosity mb_user_conf
  714. mode use_cache db_path
  715. let ro_db = db { packageDbLock = GhcPkg.DbOpenReadOnly }
  716. if hasPkg db
  717. then return (ro_db, Just db)
  718. else do
  719. -- If the database is not for modification after all,
  720. -- drop the write lock as we are already finished with
  721. -- the database.
  722. case packageDbLock db of
  723. GhcPkg.DbOpenReadWrite lock ->
  724. GhcPkg.unlockPackageDb lock
  725. return (ro_db, Nothing)
  726. | db_path <- final_stack ]
  727. to_modify <- case mto_modify of
  728. Just db -> return db
  729. Nothing -> cannotFindPackage pkgarg Nothing
  730. return (db_stack, GhcPkg.DbOpenReadWrite to_modify)
  731. where
  732. couldntOpenDbForModification :: FilePath -> IOError -> IO a
  733. couldntOpenDbForModification db_path e = die $ "Couldn't open database "
  734. ++ db_path ++ " for modification: " ++ show e
  735. -- Parse package db in read-only mode.
  736. readDatabase :: FilePath -> IO (PackageDB 'GhcPkg.DbReadOnly)
  737. readDatabase db_path = do
  738. db <- readParseDatabase verbosity mb_user_conf
  739. GhcPkg.DbOpenReadOnly use_cache db_path
  740. if expand_vars
  741. then return $ mungePackageDBPaths top_dir db
  742. else return db
  743. stateSequence :: Monad m => s -> [s -> m (a, s)] -> m ([a], s)
  744. stateSequence s [] = return ([], s)
  745. stateSequence s (m:ms) = do
  746. (a, s') <- m s
  747. (as, s'') <- stateSequence s' ms
  748. return (a : as, s'')
  749. lookForPackageDBIn :: FilePath -> IO (Maybe FilePath)
  750. lookForPackageDBIn dir = do
  751. let path_dir = dir </> "package.conf.d"
  752. exists_dir <- doesDirectoryExist path_dir
  753. if exists_dir then return (Just path_dir) else do
  754. let path_file = dir </> "package.conf"
  755. exists_file <- doesFileExist path_file
  756. if exists_file then return (Just path_file) else return Nothing
  757. readParseDatabase :: forall mode t. Verbosity
  758. -> Maybe (FilePath,Bool)
  759. -> GhcPkg.DbOpenMode mode t
  760. -> Bool -- use cache
  761. -> FilePath
  762. -> IO (PackageDB mode)
  763. readParseDatabase verbosity mb_user_conf mode use_cache path
  764. -- the user database (only) is allowed to be non-existent
  765. | Just (user_conf,False) <- mb_user_conf, path == user_conf
  766. = do lock <- F.forM mode $ \_ -> do
  767. createDirectoryIfMissing True path
  768. GhcPkg.lockPackageDb cache
  769. mkPackageDB [] lock
  770. | otherwise
  771. = do e <- tryIO $ getDirectoryContents path
  772. case e of
  773. Left err
  774. | ioeGetErrorType err == InappropriateType -> do
  775. -- We provide a limited degree of backwards compatibility for
  776. -- old single-file style db:
  777. mdb <- tryReadParseOldFileStyleDatabase verbosity
  778. mb_user_conf mode use_cache path
  779. case mdb of
  780. Just db -> return db
  781. Nothing ->
  782. die $ "ghc no longer supports single-file style package "
  783. ++ "databases (" ++ path ++ ") use 'ghc-pkg init'"
  784. ++ "to create the database with the correct format."
  785. | otherwise -> ioError err
  786. Right fs
  787. | not use_cache -> ignore_cache (const $ return ())
  788. | otherwise -> do
  789. e_tcache <- tryIO $ getModificationTime cache
  790. case e_tcache of
  791. Left ex -> do
  792. whenReportCacheErrors $
  793. if isDoesNotExistError ex
  794. then
  795. -- It's fine if the cache is not there as long as the
  796. -- database is empty.
  797. when (not $ null confs) $ do
  798. warn ("WARNING: cache does not exist: " ++ cache)
  799. warn ("ghc will fail to read this package db. " ++
  800. recacheAdvice)
  801. else do
  802. warn ("WARNING: cache cannot be read: " ++ show ex)
  803. warn "ghc will fail to read this package db."
  804. ignore_cache (const $ return ())
  805. Right tcache -> do
  806. when (verbosity >= Verbose) $ do
  807. warn ("Timestamp " ++ show tcache ++ " for " ++ cache)
  808. -- If any of the .conf files is newer than package.cache, we
  809. -- assume that cache is out of date.
  810. cache_outdated <- (`anyM` confs) $ \conf ->
  811. (tcache <) <$> getModificationTime conf
  812. if not cache_outdated
  813. then do
  814. when (verbosity > Normal) $
  815. infoLn ("using cache: " ++ cache)
  816. GhcPkg.readPackageDbForGhcPkg cache mode
  817. >>= uncurry mkPackageDB
  818. else do
  819. whenReportCacheErrors $ do
  820. warn ("WARNING: cache is out of date: " ++ cache)
  821. warn ("ghc will see an old view of this " ++
  822. "package db. " ++ recacheAdvice)
  823. ignore_cache $ \file -> do
  824. when (verbosity >= Verbose) $ do
  825. tFile <- getModificationTime file
  826. let rel = case tcache `compare` tFile of
  827. LT -> " (NEWER than cache)"
  828. GT -> " (older than cache)"
  829. EQ -> " (same as cache)"
  830. warn ("Timestamp " ++ show tFile
  831. ++ " for " ++ file ++ rel)
  832. where
  833. confs = map (path </>) $ filter (".conf" `isSuffixOf`) fs
  834. ignore_cache :: (FilePath -> IO ()) -> IO (PackageDB mode)
  835. ignore_cache checkTime = do
  836. -- If we're opening for modification, we need to acquire a
  837. -- lock even if we don't open the cache now, because we are
  838. -- going to modify it later.
  839. lock <- F.mapM (const $ GhcPkg.lockPackageDb cache) mode
  840. let doFile f = do checkTime f
  841. parseSingletonPackageConf verbosity f
  842. pkgs <- mapM doFile confs
  843. mkPackageDB pkgs lock
  844. -- We normally report cache errors for read-only commands,
  845. -- since modify commands will usually fix the cache.
  846. whenReportCacheErrors = when $ verbosity > Normal
  847. || verbosity >= Normal && GhcPkg.isDbOpenReadMode mode
  848. where
  849. cache = path </> cachefilename
  850. recacheAdvice
  851. | Just (user_conf, True) <- mb_user_conf, path == user_conf
  852. = "Use 'ghc-pkg recache --user' to fix."
  853. | otherwise
  854. = "Use 'ghc-pkg recache' to fix."
  855. mkPackageDB :: [InstalledPackageInfo]
  856. -> GhcPkg.DbOpenMode mode GhcPkg.PackageDbLock
  857. -> IO (PackageDB mode)
  858. mkPackageDB pkgs lock = do
  859. path_abs <- absolutePath path
  860. return $ PackageDB {
  861. location = path,
  862. locationAbsolute = path_abs,
  863. packageDbLock = lock,
  864. packages = pkgs
  865. }
  866. parseSingletonPackageConf :: Verbosity -> FilePath -> IO InstalledPackageInfo
  867. parseSingletonPackageConf verbosity file = do
  868. when (verbosity > Normal) $ infoLn ("reading package config: " ++ file)
  869. BS.readFile file >>= fmap fst . parsePackageInfo
  870. cachefilename :: FilePath
  871. cachefilename = "package.cache"
  872. mungePackageDBPaths :: FilePath -> PackageDB mode -> PackageDB mode
  873. mungePackageDBPaths top_dir db@PackageDB { packages = pkgs } =
  874. db { packages = map (mungePackagePaths top_dir pkgroot) pkgs }
  875. where
  876. pkgroot = takeDirectory $ dropTrailingPathSeparator (locationAbsolute db)
  877. -- It so happens that for both styles of package db ("package.conf"
  878. -- files and "package.conf.d" dirs) the pkgroot is the parent directory
  879. -- ${pkgroot}/package.conf or ${pkgroot}/package.conf.d/
  880. -- | Perform path/URL variable substitution as per the Cabal ${pkgroot} spec
  881. -- (http://www.haskell.org/pipermail/libraries/2009-May/011772.html)
  882. -- Paths/URLs can be relative to ${pkgroot} or ${pkgrooturl}.
  883. -- The "pkgroot" is the directory containing the package database.
  884. --
  885. -- Also perform a similar substitution for the older GHC-specific
  886. -- "$topdir" variable. The "topdir" is the location of the ghc
  887. -- installation (obtained from the -B option).
  888. mungePackagePaths :: FilePath -> FilePath
  889. -> InstalledPackageInfo -> InstalledPackageInfo
  890. mungePackagePaths top_dir pkgroot pkg =
  891. -- TODO: similar code is duplicated in GHC.Unit.Database
  892. pkg {
  893. importDirs = munge_paths (importDirs pkg),
  894. includeDirs = munge_paths (includeDirs pkg),
  895. libraryDirs = munge_paths (libraryDirs pkg),
  896. libraryDynDirs = munge_paths (libraryDynDirs pkg),
  897. frameworkDirs = munge_paths (frameworkDirs pkg),
  898. haddockInterfaces = munge_paths (haddockInterfaces pkg),
  899. -- haddock-html is allowed to be either a URL or a file
  900. haddockHTMLs = munge_paths (munge_urls (haddockHTMLs pkg))
  901. }
  902. where
  903. munge_paths = map munge_path
  904. munge_urls = map munge_url
  905. (munge_path,munge_url) = mkMungePathUrl top_dir pkgroot
  906. mkMungePathUrl :: FilePath -> FilePath -> (FilePath -> FilePath, FilePath -> FilePath)
  907. mkMungePathUrl top_dir pkgroot = (munge_path, munge_url)
  908. where
  909. munge_path p
  910. | Just p' <- stripVarPrefix "${pkgroot}" p = pkgroot ++ p'
  911. | Just p' <- stripVarPrefix "$topdir" p = top_dir ++ p'
  912. | otherwise = p
  913. munge_url p
  914. | Just p' <- stripVarPrefix "${pkgrooturl}" p = toUrlPath pkgroot p'
  915. | Just p' <- stripVarPrefix "$httptopdir" p = toUrlPath top_dir p'
  916. | otherwise = p
  917. toUrlPath r p = "file:///"
  918. -- URLs always use posix style '/' separators:
  919. ++ FilePath.Posix.joinPath
  920. (r : -- We need to drop a leading "/" or "\\"
  921. -- if there is one:
  922. dropWhile (all isPathSeparator)
  923. (FilePath.splitDirectories p))
  924. -- We could drop the separator here, and then use </> above. However,
  925. -- by leaving it in and using ++ we keep the same path separator
  926. -- rather than letting FilePath change it to use \ as the separator
  927. stripVarPrefix var path = case stripPrefix var path of
  928. Just [] -> Just []
  929. Just cs@(c : _) | isPathSeparator c -> Just cs
  930. _ -> Nothing
  931. -- -----------------------------------------------------------------------------
  932. -- Workaround for old single-file style package dbs
  933. -- Single-file style package dbs have been deprecated for some time, but
  934. -- it turns out that Cabal was using them in one place. So this code is for a
  935. -- workaround to allow older Cabal versions to use this newer ghc.
  936. -- We check if the file db contains just "[]" and if so, we look for a new
  937. -- dir-style db in path.d/, ie in a dir next to the given file.
  938. -- We cannot just replace the file with a new dir style since Cabal still
  939. -- assumes it's a file and tries to overwrite with 'writeFile'.
  940. -- ghc itself also cooperates in this workaround
  941. tryReadParseOldFileStyleDatabase :: Verbosity -> Maybe (FilePath, Bool)
  942. -> GhcPkg.DbOpenMode mode t -> Bool -> FilePath
  943. -> IO (Maybe (PackageDB mode))
  944. tryReadParseOldFileStyleDatabase verbosity mb_user_conf
  945. mode use_cache path = do
  946. -- assumes we've already established that path exists and is not a dir
  947. content <- readFile path `catchIO` \_ -> return ""
  948. if take 2 content == "[]"
  949. then do
  950. path_abs <- absolutePath path
  951. let path_dir = adjustOldDatabasePath path
  952. warn $ "Warning: ignoring old file-style db and trying " ++ path_dir
  953. direxists <- doesDirectoryExist path_dir
  954. if direxists
  955. then do
  956. db <- readParseDatabase verbosity mb_user_conf mode use_cache path_dir
  957. -- but pretend it was at the original location
  958. return $ Just db {
  959. location = path,
  960. locationAbsolute = path_abs
  961. }
  962. else do
  963. lock <- F.forM mode $ \_ -> do
  964. createDirectoryIfMissing True path_dir
  965. GhcPkg.lockPackageDb $ path_dir </> cachefilename
  966. return $ Just PackageDB {
  967. location = path,
  968. locationAbsolute = path_abs,
  969. packageDbLock = lock,
  970. packages = []
  971. }
  972. -- if the path is not a file, or is not an empty db then we fail
  973. else return Nothing
  974. adjustOldFileStylePackageDB :: PackageDB mode -> IO (PackageDB mode)
  975. adjustOldFileStylePackageDB db = do
  976. -- assumes we have not yet established if it's an old style or not
  977. mcontent <- liftM Just (readFile (location db)) `catchIO` \_ -> return Nothing
  978. case fmap (take 2) mcontent of
  979. -- it is an old style and empty db, so look for a dir kind in location.d/
  980. Just "[]" -> return db {
  981. location = adjustOldDatabasePath $ location db,
  982. locationAbsolute = adjustOldDatabasePath $ locationAbsolute db
  983. }
  984. -- it is old style but not empty, we have to bail
  985. Just _ -> die $ "ghc no longer supports single-file style package "
  986. ++ "databases (" ++ location db ++ ") use 'ghc-pkg init'"
  987. ++ "to create the database with the correct format."
  988. -- probably not old style, carry on as normal
  989. Nothing -> return db
  990. adjustOldDatabasePath :: FilePath -> FilePath
  991. adjustOldDatabasePath = (<.> "d")
  992. -- -----------------------------------------------------------------------------
  993. -- Creating a new package DB
  994. initPackageDB :: FilePath -> Verbosity -> [Flag] -> IO ()
  995. initPackageDB filename verbosity _flags = do
  996. let eexist = die ("cannot create: " ++ filename ++ " already exists")
  997. b1 <- doesFileExist filename
  998. when b1 eexist
  999. b2 <- doesDirectoryExist filename
  1000. when b2 eexist
  1001. createDirectoryIfMissing True filename
  1002. lock <- GhcPkg.lockPackageDb $ filename </> cachefilename
  1003. filename_abs <- absolutePath filename
  1004. changeDB verbosity [] PackageDB {
  1005. location = filename,
  1006. locationAbsolute = filename_abs,
  1007. packageDbLock = GhcPkg.DbOpenReadWrite lock,
  1008. packages = []
  1009. }
  1010. -- We can get away with passing an empty stack here, because the new DB is
  1011. -- going to be initially empty, so no dependencies are going to be actually
  1012. -- looked up.
  1013. []
  1014. -- -----------------------------------------------------------------------------
  1015. -- Registering
  1016. registerPackage :: FilePath
  1017. -> Verbosity
  1018. -> [Flag]
  1019. -> Bool -- multi_instance
  1020. -> Bool -- expand_env_vars
  1021. -> Bool -- update
  1022. -> Force
  1023. -> IO ()
  1024. registerPackage input verbosity my_flags multi_instance
  1025. expand_env_vars update force = do
  1026. (db_stack, GhcPkg.DbOpenReadWrite db_to_operate_on, _flag_dbs) <-
  1027. getPkgDatabases verbosity (GhcPkg.DbOpenReadWrite TopOne)
  1028. True{-use user-} True{-use cache-} False{-expand vars-} my_flags
  1029. let to_modify = location db_to_operate_on
  1030. s <-
  1031. case input of
  1032. "-" -> do
  1033. when (verbosity >= Normal) $
  1034. info "Reading package info from stdin ... "
  1035. -- fix the encoding to UTF-8, since this is an interchange format
  1036. hSetEncoding stdin utf8
  1037. getContents
  1038. f -> do
  1039. when (verbosity >= Normal) $
  1040. info ("Reading package info from " ++ show f ++ " ... ")
  1041. readUTF8File f
  1042. expanded <- if expand_env_vars then expandEnvVars s force
  1043. else return s
  1044. (pkg, ws) <- parsePackageInfo $ toUTF8BS expanded
  1045. when (verbosity >= Normal) $
  1046. infoLn "done."
  1047. -- report any warnings from the parse phase
  1048. _ <- reportValidateErrors verbosity [] ws
  1049. (display (mungedId pkg) ++ ": Warning: ") Nothing
  1050. -- validate the expanded pkg, but register the unexpanded
  1051. pkgroot <- absolutePath (takeDirectory to_modify)
  1052. let top_dir = takeDirectory (location (last db_stack))
  1053. pkg_expanded = mungePackagePaths top_dir pkgroot pkg
  1054. let truncated_stack = stackUpTo to_modify db_stack
  1055. -- truncate the stack for validation, because we don't allow
  1056. -- packages lower in the stack to refer to those higher up.
  1057. validatePackageConfig pkg_expanded verbosity truncated_stack
  1058. multi_instance update force
  1059. let
  1060. -- In the normal mode, we only allow one version of each package, so we
  1061. -- remove all instances with the same source package id as the one we're
  1062. -- adding. In the multi instance mode we don't do that, thus allowing
  1063. -- multiple instances with the same source package id.
  1064. removes = [ RemovePackage p
  1065. | not multi_instance,
  1066. p <- packages db_to_operate_on,
  1067. mungedId p == mungedId pkg,
  1068. -- Only remove things that were instantiated the same way!
  1069. instantiatedWith p == instantiatedWith pkg ]
  1070. --
  1071. changeDB verbosity (removes ++ [AddPackage pkg]) db_to_operate_on db_stack
  1072. parsePackageInfo
  1073. :: BS.ByteString
  1074. -> IO (InstalledPackageInfo, [ValidateWarning])
  1075. parsePackageInfo str =
  1076. case parseInstalledPackageInfo str of
  1077. Right (warnings, ok) -> pure (mungePackageInfo ok, ws)
  1078. where
  1079. ws = [ msg | msg <- warnings
  1080. , not ("Unrecognized field pkgroot" `isPrefixOf` msg) ]
  1081. Left err -> die (unlines (F.toList err))
  1082. mungePackageInfo :: InstalledPackageInfo -> InstalledPackageInfo
  1083. mungePackageInfo ipi = ipi
  1084. -- -----------------------------------------------------------------------------
  1085. -- Making changes to a package database
  1086. data DBOp = RemovePackage InstalledPackageInfo
  1087. | AddPackage InstalledPackageInfo
  1088. | ModifyPackage InstalledPackageInfo
  1089. changeDB :: Verbosity
  1090. -> [DBOp]
  1091. -> PackageDB 'GhcPkg.DbReadWrite
  1092. -> PackageDBStack
  1093. -> IO ()
  1094. changeDB verbosity cmds db db_stack = do
  1095. let db' = updateInternalDB db cmds
  1096. db'' <- adjustOldFileStylePackageDB db'
  1097. createDirectoryIfMissing True (location db'')
  1098. changeDBDir verbosity cmds db'' db_stack
  1099. updateInternalDB :: PackageDB 'GhcPkg.DbReadWrite
  1100. -> [DBOp] -> PackageDB 'GhcPkg.DbReadWrite
  1101. updateInternalDB db cmds = db{ packages = foldl do_cmd (packages db) cmds }
  1102. where
  1103. do_cmd pkgs (RemovePackage p) =
  1104. filter ((/= installedUnitId p) . installedUnitId) pkgs
  1105. do_cmd pkgs (AddPackage p) = p : pkgs
  1106. do_cmd pkgs (ModifyPackage p) =
  1107. do_cmd (do_cmd pkgs (RemovePackage p)) (AddPackage p)
  1108. changeDBDir :: Verbosity
  1109. -> [DBOp]
  1110. -> PackageDB 'GhcPkg.DbReadWrite
  1111. -> PackageDBStack
  1112. -> IO ()
  1113. changeDBDir verbosity cmds db db_stack = do
  1114. mapM_ do_cmd cmds
  1115. updateDBCache verbosity db db_stack
  1116. where
  1117. do_cmd (RemovePackage p) = do
  1118. let file = location db </> display (installedUnitId p) <.> "conf"
  1119. when (verbosity > Normal) $ infoLn ("removing " ++ file)
  1120. removeFileSafe file
  1121. do_cmd (AddPackage p) = do
  1122. let file = location db </> display (installedUnitId p) <.> "conf"
  1123. when (verbosity > Normal) $ infoLn ("writing " ++ file)
  1124. writeUTF8File file (showInstalledPackageInfo p)
  1125. do_cmd (ModifyPackage p) =
  1126. do_cmd (AddPackage p)
  1127. updateDBCache :: Verbosity
  1128. -> PackageDB 'GhcPkg.DbReadWrite
  1129. -> PackageDBStack
  1130. -> IO ()
  1131. updateDBCache verbosity db db_stack = do
  1132. let filename = location db </> cachefilename
  1133. db_stack_below = stackUpTo (location db) db_stack
  1134. pkgsCabalFormat :: [InstalledPackageInfo]
  1135. pkgsCabalFormat = packages db
  1136. -- | All the packages we can legally depend on in this step.
  1137. dependablePkgsCabalFormat :: [InstalledPackageInfo]
  1138. dependablePkgsCabalFormat = allPackagesInStack db_stack_below
  1139. pkgsGhcCacheFormat :: [(PackageCacheFormat, Bool)]
  1140. pkgsGhcCacheFormat
  1141. -- See Note [Recompute abi-depends]
  1142. = map (recomputeValidAbiDeps dependablePkgsCabalFormat)
  1143. $ map convertPackageInfoToCacheFormat
  1144. pkgsCabalFormat
  1145. hasAnyAbiDepends :: InstalledPackageInfo -> Bool
  1146. hasAnyAbiDepends x = length (abiDepends x) > 0
  1147. -- warn when we find any (possibly-)bogus abi-depends fields;
  1148. -- Note [Recompute abi-depends]
  1149. when (verbosity >= Normal) $ do
  1150. let definitelyBrokenPackages =
  1151. nub
  1152. . sort
  1153. . map (unPackageName . GhcPkg.unitPackageName . fst)
  1154. . filter snd
  1155. $ pkgsGhcCacheFormat
  1156. when (definitelyBrokenPackages /= []) $ do
  1157. warn "the following packages have broken abi-depends fields:"
  1158. forM_ definitelyBrokenPackages $ \pkg ->
  1159. warn $ " " ++ pkg
  1160. when (verbosity > Normal) $ do
  1161. let possiblyBrokenPackages =
  1162. nub
  1163. . sort
  1164. . filter (not . (`elem` definitelyBrokenPackages))
  1165. . map (unPackageName . pkgName . packageId)
  1166. . filter hasAnyAbiDepends
  1167. $ pkgsCabalFormat
  1168. when (possiblyBrokenPackages /= []) $ do
  1169. warn $
  1170. "the following packages have correct abi-depends, " ++
  1171. "but may break in the future:"
  1172. forM_ possiblyBrokenPackages $ \pkg ->
  1173. warn $ " " ++ pkg
  1174. when (verbosity > Normal) $
  1175. infoLn ("writing cache " ++ filename)
  1176. let d = fmap (fromPackageCacheFormat . fst) pkgsGhcCacheFormat
  1177. GhcPkg.writePackageDb filename d pkgsCabalFormat
  1178. `catchIO` \e ->
  1179. if isPermissionError e
  1180. then die $ filename ++ ": you don't have permission to modify this file"
  1181. else ioError e
  1182. case packageDbLock db of
  1183. GhcPkg.DbOpenReadWrite lock -> GhcPkg.unlockPackageDb lock
  1184. type PackageCacheFormat = GhcPkg.GenericUnitInfo
  1185. PackageIdentifier
  1186. PackageName
  1187. UnitId
  1188. ModuleName
  1189. OpenModule
  1190. {- Note [Recompute abi-depends]
  1191. ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  1192. Like most fields, `ghc-pkg` relies on who-ever is performing package
  1193. registration to fill in fields; this includes the `abi-depends` field present
  1194. for the package.
  1195. However, this was likely a mistake, and is not very robust; in certain cases,
  1196. versions of Cabal may use bogus abi-depends fields for a package when doing
  1197. builds. Why? Because package database information is aggressively cached; it is
  1198. possible to work Cabal into a situation where it uses a cached version of
  1199. `abi-depends`, rather than the one in the actual database after it has been
  1200. recomputed.
  1201. However, there is an easy fix: ghc-pkg /already/ knows the `abi-depends` of a
  1202. package, because they are the ABIs of the packages pointed at by the `depends`
  1203. field. So it can simply look up the abi from the dependencies in the original
  1204. database, and ignore whatever the system registering gave it.
  1205. So, instead, we do two things here:
  1206. - We throw away the information for a registered package's `abi-depends` field.
  1207. - We recompute it: we simply look up the unit ID of the package in the original
  1208. database, and use *its* abi-depends.
  1209. See #14381, and Cabal issue #4728.
  1210. Additionally, because we are throwing away the original (declared) ABI deps, we
  1211. return a boolean that indicates whether any abi-depends were actually
  1212. overridden.
  1213. -}
  1214. recomputeValidAbiDeps :: [InstalledPackageInfo]
  1215. -> PackageCacheFormat
  1216. -> (PackageCacheFormat, Bool)
  1217. recomputeValidAbiDeps db pkg =
  1218. (pkg { GhcPkg.unitAbiDepends = newAbiDeps }, abiDepsUpdated)
  1219. where
  1220. newAbiDeps =
  1221. catMaybes . flip map (GhcPkg.unitAbiDepends pkg) $ \(k, _) ->
  1222. case filter (\d -> installedUnitId d == k) db of
  1223. [x] -> Just (k, ST.pack $ unAbiHash (abiHash x))
  1224. _ -> Nothing
  1225. abiDepsUpdated =
  1226. GhcPkg.unitAbiDepends pkg /= newAbiDeps
  1227. -- | Convert from PackageCacheFormat to DbUnitInfo (the format used in
  1228. -- Ghc.PackageDb to store into the database)
  1229. fromPackageCacheFormat :: PackageCacheFormat -> GhcPkg.DbUnitInfo
  1230. fromPackageCacheFormat = GhcPkg.mapGenericUnitInfo
  1231. mkUnitId' mkPackageIdentifier' mkPackageName' mkModuleName' mkModule'
  1232. where
  1233. displayBS :: Pretty a => a -> BS.ByteString
  1234. displayBS = toUTF8BS . display
  1235. mkPackageIdentifier' = displayBS
  1236. mkPackageName' = displayBS
  1237. mkComponentId' = displayBS
  1238. mkUnitId' = displayBS
  1239. mkModuleName' = displayBS
  1240. mkInstUnitId' i = case i of
  1241. IndefFullUnitId cid insts -> DbInstUnitId (mkComponentId' cid)
  1242. (fmap (bimap mkModuleName' mkModule') (Map.toList insts))
  1243. DefiniteUnitId uid -> DbUnitId (mkUnitId' (unDefUnitId uid))
  1244. mkModule' m = case m of
  1245. OpenModule uid n -> DbModule (mkInstUnitId' uid) (mkModuleName' n)
  1246. OpenModuleVar n -> DbModuleVar (mkModuleName' n)
  1247. convertPackageInfoToCacheFormat :: InstalledPackageInfo -> PackageCacheFormat
  1248. convertPackageInfoToCacheFormat pkg =
  1249. GhcPkg.GenericUnitInfo {
  1250. GhcPkg.unitId = installedUnitId pkg,
  1251. GhcPkg.unitInstanceOf = mkUnitId (unComponentId (installedComponentId pkg)),
  1252. GhcPkg.unitInstantiations = instantiatedWith pkg,
  1253. GhcPkg.unitPackageId = sourcePackageId pkg,
  1254. GhcPkg.unitPackageName = packageName pkg,
  1255. GhcPkg.unitPackageVersion = Version.Version (versionNumbers (packageVersion pkg)) [],
  1256. GhcPkg.unitComponentName =
  1257. fmap (mkPackageName . unUnqualComponentName) (libraryNameString $ sourceLibName pkg),
  1258. GhcPkg.unitDepends = depends pkg,
  1259. GhcPkg.unitAbiDepends = map (\(AbiDependency k v) -> (k,ST.pack $ unAbiHash v)) (abiDepends pkg),
  1260. GhcPkg.unitAbiHash = ST.pack $ unAbiHash (abiHash pkg),
  1261. GhcPkg.unitImportDirs = map ST.pack $ importDirs pkg,
  1262. GhcPkg.unitLibraries = map ST.pack $ hsLibraries pkg,
  1263. GhcPkg.unitExtDepLibsSys = map ST.pack $ extraLibraries pkg,
  1264. GhcPkg.unitExtDepLibsGhc = map ST.pack $ extraGHCiLibraries pkg,
  1265. GhcPkg.unitLibraryDirs = map ST.pack $ libraryDirs pkg,
  1266. GhcPkg.unitLibraryDynDirs = map ST.pack $ libraryDynDirs pkg,
  1267. GhcPkg.unitExtDepFrameworks = map ST.pack $ frameworks pkg,
  1268. GhcPkg.unitExtDepFrameworkDirs = map ST.pack $ frameworkDirs pkg,
  1269. GhcPkg.unitLinkerOptions = map ST.pack $ ldOptions pkg,
  1270. GhcPkg.unitCcOptions = map ST.pack $ ccOptions pkg,
  1271. GhcPkg.unitIncludes = map ST.pack $ includes pkg,
  1272. GhcPkg.unitIncludeDirs = map ST.pack $ includeDirs pkg,
  1273. GhcPkg.unitHaddockInterfaces = map ST.pack $ haddockInterfaces pkg,
  1274. GhcPkg.unitHaddockHTMLs = map ST.pack $ haddockHTMLs pkg,
  1275. GhcPkg.unitExposedModules = map convertExposed (exposedModules pkg),
  1276. GhcPkg.unitHiddenModules = hiddenModules pkg,
  1277. GhcPkg.unitIsIndefinite = indefinite pkg,
  1278. GhcPkg.unitIsExposed = exposed pkg,
  1279. GhcPkg.unitIsTrusted = trusted pkg
  1280. }
  1281. where
  1282. convertExposed (ExposedModule n reexport) = (n, reexport)
  1283. -- -----------------------------------------------------------------------------
  1284. -- Exposing, Hiding, Trusting, Distrusting, Unregistering are all similar
  1285. exposePackage :: PackageArg -> Verbosity -> [Flag] -> Force -> IO ()
  1286. exposePackage = modifyPackage (\p -> ModifyPackage p{exposed=True})
  1287. hidePackage :: PackageArg -> Verbosity -> [Flag] -> Force -> IO ()
  1288. hidePackage = modifyPackage (\p -> ModifyPackage p{exposed=False})
  1289. trustPackage :: PackageArg -> Verbosity -> [Flag] -> Force -> IO ()
  1290. trustPackage = modifyPackage (\p -> ModifyPackage p{trusted=True})
  1291. distrustPackage :: PackageArg -> Verbosity -> [Flag] -> Force -> IO ()
  1292. distrustPackage = modifyPackage (\p -> ModifyPackage p{trusted=False})
  1293. unregisterPackage :: PackageArg -> Verbosity -> [Flag] -> Force -> IO ()
  1294. unregisterPackage = modifyPackage RemovePackage
  1295. modifyPackage
  1296. :: (InstalledPackageInfo -> DBOp)
  1297. -> PackageArg
  1298. -> Verbosity
  1299. -> [Flag]
  1300. -> Force
  1301. -> IO ()
  1302. modifyPackage fn pkgarg verbosity my_flags force = do
  1303. (db_stack, GhcPkg.DbOpenReadWrite db, _flag_dbs) <-
  1304. getPkgDatabases verbosity (GhcPkg.DbOpenReadWrite $ ContainsPkg pkgarg)
  1305. True{-use user-} True{-use cache-} False{-expand vars-} my_flags
  1306. let db_name = location db
  1307. pkgs = packages db
  1308. -- Get package respecting flags...
  1309. ps = findPackage pkgarg pkgs
  1310. -- This shouldn't happen if getPkgDatabases picks the DB correctly.
  1311. when (null ps) $ cannotFindPackage pkgarg $ Just db
  1312. let pks = map installedUnitId ps
  1313. cmds = [ fn pkg | pkg <- pkgs, installedUnitId pkg `elem` pks ]
  1314. new_db = updateInternalDB db cmds
  1315. new_db_ro = new_db { packageDbLock = GhcPkg.DbOpenReadOnly }
  1316. -- ...but do consistency checks with regards to the full stack
  1317. old_broken = brokenPackages (allPackagesInStack db_stack)
  1318. rest_of_stack = filter ((/= db_name) . location) db_stack
  1319. new_stack = new_db_ro : rest_of_stack
  1320. new_broken = brokenPackages (allPackagesInStack new_stack)
  1321. newly_broken = filter ((`notElem` map installedUnitId old_broken)
  1322. . installedUnitId) new_broken
  1323. --
  1324. let displayQualPkgId pkg
  1325. | [_] <- filter ((== pkgid) . mungedId)
  1326. (allPackagesInStack db_stack)
  1327. = display pkgid
  1328. | otherwise = display pkgid ++ "@" ++ display (installedUnitId pkg)
  1329. where pkgid = mungedId pkg
  1330. when (not (null newly_broken)) $
  1331. dieOrForceAll force ("unregistering would break the following packages: "
  1332. ++ unwords (map displayQualPkgId newly_broken))
  1333. changeDB verbosity cmds db db_stack
  1334. recache :: Verbosity -> [Flag] -> IO ()
  1335. recache verbosity my_flags = do
  1336. (_db_stack, GhcPkg.DbOpenReadWrite db_to_operate_on, _flag_dbs) <-
  1337. getPkgDatabases verbosity (GhcPkg.DbOpenReadWrite TopOne)
  1338. True{-use user-} False{-no cache-} False{-expand vars-} my_flags
  1339. changeDB verbosity [] db_to_operate_on _db_stack
  1340. -- -----------------------------------------------------------------------------
  1341. -- Listing packages
  1342. listPackages :: Verbosity -> [Flag] -> Maybe PackageArg
  1343. -> Maybe (String->Bool)
  1344. -> IO ()
  1345. listPackages verbosity my_flags mPackageName mModuleName = do
  1346. let simple_output = FlagSimpleOutput `elem` my_flags
  1347. (db_stack, GhcPkg.DbOpenReadOnly, flag_db_stack) <-
  1348. getPkgDatabases verbosity GhcPkg.DbOpenReadOnly
  1349. False{-use user-} True{-use cache-} False{-expand vars-} my_flags
  1350. let db_stack_filtered -- if a package is given, filter out all other packages
  1351. | Just this <- mPackageName =
  1352. [ db{ packages = filter (this `matchesPkg`) (packages db) }
  1353. | db <- flag_db_stack ]
  1354. | Just match <- mModuleName = -- packages which expose mModuleName
  1355. [ db{ packages = filter (match `exposedInPkg`) (packages db) }
  1356. | db <- flag_db_stack ]
  1357. | otherwise = flag_db_stack
  1358. db_stack_sorted
  1359. = [ db{ packages = sort_pkgs (packages db) }
  1360. | db <- db_stack_filtered ]
  1361. where sort_pkgs = sortBy cmpPkgIds
  1362. cmpPkgIds pkg1 pkg2 =
  1363. case mungedName p1 `compare` mungedName p2 of
  1364. LT -> LT
  1365. GT -> GT
  1366. EQ -> case mungedVersion p1 `compare` mungedVersion p2 of
  1367. LT -> LT
  1368. GT -> GT
  1369. EQ -> installedUnitId pkg1 `compare` installedUnitId pkg2
  1370. where (p1,p2) = (mungedId pkg1, mungedId pkg2)
  1371. stack = reverse db_stack_sorted
  1372. match `exposedInPkg` pkg = any match (map display $ exposedModules pkg)
  1373. pkg_map = allPackagesInStack db_stack
  1374. broken = map installedUnitId (brokenPackages pkg_map)
  1375. show_normal PackageDB{ location = db_name, packages = pkg_confs } =
  1376. do hPutStrLn stdout db_name
  1377. if null pkg_confs
  1378. then hPutStrLn stdout " (no packages)"
  1379. else hPutStrLn stdout $ unlines (map (" " ++) (map pp_pkg pkg_confs))
  1380. where
  1381. pp_pkg p
  1382. | installedUnitId p `elem` broken = printf "{%s}" doc
  1383. | exposed p = doc
  1384. | otherwise = printf "(%s)" doc
  1385. where doc | verbosity >= Verbose = printf "%s (%s)" pkg (display (installedUnitId p))
  1386. | otherwise = pkg
  1387. where
  1388. pkg = display (mungedId p)
  1389. show_simple = simplePackageList my_flags . allPackagesInStack
  1390. when (not (null broken) && not simple_output && verbosity /= Silent) $ do
  1391. prog <- getProgramName
  1392. warn ("WARNING: there are broken packages. Run '" ++ prog ++ " check' for more details.")
  1393. if simple_output then show_simple stack else do
  1394. #if !defined(WITH_TERMINFO)
  1395. mapM_ show_normal stack
  1396. #else
  1397. let
  1398. show_colour withF db@PackageDB{ packages = pkg_confs } =
  1399. if null pkg_confs
  1400. then termText (location db) <#> termText "\n (no packages)\n"
  1401. else
  1402. mconcat $ map (<#> termText "\n") $
  1403. (termText (location db)
  1404. : map (termText " " <#>) (map pp_pkg pkg_confs))
  1405. where
  1406. pp_pkg p
  1407. | installedUnitId p `elem` broken = withF Red doc
  1408. | exposed p = doc
  1409. | otherwise = withF Blue doc
  1410. where doc | verbosity >= Verbose
  1411. = termText (printf "%s (%s)" pkg (display (installedUnitId p)))
  1412. | otherwise
  1413. = termText pkg
  1414. where
  1415. pkg = display (mungedId p)
  1416. is_tty <- hIsTerminalDevice stdout
  1417. if not is_tty
  1418. then mapM_ show_normal stack
  1419. else do tty <- Terminfo.setupTermFromEnv
  1420. case Terminfo.getCapability tty withForegroundColor of
  1421. Nothing -> mapM_ show_normal stack
  1422. Just w -> runTermOutput tty $ mconcat $
  1423. map (show_colour w) stack
  1424. #endif
  1425. simplePackageList :: [Flag] -> [InstalledPackageInfo] -> IO ()
  1426. simplePackageList my_flags pkgs = do
  1427. let showPkg :: InstalledPackageInfo -> String
  1428. showPkg | FlagShowUnitIds `elem` my_flags = display . installedUnitId
  1429. | FlagNamesOnly `elem` my_flags = display . mungedName . mungedId
  1430. | otherwise = display . mungedId
  1431. strs = map showPkg pkgs
  1432. when (not (null pkgs)) $
  1433. hPutStrLn stdout $ concat $ intersperse " " strs
  1434. showPackageDot :: Verbosity -> [Flag] -> IO ()
  1435. showPackageDot verbosity myflags = do
  1436. (_, GhcPkg.DbOpenReadOnly, flag_db_stack) <-
  1437. getPkgDatabases verbosity GhcPkg.DbOpenReadOnly
  1438. False{-use user-} True{-use cache-} False{-expand vars-} myflags
  1439. let all_pkgs = allPackagesInStack flag_db_stack
  1440. ipix = PackageIndex.fromList all_pkgs
  1441. putStrLn "digraph {"
  1442. let quote s = '"':s ++ "\""
  1443. mapM_ putStrLn [ quote from ++ " -> " ++ quote to
  1444. | p <- all_pkgs,
  1445. let from = display (mungedId p),
  1446. key <- depends p,
  1447. Just dep <- [PackageIndex.lookupUnitId ipix key],
  1448. let to = display (mungedId dep)
  1449. ]
  1450. putStrLn "}"
  1451. -- -----------------------------------------------------------------------------
  1452. -- Prints the highest (hidden or exposed) version of a package
  1453. -- ToDo: This is no longer well-defined with unit ids, because the
  1454. -- dependencies may be varying versions
  1455. latestPackage :: Verbosity -> [Flag] -> GlobPackageIdentifier -> IO ()
  1456. latestPackage verbosity my_flags pkgid = do
  1457. (_, GhcPkg.DbOpenReadOnly, flag_db_stack) <-
  1458. getPkgDatabases verbosity GhcPkg.DbOpenReadOnly
  1459. False{-use user-} True{-use cache-} False{-expand vars-} my_flags
  1460. ps <- findPackages flag_db_stack (Id pkgid)
  1461. case ps of
  1462. [] -> die "no matches"
  1463. _ -> show_pkg . maximum . map mungedId $ ps
  1464. where
  1465. show_pkg pid = hPutStrLn stdout (display pid)
  1466. -- -----------------------------------------------------------------------------
  1467. -- Describe
  1468. describePackage :: Verbosity -> [Flag] -> PackageArg -> Bool -> IO ()
  1469. describePackage verbosity my_flags pkgarg expand_pkgroot = do
  1470. (_, GhcPkg.DbOpenReadOnly, flag_db_stack) <-
  1471. getPkgDatabases verbosity GhcPkg.DbOpenReadOnly
  1472. False{-use user-} True{-use cache-} expand_pkgroot my_flags
  1473. dbs <- findPackagesByDB flag_db_stack pkgarg
  1474. doDump expand_pkgroot [ (pkg, locationAbsolute db)
  1475. | (db, pkgs) <- dbs, pkg <- pkgs ]
  1476. dumpUnits :: Verbosity -> [Flag] -> Bool -> IO ()
  1477. dumpUnits verbosity my_flags expand_pkgroot = do
  1478. (_, GhcPkg.DbOpenReadOnly, flag_db_stack) <-
  1479. getPkgDatabases verbosity GhcPkg.DbOpenReadOnly
  1480. False{-use user-} True{-use cache-} expand_pkgroot my_flags
  1481. doDump expand_pkgroot [ (pkg, locationAbsolute db)
  1482. | db <- flag_db_stack, pkg <- packages db ]
  1483. doDump :: Bool -> [(InstalledPackageInfo, FilePath)] -> IO ()
  1484. doDump expand_pkgroot pkgs = do
  1485. -- fix the encoding to UTF-8, since this is an interchange format
  1486. hSetEncoding stdout utf8
  1487. putStrLn $
  1488. intercalate "---\n"
  1489. [ if expand_pkgroot
  1490. then showInstalledPackageInfo pkg
  1491. else showInstalledPackageInfo pkg ++ pkgrootField
  1492. | (pkg, pkgloc) <- pkgs
  1493. , let pkgroot = takeDirectory pkgloc
  1494. pkgrootField = "pkgroot: " ++ show pkgroot ++ "\n" ]
  1495. -- PackageId is can have globVersion for the version
  1496. findPackages :: PackageDBStack -> PackageArg -> IO [InstalledPackageInfo]
  1497. findPackages db_stack pkgarg
  1498. = fmap (concatMap snd) $ findPackagesByDB db_stack pkgarg
  1499. findPackage :: PackageArg -> [InstalledPackageInfo] -> [InstalledPackageInfo]
  1500. findPackage pkgarg pkgs = filter (pkgarg `matchesPkg`) pkgs
  1501. findPackagesByDB :: PackageDBStack -> PackageArg
  1502. -> IO [(PackageDB 'GhcPkg.DbReadOnly, [InstalledPackageInfo])]
  1503. findPackagesByDB db_stack pkgarg
  1504. = case [ (db, matched)
  1505. | db <- db_stack,
  1506. let matched = findPackage pkgarg $ packages db,
  1507. not (null matched) ] of
  1508. [] -> cannotFindPackage pkgarg Nothing
  1509. ps -> return ps
  1510. cannotFindPackage :: PackageArg -> Maybe (PackageDB mode) -> IO a
  1511. cannotFindPackage pkgarg mdb = die $ "cannot find package " ++ pkg_msg pkgarg
  1512. ++ maybe "" (\db -> " in " ++ location db) mdb
  1513. where
  1514. pkg_msg (Id pkgid) = displayGlobPkgId pkgid
  1515. pkg_msg (IUId ipid) = display ipid
  1516. pkg_msg (Substring pkgpat _) = "matching " ++ pkgpat
  1517. matches :: GlobPackageIdentifier -> MungedPackageId -> Bool
  1518. GlobPackageIdentifier pn `matches` pid'
  1519. = (pn == mungedName pid')
  1520. ExactPackageIdentifier pid `matches` pid'
  1521. = mungedName pid == mungedName pid' &&
  1522. (mungedVersion pid == mungedVersion pid' || mungedVersion pid == nullVersion)
  1523. matchesPkg :: PackageArg -> InstalledPackageInfo -> Bool
  1524. (Id pid) `matchesPkg` pkg = pid `matches` mungedId pkg
  1525. (IUId ipid) `matchesPkg` pkg = ipid == installedUnitId pkg
  1526. (Substring _ m) `matchesPkg` pkg = m (display (mungedId pkg))
  1527. -- -----------------------------------------------------------------------------
  1528. -- Field
  1529. describeField :: Verbosity -> [Flag] -> PackageArg -> [String] -> Bool -> IO ()
  1530. describeField verbosity my_flags pkgarg fields expand_pkgroot = do
  1531. (_, GhcPkg.DbOpenReadOnly, flag_db_stack) <-
  1532. getPkgDatabases verbosity GhcPkg.DbOpenReadOnly
  1533. False{-use user-} True{-use cache-} expand_pkgroot my_flags
  1534. fns <- mapM toField fields
  1535. ps <- findPackages flag_db_stack pkgarg
  1536. mapM_ (selectFields fns) ps
  1537. where showFun = if FlagSimpleOutput `elem` my_flags
  1538. then showSimpleInstalledPackageInfoField
  1539. else showInstalledPackageInfoField
  1540. toField f = case showFun f of
  1541. Nothing -> die ("unknown field: " ++ f)
  1542. Just fn -> return fn
  1543. selectFields fns pinfo = mapM_ (\fn->putStrLn (fn pinfo)) fns
  1544. -- -----------------------------------------------------------------------------
  1545. -- Check: Check consistency of installed packages
  1546. checkConsistency :: Verbosity -> [Flag] -> IO ()
  1547. checkConsistency verbosity my_flags = do
  1548. (db_stack, GhcPkg.DbOpenReadOnly, _) <-
  1549. getPkgDatabases verbosity GhcPkg.DbOpenReadOnly
  1550. True{-use user-} True{-use cache-} True{-expand vars-} my_flags
  1551. -- although check is not a modify command, we do need to use the user
  1552. -- db, because we may need it to verify package deps.
  1553. let simple_output = FlagSimpleOutput `elem` my_flags
  1554. let unitid_output = FlagShowUnitIds `elem` my_flags
  1555. let pkgs = allPackagesInStack db_stack
  1556. checkPackage :: InstalledPackageInfo -> IO [InstalledPackageInfo]
  1557. checkPackage p = do
  1558. (_,es,ws) <- runValidate $ checkPackageConfig p verbosity db_stack
  1559. True True
  1560. if null es
  1561. then do
  1562. when (not simple_output) $ do
  1563. _ <- reportValidateErrors verbosity [] ws "" Nothing
  1564. return ()
  1565. return []
  1566. else do
  1567. when (not simple_output) $ do
  1568. reportError ("There are problems in package " ++ display (mungedId p) ++ ":")
  1569. _ <- reportValidateErrors verbosity es ws " " Nothing
  1570. return ()
  1571. return [p]
  1572. broken_pkgs <- concat `fmap` mapM checkPackage pkgs
  1573. let filterOut pkgs1 pkgs2 = filter not_in pkgs2
  1574. where not_in p = mungedId p `notElem` all_ps
  1575. all_ps = map mungedId pkgs1
  1576. let not_broken_pkgs = filterOut broken_pkgs pkgs
  1577. (_, trans_broken_pkgs) = closure [] not_broken_pkgs
  1578. all_broken_pkgs :: [InstalledPackageInfo]
  1579. all_broken_pkgs = broken_pkgs ++ trans_broken_pkgs
  1580. when (not (null all_broken_pkgs)) $ do
  1581. if simple_output
  1582. then simplePackageList my_flags all_broken_pkgs
  1583. else do
  1584. let disp :: InstalledPackageInfo -> String
  1585. disp | unitid_output = display . installedUnitId
  1586. | otherwise = display . mungedId
  1587. reportError ("\nThe following packages are broken, either because they have a problem\n"++
  1588. "listed above, or because they depend on a broken package.")
  1589. mapM_ (hPutStrLn stderr . disp) all_broken_pkgs
  1590. when (not (null all_broken_pkgs)) $ exitWith (ExitFailure 1)
  1591. closure :: [InstalledPackageInfo] -> [InstalledPackageInfo]
  1592. -> ([InstalledPackageInfo], [InstalledPackageInfo])
  1593. closure pkgs db_stack = go pkgs db_stack
  1594. where
  1595. go avail not_avail =
  1596. case partition (depsAvailable avail) not_avail of
  1597. ([], not_avail') -> (avail, not_avail')
  1598. (new_avail, not_avail') -> go (new_avail ++ avail) not_avail'
  1599. depsAvailable :: [InstalledPackageInfo] -> InstalledPackageInfo
  1600. -> Bool
  1601. depsAvailable pkgs_ok pkg = null dangling
  1602. where dangling = filter (`notElem` pids) (depends pkg)
  1603. pids = map installedUnitId pkgs_ok
  1604. -- we want mutually recursive groups of package to show up
  1605. -- as broken. (#1750)
  1606. brokenPackages :: [InstalledPackageInfo] -> [InstalledPackageInfo]
  1607. brokenPackages pkgs = snd (closure [] pkgs)
  1608. -----------------------------------------------------------------------------
  1609. -- Sanity-check a new package config, and automatically build GHCi libs
  1610. -- if requested.
  1611. type ValidateError = (Force,String)
  1612. type ValidateWarning = String
  1613. newtype Validate a = V { runValidate :: IO (a, [ValidateError],[ValidateWarning]) }
  1614. instance Functor Validate where
  1615. fmap = liftM
  1616. instance Applicative Validate where
  1617. pure a = V $ pure (a, [], [])
  1618. (<*>) = ap
  1619. instance Monad Validate where
  1620. m >>= k = V $ do
  1621. (a, es, ws) <- runValidate m
  1622. (b, es', ws') <- runValidate (k a)
  1623. return (b,es++es',ws++ws')
  1624. verror :: Force -> String -> Validate ()
  1625. verror f s = V (return ((),[(f,s)],[]))
  1626. vwarn :: String -> Validate ()
  1627. vwarn s = V (return ((),[],["Warning: " ++ s]))
  1628. liftIO :: IO a -> Validate a
  1629. liftIO k = V (k >>= \a -> return (a,[],[]))
  1630. -- returns False if we should die
  1631. reportValidateErrors :: Verbosity -> [ValidateError] -> [ValidateWarning]
  1632. -> String -> Maybe Force -> IO Bool
  1633. reportValidateErrors verbosity es ws prefix mb_force = do
  1634. when (verbosity >= Normal) $ mapM_ (warn . (prefix++)) ws
  1635. oks <- mapM report es
  1636. return (and oks)
  1637. where
  1638. report (f,s)
  1639. | Just force <- mb_force
  1640. = if (force >= f)
  1641. then do when (verbosity >= Normal) $
  1642. reportError (prefix ++ s ++ " (ignoring)")
  1643. return True
  1644. else if f < CannotForce
  1645. then do reportError (prefix ++ s ++ " (use --force to override)")
  1646. return False
  1647. else do reportError err
  1648. return False
  1649. | otherwise = do reportError err
  1650. return False
  1651. where
  1652. err = prefix ++ s
  1653. validatePackageConfig :: InstalledPackageInfo
  1654. -> Verbosity
  1655. -> PackageDBStack
  1656. -> Bool -- multi_instance
  1657. -> Bool -- update, or check
  1658. -> Force
  1659. -> IO ()
  1660. validatePackageConfig pkg verbosity db_stack
  1661. multi_instance update force = do
  1662. (_,es,ws) <- runValidate $
  1663. checkPackageConfig pkg verbosity db_stack
  1664. multi_instance update
  1665. ok <- reportValidateErrors verbosity es ws
  1666. (display (mungedId pkg) ++ ": ") (Just force)
  1667. when (not ok) $ exitWith (ExitFailure 1)
  1668. checkPackageConfig :: InstalledPackageInfo
  1669. -> Verbosity
  1670. -> PackageDBStack
  1671. -> Bool -- multi_instance
  1672. -> Bool -- update, or check
  1673. -> Validate ()
  1674. checkPackageConfig pkg verbosity db_stack
  1675. multi_instance update = do
  1676. checkPackageId pkg
  1677. checkUnitId pkg db_stack update
  1678. checkDuplicates db_stack pkg multi_instance update
  1679. mapM_ (checkDep db_stack) (depends pkg)
  1680. checkDuplicateDepends (depends pkg)
  1681. mapM_ (checkDir False "import-dirs") (importDirs pkg)
  1682. mapM_ (checkDir True "library-dirs") (libraryDirs pkg)
  1683. mapM_ (checkDir True "dynamic-library-dirs") (libraryDynDirs pkg)
  1684. mapM_ (checkDir True "include-dirs") (includeDirs pkg)
  1685. mapM_ (checkDir True "framework-dirs") (frameworkDirs pkg)
  1686. mapM_ (checkFile True "haddock-interfaces") (haddockInterfaces pkg)
  1687. mapM_ (checkDirURL True "haddock-html") (haddockHTMLs pkg)
  1688. checkDuplicateModules pkg
  1689. checkExposedModules db_stack pkg
  1690. checkOtherModules pkg
  1691. let has_code = Set.null (openModuleSubstFreeHoles (Map.fromList (instantiatedWith pkg)))
  1692. when has_code $ mapM_ (checkHSLib verbosity (libraryDirs pkg ++ libraryDynDirs pkg)) (hsLibraries pkg)
  1693. -- ToDo: check these somehow?
  1694. -- extra_libraries :: [String],
  1695. -- c_includes :: [String],
  1696. -- When the package name and version are put together, sometimes we can
  1697. -- end up with a package id that cannot be parsed. This will lead to
  1698. -- difficulties when the user wants to refer to the package later, so
  1699. -- we check that the package id can be parsed properly here.
  1700. checkPackageId :: InstalledPackageInfo -> Validate ()
  1701. checkPackageId ipi =
  1702. let str = display (mungedId ipi) in
  1703. case Cabal.eitherParsec str :: Either String MungedPackageId of
  1704. Left e -> verror CannotForce ("invalid package identifier: '" ++ str ++ "': " ++ e)
  1705. Right _ -> pure ()
  1706. checkUnitId :: InstalledPackageInfo -> PackageDBStack -> Bool
  1707. -> Validate ()
  1708. checkUnitId ipi db_stack update = do
  1709. let uid = installedUnitId ipi
  1710. when (null (display uid)) $ verror CannotForce "missing id field"
  1711. when (display uid /= compatPackageKey ipi) $
  1712. verror CannotForce $ "installed package info from too old version of Cabal "
  1713. ++ "(key field does not match id field)"
  1714. let dups = [ p | p <- allPackagesInStack db_stack,
  1715. installedUnitId p == uid ]
  1716. when (not update && not (null dups)) $
  1717. verror CannotForce $
  1718. "package(s) with this id already exist: " ++
  1719. unwords (map (display.installedUnitId) dups)
  1720. checkDuplicates :: PackageDBStack -> InstalledPackageInfo
  1721. -> Bool -> Bool-> Validate ()
  1722. checkDuplicates db_stack pkg multi_instance update = do
  1723. let
  1724. pkgid = mungedId pkg
  1725. pkgs = packages (head db_stack)
  1726. --
  1727. -- Check whether this package id already exists in this DB
  1728. --
  1729. when (not update && not multi_instance
  1730. && (pkgid `elem` map mungedId pkgs)) $
  1731. verror CannotForce $
  1732. "package " ++ display pkgid ++ " is already installed"
  1733. let
  1734. uncasep = map toLower . display
  1735. dups = filter ((== uncasep pkgid) . uncasep) (map mungedId pkgs)
  1736. when (not update && not multi_instance
  1737. && not (null dups)) $ verror ForceAll $
  1738. "Package names may be treated case-insensitively in the future.\n"++
  1739. "Package " ++ display pkgid ++
  1740. " overlaps with: " ++ unwords (map display dups)
  1741. checkDir, checkFile, checkDirURL :: Bool -> String -> FilePath -> Validate ()
  1742. checkDir = checkPath False True
  1743. checkFile = checkPath False False
  1744. checkDirURL = checkPath True True
  1745. checkPath :: Bool -> Bool -> Bool -> String -> FilePath -> Validate ()
  1746. checkPath url_ok is_dir warn_only thisfield d
  1747. | url_ok && ("http://" `isPrefixOf` d
  1748. || "https://" `isPrefixOf` d) = return ()
  1749. | url_ok
  1750. , Just d' <- stripPrefix "file://" d
  1751. = checkPath False is_dir warn_only thisfield d'
  1752. -- Note: we don't check for $topdir/${pkgroot} here. We rely on these
  1753. -- variables having been expanded already, see mungePackagePaths.
  1754. | isRelative d = verror ForceFiles $
  1755. thisfield ++ ": " ++ d ++ " is a relative path which "
  1756. ++ "makes no sense (as there is nothing for it to be "
  1757. ++ "relative to). You can make paths relative to the "
  1758. ++ "package database itself by using ${pkgroot}."
  1759. -- relative paths don't make any sense; #4134
  1760. | otherwise = do
  1761. there <- liftIO $ if is_dir then doesDirectoryExist d else doesFileExist d
  1762. when (not there) $
  1763. let msg = thisfield ++ ": " ++ d ++ " doesn't exist or isn't a "
  1764. ++ if is_dir then "directory" else "file"
  1765. in
  1766. if warn_only
  1767. then vwarn msg
  1768. else verror ForceFiles msg
  1769. checkDep :: PackageDBStack -> UnitId -> Validate ()
  1770. checkDep db_stack pkgid
  1771. | pkgid `elem` pkgids = return ()
  1772. | otherwise = verror ForceAll ("dependency \"" ++ display pkgid
  1773. ++ "\" doesn't exist")
  1774. where
  1775. all_pkgs = allPackagesInStack db_stack
  1776. pkgids = map installedUnitId all_pkgs
  1777. checkDuplicateDepends :: [UnitId] -> Validate ()
  1778. checkDuplicateDepends deps
  1779. | null dups = return ()
  1780. | otherwise = verror ForceAll ("package has duplicate dependencies: " ++
  1781. unwords (map display dups))
  1782. where
  1783. dups = [ p | (p:_:_) <- group (sort deps) ]
  1784. checkHSLib :: Verbosity -> [String] -> String -> Validate ()
  1785. checkHSLib _verbosity dirs lib = do
  1786. let filenames = ["lib" ++ lib ++ ".a",
  1787. "lib" ++ lib ++ "_p.a",
  1788. "lib" ++ lib ++ "-ghc" ++ GHC.Version.cProjectVersion ++ ".so",
  1789. "lib" ++ lib ++ "-ghc" ++ GHC.Version.cProjectVersion ++ ".dylib",
  1790. lib ++ "-ghc" ++ GHC.Version.cProjectVersion ++ ".dll"]
  1791. b <- liftIO $ doesFileExistOnPath filenames dirs
  1792. when (not b) $
  1793. verror ForceFiles ("cannot find any of " ++ show filenames ++
  1794. " on library path")
  1795. doesFileExistOnPath :: [FilePath] -> [FilePath] -> IO Bool
  1796. doesFileExistOnPath filenames paths = anyM doesFileExist fullFilenames
  1797. where fullFilenames = [ path </> filename
  1798. | filename <- filenames
  1799. , path <- paths ]
  1800. -- | Perform validation checks (module file existence checks) on the
  1801. -- @hidden-modules@ field.
  1802. checkOtherModules :: InstalledPackageInfo -> Validate ()
  1803. checkOtherModules pkg = mapM_ (checkModuleFile pkg) (hiddenModules pkg)
  1804. -- | Perform validation checks (module file existence checks and module
  1805. -- reexport checks) on the @exposed-modules@ field.
  1806. checkExposedModules :: PackageDBStack -> InstalledPackageInfo -> Validate ()
  1807. checkExposedModules db_stack pkg =
  1808. mapM_ checkExposedModule (exposedModules pkg)
  1809. where
  1810. checkExposedModule (ExposedModule modl reexport) = do
  1811. let checkOriginal = checkModuleFile pkg modl
  1812. checkReexport = checkModule "module reexport" db_stack pkg
  1813. maybe checkOriginal checkReexport reexport
  1814. -- | Validates the existence of an appropriate @hi@ file associated with
  1815. -- a module. Used for both @hidden-modules@ and @exposed-modules@ which
  1816. -- are not reexports.
  1817. checkModuleFile :: InstalledPackageInfo -> ModuleName -> Validate ()
  1818. checkModuleFile pkg modl =
  1819. -- there's no interface file for GHC.Prim
  1820. unless (modl == ModuleName.fromString "GHC.Prim") $ do
  1821. let files = [ ModuleName.toFilePath modl <.> extension
  1822. | extension <- ["hi", "p_hi", "dyn_hi" ] ]
  1823. b <- liftIO $ doesFileExistOnPath files (importDirs pkg)
  1824. when (not b) $
  1825. verror ForceFiles ("cannot find any of " ++ show files)
  1826. -- | Validates that @exposed-modules@ and @hidden-modules@ do not have duplicate
  1827. -- entries.
  1828. -- ToDo: this needs updating for signatures: signatures can validly show up
  1829. -- multiple times in the @exposed-modules@ list as long as their backing
  1830. -- implementations agree.
  1831. checkDuplicateModules :: InstalledPackageInfo -> Validate ()
  1832. checkDuplicateModules pkg
  1833. | null dups = return ()
  1834. | otherwise = verror ForceAll ("package has duplicate modules: " ++
  1835. unwords (map display dups))
  1836. where
  1837. dups = [ m | (m:_:_) <- group (sort mods) ]
  1838. mods = map exposedName (exposedModules pkg) ++ hiddenModules pkg
  1839. -- | Validates an original module entry, either the origin of a module reexport
  1840. -- or the backing implementation of a signature, by checking that it exists,
  1841. -- really is an original definition, and is accessible from the dependencies of
  1842. -- the package.
  1843. -- ToDo: If the original module in question is a backing signature
  1844. -- implementation, then we should also check that the original module in
  1845. -- question is NOT a signature (however, if it is a reexport, then it's fine
  1846. -- for the original module to be a signature.)
  1847. checkModule :: String
  1848. -> PackageDBStack
  1849. -> InstalledPackageInfo
  1850. -> OpenModule
  1851. -> Validate ()
  1852. checkModule _ _ _ (OpenModuleVar _) = error "Impermissible reexport"
  1853. checkModule field_name db_stack pkg
  1854. (OpenModule (DefiniteUnitId def_uid) definingModule) =
  1855. let definingPkgId = unDefUnitId def_uid
  1856. mpkg = if definingPkgId == installedUnitId pkg
  1857. then Just pkg
  1858. else PackageIndex.lookupUnitId ipix definingPkgId
  1859. in case mpkg of
  1860. Nothing
  1861. -> verror ForceAll (field_name ++ " refers to a non-existent " ++
  1862. "defining package: " ++
  1863. display definingPkgId)
  1864. Just definingPkg
  1865. | not (isIndirectDependency definingPkgId)
  1866. -> verror ForceAll (field_name ++ " refers to a defining " ++
  1867. "package that is not a direct (or indirect) " ++
  1868. "dependency of this package: " ++
  1869. display definingPkgId)
  1870. | otherwise
  1871. -> case find ((==definingModule).exposedName)
  1872. (exposedModules definingPkg) of
  1873. Nothing ->
  1874. verror ForceAll (field_name ++ " refers to a module " ++
  1875. display definingModule ++ " " ++
  1876. "that is not exposed in the " ++
  1877. "defining package " ++ display definingPkgId)
  1878. Just (ExposedModule {exposedReexport = Just _} ) ->
  1879. verror ForceAll (field_name ++ " refers to a module " ++
  1880. display definingModule ++ " " ++
  1881. "that is reexported but not defined in the " ++
  1882. "defining package " ++ display definingPkgId)
  1883. _ -> return ()
  1884. where
  1885. all_pkgs = allPackagesInStack db_stack
  1886. ipix = PackageIndex.fromList all_pkgs
  1887. isIndirectDependency pkgid = fromMaybe False $ do
  1888. thispkg <- graphVertex (installedUnitId pkg)
  1889. otherpkg <- graphVertex pkgid
  1890. return (Graph.path depgraph thispkg otherpkg)
  1891. (depgraph, _, graphVertex) =
  1892. PackageIndex.dependencyGraph (PackageIndex.insert pkg ipix)
  1893. checkModule _ _ _ (OpenModule (IndefFullUnitId _ _) _) =
  1894. -- TODO: add some checks here
  1895. return ()
  1896. -- ---------------------------------------------------------------------------
  1897. -- expanding environment variables in the package configuration
  1898. expandEnvVars :: String -> Force -> IO String
  1899. expandEnvVars str0 force = go str0 ""
  1900. where
  1901. go "" acc = return $! reverse acc
  1902. go ('$':'{':str) acc | (var, '}':rest) <- break close str
  1903. = do value <- lookupEnvVar var
  1904. go rest (reverse value ++ acc)
  1905. where close c = c == '}' || c == '\n' -- don't span newlines
  1906. go (c:str) acc
  1907. = go str (c:acc)
  1908. lookupEnvVar :: String -> IO String
  1909. lookupEnvVar "pkgroot" = return "${pkgroot}" -- these two are special,
  1910. lookupEnvVar "pkgrooturl" = return "${pkgrooturl}" -- we don't expand them
  1911. lookupEnvVar nm =
  1912. catchIO (System.Environment.getEnv nm)
  1913. (\ _ -> do dieOrForceAll force ("Unable to expand variable " ++
  1914. show nm)
  1915. return "")
  1916. -----------------------------------------------------------------------------
  1917. getProgramName :: IO String
  1918. getProgramName = liftM (`withoutSuffix` ".bin") getProgName
  1919. where str `withoutSuffix` suff
  1920. | suff `isSuffixOf` str = take (length str - length suff) str
  1921. | otherwise = str
  1922. bye :: String -> IO a
  1923. bye s = putStr s >> exitWith ExitSuccess
  1924. die :: String -> IO a
  1925. die = dieWith 1
  1926. dieWith :: Int -> String -> IO a
  1927. dieWith ec s = do
  1928. prog <- getProgramName
  1929. reportError (prog ++ ": " ++ s)
  1930. exitWith (ExitFailure ec)
  1931. dieOrForceAll :: Force -> String -> IO ()
  1932. dieOrForceAll ForceAll s = ignoreError s
  1933. dieOrForceAll _other s = dieForcible s
  1934. warn :: String -> IO ()
  1935. warn = reportError
  1936. -- send info messages to stdout
  1937. infoLn :: String -> IO ()
  1938. infoLn = putStrLn
  1939. info :: String -> IO ()
  1940. info = putStr
  1941. ignoreError :: String -> IO ()
  1942. ignoreError s = reportError (s ++ " (ignoring)")
  1943. reportError :: String -> IO ()
  1944. reportError s = do hFlush stdout; hPutStrLn stderr s
  1945. dieForcible :: String -> IO ()
  1946. dieForcible s = die (s ++ " (use --force to override)")
  1947. -----------------------------------------
  1948. -- Adapted from ghc/compiler/utils/Panic
  1949. installSignalHandlers :: IO ()
  1950. installSignalHandlers = do
  1951. threadid <- myThreadId
  1952. let
  1953. interrupt = Exception.throwTo threadid
  1954. (Exception.ErrorCall "interrupted")
  1955. --
  1956. #if !defined(mingw32_HOST_OS)
  1957. _ <- installHandler sigQUIT (Catch interrupt) Nothing
  1958. _ <- installHandler sigINT (Catch interrupt) Nothing
  1959. return ()
  1960. #else
  1961. -- GHC 6.3+ has support for console events on Windows
  1962. -- NOTE: running GHCi under a bash shell for some reason requires
  1963. -- you to press Ctrl-Break rather than Ctrl-C to provoke
  1964. -- an interrupt. Ctrl-C is getting blocked somewhere, I don't know
  1965. -- why --SDM 17/12/2004
  1966. let sig_handler ControlC = interrupt
  1967. sig_handler Break = interrupt
  1968. sig_handler _ = return ()
  1969. _ <- installHandler (Catch sig_handler)
  1970. return ()
  1971. #endif
  1972. catchIO :: IO a -> (Exception.IOException -> IO a) -> IO a
  1973. catchIO = catchException
  1974. tryIO :: IO a -> IO (Either Exception.IOException a)
  1975. tryIO = Exception.try
  1976. -- removeFileSave doesn't throw an exceptions, if the file is already deleted
  1977. removeFileSafe :: FilePath -> IO ()
  1978. removeFileSafe fn =
  1979. removeFile fn `catchIO` \ e ->
  1980. when (not $ isDoesNotExistError e) $ ioError e
  1981. -- | Turn a path relative to the current directory into a (normalised)
  1982. -- absolute path.
  1983. absolutePath :: FilePath -> IO FilePath
  1984. absolutePath path = return . normalise . (</> path) =<< getCurrentDirectory