update to 7.10.3 from petersen/ghc-7.10.3 copr
- quick build - use 7.10.3b respin tarballs - no longer need: - ghc-glibc-2.20_BSD_SOURCE.patch - ghc-7.8-arm-use-ld-gold.patch - ghc-7.8-arm7_saner-linker-opt-handling-9873.patch - ghc-config.mk.in-Enable-SMP-and-GHCi-support-for-Aarch64.patch - build_minimum_smp - add Debian packages: - buildpath-abi-stability - no-missing-haddock-file-warning - reproducible-tmp-names - use llvm35 - add libraries-versions.sh script - all library versions updates except xhtml - BR ghc-rpm-macros-extra for all OS versions - support building on EL6 - deprecated libraries: haskell2010, haskell98, old-locale, old-time - symlink for integer-gmp2 - add llvm_major
This commit is contained in:
parent
9f9aa45539
commit
f50ec379b6
4
.gitignore
vendored
4
.gitignore
vendored
@ -16,3 +16,7 @@ testsuite-6.12.3.tar.bz2
|
||||
/ghc-7.8.3-testsuite.tar.xz
|
||||
/ghc-7.8.4-src.tar.xz
|
||||
/ghc-7.8.4-testsuite.tar.xz
|
||||
/ghc-7.8.4/
|
||||
/ghc-7.10.3/
|
||||
/ghc-7.10.3b-src.tar.xz
|
||||
/ghc-7.10.3b-testsuite.tar.xz
|
||||
|
@ -1,42 +0,0 @@
|
||||
armv7 by nomeata: https://ghc.haskell.org/trac/ghc/ticket/8976#comment:12
|
||||
arm64 backport of https://ghc.haskell.org/trac/ghc/ticket/9673#comment:28 (erikd)
|
||||
|
||||
--- ghc-7.8.4/aclocal.m4.24~ 2015-04-01 04:48:39.961193022 -0400
|
||||
+++ ghc-7.8.4/aclocal.m4 2015-04-01 04:50:19.708203082 -0400
|
||||
@@ -553,6 +553,14 @@
|
||||
$3="$$3 -D_HPUX_SOURCE"
|
||||
$5="$$5 -D_HPUX_SOURCE"
|
||||
;;
|
||||
+ arm*)
|
||||
+ # On arm, link using gold
|
||||
+ $3="$$3 -fuse-ld=gold"
|
||||
+ ;;
|
||||
+ aarch64*)
|
||||
+ # On arm, link using gold
|
||||
+ $3="$$3 -fuse-ld=gold"
|
||||
+ ;;
|
||||
esac
|
||||
|
||||
# If gcc knows about the stack protector, turn it off.
|
||||
--- ghc-7.8.4/configure.ac~ 2014-12-22 14:08:24.000000000 -0500
|
||||
+++ ghc-7.8.4/configure.ac 2015-04-22 00:08:54.646110535 -0400
|
||||
@@ -587,7 +587,18 @@
|
||||
dnl ** Which ld to use?
|
||||
dnl --------------------------------------------------------------
|
||||
FP_ARG_WITH_PATH_GNU_PROG([LD], [ld], [ld])
|
||||
-LdCmd="$LD"
|
||||
+case $target in
|
||||
+arm*linux* | aarch64*linux*)
|
||||
+ # Arm requires use of the binutils ld.gold linker.
|
||||
+ # This case should catch at least arm-unknown-linux-gnueabihf and
|
||||
+ # arm-linux-androideabi.
|
||||
+ FP_ARG_WITH_PATH_GNU_PROG([LD_GOLD], [ld.gold], [ld.gold])
|
||||
+ LdCmd="$LD_GOLD"
|
||||
+ ;;
|
||||
+*)
|
||||
+ LdCmd="$LD"
|
||||
+ ;;
|
||||
+esac
|
||||
AC_SUBST([LdCmd])
|
||||
|
||||
dnl ** Which nm to use?
|
25
ghc-Debian-buildpath-abi-stability.patch
Normal file
25
ghc-Debian-buildpath-abi-stability.patch
Normal file
@ -0,0 +1,25 @@
|
||||
Forwarded to https://ghc.haskell.org/trac/ghc/ticket/10424
|
||||
|
||||
Index: ghc-7.10.1/compiler/iface/MkIface.hs
|
||||
===================================================================
|
||||
--- ghc-7.10.1.orig/compiler/iface/MkIface.hs 2015-05-17 20:34:02.808643844 +0200
|
||||
+++ ghc-7.10.1/compiler/iface/MkIface.hs 2015-05-17 20:34:02.804643799 +0200
|
||||
@@ -611,7 +611,7 @@
|
||||
iface_hash <- computeFingerprint putNameLiterally
|
||||
(mod_hash,
|
||||
ann_fn (mkVarOcc "module"), -- See mkIfaceAnnCache
|
||||
- mi_usages iface0,
|
||||
+ usages,
|
||||
sorted_deps,
|
||||
mi_hpc iface0)
|
||||
|
||||
@@ -644,6 +644,9 @@
|
||||
(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 ]
|
||||
+
|
||||
|
||||
getOrphanHashes :: HscEnv -> [Module] -> IO [Fingerprint]
|
||||
getOrphanHashes hsc_env mods = do
|
22
ghc-Debian-no-missing-haddock-file-warning.patch
Normal file
22
ghc-Debian-no-missing-haddock-file-warning.patch
Normal file
@ -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 <nomeata@debian.org>
|
||||
|
||||
Index: ghc-7.10/utils/ghc-pkg/Main.hs
|
||||
===================================================================
|
||||
--- ghc-7.10.orig/utils/ghc-pkg/Main.hs 2015-07-22 11:17:04.787751658 +0200
|
||||
+++ ghc-7.10/utils/ghc-pkg/Main.hs 2015-07-22 11:17:04.787751658 +0200
|
||||
@@ -1533,8 +1533,10 @@
|
||||
mapM_ (checkDir True "library-dirs") (libraryDirs 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
|
43
ghc-Debian-reproducible-tmp-names.patch
Normal file
43
ghc-Debian-reproducible-tmp-names.patch
Normal file
@ -0,0 +1,43 @@
|
||||
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/compiler/main/SysTools.hs
|
||||
===================================================================
|
||||
--- ghc.orig/compiler/main/SysTools.hs 2015-11-02 17:23:05.410365013 +0100
|
||||
+++ ghc/compiler/main/SysTools.hs 2015-11-02 17:23:05.410365013 +0100
|
||||
@@ -66,6 +66,7 @@
|
||||
import Util
|
||||
import DynFlags
|
||||
import Exception
|
||||
+import Fingerprint
|
||||
|
||||
import Data.IORef
|
||||
import Control.Monad
|
||||
@@ -1152,8 +1153,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
|
||||
@@ -1531,6 +1532,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]
|
322
ghc-arm64.patch
322
ghc-arm64.patch
@ -1,322 +0,0 @@
|
||||
commit c29bf984dd20431cd4344e8a5c444d7a5be08389
|
||||
Author: Colin Watson <cjwatson@debian.org>
|
||||
Date: Mon Apr 21 22:26:56 2014 -0500
|
||||
Bug: https://ghc.haskell.org/trac/ghc/ticket/7942
|
||||
|
||||
ghc: initial AArch64 patches
|
||||
|
||||
Signed-off-by: Austin Seipp <austin@well-typed.com>
|
||||
|
||||
Index: ghc-7.8.3/aclocal.m4
|
||||
===================================================================
|
||||
--- ghc-7.8.3.orig/aclocal.m4 2014-07-10 10:16:42.533187516 +0200
|
||||
+++ ghc-7.8.3/aclocal.m4 2014-07-10 10:16:42.529187516 +0200
|
||||
@@ -197,6 +197,9 @@
|
||||
GET_ARM_ISA()
|
||||
test -z "[$]2" || eval "[$]2=\"ArchARM {armISA = \$ARM_ISA, armISAExt = \$ARM_ISA_EXT, armABI = \$ARM_ABI}\""
|
||||
;;
|
||||
+ aarch64)
|
||||
+ test -z "[$]2" || eval "[$]2=ArchARM64"
|
||||
+ ;;
|
||||
alpha)
|
||||
test -z "[$]2" || eval "[$]2=ArchAlpha"
|
||||
;;
|
||||
@@ -1862,6 +1865,9 @@
|
||||
# converts cpu from gnu to ghc naming, and assigns the result to $target_var
|
||||
AC_DEFUN([GHC_CONVERT_CPU],[
|
||||
case "$1" in
|
||||
+ aarch64*)
|
||||
+ $2="aarch64"
|
||||
+ ;;
|
||||
alpha*)
|
||||
$2="alpha"
|
||||
;;
|
||||
Index: ghc-7.8.3/compiler/nativeGen/AsmCodeGen.lhs
|
||||
===================================================================
|
||||
--- ghc-7.8.3.orig/compiler/nativeGen/AsmCodeGen.lhs 2014-07-10 10:16:42.533187516 +0200
|
||||
+++ ghc-7.8.3/compiler/nativeGen/AsmCodeGen.lhs 2014-07-10 10:16:42.529187516 +0200
|
||||
@@ -166,6 +166,7 @@
|
||||
ArchPPC -> nCG' (ppcNcgImpl dflags)
|
||||
ArchSPARC -> nCG' (sparcNcgImpl dflags)
|
||||
ArchARM {} -> panic "nativeCodeGen: No NCG for ARM"
|
||||
+ ArchARM64 -> panic "nativeCodeGen: No NCG for ARM64"
|
||||
ArchPPC_64 -> panic "nativeCodeGen: No NCG for PPC 64"
|
||||
ArchAlpha -> panic "nativeCodeGen: No NCG for Alpha"
|
||||
ArchMipseb -> panic "nativeCodeGen: No NCG for mipseb"
|
||||
Index: ghc-7.8.3/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs
|
||||
===================================================================
|
||||
--- ghc-7.8.3.orig/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs 2014-07-10 10:16:42.533187516 +0200
|
||||
+++ ghc-7.8.3/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs 2014-07-10 10:16:42.529187516 +0200
|
||||
@@ -113,6 +113,7 @@
|
||||
ArchSPARC -> 14
|
||||
ArchPPC_64 -> panic "trivColorable ArchPPC_64"
|
||||
ArchARM _ _ _ -> panic "trivColorable ArchARM"
|
||||
+ ArchARM64 -> panic "trivColorable ArchARM64"
|
||||
ArchAlpha -> panic "trivColorable ArchAlpha"
|
||||
ArchMipseb -> panic "trivColorable ArchMipseb"
|
||||
ArchMipsel -> panic "trivColorable ArchMipsel"
|
||||
@@ -137,6 +138,7 @@
|
||||
ArchSPARC -> 22
|
||||
ArchPPC_64 -> panic "trivColorable ArchPPC_64"
|
||||
ArchARM _ _ _ -> panic "trivColorable ArchARM"
|
||||
+ ArchARM64 -> panic "trivColorable ArchARM64"
|
||||
ArchAlpha -> panic "trivColorable ArchAlpha"
|
||||
ArchMipseb -> panic "trivColorable ArchMipseb"
|
||||
ArchMipsel -> panic "trivColorable ArchMipsel"
|
||||
@@ -161,6 +163,7 @@
|
||||
ArchSPARC -> 11
|
||||
ArchPPC_64 -> panic "trivColorable ArchPPC_64"
|
||||
ArchARM _ _ _ -> panic "trivColorable ArchARM"
|
||||
+ ArchARM64 -> panic "trivColorable ArchARM64"
|
||||
ArchAlpha -> panic "trivColorable ArchAlpha"
|
||||
ArchMipseb -> panic "trivColorable ArchMipseb"
|
||||
ArchMipsel -> panic "trivColorable ArchMipsel"
|
||||
@@ -185,6 +188,7 @@
|
||||
ArchSPARC -> 0
|
||||
ArchPPC_64 -> panic "trivColorable ArchPPC_64"
|
||||
ArchARM _ _ _ -> panic "trivColorable ArchARM"
|
||||
+ ArchARM64 -> panic "trivColorable ArchARM64"
|
||||
ArchAlpha -> panic "trivColorable ArchAlpha"
|
||||
ArchMipseb -> panic "trivColorable ArchMipseb"
|
||||
ArchMipsel -> panic "trivColorable ArchMipsel"
|
||||
Index: ghc-7.8.3/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs
|
||||
===================================================================
|
||||
--- ghc-7.8.3.orig/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs 2014-07-10 10:16:42.533187516 +0200
|
||||
+++ ghc-7.8.3/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs 2014-07-10 10:16:42.529187516 +0200
|
||||
@@ -74,6 +74,7 @@
|
||||
ArchPPC -> PPC.Instr.maxSpillSlots dflags
|
||||
ArchSPARC -> SPARC.Instr.maxSpillSlots dflags
|
||||
ArchARM _ _ _ -> panic "maxSpillSlots ArchARM"
|
||||
+ ArchARM64 -> panic "maxSpillSlots ArchARM64"
|
||||
ArchPPC_64 -> panic "maxSpillSlots ArchPPC_64"
|
||||
ArchAlpha -> panic "maxSpillSlots ArchAlpha"
|
||||
ArchMipseb -> panic "maxSpillSlots ArchMipseb"
|
||||
Index: ghc-7.8.4/compiler/nativeGen/RegAlloc/Linear/Main.hs
|
||||
===================================================================
|
||||
--- ghc-7.8.4/compiler/nativeGen/RegAlloc/Linear/Main.hs.orig 2015-02-07 18:19:27.364827776 +0100
|
||||
+++ ghc-7.8.4/compiler/nativeGen/RegAlloc/Linear/Main.hs 2015-02-07 18:20:46.813771354 +0100
|
||||
@@ -207,6 +207,7 @@
|
||||
ArchSPARC -> linearRegAlloc' dflags (frInitFreeRegs platform :: SPARC.FreeRegs) entry_ids block_live sccs
|
||||
ArchPPC -> linearRegAlloc' dflags (frInitFreeRegs platform :: PPC.FreeRegs) entry_ids block_live sccs
|
||||
ArchARM _ _ _ -> panic "linearRegAlloc ArchARM"
|
||||
+ ArchARM64 -> panic "linearRegAlloc ArchARM64"
|
||||
ArchPPC_64 -> panic "linearRegAlloc ArchPPC_64"
|
||||
ArchAlpha -> panic "linearRegAlloc ArchAlpha"
|
||||
ArchMipseb -> panic "linearRegAlloc ArchMipseb"
|
||||
Index: ghc-7.8.3/compiler/nativeGen/TargetReg.hs
|
||||
===================================================================
|
||||
--- ghc-7.8.3.orig/compiler/nativeGen/TargetReg.hs 2014-07-10 10:16:42.533187516 +0200
|
||||
+++ ghc-7.8.3/compiler/nativeGen/TargetReg.hs 2014-07-10 10:16:42.529187516 +0200
|
||||
@@ -54,6 +54,7 @@
|
||||
ArchSPARC -> SPARC.virtualRegSqueeze
|
||||
ArchPPC_64 -> panic "targetVirtualRegSqueeze ArchPPC_64"
|
||||
ArchARM _ _ _ -> panic "targetVirtualRegSqueeze ArchARM"
|
||||
+ ArchARM64 -> panic "targetVirtualRegSqueeze ArchARM64"
|
||||
ArchAlpha -> panic "targetVirtualRegSqueeze ArchAlpha"
|
||||
ArchMipseb -> panic "targetVirtualRegSqueeze ArchMipseb"
|
||||
ArchMipsel -> panic "targetVirtualRegSqueeze ArchMipsel"
|
||||
@@ -70,6 +71,7 @@
|
||||
ArchSPARC -> SPARC.realRegSqueeze
|
||||
ArchPPC_64 -> panic "targetRealRegSqueeze ArchPPC_64"
|
||||
ArchARM _ _ _ -> panic "targetRealRegSqueeze ArchARM"
|
||||
+ ArchARM64 -> panic "targetRealRegSqueeze ArchARM64"
|
||||
ArchAlpha -> panic "targetRealRegSqueeze ArchAlpha"
|
||||
ArchMipseb -> panic "targetRealRegSqueeze ArchMipseb"
|
||||
ArchMipsel -> panic "targetRealRegSqueeze ArchMipsel"
|
||||
@@ -85,6 +87,7 @@
|
||||
ArchSPARC -> SPARC.classOfRealReg
|
||||
ArchPPC_64 -> panic "targetClassOfRealReg ArchPPC_64"
|
||||
ArchARM _ _ _ -> panic "targetClassOfRealReg ArchARM"
|
||||
+ ArchARM64 -> panic "targetClassOfRealReg ArchARM64"
|
||||
ArchAlpha -> panic "targetClassOfRealReg ArchAlpha"
|
||||
ArchMipseb -> panic "targetClassOfRealReg ArchMipseb"
|
||||
ArchMipsel -> panic "targetClassOfRealReg ArchMipsel"
|
||||
@@ -100,6 +103,7 @@
|
||||
ArchSPARC -> SPARC.mkVirtualReg
|
||||
ArchPPC_64 -> panic "targetMkVirtualReg ArchPPC_64"
|
||||
ArchARM _ _ _ -> panic "targetMkVirtualReg ArchARM"
|
||||
+ ArchARM64 -> panic "targetMkVirtualReg ArchARM64"
|
||||
ArchAlpha -> panic "targetMkVirtualReg ArchAlpha"
|
||||
ArchMipseb -> panic "targetMkVirtualReg ArchMipseb"
|
||||
ArchMipsel -> panic "targetMkVirtualReg ArchMipsel"
|
||||
@@ -115,6 +119,7 @@
|
||||
ArchSPARC -> SPARC.regDotColor
|
||||
ArchPPC_64 -> panic "targetRegDotColor ArchPPC_64"
|
||||
ArchARM _ _ _ -> panic "targetRegDotColor ArchARM"
|
||||
+ ArchARM64 -> panic "targetRegDotColor ArchARM64"
|
||||
ArchAlpha -> panic "targetRegDotColor ArchAlpha"
|
||||
ArchMipseb -> panic "targetRegDotColor ArchMipseb"
|
||||
ArchMipsel -> panic "targetRegDotColor ArchMipsel"
|
||||
Index: ghc-7.8.3/compiler/utils/Platform.hs
|
||||
===================================================================
|
||||
--- ghc-7.8.3.orig/compiler/utils/Platform.hs 2014-07-10 10:16:42.533187516 +0200
|
||||
+++ ghc-7.8.3/compiler/utils/Platform.hs 2014-07-10 10:16:42.529187516 +0200
|
||||
@@ -52,6 +52,7 @@
|
||||
, armISAExt :: [ArmISAExt]
|
||||
, armABI :: ArmABI
|
||||
}
|
||||
+ | ArchARM64
|
||||
| ArchAlpha
|
||||
| ArchMipseb
|
||||
| ArchMipsel
|
||||
Index: ghc-7.8.3/includes/stg/HaskellMachRegs.h
|
||||
===================================================================
|
||||
--- ghc-7.8.3.orig/includes/stg/HaskellMachRegs.h 2014-07-10 10:16:42.533187516 +0200
|
||||
+++ ghc-7.8.3/includes/stg/HaskellMachRegs.h 2014-07-10 10:16:42.533187516 +0200
|
||||
@@ -38,6 +38,7 @@
|
||||
#define MACHREGS_powerpc (powerpc_TARGET_ARCH || powerpc64_TARGET_ARCH || rs6000_TARGET_ARCH)
|
||||
#define MACHREGS_sparc sparc_TARGET_ARCH
|
||||
#define MACHREGS_arm arm_TARGET_ARCH
|
||||
+#define MACHREGS_aarch64 aarch64_TARGET_ARCH
|
||||
#define MACHREGS_darwin darwin_TARGET_OS
|
||||
|
||||
#endif
|
||||
Index: ghc-7.8.3/includes/stg/MachRegs.h
|
||||
===================================================================
|
||||
--- ghc-7.8.3.orig/includes/stg/MachRegs.h 2014-07-10 10:16:42.533187516 +0200
|
||||
+++ ghc-7.8.3/includes/stg/MachRegs.h 2014-07-10 10:16:42.533187516 +0200
|
||||
@@ -1,6 +1,6 @@
|
||||
/* -----------------------------------------------------------------------------
|
||||
*
|
||||
- * (c) The GHC Team, 1998-2011
|
||||
+ * (c) The GHC Team, 1998-2014
|
||||
*
|
||||
* Registers used in STG code. Might or might not correspond to
|
||||
* actual machine registers.
|
||||
@@ -531,6 +531,61 @@
|
||||
#define REG_D2 d11
|
||||
#endif
|
||||
|
||||
+/* -----------------------------------------------------------------------------
|
||||
+ The ARMv8/AArch64 ABI register mapping
|
||||
+
|
||||
+ The AArch64 provides 31 64-bit general purpose registers
|
||||
+ and 32 128-bit SIMD/floating point registers.
|
||||
+
|
||||
+ General purpose registers (see Chapter 5.1.1 in ARM IHI 0055B)
|
||||
+
|
||||
+ Register | Special | Role in the procedure call standard
|
||||
+ ---------+---------+------------------------------------
|
||||
+ SP | | The Stack Pointer
|
||||
+ r30 | LR | The Link Register
|
||||
+ r29 | FP | The Frame Pointer
|
||||
+ r19-r28 | | Callee-saved registers
|
||||
+ r18 | | The Platform Register, if needed;
|
||||
+ | | or temporary register
|
||||
+ r17 | IP1 | The second intra-procedure-call temporary register
|
||||
+ r16 | IP0 | The first intra-procedure-call scratch register
|
||||
+ r9-r15 | | Temporary registers
|
||||
+ r8 | | Indirect result location register
|
||||
+ r0-r7 | | Parameter/result registers
|
||||
+
|
||||
+
|
||||
+ FPU/SIMD registers
|
||||
+
|
||||
+ s/d/q/v0-v7 Argument / result/ scratch registers
|
||||
+ s/d/q/v8-v15 callee-saved registers (must be preserved across subrutine calls,
|
||||
+ but only bottom 64-bit value needs to be preserved)
|
||||
+ s/d/q/v16-v31 temporary registers
|
||||
+
|
||||
+ ----------------------------------------------------------------------------- */
|
||||
+
|
||||
+#elif MACHREGS_aarch64
|
||||
+
|
||||
+#define REG(x) __asm__(#x)
|
||||
+
|
||||
+#define REG_Base r19
|
||||
+#define REG_Sp r20
|
||||
+#define REG_Hp r21
|
||||
+#define REG_R1 r22
|
||||
+#define REG_R2 r23
|
||||
+#define REG_R3 r24
|
||||
+#define REG_R4 r25
|
||||
+#define REG_R5 r26
|
||||
+#define REG_R6 r27
|
||||
+#define REG_SpLim r28
|
||||
+
|
||||
+#define REG_F1 s8
|
||||
+#define REG_F2 s9
|
||||
+#define REG_F3 s10
|
||||
+#define REG_F4 s11
|
||||
+
|
||||
+#define REG_D1 d12
|
||||
+#define REG_D2 d13
|
||||
+
|
||||
#else
|
||||
|
||||
#error Cannot find platform to give register info for
|
||||
Index: ghc-7.8.3/rts/StgCRun.c
|
||||
===================================================================
|
||||
--- ghc-7.8.3.orig/rts/StgCRun.c 2014-07-10 10:16:42.533187516 +0200
|
||||
+++ ghc-7.8.3/rts/StgCRun.c 2014-07-10 10:16:42.533187516 +0200
|
||||
@@ -748,4 +748,70 @@
|
||||
}
|
||||
#endif
|
||||
|
||||
+#ifdef aarch64_HOST_ARCH
|
||||
+
|
||||
+StgRegTable *
|
||||
+StgRun(StgFunPtr f, StgRegTable *basereg) {
|
||||
+ StgRegTable * r;
|
||||
+ __asm__ volatile (
|
||||
+ /*
|
||||
+ * save callee-saves registers on behalf of the STG code.
|
||||
+ */
|
||||
+ "stp x19, x20, [sp, #-16]!\n\t"
|
||||
+ "stp x21, x22, [sp, #-16]!\n\t"
|
||||
+ "stp x23, x24, [sp, #-16]!\n\t"
|
||||
+ "stp x25, x26, [sp, #-16]!\n\t"
|
||||
+ "stp x27, x28, [sp, #-16]!\n\t"
|
||||
+ "stp ip0, ip1, [sp, #-16]!\n\t"
|
||||
+ "str lr, [sp, #-8]!\n\t"
|
||||
+
|
||||
+ /*
|
||||
+ * allocate some space for Stg machine's temporary storage.
|
||||
+ * Note: RESERVER_C_STACK_BYTES has to be a round number here or
|
||||
+ * the assembler can't assemble it.
|
||||
+ */
|
||||
+ "str lr, [sp, %3]"
|
||||
+ /* "sub sp, sp, %3\n\t" */
|
||||
+ /*
|
||||
+ * Set BaseReg
|
||||
+ */
|
||||
+ "mov x19, %2\n\t"
|
||||
+ /*
|
||||
+ * Jump to function argument.
|
||||
+ */
|
||||
+ "bx %1\n\t"
|
||||
+
|
||||
+ ".globl " STG_RETURN "\n\t"
|
||||
+ ".type " STG_RETURN ", %%function\n"
|
||||
+ STG_RETURN ":\n\t"
|
||||
+ /*
|
||||
+ * Free the space we allocated
|
||||
+ */
|
||||
+ "ldr lr, [sp], %3\n\t"
|
||||
+ /* "add sp, sp, %3\n\t" */
|
||||
+ /*
|
||||
+ * Return the new register table, taking it from Stg's R1 (ARM64's R22).
|
||||
+ */
|
||||
+ "mov %0, x22\n\t"
|
||||
+ /*
|
||||
+ * restore callee-saves registers.
|
||||
+ */
|
||||
+ "ldr lr, [sp], #8\n\t"
|
||||
+ "ldp ip0, ip1, [sp], #16\n\t"
|
||||
+ "ldp x27, x28, [sp], #16\n\t"
|
||||
+ "ldp x25, x26, [sp], #16\n\t"
|
||||
+ "ldp x23, x24, [sp], #16\n\t"
|
||||
+ "ldp x21, x22, [sp], #16\n\t"
|
||||
+ "ldp x19, x20, [sp], #16\n\t"
|
||||
+
|
||||
+ : "=r" (r)
|
||||
+ : "r" (f), "r" (basereg), "i" (RESERVED_C_STACK_BYTES)
|
||||
+ : "%x19", "%x20", "%x21", "%x22", "%x23", "%x24", "%x25", "%x26", "%x27", "%x28",
|
||||
+ "%ip0", "%ip1", "%lr"
|
||||
+ );
|
||||
+ return r;
|
||||
+}
|
||||
+
|
||||
+#endif
|
||||
+
|
||||
#endif /* !USE_MINIINTERPRETER */
|
@ -1,34 +0,0 @@
|
||||
From 44cee4852282f63393d532aad59c5cd865ff3ed6 Mon Sep 17 00:00:00 2001
|
||||
From: Erik de Castro Lopo <erikd@mega-nerd.com>
|
||||
Date: Wed, 1 Apr 2015 04:46:01 +0000
|
||||
Subject: [PATCH] mk/config.mk.in : Enable SMP and GHCi support for Aarch64.
|
||||
|
||||
---
|
||||
mk/config.mk.in | 4 ++--
|
||||
1 file changed, 2 insertions(+), 2 deletions(-)
|
||||
|
||||
diff --git a/mk/config.mk.in b/mk/config.mk.in
|
||||
index f4cb52b..d6831c9 100644
|
||||
--- a/mk/config.mk.in
|
||||
+++ b/mk/config.mk.in
|
||||
@@ -172,7 +172,7 @@ HaveLibDL = @HaveLibDL@
|
||||
|
||||
# ArchSupportsSMP should be set iff there is support for that arch in
|
||||
# includes/stg/SMP.h
|
||||
-ArchSupportsSMP=$(strip $(patsubst $(TargetArch_CPP), YES, $(findstring $(TargetArch_CPP), i386 x86_64 sparc powerpc arm)))
|
||||
+ArchSupportsSMP=$(strip $(patsubst $(TargetArch_CPP), YES, $(findstring $(TargetArch_CPP), i386 x86_64 sparc powerpc arm aarch64)))
|
||||
|
||||
GhcWithSMP := $(strip $(if $(filter YESNO, $(ArchSupportsSMP)$(GhcUnregisterised)),YES,NO))
|
||||
|
||||
@@ -180,7 +180,7 @@ GhcWithSMP := $(strip $(if $(filter YESNO, $(ArchSupportsSMP)$(GhcUnregisterised
|
||||
# has support for this OS/ARCH combination.
|
||||
|
||||
OsSupportsGHCi=$(strip $(patsubst $(TargetOS_CPP), YES, $(findstring $(TargetOS_CPP), mingw32 cygwin32 linux solaris2 freebsd dragonfly netbsd openbsd darwin kfreebsdgnu)))
|
||||
-ArchSupportsGHCi=$(strip $(patsubst $(TargetArch_CPP), YES, $(findstring $(TargetArch_CPP), i386 x86_64 powerpc sparc sparc64 arm)))
|
||||
+ArchSupportsGHCi=$(strip $(patsubst $(TargetArch_CPP), YES, $(findstring $(TargetArch_CPP), i386 x86_64 powerpc sparc sparc64 arm aarch64)))
|
||||
|
||||
ifeq "$(OsSupportsGHCi)$(ArchSupportsGHCi)" "YESYES"
|
||||
GhcWithInterpreter=YES
|
||||
--
|
||||
2.1.4
|
||||
|
@ -1,7 +1,6 @@
|
||||
--- ghc-7.6.3/libraries/gen_contents_index~ 2013-04-19 06:22:46.000000000 +0900
|
||||
+++ ghc-7.6.3/libraries/gen_contents_index 2013-04-22 12:07:48.922152864 +0900
|
||||
@@ -60,7 +60,7 @@
|
||||
done
|
||||
@@ -60,6 +60,6 @@
|
||||
done
|
||||
else
|
||||
- HADDOCK=../../../../../bin/haddock
|
||||
|
@ -1,26 +0,0 @@
|
||||
From 7d738547049e686be4d90a19dcb9520418d5f72d Mon Sep 17 00:00:00 2001
|
||||
From: Jens Petersen <petersen@redhat.com>
|
||||
Date: Mon, 9 Jun 2014 15:48:41 +0900
|
||||
Subject: [PATCH] define _DEFAULT_SOURCE in Stg.h to avoid warnings from glibc
|
||||
2.20 (#9185)
|
||||
|
||||
---
|
||||
includes/Stg.h | 2 ++
|
||||
1 file changed, 2 insertions(+)
|
||||
|
||||
diff --git a/includes/Stg.h b/includes/Stg.h
|
||||
index 1707c9b..fbcf643 100644
|
||||
--- a/includes/Stg.h
|
||||
+++ b/includes/Stg.h
|
||||
@@ -47,6 +47,8 @@
|
||||
// We need _BSD_SOURCE so that math.h defines things like gamma
|
||||
// on Linux
|
||||
# define _BSD_SOURCE
|
||||
+// glibc 2.20 deprecates _BSD_SOURCE in favour of _DEFAULT_SOURCE
|
||||
+# define _DEFAULT_SOURCE
|
||||
#endif
|
||||
|
||||
#if IN_STG_CODE == 0 || defined(llvm_CC_FLAVOR)
|
||||
--
|
||||
1.9.3
|
||||
|
@ -1,6 +0,0 @@
|
||||
diff -u ghc-7.4.1/ghc/ghc.wrapper\~ ghc-7.4.1/ghc/ghc.wrapper
|
||||
--- ghc-7.4.1/ghc/ghc.wrapper~ 2012-02-02 03:10:32.000000000 +0900
|
||||
+++ ghc-7.4.1/ghc/ghc.wrapper 2012-05-02 19:39:05.503872527 +0900
|
||||
@@ -1 +1 @@
|
||||
-exec "$executablename" -B"$topdir" ${1+"$@"}
|
||||
+exec "$executablename" -B"$topdir" -optc-I$(pkg-config --variable=includedir libffi) ${1+"$@"}
|
196
ghc.spec
196
ghc.spec
@ -1,9 +1,5 @@
|
||||
# for F22 and F23 intel ghc-7.8.4, force high "make -j" to preserve ABI hashes
|
||||
# - set < 16 at your own risk
|
||||
%global build_minimum_smp 16
|
||||
|
||||
# To bootstrap build a new version of ghc, uncomment the following:
|
||||
#%%global ghc_bootstrapping 1
|
||||
%global ghc_bootstrapping 1
|
||||
|
||||
%if %{defined ghc_bootstrapping}
|
||||
%global without_testsuite 1
|
||||
@ -29,68 +25,63 @@
|
||||
Name: ghc
|
||||
# part of haskell-platform
|
||||
# ghc must be rebuilt after a version bump to avoid ABI change problems
|
||||
Version: 7.8.4
|
||||
Version: 7.10.3
|
||||
# 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
|
||||
# xhtml moved from haskell-platform to ghc-7.8.3
|
||||
Release: 48%{?dist}
|
||||
# xhtml has not had a new release for some years
|
||||
Release: 49%{?dist}
|
||||
Summary: Glasgow Haskell Compiler
|
||||
|
||||
License: %BSDHaskellReport
|
||||
URL: http://haskell.org/ghc/
|
||||
Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.xz
|
||||
Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}b-src.tar.xz
|
||||
%if %{undefined without_testsuite}
|
||||
Source2: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-testsuite.tar.xz
|
||||
Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}b-testsuite.tar.xz
|
||||
%endif
|
||||
Source3: ghc-doc-index.cron
|
||||
Source4: ghc-doc-index
|
||||
# absolute haddock path (was for html/libraries -> libraries)
|
||||
Patch1: ghc-gen_contents_index-haddock-path.patch
|
||||
# add libffi include dir to ghc wrapper for archs using gcc/llc
|
||||
#Patch10: ghc-wrapper-libffi-include.patch
|
||||
# warning "_BSD_SOURCE and _SVID_SOURCE are deprecated, use _DEFAULT_SOURCE"
|
||||
Patch20: ghc-glibc-2.20_BSD_SOURCE.patch
|
||||
# Debian patch
|
||||
Patch21: ghc-arm64.patch
|
||||
Patch22: ghc-armv7-VFPv3D16--NEON.patch
|
||||
Patch23: ghc-7.8.3-Cabal-install-PATH-warning.patch
|
||||
Patch24: ghc-7.8-arm-use-ld-gold.patch
|
||||
Patch25: ghc-7.8-arm7_saner-linker-opt-handling-9873.patch
|
||||
Patch26: ghc-config.mk.in-Enable-SMP-and-GHCi-support-for-Aarch64.patch
|
||||
Patch24: ghc-Debian-buildpath-abi-stability.patch
|
||||
Patch26: ghc-Debian-no-missing-haddock-file-warning.patch
|
||||
Patch27: ghc-Debian-reproducible-tmp-names.patch
|
||||
|
||||
%global Cabal_ver 1.18.1.5
|
||||
%global array_ver 0.5.0.0
|
||||
%global base_ver 4.7.0.2
|
||||
# 7.10.3 needs llvm-3.5
|
||||
%global llvm_major 3.5
|
||||
|
||||
# use "./libraries-versions.sh" to check versions
|
||||
%global Cabal_ver 1.22.5.0
|
||||
%global array_ver 0.5.1.0
|
||||
%global base_ver 4.8.2.0
|
||||
%global bin_package_db_ver 0.0.0.0
|
||||
%global binary_ver 0.7.1.0
|
||||
%global bytestring_ver 0.10.4.0
|
||||
%global containers_ver 0.5.5.1
|
||||
%global deepseq_ver 1.3.0.2
|
||||
%global directory_ver 1.2.1.0
|
||||
%global filepath_ver 1.3.0.2
|
||||
%global ghc_prim_ver 0.3.1.0
|
||||
%global haskeline_ver 0.7.1.2
|
||||
%global haskell2010_ver 1.1.2.0
|
||||
%global haskell98_ver 2.0.0.3
|
||||
%global hoopl_ver 3.10.0.1
|
||||
%global hpc_ver 0.6.0.1
|
||||
%global integer_gmp_ver 0.5.1.0
|
||||
%global old_locale_ver 1.0.0.6
|
||||
%global old_time_ver 1.1.0.2
|
||||
%global pretty_ver 1.1.1.1
|
||||
%global process_ver 1.2.0.0
|
||||
%global template_haskell_ver 2.9.0.0
|
||||
%global terminfo_ver 0.4.0.0
|
||||
%global time_ver 1.4.2
|
||||
%global transformers_ver 0.3.0.0
|
||||
%global unix_ver 2.7.0.1
|
||||
%global binary_ver 0.7.5.0
|
||||
%global bytestring_ver 0.10.6.0
|
||||
%global containers_ver 0.5.6.2
|
||||
%global deepseq_ver 1.4.1.1
|
||||
%global directory_ver 1.2.2.0
|
||||
%global filepath_ver 1.4.0.0
|
||||
%global ghc_prim_ver 0.4.0.0
|
||||
%global haskeline_ver 0.7.2.1
|
||||
%global hoopl_ver 3.10.0.2
|
||||
%global hpc_ver 0.6.0.2
|
||||
%global integer_gmp_ver 1.0.0.0
|
||||
%global pretty_ver 1.1.2.0
|
||||
%global process_ver 1.2.3.0
|
||||
%global template_haskell_ver 2.10.0.0
|
||||
%global terminfo_ver 0.4.0.1
|
||||
%global time_ver 1.5.0.1
|
||||
%global transformers_ver 0.4.2.0
|
||||
%global unix_ver 2.7.1.0
|
||||
%global xhtml_ver 3000.2.1
|
||||
|
||||
|
||||
# fedora ghc has been bootstrapped on
|
||||
# %{ix86} x86_64 ppc ppc64 armv7hl s390 s390x ppc64le aarch64
|
||||
# %%{ix86} x86_64 ppc ppc64 armv7hl s390 s390x ppc64le aarch64
|
||||
# and retired arches: alpha sparcv9 armv5tel
|
||||
# see ghc_arches defined in /etc/rpm/macros.ghc-srpm by redhat-rpm-macros
|
||||
ExcludeArch: sparc64
|
||||
@ -104,16 +95,11 @@ Obsoletes: ghc-feldspar-language < 0.4, ghc-feldspar-language-devel < 0.4, ghc-f
|
||||
%if %{undefined ghc_bootstrapping}
|
||||
BuildRequires: ghc-compiler = %{version}
|
||||
%endif
|
||||
%if 0%{?fedora} >= 20 || 0%{?rhel} >= 7
|
||||
BuildRequires: ghc-rpm-macros-extra
|
||||
%else
|
||||
BuildRequires: ghc-rpm-macros
|
||||
%endif
|
||||
BuildRequires: ghc-binary-devel
|
||||
BuildRequires: ghc-bytestring-devel
|
||||
BuildRequires: ghc-containers-devel
|
||||
BuildRequires: ghc-directory-devel
|
||||
BuildRequires: ghc-haskell98-devel
|
||||
BuildRequires: ghc-pretty-devel
|
||||
BuildRequires: ghc-process-devel
|
||||
BuildRequires: gmp-devel
|
||||
@ -126,10 +112,10 @@ BuildRequires: libxslt, docbook-style-xsl
|
||||
BuildRequires: python
|
||||
%endif
|
||||
%ifarch armv7hl armv5tel
|
||||
BuildRequires: llvm34
|
||||
BuildRequires: llvm35
|
||||
%endif
|
||||
%ifarch armv7hl aarch64
|
||||
# patch22 and patch24
|
||||
%ifarch armv7hl
|
||||
# patch22
|
||||
BuildRequires: autoconf, automake
|
||||
%endif
|
||||
Requires: ghc-compiler = %{version}-%{release}
|
||||
@ -170,7 +156,7 @@ Requires(postun): chkconfig
|
||||
# added in f14
|
||||
Obsoletes: ghc-doc < 6.12.3-4
|
||||
%ifarch armv7hl armv5tel
|
||||
Requires: llvm34
|
||||
Requires: llvm35
|
||||
%endif
|
||||
|
||||
%description compiler
|
||||
@ -192,15 +178,15 @@ The package provides a cronjob for re-indexing installed library development
|
||||
documention.
|
||||
%endif
|
||||
|
||||
# ghclibdir also needs ghc_version_override for bootstrapping (ghc-deps.sh)
|
||||
# ghclibdir also needs ghc_version_override for bootstrapping
|
||||
%global ghc_version_override %{version}
|
||||
|
||||
# currently only F21+ ghc-rpm-macros has ghc.attr
|
||||
%if 0%{?fedora} < 21
|
||||
# EL7 rpm supports fileattrs ghc.attr
|
||||
%if 0%{?rhel} && 0%{?rhel} < 7
|
||||
# needs ghc_version_override for bootstrapping
|
||||
%global _use_internal_dependency_generator 0
|
||||
%global __find_provides %{_rpmconfigdir}/ghc-deps.sh --provides %{buildroot}%{ghclibdir}
|
||||
%global __find_requires %{_rpmconfigdir}/ghc-deps.sh --requires %{buildroot}%{ghclibdir}
|
||||
%global __find_provides /usr/lib/rpm/rpmdeps --provides
|
||||
%global __find_requires %{_rpmconfigdir}/ghc-deps.sh %{buildroot}%{ghclibdir}
|
||||
%endif
|
||||
|
||||
%global ghc_pkg_c_deps ghc-compiler = %{ghc_version_override}-%{release}
|
||||
@ -220,12 +206,8 @@ documention.
|
||||
%ghc_lib_subpackage -x ghc %{ghc_version_override}
|
||||
%undefine ghc_pkg_obsoletes
|
||||
%ghc_lib_subpackage haskeline %{haskeline_ver}
|
||||
%ghc_lib_subpackage -l HaskellReport haskell2010 %{haskell2010_ver}
|
||||
%ghc_lib_subpackage -l HaskellReport haskell98 %{haskell98_ver}
|
||||
%ghc_lib_subpackage hoopl %{hoopl_ver}
|
||||
%ghc_lib_subpackage hpc %{hpc_ver}
|
||||
%ghc_lib_subpackage -l %BSDHaskellReport old-locale %{old_locale_ver}
|
||||
%ghc_lib_subpackage -l %BSDHaskellReport old-time %{old_time_ver}
|
||||
%ghc_lib_subpackage pretty %{pretty_ver}
|
||||
%define ghc_pkg_obsoletes ghc-process-leksah-devel < 1.0.1.4-14
|
||||
%ghc_lib_subpackage -l %BSDHaskellReport process %{process_ver}
|
||||
@ -235,8 +217,10 @@ documention.
|
||||
%ghc_lib_subpackage time %{time_ver}
|
||||
%ghc_lib_subpackage transformers %{transformers_ver}
|
||||
%ghc_lib_subpackage unix %{unix_ver}
|
||||
%if %{undefined without_haddock}
|
||||
%ghc_lib_subpackage xhtml %{xhtml_ver}
|
||||
%endif
|
||||
%endif
|
||||
|
||||
%global version %{ghc_version_override}
|
||||
|
||||
@ -258,34 +242,22 @@ except the ghc library, which is installed by the toplevel ghc metapackage.
|
||||
|
||||
|
||||
%prep
|
||||
%setup -q -n %{name}-%{version} %{!?without_testsuite:-b2}
|
||||
%setup -q -n %{name}-%{version} %{!?without_testsuite:-b1}
|
||||
|
||||
# gen_contents_index: use absolute path for haddock
|
||||
%patch1 -p1 -b .orig
|
||||
|
||||
rm -r libffi-tarballs
|
||||
|
||||
%ifnarch %{ix86} x86_64
|
||||
#%%patch10 -p1 -b .10-ffi
|
||||
%endif
|
||||
|
||||
%patch20 -p1 -b .orig
|
||||
|
||||
%ifarch aarch64
|
||||
%patch21 -p1 -b .orig
|
||||
%patch26 -p1 -b .orig
|
||||
%endif
|
||||
|
||||
%ifarch armv7hl aarch64
|
||||
%patch24 -p1 -b .24~
|
||||
%endif
|
||||
|
||||
%ifarch armv7hl
|
||||
%patch22 -p1 -b .orig
|
||||
%patch25 -p1 -b .25~
|
||||
%endif
|
||||
|
||||
%patch23 -p1 -b .orig
|
||||
%patch24 -p1 -b .orig
|
||||
|
||||
%patch26 -p1 -b .orig
|
||||
%patch27 -p1 -b .orig
|
||||
|
||||
%global gen_contents_index gen_contents_index.orig
|
||||
%if %{undefined without_haddock}
|
||||
@ -295,6 +267,9 @@ if [ ! -f "libraries/%{gen_contents_index}" ]; then
|
||||
fi
|
||||
%endif
|
||||
|
||||
mv libraries/integer-gmp{,.old}
|
||||
ln -s integer-gmp2 libraries/integer-gmp
|
||||
|
||||
|
||||
%build
|
||||
# http://hackage.haskell.org/trac/ghc/wiki/Platforms
|
||||
@ -327,12 +302,7 @@ BUILD_DOCBOOK_HTML = NO
|
||||
#EXTRA_HC_OPTS=-debug
|
||||
EOF
|
||||
|
||||
%ifarch aarch64
|
||||
for i in $(find . -name config.guess -o -name config.sub) ; do
|
||||
[ -f /usr/lib/rpm/redhat/$(basename $i) ] && %{__rm} -f $i && %{__cp} -fv /usr/lib/rpm/redhat/$(basename $i) $i
|
||||
done
|
||||
%endif
|
||||
%ifarch aarch64 armv7hl
|
||||
%ifarch armv7hl
|
||||
autoreconf
|
||||
%endif
|
||||
# x86_64: /usr/bin/ld: utils/ghc-pwd/dist-boot/Main.o: relocation R_X86_64_32S against `.text' can not be used when making a shared object; recompile with -fPIC
|
||||
@ -341,7 +311,7 @@ autoreconf
|
||||
%global _hardened_ldflags %{nil}
|
||||
%endif
|
||||
export CFLAGS="${CFLAGS:-%optflags}"
|
||||
export LDFLAGS="${LDFLAGS:-%__global_ldflags}"
|
||||
export LDFLAGS="${LDFLAGS:-%{?__global_ldflags}}"
|
||||
# * %%configure induces cross-build due to different target/host/build platform names
|
||||
# * --with-gcc=%{_bindir}/gcc is to avoid ccache hardcoding problem when bootstrapping
|
||||
./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \
|
||||
@ -349,45 +319,18 @@ export LDFLAGS="${LDFLAGS:-%__global_ldflags}"
|
||||
--datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \
|
||||
--libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \
|
||||
--sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \
|
||||
--with-gcc=%{_bindir}/gcc --with-system-libffi \
|
||||
--with-gcc=%{_bindir}/gcc \
|
||||
%if 0%{?fedora} || 0%{?rhel} > 6
|
||||
--with-system-libffi \
|
||||
%endif
|
||||
%ifarch armv7hl armv5tel
|
||||
--with-llc=%{_bindir}/llc-3.4 --with-opt=%{_bindir}/opt-3.4 \
|
||||
--with-llc=%{_bindir}/llc-%{llvm_major} --with-opt=%{_bindir}/opt-%{llvm_major} \
|
||||
%endif
|
||||
%{nil}
|
||||
|
||||
# avoid "ghc: hGetContents: invalid argument (invalid byte sequence)"
|
||||
export LANG=en_US.utf8
|
||||
|
||||
echo _smp_mflags is \'%{?_smp_mflags}\'
|
||||
# NB for future ghc versions maybe should hardcode max -j4 for all builds
|
||||
# (s390 seems ABI unstable under -j4)
|
||||
# Though apparently this does not affect 7.10
|
||||
MAKE_JOBS=$(echo %{?_smp_mflags} | sed -e "s/^-j//")
|
||||
%ifarch %{ix86} x86_64
|
||||
# hack to perserve the high "make -j" ghc ABI hashes for 7.8.4 koji/mock builds
|
||||
# (-j9 seems to be sufficient but not -j8)
|
||||
if [ "%{build_minimum_smp}" -le "8" ]; then
|
||||
echo "** NB: ghc-7.8.4 needs to be built with 'make -j9' or higher to preserve the -j16 ABI hashes for F22/F23 i686 and x86_64 **"
|
||||
fi
|
||||
if [ -z "$MAKE_JOBS" -o "0$MAKE_JOBS" -le "%{build_minimum_smp}" ]; then
|
||||
echo "Overriding 'make -j' SMP for Intel builds to preserve the ghc ABI hashes:"
|
||||
MAKE_JOBS="%{build_minimum_smp}"
|
||||
fi
|
||||
%else
|
||||
%ifarch s390
|
||||
# use 2 for s390
|
||||
if [ "0$MAKE_JOBS" -ne "2" ]; then
|
||||
MAKE_JOBS=2
|
||||
fi
|
||||
%else
|
||||
# keep < 9 for all other archs
|
||||
if [ "0$MAKE_JOBS" -gt "8" ]; then
|
||||
MAKE_JOBS=8
|
||||
fi
|
||||
%endif
|
||||
%endif
|
||||
|
||||
make ${MAKE_JOBS:+-j$MAKE_JOBS}
|
||||
make %{?_smp_mflags}
|
||||
|
||||
|
||||
%install
|
||||
@ -419,12 +362,18 @@ echo "%doc libraries/LICENSE.%1" >> ghc-%2.files
|
||||
%merge_filelist bin-package-db ghc
|
||||
|
||||
# add rts libs
|
||||
echo "%dir %{ghclibdir}/rts-1.0" >> ghc-base.files
|
||||
ls %{buildroot}%{ghclibdir}/rts-1.0/libHS*.so >> ghc-base.files
|
||||
echo "%dir %{ghclibdir}/rts" >> ghc-base.files
|
||||
ls %{buildroot}%{ghclibdir}/rts/libHS*.so >> ghc-base.files
|
||||
%if 0%{?rhel} && 0%{?rhel} < 7
|
||||
ls %{buildroot}%{ghclibdir}/rts/libffi.so.* >> ghc-base.files
|
||||
%endif
|
||||
|
||||
sed -i -e "s|^%{buildroot}||g" ghc-base.files
|
||||
|
||||
ls -d %{buildroot}%{ghclibdir}/rts-1.0/lib*.a %{buildroot}%{ghclibdir}/package.conf.d/builtin_*.conf %{buildroot}%{ghclibdir}/include >> ghc-base-devel.files
|
||||
ls -d %{buildroot}%{ghclibdir}/rts/lib*.a %{buildroot}%{ghclibdir}/package.conf.d/builtin_*.conf %{buildroot}%{ghclibdir}/include >> ghc-base-devel.files
|
||||
%if 0%{?rhel} && 0%{?rhel} < 7
|
||||
ls %{buildroot}%{ghclibdir}/rts/libffi.so >> ghc-base-devel.files
|
||||
%endif
|
||||
|
||||
sed -i -e "s|^%{buildroot}||g" ghc-base-devel.files
|
||||
|
||||
@ -536,7 +485,6 @@ fi
|
||||
%endif
|
||||
%{ghclibdir}/ghc-usage.txt
|
||||
%{ghclibdir}/ghci-usage.txt
|
||||
%{ghclibdir}/mkGmpDerivedConstants
|
||||
%dir %{ghclibdir}/package.conf.d
|
||||
%ghost %{ghclibdir}/package.conf.d/package.cache
|
||||
%{ghclibdir}/platformConstants
|
||||
@ -555,7 +503,7 @@ fi
|
||||
%{ghclibdir}/latex
|
||||
%if %{undefined without_manual}
|
||||
## needs pandoc
|
||||
#%{ghcdocbasedir}/Cabal
|
||||
#%%{ghcdocbasedir}/Cabal
|
||||
%{ghcdocbasedir}/haddock
|
||||
%{ghcdocbasedir}/users_guide
|
||||
%endif
|
||||
|
10
libraries-versions.sh
Executable file
10
libraries-versions.sh
Executable file
@ -0,0 +1,10 @@
|
||||
#!/bin/sh
|
||||
|
||||
if [ ! -d libraries ]; then
|
||||
echo Is CWD a ghc source tree?
|
||||
exit 1
|
||||
fi
|
||||
|
||||
cd libraries
|
||||
|
||||
grep -i ^version: Cabal/Cabal/Cabal.cabal */*.cabal | grep -v -e "\(Win32\|gmp.old\|gmp2\|integer-simple\|ghc-boot\)" | sed -e "s!/.*: \+!_ver !"
|
Loading…
Reference in New Issue
Block a user