[Git][ghc/ghc][wip/slowtest] 26 commits: gitlab-ci: Fix submodule linting of commits

Ben Gamari gitlab at gitlab.haskell.org
Sun Jun 9 14:17:53 UTC 2019



Ben Gamari pushed to branch wip/slowtest at Glasgow Haskell Compiler / GHC


Commits:
4a72259d by Ben Gamari at 2019-06-08T18:40:55Z
gitlab-ci: Fix submodule linting of commits

There is no notion of a base commit when we aren't checking a merge
request. Just check the HEAD commit.

- - - - -
87540029 by Ben Gamari at 2019-06-08T20:44:55Z
gitlab-ci: Ensure that all commits on a branch are submodule-linted

The previous commit reworked things such that the submodule linter would
only run on the head commit. However, the linter only checks the
submodules which are touched by the commits it is asked to lint.
Consequently it would be possible for a bad submodule to sneak through.

Thankfully, we can use the handy CI_COMMIT_BEFORE_SHA attribute to
find the base commit of the push.

- - - - -
01bc6337 by Ben Gamari at 2019-06-09T14:17:45Z
gitlab-ci: Test using slowtest in deb9-debug job

- - - - -
2176f158 by Ben Gamari at 2019-06-09T14:17:45Z
testsuite: Mark hWaitForInput-accurate-stdin as broken in threaded ways

As noted in #16535.

- - - - -
8cbf267d by Ben Gamari at 2019-06-09T14:17:45Z
testsuite: Make closureSize less sensitive to optimisation

- - - - -
a6d479c7 by Ben Gamari at 2019-06-09T14:17:45Z
process: Bump submodule

 * Skip process005 in ghci way
 * Mark process002 as fragile in threaded2

- - - - -
58883944 by Ben Gamari at 2019-06-09T14:17:45Z
testsuite: Mark T13167 as fragile in threaded2

As noted in #16536.

- - - - -
aa5d6cbf by Ben Gamari at 2019-06-09T14:17:45Z
testsuite: Mark T13910 as broken in optasm

Due to #16537.

- - - - -
dbbb6eb5 by Ben Gamari at 2019-06-09T14:17:45Z
testsuite: Mark T14761c as broken in hpc and optasm ways

As noted in #16540.

- - - - -
a7887679 by Ben Gamari at 2019-06-09T14:17:45Z
testsuite: Mark T16180 as broken in ghci and ext-interp ways

As noted in #16541.

- - - - -
33dd75c9 by Ben Gamari at 2019-06-09T14:17:45Z
testsuite: Omit tcrun022 in hpc way

As noted in #16542, the expected rule doesn't fire. However, this
doesn't seem terribly surpring given the circumstances.

- - - - -
00d4cd4e by Ben Gamari at 2019-06-09T14:17:45Z
testsuite: Mark Overflow as broken in hpc way

As noted in #16543.

- - - - -
9a55a06d by Ben Gamari at 2019-06-09T14:17:45Z
testsuite: Mark closure_size as broken in threaded2, optasm, dyn ways

As noted in #16531.

- - - - -
9207e92d by Ben Gamari at 2019-06-09T14:17:45Z
testsuite: Mark T2783 as fragile in threaded1

It was previously marked as broken but it passes non-deterministically.
See #2783.

- - - - -
009d1f62 by Ben Gamari at 2019-06-09T14:17:45Z
testsuite: Skip T7919 in ghci way

It times out pretty reliably. It's not clear that much is gained by
running this test in the ghci way anyways.

- - - - -
d7e29363 by Ben Gamari at 2019-06-09T14:17:45Z
testsuite: Fix fragile_for test modifier

- - - - -
b112a914 by Ben Gamari at 2019-06-09T14:17:45Z
Bump unix submodule

Marks posix002 as fragile in threaded2 way due to #16550.

- - - - -
192357de by Ben Gamari at 2019-06-09T14:17:45Z
testsuite: Fix omit_ways usage

omit_ways expects a list but this was broken in several cases.

