Skip to content

Commit

Permalink
Use Cabal directly in place of ghc-cabal; make build root configurable.
Browse files Browse the repository at this point in the history
This commit implements two significant changes (that were not easy to
separate):

- Don't use ghc-cabal anymore for getting information about Haskell packages.
  We now instead directly use Cabal-the-library.

- Make the build root configurable. This effectively gets rid of the inplace
  logic and allows us to place _all_ build artefacts in some directory of
  our choice, by passing '--build-root <some path>' to hadrian.

The code for this was mostly taken from snowleopard#445.
  • Loading branch information
alpmestan committed Mar 20, 2018
1 parent 47678ea commit df9ffa8
Show file tree
Hide file tree
Showing 59 changed files with 1,678 additions and 933 deletions.
2 changes: 2 additions & 0 deletions cfg/system.config.in
Original file line number Diff line number Diff line change
Expand Up @@ -106,6 +106,8 @@ conf-ld-linker-args-stage0 = @CONF_LD_LINKER_OPTS_STAGE0@
conf-ld-linker-args-stage1 = @CONF_LD_LINKER_OPTS_STAGE1@
conf-ld-linker-args-stage2 = @CONF_LD_LINKER_OPTS_STAGE2@

conf-hs-cpp-args = @HaskellCPPArgs@

# Include and library directories:
#=================================

Expand Down
17 changes: 4 additions & 13 deletions hadrian.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -22,18 +22,21 @@ executable hadrian
, Builder
, CommandLine
, Context
, Context.Paths
, Context.Type
, Environment
, Expression
, Expression.Type
, Flavour
, GHC
, GHC.Packages
, Hadrian.Builder
, Hadrian.Builder.Ar
, Hadrian.Builder.Sphinx
, Hadrian.Builder.Tar
, Hadrian.Expression
, Hadrian.Haskell.Cabal
, Hadrian.Haskell.Cabal.Configured
, Hadrian.Haskell.Cabal.Parse
, Hadrian.Haskell.Cabal.Type
, Hadrian.Oracles.ArgsHash
Expand All @@ -47,7 +50,6 @@ executable hadrian
, Oracles.Flag
, Oracles.Setting
, Oracles.ModuleFiles
, Oracles.PackageData
, Rules
, Rules.Clean
, Rules.Compile
Expand Down Expand Up @@ -91,19 +93,8 @@ executable hadrian
, Settings.Flavours.Quick
, Settings.Flavours.QuickCross
, Settings.Flavours.Quickest
, Settings.Packages.Base
, Settings.Packages.Cabal
, Settings.Packages.Compiler
, Settings.Packages.Ghc
, Settings.Packages.GhcCabal
, Settings.Packages.Ghci
, Settings.Packages.GhcPkg
, Settings.Packages.GhcPrim
, Settings.Packages.Haddock
, Settings.Packages.Haskeline
, Settings.Packages.IntegerGmp
, Settings.Packages
, Settings.Packages.Rts
, Settings.Packages.RunGhc
, Settings.Warnings
, Stage
, Target
Expand Down
78 changes: 32 additions & 46 deletions src/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,12 +18,14 @@ module Base (
module Stage,
module Way,

-- * Files
configH, ghcVersionH,
-- * Paths
hadrianPath, configPath, configFile, sourcePath, configH, shakeFilesDir,
generatedDir, inplaceBinPath, inplaceLibBinPath, inplaceLibPath,
inplaceLibCopyTargets, haddockHtmlResourcesStamp, templateHscPath,
stage0PackageDbDir, inplacePackageDbPath, packageDbPath, packageDbStamp,
ghcSplitPath
hadrianPath, configPath, configFile, sourcePath, shakeFilesDir,
generatedDir, generatedPath,
stageBinPath, stageLibPath,
templateHscPath, ghcDeps,
relativePackageDbPath, packageDbPath, packageDbStamp, ghcSplitPath
) where

import Control.Applicative
Expand Down Expand Up @@ -65,71 +67,55 @@ sourcePath = hadrianPath -/- "src"
configH :: FilePath
configH = "mk/config.h"

