[commit: ghc] wip/nfs-locking: Drop TransitiveDepNames (97d37ea)
git at git.haskell.org
git at git.haskell.org
Fri Oct 27 00:15:49 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/97d37ea64e04bf18fb4ff57d2cbd3d42d05a2cf9/ghc
>---------------------------------------------------------------
commit 97d37ea64e04bf18fb4ff57d2cbd3d42d05a2cf9
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date: Sun May 22 01:46:39 2016 +0100
Drop TransitiveDepNames
>---------------------------------------------------------------
97d37ea64e04bf18fb4ff57d2cbd3d42d05a2cf9
src/Oracles/PackageData.hs | 10 +++-------
1 file changed, 3 insertions(+), 7 deletions(-)
diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs
index af9e255..92c2e99 100644
--- a/src/Oracles/PackageData.hs
+++ b/src/Oracles/PackageData.hs
@@ -1,7 +1,6 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Oracles.PackageData (
- PackageData (..), PackageDataList (..),
- pkgData, pkgDataList, packageDataOracle
+ PackageData (..), PackageDataList (..), pkgData, pkgDataList, packageDataOracle
) where
import Development.Shake.Config
@@ -31,7 +30,6 @@ data PackageDataList = CcArgs FilePath
| LdArgs FilePath
| Modules FilePath
| SrcDirs FilePath
- | TransitiveDepNames FilePath
newtype PackageDataKey = PackageDataKey (FilePath, String)
deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
@@ -77,16 +75,14 @@ pkgDataList packageData = fmap (map unquote . words) $ case packageData of
LdArgs path -> askPackageData path "LD_OPTS"
Modules path -> askPackageData path "MODULES"
SrcDirs path -> askPackageData path "HS_SRC_DIRS"
- TransitiveDepNames path -> askPackageData path "TRANSITIVE_DEP_NAMES"
where
unquote = dropWhile (== '\'') . dropWhileEnd (== '\'')
-- | Oracle for 'package-data.mk' files.
packageDataOracle :: Rules ()
-packageDataOracle = do
+packageDataOracle = void $ do
keys <- newCache $ \file -> do
need [file]
putLoud $ "Reading " ++ file ++ "..."
liftIO $ readConfigFile file
- _ <- addOracle $ \(PackageDataKey (file, key)) -> Map.lookup key <$> keys file
- return ()
+ addOracle $ \(PackageDataKey (file, key)) -> Map.lookup key <$> keys file
More information about the ghc-commits
mailing list