- - - - -
a203e0ba by Ben Gamari at 2019-06-09T14:17:45Z
testsuite: Mark threadstatus-T9333 as fragile in ghci way

As noted in #16555.

- - - - -
f1fd85c6 by Ben Gamari at 2019-06-09T14:17:45Z
testsuite: Omit profasm way for cc017

cc017 requires TH but we can't load dynamic profiled objects.

- - - - -
4b01f803 by Ben Gamari at 2019-06-09T14:17:45Z
testsuite: Skip T493 in ghci way.

T493 tests #493, which is an FFI test. FFI tests should be skipped
in ghci way.

- - - - -
13f84463 by Ben Gamari at 2019-06-09T14:17:46Z
testsuite: Mark T16449_2 as broken due to #16742

- - - - -
043f1019 by Ben Gamari at 2019-06-09T14:17:46Z
testsuite: Mark T16737 as broken in ghci way due to #16541

- - - - -
0f26ae4b by Ben Gamari at 2019-06-09T14:17:46Z
testsuite: Fix typo in flags of T7130

- - - - -
18db063d by Ben Gamari at 2019-06-09T14:17:46Z
testsuite: Rework T9963 to pass linter

- - - - -
e1976c17 by Ben Gamari at 2019-06-09T14:17:46Z
Fix uses of #ifdef/#ifndef

The linter now enforces our preference for `#if defined()` and
`#if !defined()`.

- - - - -


24 changed files:

- .gitlab-ci.yml
- aclocal.m4
- hadrian/src/Rules/Generate.hs
- includes/ghc.mk
- libraries/base/tests/all.T
- libraries/ghc-heap/tests/all.T
- libraries/ghc-heap/tests/closure_size.hs
- libraries/process
- libraries/unix
- testsuite/driver/testlib.py
- testsuite/tests/codeGen/should_run/all.T
- testsuite/tests/concurrent/should_run/all.T
- testsuite/tests/dependent/should_compile/all.T
- testsuite/tests/driver/all.T
- testsuite/tests/ffi/should_compile/all.T
- testsuite/tests/ffi/should_run/all.T
- testsuite/tests/lib/integer/all.T
- testsuite/tests/programs/barton-mangler-bug/test.T
- testsuite/tests/rts/all.T
- testsuite/tests/th/all.T
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_run/all.T
- testsuite/tests/utils/should_run/all.T
- testsuite/tests/warnings/should_compile/all.T


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -79,19 +79,12 @@ ghc-linters:
   script:
     - git fetch "$CI_MERGE_REQUEST_PROJECT_URL" $CI_MERGE_REQUEST_TARGET_BRANCH_NAME
     - base="$(git merge-base FETCH_HEAD $CI_COMMIT_SHA)"
-    - "echo Linting changes between $base..$CI_COMMIT_SHA"
+    - "echo Linting submodule changes between $base..$CI_COMMIT_SHA"
     - submodchecker .git $(git rev-list $base..$CI_COMMIT_SHA)
   dependencies: []
   tags:
     - lint
 
-lint-submods:
-  extends: .lint-submods
-  only:
-    refs:
-      - master
-      - /ghc-[0-9]+\.[0-9]+/
-
 lint-submods-marge:
   extends: .lint-submods
   only:
@@ -112,6 +105,16 @@ lint-submods-mr:
     variables:
       - $CI_MERGE_REQUEST_LABELS =~ /.*wip/marge_bot_batch_merge_job.*/
 
+lint-submods-branch:
+  extends: .lint-submods
+  script:
+    - "echo Linting submodule changes between $CI_COMMIT_BEFORE_SHA..$CI_COMMIT_SHA"
+    - submodchecker .git $(git rev-list $CI_COMMIT_BEFORE_SHA..$CI_COMMIT_SHA)
+  only:
+    refs:
+      - master
+      - /ghc-[0-9]+\.[0-9]+/
+
 .lint-changelogs:
   stage: lint
   image: "registry.gitlab.haskell.org/ghc/ci-images/linters:$DOCKER_REV"
@@ -460,6 +463,7 @@ validate-x86_64-linux-deb9-debug:
   stage: build
   variables:
     BUILD_FLAVOUR: validate
