[Git][ghc/ghc][wip/cross-ci] 14 commits: testsuite/driver: Add basic support for testing cross-compilers

Ben Gamari (@bgamari) gitlab at gitlab.haskell.org
Tue Oct 18 20:24:04 UTC 2022



Ben Gamari pushed to branch wip/cross-ci at Glasgow Haskell Compiler / GHC


Commits:
bf493e0c by Ben Gamari at 2022-10-18T16:23:54-04:00
testsuite/driver: Add basic support for testing cross-compilers

- - - - -
b6a4dc06 by Ben Gamari at 2022-10-18T16:23:54-04:00
testsuite: Mark annrun01 as req_interp

Annotations require the compile-time code loading.

- - - - -
7dd425c2 by Ben Gamari at 2022-10-18T16:23:54-04:00
testsuite: Drop annotation from T17904

Annotations make it harder to run tests due to compile-time code loading
and this particular annotation was not critical to the test.

- - - - -
eb0e67de by Ben Gamari at 2022-10-18T16:23:54-04:00
testsuite: Mark T21115b as req_th

- - - - -
9d601276 by Ben Gamari at 2022-10-18T16:23:54-04:00
testsuite/driver: Normalize away differences in ghc executable name

- - - - -
dd356e38 by Ben Gamari at 2022-10-18T16:23:54-04:00
testsuite: Mark cc017 as req_th

- - - - -
8a12e595 by Ben Gamari at 2022-10-18T16:23:54-04:00
testsuite: Mark some multipleHomeUnits tests as req_th

- - - - -
740e1cde by Ben Gamari at 2022-10-18T16:23:54-04:00
testsuite: Mark NoFieldSelectors as req_interp

Due to ANN usage.

- - - - -
9b1b832d by Ben Gamari at 2022-10-18T16:23:54-04:00
testsuite: Mark LinearTH tests as req_th

- - - - -
dd980909 by Ben Gamari at 2022-10-18T16:23:54-04:00
testsuite: Mark overfloadedrecflds/ghci tests as req_interp

Due to ghci usage.

- - - - -
34ff19f5 by Ben Gamari at 2022-10-18T16:23:54-04:00
testsuite: Mark T7919 as req_th

- - - - -
046d666a by Ben Gamari at 2022-10-18T16:23:54-04:00
testsuite: Mark a number of tests omitting profasm as req_th

- - - - -
fab09f4b by Ben Gamari at 2022-10-18T16:23:54-04:00
testsuite: Introduce and use req_plugins

- - - - -
0a03d9d2 by Ben Gamari at 2022-10-18T16:23:55-04:00
hadrian: Pass CROSS_EMULATOR to runtests.py

- - - - -


24 changed files:

- hadrian/src/Settings/Builders/RunTest.hs
- testsuite/driver/runtests.py
- testsuite/driver/testglobals.py
- testsuite/driver/testlib.py
- testsuite/tests/annotations/should_run/all.T
- testsuite/tests/codeGen/should_compile/T17904.hs
- testsuite/tests/corelint/all.T
- testsuite/tests/dependent/should_compile/all.T
- testsuite/tests/driver/multipleHomeUnits/all.T
- testsuite/tests/driver/multipleHomeUnits/th-deps/all.T
- testsuite/tests/ffi/should_compile/all.T
- testsuite/tests/linear/should_compile/all.T
- testsuite/tests/overloadedrecflds/ghci/all.T
- testsuite/tests/overloadedrecflds/should_compile/all.T
- testsuite/tests/partial-sigs/should_compile/all.T
- testsuite/tests/patsyn/should_run/all.T
- testsuite/tests/plugins/all.T
- testsuite/tests/rts/all.T
- testsuite/tests/saks/should_compile/all.T
- testsuite/tests/simplCore/should_compile/all.T
- testsuite/tests/tcplugins/all.T
- testsuite/tests/th/should_compile/T13949/all.T
- testsuite/tests/th/should_compile/T8025/all.T
- testsuite/tests/typecheck/should_compile/all.T


