Tue Apr 10 10:03:08 EDT 2007  Tyson Whitehead <[EMAIL PROTECTED]>
  * Differentiate between use of fail and failure of code (i.e., an exception 
is thrown)

Tue Apr 10 10:06:53 EDT 2007  Tyson Whitehead <[EMAIL PROTECTED]>
  * Add a test for use of fail for trac #1265
-----BEGIN PGP SIGNED MESSAGE-----
Hash: SHA1


New patches:

[Differentiate between use of fail and failure of code (i.e., an exception is thrown)
Tyson Whitehead <[EMAIL PROTECTED]>**20070410140308] {
move ./tests/ghc-regress/th/TH_exn.hs ./tests/ghc-regress/th/TH_exn2.hs
move ./tests/ghc-regress/th/TH_exn.stderr ./tests/ghc-regress/th/TH_exn2.stderr
move ./tests/ghc-regress/th/TH_fail.hs ./tests/ghc-regress/th/TH_exn1.hs
move ./tests/ghc-regress/th/TH_fail.stderr ./tests/ghc-regress/th/TH_exn1.stderr
hunk ./tests/ghc-regress/th/TH_exn1.hs 4
- --- fails (e.g. with pattern match failure)
+-- fails in an immediate fashion (e.g. with a
+-- pattern match failure)
hunk ./tests/ghc-regress/th/TH_exn1.hs 13
- -
- -
- -
- -
hunk ./tests/ghc-regress/th/TH_exn2.hs 3
- --- A (head []) failure within a TH splice
- --- This one generates an exception in the TH 
- --- code which should be caught in a civilised way
+-- Test error message when the code in a splice
+-- fails in a lazy fashion (e.g. a (head [])
+-- thunk is embedded in the returned structure).
hunk ./tests/ghc-regress/th/TH_exn2.hs 13
- -
hunk ./tests/ghc-regress/th/TH_exn2.stderr 3
- -    Exception when trying to run compile-time code:
+    Exception when trying to interpret result of compile-time code:
hunk ./tests/ghc-regress/th/all.T 68
- -test('TH_fail', normal, compile_fail, [''])
+test('TH_exn1', normal, compile_fail, [''])
hunk ./tests/ghc-regress/th/all.T 71
- -test('TH_exn', normal, compile_fail, [''])
+test('TH_exn2', normal, compile_fail, [''])
}

