Great idea.  Please go ahead and commit.

Cheers,
        Simon

Esa Ilari Vuokko wrote:
Here's revised patch.  It fixes a bookkeepping issue and doesn't skip
few tests that previous does (it sets up TestOptions in main thread
instead of race between main thread and test-specific thread.)

Best regards,
--Esa

Esa Ilari Vuokko wrote:

Hi

I found testsuite painfully slow to run, so I came up with following solution:
Add threads-support, so that multiple tests are ran at once.  I have tested
this with make fast THREADS=3, (on Hyperthreaded machine), and got no
additional regressions.  The time (real) to run dropped from about 9min50sec
to 7min40sec.

I realize this might not be the right time to apply as release is so near.
I'd appreciate comments whetever I should resubmit after RC or Release.
Any feedback on implementation, bugs or other problems is also welcome.

The idea is to run many test() simultaneously.  This only applies within one
all.T-file, and when after all.T we wait until tests in it are ran, then move
next one.  It never spawns more than n+1 threads, but it spawns threads for
skipped tests as well.  We also get new attribute, nothreads, which will run
test alone.  If set on all.T-level, all tests are ran one after another.

The implementation is a bit crude, and there's obvious refactoring to be done,
but I wanted the initial implementation to be as straightforward as possible.

This also, I think, requires python 2.4.

Tue Aug 22 02:04:56 FLE Standard Time 2006  Esa Ilari Vuokko <[EMAIL PROTECTED]>
 * Driver: Add THREADS-support

Tue Aug 22 02:08:31 FLE Standard Time 2006  Esa Ilari Vuokko <[EMAIL PROTECTED]>
 * Fix some THREADED-caused fails

Fixes simply add nothreads-attribute.

Best regards,
--Esa



------------------------------------------------------------------------


New patches:

[Fix some THREADED-caused fails
Esa Ilari Vuokko <[EMAIL PROTECTED]>**20060821230831] {
hunk ./tests/ghc-regress/cabal/all.T 1
-setTestOpts(only_compiler_types(['ghc']))
+setTestOpts(compose(nothreads,only_compiler_types(['ghc'])))
hunk ./tests/ghc-regress/driver/all.T 1
-setTestOpts(only_compiler_types(['ghc']))
+setTestOpts(compose(nothreads, only_compiler_types(['ghc'])))
}

