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

Commit

Permalink
Move generated includes to build directory
Browse files Browse the repository at this point in the history
See #113.
  • Loading branch information
snowleopard committed Oct 2, 2016
1 parent c9ae45b commit f2cff6f
Show file tree
Hide file tree
Showing 12 changed files with 66 additions and 90 deletions.
4 changes: 1 addition & 3 deletions src/Rules/Clean.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,6 @@ import Base
import Context
import Package
import Rules.Actions
import Rules.Generate
import Settings
import Settings.Paths
import Stage
Expand All @@ -14,10 +13,9 @@ cleanRules :: Rules ()
cleanRules = do
"clean" ~> do
forM_ [Stage0 ..] $ removeDirectory . (buildRootPath -/-) . stageString
removeDirectory generatedPath
removeDirectory programInplacePath
removeDirectory "inplace/lib"
removeDirectory derivedConstantsPath
forM_ includesDependencies removeFile
putBuild $ "| Remove files generated by ghc-cabal..."
forM_ knownPackages $ \pkg ->
forM_ [Stage0 ..] $ \stage -> do
Expand Down
7 changes: 2 additions & 5 deletions src/Rules/Data.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,6 @@ import Oracles.Dependencies
import Rules.Actions
import Rules.Generate
import Rules.Libffi
import Settings.Builders.Common
import Settings.Paths
import Target
import UserSettings
Expand Down Expand Up @@ -60,7 +59,6 @@ buildPackageData context@Context {..} = do
priority 2.0 $ do
when (package == hp2ps) $ dataFile %> \mk -> do
orderOnly =<< interpretInContext context generatedDependencies
includes <- interpretInContext context $ fromDiffExpr includesArgs
let prefix = fixKey (buildPath context) ++ "_"
cSrcs = [ "AreaBelow.c", "Curves.c", "Error.c", "Main.c"
, "Reorder.c", "TopTwenty.c", "AuxFile.c"
Expand All @@ -71,7 +69,7 @@ buildPackageData context@Context {..} = do
[ "PROGNAME = hp2ps"
, "C_SRCS = " ++ unwords cSrcs
, "DEP_EXTRA_LIBS = m"
, "CC_OPTS = " ++ unwords includes ]
, "CC_OPTS = -I" ++ generatedPath ]
writeFileChanged mk contents
putSuccess $ "| Successfully generated " ++ mk

Expand Down Expand Up @@ -126,10 +124,9 @@ buildPackageData context@Context {..} = do
++ [ rtsBuildPath -/- "AutoApply.cmm" ]
++ [ rtsBuildPath -/- "sm/Evac_thr.c" ]
++ [ rtsBuildPath -/- "sm/Scav_thr.c" ]
includes <- interpretInContext context $ fromDiffExpr includesArgs
let contents = unlines $ map (prefix++)
[ "C_SRCS = " ++ unwords (cSrcs ++ cmmSrcs ++ extraSrcs)
, "CC_OPTS = " ++ unwords includes
, "CC_OPTS = -I" ++ generatedPath
, "COMPONENT_ID = rts" ]
writeFileChanged mk contents
putSuccess $ "| Successfully generated " ++ mk
Expand Down
20 changes: 8 additions & 12 deletions src/Rules/Generate.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
module Rules.Generate (
generatePackageCode, generateRules, installTargets, copyRules,
includesDependencies, derivedConstantsPath, generatedDependencies,
getPathIfGenerated
includesDependencies, generatedDependencies, getPathIfGenerated
) where

import qualified System.Directory as IO
Expand Down Expand Up @@ -43,7 +42,7 @@ platformH stage = buildPath (vanillaContext stage compiler) -/- "ghc_boot_platfo

-- TODO: move generated files to buildRootPath, see #113
includesDependencies :: [FilePath]
includesDependencies = fmap ("includes" -/-)
includesDependencies = fmap (generatedPath -/-)
[ "ghcautoconf.h"
, "ghcplatform.h"
, "ghcversion.h" ]
Expand All @@ -54,11 +53,8 @@ ghcPrimDependencies = do
let path = buildPath $ vanillaContext stage ghcPrim
return [path -/- "autogen/GHC/Prim.hs", path -/- "GHC/PrimopWrappers.hs"]

