[commit: ghc] wip/nfs-locking: Moves wordsWhen into Base, and adjusts names and types to be more descriptive. (1d3de4c)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 00:00:05 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/nfs-locking
Link       : http://ghc.haskell.org/trac/ghc/changeset/1d3de4cf66717bd5c10dda3b10b305aa736abddb/ghc

>---------------------------------------------------------------

commit 1d3de4cf66717bd5c10dda3b10b305aa736abddb
Author: Moritz Angermann <moritz.angermann at gmail.com>
Date:   Thu Jan 7 20:17:23 2016 +0800

    Moves wordsWhen into Base, and adjusts names and types to be more descriptive.


>---------------------------------------------------------------

1d3de4cf66717bd5c10dda3b10b305aa736abddb
 src/Base.hs                    | 11 ++++++++++-
 src/Builder.hs                 |  2 +-
 src/Oracles/AbsoluteCommand.hs | 20 ++++++--------------
 3 files changed, 17 insertions(+), 16 deletions(-)

diff --git a/src/Base.hs b/src/Base.hs
index 36f2eb9..8830a7c 100644
--- a/src/Base.hs
+++ b/src/Base.hs
@@ -24,7 +24,7 @@ module Base (
     -- * Miscellaneous utilities
     bimap, minusOrd, intersectOrd, replaceEq, replace, quote, chunksOfSize,
     replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-),
-    versionToInt, removeFileIfExists, removeDirectoryIfExists
+    versionToInt, removeFileIfExists, removeDirectoryIfExists, wordsWhen
     ) where
 
 import Control.Applicative
@@ -238,3 +238,12 @@ removeFileIfExists f = liftIO . whenM (IO.doesFileExist f) $ IO.removeFile f
 removeDirectoryIfExists :: FilePath -> Action ()
 removeDirectoryIfExists d =
     liftIO . whenM (IO.doesDirectoryExist d) $ IO.removeDirectoryRecursive d
+
+-- | Split function. Splits a string @s@ into chunks
+-- when the predicate @p@ holds. See: http://stackoverflow.com/a/4981265
+wordsWhen :: (Char -> Bool) -> String -> [String]
+wordsWhen p s =
+    case dropWhile p s of
+        "" -> []
+        s' -> w : wordsWhen p s''
+            where (w, s'') = break p s'
diff --git a/src/Builder.hs b/src/Builder.hs
index 0613452..743c956 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) -> lookupInPath (p -<.> exe)
+        (p, False) -> lookupInPathOracle (p -<.> exe)
 
 getBuilderPath :: Builder -> ReaderT a Action FilePath
 getBuilderPath = lift . builderPath
diff --git a/src/Oracles/AbsoluteCommand.hs b/src/Oracles/AbsoluteCommand.hs
index 23de6ff..c60f429 100644
--- a/src/Oracles/AbsoluteCommand.hs
+++ b/src/Oracles/AbsoluteCommand.hs
@@ -1,6 +1,6 @@
 {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
 module Oracles.AbsoluteCommand (
-    lookupInPath, absoluteCommandOracle
+    lookupInPathOracle, absoluteCommandOracle
     ) where
 
 import Base
@@ -8,25 +8,17 @@ import Base
 newtype AbsoluteCommand = AbsoluteCommand String
     deriving (Show, Typeable, Eq, Hashable, Binary, NFData)
 
-absoluteCommand :: String -> Action String
+-- | Fetches the absolute FilePath to a given FilePath from the
+-- Oracle.
+absoluteCommand :: FilePath -> Action FilePath
 absoluteCommand = askOracle . AbsoluteCommand
 
 -- | Lookup a @command@ in @PATH@ environment.
-lookupInPath :: FilePath -> Action FilePath
-lookupInPath c
+lookupInPathOracle :: FilePath -> Action FilePath
+lookupInPathOracle c
     | c /= takeFileName c = return c
     | otherwise           = absoluteCommand c
 
--- | Split function. Splits a string @s@ into chunks
--- when the predicate @p@ holds. See: http://stackoverflow.com/a/4981265
-wordsWhen :: (Char -> Bool) -> String -> [String]
-wordsWhen p s =
-    case dropWhile p s of
-        "" -> []
-        s' -> w : wordsWhen p s''
-            where (w, s'') = break p s'
-
-
 absoluteCommandOracle :: Rules ()
 absoluteCommandOracle = do
     o <- newCache $ \c -> do



More information about the ghc-commits mailing list