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
1 merge request!327ci: Probe boot packages from package db
Pipeline #84748 failed
......@@ -7,6 +7,7 @@ import Control.Monad
import Options.Applicative
import qualified TestPatches
import qualified MakeConstraints
import System.FilePath
mode :: Parser (IO ())
mode = hsubparser $ mconcat
......@@ -16,8 +17,13 @@ mode = hsubparser $ mconcat
where
testPatches = TestPatches.testPatches <$> TestPatches.config
makeConstraints =
(MakeConstraints.makeConstraints >=> print)
<$> argument str (metavar "DIR" <> help "patches directory")
f
<$> 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 = do
......
......@@ -5,7 +5,9 @@ module MakeConstraints where
import qualified Distribution.Package as Cabal
import Distribution.Text
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.Map.Strict as M
......@@ -27,26 +29,11 @@ extraConstraints = [
-- These packages we must use the installed version, because there's no way to upgrade
-- them
bootPkgs :: S.Set Cabal.PackageName
bootPkgs = S.fromList
[ "base"
, "template-haskell"
, "ghc"
, "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
getBootPkgs :: FilePath
-> IO (S.Set Cabal.PackageName)
getBootPkgs ghcPkgPath = do
out <- readProcessStdout_ $ proc ghcPkgPath ["list", "--global", "--names-only", "--simple-output"]
return $ S.fromList $ map Cabal.mkPackageName $ words $ BS.unpack out
constraints :: [String] -> Doc
constraints constraints =
......@@ -94,12 +81,15 @@ versionConstraints pkgs =
]
makeConstraints :: FilePath -- ^ patch directory
-> FilePath -- ^ @ghc-pkg@ path
-> IO Doc
makeConstraints patchDir = do
makeConstraints patchDir ghcPkgPath = do
bootPkgs <- getBootPkgs ghcPkgPath
putStrLn $ "Boot packages: " <> show bootPkgs
patches <- findPatchedPackages patchDir
let patchedPkgs = S.fromList $ map fst patches
doc = PP.vcat
[ allowNewer allowNewerPkgs
[ allowNewer bootPkgs
, ""
, installedConstraints bootPkgs patchedPkgs
, ""
......
......@@ -76,6 +76,9 @@ data Config = Config { configPatchDir :: FilePath
, configBuildToolPkgs :: BuildToolPackages
}
configGhcPkg :: Config -> FilePath
configGhcPkg cfg = replaceFileName (configCompiler cfg) "ghc-pkg"
cabalOptions :: Config -> [String]
cabalOptions cfg =
let
......@@ -510,7 +513,7 @@ setup cfg = do
$ proc "build-repo.sh" ["build-repository-blurb"]
extraFragments <- mapM readFile (configExtraCabalFragments cfg)
constraints <- MakeConstraints.makeConstraints (configPatchDir cfg)
constraints <- MakeConstraints.makeConstraints (configPatchDir cfg) (configGhcPkg cfg)
appendFile "cabal.project" $ show $ vcat $
[ "with-compiler: " <> PP.text (configCompiler cfg)
, constraints
......
......@@ -160,7 +160,7 @@ EOF
}
build_constraints() {
head-hackage-ci make-constraints $PATCHES
head-hackage-ci make-constraints -w "$GHC" "$PATCHES"
}
# 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