[commit: ghc] wip/nfs-locking: Clean up and optimise performance. (7a936b6)
git at git.haskell.org
git at git.haskell.org
Fri Oct 27 00:01:24 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/7a936b6313920818057e807b6898390f7c7df2f8/ghc
>---------------------------------------------------------------
commit 7a936b6313920818057e807b6898390f7c7df2f8
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date: Sat Aug 1 12:02:45 2015 +0100
Clean up and optimise performance.
>---------------------------------------------------------------
7a936b6313920818057e807b6898390f7c7df2f8
src/Oracles/DependencyList.hs | 12 ++++++------
src/Settings/Util.hs | 19 +++++++++++--------
src/Util.hs | 14 ++++++++++++--
3 files changed, 29 insertions(+), 16 deletions(-)
diff --git a/src/Oracles/DependencyList.hs b/src/Oracles/DependencyList.hs
index 0ad9267..1ffc46d 100644
--- a/src/Oracles/DependencyList.hs
+++ b/src/Oracles/DependencyList.hs
@@ -21,7 +21,7 @@ newtype DependencyListKey = DependencyListKey (FilePath, FilePath)
dependencyList :: FilePath -> FilePath -> Action [FilePath]
dependencyList depFile objFile = do
res <- askOracle $ DependencyListKey (depFile, objFile)
- return $ fromMaybe [] res
+ return . fromMaybe [] $ res
-- Oracle for 'path/dist/*.deps' files
dependencyListOracle :: Rules ()
@@ -30,11 +30,11 @@ dependencyListOracle = do
need [file]
putOracle $ "Reading " ++ file ++ "..."
contents <- parseMakefile <$> (liftIO $ readFile file)
- return $ Map.fromList
- $ map (bimap unifyPath (map unifyPath))
- $ map (bimap head concat . unzip)
- $ groupBy ((==) `on` fst)
- $ sortBy (compare `on` fst) contents
+ return . Map.fromList
+ . map (bimap unifyPath (map unifyPath))
+ . map (bimap head concat . unzip)
+ . groupBy ((==) `on` fst)
+ . sortBy (compare `on` fst) $ contents
addOracle $ \(DependencyListKey (file, obj)) ->
Map.lookup (unifyPath obj) <$> deps (unifyPath file)
return ()
diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs
index 3ea13e3..a9aabba 100644
--- a/src/Settings/Util.hs
+++ b/src/Settings/Util.hs
@@ -84,7 +84,7 @@ getHsSources = do
(foundSources, missingSources) <- findModuleFiles dirs "*hs"
- -- Generated source files will live in buildPath and have extension "hs"
+ -- Generated source files live in buildPath and have extension "hs"
let generatedSources = map (\f -> buildPath -/- f <.> "hs") missingSources
return $ foundSources ++ generatedSources
@@ -103,18 +103,21 @@ decodeModule = splitFileName . replaceEq '.' '/'
-- * a list of module files that have not been found, with paths being relative
-- to the module directory, e.g. "CodeGen/Platform", and with no extension.
findModuleFiles :: [FilePath] -> FilePattern -> Expr ([FilePath], [FilePath])
-findModuleFiles dirs ext = do
+findModuleFiles dirs extension = do
modules <- getPkgDataList Modules
- let decodedMods = sort . map decodeModule $ modules
- modDirFiles = map (bimap head sort . unzip)
- . groupBy ((==) `on` fst) $ decodedMods
+ let decodedMods = sort . map decodeModule $ modules
+ modDirFiles = map (bimap head sort . unzip)
+ . groupBy ((==) `on` fst) $ decodedMods
+ matchExtension = (?==) ("*" <.> extension)
result <- lift . fmap concat . forM dirs $ \dir -> do
todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles
forM todo $ \(mDir, mFiles) -> do
- let files = [ dir -/- mDir -/- mFile <.> ext | mFile <- mFiles ]
- found <- fmap (map unifyPath) $ getDirectoryFiles "" files
- return (found, (mDir, map takeBaseName found))
+ let fullDir = dir -/- mDir
+ files <- fmap (filter matchExtension) $ getDirectoryContents fullDir
+ let cmp fe f = compare (dropExtension fe) f
+ found = intersectOrd cmp files mFiles
+ return (map (fullDir -/-) found, (mDir, map dropExtension found))
let foundFiles = concatMap fst result
foundMods = [ (d, f) | (d, fs) <- map snd result, f <- fs ]
diff --git a/src/Util.hs b/src/Util.hs
index 31c0e6a..1c43801 100644
--- a/src/Util.hs
+++ b/src/Util.hs
@@ -6,7 +6,7 @@ module Util (
unifyPath, (-/-),
chunksOfSize,
putColoured, redError, redError_,
- bimap, minusOrd
+ bimap, minusOrd, intersectOrd
) where
import Data.Char
@@ -71,7 +71,7 @@ redError_ = void . redError
bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d)
bimap f g (x, y) = (f x, g y)
--- Depending on Data.List.Ordered only for this function seems an overkill
+-- Depending on Data.List.Ordered only for these two functions seems an overkill
minusOrd :: Ord a => [a] -> [a] -> [a]
minusOrd [] _ = []
minusOrd xs [] = xs
@@ -79,3 +79,13 @@ minusOrd (x:xs) (y:ys) = case compare x y of
LT -> x : minusOrd xs (y:ys)
EQ -> minusOrd xs ys
GT -> minusOrd (x:xs) ys
+
+intersectOrd :: (a -> b -> Ordering) -> [a] -> [b] -> [a]
+intersectOrd cmp = loop
+ where
+ loop [] _ = []
+ loop _ [] = []
+ loop (x:xs) (y:ys) = case cmp x y of
+ LT -> loop xs (y:ys)
+ EQ -> x : loop xs ys
+ GT -> loop (x:xs) ys
More information about the ghc-commits
mailing list