aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r--lib/stdlib/test/erl_eval_SUITE.erl4
-rw-r--r--lib/stdlib/test/erl_scan_SUITE.erl108
-rw-r--r--lib/stdlib/test/filelib_SUITE.erl40
-rw-r--r--lib/stdlib/test/io_SUITE.erl51
4 files changed, 129 insertions, 74 deletions
diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl
index d3c91c7326..7ff4c81ea6 100644
--- a/lib/stdlib/test/erl_eval_SUITE.erl
+++ b/lib/stdlib/test/erl_eval_SUITE.erl
@@ -1086,6 +1086,10 @@ funs(Config) when is_list(Config) ->
"begin M = lists, F = fun M:reverse/1,"
" [1,2] = F([2,1]), ok end.",
ok),
+
+ %% Test that {M,F} is not accepted as a fun.
+ error_check("{" ?MODULE_STRING ",module_info}().",
+ {badfun,{?MODULE,module_info}}),
ok.
run_many_args({S, As}) ->
diff --git a/lib/stdlib/test/erl_scan_SUITE.erl b/lib/stdlib/test/erl_scan_SUITE.erl
index 3f77d40a2e..ecd181e87c 100644
--- a/lib/stdlib/test/erl_scan_SUITE.erl
+++ b/lib/stdlib/test/erl_scan_SUITE.erl
@@ -118,13 +118,13 @@ check(String) ->
%%% (This should be useful for all format_error functions.)
check_error({error, Info, EndLine}, Module0) ->
- ?line {ErrorLine, Module, Desc} = Info,
- ?line true = (Module == Module0),
- ?line assert_type(EndLine, integer),
- ?line assert_type(ErrorLine, integer),
- ?line true = (ErrorLine =< EndLine),
- ?line String = lists:flatten(Module0:format_error(Desc)),
- ?line true = io_lib:printable_list(String).
+ {ErrorLine, Module, Desc} = Info,
+ true = (Module == Module0),
+ assert_type(EndLine, integer),
+ assert_type(ErrorLine, integer),
+ true = (ErrorLine =< EndLine),
+ String = lists:flatten(Module0:format_error(Desc)),
+ true = io_lib:printable_list(String).
iso88591(doc) -> ["Tests the support for ISO-8859-1 i.e Latin-1"];
iso88591(suite) -> [];
@@ -809,77 +809,57 @@ white_spaces() ->
unicode() ->
?line {ok,[{char,1,83},{integer,1,45}],1} =
- erl_scan:string("$\\12345", 1, [{unicode,false}]), % not unicode
+ erl_scan:string("$\\12345"), % not unicode
?line {error,{1,erl_scan,{illegal,character}},1} =
- erl_scan:string([1089], 1, [{unicode,false}]),
+ erl_scan:string([1089]),
?line {error,{{1,1},erl_scan,{illegal,character}},{1,2}} =
- erl_scan:string([1089], {1,1}, [{unicode,false}]),
- ?line {error,{1,erl_scan,{illegal,character}},1} =
- %% ?line {error,{1,erl_scan,{illegal,atom}},1} =
- erl_scan:string("'a"++[1089]++"b'", 1, [{unicode,false}]),
- ?line {error,{{1,3},erl_scan,{illegal,character}},{1,4}} =
- erl_scan:string("'a"++[1089]++"b'", {1,1}, [{unicode,false}]),
+ erl_scan:string([1089], {1,1}),
+ ?line {error,{1,erl_scan,{illegal,atom}},1} =
+ erl_scan:string("'a"++[1089]++"b'", 1),
+ ?line {error,{{1,1},erl_scan,{illegal,atom}},{1,6}} =
+ erl_scan:string("'a"++[1089]++"b'", {1,1}),
?line test("\"a"++[1089]++"b\""),
?line {ok,[{char,1,1}],1} =
- erl_scan:string([$$,$\\,$^,1089], 1, [{unicode,false}]),
+ erl_scan:string([$$,$\\,$^,1089], 1),
?line {error,{1,erl_scan,Error},1} =
- erl_scan:string("\"qa\x{aaa}", 1, [{unicode,false}]),
+ erl_scan:string("\"qa\x{aaa}", 1),
?line "unterminated string starting with \"qa"++[2730]++"\"" =
erl_scan:format_error(Error),
?line {error,{{1,1},erl_scan,_},{1,11}} =
- erl_scan:string("\"qa\\x{aaa}",{1,1}, [{unicode,false}]),
- ?line {error,{{1,4},erl_scan,{illegal,character}},{1,11}} =
- erl_scan:string("'qa\\x{aaa}'",{1,1}, [{unicode,false}]),
-
- Tags = [category, column, length, line, symbol, text],
-
- %% Workaround. No character codes greater than 255! To be changed.
- %% Note: don't remove these tests, just modify them!
+ erl_scan:string("\"qa\\x{aaa}",{1,1}),
+ ?line {error,{{1,1},erl_scan,{illegal,atom}},{1,12}} =
+ erl_scan:string("'qa\\x{aaa}'",{1,1}),
- ?line {ok,[{integer,1,1089}],1} =
- erl_scan:string([$$,1089], 1, [{unicode,false}]),
- ?line {ok,[{integer,1,1089}],1} =
- erl_scan:string([$$,$\\,1089], 1, [{unicode,false}]),
+ ?line {ok,[{char,1,1089}],1} =
+ erl_scan:string([$$,1089], 1),
+ ?line {ok,[{char,1,1089}],1} =
+ erl_scan:string([$$,$\\,1089], 1),
Qs = "$\\x{aaa}",
- ?line {ok,[{integer,1,16#aaa}],1} =
- erl_scan:string(Qs, 1, [{unicode,false}]),
+ ?line {ok,[{char,1,$\x{aaa}}],1} =
+ erl_scan:string(Qs, 1),
?line {ok,[Q2],{1,9}} =
- erl_scan:string("$\\x{aaa}", {1,1}, [text,{unicode,false}]),
- ?line [{category,integer},{column,1},{length,8},
+ erl_scan:string("$\\x{aaa}", {1,1}, [text]),
+ ?line [{category,char},{column,1},{length,8},
{line,1},{symbol,16#aaa},{text,Qs}] =
erl_scan:token_info(Q2),
U1 = "\"\\x{aaa}\"",
- ?line {ok,[T1,T2,T3],{1,10}} =
- erl_scan:string(U1, {1,1}, [text,{unicode,false}]),
- ?line [{category,'['},{column,1},{length,1},{line,1},
- {symbol,'['},{text,"\""}] = erl_scan:token_info(T1, Tags),
- ?line [{category,integer},{column,2},{length,7},
- {line,1},{symbol,16#aaa},{text,"\\x{aaa}"}] =
- erl_scan:token_info(T2, Tags),
- ?line [{category,']'},{column,9},{length,1},{line,1},
- {symbol,']'},{text,"\""}] = erl_scan:token_info(T3, Tags),
- ?line {ok,[{'[',1},{integer,1,16#aaa},{']',1}],1} =
- erl_scan:string(U1, 1, [{unicode,false}]),
+ {ok,
+ [{string,[{line,1},{column,1},{text,"\"\\x{aaa}\""}],[2730]}],
+ {1,10}} = erl_scan:string(U1, {1,1}, [text]),
+ {ok,[{string,1,[2730]}],1} = erl_scan:string(U1, 1),
U2 = "\"\\x41\\x{fff}\\x42\"",
- ?line {ok,[{'[',1},{char,1,16#41},{',',1},{integer,1,16#fff},
- {',',1},{char,1,16#42},{']',1}],1} =
- erl_scan:string(U2, 1, [{unicode,false}]),
+ {ok,[{string,1,[$\x41,$\x{fff},$\x42]}],1} = erl_scan:string(U2, 1),
U3 = "\"a\n\\x{fff}\n\"",
- ?line {ok,[{'[',1},{char,1,$a},{',',1},{char,1,$\n},
- {',',2},{integer,2,16#fff},{',',2},{char,2,$\n},
- {']',3}],3} =
- erl_scan:string(U3, 1, [{unicode,false}]),
+ {ok,[{string,1,[$a,$\n,$\x{fff},$\n]}],3} = erl_scan:string(U3, 1),
U4 = "\"\\^\n\\x{aaa}\\^\n\"",
- ?line {ok,[{'[',1},{char,1,$\n},{',',2},{integer,2,16#aaa},
- {',',2},{char,2,$\n},{']',3}],3} =
- erl_scan:string(U4, 1, [{unicode,false}]),
+ {ok,[{string,1,[$\n,$\x{aaa},$\n]}],3} = erl_scan:string(U4, 1),
%% Keep these tests:
?line test(Qs),
@@ -889,21 +869,15 @@ unicode() ->
?line test(U4),
Str1 = "\"ab" ++ [1089] ++ "cd\"",
- ?line {ok,[{'[',1},{char,1,$a},{',',1},{char,1,$b},{',',1},
- {integer,1,1089},{',',1},{char,1,$c},{',',1},
- {char,1,$d},{']',1}],1} =
- erl_scan:string(Str1, 1, [{unicode,false}]),
- ?line {ok,[{'[',_},{char,_,$a},{',',_},{char,_,$b},{',',_},
- {integer,_,1089},{',',_},{char,_,$c},{',',_},
- {char,_,$d},{']',_}],{1,8}} =
- erl_scan:string(Str1, {1,1}, [{unicode,false}]),
+ {ok,[{string,1,[$a,$b,1089,$c,$d]}],1} = erl_scan:string(Str1, 1),
+ {ok,[{string,{1,1},[$a,$b,1089,$c,$d]}],{1,8}} =
+ erl_scan:string(Str1, {1,1}),
?line test(Str1),
Comment = "%% "++[1089],
- %% Returned a comment In R15B03:
- {error,{1,erl_scan,{illegal,character}},1} =
- erl_scan:string(Comment, 1, [return,{unicode,false}]),
- {error,{{1,1},erl_scan,{illegal,character}},{1,5}} =
- erl_scan:string(Comment, {1,1}, [return,{unicode,false}]),
+ {ok,[{comment,1,[$%,$%,$\s,1089]}],1} =
+ erl_scan:string(Comment, 1, [return]),
+ {ok,[{comment,{1,1},[$%,$%,$\s,1089]}],{1,5}} =
+ erl_scan:string(Comment, {1,1}, [return]),
ok.
more_chars() ->
diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl
index 27078f0914..4a67d68428 100644
--- a/lib/stdlib/test/filelib_SUITE.erl
+++ b/lib/stdlib/test/filelib_SUITE.erl
@@ -65,19 +65,26 @@ wildcard_one(Config) when is_list(Config) ->
?line {ok,OldCwd} = file:get_cwd(),
?line Dir = filename:join(?config(priv_dir, Config), "wildcard_one"),
?line ok = file:make_dir(Dir),
+ do_wildcard_1(Dir,
+ fun(Wc) ->
+ filelib:wildcard(Wc, Dir, erl_prim_loader)
+ end),
?line file:set_cwd(Dir),
- ?line do_wildcard_1(Dir, fun(Wc) -> filelib:wildcard(Wc) end),
+ do_wildcard_1(Dir,
+ fun(Wc) ->
+ L = filelib:wildcard(Wc),
+ L = filelib:wildcard(Wc, erl_prim_loader),
+ L = filelib:wildcard(Wc, "."),
+ L = filelib:wildcard(Wc, Dir)
+ end),
?line file:set_cwd(OldCwd),
?line ok = file:del_dir(Dir),
ok.
wildcard_two(Config) when is_list(Config) ->
?line Dir = filename:join(?config(priv_dir, Config), "wildcard_two"),
- ?line DirB = unicode:characters_to_binary(Dir, file:native_name_encoding()),
?line ok = file:make_dir(Dir),
?line do_wildcard_1(Dir, fun(Wc) -> io:format("~p~n",[{Wc,Dir, X = filelib:wildcard(Wc, Dir)}]),X end),
- ?line do_wildcard_1(Dir, fun(Wc) -> io:format("~p~n",[{Wc,DirB, X = filelib:wildcard(Wc, DirB)}]),
- [unicode:characters_to_list(Y,file:native_name_encoding()) || Y <- X] end),
?line do_wildcard_1(Dir, fun(Wc) -> filelib:wildcard(Wc, Dir++"/") end),
case os:type() of
{win32,_} ->
@@ -130,6 +137,9 @@ do_wildcard_2(Dir, Wcf) ->
?line ["abc","abcdef"] = Wcf("a*{def,}"),
?line ["abc","abcdef"] = Wcf("a*{,def}"),
+ %% Constant wildcard.
+ ["abcdef"] = Wcf("abcdef"),
+
%% Negative tests.
?line [] = Wcf("b*"),
?line [] = Wcf("bufflig"),
@@ -157,6 +167,8 @@ do_wildcard_4(Dir, Wcf) ->
All = ["a-","aA","aB","aC","a[","a]"],
?line Files = mkfiles(lists:reverse(All), Dir),
?line All = Wcf("a[][A-C-]"),
+ ["a-"] = Wcf("a[-]"),
+ ["a["] = Wcf("a["),
?line del(Files),
do_wildcard_5(Dir, Wcf).
@@ -173,6 +185,7 @@ do_wildcard_5(Dir, Wcf) ->
?line ["blurf/nisse"] = Wcf("*/nisse"),
?line [] = Wcf("mountain/*"),
?line [] = Wcf("xa/gurka"),
+ ["blurf/nisse"] = Wcf("blurf/nisse"),
%% Cleanup
?line del(Files),
@@ -233,7 +246,24 @@ do_wildcard_8(Dir, Wcf) ->
del(Files),
foreach(fun(D) ->
ok = file:del_dir(filename:join(Dir, D))
- end, Dirs2 ++ Dirs1 ++ Dirs0).
+ end, Dirs2 ++ Dirs1 ++ Dirs0),
+ do_wildcard_9(Dir, Wcf).
+
+do_wildcard_9(Dir, Wcf) ->
+ Dirs0 = ["lib","lib/app","lib/app/ebin"],
+ Dirs = [filename:join(Dir, D) || D <- Dirs0],
+ [ok = file:make_dir(D) || D <- Dirs],
+ Files0 = [filename:join("lib/app/ebin", F++".bar") ||
+ F <- ["abc","foo","foobar"]],
+ Files = [filename:join(Dir, F) || F <- Files0],
+ [ok = file:write_file(F, <<"some content\n">>) || F <- Files],
+ Files0 = Wcf("lib/app/ebin/*.bar"),
+
+ %% Cleanup.
+ del(Files),
+ [ok = file:del_dir(D) || D <- lists:reverse(Dirs)],
+ ok.
+
fold_files(Config) when is_list(Config) ->
?line Dir = filename:join(?config(priv_dir, Config), "fold_files"),
diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl
index 4d2b53b265..aa698ecaa2 100644
--- a/lib/stdlib/test/io_SUITE.erl
+++ b/lib/stdlib/test/io_SUITE.erl
@@ -29,7 +29,8 @@
manpage/1, otp_6708/1, otp_7084/1, otp_7421/1,
io_lib_collect_line_3_wb/1, cr_whitespace_in_string/1,
io_fread_newlines/1, otp_8989/1, io_lib_fread_literal/1,
- io_lib_print_binary_depth_one/1, otp_10302/1]).
+ io_lib_print_binary_depth_one/1, otp_10302/1, otp_10755/1,
+ otp_10836/1]).
%-define(debug, true).
@@ -65,7 +66,7 @@ all() ->
manpage, otp_6708, otp_7084, otp_7421,
io_lib_collect_line_3_wb, cr_whitespace_in_string,
io_fread_newlines, otp_8989, io_lib_fread_literal,
- io_lib_print_binary_depth_one, otp_10302].
+ io_lib_print_binary_depth_one, otp_10302, otp_10755, otp_10836].
groups() ->
[].
@@ -2049,6 +2050,8 @@ otp_10302(Suite) when is_list(Suite) ->
"<<\"apel\"...>>" = pretty(<<"apelsin">>, 2),
"<<228,112,112,108>>" = fmt("~tp", [<<"äppl">>]),
"<<228,...>>" = fmt("~tP", [<<"äppl">>, 2]),
+ "<<0,0,0,0,0,0,1,0>>" = fmt("~p", [<<256:64/unsigned-integer>>]),
+ "<<0,0,0,0,0,0,1,0>>" = fmt("~tp", [<<256:64/unsigned-integer>>]),
Chars = lists:seq(0, 512), % just a few...
[] = [C || C <- Chars, S <- io_lib:write_char_as_latin1(C),
@@ -2076,3 +2079,47 @@ pretty(Term, Opts) when is_list(Opts) ->
is_latin1(S) ->
S >= 0 andalso S =< 255.
+
+otp_10836(doc) ->
+ "OTP-10836. ~ts extended to latin1";
+otp_10836(Suite) when is_list(Suite) ->
+ S = io_lib:format("~ts", [[<<"äpple"/utf8>>, <<"äpple">>]]),
+ "äppleäpple" = lists:flatten(S),
+ ok.
+
+otp_10755(doc) ->
+ "OTP-10755. The 'l' modifier";
+otp_10755(Suite) when is_list(Suite) ->
+ S = "string",
+ "\"string\"" = fmt("~p", [S]),
+ "[115,116,114,105,110,103]" = fmt("~lp", [S]),
+ "\"string\"" = fmt("~P", [S, 2]),
+ "[115|...]" = fmt("~lP", [S, 2]),
+ {'EXIT',{badarg,_}} = (catch fmt("~ltp", [S])),
+ {'EXIT',{badarg,_}} = (catch fmt("~tlp", [S])),
+ {'EXIT',{badarg,_}} = (catch fmt("~ltP", [S])),
+ {'EXIT',{badarg,_}} = (catch fmt("~tlP", [S])),
+ Text =
+ "-module(l_mod).\n"
+ "-export([t/0]).\n"
+ "t() ->\n"
+ " S = \"string\",\n"
+ " io:format(\"~ltp\", [S]),\n"
+ " io:format(\"~tlp\", [S]),\n"
+ " io:format(\"~ltP\", [S, 1]),\n"
+ " io:format(\"~tlP\", [S, 1]).\n",
+ {ok,l_mod,[{_File,Ws}]} = compile_file("l_mod.erl", Text, Suite),
+ ["format string invalid (invalid control ~lt)",
+ "format string invalid (invalid control ~tl)",
+ "format string invalid (invalid control ~lt)",
+ "format string invalid (invalid control ~tl)"] =
+ [lists:flatten(M:format_error(E)) || {_L,M,E} <- Ws],
+ ok.
+
+compile_file(File, Text, Config) ->
+ PrivDir = ?privdir(Config),
+ Fname = filename:join(PrivDir, File),
+ ok = file:write_file(Fname, Text),
+ try compile:file(Fname, [return])
+ after ok %file:delete(Fname)
+ end.