ghcVersionH :: Action FilePath
ghcVersionH = generatedPath <&> (-/- "ghcversion.h")

-- | The directory in 'buildRoot' containing the Shake database and other
-- auxiliary files generated by Hadrian.
shakeFilesDir :: FilePath
shakeFilesDir = "hadrian"

-- | Directory for binaries that are built "in place".
inplaceBinPath :: FilePath
inplaceBinPath = "inplace/bin"

-- | Directory for libraries that are built "in place".
inplaceLibPath :: FilePath
inplaceLibPath = "inplace/lib"

-- | Directory for binary wrappers, and auxiliary binaries such as @touchy@.
inplaceLibBinPath :: FilePath
inplaceLibBinPath = inplaceLibPath -/- "bin"

-- | The directory in 'buildRoot' containing generated source files that are not
-- package-specific, e.g. @ghcplatform.h@.
generatedDir :: FilePath
generatedDir = "generated"

-- | The directory in 'buildRoot' containing the 'Stage0' package database.
stage0PackageDbDir :: FilePath
stage0PackageDbDir = "stage0/bootstrapping.conf"
generatedPath :: Action FilePath
generatedPath = buildRoot <&> (-/- generatedDir)

-- | Path to the inplace package database used in 'Stage1' and later.
inplacePackageDbPath :: FilePath
inplacePackageDbPath = inplaceLibPath -/- "package.conf.d"
relativePackageDbPath :: Stage -> FilePath
relativePackageDbPath stage = stageString stage -/- "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
packageDbPath stage = buildRoot <&> (-/- relativePackageDbPath stage)

-- | We use a stamp file to track the existence of a package database.
packageDbStamp :: FilePath
packageDbStamp = ".stamp"

-- ref: GHC_DEPENDENCIES in ghc/ghc.mk
-- ref: INSTALL_LIBS in driver/ghc.mk
-- TODO: Derive this from Builder.runtimeDependencies
-- | Files that need to be copied over to 'inplaceLibPath'.
inplaceLibCopyTargets :: [FilePath]
inplaceLibCopyTargets = map (inplaceLibPath -/-)
[ "ghc-usage.txt"
, "ghci-usage.txt"
, "llvm-targets"
, "platformConstants"
, "settings"
, "template-hsc.h" ]

-- TODO: This is fragile and will break if @README.md@ is removed. We need to
-- improve the story of program runtime dependencies on directories.
-- See: https://github.com/snowleopard/hadrian/issues/492.
-- | Path to a file in Haddock's HTML resource library.
haddockHtmlResourcesStamp :: FilePath
haddockHtmlResourcesStamp = inplaceLibPath -/- "html/README.md"
stageBinPath :: Stage -> Action FilePath
stageBinPath stage = buildRoot <&> (-/- stageString stage -/- "bin")

stageLibPath :: Stage -> Action FilePath
stageLibPath stage = buildRoot <&> (-/- stageString stage -/- "lib")

-- | Files the `ghc` binary depends on
ghcDeps :: Stage -> Action [FilePath]
ghcDeps stage = mapM (\f -> stageLibPath stage <&> (-/- f))
[ "ghc-usage.txt"
, "ghci-usage.txt"
, "llvm-targets"
, "platformConstants"
, "settings" ]

-- ref: utils/hsc2hs/ghc.mk
-- | Path to 'hsc2hs' template.
templateHscPath :: FilePath
templateHscPath = inplaceLibPath -/- "template-hsc.h"
templateHscPath :: Stage -> Action FilePath
templateHscPath stage = stageLibPath stage <&> (-/- "template-hsc.h")

