[commit: ghc] wip/nfs-locking: Lookup builder in PATH if they are given without path. (4478851)
git at git.haskell.org
git at git.haskell.org
Fri Oct 27 00:27:32 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/44788518cb14c59788fdf320b9ca2d11e11509ca/ghc
>---------------------------------------------------------------
commit 44788518cb14c59788fdf320b9ca2d11e11509ca
Author: Moritz Angermann <moritz.angermann at gmail.com>
Date: Wed Jan 6 23:22:43 2016 +0800
Lookup builder in PATH if they are given without path.
`system-gcc` may be given without path (e.g. `clang`), this patch adds lookup using `which`
for those commands. Also drops calling `fixAbsolutePathOnWindows` on non window hosts.
Fixes #26
>---------------------------------------------------------------
44788518cb14c59788fdf320b9ca2d11e11509ca
src/Builder.hs | 4 +++-
src/Oracles/WindowsRoot.hs | 11 ++++++++++-
2 files changed, 13 insertions(+), 2 deletions(-)
diff --git a/src/Builder.hs b/src/Builder.hs
index 5ed9e1d..6e4dba5 100644
--- a/src/Builder.hs
+++ b/src/Builder.hs
@@ -94,7 +94,9 @@ builderPath builder = do
path <- askConfigWithDefault (builderKey builder) $
putError $ "\nCannot find path to '" ++ (builderKey builder)
++ "' in configuration files."
- fixAbsolutePathOnWindows $ if null path then "" else path -<.> exe
+ windows <- windowsHost
+ let path' = if null path then "" else path -<.> exe in
+ (if windows then fixAbsolutePathOnWindows else lookupInPath) path'
getBuilderPath :: Builder -> ReaderT a Action FilePath
getBuilderPath = lift . builderPath
diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs
index 413f289..195f591 100644
--- a/src/Oracles/WindowsRoot.hs
+++ b/src/Oracles/WindowsRoot.hs
@@ -1,6 +1,6 @@
{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
module Oracles.WindowsRoot (
- windowsRoot, fixAbsolutePathOnWindows, topDirectory, windowsRootOracle
+ windowsRoot, fixAbsolutePathOnWindows, lookupInPath, topDirectory, windowsRootOracle
) where
import Data.Char (isSpace)
@@ -38,6 +38,15 @@ fixAbsolutePathOnWindows path = do
else
return path
+-- | Lookup a @command@ in @PATH@ environment.
+lookupInPath :: FilePath -> Action FilePath
+lookupInPath command
+ | command /= takeFileName command = return command
+ | otherwise = do
+ Stdout out <- quietly $ cmd ["which", command]
+ let path = dropWhileEnd isSpace out
+ return path
+
-- Oracle for windowsRoot. This operation requires caching as looking up
-- the root is slow (at least the current implementation).
windowsRootOracle :: Rules ()
More information about the ghc-commits
mailing list