summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorKrzysztof Gogolewski <krzysztof.gogolewski@tweag.io>2022-03-18 20:33:44 +0100
committerKrzysztof Gogolewski <krzysztof.gogolewski@tweag.io>2022-03-30 21:19:41 +0200
commit8bad5bf2b2936135dacee1385acbf66e95208e65 (patch)
treea5db89c6b8c4a4bda22144af7f90c956b54ca70d
parent21894a6318e0daffa0e34041855c3c73ad1f5b6f (diff)
downloadhaskell-wip/minor-cleanup.tar.gz
Minor cleanupwip/minor-cleanup
- Remove unused functions exprToCoercion_maybe, applyTypeToArg, typeMonoPrimRep_maybe, runtimeRepMonoPrimRep_maybe. - Replace orValid with a simpler check - Use splitAtList in applyTysX - Remove calls to extra_clean in the testsuite; it does not do anything. Metric Decrease: T18223
-rw-r--r--compiler/GHC/Core.hs14
-rw-r--r--compiler/GHC/Core/Opt/WorkWrap/Utils.hs2
-rw-r--r--compiler/GHC/Core/Type.hs8
-rw-r--r--compiler/GHC/Core/Utils.hs8
-rw-r--r--compiler/GHC/Tc/Deriv/Utils.hs4
-rw-r--r--compiler/GHC/Types/RepType.hs24
-rw-r--r--compiler/GHC/Utils/Error.hs6
-rw-r--r--testsuite/tests/cmm/should_run/all.T3
-rw-r--r--testsuite/tests/concurrent/should_run/all.T3
-rw-r--r--testsuite/tests/driver/T8602/T8602.T1
-rw-r--r--testsuite/tests/ffi/should_run/all.T7
-rw-r--r--testsuite/tests/ghci/linking/all.T6
-rw-r--r--testsuite/tests/hpc/all.T3
-rw-r--r--testsuite/tests/indexed-types/should_compile/all.T2
-rw-r--r--testsuite/tests/perf/compiler/all.T6
-rw-r--r--testsuite/tests/perf/should_run/all.T9
-rw-r--r--testsuite/tests/perf/space_leaks/all.T3
-rw-r--r--testsuite/tests/programs/barton-mangler-bug/test.T7
-rw-r--r--testsuite/tests/programs/joao-circular/test.T6
-rw-r--r--testsuite/tests/quasiquotation/T4491/test.T1
-rw-r--r--testsuite/tests/quasiquotation/qq005/test.T1
-rw-r--r--testsuite/tests/rts/T1791/all.T2
-rw-r--r--testsuite/tests/rts/all.T3
-rw-r--r--testsuite/tests/rts/linker/all.T5
-rw-r--r--testsuite/tests/simplCore/should_compile/all.T2
25 files changed, 28 insertions, 108 deletions
diff --git a/compiler/GHC/Core.hs b/compiler/GHC/Core.hs
index a3dedcc0fb..c5d0a86d14 100644
--- a/compiler/GHC/Core.hs
+++ b/compiler/GHC/Core.hs
@@ -46,8 +46,8 @@ module GHC.Core (
collectNBinders,
collectArgs, stripNArgs, collectArgsTicks, flattenBinds,
- exprToType, exprToCoercion_maybe,
- applyTypeToArg, wrapLamBody,
+ exprToType,
+ wrapLamBody,
isValArg, isTypeArg, isCoArg, isTyCoArg, valArgCount, valBndrCount,
isRuntimeArg, isRuntimeVar,
@@ -1904,22 +1904,12 @@ These are defined here to avoid a module loop between GHC.Core.Utils and GHC.Cor
-}
-applyTypeToArg :: Type -> CoreExpr -> Type
--- ^ Determines the type resulting from applying an expression with given type
--- to a given argument expression
-applyTypeToArg fun_ty arg = piResultTy fun_ty (exprToType arg)
-
-- | If the expression is a 'Type', converts. Otherwise,
-- panics. NB: This does /not/ convert 'Coercion' to 'CoercionTy'.
exprToType :: CoreExpr -> Type
exprToType (Type ty) = ty
exprToType _bad = pprPanic "exprToType" empty
--- | If the expression is a 'Coercion', converts.
-exprToCoercion_maybe :: CoreExpr -> Maybe Coercion
-exprToCoercion_maybe (Coercion co) = Just co
-exprToCoercion_maybe _ = Nothing
-
{-
************************************************************************
* *
diff --git a/compiler/GHC/Core/Opt/WorkWrap/Utils.hs b/compiler/GHC/Core/Opt/WorkWrap/Utils.hs
index 6bb751d803..63ac670418 100644
--- a/compiler/GHC/Core/Opt/WorkWrap/Utils.hs
+++ b/compiler/GHC/Core/Opt/WorkWrap/Utils.hs
@@ -1131,7 +1131,7 @@ Needless to say, there are some wrinkles:
of the form @TYPE rep@ where @rep@ is not (and doesn't contain) a variable.
Why? Because if we don't know its representation (e.g. size in memory,
register class), we don't know what or how much rubbish to emit in codegen.
- 'typeMonoPrimRep_maybe' returns 'Nothing' in this case and we simply fall
+ 'mkLitRubbish' returns 'Nothing' in this case and we simply fall
back to passing the original parameter to the worker.
Note that currently this case should not occur, because binders always
diff --git a/compiler/GHC/Core/Type.hs b/compiler/GHC/Core/Type.hs
index 6adf7c7a34..bc864c301f 100644
--- a/compiler/GHC/Core/Type.hs
+++ b/compiler/GHC/Core/Type.hs
@@ -1428,13 +1428,13 @@ applyTysX :: [TyVar] -> Type -> [Type] -> Type
-- applyTyxX beta-reduces (/\tvs. body_ty) arg_tys
-- Assumes that (/\tvs. body_ty) is closed
applyTysX tvs body_ty arg_tys
- = assertPpr (arg_tys `lengthAtLeast` n_tvs) pp_stuff $
+ = assertPpr (tvs `leLength` arg_tys) pp_stuff $
assertPpr (tyCoVarsOfType body_ty `subVarSet` mkVarSet tvs) pp_stuff $
- mkAppTys (substTyWith tvs (take n_tvs arg_tys) body_ty)
- (drop n_tvs arg_tys)
+ mkAppTys (substTyWith tvs arg_tys_prefix body_ty)
+ arg_tys_rest
where
pp_stuff = vcat [ppr tvs, ppr body_ty, ppr arg_tys]
- n_tvs = length tvs
+ (arg_tys_prefix, arg_tys_rest) = splitAtList tvs arg_tys
diff --git a/compiler/GHC/Core/Utils.hs b/compiler/GHC/Core/Utils.hs
index 5100f958e6..90f8f3f032 100644
--- a/compiler/GHC/Core/Utils.hs
+++ b/compiler/GHC/Core/Utils.hs
@@ -41,8 +41,8 @@ module GHC.Core.Utils (
tryEtaReduce, canEtaReduceToArity,
-- * Manipulating data constructors and types
- exprToType, exprToCoercion_maybe,
- applyTypeToArgs, applyTypeToArg,
+ exprToType,
+ applyTypeToArgs,
dataConRepInstPat, dataConRepFSInstPat,
isEmptyTy, normSplitTyConApp_maybe,
@@ -232,9 +232,9 @@ Various possibilities suggest themselves:
Note that there might be existentially quantified coercion variables, too.
-}
--- Not defined with applyTypeToArg because you can't print from GHC.Core.
applyTypeToArgs :: HasDebugCallStack => SDoc -> Type -> [CoreExpr] -> Type
--- ^ A more efficient version of 'applyTypeToArg' when we have several arguments.
+-- ^ Determines the type resulting from applying an expression with given type
+--- to given argument expressions.
-- The first argument is just for debugging, and gives some context
applyTypeToArgs pp_e op_ty args
= go op_ty args
diff --git a/compiler/GHC/Tc/Deriv/Utils.hs b/compiler/GHC/Tc/Deriv/Utils.hs
index aa89f94c4b..f28ad0e8f4 100644
--- a/compiler/GHC/Tc/Deriv/Utils.hs
+++ b/compiler/GHC/Tc/Deriv/Utils.hs
@@ -989,8 +989,8 @@ cond_stdOK deriv_ctxt permissive dflags
InferContext wildcard
| null data_cons -- 1.
, not permissive
- -> checkFlag LangExt.EmptyDataDeriving dflags dit `orValid`
- NotValid (no_cons_why rep_tc)
+ , not (xopt LangExt.EmptyDataDeriving dflags)
+ -> NotValid (no_cons_why rep_tc)
| not (null con_whys)
-> NotValid $ DerivErrBadConstructor (Just $ has_wildcard wildcard) con_whys
| otherwise
diff --git a/compiler/GHC/Types/RepType.hs b/compiler/GHC/Types/RepType.hs
index 41223c625f..b565bd7400 100644
--- a/compiler/GHC/Types/RepType.hs
+++ b/compiler/GHC/Types/RepType.hs
@@ -11,7 +11,7 @@ module GHC.Types.RepType
isZeroBitTy,
-- * Type representation for the code generator
- typePrimRep, typePrimRep1, typeMonoPrimRep_maybe,
+ typePrimRep, typePrimRep1,
runtimeRepPrimRep, typePrimRepArgs,
PrimRep(..), primRepToType,
countFunRepArgs, countConRepArgs, dataConRuntimeRepStrictness,
@@ -32,7 +32,7 @@ import GHC.Core.TyCon
import GHC.Core.TyCon.RecWalk
import GHC.Core.TyCo.Rep
import GHC.Core.Type
-import {-# SOURCE #-} GHC.Builtin.Types ( anyTypeOfKind, runtimeRepTy
+import {-# SOURCE #-} GHC.Builtin.Types ( anyTypeOfKind
, vecRepDataConTyCon
, liftedRepTy, unliftedRepTy, zeroBitRepTy
, intRepDataConTy
@@ -544,14 +544,6 @@ typePrimRep1 ty = case typePrimRep ty of
[rep] -> rep
_ -> pprPanic "typePrimRep1" (ppr ty $$ ppr (typePrimRep ty))
--- | Like 'typePrimRep', but returns 'Nothing' instead of panicking, when
---
--- * The @ty@ was not of form @TYPE rep@
--- * @rep@ was not monomorphic
---
-typeMonoPrimRep_maybe :: Type -> Maybe [PrimRep]
-typeMonoPrimRep_maybe ty = getRuntimeRep_maybe ty >>= runtimeRepMonoPrimRep_maybe
-
-- | Find the runtime representation of a 'TyCon'. Defined here to
-- avoid module loops. Returns a list of the register shapes necessary.
-- See also Note [Getting from RuntimeRep to PrimRep]
@@ -585,18 +577,6 @@ kindPrimRep doc ki
= pprPanic "kindPrimRep" (ppr ki $$ doc)
-- | Take a type of kind RuntimeRep and extract the list of 'PrimRep' that
--- it encodes if it's a monomorphic rep. Otherwise returns 'Nothing'.
--- See also Note [Getting from RuntimeRep to PrimRep]
-runtimeRepMonoPrimRep_maybe :: HasDebugCallStack => Type -> Maybe [PrimRep]
-runtimeRepMonoPrimRep_maybe rr_ty
- | Just (rr_dc, args) <- splitTyConApp_maybe rr_ty
- , assertPpr (runtimeRepTy `eqType` typeKind rr_ty) (ppr rr_ty) True
- , RuntimeRep fun <- tyConRuntimeRepInfo rr_dc
- = Just (fun args)
- | otherwise
- = Nothing -- not mono rep
-
--- | Take a type of kind RuntimeRep and extract the list of 'PrimRep' that
-- it encodes. See also Note [Getting from RuntimeRep to PrimRep]
-- The [PrimRep] is the final runtime representation /after/ unarisation
runtimeRepPrimRep :: HasDebugCallStack => SDoc -> Type -> [PrimRep]
diff --git a/compiler/GHC/Utils/Error.hs b/compiler/GHC/Utils/Error.hs
index 7d2eb34c3b..db8107a65f 100644
--- a/compiler/GHC/Utils/Error.hs
+++ b/compiler/GHC/Utils/Error.hs
@@ -11,7 +11,7 @@
module GHC.Utils.Error (
-- * Basic types
- Validity'(..), Validity, andValid, allValid, getInvalids, orValid,
+ Validity'(..), Validity, andValid, allValid, getInvalids,
Severity(..),
-- * Messages
@@ -212,10 +212,6 @@ allValid (v : vs) = v `andValid` allValid vs
getInvalids :: [Validity' a] -> [a]
getInvalids vs = [d | NotValid d <- vs]
-orValid :: Validity' a -> Validity' a -> Validity' a
-orValid IsValid _ = IsValid
-orValid _ v = v
-
-- -----------------------------------------------------------------------------
-- Collecting up messages for later ordering and printing.
diff --git a/testsuite/tests/cmm/should_run/all.T b/testsuite/tests/cmm/should_run/all.T
index cd7f5d094a..bb667a93de 100644
--- a/testsuite/tests/cmm/should_run/all.T
+++ b/testsuite/tests/cmm/should_run/all.T
@@ -6,7 +6,6 @@ test('HooplPostorder',
test('cmp64',
[ extra_run_opts('"' + config.libdir + '"')
, omit_ways(['ghci'])
- , extra_clean('cmp64_cmm.o')
],
multi_compile_and_run,
['cmp64', [('cmp64_cmm.cmm', '')], '-O'])
@@ -14,7 +13,6 @@ test('cmp64',
# test('T17516',
# [ collect_compiler_stats('bytes allocated', 5),
-# extra_clean(['T17516A.hi', 'T17516A.o'])
# ],
# multimod_compile,
# ['T17516', '-O -v0'])
@@ -22,7 +20,6 @@ test('cmp64',
test('ByteSwitch',
[ extra_run_opts('"' + config.libdir + '"')
, omit_ways(['ghci'])
- , extra_clean('ByteSwitch_cmm.o')
],
multi_compile_and_run,
['ByteSwitch', [('ByteSwitch_cmm.cmm', '')], ''])
diff --git a/testsuite/tests/concurrent/should_run/all.T b/testsuite/tests/concurrent/should_run/all.T
index f12adf4269..6f015b1df3 100644
--- a/testsuite/tests/concurrent/should_run/all.T
+++ b/testsuite/tests/concurrent/should_run/all.T
@@ -228,7 +228,7 @@ test('hs_try_putmvar001',
[
when(opsys('mingw32'),skip), # uses pthread APIs in the C code
only_ways(['threaded1', 'threaded2', 'nonmoving_thr']),
- extra_clean(['hs_try_putmvar001_c.o'])],
+ ],
compile_and_run,
['hs_try_putmvar001_c.c'])
@@ -246,7 +246,6 @@ test('hs_try_putmvar003',
when(opsys('mingw32'),skip), # uses pthread APIs in the C code
pre_cmd('$MAKE -s --no-print-directory hs_try_putmvar003_setup'),
only_ways(['threaded1', 'threaded2', 'nonmoving_thr']),
- extra_clean(['hs_try_putmvar003_c.o']),
extra_run_opts('1 16 32 100'),
fragile_for(16361, ['threaded1'])
],
diff --git a/testsuite/tests/driver/T8602/T8602.T b/testsuite/tests/driver/T8602/T8602.T
index 007b8ddc42..67e7b7e50e 100644
--- a/testsuite/tests/driver/T8602/T8602.T
+++ b/testsuite/tests/driver/T8602/T8602.T
@@ -1,6 +1,5 @@
test('T8602',
[extra_files(['A.hs']),
- extra_clean(['t8602.sh']),
# Windows runs the preprocessor using runInteractiveProcess and can't
# properly run the generated shell script as a result, since it can't
# recognize e.g. a shebang or anything.
diff --git a/testsuite/tests/ffi/should_run/all.T b/testsuite/tests/ffi/should_run/all.T
index 4784d8a4e3..14c5b34af7 100644
--- a/testsuite/tests/ffi/should_run/all.T
+++ b/testsuite/tests/ffi/should_run/all.T
@@ -9,7 +9,6 @@ test('fed001', normal, compile_and_run, [''])
# Omit GHCi for these two, as they use foreign export
test('ffi001', omit_ways(['ghci']), compile_and_run, [''])
test('ffi002', [ omit_ways(['ghci']),
- extra_clean(['ffi002_c.o']),
pre_cmd('$MAKE -s --no-print-directory ffi002_setup') ],
# The ffi002_setup hack is to ensure that we generate
# ffi002_stub.h before compiling ffi002_c.c, which
@@ -104,8 +103,7 @@ test('T1288_ghci',
test('T2276', [omit_ways(['ghci'])], compile_and_run, ['T2276_c.c'])
test('T2276_ghci', [ only_ways(['ghci']),
when(opsys('darwin'), skip), # stdcall not supported on OS X
- pre_cmd('$MAKE -s --no-print-directory T2276_ghci_setup'),
- extra_clean(['T2276_ghci_c.o']) ],
+ pre_cmd('$MAKE -s --no-print-directory T2276_ghci_setup') ],
compile_and_run, ['-fobject-code T2276_ghci_c.o'])
test('T2469', normal, compile_and_run, ['-optc-std=gnu99'])
@@ -141,7 +139,6 @@ test('T4221', [omit_ways(['ghci'])], compile_and_run, ['T4221_c.c'])
test('T5402', [ omit_ways(['ghci']),
exit_code(42),
- extra_clean(['T5402_main.o']),
# The T5402_setup hack is to ensure that we generate
# T5402_stub.h before compiling T5402_main.c, which
# needs it.
@@ -149,7 +146,6 @@ test('T5402', [ omit_ways(['ghci']),
compile_and_run, ["-no-hs-main T5402_main.c"])
test('T5594', [ omit_ways(['ghci']),
- extra_clean(['T5594_c.o']),
pre_cmd('$MAKE -s --no-print-directory T5594_setup') ],
# The T5594_setup hack is to ensure that we generate
# T5594_stub.h before compiling T5594_c.c, which
@@ -180,7 +176,6 @@ test('T8083', [omit_ways(['ghci'])], compile_and_run, ['T8083_c.c'])
test('T9274', [omit_ways(['ghci'])], compile_and_run, [''])
test('ffi023', [ omit_ways(['ghci']),
- extra_clean(['ffi023_c.o']),
extra_run_opts('1000 4'),
pre_cmd('$MAKE -s --no-print-directory ffi023_setup') ],
# The ffi023_setup hack is to ensure that we generate
diff --git a/testsuite/tests/ghci/linking/all.T b/testsuite/tests/ghci/linking/all.T
index 574ff9308c..40d79cbc09 100644
--- a/testsuite/tests/ghci/linking/all.T
+++ b/testsuite/tests/ghci/linking/all.T
@@ -1,8 +1,7 @@
test('ghcilink001',
[extra_files(['TestLink.hs', 'f.c']),
when(ghc_dynamic(), expect_fail), # dynamic ghci can't load '.a's
- unless(doing_ghci, skip),
- extra_clean(['dir001/*','dir001'])],
+ unless(doing_ghci, skip)],
makefile_test, ['ghcilink001'])
test('ghcilink002', [extra_files(['TestLink.hs', 'f.c']),
@@ -62,8 +61,7 @@ test('T11531',
test('T14708',
[extra_files(['T14708.hs', 'add.c']),
unless(doing_ghci, skip),
- unless(ghc_dynamic(), skip),
- extra_clean(['T14708scratch/*', 'T14708'])],
+ unless(ghc_dynamic(), skip)],
makefile_test, ['T14708'])
test('T15729',
diff --git a/testsuite/tests/hpc/all.T b/testsuite/tests/hpc/all.T
index 6744daa92f..2e2e7710a9 100644
--- a/testsuite/tests/hpc/all.T
+++ b/testsuite/tests/hpc/all.T
@@ -17,8 +17,7 @@ def T2991(cmd):
# The .mix file for the literate module should have non-zero entries.
# The `grep` should exit with exit code 0.
return(cmd + " && grep -q cover_me .hpc/T2991LiterateModule.mix")
-test('T2991', [cmd_wrapper(T2991), extra_clean(['T2991LiterateModule.hi',
- 'T2991LiterateModule.o'])],
+test('T2991', [cmd_wrapper(T2991)],
# Run with 'ghc --main'. Do not list other modules explicitly.
multimod_compile_and_run, ['T2991', ''])
diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T
index 39f9b49b4e..3549a37f70 100644
--- a/testsuite/tests/indexed-types/should_compile/all.T
+++ b/testsuite/tests/indexed-types/should_compile/all.T
@@ -127,8 +127,6 @@ test('T4160', normal, compile, [''])
test('IndTypesPerf',
[ # expect_broken(5224),
# unbroken temporarily: #5227
- extra_clean(['IndTypesPerf.o', 'IndTypesPerf.hi',
- 'IndTypesPerfMerge.o', 'IndTypesPerfMerge.hi'])
] ,
makefile_test, ['IndTypesPerf'])
diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T
index e424639e7a..5cbe3b6e51 100644
--- a/testsuite/tests/perf/compiler/all.T
+++ b/testsuite/tests/perf/compiler/all.T
@@ -217,8 +217,7 @@ test('T9961',
test('T9233',
[ only_ways(['normal']),
- collect_compiler_stats('bytes allocated', 1),
- extra_clean(['T9233a.hi', 'T9233a.o'])
+ collect_compiler_stats('bytes allocated', 1)
],
multimod_compile,
['T9233', '-v0 -O2 -fno-spec-constr'])
@@ -272,7 +271,6 @@ test('T12234',
test('T12545',
[ only_ways(['normal']),
collect_compiler_stats('bytes allocated', 10), #
- extra_clean(['T12545a.hi', 'T12545a.o'])
],
multimod_compile,
['T12545', '-v0'] )
@@ -503,7 +501,6 @@ test('T14683',
test ('T9630',
[ collect_compiler_residency(15),
collect_compiler_stats('bytes allocated', 2),
- extra_clean(['T9630a.hi', 'T9630a.o']),
],
multimod_compile,
['T9630', '-v0 -O'])
@@ -544,7 +541,6 @@ test ('T16473',
test('T17516',
[ collect_compiler_stats('bytes allocated', 5),
- extra_clean(['T17516A.hi', 'T17516A.o'])
],
multimod_compile,
['T17516', '-O -v0'])
diff --git a/testsuite/tests/perf/should_run/all.T b/testsuite/tests/perf/should_run/all.T
index ca6570f639..eb5124a155 100644
--- a/testsuite/tests/perf/should_run/all.T
+++ b/testsuite/tests/perf/should_run/all.T
@@ -87,8 +87,7 @@ test('T4321',
test('T3736', [], makefile_test, ['T3736'])
test('T3738',
- [extra_clean(['T3738a.hi', 'T3738a.o']),
- collect_runtime_residency(1),
+ [collect_runtime_residency(1),
collect_stats('bytes allocated',8),
only_ways(['normal']),
],
@@ -106,9 +105,7 @@ test('T2902', [], makefile_test, ['T2902'])
test('T149',
[ # expect_broken(149),
# working (2 Jul 2013, x86-64/Linux)
- extra_clean(['T149_A', 'T149_B',
- 'T149_A.hi', 'T149_B.hi',
- 'T149_A.o', 'T149_B.o'])],
+ ],
makefile_test, ['T149'])
test('T5113',
@@ -168,7 +165,6 @@ test('T5237',
test('T5536',
[collect_stats('bytes allocated',1),
- extra_clean(['T5536.data']),
ignore_stdout,
only_ways(['normal'])
],
@@ -207,7 +203,6 @@ test('T7436b',
test('T7797',
[collect_stats('bytes allocated',5),
- extra_clean(['T7797a.hi', 'T7797a.o']),
only_ways(['normal'])
],
compile_and_run,
diff --git a/testsuite/tests/perf/space_leaks/all.T b/testsuite/tests/perf/space_leaks/all.T
index f6638555c9..ec8f4dae97 100644
--- a/testsuite/tests/perf/space_leaks/all.T
+++ b/testsuite/tests/perf/space_leaks/all.T
@@ -22,8 +22,7 @@ test('T4334',
test('T2762',
[collect_runtime_residency(2),
- only_ways(['normal']),
- extra_clean(['T2762A.hi', 'T2762A.o'])],
+ only_ways(['normal'])],
compile_and_run, ['-O'])
test('T4018',
diff --git a/testsuite/tests/programs/barton-mangler-bug/test.T b/testsuite/tests/programs/barton-mangler-bug/test.T
index 8258106906..61020b926d 100644
--- a/testsuite/tests/programs/barton-mangler-bug/test.T
+++ b/testsuite/tests/programs/barton-mangler-bug/test.T
@@ -1,13 +1,6 @@
test('barton-mangler-bug',
[extra_files(['Basic.hs', 'Expected.hs', 'Main.hs', 'Physical.hs', 'Plot.lhs', 'PlotExample.lhs', 'TypesettingTricks.hs']),
when(fast(), skip),
- extra_clean(['Basic.hi', 'Basic.o',
- 'Expected.hi', 'Expected.o',
- 'Main.hi', 'Main.o',
- 'Physical.hi', 'Physical.o',
- 'Plot.hi', 'Plot.o',
- 'PlotExample.hi', 'PlotExample.o',
- 'TypesettingTricks.hi', 'TypesettingTricks.o']),
omit_ways(['debug']) # Fails for debug way due to annotation linting timeout
],
multimod_compile_and_run, ['Main', ''])
diff --git a/testsuite/tests/programs/joao-circular/test.T b/testsuite/tests/programs/joao-circular/test.T
index dcc3c0aa29..83f88f6560 100644
--- a/testsuite/tests/programs/joao-circular/test.T
+++ b/testsuite/tests/programs/joao-circular/test.T
@@ -2,12 +2,6 @@ test('joao-circular',
[extra_files(['Data_Lazy.hs', 'Funcs_Lexer.hs', 'Funcs_Parser_Lazy.hs', 'LrcPrelude.hs', 'Main.hs', 'Visfun_Lazy.hs', 'inp']),
when(fast(), skip),
when(doing_ghci(), extra_hc_opts('-fobject-code')),
- extra_clean(['Data_Lazy.hi', 'Data_Lazy.o',
- 'Funcs_Lexer.hi', 'Funcs_Lexer.o',
- 'Funcs_Parser_Lazy.hi', 'Funcs_Parser_Lazy.o',
- 'LrcPrelude.hi', 'LrcPrelude.o',
- 'Main.hi', 'Main.o',
- 'Visfun_Lazy.hi', 'Visfun_Lazy.o']),
# This can take a while to compile, especially with
# LLVM backend (as is necessary on, e.g., ARM)
compile_timeout_multiplier(3.0),
diff --git a/testsuite/tests/quasiquotation/T4491/test.T b/testsuite/tests/quasiquotation/T4491/test.T
index 2ef6b89edc..01e73ea7b6 100644
--- a/testsuite/tests/quasiquotation/T4491/test.T
+++ b/testsuite/tests/quasiquotation/T4491/test.T
@@ -6,6 +6,5 @@ test('T4491',
# other ways, due to the TH use, so for now we only run it
# the TH way
only_ways([config.ghc_th_way]),
- extra_clean(['A.hi', 'A.o'])
],
compile_and_run, [''])
diff --git a/testsuite/tests/quasiquotation/qq005/test.T b/testsuite/tests/quasiquotation/qq005/test.T
index 6e7ec8d14c..531a04441d 100644
--- a/testsuite/tests/quasiquotation/qq005/test.T
+++ b/testsuite/tests/quasiquotation/qq005/test.T
@@ -5,7 +5,6 @@ test('qq005',
# profiling ways, due to the TH use, so for now we just
# omit the profiling ways
omit_ways(prof_ways),
- extra_clean(['Expr.hi', 'Expr.o', 'Main.hi', 'Main.o']),
req_interp],
multimod_compile_and_run,
['Main', ''])
diff --git a/testsuite/tests/rts/T1791/all.T b/testsuite/tests/rts/T1791/all.T
index 25fb4d1124..483a2a0f58 100644
--- a/testsuite/tests/rts/T1791/all.T
+++ b/testsuite/tests/rts/T1791/all.T
@@ -1,4 +1,4 @@
test('T1791',
- [ exit_code(0), extra_clean(['T1791.hi', 'T1791']) ],
+ [ exit_code(0) ],
run_command,
['''"$MAKE" -s --no-print-directory T1791 >/dev/null && ./T1791 +RTS -M8M'''])
diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T
index e59e4c5204..c13f1aa0ea 100644
--- a/testsuite/tests/rts/all.T
+++ b/testsuite/tests/rts/all.T
@@ -250,7 +250,6 @@ test('T5250', [extra_files(['spalign.c']),
when(platform('i386-unknown-mingw32'), expect_fail),
when(platform('i386-unknown-linux'),
expect_broken_for(4211,['llvm'])),
- extra_clean(['spalign.o']),
omit_ways(['ghci']) ],
compile_and_run, ['spalign.c'])
@@ -259,7 +258,6 @@ test('T5423', [], makefile_test, ['T5423'])
test('T5993', extra_run_opts('+RTS -k8 -RTS'), compile_and_run, [''])
test('T6006', [ omit_ways(prof_ways + ['ghci']),
- extra_clean(['T6006_c.o']),
pre_cmd('$MAKE -s --no-print-directory T6006_setup') ],
# The T6006_setup hack is to ensure that we generate
# T6006_stub.h before compiling T6006_c.c, which
@@ -314,7 +312,6 @@ test('T8242', [ req_smp, only_ways(threaded_ways), ignore_stdout ],
test('T8124', [ only_ways(threaded_ways), omit_ways(['ghci']),
when(opsys('mingw32'), skip), # uses pthreads
- extra_clean(['T8124_c.o']),
pre_cmd('$MAKE -s --no-print-directory T8124_setup') ],
# The T8124_setup hack is to ensure that we generate
# T8124_stub.h before compiling T8124_c.c, which
diff --git a/testsuite/tests/rts/linker/all.T b/testsuite/tests/rts/linker/all.T
index 5191c4b0aa..e42db98922 100644
--- a/testsuite/tests/rts/linker/all.T
+++ b/testsuite/tests/rts/linker/all.T
@@ -29,8 +29,7 @@ test('T2615',
when(opsys('openbsd'), expect_broken(20869)),
pre_cmd('$MAKE -s --no-print-directory T2615-prep'),
# Add current directory to dlopen search path
- cmd_prefix('LD_LIBRARY_PATH=$LD_LIBRARY_PATH:. '),
- extra_clean(['libfoo_T2615.so', 'libfoo_T2615.o'])],
+ cmd_prefix('LD_LIBRARY_PATH=$LD_LIBRARY_PATH:. ')],
compile_and_run,
['-package ghc'])
@@ -56,8 +55,6 @@ def checkDynAsm(actual_file, normaliser):
# in a different order (but all entries within a section
# do get loaded in a deterministic order). So we test each
# separately now.
-# These should have extra_clean() arguments, but I need
-# to somehow extract out the name of DLLs to do that
test('T5435_v_asm_a',
[extra_files(['T5435.hs', 'T5435_asm.c']),
req_rts_linker,
diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T
index f0b361b3f8..13a8602bb7 100644
--- a/testsuite/tests/simplCore/should_compile/all.T
+++ b/testsuite/tests/simplCore/should_compile/all.T
@@ -74,7 +74,7 @@ test('T4201',
test('T3772',
# only_ways(['optasm']),
- extra_clean(['T3772_A.hi', 'T3772_A.o']),
+ normal,
makefile_test, ['T3772'])
test('EvalTest',