Also a minor revision.
See #421
hadrianPath, configPath, configFile, sourcePath, configH, shakeFilesDir,
generatedDir, inplaceBinPath, inplaceLibBinPath, inplaceLibPath,
inplaceLibCopyTargets, templateHscPath, stage0PackageDbDir,
- inplacePackageDbPath, packageDbStamp
+ inplacePackageDbPath, packageDbPath, packageDbStamp
) where
import Control.Applicative
inplacePackageDbPath :: FilePath
inplacePackageDbPath = "inplace/lib/package.conf.d"
+-- | Path to the package database used in a given 'Stage'.
+packageDbPath :: Stage -> Action FilePath
+packageDbPath Stage0 = buildRoot <&> (-/- stage0PackageDbDir)
+packageDbPath _ = return inplacePackageDbPath
+
-- | We use a stamp file to track the existence of a package database.
packageDbStamp :: FilePath
packageDbStamp = ".stamp"
Just context -> programPath context
needBuilder :: Builder -> Action ()
- needBuilder (Configure dir) = need [dir -/- "configure"]
- needBuilder Hsc2Hs = do path <- H.builderPath Hsc2Hs
- need [path, templateHscPath]
- needBuilder (Make dir) = need [dir -/- "Makefile"]
- needBuilder builder = when (isJust $ builderProvenance builder) $ do
+ needBuilder builder = do
path <- H.builderPath builder
- need [path]
+ case builder of
+ Configure dir -> need [dir -/- "configure"]
+ Hsc2Hs -> need [path, templateHscPath]
+ Make dir -> need [dir -/- "Makefile"]
+ _ -> when (isJust $ builderProvenance builder) $ need [path]
runBuilderWith :: Builder -> BuildInfo -> Action ()
runBuilderWith builder BuildInfo {..} = do
bootPackageDatabaseArgs :: Args
bootPackageDatabaseArgs = do
- root <- getBuildRoot
- stage <- getStage
- let dbDir | stage == Stage0 = root -/- stage0PackageDbDir
- | otherwise = inplacePackageDbPath
- expr $ need [dbDir -/- packageDbStamp]
+ stage <- getStage
+ dbPath <- expr $ packageDbPath stage
+ expr $ need [dbPath -/- packageDbStamp]
stage0 ? do
top <- expr topDirectory
root <- getBuildRoot
module Settings.Builders.Ghc (
- ghcBuilderArgs, ghcMBuilderArgs, haddockGhcArgs, ghcCbuilderArgs
+ ghcBuilderArgs, ghcCBuilderArgs, ghcMBuilderArgs, haddockGhcArgs
) where
import Hadrian.Haskell.Cabal
touchyPath <- expr $ programPath (vanillaContext Stage0 touchy)
expr $ need [touchyPath]
-ghcCbuilderArgs :: Args
-ghcCbuilderArgs =
- builder (Ghc CompileCWithGhc) ? do
+ghcCBuilderArgs :: Args
+ghcCBuilderArgs = builder (Ghc CompileCWithGhc) ? do
way <- getWay
let ccArgs = [ getPkgDataList CcArgs
, getStagedSettingList ConfCcArgs
haddockGhcArgs :: Args
haddockGhcArgs = mconcat [ commonGhcArgs, getPkgDataList HsArgs ]
--- This is included into ghcBuilderArgs, ghcMBuilderArgs and haddockGhcArgs.
+-- Used in ghcBuilderArgs, ghcCBuilderArgs, ghcMBuilderArgs and haddockGhcArgs.
commonGhcArgs :: Args
commonGhcArgs = do
way <- getWay
path <- getBuildPath
+ pkg <- getPackage
+ when (isLibrary pkg) $ do
+ context <- getContext
+ conf <- expr $ pkgConfFile context
+ expr $ need [conf]
mconcat [ arg "-hisuf", arg $ hisuf way
, arg "-osuf" , arg $ osuf way
, arg "-hcsuf", arg $ hcsuf way
, deriveConstantsBuilderArgs
, genPrimopCodeBuilderArgs
, ghcBuilderArgs
- , ghcCbuilderArgs
, ghcCabalBuilderArgs
+ , ghcCBuilderArgs
, ghcMBuilderArgs
, ghcPkgBuilderArgs
, haddockBuilderArgs