Accepting request 305686 from devel:languages:haskell
+ add ghc-glibc-2.20_BSD_SOURCE.patch from fedora - updated to 7.8.4 + removed D177.patch (in upstream) + removed D173.patch (in upstream) + removed ghc.git-e18525f.patch (in upstream) + refresh 0001-implement-native-code-generator-for-ppc64.patch * A critical bug in the LLVM backend which would cause the compiler to generate incorrect code has been fixed (issue #9439). * Several bugs in the code generator have been fixed for unregisterised platforms, such as 64bit PowerPC (issue #8819 and #8849). * A bug that could cause GHC's constructor specialization pass (enabled by default at -O2, or via -fspec-constr) to loop forever and consume large amounts of memory has been fixed (issue #8960). * A bug that would cause GHC to fail when attempting to determine GCC's version information in non-english locales has been fixed (issue #8825). * A minor bug that allowed GHC to seemingly import (but not use) private data constructors has been fixed (issue #9006). * A bug in the register allocator which would cause GHC to crash during compilation has been fixed (issue #9303). * A bug that caused the compiler to panic on some input C-- code has been fixed (issue #9329). * A few various minor deadlocks in the runtime system when using forkProcess have been fixed. * A bug which made blocked STM transactions non-interruptible has been fixed (issue #9379). * A bug in the compiler which broke pattern synonym imports across modules in Haddock has been fixed (issue #9417). * A minor bug in the code generator in which the popCnt16# did not zero-extend its result has been fixed (issue #9435). * A bug which caused the compiler to panic on pattern synonyms inside a class declaration has been fixed (issue #9705). * A bug in the typechecker revolving around un-saturated type family applications has been fixed (issue #9433). * Several bugs have been fixed causing problems with building GHC on ARM (issues #8951, #9620, #9336, and #9552). * A bug in the typechecker that could cause an infinite loop when using superclasses in a cycle has been fixed (issue #9415). * A bug causing corruption in signal handling with the single-threaded runtime system has been fixed (issue #9817). * A bug that could cause compiled programs to crash due to use of overlapping type families has been fixed (issue #9371). * A bug in the inliner that caused certain expressions within unboxed tuples to not be properly evaluated has been fixed (issue #9390). * A bug that caused the compiler to not always properly detect LLVM tools (particularly on Windows) has been fixed (issue #7143). * A bug that prevented GHC from deriving Generic1 instances for data families has been fixed (#9563). * A bug that caused type inference to infer the incorrect type in the presence of certain type families and constraints has been fixed (issue #9316). OBS-URL: https://build.opensuse.org/request/show/305686 OBS-URL: https://build.opensuse.org/package/show/openSUSE:Factory/ghc?expand=0&rev=26
This commit is contained in:
commit
9d761d8ba2
@ -1809,16 +1809,16 @@ Index: ghc-7.8.3/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs
|
||||
ArchAlpha -> panic "maxSpillSlots ArchAlpha"
|
||||
ArchMipseb -> panic "maxSpillSlots ArchMipseb"
|
||||
ArchMipsel -> panic "maxSpillSlots ArchMipsel"
|
||||
Index: ghc-7.8.3/compiler/nativeGen/RegAlloc/Linear/Main.hs
|
||||
Index: ghc-7.8.4/compiler/nativeGen/RegAlloc/Linear/Main.hs
|
||||
===================================================================
|
||||
--- ghc-7.8.3.orig/compiler/nativeGen/RegAlloc/Linear/Main.hs
|
||||
+++ ghc-7.8.3/compiler/nativeGen/RegAlloc/Linear/Main.hs
|
||||
@@ -207,7 +207,7 @@ linearRegAlloc dflags first_id block_liv
|
||||
ArchSPARC -> linearRegAlloc' dflags (frInitFreeRegs platform :: SPARC.FreeRegs) first_id block_live sccs
|
||||
ArchPPC -> linearRegAlloc' dflags (frInitFreeRegs platform :: PPC.FreeRegs) first_id block_live sccs
|
||||
--- ghc-7.8.4.orig/compiler/nativeGen/RegAlloc/Linear/Main.hs
|
||||
+++ ghc-7.8.4/compiler/nativeGen/RegAlloc/Linear/Main.hs
|
||||
@@ -207,7 +207,7 @@ linearRegAlloc dflags entry_ids block_liv
|
||||
ArchSPARC -> linearRegAlloc' dflags (frInitFreeRegs platform :: SPARC.FreeRegs) entry_ids block_live sccs
|
||||
ArchPPC -> linearRegAlloc' dflags (frInitFreeRegs platform :: PPC.FreeRegs) entry_ids block_live sccs
|
||||
ArchARM _ _ _ -> panic "linearRegAlloc ArchARM"
|
||||
- ArchPPC_64 -> panic "linearRegAlloc ArchPPC_64"
|
||||
+ ArchPPC_64 -> linearRegAlloc' dflags (frInitFreeRegs platform :: PPC.FreeRegs) first_id block_live sccs
|
||||
+ ArchPPC_64 -> linearRegAlloc' dflags (frInitFreeRegs platform :: PPC.FreeRegs) entry_ids block_live sccs
|
||||
ArchAlpha -> panic "linearRegAlloc ArchAlpha"
|
||||
ArchMipseb -> panic "linearRegAlloc ArchMipseb"
|
||||
ArchMipsel -> panic "linearRegAlloc ArchMipsel"
|
||||
|
51
D173.patch
51
D173.patch
@ -1,51 +0,0 @@
|
||||
Index: ghc-7.8.3/compiler/cmm/PprC.hs
|
||||
===================================================================
|
||||
--- ghc-7.8.3.orig/compiler/cmm/PprC.hs
|
||||
+++ ghc-7.8.3/compiler/cmm/PprC.hs
|
||||
@@ -1220,8 +1220,9 @@ commafy xs = hsep $ punctuate comma xs
|
||||
pprHexVal :: Integer -> Width -> SDoc
|
||||
pprHexVal 0 _ = ptext (sLit "0x0")
|
||||
pprHexVal w rep
|
||||
- | w < 0 = parens (char '-' <> ptext (sLit "0x") <> go (-w) <> repsuffix rep)
|
||||
- | otherwise = ptext (sLit "0x") <> go w <> repsuffix rep
|
||||
+ | w < 0 = parens (char '-' <>
|
||||
+ ptext (sLit "0x") <> intToDoc (-w) <> repsuffix rep)
|
||||
+ | otherwise = ptext (sLit "0x") <> intToDoc w <> repsuffix rep
|
||||
where
|
||||
-- type suffix for literals:
|
||||
-- Integer literals are unsigned in Cmm/C. We explicitly cast to
|
||||
@@ -1236,10 +1237,33 @@ pprHexVal w rep
|
||||
else panic "pprHexVal: Can't find a 64-bit type"
|
||||
repsuffix _ = char 'U'
|
||||
|
||||
+ intToDoc :: Integer -> SDoc
|
||||
+ intToDoc i = go (truncInt i)
|
||||
+
|
||||
+ -- We need to truncate value as Cmm backend does not drop
|
||||
+ -- redundant bits to ease handling of negative values.
|
||||
+ -- Thus the following Cmm code on 64-bit arch, like amd64:
|
||||
+ -- CInt v;
|
||||
+ -- v = {something};
|
||||
+ -- if (v == %lobits32(-1)) { ...
|
||||
+ -- leads to the following C code:
|
||||
+ -- StgWord64 v = (StgWord32)({something});
|
||||
+ -- if (v == 0xFFFFffffFFFFffffU) { ...
|
||||
+ -- Such code is incorrect as it promotes both operands to StgWord64
|
||||
+ -- and the whole condition is always false.
|
||||
+ truncInt :: Integer -> Integer
|
||||
+ truncInt i =
|
||||
+ case rep of
|
||||
+ W8 -> i `rem` (2^(8 :: Int))
|
||||
+ W16 -> i `rem` (2^(16 :: Int))
|
||||
+ W32 -> i `rem` (2^(32 :: Int))
|
||||
+ W64 -> i `rem` (2^(64 :: Int))
|
||||
+ _ -> panic ("pprHexVal/truncInt: C backend can't encode "
|
||||
+ ++ show rep ++ " literals")
|
||||
+
|
||||
go 0 = empty
|
||||
go w' = go q <> dig
|
||||
where
|
||||
(q,r) = w' `quotRem` 16
|
||||
dig | r < 10 = char (chr (fromInteger r + ord '0'))
|
||||
| otherwise = char (chr (fromInteger r - 10 + ord 'a'))
|
||||
-
|
80
D177.patch
80
D177.patch
@ -1,80 +0,0 @@
|
||||
Index: ghc-7.8.3/compiler/main/DriverPipeline.hs
|
||||
===================================================================
|
||||
--- ghc-7.8.3.orig/compiler/main/DriverPipeline.hs
|
||||
+++ ghc-7.8.3/compiler/main/DriverPipeline.hs
|
||||
@@ -1208,6 +1208,7 @@ runPhase (RealPhase (As with_cpp)) input
|
||||
|
||||
as_prog <- whichAsProg
|
||||
let cmdline_include_paths = includePaths dflags
|
||||
+ let pic_c_flags = picCCOpts dflags
|
||||
|
||||
next_phase <- maybeMergeStub
|
||||
output_fn <- phaseOutputFilename next_phase
|
||||
@@ -1221,6 +1222,9 @@ runPhase (RealPhase (As with_cpp)) input
|
||||
= liftIO $ as_prog dflags
|
||||
([ SysTools.Option ("-I" ++ p) | p <- cmdline_include_paths ]
|
||||
|
||||
+ -- See Note [-fPIC for assembler]
|
||||
+ ++ map SysTools.Option pic_c_flags
|
||||
+
|
||||
-- We only support SparcV9 and better because V8 lacks an atomic CAS
|
||||
-- instruction so we have to make sure that the assembler accepts the
|
||||
-- instruction set. Note that the user can still override this
|
||||
@@ -1262,6 +1266,8 @@ runPhase (RealPhase SplitAs) _input_fn d
|
||||
osuf = objectSuf dflags
|
||||
split_odir = base_o ++ "_" ++ osuf ++ "_split"
|
||||
|
||||
+ let pic_c_flags = picCCOpts dflags
|
||||
+
|
||||
-- this also creates the hierarchy
|
||||
liftIO $ createDirectoryIfMissing True split_odir
|
||||
|
||||
@@ -1295,6 +1301,9 @@ runPhase (RealPhase SplitAs) _input_fn d
|
||||
then [SysTools.Option "-mcpu=v9"]
|
||||
else []) ++
|
||||
|
||||
+ -- See Note [-fPIC for assembler]
|
||||
+ map SysTools.Option pic_c_flags ++
|
||||
+
|
||||
[ SysTools.Option "-c"
|
||||
, SysTools.Option "-o"
|
||||
, SysTools.FileOption "" (split_obj n)
|
||||
@@ -2210,3 +2219,38 @@ haveRtsOptsFlags dflags =
|
||||
isJust (rtsOpts dflags) || case rtsOptsEnabled dflags of
|
||||
RtsOptsSafeOnly -> False
|
||||
_ -> True
|
||||
+
|
||||
+-- Note [-fPIC for assembler]
|
||||
+-- When compiling .c source file GHC's driver pipeline basically
|
||||
+-- does the following two things:
|
||||
+-- 1. ${CC} -S 'PIC_CFLAGS' source.c
|
||||
+-- 2. ${CC} -x assembler -c 'PIC_CFLAGS' source.S
|
||||
+--
|
||||
+-- Why do we need to pass 'PIC_CFLAGS' both to C compiler and assembler?
|
||||
+-- Because on some architectures (at least sparc32) assembler also choses
|
||||
+-- relocation type!
|
||||
+-- Consider the following C module:
|
||||
+--
|
||||
+-- /* pic-sample.c */
|
||||
+-- int v;
|
||||
+-- void set_v (int n) { v = n; }
|
||||
+-- int get_v (void) { return v; }
|
||||
+--
|
||||
+-- $ gcc -S -fPIC pic-sample.c
|
||||
+-- $ gcc -c pic-sample.s -o pic-sample.no-pic.o # incorrect binary
|
||||
+-- $ gcc -c -fPIC pic-sample.s -o pic-sample.pic.o # correct binary
|
||||
+--
|
||||
+-- $ objdump -r -d pic-sample.pic.o > pic-sample.pic.o.od
|
||||
+-- $ objdump -r -d pic-sample.no-pic.o > pic-sample.no-pic.o.od
|
||||
+-- $ diff -u pic-sample.pic.o.od pic-sample.no-pic.o.od
|
||||
+--
|
||||
+-- Most of architectures won't show any difference in this test, but on sparc32
|
||||
+-- the following assembly snippet:
|
||||
+--
|
||||
+-- sethi %hi(_GLOBAL_OFFSET_TABLE_-8), %l7
|
||||
+--
|
||||
+-- generates two kinds or relocations, only 'R_SPARC_PC22' is correct:
|
||||
+--
|
||||
+-- 3c: 2f 00 00 00 sethi %hi(0), %l7
|
||||
+-- - 3c: R_SPARC_PC22 _GLOBAL_OFFSET_TABLE_-0x8
|
||||
+-- + 3c: R_SPARC_HI22 _GLOBAL_OFFSET_TABLE_-0x8
|
14
_constraints
14
_constraints
@ -2,9 +2,19 @@
|
||||
<hardware>
|
||||
<disk>
|
||||
<size unit="G">12</size>
|
||||
</disk>
|
||||
</disk>
|
||||
<physicalmemory>
|
||||
<size unit="G">4</size>
|
||||
<size unit="G">4</size>
|
||||
</physicalmemory>
|
||||
</hardware>
|
||||
<overwrite>
|
||||
<conditions>
|
||||
<arch>ppc64le</arch>
|
||||
</conditions>
|
||||
<hardware>
|
||||
<memory>
|
||||
<size unit="G">8</size>
|
||||
</memory>
|
||||
</hardware>
|
||||
</overwrite>
|
||||
</constraints>
|
||||
|
@ -1,3 +0,0 @@
|
||||
version https://git-lfs.github.com/spec/v1
|
||||
oid sha256:b0cd96a549ba3b5e512847a4a8cd1a3174e4b2b75dadfc41c568fb812887b958
|
||||
size 9160092
|
3
ghc-7.8.4-src.tar.xz
Normal file
3
ghc-7.8.4-src.tar.xz
Normal file
@ -0,0 +1,3 @@
|
||||
version https://git-lfs.github.com/spec/v1
|
||||
oid sha256:c319cd94adb284177ed0e6d21546ed0b900ad84b86b87c06a99eac35152982c4
|
||||
size 9128576
|
31
ghc.changes
31
ghc.changes
@ -20,6 +20,37 @@ Mon Feb 23 16:48:10 UTC 2015 - peter.trommler@ohm-hochschule.de
|
||||
- drop ghc-cabal-unversion-docdir.patch
|
||||
* ghc-rpm-macros follows upstream ghc again
|
||||
|
||||
-------------------------------------------------------------------
|
||||
Wed Feb 4 11:57:35 UTC 2015 - mimi.vx@gmail.com
|
||||
|
||||
+ add ghc-glibc-2.20_BSD_SOURCE.patch from fedora
|
||||
- updated to 7.8.4
|
||||
+ removed D177.patch (in upstream)
|
||||
+ removed D173.patch (in upstream)
|
||||
+ removed ghc.git-e18525f.patch (in upstream)
|
||||
+ refresh 0001-implement-native-code-generator-for-ppc64.patch
|
||||
* A critical bug in the LLVM backend which would cause the compiler to generate incorrect code has been fixed (issue #9439).
|
||||
* Several bugs in the code generator have been fixed for unregisterised platforms, such as 64bit PowerPC (issue #8819 and #8849).
|
||||
* A bug that could cause GHC's constructor specialization pass (enabled by default at -O2, or via -fspec-constr) to loop forever and consume large amounts of memory has been fixed (issue #8960).
|
||||
* A bug that would cause GHC to fail when attempting to determine GCC's version information in non-english locales has been fixed (issue #8825).
|
||||
* A minor bug that allowed GHC to seemingly import (but not use) private data constructors has been fixed (issue #9006).
|
||||
* A bug in the register allocator which would cause GHC to crash during compilation has been fixed (issue #9303).
|
||||
* A bug that caused the compiler to panic on some input C-- code has been fixed (issue #9329).
|
||||
* A few various minor deadlocks in the runtime system when using forkProcess have been fixed.
|
||||
* A bug which made blocked STM transactions non-interruptible has been fixed (issue #9379).
|
||||
* A bug in the compiler which broke pattern synonym imports across modules in Haddock has been fixed (issue #9417).
|
||||
* A minor bug in the code generator in which the popCnt16# did not zero-extend its result has been fixed (issue #9435).
|
||||
* A bug which caused the compiler to panic on pattern synonyms inside a class declaration has been fixed (issue #9705).
|
||||
* A bug in the typechecker revolving around un-saturated type family applications has been fixed (issue #9433).
|
||||
* Several bugs have been fixed causing problems with building GHC on ARM (issues #8951, #9620, #9336, and #9552).
|
||||
* A bug in the typechecker that could cause an infinite loop when using superclasses in a cycle has been fixed (issue #9415).
|
||||
* A bug causing corruption in signal handling with the single-threaded runtime system has been fixed (issue #9817).
|
||||
* A bug that could cause compiled programs to crash due to use of overlapping type families has been fixed (issue #9371).
|
||||
* A bug in the inliner that caused certain expressions within unboxed tuples to not be properly evaluated has been fixed (issue #9390).
|
||||
* A bug that caused the compiler to not always properly detect LLVM tools (particularly on Windows) has been fixed (issue #7143).
|
||||
* A bug that prevented GHC from deriving Generic1 instances for data families has been fixed (#9563).
|
||||
* A bug that caused type inference to infer the incorrect type in the presence of certain type families and constraints has been fixed (issue #9316).
|
||||
|
||||
-------------------------------------------------------------------
|
||||
Tue Feb 3 13:35:25 UTC 2015 - mimi.vx@gmail.com
|
||||
|
||||
|
@ -1,71 +0,0 @@
|
||||
From: Sergei Trofimovich <slyfox@gentoo.org>
|
||||
Date: Thu, 4 Sep 2014 14:50:45 +0000 (+0300)
|
||||
Subject: pprC: declare extern cmm primitives as functions, not data
|
||||
X-Git-Url: https://git.haskell.org/ghc.git/commitdiff_plain/e18525fae273f4c1ad8d6cbe1dea4fc074cac721
|
||||
|
||||
pprC: declare extern cmm primitives as functions, not data
|
||||
|
||||
Summary:
|
||||
The commit fixes incorrect code generation of
|
||||
integer-gmp package on ia64 due to C prototypes mismatch.
|
||||
Before the patch prototypes for "foreign import prim" were:
|
||||
StgWord poizh[];
|
||||
After the patch they became:
|
||||
StgFunPtr poizh();
|
||||
|
||||
Long story:
|
||||
|
||||
Consider the following simple example:
|
||||
|
||||
{-# LANGUAGE MagicHash, GHCForeignImportPrim, UnliftedFFITypes #-}
|
||||
module M where
|
||||
import GHC.Prim -- Int#
|
||||
foreign import prim "poizh" poi# :: Int# -> Int#
|
||||
|
||||
Before the patch unregisterised build generated the
|
||||
following 'poizh' reference:
|
||||
EI_(poizh); /* StgWord poizh[]; */
|
||||
FN_(M_poizh_entry) {
|
||||
// ...
|
||||
JMP_((W_)&poizh);
|
||||
}
|
||||
|
||||
After the patch it looks this way:
|
||||
EF_(poizh); /* StgFunPtr poizh(); */
|
||||
FN_(M_poizh_entry) {
|
||||
// ...
|
||||
JMP_((W_)&poizh);
|
||||
}
|
||||
|
||||
On ia64 it leads to different relocation types being generated:
|
||||
incorrect one:
|
||||
addl r14 = @ltoffx(poizh#)
|
||||
ld8.mov r14 = [r14], poizh# ; r14 = address-of 'poizh#'
|
||||
correct one:
|
||||
addl r14 = @ltoff(@fptr(poizh#)), gp ; r14 = address-of-thunk 'poizh#'
|
||||
ld8 r14 = [r14]
|
||||
|
||||
'@fptr(poizh#)' basically instructs assembler to creates
|
||||
another obect consisting of real address to 'poizh' instructions
|
||||
and module address. That '@fptr' object is used as a function "address"
|
||||
This object is different for every module referencing 'poizh' symbol.
|
||||
|
||||
All indirect function calls expect '@fptr' object. That way
|
||||
call site reads real destination address and set destination
|
||||
module address in 'gp' register from '@fptr'.
|
||||
|
||||
Signed-off-by: Sergei Trofimovich <slyfox@gentoo.org>
|
||||
---
|
||||
|
||||
Index: ghc-7.8.3/compiler/cmm/CLabel.hs
|
||||
===================================================================
|
||||
--- ghc-7.8.3.orig/compiler/cmm/CLabel.hs
|
||||
+++ ghc-7.8.3/compiler/cmm/CLabel.hs
|
||||
@@ -801,6 +801,7 @@ labelType (CmmLabel _ _ CmmClosure)
|
||||
labelType (CmmLabel _ _ CmmCode) = CodeLabel
|
||||
labelType (CmmLabel _ _ CmmInfo) = DataLabel
|
||||
labelType (CmmLabel _ _ CmmEntry) = CodeLabel
|
||||
+labelType (CmmLabel _ _ CmmPrimCall) = CodeLabel
|
||||
labelType (CmmLabel _ _ CmmRetInfo) = DataLabel
|
||||
labelType (CmmLabel _ _ CmmRet) = CodeLabel
|
||||
labelType (RtsLabel (RtsSelectorInfoTable _ _)) = DataLabel
|
27
ghc.spec
27
ghc.spec
@ -19,14 +19,13 @@
|
||||
%global unregisterised_archs ppc64le s390 s390s
|
||||
|
||||
Name: ghc
|
||||
Version: 7.8.3
|
||||
Version: 7.8.4
|
||||
Release: 0
|
||||
Url: http://haskell.org/ghc/dist/%{version}/%{name}-%{version}-src.tar.bz2
|
||||
Summary: The Glorious Glasgow Haskell Compiler
|
||||
License: BSD-3-Clause
|
||||
Group: Development/Languages/Other
|
||||
ExclusiveArch: %{ix86} x86_64 ppc ppc64 ppc64le
|
||||
|
||||
BuildRequires: binutils-devel
|
||||
BuildRequires: gcc
|
||||
BuildRequires: ghc-bootstrap >= 7.4
|
||||
@ -35,6 +34,9 @@ BuildRequires: glibc-devel
|
||||
BuildRequires: gmp-devel
|
||||
BuildRequires: libelf-devel
|
||||
BuildRequires: libffi-devel
|
||||
%ifnarch ppc
|
||||
BuildRequires: llvm
|
||||
%endif
|
||||
BuildRequires: ncurses-devel
|
||||
BuildRequires: pkg-config
|
||||
BuildRequires: xz
|
||||
@ -61,12 +63,6 @@ Patch12: D349.patch
|
||||
Patch13: integer-gmp.patch
|
||||
# PATCH-FIX-UPSTREAM ghc-7.8.2-cgen-constify.patch peter.trommler@ohm-hochschule.de - Make constant strings constant in C backend to save data segment space. This is a gentoo patch.
|
||||
Patch14: ghc-7.8.2-cgen-constify.patch
|
||||
# PATCH-FIX-UPSTREAM D173.patch peter.trommler@ohm-hochschule.de -- Fix C backend. Backport of upstream fix for 7.10. See https://phabricator.haskell.org/D173.
|
||||
Patch15: D173.patch
|
||||
# PATCH-FIX-UPSTREAM D177.patch peter.trommler@ohm-hochschule.de -- Pass PIC flags to assembler. See https://phabricator.haskell.org/D177.
|
||||
Patch16: D177.patch
|
||||
# PATCH-FIX-UPSTREAM ghc.git-e18525f.patch peter.trommler@ohm-hochschule.de -- Declare extern cmm primitives as functions not data. Backport of upstream fix for 7.10. See https://git.haskell.org/ghc.git/commitdiff_plain/e18525fae273f4c1ad8d6cbe1dea4fc074cac721.
|
||||
Patch17: ghc.git-e18525f.patch
|
||||
# PATCH-FIX-UPSTREAM D560.patch peter.trommler@ohm-hochschule.de -- Fix loading of PIC register. See https://phabricator.haskell.org/D560.
|
||||
Patch18: D560.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.
|
||||
@ -116,9 +112,9 @@ 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.18.1.3
|
||||
%ghc_lib_subpackage Cabal 1.18.1.5
|
||||
%ghc_lib_subpackage array 0.5.0.0
|
||||
%ghc_lib_subpackage -c gmp-devel,libffi-devel base 4.7.0.1
|
||||
%ghc_lib_subpackage -c gmp-devel,libffi-devel base 4.7.0.2
|
||||
%ghc_lib_subpackage binary 0.7.1.0
|
||||
%ghc_lib_subpackage bytestring 0.10.4.0
|
||||
%ghc_lib_subpackage containers 0.5.5.1
|
||||
@ -167,9 +163,6 @@ except the ghc library, which is installed by the toplevel ghc metapackage.
|
||||
%patch12 -p1
|
||||
%patch13 -p1
|
||||
%patch14 -p1
|
||||
%patch15 -p1
|
||||
%patch16 -p1
|
||||
%patch17 -p1
|
||||
%patch18 -p1
|
||||
%patch19 -p1
|
||||
%patch20 -p1
|
||||
@ -345,13 +338,13 @@ rm testghc/*
|
||||
# groups under a single name 'runhaskell'. Either these tools should be
|
||||
# disentangled from the Haskell implementations or all implementations should
|
||||
# have the same set of tools. *sigh*
|
||||
"%_sbindir/update-alternatives" --install %{_bindir}/runhaskell runhaskell %{_bindir}/runghc 500
|
||||
"%_sbindir/update-alternatives" --install %{_bindir}/hsc2hs hsc2hs %{_bindir}/hsc2hs-ghc 500
|
||||
"%{_sbindir}/update-alternatives" --install %{_bindir}/runhaskell runhaskell %{_bindir}/runghc 500
|
||||
"%{_sbindir}/update-alternatives" --install %{_bindir}/hsc2hs hsc2hs %{_bindir}/hsc2hs-ghc 500
|
||||
|
||||
%preun compiler
|
||||
if test "$1" = 0; then
|
||||
"%_sbindir/update-alternatives" --remove runhaskell %{_bindir}/runghc
|
||||
"%_sbindir/update-alternatives" --remove hsc2hs %{_bindir}/hsc2hs-ghc
|
||||
"%{_sbindir}/update-alternatives" --remove runhaskell %{_bindir}/runghc
|
||||
"%{_sbindir}/update-alternatives" --remove hsc2hs %{_bindir}/hsc2hs-ghc
|
||||
fi
|
||||
|
||||
%files
|
||||
|
Loading…
x
Reference in New Issue
Block a user