Changes:

=====================================
hadrian/src/Settings/Builders/RunTest.hs
=====================================
@@ -209,6 +209,7 @@ runTestBuilderArgs = builder Testsuite ? do
     (testEnv, testMetricsFile) <- expr . liftIO $
         (,) <$> lookupEnv "TEST_ENV" <*> lookupEnv "METRICS_FILE"
     perfBaseline <- expr . liftIO $ lookupEnv "PERF_BASELINE_COMMIT"
+    targetWrapper <- expr . liftIO $ lookupEnv "CROSS_EMULATOR"
 
     threads     <- shakeThreads <$> expr getShakeOptions
     top         <- expr $ topDirectory
@@ -277,6 +278,7 @@ runTestBuilderArgs = builder Testsuite ? do
             , case perfBaseline of
                 Just commit | not (null commit) -> arg ("--perf-baseline=" ++ commit)
                 _ -> mempty
+            , emitWhenSet targetWrapper $ \cmd -> arg ("--target-wrapper=" ++ cmd)
             , emitWhenSet testEnv $ \env -> arg ("--test-env=" ++ env)
             , emitWhenSet testMetricsFile $ \file -> arg ("--metrics-file=" ++ file)
             , getTestArgs -- User-provided arguments from command line.


=====================================
testsuite/driver/runtests.py
=====================================
@@ -69,6 +69,7 @@ parser.add_argument("--config", action='append', help="config field")
 parser.add_argument("--rootdir", action='append', help="root of tree containing tests (default: .)")
 parser.add_argument("--metrics-file", help="file in which to save (append) the performance test metrics. If omitted, git notes will be used.")
 parser.add_argument("--summary-file", help="file in which to save the (human-readable) summary")
+parser.add_argument("--target-wrapper", help="wrapper executable to use when executing binaries compiled for the target")
 parser.add_argument("--no-print-summary", action="store_true", help="should we print the summary?")
 parser.add_argument("--only", action="append", help="just this test (can be give multiple --only= flags)")
 parser.add_argument("--way", action="append", help="just this way")
@@ -116,6 +117,7 @@ hasMetricsFile = config.metrics_file is not None
 config.summary_file = args.summary_file
 config.no_print_summary = args.no_print_summary
 config.baseline_commit = args.perf_baseline
+config.target_wrapper = args.target_wrapper
 
 if args.top:
     config.top = args.top


=====================================
testsuite/driver/testglobals.py
=====================================
@@ -176,6 +176,11 @@ class TestConfig:
         self.threads = 1
         self.use_threads = False
 
+        # An optional executable used to wrap target code execution
+        # When set tests which aren't marked with TestConfig.cross_okay
+        # are skipped.
+        self.target_wrapper = None
+
         # tests which should be considered to be broken during this testsuite
         # run.
         self.broken_tests = set() # type: Set[TestName]
@@ -446,6 +451,12 @@ class TestOptions:
        # Should we copy the files of symlink the files for the test?
        self.copy_files = False
 
+       # Should the test be run in a cross-compiled tree?
+       #   None:  infer from test function
+       #   True:  run when --target-wrapper is set
+       #   False: do not run in cross-compiled trees
+       self.cross_okay = None # type: Optional[bool]
+
        # The extra hadrian dependencies we need for this particular test
        self.hadrian_deps = set(["test:ghc"]) # type: Set[str]
 


=====================================
testsuite/driver/testlib.py
=====================================
@@ -98,6 +98,10 @@ def setLocalTestOpts(opts: TestOptions) -> None:
     global testopts_local
     testopts_local.x = opts
 
+def isCross() -> bool:
+    """ Are we testing a cross-compiler? """
+    return config.target_wrapper is not None
+
 def isCompilerStatsTest() -> bool:
     opts = getTestOpts()
     return bool(opts.is_compiler_stats_test)
