diff options
author | Damien Doligez <damien.doligez-inria.fr> | 2013-05-29 20:21:12 +0000 |
---|---|---|
committer | Damien Doligez <damien.doligez-inria.fr> | 2013-05-29 20:21:12 +0000 |
commit | 4321fefb50ee11a876bfff09a8df25477341b4c9 (patch) | |
tree | af14b1ea37218dd7c387145bb5b1b9727e69bbfa | |
parent | cba8ab21e437de4d22ec3c77d1c1c28f9e4cbb1c (diff) |
fix the tests for module Format
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13720 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r-- | testsuite/tests/lib-format/tformat.ml | 123 | ||||
-rw-r--r-- | testsuite/tests/lib-format/tformat.reference | 6 |
2 files changed, 67 insertions, 62 deletions
diff --git a/testsuite/tests/lib-format/tformat.ml b/testsuite/tests/lib-format/tformat.ml index cf2f4fc9e..4c0382b17 100644 --- a/testsuite/tests/lib-format/tformat.ml +++ b/testsuite/tests/lib-format/tformat.ml @@ -19,9 +19,11 @@ A test file for the Format module. open Testing;; open Format;; +let say s = Printf.printf s;; + try - printf "d/i positive\n%!"; + say "d/i positive\n%!"; test (sprintf "%d/%i" 42 43 = "42/43"); test (sprintf "%-4d/%-5i" 42 43 = "42 /43 "); test (sprintf "%04d/%05i" 42 43 = "0042/00043"); @@ -32,7 +34,7 @@ try test (sprintf "%*d/%*i" 4 42 5 43 = " 42/ 43"); test (sprintf "%-0+#4d/%-0 #5i" 42 43 = "+42 / 43 "); - printf "\nd/i negative\n%!"; + say "\nd/i negative\n%!"; test (sprintf "%d/%i" (-42) (-43) = "-42/-43"); test (sprintf "%-4d/%-5i" (-42) (-43) = "-42 /-43 "); test (sprintf "%04d/%05i" (-42) (-43) = "-042/-0043"); @@ -43,7 +45,7 @@ try test (sprintf "%*d/%*i" 4 (-42) 5 (-43) = " -42/ -43"); test (sprintf "%-0+ #4d/%-0+ #5i" (-42) (-43) = "-42 /-43 "); - printf "\nu positive\n%!"; + say "\nu positive\n%!"; test (sprintf "%u" 42 = "42"); test (sprintf "%-4u" 42 = "42 "); test (sprintf "%04u" 42 = "0042"); @@ -54,7 +56,7 @@ try test (sprintf "%*u" 4 42 = " 42"); test (sprintf "%-0+ #6d" 42 = "+42 "); - printf "\nu negative\n%!"; + say "\nu negative\n%!"; begin match Sys.word_size with | 32 -> test (sprintf "%u" (-1) = "2147483647"); @@ -63,7 +65,7 @@ try | _ -> test false end; - printf "\nx positive\n%!"; + say "\nx positive\n%!"; test (sprintf "%x" 42 = "2a"); test (sprintf "%-4x" 42 = "2a "); test (sprintf "%04x" 42 = "002a"); @@ -74,7 +76,7 @@ try test (sprintf "%*x" 5 42 = " 2a"); test (sprintf "%-0+ #*x" 5 42 = "0x2a "); - printf "\nx negative\n%!"; + say "\nx negative\n%!"; begin match Sys.word_size with | 32 -> test (sprintf "%x" (-42) = "7fffffd6"); @@ -83,7 +85,7 @@ try | _ -> test false end; - printf "\nX positive\n%!"; + say "\nX positive\n%!"; test (sprintf "%X" 42 = "2A"); test (sprintf "%-4X" 42 = "2A "); test (sprintf "%04X" 42 = "002A"); @@ -94,7 +96,7 @@ try test (sprintf "%*X" 5 42 = " 2A"); test (sprintf "%-0+ #*X" 5 42 = "0X2A "); - printf "\nx negative\n%!"; + say "\nx negative\n%!"; begin match Sys.word_size with | 32 -> test (sprintf "%X" (-42) = "7FFFFFD6"); @@ -103,7 +105,7 @@ try | _ -> test false end; - printf "\no positive\n%!"; + say "\no positive\n%!"; test (sprintf "%o" 42 = "52"); test (sprintf "%-4o" 42 = "52 "); test (sprintf "%04o" 42 = "0052"); @@ -114,7 +116,7 @@ try test (sprintf "%*o" 5 42 = " 52"); test (sprintf "%-0+ #*o" 5 42 = "052 "); - printf "\no negative\n%!"; + say "\no negative\n%!"; begin match Sys.word_size with | 32 -> test (sprintf "%o" (-42) = "17777777726"); @@ -123,7 +125,7 @@ try | _ -> test false end; - printf "\ns\n%!"; + say "\ns\n%!"; test (sprintf "%s" "foo" = "foo"); test (sprintf "%-5s" "foo" = "foo "); test (sprintf "%05s" "foo" = " foo"); @@ -135,11 +137,11 @@ try test (sprintf "%*s" 6 "foo" = " foo"); test (sprintf "%*s" 2 "foo" = "foo"); test (sprintf "%-0+ #5s" "foo" = "foo "); - test (sprintf "%s@" "foo" = "foo@"); - test (sprintf "%s@inria.fr" "foo" = "foo@inria.fr"); - test (sprintf "%s@%s" "foo" "inria.fr" = "foo@inria.fr"); + test (sprintf "%s@@" "foo" = "foo@"); + test (sprintf "%s@@inria.fr" "foo" = "foo@inria.fr"); + test (sprintf "%s@@%s" "foo" "inria.fr" = "foo@inria.fr"); - printf "\nS\n%!"; + say "\nS\n%!"; test (sprintf "%S" "fo\"o" = "\"fo\\\"o\""); (* test (sprintf "%-5S" "foo" = "\"foo\" "); padding not done *) (* test (sprintf "%05S" "foo" = " \"foo\""); padding not done *) @@ -151,11 +153,11 @@ try (* test (sprintf "%*S" 6 "foo" = " \"foo\""); padding not done *) test (sprintf "%*S" 2 "foo" = "\"foo\""); (* test (sprintf "%-0+ #5S" "foo" = "\"foo\" "); padding not done *) - test (sprintf "%S@" "foo" = "\"foo\"@"); - test (sprintf "%S@inria.fr" "foo" = "\"foo\"@inria.fr"); - test (sprintf "%S@%S" "foo" "inria.fr" = "\"foo\"@\"inria.fr\""); + test (sprintf "%S@@" "foo" = "\"foo\"@"); + test (sprintf "%S@@inria.fr" "foo" = "\"foo\"@inria.fr"); + test (sprintf "%S@@%S" "foo" "inria.fr" = "\"foo\"@\"inria.fr\""); - printf "\nc\n%!"; + say "\nc\n%!"; test (sprintf "%c" 'c' = "c"); (* test (sprintf "%-4c" 'c' = "c "); padding not done *) (* test (sprintf "%04c" 'c' = " c"); padding not done *) @@ -166,7 +168,7 @@ try (* test (sprintf "%*c" 2 'c' = " c"); padding not done *) (* test (sprintf "%-0+ #4c" 'c' = "c "); padding not done *) - printf "\nC\n%!"; + say "\nC\n%!"; test (sprintf "%C" 'c' = "'c'"); test (sprintf "%C" '\'' = "'\\''"); (* test (sprintf "%-4C" 'c' = "c "); padding not done *) @@ -178,7 +180,7 @@ try (* test (sprintf "%*C" 2 'c' = " c"); padding not done *) (* test (sprintf "%-0+ #4C" 'c' = "c "); padding not done *) - printf "\nf\n%!"; + say "\nf\n%!"; test (sprintf "%f" (-42.42) = "-42.420000"); test (sprintf "%-13f" (-42.42) = "-42.420000 "); test (sprintf "%013f" (-42.42) = "-00042.420000"); @@ -198,7 +200,7 @@ try test (sprintf "%*.*f" 12 3 42.42 = " 42.420"); test (sprintf "%-0+ #12.3f" 42.42 = "+42.420 "); - printf "\nF\n%!"; + say "\nF\n%!"; test (sprintf "%F" 42.42 = "42.42"); test (sprintf "%F" 42.42e42 = "4.242e+43"); test (sprintf "%F" 42.00 = "42."); @@ -210,7 +212,7 @@ try test (sprintf "%.3F" 0.0042 = "0.004"); *) - printf "\ne\n%!"; + say "\ne\n%!"; test (sprintf "%e" (-42.42) = "-4.242000e+01"); test (sprintf "%-15e" (-42.42) = "-4.242000e+01 "); test (sprintf "%015e" (-42.42) = "-004.242000e+01"); @@ -230,7 +232,7 @@ try test (sprintf "%*.*e" 11 3 42.42 = " 4.242e+01"); test (sprintf "%-0+ #14.3e" 42.42 = "+4.242e+01 "); - printf "\nE\n%!"; + say "\nE\n%!"; test (sprintf "%E" (-42.42) = "-4.242000E+01"); test (sprintf "%-15E" (-42.42) = "-4.242000E+01 "); test (sprintf "%015E" (-42.42) = "-004.242000E+01"); @@ -251,7 +253,7 @@ try test (sprintf "%-0+ #14.3E" 42.42 = "+4.242E+01 "); (* %g gives strange results that correspond to neither %f nor %e - printf "\ng\n%!"; + say "\ng\n%!"; test (sprintf "%g" (-42.42) = "-42.42000"); test (sprintf "%-15g" (-42.42) = "-42.42000 "); test (sprintf "%015g" (-42.42) = "-00000042.42000"); @@ -265,14 +267,14 @@ try *) (* Same for %G - printf "\nG\n%!"; + say "\nG\n%!"; *) - printf "\nB\n%!"; + say "\nB\n%!"; test (sprintf "%B" true = "true"); test (sprintf "%B" false = "false"); - printf "\nld/li positive\n%!"; + say "\nld/li positive\n%!"; test (sprintf "%ld/%li" 42l 43l = "42/43"); test (sprintf "%-4ld/%-5li" 42l 43l = "42 /43 "); test (sprintf "%04ld/%05li" 42l 43l = "0042/00043"); @@ -283,7 +285,7 @@ try test (sprintf "%*ld/%*li" 4 42l 5 43l = " 42/ 43"); test (sprintf "%-0+#4ld/%-0 #5li" 42l 43l = "+42 / 43 "); - printf "\nld/li negative\n%!"; + say "\nld/li negative\n%!"; test (sprintf "%ld/%li" (-42l) (-43l) = "-42/-43"); test (sprintf "%-4ld/%-5li" (-42l) (-43l) = "-42 /-43 "); test (sprintf "%04ld/%05li" (-42l) (-43l) = "-042/-0043"); @@ -294,7 +296,7 @@ try test (sprintf "%*ld/%*li" 4 (-42l) 5 (-43l) = " -42/ -43"); test (sprintf "%-0+ #4ld/%-0+ #5li" (-42l) (-43l) = "-42 /-43 "); - printf "\nlu positive\n%!"; + say "\nlu positive\n%!"; test (sprintf "%lu" 42l = "42"); test (sprintf "%-4lu" 42l = "42 "); test (sprintf "%04lu" 42l = "0042"); @@ -305,10 +307,10 @@ try test (sprintf "%*lu" 4 42l = " 42"); test (sprintf "%-0+ #6ld" 42l = "+42 "); - printf "\nlu negative\n%!"; + say "\nlu negative\n%!"; test (sprintf "%lu" (-1l) = "4294967295"); - printf "\nlx positive\n%!"; + say "\nlx positive\n%!"; test (sprintf "%lx" 42l = "2a"); test (sprintf "%-4lx" 42l = "2a "); test (sprintf "%04lx" 42l = "002a"); @@ -319,10 +321,10 @@ try test (sprintf "%*lx" 5 42l = " 2a"); test (sprintf "%-0+ #*lx" 5 42l = "0x2a "); - printf "\nlx negative\n%!"; + say "\nlx negative\n%!"; test (sprintf "%lx" (-42l) = "ffffffd6"); - printf "\nlX positive\n%!"; + say "\nlX positive\n%!"; test (sprintf "%lX" 42l = "2A"); test (sprintf "%-4lX" 42l = "2A "); test (sprintf "%04lX" 42l = "002A"); @@ -333,10 +335,10 @@ try test (sprintf "%*lX" 5 42l = " 2A"); test (sprintf "%-0+ #*lX" 5 42l = "0X2A "); - printf "\nlx negative\n%!"; + say "\nlx negative\n%!"; test (sprintf "%lX" (-42l) = "FFFFFFD6"); - printf "\nlo positive\n%!"; + say "\nlo positive\n%!"; test (sprintf "%lo" 42l = "52"); test (sprintf "%-4lo" 42l = "52 "); test (sprintf "%04lo" 42l = "0052"); @@ -347,13 +349,13 @@ try test (sprintf "%*lo" 5 42l = " 52"); test (sprintf "%-0+ #*lo" 5 42l = "052 "); - printf "\nlo negative\n%!"; + say "\nlo negative\n%!"; test (sprintf "%lo" (-42l) = "37777777726"); (* Nativeint not tested: looks like too much work, and anyway it should work like Int32 or Int64. *) - printf "\nLd/Li positive\n%!"; + say "\nLd/Li positive\n%!"; test (sprintf "%Ld/%Li" 42L 43L = "42/43"); test (sprintf "%-4Ld/%-5Li" 42L 43L = "42 /43 "); test (sprintf "%04Ld/%05Li" 42L 43L = "0042/00043"); @@ -364,7 +366,7 @@ try test (sprintf "%*Ld/%*Li" 4 42L 5 43L = " 42/ 43"); test (sprintf "%-0+#4Ld/%-0 #5Li" 42L 43L = "+42 / 43 "); - printf "\nLd/Li negative\n%!"; + say "\nLd/Li negative\n%!"; test (sprintf "%Ld/%Li" (-42L) (-43L) = "-42/-43"); test (sprintf "%-4Ld/%-5Li" (-42L) (-43L) = "-42 /-43 "); test (sprintf "%04Ld/%05Li" (-42L) (-43L) = "-042/-0043"); @@ -375,7 +377,7 @@ try test (sprintf "%*Ld/%*Li" 4 (-42L) 5 (-43L) = " -42/ -43"); test (sprintf "%-0+ #4Ld/%-0+ #5Li" (-42L) (-43L) = "-42 /-43 "); - printf "\nLu positive\n%!"; + say "\nLu positive\n%!"; test (sprintf "%Lu" 42L = "42"); test (sprintf "%-4Lu" 42L = "42 "); test (sprintf "%04Lu" 42L = "0042"); @@ -386,10 +388,10 @@ try test (sprintf "%*Lu" 4 42L = " 42"); test (sprintf "%-0+ #6Ld" 42L = "+42 "); - printf "\nLu negative\n%!"; + say "\nLu negative\n%!"; test (sprintf "%Lu" (-1L) = "18446744073709551615"); - printf "\nLx positive\n%!"; + say "\nLx positive\n%!"; test (sprintf "%Lx" 42L = "2a"); test (sprintf "%-4Lx" 42L = "2a "); test (sprintf "%04Lx" 42L = "002a"); @@ -400,10 +402,10 @@ try test (sprintf "%*Lx" 5 42L = " 2a"); test (sprintf "%-0+ #*Lx" 5 42L = "0x2a "); - printf "\nLx negative\n%!"; + say "\nLx negative\n%!"; test (sprintf "%Lx" (-42L) = "ffffffffffffffd6"); - printf "\nLX positive\n%!"; + say "\nLX positive\n%!"; test (sprintf "%LX" 42L = "2A"); test (sprintf "%-4LX" 42L = "2A "); test (sprintf "%04LX" 42L = "002A"); @@ -414,10 +416,10 @@ try test (sprintf "%*LX" 5 42L = " 2A"); test (sprintf "%-0+ #*LX" 5 42L = "0X2A "); - printf "\nLx negative\n%!"; + say "\nLx negative\n%!"; test (sprintf "%LX" (-42L) = "FFFFFFFFFFFFFFD6"); - printf "\nLo positive\n%!"; + say "\nLo positive\n%!"; test (sprintf "%Lo" 42L = "52"); test (sprintf "%-4Lo" 42L = "52 "); test (sprintf "%04Lo" 42L = "0052"); @@ -428,39 +430,40 @@ try test (sprintf "%*Lo" 5 42L = " 52"); test (sprintf "%-0+ #*Lo" 5 42L = "052 "); - printf "\nLo negative\n%!"; + say "\nLo negative\n%!"; test (sprintf "%Lo" (-42L) = "1777777777777777777726"); - printf "\na\n%!"; + say "\na\n%!"; let x = ref () in let f () y = if y == x then "ok" else "wrong" in test (sprintf "%a" f x = "ok"); - printf "\nt\n%!"; + say "\nt\n%!"; let f () = "ok" in test (sprintf "%t" f = "ok"); -(* Does not work as expected. Should be fixed to work like %s. - printf "\n{...%%}\n%!"; - let f = format_of_string "%f/%s" in - test (sprintf "%{%f%s%}" f = "%f/%s"); +(* %{ fmt %} prints the signature of [fmt], i.e. a canonical representation + of the conversions present in [fmt]. *) + say "\n{...%%}\n%!"; + let f = format_of_string "%f/%s" in + test (sprintf "%{%f%s%}" f = "%f%s"); - printf "\n(...%%)\n%!"; + say "\n(...%%)\n%!"; let f = format_of_string "%d/foo/%s" in test (sprintf "%(%d%s%)" f 42 "bar" = "42/foo/bar"); - printf "\n! %% @ , and constants\n%!"; + say "\n! %% @ , and constants\n%!"; test (sprintf "%!" = ""); test (sprintf "%%" = "%"); test (sprintf "%@" = "@"); test (sprintf "%," = ""); - test (sprintf "@" = "@"); - test (sprintf "@@" = "@@"); - test (sprintf "@%%" = "@%"); + test (sprintf "@@" = "@"); + test (sprintf "@@@@" = "@@"); + test (sprintf "@@%%" = "@%"); - printf "\nend of tests\n%!"; + say "\nend of tests\n%!"; with e -> - printf "unexpected exception: %s\n%!" (Printexc.to_string e); + say "unexpected exception: %s\n%!" (Printexc.to_string e); test false; ;; diff --git a/testsuite/tests/lib-format/tformat.reference b/testsuite/tests/lib-format/tformat.reference index c30013eb6..387dfb853 100644 --- a/testsuite/tests/lib-format/tformat.reference +++ b/testsuite/tests/lib-format/tformat.reference @@ -80,10 +80,12 @@ a 266 t 267 -(...%) +{...%} 268 +(...%) + 269 ! % @ , and constants - 269 270 271 272 273 274 275 + 270 271 272 273 274 275 276 end of tests All tests succeeded. |