[commit: ghc] wip/nfs-locking: Minor revisions (add comments, move Condition to Oracles.hs). (618d90d)
git at git.haskell.org
git at git.haskell.org
Thu Oct 26 22:59:52 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/618d90dc2bc41256a18c42776d701a9a4fc23d26/ghc
>---------------------------------------------------------------
commit 618d90dc2bc41256a18c42776d701a9a4fc23d26
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date: Sun Dec 28 03:33:55 2014 +0000
Minor revisions (add comments, move Condition to Oracles.hs).
>---------------------------------------------------------------
618d90dc2bc41256a18c42776d701a9a4fc23d26
src/Base.hs | 4 +---
src/Oracles.hs | 21 +++++++++++++--------
2 files changed, 14 insertions(+), 11 deletions(-)
diff --git a/src/Base.hs b/src/Base.hs
index e44b3bb..b4ea8cb 100644
--- a/src/Base.hs
+++ b/src/Base.hs
@@ -7,7 +7,7 @@ module Base (
module Data.Monoid,
module Data.List,
Stage (..),
- Args, arg, Condition,
+ Args, arg,
joinArgs, joinArgsWithSpaces,
filterOut,
) where
@@ -22,8 +22,6 @@ data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum)
type Args = Action [String]
-type Condition = Action Bool
-
instance Monoid a => Monoid (Action a) where
mempty = return mempty
mappend p q = mappend <$> p <*> q
diff --git a/src/Oracles.hs b/src/Oracles.hs
index e03d6a3..9ceb121 100644
--- a/src/Oracles.hs
+++ b/src/Oracles.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses #-}
-{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, DeriveGeneric, ConstraintKinds #-}
+{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ConstraintKinds #-}
module Oracles (
module Control.Monad,
@@ -8,7 +8,7 @@ module Oracles (
Builder (..), Flag (..), Option (..),
path, with, run, argPath,
option, argOption,
- test, when, unless, not, (&&), (||),
+ Condition, test, when, unless, not, (&&), (||),
oracleRules
) where
@@ -50,7 +50,7 @@ path builder = do
if (windows && "/" `isPrefixOf` cfgPathExe)
then do
root <- option Root
- return $ root ++ cfgPathExe
+ return $ root ++ (drop 1 $ cfgPathExe)
else
return cfgPathExe
@@ -59,19 +59,22 @@ argPath builder = do
path <- path builder
arg [path]
--- Explain!
--- TODO: document change in behaviour (LaxDeps)
+-- When LaxDeps flag is set (by adding 'lax-dependencies = YES' to user.config),
+-- dependencies on the GHC executable are turned into order-only dependencies to
+-- avoid needless recompilation when making changes to GHC's sources. In certain
+-- situations this can lead to build failures, in which case you should reset
+-- the flag (at least temporarily).
needBuilder :: Builder -> Action ()
needBuilder ghc @ (Ghc stage) = do
target <- path ghc
- laxDeps <- test LaxDeps -- TODO: get rid of test?
+ laxDeps <- test LaxDeps
if laxDeps then orderOnly [target] else need [target]
needBuilder builder = do
target <- path builder
need [target]
--- 'with Gcc' generates --with-gcc=/usr/bin/gcc and needs it
+-- Action 'with Gcc' returns an argument '--with-gcc=/path/to/gcc' and needs the builder
with :: Builder -> Args
with builder = do
let prefix = case builder of
@@ -163,7 +166,7 @@ test flag = do
Validating -> ("validating" , False)
let defaultString = if defaultValue then "YES" else "NO"
value <- askConfigWithDefault key $
- do putLoud $ "\nFlag '"
+ do putLoud $ "\nFlag '" -- TODO: Give the warning *only once* per key
++ key
++ "' not set in configuration files. "
++ "Proceeding with default value '"
@@ -172,6 +175,8 @@ test flag = do
return defaultString
return $ value == "YES"
+type Condition = Action Bool
+
class ToCondition a where
toCondition :: a -> Condition
More information about the ghc-commits
mailing list