Skip to content
This repository has been archived by the owner on Aug 2, 2020. It is now read-only.

Commit

Permalink
Don't generate in-tree directories by ghc-cabal
Browse files Browse the repository at this point in the history
See #113
  • Loading branch information
snowleopard committed Nov 26, 2016
1 parent 6d420eb commit 94c88da
Show file tree
Hide file tree
Showing 14 changed files with 56 additions and 80 deletions.
5 changes: 3 additions & 2 deletions src/Oracles/ModuleFiles.hs
Original file line number Diff line number Diff line change
Expand Up @@ -117,10 +117,11 @@ contextFiles context@Context {..} = do
moduleFilesOracle :: Rules ()
moduleFilesOracle = void $ do
void . addOracle $ \(ModuleFilesKey (stage, package)) -> do
let path = buildPath $ vanillaContext stage package
let context = vanillaContext stage package
path = buildPath context
srcDirs <- pkgDataList $ SrcDirs path
modules <- fmap sort . pkgDataList $ Modules path
let dirs = (path -/- "autogen") : map (pkgPath package -/-) srcDirs
let dirs = autogenPath context : map (pkgPath package -/-) srcDirs
modDirFiles = groupSort $ map decodeModule modules
result <- concatForM dirs $ \dir -> do
todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles
Expand Down
6 changes: 2 additions & 4 deletions src/Oracles/PackageData.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,10 +37,8 @@ newtype PackageDataKey = PackageDataKey (FilePath, String)
deriving (Binary, Eq, Hashable, NFData, Show, Typeable)

askPackageData :: FilePath -> String -> Action String
askPackageData path key = do
let fullKey = replaceSeparators '_' $ path ++ "_" ++ key
file = path -/- "package-data.mk"
fromMaybe "" <$> askOracle (PackageDataKey (file, fullKey))
askPackageData path key = fromMaybe "" <$>
askOracle (PackageDataKey (path -/- "package-data.mk", key))

-- | For each @PackageData path@ the file 'path/package-data.mk' contains a line
-- of the form 'path_VERSION = 1.2.3.4'. @pkgData (PackageData path)@ is an
Expand Down
57 changes: 13 additions & 44 deletions src/Rules/Data.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ import Expression
import GHC
import Oracles.Config.Setting
import Oracles.Dependencies
import Oracles.Path
import Rules.Generate
import Rules.Libffi
import Settings.Path
Expand All @@ -19,10 +20,8 @@ buildPackageData context@Context {..} = do
let cabalFile = pkgCabalFile package
configure = pkgPath package -/- "configure"
dataFile = pkgDataFile context
oldPath = pkgPath package -/- stageDirectory stage -- TODO: remove, #113
inTreeMk = oldPath -/- takeFileName dataFile -- TODO: remove, #113

inTreeMk %> \mk -> do
dataFile %> \mk -> do
-- Make sure all generated dependencies are in place before proceeding.
orderOnly =<< interpretInContext context generatedDependencies

Expand All @@ -34,24 +33,6 @@ buildPackageData context@Context {..} = do

need [cabalFile]
build $ Target context GhcCabal [cabalFile] [mk]