[Driver: Add THREADS-support
Esa Ilari Vuokko <[EMAIL PROTECTED]>**20060822213145] {
hunk ./driver/runtests.py 13
+import threading
hunk ./driver/runtests.py 20
-global testopts
-testopts = getTestOpts()
+global testopts_local
+testopts_local.x = TestOptions()
hunk ./driver/runtests.py 35
+  "threads=",           # threads to run simultaneously
hunk ./driver/runtests.py 65
+
+    if opt == '--threads':
+        config.threads = int(arg)
hunk ./driver/runtests.py 88
+        t.running_threads=0
hunk ./driver/runtests.py 90
+        t.thread_pool.acquire()
+        while t.running_threads>0:
+            t.thread_pool.wait()
+        t.thread_pool.release()
hunk ./driver/runtests.py 97
-
+ hunk ./driver/testlib.py 12
+import threading
+import thread
hunk ./driver/testlib.py 78
+ + # threads
+        self.threads = 1
hunk ./driver/testlib.py 108
+ + self.lock = threading.Lock()
+       self.thread_pool = threading.Condition(self.lock)
+       self.running_threads = 0
hunk ./driver/testlib.py 158
-
+       # should we run this test alone, ie disable THREADS
+       self.nothreads = 0
hunk ./driver/testlib.py 177
-global testopts
-testopts = TestOptions()
+global testopts_local
+testopts_local = threading.local()
hunk ./driver/testlib.py 181
-    return testopts
+    return testopts_local.x
hunk ./driver/testlib.py 183
-def resetTestOpts():
-    global testopts
-    testopts = copy.copy(thisdir_testopts)
+def setLocalTestOpts(opts):
+    global testopts_local
+    testopts_local.x=opts
hunk ./driver/testlib.py 311
+# ---
+def nothreads(opts):
+    opts.nothreads=1
+
hunk ./driver/testlib.py 345
-def test( name, setup, func, args ):
-    t.total_tests = t.total_tests + 1
+def test ( name, setup, func, args):
+    return test_common(0,name,setup,func,args)
{
hunk ./driver/testlib.py 348
-    # Reset the test-local options to the options for this "set"
+def test_alone (name, setup, func, args):
+    return test_common(1,name,setup,func,args)
+
+def test_common (ser, name, setup, func, args):
+    n = 1
hunk ./driver/testlib.py 354
+    setup(getTestOpts())
+    if ser or getTestOpts().nothreads:
+        n = config.threads
+
+    ok = 0
+    t.thread_pool.acquire()
+    try:
+        while config.threads<(t.running_threads+n):
+            t.thread_pool.wait()
+        t.running_threads = t.running_threads+n
+        ok=1
+        t.thread_pool.release()
+        thread.start_new_thread(test_common_thread, (n, name, setup, func, 
args))
+    except:
+        if not ok:
+            t.thread_pool.release()
+
+def test_common_thread(n, name, setup, func, args):
+    t.lock.acquire()
+    try:
+        test_common_work(name,setup,func,args)
+    finally:
+        t.lock.release()
+        t.thread_pool.acquire()
+        t.running_threads = t.running_threads - n
+        t.thread_pool.notify()
+        t.thread_pool.release()
+ }
hunk ./driver/testlib.py 353
-    resetTestOpts()
-    setup(getTestOpts())
-    if ser or getTestOpts().nothreads:
+    opts = copy.copy(thisdir_testopts)
+    setup(opts)
+    if ser or opts.nothreads:
hunk ./driver/testlib.py 366
-        thread.start_new_thread(test_common_thread, (n, name, setup, func, 
args))
+        thread.start_new_thread(test_common_thread, (n, name, opts, func, 
args))
hunk ./driver/testlib.py 371
-def test_common_thread(n, name, setup, func, args):
+def test_common_thread(n, name, opts, func, args):
hunk ./driver/testlib.py 374
-        test_common_work(name,setup,func,args)
+        test_common_work(name,opts,func,args)
hunk ./driver/testlib.py 383
-    # Set our test-local options
-    setup(testopts)
hunk ./driver/testlib.py 384
+def test_common_work (name, opts, func, args):
+    t.total_tests = t.total_tests+1
+    setLocalTestOpts(opts)
hunk ./driver/testlib.py 403
-        not testopts.skip \
+        not getTestOpts().skip \
hunk ./driver/testlib.py 405
-        and (testopts.only_ways == [] or way in testopts.only_ways) \
-        and way not in testopts.omit_ways
+        and (getTestOpts().only_ways == [] or way in getTestOpts().only_ways) \
+        and way not in getTestOpts().omit_ways
hunk ./driver/testlib.py 437
-    if testopts.cleanup != '':
+    if getTestOpts().cleanup != '':
hunk ./driver/testlib.py 448
-        result = apply(func, [name,way] + args)
+        t.lock.release()
+        try:
+            result = apply(func, [name,way] + args)
+        finally:
+            t.lock.acquire()
hunk ./driver/testlib.py 454
-        if testopts.expect != 'pass' and testopts.expect != 'fail' or \
+        if getTestOpts().expect != 'pass' and getTestOpts().expect != 'fail' 
or \
hunk ./driver/testlib.py 459
-            if testopts.expect == 'pass' \
-               and way not in testopts.expect_fail_for:
+            if getTestOpts().expect == 'pass' \
+               and way not in getTestOpts().expect_fail_for:
hunk ./driver/testlib.py 474
-            if testopts.expect == 'pass' \
-               and way not in testopts.expect_fail_for:
+            if getTestOpts().expect == 'pass' \
+               and way not in getTestOpts().expect_fail_for:
hunk ./driver/testlib.py 538
-    testopts.stdin = script
+    getTestOpts().stdin = script
hunk ./driver/testlib.py 608
-        return simple_run( name, way, './'+name, testopts.extra_run_opts, 0 )
+        return simple_run( name, way, './'+name, getTestOpts().extra_run_opts, 
0 )
hunk ./driver/testlib.py 625
-    return simple_run( name, way, './'+name, testopts.extra_run_opts, 0 )
+    return simple_run( name, way, './'+name, getTestOpts().extra_run_opts, 0 )
hunk ./driver/testlib.py 642
-    return simple_run( name, way, './'+name, testopts.extra_run_opts, 1 )
+    return simple_run( name, way, './'+name, getTestOpts().extra_run_opts, 1 )
hunk ./driver/testlib.py 662
-    elif testopts.compile_to_hc:
+    elif getTestOpts().compile_to_hc:
hunk ./driver/testlib.py 674
-          + testopts.extra_hc_opts + ' ' \
+          + getTestOpts().extra_hc_opts + ' ' \
hunk ./driver/testlib.py 697
-   if testopts.stdin != '':
-       use_stdin = testopts.stdin
+   if getTestOpts().stdin != '':
+       use_stdin = getTestOpts().stdin
hunk ./driver/testlib.py 726
-   if exit_code != testopts.exit_code:
-       print 'Wrong exit code (expected', testopts.exit_code, ', actual', 
exit_code, ')'
+   if exit_code != getTestOpts().exit_code:
+       print 'Wrong exit code (expected', getTestOpts().exit_code, ', actual', 
exit_code, ')'
hunk ./driver/testlib.py 772
-        script.write(':set args ' + testopts.extra_run_opts + '\n')
+        script.write(':set args ' + getTestOpts().extra_run_opts + '\n')
hunk ./driver/testlib.py 785
-    if testopts.stdin != '':
-        stdin_file = in_testdir(testopts.stdin)
+    if getTestOpts().stdin != '':
+        stdin_file = in_testdir(getTestOpts().stdin)
hunk ./driver/testlib.py 802
-          + testopts.extra_hc_opts + ' ' \
+          + getTestOpts().extra_hc_opts + ' ' \
hunk ./driver/testlib.py 811
-    if exit_code != testopts.exit_code:
-        print 'Wrong exit code (expected', testopts.exit_code, ', actual', 
exit_code, ')'
+    if exit_code != getTestOpts().exit_code:
+        print 'Wrong exit code (expected', getTestOpts().exit_code, ', 
actual', exit_code, ')'
hunk ./driver/testlib.py 885
-          + testopts.extra_hc_opts \
+          + getTestOpts().extra_hc_opts \
hunk ./driver/testlib.py 915
-          + testopts.extra_hc_opts + ' ' \
+          + getTestOpts().extra_hc_opts + ' ' \
hunk ./driver/testlib.py 934
-    return simple_run ( name, way, './'+name, testopts.extra_run_opts, 0 )
+    return simple_run ( name, way, './'+name, getTestOpts().extra_run_opts, 0 )
hunk ./mk/test.mk 16
+#       THREADS         -- run n tests at once
hunk ./mk/test.mk 78
+
+ifneq "$(THREADS)" ""
+RUNTEST_OPTS += --thread=$(THREADS)
+endif
}

