[commit: ghc] wip/nfs-locking: Clean up. (eda28da)

git at git.haskell.org git at git.haskell.org
Thu Oct 26 23:27:39 UTC 2017


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

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

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

commit eda28da9f239b66ea1791d0ac9850cfae1232248
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Tue Dec 22 05:07:32 2015 +0000

    Clean up.


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

eda28da9f239b66ea1791d0ac9850cfae1232248
 src/Rules/Library.hs |  2 +-
 src/Settings.hs      | 11 +++++------
 2 files changed, 6 insertions(+), 7 deletions(-)

diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs
index 134e2be..ff5ce63 100644
--- a/src/Rules/Library.hs
+++ b/src/Rules/Library.hs
@@ -49,7 +49,7 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do
         putSuccess $ renderBox
             [ "Successfully built package library '"
               ++ pkgName pkg
-              ++ "' (stage " ++ show stage ++ ", way "++ show way ++ ")."
+              ++ "' (" ++ show stage ++ ", way "++ show way ++ ")."
             , "Package synopsis: " ++ dropWhileEnd isPunctuation synopsis ++ "."
             ]
 
diff --git a/src/Settings.hs b/src/Settings.hs
index fd7c14c..9a0e07d 100644
--- a/src/Settings.hs
+++ b/src/Settings.hs
@@ -53,26 +53,25 @@ getPackageSources = do
     return $ foundSources ++ fixGhcPrim generatedSources
 
 -- findModuleFiles scans a list of given directories and finds files matching a
--- given extension pattern (e.g., "*hs") that correspond to modules of the
--- currently built package. Missing module files are returned in a separate
--- list. The returned pair contains the following:
+-- given pattern (e.g., "*hs") that correspond to modules of the currently built
+-- package. Missing module files are returned in a separate list. The returned
+-- pair contains the following:
 -- * a list of found module files, with paths being relative to one of given
 --   directories, e.g. "codeGen/CodeGen/Platform.hs" for the compiler package.
 -- * 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 extension = do
+findModuleFiles dirs pattern = do
     modules <- getPkgDataList Modules
     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 fullDir = dir -/- mDir
-            files <- fmap (filter matchExtension) $ getDirectoryContents fullDir
+            files <- getDirectoryFiles fullDir [pattern]
             let cmp fe f = compare (dropExtension fe) f
                 found    = intersectOrd cmp files mFiles
             return (map (fullDir -/-) found, (mDir, map dropExtension found))



More information about the ghc-commits mailing list