-- TODO: Get rid of this, see #113.
dataFile %> \mk -> do
-- TODO: This is a hack. Add a proper support for autogen directory
-- structure of the new Cabal (probably only after #113).
let oldBuild
| isLibrary package = oldPath -/- "build"
| package == ghc = oldPath -/- "build/ghc"
| package == hpcBin = oldPath -/- "build/hpc"
| package == iservBin = oldPath -/- "build/iserv"
| otherwise = oldPath -/- "build" -/- pkgNameString package
copyFile inTreeMk mk
autogenFiles <- getDirectoryFiles oldBuild ["autogen/*"]
forM_ autogenFiles $ \file' -> do
let file = unifyPath file'
copyFile (oldBuild -/- file) (buildPath context -/- file)
let haddockPrologue = "haddock-prologue.txt"
copyFile (oldPath -/- haddockPrologue) (buildPath context -/- haddockPrologue)
postProcessPackageData context mk

-- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps.
Expand All @@ -71,9 +52,8 @@ generatePackageData context@Context {..} file = do
asmSrcs <- packageAsmSources package
cSrcs <- packageCSources package
cmmSrcs <- packageCmmSources package
let prefix = fixKey (buildPath context) ++ "_"
pkgKey = if isLibrary package then "COMPONENT_ID = " else "PROGNAME = "
writeFileChanged file . unlines . map (prefix ++) $
let pkgKey = if isLibrary package then "COMPONENT_ID = " else "PROGNAME = "
writeFileChanged file . unlines $
[ pkgKey ++ pkgNameString package ] ++
[ "S_SRCS = " ++ unwords asmSrcs ] ++
[ "C_SRCS = " ++ unwords cSrcs ] ++
Expand Down Expand Up @@ -113,26 +93,15 @@ packageCmmSources pkg
return $ sources ++ [ rtsBuildPath -/- "cmm/AutoApply.cmm" ]

-- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile:
-- 1) Drop lines containing '$'
-- For example, get rid of
-- libraries/Win32_dist-install_CMM_SRCS := $(addprefix cbits/,$(notdir ...
-- 1) Drop lines containing '$'. For example, get rid of
-- @libraries/Win32_dist-install_CMM_SRCS := $(addprefix cbits/,$(notdir ...@
-- Reason: we don't need them and we can't parse them.
-- 2) Replace '/' and '\' with '_' before '='
-- For example libraries/deepseq/dist-install_VERSION = 1.4.0.0
-- is replaced by libraries_deepseq_dist-install_VERSION = 1.4.0.0
-- 2) Drop path prefixes to individual settings.
-- For example, @libraries/deepseq/dist-install_VERSION = 1.4.0.0@
-- is replaced by @VERSION = 1.4.0.0@.
-- Reason: Shake's built-in makefile parser doesn't recognise slashes
postProcessPackageData :: Context -> FilePath -> Action ()
postProcessPackageData Context {..} file = fixFile file fixPackageData
where
fixPackageData = unlines . map processLine . filter (not . null) . filter ('$' `notElem`) . lines
processLine line = fixKey fixedPrefix ++ suffix
where
(prefix, suffix) = break (== '=') line
-- Change package/path/targetDir to takeDirectory file
-- This is a temporary hack until we get rid of ghc-cabal
fixedPrefix = takeDirectory file ++ drop len prefix
len = length (pkgPath package -/- stageDirectory stage)

-- TODO: Remove, see #113.
fixKey :: String -> String
fixKey = replaceSeparators '_'
postProcessPackageData context@Context {..} file = do
top <- topDirectory
let len = length (pkgPath package) + length (top -/- buildPath context) + 2
fixFile file $ unlines . map (drop len) . filter ('$' `notElem`) . lines
18 changes: 7 additions & 11 deletions src/Rules/Register.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ import Base
import Context
import Expression
import GHC
import Oracles.Path
import Rules.Libffi
import Settings.Packages.Rts
import Settings.Path
Expand All @@ -22,17 +23,12 @@ registerPackage rs context@Context {..} = when (stage <= Stage1) $ do
need [pkgDataFile context]

-- Post-process inplace-pkg-config. TODO: remove, see #113, #148.
let path = buildPath context
oldPath = pkgPath package -/- stageDirectory stage
pkgConfig = oldPath -/- "inplace-pkg-config"
oldBuildPath = oldPath -/- "build"
fixPkgConf = unlines
. map
( replace oldBuildPath path
. replace (replaceSeparators '\\' oldBuildPath) path )
. lines

fixFile pkgConfig fixPkgConf
top <- topDirectory
let path = buildPath context
pkgConfig = path -/- "inplace-pkg-config"
oldPath = top -/- path </> "build"

fixFile pkgConfig $ unlines . map (replace oldPath path) . lines

buildWithResources rs $ Target context (GhcPkg stage) [pkgConfig] [conf]

Expand Down
1 change: 0 additions & 1 deletion src/Settings/Builders/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,6 @@ cIncludeArgs = do
mconcat [ arg "-Iincludes"
, arg $ "-I" ++ generatedPath
, arg $ "-I" ++ path
, arg $ "-I" ++ path -/- "autogen"
, append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ]
, append [ "-I" ++ unifyPath dir | dir <- depDirs ] ]

