summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--hadrian/src/Rules/Register.hs29
-rw-r--r--hadrian/src/Rules/Test.hs28
-rw-r--r--hadrian/src/Settings/Default.hs13
3 files changed, 36 insertions, 34 deletions
diff --git a/hadrian/src/Rules/Register.hs b/hadrian/src/Rules/Register.hs
index fdb3202afe..51df69f116 100644
--- a/hadrian/src/Rules/Register.hs
+++ b/hadrian/src/Rules/Register.hs
@@ -9,7 +9,6 @@ import Expression ( getContextData )
import Hadrian.BuildPath
import Hadrian.Expression
import Hadrian.Haskell.Cabal
-import Oracles.Setting
import Packages
import Rules.Rts
import {-# SOURCE #-} Rules.Library (needLibrary)
@@ -109,7 +108,7 @@ registerPackageRules rs stage = do
_ -> buildConf rs ctx conf
buildConf :: [(Resource, Int)] -> Context -> FilePath -> Action ()
-buildConf _ context@Context {..} conf = do
+buildConf _ context@Context {..} _conf = do
depPkgIds <- cabalDependencies context
ensureConfigured context
need =<< mapM (\pkgId -> packageDbPath stage <&> (-/- pkgId <.> "conf")) depPkgIds
@@ -137,19 +136,19 @@ buildConf _ context@Context {..} conf = do
Cabal.copyPackage context
Cabal.registerPackage context
- -- The above two steps produce an entry in the package database, with copies
- -- of many of the files we have build, e.g. Haskell interface files. We need
- -- to record this side effect so that Shake can cache these files too.
- -- See why we need 'fixWindows': https://gitlab.haskell.org/ghc/ghc/issues/16073
- let fixWindows path = do
- version <- setting GhcVersion
- hostOs <- cabalOsString <$> setting BuildOs
- hostArch <- cabalArchString <$> setting BuildArch
- let dir = hostArch ++ "-" ++ hostOs ++ "-ghc-" ++ version
- return $ if windowsHost then path -/- "../.." -/- dir else path
- pkgDbPath <- fixWindows =<< packageDbPath stage
- let dir = pkgDbPath -/- takeBaseName conf
- files <- liftIO $ getDirectoryFilesIO "." [dir -/- "**"]
+ -- We declare that this rule also produces files matching:
+ -- - <root>/stage<N>/lib/<arch>-<os>-ghc-<version>/*libHS<pkgid>*
+ -- (for .so files, Cabal's registration mechanism places them there)
+ -- - <root>/stage<N>/lib/<arch>-<os>-ghc-<version>/<pkgid>/**
+ -- (for interface files, static libs, ghci libs, includes, ...)
+ --
+ -- so that if any change ends up modifying a library (but not its .conf
+ -- file), we still rebuild things that depend on it.
+ dir <- (-/-) <$> libPath context <*> distDir stage
+ pkgid <- pkgIdentifier package
+ files <- liftIO $
+ (++) <$> getDirectoryFilesIO "." [dir -/- "*libHS"++pkgid++"*"]
+ <*> getDirectoryFilesIO "." [dir -/- pkgid -/- "**"]
produces files
copyConf :: [(Resource, Int)] -> Context -> FilePath -> Action ()
diff --git a/hadrian/src/Rules/Test.hs b/hadrian/src/Rules/Test.hs
index d4a528445b..82a37ebe41 100644
--- a/hadrian/src/Rules/Test.hs
+++ b/hadrian/src/Rules/Test.hs
@@ -6,6 +6,8 @@ import Base
import CommandLine
import Expression
import Flavour
+import Hadrian.Haskell.Cabal.Type (packageDependencies)
+import Hadrian.Oracles.Cabal (readPackageData)
import Oracles.Setting
import Oracles.TestSettings
import Packages
@@ -30,10 +32,10 @@ checkApiAnnotationsProgPath, checkApiAnnotationsSourcePath :: FilePath
checkApiAnnotationsProgPath = "test/bin/check-api-annotations" <.> exe
checkApiAnnotationsSourcePath = "utils/check-api-annotations/Main.hs"
-checkPrograms :: [(FilePath, FilePath)]
+checkPrograms :: [(FilePath, FilePath, Package)]
checkPrograms =
- [ (checkPprProgPath, checkPprSourcePath)
- , (checkApiAnnotationsProgPath, checkApiAnnotationsSourcePath)
+ [ (checkPprProgPath, checkPprSourcePath, checkPpr)
+ , (checkApiAnnotationsProgPath, checkApiAnnotationsSourcePath, checkApiAnnotations)
]
ghcConfigPath :: FilePath
@@ -53,16 +55,28 @@ testRules = do
-- Rules for building check-ppr and check-ppr-annotations with the compiler
-- we are going to test (in-tree or out-of-tree).
- forM_ checkPrograms $ \(progPath, sourcePath) ->
+ forM_ checkPrograms $ \(progPath, sourcePath, progPkg) ->
root -/- progPath %> \path -> do
+ need [ sourcePath ]
testGhc <- testCompiler <$> userSetting defaultTestArgs
top <- topDirectory
+ depsPkgs <- packageDependencies <$> readPackageData progPkg
+
+ -- when we're about to test an in-tree compiler, we make sure that
+ -- we have the corresponding GHC binary available, along with the
+ -- necessary libraries to build the check-* programs
when (testGhc `elem` ["stage1", "stage2", "stage3"]) $ do
let stg = stageOf testGhc
- need . (:[]) =<< programPath (Context stg ghc vanilla)
+ ghcPath <- programPath (Context stg ghc vanilla)
+ depsLibs <- traverse
+ (\p -> pkgRegisteredLibraryFile (vanillaContext stg p))
+ depsPkgs
+ need (ghcPath : depsLibs)
+
bindir <- getBinaryDirectory testGhc
- cmd [bindir </> "ghc" <.> exe]
- ["-package", "ghc", "-o", top -/- path, top -/- sourcePath]
+ cmd [bindir </> "ghc" <.> exe] $
+ concatMap (\p -> ["-package", pkgName p]) depsPkgs ++
+ ["-o", top -/- path, top -/- sourcePath]
root -/- ghcConfigPath %> \_ -> do
args <- userSetting defaultTestArgs
diff --git a/hadrian/src/Settings/Default.hs b/hadrian/src/Settings/Default.hs
index b0d0f04ab3..78d46b46be 100644
--- a/hadrian/src/Settings/Default.hs
+++ b/hadrian/src/Settings/Default.hs
@@ -125,18 +125,7 @@ stage2Packages = stage1Packages
-- | Packages that are built only for the testsuite.
testsuitePackages :: Action [Package]
-testsuitePackages = do
- return $ [ checkApiAnnotations
- , checkPpr
- , ghci
- , ghcCompact
- , ghcPkg
- , hpcBin
- , hsc2hs
- , iserv
- , runGhc
- , unlit ] ++
- [ timeout | windowsHost ]
+testsuitePackages = return [ timeout | windowsHost ]
-- | Default build ways for library packages:
-- * We always build 'vanilla' way.