Accepting request 430761 from devel:languages:haskell:lts:7

update devel:languages:haskell to LTS 7.x

OBS-URL: https://build.opensuse.org/request/show/430761
OBS-URL: https://build.opensuse.org/package/show/devel:languages:haskell/ghc?expand=0&rev=227
This commit is contained in:
Peter Simons 2016-09-28 10:48:25 +00:00 committed by Git OBS Bridge
parent 7313e05346
commit 8e32665755
19 changed files with 128 additions and 5305 deletions

View File

@ -1,71 +0,0 @@
From 4f52849a99753fab63d634769dd35a31f4d5a1b2 Mon Sep 17 00:00:00 2001
From: Herbert Valerio Riedel <hvr@gnu.org>
Date: Thu, 12 May 2016 20:36:34 +0200
Subject: [PATCH] Fix misspelled WORDS_BIGENDIAN macro
This was causing word{16,32,64}{le,be} primitives to break
on big endian archs (such as `powerpc`/`powerpc64`) with
serious consequences such as
https://github.com/TomMD/pureMD5/issues/5
---
Data/ByteString/Builder/Prim/Binary.hs | 12 ++++++------
1 file changed, 6 insertions(+), 6 deletions(-)
Index: ghc-8.0.1/libraries/bytestring/Data/ByteString/Builder/Prim/Binary.hs
===================================================================
--- ghc-8.0.1.orig/libraries/bytestring/Data/ByteString/Builder/Prim/Binary.hs
+++ ghc-8.0.1/libraries/bytestring/Data/ByteString/Builder/Prim/Binary.hs
@@ -83,7 +83,7 @@ word8 = storableToF
-- | Encoding 'Word16's in big endian format.
{-# INLINE word16BE #-}
word16BE :: FixedPrim Word16
-#ifdef WORD_BIGENDIAN
+#ifdef WORDS_BIGENDIAN
word16BE = word16Host
#else
word16BE = fixedPrim 2 $ \w p -> do
@@ -94,7 +94,7 @@ word16BE = fixedPrim 2 $ \w p -> do
-- | Encoding 'Word16's in little endian format.
{-# INLINE word16LE #-}
word16LE :: FixedPrim Word16
-#ifdef WORD_BIGENDIAN
+#ifdef WORDS_BIGENDIAN
word16LE = fixedPrim 2 $ \w p -> do
poke p (fromIntegral (w) :: Word8)
poke (p `plusPtr` 1) (fromIntegral (shiftr_w16 w 8) :: Word8)
@@ -105,7 +105,7 @@ word16LE = word16Host
-- | Encoding 'Word32's in big endian format.
{-# INLINE word32BE #-}
word32BE :: FixedPrim Word32
-#ifdef WORD_BIGENDIAN
+#ifdef WORDS_BIGENDIAN
word32BE = word32Host
#else
word32BE = fixedPrim 4 $ \w p -> do
@@ -118,7 +118,7 @@ word32BE = fixedPrim 4 $ \w p -> do
-- | Encoding 'Word32's in little endian format.
{-# INLINE word32LE #-}
word32LE :: FixedPrim Word32
-#ifdef WORD_BIGENDIAN
+#ifdef WORDS_BIGENDIAN
word32LE = fixedPrim 4 $ \w p -> do
poke p (fromIntegral (w) :: Word8)
poke (p `plusPtr` 1) (fromIntegral (shiftr_w32 w 8) :: Word8)
@@ -134,7 +134,7 @@ word32LE = word32Host
-- | Encoding 'Word64's in big endian format.
{-# INLINE word64BE #-}
word64BE :: FixedPrim Word64
-#ifdef WORD_BIGENDIAN
+#ifdef WORDS_BIGENDIAN
word64BE = word64Host
#else
#if WORD_SIZE_IN_BITS < 64
@@ -170,7 +170,7 @@ word64BE = fixedPrim 8 $ \w p -> do
-- | Encoding 'Word64's in little endian format.
{-# INLINE word64LE #-}
word64LE :: FixedPrim Word64
-#ifdef WORD_BIGENDIAN
+#ifdef WORDS_BIGENDIAN
#if WORD_SIZE_IN_BITS < 64
word64LE =
fixedPrim 8 $ \w p -> do

View File

@ -1,22 +0,0 @@
From ff48b3e3fd90e0328921f5e86460aba3ff217002 Mon Sep 17 00:00:00 2001
From: Peter Trommler <ptrommler@acm.org>
Date: Mon, 25 Jan 2016 20:32:44 +0100
Subject: [PATCH] PPC/CodeGen: fix lwa instruction generation
---
compiler/nativeGen/PPC/CodeGen.hs | 2 +-
1 file changed, 1 insertion(+), 1 deletion(-)
Index: ghc-7.10.3/compiler/nativeGen/PPC/CodeGen.hs
===================================================================
--- ghc-7.10.3.orig/compiler/nativeGen/PPC/CodeGen.hs
+++ ghc-7.10.3/compiler/nativeGen/PPC/CodeGen.hs
@@ -464,7 +464,7 @@ getRegister' _ (CmmMachOp (MO_UU_Conv W3
return (Any II64 (\dst -> addr_code `snocOL` LD II32 dst addr))
getRegister' _ (CmmMachOp (MO_SS_Conv W32 W64) [CmmLoad mem _]) = do
- Amode addr addr_code <- getAmode D mem
+ Amode addr addr_code <- getAmode DS mem -- lwa is DS-form
return (Any II64 (\dst -> addr_code `snocOL` LA II32 dst addr))
getRegister' dflags (CmmMachOp mop [x]) -- unary MachOps

View File

@ -7,11 +7,11 @@ Subject: [PATCH] StgCmmPrim: Add missing write barrier.
compiler/codeGen/StgCmmPrim.hs | 1 +
1 file changed, 1 insertion(+)
Index: ghc-7.10.3/compiler/codeGen/StgCmmPrim.hs
Index: ghc-8.0.1/compiler/codeGen/StgCmmPrim.hs
===================================================================
--- ghc-7.10.3.orig/compiler/codeGen/StgCmmPrim.hs
+++ ghc-7.10.3/compiler/codeGen/StgCmmPrim.hs
@@ -1324,6 +1324,7 @@ doWritePtrArrayOp addr idx val
--- ghc-8.0.1.orig/compiler/codeGen/StgCmmPrim.hs
+++ ghc-8.0.1/compiler/codeGen/StgCmmPrim.hs
@@ -1353,6 +1353,7 @@ doWritePtrArrayOp addr idx val
emit (setInfo addr (CmmLit (CmmLabel mkMAP_DIRTY_infoLabel)))
-- the write barrier. We must write a byte into the mark table:
-- bits8[a + header_size + StgMutArrPtrs_size(a) + x >> N]

File diff suppressed because it is too large Load Diff

View File

@ -1,58 +0,0 @@
From 4177e22ecf45b33758d19780dbf4ab32fed6cbac Mon Sep 17 00:00:00 2001
From: Peter Trommler <peter.trommler@th-nuernberg.de>
Date: Mon, 14 Dec 2015 19:16:22 +0100
Subject: [PATCH 1/1] link command line libs to temp so
Symbols in libraries specified on the GHCis command line are
not available to compiled modules because shared libraries
are loaded with local scope. So we link all libraries specified
on the command line into each temporary shared library.
---
compiler/ghci/Linker.hs | 15 ++++++++++++++-
1 file changed, 14 insertions(+), 1 deletion(-)
Index: ghc-7.10.3/compiler/ghci/Linker.hs
===================================================================
--- ghc-7.10.3.orig/compiler/ghci/Linker.hs
+++ ghc-7.10.3/compiler/ghci/Linker.hs
@@ -818,11 +818,14 @@ dynLoadObjs :: DynFlags -> PersistentLin
dynLoadObjs _ pls [] = return pls
dynLoadObjs dflags pls objs = do
let platform = targetPlatform dflags
+ let minus_ls = [ lib | Option ('-':'l':lib) <- ldInputs dflags ]
+ let minus_big_ls = [ lib | Option ('-':'L':lib) <- ldInputs dflags ]
(soFile, libPath , libName) <- newTempLibName dflags (soExt platform)
let -- When running TH for a non-dynamic way, we still need to make
-- -l flags to link against the dynamic libraries, so we turn
-- Opt_Static off
dflags1 = gopt_unset dflags Opt_Static
+
dflags2 = dflags1 {
-- We don't want the original ldInputs in
-- (they're already linked in), but we do want
@@ -838,7 +841,16 @@ dynLoadObjs dflags pls objs = do
, Option ("-Wl," ++ lp)
, Option ("-l" ++ l)
])
- (temp_sos pls),
+ (temp_sos pls)
+ ++ concatMap
+ (\lp ->
+ [ Option ("-L" ++ lp)
+ , Option ("-Wl,-rpath")
+ , Option ("-Wl," ++ lp)
+ ])
+ minus_big_ls
+ ++ map (\l -> Option ("-l" ++ l)) minus_ls,
+ -- add -l options and -L options from dflags
-- Even if we're e.g. profiling, we still want
-- the vanilla dynamic libraries, so we set the
-- ways / build tag to be just WayDyn.
@@ -1031,6 +1043,7 @@ data LibrarySpec
| Framework String -- Only used for darwin, but does no harm
+
-- If this package is already part of the GHCi binary, we'll already
-- have the right DLLs for this package loaded, so don't try to
-- load them again.

View File

@ -1,16 +0,0 @@
Index: ghc-7.10.3/compiler/nativeGen/PPC/Ppr.hs
===================================================================
--- ghc-7.10.3.orig/compiler/nativeGen/PPC/Ppr.hs
+++ ghc-7.10.3/compiler/nativeGen/PPC/Ppr.hs
@@ -488,9 +488,10 @@ pprInstr (STU sz reg addr) = hcat [
char '\t',
ptext (sLit "st"),
pprSize sz,
- ptext (sLit "u\t"),
+ char 'u',
case addr of AddrRegImm _ _ -> empty
AddrRegReg _ _ -> char 'x',
+ char '\t',
pprReg reg,
ptext (sLit ", "),
pprAddr addr

View File

@ -1,92 +0,0 @@
Index: ghc-7.10.3/includes/stg/SMP.h
===================================================================
--- ghc-7.10.3.orig/includes/stg/SMP.h
+++ ghc-7.10.3/includes/stg/SMP.h
@@ -119,22 +119,8 @@ xchg(StgPtr p, StgWord w)
:"+r" (result), "+m" (*p)
: /* no input-only operands */
);
-#elif powerpc_HOST_ARCH
- __asm__ __volatile__ (
- "1: lwarx %0, 0, %2\n"
- " stwcx. %1, 0, %2\n"
- " bne- 1b"
- :"=&r" (result)
- :"r" (w), "r" (p)
- );
-#elif powerpc64_HOST_ARCH || powerpc64le_HOST_ARCH
- __asm__ __volatile__ (
- "1: ldarx %0, 0, %2\n"
- " stdcx. %1, 0, %2\n"
- " bne- 1b"
- :"=&r" (result)
- :"r" (w), "r" (p)
- );
+#elif powerpc_HOST_ARCH || powerpc64_HOST_ARCH || powerpc64le_HOST_ARCH
+ result = __sync_lock_test_and_set(p, w);
#elif sparc_HOST_ARCH
result = w;
__asm__ __volatile__ (
@@ -202,34 +188,8 @@ cas(StgVolatilePtr p, StgWord o, StgWord
:"=a"(o), "+m" (*(volatile unsigned int *)p)
:"0" (o), "r" (n));
return o;
-#elif powerpc_HOST_ARCH
- StgWord result;
- __asm__ __volatile__ (
- "1: lwarx %0, 0, %3\n"
- " cmpw %0, %1\n"
- " bne 2f\n"
- " stwcx. %2, 0, %3\n"
- " bne- 1b\n"
- "2:"
- :"=&r" (result)
- :"r" (o), "r" (n), "r" (p)
- :"cc", "memory"
- );
- return result;
-#elif powerpc64_HOST_ARCH || powerpc64le_HOST_ARCH
- StgWord result;
- __asm__ __volatile__ (
- "1: ldarx %0, 0, %3\n"
- " cmpd %0, %1\n"
- " bne 2f\n"
- " stdcx. %2, 0, %3\n"
- " bne- 1b\n"
- "2:"
- :"=&r" (result)
- :"r" (o), "r" (n), "r" (p)
- :"cc", "memory"
- );
- return result;
+#elif powerpc_HOST_ARCH || powerpc64_HOST_ARCH || powerpc64le_HOST_ARCH
+ return __sync_val_compare_and_swap(p, o, n);
#elif sparc_HOST_ARCH
__asm__ __volatile__ (
"cas [%1], %2, %0"
@@ -290,6 +250,7 @@ cas(StgVolatilePtr p, StgWord o, StgWord
// RRN: Generalized to arbitrary increments to enable fetch-and-add in
// Haskell code (fetchAddIntArray#).
+// PT: add-and-fetch, returns new value
EXTERN_INLINE StgWord
atomic_inc(StgVolatilePtr p, StgWord incr)
{
@@ -301,6 +262,8 @@ atomic_inc(StgVolatilePtr p, StgWord inc
"+r" (r), "+m" (*p):
);
return r + incr;
+#elif powerpc_HOST_ARCH || powerpc64_HOST_ARCH || powerpc64le_HOST_ARCH
+ return __sync_add_and_fetch(p, incr);
#else
StgWord old, new_;
do {
@@ -322,6 +285,8 @@ atomic_dec(StgVolatilePtr p)
"+r" (r), "+m" (*p):
);
return r-1;
+#elif powerpc_HOST_ARCH || powerpc64_HOST_ARCH || powerpc64le_HOST_ARCH
+ return __sync_sub_and_fetch(p, (StgWord) 1);
#else
StgWord old, new_;
do {

View File

@ -1,546 +0,0 @@
From e3d2bab86fc89113f8ee65800fdfac81d8d54851 Mon Sep 17 00:00:00 2001
From: Andreas Schwab <schwab@suse.de>
Date: Fri, 2 Oct 2015 23:03:12 +0200
Subject: [PATCH] Fix signature of atomic builtins
This patch is due to Andreas Schwab.
This fixes #10926, which reports (on AArch64) errors of the form,
```
/tmp/ghc1492_0/ghc_1.hc:2844:25: warning: passing argument 1 of
'hs_atomic_xor64' makes pointer from integer without a cast
[-Wint-conversion]
_c1Ho = hs_atomic_xor64((*Sp) + (((Sp[1]) << 0x3UL) + 0x10UL), Sp[2]);
^
In file included from
/home/abuild/rpmbuild/BUILD/ghc-7.10.2/includes/Stg.h:273:0: 0,
from /tmp/ghc1492_0/ghc_1.hc:3:
/home/abuild/rpmbuild/BUILD/ghc-7.10.2/includes/stg/Prim.h:41:11:
note: expected 'volatile StgWord64 *
{aka volatile long unsigned int *}'
but argument is of type 'long unsigned int'
StgWord64 hs_atomic_xor64(volatile StgWord64 *x, StgWord64 val);
^
```
Test Plan: Validate
Reviewers: austin, simonmar
Reviewed By: simonmar
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1300
GHC Trac Issues: #10926
---
includes/stg/Prim.h | 72 ++++++------
libraries/ghc-prim/cbits/atomic.c | 224 +++++++++++++++++++-------------------
2 files changed, 148 insertions(+), 148 deletions(-)
Index: ghc-7.10.2.20151105/includes/stg/Prim.h
===================================================================
--- ghc-7.10.2.20151105.orig/includes/stg/Prim.h
+++ ghc-7.10.2.20151105/includes/stg/Prim.h
@@ -15,42 +15,42 @@
#define PRIM_H
/* libraries/ghc-prim/cbits/atomic.c */
-StgWord hs_atomic_add8(volatile StgWord8 *x, StgWord val);
-StgWord hs_atomic_add16(volatile StgWord16 *x, StgWord val);
-StgWord hs_atomic_add32(volatile StgWord32 *x, StgWord val);
-StgWord64 hs_atomic_add64(volatile StgWord64 *x, StgWord64 val);
-StgWord hs_atomic_sub8(volatile StgWord8 *x, StgWord val);
-StgWord hs_atomic_sub16(volatile StgWord16 *x, StgWord val);
-StgWord hs_atomic_sub32(volatile StgWord32 *x, StgWord val);
-StgWord64 hs_atomic_sub64(volatile StgWord64 *x, StgWord64 val);
-StgWord hs_atomic_and8(volatile StgWord8 *x, StgWord val);
-StgWord hs_atomic_and16(volatile StgWord16 *x, StgWord val);
-StgWord hs_atomic_and32(volatile StgWord32 *x, StgWord val);
-StgWord64 hs_atomic_and64(volatile StgWord64 *x, StgWord64 val);
-StgWord hs_atomic_nand8(volatile StgWord8 *x, StgWord val);
-StgWord hs_atomic_nand16(volatile StgWord16 *x, StgWord val);
-StgWord hs_atomic_nand32(volatile StgWord32 *x, StgWord val);
-StgWord64 hs_atomic_nand64(volatile StgWord64 *x, StgWord64 val);
-StgWord hs_atomic_or8(volatile StgWord8 *x, StgWord val);
-StgWord hs_atomic_or16(volatile StgWord16 *x, StgWord val);
-StgWord hs_atomic_or32(volatile StgWord32 *x, StgWord val);
-StgWord64 hs_atomic_or64(volatile StgWord64 *x, StgWord64 val);
-StgWord hs_atomic_xor8(volatile StgWord8 *x, StgWord val);
-StgWord hs_atomic_xor16(volatile StgWord16 *x, StgWord val);
-StgWord hs_atomic_xor32(volatile StgWord32 *x, StgWord val);
-StgWord64 hs_atomic_xor64(volatile StgWord64 *x, StgWord64 val);
-StgWord hs_cmpxchg8(volatile StgWord8 *x, StgWord old, StgWord new_);
-StgWord hs_cmpxchg16(volatile StgWord16 *x, StgWord old, StgWord new_);
-StgWord hs_cmpxchg32(volatile StgWord32 *x, StgWord old, StgWord new_);
-StgWord hs_cmpxchg64(volatile StgWord64 *x, StgWord64 old, StgWord64 new_);
-StgWord hs_atomicread8(volatile StgWord8 *x);
-StgWord hs_atomicread16(volatile StgWord16 *x);
-StgWord hs_atomicread32(volatile StgWord32 *x);
-StgWord64 hs_atomicread64(volatile StgWord64 *x);
-void hs_atomicwrite8(volatile StgWord8 *x, StgWord val);
-void hs_atomicwrite16(volatile StgWord16 *x, StgWord val);
-void hs_atomicwrite32(volatile StgWord32 *x, StgWord val);
-void hs_atomicwrite64(volatile StgWord64 *x, StgWord64 val);
+StgWord hs_atomic_add8(StgWord x, StgWord val);
+StgWord hs_atomic_add16(StgWord x, StgWord val);
+StgWord hs_atomic_add32(StgWord x, StgWord val);
+StgWord64 hs_atomic_add64(StgWord x, StgWord64 val);
+StgWord hs_atomic_sub8(StgWord x, StgWord val);
+StgWord hs_atomic_sub16(StgWord x, StgWord val);
+StgWord hs_atomic_sub32(StgWord x, StgWord val);
+StgWord64 hs_atomic_sub64(StgWord x, StgWord64 val);
+StgWord hs_atomic_and8(StgWord x, StgWord val);
+StgWord hs_atomic_and16(StgWord x, StgWord val);
+StgWord hs_atomic_and32(StgWord x, StgWord val);
+StgWord64 hs_atomic_and64(StgWord x, StgWord64 val);
+StgWord hs_atomic_nand8(StgWord x, StgWord val);
+StgWord hs_atomic_nand16(StgWord x, StgWord val);
+StgWord hs_atomic_nand32(StgWord x, StgWord val);
+StgWord64 hs_atomic_nand64(StgWord x, StgWord64 val);
+StgWord hs_atomic_or8(StgWord x, StgWord val);
+StgWord hs_atomic_or16(StgWord x, StgWord val);
+StgWord hs_atomic_or32(StgWord x, StgWord val);
+StgWord64 hs_atomic_or64(StgWord x, StgWord64 val);
+StgWord hs_atomic_xor8(StgWord x, StgWord val);
+StgWord hs_atomic_xor16(StgWord x, StgWord val);
+StgWord hs_atomic_xor32(StgWord x, StgWord val);
+StgWord64 hs_atomic_xor64(StgWord x, StgWord64 val);
+StgWord hs_cmpxchg8(StgWord x, StgWord old, StgWord new_);
+StgWord hs_cmpxchg16(StgWord x, StgWord old, StgWord new_);
+StgWord hs_cmpxchg32(StgWord x, StgWord old, StgWord new_);
+StgWord hs_cmpxchg64(StgWord64 x, StgWord64 old, StgWord64 new_);
+StgWord hs_atomicread8(StgWord x);
+StgWord hs_atomicread16(StgWord x);
+StgWord hs_atomicread32(StgWord x);
+StgWord64 hs_atomicread64(StgWord x);
+void hs_atomicwrite8(StgWord x, StgWord val);
+void hs_atomicwrite16(StgWord x, StgWord val);
+void hs_atomicwrite32(StgWord x, StgWord val);
+void hs_atomicwrite64(StgWord x, StgWord64 val);
/* libraries/ghc-prim/cbits/bswap.c */
StgWord16 hs_bswap16(StgWord16 x);
Index: ghc-7.10.2.20151105/libraries/ghc-prim/cbits/atomic.c
===================================================================
--- ghc-7.10.2.20151105.orig/libraries/ghc-prim/cbits/atomic.c
+++ ghc-7.10.2.20151105/libraries/ghc-prim/cbits/atomic.c
@@ -11,97 +11,97 @@
// FetchAddByteArrayOp_Int
-extern StgWord hs_atomic_add8(volatile StgWord8 *x, StgWord val);
+extern StgWord hs_atomic_add8(StgWord x, StgWord val);
StgWord
-hs_atomic_add8(volatile StgWord8 *x, StgWord val)
+hs_atomic_add8(StgWord x, StgWord val)
{
- return __sync_fetch_and_add(x, (StgWord8) val);
+ return __sync_fetch_and_add((volatile StgWord8 *) x, (StgWord8) val);
}
-extern StgWord hs_atomic_add16(volatile StgWord16 *x, StgWord val);
+extern StgWord hs_atomic_add16(StgWord x, StgWord val);
StgWord
-hs_atomic_add16(volatile StgWord16 *x, StgWord val)
+hs_atomic_add16(StgWord x, StgWord val)
{
- return __sync_fetch_and_add(x, (StgWord16) val);
+ return __sync_fetch_and_add((volatile StgWord16 *) x, (StgWord16) val);
}
-extern StgWord hs_atomic_add32(volatile StgWord32 *x, StgWord val);
+extern StgWord hs_atomic_add32(StgWord x, StgWord val);
StgWord
-hs_atomic_add32(volatile StgWord32 *x, StgWord val)
+hs_atomic_add32(StgWord x, StgWord val)
{
- return __sync_fetch_and_add(x, (StgWord32) val);
+ return __sync_fetch_and_add((volatile StgWord32 *) x, (StgWord32) val);
}
#if WORD_SIZE_IN_BITS == 64
-extern StgWord64 hs_atomic_add64(volatile StgWord64 *x, StgWord64 val);
+extern StgWord64 hs_atomic_add64(StgWord x, StgWord64 val);
StgWord64
-hs_atomic_add64(volatile StgWord64 *x, StgWord64 val)
+hs_atomic_add64(StgWord x, StgWord64 val)
{
- return __sync_fetch_and_add(x, val);
+ return __sync_fetch_and_add((volatile StgWord64 *) x, val);
}
#endif
// FetchSubByteArrayOp_Int
-extern StgWord hs_atomic_sub8(volatile StgWord8 *x, StgWord val);
+extern StgWord hs_atomic_sub8(StgWord x, StgWord val);
StgWord
-hs_atomic_sub8(volatile StgWord8 *x, StgWord val)
+hs_atomic_sub8(StgWord x, StgWord val)
{
- return __sync_fetch_and_sub(x, (StgWord8) val);
+ return __sync_fetch_and_sub((volatile StgWord8 *) x, (StgWord8) val);
}
-extern StgWord hs_atomic_sub16(volatile StgWord16 *x, StgWord val);
+extern StgWord hs_atomic_sub16(StgWord x, StgWord val);
StgWord
-hs_atomic_sub16(volatile StgWord16 *x, StgWord val)
+hs_atomic_sub16(StgWord x, StgWord val)
{
- return __sync_fetch_and_sub(x, (StgWord16) val);
+ return __sync_fetch_and_sub((volatile StgWord16 *) x, (StgWord16) val);
}
-extern StgWord hs_atomic_sub32(volatile StgWord32 *x, StgWord val);
+extern StgWord hs_atomic_sub32(StgWord x, StgWord val);
StgWord
-hs_atomic_sub32(volatile StgWord32 *x, StgWord val)
+hs_atomic_sub32(StgWord x, StgWord val)
{
- return __sync_fetch_and_sub(x, (StgWord32) val);
+ return __sync_fetch_and_sub((volatile StgWord32 *) x, (StgWord32) val);
}
#if WORD_SIZE_IN_BITS == 64
-extern StgWord64 hs_atomic_sub64(volatile StgWord64 *x, StgWord64 val);
+extern StgWord64 hs_atomic_sub64(StgWord x, StgWord64 val);
StgWord64
-hs_atomic_sub64(volatile StgWord64 *x, StgWord64 val)
+hs_atomic_sub64(StgWord x, StgWord64 val)
{
- return __sync_fetch_and_sub(x, val);
+ return __sync_fetch_and_sub((volatile StgWord64 *) x, val);
}
#endif
// FetchAndByteArrayOp_Int
-extern StgWord hs_atomic_and8(volatile StgWord8 *x, StgWord val);
+extern StgWord hs_atomic_and8(StgWord x, StgWord val);
StgWord
-hs_atomic_and8(volatile StgWord8 *x, StgWord val)
+hs_atomic_and8(StgWord x, StgWord val)
{
- return __sync_fetch_and_and(x, (StgWord8) val);
+ return __sync_fetch_and_and((volatile StgWord8 *) x, (StgWord8) val);
}
-extern StgWord hs_atomic_and16(volatile StgWord16 *x, StgWord val);
+extern StgWord hs_atomic_and16(StgWord x, StgWord val);
StgWord
-hs_atomic_and16(volatile StgWord16 *x, StgWord val)
+hs_atomic_and16(StgWord x, StgWord val)
{
- return __sync_fetch_and_and(x, (StgWord16) val);
+ return __sync_fetch_and_and((volatile StgWord16 *) x, (StgWord16) val);
}
-extern StgWord hs_atomic_and32(volatile StgWord32 *x, StgWord val);
+extern StgWord hs_atomic_and32(StgWord x, StgWord val);
StgWord
-hs_atomic_and32(volatile StgWord32 *x, StgWord val)
+hs_atomic_and32(StgWord x, StgWord val)
{
- return __sync_fetch_and_and(x, (StgWord32) val);
+ return __sync_fetch_and_and((volatile StgWord32 *) x, (StgWord32) val);
}
#if WORD_SIZE_IN_BITS == 64
-extern StgWord64 hs_atomic_and64(volatile StgWord64 *x, StgWord64 val);
+extern StgWord64 hs_atomic_and64(StgWord x, StgWord64 val);
StgWord64
-hs_atomic_and64(volatile StgWord64 *x, StgWord64 val)
+hs_atomic_and64(StgWord x, StgWord64 val)
{
- return __sync_fetch_and_and(x, val);
+ return __sync_fetch_and_and((volatile StgWord64 *) x, val);
}
#endif
@@ -117,204 +117,204 @@ hs_atomic_and64(volatile StgWord64 *x, S
return tmp; \
}
-extern StgWord hs_atomic_nand8(volatile StgWord8 *x, StgWord val);
+extern StgWord hs_atomic_nand8(StgWord x, StgWord val);
StgWord
-hs_atomic_nand8(volatile StgWord8 *x, StgWord val)
+hs_atomic_nand8(StgWord x, StgWord val)
{
#ifdef __clang__
- CAS_NAND(x, (StgWord8) val)
+ CAS_NAND((volatile StgWord8 *) x, (StgWord8) val)
#else
- return __sync_fetch_and_nand(x, (StgWord8) val);
+ return __sync_fetch_and_nand((volatile StgWord8 *) x, (StgWord8) val);
#endif
}
-extern StgWord hs_atomic_nand16(volatile StgWord16 *x, StgWord val);
+extern StgWord hs_atomic_nand16(StgWord x, StgWord val);
StgWord
-hs_atomic_nand16(volatile StgWord16 *x, StgWord val)
+hs_atomic_nand16(StgWord x, StgWord val)
{
#ifdef __clang__
- CAS_NAND(x, (StgWord16) val);
+ CAS_NAND((volatile StgWord16 *) x, (StgWord16) val);
#else
- return __sync_fetch_and_nand(x, (StgWord16) val);
+ return __sync_fetch_and_nand((volatile StgWord16 *) x, (StgWord16) val);
#endif
}
-extern StgWord hs_atomic_nand32(volatile StgWord32 *x, StgWord val);
+extern StgWord hs_atomic_nand32(StgWord x, StgWord val);
StgWord
-hs_atomic_nand32(volatile StgWord32 *x, StgWord val)
+hs_atomic_nand32(StgWord x, StgWord val)
{
#ifdef __clang__
- CAS_NAND(x, (StgWord32) val);
+ CAS_NAND((volatile StgWord32 *) x, (StgWord32) val);
#else
- return __sync_fetch_and_nand(x, (StgWord32) val);
+ return __sync_fetch_and_nand((volatile StgWord32 *) x, (StgWord32) val);
#endif
}
#if WORD_SIZE_IN_BITS == 64
-extern StgWord64 hs_atomic_nand64(volatile StgWord64 *x, StgWord64 val);
+extern StgWord64 hs_atomic_nand64(StgWord x, StgWord64 val);
StgWord64
-hs_atomic_nand64(volatile StgWord64 *x, StgWord64 val)
+hs_atomic_nand64(StgWord x, StgWord64 val)
{
#ifdef __clang__
- CAS_NAND(x, val);
+ CAS_NAND((volatile StgWord64 *) x, val);
#else
- return __sync_fetch_and_nand(x, val);
+ return __sync_fetch_and_nand((volatile StgWord64 *) x, val);
#endif
}
#endif
// FetchOrByteArrayOp_Int
-extern StgWord hs_atomic_or8(volatile StgWord8 *x, StgWord val);
+extern StgWord hs_atomic_or8(StgWord x, StgWord val);
StgWord
-hs_atomic_or8(volatile StgWord8 *x, StgWord val)
+hs_atomic_or8(StgWord x, StgWord val)
{
- return __sync_fetch_and_or(x, (StgWord8) val);
+ return __sync_fetch_and_or((volatile StgWord8 *) x, (StgWord8) val);
}
-extern StgWord hs_atomic_or16(volatile StgWord16 *x, StgWord val);
+extern StgWord hs_atomic_or16(StgWord x, StgWord val);
StgWord
-hs_atomic_or16(volatile StgWord16 *x, StgWord val)
+hs_atomic_or16(StgWord x, StgWord val)
{
- return __sync_fetch_and_or(x, (StgWord16) val);
+ return __sync_fetch_and_or((volatile StgWord16 *) x, (StgWord16) val);
}
-extern StgWord hs_atomic_or32(volatile StgWord32 *x, StgWord val);
+extern StgWord hs_atomic_or32(StgWord x, StgWord val);
StgWord
-hs_atomic_or32(volatile StgWord32 *x, StgWord val)
+hs_atomic_or32(StgWord x, StgWord val)
{
- return __sync_fetch_and_or(x, (StgWord32) val);
+ return __sync_fetch_and_or((volatile StgWord32 *) x, (StgWord32) val);
}
#if WORD_SIZE_IN_BITS == 64
-extern StgWord64 hs_atomic_or64(volatile StgWord64 *x, StgWord64 val);
+extern StgWord64 hs_atomic_or64(StgWord x, StgWord64 val);
StgWord64
-hs_atomic_or64(volatile StgWord64 *x, StgWord64 val)
+hs_atomic_or64(StgWord x, StgWord64 val)
{
- return __sync_fetch_and_or(x, val);
+ return __sync_fetch_and_or((volatile StgWord64 *) x, val);
}
#endif
// FetchXorByteArrayOp_Int
-extern StgWord hs_atomic_xor8(volatile StgWord8 *x, StgWord val);
+extern StgWord hs_atomic_xor8(StgWord x, StgWord val);
StgWord
-hs_atomic_xor8(volatile StgWord8 *x, StgWord val)
+hs_atomic_xor8(StgWord x, StgWord val)
{
- return __sync_fetch_and_xor(x, (StgWord8) val);
+ return __sync_fetch_and_xor((volatile StgWord8 *) x, (StgWord8) val);
}
-extern StgWord hs_atomic_xor16(volatile StgWord16 *x, StgWord val);
+extern StgWord hs_atomic_xor16(StgWord x, StgWord val);
StgWord
-hs_atomic_xor16(volatile StgWord16 *x, StgWord val)
+hs_atomic_xor16(StgWord x, StgWord val)
{
- return __sync_fetch_and_xor(x, (StgWord16) val);
+ return __sync_fetch_and_xor((volatile StgWord16 *) x, (StgWord16) val);
}
-extern StgWord hs_atomic_xor32(volatile StgWord32 *x, StgWord val);
+extern StgWord hs_atomic_xor32(StgWord x, StgWord val);
StgWord
-hs_atomic_xor32(volatile StgWord32 *x, StgWord val)
+hs_atomic_xor32(StgWord x, StgWord val)
{
- return __sync_fetch_and_xor(x, (StgWord32) val);
+ return __sync_fetch_and_xor((volatile StgWord32 *) x, (StgWord32) val);
}
#if WORD_SIZE_IN_BITS == 64
-extern StgWord64 hs_atomic_xor64(volatile StgWord64 *x, StgWord64 val);
+extern StgWord64 hs_atomic_xor64(StgWord x, StgWord64 val);
StgWord64
-hs_atomic_xor64(volatile StgWord64 *x, StgWord64 val)
+hs_atomic_xor64(StgWord x, StgWord64 val)
{
- return __sync_fetch_and_xor(x, val);
+ return __sync_fetch_and_xor((volatile StgWord64 *) x, val);
}
#endif
// CasByteArrayOp_Int
-extern StgWord hs_cmpxchg8(volatile StgWord8 *x, StgWord old, StgWord new);
+extern StgWord hs_cmpxchg8(StgWord x, StgWord old, StgWord new);
StgWord
-hs_cmpxchg8(volatile StgWord8 *x, StgWord old, StgWord new)
+hs_cmpxchg8(StgWord x, StgWord old, StgWord new)
{
- return __sync_val_compare_and_swap(x, (StgWord8) old, (StgWord8) new);
+ return __sync_val_compare_and_swap((volatile StgWord8 *) x, (StgWord8) old, (StgWord8) new);
}
-extern StgWord hs_cmpxchg16(volatile StgWord16 *x, StgWord old, StgWord new);
+extern StgWord hs_cmpxchg16(StgWord x, StgWord old, StgWord new);
StgWord
-hs_cmpxchg16(volatile StgWord16 *x, StgWord old, StgWord new)
+hs_cmpxchg16(StgWord x, StgWord old, StgWord new)
{
- return __sync_val_compare_and_swap(x, (StgWord16) old, (StgWord16) new);
+ return __sync_val_compare_and_swap((volatile StgWord16 *) x, (StgWord16) old, (StgWord16) new);
}
-extern StgWord hs_cmpxchg32(volatile StgWord32 *x, StgWord old, StgWord new);
+extern StgWord hs_cmpxchg32(StgWord x, StgWord old, StgWord new);
StgWord
-hs_cmpxchg32(volatile StgWord32 *x, StgWord old, StgWord new)
+hs_cmpxchg32(StgWord x, StgWord old, StgWord new)
{
- return __sync_val_compare_and_swap(x, (StgWord32) old, (StgWord32) new);
+ return __sync_val_compare_and_swap((volatile StgWord32 *) x, (StgWord32) old, (StgWord32) new);
}
#if WORD_SIZE_IN_BITS == 64
-extern StgWord hs_cmpxchg64(volatile StgWord64 *x, StgWord64 old, StgWord64 new);
+extern StgWord hs_cmpxchg64(StgWord x, StgWord64 old, StgWord64 new);
StgWord
-hs_cmpxchg64(volatile StgWord64 *x, StgWord64 old, StgWord64 new)
+hs_cmpxchg64(StgWord x, StgWord64 old, StgWord64 new)
{
- return __sync_val_compare_and_swap(x, old, new);
+ return __sync_val_compare_and_swap((volatile StgWord64 *) x, old, new);
}
#endif
// AtomicReadByteArrayOp_Int
-extern StgWord hs_atomicread8(volatile StgWord8 *x);
+extern StgWord hs_atomicread8(StgWord x);
StgWord
-hs_atomicread8(volatile StgWord8 *x)
+hs_atomicread8(StgWord x)
{
- return *x;
+ return *(volatile StgWord8 *) x;
}
-extern StgWord hs_atomicread16(volatile StgWord16 *x);
+extern StgWord hs_atomicread16(StgWord x);
StgWord
-hs_atomicread16(volatile StgWord16 *x)
+hs_atomicread16(StgWord x)
{
- return *x;
+ return *(volatile StgWord16 *) x;
}
-extern StgWord hs_atomicread32(volatile StgWord32 *x);
+extern StgWord hs_atomicread32(StgWord x);
StgWord
-hs_atomicread32(volatile StgWord32 *x)
+hs_atomicread32(StgWord x)
{
- return *x;
+ return *(volatile StgWord32 *) x;
}
-extern StgWord64 hs_atomicread64(volatile StgWord64 *x);
+extern StgWord64 hs_atomicread64(StgWord x);
StgWord64
-hs_atomicread64(volatile StgWord64 *x)
+hs_atomicread64(StgWord x)
{
- return *x;
+ return *(volatile StgWord64 *) x;
}
// AtomicWriteByteArrayOp_Int
-extern void hs_atomicwrite8(volatile StgWord8 *x, StgWord val);
+extern void hs_atomicwrite8(StgWord x, StgWord val);
void
-hs_atomicwrite8(volatile StgWord8 *x, StgWord val)
+hs_atomicwrite8(StgWord x, StgWord val)
{
- *x = (StgWord8) val;
+ *(volatile StgWord8 *) x = (StgWord8) val;
}
-extern void hs_atomicwrite16(volatile StgWord16 *x, StgWord val);
+extern void hs_atomicwrite16(StgWord x, StgWord val);
void
-hs_atomicwrite16(volatile StgWord16 *x, StgWord val)
+hs_atomicwrite16(StgWord x, StgWord val)
{
- *x = (StgWord16) val;
+ *(volatile StgWord16 *) x = (StgWord16) val;
}
-extern void hs_atomicwrite32(volatile StgWord32 *x, StgWord val);
+extern void hs_atomicwrite32(StgWord x, StgWord val);
void
-hs_atomicwrite32(volatile StgWord32 *x, StgWord val)
+hs_atomicwrite32(StgWord x, StgWord val)
{
- *x = (StgWord32) val;
+ *(volatile StgWord32 *) x = (StgWord32) val;
}
-extern void hs_atomicwrite64(volatile StgWord64 *x, StgWord64 val);
+extern void hs_atomicwrite64(StgWord x, StgWord64 val);
void
-hs_atomicwrite64(volatile StgWord64 *x, StgWord64 val)
+hs_atomicwrite64(StgWord x, StgWord64 val)
{
- *x = (StgWord64) val;
+ *(volatile StgWord64 *) x = (StgWord64) val;
}

View File

@ -1,103 +0,0 @@
commit 3792d212a6f60573ef43dd72088a353725d09461
Author: Joachim Breitner <mail@joachim-breitner.de>
Date: Thu Nov 5 11:31:12 2015 +0100
test: New mode --show-details=direct
This mode implements #2911, and allows to connect the test runner
directly to stdout/stdin. This is more reliable in the presence of no
threading, i.e. a work-arond for #2398.
I make the test suite use this, so that it passes again, despite
printing lots of stuff. Once #2398 is fixed properly, the test suite
should probably be extended to test all the various --show-details
modes.
Index: ghc/libraries/Cabal/Cabal/Distribution/Simple/Setup.hs
===================================================================
--- ghc.orig/libraries/Cabal/Cabal/Distribution/Simple/Setup.hs 2015-11-05 12:36:38.385252394 +0100
+++ ghc/libraries/Cabal/Cabal/Distribution/Simple/Setup.hs 2015-11-05 12:36:38.377252228 +0100
@@ -1725,7 +1725,7 @@
-- * Test flags
-- ------------------------------------------------------------
-data TestShowDetails = Never | Failures | Always | Streaming
+data TestShowDetails = Never | Failures | Always | Streaming | Direct
deriving (Eq, Ord, Enum, Bounded, Show)
knownTestShowDetails :: [TestShowDetails]
@@ -1813,7 +1813,8 @@
("'always': always show results of individual test cases. "
++ "'never': never show results of individual test cases. "
++ "'failures': show results of failing test cases. "
- ++ "'streaming': show results of test cases in real time.")
+ ++ "'streaming': show results of test cases in real time."
+ ++ "'direct': send results of test cases in real time; no log file.")
testShowDetails (\v flags -> flags { testShowDetails = v })
(reqArg "FILTER"
(readP_to_E (\_ -> "--show-details flag expects one of "
Index: ghc/libraries/Cabal/Cabal/Distribution/Simple/Test/ExeV10.hs
===================================================================
--- ghc.orig/libraries/Cabal/Cabal/Distribution/Simple/Test/ExeV10.hs 2015-11-05 12:36:38.385252394 +0100
+++ ghc/libraries/Cabal/Cabal/Distribution/Simple/Test/ExeV10.hs 2015-11-05 12:36:38.377252228 +0100
@@ -30,7 +30,7 @@
, getCurrentDirectory, removeDirectoryRecursive )
import System.Exit ( ExitCode(..) )
import System.FilePath ( (</>), (<.>) )
-import System.IO ( hGetContents, hPutStr, stdout )
+import System.IO ( hGetContents, hPutStr, stdout, stderr )
runTest :: PD.PackageDescription
-> LBI.LocalBuildInfo
@@ -63,15 +63,20 @@
-- Write summary notices indicating start of test suite
notice verbosity $ summarizeSuiteStart $ PD.testName suite
- (rOut, wOut) <- createPipe
+ (wOut, wErr, logText) <- case details of
+ Direct -> return (stdout, stderr, "")
+ _ -> do
+ (rOut, wOut) <- createPipe
+
+ -- Read test executable's output lazily (returns immediately)
+ logText <- hGetContents rOut
+ -- Force the IO manager to drain the test output pipe
+ void $ forkIO $ length logText `seq` return ()
- -- Read test executable's output lazily (returns immediately)
- logText <- hGetContents rOut
- -- Force the IO manager to drain the test output pipe
- void $ forkIO $ length logText `seq` return ()
+ -- '--show-details=streaming': print the log output in another thread
+ when (details == Streaming) $ void $ forkIO $ hPutStr stdout logText
- -- '--show-details=streaming': print the log output in another thread
- when (details == Streaming) $ void $ forkIO $ hPutStr stdout logText
+ return (wOut, wOut, logText)
-- Run the test executable
let opts = map (testOption pkg_descr lbi suite)
@@ -93,7 +98,7 @@
exit <- rawSystemIOWithEnv verbosity cmd opts Nothing (Just shellEnv')
-- these handles are automatically closed
- Nothing (Just wOut) (Just wOut)
+ Nothing (Just wOut) (Just wErr)
-- Generate TestSuiteLog from executable exit code and a machine-
-- readable test log.
@@ -112,12 +117,10 @@
-- Show the contents of the human-readable log file on the terminal
-- if there is a failure and/or detailed output is requested
let whenPrinting = when $
- (details > Never)
- && (not (suitePassed $ testLogs suiteLog) || details == Always)
+ ( details == Always ||
+ details == Failures && not (suitePassed $ testLogs suiteLog))
-- verbosity overrides show-details
&& verbosity >= normal
- -- if streaming, we already printed the log
- && details /= Streaming
whenPrinting $ putStr $ unlines $ lines logText
-- Write summary notice to terminal indicating end of test suite

View File

@ -1,3 +0,0 @@
version https://git-lfs.github.com/spec/v1
oid sha256:06c6c20077dc3cf7ea3f40126b2128ce5ab144e1fa66fd1c05ae1ade3dfaa8e5
size 11924848

3
ghc-8.0.1-src.tar.xz Normal file
View File

@ -0,0 +1,3 @@
version https://git-lfs.github.com/spec/v1
oid sha256:90fb20cd8712e3c0fbeb2eac8dab6894404c21569746655b9b12ca9684c7d1d2
size 10645912

18
ghc-no-madv-free.patch Normal file
View File

@ -0,0 +1,18 @@
diff --git a/rts/posix/OSMem.c b/rts/posix/OSMem.c
index 99620ee..e052a84 100644
--- a/rts/posix/OSMem.c
+++ b/rts/posix/OSMem.c
@@ -523,13 +523,7 @@ void osDecommitMemory(void *at, W_ size)
sysErrorBelch("unable to make released memory unaccessible");
#endif
-#ifdef MADV_FREE
- // Try MADV_FREE first, FreeBSD has both and MADV_DONTNEED
- // just swaps memory out
- r = madvise(at, size, MADV_FREE);
-#else
r = madvise(at, size, MADV_DONTNEED);
-#endif
if(r < 0)
sysErrorBelch("unable to decommit memory");
}

View File

@ -2,8 +2,6 @@ addFilter("devel-file-in-non-devel-package")
addFilter("static-library-without-debuginfo")
# ghc-compiler has devel-dependency
addFilter("devel-dependency")
# Haskell needs executable stack
addFilter("executable-stack")
# Regrettably, upstream does not provide man pages for all executables
addFilter("no-manual-page-for-binary")
# Prevent warning about ghc containing no binary (it is a metapackage)

View File

@ -1,25 +1,56 @@
-------------------------------------------------------------------
Tue Sep 27 11:53:54 UTC 2016 - peter.trommler@ohm-hochschule.de
Wed Sep 21 07:44:52 UTC 2016 - psimons@suse.com
- add ghc-no-madv-free.patch to fix "unable to decommit memory:
Invalid argument" errors GHC reports due to a misdetected
MADV_FREE capability. The configure script sees the symbol define
by glibc, but unfortunately this doesn't mean that the running
kernel actually supports the feature, too. The upstream ticket
https://ghc.haskell.org/trac/ghc/ticket/12495 has more details.
-------------------------------------------------------------------
Fri Sep 9 09:16:51 UTC 2016 - peter.trommler@ohm-hochschule.de
- add 0001-StgCmmPrim-Add-missing-write-barrier.patch
* add another missing memory barrier in mutable arrays
- refresh D2495.patch
-------------------------------------------------------------------
Wed Sep 7 03:53:10 UTC 2016 - peter.trommler@ohm-hochschule.de
- add D2495.patch
* missing memory barrier on PowerPC, ARM
- add 0001-StgCmmPrim-Add-missing-write-barrier.patch
* another issing memory barrier on PowerPC, ARM
- add 0001-PPC-CodeGen-fix-lwa-instruction-generation.patch
* fix bug in code generator
* fixes build of ghc-zeromq4-haskell on powerpc64[le]
* add missing memory barrier in mutable variables
* fixes random failures on powerpc targets
-------------------------------------------------------------------
Thu Aug 18 17:39:47 UTC 2016 - mimi.vx@gmail.com
Thu Aug 18 18:35:33 UTC 2016 - mimi.vx@gmail.com
- fix boo#994268
-------------------------------------------------------------------
Tue May 17 19:01:13 UTC 2016 - peter.trommler@ohm-hochschule.de
Mon May 30 22:04:46 UTC 2016 - mimi.vx@gmail.com
- add D2225.patch
* backport of upstream patch accepted for ghc 8.0.1
* fix SMP primitives on all powerpc archs
- disable html doc on SLE, we don't have python-sphinx
-------------------------------------------------------------------
Fri May 27 12:13:38 UTC 2016 - peter.trommler@ohm-hochschule.de
- update to 8.0.1
- drop patches fixed upstream:
* drop atomic-cast.patch
* drop cabal-show-detail-direct.patch
* drop 0001-link-command-line-libs-to-temp-so.patch
* drop 0001-implement-native-code-generator-for-ppc64.patch
* drop ghc.git-b29f20.patch
* drop u_terminfo_0402.patch
* drop u_Cabal_update.patch
* drop u_haskeline_update.patch
* drop 0001-Fix-misspelled-WORDS-BIGENDIAN-macro.patch
* drop D2214.patch
* drop D2225.patch
- GHC produces debug information on x86 and x86_64
- aarch64 has LLVM backend (requires llvm-3.7)
- native code generator for powerpc64[le] (openSUSE contribution!)
-------------------------------------------------------------------
Sat May 14 09:13:07 UTC 2016 - peter.trommler@ohm-hochschule.de

View File

@ -1,79 +0,0 @@
From b29f20edb1ca7f1763ceb001e2bb2d5f2f11bec3 Mon Sep 17 00:00:00 2001
From: Peter Trommler <ptrommler@acm.org>
Date: Fri, 2 Oct 2015 15:48:30 +0200
Subject: [PATCH] nativeGen PPC: fix > 16 bit offsets in stack handling
Implement access to spill slots at offsets larger than 16 bits.
Also allocation and deallocation of spill slots was restricted to
16 bit offsets. Now 32 bit offsets are supported on all PowerPC
platforms.
The implementation of 32 bit offsets requires more than one instruction
but the native code generator wants one instruction. So we implement
pseudo-instructions that are pretty printed into multiple assembly
instructions.
With pseudo-instructions for spill slot allocation and deallocation
we can also implement handling of the back chain pointer according
to the ELF ABIs.
Test Plan: validate (especially on powerpc (32 bit))
Reviewers: bgamari, austin, erikd
Reviewed By: erikd
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1296
GHC Trac Issues: #7830
---
compiler/nativeGen/PPC/Instr.hs | 39 ++++++++++++++++++++++++++++-----------
compiler/nativeGen/PPC/Ppr.hs | 33 +++++++++++++++++++++++++++++++++
compiler/nativeGen/PPC/Regs.hs | 14 ++++++++++++--
includes/CodeGen.Platform.hs | 18 +++++++++++++-----
4 files changed, 86 insertions(+), 18 deletions(-)
Index: ghc-7.10.2.20151105/compiler/nativeGen/PPC/Instr.hs
===================================================================
--- ghc-7.10.2.20151105.orig/compiler/nativeGen/PPC/Instr.hs
+++ ghc-7.10.2.20151105/compiler/nativeGen/PPC/Instr.hs
@@ -75,17 +75,19 @@ instance Instruction Instr where
ppc_mkStackAllocInstr :: Platform -> Int -> Instr
ppc_mkStackAllocInstr platform amount
- = case platformArch platform of
- ArchPPC -> UPDATE_SP II32 (ImmInt (-amount))
- ArchPPC_64 _ -> STU II64 sp (AddrRegImm sp (ImmInt (-amount)))
- arch -> panic $ "ppc_mkStackAllocInstr " ++ show arch
+ = ppc_mkStackAllocInstr' platform (-amount)
ppc_mkStackDeallocInstr :: Platform -> Int -> Instr
ppc_mkStackDeallocInstr platform amount
- = case platformArch platform of
- ArchPPC -> UPDATE_SP II32 (ImmInt amount)
- ArchPPC_64 _ -> ADD sp sp (RIImm (ImmInt amount))
- arch -> panic $ "ppc_mkStackDeallocInstr " ++ show arch
+ = ppc_mkStackAllocInstr' platform amount
+
+ppc_mkStackAllocInstr' :: Platform -> Int -> Instr
+ppc_mkStackAllocInstr' platform amount
+ = case platformArch platform of
+ ArchPPC -> UPDATE_SP II32 (ImmInt amount)
+ ArchPPC_64 _ -> UPDATE_SP II64 (ImmInt amount)
+ _ -> panic $ "ppc_mkStackAllocInstr' "
+ ++ show (platformArch platform)
--
-- See note [extra spill slots] in X86/Instr.hs
Index: ghc-7.10.2.20151105/compiler/nativeGen/PPC/Regs.hs
===================================================================
--- ghc-7.10.2.20151105.orig/compiler/nativeGen/PPC/Regs.hs
+++ ghc-7.10.2.20151105/compiler/nativeGen/PPC/Regs.hs
@@ -335,4 +335,5 @@ tmpReg :: Platform -> Reg
tmpReg platform =
case platformArch platform of
ArchPPC -> regSingle 13
+ ArchPPC_64 _ -> regSingle 30
_ -> panic "PPC.Regs.tmpReg: unknowm arch"

151
ghc.spec
View File

@ -15,23 +15,27 @@
# Please submit bugfixes or comments via http://bugs.opensuse.org/
#
%if 0%{?suse_version} == 1315 && !0%{?is_opensuse}
%define without_manual 1
%endif
%global unregisterised_archs aarch64 s390 s390x
Name: ghc
Version: 7.10.3
Version: 8.0.1
Release: 0
Url: http://haskell.org/ghc/dist/%{version}/%{name}-%{version}-src.tar.bz2
Url: http://haskell.org/ghc/dist/%{version}/%{name}-%{version}-src.tar.xz
Summary: The Glorious Glasgow Haskell Compiler
License: BSD-3-Clause
Group: Development/Languages/Other
ExclusiveArch: aarch64 %{ix86} x86_64 ppc ppc64 ppc64le s390 s390x
BuildRequires: binutils-devel
BuildRequires: gcc
BuildRequires: ghc-bootstrap >= 7.6
BuildRequires: ghc-bootstrap >= 7.8
BuildRequires: ghc-rpm-macros-extra
BuildRequires: glibc-devel
BuildRequires: gmp-devel
BuildRequires: libdw-devel
BuildRequires: libelf-devel
#Fix for openSUSE:Leap:42.1
%if 0%{?suse_version} == 1315
@ -39,61 +43,35 @@ BuildRequires: libffi48-devel
%else
BuildRequires: libffi-devel
%endif
#TODO ghc-7.10.2 supports only llvm-3.5, need talk with llvm packagers about
%ifarch aarch64
BuildRequires: binutils-gold
%endif
#TODO ghc-8.0.1 supports only llvm-3.7, need talk with llvm packagers about
# versioned build of llvm
#%%ifnarch ppc aarch64
# Currently, there is no llvm support for powerpc* in GHC.
# Aarch64 has unregisterised LLVM backend, we need llvm 3.7.x
#%%ifarch aarch64 %{ix86} x86_64
#BuildRequires: llvm
#%%endif
BuildRequires: ncurses-devel
BuildRequires: pkg-config
BuildRequires: xz
%if %{undefined without_manual}
BuildRequires: docbook-utils
BuildRequires: docbook-xsl-stylesheets
BuildRequires: libxslt
BuildRequires: python-sphinx
%endif
%ifarch aarch64
BuildRequires: binutils-gold
%endif
# Patch 19 changes build system
BuildRequires: autoconf
BuildRequires: automake
PreReq: update-alternatives
Requires: ghc-compiler = %{version}-%{release}
Requires: ghc-ghc-devel = %{version}-%{release}
Requires: ghc-libraries = %{version}-%{release}
Source: http://haskell.org/ghc/dist/%{version}/%{name}-%{version}b-src.tar.xz
Source: http://haskell.org/ghc/dist/%{version}/%{name}-%{version}-src.tar.xz
Source1: ghc-rpmlintrc
# PATCH-FIX-UPSTREAM fix signature of atomic builtins (#10926)
Patch1: atomic-cast.patch
# PATCH-FIX-UPSTREAM cabal-show-detail-direct.patch peter.trommler@ohm-hochschule.de -- Fix testsuites with large output. Debian patch. Thanks Joachim for suggesting it in Haskell #10870!
Patch3: cabal-show-detail-direct.patch
# PATCH_FIX-UPSTREAM 0001-link-command-line-libs-to-temp-so.patch -- peter.trommler@ohm-hochschule.de -- Fix panic in GHCi. See Haskell trac #10458.
Patch4: 0001-link-command-line-libs-to-temp-so.patch
# PATCH-FEATURE-UPSTREAM 0001-implement-native-code-generator-for-ppc64.patch peter.trommler@ohm-hochschule.de -- Implement native code generator for ppc64. Haskell Trac #9863.
Patch19: 0001-implement-native-code-generator-for-ppc64.patch
# PATCH-FIX-UPSTREAM ghc.git-b29f20.patch peter.trommler@ohm-hochschule.de -- nativeGen PPC: fix > 16 bit offsets in stack handling. This is a backport of my patch for Haskell trac #7830. We do not use erikd's patch because we have 64 bit native code generation for ppc64[le]. See patch 19.
Patch20: ghc.git-b29f20.patch
# PATCH-FIX-UPSTREAM u_terminfo_0402.patch mimi.vx@gmail.com -- update terminfo to 0.4.0.2
Patch21: u_terminfo_0402.patch
# PATCH-FIX-UPSTREAM u_Cabal_update.patch mimi.vx@gmail.com -- update Cabal to 1.22.6.0
Patch22: u_Cabal_update.patch
# PATCH-FIX-UPSTREAM u_haskeline_update.patch mimi.vx@gmail.com -- update haskeline to 0.7.2.3
Patch23: u_haskeline_update.patch
# PATCH-FIX-UPSTREAM 0001-Fix-misspelled-WORDS_BIGENDIAN-macro.patch peter.trommler@ohm-hochschule.de -- Fix ghc-pureMD5 and other Haskell packages on big-endian architectures.
Patch24: 0001-Fix-misspelled-WORDS_BIGENDIAN-macro.patch
# PATCH-FIX-UPSTREAM D2214.patch peter.trommler@ohm-hochschule.de -- Fix PowerPC code generator. See Haskell Trac #12054 and https://phabricator.haskell.org/D2214 for details.
Patch25: D2214.patch
# PATCH-FIX-UPSTREAM D2225.patch peter.trommler@ohm-hochschule.de -- Fix SMP imlementation in Haskell runtime on PPC[64[le]]. Backport of upstreamed patch. See Haskell trac #12070 and https://phabricator.haskell.org/D2225 for details.
Patch26: D2225.patch
# PATCH-FIX-UPSTREAM D2495.patch peter.trommler@ohm-hochschule.de -- Add missing memory barrier on mutable variables. See https://ghc.haskell.org/trac/ghc/ticket/12469 for details. Backport of upstream fix for ghc 8.0.2.
Patch27: D2495.patch
# PATCH-FIX_UPSTREAM 0001-StgCmmPrim-Add-missing-write-barrier.patch peter.trommler@ohm-hochschule.de -- Add missing write barrier on mutable arrays.
Patch28: 0001-StgCmmPrim-Add-missing-write-barrier.patch
# PATCH-FIX-UPSTREAM 0001-PPC-CodeGen-fix-lwa-instruction-generation.patch peter.trommler@ohm-hochschule.de -- Fix PPC codegen: Fixes ghc-zeromq4-haskell build on 64-bit PowerPCs
Patch30: 0001-PPC-CodeGen-fix-lwa-instruction-generation.patch
# PATCH-FIX_UPSTREAM ghc-no-madv-free.patch psimons@suse.com -- Fix "unable to decommit memory: Invalid argument" errors. See https://ghc.haskell.org/trac/ghc/ticket/12495 for details.
Patch29: ghc-no-madv-free.patch
BuildRoot: %{_tmppath}/%{name}-%{version}-build
@ -119,10 +97,6 @@ Summary: GHC compiler and utilities
Group: Development/Languages/Other
Requires: gcc
Requires: ghc-base-devel
# This Requires fixes an issue in ghc's runtime system (rts) when
# locale files are missing. RTS loops and a memory leak eventually
# exhausts all memory and the program crashes. See Haskell trac #7695.
Requires: glibc-locale
Requires(post): update-alternatives
Requires(postun): update-alternatives
%ifarch aarch64
@ -140,28 +114,29 @@ To install all of GHC install package ghc.
%global ghc_pkg_c_deps ghc-compiler = %{ghc_version_override}-%{release}
%if %{defined ghclibdir}
%ghc_lib_subpackage Cabal 1.22.8.0
%ghc_lib_subpackage array 0.5.1.0
%ghc_lib_subpackage -c gmp-devel,libffi-devel base 4.8.2.0
%ghc_lib_subpackage binary 0.7.5.0
%ghc_lib_subpackage bytestring 0.10.6.0
%ghc_lib_subpackage containers 0.5.6.2
%ghc_lib_subpackage deepseq 1.4.1.1
%ghc_lib_subpackage directory 1.2.2.0
%ghc_lib_subpackage filepath 1.4.0.0
%define ghc_pkg_obsoletes ghc-bin-package-db-devel < 0.0.0.0-%{release}
%ghc_lib_subpackage Cabal 1.24.0.0
%ghc_lib_subpackage array 0.5.1.1
%ghc_lib_subpackage -c gmp-devel,libffi-devel,libdw-devel,libelf-devel base 4.9.0.0
%ghc_lib_subpackage binary 0.8.3.0
%ghc_lib_subpackage bytestring 0.10.8.1
%ghc_lib_subpackage containers 0.5.7.1
%ghc_lib_subpackage deepseq 1.4.2.0
%ghc_lib_subpackage directory 1.2.6.2
%ghc_lib_subpackage filepath 1.4.1.0
%ghc_lib_subpackage -x ghc %{ghc_version_override}
%undefine ghc_pkg_obsoletes
%ghc_lib_subpackage ghc-boot %{ghc_version_override}
%ghc_lib_subpackage ghc-boot-th %{ghc_version_override}
%ghc_lib_subpackage -x ghci %{ghc_version_override}
%ghc_lib_subpackage haskeline 0.7.2.3
%ghc_lib_subpackage hoopl 3.10.0.2
%ghc_lib_subpackage hpc 0.6.0.2
%ghc_lib_subpackage pretty 1.1.2.0
%ghc_lib_subpackage process 1.2.3.0
%ghc_lib_subpackage template-haskell 2.10.0.0
%ghc_lib_subpackage hoopl 3.10.2.1
%ghc_lib_subpackage hpc 0.6.0.3
%ghc_lib_subpackage pretty 1.1.3.3
%ghc_lib_subpackage process 1.4.2.0
%ghc_lib_subpackage template-haskell 2.11.0.0
%ghc_lib_subpackage -c ncurses-devel terminfo 0.4.0.2
%ghc_lib_subpackage time 1.5.0.1
%ghc_lib_subpackage transformers 0.4.2.0
%ghc_lib_subpackage unix 2.7.1.0
%ghc_lib_subpackage time 1.6.0.1
%ghc_lib_subpackage transformers 0.5.2.0
%ghc_lib_subpackage unix 2.7.2.0
%ghc_lib_subpackage xhtml 3000.2.1
%endif
@ -183,25 +158,11 @@ except the ghc library, which is installed by the toplevel ghc metapackage.
%prep
%setup -q
%patch1 -p1
%patch3 -p1
%patch4 -p1
%patch19 -p1
%patch20 -p1
%patch21 -p2
%patch22 -p2
%patch23 -p2
%patch24 -p1
%patch25 -p1
%patch26 -p1
%patch27 -p1
%patch28 -p1
%patch30 -p1
%patch29 -p1
%build
# Patch 19 modifies build system
./boot
# Check if bootstrap is required, i.e. version is different from ghc's version
# Note: Cannot use ghc_version macro here as we defined version override earlier
%if "%version" != "%(ghc --numeric-version)"
@ -225,7 +186,9 @@ SRC_HC_OPTS += -optc-fno-builtin
SRC_CC_OPTS += -fno-builtin
%endif
HADDOCK_DOCS = NO
BUILD_DOCBOOK_HTML = NO
BUILD_SPHINX_HTML = NO
BUILD_SPHINX_PS = NO
BUILD_SPHINX_PDF = NO
HSCOLOUR_SRCS = NO
EOF
./configure --prefix=%{_builddir}/ghc-boot --with-system-libffi
@ -261,14 +224,16 @@ GhcStage1HcOpts = -O
GhcStage2HcOpts = -O
GhcHcOpts = -Rghc-timing
GhcLibHcOpts = -O
SRC_HC_OPTS += -optc-fno-builtin
SRC_CC_OPTS += -fno-builtin
SRC_HC_OPTS += -optc-fno-builtin -optc-Wno-return-type
SRC_CC_OPTS += -fno-builtin -Wno-return-type
%endif
%if %{defined without_haddock}
HADDOCK_DOCS = NO
%endif
BUILD_SPHINX_PS = NO
%if %{defined without_manual}
BUILD_DOCBOOK_HTML = NO
BUILD_SPHINX_HTML = NO
BUILD_SPHINX_PDF = NO
%endif
%if %{defined without_hscolour}
HSCOLOUR_SRCS = NO
@ -291,7 +256,7 @@ make -j 2
%endif
%install
%ghc_suse_disable_debug_packages
#%%ghc_suse_disable_debug_packages
%makeinstall
for i in %{ghc_packages_list}; do
@ -304,10 +269,10 @@ done
# ghc-base should own ghclibdir
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.4.0.0
%ghc_gen_filelists integer-gmp 1.0.0.0
%ghc_gen_filelists ghci %{ghc_version_override}
%ghc_gen_filelists ghc-prim 0.5.0.0
%ghc_gen_filelists integer-gmp 1.0.0.1
%define merge_filelist()\
cat ghc-%1.files >> ghc-%2.files\
@ -317,7 +282,6 @@ echo "%doc libraries/LICENSE.%1" >> ghc-%2.files
%merge_filelist integer-gmp base
%merge_filelist ghc-prim base
%merge_filelist bin-package-db ghc
%if %{undefined ghc_without_shared}
echo %%dir %{ghclibdir}/rts >> ghc-base.files
@ -325,7 +289,7 @@ ls %{buildroot}%{ghclibdir}/rts/libHS*.so >> ghc-base.files
sed -i -e "s|^%{buildroot}||g" ghc-base.files
%endif
echo %%dir %{ghclibdir}/rts >> ghc-base-devel.files
ls -d %{buildroot}%{ghclibdir}/rts/libHS*.a %{buildroot}%{ghclibdir}/package.conf.d/builtin_*.conf %{buildroot}%{ghclibdir}/include >> ghc-base-devel.files
ls -d %{buildroot}%{ghclibdir}/rts/libHS*.a %{buildroot}%{ghclibdir}/package.conf.d/rts.conf %{buildroot}%{ghclibdir}/include >> ghc-base-devel.files
sed -i -e "s|^%{buildroot}||g" ghc-base-devel.files
# these are handled as alternatives
@ -342,6 +306,8 @@ done
%ghc_strip_dynlinked
find %{buildroot}%{ghclibdocdir} -name LICENSE -exec rm '{}' ';'
%check
# Actually, I took this from Jens Petersen's Fedora package
# stolen from ghc6/debian/rules:
@ -414,10 +380,13 @@ fi
%dir %{ghclibdir}/bin
%{ghclibdir}/bin/ghc
%{ghclibdir}/bin/ghc-pkg
%{ghclibdir}/bin/ghc-iserv
%{ghclibdir}/bin/ghc-iserv-dyn
%{ghclibdir}/bin/ghc-iserv-prof
%{ghclibdir}/bin/hpc
%{ghclibdir}/bin/hsc2hs
%ifnarch %{unregisterised_archs}
%{ghclibdir}/ghc-split
%{ghclibdir}/bin/ghc-split
%endif
%{ghclibdir}/ghc-usage.txt
%{ghclibdir}/ghci-usage.txt
@ -426,8 +395,8 @@ fi
%{ghclibdir}/platformConstants
%{ghclibdir}/bin/runghc
%{ghclibdir}/template-hsc.h
%{ghclibdir}/unlit
%dir %{_datadir}/doc/ghc
%{ghclibdir}/bin/unlit
%dir %{_datadir}/doc/ghc-%{version}
%dir %{ghcdocbasedir}
%dir %{ghcdocbasedir}/libraries
%if %{undefined without_manual}

View File

@ -1,246 +0,0 @@
diff --git a/ghc-7.10.3.orig/libraries/Cabal/Cabal/Cabal.cabal b/ghc-7.10.3/libraries/Cabal/Cabal/Cabal.cabal
index b498ca0..e8bfb00 100644
--- a/ghc-7.10.3.orig/libraries/Cabal/Cabal/Cabal.cabal
+++ b/ghc-7.10.3/libraries/Cabal/Cabal/Cabal.cabal
@@ -1,5 +1,5 @@
name: Cabal
-version: 1.22.5.0
+version: 1.22.8.0
copyright: 2003-2006, Isaac Jones
2005-2011, Duncan Coutts
license: BSD3
@@ -19,7 +19,7 @@ description:
organizing, and cataloging Haskell libraries and tools.
category: Distribution
cabal-version: >=1.10
-build-type: Custom
+build-type: Simple
-- Even though we do use the default Setup.lhs it's vital to bootstrapping
-- that we build Setup.lhs using our own local Cabal source code.
@@ -145,7 +145,7 @@ library
if flag(bundled-binary-generic)
build-depends: binary >= 0.5 && < 0.7
else
- build-depends: binary >= 0.7 && < 0.8
+ build-depends: binary >= 0.7 && < 0.9
-- Needed for GHC.Generics before GHC 7.6
if impl(ghc < 7.6)
@@ -265,7 +265,7 @@ test-suite unit-tests
test-framework-hunit,
test-framework-quickcheck2,
HUnit,
- QuickCheck < 2.8,
+ QuickCheck < 2.9,
Cabal
ghc-options: -Wall
default-language: Haskell98
@@ -312,7 +312,7 @@ test-suite package-tests
test-framework-quickcheck2 >= 0.2.12,
test-framework-hunit,
HUnit,
- QuickCheck >= 2.1.0.1 && < 2.8,
+ QuickCheck >= 2.1.0.1 && < 2.9,
Cabal,
process,
directory,
diff --git a/ghc-7.10.3.orig/libraries/Cabal/Cabal/Distribution/Simple/GHC.hs b/ghc-7.10.3/libraries/Cabal/Cabal/Distribution/Simple/GHC.hs
index 444c851..fa6d8a8 100644
--- a/ghc-7.10.3.orig/libraries/Cabal/Cabal/Distribution/Simple/GHC.hs
+++ b/ghc-7.10.3/libraries/Cabal/Cabal/Distribution/Simple/GHC.hs
@@ -542,19 +542,22 @@ buildOrReplLib forRepl verbosity numJobs pkg_descr lbi lib clbi = do
}
odir = fromFlag (ghcOptObjDir vanillaCcOpts)
createDirectoryIfMissingVerbose verbosity True odir
- needsRecomp <- checkNeedsRecompilation filename vanillaCcOpts
- when needsRecomp $ do
- runGhcProg vanillaCcOpts
- unless forRepl $
- whenSharedLib forceSharedLib (runGhcProg sharedCcOpts)
- unless forRepl $ whenProfLib (runGhcProg profCcOpts)
+ let runGhcProgIfNeeded ccOpts = do
+ needsRecomp <- checkNeedsRecompilation filename ccOpts
+ when needsRecomp $ runGhcProg ccOpts
+ runGhcProgIfNeeded vanillaCcOpts
+ unless forRepl $
+ whenSharedLib forceSharedLib (runGhcProgIfNeeded sharedCcOpts)
+ unless forRepl $ whenProfLib (runGhcProgIfNeeded profCcOpts)
| filename <- cSources libBi]
-- TODO: problem here is we need the .c files built first, so we can load them
-- with ghci, but .c files can depend on .h files generated by ghc by ffi
-- exports.
- unless (null (libModules lib)) $
- ifReplLib (runGhcProg replOpts)
+
+ ifReplLib $ do
+ when (null (libModules lib)) $ warn verbosity "No exposed modules"
+ ifReplLib (runGhcProg replOpts)
-- link:
unless forRepl $ do
@@ -766,7 +769,9 @@ buildOrReplExe forRepl verbosity numJobs _pkg_descr lbi
ghcOptLinkLibPath = toNubListR $ extraLibDirs exeBi,
ghcOptLinkFrameworks = toNubListR $ PD.frameworks exeBi,
ghcOptInputFiles = toNubListR
- [exeDir </> x | x <- cObjs],
+ [exeDir </> x | x <- cObjs]
+ }
+ dynLinkerOpts = mempty {
ghcOptRPaths = rpaths
}
replOpts = baseOpts {
@@ -812,9 +817,9 @@ buildOrReplExe forRepl verbosity numJobs _pkg_descr lbi
| otherwise = doingTH && (withProfExe lbi || withDynExe lbi)
linkOpts = commonOpts `mappend`
- linkerOpts `mappend` mempty {
- ghcOptLinkNoHsMain = toFlag (not isHaskellMain)
- }
+ linkerOpts `mappend`
+ mempty { ghcOptLinkNoHsMain = toFlag (not isHaskellMain) } `mappend`
+ (if withDynExe lbi then dynLinkerOpts else mempty)
-- Build static/dynamic object files for TH, if needed.
when compileForTH $
diff --git a/ghc-7.10.3.orig/libraries/Cabal/Cabal/Distribution/Simple/Haddock.hs b/ghc-7.10.3/libraries/Cabal/Cabal/Distribution/Simple/Haddock.hs
index 095d6b8..2d09292 100644
--- a/ghc-7.10.3.orig/libraries/Cabal/Cabal/Distribution/Simple/Haddock.hs
+++ b/ghc-7.10.3/libraries/Cabal/Cabal/Distribution/Simple/Haddock.hs
@@ -84,14 +84,16 @@ import Language.Haskell.Extension
import Control.Monad ( when, forM_ )
+import Data.Char ( isSpace )
import Data.Either ( rights )
import Data.Monoid
+import Data.Foldable ( foldl' )
import Data.Maybe ( fromMaybe, listToMaybe )
import System.Directory (doesFileExist)
import System.FilePath ( (</>), (<.>)
, normalise, splitPath, joinPath, isAbsolute )
-import System.IO (hClose, hPutStrLn, hSetEncoding, utf8)
+import System.IO (hClose, hPutStr, hPutStrLn, hSetEncoding, utf8)
import Distribution.Version
-- ------------------------------------------------------------------------------
@@ -467,7 +469,7 @@ renderArgs :: Verbosity
-> IO a
renderArgs verbosity tmpFileOpts version comp args k = do
let haddockSupportsUTF8 = version >= Version [2,14,4] []
- haddockSupportsResponseFiles = version > Version [2,16,1] []
+ haddockSupportsResponseFiles = version > Version [2,16,2] []
createDirectoryIfMissingVerbose verbosity True outputDir
withTempFileEx tmpFileOpts outputDir "haddock-prologue.txt" $
\prologueFileName h -> do
@@ -482,7 +484,7 @@ renderArgs verbosity tmpFileOpts version comp args k = do
withTempFileEx tmpFileOpts outputDir "haddock-response.txt" $
\responseFileName hf -> do
when haddockSupportsUTF8 (hSetEncoding hf utf8)
- mapM_ (hPutStrLn hf) renderedArgs
+ hPutStr hf $ unlines $ map escapeArg renderedArgs
hClose hf
let respFile = "@" ++ responseFileName
k ([respFile], result)
@@ -500,6 +502,19 @@ renderArgs verbosity tmpFileOpts version comp args k = do
pkgstr = display $ packageName pkgid
pkgid = arg argPackageName
arg f = fromFlag $ f args
+ -- Support a gcc-like response file syntax. Each separate
+ -- argument and its possible parameter(s), will be separated in the
+ -- response file by an actual newline; all other whitespace,
+ -- single quotes, double quotes, and the character used for escaping
+ -- (backslash) are escaped. The called program will need to do a similar
+ -- inverse operation to de-escape and re-constitute the argument list.
+ escape cs c
+ | isSpace c
+ || '\\' == c
+ || '\'' == c
+ || '"' == c = c:'\\':cs -- n.b., our caller must reverse the result
+ | otherwise = c:cs
+ escapeArg = reverse . foldl' escape []
renderPureArgs :: Version -> Compiler -> HaddockArgs -> [String]
renderPureArgs version comp args = concat
diff --git a/ghc-7.10.3.orig/libraries/Cabal/Cabal/Distribution/Simple/Setup.hs b/ghc-7.10.3/libraries/Cabal/Cabal/Distribution/Simple/Setup.hs
index b87b567..abda3c7 100644
--- a/ghc-7.10.3.orig/libraries/Cabal/Cabal/Distribution/Simple/Setup.hs
+++ b/ghc-7.10.3/libraries/Cabal/Cabal/Distribution/Simple/Setup.hs
@@ -2099,7 +2099,6 @@ optionNumJobs get set =
_ -> case reads s of
[(n, "")]
| n < 1 -> Left "The number of jobs should be 1 or more."
- | n > 64 -> Left "You probably don't want that many jobs."
| otherwise -> Right (Just n)
_ -> Left "The jobs value should be a number or '$ncpus'"
diff --git a/ghc-7.10.3.orig/libraries/Cabal/Cabal/Distribution/Version.hs b/ghc-7.10.3/libraries/Cabal/Cabal/Distribution/Version.hs
index 1123749..e5c2e28 100644
--- a/ghc-7.10.3.orig/libraries/Cabal/Cabal/Distribution/Version.hs
+++ b/ghc-7.10.3/libraries/Cabal/Cabal/Distribution/Version.hs
@@ -3,7 +3,25 @@
#if __GLASGOW_HASKELL__ < 707
{-# LANGUAGE StandaloneDeriving #-}
#endif
+
+-- Hack approach to support bootstrapping
+-- Assume binary <0.8 when MIN_VERSION_binary macro is not available.
+-- Starting with GHC>=8.0, compiler will hopefully provide this macros too.
+-- https://ghc.haskell.org/trac/ghc/ticket/10970
+--
+-- Otherwise, one can specify -DMIN_VERSION_binary_0_8_0=1, when bootstrapping
+-- with binary >=0.8.0.0
+#ifdef MIN_VERSION_binary
+#define MIN_VERSION_binary_0_8_0 MIN_VERSION_binary(0,8,0)
+#else
+#ifndef MIN_VERSION_binary_0_8_0
+#define MIN_VERSION_binary_0_8_0 0
+#endif
+#endif
+
+#if !MIN_VERSION_binary_0_8_0
{-# OPTIONS_GHC -fno-warn-orphans #-}
+#endif
-----------------------------------------------------------------------------
-- |
@@ -109,6 +127,7 @@ instance Binary VersionRange
deriving instance Data Version
#endif
+#if !(MIN_VERSION_binary_0_8_0)
-- Deriving this instance from Generic gives trouble on GHC 7.2 because the
-- Generic instance has to be standalone-derived. So, we hand-roll our own.
-- We can't use a generic Binary instance on later versions because we must
@@ -119,6 +138,7 @@ instance Binary Version where
tags <- get
return $ Version br tags
put (Version br tags) = put br >> put tags
+#endif
{-# DEPRECATED AnyVersion "Use 'anyVersion', 'foldVersionRange' or 'asVersionIntervals'" #-}
{-# DEPRECATED ThisVersion "use 'thisVersion', 'foldVersionRange' or 'asVersionIntervals'" #-}
diff --git a/ghc-7.10.3.orig/libraries/Cabal/Cabal/changelog b/ghc-7.10.3/libraries/Cabal/Cabal/changelog
index f5fb8ff..45c15f9 100644
--- a/ghc-7.10.3.orig/libraries/Cabal/Cabal/changelog
+++ b/ghc-7.10.3/libraries/Cabal/Cabal/changelog
@@ -1,3 +1,17 @@
+1.22.8.0 Ryan Thomas <ryan@ryant.org> March 2016
+ * Distribution.Simple.Setup: remove job cap. Fixes #3191.
+ * Check all object file suffixes for recompilation. Fixes #3128.
+ * Move source files under 'src/'. Fixes #3003.
+
+1.22.7.0 Ryan Thomas <ryan@ryant.org> January 2016
+ * Backport #3012 to the 1.22 branch
+ * Cabal.cabal: change build-type to Simple
+ * Add foldl' import
+ * The Cabal part for fully gcc-like response files
+
+1.22.6.0
+ * Relax upper bound to allow upcoming binary-0.8
+
1.22.5.0
* Don't recompile C sources unless needed (#2601). (Luke Iannini)
* Support Haddock response files.

File diff suppressed because it is too large Load Diff

View File

@ -1,163 +0,0 @@
diff --git a/ghc-7.10.3.old/libraries/terminfo/System/Console/Terminfo/Base.hs b/ghc-7.10.3/libraries/terminfo/System/Console/Terminfo/Base.hs
index 87ac774..d2b262c 100644
--- a/ghc-7.10.3.old/libraries/terminfo/System/Console/Terminfo/Base.hs
+++ b/ghc-7.10.3/libraries/terminfo/System/Console/Terminfo/Base.hs
@@ -52,7 +52,7 @@ import Foreign.C
import Foreign.ForeignPtr
import Foreign.Ptr
import Foreign.Marshal
-import Foreign.Storable (peek,poke)
+import Foreign.Storable (peek)
import System.Environment (getEnv)
import System.IO.Unsafe (unsafePerformIO)
import System.IO
@@ -63,8 +63,8 @@ import Data.Typeable
data TERMINAL
newtype Terminal = Terminal (ForeignPtr TERMINAL)
-foreign import ccall "&" cur_term :: Ptr (Ptr TERMINAL)
-foreign import ccall set_curterm :: Ptr TERMINAL -> IO (Ptr TERMINAL)
+-- Use "unsafe" to make set_curterm faster since it's called quite a bit.
+foreign import ccall unsafe set_curterm :: Ptr TERMINAL -> IO (Ptr TERMINAL)
foreign import ccall "&" del_curterm :: FunPtr (Ptr TERMINAL -> IO ())
foreign import ccall setupterm :: CString -> CInt -> Ptr CInt -> IO ()
@@ -73,19 +73,15 @@ foreign import ccall setupterm :: CString -> CInt -> Ptr CInt -> IO ()
--
-- Throws a 'SetupTermError' if the terminfo database could not be read.
setupTerm :: String -> IO Terminal
-setupTerm term = bracket (peek cur_term) (poke cur_term) $ \_ ->
+setupTerm term =
withCString term $ \c_term ->
with 0 $ \ret_ptr -> do
-- NOTE: I believe that for the way we use terminfo
-- (i.e. custom output function)
-- this parameter does not affect anything.
let stdOutput = 1
- {-- Force ncurses to return a new struct rather than
- a copy of the current one (which it would do if the
- terminal names are the same). This prevents problems
- when calling del_term on a struct shared by more than one
- Terminal. --}
- poke cur_term nullPtr
+ -- Save the previous terminal to be restored after calling setupterm.
+ old_term <- set_curterm nullPtr
-- Call setupterm and check the return value.
setupterm c_term stdOutput ret_ptr
ret <- peek ret_ptr
@@ -93,7 +89,7 @@ setupTerm term = bracket (peek cur_term) (poke cur_term) $ \_ ->
then throwIO $ SetupTermError
$ "Couldn't look up terminfo entry " ++ show term
else do
- cterm <- peek cur_term
+ cterm <- set_curterm old_term
fmap Terminal $ newForeignPtr del_curterm cterm
data SetupTermError = SetupTermError String
@@ -120,14 +116,10 @@ setupTermFromEnv = do
-- TODO: this isn't really thread-safe...
withCurTerm :: Terminal -> IO a -> IO a
withCurTerm (Terminal term) f = withForeignPtr term $ \cterm -> do
- old_term <- peek cur_term
- if old_term /= cterm
- then do
- _ <- set_curterm cterm
- x <- f
- _ <- set_curterm old_term
- return x
- else f
+ old_term <- set_curterm cterm
+ x <- f
+ _ <- set_curterm old_term
+ return x
----------------------
@@ -198,11 +190,11 @@ instance Functor Capability where
fmap f (Capability g) = Capability $ \t -> fmap (fmap f) (g t)
instance Applicative Capability where
- pure = return
+ pure = Capability . const . pure . Just
(<*>) = ap
instance Monad Capability where
- return = Capability . const . return . Just
+ return = pure
Capability f >>= g = Capability $ \t -> do
mx <- f t
case mx of
diff --git a/ghc-7.10.3.old/libraries/terminfo/configure b/ghc-7.10.3/libraries/terminfo/configure
index be70a46..600e92f 100755
--- a/ghc-7.10.3.old/libraries/terminfo/configure
+++ b/ghc-7.10.3/libraries/terminfo/configure
@@ -656,7 +656,6 @@ infodir
docdir
oldincludedir
includedir
-runstatedir
localstatedir
sharedstatedir
sysconfdir
@@ -730,7 +729,6 @@ datadir='${datarootdir}'
sysconfdir='${prefix}/etc'
sharedstatedir='${prefix}/com'
localstatedir='${prefix}/var'
-runstatedir='${localstatedir}/run'
includedir='${prefix}/include'
oldincludedir='/usr/include'
docdir='${datarootdir}/doc/${PACKAGE_TARNAME}'
@@ -983,15 +981,6 @@ do
| -silent | --silent | --silen | --sile | --sil)
silent=yes ;;
- -runstatedir | --runstatedir | --runstatedi | --runstated \
- | --runstate | --runstat | --runsta | --runst | --runs \
- | --run | --ru | --r)
- ac_prev=runstatedir ;;
- -runstatedir=* | --runstatedir=* | --runstatedi=* | --runstated=* \
- | --runstate=* | --runstat=* | --runsta=* | --runst=* | --runs=* \
- | --run=* | --ru=* | --r=*)
- runstatedir=$ac_optarg ;;
-
-sbindir | --sbindir | --sbindi | --sbind | --sbin | --sbi | --sb)
ac_prev=sbindir ;;
-sbindir=* | --sbindir=* | --sbindi=* | --sbind=* | --sbin=* \
@@ -1129,7 +1118,7 @@ fi
for ac_var in exec_prefix prefix bindir sbindir libexecdir datarootdir \
datadir sysconfdir sharedstatedir localstatedir includedir \
oldincludedir docdir infodir htmldir dvidir pdfdir psdir \
- libdir localedir mandir runstatedir
+ libdir localedir mandir
do
eval ac_val=\$$ac_var
# Remove trailing slashes.
@@ -1282,7 +1271,6 @@ Fine tuning of the installation directories:
--sysconfdir=DIR read-only single-machine data [PREFIX/etc]
--sharedstatedir=DIR modifiable architecture-independent data [PREFIX/com]
--localstatedir=DIR modifiable single-machine data [PREFIX/var]
- --runstatedir=DIR modifiable per-process data [LOCALSTATEDIR/run]
--libdir=DIR object code libraries [EPREFIX/lib]
--includedir=DIR C header files [PREFIX/include]
--oldincludedir=DIR C header files for non-gcc [/usr/include]
diff --git a/ghc-7.10.3.old/libraries/terminfo/terminfo.cabal b/ghc-7.10.3/libraries/terminfo/terminfo.cabal
index 31d84fa..2dfbee9 100644
--- a/ghc-7.10.3.old/libraries/terminfo/terminfo.cabal
+++ b/ghc-7.10.3/libraries/terminfo/terminfo.cabal
@@ -1,6 +1,6 @@
Name: terminfo
Cabal-Version: >=1.10
-Version: 0.4.0.1
+Version: 0.4.0.2
Category: User Interfaces
License: BSD3
License-File: LICENSE
@@ -29,7 +29,7 @@ Library
other-extensions: CPP, DeriveDataTypeable, FlexibleInstances, ScopedTypeVariables
if impl(ghc>=7.3)
other-extensions: Safe, Trustworthy
- build-depends: base >= 4.3 && < 4.9
+ build-depends: base >= 4.3 && < 4.10
ghc-options: -Wall
exposed-modules:
System.Console.Terminfo