Skip to content
Snippets Groups Projects
Commit 4ebe312f authored by Ben Gamari's avatar Ben Gamari
Browse files

hadrian: Always specify flag values explicitly

Previously we would often allow cabal flags to default, making it harder
than necessary to reason about the effective build configuration.

(cherry picked from commit dd3c9602)
parent f32e3596
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE FlexibleContexts #-}
module Expression ( module Expression (
-- * Expressions -- * Expressions
Expr, Predicate, Args, Ways, Expr, Predicate, Args, Ways,
-- ** Construction and modification -- ** Construction and modification
expr, exprIO, arg, remove, expr, exprIO, arg, remove, cabalFlag,
-- ** Predicates -- ** Predicates
(?), stage, stage0, stage1, stage2, notStage0, threadedBootstrapper, (?), stage, stage0, stage1, stage2, notStage0, threadedBootstrapper,
...@@ -131,3 +133,11 @@ notPackage = notM . package ...@@ -131,3 +133,11 @@ notPackage = notM . package
-- | Is a library package currently being built? -- | Is a library package currently being built?
libraryPackage :: Predicate libraryPackage :: Predicate
libraryPackage = isLibrary <$> getPackage libraryPackage = isLibrary <$> getPackage
-- | Either @-flagName@ or @flagName@, depending upon a predicate.
-- For use in @Cabal Flags@ argument lists.
cabalFlag :: ToPredicate p Context Builder => p -> String -> Args
cabalFlag pred flagName = do
ifM (toPredicate pred) (arg flagName) (arg $ "-"<>flagName)
infixr 3 `cabalFlag`
...@@ -8,6 +8,7 @@ module Hadrian.Expression ( ...@@ -8,6 +8,7 @@ module Hadrian.Expression (
-- ** Predicates -- ** Predicates
(?), input, inputs, output, outputs, VerboseCommand (..), verboseCommand, (?), input, inputs, output, outputs, VerboseCommand (..), verboseCommand,
ToPredicate(..),
-- ** Evaluation -- ** Evaluation
interpret, interpretInContext, interpret, interpretInContext,
......
...@@ -25,7 +25,7 @@ packageArgs = do ...@@ -25,7 +25,7 @@ packageArgs = do
mconcat mconcat
--------------------------------- base --------------------------------- --------------------------------- base ---------------------------------
[ package base ? mconcat [ package base ? mconcat
[ builder (Cabal Flags) ? notStage0 ? arg (pkgName ghcBignum) [ builder (Cabal Flags) ? notStage0 `cabalFlag` (pkgName ghcBignum)
-- This fixes the 'unknown symbol stat' issue. -- This fixes the 'unknown symbol stat' issue.
-- See: https://github.com/snowleopard/hadrian/issues/259. -- See: https://github.com/snowleopard/hadrian/issues/259.
...@@ -65,8 +65,8 @@ packageArgs = do ...@@ -65,8 +65,8 @@ packageArgs = do
notStage0 ? arg "--ghc-pkg-option=--force" ] notStage0 ? arg "--ghc-pkg-option=--force" ]
, builder (Cabal Flags) ? mconcat , builder (Cabal Flags) ? mconcat
[ ghcWithInterpreter ? notStage0 ? arg "internal-interpreter" [ andM [expr ghcWithInterpreter, notStage0] `cabalFlag` "internal-interpreter"
, cross ? arg "-terminfo" , notM cross `cabalFlag` "terminfo"
] ]
, builder (Haddock BuildPackage) ? arg ("--optghc=-I" ++ path) ] , builder (Haddock BuildPackage) ? arg ("--optghc=-I" ++ path) ]
...@@ -76,25 +76,22 @@ packageArgs = do ...@@ -76,25 +76,22 @@ packageArgs = do
[ builder Ghc ? arg ("-I" ++ compilerPath) [ builder Ghc ? arg ("-I" ++ compilerPath)
, builder (Cabal Flags) ? mconcat , builder (Cabal Flags) ? mconcat
[ ghcWithInterpreter ? notStage0 ? arg "internal-interpreter" [ andM [expr ghcWithInterpreter, notStage0] `cabalFlag` "internal-interpreter"
, cross ? arg "-terminfo" , notM cross `cabalFlag` "terminfo"
, ifM stage0 , ifM stage0
-- We build a threaded stage 1 if the bootstrapping compiler -- We build a threaded stage 1 if the bootstrapping compiler
-- supports it. -- supports it.
(ifM threadedBootstrapper (threadedBootstrapper `cabalFlag` "threaded")
(arg "threaded")
(arg "-threaded"))
-- We build a threaded stage N, N>1 if the configuration calls -- We build a threaded stage N, N>1 if the configuration calls
-- for it. -- for it.
(ifM (ghcThreaded <$> expr flavour) ((ghcThreaded <$> expr flavour) `cabalFlag` "threaded")
(arg "threaded")
(arg "-threaded"))
] ]
] ]
-------------------------------- ghcPkg -------------------------------- -------------------------------- ghcPkg --------------------------------
, package ghcPkg ? , package ghcPkg ?
builder (Cabal Flags) ? cross ? arg "-terminfo" builder (Cabal Flags) ? notM cross `cabalFlag` "terminfo"
-------------------------------- ghcPrim ------------------------------- -------------------------------- ghcPrim -------------------------------
, package ghcPrim ? mconcat , package ghcPrim ? mconcat
...@@ -105,8 +102,7 @@ packageArgs = do ...@@ -105,8 +102,7 @@ packageArgs = do
--------------------------------- ghci --------------------------------- --------------------------------- ghci ---------------------------------
, package ghci ? mconcat , package ghci ? mconcat
[ notStage0 ? builder (Cabal Flags) ? arg "internal-interpreter" [
-- The use case here is that we want to build @iserv-proxy@ for the -- The use case here is that we want to build @iserv-proxy@ for the
-- cross compiler. That one needs to be compiled by the bootstrap -- cross compiler. That one needs to be compiled by the bootstrap
-- compiler as it needs to run on the host. Hence @libiserv@ needs -- compiler as it needs to run on the host. Hence @libiserv@ needs
...@@ -133,7 +129,9 @@ packageArgs = do ...@@ -133,7 +129,9 @@ packageArgs = do
-- the Stage1 libraries, as we already know that the bootstrap -- the Stage1 libraries, as we already know that the bootstrap
-- compiler comes with the same versions as the one we are building. -- compiler comes with the same versions as the one we are building.
-- --
, cross ? stage0 ? bootCross ? builder (Cabal Flags) ? arg "internal-interpreter" builder (Cabal Flags) ? ifM stage0
(andM [cross, bootCross] `cabalFlag` "internal-interpreter")
(arg "internal-interpreter")
] ]
...@@ -163,7 +161,7 @@ packageArgs = do ...@@ -163,7 +161,7 @@ packageArgs = do
-- dependencies. -- dependencies.
-- TODO: Perhaps the user should rather be responsible for this? -- TODO: Perhaps the user should rather be responsible for this?
, package haskeline ? , package haskeline ?
builder (Cabal Flags) ? cross ? arg "-terminfo" builder (Cabal Flags) ? notM cross `cabalFlag` "terminfo"
-------------------------------- hsc2hs -------------------------------- -------------------------------- hsc2hs --------------------------------
, package hsc2hs ? , package hsc2hs ?
...@@ -195,7 +193,7 @@ ghcBignumArgs = package ghcBignum ? do ...@@ -195,7 +193,7 @@ ghcBignumArgs = package ghcBignum ? do
builder (Cabal Flags) ? arg backend builder (Cabal Flags) ? arg backend
, -- check the selected backend against native backend , -- check the selected backend against native backend
builder (Cabal Flags) ? check ? arg "check" builder (Cabal Flags) ? check `cabalFlag` "check"
-- backend specific -- backend specific
, case backend of , case backend of
...@@ -358,12 +356,12 @@ rtsPackageArgs = package rts ? do ...@@ -358,12 +356,12 @@ rtsPackageArgs = package rts ? do
mconcat mconcat
[ builder (Cabal Flags) ? mconcat [ builder (Cabal Flags) ? mconcat
[ any (wayUnit Profiling) rtsWays ? arg "profiling" [ any (wayUnit Profiling) rtsWays `cabalFlag` "profiling"
, any (wayUnit Debug) rtsWays ? arg "debug" , any (wayUnit Debug) rtsWays `cabalFlag` "debug"
, any (wayUnit Logging) rtsWays ? arg "logging" , any (wayUnit Logging) rtsWays `cabalFlag` "logging"
, any (wayUnit Dynamic) rtsWays ? arg "dynamic" , any (wayUnit Dynamic) rtsWays `cabalFlag` "dynamic"
, useLibffiForAdjustors ? arg "libffi-adjustors" , useLibffiForAdjustors `cabalFlag` "libffi-adjustors"
, Debug `wayUnit` way ? arg "find-ptr" , Debug `wayUnit` way `cabalFlag` "find-ptr"
] ]
, builder (Cabal Setup) ? mconcat , builder (Cabal Setup) ? mconcat
[ if not (null libdwLibraryDir) then arg ("--extra-lib-dirs="++libdwLibraryDir) else mempty [ if not (null libdwLibraryDir) then arg ("--extra-lib-dirs="++libdwLibraryDir) else mempty
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment