[commit: ghc] wip/nfs-locking: Simplify PackageData. (2f9338d)
git at git.haskell.org
git at git.haskell.org
Thu Oct 26 23:48:04 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/2f9338d4d263435155047a69b5c802c5f76beba1/ghc
>---------------------------------------------------------------
commit 2f9338d4d263435155047a69b5c802c5f76beba1
Author: Andrey Mokhov <andrey.mokhov at ncl.ac.uk>
Date: Wed Jan 7 16:46:10 2015 +0000
Simplify PackageData.
>---------------------------------------------------------------
2f9338d4d263435155047a69b5c802c5f76beba1
src/Oracles.hs | 2 +-
src/Oracles/PackageData.hs | 20 +++++++-------------
2 files changed, 8 insertions(+), 14 deletions(-)
diff --git a/src/Oracles.hs b/src/Oracles.hs
index 093f1b8..3321610 100644
--- a/src/Oracles.hs
+++ b/src/Oracles.hs
@@ -43,5 +43,5 @@ oracleRules = do
need [file]
liftIO $ readConfigFile file
- addOracle $ \(PackageDataPair (file, key)) -> M.lookup key <$> pkgData file
+ addOracle $ \(PackageDataKey (file, key)) -> M.lookup key <$> pkgData file
return ()
diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs
index 2af8e21..4ec89d7 100644
--- a/src/Oracles/PackageData.hs
+++ b/src/Oracles/PackageData.hs
@@ -1,7 +1,7 @@
{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
module Oracles.PackageData (
- PackageDataPair (..),
+ PackageDataKey (..),
PackageData (..)
) where
@@ -9,19 +9,11 @@ import Development.Shake.Classes
import Base
import Util
-newtype PackageDataPair = PackageDataPair (FilePath, String)
+newtype PackageDataKey = PackageDataKey (FilePath, String)
deriving (Show, Typeable, Eq, Hashable, Binary, NFData)
-packagaDataWithDefault :: FilePath -> String -> Action String -> Action String
-packagaDataWithDefault file key defaultAction = do
- maybeValue <- askOracle $ PackageDataPair (file, key)
- case maybeValue of
- Just value -> return value
- Nothing -> defaultAction
-
data PackageData = Modules FilePath | SrcDirs FilePath | PackageKey FilePath
| IncludeDirs FilePath | Deps FilePath | DepKeys FilePath
- deriving Show
instance ShowAction PackageData where
showAction key = do
@@ -33,6 +25,8 @@ instance ShowAction PackageData where
Deps file -> ("DEPS" , file, "" )
DepKeys file -> ("DEP_KEYS" , file, "" )
keyFullName = replaceSeparators '_' $ takeDirectory file ++ "_" ++ keyName
- res <- packagaDataWithDefault file keyFullName $
- error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "."
- return $ words $ if res == "" then ifEmpty else res
+ res <- askOracle $ PackageDataKey (file, keyFullName)
+ return $ words $ case res of
+ Nothing -> error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "."
+ Just "" -> ifEmpty
+ Just value -> value
More information about the ghc-commits
mailing list