Repository : ssh://darcs.haskell.org//srv/darcs/packages/base

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/480b755a8397e75b6d58992664ab42c8ff0e1907

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

commit 480b755a8397e75b6d58992664ab42c8ff0e1907
Author: Ian Lynagh <[email protected]>
Date:   Thu Mar 1 13:42:25 2012 +0000

    Rename lexNum test to lex001, and expand it

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

 tests/all.T         |    2 +-
 tests/lex001.hs     |   39 +++++++++++++++++++++++
 tests/lex001.stdout |   84 +++++++++++++++++++++++++++++++++++++++++++++++++++
 tests/lexNum.hs     |   28 -----------------
 tests/lexNum.stdout |   17 ----------
 5 files changed, 124 insertions(+), 46 deletions(-)

diff --git a/tests/all.T b/tests/all.T
index c7f9e7f..4b7d905 100644
--- a/tests/all.T
+++ b/tests/all.T
@@ -19,7 +19,7 @@ test('unicode002',
 test('data-fixed-show-read', normal, compile_and_run, [''])
 test('showDouble', normal, compile_and_run, [''])
 test('hash001', normal, compile_and_run, [''])
-test('lexNum', normal, compile_and_run, [''])
+test('lex001', normal, compile_and_run, [''])
 test('take001', extra_run_opts('1'), compile_and_run, [''])
 test('genericNegative001', extra_run_opts('-1'), compile_and_run, [''])
 test('ix001', normal, compile_and_run, [''])
diff --git a/tests/lex001.hs b/tests/lex001.hs
new file mode 100644
index 0000000..7acb547
--- /dev/null
+++ b/tests/lex001.hs
@@ -0,0 +1,39 @@
+module Main where
+
+import Text.ParserCombinators.ReadP
+import qualified Text.Read.Lex
+
+testStrings
+ = [    "0x3y",
+        "0X3abx",
+        "0o39y",
+        "0O334z",
+
+        "NaN",
+        "NaNx",
+        "Infinity",
+        "Infinityx",
+
+        "Wibble Foo",
+        "Wibble8_+",
+
+        "34yy",
+        "34.4x",
+        "034.4x",
+        "31.45e-6y",
+        "49.2v",
+        "049.2v",
+        "35e-3x",
+        "035e-3x",
+        "35e+3y",
+        "83.3e-22",
+        "083.3e-22"
+   ]
+
+main = mapM test testStrings
+
+test s = do print s
+            print (lex s)
+            print (readP_to_S Text.Read.Lex.lex s)
+            putStrLn ""
+
diff --git a/tests/lex001.stdout b/tests/lex001.stdout
new file mode 100644
index 0000000..eafc596
--- /dev/null
+++ b/tests/lex001.stdout
@@ -0,0 +1,84 @@
+"0x3y"
+[("0x3","y")]
+[(Number (MkNumber 16 [3]),"y")]
+
+"0X3abx"
+[("0X3ab","x")]
+[(Number (MkNumber 16 [3,10,11]),"x")]
+
+"0o39y"
+[("0o3","9y")]
+[(Number (MkNumber 8 [3]),"9y")]
+
+"0O334z"
+[("0O334","z")]
+[(Number (MkNumber 8 [3,3,4]),"z")]
+
+"NaN"
+[("NaN","")]
+[(Ident "NaN","")]
+
+"NaNx"
+[("NaNx","")]
+[(Ident "NaNx","")]
+
+"Infinity"
+[("Infinity","")]
+[(Ident "Infinity","")]
+
+"Infinityx"
+[("Infinityx","")]
+[(Ident "Infinityx","")]
+
+"Wibble Foo"
+[("Wibble"," Foo")]
+[(Ident "Wibble"," Foo")]
+
+"Wibble8_+"
+[("Wibble8_","+")]
+[(Ident "Wibble8_","+")]
+
+"34yy"
+[("34","yy")]
+[(Number (MkDecimal [3,4] Nothing Nothing),"yy")]
+
+"34.4x"
+[("34.4","x")]
+[(Number (MkDecimal [3,4] (Just [4]) Nothing),"x")]
+
+"034.4x"
+[("034.4","x")]
+[(Number (MkDecimal [0,3,4] (Just [4]) Nothing),"x")]
+
+"31.45e-6y"
+[("31.45e-6","y")]
+[(Number (MkDecimal [3,1] (Just [4,5]) (Just (-6))),"y")]
+
+"49.2v"
+[("49.2","v")]
+[(Number (MkDecimal [4,9] (Just [2]) Nothing),"v")]
+
+"049.2v"
+[("049.2","v")]
+[(Number (MkDecimal [0,4,9] (Just [2]) Nothing),"v")]
+
+"35e-3x"
+[("35e-3","x")]
+[(Number (MkDecimal [3,5] Nothing (Just (-3))),"x")]
+
+"035e-3x"
+[("035e-3","x")]
+[(Number (MkDecimal [0,3,5] Nothing (Just (-3))),"x")]
+
+"35e+3y"
+[("35e+3","y")]
+[(Number (MkDecimal [3,5] Nothing (Just 3)),"y")]
+
+"83.3e-22"
+[("83.3e-22","")]
+[(Number (MkDecimal [8,3] (Just [3]) (Just (-22))),"")]
+
+"083.3e-22"
+[("083.3e-22","")]
+[(Number (MkDecimal [0,8,3] (Just [3]) (Just (-22))),"")]
+
diff --git a/tests/lexNum.hs b/tests/lexNum.hs
deleted file mode 100644
index ab6b862..0000000
--- a/tests/lexNum.hs
+++ /dev/null
@@ -1,28 +0,0 @@
-module Main where
-
-testStrings
- = [    "0x3y",
-        "0X3abx",
-        "0o39y",
-        "0O334z",
-
-        "NaN",
-        "Infinity",
-
-        "34yy",
-        "34.4x",
-        "034.4x",
-        "31.45e-6y",
-        "49.2v",
-        "049.2v",
-        "35e-3x",
-        "035e-3x",
-        "35e+3y",
-        "83.3e-22",
-        "083.3e-22"
-   ]
-
-main = mapM test testStrings
-
-test s = print (lex s)
-
diff --git a/tests/lexNum.stdout b/tests/lexNum.stdout
deleted file mode 100644
index 92cb063..0000000
--- a/tests/lexNum.stdout
+++ /dev/null
@@ -1,17 +0,0 @@
-[("0x3","y")]
-[("0X3ab","x")]
-[("0o3","9y")]
-[("0O334","z")]
-[("NaN","")]
-[("Infinity","")]
-[("34","yy")]
-[("34.4","x")]
-[("034.4","x")]
-[("31.45e-6","y")]
-[("49.2","v")]
-[("049.2","v")]
-[("35e-3","x")]
-[("035e-3","x")]
-[("35e+3","y")]
-[("83.3e-22","")]
-[("083.3e-22","")]



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

Reply via email to