[Git][ghc/ghc][master] Make Hadrian build with Cabal-3.2
Marge Bot
gitlab at gitlab.haskell.org
Thu Apr 2 05:49:30 UTC 2020
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
27740f24 by Ryan Scott at 2020-04-02T01:49:21-04:00
Make Hadrian build with Cabal-3.2
GHC 8.10 ships with `Cabal-3.2.0.0`, so it would be convenient to
make Hadrian supporting building against 3.2.* instead of having to
rebuild the entirety of `Cabal-3.0.0.0`. There is one API change in
`Cabal-3.2.*` that affects Hadrian: the `synopsis` and `description`
functions now return `ShortText` instead of `String`. Since Hadrian
manipulates these `String`s in various places, I found that the
simplest fix was to use CPP to convert `ShortText` to `String`s
where appropriate.
- - - - -
3 changed files:
- hadrian/hadrian.cabal
- hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
- hadrian/src/Rules/Library.hs
Changes:
=====================================
hadrian/hadrian.cabal
=====================================
@@ -133,7 +133,7 @@ executable hadrian
other-extensions: MultiParamTypeClasses
, TypeFamilies
build-depends: base >= 4.8 && < 5
- , Cabal >= 3.0 && < 3.1
+ , Cabal >= 3.0 && < 3.3
, containers >= 0.5 && < 0.7
, directory >= 1.3.1.0 && < 1.4
, extra >= 1.4.7
=====================================
hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
=====================================
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
-- Module : Hadrian.Haskell.Cabal.Parse
@@ -38,6 +39,9 @@ import qualified Distribution.Text as C
import qualified Distribution.Types.LocalBuildInfo as C
import qualified Distribution.Types.CondTree as C
import qualified Distribution.Types.MungedPackageId as C
+#if MIN_VERSION_Cabal(3,2,0)
+import qualified Distribution.Utils.ShortText as C
+#endif
import qualified Distribution.Verbosity as C
import Hadrian.Expression
import Hadrian.Haskell.Cabal
@@ -69,7 +73,10 @@ parsePackageData pkg = do
sorted = sort [ C.unPackageName p | C.Dependency p _ _ <- allDeps ]
deps = nubOrd sorted \\ [name]
depPkgs = catMaybes $ map findPackageByName deps
- return $ PackageData name version (C.synopsis pd) (C.description pd) depPkgs gpd
+ return $ PackageData name version
+ (shortTextToString (C.synopsis pd))
+ (shortTextToString (C.description pd))
+ depPkgs gpd
where
-- Collect an overapproximation of dependencies by ignoring conditionals
collectDeps :: Maybe (C.CondTree v [C.Dependency] a) -> [C.Dependency]
@@ -78,6 +85,14 @@ parsePackageData pkg = do
where
f (C.CondBranch _ t mt) = collectDeps (Just t) ++ collectDeps mt
+#if MIN_VERSION_Cabal(3,2,0)
+ shortTextToString :: C.ShortText -> String
+ shortTextToString = C.fromShortText
+#else
+ shortTextToString :: String -> String
+ shortTextToString = id
+#endif
+
-- | Parse the package identifier from a Cabal file.
parseCabalPkgId :: FilePath -> IO String
parseCabalPkgId file = C.display . C.package . C.packageDescription <$> C.readGenericPackageDescription C.silent file
=====================================
hadrian/src/Rules/Library.hs
=====================================
@@ -140,7 +140,7 @@ extraObjects context
-- | Return all the object files to be put into the library we're building for
-- the given 'Context'.
libraryObjects :: Context -> Action [FilePath]
-libraryObjects context at Context{..} = do
+libraryObjects context = do
hsObjs <- hsObjects context
noHsObjs <- nonHsObjects context
need $ noHsObjs ++ hsObjs
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/27740f24cb70fc14b00c1212c06642a144a6117d
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/27740f24cb70fc14b00c1212c06642a144a6117d
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200402/957ff377/attachment-0001.html>
More information about the ghc-commits
mailing list