[Add a test for use of fail for trac #1265
Tyson Whitehead <[EMAIL PROTECTED]>**20070410140653] {
addfile ./tests/ghc-regress/th/TH_fail.hs
hunk ./tests/ghc-regress/th/TH_fail.hs 1
+{-# OPTIONS_GHC -fth #-}
+
+-- Test for sane reporting on TH code giving up.
+
+module ShouldCompile where
+
+$( fail "Code not written yet..." )
addfile ./tests/ghc-regress/th/TH_fail.stderr
hunk ./tests/ghc-regress/th/TH_fail.stderr 1
+
+TH_fail.hs:1:0: Code not written yet...
+Loading package base ... linking ... done.
+Loading package template-haskell ... linking ... done.
hunk ./tests/ghc-regress/th/all.T 76
+test('TH_fail', normal, compile_fail, [''])
}

Context:

[ghci015 should ignore output (see comment)
Simon Marlow <[EMAIL PROTECTED]>**20070403112228] 
[Accept test output
Ian Lynagh <[EMAIL PROTECTED]>**20070401211751] 
[IsString and fromString are in Data.String now
Ian Lynagh <[EMAIL PROTECTED]>**20070401211027] 
[tc217/220/223 need mtl
Ian Lynagh <[EMAIL PROTECTED]>**20070401210909] 
[Remove generated file
Ian Lynagh <[EMAIL PROTECTED]>**20070401210528] 
[Update rnfail040 output
Ian Lynagh <[EMAIL PROTECTED]>**20070401210413] 
[Update output with new, friendlier error
Ian Lynagh <[EMAIL PROTECTED]>**20070401205626] 
[Consistent output for tests
Ian Lynagh <[EMAIL PROTECTED]>**20070401205455] 
[Add some -v0s to cabal01; cabal still isn't being quiet enough, though
Ian Lynagh <[EMAIL PROTECTED]>**20070401203313] 
[Accept output
Ian Lynagh <[EMAIL PROTECTED]>**20070401202323] 
[Check stderr output before stdout output
Ian Lynagh <[EMAIL PROTECTED]>**20070401202156] 
[On failure, diff the normalised test outputs
Ian Lynagh <[EMAIL PROTECTED]>**20070401202024] 
[Time how long is spent on each .T file
Ian Lynagh <[EMAIL PROTECTED]>**20070331115228] 
[Make our own pwd, so we don't get confused by paths on cygwin
Ian Lynagh <[EMAIL PROTECTED]>**20070330184246] 
[Update test output
Ian Lynagh <[EMAIL PROTECTED]>**20070401190122] 
[Add rnfail047, test for trac #924
Ian Lynagh <[EMAIL PROTECTED]>**20070331123429] 
[Use unified, rather than context, diffs
Ian Lynagh <[EMAIL PROTECTED]>**20070330134203] 
[Test for RULES type-matching
[EMAIL PROTECTED] 
[There is no opt way any more
[EMAIL PROTECTED]
 
 Use optc, optasm instead.
 
] 
[added more examples
[EMAIL PROTECTED] 
[add test for #1219
Simon Marlow <[EMAIL PROTECTED]>**20070327103851] 
[TH_dataD1/1193 is no longer broken, but is meant to fail
Ian Lynagh <[EMAIL PROTECTED]>**20070324003644] 
[Test for Trac #1031
[EMAIL PROTECTED] 
[Add another renamer test nhc98 used to fail
Ian Lynagh <[EMAIL PROTECTED]>**20070315001153] 
[Another renamer test that nhc98 used to fail on
Ian Lynagh <[EMAIL PROTECTED]>**20070314190837] 
[Add a renamer test (nhc98 used to fail it)
Ian Lynagh <[EMAIL PROTECTED]>**20070314185736] 
[Add test for Trac #1221
[EMAIL PROTECTED] 
[Fix gadt23 test
Ian Lynagh <[EMAIL PROTECTED]>**20070311214714] 
[Add a test gadt23 from Christophe Poucet
Ian Lynagh <[EMAIL PROTECTED]>**20070311195336] 
[Don't hide the Makefile commands
Ian Lynagh <[EMAIL PROTECTED]>**20070311195207
 The testsuite uses -s to hide them, and this way we can see what's
 happening when running make by hand.
] 
[added contract synonym test case again
[EMAIL PROTECTED] 
[added contract synonym test case
[EMAIL PROTECTED] 
[on Windows, use the .bat versions of the inplace scripts
Simon Marlow <[EMAIL PROTECTED]>**20070308131540
 This will help the Cabal tests to work (although there are still more
 issues to fix).
] 
[add test for #986
Simon Marlow <[EMAIL PROTECTED]>**20070306155450] 
[Add a test (TH_reifyDecl2) for trac #1199
Ian Lynagh <[EMAIL PROTECTED]>**20070306130708] 
[Test ghci018 for ghci running splices multiple times (trac #1201)
Ian Lynagh <[EMAIL PROTECTED]>**20070306125155] 
[Don't hide what the Makefile is doing in prog006
Ian Lynagh <[EMAIL PROTECTED]>**20070305195516] 
[newtype, prof001, prof002 require profiling
Ian Lynagh <[EMAIL PROTECTED]>**20070305184129] 
[ghci014 needs QuickCheck
Ian Lynagh <[EMAIL PROTECTED]>**20070305174521] 
[cabal02 is broken on Windows; trac #1196
Ian Lynagh <[EMAIL PROTECTED]>**20070305171757] 
[cabal01 is broken on Windows; trac #1196
Ian Lynagh <[EMAIL PROTECTED]>**20070305171411] 
[TH_spliceE5_prof needs profiling
Ian Lynagh <[EMAIL PROTECTED]>**20070305155703] 
[MERGED: Add req_profiling to the driver
Ian Lynagh <[EMAIL PROTECTED]>**20070305160444] 
[Posix tests moved to the unix package
Simon Marlow <[EMAIL PROTECTED]>**20070305145343] 
[tree requires mtl
Ian Lynagh <[EMAIL PROTECTED]>**20070304215516] 
[tcfail126 requires mtl
Ian Lynagh <[EMAIL PROTECTED]>**20070304214547] 
[tc183 depends on mtl
Ian Lynagh <[EMAIL PROTECTED]>**20070304213805] 
[Print something to stderr when a timeout happens
Ian Lynagh <[EMAIL PROTECTED]>**20070304212955
 Also fixes whitespace.
] 
[reify requires mtl
Ian Lynagh <[EMAIL PROTECTED]>**20070304210343] 
[pkg02_b requires network
Ian Lynagh <[EMAIL PROTECTED]>**20070304195629] 
[Decouple more tests from each other so CLEANUP mode works
Ian Lynagh <[EMAIL PROTECTED]>**20070304194218] 
[More tweaks
Ian Lynagh <[EMAIL PROTECTED]>**20070304193526] 
[Tweaks
Ian Lynagh <[EMAIL PROTECTED]>**20070304192457] 
[Decouple mod158 from mod157 so it works in CLEANUP mode
Ian Lynagh <[EMAIL PROTECTED]>**20070304192411] 
[Make mod144/mod146 work in CLEANUP mode
Ian Lynagh <[EMAIL PROTECTED]>**20070304191539] 
[mod133 needs mtl
Ian Lynagh <[EMAIL PROTECTED]>**20070304184609] 
[Make ghcpkg03 not depend on haskell-src
Ian Lynagh <[EMAIL PROTECTED]>**20070304174635] 
[Make ghcpkg01 not depend on haskell-src
Ian Lynagh <[EMAIL PROTECTED]>**20070304174511] 
[drvfail006 and drvfail008 need mtl
Ian Lynagh <[EMAIL PROTECTED]>**20070304172853] 
[Increase the stack size for conc030 as the profiling way was failing
Ian Lynagh <[EMAIL PROTECTED]>**20070304171748] 
[TH_dataD1 is currently broken
Ian Lynagh <[EMAIL PROTECTED]>**20070304165220] 
[Add pretty-print test
[EMAIL PROTECTED] 
[Add tests for -keep-s-file with and without --make
Simon Marlow <[EMAIL PROTECTED]>**20070301095725
 One of these fails with 6.6
] 
[prof001 & prof002 are not broken now
Simon Marlow <[EMAIL PROTECTED]>**20070228155129] 
[Windows: the .ps file is <prog>.exe.ps
Simon Marlow <[EMAIL PROTECTED]>**20070228120254] 
[Add testcase from trac #1171 as cg059
Ian Lynagh <[EMAIL PROTECTED]>**20070226232635] 
[Test for derivign
[EMAIL PROTECTED] 
[Tests for Trac #1154
[EMAIL PROTECTED] 
[Add a test for :quit and breakpoints in code with exception handlers
Pepe Iborra <[EMAIL PROTECTED]>**20070221161548] 
[remove network tests, they're moving to the network package
Simon Marlow <[EMAIL PROTECTED]>**20070221142519] 
[Look for .T files in packages too
Simon Marlow <[EMAIL PROTECTED]>**20070221140708
 This means we can put package-specific tests in the repository for the
 package, rather than putting them in the testsuite.  There should be a
 .T file to go with the tests, in the same way as for other tests in
 the testsuite (but this could be in addition to a standalone test
 driver that works with Cabal's 'setup test').
] 
[temp: omit conc063 on Windows to avoid hanging the build
Simon Marlow <[EMAIL PROTECTED]>**20070221091925] 
[make this test deterministic on a multiprocessor
Simon Marlow <[EMAIL PROTECTED]>**20070220142305] 
[conc058 is not an expected failure any more on Windows
Simon Marlow <[EMAIL PROTECTED]>**20070220140410] 
[use HsInt64 instead of int64_t, fixes this test on Windows (and is more correct)
Simon Marlow <[EMAIL PROTECTED]>**20070220140137] 
[Test for Trac #1128
[EMAIL PROTECTED] 
[Add test for Trac #1153
[EMAIL PROTECTED] 
[minor change
[EMAIL PROTECTED] 
[modified all.T
[EMAIL PROTECTED] 
[added new tests to esc
[EMAIL PROTECTED] 
[add Windows output
Simon Marlow <[EMAIL PROTECTED]>**20070220095533] 
[we should really exit(0) at the end of main()
Simon Marlow <[EMAIL PROTECTED]>**20070220095402] 
[make this test slightly more robust (fix occasional failure with threaded2)
Simon Marlow <[EMAIL PROTECTED]>**20070220093206] 
[rename GHC_PKG -> LOCAL_GHC_PKG to avoid clash with mk/test.mk
Simon Marlow <[EMAIL PROTECTED]>**20070220092011] 
[Add test for type refinement with :print in GHCi
Pepe Iborra <[EMAIL PROTECTED]>**20070218200426] 
[Update test dynbk001 due to new functionality in :break add
Pepe Iborra <[EMAIL PROTECTED]>**20070216202112] 
[Accept output
Pepe Iborra <[EMAIL PROTECTED]>**20070216201850] 
[accept output
Simon Marlow <[EMAIL PROTECTED]>**20070215093749] 
[only do win32002 on Windows
Simon Marlow <[EMAIL PROTECTED]>**20070215092806
 
] 
[add test for bug #1010
Simon Marlow <[EMAIL PROTECTED]>**20070214122124] 
[update way names (fix breakage in previous patch to this file)
Simon Marlow <[EMAIL PROTECTED]>**20070209123135] 
[Accept output
Pepe Iborra <[EMAIL PROTECTED]>**20070206191610] 
[Add tests for impredicativity
[EMAIL PROTECTED] 
[Add test for Trac #1128
[EMAIL PROTECTED] 
[Expect tests to fail if we don't have libraries that they use
Ian Lynagh <[EMAIL PROTECTED]>**20070206142600] 
[Option to skip ways when running the testsuite
Ian Lynagh <[EMAIL PROTECTED]>**20070206012212] 
[Add tests for the Haddock extension
[EMAIL PROTECTED] 
[Don't put double-quotes around the command when passing it to timeout
Simon Marlow <[EMAIL PROTECTED]>**20070202170026
 Fixes the testsuite on Cygwin/MSYS using Cygwin Python.  I hope it
 hasn't broken it using the native Python... if it has, we'll need to
 revisit.  I can't see a good reason for the quotes, anyway.
 
 
] 
[Accept output
Pepe Iborra <[EMAIL PROTECTED]>**20070202113202] 
[Add a test from #418
Ian Lynagh <[EMAIL PROTECTED]>**20070131134818] 
[Ignore output when told to in the ghci way
Ian Lynagh <[EMAIL PROTECTED]>**20070131134800] 
[Test for debugging code with unlifted values around
Pepe Iborra <[EMAIL PROTECTED]>**20070131104727] 
[Add test for infix type constructor
[EMAIL PROTECTED] 
[add test for bug #036
Simon Marlow <[EMAIL PROTECTED]>**20070130101059] 
[accept output
Simon Marlow <[EMAIL PROTECTED]>**20070130100659] 
[add a test for #896
Simon Marlow <[EMAIL PROTECTED]>**20070129125049] 
[Add a hugs import bug to the testsuite
Ian Lynagh <[EMAIL PROTECTED]>**20070128220946
 From http://www.haskell.org/pipermail/hugs-bugs/2007-January/001686.html
] 
[Add a test for trac #1012: Problems with TH and recursive module imports
Ian Lynagh <[EMAIL PROTECTED]>**20070124172850] 
[Check flags in OPTIONS_GHC pragma only apply to the module they're in
Ian Lynagh <[EMAIL PROTECTED]>**20070123143755] 
[now that -O implies -fasm, not -fvia-C, we must explicitly test -fvia-C
Simon Marlow <[EMAIL PROTECTED]>**20070123115104] 
[Add the overloaded string test case to the list.
[EMAIL PROTECTED] 
[Add a test case for overloaded strings.
[EMAIL PROTECTED] 
[Remove an obsolete test
Pepe Iborra <[EMAIL PROTECTED]>**20070120160816
 
 Breakpoint coalescing is disabled for now
] 
[Accept output
Pepe Iborra <[EMAIL PROTECTED]>**20070119112219] 
[fixes to the ignore-output patch
Simon Marlow <[EMAIL PROTECTED]>**20070116093510] 
[Remove unused import
Ian Lynagh <[EMAIL PROTECTED]>**20070115142215] 
[Add a test for trac #1042
Ian Lynagh <[EMAIL PROTECTED]>**20070115141941] 
[Add test for Trac #1092
[EMAIL PROTECTED] 
[Test for tabs warning
Ian Lynagh <[EMAIL PROTECTED]>**20070112164823] 
[Add a test for associated types and interface files
[EMAIL PROTECTED] 
[Add another GADT test
[EMAIL PROTECTED] 
[Add GADT terminating-lambda test (due to Jim Apple)
[EMAIL PROTECTED] 
[oops, fix bogosity in "ignore_output should be a test option"
Simon Marlow <[EMAIL PROTECTED]>**20070108141423] 
[tests for #1047
Simon Marlow <[EMAIL PROTECTED]>**20070105135621] 
[ignore_output should be a test option
Simon Marlow <[EMAIL PROTECTED]>**20070105135600] 
[add test for #1067
Simon Marlow <[EMAIL PROTECTED]>**20070105123546] 
[indexed types, should_fail: added missing .stderrs and adapted to new error messages
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070105011706] 
[indexed types: fixed expected fails for should_compile
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070105010317] 
[indexed types: extend Deriving to cover standalone derive
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070104013049] 
[Add a fundep test, due to Yitzchak Gale
[EMAIL PROTECTED] 
[Add test for floating strict bindings
[EMAIL PROTECTED] 
[Fixed TH problem
[EMAIL PROTECTED] 
[Add more GADT tests, this time concerning contexts in data constructors
[EMAIL PROTECTED] 
[No pattern matching on GADTs except if type is rigid
[EMAIL PROTECTED]
 
 GHC currnently will only pattern-match on a GADT if the scrutinee type
 is rigid.  It's kind-of possible to mactch a wobbly scrutinee if all
 the case alternatives can be made compatible, but that seems a rare case.
 
 So for now, I'm just making it illegal.
 
] 
[More test-suite updates
[EMAIL PROTECTED] 
[Fix sundry test failures (some of Trac #1054)
[EMAIL PROTECTED] 
[Update expected output
[EMAIL PROTECTED] 
[Add stand-alone deriving test
[EMAIL PROTECTED] 
[Add test for deriving Typeable
[EMAIL PROTECTED] 
[Add test for trac #1051
Ian Lynagh <[EMAIL PROTECTED]>**20061224125949] 
[Add test TH_dataD1 for trac #1065
Ian Lynagh <[EMAIL PROTECTED]>**20061223172536] 
[Add a test for returning Int64s through the FFI
Ian Lynagh <[EMAIL PROTECTED]>**20061222141536] 
[Fix conc063
[EMAIL PROTECTED] 
[Add test for trac #455
Ian Lynagh <[EMAIL PROTECTED]>**20061221024356] 
[fail -> broken
Ian Lynagh <[EMAIL PROTECTED]>**20061219235527] 
[fail -> broken
Ian Lynagh <[EMAIL PROTECTED]>**20061219234644] 
[whitespace change only
Ian Lynagh <[EMAIL PROTECTED]>**20061219231544] 
[fail -> broken
Ian Lynagh <[EMAIL PROTECTED]>**20061219231503] 
[fail -> broken
Ian Lynagh <[EMAIL PROTECTED]>**20061219215850] 
[indexed type: deriving indexed newtypes
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20061219212552] 
[fail -> broken
Ian Lynagh <[EMAIL PROTECTED]>**20061219203622] 
[Stop skipping tests that work
Ian Lynagh <[EMAIL PROTECTED]>**20061219195406] 
[Remove skip of ffi003 on alpha-dec-osf3 (no reason given)
Ian Lynagh <[EMAIL PROTECTED]>**20061216164552] 
[indexed types: deriving test
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20061218210544] 
[Update a readme file
Pepe Iborra <[EMAIL PROTECTED]>**20061217004749] 
[Fix a ghci.debugger test
Pepe Iborra <[EMAIL PROTECTED]>**20061217004617] 
[Go back to using $(PYTHON) rather than hardcoding python2.5
Ian Lynagh <[EMAIL PROTECTED]>**20061216154727] 
[Fix mdo test
[EMAIL PROTECTED] 
[Accept output
[EMAIL PROTECTED] 
[Improved a test
[EMAIL PROTECTED] 
[Added more tests with newtypes
[EMAIL PROTECTED] 
[More tests for the closure viewer
[EMAIL PROTECTED] 
[Accept output
[EMAIL PROTECTED] 
[Test type reconstruction in presence of newtypes
[EMAIL PROTECTED] 
[Accepted output
[EMAIL PROTECTED] 
[accept output
[EMAIL PROTECTED] 
[Advances in the test suite
[EMAIL PROTECTED] 
[Some more tests for the ghci.debugger
Pepe Iborra <[EMAIL PROTECTED]>**20060827115413] 
[GHCi.debugger tests
Pepe Iborra <[EMAIL PROTECTED]>**20060824180602] 
[indexed types: adding missing files
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20061215160008] 
[cg057 broken: trac #948. Also fix whitespace.
Ian Lynagh <[EMAIL PROTECTED]>**20061215155212] 
[Add a composes function to the driver
Ian Lynagh <[EMAIL PROTECTED]>**20061215155106] 
[Mark tests in trac #1054 as broken
Ian Lynagh <[EMAIL PROTECTED]>**20061215130656] 
[Simple2 randomly passes or fails; mark broken so we know which bug it is
Ian Lynagh <[EMAIL PROTECTED]>**20061215121729] 
[tc215 is broken: trac #366
Ian Lynagh <[EMAIL PROTECTED]>**20061215013527] 
[Accept output
Ian Lynagh <[EMAIL PROTECTED]>**20061215013411] 
[simplrun006 is broken: trac #149
Ian Lynagh <[EMAIL PROTECTED]>**20061215013213] 
[read032 is broken: trac #314
Ian Lynagh <[EMAIL PROTECTED]>**20061215013159] 
[prof001 and prof002 are broken (trac #249)
Ian Lynagh <[EMAIL PROTECTED]>**20061215011151] 
[More infrastructure for 'broken'
Ian Lynagh <[EMAIL PROTECTED]>**20061215011040] 
[Accept output
Ian Lynagh <[EMAIL PROTECTED]>**20061215005910] 
[mod174/mod175 are broken: trac bugs #414 and #437
Ian Lynagh <[EMAIL PROTECTED]>**20061215005846] 
[Fix braino
Ian Lynagh <[EMAIL PROTECTED]>**20061215005024] 
[tc175 / trac #179 fixed
Ian Lynagh <[EMAIL PROTECTED]>**20061215004506] 
[ghci016 is broken: trac #552
Ian Lynagh <[EMAIL PROTECTED]>**20061215004246] 
[Accept output; we now get info for both type and constructor
Ian Lynagh <[EMAIL PROTECTED]>**20061215003935] 
[Accept output
Ian Lynagh <[EMAIL PROTECTED]>**20061215003128] 
[ds060 and ds061 are broken: trac #322, #851
Ian Lynagh <[EMAIL PROTECTED]>**20061215002315] 
[accept output
Ian Lynagh <[EMAIL PROTECTED]>**20061215002009] 
[countReaders001 is broken - trac #629
Ian Lynagh <[EMAIL PROTECTED]>**20061215001419] 
[Set MAKEFLAGS= in recursive make call on make fast
Ian Lynagh <[EMAIL PROTECTED]>**20061215000533
 base0 was failing because of the extra noise make was generating.
] 
[Accept output
Ian Lynagh <[EMAIL PROTECTED]>**20061214235120] 
[arith011 is broken on amd64 Linux; trac #1052
Ian Lynagh <[EMAIL PROTECTED]>**20061214234903] 
[add 'broken' variant of expect_broken_if_platform
Ian Lynagh <[EMAIL PROTECTED]>**20061214234836] 
[Accept output
Ian Lynagh <[EMAIL PROTECTED]>**20061214183402] 
[Mark TH_recompile as broken
Ian Lynagh <[EMAIL PROTECTED]>**20061214183349] 
[Start ok 'broken' infrastructure
Ian Lynagh <[EMAIL PROTECTED]>**20061214183323] 
[testblockalloc: run the threaded way with -I0, so it doesn't try to GC
Simon Marlow <[EMAIL PROTECTED]>**20061214155927] 
[add test for the block allocator
Simon Marlow <[EMAIL PROTECTED]>**20061214155419] 
[add support for tests consisting of a C source file
Simon Marlow <[EMAIL PROTECTED]>**20061214155406] 
[Accept output
[EMAIL PROTECTED] 
[You can now have an MVar with a polymorphic contents
[EMAIL PROTECTED] 
[Add tc222, tests for Trac 981
[EMAIL PROTECTED] 
[Add kind-error test inspired by a message from David Roundy
[EMAIL PROTECTED] 
[Add test for Trac #1033
[EMAIL PROTECTED] 
[Add bang-pattern test
[EMAIL PROTECTED]
 
 Fixes Trac #1041
 
] 
[Check running ghci with -hide-package haskell98 works. Tests trac #1001.
Ian Lynagh <[EMAIL PROTECTED]>**20061209190118] 
[indexed types: type instance indexes my all be type variables
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20061207224216] 
[add test for #1013
Simon Marlow <[EMAIL PROTECTED]>**20061207151459] 
[indexed types: adapted two tests to omitted sigs in ATs
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20061206222005] 
[indexed types: kind sigs can be omitted from ATs
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20061206203025] 
[Accept output for tc040
[EMAIL PROTECTED] 
[Add test for typechecking lazy pattern matching 
[EMAIL PROTECTED] 
[Add test ThreadDelay001: check threadDelay sleeps as long as it is asked to
Ian Lynagh <[EMAIL PROTECTED]>**20061128204457] 
[Tests for implicit parameters, and for a specialisation bug
[EMAIL PROTECTED] 
[Remove control-Ms
[EMAIL PROTECTED] 
[Skip out lots of the middle numbers in cg058 as the test was taking too long
Ian Lynagh <[EMAIL PROTECTED]>**20061124001809
 The test still shows up the problem in hugs.
] 
[Test that deriving Data does not get confused with z-encoding
[EMAIL PROTECTED] 
[Add tcfail171
[EMAIL PROTECTED] 
[Tests for Trac #289
[EMAIL PROTECTED] 
[Add two GADT tests for Trac #301, fixed by implication constraints
[EMAIL PROTECTED] 
[New GADT tests, looking at interaction with type classes
[EMAIL PROTECTED] 
[Accept output
[EMAIL PROTECTED] 
[Add the Faxen test for completeness of type inference
[EMAIL PROTECTED] 
[Two new typechecker tests that exploit implication constraints
[EMAIL PROTECTED] 
[Add 64-bit stdout for simplrun007
Ian Lynagh <[EMAIL PROTECTED]>**20061120141304] 
[Add tests for bitshift PrelRules
Samuel Bronson <[EMAIL PROTECTED]>**20061116142723] 
[getDirContents001 hp2ps testing fix
Ravi Nanavati <[EMAIL PROTECTED]>**20060928205710
 
 This tweaks the getDirContents001 testcase to ignore the .ps and .aux files
 that might be generated by hp2ps if testing of hp2ps via GhostScript is 
 enabled. Please include in the 6.6 branch as well as HEAD.
 
] 
[add tests for heap profiles and hp2ps
[EMAIL PROTECTED] 
[Add test for trac #953: panic in ghci for lseek ffi import statement
Ian Lynagh <[EMAIL PROTECTED]>**20061112162606] 
[Remove "Arbitrary (Maybe a)" instances to track changes in QuickCheck
Ian Lynagh <[EMAIL PROTECTED]>**20061112141944] 
[Add tests for Data.List.intercalate (ticket #971)
Josef Svenningsson <[EMAIL PROTECTED]>**20061102122958] 
[test rotates larger than the wordsize
Simon Marlow <[EMAIL PROTECTED]>**20061107094606] 
[Add test for unused imports
[EMAIL PROTECTED] 
[Added tests for Data.List.intercalate and split
Josef Svenningsson <[EMAIL PROTECTED]>*-20061022135817] 
[Add test for unused imports
[EMAIL PROTECTED] 
[Add test for Trac #963
[EMAIL PROTECTED] 
[Add a simple coverage-condition test
[EMAIL PROTECTED] 
[Add test for Trac 958
[EMAIL PROTECTED] 
[Added tests for Data.List.intercalate and split
Josef Svenningsson <[EMAIL PROTECTED]>**20061022135817] 
[removing .tix files before running tests
[EMAIL PROTECTED] 
[Adding a new way for hpc
[EMAIL PROTECTED] 
[indexed types: small tests covering important cases
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20061023005347] 
[indexed types: GMap tests
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20061022203334] 
[indexed types: import/export test
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20061022182045] 
[indexed types: multi-module overlap check
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20061022180131] 
[Partitioned indexed-types tests into fail/compile/run dirs
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20061022174019] 
[Add test ds061 for trac #851 (incomplete pattern warnings wrong with n+k pats)
Ian Lynagh <[EMAIL PROTECTED]>**20061021153928] 
[Add test tc216 for trac #816 (fundep undecidable-instances typechecking loop)
Ian Lynagh <[EMAIL PROTECTED]>**20061021120628] 
[Add test gadt20 for trac #810 (GHC fails to find GADT instances)
Ian Lynagh <[EMAIL PROTECTED]>**20061021020142] 
[Add test getEnvironment01 for trac #781 (check getEnvironment doesn't break)
Ian Lynagh <[EMAIL PROTECTED]>**20061020215050] 
[Add test tcfail168 for trac #719 (error messages are too long sometimes)
Ian Lynagh <[EMAIL PROTECTED]>**20061020191818] 
[Add test countReaders001 for trac #629 (file locking doesn't count readers)
Ian Lynagh <[EMAIL PROTECTED]>**20061020165449] 
[Add test ghci016 for trac #552 (ghci doesn't handle defaults correctly).
Ian Lynagh <[EMAIL PROTECTED]>**20061020153239] 
[Add test TH_recompile for trac #481 (Recompilation check fails for TH)
Ian Lynagh <[EMAIL PROTECTED]>**20061020145617] 
[Add test mod175 for trac 437 (Recompilation check should include flags)
Ian Lynagh <[EMAIL PROTECTED]>**20061020140355] 
[Add test mod174 for trac #414 (GHC does not enforce that Main exports main)
Ian Lynagh <[EMAIL PROTECTED]>**20061020131224] 
[Tests for trac #366 (incomplete pattern warnings and GADTs)
Ian Lynagh <[EMAIL PROTECTED]>**20061019182440] 
[Add test ds060 for trac #322 (bogus overlapping patterns warnings)
Ian Lynagh <[EMAIL PROTECTED]>**20061019163244] 
[Update comments in test tcfail132
Ian Lynagh <[EMAIL PROTECTED]>**20061019155000] 
[Add a test for trac #314 (#line pragmas not respected inside nested comments)
Ian Lynagh <[EMAIL PROTECTED]>**20061019154907] 
[Update module tests slightly
[EMAIL PROTECTED] 
[Test for Trac #940
[EMAIL PROTECTED] 
[Add tests for trac#249 and #931
Ian Lynagh <[EMAIL PROTECTED]>**20061013151233] 
[Add test for correct unlitting. Tests trac #210.
Ian Lynagh <[EMAIL PROTECTED]>**20061013131602] 
[Allow literate tests
Ian Lynagh <[EMAIL PROTECTED]>**20061013131542] 
[Update bug reference for test tc175
Ian Lynagh <[EMAIL PROTECTED]>**20061013123021] 
[Test for #149 (missed CSE opportunity)
Ian Lynagh <[EMAIL PROTECTED]>**20061012200213] 
[Test for trac #921
Ian Lynagh <[EMAIL PROTECTED]>**20061011135910] 
[Fix test base01
Ian Lynagh <[EMAIL PROTECTED]>**20061010102524] 
[STM invariants
[EMAIL PROTECTED] 
[Add a test for 'module M' in export lists
[EMAIL PROTECTED] 
[Test for scoped type variables
[EMAIL PROTECTED] 
[Test separate compilation with indexed types
Roman Leshchinskiy <[EMAIL PROTECTED]>**20061005081706] 
[Two new tricky deriving tests
[EMAIL PROTECTED] 
[Add test for Trac #919
[EMAIL PROTECTED] 
[Need -fglasgow-exts for gadt18
Ian Lynagh <[EMAIL PROTECTED]>**20060924171441] 
[Allow testsuite to run under MSYS/MinGW using native Python (not Cygwin Python).
[EMAIL PROTECTED]
 This patch is based on a similar one "Enable timeout in Windows
 and don't require cygwin python" by Esa Ilari Vuokko. It seems
 like timeout is always built on Windows so I rearranged the logic
 there to make the code clearer, Esa's patch required the user to
 uncomment the MinGW-specific logic in order for it to work; this
 patch does not have the MinGW-specific logic commented out.
 
 I tested this on the trunk in Ubuntu 6.06 on i686 (VMWare).
 I tested this on the trunk and ghc-6.6 branch on Windows i686.
 
] 
[accept output
Simon Marlow <[EMAIL PROTECTED]>**20060929101912] 
[add test for #906
Simon Marlow <[EMAIL PROTECTED]>**20060928145539] 
[add test for #830
Simon Marlow <[EMAIL PROTECTED]>**20060928145442] 
[Add a test for trac #867
Ian Lynagh <[EMAIL PROTECTED]>**20060927225225] 
[A new GADT test, which killed FC temporarily
[EMAIL PROTECTED] 
[Test for problem with compiling the base package with --make
Ian Lynagh <[EMAIL PROTECTED]>**20060926205447] 
[Added drv020, a test for newtype deriving of multi-parameter type classes which currently makes HEAD panic.
[EMAIL PROTECTED]
 It is called drv020 in order not to clash with some yet to be pushed test cases for stand-alone deriving.
] 
[Add another GADT test
[EMAIL PROTECTED] 
[Accept typechecker output
[EMAIL PROTECTED] 
[Add new sub-directory indexed-types to the GHC testsuite
[EMAIL PROTECTED] 
[Add test for Hugs #37
[EMAIL PROTECTED] 
[Make it so that 'make boot' is optional in the testsuite
Simon Marlow <[EMAIL PROTECTED]>**20060916075035
 mk/wordsize.mk and timeout/timeout get built automatically if necessary.
] 
[add boot to the all target
Simon Marlow <[EMAIL PROTECTED]>**20060916071047] 
[add 'make boot' to the instructions
Simon Marlow <[EMAIL PROTECTED]>**20060916071026] 
[Add a test for impredicative polymorphism
[EMAIL PROTECTED] 
[Add test for Trac #900
[EMAIL PROTECTED] 
[Tests for impredicative polymorphism
[EMAIL PROTECTED] 
[Add another type checker test
[EMAIL PROTECTED] 
[Add GADT test from Doaitse
[EMAIL PROTECTED] 
[Added test for ticket #902, deriving for GADTs which declare H98 types fails.
[EMAIL PROTECTED] 
[Fix up tests for unboxed tuples
[EMAIL PROTECTED] 
[Accept output on sparc-sun-solaris2
Roman Leshchinskiy <[EMAIL PROTECTED]>**20060907083310] 
[Add stdout for expfloat test
Ian Lynagh <[EMAIL PROTECTED]>**20060910150353] 
[Catch exceptions while cleaning rather than checking for existence first
Ian Lynagh <[EMAIL PROTECTED]>**20060910145957
 As well as being generally a good idea, os.access('foo') seems to return
 true if foo.exe exists on Windows.
] 
[Add cleaning for .exe files
Ian Lynagh <[EMAIL PROTECTED]>**20060910144741] 
[Test expFloat# linking
Ian Lynagh <[EMAIL PROTECTED]>**20060910133339] 
[More cleaning tidyups
Ian Lynagh <[EMAIL PROTECTED]>**20060908215102] 
[Update the testsuite cleaning
Ian Lynagh <[EMAIL PROTECTED]>**20060908130210] 
[update bytestring tests 
Don Stewart <[EMAIL PROTECTED]>**20060909111806] 
[Fix another use of result type signatures (this one was easy)
[EMAIL PROTECTED] 
[Alter source code of test, now that result type signatures do not bind type variables
[EMAIL PROTECTED] 
[Improved error locations
[EMAIL PROTECTED] 
[Add test for Trac 877
[EMAIL PROTECTED] 
[Accept output
[EMAIL PROTECTED] 
[Use a python timeout for the testsuite when we don't have a threaded RTS
Ian Lynagh <[EMAIL PROTECTED]>**20060907113001] 
[Use Data.Map instead of Data.FiniteMap
[EMAIL PROTECTED] 
[More changes for scoped type variables
[EMAIL PROTECTED] 
[Revise tc103, in the light of the story for result type signatures
[EMAIL PROTECTED] 
[Accept output for ! kind
[EMAIL PROTECTED]
 
 I'm not entirely sure of this bang-kind stuff, but in so far as it works
 at all, this test is fine.  I guess I should look at the bang-kind stuff
 again, as soon as the FC branch becomes the HEAD
 
] 
[Fix this test on a fast machine
Simon Marlow <[EMAIL PROTECTED]>**20060907083932
 The artificial loop wasn't running for long enough for a context
 switch to happen, so the finalizer wasn't getting to run early enough.
] 
[Tickle a bug in impredicative polymorphism
[EMAIL PROTECTED] 
[Update output
[EMAIL PROTECTED] 
[Accept output
[EMAIL PROTECTED]
 
 These error messages (to do with failure in higher-rank situations)
 are different, but probably no worse than before.
 
] 
[Add renamer test (qualified name in binding position)
[EMAIL PROTECTED] 
[accept output
Simon Marlow <[EMAIL PROTECTED]>**20060905090412] 
[Add test for dependency analysis in type checking
[EMAIL PROTECTED] 
[improve conc039 a little bit, and omit it for threaded1
Simon Marlow <[EMAIL PROTECTED]>**20060905082828] 
[omit conc036(threaded2)
Simon Marlow <[EMAIL PROTECTED]>**20060904150015] 
[win-specific output not needed
Simon Marlow <[EMAIL PROTECTED]>**20060901150449] 
[leave EXTRA_HC_OPTS for use on the command line
Simon Marlow <[EMAIL PROTECTED]>**20060901135822] 
[fix for Windows
Simon Marlow <[EMAIL PROTECTED]>**20060831132332] 
[add conc059
Simon Marlow <[EMAIL PROTECTED]>**20060831090349] 
[accept
Simon Marlow <[EMAIL PROTECTED]>**20060831085057] 
[fix up tests for Windows
Simon Marlow <[EMAIL PROTECTED]>**20060830144428
 threadDelay is not interruptible on Windows with the threaded RTS.
 Work around it in conc014, conc015 and conc017, and add a new test for
 this specific failure, and mark it as an expected failure for the
 relevant cases.
] 
[adapt these to work on Windows
Simon Marlow <[EMAIL PROTECTED]>**20060830121158] 
[add skip_if_platform
Simon Marlow <[EMAIL PROTECTED]>**20060830121121] 
[skip conc053 on Windows (registerDelay not supported)
Simon Marlow <[EMAIL PROTECTED]>**20060830120949] 
[USETHREADS=0 by default unless you set THREADS explicitly
Simon Marlow <[EMAIL PROTECTED]>**20060830122306
 This means the testsuite works by default even if you have Python 2.2,
 but will fail with Python 2.2 if you set THREADS.
] 
[Add a test for length not causing a stack overflow (from #876)
Ian Lynagh <[EMAIL PROTECTED]>**20060829224845] 
[Add list002 to tests - seems to have got lost during the testsuite revamp
Ian Lynagh <[EMAIL PROTECTED]>**20060829224345] 
[Allow threading to be completely disabled with USETHREADS=0
Ian Lynagh <[EMAIL PROTECTED]>**20060829144159
 I had to pull the global classes and instances out into their own module
 as there was a catch-22: testlib needed to know if threading was enabled,
 but we don't know that until we have gone through the argument, but going
 through the arguments required changing things like config in testlib.
] 
[Clean .hp files
Ian Lynagh <[EMAIL PROTECTED]>**20060829124729] 
[Allow the timeout to be given as a Makefile argument
Ian Lynagh <[EMAIL PROTECTED]>**20060829124359] 
[omit conc023 the non-threaded ways on Windows (see comment)
Simon Marlow <[EMAIL PROTECTED]>*-20060829135821] 
[omit conc023 the non-threaded ways on Windows (see comment)
Simon Marlow <[EMAIL PROTECTED]>**20060829135821] 
[ds052 not an expected failure any more
Simon Marlow <[EMAIL PROTECTED]>**20060825150430] 
[update FFI syntax
Simon Marlow <[EMAIL PROTECTED]>**20060825145839] 
[fix FFI syntax
Simon Marlow <[EMAIL PROTECTED]>**20060825134227] 
[fix parse error
Simon Marlow <[EMAIL PROTECTED]>**20060825133909] 
[cg025 needs regex-compat
Simon Marlow <[EMAIL PROTECTED]>**20060825133349] 
[Don't use the threaded2 way when we don't support SMP
Ian Lynagh <[EMAIL PROTECTED]>**20060825004042] 
[fix old regex test, add two new ones
Simon Marlow <[EMAIL PROTECTED]>**20060824140622] 
[Fix typo
Esa Ilari Vuokko <[EMAIL PROTECTED]>**20060823202055] 
[update tests
Don Stewart <[EMAIL PROTECTED]>**20060823155147] 
[Driver: Add THREADS-support
Esa Ilari Vuokko <[EMAIL PROTECTED]>**20060822213145] 
[Fix some THREADED-caused fails
Esa Ilari Vuokko <[EMAIL PROTECTED]>**20060821230831] 
[Fix driver not to normalise output when using platform specific output files
Esa Ilari Vuokko <[EMAIL PROTECTED]>**20060813124649] 
[accept output
Simon Marlow <[EMAIL PROTECTED]>**20060823092224] 
[add test for Data/Fixed module, in libraries folder
Ashley Yakeley <[EMAIL PROTECTED]>**20060823073948] 
[accept output
Simon Marlow <[EMAIL PROTECTED]>**20060822102811] 
[accept output (improvements)
Simon Marlow <[EMAIL PROTECTED]>**20060822102609] 
[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:
e4fd0ee100567d061fb6802274dc574a7ac7f902
-----BEGIN PGP SIGNATURE-----
Version: GnuPG v1.4.5 (GNU/Linux)

iD8DBQFGHio/p7ZNUfdma/8RAmZAAJ4zlTpPzetlVqrWAF5Rp5utrk6cDACgqEax
vsvYTqpzfxqdPYLzyTl3OTM=
=/yH6
-----END PGP SIGNATURE-----
_______________________________________________
Cvs-ghc mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to