Skip to content
Snippets Groups Projects
Commit 3670d9c2 authored by Ben Gamari's avatar Ben Gamari :turtle:
Browse files

ci: Probe boot packages from package db

parent 96d81f4d
No related branches found
No related tags found
No related merge requests found
...@@ -7,6 +7,7 @@ import Control.Monad ...@@ -7,6 +7,7 @@ import Control.Monad
import Options.Applicative import Options.Applicative
import qualified TestPatches import qualified TestPatches
import qualified MakeConstraints import qualified MakeConstraints
import System.FilePath
mode :: Parser (IO ()) mode :: Parser (IO ())
mode = hsubparser $ mconcat mode = hsubparser $ mconcat
...@@ -16,8 +17,13 @@ mode = hsubparser $ mconcat ...@@ -16,8 +17,13 @@ mode = hsubparser $ mconcat
where where
testPatches = TestPatches.testPatches <$> TestPatches.config testPatches = TestPatches.testPatches <$> TestPatches.config
makeConstraints = makeConstraints =
(MakeConstraints.makeConstraints >=> print) f
<$> argument str (metavar "DIR" <> help "patches directory") <$> option str (short 'w' <> long "with-compiler" <> metavar "GHC" <> help "ghc path")
<*> argument str (metavar "DIR" <> help "patches directory")
f ghcPath patchesDir = do
let ghcPkgPath = replaceFileName ghcPath "ghc-pkg"
MakeConstraints.makeConstraints patchesDir ghcPkgPath >>= print
main :: IO () main :: IO ()
main = do main = do
......
...@@ -5,7 +5,9 @@ module MakeConstraints where ...@@ -5,7 +5,9 @@ module MakeConstraints where
import qualified Distribution.Package as Cabal import qualified Distribution.Package as Cabal
import Distribution.Text import Distribution.Text
import Distribution.Types.Version hiding (showVersion) import Distribution.Types.Version hiding (showVersion)
import System.Process.Typed
import qualified Data.ByteString.Lazy.Char8 as BS
import qualified Data.Set as S import qualified Data.Set as S
import qualified Data.Map.Strict as M import qualified Data.Map.Strict as M
...@@ -27,26 +29,11 @@ extraConstraints = [ ...@@ -27,26 +29,11 @@ extraConstraints = [
-- These packages we must use the installed version, because there's no way to upgrade -- These packages we must use the installed version, because there's no way to upgrade
-- them -- them
bootPkgs :: S.Set Cabal.PackageName getBootPkgs :: FilePath
bootPkgs = S.fromList -> IO (S.Set Cabal.PackageName)
[ "base" getBootPkgs ghcPkgPath = do
, "template-haskell" out <- readProcessStdout_ $ proc ghcPkgPath ["list", "--global", "--names-only", "--simple-output"]
, "ghc" return $ S.fromList $ map Cabal.mkPackageName $ words $ BS.unpack out
, "ghc-prim"
, "integer-gmp"
, "ghc-bignum"
]
-- These packages are installed, but we can install newer versions if the build plan
-- allows.. so we --allow-newer them in order to help find more build plans.
allowNewerPkgs :: S.Set Cabal.PackageName
allowNewerPkgs = S.fromList
[ "time"
, "binary"
, "bytestring"
, "Cabal"
, "deepseq"
, "text" ] `S.union` bootPkgs
constraints :: [String] -> Doc constraints :: [String] -> Doc
constraints constraints = constraints constraints =
...@@ -94,12 +81,15 @@ versionConstraints pkgs = ...@@ -94,12 +81,15 @@ versionConstraints pkgs =
] ]
makeConstraints :: FilePath -- ^ patch directory makeConstraints :: FilePath -- ^ patch directory
-> FilePath -- ^ @ghc-pkg@ path
-> IO Doc -> IO Doc
makeConstraints patchDir = do makeConstraints patchDir ghcPkgPath = do
bootPkgs <- getBootPkgs ghcPkgPath
putStrLn $ "Boot packages: " <> show bootPkgs
patches <- findPatchedPackages patchDir patches <- findPatchedPackages patchDir
let patchedPkgs = S.fromList $ map fst patches let patchedPkgs = S.fromList $ map fst patches
doc = PP.vcat doc = PP.vcat
[ allowNewer allowNewerPkgs [ allowNewer bootPkgs
, "" , ""
, installedConstraints bootPkgs patchedPkgs , installedConstraints bootPkgs patchedPkgs
, "" , ""
......
...@@ -76,6 +76,9 @@ data Config = Config { configPatchDir :: FilePath ...@@ -76,6 +76,9 @@ data Config = Config { configPatchDir :: FilePath
, configBuildToolPkgs :: BuildToolPackages , configBuildToolPkgs :: BuildToolPackages
} }
configGhcPkg :: Config -> FilePath
configGhcPkg cfg = replaceFileName (configCompiler cfg) "ghc-pkg"
cabalOptions :: Config -> [String] cabalOptions :: Config -> [String]
cabalOptions cfg = cabalOptions cfg =
let let
...@@ -510,7 +513,7 @@ setup cfg = do ...@@ -510,7 +513,7 @@ setup cfg = do
$ proc "build-repo.sh" ["build-repository-blurb"] $ proc "build-repo.sh" ["build-repository-blurb"]
extraFragments <- mapM readFile (configExtraCabalFragments cfg) extraFragments <- mapM readFile (configExtraCabalFragments cfg)
constraints <- MakeConstraints.makeConstraints (configPatchDir cfg) constraints <- MakeConstraints.makeConstraints (configPatchDir cfg) (configGhcPkg cfg)
appendFile "cabal.project" $ show $ vcat $ appendFile "cabal.project" $ show $ vcat $
[ "with-compiler: " <> PP.text (configCompiler cfg) [ "with-compiler: " <> PP.text (configCompiler cfg)
, constraints , constraints
......
...@@ -160,7 +160,7 @@ EOF ...@@ -160,7 +160,7 @@ EOF
} }
build_constraints() { build_constraints() {
head-hackage-ci make-constraints $PATCHES head-hackage-ci make-constraints -w "$GHC" "$PATCHES"
} }
# Build the hackage repository # Build the hackage repository
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment