[commit: ghc] wip/nfs-locking: Clean up build rules. (7661c31)

git at git.haskell.org git at git.haskell.org
Thu Oct 26 23:48:23 UTC 2017


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

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

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

commit 7661c319397cbcf02f8b9c4f229ebc8b0c019ad2
Author: Andrey Mokhov <andrey.mokhov at ncl.ac.uk>
Date:   Fri Jan 9 17:24:42 2015 +0000

    Clean up build rules.


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

7661c319397cbcf02f8b9c4f229ebc8b0c019ad2
 src/Package/Base.hs         |  2 +-
 src/Package/Data.hs         | 88 +++++++++++++++++++++------------------------
 src/Package/Dependencies.hs |  8 ++---
 3 files changed, 45 insertions(+), 53 deletions(-)

diff --git a/src/Package/Base.hs b/src/Package/Base.hs
index a895f5f..43b4a37 100644
--- a/src/Package/Base.hs
+++ b/src/Package/Base.hs
@@ -53,7 +53,7 @@ libraryPackage name stage settings =
         )]
 
 commonCcArgs :: Args
-commonCcArgs = when Validating $ args "-Werror" "-Wall"
+commonCcArgs = when Validating $ arg ["-Werror", "-Wall"]
 
 commonLdArgs :: Args
 commonLdArgs = mempty -- TODO: Why empty? Perhaps drop it altogether?
diff --git a/src/Package/Data.hs b/src/Package/Data.hs
index de617f4..81a7d7f 100644
--- a/src/Package/Data.hs
+++ b/src/Package/Data.hs
@@ -1,43 +1,37 @@
 {-# LANGUAGE NoImplicitPrelude, ScopedTypeVariables #-}
 module Package.Data (buildPackageData) where
-
 import Package.Base
 
 libraryArgs :: [Way] -> Args
 libraryArgs ways =
-    let argEnable x suffix = arg $ (if x then "--enable-" else "--disable-") ++ suffix
-    in mconcat
-        [ argEnable False "library-for-ghci" -- TODO: why always disable?
-        , argEnable (vanilla `elem` ways) "library-vanilla"
-        , when (ghcWithInterpreter && not DynamicGhcPrograms && vanilla `elem` ways) $
-            argEnable True "library-for-ghci"
-        , argEnable (profiling `elem` ways) "library-profiling"
-        , argEnable (dynamic   `elem` ways) "shared"
-        ]
+       argEnable False "library-for-ghci" -- TODO: why always disable?
+    <> argEnable (vanilla `elem` ways) "library-vanilla"
+    <> when (ghcWithInterpreter && not DynamicGhcPrograms && vanilla `elem` ways) (argEnable True "library-for-ghci")
+    <> argEnable (profiling `elem` ways) "library-profiling"
+    <> argEnable (dynamic   `elem` ways) "shared"
+  where
+    argEnable x suffix = arg $ (if x then "--enable-" else "--disable-") ++ suffix
 
 configureArgs :: Stage -> Settings -> Args
 configureArgs stage settings = 
-    let argConf key as = unless (null <$> as) $ joinArgs "--configure-option=" key "=" (as :: Args)
+    let argConf key as = do
+            s <- unwords <$> arg as
+            unless (null s) $ arg $ "--configure-option=" ++ key ++ "=" ++ s
 
-        cflags   = joinArgsSpaced (commonCcArgs `filterOut` ["-Werror"])
-                                  (ConfCcArgs stage)
-                                  (customCcArgs settings)
-                                  (commonCcWarninigArgs)
-        ldflags  = joinArgsSpaced commonLdArgs  (ConfGccLinkerArgs stage) (customLdArgs  settings)
-        cppflags = joinArgsSpaced commonCppArgs (ConfCppArgs       stage) (customCppArgs settings)
+        cflags   = commonCcArgs `filterOut` "-Werror" <+> ConfCcArgs stage <+> customCcArgs settings <+> commonCcWarninigArgs
+        ldflags  = commonLdArgs  <+> ConfGccLinkerArgs stage <+> customLdArgs  settings
+        cppflags = commonCppArgs <+> ConfCppArgs       stage <+> customCppArgs settings
 
-    in mconcat
-        [ argConf "CFLAGS"   cflags
-        , argConf "LDFLAGS"  ldflags
-        , argConf "CPPFLAGS" cppflags
-        , joinArgs "--gcc-options=" cflags " " ldflags
-        , argConf "--with-iconv-includes"  $ arg IconvIncludeDirs
-        , argConf "--with-iconv-libraries" $ arg IconvLibDirs
-        , argConf "--with-gmp-includes"    $ arg GmpIncludeDirs
-        , argConf "--with-gmp-libraries"   $ arg GmpLibDirs
-        , when CrossCompiling $ argConf "--host" $ arg TargetPlatformFull -- TODO: why not host?
-        , argConf "--with-cc" $ arg Gcc
-        ]
+    in argConf "CFLAGS"   cflags
+    <> argConf "LDFLAGS"  ldflags
+    <> argConf "CPPFLAGS" cppflags
+    <> arg (concat <$> "--gcc-options=" <+> cflags <+> " " <+> ldflags)
+    <> argConf "--with-iconv-includes"  IconvIncludeDirs
+    <> argConf "--with-iconv-libraries" IconvLibDirs
+    <> argConf "--with-gmp-includes"    GmpIncludeDirs
+    <> argConf "--with-gmp-libraries"   GmpLibDirs
+    <> when CrossCompiling (argConf "--host" TargetPlatformFull) -- TODO: why not host?
+    <> argConf "--with-cc" Gcc
 
 buildPackageData :: Package -> TodoItem -> Rules ()
 buildPackageData pkg @ (Package name path _) (stage, dist, settings) =
@@ -57,30 +51,28 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) =
             postProcessPackageData $ path </> dist </> "package-data.mk"
               where
                 cabalArgs, ghcPkgArgs :: Args
-                cabalArgs = mconcat
-                    [ args "configure" path dist
+                cabalArgs = arg ["configure", path, dist]
                     -- this is a positional argument, hence:
                     -- * if it is empty, we need to emit one empty string argument
                     -- * if there are many, we must collapse them into one space-separated string
-                    , joinArgsSpaced "" (customDllArgs settings)
-                    , with $ Ghc stage -- TODO: used to be stage01 (using max Stage1 GHC)
-                    , with $ GhcPkg stage
+                    <> arg (unwords <$> customDllArgs settings)
+                    <> with (Ghc stage) -- TODO: used to be stage01 (using max Stage1 GHC)
+                    <> with (GhcPkg stage)
 
-                    , customConfArgs settings
-                    , libraryArgs =<< ways settings
+                    <> customConfArgs settings
+                    <> (libraryArgs =<< ways settings)
 
-                    , when hsColourSrcs $ with HsColour
-                    , configureArgs stage settings
+                    <> when hsColourSrcs (with HsColour)
+                    <> configureArgs stage settings
 
-                    , when (stage == Stage0) $ bootPkgConstraints
-                    , with Gcc
-                    , when (stage /= Stage0) $ with Ld
+                    <> when (stage == Stage0) bootPkgConstraints
+                    <> with Gcc
+                    <> when (stage /= Stage0) (with Ld)
                     
-                    , with Ar
-                    , with Alex
-                    , with Happy
-                    ] -- TODO: reorder with's
+                    <> with Ar
+                    <> with Alex
+                    <> with Happy -- TODO: reorder with's
 
-                ghcPkgArgs = args "update" "--force"
-                    (when (stage == Stage0) $ arg "--package-db=libraries/bootstrapping.conf")
-                    (path </> dist </> "inplace-pkg-config")
+                ghcPkgArgs = arg ["update", "--force"]
+                    <> when (stage == Stage0) (arg "--package-db=libraries/bootstrapping.conf")
+                    <> arg (path </> dist </> "inplace-pkg-config")
diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs
index b3e013f..7ccb7b6 100644
--- a/src/Package/Dependencies.hs
+++ b/src/Package/Dependencies.hs
@@ -88,14 +88,14 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) =
                 return $ prefix ++ buildDir </> suffix
             , map (\d -> "-I" ++ path </> d) <$> filter isRelative <$> arg (IncludeDirs pkgData)
             , map (\d -> "-I" ++          d) <$> filter isAbsolute <$> arg (IncludeDirs pkgData)
-            , args "-optP-include" ("-optP" ++ buildDir </> "build/autogen/cabal_macros.h")
+            , arg ["-optP-include", "-optP" ++ buildDir </> "build/autogen/cabal_macros.h"]
             , if usePackageKey 
               then map ("-package-key " ++) <$> arg (DepKeys pkgData)
               else map ("-package "     ++) <$> arg (Deps    pkgData)
             , arg "-no-user-package-db"
-            , args "-odir"    (buildDir </> "build")
-            , args "-stubdir" (buildDir </> "build")
-            , joinArgsSpaced "-dep-makefile" out
+            , arg ["-odir"   , buildDir </> "build"]
+            , arg ["-stubdir", buildDir </> "build"]
+            , arg $ "-dep-makefile " ++ out
             , concatMap (\w -> ["-dep-suffix", suffix w]) <$> ways settings
             , arg "-include-pkg-deps"
             , arg $ map normalise srcs



More information about the ghc-commits mailing list