Skip to content

Commit

Permalink
Merge pull request #35 from RyanGlScott/cabal-1
Browse files Browse the repository at this point in the history
Allow building with Cabal-1.23
  • Loading branch information
kazu-yamamoto committed Jan 15, 2016
2 parents f9dfb65 + cf040f8 commit 6daef55
Show file tree
Hide file tree
Showing 4 changed files with 57 additions and 12 deletions.
14 changes: 9 additions & 5 deletions Distribution/Cab/PkgDB.hs
Expand Up @@ -21,12 +21,12 @@ module Distribution.Cab.PkgDB (
, verOfPkgInfo
) where

import Distribution.Cab.Utils (fromDotted)
import Distribution.Cab.Utils (fromDotted, installedComponentId)
import Distribution.Cab.Version
import Distribution.Cab.VerDB (PkgName)
import Distribution.Version (Version(..))
import Distribution.InstalledPackageInfo
(InstalledPackageInfo_(..), InstalledPackageInfo)
(InstalledPackageInfo, sourcePackageId)
import Distribution.Package (PackageName(..), PackageIdentifier(..))
import Distribution.Simple.Compiler (PackageDB(..))
import Distribution.Simple.GHC (configure, getInstalledPackages, getPackageDBContents)
Expand Down Expand Up @@ -74,8 +74,12 @@ toUserSpec (Just path) = SpecificPackageDB path

getDBs :: [PackageDB] -> IO PkgDB
getDBs specs = do
(_,_,pro) <- configure normal Nothing Nothing defaultProgramDb
getInstalledPackages normal specs pro
(_comp,_,pro) <- configure normal Nothing Nothing defaultProgramDb
getInstalledPackages normal
#if MIN_VERSION_Cabal(1,23,0)
comp
#endif
specs pro

getDB :: PackageDB -> IO PkgDB
getDB spec = do
Expand Down Expand Up @@ -132,5 +136,5 @@ verOfPkgInfo = version . pkgVersion . sourcePackageId
topSortedPkgs :: PkgInfo -> PkgDB -> [PkgInfo]
topSortedPkgs pkgi db = topSort $ pkgids [pkgi]
where
pkgids = map installedPackageId
pkgids = map installedComponentId
topSort = topologicalOrder . fromList . reverseDependencyClosure db
14 changes: 8 additions & 6 deletions Distribution/Cab/Printer.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
module Distribution.Cab.Printer (
printDeps
, printRevDeps
Expand All @@ -11,10 +12,11 @@ import Data.Map (Map)
import qualified Data.Map as M
import Distribution.Cab.PkgDB
import Distribution.Cab.Version
import Distribution.InstalledPackageInfo (InstalledPackageInfo_(..))
import Distribution.Cab.Utils (installedComponentId, lookupComponentId)
import Distribution.InstalledPackageInfo (author, depends, license)
import Distribution.License (License(..))
import Distribution.Package (InstalledPackageId)
import Distribution.Simple.PackageIndex (lookupInstalledPackageId, allPackages)
import Distribution.Simple.PackageIndex (allPackages)

----------------------------------------------------------------

Expand All @@ -25,7 +27,7 @@ makeRevDepDB db = M.fromList revdeps
where
pkgs = allPackages db
deps = map idDeps pkgs
idDeps pkg = (installedPackageId pkg, depends pkg)
idDeps pkg = (installedComponentId pkg, depends pkg)
kvs = sort $ concatMap decomp deps
decomp (k,vs) = map (\v -> (v,k)) vs
kvss = groupBy ((==) `on` fst) kvs
Expand All @@ -38,7 +40,7 @@ printDeps :: Bool -> Bool -> PkgDB -> Int -> PkgInfo -> IO ()
printDeps rec info db n pkgi = mapM_ (printDep rec info db n) $ depends pkgi

printDep :: Bool -> Bool -> PkgDB -> Int -> InstalledPackageId -> IO ()
printDep rec info db n pid = case lookupInstalledPackageId db pid of
printDep rec info db n pid = case lookupComponentId db pid of
Nothing -> return ()
Just pkgi -> do
putStr $ prefix ++ fullNameOfPkgInfo pkgi
Expand All @@ -60,10 +62,10 @@ printRevDeps' rec info db revdb n pkgi = case M.lookup pkgid revdb of
Nothing -> return ()
Just pkgids -> mapM_ (printRevDep' rec info db revdb n) pkgids
where
pkgid = installedPackageId pkgi
pkgid = installedComponentId pkgi

printRevDep' :: Bool -> Bool -> PkgDB -> RevDB -> Int -> InstalledPackageId -> IO ()
printRevDep' rec info db revdb n pid = case lookupInstalledPackageId db pid of
printRevDep' rec info db revdb n pid = case lookupComponentId db pid of
Nothing -> return ()
Just pkgi -> do
putStr $ prefix ++ fullNameOfPkgInfo pkgi
Expand Down
39 changes: 39 additions & 0 deletions Distribution/Cab/Utils.hs
@@ -1,7 +1,27 @@
{-# LANGUAGE CPP #-}
module Distribution.Cab.Utils where

import Data.List

import Distribution.InstalledPackageInfo (InstalledPackageInfo)
#if MIN_VERSION_Cabal(1,21,0) && !(MIN_VERSION_Cabal(1,23,0))
import Distribution.Package (PackageInstalled)
#endif
import Distribution.Simple.PackageIndex (PackageIndex)
#if MIN_VERSION_Cabal(1,23,0)
import qualified Distribution.InstalledPackageInfo as Cabal
(installedComponentId)
import Distribution.Package (ComponentId)
import qualified Distribution.Simple.PackageIndex as Cabal
(lookupComponentId)
#else
import qualified Distribution.InstalledPackageInfo as Cabal
(installedPackageId)
import Distribution.Package (InstalledPackageId)
import qualified Distribution.Simple.PackageIndex as Cabal
(lookupInstalledPackageId)
#endif

-- |
-- >>> fromDotted "1.2.3"
-- [1,2,3]
Expand All @@ -16,3 +36,22 @@ fromDotted xs = case break (=='.') xs of
-- "1.2.3"
toDotted :: [Int] -> String
toDotted = intercalate "." . map show

#if MIN_VERSION_Cabal(1,23,0)
installedComponentId :: InstalledPackageInfo -> ComponentId
installedComponentId = Cabal.installedComponentId
#else
installedComponentId :: InstalledPackageInfo -> InstalledPackageId
installedComponentId = Cabal.installedPackageId
#endif

#if MIN_VERSION_Cabal(1,23,0)
lookupComponentId :: PackageIndex a -> ComponentId -> Maybe a
lookupComponentId = Cabal.lookupComponentId
#elif MIN_VERSION_Cabal(1,21,0)
lookupComponentId :: PackageInstalled a => PackageIndex a -> InstalledPackageId -> Maybe a
lookupComponentId = Cabal.lookupInstalledPackageId
#else
lookupComponentId :: PackageIndex -> InstalledPackageId -> Maybe InstalledPackageInfo
lookupComponentId = Cabal.lookupInstalledPackageId
#endif
2 changes: 1 addition & 1 deletion cab.cabal
Expand Up @@ -21,7 +21,7 @@ Library
Default-Language: Haskell2010
GHC-Options: -Wall
Build-Depends: base >= 4.0 && < 5
, Cabal >= 1.18 && < 1.23
, Cabal >= 1.18 && < 1.25
, attoparsec >= 0.10
, bytestring
, conduit >= 1.1
Expand Down

0 comments on commit 6daef55

Please sign in to comment.