Expand Down
5 changes: 3 additions & 2 deletions src/Settings/Builders/Ghc.hs
Original file line number Diff line number Diff line change
Expand Up @@ -111,13 +111,14 @@ includeGhcArgs :: Args
includeGhcArgs = do
pkg <- getPackage
path <- getBuildPath
context <- getContext
srcDirs <- getPkgDataList SrcDirs
mconcat [ arg "-i"
, arg $ "-i" ++ path
, arg $ "-i" ++ path -/- "autogen"
, arg $ "-i" ++ autogenPath context
, append [ "-i" ++ pkgPath pkg -/- dir | dir <- srcDirs ]
, cIncludeArgs
, arg $ "-I" ++ generatedPath
, arg $ "-optc-I" ++ generatedPath
, arg "-optP-include"
, arg $ "-optP" ++ path -/- "autogen/cabal_macros.h" ]
, arg $ "-optP" ++ autogenPath context -/- "cabal_macros.h" ]
4 changes: 3 additions & 1 deletion src/Settings/Builders/GhcCabal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,9 +10,11 @@ import Util
ghcCabalBuilderArgs :: Args
ghcCabalBuilderArgs = builder GhcCabal ? do
verbosity <- lift $ getVerbosity
top <- getTopDirectory
context <- getContext
mconcat [ arg "configure"
, arg =<< getPackagePath
, arg =<< getContextDirectory
, arg $ top -/- buildPath context
, dll0Args
, withStaged $ Ghc CompileHs
, withStaged GhcPkg
Expand Down
6 changes: 2 additions & 4 deletions src/Settings/Builders/GhcPkg.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,14 +11,12 @@ initPredicate = orM $ map (output . packageDbDirectory) [Stage0 ..]
initArgs :: Args
initArgs = initPredicate ? mconcat [ arg "init", arg =<< getOutput ]

-- TODO: Move inplace-pkg-config to buildRootPath, see #113.
updateArgs :: Args
updateArgs = notM initPredicate ? do
pkg <- getPackage
dir <- getContextDirectory
path <- getBuildPath
verbosity <- lift $ getVerbosity
mconcat [ arg "update"
, arg "--force"
, verbosity < Chatty ? arg "-v0"
, bootPackageDatabaseArgs
, arg $ pkgPath pkg -/- dir -/- "inplace-pkg-config" ]
, arg $ path -/- "inplace-pkg-config" ]
4 changes: 2 additions & 2 deletions src/Settings/Builders/Hsc2Hs.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,7 @@ hsc2hsBuilderArgs = builder Hsc2Hs ? do

getCFlags :: Expr [String]
getCFlags = fromDiffExpr $ do
path <- getBuildPath
context <- getContext
cppArgs <- getPkgDataList CppArgs
depCcArgs <- getPkgDataList DepCcArgs
mconcat [ cArgs
Expand All @@ -51,7 +51,7 @@ getCFlags = fromDiffExpr $ do
, append cppArgs
, append depCcArgs
, cWarnings
, arg "-include", arg $ path -/- "autogen/cabal_macros.h" ]
, arg "-include", arg $ autogenPath context -/- "cabal_macros.h" ]

getLFlags :: Expr [String]
getLFlags = fromDiffExpr $ do
Expand Down
6 changes: 3 additions & 3 deletions src/Settings/Packages/GhcCabal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ import Base
import GHC
import Oracles.Config.Setting
import Predicate
import Settings
import Settings.Path