derivedConstantsPath :: FilePath
derivedConstantsPath = "includes/dist-derivedconstants/header"

derivedConstantsDependencies :: [FilePath]
derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-)
derivedConstantsDependencies = installTargets ++ fmap (generatedPath -/-)
[ "DerivedConstants.h"
, "GHCConstantsHaskellExports.hs"
, "GHCConstantsHaskellType.hs"
Expand Down Expand Up @@ -165,7 +161,7 @@ copyRules :: Rules ()
copyRules = do
"inplace/lib/ghc-usage.txt" <~ "driver"
"inplace/lib/ghci-usage.txt" <~ "driver"
"inplace/lib/platformConstants" <~ derivedConstantsPath
"inplace/lib/platformConstants" <~ generatedPath
"inplace/lib/settings" <~ "."
"inplace/lib/template-hsc.h" <~ pkgPath hsc2hs
rtsBuildPath -/- "sm/Evac_thr.c" %> copyFile (pkgPath rts -/- "sm/Evac.c")
Expand All @@ -175,16 +171,16 @@ copyRules = do

generateRules :: Rules ()
generateRules = do
"includes/ghcautoconf.h" <~ generateGhcAutoconfH
"includes/ghcplatform.h" <~ generateGhcPlatformH
"includes/ghcversion.h" <~ generateGhcVersionH
(generatedPath -/- "ghcautoconf.h") <~ generateGhcAutoconfH
(generatedPath -/- "ghcplatform.h") <~ generateGhcPlatformH
(generatedPath -/- "ghcversion.h") <~ generateGhcVersionH

ghcSplit %> \_ -> do
generate ghcSplit emptyTarget generateGhcSplit
makeExecutable ghcSplit

-- TODO: simplify, get rid of fake rts context
derivedConstantsPath ++ "//*" %> \file -> do
generatedPath ++ "//*" %> \file -> do
withTempDir $ \dir -> build $
Target rtsContext DeriveConstants [] [file, dir]

Expand Down
24 changes: 9 additions & 15 deletions src/Settings/Builders/Cc.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,19 +7,20 @@ import Predicate
import Settings.Builders.Common
import Settings

-- TODO: handle custom $1_$2_MKDEPENDC_OPTS and
ccBuilderArgs :: Args
ccBuilderArgs = mconcat
[ builder (Cc CompileC) ?
mconcat [ commonCcArgs
, arg "-c", arg =<< getInput
ccBuilderArgs = builder Cc ? mconcat
[ append =<< getPkgDataList CcArgs
, argSettingList . ConfCcArgs =<< getStage
, cIncludeArgs

, builder (Cc CompileC) ?
mconcat [ arg "-c", arg =<< getInput
, arg "-o", arg =<< getOutput ]

, builder (Cc FindCDependencies) ? do
output <- getOutput
mconcat [ arg "-E"
, arg "-MM"
, commonCcArgs
, arg "-MF"
, arg output
, arg "-MT"
Expand All @@ -28,18 +29,11 @@ ccBuilderArgs = mconcat
, arg "c"
, arg =<< getInput ]

, builder (Cc FindMissingInclude) ? do
, builder (Cc FindMissingInclude) ?
mconcat [ arg "-E"
, arg "-MM"
, arg "-MG"
, commonCcArgs
, arg "-MF"
, arg =<< getOutput
, arg =<< getInput
]
, arg =<< getInput ]
]

commonCcArgs :: Args
commonCcArgs = mconcat [ append =<< getPkgDataList CcArgs
, append =<< getSettingList . ConfCcArgs =<< getStage
, cIncludeArgs ]
13 changes: 4 additions & 9 deletions src/Settings/Builders/Common.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
module Settings.Builders.Common (
includes, includesArgs, cIncludeArgs, ldArgs, cArgs, cWarnings,
argSetting, argSettingList, argStagedBuilderPath, argStagedSettingList
cIncludeArgs, ldArgs, cArgs, cWarnings, argSetting, argSettingList,
argStagedBuilderPath, argStagedSettingList
) where

import Base
Expand All @@ -11,19 +11,14 @@ import Oracles.PackageData
import Settings
import UserSettings

includes :: [FilePath]
includes = ["includes", "includes/dist-derivedconstants/header"]

includesArgs :: Args
includesArgs = append $ map ("-I" ++) includes

cIncludeArgs :: Args
cIncludeArgs = do
pkg <- getPackage
path <- getBuildPath
incDirs <- getPkgDataList IncludeDirs
depDirs <- getPkgDataList DepIncludeDirs
mconcat [ arg $ "-I" ++ path
mconcat [ arg "-Iincludes"
, arg $ "-I" ++ path
, arg $ "-I" ++ path -/- "autogen"
, append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ]
, append [ "-I" ++ unifyPath dir | dir <- depDirs ] ]
Expand Down
21 changes: 10 additions & 11 deletions src/Settings/Builders/DeriveConstants.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,20 +20,19 @@ deriveConstantsBuilderArgs = builder DeriveConstants ? do
, arg "-o", arg outputFile
, arg "--tmpdir", arg tempDir
, arg "--gcc-program", arg =<< getBuilderPath (Cc CompileC Stage1)
, append . concat $ map (\a -> ["--gcc-flag", a]) cFlags
, append $ concatMap (\a -> ["--gcc-flag", a]) cFlags
, arg "--nm-program", arg =<< getBuilderPath Nm
, specified Objdump ? mconcat [ arg "--objdump-program"
, arg =<< getBuilderPath Objdump ]
, arg "--target-os", argSetting TargetOs ]

includeCcArgs :: Args
includeCcArgs = do
confCcArgs <- getSettingList $ ConfCcArgs Stage1
mconcat [ cArgs
, cWarnings
, append confCcArgs
, flag GhcUnregisterised ? arg "-DUSE_MINIINTERPRETER"
, includesArgs
, arg "-Irts"
, notM ghcWithSMP ? arg "-DNOSMP"
, arg "-fcommon" ]
includeCcArgs = mconcat
[ cArgs
, cWarnings
, argSettingList $ ConfCcArgs Stage1
, flag GhcUnregisterised ? arg "-DUSE_MINIINTERPRETER"
, arg "-Irts"
, arg "-Iincludes"
, notM ghcWithSMP ? arg "-DNOSMP"
, arg "-fcommon" ]
40 changes: 19 additions & 21 deletions src/Settings/Builders/GhcCabal.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Settings.Builders.GhcCabal (
ghcCabalBuilderArgs, ghcCabalHsColourBuilderArgs, bootPackageDatabaseArgs,
PackageDatabaseKey (..), cppArgs, buildDll0
PackageDatabaseKey (..), buildDll0
) where

import Base
Expand All @@ -17,25 +17,23 @@ import Settings.Builders.Common
import Settings.Paths

ghcCabalBuilderArgs :: Args
ghcCabalBuilderArgs = builder GhcCabal ? do
path <- getPackagePath
dir <- getContextDirectory
mconcat [ arg "configure"
, arg path
, arg dir
, dll0Args
, withStaged $ Ghc CompileHs
, withStaged GhcPkg
, bootPackageDatabaseArgs
, libraryArgs
, with HsColour
, configureArgs
, packageConstraints
, withStaged $ Cc CompileC
, notStage0 ? with Ld
, with Ar
, with Alex
, with Happy ]
ghcCabalBuilderArgs = builder GhcCabal ? mconcat
[ arg "configure"
, arg =<< getPackagePath
, arg =<< getContextDirectory
, dll0Args
, withStaged $ Ghc CompileHs
, withStaged GhcPkg
, bootPackageDatabaseArgs
, libraryArgs
, with HsColour
, configureArgs
, packageConstraints
, withStaged $ Cc CompileC
, notStage0 ? with Ld
, with Ar
, with Alex
, with Happy ]

ghcCabalHsColourBuilderArgs :: Args
ghcCabalHsColourBuilderArgs = builder GhcCabalHsColour ? do
Expand Down Expand Up @@ -105,7 +103,7 @@ packageConstraints = stage0 ? do
append $ concat [ ["--constraint", c] | c <- constraints ]

cppArgs :: Args
cppArgs = includesArgs
cppArgs = arg $ "-I" ++ generatedPath

withBuilderKey :: Builder -> String
withBuilderKey b = case b of
Expand Down
4 changes: 2 additions & 2 deletions src/Settings/Builders/HsCpp.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,15 +3,15 @@ module Settings.Builders.HsCpp (hsCppBuilderArgs) where
import GHC
import Oracles.Config.Setting
import Predicate
import Settings.Builders.GhcCabal
import Settings.Paths

hsCppBuilderArgs :: Args
hsCppBuilderArgs = builder HsCpp ? do
stage <- getStage
mconcat [ append =<< getSettingList HsCppArgs
, arg "-P"
, cppArgs
, arg "-Iincludes"
, arg $ "-I" ++ generatedPath
, arg $ "-I" ++ buildPath (vanillaContext stage compiler)
, arg "-x"
, arg "c"
Expand Down
7 changes: 3 additions & 4 deletions src/Settings/Packages/Compiler.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ import Oracles.Config.Flag
import Oracles.Config.Setting
import Predicate
import Settings
import Settings.Builders.Common
import Settings.Paths

compilerPackageArgs :: Args
compilerPackageArgs = package compiler ? do
Expand All @@ -17,9 +17,8 @@ compilerPackageArgs = package compiler ? do
mconcat [ builder Alex ? arg "--latin1"

, builder Ghc ? mconcat
[ arg ("-I" ++ path)
, includesArgs
, append [ "-optP-I" ++ dir | dir <- includes ] ]
[ arg $ "-I" ++ path
, arg $ "-optP-I" ++ generatedPath ]

, builder GhcCabal ? mconcat
[ arg $ "--ghc-option=-DSTAGE=" ++ show (fromEnum stage + 1)
Expand Down
3 changes: 1 addition & 2 deletions src/Settings/Packages/IntegerGmp.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,5 @@ integerGmpPackageArgs = package integerGmp ? do
[ (null gmpIncludeDir && null gmpLibDir) ?
arg "--configure-option=--with-intree-gmp"
, appendSub "--configure-option=CFLAGS" [includeGmp]
, appendSub "--gcc-options" [includeGmp]
]
, appendSub "--gcc-options" [includeGmp] ]
]
8 changes: 3 additions & 5 deletions src/Settings/Packages/Rts.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ import Oracles.Config.Setting
import Oracles.WindowsPath
import Predicate
import Settings
import Settings.Builders.Common
import Settings.Paths

rtsConfIn :: FilePath
rtsConfIn = pkgPath rts -/- "package.conf.in"
Expand Down Expand Up @@ -90,10 +90,9 @@ rtsPackageArgs = package rts ? do
, input "//Evac_thr.c" ? arg "-funroll-loops"

, input "//Evac_thr.c" ? append [ "-DPARALLEL_GC", "-Irts/sm" ]
, input "//Scav_thr.c" ? append [ "-DPARALLEL_GC", "-Irts/sm" ]
]
, input "//Scav_thr.c" ? append [ "-DPARALLEL_GC", "-Irts/sm" ] ]

