[commit: ghc] wip/nfs-locking: Minor revision (268155a)

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


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

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

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

commit 268155a0e615fda224d72d029749f1e2df0fa59b
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Sat Aug 19 13:12:09 2017 +0100

    Minor revision


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

268155a0e615fda224d72d029749f1e2df0fa59b
 src/Hadrian/Haskell/Cabal.hs       |  3 +--
 src/Hadrian/Haskell/Cabal/Parse.hs |  8 ++++----
 src/Hadrian/Oracles/Path.hs        |  4 ++--
 src/Hadrian/Oracles/TextFile.hs    | 23 +++++++++++++----------
 4 files changed, 20 insertions(+), 18 deletions(-)

diff --git a/src/Hadrian/Haskell/Cabal.hs b/src/Hadrian/Haskell/Cabal.hs
index bf21b18..6da1e51 100644
--- a/src/Hadrian/Haskell/Cabal.hs
+++ b/src/Hadrian/Haskell/Cabal.hs
@@ -11,7 +11,6 @@
 -----------------------------------------------------------------------------
 module Hadrian.Haskell.Cabal (pkgNameVersion, pkgDependencies) where
 
-import Data.List
 import Development.Shake
 
 import Hadrian.Haskell.Cabal.Parse
@@ -32,4 +31,4 @@ pkgNameVersion pkg = do
 pkgDependencies :: Package -> Action [PackageName]
 pkgDependencies pkg = do
     cabal <- readCabalFile (pkgCabalFile pkg)
-    return (dependencies cabal \\ [pkgName pkg])
+    return (dependencies cabal)
diff --git a/src/Hadrian/Haskell/Cabal/Parse.hs b/src/Hadrian/Haskell/Cabal/Parse.hs
index ec18781..bc234d4 100644
--- a/src/Hadrian/Haskell/Cabal/Parse.hs
+++ b/src/Hadrian/Haskell/Cabal/Parse.hs
@@ -44,14 +44,14 @@ parseCabal :: FilePath -> IO Cabal
 parseCabal file = do
     gpd <- liftIO $ C.readGenericPackageDescription C.silent file
     let pkgId   = C.package (C.packageDescription gpd)
+        name    = C.unPackageName (C.pkgName pkgId)
+        version = C.display (C.pkgVersion pkgId)
         libDeps = collectDeps (C.condLibrary gpd)
         exeDeps = map (collectDeps . Just . snd) (C.condExecutables gpd)
         allDeps = concat (libDeps : exeDeps)
         sorted  = sort [ C.unPackageName p | C.Dependency p _ <- allDeps ]
-    return $ Cabal
-        (C.unPackageName $ C.pkgName pkgId)
-        (C.display $ C.pkgVersion pkgId)
-        (nubOrd sorted)
+        deps    = nubOrd sorted \\ [name]
+    return $ Cabal name version deps
 
 collectDeps :: Maybe (C.CondTree v [C.Dependency] a) -> [C.Dependency]
 collectDeps Nothing = []
diff --git a/src/Hadrian/Oracles/Path.hs b/src/Hadrian/Oracles/Path.hs
index cab8aa1..4f6406c 100644
--- a/src/Hadrian/Oracles/Path.hs
+++ b/src/Hadrian/Oracles/Path.hs
@@ -52,11 +52,11 @@ pathOracle = do
     void $ addOracle $ \(WindowsPath path) -> do
         Stdout out <- quietly $ cmd ["cygpath", "-m", path]
         let windowsPath = unifyPath $ dropWhileEnd isSpace out
-        putLoud $ "Windows path mapping: " ++ path ++ " => " ++ windowsPath
+        putLoud $ "| Windows path mapping: " ++ path ++ " => " ++ windowsPath
         return windowsPath
 
     void $ addOracle $ \(LookupInPath name) -> do
         let unpack = fromMaybe . error $ "Cannot find executable " ++ quote name
         path <- unifyPath <$> unpack <$> liftIO (findExecutable name)
-        putLoud $ "Executable found: " ++ name ++ " => " ++ path
+        putLoud $ "| Executable found: " ++ name ++ " => " ++ path
         return path
diff --git a/src/Hadrian/Oracles/TextFile.hs b/src/Hadrian/Oracles/TextFile.hs
index 7f80c75..c2ecb4c 100644
--- a/src/Hadrian/Oracles/TextFile.hs
+++ b/src/Hadrian/Oracles/TextFile.hs
@@ -23,8 +23,8 @@ import Development.Shake
 import Development.Shake.Classes
 import Development.Shake.Config
 
-import Hadrian.Utilities
 import Hadrian.Haskell.Cabal.Parse
+import Hadrian.Utilities
 
 newtype TextFile = TextFile FilePath
     deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
@@ -32,7 +32,7 @@ type instance RuleResult TextFile = String
 
 newtype CabalFile = CabalFile FilePath
     deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
-type instance RuleResult CabalFile = String
+type instance RuleResult CabalFile = Cabal
 
 newtype KeyValue = KeyValue (FilePath, String)
     deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
@@ -99,22 +99,25 @@ textFileOracle :: Rules ()
 textFileOracle = do
     text <- newCache $ \file -> do
         need [file]
-        putLoud $ "Reading " ++ file ++ "..."
+        putLoud $ "| TextFile oracle: reading " ++ quote file ++ "..."
         liftIO $ readFile file
+    void $ addOracle $ \(TextFile file) -> text file
+
     kv <- newCache $ \file -> do
         need [file]
-        putLoud $ "Reading " ++ file ++ "..."
+        putLoud $ "| KeyValue oracle: reading " ++ quote file ++ "..."
         liftIO $ readConfigFile file
+    void $ addOracle $ \(KeyValue (file, key)) -> Map.lookup key <$> kv file
+
     kvs <- newCache $ \file -> do
         need [file]
-        putLoud $ "Reading " ++ file ++ "..."
+        putLoud $ "| KeyValues oracle: reading " ++ quote file ++ "..."
         contents <- map words <$> readFileLines file
         return $ Map.fromList [ (key, values) | (key:values) <- contents ]
+    void $ addOracle $ \(KeyValues (file, key)) -> Map.lookup key <$> kvs file
+
     cabal <- newCache $ \file -> do
         need [file]
-        putLoud $ "Reading " ++ file ++ "..."
+        putLoud $ "| CabalFile oracle: reading " ++ quote file ++ "..."
         liftIO $ parseCabal file
-    void $ addOracle $ \(TextFile   file      ) -> text                   file
-    void $ addOracle $ \(KeyValue  (file, key)) -> Map.lookup key <$> kv  file
-    void $ addOracle $ \(KeyValues (file, key)) -> Map.lookup key <$> kvs file
-    void $ addOracle $ \(CabalFile  file      ) -> cabal                  file
+    void $ addOracle $ \(CabalFile file) -> cabal file



More information about the ghc-commits mailing list