aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorDaniel Gröber <dxld@darkboxed.org>2015-10-30 19:44:42 +0100
committerDaniel Gröber <dxld@darkboxed.org>2015-10-30 19:44:42 +0100
commit103d5e6dabf8975c3903f62afd0418801778cd71 (patch)
tree02bb362914ef298d04dc7fd81119e177fd7c4575
parent4ffd00b5755da6a5c6f05f2f636d1900a35b83cd (diff)
Catch up with Cabal-1.23 git
-rw-r--r--CabalHelper/Licenses.hs86
-rw-r--r--CabalHelper/Main.hs18
2 files changed, 61 insertions, 43 deletions
diff --git a/CabalHelper/Licenses.hs b/CabalHelper/Licenses.hs
index e237e58..d1258c7 100644
--- a/CabalHelper/Licenses.hs
+++ b/CabalHelper/Licenses.hs
@@ -4,80 +4,86 @@ module CabalHelper.Licenses where
-- Copyright (c) 2014, Jasper Van der Jeugt <m@jaspervdj.be>
--------------------------------------------------------------------------------
-import Control.Arrow ((***), (&&&))
-import Control.Monad (forM_, unless)
-import Data.List (foldl', sort)
-import Data.Maybe (catMaybes)
-import Data.Version (Version)
-import Data.Set (Set)
-import qualified Data.Set as Set
-import Distribution.InstalledPackageInfo (InstalledPackageInfo)
-import qualified Distribution.InstalledPackageInfo as InstalledPackageInfo
-import qualified Distribution.License as Cabal
-import qualified Distribution.Package as Cabal
-import qualified Distribution.Simple.Configure as Cabal
-import qualified Distribution.Simple.LocalBuildInfo as Cabal
-import qualified Distribution.Simple.PackageIndex as Cabal
-import qualified Distribution.Text as Cabal
-import System.Directory (getDirectoryContents)
-import System.Exit (exitFailure)
-import System.FilePath (takeExtension)
-import System.IO (hPutStrLn, stderr)
+import Control.Arrow ((***), (&&&))
+import Control.Monad (forM_, unless)
+import Data.List (foldl', sort)
+import Data.Maybe (catMaybes)
+import Data.Version (Version)
+import Data.Set (Set)
+import qualified Data.Set as Set
+import System.Directory (getDirectoryContents)
+import System.Exit (exitFailure)
+import System.FilePath (takeExtension)
+import System.IO (hPutStrLn, stderr)
+import Distribution.InstalledPackageInfo
+import Distribution.InstalledPackageInfo
+import Distribution.License
+import Distribution.Package
+import Distribution.Simple.Configure
+import Distribution.Simple.LocalBuildInfo
+import Distribution.Simple.PackageIndex
+import Distribution.Text
--------------------------------------------------------------------------------
#if CABAL_MAJOR == 1 && CABAL_MINOR > 22
-type PackageIndex a = Cabal.PackageIndex (InstalledPackageInfo.InstalledPackageInfo)
+type CPackageIndex a = PackageIndex (InstalledPackageInfo)
#elif CABAL_MAJOR == 1 && CABAL_MINOR >= 22
-type PackageIndex a = Cabal.PackageIndex (InstalledPackageInfo.InstalledPackageInfo_ a)
+type CPackageIndex a = PackageIndex (InstalledPackageInfo_ a)
#else
-type PackageIndex a = Cabal.PackageIndex
+type CPackageIndex a = PackageIndex
#endif
+#if CABAL_MAJOR == 1 && CABAL_MINOR > 22
+type CInstalledPackageId = ComponentId
+lookupInstalledPackageId = lookupComponentId
+#endif
+
+
+
findTransitiveDependencies
- :: PackageIndex a
- -> Set Cabal.InstalledPackageId
- -> Set Cabal.InstalledPackageId
+ :: CPackageIndex a
+ -> Set CInstalledPackageId
+ -> Set CInstalledPackageId
findTransitiveDependencies pkgIdx set0 = go Set.empty (Set.toList set0)
where
go set [] = set
go set (q : queue)
| q `Set.member` set = go set queue
| otherwise =
- case Cabal.lookupInstalledPackageId pkgIdx q of
+ case lookupInstalledPackageId pkgIdx q of
Nothing ->
-- Not found can mean that the package still needs to be
-- installed (e.g. a component of the target cabal package).
-- We can ignore those.
go set queue
Just ipi ->
- go (Set.insert q set)
- (InstalledPackageInfo.depends ipi ++ queue)
+ go (Set.insert q set) (depends ipi ++ queue)
--------------------------------------------------------------------------------
getDependencyInstalledPackageIds
- :: Cabal.LocalBuildInfo -> Set Cabal.InstalledPackageId
+ :: LocalBuildInfo -> Set InstalledPackageId
getDependencyInstalledPackageIds lbi =
- findTransitiveDependencies (Cabal.installedPkgs lbi) $
- Set.fromList $ map fst $ Cabal.externalPackageDeps lbi
+ findTransitiveDependencies (installedPkgs lbi) $
+ Set.fromList $ map fst $ externalPackageDeps lbi
--------------------------------------------------------------------------------
getDependencyInstalledPackageInfos
- :: Cabal.LocalBuildInfo -> [InstalledPackageInfo]
+ :: LocalBuildInfo -> [InstalledPackageInfo]
getDependencyInstalledPackageInfos lbi = catMaybes $
- map (Cabal.lookupInstalledPackageId pkgIdx) $
+ map (lookupInstalledPackageId pkgIdx) $
Set.toList (getDependencyInstalledPackageIds lbi)
where
- pkgIdx = Cabal.installedPkgs lbi
+ pkgIdx = installedPkgs lbi
--------------------------------------------------------------------------------
groupByLicense
:: [InstalledPackageInfo]
- -> [(Cabal.License, [InstalledPackageInfo])]
+ -> [(License, [InstalledPackageInfo])]
groupByLicense = foldl'
- (\assoc ipi -> insert (InstalledPackageInfo.license ipi) ipi assoc) []
+ (\assoc ipi -> insert (license ipi) ipi assoc) []
where
-- 'Cabal.License' doesn't have an 'Ord' instance so we need to use an
-- association list instead of 'Map'. The number of licenses probably won't
@@ -91,12 +97,12 @@ groupByLicense = foldl'
--------------------------------------------------------------------------------
displayDependencyLicenseList
- :: [(Cabal.License, [InstalledPackageInfo])]
+ :: [(License, [InstalledPackageInfo])]
-> [(String, [(String, Version)])]
displayDependencyLicenseList =
- map (Cabal.display *** map (getName &&& getVersion))
+ map (display *** map (getName &&& getVersion))
where
getName =
- Cabal.display . Cabal.pkgName . InstalledPackageInfo.sourcePackageId
+ display . pkgName . sourcePackageId
getVersion =
- Cabal.pkgVersion . InstalledPackageInfo.sourcePackageId
+ pkgVersion . sourcePackageId
diff --git a/CabalHelper/Main.hs b/CabalHelper/Main.hs
index 59c3e91..2244859 100644
--- a/CabalHelper/Main.hs
+++ b/CabalHelper/Main.hs
@@ -47,8 +47,12 @@ import Distribution.Simple.LocalBuildInfo (LocalBuildInfo(..),
componentBuildInfo,
externalPackageDeps,
withComponentsLBI,
- withLibLBI,
- inplacePackageId)
+ withLibLBI)
+#if CABAL_MAJOR == 1 && CABAL_MINOR <= 22
+import Distribution.Simple.LocalBuildInfo (inplacePackageId)
+#else
+import Distribution.Simple.LocalBuildInfo (localComponentId)
+#endif
import Distribution.Simple.GHC (componentGhcOptions)
import Distribution.Simple.Program.GHC (GhcOptions(..), renderGhcOptions)
@@ -408,7 +412,10 @@ removeInplaceDeps v lbi pd clbi = let
libbi = libBuildInfo lib
liboutdir = componentOutDir lbi (CLib lib)
libopts = (componentGhcOptions normal lbi libbi libclbi liboutdir) {
- ghcOptPackageDBs = []
+ ghcOptPackageDBs = []
+#if CABAL_MAJOR == 1 && CABAL_MINOR > 22
+ , ghcOptComponentId = NoFlag
+#endif
}
(ideps, deps) = partition isInplaceDep (componentPackageDeps clbi)
@@ -419,7 +426,12 @@ removeInplaceDeps v lbi pd clbi = let
where
isInplaceDep :: (InstalledPackageId, PackageId) -> Bool
+#if CABAL_MAJOR == 1 && CABAL_MINOR <= 22
isInplaceDep (ipid, pid) = inplacePackageId pid == ipid
+#else
+ isInplaceDep (ipid, pid) = localComponentId lbi == ipid
+#endif
+
#if CABAL_MAJOR == 1 && CABAL_MINOR >= 22
-- >= 1.22 uses NubListR