From 40733c85d70dc16d3cd5bb27728fc7901cdaebda Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Feb 15 2019 16:30:41 +0000 Subject: update to 8.4 (rebase to 8.4 branch) --- diff --git a/.gitignore b/.gitignore index 8ced83f..5c04983 100644 --- a/.gitignore +++ b/.gitignore @@ -25,3 +25,4 @@ testsuite-6.12.3.tar.bz2 /ghc-8.0.2/ /ghc-8.2.2-src.tar.xz /ghc-8.2.2-testsuite.tar.xz +/ghc-8.4.4-src.tar.xz diff --git a/6e361d895dda4600a85e01c72ff219474b5c7190.patch b/6e361d895dda4600a85e01c72ff219474b5c7190.patch new file mode 100644 index 0000000..9f2e86a --- /dev/null +++ b/6e361d895dda4600a85e01c72ff219474b5c7190.patch @@ -0,0 +1,277 @@ +From 6e361d895dda4600a85e01c72ff219474b5c7190 Mon Sep 17 00:00:00 2001 +From: Kavon Farvardin +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" + diff --git a/D4159.patch b/D4159.patch deleted file mode 100644 index 17db2f3..0000000 --- a/D4159.patch +++ /dev/null @@ -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 { - diff --git a/buildpath-abi-stability.patch b/buildpath-abi-stability.patch new file mode 100644 index 0000000..1d45c72 --- /dev/null +++ b/buildpath-abi-stability.patch @@ -0,0 +1,23 @@ +Forwarded to https://ghc.haskell.org/trac/ghc/ticket/10424 + +--- a/compiler/iface/MkIface.hs ++++ b/compiler/iface/MkIface.hs +@@ -681,7 +681,7 @@ addFingerprints hsc_env mb_old_fingerpri + iface_hash <- computeFingerprint putNameLiterally + (mod_hash, + ann_fn (mkVarOcc "module"), -- See mkIfaceAnnCache +- mi_usages iface0, ++ usages, + sorted_deps, + mi_hpc iface0) + +@@ -714,6 +714,9 @@ addFingerprints hsc_env mb_old_fingerpri + (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph (mi_fam_insts iface0) + fix_fn = mi_fix_fn iface0 + ann_fn = mkIfaceAnnCache (mi_anns iface0) ++ -- Do not allow filenames to affect the interface ++ usages = [ case u of UsageFile _ fp -> UsageFile "" fp; _ -> u | u <- mi_usages iface0 ] ++ + + -- | Retrieve the orphan hashes 'mi_orphan_hash' for a list of modules + -- (in particular, the orphan modules which are transitively imported by the diff --git a/fix-build-using-unregisterized-v8.2.patch b/fix-build-using-unregisterized-v8.2.patch new file mode 100644 index 0000000..29d7b49 --- /dev/null +++ b/fix-build-using-unregisterized-v8.2.patch @@ -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 +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 + ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/ghc-7.8-arm7_saner-linker-opt-handling-9873.patch b/ghc-7.8-arm7_saner-linker-opt-handling-9873.patch deleted file mode 100644 index c44a21f..0000000 --- a/ghc-7.8-arm7_saner-linker-opt-handling-9873.patch +++ /dev/null @@ -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" diff --git a/ghc-Cabal-install-PATH-warning.patch b/ghc-Cabal-install-PATH-warning.patch index 5081fa1..786c5d9 100644 --- a/ghc-Cabal-install-PATH-warning.patch +++ b/ghc-Cabal-install-PATH-warning.patch @@ -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 diff --git a/ghc-Debian-buildpath-abi-stability.patch b/ghc-Debian-buildpath-abi-stability.patch deleted file mode 100644 index 1d45c72..0000000 --- a/ghc-Debian-buildpath-abi-stability.patch +++ /dev/null @@ -1,23 +0,0 @@ -Forwarded to https://ghc.haskell.org/trac/ghc/ticket/10424 - ---- a/compiler/iface/MkIface.hs -+++ b/compiler/iface/MkIface.hs -@@ -681,7 +681,7 @@ addFingerprints hsc_env mb_old_fingerpri - iface_hash <- computeFingerprint putNameLiterally - (mod_hash, - ann_fn (mkVarOcc "module"), -- See mkIfaceAnnCache -- mi_usages iface0, -+ usages, - sorted_deps, - mi_hpc iface0) - -@@ -714,6 +714,9 @@ addFingerprints hsc_env mb_old_fingerpri - (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph (mi_fam_insts iface0) - fix_fn = mi_fix_fn iface0 - ann_fn = mkIfaceAnnCache (mi_anns iface0) -+ -- Do not allow filenames to affect the interface -+ usages = [ case u of UsageFile _ fp -> UsageFile "" fp; _ -> u | u <- mi_usages iface0 ] -+ - - -- | Retrieve the orphan hashes 'mi_orphan_hash' for a list of modules - -- (in particular, the orphan modules which are transitively imported by the diff --git a/ghc-Debian-no-missing-haddock-file-warning.patch b/ghc-Debian-no-missing-haddock-file-warning.patch deleted file mode 100644 index eac921e..0000000 --- a/ghc-Debian-no-missing-haddock-file-warning.patch +++ /dev/null @@ -1,22 +0,0 @@ -Description: Do not emit a warning if the .haddock file is missing - As it is quite common on Debian installations to install the -dev package - without the -doc package. -Author: Joachim Breitner - -Index: ghc-8.0.2/utils/ghc-pkg/Main.hs -=================================================================== ---- ghc-8.0.2.orig/utils/ghc-pkg/Main.hs -+++ ghc-8.0.2/utils/ghc-pkg/Main.hs -@@ -1588,8 +1588,10 @@ - mapM_ (checkDir True "dynamic-library-dirs") (libraryDynDirs pkg) - mapM_ (checkDir True "include-dirs") (includeDirs pkg) - mapM_ (checkDir True "framework-dirs") (frameworkDirs pkg) -- mapM_ (checkFile True "haddock-interfaces") (haddockInterfaces pkg) -- mapM_ (checkDirURL True "haddock-html") (haddockHTMLs pkg) -+ -- In Debian, it is quite normal that the package is installed without the -+ -- documentation. Do not print a warning there. -+ -- mapM_ (checkFile True "haddock-interfaces") (haddockInterfaces pkg) -+ -- mapM_ (checkDirURL True "haddock-html") (haddockHTMLs pkg) - checkDuplicateModules pkg - checkExposedModules db_stack pkg - checkOtherModules pkg diff --git a/ghc-Debian-reproducible-tmp-names.patch b/ghc-Debian-reproducible-tmp-names.patch deleted file mode 100644 index 16ffc32..0000000 --- a/ghc-Debian-reproducible-tmp-names.patch +++ /dev/null @@ -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] diff --git a/ghc-Debian-x32-use-native-x86_64-insn.patch b/ghc-Debian-x32-use-native-x86_64-insn.patch deleted file mode 100644 index 6105b5b..0000000 --- a/ghc-Debian-x32-use-native-x86_64-insn.patch +++ /dev/null @@ -1,27 +0,0 @@ -Description: Use native x86_64 instructions on x32 - This patch enables a few native 64-bit integer instructions - on x32 which are available on this architecture despite using - 32-bit pointers. These instructions are present on x86_64 but - not on x86 and ghc checks the size of (void *) to determine - that. This method fails on x32 since despite using 32-bit - pointers and hence sizeof(void *) == 4, it still uses the - full x86_64 instruction set and software-emulated variants - of the aforementioned 64-bit integer instructions are - therefore not present in the toolchain which will make ghc - fail to build on x32. - See: https://ghc.haskell.org/trac/ghc/ticket/11571 - . - -Index: ghc-8.0.2/rts/RtsSymbols.c -=================================================================== ---- ghc-8.0.2.orig/rts/RtsSymbols.c -+++ ghc-8.0.2/rts/RtsSymbols.c -@@ -857,7 +857,7 @@ - - - // 64-bit support functions in libgcc.a --#if defined(__GNUC__) && SIZEOF_VOID_P <= 4 && !defined(_ABIN32) -+#if defined(__GNUC__) && SIZEOF_VOID_P <= 4 && !defined(_ABIN32) && !(defined(__x86_64__) && defined(__ILP32__)) - #define RTS_LIBGCC_SYMBOLS \ - SymI_NeedsProto(__divdi3) \ - SymI_NeedsProto(__udivdi3) \ diff --git a/ghc.spec b/ghc.spec index 99216be..0099070 100644 --- a/ghc.spec +++ b/ghc.spec @@ -26,20 +26,20 @@ # no longer build testsuite (takes time and not really being used) %bcond_with testsuite -# 8.2 needs llvm-3.9 -%global llvm_major 3.9 +# 8.4 needs llvm-5.0 +%global llvm_major 5.0 %global ghc_llvm_archs armv7hl aarch64 %global ghc_unregisterized_arches s390 s390x %{mips} Name: ghc # ghc must be rebuilt after a version bump to avoid ABI change problems -Version: 8.2.2 +Version: 8.4.4 # Since library subpackages are versioned: # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 72%{?dist} +Release: 73%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -56,10 +56,6 @@ Source7: runghc.man # absolute haddock path (was for html/libraries -> libraries) Patch1: ghc-gen_contents_index-haddock-path.patch Patch2: ghc-Cabal-install-PATH-warning.patch -# https://github.com/haskell/cabal/issues/4728 -# https://ghc.haskell.org/trac/ghc/ticket/14381 -# https://phabricator.haskell.org/D4159 -Patch4: D4159.patch # https://github.com/ghc/ghc/pull/143 Patch5: ghc-configure-fix-sphinx-version-check.patch @@ -69,11 +65,15 @@ Patch12: ghc-armv7-VFPv3D16--NEON.patch # https://ghc.haskell.org/trac/ghc/ticket/15689 Patch15: ghc-warnings.mk-CC-Wall.patch +# revert 8.4.4 llvm changes +# https://ghc.haskell.org/trac/ghc/ticket/15780 +Patch16: https://github.com/ghc/ghc/commit/6e361d895dda4600a85e01c72ff219474b5c7190.patch + # Debian patches: -Patch24: ghc-Debian-buildpath-abi-stability.patch -Patch26: ghc-Debian-no-missing-haddock-file-warning.patch -Patch27: ghc-Debian-reproducible-tmp-names.patch -Patch28: ghc-Debian-x32-use-native-x86_64-insn.patch +Patch24: buildpath-abi-stability.patch +Patch26: no-missing-haddock-file-warning.patch +Patch28: x32-use-native-x86_64-insn.patch +Patch30: fix-build-using-unregisterized-v8.2.patch # fedora ghc has been bootstrapped on # %%{ix86} x86_64 ppc ppc64 armv7hl s390 s390x ppc64le aarch64 @@ -85,13 +85,14 @@ BuildRequires: ghc-compiler %if %{with abicheck} BuildRequires: ghc %endif -BuildRequires: ghc-rpm-macros-extra >= 1.8 +BuildRequires: ghc-rpm-macros-extra BuildRequires: ghc-binary-devel BuildRequires: ghc-bytestring-devel BuildRequires: ghc-containers-devel BuildRequires: ghc-directory-devel BuildRequires: ghc-pretty-devel BuildRequires: ghc-process-devel +BuildRequires: ghc-transformers-devel BuildRequires: gmp-devel BuildRequires: libffi-devel # for terminfo @@ -216,35 +217,36 @@ This package provides the User Guide and Haddock manual. # use "./libraries-versions.sh" to check versions %if %{defined ghclibdir} -%ghc_lib_subpackage -d -l BSD Cabal-2.0.1.0 +%ghc_lib_subpackage -d -l BSD Cabal-2.2.0.1 %ghc_lib_subpackage -d -l %BSDHaskellReport array-0.5.2.0 -%ghc_lib_subpackage -d -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base-4.10.1.0 +%ghc_lib_subpackage -d -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base-4.11.1.0 %ghc_lib_subpackage -d -l BSD binary-0.8.5.1 %ghc_lib_subpackage -d -l BSD bytestring-0.10.8.2 -%ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.5.10.2 +%ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.5.11.0 %ghc_lib_subpackage -d -l %BSDHaskellReport deepseq-1.4.3.0 -%ghc_lib_subpackage -d -l %BSDHaskellReport directory-1.3.0.2 -%ghc_lib_subpackage -d -l BSD filepath-1.4.1.2 -%define ghc_pkg_obsoletes ghc-bin-package-db-devel < 0.0.0.0-12 +%ghc_lib_subpackage -d -l %BSDHaskellReport directory-1.3.1.5 +%ghc_lib_subpackage -d -l BSD filepath-1.4.2 # in ghc not ghc-libraries: %ghc_lib_subpackage -d -x ghc-%{ghc_version_override} -%undefine ghc_pkg_obsoletes %ghc_lib_subpackage -d -x -l BSD ghc-boot-%{ghc_version_override} %ghc_lib_subpackage -d -l BSD ghc-boot-th-%{ghc_version_override} %ghc_lib_subpackage -d -l BSD ghc-compact-0.1.0.0 %ghc_lib_subpackage -d -l BSD -x ghci-%{ghc_version_override} -%ghc_lib_subpackage -d -l BSD haskeline-0.7.4.0 -%ghc_lib_subpackage -d -l BSD hoopl-3.10.2.2 +%ghc_lib_subpackage -d -l BSD haskeline-0.7.4.2 %ghc_lib_subpackage -d -l BSD hpc-0.6.0.3 -%ghc_lib_subpackage -d -l BSD pretty-1.1.3.3 -%ghc_lib_subpackage -d -l %BSDHaskellReport process-1.6.1.0 -%ghc_lib_subpackage -d -l BSD template-haskell-2.12.0.0 -%ghc_lib_subpackage -d -l BSD -c ncurses-devel%{?_isa} terminfo-0.4.1.0 +%ghc_lib_subpackage -d -l BSD mtl-2.2.2 +%ghc_lib_subpackage -d -l BSD parsec-3.1.13.0 +%ghc_lib_subpackage -d -l BSD pretty-1.1.3.6 +%ghc_lib_subpackage -d -l %BSDHaskellReport process-1.6.3.0 +%ghc_lib_subpackage -d -l BSD stm-2.4.5.1 +%ghc_lib_subpackage -d -l BSD template-haskell-2.13.0.0 +%ghc_lib_subpackage -d -l BSD -c ncurses-devel%{?_isa} terminfo-0.4.1.1 +%ghc_lib_subpackage -d -l BSD text-1.2.3.1 %ghc_lib_subpackage -d -l BSD time-1.8.0.2 -%ghc_lib_subpackage -d -l BSD transformers-0.5.2.0 +%ghc_lib_subpackage -d -l BSD transformers-0.5.5.0 %ghc_lib_subpackage -d -l BSD unix-2.7.2.2 %if %{with docs} -%ghc_lib_subpackage -d -l BSD xhtml-3000.2.2 +%ghc_lib_subpackage -d -l BSD xhtml-3000.2.2.1 %endif %endif @@ -273,7 +275,6 @@ except the ghc library, which is installed by the toplevel ghc metapackage. %patch1 -p1 -b .orig %patch2 -p1 -b .orig -%patch4 -p1 -b .orig %patch5 -p1 -b .orig %if 0%{?fedora} || 0%{?rhel} > 6 @@ -288,10 +289,16 @@ rm -r libffi-tarballs %patch15 -p1 -b .orig %endif +%ifarch armv7hl aarch64 +%patch16 -p1 -b .orig -R +%endif + %patch24 -p1 -b .orig %patch26 -p1 -b .orig -%patch27 -p1 -b .orig %patch28 -p1 -b .orig +%ifarch s390x +%patch30 -p1 -b .orig +%endif %global gen_contents_index gen_contents_index.orig %if %{with docs} @@ -354,7 +361,6 @@ export CC=%{_bindir}/gcc --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ --docdir=%{_docdir}/ghc \ - --with-llc=%{_bindir}/llc-%{llvm_major} --with-opt=%{_bindir}/opt-%{llvm_major} \ %ifarch %{ghc_unregisterized_arches} --enable-unregisterised \ %endif @@ -379,6 +385,7 @@ done for i in %{buildroot}%{ghclibdir}/package.conf.d/*.conf; do sed -i -e 's!^dynamic-library-dirs: .*!dynamic-library-dirs: %{_libdir}!' $i done +sed -i -e 's!^library-dirs: %{ghclibdir}/rts!&\ndynamic-library-dirs: %{_libdir}!' %{buildroot}%{ghclibdir}/package.conf.d/rts.conf %endif for i in %{ghc_packages_list}; do @@ -397,8 +404,8 @@ echo "%%dir %{ghclibdir}" >> ghc-base%{?_ghcdynlibdir:-devel}.files %ghc_gen_filelists ghc-boot %{ghc_version_override} %ghc_gen_filelists ghc %{ghc_version_override} %ghc_gen_filelists ghci %{ghc_version_override} -%ghc_gen_filelists ghc-prim 0.5.1.1 -%ghc_gen_filelists integer-gmp 1.0.1.0 +%ghc_gen_filelists ghc-prim 0.5.2.0 +%ghc_gen_filelists integer-gmp 1.0.2.0 %define merge_filelist()\ cat ghc-%1.files >> ghc-%2.files\ @@ -584,6 +591,7 @@ fi %{ghclibdir}/bin/unlit %{ghclibdir}/ghc-usage.txt %{ghclibdir}/ghci-usage.txt +%{ghclibdir}/llvm-targets %dir %{ghclibdir}/package.conf.d %ghost %{ghclibdir}/package.conf.d/package.cache %{ghclibdir}/package.conf.d/package.cache.lock @@ -610,12 +618,14 @@ fi %{ghc_html_dir}/libraries/gen_contents_index %{ghc_html_dir}/libraries/prologue.txt %ghost %{ghc_html_dir}/libraries/doc-index*.html +%ghost %{ghc_html_dir}/libraries/haddock-bundle.min.js %ghost %{ghc_html_dir}/libraries/haddock-util.js %ghost %{ghc_html_dir}/libraries/hslogo-16.png %ghost %{ghc_html_dir}/libraries/index*.html %ghost %{ghc_html_dir}/libraries/minus.gif %ghost %{ghc_html_dir}/libraries/ocean.css %ghost %{ghc_html_dir}/libraries/plus.gif +%ghost %{ghc_html_dir}/libraries/quick-jump.css %ghost %{ghc_html_dir}/libraries/synopsis.png %dir %{_localstatedir}/lib/ghc %ghost %{_localstatedir}/lib/ghc/pkg-dir.cache @@ -643,6 +653,17 @@ fi %changelog +* Sat Feb 16 2019 Jens Petersen - 8.4.4-73 +- update to GHC 8.4 +- https://ghc.haskell.org/trac/ghc/blog/ghc-8.4.1-released +- new patches: + - 6e361d895dda4600a85e01c72ff219474b5c7190.patch + - fix-build-using-unregisterized-v8.2.patch +- dropped patch: + - D4159.patch + - ghc-7.8-arm7_saner-linker-opt-handling-9873.patch + - ghc-Debian-reproducible-tmp-names.patch + * Fri Feb 8 2019 Jens Petersen - 8.2.2-72 - add ghc_unregisterized_arches - Recommends zlib-devel diff --git a/no-missing-haddock-file-warning.patch b/no-missing-haddock-file-warning.patch new file mode 100644 index 0000000..eac921e --- /dev/null +++ b/no-missing-haddock-file-warning.patch @@ -0,0 +1,22 @@ +Description: Do not emit a warning if the .haddock file is missing + As it is quite common on Debian installations to install the -dev package + without the -doc package. +Author: Joachim Breitner + +Index: ghc-8.0.2/utils/ghc-pkg/Main.hs +=================================================================== +--- ghc-8.0.2.orig/utils/ghc-pkg/Main.hs ++++ ghc-8.0.2/utils/ghc-pkg/Main.hs +@@ -1588,8 +1588,10 @@ + mapM_ (checkDir True "dynamic-library-dirs") (libraryDynDirs pkg) + mapM_ (checkDir True "include-dirs") (includeDirs pkg) + mapM_ (checkDir True "framework-dirs") (frameworkDirs pkg) +- mapM_ (checkFile True "haddock-interfaces") (haddockInterfaces pkg) +- mapM_ (checkDirURL True "haddock-html") (haddockHTMLs pkg) ++ -- In Debian, it is quite normal that the package is installed without the ++ -- documentation. Do not print a warning there. ++ -- mapM_ (checkFile True "haddock-interfaces") (haddockInterfaces pkg) ++ -- mapM_ (checkDirURL True "haddock-html") (haddockHTMLs pkg) + checkDuplicateModules pkg + checkExposedModules db_stack pkg + checkOtherModules pkg diff --git a/sources b/sources index 6b499bd..a6f24f6 100644 --- a/sources +++ b/sources @@ -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 diff --git a/x32-use-native-x86_64-insn.patch b/x32-use-native-x86_64-insn.patch new file mode 100644 index 0000000..6105b5b --- /dev/null +++ b/x32-use-native-x86_64-insn.patch @@ -0,0 +1,27 @@ +Description: Use native x86_64 instructions on x32 + This patch enables a few native 64-bit integer instructions + on x32 which are available on this architecture despite using + 32-bit pointers. These instructions are present on x86_64 but + not on x86 and ghc checks the size of (void *) to determine + that. This method fails on x32 since despite using 32-bit + pointers and hence sizeof(void *) == 4, it still uses the + full x86_64 instruction set and software-emulated variants + of the aforementioned 64-bit integer instructions are + therefore not present in the toolchain which will make ghc + fail to build on x32. + See: https://ghc.haskell.org/trac/ghc/ticket/11571 + . + +Index: ghc-8.0.2/rts/RtsSymbols.c +=================================================================== +--- ghc-8.0.2.orig/rts/RtsSymbols.c ++++ ghc-8.0.2/rts/RtsSymbols.c +@@ -857,7 +857,7 @@ + + + // 64-bit support functions in libgcc.a +-#if defined(__GNUC__) && SIZEOF_VOID_P <= 4 && !defined(_ABIN32) ++#if defined(__GNUC__) && SIZEOF_VOID_P <= 4 && !defined(_ABIN32) && !(defined(__x86_64__) && defined(__ILP32__)) + #define RTS_LIBGCC_SYMBOLS \ + SymI_NeedsProto(__divdi3) \ + SymI_NeedsProto(__udivdi3) \