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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/ff4263ede1a3e9f01048c37b1b8481a33929528c

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

commit ff4263ede1a3e9f01048c37b1b8481a33929528c
Author: Ian Lynagh <[email protected]>
Date:   Tue Sep 27 13:46:43 2011 +0100

    Add tests for NoTraditionalRecordSyntax

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

 tests/parser/should_fail/all.T                     |    4 ++++
 .../should_fail/readFailTraditionalRecords1.hs     |    6 ++++++
 .../should_fail/readFailTraditionalRecords1.stderr |    3 +++
 .../should_fail/readFailTraditionalRecords2.hs     |    7 +++++++
 .../should_fail/readFailTraditionalRecords2.stderr |    3 +++
 .../should_fail/readFailTraditionalRecords3.hs     |    6 ++++++
 .../should_fail/readFailTraditionalRecords3.stderr |    3 +++
 7 files changed, 32 insertions(+), 0 deletions(-)

diff --git a/tests/parser/should_fail/all.T b/tests/parser/should_fail/all.T
index 31ec0d9..65fba07 100644
--- a/tests/parser/should_fail/all.T
+++ b/tests/parser/should_fail/all.T
@@ -69,3 +69,7 @@ test('T3811f', normal, compile_fail, [''])
 test('T3811g', normal, compile_fail, [''])
 test('NoDoAndIfThenElse', normal, compile_fail, [''])
 test('NondecreasingIndentationFail', normal, compile_fail, [''])
+test('readFailTraditionalRecords1', normal, compile_fail, [''])
+test('readFailTraditionalRecords2', normal, compile_fail, [''])
+test('readFailTraditionalRecords3', normal, compile_fail, [''])
+
diff --git a/tests/parser/should_fail/readFailTraditionalRecords1.hs 
b/tests/parser/should_fail/readFailTraditionalRecords1.hs
new file mode 100644
index 0000000..bde5527
--- /dev/null
+++ b/tests/parser/should_fail/readFailTraditionalRecords1.hs
@@ -0,0 +1,6 @@
+
+{-# LANGUAGE NoTraditionalRecordSyntax #-}
+
+module ReadFailTraditionalRecords1 where
+
+data Foo = Foo { i :: Int }
diff --git a/tests/parser/should_fail/readFailTraditionalRecords1.stderr 
b/tests/parser/should_fail/readFailTraditionalRecords1.stderr
new file mode 100644
index 0000000..34887ef
--- /dev/null
+++ b/tests/parser/should_fail/readFailTraditionalRecords1.stderr
@@ -0,0 +1,3 @@
+
+readFailTraditionalRecords1.hs:6:16:
+    Illegal record syntax (use -XTraditionalRecordSyntax): {i :: Int}
diff --git a/tests/parser/should_fail/readFailTraditionalRecords2.hs 
b/tests/parser/should_fail/readFailTraditionalRecords2.hs
new file mode 100644
index 0000000..bf67863
--- /dev/null
+++ b/tests/parser/should_fail/readFailTraditionalRecords2.hs
@@ -0,0 +1,7 @@
+
+{-# LANGUAGE NoTraditionalRecordSyntax #-}
+
+module ReadFailTraditionalRecords2 where
+
+f (Foo { i = j }) = j
+
diff --git a/tests/parser/should_fail/readFailTraditionalRecords2.stderr 
b/tests/parser/should_fail/readFailTraditionalRecords2.stderr
new file mode 100644
index 0000000..a2d6bb3
--- /dev/null
+++ b/tests/parser/should_fail/readFailTraditionalRecords2.stderr
@@ -0,0 +1,3 @@
+
+readFailTraditionalRecords2.hs:6:4:
+    Illegal record syntax (use -XTraditionalRecordSyntax): Foo {i = j}
diff --git a/tests/parser/should_fail/readFailTraditionalRecords3.hs 
b/tests/parser/should_fail/readFailTraditionalRecords3.hs
new file mode 100644
index 0000000..3d9c6e7
--- /dev/null
+++ b/tests/parser/should_fail/readFailTraditionalRecords3.hs
@@ -0,0 +1,6 @@
+
+{-# LANGUAGE NoTraditionalRecordSyntax #-}
+
+module ReadFailTraditionalRecords3 where
+
+f x = x { i = 3 }
diff --git a/tests/parser/should_fail/readFailTraditionalRecords3.stderr 
b/tests/parser/should_fail/readFailTraditionalRecords3.stderr
new file mode 100644
index 0000000..678486d
--- /dev/null
+++ b/tests/parser/should_fail/readFailTraditionalRecords3.stderr
@@ -0,0 +1,3 @@
+
+readFailTraditionalRecords3.hs:6:7:
+    Illegal record syntax (use -XTraditionalRecordSyntax): x {i = 3}



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

Reply via email to