import Oracles.Path
import Rules.Generate
import Rules.Libffi
+import Settings.Packages.Rts
import Settings.Path
import Target
import UserSettings
-- | Build @package-data.mk@ by using ghc-cabal utility to process .cabal files.
buildPackageData :: Context -> Rules ()
buildPackageData context@Context {..} = do
- let cabalFile = pkgCabalFile package
+ let path = buildPath context
+ cabalFile = pkgCabalFile package
configure = pkgPath package -/- "configure"
dataFile = pkgDataFile context
build $ Target context GhcCabal [cabalFile] [mk]
postProcessPackageData context mk
+ pkgInplaceConfig context %> \conf -> do
+ need [dataFile] -- ghc-cabal builds inplace package configuration file
+ if package == rts
+ then do
+ need [rtsConfIn]
+ build $ Target context HsCpp [rtsConfIn] [conf]
+ fixFile conf $ unlines
+ . map
+ ( replace "\"\"" ""
+ . replace "rts/dist/build" rtsBuildPath
+ . replace "includes/dist-derivedconstants/header" generatedPath )
+ . lines
+ else do
+ top <- topDirectory
+ let oldPath = top -/- path </> "build"
+ fixFile conf $ unlines . map (replace oldPath path) . lines
+
-- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps.
priority 2.0 $ do
when (package `elem` [hp2ps, rts, touchy, unlit]) $ dataFile %>
import Context
import Expression
import GHC
-import Oracles.Path
-import Rules.Libffi
-import Settings.Packages.Rts
import Settings.Path
import Target
import UserSettings
-- by running the @ghc-pkg@ utility.
registerPackage :: [(Resource, Int)] -> Context -> Rules ()
registerPackage rs context@Context {..} = when (stage <= Stage1) $ do
- let dir = packageDbDirectory stage
+ let confIn = pkgInplaceConfig context
+ dir = packageDbDirectory stage
matchVersionedFilePath (dir -/- pkgNameString package) "conf" ?> \conf -> do
- -- This produces inplace-pkg-config. TODO: Add explicit tracking.
- need [pkgDataFile context]
-
- -- Post-process inplace-pkg-config.
- top <- topDirectory
- let path = buildPath context
- pkgConfig = inplacePkgConfig context
- oldPath = top -/- path </> "build"
-
- fixFile pkgConfig $ unlines . map (replace oldPath path) . lines
-
- buildWithResources rs $ Target context (GhcPkg stage) [pkgConfig] [conf]
-
- when (package == rts && stage == Stage1) $ do
- packageDbDirectory Stage1 -/- "rts.conf" %> \conf -> do
- need [rtsConf]
- buildWithResources rs $ Target context (GhcPkg stage) [rtsConf] [conf]
-
- rtsConf %> \_ -> do
- need [pkgDataFile rtsContext, rtsConfIn]
- build $ Target context HsCpp [rtsConfIn] [rtsConf]
-
- let fixRtsConf = unlines
- . map
- ( replace "\"\"" ""
- . replace "rts/dist/build" rtsBuildPath
- . replace "includes/dist-derivedconstants/header" generatedPath )
- . filter (not . null)
- . lines
-
- fixFile rtsConf fixRtsConf
+ need [confIn]
+ buildWithResources rs $ Target context (GhcPkg stage) [confIn] [conf]
when (package == ghc) $ packageDbStamp stage %> \stamp -> do
removeDirectory dir
, arg "--force"
, verbosity < Chatty ? arg "-v0"
, bootPackageDatabaseArgs
- , arg . inplacePkgConfig =<< getContext ]
+ , arg . pkgInplaceConfig =<< getContext ]
rtsConfIn = pkgPath rts -/- "package.conf.in"
rtsConf :: FilePath
-rtsConf = inplacePkgConfig rtsContext
+rtsConf = pkgInplaceConfig rtsContext
rtsLibffiLibraryName :: Action FilePath
rtsLibffiLibraryName = do
gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath,
pkgConfFile, packageDbDirectory, packageDbStamp, bootPackageConstraints,
packageDependencies, objectPath, programInplacePath, programInplaceLibPath,
- installPath, autogenPath, inplacePkgConfig
+ installPath, autogenPath, pkgInplaceConfig
) where
import Base
autogen dir = buildPath context -/- dir -/- "autogen"
-- | Path to inplace package configuration of a given 'Context'.
-inplacePkgConfig :: Context -> FilePath
-inplacePkgConfig context = buildPath context -/- "inplace-pkg-config"
+pkgInplaceConfig :: Context -> FilePath
+pkgInplaceConfig context = buildPath context -/- "inplace-pkg-config"
-- | Path to the @package-data.mk@ of a given 'Context'.
pkgDataFile :: Context -> FilePath