[commit: ghc] master: Fix missing libHSghc-8.5-0.a (#574) (05fbe8b)
git at git.haskell.org
git at git.haskell.org
Tue Oct 23 20:15:57 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/05fbe8b36da146aae24c53455131b5b5618ee849/ghc
>---------------------------------------------------------------
commit 05fbe8b36da146aae24c53455131b5b5618ee849
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date: Mon Apr 16 23:29:25 2018 +0100
Fix missing libHSghc-8.5-0.a (#574)
* Drop support for lib0 libraries
See #573
* Minor refactoring
>---------------------------------------------------------------
05fbe8b36da146aae24c53455131b5b5618ee849
src/Context.hs | 15 +++------------
src/Hadrian/Oracles/TextFile.hs | 11 ++++++-----
src/Rules/Library.hs | 20 ++++++++------------
src/Utilities.hs | 11 +----------
4 files changed, 18 insertions(+), 39 deletions(-)
diff --git a/src/Context.hs b/src/Context.hs
index 225752d..0694eb1 100644
--- a/src/Context.hs
+++ b/src/Context.hs
@@ -7,11 +7,9 @@ module Context (
withHsPackage,
-- * Paths
- contextDir, buildPath, buildDir,
- pkgInplaceConfig, pkgSetupConfigFile,
- pkgHaddockFile, pkgLibraryFile, pkgLibraryFile0, pkgGhciLibraryFile,
- pkgConfFile, objectPath, contextPath, getContextPath,
- libDir, libPath
+ contextDir, buildPath, buildDir, pkgInplaceConfig, pkgSetupConfigFile,
+ pkgHaddockFile, pkgLibraryFile, pkgGhciLibraryFile, pkgConfFile, objectPath,
+ contextPath, getContextPath, libDir, libPath
) where
import Base
@@ -101,13 +99,6 @@ pkgLibraryFile context at Context {..} = do
extension <- libsuf way
pkgFile context "libHS" extension
--- | Path to the auxiliary library file of a given 'Context', e.g.:
--- @_build/stage1/compiler/build/libHSghc-8.1-0.a at .
-pkgLibraryFile0 :: Context -> Action FilePath
-pkgLibraryFile0 context at Context {..} = do
- extension <- libsuf way
- pkgFile context "libHS" ("-0" ++ extension)
-
-- | Path to the GHCi library file of a given 'Context', e.g.:
-- @_build/stage1/libraries/array/build/HSarray-0.5.1.0.o at .
pkgGhciLibraryFile :: Context -> Action FilePath
diff --git a/src/Hadrian/Oracles/TextFile.hs b/src/Hadrian/Oracles/TextFile.hs
index 98c098a..2f58fab 100644
--- a/src/Hadrian/Oracles/TextFile.hs
+++ b/src/Hadrian/Oracles/TextFile.hs
@@ -147,10 +147,11 @@ textFileOracle = do
confCabal <- newCache $ \(ctx at Context {..}) -> do
case pkgCabalFile package of
- Just file -> do
- need [file]
- putLoud $ "| PackageDataFile oracle: reading " ++ quote file ++ " (Stage: " ++ stageString stage ++ ")..."
- Just <$> parsePackageData ctx
- Nothing -> return Nothing
+ Just file -> do
+ need [file]
+ putLoud $ "| PackageDataFile oracle: reading " ++ quote file
+ ++ " (Stage: " ++ stageString stage ++ ")..."
+ Just <$> parsePackageData ctx
+ Nothing -> return Nothing
void $ addOracle $ \(PackageDataFile ctx) -> confCabal ctx
diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs
index 000d032..6ce0a71 100644
--- a/src/Rules/Library.hs
+++ b/src/Rules/Library.hs
@@ -12,7 +12,6 @@ import Expression hiding (way, package)
import Flavour
import GHC.Packages
import Oracles.ModuleFiles
-import Oracles.Setting
import Rules.Gmp
import Settings
import Target
@@ -60,8 +59,8 @@ buildDynamicLib :: Context -> Rules ()
buildDynamicLib context at Context{..} = do
root <- buildRootRules
pkgId <- case pkgCabalFile package of
- Just file -> liftIO $ parseCabalPkgId file
- Nothing -> return (pkgName package)
+ Just file -> liftIO $ parseCabalPkgId file
+ Nothing -> return $ pkgName package
let libPrefix = root -/- buildDir context -/- "libHS" ++ pkgId
-- OS X
libPrefix ++ "*.dylib" %> buildDynamicLibUnix
@@ -79,20 +78,17 @@ buildPackageLibrary :: Context -> Rules ()
buildPackageLibrary context at Context {..} = do
root <- buildRootRules
pkgId <- case pkgCabalFile package of
- Just file -> liftIO (parseCabalPkgId file)
- Nothing -> return (pkgName package)
+ Just file -> liftIO $ parseCabalPkgId file
+ Nothing -> return $ pkgName package
let libPrefix = root -/- buildDir context -/- "libHS" ++ pkgId
archive = libPrefix ++ (waySuffix way <.> "a")
archive %%> \a -> do
objs <- libraryObjects context
- asuf <- libsuf way
- let isLib0 = ("//*-0" ++ asuf) ?== a
removeFile a
- if isLib0 then build $ target context (Ar Pack stage) [] [a] -- TODO: Scan for dlls
- else build $ target context (Ar Pack stage) objs [a]
+ build $ target context (Ar Pack stage) objs [a]
synopsis <- pkgSynopsis context
- unless isLib0 . putSuccess $ renderLibrary
+ putSuccess $ renderLibrary
(quote (pkgName package) ++ " (" ++ show stage ++ ", way "
++ show way ++ ").") a synopsis
@@ -101,13 +97,13 @@ buildPackageLibrary context at Context {..} = do
buildPackageGhciLibrary :: Context -> Rules ()
buildPackageGhciLibrary context at Context {..} = priority 2 $ do
root <- buildRootRules
+ -- TODO: Get rid of code duplication for 'pkgId'.
pkgId <- case pkgCabalFile package of
Just file -> liftIO $ parseCabalPkgId file
Nothing -> return $ pkgName package
let libPrefix = root -/- buildDir context -/- "HS" ++ pkgId
- o = libPrefix ++ "*" ++ (waySuffix way <.> "o")
- o %> \obj -> do
+ libPrefix ++ "*" ++ (waySuffix way <.> "o") %> \obj -> do
objs <- allObjects context
need objs
build $ target context (Ld stage) objs [obj]
diff --git a/src/Utilities.hs b/src/Utilities.hs
index 57faf41..2c73d94 100644
--- a/src/Utilities.hs
+++ b/src/Utilities.hs
@@ -13,8 +13,6 @@ import Hadrian.Utilities
import Context
import Expression hiding (stage)
-import GHC.Packages
-import Oracles.Setting (windowsHost)
import Settings
import Target
@@ -67,18 +65,11 @@ stage1Dependencies =
libraryTargets :: Bool -> Context -> Action [FilePath]
libraryTargets includeGhciLib context = do
libFile <- pkgLibraryFile context
- lib0File <- pkgLibraryFile0 context
- lib0 <- buildDll0 context
ghciLib <- pkgGhciLibraryFile context
ghci <- if includeGhciLib
then interpretInContext context $ getPackageData PD.buildGhciLib
else return False
- return $ [ libFile ] ++ [ lib0File | lib0 ] ++ [ ghciLib | ghci ]
-
- where buildDll0 :: Context -> Action Bool
- buildDll0 Context {..} = do
- windows <- windowsHost
- return $ windows && stage == Stage1 && package == compiler
+ return $ [ libFile ] ++ [ ghciLib | ghci ]
-- | Coarse-grain 'need': make sure all given libraries are fully built.
needLibrary :: [Context] -> Action ()
More information about the ghc-commits
mailing list