@@ -248,9 +252,19 @@ def req_dynamic_hs( name, opts ):
         opts.expect = 'fail'
 
 def req_interp( name, opts ):
-    if not config.have_interp:
+    '''
+    Require GHCi support
+    '''
+    if not config.have_interp or isCross():
         opts.expect = 'fail'
 
+def req_plugins( name, opts ):
+    '''
+    Require plugins support
+    '''
+    # Currently no different from req_interp
+    req_interp(name, opts)
+
 def req_rts_linker( name, opts ):
     if not config.have_RTS_linker:
         opts.expect = 'fail'
@@ -1068,14 +1082,21 @@ def test_common_work(watcher: testutil.Watcher,
                 all_ways = [WayName('ghci')]
             else:
                 all_ways = []
+            if isCross() and config.cross_okay is None:
+                opts.cross_okay = False
         elif func in [makefile_test, run_command]:
             # makefile tests aren't necessarily runtime or compile-time
             # specific. Assume we can run them in all ways. See #16042 for what
             # happened previously.
             all_ways = config.compile_ways + config.run_ways
+            if isCross() and config.cross_okay is None:
+                opts.cross_okay = False
         else:
             all_ways = [WayName('normal')]
 
+        if isCross() and opts.cross_okay is False:
+            opts.skip = True
+
         # A test itself can request extra ways by setting opts.extra_ways
         all_ways = list(OrderedDict.fromkeys(all_ways + [way for way in opts.extra_ways if way not in all_ways]))
 
@@ -1791,7 +1812,10 @@ def simple_run(name: TestName, way: WayName, prog: str, extra_run_opts: str) ->
         stats_args = ''
 
     # Put extra_run_opts last: extra_run_opts('+RTS foo') should work.
-    cmd = ' '.join([prog, stats_args, my_rts_flags, extra_run_opts])
+    args = [prog, stats_args, my_rts_flags, extra_run_opts]
+    if config.target_wrapper is not None:
+        args = [config.target_wrapper] + args
+    cmd = ' '.join(args)
 
     if opts.cmd_wrapper is not None:
         cmd = opts.cmd_wrapper(cmd)
@@ -2293,21 +2317,25 @@ def normalise_errmsg(s: str) -> str:
     s = normalise_callstacks(s)
     s = normalise_type_reps(s)
 
+    # normalise slashes, minimise Windows/Unix filename differences
+    s = re.sub('\\\\', '/', s)
+
+    # Normalize the name of the GHC executable. Specifically,
+    # this catches the cases that:
+    #
+    # * In cross-compilers ghc's executable name may include
+    #   a target prefix (e.g. `aarch64-linux-gnu-ghc`)
+    # * On Windows the executable name may mention the
+    #   versioned name (e.g. `ghc-9.2.1`)
+    s = re.sub(Path(config.compiler).name + ':', 'ghc:', s)
+
     # If somefile ends in ".exe" or ".exe:", zap ".exe" (for Windows)
     #    the colon is there because it appears in error messages; this
     #    hacky solution is used in place of more sophisticated filename
     #    mangling
     s = re.sub('([^\\s])\\.exe', '\\1', s)
 
-    # normalise slashes, minimise Windows/Unix filename differences
-    s = re.sub('\\\\', '/', s)
-
-    # The inplace ghc's are called ghc-stage[123] to avoid filename
-    # collisions, so we need to normalise that to just "ghc"
-    s = re.sub('ghc-stage[123]', 'ghc', s)
-
     # On windows error messages can mention versioned executables
-    s = re.sub('ghc-[0-9.]+', 'ghc', s)
     s = re.sub('runghc-[0-9.]+', 'runghc', s)
     s = re.sub('hpc-[0-9.]+', 'hpc', s)
     s = re.sub('ghc-pkg-[0-9.]+', 'ghc-pkg', s)


=====================================
testsuite/tests/annotations/should_run/all.T
=====================================
@@ -9,18 +9,8 @@ setTestOpts(when(fast(), skip))
 test('annrun01',
      [extra_files(['Annrun01_Help.hs']),
       pre_cmd('$MAKE -s --no-print-directory config'),
-      omit_ways(['dyn'] + prof_ways)],
+      omit_ways(['dyn'] + prof_ways),
+      req_interp],
      multimod_compile_and_run,
      ['annrun01', '-package ghc ' + config.ghc_th_way_flags])
 
