[Git][ghc/ghc][ghc-9.0] 3 commits: testsuite: Only run llvm ways if llc is available

Ben Gamari gitlab at gitlab.haskell.org
Tue Sep 8 02:26:35 UTC 2020



Ben Gamari pushed to branch ghc-9.0 at Glasgow Haskell Compiler / GHC


Commits:
c2030f00 by Ben Gamari at 2020-09-07T16:16:05-04:00
testsuite: Only run llvm ways if llc is available

As noted in #18560, we previously would always run the LLVM ways since
`configure` would set `SettingsLlcCommand` to something non-null when
it otherwise couldn't find the `llc` executable. Now we rather probe for
the existence of the `llc` executable in the testsuite driver.

Fixes #18560.

(cherry picked from commit aa4b744d51aa6bdb46064f981ea8e001627921d6)

- - - - -
6dbd1054 by Sylvain Henry at 2020-09-07T16:20:38-04:00
Remove outdated note

- - - - -
c23275f4 by Sylvain Henry at 2020-09-07T16:20:38-04:00
Bignum: add missing compat import/export functions

- - - - -


6 changed files:

- compiler/GHC/Builtin/Names.hs
- hadrian/src/Settings/Builders/RunTest.hs
- libraries/integer-gmp/src/GHC/Integer/GMP/Internals.hs
- testsuite/config/ghc
- testsuite/driver/testglobals.py
- testsuite/mk/test.mk


Changes:

=====================================
compiler/GHC/Builtin/Names.hs
=====================================
@@ -116,35 +116,6 @@ known keys. See
 Note [One-tuples] (Wrinkle: Make boxed one-tuple names have known keys)
 in GHC.Builtin.Types.
 
-Note [The integer library]
-~~~~~~~~~~~~~~~~~~~~~~~~~~
-
-Clearly, we need to know the names of various definitions of the integer
-library, e.g. the type itself, `mkInteger` etc. But there are two possible
-implementations of the integer library:
-
- * integer-gmp (fast, but uses libgmp, which may not be available on all
-   targets and is GPL licensed)
- * integer-simple (slow, but pure Haskell and BSD-licensed)
-
-We want the compiler to work with either one. The way we achieve this is:
-
- * When compiling the integer-{gmp,simple} library, we pass
-     -this-unit-id  integer-wired-in
-   to GHC (see the cabal file libraries/integer-{gmp,simple}.
- * This way, GHC can use just this UnitID (see Module.integerUnitId) when
-   generating code, and the linker will succeed.
-
-Unfortuately, the abstraction is not complete: When using integer-gmp, we
-really want to use the S# constructor directly. This is controlled by
-the `integerLibrary` field of `DynFlags`: If it is IntegerGMP, we use
-this constructor directly (see  CorePrep.lookupIntegerSDataConName)
-
-When GHC reads the package data base, it (internally only) pretends it has UnitId
-`integer-wired-in` instead of the actual UnitId (which includes the version
-number); just like for `base` and other packages, as described in
-Note [Wired-in units] in GHC.Unit.Module. This is done in
-GHC.Unit.State.findWiredInUnits.
 -}
 
 {-# LANGUAGE CPP #-}


=====================================
hadrian/src/Settings/Builders/RunTest.hs
=====================================
@@ -70,7 +70,6 @@ runTestBuilderArgs = builder RunTest ? do
     withSMP             <- getBooleanSetting TestGhcWithSMP
     debugged            <- getBooleanSetting TestGhcDebugged
     keepFiles           <- expr (testKeepFiles <$> userSetting defaultTestArgs)
-    withLlvm            <- expr (not . null <$> settingsFileSetting SettingsFileSetting_LlcCommand)
 
     accept <- expr (testAccept <$> userSetting defaultTestArgs)
     (acceptPlatform, acceptOS) <- expr . liftIO $
@@ -126,8 +125,6 @@ runTestBuilderArgs = builder RunTest ? do
             , arg "-e", arg $ asBool "config.have_profiling=" (hasLibWay profiling)
             , arg "-e", arg $ asBool "config.have_fast_bignum=" (bignumBackend /= "native" && not bignumCheck)
             , arg "-e", arg $ asBool "ghc_with_smp=" withSMP
-            , arg "-e", arg $ asBool "ghc_with_llvm=" withLlvm
-
 
             , arg "-e", arg $ "config.ghc_dynamic_by_default=" ++ show hasDynamicByDefault
             , arg "-e", arg $ "config.ghc_dynamic=" ++ show hasDynamic


=====================================
libraries/integer-gmp/src/GHC/Integer/GMP/Internals.hs
=====================================
@@ -57,9 +57,6 @@ module GHC.Integer.GMP.Internals
     , bigNatToInt
     , bigNatToWord
     , indexBigNat#
-    , importBigNatFromByteArray
-    , exportBigNatToMutableByteArray
-
 
       -- ** 'BigNat' arithmetic operations
     , plusBigNat
@@ -112,9 +109,17 @@ module GHC.Integer.GMP.Internals
 
       -- ** Export
     , exportBigNatToAddr
+    , exportIntegerToAddr
+
+    , exportBigNatToMutableByteArray
+    , exportIntegerToMutableByteArray
 
       -- ** Import
     , importBigNatFromAddr
+    , importIntegerFromAddr
+
+    , importBigNatFromByteArray
+    , importIntegerFromByteArray
     ) where
 
 import GHC.Integer
@@ -373,6 +378,18 @@ exportBigNatToAddr (BN# b) addr endian = IO \s ->
    case B.bigNatToAddr# b addr endian s of
       (# s', w #) -> (# s', W# w #)
 
+{-# DEPRECATED importIntegerFromAddr "Use integerFromAddr# instead" #-}
+importIntegerFromAddr :: Addr# -> Word# -> Int# -> IO Integer
+importIntegerFromAddr addr sz endian = IO \s ->
+   case I.integerFromAddr# sz addr endian s of
+      (# s', i #) -> (# s', i #)
+
+{-# DEPRECATED exportIntegerToAddr "Use integerToAddr# instead" #-}
+exportIntegerToAddr :: Integer -> Addr# -> Int# -> IO Word
+exportIntegerToAddr i addr endian = IO \s ->
+   case I.integerToAddr# i addr endian s of
+      (# s', w #) -> (# s', W# w #)
+
 wordToBigNat :: Word# -> BigNat
 wordToBigNat w = BN# (B.bigNatFromWord# w)
 
@@ -398,3 +415,13 @@ importBigNatFromByteArray ba off sz endian = case runRW# (B.bigNatFromByteArray#
 exportBigNatToMutableByteArray :: BigNat -> MutableByteArray# RealWorld -> Word# -> Int# -> IO Word
 exportBigNatToMutableByteArray (BN# ba) mba off endian = IO (\s -> case B.bigNatToMutableByteArray# ba mba off endian s of
    (# s', r #) -> (# s', W# r #))
+
+{-# DEPRECATED importIntegerFromByteArray "Use integerFromByteArray# instead" #-}
+importIntegerFromByteArray :: ByteArray# -> Word# -> Word# -> Int# -> Integer
+importIntegerFromByteArray ba off sz endian = case runRW# (I.integerFromByteArray# sz ba off endian) of
+   (# _, r #) -> r
+
+{-# DEPRECATED exportIntegerToMutableByteArray "Use integerToMutableByteArray# instead" #-}
+exportIntegerToMutableByteArray :: Integer -> MutableByteArray# RealWorld -> Word# -> Int# -> IO Word
+exportIntegerToMutableByteArray i mba off endian = IO (\s -> case I.integerToMutableByteArray# i mba off endian s of
+   (# s', r #) -> (# s', W# r #))


=====================================
testsuite/config/ghc
=====================================
@@ -64,10 +64,6 @@ else:
 if (config.have_profiling and ghc_with_threaded_rts):
     config.run_ways.append('profthreaded')
 
-if (ghc_with_llvm and not config.unregisterised):
-    config.compile_ways.append('optllvm')
-    config.run_ways.append('optllvm')
-
 # WinIO I/O manager for Windows
 if windows:
     winio_ways = ['winio', 'winio_threaded']
@@ -195,6 +191,17 @@ def get_compiler_info():
 
     config.have_ncg = compilerInfoDict.get("Have native code generator", "NO") == "YES"
 
+    # Detect whether an LLVM toolhain is available
+    llc_path = compilerInfoDict.get("LLVM llc command")
+    config.have_llvm = shutil.which(llc_path) is not None
+    if config.unregisterised:
+        print("Unregisterised build; skipping LLVM ways...")
+    elif config.have_llvm:
+        config.compile_ways.append('optllvm')
+        config.run_ways.append('optllvm')
+    else:
+        print("Failed to find `llc` command; skipping LLVM ways...")
+
     # Whether GHC itself was built using the LLVM backend. We need to know this
     # since some tests in ext-interp fail when stage2 ghc is built using
     # LLVM. See #16087.


=====================================
testsuite/driver/testglobals.py
=====================================
@@ -115,6 +115,9 @@ class TestConfig:
         self.way_flags = {}  # type: Dict[WayName, List[str]]
         self.way_rts_flags = {}  # type: Dict[WayName, List[str]]
 
+        # Do we have a functional LLVM toolchain?
+        self.have_llvm = False
+
         # Do we have vanilla libraries?
         self.have_vanilla = False
 


=====================================
testsuite/mk/test.mk
=====================================
@@ -188,18 +188,6 @@ else
 RUNTEST_OPTS += -e ghc_with_smp=False
 endif
 
-# Does the LLVM backend work?
-ifeq "$(LLC)" ""
-RUNTEST_OPTS += -e ghc_with_llvm=False
-else ifeq "$(TargetARCH_CPP)" "powerpc"
-RUNTEST_OPTS += -e ghc_with_llvm=False
-else ifneq "$(LLC)" "llc"
-# If we have a real detected value for LLVM, then it really ought to work
-RUNTEST_OPTS += -e ghc_with_llvm=True
-else
-RUNTEST_OPTS += -e ghc_with_llvm=False
-endif
-
 ifeq "$(WINDOWS)" "YES"
 RUNTEST_OPTS += -e windows=True
 else



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cee137dcab0b33915b0add69db9535ef4227f824...c23275f4dd8999c673da1b9458c68e768e1f72a6

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cee137dcab0b33915b0add69db9535ef4227f824...c23275f4dd8999c673da1b9458c68e768e1f72a6
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200907/45f76e17/attachment-0001.html>


More information about the ghc-commits mailing list