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.erl21
-rw-r--r--lib/stdlib/test/dets_SUITE.erl95
-rw-r--r--lib/stdlib/test/ets_SUITE.erl10
-rw-r--r--lib/stdlib/test/filelib_SUITE.erl7
-rw-r--r--lib/stdlib/test/proc_lib_SUITE.erl2
-rw-r--r--lib/stdlib/test/re_SUITE.erl92
-rw-r--r--lib/stdlib/test/shell_SUITE.erl6
-rw-r--r--lib/stdlib/test/sofs_SUITE.erl6
8 files changed, 130 insertions, 109 deletions
diff --git a/lib/stdlib/test/beam_lib_SUITE.erl b/lib/stdlib/test/beam_lib_SUITE.erl
index 4ccc863795..e42dd341c0 100644
--- a/lib/stdlib/test/beam_lib_SUITE.erl
+++ b/lib/stdlib/test/beam_lib_SUITE.erl
@@ -330,6 +330,7 @@ strip(Conf) when is_list(Conf) ->
?line {Source2D1, BeamFile2D1} = make_beam(PrivDir, simple2, concat),
?line {Source3D1, BeamFile3D1} = make_beam(PrivDir, make_fun, make_fun),
?line {Source4D1, BeamFile4D1} = make_beam(PrivDir, constant, constant),
+ ?line {Source5D1, BeamFile5D1} = make_beam(PrivDir, lines, lines),
?line NoOfTables = length(ets:all()),
?line P0 = pps(),
@@ -360,13 +361,25 @@ strip(Conf) when is_list(Conf) ->
?line {module, make_fun} = code:load_abs(filename:rootname(BeamFile3D1)),
?line {module, constant} = code:load_abs(filename:rootname(BeamFile4D1)),
+ %% check that line number information is still present after stripping
+ ?line {module, lines} = code:load_abs(filename:rootname(BeamFile5D1)),
+ ?line {'EXIT',{badarith,[{lines,t,1,Info}|_]}} =
+ (catch lines:t(atom)),
+ ?line true = code:delete(lines),
+ ?line false = code:purge(lines),
+ ?line {ok, {lines,BeamFile5D1}} = beam_lib:strip(BeamFile5D1),
+ ?line {module, lines} = code:load_abs(filename:rootname(BeamFile5D1)),
+ ?line {'EXIT',{badarith,[{lines,t,1,Info}|_]}} =
+ (catch lines:t(atom)),
+
?line true = (P0 == pps()),
?line NoOfTables = length(ets:all()),
?line delete_files([SourceD1, BeamFileD1,
Source2D1, BeamFile2D1,
Source3D1, BeamFile3D1,
- Source4D1, BeamFile4D1]),
+ Source4D1, BeamFile4D1,
+ Source5D1, BeamFile5D1]),
ok.
@@ -773,6 +786,12 @@ simple_file(File, Module, constant2) ->
"t(A) -> "
" {a,b,[2,3],x,y}. "]),
ok = file:write_file(File, B);
+simple_file(File, Module, lines) ->
+ B = list_to_binary(["-module(", atom_to_list(Module), ").\n"
+ "-export([t/1]).\n"
+ "t(A) ->\n"
+ " A+1.\n"]),
+ ok = file:write_file(File, B);
simple_file(File, Module, F) ->
B = list_to_binary(["-module(", atom_to_list(Module), "). "
"-export([t/0]). "
diff --git a/lib/stdlib/test/dets_SUITE.erl b/lib/stdlib/test/dets_SUITE.erl
index 698070368f..272a8d3950 100644
--- a/lib/stdlib/test/dets_SUITE.erl
+++ b/lib/stdlib/test/dets_SUITE.erl
@@ -1857,9 +1857,9 @@ fixtable(Config, Version) when is_list(Config) ->
?line {ok, _} = dets:open_file(T, Args),
%% badarg
- ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true],_}|_]}} =
(catch dets:safe_fixtable(no_table,true)),
- ?line {'EXIT', {badarg, [{dets,safe_fixtable,[T,undefined]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,safe_fixtable,[T,undefined],_}|_]}} =
(catch dets:safe_fixtable(T,undefined)),
%% The table is not allowed to grow while the elements are inserted:
@@ -1940,21 +1940,21 @@ match(Config, Version) ->
%% match, badarg
MSpec = [{'_',[],['$_']}],
- ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true],_}|_]}} =
(catch dets:match(no_table, '_')),
- ?line {'EXIT', {badarg, [{dets,match,[T,'_',not_a_number]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,match,[T,'_',not_a_number],_}|_]}} =
(catch dets:match(T, '_', not_a_number)),
?line {EC1, _} = dets:select(T, MSpec, 1),
- ?line {'EXIT', {badarg, [{dets,match,[EC1]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,match,[EC1],_}|_]}} =
(catch dets:match(EC1)),
%% match_object, badarg
- ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true],_}|_]}} =
(catch dets:match_object(no_table, '_')),
- ?line {'EXIT', {badarg, [{dets,match_object,[T,'_',not_a_number]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,match_object,[T,'_',not_a_number],_}|_]}} =
(catch dets:match_object(T, '_', not_a_number)),
?line {EC2, _} = dets:select(T, MSpec, 1),
- ?line {'EXIT', {badarg, [{dets,match_object,[EC2]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,match_object,[EC2],_}|_]}} =
(catch dets:match_object(EC2)),
dets:safe_fixtable(T, true),
@@ -2118,16 +2118,16 @@ select(Config, Version) ->
%% badarg
MSpec = [{'_',[],['$_']}],
- ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true],_}|_]}} =
(catch dets:select(no_table, MSpec)),
- ?line {'EXIT', {badarg, [{dets,select,[T,<<17>>]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,select,[T,<<17>>],_}|_]}} =
(catch dets:select(T, <<17>>)),
- ?line {'EXIT', {badarg, [{dets,select,[T,[]]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,select,[T,[]],_}|_]}} =
(catch dets:select(T, [])),
- ?line {'EXIT', {badarg, [{dets,select,[T,MSpec,not_a_number]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,select,[T,MSpec,not_a_number],_}|_]}} =
(catch dets:select(T, MSpec, not_a_number)),
?line {EC, _} = dets:match(T, '_', 1),
- ?line {'EXIT', {badarg, [{dets,select,[EC]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,select,[EC],_}|_]}} =
(catch dets:select(EC)),
AllSpec = [{'_',[],['$_']}],
@@ -2210,7 +2210,7 @@ update_counter(Config) when is_list(Config) ->
?line file:delete(Fname),
P0 = pps(),
- ?line {'EXIT', {badarg, [{dets,update_counter,[no_table,1,1]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,update_counter,[no_table,1,1],_}|_]}} =
(catch dets:update_counter(no_table, 1, 1)),
Args = [{file,Fname},{keypos,2}],
@@ -2254,65 +2254,66 @@ badarg(Config) when is_list(Config) ->
%% badargs are tested in match, select and fixtable too.
%% open
- ?line {'EXIT', {badarg, [{dets,open_file,[{a,tuple},[]]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,open_file,[{a,tuple},[]],_}|_]}} =
(catch dets:open_file({a,tuple},[])),
- ?line {'EXIT', {badarg, [{dets,open_file,[{a,tuple}]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,open_file,[{a,tuple}],_}|_]}} =
(catch dets:open_file({a,tuple})),
- ?line {'EXIT', {badarg, [{dets,open_file,[file,[foo]]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,open_file,[file,[foo]],_}|_]}} =
(catch dets:open_file(file,[foo])),
- ?line {'EXIT', {badarg,[{dets,open_file,[{hej,san},[{type,set}|3]]}|_]}} =
+ ?line {'EXIT', {badarg,[{dets,open_file,
+ [{hej,san},[{type,set}|3]],_}|_]}} =
(catch dets:open_file({hej,san},[{type,set}|3])),
%% insert
- ?line {'EXIT', {badarg, [{dets,insert,[no_table,{1,2}]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,insert,[no_table,{1,2}],_}|_]}} =
(catch dets:insert(no_table, {1,2})),
- ?line {'EXIT', {badarg, [{dets,insert,[no_table,[{1,2}]]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,insert,[no_table,[{1,2}]],_}|_]}} =
(catch dets:insert(no_table, [{1,2}])),
- ?line {'EXIT', {badarg, [{dets,insert,[T,{1,2}]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,insert,[T,{1,2}],_}|_]}} =
(catch dets:insert(T, {1,2})),
- ?line {'EXIT', {badarg, [{dets,insert,[T,[{1,2}]]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,insert,[T,[{1,2}]],_}|_]}} =
(catch dets:insert(T, [{1,2}])),
- ?line {'EXIT', {badarg, [{dets,insert,[T,[{1,2,3}|3]]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,insert,[T,[{1,2,3}|3]],_}|_]}} =
(catch dets:insert(T, [{1,2,3} | 3])),
%% lookup{_keys}
- ?line {'EXIT', {badarg, [{dets,lookup_keys,[badarg,[]]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,lookup_keys,[badarg,[]],_}|_]}} =
(catch dets:lookup_keys(T, [])),
- ?line {'EXIT', {badarg, [{dets,lookup,[no_table,1]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,lookup,[no_table,1],_}|_]}} =
(catch dets:lookup(no_table, 1)),
- ?line {'EXIT', {badarg, [{dets,lookup_keys,[T,[1|2]]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,lookup_keys,[T,[1|2]],_}|_]}} =
(catch dets:lookup_keys(T, [1 | 2])),
%% member
- ?line {'EXIT', {badarg, [{dets,member,[no_table,1]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,member,[no_table,1],_}|_]}} =
(catch dets:member(no_table, 1)),
%% sync
- ?line {'EXIT', {badarg, [{dets,sync,[no_table]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,sync,[no_table],_}|_]}} =
(catch dets:sync(no_table)),
%% delete{_keys}
- ?line {'EXIT', {badarg, [{dets,delete,[no_table,1]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,delete,[no_table,1],_}|_]}} =
(catch dets:delete(no_table, 1)),
%% delete_object
- ?line {'EXIT', {badarg, [{dets,delete_object,[no_table,{1,2,3}]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,delete_object,[no_table,{1,2,3}],_}|_]}} =
(catch dets:delete_object(no_table, {1,2,3})),
- ?line {'EXIT', {badarg, [{dets,delete_object,[T,{1,2}]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,delete_object,[T,{1,2}],_}|_]}} =
(catch dets:delete_object(T, {1,2})),
- ?line {'EXIT', {badarg, [{dets,delete_object,[no_table,[{1,2,3}]]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,delete_object,[no_table,[{1,2,3}]],_}|_]}} =
(catch dets:delete_object(no_table, [{1,2,3}])),
- ?line {'EXIT', {badarg, [{dets,delete_object,[T,[{1,2}]]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,delete_object,[T,[{1,2}]],_}|_]}} =
(catch dets:delete_object(T, [{1,2}])),
- ?line {'EXIT', {badarg, [{dets,delete_object,[T,[{1,2,3}|3]]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,delete_object,[T,[{1,2,3}|3]],_}|_]}} =
(catch dets:delete_object(T, [{1,2,3} | 3])),
%% first,next,slot
- ?line {'EXIT', {badarg, [{dets,first,[no_table]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,first,[no_table],_}|_]}} =
(catch dets:first(no_table)),
- ?line {'EXIT', {badarg, [{dets,next,[no_table,1]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,next,[no_table,1],_}|_]}} =
(catch dets:next(no_table, 1)),
- ?line {'EXIT', {badarg, [{dets,slot,[no_table,0]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,slot,[no_table,0],_}|_]}} =
(catch dets:slot(no_table, 0)),
%% info
@@ -2321,26 +2322,26 @@ badarg(Config) when is_list(Config) ->
?line undefined = dets:info(T, foo),
%% match_delete
- ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true],_}|_]}} =
(catch dets:match_delete(no_table, '_')),
%% delete_all_objects
- ?line {'EXIT', {badarg, [{dets,delete_all_objects,[no_table]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,delete_all_objects,[no_table],_}|_]}} =
(catch dets:delete_all_objects(no_table)),
%% select_delete
MSpec = [{'_',[],['$_']}],
- ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true],_}|_]}} =
(catch dets:select_delete(no_table, MSpec)),
- ?line {'EXIT', {badarg, [{dets,select_delete,[T, <<17>>]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,select_delete,[T, <<17>>],_}|_]}} =
(catch dets:select_delete(T, <<17>>)),
%% traverse, fold
- ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true],_}|_]}} =
(catch dets:traverse(no_table, fun(_) -> continue end)),
- ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true],_}|_]}} =
(catch dets:foldl(fun(_, A) -> A end, [], no_table)),
- ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true]}|_]}} =
+ ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true],_}|_]}} =
(catch dets:foldr(fun(_, A) -> A end, [], no_table)),
%% close
@@ -2349,14 +2350,14 @@ badarg(Config) when is_list(Config) ->
?line {error, not_owner} = dets:close(T),
%% init_table
- ?line {'EXIT', {badarg,[{dets,init_table,[no_table,_,[]]}|_]}} =
+ ?line {'EXIT', {badarg,[{dets,init_table,[no_table,_,[]],_}|_]}} =
(catch dets:init_table(no_table, fun(X) -> X end)),
- ?line {'EXIT', {badarg,[{dets,init_table,[no_table,_,[]]}|_]}} =
+ ?line {'EXIT', {badarg,[{dets,init_table,[no_table,_,[]],_}|_]}} =
(catch dets:init_table(no_table, fun(X) -> X end, [])),
%% from_ets
Ets = ets:new(ets,[]),
- ?line {'EXIT', {badarg,[{dets,from_ets,[no_table,_]}|_]}} =
+ ?line {'EXIT', {badarg,[{dets,from_ets,[no_table,_],_}|_]}} =
(catch dets:from_ets(no_table, Ets)),
ets:delete(Ets),
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index 9341300f90..02e97fb3a8 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -795,16 +795,16 @@ t_ets_dets(Config, Opts) ->
?line true = ets:from_dets(ETab,DTab),
?line 3000 = ets:info(ETab,size),
?line ets:delete(ETab),
- ?line {'EXIT',{badarg,[{ets,to_dets,[ETab,DTab]}|_]}} =
+ ?line {'EXIT',{badarg,[{ets,to_dets,[ETab,DTab],_}|_]}} =
(catch ets:to_dets(ETab,DTab)),
- ?line {'EXIT',{badarg,[{ets,from_dets,[ETab,DTab]}|_]}} =
+ ?line {'EXIT',{badarg,[{ets,from_dets,[ETab,DTab],_}|_]}} =
(catch ets:from_dets(ETab,DTab)),
?line ETab2 = ets_new(x,Opts),
?line filltabint(ETab2,3000),
?line dets:close(DTab),
- ?line {'EXIT',{badarg,[{ets,to_dets,[ETab2,DTab]}|_]}} =
+ ?line {'EXIT',{badarg,[{ets,to_dets,[ETab2,DTab],_}|_]}} =
(catch ets:to_dets(ETab2,DTab)),
- ?line {'EXIT',{badarg,[{ets,from_dets,[ETab2,DTab]}|_]}} =
+ ?line {'EXIT',{badarg,[{ets,from_dets,[ETab2,DTab],_}|_]}} =
(catch ets:from_dets(ETab2,DTab)),
?line ets:delete(ETab2),
?line (catch file:delete(Fname)),
@@ -2644,7 +2644,7 @@ maybe_sort(L) when is_list(L) ->
%maybe_sort({'EXIT',{Reason, [{Module, Function, _}|_]}}) ->
% {'EXIT',{Reason, [{Module, Function, '_'}]}};
maybe_sort({'EXIT',{Reason, List}}) when is_list(List) ->
- {'EXIT',{Reason, lists:map(fun({Module, Function, _}) ->
+ {'EXIT',{Reason, lists:map(fun({Module, Function, _, _}) ->
{Module, Function, '_'}
end,
List)}};
diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl
index a355097fe2..dc4563967c 100644
--- a/lib/stdlib/test/filelib_SUITE.erl
+++ b/lib/stdlib/test/filelib_SUITE.erl
@@ -97,11 +97,12 @@ wildcard_errors(Config) when is_list(Config) ->
wcc(Wc, Error) ->
{'EXIT',{{badpattern,Error},
- [{filelib,compile_wildcard,1}|_]}} = (catch filelib:compile_wildcard(Wc)),
+ [{filelib,compile_wildcard,1,_}|_]}} =
+ (catch filelib:compile_wildcard(Wc)),
{'EXIT',{{badpattern,Error},
- [{filelib,wildcard,1}|_]}} = (catch filelib:wildcard(Wc)),
+ [{filelib,wildcard,1,_}|_]}} = (catch filelib:wildcard(Wc)),
{'EXIT',{{badpattern,Error},
- [{filelib,wildcard,2}|_]}} = (catch filelib:wildcard(Wc, ".")).
+ [{filelib,wildcard,2,_}|_]}} = (catch filelib:wildcard(Wc, ".")).
do_wildcard_1(Dir, Wcf0) ->
do_wildcard_2(Dir, Wcf0),
diff --git a/lib/stdlib/test/proc_lib_SUITE.erl b/lib/stdlib/test/proc_lib_SUITE.erl
index 1565aa9bba..c95089117c 100644
--- a/lib/stdlib/test/proc_lib_SUITE.erl
+++ b/lib/stdlib/test/proc_lib_SUITE.erl
@@ -328,7 +328,7 @@ otp_6345(doc) ->
["'monitor' spawn_opt option"];
otp_6345(Config) when is_list(Config) ->
Opts = [link,monitor],
- {'EXIT', {badarg,[{proc_lib,check_for_monitor,_}|_Stack]}} =
+ {'EXIT', {badarg,[{proc_lib,check_for_monitor,_,_}|_Stack]}} =
(catch proc_lib:start(?MODULE, otp_6345_init, [self()],
1000, Opts)),
ok.
diff --git a/lib/stdlib/test/re_SUITE.erl b/lib/stdlib/test/re_SUITE.erl
index c4817c0d38..3b2e637c84 100644
--- a/lib/stdlib/test/re_SUITE.erl
+++ b/lib/stdlib/test/re_SUITE.erl
@@ -454,115 +454,115 @@ error_handling(Config) when is_list(Config) ->
% The malformed precomiled RE is detected after
% the trap to re:grun from grun, in the grun function clause
% that handles precompiled expressions
- ?line {'EXIT',{badarg,[{re,run,["apa",{1,2,3,4},[global]]},
- {?MODULE, error_handling,1} | _]}} =
+ ?line {'EXIT',{badarg,[{re,run,["apa",{1,2,3,4},[global]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:run("apa",{1,2,3,4},[global])),
% An invalid capture list will also cause a badarg late,
% but with a non pre compiled RE, the exception should be thrown by the
% grun function clause that handles RE's compiled implicitly by
% the run/3 BIF before trapping.
- ?line {'EXIT',{badarg,[{re,run,["apa","p",[{capture,[1,{a}]},global]]},
- {?MODULE, error_handling,1} | _]}} =
+ ?line {'EXIT',{badarg,[{re,run,["apa","p",[{capture,[1,{a}]},global]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:run("apa","p",[{capture,[1,{a}]},global])),
% And so the case of a precompiled expression together with
% a compile-option (binary and list subject):
?line {ok,RE} = re:compile("(p)"),
?line {match,[[{1,1},{1,1}]]} = re:run(<<"apa">>,RE,[global]),
?line {match,[[{1,1},{1,1}]]} = re:run("apa",RE,[global]),
- {'EXIT',{badarg,[{re,run,
- [<<"apa">>,
- {re_pattern,1,0,_},
- [global,unicode]]},
- {?MODULE, error_handling,1} | _]}} =
+ ?line {'EXIT',{badarg,[{re,run,
+ [<<"apa">>,
+ {re_pattern,1,0,_},
+ [global,unicode]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:run(<<"apa">>,RE,[global,unicode])),
- {'EXIT',{badarg,[{re,run,
- ["apa",
- {re_pattern,1,0,_},
- [global,unicode]]},
- {?MODULE, error_handling,1} | _]}} =
+ ?line {'EXIT',{badarg,[{re,run,
+ ["apa",
+ {re_pattern,1,0,_},
+ [global,unicode]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:run("apa",RE,[global,unicode])),
?line {'EXIT',{badarg,_}} = (catch re:run("apa","(p",[])),
?line {'EXIT',{badarg,_}} = (catch re:run("apa","(p",[global])),
% The replace errors:
- ?line {'EXIT',{badarg,[{re,replace,["apa",{1,2,3,4},"X",[]]},
- {?MODULE, error_handling,1} | _]}} =
+ ?line {'EXIT',{badarg,[{re,replace,["apa",{1,2,3,4},"X",[]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:replace("apa",{1,2,3,4},"X",[])),
- ?line {'EXIT',{badarg,[{re,replace,["apa",{1,2,3,4},"X",[global]]},
- {?MODULE, error_handling,1} | _]}} =
+ ?line {'EXIT',{badarg,[{re,replace,["apa",{1,2,3,4},"X",[global]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:replace("apa",{1,2,3,4},"X",[global])),
?line {'EXIT',{badarg,[{re,replace,
["apa",
{re_pattern,1,0,_},
"X",
- [unicode]]},
- {?MODULE, error_handling,1} | _]}} =
+ [unicode]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:replace("apa",RE,"X",[unicode])),
?line <<"aXa">> = iolist_to_binary(re:replace("apa","p","X",[])),
?line {'EXIT',{badarg,[{re,replace,
- ["apa","p","X",[{capture,all,binary}]]},
- {?MODULE, error_handling,1} | _]}} =
+ ["apa","p","X",[{capture,all,binary}]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch iolist_to_binary(re:replace("apa","p","X",
[{capture,all,binary}]))),
?line {'EXIT',{badarg,[{re,replace,
- ["apa","p","X",[{capture,all}]]},
- {?MODULE, error_handling,1} | _]}} =
+ ["apa","p","X",[{capture,all}]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch iolist_to_binary(re:replace("apa","p","X",
[{capture,all}]))),
?line {'EXIT',{badarg,[{re,replace,
- ["apa","p","X",[{return,banana}]]},
- {?MODULE, error_handling,1} | _]}} =
+ ["apa","p","X",[{return,banana}]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch iolist_to_binary(re:replace("apa","p","X",
[{return,banana}]))),
?line {'EXIT',{badarg,_}} = (catch re:replace("apa","(p","X",[])),
% Badarg, not compile error.
?line {'EXIT',{badarg,[{re,replace,
- ["apa","(p","X",[{return,banana}]]},
- {?MODULE, error_handling,1} | _]}} =
+ ["apa","(p","X",[{return,banana}]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch iolist_to_binary(re:replace("apa","(p","X",
[{return,banana}]))),
% And the split errors:
?line [<<"a">>,<<"a">>] = (catch re:split("apa","p",[])),
?line [<<"a">>,<<"p">>,<<"a">>] = (catch re:split("apa",RE,[])),
- ?line {'EXIT',{badarg,[{re,split,["apa","p",[global]]},
- {?MODULE, error_handling,1} | _]}} =
+ ?line {'EXIT',{badarg,[{re,split,["apa","p",[global]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:split("apa","p",[global])),
- ?line {'EXIT',{badarg,[{re,split,["apa","p",[{capture,all}]]},
- {?MODULE, error_handling,1} | _]}} =
+ ?line {'EXIT',{badarg,[{re,split,["apa","p",[{capture,all}]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:split("apa","p",[{capture,all}])),
- ?line {'EXIT',{badarg,[{re,split,["apa","p",[{capture,all,binary}]]},
- {?MODULE, error_handling,1} | _]}} =
+ ?line {'EXIT',{badarg,[{re,split,["apa","p",[{capture,all,binary}]],_},
+ {?MODULE, error_handling,1,_} | _]}} =
(catch re:split("apa","p",[{capture,all,binary}])),
- ?line {'EXIT',{badarg,[{re,split,["apa",{1,2,3,4},[]]},
- {?MODULE, error_handling,1} | _]}} =
+ ?line {'EXIT',{badarg,[{re,split,["apa",{1,2,3,4},[]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:split("apa",{1,2,3,4})),
- ?line {'EXIT',{badarg,[{re,split,["apa",{1,2,3,4},[]]},
- {?MODULE, error_handling,1} | _]}} =
+ ?line {'EXIT',{badarg,[{re,split,["apa",{1,2,3,4},[]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:split("apa",{1,2,3,4},[])),
?line {'EXIT',{badarg,[{re,split,
["apa",
RE,
- [unicode]]},
- {?MODULE, error_handling,1} | _]}} =
+ [unicode]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:split("apa",RE,[unicode])),
?line {'EXIT',{badarg,[{re,split,
["apa",
RE,
- [{return,banana}]]},
- {?MODULE, error_handling,1} | _]}} =
+ [{return,banana}]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:split("apa",RE,[{return,banana}])),
?line {'EXIT',{badarg,[{re,split,
["apa",
RE,
- [banana]]},
- {?MODULE, error_handling,1} | _]}} =
+ [banana]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:split("apa",RE,[banana])),
?line {'EXIT',{badarg,_}} = (catch re:split("apa","(p")),
%Exception on bad argument, not compilation error
?line {'EXIT',{badarg,[{re,split,
["apa",
"(p",
- [banana]]},
- {?MODULE, error_handling,1} | _]}} =
+ [banana]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:split("apa","(p",[banana])),
?t:timetrap_cancel(Dog),
ok.
diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl
index 8273377ba1..b6019b86f0 100644
--- a/lib/stdlib/test/shell_SUITE.erl
+++ b/lib/stdlib/test/shell_SUITE.erl
@@ -2388,12 +2388,12 @@ otp_6554(Config) when is_list(Config) ->
comm_err(<<"V = lists:seq(1, 20), case V of a -> ok end.">>),
?line "exception error: no function clause matching" =
comm_err(<<"fun(P) when is_pid(P) -> true end(a).">>),
- ?line "exception error: {function_clause,[{erl_eval,do_apply,[unproper|list]}"++_ =
+ ?line "exception error: {function_clause," =
comm_err(<<"erlang:error(function_clause, [unproper | list]).">>),
?line "exception error: function_clause" =
comm_err(<<"erlang:error(function_clause, 4).">>),
%% Cheating:
- ?line "exception error: no function clause matching erl_eval:do_apply(4)" =
+ ?line "exception error: no function clause matching erl_eval:do_apply(4)" ++ _ =
comm_err(<<"erlang:error(function_clause, [4]).">>),
?line "exception error: no function clause matching" ++ _ =
comm_err(<<"fun(a, b, c, d) -> foo end"
@@ -2406,7 +2406,7 @@ otp_6554(Config) when is_list(Config) ->
comm_err(<<"fun(P, q) when is_pid(P) -> true end(a, b).">>),
?line "exception error: no function clause matching lists:reverse(" ++ _ =
comm_err(<<"F=fun() -> hello end, lists:reverse(F).">>),
- ?line "exception error: no function clause matching lists:reverse(34)" =
+ ?line "exception error: no function clause matching lists:reverse(34) (lists.erl, line " ++ _ =
comm_err(<<"lists:reverse(34).">>),
?line "exception error: no true branch found when evaluating an if expression" =
comm_err(<<"if length([a,b]) > 17 -> a end.">>),
diff --git a/lib/stdlib/test/sofs_SUITE.erl b/lib/stdlib/test/sofs_SUITE.erl
index d6f88a655e..73b282149a 100644
--- a/lib/stdlib/test/sofs_SUITE.erl
+++ b/lib/stdlib/test/sofs_SUITE.erl
@@ -1879,11 +1879,11 @@ digraph(Conf) when is_list(Conf) ->
?line {'EXIT', {badarg, _}} =
(catch family_to_digraph(set([a]))),
- ?line {'EXIT', {badarg, [{sofs,family_to_digraph,[_,_]}|_]}} =
+ ?line {'EXIT', {badarg, [{sofs,family_to_digraph,[_,_],_}|_]}} =
(catch family_to_digraph(set([a]), [foo])),
- ?line {'EXIT', {badarg, [{sofs,family_to_digraph,[_,_]}|_]}} =
+ ?line {'EXIT', {badarg, [{sofs,family_to_digraph,[_,_],_}|_]}} =
(catch family_to_digraph(F, [foo])),
- ?line {'EXIT', {cyclic, [{sofs,family_to_digraph,[_,_]}|_]}} =
+ ?line {'EXIT', {cyclic, [{sofs,family_to_digraph,[_,_],_}|_]}} =
(catch family_to_digraph(family([{a,[a]}]),[acyclic])),
?line G1 = family_to_digraph(E),