[commit: ghc] wip/nfs-locking: Minor revision (7792fbb)
git at git.haskell.org
git at git.haskell.org
Fri Oct 27 00:55:57 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/7792fbbebbb68f8f2b2e95d29a6365f74376b398/ghc
>---------------------------------------------------------------
commit 7792fbbebbb68f8f2b2e95d29a6365f74376b398
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date: Wed Aug 16 13:33:16 2017 +0100
Minor revision
>---------------------------------------------------------------
7792fbbebbb68f8f2b2e95d29a6365f74376b398
src/Expression.hs | 13 +++++++++++--
src/GHC.hs | 6 +++++-
src/Settings.hs | 13 -------------
3 files changed, 16 insertions(+), 16 deletions(-)
diff --git a/src/Expression.hs b/src/Expression.hs
index 8da4a6f..647c057 100644
--- a/src/Expression.hs
+++ b/src/Expression.hs
@@ -16,8 +16,8 @@ module Expression (
Context, vanillaContext, stageContext, Target,
-- * Convenient accessors
- getBuildRoot, getBuildPath, getContext, getStage, getPackage, getBuilder,
- getOutputs, getInputs, getWay, getInput, getOutput,
+ getBuildRoot, getBuildPath, getContext, getPkgData, getPkgDataList, getStage,
+ getPackage, getBuilder, getOutputs, getInputs, getWay, getInput, getOutput,
-- * Re-exports
module Base
@@ -28,6 +28,7 @@ import Hadrian.Expression hiding (Expr, Predicate, Args)
import Base
import Context (Context, vanillaContext, stageContext, getBuildPath, getStage, getPackage, getWay)
+import Oracles.PackageData
import Target hiding (builder, inputs, outputs)
-- | @Expr a@ is a computation that produces a value of type @Action a@ and can
@@ -42,6 +43,14 @@ type Args = H.Args Context Builder
type Packages = Expr [Package]
type Ways = Expr [Way]
+-- | Get a value from the @package-data.mk@ file of the current context.
+getPkgData :: (FilePath -> PackageData) -> Expr String
+getPkgData key = expr . pkgData . key =<< getBuildPath
+
+-- | Get a list of values from the @package-data.mk@ file of the current context.
+getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String]
+getPkgDataList key = expr . pkgDataList . key =<< getBuildPath
+
-- | Is the build currently in the provided stage?
stage :: Stage -> Predicate
stage s = (s ==) <$> getStage
diff --git a/src/GHC.hs b/src/GHC.hs
index 6d49630..1141030 100644
--- a/src/GHC.hs
+++ b/src/GHC.hs
@@ -18,7 +18,7 @@ module GHC (
rtsContext, rtsBuildPath, rtsConfIn,
-- * Miscellaneous
- ghcSplitPath, stripCmdPath, inplaceInstallPath
+ ghcSplitPath, stripCmdPath, inplaceInstallPath, buildDll0
) where
import Base
@@ -192,3 +192,7 @@ rtsBuildPath = buildPath rtsContext
rtsConfIn :: FilePath
rtsConfIn = pkgPath rts -/- "package.conf.in"
+buildDll0 :: Context -> Action Bool
+buildDll0 Context {..} = do
+ windows <- windowsHost
+ return $ windows && stage == Stage1 && package == compiler
diff --git a/src/Settings.hs b/src/Settings.hs
index 2b4b0ef..f25265b 100644
--- a/src/Settings.hs
+++ b/src/Settings.hs
@@ -13,8 +13,6 @@ import CommandLine
import Expression
import Flavour
import GHC
-import Oracles.PackageData
-import Oracles.Setting
import {-# SOURCE #-} Settings.Default
import Settings.Flavours.Development
import Settings.Flavours.Performance
@@ -38,12 +36,6 @@ getPackages = expr flavour >>= packages
stagePackages :: Stage -> Action [Package]
stagePackages stage = interpretInContext (stageContext stage) getPackages
-getPkgData :: (FilePath -> PackageData) -> Expr String
-getPkgData key = expr . pkgData . key =<< getBuildPath
-
-getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String]
-getPkgDataList key = expr . pkgDataList . key =<< getBuildPath
-
hadrianFlavours :: [Flavour]
hadrianFlavours =
[ defaultFlavour, developmentFlavour Stage1, developmentFlavour Stage2
@@ -154,8 +146,3 @@ stage1Only = defaultStage1Only
-- | Install's DESTDIR setting.
destDir :: FilePath
destDir = defaultDestDir
-
-buildDll0 :: Context -> Action Bool
-buildDll0 Context {..} = do
- windows <- windowsHost
- return $ windows && stage == Stage1 && package == compiler
More information about the ghc-commits
mailing list