Context:

[Update output (remove "In the call...")
[EMAIL PROTECTED] [Update output [EMAIL PROTECTED] [Add test for tagToEnum# [EMAIL PROTECTED] [Two more tests [EMAIL PROTECTED] [Update expected output [EMAIL PROTECTED] [Add flag to test [EMAIL PROTECTED] [More upated output [EMAIL PROTECTED] [More updated output [EMAIL PROTECTED] [Update test outpuot [EMAIL PROTECTED] [Remove typecheck.testeq1.run.stdout [EMAIL PROTECTED] [Comments in Makefile [EMAIL PROTECTED] [This test now compiles without errors Simon Marlow <[EMAIL PROTECTED]>**20060811102354] [accept output Simon Marlow <[EMAIL PROTECTED]>**20060811101931] [base-1.0 ==> base-2.0 Simon Marlow <[EMAIL PROTECTED]>**20060811101925] [base-1.0 ==> base-2.0 Simon Marlow <[EMAIL PROTECTED]>**20060811101619] [accept output Simon Marlow <[EMAIL PROTECTED]>**20060811101428] [update FFI syntax Simon Marlow <[EMAIL PROTECTED]>**20060811100321] [expect fail for threaded2 way, fork isn't supported in SMP mode (yet) Simon Marlow <[EMAIL PROTECTED]>**20060811100315] [fix FFI syntax Simon Marlow <[EMAIL PROTECTED]>**20060811095918] [accept output Simon Marlow <[EMAIL PROTECTED]>**20060811095501] [Fix some Array.bounds calls to Array.getBounds Esa Ilari Vuokko <[EMAIL PROTECTED]>**20060809220653] [Add tests for incomplete-pattern warnings [EMAIL PROTECTED] [Lazy patterns can't be unboxed (Trac 845) [EMAIL PROTECTED] [Test error message (Trac 844) [EMAIL PROTECTED] [Add tc206; edit a couple of others [EMAIL PROTECTED] [Add test for overlapping pattern warnings for lazy patterns [EMAIL PROTECTED] [Add a test for infix type constructors [EMAIL PROTECTED] [Add test for unboxed fields in GADT record selectors [EMAIL PROTECTED] [add new cabal test Simon Marlow <[EMAIL PROTECTED]>**20060727140657] [test fixes and new tests for package support Simon Marlow <[EMAIL PROTECTED]>**20060727140436] [accept output (improved error messages due to PrintUnqual changes) Simon Marlow <[EMAIL PROTECTED]>**20060727140124] [accept output Simon Marlow <[EMAIL PROTECTED]>**20060727134921] [add test for Ix bug Simon Marlow <[EMAIL PROTECTED]>**20060721100303] [document stage=2, and clean up a little. Simon Marlow <[EMAIL PROTECTED]>**20060710153547] [remove unused imports Simon Marlow <[EMAIL PROTECTED]>**20060616105302] [Test Trac bug #795 [EMAIL PROTECTED] [encorporate rest of property checks for Data.ByteString Don Stewart <[EMAIL PROTECTED]>**20060702093816] [Add regress tests for fusion rules. Makes sure they fire, and rewrite to correct result Don Stewart <[EMAIL PROTECTED]>**20060702090703] [Add model-based tests for ByteString.Lazy<=>ByteString<=>Data.list Don Stewart <[EMAIL PROTECTED]>**20060702055523] [Accept output change [EMAIL PROTECTED] [Add test for infix function definitions [EMAIL PROTECTED] [Test for pattern type sigs in do-notation [EMAIL PROTECTED] [add test from #799 Simon Marlow <[EMAIL PROTECTED]>**20060623094712] [omit conc039 for threaded2 Simon Marlow <[EMAIL PROTECTED]>**20060622092716] [robustify the test a little Simon Marlow <[EMAIL PROTECTED]>**20060622092148] [omit conc036 for GHCi Simon Marlow <[EMAIL PROTECTED]>**20060622091811] [add a prof/TH test Simon Marlow <[EMAIL PROTECTED]>**20060622090109] [accept output Simon Marlow <[EMAIL PROTECTED]>**20060622085217] [re-enable various tests with -threaded that now work Simon Marlow <[EMAIL PROTECTED]>**20060614144922] [fix this test to work propertly with -threaded Simon Marlow <[EMAIL PROTECTED]>**20060614144256] [Fix this test to work properly with -threaded Simon Marlow <[EMAIL PROTECTED]>**20060614144219] [test for NCG bug Simon Marlow <[EMAIL PROTECTED]>**20060606112614] [accept output
Simon Marlow <[EMAIL PROTECTED]>**20060601123936
 NOTE: I made a slight tweak to Alex to improve the lexical error messages,
 to get correct output for these tests you need an updated Alex from darcs.
] [disable ffi016 for GHCi Simon Marlow <[EMAIL PROTECTED]>**20060530095146] [first attempt at being boring Ashley Yakeley <[EMAIL PROTECTED]>**20060526070327] [Update expected output Don Stewart <[EMAIL PROTECTED]>**20060525071135] [update expected output. tougher replicate test. Don Stewart <[EMAIL PROTECTED]>**20060517020540] [accept output Simon Marlow <[EMAIL PROTECTED]>**20060508073357] [More QC tests. Update output Don Stewart <[EMAIL PROTECTED]>**20060507042341] [More QC properties. Update output Don Stewart <[EMAIL PROTECTED]>**20060506043305] [Add test for newtypes in FFI
[EMAIL PROTECTED]
The standard FFI says that newtypes are automatically unwrapped in
 argument and result types.  This test checks that it also happens
 for newtype-wrapping of the IO monad itself, a recent change to
 GHC.
] [And add QC test for group/groupBy Don Stewart <[EMAIL PROTECTED]>**20060501065658] [More QC properties, for fold{lr}1. Update expected output Don Stewart <[EMAIL PROTECTED]>**20060430084252] [Import Data.ByteString regression tests Don Stewart <[EMAIL PROTECTED]>**20060428122838] [avoid running out of stack Simon Marlow <[EMAIL PROTECTED]>**20060428083855] [test Bool arguments too Simon Marlow <[EMAIL PROTECTED]>**20060418144834] [Test for foralls to the right of => [EMAIL PROTECTED] [Test for error recovery in TH [EMAIL PROTECTED] [forgot to add this file Simon Marlow <[EMAIL PROTECTED]>**20060413080300] [Add a test for SpecConstr + GADTs [EMAIL PROTECTED] [Memo-function test
[EMAIL PROTECTED]
Checks that preInlineUnconditionally isn't to eager!
 (If it is, this test goes exponential.)
] [add a test for a division bug in the NCG Simon Marlow <[EMAIL PROTECTED]>**20060412144627] [Add test for newtype deriving (thanks to Ross) [EMAIL PROTECTED] [update for new source tree layout Simon Marlow <[EMAIL PROTECTED]>**20060410091202] [add a test for a blackhole GC bug Simon Marlow <[EMAIL PROTECTED]>**20060407101628] [the "threaded" way was renamed to "threaded1"/"threaded2" Simon Marlow <[EMAIL PROTECTED]>**20060407101619] [Track the GHC source tree reorganisation Simon Marlow <[EMAIL PROTECTED]>**20060407041720] [omit asm ways for this test on x86 Simon Marlow <[EMAIL PROTECTED]>**20060407080546] [avoid running out of stack for non-optimised ways Simon Marlow <[EMAIL PROTECTED]>**20060407080032] [add test for ForeignPtrEnv Simon Marlow <[EMAIL PROTECTED]>**20060405160129] [omit ffi007 and ffi008 for GHCi (see comment for details) Simon Marlow <[EMAIL PROTECTED]>**20060405133421] [fix tests for Windows Simon Marlow <[EMAIL PROTECTED]>**20060404153133] [unnecessary mingw-specific output Simon Marlow <[EMAIL PROTECTED]>**20060404150047] [windows output Simon Marlow <[EMAIL PROTECTED]>**20060404145525] [crummy fix for Windows Simon Marlow <[EMAIL PROTECTED]>**20060404145128] [fix the expect_fail_if_windows macro Simon Marlow <[EMAIL PROTECTED]>**20060404144611] [Add scoped tyvar test [EMAIL PROTECTED] [attempt to work around restrictions with fork() & pthreads
Simon Marlow <[EMAIL PROTECTED]>**20060323134034
 In the child process, call exec() directly instead of using
 System.Cmd.system, which involves another fork()/exec() and a
 non-blocking wait.  The problem is that in a forked child of a
 threaded process, it isn't safe to do much except exec() according to
 POSIX.  In fact calling pthread_create() in the child causes the
 pthread library to fail with an error on FreeBSD.
] [accept output (better error locations) Simon Marlow <[EMAIL PROTECTED]>**20060323102719] [fix to previous Simon Marlow <[EMAIL PROTECTED]>**20060323102523] [fcntl-FreeBSD
[EMAIL PROTECTED]
Expect failure of queryfdoption01 on FreeBSD (6/7): /dev/null can't be switched to non-blocking i/o, so fcntl() will throw an error.
 Unfortunately this went to the old CVS first.
] [fix for GHCi tests that raise exceptions or exit
Simon Marlow <[EMAIL PROTECTED]>**20060320124648
 We need to call GHC.TopHandler.runIOFastExit instead of
 GHC.TopHandler.runIO.  Recent fixes to the shutdown code have meant
 that when a thread invokes shutdownHaskellAndExit(), other main
 threads get a chance to exit (as they should), but this means that we
 might have a race between the child thread trying to exit the program
 and the main thread doing the same.  In the case of GHCi, if we're
 running an interpreted computation that needs to exit (as some tests
 do), then we really want this child thread to exit the program rather
 than the main thread.
] [sort the keys when outputting the summary Simon Marlow <[EMAIL PROTECTED]>**20060320114811] [fix a regex that was too slow Simon Marlow <[EMAIL PROTECTED]>**20060316163903] [ignore ".exe" in program output, for Windows Simon Marlow <[EMAIL PROTECTED]>**20060316155440] [fix for Win32 Simon Marlow <[EMAIL PROTECTED]>**20060316154734] [remove some dead code Simon Marlow <[EMAIL PROTECTED]>**20060315114645] [Tidy up the testsuite output by combinding failures for multiple ways
Simon Marlow <[EMAIL PROTECTED]>**20060315112501
Before:
    tc056(normal)
    tc056(opt)
    tc056(optasm)
    tc056(prof)
    tc056(profasm)
    tc056(unreg)
After:
    tc056(normal,opt,optasm,prof,profasm,unreg)
] [patch up this test again Simon Marlow <[EMAIL PROTECTED]>**20060314151844] [process003 doesn't work with GHCi, omit it Simon Marlow <[EMAIL PROTECTED]>**20060314151657] [fix clean target Simon Marlow <[EMAIL PROTECTED]>**20060314124525] [add test for #713 Simon Marlow <[EMAIL PROTECTED]>**20060314121232] [Require -fallow-undecidable-instances [EMAIL PROTECTED] [Test for deprecated constructors [EMAIL PROTECTED] [Update output [EMAIL PROTECTED] [Update output and add -fallow-undecidable-instances where necesssary [EMAIL PROTECTED] [Add -fallow-undecidable-instances to reflect more accurate termination test in fundeps [EMAIL PROTECTED] [Remove dependence on haskell98 package in expected output [EMAIL PROTECTED] [Accept output [EMAIL PROTECTED] [Add expected output for rn049 [EMAIL PROTECTED] [Accept (slightly mysterious) output formatting changes [EMAIL PROTECTED] [Update output [EMAIL PROTECTED] [Update output (TH no longer depends on haskell98 package) [EMAIL PROTECTED] [Add a fundep loop test [EMAIL PROTECTED] [add expected output for x86_64 Simon Marlow <[EMAIL PROTECTED]>**20060223121322] [accept output Simon Marlow <[EMAIL PROTECTED]>**20060210151137] [remove smp way, replace threaded with threaded1/threaded2
Simon Marlow <[EMAIL PROTECTED]>**20060210123325
threaded1 = -threaded -debug
 threaded2 = -O -threaded, and +RTS -N2 -RTS at runtime
] [Add test for bug 685 [EMAIL PROTECTED] [Add test from Markus Lauer [EMAIL PROTECTED] ["s" is in GhcRTSWays now Simon Marlow <[EMAIL PROTECTED]>**20060208150646] [allow setting stage=N variable to select compiler in the testsuite Simon Marlow <[EMAIL PROTECTED]>**20060208140219] [Eta expand gzip test to match new higher-rank-type story [EMAIL PROTECTED] [Fix GADT tests [EMAIL PROTECTED] [New GADT desugaring test [EMAIL PROTECTED] [Remove package lang reqt [EMAIL PROTECTED] [Update to track improvements in typechecker [EMAIL PROTECTED] [Update to track new scoped-tyvar story [EMAIL PROTECTED] [Eta expansion and scoped type variables in generic code
[EMAIL PROTECTED]
The new story on higher-rank types requires a few functions to be
 eta-expanded.  And the new scoped-type-variable story also forces
 a few changes.
] [Add CPR test [EMAIL PROTECTED] [remove old docs Simon Marlow <[EMAIL PROTECTED]>**20060201163734] [add test for bug #661 Simon Marlow <[EMAIL PROTECTED]>**20060201130720] [fix recently-introduced breakage in 'make accept' Simon Marlow <[EMAIL PROTECTED]>**20060201115729] [Add a higher-kinded test [EMAIL PROTECTED] [Add fundep test [EMAIL PROTECTED] [Module import test [EMAIL PROTECTED] [Wibble [EMAIL PROTECTED] [Add test for bogus unusued-import message [EMAIL PROTECTED] [[project @ 2006-01-19 09:47:11 by simonmar]
simonmar**20060119094711
 Test tryPutMVar on empty MVars too
] [[project @ 2006-01-18 16:31:10 by simonmar]
simonmar**20060118163112
 Add a fast version of the testsuite
The idea is to have a way to run as much of the testsuite as possible
 in a short time, so that we'll run it more often (such as just before
 checking in a change, for example).  'make fast' tries for good
 coverage without using too many cycles.  Currently it takes about 4
 minutes on a fast machine with an optimised GHC build; I think this
 might still be a little on the slow side.
When you say 'make fast' in testsuite/tests/ghc-regress, we run each
 test only one way, and all of the long-running tests are omitted.
 Also, to get the runtime down further, I arbitrarily omitted many of
 the should_run tests (because these tend to take a lot longer than
 should_compile or should_fail tests).  I tried to keep a
 representative few in each category.
] [[project @ 2006-01-18 15:25:45 by simonpj]
simonpj**20060118152545
 Add test for data con in class sig
] [[project @ 2006-01-12 16:10:41 by simonmar]
simonmar**20060112161041
 Add test from ticket #488
] [[project @ 2006-01-12 16:03:21 by simonmar]
simonmar**20060112160321
 add test from ticket #441
] [[project @ 2006-01-10 14:39:50 by simonmar]
simonmar**20060110143950
 accept output
] [[project @ 2006-01-10 14:11:53 by simonmar]
simonmar**20060110141153
 comment update
] [[project @ 2006-01-10 14:11:24 by simonmar]
simonmar**20060110141124
 recode this file in UTF-8 from Latin-1
] [[project @ 2006-01-10 13:41:48 by simonmar]
simonmar**20060110134148
 accept output (improved lexer error messages)
] [[project @ 2006-01-09 12:49:28 by simonmar]
simonmar**20060109124928
 Add test case that causes a core-lint failure (cut down from
 Encoding.hs in HEAD).
] [[project @ 2006-01-09 10:29:44 by simonmar]
simonmar**20060109102944
 add a cmm lint failure
] [[project @ 2006-01-09 10:27:33 by simonmar]
simonmar**20060109102733
 Add -dcmm-lint when compiling
] [[project @ 2006-01-06 16:34:56 by simonmar]
simonmar**20060106163456
 Unicode source tests
] [[project @ 2006-01-06 16:15:19 by simonpj]
simonpj**20060106161519
 Add another synonym-performance test (but comment it out of the test file; too 
slow!)
] [[project @ 2006-01-06 16:14:45 by simonpj]
simonpj**20060106161445
 Better type signature for higher-rank
] [[project @ 2006-01-06 16:12:42 by simonpj]
simonpj**20060106161242
 Add tests for boxy types
] [[project @ 2006-01-06 16:08:57 by simonpj]
simonpj**20060106160857
 Add GADT tests
] [[project @ 2006-01-06 16:03:25 by simonpj]
simonpj**20060106160325
 Cosmetic
] [[project @ 2006-01-05 13:08:14 by simonpj]
simonpj**20060105130814
 Add a nasty multiple-instantiation test
] [[project @ 2006-01-05 10:06:30 by simonpj]
simonpj**20060105100630
 Add test for newtype existential
] [[project @ 2006-01-05 09:16:28 by simonmar]
simonmar**20060105091628
 Add test for "scavenge_stack" bug fixed in rev 1.16 of Exception.cmm
] [[project @ 2006-01-04 11:50:44 by simonpj]
simonpj**20060104115044
 Add test for data con returning wrong type
] [[project @ 2006-01-02 19:36:50 by jpbernardy]
jpbernardy**20060102193650
 minor cleanups
] [[project @ 2006-01-01 21:46:31 by jpbernardy]
jpbernardy**20060101214631
 More tests for:
   * Sets
   * Non-structural equality
   * Left-Bias
   * Performance
] [[project @ 2005-12-26 19:54:32 by jpbernardy]
jpbernardy**20051226195432
 Infrastructure for testing Data structures.
  + some tests
] [[project @ 2005-12-19 09:47:49 by simonpj]
simonpj**20051219094749
 Add test for trailing parens in GADT signatures
] [[project @ 2005-12-16 16:03:02 by simonpj]
simonpj**20051216160302
 Add deriving for infix constructors
] [[project @ 2005-12-16 14:56:50 by simonpj]
simonpj**20051216145650
 Add repeated-type-variable tests for instance constexts
] [[project @ 2005-12-16 10:54:50 by simonmar]
simonmar**20051216105450
 TimeExts has gone away
] [[project @ 2005-12-16 10:53:24 by simonmar]
simonmar**20051216105324
 update to not use hslibs
] [[project @ 2005-12-16 10:50:31 by simonmar]
simonmar**20051216105031
 -package lang isn't required.
] [[project @ 2005-12-16 10:46:05 by simonmar]
simonmar**20051216104605
 Now that we aren't building hslibs, keep the memo tests alive by
 bringing Memo.hs into the testsuite.  These tests are a useful
 shakedown for StableNames.
] [[project @ 2005-12-13 16:04:25 by simonmar]
simonmar**20051213160425
 Add nested atomically test
] [[project @ 2005-12-13 16:04:09 by simonmar]
simonmar**20051213160409
 fix comments
] [[project @ 2005-12-09 19:17:57 by simonpj]
simonpj**20051209191757
 add output file
] [[project @ 2005-12-09 19:16:58 by simonpj]
simonpj**20051209191658
 A minor, probably redundant, test
] [[project @ 2005-12-05 11:43:51 by simonmar]
simonmar**20051205114351
 add newTVarIO test
] [[project @ 2005-12-05 10:08:53 by simonpj]
simonpj**20051205100853
 Add an expected-failure test
] [[project @ 2005-12-05 09:13:07 by simonpj]
simonpj**20051205091307
 Update expected output
] [[project @ 2005-12-05 09:08:51 by simonpj]
simonpj**20051205090851
 Fix test
] [[project @ 2005-12-02 10:56:34 by simonmar]
simonmar**20051202105634
 add this test that I had lying around
] [[project @ 2005-12-02 10:54:05 by simonmar]
simonmar**20051202105405
 conc053 only works in threaded & smp ways at the moment.
] [[project @ 2005-12-02 10:51:15 by simonmar]
simonmar**20051202105115
 accept output
] [[project @ 2005-12-01 08:54:57 by simonpj]
simonpj**20051201085457
 Another GADT test
] [[project @ 2005-11-30 14:17:35 by simonpj]
simonpj**20051130141735
 Add mkName test
] [[project @ 2005-11-30 12:25:20 by simonmar]
simonmar**20051130122520
 Add test for Control.Concurrent.STM.registerDelay
] [TAG Last rev before making ghc-6-4 branch John Goerzen <[EMAIL PROTECTED]>**20051128164635] [TAG Initial conversion from CVS complete John Goerzen <[EMAIL PROTECTED]>**20051128163910] Patch bundle hash:
7062a6b3f72e22c44261547e2b0cf61e037c29f1


------------------------------------------------------------------------

_______________________________________________
Cvs-ghc mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/cvs-ghc

_______________________________________________
Cvs-ghc mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to