PageRenderTime 96ms CodeModel.GetById 20ms RepoModel.GetById 1ms app.codeStats 0ms

/packages/cabal-install-0.8.2/Distribution/Client/IndexUtils.hs

https://github.com/Lainepress/hp-2010.2.0.0
Haskell | 300 lines | 216 code | 24 blank | 60 comment | 9 complexity | 4bf99932655a251e0cddac4cc0769b65 MD5 | raw file
  1. -----------------------------------------------------------------------------
  2. -- |
  3. -- Module : Distribution.Client.IndexUtils
  4. -- Copyright : (c) Duncan Coutts 2008
  5. -- License : BSD-like
  6. --
  7. -- Maintainer : duncan@haskell.org
  8. -- Stability : provisional
  9. -- Portability : portable
  10. --
  11. -- Extra utils related to the package indexes.
  12. -----------------------------------------------------------------------------
  13. module Distribution.Client.IndexUtils (
  14. getInstalledPackages,
  15. getAvailablePackages,
  16. readPackageIndexFile,
  17. parseRepoIndex,
  18. disambiguatePackageName,
  19. disambiguateDependencies
  20. ) where
  21. import qualified Distribution.Client.Tar as Tar
  22. import Distribution.Client.Types
  23. ( UnresolvedDependency(..), AvailablePackage(..)
  24. , AvailablePackageSource(..), Repo(..), RemoteRepo(..)
  25. , AvailablePackageDb(..), InstalledPackage(..) )
  26. import Distribution.Package
  27. ( PackageId, PackageIdentifier(..), PackageName(..), Package(..)
  28. , Dependency(Dependency), InstalledPackageId(..) )
  29. import Distribution.Client.PackageIndex (PackageIndex)
  30. import qualified Distribution.Client.PackageIndex as PackageIndex
  31. import qualified Distribution.Simple.PackageIndex as InstalledPackageIndex
  32. import qualified Distribution.InstalledPackageInfo as InstalledPackageInfo
  33. import Distribution.PackageDescription
  34. ( GenericPackageDescription )
  35. import Distribution.PackageDescription.Parse
  36. ( parsePackageDescription )
  37. import Distribution.Simple.Compiler
  38. ( Compiler, PackageDBStack )
  39. import Distribution.Simple.Program
  40. ( ProgramConfiguration )
  41. import qualified Distribution.Simple.Configure as Configure
  42. ( getInstalledPackages )
  43. import Distribution.ParseUtils
  44. ( ParseResult(..) )
  45. import Distribution.Version
  46. ( Version(Version), intersectVersionRanges )
  47. import Distribution.Text
  48. ( display, simpleParse )
  49. import Distribution.Verbosity (Verbosity)
  50. import Distribution.Simple.Utils (die, warn, info, intercalate, fromUTF8)
  51. import Data.Maybe (catMaybes, fromMaybe)
  52. import Data.List (isPrefixOf)
  53. import Data.Monoid (Monoid(..))
  54. import qualified Data.Map as Map
  55. import Control.Monad (MonadPlus(mplus), when)
  56. import Control.Exception (evaluate)
  57. import qualified Data.ByteString.Lazy as BS
  58. import qualified Data.ByteString.Lazy.Char8 as BS.Char8
  59. import Data.ByteString.Lazy (ByteString)
  60. import qualified Codec.Compression.GZip as GZip (decompress)
  61. import System.FilePath ((</>), takeExtension, splitDirectories, normalise)
  62. import System.FilePath.Posix as FilePath.Posix
  63. ( takeFileName )
  64. import System.IO.Error (isDoesNotExistError)
  65. import System.Directory
  66. ( getModificationTime )
  67. import System.Time
  68. ( getClockTime, diffClockTimes, normalizeTimeDiff, TimeDiff(tdDay) )
  69. getInstalledPackages :: Verbosity -> Compiler
  70. -> PackageDBStack -> ProgramConfiguration
  71. -> IO (Maybe (PackageIndex InstalledPackage))
  72. getInstalledPackages verbosity comp packageDbs conf =
  73. fmap (fmap convert)
  74. (Configure.getInstalledPackages verbosity comp packageDbs conf)
  75. where
  76. convert :: InstalledPackageIndex.PackageIndex -> PackageIndex InstalledPackage
  77. convert index = PackageIndex.fromList $
  78. reverse -- because later ones mask earlier ones, but
  79. -- InstalledPackageIndex.allPackages gives us the most preferred
  80. -- instances first, when packages share a package id, like when
  81. -- the same package is installed in the global & user dbs.
  82. [ InstalledPackage ipkg (sourceDeps index ipkg)
  83. | ipkg <- InstalledPackageIndex.allPackages index ]
  84. -- The InstalledPackageInfo only lists dependencies by the
  85. -- InstalledPackageId, which means we do not directly know the corresponding
  86. -- source dependency. The only way to find out is to lookup the
  87. -- InstalledPackageId to get the InstalledPackageInfo and look at its
  88. -- source PackageId. But if the package is broken because it depends on
  89. -- other packages that do not exist then we have a problem we cannot find
  90. -- the original source package id. Instead we make up a bogus package id.
  91. -- This should have the same effect since it should be a dependency on a
  92. -- non-existant package.
  93. sourceDeps index ipkg =
  94. [ maybe (brokenPackageId depid) packageId mdep
  95. | let depids = InstalledPackageInfo.depends ipkg
  96. getpkg = InstalledPackageIndex.lookupInstalledPackageId index
  97. , (depid, mdep) <- zip depids (map getpkg depids) ]
  98. brokenPackageId (InstalledPackageId str) =
  99. PackageIdentifier (PackageName (str ++ "-broken")) (Version [] [])
  100. -- | Read a repository index from disk, from the local files specified by
  101. -- a list of 'Repo's.
  102. --
  103. -- All the 'AvailablePackage's are marked as having come from the appropriate
  104. -- 'Repo'.
  105. --
  106. -- This is a higher level wrapper used internally in cabal-install.
  107. --
  108. getAvailablePackages :: Verbosity -> [Repo] -> IO AvailablePackageDb
  109. getAvailablePackages verbosity [] = do
  110. warn verbosity $ "No remote package servers have been specified. Usually "
  111. ++ "you would have one specified in the config file."
  112. return AvailablePackageDb {
  113. packageIndex = mempty,
  114. packagePreferences = mempty
  115. }
  116. getAvailablePackages verbosity repos = do
  117. info verbosity "Reading available packages..."
  118. pkgss <- mapM (readRepoIndex verbosity) repos
  119. let (pkgs, prefs) = mconcat pkgss
  120. prefs' = Map.fromListWith intersectVersionRanges
  121. [ (name, range) | Dependency name range <- prefs ]
  122. _ <- evaluate pkgs
  123. _ <- evaluate prefs'
  124. return AvailablePackageDb {
  125. packageIndex = pkgs,
  126. packagePreferences = prefs'
  127. }
  128. -- | Read a repository index from disk, from the local file specified by
  129. -- the 'Repo'.
  130. --
  131. -- All the 'AvailablePackage's are marked as having come from the given 'Repo'.
  132. --
  133. -- This is a higher level wrapper used internally in cabal-install.
  134. --
  135. readRepoIndex :: Verbosity -> Repo
  136. -> IO (PackageIndex AvailablePackage, [Dependency])
  137. readRepoIndex verbosity repo = handleNotFound $ do
  138. let indexFile = repoLocalDir repo </> "00-index.tar"
  139. (pkgs, prefs) <- either fail return
  140. . foldlTarball extract ([], [])
  141. =<< BS.readFile indexFile
  142. pkgIndex <- evaluate $ PackageIndex.fromList
  143. [ AvailablePackage {
  144. packageInfoId = pkgid,
  145. packageDescription = pkg,
  146. packageSource = RepoTarballPackage repo
  147. }
  148. | (pkgid, pkg) <- pkgs]
  149. warnIfIndexIsOld indexFile
  150. return (pkgIndex, prefs)
  151. where
  152. extract (pkgs, prefs) entry = fromMaybe (pkgs, prefs) $
  153. (do pkg <- extractPkg entry; return (pkg:pkgs, prefs))
  154. `mplus` (do prefs' <- extractPrefs entry; return (pkgs, prefs'++prefs))
  155. extractPrefs :: Tar.Entry -> Maybe [Dependency]
  156. extractPrefs entry = case Tar.entryContent entry of
  157. Tar.NormalFile content _
  158. | takeFileName (Tar.entryPath entry) == "preferred-versions"
  159. -> Just . parsePreferredVersions
  160. . BS.Char8.unpack $ content
  161. _ -> Nothing
  162. handleNotFound action = catch action $ \e -> if isDoesNotExistError e
  163. then do
  164. case repoKind repo of
  165. Left remoteRepo -> warn verbosity $
  166. "The package list for '" ++ remoteRepoName remoteRepo
  167. ++ "' does not exist. Run 'cabal update' to download it."
  168. Right _localRepo -> warn verbosity $
  169. "The package list for the local repo '" ++ repoLocalDir repo
  170. ++ "' is missing. The repo is invalid."
  171. return mempty
  172. else ioError e
  173. isOldThreshold = 15 --days
  174. warnIfIndexIsOld indexFile = do
  175. indexTime <- getModificationTime indexFile
  176. currentTime <- getClockTime
  177. let diff = normalizeTimeDiff (diffClockTimes currentTime indexTime)
  178. when (tdDay diff >= isOldThreshold) $ case repoKind repo of
  179. Left remoteRepo -> warn verbosity $
  180. "The package list for '" ++ remoteRepoName remoteRepo
  181. ++ "' is " ++ show (tdDay diff) ++ " days old.\nRun "
  182. ++ "'cabal update' to get the latest list of available packages."
  183. Right _localRepo -> return ()
  184. parsePreferredVersions :: String -> [Dependency]
  185. parsePreferredVersions = catMaybes
  186. . map simpleParse
  187. . filter (not . isPrefixOf "--")
  188. . lines
  189. -- | Read a compressed \"00-index.tar.gz\" file into a 'PackageIndex'.
  190. --
  191. -- This is supposed to be an \"all in one\" way to easily get at the info in
  192. -- the hackage package index.
  193. --
  194. -- It takes a function to map a 'GenericPackageDescription' into any more
  195. -- specific instance of 'Package' that you might want to use. In the simple
  196. -- case you can just use @\_ p -> p@ here.
  197. --
  198. readPackageIndexFile :: Package pkg
  199. => (PackageId -> GenericPackageDescription -> pkg)
  200. -> FilePath -> IO (PackageIndex pkg)
  201. readPackageIndexFile mkPkg indexFile = do
  202. pkgs <- either fail return
  203. . parseRepoIndex
  204. . GZip.decompress
  205. =<< BS.readFile indexFile
  206. evaluate $ PackageIndex.fromList
  207. [ mkPkg pkgid pkg | (pkgid, pkg) <- pkgs]
  208. -- | Parse an uncompressed \"00-index.tar\" repository index file represented
  209. -- as a 'ByteString'.
  210. --
  211. parseRepoIndex :: ByteString
  212. -> Either String [(PackageId, GenericPackageDescription)]
  213. parseRepoIndex = foldlTarball (\pkgs -> maybe pkgs (:pkgs) . extractPkg) []
  214. extractPkg :: Tar.Entry -> Maybe (PackageId, GenericPackageDescription)
  215. extractPkg entry = case Tar.entryContent entry of
  216. Tar.NormalFile content _
  217. | takeExtension fileName == ".cabal"
  218. -> case splitDirectories (normalise fileName) of
  219. [pkgname,vers,_] -> case simpleParse vers of
  220. Just ver -> Just (pkgid, descr)
  221. where
  222. pkgid = PackageIdentifier (PackageName pkgname) ver
  223. parsed = parsePackageDescription . fromUTF8 . BS.Char8.unpack
  224. $ content
  225. descr = case parsed of
  226. ParseOk _ d -> d
  227. _ -> error $ "Couldn't read cabal file "
  228. ++ show fileName
  229. _ -> Nothing
  230. _ -> Nothing
  231. _ -> Nothing
  232. where
  233. fileName = Tar.entryPath entry
  234. foldlTarball :: (a -> Tar.Entry -> a) -> a
  235. -> ByteString -> Either String a
  236. foldlTarball f z = either Left (Right . foldl f z) . check [] . Tar.read
  237. where
  238. check _ (Tar.Fail err) = Left err
  239. check ok Tar.Done = Right ok
  240. check ok (Tar.Next e es) = check (e:ok) es
  241. -- | Disambiguate a set of packages using 'disambiguatePackage' and report any
  242. -- ambiguities to the user.
  243. --
  244. disambiguateDependencies :: PackageIndex AvailablePackage
  245. -> [UnresolvedDependency]
  246. -> IO [UnresolvedDependency]
  247. disambiguateDependencies index deps = do
  248. let names = [ (name, disambiguatePackageName index name)
  249. | UnresolvedDependency (Dependency name _) _ <- deps ]
  250. in case [ (name, matches) | (name, Right matches) <- names ] of
  251. [] -> return
  252. [ UnresolvedDependency (Dependency name vrange) flags
  253. | (UnresolvedDependency (Dependency _ vrange) flags,
  254. (_, Left name)) <- zip deps names ]
  255. ambigious -> die $ unlines
  256. [ if null matches
  257. then "There is no package named " ++ display name ++ ". "
  258. ++ "Perhaps you need to run 'cabal update' first?"
  259. else "The package name " ++ display name ++ "is ambigious. "
  260. ++ "It could be: " ++ intercalate ", " (map display matches)
  261. | (name, matches) <- ambigious ]
  262. -- | Given an index of known packages and a package name, figure out which one it
  263. -- might be referring to. If there is an exact case-sensitive match then that's
  264. -- ok. If it matches just one package case-insensitively then that's also ok.
  265. -- The only problem is if it matches multiple packages case-insensitively, in
  266. -- that case it is ambigious.
  267. --
  268. disambiguatePackageName :: PackageIndex AvailablePackage
  269. -> PackageName
  270. -> Either PackageName [PackageName]
  271. disambiguatePackageName index (PackageName name) =
  272. case PackageIndex.searchByName index name of
  273. PackageIndex.None -> Right []
  274. PackageIndex.Unambiguous pkgs -> Left (pkgName (packageId (head pkgs)))
  275. PackageIndex.Ambiguous pkgss -> Right [ pkgName (packageId pkg)
  276. | (pkg:_) <- pkgss ]