, builder Ghc ? (arg "-Irts" <> includesArgs)
, builder Ghc ? arg "-Irts" <> arg ("-I" ++ generatedPath)

, builder (GhcPkg Stage1) ? mconcat
[ remove ["rts/stage1/inplace-pkg-config"] -- TODO: fix, see #113
Expand All @@ -106,7 +105,6 @@ rtsPackageArgs = package rts ? do
, "-DFFI_LIB=" ++ show libffiName ]
]


-- # If we're compiling on windows, enforce that we only support XP+
-- # Adding this here means it doesn't have to be done in individual .c files
-- # and also centralizes the versioning.
Expand Down
5 changes: 4 additions & 1 deletion src/Settings/Paths.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
module Settings.Paths (
contextDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile,
pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpObjects, gmpLibraryH,
gmpBuildInfoPath, libffiBuildPath, shakeFilesPath, pkgConfFile,
gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, pkgConfFile,
packageDbDirectory, bootPackageConstraints, packageDependencies
) where

Expand All @@ -21,6 +21,9 @@ bootPackageConstraints = shakeFilesPath -/- "boot-package-constraints"
packageDependencies :: FilePath
packageDependencies = shakeFilesPath -/- "package-dependencies"

generatedPath :: FilePath
generatedPath = buildRootPath -/- "generated"

-- | Path to the directory containing build artefacts of a given 'Context'.
buildPath :: Context -> FilePath
buildPath context@Context {..} =
Expand Down

0 comments on commit f2cff6f

Please sign in to comment.