Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/1ecf2598f256d44daa8face3a774edf691ff7f6a

>---------------------------------------------------------------

commit 1ecf2598f256d44daa8face3a774edf691ff7f6a
Author: Simon Peyton Jones <[email protected]>
Date:   Sat Jun 11 15:05:43 2011 +0100

    Test Trac #5211

>---------------------------------------------------------------

 tests/ghc-regress/rename/should_fail/T5211.hs     |   16 ++++++++++++++++
 tests/ghc-regress/rename/should_fail/T5211.stderr |    5 +++++
 tests/ghc-regress/rename/should_fail/all.T        |    1 +
 3 files changed, 22 insertions(+), 0 deletions(-)

diff --git a/tests/ghc-regress/rename/should_fail/T5211.hs 
b/tests/ghc-regress/rename/should_fail/T5211.hs
new file mode 100644
index 0000000..2d0e69a
--- /dev/null
+++ b/tests/ghc-regress/rename/should_fail/T5211.hs
@@ -0,0 +1,16 @@
+{-# OPTIONS_GHC -fwarn-unused-imports  #-}
+module RedundantImport where
+
+-- this import is redundant, but GHC does not spot it
+import qualified Foreign.Storable 
+
+import Foreign.Storable (Storable, sizeOf, alignment, peek, poke, )
+import Foreign.Ptr (castPtr, )
+
+newtype T a = Cons a
+
+instance Storable a => Storable (T a) where
+   sizeOf (Cons a) = sizeOf a
+   alignment (Cons a) = alignment a
+   peek = fmap Cons . peek . castPtr
+   poke p (Cons a) = poke (castPtr p) a
diff --git a/tests/ghc-regress/rename/should_fail/T5211.stderr 
b/tests/ghc-regress/rename/should_fail/T5211.stderr
new file mode 100644
index 0000000..a33a027
--- /dev/null
+++ b/tests/ghc-regress/rename/should_fail/T5211.stderr
@@ -0,0 +1,5 @@
+
+T5211.hs:5:1:
+    Warning: The import of `Foreign.Storable' is redundant
+               except perhaps to import instances from `Foreign.Storable'
+             To import instances alone, use: import Foreign.Storable()
diff --git a/tests/ghc-regress/rename/should_fail/all.T 
b/tests/ghc-regress/rename/should_fail/all.T
index 02d0ec7..40fca63 100644
--- a/tests/ghc-regress/rename/should_fail/all.T
+++ b/tests/ghc-regress/rename/should_fail/all.T
@@ -79,3 +79,4 @@ test('T4042', normal, compile_fail, [''])
 
 test('mc13', normal, compile_fail, [''])
 test('mc14', normal, compile_fail, [''])
+test('T5211', normal, compile, [''])  # Warnings only



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

Reply via email to