From 46792007c994f0f37012de2a0280a63eedfc3a5e Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 23 Apr 2013 18:33:35 +0900 Subject: [PATCH] update to new stable major version 7.6.3 - bootstrap build - use new ghc-rpm-macros-extra - no longer filter type-level package from haddock index --- .gitignore | 2 + Cabal-fix-dynamic-exec-for-TH.patch | 33 - ...12.1-gen_contents_index-haddock-path.patch | 12 - ...rt-for-ARM-hard-float-ABI-fixes-5914.patch | 1274 ----------------- ghc-7.4-silence-gen_contents_index.patch | 11 - ghc-gen_contents_index-haddock-path.patch | 11 + ghc-gen_contents_index-type-level.patch | 12 - ghc-powerpc-linker-mmap.patch | 34 - ghc-powerpc-pthread.patch | 18 - ghc-use-system-libffi.patch | 46 +- ghc.spec | 149 +- sources | 4 +- 12 files changed, 105 insertions(+), 1501 deletions(-) delete mode 100644 Cabal-fix-dynamic-exec-for-TH.patch delete mode 100644 ghc-6.12.1-gen_contents_index-haddock-path.patch delete mode 100644 ghc-7.4-add-support-for-ARM-hard-float-ABI-fixes-5914.patch delete mode 100644 ghc-7.4-silence-gen_contents_index.patch create mode 100644 ghc-gen_contents_index-haddock-path.patch delete mode 100644 ghc-gen_contents_index-type-level.patch delete mode 100644 ghc-powerpc-linker-mmap.patch delete mode 100644 ghc-powerpc-pthread.patch diff --git a/.gitignore b/.gitignore index 6f437bb..9da11de 100644 --- a/.gitignore +++ b/.gitignore @@ -9,3 +9,5 @@ testsuite-6.12.3.tar.bz2 /ghc-7.4.1-src.tar.bz2 /ghc-7.4.2-src.tar.bz2 /ghc-7.4.2-testsuite.tar.bz2 +/ghc-7.6.3-src.tar.bz2 +/ghc-7.6.3-testsuite.tar.bz2 diff --git a/Cabal-fix-dynamic-exec-for-TH.patch b/Cabal-fix-dynamic-exec-for-TH.patch deleted file mode 100644 index 5384ea7..0000000 --- a/Cabal-fix-dynamic-exec-for-TH.patch +++ /dev/null @@ -1,33 +0,0 @@ -diff -u ghc-7.2.0.20110728/libraries/Cabal/cabal/Distribution/Simple/GHC.hs.orig ghc-7.2.0.20110728/libraries/Cabal/cabal/Distribution/Simple/GHC.hs ---- ghc-7.2.0.20110728/libraries/Cabal/Cabal/Distribution/Simple/GHC.hs.orig 2011-07-29 02:12:09.000000000 +0900 -+++ ghc-7.2.0.20110728/libraries/Cabal/Cabal/Distribution/Simple/GHC.hs 2011-08-05 18:08:05.192042529 +0900 -@@ -778,7 +778,10 @@ - ++ ["-L"++libDir | libDir <- extraLibDirs exeBi] - ++ concat [["-framework", f] | f <- PD.frameworks exeBi] - ++ if dynExe -- then ["-dynamic"] -+ then ["-dynamic", -+ "-hisuf", "dyn_hi", -+ "-osuf", "dyn_o" -+ ] - else [] - ++ if profExe - then ["-prof", -@@ -787,13 +790,14 @@ - ] ++ ghcProfOptions exeBi - else [] - -- -- For building exe's for profiling that use TH we actually -+ -- For building exe's for profiling or dynamic that use TH we actually - -- have to build twice, once without profiling and the again - -- with profiling. This is because the code that TH needs to - -- run at compile time needs to be the vanilla ABI so it can - -- be loaded up and run by the compiler. -- when (withProfExe lbi && EnableExtension TemplateHaskell `elem` allExtensions exeBi) -- (runGhcProg (binArgs False (withDynExe lbi) False)) -+ when ((withProfExe lbi || withDynExe lbi) && -+ EnableExtension TemplateHaskell `elem` allExtensions exeBi) -+ (runGhcProg (binArgs False False False)) - - runGhcProg (binArgs True (withDynExe lbi) (withProfExe lbi)) - diff --git a/ghc-6.12.1-gen_contents_index-haddock-path.patch b/ghc-6.12.1-gen_contents_index-haddock-path.patch deleted file mode 100644 index d1034eb..0000000 --- a/ghc-6.12.1-gen_contents_index-haddock-path.patch +++ /dev/null @@ -1,12 +0,0 @@ -diff -u ghc-6.12.1/libraries/gen_contents_index\~ ghc-6.12.1/libraries/gen_contents_index ---- ghc-6.12.1/libraries/gen_contents_index~ 2009-12-11 04:11:33.000000000 +1000 -+++ ghc-6.12.1/libraries/gen_contents_index 2009-12-12 21:08:02.000000000 +1000 -@@ -20,7 +20,7 @@ - done - ;; - *) -- HADDOCK=../../../../../bin/haddock -+ HADDOCK=/usr/bin/haddock - # We don't want the GHC API to swamp the index - HADDOCK_FILES=`ls -1 */*.haddock | grep -v '/ghc\.haddock' | sort` - for HADDOCK_FILE in $HADDOCK_FILES diff --git a/ghc-7.4-add-support-for-ARM-hard-float-ABI-fixes-5914.patch b/ghc-7.4-add-support-for-ARM-hard-float-ABI-fixes-5914.patch deleted file mode 100644 index a9b897b..0000000 --- a/ghc-7.4-add-support-for-ARM-hard-float-ABI-fixes-5914.patch +++ /dev/null @@ -1,1274 +0,0 @@ -From 83195ff5ba73779514e3d06b1457d45f849c7fc2 Mon Sep 17 00:00:00 2001 -From: Karel Gardas -Date: Wed, 25 Apr 2012 09:04:50 +0200 -Subject: [PATCH] add support for ARM hard-float ABI (fixes #5914) - -This patch enhances Platform's ArchARM to include ARM ABI value. It also -tweaks configure machinery to detect hard-float ABI and to set it wherever -needed. Finally when hard-float ABI is in use, pass appropriate compiler -option to the LLVM's llc. Fixes #5914. ---- - aclocal.m4 | 2 +- - compiler/main/DriverPipeline.hs | 16 +- - compiler/nativeGen/AsmCodeGen.lhs | 2 +- - compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs | 56 ++-- - compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs | 14 +- - compiler/nativeGen/RegAlloc/Linear/Main.hs | 14 +- - compiler/nativeGen/TargetReg.hs | 70 ++-- - compiler/utils/Platform.hs | 12 +- - config.guess | 482 ++++++++++---------- - configure.ac | 14 + - 10 files changed, 345 insertions(+), 337 deletions(-) - -diff --git a/aclocal.m4 b/aclocal.m4 -index 5652185..c196bdf 100644 ---- a/aclocal.m4 -+++ b/aclocal.m4 -@@ -171,7 +171,7 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS], - ;; - arm) - GET_ARM_ISA() -- test -z "[$]2" || eval "[$]2=\"ArchARM {armISA = \$ARM_ISA, armISAExt = \$ARM_ISA_EXT}\"" -+ test -z "[$]2" || eval "[$]2=\"ArchARM {armISA = \$ARM_ISA, armISAExt = \$ARM_ISA_EXT, armABI = \$ARM_ABI}\"" - ;; - alpha|mips|mipseb|mipsel|hppa|hppa1_1|ia64|m68k|rs6000|s390|s390x|sparc64|vax) - test -z "[$]2" || eval "[$]2=ArchUnknown" -diff -u ghc-7.4.1.20120508/compiler/main/DriverPipeline.hs.arm ghc-7.4.1.20120508/compiler/main/DriverPipeline.hs ---- ghc-7.4.1.20120508/compiler/main/DriverPipeline.hs.arm 2012-05-15 02:10:41.000000000 +0900 -+++ ghc-7.4.1.20120508/compiler/main/DriverPipeline.hs 2012-05-18 12:19:22.779955285 +0900 -@@ -1366,7 +1366,8 @@ - SysTools.FileOption "" input_fn, - SysTools.Option "-o", SysTools.FileOption "" output_fn] - ++ map SysTools.Option lc_opts -- ++ map SysTools.Option fpOpts) -+ ++ map SysTools.Option fpOpts -+ ++ map SysTools.Option abiOpts) - - return (next_phase, output_fn) - where -@@ -1378,12 +1379,19 @@ - -- while compiling GHC source code. It's probably due to fact that it - -- does not enable VFP by default. Let's do this manually here - fpOpts = case platformArch (targetPlatform dflags) of -- ArchARM ARMv7 ext -> if (elem VFPv3 ext) -+ ArchARM ARMv7 ext _ -> if (elem VFPv3 ext) - then ["-mattr=+v7,+vfp3"] - else if (elem VFPv3D16 ext) - then ["-mattr=+v7,+vfp3,+d16"] - else [] - _ -> [] -+ -- On Ubuntu/Debian with ARM hard float ABI, LLVM's llc still -+ -- compiles into soft-float ABI. We need to explicitly set abi -+ -- to hard -+ abiOpts = case platformArch (targetPlatform dflags) of -+ ArchARM ARMv7 _ HARD -> ["-float-abi=hard"] -+ ArchARM ARMv7 _ _ -> [] -+ _ -> [] - - ----------------------------------------------------------------------------- - -- LlvmMangle phase -@@ -1532,8 +1540,8 @@ - - elfSectionNote :: String - elfSectionNote = case platformArch (targetPlatform dflags) of -- ArchARM _ _ -> "%note" -- _ -> "@note" -+ ArchARM _ _ _ -> "%note" -+ _ -> "@note" - - -- The "link info" is a string representing the parameters of the - -- link. We save this information in the binary, and the next time we -diff --git a/compiler/nativeGen/AsmCodeGen.lhs b/compiler/nativeGen/AsmCodeGen.lhs -index 1ad1242..e976e58 100644 ---- a/compiler/nativeGen/AsmCodeGen.lhs -+++ b/compiler/nativeGen/AsmCodeGen.lhs -@@ -200,7 +200,7 @@ nativeCodeGen dflags h us cmms - ,ncgExpandTop = map SPARC.CodeGen.Expand.expandTop - ,ncgMakeFarBranches = id - } -- ArchARM _ _ -> -+ ArchARM _ _ _ -> - panic "nativeCodeGen: No NCG for ARM" - ArchPPC_64 -> - panic "nativeCodeGen: No NCG for PPC 64" -diff --git a/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs b/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs -index 6067f23..6cd3f00 100644 ---- a/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs -+++ b/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs -@@ -107,13 +107,13 @@ trivColorable - trivColorable platform virtualRegSqueeze realRegSqueeze RcInteger conflicts exclusions - | let !cALLOCATABLE_REGS_INTEGER - = iUnbox (case platformArch platform of -- ArchX86 -> 3 -- ArchX86_64 -> 5 -- ArchPPC -> 16 -- ArchSPARC -> 14 -- ArchPPC_64 -> panic "trivColorable ArchPPC_64" -- ArchARM _ _ -> panic "trivColorable ArchARM" -- ArchUnknown -> panic "trivColorable ArchUnknown") -+ ArchX86 -> 3 -+ ArchX86_64 -> 5 -+ ArchPPC -> 16 -+ ArchSPARC -> 14 -+ ArchPPC_64 -> panic "trivColorable ArchPPC_64" -+ ArchARM _ _ _ -> panic "trivColorable ArchARM" -+ ArchUnknown -> panic "trivColorable ArchUnknown") - , count2 <- accSqueeze (_ILIT(0)) cALLOCATABLE_REGS_INTEGER - (virtualRegSqueeze RcInteger) - conflicts -@@ -127,13 +127,13 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcInteger conflicts excl - trivColorable platform virtualRegSqueeze realRegSqueeze RcFloat conflicts exclusions - | let !cALLOCATABLE_REGS_FLOAT - = iUnbox (case platformArch platform of -- ArchX86 -> 0 -- ArchX86_64 -> 0 -- ArchPPC -> 0 -- ArchSPARC -> 22 -- ArchPPC_64 -> panic "trivColorable ArchPPC_64" -- ArchARM _ _ -> panic "trivColorable ArchARM" -- ArchUnknown -> panic "trivColorable ArchUnknown") -+ ArchX86 -> 0 -+ ArchX86_64 -> 0 -+ ArchPPC -> 0 -+ ArchSPARC -> 22 -+ ArchPPC_64 -> panic "trivColorable ArchPPC_64" -+ ArchARM _ _ _ -> panic "trivColorable ArchARM" -+ ArchUnknown -> panic "trivColorable ArchUnknown") - , count2 <- accSqueeze (_ILIT(0)) cALLOCATABLE_REGS_FLOAT - (virtualRegSqueeze RcFloat) - conflicts -@@ -147,13 +147,13 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcFloat conflicts exclus - trivColorable platform virtualRegSqueeze realRegSqueeze RcDouble conflicts exclusions - | let !cALLOCATABLE_REGS_DOUBLE - = iUnbox (case platformArch platform of -- ArchX86 -> 6 -- ArchX86_64 -> 0 -- ArchPPC -> 26 -- ArchSPARC -> 11 -- ArchPPC_64 -> panic "trivColorable ArchPPC_64" -- ArchARM _ _ -> panic "trivColorable ArchARM" -- ArchUnknown -> panic "trivColorable ArchUnknown") -+ ArchX86 -> 6 -+ ArchX86_64 -> 0 -+ ArchPPC -> 26 -+ ArchSPARC -> 11 -+ ArchPPC_64 -> panic "trivColorable ArchPPC_64" -+ ArchARM _ _ _ -> panic "trivColorable ArchARM" -+ ArchUnknown -> panic "trivColorable ArchUnknown") - , count2 <- accSqueeze (_ILIT(0)) cALLOCATABLE_REGS_DOUBLE - (virtualRegSqueeze RcDouble) - conflicts -@@ -167,13 +167,13 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcDouble conflicts exclu - trivColorable platform virtualRegSqueeze realRegSqueeze RcDoubleSSE conflicts exclusions - | let !cALLOCATABLE_REGS_SSE - = iUnbox (case platformArch platform of -- ArchX86 -> 8 -- ArchX86_64 -> 10 -- ArchPPC -> 0 -- ArchSPARC -> 0 -- ArchPPC_64 -> panic "trivColorable ArchPPC_64" -- ArchARM _ _ -> panic "trivColorable ArchARM" -- ArchUnknown -> panic "trivColorable ArchUnknown") -+ ArchX86 -> 8 -+ ArchX86_64 -> 10 -+ ArchPPC -> 0 -+ ArchSPARC -> 0 -+ ArchPPC_64 -> panic "trivColorable ArchPPC_64" -+ ArchARM _ _ _ -> panic "trivColorable ArchARM" -+ ArchUnknown -> panic "trivColorable ArchUnknown") - , count2 <- accSqueeze (_ILIT(0)) cALLOCATABLE_REGS_SSE - (virtualRegSqueeze RcDoubleSSE) - conflicts -diff --git a/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs b/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs -index 6fbbd04..fd1fd27 100644 ---- a/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs -+++ b/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs -@@ -68,11 +68,11 @@ instance FR SPARC.FreeRegs where - maxSpillSlots :: Platform -> Int - maxSpillSlots platform - = case platformArch platform of -- ArchX86 -> X86.Instr.maxSpillSlots True -- 32bit -- ArchX86_64 -> X86.Instr.maxSpillSlots False -- not 32bit -- ArchPPC -> PPC.Instr.maxSpillSlots -- ArchSPARC -> SPARC.Instr.maxSpillSlots -- ArchARM _ _ -> panic "maxSpillSlots ArchARM" -- ArchPPC_64 -> panic "maxSpillSlots ArchPPC_64" -- ArchUnknown -> panic "maxSpillSlots ArchUnknown" -+ ArchX86 -> X86.Instr.maxSpillSlots True -- 32bit -+ ArchX86_64 -> X86.Instr.maxSpillSlots False -- not 32bit -+ ArchPPC -> PPC.Instr.maxSpillSlots -+ ArchSPARC -> SPARC.Instr.maxSpillSlots -+ ArchARM _ _ _ -> panic "maxSpillSlots ArchARM" -+ ArchPPC_64 -> panic "maxSpillSlots ArchPPC_64" -+ ArchUnknown -> panic "maxSpillSlots ArchUnknown" - -diff --git a/compiler/nativeGen/RegAlloc/Linear/Main.hs b/compiler/nativeGen/RegAlloc/Linear/Main.hs -index fc0bde4..64b0f68 100644 ---- a/compiler/nativeGen/RegAlloc/Linear/Main.hs -+++ b/compiler/nativeGen/RegAlloc/Linear/Main.hs -@@ -180,13 +180,13 @@ linearRegAlloc - linearRegAlloc dflags first_id block_live sccs - = let platform = targetPlatform dflags - in case platformArch platform of -- ArchX86 -> linearRegAlloc' platform (frInitFreeRegs :: X86.FreeRegs) first_id block_live sccs -- ArchX86_64 -> linearRegAlloc' platform (frInitFreeRegs :: X86.FreeRegs) first_id block_live sccs -- ArchSPARC -> linearRegAlloc' platform (frInitFreeRegs :: SPARC.FreeRegs) first_id block_live sccs -- ArchPPC -> linearRegAlloc' platform (frInitFreeRegs :: PPC.FreeRegs) first_id block_live sccs -- ArchARM _ _ -> panic "linearRegAlloc ArchARM" -- ArchPPC_64 -> panic "linearRegAlloc ArchPPC_64" -- ArchUnknown -> panic "linearRegAlloc ArchUnknown" -+ ArchX86 -> linearRegAlloc' platform (frInitFreeRegs :: X86.FreeRegs) first_id block_live sccs -+ ArchX86_64 -> linearRegAlloc' platform (frInitFreeRegs :: X86.FreeRegs) first_id block_live sccs -+ ArchSPARC -> linearRegAlloc' platform (frInitFreeRegs :: SPARC.FreeRegs) first_id block_live sccs -+ ArchPPC -> linearRegAlloc' platform (frInitFreeRegs :: PPC.FreeRegs) first_id block_live sccs -+ ArchARM _ _ _ -> panic "linearRegAlloc ArchARM" -+ ArchPPC_64 -> panic "linearRegAlloc ArchPPC_64" -+ ArchUnknown -> panic "linearRegAlloc ArchUnknown" - - linearRegAlloc' - :: (FR freeRegs, PlatformOutputable instr, Instruction instr) -diff --git a/compiler/nativeGen/TargetReg.hs b/compiler/nativeGen/TargetReg.hs -index cbc4c17..13293de 100644 ---- a/compiler/nativeGen/TargetReg.hs -+++ b/compiler/nativeGen/TargetReg.hs -@@ -50,35 +50,35 @@ import qualified SPARC.Regs as SPARC - targetVirtualRegSqueeze :: Platform -> RegClass -> VirtualReg -> FastInt - targetVirtualRegSqueeze platform - = case platformArch platform of -- ArchX86 -> X86.virtualRegSqueeze -- ArchX86_64 -> X86.virtualRegSqueeze -- ArchPPC -> PPC.virtualRegSqueeze -- ArchSPARC -> SPARC.virtualRegSqueeze -- ArchPPC_64 -> panic "targetVirtualRegSqueeze ArchPPC_64" -- ArchARM _ _ -> panic "targetVirtualRegSqueeze ArchARM" -- ArchUnknown -> panic "targetVirtualRegSqueeze ArchUnknown" -+ ArchX86 -> X86.virtualRegSqueeze -+ ArchX86_64 -> X86.virtualRegSqueeze -+ ArchPPC -> PPC.virtualRegSqueeze -+ ArchSPARC -> SPARC.virtualRegSqueeze -+ ArchPPC_64 -> panic "targetVirtualRegSqueeze ArchPPC_64" -+ ArchARM _ _ _ -> panic "targetVirtualRegSqueeze ArchARM" -+ ArchUnknown -> panic "targetVirtualRegSqueeze ArchUnknown" - - targetRealRegSqueeze :: Platform -> RegClass -> RealReg -> FastInt - targetRealRegSqueeze platform - = case platformArch platform of -- ArchX86 -> X86.realRegSqueeze -- ArchX86_64 -> X86.realRegSqueeze -- ArchPPC -> PPC.realRegSqueeze -- ArchSPARC -> SPARC.realRegSqueeze -- ArchPPC_64 -> panic "targetRealRegSqueeze ArchPPC_64" -- ArchARM _ _ -> panic "targetRealRegSqueeze ArchARM" -- ArchUnknown -> panic "targetRealRegSqueeze ArchUnknown" -+ ArchX86 -> X86.realRegSqueeze -+ ArchX86_64 -> X86.realRegSqueeze -+ ArchPPC -> PPC.realRegSqueeze -+ ArchSPARC -> SPARC.realRegSqueeze -+ ArchPPC_64 -> panic "targetRealRegSqueeze ArchPPC_64" -+ ArchARM _ _ _ -> panic "targetRealRegSqueeze ArchARM" -+ ArchUnknown -> panic "targetRealRegSqueeze ArchUnknown" - - targetClassOfRealReg :: Platform -> RealReg -> RegClass - targetClassOfRealReg platform - = case platformArch platform of -- ArchX86 -> X86.classOfRealReg -- ArchX86_64 -> X86.classOfRealReg -- ArchPPC -> PPC.classOfRealReg -- ArchSPARC -> SPARC.classOfRealReg -- ArchPPC_64 -> panic "targetClassOfRealReg ArchPPC_64" -- ArchARM _ _ -> panic "targetClassOfRealReg ArchARM" -- ArchUnknown -> panic "targetClassOfRealReg ArchUnknown" -+ ArchX86 -> X86.classOfRealReg -+ ArchX86_64 -> X86.classOfRealReg -+ ArchPPC -> PPC.classOfRealReg -+ ArchSPARC -> SPARC.classOfRealReg -+ ArchPPC_64 -> panic "targetClassOfRealReg ArchPPC_64" -+ ArchARM _ _ _ -> panic "targetClassOfRealReg ArchARM" -+ ArchUnknown -> panic "targetClassOfRealReg ArchUnknown" - - -- TODO: This should look at targetPlatform too - targetWordSize :: Size -@@ -87,24 +87,24 @@ targetWordSize = intSize wordWidth - targetMkVirtualReg :: Platform -> Unique -> Size -> VirtualReg - targetMkVirtualReg platform - = case platformArch platform of -- ArchX86 -> X86.mkVirtualReg -- ArchX86_64 -> X86.mkVirtualReg -- ArchPPC -> PPC.mkVirtualReg -- ArchSPARC -> SPARC.mkVirtualReg -- ArchPPC_64 -> panic "targetMkVirtualReg ArchPPC_64" -- ArchARM _ _ -> panic "targetMkVirtualReg ArchARM" -- ArchUnknown -> panic "targetMkVirtualReg ArchUnknown" -+ ArchX86 -> X86.mkVirtualReg -+ ArchX86_64 -> X86.mkVirtualReg -+ ArchPPC -> PPC.mkVirtualReg -+ ArchSPARC -> SPARC.mkVirtualReg -+ ArchPPC_64 -> panic "targetMkVirtualReg ArchPPC_64" -+ ArchARM _ _ _ -> panic "targetMkVirtualReg ArchARM" -+ ArchUnknown -> panic "targetMkVirtualReg ArchUnknown" - - targetRegDotColor :: Platform -> RealReg -> SDoc - targetRegDotColor platform - = case platformArch platform of -- ArchX86 -> X86.regDotColor platform -- ArchX86_64 -> X86.regDotColor platform -- ArchPPC -> PPC.regDotColor -- ArchSPARC -> SPARC.regDotColor -- ArchPPC_64 -> panic "targetRegDotColor ArchPPC_64" -- ArchARM _ _ -> panic "targetRegDotColor ArchARM" -- ArchUnknown -> panic "targetRegDotColor ArchUnknown" -+ ArchX86 -> X86.regDotColor platform -+ ArchX86_64 -> X86.regDotColor platform -+ ArchPPC -> PPC.regDotColor -+ ArchSPARC -> SPARC.regDotColor -+ ArchPPC_64 -> panic "targetRegDotColor ArchPPC_64" -+ ArchARM _ _ _ -> panic "targetRegDotColor ArchARM" -+ ArchUnknown -> panic "targetRegDotColor ArchUnknown" - - - targetClassOfReg :: Platform -> Reg -> RegClass -diff --git a/compiler/utils/Platform.hs b/compiler/utils/Platform.hs -index 47dd779..8252621 100644 ---- a/compiler/utils/Platform.hs -+++ b/compiler/utils/Platform.hs -@@ -7,6 +7,7 @@ module Platform ( - OS(..), - ArmISA(..), - ArmISAExt(..), -+ ArmABI(..), - - target32Bit, - osElfTarget -@@ -41,7 +42,9 @@ data Arch - | ArchSPARC - | ArchARM - { armISA :: ArmISA -- , armISAExt :: [ArmISAExt] } -+ , armISAExt :: [ArmISAExt] -+ , armABI :: ArmABI -+ } - deriving (Read, Show, Eq) - - -@@ -61,7 +64,7 @@ data OS - | OSHaiku - deriving (Read, Show, Eq) - ---- | ARM Instruction Set Architecture and Extensions -+-- | ARM Instruction Set Architecture, Extensions and ABI - -- - data ArmISA - = ARMv5 -@@ -77,6 +80,11 @@ data ArmISAExt - | IWMMX2 - deriving (Read, Show, Eq) - -+data ArmABI -+ = SOFT -+ | SOFTFP -+ | HARD -+ deriving (Read, Show, Eq) - - target32Bit :: Platform -> Bool - target32Bit p = platformWordSize p == 4 -diff --git a/config.guess b/config.guess -index 463a03a..d622a44 100644 ---- a/config.guess -+++ b/config.guess -@@ -1,10 +1,10 @@ - #! /bin/sh - # Attempt to guess a canonical system name. - # Copyright (C) 1992, 1993, 1994, 1995, 1996, 1997, 1998, 1999, --# 2000, 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008 --# Free Software Foundation, Inc. -+# 2000, 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, -+# 2011, 2012 Free Software Foundation, Inc. - --timestamp='2008-11-15' -+timestamp='2012-02-10' - - # This file is free software; you can redistribute it and/or modify it - # under the terms of the GNU General Public License as published by -@@ -17,9 +17,7 @@ timestamp='2008-11-15' - # General Public License for more details. - # - # You should have received a copy of the GNU General Public License --# along with this program; if not, write to the Free Software --# Foundation, Inc., 51 Franklin Street - Fifth Floor, Boston, MA --# 02110-1301, USA. -+# along with this program; if not, see . - # - # As a special exception to the GNU General Public License, if you - # distribute this file as part of a program that contains a -@@ -27,16 +25,16 @@ timestamp='2008-11-15' - # the same distribution terms that you use for the rest of that program. - - --# Originally written by Per Bothner . --# Please send patches to . Submit a context --# diff and a properly formatted ChangeLog entry. -+# Originally written by Per Bothner. Please send patches (context -+# diff format) to and include a ChangeLog -+# entry. - # - # This script attempts to guess a canonical system name similar to - # config.sub. If it succeeds, it prints the system name on stdout, and - # exits with 0. Otherwise, it exits with 1. - # --# The plan is that this can be called by configure scripts if you --# don't specify an explicit build system type. -+# You can get the latest version of this script from: -+# http://git.savannah.gnu.org/gitweb/?p=config.git;a=blob_plain;f=config.guess;hb=HEAD - - me=`echo "$0" | sed -e 's,.*/,,'` - -@@ -56,8 +54,9 @@ version="\ - GNU config.guess ($timestamp) - - Originally written by Per Bothner. --Copyright (C) 1992, 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, --2002, 2003, 2004, 2005, 2006, 2007, 2008 Free Software Foundation, Inc. -+Copyright (C) 1992, 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000, -+2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011, 2012 -+Free Software Foundation, Inc. - - This is free software; see the source for copying conditions. There is NO - warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE." -@@ -144,7 +143,7 @@ UNAME_VERSION=`(uname -v) 2>/dev/null` || UNAME_VERSION=unknown - case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in - *:NetBSD:*:*) - # NetBSD (nbsd) targets should (where applicable) match one or -- # more of the tupples: *-*-netbsdelf*, *-*-netbsdaout*, -+ # more of the tuples: *-*-netbsdelf*, *-*-netbsdaout*, - # *-*-netbsdecoff* and *-*-netbsd*. For targets that recently - # switched to ELF, *-*-netbsd* would select the old - # object file format. This provides both forward -@@ -170,7 +169,7 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in - arm*|i386|m68k|ns32k|sh3*|sparc|vax) - eval $set_cc_for_build - if echo __ELF__ | $CC_FOR_BUILD -E - 2>/dev/null \ -- | grep __ELF__ >/dev/null -+ | grep -q __ELF__ - then - # Once all utilities can be ECOFF (netbsdecoff) or a.out (netbsdaout). - # Return netbsd for either. FIX? -@@ -180,7 +179,7 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in - fi - ;; - *) -- os=netbsd -+ os=netbsd - ;; - esac - # The OS release -@@ -223,7 +222,7 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in - UNAME_RELEASE=`/usr/sbin/sizer -v | awk '{print $3}'` - ;; - *5.*) -- UNAME_RELEASE=`/usr/sbin/sizer -v | awk '{print $4}'` -+ UNAME_RELEASE=`/usr/sbin/sizer -v | awk '{print $4}'` - ;; - esac - # According to Compaq, /usr/sbin/psrinfo has been available on -@@ -269,7 +268,10 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in - # A Xn.n version is an unreleased experimental baselevel. - # 1.2 uses "1.2" for uname -r. - echo ${UNAME_MACHINE}-dec-osf`echo ${UNAME_RELEASE} | sed -e 's/^[PVTX]//' | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz'` -- exit ;; -+ # Reset EXIT trap before exiting to avoid spurious non-zero exit code. -+ exitcode=$? -+ trap '' 0 -+ exit $exitcode ;; - Alpha\ *:Windows_NT*:*) - # How do we know it's Interix rather than the generic POSIX subsystem? - # Should we change UNAME_MACHINE based on the output of uname instead -@@ -295,7 +297,7 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in - echo s390-ibm-zvmoe - exit ;; - *:OS400:*:*) -- echo powerpc-ibm-os400 -+ echo powerpc-ibm-os400 - exit ;; - arm:RISC*:1.[012]*:*|arm:riscix:1.[012]*:*) - echo arm-acorn-riscix${UNAME_RELEASE} -@@ -324,12 +326,18 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in - case `/usr/bin/uname -p` in - sparc) echo sparc-icl-nx7; exit ;; - esac ;; -+ s390x:SunOS:*:*) -+ echo ${UNAME_MACHINE}-ibm-solaris2`echo ${UNAME_RELEASE}|sed -e 's/[^.]*//'` -+ exit ;; - sun4H:SunOS:5.*:*) - echo sparc-hal-solaris2`echo ${UNAME_RELEASE}|sed -e 's/[^.]*//'` - exit ;; - sun4*:SunOS:5.*:* | tadpole*:SunOS:5.*:*) - echo sparc-sun-solaris2`echo ${UNAME_RELEASE}|sed -e 's/[^.]*//'` - exit ;; -+ i86pc:AuroraUX:5.*:* | i86xen:AuroraUX:5.*:*) -+ echo i386-pc-auroraux${UNAME_RELEASE} -+ exit ;; - i86pc:SunOS:5.*:* | i86xen:SunOS:5.*:*) - eval $set_cc_for_build - SUN_ARCH="i386" -@@ -337,17 +345,7 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in - # Note that the Sun cc does not turn __LP64__ into 1 like gcc does. - # This test works for both compilers. - if [ "$CC_FOR_BUILD" != 'no_compiler_found' ]; then -- # bash is not able to generate correct code here -- # i.e. it leaves \ns there -- # so we need to use /usr/bin/echo to get what we want -- # note that if config.guess is run by /bin/sh then -- # this works as expected even without /usr/bin/echo -- # but the problem is that configure is clever enough -- # to find bash installed and then runs config.guess -- # by bash instead of by /bin/sh -- # It seems that using /usr/bin/echo here is the most -- # portable Solaris fix -- if /usr/bin/echo '\n#ifdef __amd64\nIS_64BIT_ARCH\n#endif' | \ -+ if (echo '#ifdef __amd64'; echo IS_64BIT_ARCH; echo '#endif') | \ - (CCOPTS= $CC_FOR_BUILD -E - 2>/dev/null) | \ - grep IS_64BIT_ARCH >/dev/null - then -@@ -398,23 +396,23 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in - # MiNT. But MiNT is downward compatible to TOS, so this should - # be no problem. - atarist[e]:*MiNT:*:* | atarist[e]:*mint:*:* | atarist[e]:*TOS:*:*) -- echo m68k-atari-mint${UNAME_RELEASE} -+ echo m68k-atari-mint${UNAME_RELEASE} - exit ;; - atari*:*MiNT:*:* | atari*:*mint:*:* | atarist[e]:*TOS:*:*) - echo m68k-atari-mint${UNAME_RELEASE} -- exit ;; -+ exit ;; - *falcon*:*MiNT:*:* | *falcon*:*mint:*:* | *falcon*:*TOS:*:*) -- echo m68k-atari-mint${UNAME_RELEASE} -+ echo m68k-atari-mint${UNAME_RELEASE} - exit ;; - milan*:*MiNT:*:* | milan*:*mint:*:* | *milan*:*TOS:*:*) -- echo m68k-milan-mint${UNAME_RELEASE} -- exit ;; -+ echo m68k-milan-mint${UNAME_RELEASE} -+ exit ;; - hades*:*MiNT:*:* | hades*:*mint:*:* | *hades*:*TOS:*:*) -- echo m68k-hades-mint${UNAME_RELEASE} -- exit ;; -+ echo m68k-hades-mint${UNAME_RELEASE} -+ exit ;; - *:*MiNT:*:* | *:*mint:*:* | *:*TOS:*:*) -- echo m68k-unknown-mint${UNAME_RELEASE} -- exit ;; -+ echo m68k-unknown-mint${UNAME_RELEASE} -+ exit ;; - m68k:machten:*:*) - echo m68k-apple-machten${UNAME_RELEASE} - exit ;; -@@ -484,8 +482,8 @@ EOF - echo m88k-motorola-sysv3 - exit ;; - AViiON:dgux:*:*) -- # DG/UX returns AViiON for all architectures -- UNAME_PROCESSOR=`/usr/bin/uname -p` -+ # DG/UX returns AViiON for all architectures -+ UNAME_PROCESSOR=`/usr/bin/uname -p` - if [ $UNAME_PROCESSOR = mc88100 ] || [ $UNAME_PROCESSOR = mc88110 ] - then - if [ ${TARGET_BINARY_INTERFACE}x = m88kdguxelfx ] || \ -@@ -498,7 +496,7 @@ EOF - else - echo i586-dg-dgux${UNAME_RELEASE} - fi -- exit ;; -+ exit ;; - M88*:DolphinOS:*:*) # DolphinOS (SVR3) - echo m88k-dolphin-sysv3 - exit ;; -@@ -555,7 +553,7 @@ EOF - echo rs6000-ibm-aix3.2 - fi - exit ;; -- *:AIX:*:[456]) -+ *:AIX:*:[4567]) - IBM_CPU_ID=`/usr/sbin/lsdev -C -c processor -S available | sed 1q | awk '{ print $1 }'` - if /usr/sbin/lsattr -El ${IBM_CPU_ID} | grep ' POWER' >/dev/null 2>&1; then - IBM_ARCH=rs6000 -@@ -598,52 +596,52 @@ EOF - 9000/[678][0-9][0-9]) - if [ -x /usr/bin/getconf ]; then - sc_cpu_version=`/usr/bin/getconf SC_CPU_VERSION 2>/dev/null` -- sc_kernel_bits=`/usr/bin/getconf SC_KERNEL_BITS 2>/dev/null` -- case "${sc_cpu_version}" in -- 523) HP_ARCH="hppa1.0" ;; # CPU_PA_RISC1_0 -- 528) HP_ARCH="hppa1.1" ;; # CPU_PA_RISC1_1 -- 532) # CPU_PA_RISC2_0 -- case "${sc_kernel_bits}" in -- 32) HP_ARCH="hppa2.0n" ;; -- 64) HP_ARCH="hppa2.0w" ;; -+ sc_kernel_bits=`/usr/bin/getconf SC_KERNEL_BITS 2>/dev/null` -+ case "${sc_cpu_version}" in -+ 523) HP_ARCH="hppa1.0" ;; # CPU_PA_RISC1_0 -+ 528) HP_ARCH="hppa1.1" ;; # CPU_PA_RISC1_1 -+ 532) # CPU_PA_RISC2_0 -+ case "${sc_kernel_bits}" in -+ 32) HP_ARCH="hppa2.0n" ;; -+ 64) HP_ARCH="hppa2.0w" ;; - '') HP_ARCH="hppa2.0" ;; # HP-UX 10.20 -- esac ;; -- esac -+ esac ;; -+ esac - fi - if [ "${HP_ARCH}" = "" ]; then - eval $set_cc_for_build -- sed 's/^ //' << EOF >$dummy.c -+ sed 's/^ //' << EOF >$dummy.c - -- #define _HPUX_SOURCE -- #include -- #include -+ #define _HPUX_SOURCE -+ #include -+ #include - -- int main () -- { -- #if defined(_SC_KERNEL_BITS) -- long bits = sysconf(_SC_KERNEL_BITS); -- #endif -- long cpu = sysconf (_SC_CPU_VERSION); -+ int main () -+ { -+ #if defined(_SC_KERNEL_BITS) -+ long bits = sysconf(_SC_KERNEL_BITS); -+ #endif -+ long cpu = sysconf (_SC_CPU_VERSION); - -- switch (cpu) -- { -- case CPU_PA_RISC1_0: puts ("hppa1.0"); break; -- case CPU_PA_RISC1_1: puts ("hppa1.1"); break; -- case CPU_PA_RISC2_0: -- #if defined(_SC_KERNEL_BITS) -- switch (bits) -- { -- case 64: puts ("hppa2.0w"); break; -- case 32: puts ("hppa2.0n"); break; -- default: puts ("hppa2.0"); break; -- } break; -- #else /* !defined(_SC_KERNEL_BITS) */ -- puts ("hppa2.0"); break; -- #endif -- default: puts ("hppa1.0"); break; -- } -- exit (0); -- } -+ switch (cpu) -+ { -+ case CPU_PA_RISC1_0: puts ("hppa1.0"); break; -+ case CPU_PA_RISC1_1: puts ("hppa1.1"); break; -+ case CPU_PA_RISC2_0: -+ #if defined(_SC_KERNEL_BITS) -+ switch (bits) -+ { -+ case 64: puts ("hppa2.0w"); break; -+ case 32: puts ("hppa2.0n"); break; -+ default: puts ("hppa2.0"); break; -+ } break; -+ #else /* !defined(_SC_KERNEL_BITS) */ -+ puts ("hppa2.0"); break; -+ #endif -+ default: puts ("hppa1.0"); break; -+ } -+ exit (0); -+ } - EOF - (CCOPTS= $CC_FOR_BUILD -o $dummy $dummy.c 2>/dev/null) && HP_ARCH=`$dummy` - test -z "$HP_ARCH" && HP_ARCH=hppa -@@ -663,7 +661,7 @@ EOF - # => hppa64-hp-hpux11.23 - - if echo __LP64__ | (CCOPTS= $CC_FOR_BUILD -E - 2>/dev/null) | -- grep __LP64__ >/dev/null -+ grep -q __LP64__ - then - HP_ARCH="hppa2.0w" - else -@@ -734,22 +732,22 @@ EOF - exit ;; - C1*:ConvexOS:*:* | convex:ConvexOS:C1*:*) - echo c1-convex-bsd -- exit ;; -+ exit ;; - C2*:ConvexOS:*:* | convex:ConvexOS:C2*:*) - if getsysinfo -f scalar_acc - then echo c32-convex-bsd - else echo c2-convex-bsd - fi -- exit ;; -+ exit ;; - C34*:ConvexOS:*:* | convex:ConvexOS:C34*:*) - echo c34-convex-bsd -- exit ;; -+ exit ;; - C38*:ConvexOS:*:* | convex:ConvexOS:C38*:*) - echo c38-convex-bsd -- exit ;; -+ exit ;; - C4*:ConvexOS:*:* | convex:ConvexOS:C4*:*) - echo c4-convex-bsd -- exit ;; -+ exit ;; - CRAY*Y-MP:*:*:*) - echo ymp-cray-unicos${UNAME_RELEASE} | sed -e 's/\.[^.]*$/.X/' - exit ;; -@@ -773,14 +771,14 @@ EOF - exit ;; - F30[01]:UNIX_System_V:*:* | F700:UNIX_System_V:*:*) - FUJITSU_PROC=`uname -m | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz'` -- FUJITSU_SYS=`uname -p | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/\///'` -- FUJITSU_REL=`echo ${UNAME_RELEASE} | sed -e 's/ /_/'` -- echo "${FUJITSU_PROC}-fujitsu-${FUJITSU_SYS}${FUJITSU_REL}" -- exit ;; -+ FUJITSU_SYS=`uname -p | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/\///'` -+ FUJITSU_REL=`echo ${UNAME_RELEASE} | sed -e 's/ /_/'` -+ echo "${FUJITSU_PROC}-fujitsu-${FUJITSU_SYS}${FUJITSU_REL}" -+ exit ;; - 5000:UNIX_System_V:4.*:*) -- FUJITSU_SYS=`uname -p | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/\///'` -- FUJITSU_REL=`echo ${UNAME_RELEASE} | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/ /_/'` -- echo "sparc-fujitsu-${FUJITSU_SYS}${FUJITSU_REL}" -+ FUJITSU_SYS=`uname -p | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/\///'` -+ FUJITSU_REL=`echo ${UNAME_RELEASE} | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/ /_/'` -+ echo "sparc-fujitsu-${FUJITSU_SYS}${FUJITSU_REL}" - exit ;; - i*86:BSD/386:*:* | i*86:BSD/OS:*:* | *:Ascend\ Embedded/OS:*:*) - echo ${UNAME_MACHINE}-pc-bsdi${UNAME_RELEASE} -@@ -792,13 +790,12 @@ EOF - echo ${UNAME_MACHINE}-unknown-bsdi${UNAME_RELEASE} - exit ;; - *:FreeBSD:*:*) -- case ${UNAME_MACHINE} in -- pc98) -- echo i386-unknown-freebsd`echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'` ;; -+ UNAME_PROCESSOR=`/usr/bin/uname -p` -+ case ${UNAME_PROCESSOR} in - amd64) - echo x86_64-unknown-freebsd`echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'` ;; - *) -- echo ${UNAME_MACHINE}-unknown-freebsd`echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'` ;; -+ echo ${UNAME_PROCESSOR}-unknown-freebsd`echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'` ;; - esac - exit ;; - i*:CYGWIN*:*) -@@ -807,19 +804,22 @@ EOF - *:MINGW*:*) - echo ${UNAME_MACHINE}-pc-mingw32 - exit ;; -+ i*:MSYS*:*) -+ echo ${UNAME_MACHINE}-pc-msys -+ exit ;; - i*:windows32*:*) -- # uname -m includes "-pc" on this system. -- echo ${UNAME_MACHINE}-mingw32 -+ # uname -m includes "-pc" on this system. -+ echo ${UNAME_MACHINE}-mingw32 - exit ;; - i*:PW*:*) - echo ${UNAME_MACHINE}-pc-pw32 - exit ;; -- *:Interix*:[3456]*) -- case ${UNAME_MACHINE} in -+ *:Interix*:*) -+ case ${UNAME_MACHINE} in - x86) - echo i586-pc-interix${UNAME_RELEASE} - exit ;; -- EM64T | authenticamd | genuineintel) -+ authenticamd | genuineintel | EM64T) - echo x86_64-unknown-interix${UNAME_RELEASE} - exit ;; - IA64) -@@ -829,6 +829,9 @@ EOF - [345]86:Windows_95:* | [345]86:Windows_98:* | [345]86:Windows_NT:*) - echo i${UNAME_MACHINE}-pc-mks - exit ;; -+ 8664:Windows_NT:*) -+ echo x86_64-pc-mks -+ exit ;; - i*:Windows_NT*:* | Pentium*:Windows_NT*:*) - # How do we know it's Interix rather than the generic POSIX subsystem? - # It also conflicts with pre-2.0 versions of AT&T UWIN. Should we -@@ -858,6 +861,27 @@ EOF - i*86:Minix:*:*) - echo ${UNAME_MACHINE}-pc-minix - exit ;; -+ aarch64:Linux:*:*) -+ echo ${UNAME_MACHINE}-unknown-linux-gnu -+ exit ;; -+ aarch64_be:Linux:*:*) -+ UNAME_MACHINE=aarch64_be -+ echo ${UNAME_MACHINE}-unknown-linux-gnu -+ exit ;; -+ alpha:Linux:*:*) -+ case `sed -n '/^cpu model/s/^.*: \(.*\)/\1/p' < /proc/cpuinfo` in -+ EV5) UNAME_MACHINE=alphaev5 ;; -+ EV56) UNAME_MACHINE=alphaev56 ;; -+ PCA56) UNAME_MACHINE=alphapca56 ;; -+ PCA57) UNAME_MACHINE=alphapca56 ;; -+ EV6) UNAME_MACHINE=alphaev6 ;; -+ EV67) UNAME_MACHINE=alphaev67 ;; -+ EV68*) UNAME_MACHINE=alphaev68 ;; -+ esac -+ objdump --private-headers /bin/sh | grep -q ld.so.1 -+ if test "$?" = 0 ; then LIBC="libc1" ; else LIBC="" ; fi -+ echo ${UNAME_MACHINE}-unknown-linux-gnu${LIBC} -+ exit ;; - arm*:Linux:*:*) - eval $set_cc_for_build - if echo __ARM_EABI__ | $CC_FOR_BUILD -E - 2>/dev/null \ -@@ -865,20 +889,40 @@ EOF - then - echo ${UNAME_MACHINE}-unknown-linux-gnu - else -- echo ${UNAME_MACHINE}-unknown-linux-gnueabi -+ if echo __ARM_PCS_VFP | $CC_FOR_BUILD -E - 2>/dev/null \ -+ | grep -q __ARM_PCS_VFP -+ then -+ echo ${UNAME_MACHINE}-unknown-linux-gnueabi -+ else -+ echo ${UNAME_MACHINE}-unknown-linux-gnueabihf -+ fi - fi - exit ;; - avr32*:Linux:*:*) - echo ${UNAME_MACHINE}-unknown-linux-gnu - exit ;; - cris:Linux:*:*) -- echo cris-axis-linux-gnu -+ echo ${UNAME_MACHINE}-axis-linux-gnu - exit ;; - crisv32:Linux:*:*) -- echo crisv32-axis-linux-gnu -+ echo ${UNAME_MACHINE}-axis-linux-gnu - exit ;; - frv:Linux:*:*) -- echo frv-unknown-linux-gnu -+ echo ${UNAME_MACHINE}-unknown-linux-gnu -+ exit ;; -+ hexagon:Linux:*:*) -+ echo ${UNAME_MACHINE}-unknown-linux-gnu -+ exit ;; -+ i*86:Linux:*:*) -+ LIBC=gnu -+ eval $set_cc_for_build -+ sed 's/^ //' << EOF >$dummy.c -+ #ifdef __dietlibc__ -+ LIBC=dietlibc -+ #endif -+EOF -+ eval `$CC_FOR_BUILD -E $dummy.c 2>/dev/null | grep '^LIBC'` -+ echo "${UNAME_MACHINE}-pc-linux-${LIBC}" - exit ;; - ia64:Linux:*:*) - echo ${UNAME_MACHINE}-unknown-linux-gnu -@@ -889,78 +933,34 @@ EOF - m68*:Linux:*:*) - echo ${UNAME_MACHINE}-unknown-linux-gnu - exit ;; -- mips:Linux:*:*) -- eval $set_cc_for_build -- sed 's/^ //' << EOF >$dummy.c -- #undef CPU -- #undef mips -- #undef mipsel -- #if defined(__MIPSEL__) || defined(__MIPSEL) || defined(_MIPSEL) || defined(MIPSEL) -- CPU=mipsel -- #else -- #if defined(__MIPSEB__) || defined(__MIPSEB) || defined(_MIPSEB) || defined(MIPSEB) -- CPU=mips -- #else -- CPU= -- #endif -- #endif --EOF -- eval "`$CC_FOR_BUILD -E $dummy.c 2>/dev/null | sed -n ' -- /^CPU/{ -- s: ::g -- p -- }'`" -- test x"${CPU}" != x && { echo "${CPU}-unknown-linux-gnu"; exit; } -- ;; -- mips64:Linux:*:*) -+ mips:Linux:*:* | mips64:Linux:*:*) - eval $set_cc_for_build - sed 's/^ //' << EOF >$dummy.c - #undef CPU -- #undef mips64 -- #undef mips64el -+ #undef ${UNAME_MACHINE} -+ #undef ${UNAME_MACHINE}el - #if defined(__MIPSEL__) || defined(__MIPSEL) || defined(_MIPSEL) || defined(MIPSEL) -- CPU=mips64el -+ CPU=${UNAME_MACHINE}el - #else - #if defined(__MIPSEB__) || defined(__MIPSEB) || defined(_MIPSEB) || defined(MIPSEB) -- CPU=mips64 -+ CPU=${UNAME_MACHINE} - #else - CPU= - #endif - #endif - EOF -- eval "`$CC_FOR_BUILD -E $dummy.c 2>/dev/null | sed -n ' -- /^CPU/{ -- s: ::g -- p -- }'`" -+ eval `$CC_FOR_BUILD -E $dummy.c 2>/dev/null | grep '^CPU'` - test x"${CPU}" != x && { echo "${CPU}-unknown-linux-gnu"; exit; } - ;; - or32:Linux:*:*) -- echo or32-unknown-linux-gnu -- exit ;; -- ppc:Linux:*:*) -- echo powerpc-unknown-linux-gnu -- exit ;; -- ppc64:Linux:*:*) -- echo powerpc64-unknown-linux-gnu -- exit ;; -- alpha:Linux:*:*) -- case `sed -n '/^cpu model/s/^.*: \(.*\)/\1/p' < /proc/cpuinfo` in -- EV5) UNAME_MACHINE=alphaev5 ;; -- EV56) UNAME_MACHINE=alphaev56 ;; -- PCA56) UNAME_MACHINE=alphapca56 ;; -- PCA57) UNAME_MACHINE=alphapca56 ;; -- EV6) UNAME_MACHINE=alphaev6 ;; -- EV67) UNAME_MACHINE=alphaev67 ;; -- EV68*) UNAME_MACHINE=alphaev68 ;; -- esac -- objdump --private-headers /bin/sh | grep ld.so.1 >/dev/null -- if test "$?" = 0 ; then LIBC="libc1" ; else LIBC="" ; fi -- echo ${UNAME_MACHINE}-unknown-linux-gnu${LIBC} -+ echo ${UNAME_MACHINE}-unknown-linux-gnu - exit ;; - padre:Linux:*:*) - echo sparc-unknown-linux-gnu - exit ;; -+ parisc64:Linux:*:* | hppa64:Linux:*:*) -+ echo hppa64-unknown-linux-gnu -+ exit ;; - parisc:Linux:*:* | hppa:Linux:*:*) - # Look for CPU level - case `grep '^cpu[^a-z]*:' /proc/cpuinfo 2>/dev/null | cut -d' ' -f2` in -@@ -969,14 +969,17 @@ EOF - *) echo hppa-unknown-linux-gnu ;; - esac - exit ;; -- parisc64:Linux:*:* | hppa64:Linux:*:*) -- echo hppa64-unknown-linux-gnu -+ ppc64:Linux:*:*) -+ echo powerpc64-unknown-linux-gnu -+ exit ;; -+ ppc:Linux:*:*) -+ echo powerpc-unknown-linux-gnu - exit ;; - s390:Linux:*:* | s390x:Linux:*:*) - echo ${UNAME_MACHINE}-ibm-linux - exit ;; - sh64*:Linux:*:*) -- echo ${UNAME_MACHINE}-unknown-linux-gnu -+ echo ${UNAME_MACHINE}-unknown-linux-gnu - exit ;; - sh*:Linux:*:*) - echo ${UNAME_MACHINE}-unknown-linux-gnu -@@ -984,75 +987,18 @@ EOF - sparc:Linux:*:* | sparc64:Linux:*:*) - echo ${UNAME_MACHINE}-unknown-linux-gnu - exit ;; -+ tile*:Linux:*:*) -+ echo ${UNAME_MACHINE}-unknown-linux-gnu -+ exit ;; - vax:Linux:*:*) - echo ${UNAME_MACHINE}-dec-linux-gnu - exit ;; - x86_64:Linux:*:*) -- echo x86_64-unknown-linux-gnu -+ echo ${UNAME_MACHINE}-unknown-linux-gnu - exit ;; - xtensa*:Linux:*:*) -- echo ${UNAME_MACHINE}-unknown-linux-gnu -+ echo ${UNAME_MACHINE}-unknown-linux-gnu - exit ;; -- i*86:Linux:*:*) -- # The BFD linker knows what the default object file format is, so -- # first see if it will tell us. cd to the root directory to prevent -- # problems with other programs or directories called `ld' in the path. -- # Set LC_ALL=C to ensure ld outputs messages in English. -- ld_supported_targets=`cd /; LC_ALL=C ld --help 2>&1 \ -- | sed -ne '/supported targets:/!d -- s/[ ][ ]*/ /g -- s/.*supported targets: *// -- s/ .*// -- p'` -- case "$ld_supported_targets" in -- elf32-i386) -- TENTATIVE="${UNAME_MACHINE}-pc-linux-gnu" -- ;; -- a.out-i386-linux) -- echo "${UNAME_MACHINE}-pc-linux-gnuaout" -- exit ;; -- "") -- # Either a pre-BFD a.out linker (linux-gnuoldld) or -- # one that does not give us useful --help. -- echo "${UNAME_MACHINE}-pc-linux-gnuoldld" -- exit ;; -- esac -- # Determine whether the default compiler is a.out or elf -- eval $set_cc_for_build -- sed 's/^ //' << EOF >$dummy.c -- #include -- #ifdef __ELF__ -- # ifdef __GLIBC__ -- # if __GLIBC__ >= 2 -- LIBC=gnu -- # else -- LIBC=gnulibc1 -- # endif -- # else -- LIBC=gnulibc1 -- # endif -- #else -- #if defined(__INTEL_COMPILER) || defined(__PGI) || defined(__SUNPRO_C) || defined(__SUNPRO_CC) -- LIBC=gnu -- #else -- LIBC=gnuaout -- #endif -- #endif -- #ifdef __dietlibc__ -- LIBC=dietlibc -- #endif --EOF -- eval "`$CC_FOR_BUILD -E $dummy.c 2>/dev/null | sed -n ' -- /^LIBC/{ -- s: ::g -- p -- }'`" -- test x"${LIBC}" != x && { -- echo "${UNAME_MACHINE}-pc-linux-${LIBC}" -- exit -- } -- test x"${TENTATIVE}" != x && { echo "${TENTATIVE}"; exit; } -- ;; - i*86:DYNIX/ptx:4*:*) - # ptx 4.0 does uname -s correctly, with DYNIX/ptx in there. - # earlier versions are messed up and put the nodename in both -@@ -1060,11 +1006,11 @@ EOF - echo i386-sequent-sysv4 - exit ;; - i*86:UNIX_SV:4.2MP:2.*) -- # Unixware is an offshoot of SVR4, but it has its own version -- # number series starting with 2... -- # I am not positive that other SVR4 systems won't match this, -+ # Unixware is an offshoot of SVR4, but it has its own version -+ # number series starting with 2... -+ # I am not positive that other SVR4 systems won't match this, - # I just have to hope. -- rms. -- # Use sysv4.2uw... so that sysv4* matches it. -+ # Use sysv4.2uw... so that sysv4* matches it. - echo ${UNAME_MACHINE}-pc-sysv4.2uw${UNAME_VERSION} - exit ;; - i*86:OS/2:*:*) -@@ -1081,7 +1027,7 @@ EOF - i*86:syllable:*:*) - echo ${UNAME_MACHINE}-pc-syllable - exit ;; -- i*86:LynxOS:2.*:* | i*86:LynxOS:3.[01]*:* | i*86:LynxOS:4.0*:*) -+ i*86:LynxOS:2.*:* | i*86:LynxOS:3.[01]*:* | i*86:LynxOS:4.[02]*:*) - echo i386-unknown-lynxos${UNAME_RELEASE} - exit ;; - i*86:*DOS:*:*) -@@ -1096,7 +1042,7 @@ EOF - fi - exit ;; - i*86:*:5:[678]*) -- # UnixWare 7.x, OpenUNIX and OpenServer 6. -+ # UnixWare 7.x, OpenUNIX and OpenServer 6. - case `/bin/uname -X | grep "^Machine"` in - *486*) UNAME_MACHINE=i486 ;; - *Pentium) UNAME_MACHINE=i586 ;; -@@ -1124,10 +1070,13 @@ EOF - exit ;; - pc:*:*:*) - # Left here for compatibility: -- # uname -m prints for DJGPP always 'pc', but it prints nothing about -- # the processor, so we play safe by assuming i386. -- echo i386-pc-msdosdjgpp -- exit ;; -+ # uname -m prints for DJGPP always 'pc', but it prints nothing about -+ # the processor, so we play safe by assuming i586. -+ # Note: whatever this is, it MUST be the same as what config.sub -+ # prints for the "djgpp" host, or else GDB configury will decide that -+ # this is a cross-build. -+ echo i586-pc-msdosdjgpp -+ exit ;; - Intel:Mach:3*:*) - echo i386-pc-mach3 - exit ;; -@@ -1162,8 +1111,18 @@ EOF - /bin/uname -p 2>/dev/null | /bin/grep entium >/dev/null \ - && { echo i586-ncr-sysv4.3${OS_REL}; exit; } ;; - 3[34]??:*:4.0:* | 3[34]??,*:*:4.0:*) -- /bin/uname -p 2>/dev/null | grep 86 >/dev/null \ -- && { echo i486-ncr-sysv4; exit; } ;; -+ /bin/uname -p 2>/dev/null | grep 86 >/dev/null \ -+ && { echo i486-ncr-sysv4; exit; } ;; -+ NCR*:*:4.2:* | MPRAS*:*:4.2:*) -+ OS_REL='.3' -+ test -r /etc/.relid \ -+ && OS_REL=.`sed -n 's/[^ ]* [^ ]* \([0-9][0-9]\).*/\1/p' < /etc/.relid` -+ /bin/uname -p 2>/dev/null | grep 86 >/dev/null \ -+ && { echo i486-ncr-sysv4.3${OS_REL}; exit; } -+ /bin/uname -p 2>/dev/null | /bin/grep entium >/dev/null \ -+ && { echo i586-ncr-sysv4.3${OS_REL}; exit; } -+ /bin/uname -p 2>/dev/null | /bin/grep pteron >/dev/null \ -+ && { echo i586-ncr-sysv4.3${OS_REL}; exit; } ;; - m68*:LynxOS:2.*:* | m68*:LynxOS:3.0*:*) - echo m68k-unknown-lynxos${UNAME_RELEASE} - exit ;; -@@ -1176,7 +1135,7 @@ EOF - rs6000:LynxOS:2.*:*) - echo rs6000-unknown-lynxos${UNAME_RELEASE} - exit ;; -- PowerPC:LynxOS:2.*:* | PowerPC:LynxOS:3.[01]*:* | PowerPC:LynxOS:4.0*:*) -+ PowerPC:LynxOS:2.*:* | PowerPC:LynxOS:3.[01]*:* | PowerPC:LynxOS:4.[02]*:*) - echo powerpc-unknown-lynxos${UNAME_RELEASE} - exit ;; - SM[BE]S:UNIX_SV:*:*) -@@ -1196,10 +1155,10 @@ EOF - echo ns32k-sni-sysv - fi - exit ;; -- PENTIUM:*:4.0*:*) # Unisys `ClearPath HMP IX 4000' SVR4/MP effort -- # says -- echo i586-unisys-sysv4 -- exit ;; -+ PENTIUM:*:4.0*:*) # Unisys `ClearPath HMP IX 4000' SVR4/MP effort -+ # says -+ echo i586-unisys-sysv4 -+ exit ;; - *:UNIX_System_V:4*:FTX*) - # From Gerald Hewes . - # How about differentiating between stratus architectures? -djm -@@ -1225,11 +1184,11 @@ EOF - exit ;; - R[34]000:*System_V*:*:* | R4000:UNIX_SYSV:*:* | R*000:UNIX_SV:*:*) - if [ -d /usr/nec ]; then -- echo mips-nec-sysv${UNAME_RELEASE} -+ echo mips-nec-sysv${UNAME_RELEASE} - else -- echo mips-unknown-sysv${UNAME_RELEASE} -+ echo mips-unknown-sysv${UNAME_RELEASE} - fi -- exit ;; -+ exit ;; - BeBox:BeOS:*:*) # BeOS running on hardware made by Be, PPC only. - echo powerpc-be-beos - exit ;; -@@ -1269,6 +1228,16 @@ EOF - *:Darwin:*:*) - UNAME_PROCESSOR=`uname -p` || UNAME_PROCESSOR=unknown - case $UNAME_PROCESSOR in -+ i386) -+ eval $set_cc_for_build -+ if [ "$CC_FOR_BUILD" != 'no_compiler_found' ]; then -+ if (echo '#ifdef __LP64__'; echo IS_64BIT_ARCH; echo '#endif') | \ -+ (CCOPTS= $CC_FOR_BUILD -E - 2>/dev/null) | \ -+ grep IS_64BIT_ARCH >/dev/null -+ then -+ UNAME_PROCESSOR="x86_64" -+ fi -+ fi ;; - unknown) UNAME_PROCESSOR=powerpc ;; - esac - echo ${UNAME_PROCESSOR}-apple-darwin${UNAME_RELEASE} -@@ -1284,6 +1253,9 @@ EOF - *:QNX:*:4*) - echo i386-pc-qnx - exit ;; -+ NEO-?:NONSTOP_KERNEL:*:*) -+ echo neo-tandem-nsk${UNAME_RELEASE} -+ exit ;; - NSE-?:NONSTOP_KERNEL:*:*) - echo nse-tandem-nsk${UNAME_RELEASE} - exit ;; -@@ -1329,13 +1301,13 @@ EOF - echo pdp10-unknown-its - exit ;; - SEI:*:*:SEIUX) -- echo mips-sei-seiux${UNAME_RELEASE} -+ echo mips-sei-seiux${UNAME_RELEASE} - exit ;; - *:DragonFly:*:*) - echo ${UNAME_MACHINE}-unknown-dragonfly`echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'` - exit ;; - *:*VMS:*:*) -- UNAME_MACHINE=`(uname -p) 2>/dev/null` -+ UNAME_MACHINE=`(uname -p) 2>/dev/null` - case "${UNAME_MACHINE}" in - A*) echo alpha-dec-vms ; exit ;; - I*) echo ia64-dec-vms ; exit ;; -@@ -1350,6 +1322,12 @@ EOF - i*86:rdos:*:*) - echo ${UNAME_MACHINE}-pc-rdos - exit ;; -+ i*86:AROS:*:*) -+ echo ${UNAME_MACHINE}-pc-aros -+ exit ;; -+ x86_64:VMkernel:*:*) -+ echo ${UNAME_MACHINE}-unknown-esx -+ exit ;; - esac - - #echo '(No uname command or uname output not recognized.)' 1>&2 -@@ -1372,11 +1350,11 @@ main () - #include - printf ("m68k-sony-newsos%s\n", - #ifdef NEWSOS4 -- "4" -+ "4" - #else -- "" -+ "" - #endif -- ); exit (0); -+ ); exit (0); - #endif - #endif - -diff --git a/configure.ac b/configure.ac -index 9237c77..8e3d9d2 100644 ---- a/configure.ac -+++ b/configure.ac -@@ -210,6 +210,20 @@ AC_CANONICAL_BUILD - AC_CANONICAL_HOST - AC_CANONICAL_TARGET - -+# Testing ARM ABI -+# required for code generation (LLVM options) -+ARM_ABI=SOFT -+echo HOST: $host -+ -+case $host in -+ arm*-*-linux-gnueabihf) -+ ARM_ABI=HARD -+ ;; -+ arm*-*-linux-gnueabi) -+ ARM_ABI=SOFTFP -+ ;; -+esac -+ - FPTOOLS_SET_PLATFORM_VARS - - # Verify that the installed (bootstrap) GHC is capable of generating --- -1.7.4.3 - diff --git a/ghc-7.4-silence-gen_contents_index.patch b/ghc-7.4-silence-gen_contents_index.patch deleted file mode 100644 index d000b8b..0000000 --- a/ghc-7.4-silence-gen_contents_index.patch +++ /dev/null @@ -1,11 +0,0 @@ ---- ghc-7.4.1/libraries/gen_contents_index~ 2012-09-30 16:14:39.368295240 +0900 -+++ ghc-7.4.1/libraries/gen_contents_index 2012-10-30 19:12:10.017398594 +0900 -@@ -50,7 +50,7 @@ - esac - - # Now create the combined contents and index pages --echo $HADDOCK_ARGS -+#echo $HADDOCK_ARGS - $HADDOCK --gen-index --gen-contents -o . \ - -t "Haskell Hierarchical Libraries" \ - -p "prologue.txt" \ diff --git a/ghc-gen_contents_index-haddock-path.patch b/ghc-gen_contents_index-haddock-path.patch new file mode 100644 index 0000000..64ede18 --- /dev/null +++ b/ghc-gen_contents_index-haddock-path.patch @@ -0,0 +1,11 @@ +--- 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 + done + else +- HADDOCK=../../../../../bin/haddock ++ HADDOCK=/usr/bin/haddock + # We don't want the GHC API to swamp the index + HADDOCK_FILES=`ls -1 */*.haddock | grep -v '/ghc\.haddock' | sort` + HADDOCK_ARGS="-p prologue.txt" diff --git a/ghc-gen_contents_index-type-level.patch b/ghc-gen_contents_index-type-level.patch deleted file mode 100644 index 05a9e42..0000000 --- a/ghc-gen_contents_index-type-level.patch +++ /dev/null @@ -1,12 +0,0 @@ -diff -u ghc-6.12.3/libraries/gen_contents_index\~ ghc-6.12.3/libraries/gen_contents_index ---- ghc-6.12.3/libraries/gen_contents_index~ 2010-09-14 13:03:12.000000000 +1000 -+++ ghc-6.12.3/libraries/gen_contents_index 2010-11-04 16:41:32.000000000 +1000 -@@ -24,7 +24,7 @@ - *) - HADDOCK=/usr/bin/haddock - # We don't want the GHC API to swamp the index -- HADDOCK_FILES=`ls -1 */*.haddock | grep -v '/ghc\.haddock' | sort` -+ HADDOCK_FILES=`ls -1 */*.haddock | grep -v '/ghc\.haddock' | grep -v '/type-level\.haddock' | sort` - for HADDOCK_FILE in $HADDOCK_FILES - do - NAME_VERSION=`echo "$HADDOCK_FILE" | sed 's#/.*##'` diff --git a/ghc-powerpc-linker-mmap.patch b/ghc-powerpc-linker-mmap.patch deleted file mode 100644 index df0d5ff..0000000 --- a/ghc-powerpc-linker-mmap.patch +++ /dev/null @@ -1,34 +0,0 @@ -diff -up ghc-7.0.2/rts/Linker.c.fix-powerpc ghc-7.0.2/rts/Linker.c ---- ghc-7.0.2/rts/Linker.c.fix-powerpc 2011-02-28 19:10:08.000000000 +0100 -+++ ghc-7.0.2/rts/Linker.c 2011-04-25 22:20:10.781092305 +0200 -@@ -70,11 +70,12 @@ - #include - #endif - --#if defined(linux_HOST_OS ) || defined(freebsd_HOST_OS) || \ -- defined(dragonfly_HOST_OS) || defined(netbsd_HOST_OS ) || \ -- defined(openbsd_HOST_OS ) || \ -- ( defined(darwin_HOST_OS ) && !defined(powerpc_HOST_ARCH) ) --/* Don't use mmap on powerpc-apple-darwin as mmap doesn't support -+#if !defined(powerpc_HOST_ARCH) && \ -+ ( defined(linux_HOST_OS ) || defined(freebsd_HOST_OS) || \ -+ defined(dragonfly_HOST_OS) || defined(netbsd_HOST_OS ) || \ -+ defined(openbsd_HOST_OS ) || defined(darwin_HOST_OS ) || \ -+ defined(kfreebsdgnu_HOST_OS) ) -+/* Don't use mmap on powerpc_HOST_ARCH as mmap doesn't support - * reallocating but we need to allocate jump islands just after each - * object images. Otherwise relative branches to jump islands can fail - * due to 24-bits displacement overflow. -@@ -2436,7 +2437,11 @@ static void ocFlushInstructionCacheFrom( - static void ocFlushInstructionCache( ObjectCode *oc ) - { - /* The main object code */ -- ocFlushInstructionCacheFrom(oc->image + oc->misalignment, oc->fileSize); -+ ocFlushInstructionCacheFrom(oc->image -+#ifdef darwin_HOST_OS -+ + oc->misalignment -+#endif -+ , oc->fileSize); - - /* Jump Islands */ - ocFlushInstructionCacheFrom(oc->symbol_extras, sizeof(SymbolExtra) * oc->n_symbol_extras); diff --git a/ghc-powerpc-pthread.patch b/ghc-powerpc-pthread.patch deleted file mode 100644 index d317ff7..0000000 --- a/ghc-powerpc-pthread.patch +++ /dev/null @@ -1,18 +0,0 @@ -diff -up ghc-7.0.2/aclocal.m4.pthread ghc-7.0.2/aclocal.m4 ---- ghc-7.0.2/aclocal.m4.pthread 2011-02-28 13:10:03.000000000 -0500 -+++ ghc-7.0.2/aclocal.m4 2011-04-20 07:12:36.489772545 -0400 -@@ -1385,7 +1385,7 @@ AC_MSG_NOTICE(Building in-tree ghc-pwd) - dnl except we don't want to have to know what make is called. Sigh. - rm -rf utils/ghc-pwd/dist-boot - mkdir utils/ghc-pwd/dist-boot -- if ! "$WithGhc" -v0 -no-user-package-conf -hidir utils/ghc-pwd/dist-boot -odir utils/ghc-pwd/dist-boot -stubdir utils/ghc-pwd/dist-boot --make utils/ghc-pwd/Main.hs -o utils/ghc-pwd/dist-boot/ghc-pwd -+ if ! "$WithGhc" -optl-pthread -v0 -no-user-package-conf -hidir utils/ghc-pwd/dist-boot -odir utils/ghc-pwd/dist-boot -stubdir utils/ghc-pwd/dist-boot --make utils/ghc-pwd/Main.hs -o utils/ghc-pwd/dist-boot/ghc-pwd - then - AC_MSG_ERROR([Building ghc-pwd failed]) - fi -diff -up ghc-7.0.2/ghc/ghc.wrapper.pthread ghc-7.0.2/ghc/ghc.wrapper ---- ghc-7.0.2/ghc/ghc.wrapper.pthread 2011-04-20 09:58:50.307894773 -0400 -+++ ghc-7.0.2/ghc/ghc.wrapper 2011-04-20 09:59:14.477894370 -0400 -@@ -1 +1 @@ --exec "$executablename" -B"$topdir" -pgmc "$pgmgcc" -pgma "$pgmgcc" -pgml "$pgmgcc" -pgmP "$pgmgcc -E -undef -traditional" ${1+"$@"} -+exec "$executablename" -B"$topdir" -pgmc "$pgmgcc" -pgma "$pgmgcc" -pgml "$pgmgcc" -pgmP "$pgmgcc -E -undef -traditional" -optl-pthread ${1+"$@"} diff --git a/ghc-use-system-libffi.patch b/ghc-use-system-libffi.patch index 304bcb9..fb6d90a 100644 --- a/ghc-use-system-libffi.patch +++ b/ghc-use-system-libffi.patch @@ -1,10 +1,10 @@ This patch could be replaced by a configure call if http://hackage.haskell.org/trac/ghc/ticket/5743 were fixed. -Index: ghc-7.4.0.20111219/rts/package.conf.in +Index: ghc-7.6.1/rts/package.conf.in =================================================================== ---- ghc-7.4.0.20111219.orig/rts/package.conf.in 2011-12-21 23:21:03.000000000 +0100 -+++ ghc-7.4.0.20111219/rts/package.conf.in 2011-12-21 23:21:04.000000000 +0100 +--- ghc-7.6.1.orig/rts/package.conf.in 2012-09-04 19:10:15.000000000 +0200 ++++ ghc-7.6.1/rts/package.conf.in 2012-10-08 13:06:55.167887121 +0200 @@ -24,8 +24,9 @@ hs-libraries: "HSrts" @@ -16,48 +16,38 @@ Index: ghc-7.4.0.20111219/rts/package.conf.in #endif #ifdef HAVE_LIBRT , "rt" -Index: ghc-7.4.0.20111219/ghc.mk +Index: ghc-7.6.1/ghc.mk =================================================================== ---- ghc-7.4.0.20111219.orig/ghc.mk 2011-12-21 23:21:03.000000000 +0100 -+++ ghc-7.4.0.20111219/ghc.mk 2011-12-21 23:21:04.000000000 +0100 -@@ -579,7 +579,6 @@ - driver/ghci \ +--- ghc-7.6.1.orig/ghc.mk 2012-09-04 19:10:15.000000000 +0200 ++++ ghc-7.6.1/ghc.mk 2012-10-08 13:06:55.171887120 +0200 +@@ -600,7 +600,6 @@ + $(MAYBE_GHCI) \ driver/ghc \ driver/haddock \ - libffi \ includes \ rts -Index: ghc-7.4.0.20111219/rts/ghc.mk +Index: ghc-7.6.1/rts/ghc.mk =================================================================== ---- ghc-7.4.0.20111219.orig/rts/ghc.mk 2011-12-21 19:56:29.000000000 +0100 -+++ ghc-7.4.0.20111219/rts/ghc.mk 2011-12-21 23:23:52.000000000 +0100 -@@ -86,8 +86,7 @@ - ALL_RTS_DEF_LIBNAMES = base ghc-prim - ALL_RTS_DEF_LIBS = \ - rts/dist/build/win32/libHSbase.dll.a \ -- rts/dist/build/win32/libHSghc-prim.dll.a \ -- libffi/build/inst/lib/libffi.dll.a -+ rts/dist/build/win32/libHSghc-prim.dll.a - - # -- import libs for the regular Haskell libraries - define make-importlib-def # args $1 = lib name -@@ -172,12 +171,12 @@ +--- ghc-7.6.1.orig/rts/ghc.mk 2012-09-04 19:10:15.000000000 +0200 ++++ ghc-7.6.1/rts/ghc.mk 2012-10-08 13:08:52.019882891 +0200 +@@ -177,12 +177,12 @@ # Making a shared library for the RTS. ifneq "$$(findstring dyn, $1)" "" - ifeq "$$(HOSTPLATFORM)" "i386-unknown-mingw32" --$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(ALL_RTS_DEF_LIBS) rts/libs.depend rts/dist/build/libffi-5.dll + ifeq "$$(HostOS_CPP)" "mingw32" +-$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(ALL_RTS_DEF_LIBS) rts/libs.depend rts/dist/build/$$(LIBFFI_DLL) +$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(ALL_RTS_DEF_LIBS) rts/libs.depend "$$(RM)" $$(RM_OPTS) $$@ "$$(rts_dist_HC)" -package-name rts -shared -dynamic -dynload deploy \ - -no-auto-link-packages -Lrts/dist/build -lffi-5 `cat rts/libs.depend` $$(rts_$1_OBJS) $$(ALL_RTS_DEF_LIBS) -o $$@ + -no-auto-link-packages -Lrts/dist/build -l$(LIBFFI_WINDOWS_LIB) `cat rts/libs.depend` $$(rts_$1_OBJS) $$(ALL_RTS_DEF_LIBS) -o $$@ else -$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(rts_$1_DTRACE_OBJS) rts/libs.depend rts/dist/build/libffi$$(soext) +$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(rts_$1_DTRACE_OBJS) rts/libs.depend "$$(RM)" $$(RM_OPTS) $$@ "$$(rts_dist_HC)" -package-name rts -shared -dynamic -dynload deploy \ -no-auto-link-packages -Lrts/dist/build -lffi `cat rts/libs.depend` $$(rts_$1_OBJS) \ -@@ -188,9 +187,9 @@ +@@ -193,9 +193,9 @@ endif endif else @@ -69,12 +59,12 @@ Index: ghc-7.4.0.20111219/rts/ghc.mk $$(AR_OPTS_STAGE1) $$(EXTRA_AR_ARGS_STAGE1) $$@ endif -@@ -504,10 +503,8 @@ +@@ -509,10 +509,8 @@ # installing INSTALL_LIBS += $(ALL_RTS_LIBS) -INSTALL_LIBS += $(wildcard rts/dist/build/libffi$(soext)*) --INSTALL_LIBS += $(wildcard rts/dist/build/libffi-5.dll) +-INSTALL_LIBS += $(wildcard rts/dist/build/$(LIBFFI_DLL)) -install: install_libffi_headers +install: diff --git a/ghc.spec b/ghc.spec index 988509c..ec3af0c 100644 --- a/ghc.spec +++ b/ghc.spec @@ -2,10 +2,10 @@ # (disabled for other archs in ghc-rpm-macros) # To bootstrap build a new version of ghc, uncomment the following: -#%%global ghc_bootstrapping 1 -#%%{?ghc_bootstrap} -#%%global without_testsuite 1 -#%%global without_haddock 1 +%global ghc_bootstrapping 1 +%{?ghc_bootstrap} +%global without_testsuite 1 +%global without_haddock 1 # To do a test build instead with shared libs, uncomment the following: #%%global ghc_bootstrapping 1 @@ -24,25 +24,35 @@ Name: ghc # part of haskell-platform # ghc must be rebuilt after a version bump to avoid ABI change problems -Version: 7.4.2 +Version: 7.6.3 # Since library subpackages are versioned: -# - release can only be reset if all library versions get bumped simultaneously -# (eg for a major release) -# - minor release numbers should be incremented monotonically -Release: 11%{?dist} +# - 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: 11.9%{?dist} Summary: Glasgow Haskell Compiler -# fedora ghc has been bootstrapped on -# %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x -# see ghc_arches defined in /etc/rpm/macros.ghc-srpm by redhat-rpm-macros -ExcludeArch: sparc64 + License: %BSDHaskellReport +URL: http://haskell.org/ghc/ Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 %if %{undefined without_testsuite} Source2: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-testsuite.tar.bz2 %endif Source3: ghc-doc-index.cron Source4: ghc-doc-index -URL: http://haskell.org/ghc/ +# absolute haddock path (was for html/libraries -> libraries) +Patch1: ghc-gen_contents_index-haddock-path.patch +# fedora does not allow copy libraries +Patch4: ghc-use-system-libffi.patch +# add libffi include dir to ghc wrapper for archs using gcc/llc +Patch10: ghc-wrapper-libffi-include.patch +# disable building HS*.o libs for ghci +Patch12: ghc-7.4.2-Cabal-disable-ghci-libs.patch + +# fedora ghc has been bootstrapped on +# %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x +# see ghc_arches defined in /etc/rpm/macros.ghc-srpm by redhat-rpm-macros +ExcludeArch: sparc64 Obsoletes: ghc-dph-base < 0.5, ghc-dph-base-devel < 0.5, ghc-dph-base-prof < 0.5 Obsoletes: ghc-dph-par < 0.5, ghc-dph-par-devel < 0.5, ghc-dph-par-prof < 0.5 Obsoletes: ghc-dph-prim-interface < 0.5, ghc-dph-prim-interface-devel < 0.5, ghc-dph-interface-prim-prof < 0.5 @@ -53,7 +63,7 @@ Obsoletes: ghc-feldspar-language < 0.4, ghc-feldspar-language-devel < 0.4, ghc-f %if %{undefined ghc_bootstrapping} BuildRequires: ghc-compiler = %{version} %endif -BuildRequires: ghc-rpm-macros >= 0.91 +BuildRequires: ghc-rpm-macros-extra BuildRequires: ghc-bytestring-devel BuildRequires: ghc-containers-devel BuildRequires: ghc-directory-devel @@ -73,31 +83,10 @@ BuildRequires: python %ifarch armv7hl armv5tel BuildRequires: llvm >= 3.0 %endif -%ifarch armv7hl -BuildRequires: autoconf -%endif Requires: ghc-compiler = %{version}-%{release} Requires: ghc-doc-index = %{version}-%{release} Requires: ghc-libraries = %{version}-%{release} Requires: ghc-ghc-devel = %{version}-%{release} -# absolute haddock path (was for html/libraries -> libraries) -Patch1: ghc-6.12.1-gen_contents_index-haddock-path.patch -# type-level too big so skip it in gen_contents_index -Patch2: ghc-gen_contents_index-type-level.patch -# fedora does not allow copy libraries -Patch4: ghc-use-system-libffi.patch -Patch7: ghc-powerpc-pthread.patch -# http://hackage.haskell.org/trac/ghc/ticket/4999 -Patch8: ghc-powerpc-linker-mmap.patch -# fix dynamic linking of executables using Template Haskell -Patch9: Cabal-fix-dynamic-exec-for-TH.patch -# add libffi include dir to ghc wrapper for archs using gcc/llc -Patch10: ghc-wrapper-libffi-include.patch -# latest arm hf patch -Patch11: ghc-7.4-add-support-for-ARM-hard-float-ABI-fixes-5914.patch -# disable building HS*.o libs for ghci -Patch12: ghc-7.4.2-Cabal-disable-ghci-libs.patch -Patch17: ghc-7.4-silence-gen_contents_index.patch %description GHC is a state-of-the-art, open source, compiler and interactive environment @@ -161,31 +150,30 @@ documention. %global ghc_pkg_c_deps ghc-compiler = %{ghc_version_override}-%{release} %if %{defined ghclibdir} -%ghc_lib_subpackage Cabal 1.14.0 -%ghc_lib_subpackage -l %BSDHaskellReport array 0.4.0.0 -%ghc_lib_subpackage -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base 4.5.1.0 -%ghc_lib_subpackage binary 0.5.1.0 -%ghc_lib_subpackage bytestring 0.9.2.1 -%ghc_lib_subpackage -l %BSDHaskellReport containers 0.4.2.1 -%ghc_lib_subpackage -l %BSDHaskellReport deepseq 1.3.0.0 -%ghc_lib_subpackage -l %BSDHaskellReport directory 1.1.0.2 -%ghc_lib_subpackage -l %BSDHaskellReport extensible-exceptions 0.1.1.4 -%ghc_lib_subpackage filepath 1.3.0.0 +%ghc_lib_subpackage Cabal 1.16.0 +%ghc_lib_subpackage -l %BSDHaskellReport array 0.4.0.1 +%ghc_lib_subpackage -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base 4.6.0.1 +%ghc_lib_subpackage binary 0.5.1.1 +%ghc_lib_subpackage bytestring 0.10.0.2 +%ghc_lib_subpackage -l %BSDHaskellReport containers 0.5.0.0 +%ghc_lib_subpackage -l %BSDHaskellReport deepseq 1.3.0.1 +%ghc_lib_subpackage -l %BSDHaskellReport directory 1.2.0.1 +%ghc_lib_subpackage filepath 1.3.0.1 %define ghc_pkg_obsoletes ghc-bin-package-db-devel < 0.0.0.0-12 # in ghc not ghc-libraries: %ghc_lib_subpackage -x ghc %{ghc_version_override} %undefine ghc_pkg_obsoletes -%ghc_lib_subpackage -l HaskellReport haskell2010 1.1.0.1 -%ghc_lib_subpackage -l HaskellReport haskell98 2.0.0.1 -%ghc_lib_subpackage hoopl 3.8.7.3 -%ghc_lib_subpackage hpc 0.5.1.1 -%ghc_lib_subpackage -l %BSDHaskellReport old-locale 1.0.0.4 -%ghc_lib_subpackage -l %BSDHaskellReport old-time 1.1.0.0 +%ghc_lib_subpackage -l HaskellReport haskell2010 1.1.1.0 +%ghc_lib_subpackage -l HaskellReport haskell98 2.0.0.2 +%ghc_lib_subpackage hoopl 3.9.0.0 +%ghc_lib_subpackage hpc 0.6.0.0 +%ghc_lib_subpackage -l %BSDHaskellReport old-locale 1.0.0.5 +%ghc_lib_subpackage -l %BSDHaskellReport old-time 1.1.0.1 %ghc_lib_subpackage pretty 1.1.1.0 -%ghc_lib_subpackage -l %BSDHaskellReport process 1.1.0.1 -%ghc_lib_subpackage template-haskell 2.7.0.0 -%ghc_lib_subpackage time 1.4 -%ghc_lib_subpackage unix 2.5.1.1 +%ghc_lib_subpackage -l %BSDHaskellReport process 1.1.0.2 +%ghc_lib_subpackage template-haskell 2.8.0.0 +%ghc_lib_subpackage time 1.4.0.1 +%ghc_lib_subpackage unix 2.6.0.1 %endif %global version %{ghc_version_override} @@ -206,37 +194,28 @@ Obsoletes: ghc-libs < 7.0.1-3 This is a meta-package for all the development library packages in GHC except the ghc library, which is installed by the toplevel ghc metapackage. + %prep %setup -q -n %{name}-%{version} %{!?without_testsuite:-b2} -# tweaks to gen_contents_index +# gen_contents_index: use absolute path for haddock %patch1 -p1 -b .orig -%patch2 -p1 -%patch17 -p1 # make sure we don't use these -rm -r ghc-tarballs/{mingw,perl} +rm -r ghc-tarballs/{mingw*,perl} # use system libffi %patch4 -p1 -b .libffi rm -r ghc-tarballs/libffi mkdir -p rts/dist/build ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build -%patch9 -p1 -b .orig - %ifnarch %{ix86} x86_64 %patch10 -p1 -b .10-ffi %endif -# ARM patches -%ifarch armv7hl -# touches aclocal.m4 -%patch11 -p1 -b .arm -autoreconf -%endif - %patch12 -p1 -b .orig + %build # http://hackage.haskell.org/trac/ghc/wiki/Platforms # cf https://github.com/gentoo-haskell/gentoo-haskell/tree/master/dev-lang/ghc @@ -261,6 +240,7 @@ export CFLAGS="${CFLAGS:-%optflags}" make %{?_smp_mflags} + %install make DESTDIR=%{buildroot} install @@ -268,21 +248,19 @@ for i in %{ghc_packages_list}; do name=$(echo $i | sed -e "s/\(.*\)-.*/\1/") ver=$(echo $i | sed -e "s/.*-\(.*\)/\1/") %ghc_gen_filelists $name $ver -echo "%doc libraries/$name/LICENSE" >> ghc-$name%{?ghc_without_shared:-devel}.files +echo "%doc libraries/$name/LICENSE" >> ghc-$name.files done # ghc-base should own ghclibdir -echo "%dir %{ghclibdir}" >> ghc-base%{?ghc_without_shared:-devel}.files +echo "%dir %{ghclibdir}" >> ghc-base.files %ghc_gen_filelists bin-package-db 0.0.0.0 %ghc_gen_filelists ghc %{ghc_version_override} -%ghc_gen_filelists ghc-prim 0.2.0.0 -%ghc_gen_filelists integer-gmp 0.4.0.0 +%ghc_gen_filelists ghc-prim 0.3.0.0 +%ghc_gen_filelists integer-gmp 0.5.0.0 %define merge_filelist()\ -%if %{undefined ghc_without_shared}\ cat ghc-%1.files >> ghc-%2.files\ -%endif\ cat ghc-%1-devel.files >> ghc-%2-devel.files\ cp -p libraries/%1/LICENSE libraries/LICENSE.%1\ echo "%doc libraries/LICENSE.%1" >> ghc-%2.files @@ -318,6 +296,7 @@ mkdir -p %{buildroot}%{_localstatedir}/lib/ghc install -p --mode=0755 %SOURCE4 %{buildroot}%{_bindir}/ghc-doc-index %endif + %check # stolen from ghc6/debian/rules: # Do some very simple tests that the compiler actually works @@ -343,6 +322,7 @@ rm testghc/* make test %endif + %post compiler # Alas, GHC, Hugs, and nhc all come with different set of tools in # addition to a runFOO: @@ -367,6 +347,7 @@ if [ "$1" = 0 ]; then update-alternatives --remove hsc2hs %{_bindir}/hsc2hs-ghc fi + %files %files compiler @@ -381,7 +362,7 @@ fi %{_bindir}/hpc %ghost %{_bindir}/hsc2hs %{_bindir}/hsc2hs-ghc -%{_bindir}/runghc +%{_bindir}/runghc* %ghost %{_bindir}/runhaskell %{_bindir}/runhaskell-ghc %{ghclibdir}/ghc @@ -417,9 +398,10 @@ fi %dir %{ghcdocbasedir}/libraries %{ghcdocbasedir}/libraries/frames.html %{ghcdocbasedir}/libraries/gen_contents_index -%{ghcdocbasedir}/libraries/hscolour.css +%{ghcdocbasedir}/libraries/hslogo-16.png %{ghcdocbasedir}/libraries/ocean.css %{ghcdocbasedir}/libraries/prologue.txt +%{ghcdocbasedir}/libraries/synopsis.png %{ghcdocbasedir}/index.html %ghost %{ghcdocbasedir}/libraries/doc-index*.html %ghost %{ghcdocbasedir}/libraries/haddock-util.js @@ -436,7 +418,20 @@ fi %files libraries + %changelog +* Mon Apr 22 2013 Jens Petersen - 7.6.3-11.9 +- bootstrap 7.6.3, see release notes: + http://www.haskell.org/ghc/docs/7.6.3/html/users_guide/release-7-6-1.html + http://www.haskell.org/ghc/docs/7.6.3/html/users_guide/release-7-6-2.html + http://www.haskell.org/ghc/docs/7.6.3/html/users_guide/release-7-6-3.html +- all library versions bumped except pretty +- Cabal-fix-dynamic-exec-for-TH.patch, + ghc-7.4-add-support-for-ARM-hard-float-ABI-fixes-5914.patch, and + ghc-7.4-silence-gen_contents_index.patch are no longer needed +- build with ghc-rpm-macros-extra +- no longer filter type-level package from haddock index + * Tue Feb 5 2013 Jens Petersen - 7.4.2-11 - ghclibdir should be owned at runtime by ghc-base instead of ghc-compiler (thanks Michael Scherer, #907671) diff --git a/sources b/sources index 46b12d9..40df58f 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -267462db5c5a7c245fb26361b77007c4 ghc-7.4.2-src.tar.bz2 -528005749c761fe6c12a0079bd84fb90 ghc-7.4.2-testsuite.tar.bz2 +986d1f90ca30d60f7b2820d75c6b8ea7 ghc-7.6.3-src.tar.bz2 +66aa6177a31cc4b9d7eeb55cb1514918 ghc-7.6.3-testsuite.tar.bz2