ghcCabalPackageArgs :: Args
ghcCabalPackageArgs = package ghcCabal ?
Expand All @@ -23,15 +23,15 @@ ghcCabalBootArgs = stage0 ? do
, pretty, process, time ]
, notM windowsHost ? append [unix]
, windowsHost ? append [win32] ]
path <- getBuildPath
context <- getContext
mconcat
[ append [ "-package " ++ pkgNameString pkg | pkg <- cabalDeps ]
, arg "--make"
, arg "-j"
, arg "-DBOOTSTRAPPING"
, arg "-DMIN_VERSION_binary_0_8_0"
, arg "-DGENERICS"
, removePair "-optP-include" $ "-optP" ++ path -/- "autogen/cabal_macros.h"
, removePair "-optP-include" $ "-optP" ++ autogenPath context -/- "cabal_macros.h"
, arg "-optP-include"
, arg $ "-optP" ++ pkgPath ghcCabal -/- "cabal_macros_boot.h"
, arg "-ilibraries/Cabal/Cabal"
Expand Down
2 changes: 1 addition & 1 deletion src/Settings/Packages/Rts.hs
Original file line number Diff line number Diff line change
Expand Up @@ -97,7 +97,7 @@ rtsPackageArgs = package rts ? do
, builder Ghc ? arg "-Irts"

, builder (GhcPkg Stage1) ? mconcat
[ remove ["rts/stage1/inplace-pkg-config"] -- TODO: fix, see #113
[ remove [path -/- "inplace-pkg-config"]
, arg rtsConf ]

, builder HsCpp ? append
Expand Down
2 changes: 1 addition & 1 deletion src/Settings/Packages/Touchy.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ import Settings
touchyPackageArgs :: Args
touchyPackageArgs = package touchy ? do
path <- getBuildPath
let cabalMacros = path -/- "autogen/cabal_macros.h"
let cabalMacros = path -/- "build/autogen/cabal_macros.h"
builder Ghc ? mconcat [ arg "-no-hs-main"
, remove ["-hide-all-packages"]
, removePair "-optP-include" $ "-optP" ++ cabalMacros ]
2 changes: 1 addition & 1 deletion src/Settings/Packages/Unlit.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ import Settings
unlitPackageArgs :: Args
unlitPackageArgs = package unlit ? do
path <- getBuildPath
let cabalMacros = path -/- "autogen/cabal_macros.h"
let cabalMacros = path -/- "build/autogen/cabal_macros.h"
builder Ghc ? mconcat [ arg "-no-hs-main"
, remove ["-hide-all-packages"]
, removePair "-optP-include" $ "-optP" ++ cabalMacros ]
18 changes: 15 additions & 3 deletions src/Settings/Path.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,10 @@
module Settings.Path (
stageDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile,
pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpObjects, gmpLibraryH,
gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, pkgConfFile,
packageDbDirectory, packageDbStamp, bootPackageConstraints, packageDependencies,
objectPath, programInplacePath, programInplaceLibPath, installPath
gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath,
pkgConfFile, packageDbDirectory, packageDbStamp, bootPackageConstraints,
packageDependencies, objectPath, programInplacePath, programInplaceLibPath,
installPath, autogenPath
) where

import Base
Expand Down Expand Up @@ -48,6 +49,17 @@ programInplaceLibPath = "inplace/lib/bin"
buildPath :: Context -> FilePath
buildPath Context {..} = buildRootPath -/- stageDirectory stage -/- pkgPath package

-- | Path to the autogen directory generated by @ghc-cabal@ of a given 'Context'.
autogenPath :: Context -> FilePath
autogenPath context@Context {..}
| isLibrary package = autogen "build"
| package == ghc = autogen "build/ghc"
| package == hpcBin = autogen "build/hpc"
| package == iservBin = autogen "build/iserv"
| otherwise = autogen $ "build" -/- pkgNameString package
where
autogen dir = buildPath context -/- dir -/- "autogen"

-- | Path to the @package-data.mk@ of a given 'Context'.
pkgDataFile :: Context -> FilePath
pkgDataFile context = buildPath context -/- "package-data.mk"
Expand Down

0 comments on commit 94c88da

Please sign in to comment.