[commit: ghc] wip/nfs-locking: Remove user.config file, rename default.config to system.config. (a8cfbde)
git at git.haskell.org
git at git.haskell.org
Thu Oct 26 23:13:14 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/a8cfbde5e0fc9df532d739815a28ac2e022eff0d/ghc
>---------------------------------------------------------------
commit a8cfbde5e0fc9df532d739815a28ac2e022eff0d
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date: Sun Jul 19 00:15:45 2015 +0100
Remove user.config file, rename default.config to system.config.
>---------------------------------------------------------------
a8cfbde5e0fc9df532d739815a28ac2e022eff0d
.gitignore | 2 +-
cfg/configure.ac | 2 +-
cfg/{default.config.in => system.config.in} | 0
cfg/user.config | 4 ----
src/Config.hs | 4 ++--
src/Oracles.hs | 37 ++++++++---------------------
src/Oracles/Option.hs | 4 ++--
7 files changed, 16 insertions(+), 37 deletions(-)
diff --git a/.gitignore b/.gitignore
index dad3a3c..94b9664 100644
--- a/.gitignore
+++ b/.gitignore
@@ -2,5 +2,5 @@
*.hi
_shake/
_build/
-cfg/default.config
+cfg/system.config
arg/*/*.txt
diff --git a/cfg/configure.ac b/cfg/configure.ac
index 125fd49..687eac7 100644
--- a/cfg/configure.ac
+++ b/cfg/configure.ac
@@ -978,7 +978,7 @@ if grep ' ' compiler/ghc.cabal.in 2>&1 >/dev/null; then
AC_MSG_ERROR([compiler/ghc.cabal.in contains tab characters; please remove them])
fi
-AC_CONFIG_FILES([shake/cfg/default.config mk/config.mk mk/install.mk mk/project.mk compiler/ghc.cabal ghc/ghc-bin.cabal utils/runghc/runghc.cabal settings docs/users_guide/ug-book.xml docs/users_guide/ug-ent.xml docs/index.html libraries/prologue.txt distrib/configure.ac])
+AC_CONFIG_FILES([shake/cfg/system.config mk/config.mk mk/install.mk mk/project.mk compiler/ghc.cabal ghc/ghc-bin.cabal utils/runghc/runghc.cabal settings docs/users_guide/ug-book.xml docs/users_guide/ug-ent.xml docs/index.html libraries/prologue.txt distrib/configure.ac])
AC_OUTPUT
# We got caught by
diff --git a/cfg/default.config.in b/cfg/system.config.in
similarity index 100%
rename from cfg/default.config.in
rename to cfg/system.config.in
diff --git a/cfg/user.config b/cfg/user.config
deleted file mode 100644
index b72c5b4..0000000
--- a/cfg/user.config
+++ /dev/null
@@ -1,4 +0,0 @@
-# Override default settings (stored in default.config file):
-#===========================================================
-
-lax-dependencies = YES
diff --git a/src/Config.hs b/src/Config.hs
index 1a4ef9a..0dc67a2 100644
--- a/src/Config.hs
+++ b/src/Config.hs
@@ -17,7 +17,7 @@ autoconfRules = do
configureRules :: Rules ()
configureRules = do
- cfgPath </> "default.config" %> \out -> do
- need [cfgPath </> "default.config.in", "configure"]
+ cfgPath </> "system.config" %> \out -> do
+ need [cfgPath </> "system.config.in", "configure"]
putColoured White "Running configure..."
cmd "bash configure" -- TODO: get rid of 'bash'
diff --git a/src/Oracles.hs b/src/Oracles.hs
index e6e31f9..cd8c879 100644
--- a/src/Oracles.hs
+++ b/src/Oracles.hs
@@ -6,45 +6,25 @@ module Oracles (
import Development.Shake.Config
import Development.Shake.Util
import qualified Data.HashMap.Strict as M
--- TODO: get rid of Bifunctor dependency
-import Data.Bifunctor
import Base
import Util
import Config
+import Control.Monad.Extra
import Oracles.Base
import Oracles.PackageData
-import Control.Monad.Extra
import Oracles.DependencyList
-defaultConfig, userConfig :: FilePath
-defaultConfig = cfgPath </> "default.config"
-userConfig = cfgPath </> "user.config"
-
-- Oracle for configuration files
configOracle :: Rules ()
configOracle = do
+ let configFile = cfgPath </> "system.config"
cfg <- newCache $ \() -> do
- unlessM (doesFileExist $ defaultConfig <.> "in") $
- redError_ $ "\nDefault configuration file '"
- ++ (defaultConfig <.> "in")
+ unlessM (doesFileExist $ configFile <.> "in") $
+ redError_ $ "\nConfiguration file '" ++ (configFile <.> "in")
++ "' is missing; unwilling to proceed."
- need [defaultConfig]
- putOracle $ "Reading " ++ unifyPath defaultConfig ++ "..."
- cfgDefault <- liftIO $ readConfigFile defaultConfig
- existsUser <- doesFileExist userConfig
- cfgUser <- if existsUser
- then do
- putOracle $ "Reading "
- ++ unifyPath userConfig ++ "..."
- liftIO $ readConfigFile userConfig
- else do
- putColoured Red $
- "\nUser defined configuration file '"
- ++ userConfig ++ "' is missing; "
- ++ "proceeding with default configuration.\n"
- return M.empty
- putColoured Green $ "Finished processing configuration files."
- return $ cfgUser `M.union` cfgDefault
+ need [configFile]
+ putOracle $ "Reading " ++ unifyPath configFile ++ "..."
+ liftIO $ readConfigFile configFile
addOracle $ \(ConfigKey key) -> M.lookup key <$> cfg ()
return ()
@@ -59,6 +39,9 @@ packageDataOracle = do
M.lookup key <$> pkgData (unifyPath file)
return ()
+bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d)
+bimap f g (x, y) = (f x, g y)
+
-- Oracle for 'path/dist/*.deps' files
dependencyOracle :: Rules ()
dependencyOracle = do
diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs
index f1a35e2..ff0c5fc 100644
--- a/src/Oracles/Option.hs
+++ b/src/Oracles/Option.hs
@@ -5,8 +5,8 @@ module Oracles.Option (
import Base
import Oracles.Base
--- For each Option the files {default.config, user.config} contain
--- a line of the form 'target-os = mingw32'.
+-- For each Option the file default.config contains a line of the
+-- form 'target-os = mingw32'.
-- (showArg TargetOs) is an action that consults the config files
-- and returns "mingw32".
--
More information about the ghc-commits
mailing list