Tue May 8 18:12:38 EDT 2007 Isaac Dupree <[EMAIL PROTECTED]>
* Add tests for -fwarn-implicit-prelude (and -fwarn-unused-imports along with
it) (trac #1317)
New patches:
[Add tests for -fwarn-implicit-prelude (and -fwarn-unused-imports along with
it) (trac #1317)
Isaac Dupree <[EMAIL PROTECTED]>**20070508221238] {
hunk ./tests/ghc-regress/rename/should_compile/all.T 65
+test('rn055', normal, compile, [''])
+test('rn056', normal, compile, [''])
+test('rn057', normal, compile, [''])
addfile ./tests/ghc-regress/rename/should_compile/rn055.hs
hunk ./tests/ghc-regress/rename/should_compile/rn055.hs 1
+{-# OPTIONS_GHC -fwarn-implicit-prelude -fwarn-unused-imports #-}
+module ShouldCompile where
+
+-- !!! should produce warnings about implicitly imported Prelude
+-- (but not about the implicit import being unused)
+
addfile ./tests/ghc-regress/rename/should_compile/rn055.stderr-ghc
hunk ./tests/ghc-regress/rename/should_compile/rn055.stderr-ghc 1
+
+rn055.hs:1:0: Warning: Module `Prelude' implicitly imported
addfile ./tests/ghc-regress/rename/should_compile/rn056.hs
hunk ./tests/ghc-regress/rename/should_compile/rn056.hs 1
+{-# OPTIONS_GHC -fwarn-implicit-prelude -fwarn-unused-imports #-}
+module ShouldCompile where
+
+import Prelude ()
+
+-- !!! should produce no warnings
+-- (the other use of importing nothing is
+-- to nullify the implicit import of the Prelude)
+
addfile ./tests/ghc-regress/rename/should_compile/rn056.stderr
addfile ./tests/ghc-regress/rename/should_compile/rn057.hs
hunk ./tests/ghc-regress/rename/should_compile/rn057.hs 1
+{-# OPTIONS_GHC -fwarn-implicit-prelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
+module ShouldCompile where
+
+-- !!! should produce no warning
+
addfile ./tests/ghc-regress/rename/should_compile/rn057.stderr
}
Context:
[FIX #1159: This test needs to run in a subthread (see comments)
Simon Marlow <[EMAIL PROTECTED]>**20070508130950]
[add test for #1227
Simon Marlow <[EMAIL PROTECTED]>**20070508105325]
[add test for #1253
Simon Marlow <[EMAIL PROTECTED]>**20070507132429]
[add test for #1091
Simon Marlow <[EMAIL PROTECTED]>**20070507113903]
[add basic concurrency/IO test: tests that stdin is non-blocking
Simon Marlow <[EMAIL PROTECTED]>**20070507124521]
[platform-specific output no longer required
Simon Marlow <[EMAIL PROTECTED]>**20070417080859]
[Add a test that 'ghc -e "return ()"' returns successfully
Ian Lynagh <[EMAIL PROTECTED]>**20070506113229]
[Arrow tests are failing core lint; trac #1333
Ian Lynagh <[EMAIL PROTECTED]>**20070505190414]
[sed-o in the testsuite driver
Ian Lynagh <[EMAIL PROTECTED]>**20070505190353]
[dsrun014 is broken (trac #1257, Bytecode generator can't handle unboxed tuples)
Ian Lynagh <[EMAIL PROTECTED]>**20070505172037]
[tc224 (overloaded strings) is broken; trac #1332
Ian Lynagh <[EMAIL PROTECTED]>**20070505161813]
[Various indexed types tests fail due to trac #1331
Ian Lynagh <[EMAIL PROTECTED]>**20070505155605]
[Accept output (mdofail004)
Ian Lynagh <[EMAIL PROTECTED]>**20070505153527]
[Church2 is broken; trac #1330
Ian Lynagh <[EMAIL PROTECTED]>**20070505152441]
[Accept output
Ian Lynagh <[EMAIL PROTECTED]>**20070505150128]
[Accept output
Ian Lynagh <[EMAIL PROTECTED]>**20070505123344]
[Accept output
Ian Lynagh <[EMAIL PROTECTED]>**20070505120131]
[Add output
Ian Lynagh <[EMAIL PROTECTED]>**20070505115657]
[Accept output
Ian Lynagh <[EMAIL PROTECTED]>**20070505114604]
[Partially accept output
Ian Lynagh <[EMAIL PROTECTED]>**20070505113746]
[Accept output
Ian Lynagh <[EMAIL PROTECTED]>**20070505113048]
[Accept output for tcfail004
Ian Lynagh <[EMAIL PROTECTED]>**20070505105852]
[Track ... pretty-printer changes
Ian Lynagh <[EMAIL PROTECTED]>**20070505105355]
[stm is no longer a corelib, so needs to be reqlib'ed now
Ian Lynagh <[EMAIL PROTECTED]>**20070505004835]
[Don't dump stderr/stdout before we've split the ghci output
Ian Lynagh <[EMAIL PROTECTED]>**20070505004802
Fixes some framework failures.
]
[Fix spec001 test
Ian Lynagh <[EMAIL PROTECTED]>**20070505001103]
[Accept output
Ian Lynagh <[EMAIL PROTECTED]>**20070505000818]
[Accept output
Ian Lynagh <[EMAIL PROTECTED]>**20070504235810]
[maessen_hashtab needs QuickCheck
Ian Lynagh <[EMAIL PROTECTED]>**20070504235518]
[regex tests need regex-posix, which is no longer a corelib
Ian Lynagh <[EMAIL PROTECTED]>**20070504232505]
[Fix comment
Ian Lynagh <[EMAIL PROTECTED]>**20070504230405]
[skip cabal02 (cabal-setup isn't in the GHC tree any more)
Ian Lynagh <[EMAIL PROTECTED]>**20070504220048]
[Don't hardcode the version of base in the tests
Ian Lynagh <[EMAIL PROTECTED]>**20070504215708]
[Accept output for tcfail005
Ian Lynagh <[EMAIL PROTECTED]>**20070504092957]
[cg025 requires regex-compat, which is now an extralib
Ian Lynagh <[EMAIL PROTECTED]>**20070503225622]
[Test for Trac #1251
[EMAIL PROTECTED]
[Add test for Trac #1323
[EMAIL PROTECTED]
[Revert mistaken change to all.T
[EMAIL PROTECTED]
[Use letters to allow output to be matched up with the code more easily
Ian Lynagh <[EMAIL PROTECTED]>**20070503192604]
[Remove redundant arch-specific test files
Ian Lynagh <[EMAIL PROTECTED]>**20070503192139]
[Accept output
Ian Lynagh <[EMAIL PROTECTED]>**20070503191615]
[update: we give a diagnostic for an incorrect number in :delete now
Simon Marlow <[EMAIL PROTECTED]>**20070503151724]
[add a history test
Simon Marlow <[EMAIL PROTECTED]>**20070503151700]
[add a :list test
Simon Marlow <[EMAIL PROTECTED]>**20070503150446]
[add a test to demonstrate a new bug
Simon Marlow <[EMAIL PROTECTED]>**20070503131223]
[accept output
Simon Marlow <[EMAIL PROTECTED]>**20070503094206]
[add correct output now this test is fixed
Simon Marlow <[EMAIL PROTECTED]>**20070430110058]
[Add test for Trac #1255
[EMAIL PROTECTED]
[Add test for records and type families
[EMAIL PROTECTED]
[Accept output
Pepe Iborra <[EMAIL PROTECTED]>**20070430171655]
[Adapt some breakpoint tests to the new command syntax
Pepe Iborra <[EMAIL PROTECTED]>**20070430171643]
[add test for a new assertion failure
Simon Marlow <[EMAIL PROTECTED]>**20070427144739]
[modify test to reproduce a new bug
Simon Marlow <[EMAIL PROTECTED]>**20070426153744]
[add another test, and accept some output
Simon Marlow <[EMAIL PROTECTED]>**20070426152639]
[Fix the test I just added
Pepe Iborra <[EMAIL PROTECTED]>**20070426101615
:break qsort sets a breakpoint in the outer expression, before any variable
has been bound. Once you :step the things are bound
]
[Added a :break test
Pepe Iborra <[EMAIL PROTECTED]>**20070426085538]
[Disable the monomorphism restriction warnings in all tests
Pepe Iborra <[EMAIL PROTECTED]>**20070426084918]
[Accept output
Pepe Iborra <[EMAIL PROTECTED]>**20070425175248]
[add some :show bindings
Simon Marlow <[EMAIL PROTECTED]>**20070425130058]
[add test for a new bug
Simon Marlow <[EMAIL PROTECTED]>**20070425130031]
[this test requires an extra :step now
Simon Marlow <[EMAIL PROTECTED]>**20070425125920]
[New test covering bug discovered by Nicolas Frisby in TcUnify.boxySplitTyConApp
[EMAIL PROTECTED]
[move some dynbrk tests into the scripts/ directory
Simon Marlow <[EMAIL PROTECTED]>**20070423152829]
[add dynbrk tests, and a few more breakpoint tests
Simon Marlow <[EMAIL PROTECTED]>**20070423152031]
[Adapt commands to the new ghci debugger command-set
Pepe Iborra <[EMAIL PROTECTED]>**20070420170414]
[Accept output
Pepe Iborra <[EMAIL PROTECTED]>**20070420170311]
[Add test suggested by Doaitse Swierestra
[EMAIL PROTECTED]
[Update output
Ian Lynagh <[EMAIL PROTECTED]>**20070417151616]
[Add a test for use of fail for trac #1265
Tyson Whitehead <[EMAIL PROTECTED]>**20070410140653]
[Differentiate between use of fail and failure of code (i.e., an exception is
thrown)
Tyson Whitehead <[EMAIL PROTECTED]>**20070410140308]
[Use $(PYTHON) rather than assuming python will find it
Ian Lynagh <[EMAIL PROTECTED]>**20070417130516]
[Generate conc068 input in a more portable manner
Thorkil Naur <[EMAIL PROTECTED]>**20070417063754
The earlier method with 'yes .. | head ..' does not work on PPC Mac OS X.
]
[TAG 2007-04-17
Ian Lynagh <[EMAIL PROTECTED]>**20070417125057]
Patch bundle hash:
fea772bb4ec3b90cf9b31576ef1892ec5a726c97
_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc