[commit: ghc] wip/nfs-locking: Renames absoluteCommand to lookupInPath (6f88557)
git at git.haskell.org
git at git.haskell.org
Fri Oct 27 00:00:09 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/6f88557b1fa263bf22f698ec3384a0ab37ed3447/ghc
>---------------------------------------------------------------
commit 6f88557b1fa263bf22f698ec3384a0ab37ed3447
Author: Moritz Angermann <moritz.angermann at gmail.com>
Date: Thu Jan 7 20:37:59 2016 +0800
Renames absoluteCommand to lookupInPath
>---------------------------------------------------------------
6f88557b1fa263bf22f698ec3384a0ab37ed3447
shaking-up-ghc.cabal | 2 +-
src/Builder.hs | 2 +-
src/Oracles.hs | 4 ++--
.../{AbsoluteCommand.hs => LookupInPath.hs} | 22 +++++++++++-----------
src/Rules/Oracles.hs | 16 ++++++++--------
5 files changed, 23 insertions(+), 23 deletions(-)
diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal
index 96efe57..c680b85 100644
--- a/shaking-up-ghc.cabal
+++ b/shaking-up-ghc.cabal
@@ -22,12 +22,12 @@ executable ghc-shake
, Expression
, GHC
, Oracles
- , Oracles.AbsoluteCommand
, Oracles.ArgsHash
, Oracles.Config
, Oracles.Config.Flag
, Oracles.Config.Setting
, Oracles.Dependencies
+ , Oracles.LookupInPath
, Oracles.ModuleFiles
, Oracles.PackageData
, Oracles.PackageDeps
diff --git a/src/Builder.hs b/src/Builder.hs
index 743c956..0613452 100644
--- a/src/Builder.hs
+++ b/src/Builder.hs
@@ -98,7 +98,7 @@ builderPath builder = do
case (path, windows) of
("", _) -> return path
(p, True) -> fixAbsolutePathOnWindows (p -<.> exe)
- (p, False) -> lookupInPathOracle (p -<.> exe)
+ (p, False) -> lookupInPath (p -<.> exe)
getBuilderPath :: Builder -> ReaderT a Action FilePath
getBuilderPath = lift . builderPath
diff --git a/src/Oracles.hs b/src/Oracles.hs
index 07e92f2..564c7bb 100644
--- a/src/Oracles.hs
+++ b/src/Oracles.hs
@@ -1,19 +1,19 @@
module Oracles (
- module Oracles.AbsoluteCommand,
module Oracles.Config,
module Oracles.Config.Flag,
module Oracles.Config.Setting,
module Oracles.Dependencies,
+ module Oracles.LookupInPath,
module Oracles.PackageData,
module Oracles.PackageDeps,
module Oracles.WindowsRoot
) where
-import Oracles.AbsoluteCommand
import Oracles.Config
import Oracles.Config.Flag
import Oracles.Config.Setting
import Oracles.Dependencies
+import Oracles.LookupInPath
import Oracles.PackageData
import Oracles.PackageDeps
import Oracles.WindowsRoot
diff --git a/src/Oracles/AbsoluteCommand.hs b/src/Oracles/LookupInPath.hs
similarity index 61%
rename from src/Oracles/AbsoluteCommand.hs
rename to src/Oracles/LookupInPath.hs
index c60f429..c2a05e2 100644
--- a/src/Oracles/AbsoluteCommand.hs
+++ b/src/Oracles/LookupInPath.hs
@@ -1,26 +1,26 @@
{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
-module Oracles.AbsoluteCommand (
- lookupInPathOracle, absoluteCommandOracle
+module Oracles.LookupInPath (
+ lookupInPath, lookupInPathOracle
) where
import Base
-newtype AbsoluteCommand = AbsoluteCommand String
+newtype LookupInPath = LookupInPath String
deriving (Show, Typeable, Eq, Hashable, Binary, NFData)
-- | Fetches the absolute FilePath to a given FilePath from the
-- Oracle.
-absoluteCommand :: FilePath -> Action FilePath
-absoluteCommand = askOracle . AbsoluteCommand
+commandPath :: FilePath -> Action FilePath
+commandPath = askOracle . LookupInPath
-- | Lookup a @command@ in @PATH@ environment.
-lookupInPathOracle :: FilePath -> Action FilePath
-lookupInPathOracle c
+lookupInPath :: FilePath -> Action FilePath
+lookupInPath c
| c /= takeFileName c = return c
- | otherwise = absoluteCommand c
+ | otherwise = commandPath c
-absoluteCommandOracle :: Rules ()
-absoluteCommandOracle = do
+lookupInPathOracle :: Rules ()
+lookupInPathOracle = do
o <- newCache $ \c -> do
envPaths <- wordsWhen (== ':') <$> getEnvWithDefault "" "PATH"
let candidates = map (-/- c) envPaths
@@ -28,5 +28,5 @@ absoluteCommandOracle = do
fullCommand <- head <$> filterM doesFileExist candidates
putOracle $ "Found '" ++ c ++ "' at " ++ "'" ++ fullCommand ++ "'"
return fullCommand
- _ <- addOracle $ \(AbsoluteCommand c) -> o c
+ _ <- addOracle $ \(LookupInPath c) -> o c
return ()
diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs
index a4d6c70..f44b4ad 100644
--- a/src/Rules/Oracles.hs
+++ b/src/Rules/Oracles.hs
@@ -7,11 +7,11 @@ import Oracles.ModuleFiles
oracleRules :: Rules ()
oracleRules = do
- absoluteCommandOracle -- see Oracles.WindowsRoot
- argsHashOracle -- see Oracles.ArgsHash
- configOracle -- see Oracles.Config
- dependenciesOracle -- see Oracles.Dependencies
- moduleFilesOracle -- see Oracles.ModuleFiles
- packageDataOracle -- see Oracles.PackageData
- packageDepsOracle -- see Oracles.PackageDeps
- windowsRootOracle -- see Oracles.WindowsRoot
+ argsHashOracle -- see Oracles.ArgsHash
+ configOracle -- see Oracles.Config
+ dependenciesOracle -- see Oracles.Dependencies
+ lookupInPathOracle -- see Oracles.LookupInPath
+ moduleFilesOracle -- see Oracles.ModuleFiles
+ packageDataOracle -- see Oracles.PackageData
+ packageDepsOracle -- see Oracles.PackageDeps
+ windowsRootOracle -- see Oracles.WindowsRoot
More information about the ghc-commits
mailing list