[commit: ghc] wip/nfs-locking: Rename the --configure flag to --setup. (4cef7ec)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 00:48:14 UTC 2017


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

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

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

commit 4cef7ecc4f7c3e63c55a2d0800a7370c09a85aa1
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Mon Feb 8 23:53:19 2016 +0000

    Rename the --configure flag to --setup.
    
    See #204.


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

4cef7ecc4f7c3e63c55a2d0800a7370c09a85aa1
 src/CmdLineFlag.hs | 40 ++++++++++++++++++++--------------------
 src/Rules/Setup.hs | 10 +++++-----
 2 files changed, 25 insertions(+), 25 deletions(-)

diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs
index 84d4f11..c7d2b35 100644
--- a/src/CmdLineFlag.hs
+++ b/src/CmdLineFlag.hs
@@ -1,5 +1,5 @@
 module CmdLineFlag (
-    putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdConfigure, Configure (..),
+    putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdSetup, Setup (..),
     cmdFlavour, Flavour (..), cmdProgressInfo, ProgressInfo (..), cmdSplitObjects
     ) where
 
@@ -11,7 +11,7 @@ import System.IO.Unsafe (unsafePerformIO)
 
 -- Command line flags
 data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show)
-data Configure    = SkipConfigure | RunConfigure String deriving (Eq, Show)
+data Setup        = SkipSetup | RunSetup String deriving (Eq, Show)
 data Flavour      = Default | Quick deriving (Eq, Show)
 
 -- | 'CmdLineFlag.Untracked' is a collection of flags that can be passed via the
@@ -19,9 +19,9 @@ data Flavour      = Default | Quick deriving (Eq, Show)
 -- build rules to be rurun.
 data Untracked = Untracked
     { buildHaddock :: Bool
-    , configure    :: Configure
     , flavour      :: Flavour
     , progressInfo :: ProgressInfo
+    , setup        :: Setup
     , splitObjects :: Bool }
     deriving (Eq, Show)
 
@@ -29,24 +29,14 @@ data Untracked = Untracked
 defaultUntracked :: Untracked
 defaultUntracked = Untracked
     { buildHaddock = False
-    , configure    = SkipConfigure
     , flavour      = Default
     , progressInfo = Normal
+    , setup        = SkipSetup
     , splitObjects = False }
 
 readBuildHaddock :: Either String (Untracked -> Untracked)
 readBuildHaddock = Right $ \flags -> flags { buildHaddock = True }
 
-readConfigure :: Maybe String -> Either String (Untracked -> Untracked)
-readConfigure ms =
-    maybe (Left "Cannot parse configure") (Right . set) (go $ lower <$> ms)
-  where
-    go :: Maybe String -> Maybe Configure
-    go (Just args) = Just $ RunConfigure args
-    go Nothing     = Just $ RunConfigure ""
-    set :: Configure -> Untracked -> Untracked
-    set flag flags = flags { configure = flag }
-
 readFlavour :: Maybe String -> Either String (Untracked -> Untracked)
 readFlavour ms =
     maybe (Left "Cannot parse flavour") (Right . set) (go =<< lower <$> ms)
@@ -71,19 +61,29 @@ readProgressInfo ms =
     set :: ProgressInfo -> Untracked -> Untracked
     set flag flags = flags { progressInfo = flag }
 
+readSetup :: Maybe String -> Either String (Untracked -> Untracked)
+readSetup ms =
+    maybe (Left "Cannot parse setup") (Right . set) (go $ lower <$> ms)
+  where
+    go :: Maybe String -> Maybe Setup
+    go (Just args) = Just $ RunSetup args
+    go Nothing     = Just $ RunSetup ""
+    set :: Setup -> Untracked -> Untracked
+    set flag flags = flags { setup = flag }
+
 readSplitObjects :: Either String (Untracked -> Untracked)
 readSplitObjects = Right $ \flags -> flags { splitObjects = True }
 
 cmdFlags :: [OptDescr (Either String (Untracked -> Untracked))]
 cmdFlags =
-    [ Option [] ["configure"] (OptArg readConfigure "ARGS")
-      "Run configure with ARGS (also run boot if necessary)."
-    , Option [] ["flavour"] (OptArg readFlavour "FLAVOUR")
+    [ Option [] ["flavour"] (OptArg readFlavour "FLAVOUR")
       "Build flavour (Default or Quick)."
     , Option [] ["haddock"] (NoArg readBuildHaddock)
       "Generate Haddock documentation."
     , Option [] ["progress-info"] (OptArg readProgressInfo "STYLE")
       "Progress info style (None, Brief, Normal, or Unicorn)."
+    , Option [] ["setup"] (OptArg readSetup "CONFIGURE_ARGS")
+      "Setup the build system, pass CONFIGURE_ARGS to ./configure."
     , Option [] ["split-objects"] (NoArg readSplitObjects)
       "Generate split objects (requires a full clean rebuild)." ]
 
@@ -103,14 +103,14 @@ getCmdLineFlags = unsafePerformIO $ readIORef cmdLineFlags
 cmdBuildHaddock :: Bool
 cmdBuildHaddock = buildHaddock getCmdLineFlags
 
-cmdConfigure :: Configure
-cmdConfigure = configure getCmdLineFlags
-
 cmdFlavour :: Flavour
 cmdFlavour = flavour getCmdLineFlags
 
 cmdProgressInfo :: ProgressInfo
 cmdProgressInfo = progressInfo getCmdLineFlags
 
+cmdSetup :: Setup
+cmdSetup = setup getCmdLineFlags
+
 cmdSplitObjects :: Bool
 cmdSplitObjects = splitObjects getCmdLineFlags
diff --git a/src/Rules/Setup.hs b/src/Rules/Setup.hs
index ac53592..c99c8be 100644
--- a/src/Rules/Setup.hs
+++ b/src/Rules/Setup.hs
@@ -13,8 +13,8 @@ setupRules = do
     -- passed to it can affect the contents of system.config file.
     [configFile, "settings", configH] &%> \[cfg, settings, cfgH] -> do
         alwaysRerun
-        case cmdConfigure of
-            RunConfigure args -> do
+        case cmdSetup of
+            RunSetup configureArgs -> do
                 need [ settings <.> "in", cfgH <.> "in" ]
                 -- We cannot use windowsHost here due to a cyclic dependency
                 when (System.Info.os == "mingw32") $ do
@@ -23,11 +23,11 @@ setupRules = do
                                   , "mk/get-win32-tarballs.sh"
                                   , "download"
                                   , System.Info.arch ]
-                runConfigure "." [] [args]
-            SkipConfigure     -> unlessM (doesFileExist cfg) $
+                runConfigure "." [] [configureArgs]
+            SkipSetup -> unlessM (doesFileExist cfg) $
                 putError $ "Configuration file " ++ cfg ++ " is missing.\n"
                     ++ "Run the configure script either manually or via the "
-                    ++ "build system by passing --configure[=ARGS] flag."
+                    ++ "build system by passing --setup[=CONFIGURE_ARGS] flag."
 
     ["configure", configH <.> "in"] &%> \_ -> do
         putBuild "| Running boot..."



More information about the ghc-commits mailing list