PageRenderTime 55ms CodeModel.GetById 13ms RepoModel.GetById 1ms app.codeStats 0ms

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

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