[commit: ghc] wip/nfs-locking: Remove unused code. (6c89bd0)
git at git.haskell.org
git at git.haskell.org
Fri Oct 27 00:02:44 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/6c89bd01c53fe3ffa0c26499effff7687530711e/ghc
>---------------------------------------------------------------
commit 6c89bd01c53fe3ffa0c26499effff7687530711e
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date: Thu Aug 6 01:36:39 2015 +0100
Remove unused code.
>---------------------------------------------------------------
6c89bd01c53fe3ffa0c26499effff7687530711e
src/Package/Base.hs | 68 --------------------------------------------
src/Package/Library.hs | 76 --------------------------------------------------
2 files changed, 144 deletions(-)
diff --git a/src/Package/Base.hs b/src/Package/Base.hs
deleted file mode 100644
index 1f9d2c8..0000000
--- a/src/Package/Base.hs
+++ /dev/null
@@ -1,68 +0,0 @@
-{-# LANGUAGE NoImplicitPrelude #-}
-module Package.Base (
- module Base,
- module Ways,
- module Util,
- module Oracles,
- -- Package (..), Settings (..), TodoItem (..),
- -- defaultSettings, library, customise, updateSettings,
- -- commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs,
- pathArgs, packageArgs,
- includeGccArgs, includeGhcArgs, pkgHsSources,
- pkgDepHsObjects, pkgLibHsObjects, pkgCObjects,
- argSizeLimit,
- sourceDependecies,
- argList, argListWithComment,
- argListPath
- ) where
-
-import Base
-import Ways
-import Util
-import Oracles
-import Settings
-import qualified System.Directory as S
-
--- Find Haskell objects we depend on (we don't want to depend on split objects)
-pkgDepHsObjects :: FilePath -> FilePath -> Way -> Action [FilePath]
-pkgDepHsObjects path dist way = do
- let pathDist = path </> dist
- buildDir = pathDist </> "build"
- dirs <- map (dropWhileEnd isPathSeparator . unifyPath . (path </>))
- <$> args (SrcDirs pathDist)
- fmap concat $ forM dirs $ \d ->
- map (unifyPath . (buildDir ++) . (-<.> osuf way) . drop (length d))
- <$> (findModuleFiles pathDist [d] [".hs", ".lhs"])
-
-pkgCObjects :: FilePath -> FilePath -> Way -> Action [FilePath]
-pkgCObjects path dist way = do
- let pathDist = path </> dist
- buildDir = pathDist </> "build"
- srcs <- args $ CSrcs pathDist
- return $ map (unifyPath . (buildDir </>) . (-<.> osuf way)) srcs
-
--- Find Haskell objects that go to library
-pkgLibHsObjects :: FilePath -> FilePath -> Stage -> Way -> Action [FilePath]
-pkgLibHsObjects path dist stage way = do
- let pathDist = path </> dist
- buildDir = unifyPath $ pathDist </> "build"
- split <- splitObjects stage
- depObjs <- pkgDepHsObjects path dist way
- if split
- then do
- need depObjs -- Otherwise, split objects may not yet be available
- let suffix = "_" ++ osuf way ++ "_split/*." ++ osuf way
- findModuleFiles pathDist [buildDir] [suffix]
- else do return depObjs
-
--- The argument list has a limited size on Windows. Since Windows 7 the limit
--- is 32768 (theoretically). In practice we use 31000 to leave some breathing
--- space for the builder's path & name, auxiliary flags, and other overheads.
--- Use this function to set limits for other operating systems if necessary.
-argSizeLimit :: Action Int
-argSizeLimit = do
- windows <- windowsHost
- return $ if windows
- then 31000
- else 4194304 -- Cabal needs a bit more than 2MB!
-
diff --git a/src/Package/Library.hs b/src/Package/Library.hs
deleted file mode 100644
index 82b1ab8..0000000
--- a/src/Package/Library.hs
+++ /dev/null
@@ -1,76 +0,0 @@
-{-# LANGUAGE NoImplicitPrelude #-}
-module Package.Library (buildPackageLibrary) where
-
-import Package.Base
-
-argListDir :: FilePath
-argListDir = "shake/arg/buildPackageLibrary"
-
-arArgs :: [FilePath] -> FilePath -> Args
-arArgs objs result = args [ arg "q"
- , arg result
- , args objs ]
-
-ldArgs :: Stage -> [FilePath] -> FilePath -> Args
-ldArgs stage objs result = args [ args $ ConfLdLinkerArgs stage
- , arg "-r"
- , arg "-o"
- , arg result
- , args objs ]
-
-arRule :: Package -> TodoItem -> Rules ()
-arRule pkg @ (Package _ path _ _) todo @ (stage, dist, _) =
- let buildDir = path </> dist </> "build"
- in
- (buildDir <//> "*a") %> \out -> do
- let way = detectWay $ tail $ takeExtension out
- cObjs <- pkgCObjects path dist way
- hsObjs <- pkgDepHsObjects path dist way
- need $ cObjs ++ hsObjs
- libHsObjs <- pkgLibHsObjects path dist stage way
- liftIO $ removeFiles "." [out]
- -- Splitting argument list into chunks as otherwise Ar chokes up
- maxChunk <- argSizeLimit
- forM_ (chunksOfSize maxChunk $ cObjs ++ libHsObjs) $ \objs -> do
- run Ar $ arArgs objs $ unifyPath out
- -- Finally, record the argument list
- need [argListPath argListDir pkg stage]
-
-ldRule :: Package -> TodoItem -> Rules ()
-ldRule pkg @ (Package name path _ _) todo @ (stage, dist, _) =
- let pathDist = path </> dist
- buildDir = pathDist </> "build"
- in
- priority 2 $ (buildDir </> "*.o") %> \out -> do
- cObjs <- pkgCObjects path dist vanilla
- hObjs <- pkgDepHsObjects path dist vanilla
- need $ cObjs ++ hObjs
- run Ld $ ldArgs stage (cObjs ++ hObjs) $ unifyPath out
- synopsis <- dropWhileEnd isPunctuation <$> showArg (Synopsis pathDist)
- putColoured Green $ "/--------\n| Successfully built package '"
- ++ name ++ "' (stage " ++ show stage ++ ")."
- putColoured Green $ "| Package synopsis: " ++ synopsis ++ "."
- ++ "\n\\--------"
- -- Finally, record the argument list
- need [argListPath argListDir pkg stage]
-
-argListRule :: Package -> TodoItem -> Rules ()
-argListRule pkg @ (Package _ path _ _) todo @ (stage, dist, settings) =
- (argListPath argListDir pkg stage) %> \out -> do
- need $ ["shake/src/Package/Library.hs"] ++ sourceDependecies
- cObjsV <- pkgCObjects path dist vanilla
- hsObjsV <- pkgDepHsObjects path dist vanilla
- ldList <- argList Ld $ ldArgs stage (cObjsV ++ hsObjsV) "output.o"
- ways' <- ways settings
- arList <- forM ways' $ \way -> do
- cObjs <- pkgCObjects path dist way
- hsObjs <- pkgLibHsObjects path dist stage way
- suffix <- libsuf way
- argListWithComment
- ("way '" ++ tag way ++ "'")
- Ar
- (arArgs (cObjs ++ hsObjs) $ "output" <.> suffix)
- writeFileChanged out $ unlines $ [ldList] ++ arList
-
-buildPackageLibrary :: Package -> TodoItem -> Rules ()
-buildPackageLibrary = argListRule <> arRule <> ldRule
More information about the ghc-commits
mailing list