[commit: ghc] wip/fix-integer-simple-ci: Really fix it (fcf77d1)
git at git.haskell.org
git at git.haskell.org
Thu Dec 27 17:00:36 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/fix-integer-simple-ci
Link : http://ghc.haskell.org/trac/ghc/changeset/fcf77d161f2e793218dede83c5834ff4e9955e96/ghc
>---------------------------------------------------------------
commit fcf77d161f2e793218dede83c5834ff4e9955e96
Author: Ben Gamari <ben at smart-cactus.org>
Date: Sun Dec 23 17:52:33 2018 -0500
Really fix it
>---------------------------------------------------------------
fcf77d161f2e793218dede83c5834ff4e9955e96
testsuite/driver/testlib.py | 24 +++++++++++-------------
testsuite/mk/test.mk | 2 --
testsuite/tests/numeric/should_run/all.T | 2 +-
testsuite/tests/profiling/should_run/all.T | 2 +-
4 files changed, 13 insertions(+), 17 deletions(-)
diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py
index b04ecf3..e0d4e33 100644
--- a/testsuite/driver/testlib.py
+++ b/testsuite/driver/testlib.py
@@ -133,11 +133,12 @@ def stage1(name, opts):
# Cache the results of looking to see if we have a library or not.
# This makes quite a difference, especially on Windows.
-have_lib = {}
+have_lib_cache = {}
-def _reqlib( name, opts, lib ):
- if lib in have_lib:
- got_it = have_lib[lib]
+def have_library(lib):
+ """ Test whether the given library is available """
+ if lib in have_lib_cache:
+ got_it = have_lib_cache[lib]
else:
cmd = strip_quotes(config.ghc_pkg)
p = subprocess.Popen([cmd, '--no-user-package-db', 'describe', lib],
@@ -149,9 +150,12 @@ def _reqlib( name, opts, lib ):
p.communicate()
r = p.wait()
got_it = r == 0
- have_lib[lib] = got_it
+ have_lib_cache[lib] = got_it
+
+ return got_it
- if not got_it:
+def _reqlib( name, opts, lib ):
+ if not have_library(lib):
opts.expect = 'missing-lib'
def req_haddock( name, opts ):
@@ -460,14 +464,8 @@ def have_gdb( ):
def have_readelf( ):
return config.have_readelf
-def using_integer_backend(backend):
- """ A predicate to test which integer backend we are using. """
- assert backend in ["integer-gmp", "integer-simple"]
- return config.integer_backend == backend
-
# Many tests sadly break with integer-simple due to GHCi's ignorance of it.
-broken_without_gmp = when(not(using_integer_backend("integer-gmp")),
- expect_broken(16043))
+broken_without_gmp = unless(have_library('integer-gmp'), expect_broken(16043))
# ---
diff --git a/testsuite/mk/test.mk b/testsuite/mk/test.mk
index cead469..a517698 100644
--- a/testsuite/mk/test.mk
+++ b/testsuite/mk/test.mk
@@ -247,8 +247,6 @@ else
RUNTEST_OPTS += -e config.ghc_built_by_llvm=True
endif
-RUNTEST_OPTS += -e 'config.integer_backend="$(INTEGER_LIBRARY)"'
-
RUNTEST_OPTS += \
--rootdir=. \
--config-file=$(CONFIG) \
diff --git a/testsuite/tests/numeric/should_run/all.T b/testsuite/tests/numeric/should_run/all.T
index ab05048..9d996db 100644
--- a/testsuite/tests/numeric/should_run/all.T
+++ b/testsuite/tests/numeric/should_run/all.T
@@ -21,7 +21,7 @@ test('arith008', normal, compile_and_run, [opts])
test('arith009', normal, compile_and_run, [''])
test('arith010', normal, compile_and_run, [''])
test('arith011',
- when(using_integer_backend("integer-simple"), expect_broken(16091)),
+ when(have_library("integer-simple"), expect_broken(16091)),
compile_and_run, [''])
test('arith012', normal, compile_and_run, [opts])
diff --git a/testsuite/tests/profiling/should_run/all.T b/testsuite/tests/profiling/should_run/all.T
index 1e72e94..b25cbe6 100644
--- a/testsuite/tests/profiling/should_run/all.T
+++ b/testsuite/tests/profiling/should_run/all.T
@@ -118,7 +118,7 @@ test('profinline001', [], compile_and_run, [''])
test('T11627a', [ extra_ways(extra_prof_ways),
# integer-simple has an extremely large representation and
# consequently needs more time
- when(using_integer_backend('integer-simple'),
+ when(have_library('integer-simple'),
run_timeout_multiplier(3))
],
compile_and_run, [''])
More information about the ghc-commits
mailing list