[commit: ghc] wip/nfs-locking: Add comments. Minor refactoring. (acde0ea)
git at git.haskell.org
git at git.haskell.org
Thu Oct 26 23:11:58 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/acde0ea23775e06a4cfd2f60974c075e8babdc86/ghc
>---------------------------------------------------------------
commit acde0ea23775e06a4cfd2f60974c075e8babdc86
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date: Tue Jun 16 01:09:37 2015 +0100
Add comments. Minor refactoring.
>---------------------------------------------------------------
acde0ea23775e06a4cfd2f60974c075e8babdc86
src/Expression.hs | 5 +++--
src/Rules.hs | 3 +--
src/Settings.hs | 1 +
src/Settings/GhcCabal.hs | 2 +-
src/Settings/Util.hs | 5 +++++
src/Switches.hs | 2 ++
src/Targets.hs | 7 ++++---
src/UserSettings.hs | 7 ++++++-
8 files changed, 23 insertions(+), 9 deletions(-)
diff --git a/src/Expression.hs b/src/Expression.hs
index 81ed26f..a0c3bf0 100644
--- a/src/Expression.hs
+++ b/src/Expression.hs
@@ -124,7 +124,7 @@ interpretDiff env = interpret env . fromDiff
(??) :: Monoid a => Predicate -> (Expr a, Expr a) -> Expr a
p ?? (t, f) = p ? t <> (liftM not p) ? f
--- Basic predicates
+-- Basic predicates (see Switches.hs for derived predicates)
stage :: Stage -> Predicate
stage s = liftM (s ==) (asks getStage)
@@ -137,6 +137,7 @@ package p = liftM (p ==) (asks getPackage)
configKeyValue :: String -> String -> Predicate
configKeyValue key value = liftM (value ==) (lift $ askConfig key)
--- checks if there is at least one match
+-- Check if there is at least one match
+-- Example: configKeyValues "host-os-cpp" ["mingw32", "cygwin32"]
configKeyValues :: String -> [String] -> Predicate
configKeyValues key values = liftM (`elem` values) (lift $ askConfig key)
diff --git a/src/Rules.hs b/src/Rules.hs
index 5d59ae6..a84f30e 100644
--- a/src/Rules.hs
+++ b/src/Rules.hs
@@ -13,7 +13,7 @@ import Rules.Package
import Settings.Packages
-- generateTargets needs package-data.mk files of all target packages
--- TODO: make interpret total
+-- TODO: make interpretDiff total
generateTargets :: Rules ()
generateTargets = action $
forM_ [Stage0 ..] $ \stage -> do
@@ -23,7 +23,6 @@ generateTargets = action $
let dir = targetDirectory stage pkg
need [pkgPath pkg </> dir </> "package-data.mk"]
--- TODO: make interpret total
-- TODO: add Stage2 (compiler only?)
packageRules :: Rules ()
packageRules =
diff --git a/src/Settings.hs b/src/Settings.hs
index cde678e..fb0938a 100644
--- a/src/Settings.hs
+++ b/src/Settings.hs
@@ -12,6 +12,7 @@ import Expression hiding (when, liftIO)
settings :: Settings
settings = defaultSettings <> userSettings
+-- TODO: add all other settings
defaultSettings :: Settings
defaultSettings = mconcat
[ cabalSettings
diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs
index 21ca0e0..4388b17 100644
--- a/src/Settings/GhcCabal.hs
+++ b/src/Settings/GhcCabal.hs
@@ -105,7 +105,7 @@ packageConstraints = do
++ cabal ++ "'."
args $ concatMap (\c -> ["--constraint", c]) $ constraints
--- TODO: remove
+-- TODO: should be in a different file
ccSettings :: Settings
ccSettings = validating ? do
let gccGe46 = liftM not gccLt46
diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs
index dba49d5..74190ec 100644
--- a/src/Settings/Util.hs
+++ b/src/Settings/Util.hs
@@ -47,6 +47,7 @@ argStagedConfigList key = do
stage <- asks getStage
argConfigList (stagedKey stage key)
+-- Pass arguments to Gcc and corresponding lists of sub-arguments of GhcCabal
appendCcArgs :: [String] -> Settings
appendCcArgs args = do
stage <- asks getStage
@@ -54,6 +55,10 @@ appendCcArgs args = do
, builder GhcCabal ? appendSub "--configure-option=CFLAGS" args
, builder GhcCabal ? appendSub "--gcc-options" args ]
+
+
+
+
-- packageData :: Arity -> String -> Settings
-- packageData arity key =
-- return $ EnvironmentParameter $ PackageData arity key Nothing Nothing
diff --git a/src/Switches.hs b/src/Switches.hs
index 5436d94..3c6abac 100644
--- a/src/Switches.hs
+++ b/src/Switches.hs
@@ -12,6 +12,8 @@ module Switches (
import Base
import Expression
+-- TODO: This setting should be moved to UserSettings.hs
+-- TODO: Define three packages for integer library instead of one in Targets.hs
-- Support for multiple integer library implementations
data IntegerLibraryImpl = IntegerGmp | IntegerGmp2 | IntegerSimple
diff --git a/src/Targets.hs b/src/Targets.hs
index 1839112..2c61152 100644
--- a/src/Targets.hs
+++ b/src/Targets.hs
@@ -20,6 +20,7 @@ import Oracles.Builder
-- * build/ : contains compiled object code
-- * doc/ : produced by haddock
-- * package-data.mk : contains output of ghc-cabal applied to pkgCabal
+-- TODO: This is currently not user configurable. Is this right?
targetDirectory :: Stage -> Package -> FilePath
targetDirectory stage package
| package == compiler = "stage" ++ show (fromEnum stage + 1)
@@ -85,14 +86,14 @@ customPackageSettings :: Settings
customPackageSettings = mconcat
[ package integerLibrary ?
mconcat [ windowsHost ? builder GhcCabal ?
- append ["--configure-option=--with-intree-gmp"]
+ arg "--configure-option=--with-intree-gmp"
, appendCcArgs ["-Ilibraries/integer-gmp2/gmp"] ]
, package base ?
- builder GhcCabal ? append ["--flags=" ++ integerLibraryName]
+ builder GhcCabal ? arg ("--flags=" ++ integerLibraryName)
, package ghcPrim ?
- builder GhcCabal ? append ["--flag=include-ghc-prim"] ]
+ builder GhcCabal ? arg "--flag=include-ghc-prim" ]
-- Note [Cabal name weirdness]
-- Find out if we can move the contents to just Cabal/
diff --git a/src/UserSettings.hs b/src/UserSettings.hs
index f443659..378db1c 100644
--- a/src/UserSettings.hs
+++ b/src/UserSettings.hs
@@ -10,18 +10,23 @@ import Ways
import Targets
import Switches
import Expression
+import Settings.Util
-- No user-specific settings by default
userSettings :: Settings
userSettings = mempty
+-- Control conditions of which packages get to be built
+-- TODO: adding *new* packages is not possible (see knownPackages in Targets.hs)
userPackages :: Packages
userPackages = mempty
+-- Control which ways are built
userWays :: Ways
userWays = mempty
-- User-defined predicates
+-- TODO: migrate more predicates here from configuration files
buildHaddock :: Predicate
buildHaddock = return True
@@ -31,7 +36,7 @@ validating = return False
-- Examples:
userSettings' :: Settings
userSettings' = mconcat
- [ package compiler ? stage0 ? append ["foo", "bar"]
+ [ package compiler ? stage0 ? arg "foo"
, builder (Ghc Stage0) ? remove ["-O2"]
, builder GhcCabal ? removeSub "--configure-option=CFLAGS" ["-Werror"] ]
More information about the ghc-commits
mailing list