-""""
-Helpful things to C+P:
-
-test('', normal, compile_fail, [''])
-
-test('', normal, compile, [''])
-
-test('', [], multimod_compile_fail, ['', '-v0'])
-
-test('', [], multimod_compile, ['', '-v0'])
-"""


=====================================
testsuite/tests/codeGen/should_compile/T17904.hs
=====================================
@@ -13,8 +13,6 @@ module T17904
 import GHC.Exts ( TYPE, Int (..)  )
 import Prelude hiding (lookup)
 
-{-# ANN module ("HLint: ignore Eta reduce" :: String) #-}
-
 class Hashable a where
     hashWithSalt :: Int -> a -> Int
 


=====================================
testsuite/tests/corelint/all.T
=====================================
@@ -1,6 +1,6 @@
 
 test('T21115', normal, compile_fail, [''])
-test('T21115b', normal, compile_fail, ['-dsuppress-uniques -dsuppress-all'])
+test('T21115b', req_th, compile_fail, ['-dsuppress-uniques -dsuppress-all'])
 test('T21152', normal, compile, ['-g3'])
 
 ## Tests which use the GHC API.


=====================================
testsuite/tests/dependent/should_compile/all.T
=====================================
@@ -35,16 +35,7 @@ test('T13538', normal, compile, [''])
 test('T12176', normal, compile, [''])
 test('T14038', normal, compile, [''])
 test('T12742', normal, compile, [''])
-# we omit profasm because it doesn't bring much to the table but
-# introduces its share of complexity, as the test as it is fails with
-# profasm:
-# T13910.hs:6:5: fatal:
-#     Cannot load -prof objects when GHC is built with -dynamic
-#     To fix this, either:
-#       (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', req_th, compile, [''])
 test('T13938', [req_th, extra_files(['T13938a.hs'])], makefile_test, ['T13938'])
 test('T14556', normal, compile, [''])
 test('T14720', normal, compile, [''])


=====================================
testsuite/tests/driver/multipleHomeUnits/all.T
=====================================
@@ -2,7 +2,7 @@ test('multipleHomeUnits_single1', [extra_files([ 'a/', 'unitA'])], multiunit_com
 test('multipleHomeUnits_single2', [extra_files([ 'b/', 'unitB'])], multiunit_compile, [['unitB'], '-fhide-source-paths'])
 test('multipleHomeUnits_single3', [extra_files([ 'c/', 'unitC'])], multiunit_compile, [['unitC'], '-fhide-source-paths'])
 test('multipleHomeUnits_single4', [extra_files([ 'd/', 'unitD'])], multiunit_compile, [['unitD'], '-fhide-source-paths'])
-test('multipleHomeUnits_single5', [extra_files([ 'th/', 'unitTH'])], multiunit_compile, [['unitTH'], '-fhide-source-paths'])
+test('multipleHomeUnits_single5', [req_th, extra_files([ 'th/', 'unitTH'])], multiunit_compile, [['unitTH'], '-fhide-source-paths'])
 test('multipleHomeUnits_cpp', [extra_files([ 'cpp-includes/', 'unitCPPIncludes'])], multiunit_compile, [['unitCPPIncludes'], '-fhide-source-paths'])
 test('multipleHomeUnits_cfile', [extra_files([ 'c-file/', 'unitCFile'])], multiunit_compile, [['unitCFile'], '-fhide-source-paths'])
 test('multipleHomeUnits_callstack', [extra_files([ 'callstack/', 'unitCallstack'])], makefile_test, [])


=====================================
testsuite/tests/driver/multipleHomeUnits/th-deps/all.T
=====================================
@@ -1 +1 @@
-test('multipleHomeUnits_th-deps', [extra_files([ 'p1/', 'p2', 'q', 'unitP1', 'unitP2', 'unitQ'])], multiunit_compile, [['unitP1', 'unitP2', 'unitQ'], '-fhide-source-paths'])
+test('multipleHomeUnits_th-deps', [req_th, extra_files([ 'p1/', 'p2', 'q', 'unitP1', 'unitP2', 'unitQ'])], multiunit_compile, [['unitP1', 'unitP2', 'unitQ'], '-fhide-source-paths'])


=====================================
testsuite/tests/ffi/should_compile/all.T
=====================================
@@ -33,14 +33,8 @@ test('cc016', normal, compile, [''])
 test('T10460', normal, compile, [''])
 test('T11983', [omit_ways(['ghci'])], compile, ['T11983.c'])
 test('T14125', normal, compile, [''])
-test(
-    'cc017',
-    # 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'
-        + (' -optcxx=-stdlib=libc++' if opsys('darwin') else '')
-    ],
-)
+test('cc017', req_th, compile,
+     [ '-optc=-DC -optcxx=-DCXX -optcxx=-std=c++11'
+       + (' -optcxx=-stdlib=libc++' if opsys('darwin') else '')
+     ])
 test('T15531', normal, compile, ['-Wall'])


=====================================
testsuite/tests/linear/should_compile/all.T
=====================================
@@ -30,10 +30,10 @@ test('LinearEmptyCase', normal, compile, [''])
 test('Tunboxer', normal, compile, [''])
 test('MultConstructor', normal, compile, [''])
 test('LinearLetRec', expect_broken(18694), compile, ['-O -dlinear-core-lint'])
-test('LinearTH1', normal, compile, [''])
-test('LinearTH2', normal, compile, [''])
-test('LinearTH3', normal, compile, [''])
-test('LinearTH4', normal, compile, [''])
+test('LinearTH1', req_th, compile, [''])
+test('LinearTH2', req_th, compile, [''])
+test('LinearTH3', req_th, compile, [''])
+test('LinearTH4', req_th, compile, [''])
 test('LinearHole', normal, compile, [''])
 test('LinearDataConSections', normal, compile, [''])
 test('T18731', normal, compile, [''])


=====================================
testsuite/tests/overloadedrecflds/ghci/all.T
=====================================
@@ -1,3 +1,5 @@
+setTestOpts([req_interp])
+
 test('duplicaterecfldsghci01', combined_output, ghci_script, ['duplicaterecfldsghci01.script'])
 test('overloadedlabelsghci01', combined_output, ghci_script, ['overloadedlabelsghci01.script'])
 test('T13438', [expect_broken(13438), combined_output], ghci_script, ['T13438.script'])


=====================================
testsuite/tests/overloadedrecflds/should_compile/all.T
=====================================
@@ -3,7 +3,7 @@ test('T12609', normal, compile, [''])
 test('T16597', [], multimod_compile, ['T16597', '-v0'])
 test('T17176', normal, compile, [''])
 test('DRFPatSynExport', [], makefile_test, ['DRFPatSynExport'])
-test('NoFieldSelectors', normal, compile, [''])
+test('NoFieldSelectors', req_interp, compile, [''])
 test('NFSDRF', normal, compile, [''])
 test('NFSImport', [extra_files(['NFSExport.hs'])], multimod_compile, ['NFSImport NFSExport', '-v0'])
 test('T18999_NoFieldSelectors', normal, compile, [''])


=====================================
testsuite/tests/partial-sigs/should_compile/all.T
=====================================
@@ -40,16 +40,7 @@ test('PatBind', normal, compile, ['-ddump-types -fno-warn-partial-type-signature
 # Bug
 test('PatBind2', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures'])
 test('PatternSig', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures'])
-# we omit profasm because it doesn't bring much to the table but
-# introduces its share of complexity, as the test as it is fails with
-# profasm:
-# PatternSplice.hs:6:5: fatal:
-#     Cannot load -prof objects when GHC is built with -dynamic
-#     To fix this, either:
-#       (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('PatternSplice', [req_interp, omit_ways(['profasm'])], compile, ['-fno-warn-partial-type-signatures'])
+test('PatternSplice', [req_th], compile, ['-fno-warn-partial-type-signatures'])
 test('Recursive', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures'])
 test('ScopedNamedWildcards', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures'])
 test('ScopedNamedWildcardsGood', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures'])


=====================================
testsuite/tests/patsyn/should_run/all.T
=====================================
@@ -14,16 +14,7 @@ test('records-run', normal, compile_and_run, [''])
 test('ghci', just_ghci, ghci_script, ['ghci.script'])
 test('T11985', just_ghci, ghci_script, ['T11985.script'])
 test('T11224', normal, compile_and_run, ['-Wincomplete-patterns -Woverlapping-patterns'])
-# we omit profasm/profthreaded because it doesn't bring much to the table but
-# introduces its share of complexity, as the test as it is fails with
-# profasm:
-# T13688.hs:6:13: fatal:
-#     Cannot load -prof objects when GHC is built with -dynamic
-#     To fix this, either:
-#       (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('T13688', omit_ways(['profasm', 'profthreaded']), multimod_compile_and_run, ['T13688', '-v0'])
+test('T13688', req_th, multimod_compile_and_run, ['T13688', '-v0'])
 # Requires UnboxedSums, which GHCi does not support.
 test('T14228', omit_ways(['ghci']), compile_and_run, [''])
 test('records-poly-update', normal, compile_and_run, [''])


=====================================
testsuite/tests/plugins/all.T
=====================================
@@ -1,5 +1,5 @@
 setTestOpts([
-    req_interp,
+    req_plugins,
     # The implementation of ghc-pkg doesn't seem to be multi-concurrent process
     # safe on windows. These tests which mutate the package db need to be run
     # sequentially until this is fixed.  This likely means that #13194 isn't fully
@@ -213,7 +213,6 @@ test('test-hole-plugin',
      [extra_files(['hole-fit-plugin/']),
       pre_cmd('$MAKE -s --no-print-directory -C hole-fit-plugin package.hole-fit-plugin TOP={top}'),
       extra_hc_opts('-package-db hole-fit-plugin/pkg.hole-fit-plugin/local.package.conf '+ config.plugin_way_flags),
-      req_th
       ],
      compile, ['-fdefer-typed-holes'])
 test('test-hooks-plugin',
@@ -222,7 +221,6 @@ test('test-hooks-plugin',
       # The following doesn't seem to work, even though it
       # seems identical to the previous test...?
       # extra_hc_opts('-package-db hooks-plugin/pkg.hooks-plugin/local.package.conf '+ config.plugin_way_flags),
-      req_th
       ],
      compile_and_run,
      ['-package-db hooks-plugin/pkg.hooks-plugin/local.package.conf '+ config.plugin_way_flags])


=====================================
testsuite/tests/rts/all.T
=====================================
@@ -270,8 +270,8 @@ test('ffishutdown', [ignore_stderr, only_ways(['threaded1','threaded2'])],
 # Times out in ghci way.
 # Also times out on x86_64-linux from time to time.
 test('T7919', [ when(fast(), skip)
-              , omit_ways(['ghci'] + prof_ways)
               , when(platform('x86_64-unknown-linux'), fragile(22283))
+              , req_th
               ]
               , compile_and_run, [config.ghc_th_way_flags])
 


=====================================
testsuite/tests/saks/should_compile/all.T
=====================================
@@ -43,6 +43,6 @@ test('T16756a', 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('saks027', omit_ways(['profasm']), compile, ['-v0 -ddump-splices -dsuppress-uniques'])
-test('saks028', omit_ways(['profasm']), compile, [''])
+test('saks027', req_th, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
+test('saks028', req_th, compile, [''])
 test('T17164', omit_ways(['profasm']), compile, ['-v0 -ddump-splices -dsuppress-uniques'])


=====================================
testsuite/tests/simplCore/should_compile/all.T
=====================================
@@ -156,16 +156,7 @@ test('T7702',
      compile,
      ['-v0 -package-db T7702plugin/pkg.T7702/local.package.conf -fplugin T7702Plugin -package T7702plugin ' + config.plugin_way_flags])
 
-# we omit profasm because it doesn't bring much to the table but
-# introduces its share of complexity, as the test as it is fails with
-# profasm:
-# T7944.hs:7:1: fatal:
-#     Cannot load -prof objects when GHC is built with -dynamic
-#     To fix this, either:
-#       (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('T7944', omit_ways(['profasm']), compile, ['-O2'])
+test('T7944', req_th, compile, ['-O2'])
 
 test('T8196', normal, compile, [''])
 test('T8221b', normal, compile, [''])


=====================================
testsuite/tests/tcplugins/all.T
=====================================
@@ -1,3 +1,4 @@
+setTestOpts([req_plugins])
 
 # See NullaryPlugin.hs for a description of this plugin.
 test('TcPlugin_Nullary'


=====================================
testsuite/tests/th/should_compile/T13949/all.T
=====================================
@@ -1,12 +1,2 @@
-# we omit profasm because it doesn't bring much to the table but
-# introduces its share of complexity, as the test as it is fails with
-# profasm:
-# ASCII.hs:1:1: fatal:
-#     Cannot load -prof objects when GHC is built with -dynamic
-#     To fix this, either:
-#       (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('T13949', [extra_files(['ASCII.hs', 'PatternGenerator.hs', 'These.hs', 'Tree.hs']), req_interp,
-	        omit_ways(['profasm'])],
+test('T13949', [extra_files(['ASCII.hs', 'PatternGenerator.hs', 'These.hs', 'Tree.hs']), req_th],
      multimod_compile, ['ASCII PatternGenerator These Tree', '-fno-code -v0'])


=====================================
testsuite/tests/th/should_compile/T8025/all.T
=====================================
@@ -1,9 +1,2 @@
-# we omit profasm because it fails with:
-# B.hs:5:5: fatal:
-#     Cannot load -prof objects when GHC is built with -dynamic
-#     To fix this, either:
-#       (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('T8025', [extra_files(['A.hs', 'B.hs']), omit_ways(['profasm']), req_interp],
+test('T8025', [extra_files(['A.hs', 'B.hs']), req_th],
 	      multimod_compile, ['A B', '-fno-code -v0'])


=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -625,14 +625,7 @@ test('T14811', normal, compile, [''])
 test('T14934', [extra_files(['T14934.hs', 'T14934a.hs'])], makefile_test, [])
 test('T13643', normal, compile, [''])
 test('SplitWD', normal, compile, [''])
-# we omit profasm because it fails with:
-# T14441.hs:1:1: fatal:
-#     Cannot load -prof objects when GHC is built with -dynamic
-#     To fix this, either:
-#       (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('T14441', omit_ways(['profasm']), compile, [''])
+test('T14441', req_th, compile, [''])
 test('T15079', normal, compile, [''])
 test('T15050', normal, compile, [''])
 test('T14735', normal, compile, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6d90a00ec452cd2e367074f7f0b4796253d580a6...0a03d9d23abdb4399569f8804083e54e5d77b44a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6d90a00ec452cd2e367074f7f0b4796253d580a6...0a03d9d23abdb4399569f8804083e54e5d77b44a
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/20221018/14a35c41/attachment-0001.html>


More information about the ghc-commits mailing list