parent
0bb8b242db
commit
0079a61b94
@ -0,0 +1,277 @@
|
||||
From 6e361d895dda4600a85e01c72ff219474b5c7190 Mon Sep 17 00:00:00 2001
|
||||
From: Kavon Farvardin <kavon@farvard.in>
|
||||
Date: Thu, 4 Oct 2018 13:44:55 -0400
|
||||
Subject: [PATCH] Multiple fixes / improvements for LLVM backend
|
||||
|
||||
- Fix for #13904 -- stop "trashing" callee-saved registers, since it is
|
||||
not actually doing anything useful.
|
||||
|
||||
- Fix for #14251 -- fixes the calling convention for functions passing
|
||||
raw SSE-register values by adding padding as needed to get the values
|
||||
in the right registers. This problem cropped up when some args were
|
||||
unused an dropped from the live list.
|
||||
|
||||
- Fixed a typo in 'readnone' attribute
|
||||
|
||||
- Added 'lower-expect' pass to level 0 LLVM optimization passes to
|
||||
improve block layout in LLVM for stack checks, etc.
|
||||
|
||||
Test Plan: `make test WAYS=optllvm` and `make test WAYS=llvm`
|
||||
|
||||
Reviewers: bgamari, simonmar, angerman
|
||||
|
||||
Reviewed By: angerman
|
||||
|
||||
Subscribers: rwbarton, carter
|
||||
|
||||
GHC Trac Issues: #13904, #14251
|
||||
|
||||
Differential Revision: https://phabricator.haskell.org/D5190
|
||||
|
||||
(cherry picked from commit adcb5fb47c0942671d409b940d8884daa9359ca4)
|
||||
---
|
||||
compiler/llvmGen/Llvm/Types.hs | 2 +-
|
||||
compiler/llvmGen/LlvmCodeGen/Base.hs | 62 ++++++++++++++++++++----
|
||||
compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 59 +++++-----------------
|
||||
compiler/main/DriverPipeline.hs | 2 +-
|
||||
testsuite/tests/codeGen/should_run/all.T | 4 +-
|
||||
5 files changed, 67 insertions(+), 62 deletions(-)
|
||||
|
||||
diff --git a/compiler/llvmGen/Llvm/Types.hs b/compiler/llvmGen/Llvm/Types.hs
|
||||
index 87111499fc0..c1c51afcf0f 100644
|
||||
--- a/compiler/llvmGen/Llvm/Types.hs
|
||||
+++ b/compiler/llvmGen/Llvm/Types.hs
|
||||
@@ -560,7 +560,7 @@ instance Outputable LlvmFuncAttr where
|
||||
ppr OptSize = text "optsize"
|
||||
ppr NoReturn = text "noreturn"
|
||||
ppr NoUnwind = text "nounwind"
|
||||
- ppr ReadNone = text "readnon"
|
||||
+ ppr ReadNone = text "readnone"
|
||||
ppr ReadOnly = text "readonly"
|
||||
ppr Ssp = text "ssp"
|
||||
ppr SspReq = text "ssqreq"
|
||||
diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs
|
||||
index 6e20da48c1b..ec91bacc4c8 100644
|
||||
--- a/compiler/llvmGen/LlvmCodeGen/Base.hs
|
||||
+++ b/compiler/llvmGen/LlvmCodeGen/Base.hs
|
||||
@@ -26,7 +26,7 @@ module LlvmCodeGen.Base (
|
||||
|
||||
cmmToLlvmType, widthToLlvmFloat, widthToLlvmInt, llvmFunTy,
|
||||
llvmFunSig, llvmFunArgs, llvmStdFunAttrs, llvmFunAlign, llvmInfAlign,
|
||||
- llvmPtrBits, tysToParams, llvmFunSection,
|
||||
+ llvmPtrBits, tysToParams, llvmFunSection, padLiveArgs, isSSE,
|
||||
|
||||
strCLabel_llvm, strDisplayName_llvm, strProcedureName_llvm,
|
||||
getGlobalPtr, generateExternDecls,
|
||||
@@ -58,6 +58,8 @@ import ErrUtils
|
||||
import qualified Stream
|
||||
|
||||
import Control.Monad (ap)
|
||||
+import Data.List (sort)
|
||||
+import Data.Maybe (mapMaybe)
|
||||
|
||||
-- ----------------------------------------------------------------------------
|
||||
-- * Some Data Types
|
||||
@@ -147,16 +149,58 @@ llvmFunSection dflags lbl
|
||||
-- | A Function's arguments
|
||||
llvmFunArgs :: DynFlags -> LiveGlobalRegs -> [LlvmVar]
|
||||
llvmFunArgs dflags live =
|
||||
- map (lmGlobalRegArg dflags) (filter isPassed (activeStgRegs platform))
|
||||
+ map (lmGlobalRegArg dflags) (filter isPassed allRegs)
|
||||
where platform = targetPlatform dflags
|
||||
- isLive r = not (isSSE r) || r `elem` alwaysLive || r `elem` live
|
||||
+ allRegs = activeStgRegs platform
|
||||
+ paddedLive = map (\(_,r) -> r) $ padLiveArgs live
|
||||
+ isLive r = r `elem` alwaysLive || r `elem` paddedLive
|
||||
isPassed r = not (isSSE r) || isLive r
|
||||
- isSSE (FloatReg _) = True
|
||||
- isSSE (DoubleReg _) = True
|
||||
- isSSE (XmmReg _) = True
|
||||
- isSSE (YmmReg _) = True
|
||||
- isSSE (ZmmReg _) = True
|
||||
- isSSE _ = False
|
||||
+
|
||||
+
|
||||
+isSSE :: GlobalReg -> Bool
|
||||
+isSSE (FloatReg _) = True
|
||||
+isSSE (DoubleReg _) = True
|
||||
+isSSE (XmmReg _) = True
|
||||
+isSSE (YmmReg _) = True
|
||||
+isSSE (ZmmReg _) = True
|
||||
+isSSE _ = False
|
||||
+
|
||||
+sseRegNum :: GlobalReg -> Maybe Int
|
||||
+sseRegNum (FloatReg i) = Just i
|
||||
+sseRegNum (DoubleReg i) = Just i
|
||||
+sseRegNum (XmmReg i) = Just i
|
||||
+sseRegNum (YmmReg i) = Just i
|
||||
+sseRegNum (ZmmReg i) = Just i
|
||||
+sseRegNum _ = Nothing
|
||||
+
|
||||
+-- the bool indicates whether the global reg was added as padding.
|
||||
+-- the returned list is not sorted in any particular order,
|
||||
+-- but does indicate the set of live registers needed, with SSE padding.
|
||||
+padLiveArgs :: LiveGlobalRegs -> [(Bool, GlobalReg)]
|
||||
+padLiveArgs live = allRegs
|
||||
+ where
|
||||
+ sseRegNums = sort $ mapMaybe sseRegNum live
|
||||
+ (_, padding) = foldl assignSlots (1, []) $ sseRegNums
|
||||
+ allRegs = padding ++ map (\r -> (False, r)) live
|
||||
+
|
||||
+ assignSlots (i, acc) regNum
|
||||
+ | i == regNum = -- don't need padding here
|
||||
+ (i+1, acc)
|
||||
+ | i < regNum = let -- add padding for slots i .. regNum-1
|
||||
+ numNeeded = regNum-i
|
||||
+ acc' = genPad i numNeeded ++ acc
|
||||
+ in
|
||||
+ (regNum+1, acc')
|
||||
+ | otherwise = error "padLiveArgs -- i > regNum ??"
|
||||
+
|
||||
+ genPad start n =
|
||||
+ take n $ flip map (iterate (+1) start) (\i ->
|
||||
+ (True, FloatReg i))
|
||||
+ -- NOTE: Picking float should be fine for the following reasons:
|
||||
+ -- (1) Float aliases with all the other SSE register types on
|
||||
+ -- the given platform.
|
||||
+ -- (2) The argument is not live anyways.
|
||||
+
|
||||
|
||||
-- | Llvm standard fun attributes
|
||||
llvmStdFunAttrs :: [LlvmFuncAttr]
|
||||
diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
|
||||
index e812dd445f1..a7121b7909a 100644
|
||||
--- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
|
||||
+++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
|
||||
@@ -14,7 +14,7 @@ import LlvmCodeGen.Base
|
||||
import LlvmCodeGen.Regs
|
||||
|
||||
import BlockId
|
||||
-import CodeGen.Platform ( activeStgRegs, callerSaves )
|
||||
+import CodeGen.Platform ( activeStgRegs )
|
||||
import CLabel
|
||||
import Cmm
|
||||
import PprCmm
|
||||
@@ -211,7 +211,6 @@ genCall t@(PrimTarget (MO_Prefetch_Data localityInt)) [] args
|
||||
fptr <- liftExprData $ getFunPtr funTy t
|
||||
argVars' <- castVarsW Signed $ zip argVars argTy
|
||||
|
||||
- doTrashStmts
|
||||
let argSuffix = [mkIntLit i32 0, mkIntLit i32 localityInt, mkIntLit i32 1]
|
||||
statement $ Expr $ Call StdCall fptr (argVars' ++ argSuffix) []
|
||||
| otherwise = panic $ "prefetch locality level integer must be between 0 and 3, given: " ++ (show localityInt)
|
||||
@@ -294,7 +293,6 @@ genCall t@(PrimTarget op) [] args
|
||||
fptr <- getFunPtrW funTy t
|
||||
argVars' <- castVarsW Signed $ zip argVars argTy
|
||||
|
||||
- doTrashStmts
|
||||
let alignVal = mkIntLit i32 align
|
||||
arguments = argVars' ++ (alignVal:isVolVal)
|
||||
statement $ Expr $ Call StdCall fptr arguments []
|
||||
@@ -446,7 +444,6 @@ genCall target res args = runStmtsDecls $ do
|
||||
| never_returns = statement $ Unreachable
|
||||
| otherwise = return ()
|
||||
|
||||
- doTrashStmts
|
||||
|
||||
-- make the actual call
|
||||
case retTy of
|
||||
@@ -1759,12 +1756,9 @@ genLit _ CmmHighStackMark
|
||||
funPrologue :: LiveGlobalRegs -> [CmmBlock] -> LlvmM StmtData
|
||||
funPrologue live cmmBlocks = do
|
||||
|
||||
- trash <- getTrashRegs
|
||||
let getAssignedRegs :: CmmNode O O -> [CmmReg]
|
||||
getAssignedRegs (CmmAssign reg _) = [reg]
|
||||
- -- Calls will trash all registers. Unfortunately, this needs them to
|
||||
- -- be stack-allocated in the first place.
|
||||
- getAssignedRegs (CmmUnsafeForeignCall _ rs _) = map CmmGlobal trash ++ map CmmLocal rs
|
||||
+ getAssignedRegs (CmmUnsafeForeignCall _ rs _) = map CmmLocal rs
|
||||
getAssignedRegs _ = []
|
||||
getRegsBlock (_, body, _) = concatMap getAssignedRegs $ blockToList body
|
||||
assignedRegs = nub $ concatMap (getRegsBlock . blockSplit) cmmBlocks
|
||||
@@ -1794,14 +1788,9 @@ funPrologue live cmmBlocks = do
|
||||
funEpilogue :: LiveGlobalRegs -> LlvmM ([LlvmVar], LlvmStatements)
|
||||
funEpilogue live = do
|
||||
|
||||
- -- Have information and liveness optimisation is enabled?
|
||||
- let liveRegs = alwaysLive ++ live
|
||||
- isSSE (FloatReg _) = True
|
||||
- isSSE (DoubleReg _) = True
|
||||
- isSSE (XmmReg _) = True
|
||||
- isSSE (YmmReg _) = True
|
||||
- isSSE (ZmmReg _) = True
|
||||
- isSSE _ = False
|
||||
+ -- the bool indicates whether the register is padding.
|
||||
+ let alwaysNeeded = map (\r -> (False, r)) alwaysLive
|
||||
+ livePadded = alwaysNeeded ++ padLiveArgs live
|
||||
|
||||
-- Set to value or "undef" depending on whether the register is
|
||||
-- actually live
|
||||
@@ -1813,39 +1802,17 @@ funEpilogue live = do
|
||||
let ty = (pLower . getVarType $ lmGlobalRegVar dflags r)
|
||||
return (Just $ LMLitVar $ LMUndefLit ty, nilOL)
|
||||
platform <- getDynFlag targetPlatform
|
||||
- loads <- flip mapM (activeStgRegs platform) $ \r -> case () of
|
||||
- _ | r `elem` liveRegs -> loadExpr r
|
||||
- | not (isSSE r) -> loadUndef r
|
||||
+ let allRegs = activeStgRegs platform
|
||||
+ loads <- flip mapM allRegs $ \r -> case () of
|
||||
+ _ | (False, r) `elem` livePadded
|
||||
+ -> loadExpr r -- if r is not padding, load it
|
||||
+ | not (isSSE r) || (True, r) `elem` livePadded
|
||||
+ -> loadUndef r
|
||||
| otherwise -> return (Nothing, nilOL)
|
||||
|
||||
let (vars, stmts) = unzip loads
|
||||
return (catMaybes vars, concatOL stmts)
|
||||
|
||||
-
|
||||
--- | A series of statements to trash all the STG registers.
|
||||
---
|
||||
--- In LLVM we pass the STG registers around everywhere in function calls.
|
||||
--- So this means LLVM considers them live across the entire function, when
|
||||
--- in reality they usually aren't. For Caller save registers across C calls
|
||||
--- the saving and restoring of them is done by the Cmm code generator,
|
||||
--- using Cmm local vars. So to stop LLVM saving them as well (and saving
|
||||
--- all of them since it thinks they're always live, we trash them just
|
||||
--- before the call by assigning the 'undef' value to them. The ones we
|
||||
--- need are restored from the Cmm local var and the ones we don't need
|
||||
--- are fine to be trashed.
|
||||
-getTrashStmts :: LlvmM LlvmStatements
|
||||
-getTrashStmts = do
|
||||
- regs <- getTrashRegs
|
||||
- stmts <- flip mapM regs $ \ r -> do
|
||||
- reg <- getCmmReg (CmmGlobal r)
|
||||
- let ty = (pLower . getVarType) reg
|
||||
- return $ Store (LMLitVar $ LMUndefLit ty) reg
|
||||
- return $ toOL stmts
|
||||
-
|
||||
-getTrashRegs :: LlvmM [GlobalReg]
|
||||
-getTrashRegs = do plat <- getLlvmPlatform
|
||||
- return $ filter (callerSaves plat) (activeStgRegs plat)
|
||||
-
|
||||
-- | Get a function pointer to the CLabel specified.
|
||||
--
|
||||
-- This is for Haskell functions, function type is assumed, so doesn't work
|
||||
@@ -1967,7 +1934,3 @@ getCmmRegW = lift . getCmmReg
|
||||
genLoadW :: Atomic -> CmmExpr -> CmmType -> WriterT LlvmAccum LlvmM LlvmVar
|
||||
genLoadW atomic e ty = liftExprData $ genLoad atomic e ty
|
||||
|
||||
-doTrashStmts :: WriterT LlvmAccum LlvmM ()
|
||||
-doTrashStmts = do
|
||||
- stmts <- lift getTrashStmts
|
||||
- tell $ LlvmAccum stmts mempty
|
||||
diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs
|
||||
index 86dd913461c..f4d5e7f553c 100644
|
||||
--- a/compiler/main/DriverPipeline.hs
|
||||
+++ b/compiler/main/DriverPipeline.hs
|
||||
@@ -1465,7 +1465,7 @@ runPhase (RealPhase LlvmOpt) input_fn dflags
|
||||
-- we always (unless -optlo specified) run Opt since we rely on it to
|
||||
-- fix up some pretty big deficiencies in the code we generate
|
||||
llvmOpts = case optLevel dflags of
|
||||
- 0 -> "-mem2reg -globalopt"
|
||||
+ 0 -> "-mem2reg -globalopt -lower-expect"
|
||||
1 -> "-O1 -globalopt"
|
||||
_ -> "-O2"
|
||||
|
@ -1,70 +0,0 @@
|
||||
diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs
|
||||
--- a/utils/ghc-pkg/Main.hs
|
||||
+++ b/utils/ghc-pkg/Main.hs
|
||||
@@ -1208,7 +1208,18 @@
|
||||
pkgsCabalFormat = packages db
|
||||
|
||||
pkgsGhcCacheFormat :: [PackageCacheFormat]
|
||||
- pkgsGhcCacheFormat = map convertPackageInfoToCacheFormat pkgsCabalFormat
|
||||
+ pkgsGhcCacheFormat
|
||||
+ = map (recomputeValidAbiDeps pkgsCabalFormat) -- Note [Recompute abi-depends]
|
||||
+ $ map convertPackageInfoToCacheFormat
|
||||
+ pkgsCabalFormat
|
||||
+
|
||||
+ hasAnyAbiDepends :: InstalledPackageInfo -> Bool
|
||||
+ hasAnyAbiDepends x = length (abiDepends x) > 0
|
||||
+
|
||||
+-- -- warn when we find any (possibly-)bogus abi-depends fields;
|
||||
+-- -- Note [Recompute abi-depends]
|
||||
+-- when (any hasAnyAbiDepends pkgsCabalFormat) $
|
||||
+-- infoLn "ignoring (possibly broken) abi-depends field for packages"
|
||||
|
||||
when (verbosity > Normal) $
|
||||
infoLn ("writing cache " ++ filename)
|
||||
@@ -1231,6 +1242,45 @@
|
||||
ModuleName
|
||||
OpenModule
|
||||
|
||||
+{- Note [Recompute abi-depends]
|
||||
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
||||
+
|
||||
+Like most fields, `ghc-pkg` relies on who-ever is performing package
|
||||
+registration to fill in fields; this includes the `abi-depends` field present
|
||||
+for the package.
|
||||
+
|
||||
+However, this was likely a mistake, and is not very robust; in certain cases,
|
||||
+versions of Cabal may use bogus abi-depends fields for a package when doing
|
||||
+builds. Why? Because package database information is aggressively cached; it is
|
||||
+possible to work Cabal into a situation where it uses a cached version of
|
||||
+`abi-depends`, rather than the one in the actual database after it has been
|
||||
+recomputed.
|
||||
+
|
||||
+However, there is an easy fix: ghc-pkg /already/ knows the `abi-depends` of a
|
||||
+package, because they are the ABIs of the packages pointed at by the `depends`
|
||||
+field. So it can simply look up the abi from the dependencies in the original
|
||||
+database, and ignore whatever the system registering gave it.
|
||||
+
|
||||
+So, instead, we do two things here:
|
||||
+
|
||||
+ - We throw away the information for a registered package's `abi-depends` field.
|
||||
+
|
||||
+ - We recompute it: we simply look up the unit ID of the package in the original
|
||||
+ database, and use *its* abi-depends.
|
||||
+
|
||||
+See Trac #14381, and Cabal issue #4728.
|
||||
+
|
||||
+-}
|
||||
+
|
||||
+recomputeValidAbiDeps :: [InstalledPackageInfo] -> PackageCacheFormat -> PackageCacheFormat
|
||||
+recomputeValidAbiDeps db pkg = pkg { GhcPkg.abiDepends = catMaybes (newAbiDeps) }
|
||||
+ where
|
||||
+ newAbiDeps = flip map (GhcPkg.abiDepends pkg) $ \(k, _) ->
|
||||
+ case filter (\d -> installedUnitId d == k) db of
|
||||
+ [] -> Nothing
|
||||
+ [x] -> Just (k, unAbiHash (abiHash x))
|
||||
+ _ -> Nothing -- ???
|
||||
+
|
||||
convertPackageInfoToCacheFormat :: InstalledPackageInfo -> PackageCacheFormat
|
||||
convertPackageInfoToCacheFormat pkg =
|
||||
GhcPkg.InstalledPackageInfo {
|
||||
|
@ -0,0 +1,51 @@
|
||||
Description: Allow unregisterised ghc-8.2 to build newer GHC
|
||||
Commit b68697e579d38ca29c2b84377dc2affa04659a28 introduced a regression
|
||||
stopping existing unregisteristed compilers from being used to compile a newer
|
||||
version of GHC. The problem is that the bootstrap compiler uses the newer Stg.h
|
||||
where EB_, IB_, etc, definitions have changed resulting in the following error:
|
||||
.
|
||||
error: conflicting types for 'ghc_GhcPrelude_zdtrModule4_bytes'
|
||||
note: in definition of macro 'EB_'
|
||||
#define EB_(X) extern const char X[]
|
||||
note: previous definition of 'ghc_GhcPrelude_zdtrModule4_bytes' was here
|
||||
char ghc_GhcPrelude_zdtrModule4_bytes[] = "ghc";
|
||||
.
|
||||
For more information about the problem, see https://phabricator.haskell.org/D4114.
|
||||
.
|
||||
This patch is a rework of https://phabricator.haskell.org/D3741.
|
||||
It modifies Stg.h to include the old definitions, if a compiler older than
|
||||
8.4 is being used.
|
||||
.
|
||||
This patch can be removed, once ghc-8.2 is no longer the bootstrap compiler.
|
||||
Author: Ilias Tsitsimpis <iliastsi@debian.org>
|
||||
Bug: https://ghc.haskell.org/trac/ghc/ticket/15201
|
||||
|
||||
Index: b/includes/Stg.h
|
||||
===================================================================
|
||||
--- a/includes/Stg.h
|
||||
+++ b/includes/Stg.h
|
||||
@@ -232,6 +232,16 @@ typedef StgInt I_;
|
||||
typedef StgWord StgWordArray[];
|
||||
typedef StgFunPtr F_;
|
||||
|
||||
+#if __GLASGOW_HASKELL__ < 804
|
||||
+#define EB_(X) extern char X[]
|
||||
+#define IB_(X) static char X[]
|
||||
+#define EI_(X) extern StgWordArray (X) GNU_ATTRIBUTE(aligned (8))
|
||||
+#define II_(X) static StgWordArray (X) GNU_ATTRIBUTE(aligned (8))
|
||||
+#define IF_(f) static StgFunPtr GNUC3_ATTRIBUTE(used) f(void)
|
||||
+#define FN_(f) StgFunPtr f(void)
|
||||
+#define EF_(f) StgFunPtr f(void) /* External Cmm functions */
|
||||
+#define EFF_(f) void f() /* See Note [External function prototypes] */
|
||||
+#else
|
||||
/* byte arrays (and strings): */
|
||||
#define EB_(X) extern const char X[]
|
||||
#define IB_(X) static const char X[]
|
||||
@@ -250,6 +260,7 @@ typedef StgFunPtr F_;
|
||||
#define EF_(f) StgFunPtr f(void) /* External Cmm functions */
|
||||
/* foreign functions: */
|
||||
#define EFF_(f) void f() /* See Note [External function prototypes] */
|
||||
+#endif /* __GLASGOW_HASKELL__ < 804 */
|
||||
|
||||
/* Note [External function prototypes] See Trac #8965, #11395
|
||||
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
@ -1,78 +0,0 @@
|
||||
On ARM, we want to make sure that GHC uses the gold linker.
|
||||
|
||||
In order to achieve that, we need to get `-fuse-ld=gold` into
|
||||
SettingsCCompilerLinkFlags in the settings.
|
||||
|
||||
This field is filled with only CONF_GCC_LINKER_OPTS_STAGE2. So we want that
|
||||
flag to show up there.
|
||||
|
||||
But this variable is used in a few other cases (LDFLAGS, options to hsc2hs)
|
||||
where -fuse-ld=gold caused problems.
|
||||
(These problems were not investigated. Maybe _they_ could be solved?)
|
||||
|
||||
So as a work-around we remove any other use of CONF_GCC_LINKER_OPTS_STAGE2.
|
||||
|
||||
|
||||
Index: ghc-7.8.3.20141119/libffi/ghc.mk
|
||||
===================================================================
|
||||
--- ghc-7.8.3.20141119.orig/libffi/ghc.mk 2014-04-07 20:26:08.000000000 +0200
|
||||
+++ ghc-7.8.3.20141119/libffi/ghc.mk 2014-12-08 18:57:03.392339809 +0100
|
||||
@@ -88,7 +88,7 @@
|
||||
NM=$(NM) \
|
||||
RANLIB=$(REAL_RANLIB_CMD) \
|
||||
CFLAGS="$(SRC_CC_OPTS) $(CONF_CC_OPTS_STAGE1) -w" \
|
||||
- LDFLAGS="$(SRC_LD_OPTS) $(CONF_GCC_LINKER_OPTS_STAGE1) -w" \
|
||||
+ LDFLAGS="$(SRC_LD_OPTS) -w" \
|
||||
"$(SHELL)" ./configure \
|
||||
--prefix=$(TOP)/libffi/build/inst \
|
||||
--libdir=$(TOP)/libffi/build/inst/lib \
|
||||
Index: ghc-7.8.3.20141119/mk/config.mk.in
|
||||
===================================================================
|
||||
--- ghc-7.8.3.20141119.orig/mk/config.mk.in 2014-12-08 18:49:28.215171926 +0100
|
||||
+++ ghc-7.8.3.20141119/mk/config.mk.in 2014-12-08 18:57:20.637055726 +0100
|
||||
@@ -570,7 +570,6 @@
|
||||
# $1 = stage
|
||||
SRC_HSC2HS_OPTS_STAGE$1 += $$(addprefix --cflag=,$$(filter-out -O,$$(SRC_CC_OPTS) $$(CONF_CC_OPTS_STAGE$1)))
|
||||
SRC_HSC2HS_OPTS_STAGE$1 += $$(addprefix --cflag=,$$(CONF_CPP_OPTS_STAGE$1))
|
||||
-SRC_HSC2HS_OPTS_STAGE$1 += $$(addprefix --lflag=,$$(CONF_GCC_LINKER_OPTS_STAGE$1))
|
||||
endef
|
||||
$(eval $(call set_stage_HSC2HS_OPTS,0))
|
||||
$(eval $(call set_stage_HSC2HS_OPTS,1))
|
||||
Index: ghc-7.8.3.20141119/rules/build-package-data.mk
|
||||
===================================================================
|
||||
--- ghc-7.8.3.20141119.orig/rules/build-package-data.mk 2014-04-14 14:38:12.000000000 +0200
|
||||
+++ ghc-7.8.3.20141119/rules/build-package-data.mk 2014-12-08 18:57:49.366250332 +0100
|
||||
@@ -50,7 +50,7 @@
|
||||
# for a feature it may not generate warning-free C code, and thus may
|
||||
# think that the feature doesn't exist if -Werror is on.
|
||||
$1_$2_CONFIGURE_CFLAGS = $$(filter-out -Werror,$$(SRC_CC_OPTS)) $$(CONF_CC_OPTS_STAGE$3) $$($1_CC_OPTS) $$($1_$2_CC_OPTS) $$(SRC_CC_WARNING_OPTS)
|
||||
-$1_$2_CONFIGURE_LDFLAGS = $$(SRC_LD_OPTS) $$(CONF_GCC_LINKER_OPTS_STAGE$3) $$($1_LD_OPTS) $$($1_$2_LD_OPTS)
|
||||
+$1_$2_CONFIGURE_LDFLAGS = $$(SRC_LD_OPTS) $$($1_LD_OPTS) $$($1_$2_LD_OPTS)
|
||||
$1_$2_CONFIGURE_CPPFLAGS = $$(SRC_CPP_OPTS) $$(CONF_CPP_OPTS_STAGE$3) $$($1_CPP_OPTS) $$($1_$2_CPP_OPTS)
|
||||
|
||||
$1_$2_CONFIGURE_OPTS += --configure-option=CFLAGS="$$($1_$2_CONFIGURE_CFLAGS)"
|
||||
Index: ghc-7.8.3.20141119/rules/distdir-opts.mk
|
||||
===================================================================
|
||||
--- ghc-7.8.3.20141119.orig/rules/distdir-opts.mk 2014-04-07 20:26:08.000000000 +0200
|
||||
+++ ghc-7.8.3.20141119/rules/distdir-opts.mk 2014-12-08 18:58:18.435461083 +0100
|
||||
@@ -64,7 +64,6 @@
|
||||
endif
|
||||
|
||||
$1_$2_DIST_LD_OPTS = \
|
||||
- $$(CONF_GCC_LINKER_OPTS_STAGE$3) \
|
||||
$$(SRC_LD_OPTS) \
|
||||
$$($1_LD_OPTS) \
|
||||
$$($1_$2_LD_OPTS) \
|
||||
Index: ghc-7.8.3.20141119/utils/hsc2hs/ghc.mk
|
||||
===================================================================
|
||||
--- ghc-7.8.3.20141119.orig/utils/hsc2hs/ghc.mk 2014-04-07 20:26:15.000000000 +0200
|
||||
+++ ghc-7.8.3.20141119/utils/hsc2hs/ghc.mk 2014-12-08 18:57:07.848524715 +0100
|
||||
@@ -27,7 +27,7 @@
|
||||
# system uses it for all stages and passes the right options for each stage
|
||||
# on the command line
|
||||
define utils/hsc2hs_dist-install_SHELL_WRAPPER_EXTRA
|
||||
-echo 'HSC2HS_EXTRA="$(addprefix --cflag=,$(CONF_CC_OPTS_STAGE1)) $(addprefix --lflag=,$(CONF_GCC_LINKER_OPTS_STAGE1))"' >> "$(WRAPPER)"
|
||||
+echo 'HSC2HS_EXTRA="$(addprefix --cflag=,$(CONF_CC_OPTS_STAGE1))"' >> "$(WRAPPER)"
|
||||
endef
|
||||
|
||||
ifneq "$(BINDIST)" "YES"
|
@ -1,20 +1,12 @@
|
||||
--- ghc-8.2.2/libraries/Cabal/Cabal/Distribution/Simple/Install.hs~ 2017-05-05 16:51:43.000000000 +0200
|
||||
+++ ghc-8.2.2/libraries/Cabal/Cabal/Distribution/Simple/Install.hs 2018-01-23 23:05:47.047081056 +0100
|
||||
@@ -36,7 +36,7 @@
|
||||
import Distribution.Simple.Utils
|
||||
( createDirectoryIfMissingVerbose
|
||||
, installDirectoryContents, installOrdinaryFile, isInSearchPath
|
||||
- , die', info, noticeNoWrap, warn, matchDirFileGlob )
|
||||
+ , die', info, noticeNoWrap, warn, matchDirFileGlob, debug )
|
||||
import Distribution.Simple.Compiler
|
||||
( CompilerFlavor(..), compilerFlavor )
|
||||
import Distribution.Simple.Setup
|
||||
@@ -215,7 +215,7 @@
|
||||
--- ghc-8.2.2/libraries/Cabal/Cabal/Distribution/Simple/Install.hs~ 2017-05-05 23:51:43.000000000 +0900
|
||||
+++ ghc-8.2.2/libraries/Cabal/Cabal/Distribution/Simple/Install.hs 2018-02-27 12:22:13.159432104 +0900
|
||||
@@ -215,8 +215,7 @@
|
||||
++ " in " ++ binPref)
|
||||
inPath <- isInSearchPath binPref
|
||||
when (not inPath) $
|
||||
- warn verbosity ("The directory " ++ binPref
|
||||
+ debug verbosity ("The directory " ++ binPref
|
||||
++ " is not in the system search path.")
|
||||
- ++ " is not in the system search path.")
|
||||
+ warn verbosity ("Executable installed in " ++ binPref)
|
||||
case compilerFlavor (compiler lbi) of
|
||||
GHC -> GHC.installExe verbosity lbi binPref buildPref progFix pkg_descr exe
|
||||
GHCJS -> GHCJS.installExe verbosity lbi binPref buildPref progFix pkg_descr exe
|
||||
|
@ -1,43 +0,0 @@
|
||||
This is an attempt to make GHC build reproducible. The name of .c files may end
|
||||
up in the resulting binary (in the debug section), but not the directory.
|
||||
|
||||
Instead of using the process id, create a hash from the command line arguments,
|
||||
and assume that is going to be unique.
|
||||
|
||||
Index: ghc-8.0.2/compiler/main/SysTools.hs
|
||||
===================================================================
|
||||
--- ghc-8.0.2.orig/compiler/main/SysTools.hs
|
||||
+++ ghc-8.0.2/compiler/main/SysTools.hs
|
||||
@@ -65,6 +65,7 @@
|
||||
import Util
|
||||
import DynFlags
|
||||
import Exception
|
||||
+import Fingerprint
|
||||
|
||||
import LlvmCodeGen.Base (llvmVersionStr, supportedLlvmVersion)
|
||||
|
||||
@@ -1145,8 +1146,8 @@
|
||||
mapping <- readIORef dir_ref
|
||||
case Map.lookup tmp_dir mapping of
|
||||
Nothing -> do
|
||||
- pid <- getProcessID
|
||||
- let prefix = tmp_dir </> "ghc" ++ show pid ++ "_"
|
||||
+ pid <- getStableProcessID
|
||||
+ let prefix = tmp_dir </> "ghc" ++ pid ++ "_"
|
||||
mask_ $ mkTempDir prefix
|
||||
Just dir -> return dir
|
||||
where
|
||||
@@ -1562,6 +1563,13 @@
|
||||
getProcessID = System.Posix.Internals.c_getpid >>= return . fromIntegral
|
||||
#endif
|
||||
|
||||
+-- Debian-specific hack to get reproducible output, by not using the "random"
|
||||
+-- pid, but rather something determinisic
|
||||
+getStableProcessID :: IO String
|
||||
+getStableProcessID = do
|
||||
+ args <- getArgs
|
||||
+ return $ take 4 $ show $ fingerprintString $ unwords args
|
||||
+
|
||||
-- Divvy up text stream into lines, taking platform dependent
|
||||
-- line termination into account.
|
||||
linesPlatform :: String -> [String]
|
@ -1,2 +1 @@
|
||||
SHA512 (ghc-8.2.2-src.tar.xz) = 6549416f470b599973d409fa45f59c25b07e6a94798cef1a19ad432547dc225338cf4dbc4a4793114b4a417798a3b59b122b92b020251074405c5302b7ffe799
|
||||
SHA512 (ghc-8.2.2-testsuite.tar.xz) = 5b60413910bce2ef0d71e2f531d7297cefc0b03df3e23d63f7a872d9a264e1512b2d6631a3fba35e72d113389762ba34d503649ea4a852ce9fd42e94ef6b96dc
|
||||
SHA512 (ghc-8.4.4-src.tar.xz) = 685e102eee8cf8b6a377afd7871998c8c368a5da288469367e3fb804aa6109e6f59be5945b8cd3d1e36c851190ea9a7f74c576528589589313d237b721d86da5
|
||||
|
Loading…
Reference in new issue