Skip to content
Commits on Source (11)
Author: Will Thompson <will.thompson@collabora.co.uk>
Download: http://www.willthompson.co.uk/bustle/releases/
Format: https://www.debian.org/doc/packaging-manuals/copyright-format/1.0/
Upstream-Contact: Will Thompson <will.thompson@collabora.co.uk>
Upstream-Name: bustle
Source: http://www.willthompson.co.uk/bustle/releases/
Files: *
Copyright: (C) 2008-2011 © Collabora Ltd. <http://www.collabora.co.uk>
......
c2hs (0.28.5-3) UNRELEASED; urgency=medium
* Add missing "Upstream-Name" field into "debian/copyright".
-- Dmitry Bogatov <KAction@debian.org> Thu, 16 May 2019 14:24:00 +0000
c2hs (0.28.5-2) unstable; urgency=medium
* Bump debhelper compat level to 10
......
Format: https://www.debian.org/doc/packaging-manuals/copyright-format/1.0/
Name: c2hs
Maintainer: chak@cse.unsw.edu.au, duncan@haskell.org
Upstream-Name: c2hs
Upstream-Contact: chak@cse.unsw.edu.au, duncan@haskell.org
Source: https://hackage.haskell.org/packages/archive/c2hs/0.16.0/c2hs-0.16.0.tar.gz
Copyright:
......
ghc (8.6.5+dfsg1-1) unstable; urgency=medium
[ Gianfranco Costamagna ]
* New upstream release
-- Clint Adams <clint@debian.org> Tue, 23 Jul 2019 22:08:57 -0400
ghc (8.4.4+dfsg1-3) unstable; urgency=medium
* Use the ARM7TDMI core on armel (Closes: #915333)
......
libraries/dph
libraries/primitive
libraries/vector
libraries/random
libraries/dph/
libraries/primitive/
libraries/vector/
libraries/random/
......@@ -10,7 +10,7 @@ Index: b/aclocal.m4
===================================================================
--- a/aclocal.m4
+++ b/aclocal.m4
@@ -423,7 +423,7 @@ AC_DEFUN([GET_ARM_ISA],
@@ -454,7 +454,7 @@ AC_DEFUN([GET_ARM_ISA],
)],
[changequote(, )dnl
ARM_ISA=ARMv7
......
commit ec9aacf3eb2975fd302609163aaef429962ecd87
Author: Moritz Angermann <moritz.angermann@gmail.com>
Date: Thu Feb 8 16:07:07 2018 +0800
commit ce3897ffd6e7c8b8f36b8e920168bac8c7f836ae
Author: Ilias Tsitsimpis <iliastsi@debian.org>
Date: Tue Sep 18 17:45:17 2018 +0200
adds -latomic to. ghc-prim
Fix check whether GCC supports __atomic_ builtins
Reviewers: bgamari, hvr
Summary:
C11 atomics are never used because:
Reviewed By: bgamari
Subscribers: erikd, hvr, rwbarton, thomie, carter
* The program used for checking whether GCC supports
__atomic_ builtins fails with the following error:
Differential Revision: https://phabricator.haskell.org/D4378
```
error: size mismatch in argument 2 of `__atomic_load`
int test(int *x) { int y; __atomic_load(&x, &y, __ATOMIC_SEQ_CST); return x; }
```
iliastsi: The original patch fails to correctly detect and use C11
atomics, so I modified it based on https://phabricator.haskell.org/D5154.
* There is a typo when checking if CONF_GCC_SUPPORTS__ATOMICS equals YES,
resulting in PRIM_CFLAGS and PRIM_EXTRA_LIBRARIES never being set.
Index: b/aclocal.m4
===================================================================
--- a/aclocal.m4
+++ b/aclocal.m4
@@ -1284,24 +1284,6 @@ AC_SUBST(GccIsClang)
rm -f conftest.txt
])
Reviewers: bgamari
-# FP_GCC_SUPPORTS__ATOMICS
-# ------------------------
-# Does gcc support the __atomic_* family of builtins?
-AC_DEFUN([FP_GCC_SUPPORTS__ATOMICS],
-[
- AC_REQUIRE([AC_PROG_CC])
- AC_MSG_CHECKING([whether GCC supports __atomic_ builtins])
- echo 'int test(int *x) { int y; __atomic_load(&x, &y, __ATOMIC_SEQ_CST); return x; }' > conftest.c
- if $CC -c conftest.c > /dev/null 2>&1; then
- CONF_GCC_SUPPORTS__ATOMICS=YES
- AC_MSG_RESULT([yes])
- else
- CONF_GCC_SUPPORTS__ATOMICS=NO
- AC_MSG_RESULT([no])
- fi
- rm -f conftest.c conftest.o
-])
-
# FP_GCC_SUPPORTS_NO_PIE
# ----------------------
# Does gcc support the -no-pie option? If so we should pass it to gcc when
Index: b/configure.ac
===================================================================
--- a/configure.ac
+++ b/configure.ac
@@ -714,11 +714,6 @@ FP_GCC_VERSION
dnl ** See whether gcc supports -no-pie
FP_GCC_SUPPORTS_NO_PIE
Reviewed By: bgamari
-dnl ** Used to determine how to compile ghc-prim's atomics.c, used by
-dnl unregisterised, Sparc, and PPC backends.
-FP_GCC_SUPPORTS__ATOMICS
-AC_DEFINE([HAVE_C11_ATOMICS], [$CONF_GCC_SUPPORTS__ATOMICS], [Does GCC support __atomic primitives?])
-
FP_GCC_EXTRA_FLAGS
Subscribers: rwbarton, erikd, carter
dnl ** look to see if we have a C compiler using an llvm back end.
Index: b/libraries/ghc-prim/Setup.hs
===================================================================
--- a/libraries/ghc-prim/Setup.hs
+++ b/libraries/ghc-prim/Setup.hs
@@ -18,7 +18,7 @@ import System.Exit
import System.Directory
Differential Revision: https://phabricator.haskell.org/D5154
main :: IO ()
-main = do let hooks = simpleUserHooks {
+main = do let hooks = autoconfUserHooks {
regHook = addPrimModule
$ regHook simpleUserHooks,
buildHook = build_primitive_sources
Index: b/libraries/ghc-prim/aclocal.m4
===================================================================
--- /dev/null
--- a/libraries/ghc-prim/aclocal.m4
+++ b/libraries/ghc-prim/aclocal.m4
@@ -0,0 +1,17 @@
+# FP_GCC_SUPPORTS__ATOMICS
+# ------------------------
+# Does gcc support the __atomic_* family of builtins?
+AC_DEFUN([FP_GCC_SUPPORTS__ATOMICS],
+[
+ AC_REQUIRE([AC_PROG_CC])
+ AC_MSG_CHECKING([whether GCC supports __atomic_ builtins])
@@ -5,7 +5,7 @@ AC_DEFUN([FP_GCC_SUPPORTS__ATOMICS],
[
AC_REQUIRE([AC_PROG_CC])
AC_MSG_CHECKING([whether GCC supports __atomic_ builtins])
- echo 'int test(int *x) { int y; __atomic_load(&x, &y, __ATOMIC_SEQ_CST); return x; }' > conftest.c
+ echo 'int test(int *x) { int y; __atomic_load(x, &y, __ATOMIC_SEQ_CST); return y; }' > conftest.c
+ if $CC -c conftest.c > /dev/null 2>&1; then
+ CONF_GCC_SUPPORTS__ATOMICS=YES
+ AC_MSG_RESULT([yes])
+ else
+ CONF_GCC_SUPPORTS__ATOMICS=NO
+ AC_MSG_RESULT([no])
+ fi
+ rm -f conftest.c conftest.o
+])
if $CC -c conftest.c > /dev/null 2>&1; then
CONF_GCC_SUPPORTS__ATOMICS=YES
AC_MSG_RESULT([yes])
Index: b/libraries/ghc-prim/configure.ac
===================================================================
--- /dev/null
--- a/libraries/ghc-prim/configure.ac
+++ b/libraries/ghc-prim/configure.ac
@@ -0,0 +1,18 @@
+AC_INIT([ghc-prim package], [2.1], [glasgow-haskell-bugs@haskell.org], [ghc-prim])
+
+AC_CONFIG_SRCDIR([ghc-prim.cabal])
+
+# -------------------------------------------------------------------------
+dnl ** Used to determine how to compile ghc-prim's atomics.c, used by
+dnl unregisterised, Sparc, and PPC backends.
+FP_GCC_SUPPORTS__ATOMICS
+AC_DEFINE([HAVE_C11_ATOMICS], [$CONF_GCC_SUPPORTS__ATOMICS], [Does GCC support __atomic primitives?])
+
@@ -8,7 +8,7 @@ dnl unregisterised, Sparc, and PPC ba
FP_GCC_SUPPORTS__ATOMICS
AC_DEFINE([HAVE_C11_ATOMICS], [$CONF_GCC_SUPPORTS__ATOMICS], [Does GCC support __atomic primitives?])
-if test "x$CONF_GCC_SUPPORTS__ATOMICS" = YES
+if test "$CONF_GCC_SUPPORTS__ATOMICS" = "YES"
+then PRIM_CFLAGS=-DHAVE_C11_ATOMICS
+ PRIM_EXTRA_LIBRARIES=atomic
+fi
+AC_SUBST([PRIM_CFLAGS])
+AC_SUBST([PRIM_EXTRA_LIBRARIES])
+AC_CONFIG_FILES([ghc-prim.buildinfo])
+AC_OUTPUT
Index: b/libraries/ghc-prim/ghc-prim.buildinfo.in
===================================================================
--- /dev/null
+++ b/libraries/ghc-prim/ghc-prim.buildinfo.in
@@ -0,0 +1,2 @@
+cc-options: @PRIM_CFLAGS@
+extra-libraries: @PRIM_EXTRA_LIBRARIES@
\ No newline at end of file
then PRIM_CFLAGS=-DHAVE_C11_ATOMICS
PRIM_EXTRA_LIBRARIES=atomic
fi
......@@ -28,7 +28,7 @@ Index: b/compiler/main/SysTools.hs
===================================================================
--- a/compiler/main/SysTools.hs
+++ b/compiler/main/SysTools.hs
@@ -534,9 +534,12 @@ linkDynLib dflags0 o_files dep_packages
@@ -548,9 +548,12 @@ linkDynLib dflags0 o_files dep_packages
-------------------------------------------------------------------
let output_fn = case o_file of { Just s -> s; Nothing -> "a.out"; }
......@@ -43,7 +43,7 @@ Index: b/compiler/main/SysTools.hs
runLink dflags (
map Option verbFlags
@@ -593,3 +596,27 @@ getFrameworkOpts dflags platform
@@ -607,3 +610,27 @@ getFrameworkOpts dflags platform
-- reverse because they're added in reverse order from the cmd line:
framework_opts = concat [ ["-framework", fw]
| fw <- reverse frameworks ]
......
Forwarded to https://ghc.haskell.org/trac/ghc/ticket/10424
Index: b/compiler/iface/MkIface.hs
Index: ghc-8.6.4/compiler/iface/MkIface.hs
===================================================================
--- a/compiler/iface/MkIface.hs
+++ b/compiler/iface/MkIface.hs
@@ -689,7 +689,7 @@ addFingerprints hsc_env mb_old_fingerpri
--- ghc-8.6.4.orig/compiler/iface/MkIface.hs
+++ ghc-8.6.4/compiler/iface/MkIface.hs
@@ -712,7 +712,7 @@
iface_hash <- computeFingerprint putNameLiterally
(mod_hash,
ann_fn (mkVarOcc "module"), -- See mkIfaceAnnCache
......@@ -13,7 +13,7 @@ Index: b/compiler/iface/MkIface.hs
sorted_deps,
mi_hpc iface0)
@@ -724,6 +724,9 @@ addFingerprints hsc_env mb_old_fingerpri
@@ -747,6 +747,9 @@
(non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph (mi_fam_insts iface0)
fix_fn = mi_fix_fn iface0
ann_fn = mkIfaceAnnCache (mi_anns iface0)
......
......@@ -43,7 +43,7 @@ Index: b/rts/posix/OSMem.c
===================================================================
--- a/rts/posix/OSMem.c
+++ b/rts/posix/OSMem.c
@@ -435,6 +435,8 @@ osTryReserveHeapMemory (W_ len, void *hi
@@ -476,6 +476,8 @@ osTryReserveHeapMemory (W_ len, void *hi
void *base, *top;
void *start, *end;
......@@ -52,7 +52,7 @@ Index: b/rts/posix/OSMem.c
/* We try to allocate len + MBLOCK_SIZE,
because we need memory which is MBLOCK_SIZE aligned,
and then we discard what we don't need */
@@ -502,6 +504,8 @@ void *osReserveHeapMemory(void *startAdd
@@ -552,6 +554,8 @@ void *osReserveHeapMemory(void *startAdd
attempt = 0;
while (1) {
......
commit 18cb44dfae3f0847447da33c9d7a25d2709d838f
Author: Alec Theriault <alec.theriault@gmail.com>
Date: Tue Aug 21 16:03:40 2018 -0400
Explicitly tell 'getNameToInstances' mods to load
Calculating which modules to load based on the InteractiveContext means
maintaining a potentially very large GblRdrEnv.
In Haddock's case, it is much cheaper (from a memory perspective) to
just keep track of which modules interfaces we want loaded then hand
these off explicitly to 'getNameToInstancesIndex'.
Bumps haddock submodule (commit 40eb5aabed0ae)
Reviewers: alexbiehl, bgamari
Reviewed By: alexbiehl
Subscribers: rwbarton, thomie, carter
Differential Revision: https://phabricator.haskell.org/D5003
(cherry picked from commit c971e1193fa44bb507d1806d5bb61768670dc912)
Index: b/compiler/main/GHC.hs
===================================================================
--- a/compiler/main/GHC.hs
+++ b/compiler/main/GHC.hs
@@ -117,6 +117,7 @@ module GHC (
showModule,
moduleIsBootOrNotObjectLinkable,
getNameToInstancesIndex,
+ getNameToInstancesIndex2,
-- ** Inspecting types and kinds
exprType, TcRnExprMode(..),
@@ -297,7 +298,8 @@ import HscMain
import GhcMake
import DriverPipeline ( compileOne' )
import GhcMonad
-import TcRnMonad ( finalSafeMode, fixSafeInstances )
+import TcRnMonad ( finalSafeMode, fixSafeInstances, initIfaceTcRn )
+import LoadIface ( loadSysInterface )
import TcRnTypes
import Packages
import NameSet
@@ -1247,10 +1249,27 @@ getNameToInstancesIndex :: GhcMonad m
=> [Module] -- ^ visible modules. An orphan instance will be returned if and
-- only it is visible from at least one module in the list.
-> m (Messages, Maybe (NameEnv ([ClsInst], [FamInst])))
-getNameToInstancesIndex visible_mods = do
+getNameToInstancesIndex visible_mods =
+ getNameToInstancesIndex2 visible_mods Nothing
+
+-- | Retrieve all type and family instances in the environment, indexed
+-- by 'Name'. Each name's lists will contain every instance in which that name
+-- is mentioned in the instance head.
+getNameToInstancesIndex2 :: GhcMonad m
+ => [Module] -- ^ visible modules. An orphan instance will be returned
+ -- if it is visible from at least one module in the list.
+ -> Maybe [Module] -- ^ modules to load. If this is not specified, we load
+ -- modules for everything that is in scope unqualified.
+ -> m (Messages, Maybe (NameEnv ([ClsInst], [FamInst])))
+getNameToInstancesIndex2 visible_mods mods_to_load = do
hsc_env <- getSession
liftIO $ runTcInteractive hsc_env $
- do { loadUnqualIfaces hsc_env (hsc_IC hsc_env)
+ do { case mods_to_load of
+ Nothing -> loadUnqualIfaces hsc_env (hsc_IC hsc_env)
+ Just mods ->
+ let doc = text "Need interface for reporting instances in scope"
+ in initIfaceTcRn $ mapM_ (loadSysInterface doc) mods
+
; InstEnvs {ie_global, ie_local} <- tcGetInstEnvs
; let visible_mods' = mkModuleSet visible_mods
; (pkg_fie, home_fie) <- tcGetFamInstEnvs
Index: b/utils/haddock/haddock-api/src/Haddock/Interface.hs
===================================================================
--- a/utils/haddock/haddock-api/src/Haddock/Interface.hs
+++ b/utils/haddock/haddock-api/src/Haddock/Interface.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP, OverloadedStrings #-}
+{-# LANGUAGE CPP, OverloadedStrings, BangPatterns #-}
-----------------------------------------------------------------------------
-- |
-- Module : Haddock.Interface
@@ -51,6 +51,7 @@ import System.Directory
import System.FilePath
import Text.Printf
+import Module (mkModuleSet, emptyModuleSet, unionModuleSet, ModuleSet)
import Digraph
import DynFlags hiding (verbosity)
import Exception
@@ -59,7 +60,9 @@ import HscTypes
import FastString (unpackFS)
import MonadUtils (liftIO)
import TcRnTypes (tcg_rdr_env)
-import RdrName (plusGlobalRdrEnv)
+import Name (nameIsFromExternalPackage, nameOccName)
+import OccName (isTcOcc)
+import RdrName (unQualOK, gre_name, globalRdrEnvElts)
import ErrUtils (withTiming)
#if defined(mingw32_HOST_OS)
@@ -87,7 +90,7 @@ processModules verbosity modules flags e
out verbosity verbose "Creating interfaces..."
let instIfaceMap = Map.fromList [ (instMod iface, iface) | ext <- extIfaces
, iface <- ifInstalledIfaces ext ]
- interfaces <- createIfaces0 verbosity modules flags instIfaceMap
+ (interfaces, ms) <- createIfaces0 verbosity modules flags instIfaceMap
let exportedNames =
Set.unions $ map (Set.fromList . ifaceExports) $
@@ -96,7 +99,7 @@ processModules verbosity modules flags e
out verbosity verbose "Attaching instances..."
interfaces' <- {-# SCC attachInstances #-}
withTiming getDynFlags "attachInstances" (const ()) $ do
- attachInstances (exportedNames, mods) interfaces instIfaceMap
+ attachInstances (exportedNames, mods) interfaces instIfaceMap ms
out verbosity verbose "Building cross-linking environment..."
-- Combine the link envs of the external packages into one
@@ -120,7 +123,7 @@ processModules verbosity modules flags e
--------------------------------------------------------------------------------
-createIfaces0 :: Verbosity -> [String] -> [Flag] -> InstIfaceMap -> Ghc [Interface]
+createIfaces0 :: Verbosity -> [String] -> [Flag] -> InstIfaceMap -> Ghc ([Interface], ModuleSet)
createIfaces0 verbosity modules flags instIfaceMap =
-- Output dir needs to be set before calling depanal since depanal uses it to
-- compute output file names that are stored in the DynFlags of the
@@ -150,43 +153,52 @@ createIfaces0 verbosity modules flags in
depanal [] False
-createIfaces :: Verbosity -> [Flag] -> InstIfaceMap -> ModuleGraph -> Ghc [Interface]
+createIfaces :: Verbosity -> [Flag] -> InstIfaceMap -> ModuleGraph -> Ghc ([Interface], ModuleSet)
createIfaces verbosity flags instIfaceMap mods = do
let sortedMods = flattenSCCs $ topSortModuleGraph False mods Nothing
out verbosity normal "Haddock coverage:"
- (ifaces, _) <- foldM f ([], Map.empty) sortedMods
- return (reverse ifaces)
+ (ifaces, _, !ms) <- foldM f ([], Map.empty, emptyModuleSet) sortedMods
+ return (reverse ifaces, ms)
where
- f (ifaces, ifaceMap) modSummary = do
+ f (ifaces, ifaceMap, !ms) modSummary = do
x <- {-# SCC processModule #-}
withTiming getDynFlags "processModule" (const ()) $ do
processModule verbosity modSummary flags ifaceMap instIfaceMap
return $ case x of
- Just iface -> (iface:ifaces, Map.insert (ifaceMod iface) iface ifaceMap)
- Nothing -> (ifaces, ifaceMap) -- Boot modules don't generate ifaces.
+ Just (iface, ms') -> ( iface:ifaces
+ , Map.insert (ifaceMod iface) iface ifaceMap
+ , unionModuleSet ms ms' )
+ Nothing -> ( ifaces
+ , ifaceMap
+ , ms ) -- Boot modules don't generate ifaces.
-processModule :: Verbosity -> ModSummary -> [Flag] -> IfaceMap -> InstIfaceMap -> Ghc (Maybe Interface)
+processModule :: Verbosity -> ModSummary -> [Flag] -> IfaceMap -> InstIfaceMap -> Ghc (Maybe (Interface, ModuleSet))
processModule verbosity modsum flags modMap instIfaceMap = do
out verbosity verbose $ "Checking module " ++ moduleString (ms_mod modsum) ++ "..."
tm <- {-# SCC "parse/typecheck/load" #-} loadModule =<< typecheckModule =<< parseModule modsum
- -- We need to modify the interactive context's environment so that when
- -- Haddock later looks for instances, it also looks in the modules it
- -- encountered while typechecking.
- --
- -- See https://github.com/haskell/haddock/issues/469.
- hsc_env@HscEnv{ hsc_IC = old_IC } <- getSession
- let new_rdr_env = tcg_rdr_env . fst . GHC.tm_internals_ $ tm
- setSession hsc_env{ hsc_IC = old_IC {
- ic_rn_gbl_env = ic_rn_gbl_env old_IC `plusGlobalRdrEnv` new_rdr_env
- } }
-
if not $ isBootSummary modsum then do
out verbosity verbose "Creating interface..."
(interface, msg) <- {-# SCC createIterface #-}
withTiming getDynFlags "createInterface" (const ()) $ do
runWriterGhc $ createInterface tm flags modMap instIfaceMap
+
+ -- We need to modify the interactive context's environment so that when
+ -- Haddock later looks for instances, it also looks in the modules it
+ -- encountered while typechecking.
+ --
+ -- See https://github.com/haskell/haddock/issues/469.
+ hsc_env <- getSession
+ let new_rdr_env = tcg_rdr_env . fst . GHC.tm_internals_ $ tm
+ this_pkg = thisPackage (hsc_dflags hsc_env)
+ !mods = mkModuleSet [ nameModule name
+ | gre <- globalRdrEnvElts new_rdr_env
+ , let name = gre_name gre
+ , nameIsFromExternalPackage this_pkg name
+ , isTcOcc (nameOccName name) -- Types and classes only
+ , unQualOK gre ] -- In scope unqualified
+
liftIO $ mapM_ putStrLn msg
dflags <- getDynFlags
let (haddockable, haddocked) = ifaceHaddockCoverage interface
@@ -220,7 +232,7 @@ processModule verbosity modsum flags mod
unless header $ out verbosity normal " Module header"
mapM_ (out verbosity normal . (" " ++)) undocumentedExports
interface' <- liftIO $ evaluate interface
- return (Just interface')
+ return (Just (interface', mods))
else
return Nothing
Index: b/utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs
===================================================================
--- a/utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs
+++ b/utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP, MagicHash #-}
+{-# LANGUAGE CPP, MagicHash, BangPatterns #-}
{-# LANGUAGE TypeFamilies #-}
-----------------------------------------------------------------------------
-- |
@@ -34,6 +34,7 @@ import FamInstEnv
import FastString
import GHC
import InstEnv
+import Module ( ModuleSet, moduleSetElts )
import MonadUtils (liftIO)
import Name
import NameEnv
@@ -51,11 +52,13 @@ type Modules = Set.Set Module
type ExportInfo = (ExportedNames, Modules)
-- Also attaches fixities
-attachInstances :: ExportInfo -> [Interface] -> InstIfaceMap -> Ghc [Interface]
-attachInstances expInfo ifaces instIfaceMap = do
- (_msgs, mb_index) <- getNameToInstancesIndex (map ifaceMod ifaces)
+attachInstances :: ExportInfo -> [Interface] -> InstIfaceMap -> ModuleSet -> Ghc [Interface]
+attachInstances expInfo ifaces instIfaceMap mods = do
+ (_msgs, mb_index) <- getNameToInstancesIndex2 (map ifaceMod ifaces) mods'
mapM (attach $ fromMaybe emptyNameEnv mb_index) ifaces
where
+ mods' = Just (moduleSetElts mods)
+
-- TODO: take an IfaceMap as input
ifaceMap = Map.fromList [ (ifaceMod i, i) | i <- ifaces ]
Provided by “Pino” via Samuel Thibault. Not yet pushed upstream.
Index: b/aclocal.m4
===================================================================
--- a/aclocal.m4
+++ b/aclocal.m4
@@ -272,12 +272,15 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_V
nto-qnx)
test -z "[$]2" || eval "[$]2=OSQNXNTO"
;;
- dragonfly|hpux|linuxaout|freebsd2|gnu|nextstep2|nextstep3|sunos4|ultrix)
+ dragonfly|hpux|linuxaout|freebsd2|nextstep2|nextstep3|sunos4|ultrix)
test -z "[$]2" || eval "[$]2=OSUnknown"
;;
aix)
test -z "[$]2" || eval "[$]2=OSAIX"
;;
+ gnu)
+ test -z "[$]2" || eval "[$]2=OSHurd"
+ ;;
*)
echo "Unknown OS '[$]1'"
exit 1
Index: b/compiler/utils/Platform.hs
===================================================================
--- a/compiler/utils/Platform.hs
+++ b/compiler/utils/Platform.hs
@@ -87,6 +87,7 @@ data OS
| OSHaiku
| OSQNXNTO
| OSAIX
+ | OSHurd
deriving (Read, Show, Eq)
-- | ARM Instruction Set Architecture, Extensions and ABI
@@ -136,6 +137,7 @@ osElfTarget OSKFreeBSD = True
osElfTarget OSHaiku = True
osElfTarget OSQNXNTO = False
osElfTarget OSAIX = False
+osElfTarget OSHurd = True
osElfTarget OSUnknown = False
-- Defaulting to False is safe; it means don't rely on any
-- ELF-specific functionality. It is important to have a default for
......@@ -6,16 +6,16 @@ Index: b/aclocal.m4
===================================================================
--- a/aclocal.m4
+++ b/aclocal.m4
@@ -1973,7 +1973,7 @@ AC_DEFUN([GHC_CONVERT_OS],[
@@ -2014,7 +2014,7 @@ AC_DEFUN([GHC_CONVERT_OS],[
$3="openbsd"
;;
# As far as I'm aware, none of these have relevant variants
- freebsd|netbsd|dragonfly|hpux|linuxaout|kfreebsdgnu|freebsd2|mingw32|darwin|gnu|nextstep2|nextstep3|sunos4|ultrix|haiku)
+ freebsd|netbsd|dragonfly|hpux|linuxaout|freebsd2|mingw32|darwin|gnu|nextstep2|nextstep3|sunos4|ultrix|haiku)
- freebsd|netbsd|dragonfly|hpux|linuxaout|kfreebsdgnu|freebsd2|mingw32|darwin|nextstep2|nextstep3|sunos4|ultrix|haiku)
+ freebsd|netbsd|dragonfly|hpux|linuxaout|freebsd2|mingw32|darwin|nextstep2|nextstep3|sunos4|ultrix|haiku)
$3="$1"
;;
aix*) # e.g. powerpc-ibm-aix7.1.3.0
@@ -1990,6 +1990,9 @@ AC_DEFUN([GHC_CONVERT_OS],[
msys)
@@ -2034,6 +2034,9 @@ AC_DEFUN([GHC_CONVERT_OS],[
# i686-gentoo-freebsd8.2
$3="freebsd"
;;
......
......@@ -7,7 +7,7 @@ Index: b/utils/ghc-pkg/Main.hs
===================================================================
--- a/utils/ghc-pkg/Main.hs
+++ b/utils/ghc-pkg/Main.hs
@@ -1824,8 +1824,10 @@ checkPackageConfig pkg verbosity db_stac
@@ -1888,8 +1888,10 @@ checkPackageConfig pkg verbosity db_stac
mapM_ (checkDir True "dynamic-library-dirs") (libraryDynDirs pkg)
mapM_ (checkDir True "include-dirs") (includeDirs pkg)
mapM_ (checkDir True "framework-dirs") (frameworkDirs pkg)
......
commit 377fe39888b1c711d15c94583ec83680d8ae7bf4
Author: Ben Gamari <ben@smart-cactus.org>
Date: Tue Oct 30 11:12:46 2018 -0400
Revert "Multiple fixes / improvements for LLVM backend"
This reverts commit 73273be476a8cc6c13368660b042b3b0614fd928.
Unfortunately we were unable to come to a fix that didn't sacrifice the
ability to bootstrap GHC using the LLVM backend. Reverting for 8.6.2.
Index: b/compiler/llvmGen/Llvm/Types.hs
===================================================================
--- a/compiler/llvmGen/Llvm/Types.hs
+++ b/compiler/llvmGen/Llvm/Types.hs
@@ -560,7 +560,7 @@ instance Outputable LlvmFuncAttr where
ppr OptSize = text "optsize"
ppr NoReturn = text "noreturn"
ppr NoUnwind = text "nounwind"
- ppr ReadNone = text "readnone"
+ ppr ReadNone = text "readnon"
ppr ReadOnly = text "readonly"
ppr Ssp = text "ssp"
ppr SspReq = text "ssqreq"
Index: b/compiler/llvmGen/LlvmCodeGen/Base.hs
===================================================================
--- a/compiler/llvmGen/LlvmCodeGen/Base.hs
+++ b/compiler/llvmGen/LlvmCodeGen/Base.hs
@@ -26,7 +26,7 @@ module LlvmCodeGen.Base (
cmmToLlvmType, widthToLlvmFloat, widthToLlvmInt, llvmFunTy,
llvmFunSig, llvmFunArgs, llvmStdFunAttrs, llvmFunAlign, llvmInfAlign,
- llvmPtrBits, tysToParams, llvmFunSection, padLiveArgs, isSSE,
+ llvmPtrBits, tysToParams, llvmFunSection,
strCLabel_llvm, strDisplayName_llvm, strProcedureName_llvm,
getGlobalPtr, generateExternDecls,
@@ -58,8 +58,6 @@ import ErrUtils
import qualified Stream
import Control.Monad (ap)
-import Data.List (sort)
-import Data.Maybe (mapMaybe)
-- ----------------------------------------------------------------------------
-- * Some Data Types
@@ -149,58 +147,16 @@ llvmFunSection dflags lbl
-- | A Function's arguments
llvmFunArgs :: DynFlags -> LiveGlobalRegs -> [LlvmVar]
llvmFunArgs dflags live =
- map (lmGlobalRegArg dflags) (filter isPassed allRegs)
+ map (lmGlobalRegArg dflags) (filter isPassed (activeStgRegs platform))
where platform = targetPlatform dflags
- allRegs = activeStgRegs platform
- paddedLive = map (\(_,r) -> r) $ padLiveArgs live
- isLive r = r `elem` alwaysLive || r `elem` paddedLive
+ isLive r = not (isSSE r) || r `elem` alwaysLive || r `elem` live
isPassed r = not (isSSE r) || isLive r
-
-
-isSSE :: GlobalReg -> Bool
-isSSE (FloatReg _) = True
-isSSE (DoubleReg _) = True
-isSSE (XmmReg _) = True
-isSSE (YmmReg _) = True
-isSSE (ZmmReg _) = True
-isSSE _ = False
-
-sseRegNum :: GlobalReg -> Maybe Int
-sseRegNum (FloatReg i) = Just i
-sseRegNum (DoubleReg i) = Just i
-sseRegNum (XmmReg i) = Just i
-sseRegNum (YmmReg i) = Just i
-sseRegNum (ZmmReg i) = Just i
-sseRegNum _ = Nothing
-
--- the bool indicates whether the global reg was added as padding.
--- the returned list is not sorted in any particular order,
--- but does indicate the set of live registers needed, with SSE padding.
-padLiveArgs :: LiveGlobalRegs -> [(Bool, GlobalReg)]
-padLiveArgs live = allRegs
- where
- sseRegNums = sort $ mapMaybe sseRegNum live
- (_, padding) = foldl assignSlots (1, []) $ sseRegNums
- allRegs = padding ++ map (\r -> (False, r)) live
-
- assignSlots (i, acc) regNum
- | i == regNum = -- don't need padding here
- (i+1, acc)
- | i < regNum = let -- add padding for slots i .. regNum-1
- numNeeded = regNum-i
- acc' = genPad i numNeeded ++ acc
- in
- (regNum+1, acc')
- | otherwise = error "padLiveArgs -- i > regNum ??"
-
- genPad start n =
- take n $ flip map (iterate (+1) start) (\i ->
- (True, FloatReg i))
- -- NOTE: Picking float should be fine for the following reasons:
- -- (1) Float aliases with all the other SSE register types on
- -- the given platform.
- -- (2) The argument is not live anyways.
-
+ isSSE (FloatReg _) = True
+ isSSE (DoubleReg _) = True
+ isSSE (XmmReg _) = True
+ isSSE (YmmReg _) = True
+ isSSE (ZmmReg _) = True
+ isSSE _ = False
-- | Llvm standard fun attributes
llvmStdFunAttrs :: [LlvmFuncAttr]
Index: b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
===================================================================
--- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
+++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
@@ -14,7 +14,7 @@ import LlvmCodeGen.Base
import LlvmCodeGen.Regs
import BlockId
-import CodeGen.Platform ( activeStgRegs )
+import CodeGen.Platform ( activeStgRegs, callerSaves )
import CLabel
import Cmm
import PprCmm
@@ -211,6 +211,7 @@ genCall t@(PrimTarget (MO_Prefetch_Data
fptr <- liftExprData $ getFunPtr funTy t
argVars' <- castVarsW Signed $ zip argVars argTy
+ doTrashStmts
let argSuffix = [mkIntLit i32 0, mkIntLit i32 localityInt, mkIntLit i32 1]
statement $ Expr $ Call StdCall fptr (argVars' ++ argSuffix) []
| otherwise = panic $ "prefetch locality level integer must be between 0 and 3, given: " ++ (show localityInt)
@@ -293,6 +294,7 @@ genCall t@(PrimTarget op) [] args
fptr <- getFunPtrW funTy t
argVars' <- castVarsW Signed $ zip argVars argTy
+ doTrashStmts
let alignVal = mkIntLit i32 align
arguments = argVars' ++ (alignVal:isVolVal)
statement $ Expr $ Call StdCall fptr arguments []
@@ -444,6 +446,7 @@ genCall target res args = runStmtsDecls
| never_returns = statement $ Unreachable
| otherwise = return ()
+ doTrashStmts
-- make the actual call
case retTy of
@@ -1756,9 +1759,12 @@ genLit _ CmmHighStackMark
funPrologue :: LiveGlobalRegs -> [CmmBlock] -> LlvmM StmtData
funPrologue live cmmBlocks = do
+ trash <- getTrashRegs
let getAssignedRegs :: CmmNode O O -> [CmmReg]
getAssignedRegs (CmmAssign reg _) = [reg]
- getAssignedRegs (CmmUnsafeForeignCall _ rs _) = map CmmLocal rs
+ -- Calls will trash all registers. Unfortunately, this needs them to
+ -- be stack-allocated in the first place.
+ getAssignedRegs (CmmUnsafeForeignCall _ rs _) = map CmmGlobal trash ++ map CmmLocal rs
getAssignedRegs _ = []
getRegsBlock (_, body, _) = concatMap getAssignedRegs $ blockToList body
assignedRegs = nub $ concatMap (getRegsBlock . blockSplit) cmmBlocks
@@ -1788,9 +1794,14 @@ funPrologue live cmmBlocks = do
funEpilogue :: LiveGlobalRegs -> LlvmM ([LlvmVar], LlvmStatements)
funEpilogue live = do
- -- the bool indicates whether the register is padding.
- let alwaysNeeded = map (\r -> (False, r)) alwaysLive
- livePadded = alwaysNeeded ++ padLiveArgs live
+ -- Have information and liveness optimisation is enabled?
+ let liveRegs = alwaysLive ++ live
+ isSSE (FloatReg _) = True
+ isSSE (DoubleReg _) = True
+ isSSE (XmmReg _) = True
+ isSSE (YmmReg _) = True
+ isSSE (ZmmReg _) = True
+ isSSE _ = False
-- Set to value or "undef" depending on whether the register is
-- actually live
@@ -1802,17 +1813,39 @@ funEpilogue live = do
let ty = (pLower . getVarType $ lmGlobalRegVar dflags r)
return (Just $ LMLitVar $ LMUndefLit ty, nilOL)
platform <- getDynFlag targetPlatform
- let allRegs = activeStgRegs platform
- loads <- flip mapM allRegs $ \r -> case () of
- _ | (False, r) `elem` livePadded
- -> loadExpr r -- if r is not padding, load it
- | not (isSSE r) || (True, r) `elem` livePadded
- -> loadUndef r
+ loads <- flip mapM (activeStgRegs platform) $ \r -> case () of
+ _ | r `elem` liveRegs -> loadExpr r
+ | not (isSSE r) -> loadUndef r
| otherwise -> return (Nothing, nilOL)
let (vars, stmts) = unzip loads
return (catMaybes vars, concatOL stmts)
+
+-- | A series of statements to trash all the STG registers.
+--
+-- In LLVM we pass the STG registers around everywhere in function calls.
+-- So this means LLVM considers them live across the entire function, when
+-- in reality they usually aren't. For Caller save registers across C calls
+-- the saving and restoring of them is done by the Cmm code generator,
+-- using Cmm local vars. So to stop LLVM saving them as well (and saving
+-- all of them since it thinks they're always live, we trash them just
+-- before the call by assigning the 'undef' value to them. The ones we
+-- need are restored from the Cmm local var and the ones we don't need
+-- are fine to be trashed.
+getTrashStmts :: LlvmM LlvmStatements
+getTrashStmts = do
+ regs <- getTrashRegs
+ stmts <- flip mapM regs $ \ r -> do
+ reg <- getCmmReg (CmmGlobal r)
+ let ty = (pLower . getVarType) reg
+ return $ Store (LMLitVar $ LMUndefLit ty) reg
+ return $ toOL stmts
+
+getTrashRegs :: LlvmM [GlobalReg]
+getTrashRegs = do plat <- getLlvmPlatform
+ return $ filter (callerSaves plat) (activeStgRegs plat)
+
-- | Get a function pointer to the CLabel specified.
--
-- This is for Haskell functions, function type is assumed, so doesn't work
@@ -1934,3 +1967,7 @@ getCmmRegW = lift . getCmmReg
genLoadW :: Atomic -> CmmExpr -> CmmType -> WriterT LlvmAccum LlvmM LlvmVar
genLoadW atomic e ty = liftExprData $ genLoad atomic e ty
+doTrashStmts :: WriterT LlvmAccum LlvmM ()
+doTrashStmts = do
+ stmts <- lift getTrashStmts
+ tell $ LlvmAccum stmts mempty
Index: b/compiler/main/DriverPipeline.hs
===================================================================
--- a/compiler/main/DriverPipeline.hs
+++ b/compiler/main/DriverPipeline.hs
@@ -1465,7 +1465,7 @@ runPhase (RealPhase LlvmOpt) input_fn df
-- we always (unless -optlo specified) run Opt since we rely on it to
-- fix up some pretty big deficiencies in the code we generate
llvmOpts = case optLevel dflags of
- 0 -> "-mem2reg -globalopt -lower-expect"
+ 0 -> "-mem2reg -globalopt"
1 -> "-O1 -globalopt"
_ -> "-O2"
Description: cherry-pick of upstream commits
beba89a0f16681c85d39fc8a894bde4162ff492a.patch:
5e63a25249f3cb07300258e115af9ff55079d2ea.patch:
Last-Update: 2018-07-19
Index: b/aclocal.m4
===================================================================
--- a/aclocal.m4
+++ b/aclocal.m4
@@ -217,7 +217,7 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_V
mipsel)
test -z "[$]2" || eval "[$]2=ArchMipsel"
;;
- hppa|hppa1_1|ia64|m68k|rs6000|s390|s390x|sh4|vax)
+ hppa|hppa1_1|ia64|m68k|riscv32|riscv64|rs6000|s390|s390x|sh4|vax)
test -z "[$]2" || eval "[$]2=ArchUnknown"
;;
*)
@@ -1884,6 +1884,12 @@ case "$1" in
powerpc*)
$2="powerpc"
;;
+ riscv64*)
+ $2="riscv64"
+ ;;
+ riscv|riscv32*)
+ $2="riscv32"
+ ;;
rs6000)
$2="rs6000"
;;
use-debian-gen_contents_index
ARM-VFPv3D16
no-missing-haddock-file-warning
hurd.diff
buildpath-abi-stability.patch
x32-use-native-x86_64-insn.patch
use-stage1-binaries-for-install.patch
llvm-arm-unknown-linux-gnueabi.patch
bsymbolic-only-for-registerised.patch
use-llvm-6.0.patch
e175aaf6918bb2b497b83618dc4c270a0d231a1c.patch
risc-support.patch
fix-build-using-unregisterized-v8.2
add_-latomic_to_ghc-prim
haddock-out-of-memory.patch
kfreebsd-aclocal.m4
revert-llvm-fixes
local-mathjax
fix-build-sphinx.patch
......@@ -2,7 +2,7 @@ Index: b/ghc.mk
===================================================================
--- a/ghc.mk
+++ b/ghc.mk
@@ -820,7 +820,6 @@ endif
@@ -809,7 +809,6 @@ endif
# Build the Haddock contents and index
ifeq "$(HADDOCK_DOCS)" "YES"
libraries/dist-haddock/index.html: $(haddock_INPLACE) $(ALL_HADDOCK_FILES)
......@@ -10,7 +10,7 @@ Index: b/ghc.mk
ifeq "$(phase)" "final"
$(eval $(call all-target,library_doc_index,libraries/dist-haddock/index.html))
endif
@@ -953,12 +952,8 @@ endif
@@ -942,12 +941,8 @@ endif
$(INSTALL_DIR) "$(DESTDIR)$(docdir)/html"
$(INSTALL_DOC) $(INSTALL_OPTS) docs/index.html "$(DESTDIR)$(docdir)/html"
ifneq "$(INSTALL_LIBRARY_DOCS)" ""
......@@ -24,11 +24,11 @@ Index: b/ghc.mk
endif
ifneq "$(INSTALL_HTML_DOC_DIRS)" ""
for i in $(INSTALL_HTML_DOC_DIRS); do \
@@ -1078,7 +1073,6 @@ $(eval $(call bindist-list,.,\
@@ -1068,7 +1063,6 @@ $(eval $(call bindist-list,.,\
mk/project.mk \
mk/install.mk.in \
bindist.mk \
- libraries/gen_contents_index \
libraries/prologue.txt \
$(wildcard libraries/dph/LICENSE \
libraries/dph/ghc-packages \
))
endif
Description: Use llvm 6.0 on arm*
Author: Gianfranco Costamagna <locutusofborg@debian.org>
Last-Update: 2018-07-19
Index: b/configure.ac
===================================================================
--- a/configure.ac
+++ b/configure.ac
@@ -638,7 +638,7 @@ AC_SUBST([LibtoolCmd])
# tools we are looking for. In the past, GHC supported a number of
# versions of LLVM simultaneously, but that stopped working around
# 3.5/3.6 release of LLVM.
-LlvmVersion=5.0
+LlvmVersion=6.0
AC_SUBST([LlvmVersion])
sUPPORTED_LLVM_VERSION=$(echo \($LlvmVersion\) | sed 's/\./,/')
AC_DEFINE_UNQUOTED([sUPPORTED_LLVM_VERSION], ${sUPPORTED_LLVM_VERSION}, [The supported LLVM version number])
......@@ -11,7 +11,7 @@ Index: b/ghc.mk
===================================================================
--- a/ghc.mk
+++ b/ghc.mk
@@ -972,8 +972,12 @@ else # CrossCompiling
@@ -961,8 +961,12 @@ else # CrossCompiling
# Install packages in the right order, so that ghc-pkg doesn't complain.
# Also, install ghc-pkg first.
ifeq "$(Windows_Host)" "NO"
......