-- | @ghc-split@ is a Perl script used by GHC when run with @-split-objs@ flag.
-- It is generated in "Rules.Generate".
ghcSplitPath :: FilePath
ghcSplitPath = inplaceLibBinPath -/- "ghc-split"
ghcSplitPath = "path/to/ghc-split" -- TODO: fix this
70 changes: 54 additions & 16 deletions src/Builder.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,11 @@
{-# LANGUAGE InstanceSigs #-}
module Builder (
-- * Data types
ArMode (..), CcMode (..), GhcMode (..), GhcPkgMode (..), HaddockMode (..),
ArMode (..), CcMode (..), GhcCabalMode (..), GhcMode (..), GhcPkgMode (..), HaddockMode (..),
SphinxMode (..), TarMode (..), Builder (..),

builderPath',

-- * Builder properties
builderProvenance, systemBuilderPath, builderPath, isSpecified, needBuilder,
runBuilder, runBuilderWith, runBuilderWithCmdOptions, getBuilderPath,
Expand Down Expand Up @@ -53,8 +55,20 @@ instance Binary GhcMode
instance Hashable GhcMode
instance NFData GhcMode

-- | GHC cabal mode. Can configure, copy and register pacakges.
data GhcCabalMode = Conf | Copy | Reg | HsColour | Check | Sdist
deriving (Eq, Generic, Show)

instance Binary GhcCabalMode
instance Hashable GhcCabalMode
instance NFData GhcCabalMode

-- | GhcPkg can initialise a package database and register packages in it.
data GhcPkgMode = Init | Update deriving (Eq, Generic, Show)
data GhcPkgMode = Init -- initialize a new database.
| Update -- update a package.
| Clone -- clone a package from one pkg database into another. @Copy@ is already taken by GhcCabalMode.
| Dependencies -- compute package dependencies.
deriving (Eq, Generic, Show)

instance Binary GhcPkgMode
instance Hashable GhcPkgMode
Expand Down Expand Up @@ -82,15 +96,15 @@ data Builder = Alex
| GenApply
| GenPrimopCode
| Ghc GhcMode Stage
| GhcCabal
| GhcCabal GhcCabalMode Stage
| GhcPkg GhcPkgMode Stage
| Haddock HaddockMode
| Happy
| Hpc
| Hp2Ps
| HsCpp
| Hsc2Hs
| Ld
| Hsc2Hs Stage
| Ld Stage
| Make FilePath
| Nm
| Objdump
Expand All @@ -103,6 +117,9 @@ data Builder = Alex
| Tar TarMode
| Unlit
| Xelatex
| CabalFlags Stage -- ^ a virtual builder to use the Arg predicate logic
-- to collect cabal flags. +x, -x

deriving (Eq, Generic, Show)

instance Binary Builder
Expand All @@ -119,18 +136,21 @@ builderProvenance = \case
GenPrimopCode -> context Stage0 genprimopcode
Ghc _ Stage0 -> Nothing
Ghc _ stage -> context (pred stage) ghc
GhcCabal -> context Stage0 ghcCabal
GhcCabal _ _ -> context Stage1 ghcCabal
GhcPkg _ Stage0 -> Nothing
GhcPkg _ _ -> context Stage0 ghcPkg
Haddock _ -> context Stage2 haddock
Hpc -> context Stage1 hpcBin
Hp2Ps -> context Stage0 hp2ps
Hsc2Hs -> context Stage0 hsc2hs
Hsc2Hs _ -> context Stage0 hsc2hs
Unlit -> context Stage0 unlit
_ -> Nothing
where
context s p = Just $ vanillaContext s p

builderPath' :: Builder -> Action FilePath
builderPath' = builderPath

instance H.Builder Builder where
builderPath :: Builder -> Action FilePath
builderPath builder = case builderProvenance builder of
Expand All @@ -142,24 +162,37 @@ instance H.Builder Builder where
Configure dir -> return [dir -/- "configure"]

Ghc _ Stage0 -> return []
Ghc _ _ -> do
Ghc _ stage -> do
win <- windowsHost
touchyPath <- programPath (vanillaContext Stage0 touchy)
unlitPath <- builderPath Unlit
ghcdeps <- ghcDeps stage
return $ [ ghcSplitPath -- TODO: Make conditional on --split-objects
, inplaceLibPath -/- "ghc-usage.txt"
, inplaceLibPath -/- "ghci-usage.txt"
, inplaceLibPath -/- "llvm-targets"
, inplaceLibPath -/- "platformConstants"
, inplaceLibPath -/- "settings"
, unlitPath ]
++ ghcdeps
++ [ touchyPath | win ]

Haddock _ -> return [haddockHtmlResourcesStamp]
Hsc2Hs -> return [templateHscPath]
Hsc2Hs stage -> (\p -> [p]) <$> templateHscPath stage
Make dir -> return [dir -/- "Makefile"]
_ -> return []

-- query the builder for some information.
-- contrast this with runBuilderWith, which returns @Action ()@
-- this returns the @stdout@ from running the builder.
-- For now this only implements asking @ghc-pkg@ about pacakge
-- dependencies.
askBuilderWith :: Builder -> BuildInfo -> Action String
askBuilderWith builder BuildInfo {..} = case builder of
GhcPkg Dependencies _ -> do
let input = fromSingleton msgIn buildInputs
msgIn = "[askBuilder] Exactly one input file expected."
needBuilder builder
path <- H.builderPath builder
need [path]
Stdout stdout <- cmd [path] ["--no-user-package-db", "field", input, "depends"]
return stdout
_ -> error $ "Builder " ++ show builder ++ " can not be asked!"

runBuilderWith :: Builder -> BuildInfo -> Action ()
runBuilderWith builder BuildInfo {..} = do
path <- builderPath builder
Expand Down Expand Up @@ -208,6 +241,11 @@ instance H.Builder Builder where
unit $ cmd [Cwd output] [path] buildArgs
unit $ cmd [Cwd output] [path] buildArgs

GhcPkg Clone _ -> do
-- input is "virtual" here. it's essentially a package name
Stdout pkgDesc <- cmd [path] ["--expand-pkgroot", "--no-user-package-db", "describe", input ]
cmd (Stdin pkgDesc) [path] (buildArgs ++ ["-"])

_ -> cmd echo [path] buildArgs

-- TODO: Some builders are required only on certain platforms. For example,
Expand All @@ -233,7 +271,7 @@ systemBuilderPath builder = case builder of
GhcPkg _ Stage0 -> fromKey "system-ghc-pkg"
Happy -> fromKey "happy"
HsCpp -> fromKey "hs-cpp"
Ld -> fromKey "ld"
Ld _ -> fromKey "ld"
Make _ -> fromKey "make"
Nm -> fromKey "nm"
Objdump -> fromKey "objdump"
Expand Down
49 changes: 49 additions & 0 deletions src/Builder.hs-boot
Original file line number Diff line number Diff line change
@@ -0,0 +1,49 @@
module Builder where

import Stage
import Hadrian.Builder.Ar
import Hadrian.Builder.Sphinx
import Hadrian.Builder.Tar
import Development.Shake

data CcMode = CompileC | FindCDependencies
data GhcMode = CompileHs | CompileCWithGhc | FindHsDependencies | LinkHs
data GhcCabalMode = Conf | Copy | Reg | HsColour | Check | Sdist
data GhcPkgMode = Init | Update | Clone | Dependencies
data HaddockMode = BuildPackage | BuildIndex

data Builder = Alex
| Ar ArMode Stage
| DeriveConstants
| Cc CcMode Stage
| Configure FilePath
| GenApply
| GenPrimopCode
| Ghc GhcMode Stage
| GhcCabal GhcCabalMode Stage
| GhcPkg GhcPkgMode Stage
| Haddock HaddockMode
| Happy
| Hpc
| Hp2Ps
| HsCpp
| Hsc2Hs Stage
| Ld Stage
| Make FilePath
| Nm
| Objdump
| Patch
| Perl
| Python
| Ranlib
| RunTest
| Sphinx SphinxMode
| Tar TarMode
| Unlit
| Xelatex
| CabalFlags Stage

instance Eq Builder
instance Show Builder

builderPath' :: Builder -> Action FilePath
Loading

0 comments on commit df9ffa8

Please sign in to comment.