PageRenderTime 103ms CodeModel.GetById 37ms 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

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

  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 sam

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