+    TEST_TYPE: slowtest
     TEST_ENV: "x86_64-linux-deb9-debug"
 
 validate-x86_64-linux-deb9-llvm:


=====================================
aclocal.m4
=====================================
@@ -866,7 +866,7 @@ case $TargetPlatform in
       esac ;;
     i386-unknown-mingw32) fptools_cv_leading_underscore=yes;;
     x86_64-unknown-mingw32) fptools_cv_leading_underscore=no;;
-    *) AC_RUN_IFELSE([AC_LANG_SOURCE([[#ifdef HAVE_NLIST_H
+    *) AC_RUN_IFELSE([AC_LANG_SOURCE([[#if defined(HAVE_NLIST_H)
 #include <nlist.h>
 struct nlist xYzzY1[] = {{"xYzzY1", 0},{0}};
 struct nlist xYzzY2[] = {{"_xYzzY2", 0},{0}};
@@ -876,7 +876,7 @@ int main(argc, argv)
 int argc;
 char **argv;
 {
-#ifdef HAVE_NLIST_H
+#if defined(HAVE_NLIST_H)
     if(nlist(argv[0], xYzzY1) == 0 && xYzzY1[0].n_value != 0)
         exit(1);
     if(nlist(argv[0], xYzzY2) == 0 && xYzzY2[0].n_value != 0)
@@ -1650,16 +1650,16 @@ then
     [fptools_cv_timer_create_works],
     [AC_TRY_RUN([
 #include <stdio.h>
-#ifdef HAVE_STDLIB_H
+#if defined(HAVE_STDLIB_H)
 #include <stdlib.h>
 #endif
-#ifdef HAVE_TIME_H
+#if defined(HAVE_TIME_H)
 #include <time.h>
 #endif
-#ifdef HAVE_SIGNAL_H
+#if defined(HAVE_SIGNAL_H)
 #include <signal.h>
 #endif
-#ifdef HAVE_UNISTD_H
+#if defined(HAVE_UNISTD_H)
 #include <unistd.h>
 #endif
 


=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -233,7 +233,7 @@ generateGhcPlatformH = do
     targetVendor   <- getSetting TargetVendor
     ghcUnreg       <- getFlag    GhcUnregisterised
     return . unlines $
-        [ "#ifndef __GHCPLATFORM_H__"
+        [ "#if !defined(__GHCPLATFORM_H__)"
         , "#define __GHCPLATFORM_H__"
         , ""
         , "#define BuildPlatform_TYPE  " ++ cppify hostPlatform
@@ -386,7 +386,7 @@ generateGhcAutoconfH = do
     ccLlvmBackend    <- getSetting CcLlvmBackend
     ccClangBackend   <- getSetting CcClangBackend
     return . unlines $
-        [ "#ifndef __GHCAUTOCONF_H__"
+        [ "#if !defined(__GHCAUTOCONF_H__)")
         , "#define __GHCAUTOCONF_H__" ]
         ++ configHContents ++
         [ "\n#define TABLES_NEXT_TO_CODE 1" | tablesNextToCode && not ghcUnreg ]
@@ -422,7 +422,7 @@ generateGhcBootPlatformH = do
     targetOs       <- getSetting TargetOs
     targetVendor   <- getSetting TargetVendor
     return $ unlines
-        [ "#ifndef __PLATFORM_H__"
+        [ "#if !defined(__PLATFORM_H__)")
         , "#define __PLATFORM_H__"
         , ""
         , "#define BuildPlatform_NAME  " ++ show buildPlatform
@@ -464,10 +464,10 @@ generateGhcVersionH = do
     patchLevel1 <- getSetting ProjectPatchLevel1
     patchLevel2 <- getSetting ProjectPatchLevel2
     return . unlines $
-        [ "#ifndef __GHCVERSION_H__"
+        [ "#if !defined(__GHCVERSION_H__)")
         , "#define __GHCVERSION_H__"
         , ""
-        , "#ifndef __GLASGOW_HASKELL__"
+        , "#if !defined(__GLASGOW_HASKELL__)")
         , "# define __GLASGOW_HASKELL__ " ++ version
         , "#endif"
         , ""]


=====================================
includes/ghc.mk
=====================================
@@ -57,7 +57,7 @@ endif
 
 $(includes_H_VERSION) : mk/project.mk | $$(dir $$@)/.
 	@echo "Creating $@..."
-	@echo "#ifndef __GHCVERSION_H__"  > $@
+	@echo "#if !defined(__GHCVERSION_H__)"  > $@)
 	@echo "#define __GHCVERSION_H__" >> $@
 	@echo >> $@
 	@echo "#define __GLASGOW_HASKELL__ $(ProjectVersionInt)" >> $@
@@ -92,7 +92,7 @@ else
 
 $(includes_H_CONFIG) : mk/config.h mk/config.mk includes/ghc.mk | $$(dir $$@)/.
 	@echo "Creating $@..."
-	@echo "#ifndef __GHCAUTOCONF_H__"  >$@
+	@echo "#if !defined(__GHCAUTOCONF_H__)"  >$@)
 	@echo "#define __GHCAUTOCONF_H__" >>$@
 #
 #	Copy the contents of mk/config.h, turning '#define PACKAGE_FOO
@@ -125,7 +125,7 @@ endif
 $(includes_H_PLATFORM) : includes/Makefile | $$(dir $$@)/.
 	$(call removeFiles,$@)
 	@echo "Creating $@..."
-	@echo "#ifndef __GHCPLATFORM_H__"  >$@
+	@echo "#if !defined(__GHCPLATFORM_H__)"  >$@)
 	@echo "#define __GHCPLATFORM_H__" >>$@
 	@echo >> $@
 	@echo "#define BuildPlatform_TYPE  $(HostPlatform_CPP)" >> $@


=====================================
libraries/base/tests/all.T
=====================================
@@ -203,7 +203,7 @@ test('T8089',
      compile_and_run, [''])
 test('hWaitForInput-accurate-socket', reqlib('unix'), compile_and_run, [''])
 test('T8684', expect_broken(8684), compile_and_run, [''])
-test('hWaitForInput-accurate-stdin', normal, compile_and_run, [''])
+test('hWaitForInput-accurate-stdin', [expect_broken_for(16535, ['threaded1', 'threaded2']), omit_ways(['ghci'])], compile_and_run, [''])
 test('hWaitForInput-accurate-pipe', reqlib('unix'), compile_and_run, [''])
 test('T9826',normal, compile_and_run,[''])
 test('T9848',
@@ -234,6 +234,6 @@ test('T3474',
 test('T14425', normal, compile_and_run, [''])
 test('T10412', normal, compile_and_run, [''])
 test('T13896', normal, compile_and_run, [''])
-test('T13167', normal, compile_and_run, [''])
+test('T13167', fragile_for(16536, ['threaded2']), compile_and_run, [''])
 test('T15349', [exit_code(1), expect_broken_for(15349, 'ghci')], compile_and_run, [''])
 test('T16111', exit_code(1), compile_and_run, [''])


=====================================
libraries/ghc-heap/tests/all.T
=====================================
@@ -7,5 +7,5 @@ test('heap_all',
      ],
      compile_and_run, [''])
 test('closure_size',
-     omit_ways(['ghci', 'hpc', 'prof']),
+     [omit_ways(['ghci', 'hpc', 'prof']), expect_broken_for(16544, ['dyn', 'optasm', 'threaded2'])],
      compile_and_run, [''])


=====================================
libraries/ghc-heap/tests/closure_size.hs
=====================================
@@ -1,6 +1,7 @@
 {-# LANGUAGE BangPatterns #-}
 {-# LANGUAGE TypeApplications #-}
 {-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE MagicHash #-}
 
 import Control.Monad
 import Type.Reflection
@@ -17,12 +18,17 @@ assertSize !x expected = do
     putStrLn $ prettyCallStack callStack
 {-# NOINLINE assertSize #-}
 
-pap :: Int -> Char -> Int
+pap :: Int -> Maybe Char -> Int
 pap x _ = x
 {-# NOINLINE pap #-}
 
 main :: IO ()
 main = do
+  -- Ensure that GHC can't turn PAP into a FUN (see #16531)
+  let x :: Int
+      x = 42
+      {-# NOINLINE x #-}
+
   assertSize 'a' 2
   assertSize (Just ()) 2
   assertSize (Nothing :: Maybe ()) 2
@@ -30,5 +36,5 @@ main = do
   assertSize ((1,2,3) :: (Int,Int,Int)) 4
   assertSize (id :: Int -> Int) 1
   assertSize (fst :: (Int,Int) -> Int) 1
-  assertSize (pap 1) 2
+  assertSize (pap x) 2
 


=====================================
libraries/process
=====================================
@@ -1 +1 @@
-Subproject commit d860209e53c1b40b7c251fc8378886bbcb394402
+Subproject commit 5c81524694ceaf8523a1846718a7a7c3f402124f


=====================================
libraries/unix
=====================================
@@ -1 +1 @@
-Subproject commit a102df29c107e8f853129dd40fbbb487e1818149
+Subproject commit a67b5e9e70a2a0c438d4f186fda9f38409ff1435


=====================================
testsuite/driver/testlib.py
=====================================
@@ -257,14 +257,14 @@ def fragile( bug ):
 
     return helper
 
-def fragile_for( name, opts, bug, ways ):
+def fragile_for( bug, ways ):
     """
     Indicates that the test should be skipped due to fragility in the given
     test ways as documented in the given ticket.
     """
     def helper( name, opts, bug=bug, ways=ways ):
         record_broken(name, opts, bug)
-        opts.omit_ways = ways
+        opts.omit_ways += ways
 
     return helper
 
@@ -274,7 +274,8 @@ def omit_ways( ways ):
     return lambda name, opts, w=ways: _omit_ways( name, opts, w )
 
 def _omit_ways( name, opts, ways ):
-    opts.omit_ways = ways
+    assert ways.__class__ is list
+    opts.omit_ways += ways
 
 # -----
 
@@ -1432,7 +1433,6 @@ def simple_run(name, way, prog, extra_run_opts):
         return failBecause('bad stderr')
     if not (opts.ignore_stdout or stdout_ok(name, way)):
         return failBecause('bad stdout')
-
     check_hp = '-h' in my_rts_flags and opts.check_hp
     check_prof = '-p' in my_rts_flags
 


=====================================
testsuite/tests/codeGen/should_run/all.T
=====================================
@@ -195,4 +195,4 @@ test('T15892',
         extra_run_opts('+RTS -G1 -A32k -RTS') ],
      compile_and_run, ['-O'])
 test('T16617', normal, compile_and_run, [''])
-test('T16449_2', exit_code(1), compile_and_run, [''])
+test('T16449_2', [expect_broken_for(16742, ['dyn', 'ghci', 'optasm', 'threaded2']), exit_code(1)], compile_and_run, [''])


=====================================
testsuite/tests/concurrent/should_run/all.T
=====================================
@@ -88,7 +88,7 @@ test('T7970', normal, compile_and_run, [''])
 test('AtomicPrimops', normal, compile_and_run, [''])
 
 # test uses 2 threads and yield, scheduling can vary with threaded2
-test('threadstatus-9333', [omit_ways(['threaded2'])], compile_and_run, [''])
+test('threadstatus-9333', [fragile_for(16555, ['ghci']), omit_ways(['threaded2'])], compile_and_run, [''])
 
 test('T9379', normal, compile_and_run, [''])
 
@@ -239,7 +239,7 @@ test('conc067', ignore_stdout, compile_and_run, [''])
 
 # omit threaded2, the behaviour of this test is non-deterministic with more
 # than one CPU.
-test('conc068', [ omit_ways('threaded2'), exit_code(1) ], compile_and_run, [''])
+test('conc068', [ omit_ways(['threaded2']), exit_code(1) ], compile_and_run, [''])
 
 test('setnumcapabilities001',
      [ only_ways(['threaded1','threaded2']),


=====================================
testsuite/tests/dependent/should_compile/all.T
=====================================
@@ -40,7 +40,7 @@ test('T12742', normal, compile, [''])
 #       (1) Use -fexternal-interpreter, or
 #       (2) Build the program twice: once with -dynamic, and then
 #           with -prof using -osuf to set a different object file suffix.
-test('T13910', omit_ways(['profasm']), compile, [''])
+test('T13910', [expect_broken_for(16537, ['optasm']), omit_ways(['profasm'])], compile, [''])
 test('T13938', [extra_files(['T13938a.hs'])], makefile_test, ['T13938'])
 test('T14556', normal, compile, [''])
 test('T14720', normal, compile, [''])


=====================================
testsuite/tests/driver/all.T
=====================================
@@ -170,7 +170,7 @@ test( 'T4114d', [fobject_code, expect_broken_for(4114, ['ghci'])], compile_and_r
 test('T5584', [], makefile_test, [])
 test('T5198', [], makefile_test, [])
 test('T7060', [], makefile_test, [])
-test('T7130', normal, compile_fail, ['-fflul-laziness'])
+test('T7130', normal, compile_fail, ['-ffull-laziness'])
 test('T7563', when(unregisterised(), skip), makefile_test, [])
 test('T6037',
      # The testsuite doesn't know how to set a non-Unicode locale on Windows or Mac OS X
@@ -207,7 +207,7 @@ test('T9938', [], makefile_test, [])
 test('T9938B', [], makefile_test, [])
 
 test('T9963', exit_code(1), run_command,
-     ['{compiler} --interactive -ignore-dot-ghci --print-libdir'])
+     ['{compiler} --print-libdir'])
 
 test('T10219', normal, run_command,
      # `-x hspp` in make mode should work.
@@ -270,4 +270,6 @@ test('inline-check', omit_ways(['hpc', 'profasm'])
 
 test('T14452', [], makefile_test, [])
 test('T15396', normal, compile_and_run, ['-package ghc'])
-test('T16737', [extra_files(['T16737include/'])], compile_and_run, ['-optP=-isystem -optP=T16737include'])
+test('T16737',
+     [extra_files(['T16737include/']), expect_broken_for(16541, ['ghci'])],
+     compile_and_run, ['-optP=-isystem -optP=T16737include'])


=====================================
testsuite/tests/ffi/should_compile/all.T
=====================================
@@ -35,7 +35,8 @@ test('T11983', [omit_ways(['ghci'])], compile, ['T11983.c'])
 test('T14125', normal, compile, [''])
 test(
     'cc017',
-    normal,
+    # We need TH but can't load profiled dynamic objects
+    when(ghc_dynamic(), omit_ways(['profasm'])),
     compile,
     [
         '-optc=-DC -optcxx=-DCXX -optcxx=-std=c++11'


=====================================
testsuite/tests/ffi/should_run/all.T
=====================================
@@ -207,4 +207,4 @@ test('PrimFFIInt16', [omit_ways(['ghci'])], compile_and_run, ['PrimFFIInt16_c.c'
 
 test('PrimFFIWord16', [omit_ways(['ghci'])], compile_and_run, ['PrimFFIWord16_c.c'])
 
-test('T493', [], compile_and_run, ['T493_c.c'])
+test('T493', [omit_ways(['ghci'])], compile_and_run, ['T493_c.c'])


=====================================
testsuite/tests/lib/integer/all.T
=====================================
@@ -1,8 +1,8 @@
 test('integerBits', normal, compile_and_run, [''])
 test('integerConversions', normal, compile_and_run, [''])
 # skip ghci as it doesn't support unboxed tuples
-test('integerGmpInternals', [reqlib('integer-gmp'), omit_ways('ghci')], compile_and_run, [''])
-test('plusMinusInteger', [omit_ways('ghci')], compile_and_run, [''])
+test('integerGmpInternals', [reqlib('integer-gmp'), omit_ways(['ghci'])], compile_and_run, [''])
+test('plusMinusInteger', [omit_ways(['ghci'])], compile_and_run, [''])
 test('integerConstantFolding', normal, makefile_test, ['integerConstantFolding'])
 test('fromToInteger', [], makefile_test, ['fromToInteger'])
 test('IntegerConversionRules', [], makefile_test, ['IntegerConversionRules'])


=====================================
testsuite/tests/programs/barton-mangler-bug/test.T
=====================================
@@ -8,7 +8,7 @@ test('barton-mangler-bug',
                    'Plot.hi',              'Plot.o',
                    'PlotExample.hi',       'PlotExample.o',
                    'TypesettingTricks.hi', 'TypesettingTricks.o']),
-      omit_ways('debug') # Fails for debug way due to annotation linting timeout
+      omit_ways(['debug']) # Fails for debug way due to annotation linting timeout
       ],
      multimod_compile_and_run, ['Main', ''])
 


=====================================
testsuite/tests/rts/all.T
=====================================
@@ -73,7 +73,7 @@ test('T2047', [ignore_stdout, extra_run_opts('+RTS -c -RTS')],
 # Blackhole-detection test.
 # Skip GHCi due to #2786
 test('T2783', [ omit_ways(['ghci']), exit_code(1)
-              , expect_broken_for(2783, ['threaded1'])
+              , fragile_for(2783, ['threaded1'])
               ], compile_and_run, [''])
 
 # Test the work-stealing deque implementation.  We run this test in
@@ -93,7 +93,7 @@ test('stack002', [extra_files(['stack001.hs']),
 
 # run this test with very small stack chunks to exercise the stack
 # overflow/underflow machinery.
-test('stack003', [ omit_ways('ghci'), # uses unboxed tuples
+test('stack003', [ omit_ways(['ghci']), # uses unboxed tuples
                    extra_run_opts('500000 +RTS -kc1k -kb100 -K96m -RTS') ],
                  compile_and_run, [''])
 
@@ -214,7 +214,8 @@ test('T7815', [ multi_cpu_race,
 test('ffishutdown', [ignore_stderr, only_ways(['threaded1','threaded2'])],
      compile_and_run, [''])
 
-test('T7919', [when(fast(), skip), omit_ways(prof_ways)], compile_and_run,
+# Times out in ghci way
+test('T7919', [when(fast(), skip), omit_ways(['ghci'] + prof_ways)], compile_and_run,
      [config.ghc_th_way_flags])
 
 test('T8035', normal, compile_and_run, [''])


=====================================
testsuite/tests/th/all.T
=====================================
@@ -13,7 +13,7 @@ if config.have_ext_interp :
        setTestOpts(extra_ways(['ext-interp']))
        setTestOpts(only_ways(['normal','ghci','ext-interp']))
 
-broken_tests = ["ClosedFam1TH","T10620","T10828","T11721_TH","T11797","T12045TH2","T12478_1","T12646","T13642","T14060","T15502","T15738","T15792","T15845","T1835","T3920","T4135","T4188","T5037","T5362","T7477","T7910","T8761","T8884","T8953","T9262","T9692","T9738","TH_Lift","TH_RichKinds","TH_RichKinds2","TH_Roles3","TH_TyInstWhere2","TH_implicitParams","TH_recursiveDo","TH_reifyDecl1","TH_reifyExplicitForAllFams","TH_reifyInstances","TH_reifyMkName","TH_repE2","TH_repGuard","TH_repPrim","TH_repPrim2","TH_repUnboxedTuples","TH_spliceE6","T16326_TH"]
+broken_tests = ["ClosedFam1TH","T10620","T10828","T11721_TH","T11797","T12045TH2","T12478_1","T12646","T13642","T14060","T15502","T15738","T15792","T15845","T16180","T1835","T3920","T4135","T4188","T5037","T5362","T7477","T7910","T8761","T8884","T8953","T9262","T9692","T9738","TH_Lift","TH_RichKinds","TH_RichKinds2","TH_Roles3","TH_TyInstWhere2","TH_implicitParams","TH_recursiveDo","TH_reifyDecl1","TH_reifyExplicitForAllFams","TH_reifyInstances","TH_reifyMkName","TH_repE2","TH_repGuard","TH_repPrim","TH_repPrim2","TH_repUnboxedTuples","TH_spliceE6","T16326_TH"]
 # ext-interp, integer-gmp and llvm is broken see #16087
 def broken_ext_interp(name, opts):
 	if name in broken_tests and config.ghc_built_by_llvm:
@@ -467,7 +467,10 @@ test('T15437', expect_broken(15437), multimod_compile,
 test('T15985', normal, compile, [''])
 test('T16133', normal, compile_fail, [''])
 test('T15471', normal, multimod_compile, ['T15471.hs', '-v0'])
-test('T16180', normal, compile_and_run, [''])
+test('T16180',
+     [when(llvm_build(), expect_broken_for(16541, ['ext-interp'])),
+      expect_broken_for(16541, ['ghci'])],
+     compile_and_run, ['-package ghc'])
 test('T16183', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
 test('T16195', normal, multimod_compile, ['T16195.hs', '-v0'])
 test('T16293b', normal, compile, [''])


=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -659,7 +659,7 @@ test('T15586', normal, compile, [''])
 test('T15368', normal, compile, ['-fdefer-type-errors'])
 test('T15645', normal, compile, ['-Wwarn=missing-monadfail-instances'])
 test('T15778', normal, compile, [''])
-test('T14761c', normal, compile, [''])
+test('T14761c', expect_broken_for(16540, ['hpc', 'optasm']), compile, [''])
 test('T16008', normal, compile, [''])
 test('T16033', normal, compile, [''])
 test('T16141', normal, compile, ['-O'])


=====================================
testsuite/tests/typecheck/should_run/all.T
=====================================
@@ -35,7 +35,7 @@ test('tcrun018', normal, compile_and_run, [''])
 test('tcrun019', normal, compile_and_run, [''])
 test('tcrun020', normal, compile_and_run, [''])
 test('tcrun021', normal, compile_and_run, ['-package containers'])
-test('tcrun022', omit_ways(['ghci']), compile_and_run, ['-O'])
+test('tcrun022', omit_ways(['hpc', 'ghci']), compile_and_run, ['-O'])
 test('tcrun023', [when(doing_ghci(), extra_hc_opts('-fobject-code'))],
      compile_and_run, ['-O'])
 test('tcrun024', normal, compile_and_run, ['-O'])
@@ -96,7 +96,7 @@ test('T6117', normal, compile_and_run, [''])
 test('T5751', normal, compile_and_run, [''])
 test('T5913', normal, compile_and_run, [''])
 test('T7748', normal, compile_and_run, [''])
-test('T7861', [omit_ways('debug'), exit_code(1)], compile_and_run, [''])
+test('T7861', [omit_ways(['debug']), exit_code(1)], compile_and_run, [''])
 test('TcTypeNatSimpleRun', normal, compile_and_run, [''])
 test('TcTypeSymbolSimpleRun', normal, compile_and_run, [''])
 test('T8119', normal, ghci_script, ['T8119.script'])


=====================================
testsuite/tests/utils/should_run/all.T
=====================================
@@ -1,6 +1,6 @@
 test('T14854',
      [only_ways(threaded_ways),
-      omit_ways('ghci'),
+      omit_ways(['ghci']),
       reqlib('random'),
       ignore_stderr],
      compile_and_run,


=====================================
testsuite/tests/warnings/should_compile/all.T
=====================================
@@ -26,4 +26,4 @@ test('T16551', [extra_files(['T16551/'])], multimod_compile, ['T16551/A.hs T1655
 
 test('StarBinder', normal, compile, [''])
 
-test('Overflow', normal, compile, [''])
+test('Overflow', expect_broken_for(16543, ['hpc']), compile, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/852c0671308c4acafc5fff43d2e898296609af36...e1976c17127a1bb39b58cacad4593ddaa0c02a0d

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/852c0671308c4acafc5fff43d2e898296609af36...e1976c17127a1bb39b58cacad4593ddaa0c02a0d
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/20190609/72b5c611/attachment-0001.html>


More information about the ghc-commits mailing list