aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r--lib/stdlib/test/beam_lib_SUITE.erl4
-rw-r--r--lib/stdlib/test/erl_lint_SUITE.erl52
-rw-r--r--lib/stdlib/test/io_proto_SUITE.erl271
-rw-r--r--lib/stdlib/test/re_SUITE.erl14
4 files changed, 64 insertions, 277 deletions
diff --git a/lib/stdlib/test/beam_lib_SUITE.erl b/lib/stdlib/test/beam_lib_SUITE.erl
index 279e15f703..1baf7d0a94 100644
--- a/lib/stdlib/test/beam_lib_SUITE.erl
+++ b/lib/stdlib/test/beam_lib_SUITE.erl
@@ -240,7 +240,7 @@ do_error(BeamFile, ACopy) ->
verify(missing_chunk, beam_lib:chunks(BF3, [imports])),
BF4 = set_byte(ACopy, BeamFile, AbstractStart+10, 17),
verify(invalid_chunk, beam_lib:chunks(BF4, [abstract_code])),
- BF5 = set_byte(ACopy, BeamFile, AttributesStart+10, 17),
+ BF5 = set_byte(ACopy, BeamFile, AttributesStart+8, 17),
verify(invalid_chunk, beam_lib:chunks(BF5, [attributes])),
BF6 = set_byte(ACopy, BeamFile, 1, 17),
@@ -251,7 +251,7 @@ do_error(BeamFile, ACopy) ->
BF8 = set_byte(ACopy, BeamFile, 13, 17),
verify(missing_chunk, beam_lib:chunks(BF8, ["AtU8"])),
- BF9 = set_byte(ACopy, BeamFile, CompileInfoStart+10, 17),
+ BF9 = set_byte(ACopy, BeamFile, CompileInfoStart+8, 17),
verify(invalid_chunk, beam_lib:chunks(BF9, [compile_info])).
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index fd7de65302..c469624fb4 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -64,8 +64,8 @@
predef/1,
maps/1,maps_type/1,maps_parallel_match/1,
otp_11851/1,otp_11879/1,otp_13230/1,
- record_errors/1, otp_xxxxx/1,
- non_latin1_module/1]).
+ record_errors/1, otp_11879_cont/1,
+ non_latin1_module/1, otp_14323/1]).
suite() ->
[{ct_hooks,[ts_install_cth]},
@@ -85,7 +85,7 @@ all() ->
too_many_arguments, basic_errors, bin_syntax_errors, predef,
maps, maps_type, maps_parallel_match,
otp_11851, otp_11879, otp_13230,
- record_errors, otp_xxxxx, non_latin1_module].
+ record_errors, otp_11879_cont, non_latin1_module, otp_14323].
groups() ->
[{unused_vars_warn, [],
@@ -3875,7 +3875,7 @@ record_errors(Config) when is_list(Config) ->
{3,erl_lint,{redefine_field,r,a}}],[]}}],
run(Config, Ts).
-otp_xxxxx(Config) ->
+otp_11879_cont(Config) ->
Ts = [{constraint1,
<<"-export([t/1]).
-spec t(X) -> X when is_subtype(integer()).
@@ -3942,6 +3942,50 @@ do_non_latin1_module(Mod) ->
ok.
+%% OTP-14323: Check the dialyzer attribute.
+otp_14323(Config) ->
+ Ts = [
+ {otp_14323_1,
+ <<"-import(mod, [m/1]).
+
+ -export([f/0, g/0, h/0]).
+
+ -dialyzer({nowarn_function,module_info/0}). % undefined function
+ -dialyzer({nowarn_function,record_info/2}). % undefined function
+ -dialyzer({nowarn_function,m/1}). % undefined function
+
+ -dialyzer(nowarn_function). % unknown option
+ -dialyzer(1). % badly formed
+ -dialyzer(malformed). % unkonwn option
+ -dialyzer({malformed,f/0}). % unkonwn option
+ -dialyzer({nowarn_function,a/1}). % undefined function
+ -dialyzer({nowarn_function,{a,-1}}). % badly formed
+
+ -dialyzer([no_return, no_match]).
+ -dialyzer({nowarn_function, f/0}).
+ -dialyzer(no_improper_lists).
+ -dialyzer([{nowarn_function, [f/0]}, no_improper_lists]).
+ -dialyzer({no_improper_lists, g/0}).
+ -dialyzer({[no_return, no_match], [g/0, h/0]}).
+
+ f() -> a.
+ g() -> b.
+ h() -> c.">>,
+ [],
+ {errors,[{5,erl_lint,{undefined_function,{module_info,0}}},
+ {6,erl_lint,{undefined_function,{record_info,2}}},
+ {7,erl_lint,{undefined_function,{m,1}}},
+ {9,erl_lint,{bad_dialyzer_option,nowarn_function}},
+ {10,erl_lint,{bad_dialyzer_attribute,1}},
+ {11,erl_lint,{bad_dialyzer_option,malformed}},
+ {12,erl_lint,{bad_dialyzer_option,malformed}},
+ {13,erl_lint,{undefined_function,{a,1}}},
+ {14,erl_lint,{bad_dialyzer_attribute,
+ {nowarn_function,{a,-1}}}}],
+ []}}],
+ [] = run(Config, Ts),
+ ok.
+
run(Config, Tests) ->
F = fun({N,P,Ws,E}, BadL) ->
case catch run_test(Config, P, Ws) of
diff --git a/lib/stdlib/test/io_proto_SUITE.erl b/lib/stdlib/test/io_proto_SUITE.erl
index db321d7490..4cc4e3292c 100644
--- a/lib/stdlib/test/io_proto_SUITE.erl
+++ b/lib/stdlib/test/io_proto_SUITE.erl
@@ -26,15 +26,14 @@
-export([init_per_testcase/2, end_per_testcase/2]).
-export([setopts_getopts/1,unicode_options/1,unicode_options_gen/1,
- binary_options/1, bc_with_r12/1,
- bc_with_r12_gl/1, read_modes_gl/1,bc_with_r12_ogl/1,
+ binary_options/1, read_modes_gl/1,
read_modes_ogl/1, broken_unicode/1,eof_on_pipe/1,unicode_prompt/1]).
-export([io_server_proxy/1,start_io_server_proxy/0, proxy_getall/1,
proxy_setnext/2, proxy_quit/1]).
%% For spawn
--export([toerl_server/3,hold_the_line/3,answering_machine1/3,
+-export([toerl_server/3,answering_machine1/3,
answering_machine2/3]).
-export([uprompt/1]).
@@ -79,8 +78,7 @@ suite() ->
all() ->
[setopts_getopts, unicode_options, unicode_options_gen,
- binary_options, bc_with_r12, bc_with_r12_gl,
- bc_with_r12_ogl, read_modes_gl, read_modes_ogl,
+ binary_options, read_modes_gl, read_modes_ogl,
broken_unicode, eof_on_pipe, unicode_prompt].
groups() ->
@@ -742,263 +740,7 @@ binary_options(Config) when is_list(Config) ->
],[],[],"-oldshell"),
ok.
-%% Test io protocol compatibility with R12 nodes.
-bc_with_r12(Config) when is_list(Config) ->
- case test_server:is_release_available("r12b") of
- true -> bc_with_r12_1(Config);
- false -> {skip,"No R12B found"}
- end.
-
-bc_with_r12_1(Config) ->
- PA = filename:dirname(code:which(?MODULE)),
- Name1 = io_proto_r12_1,
- N1 = list_to_atom(atom_to_list(Name1) ++ "@" ++ hostname()),
- test_server:start_node(Name1, peer, [{args, "-pz \""++PA++"\""},
- {erl,[{release,"r12b"}]}]),
- DataDir = proplists:get_value(data_dir,Config),
- FileName1 = filename:join([DataDir,"testdata_latin1.dat"]),
- TestDataLine1 = [229,228,246],
- TestDataLine2 = [197,196,214],
- SPid1 = rpc:call(N1,erlang,spawn,[?MODULE,hold_the_line,[self(),FileName1,[read]]]),
- {ok,F1} = receive
- {SPid1,Res1} ->
- Res1
- after 5000 ->
- exit(timeout)
- end,
- TestDataLine1 = chomp(io:get_line(F1,'')),
- SPid1 ! die,
- receive after 1000 -> ok end,
- SPid2 = rpc:call(N1,erlang,spawn,[?MODULE,hold_the_line,[self(),FileName1,[read,binary]]]),
- {ok,F2} = receive
- {SPid2,Res2} ->
- Res2
- after 5000 ->
- exit(timeout)
- end,
- TestDataLine1BinUtf = unicode:characters_to_binary(TestDataLine1),
- TestDataLine1BinLatin = list_to_binary(TestDataLine1),
- TestDataLine2BinUtf = unicode:characters_to_binary(TestDataLine2),
- TestDataLine2BinLatin = list_to_binary(TestDataLine2),
- TestDataLine1BinUtf = chomp(io:get_line(F2,'')),
- TestDataLine2BinUtf = chomp(io:get_line(F2,'')),
- %%io:format(standard_error,"Exec:~s\r\n",[rpc:call(N1,os,find_executable,["erl"])]),
- %%io:format(standard_error,"Io:~s\r\n",[rpc:call(N1,code,which,[io])]),
- %%io:format(standard_error,"File_io_server:~s\r\n",[rpc:call(N1,code,which,[file_io_server])]),
- file:position(F2,0),
- TestDataLine1BinLatin = chomp(rpc:call(N1,io,get_line,[F2,''])),
- TestDataLine2BinUtf = chomp(io:get_line(F2,'')),
- file:position(F2,0),
- TestDataLine1BinUtf = chomp(io:get_line(F2,'')),
- TestDataLine2BinLatin = chomp(rpc:call(N1,io,get_line,[F2,''])),
- eof = chomp(rpc:call(N1,io,get_line,[F2,''])),
- file:position(F2,0),
- TestDataLine1BinLatin = rpc:call(N1,io,get_chars,[F2,'',3]),
- io:get_chars(F2,'',1),
- TestDataLine2BinLatin = chomp(rpc:call(N1,io,get_line,[F2,''])),
- file:position(F2,0),
- {ok,[TestDataLine1]} = io:fread(F2,'',"~s"),
- {ok,[TestDataLine2]} = rpc:call(N1,io,fread,[F2,'',"~s"]),
-
- DataLen1 = length(TestDataLine1),
- DataLen2 = length(TestDataLine2),
- file:position(F2,0),
- {ok,TestDataLine1BinLatin} = file:read(F2,DataLen1),
- {ok,_} = file:read(F2,1),
- {ok,TestDataLine2BinLatin} = rpc:call(N1,file,read,[F2,DataLen2]),
- {ok,_} = file:read(F2,1),
- eof = rpc:call(N1,file,read,[F2,1]),
- %% As r12 has a bug when setting options with setopts, we need
- %% to reopen the file...
- SPid2 ! die,
- receive after 1000 -> ok end,
- SPid3 = rpc:call(N1,erlang,spawn,[?MODULE,hold_the_line,[self(),FileName1,[read]]]),
- {ok,F3} = receive
- {SPid3,Res3} ->
- Res3
- after 5000 ->
- exit(timeout)
- end,
-
- file:position(F3,0),
- {ok,[TestDataLine1]} = io:fread(F3,'',"~s"),
- {ok,[TestDataLine2]} = rpc:call(N1,io,fread,[F3,'',"~s"]),
-
-
- file:position(F3,0),
- {ok,TestDataLine1} = file:read(F3,DataLen1),
- {ok,_} = file:read(F3,1),
- {ok,TestDataLine2} = rpc:call(N1,file,read,[F3,DataLen2]),
- {ok,_} = file:read(F3,1),
- eof = rpc:call(N1,file,read,[F3,1]),
-
-
- %% So, lets do it all again, but the other way around
- {ok,F4} = file:open(FileName1,[read]),
- TestDataLine1 = chomp(io:get_line(F4,'')),
- file:position(F4,0),
- io:setopts(F4,[binary]),
- TestDataLine1BinUtf = chomp(io:get_line(F4,'')),
- TestDataLine2BinUtf = chomp(io:get_line(F4,'')),
- file:position(F4,0),
- TestDataLine1BinUtf = chomp(io:get_line(F4,'')),
- TestDataLine2BinUtf = chomp(io:get_line(F4,'')),
- file:position(F4,0),
- TestDataLine1BinUtf = chomp(io:get_line(F4,'')),
- TestDataLine2BinLatin = chomp(rpc:call(N1,io,get_line,[F4,''])),
- file:position(F4,0),
- TestDataLine1BinLatin = chomp(rpc:call(N1,io,get_line,[F4,''])),
- TestDataLine2BinUtf = chomp(io:get_line(F4,'')),
- eof = chomp(rpc:call(N1,io,get_line,[F4,''])),
- file:position(F4,0),
- TestDataLine1BinLatin = rpc:call(N1,io,get_chars,[F4,'',3]),
- io:get_chars(F4,'',1),
- TestDataLine2BinLatin = chomp(rpc:call(N1,io,get_line,[F4,''])),
- file:position(F4,0),
- {ok,[TestDataLine1]} = io:fread(F4,'',"~s"),
- {ok,[TestDataLine2]} = rpc:call(N1,io,fread,[F4,'',"~s"]),
- file:position(F4,0),
- {ok,TestDataLine1BinLatin} = file:read(F4,DataLen1),
- {ok,_} = file:read(F4,1),
- {ok,TestDataLine2BinLatin} = rpc:call(N1,file,read,[F4,DataLen2]),
- {ok,_} = file:read(F4,1),
- eof = rpc:call(N1,file,read,[F4,1]),
- io:setopts(F4,[list]),
-
- file:position(F4,0),
- {ok,[TestDataLine1]} = io:fread(F4,'',"~s"),
- {ok,[TestDataLine2]} = rpc:call(N1,io,fread,[F4,'',"~s"]),
-
-
- file:position(F4,0),
- {ok,TestDataLine1} = file:read(F4,DataLen1),
- {ok,_} = file:read(F4,1),
- {ok,TestDataLine2} = rpc:call(N1,file,read,[F4,DataLen2]),
- {ok,_} = file:read(F4,1),
- eof = rpc:call(N1,file,read,[F4,1]),
-
- file:close(F4),
- test_server:stop_node(N1),
- ok.
-
-hold_the_line(Parent,Filename,Options) ->
- Parent ! {self(), file:open(Filename,Options)},
- receive
- die ->
- ok
- end.
-
-
-%% Test io protocol compatibility with R12 nodes (terminals).
-bc_with_r12_gl(Config) when is_list(Config) ->
- case test_server:is_release_available("r12b") of
- true ->
- case get_progs() of
- {error,Reason} ->
- {skip, Reason};
- _ ->
- bc_with_r12_gl_1(Config,answering_machine1)
- end;
- false ->
- {skip,"No R12B found"}
- end.
-
-%% Test io protocol compatibility with R12 nodes (oldshell).
-bc_with_r12_ogl(Config) when is_list(Config) ->
- case test_server:is_release_available("r12b") of
- true ->
- case get_progs() of
- {error,Reason} ->
- {skip, Reason};
- _ ->
- bc_with_r12_gl_1(Config,answering_machine2)
- end;
- false ->
- {skip,"No R12B found"}
- end.
-
-bc_with_r12_gl_1(_Config,Machine) ->
- PA = filename:dirname(code:which(?MODULE)),
- Name1 = io_proto_r12_gl_1,
- N1 = list_to_atom(atom_to_list(Name1) ++ "@" ++ hostname()),
- test_server:start_node(Name1, peer, [{args, "-pz \""++PA++"\""},
- {erl,[{release,"r12b"}]}]),
- TestDataLine1 = [229,228,246],
- TestDataLine1BinUtf = unicode:characters_to_binary(TestDataLine1),
- TestDataLine1BinLatin = list_to_binary(TestDataLine1),
-
- {ok,N2List} = create_nodename(),
- MyNodeList = atom2list(node()),
- register(io_proto_suite,self()),
- AM1 = spawn(?MODULE,Machine,
- [MyNodeList, "io_proto_suite", N2List]),
-
- GL = receive X when is_pid(X) -> X end,
- %% get_line
- "Hej\n" = rpc:call(N1,io,get_line,[GL,"Prompt\n"]),
- io:setopts(GL,[binary]),
- io:format(GL,"Okej~n",[]),
- <<"Hej\n">> = rpc:call(N1,io,get_line,[GL,"Prompt\n"]),
- io:setopts(GL,[{encoding,latin1}]),
- io:format(GL,"Okej~n",[]),
- TestDataLine1BinLatin = chomp(rpc:call(N1,io,get_line,[GL,"Prompt\n"])),
- io:format(GL,"Okej~n",[]),
- TestDataLine1BinUtf = chomp(io:get_line(GL,"Prompt\n")),
- io:setopts(GL,[{encoding,unicode}]),
-
- io:format(GL,"Okej~n",[]),
- TestDataLine1BinLatin = chomp(rpc:call(N1,io,get_line,[GL,"Prompt\n"])),
- io:format(GL,"Okej~n",[]),
- TestDataLine1BinUtf = chomp(io:get_line(GL,"Prompt\n")),
- io:setopts(GL,[list]),
- io:format(GL,"Okej~n",[]),
-
- %%get_chars
- "Hej" = rpc:call(N1,io,get_chars,[GL,"Prompt\n",3]),
- io:setopts(GL,[binary]),
- io:format(GL,"Okej~n",[]),
- <<"Hej">> = rpc:call(N1,io,get_chars,[GL,"Prompt\n",3]),
- io:setopts(GL,[{encoding,latin1}]),
- io:format(GL,"Okej~n",[]),
- TestDataLine1BinLatin = rpc:call(N1,io,get_chars,[GL,"Prompt\n",3]),
- io:format(GL,"Okej~n",[]),
- TestDataLine1BinUtf = io:get_chars(GL,"Prompt\n",3),
- io:setopts(GL,[{encoding,unicode}]),
-
- io:format(GL,"Okej~n",[]),
- TestDataLine1BinLatin = rpc:call(N1,io,get_chars,[GL,"Prompt\n",3]),
- io:format(GL,"Okej~n",[]),
- TestDataLine1BinUtf = io:get_chars(GL,"Prompt\n",3),
- io:setopts(GL,[list]),
- io:format(GL,"Okej~n",[]),
- %%fread
- {ok,["Hej"]} = rpc:call(N1,io,fread,[GL,"Prompt\n","~s"]),
- io:setopts(GL,[binary]),
- io:format(GL,"Okej~n",[]),
- {ok,["Hej"]} = rpc:call(N1,io,fread,[GL,"Prompt\n","~s"]),
- io:setopts(GL,[{encoding,latin1}]),
- io:format(GL,"Okej~n",[]),
- {ok,[TestDataLine1]} = rpc:call(N1,io,fread,[GL,"Prompt\n","~s"]),
- io:format(GL,"Okej~n",[]),
- {ok,[TestDataLine1]} = io:fread(GL,"Prompt\n","~s"),
- io:setopts(GL,[{encoding,unicode}]),
- io:format(GL,"Okej~n",[]),
- {ok,[TestDataLine1]} = rpc:call(N1,io,fread,[GL,"Prompt\n","~s"]),
- io:format(GL,"Okej~n",[]),
- {ok,[TestDataLine1]} = io:fread(GL,"Prompt\n","~s"),
- io:setopts(GL,[list]),
- io:format(GL,"Okej~n",[]),
-
-
- receive
- {AM1,done} ->
- ok
- after 5000 ->
- exit(timeout)
- end,
- test_server:stop_node(N1),
- ok.
answering_machine1(OthNode,OthReg,Me) ->
@@ -1900,13 +1642,6 @@ convert(Data, latin1, binary) ->
{error, {cannot_convert, unicode, latin1}}
end.
-hostname() ->
- from($@, atom_to_list(node())).
-
-from(H, [H | T]) -> T;
-from(H, [_ | T]) -> from(H, T);
-from(_, []) -> [].
-
atom2list(A) ->
lists:flatten(io_lib:format("~w", [A])).
diff --git a/lib/stdlib/test/re_SUITE.erl b/lib/stdlib/test/re_SUITE.erl
index a76ded5f60..71f86e32e5 100644
--- a/lib/stdlib/test/re_SUITE.erl
+++ b/lib/stdlib/test/re_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2008-2016. All Rights Reserved.
+%% Copyright Ericsson AB 2008-2017. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -24,7 +24,7 @@
run_options/1,combined_options/1,replace_autogen/1,
global_capture/1,replace_input_types/1,replace_return/1,
split_autogen/1,split_options/1,split_specials/1,
- error_handling/1,pcre_cve_2008_2371/1,
+ error_handling/1,pcre_cve_2008_2371/1,re_version/1,
pcre_compile_workspace_overflow/1,re_infinite_loop/1,
re_backwards_accented/1,opt_dupnames/1,opt_all_names/1,inspect/1,
opt_no_start_optimize/1,opt_never_utf/1,opt_ucp/1,
@@ -45,7 +45,7 @@ all() ->
pcre_compile_workspace_overflow, re_infinite_loop,
re_backwards_accented, opt_dupnames, opt_all_names,
inspect, opt_no_start_optimize,opt_never_utf,opt_ucp,
- match_limit, sub_binaries].
+ match_limit, sub_binaries, re_version].
groups() ->
[].
@@ -194,6 +194,14 @@ run_options(Config) when is_list(Config) ->
+%% Test the version is retorned correctly
+re_version(_Config) ->
+ Version = re:version(),
+ {match,[Version]} = re:run(Version,"^[0-9]\\.[0-9]{2} 20[0-9]{2}-[0-9]{2}-[0-9]{2}",[{capture,all,binary}]),
+ ok.
+
+
+
%% Test compile options given directly to run.
combined_options(Config) when is_list(Config) ->
ok = crtest("ABDabcdABCD","abcd",[],true,{match,[{3,4}]}),