rebase to 9.2.5 from ghc9.2
This commit is contained in:
parent
2cf80b12e6
commit
a15483db6e
256
7689.patch
256
7689.patch
@ -1,256 +0,0 @@
|
||||
From 18d7007e0cd1140936b803df4816110cee0ed086 Mon Sep 17 00:00:00 2001
|
||||
From: Ben Gamari <ben@smart-cactus.org>
|
||||
Date: Tue, 1 Mar 2022 13:49:57 -0500
|
||||
Subject: [PATCH 1/2] rts: Factor out built-in GC roots
|
||||
|
||||
---
|
||||
rts/RtsStartup.c | 76 ++++++++++++++++++++++++++----------------------
|
||||
1 file changed, 41 insertions(+), 35 deletions(-)
|
||||
|
||||
diff --git a/rts/RtsStartup.c b/rts/RtsStartup.c
|
||||
index 347434420b02..e412715cdf55 100644
|
||||
--- a/rts/RtsStartup.c
|
||||
+++ b/rts/RtsStartup.c
|
||||
@@ -174,6 +174,45 @@ hs_restoreConsoleCP (void)
|
||||
Starting up the RTS
|
||||
-------------------------------------------------------------------------- */
|
||||
|
||||
+static void initBuiltinGcRoots(void)
|
||||
+{
|
||||
+ /* Add some GC roots for things in the base package that the RTS
|
||||
+ * knows about. We don't know whether these turn out to be CAFs
|
||||
+ * or refer to CAFs, but we have to assume that they might.
|
||||
+ *
|
||||
+ * Because these stable pointers will retain any CAF references in
|
||||
+ * these closures `Id`s of these can be safely marked as non-CAFFY
|
||||
+ * in the compiler.
|
||||
+ */
|
||||
+ getStablePtr((StgPtr)runIO_closure);
|
||||
+ getStablePtr((StgPtr)runNonIO_closure);
|
||||
+ getStablePtr((StgPtr)flushStdHandles_closure);
|
||||
+
|
||||
+ getStablePtr((StgPtr)runFinalizerBatch_closure);
|
||||
+
|
||||
+ getStablePtr((StgPtr)stackOverflow_closure);
|
||||
+ getStablePtr((StgPtr)heapOverflow_closure);
|
||||
+ getStablePtr((StgPtr)unpackCString_closure);
|
||||
+ getStablePtr((StgPtr)blockedIndefinitelyOnMVar_closure);
|
||||
+ getStablePtr((StgPtr)nonTermination_closure);
|
||||
+ getStablePtr((StgPtr)blockedIndefinitelyOnSTM_closure);
|
||||
+ getStablePtr((StgPtr)allocationLimitExceeded_closure);
|
||||
+ getStablePtr((StgPtr)cannotCompactFunction_closure);
|
||||
+ getStablePtr((StgPtr)cannotCompactPinned_closure);
|
||||
+ getStablePtr((StgPtr)cannotCompactMutable_closure);
|
||||
+ getStablePtr((StgPtr)nestedAtomically_closure);
|
||||
+ getStablePtr((StgPtr)runSparks_closure);
|
||||
+ getStablePtr((StgPtr)ensureIOManagerIsRunning_closure);
|
||||
+ getStablePtr((StgPtr)interruptIOManager_closure);
|
||||
+ getStablePtr((StgPtr)ioManagerCapabilitiesChanged_closure);
|
||||
+#if !defined(mingw32_HOST_OS)
|
||||
+ getStablePtr((StgPtr)blockedOnBadFD_closure);
|
||||
+ getStablePtr((StgPtr)runHandlersPtr_closure);
|
||||
+#else
|
||||
+ getStablePtr((StgPtr)processRemoteCompletion_closure);
|
||||
+#endif
|
||||
+}
|
||||
+
|
||||
void
|
||||
hs_init(int *argc, char **argv[])
|
||||
{
|
||||
@@ -311,41 +350,8 @@ hs_init_ghc(int *argc, char **argv[], RtsConfig rts_config)
|
||||
/* initialise the stable name table */
|
||||
initStableNameTable();
|
||||
|
||||
- /* Add some GC roots for things in the base package that the RTS
|
||||
- * knows about. We don't know whether these turn out to be CAFs
|
||||
- * or refer to CAFs, but we have to assume that they might.
|
||||
- *
|
||||
- * Because these stable pointers will retain any CAF references in
|
||||
- * these closures `Id`s of these can be safely marked as non-CAFFY
|
||||
- * in the compiler.
|
||||
- */
|
||||
- getStablePtr((StgPtr)runIO_closure);
|
||||
- getStablePtr((StgPtr)runNonIO_closure);
|
||||
- getStablePtr((StgPtr)flushStdHandles_closure);
|
||||
-
|
||||
- getStablePtr((StgPtr)runFinalizerBatch_closure);
|
||||
-
|
||||
- getStablePtr((StgPtr)stackOverflow_closure);
|
||||
- getStablePtr((StgPtr)heapOverflow_closure);
|
||||
- getStablePtr((StgPtr)unpackCString_closure);
|
||||
- getStablePtr((StgPtr)blockedIndefinitelyOnMVar_closure);
|
||||
- getStablePtr((StgPtr)nonTermination_closure);
|
||||
- getStablePtr((StgPtr)blockedIndefinitelyOnSTM_closure);
|
||||
- getStablePtr((StgPtr)allocationLimitExceeded_closure);
|
||||
- getStablePtr((StgPtr)cannotCompactFunction_closure);
|
||||
- getStablePtr((StgPtr)cannotCompactPinned_closure);
|
||||
- getStablePtr((StgPtr)cannotCompactMutable_closure);
|
||||
- getStablePtr((StgPtr)nestedAtomically_closure);
|
||||
- getStablePtr((StgPtr)runSparks_closure);
|
||||
- getStablePtr((StgPtr)ensureIOManagerIsRunning_closure);
|
||||
- getStablePtr((StgPtr)interruptIOManager_closure);
|
||||
- getStablePtr((StgPtr)ioManagerCapabilitiesChanged_closure);
|
||||
-#if !defined(mingw32_HOST_OS)
|
||||
- getStablePtr((StgPtr)blockedOnBadFD_closure);
|
||||
- getStablePtr((StgPtr)runHandlersPtr_closure);
|
||||
-#else
|
||||
- getStablePtr((StgPtr)processRemoteCompletion_closure);
|
||||
-#endif
|
||||
+ /* create StablePtrs for builtin GC roots*/
|
||||
+ initBuiltinGcRoots();
|
||||
|
||||
/*
|
||||
* process any foreign exports which were registered while loading the
|
||||
--
|
||||
GitLab
|
||||
|
||||
|
||||
From 2ac45ba0ff0ab2911ecfe443e54df6f30eec5ff5 Mon Sep 17 00:00:00 2001
|
||||
From: Ben Gamari <ben@smart-cactus.org>
|
||||
Date: Tue, 1 Mar 2022 13:50:20 -0500
|
||||
Subject: [PATCH 2/2] Ensure that wired-in exception closures aren't GC'd
|
||||
|
||||
As described in Note [Wired-in exceptions are not CAFfy], a small set of
|
||||
built-in exception closures get special treatment in the code generator,
|
||||
being declared as non-CAFfy despite potentially containing CAF
|
||||
references. The original intent of this treatment for the RTS to then
|
||||
add StablePtrs for each of the closures, ensuring that they are not
|
||||
GC'd. However, this logic was not applied consistently and eventually
|
||||
removed entirely in 951c1fb0. This lead to #21141.
|
||||
|
||||
Here we fix this bug by reintroducing the StablePtrs and document the
|
||||
status quo.
|
||||
|
||||
Closes #21141.
|
||||
---
|
||||
compiler/GHC/Core/Make.hs | 25 ++++++++++++++++++++++--
|
||||
libraries/ghc-prim/GHC/Prim/Exception.hs | 3 ++-
|
||||
rts/Prelude.h | 10 ++++++++++
|
||||
rts/RtsStartup.c | 6 ++++++
|
||||
4 files changed, 41 insertions(+), 3 deletions(-)
|
||||
|
||||
diff --git a/compiler/GHC/Core/Make.hs b/compiler/GHC/Core/Make.hs
|
||||
index 619b7adaf403..ff824158c3de 100644
|
||||
--- a/compiler/GHC/Core/Make.hs
|
||||
+++ b/compiler/GHC/Core/Make.hs
|
||||
@@ -816,7 +816,9 @@ tYPE_ERROR_ID = mkRuntimeErrorId typeErrorName
|
||||
-- argument would require allocating a thunk.
|
||||
--
|
||||
-- 4. it can't be CAFFY because that would mean making some non-CAFFY
|
||||
--- definitions that use unboxed sums CAFFY in unarise.
|
||||
+-- definitions that use unboxed sums CAFFY in unarise. We work around
|
||||
+-- this by declaring the absentSumFieldError as non-CAFfy, as described
|
||||
+-- in Note [Wired-in exceptions are not CAFfy].
|
||||
--
|
||||
-- Getting this wrong causes hard-to-debug runtime issues, see #15038.
|
||||
--
|
||||
@@ -850,6 +852,21 @@ tYPE_ERROR_ID = mkRuntimeErrorId typeErrorName
|
||||
-- error. That's why it is OK for it to be un-catchable.
|
||||
--
|
||||
|
||||
+-- Note [Wired-in exceptions are not CAFfy]
|
||||
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
||||
+-- mkExceptionId claims that all exceptions are not CAFfy, despite the fact
|
||||
+-- that their closures' code may in fact contain CAF references. We get away
|
||||
+-- with this lie because the RTS ensures that all exception closures are
|
||||
+-- considered live by the GC by creating StablePtrs during initialization.
|
||||
+-- The lie is necessary to avoid unduly growing SRTs as these exceptions are
|
||||
+-- sufficiently common to warrant special treatment.
|
||||
+--
|
||||
+-- At some point we could consider removing this optimisation as it is quite
|
||||
+-- fragile, but we do want to be careful to avoid adding undue cost. Unboxed
|
||||
+-- sums in particular are intended to be used in performance-critical contexts.
|
||||
+--
|
||||
+-- See #15038, #21141.
|
||||
+
|
||||
absentSumFieldErrorName
|
||||
= mkWiredInIdName
|
||||
gHC_PRIM_PANIC
|
||||
@@ -884,6 +901,9 @@ rAISE_UNDERFLOW_ID = mkExceptionId raiseUnderflowName
|
||||
rAISE_DIVZERO_ID = mkExceptionId raiseDivZeroName
|
||||
|
||||
-- | Exception with type \"forall a. a\"
|
||||
+--
|
||||
+-- Any exceptions added via this function needs to be added to
|
||||
+-- the RTS's initBuiltinGcRoots() function.
|
||||
mkExceptionId :: Name -> Id
|
||||
mkExceptionId name
|
||||
= mkVanillaGlobalWithInfo name
|
||||
@@ -891,7 +911,8 @@ mkExceptionId name
|
||||
(vanillaIdInfo `setStrictnessInfo` mkClosedStrictSig [] botDiv
|
||||
`setCprInfo` mkCprSig 0 botCpr
|
||||
`setArityInfo` 0
|
||||
- `setCafInfo` NoCafRefs) -- #15038
|
||||
+ `setCafInfo` NoCafRefs)
|
||||
+ -- See Note [Wired-in exceptions are not CAFfy]
|
||||
|
||||
mkRuntimeErrorId :: Name -> Id
|
||||
-- Error function
|
||||
diff --git a/libraries/ghc-prim/GHC/Prim/Exception.hs b/libraries/ghc-prim/GHC/Prim/Exception.hs
|
||||
index 36889dc1e325..0ab17946150e 100644
|
||||
--- a/libraries/ghc-prim/GHC/Prim/Exception.hs
|
||||
+++ b/libraries/ghc-prim/GHC/Prim/Exception.hs
|
||||
@@ -20,13 +20,14 @@ default () -- Double and Integer aren't available yet
|
||||
|
||||
-- Note [Arithmetic exceptions]
|
||||
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
||||
---
|
||||
-- ghc-prim provides several functions to raise arithmetic exceptions
|
||||
-- (raiseDivZero, raiseUnderflow, raiseOverflow) that are wired-in the RTS.
|
||||
-- These exceptions are meant to be used by the package implementing arbitrary
|
||||
-- precision numbers (Natural,Integer). It can't depend on `base` package to
|
||||
-- raise exceptions in a normal way because it would create a dependency
|
||||
-- cycle (base <-> bignum package). See #14664
|
||||
+--
|
||||
+-- See also: Note [Wired-in exceptions are not CAFfy] in GHC.Core.Make.
|
||||
|
||||
foreign import prim "stg_raiseOverflowzh" raiseOverflow# :: State# RealWorld -> (# State# RealWorld, Void# #)
|
||||
foreign import prim "stg_raiseUnderflowzh" raiseUnderflow# :: State# RealWorld -> (# State# RealWorld, Void# #)
|
||||
diff --git a/rts/Prelude.h b/rts/Prelude.h
|
||||
index d2511b2fc3b6..5f1e070e331f 100644
|
||||
--- a/rts/Prelude.h
|
||||
+++ b/rts/Prelude.h
|
||||
@@ -19,6 +19,12 @@
|
||||
#define PRELUDE_CLOSURE(i) extern StgClosure DLL_IMPORT_DATA_VARNAME(i)
|
||||
#endif
|
||||
|
||||
+/* See Note [Wired-in exceptions are not CAFfy] in GHC.Core.Make. */
|
||||
+PRELUDE_CLOSURE(ghczmprim_GHCziPrimziPanic_absentSumFieldError_closure);
|
||||
+PRELUDE_CLOSURE(ghczmprim_GHCziPrimziException_raiseUnderflow_closure);
|
||||
+PRELUDE_CLOSURE(ghczmprim_GHCziPrimziException_raiseOverflow_closure);
|
||||
+PRELUDE_CLOSURE(ghczmprim_GHCziPrimziException_raiseDivZZero_closure);
|
||||
+
|
||||
/* Define canonical names so we can abstract away from the actual
|
||||
* modules these names are defined in.
|
||||
*/
|
||||
@@ -111,6 +117,10 @@ PRELUDE_INFO(base_GHCziStable_StablePtr_con_info);
|
||||
#define nonTermination_closure DLL_IMPORT_DATA_REF(base_ControlziExceptionziBase_nonTermination_closure)
|
||||
#define nestedAtomically_closure DLL_IMPORT_DATA_REF(base_ControlziExceptionziBase_nestedAtomically_closure)
|
||||
#define doubleReadException DLL_IMPORT_DATA_REF(base_GHCziIOPort_doubleReadException_closure)
|
||||
+#define absentSumFieldError_closure DLL_IMPORT_DATA_REF(ghczmprim_GHCziPrimziPanic_absentSumFieldError_closure)
|
||||
+#define raiseUnderflowException_closure DLL_IMPORT_DATA_REF(ghczmprim_GHCziPrimziException_raiseUnderflow_closure)
|
||||
+#define raiseOverflowException_closure DLL_IMPORT_DATA_REF(ghczmprim_GHCziPrimziException_raiseOverflow_closure)
|
||||
+#define raiseDivZeroException_closure DLL_IMPORT_DATA_REF(ghczmprim_GHCziPrimziException_raiseDivZZero_closure)
|
||||
|
||||
#define blockedOnBadFD_closure DLL_IMPORT_DATA_REF(base_GHCziEventziThread_blockedOnBadFD_closure)
|
||||
|
||||
diff --git a/rts/RtsStartup.c b/rts/RtsStartup.c
|
||||
index e412715cdf55..79c6e3f6b88a 100644
|
||||
--- a/rts/RtsStartup.c
|
||||
+++ b/rts/RtsStartup.c
|
||||
@@ -211,6 +211,12 @@ static void initBuiltinGcRoots(void)
|
||||
#else
|
||||
getStablePtr((StgPtr)processRemoteCompletion_closure);
|
||||
#endif
|
||||
+
|
||||
+ /* See Note [Wired-in exceptions are not CAFfy] in GHC.Core.Make. */
|
||||
+ getStablePtr((StgPtr)absentSumFieldError_closure);
|
||||
+ getStablePtr((StgPtr)raiseUnderflowException_closure);
|
||||
+ getStablePtr((StgPtr)raiseOverflowException_closure);
|
||||
+ getStablePtr((StgPtr)raiseDivZeroException_closure);
|
||||
}
|
||||
|
||||
void
|
||||
--
|
||||
GitLab
|
||||
|
93
9aace0eaf6279f17368a1753b65afbdc466e8291.patch
Normal file
93
9aace0eaf6279f17368a1753b65afbdc466e8291.patch
Normal file
@ -0,0 +1,93 @@
|
||||
From 9aace0eaf6279f17368a1753b65afbdc466e8291 Mon Sep 17 00:00:00 2001
|
||||
From: Sylvain Henry <sylvain@haskus.fr>
|
||||
Date: Sat, 10 Apr 2021 14:48:16 +0200
|
||||
Subject: [PATCH] Produce constant file atomically (#19684)
|
||||
|
||||
---
|
||||
utils/deriveConstants/Main.hs | 21 ++++++++++++++++-----
|
||||
utils/deriveConstants/deriveConstants.cabal | 3 ++-
|
||||
2 files changed, 18 insertions(+), 6 deletions(-)
|
||||
|
||||
diff --git a/utils/deriveConstants/Main.hs b/utils/deriveConstants/Main.hs
|
||||
index 8bf8ae7b44d..9db673a9852 100644
|
||||
--- a/utils/deriveConstants/Main.hs
|
||||
+++ b/utils/deriveConstants/Main.hs
|
||||
@@ -34,9 +34,10 @@ import Data.Maybe (catMaybes, mapMaybe, fromMaybe)
|
||||
import Numeric (readHex)
|
||||
import System.Environment (getArgs)
|
||||
import System.Exit (ExitCode(ExitSuccess), exitFailure)
|
||||
-import System.FilePath ((</>))
|
||||
+import System.FilePath ((</>),(<.>))
|
||||
import System.IO (stderr, hPutStrLn)
|
||||
import System.Process (showCommandForUser, readProcess, rawSystem)
|
||||
+import System.Directory (renameFile)
|
||||
|
||||
main :: IO ()
|
||||
main = do opts <- parseArgs
|
||||
@@ -79,6 +80,16 @@ data Options = Options {
|
||||
o_targetOS :: Maybe String
|
||||
}
|
||||
|
||||
+-- | Write a file atomically
|
||||
+--
|
||||
+-- This avoids other processes seeing the file while it is being written into.
|
||||
+atomicWriteFile :: FilePath -> String -> IO ()
|
||||
+atomicWriteFile fn s = do
|
||||
+ let tmp = fn <.> "tmp"
|
||||
+ writeFile tmp s
|
||||
+ renameFile tmp fn
|
||||
+
|
||||
+
|
||||
parseArgs :: IO Options
|
||||
parseArgs = do args <- getArgs
|
||||
opts <- f emptyOptions args
|
||||
@@ -670,7 +681,7 @@ getWanted verbose os tmpdir gccProgram gccFlags nmProgram mobjdumpProgram
|
||||
= do let cStuff = unlines (headers ++ concatMap (doWanted . snd) (wanteds os))
|
||||
cFile = tmpdir </> "tmp.c"
|
||||
oFile = tmpdir </> "tmp.o"
|
||||
- writeFile cFile cStuff
|
||||
+ atomicWriteFile cFile cStuff
|
||||
execute verbose gccProgram (gccFlags ++ ["-c", cFile, "-o", oFile])
|
||||
xs <- case os of
|
||||
"openbsd" -> readProcess objdumpProgam ["--syms", oFile] ""
|
||||
@@ -855,7 +866,7 @@ getWanted verbose os tmpdir gccProgram gccFlags nmProgram mobjdumpProgram
|
||||
= return (w, FieldTypeGcptrMacro name)
|
||||
|
||||
writeHaskellType :: FilePath -> [What Fst] -> IO ()
|
||||
-writeHaskellType fn ws = writeFile fn xs
|
||||
+writeHaskellType fn ws = atomicWriteFile fn xs
|
||||
where xs = unlines [header, body, footer, parser]
|
||||
header = "module GHC.Platform.Constants where\n\n\
|
||||
\import Prelude\n\
|
||||
@@ -920,7 +931,7 @@ writeHaskellType fn ws = writeFile fn xs
|
||||
|
||||
|
||||
writeHaskellValue :: FilePath -> [What Snd] -> IO ()
|
||||
-writeHaskellValue fn rs = writeFile fn xs
|
||||
+writeHaskellValue fn rs = atomicWriteFile fn xs
|
||||
where xs = unlines [header, body, footer]
|
||||
header = "PlatformConstants {"
|
||||
footer = " }"
|
||||
@@ -937,7 +948,7 @@ writeHaskellValue fn rs = writeFile fn xs
|
||||
doWhat (FieldTypeGcptrMacro {}) = []
|
||||
|
||||
writeHeader :: FilePath -> [(Where, What Snd)] -> IO ()
|
||||
-writeHeader fn rs = writeFile fn xs
|
||||
+writeHeader fn rs = atomicWriteFile fn xs
|
||||
where xs = headers ++ hs ++ unlines body
|
||||
headers = "/* This file is created automatically. Do not edit by hand.*/\n\n"
|
||||
haskellRs = fmap snd $ filter (\r -> fst r `elem` [Haskell,Both]) rs
|
||||
diff --git a/utils/deriveConstants/deriveConstants.cabal b/utils/deriveConstants/deriveConstants.cabal
|
||||
index 50b5b695c30..36ba7ebe1f7 100644
|
||||
--- a/utils/deriveConstants/deriveConstants.cabal
|
||||
+++ b/utils/deriveConstants/deriveConstants.cabal
|
||||
@@ -20,4 +20,5 @@ Executable deriveConstants
|
||||
Build-Depends: base >= 4 && < 5,
|
||||
containers,
|
||||
process,
|
||||
- filepath
|
||||
+ filepath,
|
||||
+ directory
|
||||
--
|
||||
GitLab
|
||||
|
@ -1,35 +0,0 @@
|
||||
--- ghc-8.6.3/docs/users_guide/flags.py~ 2018-09-21 06:18:23.000000000 +0800
|
||||
+++ ghc-8.6.3/docs/users_guide/flags.py 2019-03-05 10:20:38.639782096 +0800
|
||||
@@ -49,6 +49,8 @@
|
||||
import sphinx
|
||||
from sphinx import addnodes
|
||||
from sphinx.domains.std import GenericObject
|
||||
+from sphinx.domains import ObjType
|
||||
+from sphinx.roles import XRefRole
|
||||
from sphinx.errors import SphinxError
|
||||
from distutils.version import LooseVersion
|
||||
from utils import build_table_from_list
|
||||
@@ -603,14 +605,21 @@
|
||||
sphinx_version = LooseVersion(sphinx.__version__)
|
||||
override_arg = {'override': True} if sphinx_version >= LooseVersion('1.8') else {}
|
||||
|
||||
+ # Yuck: We can't use app.add_object_type since we need to provide the
|
||||
+ # Directive instance ourselves.
|
||||
+ std_object_types = app.registry.domain_object_types.setdefault('std', {})
|
||||
+
|
||||
# Add ghc-flag directive, and override the class with our own
|
||||
- app.add_object_type('ghc-flag', 'ghc-flag')
|
||||
app.add_directive_to_domain('std', 'ghc-flag', Flag, **override_arg)
|
||||
+ app.add_role_to_domain('std', 'ghc-flag', XRefRole())
|
||||
+ std_object_types['ghc-flag'] = ObjType('ghc-flag', 'ghc-flag')
|
||||
|
||||
# Add extension directive, and override the class with our own
|
||||
- app.add_object_type('extension', 'extension')
|
||||
app.add_directive_to_domain('std', 'extension', LanguageExtension,
|
||||
**override_arg)
|
||||
+ app.add_role_to_domain('std', 'extension', XRefRole())
|
||||
+ std_object_types['extension'] = ObjType('ghc-flag', 'ghc-flag')
|
||||
+
|
||||
# NB: language-extension would be misinterpreted by sphinx, and produce
|
||||
# lang="extensions" XML attributes
|
||||
|
9
ghc-9.2.1-hadrian-s390x-rts--qg.patch
Normal file
9
ghc-9.2.1-hadrian-s390x-rts--qg.patch
Normal file
@ -0,0 +1,9 @@
|
||||
--- ghc-9.2.1/hadrian/hadrian.cabal~ 2021-10-29 04:41:34.000000000 +0800
|
||||
+++ ghc-9.2.1/hadrian/hadrian.cabal 2021-11-01 15:02:49.625656704 +0800
|
||||
@@ -162,5 +162,5 @@
|
||||
-- waiting for external processes
|
||||
-- * -qg: Don't use parallel GC as the synchronization
|
||||
-- time tends to eat any benefit.
|
||||
- "-with-rtsopts=-I0 -qg"
|
||||
+ "-with-rtsopts=-I0"
|
||||
-threaded
|
@ -1,5 +1,5 @@
|
||||
--- ghc-8.2.2/libraries/Cabal/Cabal/Distribution/Simple/Install.hs~ 2017-05-05 23:51:43.000000000 +0900
|
||||
+++ ghc-8.2.2/libraries/Cabal/Cabal/Distribution/Simple/Install.hs 2018-02-27 12:22:13.159432104 +0900
|
||||
--- ghc/libraries/Cabal/Cabal/src/Distribution/Simple/Install.hs~ 2017-05-05 23:51:43.000000000 +0900
|
||||
+++ ghc/libraries/Cabal/Cabal/src/Distribution/Simple/Install.hs 2018-02-27 12:22:13.159432104 +0900
|
||||
@@ -215,8 +215,7 @@
|
||||
++ " in " ++ binPref)
|
||||
inPath <- isInSearchPath binPref
|
||||
|
398
ghc.spec
398
ghc.spec
@ -5,12 +5,25 @@
|
||||
# make sure ghc libraries' ABI hashes unchanged
|
||||
%bcond abicheck 1
|
||||
|
||||
%global ghc_major 9.0
|
||||
# use Hadrian buildsystem for production builds
|
||||
%bcond hadrian 1
|
||||
|
||||
# build hadrian for production builds:
|
||||
%bcond build_hadrian 1
|
||||
|
||||
# enable debuginfo for production builds
|
||||
%bcond ghc_debuginfo 1
|
||||
|
||||
%if %{without ghc_debuginfo}
|
||||
%undefine _enable_debug_packages
|
||||
%endif
|
||||
|
||||
%global ghc_major 9.2
|
||||
|
||||
# to handle RCs
|
||||
%global ghc_release %{version}
|
||||
|
||||
%global base_ver 4.15.1.0
|
||||
%global base_ver 4.16.4.0
|
||||
%global ghc_compact_ver 0.1.0.0
|
||||
%global hpc_ver 0.6.1.0
|
||||
|
||||
@ -18,17 +31,30 @@
|
||||
# perf production build (disable for quick build)
|
||||
%if %{with prodbuild}
|
||||
%bcond ghc_prof 1
|
||||
# https://gitlab.haskell.org/ghc/ghc/-/issues/19754
|
||||
# https://github.com/haskell/haddock/issues/1384
|
||||
%ifarch armv7hl
|
||||
%undefine with_haddock
|
||||
%else
|
||||
%bcond haddock 1
|
||||
%endif
|
||||
%if %{with hadrian}
|
||||
%bcond manual 1
|
||||
%endif
|
||||
%bcond perf_build 1
|
||||
%else
|
||||
%undefine with_ghc_prof
|
||||
%undefine with_haddock
|
||||
%if %{with hadrian}
|
||||
%bcond manual 0
|
||||
%endif
|
||||
%bcond perf_build 0
|
||||
%undefine _enable_debug_packages
|
||||
%endif
|
||||
|
||||
%if %{without hadrian}
|
||||
# to enable dwarf info (only on intel archs): overrides perf
|
||||
# disabled 0 by default
|
||||
# Not setup yet for hadrian
|
||||
%ifarch x86_64 i686
|
||||
%bcond dwarf 0
|
||||
%endif
|
||||
@ -37,15 +63,20 @@
|
||||
# and disabling haddock still created index.html
|
||||
# https://gitlab.haskell.org/ghc/ghc/-/issues/15190
|
||||
%{?with_haddock:%bcond manual 1}
|
||||
%endif
|
||||
|
||||
# no longer build testsuite (takes time and not really being used)
|
||||
%bcond testsuite 0
|
||||
|
||||
# 9.0.2 recommends llvm 9-12
|
||||
# 9.2 needs llvm 9-12
|
||||
%global llvm_major 12
|
||||
%global ghc_llvm_archs armv7hl aarch64
|
||||
|
||||
%if %{with hadrian}
|
||||
%global ghc_llvm_archs armv7hl s390x
|
||||
%global ghc_unregisterized_arches s390 %{mips} riscv64
|
||||
%else
|
||||
%global ghc_llvm_archs armv7hl
|
||||
%global ghc_unregisterized_arches s390 s390x %{mips} riscv64
|
||||
%endif
|
||||
|
||||
%global obsoletes_ghcXY() \
|
||||
Obsoletes: ghc%{ghc_major}%{?1:-%1} < %{version}-%{release}\
|
||||
@ -53,12 +84,12 @@ Provides: ghc%{ghc_major}%{?1:-%1} = %{version}-%{release}\
|
||||
%{nil}
|
||||
|
||||
Name: ghc
|
||||
Version: 9.0.2
|
||||
Version: 9.2.5
|
||||
# Since library subpackages are versioned:
|
||||
# - release can only be reset if *all* library versions get bumped simultaneously
|
||||
# (sometimes after a major release)
|
||||
# - minor release numbers for a branch should be incremented monotonically
|
||||
Release: 123%{?dist}
|
||||
Release: 125%{?dist}
|
||||
Summary: Glasgow Haskell Compiler
|
||||
|
||||
License: BSD and HaskellReport
|
||||
@ -71,22 +102,29 @@ Source2: https://downloads.haskell.org/ghc/%{ghc_release}/ghc-%{version}-src.tar
|
||||
Source5: ghc-pkg.man
|
||||
Source6: haddock.man
|
||||
Source7: runghc.man
|
||||
|
||||
# https://bugzilla.redhat.com/show_bug.cgi?id=2142238
|
||||
ExcludeArch: armv7hl
|
||||
|
||||
# absolute haddock path (was for html/libraries -> libraries)
|
||||
Patch1: ghc-gen_contents_index-haddock-path.patch
|
||||
Patch2: ghc-Cabal-install-PATH-warning.patch
|
||||
Patch3: ghc-gen_contents_index-nodocs.patch
|
||||
# https://phabricator.haskell.org/rGHC4eebc8016f68719e1ccdf460754a97d1f4d6ef05
|
||||
Patch6: ghc-8.6.3-sphinx-1.8.patch
|
||||
# https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7689 (from ghc-9.0)
|
||||
Patch7: 7689.patch
|
||||
# https://gitlab.haskell.org/ghc/ghc/-/issues/19684
|
||||
# DerivedConstants.h not produced atomically
|
||||
Patch10: https://gitlab.haskell.org/ghc/ghc/-/commit/9aace0eaf6279f17368a1753b65afbdc466e8291.patch
|
||||
|
||||
# Arch dependent patches
|
||||
# arm
|
||||
Patch11: ghc-configure-c99.patch
|
||||
|
||||
|
||||
# armv7hl patches
|
||||
Patch12: ghc-armv7-VFPv3D16--NEON.patch
|
||||
|
||||
# for unregisterized
|
||||
# https://gitlab.haskell.org/ghc/ghc/-/issues/15689
|
||||
Patch15: ghc-warnings.mk-CC-Wall.patch
|
||||
Patch16: ghc-9.2.1-hadrian-s390x-rts--qg.patch
|
||||
|
||||
# bigendian (s390x and ppc64)
|
||||
# https://gitlab.haskell.org/ghc/ghc/issues/15411
|
||||
@ -100,19 +138,16 @@ Patch18: Disable-unboxed-arrays.patch
|
||||
|
||||
# Debian patches:
|
||||
Patch24: buildpath-abi-stability.patch
|
||||
Patch25: buildpath-abi-stability-2.patch
|
||||
Patch26: no-missing-haddock-file-warning.patch
|
||||
Patch27: haddock-remove-googleapis-fonts.patch
|
||||
|
||||
Patch27: ghc-configure-c99.patch
|
||||
|
||||
# fedora ghc has been bootstrapped on
|
||||
# %%{ix86} x86_64 ppc ppc64 armv7hl s390 s390x ppc64le aarch64
|
||||
# and retired arches: alpha sparcv9 armv5tel
|
||||
# see also deprecated ghc_arches defined in ghc-srpm-macros
|
||||
# /usr/lib/rpm/macros.d/macros.ghc-srpm
|
||||
|
||||
BuildRequires: ghc-compiler > 8.8
|
||||
BuildRequires: ghc-compiler > 8.10
|
||||
# for ABI hash checking
|
||||
%if %{with abicheck}
|
||||
BuildRequires: %{name}
|
||||
@ -131,6 +166,7 @@ BuildRequires: alex
|
||||
BuildRequires: gmp-devel
|
||||
BuildRequires: libffi-devel
|
||||
BuildRequires: make
|
||||
BuildRequires: gcc-c++
|
||||
# for terminfo
|
||||
BuildRequires: ncurses-devel
|
||||
BuildRequires: perl-interpreter
|
||||
@ -146,13 +182,38 @@ BuildRequires: llvm%{llvm_major}
|
||||
%if %{with dwarf}
|
||||
BuildRequires: elfutils-devel
|
||||
%endif
|
||||
%ifarch armv7hl
|
||||
# patch12
|
||||
BuildRequires: autoconf, automake
|
||||
%endif
|
||||
%if %{with prodbuild}
|
||||
#BuildRequires: gnupg2
|
||||
%endif
|
||||
%if %{with hadrian}
|
||||
# needed for binary-dist-dir
|
||||
BuildRequires: autoconf automake
|
||||
%if %{with build_hadrian}
|
||||
BuildRequires: ghc-Cabal-static
|
||||
BuildRequires: ghc-QuickCheck-static
|
||||
BuildRequires: ghc-base-static
|
||||
BuildRequires: ghc-bytestring-static
|
||||
BuildRequires: ghc-containers-static
|
||||
BuildRequires: ghc-directory-static
|
||||
BuildRequires: ghc-extra-static
|
||||
BuildRequires: ghc-filepath-static
|
||||
BuildRequires: ghc-mtl-static
|
||||
BuildRequires: ghc-parsec-static
|
||||
BuildRequires: ghc-shake-static
|
||||
BuildRequires: ghc-stm-static
|
||||
BuildRequires: ghc-transformers-static
|
||||
BuildRequires: ghc-unordered-containers-static
|
||||
BuildRequires: alex
|
||||
BuildRequires: happy
|
||||
%else
|
||||
BuildRequires: %{name}-hadrian
|
||||
%endif
|
||||
%else
|
||||
%ifarch armv7hl
|
||||
# patch12
|
||||
BuildRequires: autoconf automake
|
||||
%endif
|
||||
%endif
|
||||
Requires: %{name}-compiler = %{version}-%{release}
|
||||
Requires: %{name}-devel = %{version}-%{release}
|
||||
Requires: %{name}-ghc-devel = %{version}-%{release}
|
||||
@ -221,7 +282,7 @@ To install all of ghc (including the ghc library),
|
||||
install the main ghc package.
|
||||
|
||||
|
||||
%if %{with haddock}
|
||||
%if %{with haddock} || (%{with hadrian} && %{with manual})
|
||||
%package doc
|
||||
Summary: Haskell library documentation meta package
|
||||
License: BSD
|
||||
@ -272,20 +333,30 @@ This package provides the User Guide and Haddock manual.
|
||||
# ghclibdir also needs ghc_version_override for bootstrapping
|
||||
%global ghc_version_override %{version}
|
||||
|
||||
%if %{with hadrian}
|
||||
%package hadrian
|
||||
Summary: GHC Hadrian buildsystem tool
|
||||
License: MIT
|
||||
Version: 0.1.0.0
|
||||
|
||||
%description hadrian
|
||||
This provides the hadrian tool which can be used to build ghc.
|
||||
%endif
|
||||
|
||||
%global BSDHaskellReport %{quote:BSD and HaskellReport}
|
||||
|
||||
# use "./libraries-versions.sh" to check versions
|
||||
%if %{defined ghclibdir}
|
||||
%ghc_lib_subpackage -d -l BSD Cabal-3.4.1.0
|
||||
%ghc_lib_subpackage -d -l BSD Cabal-3.6.3.0
|
||||
%ghc_lib_subpackage -d -l %BSDHaskellReport array-0.5.4.0
|
||||
%ghc_lib_subpackage -d -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base-%{base_ver}
|
||||
%ghc_lib_subpackage -d -l BSD binary-0.8.8.0
|
||||
%ghc_lib_subpackage -d -l BSD bytestring-0.10.12.1
|
||||
%ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.6.4.1
|
||||
%ghc_lib_subpackage -d -l %BSDHaskellReport deepseq-1.4.5.0
|
||||
%ghc_lib_subpackage -d -l BSD binary-0.8.9.0
|
||||
%ghc_lib_subpackage -d -l BSD bytestring-0.11.3.1
|
||||
%ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.6.5.1
|
||||
%ghc_lib_subpackage -d -l %BSDHaskellReport deepseq-1.4.6.1
|
||||
%ghc_lib_subpackage -d -l %BSDHaskellReport directory-1.3.6.2
|
||||
%ghc_lib_subpackage -d -l %BSDHaskellReport exceptions-0.10.4
|
||||
%ghc_lib_subpackage -d -l BSD filepath-1.4.2.1
|
||||
%ghc_lib_subpackage -d -l BSD filepath-1.4.2.2
|
||||
# in ghc not ghc-libraries:
|
||||
%ghc_lib_subpackage -d -x ghc-%{ghc_version_override}
|
||||
# see below for ghc-bignum
|
||||
@ -300,17 +371,17 @@ This package provides the User Guide and Haddock manual.
|
||||
# see below for integer-gmp
|
||||
%ghc_lib_subpackage -d -x -l %BSDHaskellReport libiserv-%{ghc_version_override}
|
||||
%ghc_lib_subpackage -d -l BSD mtl-2.2.2
|
||||
%ghc_lib_subpackage -d -l BSD parsec-3.1.14.0
|
||||
%ghc_lib_subpackage -d -l BSD parsec-3.1.15.0
|
||||
%ghc_lib_subpackage -d -l BSD pretty-1.1.3.6
|
||||
%ghc_lib_subpackage -d -l %BSDHaskellReport process-1.6.13.2
|
||||
%ghc_lib_subpackage -d -l BSD stm-2.5.0.0
|
||||
%ghc_lib_subpackage -d -l BSD template-haskell-2.17.0.0
|
||||
%ghc_lib_subpackage -d -l %BSDHaskellReport process-1.6.16.0
|
||||
%ghc_lib_subpackage -d -l BSD stm-2.5.0.2
|
||||
%ghc_lib_subpackage -d -l BSD template-haskell-2.18.0.0
|
||||
%ghc_lib_subpackage -d -l BSD -c ncurses-devel%{?_isa} terminfo-0.4.1.5
|
||||
%ghc_lib_subpackage -d -l BSD text-1.2.5.0
|
||||
%ghc_lib_subpackage -d -l BSD time-1.9.3
|
||||
%ghc_lib_subpackage -d -l BSD time-1.11.1.1
|
||||
%ghc_lib_subpackage -d -l BSD transformers-0.5.6.2
|
||||
%ghc_lib_subpackage -d -l BSD unix-2.7.2.2
|
||||
%if %{with haddock}
|
||||
%if %{with haddock} || %{with hadrian}
|
||||
%ghc_lib_subpackage -d -l BSD xhtml-3000.2.2.1
|
||||
%endif
|
||||
%endif
|
||||
@ -321,8 +392,8 @@ This package provides the User Guide and Haddock manual.
|
||||
Summary: GHC development libraries meta package
|
||||
License: BSD and HaskellReport
|
||||
Requires: %{name}-compiler = %{version}-%{release}
|
||||
Obsoletes: ghc-libraries < %{version}-%{release}
|
||||
Provides: ghc-libraries = %{version}-%{release}
|
||||
Obsoletes: %{name}-libraries < %{version}-%{release}
|
||||
Provides: %{name}-libraries = %{version}-%{release}
|
||||
%{?ghc_packages_list:Requires: %(echo %{ghc_packages_list} | sed -e "s/\([^ ]*\)-\([^ ]*\)/%{name}-\1-devel = \2-%{release},/g")}
|
||||
%obsoletes_ghcXY devel
|
||||
|
||||
@ -349,41 +420,37 @@ Installing this package causes %{name}-*-prof packages corresponding to
|
||||
#%%{gpgverify} --keyring='%{SOURCE3}' --signature='%{SOURCE2}' --data='%{SOURCE0}'
|
||||
%endif
|
||||
%setup -q -n ghc-%{version} %{?with_testsuite:-b1}
|
||||
# ghc-9.0.2 release anomaly
|
||||
rm -r libraries/containers/containers/dist-install
|
||||
|
||||
%patch1 -p1 -b .orig
|
||||
%patch3 -p1 -b .orig
|
||||
|
||||
%patch2 -p1 -b .orig
|
||||
%patch6 -p1 -b .orig
|
||||
%patch7 -p1 -b .orig
|
||||
%patch10 -p1 -b .orig
|
||||
%patch11 -p1 -b .orig11
|
||||
|
||||
rm -r libffi-tarballs
|
||||
rm libffi-tarballs/libffi-*.tar.gz
|
||||
|
||||
%ifarch armv7hl
|
||||
%patch12 -p1 -b .orig12
|
||||
%patch12 -p1 -b .orig
|
||||
%endif
|
||||
|
||||
# remove s390x after complete switching to llvm
|
||||
%ifarch %{ghc_unregisterized_arches} s390x
|
||||
%patch15 -p1 -b .orig
|
||||
%patch16 -p1 -b .orig
|
||||
%endif
|
||||
|
||||
# bigendian
|
||||
%ifarch ppc64 s390x
|
||||
%ifarch s390x
|
||||
%patch18 -p1 -b .orig
|
||||
%endif
|
||||
|
||||
# debian
|
||||
%patch24 -p1 -b .orig
|
||||
%patch25 -p1 -b .orig
|
||||
%patch26 -p1 -b .orig
|
||||
%patch27 -p1 -b .orig
|
||||
|
||||
%patch27 -p1
|
||||
|
||||
%if %{with haddock}
|
||||
%if %{with haddock} && %{without hadrian}
|
||||
%global gen_contents_index gen_contents_index.orig
|
||||
if [ ! -f "libraries/%{gen_contents_index}" ]; then
|
||||
echo "Missing libraries/%{gen_contents_index}, needed at end of %%install!"
|
||||
@ -391,6 +458,7 @@ if [ ! -f "libraries/%{gen_contents_index}" ]; then
|
||||
fi
|
||||
%endif
|
||||
|
||||
%if %{without hadrian}
|
||||
# https://gitlab.haskell.org/ghc/ghc/-/wikis/platforms
|
||||
cat > mk/build.mk << EOF
|
||||
%if %{with perf_build}
|
||||
@ -426,6 +494,8 @@ BUILD_SPHINX_HTML = NO
|
||||
%endif
|
||||
BUILD_SPHINX_PDF = NO
|
||||
EOF
|
||||
%endif
|
||||
|
||||
|
||||
%build
|
||||
# for patch12
|
||||
@ -435,6 +505,11 @@ autoreconf
|
||||
|
||||
%ghc_set_gcc_flags
|
||||
export CC=%{_bindir}/gcc
|
||||
# lld breaks build-id
|
||||
# /usr/bin/debugedit: Cannot handle 8-byte build ID
|
||||
# https://bugzilla.redhat.com/show_bug.cgi?id=2116508
|
||||
# https://gitlab.haskell.org/ghc/ghc/-/issues/22195
|
||||
export LD=%{_bindir}/ld.gold
|
||||
|
||||
# * %%configure induces cross-build due to different target/host/build platform names
|
||||
./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \
|
||||
@ -452,12 +527,56 @@ export CC=%{_bindir}/gcc
|
||||
|
||||
# avoid "ghc: hGetContents: invalid argument (invalid byte sequence)"
|
||||
export LANG=C.utf8
|
||||
%if %{with hadrian}
|
||||
%if %{defined _ghcdynlibdir}
|
||||
%undefine _ghcdynlibdir
|
||||
%endif
|
||||
|
||||
%if %{with build_hadrian}
|
||||
%if %{with ghc_debuginfo}
|
||||
# do not disable debuginfo with ghc_bin_build
|
||||
%global ghc_debuginfo 1
|
||||
%endif
|
||||
(
|
||||
cd hadrian
|
||||
%ghc_bin_build
|
||||
)
|
||||
%global hadrian hadrian/dist/build/hadrian/hadrian
|
||||
%else
|
||||
%global hadrian %{_bindir}/hadrian
|
||||
%endif
|
||||
|
||||
%ifarch %{ghc_llvm_archs}
|
||||
%global hadrian_llvm +llvm
|
||||
%endif
|
||||
%define hadrian_docs %{!?with_haddock:--docs=no-haddocks} %{!?with_manual:--docs=no-sphinx}%{?with_manual:--docs=no-sphinx-pdfs --docs=no-sphinx-man}
|
||||
# quickest does not build shared libs
|
||||
%{hadrian} %{?_smp_mflags} --flavour=%{!?with_prodbuild:quick+no_profiled_libs}%{?with_prodbuild:perf%{!?with_ghc_prof:+no_profiled_libs}}%{?hadrian_llvm} %{hadrian_docs} binary-dist-dir
|
||||
%else
|
||||
make %{?_smp_mflags}
|
||||
%endif
|
||||
|
||||
|
||||
%install
|
||||
%if %{with hadrian}
|
||||
%if %{with build_hadrian}
|
||||
(
|
||||
cd hadrian
|
||||
%ghc_bin_install
|
||||
rm %{buildroot}%{_ghclicensedir}/%{name}/LICENSE
|
||||
cp -p LICENSE ../LICENSE.hadrian
|
||||
)
|
||||
%endif
|
||||
# https://gitlab.haskell.org/ghc/ghc/-/issues/20120#note_366872
|
||||
(
|
||||
cd _build/bindist/ghc-%{version}-*
|
||||
./configure --prefix=%{buildroot}%{ghclibdir} --bindir=%{buildroot}%{_bindir} --libdir=%{buildroot}%{_libdir} --mandir=%{buildroot}%{_mandir} --docdir=%{buildroot}%{_docdir}/%{name}
|
||||
make install
|
||||
)
|
||||
mkdir -p %{buildroot}%{_sysconfdir}/ld.so.conf.d
|
||||
echo "%{ghclibplatform}" > %{buildroot}%{_sysconfdir}/ld.so.conf.d/%{name}.conf
|
||||
%else
|
||||
make DESTDIR=%{buildroot} install
|
||||
|
||||
%if %{defined _ghcdynlibdir}
|
||||
mv %{buildroot}%{ghclibdir}/*/libHS*ghc%{ghc_version}.so %{buildroot}%{_ghcdynlibdir}/
|
||||
for i in $(find %{buildroot} -type f -executable -exec sh -c "file {} | grep -q 'dynamically linked'" \; -print); do
|
||||
@ -468,10 +587,13 @@ for i in %{buildroot}%{ghclibdir}/package.conf.d/*.conf; do
|
||||
done
|
||||
sed -i -e 's!^library-dirs: %{ghclibdir}/rts!&\ndynamic-library-dirs: %{_ghcdynlibdir}!' %{buildroot}%{ghclibdir}/package.conf.d/rts.conf
|
||||
%endif
|
||||
%endif
|
||||
|
||||
# containers src moved to a subdir
|
||||
cp -p libraries/containers/containers/LICENSE libraries/containers/LICENSE
|
||||
|
||||
rm -f %{name}-*.files
|
||||
|
||||
# FIXME replace with ghc_subpackages_list
|
||||
for i in %{ghc_packages_list}; do
|
||||
name=$(echo $i | sed -e "s/\(.*\)-.*/\1/")
|
||||
@ -490,9 +612,12 @@ echo "%%dir %{ghclibdir}" >> %{name}-base%{?_ghcdynlibdir:-devel}.files
|
||||
%ghc_gen_filelists hpc %{hpc_ver}
|
||||
%ghc_gen_filelists libiserv %{ghc_version_override}
|
||||
|
||||
%ghc_gen_filelists ghc-bignum 1.1
|
||||
%ghc_gen_filelists ghc-prim 0.7.0
|
||||
%ghc_gen_filelists ghc-bignum 1.2
|
||||
%ghc_gen_filelists ghc-prim 0.8.0
|
||||
%ghc_gen_filelists integer-gmp 1.1
|
||||
%if %{with hadrian}
|
||||
%ghc_gen_filelists rts 1.0.2
|
||||
%endif
|
||||
|
||||
%define merge_filelist()\
|
||||
cat %{name}-%1.files >> %{name}-%2.files\
|
||||
@ -501,15 +626,26 @@ cat %{name}-%1-devel.files >> %{name}-%2-devel.files\
|
||||
cat %{name}-%1-doc.files >> %{name}-%2-doc.files\
|
||||
cat %{name}-%1-prof.files >> %{name}-%2-prof.files\
|
||||
%endif\
|
||||
if [ "%1" != "rts" ]; then\
|
||||
cp -p libraries/%1/LICENSE libraries/LICENSE.%1\
|
||||
echo "%%license libraries/LICENSE.%1" >> %{name}-%2.files\
|
||||
fi\
|
||||
%{nil}
|
||||
|
||||
%merge_filelist ghc-bignum base
|
||||
%merge_filelist ghc-prim base
|
||||
%merge_filelist integer-gmp base
|
||||
%if %{with hadrian}
|
||||
%merge_filelist rts base
|
||||
%endif
|
||||
|
||||
# add rts libs
|
||||
%if %{with hadrian}
|
||||
for i in %{buildroot}%{ghclibplatform}/libHSrts*ghc%{ghc_version}.so; do
|
||||
echo $i >> %{name}-base.files
|
||||
done
|
||||
echo "%{_sysconfdir}/ld.so.conf.d/%{name}.conf" >> %{name}-base.files
|
||||
%else
|
||||
%if %{defined _ghcdynlibdir}
|
||||
echo "%{ghclibdir}/rts" >> %{name}-base-devel.files
|
||||
%else
|
||||
@ -520,23 +656,44 @@ ls %{buildroot}%{?_ghcdynlibdir}%{!?_ghcdynlibdir:%{ghclibdir}/rts}/libHSrts*.so
|
||||
%if %{defined _ghcdynlibdir}
|
||||
sed -i -e 's!^library-dirs: %{ghclibdir}/rts!&\ndynamic-library-dirs: %{_libdir}!' %{buildroot}%{ghclibdir}/package.conf.d/rts.conf
|
||||
%endif
|
||||
ls -d %{buildroot}%{ghclibdir}/package.conf.d/rts.conf %{buildroot}%{ghclibdir}/include >> %{name}-base-devel.files
|
||||
ls -d %{buildroot}%{ghclibdir}/package.conf.d/rts.conf >> %{name}-base-devel.files
|
||||
%endif
|
||||
|
||||
ls -d %{buildroot}%{ghclibdir}/include >> %{name}-base-devel.files
|
||||
|
||||
%if %{with ghc_prof}
|
||||
ls %{buildroot}%{ghclibdir}/bin/ghc-iserv-prof* >> %{name}-base-prof.files
|
||||
%if %{with hadrian}
|
||||
ls %{buildroot}%{ghclibdir}/lib/bin/ghc-iserv-prof >> %{name}-base-prof.files
|
||||
%endif
|
||||
%endif
|
||||
|
||||
sed -i -e "s|^%{buildroot}||g" %{name}-base*.files
|
||||
%if %{with hadrian}
|
||||
sed -i -e "s|%{buildroot}||g" %{buildroot}%{_bindir}/*
|
||||
%endif
|
||||
|
||||
%if %{with haddock}
|
||||
%if %{with haddock} && %{without hadrian}
|
||||
# generate initial lib doc index
|
||||
cd libraries
|
||||
sh %{gen_contents_index} --intree --verbose
|
||||
cd ..
|
||||
%endif
|
||||
|
||||
%if %{with hadrian}
|
||||
%if %{with haddock}
|
||||
rm %{buildroot}%{_pkgdocdir}/archives/libraries.html.tar.xz
|
||||
%endif
|
||||
%if %{with manual}
|
||||
rm %{buildroot}%{_pkgdocdir}/archives/Haddock.html.tar.xz
|
||||
rm %{buildroot}%{_pkgdocdir}/archives/users_guide.html.tar.xz
|
||||
%endif
|
||||
%endif
|
||||
|
||||
# we package the library license files separately
|
||||
%if %{without hadrian}
|
||||
find %{buildroot}%{ghc_html_libraries_dir} -name LICENSE -exec rm '{}' ';'
|
||||
%endif
|
||||
|
||||
mkdir -p %{buildroot}%{_mandir}/man1
|
||||
install -p -m 0644 %{SOURCE5} %{buildroot}%{_mandir}/man1/ghc-pkg.1
|
||||
@ -547,11 +704,42 @@ install -p -m 0644 %{SOURCE7} %{buildroot}%{_mandir}/man1/runghc.1
|
||||
export RPM_BUILD_NCPUS=1
|
||||
%endif
|
||||
|
||||
%if %{with hadrian}
|
||||
rm %{buildroot}%{ghclibdir}/lib/package.conf.d/.stamp
|
||||
rm %{buildroot}%{ghclibdir}/lib/package.conf.d/*.conf.copy
|
||||
|
||||
(cd %{buildroot}%{ghclibdir}/lib/bin
|
||||
for i in *; do
|
||||
if [ -f %{buildroot}%{ghclibdir}/bin/$i ]; then
|
||||
ln -sf ../../bin/$i
|
||||
fi
|
||||
done
|
||||
)
|
||||
%endif
|
||||
|
||||
(
|
||||
cd %{buildroot}%{_bindir}
|
||||
for i in *; do
|
||||
case $i in
|
||||
*-%{version}) ;;
|
||||
*)
|
||||
if [ -f $i-%{version} ]; then
|
||||
ln -s $i-%{version} $i-%{ghc_major}
|
||||
fi
|
||||
esac
|
||||
done
|
||||
)
|
||||
|
||||
|
||||
%check
|
||||
export LANG=C.utf8
|
||||
# stolen from ghc6/debian/rules:
|
||||
%if %{with hadrian}
|
||||
export LD_LIBRARY_PATH=%{buildroot}%{ghclibplatform}:
|
||||
GHC=%{buildroot}%{ghclibdir}/bin/ghc
|
||||
%else
|
||||
GHC=inplace/bin/ghc-stage2
|
||||
%endif
|
||||
# Do some very simple tests that the compiler actually works
|
||||
rm -rf testghc
|
||||
mkdir testghc
|
||||
@ -604,16 +792,20 @@ make test
|
||||
|
||||
|
||||
%if %{defined ghclibdir}
|
||||
%transfiletriggerin compiler -- %{ghclibdir}/package.conf.d
|
||||
%post base -p /sbin/ldconfig
|
||||
%postun base -p /sbin/ldconfig
|
||||
|
||||
|
||||
%transfiletriggerin compiler -- %{ghcliblib}/package.conf.d
|
||||
%ghc_pkg_recache
|
||||
%end
|
||||
|
||||
%transfiletriggerpostun compiler -- %{ghclibdir}/package.conf.d
|
||||
%transfiletriggerpostun compiler -- %{ghcliblib}/package.conf.d
|
||||
%ghc_pkg_recache
|
||||
%end
|
||||
|
||||
|
||||
%if %{with haddock}
|
||||
%if %{with haddock} && %{without hadrian}
|
||||
%transfiletriggerin doc-index -- %{ghc_html_libraries_dir}
|
||||
env -C %{ghc_html_libraries_dir} ./gen_contents_index
|
||||
%end
|
||||
@ -637,78 +829,129 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index
|
||||
%{_bindir}/ghci
|
||||
%{_bindir}/ghci-%{version}
|
||||
%{_bindir}/hp2ps
|
||||
%{_bindir}/hp2ps-%{?with_hadrian:ghc-}%{version}
|
||||
%{_bindir}/hpc
|
||||
%{_bindir}/hpc-%{?with_hadrian:ghc-}%{version}
|
||||
%{_bindir}/hsc2hs
|
||||
%{_bindir}/hsc2hs-%{?with_hadrian:ghc-}%{version}
|
||||
%{_bindir}/runghc
|
||||
%{_bindir}/runghc-%{ghc_version}
|
||||
%{_bindir}/runhaskell
|
||||
%{_bindir}/runhaskell-%{version}
|
||||
%{_bindir}/ghc-%{ghc_major}
|
||||
%{_bindir}/ghc-pkg-%{ghc_major}
|
||||
%{_bindir}/ghci-%{ghc_major}
|
||||
%{_bindir}/runghc-%{ghc_major}
|
||||
%{_bindir}/runhaskell-%{ghc_major}
|
||||
%if %{without hadrian}
|
||||
%{_bindir}/hp2ps-%{ghc_major}
|
||||
%{_bindir}/hpc-%{ghc_major}
|
||||
%{_bindir}/hsc2hs-%{ghc_major}
|
||||
%endif
|
||||
%dir %{ghclibdir}/bin
|
||||
%{ghclibdir}/bin/ghc
|
||||
%{ghclibdir}/bin/ghc-iserv
|
||||
%{ghclibdir}/bin/ghc-iserv-dyn
|
||||
%if %{with ghc_prof}
|
||||
%{ghclibdir}/bin/ghc-iserv-prof
|
||||
%endif
|
||||
%{ghclibdir}/bin/ghc-pkg
|
||||
%{ghclibdir}/bin/hpc
|
||||
%{ghclibdir}/bin/hsc2hs
|
||||
%{ghclibdir}/bin/runghc
|
||||
%{ghclibdir}/bin/hp2ps
|
||||
%{ghclibdir}/bin/unlit
|
||||
%{ghclibdir}/ghc-usage.txt
|
||||
%{ghclibdir}/ghci-usage.txt
|
||||
%{ghclibdir}/llvm-passes
|
||||
%{ghclibdir}/llvm-targets
|
||||
%dir %{ghclibdir}/package.conf.d
|
||||
%ghost %{ghclibdir}/package.conf.d/package.cache
|
||||
%{ghclibdir}/package.conf.d/package.cache.lock
|
||||
%{ghclibdir}/platformConstants
|
||||
%{ghclibdir}/settings
|
||||
%{ghclibdir}/template-hsc.h
|
||||
%if %{with hadrian}
|
||||
%{ghclibdir}/bin/ghc-%{version}
|
||||
%{ghclibdir}/bin/ghc-iserv-ghc-%{version}
|
||||
%{ghclibdir}/bin/ghc-iserv-dyn-ghc-%{version}
|
||||
%{ghclibdir}/bin/ghc-pkg-%{version}
|
||||
%{ghclibdir}/bin/haddock
|
||||
%{ghclibdir}/bin/haddock-ghc-%{version}
|
||||
%{ghclibdir}/bin/hp2ps-ghc-%{version}
|
||||
%{ghclibdir}/bin/hpc-ghc-%{version}
|
||||
%{ghclibdir}/bin/hsc2hs-ghc-%{version}
|
||||
%{ghclibdir}/bin/runghc-%{version}
|
||||
%{ghclibdir}/bin/runhaskell
|
||||
%{ghclibdir}/bin/runhaskell-%{version}
|
||||
%{ghclibdir}/bin/unlit-ghc-%{version}
|
||||
%{ghclibdir}/lib/bin/ghc-iserv
|
||||
%{ghclibdir}/lib/bin/ghc-iserv-dyn
|
||||
%{ghclibdir}/lib/bin/unlit
|
||||
%{ghclibdir}/lib/DerivedConstants.h
|
||||
%{ghclibdir}/lib/ghcautoconf.h
|
||||
%{ghclibdir}/lib/ghcplatform.h
|
||||
%{ghclibdir}/lib/ghcversion.h
|
||||
%endif
|
||||
%{ghcliblib}/ghc-usage.txt
|
||||
%{ghcliblib}/ghci-usage.txt
|
||||
%{ghcliblib}/llvm-passes
|
||||
%{ghcliblib}/llvm-targets
|
||||
%dir %{ghcliblib}/package.conf.d
|
||||
%ghost %{ghcliblib}/package.conf.d/package.cache
|
||||
%{ghcliblib}/package.conf.d/package.cache.lock
|
||||
%{ghcliblib}/settings
|
||||
%{ghcliblib}/template-hsc.h
|
||||
%{_mandir}/man1/ghc-pkg.1*
|
||||
%{_mandir}/man1/haddock.1*
|
||||
%{_mandir}/man1/runghc.1*
|
||||
|
||||
%if %{with haddock}
|
||||
%if %{with hadrian} || %{with haddock}
|
||||
%{_bindir}/haddock
|
||||
%{_bindir}/haddock-ghc-%{version}
|
||||
%{ghcliblib}/html
|
||||
%{ghcliblib}/latex
|
||||
%endif
|
||||
%if %{with haddock}
|
||||
%if %{without hadrian}
|
||||
%{ghclibdir}/bin/haddock
|
||||
%{ghclibdir}/html
|
||||
%{ghclibdir}/latex
|
||||
%{ghc_html_libraries_dir}/prologue.txt
|
||||
%endif
|
||||
%verify(not size mtime) %{ghc_html_libraries_dir}/haddock-bundle.min.js
|
||||
%verify(not size mtime) %{ghc_html_libraries_dir}/linuwial.css
|
||||
%verify(not size mtime) %{ghc_html_libraries_dir}/quick-jump.css
|
||||
%verify(not size mtime) %{ghc_html_libraries_dir}/synopsis.png
|
||||
%endif
|
||||
%if %{with manual}
|
||||
%if %{with manual} && %{without hadrian}
|
||||
%{_mandir}/man1/ghc.1*
|
||||
%endif
|
||||
|
||||
%files devel
|
||||
|
||||
%if %{with haddock}
|
||||
%if %{with haddock} || (%{with hadrian} && %{with manual})
|
||||
%files doc
|
||||
%{ghc_html_dir}/index.html
|
||||
|
||||
%files doc-index
|
||||
%{ghc_html_libraries_dir}/gen_contents_index
|
||||
%if %{with haddock}
|
||||
#%%{ghc_html_libraries_dir}/gen_contents_index
|
||||
%verify(not size mtime) %{ghc_html_libraries_dir}/doc-index*.html
|
||||
%verify(not size mtime) %{ghc_html_libraries_dir}/index*.html
|
||||
%endif
|
||||
|
||||
%files filesystem
|
||||
%dir %_ghc_doc_dir
|
||||
%dir %ghc_html_dir
|
||||
%if %{with haddock}
|
||||
%dir %ghc_html_libraries_dir
|
||||
%endif
|
||||
%endif
|
||||
|
||||
%if %{with hadrian} && %{with build_hadrian}
|
||||
%files hadrian
|
||||
%license LICENSE.hadrian
|
||||
%{_bindir}/hadrian
|
||||
%endif
|
||||
|
||||
%if %{with manual}
|
||||
%files manual
|
||||
## needs pandoc
|
||||
#%%{ghc_html_dir}/Cabal
|
||||
%if %{with haddock}
|
||||
%{ghc_html_dir}/haddock
|
||||
%{ghc_html_dir}/index.html
|
||||
%{ghc_html_dir}/users_guide
|
||||
%if %{with hadrian}
|
||||
%{ghc_html_dir}/Haddock
|
||||
%else
|
||||
%if %{with haddock}
|
||||
%{ghc_html_dir}/haddock
|
||||
%endif
|
||||
%endif
|
||||
%endif
|
||||
|
||||
@ -718,6 +961,9 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index
|
||||
|
||||
|
||||
%changelog
|
||||
* Mon Jan 30 2023 Jens Petersen <petersen@redhat.com> - 9.2.5-125
|
||||
- rebase to ghc-9.2.5 from ghc9.2
|
||||
|
||||
* Sun Jan 15 2023 Jens Petersen <petersen@redhat.com> - 9.0.2-124
|
||||
- rebase to 9.0.2 from ghc9.0
|
||||
- https://downloads.haskell.org/~ghc/9.0.2/docs/html/users_guide/9.0.1-notes.html
|
||||
|
Loading…
Reference in New Issue
Block a user