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

On branch  : ghc-7.2

http://hackage.haskell.org/trac/ghc/changeset/490f64f739d08bb676680c0279cb8566328dd948

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

commit 490f64f739d08bb676680c0279cb8566328dd948
Author: Ian Lynagh <[email protected]>
Date:   Thu Aug 4 15:56:50 2011 +0100

    Test Trac #5372
    
    and update output for T2901
    
    Conflicts:
    
        tests/rename/should_fail/all.T

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

 tests/rename/should_fail/T2901.stderr |    3 +--
 tests/rename/should_fail/T5372.hs     |    4 ++++
 tests/rename/should_fail/T5372.stderr |    6 ++++++
 tests/rename/should_fail/T5372a.hs    |    2 ++
 tests/rename/should_fail/all.T        |    4 ++++
 5 files changed, 17 insertions(+), 2 deletions(-)

diff --git a/tests/rename/should_fail/T2901.stderr 
b/tests/rename/should_fail/T2901.stderr
index 7b3e9d5..8cf5b2f 100644
--- a/tests/rename/should_fail/T2901.stderr
+++ b/tests/rename/should_fail/T2901.stderr
@@ -1,5 +1,4 @@
 
 T2901.hs:6:5: Not in scope: data constructor `F.Foo'
 
-T2901.hs:6:13:
-    `F.field' is not a (visible) field of constructor `Foo'
+T2901.hs:6:13: `F.field' is not a (visible) constructor field name
diff --git a/tests/rename/should_fail/T5372.hs 
b/tests/rename/should_fail/T5372.hs
new file mode 100644
index 0000000..b0f5906
--- /dev/null
+++ b/tests/rename/should_fail/T5372.hs
@@ -0,0 +1,4 @@
+{-# LANGUAGE DisambiguateRecordFields #-}  
+module T5372 where  
+import qualified T5372a  
+notScope (MkS { x = n }) = n  
diff --git a/tests/rename/should_fail/T5372.stderr 
b/tests/rename/should_fail/T5372.stderr
new file mode 100644
index 0000000..47e50dc
--- /dev/null
+++ b/tests/rename/should_fail/T5372.stderr
@@ -0,0 +1,6 @@
+
+T5372.hs:4:11:
+    Not in scope: data constructor `MkS'
+    Perhaps you meant `T5372a.MkS' (imported from T5372a)
+
+T5372.hs:4:17: `x' is not a (visible) constructor field name
diff --git a/tests/rename/should_fail/T5372a.hs 
b/tests/rename/should_fail/T5372a.hs
new file mode 100644
index 0000000..054f8c8
--- /dev/null
+++ b/tests/rename/should_fail/T5372a.hs
@@ -0,0 +1,2 @@
+module T5372a where
+data S = MkS { x :: Int, y :: Bool }
diff --git a/tests/rename/should_fail/all.T b/tests/rename/should_fail/all.T
index 78d35ce..c8c93b2 100644
--- a/tests/rename/should_fail/all.T
+++ b/tests/rename/should_fail/all.T
@@ -81,3 +81,7 @@ test('mc13', normal, compile_fail, [''])
 test('mc14', normal, compile_fail, [''])
 test('T5211', normal, compile, [''])  # Warnings only
 test('T1595a', normal, compile_fail, [''])
+test('T5372',
+     extra_clean(['T5372a.hi', 'T5372a.o']),
+     multimod_compile_fail,
+     ['T5372','-v0'])



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

Reply via email to