[commit: ghc] wip/nfs-locking: Add comments. (7c2279b)

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


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

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

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

commit 7c2279b523ce8b71dc0e9492380d8798a8b1b4f2
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Wed Jan 21 23:20:52 2015 +0000

    Add comments.


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

7c2279b523ce8b71dc0e9492380d8798a8b1b4f2
 src/Oracles.hs              |  1 +
 src/Package.hs              |  2 +-
 src/Package/Base.hs         | 11 ++++++++---
 src/Package/Data.hs         |  4 ++--
 src/Package/Dependencies.hs |  7 ++++---
 src/Targets.hs              | 19 +++++++++++++++++++
 6 files changed, 35 insertions(+), 9 deletions(-)

diff --git a/src/Oracles.hs b/src/Oracles.hs
index 80e2e60..4e6fe5b 100644
--- a/src/Oracles.hs
+++ b/src/Oracles.hs
@@ -11,6 +11,7 @@ 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
diff --git a/src/Package.hs b/src/Package.hs
index 4d24e2a..1931ea3 100644
--- a/src/Package.hs
+++ b/src/Package.hs
@@ -26,7 +26,7 @@ packageRules = do
             -- We build *only one* vanilla .o file (not sure why)
             -- We build .way_a file for each way (or its dynamic version).
             -- TODO: Check BUILD_GHCI_LIB flag to decide if .o is needed
-            -- TODO: move this into buildPackage
+            -- TODO: move this into a separate file (perhaps, to Targets.hs?)
             action $ when (buildWhen settings) $ do
                 let pathDist = path </> dist
                     buildDir = pathDist </> "build"
diff --git a/src/Package/Base.hs b/src/Package/Base.hs
index 00b4356..88e357f 100644
--- a/src/Package/Base.hs
+++ b/src/Package/Base.hs
@@ -39,9 +39,9 @@ defaultSettings stage = Settings
                         {
                             customConfArgs  = mempty,
                             customCcArgs    = mempty,
-                            customLdArgs    = mempty,
-                            customCppArgs   = mempty,
-                            customDllArgs   = mempty,
+                            customLdArgs    = mempty, -- currently not used
+                            customCppArgs   = mempty, -- currently not used
+                            customDllArgs   = mempty, -- only for compiler
                             registerPackage = True,
                             ways            = defaultWays stage,
                             buildWhen       = return True
@@ -54,6 +54,11 @@ defaultSettings stage = Settings
 -- * doc/             : produced by haddock
 -- * package-data.mk  : contains output of ghc-cabal applied to package.cabal
 -- Settings may be different for different combinations of Stage & FilePath
+-- TODO: the above may be incorrect, settings seem to *only* depend on the
+-- stage. In fact Stage seem to define FilePath and Settings, therefore we
+-- can drop the TodoItem and replace it by [Stage] and two functions
+--    * distDirectory :: Package -> Stage -> FilePath
+--    * settings      :: Package -> Stage -> Settings
 type TodoItem = (Stage, FilePath, Settings)
 
 -- pkgPath is the path to the source code relative to the root
diff --git a/src/Package/Data.hs b/src/Package/Data.hs
index b2de8c5..602993e 100644
--- a/src/Package/Data.hs
+++ b/src/Package/Data.hs
@@ -26,8 +26,8 @@ configureArgs stage settings =
             unless (null s) $ arg $ "--configure-option=" ++ key ++ "=" ++ s
         cflags   = [ commonCcArgs `filterOut` "-Werror"
                    , args $ ConfCcArgs stage
-                   -- , customCcArgs settings -- TODO: fix
-                   , commonCcWarninigArgs ] -- TODO: check if cflags are glued
+                   -- , customCcArgs settings -- TODO: bring this back
+                   , commonCcWarninigArgs ] -- TODO: check why cflags are glued
         ldflags  = [ commonLdArgs
                    , args $ ConfGccLinkerArgs stage
                    , customLdArgs settings ]
diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs
index 604034e..c861707 100644
--- a/src/Package/Dependencies.hs
+++ b/src/Package/Dependencies.hs
@@ -3,6 +3,7 @@ module Package.Dependencies (buildPackageDependencies) where
 
 import Package.Base
 
+-- TODO: use oracles instead of arg files.
 argListDir :: FilePath
 argListDir = "shake/arg/buildPackageDependencies"
 
@@ -49,9 +50,9 @@ gccArgs sourceFile (Package _ path _ _) (stage, dist, settings) =
         depFile  = buildDir </> takeFileName sourceFile <.> "deps"
     in args [ args ["-E", "-MM"] -- TODO: add a Cpp Builder instead
             , args $ CcArgs pathDist
-            , commonCcArgs
-            , customCcArgs settings
-            , commonCcWarninigArgs
+            , commonCcArgs          -- TODO: remove?
+            , customCcArgs settings -- TODO: Replace by customCppArgs?
+            , commonCcWarninigArgs  -- TODO: remove?
             , includeGccArgs path dist
             , args ["-MF", unifyPath depFile]
             , args ["-x", "c"]
diff --git a/src/Targets.hs b/src/Targets.hs
index 2ff6eae..bc4c29d 100644
--- a/src/Targets.hs
+++ b/src/Targets.hs
@@ -15,12 +15,14 @@ instance Show IntegerLibrary where
          IntegerGmp2   -> "integer-gmp2"
          IntegerSimple -> "integer-simple"
 
+-- TODO: keep or move to configuration files? see Note [configuration files]
 integerLibrary :: IntegerLibrary
 integerLibrary = IntegerGmp2
 
 integerLibraryName :: String
 integerLibraryName = show integerLibrary
 
+-- see Note [configuration files]
 buildHaddock :: Bool
 buildHaddock = True
 
@@ -107,6 +109,23 @@ targetPackagesInStage stage = filter inStage targetPackages
     inStage (Package _ _ _ todoItems) = any matchStage todoItems
     matchStage (todoStage, _, _)    = todoStage == stage
 
+-- TODISCUSS
 -- Note [Cabal package weirdness]
 -- Find out if we can move the contents to just Cabal/
 -- What is Cabal/cabal-install? Do we need it?
+
+-- TODISCUSS
+-- Note [configuration files]
+-- In this file we have two configuration options: integerLibrary and
+-- buildHaddock. Arguably, their place should be among other configuration
+-- options in the config files, however, moving integerLibrary there would
+-- actually be quite painful, because it would then be confined to live in
+-- the Action monad.
+-- In general, shall we keep as many options as possible inside Shake, or
+-- leave them in one place -- configuration files? We could try to move
+-- everything to Shake which would be great:
+--    * type safety and better abstractions
+--    * useable outside the Action monad, e.g. for creating rules
+--    * recompiling Shake is much faster then re-running configure script
+--    * ... no more autoconf/configure and native Windows build?! Sign me up!
+-- However, moving everything to Shake seems unfeasible at the moment.



More information about the ghc-commits mailing list